TL Catalog
  1. Tables
  2. Clinical Laboratory Evaluation
  3. TSFLAB05
  • Introduction

  • Index

  • Tables
    • Adverse Events
      • TSFAE01A
      • TSFAE01B
      • TSFAE02
      • TSFAE02A
      • TSFAE03
      • TSFAE03A
      • TSFAE04
      • TSFAE04A
      • TSFAE05
      • TSFAE05A
      • TSFAE06A
      • TSFAE06B
      • TSFAE07A
      • TSFAE07B
      • TSFAE08
      • TSFAE09
      • TSFAE10
      • TSFAE11
      • TSFAE12
      • TSFAE13
      • TSFAE14
      • TSFAE15
      • TSFAE16
      • TSFAE17A
      • TSFAE17B
      • TSFAE17C
      • TSFAE17D
      • TSFAE19A
      • TSFAE19B
      • TSFAE19C
      • TSFAE19D
      • TSFAE20A
      • TSFAE20B
      • TSFAE20C
      • TSFAE21A
      • TSFAE21B
      • TSFAE21C
      • TSFAE21D
      • TSFAE22A
      • TSFAE22B
      • TSFAE22C
      • TSFAE23A
      • TSFAE23B
      • TSFAE23C
      • TSFAE23D
      • TSFAE24A
      • TSFAE24B
      • TSFAE24C
      • TSFAE24D
      • TSFAE24F
      • TSFDTH01
    • Clinical Laboratory Evaluation
      • TSFLAB01
      • TSFLAB01A
      • TSFLAB02
      • TSFLAB02A
      • TSFLAB02B
      • TSFLAB03
      • TSFLAB03A
      • TSFLAB04A
      • TSFLAB04B
      • TSFLAB05
      • TSFLAB06
      • TSFLAB07
    • Demographic
      • TSIDEM01
      • TSIDEM02
      • TSIMH01
    • Disposition of Subjects
      • TSIDS01
      • TSIDS02
      • TSIDS02A
    • Electrocardiograms
      • TSFECG01
      • TSFECG01A
      • TSFECG02
      • TSFECG03
      • TSFECG04
      • TSFECG05
    • Exposure
      • TSIEX01
      • TSIEX02
      • TSIEX03
      • TSIEX04
      • TSIEX06
      • TSIEX07
      • TSIEX08
      • TSIEX09
      • TSIEX10
      • TSIEX11
    • Pharmacokinetics
      • TPK01A
      • TPK01B
      • TPK02
      • TPK03
    • Prior and Concomitant Therapies
      • TSICM01
      • TSICM02
      • TSICM03
      • TSICM04
      • TSICM05
      • TSICM06
      • TSICM07
      • TSICM08
    • Vital Signs and Physical Findings
      • TSFVIT01
      • TSFVIT01A
      • TSFVIT02
      • TSFVIT03
      • TSFVIT04
      • TSFVIT05
      • TSFVIT06
  • Listings
    • Adverse Events
      • LSFAE01
      • LSFAE02
      • LSFAE03
      • LSFAE04
      • LSFAE05
      • LSFAE06A
      • LSFAE06B
      • LSFDTH01
    • Clinical Laboratory Evaluation
      • LSFLAB01
    • Demographic
      • LSIDEM01
      • LSIDEM02
      • LSIMH01
    • Disposition of Subjects
      • LSIDS01
      • LSIDS02
      • LSIDS03
      • LSIDS04
      • LSIDS05
    • Electrocardiograms
      • LSFECG01
      • LSFECG02
    • Exposure
      • LSIEX01
      • LSIEX02
      • LSIEX03
    • Prior and Concomitant Therapies
      • LSICM01
    • Vital Signs and Physical Findings
      • LSFVIT01
      • LSFVIT02

  • Reproducibility

  • Changelog

On this page

  • Output
  • Edit this page
  • Report an issue
  1. Tables
  2. Clinical Laboratory Evaluation
  3. TSFLAB05

TSFLAB05

Subjects With Last/Any On-treatment Laboratory Values = Grade 2 Based on NCI-CTCAE Criteria


Output

  • Preview
Code
# Program Name:              tsflab05

# Prep Environment

library(envsetup)
library(tern)
library(dplyr)
library(rtables)
library(junco)

# Define script level parameters:

tblid <- "TSFLAB05"
titles <- get_titles_from_file(input_path = '../../_data/', tblid)
string_map <- default_str_map
fileid <- tblid

popfl <- "SAFFL"
trtvar <- "TRT01A"
ctrl_grp <- "Placebo"

grade_threshold <- "2"

## For toxicity grades, the units should not matter, work with adlb dataset as default

ad_domain <- "ADLB"

#### table options:
# last_any <- "LAST"
last_any <- "ANY"
### if ANY, then Subjects with Any on-treatment value >= Level 2 will be presented (ANL04FL/ANL05FL/ONTRTFL will be used here)
### if Last, then Subjects with Last on-treatment value >= Level 2 will be presented (LVOTFL will be used here)

## if the option TRTEMFL needs to be added to the TLF -- ensure the same setting as in tsflabxxxx
trtemfl <- TRUE

