Browse code

fix check warnings RGLab/flowWorkspace#283

mikejiang authored on 02/04/2019 04:30:43
Showing 8 changed files

... ...
@@ -16,7 +16,7 @@
16 16
 #' }
17 17
 #' @importFrom flowWorkspace GatingSet transform
18 18
 #' @importFrom ncdfFlow read.ncdfFlowSet
19
-cytobank2GatingSet.default <- function(x, FCS){
19
+cytobank2GatingSet.default <- function(x, FCS, ...){
20 20
   g <- read.gatingML.cytobank(x)
21 21
   fs <- read.ncdfFlowSet(FCS)
22 22
   gs <- GatingSet(fs)
... ...
@@ -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");
... ...
@@ -122,6 +125,7 @@ setMethod("markernames",
122 125
           })
123 126
 
124 127
 #' @rdname cytobankExperiment
128
+#' @param do.NULL,prefix not used
125 129
 #' @export
126 130
 setMethod("colnames",
127 131
           signature=signature(x="cytobankExperiment"),
... ...
@@ -148,7 +152,7 @@ get_panel_per_file <- function(ce){
148 152
 #' @export
149 153
 #' @method getTransformations cytobankExperiment
150 154
 #' @export getTransformations
151
-getTransformations.cytobankExperiment <- function(x){
155
+getTransformations.cytobankExperiment <- function(x, ...){
152 156
   chnls <- colnames(x)
153 157
   low.chnls <- tolower(chnls)
154 158
   scales <- x$experiment$scales
... ...
@@ -292,7 +292,7 @@ getCompensationMatrices.graphGML <- function(x){
292 292
 #' @importFrom methods extends
293 293
 #' @export
294 294
 #' @method getTransformations graphGML
295
-getTransformations.graphGML <- function(x){
295
+getTransformations.graphGML <- function(x, ...){
296 296
   trans <- x@graphData[["transformations"]]
297 297
   if(!is.null(trans)){
298 298
     chnls <- names(trans)
... ...
@@ -24,12 +24,11 @@ compare the counts to cytobank's exported csv so that the parsing result can be
24 24
 }
25 25
 \examples{
26 26
 
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)
27
+acsfile <- system.file("extdata/cytobank_experiment.acs", package = "CytoML")
28
+ce <- cytobankExperiment(acsfile)
29
+gs <- cytobank2GatingSet(ce)
31 30
 ## verify the stats are correct
32
-statsfile <- system.file("extdata/cytotrol_tcell_cytobank_counts.csv", package = "CytoML")
31
+statsfile <- ce$attachments[1]
33 32
 dt_merged <- compare.counts(gs, statsfile, id.vars = "population", skip = "FCS Filename")
34 33
 all.equal(dt_merged[, count.x], dt_merged[, count.y], tol = 5e-4)
35 34
 
... ...
@@ -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
 }
... ...
@@ -14,7 +14,7 @@
14 14
 \usage{
15 15
 cytobankExperiment(acs, exdir = tempfile())
16 16
 
17
-\method{print}{cytobankExperiment}(x)
17
+\method{print}{cytobankExperiment}(x, ...)
18 18
 
19 19
 \method{getCompensationMatrices}{cytobankExperiment}(x)
20 20
 
... ...
@@ -23,7 +23,7 @@ cytobankExperiment(acs, exdir = tempfile())
23 23
 \S4method{colnames}{cytobankExperiment}(x, do.NULL = "missing",
24 24
   prefix = "missing")
25 25
 
26
-\method{getTransformations}{cytobankExperiment}(x)
26
+\method{getTransformations}{cytobankExperiment}(x, ...)
27 27
 
28 28
 \S4method{sampleNames}{cytobankExperiment}(object)
29 29
 
... ...
@@ -36,7 +36,11 @@ cytobankExperiment(acs, exdir = tempfile())
36 36
 
37 37
 \item{x}{cytobankExperiment object}
38 38
 
39
+\item{...}{not used}
40
+
39 41
 \item{object}{cytobankExperiment object}
42
+
43
+\item{do.NULL, prefix}{not used}
40 44
 }
41 45
 \value{
42 46
 cytobankExperiment object
... ...
@@ -4,7 +4,7 @@
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}
... ...
@@ -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}