knitr::opts_chunk$set( collapse = TRUE, comment = "#>" ) library(admiral) link <- function(text, url) { return( paste0( "[", text, "]", "(", url, ")" ) ) } dyn_link <- function(text, base_url, relative_url = "", # Change to TRUE when admiral adopts multiversion docs is_multiversion = FALSE, multiversion_default_ref = "main") { url <- paste(base_url, relative_url, sep = "/") if (is_multiversion) { url <- paste( base_url, Sys.getenv("BRANCH_NAME", multiversion_default_ref), relative_url, sep = "/" ) } return(link(text, url)) } # Other variables admiral_homepage <- "https://pharmaverse.github.io/admiral"
This article describes how to create an ADIS
ADaM domain.
The parameters derived reflects common vaccine immunogenicity
endpoints.
Examples are currently presented and tested using ADSL
(ADaM) and
IS
and SUPPIS
(SDTM) inputs.
Note: All examples assume CDISC SDTM and/or ADaM format as input unless otherwise specified.
In this first step you may read all the input data you need in order to proceed with
ADIS development.
In this template, SDTM.IS
, SDTM.SUPPIS
and ADAM.ADSL
has been used.
library(admiral) library(dplyr) library(lubridate) library(admiraldev) library(admiralvaccine) library(pharmaversesdtm) library(metatools) library(pharmaversesdtm) # Load source datasets data("is_vaccine") data("suppis_vaccine") data("admiralvaccine_adsl") # Convert blanks into NA is <- convert_blanks_to_na(is_vaccine) suppis <- convert_blanks_to_na(suppis_vaccine) adsl <- convert_blanks_to_na(admiralvaccine_adsl)
Combine IS
with its supplemental domain SUPPIS
.
is_suppis <- metatools::combine_supp(is, suppis)
Derive AVISIT
, AVISITN
, ATPT
, ATPTN
and ATPTREF
variables.
Please, update visit records according to your Study Design/Protocol.
For the visit values, please refers to your ADAM SPECIFICATIONS.
adis <- is_suppis %>% mutate( AVISITN = as.numeric(VISITNUM), AVISIT = case_when( VISITNUM == 10 ~ "Visit 1", VISITNUM == 20 ~ "Visit 2", VISITNUM == 30 ~ "Visit 3", VISITNUM == 40 ~ "Visit 4", is.na(VISITNUM) ~ NA_character_ ), ATPTN = as.numeric(VISITNUM / 10), ATPT = case_when( VISITNUM == 10 ~ "Visit 1 (Day 1)", VISITNUM == 20 ~ "Visit 2 (Day 31)", VISITNUM == 30 ~ "Visit 3 (Day 61)", VISITNUM == 40 ~ "Visit 4 (Day 121)", is.na(VISITNUM) ~ NA_character_ ), ATPTREF = case_when( VISITNUM %in% c(10, 20) ~ "FIRST TREATMENT", VISITNUM %in% c(30, 40) ~ "SECOND TREATMENT", is.na(VISITNUM) ~ NA_character_ ) )
dataset_vignette( adis, display_vars = exprs(USUBJID, VISITNUM, ISTEST, ISORRES, AVISIT, AVISITN, ATPT, ATPTN, ATPTREF) )
For ADT
derivation, please follow your imputation rules.
In the example below:
when day is missing then 15 is imputed;
When both day and month are missing then 30-06 is imputed;
If input date is missing then no imputation is done;
For ADY
derivation RFSTDTC
has been used in this template.
If your derivation is different, please adapt.
# ADT derivation # Add also PPROTFL from ADSL (to avoid additional merges) in order to derive # PPSRFL at step 11. adis <- derive_vars_dt( dataset = adis, new_vars_prefix = "A", dtc = ISDTC, highest_imputation = "M", date_imputation = "mid", flag_imputation = "none" ) %>% derive_vars_merged( dataset_add = adsl, new_vars = exprs(RFSTDTC, PPROTFL), by_vars = get_admiral_option("subject_keys") ) %>% mutate( ADT = as.Date(ADT), RFSTDTC = as.Date(RFSTDTC) ) %>% # ADY derivation derive_vars_dy( reference_date = RFSTDTC, source_vars = exprs(ADT) )
dataset_vignette( adis, display_vars = exprs(USUBJID, VISITNUM, ISTEST, ISORRES, ISDTC, RFSTDTC, ADT, ADY, PPROTFL) )
In this template, duplicated records for PARAMCD
have been created.
In particular, you may find 4 different parameters values:
Original values and relative log10 values;
4fold values and relative log10 values;
Please, add or remove datasets according to your study needs.
# Create record duplication in order to plot both original and LOG10 parameter values. # Add also records related to 4fold. # Please, keep or modify PARAM values according to your purposes. is_log <- adis %>% mutate( DERIVED = "LOG10", ISSEQ = NA_real_ ) is_4fold <- adis %>% mutate( DERIVED = "4FOLD", ISSEQ = NA_real_ ) is_log_4fold <- adis %>% mutate( DERIVED = "LOG10 4FOLD", ISSEQ = NA_real_ ) adis <- bind_rows(adis, is_log, is_4fold, is_log_4fold) %>% arrange(STUDYID, USUBJID, !is.na(DERIVED), ISSEQ) %>% mutate(DERIVED = if_else(is.na(DERIVED), "ORIG", DERIVED)) adis <- adis %>% mutate( # PARAMCD: for log values, concatenation of L and ISTESTCD. PARAMCD = case_when( DERIVED == "ORIG" ~ ISTESTCD, DERIVED == "LOG10" ~ paste0(ISTESTCD, "L"), DERIVED == "4FOLD" ~ paste0(ISTESTCD, "F"), # As per CDISC rule, PARAMCD should be 8 characters long. Please, adapt if needed DERIVED == "LOG10 4FOLD" ~ paste0(substr(ISTESTCD, 1, 6), "LF") ) ) # Update param_lookup dataset with your PARAM values. param_lookup <- tribble( ~PARAMCD, ~PARAM, ~PARAMN, "J0033VN", "J0033VN Antibody", 1, "I0019NT", "I0019NT Antibody", 2, "M0019LN", "M0019LN Antibody", 3, "R0003MA", "R0003MA Antibody", 4, "J0033VNL", "LOG10 (J0033VN Antibody)", 11, "I0019NTL", "LOG10 (I0019NT Antibody)", 12, "M0019LNL", "LOG10 (M0019LN Antibody)", 13, "R0003MAL", "LOG10 (R0003MA Antibody)", 14, "J0033VNF", "4FOLD (J0033VN Antibody)", 21, "I0019NTF", "4FOLD (I0019NT Antibody)", 22, "M0019LNF", "4FOLD (M0019LN Antibody)", 23, "R0003MAF", "4FOLD (R0003MA Antibody)", 24, "J0033VLF", "LOG10 4FOLD (J0033VN Antibody)", 31, "I0019NLF", "LOG10 4FOLD (I0019NT Antibody)", 32, "M0019LLF", "LOG10 4FOLD (M0019LN Antibody)", 33, "R0003MLF", "LOG10 4FOLD (R0003MA Antibody)", 34 ) adis <- derive_vars_merged_lookup( dataset = adis, dataset_add = param_lookup, new_vars = exprs(PARAM, PARAMN), by_vars = exprs(PARAMCD) )
dataset_vignette( adis, display_vars = exprs(USUBJID, VISITNUM, ISTEST, ISORRES, PARAMCD, PARAM, PARAMN) )
Derive PARCAT1
and CUTOFF
x variables.
Fake values has been put for CUTOFF
values. Please, adapt base on your objectives.
adis <- adis %>% mutate( PARCAT1 = ISCAT, # Please, define your additional cutoff values. Delete if not needed. CUTOFF02 = 4, CUTOFF03 = 8 )
dataset_vignette( adis, display_vars = exprs(USUBJID, VISITNUM, ISTEST, ISORRES, PARCAT1, CUTOFF02, CUTOFF03) )
This is the core of ADIS template.
For ORIGINAL (and relative log10 values) the following rule has been followed for AVAL
derivation:
When the lab result (ISSTRESN
) is below the Lower Limit Of Quantitation, then set ISSTRESN/2
;
When the lab result (ISSTRESN
) falls in the Lower Limit Of Quantitation and Upper
Limit Of Quantitation range, then set ISSTRESN
. If Upper Limit Of Quantitation is not
present (not mapped into SDTM), then AVAL is equals to ISSTRESN
when it is greater
than Lower Limit Of Quantitation;
When the lab result (ISSTRESN
) is greater then the Upper Limit Of Quantitation,
then set to ISSTRESN
. Upper_rule is an optional argument. If Upper Limit Of Quantitation is
not present, you can remove it;
For 4fold (and relative log10 values) the rule is pretty the same, except when the
LAB result (ISSTRESN
) is lower than the Lower Limit Of Quantitation.
In that case put ISSTRESN
instead of ISSTRESN/2
.
With log10 transformations, simply follow the before rules and apply log10 function.
Please, update this algorithm according to your Protocol/SAP.
AVALU
is set equal to IS.ISSTRESU
.
Later you can find SERCAT1/N
and DTYPE
derivations.
DTYPE
is filled only for those records who exceed or are below the ISULOQ
and
ISSLOQ
, respectively. If ISULOQ
is not present, DTYPE
is filled only when lab
result is below Lower Limit of Quantitation.
adis_or <- adis %>% filter(DERIVED == "ORIG") %>% derive_var_aval_adis( lower_rule = ISLLOQ / 2, middle_rule = ISSTRESN, upper_rule = ISULOQ, round = 2 ) adis_log_or <- adis %>% filter(DERIVED == "LOG10") %>% derive_var_aval_adis( lower_rule = log10(ISLLOQ / 2), middle_rule = log10(ISSTRESN), upper_rule = log10(ISULOQ), round = 2 ) adis_4fold <- adis %>% filter(DERIVED == "4FOLD") %>% derive_var_aval_adis( lower_rule = ISLLOQ, middle_rule = ISSTRESN, upper_rule = ISULOQ, round = 2 ) adis_log_4fold <- adis %>% filter(DERIVED == "LOG10 4FOLD") %>% derive_var_aval_adis( lower_rule = log10(ISLLOQ), middle_rule = log10(ISSTRESN), upper_rule = log10(ISULOQ), round = 2 ) adis <- bind_rows(adis_or, adis_log_or, adis_4fold, adis_log_4fold) %>% mutate( # AVALU derivation (please delete if not needed for your study) AVALU = ISSTRESU, # SERCAT1 derivation SERCAT1 = case_when( ISBLFL == "Y" & !is.na(AVAL) & !is.na(ISLLOQ) & AVAL < ISLLOQ ~ "S-", ISBLFL == "Y" & !is.na(AVAL) & !is.na(ISLLOQ) & AVAL >= ISLLOQ ~ "S+", ISBLFL == "Y" & (is.na(AVAL) | is.na(ISLLOQ)) ~ "UNKNOWN" ) ) # Update param_lookup2 dataset with your SERCAT1N values. param_lookup2 <- tribble( ~SERCAT1, ~SERCAT1N, "S-", 1, "S+", 2, "UNKNOWN", 3, NA_character_, NA_real_ ) adis <- derive_vars_merged_lookup( dataset = adis, dataset_add = param_lookup2, new_vars = exprs(SERCAT1N), by_vars = exprs(SERCAT1) ) # DTYPE derivation. # Please update code when <,<=,>,>= are present in your lab results (in ISSTRESC) if (any(names(adis) == "ISULOQ") == TRUE) { adis <- adis %>% mutate(DTYPE = case_when( DERIVED %in% c("ORIG", "LOG10") & !is.na(ISLLOQ) & ((ISSTRESN < ISLLOQ) | grepl("<", ISORRES)) ~ "HALFLLOQ", DERIVED %in% c("ORIG", "LOG10") & !is.na(ISULOQ) & ((ISSTRESN > ISULOQ) | grepl(">", ISORRES)) ~ "ULOQ", TRUE ~ NA_character_ )) } if (any(names(adis) == "ISULOQ") == FALSE) { adis <- adis %>% mutate(DTYPE = case_when( DERIVED %in% c("ORIG", "LOG10") & !is.na(ISLLOQ) & ((ISSTRESN < ISLLOQ) | grepl("<", ISORRES)) ~ "HALFLLOQ", TRUE ~ NA_character_ )) }
dataset_vignette( adis, display_vars = exprs(USUBJID, VISITNUM, ISTEST, ISORRES, AVAL, AVALU, DTYPE, SERCAT1, SERCAT1N) )
Derive Baseline values for each Subject/Visit and relative flag, ABLFL
.
In a later stage, derive BASECAT
variable, which represents the base category.
Update accordingly.
# ABLFL derivation adis <- restrict_derivation( adis, derivation = derive_var_extreme_flag, args = params( by_vars = exprs(STUDYID, USUBJID, PARAMN), order = exprs(STUDYID, USUBJID, VISITNUM, PARAMN), new_var = ABLFL, mode = "first" ), filter = VISITNUM == 10 ) %>% # BASE derivation derive_var_base( by_vars = exprs(STUDYID, USUBJID, PARAMN), source_var = AVAL, new_var = BASE, filter = ABLFL == "Y" ) %>% # BASETYPE derivation derive_basetype_records( basetypes = exprs("VISIT 1" = AVISITN %in% c(10, 30)) ) %>% arrange(STUDYID, USUBJID, !is.na(DERIVED), ISSEQ) # BASECAT derivation adis <- adis %>% mutate( BASECAT1 = case_when( !grepl("L", PARAMCD) & BASE < 10 ~ "Titer value < 1:10", !grepl("L", PARAMCD) & BASE >= 10 ~ "Titer value >= 1:10", grepl("L", PARAMCD) & BASE < 10 ~ "Titer value < 1:10", grepl("L", PARAMCD) & BASE >= 10 ~ "Titer value >= 1:10" ) )
dataset_vignette( adis, display_vars = exprs(USUBJID, VISITNUM, ISTEST, ISORRES, ABLFL, BASE, BASETYPE, BASECAT1) )
Derive change from baseline values.
Derive ratio to base values.
adis <- restrict_derivation(adis, derivation = derive_var_chg, filter = AVISITN > 10 ) %>% restrict_derivation( derivation = derive_var_analysis_ratio, args = params( numer_var = AVAL, denom_var = BASE ), filter = AVISITN > 10 ) %>% arrange(STUDYID, USUBJID, DERIVED, ISSEQ)
dataset_vignette( adis, display_vars = exprs(USUBJID, VISITNUM, ISTEST, ISORRES, CHG, R2BASE) )
Derive Criteria Evaluation Analysis Flags.
The function selects a subset of rows from the input dataset and apply a criterion to them.
If this criterion is met then CRIT1FL
(or the name you specified in the first argument)
is equal to Y
; N
otherwise.
The function returns a relative numeric CRIT1FN
variable (1
or 0
if the
criterion is met, respectively) and a label CRIT1
variable
(with the text specified in label_var argument).
adis <- derive_vars_crit( dataset = adis, prefix = "CRIT1", crit_label = "Titer >= ISLLOQ", condition = !is.na(AVAL) & !is.na(ISLLOQ), criterion = AVAL >= ISLLOQ )
dataset_vignette( adis, display_vars = exprs(USUBJID, VISITNUM, ISTEST, ISORRES, CRIT1, CRIT1FL, CRIT1FN) )
period_ref <- create_period_dataset( dataset = adsl, new_vars = exprs(APERSDT = APxxSDT, APEREDT = APxxEDT, TRTA = TRTxxA, TRTP = TRTxxP) ) adis <- derive_vars_joined( adis, dataset_add = period_ref, by_vars = get_admiral_option("subject_keys"), filter_join = ADT >= APERSDT & ADT <= APEREDT, join_type = "all" )
dataset_vignette( adis, display_vars = exprs(USUBJID, VISITNUM, ISTEST, ISORRES, TRTP, TRTA) )
This is a record level flag which identifies which rows are included/excluded for the PPS related objectives.
This step could change according to your study needs.
adis <- adis %>% mutate(PPSRFL = if_else(VISITNUM %in% c(10, 30) & PPROTFL == "Y", "Y", NA_character_))
dataset_vignette( adis, display_vars = exprs(USUBJID, VISITNUM, ISTEST, ISORRES, TRTP, TRTA) )
Attach all ADAM.ADSL
variables to the is build-in dataset.
If you may need to keep only a subset of them, please update accordingly.
# Get list of ADSL variables not to be added to ADIS vx_adsl_vars <- exprs(RFSTDTC, PPROTFL) adis <- derive_vars_merged( dataset = adis, dataset_add = select(adsl, !!!negate_vars(vx_adsl_vars)), by_vars = get_admiral_option("subject_keys") )
dataset_vignette( adis, display_vars = exprs(USUBJID, VISITNUM, ISTEST, ISORRES, AGE, COUNTRY, ARM, ACTARM) )
ADaM | Sample Code ---- | -------------- ADIS | ad_adis.R{target="_blank"}
Any scripts or data that you put into this service are public.
Add the following code to your website.
For more information on customizing the embed code, read Embedding Snippets.