... | ... |
@@ -1,7 +1,7 @@ |
1 | 1 |
Package: CytoML |
2 | 2 |
Type: Package |
3 | 3 |
Title: A GatingML Interface for Cross Platform Cytometry Data Sharing |
4 |
-Version: 1.9.5 |
|
4 |
+Version: 1.9.6 |
|
5 | 5 |
Date: 2016-04-15 |
6 | 6 |
Author: Mike Jiang |
7 | 7 |
Maintainer: Mike Jiang <wjiang2@fhcrc.org> |
... | ... |
@@ -31,7 +31,8 @@ Imports: |
31 | 31 |
grDevices, |
32 | 32 |
methods, |
33 | 33 |
ggcyto (>= 1.11.4), |
34 |
- yaml |
|
34 |
+ yaml, |
|
35 |
+ lattice |
|
35 | 36 |
biocViews: ImmunoOncology, FlowCytometry, DataImport, DataRepresentation |
36 | 37 |
LinkingTo: Rcpp, BH(>= 1.62.0-1), RProtoBufLib(>= 1.3.7), cytolib(>= 1.3.3), RcppParallel |
37 | 38 |
Suggests: |
... | ... |
@@ -56,5 +57,6 @@ Collate: |
56 | 57 |
'graphGML_methods.R' |
57 | 58 |
'parseDivaWorkspace_old.R' |
58 | 59 |
'utils.R' |
60 |
+ 'zzz.R' |
|
59 | 61 |
SystemRequirements: xml2, GNU make, C++11 |
60 | 62 |
Encoding: UTF-8 |
... | ... |
@@ -11,6 +11,8 @@ S3method(getTransformations,cytobankExperiment) |
11 | 11 |
S3method(getTransformations,graphGML) |
12 | 12 |
S3method(openWorkspace,character) |
13 | 13 |
S3method(print,cytobankExperiment) |
14 |
+export(CytoML.par.get) |
|
15 |
+export(CytoML.par.set) |
|
14 | 16 |
export(GatingSet2cytobank) |
15 | 17 |
export(GatingSet2flowJo) |
16 | 18 |
export(closeWorkspace) |
... | ... |
@@ -157,7 +157,7 @@ DerivedParameterNode <- function(sn, parent, childnodes, vec, cluster_name, env. |
157 | 157 |
csvfile <- paste(sn, pname, "EPA.csv", sep = ".") |
158 | 158 |
csvpath <- file.path(outputdir, csvfile) |
159 | 159 |
write.csv(vec, csvpath, row.names = FALSE) |
160 |
- message("DerivedParameter: ", csvpath) |
|
160 |
+ message("DerivedParameter: ", normalizePath(csvpath)) |
|
161 | 161 |
xmlNode("DerivedParameter" |
162 | 162 |
, attrs = c(name = pname |
163 | 163 |
, type = "importCsv" |
... | ... |
@@ -6,15 +6,17 @@ |
6 | 6 |
#' @rdname cytobank2GatingSet |
7 | 7 |
#' @examples |
8 | 8 |
#' \dontrun{ |
9 |
-#' xmlfile <- system.file("extdata/cytotrol_tcell_cytobank.xml", package = "CytoML") |
|
10 |
-#' fcsFiles <- list.files(pattern = "CytoTrol", |
|
11 |
-#' system.file("extdata", package = "flowWorkspaceData"), full = TRUE) |
|
12 |
-#' gs <- cytobank2GatingSet(xmlfile, fcsFiles) |
|
13 |
-#' #plotGate(gs[[1]]) |
|
9 |
+#' acsfile <- system.file("extdata/cytobank_experiment.acs", package = "CytoML") |
|
10 |
+#' ce <- cytobankExperiment(acsfile) |
|
11 |
+#' xmlfile <- ce$gatingML |
|
12 |
+#' fcsFiles <- list.files(ce$fcsdir, full.names = TRUE) |
|
13 |
+#' gs <<- cytobank2GatingSet(xmlfile, fcsFiles) |
|
14 |
+#' library(ggcyto) |
|
15 |
+#' autoplot(gs[[1]]) |
|
14 | 16 |
#' } |
15 | 17 |
#' @importFrom flowWorkspace GatingSet transform |
16 | 18 |
#' @importFrom ncdfFlow read.ncdfFlowSet |
17 |
-cytobank2GatingSet.default <- function(x, FCS){ |
|
19 |
+cytobank2GatingSet.default <- function(x, FCS, ...){ |
|
18 | 20 |
g <- read.gatingML.cytobank(x) |
19 | 21 |
fs <- read.ncdfFlowSet(FCS) |
20 | 22 |
gs <- GatingSet(fs) |
... | ... |
@@ -42,12 +44,11 @@ cytobank2GatingSet.default <- function(x, FCS){ |
42 | 44 |
#' @export compare.counts |
43 | 45 |
#' @examples |
44 | 46 |
#' |
45 |
-#' xmlfile <- system.file("extdata/cytotrol_tcell_cytobank.xml", package = "CytoML") |
|
46 |
-#' fcsFiles <- list.files(pattern = "CytoTrol", |
|
47 |
-#' system.file("extdata", package = "flowWorkspaceData"), full = TRUE) |
|
48 |
-#' gs <- cytobank2GatingSet(xmlfile, fcsFiles) |
|
47 |
+#' acsfile <- system.file("extdata/cytobank_experiment.acs", package = "CytoML") |
|
48 |
+#' ce <- cytobankExperiment(acsfile) |
|
49 |
+#' gs <- cytobank2GatingSet(ce) |
|
49 | 50 |
#' ## verify the stats are correct |
50 |
-#' statsfile <- system.file("extdata/cytotrol_tcell_cytobank_counts.csv", package = "CytoML") |
|
51 |
+#' statsfile <- ce$attachments[1] |
|
51 | 52 |
#' dt_merged <- compare.counts(gs, statsfile, id.vars = "population", skip = "FCS Filename") |
52 | 53 |
#' all.equal(dt_merged[, count.x], dt_merged[, count.y], tol = 5e-4) |
53 | 54 |
#' |
... | ... |
@@ -42,9 +42,11 @@ cytobankExperiment <- function(acs, exdir = tempfile()){ |
42 | 42 |
) |
43 | 43 |
, class = "cytobankExperiment") |
44 | 44 |
} |
45 |
+#' @rdname cytobank2GatingSet |
|
45 | 46 |
#' @export |
46 | 47 |
cytobank2GatingSet <- function(x, ...)UseMethod("cytobank2GatingSet") |
47 | 48 |
#' @importFrom flowWorkspace markernames<- |
49 |
+#' @param ... other arguments |
|
48 | 50 |
#' @export |
49 | 51 |
#' @method cytobank2GatingSet cytobankExperiment |
50 | 52 |
#' @rdname cytobank2GatingSet |
... | ... |
@@ -73,9 +75,10 @@ setOldClass("cytobankExperiment") |
73 | 75 |
|
74 | 76 |
#' @param x cytobankExperiment object |
75 | 77 |
#' @rdname cytobankExperiment |
78 |
+#' @param ... not used |
|
76 | 79 |
#' @export |
77 | 80 |
#' @method print cytobankExperiment |
78 |
-print.cytobankExperiment <- function(x){ |
|
81 |
+print.cytobankExperiment <- function(x, ...){ |
|
79 | 82 |
exp <- x[["experiment"]] |
80 | 83 |
cat("cytobank Experiment: ", exp[["name"]],"\n"); |
81 | 84 |
cat("gatingML File: ",x[["gatingML"]], "\n"); |
... | ... |
@@ -90,6 +93,7 @@ print.cytobankExperiment <- function(x){ |
90 | 93 |
#' @rdname cytobankExperiment |
91 | 94 |
#' @method getCompensationMatrices cytobankExperiment |
92 | 95 |
#' @export |
96 |
+#' @aliases getCompensationMatrices |
|
93 | 97 |
#' @export getCompensationMatrices |
94 | 98 |
getCompensationMatrices.cytobankExperiment <- function(x){ |
95 | 99 |
comps <- x[["experiment"]][["compensations"]] |
... | ... |
@@ -122,6 +126,7 @@ setMethod("markernames", |
122 | 126 |
}) |
123 | 127 |
|
124 | 128 |
#' @rdname cytobankExperiment |
129 |
+#' @param do.NULL,prefix not used |
|
125 | 130 |
#' @export |
126 | 131 |
setMethod("colnames", |
127 | 132 |
signature=signature(x="cytobankExperiment"), |
... | ... |
@@ -148,7 +153,8 @@ get_panel_per_file <- function(ce){ |
148 | 153 |
#' @export |
149 | 154 |
#' @method getTransformations cytobankExperiment |
150 | 155 |
#' @export getTransformations |
151 |
-getTransformations.cytobankExperiment <- function(x){ |
|
156 |
+#' @aliases getTransformations |
|
157 |
+getTransformations.cytobankExperiment <- function(x, ...){ |
|
152 | 158 |
chnls <- colnames(x) |
153 | 159 |
low.chnls <- tolower(chnls) |
154 | 160 |
scales <- x$experiment$scales |
... | ... |
@@ -127,7 +127,7 @@ setMethod("closeWorkspace","flowJoWorkspace",function(workspace){ |
127 | 127 |
#' @return the macthed workspace type |
128 | 128 |
#' @noRd |
129 | 129 |
.getWorkspaceType <- function(wsversion){ |
130 |
- curSupport <- unlist(flowWorkspace.par.get("flowJo_versions")) |
|
130 |
+ curSupport <- unlist(CytoML.par.get("flowJo_versions")) |
|
131 | 131 |
ver_ind <- match(wsversion, curSupport) |
132 | 132 |
if(is.na(ver_ind)) |
133 | 133 |
stop("Unsupported version: ", wsversion) |
... | ... |
@@ -244,7 +244,7 @@ setMethod("parseWorkspace",signature("flowJoWorkspace"),function(obj, ...){ |
244 | 244 |
wsversion <- obj@version |
245 | 245 |
|
246 | 246 |
wsType <- .getWorkspaceType(wsversion) |
247 |
- wsNodePath <- flowWorkspace.par.get("nodePath")[[wsType]] |
|
247 |
+ wsNodePath <- CytoML.par.get("nodePath")[[wsType]] |
|
248 | 248 |
|
249 | 249 |
#sample info |
250 | 250 |
allSamples <- .getSamples(x, wsType, sampNloc = sampNloc) |
... | ... |
@@ -692,7 +692,7 @@ getFileNames <- function(ws){ |
692 | 692 |
} |
693 | 693 |
} |
694 | 694 |
.getFileNames <- function(x, wsType){ |
695 |
- wsNodePath <- flowWorkspace.par.get("nodePath")[[wsType]] |
|
695 |
+ wsNodePath <- CytoML.par.get("nodePath")[[wsType]] |
|
696 | 696 |
unlist(xpathApply(x, file.path(wsNodePath[["sample"]], "Keywords/Keyword[@name='$FIL']") |
697 | 697 |
, function(x)xmlGetAttr(x,"value") |
698 | 698 |
) |
... | ... |
@@ -736,7 +736,7 @@ setMethod("getKeywords",c("flowJoWorkspace","character"),function(obj,y, ...){ |
736 | 736 |
x <- obj@doc |
737 | 737 |
wsversion <- obj@version |
738 | 738 |
wsType <- .getWorkspaceType(wsversion) |
739 |
- wsNodePath <- flowWorkspace.par.get("nodePath")[[wsType]] |
|
739 |
+ wsNodePath <- CytoML.par.get("nodePath")[[wsType]] |
|
740 | 740 |
.getKeywordsBySampleName(obj@doc,y, wsNodePath[["sample"]], ...) |
741 | 741 |
}) |
742 | 742 |
#' @rdname getKeywords |
... | ... |
@@ -747,7 +747,7 @@ setMethod("getKeywords",c("flowJoWorkspace","numeric"),function(obj,y, ...){ |
747 | 747 |
x <- obj@doc |
748 | 748 |
wsversion <- obj@version |
749 | 749 |
wsType <- .getWorkspaceType(wsversion) |
750 |
- wsNodePath <- flowWorkspace.par.get("nodePath")[[wsType]] |
|
750 |
+ wsNodePath <- CytoML.par.get("nodePath")[[wsType]] |
|
751 | 751 |
.getKeywordsBySampleID(obj@doc,y, wsNodePath[["sampleID"]],...) |
752 | 752 |
}) |
753 | 753 |
|
... | ... |
@@ -840,7 +840,7 @@ getFJWSubsetIndices<-function(ws,key=NULL,value=NULL,group,requiregates=TRUE){ |
840 | 840 |
x <- ws@doc |
841 | 841 |
wsversion <- ws@version |
842 | 842 |
wsType <- .getWorkspaceType(wsversion) |
843 |
- wsNodePath <- flowWorkspace.par.get("nodePath")[[wsType]] |
|
843 |
+ wsNodePath <- CytoML.par.get("nodePath")[[wsType]] |
|
844 | 844 |
|
845 | 845 |
s<- .getSamples(x, wsType); |
846 | 846 |
#TODO Use the actual value of key to name the column |
... | ... |
@@ -929,7 +929,7 @@ setMethod("getSampleGroups","flowJoWorkspace",function(x){ |
929 | 929 |
#' @importFrom stats na.omit |
930 | 930 |
.getSampleGroups<-function(x, wsType){ |
931 | 931 |
|
932 |
- wsNodePath <- flowWorkspace.par.get("nodePath")[[wsType]] |
|
932 |
+ wsNodePath <- CytoML.par.get("nodePath")[[wsType]] |
|
933 | 933 |
|
934 | 934 |
if(grepl("mac", wsType)){ |
935 | 935 |
do.call(rbind,xpathApply(x, wsNodePath[["group"]],function(x){ |
... | ... |
@@ -980,7 +980,7 @@ setMethod("getSampleGroups","flowJoWorkspace",function(x){ |
980 | 980 |
|
981 | 981 |
.getSamples<-function(x, wsType, sampNloc="keyword"){ |
982 | 982 |
|
983 |
- wsNodePath <- flowWorkspace.par.get("nodePath")[[wsType]] |
|
983 |
+ wsNodePath <- CytoML.par.get("nodePath")[[wsType]] |
|
984 | 984 |
lastwarn<-options("warn")[[1]] |
985 | 985 |
options("warn"=-1) |
986 | 986 |
top <- xmlRoot(x) |
... | ... |
@@ -12,10 +12,12 @@ NULL |
12 | 12 |
#' @importFrom graph nodeData |
13 | 13 |
#' @export |
14 | 14 |
#' @examples |
15 |
+#' \dontrun{ |
|
15 | 16 |
#' xmlfile <- system.file("extdata/cytotrol_tcell_cytobank.xml", package = "CytoML") |
16 | 17 |
#' g <- read.gatingML.cytobank(xmlfile) |
17 | 18 |
#' getNodes(g) |
18 | 19 |
#' getNodes(g, only.names = FALSE) |
20 |
+#' } |
|
19 | 21 |
setMethod("getNodes", signature = c("graphGML"), |
20 | 22 |
definition = function(x, y |
21 | 23 |
, order = c("default", "bfs", "dfs", "tsort") |
... | ... |
@@ -68,10 +70,12 @@ setMethod("getNodes", signature = c("graphGML"), |
68 | 70 |
#' @export |
69 | 71 |
#' @return a graphNEL node |
70 | 72 |
#' @examples |
73 |
+#' \dontrun{ |
|
71 | 74 |
#' xmlfile <- system.file("extdata/cytotrol_tcell_cytobank.xml", package = "CytoML") |
72 | 75 |
#' g <- read.gatingML.cytobank(xmlfile) |
73 | 76 |
#' getChildren(g, "GateSet_722326") |
74 | 77 |
#' getParent(g, "GateSet_722326") |
78 |
+#' } |
|
75 | 79 |
#' @importClassesFrom methods character ANY data.frame environment list logical matrix missing numeric oldClass |
76 | 80 |
#' @importFrom flowWorkspace getChildren |
77 | 81 |
setMethod("getChildren", signature = c("graphGML", "character"), |
... | ... |
@@ -136,10 +140,11 @@ setMethod("show", signature = c("graphGML"), |
136 | 140 |
#' @importFrom graph nodeData nodes<- nodeRenderInfo<- |
137 | 141 |
#' @importFrom Rgraphviz renderGraph layoutGraph |
138 | 142 |
#' @examples |
143 |
+#' \dontrun{ |
|
139 | 144 |
#' xmlfile <- system.file("extdata/cytotrol_tcell_cytobank.xml", package = "CytoML") |
140 | 145 |
#' g <- read.gatingML.cytobank(xmlfile) |
141 | 146 |
#' plot(g) |
142 |
-#' |
|
147 |
+#'} |
|
143 | 148 |
setMethod("plot", signature = c(x = "graphGML", y = "missing"), definition = function(x, y = "missing", label = c("popName", "gateName")){ |
144 | 149 |
label <- match.arg(label, c("popName", "gateName")) |
145 | 150 |
if(label == "popName") |
... | ... |
@@ -286,13 +291,14 @@ getCompensationMatrices.graphGML <- function(x){ |
286 | 291 |
|
287 | 292 |
#' Extract transformations from graphGML object. |
288 | 293 |
#' @param x graphGML |
294 |
+#' @param ... not used |
|
289 | 295 |
#' @return transformerList object |
290 | 296 |
#' @importFrom flowCore eval parameters colnames |
291 | 297 |
#' @importFrom flowWorkspace transformerList asinh_Gml2 flow_trans asinhtGml2_trans logicleGml2_trans logtGml2_trans |
292 | 298 |
#' @importFrom methods extends |
293 | 299 |
#' @export |
294 | 300 |
#' @method getTransformations graphGML |
295 |
-getTransformations.graphGML <- function(x){ |
|
301 |
+getTransformations.graphGML <- function(x, ...){ |
|
296 | 302 |
trans <- x@graphData[["transformations"]] |
297 | 303 |
if(!is.null(trans)){ |
298 | 304 |
chnls <- names(trans) |
... | ... |
@@ -25,9 +25,11 @@ setClass("graphGML", contains = "graphNEL") |
25 | 25 |
#' The gate and population name are stored in nodeData of each node. |
26 | 26 |
#' Compensation and transformations are stored in graphData. |
27 | 27 |
#' @examples |
28 |
+#' \dontrun{ |
|
28 | 29 |
#' xml <- system.file("extdata/cytotrol_tcell_cytobank.xml", package = "CytoML") |
29 | 30 |
#' g <- read.gatingML.cytobank(xml) #parse the population tree |
30 | 31 |
#' #plot(g) #visualize it |
32 |
+#' } |
|
31 | 33 |
read.gatingML.cytobank <- function(file, ...){ |
32 | 34 |
|
33 | 35 |
#parse all the elements:gate, GateSets, comp, trans |
34 | 36 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,107 @@ |
1 |
+## Store state info in this internal global environment |
|
2 |
+CytoML.state <- new.env(hash = FALSE) |
|
3 |
+CytoML.state[["par"]] <- list() |
|
4 |
+ |
|
5 |
+#' workspace version is parsed from xml node '/Workspace/version' in flowJo workspace |
|
6 |
+#' and matched with this list to dispatch to the one of the three workspace parsers |
|
7 |
+CytoML.par.init <- function(){ |
|
8 |
+ |
|
9 |
+ fj_ver <- list(win = c("1.61", "1.6") |
|
10 |
+ , macII = c("2.0") |
|
11 |
+ , macIII = c("3.0") |
|
12 |
+ , vX = c("1.8", "20.0") |
|
13 |
+ ) |
|
14 |
+ |
|
15 |
+ mac_II_path <- list(group = "/Workspace/Groups/GroupNode"# abs path |
|
16 |
+ , sampleRef = ".//SampleRefs/SampleRef"#relative GroupNode |
|
17 |
+ , sample = "/Workspace/SampleList/Sample"#abs path |
|
18 |
+ , sampleNode = "./SampleNode"#relative to sample |
|
19 |
+ , popNode = "./Population"#relative to sampleNode |
|
20 |
+ , attrName = "name" |
|
21 |
+ , compMatName = "name" |
|
22 |
+ , compMatChName = "name" |
|
23 |
+ , compMatVal = "value" |
|
24 |
+ ) |
|
25 |
+ mac_II_path[["sampleID"]] <- mac_II_path[["sample"]] |
|
26 |
+ |
|
27 |
+ #mac version 3.0 (flowJo version 9.7.2-9.7.4) |
|
28 |
+ mac_III_path <- mac_II_path |
|
29 |
+ mac_III_path[["sample"]] <- sub("SampleList", "Samples", mac_III_path[["sample"]]) |
|
30 |
+ mac_III_path[["attrName"]] <- "nodeName" |
|
31 |
+ mac_III_path[["compMatName"]] <- "matrixName" |
|
32 |
+ mac_III_path[["compMatChName"]] <- "fluorName" |
|
33 |
+ mac_III_path[["compMatVal"]] <- "spillValue" |
|
34 |
+ mac_III_path[["sampleID"]] <- mac_III_path[["sample"]] |
|
35 |
+ ####windows version |
|
36 |
+ #inherit most paths from mac |
|
37 |
+ win_path <- mac_II_path |
|
38 |
+ win_path[["popNode"]] <- "./*/Population" |
|
39 |
+ win_path[["gateDim"]] <- "*[local-name()='dimension']"#relative to gateNode |
|
40 |
+ win_path[["gateParam"]] <- "*[local-name()='parameter']"#relative to dimNode |
|
41 |
+ win_path[["sampleID"]] <- file.path(win_path[["sample"]],"DataSet") |
|
42 |
+ |
|
43 |
+ ####version X |
|
44 |
+ #inherit most paths from win |
|
45 |
+ vX_path <- win_path |
|
46 |
+ vX_path[["gateParam"]] <- "*[local-name()='fcs-dimension']"; |
|
47 |
+ |
|
48 |
+ CytoML.state[["par"]] <- list(flowJo_versions = fj_ver |
|
49 |
+ , nodePath = list(win = win_path |
|
50 |
+ , macII = mac_II_path |
|
51 |
+ , macIII = mac_III_path |
|
52 |
+ , vX = vX_path |
|
53 |
+ ) |
|
54 |
+ ) |
|
55 |
+ |
|
56 |
+} |
|
57 |
+ |
|
58 |
+## call the init function |
|
59 |
+CytoML.par.init() |
|
60 |
+ |
|
61 |
+#' CytoML.par.set sets a set of parameters in the CytoML package namespace. |
|
62 |
+#' |
|
63 |
+#' @param value A named list of values to set for category name or a list of such lists if name is missing. |
|
64 |
+#' @rdname CytoML.par.get |
|
65 |
+#' @export |
|
66 |
+CytoML.par.set <- function (name, value) |
|
67 |
+{ |
|
68 |
+ old <- CytoML.state[["par"]] |
|
69 |
+ if(name%in%names(old)){ |
|
70 |
+ CytoML.state[["par"]][[name]] <- lattice:::updateList(old[[name]], value) |
|
71 |
+ }else |
|
72 |
+ stop(name, " is not a valid CytoML parameters!") |
|
73 |
+ |
|
74 |
+ invisible() |
|
75 |
+} |
|
76 |
+ |
|
77 |
+#' Query and set session-wide parameter defaults. |
|
78 |
+#' |
|
79 |
+#' CytoML.par.get gets a set of parameters in the CytoML package namespace. |
|
80 |
+#' |
|
81 |
+#' It is currently used to add/remove the support for a specific flowJo versions (parsed from xml node '/Workspace/version' in flowJo workspace) |
|
82 |
+#' |
|
83 |
+#' @param name The name of a parameter category to get or set. |
|
84 |
+#' |
|
85 |
+#' |
|
86 |
+#' @examples |
|
87 |
+#' #get the flowJo versions currently supported |
|
88 |
+#' old <- CytoML.par.get("flowJo_versions") |
|
89 |
+#' |
|
90 |
+#' #add the new version |
|
91 |
+#' old[["win"]] <- c(old[["win"]], "1.7") |
|
92 |
+#' CytoML.par.set("flowJo_versions", old) |
|
93 |
+#' |
|
94 |
+#' CytoML.par.get("flowJo_versions") |
|
95 |
+#' |
|
96 |
+#' @export |
|
97 |
+#' @rdname CytoML.par.get |
|
98 |
+CytoML.par.get <- function (name = NULL) |
|
99 |
+{ |
|
100 |
+ lPars <- CytoML.state[["par"]] |
|
101 |
+ if (is.null(name)) |
|
102 |
+ lPars |
|
103 |
+ else if (name %in% names(lPars)) |
|
104 |
+ lPars[[name]] |
|
105 |
+ else NULL |
|
106 |
+} |
|
107 |
+ |
0 | 108 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,33 @@ |
1 |
+% Generated by roxygen2: do not edit by hand |
|
2 |
+% Please edit documentation in R/zzz.R |
|
3 |
+\name{CytoML.par.set} |
|
4 |
+\alias{CytoML.par.set} |
|
5 |
+\alias{CytoML.par.get} |
|
6 |
+\title{CytoML.par.set sets a set of parameters in the CytoML package namespace.} |
|
7 |
+\usage{ |
|
8 |
+CytoML.par.set(name, value) |
|
9 |
+ |
|
10 |
+CytoML.par.get(name = NULL) |
|
11 |
+} |
|
12 |
+\arguments{ |
|
13 |
+\item{name}{The name of a parameter category to get or set.} |
|
14 |
+ |
|
15 |
+\item{value}{A named list of values to set for category name or a list of such lists if name is missing.} |
|
16 |
+} |
|
17 |
+\description{ |
|
18 |
+CytoML.par.get gets a set of parameters in the CytoML package namespace. |
|
19 |
+} |
|
20 |
+\details{ |
|
21 |
+It is currently used to add/remove the support for a specific flowJo versions (parsed from xml node '/Workspace/version' in flowJo workspace) |
|
22 |
+} |
|
23 |
+\examples{ |
|
24 |
+ #get the flowJo versions currently supported |
|
25 |
+ old <- CytoML.par.get("flowJo_versions") |
|
26 |
+ |
|
27 |
+ #add the new version |
|
28 |
+ old[["win"]] <- c(old[["win"]], "1.7") |
|
29 |
+ CytoML.par.set("flowJo_versions", old) |
|
30 |
+ |
|
31 |
+ CytoML.par.get("flowJo_versions") |
|
32 |
+ |
|
33 |
+} |
0 | 34 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,13 @@ |
1 |
+% Generated by roxygen2: do not edit by hand |
|
2 |
+% Please edit documentation in R/zzz.R |
|
3 |
+\name{CytoML.par.init} |
|
4 |
+\alias{CytoML.par.init} |
|
5 |
+\title{workspace version is parsed from xml node '/Workspace/version' in flowJo workspace |
|
6 |
+and matched with this list to dispatch to the one of the three workspace parsers} |
|
7 |
+\usage{ |
|
8 |
+CytoML.par.init() |
|
9 |
+} |
|
10 |
+\description{ |
|
11 |
+workspace version is parsed from xml node '/Workspace/version' in flowJo workspace |
|
12 |
+and matched with this list to dispatch to the one of the three workspace parsers |
|
13 |
+} |
... | ... |
@@ -4,8 +4,7 @@ |
4 | 4 |
\alias{compare.counts} |
5 | 5 |
\title{compare the counts to cytobank's exported csv so that the parsing result can be verified.} |
6 | 6 |
\usage{ |
7 |
-\method{compare}{counts}(gs, file, id.vars = c("FCS Filename", |
|
8 |
- "population"), ...) |
|
7 |
+compare.counts(gs, file, id.vars = c("FCS Filename", "population"), ...) |
|
9 | 8 |
} |
10 | 9 |
\arguments{ |
11 | 10 |
\item{gs}{parsed GatingSet} |
... | ... |
@@ -24,12 +23,11 @@ compare the counts to cytobank's exported csv so that the parsing result can be |
24 | 23 |
} |
25 | 24 |
\examples{ |
26 | 25 |
|
27 |
-xmlfile <- system.file("extdata/cytotrol_tcell_cytobank.xml", package = "CytoML") |
|
28 |
-fcsFiles <- list.files(pattern = "CytoTrol", |
|
29 |
- system.file("extdata", package = "flowWorkspaceData"), full = TRUE) |
|
30 |
-gs <- cytobank2GatingSet(xmlfile, fcsFiles) |
|
26 |
+acsfile <- system.file("extdata/cytobank_experiment.acs", package = "CytoML") |
|
27 |
+ce <- cytobankExperiment(acsfile) |
|
28 |
+gs <- cytobank2GatingSet(ce) |
|
31 | 29 |
## verify the stats are correct |
32 |
-statsfile <- system.file("extdata/cytotrol_tcell_cytobank_counts.csv", package = "CytoML") |
|
30 |
+statsfile <- ce$attachments[1] |
|
33 | 31 |
dt_merged <- compare.counts(gs, statsfile, id.vars = "population", skip = "FCS Filename") |
34 | 32 |
all.equal(dt_merged[, count.x], dt_merged[, count.y], tol = 5e-4) |
35 | 33 |
|
... | ... |
@@ -2,10 +2,13 @@ |
2 | 2 |
% Please edit documentation in R/cytobank2GatingSet.R, R/cytobankExperiment.R |
3 | 3 |
\name{cytobank2GatingSet.default} |
4 | 4 |
\alias{cytobank2GatingSet.default} |
5 |
+\alias{cytobank2GatingSet} |
|
5 | 6 |
\alias{cytobank2GatingSet.cytobankExperiment} |
6 | 7 |
\title{A wrapper that parse the gatingML and FCS files (or cytobankExperiment object) into GatingSet} |
7 | 8 |
\usage{ |
8 |
-\method{cytobank2GatingSet}{default}(x, FCS) |
|
9 |
+\method{cytobank2GatingSet}{default}(x, FCS, ...) |
|
10 |
+ |
|
11 |
+cytobank2GatingSet(x, ...) |
|
9 | 12 |
|
10 | 13 |
\method{cytobank2GatingSet}{cytobankExperiment}(x, ...) |
11 | 14 |
} |
... | ... |
@@ -13,6 +16,8 @@ |
13 | 16 |
\item{x}{the cytobankExperiment object or the full path of gatingML file} |
14 | 17 |
|
15 | 18 |
\item{FCS}{FCS files to be loaded} |
19 |
+ |
|
20 |
+\item{...}{other arguments} |
|
16 | 21 |
} |
17 | 22 |
\value{ |
18 | 23 |
a GatingSet |
... | ... |
@@ -22,10 +27,12 @@ A wrapper that parse the gatingML and FCS files (or cytobankExperiment object) i |
22 | 27 |
} |
23 | 28 |
\examples{ |
24 | 29 |
\dontrun{ |
25 |
-xmlfile <- system.file("extdata/cytotrol_tcell_cytobank.xml", package = "CytoML") |
|
26 |
-fcsFiles <- list.files(pattern = "CytoTrol", |
|
27 |
- system.file("extdata", package = "flowWorkspaceData"), full = TRUE) |
|
28 |
-gs <- cytobank2GatingSet(xmlfile, fcsFiles) |
|
29 |
-#plotGate(gs[[1]]) |
|
30 |
+acsfile <- system.file("extdata/cytobank_experiment.acs", package = "CytoML") |
|
31 |
+ce <- cytobankExperiment(acsfile) |
|
32 |
+xmlfile <- ce$gatingML |
|
33 |
+fcsFiles <- list.files(ce$fcsdir, full.names = TRUE) |
|
34 |
+gs <<- cytobank2GatingSet(xmlfile, fcsFiles) |
|
35 |
+library(ggcyto) |
|
36 |
+autoplot(gs[[1]]) |
|
30 | 37 |
} |
31 | 38 |
} |
... | ... |
@@ -5,16 +5,18 @@ |
5 | 5 |
\alias{cytobankExperiment} |
6 | 6 |
\alias{print.cytobankExperiment} |
7 | 7 |
\alias{getCompensationMatrices.cytobankExperiment} |
8 |
+\alias{getCompensationMatrices} |
|
8 | 9 |
\alias{markernames,cytobankExperiment-method} |
9 | 10 |
\alias{colnames,cytobankExperiment-method} |
10 | 11 |
\alias{getTransformations.cytobankExperiment} |
12 |
+\alias{getTransformations} |
|
11 | 13 |
\alias{sampleNames,cytobankExperiment-method} |
12 | 14 |
\alias{pData,cytobankExperiment-method} |
13 | 15 |
\title{Construct cytobankExperiment object from ACS file} |
14 | 16 |
\usage{ |
15 | 17 |
cytobankExperiment(acs, exdir = tempfile()) |
16 | 18 |
|
17 |
-\method{print}{cytobankExperiment}(x) |
|
19 |
+\method{print}{cytobankExperiment}(x, ...) |
|
18 | 20 |
|
19 | 21 |
\method{getCompensationMatrices}{cytobankExperiment}(x) |
20 | 22 |
|
... | ... |
@@ -23,7 +25,7 @@ cytobankExperiment(acs, exdir = tempfile()) |
23 | 25 |
\S4method{colnames}{cytobankExperiment}(x, do.NULL = "missing", |
24 | 26 |
prefix = "missing") |
25 | 27 |
|
26 |
-\method{getTransformations}{cytobankExperiment}(x) |
|
28 |
+\method{getTransformations}{cytobankExperiment}(x, ...) |
|
27 | 29 |
|
28 | 30 |
\S4method{sampleNames}{cytobankExperiment}(object) |
29 | 31 |
|
... | ... |
@@ -36,7 +38,11 @@ cytobankExperiment(acs, exdir = tempfile()) |
36 | 38 |
|
37 | 39 |
\item{x}{cytobankExperiment object} |
38 | 40 |
|
41 |
+\item{...}{not used} |
|
42 |
+ |
|
39 | 43 |
\item{object}{cytobankExperiment object} |
44 |
+ |
|
45 |
+\item{do.NULL, prefix}{not used} |
|
40 | 46 |
} |
41 | 47 |
\value{ |
42 | 48 |
cytobankExperiment object |
... | ... |
@@ -19,8 +19,10 @@ a graphNEL node |
19 | 19 |
get children nodes |
20 | 20 |
} |
21 | 21 |
\examples{ |
22 |
+\dontrun{ |
|
22 | 23 |
xmlfile <- system.file("extdata/cytotrol_tcell_cytobank.xml", package = "CytoML") |
23 | 24 |
g <- read.gatingML.cytobank(xmlfile) |
24 | 25 |
getChildren(g, "GateSet_722326") |
25 | 26 |
getParent(g, "GateSet_722326") |
26 | 27 |
} |
28 |
+} |
... | ... |
@@ -24,8 +24,10 @@ It returns the node names and population names by default. Or return the entire |
24 | 24 |
get nodes from {graphGML} object |
25 | 25 |
} |
26 | 26 |
\examples{ |
27 |
+\dontrun{ |
|
27 | 28 |
xmlfile <- system.file("extdata/cytotrol_tcell_cytobank.xml", package = "CytoML") |
28 | 29 |
g <- read.gatingML.cytobank(xmlfile) |
29 | 30 |
getNodes(g) |
30 | 31 |
getNodes(g, only.names = FALSE) |
31 | 32 |
} |
33 |
+} |
... | ... |
@@ -4,10 +4,12 @@ |
4 | 4 |
\alias{getTransformations.graphGML} |
5 | 5 |
\title{Extract transformations from graphGML object.} |
6 | 6 |
\usage{ |
7 |
-\method{getTransformations}{graphGML}(x) |
|
7 |
+\method{getTransformations}{graphGML}(x, ...) |
|
8 | 8 |
} |
9 | 9 |
\arguments{ |
10 | 10 |
\item{x}{graphGML} |
11 |
+ |
|
12 |
+\item{...}{not used} |
|
11 | 13 |
} |
12 | 14 |
\value{ |
13 | 15 |
transformerList object |
... | ... |
@@ -22,8 +22,9 @@ nothing |
22 | 22 |
The node with dotted order represents the population that has tailored gates (sample-specific gates) defined. |
23 | 23 |
} |
24 | 24 |
\examples{ |
25 |
+\dontrun{ |
|
25 | 26 |
xmlfile <- system.file("extdata/cytotrol_tcell_cytobank.xml", package = "CytoML") |
26 | 27 |
g <- read.gatingML.cytobank(xmlfile) |
27 | 28 |
plot(g) |
28 |
- |
|
29 |
+} |
|
29 | 30 |
} |
... | ... |
@@ -21,7 +21,9 @@ The Default parser (flowUtils::read.gatingML) does not parse the population tre |
21 | 21 |
the custom information from cytobank. (e.g. gate name, fcs filename). |
22 | 22 |
} |
23 | 23 |
\examples{ |
24 |
+\dontrun{ |
|
24 | 25 |
xml <- system.file("extdata/cytotrol_tcell_cytobank.xml", package = "CytoML") |
25 | 26 |
g <- read.gatingML.cytobank(xml) #parse the population tree |
26 | 27 |
#plot(g) #visualize it |
27 | 28 |
} |
29 |
+} |
... | ... |
@@ -7,7 +7,7 @@ This makefile requires GNU Make. |
7 | 7 |
endif |
8 | 8 |
|
9 | 9 |
CXX_STD = CXX11 |
10 |
-PKG_CPPFLAGS =-DROUT -I../inst/include/ @PKG_CPPFLAGS@ -Wno-deprecated-declarations |
|
10 |
+PKG_CPPFLAGS =-DROUT -I../inst/include/ @PKG_CPPFLAGS@ |
|
11 | 11 |
PKG_LIBS =`${R_HOME}/bin/Rscript -e "RProtoBufLib:::LdFlags();cat(' ');RcppParallel::RcppParallelLibs()"` @PKG_LIBS@ |
12 | 12 |
|
13 | 13 |
USERDIR = ${R_PACKAGE_DIR}/lib${R_ARCH} |