Mercurial > repos > marie-tremblay-metatoul > 2dnmrannotation
changeset 3:546c7ccd2ed4 draft
"planemo upload for repository https://github.com/workflow4metabolomics/tools-metabolomics commit 911f4beba3dcb25c1033e8239426f8f763683523"
line wrap: on
 line diff
--- a/annotationRmn2D.R Tue Feb 04 10:59:26 2020 -0500 +++ b/annotationRmn2D.R Fri Feb 04 09:01:11 2022 +0000 @@ -1,15 +1,14 @@ -########################################################################################################################################### -# ANNOTATION SPECTRE 2D MATRICE COMPLEXE BASEE SUR UNE SEQUENCE RMN # -# matriceComplexe : data.frame liste couples ppm de la matrice a annoter # -# BdDStandards : objet contenant la base de donnees des composes standards # -# nom_séquence : nom sequence 2D a utiliser pour annotation ("JRES","COSY","TOCSY","HMBC","HSQC") # -# ppm1Tol : tolerance ppm axe abscisses # -# ppm2Tol : tolerance ppm axe ordonnees # -# nb_ligne_template : préciser le nombre total de ligne de la feuille de calcul à annoter # -########################################################################################################################################### -annotationRmn2D <- function(matriceComplexe, BdDStandards, nom_sequence, ppm1Tol=0.01, ppm2Tol=0.01, - seuil=0, unicite="NO") -{ +########################################################################## +# ANNOTATION SPECTRE 2D MATRICE COMPLEXE BASEE SUR UNE SEQUENCE RMN # +# matriceComplexe : data.frame liste couples ppm de la matrice a annoter # +# BdDStandards : objet contenant la base de donnees des composes standards # +# nom_sequence : nom sequence 2D a utiliser pour annotation ("JRES", "COSY", "TOCSY", "HMBC", "HSQC") # +# ppm1Tol : tolerance ppm axe abscisses # +# ppm2Tol : tolerance ppm axe ordonnees # +# nb_ligne_template : preciser le nombre total de ligne de la feuille de calcul a annoter # +####################################################################################################### +annotationRmn2D <- function(matriceComplexe, BdDStandards, nom_sequence, ppm1Tol = 0.01, ppm2Tol = 0.01, + seuil = 0, unicite = "NO") { ## Longueur de la peak-list de la matrice a annoter PeakListLength <- length(matriceComplexe[, 1]) @@ -18,17 +17,16 @@ matrixAnnotation <- data.frame() allMetabolitesList <- data.frame() seuil_score <- seuil - + ## Boucle sur les metabolites inclus dans BdD - for (i in 1:nbMetabolitesBdD) - { + for (i in seq_len(nbMetabolitesBdD)) { ## Infos metabolite en cours iMetabolite <- BdDStandards[[i]] - ppm1M <- iMetabolite[,1] - ppm2M <- iMetabolite[,2] + ppm1M <- iMetabolite[, 1] + ppm2M <- iMetabolite[, 2] nbPeakMetabolite <- length(ppm1M) MetaboliteName <- names(BdDStandards[i]) -## print(MetaboliteName) + ## Initialisation k <- 0 presenceScore <- 0 @@ -37,65 +35,59 @@ annotatedPeakLength <- 0 metabolites <- data.frame() metabolitesList <- data.frame() - + ## Boucle sur les couples de pics de la matrice a annoter - for (p in 1:PeakListLength) - { + for (p in seq_len(PeakListLength)) { ppmAnnotationF1 <- as.numeric(matriceComplexe[p, 3]) ppmAnnotationF2 <- as.numeric(matriceComplexe[p, 2]) e <- simpleMessage("end of file") tryCatch({ - if (!is.na(ppmAnnotationF1)) - { + if (!is.na(ppmAnnotationF1)) { matrixAnnotation <- unique.data.frame(rbind.data.frame(matrixAnnotation, matriceComplexe[p, ])) } # Recherche du couple de pics de la matrice la liste des couples du metabolite standard - metaboliteIn <- (ppm1M >= (ppmAnnotationF2-ppm1Tol) & ppm1M <= (ppmAnnotationF2+ppm1Tol) & - ppm2M >= (ppmAnnotationF1-ppm2Tol) & ppm2M <= (ppmAnnotationF1+ppm2Tol)) + metaboliteIn <- (ppm1M >= (ppmAnnotationF2 - ppm1Tol) & ppm1M <= (ppmAnnotationF2 + ppm1Tol) & + ppm2M >= (ppmAnnotationF1 - ppm2Tol) & ppm2M <= (ppmAnnotationF1 + ppm2Tol)) WhichMetaboliteIn <- which(metaboliteIn) # Si au moins un couple de la matrice a annoter dans liste couples metabolite standard - if (length(WhichMetaboliteIn) > 0) - { - for (a in 1:length(WhichMetaboliteIn)) - { - annotatedPpmList <- data.frame(ppm1=ppm1M[WhichMetaboliteIn[a]], ppm2=ppm2M[WhichMetaboliteIn[a]], theoricalLength=nbPeakMetabolite) - annotatedPpmRef <- rbind(annotatedPpmRef,annotatedPpmList) + if (length(WhichMetaboliteIn) > 0) { + for (a in seq_len(length(WhichMetaboliteIn))) { + annotatedPpmList <- data.frame(ppm1 = ppm1M[WhichMetaboliteIn[a]], ppm2 = ppm2M[WhichMetaboliteIn[a]], theoricalLength = nbPeakMetabolite) + annotatedPpmRef <- rbind(annotatedPpmRef, annotatedPpmList) } } - }, error=function(e){cat ("End of file \n");}) + }, error = function(e) { + cat("End of file \n"); + }) } # Au - 1 couple de ppm de la matrice complexe annote - if (nrow(annotatedPpmRef) >= 1) - { + if (nrow(annotatedPpmRef) >= 1) { ## Nombre couples annotes annotatedPeakLength <- nrow(annotatedPpmRef) - + ## Recherche doublons annotatedDoublons <- duplicated(annotatedPpmRef) - if (sum(duplicated(annotatedPpmRef)) > 0) - { + if (sum(duplicated(annotatedPpmRef)) > 0) { annotatedPeakLength <- nrow(annotatedPpmRef) - sum(duplicated(annotatedPpmRef)) annotatedPpmRef <- annotatedPpmRef[-duplicated(annotatedPpmRef), ] } - presenceScore <- annotatedPeakLength/nbPeakMetabolite + presenceScore <- round(annotatedPeakLength / nbPeakMetabolite, 2) } - + ## Conservation metabolites dont score > seuil - if (presenceScore > seuil_score) - { - metabolites <- data.frame(Metabolite=MetaboliteName, score=presenceScore) - metabolitesList <- cbind.data.frame(annotatedPpmRef, metabolites) + if (presenceScore > seuil_score) { + metabolites <- data.frame(Metabolite = MetaboliteName, score = presenceScore) + metabolitesList <- cbind.data.frame(annotatedPpmRef, metabolites) allMetabolitesList <- rbind.data.frame(allMetabolitesList, metabolitesList) } } - + # Initialisation commonPpm <- data.frame() commonPpmList <- data.frame() metaboliteAdd <- data.frame() metaboliteAddList <- data.frame() -# metabolite_ref <- data.frame() commonMetabolitesList <- data.frame() commonMetabolitesPpmList <- data.frame() commonMetabolitesPpmAllList1 <- data.frame() @@ -103,34 +95,30 @@ listeTotale_2D_unicite <- allMetabolitesList[, 1:4] allMetabolitesList <- allMetabolitesList[, -3] metabolitesAllUnicite <- data.frame() - + ## Boucle sur tous couples annotes - for (j in 1:length(allMetabolitesList$ppm1)) - { + for (j in seq_len(length(allMetabolitesList$ppm1))) { ## Boucle sur metabolites dans BdD composes standards - for (i in 1:nbMetabolitesBdD) - { + for (i in seq_len(nbMetabolitesBdD)) { ppmMetaboliteBdD <- BdDStandards[[i]] - ppm1M <- ppmMetaboliteBdD[,1] - ppm2M <- ppmMetaboliteBdD[,2] + ppm1M <- ppmMetaboliteBdD[, 1] + ppm2M <- ppmMetaboliteBdD[, 2] # Nombre de couples metabolite nbPeakMetabolite <- length(ppm1M) MetaboliteName <- names(BdDStandards[i]) - metabolitesInAll <- (ppm1M >= (allMetabolitesList[j,1]-ppm1Tol) & ppm1M <= (allMetabolitesList[j,1]+ppm1Tol) & - ppm2M >= (allMetabolitesList[j,2]-ppm2Tol) & ppm2M <= (allMetabolitesList[j,2]+ppm2Tol)) + metabolitesInAll <- (ppm1M >= (allMetabolitesList[j, 1] - ppm1Tol) & ppm1M <= (allMetabolitesList[j, 1] + ppm1Tol) & + ppm2M >= (allMetabolitesList[j, 2] - ppm2Tol) & ppm2M <= (allMetabolitesList[j, 2] + ppm2Tol)) WhichMetabolitesInAll <- which(metabolitesInAll) - if (MetaboliteName != allMetabolitesList[j, 3] & length(WhichMetabolitesInAll) > 0) - { - metabolitesAllUnicite <- rbind.data.frame(metabolitesAllUnicite, listeTotale_2D_unicite[j,]) - commonPpm <- data.frame(ppm1=allMetabolitesList[j,1], ppm2=allMetabolitesList[j,2]) + if (MetaboliteName != allMetabolitesList[j, 3] & length(WhichMetabolitesInAll) > 0) { + metabolitesAllUnicite <- rbind.data.frame(metabolitesAllUnicite, listeTotale_2D_unicite[j, ]) + commonPpm <- data.frame(ppm1 = allMetabolitesList[j, 1], ppm2 = allMetabolitesList[j, 2]) commonPpmList <- rbind.data.frame(commonPpmList, commonPpm) commonPpmList <- unique(commonPpmList) - metaboliteAdd <- data.frame(nom_metabolite=MetaboliteName) + metaboliteAdd <- data.frame(nom_metabolite = MetaboliteName) metaboliteAddList <- rbind.data.frame(metaboliteAddList, metaboliteAdd) -# metabolite_ref <- data.frame(nom_metabolite=allMetabolitesList[j,3]) - commonMetabolitesList <- rbind.data.frame(data.frame(nom_metabolite=allMetabolitesList[j, 3]), metaboliteAddList) + commonMetabolitesList <- rbind.data.frame(data.frame(nom_metabolite = allMetabolitesList[j, 3]), metaboliteAddList) commonMetabolitesPpmList <- cbind.data.frame(commonPpm, commonMetabolitesList) commonMetabolitesPpmAllList1 <- rbind.data.frame(commonMetabolitesPpmAllList1, commonMetabolitesPpmList) commonMetabolitesPpmAllList1 <- unique.data.frame(commonMetabolitesPpmAllList1) @@ -138,7 +126,7 @@ } commonMetabolitesPpmAllList <- rbind.data.frame(commonMetabolitesPpmAllList, commonMetabolitesPpmAllList1) commonMetabolitesPpmAllList <- unique.data.frame(commonMetabolitesPpmAllList) - + #initialisation des data.frame commonPpm <- data.frame() metaboliteAdd <- data.frame() @@ -150,12 +138,11 @@ } unicityAllList <- listeTotale_2D_unicite - if (nrow(listeTotale_2D_unicite)!=0 & nrow(metabolitesAllUnicite)!=0) + if (nrow(listeTotale_2D_unicite) != 0 & nrow(metabolitesAllUnicite) != 0) unicityAllList <- setdiff(listeTotale_2D_unicite, metabolitesAllUnicite) unicitynbCouplesRectif <- data.frame() - for (g in 1:nrow(unicityAllList)) - { + for (g in seq_len(nrow(unicityAllList))) { metaboliteUnicity <- (unicityAllList$Metabolite == unicityAllList$Metabolite[g]) WhichMetaboliteUnicity <- which(metaboliteUnicity) nb_occurence <- length(WhichMetaboliteUnicity) @@ -163,84 +150,74 @@ } names(unicitynbCouplesRectif) <- "NbCouplesAnnotes" unicityAllList <- cbind.data.frame(unicityAllList, unicitynbCouplesRectif) - - unicityAllList <- cbind.data.frame(unicityAllList, score_unicite=unicityAllList$NbCouplesAnnotes/unicityAllList$theoricalLength) + + unicityAllList <- cbind.data.frame(unicityAllList, score_unicite = unicityAllList$NbCouplesAnnotes / unicityAllList$theoricalLength) unicityAllList <- unicityAllList[, -3] unicityAllList <- unicityAllList[, -4] -## unicityAllList <- filter(unicityAllList, unicityAllList$score_unicite > seuil_score) - unicityAllList <- unicityAllList[unicityAllList$score_unicite > seuil_score,] + unicityAllList <- unicityAllList[unicityAllList$score_unicite > seuil_score, ] listeTotale_metabo <- data.frame() - if (nrow(commonPpmList) !=0) - { - for (o in 1:length(commonPpmList[, 1])) - { - tf6 <- (commonMetabolitesPpmAllList$ppm1 == commonPpmList[o,1] & commonMetabolitesPpmAllList$ppm2 == commonPpmList[o,2]) - w6 <- which(tf6) - - for (s in 1:length(w6)) - { - metaboliteAdd <- data.frame(nom_metabolite=commonMetabolitesPpmAllList[w6[s],3]) - commonMetabolitesList <- paste(commonMetabolitesList, metaboliteAdd[1,], sep = " ") + if (nrow(commonPpmList) != 0) { + for (o in seq_len(length(commonPpmList[, 1]))) { + tf6 <- (commonMetabolitesPpmAllList$ppm1 == commonPpmList[o, 1] & commonMetabolitesPpmAllList$ppm2 == commonPpmList[o, 2]) + w6 <- which(tf6) + + for (s in seq_len(length(w6))) { + metaboliteAdd <- data.frame(nom_metabolite = commonMetabolitesPpmAllList[w6[s], 3]) + commonMetabolitesList <- paste(commonMetabolitesList, metaboliteAdd[1, ], sep = " ") } - liste_metabo_ppm <- cbind.data.frame(ppm1=commonPpmList[o,1],ppm2=commonPpmList[o,2], commonMetabolitesList) + liste_metabo_ppm <- cbind.data.frame(ppm1 = commonPpmList[o, 1], ppm2 = commonPpmList[o, 2], commonMetabolitesList) listeTotale_metabo <- rbind.data.frame(listeTotale_metabo, liste_metabo_ppm) commonMetabolitesList <- data.frame() } } # Representation graphique - if (nom_sequence == "HSQC" | nom_sequence == "HMBC") - { + if (nom_sequence == "HSQC" | nom_sequence == "HMBC") { atome <- "13C" indice_positif <- 1 indice_negatif <- -10 - }else{ + } else { atome <- "1H" indice_positif <- 0.5 indice_negatif <- -0.5 } - + matriceComplexe <- matrixAnnotation - ppm1 <- as.numeric(matriceComplexe[,2]) - ppm2 <- as.numeric(matriceComplexe[,3]) - - if (unicite == "NO") - { + ppm1 <- as.numeric(matriceComplexe[, 2]) + ppm2 <- as.numeric(matriceComplexe[, 3]) + + if (unicite == "NO") { listeTotale_2D_a_utiliser <- allMetabolitesList - d1.ppm <- allMetabolitesList$ppm1 + d1.ppm <- allMetabolitesList$ppm1 d2.ppm <- allMetabolitesList$ppm2 - }else{ + } else { listeTotale_2D_a_utiliser <- unicityAllList - d1.ppm <- listeTotale_2D_a_utiliser$ppm1 + d1.ppm <- listeTotale_2D_a_utiliser$ppm1 d2.ppm <- listeTotale_2D_a_utiliser$ppm2 } - if (nrow(listeTotale_2D_a_utiliser) > 0) - { + if (nrow(listeTotale_2D_a_utiliser) > 0) { ## Taches de correlations # Matrice biologique + Annotations - maxX <- max(round(max(as.numeric(matriceComplexe[,2])))+0.5, round(max(as.numeric(matriceComplexe[,2])))) - maxY <- max(round(max(as.numeric(matriceComplexe[,3])))+indice_positif, round(max(as.numeric(matriceComplexe[,3])))) - probability.score <- as.factor(round(listeTotale_2D_a_utiliser[,4],2)) + maxX <- max(round(max(as.numeric(matriceComplexe[, 2]))) + 0.5, round(max(as.numeric(matriceComplexe[, 2])))) + maxY <- max(round(max(as.numeric(matriceComplexe[, 3]))) + indice_positif, round(max(as.numeric(matriceComplexe[, 3])))) + probability.score <- as.factor(round(listeTotale_2D_a_utiliser[, 4], 2)) lgr <- length(unique(probability.score)) - sp <- ggplot(matriceComplexe, aes(x=ppm1, y=ppm2)) - sp <- sp + geom_point(size=2) + scale_x_reverse(breaks=seq(maxX, 0, -0.5)) + - scale_y_reverse(breaks=seq(maxY, 0, indice_negatif)) + + sp <- ggplot(matriceComplexe, aes(x = ppm1, y = ppm2)) + sp <- sp + geom_point(size = 2) + scale_x_reverse(breaks = seq(maxX, 0, -0.5)) + + scale_y_reverse(breaks = seq(maxY, 0, indice_negatif)) + xlab("1H chemical shift (ppm)") + ylab(paste(atome, " chemical shift (ppm)")) + ggtitle(nom_sequence) + - geom_text(data=listeTotale_2D_a_utiliser, aes(d1.ppm, d2.ppm, label=str_to_lower(substr(listeTotale_2D_a_utiliser[,3],1,3)), - col=probability.score), - size=4, hjust=0, nudge_x=0.02, vjust=0, nudge_y=0.2) + scale_colour_manual(values=viridis(lgr)) -## scale_color_colormap('Annotation', discrete=T, reverse=T) + geom_text(data = listeTotale_2D_a_utiliser, aes(d1.ppm, d2.ppm, label = str_to_lower(substr(listeTotale_2D_a_utiliser[, 3], 1, 3)), col = probability.score), + size = 4, hjust = 0, nudge_x = 0.02, vjust = 0, nudge_y = 0.2) + scale_colour_manual(values = viridis(lgr)) print(sp) } - - # Liste des résultats (couples pmm / metabolite / score) + liste ppms metabolites communs - if (unicite == "NO") - { - return(list(liste_resultat=allMetabolitesList, listing_ppm_commun=listeTotale_metabo)) - }else{ - return(list(liste_resultat_unicite=unicityAllList, listing_ppm_commun_affichage=listeTotale_metabo)) + + # Liste des resultats (couples pmm / metabolite / score) + liste ppms metabolites communs + if (unicite == "NO") { + return(list(liste_resultat = allMetabolitesList, listing_ppm_commun = listeTotale_metabo)) + } else { + return(list(liste_resultat_unicite = unicityAllList, listing_ppm_commun_affichage = listeTotale_metabo)) } -} \ No newline at end of file +}
--- a/annotationRmn2DGlobale.R Tue Feb 04 10:59:26 2020 -0500 +++ b/annotationRmn2DGlobale.R Fri Feb 04 09:01:11 2022 +0000 @@ -1,28 +1,25 @@ -########################################################################################################################################### -# ANNOTATION SPECTRE 2D MATRICE COMPLEXE BASEE SUR UNE (OU PLUSIEURS) SEQUENCE(s) RMN # -# template : dataframe contenant la liste des couples de deplacements chimiques de la matrice complexe a annoter # -# cosy : 1 si sequence a utiliser / 0 sinon # -# hmbc : 1 si sequence a utiliser / 0 sinon # -# hsqc : 1 si sequence a utiliser / 0 sinon # -# jres : 1 si sequence a utiliser / 0 sinon # -# tocsy : 1 si sequence a utiliser / 0 sinon # -# tolPpm1 : tolerance autorisee autour de la valeur1 du couple de deplacements chimiques # -# tolPpm2HJRes : tolerance autorisee autour de la valeur2 du couple de deplacements chimiques si H dans dimension 2 # -# tolPpm2C : tolerance autorisee autour de la valeur2 du couple de deplacements chimiques si C dans dimension 2 # -# seuil : valeur du score de presence en deça de laquelle les metabolites annotes ne sont pas retenus # -# unicite : boolean pour ne retenir que les ... # -########################################################################################################################################### +################################################################################################### +# ANNOTATION SPECTRE 2D MATRICE COMPLEXE BASEE SUR UNE (OU PLUSIEURS) SEQUENCE(s) # +# template : dataframe contenant la liste des couples de deplacements chimiques de la matrice complexe a annoter # +# cosy : 1 si sequence a utiliser / 0 sinon # +# hmbc : 1 si sequence a utiliser / 0 sinon # +# hsqc : 1 si sequence a utiliser / 0 sinon # +# jres : 1 si sequence a utiliser / 0 sinon # +# tocsy : 1 si sequence a utiliser / 0 sinon # +# tolPpm1 : tolerance autorisee autour de la valeur1 du couple de deplacements chimiques # +# tolPpm2HJRes : tolerance autorisee autour de la valeur2 du couple de deplacements chimiques si H dans dimension 2 # +# tolPpm2C : tolerance autorisee autour de la valeur2 du couple de deplacements chimiques si C dans dimension 2 # +# seuil : valeur du score de presence en dela de laquelle les metabolites annotes ne sont pas retenus # +# unicite : boolean pour ne retenir que les ... # +################################################################################################### ## CALCUL MOYENNE SANS VALEUR(S) MANQUANTE(S) -mean.rmNa <- function(x) -{ - mean(x, na.rm=TRUE) +mean.rmNa <- function(x) { + mean(x, na.rm = TRUE) } -annotationRmn2DGlobale <- function(template, tolPpm1=0.01, tolPpm2HJRes=0.002, tolPpm2C=0.5, cosy=1, hmbc=1, hsqc=1, jres=1, tocsy=1, - seuil, unicite="NO") -{ +annotationRmn2DGlobale <- function(template, tolPpm1 = 0.01, tolPpm2HJRes = 0.002, tolPpm2C = 0.5, cosy = 1, hmbc = 1, hsqc = 1, jres = 1, tocsy = 1, seuil, unicite = "NO") { ## Initialisation - options (max.print=999999999) + options(max.print = 999999999) annotationCOSY <- data.frame() annotationHMBC <- data.frame() annotationHSQC <- data.frame() @@ -34,88 +31,117 @@ dataHSQC <- "NA" dataJRES <- "NA" dataTOCSY <- "NA" - + ## Application seuil seulement si annotation avec 1 seule sequence -## seuilPls2D <- 0 -## if ((sum(cosy, hmbc, hsqc, jres, tocsy)) == 1) -## seuilPls2D <- seuil seuilPls2D <- seuil - - if (cosy == 1) - { - matrice.cosy <- read.xlsx(template, sheet="COSY", startRow=2, colNames=TRUE, rowNames=FALSE, cols=1:3, na.strings="NA") + + if (cosy == 1) { + matrice.cosy <- read.xlsx(template, sheet = "COSY", startRow = 2, colNames = TRUE, rowNames = FALSE, cols = 1:3, na.strings = "NA") matrice.cosy <- matrice.cosy[matrice.cosy$peak.index != "x", ] - annotationCOSY <- annotationRmn2D(matrice.cosy, BdDReference_COSY, "COSY", ppm1Tol=tolPpm1, ppm2Tol=tolPpm1, seuil=seuilPls2D, - unicite=unicite) - dataCOSY <- data.frame(Metabolite=str_to_lower(annotationCOSY$liste_resultat$Metabolite), score.COSY=annotationCOSY$liste_resultat$score) + annotationCOSY <- annotationRmn2D(matrice.cosy, BdDReference_COSY, "COSY", ppm1Tol = tolPpm1, ppm2Tol = tolPpm1, seuil = seuilPls2D, unicite = unicite) + dataCOSY <- data.frame(Metabolite = str_to_lower(annotationCOSY$liste_resultat$Metabolite), score.COSY = annotationCOSY$liste_resultat$score) dataCOSY <- unique.data.frame(dataCOSY) } - - if (hmbc == 1) - { - matrice.hmbc <- read.xlsx(template, sheet="HMBC", startRow=2, colNames=TRUE, rowNames=FALSE, cols=1:3, na.strings="NA") + + if (hmbc == 1) { + matrice.hmbc <- read.xlsx(template, sheet = "HMBC", startRow = 2, colNames = TRUE, rowNames = FALSE, cols = 1:3, na.strings = "NA") matrice.hmbc <- matrice.hmbc[matrice.hmbc$peak.index != "x", ] - annotationHMBC <- annotationRmn2D(matrice.hmbc, BdDReference_HMBC, "HMBC", ppm1Tol=tolPpm1, ppm2Tol=tolPpm2C, seuil=seuilPls2D, - unicite=unicite) - dataHMBC <- data.frame(Metabolite=str_to_lower(annotationHMBC$liste_resultat$Metabolite), score.HMBC=annotationHMBC$liste_resultat$score) + annotationHMBC <- annotationRmn2D(matrice.hmbc, BdDReference_HMBC, "HMBC", ppm1Tol = tolPpm1, ppm2Tol = tolPpm2C, seuil = seuilPls2D, unicite = unicite) + dataHMBC <- data.frame(Metabolite = str_to_lower(annotationHMBC$liste_resultat$Metabolite), score.HMBC = annotationHMBC$liste_resultat$score) dataHMBC <- unique.data.frame(dataHMBC) } - if (hsqc == 1) - { - matrice.hsqc <- read.xlsx(template, sheet="HSQC", startRow=2, colNames=TRUE, rowNames=FALSE, cols=1:3, na.strings="NA") + if (hsqc == 1) { + matrice.hsqc <- read.xlsx(template, sheet = "HSQC", startRow = 2, colNames = TRUE, rowNames = FALSE, cols = 1:3, na.strings = "NA") matrice.hsqc <- matrice.hsqc[matrice.hsqc$peak.index != "x", ] - annotationHSQC <- annotationRmn2D(matrice.hsqc, BdDReference_HSQC, "HSQC", ppm1Tol=tolPpm1, ppm2Tol=tolPpm2C, seuil=seuilPls2D, - unicite=unicite) - dataHSQC <- data.frame(Metabolite=str_to_lower(annotationHSQC$liste_resultat$Metabolite), score.HSQC=annotationHSQC$liste_resultat$score) + annotationHSQC <- annotationRmn2D(matrice.hsqc, BdDReference_HSQC, "HSQC", ppm1Tol = tolPpm1, ppm2Tol = tolPpm2C, seuil = seuilPls2D, unicite = unicite) + dataHSQC <- data.frame(Metabolite = str_to_lower(annotationHSQC$liste_resultat$Metabolite), score.HSQC = annotationHSQC$liste_resultat$score) dataHSQC <- unique.data.frame(dataHSQC) } - - if (jres == 1) - { - matrice.jres <- read.xlsx(template, sheet="JRES", startRow=2, colNames=TRUE, rowNames=FALSE, cols=1:3, na.strings="NA") + + if (jres == 1) { + matrice.jres <- read.xlsx(template, sheet = "JRES", startRow = 2, colNames = TRUE, rowNames = FALSE, cols = 1:3, na.strings = "NA") matrice.jres <- matrice.jres[matrice.jres$peak.index != "x", ] - annotationJRES <- annotationRmn2D(matrice.jres, BdDReference_JRES, "JRES", ppm1Tol=tolPpm1, ppm2Tol=tolPpm2HJRes, seuil=seuilPls2D, - unicite=unicite) - dataJRES <- data.frame(Metabolite=str_to_lower(annotationJRES$liste_resultat$Metabolite), score.JRES=annotationJRES$liste_resultat$score) + annotationJRES <- annotationRmn2D(matrice.jres, BdDReference_JRES, "JRES", ppm1Tol = tolPpm1, ppm2Tol = tolPpm2HJRes, seuil = seuilPls2D, unicite = unicite) + dataJRES <- data.frame(Metabolite = str_to_lower(annotationJRES$liste_resultat$Metabolite), score.JRES = annotationJRES$liste_resultat$score) dataJRES <- unique.data.frame(dataJRES) } - - if (tocsy == 1) - { - matrice.tocsy <- read.xlsx(template, sheet="TOCSY", startRow=2, colNames=TRUE, rowNames=FALSE, cols=1:3, na.strings="NA") + + if (tocsy == 1) { + matrice.tocsy <- read.xlsx(template, sheet = "TOCSY", startRow = 2, colNames = TRUE, rowNames = FALSE, cols = 1:3, na.strings = "NA") matrice.tocsy <- matrice.tocsy[matrice.tocsy$peak.index != "x", ] - annotationTOCSY <- annotationRmn2D(matrice.tocsy, BdDReference_TOCSY, "TOCSY", ppm1Tol=tolPpm1, ppm2Tol=tolPpm1, seuil=seuilPls2D, - unicite=unicite) - dataTOCSY <- data.frame(Metabolite=str_to_lower(annotationTOCSY$liste_resultat$Metabolite), score.TOCSY=annotationTOCSY$liste_resultat$score) + annotationTOCSY <- annotationRmn2D(matrice.tocsy, BdDReference_TOCSY, "TOCSY", ppm1Tol = tolPpm1, ppm2Tol = tolPpm1, seuil = seuilPls2D, unicite = unicite) + dataTOCSY <- data.frame(Metabolite = str_to_lower(annotationTOCSY$liste_resultat$Metabolite), score.TOCSY = annotationTOCSY$liste_resultat$score) dataTOCSY <- unique.data.frame(dataTOCSY) } - sequencesCombinationAverageScoreSeuil <- data.frame() - sequencesCombinationAverageScoreSeuilFiltre <- data.frame() - + seqCombiMeanScoreSeuil <- data.frame() + seqCombiMeanScoreSeuilFiltre <- data.frame() + ## CONCATENATION RESULTATS DIFFERENTES SEQUENCES data2D <- list(dataCOSY, dataHMBC, dataHSQC, dataJRES, dataTOCSY) whichSequenceNaN <- which((data2D != "NA")) data2D <- data2D[whichSequenceNaN] sequencesCombination <- data.frame(data2D[1]) - sequencesCombinationAverageScore <- sequencesCombination - + seqCombiMeanScore <- sequencesCombination + ## Si une seule sequence et seuil sur score = filtre applique dans la fonction annotationRmn2D - if (length(data2D) >= 2) - { + if (length(data2D) >= 2) { ## CONCATENATION SCORE PAR SEQUENCE for (l in 2:length(data2D)) - sequencesCombination <- merge.data.frame(sequencesCombination, data2D[l], by="Metabolite", all.x=TRUE, all.y=TRUE) - - ## SCORE MOYEN (sans prise en compte valeurs manquantes) - meanScore <- apply(sequencesCombination[, -1], 1, FUN=mean.rmNa) - sequencesCombinationAverageScore <- cbind.data.frame(sequencesCombination, averageScore=meanScore) - ## SUPPRESSION METABOLITE AVEC SCORE MOYEN < SEUIL -## sequencesCombinationAverageScoreSeuilFiltre <- filter(sequencesCombinationAverageScore, averageScore >= seuil) - sequencesCombinationAverageScoreSeuilFiltre <- sequencesCombinationAverageScore[sequencesCombinationAverageScore$averageScore > seuil, ] + sequencesCombination <- merge.data.frame(sequencesCombination, data2D[l], by = "Metabolite", all.x = TRUE, all.y = TRUE) + + ## Replacement of NA values due to mis annotation + for (m in seq_len(nrow(sequencesCombination))) { + COSYcompound <- sort(names(BdDReference_COSY)) + HMBCcompound <- sort(names(BdDReference_HMBC)) + HSQCcompound <- sort(names(BdDReference_HSQC)) + JREScompound <- sort(names(BdDReference_JRES)) + TOCSYcompound <- sort(names(BdDReference_TOCSY)) + + if (is.na(sequencesCombination[m, 2])) { + compound <- as.character(sequencesCombination[m, 1]) + for (c in seq_len(length(COSYcompound))) + if (str_to_lower(compound) == str_to_lower(COSYcompound[c])) + sequencesCombination[m, 2] <- 0 + } + + if (is.na(sequencesCombination[m, 3])) { + compound <- as.character(sequencesCombination[m, 1]) + for (c in seq_len(length(HMBCcompound))) + if (str_to_lower(compound) == str_to_lower(HMBCcompound[c])) + sequencesCombination[m, 3] <- 0 + } + + if (is.na(sequencesCombination[m, 4])) { + compound <- as.character(sequencesCombination[m, 1]) + for (c in seq_len(length(HSQCcompound))) + if (str_to_lower(compound) == str_to_lower(HSQCcompound[c])) + sequencesCombination[m, 4] <- 0 + } + + if (is.na(sequencesCombination[m, 5])) { + compound <- as.character(sequencesCombination[m, 1]) + for (c in seq_len(length(JREScompound))) + if (str_to_lower(compound) == str_to_lower(JREScompound[c])) + sequencesCombination[m, 5] <- 0 + } + + if (is.na(sequencesCombination[m, 6])) { + compound <- as.character(sequencesCombination[m, 1]) + for (c in seq_len(length(TOCSYcompound))) + if (str_to_lower(compound) == str_to_lower(TOCSYcompound[c])) + sequencesCombination[m, 6] <- 0 + } } - return(list(COSY=annotationCOSY, HMBC=annotationHMBC, HSQC=annotationHSQC, JRES=annotationJRES, TOCSY=annotationTOCSY, - combination=sequencesCombinationAverageScoreSeuilFiltre)) + ## SCORE MOYEN (sans prise en compte valeurs manquantes) + meanScore <- round(apply(sequencesCombination[, -1], 1, FUN = mean.rmNa), 2) + seqCombiMeanScore <- cbind.data.frame(sequencesCombination, averageScore = meanScore) + + ## SUPPRESSION METABOLITE AVEC SCORE MOYEN < SEUIL + seqCombiMeanScoreSeuilFiltre <- seqCombiMeanScore[seqCombiMeanScore$averageScore > seuil, ] + } + + return(list(COSY = annotationCOSY, HMBC = annotationHMBC, HSQC = annotationHSQC, JRES = annotationJRES, TOCSY = annotationTOCSY, combination = seqCombiMeanScoreSeuilFiltre)) }
--- a/annotationRmn2DWrapper.R Tue Feb 04 10:59:26 2020 -0500 +++ b/annotationRmn2DWrapper.R Fri Feb 04 09:01:11 2022 +0000 @@ -3,12 +3,11 @@ ## 201919016 2DNmrAnnotation_1.0.0.R ## Marie Tremblay-Franco ## MetaboHUB: The French Infrastructure for Metabolomics and Fluxomics -## www.metabohub.fr/en -## marie.tremblay-franco@toulouse.inra.fr +## marie.tremblay-franco@inrae.fr runExampleL <- FALSE -if(runExampleL) { +if (runExampleL) { ##------------------------------ ## Example of arguments ##------------------------------ @@ -20,6 +19,7 @@ ##------------------------------ strAsFacL <- options()$stringsAsFactors options(stringsAsFactors = FALSE) +options(digits = 8, scipen = 3) ##------------------------------ ## Constants @@ -41,9 +41,12 @@ library(openxlsx) library(stringr) library(tidyr) +library(curl) +library(jsonlite) +library(stringi) -if(!runExampleL) - argLs <- parseCommandArgs(evaluate=FALSE) +if (!runExampleL) + argLs <- parseCommandArgs(evaluate = FALSE) logFile <- argLs[["logOut"]] sink(logFile) @@ -53,11 +56,10 @@ ##------------------------------ ## Functions ##------------------------------ -source_local <- function(fname) -{ - argv <- commandArgs(trailingOnly = FALSE) - base_dir <- dirname(substring(argv[grep("--file=", argv)], 8)) - source(paste(base_dir, fname, sep="/")) +source_local <- function(fname) { + argv <- commandArgs(trailingOnly = FALSE) + base_dir <- dirname(substring(argv[grep("--file=", argv)], 8)) + source(paste(base_dir, fname, sep = "/")) } #Import the different functions source_local("annotationRmn2D.R") @@ -66,78 +68,159 @@ ## Input parameter values fileToAnnotate <- argLs[[1]] + # Constraints values +ph <- argLs$pH +field <- argLs$magneticField + # Chosen sequence(s) cosy <- 0 hmbc <- 0 hsqc <- 0 jres <- 0 tocsy <- 0 -## sequences <- str_split(argLs[[2]], ",")[[1]] -## for (s in 1:length(sequences)) -## { -## argv <- commandArgs(trailingOnly = FALSE) -## currentDir <- dirname(substring(argv[grep("--file=", argv)], 8)) -## if (sequences[s]=="cosy"){ -## cosy <- 1 -## load(paste(currentDir, "BdDReference_COSY.RData", sep="/")) -## }else if(sequences[s]=="hmbc"){ -## hmbc <- 1 -## load(paste(currentDir, "BdDReference_HMBC.RData", sep="/")) -## }else if(sequences[s]=="hsqc"){ -## hsqc <- 1 -## load(paste(currentDir, "BdDReference_HSQC.RData", sep="/")) -## }else if(sequences[s]=="jres"){ -## jres <- 1 -## load(paste(currentDir, "BdDReference_JRES.RData", sep="/")) -## }else if(sequences[s]=="tocsy"){ -## tocsy <- 1 -## load(paste(currentDir, "BdDReference_TOCSY.RData", sep="/")) -## }else -## stop("No chosen sequence", call.=FALSE) -## } + +if (argLs$cosy_2dsequences == "yes") { + cosy <- 1 + peakforestSpectra <- readLines(curl("https://metabohub.peakforest.org/rest/v1/spectra/nmr2d/search?query=cosy&token=9131jq9l8gsjn1j14t351h716u&max=500")) + peakforestSpectra <- fromJSON(peakforestSpectra, simplifyDataFrame = TRUE) + if (ph != 0) + peakforestSpectra <- peakforestSpectra[peakforestSpectra$sampleNMRTubeConditionsMetadata$potentiaHydrogenii == ph, ] + if (field != 0) + peakforestSpectra <- peakforestSpectra[peakforestSpectra$analyzerNMRSpectrometerDevice$magneticFieldStrenght == field, ] + + if (nrow(peakforestSpectra) != 0) { + BdDReference_COSY <- peakforestSpectra$peaks + names(BdDReference_COSY) <- str_split(peakforestSpectra[, 2], simplify = TRUE, pattern = ";")[, 1] + names(BdDReference_COSY) <- enc2utf8(names(BdDReference_COSY)) + names(BdDReference_COSY) <- str_replace_all(names(BdDReference_COSY), "\u00e9", "e") + + for (k in seq_len(length(BdDReference_COSY))) { + peakforestSpectra_df <- data.frame(ppm.dim1 = BdDReference_COSY[[k]][, 2], ppm.dim2 = BdDReference_COSY[[k]][, 1], + BdDReference_COSY[[k]][, 3:ncol(BdDReference_COSY[[k]])]) + BdDReference_COSY[[k]] <- peakforestSpectra_df + } + } else { + stop("No COSY spectra correspond to requested pH and/or magnetic field", call. = FALSE) + } + rm(peakforestSpectra) + rm(peakforestSpectra_df) +} -if (argLs[[2]]=='yes') -{ - argv <- commandArgs(trailingOnly = FALSE) - currentDir <- dirname(substring(argv[grep("--file=", argv)], 8)) - cosy <- 1 - load(paste(currentDir, "BdDReference_COSY.RData", sep="/")) +if (argLs$hmbc_2dsequences == "yes") { + hmbc <- 1 + peakforestSpectra <- readLines(curl("https://metabohub.peakforest.org/rest/v1/spectra/nmr2d/search?query=hmbc&token=9131jq9l8gsjn1j14t351h716u&max=500")) + peakforestSpectra <- fromJSON(peakforestSpectra, simplifyDataFrame = TRUE) + if (ph != 0) + peakforestSpectra <- peakforestSpectra[peakforestSpectra$sampleNMRTubeConditionsMetadata$potentiaHydrogenii == ph, ] + if (field != 0) + peakforestSpectra <- peakforestSpectra[peakforestSpectra$analyzerNMRSpectrometerDevice$magneticFieldStrenght == field, ] + + if (nrow(peakforestSpectra) != 0) { + + BdDReference_HMBC <- peakforestSpectra$peaks + names(BdDReference_HMBC) <- str_split(peakforestSpectra[, 2], simplify = TRUE, pattern = ";")[, 1] + names(BdDReference_HMBC) <- enc2utf8(names(BdDReference_HMBC)) + names(BdDReference_HMBC) <- str_replace_all(names(BdDReference_HMBC), "\u00e9", "e") + + peakforestSpectra_df <- data.frame() + for (k in seq_len(length(BdDReference_HMBC))) { + peakforestSpectra_df <- data.frame(ppm.dim1 = BdDReference_HMBC[[k]][, 2], ppm.dim2 = BdDReference_HMBC[[k]][, 1], + BdDReference_HMBC[[k]][, 3:ncol(BdDReference_HMBC[[k]])]) + BdDReference_HMBC[[k]] <- peakforestSpectra_df + } + } else { + stop("No HMBC spectra correspond to requested pH and/or magnetic field", call. = FALSE) + } + rm(peakforestSpectra) + rm(peakforestSpectra_df) } -if (argLs[[3]]=='yes') -{ - argv <- commandArgs(trailingOnly = FALSE) - currentDir <- dirname(substring(argv[grep("--file=", argv)], 8)) - jres <- 1 - load(paste(currentDir, "BdDReference_JRES.RData", sep="/")) -} +if (argLs$hsqc_2dsequences == "yes") { + hsqc <- 1 + peakforestSpectra <- readLines(curl("https://metabohub.peakforest.org/rest/v1/spectra/nmr2d/search?query=hsqc&token=9131jq9l8gsjn1j14t351h716u&max=500")) + peakforestSpectra <- fromJSON(peakforestSpectra, simplifyDataFrame = TRUE) + + if (ph != 0) + peakforestSpectra <- peakforestSpectra[peakforestSpectra$sampleNMRTubeConditionsMetadata$potentiaHydrogenii == ph, ] + if (field != 0) + peakforestSpectra <- peakforestSpectra[peakforestSpectra$analyzerNMRSpectrometerDevice$magneticFieldStrenght == field, ] -if (argLs[[4]]=='yes') -{ - argv <- commandArgs(trailingOnly = FALSE) - currentDir <- dirname(substring(argv[grep("--file=", argv)], 8)) - hmbc <- 1 - load(paste(currentDir, "BdDReference_HMBC.RData", sep="/")) + if (nrow(peakforestSpectra) != 0) { + BdDReference_HSQC <- peakforestSpectra$peaks + names(BdDReference_HSQC) <- str_split(peakforestSpectra[, 2], simplify = TRUE, pattern = ";")[, 1] + names(BdDReference_HSQC) <- enc2utf8(names(BdDReference_HSQC)) + names(BdDReference_HSQC) <- str_replace_all(names(BdDReference_HSQC), "\u00e9", "e") + + for (k in seq_len(length(BdDReference_HSQC))) { + peakforestSpectra_df <- data.frame(ppm.dim1 = BdDReference_HSQC[[k]][, 2], ppm.dim2 = BdDReference_HSQC[[k]][, 1], + BdDReference_HSQC[[k]][, 3:ncol(BdDReference_HSQC[[k]])]) + BdDReference_HSQC[[k]] <- peakforestSpectra_df + } + } else { + stop("No HSQC spectra correspond to requested pH and/or magnetic field", call. = FALSE) + } + rm(peakforestSpectra) + rm(peakforestSpectra_df) } -if (argLs[[5]]=='yes') -{ - argv <- commandArgs(trailingOnly = FALSE) - currentDir <- dirname(substring(argv[grep("--file=", argv)], 8)) - hsqc <- 1 - load(paste(currentDir, "BdDReference_HSQC.RData", sep="/")) +if (argLs$jres_2dsequences == "yes") { + jres <- 1 + peakforestSpectra <- readLines(curl("https://metabohub.peakforest.org/rest/v1/spectra/nmr2d/search?query=jres&token=9131jq9l8gsjn1j14t351h716u&max=500")) + peakforestSpectra <- fromJSON(peakforestSpectra, simplifyDataFrame = TRUE) + + if (ph != 0) + peakforestSpectra <- peakforestSpectra[peakforestSpectra$sampleNMRTubeConditionsMetadata$potentiaHydrogenii == ph, ] + if (field != 0) + peakforestSpectra <- peakforestSpectra[peakforestSpectra$analyzerNMRSpectrometerDevice$magneticFieldStrenght == field, ] + + if (nrow(peakforestSpectra) != 0) { + BdDReference_JRES <- peakforestSpectra$peaks + names(BdDReference_JRES) <- str_split(peakforestSpectra[, 2], simplify = TRUE, pattern = ";")[, 1] + names(BdDReference_JRES) <- enc2utf8(names(BdDReference_JRES)) + names(BdDReference_JRES) <- str_replace_all(names(BdDReference_JRES), "\u00e9", "e") + + for (k in seq_len(length(BdDReference_JRES))) { + peakforestSpectra_df <- data.frame(ppm.dim1 = BdDReference_JRES[[k]][, 2], ppm.dim2 = BdDReference_JRES[[k]][, 1], + BdDReference_JRES[[k]][, 3:ncol(BdDReference_JRES[[k]])]) + BdDReference_JRES[[k]] <- peakforestSpectra_df + } + } else { + stop("No JRES spectra correspond to requested pH and/or magnetic field", call. = FALSE) + } + rm(peakforestSpectra) + rm(peakforestSpectra_df) } -if (argLs[[6]]=='yes') -{ - argv <- commandArgs(trailingOnly = FALSE) - currentDir <- dirname(substring(argv[grep("--file=", argv)], 8)) +if (argLs$tocsy_2dsequences == "yes") { tocsy <- 1 - load(paste(currentDir, "BdDReference_TOCSY.RData", sep="/")) + peakforestSpectra <- readLines(curl("https://metabohub.peakforest.org/rest/v1/spectra/nmr2d/search?query=tocsy&token=9131jq9l8gsjn1j14t351h716u&max=500")) + peakforestSpectra <- fromJSON(peakforestSpectra, simplifyDataFrame = TRUE) + + if (ph != 0) + peakforestSpectra <- peakforestSpectra[peakforestSpectra$sampleNMRTubeConditionsMetadata$potentiaHydrogenii == ph, ] + if (field != 0) + peakforestSpectra <- peakforestSpectra[peakforestSpectra$analyzerNMRSpectrometerDevice$magneticFieldStrenght == field, ] + + if (nrow(peakforestSpectra) != 0) { + BdDReference_TOCSY <- peakforestSpectra$peaks + names(BdDReference_TOCSY) <- str_split(peakforestSpectra[, 2], simplify = TRUE, pattern = ";")[, 1] + names(BdDReference_TOCSY) <- enc2utf8(names(BdDReference_TOCSY)) + names(BdDReference_TOCSY) <- str_replace_all(names(BdDReference_TOCSY), "\u00e9", "e") + + for (k in seq_len(length(BdDReference_TOCSY))) { + peakforestSpectra_df <- data.frame(ppm.dim1 = BdDReference_TOCSY[[k]][, 2], ppm.dim2 = BdDReference_TOCSY[[k]][, 1], + BdDReference_TOCSY[[k]][, 3:ncol(BdDReference_TOCSY[[k]])]) + BdDReference_TOCSY[[k]] <- peakforestSpectra_df + } + } else { + stop("No TOCSY spectra correspond to requested pH and/or magnetic field", call. = FALSE) + } + rm(peakforestSpectra) + rm(peakforestSpectra_df) } -if (argLs[[2]]=='no' & argLs[[3]]=='no' & argLs[[4]]=='no' & argLs[[5]]=='no' & argLs[[6]]=='no') - stop("No chosen sequence", call.=FALSE) +if (argLs$cosy_2dsequences == "no" & argLs$hmbc_2dsequences == "no" & argLs$hsqc_2dsequences == "no" & argLs$jres_2dsequences == "no" & argLs$tocsy_2dsequences == "no") + stop("No chosen sequence. You have to choose at least 1 sequence", call. = FALSE) # User database @@ -158,66 +241,60 @@ print(argLs) ## ANNOTATION -st0=Sys.time() -pdf(AnnotationGraph,onefile=TRUE) -annotationMelange <- annotationRmn2DGlobale(fileToAnnotate, tolPpm1=tolPpm1, tolPpm2HJRes=tolPpm2HJRes, - tolPpm2C=tolPpm2C, cosy=cosy, hmbc=hmbc, hsqc=hsqc, - jres=jres, tocsy=tocsy, seuil=seuil, unicite=unicite) +st0 <- Sys.time() +pdf(AnnotationGraph, onefile = TRUE) +annotationMelange <- annotationRmn2DGlobale(fileToAnnotate, tolPpm1 = tolPpm1, tolPpm2HJRes = tolPpm2HJRes, + tolPpm2C = tolPpm2C, cosy = cosy, hmbc = hmbc, hsqc = hsqc, + jres = jres, tocsy = tocsy, seuil = seuil, unicite = unicite) dev.off() -if (cosy==1) -{ - write.table(annotationMelange$COSY$liste_resultat, file=argLs[["annotationCOSY"]], quote=FALSE, - row.names=FALSE,sep="\t") +if (cosy == 1) { + write.table(annotationMelange$COSY$liste_resultat, file = argLs[["annotationCOSY"]], quote = FALSE, + row.names = FALSE, sep = "\t") if (nrow(annotationMelange$COSY$listing_ppm_commun) != 0) - write.table(annotationMelange$COSY$listing_ppm_commun, file=argLs[["ppmCommunCOSY"]], quote=FALSE, - row.names=FALSE,sep="\t") + write.table(annotationMelange$COSY$listing_ppm_commun, file = argLs[["ppmCommunCOSY"]], quote = FALSE, + row.names = FALSE, sep = "\t") } -if (hmbc==1) -{ - write.table(annotationMelange$HMBC$liste_resultat, file=argLs[["annotationHMBC"]], quote=FALSE, - row.names=FALSE,sep="\t") +if (hmbc == 1) { + write.table(annotationMelange$HMBC$liste_resultat, file = argLs[["annotationHMBC"]], quote = FALSE, + row.names = FALSE, sep = "\t") if (nrow(annotationMelange$HMBC$listing_ppm_commun) != 0) - write.table(annotationMelange$HMBC$listing_ppm_commun, file=argLs[["ppmCommunHMBC"]], quote=FALSE, - row.names=FALSE,sep="\t") + write.table(annotationMelange$HMBC$listing_ppm_commun, file = argLs[["ppmCommunHMBC"]], quote = FALSE, + row.names = FALSE, sep = "\t") } -if (hsqc==1) -{ - write.table(annotationMelange$HSQC$liste_resultat, file=argLs[["annotationHSQC"]], quote=FALSE, - row.names=FALSE,sep="\t") +if (hsqc == 1) { + write.table(annotationMelange$HSQC$liste_resultat, file = argLs[["annotationHSQC"]], quote = FALSE, + row.names = FALSE, sep = "\t") if (nrow(annotationMelange$HSQC$listing_ppm_commun) != 0) - write.table(annotationMelange$HSQC$listing_ppm_commun, file=argLs[["ppmCommunHSQC"]], quote=FALSE, - row.names=FALSE,sep="\t") + write.table(annotationMelange$HSQC$listing_ppm_commun, file = argLs[["ppmCommunHSQC"]], quote = FALSE, + row.names = FALSE, sep = "\t") } -if (jres==1) -{ - write.table(annotationMelange$JRES$liste_resultat, file=argLs[["annotationJRES"]], quote=FALSE, - row.names=FALSE,sep="\t") +if (jres == 1) { + write.table(annotationMelange$JRES$liste_resultat, file = argLs[["annotationJRES"]], quote = FALSE, + row.names = FALSE, sep = "\t") if (nrow(annotationMelange$JRES$listing_ppm_commun) != 0) - write.table(annotationMelange$JRES$listing_ppm_commun, file=argLs[["ppmCommunJRES"]], quote=FALSE, - row.names=FALSE,sep="\t") + write.table(annotationMelange$JRES$listing_ppm_commun, file = argLs[["ppmCommunJRES"]], quote = FALSE, + row.names = FALSE, sep = "\t") } -if (tocsy==1) -{ - write.table(annotationMelange$TOCSY$liste_resultat, file=argLs[["annotationTOCSY"]], quote=FALSE, - row.names=FALSE,sep="\t") +if (tocsy == 1) { + write.table(annotationMelange$TOCSY$liste_resultat, file = argLs[["annotationTOCSY"]], quote = FALSE, + row.names = FALSE, sep = "\t") if (nrow(annotationMelange$TOCSY$listing_ppm_commun) != 0) - write.table(annotationMelange$TOCSY$listing_ppm_commun, file=argLs[["ppmCommunTOCSY"]], quote=FALSE, - row.names=FALSE,sep="\t") + write.table(annotationMelange$TOCSY$listing_ppm_commun, file = argLs[["ppmCommunTOCSY"]], quote = FALSE, + row.names = FALSE, sep = "\t") } ## Combinaison de sequences -if (cosy + jres + hmbc + hsqc + tocsy > 1) -{ - write.table(annotationMelange$combination, file=argLs[["annotationCombination"]], quote=FALSE, - row.names=FALSE,sep="\t") +if (cosy + jres + hmbc + hsqc + tocsy > 1) { + write.table(annotationMelange$combination, file = argLs[["annotationCombination"]], quote = FALSE, + row.names = FALSE, sep = "\t") } -st1=Sys.time() -print(st1-st0) +st1 <- Sys.time() +print(st1 - st0) ## Ending ##--------
--- a/annotationRmn2D_xml.xml Tue Feb 04 10:59:26 2020 -0500 +++ b/annotationRmn2D_xml.xml Fri Feb 04 09:01:11 2022 +0000 @@ -1,4 +1,4 @@ -<tool id="2DNmrAnnotation" name="2DNMR_Annotation" version="1.0.0"> +<tool id="2DNmrAnnotation" name="2DNMRAnnotation" version="2.0.0" profile="20.09"> <description> Annotation of complex mixture bidimensional NMR spectra </description> @@ -9,6 +9,9 @@ <requirement type="package" version="4.0.17">r-openxlsx</requirement> <requirement type="package" version="1.4.0">r-stringr</requirement> <requirement type="package" version="1.0.2">r-tidyr</requirement> + <requirement type="package" version="3.3">r-curl</requirement> + <requirement type="package" version="1.6">r-jsonlite</requirement> + <requirement type="package">r-stringi</requirement> </requirements> <stdio> @@ -19,10 +22,13 @@ ## Wrapper + Libraries of 2D-NMR sequences for reference compounds Rscript '$__tool_directory__/annotationRmn2DWrapper.R' - ## XLS file xlsfile '$zip_xlsfile' + ## Parameters to reduce search + pH $pH + magneticField $magneticField + ## 2D-NMR sequences to annotate cosy_2dsequences $cosy_2dsequences jres_2dsequences $jres_2dsequences @@ -60,7 +66,6 @@ tolppm2 $tolppm2 tolppmJRES $tolppmJRES - ## Treshold (probability score) threshold $threshold @@ -81,20 +86,18 @@ ppmCommunTOCSY '$ppmCommunTOCSY' annotationCombination '$annotationCombination' AnnotationGraph '$AnnotationGraph' - </command> <inputs> <param name="zip_xlsfile" type="data" format="xlsx" label="File to annotate in xlsx format" /> + <param name="pH" type="float" value="0" help="pH value of standards. Default value is 0 (no specific pH value required)" /> + <param name="magneticField" type="integer" value="0" help="Magnetic filed of NMR spectrometer used to generate standard spectra. Default value is 0 (no specific field required)" /> + <param name="cosy_2dsequences" type="select" label="2D-NMR COSY sequence"> <option value="yes" > yes </option> <option value="no" selected="true"> no </option> </param> - <param name="jres_2dsequences" type="select" label="2D-NMR JRES sequence"> - <option value="yes" > yes </option> - <option value="no" selected="true"> no </option> - </param> <param name="hmbc_2dsequences" type="select" label="2D-NMR HMBC sequence"> <option value="yes" > yes </option> <option value="no" selected="true"> no </option> @@ -103,6 +106,10 @@ <option value="yes" > yes </option> <option value="no" selected="true"> no </option> </param> + <param name="jres_2dsequences" type="select" label="2D-NMR JRES sequence"> + <option value="yes" > yes </option> + <option value="no" selected="true"> no </option> + </param> <param name="tocsy_2dsequences" type="select" label="2D-NMR TOCSY sequence"> <option value="yes" > yes </option> <option value="no" selected="true"> no </option> @@ -168,53 +175,54 @@ <when value="no" /> </conditional> - <param name="tolppm1" type="float" value="0.01" help="Tolerance on chemical shift for the x-axis (H). Default value is 0.01ppm" /> - <param name="tolppm2" type="float" value="0.5" help="Tolerance on chemical shift for the y-axis (C). Default value is 0.01ppm" /> - <param name="tolppmJRES" type="float" value="0.002" help="Tolerance on chemical shift for the y-axis for the JRES sequence. Default value is 0.002 (Hz)" /> + <param name="tolppm1" type="float" min="0" value="0.01" help="Tolerance on chemical shift for the x-axis (H). Default value is 0.01ppm" /> + <param name="tolppm2" type="float" min="0" value="0.5" help="Tolerance on chemical shift for the y-axis (C). Default value is 0.01ppm" /> + <param name="tolppmJRES" type="float" min="0" value="0.002" help="Tolerance on chemical shift for the y-axis for the JRES sequence. Default value is 0.002 (Hz)" /> - <param name="threshold" type="float" value="0" help="Treshold on score of presence. Default value is 0" /> + <param name="threshold" type="float" min="0" max="1" value="0" help="Treshold on score of presence. Default value is 0" /> - <param name="unicity" label="Unicity of annotation" type="select" display="radio" help=""> + <param name="unicity" label="Unicity of annotation" type="select" display="radio" help="Select only chemical shifts corresponding to one one metabolite"> <option value="no">No</option> - <option value="yes"></option> + <option value="yes">Yes</option> </param> </inputs> <outputs> <data format="txt" name="logOut" label="${tool.name}_log" /> - <data format="tabular" name="annotationCOSY" label="annotationCosy" > + + <data format="tabular" name="annotationCOSY" label="${tool.name}_annotationCOSY" > <filter> cosy_2dsequences != "no" </filter> </data> - <data format="tabular" name="ppmCommunCOSY" label="duplicateCosy" > + <data format="tabular" name="ppmCommunCOSY" label="${tool.name}_uplicateCOSY" > <filter> cosy_2dsequences != "no" </filter> </data> - <data format="tabular" name="annotationJRES" label="annotationJres" > + <data format="tabular" name="annotationJRES" label="${tool.name}_annotationJRES" > <filter> jres_2dsequences != "no" </filter> </data> - <data format="tabular" name="ppmCommunJRES" label="duplicateJres" > + <data format="tabular" name="ppmCommunJRES" label="${tool.name}_duplicateJRES" > <filter> jres_2dsequences != "no" </filter> </data> - <data format="tabular" name="annotationHMBC" label="annotationHmbc" > + <data format="tabular" name="annotationHMBC" label="${tool.name}_annotationHMBC" > <filter> hmbc_2dsequences != "no" </filter> </data> - <data format="tabular" name="ppmCommunHMBC" label="duplicateHmbc" > + <data format="tabular" name="ppmCommunHMBC" label="${tool.name}_duplicateHMBC" > <filter> hmbc_2dsequences != "no" </filter> </data> - <data format="tabular" name="annotationHSQC" label="annotationHsqc" > + <data format="tabular" name="annotationHSQC" label="${tool.name}_annotationHSQC" > <filter> hsqc_2dsequences != "no" </filter> </data> - <data format="tabular" name="ppmCommunHSQC" label="duplicateHsqc" > + <data format="tabular" name="ppmCommunHSQC" label="${tool.name}_duplicateHSQC" > <filter> hsqc_2dsequences != "no" </filter> </data> - <data format="tabular" name="annotationTOCSY" label="annotationTocsy" > + <data format="tabular" name="annotationTOCSY" label="${tool.name}_annotationTOCSY" > <filter> tocsy_2dsequences != "no" </filter> </data> - <data format="tabular" name="ppmCommunTOCSY" label="duplicateTocsy" > + <data format="tabular" name="ppmCommunTOCSY" label="${tool.name}_duplicateTOCSY" > <filter> tocsy_2dsequences != "no" </filter> </data> @@ -222,28 +230,33 @@ <data format="pdf" name="AnnotationGraph" label="${tool.name}_graph" /> </outputs> <tests> - <test> - <param name="zip_xlsfile" value="Template_melange.xlsm" ftype="xlsx"/> - <param name="cosy_2dsequences" value="no"/> - <param name="jres_2dsequences" value="yes"/> - <param name="hmbc_2dsequences" value="no"/> - <param name="hsqc_2dsequences" value="yes"/> - <param name="tocsy_2dsequences" value="no"/> - <param name="tocsy_2dsequences" value="no"/> - <param name="inHouse_DB_choices.choice" value="no"/> - <param name="tolppm1" value="0.01"/> - <param name="tolppm2" value="0.5"/> - <param name="tolppmJRES" value="0.002"/> - <param name="threshold" value="0.3"/> - <param name="unicity" value="no"/> - <output name="annotationJRES" file="annotationJres.tabular"/> - <output name="ppmCommunJRES" file="duplicateJres.tabular"/> - <output name="annotationHSQC" file="annotationHsqc.tabular"/> - <output name="ppmCommunHSQC" file="duplicateHsqc.tabular"/> - <output name="annotationCombination" file="2DNMR_Annotation_annotationCombination.tabular"/> - </test> - </tests> -<help> + <test expect_num_outputs="13"> + <param name="zip_xlsfile" value="Template_melange.xlsx" ftype="xlsx"/> + <param name="cosy_2dsequences" value="yes"/> + <param name="jres_2dsequences" value="yes"/> + <param name="hmbc_2dsequences" value="yes"/> + <param name="hsqc_2dsequences" value="yes"/> + <param name="tocsy_2dsequences" value="yes"/> + <param name="inHouse_DB_choices.choice" value="no"/> + <param name="tolppm1" value="0.01"/> + <param name="tolppm2" value="0.5"/> + <param name="tolppmJRES" value="0.002"/> + <param name="threshold" value="0.3"/> + <param name="unicity" value="no"/> + <output name="annotationCOSY" file="2DNMRAnnotation_annotationCOSY.tabular"/> + <output name="ppmCommunCOSY" file="2DNMRAnnotation_duplicateCOSY.tabular"/> + <output name="annotationHMBC" file="2DNMRAnnotation_annotationHMBC.tabular"/> + <output name="ppmCommunHMBC" file="2DNMRAnnotation_duplicateHMBC.tabular"/> + <output name="annotationHSQC" file="2DNMRAnnotation_annotationHSQC.tabular"/> + <output name="ppmCommunHSQC" file="2DNMRAnnotation_duplicateHSQC.tabular"/> + <output name="annotationJRES" file="2DNMRAnnotation_annotationJRES.tabular"/> + <output name="ppmCommunJRES" file="2DNMRAnnotation_duplicateJRES.tabular"/> + <output name="annotationTOCSY" file="2DNMRAnnotation_annotationTOCSY.tabular"/> + <output name="ppmCommunTOCSY" file="2DNMRAnnotation_duplicateTOCSY.tabular"/> + <output name="annotationCombination" file="2DNMRAnnotation_annotationCombination.tabular"/> + </test> + </tests> + <help> .. class:: infomark
--- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/2DNMRAnnotation_annotationCOSY.tabular Fri Feb 04 09:01:11 2022 +0000 @@ -0,0 +1,22 @@ +ppm1 ppm2 Metabolite score +1.0475 2.2765 L-valine 0.4 +2.2801 1.0251 L-valine 0.4 +1.4869 3.7917 L-alanine 0.5 +4.572 2.453 carnitine 0.5 +4.572 3.431 carnitine 0.5 +0.8975 1.5674 Butyric acid 0.5 +1.5664 0.898 Butyric acid 0.5 +1.7296 3.0195 Cadaverine 0.5 +3.0256 1.7292 Cadaverine 0.5 +4.2594 1.3323 L-Threonine 0.5 +4.2601 3.5979 L-Threonine 0.5 +2.8816 4.0178 L-asparagine 0.8 +2.8825 2.9639 L-asparagine 0.8 +2.9617 2.8831 L-asparagine 0.8 +4.0137 2.9132 L-asparagine 0.8 +3.3187 4.0587 L-Tryptophan 0.31 +4.0638 3.4884 L-Tryptophan 0.31 +7.2048 7.2841 L-Tryptophan 0.31 +7.7385 7.2038 L-Tryptophan 0.31 +7.21 7.281 indoxyl sulfate 0.33 +7.283 7.205 indoxyl sulfate 0.33
--- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/2DNMRAnnotation_annotationCombination.tabular Fri Feb 04 09:01:11 2022 +0000 @@ -0,0 +1,23 @@ +Metabolite score.COSY score.HMBC score.HSQC score.JRES score.TOCSY averageScore +butyric acid 0.5 0.38 0.33 0.92 0 0.43 +cadaverine 0.5 0.67 0.33 0.62 0 0.42 +carnitine 0.5 0.64 1 0.61 0 0.55 +choline chloride 0 0.5 0.67 0.71 0 0.38 +d-glucose 0 0.36 0.67 0.81 0 0.37 +dimethylamine NA NA 0 1 0 0.33 +fumaric acid NA 1 1 1 NA 1 +glycine NA NA NA 1 NA 1 +glycine betaine NA 0.67 1 1 NA 0.89 +hippuric acid 0 0.7 1 1 0 0.54 +isoleucine 0 0.41 1 0.38 0 0.36 +l-alanine 0.5 0.75 1 1 1 0.85 +l-asparagine 0.8 0.78 1 1 0 0.72 +l-aspartic acid 0 0.67 1 1 0 0.53 +l-glutamine 0 1 1 0.58 0 0.52 +l-histidine 0 0.41 1 0.43 0 0.37 +l-lactic acid (sodium salt) 0 0.5 1 1 0 0.5 +l-proline 0 0.52 1 0.41 0 0.39 +l-threonine 0.5 0.71 0.67 1 0 0.58 +l-tryptophan 0.31 0.56 1 0.52 0 0.48 +l-valine 0.4 0.57 0.75 0.75 0 0.49 +n,n-dimethylglycine NA NA NA 0.33 NA 0.33
--- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/2DNMRAnnotation_annotationHMBC.tabular Fri Feb 04 09:01:11 2022 +0000 @@ -0,0 +1,134 @@ +ppm1 ppm2 Metabolite score +0.9975 31.8443 L-valine 0.57 +0.9975 20.612 L-valine 0.57 +1.0462 63.1097 L-valine 0.57 +1.0454 31.8443 L-valine 0.57 +1.0454 19.454 L-valine 0.57 +3.619 177.1029 L-valine 0.57 +3.619 19.5355 L-valine 0.57 +3.619 31.7987 L-valine 0.57 +3.658 74.853 Glycerol 0.33 +1.4865 53.2396 L-alanine 0.75 +1.4864 178.8022 L-alanine 0.75 +3.7912 19.0064 L-alanine 0.75 +3.41 63.2018 D-Glucose 0.36 +3.4086 78.5367 D-Glucose 0.36 +3.4973 76.8375 D-Glucose 0.36 +3.5453 75.5793 D-Glucose 0.36 +3.7256 72.2932 D-Glucose 0.36 +3.7214 73.9362 D-Glucose 0.36 +3.7446 78.4272 D-Glucose 0.36 +3.8341 71.9646 D-Glucose 0.36 +5.2443 75.3522 D-Glucose 0.36 +2.437 72.979 carnitine 0.64 +2.437 66.884 carnitine 0.64 +3.234 73.033 carnitine 0.64 +3.434 56.947 carnitine 0.64 +3.434 66.868 carnitine 0.64 +4.571 45.799 carnitine 0.64 +4.572 72.95 carnitine 0.64 +3.41 63.2018 D-Glucose 0.36 +3.4086 78.5367 D-Glucose 0.36 +3.4973 76.8375 D-Glucose 0.36 +3.5453 75.5793 D-Glucose 0.36 +3.7256 72.2932 D-Glucose 0.36 +3.7214 73.9362 D-Glucose 0.36 +3.7446 78.4272 D-Glucose 0.36 +3.8341 71.9646 D-Glucose 0.36 +5.2443 75.3522 D-Glucose 0.36 +0.9443 39.0608 Isoleucine 0.41 +0.9431 27.3862 Isoleucine 0.41 +1.0131 62.3008 Isoleucine 0.41 +1.0124 38.7334 Isoleucine 0.41 +1.0128 27.2771 Isoleucine 0.41 +3.6796 17.4149 Isoleucine 0.41 +3.6796 27.2431 Isoleucine 0.41 +3.6796 38.7956 Isoleucine 0.41 +3.6795 177.2002 Isoleucine 0.41 +0.9069 42.6604 Butyric acid 0.38 +2.1721 16.3309 Butyric acid 0.38 +2.1721 22.6634 Butyric acid 0.38 +1.7317 41.9356 Cadaverine 0.67 +1.7224 25.1451 Cadaverine 0.67 +3.0227 25.6132 Cadaverine 0.67 +3.0227 29.096 Cadaverine 0.67 +6.5238 177.4902 Fumaric acid 1 +1.3375 68.918 L-Threonine 0.71 +1.3375 63.3411 L-Threonine 0.71 +3.5999 22.2276 L-Threonine 0.71 +3.601 175.8079 L-Threonine 0.71 +3.6011 68.7524 L-Threonine 0.71 +2.0121 64.0847 L-Proline 0.52 +2.0118 31.7788 L-Proline 0.52 +2.0774 48.8731 L-Proline 0.52 +2.0786 26.5822 L-Proline 0.52 +2.0764 177.7637 L-Proline 0.52 +3.3482 31.6679 L-Proline 0.52 +3.3489 26.2332 L-Proline 0.52 +3.4227 26.4422 L-Proline 0.52 +3.4234 31.877 L-Proline 0.52 +4.1421 177.7407 L-Proline 0.52 +4.142 31.6162 L-Proline 0.52 +3.208 120.0895 L-Histidine 0.41 +3.2958 119.9833 L-Histidine 0.41 +3.2934 133.7111 L-Histidine 0.41 +4.0133 30.2323 L-Histidine 0.41 +4.0208 133.0698 L-Histidine 0.41 +4.0162 176.6782 L-Histidine 0.41 +7.1541 138.3494 L-Histidine 0.41 +3.967 173.358 Hippuric acid 0.7 +3.967 179.778 Hippuric acid 0.7 +7.556 136.202 Hippuric acid 0.7 +7.643 130.002 Hippuric acid 0.7 +7.836 129.968 Hippuric acid 0.7 +7.834 173.399 Hippuric acid 0.7 +7.836 135.05 Hippuric acid 0.7 +2.8801 54.0553 L-asparagine 0.78 +2.8795 177.2568 L-asparagine 0.78 +2.9588 53.9465 L-asparagine 0.78 +2.9596 176.1964 L-asparagine 0.78 +2.9604 177.2568 L-asparagine 0.78 +4.0136 37.3441 L-asparagine 0.78 +4.0138 176.324 L-asparagine 0.78 +3.3185 177.2984 L-Tryptophan 0.56 +3.4878 110.3328 L-Tryptophan 0.56 +3.4867 177.422 L-Tryptophan 0.56 +4.0724 29.0374 L-Tryptophan 0.56 +4.0632 177.422 L-Tryptophan 0.56 +4.0621 110.3328 L-Tryptophan 0.56 +7.2025 114.7667 L-Tryptophan 0.56 +7.2048 129.3079 L-Tryptophan 0.56 +7.2912 121.154 L-Tryptophan 0.56 +7.2897 139.0247 L-Tryptophan 0.56 +7.3342 29.163 L-Tryptophan 0.56 +7.3341 110.2141 L-Tryptophan 0.56 +7.3302 129.3759 L-Tryptophan 0.56 +7.3333 139.1606 L-Tryptophan 0.56 +7.5498 122.0373 L-Tryptophan 0.56 +7.5498 129.3759 L-Tryptophan 0.56 +7.7403 124.7553 L-Tryptophan 0.56 +7.7403 110.2141 L-Tryptophan 0.56 +7.7395 129.3079 L-Tryptophan 0.56 +7.7395 139.1606 L-Tryptophan 0.56 +2.693 54.928 L-Aspartic acid 0.67 +2.817 177.087 L-Aspartic acid 0.67 +2.817 180.405 L-Aspartic acid 0.67 +3.905 177.135 L-Aspartic acid 0.67 +3.906 39.415 L-Aspartic acid 0.67 +3.905 180.436 L-Aspartic acid 0.67 +3.2093 70.2754 Choline chloride 0.5 +4.0684 70.1334 Choline chloride 0.5 +3.2714 69.0499 glycine betaine 0.67 +3.9074 172.0445 glycine betaine 0.67 +1.3325 185.3304 L-Lactic acid (sodium salt) 0.5 +1.3321 71.365 L-Lactic acid (sodium salt) 0.5 +2.147 56.9062 L-glutamine 1 +2.1472 176.985 L-glutamine 1 +2.1472 180.549 L-glutamine 1 +2.147 33.5561 L-glutamine 1 +2.4585 180.549 L-glutamine 1 +2.4595 29.2263 L-glutamine 1 +2.4612 56.7516 L-glutamine 1 +3.7841 29.0914 L-glutamine 1 +3.7836 33.6316 L-glutamine 1 +3.7825 177.069 L-glutamine 1
--- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/2DNMRAnnotation_annotationHSQC.tabular Fri Feb 04 09:01:11 2022 +0000 @@ -0,0 +1,86 @@ +ppm1 ppm2 Metabolite score +0.9996 19.4973 L-valine 0.75 +1.0493 20.7695 L-valine 0.75 +2.2812 31.8928 L-valine 0.75 +1.487 19.022 L-alanine 1 +3.7914 53.3428 L-alanine 1 +3.425 72.3072 D-Glucose 0.67 +3.4602 78.6475 D-Glucose 0.67 +3.5494 74.1688 D-Glucose 0.67 +3.7454 63.5139 D-Glucose 0.67 +3.8409 74.2228 D-Glucose 0.67 +3.8472 63.4002 D-Glucose 0.67 +4.6599 98.7368 D-Glucose 0.67 +5.2521 94.768 D-Glucose 0.67 +2.0091 26.5429 L-Proline 1 +2.062 31.789 L-Proline 1 +2.3567 31.8174 L-Proline 1 +3.3461 48.8306 L-Proline 1 +3.4218 48.8668 L-Proline 1 +4.1397 63.9465 L-Proline 1 +2.444 45.792 carnitine 1 +3.232 56.932 carnitine 1 +3.44 72.954 carnitine 1 +4.571 66.903 carnitine 1 +3.425 72.3072 D-Glucose 0.67 +3.4602 78.6475 D-Glucose 0.67 +3.5494 74.1688 D-Glucose 0.67 +3.7454 63.5139 D-Glucose 0.67 +3.8409 74.2228 D-Glucose 0.67 +3.8472 63.4002 D-Glucose 0.67 +4.6599 98.7368 D-Glucose 0.67 +5.2521 94.768 D-Glucose 0.67 +0.9442 14.0011 Isoleucine 1 +1.0172 17.5257 Isoleucine 1 +1.2698 27.2621 Isoleucine 1 +1.4789 27.34 Isoleucine 1 +1.9872 38.7092 Isoleucine 1 +3.6801 62.4334 Isoleucine 1 +2.1645 42.3691 Butyric acid 0.33 +3.024 41.9605 Cadaverine 0.33 +6.5261 138.1571 Fumaric acid 1 +2.1475 29.0091 L-glutamine 1 +2.4598 33.6379 L-glutamine 1 +3.7832 56.8999 L-glutamine 1 +1.3449 22.198 L-Threonine 0.67 +3.6109 63.2758 L-Threonine 0.67 +3.2093 30.1637 L-Histidine 1 +3.29 30.1939 L-Histidine 1 +4.0137 57.2686 L-Histidine 1 +7.1554 119.9689 L-Histidine 1 +8.0399 138.3896 L-Histidine 1 +3.502 74.756 D-Galactose 0.83 +3.661 75.593 D-Galactose 0.83 +3.717 78.019 D-Galactose 0.83 +3.815 71.175 D-Galactose 0.83 +3.866 71.993 D-Galactose 0.83 +3.942 71.619 D-Galactose 0.83 +4 72.162 D-Galactose 0.83 +4.096 73.292 D-Galactose 0.83 +4.598 99.277 D-Galactose 0.83 +5.277 95.132 D-Galactose 0.83 +3.967 46.611 Hippuric acid 1 +7.556 131.578 Hippuric acid 1 +7.643 135.065 Hippuric acid 1 +7.837 130.019 Hippuric acid 1 +2.8832 37.3717 L-asparagine 1 +2.964 37.3818 L-asparagine 1 +4.0158 54.0397 L-asparagine 1 +3.3207 29.2479 L-Tryptophan 1 +3.4922 29.268 L-Tryptophan 1 +4.0659 57.8237 L-Tryptophan 1 +7.2088 122.2507 L-Tryptophan 1 +7.2919 124.9626 L-Tryptophan 1 +7.3372 127.8914 L-Tryptophan 1 +7.554 114.8383 L-Tryptophan 1 +7.7426 121.2383 L-Tryptophan 1 +2.694 39.367 L-Aspartic acid 1 +2.816 39.387 L-Aspartic acid 1 +3.905 54.962 L-Aspartic acid 1 +3.208 56.7037 Choline chloride 0.67 +4.0716 58.2271 Choline chloride 0.67 +3.015 42.093 4-aminobutyric acid 0.33 +3.264 56.2724 glycine betaine 1 +3.9005 69.0738 glycine betaine 1 +1.3356 22.9129 L-Lactic acid (sodium salt) 1 +4.1198 71.3177 L-Lactic acid (sodium salt) 1
--- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/2DNMRAnnotation_annotationJRES.tabular Fri Feb 04 09:01:11 2022 +0000 @@ -0,0 +1,381 @@ +ppm1 ppm2 Metabolite score +1.3404 0.0051 L-Threonine 1 +1.3395 -0.006 L-Threonine 1 +1.3404 0.0051 L-Threonine 1 +3.6026 0.0039 L-Threonine 1 +3.6044 -0.0048 L-Threonine 1 +4.2598 -0.0105 L-Threonine 1 +4.2584 -0.02 L-Threonine 1 +4.2603 0.0099 L-Threonine 1 +4.2587 0.0005 L-Threonine 1 +4.2591 0.021 L-Threonine 1 +4.0661 0.0003 Creatinine 0.5 +2.452 0 Phloretic acid 0.5 +2.452 -0.013 Phloretic acid 0.5 +2.452 0.013 Phloretic acid 0.5 +2.818 -0.013 Phloretic acid 0.5 +2.818 0.013 Phloretic acid 0.5 +7.5517 -0.0063 Uracil 0.5 +7.5517 0.0066 Uracil 0.5 +3.568 0 Glycine 1 +3.275 0 taurine 0.33 +3.43 0 taurine 0.33 +0.9979 -0.006 L-valine 0.75 +0.9965 0.0062 L-valine 0.75 +1.0473 -0.0062 L-valine 0.75 +1.0473 0.006 L-valine 0.75 +2.2785 -0.0035 L-valine 0.75 +2.2799 0.0027 L-valine 0.75 +2.2799 0.0155 L-valine 0.75 +2.2813 -0.0157 L-valine 0.75 +2.2799 -0.008 L-valine 0.75 +2.2799 0.0078 L-valine 0.75 +3.6196 -0.0035 L-valine 0.75 +3.6196 0.0041 L-valine 0.75 +3.937 0 Creatine 0.5 +3.656 -0.013 Glycerol 0.67 +3.656 -0.006 Glycerol 0.67 +3.656 0.006 Glycerol 0.67 +3.791 -0.011 Glycerol 0.67 +3.791 0 Glycerol 0.67 +3.791 0.01 Glycerol 0.67 +3.791 -0.007 Glycerol 0.67 +3.791 -0.018 Glycerol 0.67 +3.791 0.007 Glycerol 0.67 +3.791 0.018 Glycerol 0.67 +1.4868 0.006 L-alanine 1 +1.4868 -0.006 L-alanine 1 +3.7908 -0.0062 L-alanine 1 +3.7906 -0.0182 L-alanine 1 +3.7908 0.006 L-alanine 1 +3.791 0.0184 L-alanine 1 +3.2556 -0.0143 D-Glucose 0.81 +3.2554 0.0002 D-Glucose 0.81 +3.4216 0.0159 D-Glucose 0.81 +3.4111 0.0157 D-Glucose 0.81 +3.4218 -0.016 D-Glucose 0.81 +3.4109 -0.0158 D-Glucose 0.81 +3.4215 -0.0002 D-Glucose 0.81 +3.4748 -0.0002 D-Glucose 0.81 +3.4751 -0.0111 D-Glucose 0.81 +3.4751 -0.0054 D-Glucose 0.81 +3.4751 0.0054 D-Glucose 0.81 +3.475 0.011 D-Glucose 0.81 +3.4751 0.0146 D-Glucose 0.81 +3.5015 -0.0153 D-Glucose 0.81 +3.5017 -0.0001 D-Glucose 0.81 +3.502 0.0153 D-Glucose 0.81 +3.5453 0.0112 D-Glucose 0.81 +3.5453 -0.0051 D-Glucose 0.81 +3.5452 0.0048 D-Glucose 0.81 +3.5453 -0.0115 D-Glucose 0.81 +3.7312 -0.015 D-Glucose 0.81 +3.7209 -0.0157 D-Glucose 0.81 +3.7315 0.0149 D-Glucose 0.81 +3.7209 0.0158 D-Glucose 0.81 +3.7315 0.0149 D-Glucose 0.81 +3.7315 -0.0057 D-Glucose 0.81 +3.7312 -0.015 D-Glucose 0.81 +3.7315 0.0053 D-Glucose 0.81 +3.8434 0.0093 D-Glucose 0.81 +3.839 0.0108 D-Glucose 0.81 +3.844 -0.0097 D-Glucose 0.81 +3.8393 -0.0111 D-Glucose 0.81 +3.901 -0.0088 D-Glucose 0.81 +3.901 0.0083 D-Glucose 0.81 +3.901 0.0083 D-Glucose 0.81 +3.9017 0.0121 D-Glucose 0.81 +3.9007 -0.0124 D-Glucose 0.81 +3.901 -0.0088 D-Glucose 0.81 +4.6554 0.0067 D-Glucose 0.81 +4.6553 -0.0065 D-Glucose 0.81 +5.2433 -0.0032 D-Glucose 0.81 +5.2433 0.0033 D-Glucose 0.81 +2.426 -0.018 carnitine 0.61 +2.426 0.007 carnitine 0.61 +2.426 0.018 carnitine 0.61 +2.446 0.013 carnitine 0.61 +2.446 -0.013 carnitine 0.61 +2.445 0.027 carnitine 0.61 +2.445 0 carnitine 0.61 +2.445 -0.027 carnitine 0.61 +2.445 0 carnitine 0.61 +2.446 -0.038 carnitine 0.61 +2.445 -0.027 carnitine 0.61 +2.445 0.027 carnitine 0.61 +2.446 0.038 carnitine 0.61 +2.446 -0.013 carnitine 0.61 +2.446 0.013 carnitine 0.61 +2.465 -0.007 carnitine 0.61 +2.465 0.007 carnitine 0.61 +2.465 0.019 carnitine 0.61 +2.465 0.019 carnitine 0.61 +2.465 -0.007 carnitine 0.61 +2.465 -0.019 carnitine 0.61 +2.465 0.007 carnitine 0.61 +3.234 0 carnitine 0.61 +3.422 0.015 carnitine 0.61 +3.422 -0.015 carnitine 0.61 +3.434 0 carnitine 0.61 +3.422 -0.009 carnitine 0.61 +3.438 -0.008 carnitine 0.61 +3.438 0.008 carnitine 0.61 +3.2556 -0.0143 D-Glucose 0.81 +3.2554 0.0002 D-Glucose 0.81 +3.4216 0.0159 D-Glucose 0.81 +3.4111 0.0157 D-Glucose 0.81 +3.4218 -0.016 D-Glucose 0.81 +3.4109 -0.0158 D-Glucose 0.81 +3.4215 -0.0002 D-Glucose 0.81 +3.4748 -0.0002 D-Glucose 0.81 +3.4751 -0.0111 D-Glucose 0.81 +3.4751 -0.0054 D-Glucose 0.81 +3.4751 0.0054 D-Glucose 0.81 +3.475 0.011 D-Glucose 0.81 +3.4751 0.0146 D-Glucose 0.81 +3.5015 -0.0153 D-Glucose 0.81 +3.5017 -0.0001 D-Glucose 0.81 +3.502 0.0153 D-Glucose 0.81 +3.5453 0.0112 D-Glucose 0.81 +3.5453 -0.0051 D-Glucose 0.81 +3.5452 0.0048 D-Glucose 0.81 +3.5453 -0.0115 D-Glucose 0.81 +3.7312 -0.015 D-Glucose 0.81 +3.7209 -0.0157 D-Glucose 0.81 +3.7315 0.0149 D-Glucose 0.81 +3.7209 0.0158 D-Glucose 0.81 +3.7315 0.0149 D-Glucose 0.81 +3.7315 -0.0057 D-Glucose 0.81 +3.7312 -0.015 D-Glucose 0.81 +3.7315 0.0053 D-Glucose 0.81 +3.8434 0.0093 D-Glucose 0.81 +3.839 0.0108 D-Glucose 0.81 +3.844 -0.0097 D-Glucose 0.81 +3.8393 -0.0111 D-Glucose 0.81 +3.901 -0.0088 D-Glucose 0.81 +3.901 0.0083 D-Glucose 0.81 +3.901 0.0083 D-Glucose 0.81 +3.9017 0.0121 D-Glucose 0.81 +3.9007 -0.0124 D-Glucose 0.81 +3.901 -0.0088 D-Glucose 0.81 +4.6554 0.0067 D-Glucose 0.81 +4.6553 -0.0065 D-Glucose 0.81 +5.2433 -0.0032 D-Glucose 0.81 +5.2433 0.0033 D-Glucose 0.81 +3.741 -0.005 D-Mannose 0.31 +3.741 -0.015 D-Mannose 0.31 +3.741 0.005 D-Mannose 0.31 +3.823 0.004 D-Mannose 0.31 +3.823 -0.004 D-Mannose 0.31 +3.856 -0.011 D-Mannose 0.31 +3.856 -0.005 D-Mannose 0.31 +3.856 0.005 D-Mannose 0.31 +3.856 0.011 D-Mannose 0.31 +3.91 -0.012 D-Mannose 0.31 +3.91 0.009 D-Mannose 0.31 +3.91 0.009 D-Mannose 0.31 +3.91 0.012 D-Mannose 0.31 +3.91 -0.012 D-Mannose 0.31 +3.943 0 D-Mannose 0.31 +3.956 0 D-Mannose 0.31 +0.9461 -0.0116 Isoleucine 0.38 +0.9475 0.0121 Isoleucine 0.38 +0.9488 0 Isoleucine 0.38 +1.0168 0.0067 Isoleucine 0.38 +1.0168 -0.0059 Isoleucine 0.38 +1.2688 0.0249 Isoleucine 0.38 +1.2689 -0.0241 Isoleucine 0.38 +1.2689 -0.011 Isoleucine 0.38 +1.2689 0.0114 Isoleucine 0.38 +3.6866 -0.004 Isoleucine 0.38 +3.6831 0.0034 Isoleucine 0.38 +0.8977 -0.0121 Butyric acid 0.92 +0.9022 0 Butyric acid 0.92 +0.9067 0.0126 Butyric acid 0.92 +1.5653 0.0066 Butyric acid 0.92 +1.5698 0.0189 Butyric acid 0.92 +1.5653 -0.0299 Butyric acid 0.92 +1.5653 -0.0059 Butyric acid 0.92 +1.5698 -0.0184 Butyric acid 0.92 +2.1652 0.0003 Butyric acid 0.92 +2.1697 0.0128 Butyric acid 0.92 +2.1697 -0.0119 Butyric acid 0.92 +1.7263 0.0253 Cadaverine 0.62 +1.7299 -0.0259 Cadaverine 0.62 +1.7287 -0.0002 Cadaverine 0.62 +1.7287 0.0131 Cadaverine 0.62 +1.7312 -0.0131 Cadaverine 0.62 +3.0216 0.0117 Cadaverine 0.62 +3.0216 -0.0123 Cadaverine 0.62 +3.0244 -0.0003 Cadaverine 0.62 +6.5188 0.0001 Fumaric acid 1 +2.1458 -0.0143 L-glutamine 0.58 +2.1457 -0.0223 L-glutamine 0.58 +2.1462 0.0223 L-glutamine 0.58 +2.1468 0.0145 L-glutamine 0.58 +2.4383 0.0139 L-glutamine 0.58 +2.4393 -0.0127 L-glutamine 0.58 +2.4387 0.0262 L-glutamine 0.58 +2.439 0.0008 L-glutamine 0.58 +2.4383 -0.0254 L-glutamine 0.58 +2.439 0.0008 L-glutamine 0.58 +2.4387 0.0262 L-glutamine 0.58 +2.4393 -0.0127 L-glutamine 0.58 +2.4383 0.0139 L-glutamine 0.58 +2.459 -0.0056 L-glutamine 0.58 +2.4587 0.0067 L-glutamine 0.58 +2.4587 0.0214 L-glutamine 0.58 +2.4597 -0.0199 L-glutamine 0.58 +2.459 -0.0056 L-glutamine 0.58 +2.4597 -0.0199 L-glutamine 0.58 +2.4587 0.0067 L-glutamine 0.58 +2.4787 0.0131 L-glutamine 0.58 +2.4797 -0.0258 L-glutamine 0.58 +2.4787 -0.0131 L-glutamine 0.58 +2.4794 0 L-glutamine 0.58 +2.4794 0.0262 L-glutamine 0.58 +3.7826 -0.0099 L-glutamine 0.58 +3.7826 0.0002 L-glutamine 0.58 +3.7825 0.0106 L-glutamine 0.58 +2.0117 -0.0211 L-Proline 0.41 +2.0113 -0.0096 L-Proline 0.41 +2.0113 -0.0001 L-Proline 0.41 +2.0117 0.0095 L-Proline 0.41 +2.0117 0.0211 L-Proline 0.41 +2.3564 -0.0036 L-Proline 0.41 +2.3564 -0.017 L-Proline 0.41 +2.3561 0.004 L-Proline 0.41 +2.3564 0.018 L-Proline 0.41 +3.3471 -0.0092 L-Proline 0.41 +3.3474 0.0102 L-Proline 0.41 +3.4233 0.0007 L-Proline 0.41 +3.423 -0.0094 L-Proline 0.41 +3.423 0.0101 L-Proline 0.41 +4.1413 0.0126 L-Proline 0.41 +4.1413 -0.0126 L-Proline 0.41 +4.1403 -0.0023 L-Proline 0.41 +4.142 0.0015 L-Proline 0.41 +4.0154 -0.0107 L-Histidine 0.43 +4.0154 0.0105 L-Histidine 0.43 +4.0154 -0.0019 L-Histidine 0.43 +4.015 0.0018 L-Histidine 0.43 +7.1559 -0.0001 L-Histidine 0.43 +8.0429 -0.0001 L-Histidine 0.43 +3.5 -0.002 D-Galactose 0.47 +3.498 0.015 D-Galactose 0.47 +3.658 -0.011 D-Galactose 0.47 +3.658 -0.005 D-Galactose 0.47 +3.658 0.005 D-Galactose 0.47 +3.658 0.011 D-Galactose 0.47 +3.723 -0.016 D-Galactose 0.47 +3.723 0.016 D-Galactose 0.47 +3.723 0.016 D-Galactose 0.47 +3.723 -0.004 D-Galactose 0.47 +3.723 -0.016 D-Galactose 0.47 +3.723 0.004 D-Galactose 0.47 +3.736 0 D-Galactose 0.47 +3.76 -0.002 D-Galactose 0.47 +3.762 0.008 D-Galactose 0.47 +3.763 -0.009 D-Galactose 0.47 +3.812 -0.012 D-Galactose 0.47 +3.812 0.005 D-Galactose 0.47 +3.812 -0.006 D-Galactose 0.47 +3.812 0.012 D-Galactose 0.47 +3.863 -0.012 D-Galactose 0.47 +3.863 -0.006 D-Galactose 0.47 +3.863 0.006 D-Galactose 0.47 +3.863 0.012 D-Galactose 0.47 +4.595 -0.007 D-Galactose 0.47 +4.595 0.007 D-Galactose 0.47 +5.274 -0.004 D-Galactose 0.47 +5.274 0.004 D-Galactose 0.47 +2.8806 -0.0081 L-asparagine 1 +2.8806 0.0202 L-asparagine 1 +2.8806 0.0079 L-asparagine 1 +2.8805 -0.0205 L-asparagine 1 +2.9607 0.0105 L-asparagine 1 +2.9607 -0.018 L-asparagine 1 +2.9607 -0.011 L-asparagine 1 +2.9608 0.0175 L-asparagine 1 +4.0139 -0.0098 L-asparagine 1 +4.0139 0.0097 L-asparagine 1 +4.0139 -0.0025 L-asparagine 1 +4.0139 0.0024 L-asparagine 1 +4.0631 -0.002 L-Tryptophan 0.52 +7.204 0.0122 L-Tryptophan 0.52 +7.2039 -0.0125 L-Tryptophan 0.52 +7.204 -0.0002 L-Tryptophan 0.52 +7.2882 -0.0125 L-Tryptophan 0.52 +7.2885 0.0127 L-Tryptophan 0.52 +7.2884 -0.0002 L-Tryptophan 0.52 +7.3338 0 L-Tryptophan 0.52 +7.548 -0.0065 L-Tryptophan 0.52 +7.5489 0.0066 L-Tryptophan 0.52 +7.7378 -0.0064 L-Tryptophan 0.52 +7.7378 0.0064 L-Tryptophan 0.52 +3.544 0.011 Myo-Inositol 0.38 +3.544 -0.006 Myo-Inositol 0.38 +3.544 0.006 Myo-Inositol 0.38 +3.544 -0.011 Myo-Inositol 0.38 +4.073 0 Myo-Inositol 0.38 +2.694 0.0072 L-Aspartic acid 1 +2.694 0.0219 L-Aspartic acid 1 +2.694 -0.0075 L-Aspartic acid 1 +2.817 -0.0114 L-Aspartic acid 1 +2.817 0.0112 L-Aspartic acid 1 +2.817 0.0177 L-Aspartic acid 1 +2.817 -0.0178 L-Aspartic acid 1 +3.906 -0.0101 L-Aspartic acid 1 +3.906 0.0103 L-Aspartic acid 1 +3.906 -0.0039 L-Aspartic acid 1 +3.906 0.0039 L-Aspartic acid 1 +3.906 0.0103 L-Aspartic acid 1 +3.906 -0.0101 L-Aspartic acid 1 +2.7286 -0.0002 Dimethylamine 1 +3.969 0 Hippuric acid 1 +7.555 0.013 Hippuric acid 1 +7.555 0 Hippuric acid 1 +7.555 -0.013 Hippuric acid 1 +7.642 0 Hippuric acid 1 +7.642 -0.013 Hippuric acid 1 +7.642 0.012 Hippuric acid 1 +7.836 -0.007 Hippuric acid 1 +7.836 0.007 Hippuric acid 1 +7.21 0.013 indoxyl sulfate 0.55 +7.21 -0.013 indoxyl sulfate 0.55 +7.21 0 indoxyl sulfate 0.55 +7.283 -0.013 indoxyl sulfate 0.55 +7.283 0.013 indoxyl sulfate 0.55 +7.283 0 indoxyl sulfate 0.55 +3.2091 -0.0007 Choline chloride 0.71 +3.5291 0.0082 Choline chloride 0.71 +3.5291 -0.008 Choline chloride 0.71 +4.0693 0.0002 Choline chloride 0.71 +4.0693 0.0088 Choline chloride 0.71 +3.2729 0.0002 glycine betaine 1 +3.908 0.0001 glycine betaine 1 +3.7408 0.0005 N,N-Dimethylglycine 0.33 +3.517 0.002 L-arabinopyranose 0.35 +3.655 -0.013 L-arabinopyranose 0.35 +3.655 0.013 L-arabinopyranose 0.35 +3.671 -0.005 L-arabinopyranose 0.35 +3.824 -0.011 L-arabinopyranose 0.35 +3.824 0.005 L-arabinopyranose 0.35 +3.824 -0.005 L-arabinopyranose 0.35 +3.824 0.011 L-arabinopyranose 0.35 +3.905 -0.012 L-arabinopyranose 0.35 +3.905 -0.009 L-arabinopyranose 0.35 +3.905 0.009 L-arabinopyranose 0.35 +3.905 0.009 L-arabinopyranose 0.35 +3.905 -0.012 L-arabinopyranose 0.35 +3.905 -0.009 L-arabinopyranose 0.35 +4.013 0.004 L-arabinopyranose 0.35 +5.248 -0.002 L-arabinopyranose 0.35 +5.248 0.003 L-arabinopyranose 0.35 +1.3329 0.0057 L-Lactic acid (sodium salt) 1 +1.3328 -0.0058 L-Lactic acid (sodium salt) 1 +1.3329 0.0057 L-Lactic acid (sodium salt) 1 +4.1172 -0.0171 L-Lactic acid (sodium salt) 1 +4.1176 0.017 L-Lactic acid (sodium salt) 1 +4.117 -0.006 L-Lactic acid (sodium salt) 1 +4.1173 0.0058 L-Lactic acid (sodium salt) 1
--- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/2DNMRAnnotation_annotationTOCSY.tabular Fri Feb 04 09:01:11 2022 +0000 @@ -0,0 +1,5 @@ +ppm1 ppm2 Metabolite score +3.7915 1.4891 L-alanine 1 +3.7915 3.7859 L-alanine 1 +1.4861 1.4821 L-alanine 1 +1.4869 3.7859 L-alanine 1
--- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/2DNMRAnnotation_duplicateCOSY.tabular Fri Feb 04 09:01:11 2022 +0000 @@ -0,0 +1,5 @@ +ppm1 ppm2 commonMetabolitesList +1.7296 3.0195 Cadaverine L-lysine +7.2048 7.2841 L-Tryptophan indoxyl sulfate +7.21 7.281 indoxyl sulfate L-Tryptophan +7.283 7.205 indoxyl sulfate L-Tryptophan
--- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/2DNMRAnnotation_duplicateHMBC.tabular Fri Feb 04 09:01:11 2022 +0000 @@ -0,0 +1,20 @@ +ppm1 ppm2 commonMetabolitesList +0.9975 31.8443 L-valine Taurocholic acid +3.658 74.853 Glycerol D-Mannose D-Galactose +3.5453 75.5793 D-Glucose Myo-Inositol +3.7256 72.2932 D-Glucose D-Galactose L-ascorbic acid +3.7214 73.9362 D-Glucose maltose +3.8341 71.9646 D-Glucose Sucrose Raffinose +0.9431 27.3862 Isoleucine 4-methyl-2-oxopentanoic acid +3.6795 177.2002 Isoleucine Phenylacetylglycine Phenylacetyl-L-glutamine +1.7317 41.9356 Cadaverine L-lysine +1.7224 25.1451 Cadaverine L-leucine +3.0227 25.6132 Cadaverine 5-aminopentanoic acid +3.0227 29.096 Cadaverine L-lysine 5-aminopentanoic acid +4.0162 176.6782 L-Histidine L-asparagine +4.0138 176.324 L-asparagine L-Histidine L-Phenylalanine +4.0724 29.0374 L-Tryptophan Cholic acid +7.2025 114.7667 L-Tryptophan indoxyl sulfate +2.147 56.9062 L-glutamine Glutamic acid L-methionine +2.1472 176.985 L-glutamine Glutamic acid L-methionine +3.7825 177.069 L-glutamine L-Arginine
--- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/2DNMRAnnotation_duplicateHSQC.tabular Fri Feb 04 09:01:11 2022 +0000 @@ -0,0 +1,22 @@ +ppm1 ppm2 commonMetabolitesList +0.9996 19.4973 L-valine Cholic acid Cholesterol +1.0493 20.7695 L-valine Cholesterol +3.425 72.3072 D-Glucose maltose +3.5494 74.1688 D-Glucose Myo-Inositol +4.6599 98.7368 D-Glucose maltose +2.3567 31.8174 L-Proline Taurocholic acid +3.232 56.932 carnitine Glycerophosphocholine +1.2698 27.2621 Isoleucine Glycocholic acid +3.024 41.9605 Cadaverine L-lysine 4-aminobutyric acid 5-aminopentanoic acid +3.2093 30.1637 L-Histidine 3-Methyl-L-Histidine +3.502 74.756 D-Galactose Cholic acid +3.661 75.593 D-Galactose D-Mannose +3.866 71.993 D-Galactose Stachyose +3.942 71.619 D-Galactose D-(-)-Ribose +4 72.162 D-Galactose Stachyose D-Fructose +4.0659 57.8237 L-Tryptophan Choline chloride +7.2088 122.2507 L-Tryptophan indoxyl sulfate +7.2919 124.9626 L-Tryptophan indoxyl sulfate +4.0716 58.2271 Choline chloride L-Tryptophan +3.015 42.093 4-aminobutyric acid Cadaverine 5-aminopentanoic acid +4.1198 71.3177 L-Lactic acid (sodium salt) D-(-)-Ribose
--- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/2DNMRAnnotation_duplicateJRES.tabular Fri Feb 04 09:01:11 2022 +0000 @@ -0,0 +1,216 @@ +ppm1 ppm2 commonMetabolitesList +1.3404 0.0051 L-Threonine L-Lactic acid (sodium salt) +1.3395 -0.006 L-Threonine L-Lactic acid (sodium salt) +3.6026 0.0039 L-Threonine maltose L-rhamnose +3.6044 -0.0048 L-Threonine L-rhamnose +4.0661 0.0003 Creatinine Sucrose Cholic acid Raffinose Stachyose L-Tryptophan Myo-Inositol Choline chloride +2.452 0 Phloretic acid carnitine +2.452 -0.013 Phloretic acid carnitine +2.452 0.013 Phloretic acid carnitine +2.818 -0.013 Phloretic acid L-Aspartic acid +2.818 0.013 Phloretic acid L-Aspartic acid +7.5517 -0.0063 Uracil L-Tryptophan +7.5517 0.0066 Uracil L-Tryptophan +3.275 0 taurine glycine betaine +3.43 0 taurine maltose D-Glucose carnitine L-Proline +0.9979 -0.006 L-valine Cholic acid +0.9965 0.0062 L-valine Cholic acid +1.0473 -0.0062 L-valine DL-2-methylbutyric acid +1.0473 0.006 L-valine DL-2-methylbutyric acid +3.6196 -0.0035 L-valine L-rhamnose Glycerophosphocholine +3.6196 0.0041 L-valine L-rhamnose Glycerophosphocholine +3.937 0 Creatine D-Mannose D-(-)-Ribose +3.656 -0.013 Glycerol maltose D-Galactose D-(-)-Ribose L-arabinopyranose +3.656 -0.006 Glycerol ethanol Stachyose D-Galactose D-(-)-Ribose L-arabinopyranose +3.656 0.006 Glycerol ethanol Stachyose D-Galactose D-(-)-Ribose +3.791 -0.011 Glycerol L-glutamine L-ornithine L-Arginine +3.791 0 Glycerol maltose L-glutamine L-ornithine L-Arginine Guanidineacetic acid +3.791 0.01 Glycerol L-glutamine Glutamic acid L-ornithine L-Arginine +3.791 -0.007 Glycerol L-alanine +3.791 -0.018 Glycerol maltose L-alanine Raffinose Stachyose +3.791 0.007 Glycerol L-alanine +3.791 0.018 Glycerol L-alanine Raffinose Stachyose +3.7908 -0.0062 L-alanine Glycerol +3.7906 -0.0182 L-alanine Glycerol Raffinose +3.7908 0.006 L-alanine Glycerol Raffinose Stachyose +3.791 0.0184 L-alanine Glycerol +3.2554 0.0002 D-Glucose L-Arginine +3.4216 0.0159 D-Glucose carnitine +3.4218 -0.016 D-Glucose carnitine +3.4215 -0.0002 D-Glucose taurine L-Proline +3.4748 -0.0002 D-Glucose Sucrose +3.4751 0.0146 D-Glucose Sucrose +3.5015 -0.0153 D-Glucose D-Galactose +3.5017 -0.0001 D-Glucose Cholic acid D-Galactose +3.502 0.0153 D-Glucose D-Galactose +3.5453 0.0112 D-Glucose Myo-Inositol +3.5453 -0.0051 D-Glucose Myo-Inositol +3.5452 0.0048 D-Glucose Myo-Inositol D-(-)-Ribose +3.5453 -0.0115 D-Glucose Myo-Inositol +3.7312 -0.015 D-Glucose D-Mannose Stachyose D-Galactose L-ascorbic acid +3.7209 -0.0157 D-Glucose D-Galactose +3.7315 0.0149 D-Glucose D-Mannose Stachyose D-Galactose L-ascorbic acid +3.7209 0.0158 D-Glucose D-Galactose +3.7315 -0.0057 D-Glucose D-Mannose Stachyose D-Galactose L-ascorbic acid +3.7315 0.0053 D-Glucose D-Mannose Stachyose D-Galactose L-ascorbic acid +3.8434 0.0093 D-Glucose Sucrose Raffinose +3.839 0.0108 D-Glucose Raffinose +3.844 -0.0097 D-Glucose Sucrose Raffinose ethanolamine +3.8393 -0.0111 D-Glucose Raffinose D-(-)-Ribose +3.901 -0.0088 D-Glucose Sucrose D-Mannose D-(-)-Ribose L-Aspartic acid L-arabinopyranose +3.901 0.0083 D-Glucose Sucrose D-Mannose D-(-)-Ribose L-Aspartic acid L-arabinopyranose +3.9017 0.0121 D-Glucose D-Mannose Raffinose Stachyose D-Fructose D-(-)-Ribose L-Aspartic acid L-arabinopyranose +3.9007 -0.0124 D-Glucose D-Mannose Raffinose Stachyose D-Fructose D-(-)-Ribose L-arabinopyranose +5.2433 -0.0032 D-Glucose maltose L-arabinopyranose +5.2433 0.0033 D-Glucose maltose L-arabinopyranose +2.426 -0.018 carnitine Isocitric acid +2.426 0.007 carnitine Isocitric acid +2.426 0.018 carnitine Isocitric acid +2.446 0.013 carnitine Phloretic acid L-glutamine +2.446 -0.013 carnitine Phloretic acid L-glutamine +2.445 0.027 carnitine L-glutamine +2.445 0 carnitine Phloretic acid L-glutamine +2.445 -0.027 carnitine L-glutamine +2.465 -0.007 carnitine L-glutamine +2.465 0.007 carnitine L-glutamine +2.465 -0.019 carnitine L-glutamine +3.234 0 carnitine Glycerophosphocholine +3.422 0.015 carnitine D-Glucose +3.422 -0.015 carnitine D-Glucose +3.434 0 carnitine maltose taurine L-rhamnose +3.422 -0.009 carnitine taurine L-Proline +3.741 -0.005 D-Mannose D-Glucose L-leucine Raffinose Stachyose D-Galactose L-ascorbic acid +3.741 -0.015 D-Mannose D-Glucose Raffinose Stachyose D-Galactose L-ascorbic acid +3.741 0.005 D-Mannose D-Glucose L-leucine Raffinose Stachyose D-Galactose L-ascorbic acid +3.823 0.004 D-Mannose maltose Stachyose D-(-)-Ribose L-arabinopyranose +3.823 -0.004 D-Mannose maltose Stachyose D-(-)-Ribose L-arabinopyranose +3.856 -0.011 D-Mannose maltose Raffinose Stachyose D-Galactose D-(-)-Ribose +3.856 -0.005 D-Mannose Inosine Stachyose D-Galactose D-(-)-Ribose 2-Hydroxy-3-methylbutyric acid +3.856 0.005 D-Mannose Inosine Stachyose D-Galactose D-(-)-Ribose 2-Hydroxy-3-methylbutyric acid +3.856 0.011 D-Mannose maltose Sucrose Raffinose Stachyose D-Galactose D-(-)-Ribose +3.91 -0.012 D-Mannose maltose D-Glucose Raffinose Stachyose D-Fructose L-Aspartic acid L-arabinopyranose +3.91 0.009 D-Mannose maltose D-Glucose Raffinose Stachyose L-Aspartic acid L-arabinopyranose +3.91 0.012 D-Mannose maltose D-Glucose Raffinose Stachyose D-Fructose L-Aspartic acid L-arabinopyranose +3.943 0 D-Mannose Creatine L-Tyrosine D-(-)-Ribose L-arabinopyranose +3.956 0 D-Mannose Raffinose L-Tyrosine L-arabinopyranose +3.6866 -0.004 Isoleucine Raffinose D-Fructose D-(-)-Ribose +3.6831 0.0034 Isoleucine Raffinose D-Fructose +0.8977 -0.0121 Butyric acid Valeric acid 2-hydroxybutyric acid 3-Methyl-2-oxovaleric acid +0.9022 0 Butyric acid Valeric acid 2-hydroxybutyric acid 3-Methyl-2-oxovaleric acid +0.9067 0.0126 Butyric acid 2-hydroxybutyric acid 3-Methyl-2-oxovaleric acid +2.1697 0.0128 Butyric acid Octanoic acid +2.1697 -0.0119 Butyric acid Octanoic acid +1.7263 0.0253 Cadaverine L-leucine +1.7299 -0.0259 Cadaverine L-lysine +1.7287 -0.0002 Cadaverine L-lysine L-leucine +1.7287 0.0131 Cadaverine L-lysine L-leucine +1.7312 -0.0131 Cadaverine L-lysine +3.0216 0.0117 Cadaverine 4-aminobutyric acid 5-aminopentanoic acid +3.0216 -0.0123 Cadaverine 4-aminobutyric acid 5-aminopentanoic acid +3.0244 -0.0003 Cadaverine L-lysine 4-aminobutyric acid 5-aminopentanoic acid +2.4383 0.0139 L-glutamine carnitine +2.4393 -0.0127 L-glutamine carnitine +2.4387 0.0262 L-glutamine carnitine +2.439 0.0008 L-glutamine carnitine +2.4383 -0.0254 L-glutamine carnitine +2.459 -0.0056 L-glutamine carnitine +2.4587 0.0067 L-glutamine carnitine +2.4597 -0.0199 L-glutamine carnitine +2.4787 0.0131 L-glutamine 3-(3-hydroxyphenyl)propanoic acid +2.4787 -0.0131 L-glutamine 3-(3-hydroxyphenyl)propanoic acid +2.4794 0 L-glutamine 3-(3-hydroxyphenyl)propanoic acid +3.7826 -0.0099 L-glutamine Glycerol L-Arginine +3.7826 0.0002 L-glutamine maltose Sucrose Glycerol Raffinose L-Arginine +3.7825 0.0106 L-glutamine Glycerol Glutamic acid L-Arginine +2.0117 -0.0211 L-Proline 2-Hydroxy-3-methylbutyric acid +2.0113 -0.0096 L-Proline 2-Hydroxy-3-methylbutyric acid +2.0117 0.0095 L-Proline 2-Hydroxy-3-methylbutyric acid +2.0117 0.0211 L-Proline 2-Hydroxy-3-methylbutyric acid +3.4233 0.0007 L-Proline taurine D-Glucose +3.423 -0.0094 L-Proline taurine carnitine +3.423 0.0101 L-Proline taurine carnitine +4.1413 0.0126 L-Proline Stachyose +4.1413 -0.0126 L-Proline Stachyose D-(-)-Ribose +4.1403 -0.0023 L-Proline D-(-)-Ribose +4.142 0.0015 L-Proline Stachyose D-(-)-Ribose +4.0154 -0.0107 L-Histidine L-asparagine +4.0154 0.0105 L-Histidine L-asparagine +4.0154 -0.0019 L-Histidine Raffinose D-Fructose L-asparagine +4.015 0.0018 L-Histidine Raffinose D-Fructose L-asparagine +3.5 -0.002 D-Galactose D-Glucose Cholic acid +3.498 0.015 D-Galactose D-Glucose +3.658 -0.011 D-Galactose Glycerol L-arabinopyranose +3.658 -0.005 D-Galactose ethanol Glycerol Stachyose D-(-)-Ribose +3.658 0.005 D-Galactose ethanol Glycerol Stachyose D-(-)-Ribose +3.658 0.011 D-Galactose L-arabinopyranose +3.723 -0.016 D-Galactose D-Glucose L-ascorbic acid +3.723 0.016 D-Galactose D-Glucose L-ascorbic acid +3.723 -0.004 D-Galactose D-Glucose L-ascorbic acid +3.723 0.004 D-Galactose D-Glucose L-ascorbic acid +3.736 0 D-Galactose L-leucine N,N-Dimethylglycine 3-Methyl-L-Histidine +3.76 -0.002 D-Galactose L-lysine Phenylacetylglycine +3.762 0.008 D-Galactose maltose Raffinose D-(-)-Ribose +3.763 -0.009 D-Galactose L-lysine Raffinose D-(-)-Ribose +3.812 -0.012 D-Galactose maltose L-rhamnose D-Fructose D-(-)-Ribose +3.812 0.005 D-Galactose maltose Sucrose L-rhamnose +3.812 -0.006 D-Galactose maltose Sucrose L-rhamnose D-(-)-Ribose +3.812 0.012 D-Galactose maltose L-rhamnose D-Fructose D-(-)-Ribose +3.863 -0.012 D-Galactose maltose D-Mannose Stachyose L-rhamnose L-methionine +3.863 -0.006 D-Galactose maltose L-Serine D-Mannose Stachyose +3.863 0.006 D-Galactose maltose L-Serine D-Mannose Stachyose D-(-)-Ribose +3.863 0.012 D-Galactose maltose D-Mannose Stachyose L-rhamnose L-methionine +4.0139 -0.0098 L-asparagine L-Histidine +4.0139 0.0097 L-asparagine L-Histidine +4.0139 -0.0025 L-asparagine L-Histidine D-(-)-Ribose +4.0139 0.0024 L-asparagine L-Histidine L-arabinopyranose +4.0631 -0.002 L-Tryptophan Sucrose Cholic acid Raffinose Stachyose Myo-Inositol +7.204 0.0122 L-Tryptophan indoxyl sulfate +7.2039 -0.0125 L-Tryptophan indoxyl sulfate +7.204 -0.0002 L-Tryptophan indoxyl sulfate N(tele)-methyl-L-histidine +7.2882 -0.0125 L-Tryptophan indoxyl sulfate +7.2885 0.0127 L-Tryptophan indoxyl sulfate +7.2884 -0.0002 L-Tryptophan indoxyl sulfate +7.548 -0.0065 L-Tryptophan Uracil +7.5489 0.0066 L-Tryptophan Uracil +3.544 0.011 Myo-Inositol D-Glucose +3.544 -0.006 Myo-Inositol D-Glucose D-(-)-Ribose +3.544 0.006 Myo-Inositol D-Glucose D-(-)-Ribose +3.544 -0.011 Myo-Inositol D-Glucose +4.073 0 Myo-Inositol Creatinine Cholic acid Raffinose Stachyose L-Tryptophan Choline chloride +2.817 -0.0114 L-Aspartic acid Phloretic acid +2.817 0.0112 L-Aspartic acid Phloretic acid +3.906 -0.0101 L-Aspartic acid D-Glucose D-Mannose Raffinose Stachyose D-Fructose L-arabinopyranose +3.906 0.0103 L-Aspartic acid D-Glucose D-Mannose Raffinose Stachyose D-Fructose L-arabinopyranose +3.906 -0.0039 L-Aspartic acid Stachyose D-Fructose +3.906 0.0039 L-Aspartic acid Stachyose D-Fructose +3.969 0 Hippuric acid maltose Raffinose +7.21 0.013 indoxyl sulfate L-Tryptophan +7.21 -0.013 indoxyl sulfate L-Tryptophan +7.21 0 indoxyl sulfate L-Tryptophan Indole-3-propionic acid N(tele)-methyl-L-histidine +7.283 -0.013 indoxyl sulfate hydrozimtsaeure L-Tryptophan +7.283 0.013 indoxyl sulfate hydrozimtsaeure L-Tryptophan +7.283 0 indoxyl sulfate L-Tryptophan +3.5291 0.0082 Choline chloride D-(-)-Ribose +3.5291 -0.008 Choline chloride D-(-)-Ribose +4.0693 0.0002 Choline chloride Creatinine Cholic acid Raffinose Stachyose L-Tryptophan Myo-Inositol +4.0693 0.0088 Choline chloride L-Tryptophan +3.2729 0.0002 glycine betaine taurine +3.908 0.0001 glycine betaine Cholic acid Raffinose Stachyose +3.7408 0.0005 N,N-Dimethylglycine L-leucine D-Galactose 3-Methyl-L-Histidine +3.655 -0.013 L-arabinopyranose maltose Glycerol D-Galactose D-(-)-Ribose Phenylacetyl-L-glutamine +3.655 0.013 L-arabinopyranose Glycerol D-Galactose D-(-)-Ribose Phenylacetyl-L-glutamine +3.671 -0.005 L-arabinopyranose D-Mannose D-(-)-Ribose +3.824 -0.011 L-arabinopyranose Stachyose D-(-)-Ribose +3.824 0.005 L-arabinopyranose D-Mannose Stachyose D-(-)-Ribose +3.824 -0.005 L-arabinopyranose D-Mannose Stachyose D-(-)-Ribose +3.824 0.011 L-arabinopyranose Stachyose ethanolamine D-(-)-Ribose +3.905 -0.012 L-arabinopyranose D-Glucose D-Mannose Raffinose Stachyose D-Fructose D-(-)-Ribose L-Aspartic acid +3.905 -0.009 L-arabinopyranose Sucrose D-Glucose D-Mannose Raffinose Stachyose D-(-)-Ribose L-Aspartic acid +3.905 0.009 L-arabinopyranose Sucrose D-Glucose D-Mannose Raffinose Stachyose D-(-)-Ribose L-Aspartic acid +4.013 0.004 L-arabinopyranose L-asparagine D-(-)-Ribose +5.248 -0.002 L-arabinopyranose maltose D-Glucose +5.248 0.003 L-arabinopyranose maltose D-Glucose +1.3329 0.0057 L-Lactic acid (sodium salt) L-Threonine +1.3328 -0.0058 L-Lactic acid (sodium salt) L-Threonine +4.117 -0.006 L-Lactic acid (sodium salt) D-(-)-Ribose +4.1173 0.0058 L-Lactic acid (sodium salt) D-(-)-Ribose
--- /dev/null Thu Jan 01 00:00:00 1970 +0000 +++ b/test-data/2DNMRAnnotation_duplicateTOCSY.tabular Fri Feb 04 09:01:11 2022 +0000 @@ -0,0 +1,3 @@ +ppm1 ppm2 commonMetabolitesList +3.7915 3.7859 L-alanine Glycerol L-glutamine +1.4861 1.4821 L-alanine Isoleucine
--- a/test-data/2DNMR_Annotation_annotationCombination.tabular Tue Feb 04 10:59:26 2020 -0500 +++ /dev/null Thu Jan 01 00:00:00 1970 +0000 @@ -1,34 +0,0 @@ -Metabolite score.HSQC score.JRES averageScore -4_hydroxyphenylpropionic_acid NA 0.5 0.5 -alanine 1 1 1 -arabinose NA 0.348837209302326 0.348837209302326 -asparagine 1 1 1 -aspartic_acid 1 1 1 -betaine 1 1 1 -butyric acid 0.333333333333333 0.916666666666667 0.625 -cadaverine 0.333333333333333 0.615384615384615 0.474358974358974 -carnitine 1 0.611111111111111 0.805555555555556 -cholinechloride 0.666666666666667 0.714285714285714 0.69047619047619 -creatine NA 0.5 0.5 -desaminotyrosine NA 0.4 0.4 -dimethylamine NA 1 1 -dimethylglycine NA 0.333333333333333 0.333333333333333 -fumaric acid 1 1 1 -gaba 0.333333333333333 NA 0.333333333333333 -galactose 0.833333333333333 0.473684210526316 0.653508771929825 -glucose 0.666666666666667 0.8125 0.739583333333333 -glycerol NA 0.666666666666667 0.666666666666667 -glycine 1 1 1 -hippuric_acid 1 1 1 -histidine 1 0.428571428571429 0.714285714285714 -indoxylsulfate NA 0.545454545454545 0.545454545454545 -isoleucine 1 0.379310344827586 0.689655172413793 -lactic acid 1 1 1 -mannose NA 0.3125 0.3125 -myo_inositol NA 0.384615384615385 0.384615384615385 -proline 1 0.409090909090909 0.704545454545455 -taurine NA 0.333333333333333 0.333333333333333 -threonine 1 1 1 -tryptophan 1 0.521739130434783 0.760869565217391 -uracil NA 0.5 0.5 -valine 0.75 0.75 0.75
--- a/test-data/2DNMR_Annotation_log.txt Tue Feb 04 10:59:26 2020 -0500 +++ /dev/null Thu Jan 01 00:00:00 1970 +0000 @@ -1,112 +0,0 @@ - PACKAGE INFO -R version 3.4.3 (2017-11-30) -Platform: x86_64-pc-linux-gnu (64-bit) -Running under: Ubuntu 14.04.5 LTS - -Matrix products: default -BLAS: /usr/lib/libblas/libblas.so.3.0 -LAPACK: /usr/lib/lapack/liblapack.so.3.0 - -locale: - [1] LC_CTYPE=en_US.UTF-8 LC_NUMERIC=C - [3] LC_TIME=en_US.UTF-8 LC_COLLATE=en_US.UTF-8 - [5] LC_MONETARY=en_US.UTF-8 LC_MESSAGES=en_US.UTF-8 - [7] LC_PAPER=en_US.UTF-8 LC_NAME=C - [9] LC_ADDRESS=C LC_TELEPHONE=C -[11] LC_MEASUREMENT=en_US.UTF-8 LC_IDENTIFICATION=C - -attached base packages: -[1] stats graphics grDevices utils datasets base - -other attached packages: -[1] tidyr_0.7.2 stringr_1.2.0 openxlsx_4.1.3 ggplot2_2.2.1 dplyr_0.7.4 -[6] batch_1.1-4 - -loaded via a namespace (and not attached): - [1] Rcpp_0.12.14 bindr_0.1 magrittr_1.5 munsell_0.4.3 - [5] colorspace_1.3-2 R6_2.2.2 rlang_0.4.2 plyr_1.8.4 - [9] tools_3.4.3 grid_3.4.3 gtable_0.2.0 cli_1.1.0 -[13] lazyeval_0.2.1 assertthat_0.2.0 tibble_1.3.4 crayon_1.3.4 -[17] bindrcpp_0.2 zip_1.0.0 purrr_0.3.3 glue_1.2.0 -[21] stringi_1.1.6 compiler_3.4.3 methods_3.4.3 scales_0.5.0 -[25] pkgconfig_2.0.1 -$xlsfile -[1] "/home/vagrant/galaxy/database/datasets/001/dataset_1825.dat" - -$cosy_2dsequences -[1] "no" - -$jres_2dsequences -[1] "yes" - -$hmbc_2dsequences -[1] "no" - -$hsqc_2dsequences -[1] "yes" - -$tocsy_2dsequences -[1] "no" - -$inHouse_DB_choices.choice -[1] "no" - -$tolppm1 -[1] 0.01 - -$tolppm2 -[1] 0.5 - -$tolppmJRES -[1] 0.002 - -$threshold -[1] 0.3 - -$unicity -[1] "no" - -$logOut -[1] "/home/vagrant/galaxy/database/datasets/002/dataset_2767.dat" - -$annotationCOSY -[1] "None" - -$ppmCommunCOSY -[1] "None" - -$annotationJRES -[1] "/home/vagrant/galaxy/database/datasets/002/dataset_2768.dat" - -$ppmCommunJRES -[1] "/home/vagrant/galaxy/database/datasets/002/dataset_2769.dat" - -$annotationHMBC -[1] "None" - -$ppmCommunHMBC -[1] "None" - -$annotationHSQC -[1] "/home/vagrant/galaxy/database/datasets/002/dataset_2770.dat" - -$ppmCommunHSQC -[1] "/home/vagrant/galaxy/database/datasets/002/dataset_2771.dat" - -$annotationTOCSY -[1] "None" - -$ppmCommunTOCSY -[1] "None" - -$annotationCombination -[1] "/home/vagrant/galaxy/database/datasets/002/dataset_2772.dat" - -$AnnotationGraph -[1] "/home/vagrant/galaxy/database/datasets/002/dataset_2773.dat" - -null device - 1 -Time difference of 1.566586 mins - -End of '2D NMR annotation' Galaxy module call: 2019-12-23 10:55:29 \ No newline at end of file
--- a/test-data/annotationHsqc.tabular Tue Feb 04 10:59:26 2020 -0500 +++ /dev/null Thu Jan 01 00:00:00 1970 +0000 @@ -1,77 +0,0 @@ -ppm1 ppm2 Metabolite score -1.487 19.022 alanine 1 -3.791 53.343 alanine 1 -2.883 37.372 asparagine 1 -2.964 37.382 asparagine 1 -4.016 54.04 asparagine 1 -2.694 39.367 Aspartic_acid 1 -2.816 39.387 Aspartic_acid 1 -3.905 54.962 Aspartic_acid 1 -3.264 56.272 betaine 1 -3.901 69.074 betaine 1 -2.164 42.369 Butyric acid 0.333333333333333 -3.024 41.961 Cadaverine 0.333333333333333 -2.444 45.792 carnitine 1 -3.232 56.932 carnitine 1 -3.44 72.954 carnitine 1 -4.571 66.903 carnitine 1 -3.208 56.704 CholineChloride 0.666666666666667 -4.072 58.227 CholineChloride 0.666666666666667 -6.526 138.157 Fumaric acid 1 -3.015 42.093 gaba 0.333333333333333 -3.502 74.756 galactose 0.833333333333333 -3.661 75.593 galactose 0.833333333333333 -3.717 78.019 galactose 0.833333333333333 -3.815 71.175 galactose 0.833333333333333 -3.866 71.993 galactose 0.833333333333333 -3.942 71.619 galactose 0.833333333333333 -4 72.162 galactose 0.833333333333333 -4.096 73.292 galactose 0.833333333333333 -4.598 99.277 galactose 0.833333333333333 -5.277 95.132 galactose 0.833333333333333 -3.425 72.307 glucose 0.666666666666667 -3.46 78.647 glucose 0.666666666666667 -3.549 74.169 glucose 0.666666666666667 -3.745 63.514 glucose 0.666666666666667 -3.841 74.223 glucose 0.666666666666667 -3.847 63.4 glucose 0.666666666666667 -4.66 98.737 glucose 0.666666666666667 -5.252 94.768 glucose 0.666666666666667 -3.566 44.267 glycine 1 -3.967 46.611 hippuric_acid 1 -7.556 131.578 hippuric_acid 1 -7.643 135.065 hippuric_acid 1 -7.837 130.019 hippuric_acid 1 -3.209 30.164 Histidine 1 -3.29 30.194 Histidine 1 -4.014 57.269 Histidine 1 -7.155 119.969 Histidine 1 -8.04 138.39 Histidine 1 -0.944 14.001 Isoleucine 1 -1.017 17.526 Isoleucine 1 -1.27 27.262 Isoleucine 1 -1.479 27.34 Isoleucine 1 -1.987 38.709 Isoleucine 1 -3.68 62.433 Isoleucine 1 -1.336 22.913 Lactic acid 1 -4.12 71.318 Lactic acid 1 -2.009 26.543 Proline 1 -2.062 31.789 Proline 1 -2.357 31.817 Proline 1 -3.346 48.831 Proline 1 -3.422 48.867 Proline 1 -4.14 63.947 Proline 1 -1.342 22.349 threonine 1 -3.609 63.354 threonine 1 -4.261 68.825 threonine 1 -3.321 29.248 tryptophan 1 -3.492 29.268 tryptophan 1 -4.066 57.824 tryptophan 1 -7.209 122.251 tryptophan 1 -7.292 124.963 tryptophan 1 -7.337 127.891 tryptophan 1 -7.554 114.838 tryptophan 1 -7.743 121.238 tryptophan 1 -1 19.497 valine 0.75 -1.049 20.77 valine 0.75 -2.281 31.893 valine 0.75
--- a/test-data/annotationJres.tabular Tue Feb 04 10:59:26 2020 -0500 +++ /dev/null Thu Jan 01 00:00:00 1970 +0000 @@ -1,314 +0,0 @@ -ppm1 ppm2 Metabolite score -2.452 0 4_hydroxyphenylpropionic_acid 0.5 -2.452 -0.013 4_hydroxyphenylpropionic_acid 0.5 -2.452 0.013 4_hydroxyphenylpropionic_acid 0.5 -2.818 -0.013 4_hydroxyphenylpropionic_acid 0.5 -2.818 0.013 4_hydroxyphenylpropionic_acid 0.5 -1.487 0.006 alanine 1 -1.487 -0.006 alanine 1 -3.791 -0.006 alanine 1 -3.791 -0.018 alanine 1 -3.791 0.006 alanine 1 -3.791 0.018 alanine 1 -3.517 0.002 arabinose 0.348837209302326 -3.655 -0.013 arabinose 0.348837209302326 -3.655 0.013 arabinose 0.348837209302326 -3.671 -0.005 arabinose 0.348837209302326 -3.824 -0.011 arabinose 0.348837209302326 -3.824 0.005 arabinose 0.348837209302326 -3.824 -0.005 arabinose 0.348837209302326 -3.824 0.011 arabinose 0.348837209302326 -3.905 -0.012 arabinose 0.348837209302326 -3.905 -0.009 arabinose 0.348837209302326 -3.905 0.009 arabinose 0.348837209302326 -3.905 0.009 arabinose 0.348837209302326 -3.905 -0.012 arabinose 0.348837209302326 -3.905 -0.009 arabinose 0.348837209302326 -4.013 0.004 arabinose 0.348837209302326 -5.248 -0.002 arabinose 0.348837209302326 -5.248 0.003 arabinose 0.348837209302326 -2.881 -0.008 asparagine 1 -2.881 0.02 asparagine 1 -2.881 0.008 asparagine 1 -2.881 -0.02 asparagine 1 -2.961 0.01 asparagine 1 -2.961 -0.018 asparagine 1 -2.961 -0.011 asparagine 1 -2.961 0.018 asparagine 1 -4.014 -0.01 asparagine 1 -4.014 0.01 asparagine 1 -4.014 -0.002 asparagine 1 -4.014 0.002 asparagine 1 -2.694 0.007 Aspartic_acid 1 -2.694 0.022 Aspartic_acid 1 -2.694 -0.008 Aspartic_acid 1 -2.817 -0.011 Aspartic_acid 1 -2.817 0.011 Aspartic_acid 1 -2.817 0.018 Aspartic_acid 1 -2.817 -0.018 Aspartic_acid 1 -3.906 -0.01 Aspartic_acid 1 -3.906 0.01 Aspartic_acid 1 -3.906 -0.004 Aspartic_acid 1 -3.906 0.004 Aspartic_acid 1 -3.906 0.01 Aspartic_acid 1 -3.906 -0.01 Aspartic_acid 1 -3.273 0 betaine 1 -3.908 0 betaine 1 -0.898 -0.012 Butyric acid 0.916666666666667 -0.902 0 Butyric acid 0.916666666666667 -0.907 0.013 Butyric acid 0.916666666666667 -1.565 0.007 Butyric acid 0.916666666666667 -1.57 0.019 Butyric acid 0.916666666666667 -1.565 -0.03 Butyric acid 0.916666666666667 -1.565 -0.006 Butyric acid 0.916666666666667 -1.57 -0.018 Butyric acid 0.916666666666667 -2.165 0 Butyric acid 0.916666666666667 -2.17 0.013 Butyric acid 0.916666666666667 -2.17 -0.012 Butyric acid 0.916666666666667 -1.726 0.025 Cadaverine 0.615384615384615 -1.73 -0.026 Cadaverine 0.615384615384615 -1.729 0 Cadaverine 0.615384615384615 -1.729 0.013 Cadaverine 0.615384615384615 -1.731 -0.013 Cadaverine 0.615384615384615 -3.022 0.012 Cadaverine 0.615384615384615 -3.022 -0.012 Cadaverine 0.615384615384615 -3.024 0 Cadaverine 0.615384615384615 -2.426 -0.018 carnitine 0.611111111111111 -2.426 0.007 carnitine 0.611111111111111 -2.426 0.018 carnitine 0.611111111111111 -2.446 0.013 carnitine 0.611111111111111 -2.446 -0.013 carnitine 0.611111111111111 -2.445 0.027 carnitine 0.611111111111111 -2.445 0 carnitine 0.611111111111111 -2.445 -0.027 carnitine 0.611111111111111 -2.445 0 carnitine 0.611111111111111 -2.446 -0.038 carnitine 0.611111111111111 -2.445 -0.027 carnitine 0.611111111111111 -2.445 0.027 carnitine 0.611111111111111 -2.446 0.038 carnitine 0.611111111111111 -2.446 -0.013 carnitine 0.611111111111111 -2.446 0.013 carnitine 0.611111111111111 -2.465 -0.007 carnitine 0.611111111111111 -2.465 0.007 carnitine 0.611111111111111 -2.465 0.019 carnitine 0.611111111111111 -2.465 0.019 carnitine 0.611111111111111 -2.465 -0.007 carnitine 0.611111111111111 -2.465 -0.019 carnitine 0.611111111111111 -2.465 0.007 carnitine 0.611111111111111 -3.234 0 carnitine 0.611111111111111 -3.422 0.015 carnitine 0.611111111111111 -3.422 -0.015 carnitine 0.611111111111111 -3.434 0 carnitine 0.611111111111111 -3.422 -0.009 carnitine 0.611111111111111 -3.438 -0.008 carnitine 0.611111111111111 -3.438 0.008 carnitine 0.611111111111111 -3.209 -0.001 CholineChloride 0.714285714285714 -3.529 0.008 CholineChloride 0.714285714285714 -3.529 -0.008 CholineChloride 0.714285714285714 -4.069 0 CholineChloride 0.714285714285714 -4.069 0.009 CholineChloride 0.714285714285714 -3.937 0 creatine 0.5 -2.454 -0.013 Desaminotyrosine 0.4 -2.454 0.013 Desaminotyrosine 0.4 -2.822 -0.013 Desaminotyrosine 0.4 -2.822 0.012 Desaminotyrosine 0.4 -2.729 0 Dimethylamine 1 -3.741 0 Dimethylglycine 0.333333333333333 -6.519 0 Fumaric acid 1 -3.5 -0.002 galactose 0.473684210526316 -3.498 0.015 galactose 0.473684210526316 -3.658 -0.011 galactose 0.473684210526316 -3.658 -0.005 galactose 0.473684210526316 -3.658 0.005 galactose 0.473684210526316 -3.658 0.011 galactose 0.473684210526316 -3.723 -0.016 galactose 0.473684210526316 -3.723 0.016 galactose 0.473684210526316 -3.723 0.016 galactose 0.473684210526316 -3.723 -0.004 galactose 0.473684210526316 -3.723 -0.016 galactose 0.473684210526316 -3.723 0.004 galactose 0.473684210526316 -3.736 0 galactose 0.473684210526316 -3.76 -0.002 galactose 0.473684210526316 -3.762 0.008 galactose 0.473684210526316 -3.763 -0.009 galactose 0.473684210526316 -3.812 -0.012 galactose 0.473684210526316 -3.812 0.005 galactose 0.473684210526316 -3.812 -0.006 galactose 0.473684210526316 -3.812 0.012 galactose 0.473684210526316 -3.863 -0.012 galactose 0.473684210526316 -3.863 -0.006 galactose 0.473684210526316 -3.863 0.006 galactose 0.473684210526316 -3.863 0.012 galactose 0.473684210526316 -4.595 -0.007 galactose 0.473684210526316 -4.595 0.007 galactose 0.473684210526316 -5.274 -0.004 galactose 0.473684210526316 -5.274 0.004 galactose 0.473684210526316 -3.256 -0.014 glucose 0.8125 -3.255 0 glucose 0.8125 -3.422 0.016 glucose 0.8125 -3.411 0.016 glucose 0.8125 -3.422 -0.016 glucose 0.8125 -3.411 -0.016 glucose 0.8125 -3.422 0 glucose 0.8125 -3.475 0 glucose 0.8125 -3.475 -0.011 glucose 0.8125 -3.475 -0.005 glucose 0.8125 -3.475 0.005 glucose 0.8125 -3.475 0.011 glucose 0.8125 -3.475 0.015 glucose 0.8125 -3.502 -0.015 glucose 0.8125 -3.502 0 glucose 0.8125 -3.502 0.015 glucose 0.8125 -3.545 0.011 glucose 0.8125 -3.545 -0.005 glucose 0.8125 -3.545 0.005 glucose 0.8125 -3.545 -0.012 glucose 0.8125 -3.731 -0.015 glucose 0.8125 -3.721 -0.016 glucose 0.8125 -3.732 0.015 glucose 0.8125 -3.721 0.016 glucose 0.8125 -3.732 0.015 glucose 0.8125 -3.732 -0.006 glucose 0.8125 -3.731 -0.015 glucose 0.8125 -3.732 0.005 glucose 0.8125 -3.843 0.009 glucose 0.8125 -3.839 0.011 glucose 0.8125 -3.844 -0.01 glucose 0.8125 -3.839 -0.011 glucose 0.8125 -3.901 -0.012 glucose 0.8125 -3.901 -0.009 glucose 0.8125 -3.901 0.008 glucose 0.8125 -3.902 0.012 glucose 0.8125 -3.901 -0.012 glucose 0.8125 -3.901 -0.009 glucose 0.8125 -4.655 0.007 glucose 0.8125 -4.655 -0.006 glucose 0.8125 -5.243 -0.003 glucose 0.8125 -5.243 0.003 glucose 0.8125 -3.656 -0.013 glycerol 0.666666666666667 -3.656 -0.006 glycerol 0.666666666666667 -3.656 0.006 glycerol 0.666666666666667 -3.791 -0.011 glycerol 0.666666666666667 -3.791 0 glycerol 0.666666666666667 -3.791 0.01 glycerol 0.666666666666667 -3.791 -0.007 glycerol 0.666666666666667 -3.791 -0.018 glycerol 0.666666666666667 -3.791 0.007 glycerol 0.666666666666667 -3.791 0.018 glycerol 0.666666666666667 -3.568 0 glycine 1 -3.969 0 hippuric_acid 1 -7.555 0.013 hippuric_acid 1 -7.555 0 hippuric_acid 1 -7.555 -0.013 hippuric_acid 1 -7.642 0 hippuric_acid 1 -7.642 -0.013 hippuric_acid 1 -7.642 0.012 hippuric_acid 1 -7.836 -0.007 hippuric_acid 1 -7.836 0.007 hippuric_acid 1 -4.015 -0.011 Histidine 0.428571428571429 -4.015 0.01 Histidine 0.428571428571429 -4.015 -0.002 Histidine 0.428571428571429 -4.015 0.002 Histidine 0.428571428571429 -7.156 0 Histidine 0.428571428571429 -8.043 0 Histidine 0.428571428571429 -7.21 0.013 indoxylsulfate 0.545454545454545 -7.21 -0.013 indoxylsulfate 0.545454545454545 -7.21 0 indoxylsulfate 0.545454545454545 -7.283 -0.013 indoxylsulfate 0.545454545454545 -7.283 0.013 indoxylsulfate 0.545454545454545 -7.283 0 indoxylsulfate 0.545454545454545 -0.946 -0.012 Isoleucine 0.379310344827586 -0.948 0.012 Isoleucine 0.379310344827586 -0.949 0 Isoleucine 0.379310344827586 -1.017 0.007 Isoleucine 0.379310344827586 -1.017 -0.006 Isoleucine 0.379310344827586 -1.269 0.025 Isoleucine 0.379310344827586 -1.269 -0.024 Isoleucine 0.379310344827586 -1.269 -0.011 Isoleucine 0.379310344827586 -1.269 0.011 Isoleucine 0.379310344827586 -3.687 -0.004 Isoleucine 0.379310344827586 -3.683 0.003 Isoleucine 0.379310344827586 -1.333 0.006 Lactic acid 1 -1.333 -0.006 Lactic acid 1 -1.333 0.006 Lactic acid 1 -4.117 -0.017 Lactic acid 1 -4.118 0.017 Lactic acid 1 -4.117 -0.006 Lactic acid 1 -4.117 0.006 Lactic acid 1 -3.741 -0.005 mannose 0.3125 -3.741 -0.015 mannose 0.3125 -3.741 0.005 mannose 0.3125 -3.823 0.004 mannose 0.3125 -3.823 -0.004 mannose 0.3125 -3.856 -0.011 mannose 0.3125 -3.856 -0.005 mannose 0.3125 -3.856 0.005 mannose 0.3125 -3.856 0.011 mannose 0.3125 -3.91 -0.012 mannose 0.3125 -3.91 0.009 mannose 0.3125 -3.91 0.009 mannose 0.3125 -3.91 0.012 mannose 0.3125 -3.91 -0.012 mannose 0.3125 -3.943 0 mannose 0.3125 -3.956 0 mannose 0.3125 -3.544 0.011 myo_inositol 0.384615384615385 -3.544 -0.006 myo_inositol 0.384615384615385 -3.544 0.006 myo_inositol 0.384615384615385 -3.544 -0.011 myo_inositol 0.384615384615385 -4.073 0 myo_inositol 0.384615384615385 -2.012 -0.021 Proline 0.409090909090909 -2.011 -0.01 Proline 0.409090909090909 -2.012 0.01 Proline 0.409090909090909 -2.012 0.021 Proline 0.409090909090909 -2.011 0 Proline 0.409090909090909 -2.356 -0.004 Proline 0.409090909090909 -2.356 -0.017 Proline 0.409090909090909 -2.356 0.004 Proline 0.409090909090909 -2.356 0.018 Proline 0.409090909090909 -3.347 -0.009 Proline 0.409090909090909 -3.347 0.01 Proline 0.409090909090909 -3.423 0.001 Proline 0.409090909090909 -3.423 -0.009 Proline 0.409090909090909 -3.423 0.01 Proline 0.409090909090909 -4.141 0.013 Proline 0.409090909090909 -4.141 -0.013 Proline 0.409090909090909 -4.14 -0.002 Proline 0.409090909090909 -4.142 0.002 Proline 0.409090909090909 -3.275 0 taurine 0.333333333333333 -3.43 0 taurine 0.333333333333333 -1.34 0.005 threonine 1 -1.339 -0.006 threonine 1 -1.34 0.005 threonine 1 -3.603 0.004 threonine 1 -3.604 -0.005 threonine 1 -4.26 -0.01 threonine 1 -4.258 -0.02 threonine 1 -4.26 0.01 threonine 1 -4.259 0 threonine 1 -4.259 0.021 threonine 1 -4.063 -0.002 tryptophan 0.521739130434783 -7.204 0.012 tryptophan 0.521739130434783 -7.204 -0.012 tryptophan 0.521739130434783 -7.204 0 tryptophan 0.521739130434783 -7.288 -0.012 tryptophan 0.521739130434783 -7.288 0.013 tryptophan 0.521739130434783 -7.288 0 tryptophan 0.521739130434783 -7.334 0 tryptophan 0.521739130434783 -7.548 -0.006 tryptophan 0.521739130434783 -7.549 0.007 tryptophan 0.521739130434783 -7.738 -0.006 tryptophan 0.521739130434783 -7.738 0.006 tryptophan 0.521739130434783 -7.552 -0.006 Uracil 0.5 -7.552 0.007 Uracil 0.5 -0.998 -0.006 valine 0.75 -0.996 0.006 valine 0.75 -1.047 -0.006 valine 0.75 -1.047 0.006 valine 0.75 -2.279 -0.004 valine 0.75 -2.28 0.003 valine 0.75 -2.28 0.016 valine 0.75 -2.281 -0.016 valine 0.75 -2.28 -0.008 valine 0.75 -2.28 0.008 valine 0.75 -3.62 -0.004 valine 0.75 -3.62 0.004 valine 0.75
--- a/test-data/duplicateHsqc.tabular Tue Feb 04 10:59:26 2020 -0500 +++ /dev/null Thu Jan 01 00:00:00 1970 +0000 @@ -1,19 +0,0 @@ -ppm1 ppm2 commonMetabolitesList -3.024 41.961 Cadaverine 5aminovalericacid gaba Lysine -3.232 56.932 carnitine gpc -4.072 58.227 CholineChloride tryptophan -3.015 42.093 gaba 5aminovalericacid Cadaverine -3.502 74.756 galactose cholic_acid -3.661 75.593 galactose mannose -3.866 71.993 galactose stachyose -3.942 71.619 galactose ribose -4 72.162 galactose stachyose -3.425 72.307 glucose maltose -3.549 74.169 glucose myo_inositol -4.66 98.737 glucose maltose -5.252 94.768 glucose maltose -4.12 71.318 Lactic acid ribose -4.066 57.824 tryptophan CholineChloride -7.209 122.251 tryptophan indoxylsulfate -7.292 124.963 tryptophan indoxylsulfate -1 19.497 valine cholic_acid
--- a/test-data/duplicateJres.tabular Tue Feb 04 10:59:26 2020 -0500 +++ /dev/null Thu Jan 01 00:00:00 1970 +0000 @@ -1,197 +0,0 @@ -ppm1 ppm2 commonMetabolitesList -2.452 0 4_hydroxyphenylpropionic_acid carnitine Desaminotyrosine glutamine -2.452 -0.013 4_hydroxyphenylpropionic_acid carnitine Desaminotyrosine glutamine -2.452 0.013 4_hydroxyphenylpropionic_acid carnitine Desaminotyrosine -2.818 -0.013 4_hydroxyphenylpropionic_acid Aspartic_acid Desaminotyrosine -2.818 0.013 4_hydroxyphenylpropionic_acid Aspartic_acid Desaminotyrosine -3.791 -0.006 alanine glycerol raffinose stachyose -3.791 -0.018 alanine glycerol maltose raffinose stachyose -3.791 0.006 alanine glycerol raffinose stachyose -3.791 0.018 alanine glycerol raffinose stachyose -3.655 -0.013 arabinose galactose glycerol maltose ribose -3.655 0.013 arabinose galactose glycerol ribose -3.671 -0.005 arabinose mannose ribose -3.824 -0.011 arabinose ribose stachyose -3.824 0.005 arabinose mannose ribose stachyose -3.824 -0.005 arabinose mannose ribose stachyose -3.824 0.011 arabinose Ethanolamine ribose stachyose -3.905 -0.012 arabinose Aspartic_acid glucose mannose raffinose ribose stachyose -3.905 -0.009 arabinose Aspartic_acid glucose mannose raffinose ribose stachyose sucrose -3.905 0.009 arabinose Aspartic_acid glucose mannose raffinose ribose stachyose sucrose -4.013 0.004 arabinose asparagine Histidine ribose -5.248 -0.002 arabinose glucose maltose -5.248 0.003 arabinose glucose maltose -4.014 -0.01 asparagine Histidine -4.014 0.01 asparagine Histidine -4.014 -0.002 asparagine Histidine raffinose ribose -4.014 0.002 asparagine arabinose Histidine raffinose -2.817 -0.011 Aspartic_acid 4_hydroxyphenylpropionic_acid Desaminotyrosine -2.817 0.011 Aspartic_acid 4_hydroxyphenylpropionic_acid Desaminotyrosine -3.906 -0.01 Aspartic_acid arabinose glucose mannose raffinose stachyose -3.906 0.01 Aspartic_acid arabinose glucose mannose raffinose stachyose -3.906 -0.004 Aspartic_acid raffinose stachyose -3.906 0.004 Aspartic_acid raffinose stachyose -3.273 0 betaine taurine -3.908 0 betaine cholic_acid raffinose stachyose -0.898 -0.012 Butyric acid 2_hydroxybutyric_acid 3_methyl-2-oxovaleric acid valeric_acid -0.902 0 Butyric acid 2_hydroxybutyric_acid 3_methyl-2-oxovaleric acid valeric_acid -0.907 0.013 Butyric acid 2_hydroxybutyric_acid 3_methyl-2-oxovaleric acid -1.57 0.019 Butyric acid cholic_acid -1.57 -0.018 Butyric acid cholic_acid -2.17 0.013 Butyric acid octanoic_acid -2.17 -0.012 Butyric acid octanoic_acid -1.73 -0.026 Cadaverine Lysine -1.729 0 Cadaverine Lysine -1.729 0.013 Cadaverine Lysine -1.731 -0.013 Cadaverine Lysine -3.022 0.012 Cadaverine 5aminovalericacid gaba -3.022 -0.012 Cadaverine 5aminovalericacid gaba -3.024 0 Cadaverine 5aminovalericacid gaba Lysine -2.446 0.013 carnitine 4_hydroxyphenylpropionic_acid Desaminotyrosine -2.446 -0.013 carnitine 4_hydroxyphenylpropionic_acid Desaminotyrosine -2.445 0.027 carnitine glutamine -2.445 0 carnitine 4_hydroxyphenylpropionic_acid Desaminotyrosine -3.234 0 carnitine gpc -3.422 0.015 carnitine glucose -3.422 -0.015 carnitine glucose -3.434 0 carnitine maltose rahmnose taurine -3.422 -0.009 carnitine Proline taurine -3.529 0.008 CholineChloride ribose -3.529 -0.008 CholineChloride ribose -4.069 0 CholineChloride cholic_acid myo_inositol raffinose stachyose sucrose tryptophan -4.069 0.009 CholineChloride tryptophan -3.937 0 creatine mannose ribose -2.454 -0.013 Desaminotyrosine 4_hydroxyphenylpropionic_acid carnitine glutamine -2.454 0.013 Desaminotyrosine 4_hydroxyphenylpropionic_acid carnitine -2.822 -0.013 Desaminotyrosine 4_hydroxyphenylpropionic_acid Aspartic_acid -2.822 0.012 Desaminotyrosine 4_hydroxyphenylpropionic_acid Aspartic_acid -3.741 0 Dimethylglycine galactose -3.5 -0.002 galactose cholic_acid glucose -3.498 0.015 galactose glucose -3.658 -0.011 galactose arabinose glycerol -3.658 -0.005 galactose Ethanol glycerol ribose stachyose -3.658 0.005 galactose Ethanol glycerol ribose stachyose -3.658 0.011 galactose arabinose -3.723 -0.016 galactose glucose -3.723 0.016 galactose glucose -3.723 -0.004 galactose glucose -3.723 0.004 galactose glucose -3.736 0 galactose Dimethylglycine -3.76 -0.002 galactose Lysine phenylacetylglycine -3.762 0.008 galactose glucose Lysine maltose raffinose ribose -3.763 -0.009 galactose glutamic acid Lysine raffinose ribose -3.812 -0.012 galactose maltose rahmnose ribose -3.812 0.005 galactose maltose rahmnose sucrose -3.812 -0.006 galactose maltose rahmnose ribose sucrose -3.812 0.012 galactose maltose rahmnose ribose -3.863 -0.012 galactose maltose mannose Methionine rahmnose stachyose -3.863 -0.006 galactose Ethanolamine maltose mannose Serine stachyose -3.863 0.006 galactose maltose mannose ribose Serine stachyose -3.863 0.012 galactose maltose mannose Methionine rahmnose stachyose -3.255 0 glucose arginine -3.422 0.016 glucose carnitine -3.422 -0.016 glucose carnitine -3.422 0 glucose Proline taurine -3.475 0 glucose sucrose -3.475 0.015 glucose sucrose -3.502 -0.015 glucose galactose -3.502 0 glucose cholic_acid galactose -3.502 0.015 glucose galactose -3.545 0.011 glucose myo_inositol -3.545 -0.005 glucose myo_inositol ribose -3.545 0.005 glucose myo_inositol ribose -3.545 -0.012 glucose myo_inositol -3.731 -0.015 glucose galactose stachyose -3.721 -0.016 glucose galactose -3.732 0.015 glucose galactose mannose stachyose -3.721 0.016 glucose galactose -3.732 -0.006 glucose galactose mannose stachyose -3.732 0.005 glucose galactose mannose stachyose -3.843 0.009 glucose inosine raffinose sucrose -3.839 0.011 glucose raffinose ribose -3.844 -0.01 glucose Ethanolamine raffinose sucrose -3.839 -0.011 glucose raffinose ribose -3.901 -0.012 glucose arabinose Aspartic_acid mannose raffinose ribose stachyose -3.901 -0.009 glucose arabinose Aspartic_acid mannose raffinose ribose stachyose sucrose -3.901 0.008 glucose arabinose Aspartic_acid mannose raffinose ribose sucrose -3.902 0.012 glucose arabinose Aspartic_acid mannose raffinose ribose stachyose -5.243 -0.003 glucose arabinose maltose -5.243 0.003 glucose arabinose maltose -3.656 -0.013 glycerol arabinose galactose maltose ribose -3.656 -0.006 glycerol arabinose Ethanol galactose ribose stachyose -3.656 0.006 glycerol Ethanol galactose ribose stachyose -3.791 -0.011 glycerol arginine glutamine ornithine -3.791 0 glycerol arginine glutamine maltose ornithine -3.791 0.01 glycerol arginine glutamic acid glutamine ornithine -3.791 -0.007 glycerol alanine -3.791 0.007 glycerol alanine -3.969 0 hippuric_acid maltose raffinose -4.015 -0.011 Histidine asparagine -4.015 0.01 Histidine asparagine -4.015 -0.002 Histidine asparagine raffinose ribose -4.015 0.002 Histidine arabinose asparagine raffinose -7.21 0.013 indoxylsulfate tryptophan -7.21 -0.013 indoxylsulfate tryptophan -7.21 0 indoxylsulfate indole_3_propionic_acid tryptophan -7.283 -0.013 indoxylsulfate tryptophan -7.283 0.013 indoxylsulfate tryptophan -7.283 0 indoxylsulfate tryptophan -3.687 -0.004 Isoleucine raffinose ribose -3.683 0.003 Isoleucine raffinose sucrose -1.333 0.006 Lactic acid threonine -1.333 -0.006 Lactic acid threonine -4.117 -0.006 Lactic acid ribose -4.117 0.006 Lactic acid ribose -3.741 -0.005 mannose galactose glucose raffinose stachyose -3.741 -0.015 mannose galactose raffinose stachyose -3.741 0.005 mannose galactose glucose raffinose stachyose -3.823 0.004 mannose arabinose maltose ribose stachyose -3.823 -0.004 mannose arabinose maltose ribose stachyose -3.856 -0.011 mannose galactose maltose raffinose ribose stachyose -3.856 -0.005 mannose galactose hydroxyisovaleric inosine ribose stachyose -3.856 0.005 mannose galactose hydroxyisovaleric inosine ribose stachyose -3.856 0.011 mannose galactose maltose raffinose ribose stachyose sucrose -3.91 -0.012 mannose arabinose Aspartic_acid glucose maltose raffinose stachyose -3.91 0.009 mannose arabinose Aspartic_acid glucose maltose raffinose stachyose -3.91 0.012 mannose arabinose Aspartic_acid glucose maltose raffinose stachyose -3.943 0 mannose arabinose creatine ribose -3.956 0 mannose arabinose raffinose -3.544 0.011 myo_inositol glucose -3.544 -0.006 myo_inositol glucose ribose -3.544 0.006 myo_inositol glucose ribose -3.544 -0.011 myo_inositol glucose -4.073 0 myo_inositol cholic_acid CholineChloride raffinose stachyose -2.012 -0.021 Proline hydroxyisovaleric -2.011 -0.01 Proline hydroxyisovaleric -2.012 0.01 Proline hydroxyisovaleric -2.012 0.021 Proline hydroxyisovaleric -3.423 0.001 Proline glucose taurine -3.423 -0.009 Proline carnitine taurine -3.423 0.01 Proline carnitine taurine -4.141 0.013 Proline stachyose -4.141 -0.013 Proline ribose stachyose -4.14 -0.002 Proline ribose -4.142 0.002 Proline ribose stachyose -3.275 0 taurine betaine -3.43 0 taurine carnitine glucose maltose Proline -1.34 0.005 threonine Lactic acid -1.339 -0.006 threonine Lactic acid -3.603 0.004 threonine maltose rahmnose -3.604 -0.005 threonine rahmnose -4.063 -0.002 tryptophan cholic_acid CholineChloride raffinose stachyose sucrose -7.204 0.012 tryptophan indoxylsulfate -7.204 -0.012 tryptophan indoxylsulfate -7.204 0 tryptophan indoxylsulfate -7.288 -0.012 tryptophan indoxylsulfate -7.288 0.013 tryptophan indoxylsulfate -7.288 0 tryptophan indoxylsulfate -7.548 -0.006 tryptophan Uracil -7.549 0.007 tryptophan Uracil -7.552 -0.006 Uracil tryptophan -7.552 0.007 Uracil tryptophan -0.998 -0.006 valine cholic_acid -0.996 0.006 valine cholic_acid -1.047 -0.006 valine 2_methylbutyric_acid -1.047 0.006 valine 2_methylbutyric_acid -3.62 -0.004 valine gpc rahmnose -3.62 0.004 valine gpc rahmnose
--- a/viridis.R Tue Feb 04 10:59:26 2020 -0500 +++ b/viridis.R Fri Feb 04 09:01:11 2022 +0000 @@ -1,5 +1,4 @@ -viridis <- function (n, alpha = 1, begin = 0, end = 1, direction = 1, option = "D") -{ +viridis <- function(n, alpha = 1, begin = 0, end = 1, direction = 1, option = "D") { if (begin < 0 | begin > 1 | end < 0 | end > 1) { stop("begin and end must be in [0,1]") } @@ -11,18 +10,17 @@ begin <- end end <- tmp } - option <- switch(EXPR = option, A = "A", magma = "A", - B = "B", inferno = "B", C = "C", plasma = "C", - D = "D", viridis = "D", E = "E", cividis = "E", - { + option <- switch(EXPR = option, A = "A", magma = "A", + B = "B", inferno = "B", C = "C", plasma = "C", + D = "D", viridis = "D", E = "E", cividis = "E", { warning(paste0("Option '", option, "' does not exist. Defaulting to 'viridis'.")) "D" }) - map <- viridisLite::viridis.map[viridisLite::viridis.map$opt == + map <- viridisLite::viridis.map[viridisLite::viridis.map$opt == option, ] map_cols <- grDevices::rgb(map$R, map$G, map$B) - fn_cols <- grDevices::colorRamp(map_cols, space = "Lab", + fn_cols <- grDevices::colorRamp(map_cols, space = "Lab", interpolate = "spline") - cols <- fn_cols(seq(begin, end, length.out = n))/255 + cols <- fn_cols(seq(begin, end, length.out = n)) / 255 grDevices::rgb(cols[, 1], cols[, 2], cols[, 3], alpha = alpha) -} \ No newline at end of file +}