## parcat5 and 6 options :

availparcat56 <- c(
  "Investigations",
  "Metabolism and nutritional disorders",
  "Renal and urinary disorders",
  "Blood and lymphatic system disorders"
)

## resrict to some
selparcat56 <- availparcat56[c(1, 2, 4)]

## get all
selparcat56 <- availparcat56

# Initial processing of data

adlb_complete <- pharmaverseadamjnj::adlb

# Process lab toxicity file

lbtoxgrade_file <- file.path('../../_data', "lbtoxgrade.xlsx")
lbtoxgrade_sheets <- readxl::excel_sheets(path = lbtoxgrade_file)

### CTC5 or DAIDS21c : default CTC5

lbvars <- c("LBTESTCD", "LBTEST", "LBSPEC", "LBMETHOD")

lbtoxgrade_defs <- readxl::read_excel(lbtoxgrade_file, sheet = "CTC5")

lbtoxgrade_defs <- unique(
  unique(
    lbtoxgrade_defs %>%
      select(all_of(lbvars), TOXTERM, TOXGRD, INDICATR)
  ) %>%
    mutate(
      ATOXDSCLH = TOXTERM,
      ATOXGRLH = paste("Grade", TOXGRD)
    ) %>%
    rename(ATOXDIR = INDICATR) %>%
    select(all_of(lbvars), ATOXDSCLH, ATOXDIR)
)

# Initial processing of data

### be aware, there are toxicity terms that are based upon diff tests (example "Neutrophil Count Decreased": NEUT and NEUTSG) !!!!!
### if both tests are included in ADaM dataset, review your derivations carefully
attention_terms <-
  unique(lbtoxgrade_defs %>% select(ATOXDSCLH, all_of(lbvars))) %>%
  group_by(ATOXDSCLH) %>%
  mutate(n = n_distinct(LBTESTCD)) %>%
  filter(n > 1)

ad_toxterms <- bind_rows(
  unique(
    adlb_complete %>%
      select(PARAMCD, ATOXDSCL) %>%
      mutate(TOXTERM = ATOXDSCL, TOXDIR = "LOW")
  ),
  unique(
    adlb_complete %>%
      select(PARAMCD, ATOXDSCH) %>%
      mutate(TOXTERM = ATOXDSCH, TOXDIR = "HIGH")
  )
) %>%
  select(PARAMCD, TOXTERM, TOXDIR) %>%
  filter(!is.na(TOXTERM)) %>%
  arrange(TOXTERM, TOXDIR, PARAMCD)


attention_ad_toxterms <- ad_toxterms %>%
  group_by(TOXTERM) %>%
  mutate(n = n_distinct(PARAMCD)) %>%
  filter(n > 1)

#### From here onwards: avoid using PARAMCD, to ensure toxterm is combined

### could also work with param_lookup and lbtoxgrade_defs
### ALERT: do not include PARAMCD here as some toxicity terms are based on more than one PARAMCD: here : NEUT and NEUTSG both have TOXTERM = Neutrophil Count Decreased
toxterms <- unique(
  adlb_complete %>%
    filter(!(is.na(ATOXDSCL) & is.na(ATOXDSCH))) %>%
    ### do not include PARAMCD here!!!!
    select(ATOXDSCL, ATOXDSCH) %>%
    tidyr::pivot_longer(
      .,
      cols = c("ATOXDSCL", "ATOXDSCH"),
      names_to = "VARNAME",
      values_to = "ATOXDSCLH"
    )
) %>%
  filter(!is.na(ATOXDSCLH))

### convert dataframe into label_map that can be used with the a_freq_j afun function
xlabel_map <- toxterms %>%
  mutate(
    var = "ATOXGRLHx",
    value = "Y",
    label = as.character(ATOXDSCLH)
  ) %>%
  select(ATOXDSCLH, value, label)

# Process Data:

adsl <- pharmaverseadamjnj::adsl %>%
  filter(.data[[popfl]] == "Y") %>%
  select(STUDYID, USUBJID, all_of(c(popfl, trtvar)))

adsl$colspan_trt <- factor(
  ifelse(adsl[[trtvar]] == ctrl_grp, " ", "Active Study Agent"),
  levels = c("Active Study Agent", " ")
)

adsl$rrisk_header <- "Risk Difference (%) (95% CI)"
adsl$rrisk_label <- paste(adsl[[trtvar]], paste("vs", ctrl_grp))

colspan_trt_map <- create_colspan_map(
  adsl,
  non_active_grp = ctrl_grp,
  non_active_grp_span_lbl = " ",
  active_grp_span_lbl = "Active Study Agent",
  colspan_var = "colspan_trt",
  trt_var = trtvar
)

ref_path <- c("colspan_trt", " ", trtvar, ctrl_grp)

