From cc4d3c20931e2176a2c8c8c96ab01e01ad688dbd Mon Sep 17 00:00:00 2001 From: Gero1999 Date: Sat, 7 Jun 2025 13:00:47 +0200 Subject: [PATCH 01/18] draft: default units_table for PKNCAdata --- R/class-PKNCAdata.R | 30 +------ R/unit-support.R | 206 +++++++++++++++++++++++++++++++++++++++++++- 2 files changed, 207 insertions(+), 29 deletions(-) diff --git a/R/class-PKNCAdata.R b/R/class-PKNCAdata.R index 495de041..a88abc11 100644 --- a/R/class-PKNCAdata.R +++ b/R/class-PKNCAdata.R @@ -170,34 +170,8 @@ PKNCAdata.default <- function(data.conc, data.dose, ..., # Insert the unit conversion table if (missing(units)) { - # What unit types are recognized? - possible_units <- - setdiff( - grep(x = names(formals(pknca_units_table)), pattern = "_", invert = TRUE, value = TRUE), - "conversions" - ) - possible_units_pref <- paste0(possible_units, "_pref") - # Accumulate available units - conc_units_values <- ret$conc$units - conc_units_cols <- ret$conc$columns[names(ret$conc$columns) %in% possible_units] - - unit_args <- conc_units_values - for (nm in names(conc_units_cols)) { - unit_args[[nm]] <- unique(stats::na.omit(ret$conc$data[[conc_units_cols[[nm]]]])) - } - - if (!identical(ret$dose, NA)) { - unit_args <- append(unit_args, ret$dose$units) - dose_units_cols <- ret$dose$columns[names(ret$dose$columns) %in% possible_units] - for (nm in names(dose_units_cols)) { - unit_args[[nm]] <- unique(stats::na.omit(ret$dose$data[[dose_units_cols[[nm]]]])) - } - } - # If there are any units to set, set them here - if (length(unit_args) > 0) { - unit_args <- lapply(X = unit_args, FUN = drop_attributes) - ret$units <- do.call(pknca_units_table, args = unit_args) - } + # Use the new automatic units table builder + ret$units <- pknca_units_table_auto(ret$conc, ret$dose) } else { stopifnot("`units` must be a data.frame"=is.data.frame(units)) stopifnot( diff --git a/R/unit-support.R b/R/unit-support.R index e1c97d37..ec8bbc38 100644 --- a/R/unit-support.R +++ b/R/unit-support.R @@ -110,7 +110,7 @@ pknca_units_table <- function(concu, doseu, amountu, timeu, conversions <- conversions_pref } - extra_cols <- setdiff(ret$PPTESTCD, names(PKNCA::get.interval.cols())) + extra_cols <- setdiff(ret$PPTESTCD, names(get.interval.cols())) if (length(extra_cols) > 0) { stop("Please report a bug. Unknown NCA parameters have units defined: ", paste(extra_cols, collapse=", ")) # nocov } @@ -420,3 +420,207 @@ pknca_unit_conversion <- function(result, units, allow_partial_missing_units = F } ret } + +#' Build Units Table for PKNCA +#' +#' This function generates a PKNCA units table including the potential unit segregating columns +#' among the dose and/or concentration groups. +#' +#' @param o_conc A PKNCA concentration object (PKNCAconc). +#' @param o_dose A PKNCA dose object (PKNCAdose). +#' +#' @returns A data frame containing the PKNCA formatted units table. +#' +#' @details +#' The function performs the following steps: +#' 1. Ensures the unit columns (e.g., `concu`, `timeu`, `doseu`, `amountu`) exist in the inputs. +#' 2. Joins the concentration and dose data based on their grouping columns. +#' 3. Generates a PKNCA units table for each group, including conversion factors and custom units. +#' 4. Returns a unique table with relevant columns for PKNCA analysis. +#' +#' @examples +#' # Assuming `o_conc` and `o_dose` are valid PKNCA objects: +#' # 1) Sharing group variables in their formulas +#' # 2) Time units are the same within dose and concentration groups +#' # 3) Units are the same for subjects within the same concentration group +#' +#' d_conc <- data.frame( +#' subj = 1, +#' analyte = rep(c("A", "B"), each = 2), +#' concu = rep(c("ng/mL", "ug/mL"), each = 2), +#' conc = c(0, 2, 0, 5), +#' time = rep(0:1, 2), +#' timeu = "h" +#' ) +#' d_dose <- data.frame( +#' subj = 1, +#' dose = 100, +#' doseu = "mg", +#' time = 0, +#' timeu = "h" +#' ) +#' o_conc <- PKNCAconc(d_conc, conc ~ time | subj / analyte, concu = "concu") +#' o_dose <- PKNCAdose(d_dose, dose ~ time | subj, doseu = "doseu") +#' units_table <- PKNCA_build_units_table(o_conc, o_dose) +#' +#' @importFrom dplyr select mutate rowwise any_of across everything %>% add_count inner_join group_vars +#' @importFrom tidyr unnest +#' @importFrom rlang sym syms +#' @importFrom utils capture.output +#' @export +pknca_units_table_auto <- function(o_conc, o_dose) { # nolint + + o_conc <- ensure_column_unit_exists(o_conc, c("concu", "timeu", "amountu")) + o_dose <- ensure_column_unit_exists(o_dose, c("doseu")) + + # Extract relevant columns from o_conc and o_dose + group_dose_cols <- group_vars(o_dose) + group_conc_cols <- group_vars(o_conc) + concu_col <- o_conc$columns$concu + amountu_col <- o_conc$columns$amountu + timeu_col <- o_conc$columns$timeu + doseu_col <- o_dose$columns$doseu + all_unit_cols <- c(concu_col, amountu_col, timeu_col, doseu_col) + + # Join dose units with concentration group columns and units + groups_units_tbl <- left_join( + o_conc$data %>% + select(any_of(c(group_conc_cols, concu_col, amountu_col, timeu_col))) %>% + unique(), + o_dose$data %>% + select(any_of(c(group_dose_cols, doseu_col))) %>% + unique(), + by = intersect(group_conc_cols, group_dose_cols) + ) %>% + # Prevent any issue with NAs in the group(s) or unit columns + mutate(across(everything(), ~ as.character(.))) %>% + unique() + + # Check that at least for each concentration group units are uniform + mismatching_units_groups <- groups_units_tbl %>% + add_count(!!!syms(group_conc_cols), name = "n") %>% + filter(n > 1) %>% + select(-n) + if (nrow(mismatching_units_groups) > 0) { + stop( + "Units should be uniform at least across concentration groups.", + "Review the units for the next group(s):\n", + paste(utils::capture.output(print(mismatching_units_groups)), collapse = "\n") + ) + } + + # Generate the PKNCA units table + groups_units_tbl %>% + # Pick only the group columns that are relevant in stratifying the units + select_minimal_grouping_cols(all_unit_cols) %>% + unique() %>% + # Create a PKNCA units table for each group + rowwise() %>% + mutate( + pknca_units_tbl = list( + pknca_units_table( + concu = !!sym(concu_col), + doseu = !!sym(doseu_col), + amountu = !!sym(amountu_col), + timeu = !!sym(timeu_col), + concu_pref = o_conc$units$concu_pref, + doseu_pref = o_dose$units$doseu_pref, + amountu_pref = o_conc$units$amountu_pref, + timeu_pref = o_conc$units$timeu_pref + ) + ) + ) %>% + # Combine all PKNCA units tables into one + unnest(cols = c(pknca_units_tbl)) %>% + # Order the columns to have them in a clean display + select( + any_of(c(group_conc_cols, group_dose_cols)), + any_of(c("PPTESTCD", "PPORRESU", "PPSTRESU", "conversion_factor")) + ) %>% + as.data.frame() +} + +#' Ensure Unit Columns Exist in PKNCA Object +#' +#' Checks if specified unit columns exist in a PKNCA object (either PKNCAconc or PKNCAdose). +#' If the columns do not exist, it creates them and assigns default values (NA or existing units). +#' +#' @param pknca_obj A PKNCA object (either PKNCAconc or PKNCAdose). +#' @param unit_name A character vector of unit column names to ensure (concu, amountu, timeu...). +#' @returns The updated PKNCA object with ensured unit columns. +#' +#' @details +#' The function performs the following steps: +#' 1. Checks if the specified unit columns exist in the PKNCA object. +#' 2. If a column does not exist, it creates the column and assigns default values. +#' 3. If not default values are provided, it assigns NA to the new column. +#' @keywords Internal +ensure_column_unit_exists <- function(pknca_obj, unit_name) { + for (unit in unit_name) { + if (is.null(pknca_obj$columns[[unit]])) { + unit_colname <- make.unique(c(names(pknca_obj$data), unit))[ncol(pknca_obj$data) + 1] + pknca_obj$columns[[unit]] <- unit_colname + if (!is.null(pknca_obj$units[[unit]])) { + pknca_obj$data[[unit_colname]] <- pknca_obj$units[[unit]] + } else { + pknca_obj$data[[unit_colname]] <- NA_character_ + } + } + } + pknca_obj +} + +#' Find Minimal Grouping Columns for Strata Reconstruction +#' +#' This function identifies the smallest set of columns in a data frame whose unique combinations +#' can reconstruct the grouping structure defined by the specified strata columns. +#' It removes duplicate, constant, and redundant columns, then searches for the minimal combination +#' that uniquely identifies each stratum. +#' +#' @param df A data frame. +#' @param strata_cols Column names in df whose unique combination defines the strata. +#' @returns A data frame containing the strata columns and their minimal set of grouping columns. +#' @keywords Internal +select_minimal_grouping_cols <- function(df, strata_cols) { + # If there is no strata_cols specified, simply return the original df + if (length(strata_cols) == 0) return(df) + + # Obtain the comb_vals values of the target column(s) + strata_vals <- df %>% + mutate(strata_cols_comb = paste(!!!syms(strata_cols), sep = "_")) %>% + pull(strata_cols_comb) + + # If the target column(s) only has one level, there are no relevant columns + if (length(unique(strata_vals)) == 1) { + return(df[strata_cols]) + } + + candidate_cols <- setdiff(names(df), strata_cols) + # 1. Remove columns that are duplicates in levels terms + candidate_levels <- lapply( + df[candidate_cols], function(x) as.numeric(factor(x, levels = unique(x))) + ) + candidate_cols <- candidate_cols[!duplicated(candidate_levels)] + + # 2. Remove columns with only 1 level + candidate_n_levels <- sapply(df[candidate_cols], function(x) length(unique(x))) + candidate_cols <- candidate_cols[candidate_n_levels > 1] + + # 3. Check combinations of columns to find minimal key combination to level group strata_cols + for (n in seq_len(length(candidate_cols))) { + all_candidate_combs <- combn(candidate_cols, n, simplify = FALSE) + for (comb in all_candidate_combs) { + comb_vals <- apply(df[, comb, drop = FALSE], 1, paste, collapse = "_") + if (all(tapply(strata_vals, comb_vals, FUN = \(x) length(unique(x)) == 1))) { + return(df[c(comb, strata_cols)]) + } + } + } + df[strata_cols] +} + +# Add globalVariables for NSE/dplyr/rlang/tidyr usage +utils::globalVariables(c( + "group_vars", "select", "any_of", "across", "everything", "add_count", "syms", "rowwise", "unnest", "pull", + "n", "pknca_units_tbl", "PPORRESU", "PPTESTCD", "PPSTRESU", "conversion_factor", "strata_cols_comb" +)) \ No newline at end of file From eae9cfb7564f701f3371b579d70601af7ecb4324 Mon Sep 17 00:00:00 2001 From: Gero1999 Date: Sat, 7 Jun 2025 13:01:51 +0200 Subject: [PATCH 02/18] test: include tests for the default units table for PKNCAconc &PKNCAdose --- tests/testthat/test-unit-support.R | 139 +++++++++++++++++++++++++++++ 1 file changed, 139 insertions(+) diff --git a/tests/testthat/test-unit-support.R b/tests/testthat/test-unit-support.R index 02f310a8..76dea7d7 100644 --- a/tests/testthat/test-unit-support.R +++ b/tests/testthat/test-unit-support.R @@ -311,3 +311,142 @@ test_that("pknca_unit_conversion", { fixed = TRUE ) }) + +# Tests for PKNA_build_units_table +describe("PKNCA_build_units_table", { + + # Subset the data to only include USUBJID 8 (2 analytes, A & B) + d_conc <- data.frame( + subject = 1, + time = rep(1:10, times = 4), + conc = rep(c(0:5, 4:1), times = 4), + analyte = rep(c("A", "B"), each = 20), + specimen = rep(c("blood", "urine"), each = 10, times = 4), + dose = 100, + treatment = rep(c("drug1", "drug2"), each = 10 * 4) + ) + d_dose <- unique(d_conc[d_conc$time %in% c(0, 5), c("dose", "time", "subject", "treatment")]) + + it("creates a stratified units table when PKNCAconc has a unit-stratifying group column", { + + for (strat_var in c("specimen", "analyte")) { + d_conc$concu_col <- ifelse(d_conc[[strat_var]] == d_conc[[strat_var]][1], "ng/mL", "ug/mL") + + o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte, concu = "concu_col") + o_dose <- PKNCAdose(d_dose, dose ~ time | treatment + subject) + units_table <- expect_no_error(pknca_units_table_auto(o_conc, o_dose)) + + expect_equal( + units_table[units_table$PPTESTCD == "cmax", c(strat_var, "PPORRESU")], + data.frame( + specimen = c(unique(d_conc[[strat_var]])[1], unique(d_conc[[strat_var]])[2]), + PPORRESU = c("ng/mL", "ug/mL") + ), ignore_attr = TRUE + ) + } + }) + it("creates a stratified units table when PKNCAconc has two unit-stratifying group columns", { + d_conc$concu_col <- ifelse(d_conc$analyte == "A", "ng/mL", "ug/mL") + d_conc$concu_col <- ifelse(d_conc$specimen == "blood", d_conc$concu_col, "pg/mL") + o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte, concu = "concu_col") + o_dose <- PKNCAdose(d_dose, dose ~ time | treatment + subject) + units_table <- expect_no_error(pknca_units_table_auto(o_conc, o_dose)) + + expect_equal( + units_table[units_table$PPTESTCD == "cmax",], + data.frame( + specimen = c("blood", "urine", "blood", "urine"), + analyte = rep(c("A", "B"), each = 2), + PPTESTCD = "cmax", + PPORRESU = c("ng/mL", "pg/mL", "ug/mL", "pg/mL") + ), ignore_attr = TRUE + ) + }) + + it("creates a stratified units table when PKNCAdose has a unit-stratifying column", { + d_dose$doseu_col <- ifelse(d_dose$treatment == d_dose$treatment[1], "mg", "ug") + o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte) + o_dose <- PKNCAdose(d_dose, dose ~ time | treatment + subject, doseu = "doseu_col") + units_table <- expect_no_error(pknca_units_table_auto(o_conc, o_dose)) + + expect_equal( + units_table[units_table$PPTESTCD == "totdose",], + data.frame( + treatment = c("drug1", "drug2"), + PPTESTCD = "totdose", + PPORRESU = c("mg", "ug") + ), ignore_attr = TRUE + ) + }) + + it("creates an uniform units table when units are not defined as columns in the PKNCA obj", { + o_conc <- PKNCAconc( + d_conc, conc ~ time | treatment + specimen + subject / analyte, + concu = "ng/mL", timeu = "h" + ) + o_dose <- PKNCAdose( + d_dose, dose ~ time | treatment + subject, + doseu = "mg" + ) + units_table <- expect_no_error(pknca_units_table_auto(o_conc, o_dose)) + expect_equal( + units_table[units_table$PPTESTCD == "cmax.dn",], + data.frame( + PPTESTCD = c("cmax.dn"), + PPORRESU = c("(ng/mL)/mg") + ), ignore_attr = TRUE + ) + }) + + it("creates a NA units table when units are not defined at all in the PKNCA objects", { + o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte) + o_dose <- PKNCAdose(d_dose, dose ~ time | treatment + subject) + units_table <- expect_no_error(pknca_units_table_auto(o_conc, o_dose)) + + expect_equal( + units_table[units_table$PPTESTCD %in% c("cmax", "totdose"),], + data.frame( + PPTESTCD = c("cmax", "totdose"), + PPORRESU = c(NA_character_, NA_character_) + ), ignore_attr = TRUE + ) + }) + + it("reports an error when units are inconsistent through all concentration groups", { + d_conc$concu_col <- "ng/mL" + d_conc$concu_col[1] <- "pg/L" # Introduce inconsistency + o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte, concu = "concu_col") + o_dose <- PKNCAdose(d_dose, dose ~ time | treatment + subject) + expect_error( + pknca_units_table_auto(o_conc, o_dose), + regexp = "Units should be uniform at least across concentration groups.*" + ) + }) +}) + +describe("select_level_grouping_cols", { + # Make a dataset where a variable `d` depends on `a` & `b` + data <- data.frame( + a = rep(letters[c(1, 2, 3)], each = 4), + b = rep(letters[c(1, 2)], each = 3), + c = letters[1] + ) + data$d <- paste0(data$a, data$b) + + it("returns the minimal grouping_columns (a, b) for one target column", { + result <- select_minimal_grouping_cols(data, "d") + expect_equal(result, data[c("a", "b", "d")]) + }) + + # Note: this case will never happen in the App or PKNCA_build_units_table + it("returns the original data if target_columns is NULL", { + result <- select_minimal_grouping_cols(data, NULL) + expect_equal(result, data) + }) + + it("returns just the strata columns if no stratification groups are found", { + data[, "a"] <- 10 + result <- select_minimal_grouping_cols(data, "d") + expect_equal(result, data["d"]) + }) +}) From 5fa7fd52043949b5852af8f6ef582ea4fe79622a Mon Sep 17 00:00:00 2001 From: Gero1999 Date: Sat, 7 Jun 2025 15:38:03 +0200 Subject: [PATCH 03/18] make fun to not need PKNCAdose --- R/unit-support.R | 6 +++++- tests/testthat/test-unit-support.R | 16 ++++++++++++++++ 2 files changed, 21 insertions(+), 1 deletion(-) diff --git a/R/unit-support.R b/R/unit-support.R index ec8bbc38..a6961643 100644 --- a/R/unit-support.R +++ b/R/unit-support.R @@ -468,8 +468,12 @@ pknca_unit_conversion <- function(result, units, allow_partial_missing_units = F #' @importFrom rlang sym syms #' @importFrom utils capture.output #' @export -pknca_units_table_auto <- function(o_conc, o_dose) { # nolint +pknca_units_table_auto <- function(o_conc, o_dose = NULL) { + # PKNCAdose is an optional argument with dose units, if not provided it will be ignored + if (is.null(o_dose)) o_dose <- o_conc + + # If needed, ensure that the PKNCA objects have the required unit columns o_conc <- ensure_column_unit_exists(o_conc, c("concu", "timeu", "amountu")) o_dose <- ensure_column_unit_exists(o_dose, c("doseu")) diff --git a/tests/testthat/test-unit-support.R b/tests/testthat/test-unit-support.R index 76dea7d7..4e072a9b 100644 --- a/tests/testthat/test-unit-support.R +++ b/tests/testthat/test-unit-support.R @@ -345,6 +345,7 @@ describe("PKNCA_build_units_table", { ) } }) + it("creates a stratified units table when PKNCAconc has two unit-stratifying group columns", { d_conc$concu_col <- ifelse(d_conc$analyte == "A", "ng/mL", "ug/mL") d_conc$concu_col <- ifelse(d_conc$specimen == "blood", d_conc$concu_col, "pg/mL") @@ -412,6 +413,21 @@ describe("PKNCA_build_units_table", { ) }) + it("does not strictly need o_dose (PKNCAdose object) to be provided", { + o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte, + concu = "concu_col") + units_table <- expect_no_error(pknca_units_table_auto(o_conc)) + expect_equal( + units_table[units_table$PPTESTCD == "cmax",], + data.frame( + specimen = c("blood", "urine", "blood", "urine"), + analyte = rep(c("A", "B"), each = 2), + PPTESTCD = "cmax", + PPORRESU = c("ng/mL", "pg/mL", "ug/mL", "pg/mL") + ), ignore_attr = TRUE + ) + }) + it("reports an error when units are inconsistent through all concentration groups", { d_conc$concu_col <- "ng/mL" d_conc$concu_col[1] <- "pg/L" # Introduce inconsistency From ebb0cab090239d25819fb6060367e22cec6ffcfc Mon Sep 17 00:00:00 2001 From: Gero1999 Date: Sat, 7 Jun 2025 16:06:26 +0200 Subject: [PATCH 04/18] rename: fun to pknca_units_table_from_pknca --- R/class-PKNCAdata.R | 2 +- R/unit-support.R | 8 ++++---- tests/testthat/test-unit-support.R | 14 +++++++------- 3 files changed, 12 insertions(+), 12 deletions(-) diff --git a/R/class-PKNCAdata.R b/R/class-PKNCAdata.R index a88abc11..132d077e 100644 --- a/R/class-PKNCAdata.R +++ b/R/class-PKNCAdata.R @@ -171,7 +171,7 @@ PKNCAdata.default <- function(data.conc, data.dose, ..., # Insert the unit conversion table if (missing(units)) { # Use the new automatic units table builder - ret$units <- pknca_units_table_auto(ret$conc, ret$dose) + ret$units <- pknca_units_table_from_pknca(ret$conc, ret$dose) } else { stopifnot("`units` must be a data.frame"=is.data.frame(units)) stopifnot( diff --git a/R/unit-support.R b/R/unit-support.R index a6961643..89ef05f5 100644 --- a/R/unit-support.R +++ b/R/unit-support.R @@ -421,13 +421,13 @@ pknca_unit_conversion <- function(result, units, allow_partial_missing_units = F ret } -#' Build Units Table for PKNCA +#' Build Units Table from PKNCA object(s) #' #' This function generates a PKNCA units table including the potential unit segregating columns #' among the dose and/or concentration groups. #' #' @param o_conc A PKNCA concentration object (PKNCAconc). -#' @param o_dose A PKNCA dose object (PKNCAdose). +#' @param o_dose A PKNCA dose object (PKNCAdose). Optional, if not provided dose units are considered missing. #' #' @returns A data frame containing the PKNCA formatted units table. #' @@ -468,7 +468,7 @@ pknca_unit_conversion <- function(result, units, allow_partial_missing_units = F #' @importFrom rlang sym syms #' @importFrom utils capture.output #' @export -pknca_units_table_auto <- function(o_conc, o_dose = NULL) { +pknca_units_table_from_pknca <- function(o_conc, o_dose = NULL) { # PKNCAdose is an optional argument with dose units, if not provided it will be ignored if (is.null(o_dose)) o_dose <- o_conc @@ -627,4 +627,4 @@ select_minimal_grouping_cols <- function(df, strata_cols) { utils::globalVariables(c( "group_vars", "select", "any_of", "across", "everything", "add_count", "syms", "rowwise", "unnest", "pull", "n", "pknca_units_tbl", "PPORRESU", "PPTESTCD", "PPSTRESU", "conversion_factor", "strata_cols_comb" -)) \ No newline at end of file +)) diff --git a/tests/testthat/test-unit-support.R b/tests/testthat/test-unit-support.R index 4e072a9b..c8ba5140 100644 --- a/tests/testthat/test-unit-support.R +++ b/tests/testthat/test-unit-support.R @@ -334,7 +334,7 @@ describe("PKNCA_build_units_table", { o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte, concu = "concu_col") o_dose <- PKNCAdose(d_dose, dose ~ time | treatment + subject) - units_table <- expect_no_error(pknca_units_table_auto(o_conc, o_dose)) + units_table <- expect_no_error(pknca_units_table_from_pknca(o_conc, o_dose)) expect_equal( units_table[units_table$PPTESTCD == "cmax", c(strat_var, "PPORRESU")], @@ -351,7 +351,7 @@ describe("PKNCA_build_units_table", { d_conc$concu_col <- ifelse(d_conc$specimen == "blood", d_conc$concu_col, "pg/mL") o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte, concu = "concu_col") o_dose <- PKNCAdose(d_dose, dose ~ time | treatment + subject) - units_table <- expect_no_error(pknca_units_table_auto(o_conc, o_dose)) + units_table <- expect_no_error(pknca_units_table_from_pknca(o_conc, o_dose)) expect_equal( units_table[units_table$PPTESTCD == "cmax",], @@ -368,7 +368,7 @@ describe("PKNCA_build_units_table", { d_dose$doseu_col <- ifelse(d_dose$treatment == d_dose$treatment[1], "mg", "ug") o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte) o_dose <- PKNCAdose(d_dose, dose ~ time | treatment + subject, doseu = "doseu_col") - units_table <- expect_no_error(pknca_units_table_auto(o_conc, o_dose)) + units_table <- expect_no_error(pknca_units_table_from_pknca(o_conc, o_dose)) expect_equal( units_table[units_table$PPTESTCD == "totdose",], @@ -389,7 +389,7 @@ describe("PKNCA_build_units_table", { d_dose, dose ~ time | treatment + subject, doseu = "mg" ) - units_table <- expect_no_error(pknca_units_table_auto(o_conc, o_dose)) + units_table <- expect_no_error(pknca_units_table_from_pknca(o_conc, o_dose)) expect_equal( units_table[units_table$PPTESTCD == "cmax.dn",], data.frame( @@ -402,7 +402,7 @@ describe("PKNCA_build_units_table", { it("creates a NA units table when units are not defined at all in the PKNCA objects", { o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte) o_dose <- PKNCAdose(d_dose, dose ~ time | treatment + subject) - units_table <- expect_no_error(pknca_units_table_auto(o_conc, o_dose)) + units_table <- expect_no_error(pknca_units_table_from_pknca(o_conc, o_dose)) expect_equal( units_table[units_table$PPTESTCD %in% c("cmax", "totdose"),], @@ -416,7 +416,7 @@ describe("PKNCA_build_units_table", { it("does not strictly need o_dose (PKNCAdose object) to be provided", { o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte, concu = "concu_col") - units_table <- expect_no_error(pknca_units_table_auto(o_conc)) + units_table <- expect_no_error(pknca_units_table_from_pknca(o_conc)) expect_equal( units_table[units_table$PPTESTCD == "cmax",], data.frame( @@ -434,7 +434,7 @@ describe("PKNCA_build_units_table", { o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte, concu = "concu_col") o_dose <- PKNCAdose(d_dose, dose ~ time | treatment + subject) expect_error( - pknca_units_table_auto(o_conc, o_dose), + pknca_units_table_from_pknca(o_conc, o_dose), regexp = "Units should be uniform at least across concentration groups.*" ) }) From 9ded1118f5a15fd41fbcbb9cbf6114a175254f8c Mon Sep 17 00:00:00 2001 From: Gero1999 Date: Sat, 7 Jun 2025 17:36:22 +0200 Subject: [PATCH 05/18] docs: roxygenise funs --- NAMESPACE | 12 +++++++ man/ensure_column_unit_exists.Rd | 29 +++++++++++++++ man/pknca_units_table_auto.Rd | 55 +++++++++++++++++++++++++++++ man/select_minimal_grouping_cols.Rd | 23 ++++++++++++ 4 files changed, 119 insertions(+) create mode 100644 man/ensure_column_unit_exists.Rd create mode 100644 man/pknca_units_table_auto.Rd create mode 100644 man/select_minimal_grouping_cols.Rd diff --git a/NAMESPACE b/NAMESPACE index 678742e6..91c15bd7 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -218,6 +218,7 @@ export(pk.tss) export(pk.tss.monoexponential) export(pk.tss.stepwise.linear) export(pknca_units_table) +export(pknca_units_table_from_pknca) export(right_join) export(roundString) export(roundingSummarize) @@ -232,16 +233,27 @@ export(time_calc) export(ungroup) export(var_sparse_auc) importFrom(dplyr,"%>%") +importFrom(dplyr,across) +importFrom(dplyr,add_count) +importFrom(dplyr,any_of) +importFrom(dplyr,everything) importFrom(dplyr,filter) importFrom(dplyr,full_join) importFrom(dplyr,group_by) +importFrom(dplyr,group_vars) importFrom(dplyr,inner_join) importFrom(dplyr,left_join) importFrom(dplyr,mutate) importFrom(dplyr,right_join) +importFrom(dplyr,rowwise) +importFrom(dplyr,select) importFrom(dplyr,ungroup) importFrom(lifecycle,deprecated) importFrom(nlme,getGroups) importFrom(rlang,.data) +importFrom(rlang,sym) +importFrom(rlang,syms) importFrom(stats,formula) importFrom(stats,model.frame) +importFrom(tidyr,unnest) +importFrom(utils,capture.output) diff --git a/man/ensure_column_unit_exists.Rd b/man/ensure_column_unit_exists.Rd new file mode 100644 index 00000000..5c630851 --- /dev/null +++ b/man/ensure_column_unit_exists.Rd @@ -0,0 +1,29 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/unit-support.R +\name{ensure_column_unit_exists} +\alias{ensure_column_unit_exists} +\title{Ensure Unit Columns Exist in PKNCA Object} +\usage{ +ensure_column_unit_exists(pknca_obj, unit_name) +} +\arguments{ +\item{pknca_obj}{A PKNCA object (either PKNCAconc or PKNCAdose).} + +\item{unit_name}{A character vector of unit column names to ensure (concu, amountu, timeu...).} +} +\value{ +The updated PKNCA object with ensured unit columns. +} +\description{ +Checks if specified unit columns exist in a PKNCA object (either PKNCAconc or PKNCAdose). +If the columns do not exist, it creates them and assigns default values (NA or existing units). +} +\details{ +The function performs the following steps: +\enumerate{ +\item Checks if the specified unit columns exist in the PKNCA object. +\item If a column does not exist, it creates the column and assigns default values. +\item If not default values are provided, it assigns NA to the new column. +} +} +\keyword{Internal} diff --git a/man/pknca_units_table_auto.Rd b/man/pknca_units_table_auto.Rd new file mode 100644 index 00000000..7d44e4fe --- /dev/null +++ b/man/pknca_units_table_auto.Rd @@ -0,0 +1,55 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/unit-support.R +\name{pknca_units_table_from_pknca} +\alias{pknca_units_table_from_pknca} +\title{Build Units Table for PKNCA} +\usage{ +pknca_units_table_from_pknca(o_conc, o_dose = NULL) +} +\arguments{ +\item{o_conc}{A PKNCA concentration object (PKNCAconc).} + +\item{o_dose}{A PKNCA dose object (PKNCAdose).} +} +\value{ +A data frame containing the PKNCA formatted units table. +} +\description{ +This function generates a PKNCA units table including the potential unit segregating columns +among the dose and/or concentration groups. +} +\details{ +The function performs the following steps: +\enumerate{ +\item Ensures the unit columns (e.g., \code{concu}, \code{timeu}, \code{doseu}, \code{amountu}) exist in the inputs. +\item Joins the concentration and dose data based on their grouping columns. +\item Generates a PKNCA units table for each group, including conversion factors and custom units. +\item Returns a unique table with relevant columns for PKNCA analysis. +} +} +\examples{ +# Assuming `o_conc` and `o_dose` are valid PKNCA objects: +# 1) Sharing group variables in their formulas +# 2) Time units are the same within dose and concentration groups +# 3) Units are the same for subjects within the same concentration group + +d_conc <- data.frame( + subj = 1, + analyte = rep(c("A", "B"), each = 2), + concu = rep(c("ng/mL", "ug/mL"), each = 2), + conc = c(0, 2, 0, 5), + time = rep(0:1, 2), + timeu = "h" +) +d_dose <- data.frame( + subj = 1, + dose = 100, + doseu = "mg", + time = 0, + timeu = "h" +) +o_conc <- PKNCAconc(d_conc, conc ~ time | subj / analyte, concu = "concu") +o_dose <- PKNCAdose(d_dose, dose ~ time | subj, doseu = "doseu") +units_table <- PKNCA_build_units_table(o_conc, o_dose) + +} diff --git a/man/select_minimal_grouping_cols.Rd b/man/select_minimal_grouping_cols.Rd new file mode 100644 index 00000000..d080bd42 --- /dev/null +++ b/man/select_minimal_grouping_cols.Rd @@ -0,0 +1,23 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/unit-support.R +\name{select_minimal_grouping_cols} +\alias{select_minimal_grouping_cols} +\title{Find Minimal Grouping Columns for Strata Reconstruction} +\usage{ +select_minimal_grouping_cols(df, strata_cols) +} +\arguments{ +\item{df}{A data frame.} + +\item{strata_cols}{Column names in df whose unique combination defines the strata.} +} +\value{ +A data frame containing the strata columns and their minimal set of grouping columns. +} +\description{ +This function identifies the smallest set of columns in a data frame whose unique combinations +can reconstruct the grouping structure defined by the specified strata columns. +It removes duplicate, constant, and redundant columns, then searches for the minimal combination +that uniquely identifies each stratum. +} +\keyword{Internal} From 518347f0427f42e38a0774ddc5828000e4b614ef Mon Sep 17 00:00:00 2001 From: Gero1999 Date: Sun, 8 Jun 2025 09:38:19 +0200 Subject: [PATCH 06/18] fix: consider case when ret$o_dose = NA --- R/unit-support.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/unit-support.R b/R/unit-support.R index c91b8d9b..074c1d4d 100644 --- a/R/unit-support.R +++ b/R/unit-support.R @@ -485,7 +485,7 @@ pknca_unit_conversion <- function(result, units, allow_partial_missing_units = F pknca_units_table_from_pknca <- function(o_conc, o_dose = NULL) { # PKNCAdose is an optional argument with dose units, if not provided it will be ignored - if (is.null(o_dose)) o_dose <- o_conc + if (is.null(o_dose) || is.na(o_dose)) o_dose <- o_conc # If needed, ensure that the PKNCA objects have the required unit columns o_conc <- ensure_column_unit_exists(o_conc, c("concu", "timeu", "amountu")) From 41d8bb563bda935bb4bcf95481b8264641e7dd37 Mon Sep 17 00:00:00 2001 From: Gero1999 Date: Sun, 8 Jun 2025 11:47:45 +0200 Subject: [PATCH 07/18] fix: 1) columns order, 2) NULL if no units specified, 3) ignore NAs --- R/unit-support.R | 20 ++++++++---- ...uto.Rd => pknca_units_table_from_pknca.Rd} | 6 ++-- tests/testthat/test-class-PKNCAdata.R | 2 +- tests/testthat/test-unit-support.R | 32 ++++++++----------- 4 files changed, 33 insertions(+), 27 deletions(-) rename man/{pknca_units_table_auto.Rd => pknca_units_table_from_pknca.Rd} (82%) diff --git a/R/unit-support.R b/R/unit-support.R index 074c1d4d..713bc797 100644 --- a/R/unit-support.R +++ b/R/unit-support.R @@ -451,6 +451,8 @@ pknca_unit_conversion <- function(result, units, allow_partial_missing_units = F #' 2. Joins the concentration and dose data based on their grouping columns. #' 3. Generates a PKNCA units table for each group, including conversion factors and custom units. #' 4. Returns a unique table with relevant columns for PKNCA analysis. +#' Note: NA values in the unit columns are allowed, but at least one unit must be present for each concentration group. +#' Units should be uniform across concentration groups, and mismatches will raise an error. #' #' @examples #' # Assuming `o_conc` and `o_dose` are valid PKNCA objects: @@ -512,6 +514,11 @@ pknca_units_table_from_pknca <- function(o_conc, o_dose = NULL) { ) %>% # Prevent any issue with NAs in the group(s) or unit columns mutate(across(everything(), ~ as.character(.))) %>% + # Ignore NAs in the unit columns within groups + # TODO: (? Gerardo): Shouldn't we disallow missing units? test "PKNCAdata units (#336)" + group_by(!!!syms(group_conc_cols)) %>% + tidyr::fill(!!!syms(all_unit_cols), .direction = "downup") %>% + ungroup() %>% unique() # Check that at least for each concentration group units are uniform @@ -521,12 +528,17 @@ pknca_units_table_from_pknca <- function(o_conc, o_dose = NULL) { select(-n) if (nrow(mismatching_units_groups) > 0) { stop( - "Units should be uniform at least across concentration groups.", + "Units should be uniform at least across concentration groups. ", "Review the units for the next group(s):\n", paste(utils::capture.output(print(mismatching_units_groups)), collapse = "\n") ) } + # Check that at least one unit column is not NA + # TODO (? Gerardo): Shouldn't pk.nca be able to deal with empty pknca_units_table() and just warn? + units.are.all.na <- all(is.na(groups_units_tbl[,all_unit_cols])) + if (units.are.all.na) return(NULL) + # Generate the PKNCA units table groups_units_tbl %>% # Pick only the group columns that are relevant in stratifying the units @@ -550,11 +562,7 @@ pknca_units_table_from_pknca <- function(o_conc, o_dose = NULL) { ) %>% # Combine all PKNCA units tables into one unnest(cols = c(pknca_units_tbl)) %>% - # Order the columns to have them in a clean display - select( - any_of(c(group_conc_cols, group_dose_cols)), - any_of(c("PPTESTCD", "PPORRESU", "PPSTRESU", "conversion_factor")) - ) %>% + select(-any_of(all_unit_cols)) %>% as.data.frame() } diff --git a/man/pknca_units_table_auto.Rd b/man/pknca_units_table_from_pknca.Rd similarity index 82% rename from man/pknca_units_table_auto.Rd rename to man/pknca_units_table_from_pknca.Rd index 7d44e4fe..16c2d4a0 100644 --- a/man/pknca_units_table_auto.Rd +++ b/man/pknca_units_table_from_pknca.Rd @@ -2,14 +2,14 @@ % Please edit documentation in R/unit-support.R \name{pknca_units_table_from_pknca} \alias{pknca_units_table_from_pknca} -\title{Build Units Table for PKNCA} +\title{Build Units Table from PKNCA object(s)} \usage{ pknca_units_table_from_pknca(o_conc, o_dose = NULL) } \arguments{ \item{o_conc}{A PKNCA concentration object (PKNCAconc).} -\item{o_dose}{A PKNCA dose object (PKNCAdose).} +\item{o_dose}{A PKNCA dose object (PKNCAdose). Optional, if not provided dose units are considered missing.} } \value{ A data frame containing the PKNCA formatted units table. @@ -25,6 +25,8 @@ The function performs the following steps: \item Joins the concentration and dose data based on their grouping columns. \item Generates a PKNCA units table for each group, including conversion factors and custom units. \item Returns a unique table with relevant columns for PKNCA analysis. +Note: NA values in the unit columns are allowed, but at least one unit must be present for each concentration group. +Units should be uniform across concentration groups, and mismatches will raise an error. } } \examples{ diff --git a/tests/testthat/test-class-PKNCAdata.R b/tests/testthat/test-class-PKNCAdata.R index a401b373..2bcb03be 100644 --- a/tests/testthat/test-class-PKNCAdata.R +++ b/tests/testthat/test-class-PKNCAdata.R @@ -395,7 +395,7 @@ test_that("PKNCAdata units (#336)", { o_dose <- PKNCAdose(data = d_dose, dose~time, doseu = "doseu_x") expect_error( PKNCAdata(o_conc, o_dose), - regexp = "Only one unit may be provided at a time: A, C" + regexp = "Units should be uniform at least across concentration groups" ) }) diff --git a/tests/testthat/test-unit-support.R b/tests/testthat/test-unit-support.R index 4949918d..49ac1fad 100644 --- a/tests/testthat/test-unit-support.R +++ b/tests/testthat/test-unit-support.R @@ -377,8 +377,8 @@ describe("PKNCA_build_units_table", { data.frame( specimen = c("blood", "urine", "blood", "urine"), analyte = rep(c("A", "B"), each = 2), - PPTESTCD = "cmax", - PPORRESU = c("ng/mL", "pg/mL", "ug/mL", "pg/mL") + PPORRESU = c("ng/mL", "pg/mL", "ug/mL", "pg/mL"), + PPTESTCD = "cmax" ), ignore_attr = TRUE ) }) @@ -389,12 +389,12 @@ describe("PKNCA_build_units_table", { o_dose <- PKNCAdose(d_dose, dose ~ time | treatment + subject, doseu = "doseu_col") units_table <- expect_no_error(pknca_units_table_from_pknca(o_conc, o_dose)) - expect_equal( + expect_equal( units_table[units_table$PPTESTCD == "totdose",], data.frame( treatment = c("drug1", "drug2"), - PPTESTCD = "totdose", - PPORRESU = c("mg", "ug") + PPORRESU = c("mg", "ug"), + PPTESTCD = "totdose" ), ignore_attr = TRUE ) }) @@ -412,27 +412,23 @@ describe("PKNCA_build_units_table", { expect_equal( units_table[units_table$PPTESTCD == "cmax.dn",], data.frame( - PPTESTCD = c("cmax.dn"), - PPORRESU = c("(ng/mL)/mg") + PPORRESU = c("(ng/mL)/mg"), + PPTESTCD = c("cmax.dn") ), ignore_attr = TRUE ) }) - it("creates a NA units table when units are not defined at all in the PKNCA objects", { + it("returns NULL when units are not defined at all in the PKNCA objects", { o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte) o_dose <- PKNCAdose(d_dose, dose ~ time | treatment + subject) units_table <- expect_no_error(pknca_units_table_from_pknca(o_conc, o_dose)) - - expect_equal( - units_table[units_table$PPTESTCD %in% c("cmax", "totdose"),], - data.frame( - PPTESTCD = c("cmax", "totdose"), - PPORRESU = c(NA_character_, NA_character_) - ), ignore_attr = TRUE - ) + + expect_true(is.null(units_table)) }) it("does not strictly need o_dose (PKNCAdose object) to be provided", { + d_conc$concu_col <- ifelse(d_conc$analyte == "A", "ng/mL", "ug/mL") + d_conc$concu_col <- ifelse(d_conc$specimen == "blood", d_conc$concu_col, "pg/mL") o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte, concu = "concu_col") units_table <- expect_no_error(pknca_units_table_from_pknca(o_conc)) @@ -441,8 +437,8 @@ describe("PKNCA_build_units_table", { data.frame( specimen = c("blood", "urine", "blood", "urine"), analyte = rep(c("A", "B"), each = 2), - PPTESTCD = "cmax", - PPORRESU = c("ng/mL", "pg/mL", "ug/mL", "pg/mL") + PPORRESU = c("ng/mL", "pg/mL", "ug/mL", "pg/mL"), + PPTESTCD = "cmax" ), ignore_attr = TRUE ) }) From c4c6c69672145cf000698d1fa9f3d57b9c16f115 Mon Sep 17 00:00:00 2001 From: Gero1999 Date: Sun, 8 Jun 2025 13:18:40 +0200 Subject: [PATCH 08/18] docs: roxygenise indicating additional dplyr funs --- NAMESPACE | 1 + R/unit-support.R | 4 ++-- 2 files changed, 3 insertions(+), 2 deletions(-) diff --git a/NAMESPACE b/NAMESPACE index b5178231..9c44443e 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -256,5 +256,6 @@ importFrom(rlang,sym) importFrom(rlang,syms) importFrom(stats,formula) importFrom(stats,model.frame) +importFrom(tidyr,fill) importFrom(tidyr,unnest) importFrom(utils,capture.output) diff --git a/R/unit-support.R b/R/unit-support.R index 713bc797..8cdbb3dc 100644 --- a/R/unit-support.R +++ b/R/unit-support.R @@ -479,8 +479,8 @@ pknca_unit_conversion <- function(result, units, allow_partial_missing_units = F #' o_dose <- PKNCAdose(d_dose, dose ~ time | subj, doseu = "doseu") #' units_table <- PKNCA_build_units_table(o_conc, o_dose) #' -#' @importFrom dplyr select mutate rowwise any_of across everything %>% add_count inner_join group_vars -#' @importFrom tidyr unnest +#' @importFrom dplyr select mutate rowwise any_of across everything %>% add_count inner_join group_vars group_by ungroup left_join +#' @importFrom tidyr unnest fill #' @importFrom rlang sym syms #' @importFrom utils capture.output #' @export From 64285e2ce448f0ed0486673da450cf05cd6c5524 Mon Sep 17 00:00:00 2001 From: Gero1999 Date: Sun, 15 Jun 2025 13:58:57 +0200 Subject: [PATCH 09/18] fix: error for NA o_dose list & attr in units Xu_pref --- R/unit-support.R | 22 +++++++++++----------- 1 file changed, 11 insertions(+), 11 deletions(-) diff --git a/R/unit-support.R b/R/unit-support.R index 8cdbb3dc..2a41ee24 100644 --- a/R/unit-support.R +++ b/R/unit-support.R @@ -477,18 +477,18 @@ pknca_unit_conversion <- function(result, units, allow_partial_missing_units = F #' ) #' o_conc <- PKNCAconc(d_conc, conc ~ time | subj / analyte, concu = "concu") #' o_dose <- PKNCAdose(d_dose, dose ~ time | subj, doseu = "doseu") -#' units_table <- PKNCA_build_units_table(o_conc, o_dose) +#' units_table <- pknca_units_table_from_pknca(o_conc, o_dose) #' -#' @importFrom dplyr select mutate rowwise any_of across everything %>% add_count inner_join group_vars group_by ungroup left_join -#' @importFrom tidyr unnest fill +#' @importFrom dplyr select mutate rowwise any_of across everything %>% add_count inner_join group_vars +#' @importFrom tidyr unnest #' @importFrom rlang sym syms #' @importFrom utils capture.output #' @export pknca_units_table_from_pknca <- function(o_conc, o_dose = NULL) { # PKNCAdose is an optional argument with dose units, if not provided it will be ignored - if (is.null(o_dose) || is.na(o_dose)) o_dose <- o_conc - + if (is.null(o_dose) || all(is.na(o_dose))) o_dose <- o_conc + # If needed, ensure that the PKNCA objects have the required unit columns o_conc <- ensure_column_unit_exists(o_conc, c("concu", "timeu", "amountu")) o_dose <- ensure_column_unit_exists(o_dose, c("doseu")) @@ -553,10 +553,10 @@ pknca_units_table_from_pknca <- function(o_conc, o_dose = NULL) { doseu = !!sym(doseu_col), amountu = !!sym(amountu_col), timeu = !!sym(timeu_col), - concu_pref = o_conc$units$concu_pref, - doseu_pref = o_dose$units$doseu_pref, - amountu_pref = o_conc$units$amountu_pref, - timeu_pref = o_conc$units$timeu_pref + concu_pref = o_conc$units$concu_pref[1], + doseu_pref = o_dose$units$doseu_pref[1], + amountu_pref = o_conc$units$amountu_pref[1], + timeu_pref = o_conc$units$timeu_pref[1] ) ) ) %>% @@ -614,8 +614,8 @@ select_minimal_grouping_cols <- function(df, strata_cols) { # Obtain the comb_vals values of the target column(s) strata_vals <- df %>% mutate(strata_cols_comb = paste(!!!syms(strata_cols), sep = "_")) %>% - pull(strata_cols_comb) - + .[["strata_cols_comb"]] + # If the target column(s) only has one level, there are no relevant columns if (length(unique(strata_vals)) == 1) { return(df[strata_cols]) From 3b0aa18c5081fd121afdcf01e8378ef76bdcfbce Mon Sep 17 00:00:00 2001 From: Gero1999 Date: Sun, 15 Jun 2025 14:02:51 +0200 Subject: [PATCH 10/18] docs: fix example and update namespace --- NAMESPACE | 1 - man/pknca_units_table_from_pknca.Rd | 2 +- 2 files changed, 1 insertion(+), 2 deletions(-) diff --git a/NAMESPACE b/NAMESPACE index 9c44443e..b5178231 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -256,6 +256,5 @@ importFrom(rlang,sym) importFrom(rlang,syms) importFrom(stats,formula) importFrom(stats,model.frame) -importFrom(tidyr,fill) importFrom(tidyr,unnest) importFrom(utils,capture.output) diff --git a/man/pknca_units_table_from_pknca.Rd b/man/pknca_units_table_from_pknca.Rd index 16c2d4a0..43117603 100644 --- a/man/pknca_units_table_from_pknca.Rd +++ b/man/pknca_units_table_from_pknca.Rd @@ -52,6 +52,6 @@ d_dose <- data.frame( ) o_conc <- PKNCAconc(d_conc, conc ~ time | subj / analyte, concu = "concu") o_dose <- PKNCAdose(d_dose, dose ~ time | subj, doseu = "doseu") -units_table <- PKNCA_build_units_table(o_conc, o_dose) +units_table <- pknca_units_table_from_pknca(o_conc, o_dose) } From 02bff3dbf7a8457d36114739f4961330a342ea42 Mon Sep 17 00:00:00 2001 From: Gero1999 Date: Sat, 13 Sep 2025 23:17:16 +0200 Subject: [PATCH 11/18] feat: make pknca_units_table a method for PKNCAdata --- NAMESPACE | 14 +- R/class-PKNCAdata.R | 2 +- R/unit-support.R | 231 ++++++++++++---------------- man/pknca_units_table.Rd | 13 +- man/pknca_units_table_from_pknca.Rd | 57 ------- 5 files changed, 112 insertions(+), 205 deletions(-) delete mode 100644 man/pknca_units_table_from_pknca.Rd diff --git a/NAMESPACE b/NAMESPACE index b5178231..475e5081 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -63,6 +63,8 @@ S3method(model.frame,PKNCAdose) S3method(mutate,PKNCAconc) S3method(mutate,PKNCAdose) S3method(mutate,PKNCAresults) +S3method(pknca_units_table,PKNCAdata) +S3method(pknca_units_table,default) S3method(print,PKNCAconc) S3method(print,PKNCAdata) S3method(print,PKNCAdose) @@ -219,7 +221,6 @@ export(pk.tss) export(pk.tss.monoexponential) export(pk.tss.stepwise.linear) export(pknca_units_table) -export(pknca_units_table_from_pknca) export(right_join) export(roundString) export(roundingSummarize) @@ -234,27 +235,16 @@ export(time_calc) export(ungroup) export(var_sparse_auc) importFrom(dplyr,"%>%") -importFrom(dplyr,across) -importFrom(dplyr,add_count) -importFrom(dplyr,any_of) -importFrom(dplyr,everything) importFrom(dplyr,filter) importFrom(dplyr,full_join) importFrom(dplyr,group_by) -importFrom(dplyr,group_vars) importFrom(dplyr,inner_join) importFrom(dplyr,left_join) importFrom(dplyr,mutate) importFrom(dplyr,right_join) -importFrom(dplyr,rowwise) -importFrom(dplyr,select) importFrom(dplyr,ungroup) importFrom(lifecycle,deprecated) importFrom(nlme,getGroups) importFrom(rlang,.data) -importFrom(rlang,sym) -importFrom(rlang,syms) importFrom(stats,formula) importFrom(stats,model.frame) -importFrom(tidyr,unnest) -importFrom(utils,capture.output) diff --git a/R/class-PKNCAdata.R b/R/class-PKNCAdata.R index 132d077e..68d14095 100644 --- a/R/class-PKNCAdata.R +++ b/R/class-PKNCAdata.R @@ -171,7 +171,7 @@ PKNCAdata.default <- function(data.conc, data.dose, ..., # Insert the unit conversion table if (missing(units)) { # Use the new automatic units table builder - ret$units <- pknca_units_table_from_pknca(ret$conc, ret$dose) + ret$units <- pknca_units_table(ret) } else { stopifnot("`units` must be a data.frame"=is.data.frame(units)) stopifnot( diff --git a/R/unit-support.R b/R/unit-support.R index 2a41ee24..d590ce72 100644 --- a/R/unit-support.R +++ b/R/unit-support.R @@ -50,10 +50,21 @@ #' concu = "ng/mL", doseu = "mg/kg", timeu = "hr", amountu = "mg", #' timeu_pref = "day" #' ) + +#' S3 generic for pknca_units_table +#' +#' @export +pknca_units_table <- function(concu, ...) { + UseMethod("pknca_units_table") +} + +##' Default method for pknca_units_table +#' +#' @rdname pknca_units_table #' @export -pknca_units_table <- function(concu, doseu, amountu, timeu, +pknca_units_table.default <- function(concu, doseu, amountu, timeu, concu_pref = NULL, doseu_pref = NULL, amountu_pref = NULL, timeu_pref = NULL, - conversions = data.frame()) { + conversions = data.frame(), ...) { checkmate::assert_data_frame(conversions) if (nrow(conversions) > 0) { checkmate::assert_names( @@ -158,6 +169,87 @@ pknca_units_table <- function(concu, doseu, amountu, timeu, ret } +##' Method for PKNCAdata objects +#' +#' @rdname pknca_units_table +#' @importFrom dplyr across any_of bind_rows case_when filter group_by left_join mutate n select ungroup +#' @importFrom tidyr fill unnest +#' @importFrom rlang syms +#' @export +pknca_units_table.PKNCAdata <- function(concu, ..., conversions = data.frame()) { + # concu is the PKNCAdata object + o_conc <- concu$conc + o_dose <- concu$dose + # If needed, ensure that the PKNCA objects have the required unit columns + o_conc <- ensure_column_unit_exists(o_conc, c("concu", "timeu", "amountu")) + o_dose <- ensure_column_unit_exists(o_dose, c("doseu")) + + # Extract relevant columns from o_conc and o_dose + group_dose_cols <- unname(unlist(o_dose$columns$groups)) + group_conc_cols <- unname(unlist(o_conc$columns$groups)) + concu_col <- o_conc$columns$concu + amountu_col <- o_conc$columns$amountu + timeu_col <- o_conc$columns$timeu + doseu_col <- o_dose$columns$doseu + all_unit_cols <- c(concu_col, amountu_col, timeu_col, doseu_col) + + # Join dose units with concentration group columns and units + groups_units_tbl <- dplyr::left_join( + o_conc$data %>% + dplyr::select(dplyr::any_of(c(group_conc_cols, concu_col, amountu_col, timeu_col))) %>% + unique(), + o_dose$data %>% + dplyr::select(dplyr::any_of(c(group_dose_cols, doseu_col))) %>% + unique(), + by = intersect(group_conc_cols, group_dose_cols) + ) %>% + dplyr::mutate(dplyr::across(dplyr::everything(), ~ as.character(.))) %>% + dplyr::group_by(!!!rlang::syms(group_conc_cols)) %>% + tidyr::fill(!!!rlang::syms(all_unit_cols), .direction = "downup") %>% + dplyr::ungroup() %>% + unique() + + # Check that at least for each concentration group units are uniform + mismatching_units_groups <- groups_units_tbl %>% + dplyr::add_count(!!!rlang::syms(group_conc_cols), name = "n") %>% + dplyr::filter(n > 1) %>% + dplyr::select(-n) + if (nrow(mismatching_units_groups) > 0) { + stop( + "Units should be uniform at least across concentration groups. ", + "Review the units for the next group(s):\n", + paste(utils::capture.output(print(mismatching_units_groups)), collapse = "\n") + ) + } + + # Check that at least one unit column is not NA + units.are.all.na <- all(is.na(groups_units_tbl[,all_unit_cols])) + if (units.are.all.na) return(NULL) + + groups_units_tbl %>% + select_minimal_grouping_cols(all_unit_cols) %>% + unique() %>% + dplyr::rowwise() %>% + dplyr::mutate( + pknca_units_tbl = list( + pknca_units_table( + concu = !!rlang::sym(concu_col), + doseu = !!rlang::sym(doseu_col), + amountu = !!rlang::sym(amountu_col), + timeu = !!rlang::sym(timeu_col), + concu_pref = o_conc$units$concu_pref[1], + doseu_pref = o_dose$units$doseu_pref[1], + amountu_pref = o_conc$units$amountu_pref[1], + timeu_pref = o_conc$units$timeu_pref[1], + conversions = conversions + ) + ) + ) %>% + tidyr::unnest(cols = c(pknca_units_tbl)) %>% + dplyr::select(-dplyr::any_of(all_unit_cols)) %>% + as.data.frame() +} + pknca_units_table_unitless <- function() { rbind( data.frame( @@ -435,136 +527,6 @@ pknca_unit_conversion <- function(result, units, allow_partial_missing_units = F ret } -#' Build Units Table from PKNCA object(s) -#' -#' This function generates a PKNCA units table including the potential unit segregating columns -#' among the dose and/or concentration groups. -#' -#' @param o_conc A PKNCA concentration object (PKNCAconc). -#' @param o_dose A PKNCA dose object (PKNCAdose). Optional, if not provided dose units are considered missing. -#' -#' @returns A data frame containing the PKNCA formatted units table. -#' -#' @details -#' The function performs the following steps: -#' 1. Ensures the unit columns (e.g., `concu`, `timeu`, `doseu`, `amountu`) exist in the inputs. -#' 2. Joins the concentration and dose data based on their grouping columns. -#' 3. Generates a PKNCA units table for each group, including conversion factors and custom units. -#' 4. Returns a unique table with relevant columns for PKNCA analysis. -#' Note: NA values in the unit columns are allowed, but at least one unit must be present for each concentration group. -#' Units should be uniform across concentration groups, and mismatches will raise an error. -#' -#' @examples -#' # Assuming `o_conc` and `o_dose` are valid PKNCA objects: -#' # 1) Sharing group variables in their formulas -#' # 2) Time units are the same within dose and concentration groups -#' # 3) Units are the same for subjects within the same concentration group -#' -#' d_conc <- data.frame( -#' subj = 1, -#' analyte = rep(c("A", "B"), each = 2), -#' concu = rep(c("ng/mL", "ug/mL"), each = 2), -#' conc = c(0, 2, 0, 5), -#' time = rep(0:1, 2), -#' timeu = "h" -#' ) -#' d_dose <- data.frame( -#' subj = 1, -#' dose = 100, -#' doseu = "mg", -#' time = 0, -#' timeu = "h" -#' ) -#' o_conc <- PKNCAconc(d_conc, conc ~ time | subj / analyte, concu = "concu") -#' o_dose <- PKNCAdose(d_dose, dose ~ time | subj, doseu = "doseu") -#' units_table <- pknca_units_table_from_pknca(o_conc, o_dose) -#' -#' @importFrom dplyr select mutate rowwise any_of across everything %>% add_count inner_join group_vars -#' @importFrom tidyr unnest -#' @importFrom rlang sym syms -#' @importFrom utils capture.output -#' @export -pknca_units_table_from_pknca <- function(o_conc, o_dose = NULL) { - - # PKNCAdose is an optional argument with dose units, if not provided it will be ignored - if (is.null(o_dose) || all(is.na(o_dose))) o_dose <- o_conc - - # If needed, ensure that the PKNCA objects have the required unit columns - o_conc <- ensure_column_unit_exists(o_conc, c("concu", "timeu", "amountu")) - o_dose <- ensure_column_unit_exists(o_dose, c("doseu")) - - # Extract relevant columns from o_conc and o_dose - group_dose_cols <- group_vars(o_dose) - group_conc_cols <- group_vars(o_conc) - concu_col <- o_conc$columns$concu - amountu_col <- o_conc$columns$amountu - timeu_col <- o_conc$columns$timeu - doseu_col <- o_dose$columns$doseu - all_unit_cols <- c(concu_col, amountu_col, timeu_col, doseu_col) - - # Join dose units with concentration group columns and units - groups_units_tbl <- left_join( - o_conc$data %>% - select(any_of(c(group_conc_cols, concu_col, amountu_col, timeu_col))) %>% - unique(), - o_dose$data %>% - select(any_of(c(group_dose_cols, doseu_col))) %>% - unique(), - by = intersect(group_conc_cols, group_dose_cols) - ) %>% - # Prevent any issue with NAs in the group(s) or unit columns - mutate(across(everything(), ~ as.character(.))) %>% - # Ignore NAs in the unit columns within groups - # TODO: (? Gerardo): Shouldn't we disallow missing units? test "PKNCAdata units (#336)" - group_by(!!!syms(group_conc_cols)) %>% - tidyr::fill(!!!syms(all_unit_cols), .direction = "downup") %>% - ungroup() %>% - unique() - - # Check that at least for each concentration group units are uniform - mismatching_units_groups <- groups_units_tbl %>% - add_count(!!!syms(group_conc_cols), name = "n") %>% - filter(n > 1) %>% - select(-n) - if (nrow(mismatching_units_groups) > 0) { - stop( - "Units should be uniform at least across concentration groups. ", - "Review the units for the next group(s):\n", - paste(utils::capture.output(print(mismatching_units_groups)), collapse = "\n") - ) - } - - # Check that at least one unit column is not NA - # TODO (? Gerardo): Shouldn't pk.nca be able to deal with empty pknca_units_table() and just warn? - units.are.all.na <- all(is.na(groups_units_tbl[,all_unit_cols])) - if (units.are.all.na) return(NULL) - - # Generate the PKNCA units table - groups_units_tbl %>% - # Pick only the group columns that are relevant in stratifying the units - select_minimal_grouping_cols(all_unit_cols) %>% - unique() %>% - # Create a PKNCA units table for each group - rowwise() %>% - mutate( - pknca_units_tbl = list( - pknca_units_table( - concu = !!sym(concu_col), - doseu = !!sym(doseu_col), - amountu = !!sym(amountu_col), - timeu = !!sym(timeu_col), - concu_pref = o_conc$units$concu_pref[1], - doseu_pref = o_dose$units$doseu_pref[1], - amountu_pref = o_conc$units$amountu_pref[1], - timeu_pref = o_conc$units$timeu_pref[1] - ) - ) - ) %>% - # Combine all PKNCA units tables into one - unnest(cols = c(pknca_units_tbl)) %>% - select(-any_of(all_unit_cols)) %>% - as.data.frame() -} #' Ensure Unit Columns Exist in PKNCA Object #' @@ -606,6 +568,9 @@ ensure_column_unit_exists <- function(pknca_obj, unit_name) { #' @param df A data frame. #' @param strata_cols Column names in df whose unique combination defines the strata. #' @returns A data frame containing the strata columns and their minimal set of grouping columns. +#' @importFrom dplyr mutate select any_of +#' @importFrom rlang syms +#' @importFrom stats combn #' @keywords Internal select_minimal_grouping_cols <- function(df, strata_cols) { # If there is no strata_cols specified, simply return the original df @@ -613,7 +578,7 @@ select_minimal_grouping_cols <- function(df, strata_cols) { # Obtain the comb_vals values of the target column(s) strata_vals <- df %>% - mutate(strata_cols_comb = paste(!!!syms(strata_cols), sep = "_")) %>% + mutate(strata_cols_comb = paste(!!!rlang::syms(strata_cols), sep = "_")) %>% .[["strata_cols_comb"]] # If the target column(s) only has one level, there are no relevant columns diff --git a/man/pknca_units_table.Rd b/man/pknca_units_table.Rd index 73339027..e59e235a 100644 --- a/man/pknca_units_table.Rd +++ b/man/pknca_units_table.Rd @@ -2,9 +2,13 @@ % Please edit documentation in R/unit-support.R \name{pknca_units_table} \alias{pknca_units_table} +\alias{pknca_units_table.default} +\alias{pknca_units_table.PKNCAdata} \title{Create a unit assignment and conversion table} \usage{ -pknca_units_table( +pknca_units_table(concu, ...) + +\method{pknca_units_table}{default}( concu, doseu, amountu, @@ -13,8 +17,11 @@ pknca_units_table( doseu_pref = NULL, amountu_pref = NULL, timeu_pref = NULL, - conversions = data.frame() + conversions = data.frame(), + ... ) + +\method{pknca_units_table}{PKNCAdata}(concu, ..., conversions = data.frame()) } \arguments{ \item{concu, doseu, amountu, timeu}{Units for concentration, dose, amount, and @@ -72,6 +79,8 @@ pknca_units_table( concu = "ng/mL", doseu = "mg/kg", timeu = "hr", amountu = "mg", timeu_pref = "day" ) +S3 generic for pknca_units_table + } \seealso{ The \code{units} argument for \code{\link[=PKNCAdata]{PKNCAdata()}} diff --git a/man/pknca_units_table_from_pknca.Rd b/man/pknca_units_table_from_pknca.Rd deleted file mode 100644 index 43117603..00000000 --- a/man/pknca_units_table_from_pknca.Rd +++ /dev/null @@ -1,57 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/unit-support.R -\name{pknca_units_table_from_pknca} -\alias{pknca_units_table_from_pknca} -\title{Build Units Table from PKNCA object(s)} -\usage{ -pknca_units_table_from_pknca(o_conc, o_dose = NULL) -} -\arguments{ -\item{o_conc}{A PKNCA concentration object (PKNCAconc).} - -\item{o_dose}{A PKNCA dose object (PKNCAdose). Optional, if not provided dose units are considered missing.} -} -\value{ -A data frame containing the PKNCA formatted units table. -} -\description{ -This function generates a PKNCA units table including the potential unit segregating columns -among the dose and/or concentration groups. -} -\details{ -The function performs the following steps: -\enumerate{ -\item Ensures the unit columns (e.g., \code{concu}, \code{timeu}, \code{doseu}, \code{amountu}) exist in the inputs. -\item Joins the concentration and dose data based on their grouping columns. -\item Generates a PKNCA units table for each group, including conversion factors and custom units. -\item Returns a unique table with relevant columns for PKNCA analysis. -Note: NA values in the unit columns are allowed, but at least one unit must be present for each concentration group. -Units should be uniform across concentration groups, and mismatches will raise an error. -} -} -\examples{ -# Assuming `o_conc` and `o_dose` are valid PKNCA objects: -# 1) Sharing group variables in their formulas -# 2) Time units are the same within dose and concentration groups -# 3) Units are the same for subjects within the same concentration group - -d_conc <- data.frame( - subj = 1, - analyte = rep(c("A", "B"), each = 2), - concu = rep(c("ng/mL", "ug/mL"), each = 2), - conc = c(0, 2, 0, 5), - time = rep(0:1, 2), - timeu = "h" -) -d_dose <- data.frame( - subj = 1, - dose = 100, - doseu = "mg", - time = 0, - timeu = "h" -) -o_conc <- PKNCAconc(d_conc, conc ~ time | subj / analyte, concu = "concu") -o_dose <- PKNCAdose(d_dose, dose ~ time | subj, doseu = "doseu") -units_table <- pknca_units_table_from_pknca(o_conc, o_dose) - -} From 1c71730a65245c41851f5a9e7c9ce8d225d3035d Mon Sep 17 00:00:00 2001 From: Gero1999 Date: Sat, 13 Sep 2025 23:18:39 +0200 Subject: [PATCH 12/18] test: adjust tests for PKNCAdata input --- tests/testthat/test-unit-support.R | 36 ++++++++++-------------------- 1 file changed, 12 insertions(+), 24 deletions(-) diff --git a/tests/testthat/test-unit-support.R b/tests/testthat/test-unit-support.R index 49ac1fad..e336b0c6 100644 --- a/tests/testthat/test-unit-support.R +++ b/tests/testthat/test-unit-support.R @@ -353,7 +353,8 @@ describe("PKNCA_build_units_table", { o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte, concu = "concu_col") o_dose <- PKNCAdose(d_dose, dose ~ time | treatment + subject) - units_table <- expect_no_error(pknca_units_table_from_pknca(o_conc, o_dose)) + o_data <- PKNCAdata(o_conc, o_dose) + units_table <- expect_no_error(pknca_units_table(o_data)) expect_equal( units_table[units_table$PPTESTCD == "cmax", c(strat_var, "PPORRESU")], @@ -370,7 +371,8 @@ describe("PKNCA_build_units_table", { d_conc$concu_col <- ifelse(d_conc$specimen == "blood", d_conc$concu_col, "pg/mL") o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte, concu = "concu_col") o_dose <- PKNCAdose(d_dose, dose ~ time | treatment + subject) - units_table <- expect_no_error(pknca_units_table_from_pknca(o_conc, o_dose)) + o_data <- PKNCAdata(o_conc, o_dose) + units_table <- expect_no_error(pknca_units_table(o_data)) expect_equal( units_table[units_table$PPTESTCD == "cmax",], @@ -387,7 +389,8 @@ describe("PKNCA_build_units_table", { d_dose$doseu_col <- ifelse(d_dose$treatment == d_dose$treatment[1], "mg", "ug") o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte) o_dose <- PKNCAdose(d_dose, dose ~ time | treatment + subject, doseu = "doseu_col") - units_table <- expect_no_error(pknca_units_table_from_pknca(o_conc, o_dose)) + o_data <- PKNCAdata(o_conc, o_dose) + units_table <- expect_no_error(pknca_units_table(o_data)) expect_equal( units_table[units_table$PPTESTCD == "totdose",], @@ -408,7 +411,8 @@ describe("PKNCA_build_units_table", { d_dose, dose ~ time | treatment + subject, doseu = "mg" ) - units_table <- expect_no_error(pknca_units_table_from_pknca(o_conc, o_dose)) + o_data <- PKNCAdata(o_conc, o_dose) + units_table <- expect_no_error(pknca_units_table(o_data)) expect_equal( units_table[units_table$PPTESTCD == "cmax.dn",], data.frame( @@ -421,26 +425,10 @@ describe("PKNCA_build_units_table", { it("returns NULL when units are not defined at all in the PKNCA objects", { o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte) o_dose <- PKNCAdose(d_dose, dose ~ time | treatment + subject) - units_table <- expect_no_error(pknca_units_table_from_pknca(o_conc, o_dose)) - - expect_true(is.null(units_table)) - }) + o_data <- PKNCAdata(o_conc, o_dose) + units_table <- expect_no_error(pknca_units_table(o_data)) - it("does not strictly need o_dose (PKNCAdose object) to be provided", { - d_conc$concu_col <- ifelse(d_conc$analyte == "A", "ng/mL", "ug/mL") - d_conc$concu_col <- ifelse(d_conc$specimen == "blood", d_conc$concu_col, "pg/mL") - o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte, - concu = "concu_col") - units_table <- expect_no_error(pknca_units_table_from_pknca(o_conc)) - expect_equal( - units_table[units_table$PPTESTCD == "cmax",], - data.frame( - specimen = c("blood", "urine", "blood", "urine"), - analyte = rep(c("A", "B"), each = 2), - PPORRESU = c("ng/mL", "pg/mL", "ug/mL", "pg/mL"), - PPTESTCD = "cmax" - ), ignore_attr = TRUE - ) + expect_true(is.null(units_table)) }) it("reports an error when units are inconsistent through all concentration groups", { @@ -449,7 +437,7 @@ describe("PKNCA_build_units_table", { o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte, concu = "concu_col") o_dose <- PKNCAdose(d_dose, dose ~ time | treatment + subject) expect_error( - pknca_units_table_from_pknca(o_conc, o_dose), + PKNCAdata(o_conc, o_dose), regexp = "Units should be uniform at least across concentration groups.*" ) }) From 04b393cad40a080a062be374bcdfdde1292c058d Mon Sep 17 00:00:00 2001 From: Gero1999 Date: Sat, 13 Sep 2025 23:35:51 +0200 Subject: [PATCH 13/18] test: refactor to follow PKNCA structure --- tests/testthat/test-unit-support.R | 179 ++++++++++++++--------------- 1 file changed, 84 insertions(+), 95 deletions(-) diff --git a/tests/testthat/test-unit-support.R b/tests/testthat/test-unit-support.R index e336b0c6..b79a66df 100644 --- a/tests/testthat/test-unit-support.R +++ b/tests/testthat/test-unit-support.R @@ -331,8 +331,8 @@ test_that("pknca_unit_conversion", { ) }) -# Tests for PKNA_build_units_table -describe("PKNCA_build_units_table", { +# Tests for pknca_units_table for PKNCAdata +test_that("pknca_units_table for PKNCAdata", { # Subset the data to only include USUBJID 8 (2 analytes, A & B) d_conc <- data.frame( @@ -346,104 +346,97 @@ describe("PKNCA_build_units_table", { ) d_dose <- unique(d_conc[d_conc$time %in% c(0, 5), c("dose", "time", "subject", "treatment")]) - it("creates a stratified units table when PKNCAconc has a unit-stratifying group column", { + # Creates a stratified units table when PKNCAconc has a unit-stratifying group column + for (strat_var in c("specimen", "analyte")) { + d_conc$concu_col <- ifelse(d_conc[[strat_var]] == d_conc[[strat_var]][1], "ng/mL", "ug/mL") - for (strat_var in c("specimen", "analyte")) { - d_conc$concu_col <- ifelse(d_conc[[strat_var]] == d_conc[[strat_var]][1], "ng/mL", "ug/mL") - - o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte, concu = "concu_col") - o_dose <- PKNCAdose(d_dose, dose ~ time | treatment + subject) - o_data <- PKNCAdata(o_conc, o_dose) - units_table <- expect_no_error(pknca_units_table(o_data)) - - expect_equal( - units_table[units_table$PPTESTCD == "cmax", c(strat_var, "PPORRESU")], - data.frame( - specimen = c(unique(d_conc[[strat_var]])[1], unique(d_conc[[strat_var]])[2]), - PPORRESU = c("ng/mL", "ug/mL") - ), ignore_attr = TRUE - ) - } - }) - - it("creates a stratified units table when PKNCAconc has two unit-stratifying group columns", { - d_conc$concu_col <- ifelse(d_conc$analyte == "A", "ng/mL", "ug/mL") - d_conc$concu_col <- ifelse(d_conc$specimen == "blood", d_conc$concu_col, "pg/mL") o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte, concu = "concu_col") o_dose <- PKNCAdose(d_dose, dose ~ time | treatment + subject) o_data <- PKNCAdata(o_conc, o_dose) units_table <- expect_no_error(pknca_units_table(o_data)) expect_equal( - units_table[units_table$PPTESTCD == "cmax",], + units_table[units_table$PPTESTCD == "cmax", c(strat_var, "PPORRESU")], data.frame( - specimen = c("blood", "urine", "blood", "urine"), - analyte = rep(c("A", "B"), each = 2), - PPORRESU = c("ng/mL", "pg/mL", "ug/mL", "pg/mL"), - PPTESTCD = "cmax" + specimen = c(unique(d_conc[[strat_var]])[1], unique(d_conc[[strat_var]])[2]), + PPORRESU = c("ng/mL", "ug/mL") ), ignore_attr = TRUE ) - }) + } - it("creates a stratified units table when PKNCAdose has a unit-stratifying column", { - d_dose$doseu_col <- ifelse(d_dose$treatment == d_dose$treatment[1], "mg", "ug") - o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte) - o_dose <- PKNCAdose(d_dose, dose ~ time | treatment + subject, doseu = "doseu_col") - o_data <- PKNCAdata(o_conc, o_dose) - units_table <- expect_no_error(pknca_units_table(o_data)) + # Creates a stratified units table when PKNCAconc has two unit-stratifying group columns + d_conc$concu_col <- ifelse(d_conc$analyte == "A", "ng/mL", "ug/mL") + d_conc$concu_col <- ifelse(d_conc$specimen == "blood", d_conc$concu_col, "pg/mL") + o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte, concu = "concu_col") + o_dose <- PKNCAdose(d_dose, dose ~ time | treatment + subject) + o_data <- PKNCAdata(o_conc, o_dose) + units_table <- expect_no_error(pknca_units_table(o_data)) - expect_equal( - units_table[units_table$PPTESTCD == "totdose",], - data.frame( - treatment = c("drug1", "drug2"), - PPORRESU = c("mg", "ug"), - PPTESTCD = "totdose" - ), ignore_attr = TRUE - ) - }) + expect_equal( + units_table[units_table$PPTESTCD == "cmax",], + data.frame( + specimen = c("blood", "urine", "blood", "urine"), + analyte = rep(c("A", "B"), each = 2), + PPORRESU = c("ng/mL", "pg/mL", "ug/mL", "pg/mL"), + PPTESTCD = "cmax" + ), ignore_attr = TRUE + ) - it("creates an uniform units table when units are not defined as columns in the PKNCA obj", { - o_conc <- PKNCAconc( - d_conc, conc ~ time | treatment + specimen + subject / analyte, - concu = "ng/mL", timeu = "h" - ) - o_dose <- PKNCAdose( - d_dose, dose ~ time | treatment + subject, - doseu = "mg" - ) - o_data <- PKNCAdata(o_conc, o_dose) - units_table <- expect_no_error(pknca_units_table(o_data)) - expect_equal( - units_table[units_table$PPTESTCD == "cmax.dn",], + # Creates a stratified units table when PKNCAdose has a unit-stratifying group column + d_dose$doseu_col <- ifelse(d_dose$treatment == d_dose$treatment[1], "mg", "ug") + o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte) + o_dose <- PKNCAdose(d_dose, dose ~ time | treatment + subject, doseu = "doseu_col") + o_data <- PKNCAdata(o_conc, o_dose) + units_table <- expect_no_error(pknca_units_table(o_data)) + + expect_equal( + units_table[units_table$PPTESTCD == "totdose",], data.frame( - PPORRESU = c("(ng/mL)/mg"), - PPTESTCD = c("cmax.dn") + treatment = c("drug1", "drug2"), + PPORRESU = c("mg", "ug"), + PPTESTCD = "totdose" ), ignore_attr = TRUE ) - }) - it("returns NULL when units are not defined at all in the PKNCA objects", { - o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte) - o_dose <- PKNCAdose(d_dose, dose ~ time | treatment + subject) - o_data <- PKNCAdata(o_conc, o_dose) - units_table <- expect_no_error(pknca_units_table(o_data)) + # Creates an uniform units table when units are not defined as columns + o_conc <- PKNCAconc( + d_conc, conc ~ time | treatment + specimen + subject / analyte, + concu = "ng/mL", timeu = "h" + ) + o_dose <- PKNCAdose( + d_dose, dose ~ time | treatment + subject, + doseu = "mg" + ) + o_data <- PKNCAdata(o_conc, o_dose) + units_table <- expect_no_error(pknca_units_table(o_data)) + expect_equal( + units_table[units_table$PPTESTCD == "cmax.dn",], + data.frame( + PPORRESU = c("(ng/mL)/mg"), + PPTESTCD = c("cmax.dn") + ), ignore_attr = TRUE + ) - expect_true(is.null(units_table)) - }) + # Returns NULL when no units are defined anywhere + o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte) + o_dose <- PKNCAdose(d_dose, dose ~ time | treatment + subject) + o_data <- PKNCAdata(o_conc, o_dose) + units_table <- expect_no_error(pknca_units_table(o_data)) - it("reports an error when units are inconsistent through all concentration groups", { - d_conc$concu_col <- "ng/mL" - d_conc$concu_col[1] <- "pg/L" # Introduce inconsistency - o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte, concu = "concu_col") - o_dose <- PKNCAdose(d_dose, dose ~ time | treatment + subject) - expect_error( - PKNCAdata(o_conc, o_dose), - regexp = "Units should be uniform at least across concentration groups.*" - ) - }) + expect_true(is.null(units_table)) + + # Errors when units are not uniform within a concentration group + d_conc$concu_col <- "ng/mL" + d_conc$concu_col[1] <- "pg/L" # Introduce inconsistency + o_conc <- PKNCAconc(d_conc, conc ~ time | treatment + specimen + subject / analyte, concu = "concu_col") + o_dose <- PKNCAdose(d_dose, dose ~ time | treatment + subject) + expect_error( + PKNCAdata(o_conc, o_dose), + regexp = "Units should be uniform at least across concentration groups.*" + ) }) -describe("select_level_grouping_cols", { +test_that("select_level_grouping_cols", { # Make a dataset where a variable `d` depends on `a` & `b` data <- data.frame( a = rep(letters[c(1, 2, 3)], each = 4), @@ -452,20 +445,16 @@ describe("select_level_grouping_cols", { ) data$d <- paste0(data$a, data$b) - it("returns the minimal grouping_columns (a, b) for one target column", { - result <- select_minimal_grouping_cols(data, "d") - expect_equal(result, data[c("a", "b", "d")]) - }) - - # Note: this case will never happen in the App or PKNCA_build_units_table - it("returns the original data if target_columns is NULL", { - result <- select_minimal_grouping_cols(data, NULL) - expect_equal(result, data) - }) - - it("returns just the strata columns if no stratification groups are found", { - data[, "a"] <- 10 - result <- select_minimal_grouping_cols(data, "d") - expect_equal(result, data["d"]) - }) + # Returns the minimal grouping_columns (a, b) for one target columns + result <- select_minimal_grouping_cols(data, "d") + expect_equal(result, data[c("a", "b", "d")]) + + # Returns the original data if all grouping columns are needed + result <- select_minimal_grouping_cols(data, c("c", "d")) + expect_equal(result, data) + + # Returns just the strata columns if no stratification groups are found + data[, "a"] <- 10 + result <- select_minimal_grouping_cols(data, "d") + expect_equal(result, data["d"]) }) From 957091b8f15709165cdcc402ce7a0799c446171e Mon Sep 17 00:00:00 2001 From: Gero1999 Date: Sat, 13 Sep 2025 23:45:27 +0200 Subject: [PATCH 14/18] fix: typpo namespaces and docs --- NAMESPACE | 10 ++++++++++ R/unit-support.R | 3 ++- man/pknca_units_table.Rd | 2 ++ 3 files changed, 14 insertions(+), 1 deletion(-) diff --git a/NAMESPACE b/NAMESPACE index 475e5081..fd815981 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -235,16 +235,26 @@ export(time_calc) export(ungroup) export(var_sparse_auc) importFrom(dplyr,"%>%") +importFrom(dplyr,across) +importFrom(dplyr,any_of) +importFrom(dplyr,bind_rows) +importFrom(dplyr,case_when) importFrom(dplyr,filter) importFrom(dplyr,full_join) importFrom(dplyr,group_by) importFrom(dplyr,inner_join) importFrom(dplyr,left_join) importFrom(dplyr,mutate) +importFrom(dplyr,n) importFrom(dplyr,right_join) +importFrom(dplyr,select) importFrom(dplyr,ungroup) importFrom(lifecycle,deprecated) importFrom(nlme,getGroups) importFrom(rlang,.data) +importFrom(rlang,syms) importFrom(stats,formula) importFrom(stats,model.frame) +importFrom(tidyr,fill) +importFrom(tidyr,unnest) +importFrom(utils,combn) diff --git a/R/unit-support.R b/R/unit-support.R index d590ce72..f1768bd4 100644 --- a/R/unit-support.R +++ b/R/unit-support.R @@ -14,6 +14,7 @@ #' by to get a standardized value. This argument overrides any preferred unit #' conversions from `concu_pref`, `doseu_pref`, `amountu_pref`, or #' `timeu_pref`. +#' @param ... Additional arguments (not used) #' @returns A unit conversion table with columns for "PPTESTCD" and "PPORRESU" #' if `conversions` is not given, and adding "PPSTRESU" and #' "conversion_factor" if `conversions` is given. @@ -570,7 +571,7 @@ ensure_column_unit_exists <- function(pknca_obj, unit_name) { #' @returns A data frame containing the strata columns and their minimal set of grouping columns. #' @importFrom dplyr mutate select any_of #' @importFrom rlang syms -#' @importFrom stats combn +#' @importFrom utils combn #' @keywords Internal select_minimal_grouping_cols <- function(df, strata_cols) { # If there is no strata_cols specified, simply return the original df diff --git a/man/pknca_units_table.Rd b/man/pknca_units_table.Rd index e59e235a..664d5e96 100644 --- a/man/pknca_units_table.Rd +++ b/man/pknca_units_table.Rd @@ -27,6 +27,8 @@ pknca_units_table(concu, ...) \item{concu, doseu, amountu, timeu}{Units for concentration, dose, amount, and time in the source data} +\item{...}{Additional arguments (not used)} + \item{concu_pref, doseu_pref, amountu_pref, timeu_pref}{Preferred units for reporting; \code{conversions} will be automatically.} From 3c7e6fcd74209026450bff6b1ca6dbdacd926a00 Mon Sep 17 00:00:00 2001 From: Gero1999 Date: Sun, 14 Sep 2025 00:05:10 +0200 Subject: [PATCH 15/18] fix: issue for PKNCAdose not being present --- R/unit-support.R | 11 ++++++++--- 1 file changed, 8 insertions(+), 3 deletions(-) diff --git a/R/unit-support.R b/R/unit-support.R index f1768bd4..25de9fc8 100644 --- a/R/unit-support.R +++ b/R/unit-support.R @@ -173,21 +173,26 @@ pknca_units_table.default <- function(concu, doseu, amountu, timeu, ##' Method for PKNCAdata objects #' #' @rdname pknca_units_table -#' @importFrom dplyr across any_of bind_rows case_when filter group_by left_join mutate n select ungroup +#' @importFrom dplyr across any_of bind_rows case_when filter group_by left_join mutate n select ungroup group_vars #' @importFrom tidyr fill unnest #' @importFrom rlang syms #' @export pknca_units_table.PKNCAdata <- function(concu, ..., conversions = data.frame()) { + # concu is the PKNCAdata object o_conc <- concu$conc o_dose <- concu$dose + + # PKNCAdose can optionally be no present, being unit undefining + if (is.null(o_dose) || all(is.na(o_dose))) o_dose <- o_conc + # If needed, ensure that the PKNCA objects have the required unit columns o_conc <- ensure_column_unit_exists(o_conc, c("concu", "timeu", "amountu")) o_dose <- ensure_column_unit_exists(o_dose, c("doseu")) # Extract relevant columns from o_conc and o_dose - group_dose_cols <- unname(unlist(o_dose$columns$groups)) - group_conc_cols <- unname(unlist(o_conc$columns$groups)) + group_dose_cols <- dplyr::group_vars(o_dose) + group_conc_cols <- dplyr::group_vars(o_conc) concu_col <- o_conc$columns$concu amountu_col <- o_conc$columns$amountu timeu_col <- o_conc$columns$timeu From efb9118a0c19a86f3535bea9a68c5878dd4e4d40 Mon Sep 17 00:00:00 2001 From: Gero1999 Date: Sun, 14 Sep 2025 10:33:31 +0200 Subject: [PATCH 16/18] fix: warning in test due to left_join --- R/unit-support.R | 19 +++++++++---------- 1 file changed, 9 insertions(+), 10 deletions(-) diff --git a/R/unit-support.R b/R/unit-support.R index 25de9fc8..9f3e9c07 100644 --- a/R/unit-support.R +++ b/R/unit-support.R @@ -173,7 +173,7 @@ pknca_units_table.default <- function(concu, doseu, amountu, timeu, ##' Method for PKNCAdata objects #' #' @rdname pknca_units_table -#' @importFrom dplyr across any_of bind_rows case_when filter group_by left_join mutate n select ungroup group_vars +#' @importFrom dplyr across any_of bind_rows case_when filter group_by mutate n select ungroup group_vars #' @importFrom tidyr fill unnest #' @importFrom rlang syms #' @export @@ -200,15 +200,14 @@ pknca_units_table.PKNCAdata <- function(concu, ..., conversions = data.frame()) all_unit_cols <- c(concu_col, amountu_col, timeu_col, doseu_col) # Join dose units with concentration group columns and units - groups_units_tbl <- dplyr::left_join( - o_conc$data %>% - dplyr::select(dplyr::any_of(c(group_conc_cols, concu_col, amountu_col, timeu_col))) %>% - unique(), - o_dose$data %>% - dplyr::select(dplyr::any_of(c(group_dose_cols, doseu_col))) %>% - unique(), - by = intersect(group_conc_cols, group_dose_cols) - ) %>% + d_concu <- o_conc$data %>% + dplyr::select(dplyr::any_of(c(group_conc_cols, concu_col, amountu_col, timeu_col))) %>% + unique() + d_doseu <- o_dose$data %>% + dplyr::select(dplyr::any_of(c(group_dose_cols, doseu_col))) %>% + unique() + + groups_units_tbl <- merge(d_concu, d_doseu, all.x = TRUE) %>% dplyr::mutate(dplyr::across(dplyr::everything(), ~ as.character(.))) %>% dplyr::group_by(!!!rlang::syms(group_conc_cols)) %>% tidyr::fill(!!!rlang::syms(all_unit_cols), .direction = "downup") %>% From 1d1983db1d8f06b007b7706342e7b00b75a23609 Mon Sep 17 00:00:00 2001 From: Gero1999 Date: Sun, 14 Sep 2025 11:26:05 +0200 Subject: [PATCH 17/18] fix check: update namespace & rm S3 generic message --- NAMESPACE | 1 + R/unit-support.R | 2 -- man/pknca_units_table.Rd | 1 - 3 files changed, 1 insertion(+), 3 deletions(-) diff --git a/NAMESPACE b/NAMESPACE index fd815981..1be7135f 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -242,6 +242,7 @@ importFrom(dplyr,case_when) importFrom(dplyr,filter) importFrom(dplyr,full_join) importFrom(dplyr,group_by) +importFrom(dplyr,group_vars) importFrom(dplyr,inner_join) importFrom(dplyr,left_join) importFrom(dplyr,mutate) diff --git a/R/unit-support.R b/R/unit-support.R index 9f3e9c07..b5ec6c86 100644 --- a/R/unit-support.R +++ b/R/unit-support.R @@ -51,8 +51,6 @@ #' concu = "ng/mL", doseu = "mg/kg", timeu = "hr", amountu = "mg", #' timeu_pref = "day" #' ) - -#' S3 generic for pknca_units_table #' #' @export pknca_units_table <- function(concu, ...) { diff --git a/man/pknca_units_table.Rd b/man/pknca_units_table.Rd index 664d5e96..cd5a0867 100644 --- a/man/pknca_units_table.Rd +++ b/man/pknca_units_table.Rd @@ -81,7 +81,6 @@ pknca_units_table( concu = "ng/mL", doseu = "mg/kg", timeu = "hr", amountu = "mg", timeu_pref = "day" ) -S3 generic for pknca_units_table } \seealso{ From 877a26e2e63abe57f90adbce9442be6fa28c2dd7 Mon Sep 17 00:00:00 2001 From: Gero1999 Date: Mon, 24 Nov 2025 22:12:38 +0100 Subject: [PATCH 18/18] suggestions: as_PKNCAconc, as_PKNCAdose --- R/unit-support.R | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/R/unit-support.R b/R/unit-support.R index b5ec6c86..9845e3d6 100644 --- a/R/unit-support.R +++ b/R/unit-support.R @@ -178,8 +178,8 @@ pknca_units_table.default <- function(concu, doseu, amountu, timeu, pknca_units_table.PKNCAdata <- function(concu, ..., conversions = data.frame()) { # concu is the PKNCAdata object - o_conc <- concu$conc - o_dose <- concu$dose + o_conc <- as_PKNCAconc(concu) + o_dose <- as_PKNCAdose(concu) # PKNCAdose can optionally be no present, being unit undefining if (is.null(o_dose) || all(is.na(o_dose))) o_dose <- o_conc