diff --git a/NAMESPACE b/NAMESPACE index 67ed9b53..8bbd1724 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -7,12 +7,14 @@ export(createLink) export(create_toxEval) export(endPointInfo) export(endpoint_hits) -export(endpoint_table) +export(endpoint_hits_DT) export(explore_endpoints) export(filter_groups) export(get_ACC) export(get_chemical_summary) export(graph_chem_data) +export(hits_by_groupings) +export(hits_by_groupings_DT) export(hits_summary) export(hits_summary_DT) export(make_tox_map) @@ -26,8 +28,6 @@ export(plot_tox_stacks) export(rank_sites) export(rank_sites_DT) export(remove_flags) -export(table_endpoint_hits) -export(table_tox_endpoint) export(tox_boxplot_data) export(tox_chemicals) import(DT) diff --git a/R/table_endpoint_hits.R b/R/endpoint_hits.R similarity index 61% rename from R/table_endpoint_hits.R rename to R/endpoint_hits.R index d5a7e968..0e82dd62 100644 --- a/R/table_endpoint_hits.R +++ b/R/endpoint_hits.R @@ -1,13 +1,20 @@ -#' table_endpoint_hits +#' Rank endpoints by category +#' +#' These functions create a table with one row per endPoint, and one +#' column per category("Biological", "Chemical", or "Chemical Class"). +#' The values in the table are number of sites with hits in that endpoint/category +#' combination, based on a user-specified threshold (defined by hit_threshold). +#' +#' The tables show slightly different results for a single site. Instead of the +#' number of sites with hits above a threshold, it is now the number of samples with hits. #' -#' Table of ranks #' @param chemicalSummary data frame from \code{get_chemical_summary} #' @param mean_logic logical \code{TRUE} is mean, \code{FALSE} is maximum #' @param category either "Biological", "Chemical Class", or "Chemical" #' @param hit_threshold numeric threshold defining a "hit" #' @export #' @import DT -#' @rdname table_endpoint_hits +#' @rdname endpoint_hits_DT #' @importFrom stats median #' @importFrom tidyr spread unite #' @importFrom dplyr full_join filter mutate select left_join right_join @@ -28,11 +35,11 @@ #' chemicalSummary <- get_chemical_summary(tox_list, ACClong, filtered_ep) #' #' hits_df <- endpoint_hits(chemicalSummary, category = "Biological") -#' table_endpoint_hits(chemicalSummary, category = "Biological") -#' table_endpoint_hits(chemicalSummary, category = "Chemical Class") -#' table_endpoint_hits(chemicalSummary, category = "Chemical") +#' endpoint_hits_DT(chemicalSummary, category = "Biological") +#' endpoint_hits_DT(chemicalSummary, category = "Chemical Class") +#' endpoint_hits_DT(chemicalSummary, category = "Chemical") #' } -table_endpoint_hits <- function(chemicalSummary, +endpoint_hits_DT <- function(chemicalSummary, category = "Biological", mean_logic = FALSE, hit_threshold = 0.1){ @@ -45,35 +52,72 @@ table_endpoint_hits <- function(chemicalSummary, hit_threshold = hit_threshold) if(category == "Chemical"){ + orig_names <- names(fullData) + casKey <- select(chemicalSummary, chnm, CAS) %>% distinct() - + + numeric_hits <- fullData hits <- sapply(fullData, function(x) as.character(x)) for(k in 1:nrow(fullData)){ for(z in 2:ncol(fullData)){ if(!is.na(fullData[k,z])){ - hits[k,z] <- createLink(cas = casKey$CAS[casKey$chnm == names(fullData)[z]], - endpoint = fullData[k,1], - hits = fullData[k,z]) + if(fullData[k,z] < 10){ + hit_char <- paste0("0",fullData[k,z]) + } else{ + hit_char <- as.character(fullData[k,z]) + } + hits[k,z] <- paste(hit_char,createLink(cas = casKey$CAS[casKey$chnm == names(fullData)[z]], + endpoint = fullData[k,1])) } } } - fullData <- hits + fullData <- data.frame(hits, stringsAsFactors = FALSE) + names(fullData) <- orig_names + } + + n <- ncol(fullData)-1 + + if(n > 20 & n<30){ + colors <- c(brewer.pal(n = 12, name = "Set3"), + brewer.pal(n = 8, name = "Set2"), + brewer.pal(n = max(c(3,n-20)), name = "Set1")) + } else if (n <= 20){ + colors <- c(brewer.pal(n = 12, name = "Set3"), + brewer.pal(n = max(c(3,n-12)), name = "Set2")) + } else { + colors <- colorRampPalette(brewer.pal(11,"Spectral"))(n) } - fullData <- DT::datatable(fullData, extensions = 'Buttons', + fullData_dt <- DT::datatable(fullData, extensions = 'Buttons', escape = FALSE, rownames = FALSE, options = list(dom = 'Bfrtip', buttons = list('colvis'), scrollX = TRUE, - order=list(list(2,'desc')))) - return(fullData) + order=list(list(1,'desc')))) + + for(i in 2:ncol(fullData)){ + fullData_dt <- formatStyle(fullData_dt, + names(fullData)[i], + backgroundColor = colors[i]) + + if(category != "Chemical"){ + fullData_dt <- formatStyle(fullData_dt, names(fullData)[i], + background = styleColorBar(range(fullData[,names(fullData)[i]],na.rm = TRUE), 'goldenrod'), + backgroundSize = '100% 90%', + backgroundRepeat = 'no-repeat', + backgroundPosition = 'center' ) + } + + } + + return(fullData_dt) } -#' @rdname table_endpoint_hits +#' @rdname endpoint_hits_DT #' @export endpoint_hits <- function(chemicalSummary, category = "Biological", @@ -112,9 +156,7 @@ endpoint_hits <- function(chemicalSummary, group_by(category, endPoint, date) %>% summarize(sumEAR = sum(EAR)) %>% group_by(category, endPoint) %>% - summarize(meanEAR = ifelse(mean_logic, mean(sumEAR),max(sumEAR))) %>% - group_by(category, endPoint) %>% - summarize(nSites = sum(meanEAR > hit_threshold)) %>% + summarise(nSites = sum(sumEAR > hit_threshold)) %>% spread(category, nSites) } @@ -143,6 +185,6 @@ endpoint_hits <- function(chemicalSummary, #' @param hits character #' @export #' @keywords internal -createLink <- function(cas, endpoint, hits) { - paste0('',hits,'') +createLink <- function(cas, endpoint) { + paste0('') } \ No newline at end of file diff --git a/R/table_tox_endpoint.R b/R/hits_by_groupings.R similarity index 78% rename from R/table_tox_endpoint.R rename to R/hits_by_groupings.R index 1fdbcbc4..d84f03b8 100644 --- a/R/table_tox_endpoint.R +++ b/R/hits_by_groupings.R @@ -1,12 +1,21 @@ -#' rank_sites_DT +#' Biological hits per category +#' +#' These functions create a table with one row per category("Biological", +#' "Chemical", or "Chemical Class"). The columns are always the "Biological" +#' groupings. The values in the table are how many sites have hits (based on +#' hit_threshold), for that particular "Biological"/category combination. Note, +#' if the user chooses "Biological", it is a simple 2-column table of +#' "Biological" groupings and number of sites (nSites). +#' +#' The tables show slightly different results for a single site, showing the +#' number of samples with hits (instead of number of sites). #' -#' Table of ranks #' @param chemicalSummary data frame from \code{get_chemical_summary} #' @param mean_logic logical \code{TRUE} is mean, \code{FALSE} is maximum #' @param category either "Biological", "Chemical Class", or "Chemical" #' @param hit_threshold numeric threshold defining a "hit" #' @export -#' @rdname table_tox_endpoint +#' @rdname hits_by_groupings_DT #' @import DT #' @importFrom stats median #' @importFrom tidyr spread unite @@ -27,12 +36,12 @@ #' filtered_ep <- filter_groups(cleaned_ep) #' chemicalSummary <- get_chemical_summary(tox_list, ACClong, filtered_ep) #' -#' site_df <- endpoint_table(chemicalSummary, category = "Biological") -#' table_tox_endpoint(chemicalSummary, category = "Biological") -#' table_tox_endpoint(chemicalSummary, category = "Chemical Class") -#' table_tox_endpoint(chemicalSummary, category = "Chemical") +#' site_df <- hits_by_groupings(chemicalSummary, category = "Biological") +#' hits_by_groupings_DT(chemicalSummary, category = "Biological") +#' hits_by_groupings_DT(chemicalSummary, category = "Chemical Class") +#' hits_by_groupings_DT(chemicalSummary, category = "Chemical") #' } -table_tox_endpoint <- function(chemicalSummary, +hits_by_groupings_DT <- function(chemicalSummary, category = "Biological", mean_logic = FALSE, hit_threshold = 0.1){ @@ -40,7 +49,7 @@ table_tox_endpoint <- function(chemicalSummary, match.arg(category, c("Biological","Chemical Class","Chemical")) - tableData <- endpoint_table(chemicalSummary=chemicalSummary, + tableData <- hits_by_groupings(chemicalSummary=chemicalSummary, category = category, mean_logic = mean_logic, hit_threshold = hit_threshold) @@ -68,8 +77,8 @@ table_tox_endpoint <- function(chemicalSummary, } #' @export -#' @rdname table_tox_endpoint -endpoint_table <- function(chemicalSummary, category, mean_logic=FALSE, hit_threshold = 0.1){ +#' @rdname hits_by_groupings_DT +hits_by_groupings <- function(chemicalSummary, category, mean_logic=FALSE, hit_threshold = 0.1){ Bio_category <- Class <- EAR <- sumEAR <- value <- calc <- chnm <- choice_calc <- n <- nHits <- site <- ".dplyr" meanEAR <- nSites <- ".dplyr" diff --git a/R/table_tox_sum.R b/R/hits_summary.R similarity index 77% rename from R/table_tox_sum.R rename to R/hits_summary.R index cb90cd6c..76440ab9 100644 --- a/R/table_tox_sum.R +++ b/R/hits_summary.R @@ -1,6 +1,17 @@ -#' hits_summary_DT +#' Summary of hits per site/category +#' +#' These functions create a table with several rows per site depending on which +#' categories get hits. A "hit" is based on a user specified hit_threshold. For example, +#' if "Biological" is the category, and a site has hits above a threshold for +#' "DNA Binding" and "Nuclear Receptors", that site will have 2 rows of data in this table. +#' +#' For each row, there are 4 columns. Site and category (as defined by the category argument) +#' define the row. "Hits per Sample" are how many samples at that site had hits (based on +#' hit_threshold) for the category. "Number of Samples" is number of samples. +#' +#' The tables show slightly different results for a single site. Instead of one row per +#' site/category, there is one row per category. #' -#' Table of sums #' @param chemicalSummary data frame from \code{get_chemical_summary} #' @param mean_logic logical \code{TRUE} is mean, \code{FALSE} is maximum #' @param category either "Biological", "Chemical Class", or "Chemical" @@ -37,7 +48,8 @@ hits_summary_DT <- function(chemicalSummary, mean_logic = FALSE, hit_threshold = 0.1){ - chnm <- Class <- Bio_category <- site <- EAR <- sumEAR <- hits <- n <- ".dplyr" + chnm <- Class <- Bio_category <- site <- EAR <- sumEAR <- hits <- n <- `Samples with + hits` <- ".dplyr" match.arg(category, c("Biological","Chemical Class","Chemical")) @@ -58,12 +70,6 @@ hits_summary_DT <- function(chemicalSummary, dom = 'Bfrtip', buttons = list('colvis'))) - # tableGroup <- formatStyle(tableGroup, names(hits_summaryOrdered)[maxChem], - # background = styleColorBar(range(hits_summaryOrdered[,maxChem],na.rm=TRUE), 'goldenrod'), - # backgroundSize = '100% 90%', - # backgroundRepeat = 'no-repeat', - # backgroundPosition = 'center' ) - tableGroup <- formatStyle(tableGroup, names(hits_summaryOrdered)[meanChem], background = styleColorBar(range(hits_summaryOrdered[,meanChem],na.rm=TRUE), 'wheat'), backgroundSize = '100% 90%', @@ -80,7 +86,7 @@ hits_summary_DT <- function(chemicalSummary, hits_summary <- function(chemicalSummary, category, hit_threshold = 0.1, mean_logic = FALSE){ - Class <- Bio_category <- `Hits per Sample` <- site <- EAR <- sumEAR <- chnm <- n <- hits <- ".dplyr" + Class <- Bio_category <- `Samples with hits` <- nSamples <- site <- EAR <- sumEAR <- chnm <- n <- hits <- ".dplyr" siteToFind <- unique(chemicalSummary$site) @@ -109,5 +115,11 @@ hits_summary <- function(chemicalSummary, category, nSamples = n()) %>% arrange(desc(`Samples with hits`)) + if(length(siteToFind) == 1){ + hits_summary <- hits_summary[,c("category","Samples with hits","nSamples")] + } + + hits_summary <- rename(hits_summary, `Number of Samples`=nSamples) + return(hits_summary) } \ No newline at end of file diff --git a/R/plot_chemical_boxplots.R b/R/plot_chemical_boxplots.R index 259272b0..d5a81d55 100644 --- a/R/plot_chemical_boxplots.R +++ b/R/plot_chemical_boxplots.R @@ -6,7 +6,9 @@ plot_chemical_boxplots <- function(chemicalSummary, mean_logic = FALSE, plot_ND = TRUE, font_size = NA, - title = NA){ + title = NA, + pallette = NA, + hit_threshold = NA){ site <- EAR <- sumEAR <- meanEAR <- groupCol <- nonZero <- ".dplyr" chnm <- Class <- maxEAR <- x <- y <- ".dplyr" @@ -41,13 +43,25 @@ plot_chemical_boxplots <- function(chemicalSummary, countNonZero <- chemicalSummary %>% select(chnm, Class, EAR) %>% group_by(chnm, Class) %>% - summarize(nonZero = as.character(sum(EAR>0))) + summarize(nonZero = as.character(sum(EAR>0)), + hits = as.character(sum(EAR > hit_threshold))) + + countNonZero$hits[countNonZero$hits == "0"] <- "" label <- "# Endpoints" - toxPlot_All <- ggplot(data=chemicalSummary) + - geom_boxplot(aes(x=chnm, y=EAR, fill=Class), - lwd=0.1,outlier.size=1) + toxPlot_All <- ggplot(data=chemicalSummary) + + if(!all(is.na(pallette))){ + toxPlot_All <- toxPlot_All + + geom_boxplot(aes(x=chnm, y=EAR, fill=chnm),lwd=0.1,outlier.size=1) + + scale_fill_manual(values = pallette) + + theme(legend.position = "none") + } else { + toxPlot_All <- toxPlot_All + + geom_boxplot(aes(x=chnm, y=EAR, fill=Class), + lwd=0.1,outlier.size=1) + } } else { graphData <- graph_chem_data(chemicalSummary=chemicalSummary, @@ -57,12 +71,25 @@ plot_chemical_boxplots <- function(chemicalSummary, countNonZero <- graphData %>% select(chnm, Class, maxEAR) %>% group_by(chnm, Class) %>% - summarize(nonZero = as.character(sum(maxEAR>0))) + summarize(nonZero = as.character(sum(maxEAR>0)), + hits = as.character(sum(maxEAR > hit_threshold))) + + countNonZero$hits[countNonZero$hits == "0"] <- "" label <- "# Sites" - toxPlot_All <- ggplot(data=graphData) + - geom_boxplot(aes(x=chnm, y=maxEAR, fill=Class), - lwd=0.1,outlier.size=1) + toxPlot_All <- ggplot(data=graphData) + + if(!all(is.na(pallette))){ + toxPlot_All <- toxPlot_All + + geom_boxplot(aes(x=chnm, y=maxEAR, fill=chnm),lwd=0.1,outlier.size=1) + + scale_fill_manual(values = pallette) + + theme(legend.position = "none") + } else { + toxPlot_All <- toxPlot_All + + geom_boxplot(aes(x=chnm, y=maxEAR, fill=Class), + lwd=0.1,outlier.size=1) + } + } toxPlot_All <- toxPlot_All + @@ -70,6 +97,7 @@ plot_chemical_boxplots <- function(chemicalSummary, theme_bw() + scale_x_discrete(drop = TRUE) + coord_flip() + + geom_hline(yintercept = hit_threshold, linetype="dashed", color="black") + theme(axis.text = element_text( color = "black"), axis.title=element_blank(), panel.background = element_blank(), @@ -77,14 +105,19 @@ plot_chemical_boxplots <- function(chemicalSummary, strip.background = element_rect(fill = "transparent",colour = NA), strip.text.y = element_blank(), panel.border = element_blank(), - axis.ticks = element_blank()) + - guides(fill=guide_legend(ncol=6)) + - theme(legend.position="bottom", - legend.justification = "left", - legend.background = element_rect(fill = "transparent", colour = "transparent"), - legend.title=element_blank(), - legend.key.height = unit(1,"line")) + - scale_fill_manual(values = cbValues, drop=FALSE) + axis.ticks = element_blank()) + + if(all(is.na(pallette))){ + toxPlot_All <- toxPlot_All + + scale_fill_manual(values = cbValues, drop=FALSE) + + guides(fill=guide_legend(ncol=6)) + + theme(legend.position="bottom", + legend.justification = "left", + legend.background = element_rect(fill = "transparent", colour = "transparent"), + legend.title=element_blank(), + legend.key.height = unit(1,"line")) + } + if(!is.na(font_size)){ toxPlot_All <- toxPlot_All + @@ -96,8 +129,10 @@ plot_chemical_boxplots <- function(chemicalSummary, if(packageVersion("ggplot2") >= "2.2.1.9000"){ ymin <- 10^(layout_stuff$panel_scales_y[[1]]$range$range[1]) + ymax <- 10^(layout_stuff$panel_scales_y[[1]]$range$range[2]) } else { ymin <- 10^(layout_stuff$panel_ranges[[1]]$x.range[1]) + ymax <- 10^(layout_stuff$panel_ranges[[1]]$x.range[2]) } toxPlot_All_withLabels <- toxPlot_All + @@ -106,6 +141,16 @@ plot_chemical_boxplots <- function(chemicalSummary, aes(x=x, y=y, label = label), size=ifelse(is.na(font_size),3,0.30*font_size)) + nHitsEP <- countNonZero$hits + + if(isTRUE(sum(as.numeric(nHitsEP), na.rm = TRUE) > 0)) { + toxPlot_All_withLabels <- toxPlot_All_withLabels + + geom_text(data=countNonZero, aes(x=chnm, y=ymax,label=nHitsEP),size=ifelse(is.na(font_size),3,0.30*font_size)) + + geom_text(data=data.frame(x = Inf, y=ymax, label = "# Hits", stringsAsFactors = FALSE), + aes(x = x, y=y, label = label), + size=ifelse(is.na(font_size),3,0.30*font_size)) + } + if(!is.na(title)){ toxPlot_All_withLabels <- toxPlot_All_withLabels + ggtitle(title) @@ -116,6 +161,13 @@ plot_chemical_boxplots <- function(chemicalSummary, } } + if(!is.na(hit_threshold)) { + toxPlot_All_withLabels <- toxPlot_All_withLabels + + geom_text(data=data.frame(x = Inf, y=hit_threshold, label = "Threshold", stringsAsFactors = FALSE), + aes(x = x, y=y, label = label), + size=ifelse(is.na(font_size),3,0.30*font_size)) + } + return(toxPlot_All_withLabels) } diff --git a/R/plot_group_boxplots.R b/R/plot_group_boxplots.R index 9d037c47..d9a45991 100644 --- a/R/plot_group_boxplots.R +++ b/R/plot_group_boxplots.R @@ -22,6 +22,7 @@ #' @param manual_remove vector of categories to remove #' @param mean_logic logical \code{TRUE} is mean, \code{FALSE} is maximum #' @param plot_ND logical whether or not to plot the non-detects +#' @param hit_threshold numeric threshold defining a "hit" #' @param font_size numeric to adjust the axis font size #' @param title character title for plot. #' @param pallette vector of color pallette for fill. Can be a named vector @@ -58,6 +59,21 @@ #' gt$layout$clip[gt$layout$name=="panel"] <- "off" #' #' grid::grid.draw(gt) +#' +#' cbPalette <- c("#999999", "#E69F00", "#56B4E9", "#009E73", "#F0E442", +#' "#0072B2", "#D55E00", "#CC79A7") +#' graphData <- tox_boxplot_data(chemicalSummary = chemicalSummary, +#' category = "Biological") +#' cbValues <- colorRampPalette(cbPalette)(length(levels(graphData$category))) +#' names(cbValues) <- levels(graphData$category) +#' +#' plot_tox_boxplots(chemicalSummary, +#' hit_threshold = 0.1, +#' category = "Biological", +#' pallette = cbValues, +#' title = 'Maximum EAR per site, grouped by biological activity groupings') +#' +#' #' } plot_tox_boxplots <- function(chemicalSummary, category = "Biological", @@ -66,7 +82,8 @@ plot_tox_boxplots <- function(chemicalSummary, plot_ND = TRUE, font_size = NA, title = NA, - pallette = NA){ + pallette = NA, + hit_threshold = NA){ match.arg(category, c("Biological","Chemical Class","Chemical")) @@ -79,7 +96,9 @@ plot_tox_boxplots <- function(chemicalSummary, mean_logic = mean_logic, plot_ND = plot_ND, font_size = font_size, - title = title) + title = title, + pallette = pallette, + hit_threshold = hit_threshold) return(chemPlot) } else { @@ -99,9 +118,12 @@ plot_tox_boxplots <- function(chemicalSummary, countNonZero <- chemicalSummary %>% group_by(category) %>% - summarise(nonZero = as.character(length(unique(CAS)))) %>% + summarise(nonZero = as.character(length(unique(CAS))), + hits = as.character(sum(EAR > hit_threshold))) %>% data.frame() + countNonZero$hits[countNonZero$hits == "0"] <- "" + label <- "# Chemicals" if(!is.null(manual_remove)){ @@ -132,7 +154,8 @@ plot_tox_boxplots <- function(chemicalSummary, axis.text.x = element_text(color = "black", vjust = 0, margin = margin(-0.5,0,0,0)), panel.border = element_blank(), axis.ticks = element_blank()) + - scale_y_log10("EAR Per Sample",labels=fancyNumbers) + scale_y_log10("EAR Per Sample",labels=fancyNumbers) + + geom_hline(yintercept = hit_threshold, linetype="dashed", color="black") if(!all(is.na(pallette))){ bioPlot <- bioPlot + @@ -152,8 +175,11 @@ plot_tox_boxplots <- function(chemicalSummary, countNonZero <- graphData %>% group_by(category) %>% - summarise(nonZero = as.character(length(unique(site[meanEAR>0])))) %>% - data.frame() + summarise(nonZero = as.character(length(unique(site[meanEAR>0]))), + hits = as.character(sum(meanEAR > hit_threshold))) %>% + data.frame() + + countNonZero$hits[countNonZero$hits == "0"] <- "" label <- "# Sites" @@ -166,7 +192,8 @@ plot_tox_boxplots <- function(chemicalSummary, axis.text.x = element_text(color = "black", vjust = 0, margin = margin(-0.5,0,0,0)), panel.border = element_blank(), axis.ticks = element_blank()) + - scale_y_log10("Maximum EAR Per Site",labels=fancyNumbers) + scale_y_log10("Maximum EAR Per Site",labels=fancyNumbers) + + geom_hline(yintercept = hit_threshold, linetype="dashed", color="black") if(!all(is.na(pallette))){ bioPlot <- bioPlot + @@ -196,12 +223,30 @@ plot_tox_boxplots <- function(chemicalSummary, ymax <- suppressWarnings(layout_stuff$panel_ranges[[1]]$y.range[2]) } + bioPlot_w_labels <- bioPlot + geom_text(data=countNonZero, aes(x=category, y=xmin,label=nonZero),size=ifelse(is.na(font_size),3,0.30*font_size)) + geom_text(data=data.frame(x = Inf, y=xmin, label = label, stringsAsFactors = FALSE), aes(x = x, y=y, label = label), size=ifelse(is.na(font_size),3,0.30*font_size)) + nHitsEP <- countNonZero$hits + + if(isTRUE(sum(as.numeric(nHitsEP), na.rm = TRUE) > 0)) { + bioPlot_w_labels <- bioPlot_w_labels + + geom_text(data=countNonZero, aes(x=category, y=ymax,label=nHitsEP),size=ifelse(is.na(font_size),3,0.30*font_size)) + + geom_text(data=data.frame(x = Inf, y=ymax, label = "# Hits", stringsAsFactors = FALSE), + aes(x = x, y=y, label = label), + size=ifelse(is.na(font_size),3,0.30*font_size)) + } + + if(!is.na(hit_threshold)) { + bioPlot_w_labels <- bioPlot_w_labels + + geom_text(data=data.frame(x = Inf, y=hit_threshold, label = "Threshold", stringsAsFactors = FALSE), + aes(x = x, y=y, label = label), + size=ifelse(is.na(font_size),3,0.30*font_size)) + } + if(!is.na(title)){ bioPlot_w_labels <- bioPlot_w_labels + ggtitle(title) diff --git a/R/table_tox_rank.R b/R/rank_sites.R similarity index 96% rename from R/table_tox_rank.R rename to R/rank_sites.R index 7284f44c..fa2f1d3f 100644 --- a/R/table_tox_rank.R +++ b/R/rank_sites.R @@ -56,14 +56,11 @@ rank_sites_DT <- function(chemicalSummary, mean_logic = mean_logic) colToSort <- 1 - if("nSamples" %in% names(statsOfColumn)){ - colToSort <- 2 - } - + maxEARS <- grep("maxEAR",names(statsOfColumn)) freqCol <- grep("freq",names(statsOfColumn)) n <- length(maxEARS) - ignoreIndex <- which(names(statsOfColumn) %in% c("site","nSamples")) + ignoreIndex <- which(names(statsOfColumn) %in% c("site","category")) if(n > 20 & n<30){ colors <- c(brewer.pal(n = 12, name = "Set3"), @@ -144,7 +141,7 @@ rank_sites <- function(chemicalSummary, statsOfColumn <- chemicalSummary %>% group_by(site, date, category) %>% summarise(sumEAR = sum(EAR), - nHits = sum(EAR > hit_threshold)) %>% + nHits = sum(sumEAR > hit_threshold)) %>% group_by(site, category) %>% summarise(maxEAR = ifelse(mean_logic, mean(sumEAR), max(sumEAR)), freq = sum(nHits > 0)/n()) %>% @@ -185,6 +182,9 @@ rank_sites <- function(chemicalSummary, statsOfColumn <- statsOfColumn[order(statsOfColumn[[colToSort]], decreasing = TRUE),] + if(length(siteToFind) == 1){ + names(statsOfColumn)[which(names(statsOfColumn) == "site")] <- "category" + } return(statsOfColumn) } diff --git a/inst/doc/Introduction.html b/inst/doc/Introduction.html index ad99ede9..d177657b 100644 --- a/inst/doc/Introduction.html +++ b/inst/doc/Introduction.html @@ -67,7 +67,7 @@

