Browse code

implement the gate extension for concave polygons. #7

mikejiang authored on 30/07/2016 01:23:15
Showing 26 changed files

... ...
@@ -1,4 +1,4 @@
1
-# Generated by roxygen2 (4.1.0): do not edit by hand
1
+# Generated by roxygen2: do not edit by hand
2 2
 
3 3
 S3method(extend,ellipsoidGate)
4 4
 S3method(extend,polygonGate)
... ...
@@ -234,8 +234,7 @@ gating.graphGML <- function(gt, gs, ...) {
234 234
     gateInfo <- gt_node[["gateInfo"]]
235 235
     this_gate <- gateInfo[["gate"]]
236 236
 
237
-#     if(popName == "PD-1(Histo)")
238
-#       browser()
237
+
239 238
 
240 239
     # transform bounds if applicable
241 240
     bound <- gateInfo[["bound"]]
... ...
@@ -248,7 +247,8 @@ gating.graphGML <- function(gt, gs, ...) {
248 247
       }
249 248
     }
250 249
 
251
-
250
+        # if(popName == "MDSC(gran-cd15+)")
251
+        #   browser()
252 252
     this_gate <- extend(this_gate,bound = bound)
253 253
 
254 254
     sn <- sampleNames(gs)
... ...
@@ -411,6 +411,7 @@ addGate <- function(gateInfo,flowEnv, g, popId, gateID){
411 411
 #'        rownames should be the channel names. colnames should be c("min", "max")
412 412
 #' @param data.range numeric matrix specifying the data limits of each channel. It is used to set the extended value of vertices and must has the same structure as 'bound'.
413 413
 #'        when it is not supplied, c(-.Machine$integer.max, - .Machine$integer.max) is used.
414
+#' @param limits character whether to plot in "extended" or "original" gate limits. Default is "original".
414 415
 #' @param ... other arguments
415 416
 #' @return a flowCore filter/gate
416 417
 #' @examples
... ...
@@ -422,7 +423,7 @@ addGate <- function(gateInfo,flowEnv, g, popId, gateID){
422 423
 #' bound <- matrix(c(100,3e3,100,3e3), byrow = TRUE, nrow = 2, dimnames = list(c("FSC-H", "SSC-H"), c("min", "max")))
423 424
 #' bound
424 425
 #' pg.extened <- extend(pg, bound, plot = TRUE)
425
-extend <- function(gate, bound, data.range = NULL, plot = FALSE)UseMethod("extend")
426
+extend <- function(gate, bound, data.range = NULL, plot = FALSE, limits = c("original", "extended"))UseMethod("extend")
426 427
 
427 428
 #' @export
428 429
 #' @S3method extend polygonGate
... ...
@@ -430,8 +431,8 @@ extend <- function(gate, bound, data.range = NULL, plot = FALSE)UseMethod("exten
430 431
 #' @param plot whether to plot the extended polygon.
431 432
 #' @importFrom flowCore polygonGate
432 433
 #' @importFrom graphics abline polygon text
433
-extend.polygonGate <- function(gate, bound, data.range = NULL, plot = FALSE){
434
-
434
+extend.polygonGate <- function(gate, bound, data.range = NULL, plot = FALSE, limits = c("original", "extended")){
435
+  limits <- match.arg(limits)
435 436
   #linear functions
436 437
   f.solve <- list(x = function(x, slope, x1, y1){
437 438
 
... ...
@@ -461,7 +462,7 @@ extend.polygonGate <- function(gate, bound, data.range = NULL, plot = FALSE){
461 462
   #this is a hack: We assume the polygon is convex
462 463
   #if not we turn the convcave into convex
463 464
   #to avoid the error
464
-  verts.orig <- verts.orig[chull(verts.orig),]
465
+  # verts.orig <- verts.orig[chull(verts.orig),]
465 466
 
466 467
   verts <- data.table(verts.orig)
467 468
   pname <- as.vector(parameters(gate))
... ...
@@ -539,7 +540,7 @@ extend.polygonGate <- function(gate, bound, data.range = NULL, plot = FALSE){
539 540
           }
540 541
 
541 542
 
542
-          c(point, id = i + 0.5)#jitter a positive ammount to break the tie with vert1
543
+          c(point, id = i + 0.1)#jitter a positive ammount to break the tie with vert1
543 544
 
544 545
         }
545 546
 
... ...
@@ -548,61 +549,96 @@ extend.polygonGate <- function(gate, bound, data.range = NULL, plot = FALSE){
548 549
 
549 550
 
550 551
 
551
-      this.intersect <- do.call(rbind, this.intersect)
552
+      this.intersect.df <- do.call(rbind, this.intersect)
553
+
552 554
       dim.flip <- ifelse(dim == "x", "y", "x")
553 555
 #       this.intersect <- this.intersect[order(this.intersect[[dim.flip]]),] #bottom to top/or left to right
554
-      nCount <- ifelse(is.null(this.intersect), 0, nrow(this.intersect))
556
+      nCount <- ifelse(is.null(this.intersect.df), 0, nrow(this.intersect.df))
555 557
       if(nCount > 0){
556
-        if(nCount!= 2)
557
-          stop("Unsupported number of intersected points with ", bn, " boundary on ", dim, " axis: ", nCount)
558
-
559
-        verts[, id := 1:nVerts]#record the id before insertion
560
-        this.intersect <- as.data.table(this.intersect)
561
-
562
-        #insert the intersect points
563
-        verts <- rbindlist(list(verts, this.intersect))
564
-        verts <- verts[order(id),]
565
-
566
-        #remove off-bound points
567
-        if(bn == "min")
568
-          ind <- verts[, dim, with = FALSE] < intersect.coord
569
-        else
570
-          ind <- verts[, dim, with = FALSE] > intersect.coord
571
-        ind <- as.vector(ind)
572
-        verts <- verts[!ind, ]
573
-
574
-        #add extended points
575
-        this.extend <- this.intersect
576
-        this.extend[, dim] <- data.range[dim, bn]
577
-
578
-        #sort by the Id
579
-        this.extend[, is.smaller:= order(id) == 1]
580
-        #check if head-tail node situation
581
-
582
-        this.extend[, is.tail := id == verts[,max(id)]]
583
-        this.extend[, is.head := id == verts[,min(id)]]
584
-
585
-        nhead <- sum(this.extend[, is.head])
586
-        ntail <- sum(this.extend[, is.tail])
587
-
588
-
589
-        if(nhead == 0||ntail == 0){#two consecutive points
590
-          this.extend[is.smaller == TRUE, id := id + 0.1]
591
-          this.extend[is.smaller == FALSE, id := this.extend[is.smaller == TRUE, id] + 0.1]
592
-        }else if(nhead == 1 && ntail == 1){
593
-          #deal with head-tail points
594
-          this.extend[is.smaller == TRUE, id := id - 0.1]
595
-          this.extend[is.smaller == FALSE, id := this.extend[is.smaller == TRUE, id] - 0.1]
596
-        }else
597
-          stop("Incorrect number of head and tail points!")
558
+        if(nCount %% 2 != 0)
559
+          stop("uneven number of intersected points with ", bn, " boundary on ", dim, " axis: ", nCount)
560
+      verts[, id := 1:nVerts]#record the id before insertion
561
+      verts[, key := paste0(x,",", y)] # generate key for the comparsion to intersected points later on
562
+
563
+      #reset id for the duplicated intersects so that they won't cause chaos for the ordering later on
564
+      this.intersect.df <- as.data.table(this.intersect.df)
565
+      this.intersect.df[, key := paste0(x,",", y)]
566
+      this.intersect.df[, id := min(id), by = key]
567
+      #order by dim so that extension to pairs follows the order
568
+      setorderv(this.intersect.df, dim.flip)
569
+      inserted.ids <- NULL
570
+      #loop through each pair of extended points
571
+      for(i in seq_len(nCount/2)){
572
+          j <- 2 * i
573
+          # browser()
574
+          this.intersect <- this.intersect.df[(j -1):j, ]
575
+
576
+          # this.intersect <- as.data.table(this.intersect)
577
+
578
+          #remove the original edge points that overlap with intersect points
579
+          #but keep the intersected points inserted previously
580
+          #nchar(id) : length of significant digits
581
+          #== 1: original points
582
+          #== 2: intersected
583
+          #== 4: extended
584
+          # verts <- verts[!(key %in% this.intersect[, key] && nchar(id) == 1), ]
585
+          verts <- verts[!(key %in% this.intersect[, key]), ]
586
+
587
+
588
+
589
+          #keep track of id that has been inserted repeatly
590
+          #so that the duplicated intersects can be removed later
591
+          #otherwise, it could mess up the already removed off-bound points
592
+          dup.id <- this.intersect[id %in% inserted.ids, id]
593
+          inserted.ids <- unique(c(inserted.ids, this.intersect[, id]))
594
+          #insert the intersect points
595
+          verts <- rbindlist(list(verts, this.intersect))
596
+          verts <- verts[order(id),]
597
+
598
+          #remove off-bound points between the two intersected points
599
+          vals.dim <- verts[, dim, with = FALSE]
600
+          vals.dim.flip <- verts[, dim.flip, with = FALSE]
601
+          rng.dim.flip  <- range(this.intersect[[dim.flip]])
602
+          ind.between <- vals.dim.flip <= rng.dim.flip[2] & vals.dim.flip >= rng.dim.flip[1]
603
+          if(bn == "min")
604
+            ind <- vals.dim < intersect.coord & ind.between
605
+          else
606
+            ind <- vals.dim > intersect.coord & ind.between
607
+          ind <- as.vector(ind)
608
+          verts <- verts[!ind, ]
609
+
610
+
611
+
612
+          #add extended points
613
+          this.extend <- this.intersect
614
+          this.extend[, dim] <- data.range[dim, bn]
615
+          this.extend[, key := paste0(x,",", y)]#update key
616
+
617
+          #sort by the Id
618
+          this.extend[, is.smaller:= order(id) == 1]
619
+          #check if head-tail node situation
620
+          # by cal the distance between two points
621
+          this.extend[, order := match(id, verts[,id])]
622
+          dist <- abs(diff(this.extend[, order]))
623
+          if(dist == 1){#two consecutive points
624
+            this.extend[is.smaller == TRUE, id := id + 0.01]
625
+            this.extend[is.smaller == FALSE, id := this.extend[is.smaller == TRUE, id] + 0.01]
626
+          }else{
627
+            #deal with head-tail points
628
+            this.extend[is.smaller == TRUE, id := id - 0.01]
629
+            this.extend[is.smaller == FALSE, id := this.extend[is.smaller == TRUE, id] - 0.01]
630
+          }
631
+          # browser()
632
+          this.extend[, is.smaller := NULL]
633
+          this.extend[, order := NULL]
598 634
 
635
+          #remove dup id
636
+          verts <- verts[!id%in%dup.id, ]
599 637
 
600
-        this.extend[, is.smaller := NULL]
601
-        this.extend[, is.head := NULL]
602
-        this.extend[, is.tail := NULL]
638
+          verts <- rbindlist(list(verts, this.extend))
639
+          verts <- verts[order(id),]
603 640
 
604
-        verts <- rbindlist(list(verts, this.extend))
605
-        verts <- verts[order(id),]
641
+        }
606 642
 
607 643
       }
608 644
 
... ...
@@ -610,16 +646,19 @@ extend.polygonGate <- function(gate, bound, data.range = NULL, plot = FALSE){
610 646
   }
611 647
 
612 648
 
613
-
649
+# browser()
614 650
 
615 651
 
616 652
   if(plot){
617
-    plot(type = "n", x = verts.orig[,1], y = verts.orig[,2])
653
+    if(limits == "extended")
654
+      plot(type = "n", x = verts[[1]], y = verts[[2]])
655
+    else
656
+      plot(type = "n", x = verts.orig[,1], y = verts.orig[,2])
618 657
     polygon(verts.orig, lwd =  4, border = rgb(0, 0, 0,0.5))
619 658
     # points(verts.orig, col = "red")
620 659
     # points(t(as.data.frame(colMeans(verts.orig))), col = "red")
621
-    abline(v = bound[1,], lty = "dashed", col = "red")
622
-    abline(h = bound[2,], lty = "dashed", col = "red")
660
+    # abline(v = bound[1,], lty = "dashed", col = "red")
661
+    # abline(h = bound[2,], lty = "dashed", col = "red")
623 662
     text(verts, labels = verts[, id], col = "red")
624 663
     # points(intersect.points[, c(axis.names)], col = "blue")
625 664
     polygon(verts, lty = "dotted", border = "green", lwd = 3)
... ...
@@ -26,6 +26,6 @@ test_that("gatingML-cytobank exporting: cytotrol tcell",{
26 26
   stats.new <- getPopStats(gs1)
27 27
   stats <- merge(stats.orig, stats.new, by = c("name", "Population", "Parent"))
28 28
 
29
-  expect_equal(stats[, Count.x/ParentCount.x], stats[, Count.y/ParentCount.y], tol = 7e-3)
29
+  expect_equal(stats[, Count.x/ParentCount.x], stats[, Count.y/ParentCount.y])
30 30
 
31 31
 })
32 32
\ No newline at end of file
33 33
new file mode 100644
... ...
@@ -0,0 +1,90 @@
1
+chnls <- c("FSC-H","SSC-H")
2
+data.range <- data.frame(min = c(-1, -1), max = c(4e3, 4e3), row.names = chnls)
3
+sqrcut <- matrix(c(300, 50
4
+                   ,300, 300
5
+                   , 600, 300
6
+                   , 600, 50)
7
+                 , byrow = TRUE, nrow=4
8
+                 , dimnames = list(NULL, chnls))
9
+pg <- polygonGate(filterId="nonDebris", sqrcut)
10
+
11
+test_that("extend.polygonGate: y axis",{
12
+
13
+  bound <- matrix(c(100,3e3
14
+                    ,100,3e3)
15
+                  , byrow = TRUE, nrow = 2
16
+                  , dimnames = list(chnls, c("min", "max")))
17
+  pg.extened <- extend(pg, bound)
18
+  # paste(as.vector(pg.extened@boundaries), collapse = ",")
19
+  expectRes <- matrix(c(600,-2147483647
20
+                        ,300,-2147483647
21
+                        ,300,100
22
+                        ,300,300
23
+                        ,600,300
24
+                        ,600,100
25
+                       )
26
+                     ,byrow = TRUE,nrow=6)
27
+  expect_equivalent(pg.extened@boundaries, expectRes)
28
+
29
+})
30
+
31
+test_that("extend.polygonGate: both x and y axis",{
32
+  bound <- matrix(c(400,3e3
33
+                    ,100,3e3)
34
+                  , byrow = TRUE, nrow = 2
35
+                  , dimnames = list(chnls, c("min", "max")))
36
+  pg.extened <- extend(pg, bound)
37
+
38
+
39
+  expectRes <- matrix(c(600,-2147483647,-2147483647,-2147483647,400,600,600,-2147483647,-2147483647,100,300,300,300,100), nrow = 7)
40
+
41
+  expect_equivalent(pg.extened@boundaries, expectRes)
42
+
43
+})
44
+
45
+test_that("extend.polygonGate: concave on left with data.range",{
46
+  sqrcut <- matrix(c(300, 50
47
+                     , 450, 150
48
+                     ,300, 300
49
+                     , 600, 300
50
+                     , 600, 50)
51
+                   , byrow = TRUE, nrow=5
52
+                   , dimnames = list(NULL, chnls))
53
+  pg <- polygonGate(filterId="nonDebris", sqrcut)
54
+  bound <- matrix(c(400,3e3
55
+                    ,10,3e3)
56
+                  , byrow = TRUE, nrow = 2
57
+                  , dimnames = list(chnls, c("min", "max")))
58
+  pg.extened <- extend(pg, bound, data.range = data.range)
59
+
60
+  expectRes <- matrix(c(-1,-1,400,450,400,-1,-1,400,600,600,400,50,116.666666666667,116.666666666667,150,200,200,300,300,300,50,50)
61
+                      , nrow = 11)
62
+
63
+  expect_equivalent(pg.extened@boundaries, expectRes)
64
+
65
+})
66
+
67
+test_that("extend.polygonGate: concave on left& bottom with data.range",{
68
+  sqrcut <- matrix(c(300, 50
69
+                     , 450, 150
70
+                     ,300, 300
71
+                     , 600, 300
72
+                     , 600, 50
73
+                     , 550,100
74
+                     , 500,50
75
+                     , 450,60)
76
+                   , byrow = TRUE, nrow=8
77
+                   , dimnames = list(NULL, chnls))
78
+  pg <- polygonGate(filterId="nonDebris", sqrcut)
79
+  bound <- matrix(c(400,3e3
80
+                    ,100,3e3)
81
+                  , byrow = TRUE, nrow = 2
82
+                  , dimnames = list(chnls, c("min", "max")))
83
+  pg.extened <- extend(pg, bound, data.range = data.range)
84
+
85
+  expectRes <- matrix(c(-1,-1,-1,400,450,400,-1,-1,400,600,600,600,550,-1,100,116.666666666667,116.666666666667,150,200,200,300,300,300,100,-1,-1)
86
+                      , nrow = 13)
87
+
88
+  expect_equivalent(pg.extened@boundaries, expectRes)
89
+
90
+})
0 91
\ No newline at end of file
... ...
@@ -1,4 +1,4 @@
1
-% Generated by roxygen2 (4.1.0): do not edit by hand
1
+% Generated by roxygen2: do not edit by hand
2 2
 % Please edit documentation in R/GatingSet2cytobank.R
3 3
 \name{GatingSet2cytobank}
4 4
 \alias{GatingSet2cytobank}
... ...
@@ -43,5 +43,7 @@ Rm("CD8", gs)
43 43
 #output to cytobank
44 44
 outFile <- tempfile(fileext = ".xml")
45 45
 GatingSet2cytobank(gs, outFile) #type by default is 'cytobank'
46
+
47
+
46 48
 }
47 49
 
... ...
@@ -1,4 +1,4 @@
1
-% Generated by roxygen2 (4.1.0): do not edit by hand
1
+% Generated by roxygen2: do not edit by hand
2 2
 % Please edit documentation in R/GatingSet2flowJo.R
3 3
 \name{GatingSet2flowJo}
4 4
 \alias{GatingSet2flowJo}
... ...
@@ -29,5 +29,7 @@ gs <- load_gs(list.files(dataDir, pattern = "gs_manual",full = TRUE))
29 29
 #output to flowJo
30 30
 outFile <- tempfile(fileext = ".wsp")
31 31
 GatingSet2flowJo(gs, outFile)
32
+
33
+
32 34
 }
33 35
 
... ...
@@ -1,4 +1,4 @@
1
-% Generated by roxygen2 (4.1.0): do not edit by hand
1
+% Generated by roxygen2: do not edit by hand
2 2
 % Please edit documentation in R/GatingSet2cytobank.R
3 3
 \name{addCustomInfo}
4 4
 \alias{addCustomInfo}
... ...
@@ -1,10 +1,10 @@
1
-% Generated by roxygen2 (4.1.0): do not edit by hand
1
+% Generated by roxygen2: do not edit by hand
2 2
 % Please edit documentation in R/cytobank2GatingSet.R
3 3
 \name{compare.counts}
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
-compare.counts(gs, file, id.vars = c("FCS Filename", "population"))
7
+\method{compare}{counts}(gs, file, id.vars = c("FCS Filename", "population"))
8 8
 }
9 9
 \arguments{
10 10
 \item{gs}{parsed GatingSet}
... ...
@@ -20,6 +20,7 @@ a data.table (in long format) that contains the counts from openCyto and Cytoban
20 20
 compare the counts to cytobank's exported csv so that the parsing result can be verified.
21 21
 }
22 22
 \examples{
23
+
23 24
 xmlfile <- system.file("extdata/cytotrol_tcell_cytobank.xml", package = "CytoML")
24 25
 fcsFiles <- list.files(pattern = "CytoTrol", system.file("extdata", package = "flowWorkspaceData"), full = TRUE)
25 26
 gs <- cytobank2GatingSet(xmlfile, fcsFiles)
... ...
@@ -27,5 +28,6 @@ gs <- cytobank2GatingSet(xmlfile, fcsFiles)
27 28
 statsfile <- system.file("extdata/cytotrol_tcell_cytobank_counts.csv", package = "CytoML")
28 29
 dt_merged <- compare.counts(gs, statsfile, id.vars = "population")
29 30
 all.equal(dt_merged[, count.x], dt_merged[, count.y], tol = 5e-4)
31
+
30 32
 }
31 33
 
... ...
@@ -1,4 +1,4 @@
1
-% Generated by roxygen2 (4.1.0): do not edit by hand
1
+% Generated by roxygen2: do not edit by hand
2 2
 % Please edit documentation in R/graphGML_methods.R
3 3
 \docType{methods}
4 4
 \name{compensate,GatingSet,graphGML-method}
... ...
@@ -1,4 +1,4 @@
1
-% Generated by roxygen2 (4.1.0): do not edit by hand
1
+% Generated by roxygen2: do not edit by hand
2 2
 % Please edit documentation in R/read.gatingML.cytobank.R
3 3
 \name{constructTree}
4 4
 \alias{constructTree}
... ...
@@ -1,4 +1,4 @@
1
-% Generated by roxygen2 (4.1.0): do not edit by hand
1
+% Generated by roxygen2: do not edit by hand
2 2
 % Please edit documentation in R/cytobank2GatingSet.R
3 3
 \name{cytobank2GatingSet}
4 4
 \alias{cytobank2GatingSet}
... ...
@@ -18,9 +18,11 @@ a GatingSet
18 18
 A wrapper that parse the gatingML and FCS files into GatingSet
19 19
 }
20 20
 \examples{
21
+
21 22
 xmlfile <- system.file("extdata/cytotrol_tcell_cytobank.xml", package = "CytoML")
22 23
 fcsFiles <- list.files(pattern = "CytoTrol", system.file("extdata", package = "flowWorkspaceData"), full = TRUE)
23 24
 gs <- cytobank2GatingSet(xmlfile, fcsFiles)
24 25
 #plotGate(gs[[1]])
26
+
25 27
 }
26 28
 
... ...
@@ -1,4 +1,4 @@
1
-% Generated by roxygen2 (4.1.0): do not edit by hand
1
+% Generated by roxygen2: do not edit by hand
2 2
 % Please edit documentation in R/read.gatingML.cytobank.R
3 3
 \name{extend}
4 4
 \alias{extend}
... ...
@@ -7,9 +7,11 @@
7 7
 \alias{extend.rectangleGate}
8 8
 \title{extend the gate to the minimum and maximum limit of both dimensions based on the bounding information.}
9 9
 \usage{
10
-extend(gate, bound, data.range = NULL, plot = FALSE)
10
+extend(gate, bound, data.range = NULL, plot = FALSE,
11
+  limits = c("original", "extended"))
11 12
 
12
-\method{extend}{polygonGate}(gate, bound, data.range = NULL, plot = FALSE)
13
+\method{extend}{polygonGate}(gate, bound, data.range = NULL, plot = FALSE,
14
+  limits = c("original", "extended"))
13 15
 
14 16
 \method{extend}{rectangleGate}(gate, ...)
15 17
 
... ...
@@ -26,6 +28,8 @@ when it is not supplied, c(-.Machine$integer.max, - .Machine$integer.max) is use
26 28
 
27 29
 \item{plot}{whether to plot the extended polygon.}
28 30
 
31
+\item{limits}{character whether to plot in "extended" or "original" gate limits. Default is "original".}
32
+
29 33
 \item{...}{other arguments}
30 34
 }
31 35
 \value{
... ...
@@ -1,4 +1,4 @@
1
-% Generated by roxygen2 (4.1.0): do not edit by hand
1
+% Generated by roxygen2: do not edit by hand
2 2
 % Please edit documentation in R/graphGML_methods.R
3 3
 \docType{methods}
4 4
 \name{gating,graphGML,GatingSet-method}
... ...
@@ -1,4 +1,4 @@
1
-% Generated by roxygen2 (4.1.0): do not edit by hand
1
+% Generated by roxygen2: do not edit by hand
2 2
 % Please edit documentation in R/graphGML_methods.R
3 3
 \docType{methods}
4 4
 \name{getChildren,graphGML,character-method}
... ...
@@ -1,4 +1,4 @@
1
-% Generated by roxygen2 (4.1.0): do not edit by hand
1
+% Generated by roxygen2: do not edit by hand
2 2
 % Please edit documentation in R/graphGML_methods.R
3 3
 \docType{methods}
4 4
 \name{getCompensationMatrices,graphGML-method}
... ...
@@ -1,4 +1,4 @@
1
-% Generated by roxygen2 (4.1.0): do not edit by hand
1
+% Generated by roxygen2: do not edit by hand
2 2
 % Please edit documentation in R/graphGML_methods.R
3 3
 \docType{methods}
4 4
 \name{getGate,graphGML,character-method}
... ...
@@ -1,4 +1,4 @@
1
-% Generated by roxygen2 (4.1.0): do not edit by hand
1
+% Generated by roxygen2: do not edit by hand
2 2
 % Please edit documentation in R/graphGML_methods.R
3 3
 \docType{methods}
4 4
 \name{getNodes,graphGML-method}
... ...
@@ -1,4 +1,4 @@
1
-% Generated by roxygen2 (4.1.0): do not edit by hand
1
+% Generated by roxygen2: do not edit by hand
2 2
 % Please edit documentation in R/graphGML_methods.R
3 3
 \docType{methods}
4 4
 \name{getParent,graphGML,character-method}
... ...
@@ -1,4 +1,4 @@
1
-% Generated by roxygen2 (4.1.0): do not edit by hand
1
+% Generated by roxygen2: do not edit by hand
2 2
 % Please edit documentation in R/graphGML_methods.R
3 3
 \docType{methods}
4 4
 \name{getTransformations,graphGML-method}
... ...
@@ -1,4 +1,4 @@
1
-% Generated by roxygen2 (4.1.0): do not edit by hand
1
+% Generated by roxygen2: do not edit by hand
2 2
 % Please edit documentation in R/read.gatingML.cytobank.R
3 3
 \docType{class}
4 4
 \name{graphGML-class}
... ...
@@ -1,4 +1,4 @@
1
-% Generated by roxygen2 (4.1.0): do not edit by hand
1
+% Generated by roxygen2: do not edit by hand
2 2
 % Please edit documentation in R/read.gatingML.cytobank.R
3 3
 \name{matchPath}
4 4
 \alias{matchPath}
... ...
@@ -1,4 +1,4 @@
1
-% Generated by roxygen2 (4.1.0): do not edit by hand
1
+% Generated by roxygen2: do not edit by hand
2 2
 % Please edit documentation in R/read.gatingML.cytobank.R
3 3
 \name{parse.gateInfo}
4 4
 \alias{parse.gateInfo}
... ...
@@ -1,4 +1,4 @@
1
-% Generated by roxygen2 (4.1.0): do not edit by hand
1
+% Generated by roxygen2: do not edit by hand
2 2
 % Please edit documentation in R/graphGML_methods.R
3 3
 \docType{methods}
4 4
 \name{plot,graphGML,missing-method}
... ...
@@ -25,5 +25,6 @@ The node with dotted order represents the population that has tailored gates (sa
25 25
 xmlfile <- system.file("extdata/cytotrol_tcell_cytobank.xml", package = "CytoML")
26 26
 g <- read.gatingML.cytobank(xmlfile)
27 27
 plot(g)
28
+
28 29
 }
29 30
 
... ...
@@ -1,4 +1,4 @@
1
-% Generated by roxygen2 (4.1.0): do not edit by hand
1
+% Generated by roxygen2: do not edit by hand
2 2
 % Please edit documentation in R/read.gatingML.cytobank.R
3 3
 \name{read.gatingML.cytobank}
4 4
 \alias{read.gatingML.cytobank}
... ...
@@ -1,4 +1,4 @@
1
-% Generated by roxygen2 (4.1.0): do not edit by hand
1
+% Generated by roxygen2: do not edit by hand
2 2
 % Please edit documentation in R/graphGML_methods.R
3 3
 \docType{methods}
4 4
 \name{show,graphGML-method}