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

Changeset 9:62c62e31fc80 (2017-04-21)
Previous changeset 8:c54c70af216b (2017-04-20) Next changeset 10:06b7a5815a1c (2017-04-21)
Commit message:
planemo upload for repository https://github.com/workflow4metabolomics/nmr_bucketing commit fc2be0f9fa66f830d592d74d14b47a63e761647b
added:
DrawSpec.R
MANUAL_INSTALL.txt
NmrBucketing_script.R
NmrBucketing_wrapper.R
NmrBucketing_xml.xml
README.rst
repository_dependencies.xml
static/images/MTH - Architecture repertoire Bruker.png
static/images/Mth_Travaux.png
test-data/MTBLS1.zip
test-data/MTBLS1_bucketedData.tabular
test-data/MTBLS1_sampleMetadata.tabular
test-data/MTBLS1_variableMetadata.tabular
removed:
nmr_bucketing/.shed.yml
nmr_bucketing/DrawSpec.R
nmr_bucketing/MANUAL_INSTALL.txt
nmr_bucketing/NmrBucketing_script.R
nmr_bucketing/NmrBucketing_wrapper.R
nmr_bucketing/NmrBucketing_xml.xml
nmr_bucketing/README.rst
nmr_bucketing/planemo_test.sh
nmr_bucketing/repository_dependencies.xml
nmr_bucketing/static/images/MTH - Architecture repertoire Bruker.png
nmr_bucketing/static/images/Mth_Travaux.png
nmr_bucketing/test-data/MTBLS1.zip
nmr_bucketing/test-data/MTBLS1_bucketedData.tabular
nmr_bucketing/test-data/MTBLS1_sampleMetadata.tabular
nmr_bucketing/test-data/MTBLS1_variableMetadata.tabular
nmr_bucketing/tool_dependencies.xml
b
diff -r c54c70af216b -r 62c62e31fc80 DrawSpec.R
--- /dev/null Thu Jan 01 00:00:00 1970 +0000
+++ b/DrawSpec.R Fri Apr 21 08:53:40 2017 -0400
[
@@ -0,0 +1,74 @@
+drawSpec <- function (X, startP = -1, endP = -1, groupLabel = NULL, useLog = -1, highBound = -1, lowBound = -1, 
+                      xlab = NULL, ylab = NULL, main = NULL, nAxisPos = 4, offside = 0) 
+{
+  groupLabel_name = groupLabel
+  X = as.data.frame(X)
+#  colnames(X) = c(1:ncol(X))
+  X = as.matrix(X)
+  if (highBound != -1) {
+    for (i in 1:nrow(X)) {
+      myIndex = which(X[i, ] > highBound)
+      X[i, myIndex] = highBound
+    }
+  }
+  if (lowBound != -1) {
+    for (i in 1:nrow(X)) {
+      myIndex = which(X[i, ] < lowBound)
+      X[i, myIndex] = lowBound
+    }
+  }
+  if (is.null(groupLabel)) {
+    groupLabel = c(1:nrow(X))
+    groupLabel = as.factor(groupLabel)
+  }
+  else {
+    levels(groupLabel) = c(1:length(levels(groupLabel)))
+  }
+  if (startP == -1) 
+    startP = 1
+  if (endP == -1) 
+    endP = ncol(X)
+  if (is.null(xlab)) {
+    xlab = "index"
+  }
+  if (is.null(ylab)) {
+    ylab = "intensity"
+  }
+  if (is.null(main)) {
+    main = paste(" ", startP + offside, "-", endP + offside)
+  }
+  GraphRange <- c(startP:endP)
+  yn <- X[, GraphRange]
+  if (useLog != -1) 
+    yn = log(yn)
+  if (length(yn) > ncol(X))
+  {
+    plot(yn[1, ], ylim = c(min(yn), max(yn)), type = "n", ylab = ylab, xlab = xlab, main = main, xaxt = "n")
+    tempVal = trunc(length(GraphRange)/nAxisPos)
+    xPos = c(0:nAxisPos) * tempVal
+    axis(1, at = xPos, labels = colnames(X)[xPos + startP + offside])
+    for (i in 1:length(levels(groupLabel))) 
+    {
+      groupLabelIdx = which(groupLabel == levels(groupLabel)[i])
+      color <- palette(rainbow(length(levels(groupLabel))))
+      for (j in 1:length(groupLabelIdx)) 
+      {
+        lines(yn[groupLabelIdx[j], ], col = color[i])
+      }
+    }
+    if (!is.null(groupLabel_name)) 
+    {
+      legendPos = "topleft"
+      legend(legendPos, levels(groupLabel_name), col = as.integer(levels(groupLabel)), text.col = "black", pch = c(19, 19), bg = "gray90")
+    }
+  }
+  if (length(yn) == ncol(X))
+  {
+    plot(yn, ylim = c(min(yn), max(yn)), type = "n", ylab = ylab, xlab = xlab, main = main, xaxt = "n")
+    tempVal = trunc(length(GraphRange)/nAxisPos)
+    xPos = c(0:nAxisPos) * tempVal
+#    axis(1, at = xPos, labels = xPos + startP + offside)
+    axis(1, at = xPos, labels = colnames(X)[xPos + startP + offside])
+    lines(yn)
+  }
+}
\ No newline at end of file
b
diff -r c54c70af216b -r 62c62e31fc80 MANUAL_INSTALL.txt
--- /dev/null Thu Jan 01 00:00:00 1970 +0000
+++ b/MANUAL_INSTALL.txt Fri Apr 21 08:53:40 2017 -0400
b
@@ -0,0 +1,59 @@
+Instructions to integrate the "NMR bucketing" tool into a local instance of Galaxy
+Version February 2015 M Tremblay-Franco
+
+
+## --- R bin and Packages : --- ##
+R version 3.0.2 (2013-09-25) -- "Frisbee Sailing"
+Platform: x86_64-redhat-linux-gnu (64-bit)
+
+Install the "batch" library, necessary for parseCommandArgs function and the "pracma" library, nessecary for cumtrapz function:
+ - Download package source (*.tar.gz file) from your favorite CRAN (http://www.r-project.org/)
+For example: http://cran.univ-lyon1.fr/
+
+ - Install package in your R session
+install.packages("path/package_name.tar.gz",lib="path",repos=NULL)
+For Example: install.packages("/usr/lib64/R/library/pracma_1.8.3.tar",lib="/usr/lib64/R/library",repos=NULL)
+
+ - Finally, load the package into your R session
+library(batch)
+library(pracma)
+
+
+## --- Config : --- ##
+ - Edit the file "/galaxy/dist/galaxy-dist/tool_conf.xml" and add 
+<section id="id_name" name="Name">
+  <tool file="path/NmrBucketing_xml.xml" />
+</section>
+to create a new section containing the NMR_Bucketing tool
+or add
+  <tool file="path/NmrBucketing_xml.xml" />
+in an existing section
+
+ - Put the three files NmrBucketing_xml.xml, NmrBucketing_wrapper.R and NmrBucketing_script.R in a same directory
+For example, path=/galaxy/dist/galaxy-dist/tools/stats
+
+ - Edit the NmrBucketing_xml.xml file and change the path in the following lines
+    # R script
+    R --vanilla --slave --no-site-file --file=path/NmrBucketing_wrapper.R --args
+    
+    ## Library name for raw files storage
+    library path/$library
+
+## --- XML help part --- ##
+one image: 
+Copy the 'Mth_Architecture_Repertoire_Bruker.png' file within the directory to your galaxy-dist/static/images/
+
+
+ - Activate the "user_library_import_dir" in your /galaxy/dist/galaxy-dist/universe_wsgi.ini and create the users directories in this path, for example:
+
+ #In universe_wsgi.ini
+  user_library_import_dir = /projet/sbr/galaxy/import/user
+
+ #Create the user "myaccount" in this path
+
+ User path: /projet/sbr/galaxy/import/user/myaccount@sb-roscoff.fr
+
+
+
+
+Finally, restart Galaxy
\ No newline at end of file
b
diff -r c54c70af216b -r 62c62e31fc80 NmrBucketing_script.R
--- /dev/null Thu Jan 01 00:00:00 1970 +0000
+++ b/NmrBucketing_script.R Fri Apr 21 08:53:40 2017 -0400
[
b'@@ -0,0 +1,273 @@\n+################################################################################################\r\n+# SPECTRA BUCKETING AND INTEGRATION FROM RAW BRUKER FILES                                      #\r\n+# User : Galaxy                                                                                #\r\n+# Original data : --                                                                           #\r\n+# Starting date : 20-10-2014                                                                   #\r\n+# Version 1 : 18-12-2014                                                                       #\r\n+# Version 2 : 07-01-2015                                                                       #\r\n+# Version 3 : 24-10-2016                                                                       #\r\n+#                                                                                              #\r\n+# Input files : modification on october 2016                                                   #\r\n+#   - Raw bruker files included in user-defined fileName                                      #\r\n+#   - Preprocessed files (alignment, ...) included in p x n dataframe                          #\r\n+################################################################################################\r\n+NmrBucketing <- function(fileType,fileName,leftBorder = 10.0,rightBorder = 0.5,bucketSize = 0.04,exclusionZones,\r\n+                         exclusionZonesBorders=NULL,graph=c("None","Overlay","One_per_individual"),\r\n+                         nomFichier,savLog.txtC = NULL) \r\n+{\r\n+  ## Option\r\n+  ##---------------\r\n+  strAsFacL <- options()$stringsAsFactors\r\n+  options(stingsAsFactors = FALSE)\r\n+  options(warn = -1)\r\n+  \r\n+  \r\n+  ## Constants\r\n+  ##---------------\r\n+  topEnvC <- environment()\r\n+  flgC <- "\\n"\r\n+  \r\n+  ## Log file (in case of integration into Galaxy)\r\n+  ##----------------------------------------------\r\n+  if(!is.null(savLog.txtC))\r\n+    sink(savLog.txtC, append = TRUE)\r\n+  \r\n+  ## Functions definition\r\n+  ##---------------------  \r\n+    ## RAW BRUKER FILE READING FUNCTION\r\n+  NmRBrucker_read <- function(DataDir,SampleSpectrum)\r\n+  {\r\n+    \r\n+    bruker.get_param <- function (ACQ,paramStr)\r\n+    {\r\n+      regexpStr <- paste("^...",paramStr,"=",sep="")\r\n+      as.numeric(gsub("^[^=]+= ","" ,ACQ[which(simplify2array(regexpr(regexpStr,ACQ))>0)]))\r\n+    }\r\n+    \r\n+    ACQFILE <- "acqus"\r\n+    SPECFILE <- paste(DataDir,"/1r",sep="")\r\n+    PROCFILE <- paste(DataDir,"/procs",sep="")\r\n+    \r\n+    ACQ <- readLines(ACQFILE)\r\n+    TD      <- bruker.get_param(ACQ,"TD")\r\n+    SW      <- bruker.get_param(ACQ,"SW")\r\n+    SWH     <- bruker.get_param(ACQ,"SW_h")\r\n+    DTYPA   <- bruker.get_param(ACQ,"DTYPA")\r\n+    BYTORDA <- bruker.get_param(ACQ,"BYTORDA")\r\n+    #ENDIAN = ifelse( BYTORDA==0, "little", "big")\r\n+    ENDIAN <- "little"\r\n+    SIZE = ifelse( DTYPA==0, 4, 8)\r\n+    \r\n+    PROC <- readLines(PROCFILE)\r\n+    OFFSET <- bruker.get_param(PROC,"OFFSET")\r\n+    SI <- bruker.get_param(PROC,"SI")\r\n+    \r\n+    to.read = file(SPECFILE,"rb")\r\n+    maxTDSI = max(TD,SI)\r\n+    #  signal<-rev(readBin(to.read, what="int",size=SIZE, n=TD, signed = TRUE, endian = ENDIAN))\r\n+    signal<-rev(readBin(to.read, what="int",size=SIZE, n=maxTDSI, signed = TRUE, endian = ENDIAN))\r\n+    close(to.read)\r\n+    \r\n+    td <- length(signal)\r\n+    \r\n+    #  dppm <- SW/(TD-1)\r\n+    dppm <- SW/(td-1)\r\n+    pmax <- OFFSET\r\n+    pmin <- OFFSET - SW\r\n+    ppmseq <- seq(from=pmin, to=pmax, by=dppm)\r\n+    signal <- 100*signal/max(signal)\r\n+    \r\n+    SampleSpectrum <- cbind(ppmseq,signal)\r\n+    return(SampleSpectrum)\r\n+  }\r\n+  \r\n+    ## SPECTRUM BUCKETING\r\n+  NmrBrucker_bucket <- function(spectrum)\r\n+  {\r\n+    # Initialisations\r\n+    b <- 1\r\n+    j <- 1\r\n+    # Variable number\r\n+    J <- round((spectrum[1,1]-spectrum[dim(spectrum)[1],1])/bucketSize)\r\n+    f.bucket <- matrix(rep(0,J*2),ncol=2)\r\n+    colnames(f.bucket) <- c("Bucket",FileNames[i])\r\n+    \r\n+    \r\n+    # Data bucketing\r\n+'..b'Names <- list.files(fileName)\r\n+    n <- length(FileNames)\r\n+    \r\n+    # Reading and Bucketing\r\n+    fileName <- paste(fileName,"/",sep="")\r\n+  \r\n+    i <- 1\r\n+    while (i <= n)\r\n+    {\r\n+      # File reading\r\n+      SampleDir <- paste(fileName,FileNames[i],"/1/",sep="")\r\n+      setwd(SampleDir)\r\n+      DataDir <- "pdata/1"\r\n+  \r\n+      rawSpectrum <- NmRBrucker_read(DataDir,rawSpectrum)\r\n+  \r\n+      orderedSpectrum <- rawSpectrum[order(rawSpectrum[,1],decreasing=T), ]\r\n+      \r\n+      # Removal of chemical shifts > leftBorder or < rightBorder boundaries\r\n+      truncatedSpectrum <- orderedSpectrum[orderedSpectrum[,1] < leftBorder & orderedSpectrum[,1] > rightBorder, ]\r\n+      truncatedSpectrum[,1] <- round(truncatedSpectrum[,1],3)\r\n+      \r\n+      # Bucketing\r\n+      spectrum.bucket <- NmrBrucker_bucket(truncatedSpectrum)\r\n+      ppm <- spectrum.bucket[,1]\r\n+      \r\n+      # spectrum Concatenation\r\n+      if (i == 1)\r\n+        bucketedSpectra <- spectrum.bucket\r\n+      if (i > 1)\r\n+        bucketedSpectra <- cbind(bucketedSpectra,spectrum.bucket[,2])\r\n+      colnames(bucketedSpectra)[i+1] <- FileNames[i]\r\n+      \r\n+      # Next sample\r\n+      rm(spectrum.bucket)\r\n+      i <- i +1\r\n+    }\r\n+    # Directory\r\n+    cd(fileName)  \r\n+  }\r\n+  \r\n+  ## Inputs from dataset (preprocessed files)\r\n+  if (fileType=="tsv")\r\n+  {\r\n+    FileNames <- colnames(fileName)\r\n+    n <- length(FileNames)\r\n+    \r\n+    for (i in 1:ncol(fileName))\r\n+    {\r\n+      orderedSpectrum <- cbind(as.numeric(rownames(fileName)),fileName[,i])\r\n+      orderedSpectrum <- orderedSpectrum[order(orderedSpectrum[,1],decreasing=T), ]\r\n+      \r\n+      truncatedSpectrum <- orderedSpectrum[orderedSpectrum[,1] < leftBorder & orderedSpectrum[,1] > rightBorder, ]\r\n+      truncatedSpectrum[,1] <- round(truncatedSpectrum[,1],3)\r\n+      \r\n+      # Bucketing\r\n+      spectrum.bucket <- NmrBrucker_bucket(truncatedSpectrum)\r\n+      ppm <- spectrum.bucket[,1]\r\n+      \r\n+      # spectrum Concatenation\r\n+      if (i == 1)\r\n+        bucketedSpectra <- spectrum.bucket\r\n+      if (i > 1)\r\n+        bucketedSpectra <- cbind(bucketedSpectra,spectrum.bucket[,2])\r\n+      colnames(bucketedSpectra)[i+1] <- colnames(fileName)[i]\r\n+    }\r\n+  }\r\n+  \r\n+  identifiants <- gsub("([- , * { } | \\\\[ ])","_",colnames(bucketedSpectra)[-1])\r\n+  colnames(bucketedSpectra) <- c(colnames(bucketedSpectra)[1],identifiants)\r\n+\r\n+  bucketedSpectra <- bucketedSpectra[bucketedSpectra[,1]!=0,]\r\n+  rownames(bucketedSpectra) <- paste("B",bucketedSpectra[,1],sep="")\r\n+  bucketedSpectra <- bucketedSpectra[,-1]\r\n+  \r\n+  # Metadata matrice outputs\r\n+  sampleMetadata <- data.frame(1:n)\r\n+  rownames(sampleMetadata) <- colnames(bucketedSpectra)\r\n+  colnames(sampleMetadata) <- "SampleOrder"\r\n+  \r\n+  variableMetadata <- data.frame(1:nrow(bucketedSpectra))\r\n+  rownames(variableMetadata) <- rownames(bucketedSpectra)\r\n+  colnames(variableMetadata) <- "VariableOrder"\r\n+\r\n+\r\n+  return(list(bucketedSpectra,sampleMetadata,variableMetadata,ppm)) # ,truncatedSpectrum_matrice\r\n+}\r\n+\r\n+\r\n+#################################################################################################################\r\n+## Typical function call\r\n+#################################################################################################################\r\n+## StudyDir <- "K:/PROJETS/Metabohub/Bruker/Tlse_BPASourisCerveau/"\r\n+## upper <- 9.5\r\n+## lower <- 0.8\r\n+## bucket.width <- 0.01\r\n+## exclusion <- TRUE\r\n+## exclusion.zone <- list(c(5.1,4.5))\r\n+## graphique <- "Overlay"\r\n+## nomFichier <- "Tlse_BPASourisCerveau_NmrBucketing_graph.pdf"\r\n+## tlse_cerveaupnd21.bucket <- NmrBucketing(StudyDir,upper,lower,bucket.width,exclusion,exclusion.zone,graphique,nomFichier)\r\n+## write.table(tlse_cerveaupnd21.bucket,file=paste(StudyDir,"Tlse_BPASourisCerveau_NmrBucketing_dataMatrix.tsv",sep=""),\r\n+##             quote=FALSE,row.nmaes=FALSE,sep="\\t")\r\n+#################################################################################################################\r\n'
b
diff -r c54c70af216b -r 62c62e31fc80 NmrBucketing_wrapper.R
--- /dev/null Thu Jan 01 00:00:00 1970 +0000
+++ b/NmrBucketing_wrapper.R Fri Apr 21 08:53:40 2017 -0400
[
b'@@ -0,0 +1,295 @@\n+#!/usr/local/public/bin/Rscript --vanilla --slave --no-site-file\r\n+\r\n+## 070115_NmrBucketing2galaxy_v1.R\r\n+## Marie Tremblay-Franco\r\n+## MetaboHUB: The French Infrastructure for Metabolomics and Fluxomics\r\n+## www.metabohub.fr/en\r\n+## marie.tremblay-franco@toulouse.inra.fr\r\n+\r\n+runExampleL <- FALSE\r\n+\r\n+if(runExampleL) {\r\n+##------------------------------\r\n+## Example of arguments\r\n+##------------------------------\r\n+argLs <- list(StudyDir = "Tlse_BPASourisCerveau",\r\n+              upper = "10.0",\r\n+              lower = "0.50",\r\n+              bucket.width = "0.01",\r\n+              exclusion = "TRUE",\r\n+              exclusion.zone = list(c(6.5,4.5)),\r\n+              graph="Overlay")\r\n+\r\n+argLs <- c(argLs,\r\n+           list(dataMatrixOut = paste(directory,"_NmrBucketing_dataMatrix.tsv",sep=""),\r\n+                sampleMetadataOut = paste(directory,"_NmrBucketing_sampleMetadata.tsv",sep=""),\r\n+                variableMetadataOut = paste(directory,"_NmrBucketing_variableMetadata.tsv",sep=""),\r\n+                graphOut = paste(directory,"_NmrBucketing_graph.pdf",sep=""),\r\n+                logOut = paste(directory,"_NmrBucketing_log.txt",sep="")))\r\n+}\r\n+\r\n+##------------------------------\r\n+## Options\r\n+##------------------------------\r\n+strAsFacL <- options()$stringsAsFactors\r\n+options(stringsAsFactors = FALSE)\r\n+\r\n+\r\n+##------------------------------\r\n+## Libraries laoding\r\n+##------------------------------\r\n+# For parseCommandArgs function\r\n+library(batch)\r\n+# For cumtrapz function\r\n+library(pracma)\r\n+\r\n+# R script call\r\n+source_local <- function(fname)\r\n+{\r\n+\targv <- commandArgs(trailingOnly = FALSE)\r\n+\tbase_dir <- dirname(substring(argv[grep("--file=", argv)], 8))\r\n+\tsource(paste(base_dir, fname, sep="/"))\r\n+}\r\n+#Import the different functions\r\n+source_local("NmrBucketing_script.R")\r\n+source_local("DrawSpec.R")\r\n+\r\n+##------------------------------\r\n+## Errors ?????????????????????\r\n+##------------------------------\r\n+\r\n+\r\n+##------------------------------\r\n+## Constants\r\n+##------------------------------\r\n+topEnvC <- environment()\r\n+flagC <- "\\n"\r\n+\r\n+\r\n+##------------------------------\r\n+## Script\r\n+##------------------------------\r\n+if(!runExampleL)\r\n+    argLs <- parseCommandArgs(evaluate=FALSE)\r\n+\r\n+\r\n+## Parameters Loading\r\n+##-------------------\r\n+  # Inputs\r\n+if (!is.null(argLs[["zipfile"]])){\r\n+\tfileType="zip"\r\n+\tzipfile= argLs[["zipfile"]]\r\n+\tdirectory=unzip(zipfile, list=F)\r\n+\tdirectory=paste(getwd(),strsplit(directory[1],"/")[[1]][2],sep="/")\r\n+} else if (!is.null(argLs[["tsvfile"]])){\r\n+\tfileType="tsv"\r\n+\tdirectory <- read.table(argLs[["tsvfile"]],check.names=FALSE,header=TRUE,sep="\\t")\r\n+}\r\n+\r\n+leftBorder <- argLs[["left_border"]]\r\n+rightBorder <- argLs[["right_border"]]\r\n+bucketSize <- argLs[["bucket_width"]]\r\n+exclusionZones <- argLs[["zone_exclusion_choices.choice"]]\r\n+\r\n+exclusionZonesBorders <- NULL\r\n+if (!is.null(argLs$zone_exclusion_left))\r\n+{\r\n+   for(i in which(names(argLs)=="zone_exclusion_left"))\r\n+   {\r\n+     exclusionZonesBorders <- c(exclusionZonesBorders,list(c(argLs[[i]],argLs[[i+1]])))\r\n+   }\r\n+}\r\n+\r\n+graphique <- argLs[["graphType"]]\r\n+\r\n+  # Outputs\r\n+nomGraphe <- argLs[["graphOut"]]\r\n+dataMatrixOut <- argLs[["dataMatrixOut"]]\r\n+logFile <- argLs[["logOut"]]\r\n+if (fileType=="zip")\r\n+{\r\n+  sampleMetadataOut <- argLs[["sampleOut"]]\r\n+  variableMetadataOut <- argLs[["variableOut"]]\r\n+}\r\n+\r\n+## Checking arguments\r\n+##-------------------\r\n+error.stock <- "\\n"\r\n+\r\n+if(length(error.stock) > 1)\r\n+  stop(error.stock)\r\n+\r\n+\r\n+## Computation\r\n+##------------\r\n+outputs <- NmrBucketing(fileType=fileType, fileName=directory, leftBorder=leftBorder, rightBorder=rightBorder, bucketSize=bucketSize,\r\n+\t\t\t\t\t\texclusionZones=exclusionZones, exclusionZonesBorders=exclusionZonesBorders, graph=graphique, nomFichier=nomGraphe,\r\n+\t\t\t\t\t\tsavLog.txtC=logFile)\r\n+data_bucket <- outputs[[1]]\r\n+data_sample <- outputs[[2]]\r\n+data_variable <- outputs[[3]]\r\n+ppm <- outputs[[4]]\r\n+ppm <- round(ppm,2)\r\n+\r\n+## G'..b'):nrow(data_bucket),]))\r\n+      drawSpec(spectra,xlab="", ylab="Intensity", main="")\r\n+    }\r\n+  }\r\n+  else\r\n+  {\r\n+    for (i in 1:ncol(data_bucket))\r\n+    {\r\n+      par(mfrow=c((nbZones+2),1))\r\n+      n <- length(excludedZone)\r\n+      spectra <- t(data_bucket[,i])\r\n+\t  names(spectra) <- rownames(data_bucket)\r\n+      plot(1:length(spectra), spectra, type=\'l\', xlab="", ylab="Intensity", main=colnames(data_bucket)[i], xaxt = "n")\r\n+\t  xPos <- 1\r\n+\t  nAxisPos <- 4\r\n+\t  startP <- length(nAxisPos) \r\n+\t  endP <- nrow(data_bucket)\r\n+\t  GraphRange <- c(startP:endP)\r\n+\t  tempVal = trunc(length(GraphRange)/nAxisPos)\r\n+\t  xPos = c(0:nAxisPos) * tempVal\r\n+\t  axis(1, at = xPos, labels = rownames(data_bucket)[xPos + startP])\r\n+     \r\n+      ## Zoomed spectral window depending on exclusion zone(s)\r\n+      if (nbZones != 0)\r\n+      {\r\n+        BInf <- excludedZone[n]\r\n+        if (round(BInf,1) == BInf)\r\n+        {\r\n+          BInf <- BInf+0.01\r\n+        }\r\n+        spectra <- t(data_bucket[1:(which(ppm == BInf)[[1]]),i])\r\n+\t\tnames(spectra) <- rownames(data_bucket)[1:(which(ppm == BInf)[[1]])]\r\n+\t\tplot(1:length(spectra), spectra, type=\'l\',xlab="", ylab="Intensity", main="", xaxt = "n")\t\t\t\r\n+\t\txPos <- 1\r\n+\t\tnAxisPos <- 4\r\n+\t\tstartP <- length(nAxisPos) \r\n+\t\tendP <- length(spectra)\r\n+\t\tGraphRange <- c(startP:endP)\r\n+\t\ttempVal = trunc(length(GraphRange)/nAxisPos)\r\n+\t\txPos = c(0:nAxisPos) * tempVal\r\n+\t\taxis(1, at = xPos, labels = rownames(data_bucket)[xPos + startP])\r\n+        n <- n - 1\r\n+        \r\n+        while (n >= nbZones & nbZones > 1)\r\n+        {\r\n+          BInf <- excludedZone[n-1]\r\n+          if (round(BInf,1) > BInf)\r\n+          {\r\n+            BInf <- BInf+0.01\r\n+          }\r\n+          spectra <- t(data_bucket[(which(ppm == excludedZone[n])[[1]]):(which(ppm == BInf)[[1]]),i])\r\n+\t\t  names(spectra) <- rownames(data_bucket)[(which(ppm == excludedZone[n])[[1]]):(which(ppm == BInf)[[1]])]\r\n+          plot(1:length(spectra), spectra, type=\'l\',xlab="", ylab="Intensity", main="", xaxt = "n")\r\n+\t\t  xPos <- 1\r\n+\t\t  nAxisPos <- 4\r\n+\t\t  startP <- length(nAxisPos) \r\n+\t\t  endP <- length(spectra)\r\n+\t\t  GraphRange <- c(startP:endP)\r\n+\t\t  tempVal = trunc(length(GraphRange)/nAxisPos)\r\n+\t\t  xPos = c(0:nAxisPos) * tempVal\r\n+\t\t  axis(1, at = xPos, labels = rownames(data_bucket)[xPos + startP])\r\n+          n <- n - 2\r\n+        }\r\n+        \r\n+        BInf <- excludedZone[1]\r\n+        if (round(BInf,1) <= BInf)\r\n+        {\r\n+          BInf <- BInf+0.01\r\n+        }\r\n+        spectra <- t(data_bucket[(which(ppm == BInf)[[1]]):nrow(data_bucket),i])\r\n+\t\tnames(spectra) <- rownames(data_bucket)[(which(ppm == BInf)[[1]]):nrow(data_bucket)]\r\n+        plot(1:length(spectra), spectra, type=\'l\',xlab="", ylab="Intensity", main="", xaxt = "n")\r\n+\t\txPos <- 1\r\n+\t\tnAxisPos <- 4\r\n+\t\tstartP <- length(nAxisPos) \r\n+\t\tendP <- length(spectra)\r\n+\t\tGraphRange <- c(startP:endP)\r\n+\t\ttempVal = trunc(length(GraphRange)/nAxisPos)\r\n+\t\txPos = c(0:nAxisPos) * tempVal\r\n+\t\taxis(1, at = xPos, labels = rownames(data_bucket)[xPos + startP])\r\n+      }\r\n+    }\r\n+  }\r\n+  dev.off()\r\n+}\r\n+## Saving\r\n+##-------\r\n+  # Data\r\n+data_bucket <- cbind(rownames(data_bucket),data_bucket)\r\n+colnames(data_bucket) <- c("Bucket",colnames(data_bucket)[-1])\r\n+write.table(data_bucket,file=argLs$dataMatrixOut,quote=FALSE,row.names=FALSE,sep="\\t")\r\n+  # Sample\r\n+data_sample <- cbind(rownames(data_sample),data_sample)\r\n+colnames(data_sample) <- c("Sample",colnames(data_sample)[-1])\r\n+write.table(data_sample,file=argLs$sampleOut,quote=FALSE,row.names=FALSE,sep="\\t")\r\n+  # Variable\r\n+data_variable <- cbind(rownames(data_variable),data_variable)\r\n+colnames(data_variable) <- c("Bucket",colnames(data_variable)[-1])\r\n+write.table(data_variable,file=argLs$variableOut,quote=FALSE,row.names=FALSE,sep="\\t")\r\n+\r\n+\r\n+## Ending\r\n+##---------------------\r\n+\r\n+cat("\\nEnd of \'NMR bucketing\' Galaxy module call: ", as.character(Sys.time()), sep = "")\r\n+\r\n+## sink(NULL)\r\n+\r\n+options(stringsAsFactors = strAsFacL)\r\n+\r\n+rm(list = ls())\r\n'
b
diff -r c54c70af216b -r 62c62e31fc80 NmrBucketing_xml.xml
--- /dev/null Thu Jan 01 00:00:00 1970 +0000
+++ b/NmrBucketing_xml.xml Fri Apr 21 08:53:40 2017 -0400
b
b'@@ -0,0 +1,297 @@\n+<tool id="NmrBucketing" name="NMR_Bucketing" version="1.0.4">\r\n+\r\n+    <description> Bucketing and integration of NMR Bruker raw data</description>\r\n+\r\n+    <requirements>\r\n+\t    <requirement type="package" version="1.1_4">r-batch</requirement>\r\n+\t    <requirement type="package" version="1.8.8">r-pracma</requirement>\r\n+    </requirements>\r\n+\r\n+    <stdio>\r\n+        <exit_code range="1:" level="fatal" />\r\n+    </stdio>\r\n+\r\n+    <command>\r\n+        Rscript \'$__tool_directory__/NmrBucketing_wrapper.R\'\r\n+\r\n+        #if $inputs.input == "tsv_file":\r\n+            tsvfile \'$inputs.tsv_file\'\r\n+        #elif $inputs.input == "zip_file":\r\n+            zipfile \'$inputs.zip_file\'\r\n+        #end if\r\n+\r\n+\r\n+        ## Bucket width\r\n+        bucket_width $bucket_width\r\n+\r\n+        ## Spectra borders\r\n+        left_border $left_border\r\n+        right_border $right_border\r\n+\r\n+\r\n+        ## Spectra representation\r\n+        graphType $graphType\r\n+\r\n+        ## Exclusion zone\r\n+        zone_exclusion_choices.choice ${zone_exclusion_choices.choice}\r\n+        #if str($zone_exclusion_choices.choice) == \'yes\':\r\n+            #for $i in $zone_exclusion_choices.conditions:\r\n+                zone_exclusion_left ${i.zone_exclusion_left}\r\n+                zone_exclusion_right ${i.zone_exclusion_right}\r\n+            #end for\r\n+        #end if\r\n+\r\n+        ## Outputs\r\n+        logOut log.log\r\n+        dataMatrixOut \'$dataMatrixOut\'\r\n+        sampleOut \'$sampleOut\'\r\n+        variableOut \'$variableOut\'\r\n+        graphOut \'$graphOut\'; cat log.log\r\n+    </command>\r\n+\r\n+    <inputs>\r\n+        <conditional name="inputs">\r\n+            <param name="input" type="select" label="Choose your inputs method" >\r\n+                <option value="zip_file" selected="true">Zip file from your history containing your Bruker directories</option>\r\n+                <option value="tsv_file">Tsv file containing preprocessed spectra (from your history)</option>\r\n+            </param>\r\n+            <when value="zip_file">\r\n+                <param name="zip_file" type="data" format="no_unzip.zip" label="Zip file" />\r\n+            </when>\r\n+            <when value="tsv_file">\r\n+                <param name="tsv_file" type="data" format="tabular" label="Tsv file" />\r\n+            </when>\r\n+        </conditional>\r\n+\r\n+        <param name="bucket_width" label="Bucket width" type="float" value="0.04" help="Default value is 0.04 ppm"/>\r\n+\r\n+        <param name="left_border" label="Left Border" type="float" value="10.0" size="10" help="Default value is 10 ppm"/>\r\n+        <param name="right_border" label="Right Border" type="float" value="0.5" size="10" help="Default value is 0.5 ppm"/>\r\n+\r\n+        <conditional name="zone_exclusion_choices">\r\n+            <param name="choice" type="select" label="Exclusion zone(s)" help="Choose if you want to exclude particular zone(s)" >\r\n+                <option value="yes" > yes </option>\r\n+                <option value="no" selected="true"> no </option>\r\n+            </param>\r\n+            <when value="yes">\r\n+                <repeat name="conditions" title="exclusion zones">\r\n+                    <param name="zone_exclusion_left" label="Left exclusion zone border" type="float" value="10.0" />\r\n+                    <param name="zone_exclusion_right" label="Right exclusion zone border" type="float" value="10.0" />\r\n+                </repeat>\r\n+            </when>\r\n+            <when value="no">\r\n+            </when>\r\n+        </conditional>\r\n+\r\n+        <param name="graphType" label="Spectra representation" type="select" help="Select \'None\' for no representation,\'Overlay\' to overlay all spectra on a unique chart and \'One per individual\' to generate an individual chart for each observation">\r\n+            <option value="None"> none </option>\r\n+            <option value="Overlay"> Overlay </option>\r\n+            <option value="One_per_individual"> One_per_individual </option>\r\n+        </param>\r\n+\r\n+    </inputs>\r\n+\r\n+    <outputs>\r\n+   '..b'-+----------------------+--------+\r\n+\r\n+\r\n+-----------\r\n+Input files\r\n+-----------\r\n+\r\n++---------------------------+------------+\r\n+| Parameter : num + label   |   Format   |\r\n++===========================+============+\r\n+| 1 : Choose your inputs    |   zip      |\r\n++---------------------------+------------+\r\n+| 1 : Choose your inputs    |   tsv      |\r\n++---------------------------+------------+\r\n+\r\n+**Choose your inputs**\r\n+\r\n+You have three methods for your inputs:\r\n+\r\n+| Zip file (recommended): You can put a zip file containing your inputs as raw Bruker files: myinputs.zip (containing all your conditions as sub-directories).\r\n+| Tsv file: You can put a tsv file containing your inputs as preprocessed spectra: myinputs.tsv (containing all your conditions in columns and chemical shifts in rows).\r\n+\r\n+.. image:: ./static/images/Mth_Architecture_Repertoire_Bruker.png\r\n+:width: 800\r\n+\r\n+----------\r\n+Parameters\r\n+----------\r\n+\r\n+Bucket width\r\n+| size of windows\r\n+|\r\n+\r\n+Left limit\r\n+| Upper boundary: values greater than this value are not used in the bucketing. Default value is 10.0 ppm\r\n+|\r\n+\r\n+Right limit\r\n+| Lower boundary: values lower than this value are not used in the bucketing. Default value is 0.5 ppm\r\n+|\r\n+\r\n+Exclusion zone(s)\r\n+| Spectral regions to exclude, water, solvents, ... resonance\r\n+| If YES: parameters **Lower exclusion zone** and **Upper exclusion zone** are visible,\r\n+| If NO: no zone to exclude\r\n+| Default value is NO\r\n+|\r\n+\r\n+Left exclusion zone\r\n+| Upper boundary of exclusion zone\r\n+|\r\n+\r\n+Right exclusion zone\r\n+| Lower boundary of exclusion zone\r\n+\r\n+| *Notes:*\r\n+| - these parameters can be used several times using the "Add new exclusion zones" button\r\n+|\r\n+\r\n+Spectra representation:\r\n+| Graphical chart of bucketed and integrated raw files\r\n+| If "Overlay": the n (sample number) spectra are overlaid on the same figure\r\n+| If "One_per_individual": pdf file includes n pages (1 per sample)\r\n+|\r\n+\r\n+\r\n+------------\r\n+Output files\r\n+------------\r\n+\r\n+\r\n+bucketedData.tsv\r\n+| tabular output\r\n+| Data matrix with p rows (buckets) and n columns (samples) containing the intensities\r\n+|\r\n+\r\n+sampleMetadata.tsv\r\n+| tabular output\r\n+| file with n rows (samples) and 2 columns containing sample identifier (rownames) and sample order: the rownames of sampleMetadata must be identical to the colnames of the bucketedData. Can add columns with numeric and/or character sample metadata. This file is optional in the normalization step and mandatory in the statistical analysis step of the workflow.\r\n+|\r\n+\r\n+variableMetadata.tsv\r\n+| tabular output\r\n+| file with p rows (buckets) and 2 columns containing variable identifier (rownames) and bucket order: the rownames of variableMetadata must be identical to the rownames of the bucketedData. Can add columns with numeric and/or character variable metadata. This file is mandatory in the statistical analysis step of the workflow.\r\n+|\r\n+\r\n+spectra.pdf\r\n+| pdf output\r\n+| Graphical chart of bucketed and integrated data\r\n+|\r\n+\r\n+\r\n+---------------------------------------------------\r\n+\r\n+---------------\r\n+Working example\r\n+---------------\r\n+\r\n+\r\n+.. class:: warningmark\r\n+\r\n+Under construction\r\n+\r\n+.. image:: ./static/images/Mth_Travaux.png\r\n+:width: 100\r\n+\r\n+---------------------------------------------------\r\n+\r\n+Changelog/News\r\n+--------------\r\n+\r\n+**Version 1.0.4 - 21/04/2017**\r\n+\r\n+- IMPROVEMENT: Add \xe2\x80\x9czoomed\xe2\x80\x9d representations of bucketed spectra, depending on exclusion zone borders\r\n+\r\n+**Version 1.0.3 - 24/10/2016**\r\n+\r\n+- ENHANCEMENT: add possibility of bucketing processed files (upstream tools)\r\n+\r\n+**Version 1.0.2 - 12/08/2016**\r\n+\r\n+- ENHANCEMENT: x-axis customization: add chemical shift labels\r\n+\r\n+**Version 1.0.1 - 04/04/2016**\r\n+\r\n+- TEST: refactoring to pass planemo test using conda dependencies\r\n+\r\n+\r\n+**Version 2015-01-08 - 08/01/2015**\r\n+\r\n+    </help>\r\n+    <citations>\r\n+        <citation type="doi">10.1093/bioinformatics/btu813</citation>\r\n+    </citations>\r\n+</tool>\r\n'
b
diff -r c54c70af216b -r 62c62e31fc80 README.rst
--- /dev/null Thu Jan 01 00:00:00 1970 +0000
+++ b/README.rst Fri Apr 21 08:53:40 2017 -0400
b
@@ -0,0 +1,32 @@
+
+Changelog/News
+--------------
+
+**Version 1.0.4 - 21/04/2017**
+
+- IMPROVEMENT: Add “zoomed” representations of bucketed spectra, depending on exclusion zone borders
+
+**Version 1.0.3 - 24/10/2016**
+
+- ENHANCEMENT: add possibility of bucketing processed files (upstream tools)
+
+**Version 1.0.2 - 12/08/2016**
+
+- ENHANCEMENT: x-axis customization: add chemical shift labels 
+
+**Version 1.0.1 - 04/04/2016**
+
+- TEST: refactoring to pass planemo test using conda dependencies
+
+
+**Version 2015-01-08 - 08/01/2015**
+
+
+
+Test Status
+-----------
+
+Planemo test using conda: passed
+
+Planemo shed_test: passed
+
b
diff -r c54c70af216b -r 62c62e31fc80 nmr_bucketing/.shed.yml
--- a/nmr_bucketing/.shed.yml Thu Apr 20 06:34:51 2017 -0400
+++ /dev/null Thu Jan 01 00:00:00 1970 +0000
[
@@ -1,7 +0,0 @@
-categories: [Metabolomics]
-description: '[Metabolomics][W4M][NMR] NMR Bucketing - Bucketing / Binning (spectra segmentation in fixed-size windows) and integration (sum of absolute intensities inside each bucket) to preprocess NMR data'
-homepage_url: http://workflow4metabolomics.org
-long_description: 'Part of the W4M project: http://workflow4metabolomics.org'
-name: nmr_bucketing
-owner: marie-tremblay-metatoul
-remote_repository_url: https://github.com/workflow4metabolomics/nmr_bucketing
b
diff -r c54c70af216b -r 62c62e31fc80 nmr_bucketing/DrawSpec.R
--- a/nmr_bucketing/DrawSpec.R Thu Apr 20 06:34:51 2017 -0400
+++ /dev/null Thu Jan 01 00:00:00 1970 +0000
[
@@ -1,74 +0,0 @@
-drawSpec <- function (X, startP = -1, endP = -1, groupLabel = NULL, useLog = -1, highBound = -1, lowBound = -1, 
-                      xlab = NULL, ylab = NULL, main = NULL, nAxisPos = 4, offside = 0) 
-{
-  groupLabel_name = groupLabel
-  X = as.data.frame(X)
-#  colnames(X) = c(1:ncol(X))
-  X = as.matrix(X)
-  if (highBound != -1) {
-    for (i in 1:nrow(X)) {
-      myIndex = which(X[i, ] > highBound)
-      X[i, myIndex] = highBound
-    }
-  }
-  if (lowBound != -1) {
-    for (i in 1:nrow(X)) {
-      myIndex = which(X[i, ] < lowBound)
-      X[i, myIndex] = lowBound
-    }
-  }
-  if (is.null(groupLabel)) {
-    groupLabel = c(1:nrow(X))
-    groupLabel = as.factor(groupLabel)
-  }
-  else {
-    levels(groupLabel) = c(1:length(levels(groupLabel)))
-  }
-  if (startP == -1) 
-    startP = 1
-  if (endP == -1) 
-    endP = ncol(X)
-  if (is.null(xlab)) {
-    xlab = "index"
-  }
-  if (is.null(ylab)) {
-    ylab = "intensity"
-  }
-  if (is.null(main)) {
-    main = paste(" ", startP + offside, "-", endP + offside)
-  }
-  GraphRange <- c(startP:endP)
-  yn <- X[, GraphRange]
-  if (useLog != -1) 
-    yn = log(yn)
-  if (length(yn) > ncol(X))
-  {
-    plot(yn[1, ], ylim = c(min(yn), max(yn)), type = "n", ylab = ylab, xlab = xlab, main = main, xaxt = "n")
-    tempVal = trunc(length(GraphRange)/nAxisPos)
-    xPos = c(0:nAxisPos) * tempVal
-    axis(1, at = xPos, labels = colnames(X)[xPos + startP + offside])
-    for (i in 1:length(levels(groupLabel))) 
-    {
-      groupLabelIdx = which(groupLabel == levels(groupLabel)[i])
-      color <- palette(rainbow(length(levels(groupLabel))))
-      for (j in 1:length(groupLabelIdx)) 
-      {
-        lines(yn[groupLabelIdx[j], ], col = color[i])
-      }
-    }
-    if (!is.null(groupLabel_name)) 
-    {
-      legendPos = "topleft"
-      legend(legendPos, levels(groupLabel_name), col = as.integer(levels(groupLabel)), text.col = "black", pch = c(19, 19), bg = "gray90")
-    }
-  }
-  if (length(yn) == ncol(X))
-  {
-    plot(yn, ylim = c(min(yn), max(yn)), type = "n", ylab = ylab, xlab = xlab, main = main, xaxt = "n")
-    tempVal = trunc(length(GraphRange)/nAxisPos)
-    xPos = c(0:nAxisPos) * tempVal
-#    axis(1, at = xPos, labels = xPos + startP + offside)
-    axis(1, at = xPos, labels = colnames(X)[xPos + startP + offside])
-    lines(yn)
-  }
-}
\ No newline at end of file
b
diff -r c54c70af216b -r 62c62e31fc80 nmr_bucketing/MANUAL_INSTALL.txt
--- a/nmr_bucketing/MANUAL_INSTALL.txt Thu Apr 20 06:34:51 2017 -0400
+++ /dev/null Thu Jan 01 00:00:00 1970 +0000
b
@@ -1,59 +0,0 @@
-Instructions to integrate the "NMR bucketing" tool into a local instance of Galaxy
-Version February 2015 M Tremblay-Franco
-
-
-## --- R bin and Packages : --- ##
-R version 3.0.2 (2013-09-25) -- "Frisbee Sailing"
-Platform: x86_64-redhat-linux-gnu (64-bit)
-
-Install the "batch" library, necessary for parseCommandArgs function and the "pracma" library, nessecary for cumtrapz function:
- - Download package source (*.tar.gz file) from your favorite CRAN (http://www.r-project.org/)
-For example: http://cran.univ-lyon1.fr/
-
- - Install package in your R session
-install.packages("path/package_name.tar.gz",lib="path",repos=NULL)
-For Example: install.packages("/usr/lib64/R/library/pracma_1.8.3.tar",lib="/usr/lib64/R/library",repos=NULL)
-
- - Finally, load the package into your R session
-library(batch)
-library(pracma)
-
-
-## --- Config : --- ##
- - Edit the file "/galaxy/dist/galaxy-dist/tool_conf.xml" and add 
-<section id="id_name" name="Name">
-  <tool file="path/NmrBucketing_xml.xml" />
-</section>
-to create a new section containing the NMR_Bucketing tool
-or add
-  <tool file="path/NmrBucketing_xml.xml" />
-in an existing section
-
- - Put the three files NmrBucketing_xml.xml, NmrBucketing_wrapper.R and NmrBucketing_script.R in a same directory
-For example, path=/galaxy/dist/galaxy-dist/tools/stats
-
- - Edit the NmrBucketing_xml.xml file and change the path in the following lines
-    # R script
-    R --vanilla --slave --no-site-file --file=path/NmrBucketing_wrapper.R --args
-    
-    ## Library name for raw files storage
-    library path/$library
-
-## --- XML help part --- ##
-one image: 
-Copy the 'Mth_Architecture_Repertoire_Bruker.png' file within the directory to your galaxy-dist/static/images/
-
-
- - Activate the "user_library_import_dir" in your /galaxy/dist/galaxy-dist/universe_wsgi.ini and create the users directories in this path, for example:
-
- #In universe_wsgi.ini
-  user_library_import_dir = /projet/sbr/galaxy/import/user
-
- #Create the user "myaccount" in this path
-
- User path: /projet/sbr/galaxy/import/user/myaccount@sb-roscoff.fr
-
-
-
-
-Finally, restart Galaxy
\ No newline at end of file
b
diff -r c54c70af216b -r 62c62e31fc80 nmr_bucketing/NmrBucketing_script.R
--- a/nmr_bucketing/NmrBucketing_script.R Thu Apr 20 06:34:51 2017 -0400
+++ /dev/null Thu Jan 01 00:00:00 1970 +0000
[
b'@@ -1,273 +0,0 @@\n-################################################################################################\r\n-# SPECTRA BUCKETING AND INTEGRATION FROM RAW BRUKER FILES                                      #\r\n-# User : Galaxy                                                                                #\r\n-# Original data : --                                                                           #\r\n-# Starting date : 20-10-2014                                                                   #\r\n-# Version 1 : 18-12-2014                                                                       #\r\n-# Version 2 : 07-01-2015                                                                       #\r\n-# Version 3 : 24-10-2016                                                                       #\r\n-#                                                                                              #\r\n-# Input files : modification on october 2016                                                   #\r\n-#   - Raw bruker files included in user-defined fileName                                      #\r\n-#   - Preprocessed files (alignment, ...) included in p x n dataframe                          #\r\n-################################################################################################\r\n-NmrBucketing <- function(fileType,fileName,leftBorder = 10.0,rightBorder = 0.5,bucketSize = 0.04,exclusionZones,\r\n-                         exclusionZonesBorders=NULL,graph=c("None","Overlay","One_per_individual"),\r\n-                         nomFichier,savLog.txtC = NULL) \r\n-{\r\n-  ## Option\r\n-  ##---------------\r\n-  strAsFacL <- options()$stringsAsFactors\r\n-  options(stingsAsFactors = FALSE)\r\n-  options(warn = -1)\r\n-  \r\n-  \r\n-  ## Constants\r\n-  ##---------------\r\n-  topEnvC <- environment()\r\n-  flgC <- "\\n"\r\n-  \r\n-  ## Log file (in case of integration into Galaxy)\r\n-  ##----------------------------------------------\r\n-  if(!is.null(savLog.txtC))\r\n-    sink(savLog.txtC, append = TRUE)\r\n-  \r\n-  ## Functions definition\r\n-  ##---------------------  \r\n-    ## RAW BRUKER FILE READING FUNCTION\r\n-  NmRBrucker_read <- function(DataDir,SampleSpectrum)\r\n-  {\r\n-    \r\n-    bruker.get_param <- function (ACQ,paramStr)\r\n-    {\r\n-      regexpStr <- paste("^...",paramStr,"=",sep="")\r\n-      as.numeric(gsub("^[^=]+= ","" ,ACQ[which(simplify2array(regexpr(regexpStr,ACQ))>0)]))\r\n-    }\r\n-    \r\n-    ACQFILE <- "acqus"\r\n-    SPECFILE <- paste(DataDir,"/1r",sep="")\r\n-    PROCFILE <- paste(DataDir,"/procs",sep="")\r\n-    \r\n-    ACQ <- readLines(ACQFILE)\r\n-    TD      <- bruker.get_param(ACQ,"TD")\r\n-    SW      <- bruker.get_param(ACQ,"SW")\r\n-    SWH     <- bruker.get_param(ACQ,"SW_h")\r\n-    DTYPA   <- bruker.get_param(ACQ,"DTYPA")\r\n-    BYTORDA <- bruker.get_param(ACQ,"BYTORDA")\r\n-    #ENDIAN = ifelse( BYTORDA==0, "little", "big")\r\n-    ENDIAN <- "little"\r\n-    SIZE = ifelse( DTYPA==0, 4, 8)\r\n-    \r\n-    PROC <- readLines(PROCFILE)\r\n-    OFFSET <- bruker.get_param(PROC,"OFFSET")\r\n-    SI <- bruker.get_param(PROC,"SI")\r\n-    \r\n-    to.read = file(SPECFILE,"rb")\r\n-    maxTDSI = max(TD,SI)\r\n-    #  signal<-rev(readBin(to.read, what="int",size=SIZE, n=TD, signed = TRUE, endian = ENDIAN))\r\n-    signal<-rev(readBin(to.read, what="int",size=SIZE, n=maxTDSI, signed = TRUE, endian = ENDIAN))\r\n-    close(to.read)\r\n-    \r\n-    td <- length(signal)\r\n-    \r\n-    #  dppm <- SW/(TD-1)\r\n-    dppm <- SW/(td-1)\r\n-    pmax <- OFFSET\r\n-    pmin <- OFFSET - SW\r\n-    ppmseq <- seq(from=pmin, to=pmax, by=dppm)\r\n-    signal <- 100*signal/max(signal)\r\n-    \r\n-    SampleSpectrum <- cbind(ppmseq,signal)\r\n-    return(SampleSpectrum)\r\n-  }\r\n-  \r\n-    ## SPECTRUM BUCKETING\r\n-  NmrBrucker_bucket <- function(spectrum)\r\n-  {\r\n-    # Initialisations\r\n-    b <- 1\r\n-    j <- 1\r\n-    # Variable number\r\n-    J <- round((spectrum[1,1]-spectrum[dim(spectrum)[1],1])/bucketSize)\r\n-    f.bucket <- matrix(rep(0,J*2),ncol=2)\r\n-    colnames(f.bucket) <- c("Bucket",FileNames[i])\r\n-    \r\n-    \r\n-    # Data bucketing\r\n-'..b'Names <- list.files(fileName)\r\n-    n <- length(FileNames)\r\n-    \r\n-    # Reading and Bucketing\r\n-    fileName <- paste(fileName,"/",sep="")\r\n-  \r\n-    i <- 1\r\n-    while (i <= n)\r\n-    {\r\n-      # File reading\r\n-      SampleDir <- paste(fileName,FileNames[i],"/1/",sep="")\r\n-      setwd(SampleDir)\r\n-      DataDir <- "pdata/1"\r\n-  \r\n-      rawSpectrum <- NmRBrucker_read(DataDir,rawSpectrum)\r\n-  \r\n-      orderedSpectrum <- rawSpectrum[order(rawSpectrum[,1],decreasing=T), ]\r\n-      \r\n-      # Removal of chemical shifts > leftBorder or < rightBorder boundaries\r\n-      truncatedSpectrum <- orderedSpectrum[orderedSpectrum[,1] < leftBorder & orderedSpectrum[,1] > rightBorder, ]\r\n-      truncatedSpectrum[,1] <- round(truncatedSpectrum[,1],3)\r\n-      \r\n-      # Bucketing\r\n-      spectrum.bucket <- NmrBrucker_bucket(truncatedSpectrum)\r\n-      ppm <- spectrum.bucket[,1]\r\n-      \r\n-      # spectrum Concatenation\r\n-      if (i == 1)\r\n-        bucketedSpectra <- spectrum.bucket\r\n-      if (i > 1)\r\n-        bucketedSpectra <- cbind(bucketedSpectra,spectrum.bucket[,2])\r\n-      colnames(bucketedSpectra)[i+1] <- FileNames[i]\r\n-      \r\n-      # Next sample\r\n-      rm(spectrum.bucket)\r\n-      i <- i +1\r\n-    }\r\n-    # Directory\r\n-    cd(fileName)  \r\n-  }\r\n-  \r\n-  ## Inputs from dataset (preprocessed files)\r\n-  if (fileType=="tsv")\r\n-  {\r\n-    FileNames <- colnames(fileName)\r\n-    n <- length(FileNames)\r\n-    \r\n-    for (i in 1:ncol(fileName))\r\n-    {\r\n-      orderedSpectrum <- cbind(as.numeric(rownames(fileName)),fileName[,i])\r\n-      orderedSpectrum <- orderedSpectrum[order(orderedSpectrum[,1],decreasing=T), ]\r\n-      \r\n-      truncatedSpectrum <- orderedSpectrum[orderedSpectrum[,1] < leftBorder & orderedSpectrum[,1] > rightBorder, ]\r\n-      truncatedSpectrum[,1] <- round(truncatedSpectrum[,1],3)\r\n-      \r\n-      # Bucketing\r\n-      spectrum.bucket <- NmrBrucker_bucket(truncatedSpectrum)\r\n-      ppm <- spectrum.bucket[,1]\r\n-      \r\n-      # spectrum Concatenation\r\n-      if (i == 1)\r\n-        bucketedSpectra <- spectrum.bucket\r\n-      if (i > 1)\r\n-        bucketedSpectra <- cbind(bucketedSpectra,spectrum.bucket[,2])\r\n-      colnames(bucketedSpectra)[i+1] <- colnames(fileName)[i]\r\n-    }\r\n-  }\r\n-  \r\n-  identifiants <- gsub("([- , * { } | \\\\[ ])","_",colnames(bucketedSpectra)[-1])\r\n-  colnames(bucketedSpectra) <- c(colnames(bucketedSpectra)[1],identifiants)\r\n-\r\n-  bucketedSpectra <- bucketedSpectra[bucketedSpectra[,1]!=0,]\r\n-  rownames(bucketedSpectra) <- paste("B",bucketedSpectra[,1],sep="")\r\n-  bucketedSpectra <- bucketedSpectra[,-1]\r\n-  \r\n-  # Metadata matrice outputs\r\n-  sampleMetadata <- data.frame(1:n)\r\n-  rownames(sampleMetadata) <- colnames(bucketedSpectra)\r\n-  colnames(sampleMetadata) <- "SampleOrder"\r\n-  \r\n-  variableMetadata <- data.frame(1:nrow(bucketedSpectra))\r\n-  rownames(variableMetadata) <- rownames(bucketedSpectra)\r\n-  colnames(variableMetadata) <- "VariableOrder"\r\n-\r\n-\r\n-  return(list(bucketedSpectra,sampleMetadata,variableMetadata,ppm)) # ,truncatedSpectrum_matrice\r\n-}\r\n-\r\n-\r\n-#################################################################################################################\r\n-## Typical function call\r\n-#################################################################################################################\r\n-## StudyDir <- "K:/PROJETS/Metabohub/Bruker/Tlse_BPASourisCerveau/"\r\n-## upper <- 9.5\r\n-## lower <- 0.8\r\n-## bucket.width <- 0.01\r\n-## exclusion <- TRUE\r\n-## exclusion.zone <- list(c(5.1,4.5))\r\n-## graphique <- "Overlay"\r\n-## nomFichier <- "Tlse_BPASourisCerveau_NmrBucketing_graph.pdf"\r\n-## tlse_cerveaupnd21.bucket <- NmrBucketing(StudyDir,upper,lower,bucket.width,exclusion,exclusion.zone,graphique,nomFichier)\r\n-## write.table(tlse_cerveaupnd21.bucket,file=paste(StudyDir,"Tlse_BPASourisCerveau_NmrBucketing_dataMatrix.tsv",sep=""),\r\n-##             quote=FALSE,row.nmaes=FALSE,sep="\\t")\r\n-#################################################################################################################\r\n'
b
diff -r c54c70af216b -r 62c62e31fc80 nmr_bucketing/NmrBucketing_wrapper.R
--- a/nmr_bucketing/NmrBucketing_wrapper.R Thu Apr 20 06:34:51 2017 -0400
+++ /dev/null Thu Jan 01 00:00:00 1970 +0000
[
b'@@ -1,295 +0,0 @@\n-#!/usr/local/public/bin/Rscript --vanilla --slave --no-site-file\r\n-\r\n-## 070115_NmrBucketing2galaxy_v1.R\r\n-## Marie Tremblay-Franco\r\n-## MetaboHUB: The French Infrastructure for Metabolomics and Fluxomics\r\n-## www.metabohub.fr/en\r\n-## marie.tremblay-franco@toulouse.inra.fr\r\n-\r\n-runExampleL <- FALSE\r\n-\r\n-if(runExampleL) {\r\n-##------------------------------\r\n-## Example of arguments\r\n-##------------------------------\r\n-argLs <- list(StudyDir = "Tlse_BPASourisCerveau",\r\n-              upper = "10.0",\r\n-              lower = "0.50",\r\n-              bucket.width = "0.01",\r\n-              exclusion = "TRUE",\r\n-              exclusion.zone = list(c(6.5,4.5)),\r\n-              graph="Overlay")\r\n-\r\n-argLs <- c(argLs,\r\n-           list(dataMatrixOut = paste(directory,"_NmrBucketing_dataMatrix.tsv",sep=""),\r\n-                sampleMetadataOut = paste(directory,"_NmrBucketing_sampleMetadata.tsv",sep=""),\r\n-                variableMetadataOut = paste(directory,"_NmrBucketing_variableMetadata.tsv",sep=""),\r\n-                graphOut = paste(directory,"_NmrBucketing_graph.pdf",sep=""),\r\n-                logOut = paste(directory,"_NmrBucketing_log.txt",sep="")))\r\n-}\r\n-\r\n-##------------------------------\r\n-## Options\r\n-##------------------------------\r\n-strAsFacL <- options()$stringsAsFactors\r\n-options(stringsAsFactors = FALSE)\r\n-\r\n-\r\n-##------------------------------\r\n-## Libraries laoding\r\n-##------------------------------\r\n-# For parseCommandArgs function\r\n-library(batch)\r\n-# For cumtrapz function\r\n-library(pracma)\r\n-\r\n-# R script call\r\n-source_local <- function(fname)\r\n-{\r\n-\targv <- commandArgs(trailingOnly = FALSE)\r\n-\tbase_dir <- dirname(substring(argv[grep("--file=", argv)], 8))\r\n-\tsource(paste(base_dir, fname, sep="/"))\r\n-}\r\n-#Import the different functions\r\n-source_local("NmrBucketing_script.R")\r\n-source_local("DrawSpec.R")\r\n-\r\n-##------------------------------\r\n-## Errors ?????????????????????\r\n-##------------------------------\r\n-\r\n-\r\n-##------------------------------\r\n-## Constants\r\n-##------------------------------\r\n-topEnvC <- environment()\r\n-flagC <- "\\n"\r\n-\r\n-\r\n-##------------------------------\r\n-## Script\r\n-##------------------------------\r\n-if(!runExampleL)\r\n-    argLs <- parseCommandArgs(evaluate=FALSE)\r\n-\r\n-\r\n-## Parameters Loading\r\n-##-------------------\r\n-  # Inputs\r\n-if (!is.null(argLs[["zipfile"]])){\r\n-\tfileType="zip"\r\n-\tzipfile= argLs[["zipfile"]]\r\n-\tdirectory=unzip(zipfile, list=F)\r\n-\tdirectory=paste(getwd(),strsplit(directory[1],"/")[[1]][2],sep="/")\r\n-} else if (!is.null(argLs[["tsvfile"]])){\r\n-\tfileType="tsv"\r\n-\tdirectory <- read.table(argLs[["tsvfile"]],check.names=FALSE,header=TRUE,sep="\\t")\r\n-}\r\n-\r\n-leftBorder <- argLs[["left_border"]]\r\n-rightBorder <- argLs[["right_border"]]\r\n-bucketSize <- argLs[["bucket_width"]]\r\n-exclusionZones <- argLs[["zone_exclusion_choices.choice"]]\r\n-\r\n-exclusionZonesBorders <- NULL\r\n-if (!is.null(argLs$zone_exclusion_left))\r\n-{\r\n-   for(i in which(names(argLs)=="zone_exclusion_left"))\r\n-   {\r\n-     exclusionZonesBorders <- c(exclusionZonesBorders,list(c(argLs[[i]],argLs[[i+1]])))\r\n-   }\r\n-}\r\n-\r\n-graphique <- argLs[["graphType"]]\r\n-\r\n-  # Outputs\r\n-nomGraphe <- argLs[["graphOut"]]\r\n-dataMatrixOut <- argLs[["dataMatrixOut"]]\r\n-logFile <- argLs[["logOut"]]\r\n-if (fileType=="zip")\r\n-{\r\n-  sampleMetadataOut <- argLs[["sampleOut"]]\r\n-  variableMetadataOut <- argLs[["variableOut"]]\r\n-}\r\n-\r\n-## Checking arguments\r\n-##-------------------\r\n-error.stock <- "\\n"\r\n-\r\n-if(length(error.stock) > 1)\r\n-  stop(error.stock)\r\n-\r\n-\r\n-## Computation\r\n-##------------\r\n-outputs <- NmrBucketing(fileType=fileType, fileName=directory, leftBorder=leftBorder, rightBorder=rightBorder, bucketSize=bucketSize,\r\n-\t\t\t\t\t\texclusionZones=exclusionZones, exclusionZonesBorders=exclusionZonesBorders, graph=graphique, nomFichier=nomGraphe,\r\n-\t\t\t\t\t\tsavLog.txtC=logFile)\r\n-data_bucket <- outputs[[1]]\r\n-data_sample <- outputs[[2]]\r\n-data_variable <- outputs[[3]]\r\n-ppm <- outputs[[4]]\r\n-ppm <- round(ppm,2)\r\n-\r\n-## G'..b'):nrow(data_bucket),]))\r\n-      drawSpec(spectra,xlab="", ylab="Intensity", main="")\r\n-    }\r\n-  }\r\n-  else\r\n-  {\r\n-    for (i in 1:ncol(data_bucket))\r\n-    {\r\n-      par(mfrow=c((nbZones+2),1))\r\n-      n <- length(excludedZone)\r\n-      spectra <- t(data_bucket[,i])\r\n-\t  names(spectra) <- rownames(data_bucket)\r\n-      plot(1:length(spectra), spectra, type=\'l\', xlab="", ylab="Intensity", main=colnames(data_bucket)[i], xaxt = "n")\r\n-\t  xPos <- 1\r\n-\t  nAxisPos <- 4\r\n-\t  startP <- length(nAxisPos) \r\n-\t  endP <- nrow(data_bucket)\r\n-\t  GraphRange <- c(startP:endP)\r\n-\t  tempVal = trunc(length(GraphRange)/nAxisPos)\r\n-\t  xPos = c(0:nAxisPos) * tempVal\r\n-\t  axis(1, at = xPos, labels = rownames(data_bucket)[xPos + startP])\r\n-     \r\n-      ## Zoomed spectral window depending on exclusion zone(s)\r\n-      if (nbZones != 0)\r\n-      {\r\n-        BInf <- excludedZone[n]\r\n-        if (round(BInf,1) == BInf)\r\n-        {\r\n-          BInf <- BInf+0.01\r\n-        }\r\n-        spectra <- t(data_bucket[1:(which(ppm == BInf)[[1]]),i])\r\n-\t\tnames(spectra) <- rownames(data_bucket)[1:(which(ppm == BInf)[[1]])]\r\n-\t\tplot(1:length(spectra), spectra, type=\'l\',xlab="", ylab="Intensity", main="", xaxt = "n")\t\t\t\r\n-\t\txPos <- 1\r\n-\t\tnAxisPos <- 4\r\n-\t\tstartP <- length(nAxisPos) \r\n-\t\tendP <- length(spectra)\r\n-\t\tGraphRange <- c(startP:endP)\r\n-\t\ttempVal = trunc(length(GraphRange)/nAxisPos)\r\n-\t\txPos = c(0:nAxisPos) * tempVal\r\n-\t\taxis(1, at = xPos, labels = rownames(data_bucket)[xPos + startP])\r\n-        n <- n - 1\r\n-        \r\n-        while (n >= nbZones & nbZones > 1)\r\n-        {\r\n-          BInf <- excludedZone[n-1]\r\n-          if (round(BInf,1) > BInf)\r\n-          {\r\n-            BInf <- BInf+0.01\r\n-          }\r\n-          spectra <- t(data_bucket[(which(ppm == excludedZone[n])[[1]]):(which(ppm == BInf)[[1]]),i])\r\n-\t\t  names(spectra) <- rownames(data_bucket)[(which(ppm == excludedZone[n])[[1]]):(which(ppm == BInf)[[1]])]\r\n-          plot(1:length(spectra), spectra, type=\'l\',xlab="", ylab="Intensity", main="", xaxt = "n")\r\n-\t\t  xPos <- 1\r\n-\t\t  nAxisPos <- 4\r\n-\t\t  startP <- length(nAxisPos) \r\n-\t\t  endP <- length(spectra)\r\n-\t\t  GraphRange <- c(startP:endP)\r\n-\t\t  tempVal = trunc(length(GraphRange)/nAxisPos)\r\n-\t\t  xPos = c(0:nAxisPos) * tempVal\r\n-\t\t  axis(1, at = xPos, labels = rownames(data_bucket)[xPos + startP])\r\n-          n <- n - 2\r\n-        }\r\n-        \r\n-        BInf <- excludedZone[1]\r\n-        if (round(BInf,1) <= BInf)\r\n-        {\r\n-          BInf <- BInf+0.01\r\n-        }\r\n-        spectra <- t(data_bucket[(which(ppm == BInf)[[1]]):nrow(data_bucket),i])\r\n-\t\tnames(spectra) <- rownames(data_bucket)[(which(ppm == BInf)[[1]]):nrow(data_bucket)]\r\n-        plot(1:length(spectra), spectra, type=\'l\',xlab="", ylab="Intensity", main="", xaxt = "n")\r\n-\t\txPos <- 1\r\n-\t\tnAxisPos <- 4\r\n-\t\tstartP <- length(nAxisPos) \r\n-\t\tendP <- length(spectra)\r\n-\t\tGraphRange <- c(startP:endP)\r\n-\t\ttempVal = trunc(length(GraphRange)/nAxisPos)\r\n-\t\txPos = c(0:nAxisPos) * tempVal\r\n-\t\taxis(1, at = xPos, labels = rownames(data_bucket)[xPos + startP])\r\n-      }\r\n-    }\r\n-  }\r\n-  dev.off()\r\n-}\r\n-## Saving\r\n-##-------\r\n-  # Data\r\n-data_bucket <- cbind(rownames(data_bucket),data_bucket)\r\n-colnames(data_bucket) <- c("Bucket",colnames(data_bucket)[-1])\r\n-write.table(data_bucket,file=argLs$dataMatrixOut,quote=FALSE,row.names=FALSE,sep="\\t")\r\n-  # Sample\r\n-data_sample <- cbind(rownames(data_sample),data_sample)\r\n-colnames(data_sample) <- c("Sample",colnames(data_sample)[-1])\r\n-write.table(data_sample,file=argLs$sampleOut,quote=FALSE,row.names=FALSE,sep="\\t")\r\n-  # Variable\r\n-data_variable <- cbind(rownames(data_variable),data_variable)\r\n-colnames(data_variable) <- c("Bucket",colnames(data_variable)[-1])\r\n-write.table(data_variable,file=argLs$variableOut,quote=FALSE,row.names=FALSE,sep="\\t")\r\n-\r\n-\r\n-## Ending\r\n-##---------------------\r\n-\r\n-cat("\\nEnd of \'NMR bucketing\' Galaxy module call: ", as.character(Sys.time()), sep = "")\r\n-\r\n-## sink(NULL)\r\n-\r\n-options(stringsAsFactors = strAsFacL)\r\n-\r\n-rm(list = ls())\r\n'
b
diff -r c54c70af216b -r 62c62e31fc80 nmr_bucketing/NmrBucketing_xml.xml
--- a/nmr_bucketing/NmrBucketing_xml.xml Thu Apr 20 06:34:51 2017 -0400
+++ /dev/null Thu Jan 01 00:00:00 1970 +0000
b
b'@@ -1,293 +0,0 @@\n-<tool id="NmrBucketing" name="NMR_Bucketing" version="1.0.3">\r\n-\r\n-    <description> Bucketing and integration of NMR Bruker raw data</description>\r\n-\r\n-    <requirements>\r\n-\t    <requirement type="package" version="1.1_4">r-batch</requirement>\r\n-\t    <requirement type="package" version="1.8.8">r-pracma</requirement>\r\n-    </requirements>\r\n-\r\n-    <stdio>\r\n-        <exit_code range="1:" level="fatal" />\r\n-    </stdio>\r\n-\r\n-    <command>\r\n-        Rscript \'$__tool_directory__/NmrBucketing_wrapper.R\'\r\n-\r\n-        #if $inputs.input == "tsv_file":\r\n-            tsvfile \'$inputs.tsv_file\'\r\n-        #elif $inputs.input == "zip_file":\r\n-            zipfile \'$inputs.zip_file\'\r\n-        #end if\r\n-\r\n-\r\n-        ## Bucket width\r\n-        bucket_width $bucket_width\r\n-\r\n-        ## Spectra borders\r\n-        left_border $left_border\r\n-        right_border $right_border\r\n-\r\n-\r\n-        ## Spectra representation\r\n-        graphType $graphType\r\n-\r\n-        ## Exclusion zone\r\n-        zone_exclusion_choices.choice ${zone_exclusion_choices.choice}\r\n-        #if str($zone_exclusion_choices.choice) == \'yes\':\r\n-            #for $i in $zone_exclusion_choices.conditions:\r\n-                zone_exclusion_left ${i.zone_exclusion_left}\r\n-                zone_exclusion_right ${i.zone_exclusion_right}\r\n-            #end for\r\n-        #end if\r\n-\r\n-        ## Outputs\r\n-        logOut log.log\r\n-        dataMatrixOut \'$dataMatrixOut\'\r\n-        sampleOut \'$sampleOut\'\r\n-        variableOut \'$variableOut\'\r\n-        graphOut \'$graphOut\'; cat log.log\r\n-    </command>\r\n-\r\n-    <inputs>\r\n-        <conditional name="inputs">\r\n-            <param name="input" type="select" label="Choose your inputs method" >\r\n-                <option value="zip_file" selected="true">Zip file from your history containing your Bruker directories</option>\r\n-                <option value="tsv_file">Tsv file containing preprocessed spectra (from your history)</option>\r\n-            </param>\r\n-            <when value="zip_file">\r\n-                <param name="zip_file" type="data" format="no_unzip.zip" label="Zip file" />\r\n-            </when>\r\n-            <when value="tsv_file">\r\n-                <param name="tsv_file" type="data" format="tabular" label="Tsv file" />\r\n-            </when>\r\n-        </conditional>\r\n-\r\n-        <param name="bucket_width" label="Bucket width" type="float" value="0.04" help="Default value is 0.04 ppm"/>\r\n-\r\n-        <param name="left_border" label="Left Border" type="float" value="10.0" size="10" help="Default value is 10 ppm"/>\r\n-        <param name="right_border" label="Right Border" type="float" value="0.5" size="10" help="Default value is 0.5 ppm"/>\r\n-\r\n-        <conditional name="zone_exclusion_choices">\r\n-            <param name="choice" type="select" label="Exclusion zone(s)" help="Choose if you want to exclude particular zone(s)" >\r\n-                <option value="yes" > yes </option>\r\n-                <option value="no" selected="true"> no </option>\r\n-            </param>\r\n-            <when value="yes">\r\n-                <repeat name="conditions" title="exclusion zones">\r\n-                    <param name="zone_exclusion_left" label="Left exclusion zone border" type="float" value="10.0" />\r\n-                    <param name="zone_exclusion_right" label="Right exclusion zone border" type="float" value="10.0" />\r\n-                </repeat>\r\n-            </when>\r\n-            <when value="no">\r\n-            </when>\r\n-        </conditional>\r\n-\r\n-        <param name="graphType" label="Spectra representation" type="select" help="Select \'None\' for no representation,\'Overlay\' to overlay all spectra on a unique chart and \'One per individual\' to generate an individual chart for each observation">\r\n-            <option value="None"> none </option>\r\n-            <option value="Overlay"> Overlay </option>\r\n-            <option value="One_per_individual"> One_per_individual </option>\r\n-        </param>\r\n-\r\n-    </inputs>\r\n-\r\n-    <outputs>\r\n-   '..b'-------------------+----------------------+--------+\r\n-|                           | variableMetadata.tsv | Tabular|\r\n-+---------------------------+----------------------+--------+\r\n-\r\n-\r\n------------\r\n-Input files\r\n------------\r\n-\r\n-+---------------------------+------------+\r\n-| Parameter : num + label   |   Format   |\r\n-+===========================+============+\r\n-| 1 : Choose your inputs    |   zip      |\r\n-+---------------------------+------------+\r\n-| 1 : Choose your inputs    |   tsv      |\r\n-+---------------------------+------------+\r\n-\r\n-**Choose your inputs**\r\n-\r\n-You have three methods for your inputs:\r\n-\r\n-| Zip file (recommended): You can put a zip file containing your inputs as raw Bruker files: myinputs.zip (containing all your conditions as sub-directories).\r\n-| Tsv file: You can put a tsv file containing your inputs as preprocessed spectra: myinputs.tsv (containing all your conditions in columns and chemical shifts in rows).\r\n-\r\n-.. image:: ./static/images/Mth_Architecture_Repertoire_Bruker.png\r\n-:width: 800\r\n-\r\n-----------\r\n-Parameters\r\n-----------\r\n-\r\n-Bucket width\r\n-| size of windows\r\n-|\r\n-\r\n-Left limit\r\n-| Upper boundary: values greater than this value are not used in the bucketing. Default value is 10.0 ppm\r\n-|\r\n-\r\n-Right limit\r\n-| Lower boundary: values lower than this value are not used in the bucketing. Default value is 0.5 ppm\r\n-|\r\n-\r\n-Exclusion zone(s)\r\n-| Spectral regions to exclude, water, solvents, ... resonance\r\n-| If YES: parameters **Lower exclusion zone** and **Upper exclusion zone** are visible,\r\n-| If NO: no zone to exclude\r\n-| Default value is NO\r\n-|\r\n-\r\n-Left exclusion zone\r\n-| Upper boundary of exclusion zone\r\n-|\r\n-\r\n-Right exclusion zone\r\n-| Lower boundary of exclusion zone\r\n-\r\n-| *Notes:*\r\n-| - these parameters can be used several times using the "Add new exclusion zones" button\r\n-|\r\n-\r\n-Spectra representation:\r\n-| Graphical chart of bucketed and integrated raw files\r\n-| If "Overlay": the n (sample number) spectra are overlaid on the same figure\r\n-| If "One_per_individual": pdf file includes n pages (1 per sample)\r\n-|\r\n-\r\n-\r\n-------------\r\n-Output files\r\n-------------\r\n-\r\n-\r\n-bucketedData.tsv\r\n-| tabular output\r\n-| Data matrix with p rows (buckets) and n columns (samples) containing the intensities\r\n-|\r\n-\r\n-sampleMetadata.tsv\r\n-| tabular output\r\n-| file with n rows (samples) and 2 columns containing sample identifier (rownames) and sample order: the rownames of sampleMetadata must be identical to the colnames of the bucketedData. Can add columns with numeric and/or character sample metadata. This file is optional in the normalization step and mandatory in the statistical analysis step of the workflow.\r\n-|\r\n-\r\n-variableMetadata.tsv\r\n-| tabular output\r\n-| file with p rows (buckets) and 2 columns containing variable identifier (rownames) and bucket order: the rownames of variableMetadata must be identical to the rownames of the bucketedData. Can add columns with numeric and/or character variable metadata. This file is mandatory in the statistical analysis step of the workflow.\r\n-|\r\n-\r\n-spectra.pdf\r\n-| pdf output\r\n-| Graphical chart of bucketed and integrated data\r\n-|\r\n-\r\n-\r\n----------------------------------------------------\r\n-\r\n----------------\r\n-Working example\r\n----------------\r\n-\r\n-\r\n-.. class:: warningmark\r\n-\r\n-Under construction\r\n-\r\n-.. image:: ./static/images/Mth_Travaux.png\r\n-:width: 100\r\n-\r\n----------------------------------------------------\r\n-\r\n-Changelog/News\r\n---------------\r\n-\r\n-**Version 1.0.3 - 24/10/2016**\r\n-\r\n-- ENHANCEMENT: add possibility of bucketing processed files (upstream tools)\r\n-\r\n-**Version 1.0.2 - 12/08/2016**\r\n-\r\n-- ENHANCEMENT: x-axis customization: add chemical shift labels\r\n-\r\n-**Version 1.0.1 - 04/04/2016**\r\n-\r\n-- TEST: refactoring to pass planemo test using conda dependencies\r\n-\r\n-\r\n-**Version 2015-01-08 - 08/01/2015**\r\n-\r\n-    </help>\r\n-    <citations>\r\n-        <citation type="doi">10.1093/bioinformatics/btu813</citation>\r\n-    </citations>\r\n-</tool>\r\n'
b
diff -r c54c70af216b -r 62c62e31fc80 nmr_bucketing/README.rst
--- a/nmr_bucketing/README.rst Thu Apr 20 06:34:51 2017 -0400
+++ /dev/null Thu Jan 01 00:00:00 1970 +0000
b
@@ -1,28 +0,0 @@
-
-Changelog/News
---------------
-
-**Version 1.0.3 - 24/10/2016**
-
-- ENHANCEMENT: add possibility of bucketing processed files (upstream tools)
-
-**Version 1.0.2 - 12/08/2016**
-
-- ENHANCEMENT: x-axis customization: add chemical shift labels 
-
-**Version 1.0.1 - 04/04/2016**
-
-- TEST: refactoring to pass planemo test using conda dependencies
-
-
-**Version 2015-01-08 - 08/01/2015**
-
-
-
-Test Status
------------
-
-Planemo test using conda: passed
-
-Planemo shed_test: passed
-
b
diff -r c54c70af216b -r 62c62e31fc80 nmr_bucketing/planemo_test.sh
--- a/nmr_bucketing/planemo_test.sh Thu Apr 20 06:34:51 2017 -0400
+++ /dev/null Thu Jan 01 00:00:00 1970 +0000
[
@@ -1,12 +0,0 @@
-planemo conda_init
-planemo conda_install .
-planemo test --install_galaxy --conda_dependency_resolution --galaxy_branch "dev"
-
-#All 1 test(s) executed passed.
-#nmr_bucketing[0]: passed
-
-
-planemo shed_test -t testtoolshed --install_galaxy --galaxy_branch "dev"
-
-#All 1 test(s) executed passed.
-#testtoolshed.g2.bx.psu.edu/repos/marie-tremblay-metatoul/nmr_bucketing/NmrBucketing/1.0.1[0]: passed
b
diff -r c54c70af216b -r 62c62e31fc80 nmr_bucketing/repository_dependencies.xml
--- a/nmr_bucketing/repository_dependencies.xml Thu Apr 20 06:34:51 2017 -0400
+++ /dev/null Thu Jan 01 00:00:00 1970 +0000
b
@@ -1,4 +0,0 @@
-<?xml version="1.0"?>
-<repositories>
-    <repository changeset_revision="7800ba9a4c1e" name="no_unzip_datatype" owner="lecorguille" toolshed="https://toolshed.g2.bx.psu.edu" />
-</repositories>
b
diff -r c54c70af216b -r 62c62e31fc80 nmr_bucketing/static/images/MTH - Architecture repertoire Bruker.png
b
Binary file nmr_bucketing/static/images/MTH - Architecture repertoire Bruker.png has changed
b
diff -r c54c70af216b -r 62c62e31fc80 nmr_bucketing/static/images/Mth_Travaux.png
b
Binary file nmr_bucketing/static/images/Mth_Travaux.png has changed
b
diff -r c54c70af216b -r 62c62e31fc80 nmr_bucketing/test-data/MTBLS1.zip
b
Binary file nmr_bucketing/test-data/MTBLS1.zip has changed
b
diff -r c54c70af216b -r 62c62e31fc80 nmr_bucketing/test-data/MTBLS1_bucketedData.tabular
--- a/nmr_bucketing/test-data/MTBLS1_bucketedData.tabular Thu Apr 20 06:34:51 2017 -0400
+++ /dev/null Thu Jan 01 00:00:00 1970 +0000
b
b'@@ -1,595 +0,0 @@\n-Bucket\tADG10003u_007\tADG10003u_008\tADG10003u_009\tADG10003u_010\tADG10003u_015\tADG10003u_016\tADG10003u_017\tADG10003u_021\tADG10003u_022\tADG10003u_023\tADG10003u_051\tADG10003u_052\tADG10003u_053\tADG10003u_066\tADG10003u_067\tADG10003u_071\tADG10003u_072\tADG10003u_073\tADG10003u_087\tADG10003u_088\tADG10003u_089\tADG10003u_097\tADG10003u_098\r\n-B9.295\t1.79949423217956e-06\t1.36845276225836e-05\t2.01160697683997e-05\t7.25986492795804e-07\t2.42490464839257e-05\t3.11580892214512e-05\t8.19866824235026e-06\t3.09192259268499e-05\t2.64389193821353e-05\t1.45055826888266e-05\t3.45040700032625e-06\t1.60970199365859e-05\t1.05993065753594e-05\t2.90248760646802e-05\t1.06130409475137e-05\t5.2278556041205e-06\t2.44519080406605e-05\t3.7420635381202e-05\t1.57230624459948e-05\t2.75224138622866e-06\t2.08828714579133e-05\t5.49917968773367e-05\t8.22464110337308e-06\r\n-B9.286\t0.000183987136571742\t4.73741598311689e-05\t6.48220850387143e-05\t4.08486623139604e-05\t0.000124595459054319\t3.41874426311483e-05\t0.000122371178407348\t3.49547713922308e-05\t0.00015628757744243\t2.37737814473545e-05\t5.13987818577577e-05\t0.000134108924379129\t9.59219627606648e-05\t8.44451844992086e-05\t0.00022720535031565\t9.86157895513715e-05\t1.06199525078497e-05\t3.70983827911379e-05\t3.16119098225048e-05\t5.1709215131723e-06\t2.21703993321988e-05\t1.19479684646357e-05\t8.95607890845055e-06\r\n-B9.276\t6.1185692617288e-05\t0.00020732837726723\t0.00012538786536446\t2.84181782334477e-05\t2.53083682825459e-05\t2.76930477756038e-05\t9.7914592965261e-05\t1.44908072132008e-05\t7.76504143484867e-05\t2.21918164602678e-05\t0.000443221195814841\t0.00034996670727668\t0.000412632862820386\t0.000146364982064243\t0.000101892447453022\t0.00020898968160112\t0.00018589786110267\t0.000307514987819811\t0.000357112398084273\t0.000316352014982079\t0.00021198645013364\t0.000691068949900525\t0.000221146831632783\r\n-B9.266\t4.50617404358542e-05\t7.7187909059995e-06\t1.52411037411529e-05\t1.10253427920853e-05\t4.1745051441984e-05\t3.63488304424524e-05\t3.3290398209022e-05\t1.13169550474572e-05\t9.45184418976979e-06\t7.6012521812347e-06\t6.92482995870393e-06\t3.8268420757911e-05\t2.37195119946984e-06\t2.86004474506151e-05\t3.22860579421692e-06\t2.96039906990133e-06\t2.52808779783966e-05\t0.000142090898957934\t1.10312630129144e-05\t3.60677293639806e-06\t2.97265975382987e-05\t6.66305467846902e-06\t1.14495101906091e-05\r\n-B9.255\t1.15660880406503e-05\t2.14664012391468e-05\t4.60009639329725e-06\t1.25395676678615e-05\t4.17248489153109e-05\t1.46532714803481e-05\t1.00057270405122e-05\t2.75328532847705e-05\t2.74077840472564e-05\t2.41894891121703e-06\t8.0400281246103e-06\t1.59037103857697e-05\t1.00611731499731e-06\t6.71681516896861e-06\t1.36105357122668e-05\t7.11442411954162e-06\t2.21537557041547e-05\t2.87845824558775e-05\t4.03717597605331e-05\t1.42618582461408e-05\t1.84330229833385e-05\t6.39363012853215e-05\t2.18920831381193e-05\r\n-B9.246\t2.03293920474837e-07\t2.02423815996018e-05\t4.96598896737477e-06\t1.35705313106542e-05\t3.41075710581766e-05\t6.53017072634504e-05\t4.43984949390479e-06\t1.63183767828055e-05\t2.72484433555238e-06\t8.78724169594538e-06\t8.95623692386308e-07\t2.45735590368271e-05\t5.26105502709834e-06\t2.37539064007069e-05\t2.19035721346259e-05\t1.50517785846819e-05\t2.16082826646081e-05\t2.53649297518041e-05\t1.32773972605395e-05\t1.00977058894297e-05\t1.55783781762885e-05\t3.76630403674761e-05\t2.14582962168246e-05\r\n-B9.236\t3.37742336734625e-05\t1.09466424044581e-05\t1.26844396116922e-05\t1.41040509503652e-05\t8.32806751647478e-06\t6.89331798338183e-05\t1.31306116922384e-05\t2.44043814312157e-05\t2.60353424850613e-06\t1.5498729364209e-05\t1.12441000124573e-05\t1.90904945628191e-05\t4.77289113406423e-06\t2.6783614160707e-05\t1.81281101162131e-05\t2.27290178082349e-05\t2.2060579242685e-05\t2.02102446881195e-05\t2.82836945109232e-05\t2.6769889759727e-05\t3.20529608453921e-05\t1.46895321061598e-05\t2.72459848898296e-05\r\n-B9.226\t1.02347475703096e-05\t1.61525191983677e-05\t6.32740402153627e-06\t2.17291460045977e-06\t3.58860102752402e-05\t5.32064617047859e-05\t3.88074184844747e-06\t1.41925328605111e-05\t3.61825110992116e-05\t1.56626397248238e-05\t1.488989398'..b'2263392642444\t0.00538943800528357\t0.00514775819006039\t0.00559553789396426\t0.0173520429506117\t0.028324033261543\r\n-B0.876\t0.00215863677466562\t0.00369895246404019\t0.00360045348807487\t0.00134769212206423\t0.00218354336599731\t0.00245532683379321\t0.00345022433982449\t0.000717888096909645\t0.00170401747506495\t0.000356847987108017\t0.0041628951177036\t0.005088145578844\t0.00284987245949532\t0.00268286392210182\t0.00197915272339639\t0.0164744229799929\t0.00871859567919084\t0.0291624658349522\t0.00450433606743076\t0.00467317787458834\t0.00464469278467577\t0.0176322957897126\t0.0298903125539951\r\n-B0.866\t0.00150013418482023\t0.00258508360037412\t0.00238111738536749\t0.000983712268869988\t0.00157378746779101\t0.00184741600638927\t0.00259613706860757\t0.000530590445564721\t0.00114218607490948\t0.000297719443003154\t0.00236377135640083\t0.00299039447289031\t0.00169838032153178\t0.00202478720109677\t0.00155237208983581\t0.00506508824735588\t0.00335278099612616\t0.00916049409218431\t0.00304824370929634\t0.0028945285734165\t0.0028543532645478\t0.00397438831823791\t0.00746021084696681\r\n-B0.857\t0.000986962374512856\t0.00174301185204418\t0.00155459274530862\t0.00059744100374567\t0.000946611593982685\t0.00119641009019251\t0.00173321235334005\t0.000356899004924163\t0.000758730491964375\t0.000160811437925477\t0.00152510957100737\t0.00196835887814581\t0.00101457930295155\t0.00150335976451684\t0.00101420955937978\t0.0033735623219071\t0.00210956426055451\t0.00493276854725743\t0.00178283936255044\t0.00165275426730159\t0.00170372495712446\t0.00248870525573775\t0.0039846322834038\r\n-B0.846\t0.000839825601114667\t0.0012769784113784\t0.00110091918664795\t0.000413961172391942\t0.000708888771217311\t0.000778154520699405\t0.00111234240481985\t0.000244663266226838\t0.000484525523691875\t7.68758960306947e-05\t0.000909219126236251\t0.00113056799032888\t0.000631562997579227\t0.00107030332221529\t0.000634580995745331\t0.00106135884542878\t0.000970558123349218\t0.00157698752726719\t0.00109118524592164\t0.0010809000005087\t0.00117405624971632\t0.00104182637112804\t0.00136932315987551\r\n-B0.836\t0.000540291147081289\t0.00110805916107828\t0.000991944918364915\t0.000259305489167024\t0.000414200683547401\t0.000446851710747917\t0.000739324952553648\t0.00014512091218808\t0.000240131270356258\t1.53279187890163e-05\t0.000995779500719967\t0.00117589795062701\t0.000663607401633198\t0.00072607607121414\t0.000348533637762843\t0.000814771690737036\t0.000852228105038011\t0.00106417265964175\t0.00106436355116083\t0.00088998568772594\t0.00115577335390134\t0.000793475313473202\t0.000969704476916626\r\n-B0.826\t0.000439210376659004\t0.000622025753244184\t0.0005877341421479\t0.000201776175879904\t0.000325527630159852\t0.000344597178120722\t0.000468730496980652\t0.000169188243600758\t0.000244354283493434\t1.80591932027473e-05\t0.000645393534597378\t0.00076364124043746\t0.000411619698520102\t0.000416731585656504\t0.000256480294202034\t0.000524752271786902\t0.000676304092825243\t0.000814916554483356\t0.000597779964300897\t0.000807012376046873\t0.000712066733726576\t0.000508127245813254\t0.000691958647587166\r\n-B0.816\t0.000394076959769821\t0.000626251816952311\t0.000644546372165628\t0.000163741793970591\t0.000294493619073591\t0.000396363737760121\t0.000520046367222883\t0.00012853568638618\t0.000243131055493038\t1.18743008584546e-05\t0.000604929046893319\t0.000717510278393041\t0.000373029125568352\t0.000391937364448496\t0.000234261393789731\t0.000523235700797077\t0.000619868853421147\t0.000730622691788109\t0.000640770168804395\t0.000676985988978989\t0.000745527871203007\t0.00061791716531139\t0.000781012740687151\r\n-B0.806\t0.000336785447055572\t0.000470318285990568\t0.000447571911175899\t0.00015477142985862\t0.000254766661248894\t0.000300355488014835\t0.000386815449880438\t0.000128859420585409\t0.000182934749398549\t1.11417886043334e-05\t0.0003939533156056\t0.000417332638774188\t0.000210616293653824\t0.000296880999894829\t0.000120837576055159\t0.00033047173709954\t0.000388172417071423\t0.000450376987152908\t0.000452051328977898\t0.000485123182275246\t0.00047918667429437\t0.000397128925502763\t0.000516124725384787\r\n-B0.8\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\r\n'
b
diff -r c54c70af216b -r 62c62e31fc80 nmr_bucketing/test-data/MTBLS1_sampleMetadata.tabular
--- a/nmr_bucketing/test-data/MTBLS1_sampleMetadata.tabular Thu Apr 20 06:34:51 2017 -0400
+++ /dev/null Thu Jan 01 00:00:00 1970 +0000
b
@@ -1,24 +0,0 @@
-Sample SampleOrder
-ADG10003u_007 1
-ADG10003u_008 2
-ADG10003u_009 3
-ADG10003u_010 4
-ADG10003u_015 5
-ADG10003u_016 6
-ADG10003u_017 7
-ADG10003u_021 8
-ADG10003u_022 9
-ADG10003u_023 10
-ADG10003u_051 11
-ADG10003u_052 12
-ADG10003u_053 13
-ADG10003u_066 14
-ADG10003u_067 15
-ADG10003u_071 16
-ADG10003u_072 17
-ADG10003u_073 18
-ADG10003u_087 19
-ADG10003u_088 20
-ADG10003u_089 21
-ADG10003u_097 22
-ADG10003u_098 23
b
diff -r c54c70af216b -r 62c62e31fc80 nmr_bucketing/test-data/MTBLS1_variableMetadata.tabular
--- a/nmr_bucketing/test-data/MTBLS1_variableMetadata.tabular Thu Apr 20 06:34:51 2017 -0400
+++ /dev/null Thu Jan 01 00:00:00 1970 +0000
b
@@ -1,595 +0,0 @@
-Bucket VariableOrder
-B9.295 1
-B9.286 2
-B9.276 3
-B9.266 4
-B9.255 5
-B9.246 6
-B9.236 7
-B9.226 8
-B9.215 9
-B9.206 10
-B9.196 11
-B9.186 12
-B9.175 13
-B9.165 14
-B9.156 15
-B9.146 16
-B9.135 17
-B9.126 18
-B9.116 19
-B9.106 20
-B9.095 21
-B9.085 22
-B9.076 23
-B9.066 24
-B9.055 25
-B9.046 26
-B9.036 27
-B9.026 28
-B9.015 29
-B9.005 30
-B8.996 31
-B8.986 32
-B8.975 33
-B8.966 34
-B8.956 35
-B8.946 36
-B8.935 37
-B8.925 38
-B8.916 39
-B8.905 40
-B8.895 41
-B8.886 42
-B8.876 43
-B8.865 44
-B8.855 45
-B8.845 46
-B8.836 47
-B8.825 48
-B8.815 49
-B8.806 50
-B8.796 51
-B8.785 52
-B8.775 53
-B8.765 54
-B8.756 55
-B8.745 56
-B8.735 57
-B8.726 58
-B8.716 59
-B8.705 60
-B8.695 61
-B8.685 62
-B8.676 63
-B8.665 64
-B8.655 65
-B8.646 66
-B8.636 67
-B8.625 68
-B8.615 69
-B8.605 70
-B8.596 71
-B8.585 72
-B8.575 73
-B8.565 74
-B8.556 75
-B8.545 76
-B8.535 77
-B8.525 78
-B8.516 79
-B8.505 80
-B8.495 81
-B8.485 82
-B8.476 83
-B8.465 84
-B8.455 85
-B8.445 86
-B8.436 87
-B8.425 88
-B8.415 89
-B8.405 90
-B8.396 91
-B8.385 92
-B8.375 93
-B8.365 94
-B8.356 95
-B8.345 96
-B8.335 97
-B8.325 98
-B8.316 99
-B8.305 100
-B8.295 101
-B8.285 102
-B8.276 103
-B8.265 104
-B8.255 105
-B8.245 106
-B8.236 107
-B8.225 108
-B8.215 109
-B8.205 110
-B8.196 111
-B8.185 112
-B8.175 113
-B8.165 114
-B8.156 115
-B8.145 116
-B8.135 117
-B8.125 118
-B8.116 119
-B8.105 120
-B8.096 121
-B8.086 122
-B8.076 123
-B8.065 124
-B8.056 125
-B8.046 126
-B8.036 127
-B8.025 128
-B8.016 129
-B8.006 130
-B7.996 131
-B7.985 132
-B7.976 133
-B7.966 134
-B7.956 135
-B7.945 136
-B7.936 137
-B7.926 138
-B7.916 139
-B7.905 140
-B7.896 141
-B7.886 142
-B7.876 143
-B7.865 144
-B7.856 145
-B7.846 146
-B7.836 147
-B7.825 148
-B7.816 149
-B7.806 150
-B7.796 151
-B7.785 152
-B7.776 153
-B7.766 154
-B7.756 155
-B7.745 156
-B7.736 157
-B7.726 158
-B7.716 159
-B7.705 160
-B7.696 161
-B7.686 162
-B7.676 163
-B7.665 164
-B7.656 165
-B7.646 166
-B7.636 167
-B7.625 168
-B7.616 169
-B7.606 170
-B7.596 171
-B7.585 172
-B7.575 173
-B7.566 174
-B7.556 175
-B7.545 176
-B7.535 177
-B7.526 178
-B7.516 179
-B7.505 180
-B7.495 181
-B7.486 182
-B7.476 183
-B7.465 184
-B7.455 185
-B7.446 186
-B7.436 187
-B7.425 188
-B7.415 189
-B7.406 190
-B7.396 191
-B7.385 192
-B7.375 193
-B7.366 194
-B7.356 195
-B7.345 196
-B7.335 197
-B7.326 198
-B7.316 199
-B7.305 200
-B7.295 201
-B7.286 202
-B7.275 203
-B7.265 204
-B7.255 205
-B7.246 206
-B7.235 207
-B7.225 208
-B7.216 209
-B7.206 210
-B7.195 211
-B7.185 212
-B7.175 213
-B7.166 214
-B7.155 215
-B7.145 216
-B7.136 217
-B7.126 218
-B7.115 219
-B7.105 220
-B7.096 221
-B7.086 222
-B7.075 223
-B7.065 224
-B7.056 225
-B7.046 226
-B7.035 227
-B7.025 228
-B7.016 229
-B7.006 230
-B6.995 231
-B6.985 232
-B6.976 233
-B6.966 234
-B6.955 235
-B6.945 236
-B6.935 237
-B6.926 238
-B6.915 239
-B6.905 240
-B6.895 241
-B6.886 242
-B6.875 243
-B6.865 244
-B6.855 245
-B6.846 246
-B6.835 247
-B6.825 248
-B6.815 249
-B6.806 250
-B6.795 251
-B6.785 252
-B6.775 253
-B6.766 254
-B6.755 255
-B6.745 256
-B6.735 257
-B6.726 258
-B6.715 259
-B6.705 260
-B6.695 261
-B6.686 262
-B6.675 263
-B6.665 264
-B6.655 265
-B6.646 266
-B6.635 267
-B6.625 268
-B6.615 269
-B6.606 270
-B6.595 271
-B6.585 272
-B6.575 273
-B6.566 274
-B6.555 275
-B6.545 276
-B6.535 277
-B6.526 278
-B6.515 279
-B6.505 280
-B6.495 281
-B6.486 282
-B6.475 283
-B6.466 284
-B6.456 285
-B6.446 286
-B6.435 287
-B6.426 288
-B6.416 289
-B6.406 290
-B6.395 291
-B6.386 292
-B6.376 293
-B6.366 294
-B6.355 295
-B6.346 296
-B6.336 297
-B6.326 298
-B6.315 299
-B6.306 300
-B6.296 301
-B6.286 302
-B6.275 303
-B6.266 304
-B6.256 305
-B6.246 306
-B6.235 307
-B6.226 308
-B6.216 309
-B6.206 310
-B6.195 311
-B6.186 312
-B6.176 313
-B6.166 314
-B6.155 315
-B6.146 316
-B6.136 317
-B6.126 318
-B6.115 319
-B6.106 320
-B6.096 321
-B6.086 322
-B6.075 323
-B6.066 324
-B6.056 325
-B6.046 326
-B6.035 327
-B6.026 328
-B6.016 329
-B6.006 330
-B4.236 331
-B4.226 332
-B4.216 333
-B4.205 334
-B4.196 335
-B4.186 336
-B4.176 337
-B4.165 338
-B4.155 339
-B4.146 340
-B4.136 341
-B4.125 342
-B4.115 343
-B4.106 344
-B4.096 345
-B4.085 346
-B4.075 347
-B4.066 348
-B4.056 349
-B4.045 350
-B4.035 351
-B4.026 352
-B4.015 353
-B4.005 354
-B3.995 355
-B3.186 356
-B3.175 357
-B3.166 358
-B3.156 359
-B3.146 360
-B3.135 361
-B3.126 362
-B3.116 363
-B3.106 364
-B3.095 365
-B3.086 366
-B3.076 367
-B3.066 368
-B3.055 369
-B3.046 370
-B3.036 371
-B3.026 372
-B3.015 373
-B3.006 374
-B2.996 375
-B2.986 376
-B2.975 377
-B2.966 378
-B2.956 379
-B2.946 380
-B2.935 381
-B2.926 382
-B2.916 383
-B2.906 384
-B2.895 385
-B2.886 386
-B2.876 387
-B2.866 388
-B2.855 389
-B2.846 390
-B2.836 391
-B2.826 392
-B2.815 393
-B2.806 394
-B2.796 395
-B2.786 396
-B2.775 397
-B2.766 398
-B2.756 399
-B2.746 400
-B2.735 401
-B2.726 402
-B2.716 403
-B2.706 404
-B2.695 405
-B2.686 406
-B2.676 407
-B2.666 408
-B2.655 409
-B2.646 410
-B2.636 411
-B2.626 412
-B2.615 413
-B2.606 414
-B2.596 415
-B2.586 416
-B2.575 417
-B2.566 418
-B2.556 419
-B2.546 420
-B2.535 421
-B2.526 422
-B2.516 423
-B2.506 424
-B2.495 425
-B2.486 426
-B2.476 427
-B2.466 428
-B2.455 429
-B2.446 430
-B2.436 431
-B2.426 432
-B2.415 433
-B2.406 434
-B2.396 435
-B2.385 436
-B2.375 437
-B2.365 438
-B2.356 439
-B2.345 440
-B2.335 441
-B2.325 442
-B2.316 443
-B2.305 444
-B2.295 445
-B2.285 446
-B2.276 447
-B2.265 448
-B2.255 449
-B2.245 450
-B2.236 451
-B2.225 452
-B2.215 453
-B2.205 454
-B2.196 455
-B2.185 456
-B2.175 457
-B2.165 458
-B2.156 459
-B2.145 460
-B2.135 461
-B2.126 462
-B2.116 463
-B2.105 464
-B2.095 465
-B2.086 466
-B2.076 467
-B2.065 468
-B2.055 469
-B2.045 470
-B2.036 471
-B2.025 472
-B2.015 473
-B2.005 474
-B1.994 475
-B1.985 476
-B1.974 477
-B1.964 478
-B1.954 479
-B1.945 480
-B1.934 481
-B1.924 482
-B1.914 483
-B1.905 484
-B1.894 485
-B1.884 486
-B1.874 487
-B1.865 488
-B1.854 489
-B1.844 490
-B1.834 491
-B1.825 492
-B1.814 493
-B1.804 494
-B1.794 495
-B1.785 496
-B1.774 497
-B1.764 498
-B1.754 499
-B1.743 500
-B1.734 501
-B1.723 502
-B1.713 503
-B1.703 504
-B1.694 505
-B1.683 506
-B1.673 507
-B1.663 508
-B1.654 509
-B1.643 510
-B1.633 511
-B1.623 512
-B1.612 513
-B1.603 514
-B1.592 515
-B1.582 516
-B1.572 517
-B1.563 518
-B1.552 519
-B1.542 520
-B1.532 521
-B1.523 522
-B1.512 523
-B1.502 524
-B1.491 525
-B1.482 526
-B1.472 527
-B1.461 528
-B1.451 529
-B1.442 530
-B1.432 531
-B1.421 532
-B1.411 533
-B1.401 534
-B1.392 535
-B1.381 536
-B1.371 537
-B1.36 538
-B1.351 539
-B1.341 540
-B1.33 541
-B1.32 542
-B1.31 543
-B1.301 544
-B1.29 545
-B1.28 546
-B1.27 547
-B1.261 548
-B1.25 549
-B1.239 550
-B1.229 551
-B1.22 552
-B1.21 553
-B1.199 554
-B1.189 555
-B1.18 556
-B1.17 557
-B1.159 558
-B1.149 559
-B1.139 560
-B1.129 561
-B1.119 562
-B1.108 563
-B1.098 564
-B1.089 565
-B1.079 566
-B1.068 567
-B1.058 568
-B1.048 569
-B1.039 570
-B1.028 571
-B1.018 572
-B1.008 573
-B0.998 574
-B0.988 575
-B0.977 576
-B0.967 577
-B0.958 578
-B0.948 579
-B0.937 580
-B0.926 581
-B0.916 582
-B0.907 583
-B0.897 584
-B0.886 585
-B0.876 586
-B0.866 587
-B0.857 588
-B0.846 589
-B0.836 590
-B0.826 591
-B0.816 592
-B0.806 593
-B0.8 594
b
diff -r c54c70af216b -r 62c62e31fc80 nmr_bucketing/tool_dependencies.xml
--- a/nmr_bucketing/tool_dependencies.xml Thu Apr 20 06:34:51 2017 -0400
+++ /dev/null Thu Jan 01 00:00:00 1970 +0000
b
@@ -1,9 +0,0 @@
-<?xml version="1.0"?>
-<tool_dependency>
-    <package name="R" version="3.1.2">
-        <repository changeset_revision="4d2fd1413b56" name="package_r_3_1_2" owner="iuc" toolshed="https://toolshed.g2.bx.psu.edu" />
-    </package>
-    <package name="r-pracma" version="1.8.8">
- <repository changeset_revision="48eb1ff95b33" name="package_r_pracma_1_8_8" owner="lecorguille" toolshed="https://toolshed.g2.bx.psu.edu" />
-    </package>
-</tool_dependency>
b
diff -r c54c70af216b -r 62c62e31fc80 repository_dependencies.xml
--- /dev/null Thu Jan 01 00:00:00 1970 +0000
+++ b/repository_dependencies.xml Fri Apr 21 08:53:40 2017 -0400
b
@@ -0,0 +1,4 @@
+<?xml version="1.0"?>
+<repositories>
+    <repository changeset_revision="7800ba9a4c1e" name="no_unzip_datatype" owner="lecorguille" toolshed="https://toolshed.g2.bx.psu.edu" />
+</repositories>
b
diff -r c54c70af216b -r 62c62e31fc80 static/images/MTH - Architecture repertoire Bruker.png
b
Binary file static/images/MTH - Architecture repertoire Bruker.png has changed
b
diff -r c54c70af216b -r 62c62e31fc80 static/images/Mth_Travaux.png
b
Binary file static/images/Mth_Travaux.png has changed
b
diff -r c54c70af216b -r 62c62e31fc80 test-data/MTBLS1.zip
b
Binary file test-data/MTBLS1.zip has changed
b
diff -r c54c70af216b -r 62c62e31fc80 test-data/MTBLS1_bucketedData.tabular
--- /dev/null Thu Jan 01 00:00:00 1970 +0000
+++ b/test-data/MTBLS1_bucketedData.tabular Fri Apr 21 08:53:40 2017 -0400
b
b'@@ -0,0 +1,851 @@\n+Bucket\tADG10003u_007\tADG10003u_008\tADG10003u_009\tADG10003u_010\tADG10003u_015\tADG10003u_016\tADG10003u_017\tADG10003u_021\tADG10003u_022\tADG10003u_023\tADG10003u_051\tADG10003u_052\tADG10003u_053\tADG10003u_066\tADG10003u_067\tADG10003u_071\tADG10003u_072\tADG10003u_073\tADG10003u_087\tADG10003u_088\tADG10003u_089\tADG10003u_097\tADG10003u_098\n+B9.295\t1.79949423217956e-06\t1.36845276225836e-05\t2.01160697683997e-05\t7.25986492795804e-07\t2.42490464839257e-05\t3.11580892214512e-05\t8.19866824235026e-06\t3.09192259268499e-05\t2.64389193821353e-05\t1.45055826888266e-05\t3.45040700032625e-06\t1.60970199365859e-05\t1.05993065753594e-05\t2.90248760646802e-05\t1.06130409475137e-05\t5.2278556041205e-06\t2.44519080406605e-05\t3.7420635381202e-05\t1.57230624459948e-05\t2.75224138622866e-06\t2.08828714579133e-05\t5.49917968773367e-05\t8.22464110337308e-06\n+B9.286\t0.000183987136571742\t4.73741598311689e-05\t6.48220850387143e-05\t4.08486623139604e-05\t0.000124595459054319\t3.41874426311483e-05\t0.000122371178407348\t3.49547713922308e-05\t0.00015628757744243\t2.37737814473545e-05\t5.13987818577577e-05\t0.000134108924379129\t9.59219627606648e-05\t8.44451844992086e-05\t0.00022720535031565\t9.86157895513715e-05\t1.06199525078497e-05\t3.70983827911379e-05\t3.16119098225048e-05\t5.1709215131723e-06\t2.21703993321988e-05\t1.19479684646357e-05\t8.95607890845055e-06\n+B9.276\t6.1185692617288e-05\t0.00020732837726723\t0.00012538786536446\t2.84181782334477e-05\t2.53083682825459e-05\t2.76930477756038e-05\t9.7914592965261e-05\t1.44908072132008e-05\t7.76504143484867e-05\t2.21918164602678e-05\t0.000443221195814841\t0.00034996670727668\t0.000412632862820386\t0.000146364982064243\t0.000101892447453022\t0.00020898968160112\t0.00018589786110267\t0.000307514987819811\t0.000357112398084273\t0.000316352014982079\t0.00021198645013364\t0.000691068949900525\t0.000221146831632783\n+B9.266\t4.50617404358542e-05\t7.7187909059995e-06\t1.52411037411529e-05\t1.10253427920853e-05\t4.1745051441984e-05\t3.63488304424524e-05\t3.3290398209022e-05\t1.13169550474572e-05\t9.45184418976979e-06\t7.6012521812347e-06\t6.92482995870393e-06\t3.8268420757911e-05\t2.37195119946984e-06\t2.86004474506151e-05\t3.22860579421692e-06\t2.96039906990133e-06\t2.52808779783966e-05\t0.000142090898957934\t1.10312630129144e-05\t3.60677293639806e-06\t2.97265975382987e-05\t6.66305467846902e-06\t1.14495101906091e-05\n+B9.255\t1.15660880406503e-05\t2.14664012391468e-05\t4.60009639329725e-06\t1.25395676678615e-05\t4.17248489153109e-05\t1.46532714803481e-05\t1.00057270405122e-05\t2.75328532847705e-05\t2.74077840472564e-05\t2.41894891121703e-06\t8.0400281246103e-06\t1.59037103857697e-05\t1.00611731499731e-06\t6.71681516896861e-06\t1.36105357122668e-05\t7.11442411954162e-06\t2.21537557041547e-05\t2.87845824558775e-05\t4.03717597605331e-05\t1.42618582461408e-05\t1.84330229833385e-05\t6.39363012853215e-05\t2.18920831381193e-05\n+B9.246\t2.03293920474837e-07\t2.02423815996018e-05\t4.96598896737477e-06\t1.35705313106542e-05\t3.41075710581766e-05\t6.53017072634504e-05\t4.43984949390479e-06\t1.63183767828055e-05\t2.72484433555238e-06\t8.78724169594538e-06\t8.95623692386308e-07\t2.45735590368271e-05\t5.26105502709834e-06\t2.37539064007069e-05\t2.19035721346259e-05\t1.50517785846819e-05\t2.16082826646081e-05\t2.53649297518041e-05\t1.32773972605395e-05\t1.00977058894297e-05\t1.55783781762885e-05\t3.76630403674761e-05\t2.14582962168246e-05\n+B9.236\t3.37742336734625e-05\t1.09466424044581e-05\t1.26844396116922e-05\t1.41040509503652e-05\t8.32806751647478e-06\t6.89331798338183e-05\t1.31306116922384e-05\t2.44043814312157e-05\t2.60353424850613e-06\t1.5498729364209e-05\t1.12441000124573e-05\t1.90904945628191e-05\t4.77289113406423e-06\t2.6783614160707e-05\t1.81281101162131e-05\t2.27290178082349e-05\t2.2060579242685e-05\t2.02102446881195e-05\t2.82836945109232e-05\t2.6769889759727e-05\t3.20529608453921e-05\t1.46895321061598e-05\t2.72459848898296e-05\n+B9.226\t1.02347475703096e-05\t1.61525191983677e-05\t6.32740402153627e-06\t2.17291460045977e-06\t3.58860102752402e-05\t5.32064617047859e-05\t3.88074184844747e-06\t1.41925328605111e-05\t3.61825110992116e-05\t1.56626397248238e-05\t1.48898939857621e-0'..b'7579\t0.0232263392642444\t0.00538943800528357\t0.00514775819006039\t0.00559553789396426\t0.0173520429506117\t0.028324033261543\n+B0.876\t0.00215863677466562\t0.00369895246404019\t0.00360045348807487\t0.00134769212206423\t0.00218354336599731\t0.00245532683379321\t0.00345022433982449\t0.000717888096909645\t0.00170401747506495\t0.000356847987108017\t0.0041628951177036\t0.005088145578844\t0.00284987245949532\t0.00268286392210182\t0.00197915272339639\t0.0164744229799929\t0.00871859567919084\t0.0291624658349522\t0.00450433606743076\t0.00467317787458834\t0.00464469278467577\t0.0176322957897126\t0.0298903125539951\n+B0.866\t0.00150013418482023\t0.00258508360037412\t0.00238111738536749\t0.000983712268869988\t0.00157378746779101\t0.00184741600638927\t0.00259613706860757\t0.000530590445564721\t0.00114218607490948\t0.000297719443003154\t0.00236377135640083\t0.00299039447289031\t0.00169838032153178\t0.00202478720109677\t0.00155237208983581\t0.00506508824735588\t0.00335278099612616\t0.00916049409218431\t0.00304824370929634\t0.0028945285734165\t0.0028543532645478\t0.00397438831823791\t0.00746021084696681\n+B0.857\t0.000986962374512856\t0.00174301185204418\t0.00155459274530862\t0.00059744100374567\t0.000946611593982685\t0.00119641009019251\t0.00173321235334005\t0.000356899004924163\t0.000758730491964375\t0.000160811437925477\t0.00152510957100737\t0.00196835887814581\t0.00101457930295155\t0.00150335976451684\t0.00101420955937978\t0.0033735623219071\t0.00210956426055451\t0.00493276854725743\t0.00178283936255044\t0.00165275426730159\t0.00170372495712446\t0.00248870525573775\t0.0039846322834038\n+B0.846\t0.000839825601114667\t0.0012769784113784\t0.00110091918664795\t0.000413961172391942\t0.000708888771217311\t0.000778154520699405\t0.00111234240481985\t0.000244663266226838\t0.000484525523691875\t7.68758960306947e-05\t0.000909219126236251\t0.00113056799032888\t0.000631562997579227\t0.00107030332221529\t0.000634580995745331\t0.00106135884542878\t0.000970558123349218\t0.00157698752726719\t0.00109118524592164\t0.0010809000005087\t0.00117405624971632\t0.00104182637112804\t0.00136932315987551\n+B0.836\t0.000540291147081289\t0.00110805916107828\t0.000991944918364915\t0.000259305489167024\t0.000414200683547401\t0.000446851710747917\t0.000739324952553648\t0.00014512091218808\t0.000240131270356258\t1.53279187890163e-05\t0.000995779500719967\t0.00117589795062701\t0.000663607401633198\t0.00072607607121414\t0.000348533637762843\t0.000814771690737036\t0.000852228105038011\t0.00106417265964175\t0.00106436355116083\t0.00088998568772594\t0.00115577335390134\t0.000793475313473202\t0.000969704476916626\n+B0.826\t0.000439210376659004\t0.000622025753244184\t0.0005877341421479\t0.000201776175879904\t0.000325527630159852\t0.000344597178120722\t0.000468730496980652\t0.000169188243600758\t0.000244354283493434\t1.80591932027473e-05\t0.000645393534597378\t0.00076364124043746\t0.000411619698520102\t0.000416731585656504\t0.000256480294202034\t0.000524752271786902\t0.000676304092825243\t0.000814916554483356\t0.000597779964300897\t0.000807012376046873\t0.000712066733726576\t0.000508127245813254\t0.000691958647587166\n+B0.816\t0.000394076959769821\t0.000626251816952311\t0.000644546372165628\t0.000163741793970591\t0.000294493619073591\t0.000396363737760121\t0.000520046367222883\t0.00012853568638618\t0.000243131055493038\t1.18743008584546e-05\t0.000604929046893319\t0.000717510278393041\t0.000373029125568352\t0.000391937364448496\t0.000234261393789731\t0.000523235700797077\t0.000619868853421147\t0.000730622691788109\t0.000640770168804395\t0.000676985988978989\t0.000745527871203007\t0.00061791716531139\t0.000781012740687151\n+B0.806\t0.000336785447055572\t0.000470318285990568\t0.000447571911175899\t0.00015477142985862\t0.000254766661248894\t0.000300355488014835\t0.000386815449880438\t0.000128859420585409\t0.000182934749398549\t1.11417886043334e-05\t0.0003939533156056\t0.000417332638774188\t0.000210616293653824\t0.000296880999894829\t0.000120837576055159\t0.00033047173709954\t0.000388172417071423\t0.000450376987152908\t0.000452051328977898\t0.000485123182275246\t0.00047918667429437\t0.000397128925502763\t0.000516124725384787\n+B0.8\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\t0\n'
b
diff -r c54c70af216b -r 62c62e31fc80 test-data/MTBLS1_sampleMetadata.tabular
--- /dev/null Thu Jan 01 00:00:00 1970 +0000
+++ b/test-data/MTBLS1_sampleMetadata.tabular Fri Apr 21 08:53:40 2017 -0400
b
@@ -0,0 +1,24 @@
+Sample SampleOrder
+ADG10003u_007 1
+ADG10003u_008 2
+ADG10003u_009 3
+ADG10003u_010 4
+ADG10003u_015 5
+ADG10003u_016 6
+ADG10003u_017 7
+ADG10003u_021 8
+ADG10003u_022 9
+ADG10003u_023 10
+ADG10003u_051 11
+ADG10003u_052 12
+ADG10003u_053 13
+ADG10003u_066 14
+ADG10003u_067 15
+ADG10003u_071 16
+ADG10003u_072 17
+ADG10003u_073 18
+ADG10003u_087 19
+ADG10003u_088 20
+ADG10003u_089 21
+ADG10003u_097 22
+ADG10003u_098 23
b
diff -r c54c70af216b -r 62c62e31fc80 test-data/MTBLS1_variableMetadata.tabular
--- /dev/null Thu Jan 01 00:00:00 1970 +0000
+++ b/test-data/MTBLS1_variableMetadata.tabular Fri Apr 21 08:53:40 2017 -0400
b
b'@@ -0,0 +1,851 @@\n+Bucket\tVariableOrder\n+B9.295\t1\n+B9.286\t2\n+B9.276\t3\n+B9.266\t4\n+B9.255\t5\n+B9.246\t6\n+B9.236\t7\n+B9.226\t8\n+B9.215\t9\n+B9.206\t10\n+B9.196\t11\n+B9.186\t12\n+B9.175\t13\n+B9.165\t14\n+B9.156\t15\n+B9.146\t16\n+B9.135\t17\n+B9.126\t18\n+B9.116\t19\n+B9.106\t20\n+B9.095\t21\n+B9.085\t22\n+B9.076\t23\n+B9.066\t24\n+B9.055\t25\n+B9.046\t26\n+B9.036\t27\n+B9.026\t28\n+B9.015\t29\n+B9.005\t30\n+B8.996\t31\n+B8.986\t32\n+B8.975\t33\n+B8.966\t34\n+B8.956\t35\n+B8.946\t36\n+B8.935\t37\n+B8.925\t38\n+B8.916\t39\n+B8.905\t40\n+B8.895\t41\n+B8.886\t42\n+B8.876\t43\n+B8.865\t44\n+B8.855\t45\n+B8.845\t46\n+B8.836\t47\n+B8.825\t48\n+B8.815\t49\n+B8.806\t50\n+B8.796\t51\n+B8.785\t52\n+B8.775\t53\n+B8.765\t54\n+B8.756\t55\n+B8.745\t56\n+B8.735\t57\n+B8.726\t58\n+B8.716\t59\n+B8.705\t60\n+B8.695\t61\n+B8.685\t62\n+B8.676\t63\n+B8.665\t64\n+B8.655\t65\n+B8.646\t66\n+B8.636\t67\n+B8.625\t68\n+B8.615\t69\n+B8.605\t70\n+B8.596\t71\n+B8.585\t72\n+B8.575\t73\n+B8.565\t74\n+B8.556\t75\n+B8.545\t76\n+B8.535\t77\n+B8.525\t78\n+B8.516\t79\n+B8.505\t80\n+B8.495\t81\n+B8.485\t82\n+B8.476\t83\n+B8.465\t84\n+B8.455\t85\n+B8.445\t86\n+B8.436\t87\n+B8.425\t88\n+B8.415\t89\n+B8.405\t90\n+B8.396\t91\n+B8.385\t92\n+B8.375\t93\n+B8.365\t94\n+B8.356\t95\n+B8.345\t96\n+B8.335\t97\n+B8.325\t98\n+B8.316\t99\n+B8.305\t100\n+B8.295\t101\n+B8.285\t102\n+B8.276\t103\n+B8.265\t104\n+B8.255\t105\n+B8.245\t106\n+B8.236\t107\n+B8.225\t108\n+B8.215\t109\n+B8.205\t110\n+B8.196\t111\n+B8.185\t112\n+B8.175\t113\n+B8.165\t114\n+B8.156\t115\n+B8.145\t116\n+B8.135\t117\n+B8.125\t118\n+B8.116\t119\n+B8.105\t120\n+B8.096\t121\n+B8.086\t122\n+B8.076\t123\n+B8.065\t124\n+B8.056\t125\n+B8.046\t126\n+B8.036\t127\n+B8.025\t128\n+B8.016\t129\n+B8.006\t130\n+B7.996\t131\n+B7.985\t132\n+B7.976\t133\n+B7.966\t134\n+B7.956\t135\n+B7.945\t136\n+B7.936\t137\n+B7.926\t138\n+B7.916\t139\n+B7.905\t140\n+B7.896\t141\n+B7.886\t142\n+B7.876\t143\n+B7.865\t144\n+B7.856\t145\n+B7.846\t146\n+B7.836\t147\n+B7.825\t148\n+B7.816\t149\n+B7.806\t150\n+B7.796\t151\n+B7.785\t152\n+B7.776\t153\n+B7.766\t154\n+B7.756\t155\n+B7.745\t156\n+B7.736\t157\n+B7.726\t158\n+B7.716\t159\n+B7.705\t160\n+B7.696\t161\n+B7.686\t162\n+B7.676\t163\n+B7.665\t164\n+B7.656\t165\n+B7.646\t166\n+B7.636\t167\n+B7.625\t168\n+B7.616\t169\n+B7.606\t170\n+B7.596\t171\n+B7.585\t172\n+B7.575\t173\n+B7.566\t174\n+B7.556\t175\n+B7.545\t176\n+B7.535\t177\n+B7.526\t178\n+B7.516\t179\n+B7.505\t180\n+B7.495\t181\n+B7.486\t182\n+B7.476\t183\n+B7.465\t184\n+B7.455\t185\n+B7.446\t186\n+B7.436\t187\n+B7.425\t188\n+B7.415\t189\n+B7.406\t190\n+B7.396\t191\n+B7.385\t192\n+B7.375\t193\n+B7.366\t194\n+B7.356\t195\n+B7.345\t196\n+B7.335\t197\n+B7.326\t198\n+B7.316\t199\n+B7.305\t200\n+B7.295\t201\n+B7.286\t202\n+B7.275\t203\n+B7.265\t204\n+B7.255\t205\n+B7.246\t206\n+B7.235\t207\n+B7.225\t208\n+B7.216\t209\n+B7.206\t210\n+B7.195\t211\n+B7.185\t212\n+B7.175\t213\n+B7.166\t214\n+B7.155\t215\n+B7.145\t216\n+B7.136\t217\n+B7.126\t218\n+B7.115\t219\n+B7.105\t220\n+B7.096\t221\n+B7.086\t222\n+B7.075\t223\n+B7.065\t224\n+B7.056\t225\n+B7.046\t226\n+B7.035\t227\n+B7.025\t228\n+B7.016\t229\n+B7.006\t230\n+B6.995\t231\n+B6.985\t232\n+B6.976\t233\n+B6.966\t234\n+B6.955\t235\n+B6.945\t236\n+B6.935\t237\n+B6.926\t238\n+B6.915\t239\n+B6.905\t240\n+B6.895\t241\n+B6.886\t242\n+B6.875\t243\n+B6.865\t244\n+B6.855\t245\n+B6.846\t246\n+B6.835\t247\n+B6.825\t248\n+B6.815\t249\n+B6.806\t250\n+B6.795\t251\n+B6.785\t252\n+B6.775\t253\n+B6.766\t254\n+B6.755\t255\n+B6.745\t256\n+B6.735\t257\n+B6.726\t258\n+B6.715\t259\n+B6.705\t260\n+B6.695\t261\n+B6.686\t262\n+B6.675\t263\n+B6.665\t264\n+B6.655\t265\n+B6.646\t266\n+B6.635\t267\n+B6.625\t268\n+B6.615\t269\n+B6.606\t270\n+B6.595\t271\n+B6.585\t272\n+B6.575\t273\n+B6.566\t274\n+B6.555\t275\n+B6.545\t276\n+B6.535\t277\n+B6.526\t278\n+B6.515\t279\n+B6.505\t280\n+B6.495\t281\n+B6.486\t282\n+B6.475\t283\n+B6.466\t284\n+B6.456\t285\n+B6.446\t286\n+B6.435\t287\n+B6.426\t288\n+B6.416\t289\n+B6.406\t290\n+B6.395\t291\n+B6.386\t292\n+B6.376\t293\n+B6.366\t294\n+B6.355\t295\n+B6.346\t296\n+B6.336\t297\n+B6.326\t298\n+B6.315\t299\n+B6.306\t300\n+B6.296\t301\n+B6.286\t302\n+B6.275\t303\n+B6.266\t304\n+B6.256\t305\n+B6.246\t306\n+B6.235\t307\n+B6.226\t308\n+B6.216\t309\n+B6.206\t310\n+B6.195\t311\n+B6.186\t312\n+B6.176\t313\n+B6.166\t314\n+B6.155\t315\n+B6.146\t316\n+B6.136\t317\n+B6.126\t318\n+B6.115\t319\n+B6.106\t320\n+B6.096\t321\n+B6.086\t322\n+B6.075\t323\n+B6.066\t324\n+B6.056\t325\n+B6.046\t326\n+B6.035\t327\n+B6.026\t328\n+B6.016\t329\n+B6.006\t330\n+B5.995\t331\n+B5.986\t332\n+B5.976\t333\n+B5.966\t334\n+B5.955\t335\n+B5.946\t336\n+B5.936\t337\n+B5.926\t338\n+B5.915\t339'..b'\t516\n+B4.136\t517\n+B4.125\t518\n+B4.115\t519\n+B4.106\t520\n+B4.096\t521\n+B4.085\t522\n+B4.075\t523\n+B4.066\t524\n+B4.056\t525\n+B4.045\t526\n+B4.035\t527\n+B4.026\t528\n+B4.015\t529\n+B4.005\t530\n+B3.995\t531\n+B3.986\t532\n+B3.975\t533\n+B3.965\t534\n+B3.955\t535\n+B3.946\t536\n+B3.935\t537\n+B3.925\t538\n+B3.915\t539\n+B3.906\t540\n+B3.895\t541\n+B3.885\t542\n+B3.876\t543\n+B3.866\t544\n+B3.855\t545\n+B3.845\t546\n+B3.836\t547\n+B3.826\t548\n+B3.815\t549\n+B3.805\t550\n+B3.796\t551\n+B3.786\t552\n+B3.775\t553\n+B3.765\t554\n+B3.756\t555\n+B3.746\t556\n+B3.735\t557\n+B3.725\t558\n+B3.716\t559\n+B3.706\t560\n+B3.695\t561\n+B3.685\t562\n+B3.675\t563\n+B3.666\t564\n+B3.655\t565\n+B3.645\t566\n+B3.635\t567\n+B3.626\t568\n+B3.615\t569\n+B3.605\t570\n+B3.595\t571\n+B3.586\t572\n+B3.575\t573\n+B3.565\t574\n+B3.555\t575\n+B3.546\t576\n+B3.535\t577\n+B3.525\t578\n+B3.515\t579\n+B3.506\t580\n+B3.495\t581\n+B3.485\t582\n+B3.475\t583\n+B3.466\t584\n+B3.455\t585\n+B3.445\t586\n+B3.435\t587\n+B3.426\t588\n+B3.415\t589\n+B3.405\t590\n+B3.395\t591\n+B3.386\t592\n+B3.375\t593\n+B3.365\t594\n+B3.355\t595\n+B3.346\t596\n+B3.335\t597\n+B3.325\t598\n+B3.315\t599\n+B3.306\t600\n+B3.295\t601\n+B3.285\t602\n+B3.275\t603\n+B3.266\t604\n+B3.255\t605\n+B3.245\t606\n+B3.235\t607\n+B3.226\t608\n+B3.215\t609\n+B3.206\t610\n+B3.196\t611\n+B3.186\t612\n+B3.175\t613\n+B3.166\t614\n+B3.156\t615\n+B3.146\t616\n+B3.135\t617\n+B3.126\t618\n+B3.116\t619\n+B3.106\t620\n+B3.095\t621\n+B3.086\t622\n+B3.076\t623\n+B3.066\t624\n+B3.055\t625\n+B3.046\t626\n+B3.036\t627\n+B3.026\t628\n+B3.015\t629\n+B3.006\t630\n+B2.996\t631\n+B2.986\t632\n+B2.975\t633\n+B2.966\t634\n+B2.956\t635\n+B2.946\t636\n+B2.935\t637\n+B2.926\t638\n+B2.916\t639\n+B2.906\t640\n+B2.895\t641\n+B2.886\t642\n+B2.876\t643\n+B2.866\t644\n+B2.855\t645\n+B2.846\t646\n+B2.836\t647\n+B2.826\t648\n+B2.815\t649\n+B2.806\t650\n+B2.796\t651\n+B2.786\t652\n+B2.775\t653\n+B2.766\t654\n+B2.756\t655\n+B2.746\t656\n+B2.735\t657\n+B2.726\t658\n+B2.716\t659\n+B2.706\t660\n+B2.695\t661\n+B2.686\t662\n+B2.676\t663\n+B2.666\t664\n+B2.655\t665\n+B2.646\t666\n+B2.636\t667\n+B2.626\t668\n+B2.615\t669\n+B2.606\t670\n+B2.596\t671\n+B2.586\t672\n+B2.575\t673\n+B2.566\t674\n+B2.556\t675\n+B2.546\t676\n+B2.535\t677\n+B2.526\t678\n+B2.516\t679\n+B2.506\t680\n+B2.495\t681\n+B2.486\t682\n+B2.476\t683\n+B2.466\t684\n+B2.455\t685\n+B2.446\t686\n+B2.436\t687\n+B2.426\t688\n+B2.415\t689\n+B2.406\t690\n+B2.396\t691\n+B2.385\t692\n+B2.375\t693\n+B2.365\t694\n+B2.356\t695\n+B2.345\t696\n+B2.335\t697\n+B2.325\t698\n+B2.316\t699\n+B2.305\t700\n+B2.295\t701\n+B2.285\t702\n+B2.276\t703\n+B2.265\t704\n+B2.255\t705\n+B2.245\t706\n+B2.236\t707\n+B2.225\t708\n+B2.215\t709\n+B2.205\t710\n+B2.196\t711\n+B2.185\t712\n+B2.175\t713\n+B2.165\t714\n+B2.156\t715\n+B2.145\t716\n+B2.135\t717\n+B2.126\t718\n+B2.116\t719\n+B2.105\t720\n+B2.095\t721\n+B2.086\t722\n+B2.076\t723\n+B2.065\t724\n+B2.055\t725\n+B2.045\t726\n+B2.036\t727\n+B2.025\t728\n+B2.015\t729\n+B2.005\t730\n+B1.994\t731\n+B1.985\t732\n+B1.974\t733\n+B1.964\t734\n+B1.954\t735\n+B1.945\t736\n+B1.934\t737\n+B1.924\t738\n+B1.914\t739\n+B1.905\t740\n+B1.894\t741\n+B1.884\t742\n+B1.874\t743\n+B1.865\t744\n+B1.854\t745\n+B1.844\t746\n+B1.834\t747\n+B1.825\t748\n+B1.814\t749\n+B1.804\t750\n+B1.794\t751\n+B1.785\t752\n+B1.774\t753\n+B1.764\t754\n+B1.754\t755\n+B1.743\t756\n+B1.734\t757\n+B1.723\t758\n+B1.713\t759\n+B1.703\t760\n+B1.694\t761\n+B1.683\t762\n+B1.673\t763\n+B1.663\t764\n+B1.654\t765\n+B1.643\t766\n+B1.633\t767\n+B1.623\t768\n+B1.612\t769\n+B1.603\t770\n+B1.592\t771\n+B1.582\t772\n+B1.572\t773\n+B1.563\t774\n+B1.552\t775\n+B1.542\t776\n+B1.532\t777\n+B1.523\t778\n+B1.512\t779\n+B1.502\t780\n+B1.491\t781\n+B1.482\t782\n+B1.472\t783\n+B1.461\t784\n+B1.451\t785\n+B1.442\t786\n+B1.432\t787\n+B1.421\t788\n+B1.411\t789\n+B1.401\t790\n+B1.392\t791\n+B1.381\t792\n+B1.371\t793\n+B1.36\t794\n+B1.351\t795\n+B1.341\t796\n+B1.33\t797\n+B1.32\t798\n+B1.31\t799\n+B1.301\t800\n+B1.29\t801\n+B1.28\t802\n+B1.27\t803\n+B1.261\t804\n+B1.25\t805\n+B1.239\t806\n+B1.229\t807\n+B1.22\t808\n+B1.21\t809\n+B1.199\t810\n+B1.189\t811\n+B1.18\t812\n+B1.17\t813\n+B1.159\t814\n+B1.149\t815\n+B1.139\t816\n+B1.129\t817\n+B1.119\t818\n+B1.108\t819\n+B1.098\t820\n+B1.089\t821\n+B1.079\t822\n+B1.068\t823\n+B1.058\t824\n+B1.048\t825\n+B1.039\t826\n+B1.028\t827\n+B1.018\t828\n+B1.008\t829\n+B0.998\t830\n+B0.988\t831\n+B0.977\t832\n+B0.967\t833\n+B0.958\t834\n+B0.948\t835\n+B0.937\t836\n+B0.926\t837\n+B0.916\t838\n+B0.907\t839\n+B0.897\t840\n+B0.886\t841\n+B0.876\t842\n+B0.866\t843\n+B0.857\t844\n+B0.846\t845\n+B0.836\t846\n+B0.826\t847\n+B0.816\t848\n+B0.806\t849\n+B0.8\t850\n'