Introduction to toxEval

-

13 April, 2018

+

16 April, 2018

diff --git a/inst/doc/PrepareData.html b/inst/doc/PrepareData.html index fa48b655..4edec250 100644 --- a/inst/doc/PrepareData.html +++ b/inst/doc/PrepareData.html @@ -29,7 +29,7 @@

Preparing toxEval Data

-

13 April, 2018

+

16 April, 2018

diff --git a/inst/doc/basicWorkflow.R b/inst/doc/basicWorkflow.R index 7c74b478..8a5c86b5 100644 --- a/inst/doc/basicWorkflow.R +++ b/inst/doc/basicWorkflow.R @@ -67,6 +67,19 @@ grid::grid.draw(gt) # plot_tox_boxplots(chemicalSummary, "Chemical Class") # plot_tox_boxplots(chemicalSummary, "Chemical") +## ----plot_box_thres, warning=FALSE, message=FALSE------------------------ +bio_box_thresh <- plot_tox_boxplots(chemicalSummary, + category = "Biological", + hit_threshold = 0.001) + +# The graph can be plotted without these additional lines, +# but they allow the labels to look nicer: +gb <- ggplot2::ggplot_build(bio_box_thresh) +gt <- ggplot2::ggplot_gtable(gb) +gt$layout$clip[gt$layout$name=="panel"] <- "off" +grid::grid.draw(gt) + + ## ----filtersiteBox, message=FALSE, warning=FALSE------------------------- library(dplyr) @@ -189,50 +202,51 @@ rank_df <- rank_sites(chemicalSummary, category = "Biological", hit_threshold = 0.1) -rank_sites_DT(chemicalSummary, category = "Biological") -# More options: -# rank_sites_DT(chemicalSummary, -# category = "Chemical Class", -# hit_threshold = 0.1) -# rank_sites_DT(chemicalSummary, -# category = "Chemical", -# hit_threshold = 0.1) +rank_sites_DT(chemicalSummary, + category = "Biological", + hit_threshold = 0.1) ## ----rank_sites_DT_site, warning=FALSE----------------------------------- rank_sites_DT(maumee, category = "Biological") ## ----hits_summary_DT, warning=FALSE-------------------------------------- -hit_df <- hits_summary(chemicalSummary, category = "Biological") +hit_df <- hits_summary(chemicalSummary, + category = "Biological", + hit_threshold = 0.1 ) -hits_summary_DT(chemicalSummary, category = "Biological") -# More options: -# hits_summary_DT(chemicalSummary, category = "Chemical Class") -# hits_summary_DT(chemicalSummary, category = "Chemical") +hits_summary_DT(chemicalSummary, + category = "Biological", + hit_threshold = 0.1) ## ----hits_summary_DT_site, warning=FALSE--------------------------------- hits_summary_DT(maumee, category = "Biological") -## ----table_endpoint_hits, warning=FALSE---------------------------------- +## ----endpoint_hits_DT, warning=FALSE------------------------------------- -ep_hits <- endpoint_hits(chemicalSummary, category = "Biological") +ep_hits <- endpoint_hits(chemicalSummary, + category = "Biological", + hit_threshold = 0.1) -table_endpoint_hits(chemicalSummary, category = "Biological") -# More options: -# table_endpoint_hits(chemicalSummary, category = "Chemical Class") -# table_endpoint_hits(chemicalSummary, category = "Chemical") +endpoint_hits_DT(chemicalSummary, + category = "Biological", + hit_threshold = 0.1) -## ----table_endpoint_hits_site, warning=FALSE----------------------------- -table_endpoint_hits(maumee, category = "Biological") -## ----table_tox_endpoint, warning=FALSE----------------------------------- -table_tox_endpoint(chemicalSummary, category = "Chemical Class") -# More options: -# table_tox_endpoint(chemicalSummary, category = "Biological") -# table_tox_endpoint(chemicalSummary, category = "Chemical") +## ----endpoint_hits_DT_site, warning=FALSE-------------------------------- +endpoint_hits_DT(maumee, category = "Biological") + +## ----hits_by_groupings_DT, warning=FALSE--------------------------------- +site_df <- hits_by_groupings(chemicalSummary, + category = "Chemical Class", + hit_threshold = 0.1) + +hits_by_groupings_DT(chemicalSummary, + category = "Chemical Class", + hit_threshold = 0.1) -## ----table_tox_endpoint_site, warning=FALSE------------------------------ -table_tox_endpoint(maumee, category = "Chemical Class") +## ----hits_by_groupings_DT_site, warning=FALSE---------------------------- +hits_by_groupings_DT(maumee, category = "Chemical Class") ## ----makeMap, warning=FALSE, message=FALSE------------------------------- make_tox_map(chemicalSummary, diff --git a/inst/doc/basicWorkflow.Rmd b/inst/doc/basicWorkflow.Rmd index 2a3be44d..fe07c592 100644 --- a/inst/doc/basicWorkflow.Rmd +++ b/inst/doc/basicWorkflow.Rmd @@ -171,6 +171,22 @@ grid::grid.draw(gt) # plot_tox_boxplots(chemicalSummary, "Chemical") ``` +It is also possible to show a threshold line using the `hit_threshold` argument. The graph will then include the number of sites with detections, the threshold line, and the number of sites with "hits" as defined by measured concentration higher than the `hit_threshold`. + +```{r plot_box_thres, warning=FALSE, message=FALSE} +bio_box_thresh <- plot_tox_boxplots(chemicalSummary, + category = "Biological", + hit_threshold = 0.001) + +# The graph can be plotted without these additional lines, +# but they allow the labels to look nicer: +gb <- ggplot2::ggplot_build(bio_box_thresh) +gt <- ggplot2::ggplot_gtable(gb) +gt$layout$clip[gt$layout$name=="panel"] <- "off" +grid::grid.draw(gt) + +``` + The graph shows a slightly different result for a single site. First, let's set up a subset of data that we will use throughout this document to show a single site. We'll use the Maumee River data. ```{r filtersiteBox, message=FALSE, warning=FALSE} @@ -199,7 +215,6 @@ grid::grid.draw(gt) The `plot_tox_stacks` function creates a set of stacked bar charts based on the original input data modified by the processing steps above, and the choice of several input options. See ["Summarizing the data"](Introduction.html#summarize_data) for a description on how the EAR values are aggregated and summarized. Choosing "Chemical Class" in the `category` argument will generate separate stacked bars for each unique class. "Chemical" will generate stacked bars for each individual chemical, and "Biological" will generate stacked bars for each group in the selected ToxCast annotation. There is an option `include_legend` to turn on and off the legend. It may be impractical for instance to show the legend for "Chemical" if there are hundreds of chemicals. - ```{r stackplots1, warning=FALSE, fig.width=10} stack_plot <- plot_tox_stacks(chemicalSummary, chem_site = tox_list$chem_site, @@ -350,14 +365,9 @@ rank_df <- rank_sites(chemicalSummary, category = "Biological", hit_threshold = 0.1) -rank_sites_DT(chemicalSummary, category = "Biological") -# More options: -# rank_sites_DT(chemicalSummary, -# category = "Chemical Class", -# hit_threshold = 0.1) -# rank_sites_DT(chemicalSummary, -# category = "Chemical", -# hit_threshold = 0.1) +rank_sites_DT(chemicalSummary, + category = "Biological", + hit_threshold = 0.1) ``` The tables show slightly different results for a single site. Instead of multiple columns for category, there is now 1 row per category (since the site is known). @@ -368,60 +378,70 @@ rank_sites_DT(maumee, category = "Biological") ## hits_summary_DT {#hits_summary_DT} -The `hits_summary_DT` (`DT` option) and `hits_summary` (data frame option) functions create a table with one several rows per site depending on which categories get hits based on a user specified `hit_threshold`. So for example, if "Biological" is chosen, and a site has hits above a threshold for "DNA Binding" and "Nuclear Receptors", that site will have 2 rows of data in this table. +The `hits_summary_DT` (`DT` option) and `hits_summary` (data frame option) functions create a table with several rows per site depending on which categories get hits. A "hit" is based on a user specified `hit_threshold`. For example, if "Biological" is the category, and a site has hits above a threshold for "DNA Binding" and "Nuclear Receptors", that site will have 2 rows of data in this table. -For each row, there are 5 colums. Site and category (as defined by the `category` argument) define the row. "Hits per Sample" +For each row, there are 4 columns. Site and category (as defined by the `category` argument) define the row. "Hits per Sample" are how many samples at that site had hits (based on `hit_threshold`) for the category. "Number of Samples" is how many individual samples were collected at an individual site based on unique date. ```{r hits_summary_DT, warning=FALSE} -hit_df <- hits_summary(chemicalSummary, category = "Biological") +hit_df <- hits_summary(chemicalSummary, + category = "Biological", + hit_threshold = 0.1 ) -hits_summary_DT(chemicalSummary, category = "Biological") -# More options: -# hits_summary_DT(chemicalSummary, category = "Chemical Class") -# hits_summary_DT(chemicalSummary, category = "Chemical") +hits_summary_DT(chemicalSummary, + category = "Biological", + hit_threshold = 0.1) ``` -The tables show slightly different results for a single site: +The tables show slightly different results for a single site. Instead of one row per site/category, there is one row per category. ```{r hits_summary_DT_site, warning=FALSE} hits_summary_DT(maumee, category = "Biological") ``` -## table_endpoint_hits {#table_endpoint_hits} +## endpoint_hits_DT {#endpoint_hits_DT} -```{r table_endpoint_hits, warning=FALSE} +The `endpoint_hits_DT` (`DT` option) and `endpoint_hits` (data frame option) functions create a table with one row per endPoint, and one column per category("Biological", "Chemical", or "Chemical Class"). The values in the table are number of sites with hits in that endpoint/category combination, based on a user-specified threshold (defined by `hit_threshold`). One unique feature of this table is that if the category is "Chemical", there will be an "info" link to the ToxCast ("Actor Dashboard")[https://actor.epa.gov/dashboard], directly to the chemical/endpoint combination. +. +```{r endpoint_hits_DT, warning=FALSE} -ep_hits <- endpoint_hits(chemicalSummary, category = "Biological") +ep_hits <- endpoint_hits(chemicalSummary, + category = "Biological", + hit_threshold = 0.1) + +endpoint_hits_DT(chemicalSummary, + category = "Biological", + hit_threshold = 0.1) -table_endpoint_hits(chemicalSummary, category = "Biological") -# More options: -# table_endpoint_hits(chemicalSummary, category = "Chemical Class") -# table_endpoint_hits(chemicalSummary, category = "Chemical") ``` -The tables show slightly different results for a single site. Instead of the number of sites with hits above a threshold, it is now the number of samples. +The tables show slightly different results for a single site. Instead of the number of sites with hits above a threshold, it is now the number of samples with hits. -```{r table_endpoint_hits_site, warning=FALSE} -table_endpoint_hits(maumee, category = "Biological") +```{r endpoint_hits_DT_site, warning=FALSE} +endpoint_hits_DT(maumee, category = "Biological") ``` -## table_tox_endpoint {#table_tox_endpoint} +## hits_by_groupings_DT {#hits_by_groupings_DT} -```{r table_tox_endpoint, warning=FALSE} -table_tox_endpoint(chemicalSummary, category = "Chemical Class") -# More options: -# table_tox_endpoint(chemicalSummary, category = "Biological") -# table_tox_endpoint(chemicalSummary, category = "Chemical") +The `hits_by_groupings_DT` (`DT` option) and `hits_by_groupings` (data frame option) functions create a table with one row per category("Biological", "Chemical", or "Chemical Class"). The columns are always the "Biological" groupings. The values in the table are how many sites have hits (based on `hit_threshold`), for that particular "Biological"/category combination. Note, if the user chooses "Biological", it is a simple 2-column table of "Biological" groupings and number of sites (nSites). + +```{r hits_by_groupings_DT, warning=FALSE} +site_df <- hits_by_groupings(chemicalSummary, + category = "Chemical Class", + hit_threshold = 0.1) + +hits_by_groupings_DT(chemicalSummary, + category = "Chemical Class", + hit_threshold = 0.1) ``` The tables show slightly different results for a single site, showing the number of samples with hits (instead of number of sites). -```{r table_tox_endpoint_site, warning=FALSE} -table_tox_endpoint(maumee, category = "Chemical Class") +```{r hits_by_groupings_DT_site, warning=FALSE} +hits_by_groupings_DT(maumee, category = "Chemical Class") ``` # Maps {#make_tox_map} diff --git a/inst/doc/basicWorkflow.html b/inst/doc/basicWorkflow.html index 9080dcdb..8305db54 100644 --- a/inst/doc/basicWorkflow.html +++ b/inst/doc/basicWorkflow.html @@ -92,7 +92,7 @@

