From 69df6c23026094e0d1f431cab21b4c16c9df7b19 Mon Sep 17 00:00:00 2001 From: hechth Date: Thu, 24 Oct 2024 12:33:53 +0200 Subject: [PATCH 1/8] added tabular version of the tool --- tools/isolib/isolib.R | 83 +++++- tools/isolib/isolib.xml | 31 ++- tools/isolib/test-data/test2.tabular | 123 +++++++++ tools/isolib/test-data/test3.tabular | 366 +++++++++++++++++++++++++++ 4 files changed, 586 insertions(+), 17 deletions(-) create mode 100644 tools/isolib/test-data/test2.tabular create mode 100644 tools/isolib/test-data/test3.tabular diff --git a/tools/isolib/isolib.R b/tools/isolib/isolib.R index 7804e15b..43050d2f 100644 --- a/tools/isolib/isolib.R +++ b/tools/isolib/isolib.R @@ -4,22 +4,37 @@ library(MsBackendMsp) library(MetaboCoreUtils) library(readr) -#' @param args A list of command line arguments. -main <- function() { - data(isotopes) - data(adducts) +parse_args <- function() { args <- commandArgs(trailingOnly = TRUE) + compound_table <- read_tsv( file = args[1], col_types = "ccd", col_select = tidyselect::all_of(c("name", "formula")) | tidyselect::any_of("rt") ) - adducts_to_use <- c(unlist(strsplit(args[2], ",", fixed = TRUE))) - chemforms <- compound_table$formula - chemforms <- check_chemform(isotopes, chemforms)[, 2] + parsed <- list( + compound_table = compound_table, + adducts_to_use = c(unlist(strsplit(args[2], ",", fixed = TRUE))), + threshold = as.numeric(args[3]), + append_adducts = args[4], + out_format=args[5], + outfile = args[6] + ) + return(parsed) +} + +generate_isotope_spectra <- function(compound_table, adducts_to_use, append_adducts, threshold) { + data(isotopes) + data(adducts) + monoisotopic <- isotopes |> + dplyr::group_by(element) |> + dplyr::slice_max(abundance, n = 1) |> + dplyr::filter(!stringr::str_detect(element, "\\[|\\]")) + + chemforms <- check_chemform(isotopes, compound_table$formula)[, 2] spectra <- data.frame() for (current in adducts_to_use) { @@ -36,7 +51,7 @@ main <- function() { adduct_string <- paste0("[", adduct$Name, "]", charge_string) precursor_mz <- calculateMass(multiplied_chemforms) + adduct$Mass - if (args[4] == TRUE) { + if (append_adducts == TRUE) { names <- paste(compound_table$name, paste0("(", adduct$Name, ")"), sep = " ") } else { names <- compound_table$name @@ -60,26 +75,68 @@ main <- function() { isotopes = isotopes, chemforms = merged_chemforms, charge = adduct$Charge, - threshold = as.numeric(args[3]), + threshold = threshold, ) mzs <- list() intensities <- list() + isos <- list() + for (i in seq_along(patterns)) { mzs <- append(mzs, list(patterns[[i]][, 1])) intensities <- append(intensities, list(patterns[[i]][, 2])) + compositions <- as.data.frame(patterns[[i]][,-c(1,2)]) |> # select all columns which describe the elemental composition + dplyr::select(-tidyselect::any_of(monoisotopic$isotope)) |> # remove all 12C, 35Cl etc. + dplyr::select_if(~ !all(. == 0)) # remove isotopes which don't occur + compositions <- compositions |> + dplyr::rowwise() |> + dplyr::mutate(isotopes = paste( # combine elemental composition into single string + purrr::map2_chr(names(compositions), dplyr::c_across(everything()), ~ paste(.x, .y, sep = ":")), collapse = ", ") + ) |> + dplyr::ungroup() |> + dplyr::select(isotopes) + isos <- append(isos, list(compositions$isotopes)) } spectra_df$mz <- mzs spectra_df$intensity <- intensities + spectra_df$isotopes <- isos spectra <- rbind(spectra, spectra_df) } + return(spectra) +} + +write_to_msp <- function(spectra, file) { + sps <- Spectra(dplyr::select(spectra, -isotopes)) + export(sps, MsBackendMsp(), file = file) +} + +write_to_table <- function(spectra, file) { + entries <- spectra |> + dplyr::rowwise() |> + dplyr::mutate(peaks = paste(unlist(mz), collapse=";"))|> + dplyr::mutate(isos = paste(unlist(isotopes), collapse=";") + ) + result <- tidyr::separate_longer_delim(entries, tidyselect::all_of(c("peaks", "isos")), ";") |> + dplyr::select(-c("mz", "intensity", "isotopes")) |> + dplyr::rename(mz = peaks, isotopes=isos) + readr::write_tsv(result, file=file) +} + +main <- function() { + args <- parse_args() + spectra <- generate_isotope_spectra(args$compound_table, args$adducts_to_use, args$append_adducts, args$threshold) - sps <- Spectra(spectra) - export(sps, MsBackendMsp(), file = args[5]) + if(args$out_format == "msp") { + write_to_msp(spectra, args$outfile) + } else if (args$out_format == "tabular") { + write_to_table(spectra, args$outfile) + } } -# Get the command line arguments -args <- commandArgs(trailingOnly = TRUE) # Call the main function main() + +# > u <- dplyr::mutate(x, peaks = paste(unlist(mz), collapse=",")) +# > res <- tidyr::separate_longer_delim(u, peaks, ",") +# > monoisotopic <- isotopes |> dplyr::group_by(element) |> dplyr::slice_max(abundance, n = 1) |> dplyr::filter(!stringr::str_detect(element, "\\[|\\]")) diff --git a/tools/isolib/isolib.xml b/tools/isolib/isolib.xml index af83e572..60c3f698 100644 --- a/tools/isolib/isolib.xml +++ b/tools/isolib/isolib.xml @@ -1,5 +1,5 @@ - - create an isotopic pattern library for given compounds and adducts + + create an isotopic pattern library for given compounds and adducts based on enviPat bioconductor-msbackendmsp r-envipat r-readr + r-tidyr + r-stringr + r-purrr @@ -46,9 +49,18 @@ + + + + - + + + + + + @@ -60,6 +72,17 @@ + + + + + + + + + + + Date: Thu, 24 Oct 2024 13:28:24 +0200 Subject: [PATCH 2/8] made updates to add the isotope composition to the formula --- tools/isolib/isolib.R | 18 +++++++++++++----- tools/isolib/isolib.xml | 32 +++++++++++++++++++++++++------- 2 files changed, 38 insertions(+), 12 deletions(-) diff --git a/tools/isolib/isolib.R b/tools/isolib/isolib.R index 43050d2f..2de7c899 100644 --- a/tools/isolib/isolib.R +++ b/tools/isolib/isolib.R @@ -19,8 +19,9 @@ parse_args <- function() { adducts_to_use = c(unlist(strsplit(args[2], ",", fixed = TRUE))), threshold = as.numeric(args[3]), append_adducts = args[4], - out_format=args[5], - outfile = args[6] + append_isotopes = args[5], + out_format=args[6], + outfile = args[7] ) return(parsed) } @@ -111,7 +112,7 @@ write_to_msp <- function(spectra, file) { export(sps, MsBackendMsp(), file = file) } -write_to_table <- function(spectra, file) { +write_to_table <- function(spectra, file, append_isotopes) { entries <- spectra |> dplyr::rowwise() |> dplyr::mutate(peaks = paste(unlist(mz), collapse=";"))|> @@ -119,7 +120,14 @@ write_to_table <- function(spectra, file) { ) result <- tidyr::separate_longer_delim(entries, tidyselect::all_of(c("peaks", "isos")), ";") |> dplyr::select(-c("mz", "intensity", "isotopes")) |> - dplyr::rename(mz = peaks, isotopes=isos) + dplyr::rename(mz = peaks, isotopes=isos, rt=retention_time) + + if(append_isotopes) { + result <- dplyr::mutate(result, full_formula = paste0(formula, " (", isotopes, ")")) |> + dplyr::select(-all_of(c("formula", "isotopes"))) |> + dplyr::rename(formula = full_formula) |> + dplyr::relocate(formula, .after = name) + } readr::write_tsv(result, file=file) } @@ -130,7 +138,7 @@ main <- function() { if(args$out_format == "msp") { write_to_msp(spectra, args$outfile) } else if (args$out_format == "tabular") { - write_to_table(spectra, args$outfile) + write_to_table(spectra, args$outfile, args$append_isotopes) } } diff --git a/tools/isolib/isolib.xml b/tools/isolib/isolib.xml index 60c3f698..1c950643 100644 --- a/tools/isolib/isolib.xml +++ b/tools/isolib/isolib.xml @@ -25,7 +25,18 @@ r-purrr @@ -49,16 +60,23 @@ - - - - + + + + + + + + + + + - - + + From efec3a843842b85d2ead40bf0aa7a6c73d73cb1f Mon Sep 17 00:00:00 2001 From: hechth Date: Thu, 24 Oct 2024 15:05:03 +0200 Subject: [PATCH 3/8] fixed formatting --- tools/isolib/isolib.xml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tools/isolib/isolib.xml b/tools/isolib/isolib.xml index 1c950643..61a17550 100644 --- a/tools/isolib/isolib.xml +++ b/tools/isolib/isolib.xml @@ -30,7 +30,7 @@ '${ionization.adducts}' '${threshold}' '${append_adduct}' - #if '${formatting.out_format}' == "tabular" + #if $formatting.out_format == "tabular" '${formatting.append_isotopes}' #else 'FALSE' From cff766a8bab8220ba806ff7c35c4fa4a76408071 Mon Sep 17 00:00:00 2001 From: hechth Date: Fri, 25 Oct 2024 09:21:43 +0200 Subject: [PATCH 4/8] lint --- tools/isolib/isolib.R | 15 ++++++++------- tools/isolib/isolib.xml | 2 +- 2 files changed, 9 insertions(+), 8 deletions(-) diff --git a/tools/isolib/isolib.R b/tools/isolib/isolib.R index 2de7c899..cd9cefe1 100644 --- a/tools/isolib/isolib.R +++ b/tools/isolib/isolib.R @@ -92,8 +92,8 @@ generate_isotope_spectra <- function(compound_table, adducts_to_use, append_addu compositions <- compositions |> dplyr::rowwise() |> dplyr::mutate(isotopes = paste( # combine elemental composition into single string - purrr::map2_chr(names(compositions), dplyr::c_across(everything()), ~ paste(.x, .y, sep = ":")), collapse = ", ") - ) |> + purrr::map2_chr(names(compositions), dplyr::c_across(everything()), ~ paste(.x, .y, sep = ":")), + collapse = ", ")) |> dplyr::ungroup() |> dplyr::select(isotopes) isos <- append(isos, list(compositions$isotopes)) @@ -133,7 +133,12 @@ write_to_table <- function(spectra, file, append_isotopes) { main <- function() { args <- parse_args() - spectra <- generate_isotope_spectra(args$compound_table, args$adducts_to_use, args$append_adducts, args$threshold) + spectra <- generate_isotope_spectra( + args$compound_table, + args$adducts_to_use, + args$append_adducts, + args$threshold + ) if(args$out_format == "msp") { write_to_msp(spectra, args$outfile) @@ -144,7 +149,3 @@ main <- function() { # Call the main function main() - -# > u <- dplyr::mutate(x, peaks = paste(unlist(mz), collapse=",")) -# > res <- tidyr::separate_longer_delim(u, peaks, ",") -# > monoisotopic <- isotopes |> dplyr::group_by(element) |> dplyr::slice_max(abundance, n = 1) |> dplyr::filter(!stringr::str_detect(element, "\\[|\\]")) diff --git a/tools/isolib/isolib.xml b/tools/isolib/isolib.xml index 61a17550..38d3fbcd 100644 --- a/tools/isolib/isolib.xml +++ b/tools/isolib/isolib.xml @@ -73,7 +73,7 @@ - + From 5c6f057cea54f1e5f483c7cb2dc41b529ea72467 Mon Sep 17 00:00:00 2001 From: hechth Date: Fri, 25 Oct 2024 09:29:29 +0200 Subject: [PATCH 5/8] linting --- tools/isolib/isolib.R | 248 +++++++++++++++++++++--------------------- 1 file changed, 124 insertions(+), 124 deletions(-) diff --git a/tools/isolib/isolib.R b/tools/isolib/isolib.R index cd9cefe1..0fddabd2 100644 --- a/tools/isolib/isolib.R +++ b/tools/isolib/isolib.R @@ -6,145 +6,145 @@ library(readr) parse_args <- function() { - args <- commandArgs(trailingOnly = TRUE) + args <- commandArgs(trailingOnly = TRUE) + + compound_table <- read_tsv( + file = args[1], + col_types = "ccd", + col_select = tidyselect::all_of(c("name", "formula")) | tidyselect::any_of("rt") + ) + + parsed <- list( + compound_table = compound_table, + adducts_to_use = c(unlist(strsplit(args[2], ",", fixed = TRUE))), + threshold = as.numeric(args[3]), + append_adducts = args[4], + append_isotopes = args[5], + out_format = args[6], + outfile = args[7] + ) + return(parsed) +} + +generate_isotope_spectra <- function(compound_table, adducts_to_use, append_adducts, threshold) { + data(isotopes) + data(adducts) + + monoisotopic <- isotopes |> + dplyr::group_by(element) |> + dplyr::slice_max(abundance, n = 1) |> + dplyr::filter(!stringr::str_detect(element, "\\[|\\]")) + + chemforms <- check_chemform(isotopes, compound_table$formula)[, 2] + spectra <- data.frame() + + for (current in adducts_to_use) { + adduct <- adducts[adducts$Name == current, ] + multiplied_chemforms <- multiform(chemforms, adduct$Mult) - compound_table <- read_tsv( - file = args[1], - col_types = "ccd", - col_select = tidyselect::all_of(c("name", "formula")) | tidyselect::any_of("rt") + if (adduct$Ion_mode == "negative") { + merged_chemforms <- subform(multiplied_chemforms, adduct$Formula_ded) + } else { + merged_chemforms <- mergeform(multiplied_chemforms, adduct$Formula_add) + } + + charge_string <- paste0(if (adduct$Charge > 0) "+" else "-", if (abs(adduct$Charge) > 1) abs(adduct$Charge) else "") + adduct_string <- paste0("[", adduct$Name, "]", charge_string) + precursor_mz <- calculateMass(multiplied_chemforms) + adduct$Mass + + if (append_adducts == TRUE) { + names <- paste(compound_table$name, paste0("(", adduct$Name, ")"), sep = " ") + } else { + names <- compound_table$name + } + + spectra_df <- data.frame( + name = names, + adduct = adduct_string, + formula = chemforms, + charge = adduct$Charge, + ionization_mode = adduct$Ion_mode, + precursor_mz = precursor_mz, + msLevel = as.integer(1) ) - parsed <- list( - compound_table = compound_table, - adducts_to_use = c(unlist(strsplit(args[2], ",", fixed = TRUE))), - threshold = as.numeric(args[3]), - append_adducts = args[4], - append_isotopes = args[5], - out_format=args[6], - outfile = args[7] + if ("rt" %in% colnames(compound_table)) { + spectra_df$retention_time <- compound_table$rt + } + + patterns <- enviPat::isopattern( + isotopes = isotopes, + chemforms = merged_chemforms, + charge = adduct$Charge, + threshold = threshold, ) - return(parsed) -} -generate_isotope_spectra <- function(compound_table, adducts_to_use, append_adducts, threshold) { - data(isotopes) - data(adducts) - - monoisotopic <- isotopes |> - dplyr::group_by(element) |> - dplyr::slice_max(abundance, n = 1) |> - dplyr::filter(!stringr::str_detect(element, "\\[|\\]")) - - chemforms <- check_chemform(isotopes, compound_table$formula)[, 2] - spectra <- data.frame() - - for (current in adducts_to_use) { - adduct <- adducts[adducts$Name == current, ] - multiplied_chemforms <- multiform(chemforms, adduct$Mult) - - if (adduct$Ion_mode == "negative") { - merged_chemforms <- subform(multiplied_chemforms, adduct$Formula_ded) - } else { - merged_chemforms <- mergeform(multiplied_chemforms, adduct$Formula_add) - } - - charge_string <- paste0(if (adduct$Charge > 0) "+" else "-", if (abs(adduct$Charge) > 1) abs(adduct$Charge) else "") - adduct_string <- paste0("[", adduct$Name, "]", charge_string) - precursor_mz <- calculateMass(multiplied_chemforms) + adduct$Mass - - if (append_adducts == TRUE) { - names <- paste(compound_table$name, paste0("(", adduct$Name, ")"), sep = " ") - } else { - names <- compound_table$name - } - - spectra_df <- data.frame( - name = names, - adduct = adduct_string, - formula = chemforms, - charge = adduct$Charge, - ionization_mode = adduct$Ion_mode, - precursor_mz = precursor_mz, - msLevel = as.integer(1) - ) - - if ("rt" %in% colnames(compound_table)) { - spectra_df$retention_time <- compound_table$rt - } - - patterns <- enviPat::isopattern( - isotopes = isotopes, - chemforms = merged_chemforms, - charge = adduct$Charge, - threshold = threshold, - ) - - mzs <- list() - intensities <- list() - isos <- list() - - for (i in seq_along(patterns)) { - mzs <- append(mzs, list(patterns[[i]][, 1])) - intensities <- append(intensities, list(patterns[[i]][, 2])) - compositions <- as.data.frame(patterns[[i]][,-c(1,2)]) |> # select all columns which describe the elemental composition - dplyr::select(-tidyselect::any_of(monoisotopic$isotope)) |> # remove all 12C, 35Cl etc. - dplyr::select_if(~ !all(. == 0)) # remove isotopes which don't occur - compositions <- compositions |> - dplyr::rowwise() |> - dplyr::mutate(isotopes = paste( # combine elemental composition into single string - purrr::map2_chr(names(compositions), dplyr::c_across(everything()), ~ paste(.x, .y, sep = ":")), - collapse = ", ")) |> - dplyr::ungroup() |> - dplyr::select(isotopes) - isos <- append(isos, list(compositions$isotopes)) - } - - spectra_df$mz <- mzs - spectra_df$intensity <- intensities - spectra_df$isotopes <- isos - spectra <- rbind(spectra, spectra_df) + mzs <- list() + intensities <- list() + isos <- list() + + for (i in seq_along(patterns)) { + mzs <- append(mzs, list(patterns[[i]][, 1])) + intensities <- append(intensities, list(patterns[[i]][, 2])) + compositions <- as.data.frame(patterns[[i]][, -c(1, 2)]) |> # select all columns which describe the elemental composition + dplyr::select(-tidyselect::any_of(monoisotopic$isotope)) |> # remove all 12C, 35Cl etc. + dplyr::select_if(~ !all(. == 0)) # remove isotopes which don't occur + compositions <- compositions |> + dplyr::rowwise() |> + dplyr::mutate(isotopes = paste( # combine elemental composition into single string + purrr::map2_chr(names(compositions), dplyr::c_across(everything()), ~ paste(.x, .y, sep = ":")), + collapse = ", " + )) |> + dplyr::ungroup() |> + dplyr::select(isotopes) + isos <- append(isos, list(compositions$isotopes)) } - return(spectra) + + spectra_df$mz <- mzs + spectra_df$intensity <- intensities + spectra_df$isotopes <- isos + spectra <- rbind(spectra, spectra_df) + } + return(spectra) } write_to_msp <- function(spectra, file) { - sps <- Spectra(dplyr::select(spectra, -isotopes)) - export(sps, MsBackendMsp(), file = file) + sps <- Spectra(dplyr::select(spectra, -isotopes)) + export(sps, MsBackendMsp(), file = file) } write_to_table <- function(spectra, file, append_isotopes) { - entries <- spectra |> - dplyr::rowwise() |> - dplyr::mutate(peaks = paste(unlist(mz), collapse=";"))|> - dplyr::mutate(isos = paste(unlist(isotopes), collapse=";") - ) - result <- tidyr::separate_longer_delim(entries, tidyselect::all_of(c("peaks", "isos")), ";") |> - dplyr::select(-c("mz", "intensity", "isotopes")) |> - dplyr::rename(mz = peaks, isotopes=isos, rt=retention_time) - - if(append_isotopes) { - result <- dplyr::mutate(result, full_formula = paste0(formula, " (", isotopes, ")")) |> - dplyr::select(-all_of(c("formula", "isotopes"))) |> - dplyr::rename(formula = full_formula) |> - dplyr::relocate(formula, .after = name) - } - readr::write_tsv(result, file=file) + entries <- spectra |> + dplyr::rowwise() |> + dplyr::mutate(peaks = paste(unlist(mz), collapse = ";")) |> + dplyr::mutate(isos = paste(unlist(isotopes), collapse = ";")) + result <- tidyr::separate_longer_delim(entries, tidyselect::all_of(c("peaks", "isos")), ";") |> + dplyr::select(-c("mz", "intensity", "isotopes")) |> + dplyr::rename(mz = peaks, isotopes = isos, rt = retention_time) + + if (append_isotopes) { + result <- dplyr::mutate(result, full_formula = paste0(formula, " (", isotopes, ")")) |> + dplyr::select(-all_of(c("formula", "isotopes"))) |> + dplyr::rename(formula = full_formula) |> + dplyr::relocate(formula, .after = name) + } + readr::write_tsv(result, file = file) } main <- function() { - args <- parse_args() - spectra <- generate_isotope_spectra( - args$compound_table, - args$adducts_to_use, - args$append_adducts, - args$threshold - ) - - if(args$out_format == "msp") { - write_to_msp(spectra, args$outfile) - } else if (args$out_format == "tabular") { - write_to_table(spectra, args$outfile, args$append_isotopes) - } + args <- parse_args() + spectra <- generate_isotope_spectra( + args$compound_table, + args$adducts_to_use, + args$append_adducts, + args$threshold + ) + + if (args$out_format == "msp") { + write_to_msp(spectra, args$outfile) + } else if (args$out_format == "tabular") { + write_to_table(spectra, args$outfile, args$append_isotopes) + } } # Call the main function From 862b3801b6b73aa6a4eb774a4b20f55a42ec12a6 Mon Sep 17 00:00:00 2001 From: hechth Date: Fri, 25 Oct 2024 10:03:51 +0200 Subject: [PATCH 6/8] lint and updated test data --- tools/isolib/isolib.R | 49 +++++++++++++++++++++------- tools/isolib/test-data/test2.tabular | 2 +- tools/isolib/test-data/test3.tabular | 2 +- 3 files changed, 40 insertions(+), 13 deletions(-) diff --git a/tools/isolib/isolib.R b/tools/isolib/isolib.R index 0fddabd2..6ae0cd11 100644 --- a/tools/isolib/isolib.R +++ b/tools/isolib/isolib.R @@ -3,6 +3,7 @@ library(Spectra) library(MsBackendMsp) library(MetaboCoreUtils) library(readr) +library(tidyselect) parse_args <- function() { @@ -11,7 +12,7 @@ parse_args <- function() { compound_table <- read_tsv( file = args[1], col_types = "ccd", - col_select = tidyselect::all_of(c("name", "formula")) | tidyselect::any_of("rt") + col_select = all_of(c("name", "formula")) | any_of("rt") ) parsed <- list( @@ -26,7 +27,10 @@ parse_args <- function() { return(parsed) } -generate_isotope_spectra <- function(compound_table, adducts_to_use, append_adducts, threshold) { +generate_isotope_spectra <- function(compound_table, + adducts_to_use, + append_adducts, + threshold) { data(isotopes) data(adducts) @@ -48,12 +52,18 @@ generate_isotope_spectra <- function(compound_table, adducts_to_use, append_addu merged_chemforms <- mergeform(multiplied_chemforms, adduct$Formula_add) } - charge_string <- paste0(if (adduct$Charge > 0) "+" else "-", if (abs(adduct$Charge) > 1) abs(adduct$Charge) else "") + charge_string <- paste0( + if (adduct$Charge > 0) "+" else "-", + if (abs(adduct$Charge) > 1) abs(adduct$Charge) else "" + ) adduct_string <- paste0("[", adduct$Name, "]", charge_string) precursor_mz <- calculateMass(multiplied_chemforms) + adduct$Mass if (append_adducts == TRUE) { - names <- paste(compound_table$name, paste0("(", adduct$Name, ")"), sep = " ") + names <- paste( + compound_table$name, + paste0("(", adduct$Name, ")"), sep = " " + ) } else { names <- compound_table$name } @@ -86,13 +96,23 @@ generate_isotope_spectra <- function(compound_table, adducts_to_use, append_addu for (i in seq_along(patterns)) { mzs <- append(mzs, list(patterns[[i]][, 1])) intensities <- append(intensities, list(patterns[[i]][, 2])) - compositions <- as.data.frame(patterns[[i]][, -c(1, 2)]) |> # select all columns which describe the elemental composition - dplyr::select(-tidyselect::any_of(monoisotopic$isotope)) |> # remove all 12C, 35Cl etc. - dplyr::select_if(~ !all(. == 0)) # remove isotopes which don't occur + + # select all columns which describe the elemental composition + # remove all 12C, 35Cl etc. + # remove isotopes which don't occur + compositions <- as.data.frame(patterns[[i]][, -c(1, 2)]) |> + dplyr::select(-tidyselect::any_of(monoisotopic$isotope)) |> + dplyr::select_if(~ !all(. == 0)) + + # combine elemental composition into single string compositions <- compositions |> dplyr::rowwise() |> - dplyr::mutate(isotopes = paste( # combine elemental composition into single string - purrr::map2_chr(names(compositions), dplyr::c_across(everything()), ~ paste(.x, .y, sep = ":")), + dplyr::mutate(isotopes = paste( + purrr::map2_chr( + names(compositions), + dplyr::c_across(everything()), + ~ paste(.x, .y, sep = ":") + ), collapse = ", " )) |> dplyr::ungroup() |> @@ -118,12 +138,19 @@ write_to_table <- function(spectra, file, append_isotopes) { dplyr::rowwise() |> dplyr::mutate(peaks = paste(unlist(mz), collapse = ";")) |> dplyr::mutate(isos = paste(unlist(isotopes), collapse = ";")) - result <- tidyr::separate_longer_delim(entries, tidyselect::all_of(c("peaks", "isos")), ";") |> + result <- tidyr::separate_longer_delim( + entries, + all_of(c("peaks", "isos")), + ";" + ) + result <- result |> dplyr::select(-c("mz", "intensity", "isotopes")) |> dplyr::rename(mz = peaks, isotopes = isos, rt = retention_time) if (append_isotopes) { - result <- dplyr::mutate(result, full_formula = paste0(formula, " (", isotopes, ")")) |> + result <- result |> + dplyr::mutate(result, + full_formula = paste0(formula, " (", isotopes, ")")) |> dplyr::select(-all_of(c("formula", "isotopes"))) |> dplyr::rename(formula = full_formula) |> dplyr::relocate(formula, .after = name) diff --git a/tools/isolib/test-data/test2.tabular b/tools/isolib/test-data/test2.tabular index 6b466f50..d24c8cc8 100644 --- a/tools/isolib/test-data/test2.tabular +++ b/tools/isolib/test-data/test2.tabular @@ -1,4 +1,4 @@ -name adduct formula charge ionization_mode precursor_mz msLevel retention_time mz isotopes +name adduct formula charge ionization_mode precursor_mz msLevel rt mz isotopes 2,4-Dichlorophenoxyacetic acid ou 2,4-D (M-H) [M-H]- C8H6Cl2O3 -1 negative 218.962123412 1 484.2 218.962123019909 13C:0, 37Cl:0 2,4-Dichlorophenoxyacetic acid ou 2,4-D (M-H) [M-H]- C8H6Cl2O3 -1 negative 218.962123412 1 484.2 219.965477859909 13C:1, 37Cl:0 2,4-Dichlorophenoxyacetic acid ou 2,4-D (M-H) [M-H]- C8H6Cl2O3 -1 negative 218.962123412 1 484.2 220.959172909909 13C:0, 37Cl:1 diff --git a/tools/isolib/test-data/test3.tabular b/tools/isolib/test-data/test3.tabular index 263bc6b7..da011bb8 100644 --- a/tools/isolib/test-data/test3.tabular +++ b/tools/isolib/test-data/test3.tabular @@ -1,4 +1,4 @@ -name adduct formula charge ionization_mode precursor_mz msLevel retention_time mz isotopes +name adduct formula charge ionization_mode precursor_mz msLevel rt mz isotopes 2,4-Dichlorophenoxyacetic acid ou 2,4-D (M-H) [M-H]- C8H6Cl2O3 -1 negative 218.962123412 1 484.2 218.962123019909 13C:0, 37Cl:0 2,4-Dichlorophenoxyacetic acid ou 2,4-D (M-H) [M-H]- C8H6Cl2O3 -1 negative 218.962123412 1 484.2 219.965477859909 13C:1, 37Cl:0 2,4-Dichlorophenoxyacetic acid ou 2,4-D (M-H) [M-H]- C8H6Cl2O3 -1 negative 218.962123412 1 484.2 220.959172909909 13C:0, 37Cl:1 From f92cda068692a2397d95de46f28877140085a54a Mon Sep 17 00:00:00 2001 From: hechth Date: Fri, 25 Oct 2024 10:12:03 +0200 Subject: [PATCH 7/8] indent with 4 spaces --- tools/isolib/isolib.R | 298 +++++++++++++++++++++--------------------- 1 file changed, 150 insertions(+), 148 deletions(-) diff --git a/tools/isolib/isolib.R b/tools/isolib/isolib.R index 6ae0cd11..4354ea36 100644 --- a/tools/isolib/isolib.R +++ b/tools/isolib/isolib.R @@ -7,171 +7,173 @@ library(tidyselect) parse_args <- function() { - args <- commandArgs(trailingOnly = TRUE) - - compound_table <- read_tsv( - file = args[1], - col_types = "ccd", - col_select = all_of(c("name", "formula")) | any_of("rt") - ) - - parsed <- list( - compound_table = compound_table, - adducts_to_use = c(unlist(strsplit(args[2], ",", fixed = TRUE))), - threshold = as.numeric(args[3]), - append_adducts = args[4], - append_isotopes = args[5], - out_format = args[6], - outfile = args[7] - ) - return(parsed) + args <- commandArgs(trailingOnly = TRUE) + + compound_table <- read_tsv( + file = args[1], + col_types = "ccd", + col_select = all_of(c("name", "formula")) | any_of("rt") + ) + + parsed <- list( + compound_table = compound_table, + adducts_to_use = c(unlist(strsplit(args[2], ",", fixed = TRUE))), + threshold = as.numeric(args[3]), + append_adducts = args[4], + append_isotopes = args[5], + out_format = args[6], + outfile = args[7] + ) + return(parsed) } generate_isotope_spectra <- function(compound_table, adducts_to_use, append_adducts, threshold) { - data(isotopes) - data(adducts) - - monoisotopic <- isotopes |> - dplyr::group_by(element) |> - dplyr::slice_max(abundance, n = 1) |> - dplyr::filter(!stringr::str_detect(element, "\\[|\\]")) - - chemforms <- check_chemform(isotopes, compound_table$formula)[, 2] - spectra <- data.frame() - - for (current in adducts_to_use) { - adduct <- adducts[adducts$Name == current, ] - multiplied_chemforms <- multiform(chemforms, adduct$Mult) - - if (adduct$Ion_mode == "negative") { - merged_chemforms <- subform(multiplied_chemforms, adduct$Formula_ded) - } else { - merged_chemforms <- mergeform(multiplied_chemforms, adduct$Formula_add) - } - - charge_string <- paste0( - if (adduct$Charge > 0) "+" else "-", - if (abs(adduct$Charge) > 1) abs(adduct$Charge) else "" - ) - adduct_string <- paste0("[", adduct$Name, "]", charge_string) - precursor_mz <- calculateMass(multiplied_chemforms) + adduct$Mass - - if (append_adducts == TRUE) { - names <- paste( - compound_table$name, - paste0("(", adduct$Name, ")"), sep = " " - ) - } else { - names <- compound_table$name - } - - spectra_df <- data.frame( - name = names, - adduct = adduct_string, - formula = chemforms, - charge = adduct$Charge, - ionization_mode = adduct$Ion_mode, - precursor_mz = precursor_mz, - msLevel = as.integer(1) - ) - - if ("rt" %in% colnames(compound_table)) { - spectra_df$retention_time <- compound_table$rt + data(isotopes) + data(adducts) + + monoisotopic <- isotopes |> + dplyr::group_by(element) |> + dplyr::slice_max(abundance, n = 1) |> + dplyr::filter(!stringr::str_detect(element, "\\[|\\]")) + + chemforms <- check_chemform(isotopes, compound_table$formula)[, 2] + spectra <- data.frame() + + for (current in adducts_to_use) { + adduct <- adducts[adducts$Name == current, ] + multiplied_chemforms <- multiform(chemforms, adduct$Mult) + + if (adduct$Ion_mode == "negative") { + merged_chemforms <- subform(multiplied_chemforms, adduct$Formula_ded) + } else { + merged_chemforms <- mergeform(multiplied_chemforms, adduct$Formula_add) + } + + charge_string <- paste0( + if (adduct$Charge > 0) "+" else "-", + if (abs(adduct$Charge) > 1) abs(adduct$Charge) else "" + ) + adduct_string <- paste0("[", adduct$Name, "]", charge_string) + precursor_mz <- calculateMass(multiplied_chemforms) + adduct$Mass + + if (append_adducts == TRUE) { + names <- paste( + compound_table$name, + paste0("(", adduct$Name, ")"), + sep = " " + ) + } else { + names <- compound_table$name + } + + spectra_df <- data.frame( + name = names, + adduct = adduct_string, + formula = chemforms, + charge = adduct$Charge, + ionization_mode = adduct$Ion_mode, + precursor_mz = precursor_mz, + msLevel = as.integer(1) + ) + + if ("rt" %in% colnames(compound_table)) { + spectra_df$retention_time <- compound_table$rt + } + + patterns <- enviPat::isopattern( + isotopes = isotopes, + chemforms = merged_chemforms, + charge = adduct$Charge, + threshold = threshold, + ) + + mzs <- list() + intensities <- list() + isos <- list() + + for (i in seq_along(patterns)) { + mzs <- append(mzs, list(patterns[[i]][, 1])) + intensities <- append(intensities, list(patterns[[i]][, 2])) + + # select all columns which describe the elemental composition + # remove all 12C, 35Cl etc. + # remove isotopes which don't occur + compositions <- as.data.frame(patterns[[i]][, -c(1, 2)]) |> + dplyr::select(-tidyselect::any_of(monoisotopic$isotope)) |> + dplyr::select_if(~ !all(. == 0)) + + # combine elemental composition into single string + compositions <- compositions |> + dplyr::rowwise() |> + dplyr::mutate(isotopes = paste( + purrr::map2_chr( + names(compositions), + dplyr::c_across(everything()), + ~ paste(.x, .y, sep = ":") + ), + collapse = ", " + )) |> + dplyr::ungroup() |> + dplyr::select(isotopes) + isos <- append(isos, list(compositions$isotopes)) + } + + spectra_df$mz <- mzs + spectra_df$intensity <- intensities + spectra_df$isotopes <- isos + spectra <- rbind(spectra, spectra_df) } - - patterns <- enviPat::isopattern( - isotopes = isotopes, - chemforms = merged_chemforms, - charge = adduct$Charge, - threshold = threshold, - ) - - mzs <- list() - intensities <- list() - isos <- list() - - for (i in seq_along(patterns)) { - mzs <- append(mzs, list(patterns[[i]][, 1])) - intensities <- append(intensities, list(patterns[[i]][, 2])) - - # select all columns which describe the elemental composition - # remove all 12C, 35Cl etc. - # remove isotopes which don't occur - compositions <- as.data.frame(patterns[[i]][, -c(1, 2)]) |> - dplyr::select(-tidyselect::any_of(monoisotopic$isotope)) |> - dplyr::select_if(~ !all(. == 0)) - - # combine elemental composition into single string - compositions <- compositions |> - dplyr::rowwise() |> - dplyr::mutate(isotopes = paste( - purrr::map2_chr( - names(compositions), - dplyr::c_across(everything()), - ~ paste(.x, .y, sep = ":") - ), - collapse = ", " - )) |> - dplyr::ungroup() |> - dplyr::select(isotopes) - isos <- append(isos, list(compositions$isotopes)) - } - - spectra_df$mz <- mzs - spectra_df$intensity <- intensities - spectra_df$isotopes <- isos - spectra <- rbind(spectra, spectra_df) - } - return(spectra) + return(spectra) } write_to_msp <- function(spectra, file) { - sps <- Spectra(dplyr::select(spectra, -isotopes)) - export(sps, MsBackendMsp(), file = file) + sps <- Spectra(dplyr::select(spectra, -isotopes)) + export(sps, MsBackendMsp(), file = file) } write_to_table <- function(spectra, file, append_isotopes) { - entries <- spectra |> - dplyr::rowwise() |> - dplyr::mutate(peaks = paste(unlist(mz), collapse = ";")) |> - dplyr::mutate(isos = paste(unlist(isotopes), collapse = ";")) - result <- tidyr::separate_longer_delim( - entries, - all_of(c("peaks", "isos")), - ";" - ) - result <- result |> - dplyr::select(-c("mz", "intensity", "isotopes")) |> - dplyr::rename(mz = peaks, isotopes = isos, rt = retention_time) - - if (append_isotopes) { + entries <- spectra |> + dplyr::rowwise() |> + dplyr::mutate(peaks = paste(unlist(mz), collapse = ";")) |> + dplyr::mutate(isos = paste(unlist(isotopes), collapse = ";")) + result <- tidyr::separate_longer_delim( + entries, + all_of(c("peaks", "isos")), + ";" + ) result <- result |> - dplyr::mutate(result, - full_formula = paste0(formula, " (", isotopes, ")")) |> - dplyr::select(-all_of(c("formula", "isotopes"))) |> - dplyr::rename(formula = full_formula) |> - dplyr::relocate(formula, .after = name) - } - readr::write_tsv(result, file = file) + dplyr::select(-c("mz", "intensity", "isotopes")) |> + dplyr::rename(mz = peaks, isotopes = isos, rt = retention_time) + + if (append_isotopes) { + result <- result |> + dplyr::mutate(result, + full_formula = paste0(formula, " (", isotopes, ")") + ) |> + dplyr::select(-all_of(c("formula", "isotopes"))) |> + dplyr::rename(formula = full_formula) |> + dplyr::relocate(formula, .after = name) + } + readr::write_tsv(result, file = file) } main <- function() { - args <- parse_args() - spectra <- generate_isotope_spectra( - args$compound_table, - args$adducts_to_use, - args$append_adducts, - args$threshold - ) - - if (args$out_format == "msp") { - write_to_msp(spectra, args$outfile) - } else if (args$out_format == "tabular") { - write_to_table(spectra, args$outfile, args$append_isotopes) - } + args <- parse_args() + spectra <- generate_isotope_spectra( + args$compound_table, + args$adducts_to_use, + args$append_adducts, + args$threshold + ) + + if (args$out_format == "msp") { + write_to_msp(spectra, args$outfile) + } else if (args$out_format == "tabular") { + write_to_table(spectra, args$outfile, args$append_isotopes) + } } # Call the main function From d74b0daa10e6aefc8d3c98fc94ab9c0b8ebee62f Mon Sep 17 00:00:00 2001 From: hechth Date: Wed, 30 Oct 2024 20:23:19 +0100 Subject: [PATCH 8/8] updated test data with append_isotopes param --- tools/isolib/isolib.xml | 1 + tools/isolib/test-data/test2.tabular | 246 +++++++++++++-------------- 2 files changed, 124 insertions(+), 123 deletions(-) diff --git a/tools/isolib/isolib.xml b/tools/isolib/isolib.xml index 38d3fbcd..22821394 100644 --- a/tools/isolib/isolib.xml +++ b/tools/isolib/isolib.xml @@ -93,6 +93,7 @@ + diff --git a/tools/isolib/test-data/test2.tabular b/tools/isolib/test-data/test2.tabular index d24c8cc8..559b972a 100644 --- a/tools/isolib/test-data/test2.tabular +++ b/tools/isolib/test-data/test2.tabular @@ -1,123 +1,123 @@ -name adduct formula charge ionization_mode precursor_mz msLevel rt mz isotopes -2,4-Dichlorophenoxyacetic acid ou 2,4-D (M-H) [M-H]- C8H6Cl2O3 -1 negative 218.962123412 1 484.2 218.962123019909 13C:0, 37Cl:0 -2,4-Dichlorophenoxyacetic acid ou 2,4-D (M-H) [M-H]- C8H6Cl2O3 -1 negative 218.962123412 1 484.2 219.965477859909 13C:1, 37Cl:0 -2,4-Dichlorophenoxyacetic acid ou 2,4-D (M-H) [M-H]- C8H6Cl2O3 -1 negative 218.962123412 1 484.2 220.959172909909 13C:0, 37Cl:1 -2,4-Dichlorophenoxyacetic acid ou 2,4-D (M-H) [M-H]- C8H6Cl2O3 -1 negative 218.962123412 1 484.2 221.962527749909 13C:1, 37Cl:1 -2,4-Dichlorophenoxyacetic acid ou 2,4-D (M-H) [M-H]- C8H6Cl2O3 -1 negative 218.962123412 1 484.2 222.956222799909 13C:0, 37Cl:2 -2-diethylamino-6-methyl pyrimidin-4-ol/one (M-H) [M-H]- C9H15N3O1 -1 negative 180.1142361 1 451.8 180.114235677909 13C:0, 15N:0 -2-diethylamino-6-methyl pyrimidin-4-ol/one (M-H) [M-H]- C9H15N3O1 -1 negative 180.1142361 1 451.8 181.111270637909 13C:0, 15N:1 -2-diethylamino-6-methyl pyrimidin-4-ol/one (M-H) [M-H]- C9H15N3O1 -1 negative 180.1142361 1 451.8 181.117590517909 13C:1, 15N:0 -3,5,6-Trichloro-2-pyridinol (M-H) [M-H]- C5H2Cl3N1O1 -1 negative 195.912920724 1 499.2 195.912920371909 13C:0, 37Cl:0 -3,5,6-Trichloro-2-pyridinol (M-H) [M-H]- C5H2Cl3N1O1 -1 negative 195.912920724 1 499.2 196.916275211909 13C:1, 37Cl:0 -3,5,6-Trichloro-2-pyridinol (M-H) [M-H]- C5H2Cl3N1O1 -1 negative 195.912920724 1 499.2 197.909970261909 13C:0, 37Cl:1 -3,5,6-Trichloro-2-pyridinol (M-H) [M-H]- C5H2Cl3N1O1 -1 negative 195.912920724 1 499.2 198.913325101909 13C:1, 37Cl:1 -3,5,6-Trichloro-2-pyridinol (M-H) [M-H]- C5H2Cl3N1O1 -1 negative 195.912920724 1 499.2 199.907020151909 13C:0, 37Cl:2 -3,5,6-Trichloro-2-pyridinol (M-H) [M-H]- C5H2Cl3N1O1 -1 negative 195.912920724 1 499.2 200.910374991909 13C:1, 37Cl:2 -3,5,6-Trichloro-2-pyridinol (M-H) [M-H]- C5H2Cl3N1O1 -1 negative 195.912920724 1 499.2 201.904070041909 13C:0, 37Cl:3 -3-phenoxybenzoic acid (M-H) [M-H]- C13H10O3 -1 negative 213.05571818 1 517.8 213.055717727909 13C:0 -3-phenoxybenzoic acid (M-H) [M-H]- C13H10O3 -1 negative 213.05571818 1 517.8 214.059072567909 13C:1 -4-Fluoro-3-phenoxybenzoic acid (M-H) [M-H]- C13H9F1O3 -1 negative 231.04629636800001 1 532.2 231.046295895909 13C:0 -4-Fluoro-3-phenoxybenzoic acid (M-H) [M-H]- C13H9F1O3 -1 negative 231.04629636800001 1 532.2 232.049650735909 13C:1 -4-nitrophenol (M-H) [M-H]- C6H5N1O3 -1 negative 138.01966702000001 1 165 138.019666577909 13C:0 -4-nitrophenol (M-H) [M-H]- C6H5N1O3 -1 negative 138.01966702000001 1 165 139.023021417909 13C:1 -6-Chloronicotinic acid (M-H) [M-H]- C6H4Cl1N1O2 -1 negative 155.985780048 1 172.2 155.985779635909 13C:0, 37Cl:0 -6-Chloronicotinic acid (M-H) [M-H]- C6H4Cl1N1O2 -1 negative 155.985780048 1 172.2 156.989134475909 13C:1, 37Cl:0 -6-Chloronicotinic acid (M-H) [M-H]- C6H4Cl1N1O2 -1 negative 155.985780048 1 172.2 157.982829525909 13C:0, 37Cl:1 -6-Chloronicotinic acid (M-H) [M-H]- C6H4Cl1N1O2 -1 negative 155.985780048 1 172.2 158.986184365909 13C:1, 37Cl:1 -Acetochlor mercapturate (M-H) [M-H]- C19H28N2O5S1 -1 negative 395.164616996 1 607.2 395.164616293909 13C:0, 18O:0, 34S:0 -Acetochlor mercapturate (M-H) [M-H]- C19H28N2O5S1 -1 negative 395.164616996 1 607.2 396.167971133909 13C:1, 18O:0, 34S:0 -Acetochlor mercapturate (M-H) [M-H]- C19H28N2O5S1 -1 negative 395.164616996 1 607.2 397.160412433909 13C:0, 18O:0, 34S:1 -Acetochlor mercapturate (M-H) [M-H]- C19H28N2O5S1 -1 negative 395.164616996 1 607.2 397.168862073909 13C:0, 18O:1, 34S:0 -Acetochlor mercapturate (M-H) [M-H]- C19H28N2O5S1 -1 negative 395.164616996 1 607.2 397.171325973909 13C:2, 18O:0, 34S:0 -Alachlor mercapturate (M-H) [M-H]- C19H28N2O5S1 -1 negative 395.164616996 1 607.2 395.164616293909 13C:0, 18O:0, 34S:0 -Alachlor mercapturate (M-H) [M-H]- C19H28N2O5S1 -1 negative 395.164616996 1 607.2 396.167971133909 13C:1, 18O:0, 34S:0 -Alachlor mercapturate (M-H) [M-H]- C19H28N2O5S1 -1 negative 395.164616996 1 607.2 397.160412433909 13C:0, 18O:0, 34S:1 -Alachlor mercapturate (M-H) [M-H]- C19H28N2O5S1 -1 negative 395.164616996 1 607.2 397.168862073909 13C:0, 18O:1, 34S:0 -Alachlor mercapturate (M-H) [M-H]- C19H28N2O5S1 -1 negative 395.164616996 1 607.2 397.171325973909 13C:2, 18O:0, 34S:0 -Bentazone (M-H) [M-H]- C10H12N2O3S1 -1 negative 239.049587244 1 747.6 239.049586541909 13C:0, 34S:0 -Bentazone (M-H) [M-H]- C10H12N2O3S1 -1 negative 239.049587244 1 747.6 240.052941381909 13C:1, 34S:0 -Bentazone (M-H) [M-H]- C10H12N2O3S1 -1 negative 239.049587244 1 747.6 241.045382681909 13C:0, 34S:1 -Diethylthiophosphate (M-H) [M-H]- C4H11O3P1S1 -1 negative 169.009375842 1 177 169.009374979909 13C:0, 34S:0 -Diethylthiophosphate (M-H) [M-H]- C4H11O3P1S1 -1 negative 169.009375842 1 177 170.012729819909 13C:1, 34S:0 -Diethylthiophosphate (M-H) [M-H]- C4H11O3P1S1 -1 negative 169.009375842 1 177 171.005171119909 13C:0, 34S:1 -Fenhexamid (M-H) [M-H]- C14H17Cl2N1O2 -1 negative 300.056358144 1 689.4 300.056357761909 13C:0, 37Cl:0 -Fenhexamid (M-H) [M-H]- C14H17Cl2N1O2 -1 negative 300.056358144 1 689.4 301.059712601909 13C:1, 37Cl:0 -Fenhexamid (M-H) [M-H]- C14H17Cl2N1O2 -1 negative 300.056358144 1 689.4 302.053407651909 13C:0, 37Cl:1 -Fenhexamid (M-H) [M-H]- C14H17Cl2N1O2 -1 negative 300.056358144 1 689.4 302.063067441909 13C:2, 37Cl:0 -Fenhexamid (M-H) [M-H]- C14H17Cl2N1O2 -1 negative 300.056358144 1 689.4 303.056762491909 13C:1, 37Cl:1 -Fenhexamid (M-H) [M-H]- C14H17Cl2N1O2 -1 negative 300.056358144 1 689.4 304.050457541909 13C:0, 37Cl:2 -Fenhexamid (M-H) [M-H]- C14H17Cl2N1O2 -1 negative 300.056358144 1 689.4 305.053812381909 13C:1, 37Cl:2 -Fenvalerate free acid (M-H) [M-H]- C11H13Cl1O2 -1 negative 211.053131336 1 585 211.053130913909 13C:0, 37Cl:0 -Fenvalerate free acid (M-H) [M-H]- C11H13Cl1O2 -1 negative 211.053131336 1 585 212.056485753909 13C:1, 37Cl:0 -Fenvalerate free acid (M-H) [M-H]- C11H13Cl1O2 -1 negative 211.053131336 1 585 213.050180803909 13C:0, 37Cl:1 -Fenvalerate free acid (M-H) [M-H]- C11H13Cl1O2 -1 negative 211.053131336 1 585 214.053535643909 13C:1, 37Cl:1 -Fipronil (M-H) [M-H]- C12H4Cl2F6N4O1S1 -1 negative 434.931430428 1 750 434.931429685909 13C:0, 37Cl:0, 15N:0, 34S:0 -Fipronil (M-H) [M-H]- C12H4Cl2F6N4O1S1 -1 negative 434.931430428 1 750 435.928464645909 13C:0, 37Cl:0, 15N:1, 34S:0 -Fipronil (M-H) [M-H]- C12H4Cl2F6N4O1S1 -1 negative 434.931430428 1 750 435.934784525909 13C:1, 37Cl:0, 15N:0, 34S:0 -Fipronil (M-H) [M-H]- C12H4Cl2F6N4O1S1 -1 negative 434.931430428 1 750 436.927225825909 13C:0, 37Cl:0, 15N:0, 34S:1 -Fipronil (M-H) [M-H]- C12H4Cl2F6N4O1S1 -1 negative 434.931430428 1 750 436.928479575909 13C:0, 37Cl:1, 15N:0, 34S:0 -Fipronil (M-H) [M-H]- C12H4Cl2F6N4O1S1 -1 negative 434.931430428 1 750 437.931834415909 13C:1, 37Cl:1, 15N:0, 34S:0 -Fipronil (M-H) [M-H]- C12H4Cl2F6N4O1S1 -1 negative 434.931430428 1 750 438.924275715909 13C:0, 37Cl:1, 15N:0, 34S:1 -Fipronil (M-H) [M-H]- C12H4Cl2F6N4O1S1 -1 negative 434.931430428 1 750 438.925529465909 13C:0, 37Cl:2, 15N:0, 34S:0 -Fipronil (M-H) [M-H]- C12H4Cl2F6N4O1S1 -1 negative 434.931430428 1 750 439.928884305909 13C:1, 37Cl:2, 15N:0, 34S:0 -Fipronil sulfone (M-H) [M-H]- C12H4Cl2F6N4O2S1 -1 negative 450.92634504800003 1 771 450.926344305909 13C:0, 37Cl:0, 15N:0, 34S:0 -Fipronil sulfone (M-H) [M-H]- C12H4Cl2F6N4O2S1 -1 negative 450.92634504800003 1 771 451.923379265909 13C:0, 37Cl:0, 15N:1, 34S:0 -Fipronil sulfone (M-H) [M-H]- C12H4Cl2F6N4O2S1 -1 negative 450.92634504800003 1 771 451.929699145909 13C:1, 37Cl:0, 15N:0, 34S:0 -Fipronil sulfone (M-H) [M-H]- C12H4Cl2F6N4O2S1 -1 negative 450.92634504800003 1 771 452.922140445909 13C:0, 37Cl:0, 15N:0, 34S:1 -Fipronil sulfone (M-H) [M-H]- C12H4Cl2F6N4O2S1 -1 negative 450.92634504800003 1 771 452.923394195909 13C:0, 37Cl:1, 15N:0, 34S:0 -Fipronil sulfone (M-H) [M-H]- C12H4Cl2F6N4O2S1 -1 negative 450.92634504800003 1 771 453.926749035909 13C:1, 37Cl:1, 15N:0, 34S:0 -Fipronil sulfone (M-H) [M-H]- C12H4Cl2F6N4O2S1 -1 negative 450.92634504800003 1 771 454.919190335909 13C:0, 37Cl:1, 15N:0, 34S:1 -Fipronil sulfone (M-H) [M-H]- C12H4Cl2F6N4O2S1 -1 negative 450.92634504800003 1 771 454.920444085909 13C:0, 37Cl:2, 15N:0, 34S:0 -Fipronil sulfone (M-H) [M-H]- C12H4Cl2F6N4O2S1 -1 negative 450.92634504800003 1 771 455.923798925909 13C:1, 37Cl:2, 15N:0, 34S:0 -Hydroxy-tebuconazole (M-H) [M-H]- C16H22Cl1N3O2 -1 negative 322.132778624 1 696.6 322.132778231909 13C:0, 37Cl:0, 15N:0 -Hydroxy-tebuconazole (M-H) [M-H]- C16H22Cl1N3O2 -1 negative 322.132778624 1 696.6 323.129813191909 13C:0, 37Cl:0, 15N:1 -Hydroxy-tebuconazole (M-H) [M-H]- C16H22Cl1N3O2 -1 negative 322.132778624 1 696.6 323.136133071909 13C:1, 37Cl:0, 15N:0 -Hydroxy-tebuconazole (M-H) [M-H]- C16H22Cl1N3O2 -1 negative 322.132778624 1 696.6 324.129828121909 13C:0, 37Cl:1, 15N:0 -Hydroxy-tebuconazole (M-H) [M-H]- C16H22Cl1N3O2 -1 negative 322.132778624 1 696.6 324.139487911909 13C:2, 37Cl:0, 15N:0 -Hydroxy-tebuconazole (M-H) [M-H]- C16H22Cl1N3O2 -1 negative 322.132778624 1 696.6 325.133182961909 13C:1, 37Cl:1, 15N:0 -Fluopyram (M-H) [M-H]- C16H11Cl1F6N2O1 -1 negative 395.039133972 1 725.4 395.039133449909 13C:0, 37Cl:0 -Fluopyram (M-H) [M-H]- C16H11Cl1F6N2O1 -1 negative 395.039133972 1 725.4 396.042488289909 13C:1, 37Cl:0 -Fluopyram (M-H) [M-H]- C16H11Cl1F6N2O1 -1 negative 395.039133972 1 725.4 397.036183339909 13C:0, 37Cl:1 -Fluopyram (M-H) [M-H]- C16H11Cl1F6N2O1 -1 negative 395.039133972 1 725.4 397.045843129909 13C:2, 37Cl:0 -Fluopyram (M-H) [M-H]- C16H11Cl1F6N2O1 -1 negative 395.039133972 1 725.4 398.039538179909 13C:1, 37Cl:1 -Mecoprop (M-H) [M-H]- C10H11Cl1O3 -1 negative 213.032395892 1 544.8 213.032395469909 13C:0, 37Cl:0 -Mecoprop (M-H) [M-H]- C10H11Cl1O3 -1 negative 213.032395892 1 544.8 214.035750309909 13C:1, 37Cl:0 -Mecoprop (M-H) [M-H]- C10H11Cl1O3 -1 negative 213.032395892 1 544.8 215.029445359909 13C:0, 37Cl:1 -Mecoprop (M-H) [M-H]- C10H11Cl1O3 -1 negative 213.032395892 1 544.8 216.032800199909 13C:1, 37Cl:1 -p-Toluenesulfonamide (M-H) [M-H]- C7H9N1O2S1 -1 negative 170.028123528 1 362.4 170.028122815909 13C:0, 34S:0 -p-Toluenesulfonamide (M-H) [M-H]- C7H9N1O2S1 -1 negative 170.028123528 1 362.4 171.031477655909 13C:1, 34S:0 -p-Toluenesulfonamide (M-H) [M-H]- C7H9N1O2S1 -1 negative 170.028123528 1 362.4 172.023918955909 13C:0, 34S:1 -Triclosan (M-H) [M-H]- C12H7Cl3O2 -1 negative 286.943886504 1 811.8 286.943886141909 13C:0, 37Cl:0 -Triclosan (M-H) [M-H]- C12H7Cl3O2 -1 negative 286.943886504 1 811.8 287.947240981909 13C:1, 37Cl:0 -Triclosan (M-H) [M-H]- C12H7Cl3O2 -1 negative 286.943886504 1 811.8 288.940936031909 13C:0, 37Cl:1 -Triclosan (M-H) [M-H]- C12H7Cl3O2 -1 negative 286.943886504 1 811.8 289.944290871909 13C:1, 37Cl:1 -Triclosan (M-H) [M-H]- C12H7Cl3O2 -1 negative 286.943886504 1 811.8 290.937985921909 13C:0, 37Cl:2 -Triclosan (M-H) [M-H]- C12H7Cl3O2 -1 negative 286.943886504 1 811.8 291.941340761909 13C:1, 37Cl:2 -Triclosan (M-H) [M-H]- C12H7Cl3O2 -1 negative 286.943886504 1 811.8 292.935035811909 13C:0, 37Cl:3 -Triclosan glucuronide (M-H) [M-H]- C18H15Cl3O8 -1 negative 462.97597448 1 665.4 462.975974117909 13C:0, 37Cl:0, 18O:0 -Triclosan glucuronide (M-H) [M-H]- C18H15Cl3O8 -1 negative 462.97597448 1 665.4 463.979328957909 13C:1, 37Cl:0, 18O:0 -Triclosan glucuronide (M-H) [M-H]- C18H15Cl3O8 -1 negative 462.97597448 1 665.4 464.973024007909 13C:0, 37Cl:1, 18O:0 -Triclosan glucuronide (M-H) [M-H]- C18H15Cl3O8 -1 negative 462.97597448 1 665.4 464.980219897909 13C:0, 37Cl:0, 18O:1 -Triclosan glucuronide (M-H) [M-H]- C18H15Cl3O8 -1 negative 462.97597448 1 665.4 464.982683797909 13C:2, 37Cl:0, 18O:0 -Triclosan glucuronide (M-H) [M-H]- C18H15Cl3O8 -1 negative 462.97597448 1 665.4 465.976378847909 13C:1, 37Cl:1, 18O:0 -Triclosan glucuronide (M-H) [M-H]- C18H15Cl3O8 -1 negative 462.97597448 1 665.4 466.970073897909 13C:0, 37Cl:2, 18O:0 -Triclosan glucuronide (M-H) [M-H]- C18H15Cl3O8 -1 negative 462.97597448 1 665.4 466.977269787909 13C:0, 37Cl:1, 18O:1 -Triclosan glucuronide (M-H) [M-H]- C18H15Cl3O8 -1 negative 462.97597448 1 665.4 466.979733687909 13C:2, 37Cl:1, 18O:0 -Triclosan glucuronide (M-H) [M-H]- C18H15Cl3O8 -1 negative 462.97597448 1 665.4 467.973428737909 13C:1, 37Cl:2, 18O:0 -Triclosan glucuronide (M-H) [M-H]- C18H15Cl3O8 -1 negative 462.97597448 1 665.4 468.967123787909 13C:0, 37Cl:3, 18O:0 -Triclosan sulfate (M-H) [M-H]- C12H7Cl3O5S1 -1 negative 366.900701364 1 695.4 366.900700731909 13C:0, 37Cl:0, 18O:0, 34S:0 -Triclosan sulfate (M-H) [M-H]- C12H7Cl3O5S1 -1 negative 366.900701364 1 695.4 367.904055571909 13C:1, 37Cl:0, 18O:0, 34S:0 -Triclosan sulfate (M-H) [M-H]- C12H7Cl3O5S1 -1 negative 366.900701364 1 695.4 368.896496871909 13C:0, 37Cl:0, 18O:0, 34S:1 -Triclosan sulfate (M-H) [M-H]- C12H7Cl3O5S1 -1 negative 366.900701364 1 695.4 368.897750621909 13C:0, 37Cl:1, 18O:0, 34S:0 -Triclosan sulfate (M-H) [M-H]- C12H7Cl3O5S1 -1 negative 366.900701364 1 695.4 368.904946511909 13C:0, 37Cl:0, 18O:1, 34S:0 -Triclosan sulfate (M-H) [M-H]- C12H7Cl3O5S1 -1 negative 366.900701364 1 695.4 369.901105461909 13C:1, 37Cl:1, 18O:0, 34S:0 -Triclosan sulfate (M-H) [M-H]- C12H7Cl3O5S1 -1 negative 366.900701364 1 695.4 370.893546761909 13C:0, 37Cl:1, 18O:0, 34S:1 -Triclosan sulfate (M-H) [M-H]- C12H7Cl3O5S1 -1 negative 366.900701364 1 695.4 370.894800511909 13C:0, 37Cl:2, 18O:0, 34S:0 -Triclosan sulfate (M-H) [M-H]- C12H7Cl3O5S1 -1 negative 366.900701364 1 695.4 371.898155351909 13C:1, 37Cl:2, 18O:0, 34S:0 -Triclosan sulfate (M-H) [M-H]- C12H7Cl3O5S1 -1 negative 366.900701364 1 695.4 372.890596651909 13C:0, 37Cl:2, 18O:0, 34S:1 -Triclosan sulfate (M-H) [M-H]- C12H7Cl3O5S1 -1 negative 366.900701364 1 695.4 372.891850401909 13C:0, 37Cl:3, 18O:0, 34S:0 -acetamiprid-N-desmethyl (M-H) [M-H]- C9H9N4Cl1 -1 negative 207.044297968 1 402.6 207.044297585909 13C:0, 15N:0, 37Cl:0 -acetamiprid-N-desmethyl (M-H) [M-H]- C9H9N4Cl1 -1 negative 207.044297968 1 402.6 208.041332545909 13C:0, 15N:1, 37Cl:0 -acetamiprid-N-desmethyl (M-H) [M-H]- C9H9N4Cl1 -1 negative 207.044297968 1 402.6 208.047652425909 13C:1, 15N:0, 37Cl:0 -acetamiprid-N-desmethyl (M-H) [M-H]- C9H9N4Cl1 -1 negative 207.044297968 1 402.6 209.041347475909 13C:0, 15N:0, 37Cl:1 -acetamiprid-N-desmethyl (M-H) [M-H]- C9H9N4Cl1 -1 negative 207.044297968 1 402.6 210.044702315909 13C:1, 15N:0, 37Cl:1 +name formula adduct charge ionization_mode precursor_mz msLevel rt mz +2,4-Dichlorophenoxyacetic acid ou 2,4-D (M-H) C8H6Cl2O3 (13C:0, 37Cl:0) [M-H]- -1 negative 218.962123412 1 484.2 218.962123019909 +2,4-Dichlorophenoxyacetic acid ou 2,4-D (M-H) C8H6Cl2O3 (13C:1, 37Cl:0) [M-H]- -1 negative 218.962123412 1 484.2 219.965477859909 +2,4-Dichlorophenoxyacetic acid ou 2,4-D (M-H) C8H6Cl2O3 (13C:0, 37Cl:1) [M-H]- -1 negative 218.962123412 1 484.2 220.959172909909 +2,4-Dichlorophenoxyacetic acid ou 2,4-D (M-H) C8H6Cl2O3 (13C:1, 37Cl:1) [M-H]- -1 negative 218.962123412 1 484.2 221.962527749909 +2,4-Dichlorophenoxyacetic acid ou 2,4-D (M-H) C8H6Cl2O3 (13C:0, 37Cl:2) [M-H]- -1 negative 218.962123412 1 484.2 222.956222799909 +2-diethylamino-6-methyl pyrimidin-4-ol/one (M-H) C9H15N3O1 (13C:0, 15N:0) [M-H]- -1 negative 180.1142361 1 451.8 180.114235677909 +2-diethylamino-6-methyl pyrimidin-4-ol/one (M-H) C9H15N3O1 (13C:0, 15N:1) [M-H]- -1 negative 180.1142361 1 451.8 181.111270637909 +2-diethylamino-6-methyl pyrimidin-4-ol/one (M-H) C9H15N3O1 (13C:1, 15N:0) [M-H]- -1 negative 180.1142361 1 451.8 181.117590517909 +3,5,6-Trichloro-2-pyridinol (M-H) C5H2Cl3N1O1 (13C:0, 37Cl:0) [M-H]- -1 negative 195.912920724 1 499.2 195.912920371909 +3,5,6-Trichloro-2-pyridinol (M-H) C5H2Cl3N1O1 (13C:1, 37Cl:0) [M-H]- -1 negative 195.912920724 1 499.2 196.916275211909 +3,5,6-Trichloro-2-pyridinol (M-H) C5H2Cl3N1O1 (13C:0, 37Cl:1) [M-H]- -1 negative 195.912920724 1 499.2 197.909970261909 +3,5,6-Trichloro-2-pyridinol (M-H) C5H2Cl3N1O1 (13C:1, 37Cl:1) [M-H]- -1 negative 195.912920724 1 499.2 198.913325101909 +3,5,6-Trichloro-2-pyridinol (M-H) C5H2Cl3N1O1 (13C:0, 37Cl:2) [M-H]- -1 negative 195.912920724 1 499.2 199.907020151909 +3,5,6-Trichloro-2-pyridinol (M-H) C5H2Cl3N1O1 (13C:1, 37Cl:2) [M-H]- -1 negative 195.912920724 1 499.2 200.910374991909 +3,5,6-Trichloro-2-pyridinol (M-H) C5H2Cl3N1O1 (13C:0, 37Cl:3) [M-H]- -1 negative 195.912920724 1 499.2 201.904070041909 +3-phenoxybenzoic acid (M-H) C13H10O3 (13C:0) [M-H]- -1 negative 213.05571818 1 517.8 213.055717727909 +3-phenoxybenzoic acid (M-H) C13H10O3 (13C:1) [M-H]- -1 negative 213.05571818 1 517.8 214.059072567909 +4-Fluoro-3-phenoxybenzoic acid (M-H) C13H9F1O3 (13C:0) [M-H]- -1 negative 231.04629636800001 1 532.2 231.046295895909 +4-Fluoro-3-phenoxybenzoic acid (M-H) C13H9F1O3 (13C:1) [M-H]- -1 negative 231.04629636800001 1 532.2 232.049650735909 +4-nitrophenol (M-H) C6H5N1O3 (13C:0) [M-H]- -1 negative 138.01966702000001 1 165 138.019666577909 +4-nitrophenol (M-H) C6H5N1O3 (13C:1) [M-H]- -1 negative 138.01966702000001 1 165 139.023021417909 +6-Chloronicotinic acid (M-H) C6H4Cl1N1O2 (13C:0, 37Cl:0) [M-H]- -1 negative 155.985780048 1 172.2 155.985779635909 +6-Chloronicotinic acid (M-H) C6H4Cl1N1O2 (13C:1, 37Cl:0) [M-H]- -1 negative 155.985780048 1 172.2 156.989134475909 +6-Chloronicotinic acid (M-H) C6H4Cl1N1O2 (13C:0, 37Cl:1) [M-H]- -1 negative 155.985780048 1 172.2 157.982829525909 +6-Chloronicotinic acid (M-H) C6H4Cl1N1O2 (13C:1, 37Cl:1) [M-H]- -1 negative 155.985780048 1 172.2 158.986184365909 +Acetochlor mercapturate (M-H) C19H28N2O5S1 (13C:0, 18O:0, 34S:0) [M-H]- -1 negative 395.164616996 1 607.2 395.164616293909 +Acetochlor mercapturate (M-H) C19H28N2O5S1 (13C:1, 18O:0, 34S:0) [M-H]- -1 negative 395.164616996 1 607.2 396.167971133909 +Acetochlor mercapturate (M-H) C19H28N2O5S1 (13C:0, 18O:0, 34S:1) [M-H]- -1 negative 395.164616996 1 607.2 397.160412433909 +Acetochlor mercapturate (M-H) C19H28N2O5S1 (13C:0, 18O:1, 34S:0) [M-H]- -1 negative 395.164616996 1 607.2 397.168862073909 +Acetochlor mercapturate (M-H) C19H28N2O5S1 (13C:2, 18O:0, 34S:0) [M-H]- -1 negative 395.164616996 1 607.2 397.171325973909 +Alachlor mercapturate (M-H) C19H28N2O5S1 (13C:0, 18O:0, 34S:0) [M-H]- -1 negative 395.164616996 1 607.2 395.164616293909 +Alachlor mercapturate (M-H) C19H28N2O5S1 (13C:1, 18O:0, 34S:0) [M-H]- -1 negative 395.164616996 1 607.2 396.167971133909 +Alachlor mercapturate (M-H) C19H28N2O5S1 (13C:0, 18O:0, 34S:1) [M-H]- -1 negative 395.164616996 1 607.2 397.160412433909 +Alachlor mercapturate (M-H) C19H28N2O5S1 (13C:0, 18O:1, 34S:0) [M-H]- -1 negative 395.164616996 1 607.2 397.168862073909 +Alachlor mercapturate (M-H) C19H28N2O5S1 (13C:2, 18O:0, 34S:0) [M-H]- -1 negative 395.164616996 1 607.2 397.171325973909 +Bentazone (M-H) C10H12N2O3S1 (13C:0, 34S:0) [M-H]- -1 negative 239.049587244 1 747.6 239.049586541909 +Bentazone (M-H) C10H12N2O3S1 (13C:1, 34S:0) [M-H]- -1 negative 239.049587244 1 747.6 240.052941381909 +Bentazone (M-H) C10H12N2O3S1 (13C:0, 34S:1) [M-H]- -1 negative 239.049587244 1 747.6 241.045382681909 +Diethylthiophosphate (M-H) C4H11O3P1S1 (13C:0, 34S:0) [M-H]- -1 negative 169.009375842 1 177 169.009374979909 +Diethylthiophosphate (M-H) C4H11O3P1S1 (13C:1, 34S:0) [M-H]- -1 negative 169.009375842 1 177 170.012729819909 +Diethylthiophosphate (M-H) C4H11O3P1S1 (13C:0, 34S:1) [M-H]- -1 negative 169.009375842 1 177 171.005171119909 +Fenhexamid (M-H) C14H17Cl2N1O2 (13C:0, 37Cl:0) [M-H]- -1 negative 300.056358144 1 689.4 300.056357761909 +Fenhexamid (M-H) C14H17Cl2N1O2 (13C:1, 37Cl:0) [M-H]- -1 negative 300.056358144 1 689.4 301.059712601909 +Fenhexamid (M-H) C14H17Cl2N1O2 (13C:0, 37Cl:1) [M-H]- -1 negative 300.056358144 1 689.4 302.053407651909 +Fenhexamid (M-H) C14H17Cl2N1O2 (13C:2, 37Cl:0) [M-H]- -1 negative 300.056358144 1 689.4 302.063067441909 +Fenhexamid (M-H) C14H17Cl2N1O2 (13C:1, 37Cl:1) [M-H]- -1 negative 300.056358144 1 689.4 303.056762491909 +Fenhexamid (M-H) C14H17Cl2N1O2 (13C:0, 37Cl:2) [M-H]- -1 negative 300.056358144 1 689.4 304.050457541909 +Fenhexamid (M-H) C14H17Cl2N1O2 (13C:1, 37Cl:2) [M-H]- -1 negative 300.056358144 1 689.4 305.053812381909 +Fenvalerate free acid (M-H) C11H13Cl1O2 (13C:0, 37Cl:0) [M-H]- -1 negative 211.053131336 1 585 211.053130913909 +Fenvalerate free acid (M-H) C11H13Cl1O2 (13C:1, 37Cl:0) [M-H]- -1 negative 211.053131336 1 585 212.056485753909 +Fenvalerate free acid (M-H) C11H13Cl1O2 (13C:0, 37Cl:1) [M-H]- -1 negative 211.053131336 1 585 213.050180803909 +Fenvalerate free acid (M-H) C11H13Cl1O2 (13C:1, 37Cl:1) [M-H]- -1 negative 211.053131336 1 585 214.053535643909 +Fipronil (M-H) C12H4Cl2F6N4O1S1 (13C:0, 37Cl:0, 15N:0, 34S:0) [M-H]- -1 negative 434.931430428 1 750 434.931429685909 +Fipronil (M-H) C12H4Cl2F6N4O1S1 (13C:0, 37Cl:0, 15N:1, 34S:0) [M-H]- -1 negative 434.931430428 1 750 435.928464645909 +Fipronil (M-H) C12H4Cl2F6N4O1S1 (13C:1, 37Cl:0, 15N:0, 34S:0) [M-H]- -1 negative 434.931430428 1 750 435.934784525909 +Fipronil (M-H) C12H4Cl2F6N4O1S1 (13C:0, 37Cl:0, 15N:0, 34S:1) [M-H]- -1 negative 434.931430428 1 750 436.927225825909 +Fipronil (M-H) C12H4Cl2F6N4O1S1 (13C:0, 37Cl:1, 15N:0, 34S:0) [M-H]- -1 negative 434.931430428 1 750 436.928479575909 +Fipronil (M-H) C12H4Cl2F6N4O1S1 (13C:1, 37Cl:1, 15N:0, 34S:0) [M-H]- -1 negative 434.931430428 1 750 437.931834415909 +Fipronil (M-H) C12H4Cl2F6N4O1S1 (13C:0, 37Cl:1, 15N:0, 34S:1) [M-H]- -1 negative 434.931430428 1 750 438.924275715909 +Fipronil (M-H) C12H4Cl2F6N4O1S1 (13C:0, 37Cl:2, 15N:0, 34S:0) [M-H]- -1 negative 434.931430428 1 750 438.925529465909 +Fipronil (M-H) C12H4Cl2F6N4O1S1 (13C:1, 37Cl:2, 15N:0, 34S:0) [M-H]- -1 negative 434.931430428 1 750 439.928884305909 +Fipronil sulfone (M-H) C12H4Cl2F6N4O2S1 (13C:0, 37Cl:0, 15N:0, 34S:0) [M-H]- -1 negative 450.92634504800003 1 771 450.926344305909 +Fipronil sulfone (M-H) C12H4Cl2F6N4O2S1 (13C:0, 37Cl:0, 15N:1, 34S:0) [M-H]- -1 negative 450.92634504800003 1 771 451.923379265909 +Fipronil sulfone (M-H) C12H4Cl2F6N4O2S1 (13C:1, 37Cl:0, 15N:0, 34S:0) [M-H]- -1 negative 450.92634504800003 1 771 451.929699145909 +Fipronil sulfone (M-H) C12H4Cl2F6N4O2S1 (13C:0, 37Cl:0, 15N:0, 34S:1) [M-H]- -1 negative 450.92634504800003 1 771 452.922140445909 +Fipronil sulfone (M-H) C12H4Cl2F6N4O2S1 (13C:0, 37Cl:1, 15N:0, 34S:0) [M-H]- -1 negative 450.92634504800003 1 771 452.923394195909 +Fipronil sulfone (M-H) C12H4Cl2F6N4O2S1 (13C:1, 37Cl:1, 15N:0, 34S:0) [M-H]- -1 negative 450.92634504800003 1 771 453.926749035909 +Fipronil sulfone (M-H) C12H4Cl2F6N4O2S1 (13C:0, 37Cl:1, 15N:0, 34S:1) [M-H]- -1 negative 450.92634504800003 1 771 454.919190335909 +Fipronil sulfone (M-H) C12H4Cl2F6N4O2S1 (13C:0, 37Cl:2, 15N:0, 34S:0) [M-H]- -1 negative 450.92634504800003 1 771 454.920444085909 +Fipronil sulfone (M-H) C12H4Cl2F6N4O2S1 (13C:1, 37Cl:2, 15N:0, 34S:0) [M-H]- -1 negative 450.92634504800003 1 771 455.923798925909 +Hydroxy-tebuconazole (M-H) C16H22Cl1N3O2 (13C:0, 37Cl:0, 15N:0) [M-H]- -1 negative 322.132778624 1 696.6 322.132778231909 +Hydroxy-tebuconazole (M-H) C16H22Cl1N3O2 (13C:0, 37Cl:0, 15N:1) [M-H]- -1 negative 322.132778624 1 696.6 323.129813191909 +Hydroxy-tebuconazole (M-H) C16H22Cl1N3O2 (13C:1, 37Cl:0, 15N:0) [M-H]- -1 negative 322.132778624 1 696.6 323.136133071909 +Hydroxy-tebuconazole (M-H) C16H22Cl1N3O2 (13C:0, 37Cl:1, 15N:0) [M-H]- -1 negative 322.132778624 1 696.6 324.129828121909 +Hydroxy-tebuconazole (M-H) C16H22Cl1N3O2 (13C:2, 37Cl:0, 15N:0) [M-H]- -1 negative 322.132778624 1 696.6 324.139487911909 +Hydroxy-tebuconazole (M-H) C16H22Cl1N3O2 (13C:1, 37Cl:1, 15N:0) [M-H]- -1 negative 322.132778624 1 696.6 325.133182961909 +Fluopyram (M-H) C16H11Cl1F6N2O1 (13C:0, 37Cl:0) [M-H]- -1 negative 395.039133972 1 725.4 395.039133449909 +Fluopyram (M-H) C16H11Cl1F6N2O1 (13C:1, 37Cl:0) [M-H]- -1 negative 395.039133972 1 725.4 396.042488289909 +Fluopyram (M-H) C16H11Cl1F6N2O1 (13C:0, 37Cl:1) [M-H]- -1 negative 395.039133972 1 725.4 397.036183339909 +Fluopyram (M-H) C16H11Cl1F6N2O1 (13C:2, 37Cl:0) [M-H]- -1 negative 395.039133972 1 725.4 397.045843129909 +Fluopyram (M-H) C16H11Cl1F6N2O1 (13C:1, 37Cl:1) [M-H]- -1 negative 395.039133972 1 725.4 398.039538179909 +Mecoprop (M-H) C10H11Cl1O3 (13C:0, 37Cl:0) [M-H]- -1 negative 213.032395892 1 544.8 213.032395469909 +Mecoprop (M-H) C10H11Cl1O3 (13C:1, 37Cl:0) [M-H]- -1 negative 213.032395892 1 544.8 214.035750309909 +Mecoprop (M-H) C10H11Cl1O3 (13C:0, 37Cl:1) [M-H]- -1 negative 213.032395892 1 544.8 215.029445359909 +Mecoprop (M-H) C10H11Cl1O3 (13C:1, 37Cl:1) [M-H]- -1 negative 213.032395892 1 544.8 216.032800199909 +p-Toluenesulfonamide (M-H) C7H9N1O2S1 (13C:0, 34S:0) [M-H]- -1 negative 170.028123528 1 362.4 170.028122815909 +p-Toluenesulfonamide (M-H) C7H9N1O2S1 (13C:1, 34S:0) [M-H]- -1 negative 170.028123528 1 362.4 171.031477655909 +p-Toluenesulfonamide (M-H) C7H9N1O2S1 (13C:0, 34S:1) [M-H]- -1 negative 170.028123528 1 362.4 172.023918955909 +Triclosan (M-H) C12H7Cl3O2 (13C:0, 37Cl:0) [M-H]- -1 negative 286.943886504 1 811.8 286.943886141909 +Triclosan (M-H) C12H7Cl3O2 (13C:1, 37Cl:0) [M-H]- -1 negative 286.943886504 1 811.8 287.947240981909 +Triclosan (M-H) C12H7Cl3O2 (13C:0, 37Cl:1) [M-H]- -1 negative 286.943886504 1 811.8 288.940936031909 +Triclosan (M-H) C12H7Cl3O2 (13C:1, 37Cl:1) [M-H]- -1 negative 286.943886504 1 811.8 289.944290871909 +Triclosan (M-H) C12H7Cl3O2 (13C:0, 37Cl:2) [M-H]- -1 negative 286.943886504 1 811.8 290.937985921909 +Triclosan (M-H) C12H7Cl3O2 (13C:1, 37Cl:2) [M-H]- -1 negative 286.943886504 1 811.8 291.941340761909 +Triclosan (M-H) C12H7Cl3O2 (13C:0, 37Cl:3) [M-H]- -1 negative 286.943886504 1 811.8 292.935035811909 +Triclosan glucuronide (M-H) C18H15Cl3O8 (13C:0, 37Cl:0, 18O:0) [M-H]- -1 negative 462.97597448 1 665.4 462.975974117909 +Triclosan glucuronide (M-H) C18H15Cl3O8 (13C:1, 37Cl:0, 18O:0) [M-H]- -1 negative 462.97597448 1 665.4 463.979328957909 +Triclosan glucuronide (M-H) C18H15Cl3O8 (13C:0, 37Cl:1, 18O:0) [M-H]- -1 negative 462.97597448 1 665.4 464.973024007909 +Triclosan glucuronide (M-H) C18H15Cl3O8 (13C:0, 37Cl:0, 18O:1) [M-H]- -1 negative 462.97597448 1 665.4 464.980219897909 +Triclosan glucuronide (M-H) C18H15Cl3O8 (13C:2, 37Cl:0, 18O:0) [M-H]- -1 negative 462.97597448 1 665.4 464.982683797909 +Triclosan glucuronide (M-H) C18H15Cl3O8 (13C:1, 37Cl:1, 18O:0) [M-H]- -1 negative 462.97597448 1 665.4 465.976378847909 +Triclosan glucuronide (M-H) C18H15Cl3O8 (13C:0, 37Cl:2, 18O:0) [M-H]- -1 negative 462.97597448 1 665.4 466.970073897909 +Triclosan glucuronide (M-H) C18H15Cl3O8 (13C:0, 37Cl:1, 18O:1) [M-H]- -1 negative 462.97597448 1 665.4 466.977269787909 +Triclosan glucuronide (M-H) C18H15Cl3O8 (13C:2, 37Cl:1, 18O:0) [M-H]- -1 negative 462.97597448 1 665.4 466.979733687909 +Triclosan glucuronide (M-H) C18H15Cl3O8 (13C:1, 37Cl:2, 18O:0) [M-H]- -1 negative 462.97597448 1 665.4 467.973428737909 +Triclosan glucuronide (M-H) C18H15Cl3O8 (13C:0, 37Cl:3, 18O:0) [M-H]- -1 negative 462.97597448 1 665.4 468.967123787909 +Triclosan sulfate (M-H) C12H7Cl3O5S1 (13C:0, 37Cl:0, 18O:0, 34S:0) [M-H]- -1 negative 366.900701364 1 695.4 366.900700731909 +Triclosan sulfate (M-H) C12H7Cl3O5S1 (13C:1, 37Cl:0, 18O:0, 34S:0) [M-H]- -1 negative 366.900701364 1 695.4 367.904055571909 +Triclosan sulfate (M-H) C12H7Cl3O5S1 (13C:0, 37Cl:0, 18O:0, 34S:1) [M-H]- -1 negative 366.900701364 1 695.4 368.896496871909 +Triclosan sulfate (M-H) C12H7Cl3O5S1 (13C:0, 37Cl:1, 18O:0, 34S:0) [M-H]- -1 negative 366.900701364 1 695.4 368.897750621909 +Triclosan sulfate (M-H) C12H7Cl3O5S1 (13C:0, 37Cl:0, 18O:1, 34S:0) [M-H]- -1 negative 366.900701364 1 695.4 368.904946511909 +Triclosan sulfate (M-H) C12H7Cl3O5S1 (13C:1, 37Cl:1, 18O:0, 34S:0) [M-H]- -1 negative 366.900701364 1 695.4 369.901105461909 +Triclosan sulfate (M-H) C12H7Cl3O5S1 (13C:0, 37Cl:1, 18O:0, 34S:1) [M-H]- -1 negative 366.900701364 1 695.4 370.893546761909 +Triclosan sulfate (M-H) C12H7Cl3O5S1 (13C:0, 37Cl:2, 18O:0, 34S:0) [M-H]- -1 negative 366.900701364 1 695.4 370.894800511909 +Triclosan sulfate (M-H) C12H7Cl3O5S1 (13C:1, 37Cl:2, 18O:0, 34S:0) [M-H]- -1 negative 366.900701364 1 695.4 371.898155351909 +Triclosan sulfate (M-H) C12H7Cl3O5S1 (13C:0, 37Cl:2, 18O:0, 34S:1) [M-H]- -1 negative 366.900701364 1 695.4 372.890596651909 +Triclosan sulfate (M-H) C12H7Cl3O5S1 (13C:0, 37Cl:3, 18O:0, 34S:0) [M-H]- -1 negative 366.900701364 1 695.4 372.891850401909 +acetamiprid-N-desmethyl (M-H) C9H9N4Cl1 (13C:0, 15N:0, 37Cl:0) [M-H]- -1 negative 207.044297968 1 402.6 207.044297585909 +acetamiprid-N-desmethyl (M-H) C9H9N4Cl1 (13C:0, 15N:1, 37Cl:0) [M-H]- -1 negative 207.044297968 1 402.6 208.041332545909 +acetamiprid-N-desmethyl (M-H) C9H9N4Cl1 (13C:1, 15N:0, 37Cl:0) [M-H]- -1 negative 207.044297968 1 402.6 208.047652425909 +acetamiprid-N-desmethyl (M-H) C9H9N4Cl1 (13C:0, 15N:0, 37Cl:1) [M-H]- -1 negative 207.044297968 1 402.6 209.041347475909 +acetamiprid-N-desmethyl (M-H) C9H9N4Cl1 (13C:1, 15N:0, 37Cl:1) [M-H]- -1 negative 207.044297968 1 402.6 210.044702315909