Skip to content

Commit

Permalink
always lock assaydata - close #92
Browse files Browse the repository at this point in the history
  • Loading branch information
LaurentGatto committed Aug 14, 2017
1 parent d2f46c6 commit 75233ee
Showing 1 changed file with 48 additions and 44 deletions.
92 changes: 48 additions & 44 deletions R/functions-MSnExp.R
Original file line number Diff line number Diff line change
Expand Up @@ -103,47 +103,48 @@ removePeaks_MSnExp <- function(object, t = "min", verbose = isMSnbaseVerbose())


clean_MSnExp <- function(object, all, verbose = isMSnbaseVerbose()) {
## -- was ---------------------------------------------------
## ifelse(verbose,progress <- "text",progress <- "none")
## spectra <- llply(spectra(object),function(x) clean(x),.progress=progress)
## object@assayData <- list2env(spectra)
## -- new ---------------------------------------------------
e <- new.env()
if (verbose) {
._cnt <- 1
pb <- txtProgressBar(min = 0, max = length(object), style = 3)
}
sapply(featureNames(object),
function(x) {
if (verbose) {
setTxtProgressBar(pb, ._cnt)
._cnt <<- ._cnt+1
}
sp <- get(x, envir = assayData(object))
xx <- clean(sp, all)
assign(x, xx, envir = e)
invisible(TRUE)
})
if (verbose) {
close(pb)
rm(pb)
rm(._cnt)
}
## ----------------------------------------------------------
object@processingData@cleaned <- TRUE
object@processingData@processing <- c(object@processingData@processing,
paste0("Spectra cleaned: ", date()))
## -- was ---------------------------------------------------
## ifelse(verbose,progress <- "text",progress <- "none")
## spectra <- llply(spectra(object),function(x) clean(x),.progress=progress)
## object@assayData <- list2env(spectra)
## -- new ---------------------------------------------------
e <- new.env()
if (verbose) {
._cnt <- 1
pb <- txtProgressBar(min = 0, max = length(object), style = 3)
}
sapply(featureNames(object),
function(x) {
if (verbose) {
setTxtProgressBar(pb, ._cnt)
._cnt <<- ._cnt+1
}
sp <- get(x, envir = assayData(object))
xx <- clean(sp, all)
assign(x, xx, envir = e)
invisible(TRUE)
})
if (verbose) {
close(pb)
rm(pb)
rm(._cnt)
}
## ----------------------------------------------------------
object@processingData@cleaned <- TRUE
object@processingData@processing <- c(object@processingData@processing,
paste0("Spectra cleaned: ", date()))

if (object@.cache$level > 0) {
hd <- header(object)
hd$peaks.count <- peaksCount(object)
object@.cache <- setCacheEnv(list(assaydata = assayData(object),
hd = hd),
object@.cache$level)
}
object@assayData <- e
if (validObject(object))
return(object)
if (object@.cache$level > 0) {
hd <- header(object)
hd$peaks.count <- peaksCount(object)
object@.cache <- setCacheEnv(list(assaydata = assayData(object),
hd = hd),
object@.cache$level)
}
lockEnvironment(e, bindings = TRUE)
object@assayData <- e
if (validObject(object))
return(object)
}


Expand Down Expand Up @@ -205,6 +206,7 @@ bin_MSnExp <- function(object, binSize = 1, verbose = isMSnbaseVerbose()) {
hd = hd),
object@.cache$level)
}
lockEnvironment(e, bindings = TRUE)
object@assayData <- e
if (validObject(object))
return(object)
Expand Down Expand Up @@ -268,8 +270,9 @@ pickPeaks_MSnExp <- function(object, halfWindowSize, method, SNR,
hd = hd),
object@.cache$level)
}
object@assayData <- e
if (validObject(object))
lockEnvironment(e, bindings = TRUE)
object@assayData <- e
if (validObject(object))
return(object)
}

Expand Down Expand Up @@ -312,8 +315,9 @@ smooth_MSnExp <- function(object, method, halfWindowSize, ...,
hd = hd),
object@.cache$level)
}
object@assayData <- e
if (validObject(object))
lockEnvironment(e, bindings = TRUE)
object@assayData <- e
if (validObject(object))
return(object)
}

Expand Down

0 comments on commit 75233ee

Please sign in to comment.