1 | 1 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,28 @@ |
1 |
+Package: CytoML |
|
2 |
+Type: Package |
|
3 |
+Title: GatingML interface for openCyto |
|
4 |
+Version: 0.1 |
|
5 |
+Date: 2016-04-15 |
|
6 |
+Author: Mike Jiang |
|
7 |
+Maintainer: Mike Jiang <wjiang2@fhcrc.org> |
|
8 |
+Description: This package is designed to use GatingML2.0 as the standard format to exchange the gated data with other software platform. |
|
9 |
+License: Artistic-2.0 |
|
10 |
+LazyData: TRUE |
|
11 |
+Imports: |
|
12 |
+ flowCore, |
|
13 |
+ flowWorkspace, |
|
14 |
+ XML, |
|
15 |
+ data.table, |
|
16 |
+ flowUtils (>= 1.35.7), |
|
17 |
+ jsonlite, |
|
18 |
+ RBGL, |
|
19 |
+ graph, |
|
20 |
+ base64enc |
|
21 |
+biocViews: FlowCytometry, DataImport, DataRepresentation |
|
22 |
+Suggests: |
|
23 |
+ testthat, |
|
24 |
+ flowWorkspaceData, |
|
25 |
+ knitr, |
|
26 |
+ ggcyto |
|
27 |
+VignetteBuilder: knitr |
|
28 |
+RoxygenNote: 5.0.1 |
0 | 29 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,97 @@ |
1 |
+# Generated by roxygen2 (4.1.0): do not edit by hand |
|
2 |
+ |
|
3 |
+S3method(extend,ellipsoidGate) |
|
4 |
+S3method(extend,polygonGate) |
|
5 |
+S3method(extend,rectangleGate) |
|
6 |
+export(GatingSet2GatingML) |
|
7 |
+export(compare.counts) |
|
8 |
+export(extend) |
|
9 |
+export(parse.gatingML) |
|
10 |
+export(read.gatingML.cytobank) |
|
11 |
+exportClasses(graphGML) |
|
12 |
+exportMethods(compensate) |
|
13 |
+exportMethods(gating) |
|
14 |
+exportMethods(getChildren) |
|
15 |
+exportMethods(getCompensationMatrices) |
|
16 |
+exportMethods(getGate) |
|
17 |
+exportMethods(getNodes) |
|
18 |
+exportMethods(getParent) |
|
19 |
+exportMethods(getTransformations) |
|
20 |
+exportMethods(plot) |
|
21 |
+exportMethods(show) |
|
22 |
+import(data.table) |
|
23 |
+importClassesFrom(Biobase,AssayData) |
|
24 |
+importClassesFrom(graph,graph) |
|
25 |
+importClassesFrom(graph,graphBase) |
|
26 |
+importClassesFrom(graph,graphNEL) |
|
27 |
+importClassesFrom(methods,ANY) |
|
28 |
+importClassesFrom(methods,character) |
|
29 |
+importClassesFrom(methods,data.frame) |
|
30 |
+importClassesFrom(methods,environment) |
|
31 |
+importClassesFrom(methods,list) |
|
32 |
+importClassesFrom(methods,logical) |
|
33 |
+importClassesFrom(methods,matrix) |
|
34 |
+importClassesFrom(methods,missing) |
|
35 |
+importClassesFrom(methods,numeric) |
|
36 |
+importClassesFrom(methods,oldClass) |
|
37 |
+importFrom(RBGL,tsort) |
|
38 |
+importFrom(Rgraphviz,layoutGraph) |
|
39 |
+importFrom(Rgraphviz,renderGraph) |
|
40 |
+importFrom(XML,"xmlAttrs<-") |
|
41 |
+importFrom(XML,addChildren) |
|
42 |
+importFrom(XML,getNodeSet) |
|
43 |
+importFrom(XML,newXMLNode) |
|
44 |
+importFrom(XML,saveXML) |
|
45 |
+importFrom(XML,xmlAttrs) |
|
46 |
+importFrom(XML,xmlChildren) |
|
47 |
+importFrom(XML,xmlElementsByTagName) |
|
48 |
+importFrom(XML,xmlGetAttr) |
|
49 |
+importFrom(XML,xmlName) |
|
50 |
+importFrom(XML,xmlNode) |
|
51 |
+importFrom(XML,xmlRoot) |
|
52 |
+importFrom(XML,xmlTree) |
|
53 |
+importFrom(XML,xmlTreeParse) |
|
54 |
+importFrom(XML,xmlValue) |
|
55 |
+importFrom(base64enc,base64decode) |
|
56 |
+importFrom(base64enc,base64encode) |
|
57 |
+importFrom(flowCore,"parameters<-") |
|
58 |
+importFrom(flowCore,colnames) |
|
59 |
+importFrom(flowCore,compensate) |
|
60 |
+importFrom(flowCore,ellipsoidGate) |
|
61 |
+importFrom(flowCore,eval) |
|
62 |
+importFrom(flowCore,parameters) |
|
63 |
+importFrom(flowCore,polygonGate) |
|
64 |
+importFrom(flowCore,rectangleGate) |
|
65 |
+importFrom(flowUtils,read.gatingML) |
|
66 |
+importFrom(flowUtils,write.gatingML) |
|
67 |
+importFrom(flowWorkspace,GatingSet) |
|
68 |
+importFrom(flowWorkspace,add) |
|
69 |
+importFrom(flowWorkspace,asinh_Gml2) |
|
70 |
+importFrom(flowWorkspace,flow_trans) |
|
71 |
+importFrom(flowWorkspace,getChildren) |
|
72 |
+importFrom(flowWorkspace,getCompensationMatrices) |
|
73 |
+importFrom(flowWorkspace,getGate) |
|
74 |
+importFrom(flowWorkspace,getNodes) |
|
75 |
+importFrom(flowWorkspace,getParent) |
|
76 |
+importFrom(flowWorkspace,getPopStats) |
|
77 |
+importFrom(flowWorkspace,getTransformations) |
|
78 |
+importFrom(flowWorkspace,recompute) |
|
79 |
+importFrom(flowWorkspace,sampleNames) |
|
80 |
+importFrom(flowWorkspace,transform) |
|
81 |
+importFrom(flowWorkspace,transformerList) |
|
82 |
+importFrom(graph,"nodeData<-") |
|
83 |
+importFrom(graph,"nodeDataDefaults<-") |
|
84 |
+importFrom(graph,"nodeRenderInfo<-") |
|
85 |
+importFrom(graph,"nodes<-") |
|
86 |
+importFrom(graph,addEdge) |
|
87 |
+importFrom(graph,edges) |
|
88 |
+importFrom(graph,graphNEL) |
|
89 |
+importFrom(graph,inEdges) |
|
90 |
+importFrom(graph,nodeData) |
|
91 |
+importFrom(graph,removeNode) |
|
92 |
+importFrom(graphics,plot) |
|
93 |
+importFrom(jsonlite,fromJSON) |
|
94 |
+importFrom(jsonlite,toJSON) |
|
95 |
+importFrom(methods,show) |
|
96 |
+importFrom(ncdfFlow,read.ncdfFlowSet) |
|
97 |
+importFrom(openCyto,gating) |
0 | 98 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,653 @@ |
1 |
+#' Convert a GatingSet to gatingML |
|
2 |
+#' |
|
3 |
+#' this function retrieves the gates from GatingSet |
|
4 |
+#' and writes a customed GatingML-2.0 file |
|
5 |
+#' which can then be imported into cytobank |
|
6 |
+#' operation: |
|
7 |
+#' 1. Read in gate geometry, compensation and transformation from gatingSet |
|
8 |
+#' 2. Rescale gate boundaries with flowJoTrans() so gates show up in flowJo |
|
9 |
+#' 3. Save gates and hierarchy structure to R environment |
|
10 |
+#' 4. Write environment out to gatingML using write.GatingML() |
|
11 |
+#' @importFrom flowUtils write.gatingML |
|
12 |
+#' @importFrom XML saveXML xmlTreeParse xmlRoot |
|
13 |
+#' @export |
|
14 |
+#' @examples |
|
15 |
+#' \dontrun{ |
|
16 |
+#' library(CytoML) |
|
17 |
+#' dataDir <- system.file("extdata",package="flowWorkspaceData") |
|
18 |
+#' gs <- load_gs(list.files(dataDir, pattern = "gs_manual",full = TRUE)) |
|
19 |
+#' outFile <- tempfile(fileext = ".xml") |
|
20 |
+#' GatingSet2GatingML(gs, outFile) |
|
21 |
+#' } |
|
22 |
+GatingSet2GatingML <- function(gs, outFile, showHidden = FALSE, ...){ |
|
23 |
+ flowEnv <- GatingSet2Environment(gs, showHidden = showHidden, ...) |
|
24 |
+ tmp <- tempfile(fileext = ".xml")#ensure correct file extension for xmlTreeParse to work |
|
25 |
+ flowUtils::write.gatingML(flowEnv, tmp) |
|
26 |
+ tree <- xmlTreeParse(tmp, trim = FALSE) |
|
27 |
+ root <- xmlRoot(tree) |
|
28 |
+ # browser() |
|
29 |
+ |
|
30 |
+ root <- addCustomInfo(root, gs, flowEnv, showHidden = showHidden, ...) |
|
31 |
+ #add pop (GateSet/BooleanAndGate) |
|
32 |
+ root <- addGateSets(root, gs, flowEnv[["guid_mapping"]], showHidden = showHidden) |
|
33 |
+ #add experiment info to custom node |
|
34 |
+ root <- addExperimentInfo(root) |
|
35 |
+ saveXML(root, file = outFile) |
|
36 |
+} |
|
37 |
+ |
|
38 |
+ |
|
39 |
+#' extract the trans, comps and gates into GML2 compatible format |
|
40 |
+#' and save to environment |
|
41 |
+GatingSet2Environment <- function(gs, cytobank.default.scale = TRUE, showHidden) { |
|
42 |
+ if(cytobank.default.scale) |
|
43 |
+ warning("With 'cytobank.default.scale' set to 'TRUE', data and gates will be re-transformed with cytobank's default scaling settings, which may affect how gates look like.") |
|
44 |
+ flowEnv <- new.env(parent = emptyenv()) |
|
45 |
+ |
|
46 |
+ #parse comp and channel names |
|
47 |
+ comp <- gs@compensation |
|
48 |
+ if(is.null(comp)){ |
|
49 |
+ #(assume it is identical across samples) |
|
50 |
+ comp.obj <- flowWorkspace:::.cpp_getCompensation(gs@pointer, sampleNames(gs)[1]) |
|
51 |
+ if(is.null(comp.obj)){ |
|
52 |
+ #no compensation and channel names in transformation are not prefixed |
|
53 |
+ chnls <- colnames(getData(gs)) |
|
54 |
+ }else{ |
|
55 |
+ #parsed from flowJo and channel names are usually prefixed |
|
56 |
+ #thus get the raw channel names from here |
|
57 |
+ chnls <- comp.obj[["parameters"]] |
|
58 |
+ comp <- compensation(matrix(comp.obj$spillOver |
|
59 |
+ ,nrow=length(chnls) |
|
60 |
+ ,ncol=length(chnls) |
|
61 |
+ ,byrow=TRUE |
|
62 |
+ ,dimnames=list(chnls,chnls) |
|
63 |
+ ) |
|
64 |
+ ) |
|
65 |
+ |
|
66 |
+ } |
|
67 |
+ }else{ |
|
68 |
+ #compensation was added in R |
|
69 |
+ #channel names are not prefixed |
|
70 |
+ chnls <- as.vector(parameters(comp)) |
|
71 |
+ |
|
72 |
+ } |
|
73 |
+ |
|
74 |
+ #add comp |
|
75 |
+ if(!is.null(comp)){ |
|
76 |
+ #prefix the channels since cytobank expect that |
|
77 |
+ prefix_chnls <- paste0("Comp_", chnls) |
|
78 |
+ rownames(comp@spillover) <- prefix_chnls #change fluorochromes and leave detector(colnames) unchanged |
|
79 |
+ comp <- compensation(comp@spillover) |
|
80 |
+ |
|
81 |
+ compId <- identifier(comp) |
|
82 |
+ compId <- paste("Spill", compId, sep = "_") |
|
83 |
+ identifier(comp) <- compId |
|
84 |
+ |
|
85 |
+ flowEnv[[compId]] <- comp |
|
86 |
+ }else |
|
87 |
+ prefix_chnls <- chnls |
|
88 |
+ |
|
89 |
+ |
|
90 |
+ |
|
91 |
+ #add trans (assume it is identical across samples) |
|
92 |
+ trans <- getTransformations(gs[[1]], only.function = FALSE) |
|
93 |
+ |
|
94 |
+ if(length(trans) == 0) |
|
95 |
+ stop("no transformation is found in GatingSet!") |
|
96 |
+ trans.Gm2objs <- list() |
|
97 |
+ rescale.gate <- FALSE |
|
98 |
+ for(transName in names(trans)){ |
|
99 |
+ trans.obj <- trans[[transName]] |
|
100 |
+ type <- trans.obj[["name"]] |
|
101 |
+ ind <- sapply(chnls, grepl, x = transName, USE.NAMES = FALSE) |
|
102 |
+ nMatched <- sum(ind) |
|
103 |
+ if(nMatched > 1) |
|
104 |
+ stop("More than one channels matched to transformation: ", transName) |
|
105 |
+ else if(nMatched == 1){ |
|
106 |
+ trans.func <- trans.obj[["transform"]] |
|
107 |
+ chnl <- chnls[ind] |
|
108 |
+ prefix_chnl <- prefix_chnls[ind] |
|
109 |
+ param.obj <- compensatedParameter(prefix_chnl |
|
110 |
+ , spillRefId = compId |
|
111 |
+ , searchEnv = flowEnv |
|
112 |
+ , transformationId = prefix_chnl) |
|
113 |
+ |
|
114 |
+ if(type == "asinhtGml2"){ |
|
115 |
+ #extract parameters |
|
116 |
+ env <- environment(trans.func) |
|
117 |
+ transID <- paste0("Tr_Arcsinh_", prefix_chnl) |
|
118 |
+ flowEnv[[transID]] <- asinhtGml2(parameters = param.obj |
|
119 |
+ , M = env[["m"]] |
|
120 |
+ , T = env[["t"]] |
|
121 |
+ , A = env[["a"]] |
|
122 |
+ , transformationId = transID |
|
123 |
+ ) |
|
124 |
+ }else if(type == "logicleGml2"){ |
|
125 |
+ #extract parameters |
|
126 |
+ env <- environment(trans.func) |
|
127 |
+ transID <- paste0("Tr_logicleGml2_", prefix_chnl) |
|
128 |
+ flowEnv[[transID]] <- logicletGml2(parameters = param.obj |
|
129 |
+ , M = env[["M"]] |
|
130 |
+ , T = env[["T"]] |
|
131 |
+ , A = env[["A"]] |
|
132 |
+ , W = env[["W"]] |
|
133 |
+ , transformationId = transID |
|
134 |
+ ) |
|
135 |
+ }else if(type == "logicle"){ |
|
136 |
+ #extract parameters |
|
137 |
+ env <- environment(trans.func) |
|
138 |
+ transID <- paste0("Tr_logicle_", prefix_chnl) |
|
139 |
+ flowEnv[[transID]] <- logicletGml2(parameters = param.obj |
|
140 |
+ , M = env[["m"]] |
|
141 |
+ , T = env[["t"]] |
|
142 |
+ , A = env[["a"]] |
|
143 |
+ , W = env[["w"]] |
|
144 |
+ , transformationId = transID |
|
145 |
+ ) |
|
146 |
+ rescale.gate <- TRUE |
|
147 |
+ }else if(type %in% c("flowJo_biexp", "flowJo_fasinh")){ |
|
148 |
+ transID <- paste0("Tr_Arcsinh_", prefix_chnl) |
|
149 |
+ #use asinhtGml2 with cytobank default setting |
|
150 |
+ flowEnv[[transID]] <- asinhtGml2(parameters = param.obj |
|
151 |
+ , M = 0.43429448190325176 |
|
152 |
+ , T = 176.2801790465702 |
|
153 |
+ , A = 0.0 |
|
154 |
+ , transformationId = transID |
|
155 |
+ ) |
|
156 |
+ rescale.gate <- TRUE |
|
157 |
+ }else{ |
|
158 |
+ # browser() |
|
159 |
+ stop("unsupported trans: ", type) |
|
160 |
+ } |
|
161 |
+ |
|
162 |
+ |
|
163 |
+ } |
|
164 |
+ |
|
165 |
+ if(cytobank.default.scale){ |
|
166 |
+ rescale.gate <- TRUE |
|
167 |
+ #overwrite the customed scale with default one |
|
168 |
+ flowEnv[[transID]] <- asinhtGml2(parameters = param.obj |
|
169 |
+ , M = 0.43429448190325176 |
|
170 |
+ , T = 176.2801790465702 |
|
171 |
+ , A = 0.0 |
|
172 |
+ , transformationId = transID) |
|
173 |
+ } |
|
174 |
+ |
|
175 |
+ #save another copy of trans.obj in the list |
|
176 |
+ trans.Gm2objs[[chnl]] <- flowEnv[[transID]] |
|
177 |
+ } |
|
178 |
+ |
|
179 |
+ #add gates and pops(as GateSets) |
|
180 |
+ nodePaths <- getNodes(gs, showHidden = showHidden)[-1] |
|
181 |
+ fcs_names <- pData(gs)[["name"]] |
|
182 |
+ rng <- range(getData(gs[[1]], use.exprs = FALSE)) |
|
183 |
+ for(gate_id in seq_along(nodePaths)){ |
|
184 |
+ nodePath <- nodePaths[gate_id] |
|
185 |
+ gates <- getGate(gs, nodePath) |
|
186 |
+ popName <- basename(nodePath) |
|
187 |
+ for(fcs_id in seq_along(fcs_names)){ |
|
188 |
+ sn <- fcs_names[fcs_id] |
|
189 |
+ gate <- gates[[sn]] |
|
190 |
+# browser() |
|
191 |
+ #cytobank does not support negated gate |
|
192 |
+ #we have to create inverse gate on our end |
|
193 |
+ if(flowWorkspace:::isNegated(gs[[sn]], nodePath)){ |
|
194 |
+ gate <- inverse(gate, rng) |
|
195 |
+ } |
|
196 |
+ #transform to raw scale |
|
197 |
+ #and attach comp and trans reference to parameters |
|
198 |
+ gate <- processGate(gate, trans.Gm2objs, compId, flowEnv, rescale.gate, trans) |
|
199 |
+ |
|
200 |
+ parent <- getParent(gs, nodePath) |
|
201 |
+ if(parent == "root") |
|
202 |
+ parent_id <- 0 |
|
203 |
+ else |
|
204 |
+ parent_id <- match(parent, nodePaths) |
|
205 |
+ |
|
206 |
+ guid <- paste("gate", gate_id, fcs_id, sep = "_") |
|
207 |
+ identifier(gate) <- guid |
|
208 |
+ #add gate |
|
209 |
+ flowEnv[[guid]] <- gate |
|
210 |
+ |
|
211 |
+ } |
|
212 |
+ } |
|
213 |
+ flowEnv |
|
214 |
+} |
|
215 |
+ |
|
216 |
+#' @importFrom base64enc base64encode base64decode |
|
217 |
+base64encode_cytobank <- function(x){ |
|
218 |
+ x <- base64encode(charToRaw(x)) |
|
219 |
+ x <- gsub("=", ".", x) |
|
220 |
+ x <- gsub("\\+", "_", x) |
|
221 |
+ x <- gsub("/", "-", x) |
|
222 |
+ x |
|
223 |
+} |
|
224 |
+base64decode_cytobank <- function(x){ |
|
225 |
+ x <- gsub("\\.", "=", x) |
|
226 |
+ x <- gsub("_", "\\+", x) |
|
227 |
+ x <- gsub("-", "/", x) |
|
228 |
+ base64decode(x) |
|
229 |
+} |
|
230 |
+ |
|
231 |
+setMethod("transform", signature = c("polygonGate"), function(`_data`, ...){ |
|
232 |
+ .transform.polygonGate(`_data`, ...) |
|
233 |
+}) |
|
234 |
+.transform.polygonGate <- function(gate, trans.fun, param){ |
|
235 |
+ gate@boundaries[, param] <- trans.fun(gate@boundaries[, param]) |
|
236 |
+ gate |
|
237 |
+} |
|
238 |
+ |
|
239 |
+setMethod("transform", signature = c("ellipsoidGate"), function(`_data`, ...){ |
|
240 |
+ # .transform.ellipsoidGate(`_data`, ...) |
|
241 |
+ transform(as(`_data`, "polygonGate"), ...) |
|
242 |
+}) |
|
243 |
+# somehow ellips shape is not well perseved after transforming the two antipods and mean |
|
244 |
+.transform.ellipsoidGate <- function(gate, trans.fun, param){ |
|
245 |
+ #convert cov format to antipotal format since cov can not be transformed independently on each param |
|
246 |
+ #it is based on 5.3.1 of gatingML2 doc |
|
247 |
+ mu <- gate@mean |
|
248 |
+ CC <- gate@cov |
|
249 |
+ dims <- colnames(CC) |
|
250 |
+ x <- dims[1] |
|
251 |
+ y <- dims[2] |
|
252 |
+ D <- gate@distance |
|
253 |
+ |
|
254 |
+# term <- sqrt((CC[x, x] - CC[y, y]) ^ 2 + 4 * CC[x, y] ^ 2) |
|
255 |
+# lambda <- ((CC[x, x] + CC[y, y]) + c(term, -term)) / 2 |
|
256 |
+# |
|
257 |
+# if(CC[x,y] == 0){ |
|
258 |
+# X1 <- c(1, 0) |
|
259 |
+# X2 <- c(0, 1) |
|
260 |
+# }else{ |
|
261 |
+# X1 <- c(lambda[1] - CC[y, y], CC[x, y]) |
|
262 |
+# X2 <- c(lambda[2] - CC[y, y], CC[x, y]) |
|
263 |
+# } |
|
264 |
+ #compute eigen value (for a, b) and eigen vector (for angle) |
|
265 |
+ res <- eigen(CC) |
|
266 |
+ lambda <- res[["values"]] |
|
267 |
+ X1 <- res[["vectors"]][,1] |
|
268 |
+ if(X1[1] == 0){ |
|
269 |
+ theta <- pi/2 |
|
270 |
+ }else{ |
|
271 |
+ theta <- atan(X1[2]/X1[1]) |
|
272 |
+ } |
|
273 |
+ |
|
274 |
+ a <- sqrt(lambda[1] * D ^ 2) |
|
275 |
+ b <- sqrt(lambda[2] * D ^ 2) |
|
276 |
+ |
|
277 |
+ #get coordinates of centred antipodal points |
|
278 |
+ antipod1 <- c(a * cos(theta), a * sin(theta)) |
|
279 |
+ antipod2 <- c(b * sin(theta), - b * cos(theta)) |
|
280 |
+ # browser() |
|
281 |
+ #shift to mu |
|
282 |
+ antipod1 <- antipod1 + mu |
|
283 |
+ antipod2 <- antipod2 + mu |
|
284 |
+ names(antipod1) <- dims |
|
285 |
+ names(antipod2) <- dims |
|
286 |
+ #transform the respective dim of antipods |
|
287 |
+ antipod1[param] <- trans.fun(antipod1[param]) |
|
288 |
+ antipod2[param] <- trans.fun(antipod2[param]) |
|
289 |
+ |
|
290 |
+ # transform to get new mu |
|
291 |
+ mu[param] <- trans.fun(mu[param]) |
|
292 |
+ #shift to new center |
|
293 |
+ antipod1 <- antipod1 - mu |
|
294 |
+ antipod2 <- antipod2 - mu |
|
295 |
+ #compute the new a, b |
|
296 |
+ a <- sqrt(sum(antipod1 ^ 2)) |
|
297 |
+ b <- sqrt(sum(antipod2 ^ 2)) |
|
298 |
+ #convert it back to the inverse covaiance mat |
|
299 |
+ |
|
300 |
+ CC.inv <- CC |
|
301 |
+ CC.inv[x, x] <- cos(theta) ^ 2 / a ^ 2 + sin(theta) ^ 2 / b ^ 2 |
|
302 |
+ CC.inv[y, y] <- sin(theta) ^ 2 / a ^ 2 + cos(theta) ^ 2 / b ^ 2 |
|
303 |
+ CC.inv[x, y] <- CC.inv[y, x] <- sin(theta) * cos(theta) * (1/a^2 - 1/b^2) |
|
304 |
+ CC <- solve(CC.inv) |
|
305 |
+ |
|
306 |
+ |
|
307 |
+ gate1 <- gate |
|
308 |
+ gate1@cov <- CC |
|
309 |
+ gate1@mean <- mu |
|
310 |
+ # browser() |
|
311 |
+ gate1 |
|
312 |
+ |
|
313 |
+} |
|
314 |
+ |
|
315 |
+setMethod("transform", signature = c("rectangleGate"), function(`_data`, ...){ |
|
316 |
+ .transform.rectangleGate(`_data`, ...) |
|
317 |
+}) |
|
318 |
+.transform.rectangleGate <- function(gate, trans.fun, param){ |
|
319 |
+ |
|
320 |
+ min <- gate@min[[param]] |
|
321 |
+ if(!is.infinite(min)) |
|
322 |
+ gate@min[[param]] <- trans.fun(min) |
|
323 |
+ |
|
324 |
+ max <- gate@max[[param]] |
|
325 |
+ if(!is.infinite(max)) |
|
326 |
+ gate@max[[param]] <- trans.fun(max) |
|
327 |
+ |
|
328 |
+ gate |
|
329 |
+ |
|
330 |
+} |
|
331 |
+#' @importFrom flowCore eval |
|
332 |
+processGate <- function(gate, gml2.trans, compId, flowEnv, rescale.gate = FALSE, orig.trans){ |
|
333 |
+ |
|
334 |
+ params <- as.vector(parameters(gate)) |
|
335 |
+ chnls <- names(gml2.trans) |
|
336 |
+ |
|
337 |
+ for(i in seq_along(params)){ |
|
338 |
+ param <- params[i] |
|
339 |
+ ind <- sapply(chnls, function(chnl)grepl(chnl, param), USE.NAMES = FALSE) |
|
340 |
+ nMatched <- sum(ind) |
|
341 |
+ if(nMatched == 0){ |
|
342 |
+ |
|
343 |
+ chnl <- gate@parameters[[i]]@parameters |
|
344 |
+ gate@parameters[[i]] <- compensatedParameter(chnl |
|
345 |
+ , spillRefId = "uncompensated"#compId |
|
346 |
+ , searchEnv = flowEnv |
|
347 |
+ , transformationId = chnl |
|
348 |
+ ) |
|
349 |
+ }else if(nMatched == 1){ |
|
350 |
+ chnl <- chnls[ind] |
|
351 |
+ orig.trans.obj <- orig.trans[[which(ind)]] |
|
352 |
+ gml2.trans.obj <- gml2.trans[[chnl]] |
|
353 |
+ if(rescale.gate){ |
|
354 |
+ inv.fun <- orig.trans.obj[["inverse"]] |
|
355 |
+ trans.fun <- eval(gml2.trans.obj) |
|
356 |
+ #rescale |
|
357 |
+ gate <- transform(gate, inv.fun, param) |
|
358 |
+ gate <- transform(gate, trans.fun, param) |
|
359 |
+ } |
|
360 |
+ |
|
361 |
+ |
|
362 |
+ #attach trans reference |
|
363 |
+ gate@parameters[[i]] <- gml2.trans.obj |
|
364 |
+ }else if(nMatched > 1) |
|
365 |
+ stop("multiple trans matched to :", param) |
|
366 |
+ } |
|
367 |
+ |
|
368 |
+ # round |
|
369 |
+ gate |
|
370 |
+ |
|
371 |
+} |
|
372 |
+ |
|
373 |
+#' @importFrom XML xmlTree |
|
374 |
+addGateSets <- function(root, gs, showHidden, ...) |
|
375 |
+{ |
|
376 |
+ |
|
377 |
+ nodePaths <- getNodes(gs, showHidden = showHidden)[-1] |
|
378 |
+ # browser() |
|
379 |
+ newNodes <- lapply(seq_along(nodePaths), function(gate_id){ |
|
380 |
+ nodePath <- nodePaths[gate_id] |
|
381 |
+ curNode <- nodePath |
|
382 |
+ pop_name <- basename(nodePath) |
|
383 |
+ gate_id_path <- gate_id |
|
384 |
+ # browser() |
|
385 |
+ repeat{ |
|
386 |
+ curNode <- getParent(gs, curNode) |
|
387 |
+ if(curNode == "root") |
|
388 |
+ break |
|
389 |
+ else{ |
|
390 |
+ cur_parent_id <- match(curNode, nodePaths) |
|
391 |
+ gate_id_path <- c(cur_parent_id, gate_id_path) |
|
392 |
+ } |
|
393 |
+ |
|
394 |
+ } |
|
395 |
+ GateSetNode(gate_id, pop_name, gate_id_path, nodePaths, ...) |
|
396 |
+ }) |
|
397 |
+ |
|
398 |
+ addChildren(root, kids = newNodes) |
|
399 |
+} |
|
400 |
+ |
|
401 |
+#' @importFrom jsonlite toJSON |
|
402 |
+#' @importFrom XML xmlNode |
|
403 |
+GateSetNode <- function(gate_id, pop_name, gate_id_path, nodePaths, guid_mapping){ |
|
404 |
+ |
|
405 |
+ attrs = c("gating:id" = paste("GateSet", gate_id, sep = "_")) |
|
406 |
+ |
|
407 |
+ definition <- toJSON(list(gates = gate_id_path, negGates = vector())) |
|
408 |
+ |
|
409 |
+ #duplicate the refs if it is the root |
|
410 |
+ ref_gate_id_path <- gate_id_path |
|
411 |
+ if(length(ref_gate_id_path) == 1) |
|
412 |
+ ref_gate_id_path <- c(ref_gate_id_path, ref_gate_id_path) |
|
413 |
+ xmlNode("gating:BooleanGate", attrs = attrs |
|
414 |
+ , xmlNode("data-type:custom_info" |
|
415 |
+ , xmlNode("cytobank" |
|
416 |
+ , xmlNode("name", pop_name) |
|
417 |
+ , xmlNode("gate_set_id", gate_id) |
|
418 |
+ , xmlNode("definition", I(definition))#set AsIs to avoid xml escaping |
|
419 |
+ ) |
|
420 |
+ ) |
|
421 |
+ |
|
422 |
+ , xmlNode("gating:and" |
|
423 |
+ #create two dummy reference |
|
424 |
+ , .children = lapply(ref_gate_id_path, function(gate_id){ |
|
425 |
+ |
|
426 |
+ guid <- guid_mapping[[gate_id]] |
|
427 |
+ attrs = c("gating:ref" = guid) |
|
428 |
+ xmlNode("gating:gateReference", attrs = attrs) |
|
429 |
+ }) |
|
430 |
+ ) |
|
431 |
+ ) |
|
432 |
+} |
|
433 |
+ |
|
434 |
+#' add customInfo nodes to each gate node and add BooleanAndGates |
|
435 |
+#' @importFrom XML xmlAttrs getNodeSet addChildren xmlAttrs<- |
|
436 |
+addCustomInfo <- function(root, gs, flowEnv, cytobank.default.scale = TRUE, showHidden){ |
|
437 |
+ nodePaths <- getNodes(gs, showHidden = showHidden)[-1] |
|
438 |
+ pd <- pData(gs) |
|
439 |
+ fcs_names <- pd[["name"]] |
|
440 |
+ fcs_guids <- rownames(pd) |
|
441 |
+ translist <- getTransformations(gs[[1]], only.function = FALSE) |
|
442 |
+ transNames <- names(translist) |
|
443 |
+ rng <- range(getData(gs[[1]], use.exprs = FALSE)) |
|
444 |
+ for(id in 1:length(root)){ |
|
445 |
+ |
|
446 |
+ curNode <- root[[id]] |
|
447 |
+ guid <- as.vector(xmlAttrs(curNode, "gating:id")) |
|
448 |
+ if(!is.null(guid)&&grepl("gate_", guid)){ |
|
449 |
+ #parse pop and fcs info from guid |
|
450 |
+ fields <- strsplit(guid, "_")[[1]] |
|
451 |
+ gate_id <- as.integer(fields[[2]]) |
|
452 |
+ fcs_id <- as.integer(fields[[3]]) |
|
453 |
+ |
|
454 |
+ nodePath <- nodePaths[gate_id] |
|
455 |
+ pop_name<- basename(nodePath) |
|
456 |
+ fcs_name <- fcs_names[fcs_id] |
|
457 |
+ fcs_guid <- fcs_guids[fcs_id] |
|
458 |
+ # browser() |
|
459 |
+ |
|
460 |
+ gate <- flowEnv[[guid]] |
|
461 |
+ gate_type <- class(gate) |
|
462 |
+ if(gate_type == "rectangleGate"){ |
|
463 |
+ if(length(parameters(gate)) == 1) |
|
464 |
+ gate_type <- "RangeGate" |
|
465 |
+ else |
|
466 |
+ gate_type <- "RectangleGate" |
|
467 |
+ }else if(gate_type == "polygonGate") |
|
468 |
+ gate_type <- "PolygonGate" |
|
469 |
+ else if(gate_type == "ellipsoidGate") |
|
470 |
+ gate_type <- "EllipseGate" |
|
471 |
+ else |
|
472 |
+ stop("unsupported gate: ", gate_type) |
|
473 |
+ # browser() |
|
474 |
+ # message(guid) |
|
475 |
+ #parse scale info from gate parameter |
|
476 |
+ scale <- lapply(gate@parameters@.Data, function(param){ |
|
477 |
+ # browser() |
|
478 |
+ if(class(param) == "compensatedParameter"){ |
|
479 |
+ if(cytobank.default.scale){ |
|
480 |
+ thisRng <- c(1, 262144.0) |
|
481 |
+ }else{ |
|
482 |
+ chnl <- as.vector(parameters(param)) |
|
483 |
+ thisRng <- rng[, chnl] |
|
484 |
+ } |
|
485 |
+ |
|
486 |
+ flag <- 1 |
|
487 |
+ argument <- "1" |
|
488 |
+ }else if(is(param, "singleParameterTransform")){ |
|
489 |
+ |
|
490 |
+ chnl <- as.vector(parameters(param@parameters)) |
|
491 |
+ chnl <- sub("(^Comp_)(.*)", "\\2", chnl) #strip the prefix before matching |
|
492 |
+ ind <- grepl(chnl, names(rng)) |
|
493 |
+ nMatched <- sum(ind) |
|
494 |
+ if(nMatched == 1){ |
|
495 |
+ if(cytobank.default.scale){ |
|
496 |
+ thisRng <- c(-200, 262144.0) |
|
497 |
+ }else |
|
498 |
+ thisRng <- rng[, ind] |
|
499 |
+ }else |
|
500 |
+ stop(chnl , " not found in range info") |
|
501 |
+ if(is(param, "asinhtGml2")){ |
|
502 |
+ flag <- 4 |
|
503 |
+ argument <- as.character(round(param@T/sinh(1))) |
|
504 |
+ }else if(is(param, "logicletGml2")){ |
|
505 |
+ flag <- 4 |
|
506 |
+ argument <- as.character(round(param@T/sinh(1))) |
|
507 |
+ }else |
|
508 |
+ stop("unsupported transform: ", class(param)) |
|
509 |
+ if(!cytobank.default.scale){ |
|
510 |
+ #inverse range into raw scale |
|
511 |
+ ind <- sapply(transNames, function(transName)grepl(chnl, transName), USE.NAMES = FALSE) |
|
512 |
+ nMatched <- sum(ind) |
|
513 |
+ if(nMatched == 1){ |
|
514 |
+ trans.obj <- translist[[which(ind)]] |
|
515 |
+ trans.fun <- trans.obj[["inverse"]] |
|
516 |
+ thisRng <- round(trans.fun(thisRng))#cytobank experiment scale expect 0 digits after decimal |
|
517 |
+ }else |
|
518 |
+ stop("can't find the transformation function in GatingSet to inverse the range for :", chnl) |
|
519 |
+ } |
|
520 |
+ |
|
521 |
+ }else |
|
522 |
+ stop("unsupported transform: ", class(param)) |
|
523 |
+ |
|
524 |
+ thisRng <- round(thisRng, 2) |
|
525 |
+ list(flag = flag, argument = argument, min = thisRng[1], max = thisRng[2], bins = 256, size = 256) |
|
526 |
+ }) |
|
527 |
+ if(length(scale) == 1){ |
|
528 |
+ scale <- unlist(scale, recursive = FALSE) |
|
529 |
+ }else{ |
|
530 |
+ names(scale) <- c("x", "y") |
|
531 |
+ } |
|
532 |
+ definition <- list(scale = scale) |
|
533 |
+ definition <- toJSON(definition, auto_unbox = TRUE) |
|
534 |
+ #insert custom info |
|
535 |
+ customNode <- customInfoNodeForGate(id, gate_id, pop_name, fcs_id, fcs_name, gate_type, definition) |
|
536 |
+ newNode <- addChildren(curNode, kids = list(customNode), at = 0) |
|
537 |
+ #modify id |
|
538 |
+ guid.new <- paste("Gate", id, base64encode_cytobank(pop_name), sep = "_") |
|
539 |
+ xmlAttrs(newNode, suppressNamespaceWarning = TRUE, append = FALSE) <- c("gating:id" = guid.new) |
|
540 |
+ #update the tree |
|
541 |
+ root[[id]] <- newNode |
|
542 |
+ |
|
543 |
+ #record the mapping between gate_id and guid.new for the refs of GateSets |
|
544 |
+ if(fcs_id == 1) |
|
545 |
+ flowEnv[["guid_mapping"]][[gate_id]] <- guid.new |
|
546 |
+ } |
|
547 |
+ } |
|
548 |
+ root |
|
549 |
+ |
|
550 |
+} |
|
551 |
+ |
|
552 |
+#' @importFrom XML newXMLNode |
|
553 |
+customInfoNodeForGate <- function(id, gate_id, pop_name, fcs_id, fcs_name, type, definition) |
|
554 |
+{ |
|
555 |
+ if(fcs_id == 1){ |
|
556 |
+ fcs_id <- fcs_name <- "" |
|
557 |
+ } |
|
558 |
+ |
|
559 |
+ #avoid using newXMLNode since it is not segfault-free. |
|
560 |
+ xmlNode("data-type:custom_info" |
|
561 |
+ , xmlNode("cytobank" |
|
562 |
+ , xmlNode("name", pop_name) |
|
563 |
+ , xmlNode("id", id) |
|
564 |
+ , xmlNode("gate_id", gate_id) |
|
565 |
+ , xmlNode("type", type) |
|
566 |
+ , xmlNode("version", 1) |
|
567 |
+ , xmlNode("fcs_file_id", fcs_id) |
|
568 |
+ , xmlNode("fcs_file_filename", fcs_name) |
|
569 |
+ , xmlNode("definition", I(definition)) |
|
570 |
+ ) |
|
571 |
+ ) |
|
572 |
+} |
|
573 |
+ |
|
574 |
+addExperimentInfo <- function(root, experiment_number = ""){ |
|
575 |
+ |
|
576 |
+ customNode <- root[["custom_info"]] |
|
577 |
+ customNode <- addChildren(customNode, xmlNode("flowWorkspace-version", packageVersion("flowWorkspace"))) |
|
578 |
+ |
|
579 |
+ newNode <- xmlNode("cytobank" |
|
580 |
+ , xmlNode("experiment_number", experiment_number) |
|
581 |
+ ) |
|
582 |
+ customNode <- addChildren(customNode, newNode, at = 0) |
|
583 |
+ |
|
584 |
+ root[["custom_info"]] <- customNode |
|
585 |
+ root |
|
586 |
+} |
|
587 |
+ |
|
588 |
+inverse <- function(gate, boundary){ |
|
589 |
+ UseMethod("inverse") |
|
590 |
+} |
|
591 |
+ |
|
592 |
+inverse.polygonGate <- function(gate, ...){ |
|
593 |
+ gate@boundaries <- inverse.polygon(gate@boundaries, ...) |
|
594 |
+ gate |
|
595 |
+} |
|
596 |
+inverse.ellipsoidGate <- function(gate, ...){ |
|
597 |
+ inverse(as(gate, "polygonGate"), ...) |
|
598 |
+} |
|
599 |
+inverse.rectangleGate <- function(gate, ...){ |
|
600 |
+ param <- as.vector(parameters(gate)) |
|
601 |
+ if(length(param) == 1){ |
|
602 |
+ stop("to be implemented!") |
|
603 |
+ }else |
|
604 |
+ inverse(as(gate, "polygonGate"), ...) |
|
605 |
+} |
|
606 |
+ |
|
607 |
+inverse.polygon <- function(mat, boundary){ |
|
608 |
+ |
|
609 |
+ |
|
610 |
+ dims <- colnames(mat) |
|
611 |
+ stopifnot(all(dims %in% colnames(boundary))) |
|
612 |
+ |
|
613 |
+ #enlarge the boundary to ensure the negated polygon includes all events outside of original polygon |
|
614 |
+ boundary["min", ] <- boundary["min", ] - 1e4 |
|
615 |
+ boundary["max", ] <- boundary["max", ] + 1e4 |
|
616 |
+ |
|
617 |
+ x <- dims[1] |
|
618 |
+ y <- dims[2] |
|
619 |
+ |
|
620 |
+ #find the top most point as starting point |
|
621 |
+ ind <- which.max(mat[, y]) |
|
622 |
+ #reorder mat starting from top most |
|
623 |
+ nRow <- nrow(mat) |
|
624 |
+ orig.seq <- seq_len(nRow) |
|
625 |
+ seq1 <- ind:nRow |
|
626 |
+ seq2 <- setdiff(orig.seq, seq1) |
|
627 |
+ new.seq <- c(seq1, seq2) |
|
628 |
+ new.seq |
|
629 |
+ mat.new <- mat[new.seq, ] |
|
630 |
+ |
|
631 |
+ |
|
632 |
+ mat.inv <- mat.new[1, ] |
|
633 |
+ #extend to upper bound |
|
634 |
+ pt1 <- c(mat.new[1, x], boundary["max", y]) |
|
635 |
+ mat.inv <- rbind(mat.inv, pt1, deparse.level = 0) |
|
636 |
+ #left top |
|
637 |
+ mat.inv <- rbind(mat.inv, c(boundary["min", x], boundary["max",y])) |
|
638 |
+ #left bottom |
|
639 |
+ mat.inv <- rbind(mat.inv, c(boundary["min", x], boundary["min",y])) |
|
640 |
+ #right bottom |
|
641 |
+ mat.inv <- rbind(mat.inv, c(boundary["max", x], boundary["min",y])) |
|
642 |
+ #right top |
|
643 |
+ mat.inv <- rbind(mat.inv, c(boundary["max", x], boundary["max",y])) |
|
644 |
+ #back to first extended point |
|
645 |
+ mat.inv <- rbind(mat.inv, pt1, deparse.level = 0) |
|
646 |
+ #connect to the remain mat.new in reverse order |
|
647 |
+ mat.inv <- rbind(mat.inv, mat.new[rev(seq_len(nRow)[-1]), ]) |
|
648 |
+ |
|
649 |
+# plot(mat.inv, type = "n") |
|
650 |
+# polygon(mat.new, col = "red") |
|
651 |
+# polygon(mat.inv, col = "blue") |
|
652 |
+ mat.inv |
|
653 |
+} |
0 | 654 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,368 @@ |
1 |
+#' get nodes from {graphGML} object |
|
2 |
+#' |
|
3 |
+#' @param x \code{graphGML} |
|
4 |
+#' @param y \code{character} node index. When \code{missing}, return all the nodes |
|
5 |
+#' @param order \code{character} specifying the order of nodes. options are "default", "bfs", "dfs", "tsort" |
|
6 |
+#' @param only.names \code{logical} specifiying whether user wants to get the entire \code{nodeData} or just the name of the population node |
|
7 |
+#' @return It returns the node names and population names by default. Or return the entire nodeData associated with each node. |
|
8 |
+#' @importFrom flowWorkspace getNodes |
|
9 |
+#' @importFrom graph nodeData |
|
10 |
+#' @export |
|
11 |
+#' @examples |
|
12 |
+#' \dontrun{ |
|
13 |
+#' xmlfile <- system.file("extdata/cytotrol_tcell_cytobank.xml", package = "CytoML") |
|
14 |
+#' g <- read.gatingML.cytobank(xmlfile) |
|
15 |
+#' getNodes(g) |
|
16 |
+#' getNodes(g, only.names = FALSE) |
|
17 |
+#' } |
|
18 |
+setMethod("getNodes", signature = c("graphGML"), |
|
19 |
+ definition = function(x, y |
|
20 |
+ , order = c("default", "bfs", "dfs", "tsort") |
|
21 |
+ , only.names = TRUE) { |
|
22 |
+ |
|
23 |
+ if (missing(y)){ |
|
24 |
+ res <- nodeData(x) |
|
25 |
+ order <- match.arg(order) |
|
26 |
+ if(order != "default"){ |
|
27 |
+ nodeIds <- eval(substitute(f1(x),list(f1=as.symbol(order)))) |
|
28 |
+ if(order == "dfs") |
|
29 |
+ nodeIds <- nodeIds$discovered |
|
30 |
+ res <- res[nodeIds] |
|
31 |
+ } |
|
32 |
+ }else |
|
33 |
+ { |
|
34 |
+ res <- nodeData(x, y) |
|
35 |
+ |
|
36 |
+ } |
|
37 |
+ if(only.names){ |
|
38 |
+ res <- sapply(res,`[[`,"popName") |
|
39 |
+ } |
|
40 |
+ if(length(res) == 1 && class(res) == "list") |
|
41 |
+ res <- res[[1]] |
|
42 |
+ res |
|
43 |
+}) |
|
44 |
+ |
|
45 |
+#' get full path of the parent |
|
46 |
+#' @param x \code{graphGML} |
|
47 |
+#' @param y \code{character} node index. When \code{missing}, return all the nodes |
|
48 |
+.getPath <- function(x, y){ |
|
49 |
+ #get full path |
|
50 |
+ nodeIds <- y |
|
51 |
+ thisNodeID <- y |
|
52 |
+ while(length(thisNodeID) > 0){ |
|
53 |
+ thisNodeID <- getParent(x, thisNodeID) |
|
54 |
+ nodeIds <- c(thisNodeID,nodeIds) |
|
55 |
+ } |
|
56 |
+ |
|
57 |
+ pops <- lapply(nodeIds, function(i)nodeData(x,i)[[1]][["popName"]]) |
|
58 |
+ path <- paste(pops, collapse = "/") |
|
59 |
+ paste0("/", path) |
|
60 |
+} |
|
61 |
+ |
|
62 |
+#' get children nodes |
|
63 |
+#' |
|
64 |
+#' @param obj \code{graphGML} |
|
65 |
+#' @param y \code{character} parent node path |
|
66 |
+#' @export |
|
67 |
+#' @examples |
|
68 |
+#' \dontrun{ |
|
69 |
+#' xmlfile <- system.file("extdata/cytotrol_tcell_cytobank.xml", package = "CytoML") |
|
70 |
+#' g <- read.gatingML.cytobank(xmlfile) |
|
71 |
+#' getChildren(g, "GateSet_722326") |
|
72 |
+#' getParent(g, "GateSet_722326") |
|
73 |
+#' } |
|
74 |
+#' @importClassesFrom methods character ANY data.frame environment list logical matrix missing numeric oldClass |
|
75 |
+#' @importFrom flowWorkspace getChildren |
|
76 |
+setMethod("getChildren", signature = c("graphGML", "character"), |
|
77 |
+ definition = function(obj, y) { |
|
78 |
+ edges(obj, y)[[1]] |
|
79 |
+}) |
|
80 |
+ |
|
81 |
+#' get parent nodes |
|
82 |
+#' |
|
83 |
+#' @param obj \code{graphGML} |
|
84 |
+#' @param y \code{character} child node path |
|
85 |
+#' |
|
86 |
+#' @export |
|
87 |
+#' @importFrom flowWorkspace getParent |
|
88 |
+setMethod("getParent", signature = c("graphGML", "character"), |
|
89 |
+ definition = function(obj, y) { |
|
90 |
+ |
|
91 |
+ inEdges(y, obj)[[1]] |
|
92 |
+ |
|
93 |
+}) |
|
94 |
+ |
|
95 |
+#' get gate from the node |
|
96 |
+#' |
|
97 |
+#' @param obj \code{graphGML} |
|
98 |
+#' @param y \code{character} node path |
|
99 |
+#' @export |
|
100 |
+#' @importFrom flowWorkspace getGate |
|
101 |
+setMethod("getGate", signature = c("graphGML", "character"), |
|
102 |
+ definition = function(obj, y) { |
|
103 |
+ |
|
104 |
+ nodeData(obj, y)[["gateInfo"]] |
|
105 |
+}) |
|
106 |
+ |
|
107 |
+ |
|
108 |
+#' show method for graphGML |
|
109 |
+#' |
|
110 |
+#' show method for graphGML |
|
111 |
+#' |
|
112 |
+#' @param object \code{graphGML} |
|
113 |
+#' @export |
|
114 |
+#' @importFrom methods show |
|
115 |
+setMethod("show", signature = c("graphGML"), |
|
116 |
+ definition = function(object) { |
|
117 |
+ cat("--- Gating hieararchy parsed from GatingML: ") |
|
118 |
+ |
|
119 |
+ cat("\n") |
|
120 |
+ cat("\twith ", length(object@nodes), " populations defined\n") |
|
121 |
+}) |
|
122 |
+ |
|
123 |
+ |
|
124 |
+#' plot the population tree stored in graphGML. |
|
125 |
+#' |
|
126 |
+#' The node with dotted order represents the population that has tailored gates (sample-specific gates) defined. |
|
127 |
+#' |
|
128 |
+#' @param x a graphNEL generated by constructTree function |
|
129 |
+#' @param y not used |
|
130 |
+#' @param label specifies what to be dispaled as node label. Can be either 'popName' (population name parsed from GateSets) or 'gateName'(the name of the actual gate associated with each node) |
|
131 |
+#' @export |
|
132 |
+#' @importFrom graph nodeData nodes<- nodeRenderInfo<- |
|
133 |
+#' @importFrom Rgraphviz renderGraph layoutGraph |
|
134 |
+#' @importFrom graphics plot |
|
135 |
+#' @examples |
|
136 |
+#' \dontrun{ |
|
137 |
+#' xmlfile <- system.file("extdata/cytotrol_tcell_cytobank.xml", package = "CytoML") |
|
138 |
+#' g <- read.gatingML.cytobank(xmlfile) |
|
139 |
+#' plot(g) |
|
140 |
+#' |
|
141 |
+#' } |
|
142 |
+setMethod("plot", signature = c(x = "graphGML", y = "missing"), definition = function(x, y = "missing", label = c("popName", "gateName")){ |
|
143 |
+ label <- match.arg(label, c("popName", "gateName")) |
|
144 |
+ if(label == "popName") |
|
145 |
+ nodeLabel <- sapply(nodeData(x), `[[`, "popName") |
|
146 |
+ else |
|
147 |
+ nodeLabel <- sapply(nodeData(x), function(i)i[["gateInfo"]][["gateName"]]) |
|
148 |
+ |
|
149 |
+ |
|
150 |
+ #annotate the node with tailor gate info |
|
151 |
+ nTailoredGate <- sapply(nodeData(x), function(i)length(i[["gateInfo"]][["tailored_gate"]])) |
|
152 |
+ |
|
153 |
+ nAttrs <- list() |
|
154 |
+ |
|
155 |
+ nAttrs$label <- nodeLabel |
|
156 |
+ |
|
157 |
+ nAttrs$lty <- sapply(nTailoredGate |
|
158 |
+ ,function(i) |
|
159 |
+ { |
|
160 |
+ ifelse(i>0,"dotted","solid") |
|
161 |
+ }) |
|
162 |
+ |
|
163 |
+ nodeRenderInfo(x) <- nAttrs |
|
164 |
+ lay <- layoutGraph(x |
|
165 |
+ ,attrs=list(graph=list(rankdir="LR",page=c(8.5,11)) |
|
166 |
+ ,node=list(fixedsize=FALSE |
|
167 |
+ ,fontsize = 12 |
|
168 |
+ ,shape="ellipse" |
|
169 |
+ ) |
|
170 |
+ ) |
|
171 |
+ ) |
|
172 |
+ renderGraph(lay) |
|
173 |
+ |
|
174 |
+}) |
|
175 |
+ |
|
176 |
+ |
|
177 |
+#' Apply the gatingML graph to a GatingSet |
|
178 |
+#' |
|
179 |
+#' It applies the gates to the GatingSet based on the population tree described in graphGML. |
|
180 |
+#' |
|
181 |
+#' @param x graphGML |
|
182 |
+#' @param y GatingSet |
|
183 |
+#' @param ... other arguments |
|
184 |
+#' @return |
|
185 |
+#' Nothing. As the side effect, gates generated by gating methods are saved in \code{GatingSet}. |
|
186 |
+#' @export |
|
187 |
+#' @aliases |
|
188 |
+#' gating,graphGML,GatingSet-method |
|
189 |
+#' @rdname gating-methods |
|
190 |
+#' @importFrom openCyto gating |
|
191 |
+setMethod("gating", signature = c("graphGML", "GatingSet"), function(x, y, ...){ |
|
192 |
+ gating.graphGML(x, y, ...) |
|
193 |
+}) |
|
194 |
+ |
|
195 |
+#' @importFrom flowWorkspace getTransformations add recompute sampleNames |
|
196 |
+#' @importFrom RBGL tsort |
|
197 |
+gating.graphGML <- function(gt, gs, ...) { |
|
198 |
+ |
|
199 |
+ trans <- getTransformations(gt) |
|
200 |
+ |
|
201 |
+ gt_nodes <- tsort(gt) |
|
202 |
+ for (nodeID in gt_nodes) { |
|
203 |
+ |
|
204 |
+ # get parent node to gate |
|
205 |
+ gt_node <- getNodes(gt, nodeID, only.names = F) |
|
206 |
+ popName <- gt_node[["popName"]] |
|
207 |
+ |
|
208 |
+ |
|
209 |
+ parentID <- getParent(gt, nodeID) |
|
210 |
+ |
|
211 |
+ if(length(parentID) == 0) |
|
212 |
+ parent <- "root" |
|
213 |
+ else{ |
|
214 |
+ parent <- .getPath(gt, parentID) |
|
215 |
+ } |
|
216 |
+ |
|
217 |
+ |
|
218 |
+ gs_nodes <- basename(getChildren(gs[[1]], parent)) |
|
219 |
+ |
|
220 |
+ if (length(gs_nodes) == 0) |
|
221 |
+ isGated <- FALSE |
|
222 |
+ else |
|
223 |
+ isGated <- any(popName %in% gs_nodes) |
|
224 |
+ |
|
225 |
+ #TODO: rename the node name with path in order to match against gs |
|
226 |
+# parentInd <- match(parent, getNodes(gs[[1]], showHidden = TRUE)) |
|
227 |
+# if (is.na(parentInd)) |
|
228 |
+# stop("parent node '", parent, "' not gated yet!") |
|
229 |
+ if(isGated){ |
|
230 |
+ message("Skip gating! Population '", paste(popName, collapse = ","), "' already exists.") |
|
231 |
+ next |
|
232 |
+ } |
|
233 |
+ message(popName) |
|
234 |
+ gateInfo <- gt_node[["gateInfo"]] |
|
235 |
+ this_gate <- gateInfo[["gate"]] |
|
236 |
+ |
|
237 |
+# if(popName == "PD-1(Histo)") |
|
238 |
+# browser() |
|
239 |
+ |
|
240 |
+ # transform bounds if applicable |
|
241 |
+ bound <- gateInfo[["bound"]] |
|
242 |
+ if(!is.null(trans)) |
|
243 |
+ { |
|
244 |
+ for(rn in rownames(bound)){ |
|
245 |
+ thisTrans <- trans[[rn]] |
|
246 |
+ if(!is.null(thisTrans)) |
|
247 |
+ bound[rn, ] <- thisTrans[["transform"]](unlist(bound[rn, ])) |
|
248 |
+ } |
|
249 |
+ } |
|
250 |
+ |
|
251 |
+ |
|
252 |
+ this_gate <- extend(this_gate,bound = bound) |
|
253 |
+ |
|
254 |
+ sn <- sampleNames(gs) |
|
255 |
+ this_gate <- sapply(sn, function(i)this_gate) |
|
256 |
+ |
|
257 |
+ #update gates that are tailored for specific samples |
|
258 |
+ tailor_gate <- gateInfo[["tailored_gate"]] |
|
259 |
+ tg_sn <- names(tailor_gate) |
|
260 |
+ tg_sn <- tg_sn[tg_sn %in% sn] #filter tailor gates in case sample set provided are not complete |
|
261 |
+ if(length(tg_sn) >0){ |
|
262 |
+ this_tgs <- lapply(tailor_gate[tg_sn], extend,bound = bound) |
|
263 |
+ this_gate[tg_sn] <- this_tgs |
|
264 |
+ } |
|
265 |
+ |
|
266 |
+ |
|
267 |
+ |
|
268 |
+ |
|
269 |
+ add(gs, this_gate, parent = parent, name = popName) |
|
270 |
+ |
|
271 |
+ } |
|
272 |
+ recompute(gs) |
|
273 |
+} |
|
274 |
+ |
|
275 |
+#' Extract compensation from graphGML object. |
|
276 |
+#' @param x graphGML |
|
277 |
+#' @return compensation object or "FCS" when compensation comes from FCS keywords |
|
278 |
+#' @export |
|
279 |
+#' @importFrom flowWorkspace getCompensationMatrices |
|
280 |
+setMethod("getCompensationMatrices", signature = "graphGML", definition = function(x){ |
|
281 |
+ x@graphData[["compensation"]] |
|
282 |
+ |
|
283 |
+}) |
|
284 |
+ |
|
285 |
+#' Extract transformations from graphGML object. |
|
286 |
+#' @param x graphGML |
|
287 |
+#' @return transformerList object |
|
288 |
+#' @importFrom flowCore eval parameters colnames |
|
289 |
+#' @importFrom flowWorkspace transformerList asinh_Gml2 flow_trans |
|
290 |
+#' @export |
|
291 |
+setMethod("getTransformations", signature = c(x = "graphGML"), function(x){ |
|
292 |
+ trans <- x@graphData[["transformations"]] |
|
293 |
+ if(!is.null(trans)){ |
|
294 |
+ chnls <- names(trans) |
|
295 |
+ trans <- sapply(trans, function(thisTrans){ |
|
296 |
+ |
|
297 |
+ #convert from transform object to function since transform has empty function in .Data slot |
|
298 |
+ #which is not suitable for transformList constructor |
|
299 |
+ trans.fun <- eval(thisTrans) |
|
300 |
+ trans.type <- class(thisTrans) |
|
301 |
+ if(extends(trans.type, "asinhtGml2")){ |
|
302 |
+ inv.func <- asinh_Gml2(thisTrans@T, thisTrans@M, thisTrans@A, inverse = TRUE) |
|
303 |
+ |
|
304 |
+ }else |
|
305 |
+ stop("Don't know how to inverse transformation: ", trans.type) |
|
306 |
+ |
|
307 |
+ trans.obj <- flow_trans(trans.type, trans.fun, inv.func) |
|
308 |
+ |
|
309 |
+ } |
|
310 |
+ , USE.NAMES = FALSE, simplify = FALSE) |
|
311 |
+ |
|
312 |
+ trans <- transformerList(chnls, trans) |
|
313 |
+ } |
|
314 |
+ trans |
|
315 |
+}) |
|
316 |
+ |
|
317 |
+#' compensate a GatingSet based on the compensation information stored in graphGML object |
|
318 |
+#' |
|
319 |
+#' |
|
320 |
+#' @param x GatingSet |
|
321 |
+#' @param spillover graphGML |
|
322 |
+#' @param ... unused. |
|
323 |
+#' @return compensated GatingSet |
|
324 |
+#' @importFrom flowCore compensate |
|
325 |
+#' @export |
|
326 |
+#' @importFrom flowCore compensate |
|
327 |
+setMethod("compensate", signature = c("GatingSet", "graphGML"), function(x, spillover, ...){ |
|
328 |
+ |
|
329 |
+ comp <- getCompensationMatrices(spillover) |
|
330 |
+ if(is(comp, "compensation")){ |
|
331 |
+ # prefix <- TRUE |
|
332 |
+ skip <- FALSE |
|
333 |
+ }else if(comp == "FCS"){ |
|
334 |
+ # prefix <- FALSE |
|
335 |
+ fs <- getData(x) |
|
336 |
+ fr <- fs[[1, use.exprs = FALSE]] |
|
337 |
+ #can't use spillover method directly because it will error out when none is found |
|
338 |
+ mat <- keyword(fr, c("spillover", "SPILL")) |
|
339 |
+ mat <- compact(mat) |
|
340 |
+ if(length(mat) == 0){ |
|
341 |
+ skip <- TRUE |
|
342 |
+ warning("Compensation is skipped!Because gates refer to 'FCS' for compensation but no spillover is found in FCS.") |
|
343 |
+ }else{ |
|
344 |
+ skip <- FALSE |
|
345 |
+ mat <- mat[[1]] |
|
346 |
+ comp <- compensation(mat) |
|
347 |
+ } |
|
348 |
+ } |
|
349 |
+ if(skip) |
|
350 |
+ return(x) |
|
351 |
+ else{ |
|
352 |
+ x <- compensate(x, comp) |
|
353 |
+ |
|
354 |
+# if(prefix){ |
|
355 |
+# |
|
356 |
+# comp_param <- colnames(comp@spillover) |
|
357 |
+# #strip prefix |
|
358 |
+# comp_param <- sapply(comp_param, function(i)sub("(^Comp_)(.*)", "\\2", i), USE.NAMES = FALSE) |
|
359 |
+# #match to chnls |
|
360 |
+# chnls <- colnames(x) |
|
361 |
+# ind <- match(comp_param, chnls) |
|
362 |
+# chnls[ind] <- paste0("Comp_", chnls[ind]) |
|
363 |
+# colnames(x) <- chnls |
|
364 |
+# } |
|
365 |
+ return(x) |
|
366 |
+ } |
|
367 |
+ |
|
368 |
+}) |
0 | 369 |
new file mode 100644 |
... | ... |
@@ -0,0 +1,769 @@ |
1 |
+#' A graph object returned by 'read.gatingML.cytobank' function. |
|
2 |
+#' |
|
3 |
+#' Each node corresponds to a population(or GateSet) defined in gatingML file. The actual gate object (both global and tailored gates) is |
|
4 |
+#' associated with each node as nodeData. Compensation and transformations are stored in graphData slot. |
|
5 |
+#' |
|
6 |
+#' The class simply extends the graphNEL class and exists for the purpose of method dispatching. |
|
7 |
+#' |
|
8 |
+#' @importClassesFrom graph graphNEL graphBase graph |
|
9 |
+#' @importClassesFrom Biobase AssayData |
|
10 |
+#' @export |
|
11 |
+setClass("graphGML", contains = "graphNEL") |
|
12 |
+ |
|
13 |
+#' Parser for gatingML exported by Cytobank |
|
14 |
+#' |
|
15 |
+#' The Default parser (flowUtils::read.gatingML) does not parse the population tree as well as |
|
16 |
+#' the custom information from cytobank. (e.g. gate name, fcs filename). |
|
17 |
+#' |
|
18 |
+#' @param file Gating-ML XML file |
|
19 |
+#' @param ... additional arguments passed to the handlers of 'xmlTreeParse' |
|
20 |
+#' @export |
|
21 |
+#' @importFrom flowUtils read.gatingML |
|
22 |
+#' @importFrom flowCore parameters parameters<- |
|
23 |
+#' @return a graphGML that represents the population tree. |
|
24 |
+#' The gate and population name are stored in nodeData of each node. |
|
25 |
+#' Compensation and transformations are stored in graphData. |
|
26 |
+#' @examples |
|
27 |
+#' \dontrun{ |
|
28 |
+#' xml <- system.file("extdata/cytotrol_tcell_cytobank.xml", package = "CytoML") |
|
29 |
+#' g <- read.gatingML.cytobank(xml) #parse the population tree |
|
30 |
+#' plot(g) #visualize it |
|
31 |
+#' } |
|
32 |
+read.gatingML.cytobank <- function(file, ...){ |
|
33 |
+ |
|
34 |
+ #parse all the elements:gate, GateSets, comp, trans |
|
35 |
+ flowEnv <- new.env() |
|
36 |
+ read.gatingML(file, flowEnv) |
|
37 |
+ |
|
38 |
+ #parse gate info (id vs fcs and pop name) |
|
39 |
+ gateInfo <- parse.gateInfo(file) |
|
40 |
+ if(nrow(gateInfo) == 0) |
|
41 |
+ stop("No gates defined in gatingML file!") |
|
42 |
+ |
|
43 |
+ #restore the original gate parameter names |
|
44 |
+ #because flowUtils add comp and tran names as prefix which is really not neccessary (even problematic) here. |
|
45 |
+ for(objID in ls(flowEnv)){ |
|
46 |
+ obj <- flowEnv[[objID]] |
|
47 |
+ if(is(obj, "parameterFilter")){ |
|
48 |
+ |
|
49 |
+ # message(class(obj)) |
|
50 |
+ |
|
51 |
+ sb <- gateInfo[id == objID, ] |
|
52 |
+ if(nrow(sb)>0){ |
|
53 |
+ orig_params <- sb[, params] |
|
54 |
+ orig_params <- strsplit(split = ":", orig_params)[[1]] |
|
55 |
+ params <- parameters(obj) |
|
56 |
+ ind <- sapply(orig_params, function(orig_param)grep(paste0(orig_param, "$"), params)) |
|
57 |
+ |
|
58 |
+ orig_param <- orig_params[ind] |
|
59 |
+ |
|
60 |
+ #cytobank add Comp_ prefix when the custom compensation is specified and referred by gates |
|
61 |
+ #We always strip it to ensure the bare channel names are used for gates (so that flow data does not need changes) |
|
62 |
+ orig_param <- sub("(^Comp_)(.*)", "\\2", orig_param) |
|
63 |
+ |
|
64 |
+ parameters(obj) <- orig_param |
|
65 |
+ flowEnv[[objID]] <- obj |
|
66 |
+ } |
|
67 |
+ |
|
68 |
+ } |
|
69 |
+ |
|
70 |
+ } |
|
71 |
+ |
|
72 |
+ |
|
73 |
+ #construct tree from GateSets |
|
74 |
+ g <- constructTree(flowEnv, gateInfo) |
|
75 |
+ |
|
76 |
+ #determine comps and trans to be used |
|
77 |
+ |
|
78 |
+ comp_refs <- gateInfo[, comp_ref] |
|
79 |
+ comp_refs <- unique(comp_refs[comp_refs!=""]) |
|
80 |
+ comp_refs <- comp_refs[comp_refs != "uncompensated"] |
|
81 |
+ if(length(comp_refs) > 1) |
|
82 |
+ stop("More than one compensation referred in gates!") |
|
83 |
+ else{ |
|
84 |
+ if(comp_refs == "FCS") |
|
85 |
+ comps <- "FCS" |
|
86 |
+ else{ |
|
87 |
+ comps <- flowEnv[[comp_refs]] |
|
88 |
+ #strip Comp_ prefix that was added by cytobank |
|
89 |
+# mat <- comps@spillover |
|
90 |
+# comp_param <- colnames(mat) |
|
91 |
+# comp_param <- sapply(comp_param, function(i)sub("(^Comp_)(.*)", "\\2", i), USE.NAMES = FALSE) |
|
92 |
+# colnames(mat) <- comp_param |
|
93 |
+# comps <- compensation(mat) |
|
94 |
+ |
|
95 |
+ } |
|
96 |
+ |
|
97 |
+ } |
|
98 |
+ g@graphData[["compensation"]] <- comps |
|
99 |
+ |
|
100 |
+ |
|
101 |
+ trans <- sapply(ls(flowEnv), function(i){ |
|
102 |
+ |
|
103 |
+ obj <- flowEnv[[i]] |
|
104 |
+ #exclude the compensatedParameter since it also inherits transformation class |
|
105 |
+ if(is(obj, "transformation")&&!is(obj, "compensatedParameter")) |
|
106 |
+ obj |
|
107 |
+ }, USE.NAMES = FALSE) |
|
108 |
+ |
|
109 |
+ trans <- compact(trans) |
|
110 |
+ chnl <- sapply(trans, function(tran)unname(parameters(tran@parameters)), USE.NAMES = F) |
|
111 |
+ |
|
112 |
+ ind <- chnl != "any" |
|
113 |
+ |
|
114 |
+ chnl <- chnl[ind] |
|
115 |
+ trans <- trans[ind] |
|
116 |
+ names(trans) <- chnl |
|
117 |
+ if(length(trans) > 0) |
|
118 |
+ g@graphData[["transformations"]] <- trans |
|
119 |
+ |
|
120 |
+ as(g, "graphGML") |
|
121 |
+ |
|
122 |
+} |
|
123 |
+ |
|
124 |
+#' Parse the cytobank custom_info for each gate |
|
125 |
+#' |
|
126 |
+#' Fcs filename and gate name stored in 'custom_info' element are beyong the scope of |
|
127 |
+#' the gatingML standard and thus not covered by the default 'read.gatingML'. |
|
128 |
+#' |
|
129 |
+#' @param file xml file path |
|
130 |
+#' @param ... additional arguments passed to the handlers of 'xmlTreeParse' |
|
131 |
+#' @return a data.frame that contains three columns: id (gateId), name (gate name), fcs (fcs_file_filename). |
|
132 |
+#' @importFrom XML xmlRoot xmlName xmlGetAttr xmlValue xmlElementsByTagName xmlChildren |
|
133 |
+#' @import data.table |
|
134 |
+parse.gateInfo <- function(file, ...) |
|
135 |
+{ |
|
136 |
+ |
|
137 |
+ root <- xmlRoot(flowUtils:::smartTreeParse(file,...)) |
|
138 |
+ |
|
139 |
+ rbindlist( |
|
140 |
+ lapply(xmlChildren(root), function(node){ |
|
141 |
+ nodeName <- xmlName(node) |
|
142 |
+ |
|
143 |
+ if(grepl("*Gate", nodeName)){ |
|
144 |
+ |
|
145 |
+ |
|
146 |
+ id <- xmlGetAttr(node, "id") |
|
147 |
+ |
|
148 |
+ name <- getCustomNodeInfo(node, "name") |
|
149 |
+ fcs_file_filename <- getCustomNodeInfo(node, "fcs_file_filename") |
|
150 |
+ gate_id <- getCustomNodeInfo(node, "gate_id")#used to find tailored gate |
|
151 |
+ if(nodeName %in% c("BooleanGate")) |
|
152 |
+ { |
|
153 |
+ gate_def <- comp_ref <- trans_ref <- params <- "" |
|
154 |
+ }else |
|
155 |
+ { |
|
156 |
+ |
|
157 |
+ gate_def <- getCustomNodeInfo(node, "definition") |
|
158 |
+ |
|
159 |
+ if(nodeName == "QuadrantGate"){ |
|
160 |
+ dimTag <- "divider" |
|
161 |
+ #update id with quardant definition |
|
162 |
+ quadrantList <- xmlElementsByTagName(node, "Quadrant") |
|
163 |
+ id <- unname(sapply(quadrantList, function(i)xmlGetAttr(i, "id"))) |
|
164 |
+ |
|
165 |
+ }else |
|
166 |
+ dimTag <- "dimension" |
|
167 |
+ |
|
168 |
+ dimNode <- xmlElementsByTagName(node, dimTag) |
|
169 |
+ comp_ref <- unique(sapply(dimNode, function(i)xmlGetAttr(i, "compensation-ref"))) |
|
170 |
+ trans_ref <- unique(unname(unlist(compact(sapply(dimNode, function(i)xmlGetAttr(i, "transformation-ref")))))) |
|
171 |
+ trans_ref <- ifelse(is.null(trans_ref), "", trans_ref) |
|
172 |
+ params <- paste(sapply(dimNode, function(i)xmlGetAttr(i[["fcs-dimension"]], "name")), collapse = ":") |
|
173 |
+ } |
|
174 |
+ # message(name) |
|
175 |
+ # browser() |
|
176 |
+ data.table(id = id, name = name, gate_id = gate_id, fcs = fcs_file_filename |
|
177 |
+ , comp_ref = comp_ref, trans_ref = trans_ref, params = params, gate_def = gate_def |
|
178 |
+ ) |
|
179 |
+ |
|
180 |
+ |
|
181 |
+ } |
|
182 |
+ |
|
183 |
+ }) |
|
184 |
+ ) |
|
185 |
+} |
|
186 |
+ |
|
187 |
+getCustomNodeInfo <- function(node, nodeName){ |
|
188 |
+ custom_node <- xmlElementsByTagName(node, nodeName, recursive = TRUE) |
|
189 |
+ if(length(custom_node) >0 ){ |
|
190 |
+ value <- xmlValue(custom_node[[1]]) |
|
191 |
+ if(length(value)==0) |
|
192 |
+ value <- "" |
|
193 |
+ } |
|
194 |
+ else |
|
195 |
+ value <- "" |
|
196 |
+ |
|
197 |
+ value |
|
198 |
+} |
|
199 |
+ |
|
200 |
+#' Given the leaf node, try to find out if a collection of nodes can be matched to a path in a graph(tree) by the bottom-up searching |
|
201 |
+#' @param g graphNEL |
|
202 |
+#' @param leaf the name of leaf(terminal) node |
|
203 |
+#' @param nodeSet a set of node names |
|
204 |
+#' @return TRUE if path is found, FALSE if not path is matched. |
|
205 |
+#' @importFrom graph inEdges |
|
206 |
+matchPath <- function(g, leaf, nodeSet){ |
|
207 |
+ |
|
208 |
+ if(leaf %in% nodeSet){ |
|
209 |
+ nodeSet <- nodeSet[-match(leaf, nodeSet)] #pop it out |
|
210 |
+ leaf <- inEdges(leaf, g)[[1]]#update it with parent node |
|
211 |
+ if(length(nodeSet) == 0){ #nodeSet emptied |
|
212 |
+ if(length(leaf) == 0) #and path reach to the top |
|
213 |
+ return (TRUE) |
|
214 |
+ else |
|
215 |
+ return(FALSE) #path has not reached to the top |
|
216 |
+ }else |
|
217 |
+ { |
|
218 |
+ if(length(leaf) == 0) #reach the top before nodeSet is emptied |
|
219 |
+ return(FALSE) |
|
220 |
+ else |
|
221 |
+ matchPath(g, leaf, nodeSet) #continue match the path against nodeSet |
|
222 |
+ } |
|
223 |
+ }else |
|
224 |
+ return(FALSE) |
|
225 |
+ |
|
226 |
+} |
|
227 |
+ |
|
228 |
+#' Reconstruct the population tree from the GateSets |
|
229 |
+#' @param flowEnv the enivornment contains the elements parsed by read.gatingML function |
|
230 |
+#' @param gateInfo the data.frame contains the gate name, fcs filename parsed by parse.gateInfo function |
|
231 |
+#' @return a graphNEL represent the population tree. The gate and population name are stored as nodeData in each node. |
|
232 |
+#' @importFrom graph graphNEL nodeDataDefaults<- nodeData<- addEdge edges removeNode |
|
233 |
+#' @importFrom jsonlite fromJSON |
|
234 |
+constructTree <- function(flowEnv, gateInfo){ |
|
235 |
+ |
|