Repository 'nmr_preprocessing'
hg clone https://toolshed.g2.bx.psu.edu/repos/marie-tremblay-metatoul/nmr_preprocessing

Changeset 1:cbea5e9fd0b4 (2017-05-23)
Previous changeset 0:68e2d63bece0 (2017-05-05) Next changeset 2:5e64657b4fe5 (2018-03-28)
Commit message:
Uploaded
modified:
nmr_preprocessing/NmrPreprocessing_script.R
nmr_preprocessing/NmrPreprocessing_wrapper.R
nmr_preprocessing/NmrPreprocessing_xml.xml
b
diff -r 68e2d63bece0 -r cbea5e9fd0b4 nmr_preprocessing/NmrPreprocessing_script.R
--- a/nmr_preprocessing/NmrPreprocessing_script.R Fri May 05 07:13:02 2017 -0400
+++ b/nmr_preprocessing/NmrPreprocessing_script.R Tue May 23 03:32:51 2017 -0400
[
b'@@ -550,7 +550,7 @@\n # InternalReferencing       \n ## ====================================================\n \n-InternalReferencing <- function(RawSpect_data, RawSpect_info, method = c("max", "thres"), \n+InternalReferencing <- function(Spectrum_data, Fid_info, method = c("max", "thres"), \n                                 range = c("near0", "all", "window"), ppm.ref = 0, \n                                 shiftHandling = c("zerofilling", "cut", "NAfilling", \n                                                   "circular"), c = 2, pc = 0.02, fromto.RC = NULL,\n@@ -560,9 +560,9 @@\n   \n   # Data initialisation and checks ----------------------------------------------\n   \n-  begin_info <- beginTreatment("InternalReferencing", RawSpect_data, RawSpect_info)\n-  RawSpect_data <- begin_info[["Signal_data"]]\n-  RawSpect_info <- begin_info[["Signal_info"]]\n+  begin_info <- beginTreatment("InternalReferencing", Spectrum_data, Fid_info)\n+  Spectrum_data <- begin_info[["Signal_data"]]\n+  Fid_info <- begin_info[["Signal_info"]]\n   \n   \n   # Check input arguments\n@@ -582,9 +582,9 @@\n   if (!is.null(fromto.RC)) {\n     diff <- diff(unlist(fromto.RC))[1:length(diff(unlist(fromto.RC)))%%2 !=0]\n     for (i in 1:length(diff)) {\n-      if (diff[i] <= 0)  {\n-        stop(paste("Invalid region removal because from > to"))\n-      }\n+      if (ppm == TRUE & diff[i] >= 0)  {\n+        stop(paste("Invalid region removal because from <= to in ppm"))\n+      } else if (ppm == FALSE & diff[i] <= 0) {stop(paste("Invalid region removal because from >= to in column index"))}\n     }\n   }\n   \n@@ -627,15 +627,15 @@\n   # Apply the method (\'thres\' or \'max\') on spectra\n   # ----------------------------------------------\n   \n-  n <- nrow(RawSpect_data)\n-  m <- ncol(RawSpect_data)\n+  n <- nrow(Spectrum_data)\n+  m <- ncol(Spectrum_data)\n   \n   # The Sweep Width has to be the same since the column names are the same\n-  SW <- RawSpect_info[1, "SW"]  # Sweep Width in ppm (semi frequency scale in ppm)\n+  SW <- Fid_info[1, "SW"]  # Sweep Width in ppm (semi frequency scale in ppm)\n   ppmInterval <- SW/m  # FIXME divide by two ??\n   \n   if (range == "all") {\n-    Data <- RawSpect_data\n+    Data <- Spectrum_data\n   } else {\n     if (range == "near0")  {\n       fromto.RC <- list(c(-(SW * pc)/2, (SW * pc)/2))  # automatic fromto values in ppm\n@@ -644,7 +644,7 @@\n     # if ppm == TRUE, then fromto is in the colnames values, else, in the column\n     # index\n     if (ppm == TRUE)   {\n-      colindex <- as.numeric(colnames(RawSpect_data))\n+      colindex <- as.numeric(colnames(Spectrum_data))\n     } else   {\n       colindex <- 1:m\n     }\n@@ -659,9 +659,9 @@\n     vector <- rep(0, m)\n     vector[unlist(Int)] <- 1\n     if (n > 1)  {\n-      Data <- sweep(RawSpect_data, MARGIN = 2, FUN = "*", vector)  # Cropped_Spectrum\n+      Data <- sweep(Spectrum_data, MARGIN = 2, FUN = "*", vector)  # Cropped_Spectrum\n     } else  {\n-      Data <- RawSpect_data * vector\n+      Data <- Spectrum_data * vector\n     }  # Cropped_Spectrum\n   }\n   \n@@ -701,17 +701,17 @@\n     \n     ppmScale <- ppmScale + ppm.ref\n     \n-    Spectrum_data <- matrix(fill, nrow = n, ncol =  -(end - start) + 1, \n-                            dimnames = list(rownames(RawSpect_data), ppmScale))\n+    Spectrum_data_calib <- matrix(fill, nrow = n, ncol =  -(end - start) + 1, \n+                                  dimnames = list(rownames(Spectrum_data), ppmScale))\n     for (i in 1:n)  {\n       shift <- (1 - TMSPpeaks[i]) + start\n-      Spectrum_data[i, (1 + shift):(m + shift)] <- RawSpect_data[i, ]\n+      Spectrum_data_calib[i, (1 + shift):(m + shift)] <- Spectrum_data[i, ]\n     }\n     \n     if (shiftHandling == "cut")  {\n-      Spectrum_data = as.matrix(stats::na.omit(t(Spectrum_data)))\n-      Spectrum_data = t(Spectrum_data)\n-      base::attr(Spectrum_data, "na.action") <- NULL\n+      Spectrum_data_calib = as.matrix(stats::na.omit(t(Spectrum_data_calib)))\n+      Spectrum_data_calib = t(Spectrum_data_calib)\n+      base::attr(Spectrum_data_calib,'..b'"Invalid region removal because from <= to in ppm"))\n+        } else if (ppm == FALSE & diff[i] <= 0) {stop(paste("Invalid region removal because from >= to in column index"))}\n       }\n       \n-      Int <- vector("list", length(fromto.0OPC))\n-      for (i in 1:length(fromto.0OPC))  {\n-        Int[[i]] <- indexInterval(colindex, from = fromto.0OPC[[i]][1], \n-                                  to = fromto.0OPC[[i]][2], inclusive = TRUE)\n+      \n+      Int <- vector("list", length(exclude))\n+      for (i in 1:length(exclude))  {\n+        Int[[i]] <- indexInterval(colindex, from = exclude[[i]][1], \n+                                  to = exclude[[i]][2], inclusive = TRUE)\n       }\n       \n-      vector <- rep(0, m)\n-      vector[unlist(Int)] <- 1\n+      vector <- rep(1, m)\n+      vector[unlist(Int)] <- 0\n       if (n > 1)  {\n         Data <- sweep(Spectrum_data, MARGIN = 2, FUN = "*", vector)  # Cropped_Spectrum\n       } else   {\n@@ -953,8 +940,8 @@\n       # work in either [-pi;pi] or [0;2pi] (this is not easy to be convinced by that I\n       # agree) and we can check which one it is simply by the following trick\n       \n-      f0 <- rms(0, Data[k, ], p = quant, meth = method)\n-      fpi <- rms(pi, Data[k, ], p = quant, meth = method)\n+      f0 <- rms(0, Data[k, ],meth = method)\n+      fpi <- rms(pi, Data[k, ], meth = method)\n       if (f0 < fpi) {\n         interval <- c(-pi, pi)\n       } else {\n@@ -967,7 +954,7 @@\n         x <- seq(min(interval), max(interval), length.out = 100)\n         y <- rep(1, 100)\n         for (K in (1:100))   {\n-          y[K] <- rms(x[K], Data[k, ], p = quant, meth = method)\n+          y[K] <- rms(x[K], Data[k, ],  meth = method)\n         }\n         if (createWindow == TRUE)  {\n           grDevices::dev.new(noRStudioGD = FALSE)\n@@ -978,7 +965,7 @@\n       \n       # Best angle\n       best <- stats::optimize(rms, interval = interval, maximum = TRUE, \n-                              y = Data[k,], p = quant, meth = method)\n+                              y = Data[k,],  meth = method)\n       ang <- best[["maximum"]]\n       \n       \n@@ -1011,32 +998,12 @@\n       stop(paste("angle has length", length(angle), "and there are", n, "spectra to rotate."))\n     }\n     for (k in 1:n)  {\n-      Spectrum_data[k, ] <- Spectrum_data[k, ] * exp(complex(real = 0, imaginary = ang))\n+      Spectrum_data[k, ] <- Spectrum_data[k, ] * exp(complex(real = 0, imaginary = - angle[k]))\n     }\n   }\n   \n   \n   \n-  # #================== Detect a 180\xc2\xb0 rotation due to the water signal MEAN_Q = c()\n-  # for (i in 1:nrow(Spectrum_data)) { data = Re(Spectrum_data[i,]) data_p =\n-  # data[data >= stats::quantile(data[data >=0 ], p.zo)] data_n = data[data <=\n-  # stats::quantile(data[data <0 ], (1-p.zo))] mean_quant = (sum(data_p) +\n-  # sum(data_n)) / (length(data_p) +length(data_n)) # mean(p.zo% higher pos and neg\n-  # values) MEAN_Q = c(MEAN_Q, mean_quant) } vect = which(MEAN_Q < 0) if\n-  # (length(vect)!=0) { warning(\'The mean of\', p.zo,\' positive and negative\n-  # quantiles is negative for \', paste0(rownames(Spectrum_data)[vect],\'; \'))\n-  # if(rotation == TRUE) { warning(\' An automatic 180 degree rotation is applied to\n-  # these spectra\') Angle[vect] = Angle[vect] + pi } } vect_risk =\n-  # which(MEAN_Q<0.1*mean(MEAN_Q[MEAN_Q>0])) # is there any MEAN_Q with a very low\n-  # value copared to mean of positive mean values?  if (length(vect_risk)!=0)\n-  # { warning(\'the rotation angle for spectra\',\n-  # paste0(rownames(Spectrum_data)[vect_risk],\'; \'), \'might not be optimal, you\n-  # need to check visually for those spectra\') } # result of automatic rotation for\n-  # (k in vect_risk) { Spectrum_data[k,] <- Spectrum_data[k,] * exp(complex(real=0,\n-  # imaginary=Angle[k])) } #==================\n-  \n-  \n-  \n   #  Draw spectra\n   if (plot_spectra == TRUE) {\n     nn <- ceiling(n/4)\n@@ -1070,6 +1037,7 @@\n }\n \n \n+\n ## ====================================================\n # Baseline Correction   \n ## ====================================================\n'
b
diff -r 68e2d63bece0 -r cbea5e9fd0b4 nmr_preprocessing/NmrPreprocessing_wrapper.R
--- a/nmr_preprocessing/NmrPreprocessing_wrapper.R Fri May 05 07:13:02 2017 -0400
+++ b/nmr_preprocessing/NmrPreprocessing_wrapper.R Tue May 23 03:32:51 2017 -0400
[
b'@@ -70,11 +70,22 @@\n ##======================================================\n ##======================================================\n \n+# graphical inputs\n+FirstOPCGraph <- argLs[["FirstOPCGraph"]]\n+SSGraph <- argLs[["SSGraph"]]\n+ApodGraph <- argLs[["ApodGraph"]]\n+FTGraph <- argLs[["FTGraph"]]\n+SRGraph <- argLs[["SRGraph"]]\n+ZeroOPCGraph <- argLs[["ZeroOPCGraph"]]\n+BCGraph <- argLs[["BCGraph"]]\n+FinalGraph <- argLs[["FinalGraph"]]\n+\n+\n # 1rst order phase correction ------------------------\n   # Inputs\n \t## Data matrix\n Fid_data0 <- read.table(argLs[["dataMatrixFid"]],header=TRUE, check.names=FALSE, sep=\'\\t\')\n-Fid_data0 <- Fid_data0[,-1]\n+# Fid_data0 <- Fid_data0[,-1]\n Fid_data0 <- as.matrix(Fid_data0)\n \n \t## Samplemetadata\n@@ -120,7 +131,7 @@\n \n # Fourier transform ----------------------------------\n   # Inputs\n-FTGraph <- argLs[["FTGraph"]]\n+\n \n # Internal referencering ----------------------------------\n   # Inputs\n@@ -138,11 +149,11 @@\n # if (shiftReferencing=="YES")\n # {\n #   \n-\tshiftReferencingMethod <- argLs[["shiftReferencingMethod"]]\n-\n-\tif (shiftReferencingMethod == "thres")\t{\n-\t\tshiftTreshold <- argLs[["shiftTreshold"]]\n-\t}\n+\t# shiftReferencingMethod <- argLs[["shiftReferencingMethod"]]\n+\t# \n+\t# if (shiftReferencingMethod == "thres")\t{\n+\t# \tshiftTreshold <- argLs[["shiftTreshold"]]\n+\t# }\n \t\n \tshiftReferencingRange <- argLs[["shiftReferencingRange"]]\n \t\n@@ -151,15 +162,18 @@\n \t}\n \t\n \tif (shiftReferencingRange == "window"){\n-\t  shiftReferencingRangeList <- NULL\n-\t\tshiftReferencingRangeLeft <- argLs[["shiftReferencingRangeLeft"]]\n-\t\tshiftReferencingRangeRight <- argLs[["shiftReferencingRangeRight"]]\n-\t\tshiftReferencingRangeList <- list(shiftReferencingRangeList,c(shiftReferencingRangeLeft,shiftReferencingRangeRight))\n+\t  shiftReferencingRangeList <- list()\n+\t  for(i in which(names(argLs)=="shiftReferencingRangeLeft")) \n+\t  {\n+  \t\tshiftReferencingRangeLeft <- argLs[[i]]\n+  \t\tshiftReferencingRangeRight <- argLs[[i+1]]\n+  \t\tshiftReferencingRangeList <- c(shiftReferencingRangeList,list(c(shiftReferencingRangeLeft,shiftReferencingRangeRight)))\n+\t  }\n \t}\n \t\n \tshiftHandling <- argLs[["shiftHandling"]]\n \t\n-\tppm_ref <-  argLs[["ppm_ref"]]\n+\n \t\n # }\n \n@@ -171,27 +185,24 @@\n createWindow = TRUE\n angle = NULL\n plot_spectra = FALSE\n-quant = 0.95\n ppm = TRUE\n-fromto.0OPC = NULL\n+exclude = NULL\n zeroOrderPhaseMethod <- argLs[["zeroOrderPhaseMethod"]]\n-if (zeroOrderPhaseMethod==\'rms\')\n-{\n-  quant <- argLs[["quant"]]\n-}\n-if (zeroOrderPhaseMethod==\'max\')\n-{\n+\t\t\t\t\t\t\t\t\t\t   \n+if (zeroOrderPhaseMethod==\'manual\'){\n   angle <- argLs[["angle"]]\n }\n \n-searchZoneZeroPhase <- argLs[["searchZoneZeroPhase.choice"]]\n-if (searchZoneZeroPhase == "YES") {\n-  searchZoneZeroPhaseList <- NULL\n-  searchZoneZeroPhaseLeft <- argLs[["shiftReferencingRangeLeft"]]\n-  searchZoneZeroPhaseRight <- argLs[["shiftReferencingRangeRight"]]\n-  searchZoneZeroPhaseList <- list(searchZoneZeroPhaseList,c(searchZoneZeroPhaseLeft,searchZoneZeroPhaseRight))\n+excludeZoneZeroPhase <- argLs[["excludeZoneZeroPhase.choice"]]\n+if (excludeZoneZeroPhase == \'YES\') {\n+  excludeZoneZeroPhaseList <- list()\n+  for(i in which(names(argLs)=="excludeZoneZeroPhase_left")) {\n+    excludeZoneZeroPhaseLeft <- argLs[[i]]\n+    excludeZoneZeroPhaseRight <- argLs[[i+1]]\n+    excludeZoneZeroPhaseList <- c(excludeZoneZeroPhaseList,list(c(excludeZoneZeroPhaseLeft,excludeZoneZeroPhaseRight)))\n   }\n-\n+  exclude <- excludeZoneZeroPhaseList\n+}\n \n \n # Baseline Correction -------------------------------\n@@ -235,20 +246,45 @@\n # FirstOrderPhaseCorrection ---------------------------------\n Fid_data <- FirstOrderPhaseCorrection(Fid_data0, Fid_info = samplemetadataFid, group_delay = NULL)\n \n+if (FirstOPCGraph == "YES") {\n+  title = "FIDs after First Order Phase Correction"\n+  DrawSignal(Fid_data, subtype = "stacked",\n+             ReImModArg = c(TRUE, FALSE, FALSE, FALSE), vertical = T, \n+             xlab = "Frequency", num.stacked = 4, \n+             main = title, createWindow=FALSE)\n+}\n \n # SolventSuppressi'..b'LSE, FALSE, FALSE), vertical = T, \n+             xlab = "Frequency", num.stacked = 4, \n+             main = title, createWindow=FALSE)\n+}\n+\n+\n # FourierTransform ---------------------------------\n Spectrum_data <- FourierTransform(Fid_data, Fid_info = samplemetadataFid, reverse.axis = TRUE)\n \n \n if (FTGraph == "YES") {\n-  title = "Fourier transformed specta"\n+  title = "Fourier transformed spectra"\n   DrawSignal(Spectrum_data, subtype = "stacked",\n              ReImModArg = c(TRUE, FALSE, FALSE, FALSE), vertical = T, \n              xlab = "Frequency", num.stacked = 4, \n@@ -257,45 +293,59 @@\n \n # InternalReferencing ---------------------------------\n # if (shiftReferencing=="YES") {\n-Spectrum_data <- InternalReferencing(Spectrum_data, samplemetadataFid, method = shiftReferencingMethod, range = shiftReferencingRange, \n+Spectrum_data <- InternalReferencing(Spectrum_data, samplemetadataFid, method = "max", range = shiftReferencingRange,\n                                      ppm.ref = 0, shiftHandling = shiftHandling,ppm = TRUE,\n-\t\t\t\t\t\t\t\t\t\t\t c = shiftTreshold, fromto.RC = shiftReferencingRangeList, pc = pctNear0)\n+\t\t\t\t\t\t\t\t\t c = shiftTreshold, fromto.RC = shiftReferencingRangeList, pc = pctNear0)\n+\n+if (SRGraph == "YES") {\n+  title = "Spectra after Shift Referencing"\n+  DrawSignal(Spectrum_data, subtype = "stacked",\n+             ReImModArg = c(TRUE, FALSE, FALSE, FALSE), vertical = T, \n+             xlab = "Frequency", num.stacked = 4, \n+             main = title, createWindow=FALSE)\n+}\n \n # }\n \n # ZeroOrderPhaseCorrection ---------------------------------\n-Spectrum_data  <- ZeroOrderPhaseCorrection(Spectrum_data, method = zeroOrderPhaseMethod, \n-                                           plot_rms = plot_rms, returnAngle = returnAngle, \n-                                           createWindow = createWindow,angle = angle, \n-                                           plot_spectra = plot_spectra, quant = quant, \n-                                           ppm = ppm, fromto.0OPC = fromto.0OPC)\n+Spectrum_data  <- ZeroOrderPhaseCorrection(Spectrum_data, method = zeroOrderPhaseMethod,\n+                                           plot_rms = plot_rms, returnAngle = returnAngle,\n+                                           createWindow = createWindow,angle = angle,\n+                                           plot_spectra = plot_spectra,\n+                                           ppm = ppm, exclude = exclude)\n \n+if (ZeroOPCGraph == "YES") {\n title = "Spectra after Zero Order Phase Correction"\n DrawSignal(Spectrum_data, subtype = "stacked",\n            ReImModArg = c(TRUE, FALSE, FALSE, FALSE), vertical = T, \n            xlab = "Frequency", num.stacked = 4, \n            main = title, createWindow=FALSE)\n+}\n \n # BaselineCorrection ---------------------------------\t\t\t\t\t\t\t\t\t \n-Spectrum_data <- BaselineCorrection(Spectrum_data, ptw.bc = TRUE, maxIter = maxIter, lambda.bc = lambdaBc, p.bc = pBc, eps = epsilon, returnBaseline = F) \n+Spectrum_data <- BaselineCorrection(Spectrum_data, ptw.bc = ptwBc, maxIter = maxIter, lambda.bc = lambdaBc, p.bc = pBc, eps = epsilon, returnBaseline = F) \n \n+if (BCGraph == "YES") {\n title = "Spectra after Baseline Correction"\n DrawSignal(Spectrum_data, subtype = "stacked",\n            ReImModArg = c(TRUE, FALSE, FALSE, FALSE), vertical = T, \n            xlab = "Frequency", num.stacked = 4, \n            main = title, createWindow=FALSE)\n+}\n+\n \n # NegativeValuesZeroing ---------------------------------\n if (NegativetoZero=="YES") {\n+  Spectrum_data <- NegativeValuesZeroing(Spectrum_data)\n+}\n \n-  Spectrum_data <- NegativeValuesZeroing(Spectrum_data)\n-\n-  title = "Spectra after Negative Values Zeroing"\n+if (FinalGraph == "YES") {\n+  title = "Final preprocessed spectra"\n   DrawSignal(Spectrum_data, subtype = "stacked",\n              ReImModArg = c(TRUE, FALSE, FALSE, FALSE), vertical = T, \n              xlab = "Frequency", num.stacked = 4, \n              main = title, createWindow=FALSE)\n-   }\n+}\n \n invisible(dev.off())\n \n'
b
diff -r 68e2d63bece0 -r cbea5e9fd0b4 nmr_preprocessing/NmrPreprocessing_xml.xml
--- a/nmr_preprocessing/NmrPreprocessing_xml.xml Fri May 05 07:13:02 2017 -0400
+++ b/nmr_preprocessing/NmrPreprocessing_xml.xml Tue May 23 03:32:51 2017 -0400
b
b'@@ -1,4 +1,4 @@\n-<tool id="NMR_Preprocessing" name="NMR_Preprocessing" version="3.0.1">\r\n+<tool id="NMR_Preprocessing" name="NMR_Preprocessing" version="3.1.0">\r\n \t<description> Preprocessing of 1D NMR spectra </description>\r\n \r\n     <stdio>\r\n@@ -10,6 +10,8 @@\n         Rscript $__tool_directory__/NmrPreprocessing_wrapper.R\r\n \r\n \t\t## First order phase correction\r\n+\t\t\t## Graphical display\r\n+\t\tFirstOPCGraph $FirstOPCGraph\r\n \t\t\t## Data matrix of FID spectra\r\n \t\tdataMatrixFid $dataMatrixFid\r\n \t\t\t## Sample metadata matrix\r\n@@ -20,9 +22,14 @@\n \t\t    ## Smoothing parameter\r\n         lambda $lambda\r\n \t\tptwSS  $ptwSS\r\n+\t\t\t## Graphical display\r\n+\t\tSSGraph $SSGraph\r\n \t\t\r\n \t\t\r\n \t\t## Apodization\r\n+\t\t\t\t## Graphical display\r\n+\t\tApodGraph $ApodGraph\r\n+\t\r\n \t    apodizationMethod $apodizationMethod.method\r\n \t\t    #if $apodizationMethod.method == "exp":\r\n \t\t\t    ## Line broadening for the exponential window\r\n@@ -54,18 +61,15 @@\n \t\t\t    gaussLB $apodizationMethod.gaussLB \r\n \t\t    #end if\r\n \t\r\n-\t\r\n \t\t## Fourier transform\r\n \t\t\t## Graphical display\r\n \t\t\tFTGraph $FTGraph\r\n \t\t\r\n \t\t\r\n \t\t## Shift referencing\r\n-\t\t\t## Method used to find the TMSP peaks in spectra\r\n-\t\t\tshiftReferencingMethod $shiftReferencingMethod.method\r\n-\t\t\t#if $shiftReferencingMethod.method == "thres":\r\n-\t\t\t\tshiftTreshold $shiftReferencingMethod.shiftTreshold\r\n-\t\t\t#end if\r\n+\t\t\t## Graphical display\r\n+\t\t\tSRGraph $SRGraph\r\n+\t\t\r\n \t\t\t## Definition of the search zone\r\n \t\t\tshiftReferencingRange $shiftReferencingRange.method\r\n \t\t\t#if $shiftReferencingRange.method == "near0":\r\n@@ -78,24 +82,27 @@\n                \t #end for\r\n \t\t\t#end if\r\n \t\t\tshiftHandling $shiftHandling\r\n+\t\t\t\r\n \t\t\r\n \t\t\r\n \t\t## Zero order phase correction\r\n-\t\tzeroOrderPhaseMethod $zeroOrderPhaseMethod.method\r\n-\t    #if $zeroOrderPhaseMethod.method == "rms":\r\n-\t\t\t    ## Line broadening for the exponential window\r\n-\t\t\t    quant $zeroOrderPhaseMethod.quant \r\n-\t\t#end if\r\n-\t\tsearchZoneZeroPhase.choice ${searchZoneZeroPhase.choice}\r\n-        #if str($searchZoneZeroPhase.choice) == "YES":\r\n-            #for $i in $searchZoneZeroPhase.conditions:\r\n-                searchZoneZeroPhase_left ${i.searchZoneZeroPhase_left}\r\n-                searchZoneZeroPhase_right ${i.searchZoneZeroPhase_right}\r\n+\t\t## Graphical display\r\n+\t\t\tZeroOPCGraph $ZeroOPCGraph\r\n+\t\t\t\r\n+\t\tzeroOrderPhaseMethod $zeroOrderPhaseMethod\r\n+\t\t\r\n+\t\texcludeZoneZeroPhase.choice ${excludeZoneZeroPhase.choice}\r\n+        #if str($excludeZoneZeroPhase.choice) == "YES":\r\n+            #for $i in $excludeZoneZeroPhase.conditions:\r\n+                excludeZoneZeroPhase_left ${i.excludeZoneZeroPhase_left}\r\n+                excludeZoneZeroPhase_right ${i.excludeZoneZeroPhase_right}\r\n             #end for\r\n         #end if\t\t\r\n \r\n \r\n \t\t## Baseline correction\r\n+\t\t## Graphical display\r\n+\t\t\tBCGraph $BCGraph\r\n \t\tptwBc $ptwBc\r\n \t\tmaxIter $maxIter\r\n \t\tlambdaBc $lambdaBc\r\n@@ -106,7 +113,11 @@\n \t\t## sets negative intensities to zero\r\n \t\tNegativetoZero $NegativetoZero\r\n \t\t\t\t\r\n-\t\t\r\n+\t\t## final spectra\r\n+\t\t## Graphical display\r\n+\t\t\tFinalGraph $FinalGraph\r\n+\t\t\t\r\n+\t\t\t\r\n         ## Outputs\r\n         dataMatrixOut $dataMatrixOut\r\n \t\tgraphOut $graphOut\r\n@@ -118,14 +129,28 @@\n \t\t<param name="dataMatrixFid" type="data" label="Data matrix of FIDs" help="" format="tabular" />\r\n \t\t<param name="sampleMetadataFid" type="data" label="Sample metadata matrix" help="" format="tabular" />\r\n \t\t\r\n-       \t<param name="lambda" label="Smoothing parameter for solvent suppression" type="float" value="1000000" help="Default value is 1e6"/>\r\n+\t\t## First order phase correction\r\n+\t\t<param name="FirstOPCGraph" label="Display the FIDs after 1st order phase correction?" type="select" help="Select \'YES\' to display the spectra or \'NO\' to not display them ">\r\n+\t\t\t\t<option value="NO"> NO </option>\r\n+\t\t\t\t<option value="YES"> YES </option>\r\n+\t\t</param>\r\n+\t\t\t\t\r\n+\t\t## Water and / or solvents suppression\r\n+       \t<param name="lambda" label="Solvent Suppression: Smoothing parameter" type="float" value="1000000" help="Default value is 1e6"/>\r'..b'rrection: smoothing parameter" value="100000.0" help="Smoothing parameter, generally 1e5 \xe2\x80\x93 1e8. Default value is 100000" />\r\n+\t\t<param name="pBc" type="float" label="Baseline Correction: asymmetry parameter" value="0.05" help="Asymmetry parameter. Default value is 0.05" />\r\n+\t\t<param name="epsilon" type="float" label="Baseline Correction: numerical precision for convergence when estimating the baseline" value="0.00000001" help="Numerical precision for convergence when estimating the \tbaseline. Default value is 1e-8" />\r\n \t\t\r\n-\t\t<param name="maxIter" type="integer" label="Maximum of iterations if ptw.bc is set to FALSE" value="50" help="Maximum of iterations if ptw.bc is set to FALSE. Default value is 50" />\r\n-\t\t<param name="lambdaBc" type="float" label="Smoothing parameter" value="100000.0" help="Smoothing parameter, generally 1e5 \xe2\x80\x93 1e8. Default value is 100000" />\r\n-\t\t<param name="pBc" type="float" label="Asymmetry parameter" value="0.05" help="Asymmetry parameter. Default value is 0.05" />\r\n-\t\t<param name="epsilon" type="float" label="Numerical precision for convergence when estimating the baseline" value="0.00000001" help="Numerical precision for convergence when estimating the \tbaseline. Default value is 1e-8" />\r\n+\t\t<param name="BCGraph" label="Display the spectra after Baseline Correction?" type="select" help="Select \'YES\' to display the spectra or \'NO\' to not display them ">\r\n+\t\t\t\t<option value="NO"> NO </option>\r\n+\t\t\t\t<option value="YES"> YES </option>\r\n+\t\t</param>\r\n \t\t\r\n+\t\t\r\n+\t\t## NegativetoZero\r\n \t\t<param name="NegativetoZero" label="Set negative intensities to zero?" type="select" help="If YES, sets negative intensities to zero">\r\n \t\t\t<option value="NO"> NO </option>\r\n \t\t\t<option value="YES"> YES </option>\r\n \t\t</param>\r\n+\t\t\r\n+\t\t## final spectra\r\n+\t\t<param name="FinalGraph" label="Display the final spectra?" type="select" help="Select \'YES\' to display the spectra or \'NO\' to not display them ">\r\n+\t\t\t<option value="YES"> YES </option>\t\t\r\n+\t\t\t<option value="NO"> NO </option>\r\n+\t\t</param>\r\n+\t\t\r\n \t\t</inputs>\t\r\n \t\r\n \t<outputs>\r\n@@ -269,7 +313,7 @@\n \r\n These steps correspond to the following steps in the PEPS-NMR R library (https://github.com/ManonMartin/PEPSNMR):\r\n \r\n-* First order phase correction\r\n+* Group Delay suppression (First order phase correction)\r\n * Removal of solvent residuals signal from the FID\r\n * Apodization to increase the Signal-to-Noise ratio of the FID\r\n * Fourier transformation\r\n@@ -287,7 +331,6 @@\n \r\n The **types of apodization** are:\r\n \r\n-\r\n * exp: The signal is multiplied by a decreasing exponential exp(-t/LineBroadening).\r\n \r\n * cos2: The signal is multiplied by the value of a cosinus squared from 0 (where its value is 1) until pi/2 (where its value is 0).\r\n@@ -306,13 +349,6 @@\n **Shift referencing**\r\n ----------------------\r\n \r\n-Different **methods for shift referencing**:\r\n-\r\n-* max: the maximum intensity in the search zone is defined as the reference compound peak.\r\n-\r\n-* thres: the reference compound peak is the first peak in the spectrum higher than a predefined threshold (c) which is computed as: c*(cumulated_mean/cumulated_sd).\r\n-\r\n-\r\n The **searching window** can be adapted:\r\n \r\n * near0: the search concentrates around the 0ppm.\r\n@@ -333,8 +369,6 @@\n * cut: The ppm values for which some spectra are not defined are removed.\r\n \r\n \r\n-**ppm value of the reference compound**: By default, the ppm value of the reference compound is set to 0, but any arbitrary value in the ppm interval can be used instead.\r\n-\r\n \r\n **Zero Order Phase correction**\r\n -----------------------------------\r\n@@ -348,7 +382,7 @@\n * max: Optimization of the maximal spectral intensity.\r\n \r\n \r\n-**Search zone for the Zero order phase correction**: enables to optimize the criterion only on the selected spectral window(s).\r\n+** Exclusion area(s) for the Zero order phase correction**: enables to optimize the criterion with excluded spectral window(s), by default the water region is excluded.\r\n \r\n \r\n **Baseline computation**\r\n'