Skip to content

Commit

Permalink
0063 Move examples for internal functions to unit tests (#69)
Browse files Browse the repository at this point in the history
* cnd_df internal examples removal

* ct and derive_seq remove examples for internal funs. Added unit test for derive_seq

* rest of the internal funs

* address lintr

* style issue and failed test
  • Loading branch information
ShiyuC authored Jul 24, 2024
1 parent a6e52d5 commit 6862b84
Show file tree
Hide file tree
Showing 62 changed files with 860 additions and 1,072 deletions.
1 change: 0 additions & 1 deletion NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,6 @@ export(derive_blfl)
export(derive_seq)
export(derive_study_day)
export(domain_example)
export(dtc_timepart)
export(fmt_cmp)
export(generate_oak_id_vars)
export(hardcode_ct)
Expand Down
76 changes: 0 additions & 76 deletions R/cnd_df.R
Original file line number Diff line number Diff line change
Expand Up @@ -48,10 +48,6 @@
#' @seealso [is_cnd_df()], [get_cnd_df_cnd()], [get_cnd_df_cnd_sum()],
#' [rm_cnd_df()].
#'
#' @examples
#' df <- data.frame(x = 1:3, y = letters[1:3])
#' sdtm.oak:::new_cnd_df(dat = df, cnd = c(FALSE, NA, TRUE))
#'
#' @keywords internal
new_cnd_df <- function(dat, cnd, .warn = TRUE) {
admiraldev::assert_data_frame(dat)
Expand Down Expand Up @@ -98,13 +94,6 @@ new_cnd_df <- function(dat, cnd, .warn = TRUE) {
#' @seealso [new_cnd_df()], [get_cnd_df_cnd()], [get_cnd_df_cnd_sum()],
#' [rm_cnd_df()].
#'
#' @examples
#' df <- data.frame(x = 1:3, y = letters[1:3])
#' sdtm.oak:::is_cnd_df(df)
#'
#' cnd_df <- sdtm.oak:::new_cnd_df(dat = df, cnd = c(FALSE, NA, TRUE))
#' sdtm.oak:::is_cnd_df(cnd_df)
#'
#' @keywords internal
is_cnd_df <- function(dat) {
inherits(dat, "cnd_df")
Expand All @@ -123,13 +112,6 @@ is_cnd_df <- function(dat) {
#' @seealso [new_cnd_df()], [is_cnd_df()], [get_cnd_df_cnd_sum()],
#' [rm_cnd_df()].
#'
#' @examples
#' df <- data.frame(x = 1:3, y = letters[1:3])
#' sdtm.oak:::get_cnd_df_cnd(df)
#'
#' cnd_df <- sdtm.oak:::new_cnd_df(dat = df, cnd = c(FALSE, NA, TRUE))
#' sdtm.oak:::get_cnd_df_cnd(cnd_df)
#'
#' @keywords internal
get_cnd_df_cnd <- function(dat) {
if (is_cnd_df(dat)) {
Expand All @@ -151,13 +133,6 @@ get_cnd_df_cnd <- function(dat) {
#'
#' @seealso [new_cnd_df()], [is_cnd_df()], [get_cnd_df_cnd()], [rm_cnd_df()].
#'
#' @examples
#' df <- data.frame(x = 1:3, y = letters[1:3])
#' sdtm.oak:::get_cnd_df_cnd_sum(df)
#'
#' cnd_df <- sdtm.oak:::new_cnd_df(dat = df, cnd = c(FALSE, NA, TRUE))
#' sdtm.oak:::get_cnd_df_cnd_sum(cnd_df)
#'
#' @keywords internal
get_cnd_df_cnd_sum <- function(dat) {
if (is_cnd_df(dat)) {
Expand All @@ -178,13 +153,6 @@ get_cnd_df_cnd_sum <- function(dat) {
#' @seealso [new_cnd_df()], [is_cnd_df()], [get_cnd_df_cnd()],
#' [get_cnd_df_cnd_sum()].
#'
#' @examples
#' df <- data.frame(x = 1:3, y = letters[1:3])
#' cnd_df <- sdtm.oak:::new_cnd_df(dat = df, cnd = c(FALSE, NA, TRUE))
#'
#' sdtm.oak:::is_cnd_df(cnd_df)
#' sdtm.oak:::is_cnd_df(sdtm.oak:::rm_cnd_df(cnd_df))
#'
#' @keywords internal
rm_cnd_df <- function(dat) {
if (is_cnd_df(dat)) {
Expand Down Expand Up @@ -290,41 +258,6 @@ ctl_new_rowid_pillar.cnd_df <- function(controller, x, width, ...) {
#'
#' @returns A logical vector reflecting matching rows in `dat`.
#'
#' @examples
#' # Create a sample data frame
#' df <- data.frame(
#' x = c(1, 2, NA_integer_, 4, 5),
#' y = c(TRUE, FALSE, TRUE, FALSE, TRUE),
#' z = c("a", "b", "a", "b", "a")
#' )
#'
#' # Simple condition on one column
#' sdtm.oak:::eval_conditions(df, x > 2)
#'
#' # Combined conditions on multiple columns
#' sdtm.oak:::eval_conditions(df, x > 2 & y)
#' sdtm.oak:::eval_conditions(df, x > 2, y)
#'
#' # Using conditions with NA handling
#' df_with_na <- data.frame(
#' x = c(1, 2, NA, 4, 5),
#' y = c(TRUE, FALSE, TRUE, FALSE, TRUE)
#' )
#' sdtm.oak:::eval_conditions(df_with_na, x > 2, .na = FALSE)
#'
#' # The environment where `eval_conditions()` is called is also inspected
#' # when evaluating conditions in `...`.
#' w <- 1
#' sdtm.oak:::eval_conditions(df, x > w)
#'
#' # Using an environment
#' env <- rlang::env(w = 2)
#' sdtm.oak:::eval_conditions(df, x > w, .env = env)
#'
#' # In place of an environment, you may alternatively pass a list or data frame.
#' sdtm.oak:::eval_conditions(df, x > w, .env = list(w = 3))
#' sdtm.oak:::eval_conditions(df, x > w, .env = tibble::tibble(w = 4))
#'
#' @keywords internal
eval_conditions <- function(dat,
...,
Expand Down Expand Up @@ -405,15 +338,6 @@ condition_add <- function(dat, ..., .na = NA, .dat2 = rlang::env()) {
#' @param .after Control where new columns should appear, i.e. after which
#' columns.
#'
#' @examples
#' df <- tibble::tibble(x = 1L:3L, y = letters[x])
#' cnd_df <- condition_add(df, x > 1L, y %in% c("a", "b"))
#'
#' # Because `cnd_df` is a conditioned data frame, dplyr::mutate() generic
#' # dispatches this S3 method and mutates only the second row, as that is the
#' # only record that fulfills simultaneously `x > 1L` and `y %in% c("a", "b")`.
#' dplyr::mutate(cnd_df, z = "match")
#'
#' @inheritParams dplyr::mutate
#' @importFrom dplyr mutate
#' @export
Expand Down
61 changes: 0 additions & 61 deletions R/ct.R
Original file line number Diff line number Diff line change
Expand Up @@ -13,21 +13,6 @@
#' @param set A scalar character (string), one of: `"all"` (default), `"ct_clst"`,
#' `"from"` or `"to"`.
#'
#' @examples
#' # These two calls are equivalent and return all required variables in a
#' # controlled terminology data set.
#' ct_spec_vars()
#' ct_spec_vars("all")
#'
#' # "Codelist code" variable name.
#' ct_spec_vars("ct_clst")
#'
#' # "From" variables
#' ct_spec_vars("from")
#'
#' # The "to" variable.
#' ct_spec_vars("to")
#'
#' @keywords internal
#' @export
ct_spec_vars <- function(set = c("all", "ct_clst", "from", "to")) {
Expand Down Expand Up @@ -71,25 +56,6 @@ ct_spec_vars <- function(set = c("all", "ct_clst", "from", "to")) {
#' @returns The function throws an error if `ct_spec` is not a valid controlled
#' terminology data set; otherwise, `ct_spec` is returned invisibly.
#'
#' @examples
#' # If `ct_spec` is a valid controlled terminology then it is returned invisibly.
#' ct_spec_01 <- read_ct_spec_example("ct-01-cm")
#' all.equal(ct_spec_01, sdtm.oak:::assert_ct_spec(ct_spec_01))
#'
#' # A minimal set of variables needs to be present in `ct_spec` for it to pass the
#' # assertion; `sdtm.oak:::ct_spec_vars()` defines their names.
#' (req_vars <- sdtm.oak:::ct_spec_vars())
#'
#' # Other (facultative) variables also present in the controlled terminology
#' # example.
#' (opt_vars <- setdiff(colnames(ct_spec_01), req_vars))
#'
#' # With only the mandatory variables, the assertion still passes.
#' sdtm.oak:::assert_ct_spec(ct_spec_01[req_vars])
#'
#' # Not having the required variables results in an error.
#' try(sdtm.oak:::assert_ct_spec(ct_spec_01[opt_vars]))
#'
#' @keywords internal
assert_ct_spec <- function(ct_spec, optional = FALSE) {
admiraldev::assert_data_frame(
Expand Down Expand Up @@ -128,21 +94,6 @@ assert_ct_spec <- function(ct_spec, optional = FALSE) {
#' given the controlled terminology data set; otherwise, `ct_clst` is returned
#' invisibly.
#'
#' @examples
#' # Load a controlled terminology example.
#' (ct_spec <- read_ct_spec_example("ct-01-cm"))
#'
#' # Should work fine.
#' sdtm.oak:::assert_ct_clst(ct_spec = ct_spec, ct_clst = "C71113")
#'
#' # In certain cases, you might allow `ct_clst` to be `NULL` as to indicate absence,
#' # in that case, set `optional` to `TRUE` to make `assert_ct_clst()` more
#' # forgiving.
#' sdtm.oak:::assert_ct_clst(ct_spec = ct_spec, ct_clst = NULL, optional = TRUE)
#'
#' # Otherwise it would err.
#' try(sdtm.oak:::assert_ct_clst(ct_spec = ct_spec, ct_clst = NULL, optional = FALSE))
#'
#' @keywords internal
assert_ct_clst <- function(ct_spec, ct_clst, optional = FALSE) {
is_ct_spec_missing <- is.null(ct_spec)
Expand Down Expand Up @@ -206,18 +157,6 @@ assert_ct_clst <- function(ct_spec, ct_clst, optional = FALSE) {
#' @returns A [tibble][tibble::tibble-package] with two columns, `from` and
#' `to`, indicating the mapping of values, one per row.
#'
#' @examples
#' # Read in a bundled controlled terminology spec example (ex. 01).
#' (ct_spec_01 <- read_ct_spec_example("ct-01-cm"))
#'
#' # Generate mappings from the terminology specification.
#' sdtm.oak:::ct_mappings(ct_spec = ct_spec_01)
#'
#' # Take a glimpse at those mappings where an actual recoding happens.
#' sdtm.oak:::ct_mappings(ct_spec = ct_spec_01) |>
#' dplyr::filter(from != to) |>
#' print(n = 20)
#'
#' @importFrom rlang .data
#' @keywords internal
ct_mappings <- function(ct_spec, from = ct_spec_vars("from"), to = ct_spec_vars("to")) {
Expand Down
43 changes: 0 additions & 43 deletions R/derive_blfl.R
Original file line number Diff line number Diff line change
Expand Up @@ -9,19 +9,6 @@
#'
#' @return Character vector containing ISO8601 dates.
#'
#' @examples
#' ## Partial or missing dates set to NA by default
#' sdtm.oak:::dtc_datepart(
#' c(NA, "", "2021", "2021-12", "2021-12-25", "2021-12-25T12:00:00")
#' )
#' # |--> c(NA, NA, NA, NA, "2021-12-25", "2021-12-25")
#'
#' ## Prevent partial or missing dates from being set to NA
#' sdtm.oak:::dtc_datepart(
#' c(NA, "", "2021", "2021-12", "2021-12-25", "2021-12-25T12:00:00"),
#' partial_as_na = FALSE
#' )
#' # |--> c(NA, "", "2021", "2021-12", "2021-12-25", "2021-12-25")
#' @keywords internal
dtc_datepart <- function(dtc, partial_as_na = TRUE) {
# Assert that dtc is a character vector
Expand Down Expand Up @@ -51,38 +38,8 @@ dtc_datepart <- function(dtc, partial_as_na = TRUE) {
#' seconds should be ignored (default is `TRUE`).
#'
#' @return Character vector containing ISO 8601 times.
#' @export
#'
#' @keywords internal
#'
#' @examples
#' ## Partial or missing times set to NA and seconds ignored by default
#' sdtm.oak:::dtc_timepart(
#' c(NA, "", "2021-12-25", "2021-12-25T12", "2021-12-25T12:30", "2021-12-25T12:30:59")
#' )
#' # |--> c(NA, NA, NA, NA, "12:30", "12:30")
#'
#' ## Prevent partial or missing times from being set to NA
#' sdtm.oak:::dtc_timepart(
#' c(NA, "", "2021-12-25", "2021-12-25T12", "2021-12-25T12:30", "2021-12-25T12:30:59"),
#' partial_as_na = FALSE
#' )
#' # |--> c(NA, "", "", "12", "12:30", "12:30")
#'
#' ## Do not ignore seconds, partial or missing times set to NA
#' sdtm.oak:::dtc_timepart(
#' c(NA, "", "2021-12-25", "2021-12-25T12", "2021-12-25T12:30", "2021-12-25T12:30:59"),
#' ignore_seconds = FALSE
#' )
#' # |--> c(NA, NA, NA, NA, NA, "12:30:59")
#'
#' ## Do not ignore seconds and prevent partial or missing times from being set to NA
#' sdtm.oak:::dtc_timepart(
#' c(NA, "", "2021-12-25", "2021-12-25T12", "2021-12-25T12:30", "2021-12-25T12:30:59"),
#' partial_as_na = FALSE,
#' ignore_seconds = FALSE
#' )
#' # |--> c(NA, "", "", "12", "12:30", "12:30:59")
dtc_timepart <- function(dtc, partial_as_na = TRUE, ignore_seconds = TRUE) {
# Assert that dtc is a character vector
admiraldev::assert_character_vector(dtc)
Expand Down
11 changes: 0 additions & 11 deletions R/derive_seq.R
Original file line number Diff line number Diff line change
Expand Up @@ -80,17 +80,6 @@ derive_seq <-
#'
#' @returns A logical vector.
#'
#' @examples
#' # A valid SEQ name.
#' sdtm.oak:::is_seq_name("AESEQ")
#'
#' # Not valid sequence number (`--SEQ`) variable names.
#' # Case matters.
#' sdtm.oak:::is_seq_name("AEseq")
#'
#' # A valid name has to end in "SEQ".
#' sdtm.oak:::is_seq_name("AESEQUENCE")
#'
#' @keywords internal
is_seq_name <- function(x) {
stringr::str_detect(x, "SEQ$")
Expand Down
Loading

0 comments on commit 6862b84

Please sign in to comment.