flagvars <- c("ONTRTFL", "TRTEMFL", "LVOTFL")
adlb00 <- adlb_complete %>%
  select(
    USUBJID,
    AVISITN,
    AVISIT,
    starts_with("PAR"),
    starts_with("ATOX"),
    starts_with("ANL"),
    all_of(flagvars),
    LBSEQ,
    AVAL,
    AVALC
  ) %>%
  inner_join(adsl) %>%
  mutate(
    ATOXGRL = as.character(ATOXGRL),
    ATOXGRH = as.character(ATOXGRH)
  ) %>%
  relocate(
    .,
    USUBJID,
    ANL04FL,
    ANL05FL,
    ONTRTFL,
    TRTEMFL,
    AVISIT,
    ATOXGRL,
    ATOXGRH,
    ATOXDSCL,
    ATOXDSCH,
    PARAMCD,
    AVISIT,
    AVAL
  )


# adlb00 <- adlb00 #%>%
## APT comment on PARCAT6 :
## HGB and WBC : Set to "Blood and lymphatic system disorders".
## HGB and WBC parameter are in 2 categories, one for the high and another one for the low direction grading.
## Anemia (HGB low) and Leukocytosis (WBC high) are in the category "Blood and lymphatic system disorders".
## The grading in the opposite directions are categorized under "Investigations".
## Therefor, both PARCAT5 and PARCAT6 are populated for HGB abd WBC.
## Deal with what is needed at later level, when we have splitted low and high

# obj_label(adlb00$PARCAT56) <- "Combined PARCAT56"

### important: previous actions lost the label of variables

adlb00 <- var_relabel_list(adlb00, var_labels(adlb_complete, fill = T))

if (all(selparcat56 != "")) {
  filtered_adlb <- adlb00 %>%
    filter((PARCAT5 %in% selparcat56) | (PARCAT6 %in% selparcat56))
} else {
  filtered_adlb <- adlb00
}

### low grades : ATOXDSCL ATOXGRL ANL04FL
filtered_adlb_low <- filtered_adlb %>%
  filter(!is.na(ATOXDSCL) & !is.na(ATOXGRL)) %>%
  mutate(
    ATOXDSCLH = ATOXDSCL,
    ATOXGRLH = ATOXGRL,
    ATOXDIR = "LOW",
    ANL045FL = ANL04FL
  ) %>%
  select(
    USUBJID,
    starts_with("PAR"),
    starts_with("ATOX"),
    all_of(flagvars),
    ANL04FL,
    ANL05FL,
    ANL045FL,
    LBSEQ,
    AVAL,
    AVALC
  ) %>%
  select(-c(ATOXGRL, ATOXGRH, ATOXDSCL, ATOXDSCH))

### high grades: ATOXDSCH ATOXGRH ANL05FL
filtered_adlb_high <- filtered_adlb %>%
  filter(ANL05FL == "Y" & !is.na(ATOXDSCH) & !is.na(ATOXGRH)) %>%
  mutate(
    ATOXDSCLH = ATOXDSCH,
    ATOXGRLH = ATOXGRH,
    ATOXDIR = "HIGH",
    ANL045FL = ANL05FL
  ) %>%
  select(
    USUBJID,
    starts_with("PAR"),
    starts_with("ATOX"),
    all_of(flagvars),
    ANL04FL,
    ANL05FL,
    ANL045FL,
    LBSEQ,
    AVAL,
    AVALC
  ) %>%
  select(-c(ATOXGRL, ATOXGRH, ATOXDSCL, ATOXDSCH))


## combine Low and high into adlb_tox
filtered_adlb_tox <-
  bind_rows(
    filtered_adlb_low,
    filtered_adlb_high
  ) %>%
  select(-c(ATOXGR, ATOXGRN)) %>%
  mutate(ATOXGRLHN = as.numeric(ATOXGRLH)) %>%
  inner_join(adsl)


### correction of proper category (PARCAT56) for HGB (LOW) and WBC (HIGH)
filtered_adlb_tox <-
  filtered_adlb_tox %>%
  mutate(
    PARCAT56 = case_when(
      PARAMCD == "HGB" & ATOXDIR == "LOW" ~ PARCAT6,
      PARAMCD == "WBC" & ATOXDIR == "HIGH" ~ PARCAT6,
      TRUE ~ PARCAT5
    )
  ) %>%
  mutate(
    PARCAT56 = factor(
      PARCAT56,
      levels = unique(c(
        "Blood and lymphatic system disorders",
        levels(adlb_complete$PARCAT5)
      ))
    )
  )


filtered_adlb_tox <- unique(
  filtered_adlb_tox
)

filtered_adlb_tox_1 <- filtered_adlb_tox # %>%
# ## On treatment
# filter(ONTRTFL == "Y")

### Note on On-treatment
### note: by filter ANL04FL/ANL05FL, this table is restricted to On-treatment values, per definition of ANL04FL/ANL05FL
### Same for LVOTFL
### therefor, no need to add ONTRTFL in filter
### if derivation of ANL04FL/ANL05FL/LVOTFL is not restricted to ONTRTFL records, adding ONTRTFL here will not give the correct answer either
### as mixing worst with other period is not giving the proper selection !!!

if (toupper(last_any) == "ANY") {
  filtered_adlb_tox_1 <- filtered_adlb_tox_1 %>%
    ## Optional : Any : ensure to have one record per subject for direction
    filter(ANL04FL == "Y" | ANL05FL == "Y")
}