Basic Workflow

-

13 April, 2018

+

16 April, 2018

@@ -117,8 +117,8 @@

13 April, 2018

  • Tables
  • Maps
  • @@ -326,6 +326,18 @@

    plot_tox_boxplots

    # Other options:
     # plot_tox_boxplots(chemicalSummary, "Chemical Class")
     # plot_tox_boxplots(chemicalSummary, "Chemical") 
    +

    It is also possible to show a threshold line using the hit_threshold argument. The graph will then include the number of sites with detections, the threshold line, and the number of sites with “hits” as defined by measured concentration higher than the hit_threshold.

    +
    bio_box_thresh <- plot_tox_boxplots(chemicalSummary, 
    +                             category = "Biological",
    +                             hit_threshold = 0.001)
    +
    +# The graph can be plotted without these additional lines,
    +# but they allow the labels to look nicer:
    +gb <- ggplot2::ggplot_build(bio_box_thresh)
    +gt <- ggplot2::ggplot_gtable(gb)
    +gt$layout$clip[gt$layout$name=="panel"] <- "off"
    +grid::grid.draw(gt)
    +

    The graph shows a slightly different result for a single site. First, let’s set up a subset of data that we will use throughout this document to show a single site. We’ll use the Maumee River data.

    library(dplyr)
     
    @@ -462,63 +474,65 @@ 

    rank_sites_DT

    category = "Biological", hit_threshold = 0.1) -rank_sites_DT(chemicalSummary, category = "Biological")
    +rank_sites_DT(chemicalSummary, + category = "Biological", + hit_threshold = 0.1)
    - -
    # More options:
    -# rank_sites_DT(chemicalSummary, 
    -#               category = "Chemical Class", 
    -#               hit_threshold = 0.1)
    -# rank_sites_DT(chemicalSummary, 
    -#               category = "Chemical", 
    -#               hit_threshold = 0.1)
    +

    The tables show slightly different results for a single site. Instead of multiple columns for category, there is now 1 row per category (since the site is known).

    rank_sites_DT(maumee, category = "Biological")
    - +

    hits_summary_DT

    -

    The hits_summary_DT (DT option) and hits_summary (data frame option) functions create a table with one several rows per site depending on which categories get hits based on a user specified hit_threshold. So for example, if “Biological” is chosen, and a site has hits above a threshold for “DNA Binding” and “Nuclear Receptors”, that site will have 2 rows of data in this table.

    -

    For each row, there are 5 colums. Site and category (as defined by the category argument) define the row. “Hits per Sample”

    -
    hit_df <- hits_summary(chemicalSummary, category = "Biological")
    -
    -hits_summary_DT(chemicalSummary, category = "Biological")
    +

    The hits_summary_DT (DT option) and hits_summary (data frame option) functions create a table with several rows per site depending on which categories get hits. A “hit” is based on a user specified hit_threshold. For example, if “Biological” is the category, and a site has hits above a threshold for “DNA Binding” and “Nuclear Receptors”, that site will have 2 rows of data in this table.

    +

    For each row, there are 4 columns. Site and category (as defined by the category argument) define the row. “Hits per Sample” are how many samples at that site had hits (based on hit_threshold) for the category. “Number of Samples” is how many individual samples were collected at an individual site based on unique date.

    +
    hit_df <- hits_summary(chemicalSummary,
    +                       category = "Biological",
    +                       hit_threshold = 0.1 )
    +
    +hits_summary_DT(chemicalSummary, 
    +                category = "Biological",
    +                hit_threshold = 0.1)
    - -
    # More options:
    -# hits_summary_DT(chemicalSummary, category = "Chemical Class")
    -# hits_summary_DT(chemicalSummary, category = "Chemical")
    -

    The tables show slightly different results for a single site:

    + +

    The tables show slightly different results for a single site. Instead of one row per site/category, there is one row per category.

    hits_summary_DT(maumee, category = "Biological")
    - +
    -
    -

    table_endpoint_hits

    -
    ep_hits <- endpoint_hits(chemicalSummary, category = "Biological")
    -
    -table_endpoint_hits(chemicalSummary, category = "Biological")
    +
    +

    endpoint_hits_DT

    +

    The endpoint_hits_DT (DT option) and endpoint_hits (data frame option) functions create a table with one row per endPoint, and one column per category(“Biological”, “Chemical”, or “Chemical Class”). The values in the table are number of sites with hits in that endpoint/category combination, based on a user-specified threshold (defined by hit_threshold). One unique feature of this table is that if the category is “Chemical”, there will be an “info” link to the ToxCast (“Actor Dashboard”)[https://actor.epa.gov/dashboard], directly to the chemical/endpoint combination. .

    +
    ep_hits <- endpoint_hits(chemicalSummary, 
    +                         category = "Biological", 
    +                         hit_threshold = 0.1)
    +
    +endpoint_hits_DT(chemicalSummary, 
    +                 category = "Biological",
    +                 hit_threshold = 0.1)
    - -
    # More options:
    -# table_endpoint_hits(chemicalSummary, category = "Chemical Class")
    -# table_endpoint_hits(chemicalSummary, category = "Chemical")
    -

    The tables show slightly different results for a single site. Instead of the number of sites with hits above a threshold, it is now the number of samples.

    -
    table_endpoint_hits(maumee, category = "Biological")
    + +

    The tables show slightly different results for a single site. Instead of the number of sites with hits above a threshold, it is now the number of samples with hits.

    +
    endpoint_hits_DT(maumee, category = "Biological")
    - +
    -
    -

    table_tox_endpoint

    -
    table_tox_endpoint(chemicalSummary, category = "Chemical Class")
    +
    +

    hits_by_groupings_DT

    +

    The hits_by_groupings_DT (DT option) and hits_by_groupings (data frame option) functions create a table with one row per category(“Biological”, “Chemical”, or “Chemical Class”). The columns are always the “Biological” groupings. The values in the table are how many sites have hits (based on hit_threshold), for that particular “Biological”/category combination. Note, if the user chooses “Biological”, it is a simple 2-column table of “Biological” groupings and number of sites (nSites).

    +
    site_df <- hits_by_groupings(chemicalSummary, 
    +                             category = "Chemical Class",
    +                             hit_threshold = 0.1)
    +
    +hits_by_groupings_DT(chemicalSummary, 
    +                     category = "Chemical Class",
    +                     hit_threshold = 0.1)
    -
    # More options:
    -# table_tox_endpoint(chemicalSummary, category = "Biological")
    -# table_tox_endpoint(chemicalSummary, category = "Chemical")

    The tables show slightly different results for a single site, showing the number of samples with hits (instead of number of sites).

    -
    table_tox_endpoint(maumee, category = "Chemical Class")
    +
    hits_by_groupings_DT(maumee, category = "Chemical Class")
    diff --git a/inst/doc/shinyApp.Rmd b/inst/doc/shinyApp.Rmd index 18303db9..2169b65e 100644 --- a/inst/doc/shinyApp.Rmd +++ b/inst/doc/shinyApp.Rmd @@ -122,8 +122,8 @@ The following table shows the main function that each tab in the app uses: | Bar Charts | [`plot_tox_stacks`](basicWorkFlow.html#plot_tox_stacks)| | Max EAR and Frequency | [`rank_sites_DT`](basicWorkFlow.html#rank_sites_DT)| | Hit Counts | [`hits_summary_DT`](basicWorkFlow.html#hits_summary_DT)| -| Site Hits | [`table_tox_endpoint`](basicWorkFlow.html#table_tox_endpoint)| -| Endpoint Hits | [`table_endpoint_hits`](basicWorkFlow.html#table_endpoint_hits)| +| Site Hits | [`hits_by_groupings_DT`](basicWorkFlow.html#hits_by_groupings_DT)| +| Endpoint Hits | [`endpoint_hits_DT`](basicWorkFlow.html#endpoint_hits_DT)| | Endpoint | [`plot_tox_endpoints`](basicWorkFlow.html#plot_tox_endpoints)| | Heat Map | [`plot_tox_heatmap`](basicWorkFlow.html#plot_tox_heatmap)| diff --git a/inst/doc/shinyApp.html b/inst/doc/shinyApp.html index 4d2b4181..13d6dbbd 100644 --- a/inst/doc/shinyApp.html +++ b/inst/doc/shinyApp.html @@ -67,7 +67,7 @@

    Shiny App

    -

    13 April, 2018

    +

    16 April, 2018

    @@ -196,11 +196,11 @@

    Main Output

    Site Hits -table_tox_endpoint +hits_by_groupings_DT Endpoint Hits -table_endpoint_hits +endpoint_hits_DT Endpoint diff --git a/inst/shiny/hitTable.R b/inst/shiny/hitTable.R index ddbb3966..a98778b8 100644 --- a/inst/shiny/hitTable.R +++ b/inst/shiny/hitTable.R @@ -9,7 +9,7 @@ output$hitsTable <- DT::renderDataTable({ hitThres <- hitThresValue() mean_logic <- as.logical(input$meanEAR) - tableGroup <- table_tox_endpoint(chemicalSummary, + tableGroup <- hits_by_groupings_DT(chemicalSummary, category = c("Biological","Chemical","Chemical Class")[catType], mean_logic = mean_logic, hit_threshold = hitThres) @@ -36,8 +36,8 @@ siteHitCode <- reactive({ hitThres <- hitThresValue() siteHitCode <- paste0(rCodeSetup()," -# Use the table_tox_endpoint function for the formatted DT table -hitSiteTable <- endpoint_table(chemicalSummary, +# Use the hits_by_groupings_DT function for the formatted DT table +hitSiteTable <- hits_by_groupings(chemicalSummary, category = '",category,"', mean_logic = ",as.logical(input$meanEAR),", hit_threshold = ",hitThres,")") @@ -57,7 +57,7 @@ siteHitTableData <- reactive({ hitThres <- hitThresValue() mean_logic <- as.logical(input$meanEAR) - tableGroup <- endpoint_table(chemicalSummary, + tableGroup <- hits_by_groupings(chemicalSummary, category = c("Biological","Chemical","Chemical Class")[catType], mean_logic = mean_logic, hit_threshold = hitThres) diff --git a/inst/shiny/hitsTableEP.R b/inst/shiny/hitsTableEP.R index 19ae3646..ee0c15e0 100644 --- a/inst/shiny/hitsTableEP.R +++ b/inst/shiny/hitsTableEP.R @@ -10,7 +10,7 @@ output$hitsTableEPs <- DT::renderDataTable({ mean_logic <- as.logical(input$meanEAR) hitThres <- hitThresValue() - tableEPs <- table_endpoint_hits(chemicalSummary, + tableEPs <- endpoint_hits_DT(chemicalSummary, category = c("Biological","Chemical","Chemical Class")[catType], mean_logic = mean_logic, hit_threshold = hitThres) @@ -25,7 +25,7 @@ hitsTableEPCode <- reactive({ hitThres <- hitThresValue() hitsTableEPCode <- paste0(rCodeSetup()," -# Use the table_endpoint_hits for a formatted DT table +# Use the endpoint_hits_DT for a formatted DT table hitTable <- endpoint_hits(chemicalSummary, category = '",category,"', mean_logic = ",as.logical(input$meanEAR),", diff --git a/man/createLink.Rd b/man/createLink.Rd index 400eaf57..320564df 100644 --- a/man/createLink.Rd +++ b/man/createLink.Rd @@ -1,10 +1,10 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/table_endpoint_hits.R +% Please edit documentation in R/endpoint_hits.R \name{createLink} \alias{createLink} \title{createLink} \usage{ -createLink(cas, endpoint, hits) +createLink(cas, endpoint) } \arguments{ \item{cas}{character} diff --git a/man/table_endpoint_hits.Rd b/man/endpoint_hits_DT.Rd similarity index 56% rename from man/table_endpoint_hits.Rd rename to man/endpoint_hits_DT.Rd index 8c6be161..c3b792a1 100644 --- a/man/table_endpoint_hits.Rd +++ b/man/endpoint_hits_DT.Rd @@ -1,11 +1,11 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/table_endpoint_hits.R -\name{table_endpoint_hits} -\alias{table_endpoint_hits} +% Please edit documentation in R/endpoint_hits.R +\name{endpoint_hits_DT} +\alias{endpoint_hits_DT} \alias{endpoint_hits} -\title{table_endpoint_hits} +\title{Rank endpoints by category} \usage{ -table_endpoint_hits(chemicalSummary, category = "Biological", +endpoint_hits_DT(chemicalSummary, category = "Biological", mean_logic = FALSE, hit_threshold = 0.1) endpoint_hits(chemicalSummary, category = "Biological", mean_logic = FALSE, @@ -21,7 +21,14 @@ endpoint_hits(chemicalSummary, category = "Biological", mean_logic = FALSE, \item{hit_threshold}{numeric threshold defining a "hit"} } \description{ -Table of ranks +These functions create a table with one row per endPoint, and one +column per category("Biological", "Chemical", or "Chemical Class"). +The values in the table are number of sites with hits in that endpoint/category +combination, based on a user-specified threshold (defined by hit_threshold). +} +\details{ +The tables show slightly different results for a single site. Instead of the +number of sites with hits above a threshold, it is now the number of samples with hits. } \examples{ # This is the example workflow: @@ -40,8 +47,8 @@ filtered_ep <- filter_groups(cleaned_ep) chemicalSummary <- get_chemical_summary(tox_list, ACClong, filtered_ep) hits_df <- endpoint_hits(chemicalSummary, category = "Biological") -table_endpoint_hits(chemicalSummary, category = "Biological") -table_endpoint_hits(chemicalSummary, category = "Chemical Class") -table_endpoint_hits(chemicalSummary, category = "Chemical") +endpoint_hits_DT(chemicalSummary, category = "Biological") +endpoint_hits_DT(chemicalSummary, category = "Chemical Class") +endpoint_hits_DT(chemicalSummary, category = "Chemical") } } diff --git a/man/hits_by_groupings_DT.Rd b/man/hits_by_groupings_DT.Rd new file mode 100644 index 00000000..08ced35d --- /dev/null +++ b/man/hits_by_groupings_DT.Rd @@ -0,0 +1,56 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/hits_by_groupings.R +\name{hits_by_groupings_DT} +\alias{hits_by_groupings_DT} +\alias{hits_by_groupings} +\title{Biological hits per category} +\usage{ +hits_by_groupings_DT(chemicalSummary, category = "Biological", + mean_logic = FALSE, hit_threshold = 0.1) + +hits_by_groupings(chemicalSummary, category, mean_logic = FALSE, + hit_threshold = 0.1) +} +\arguments{ +\item{chemicalSummary}{data frame from \code{get_chemical_summary}} + +\item{category}{either "Biological", "Chemical Class", or "Chemical"} + +\item{mean_logic}{logical \code{TRUE} is mean, \code{FALSE} is maximum} + +\item{hit_threshold}{numeric threshold defining a "hit"} +} +\description{ +These functions create a table with one row per category("Biological", +"Chemical", or "Chemical Class"). The columns are always the "Biological" +groupings. The values in the table are how many sites have hits (based on +hit_threshold), for that particular "Biological"/category combination. Note, +if the user chooses "Biological", it is a simple 2-column table of +"Biological" groupings and number of sites (nSites). +} +\details{ +The tables show slightly different results for a single site, showing the +number of samples with hits (instead of number of sites). +} +\examples{ +# This is the example workflow: +path_to_tox <- system.file("extdata", package="toxEval") +file_name <- "OWC_data_fromSup.xlsx" + +full_path <- file.path(path_to_tox, file_name) + +tox_list <- create_toxEval(full_path) +\dontrun{ +ACClong <- get_ACC(tox_list$chem_info$CAS) +ACClong <- remove_flags(ACClong) + +cleaned_ep <- clean_endPoint_info(endPointInfo) +filtered_ep <- filter_groups(cleaned_ep) +chemicalSummary <- get_chemical_summary(tox_list, ACClong, filtered_ep) + +site_df <- hits_by_groupings(chemicalSummary, category = "Biological") +hits_by_groupings_DT(chemicalSummary, category = "Biological") +hits_by_groupings_DT(chemicalSummary, category = "Chemical Class") +hits_by_groupings_DT(chemicalSummary, category = "Chemical") +} +} diff --git a/man/hits_summary_DT.Rd b/man/hits_summary_DT.Rd index bd970329..31aaeaaf 100644 --- a/man/hits_summary_DT.Rd +++ b/man/hits_summary_DT.Rd @@ -1,9 +1,9 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/table_tox_sum.R +% Please edit documentation in R/hits_summary.R \name{hits_summary_DT} \alias{hits_summary_DT} \alias{hits_summary} -\title{hits_summary_DT} +\title{Summary of hits per site/category} \usage{ hits_summary_DT(chemicalSummary, category = "Biological", mean_logic = FALSE, hit_threshold = 0.1) @@ -25,7 +25,18 @@ data frame with columns "Hits per Sample", "Individual Hits", "nSample", "site", and "category" } \description{ -Table of sums +These functions create a table with several rows per site depending on which +categories get hits. A "hit" is based on a user specified hit_threshold. For example, +if "Biological" is the category, and a site has hits above a threshold for +"DNA Binding" and "Nuclear Receptors", that site will have 2 rows of data in this table. +} +\details{ +For each row, there are 4 columns. Site and category (as defined by the category argument) +define the row. "Hits per Sample" are how many samples at that site had hits (based on +hit_threshold) for the category. "Number of Samples" is number of samples. + +The tables show slightly different results for a single site. Instead of one row per +site/category, there is one row per category. } \examples{ # This is the example workflow: diff --git a/man/plot_tox_boxplots.Rd b/man/plot_tox_boxplots.Rd index 044f80ea..4b7ba8d8 100644 --- a/man/plot_tox_boxplots.Rd +++ b/man/plot_tox_boxplots.Rd @@ -9,13 +9,14 @@ \title{Grouped Boxplots} \usage{ plot_chemical_boxplots(chemicalSummary, manual_remove = NULL, - mean_logic = FALSE, plot_ND = TRUE, font_size = NA, title = NA) + mean_logic = FALSE, plot_ND = TRUE, font_size = NA, title = NA, + pallette = NA, hit_threshold = NA) graph_chem_data(chemicalSummary, manual_remove = NULL, mean_logic = FALSE) plot_tox_boxplots(chemicalSummary, category = "Biological", manual_remove = NULL, mean_logic = FALSE, plot_ND = TRUE, - font_size = NA, title = NA, pallette = NA) + font_size = NA, title = NA, pallette = NA, hit_threshold = NA) tox_boxplot_data(chemicalSummary, category = "Biological", manual_remove = NULL, mean_logic = FALSE) @@ -33,10 +34,12 @@ tox_boxplot_data(chemicalSummary, category = "Biological", \item{title}{character title for plot.} -\item{category}{either "Biological", "Chemical Class", or "Chemical"} - \item{pallette}{vector of color pallette for fill. Can be a named vector to specify specific color for specific categories.} + +\item{hit_threshold}{numeric threshold defining a "hit"} + +\item{category}{either "Biological", "Chemical Class", or "Chemical"} } \description{ This function creates a set of boxplots based on the original input data @@ -84,5 +87,20 @@ gt <- ggplot2::ggplot_gtable(gb) gt$layout$clip[gt$layout$name=="panel"] <- "off" grid::grid.draw(gt) + +cbPalette <- c("#999999", "#E69F00", "#56B4E9", "#009E73", "#F0E442", + "#0072B2", "#D55E00", "#CC79A7") +graphData <- tox_boxplot_data(chemicalSummary = chemicalSummary, + category = "Biological") +cbValues <- colorRampPalette(cbPalette)(length(levels(graphData$category))) +names(cbValues) <- levels(graphData$category) + +plot_tox_boxplots(chemicalSummary, + hit_threshold = 0.1, + category = "Biological", + pallette = cbValues, + title = 'Maximum EAR per site, grouped by biological activity groupings') + + } } diff --git a/man/rank_sites_DT.Rd b/man/rank_sites_DT.Rd index bc842c4e..76547a31 100644 --- a/man/rank_sites_DT.Rd +++ b/man/rank_sites_DT.Rd @@ -1,5 +1,5 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/table_tox_rank.R +% Please edit documentation in R/rank_sites.R \name{rank_sites_DT} \alias{rank_sites_DT} \alias{rank_sites} diff --git a/man/table_tox_endpoint.Rd b/man/table_tox_endpoint.Rd deleted file mode 100644 index 8aff3112..00000000 --- a/man/table_tox_endpoint.Rd +++ /dev/null @@ -1,47 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/table_tox_endpoint.R -\name{table_tox_endpoint} -\alias{table_tox_endpoint} -\alias{endpoint_table} -\title{rank_sites_DT} -\usage{ -table_tox_endpoint(chemicalSummary, category = "Biological", - mean_logic = FALSE, hit_threshold = 0.1) - -endpoint_table(chemicalSummary, category, mean_logic = FALSE, - hit_threshold = 0.1) -} -\arguments{ -\item{chemicalSummary}{data frame from \code{get_chemical_summary}} - -\item{category}{either "Biological", "Chemical Class", or "Chemical"} - -\item{mean_logic}{logical \code{TRUE} is mean, \code{FALSE} is maximum} - -\item{hit_threshold}{numeric threshold defining a "hit"} -} -\description{ -Table of ranks -} -\examples{ -# This is the example workflow: -path_to_tox <- system.file("extdata", package="toxEval") -file_name <- "OWC_data_fromSup.xlsx" - -full_path <- file.path(path_to_tox, file_name) - -tox_list <- create_toxEval(full_path) -\dontrun{ -ACClong <- get_ACC(tox_list$chem_info$CAS) -ACClong <- remove_flags(ACClong) - -cleaned_ep <- clean_endPoint_info(endPointInfo) -filtered_ep <- filter_groups(cleaned_ep) -chemicalSummary <- get_chemical_summary(tox_list, ACClong, filtered_ep) - -site_df <- endpoint_table(chemicalSummary, category = "Biological") -table_tox_endpoint(chemicalSummary, category = "Biological") -table_tox_endpoint(chemicalSummary, category = "Chemical Class") -table_tox_endpoint(chemicalSummary, category = "Chemical") -} -} diff --git a/tests/testthat/tests_summary.R b/tests/testthat/tests_summary.R index 1e003e3e..447693e7 100644 --- a/tests/testthat/tests_summary.R +++ b/tests/testthat/tests_summary.R @@ -61,15 +61,15 @@ test_that("Plotting summaries", { category = "Biological") expect_true(all(names(bioPlot$data) %in% c("site","category","meanEAR"))) - expect_equal(bioPlot$layers[[1]]$geom_params$outlier.shape, 19) - expect_equal(bioPlot$layers[[1]]$aes_params$fill, "steelblue") + expect_equal(bioPlot$layers[[2]]$geom_params$outlier.shape, 19) + expect_equal(bioPlot$layers[[2]]$aes_params$fill, "steelblue") classPlot <- plot_tox_boxplots(chemicalSummary, category = "Chemical Class") expect_true(all(names(classPlot$data) %in% c("site","category","meanEAR"))) - expect_equal(classPlot$layers[[1]]$geom_params$outlier.shape, 19) - expect_equal(classPlot$layers[[1]]$aes_params$fill, "steelblue") + expect_equal(classPlot$layers[[2]]$geom_params$outlier.shape, 19) + expect_equal(classPlot$layers[[2]]$aes_params$fill, "steelblue") chemPlot <- suppressWarnings(plot_tox_boxplots(chemicalSummary, category = "Chemical")) @@ -116,7 +116,7 @@ test_that("Plotting stacked summaries", { chemStackPlot <- plot_tox_stacks(chemicalSummary, chem_site, category = "Chemical",include_legend = FALSE) expect_true(all(names(chemStackPlot$data) %in% c("site","category","meanEAR", - "site_grouping","Short Name"))) + "site_grouping","Short Name","Class"))) }) @@ -155,13 +155,10 @@ test_that("Table functions", { groupStuff <- hits_summary(chemicalSummary, "Biological", hit_threshold = 1) expect_true(all(unique(groupStuff$site) %in% chem_site$`Short Name`)) - expect_true(all(c("site","category","Hits per Sample", - "Individual Hits","nSamples") %in% names(groupStuff))) - expect_equal(groupStuff[["Hits per Sample"]][which(groupStuff[["site"]] == "Raisin" & + expect_true(all(c("site","category","Samples with hits","Number of Samples") %in% names(groupStuff))) + expect_equal(groupStuff[["Samples with hits"]][which(groupStuff[["site"]] == "Raisin" & groupStuff[["category"]] == "DNA Binding")],28) - expect_equal(groupStuff[["Individual Hits"]][which(groupStuff[["site"]] == "Raisin" & - groupStuff[["category"]] == "DNA Binding")],19) - expect_equal(groupStuff[["nSamples"]][which(groupStuff[["site"]] == "Raisin" & + expect_equal(groupStuff[["Number of Samples"]][which(groupStuff[["site"]] == "Raisin" & groupStuff[["category"]] == "DNA Binding")],44) }) @@ -204,7 +201,7 @@ test_that("Map stuff functions", { test_that("Table endpoint hits", { testthat::skip_on_cran() - bt <- table_endpoint_hits(chemicalSummary, category = "Biological") + bt <- endpoint_hits_DT(chemicalSummary, category = "Biological") expect_type(bt, "list") expect_true(all(names(bt$x$data) %in% c("endPoint","Nuclear Receptor","DNA Binding", "Phosphatase","Steroid Hormone","Esterase"))) @@ -216,16 +213,16 @@ test_that("Table endpoint hits", { expect_equal(bt_df[["Nuclear Receptor"]][bt_df[["endPoint"]] == "NVS_NR_hPPARg"],11) expect_true(is.na(bt_df[["Esterase"]][bt_df[["endPoint"]] == "NVS_NR_hPPARg"])) - expect_error(table_endpoint_hits(chemicalSummary, category = "Class")) + expect_error(endpoint_hits_DT(chemicalSummary, category = "Class")) - ct <- table_endpoint_hits(chemicalSummary, category = "Chemical Class") + ct <- endpoint_hits_DT(chemicalSummary, category = "Chemical Class") expect_type(ct, "list") expect_true(all(names(ct$x$data) %in% c("endPoint","Antioxidants","PAHs", "Detergent Metabolites","Herbicides", "Plasticizers"))) - cht <- table_endpoint_hits(chemicalSummary, category = "Chemical") + cht <- endpoint_hits_DT(chemicalSummary, category = "Chemical") expect_type(cht, "list") expect_true(all(names(cht$x$data) %in% c("endPoint","Bisphenol A","Fluoranthene","Tris(2-chloroethyl) phosphate", @@ -233,30 +230,30 @@ test_that("Table endpoint hits", { "Metolachlor","Atrazine"))) }) -test_that("table_tox_endpoint", { +test_that("hits_by_groupings_DT", { testthat::skip_on_cran() - bt <- table_tox_endpoint(chemicalSummary, category = "Biological") + bt <- hits_by_groupings_DT(chemicalSummary, category = "Biological") expect_type(bt, "list") expect_true(all(class(bt) %in% c("datatables","htmlwidget"))) expect_true("nSites" %in% names(bt$x$data)) - bt_df <- endpoint_table(chemicalSummary, category = "Chemical Class") + bt_df <- hits_by_groupings(chemicalSummary, category = "Chemical Class") expect_true(all(names(bt_df) %in% c("Nuclear Receptor","DNA Binding","Esterase", "Steroid Hormone","Zebrafish"))) expect_true(all(c("Detergent Metabolites","Antioxidants","Herbicides") %in% rownames(bt_df))) expect_equal(bt_df[["Nuclear Receptor"]], c(10,11,7,11,rep(0,9))) - expect_error(table_tox_endpoint(chemicalSummary, category = "Class")) + expect_error(hits_by_groupings_DT(chemicalSummary, category = "Class")) - ct <- table_tox_endpoint(chemicalSummary, category = "Chemical Class") + ct <- hits_by_groupings_DT(chemicalSummary, category = "Chemical Class") expect_type(ct, "list") expect_true(all(class(ct) %in% c("datatables","htmlwidget"))) expect_true(all(names(ct$x$data) %in% c(" ","Nuclear Receptor","DNA Binding", "Phosphatase","Esterase","Steroid Hormone", "Zebrafish"))) - cht <- table_tox_endpoint(chemicalSummary, category = "Chemical") + cht <- hits_by_groupings_DT(chemicalSummary, category = "Chemical") expect_type(cht, "list") expect_true(all(names(cht$x$data) %in% c(" ","Nuclear Receptor","DNA Binding", @@ -271,19 +268,19 @@ test_that("hits_summary_DT", { bt <- hits_summary_DT(chemicalSummary, category = "Biological") expect_type(bt, "list") expect_true(all(class(bt) %in% c("datatables","htmlwidget"))) - expect_true(all(c("site","category","Hits per Sample","Individual Hits","nSamples") %in% names(bt$x$data))) + expect_true(all(c("site","category","Samples with hits","Number of Samples") %in% names(bt$x$data))) expect_error(hits_summary_DT(chemicalSummary, category = "Class")) ct <- hits_summary_DT(chemicalSummary, category = "Chemical Class") expect_type(ct, "list") - expect_true(all(names(ct$x$data) %in% c("site","category","Hits per Sample","Individual Hits","nSamples"))) + expect_true(all(names(ct$x$data) %in% c("site","category","Samples with hits","Number of Samples"))) cht <- hits_summary_DT(chemicalSummary, category = "Chemical") expect_type(cht, "list") - expect_true(all(names(cht$x$data) %in% c("site","category","Hits per Sample","Individual Hits","nSamples"))) + expect_true(all(names(cht$x$data) %in% c("site","category","Samples with hits","Number of Samples"))) }) test_that("rank_sites_DT", { diff --git a/vignettes/basicWorkflow.Rmd b/vignettes/basicWorkflow.Rmd index 2a3be44d..fe07c592 100644 --- a/vignettes/basicWorkflow.Rmd +++ b/vignettes/basicWorkflow.Rmd @@ -171,6 +171,22 @@ grid::grid.draw(gt) # plot_tox_boxplots(chemicalSummary, "Chemical") ``` +It is also possible to show a threshold line using the `hit_threshold` argument. The graph will then include the number of sites with detections, the threshold line, and the number of sites with "hits" as defined by measured concentration higher than the `hit_threshold`. + +```{r plot_box_thres, warning=FALSE, message=FALSE} +bio_box_thresh <- plot_tox_boxplots(chemicalSummary, + category = "Biological", + hit_threshold = 0.001) + +# The graph can be plotted without these additional lines, +# but they allow the labels to look nicer: +gb <- ggplot2::ggplot_build(bio_box_thresh) +gt <- ggplot2::ggplot_gtable(gb) +gt$layout$clip[gt$layout$name=="panel"] <- "off" +grid::grid.draw(gt) + +``` + The graph shows a slightly different result for a single site. First, let's set up a subset of data that we will use throughout this document to show a single site. We'll use the Maumee River data. ```{r filtersiteBox, message=FALSE, warning=FALSE} @@ -199,7 +215,6 @@ grid::grid.draw(gt) The `plot_tox_stacks` function creates a set of stacked bar charts based on the original input data modified by the processing steps above, and the choice of several input options. See ["Summarizing the data"](Introduction.html#summarize_data) for a description on how the EAR values are aggregated and summarized. Choosing "Chemical Class" in the `category` argument will generate separate stacked bars for each unique class. "Chemical" will generate stacked bars for each individual chemical, and "Biological" will generate stacked bars for each group in the selected ToxCast annotation. There is an option `include_legend` to turn on and off the legend. It may be impractical for instance to show the legend for "Chemical" if there are hundreds of chemicals. - ```{r stackplots1, warning=FALSE, fig.width=10} stack_plot <- plot_tox_stacks(chemicalSummary, chem_site = tox_list$chem_site, @@ -350,14 +365,9 @@ rank_df <- rank_sites(chemicalSummary, category = "Biological", hit_threshold = 0.1) -rank_sites_DT(chemicalSummary, category = "Biological") -# More options: -# rank_sites_DT(chemicalSummary, -# category = "Chemical Class", -# hit_threshold = 0.1) -# rank_sites_DT(chemicalSummary, -# category = "Chemical", -# hit_threshold = 0.1) +rank_sites_DT(chemicalSummary, + category = "Biological", + hit_threshold = 0.1) ``` The tables show slightly different results for a single site. Instead of multiple columns for category, there is now 1 row per category (since the site is known). @@ -368,60 +378,70 @@ rank_sites_DT(maumee, category = "Biological") ## hits_summary_DT {#hits_summary_DT} -The `hits_summary_DT` (`DT` option) and `hits_summary` (data frame option) functions create a table with one several rows per site depending on which categories get hits based on a user specified `hit_threshold`. So for example, if "Biological" is chosen, and a site has hits above a threshold for "DNA Binding" and "Nuclear Receptors", that site will have 2 rows of data in this table. +The `hits_summary_DT` (`DT` option) and `hits_summary` (data frame option) functions create a table with several rows per site depending on which categories get hits. A "hit" is based on a user specified `hit_threshold`. For example, if "Biological" is the category, and a site has hits above a threshold for "DNA Binding" and "Nuclear Receptors", that site will have 2 rows of data in this table. -For each row, there are 5 colums. Site and category (as defined by the `category` argument) define the row. "Hits per Sample" +For each row, there are 4 columns. Site and category (as defined by the `category` argument) define the row. "Hits per Sample" are how many samples at that site had hits (based on `hit_threshold`) for the category. "Number of Samples" is how many individual samples were collected at an individual site based on unique date. ```{r hits_summary_DT, warning=FALSE} -hit_df <- hits_summary(chemicalSummary, category = "Biological") +hit_df <- hits_summary(chemicalSummary, + category = "Biological", + hit_threshold = 0.1 ) -hits_summary_DT(chemicalSummary, category = "Biological") -# More options: -# hits_summary_DT(chemicalSummary, category = "Chemical Class") -# hits_summary_DT(chemicalSummary, category = "Chemical") +hits_summary_DT(chemicalSummary, + category = "Biological", + hit_threshold = 0.1) ``` -The tables show slightly different results for a single site: +The tables show slightly different results for a single site. Instead of one row per site/category, there is one row per category. ```{r hits_summary_DT_site, warning=FALSE} hits_summary_DT(maumee, category = "Biological") ``` -## table_endpoint_hits {#table_endpoint_hits} +## endpoint_hits_DT {#endpoint_hits_DT} -```{r table_endpoint_hits, warning=FALSE} +The `endpoint_hits_DT` (`DT` option) and `endpoint_hits` (data frame option) functions create a table with one row per endPoint, and one column per category("Biological", "Chemical", or "Chemical Class"). The values in the table are number of sites with hits in that endpoint/category combination, based on a user-specified threshold (defined by `hit_threshold`). One unique feature of this table is that if the category is "Chemical", there will be an "info" link to the ToxCast ("Actor Dashboard")[https://actor.epa.gov/dashboard], directly to the chemical/endpoint combination. +. +```{r endpoint_hits_DT, warning=FALSE} -ep_hits <- endpoint_hits(chemicalSummary, category = "Biological") +ep_hits <- endpoint_hits(chemicalSummary, + category = "Biological", + hit_threshold = 0.1) + +endpoint_hits_DT(chemicalSummary, + category = "Biological", + hit_threshold = 0.1) -table_endpoint_hits(chemicalSummary, category = "Biological") -# More options: -# table_endpoint_hits(chemicalSummary, category = "Chemical Class") -# table_endpoint_hits(chemicalSummary, category = "Chemical") ``` -The tables show slightly different results for a single site. Instead of the number of sites with hits above a threshold, it is now the number of samples. +The tables show slightly different results for a single site. Instead of the number of sites with hits above a threshold, it is now the number of samples with hits. -```{r table_endpoint_hits_site, warning=FALSE} -table_endpoint_hits(maumee, category = "Biological") +```{r endpoint_hits_DT_site, warning=FALSE} +endpoint_hits_DT(maumee, category = "Biological") ``` -## table_tox_endpoint {#table_tox_endpoint} +## hits_by_groupings_DT {#hits_by_groupings_DT} -```{r table_tox_endpoint, warning=FALSE} -table_tox_endpoint(chemicalSummary, category = "Chemical Class") -# More options: -# table_tox_endpoint(chemicalSummary, category = "Biological") -# table_tox_endpoint(chemicalSummary, category = "Chemical") +The `hits_by_groupings_DT` (`DT` option) and `hits_by_groupings` (data frame option) functions create a table with one row per category("Biological", "Chemical", or "Chemical Class"). The columns are always the "Biological" groupings. The values in the table are how many sites have hits (based on `hit_threshold`), for that particular "Biological"/category combination. Note, if the user chooses "Biological", it is a simple 2-column table of "Biological" groupings and number of sites (nSites). + +```{r hits_by_groupings_DT, warning=FALSE} +site_df <- hits_by_groupings(chemicalSummary, + category = "Chemical Class", + hit_threshold = 0.1) + +hits_by_groupings_DT(chemicalSummary, + category = "Chemical Class", + hit_threshold = 0.1) ``` The tables show slightly different results for a single site, showing the number of samples with hits (instead of number of sites). -```{r table_tox_endpoint_site, warning=FALSE} -table_tox_endpoint(maumee, category = "Chemical Class") +```{r hits_by_groupings_DT_site, warning=FALSE} +hits_by_groupings_DT(maumee, category = "Chemical Class") ``` # Maps {#make_tox_map} diff --git a/vignettes/shinyApp.Rmd b/vignettes/shinyApp.Rmd index 18303db9..2169b65e 100644 --- a/vignettes/shinyApp.Rmd +++ b/vignettes/shinyApp.Rmd @@ -122,8 +122,8 @@ The following table shows the main function that each tab in the app uses: | Bar Charts | [`plot_tox_stacks`](basicWorkFlow.html#plot_tox_stacks)| | Max EAR and Frequency | [`rank_sites_DT`](basicWorkFlow.html#rank_sites_DT)| | Hit Counts | [`hits_summary_DT`](basicWorkFlow.html#hits_summary_DT)| -| Site Hits | [`table_tox_endpoint`](basicWorkFlow.html#table_tox_endpoint)| -| Endpoint Hits | [`table_endpoint_hits`](basicWorkFlow.html#table_endpoint_hits)| +| Site Hits | [`hits_by_groupings_DT`](basicWorkFlow.html#hits_by_groupings_DT)| +| Endpoint Hits | [`endpoint_hits_DT`](basicWorkFlow.html#endpoint_hits_DT)| | Endpoint | [`plot_tox_endpoints`](basicWorkFlow.html#plot_tox_endpoints)| | Heat Map | [`plot_tox_heatmap`](basicWorkFlow.html#plot_tox_heatmap)|