diff --git a/DESCRIPTION b/DESCRIPTION
index ae08e5e7501c3dbd9245444e16996c4fbcec7599..91db8f950b0db57f1591386590c522e3032fea1a 100755
--- a/DESCRIPTION
+++ b/DESCRIPTION
@@ -45,3 +45,4 @@ Collate:
     'validateMassBank.R'
     'zzz.R'
     'tools.R'
+    'msmsRead.R'
diff --git a/NAMESPACE b/NAMESPACE
index c42d2ea5de520cc98a04e0b6d8e9a31183bfd163..a278b382d15c37458409d28642a957cfccc2351c 100755
--- a/NAMESPACE
+++ b/NAMESPACE
@@ -61,6 +61,7 @@ export(loadRmbSettingsFromEnv)
 export(makeMollist)
 export(makeRecalibration)
 export(mbWorkflow)
+export(msmsRead)
 export(msmsWorkflow)
 export(multiply.formula)
 export(newMbWorkspace)
@@ -89,6 +90,7 @@ export(smiles2mass)
 export(to.limits.rcdk)
 export(toMassbank)
 export(toRMB)
+export(updateSettings)
 export(validate)
 exportClasses(mbWorkspace)
 exportClasses(msmsWorkspace)
diff --git a/R/createMassBank.R b/R/createMassBank.R
index 13a3e61cb56f84215d760b7924422abbf37853e4..392e77dc7b0ef3b5bd8a09444bf489a273c62f2c 100755
--- a/R/createMassBank.R
+++ b/R/createMassBank.R
@@ -823,6 +823,8 @@ gatherCompound <- function(spec, refiltered, additionalPeaks = NULL)
   return(allSpectra)
 }
 
+
+
 # Process one single MSMS child scan.
 # spec: an object of "analyzedSpectrum" type (i.e. contains 
 #       14x (or other number) msmsdata, info, mzrange,
