Skip to content

Commit

Permalink
fixes
Browse files Browse the repository at this point in the history
  • Loading branch information
philouail committed Mar 14, 2024
1 parent e5fab92 commit 4c4caa7
Show file tree
Hide file tree
Showing 8 changed files with 46 additions and 33 deletions.
6 changes: 3 additions & 3 deletions R/AllGenerics.R
Original file line number Diff line number Diff line change
Expand Up @@ -80,10 +80,10 @@ setGeneric("addProcessHistory", function(object, ...)
#' example, by checking the number of matches and ranges of the matching
#' peaks, by first running `[matchLamasChromPeaks()]`.
#'
#' Different warping methods are available; users can choose to fit a loess
#' (`method = "loess"`, the default) or a gam (`method = "gam"`) between the
#' Different warping methods are available; users can choose to fit a *loess*
#' (`method = "loess"`, the default) or a *gam* (`method = "gam"`) between the
#' reference data points and observed matching ChromPeaks. Additional
#' parameters such as `span`, `weight`, `outlier_tolerance`, `zeroWeight`,
#' parameters such as `span`, `weight`, `outlierTolerance`, `zeroWeight`,
#' and `bs` are specific to these models. These parameters offer flexibility
#' in fine-tuning how the matching chromatographic peaks are fitted to the
#' lamas, thereby generating a model to align the overall retention time for
Expand Down
27 changes: 16 additions & 11 deletions R/do_adjustRtime-functions.R
Original file line number Diff line number Diff line change
Expand Up @@ -741,13 +741,13 @@ adjustRtimeSubset <- function(rtraw, rtadj, subset,
#' @title Match reference Lamas to ChromPeaks for evaluation prior to alignment
#'
#' @description
#' This function quickly matches each file's ChromPeaks to Lamas, allowing the
#' user to evaluate the matches for each file.
#' The `matchLamasChromPeaks()` function quickly matches each file's ChromPeaks
#' to Lamas, allowing the user to evaluate the matches for each file.
#'
#' @param object An object of class `XcmsExperiment` with defined ChromPeaks.
#'
#' @param param An object of class `LamaParama` that will later be used for
#' adjustment using the [adjustRtime()] function.
#' adjustment using the `[adjustRtime()]` function.
#'
#' @return A `LamaParama` object with new slot rtMap composed of a list of
#' matrices representing the 1:1 matches between Lamas (ref) and ChromPeaks
Expand All @@ -757,7 +757,7 @@ adjustRtimeSubset <- function(rtraw, rtadj, subset,
#' calling [adjustRtime()] with the same `LamaParama` and `XcmsExperiment`
#' object.
#'
#' @author Philippine Louail
#' @author Philippine Louail, Carl Brunius
#'
#' @rdname matchLamaChromPeaks
matchLamasChromPeaks <- function(object, param, BPPARAM = bpparam()){
Expand All @@ -778,18 +778,23 @@ matchLamasChromPeaks <- function(object, param, BPPARAM = bpparam()){
#' @title Summary of LamaParama retention time alignment
#'
#' @description
#' Generates a summary of the LamaParama method. Composed of coverage % of the
#' chrompeaks match over the total chrompeaks of the object. as well as a
#' summary of the model that will be applied to the file to adjust the
#' retention times
#' The `summarizeLamaMatch()` generates a summary of the LamaParama method.
#' Composed of coverage % of the chrompeaks match over the total chrompeaks of
#' the object. as well as a summary of the model that will be applied to the
#' file to adjust the retention times
#'
#' @param `LamaParama` same object that will be passed to the `adjustRtime()`
#' function. To run this function the `matchLamasChromPeaks()` need to be run
#' on this first.
#'
#' @return a data.frame
#' @return A `data.frame` with:
#'
#' @author Philippine Louail
#' - Total_peaks: total number of chromatographic peaks in the file
#' - Matched_peak: The number of matched peaks to Lamas
#' - Total_Lamas: Total number of Lamas
#' - Model_summary: `summary.loess` or `summary.gam` object for each file.
#'
#' @author Philippine Louail, Carl Brunius
#'
#' @rdname matchLamaChromPeaks
summarizeLamaMatch <- function(param){
Expand All @@ -808,7 +813,7 @@ summarizeLamaMatch <- function(param){
zero_weight = param@zeroWeight,
bs = param@bs))
})
res$model_summary <- res_model
res$Model_summary <- res_model
res
}

Expand Down
4 changes: 2 additions & 2 deletions R/functions-Params.R
Original file line number Diff line number Diff line change
Expand Up @@ -313,8 +313,8 @@ LamaParama <- function(lamas = matrix(ncol = 2, nrow = 0,
#' @export
#'
#' @rdname matchLamaChromPeaks
rtMap <- function(x){
if(!inherits(x, "LamaParama"))
rtMap <- function(param){
if(!inherits(param, "LamaParama"))
stop("The inputs need to be of class LamaParama")
rtMap <- param@rtMap
rtMap
Expand Down
6 changes: 3 additions & 3 deletions inst/NEWS
Original file line number Diff line number Diff line change
Expand Up @@ -4,9 +4,9 @@ Changes in version 4.1.10
- Implementation of the `LamaParama` class and method for the `adjustRtime()`
function. Allowing alignment of a dataset based on landmarks (lamas) from an
external reference dataset.
- Implementation of related user-level function `matchLamasChromPeaks()` which
allows for pre evaluation of matching between lamas and chromPeaks before
alignment.
- Implementation of related user-level function `matchLamasChromPeaks()`,
`summarizeMatchLama()` and `plot(LamaParama)` which allows for evaluation of
matching between lamas and chromPeaks.

Changes in version 4.1.9
----------------------
Expand Down
6 changes: 3 additions & 3 deletions man/adjustRtime.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

25 changes: 15 additions & 10 deletions man/matchLamaChromPeaks.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion tests/testthat/test_do_adjustRtime-functions.R
Original file line number Diff line number Diff line change
Expand Up @@ -390,7 +390,7 @@ test_that("summarizeLamaMatch works", {
res <- summarizeLamaMatch(param)
expect_equal(nrow(res), length(tst))
expect_equal(ncol(res), 4)
expect_true(inherits(res$model_summary[[1]], "summary.loess"))
expect_true(inherits(res$Model_summary[[1]], "summary.loess"))
})

test_that("Accessing rtMap from LamaParama object works", {
Expand Down
3 changes: 3 additions & 0 deletions vignettes/xcms.Rmd
Original file line number Diff line number Diff line change
Expand Up @@ -1410,6 +1410,9 @@ chromatographic peaks along with the fitted model line.
summary <- summarizeLamaMatch(param)
summary
# coverage for each file
summary$Matched_peaks / summary$Total_peaks * 100
#access the information on the model of for the first file
summary$model_summary[[1]]
Expand Down

0 comments on commit 4c4caa7

Please sign in to comment.