diff --git a/R/api.R b/R/api.R
index 78afd5b72e1e278dbe655344088e3649dff070a4..46e2f7132a2f63c6c37d4263fa31c9224b95d238 100644
--- a/R/api.R
+++ b/R/api.R
@@ -1,4 +1,4 @@
-## Copyright (C) 2020,2021 by University of Luxembourg
+## Copyright (C) 2020,2021,2023 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.
@@ -14,6 +14,11 @@
 
 ##' @export
 run <- function(project="",m=NULL,phases=NULL,help=F) {
+
+    ## Get system-wide config.
+    eo = load_envopts()
+                        
+    
     all_phases=list(setup=setup_phase,
                     comptab=mk_comp_tab,
                     extract=extr_data,
@@ -37,7 +42,7 @@ run <- function(project="",m=NULL,phases=NULL,help=F) {
                                                       all_phases[phases]
                                                   }
     
-    m <- if (nchar(project)!=0) new_project(project) else if (!is.null(m)) m else stop("(run): Either the YAML config file (project),\n or the starting state (m) must be provided\n as the argument to the run function.")
+    m <- if (nchar(project)!=0) new_project(project,envopts=eo) else if (!is.null(m)) m else stop("(run): Either the YAML config file (project),\n or the starting state (m) must be provided\n as the argument to the run function.")
     ## m$conf$project <- norm_path(m$conf$project) #FIXME: Test in all workflows!
     m <- withr::with_dir(new=m$run$paths$project,code = Reduce(function (prev,f) f(prev),
                                                             x = the_phases,
@@ -675,17 +680,14 @@ create_plots <- function(m) {
 
 prepare_app <- function(dir_before,
                         projects,
-                        top_data_dir,
-                        metfrag_db_dir,
-                        metfrag_runtime) {
+                        top_data_dir) {
 
     ## Information that needs to be availabe to the shiny server.
     init <- list()
     init$dir_before <- dir_before
     init$top_data_dir <- norm_path(top_data_dir)
     init$projects <- norm_path(projects)
-    init$envopts = envopts(metfrag_db_dir=metfrag_db_dir,
-                           metfrag_jar=metfrag_runtime)
+    init$envopts = load_envopts()
 
     check_dir_absent(init$top_data_dir,what="top-data-dir")
     check_dir_absent(init$projects,what="projects")
@@ -699,6 +701,7 @@ prepare_app <- function(dir_before,
     dir.create(file.path(dir_start,'www'), showWarnings=F)
     saveRDS(object = init,file=file.path(dir_start,"init.rds"))
     file.copy(system.file(file.path("rmd","app.Rmd"),package = "shinyscreen"),file.path(dir_start,"app_run.Rmd"))
+    file.copy(system.file(file.path("rmd","app_config_and_status.Rmd"),package = "shinyscreen"),file.path(dir_start,"app_config_and_status.Rmd"))
     file.copy(system.file(file.path("www","custom.css"),package = "shinyscreen"),file.path(dir_start,"www","custom.css"))
     dir_start
 }
@@ -709,20 +712,18 @@ prepare_app <- function(dir_before,
 #'     containing project directories.
 #' @param top_data_dir `character(1)`, a location on the server side
 #'     containing data directories.
-#' @param metfrag_db_dir `character(1)`, a location on the server side
-#'     containing MetFrag databases.
-#' @param metfrag_runtime `character(1)`, a location on the server side
-#'     of the MetFrag jar file.
 #' @param shiny_args `list`, optional list of arguments conveyed to
 #'     `rmarkdown::run` `shiny_args` argument.
 #' @param render_args `list`, optional list of arguments conveyed to
 #'     `rmarkdown::run` `render_args` argument.
+#' @param metfrag_db_dir `character(1)`, a location on the server side
+#'     containing MetFrag databases.
+#' @param metfrag_runtime `character(1)`, a location on the server side
+#'     of the MetFrag jar file.
 #' @return Nada.
 #' @author Todor Kondić
 app <- function(projects=getwd(),
                 top_data_dir=getwd(),
-                metfrag_db_dir="",
-                metfrag_runtime="",
                 shiny_args=list(launch.browser=F),
                 render_args=NULL) {
     dir_before = getwd()
@@ -731,9 +732,7 @@ app <- function(projects=getwd(),
     message("projects: ", projects)
     dir_start = prepare_app(dir_before=dir_before,
                             projects=projects,
-                            top_data_dir=top_data_dir,
-                            metfrag_db_dir=metfrag_db_dir,
-                            metfrag_runtime=metfrag_runtime)
+                            top_data_dir=top_data_dir)
 
     on.exit(expr=setwd(dir_before))
     setwd(dir_start)
@@ -849,3 +848,18 @@ report <- function(m) {
     message("(report) ...done.")
     m
 }
+
+
+#' @title Initialise Shinyscreen Configuration
+#' @details This function is used to inform `shinyscreen` about the
+#'     working environment. It is only necessary to call it once. The
+#'     parameters will be memorised.
+#' @inheritParams envopts
+#' @return Nothing.
+#' @author Todor Kondić
+init <- function(metfrag_db_dir="",metfrag_jar="",java_bin=Sys.which("java")) {
+    e = envopts(metfrag_db_dir=metfrag_db_dir,
+                metfrag_jar=metfrag_jar,
+                java_bin=java_bin)
+    save_envopts(o=e)
+}
diff --git a/R/envopts.R b/R/envopts.R
index 9d0f5224d6ded284d57c27de610e2732b6eaf3e0..29ab7a3b625a15616206739eff92c7d811e711dd 100644
--- a/R/envopts.R
+++ b/R/envopts.R
@@ -59,3 +59,24 @@ is_metfrag_available <- function(e) {
 is_metfrag_local_available <- function(e) {
     is_metfrag_available(e) && nchar(e$metfrag$db_dir)>0L
 }
+
+
+get_envopts_fn <- function() {
+    file.path(tools::R_user_dir(package="shinyscreen",
+                                which="config"),
+              FN_ENVOPTS)
+}
+
+load_envopts <- function() {
+    cfgfile = get_envopts_fn()
+    check_conf_absent(cfgfile)
+    readRDS(cfgfile)
+    
+}
+
+save_envopts <- function(o) {
+    cfgfile = get_envopts_fn()
+    dr = dirname(cfgfile)
+    dir.create(path = dr, showWarnings = F, recursive=T)
+    saveRDS(o,cfgfile)
+}
diff --git a/R/errors.R b/R/errors.R
index d6175be288e8afcbae71304653ba8eff6560eebb..d74ca7d699c45050f25ce011bee009b33914b84c 100644
--- a/R/errors.R
+++ b/R/errors.R
@@ -47,3 +47,9 @@ check_key_absent <- function(keys,l,what) {
     if (length(keys_absent)>0L) stop(errorCondition(paste0("Keys [",paste0(keys_absent,collapse=', '), "] ",hv," not been found for ", what),
                                                     class = paste0(what,'-absent')))
 }
+
+
+check_conf_absent <- function(cfgfile) {
+    check_notastring(cfgfile,"envopts")
+    if (!file.exists(cfgfile)) stop(errorCondition("The system configuration file does not exist. Please initialise shinyscreen by calling `shinyscreen::init' function.", class="envopts-file-absent"))
+}
diff --git a/R/resources.R b/R/resources.R
index fe6136de0e4d25c0618ae142f7b817d5374c1cb7..25f12f91a53647120dee44ccd18539e3ec0b0fcb 100644
--- a/R/resources.R
+++ b/R/resources.R
@@ -1,4 +1,4 @@
-## Copyright (C) 2020,2021 by University of Luxembourg
+## Copyright (C) 2020,2021,2022,2023 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.
@@ -22,6 +22,7 @@ CONF <- list(data=NA_character_,
                             sets=NA_character_))
 
 ## Constants
+FN_ENVOPTS="envopts.rds"
 FN_SUMM_BASE<-"summ.base.csv"
 FN_SUMM_PP<-"summ.pp.csv"
 FN_PP_OUT_PREF<-"PP.filetable"
@@ -117,7 +118,7 @@ MS1_SN_FAC <- 3.0
 
 ## Shiny objects
 
-NUM_INP_WIDTH=40
+NUM_INP_WIDTH=20
 NUM_INP_HEIGHT="5%"
 
 
@@ -344,13 +345,10 @@ METFRAG_PREPFLT_DEFAULT = c("UnconnectedCompoundFilter","IsotopeFilter")
 METFRAG_POSTPFLT_CHOICES = c("InChIKeyFilter")
 METFRAG_POSTPFLT_DEFAULT = c("InChIKeyFilter")
 METFRAG_DEFAULT_SCORES = list(FragmenterScore=1.0,OfflineIndividualMoNAScore=1.0)
-                                        # AutomatedPeakFingerprintAnnotationScore,
-                                        # AutomatedLossFingerprintAnnotationScore
-                                        # supposedly
-                                        # do
-                                        # not
-                                        # work
-                                        # well.
+METFRAG_INTRINSIC_SCORES = list("FragmenterScore",
+                                "OfflineIndividualMoNAScore",
+                                "AutomatedPeakFingerprintAnnotationScore",
+                                "AutomatedLossFingerprintAnnotationScore")
 
 ## METFRAG_DEFAULT_WEIGHTS = "1,1"
 METFRAG_DEFAULT_MAX_TREE_DEPTH = 2
diff --git a/R/shiny-state.R b/R/shiny-state.R
index 5f04631350d33c2635c51eccdef758aeebc79f24..b76e04dbd774d7d6ae6f7ae1ddc7fc8803c0ed68 100644
--- a/R/shiny-state.R
+++ b/R/shiny-state.R
@@ -528,61 +528,3 @@ get_mprop_ms2_metadata <- function(ltab_entry) {
  res
   
 }
-
-make_metfrag_panel <- function(envopts) {
-
-    ctrls = list(HTML("MetFrag submodule has been disabled, because no MetFrag runtime has been specified in `envopts'"))
-    if (is_metfrag_available(envopts)) {
-
-        if (is_metfrag_local_available(envopts)) {
-            dbtype = selectInput("mf_database_type", label="Database type",
-                                 choices=METFRAG_DATABASE_TYPE,
-                                 selected=METFRAG_DEFAULT_DATABASE_TYPE)
-            dbselect = selectInput("mf_local_database_path",
-                                   "Local Database Path",
-                                   choices=character(0))
-            
-        } else {
-            dbtype = selectInput("mf_database_type", label="Database type",
-                                 choices=METFRAG_REMOTE_DATABASE_TYPE,
-                                 selected=METFRAG_DEFAULT_REMOTE_DATABASE_TYPE)
-            dbselect = HTML("No local MetFrag databases available.")
-        }
-        
-        
-        ctrls = list(numericInput("mf_database_search_relative_mass_deviation",
-                              label="Database search relative mass deviation",
-                              value=5),
-                     numericInput("mf_fragment_peak_match_absolute_mass_deviation",
-                                  label="Fragment peak match absolute mass deviation",
-                                  value=METFRAG_DEFAULT_ABSMASSDEV),
-                     numericInput("mf_fragment_peak_match_relative_mass_deviation",
-                                  label="Fragment peak match relative mass deviation",
-                                  value=METFRAG_DEFAULT_RELMASSDEV),
-                     numericInput("mf_maximum_tree_depth", label="MaximumTreeDepth",
-                                  value=METFRAG_DEFAULT_MAX_TREE_DEPTH),
-                     selectInput("mf_metfrag_candidate_writer",
-                                 label="MetFrag Candidate Writer",
-                                 choices=shinyscreen:::METFRAG_WRITER_CHOICES,
-                                 selected=shinyscreen:::METFRAG_DEFAULT_WRITER),
-                     dbtype,
-                     dbselect,
-                     selectInput("mf_pre_processing_candidate_filter",
-                                 label="Preprocessing candidate filter",
-                                 choices=shinyscreen:::METFRAG_PREPFLT_CHOICES,
-                                 selected=shinyscreen:::METFRAG_PREPFLT_DEFAULT,
-                                 multiple=T),
-                     selectInput("mf_post_processing_candidate_filter",
-                                 label="Postprocessing candidate filter",
-                                 choices=shinyscreen:::METFRAG_POSTPFLT_CHOICES,
-                                 selected=shinyscreen:::METFRAG_POSTPFLT_DEFAULT,
-                                 multiple=T),
-                     textInput("mf_score_types",label="Score Types",value=METFRAG_DEFAULT_SCORES),
-                     textInput("mf_score_weights",label="Score Weights",
-                               value=METFRAG_DEFAULT_WEIGHTS),
-                     numericInput("mf_num_threads",label="Number of threads", value=1L))
-    }
-
-
-    ctrls
-}
diff --git a/R/shiny-ui-base.R b/R/shiny-ui-base.R
index 581f0778549ef35b1a03e66e28ca71437e2c2613..8193bc71f0e2a2ddf128dcf7120ecd93a30d6b61 100644
--- a/R/shiny-ui-base.R
+++ b/R/shiny-ui-base.R
@@ -23,6 +23,12 @@ obsrv_e = shiny::observeEvent
 isol = shiny::isolate
 
 
+
+embed_rmd <- function(fn) {
+}
+
+
+
 celledit_values <- function(col,values,labels=NULL,addna=T) {
     if (is.null(labels)) labels = values
     if (length(values)==0 || nchar(values)==0) return(character(0))
@@ -141,12 +147,13 @@ mz_input <- function(input_mz,input_unit,width=NUM_INP_WIDTH,height=NUM_INP_HEIG
 }
 
 ##' @export
-rt_input <- function(input_rt,input_unit,width=NUM_INP_WIDTH,width_u=1-NUM_INP_WIDTH,height=NUM_INP_HEIGHT,def_rt=0,def_unit="min",pref="+/-") {
+rt_input <- function(input_rt,input_unit,width=NUM_INP_WIDTH,width_u=NUM_INP_WIDTH,height=NUM_INP_HEIGHT,def_rt=0,def_unit="min",pref="+/-") {
     width=paste0(as.character(width), "%")
     width_u=paste0(as.character(width_u), "%")
 
     style="display: inline-block; vertical-align:top; width: "
     style=paste0(style,width,"; ")
+    style="display: inline-block; vertical-align:top;"
     stylel = "display: inline-block; vertical-align:top;"
     styleu = paste0("display: inline-block; vertical-align:top; color: black; width: ",width_u,";")
     shiny::div(shiny::div(style=stylel,
@@ -1204,12 +1211,12 @@ mk_shinyscreen_server <- function(projects,init) {
                 if (dtype == "LocalSDF") patt = "(sdf)|(SDF)$"
                 if (dtype == "LocalPSV") patt = "(psv)|(PSV)$"
                 updateSelectInput(session=session,
-                                  inputId="mf_local_database_path",
+                                  inputId="mf_local_database",
                                   choices=list.files(path=init$envopts$metfrag$db_dir,
                                                      pattern=patt))
             } else {
                    updateSelectInput(session=session,
-                                     inputId="mf_local_database_path",
+                                     inputId="mf_local_database",
                                      choices=character(0))
             }
         }, label = "mf-database-type")
@@ -1663,8 +1670,6 @@ mk_shinyscreen_server <- function(projects,init) {
                 notfound
             }
         })
-        
-            
             
     }
 
diff --git a/inst/rmd/app.Rmd b/inst/rmd/app.Rmd
index a0c275ac0cf86a33d649be72fd3cca19d627cffd..1f14066eeb97197d545628322c5ab5ce5cece077 100644
--- a/inst/rmd/app.Rmd
+++ b/inst/rmd/app.Rmd
@@ -218,9 +218,9 @@ CSV file used with Shinyscreen.
 Select one, or more compound lists by clicking `Select` button.
 </details>
 
-<div style= "display: flex; vertical-align:top; padding-right: 1.0em">
+<div style= "display: flex; vertical-align:top; padding-right: 1.0em"> <!-- comp-list-box -->
 
-<div>
+<div> <!-- comp-list-sel -->
 ```{r, echo=FALSE}
 selectInput('comp_list',
             label = "Select compound lists",
@@ -230,9 +230,9 @@ actionButton(inputId = "comp_list_b",
              label= "Select")
 
 ```
-</div>
+</div> <!-- comp-list-sel -->
 
-<div>
+<div> <!-- comp-list-disp -->
 
 **Selected compound lists**
 
@@ -240,9 +240,10 @@ actionButton(inputId = "comp_list_b",
 htmlOutput('comp_list_report')
 ```
 
-</div>
+</div> <!-- comp-list-disp -->
+
+</div> <!-- comp-list-box -->
 
-</div>
 #### Select set lists
 
 <details><summary>About set lists (_setid_ tables)</summary>
@@ -259,9 +260,9 @@ columns,
 Select one set list by clicking `Select` button.
 </details>
 
-<div style= "display: flex; vertical-align:top; padding-right: 1em">
+<div style= "display: flex; vertical-align:top; padding-right: 1em"> <!-- set-list-box -->
 
-<div>
+<div> <!-- set-list-sel -->
 
 ```{r, echo=FALSE}
 selectInput('set_list',
@@ -273,9 +274,9 @@ actionButton(inputId = "set_list_b",
 
 ```
 
-</div>
+</div> <!-- set-list-sel -->
 
-<div>
+<div> <!-- set-list-rep -->
 
 **Selected `setid' list**
 
@@ -283,9 +284,9 @@ actionButton(inputId = "set_list_b",
 htmlOutput('sets_report')
 ```
 
-</div>
+</div> <!-- set-list-rep -->
 
-<div>
+</div> <!-- set-list-box -->
 
 ### Data files
 <details><summary>Load data files</summary>
@@ -324,9 +325,6 @@ DT::DTOutput("datafiles",width="25%")
 actionButton("rem_dfiles_b",label="Remove selected entries",width="10%")
 ```
 
-
-
-
 <details>
 
 <summary>Assign sets to tags.</summary>
@@ -341,489 +339,24 @@ DT::DTOutput("datatab",width="25%")
 ```
 
 ## Configure, Extract, Prescreen {.tabset}
-
-<details><summary>Extract spectra from data files.</summary>
-
-Spectral extraction is controled by the parameters under the
-_Extraction_ tab, while the quality check parameters are located under
-the _Prescreening_ tab.
-
-After Shinyscreen is configured, the compound and setid lists loaded,
-it is possible to proceed with extracting the data. The extraction
-process can start after pressing `Extract`. Depending on the size of
-the commpound list and the properties of the data files this may take
-a while.
-
-Once the data is extracted, quality checking can be carried out using
-the `Prescreen` button.
-
-The parameters affecting current extraction are displayed in the
-*Overview* section. 
-
-</details>
-
-
-<div style= "display: flex; vertical-align:top;">
-<div style= "padding-right: 0.5em">
-### Extraction
-
-#### Spectra extraction based settings
-
-<details><summary>MS1 coarse error</summary>
-
-Extract all entries matching the target mass within this error in the
-precursor table.
-</details>
-```{r, echo=F}
-vu <- get_val_unit(def_state$conf$tolerance[["ms1 coarse"]])
-shinyscreen::mz_input(input_mz = "ms1_coarse",
-                       input_unit = "ms1_coarse_unit",
-                       def_mz = vu[['val']],
-                       def_unit = vu[['unit']])
-```
-
-<details><summary>MS1 fine error</summary>
-
-The precursor table masses can be of lower accuracy. Once there is a
-match within the coarse error, it can be further checked versus the
-fine error bounds directly in the mass spectrum.
-
-</details>
-```{r, echo=F}
-vu <- get_val_unit(def_state$conf$tolerance[["ms1 fine"]])
-shinyscreen::mz_input(input_mz = "ms1_fine",
-                      input_unit = "ms1_fine_unit",
-                      def_mz = vu[['val']],
-                      def_unit = vu[['unit']])
-```
-
-<details><summary>MS1 EIC window</summary>
-
-The mz interval over which the intensities are aggregated to generate
-a chromatogram.
-
-</details>
-```{r, echo=F}
-vu <- get_val_unit(def_state$conf$tolerance[["eic"]])
-shinyscreen::mz_input(input_mz = "ms1_eic",
-                      input_unit = "ms1_eic_unit",
-                      def_mz = vu[['val']],
-                      def_unit = vu[['unit']])
-```
-
-<details><summary>Retention time window</summary>
-
-If the expected retention time has been specified for the compound,
-then search for the MS1 signature inside the window defined by this
-range.
-
-</details>
-```{r, echo=F}
-vu <- get_val_unit(def_state$conf$tolerance[["rt"]])
-shinyscreen::rt_input(input_rt = "ms1_rt_win",
-                      input_unit = "ms1_rt_win_unit",
-                      def_rt = vu[['val']],
-                      def_unit = vu[['unit']])
-```
-
-<details><summary>Fill missing precursors</summary>
-
-* **fill** : Try to guess precursors of MS2 entries. This is done by
-picking MS1 which chronologically preceeds a given MS2 entry.
-* **omit** : Ignore MS2 with missing precursors.
-* **do_nothing** : Default. Use MS1--MS2 metadata recorded in the file
-to associate MS1 and MS2 entries. Usually works.  
-</details>
-```{r, echo=F}
-radioButtons("missingprec",
-             label = "Missing precursors",
-             choices = c("do_nothing","fill","omit"),
-             selected = "do_nothing")
-
-```
-
-### Prescreening
-
-<details><summary>MS1 intensity threshold</summary>
-
-Ignore MS1 signal below the threshold.
-
-</details>
-```{r, echo=F}
-
-numericInput(inputId = "ms1_int_thresh",
-             label = NULL,
-             value = def_state$conf$prescreen$ms1_int_thresh)
-```
-
-<details><summary>MS2 intensity threshold</summary>
-
-Ignore MS2 signal below the threshold.
-
-</details>
-```{r, echo=F}
-
-numericInput(inputId = "ms2_int_thresh",
-             label = NULL,
-             value = def_state$conf$prescreen$ms2_int_thresh)
-```
-
-
-MS1 signal-to-noise ratio.
-
-```{r, echo=F}
-
-numericInput(inputId = "s2n",
-             label = NULL,
-             value = def_state$conf$prescreen$s2n)
-```
-
-
-<details><summary>MS1/MS2 retention delay.</summary>
-
-Look for associated MS2 spectrum within this window around the MS1
-peak.
-
-</details>
-```{r, echo=F}
-vu <- get_val_unit(def_state$conf$prescreen[["ret_time_shift_tol"]])
-shinyscreen::rt_input(input_rt = "ret_time_shift_tol",
-                      input_unit = "ret_time_shift_tol_unit",
-                      def_rt = vu[['val']],
-                      def_unit = vu[['unit']])
-```
-
-### MetFrag (`r htmlOutput("cando_metfrag", inline=T)`)
-
-If `java` and `MetFragCL` are available, Shinyscreen can run
-`MetFragCL`. The configuration is a subset of what a MetFrag config
-file looks like.
-
-```{r, echo=F}
-uiOutput('metfrag_panel')
-```
-### Report
-
-<details><summary>Create a report</summary>
-
-Shinyscreen can produce a report containing graps of EICs and spectra
-for some or all compounds. The controls below define what enters the
-report. Please keep in mind that producing a PDF output with thousands
-of compounds will take huge amount of time, so if you are prescreening
-a lot of compounds, consider restricting limiting the output to, for
-example, those entries that have passed the quality checks.
-
-</details>
-
-
-<div style= "display: flex; vertical-align:top; padding-right: 0.5em">
-
-<div>
-
-```{r, echo=F}
-shiny::textInput(inputId = "rep_aut", label = "Report author", value = def_state$conf$report$author)
-shiny::textInput(inputId = "rep_tit", label = "Report title", value = def_state$conf$report$title)
-```
-
-</div>
-
-
-<div>
-
-<details><summary>Filter summary table</summary>
-
-Filter entries in the report according to the QA criteria.
-
-* **qa_pass** : entries that passed all checks
-
-* **qa_ms1_exists** : MS1 intensity is above the MS1 threshold
-
-* **qa_ms2_exists** : those entries for which some MS2 spectra have been found
-
-* **qa_ms1_above_noise** : MS1 is intense enough and above the noise level
-
-* **qa_ms2_good_int** : MS2 intensity is above the MS2 threshold
-
-* **qa_ms2_near** : MS2 spectrum is close enough to the MS1 peak
-
-Values:
-
-* **ignore** : ignore QA criterion
-* **take the good ones** : entry passed QA
-* **take the bad ones** : entry failed QA
-
-</details>
-
-```{r, echo=F}
-
-DT::DTOutput("summ_subset")
-
-```
-</div>
-
-</div>
-
-</div>
-
-<div style="padding-left: 3em">
-
-#### Control
-<div style="display: flex;flex-flow: row wrap;">
-```{r, echo=FALSE}
-actionButton(inputId = "extract_b",
-             label = "Extract")
-```
-
-```{r, echo=FALSE}
-actionButton(inputId = "presc_b",
-             label = "Prescreen")
-```
-</div>
-
-#### Overview
-
-- Has the data been extracted? `r htmlOutput("is_extracted_stat", inline=T)`
-- Has the data been auto-quality checked? `r htmlOutput("is_qa_stat", inline=T)`
-
-##### Extraction
-
-- MS1 coarse: `r htmlOutput("ms1_coarse_stat", inline=T)`
-- MS1 fine: `r htmlOutput("ms1_fine_stat", inline=T)`
-- MS1 eic: `r htmlOutput("ms1_eic_stat", inline=T)`
-- Retention time window: `r htmlOutput("rt_stat", inline=T)`
-
-##### Prescreening
-
-- Intensity Threshold (MS1): `r htmlOutput("ms1_int_thresh_stat", inline=T)`
-- Intensity Threshold (MS2): `r htmlOutput("ms2_int_thresh_stat", inline=T)`
-- Retention time shift: `r htmlOutput("ret_time_shift_tol_stat", inline=T)`
-- Signal-to-noise ratio: `r htmlOutput("s2n_stat", inline=T)`
-
-</div>
-
-</div>
-
-## View compound Lists and Sets
-
-### Compound List
-
-```{r, echo=F}
-DT::dataTableOutput("comp_table")
-```
-
-### Setid Table
-```{r, echo=F}
-DT::dataTableOutput("setid_table")
-```
-
-## Results Explorer
-
-
-<div style="display: flex; flex-flow: column nowrap;">
-<div style="display: flex; flex-flow: column; padding-right:1.0em">
-
-### Compound Index
-
-```{r, echo=F}
-selectInput("cindex_group",label="Group",
-            choices=c(NA_character_,
-                      "adduct","tag"),
-            multiple=T,
-            selected=c("adduct","tag"))
-```
-            
-<div style="display: flex; flex-flow: row nowrap">
-```{r, echo=F}
-selectInput("sort1",label="Sort by ", choices=shinyscreen:::ARRANGE_CHOICES,width="15%",selected="quality")
-selectInput("sort2",label="then by ", choices=shinyscreen:::ARRANGE_CHOICES,width="15%",selected="mz")
-selectInput("sort3",label="then", choices=shinyscreen:::ARRANGE_CHOICES,width="15%")
-selectInput("sort4",label="and finally by", choices=shinyscreen:::ARRANGE_CHOICES,width="15%")
-```
-</div> <!-- Arrange -->
-
+<div class = "flex-cols"> <!-- confstatus-panes -->
 <div>
-```{r, echo=F}
-DT::DTOutput("cindex")
-```
-
-</div> <!-- cindex -->
-
-</div> <!-- Compound Explorer Panel -->
-
-### Viewer
-
-<div class="plot-layout"> <!-- Plot Section -->
-<div> 
-```{r, echo=F}
-plotOutput("plot_eic_ms1",
-           hover = hoverOpts(id="plot_hover",
-                             delayType = "throttle",
-                             delay=100),
-           dblclick = "plot_rt_click",
-           brush = "plot_brush")
+```{r, child='app_config_and_status.Rmd'}
 ```
 </div>
 <div>
-```{r, echo=F}
-plotOutput("plot_struct")
-```
+Unimplemented
 </div>
-<div>
-```{r, echo=F}
-plotOutput("plot_eic_ms2",
-           hover = hoverOpts(id="plot_hover",
-                             delayType = "throttle",
-                             delay=100),
-           dblclick = "plot_rt_click",
-           brush = "plot_brush")
-```
-</div>
-<div> 
-
-#### Tweak Plot Parameters
-
-```{r, echo=F}
-textOutput("plot_hover_out")
-```
-
-#### Retention Time Range
-
-<div style="display:flex; flex-direction: row;"> <!-- RT div -->
-```{r, echo=F}
-numericInput(inputId = "plot_rt_min",
-             label="Start",
-             value=NA_real_,
-             width="30%")
-```
-```{r, echo=F}
-numericInput(inputId = "plot_rt_max",
-             label="End",
-             value=NA_real_,
-             width="30%")
-
-
-```
-</div> <!-- RT div -->
-
-#### Intensity Range (MS1)
-
-<div style="display:flex; flex-direction: row;"> <!-- Intensity div -->
-```{r, echo=F}
-numericInput(inputId = "plot_i_min",
-             label="Start",
-             value=NA_real_,
-             width="30%")
-```
-```{r, echo=F}
-numericInput(inputId = "plot_i_max",
-             label="End",
-             value=NA_real_,
-             width="30%")
-
-
-```
-</div> <!-- Intensity div -->
-
-#### Report
-
-<div style="display: flex-flow: row nowrap"> <!-- Control Bar -->
-```{r, echo=F}
-textInput("single_plot_fname",
-          label="Filename of the single entry plot",
-          value="default.pdf")
-actionButton("plot_save_single",
-             label="Save single entry plot")
-textInput("report_name",
-          label="Report Name",
-          value="report")
-actionButton("make_report_b",
-             label="Create report")
-textInput("summ_name",
-          label="Summary table name",
-          value="summary.csv")
-actionButton("summ_tab_b", "Save summary table")
-
-textInput("ms2_spectra_tab_name",
-          label="Table of MS2 spectra",
-          value="ms2_spectra_table.csv")
-actionButton("ms2_spectra_tab_b", "Save MS2 spectra table")
-```
-
-</div> <!-- Control Bar -->
+</div> <!-- confstatus-panes -->
 
-</div>
-<div>
-```{r, echo=F}
-plotOutput("plot_spec_ms2",
-           hover = hoverOpts(id="plot_hover",
-                             delayType = "throttle",
-                             delay=100),
-           dblclick = "plot_mz_click",
-           brush = brushOpts(id="plot_mz_brush"))
-```
-</div>
-<div></div>
-</div> <!-- Plots -->
-
-
-### Measurement Properties
-
-<div class="measure-prop-sec">
-
-<div class="sel-spec"> <!-- sel-spec -->
-
-#### Select Spectrum
-
-```{r, echo=F}
-selectInput("sel_parent_trace",label="Select parent", choices=character(),size=10L,selectize=F)
-```
-
-```{r, echo=F}
-selectInput("sel_spec",label="Select spectrum", choices=character(),size=10L,selectize=F)
-```
-
-```{r, echo=F}
-actionButton("cmt_changes_b",label="Commit changes")
-```
-
-</div> <!-- sel-spec -->
-
-<div class="measure-props"> <!-- measure-props -->
+<!-- SNIP -->
 
-#### Properties
 
-```{r,echo=F}
-numericInput(inputId="chg_ms1_rt",
-             label="Retention time (MS1)",
-             value=NA_real_)
-numericInput(inputId="chg_ms1_int",
-             label="Intensity (MS1)",
-             value=NA_real_)
-```
 
-```{r,echo=F}
-checkboxGroupInput(inputId="qabox",
-                   label="Quality Control",
-                   choices=QABOX_VALS)
-```
-```{r,echo=F}
-checkboxInput(inputId="chg_ms2sel",
-              label="MS2 Selected",
-              value=F)
-```
-</div> <!-- measure-props -->
 
-<div class="spec-tab"> <!-- spec tab -->
 
-#### Mass Spectrum
 
-```{r, echo=F}
-verbatimTextOutput("print_spec_tab")
-```
-
-</div> <!-- spec tab -->
 
-</div> <!-- measure-prop-sec -->
 
 <!-- ENGINE -->
 
@@ -835,3 +368,4 @@ shinyscreen_server <- shinyscreen:::mk_shinyscreen_server(projects=projects,
 ```{r, echo = F, context = 'server'}
 shinyscreen_server(input=input,output=output,session=session)
 ```
+
diff --git a/inst/rmd/app.snip.rmd b/inst/rmd/app.snip.rmd
new file mode 100644
index 0000000000000000000000000000000000000000..04201d602e1634eb9082f92cdc090d6c972206cc
--- /dev/null
+++ b/inst/rmd/app.snip.rmd
@@ -0,0 +1,323 @@
+
+### Report
+
+<details><summary>Create a report</summary>
+
+Shinyscreen can produce a report containing graps of EICs and spectra
+for some or all compounds. The controls below define what enters the
+report. Please keep in mind that producing a PDF output with thousands
+of compounds will take huge amount of time, so if you are prescreening
+a lot of compounds, consider restricting limiting the output to, for
+example, those entries that have passed the quality checks.
+
+</details>
+
+
+<div style= "display: flex; vertical-align:top; padding-right: 0.5em">
+
+<div>
+
+```{r, echo=F}
+shiny::textInput(inputId = "rep_aut", label = "Report author", value = def_state$conf$report$author)
+shiny::textInput(inputId = "rep_tit", label = "Report title", value = def_state$conf$report$title)
+```
+
+</div>
+
+
+<div>
+
+<details><summary>Filter summary table</summary>
+
+Filter entries in the report according to the QA criteria.
+
+* **qa_pass** : entries that passed all checks
+
+* **qa_ms1_exists** : MS1 intensity is above the MS1 threshold
+
+* **qa_ms2_exists** : those entries for which some MS2 spectra have been found
+
+* **qa_ms1_above_noise** : MS1 is intense enough and above the noise level
+
+* **qa_ms2_good_int** : MS2 intensity is above the MS2 threshold
+
+* **qa_ms2_near** : MS2 spectrum is close enough to the MS1 peak
+
+Values:
+
+* **ignore** : ignore QA criterion
+* **take the good ones** : entry passed QA
+* **take the bad ones** : entry failed QA
+
+</details>
+
+```{r, echo=F}
+
+DT::DTOutput("summ_subset")
+
+```
+</div>
+
+</div>
+
+</div>
+
+<div style="padding-left: 3em">
+
+#### Control
+<div style="display: flex;flex-flow: row wrap;">
+```{r, echo=FALSE}
+actionButton(inputId = "extract_b",
+             label = "Extract")
+```
+
+```{r, echo=FALSE}
+actionButton(inputId = "presc_b",
+             label = "Prescreen")
+```
+</div>
+
+#### Overview
+
+- Has the data been extracted? `r htmlOutput("is_extracted_stat", inline=T)`
+- Has the data been auto-quality checked? `r htmlOutput("is_qa_stat", inline=T)`
+
+##### Extraction
+
+- MS1 coarse: `r htmlOutput("ms1_coarse_stat", inline=T)`
+- MS1 fine: `r htmlOutput("ms1_fine_stat", inline=T)`
+- MS1 eic: `r htmlOutput("ms1_eic_stat", inline=T)`
+- Retention time window: `r htmlOutput("rt_stat", inline=T)`
+
+##### Prescreening
+
+- Intensity Threshold (MS1): `r htmlOutput("ms1_int_thresh_stat", inline=T)`
+- Intensity Threshold (MS2): `r htmlOutput("ms2_int_thresh_stat", inline=T)`
+- Retention time shift: `r htmlOutput("ret_time_shift_tol_stat", inline=T)`
+- Signal-to-noise ratio: `r htmlOutput("s2n_stat", inline=T)`
+
+</div>
+
+</div>
+
+## View compound Lists and Sets
+
+### Compound List
+
+```{r, echo=F}
+DT::dataTableOutput("comp_table")
+```
+
+### Setid Table
+```{r, echo=F}
+DT::dataTableOutput("setid_table")
+```
+
+## Results Explorer
+
+
+<div style="display: flex; flex-flow: column nowrap;">
+<div style="display: flex; flex-flow: column; padding-right:1.0em">
+
+### Compound Index
+
+```{r, echo=F}
+selectInput("cindex_group",label="Group",
+            choices=c(NA_character_,
+                      "adduct","tag"),
+            multiple=T,
+            selected=c("adduct","tag"))
+```
+            
+<div style="display: flex; flex-flow: row nowrap">
+```{r, echo=F}
+selectInput("sort1",label="Sort by ", choices=shinyscreen:::ARRANGE_CHOICES,width="15%",selected="quality")
+selectInput("sort2",label="then by ", choices=shinyscreen:::ARRANGE_CHOICES,width="15%",selected="mz")
+selectInput("sort3",label="then", choices=shinyscreen:::ARRANGE_CHOICES,width="15%")
+selectInput("sort4",label="and finally by", choices=shinyscreen:::ARRANGE_CHOICES,width="15%")
+```
+</div> <!-- Arrange -->
+
+<div>
+```{r, echo=F}
+DT::DTOutput("cindex")
+```
+
+</div> <!-- cindex -->
+
+</div> <!-- Compound Explorer Panel -->
+
+### Viewer
+
+<div class="plot-layout"> <!-- Plot Section -->
+<div> 
+```{r, echo=F}
+plotOutput("plot_eic_ms1",
+           hover = hoverOpts(id="plot_hover",
+                             delayType = "throttle",
+                             delay=100),
+           dblclick = "plot_rt_click",
+           brush = "plot_brush")
+```
+</div>
+<div>
+```{r, echo=F}
+plotOutput("plot_struct")
+```
+</div>
+<div>
+```{r, echo=F}
+plotOutput("plot_eic_ms2",
+           hover = hoverOpts(id="plot_hover",
+                             delayType = "throttle",
+                             delay=100),
+           dblclick = "plot_rt_click",
+           brush = "plot_brush")
+```
+</div>
+<div> 
+
+#### Tweak Plot Parameters
+
+```{r, echo=F}
+textOutput("plot_hover_out")
+```
+
+#### Retention Time Range
+
+<div style="display:flex; flex-direction: row;"> <!-- RT div -->
+```{r, echo=F}
+numericInput(inputId = "plot_rt_min",
+             label="Start",
+             value=NA_real_,
+             width="30%")
+```
+```{r, echo=F}
+numericInput(inputId = "plot_rt_max",
+             label="End",
+             value=NA_real_,
+             width="30%")
+
+
+```
+</div> <!-- RT div -->
+
+#### Intensity Range (MS1)
+
+<div style="display:flex; flex-direction: row;"> <!-- Intensity div -->
+```{r, echo=F}
+numericInput(inputId = "plot_i_min",
+             label="Start",
+             value=NA_real_,
+             width="30%")
+```
+```{r, echo=F}
+numericInput(inputId = "plot_i_max",
+             label="End",
+             value=NA_real_,
+             width="30%")
+
+
+```
+</div> <!-- Intensity div -->
+
+#### Report
+
+<div style="display: flex-flow: row nowrap"> <!-- Control Bar -->
+```{r, echo=F}
+textInput("single_plot_fname",
+          label="Filename of the single entry plot",
+          value="default.pdf")
+actionButton("plot_save_single",
+             label="Save single entry plot")
+textInput("report_name",
+          label="Report Name",
+          value="report")
+actionButton("make_report_b",
+             label="Create report")
+textInput("summ_name",
+          label="Summary table name",
+          value="summary.csv")
+actionButton("summ_tab_b", "Save summary table")
+
+textInput("ms2_spectra_tab_name",
+          label="Table of MS2 spectra",
+          value="ms2_spectra_table.csv")
+actionButton("ms2_spectra_tab_b", "Save MS2 spectra table")
+```
+
+</div> <!-- Control Bar -->
+
+</div>
+<div>
+```{r, echo=F}
+plotOutput("plot_spec_ms2",
+           hover = hoverOpts(id="plot_hover",
+                             delayType = "throttle",
+                             delay=100),
+           dblclick = "plot_mz_click",
+           brush = brushOpts(id="plot_mz_brush"))
+```
+</div>
+<div></div>
+</div> <!-- Plots -->
+
+
+### Measurement Properties
+
+<div class="measure-prop-sec">
+
+<div class="sel-spec"> <!-- sel-spec -->
+
+#### Select Spectrum
+
+```{r, echo=F}
+selectInput("sel_parent_trace",label="Select parent", choices=character(),size=10L,selectize=F)
+```
+
+```{r, echo=F}
+selectInput("sel_spec",label="Select spectrum", choices=character(),size=10L,selectize=F)
+```
+
+```{r, echo=F}
+actionButton("cmt_changes_b",label="Commit changes")
+```
+
+</div> <!-- sel-spec -->
+
+<div class="measure-props"> <!-- measure-props -->
+
+#### Properties
+
+```{r,echo=F}
+numericInput(inputId="chg_ms1_rt",
+             label="Retention time (MS1)",
+             value=NA_real_)
+numericInput(inputId="chg_ms1_int",
+             label="Intensity (MS1)",
+             value=NA_real_)
+```
+
+```{r,echo=F}
+checkboxGroupInput(inputId="qabox",
+                   label="Quality Control",
+                   choices=QABOX_VALS)
+```
+```{r,echo=F}
+checkboxInput(inputId="chg_ms2sel",
+              label="MS2 Selected",
+              value=F)
+```
+</div> <!-- measure-props -->
+
+<div class="spec-tab"> <!-- spec tab -->
+
+#### Mass Spectrum
+
+```{r, echo=F}
+verbatimTextOutput("print_spec_tab")
+```
+
+</div> <!-- spec tab -->
+
+</div> <!-- measure-prop-sec -->
diff --git a/inst/www/custom.css b/inst/www/custom.css
index b2c4d5df6d876fe57be9640e19b886dd4b8c03b7..86c38b57deed50f1d425bf111755b3e1e1826ad3 100644
--- a/inst/www/custom.css
+++ b/inst/www/custom.css
@@ -61,3 +61,9 @@
 }
 
 /* test comment */
+
+.flex-cols {
+  display: flex;
+  flex-direction: row nowrap;
+  column-gap: 1rem;
+}
diff --git a/man/app.Rd b/man/app.Rd
index d4ba1d3bbc1579368b5ae046a973748ad1ca9609..a8967036119890a602e80afeee3afa7889f10dcb 100644
--- a/man/app.Rd
+++ b/man/app.Rd
@@ -7,8 +7,6 @@
 app(
   projects = getwd(),
   top_data_dir = getwd(),
-  metfrag_db_dir = "",
-  metfrag_runtime = "",
   shiny_args = list(launch.browser = F),
   render_args = NULL
 )
@@ -20,17 +18,17 @@ containing project directories.}
 \item{top_data_dir}{\code{character(1)}, a location on the server side
 containing data directories.}
 
-\item{metfrag_db_dir}{\code{character(1)}, a location on the server side
-containing MetFrag databases.}
-
-\item{metfrag_runtime}{\code{character(1)}, a location on the server side
-of the MetFrag jar file.}
-
 \item{shiny_args}{\code{list}, optional list of arguments conveyed to
 \code{rmarkdown::run} \code{shiny_args} argument.}
 
 \item{render_args}{\code{list}, optional list of arguments conveyed to
 \code{rmarkdown::run} \code{render_args} argument.}
+
+\item{metfrag_db_dir}{\code{character(1)}, a location on the server side
+containing MetFrag databases.}
+
+\item{metfrag_runtime}{\code{character(1)}, a location on the server side
+of the MetFrag jar file.}
 }
 \value{
 Nada.
diff --git a/man/envopts.Rd b/man/envopts.Rd
index 027d62742a017148674115774c3b71ca8be84fac..91650421453ff49ca5ae7e9b8a6544ee16dc759c 100644
--- a/man/envopts.Rd
+++ b/man/envopts.Rd
@@ -4,7 +4,7 @@
 \alias{envopts}
 \title{Create a \code{envopts} Object}
 \usage{
-envopts(metfrag_db_dir = "", metfrag_jar = "")
+envopts(metfrag_db_dir = "", metfrag_jar = "", java_bin = Sys.which("java"))
 }
 \arguments{
 \item{metfrag_db_dir}{\code{character(1)}, a path to the directory which contains MetFrag databases}