diff --git a/R/leMsMs.r b/R/leMsMs.r
index 11a9b1e2b3732635f26e3376d22116678ef05159..e7f74ec08a06cd944577b4002f4eddbb60f2609c 100755
--- a/R/leMsMs.r
+++ b/R/leMsMs.r
@@ -465,6 +465,15 @@ analyzeMsMs.formula <- function(msmsPeaks, mode="pH", detail=FALSE, run="prelimi
   parentSpectrum <- msmsPeaks$parentPeak
 
 
+  # Check whether the spectra can be fitted to the spectra list correctly!
+  if(nrow(msmsPeaks$childHeaders) != length(spectraList))
+  {
+    warning(paste0(
+            "The spectra count of the substance ", msmsPeaks$id, " (", nrow(msmsPeaks$childHeaders), " spectra) doesn't match the provided spectra list (", length(spectraList), " spectra)."
+                ))
+    return(list(specOK=FALSE))
+    
+  }
   
   # On each spectrum the following function analyzeTandemShot will be applied.
   # It takes the raw peaks matrix as argument (mz, int) and processes the spectrum by
diff --git a/R/msmsRead.R b/R/msmsRead.R
index 6f8472343c7e7cdf6ac7ae51ca5ceebbbe10188e..b8fa20562173299ae2924a513a3dd8bd928a1fe2 100644
--- a/R/msmsRead.R
+++ b/R/msmsRead.R
@@ -7,7 +7,7 @@
 #' See the vignette \code{vignette("RMassBank")} for further details about the
 #' workflow.
 #' 
-#' @usage msmsWorkflow(w, filetable = NULL, files = NULL, cpdids = NULL, 
+#' @usage msmsRead(w, filetable = NULL, files = NULL, cpdids = NULL, 
 #'					readMethod, mode, confirmMode = FALSE, useRtLimit = TRUE, 
 #'					Args, settings = getOption("RMassBank"), progressbar = "progressBarHook")
 #' @param w A \code{msmsWorkspace} to work with.
@@ -38,7 +38,7 @@
 #' 			Cf. the documentation of \code{\link{progressBarHook}} for usage.
 #' @return The \code{msmsWorkspace} with msms-spectra read.
 #' @seealso \code{\link{msmsWorkspace-class}}, \code{\link{msmsWorkflow}}
-#' @author Michael Stravs, Eawag <michael.stravs@eawag.ch>
+#' @author Michael Stravs, Eawag <michael.stravs@@eawag.ch>
 #' @author Erik Mueller, UFZ
 #' @export
 msmsRead <- function(w, filetable = NULL, files = NULL, cpdids = NULL, 
@@ -139,23 +139,4 @@ msmsRead <- function(w, filetable = NULL, files = NULL, cpdids = NULL,
 			   
 			   
 			   
-			   
-			   
-			   
-			   
-			   
-			   
-#####SCRIPT
-library(RMassBank)
-loadRmbSettings("settings_comrecal_QEx_EX.INI")
-loadList("QEx_10_compoundlist.csv")
-msmsmzR <- newMsmsWorkspace()
-msmsXCMS <- newMsmsWorkspace()
-Args <- list(method="centWave", ppm = 5, snthresh = 1.5,
-                  peakwidth = c(20,60), integrate = 1, mzdiff = -0.001, mzCenterFun = "meanApex3")
-msmsmzR <- msmsRead(msmsmzR, filetable = "Filelist_QEx.csv", readMethod="mzR", mode="pH", Args=Args)
-
-datadir <- "/vol/data_extern/emma.schymanski@ufz.de/Qexactive/10_centroided_mzMLs"
-files <- list.files(datadir, pattern=".mzML", full.names=TRUE)
-cpdid <- c(3035,2845,3040,3041,139,3046,297,3050,2856,3052)
-msmsXCMS <- msmsRead(msmsXCMS, files=files, cpdids = cpdid, readMethod="xcms",mode="pH",Args=Args)
+			   
\ No newline at end of file
diff --git a/R/settings_example.R b/R/settings_example.R
index 65e05904a19aadb988d21d78c04508614a6e37f5..25aabfccf9f877cf3a0e79dfa14798bb5024f349 100755
--- a/R/settings_example.R
+++ b/R/settings_example.R
@@ -353,8 +353,9 @@ loadRmbSettings <- function(file_or_list)
 	}
 	else if (isR)
 	{
-		o <- source(file_or_list)
-		options(RMassBank = o$value)
+		ov <- source(file_or_list)
+    o <- ov$value
+		options(RMassBank = o)
 	}
 	else
 		stop("Options format not recognized. Use YAML (.ini, .yml) or R file (.R) format.")
@@ -362,6 +363,18 @@ loadRmbSettings <- function(file_or_list)
   }
   else
     stop("Options incorrectly specified.")
+  
+  # Settings are loaded, now check if they are up to date
+  o <- getOption("RMassBank")
+  curr <- names(.settingsList)
+  problem <- length(setdiff(curr, names(o))) > 0
+  # Hesch es problem? He?
+  if(problem)
+  {
+    warning("Your settings are outdated. Missing will be replaced by default values.")
+    o <- updateSettings(o)
+    options(RMassBank = o)
+  }
 }
 
 #' @export
diff --git a/R/tools.R b/R/tools.R
index 57176b599cc64d6c80a61c3caef434250cf9867d..d3bad6d7afde6a6e14fd3fbe5933a2889e1a6bc0 100644
--- a/R/tools.R
+++ b/R/tools.R
@@ -84,3 +84,45 @@ findProgress <- function(workspace)
     steps <- which(c(step1, step2, step3, step4, step5, step6, step7, step8))
     return(steps)
 }
