Skip to content

Commit

Permalink
align_ip inside align
Browse files Browse the repository at this point in the history
  • Loading branch information
lalo-caballero committed Feb 22, 2024
1 parent cccb778 commit 89bdf87
Show file tree
Hide file tree
Showing 4 changed files with 36 additions and 79 deletions.
47 changes: 22 additions & 25 deletions R/align-GCIMSDataset.R
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@
setMethod(
"align",
"GCIMSDataset",
function(object) {
function(object, method = "pow", shift_ip = TRUE) {
tis_matrix <- getTIS(object)
ric_matrix <- getRIC(object)
dt <- dtime(object)
Expand All @@ -19,7 +19,9 @@ setMethod(
dt = dt,
rt = rt,
tis_matrix = tis_matrix,
ric_matrix = ric_matrix
ric_matrix = ric_matrix,
method = method,
shift_ip = shift_ip
)

delayed_op <- DelayedOperation(
Expand Down Expand Up @@ -70,30 +72,14 @@ setMethod(
ds
}

#' Find the best retention time reference chromatogram.
#' @noRd
#'
#' @description This function provides the index corresponding to the reference Reactant Ion Chromatogram (RIC) to correct
#' misalignments in retention time.
#' @param rics A matrix. Each row correspond to a different RIC. There are as many RICs as samples.
#' @return An Integer number that indicates the reference sample.
#' @examples
#' rics <- rbind(
#' dnorm(1:100, mean=50, sd =1),
#' dnorm(1:100, mean=51, sd =1),
#' dnorm(1:100, mean=52, sd =1)
#' )
#' find_reference_ric(rics) == 2L
find_reference_ric <- function(rics){
ref_ric_sample_idx <- ptw::bestref(rics)$best.ref
return(ref_ric_sample_idx)
}



alignParams <- function(dt, rt, tis_matrix, ric_matrix) {
alignParams <- function(dt, rt, tis_matrix, ric_matrix, method, shift_ip) {
# Optimize ret time alignment parameters:
ref_ric_sample_idx <- find_reference_ric(ric_matrix)
if (method == "ptw"){
ref_ric_sample_idx <- ptw::bestref(ric_matrix)$best.ref
} else {
ref_ric_sample_idx <- pow::select_reference(ric_matrix)
}
# Select reference RIC
ric_ref <- as.numeric(ric_matrix[ref_ric_sample_idx, ])

Expand All @@ -102,7 +88,18 @@ alignParams <- function(dt, rt, tis_matrix, ric_matrix) {
rip_ref_idx <- round(stats::median(rip_position, na.rm = TRUE))
rip_ref_ms <- dt[rip_ref_idx]

list(rip_ref_ms = rip_ref_ms, ric_ref = ric_ref, ric_ref_rt = rt)
# align ip params

mins <- apply(ric_matrix, 1,which.min)
rt_ref <- rt[1 : (length(rt) - (max(mins) - min(mins)))]
min_start <- min(mins) - 1

list(rip_ref_ms = rip_ref_ms,
ric_ref = ric_ref,
ric_ref_rt = rt,
min_start = min_start,
rt_ref = rt_ref,
shift_ip = shift_ip)
}

#' Plots to interpret alignment results
Expand Down
17 changes: 14 additions & 3 deletions R/align-GCIMSSample.R
Original file line number Diff line number Diff line change
Expand Up @@ -7,15 +7,26 @@
#' @export
methods::setMethod(
"align", "GCIMSSample",
function(object, rip_ref_ms, ric_ref, ric_ref_rt){
function(object, rip_ref_ms, ric_ref, ric_ref_rt, min_start, rt_ref, shift_ip){
if (all(is.na(object@data))) {
cli_abort("All the data matrix of {description(object)} are missing values. Align is impossible")
}
object <- alignDt(object, rip_ref_ms = rip_ref_ms)
if (all(is.na(object@data))) {
cli_abort("After aligning drift times, all the data matrix of {description(object)} are missing values. This should not happen")
}
object <- alignRt(object, ric_ref = ric_ref, ric_ref_rt = ric_ref_rt)
if (shift_ip){
ric <- getRIC(object)
injection_point <- which.min(ric)
object@retention_time <- rt_ref
object@data <- object@data[, (injection_point - min_start):((injection_point - min_start)+length(rt_ref)-1)]
}
if (method == "ptw") {
object <- alignRt_ptw(object, ric_ref = ric_ref, ric_ref_rt = ric_ref_rt)
} else {
####object <- alignRt_pow
}

if (all(is.na(object@data))) {
cli_abort("After aligning drift and retention times, all the data matrix of {description(object)} are missing values. This should not happen")
}
Expand Down Expand Up @@ -100,7 +111,7 @@ methods::setMethod(
#' @importMethodsFrom ProtGenerics alignRt
#' @export
methods::setMethod(
"alignRt",
"alignRt_ptw",
signature = c(x = "GCIMSSample", y = "ANY"),
function(x, y, ric_ref, ric_ref_rt) {
optimize_polynomial_order <- function(ric_sample, ric_ref) {
Expand Down
31 changes: 0 additions & 31 deletions R/align_ip-GCIMSDataset.R

This file was deleted.

20 changes: 0 additions & 20 deletions R/align_ip-GCIMSSample.R

This file was deleted.

0 comments on commit 89bdf87

Please sign in to comment.