Skip to content

Commit

Permalink
Update documentation and NAMESPACE
Browse files Browse the repository at this point in the history
  • Loading branch information
RogerGinBer committed Jul 5, 2021
1 parent d8535b4 commit 0562e62
Show file tree
Hide file tree
Showing 6 changed files with 101 additions and 73 deletions.
2 changes: 2 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -70,8 +70,10 @@ importFrom(grDevices,colorRamp)
importFrom(grDevices,rgb)
importFrom(keras,load_model_hdf5)
importFrom(keras,predict_classes)
importFrom(stats,IQR)
importFrom(stats,approx)
importFrom(stats,median)
importFrom(stats,quantile)
importFrom(stats,sd)
importFrom(utils,data)
importFrom(utils,read.csv)
Expand Down
71 changes: 40 additions & 31 deletions R/IL_methods.R
Original file line number Diff line number Diff line change
Expand Up @@ -43,27 +43,35 @@ function(struct, id, rts, minint = Inf) {

#'@title exportIL
#'@md
#'@description Organizes the IL entries into multiple injections
#' taking into account the user-specified parameters. Outputs a
#' single or multiple csv files that serve as input for the MS
#' to performed MSMS analysis.
#'@description Organizes the IL entries into multiple injections taking into
#' account the user-specified parameters. Outputs a single or multiple csv
#' files that serve as input for the MS to performed MSMS analysis.
#'
#'@param struct The RHermesExp object.
#'@param id The IL ID in the RHermesExp object. The IDs are
#' assigned by the order in which the IL are generated.
#'@param folder A string containing the folder to save the IL
#' csv/s into. By default will be your working directory
#'@param maxOver Numeric, very important. It's the number of
#' mz-rt segments that can be monitored at the same time by the
#' MS instrument. Higher numbers lead to less injections but the
#' number of scans for each IL entry will be reduced and gives
#' problems when deconvoluting the MS2 spectras.
#'@param sepFiles Logical, whether to generate a single csv file
#' or multiple csvs, each corresponding to each
#' injection/chromatographic run. From our experience with an
#' Orbitrap Fusion, separate csvs will simplify the task.
#'@return Nothing. As a side effect, it generates one/multiple
#' .csv files with the inclusion list data
#'@param id The IL ID in the RHermesExp object. The IDs are assigned by the
#' order in which the IL are generated.
#'@param file A string containing the folder to save the IL csv/s into and the
#' basename for the file. By default will be your working directory and the
#' default name is 'InclusionList' as in './InclusionList'.
#'@param mode Whether to plan set of continuous MS2 entries (PRM), adaptative
#' injection time scans at the apexes of the entries' peaks or both (which
#' optimizes instrument free time). Options are: "continuous", "deep" or
#' "both".
#'@param maxOver Numeric, very important. It's the number of mz-rt segments that
#' can be monitored at the same time by the MS instrument. Higher numbers lead
#' to less injections but the number of scans for each IL entry will be reduced
#' and gives problems when deconvoluting the MS2 spectras. It is ignored if
#' mode = "deep". Defaults to 5.
#'@param defaultIT Numeric, the default IT in ms for continuous MS2 scans (only
#' aplicable in Orbitrap instruments and for "continuous" and "both" modes).
#' Defaults to 100ms.
#'@param maxInjections Numeric, the maximum number of planned injections to
#' export. Defaults to 9999 to export all of them.
#'@param sepFiles Logical, whether to generate a single csv file or multiple
#' csvs, each corresponding to each injection/chromatographic run. From our
#' experience with an Orbitrap Fusion, separate csvs will simplify the task.
#'@return Nothing. As a side effect, it generates one/multiple .csv files with
#' the inclusion list data
#'@examples
#'if(FALSE){
#' exportIL(myHermes, 1, 'C:/SomeFolder', maxOver = 5, sepFiles = FALSE)
Expand Down Expand Up @@ -129,17 +137,17 @@ injectionPlanner <- function(IL, injections, maxover, byMaxInt = TRUE,
idx <- which(is.na(IL$start) | is.na(IL$end)) #NA depuration
if (length(idx) != 0) {IL <- IL[-idx, ]}
plan <- list()

if(mode != "continuous"){
message("Calculating high IT scans")
deep_IL <- calculate_deep_IL(IL)
} else {
deep_IL <- data.frame()
}

mint <- min(IL$start)
maxt <- max(IL$end)

if(mode %in% c("continuous", "both")){
while (nrow(IL) != 0 & injections > 0) {
timeInt <- seq(mint,
Expand All @@ -155,7 +163,7 @@ injectionPlanner <- function(IL, injections, maxover, byMaxInt = TRUE,
}
curinj <- IL[ok_entries, ]
IL <- IL[-ok_entries, ]

if(mode == "both" & any(OL == 0)){
deep_ok_entries <- c()
for (i in seq_len(nrow(deep_IL))) {
Expand All @@ -171,7 +179,7 @@ injectionPlanner <- function(IL, injections, maxover, byMaxInt = TRUE,
curinj <- rbind(curinj, deep_curinj, fill = TRUE)
}
}

plan <- c(plan, list(curinj))
injections <- injections - 1
}
Expand Down Expand Up @@ -219,7 +227,7 @@ injectionPlanner <- function(IL, injections, maxover, byMaxInt = TRUE,
}
}


if (nrow(IL) != 0) {
message(paste0(nrow(IL), "ILs haven't been added to the injection plan",
" due to lack of space. Try again with more injections,",
Expand Down Expand Up @@ -249,10 +257,10 @@ setMethod("show", "RHermesIL", function(object){
})

calculate_XIC_estimation <- function(raw, mzs, rts){
points <- filter(raw, between(mz, mzs[1], mzs[2]))
points <- filter(points, between(rt, rts[1], rts[2]))
points <- filter(raw, between(.data$mz, mzs[1], mzs[2]))
points <- filter(points, between(.data$rt, rts[1], rts[2]))
xic <- sapply(unique(points$rt), function(rt){
sum(points$rtiv[points$rt == rt])
sum(points$rtiv[points$rt == rt])
})
xic <- data.frame(rt = unique(points$rt), int = xic)
return(xic)
Expand Down Expand Up @@ -293,10 +301,11 @@ calculate_best_interval <- function(scans, objective = 1e6, maxIT = 2000){
intervals <- lapply(apexes, function(apex){
maxt <- min(max(apex - min(scans$rt), max(scans$rt) - apex), maxIT/1000)
scans <- approx(scans$rt, scans$int, n = 1000) %>% do.call(rbind, .) %>%
t %>% as.data.frame %>% rename(rt = x, rtiv = y)
t %>% as.data.frame
for(t in seq(0.1, maxt, 0.01)){
integral <- calculate_integral(filter(scans,
between(rt, apex-t, apex+t)))
between(.data$x,
apex-t, apex+t)))
if(integral > objective){return(c(apex-t, apex+t))}
}
return(c(apex-maxt, apex+maxt))
Expand All @@ -312,7 +321,7 @@ calculate_integral <- function(scans){
# Authorship Evan Friedland, Stackoverflow #6836409
inflect <- function(x, threshold = 1){
up <- sapply(1:threshold, function(n) c(x[-(seq(n))], rep(NA, n)))
down <- sapply(-1:-threshold, function(n){
down <- sapply(-1:-threshold, function(n){
c(rep(NA, abs(n)),
x[-seq(length(x), length(x) - abs(n) + 1)])
})
Expand Down
2 changes: 1 addition & 1 deletion R/Metadata_methods.R
Original file line number Diff line number Diff line change
Expand Up @@ -164,7 +164,7 @@ function(struct, db = "hmdb", adcharge = 1, admult = 1, DBfile = "",
row.names(struct@metadata@ExpParam@adlist) <- NULL
if(all(!is.na(adlist))){
struct@metadata@ExpParam@adlist <- filter(adlist(struct),
adduct %in% adlist)
.data$adduct %in% adlist)
if(nrow(adlist(struct)) == 0){
warning("No adducts remaining, please check the adduct names.")
}
Expand Down
41 changes: 22 additions & 19 deletions R/SOI_functions.R
Original file line number Diff line number Diff line change
Expand Up @@ -157,7 +157,7 @@ PLprocesser <- function(PL, ExpParam, SOIParam, blankPL = NA, filename) {
}
Groups <- distinct(Groups)


## Initial Peak Retrieval
message("Initial peak retrieval:")
peakscol <- lapply(seq_len(nrow(Groups)), retrievePeaks,
Expand Down Expand Up @@ -242,7 +242,7 @@ densityProc <- function(x, DataPL, h){
message("Running Density Filter")
BinRes <- densityFilter(DataPL, h, rtbin, "M0", shift)
cutoff <- BinRes[[1]] * scanspercent

#Correcting CUT < 1 cases to avoid errors (eg. if it was 0, any time region
#would be included). Added a 1 for robustness.
cutoff[cutoff < 1] <- median(c(cutoff[cutoff > 1], 1))
Expand Down Expand Up @@ -477,6 +477,7 @@ blankSubstraction <- function(Groups, blankPL){
Groups <- rbind(sure, Groups)
}

#'@importFrom stats IQR quantile
firstCleaning <- function(i, Groups, blankPL){
cur <- Groups[i, ]
st <- cur$start
Expand All @@ -497,11 +498,11 @@ firstCleaning <- function(i, Groups, blankPL){
(quantile(blankpks$rtiv, 0.25) + quantile(blankpks$rtiv, 0.75))

if(is.na(sampleCV) | is.na(blankCV)){return(FALSE)}

sampleMax <- max(peaks$rtiv)
# blankMax <- max(blankpks$rtiv)
q90_ratio <- quantile(peaks$rtiv,0.9) / quantile(blankpks$rtiv,0.9)

#We have to be restrictive with the conditions, otherwise we collect junk
if (sampleCV/blankCV > 5) {return(TRUE)}
if (q90_ratio > 3 & sampleMax > 15000) {return(TRUE)}
Expand All @@ -525,7 +526,7 @@ prepareNetInput <- function(i, Groups, blankPL){
smooth_pks <- data.frame(approx(x = peaks,
xout = seq(from = st, to = end,
length.out = Npoints),
rule = 1, ties = min))
rule = 1, ties = min))
smooth_pks[is.na(smooth_pks[, "y"]), "y"] <- 0
blankpks <- blankPL[.(f)] %>% filter(., .data$rt >= st - deltat &
.data$rt <= end + deltat &
Expand Down Expand Up @@ -573,7 +574,7 @@ parallelFilter <- function(anot, ScanResults, bins, timebin){
mint <- min(data)
maxt <- max(data)
res <- rep(0, length(bins))

#Shortcut to get in which bin each point is
l <- table(ceiling((data - bins[1]) / timebin))
if (length(l) == 0) return(res)
Expand All @@ -586,14 +587,14 @@ densityFilter <- function(ScanResults, h, timebin, iso = "M0", tshift = 0) {
rtmin <- floor(min(h$retentionTime))
rtmax <- ceiling(max(h$retentionTime))
bins <- seq(from = rtmin - tshift, to = rtmax + tshift, by = timebin)

#Getting how many scans were taken on each bin
scans <- lapply(bins, function(curbin) {
return(h %>% filter(., .data$retentionTime > curbin &
.data$retentionTime <= curbin + timebin) %>%
dim(.) %>% .[1])
})

#Counting how many scan entries are on each bin
setkeyv(ScanResults, c("formv", "rt"))
RES <- lapply(unique(ScanResults$formv), parallelFilter, ScanResults,
Expand Down Expand Up @@ -656,21 +657,23 @@ rho_chaos <- function(data, nlevels = 20, fillGaps = TRUE){

#### filterSOI-related ####

#' @title filterSOI
#' @author Roger Gine
#' @description Performs a series of filters and quality checks to a given SOI
#' list, removing unwanted SOIs in the process.
#' @inheritParams findSOI
#' @param id ID of the SOI list to be filtered/checked.
#' @param minint Minimun SOI intensity. All SOIs below this value will be
#' removed from the SOI list
#' @param isofidelity Boolean. Whether to perform an isotopic fidelity check.
#' @return A filtered SOI list.
#'@title filterSOI
#'@author Roger Gine
#'@description Performs a series of filters and quality checks to a given SOI
#' list, removing unwanted SOIs in the process.
#'@inheritParams findSOI
#'@param id ID of the SOI list to be filtered/checked.
#'@param minint Minimun SOI intensity. All SOIs below this value will be removed
#' from the SOI list
#'@param isofidelity Boolean. Whether to perform an isotopic fidelity check.
#'@param minscore Numeric. Minimum value (between 0 and 1) of isofidelity to
#' retain an entry. Defaults to 0.8.
#'@return A filtered SOI list.
#' @examples
#'\dontshow{struct <- readRDS(system.file("extdata", "exampleObject.rds",
#' package = "RHermes"))}
#' struct <- filterSOI(struct, id = 1, minint = 10000, isofidelity = TRUE)
#' @export
#'@export
setGeneric("filterSOI", function(struct, id, minint = 1e4, isofidelity, minscore = 0.8) {
standardGeneric("filterSOI")
})
Expand Down
49 changes: 30 additions & 19 deletions man/exportIL.Rd

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

9 changes: 6 additions & 3 deletions man/filterSOI.Rd

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

0 comments on commit 0562e62

Please sign in to comment.