+
+#' Update settings to current version
+#'
+#' Checks if all necessary fields are present in the current settings
+#' and fills in default values from the \code{\link{RmbDefaultSettings}}
+#' if required.
+#' 
+#' @note Important: There is a change in behaviour of RMassBank in certain cases when \code{filterSettings} is not
+#' present in the old settings! The default pre-recalibration cutoff from \code{\link{RmbDefaultSettings}} is 10000.
+#' Formerly the pre-recalibration cutoff was set to be 10000 for positive spectra but 0 for negative spectra.
+#' 
+#' Updating the settings files is preferred to using the \code{updateSettings} function.
+#' 
+#' @param settings The set of settings to check and update.
+#' 
+#' @param warn Whether to update parameters quietly (\code{FALSE}) or to notify the user
+#' 	of the changed parameters (\code{TRUE}, default.) This serves to make the user aware that
+#' standard parameters are filled in!
+#' 
+#' @return The updated set of settings.
+#' 
+#' @examples \dontrun{
+#' w@@settings <- updateSettings(w@@settings)
+#' }
+#' 
+#' @author Stravs MA, Eawag <michael.stravs@@eawag.ch>
+#' @export
+#' 
+updateSettings <- function(settings, warn=TRUE)
+{
+  settings.new <- .settingsList
+  settings.old <- settings
+  renew <- setdiff(names(settings.new), names(settings.old))
+  if(length(renew) > 0 && warn==TRUE){
+    warning(paste0("Your settings are outdated! The following fields were taken from default values: ", 
+            paste(renew,collapse=", ")))
+    if("filterSettings" %in% renew)
+      warning("The default values of filterSettings could change the processing behaviour if you have negative-mode spectra. Check ?updateSettings for details.")
+  }
+  settings.old[renew] <- settings.new[renew]
+  return(settings.old)
+}
diff --git a/man/addPeaksManually.Rd b/man/addPeaksManually.Rd
index 7160d274d439fca980e3d33e57a509b64f0bec5b..1491c8b36e45ea1cfd0c9510cbdacb4f8cd6c53d 100644
--- a/man/addPeaksManually.Rd
+++ b/man/addPeaksManually.Rd
@@ -25,9 +25,8 @@
 }
 \examples{
 \dontrun{
-		handSpec <- matrix(0,4,2)
-		handSpec[,1] <- c(274.986685367956, 259.012401087427, 95.9493025990907, 96.9573002472772)
-		handSpec[,2] <- c(357,761, 2821, 3446)
+		handSpec <- cbind(mz=c(274.986685367956, 259.012401087427, 95.9493025990907, 96.9573002472772),
+                               intensity=c(357,761, 2821, 3446))
 		addPeaksManually(w, cpdID, handSpec)
 }
 }
