Skip to content
Snippets Groups Projects
Unverified Commit c03a085d authored by Todor Kondic's avatar Todor Kondic
Browse files

api: prescreen creates new m$out$tab members, ms1_spec, ms2_spec, summ

* R/api.R(prescreen): Split the qa$ms table into three: one to hold
ms1 spectra (ms1_spec), one for ms2 spectra (ms2_spec) and a summary
table (former ftable, now summ). This was done due to mismatch in the
number of entries between MS1 and MS2 spectra and in order to keep
summ table lightweight (no complex objects such as other tables).

* R/resources.R(MS2_SPEC_COLS, MS1_SPEC_COLS, DEF_ORDER_SPECTRA):
Constants COLS define the columns of ms?_spec and DEF_ORDER_SPECTRA
lost set as uninteresting column.
parent 39c3ae5e
No related branches found
No related tags found
No related merge requests found
......@@ -333,14 +333,54 @@ conf_trans <- function(conf) {
##' @export
prescreen <- function(m) {
## Top-level auto prescreening function.
## TODO need to fix max spec intensity
gen_ms2_spec_tab <- function(ms) {data.table::rbindlist(lapply(1:nrow(ms), function (nr) {
adduct <- ms$adduct[[nr]]
ID <- ms$ID[[nr]]
Files <- ms$Files[[nr]]
spec <- ms$spec[[nr]]
dt <- if (length(spec[[1]]) < 3)
dtable(CE=NA_real_,
rt=NA_real_,
spec=list(dtable(mz=NA_real_,intensity=NA_real_))) else {
dtable(
CE=sapply(spec,
function (x) x$CE),
rt=sapply(spec,
function (x) x$rt),
spec=lapply(spec,
function (x) x$spec))
}
dt$Files <- Files
dt$ID <- ID
dt$adduct <- adduct
dt[,ms2_max_int := .(sapply(spec,function (sp) sp[,max(intensity)]))]
dt
}))}
gen_ms1_spec_tab <- function(ms) {
cols <- MS1_SPEC_COLS
ms[,..cols]
}
m$qa <- create_qa_table(m$extr$ms,m$conf$prescreen)
mms1 <- assess_ms1(m)
m <- assess_ms2(mms1)
fields <- c("Files","adduct","ID",QA_COLS,SPEC_DATA_COLS)
fields <- c("Files","adduct","ID",QA_COLS)
m$out$tab$ms2_spec <- gen_ms2_spec_tab(m$qa$ms)
data.table::setkeyv(m$out$tab$ms2_spec,c("adduct","Files","ID"))
m$out$tab$ms1_spec <- gen_ms1_spec_tab(m$qa$ms)
data.table::setkeyv(m$out$tab$ms1_spec,c("adduct","Files","ID"))
m$out$tab$summ <- merge(m$out$tab$comp,m$qa$ms[,..fields],by=c("Files","adduct","ID"))
m
}
##' @export
sort_spectra <- function(m) {
## Sorts the summary table (summ) in order specified either in
......
......@@ -183,7 +183,10 @@ QA_NUM_INT <- c("ms2_sel","ms1_rt_ind")
QA_COLS <- c(QA_FLAGS,QA_NUM_REAL,QA_NUM_INT)
SPEC_DATA_COLS <- c("eicMS1")
## MS2 spectral table columns
MS2_SPEC_COLS <- c("adduct","ID","CE","rt","Files","spec","ms2_max_int")
## MS1 spectral table columns
MS1_SPEC_COLS <- c("adduct","Files","ID","eicMS1","ms1_int","ms1_rt","ms1_mean")
## Default order of spectra in summary table
DEF_ORDER_SPECTRA <- c("set","qa_pass","ms1_int","adduct","mz","tag")
DEF_ORDER_SPECTRA <- c("qa_pass","ms1_int","adduct","mz","tag")
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment