Mercurial > repos > azomics > flowviz_density_plots
changeset 0:23c0af6be9a7 draft default tip
"planemo upload for repository https://github.com/ImmPortDB/immport-galaxy-tools/tree/master/flowtools/flowviz_density_plots commit 8645b278253fe79de4a23fd3e54e397bca2a9919"
author | azomics |
---|---|
date | Mon, 22 Jun 2020 20:48:47 -0400 |
parents | |
children | |
files | FCSflowViz.R FCSflowViz.xml test-data/graph.pdf test-data/graph.png test-data/graph2.png test-data/input1.fcs test-data/input2.fcs test-data/input3.fcs |
diffstat | 8 files changed, 228 insertions(+), 0 deletions(-) [+] |
line wrap: on
line diff
--- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/FCSflowViz.R Mon Jun 22 20:48:47 2020 -0400 @@ -0,0 +1,128 @@ +#!/usr/bin/Rscript +# Stacked 1D Density Plot Module for Galaxy +# flowviz +###################################################################### +# Copyright (c) 2016 Northrop Grumman. +# All rights reserved. +###################################################################### +# +# Version 1 +# Cristel Thomas +# +# + +library(flowViz) +library(methods) + +generateStackedPlots <- function(fs, chans=list(), output="", flag_pdf=FALSE) { + h <- 800 + w <- 1200 + if (length(fs@colnames)>8){ + h <- 1200 + w <- 1600 + } + channels_to_plot <- fs@colnames + if (length(chans) > 0){ + channels_to_plot <- fs@colnames[chans] + } + + if (flag_pdf) { + pdf(output, useDingbats=FALSE, onefile=TRUE) + print({ + densityplot(~., fs, channels = channels_to_plot) + }) + dev.off() + } else { + png(output, type="cairo", height=h, width=w) + print({ + densityplot(~., fs, channels = channels_to_plot) + }) + dev.off() + } +} + +checkFlowSet <- function(fcsfiles, newnames, channels=list(), out_file ="", + flag_pdf=FALSE) { + + isValid <- F + markerCheck <- T + + for (i in 1:length(fcsfiles)){ + is_file_valid <- F + tryCatch({ + fcs <- read.FCS(fcsfiles[i], transformation=FALSE) + is_file_valid <- T + }, error = function(ex) { + print(paste(ex)) + }) + if (i == 1) { + m1 <- as.vector(pData(parameters(fcs))$desc) + } else { + m2 <- as.vector(pData(parameters(fcs))$desc) + if (is.na(all(m1==m2))) { + mm1 <- is.na(m1) + mm2 <- is.na(m2) + if (all(mm1==mm2)){ + if (!all(m1==m2, na.rm=TRUE)){ + markerCheck <- F + } + } else { + markerCheck <- F + } + } else if (!all(m1==m2)) { + markerCheck <- F + } + } + } + if (markerCheck) { + isValid <- T + } else { + quit(save = "no", status = 12, runLast = FALSE) + } + + if (isValid) { + fs <- read.flowSet(files=fcsfiles, transformation=FALSE) + fs@phenoData@data$name <- newnames + generateStackedPlots(fs, channels, out_file, flag_pdf) + } else { + quit(save = "no", status = 12, runLast = FALSE) + } +} + +args <- commandArgs(trailingOnly = TRUE) +channels <- list() +flag_pdf <- FALSE + +if (args[1]=="None") { + flag_default <- TRUE +} else { + if (args[1] == "i.e.:1,3,4"){ + flag_default <- TRUE + } else { + channels <- as.numeric(strsplit(args[1], ",")[[1]]) + for (channel in channels){ + if (is.na(channel)){ + quit(save = "no", status = 11, runLast = FALSE) + } + } + } +} + +if (args[3] == "PDF"){ + flag_pdf <- TRUE +} + +nb_files <- (length(args) - 3) / 2 +fcsfiles <- character(nb_files) +newnames <- character(nb_files) +j <- 1 +## get files and file names +for (i in 4:length(args)) { + if (!i%%2){ + fcsfiles[[j]] <- args[i] + newnames[[j]] <- args[i+1] + j <- j + 1 + } +} + +checkFlowSet(fcsfiles, newnames, channels, args[2], flag_pdf)
--- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/FCSflowViz.xml Mon Jun 22 20:48:47 2020 -0400 @@ -0,0 +1,100 @@ +<tool id="flowviz_density_plots" name="Generate stacked density plots" version="1.0+galaxy0"> + <description>for a set of FCS files</description> + <requirements> + <requirement type="package" version="1.40.0">bioconductor-flowviz</requirement> + </requirements> + <stdio> + <exit_code range="10" level="fatal" description="Please provide a comma separated list of channels to plot" /> + <exit_code range="11" level="fatal" description="Please provide numeric values for the list of channels to plot" /> + <exit_code range="12" level="fatal" description="The set of FCS files must have the same set of channels" /> + </stdio> + <command><![CDATA[ + Rscript $__tool_directory__/FCSflowViz.R '${channels}' '${output}' '${outformat}' + #for $f in $input + '${f}' '${f.name}' + #end for + ]]> + </command> + <inputs> + <param format="fcs" name="input" type="data_collection" collection_type="list" label="FCS files Collection"/> + <param name="channels" type="text" label="Markers to plot:" value="i.e.:1,3,4" help="By default, will plot all channels."/> + <param name="outformat" type="select" label="Output Format" help="PDF will be larger files that may take some time to load."> + <option value="PNG">PNG</option> + <option value="PDF">PDF</option> + </param> + </inputs> + <outputs> + <data format="png" name="output" label="Stacked Density Plots from ${input.name} in ${outformat}"> + <change_format> + <when input="outformat" value="PDF" format="pdf" /> + </change_format> + </data> + </outputs> + <tests> + <test> + <param name="input"> + <collection type="list"> + <element name="input1.fcs" value="input1.fcs"/> + <element name="input2.fcs" value="input2.fcs"/> + <element name="input3.fcs" value="input3.fcs"/> + </collection> + </param> + <param name="channels" value="1,3"/> + <param name="outformat" value="PDF"/> + <output name="output" file="graph.pdf" compare="sim_size"/> + </test> + <test> + <param name="input"> + <collection type="list"> + <element name="input1.fcs" value="input1.fcs"/> + <element name="input2.fcs" value="input2.fcs"/> + <element name="input3.fcs" value="input3.fcs"/> + </collection> + </param> + <param name="channels" value="i.e.:1,3,4"/> + <param name="outformat" value="PNG"/> + <output name="output" file="graph.png" compare="sim_size"/> + </test> + </tests> + <help><![CDATA[ +FlowViz stacked 1D density plots +-------------------------------- + +This tool generates stacked 1D density plots using flowViz. + +**Input files** + +This tool takes a collection of valid FCS files as input. + +.. class:: warningmark + +Each FCS file in the input data collection should have the SAME set of channels. + +**Output files** + +This tool generates stacked 1D density plots for each channel. A pdf file can optionally be generated. + +class:: warningmark + +PDF are larger files that may take some time to load. It might be faster to download the PDF output once generated to open it locally. + +----- + +**Example** + +*Output*: + +.. image:: ./static/images/flowtools/flowviz.png + +----- + +**flowViz reference** + +Ellis B, Gentleman R, Hahne F, Le Meur N, Sarkar D and Jiang M (2017). flowViz: Visualization for flow cytometry. R package version 1.40.0. + + ]]> + </help> + <citations> + <citation type="doi">10.1186/1471-2105-10-106</citation> + </citations> +</tool>