diff --git a/man/findEIC.Rd b/man/findEIC.Rd
index 88f3e76eeb7acc7c9d674c677496281538f3a36a..e28dc1790e9c23784f416bfccc511a78c1100f37 100755
--- a/man/findEIC.Rd
+++ b/man/findEIC.Rd
@@ -3,7 +3,7 @@
 \title{Extract EICs}
 \usage{
   findEIC(msRaw, mz, limit = NULL, rtLimit = NA,
-    headerCache = NA)
+    headerCache = NULL)
 }
 \arguments{
   \item{msRaw}{The mzR file handle}
diff --git a/man/msmsRead.Rd b/man/msmsRead.Rd
new file mode 100644
index 0000000000000000000000000000000000000000..c68bfa232e5428dad46d7a3d19a7494f37c63fff
--- /dev/null
+++ b/man/msmsRead.Rd
@@ -0,0 +1,81 @@
+\name{msmsRead}
+\alias{msmsRead}
+\title{Extracts and processes spectra from a specified file list, according to
+loaded options and given parameters.}
+\usage{
+  msmsRead(w, filetable = NULL, files = NULL, cpdids =
+    NULL, readMethod, mode, confirmMode = FALSE, useRtLimit
+    = TRUE, Args, settings = getOption("RMassBank"),
+    progressbar = "progressBarHook")
+}
+\arguments{
+  \item{w}{A \code{msmsWorkspace} to work with.}
+
+  \item{filetable}{The path to a .csv-file that contains
+  the columns "files" and "cpdid" supplying the
+  relationships between files and compound IDs. Either this
+  or "files" need to be specified.}
+
+  \item{files}{A vector or list containing the filenames of
+  the files that are to be read as spectra.  For the IDs to
+  be inferred from the filenames alone, there need to be
+  exactly 2 underscores.}
+
+  \item{cpdids}{A vector or list containing the compound
+  IDs of the files that are to be read as spectra.  The
+  ordering of this and \code{files} implicitly assigns each
+  ID to the corresponding file.  If this is supplied, then
+  the IDs implicitly named in the filenames are ignored.}
+
+  \item{readMethod}{Several methods are available to get
+  peak lists from the files.  Currently supported are
+  "mzR", "xcms", "MassBank" and "peaklist".  The first two
+  read MS/MS raw data, and differ in the strategy used to
+  extract peaks. MassBank will read existing records, so
+  that e.g. a recalibration can be performed, and
+  "peaklist" just requires a CSV with two columns and the
+  column header "mz", "int".}
+
+  \item{mode}{\code{"pH", "pNa", "pM", "mH", "mM", "mFA"}
+  for different ions ([M+H]+, [M+Na]+, [M]+, [M-H]-, [M]-,
+  [M+FA]-).}
+
+  \item{confirmMode}{Defaults to false (use most intense
+  precursor). Value 1 uses the 2nd-most intense precursor
+  for a chosen ion (and its data-dependent scans) , etc.}
+
+  \item{useRtLimit}{Whether to enforce the given retention
+  time window.}
+
+  \item{Args}{A list of arguments that will be handed to
+  the xcms-method findPeaks via do.call}
+
+  \item{settings}{Options to be used for processing.
+  Defaults to the options loaded via
+  \code{\link{loadRmbSettings}} et al. Refer to there for
+  specific settings.}
+
+  \item{progressbar}{The progress bar callback to use. Only
+  needed for specialized applications.  Cf. the
+  documentation of \code{\link{progressBarHook}} for
+  usage.}
+}
+\value{
+  The \code{msmsWorkspace} with msms-spectra read.
+}
+\description{
+  The filenames of the raw LC-MS runs are read from the
+  array \code{files} in the global enviroment. See the
+  vignette \code{vignette("RMassBank")} for further details
+  about the workflow.
+}
+\author{
+  Michael Stravs, Eawag <michael.stravs@eawag.ch>
+
+  Erik Mueller, UFZ
+}
+\seealso{
+  \code{\link{msmsWorkspace-class}},
+  \code{\link{msmsWorkflow}}
+}
+
diff --git a/man/updateSettings.Rd b/man/updateSettings.Rd
new file mode 100644
index 0000000000000000000000000000000000000000..3d9b81541ec2a0ae6a41d033ac469c48f9fdea53
--- /dev/null
+++ b/man/updateSettings.Rd
@@ -0,0 +1,41 @@
+\name{updateSettings}
+\alias{updateSettings}
+\title{Update settings to current version}
+\usage{
+  updateSettings(settings, warn = TRUE)
+}
+\arguments{
+  \item{settings}{The set of settings to check and update.}
+
+  \item{warn}{Whether to update parameters quietly
+  (\code{FALSE}) or to notify the user of the changed
+  parameters (\code{TRUE}, default.) This serves to make
+  the user aware that standard parameters are filled in!}
+}
+\value{
+  The updated set of settings.
+}
+\description{
+  Checks if all necessary fields are present in the current
+  settings and fills in default values from the
+  \code{\link{RmbDefaultSettings}} if required.
+}
+\note{
+  Important: There is a change in behaviour of RMassBank in
+  certain cases when \code{filterSettings} is not present
+  in the old settings! The default pre-recalibration cutoff
+  from \code{\link{RmbDefaultSettings}} is 10000. Formerly
+  the pre-recalibration cutoff was hardcoded to be 10000
+  for positive spectra but 0 for negative spectra! Updating
+  the settings files is preferred to using the
+  \code{updateSettings} function.
+}
+\examples{
+\dontrun{
+w@settings <- updateSettings(w@settings)
+}
+}
+\author{
+  Stravs MA, Eawag <michael.stravs@eawag.ch>
+}
+
diff --git a/vignettes/RMassBank.Rnw b/vignettes/RMassBank.Rnw
index 8fe8cfb645cdddb73942ce07211aaef58226c4b2..e686da94ff1a8bd52d0994d9102f6478dd43baee 100755
--- a/vignettes/RMassBank.Rnw
+++ b/vignettes/RMassBank.Rnw
@@ -282,6 +282,29 @@ First, create a workspace for the \Rvar{msmsWorkflow}:
 w <- newMsmsWorkspace()
 @
 
+
+
+Temporary deposit for the script using msmsRead. Build into actual vignette!
+<<eval=FALSE>>=
+
+#####SCRIPT
+library(RMassBank)
+loadRmbSettings("settings_comrecal_QEx_EX.INI")
+loadList("QEx_10_compoundlist.csv")
+msmsmzR <- newMsmsWorkspace()
+msmsXCMS <- newMsmsWorkspace()
+Args <- list(method="centWave", ppm = 5, snthresh = 1.5,
+    peakwidth = c(20,60), integrate = 1, mzdiff = -0.001, mzCenterFun = "meanApex3")
+msmsmzR <- msmsRead(msmsmzR, filetable = "Filelist_QEx.csv", readMethod="mzR", mode="pH", Args=Args)
+
+datadir <- "/vol/data_extern/emma.schymanski@ufz.de/Qexactive/10_centroided_mzMLs"
+files <- list.files(datadir, pattern=".mzML", full.names=TRUE)
+cpdid <- c(3035,2845,3040,3041,139,3046,297,3050,2856,3052)
+msmsXCMS <- msmsRead(msmsXCMS, files=files, cpdids = cpdid, readMethod="xcms",mode="pH",Args=Args)
+@
+
+
+
 The full paths of the files must be loaded into the container in the array
 \Rvar{files}: