Skip to content
Snippets Groups Projects

Compare revisions

Changes are shown as if the source revision was being merged into the target revision. Learn more about comparing revisions.

Source

Select target project
No results found

Target

Select target project
  • eci/shinyscreen
  • miroslav.kratochvil/shinyscreen
2 results
Show changes
Commits on Source (113)
Package: shinyscreen
Title: Pre-screening of Mass Spectrometry Data
Version: 0.8
Version: 0.9.0
Author: Todor Kondić
Maintainer: Todor Kondić <todor.kondic@uni.lu>
Authors@R:
......@@ -29,15 +29,21 @@ Description: Pre-screening of Mass Spectrometry Data.
License: Apache License (>= 2.0)
Encoding: UTF-8
LazyData: true
RoxygenNote: 6.1.1
RoxygenNote: 7.1.0
Roxygen: list(markdown = TRUE)
Collate:
'resources.R'
'base.R'
'resources.R'
'mix.R'
'extraction.R'
'run.R'
'shinyUI.R'
'api.R'
'shiny-ui-base.R'
'shiny-ui-config.R'
'shiny-ui-cmpd.R'
'shiny-ui-sets.R'
'shiny-ui-gen.R'
'shiny-ui-top.R'
Depends:
RMassBank,
RChemMass
......@@ -48,6 +54,9 @@ Imports:
yaml,
mzR,
MSnbase,
data.table,
assertthat,
withr,
ggplot2,
cowplot,
RColorBrewer,
......
# Generated by roxygen2: do not edit by hand
export(gen)
export(gen_base_ftab)
export(launch)
export(load_inputs)
export(mk_comp_tab)
export(read_conf)
export(run)
export(run_in_dir)
export(vrfy_conf)
import(data.table)
importFrom(shiny,validate)
## Copyright (C) 2020 by University of Luxembourg
## Licensed under the Apache License, Version 2.0 (the "License");
## you may not use this file except in compliance with the License.
## You may obtain a copy of the License at
## http://www.apache.org/licenses/LICENSE-2.0
## Unless required by applicable law or agreed to in writing, software
## distributed under the License is distributed on an "AS IS" BASIS,
## WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
## See the License for the specific language governing permissions and
## limitations under the License.
##' @export
run <- function(fn_conf) {
conf <- read_conf(fn_conf)
dir.create(conf$project,
showWarnings = F,
recursive = T)
m <- new_state(conf=conf,
GUI=F)
withr::with_dir(new=conf$project,code = run_in_dir(m))
return()
}
##' @export
run_in_dir <- function(m) {
m <- load_inputs(m)
m <- mk_comp_tab(m)
m <- gen_base_ftab(m)
invisible(m)
}
##' @export
gen_base_ftab <- function(m) {
files <- add_wd_to_mzml(df=m$input$tab$mzml,wdir=m$conf$project)
df <- gen_sup_ftab(files,m$out$tab$comp)
tab2file(df,file.path(m$conf$project,FN_FTAB_BASE))
m$out$tab$ftab <- df
m
}
##' @export
load_compound_input <- function(m) {
if (shiny::isTruthy(m$conf$compounds$known)) m$input$tab$known <- file2tab(m$conf$compounds$known)
if (shiny::isTruthy(m$conf$compounds$unknown)) m$input$tab$unknown <- file2tab(m$conf$compounds$unknown)
m$input$tab$setid <- read_setid(m$conf$compounds$sets,
m$input$tab$known,
m$input$tab$unknown)
m
}
load_data_input <- function(m) {
m$input$tab$mzml <- file2tab(m$conf$data)
m
}
##' @export
load_inputs <- function(m) {
m <- load_compound_input(m)
m <- load_data_input(m)
m
}
##' @export
mk_comp_tab <- function(m) {
message("Started assembling the lists of knowns and unknowns into the `comprehensive' table.")
setid <- m$input$tab$setid
setkey(setid,set,ID)
mzml<- m$input$tab$mzml
setkey(mzml,set)
setkey(m$input$tab$unknown,ID)
setkey(m$input$tab$known,ID)
unk<-m$input$tab$unknown
known<-m$input$tab$known
assert(xor(nrow(unk)==0,nrow(known)==0),msg="No compound lists have been provided. At least one of the known, or unknown compound lists is required.")
message("Begin generation of comp table.")
## knowns
setidKnown<- merge(mzml[,.(mode,tag,set)],setid[origin=="known",],allow.cartesian = T)
compKnown <- setidKnown[known,on="ID"]
compKnown[,`:=`(mz=mapply(get_mz_from_smiles,SMILES,mode,USE.NAMES = F))]
message("Generation of comp table: knowns done.")
## unknows
setidUnk<-merge(mzml[,.(mode,tag,set)],setid[origin=="unknown",],allow.cartesian = T)
compUnk <- setidUnk[unk,on="ID"]
message("Generation of comp table: unknowns done.")
df<-rbindlist(l=list(compKnown, compUnk),fill = T)
setnames(df,names(COMP_NAME_MAP),
function(o) COMP_NAME_MAP[[o]])
fn_out <- file.path(m$conf$project,FN_COMP_TAB)
tab2file(tab=df,file=fn_out)
message("Generation of comp table finished.")
setkeyv(df,c("set","tag","mz"))
m$out$tab$comp <- df
m
}
##' @export
read_conf <- function(fn) {
yaml::yaml.load_file(fn)
}
## read_conf <- function(fn_conf) {
## assert(isThingFile(fn_conf),msg=paste("Unable to read the configuration file:", fn_conf))
## conf <- yaml::yaml.load_file(fn_conf)
## conf <- vrfy_conf(conf)
## conf
## }
verify_compounds <- function(conf) {
## * Existence of input files
fn_cmpd_known <- conf$compounds$known
fn_cmpd_unk <- conf$compounds$unknown
fn_cmpd_sets <- conf$compounds$sets
## ** Compound lists and sets
assert(isThingFile(fn_cmpd_sets),
msg=paste("Cannot find the compound sets file:",fn_cmpd_sets))
## if (!is.null(fn_cmpd_known)) assert(isThingFile(fn_cmpd_known),
## msg=paste("Cannot find known compounds file:",fn_cmpd_known))
## if (!is.null(fn_cmpd_unk)) assert(isThingFile(fn_cmpd_unk),
## msg=paste("Cannot find unknown compounds file:",fn_cmpd_unk))
assert(xor(!isThingFile(fn_cmpd_known),!isThingFile(fn_cmpd_unk)),msg=paste("Both known and unknown compounds lists are missing."))
## * Data files
df_sets <- file2tab(fn_cmpd_sets)
all_sets<-unique(df_sets$set)
## ** Knowns
if (isThingFile(fn_cmpd_unk)) {
df_k <- file2tab(fn_cmpd_known)
are_knowns_OK <- shiny::isTruthy(vald_comp_tab(df_k,fn_cmpd_known, checkSMILES=T, checkNames=T))
assert(are_knowns_OK,msg='Aborted because known compounds table contained errors.')
}
## ** Unknowns
if (isThingFile(fn_cmpd_unk)) {
df_u <- file2tab(fn_cmpd_unk)
are_unknowns_OK <- shiny::isTruthy(vald_comp_tab(df_u,fn_cmpd_unk, checkSMILES=F, checkMz=T))
assert(are_unknowns_OK, msg='Aborted because unknown compounds table contained errors.')
}
return(list(conf=conf,all_sets=all_sets))
}
verify_data_df <- function(mzml,all_sets) {
no_files <- which(mzml[,!file.exists(Files)])
no_modes <- which(mzml[,!(mode %in% names(MODEMAP))])
no_sets <- which(mzml[,!(set %in% all_sets)])
assert(length(no_files)==0,msg = paste("Non-existent data files at rows:",paste(no_files,collapse = ',')))
assert(length(no_modes)==0,msg = paste("Unrecognised modes at rows:",paste(no_modes,collapse = ',')))
assert(length(no_sets)==0,msg = paste("Unknown sets at rows:",paste(no_sets,collapse = ',')))
}
verify_data <- function(conf,all_sets) {
## * Existence of input files
fn_data <- conf$data
assert(isThingFile(fn_data),msg=paste("Data table does not exist:",fn_data))
mzml <- file2tab(fn_data)
verify_data_df(mzml=mzml,all_sets)
return(conf)
}
##' @export
vrfy_conf <- function(conf) {
## * Existence of input files
z <- verify_compounds(conf)
conf <- z$conf
all_sets <- z$all_sets
verify_data(conf=conf,all_sets=all_sets)
return(conf)
}
......@@ -12,16 +12,18 @@
## See the License for the specific language governing permissions and
## limitations under the License.
##' @import data.table
## Redirections
the_ifelse <- data.table::fifelse
dtable <- data.table::data.table
tab2file<-function(tab,file,...) {
write.csv(x=tab,file=file,row.names=F,...)
data.table::fwrite(x=tab,file=file,...)
}
file2tab<-function(file,stringsAsFactors=F,comment.char='',sep=',',...) {
read.csv(file=file,
header=T,
stringsAsFactors=stringsAsFactors,
comment.char=comment.char,
na.strings=c("","NA"),...)
file2tab<-function(file,na.strings=c("","NA"),...) {
data.table::fread(file=file,na.strings = na.strings, ...)
}
isThingFile<-function(fn) {
......@@ -30,3 +32,15 @@ isThingFile<-function(fn) {
} else F
}
## Stolen from Stack Overflow
split_path <- function(path) {
if (dirname(path) %in% c(".", path)) return(basename(path))
return(c(basename(path), split_path(dirname(path))))
}
print_table <- function (df) {
paste(apply(df,1,function (row) paste(row,collapse=',')),collapse = "\n")
}
assert <- function(expr,msg) shiny::validate(shiny::need(expr,message=msg))
......@@ -267,20 +267,6 @@ gen_ms1_chrom_ht<-function(raw,mz,errEIC,rt=NULL,errRT=NULL) {
res
}
tab2file<-function(tab,file,...) {
write.csv(x=tab,file=file,row.names=F,...)
}
file2tab<-function(file,stringsAsFactors=F,comment.char='',...) {
read.csv(file=file,
header=T,
stringsAsFactors=stringsAsFactors,
comment.char=comment.char,
na.strings=c("","NA"),...)
}
get_ext_width <- function(maxid) {as.integer(log10(maxid)+1)}
id_fn_ext<-function(width,id) {
formatC(as.numeric(id),width=width,flag=0)
......
......@@ -31,6 +31,10 @@ get_mz_cmp_l<-function(id,mode,cmpL) {
res
}
get_mz_from_smiles <- function(smiles,mode) {
RChemMass::getSuspectFormulaMass(smiles)[[MODEMAP[[mode]]]]
}
get_col_from_cmp_l<-function(id,cname,cmpL) {
ind<-match(id,cmpL$ID)
x<-cmpL[[cname]][[ind]]
......@@ -53,7 +57,7 @@ pp_touch_q<-function(ftab) {
which(ftab$checked==FTAB_CHK_NONE | ftab$checked==FTAB_CHK_AUTO)
}
preProc <- function (ftable,noiseFac=3,errRT=0.5,intThreshMS1=1e5,intThreshMS2=0.05) {
preProc <- function (ftable,noiseFac=3,errRT=0.5,intThreshMS1=1e5,intThreshMS2=5000.) {
wds<-unique(ftable$wd)
fn_spec<-function(wd) readRDS(file.path(wd,FN_SPEC))
message("Loading RDS-es ...")
......@@ -145,7 +149,7 @@ preProc <- function (ftable,noiseFac=3,errRT=0.5,intThreshMS1=1e5,intThreshMS2=0
eicFilt<- eic[rtIndMS1,]
eicFilt<- eicFilt[which(eicFilt$intensity>intThreshMS1),]
mInt<- maxInt #mean(eicFilt$intensity)
rtInd <- rtInd[which(msms$intensity[rtInd]>intThreshMS2*mInt)] #Intense enough?
rtInd <- rtInd[which(msms$intensity[rtInd]>intThreshMS2)] #Intense enough?
msmsRT <- msms$rt[rtInd]
msmsInt<- msms$intensity[rtInd]
if (length(msmsRT) > 0) {
......@@ -449,7 +453,7 @@ plot_id_msn <- function(ni,
adornmzMLTab<-function(df,projDir=getwd()) {
add_wd_to_mzml <- function(df,wdir) {
pref<-df$set
mask<-is.na(pref)
drop<-df$files[mask]
......@@ -457,36 +461,16 @@ adornmzMLTab<-function(df,projDir=getwd()) {
df<-df[!mask,]
pref<-df$set
wd<-basename(tools::file_path_sans_ext(df$Files))
wd<-file.path(projDir,pref,wd)
wd<-file.path(wdir,pref,wd)
df$wd<-wd
df
}
genSuprFileTab <- function(fileTab,compTab) {
genOne<-function(ids,fn) {
K<-length(ids)
fTabRow<-fileTab[fileTab$Files == fn,]
cols<-lapply(names(fileTab),function(n) rep(fTabRow[[n]],K))
names(cols)<-NULL
cols<-c(cols,list(ids))
names(cols)<-c(names(fileTab),"ID")
df<-as.data.frame(cols,stringsAsFactors = F)
df
}
tabs<-lapply(fileTab$Files,function(fn)
{
wh<-which(fileTab$Files==fn)
set<-fileTab$set[[wh]]
md<-fileTab$mode[[wh]]
sel<-(compTab$set %in% set) & (compTab$mode %in% md)
ids<-compTab$ID[sel]
genOne(ids,fn)
})
res<-do.call(rbind,tabs)
res
gen_sup_ftab <- function(ftab,ctab) {
df<-ctab[ftab,on=c("set","mode"),allow.cartesian=T]
setkeyv(df,cols=FTAB_KEY)
setcolorder(df,neworder = FTAB_NAMES)
df
}
getEntryFromComp<-function(entry,id,set,mode,compTab) {
......@@ -496,9 +480,13 @@ getEntryFromComp<-function(entry,id,set,mode,compTab) {
res<- if (length(ind)==1) compTab[ind,entry] else {
if (length(ind)>1) {
stop("Nonunique entry selection in comprehensive table.")
warning("Nonunique selection in comprehensive table:")
for (i in ind) {
message('ID: ',compTab$ID[[i]],' set: ',compTab$set[[i]],' mode: ',compTab$mode[[i]])
}
warning("The compound set table likely containes duplicate IDs per set/mode combination. Please correct this.")
} else {
stop("Entries not found for id ", id,"set ",set, "and mode ", mode, " .")
warning("Entries not found for id ", id,"set ",set, "and mode ", mode, " .")
}
}
res
......@@ -506,29 +494,32 @@ getEntryFromComp<-function(entry,id,set,mode,compTab) {
res
}
addCompColsToFileTbl<-function(ft,compTab) {
nR<-nrow(ft)
mzCol<-rep(NA,nR)
nmCol<-rep("",nR)
rtCol<-rep(NA,nR)
## add_comp_ftab <- function(ft,ctab) {
## nR<-nrow(ft)
## mzCol<-rep(NA,nR)
## nmCol<-rep("",nR)
## rtCol<-rep(NA,nR)
for (ir in 1:nR) {
id<-ft[ir,"ID"]
set<-ft[ir,"set"]
m<-ft[ir,"mode"]
entries<-getEntryFromComp(c("mz","Name","rt"),id,set,m,compTab)
mzCol[[ir]]<- entries[["mz"]]
nm<-entries[["Name"]]
nmCol[[ir]]<- if (!is.na(nm)) nm else ""
rtCol[[ir]]<- entries[["rt"]]
}
ft$mz<-mzCol
ft$Name<-nmCol
ft$rt<-rtCol
ft
## for (ir in 1:nR) {
## id<-ft[ir,"ID"]
## set<-ft[ir,"set"]
## m<-ft[ir,"mode"]
## entries<-getEntryFromComp(c("mz","Name","rt"),id,set,m,ctab)
## mzCol[[ir]]<- entries[["mz"]]
## nm<-entries[["Name"]]
## nmCol[[ir]]<- if (!is.na(nm)) nm else ""
## rtCol[[ir]]<- entries[["rt"]]
## }
## ft$mz<-mzCol
## ft$Name<-nmCol
## ft$rt<-rtCol
## ft
## }
get_set_mode <- function(s,mzml) {
unique(mzml[set == s,mode])
}
vald_comp_tab<-function(df,ndf,checkSMILES=F,checkMz=F,checkNames=F) {
## Fields.
if (is.null(df$ID)) stop("Column ID missing in ",ndf," .")
......@@ -574,7 +565,6 @@ vald_comp_tab<-function(df,ndf,checkSMILES=F,checkMz=F,checkNames=F) {
ll<-length(unique(df$SMILES))
if (ll<lsmiles) {
warning("There are duplicate SMILES in the compound list. Trouble ahead.")
return(NULL)
}
}
......@@ -591,3 +581,40 @@ vald_comp_tab<-function(df,ndf,checkSMILES=F,checkMz=F,checkNames=F) {
df
}
read_setid <- function(fn,known,unk) {
assert(file.exists(fn),msg=paste("Please provide valid compounds set table:", fn))
assert(nrow(known)>0 || nrow(unk) > 0,msg="Please provide at least one compounds list.")
setid <- file2tab(fn)
id_k <- known$ID
id_u <- unk$ID
tmp <- setid[,.(ID,set,origin=the_ifelse(ID %in% id_k,"known",NA_character_))]
tmp <- tmp[,.(ID,set,origin=the_ifelse(is.na(origin) & ID %in% id_u,"unknown",origin))]
natmp <- tmp[is.na(origin),.(ID,set)]
assert(nrow(natmp)==0,msg=paste("The following IDs from set table have not been found in the compound table:","------",print_table(natmp),"------",sep = "\n"))
tmp
}
write_conf <- function(m,fn) {
m$conf$data <- file.path(m$conf$project,FN_DATA_TAB)
yaml::write_yaml(x=m$conf,file=fn)
}
write_state <- function(m,fn_conf) {
write_conf(m,fn_conf)
tab2file(tab=m$input$tab$mzml,file=file.path(m$conf$project,FN_DATA_TAB))
}
new_state <- function(conf,GUI) {
m <- list()
m$conf <- conf
m$GUI <- GUI
m$out$tab <- list()
m$input$tab$mzml <- EMPTY_MZML
m$input$tab$known <- EMPTY_KNOWN
m$input$tab$unknown <- EMPTY_UNKNOWN
m
}
......@@ -14,6 +14,14 @@
## Config defaults
CONF <- list(data=NA_character_,
project=getwd(),
compounds=list(known=NA_character_,
unknown=NA_character_,
sets=NA_character_))
## Constants
FN_FTAB_BASE<-"ftable.base.csv"
FN_FTAB_PP<-"ftable.pp.csv"
......@@ -24,12 +32,13 @@ FN_CMP_L<-"compounds.csv"
FN_LOC_SETID <-"setid.csv"
FN_COMP_TAB<-"comprehensive.csv"
FN_SPEC<-"specdata.rds"
MODEMAP<-list(pH="MpHp_mass",
mH="MmHm_mass",
pNH4="MpNH4_mass",
pNa="MpNa_mass")
MODEMAP<-list("[M+H]+"="MpHp_mass",
"[M-H]-"="MmHm_mass",
"[M+NH4]+"="MpNH4_mass",
"[M+Na]+"="MpNa_mass")
TAG_DEF<-"unspecified"
DISP_MODEMAP <- c(list("UNSET"="UNSET_MODE_ERROR"),MODEMAP)
TAG_DEF <- "unspecified"
TAG_DEF_DESC<-"Case"
DEFAULT_RT_RANGE=c(NA,NA)
DEFAULT_INT_RANGE=c(NA,NA)
......@@ -44,10 +53,10 @@ RT_DIGITS=2
M_DIGITS=4
PAL="Dark2"
REST_TXT_INP<-c("fnKnownL",
"fnUnkL",
"fnSetId",
"tagsInp")
## REST_TXT_INP<-c("fnKnownL",
## "fnUnkL",
## "fnSetId",
## "tagsInp")
REST_TAB<-c("mzml")
......@@ -90,7 +99,7 @@ RT_EXTR_ERR<-0.5 # min
RT_SHIFT_ERR <- 0.5 # min
MS1_INT_THOLD <- 1e5
MS2_INT_THOLD <- 0.05
MS2_INT_THOLD <- 5000.
MS1_SN_FAC <- 3.0
......@@ -98,3 +107,24 @@ MS1_SN_FAC <- 3.0
## Shiny objects
NUM_INP_WIDTH="15%"
## Comprehensive table properties
COMP_NAME_MAP <- list(RT="rt")
# COMP_NAMES <-c("ID","mz","rt","mode","set","origin","Name","SMILES")
## File table properties
FTAB_KEY=c("set","tag","mz")
FTAB_NAMES=c("ID", "mz", "rt", "tag", "mode", "set", "Name", "SMILES", "Files" , "wd","origin")
EMPTY_UNKNOWN <- dtable(ID=character(0),mz=numeric(0),RT=numeric(0),Name=character(0),CAS=character(0))
EMPTY_KNOWN <- dtable(ID=character(0),SMILES=character(0),RT=numeric(0),Name=character(0),CAS=character(0))
## Trivial data table
EMPTY_MZML <- dtable(Files=character(0),
tag=character(0),
mode=character(0),
set=character(0))
FN_DATA_TAB <- "data-files.csv"
## Copyright (C) 2020 by University of Luxembourg
## Licensed under the Apache License, Version 2.0 (the "License");
## you may not use this file except in compliance with the License.
## You may obtain a copy of the License at
## http://www.apache.org/licenses/LICENSE-2.0
## Unless required by applicable law or agreed to in writing, software
## distributed under the License is distributed on an "AS IS" BASIS,
## WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
## See the License for the specific language governing permissions and
## limitations under the License.
##' @importFrom shiny validate
react_v <- shiny::reactiveValues
react_f <- shiny::reactive
react_e <- shiny::eventReactive
obsrv <- shiny::observe
obsrv_e <- shiny::observeEvent
isol <- shiny::isolate
# volumes <- function() c(wd=getwd(), shinyFiles::getVolumes()())
validate1 <- function(expr,msg) shiny::validate(shiny::need(expr,msg))
path2vol <- function(path) {
## This function returns shinyFiles compatible volumes.
splits <- split_path(path)
file.path(tail(splits,1),'')
}
prim_box<-function(...) {shinydashboard::box(...,
status="primary",
solidHeader=T)}
good_box<-function(...) {shinydashboard::box(...,
status="success",
solidHeader=T)}
err_box<-function(...) {shinydashboard::box(...,
status="danger",
solidHeader=T)}
inact_box<-function(...) {shinydashboard::box(...,
status="danger",
solidHeader=T)}
html<-function(...) {shiny::tags$div(shiny::HTML(...))}
## num_input<-function(...,width=NUM_INP_WIDTH) {shiny::tags$div(id="inline",shiny::textInput(...,width=width))}
num_input <- function(inputId,label,...,width=NUM_INP_WIDTH) {
shiny::tags$div(style="display:inline-block",
shiny::tags$label(label, `for` = inputId),
shiny::tags$input(id = inputId, type = "text",style=paste("width:",width,sep = ""),...))
}
num_input_unit <- function(inputId,l1,l2,width=NUM_INP_WIDTH,...) {
shiny::tags$div(style="display:inline-block",
shiny::tags$label(l1, `for` = inputId),
shiny::tags$input(id = inputId, type = "text",style=paste("width:",width,sep = ""),...),
shiny::tags$label(paste(" ",l2,sep=""), `for` = inputId))
}
txt_file_input <- function(inputId,input,fileB,label,volumes) {
fnobj<-shinyFiles::parseFilePaths(roots = volumes,
selection = input[[fileB]])
fn <- fnobj[['datapath']]
if (isThingFile(fn)) {
shiny::textInput(inputId = inputId,
label = label,
value = fn)
} else {
shiny::isolate(currFn <- input[[inputId]])
if (!isThingFile(currFn)) {
shiny::textInput(inputId = inputId,
label = label,
value = "")
} else {
message('Why is this happening so much?')
shiny::textInput(inputId = inputId,
label = label,
value = currFn)
}
}
}
rev2list <- function(rv) {
## Take reactive values structure and convert them to nested
## lists.
if (class(rv)[[1]] != "reactivevalues")
rv else lapply(shiny::reactiveValuesToList(rv),rev2list)
}
list2rev <- function(lst) {
## Take nested named list and create reactive values from it.
if (class(lst)[[1]] != "list")
lst else do.call(react_v,lapply(lst,list2rev))
}
new_rv_state <- function(project) {
p <- normalizePath(path=project,winslash = '/')
x <- react_v(m=list2rev(new_state(list(project=p,data=""),GUI=T)))
x
}
mk_roots <- function(wd) local({
addons <- c("project"=normalizePath(wd,winslash = '/'))
def_vol <- function() {
path <- addons[['project']]
svols <- shinyFiles::getVolumes()()
vol <- path2vol(path)
sel <- match(vol,svols)
res <- names(svols)[[sel]]
res
}
list(set=function (rts) {addons <<- rts},
get=function () c(addons,shinyFiles::getVolumes()()),
def_vol=def_vol,
def_path=function() {
vol <- def_vol()
svols <- shinyFiles::getVolumes()()
pref <- svols[[vol]]
res <- sub(paste0(pref,'(.*)'),'\\1',addons[["project"]])
message('Relative path: ',res)
res
})
})
## Copyright (C) 2020 by University of Luxembourg
## Licensed under the Apache License, Version 2.0 (the "License");
## you may not use this file except in compliance with the License.
## You may obtain a copy of the License at
## http://www.apache.org/licenses/LICENSE-2.0
## Unless required by applicable law or agreed to in writing, software
## distributed under the License is distributed on an "AS IS" BASIS,
## WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
## See the License for the specific language governing permissions and
## limitations under the License.
## Commentary:
##
## Defines compound lists tab.
mk_ui_cmpd <- function() {
## ***** Compound List Tab *****
knownListBox<-prim_box(title="Known Compounds List",
rhandsontable::rHandsontableOutput("knownCtrl"),
width=NULL)
unkListBox<-prim_box(title="Unknown Compounds List",
rhandsontable::rHandsontableOutput("unkCtrl"),
width=NULL)
cmpListLayout <- shiny::fluidRow(shiny::column(knownListBox,
unkListBox,
width = 12))
cmpListTab <- shinydashboard::tabItem(tabName="compList",
cmpListLayout)
compListSideItem <- shinydashboard::menuItem(text="Compound list",
tabName="compList",
icon=shiny::icon("table"))
return(list(tab=cmpListTab,
side=compListSideItem))
}
server_cmpd <- function(input,output,session,rv,rf,roots) {
output$knownCtrl <- rhandsontable::renderRHandsontable({
df<-rv$m$input$tab$known
out<-if (!is.null(df)) {
df
} else {
data.frame(ID=numeric(),Name=character(),SMILES=character(),RT=numeric())
}
rhandsontable::rhandsontable(out,stretchH="all")
})
output$unkCtrl <- rhandsontable::renderRHandsontable({
df<-rv$m$input$tab$unknown
out<-if (!is.null(df)) {
df
} else {
data.frame(ID=numeric(),mz=numeric())
}
rhandsontable::rhandsontable(out,stretchH="all")
})
rv
}
## Copyright (C) 2020 by University of Luxembourg
## Licensed under the Apache License, Version 2.0 (the "License");
## you may not use this file except in compliance with the License.
## You may obtain a copy of the License at
## http://www.apache.org/licenses/LICENSE-2.0
## Unless required by applicable law or agreed to in writing, software
## distributed under the License is distributed on an "AS IS" BASIS,
## WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
## See the License for the specific language governing permissions and
## limitations under the License.
## Commentary:
##
## Defines config tab.
mk_ui_config <- function() {
browseFile <- function(title,
buttonName,
txtName,
buttonTxt="Import compound list.",
txtTxt="",
icon="file",
description=NULL,
...) {
prim_box(title=title,
shiny::h5(description),
collapsible=F,...)}
confImport <- prim_box(title="Import",
shiny::uiOutput("fnKnownLCtrl"),
shiny::uiOutput("fnUnkLCtrl"),
shiny::uiOutput("fnSetIdCtrl"),
shinyFiles::shinyFilesButton("impKnownListB",
label="Import knowns.",
title="",
icon=shiny::icon("file"),
multiple=F),
shinyFiles::shinyFilesButton("impUnkListB",
label="Import unknowns.",
title="",
icon=shiny::icon("file"),
multiple=F),
shinyFiles::shinyFilesButton("impSetIdB",
label="Import set ID table.",
title="",
icon=shiny::icon("file"),
multiple=T),
width=NULL)
confmzMLTags <- prim_box(title="Tags",
shiny::textInput("tagPropInp",
"What is a tag? (optional)",
value=TAG_DEF_DESC),
shiny::textInput("tagsInp",
"Comma-delimited list of tag types.",
value=""),
shiny::actionButton("updTagsB",
label = "Update tags.",
icon=shiny::icon("bomb")),
width=NULL)
confState <- prim_box(title="Configuration State",
shinyFiles::shinySaveButton("saveConfB",
"Save project.",
title="Save",
filename = "conf-state.yaml",
"yaml"),
shinyFiles::shinyFilesButton("restoreConfB",
label="Restore project.",
multiple=F,
title="Restore"),
shiny::actionButton(inputId="resetConfB",
label="Reset config (CAUTION!)",
icon=shiny::icon("trash")),
width=NULL)
confProj <- prim_box(title="Project",
shinyFiles::shinyDirButton(id="switchProjB",
label="Switch project.",
title="Switch project.",
icon=shiny::icon("recycle")),
width=NULL)
confmzMLtab <-prim_box(title="Raw Files in mzML Format",
shiny::h5("Use this file table to assign adduct modes and tags to the data files."),
shinyFiles::shinyFilesButton("mzMLB",
label="Select mzML files",
title="Select mzML files",
icon=shiny::icon("files-o"),
multiple=T),
rhandsontable::rHandsontableOutput("mzMLtabCtrl"),
width=NULL)
confLayout <- shiny::fluidRow(shiny::column(confImport,
confmzMLTags,
confState,
confProj,
width=4),
shiny::column(width=8,
confmzMLtab))
confTab <- shinydashboard::tabItem(tabName="config",
shiny::h2(GUI_TAB_TITLE[["conf"]]),
confLayout)
confSideItem <- shinydashboard::menuItem(text=GUI_SIDE_TITLE[["conf"]],
tabName="config",
icon=shiny::icon("user-cog"))
return(list(tab=confTab,
side=confSideItem))
}
react_conf_f <- function(input,output,session,rv,rf) {
## Reactive functions.
rf$gen_cmpd_inputs <- react_f({
rv$m$conf$compounds$known
rv$m$conf$compounds$unknown
rv$m$conf$compounds$sets
verify_compounds(rv$m$conf)
load_compound_input(rv$m)
})
rf$get_tags_from_txt <- react_f({
## Tags in the text box.
input$updTagsB
isol(if (isTruthy(input$tagsInp)) unique(txt2tags(input$tagsInp)) else TAG_DEF)
})
rf$ctrl2mzml_df <- react_f({
x <- tryCatch(rhandsontable::hot_to_r(input$mzMLtabCtrl),error=function(m) NULL)
shiny::req(x)
x
})
rf$ctrl2mzml <- react_f({
dtable(rf$ctrl2mzml_df())
})
rf$get_all_sets <- react_e(rv$m$input$tab$setid,unique(rv$m$input$tab$setid$set))
rf
}
server_conf <- function(input,output,session,rv,rf,roots) {
## ***** shinyFiles observers *****
shinyFiles::shinyFileChoose(input, 'impKnownListB',defaultRoot=roots$def_vol(),
defaultPath=roots$def_path(),roots=roots$get)
shinyFiles::shinyFileChoose(input, 'impUnkListB',defaultRoot=roots$def_vol(),
defaultPath=roots$def_path(),roots=roots$get)
shinyFiles::shinyFileChoose(input, 'impSetIdB',defaultRoot=roots$def_vol(),
defaultPath=roots$def_path(),roots=roots$get)
shinyFiles::shinyFileSave(input, 'saveConfB',defaultRoot=roots$def_vol(),
defaultPath=roots$def_path(),roots=roots$get)
shinyFiles::shinyFileChoose(input, 'restoreConfB',defaultRoot=roots$def_vol(),
defaultPath=roots$def_path(),roots=roots$get)
shinyFiles::shinyFileChoose(input, 'mzMLB',defaultRoot=roots$def_vol(),
defaultPath=roots$def_path(),roots=roots$get)
shinyFiles::shinyDirChoose(input, 'switchProjB',
roots=roots$get,
defaultRoot = "Computer",
defaultPath = "")
obsrv_e(input$switchProjB,{
## Update volumes function as needed.
spath<-shinyFiles::parseDirPath(roots=roots$get,
selection=input$switchProjB)
path<- if(length(spath)>0) spath[[1]] else NA
if (shiny::isTruthy(path)) {
rv$m$conf$project <- path
}
})
obsrv_e(input$saveConfB, {
conf<-rev2list(rv$m$conf)
fn <- shinyFiles::parseSavePath(roots=roots$get,input$saveConfB)[["datapath"]]
validate1(fn,msg="Invalid file to save config to.")
write_state(rev2list(rv$m),fn)
})
obsrv_e(input$restoreConfB,{
fn <- shinyFiles::parseFilePaths(roots=roots$get,input$restoreConfB)[["datapath"]]
assert(file.exists(fn), msg="The file is unreadable.")
rv$m$conf <- read_conf(fn)
for (nm in names(rv$m$conf$compounds)) {
shiny::updateTextInput(session=session,
inputId=nm,
value=rv$m$conf$compounds[[nm]])
}
fn <- rv$m$conf$data
shiny::req(fn)
rv$work_mzml_pre <- file2tab(fn)
})
obsrv_e(rv$work_mzml_pre,{
## update-files-on-restore
assert(rv$m$input$tab$setid, msg = "Compounds set table not built yet.")
all_sets <- rf$get_all_sets()
dt <- rv$work_mzml_pre
txt_tags <- rf$get_tags_from_txt()
dt_tags <- unique(dt$tag)
tags <- combine_tags(dt_tags,txt_tags)
inp_tags <- setdiff(tags,TAG_DEF)
shiny::updateTextInput(session = session,
inputId = "tagsInp",
value = inp_tags)
rv$work_mzml <- mzml2disp(dt, sets = all_sets, tags = tags)
})
obsrv_e(input$mzMLB,{
## update-files-on-mzmlb
df <- tryCatch(rhandsontable::hot_to_r(input$mzMLtabCtrl),error=function (e) NULL)
shiny::req(df)
assert(rv$m$input$tab$setid, msg = "Compounds set table not built yet.")
fchoice<-shinyFiles::parseFilePaths(roots = roots$get,input$mzMLB)
paths<-fchoice[["datapath"]]
tags <- rf$get_tags_from_txt()
all_sets <- unique(rv$m$input$tab$setid$set)
df <- add_mzML_files(df,paths)
rv$work_mzml <- df
})
obsrv_e(input$updTagsB,{
message("update-tags:",Sys.time())
df <- rf$ctrl2mzml_df()
tags <- rf$get_tags_from_txt()
z <- factor(as.character(df$tag), levels = tags)
df$tag <- factor(sapply(as.character(z),function(x) if (!is.na(x)) x else TAG_DEF),levels = tags)
rv$work_mzml <- df
})
obsrv({
## build-config
message("build-config:",Sys.time())
rv$m$conf$compounds$known <- input$known
rv$m$conf$compounds$unknown <- input$unknown
rv$m$conf$compounds$sets <- input$sets
rv$m$conf$data <- file.path(rv$m$conf$project,FN_DATA_TAB)
})
obsrv({
## build-compounds
message("build-compounds:",Sys.time())
rv$m <- rf$gen_cmpd_inputs()
})
obsrv({
## update-data-table
message("update-data-table:",Sys.time())
mzml <- rf$ctrl2mzml()
verify_data_df(mzml=mzml,all_sets=rf$get_all_sets())
rv$m$input$tab$mzml <- mzml
})
obsrv_e(rv$m$conf$project,{
## update-roots
message("update-roots:",Sys.time())
shiny::req(rv$m$conf$project)
dir <- normalizePath(rv$m$conf$project,winslash = '/')
if (roots$get()[["project"]] != dir) {
roots$set(c("start"= roots$get()[['project']] ,
"project" = dir))
} else {
roots$set(c("project" = dir))
}
})
## ***** Render *****
output$fnKnownLCtrl <- shiny::renderUI({
txt_file_input(inputId = 'known',
input = input,
label = html("The list of knowns. Required columns: <i>ID</i>, <i>SMILES</i>, <i>Name</i> and <i>RT</i> (the last two can be empty). Remember to quote <i>SMILES</i> and <i>Name</i> entries!"),
fileB = 'impKnownListB',
volumes=roots$get)
})
output$fnUnkLCtrl <- shiny::renderUI({
txt_file_input(inputId = 'unknown',
input = input,
label = html("The list of unknowns. Required columns: <i>ID</i>, <i>mz</i> and <i>RT</i> (<i>RT</i> can be empty)."),
fileB = 'impUnkListB',
volumes=roots$get)
})
output$fnSetIdCtrl <- shiny::renderUI({
txt_file_input(inputId = 'sets',
input = input,
label = html("Compounds set table. Required columns <i>ID</i> and <i>set</i>."),
fileB = 'impSetIdB',
volumes=roots$get)
})
output$mzMLtabCtrl <- rhandsontable::renderRHandsontable({
df <- rv$work_mzml
if (!shiny::isTruthy(df)) {
assert(rv$m$input$tab$setid, msg = "Compounds set table not built yet.")
all_sets <- unique(rv$m$input$tab$setid$set)
txt_tags <- rf$get_tags_from_txt()
df <- mzml2disp(EMPTY_MZML, sets = all_sets, tags = txt_tags)
}
rhandsontable::rhandsontable(df,stretchH="all")
})
rv
}
mzml2disp <- function(mzml,sets, tags) {
## Add factors for nicer rhandsontable output.
df <- as.data.frame(mzml,stringsAsFactors=F)
df$set <- factor(df$set,levels=sets)
df$tag <- factor(df$tag,levels=tags)
df$mode <- factor(df$mode,levels=names(DISP_MODEMAP))
df
}
disp2mzml <- function(df) {
df$set <- as.character(df$set)
df$mode <- as.character(df$mode)
df$tag <- as.character(df$tag)
dtable(df)
}
txt2tags <- function(txt) {
## Turns a string into tags
x <- if (shiny::isTruthy(txt)) {
trimws(unlist(strsplit(txt, ",")))
} else list()
as.list(c(TAG_DEF,x))
}
combine_tags <- function(df_tags,txt_tags) {
unique(c(TAG_DEF,df_tags,txt_tags))
}
add_mzML_files<-function(df,paths) {
lSet<-levels(df$set)
if (length(lSet > 0) && !is.na(lSet)) {
nR<-length(paths)
if (nR > 0) {
st <- nrow(df)+1
fi <- nrow(df)+nR
df[st:fi,'tag'] <- levels(df$tag)[[1]]
df[st:fi,'set'] <- levels(df$set)[[1]]
df[st:fi,'mode'] <- levels(df$mode)[[1]]
df[st:fi,'Files'] <- paths
}
} else {
warning("Define sets using the compound set table before trying to add files!")
}
df
}
## Copyright (C) 2020 by University of Luxembourg
## Licensed under the Apache License, Version 2.0 (the "License");
## you may not use this file except in compliance with the License.
## You may obtain a copy of the License at
## http://www.apache.org/licenses/LICENSE-2.0
## Unless required by applicable law or agreed to in writing, software
## distributed under the License is distributed on an "AS IS" BASIS,
## WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
## See the License for the specific language governing permissions and
## limitations under the License.
## Commentary:
##
## Defines gen tab.
mk_ui_gen <- function() {
genBoxExtract<-prim_box(title="Extract Spectra",
num_input(inputId="genNoProc",
label="Number of processes: ",
value=1),
num_input_unit(inputId="errCoarse",
l1="Precursor m/z error (coarse) (+/-): ",
l2="[Da]",
value=MS1_ERR_COARSE),
num_input_unit("errFinePPM",
l1="Precursor m/z error (fine) (+/-): ",
l2="[ppm]",
value=MS1_ERR_FINE),
num_input_unit("errEIC",
l1="EIC m/z error (+/-): ",
l2="[Da]",
value=EIC_ERR),
num_input_unit("errRTWin",
l1="Retention time tolerance (+/-): ",
l2="[min]",
value=RT_EXTR_ERR),
shiny::uiOutput("genSetSelInpCtrl"),
shiny::actionButton(inputId="genRunB",
label="Run!",
icon=shiny::icon("bomb")),
width=NULL)
genBoxAutoQA<-prim_box(title="Automatic Quality Control",
num_input("intThreshMS1",
label="Intensity threshold (MS1): ",
value=MS1_INT_THOLD),
num_input("intThreshMS2",
label="Intensity threshold (MS2): ",
value=MS2_INT_THOLD),
num_input("noiseFac",
label="Signal-to-noise ratio: ",
value=MS1_SN_FAC),
num_input_unit("errRT",
l1="Retention time shift tolerance (+/-): ",
value=RT_SHIFT_ERR,
l2="[min]"),
shiny::actionButton(inputId="qaAutoB",
label="Preprocess!",
icon=shiny::icon("bomb")),
width=NULL)
genBoxProcessed<-prim_box(title="Processed Sets",
rhandsontable::rHandsontableOutput("genTabProcCtrl"),
width=NULL)
genTab<-shinydashboard::tabItem(tabName = "gen",
shiny::h2(GUI_TAB_TITLE[["gen"]]),
shiny::fluidRow(shiny::column(genBoxExtract,
width=4),
shiny::column(genBoxProcessed,
genBoxAutoQA,width=4)))
genSideItem <- shinydashboard::menuItem(text=GUI_SIDE_TITLE[["gen"]],
tabName="gen",
icon=shiny::icon("cogs"))
return(list(tab=genTab,
side=genSideItem))
}
## Copyright (C) 2020 by University of Luxembourg
## Licensed under the Apache License, Version 2.0 (the "License");
## you may not use this file except in compliance with the License.
## You may obtain a copy of the License at
## http://www.apache.org/licenses/LICENSE-2.0
## Unless required by applicable law or agreed to in writing, software
## distributed under the License is distributed on an "AS IS" BASIS,
## WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
## See the License for the specific language governing permissions and
## limitations under the License.
## Commentary:
##
## Defines compounds sets tab.
mk_ui_sets <- function() {
## ***** Sets of compounds *****
setIdBox<-prim_box(title="Compound Sets",
rhandsontable::rHandsontableOutput("setIdCtrl"),
width = NULL)
setIdLayout<-shiny::fluidRow(shiny::column(setIdBox,
width = 12))
setIdTab<-shinydashboard::tabItem(tabName="setId",
setIdLayout)
setIdSideItem <- shinydashboard::menuItem(text="Compound sets",
tabName="setId",
icon=shiny::icon("table"))
return(list(tab=setIdTab,
side=setIdSideItem))
}
server_sets <- function(input,output,session,rv,rf,roots) {
output$setIdCtrl<- rhandsontable::renderRHandsontable({
df<-rv$m$input$tab$setid
rhandsontable::rhandsontable(df,stretchH="all")
})
rv
}
## Copyright (C) 2020 by University of Luxembourg
## Licensed under the Apache License, Version 2.0 (the "License");
## you may not use this file except in compliance with the License.
## You may obtain a copy of the License at
## http://www.apache.org/licenses/LICENSE-2.0
## Unless required by applicable law or agreed to in writing, software
## distributed under the License is distributed on an "AS IS" BASIS,
## WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
## See the License for the specific language governing permissions and
## limitations under the License.
## Commentary:
##
## This is a top-level Shiny file to bind them all.
mk_ui <- function (fn_style) {
## Top-level UI function.
headerText <- "Shinyscreen"
header <- shinydashboard::dashboardHeader(title=headerText,
shinydashboard::dropdownMenuOutput("notify"))
## Plugins
conf <- mk_ui_config()
cmpd <- mk_ui_cmpd()
sets <- mk_ui_sets()
gen <- mk_ui_gen()
sidebar <- shinydashboard::dashboardSidebar(shinydashboard::sidebarMenu(id='tabs',
conf$side,
gen$side,
shiny::hr(),
shiny::h5("Inputs"),
cmpd$side,
sets$side,
shiny::hr()))
body <- shinydashboard::dashboardBody(
shiny::tags$head(shiny::tags$style(shiny::includeHTML(fn_style))),
shinydashboard::tabItems(conf$tab,
cmpd$tab,
gen$tab,
sets$tab))
shinydashboard::dashboardPage(
header,
sidebar,
body)
}
mk_shinyscreen <- function(wd=getwd(),fn_style=system.file('www/custom.css',package = 'shinyscreen')) {
roots <- mk_roots(wd)
server <- function(input,output,session) {
## Top-level server function.
rf <- list() # Container for all
# reactive functions.
rv <- new_rv_state(project=wd) # Container for all
# reactive values.
rf <- react_conf_f(input,output,session,rv=rv,rf=rf) # Config related r. functions.
## Plugin servers.
rv <- server_conf(input,output,session,rv=rv,rf=rf,roots=roots)
rv <- server_cmpd(input,output,session,rv=rv,rf=rf,roots=roots)
rv <- server_sets(input,output,session,rv=rv,rf=rf,roots=roots)
obsrv_e(rv,{
message(paste("rv changed at ",Sys.time()))
})
session$onSessionEnded(function () {
stopApp()
})
}
shiny::shinyApp(ui=mk_ui(fn_style=fn_style),server=server)
}
##' @export
launch <- function(GUI=T,fn_conf="",wd=getwd(),...) {
if (GUI) {
app<-mk_shinyscreen(wd=wd)
shiny::runApp(appDir = app,...)
} else {
if (nchar(fn_conf)==0) {
fn_conf <- commandArgs(trailingOnly=T)[[1]]
}
run(fn_conf)
}
}
This diff is collapsed.
......@@ -253,12 +253,37 @@
In addition, the IDs of compounds belonging to the same set/mode
combination must be unique. Different ID sets may overlap.
Essentially, sets serve the purpouse of visually grouping files in
the plots. Also, set combines those groups of files with particular
collections of compounds (from the compound set CSV file).
** Config Screen
This is the start tab. Import the compound and set lists first,
then proceed to import the mzML files. Provide tags in the tag text
box and then assign the sets, modes and tags to the imported mzML
files using table widget. Once this is done, move on to the
`Spectra Extraction' tab.
~Spectra Extraction~ tab.
*** Resetting State
In case some inputs have been changed, but the program for some
reason does not seem to respond to those changes, perhaps
resetting the state using the button ~Reset State~ will help. This
will clean the current compound state tables (but, all the inputs
remain unchanged).
*** Switching Projects
The ~Switch project.~ button can be used to start new projects, or
change between them in the middle of processing.
Switching projects while the program is running makes most sense
if it is desired to change some of the inputs (e.g. different set
configuration, or same compound lists but different files) while
retaining the others. The user is presented with a directory
change dialogue which is then used to select the new project
directory. If needed, a new project directory can be created from
the same dialogue. All the inputs that currently exist on the
configuration tab will be kept during switching. This way, only
what needs to be changed can be changed.
** Spectra Extraction
Set the extraction parameters and then select a certain number of
......
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/mix.R
\name{RMB_EIC_prescreen_df}
\alias{RMB_EIC_prescreen_df}
\title{Prescreen}
\usage{
RMB_EIC_prescreen_df(wd, RMB_mode, FileList, cmpd_list,
ppm_limit_fine = 10, EIC_limit = 0.001)
}
\arguments{
\item{wd}{Absolute path to the directory that will contain the
resulting data frame.}
\item{RMB_mode}{...}
\item{FileList}{...}
\item{cmpd_list}{...}
\item{ppm_limit_fine}{...}
\item{EIC_limit}{...}
}
\description{
Prescreens. Writes data out. Adapted from ReSOLUTION
}
\author{
Emma Schymanski, Todor Kondić
}
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/mix.R
\name{gen_cmpd_l}
\alias{gen_cmpd_l}
\title{Generate Compound List File}
\usage{
gen_cmpd_l(src_fn, dest_fn)
}
\arguments{
\item{src_fn}{The input compound list CSV filename.}
\item{dest_fn}{The resulting compound list CSV filename.}
}
\value{
Number of compounds.
}
\description{
Generate the RMassBank compound list from the input compound list
in CSV file src_fn. The input compound list format is either a
Chemical Dashboard csv file with, at least, PREFERRED_ SMILES
columns \emph{filled} out, or just an ordinary CSV file with columns
SMILES and Names filled. Argument dest_fn is the destination
filename. Returns the number of compounds.
}
\author{
Todor Kondić
}
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/mix.R
\name{gen_cmpdl_and_load}
\alias{gen_cmpdl_and_load}
\title{Generate and Load the RMassBank Compound List}
\usage{
gen_cmpdl_and_load(wd, fn_cmpdl)
}
\arguments{
\item{wd}{Directory under which results are archived.}
\item{fn_cmpdl}{The input compound list filename.}
}
\value{
Named list. The key \code{fn_cmpdl} is the path of the
generated compound list and the key \code{n} the number of
compounds.
}
\description{
Generates the RMassBank compound list and loads it.
}
\author{
Todor Kondić
}
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/mix.R
\name{gen_ftable}
\alias{gen_ftable}
\title{Generate and Load the RMassBank Settings File}
\usage{
gen_ftable(fn_data, wd, n_cmpd)
}
\arguments{
\item{fn_data}{The mzML filename.}
\item{wd}{Directory under which results are archived.}
\item{n_cmpd}{Number of compounds.}
}
\value{
File path of the file table.
}
\description{
Generates file table.
}
\author{
Todor Kondić
}
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/mix.R
\name{gen_stgs_and_load}
\alias{gen_stgs_and_load}
\title{Generate and Load the RMassBank Settings File}
\usage{
gen_stgs_and_load(stgs, wd)
}
\arguments{
\item{stgs}{Settings named list, or a settings filename.}
\item{wd}{Directory under which results are archived.}
}
\value{
result of RMassBank::loadRmbSettings
}
\description{
Generates settings file and loads it.
}
\author{
Todor Kondić
}