diff --git a/NAMESPACE b/NAMESPACE index 41635b1..dff3e3b 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -93,6 +93,7 @@ export(is.apt) export(is.intact.attributes) export(is.soma_adat) export(is_intact_attr) +export(is_lifted) export(is_seqFormat) export(left_join) export(lift_adat) @@ -144,6 +145,8 @@ importFrom(dplyr,ungroup) importFrom(lifecycle,deprecate_soft) importFrom(lifecycle,deprecate_stop) importFrom(lifecycle,deprecate_warn) +importFrom(lifecycle,deprecated) +importFrom(lifecycle,is_present) importFrom(magrittr,"%>%") importFrom(methods,new) importFrom(methods,setGeneric) diff --git a/R/adat-helpers.R b/R/adat-helpers.R index d944f1d..13812d0 100644 --- a/R/adat-helpers.R +++ b/R/adat-helpers.R @@ -62,12 +62,6 @@ getAdatVersion <- function(atts) { } -.ss_ver_map <- c(v3 = "1129", v3.0 = "1129", - v4 = "5k", v4.0 = "5k", - v4.1 = "7k", - v5 = "11k", v5.0 = "11k") - - #' Gets the SomaScan version #' #' @rdname adat-helpers @@ -92,7 +86,7 @@ getSomaScanVersion <- function(adat) { #' is.null(checkSomaScanVersion(ver)) #' @export checkSomaScanVersion <- function(ver) { - allowed <- c("v3.0", "v4", "v4.0", "v4.1", "v5", "v5.0") + allowed <- c("v4", "v4.0", "v4.1", "v5", "v5.0") if ( !tolower(ver) %in% allowed ) { stop("Unsupported assay version: ", .value(ver), ". Supported versions: ", .value(allowed), call. = FALSE) diff --git a/R/lift-adat.R b/R/lift-adat.R index 8b15dca..daabd46 100644 --- a/R/lift-adat.R +++ b/R/lift-adat.R @@ -17,9 +17,9 @@ #' Likewise, "lifting" from `v4.0` -> `v4.1` requires #' a separate annotations file and a `soma_adat` from SomaScan `v4.0`. #' -#' @param adat A `soma_adat` class object. -#' @param anno.tbl A table of annotations, typically the result of a call -#' to [read_annotations()]. +#' @inheritParams params +#' @param bridge The direction of the lift (i.e. bridge). +#' @param anno.tbl Deprecated. #' @return A "lifted" `soma_adat` object corresponding to the scaling #' reference in the `anno.tbl`. RFU values are rounded to 1 decimal to #' match standard SomaScan delivery format. @@ -50,19 +50,43 @@ #' attr(lifted, "Header")$HEADER$ProcessSteps #' attr(lifted, "Header")$HEADER$SignalSpace #' @importFrom tibble enframe deframe +#' @importFrom lifecycle deprecated is_present #' @export -lift_adat <- function(adat, anno.tbl) { +lift_adat <- function(adat, + bridge = c("11k_to_7k", "11k_to_5k", + "7k_to_11k", "7k_to_5k", + "5k_to_11k", "5k_to_7k"), + anno.tbl = deprecated()) { - stopifnot(inherits(adat, "soma_adat")) + stopifnot( + "`adat` must be a `soma_adat` class object." = inherits(adat, "soma_adat"), + "`adat` must have intact attributes." = is_intact_attr(adat) + ) + + if ( is_present() ) { + deprecate_warn( + "6.1.0", + "SomaDataIO::lift_adat(anno.tbl =)", + "SomaDataIO::lift_adat(bridge =)", + details = "Passing 'anno.tbl =' is now unnecessary." + ) + } + + bridge <- match.arg(bridge) # does a syntax check for allowed params atts <- attr(adat, "Header.Meta")$HEADER - anno_ver <- attr(anno.tbl, "version") - .check_anno(anno_ver) .check_anml(atts) + # the 'space' refers to the SomaScan assay version signal space + # prefer SignalSpace if present; NULL if absent + from_space <- getSomaScanVersion(adat) + checkSomaScanVersion(from_space) + from_space <- map_ver2k[[from_space]] # map ver to k and strip names + new_space <- .check_direction(from_space, bridge) # check and return new space + if ( grepl("Plasma", atts$StudyMatrix, ignore.case = TRUE) ) { - scalar_col <- ver_dict[[anno_ver]]$col_plasma + ref_vec <- .get_lift_ref(matrx = "plasma", bridge = bridge) } else if ( grepl("Serum", atts$StudyMatrix, ignore.case = TRUE) ) { - scalar_col <- ver_dict[[anno_ver]]$col_serum + ref_vec <- .get_lift_ref(matrx = "serum", bridge = bridge) } else { stop( "Unsupported matrix: ", .value(atts$StudyMatrix), ".\n", @@ -71,92 +95,28 @@ lift_adat <- function(adat, anno.tbl) { ) } - if ( scalar_col %in% names(anno.tbl) ) { - anno.tbl <- anno.tbl[, c("SeqId", scalar_col)] - } else { - stop( - "Unable to find the required 'Scalar' column in the annotations file.\n", - "Do you have the correct annotations file?", - call. = FALSE - ) - } - - # the 'space' refers to the assay version signal space - from_space <- atts$SignalSpace # prefer this; NULL if absent - if ( is.null(from_space) ) { - from_space <- atts$AssayVersion # if missing; use this - } - - .check_ver(from_space) - .check_direction(scalar_col, from_space) - - new_space <- gsub(".*(v[0-9]\\.[0-9])$", "\\1", scalar_col) - attr(adat, "Header.Meta")$HEADER$SignalSpace <- new_space - new_step <- sprintf("Annotation Lift (%s to %s)", tolower(from_space), new_space) + # update attrs with new SignalSpace information + attr(adat, "Header.Meta")$HEADER$SignalSpace <- map_k2ver[[new_space]] + attr(adat, "Header.Meta")$HEADER$AssayVersion <- map_k2ver[[new_space]] + new_step <- sprintf("Lifting Bridge (%s to %s)", + tolower(from_space), new_space) steps <- attr(adat, "Header.Meta")$HEADER$ProcessSteps attr(adat, "Header.Meta")$HEADER$ProcessSteps <- paste0(steps, ", ", new_step) - ref_vec <- deframe(anno.tbl) scaleAnalytes(adat, ref_vec) |> round(1L) } - -# Checks ---- -# check attributes of annotations tbl for a version -# x = annotations version from annotations tbl -.check_anno <- function(x) { - if ( is.null(x) ) { - stop("Unable to determine the Annotations file version in `anno.tbl`.\n", - "Please check the attributes via `attr(anno.tbl, 'version')`.", - call. = FALSE) - } - if ( !x %in% names(ver_dict) ) { - stop("Unknown Annotations file version from `anno.tbl`: ", .value(x), - "\nUnable to proceed without knowing annotations table specs.", - call. = FALSE) - } - invisible(NULL) -} - -# check that SomaScan data has been ANML normalized -# x = Header attributes -.check_anml <- function(x) { - steps <- x$ProcessSteps - if ( is.null(steps) | !grepl("ANML", steps, ignore.case = TRUE) ) { - stop("ANML normalized SOMAscan data is required for lifting.", - call. = FALSE) - } - invisible(NULL) -} - -# check supported versions: v4, v4.0, v4.1 -.check_ver <- function(ver) { - allowed <- c("v4", "v4.0", "v4.1") - if ( !tolower(ver) %in% allowed ) { - stop( - "Unsupported assay version: ", .value(ver), - ". Supported versions: ", .value(allowed), call. = FALSE - ) - } - invisible(NULL) -} - -#' @param x the name of the scalar column from the annotations table. -#' @param y the assay version from the adat header information. -#' @noRd -.check_direction <- function(x, y) { - y <- tolower(y) - if ( grepl("4\\.1.*4\\.0", x) & y == "v4" ) { - stop( - "Annotations table indicates v4.1 -> v4.0, however the ADAT object ", - "already appears to be in version ", y, " space.", call. = FALSE - ) - } - if ( grepl("4\\.0.*4\\.1", x) & y == "v4.1" ) { - stop( - "Annotations table indicates v4.0 -> v4.1, however the ADAT object ", - "already appears to be in version ", y, " space.", call. = FALSE - ) - } - invisible(NULL) +#' Test for lifted objects +#' +#' [is_lifted()] checks whether an object +#' has been lifted (bridged) by the presence +#' (or absence) of the `SignalSpace` entry +#' in the `soma_adat` attributes. +#' +#' @rdname lift_adat +#' @return Logical. Whether `adat` has been lifted. +#' @export +is_lifted <- function(adat) { + x <- attr(adat, "Header.Meta")$HEADER + !is.null(x$SignalSpace) } diff --git a/R/s3-print-soma-adat.R b/R/s3-print-soma-adat.R index 15f6c58..0c11705 100644 --- a/R/s3-print-soma-adat.R +++ b/R/s3-print-soma-adat.R @@ -24,7 +24,7 @@ print.soma_adat <- function(x, show_header = FALSE, ...) { atts_symbol <- if ( attsTRUE ) symb_tick else symb_cross meta <- getMeta(x) ver <- getSomaScanVersion(x) %||% "unknown" - ver <- sprintf("%s (%s)", ver, .ss_ver_map[tolower(ver)]) + ver <- sprintf("%s (%s)", ver, map_ver2k[tolower(ver)]) n_apts <- getAnalytes(x, n = TRUE) pad <- strrep(" ", 5L) dim_vars <- c("SomaScan version", "Attributes intact", "Rows", diff --git a/R/sysdata.rda b/R/sysdata.rda new file mode 100644 index 0000000..829a19b Binary files /dev/null and b/R/sysdata.rda differ diff --git a/R/utils-lift.R b/R/utils-lift.R new file mode 100644 index 0000000..fcb3e4d --- /dev/null +++ b/R/utils-lift.R @@ -0,0 +1,79 @@ + +# map external commercial names to +# internal SomaScan version names +# ---------------------------------- +# 1) bridge 2) lref obj +# ---------------------------------- +.bridge_map <- c( + "7k_to_5k" = "v4.1_to_v4.0", + "5k_to_7k" = "v4.0_to_v4.1", + "11k_to_7k" = "v5.0_to_v4.1", + "7k_to_11k" = "v4.1_to_v5.0", + "5k_to_11k" = "v4.0_to_v5.0", + "11k_to_5k" = "v5.0_to_v4.0" +) + +map_ver2k <- c( + V3 = "1129", + v3 = "1129", + v3.0 = "1129", + V4 = "5k", + v4 = "5k", + v4.0 = "5k", + V4.1 = "7k", + v4.1 = "7k", + V5 = "11k", + v5 = "11k", + v5.0 = "11k" +) + +map_k2ver <- c("1129" = "v3.0", "5k" = "v4.0", "7k" = "v4.1", "11k" = "v5.0") + +# matrx: either serum or plasma +# bridge: direction of the bridge +.get_lift_ref <- function(matrx = c("plasma", "serum"), bridge) { + matrx <- match.arg(matrx) + bridge <- .bridge_map[bridge] + df <- lref[[matrx]][, c("SeqId", bridge)] + setNames(df[[2L]], df[[1L]]) +} + + +# Checks ---- +# check that SomaScan data has been ANML normalized +# x = Header attributes +.check_anml <- function(x) { + steps <- x$ProcessSteps + if ( is.null(steps) | !grepl("ANML", steps, ignore.case = TRUE) ) { + stop("ANML normalized SOMAscan data is required for lifting.", + call. = FALSE) + } + invisible(NULL) +} + +#' @param x the 'from' space. +#' @param y the bridge variable, e.g. '5k_to_7k'. +#' @return The 'to' space, from the 'y' param. +#' @noRd +.check_direction <- function(x, y) { + x <- tolower(x) + from <- gsub("(.*)_to_(.*)$", "\\1", y) + to <- gsub("(.*)_to_(.*)$", "\\2", y) + + if ( isFALSE(x == from) ) { + stop( + "You have indicated a bridge from ", .value(from), + " space, however your RFU data appears to be in ", + .value(x), " space.", call. = FALSE + ) + } + if ( isTRUE(x == to) ) { + stop( + "You have indicated a bridge to ", .value(to), + " space, however your RFU data already appears to be in ", + .value(x), " space.", call. = FALSE + ) + } + + invisible(to) +} diff --git a/man/lift_adat.Rd b/man/lift_adat.Rd index 088eda5..13522f0 100644 --- a/man/lift_adat.Rd +++ b/man/lift_adat.Rd @@ -2,20 +2,31 @@ % Please edit documentation in R/lift-adat.R \name{lift_adat} \alias{lift_adat} +\alias{is_lifted} \title{Lift an ADAT Between Assay Versions} \usage{ -lift_adat(adat, anno.tbl) +lift_adat( + adat, + bridge = c("7k_to_5k", "5k_to_7k", "11k_to_7k", "7k_to_11k"), + anno.tbl = deprecated() +) + +is_lifted(adat) } \arguments{ -\item{adat}{A \code{soma_adat} class object.} +\item{adat}{A \code{soma_adat} object (with intact attributes), +typically created using \code{\link[=read_adat]{read_adat()}}.} + +\item{bridge}{The direction of the lift (i.e. bridge).} -\item{anno.tbl}{A table of annotations, typically the result of a call -to \code{\link[=read_annotations]{read_annotations()}}.} +\item{anno.tbl}{Deprecated.} } \value{ A "lifted" \code{soma_adat} object corresponding to the scaling reference in the \code{anno.tbl}. RFU values are rounded to 1 decimal to match standard SomaScan delivery format. + +Logical. Whether \code{adat} has been lifted. } \description{ The SomaScan platform continually improves its technical processes @@ -26,6 +37,11 @@ minute differences in RFU space for a given analyte, requiring a calibration This is accomplished by applying an analyte-specific scalar to each analyte RFU (ADAT column). The scalar values themselves are typically provided via \verb{*.xlsx} file, which can be parsed via \code{\link[=read_annotations]{read_annotations()}}. See Details. + +\code{\link[=is_lifted]{is_lifted()}} checks whether an object +has been lifted (bridged) by the presence +(or absence) of the \code{SignalSpace} entry +in the \code{soma_adat} attributes. } \details{ Lifting between various versions requires a specific diff --git a/tests/testthat/test-lift-adat.R b/tests/testthat/test-lift-adat.R index 3f2cffb..55e9e92 100644 --- a/tests/testthat/test-lift-adat.R +++ b/tests/testthat/test-lift-adat.R @@ -1,81 +1,58 @@ # Setup ---- apts <- head(getAnalytes(example_data), 3L) -adat <- example_data[1:3, c("SampleId", apts)] - -# mock up a dummy annotations table -# example_data is V4; lift V4 -> v4.1 -tbl <- tibble::tibble( - SeqId = getSeqId(apts), "Plasma Scalar v4.0 to v4.1" = c(0.5, 1.1, 1.5) -) -attr(tbl, "version") <- "SL-99999999-rev99-1999-01" # lookup test from `ver_dict` - - +adat <- example_data[1:3L, c("SampleId", apts)] # Testing ---- test_that("a mock table of scalars transforms to correct, rounded values", { - a <- lift_adat(adat, tbl) - expect_equal(a$seq.10000.28, round(adat$seq.10000.28 * 0.5, 1L)) - expect_equal(a$seq.10001.7, round(adat$seq.10001.7 * 1.1, 1L)) - expect_equal(a$seq.10003.15, round(adat$seq.10003.15 * 1.5, 1L)) -}) - -test_that("a reference vector of 1.0 scalars returns identical adat", { - tbl$`Plasma Scalar v4.0 to v4.1` <- 1.0 - a <- lift_adat(adat, tbl) - expect_equal(a, adat, ignore_attr = TRUE) # Header.Meta modified - # check that header entries were added correctly + expect_equal(getSomaScanVersion(adat), "V4") # orig; 5k + expect_warning( a <- lift_adat(adat, bridge = "5k_to_7k") ) + expect_true(is_lifted(a)) + expect_equal(getSomaScanVersion(a), "v4.1") # updated; 7k expect_equal(attr(a, "Header")$HEADER$SignalSpace, "v4.1") - expect_match(attr(a, "Header")$HEADER$ProcessSteps, "Annotation Lift") + expect_match(attr(a, "Header")$HEADER$ProcessSteps, "Lifting Bridge") + expect_equal(a$seq.10000.28, round(adat$seq.10000.28 * 1.054, 1L)) + expect_equal(a$seq.10001.7, round(adat$seq.10001.7 * 1.300, 1L)) + expect_equal(a$seq.10003.15, round(adat$seq.10003.15 * 1.508, 1L)) }) -test_that("an error occurs if analytes are missing from anno.tbl", { - t2 <- head(tbl, 2) +test_that("lifting wrong direction triggers error; .check_direction()", { expect_error( - lift_adat(adat, t2), - paste0("Missing scalar value for 1 analytes. Cannot continue.\n", - "Please check the reference scalars, their names, or the ", - "annotations file to proceed."), fixed = TRUE + lift_adat(adat, "5k_to_5k"), + "'arg' should be one of" ) -}) - -test_that("lifting wrong direction triggers error", { - attributes(adat)$Header.Meta$HEADER$AssayVersion <- "v4.1" expect_error( - lift_adat(adat, tbl), - "Annotations table indicates v4.0 -> v4.1, .* v4.1 space" + lift_adat(adat, "7k_to_5k"), + "You have indicated a bridge from '7k' space" ) -}) - -test_that("error is tripped if Scalar is not found in annotations table", { - names(tbl) <- c("SeqId", "ReferenceScalars") + attr(adat, "Header.Meta")$HEADER$AssayVersion <- "v5.0" # 11k expect_error( - lift_adat(adat, tbl), - "Unable to find the required 'Scalar' column in the annotations file" + lift_adat(adat, "5k_to_7k"), + "You have indicated a bridge from '5k' space" ) }) test_that("un-supported matrices are trapped", { - attributes(adat)$Header.Meta$HEADER$StudyMatrix <- "Cell Lysate" + attr(adat, "Header.Meta")$HEADER$StudyMatrix <- "Cell Lysate" expect_error( - lift_adat(adat, tbl), + lift_adat(adat, "5k_to_7k"), "Unsupported matrix: .*'Cell Lysate'.*\\.\nCurrent supported matrices:" ) }) test_that("only supported assay versions are allowed", { - attributes(adat)$Header.Meta$HEADER$AssayVersion <- "V3" + attr(adat, "Header.Meta")$HEADER$AssayVersion <- "V3" expect_error( - lift_adat(adat, tbl), - "Unsupported assay version: .*V3.*\\. Supported versions:" + lift_adat(adat), + "Unsupported assay version: 'V3'\\. Supported versions:" ) }) test_that("only ANML normalized data can be lifted", { - attributes(adat)$Header.Meta$HEADER$ProcessSteps <- # trim off ANML step - strtrim(attributes(adat)$Header.Meta$HEADER$ProcessSteps, 74) + attr(adat, "Header.Meta")$HEADER$ProcessSteps <- # trim off ANML step + strtrim(attr(adat, "Header.Meta")$HEADER$ProcessSteps, 74L) expect_error( - lift_adat(adat, tbl), + lift_adat(adat), "ANML normalized SOMAscan data is required for lifting." ) })