if (toupper(last_any) == "LAST") {
  filtered_adlb_tox_1 <- filtered_adlb_tox_1 %>%
    ## Optional : last on treatment record only
    filter(LVOTFL == "Y")
}


#### DO NOT USE TRTEMFL = Y in filter, as this will remove subjects from both numerator and denominator
#### instead : set ATOXGRLH to a non-reportable value (ie Grade 0) and keep in dataset
if (trtemfl) {
  filtered_adlb_tox_1 <- filtered_adlb_tox_1 %>%
    mutate(
      ATOXGRLHN = case_when(
        is.na(TRTEMFL) | TRTEMFL != "Y" ~ 0,
        TRUE ~ ATOXGRLHN
      )
    )
}


### Alphabetical sorting of toxicity terms
atoxdsclh_levels <- sort(as.character(unique(filtered_adlb_tox_1$ATOXDSCLH)))

filtered_adlb_tox_1 <- filtered_adlb_tox_1 %>%
  mutate(
    ATOXGRLHx = case_when(
      ATOXGRLHN >= as.numeric(grade_threshold) ~ "Y",
      TRUE ~ "N"
    )
  ) %>%
  mutate(ATOXGRLHx = factor(ATOXGRLHx, levels = c("Y", "N"))) %>%
  mutate(ATOXDSCLH = factor(ATOXDSCLH, levels = atoxdsclh_levels))


# check uniqueness
check_non_unique_subject <- filtered_adlb_tox_1 %>%
  group_by(USUBJID, ATOXDSCLH) %>%
  mutate(n_subject = n()) %>%
  filter(n_subject > 1)

if (nrow(check_non_unique_subject)) {
  message(
    "Please review your data selection process, subject has multiple records"
  )
}

### syntethic data: no records for NEUT/NEUTSG for the further selection (ATOXGRL is never populated for these records)
xx <- adlb00 %>%
  filter(ATOXDSCL == "Neutrophil Count Decreased" & !is.na(ATOXGRL))

# Define layout and build table:

extra_args_rr <- list(
  method = "wald",
  denom = "n_df",
  .stats = c("count_unique_denom_fraction"),
  ref_path = ref_path
)


lyt <- basic_table(show_colcounts = TRUE, colcount_format = "N=xx") %>%
  ### first columns
  split_cols_by(
    "colspan_trt",
    split_fun = trim_levels_to_map(map = colspan_trt_map)
  ) %>%
  split_cols_by(trtvar) %>%
  split_cols_by("rrisk_header", nested = FALSE) %>%
  split_cols_by(
    trtvar,
    labels_var = "rrisk_label",
    split_fun = remove_split_levels(ctrl_grp)
  ) %>%
  split_rows_by(
    "PARCAT56",
    label_pos = "topleft",
    child_labels = "visible",
    split_label = "Laboratory Category",
    split_fun = drop_split_levels,
    section_div = " "
  ) %>%
  split_rows_by(
    "ATOXDSCLH",
    label_pos = "topleft",
    split_label = paste0(
      "Laboratory Test \u2265 Grade ",
      grade_threshold,
      ", n (%)"
    ),
    child_labels = "hidden",
    split_fun = drop_split_levels
  ) %>%
  analyze(
    "ATOXGRLHx",
    afun = a_freq_j,
    extra_args = append(
      extra_args_rr,
      list(
        val = c("Y"),
        label_map = xlabel_map
      )
    ),
    show_labels = "hidden",
    indent_mod = 0L
  )

result <- build_table(lyt, filtered_adlb_tox_1, alt_counts_df = adsl)

# Post-Processing:

### Issue: tests with only 1 direction (either low or high) get a line with label a_freq_j (analyze function)
### remove these lines here

result <- result %>% prune_table(prune_func = keep_rows(keep_non_null_rows))

# Remove colcount from rrisk_header:

result <- remove_col_count(result)

# Add titles and footnotes:

result <- set_titles(result, titles)

# Convert to tbl file and output table

tt_to_tlgrtf(string_map = string_map, tt = result, file = fileid, orientation = "landscape")

TSFLAB05: Subjects With [Last/Any] On-treatment Laboratory Values [= Grade 2] Based on NCI-CTCAE Criteria; Safety Analysis Set (Study jjcs - core)

Active Study Agent

Risk Difference (%) (95% CI)

Laboratory Category

Xanomeline High Dose

Xanomeline Low Dose

Placebo

Xanomeline High Dose vs Placebo

Xanomeline Low Dose vs Placebo

Laboratory Test ≥ Grade 2, n (%)

N=53

N=73

N=59

Blood and lymphatic system
 disorders

Anemia

28/53 (52.8%)

36/73 (49.3%)

33/59 (55.9%)

-3.1 (-21.6, 15.4)

-6.6 (-23.7, 10.5)

Leukocytosis

0/53 (0.0%)

0/73 (0.0%)

0/59 (0.0%)

0.0 (0.0, 0.0)

0.0 (0.0, 0.0)

Investigations

Alanine aminotransferase
 increased

0/53 (0.0%)

0/73 (0.0%)

1/59 (1.7%)

-1.7 (-5.0, 1.6)

-1.7 (-5.0, 1.6)

Alkaline phosphatase
 increased

0/53 (0.0%)

0/73 (0.0%)

1/59 (1.7%)

-1.7 (-5.0, 1.6)

-1.7 (-5.0, 1.6)

Aspartate aminotransferase
 increased

1/53 (1.9%)

1/73 (1.4%)

1/59 (1.7%)

0.2 (-4.7, 5.1)

-0.3 (-4.6, 3.9)

Blood bilirubin increased

2/53 (3.8%)

1/73 (1.4%)

0/59 (0.0%)

3.8 (-1.4, 8.9)

1.4 (-1.3, 4.0)

Cholesterol high

2/53 (3.8%)

2/73 (2.7%)

3/59 (5.1%)

-1.3 (-8.9, 6.3)

-2.3 (-9.1, 4.4)

Creatinine increased

0/53 (0.0%)

0/73 (0.0%)

0/59 (0.0%)

0.0 (0.0, 0.0)

0.0 (0.0, 0.0)

Platelet count decreased

26/53 (49.1%)

32/73 (43.8%)

24/59 (40.7%)

8.4 (-10.0, 26.8)

3.2 (-13.8, 20.1)

White blood cell decreased

24/53 (45.3%)

25/73 (34.2%)

33/59 (55.9%)

-10.6 (-29.1, 7.8)

-21.7 (-38.4, -5.0)

Metabolism and nutritional
 disorders

CD4 lymphocytes decreased

23/53 (43.4%)

32/73 (43.8%)

34/59 (57.6%)

-14.2 (-32.6, 4.1)

-13.8 (-30.8, 3.2)

Hyperglycemia

4/53 (7.5%)

1/73 (1.4%)

0/59 (0.0%)

7.5 (0.4, 14.7)

1.4 (-1.3, 4.0)

Hyperkalemia

0/53 (0.0%)

0/73 (0.0%)

1/59 (1.7%)

-1.7 (-5.0, 1.6)

-1.7 (-5.0, 1.6)

Hypernatremia

1/53 (1.9%)

0/73 (0.0%)

0/59 (0.0%)

1.9 (-1.8, 5.5)

0.0 (0.0, 0.0)

Hypoalbuminemia

29/53 (54.7%)

27/73 (37.0%)

33/59 (55.9%)

-1.2 (-19.7, 17.2)

-18.9 (-35.8, -2.1)

Hypoglycemia

35/53 (66.0%)

32/73 (43.8%)

35/59 (59.3%)

6.7 (-11.2, 24.6)

-15.5 (-32.4, 1.4)

Hypokalemia

29/53 (54.7%)

32/73 (43.8%)

29/59 (49.2%)

5.6 (-12.9, 24.1)

-5.3 (-22.4, 11.8)

Hyponatremia

30/53 (56.6%)

37/73 (50.7%)

25/59 (42.4%)

14.2 (-4.1, 32.6)

8.3 (-8.7, 25.4)

Note: On-treatment is defined as treatment-emergentlaboratory values obtained after the first dose and within [30 days] following treatment discontinuation. [Treatment-emergent values are those that worsened from baseline.]

Note: NCI-CTCAE grades (version 5.0.) are based on the laboratory result and do not take into account the clinical component, if applicable.

Download RTF file

TSFLAB04B
TSFLAB06
Source Code
---
title: TSFLAB05
subtitle: Subjects With Last/Any On-treatment Laboratory Values = Grade 2 Based on NCI-CTCAE Criteria
---

------------------------------------------------------------------------

{{< include ../../_utils/envir_hook.qmd >}}

```{r setup, echo = FALSE, warning = FALSE, message = FALSE}
options(docx.add_datetime = FALSE, tidytlg.add_datetime = FALSE)
envsetup_config_name <- "default"

# Path to the combined config file
envsetup_file_path <- file.path("../..", "envsetup.yml")

Sys.setenv(ENVSETUP_ENVIRON = '')
library(envsetup)
loaded_config <- config::get(config = envsetup_config_name, file = envsetup_file_path)
envsetup::rprofile(loaded_config)


dpscomp <- compound
dpspdr <- paste(protocol,dbrelease,rpteff,sep="__")

aptcomp <- compound
aptpdr <- paste(protocol,dbrelease,rpteff,sep="__")

###### Study specific updates (formerly in envre)

dpscomp <- "standards"
dpspdr <- "jjcs__NULL__jjcs - core"

apt <- FALSE
library(junco)
default_str_map <- rbind(default_str_map, c("&ctcae", "5.0"))

```

## Output

:::: panel-tabset
## {{< fa regular file-lines sm fw >}} Preview

```{r variant1, results='hide', warning = FALSE, message = FALSE}

# Program Name:              tsflab05

# Prep Environment

library(envsetup)
library(tern)
library(dplyr)
library(rtables)
library(junco)

# Define script level parameters:

tblid <- "TSFLAB05"
titles <- get_titles_from_file(input_path = '../../_data/', tblid)
string_map <- default_str_map
fileid <- tblid

popfl <- "SAFFL"
trtvar <- "TRT01A"
ctrl_grp <- "Placebo"

grade_threshold <- "2"

## For toxicity grades, the units should not matter, work with adlb dataset as default

ad_domain <- "ADLB"

#### table options:
# last_any <- "LAST"
last_any <- "ANY"
### if ANY, then Subjects with Any on-treatment value >= Level 2 will be presented (ANL04FL/ANL05FL/ONTRTFL will be used here)
### if Last, then Subjects with Last on-treatment value >= Level 2 will be presented (LVOTFL will be used here)

## if the option TRTEMFL needs to be added to the TLF -- ensure the same setting as in tsflabxxxx
trtemfl <- TRUE

## parcat5 and 6 options :

availparcat56 <- c(
  "Investigations",
  "Metabolism and nutritional disorders",
  "Renal and urinary disorders",
  "Blood and lymphatic system disorders"
)

## resrict to some
selparcat56 <- availparcat56[c(1, 2, 4)]

## get all
selparcat56 <- availparcat56

# Initial processing of data

adlb_complete <- pharmaverseadamjnj::adlb

# Process lab toxicity file

lbtoxgrade_file <- file.path('../../_data', "lbtoxgrade.xlsx")
lbtoxgrade_sheets <- readxl::excel_sheets(path = lbtoxgrade_file)

### CTC5 or DAIDS21c : default CTC5

lbvars <- c("LBTESTCD", "LBTEST", "LBSPEC", "LBMETHOD")

lbtoxgrade_defs <- readxl::read_excel(lbtoxgrade_file, sheet = "CTC5")

lbtoxgrade_defs <- unique(
  unique(
    lbtoxgrade_defs %>%
      select(all_of(lbvars), TOXTERM, TOXGRD, INDICATR)
  ) %>%
    mutate(
      ATOXDSCLH = TOXTERM,
      ATOXGRLH = paste("Grade", TOXGRD)
    ) %>%
    rename(ATOXDIR = INDICATR) %>%
    select(all_of(lbvars), ATOXDSCLH, ATOXDIR)
)

# Initial processing of data

### be aware, there are toxicity terms that are based upon diff tests (example "Neutrophil Count Decreased": NEUT and NEUTSG) !!!!!
### if both tests are included in ADaM dataset, review your derivations carefully
attention_terms <-
  unique(lbtoxgrade_defs %>% select(ATOXDSCLH, all_of(lbvars))) %>%
  group_by(ATOXDSCLH) %>%
  mutate(n = n_distinct(LBTESTCD)) %>%
  filter(n > 1)

ad_toxterms <- bind_rows(
  unique(
    adlb_complete %>%
      select(PARAMCD, ATOXDSCL) %>%
      mutate(TOXTERM = ATOXDSCL, TOXDIR = "LOW")
  ),
  unique(
    adlb_complete %>%
      select(PARAMCD, ATOXDSCH) %>%
      mutate(TOXTERM = ATOXDSCH, TOXDIR = "HIGH")
  )
) %>%
  select(PARAMCD, TOXTERM, TOXDIR) %>%
  filter(!is.na(TOXTERM)) %>%
  arrange(TOXTERM, TOXDIR, PARAMCD)


attention_ad_toxterms <- ad_toxterms %>%
  group_by(TOXTERM) %>%
  mutate(n = n_distinct(PARAMCD)) %>%
  filter(n > 1)

#### From here onwards: avoid using PARAMCD, to ensure toxterm is combined

### could also work with param_lookup and lbtoxgrade_defs
### ALERT: do not include PARAMCD here as some toxicity terms are based on more than one PARAMCD: here : NEUT and NEUTSG both have TOXTERM = Neutrophil Count Decreased
toxterms <- unique(
  adlb_complete %>%
    filter(!(is.na(ATOXDSCL) & is.na(ATOXDSCH))) %>%
    ### do not include PARAMCD here!!!!
    select(ATOXDSCL, ATOXDSCH) %>%
    tidyr::pivot_longer(
      .,
      cols = c("ATOXDSCL", "ATOXDSCH"),
      names_to = "VARNAME",
      values_to = "ATOXDSCLH"
    )
) %>%
  filter(!is.na(ATOXDSCLH))

### convert dataframe into label_map that can be used with the a_freq_j afun function
xlabel_map <- toxterms %>%
  mutate(
    var = "ATOXGRLHx",
    value = "Y",
    label = as.character(ATOXDSCLH)
  ) %>%
  select(ATOXDSCLH, value, label)

# Process Data:

adsl <- pharmaverseadamjnj::adsl %>%
  filter(.data[[popfl]] == "Y") %>%
  select(STUDYID, USUBJID, all_of(c(popfl, trtvar)))

adsl$colspan_trt <- factor(
  ifelse(adsl[[trtvar]] == ctrl_grp, " ", "Active Study Agent"),
  levels = c("Active Study Agent", " ")
)

adsl$rrisk_header <- "Risk Difference (%) (95% CI)"
adsl$rrisk_label <- paste(adsl[[trtvar]], paste("vs", ctrl_grp))

colspan_trt_map <- create_colspan_map(
  adsl,
  non_active_grp = ctrl_grp,
  non_active_grp_span_lbl = " ",
  active_grp_span_lbl = "Active Study Agent",
  colspan_var = "colspan_trt",
  trt_var = trtvar
)

ref_path <- c("colspan_trt", " ", trtvar, ctrl_grp)

flagvars <- c("ONTRTFL", "TRTEMFL", "LVOTFL")
adlb00 <- adlb_complete %>%
  select(
    USUBJID,
    AVISITN,
    AVISIT,
    starts_with("PAR"),
    starts_with("ATOX"),
    starts_with("ANL"),
    all_of(flagvars),
    LBSEQ,
    AVAL,
    AVALC
  ) %>%
  inner_join(adsl) %>%
  mutate(
    ATOXGRL = as.character(ATOXGRL),
    ATOXGRH = as.character(ATOXGRH)
  ) %>%
  relocate(
    .,
    USUBJID,
    ANL04FL,
    ANL05FL,
    ONTRTFL,
    TRTEMFL,
    AVISIT,
    ATOXGRL,
    ATOXGRH,
    ATOXDSCL,
    ATOXDSCH,
    PARAMCD,
    AVISIT,
    AVAL
  )


# adlb00 <- adlb00 #%>%
## APT comment on PARCAT6 :
## HGB and WBC : Set to "Blood and lymphatic system disorders".
## HGB and WBC parameter are in 2 categories, one for the high and another one for the low direction grading.
## Anemia (HGB low) and Leukocytosis (WBC high) are in the category "Blood and lymphatic system disorders".
## The grading in the opposite directions are categorized under "Investigations".
## Therefor, both PARCAT5 and PARCAT6 are populated for HGB abd WBC.
## Deal with what is needed at later level, when we have splitted low and high

# obj_label(adlb00$PARCAT56) <- "Combined PARCAT56"

### important: previous actions lost the label of variables

adlb00 <- var_relabel_list(adlb00, var_labels(adlb_complete, fill = T))

if (all(selparcat56 != "")) {
  filtered_adlb <- adlb00 %>%
    filter((PARCAT5 %in% selparcat56) | (PARCAT6 %in% selparcat56))
} else {
  filtered_adlb <- adlb00
}

### low grades : ATOXDSCL ATOXGRL ANL04FL
filtered_adlb_low <- filtered_adlb %>%
  filter(!is.na(ATOXDSCL) & !is.na(ATOXGRL)) %>%
  mutate(
    ATOXDSCLH = ATOXDSCL,
    ATOXGRLH = ATOXGRL,
    ATOXDIR = "LOW",
    ANL045FL = ANL04FL
  ) %>%
  select(
    USUBJID,
    starts_with("PAR"),
    starts_with("ATOX"),
    all_of(flagvars),
    ANL04FL,
    ANL05FL,
    ANL045FL,
    LBSEQ,
    AVAL,
    AVALC
  ) %>%
  select(-c(ATOXGRL, ATOXGRH, ATOXDSCL, ATOXDSCH))

### high grades: ATOXDSCH ATOXGRH ANL05FL
filtered_adlb_high <- filtered_adlb %>%
  filter(ANL05FL == "Y" & !is.na(ATOXDSCH) & !is.na(ATOXGRH)) %>%
  mutate(
    ATOXDSCLH = ATOXDSCH,
    ATOXGRLH = ATOXGRH,
    ATOXDIR = "HIGH",
    ANL045FL = ANL05FL
  ) %>%
  select(
    USUBJID,
    starts_with("PAR"),
    starts_with("ATOX"),
    all_of(flagvars),
    ANL04FL,
    ANL05FL,
    ANL045FL,
    LBSEQ,
    AVAL,
    AVALC
  ) %>%
  select(-c(ATOXGRL, ATOXGRH, ATOXDSCL, ATOXDSCH))


## combine Low and high into adlb_tox
filtered_adlb_tox <-
  bind_rows(
    filtered_adlb_low,
    filtered_adlb_high
  ) %>%
  select(-c(ATOXGR, ATOXGRN)) %>%
  mutate(ATOXGRLHN = as.numeric(ATOXGRLH)) %>%
  inner_join(adsl)


### correction of proper category (PARCAT56) for HGB (LOW) and WBC (HIGH)
filtered_adlb_tox <-
  filtered_adlb_tox %>%
  mutate(
    PARCAT56 = case_when(
      PARAMCD == "HGB" & ATOXDIR == "LOW" ~ PARCAT6,
      PARAMCD == "WBC" & ATOXDIR == "HIGH" ~ PARCAT6,
      TRUE ~ PARCAT5
    )
  ) %>%
  mutate(
    PARCAT56 = factor(
      PARCAT56,
      levels = unique(c(
        "Blood and lymphatic system disorders",
        levels(adlb_complete$PARCAT5)
      ))
    )
  )


filtered_adlb_tox <- unique(
  filtered_adlb_tox
)

filtered_adlb_tox_1 <- filtered_adlb_tox # %>%
# ## On treatment
# filter(ONTRTFL == "Y")

### Note on On-treatment
### note: by filter ANL04FL/ANL05FL, this table is restricted to On-treatment values, per definition of ANL04FL/ANL05FL
### Same for LVOTFL
### therefor, no need to add ONTRTFL in filter
### if derivation of ANL04FL/ANL05FL/LVOTFL is not restricted to ONTRTFL records, adding ONTRTFL here will not give the correct answer either
### as mixing worst with other period is not giving the proper selection !!!

if (toupper(last_any) == "ANY") {
  filtered_adlb_tox_1 <- filtered_adlb_tox_1 %>%
    ## Optional : Any : ensure to have one record per subject for direction
    filter(ANL04FL == "Y" | ANL05FL == "Y")
}

if (toupper(last_any) == "LAST") {
  filtered_adlb_tox_1 <- filtered_adlb_tox_1 %>%
    ## Optional : last on treatment record only
    filter(LVOTFL == "Y")
}


#### DO NOT USE TRTEMFL = Y in filter, as this will remove subjects from both numerator and denominator
#### instead : set ATOXGRLH to a non-reportable value (ie Grade 0) and keep in dataset
if (trtemfl) {
  filtered_adlb_tox_1 <- filtered_adlb_tox_1 %>%
    mutate(
      ATOXGRLHN = case_when(
        is.na(TRTEMFL) | TRTEMFL != "Y" ~ 0,
        TRUE ~ ATOXGRLHN
      )
    )
}


### Alphabetical sorting of toxicity terms
atoxdsclh_levels <- sort(as.character(unique(filtered_adlb_tox_1$ATOXDSCLH)))

filtered_adlb_tox_1 <- filtered_adlb_tox_1 %>%
  mutate(
    ATOXGRLHx = case_when(
      ATOXGRLHN >= as.numeric(grade_threshold) ~ "Y",
      TRUE ~ "N"
    )
  ) %>%
  mutate(ATOXGRLHx = factor(ATOXGRLHx, levels = c("Y", "N"))) %>%
  mutate(ATOXDSCLH = factor(ATOXDSCLH, levels = atoxdsclh_levels))


# check uniqueness
check_non_unique_subject <- filtered_adlb_tox_1 %>%
  group_by(USUBJID, ATOXDSCLH) %>%
  mutate(n_subject = n()) %>%
  filter(n_subject > 1)

if (nrow(check_non_unique_subject)) {
  message(
    "Please review your data selection process, subject has multiple records"
  )
}

### syntethic data: no records for NEUT/NEUTSG for the further selection (ATOXGRL is never populated for these records)
xx <- adlb00 %>%
  filter(ATOXDSCL == "Neutrophil Count Decreased" & !is.na(ATOXGRL))

# Define layout and build table:

extra_args_rr <- list(
  method = "wald",
  denom = "n_df",
  .stats = c("count_unique_denom_fraction"),
  ref_path = ref_path
)


lyt <- basic_table(show_colcounts = TRUE, colcount_format = "N=xx") %>%
  ### first columns
  split_cols_by(
    "colspan_trt",
    split_fun = trim_levels_to_map(map = colspan_trt_map)
  ) %>%
  split_cols_by(trtvar) %>%
  split_cols_by("rrisk_header", nested = FALSE) %>%
  split_cols_by(
    trtvar,
    labels_var = "rrisk_label",
    split_fun = remove_split_levels(ctrl_grp)
  ) %>%
  split_rows_by(
    "PARCAT56",
    label_pos = "topleft",
    child_labels = "visible",
    split_label = "Laboratory Category",
    split_fun = drop_split_levels,
    section_div = " "
  ) %>%
  split_rows_by(
    "ATOXDSCLH",
    label_pos = "topleft",
    split_label = paste0(
      "Laboratory Test \u2265 Grade ",
      grade_threshold,
      ", n (%)"
    ),
    child_labels = "hidden",
    split_fun = drop_split_levels
  ) %>%
  analyze(
    "ATOXGRLHx",
    afun = a_freq_j,
    extra_args = append(
      extra_args_rr,
      list(
        val = c("Y"),
        label_map = xlabel_map
      )
    ),
    show_labels = "hidden",
    indent_mod = 0L
  )

result <- build_table(lyt, filtered_adlb_tox_1, alt_counts_df = adsl)

# Post-Processing:

### Issue: tests with only 1 direction (either low or high) get a line with label a_freq_j (analyze function)
### remove these lines here

result <- result %>% prune_table(prune_func = keep_rows(keep_non_null_rows))

# Remove colcount from rrisk_header:

result <- remove_col_count(result)

# Add titles and footnotes:

result <- set_titles(result, titles)

# Convert to tbl file and output table

tt_to_tlgrtf(string_map = string_map, tt = result, file = fileid, orientation = "landscape")
```
```{r result1, echo=FALSE, message=FALSE, warning=FALSE, test = list(result_v1 = "result")}
tt_to_flextable_j(result, tblid, string_map = string_map) 
```

[Download RTF file](`r paste0(tolower(tblid), '.rtf')`)
::::

Made with ❤️ by the J&J Team

  • Edit this page
  • Report an issue
Cookie Preferences