Skip to content

Commit

Permalink
add multiple datasets support to read.ncdfFlowSet #47
Browse files Browse the repository at this point in the history
  • Loading branch information
mikejiang committed Jul 31, 2019
1 parent 050cdc6 commit 6d334c5
Show file tree
Hide file tree
Showing 2 changed files with 27 additions and 4 deletions.
13 changes: 9 additions & 4 deletions R/ncdfIO.R
Original file line number Diff line number Diff line change
Expand Up @@ -62,7 +62,7 @@ read.ncdfFlowSet <- function(files = NULL
,...) #dots to be passed to read.FCS
{
dots <- list(...)
emptyValue <- ifelse("emptyValue" %in% names(dots), dots[["emptyValue"]], TRUE)
dots[["emptyValue"]] <- ifelse("emptyValue" %in% names(dots), dots[["emptyValue"]], TRUE)
dim <- as.integer(match.arg(as.character(dim), c("2","3")))
channel_alias <- flowCore:::check_channel_alias(channel_alias)

Expand Down Expand Up @@ -94,7 +94,10 @@ read.ncdfFlowSet <- function(files = NULL
fileIds <- seq_len(nFile)

getChnlEvt <- function(curFile){
txt <- read.FCSheader(curFile, emptyValue = emptyValue)[[1]]

thisCall <- quote(read.FCSheader(curFile))
thisCall <- as.call(c(as.list(thisCall),dots))
txt <- eval(thisCall)[[1]]
nChannels <- as.integer(txt[["$PAR"]])
channelNames <- unlist(lapply(1:nChannels,function(i)flowCore:::readFCSgetPar(txt,paste("$P",i,"N",sep=""))))
channelNames<- unname(channelNames)
Expand Down Expand Up @@ -166,8 +169,10 @@ read.ncdfFlowSet <- function(files = NULL
}
}else
chnls_common <- channels

tmp <- read.FCSheader(files[1], emptyValue = emptyValue)[[1]]

thisCall <- quote(read.FCSheader(files[1]))
thisCall <- as.call(c(as.list(thisCall),dots))
tmp <- eval(thisCall)[[1]]

#make a dummy parameters slot for every frames to pass the validity check of flowSet class
#Note:This call will generate wrong params when chnls_common is less than original chnls
Expand Down
18 changes: 18 additions & 0 deletions tests/testthat/test_IO.R
Original file line number Diff line number Diff line change
@@ -1,4 +1,22 @@
context("IO test")

test_that("multi data segment", {
dataPath <- "~/rglab/workspace/flowCore/misc/"
filename <- file.path(dataPath, "multi-datasegment.fcs")
skip_if_not(file.exists(filename))
expect_warning(fr <- read.ncdfFlowSet(filename)[[1]], "39 additional data")
expect_is(fr, "flowFrame")
expect_equal(nrow(fr), 1244)

fr <- read.ncdfFlowSet(filename, dataset = 1)[[1]]
expect_equal(nrow(fr), 1244)
expect_equal(colnames(fr)[10], "FL2-PL")

fr <- read.ncdfFlowSet(filename, dataset = 10)[[1]]
expect_equal(nrow(fr), 955)
expect_equal(colnames(fr)[10], "testPL")
})

test_that("read.ncdfFlowSet", {

path <- system.file("extdata","compdata","data",package="flowCore")
Expand Down

0 comments on commit 6d334c5

Please sign in to comment.