Skip to content

Commit

Permalink
add multi data segment support for read.FCSheader RGLab/ncdfFlow#47
Browse files Browse the repository at this point in the history
  • Loading branch information
mikejiang committed Jul 31, 2019
1 parent ec6421d commit dce6fde
Show file tree
Hide file tree
Showing 3 changed files with 27 additions and 10 deletions.
16 changes: 8 additions & 8 deletions R/IO.R
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,7 @@ isFCSfile <- function(files)
#' @param path Directory where to look for the files.
#' @param keyword An optional character vector that specifies the FCS keyword
#' to read.
#' @param emptyValue see \code{link[flowCore]{read.FCS}}
#' @param ... other arguments passed to \code{link[flowCore]{read.FCS}}
#'
#' @return A list of character vectors. Each element of the list correspond to
#' one FCS file.
Expand All @@ -60,7 +60,7 @@ isFCSfile <- function(files)
#' samp
#'
#' @export
read.FCSheader <- function(files, path=".", keyword=NULL, emptyValue = TRUE)
read.FCSheader <- function(files, path=".", keyword=NULL, ...)
{

stopifnot(is.character(files), length(files)>=1, files!="")
Expand All @@ -69,7 +69,7 @@ read.FCSheader <- function(files, path=".", keyword=NULL, emptyValue = TRUE)
files = file.path(path, files)
res <- lapply(files, function(file){

thisRes <- try(header(file, emptyValue = emptyValue), silent = TRUE)
thisRes <- try(header(file, ...), silent = TRUE)
if(class(thisRes) == "try-error"){
stop(thisRes, file)
}else
Expand All @@ -81,10 +81,10 @@ read.FCSheader <- function(files, path=".", keyword=NULL, emptyValue = TRUE)
res
}

header <- function(files,emptyValue=TRUE){
header <- function(files, ...){
con <- file(files, open="rb")
offsets <- readFCSheader(con)
txt <- readFCStext(con, offsets,emptyValue=emptyValue)
offsets <- findOffsets(con, ...)
txt <- readFCStext(con, offsets, ...)
close(con)
txt
}
Expand Down Expand Up @@ -478,7 +478,7 @@ readFCSgetPar <- function(x, pnam, strict=TRUE)
## ==========================================================================
## Find all data sections in a file and record their offsets.
## - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
findOffsets <- function(con,emptyValue=TRUE, dataset, ...)
findOffsets <- function(con,emptyValue=TRUE, dataset = NULL, ...)
{
offsets <- readFCSheader(con)
offsets <- matrix(offsets, nrow = 1, dimnames = list(NULL, names(offsets)))
Expand Down Expand Up @@ -629,7 +629,7 @@ readFCSheader <- function(con, start=0)
## ==========================================================================
## parse FCS file text section
## - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
readFCStext <- function(con, offsets,emptyValue, cpp = TRUE, ...)
readFCStext <- function(con, offsets,emptyValue = TRUE, cpp = TRUE, ...)
{

seek(con, offsets["textstart"])
Expand Down
4 changes: 2 additions & 2 deletions man/read.FCSheader.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

17 changes: 17 additions & 0 deletions tests/testthat/test-IO.R
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,23 @@ rownames(expectPD) <- paste0(rownames(expectPD), ".fcs")
tmpdir <- tempfile()

write.flowSet(fs, tmpdir)


test_that("read.FCSheader--multi data segment", {
dataPath <- "~/rglab/workspace/flowCore/misc/"
filename <- file.path(dataPath, "multi-datasegment.fcs")
skip_if_not(file.exists(filename))

expect_warning(txt <- read.FCSheader(filename)[[1]], "39 additional data")
expect_equal(txt[['$TOT']], "1244")

txt <- read.FCSheader(filename, dataset = 1)[[1]]
expect_equal(txt[['$TOT']], "1244")

txt <- read.FCSheader(filename, dataset = 10)[[1]]
expect_equal(txt[['$TOT']], "955")

})
test_that("write.FCS--write correct $BEGINDATA",{

mat <- matrix(1:30,ncol = 3, dimnames = list(NULL, letters[1:3]))
Expand Down

0 comments on commit dce6fde

Please sign in to comment.