Skip to content
Snippets Groups Projects
Commit b9745c46 authored by Boris Koch's avatar Boris Koch
Browse files

update to version 1.0.4

parent 952d978c
No related branches found
No related tags found
No related merge requests found
![UltraMassExplorer](inst/figures/ume_package_icon.png)
### Version 1.0.4
- `assign_formulas()` adapted for formula libraries containing only one formula (e.g. when assigning the post-column standard in LCMS)
- `calc_recalibrate_ms()` adapted for formula libraries containing only one formula (e.g. when assigning the post-column standard in LCMS)
### Version 1.0.3
- New plot added for LCMS data (as provided by Dr. Xianyu Kong)
- Post-column standard (Naproxen) added to ume::known_mf.
......
......@@ -53,7 +53,7 @@ assign_formulas <- function(pl, formula_library, msg = FALSE, ...){
if(msg==T) message(" Peaklist mass range: ", round(pl[, min(m)],5), " - ", round(pl[, max(m)],5), " Da (", pl[, .N], " peaks)")
if(msg==T) message(" Library mass range: ", round(formula_library[, min(mass)],5), " - ", round(formula_library[, max(mass)],5), " Da (", formula_library[, .N], " formulas)\n")
a <- pl[, .N]
pl <- pl[m >= formula_library[, min(mass)] & m <= formula_library[, max(mass)],]
pl <- pl[m >= formula_library[, min(mass)]*0.9999 & m <= formula_library[, max(mass)]*1.0001,]
warning("Mass range in peaklist is not completely covered by formula library.\n "
, a-pl[,.N], " peaks were truncated from the original peak list.\n")
}
......
......@@ -10,7 +10,7 @@
#' @import data.table
#' @export
#' @return Adds columns 'm' for neutral molecular mass and m_min, m_max for the mass accuracy thresholds.
#' @examples calc_neutral_mass(m = 199.32, pol = "neg")
#' @examples calc_neutral_mass(mz = 199.32, pol = "neg")
calc_neutral_mass <- function(mz, pol = c("neg", "pos", "neutral"), ...){
......
......@@ -71,6 +71,15 @@ calc_recalibrate_ms <- function(pl,
# browser()
# formula_library <- data.table(c = c(14, 28), h = c(14, 28), o = c(3, 6),
# n = c(0,0), s = c(0,0), p = c(0,0),
# `13c`=c(0,0), `15n`=c(0,0), `34s`=c(0,0),
# mass = c(233.11312455, 466.2262491), mf = c("C14H11D3O3", "C28H22D6O6"))
formula_library <- check_formula_library(formula_library)
# formula_library
calibr_list <- match.arg(calibr_list)
pol <- match.arg(pol)
......@@ -108,7 +117,8 @@ calc_recalibrate_ms <- function(pl,
mf_library[, vkey:=1:nrow(mf_library)]
cal_peaks <- ume::assign_formulas(pl = pl[, ..cols], formula_library = mf_library, ...)
# cal_peaks <- assign_formulas(pl = pl[, ..cols], formula_library = mf_library, ma_dev = 2, pol = "neg")
# cal_peaks
# maximum number of annotations per spectrum
#cal_peaks[, .N, analysis_filename][,max(N)]
......@@ -116,7 +126,7 @@ calc_recalibrate_ms <- function(pl,
# Number of identified calibrant peaks in a spectrum
check <-
cal_peaks[, .(n_calibrants = .N), col_file_id][pl[, .(n_peaks = .N), col_file_id], on = col_file_id]
check
# Check if there are files, for which less than 'min_no_calibrants' masses was found
no_cal <- nrow(check[n_calibrants < min_no_calibrants | is.na(n_calibrants)])
......@@ -298,7 +308,8 @@ calc_recalibrate_ms <- function(pl,
# Recalibrate entire peaklist ####
pl <- cal_stats[pl, on = col_file_id]
pl <- ume::calc_neutral_mass(pl, ...)
# pl[, pl:=calc_neutral_mass(...)]
pl[, m:=calc_neutral_mass(...)]
pl[, m := (m - intercept) / slope]
if (pol == "neg") {
......
......@@ -78,7 +78,7 @@
# Local installation from tarball ####
utils::install.packages(
"\\\\smb.isibhv.dmawi.de\\projects-noreplica\\p_ume\\UME\\ume_1.0.2.tar.gz",
"\\\\smb.isibhv.dmawi.de\\projects-noreplica\\p_ume\\UME\\ume_1.0.3.tar.gz",
repos = NULL,
type = "source"
)
......@@ -429,13 +429,14 @@ known_mf <-
DBI::dbDisconnect(ch)
known_mf[info1 %like% "Naprox"]
is.data.table(known_mf)
usethis::use_data(known_mf,
overwrite = TRUE,
version = 3,
compress = "xz")
# save(known_mf, file = "data/known_mf.rda", version = 3, compress = "xz")
save(known_mf, file = "data/known_mf.rda", version = 2)
known_mf <- ume::known_mf
......
No preview for this file type
......@@ -22,6 +22,6 @@ The function also calculates the upper and lower mass boundaries for a mass accu
Expects column names 'mz' for m/z values and 'i_magnitude' for mass peak magnitude.
}
\examples{
calc_neutral_mass(m = 199.32, pol = "neg")
calc_neutral_mass(mz = 199.32, pol = "neg")
}
\keyword{misc}
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment