Skip to content

Commit

Permalink
Merge pull request #72 from yerkes-gencore/writeDGEResults
Browse files Browse the repository at this point in the history
Write dge results
  • Loading branch information
derrik-gratz authored Oct 5, 2023
2 parents c22f981 + 786cc04 commit 5a48996
Show file tree
Hide file tree
Showing 5 changed files with 156 additions and 3 deletions.
1 change: 1 addition & 0 deletions DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,7 @@ Imports:
magrittr,
Matrix,
methods,
openxlsx,
plotly,
plyr,
reshape2,
Expand Down
3 changes: 3 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -42,13 +42,15 @@ export(runSoupX)
export(run_scDblFinder)
export(scoreCC)
export(update_sc)
export(writeDGEResults)
import(DoubletFinder)
import(Seurat)
import(SingleR)
import(SoupX)
import(dplyr)
import(ggplot2)
import(grDevices)
import(openxlsx)
import(scDblFinder)
importFrom(Matrix,rowSums)
importFrom(S4Vectors,mcols)
Expand Down Expand Up @@ -78,6 +80,7 @@ importFrom(ggplot2,stat_smooth)
importFrom(ggplot2,theme)
importFrom(ggplot2,theme_classic)
importFrom(gtools,mixedsort)
importFrom(here,here)
importFrom(magrittr,"%>%")
importFrom(methods,show)
importFrom(plotly,ggplotly)
Expand Down
77 changes: 77 additions & 0 deletions R/writeDGEResults.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,77 @@
#' Write differential expression test results to excel sheet
#'
#' Take a list of differential expression results tables returned from `Seurat::FindMarkers()`
#' or a similar function and write them to an excel worksheet, with one sheet for each result.
#'
#' @param results List of outputs from `Seurat::FindMarkers()` or a similar function
#' @param sheet_names List of names for sheets, defaults to names of `results`
#' @param output_name Name of file
#' @param outdir Location of file
#' @param p_val_colname Name of column with adjusted P value data
#' @param drop_NA Exclude values with NA for adjusted P value?
#' @param write_rownames Write rownames of `results` to sheet?
#'
#' @return `NULL`
#' @export
#'
#' @import openxlsx
#' @importFrom here here
#'
#' @examples
#' \dontrun{
#' dge_results$NK_adaptive.post.1D3_vs_cnt <- FindMarkers(object = cd8_obj,
#' group.by = 'condition.timepoint',
#' ident.1 = 'post-ATI.1D3', ident.2 = 'post-ATI.control',
#' subset.ident = 'NK (adaptive)',
#' features = dge_genes,
#' logfc.threshold = 0, min.pct = 0,
#' test.use = 'MAST', assay = 'RNA')
#' dge_results$NK_adaptive.pre.1D3_vs_cnt <- FindMarkers(object = cd8_obj,
#' group.by = 'condition.timepoint',
#' ident.1 = 'pre-ATI.1D3', ident.2 = 'pre-ATI.control',
#' subset.ident = 'NK (adaptive)',
#' features = dge_genes,
#' logfc.threshold = 0, min.pct = 0,
#' test.use = 'MAST', assay = 'RNA')
#' writeDGEResults(dge_results)
#' }
writeDGEResults <- function(results,
sheet_names = names(results),
output_name = paste0("differentially_expressed_genes.xlsx"),
outdir = here::here('outputs'),
p_val_colname = 'p_val_adj',
drop_NA = FALSE,
write_rownames = TRUE){
outfile <- file.path(outdir, output_name)
message(paste0('Writing results to ', outfile))
wb <- openxlsx::createWorkbook('ENPRC Gencore')
mapply(FUN = .addWorksheet_DGEres,
result = results,
sheet_name = sheet_names,
MoreArgs = list(wb = wb,
drop_NA = drop_NA,
p_val_colname = p_val_colname,
write_rownames = write_rownames)
)
openxlsx::saveWorkbook(wb, outfile, overwrite = TRUE)
}

.addWorksheet_DGEres <- function(wb,
result,
sheet_name,
drop_NA,
p_val_colname,
write_rownames){
if (nchar(sheet_name) > 31) {
sheet_name <- substr(sheet_name, 1, 31)
}
if (drop_NA) {
result <- result[!is.na(result[[pval_col_name]]),]
}
result <- result[order(result[[pval_col_name]]),]
openxlsx::addWorksheet(wb, sheet_name)
openxlsx::writeData(wb,
sheet = sheet_name,
x = as.data.frame(result),
rowNames = write_rownames)
}
21 changes: 18 additions & 3 deletions man/runSingleR.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

57 changes: 57 additions & 0 deletions man/writeDGEResults.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

0 comments on commit 5a48996

Please sign in to comment.