Previous changeset 4:56371b5a2da9 (2022-02-10) Next changeset 6:fb36f390cc52 (2024-10-28) |
Commit message:
"planemo upload for repository https://github.com/galaxyproject/tools-iuc/tree/master/tools/music/ commit d007ae51743e621dc47524f681501e72ef3a2910" |
modified:
macros.xml music_deconvolution.xml scripts/compare.R |
added:
test-data/APOL1_Bulk.rds test-data/Control_Bulk.rds |
b |
diff -r 56371b5a2da9 -r 2ba99a52bd44 macros.xml --- a/macros.xml Thu Feb 10 12:52:31 2022 +0000 +++ b/macros.xml Mon May 02 10:00:16 2022 +0000 |
b |
@@ -1,5 +1,5 @@ <macros> - <token name="@VERSION_SUFFIX@">3</token> + <token name="@VERSION_SUFFIX@">4</token> <!-- The ESet inspector/constructor and MuSiC tool can have independent Galaxy versions but should reference the same package version always. --> @@ -14,6 +14,7 @@ <requirement type="package" version="@TOOL_VERSION@" >music-deconvolution</requirement> <requirement type="package" version="0.9.3" >r-cowplot</requirement> <requirement type="package" version="1.4.4" >r-reshape2</requirement> + <requirement type="package" version="0.1_20">r-ggdendro</requirement> </requirements> </xml> <xml name="validator_index_identifiers" > |
b |
diff -r 56371b5a2da9 -r 2ba99a52bd44 music_deconvolution.xml --- a/music_deconvolution.xml Thu Feb 10 12:52:31 2022 +0000 +++ b/music_deconvolution.xml Mon May 02 10:00:16 2022 +0000 |
[ |
@@ -6,6 +6,7 @@ </macros> <expand macro="requirements" /> <command detect_errors="exit_code" ><![CDATA[ +cat '$conf' >> /dev/stderr && mkdir report_data && Rscript --vanilla '$__tool_directory__/scripts/${do.method}.R' '$conf' ]]></command> |
b |
diff -r 56371b5a2da9 -r 2ba99a52bd44 scripts/compare.R --- a/scripts/compare.R Thu Feb 10 12:52:31 2022 +0000 +++ b/scripts/compare.R Mon May 02 10:00:16 2022 +0000 |
[ |
b'@@ -11,6 +11,7 @@\n method_key <- list("MuSiC" = "est_music",\n "NNLS" = "est_nnls")[[est_method]]\n \n+delim <- "::" ## separator bulk datasets and their samples\n \n scale_yaxes <- function(gplot, value) {\n if (is.na(value)) {\n@@ -136,43 +137,6 @@\n return(tab)\n }\n \n-\n-plot_grouped_heatmaps <- function(results) {\n- pdf(out_heatmulti_pdf, width = 8, height = 8)\n- for (sc_name in names(results)) {\n- named_list <- sapply(\n- names(results[[sc_name]]),\n- function(n) {\n- ## We transpose the data here, because\n- ## the plotting function omits by default\n- ## the Y-axis which are the samples.\n- ## Since the celltypes are the common factor\n- ## these should be the Y-axis instead.\n- t(data.matrix(results[[sc_name]][[n]][[method_key]]))\n- }, simplify = F, USE.NAMES = T)\n- named_methods <- names(results[[sc_name]])\n- ##\n- plot_hmap <- Prop_heat_Est(\n- named_list,\n- method.name = named_methods) +\n- ggtitle(paste0("[", est_method, "] Cell type ",\n- "proportions of ",\n- "Bulk Datasets based on ",\n- sc_name, " (scRNA)")) +\n- xlab("Samples (Bulk)") +\n- ylab("Cell Types (scRNA)") +\n- theme(axis.text.x = element_text(angle = -90),\n- axis.text.y = element_text(size = 6))\n- print(plot_hmap)\n- }\n- dev.off()\n-}\n-\n-## Desired plots\n-## 1. Pie chart:\n-## - Per Bulk dataset (using just normalised proportions)\n-## - Per Bulk dataset (multiplying proportions by nreads)\n-\n unlist_names <- function(results, method, prepend_bkname=FALSE) {\n unique(sort(\n unlist(lapply(names(results), function(scname) {\n@@ -181,7 +145,7 @@\n if (prepend_bkname) {\n ## We *do not* assume unique bulk sample names\n ## across different bulk datasets.\n- res <- paste0(bkname, "::", res)\n+ res <- paste0(bkname, delim, res)\n }\n return(res)\n })\n@@ -201,7 +165,7 @@\n ddff_scale <- data.frame()\n for (cell in all_celltypes) {\n for (sample in all_samples) {\n- group_sname <- unlist(strsplit(sample, split = "::"))\n+ group_sname <- unlist(strsplit(sample, split = delim))\n bulk <- group_sname[1]\n id_sample <- group_sname[2]\n for (scgroup in names(results)) {\n@@ -231,7 +195,7 @@\n for (scgroup in names(results)) {\n for (bulkgroup in names(results[[scgroup]])) {\n dat <- results[[scgroup]][[bulkgroup]]$plot_groups\n- dat$Samples <- paste0(bulkgroup, "::", dat$Samples) #nolint\n+ dat$Samples <- paste0(bulkgroup, delim, dat$Samples) #nolint\n res <- rbind(res, dat)\n }\n }\n@@ -247,7 +211,7 @@\n bd_spread_scale <- list()\n bd_spread_prop <- list()\n for (bname in bulk_names) {\n- subs <- mat_names[startsWith(mat_names, paste0(bname, "::"))]\n+ subs <- mat_names[startsWith(mat_names, paste0(bname, delim))]\n ## -\n bd[[bname]] <- rowSums(summat$prop[, subs])\n bd_scale[[bname]] <- rowSums(summat$scaled[, subs])\n@@ -260,8 +224,75 @@\n prop = bd_spread_prop)))\n }\n \n-summarize_heatmaps <- function(grudat_spread_melt, do_factors) {\n- ## -\n+do_cluster <- function(grudat_spread_melt, xaxis, yaxis, value_name,\n+ xlabs="", ylabs="", titled="",\n+ order_col=T, order_row=T, size=11) {\n+\n+ data_m <- grudat_spread_melt\n+ data_matrix <- {\n+ tmp <- dcast(data_m, formula(paste0(yaxis, " ~ ", xaxis)), value.var = value_name)\n+ rownames(tmp) <- tmp[[yaxis]]\n+ tmp[[yaxis]] <- NULL\n+ tmp\n+ }\n+ dist_method <- "euclidean"\n+ clust_me'..b' name = element_blank()) +\n+ theme(axis.text.x = element_text(\n+ angle = -90, hjust = 0, size = size)) +\n+ ggtitle(label = title) + xlab(xlabs) + ylab(ylabs))\n+ } else {\n+ return(do_cluster(grudat_spread_melt, xaxis, yaxis, fillval,\n+ xlabs, ylabs, title,\n+ (cluster %in% c("Cols", "Both")),\n+ (cluster %in% c("Rows", "Both"))))\n+ }\n }\n \n do_gridplot <- function(title, xvar, plot="both", ncol=2, size = 11) {\n@@ -303,16 +342,16 @@\n return(plot_grid(ggdraw() + draw_label(title, fontface = "bold"),\n plot_grid(plotlist = plist, ncol = ncol),\n ncol = 1, rel_heights = c(0.05, 0.95)))\n+ }\n \n- }\n- p1 <- do_gridplot("Cell Types vs Bulk Datasets", "Bulk", "both", )\n- p2a <- do_gridplot("Cell Types vs Samples", "Sample", "normal", 1,\n- size = 8)\n- p2b <- do_gridplot("Cell Types vs Samples (log10+1)", "Sample", "log", 1,\n- size = 8)\n+ p1 <- do_gridplot("Cell Types vs Bulk Datasets", "Bulk", "both")\n+ p2a <- do_gridplot("Cell Types vs Samples", "Sample", "normal",\n+ ncol = 1, size = 8)\n+ p2b <- do_gridplot("Cell Types vs Samples (log10+1)", "Sample", "log",\n+ ncol = 1, size = 8)\n p3 <- ggplot + theme_void()\n if (do_factors) {\n- p3 <- do_gridplot("Cell Types against Factors", "Factors", "both")\n+ p3 <- do_gridplot("Cell Types vs Factors", "Factors", "both")\n }\n return(list(bulk = p1,\n samples = list(log = p2b, normal = p2a),\n@@ -346,8 +385,8 @@\n ylab("Bulk Dataset")\n }\n \n- title_a <- "Cell Types against Bulk"\n- title_b <- "Bulk Datasets against Cells"\n+ title_a <- "Cell Types vs Bulk Datasets"\n+ title_b <- "Bulk Datasets vs Cell Types"\n if (do_factors) {\n title_a <- paste0(title_a, " and Factors")\n title_b <- paste0(title_b, " and Factors")\n@@ -380,31 +419,28 @@\n return(grudat_filt)\n }\n \n+writable2 <- function(obj, prefix, title) {\n+ write.table(obj,\n+ file = paste0("report_data/", prefix, "_",\n+ title, ".tabular"),\n+ quote = F, sep = "\\t", col.names = NA)\n+}\n+\n \n results <- music_on_all(files)\n-\n-if (heat_grouped_p) {\n- plot_grouped_heatmaps(results)\n-} else {\n- plot_all_individual_heatmaps(results)\n-}\n-\n-save.image("/tmp/sesh.rds")\n-\n summat <- summarized_matrix(results)\n grudat <- group_by_dataset(summat)\n grudat_spread_melt <- merge_factors_spread(grudat$spread,\n flatten_factor_list(results))\n+grudat_spread_melt_filt <- filter_output(grudat_spread_melt, out_filt)\n \n-\n+plot_all_individual_heatmaps(results)\n \n ## The output filters ONLY apply to boxplots, since these take\n do_factors <- (length(unique(grudat_spread_melt[["Factors"]])) > 1)\n-\n-grudat_spread_melt_filt <- filter_output(grudat_spread_melt, out_filt)\n-\n-heat_maps <- summarize_heatmaps(grudat_spread_melt_filt, do_factors)\n box_plots <- summarize_boxplots(grudat_spread_melt_filt, do_factors)\n+heat_maps <- summarize_heatmaps(grudat_spread_melt_filt, do_factors,\n+ dendro_setting)\n \n pdf(out_heatsumm_pdf, width = 14, height = 14)\n print(heat_maps)\n@@ -417,12 +453,6 @@\n stats_scale <- lapply(grudat$spread$scale, function(x) {\n t(apply(x, 1, summary))})\n \n-writable2 <- function(obj, prefix, title) {\n- write.table(obj,\n- file = paste0("report_data/", prefix, "_",\n- title, ".tabular"),\n- quote = F, sep = "\\t", col.names = NA)\n-}\n ## Make the value table printable\n grudat_spread_melt$value.scale <- as.integer(grudat_spread_melt$value.scale) # nolint\n colnames(grudat_spread_melt) <- c("Sample", "Cell", "Bulk", "Factors",\n' |
b |
diff -r 56371b5a2da9 -r 2ba99a52bd44 test-data/APOL1_Bulk.rds |
b |
Binary file test-data/APOL1_Bulk.rds has changed |
b |
diff -r 56371b5a2da9 -r 2ba99a52bd44 test-data/Control_Bulk.rds |
b |
Binary file test-data/Control_Bulk.rds has changed |