diff --git a/.gitignore b/.gitignore index 91544cf9..ec17d0c2 100644 --- a/.gitignore +++ b/.gitignore @@ -7,4 +7,5 @@ inst/guidelines inst/templates inst/shiny/data !inst/shiny/data/DummyRO_ADNCA.csv +!inst/shiny/data/adnca_labels.csv .Rprofile \ No newline at end of file diff --git a/NAMESPACE b/NAMESPACE index b77cde10..32c78d52 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -2,6 +2,7 @@ export(anonymize_pk_data) export(apply_filters) +export(apply_labels) export(as_factor_preserve_label) export(calculate_summary_stats) export(create_conc) diff --git a/R/label_operators.R b/R/label_operators.R index 09a64729..b2723926 100644 --- a/R/label_operators.R +++ b/R/label_operators.R @@ -1,3 +1,48 @@ +#' Apply Labels to a dataset +#' +#' This function adds "label" attributes to all columns in a dataset +#' +#' @param data The dataset to which labels will be applied. +#' @param labels_file A data frame with two columns: Variable and Label, +#' for the dataset you are applying it . +#' +#' @return The same dataset with label attributes applied to all columns. +#' If a column is not present in the labels list, it will be assigned the name of the col. +#' +#' @examples +#' \dontrun{ +#' # Example usage: +#' data <- data.frame(USUBJID = c(1, 2, 3), AVAL = c(4, 5, 6)) +#' labels <- data.frame( +#' Variable = c("USUBJID", "AVAL"), +#' Label = c("Unique Subject Identifier", "Analysis Value") +#' ) +#' data <- apply_labels(data, labels) +#' print(attr(data$A, "label")) +#' } +#' +#' @export +apply_labels <- function(data, labels_file) { + + # Create the label_ADNCA named vector from labels_app + label_adnca <- setNames(labels_file$Label, labels_file$Variable) + + for (col in colnames(data)) { + if (col %in% names(label_adnca)) { + attr(data[[col]], "label") <- label_adnca[[col]] + } else { + attr(data[[col]], "label") <- col + } + + # Check if the column is a factor and keep the levels order + if (is.factor(data[[col]])) { + data[[col]] <- as_factor_preserve_label(data[[col]]) + } + } + + data +} + #' Convert to Factor While Preserving Label #' #' This function converts a vector to a factor while preserving its "label" attribute. diff --git a/inst/WORDLIST b/inst/WORDLIST index 548d118c..f9d236b2 100644 --- a/inst/WORDLIST +++ b/inst/WORDLIST @@ -1,4 +1,5 @@ ADNCA +ADPC ADPP AFRLT AUClast @@ -25,8 +26,8 @@ analyte analytes anonymized anonymizes -cheatsheet cmax +codebase csv customizable ggplot @@ -36,12 +37,13 @@ pknca plotly pptest pre +reactable reupload ruleset rulesets sas summarization timepoint +tooltip visualizable xpt -codebase diff --git a/inst/shiny/data/adnca_labels.csv b/inst/shiny/data/adnca_labels.csv new file mode 100644 index 00000000..1d375b8c --- /dev/null +++ b/inst/shiny/data/adnca_labels.csv @@ -0,0 +1,343 @@ +Variable,Label,Dataset +STUDYID,Study Identifier,ADPC +USUBJID,Unique Subject Identifier,ADPC +SUBJID,Subject Identifier for the Study,ADPC +SITEID,Study Site Identifier,ADPC +ASEQ,Analysis Sequence Number,ADPC +REGION1,Geographic Region 1,ADPC +COUNTRY,Country,ADPC +ETHNIC,Ethnicity,ADPC +AGE,Age,ADPC +AGEU,Age Units,ADPC +AAGE,Analysis Age,ADPC +AAGEU,Analysis Age Unit,ADPC +AGEGR1,Pooled Age Group 1,ADPC +AGEGR2,Pooled Age Group 2,ADPC +AGEGR3,Pooled Age Group 3,ADPC +STRATwNM,Description of Stratum w,ADPC +STRATw,Randomized Value of Stratum w,ADPC +STRATwV,Verified Value of Stratum w,ADPC +SEX,Sex,ADPC +RACE,Race,ADPC +ITTFL,Intent-To-Treat Population Flag,ADPC +SAFFL,Safety Population Flag,ADPC +PPROTFL,Per-Protocol Population Flag,ADPC +TRT01P,Planned Treatment for Period 01,ADPC +TRT02P,Planned Treatment for Period 02,ADPC +TRT03P,Planned Treatment for Period 03,ADPC +TRT04P,Planned Treatment for Period 04,ADPC +TRT05P,Planned Treatment for Period 05,ADPC +TRT01A,Actual Treatment for Period 01,ADPC +TRT02A,Actual Treatment for Period 02,ADPC +TRT03A,Actual Treatment for Period 03,ADPC +TRT04A,Actual Treatment for Period 04,ADPC +TRT05A,Actual Treatment for Period 05,ADPC +TRTSEQP,Planned Sequence of Treatments,ADPC +TRTSEQA,Actual Sequence of Treatments,ADPC +TRTSDTM,Datetime of First Exposure to Treatment,ADPC +TRTSDT,Date of First Exposure to Treatment,ADPC +TRTEDTM,Datetime of Last Exposure to Treatment,ADPC +TRTEDT,Date of Last Exposure to Treatment,ADPC +DCUTDT,Date of Data Cut,ADPC +PCSEQ,Sequence Number,ADPC +PCGRPID,Group ID,ADPC +PCREFID,Reference ID,ADPC +PCSPID,Sponsor-Defined Identifier,ADPC +PCTESTCD,Pharmacokinetic Test Short Name,ADPC +PCTEST,Pharmacokinetic Test Name,ADPC +PCCAT,Test Category,ADPC +PCSCAT,Test Subcategory,ADPC +PCSTRESC,Character Result/Finding in Std Format,ADPC +PCSTRESN,Numeric Result/Finding in Standard Units,ADPC +PCSTRESU,Standard Units,ADPC +PCSTAT,Completion Status,ADPC +PCREASND,Reason Test Not Done,ADPC +PCSPEC,Specimen Material Type,ADPC +PCSPCCND,Specimen Condition,ADPC +PCMETHOD,Method of Test or Examination,ADPC +PCFAST,Fasting Status,ADPC +PCLLOQ,Lower Limit of Quantitation,ADPC +VISITNUM,Visit Number,ADPC +VISIT,Visit Name,ADPC +VISITDY,Planned Study Day of Visit,ADPC +EPOCH,Epoch,ADPC +PCDTC,Date/Time of Specimen Collection,ADPC +PCDY,Actual Study Day of Specimen Collection,ADPC +PCTPT,Planned Time Point Name,ADPC +PCTPTNUM,Planned Time Point Number,ADPC +PCSMPLID,Alternate Sample Identifier,ADPC +PCAINTP,Assay Interpretation,ADPC +PARAM,Parameter,ADPC +PARAMCD,Parameter Code,ADPC +PARCAT1,Parameter Category 1,ADPC +AVAL,Analysis Value,ADPC +AVALCAT1,Analysis Value Category 1,ADPC +AVALU,Analysis Value Unit,ADPC +AVALU,Analysis Value Unit,ADPC +BASE,Baseline Value,ADPC +BASETYPE,Baseline Type,ADPC +ABLFL,Baseline Record Flag,ADPC +ALLOQ,Analysis Lower Limit of Quantitation,ADPC +ADTM,Analysis Datetime,ADPC +ADT,Analysis Date,ADPC +ATM,Analysis Time,ADPC +ADY,Analysis Relative Day,ADPC +ADTF,Analysis Date Imputation Flag,ADPC +ATMF,Analysis Time Imputation Flag,ADPC +ASTDT,Analysis Start Date,ADPC +ASTTM,Analysis Start Time,ADPC +ASTDTM,Analysis Start Date/Time,ADPC +ASTDTF,Analysis Start Date Imputation Flag,ADPC +ASTTMF,Analysis Start Time Imputation Flag,ADPC +AENDT,Analysis End Date,ADPC +AENTM,Analysis End Time,ADPC +AENDTM,Analysis End Date/Time,ADPC +AENDTF,Analysis End Date Imputation Flag,ADPC +AENTMF,Analysis End Time Imputation Flag,ADPC +ATPT,Analysis Timepoint,ADPC +ATPT,Analysis Timepoint,ADPC +ATPTN,Analysis Timepoint (N),ADPC +ATPTN,Analysis Timepoint (N),ADPC +ATPTREF,Analysis Timepoint Reference,ADPC +AVISIT,Analysis Visit,ADPC +AVISIT,Analysis Visit,ADPC +AVISITN,Analysis Visit (N),ADPC +AVISITN,Analysis Visit (N),ADPC +APERIOD,Period,ADPC +APERIODC,Period (C),ADPC +FANLDT,First Date of Dose for Analyte,ADPC +FANLTM,First Time of Dose for Analyte,ADPC +FANLDTM,First Datetime of Dose for Analyte,ADPC +FANLDTMF,First Time of Dose Time Imputation Flag,ADPC +FANLEDT,First End Date of Dose for Analyte,ADPC +FANLETM,First End Time of Dose for Analyte,ADPC +FANLEDTM,First End Datetime of Dose for Analyte,ADPC +FANLEDTF,First End of Dose Time Imputation Flag,ADPC +PCRFTDT,Reference Date of Dose for Analyte,ADPC +PCRFTTM,Reference Time of Dose for Analyte,ADPC +PCRFTDTM,Reference Datetime of Dose for Analyte,ADPC +PCRFEDT,Reference End Date of Dose for Analyte,ADPC +PCRFETM,Reference End Time of Dose for Analyte,ADPC +PCRFEDTM,Ref. End Datetime of Dose for Analyte,ADPC +NFRLT,Nom. Rel. Time from Analyte First Dose,ADPC +AFRLT,Act. Rel. Time from Analyte First Dose,ADPC +TMPCTDF,Percent Diff. Nominal vs. Actual Time,ADPC +FRLTU,Rel. Time from First Dose Unit,ADPC +NEFRLT,Nom. Rel. End Time from First Dose,ADPC +AEFRLT,Act. Rel. End Time from First Dose,ADPC +NRRLT,Nominal Rel. Time from Ref. Dose,ADPC +ARRLT,Actual Rel. Time from Ref. Dose,ADPC +MRRLT,Modified Rel. Time from Ref. Dose,ADPC +RRLTU,Rel. Time from Ref. Dose Unit,ADPC +NERRLT,Nominal Rel. End Time from Ref. Dose,ADPC +NERRLT,Nominal Rel. End Time from Ref. Dose,ADPC +AERRLT,Actual Rel. End Time from Ref. Dose,ADPC +AERRLT,Actual Rel. End Time from Ref. Dose,ADPC +MERRLT,Modified Rel. End Time from Ref. Dose,ADPC +MERRLT,Modified Rel. End Time from Ref. Dose,ADPC +CHG,Change from Baseline,ADPC +CRIT1,Analysis Criterion 1,ADPC +CRIT1FL,Criterion 1 Evaluation Result Flag,ADPC +CRIT1FL,Criterion 1 Evaluation Result Flag,ADPC +DTYPE,Derivation Type,ADPC +SPARSFL,Sparse Flag,ADPC +NCAXFL,PK NCA Exclusion Flag,ADPC +NCAXFN,PK NCA Exclusion Flag (N),ADPC +NCAwXRS,Reason w for PK NCA Exclusion,ADPC +NCAwXRSN,Reason for PK NCA Exclusion of w (N),ADPC +PKSUMXF,PK Summary Exclusion Flag,ADPC +PKSUMXFN,PK Summary Exclusion Flag (N),ADPC +METABFL,Metabolite Flag,ADPC +COHORT,Subject Cohort,ADPC +COHORTN,Subject Cohort (N),ADPC +ROUTE,Route,ADPC +TRTRINT,Planned Treatment Interval,ADPC +TRTRINTU,Planned Treatment Interval Units,ADPC +DOSPCTDF,Percent Diff. Nominal vs. Actual Dose,ADPC +DOSEFRQ,Dose Frequency,ADPC +DOSEP,Planned Treatment Dose,ADPC +DOSEA,Actual Treatment Dose,ADPC +DOSEPU,Planned Treatment Dose Units,ADPC +DOSEAU,Actual Treatment Dose Units,ADPC +ACYCLE,Analysis Cycle,ADPC +ACYCLEC,Analysis Cycle (C),ADPC +ADOSEDUR,Actual Duration of Treatment Dose,ADPC +NDOSEDUR,Nominal duration of Treatment Dose,ADPC +DOSEDURU,Duration of Treatment Dose Units,ADPC +VOLUME,Volume Value,ADPC +VOLUMEU,Volume Value Unit,ADPC +SPWEIGHT,Specimen Weight Value,ADPC +SPWEIGHU,Specimen Weight Value Unit,ADPC +WTBL,Weight at Baseline,ADPC +HTBL,Height at Baseline,ADPC +IBWBL,Ideal Body Weight (IBW) at Baseline,ADPC +LBMBL,Lean Body Mass (LBM) at Baseline,ADPC +BMIBL,BMI at Baseline,ADPC +BSABL,BSA at Baseline,ADPC +SBPBL,Systolic BP at Baseline,ADPC +DBPBL,Diastolic BP at Baseline,] +TOBBL,Smoking Status at Baseline,ADPC +ALCOBL,Alcohol at Baseline,ADPC +TEMPBL,Temperature at Baseline,ADPC +PULSBL,Pulse rate at Baseline,ADPC +ADA,Treatment Emergent ADA status,ADPC +AAGBL,Alpha-1 Acid Glycoprotein at Baseline,ADPC +CREATBL,Creatinine at Baseline (BLOOD),ADPC +CRCLBL,CrCL at Baseline,ADPC +ALBUBL,Albumin at Baseline,ADPC +EOSBL,Eosinophils at Baseline,ADPC +BUNBL,Blood Urea Nitrogen at Baseline,ADPC +CALCBL,Calcium at Baseline,ADPC +CLBL,Chloride at Baseline,ADPC +PHBL,Phosphate at Baseline,ADPC +PLATEBL,Platelet Count at Baseline,ADPC +WBCBL,WBC Count at Baseline,ADPC +GGTBL,GGT at Baseline,ADPC +GLUCBL,Glucose at Baseline,ADPC +HCTBL,Hematocrit at Baseline,ADPC +HGBBL,Hemoglobin at Baseline,ADPC +ALKPHBL,Alkaline Phosphatase at Baseline,ADPC +KBL,Potassium at Baseline,ADPC +LYMBL,Lymphocytes at Baseline,ADPC +MONOBL,Monocytes at Baseline,ADPC +NABL,Sodium at Baseline,ADPC +NEUBL,Neutrophils at Baseline,ADPC +RBCBL,RBC Count at Baseline,ADPC +TBILIBL,Bilirubin at Baseline (BLOOD),ADPC +TPROTBL,Total Protein at Baseline (BLOOD),ADPC +SGOTBL,SGOT-AST at Baseline,ADPC +SGPTBL,SGPT-ALT at Baseline,ADPC +RRBL,RR Duration at Baseline,ADPC +PRBL,PR Duration at Baseline,ADPC +QRSBL,QRS Duration at Baseline,ADPC +QTBL,QT duration at Baseline,ADPC +QTCBBL,QTcB at Baseline,ADPC +QTCFBL,QTcF at Baseline,ADPC +HRBL,Heart Rate at Baseline,ADPC +WTBLU,Weight at Baseline (Unit),ADPC +HTBLU,Height at Baseline (Unit),ADPC +IBWBLU,IBW at Baseline (Unit),ADPC +LBWBLU,LBM at Baseline (Unit),ADPC +BMIBLU,BMI at Baseline (Unit),ADPC +BSABLU,BSA at Baseline (Unit),ADPC +SBPBLU,Systolic BP at Baseline (Unit),ADPC +DBPBLU,Diastolic BP at Baseline (Unit),ADPC +TOBBLU,Smoking Status at Baseline (Unit),ADPC +PULSBLU,Pulse rate at Baseline (Unit),ADPC +AAGBLU,AAG at baseline (Unit),ADPC +CREATBLU,Creat at baseline (BLOOD),ADPC +CRCLBLU,CrCL at baseline (BLOOD),ADPC +ALBUBLU,Albumin at baseline (Unit),ADPC +EOSBLU,Eosinophils at baseline (Unit),ADPC +BUNBLU,Blood Urea Nitrogen at baseline (Unit),ADPC +CALCBLU,Calcium at baseline (Unit),ADPC +CLBLU,Chloride at baseline (Unit),ADPC +PHBLU,Phosphate at baseline (Unit),ADPC +PLATEBLU,Platelet Count at baseline (Unit),ADPC +WBCBLU,WBC Count at baseline (Unit),ADPC +GGTBLU,GGT at Baseline (Unit),ADPC +GLUBLU,Glucose at Baseline (Unit),ADPC +HCTBLU,HCT at Baseline (Unit),ADPC +HGBBLU,HGB at Baseline (Unit),ADPC +ALKPHBLU,Alkaline Phosphatase at Baseline (Unit),ADPC +KBLU,Potassium at Baseline (Unit),ADPC +LYMBLU,Lymphocytes at Baseline (Unit),ADPC +MONOBLU,Monocytes at Baseline (Unit),ADPC +NABLU,Sodium at Baseline (Unit),ADPC +NEUBLU,Neutrophils at Baseline (Unit),ADPC +RBCBLU,RBC Count at Baseline (Unit),ADPC +TBILIBLU,Bilirubin at Baseline (Unit),ADPC +TPROTBLU,Total Protein at Baseline (Unit),ADPC +SGOTBLU,SGOT-AST at Baseline (Unit),ADPC +SGPTBLU,SGPT-ALT at Baseline (Unit),ADPC +RRBLU,RR Duration at Baseline (Unit),ADPC +PRBLU,PR Duration at Baseline (Unit),ADPC +QRSBLU,QRS Duration at Baseline (Unit),ADPC +QTBLU,QT Duration at Baseline (Unit),ADPC +QTCBBLU,QTcB at Baseline (Unit),ADPC +QTCFBLU,QTcF at Baseline (Unit),ADPC +HRBLU,Heart Rate at Baseline (Unit),ADPC +DRUG,Medication Name,ADPC +REGIME,Regimen of Medication,ADPC +FRMUL,Treatment Formulation,ADPC +DOSNO,Dose Number,ADPC +FEDSTATE,Fasted / Fed Status,ADPC +ANL01FL,Analysis Flag 01,ADPC +ANL02FL,Analysis Flag 02,ADPC +ANL03FL,Analysis Flag 03,ADPC +ANL04FL,Analysis Flag 04,ADPC +ANL05FL,Analysis Flag 05,ADPC +STUDYID,Study Identifier,ADPP +USUBJID,Unique Subject Identifier,ADPP +SUBJID,Subject Identifier for the Study,ADPP +SITEID,Study Site Identifier,ADPP +ASEQ,Analysis Sequence Number,ADPP +REGION1,Geographic Region 1,ADPP +COUNTRY,Country,ADPP +ETHNIC,Ethnicity,ADPP +AGE,Age,ADPP +AGEU,Age Units,ADPP +AAGE,Analysis Age,ADPP +AAGEU,Analysis Age Unit,ADPP +AGEGR1,Pooled Age Group 1,ADPP +AGEGR2,Pooled Age Group 2,ADPP +AGEGR3,Pooled Age Group 3,ADPP +STRATwNM,Description of Stratum w,ADPP +STRATw,Randomized Value of Stratum w,ADPP +STRATwV,Verified Value of Stratum w,ADPP +SEX,Sex,ADPP +RACE,Race,ADPP +ITTFL,Intent-To-Treat Population Flag,ADPP +SAFFL,Safety Population Flag,ADPP +PPROTFL,Per-Protocol Population Flag,ADPP +TRT01P,Planned Treatment for Period 01,ADPP +TRTxxP,Planned Treatment for Period xx,ADPP +TRT01A,Actual Treatment for Period 01,ADPP +TRTxxA,Actual Treatment for Period xx,ADPP +TRTSEQP,Planned Sequence of Treatments,ADPP +TRTSEQA,Actual Sequence of Treatments,ADPP +TRTSDTM,Datetime of First Exposure to Treatment,ADPP +TRTSDT,Date of First Exposure to Treatment,ADPP +TRTEDTM,Datetime of Last Exposure to Treatment,ADPP +TRTEDT,Date of Last Exposure to Treatment,ADPP +DCUTDT,Date of Data Cut,ADPP +PPSEQ,Sequence Number,ADPP +PPGRPID,Group ID,ADPP +PPSPID,Sponsor-Defined Identifier,ADPP +PPTESTCD,Parameter Short Name,ADPP +PPTEST,Parameter Name,ADPP +PPCAT,Parameter Category,ADPP +PPSCAT,Parameter Subcategory,ADPP +PPSTRESC,Character Result/Finding in Std Format,ADPP +PPSTRESN,Numeric Result/Finding in Standard Units,ADPP +PPSTRESU,Standard Units,ADPP +PPSTAT,Completion Status,ADPP +PPREASND,Reason Parameter Not Calculated,ADPP +PPSPEC,Specimen Material Type,ADPP +PPDTC,Date/Time of Parameter Calculations,ADPP +PPRFTDTC,Date/Time of Reference Point,ADPP +PPSTINT,Planned Start of Assessment Interval,ADPP +PPENINT,Planned End of Assessment Interval,ADPP +PARAM,Parameter,ADPP +PARAMCD,Parameter Code,ADPP +PARCAT1,Parameter Category 1,ADPP +PARCAT1,Parameter Category 1,ADPP +AVAL,Analysis Value,ADPP +AVALC,Analysis Value (C),ADPP +ADTM,Analysis Datetime,ADPP +ADT,Analysis Date,ADPP +ATM,Analysis Time,ADPP +ADY,Analysis Relative Day,ADPP +ADTF,Analysis Date Imputation Flag,ADPP +ATMF,Analysis Time Imputation Flag,ADPP +ATPT,Analysis Timepoint,ADPP +ATPT,Analysis Timepoint,ADPP +ATPTN,Analysis Timepoint (N),ADPP +ATPTN,Analysis Timepoint (N),ADPP +AVISIT,Analysis Visit,ADPP +AVISIT,Analysis Visit,ADPP +AVISITN,Analysis Visit (N),ADPP +AVISITN,Analysis Visit (N),ADPP +ANALYTE,Analyte,ADPC +EVID,Event ID,ADPC +DOSEU,Treatment Dose Units,ADPC diff --git a/inst/shiny/functions/generate_col_defs.R b/inst/shiny/functions/generate_col_defs.R new file mode 100644 index 00000000..2038ac28 --- /dev/null +++ b/inst/shiny/functions/generate_col_defs.R @@ -0,0 +1,44 @@ +#' Generate Column Definitions for Tables +#' +#' This function generates column definitions for a reactable table, +#' including both the column heading and the label (if available) as a tooltip. +#' +#' @param data A data frame containing the data to be displayed in the reactable table. +#' +#' @return A named list of column definitions for the reactable table. +#' +#' @examples +#' \dontrun{ +#' data <- data.frame( +#' USUBJID = c(1, 2, 3), +#' AVAL = c(4, 5, 6) +#' ) +#' attr(data$USUBJID, "label") <- "Unique Subject Identifier" +#' attr(data$AVAL, "label") <- "Analysis Value" +#' col_defs <- generate_col_defs(data) +#' } +#' +#' @export +generate_col_defs <- function(data) { + # Extract labels from the dataset + labels <- sapply(data, function(col) attr(col, "label")) + + # Generate column definitions + col_defs <- lapply(names(data), function(col) { + label <- labels[[col]] + if (!is.null(label)) { + reactable::colDef( + html = TRUE, + header = htmltools::tags$span( + col, + `data-toggle` = "tooltip", + `data-placement` = "top", + title = label + ) + ) + } else { + reactable::colDef(name = col) + } + }) |> + setNames(names(data)) +} diff --git a/inst/shiny/functions/mapping_selectize_inputs.R b/inst/shiny/functions/mapping_selectize_inputs.R index 62bf77ed..b4f67a82 100644 --- a/inst/shiny/functions/mapping_selectize_inputs.R +++ b/inst/shiny/functions/mapping_selectize_inputs.R @@ -51,4 +51,4 @@ update_selectize_inputs <- function(session, input_ids, column_names, manual_uni session, "select_Grouping_Variables", choices = setdiff(column_names, desired_order) ) -} \ No newline at end of file +} diff --git a/inst/shiny/global.R b/inst/shiny/global.R index adb6198f..8de83f7e 100644 --- a/inst/shiny/global.R +++ b/inst/shiny/global.R @@ -7,4 +7,4 @@ source("functions/partial_auc_input.R") source("modules/tab_visuals.R") source("functions/mapping_selectize_inputs.R") - +source("functions/generate_col_defs.R") diff --git a/inst/shiny/modules/column_mapping.R b/inst/shiny/modules/column_mapping.R index c88f6777..827f1812 100644 --- a/inst/shiny/modules/column_mapping.R +++ b/inst/shiny/modules/column_mapping.R @@ -334,10 +334,17 @@ column_mapping_server <- function(id, data, manual_units, on_submit) { } # Reorder columns based on the desired order - dataset %>% + dataset <- dataset %>% relocate(all_of(desired_order)) %>% - mutate(TIME = ifelse(DOSNO == 1, AFRLT, ARRLT)) %>% #TODO: Remove this after AUC0 merged - processed_data() + mutate(TIME = ifelse(DOSNO == 1, AFRLT, ARRLT))#TODO: Remove this after AUC0 merged + + #Load labels + labels_file <- read.csv(system.file("shiny/data/adnca_labels.csv", package = "aNCA")) + # Apply labels to the dataset + dataset <- apply_labels(dataset, labels_file) + + # Update the processed data + processed_data(dataset) # Execute the callback function to change the tab on_submit() @@ -348,4 +355,4 @@ column_mapping_server <- function(id, data, manual_units, on_submit) { grouping_variables = grouping_variables ) }) -} \ No newline at end of file +} diff --git a/inst/shiny/modules/tab_data.R b/inst/shiny/modules/tab_data.R index 3d2c937e..d61a5ff1 100644 --- a/inst/shiny/modules/tab_data.R +++ b/inst/shiny/modules/tab_data.R @@ -41,7 +41,12 @@ tab_data_ui <- function(id) { nav_panel("Review Data", "This is the data set that will be used for the analysis. If you want to make any changes, please do so in the Mapping and Filters tab.", - reactableOutput(ns("data_processed")) + reactableOutput(ns("data_processed")), + tags$script(HTML(" + $(document).ready(function(){ + $('[data-toggle=\"tooltip\"]').tooltip(); + }); + ")) ) ) @@ -154,8 +159,13 @@ tab_data_server <- function(id) { # Update the data table object with the filtered data output$data_processed <- renderReactable({ req(data()) + + # Generate column definitions + col_defs <- generate_col_defs(data()) + reactable( data(), + columns = col_defs, searchable = TRUE, sortable = TRUE, highlight = TRUE, @@ -174,4 +184,4 @@ tab_data_server <- function(id) { grouping_variables = grouping_variables ) }) -} \ No newline at end of file +} diff --git a/inst/shiny/tabs/nca.R b/inst/shiny/tabs/nca.R index aeaf8dac..0c3e7de2 100644 --- a/inst/shiny/tabs/nca.R +++ b/inst/shiny/tabs/nca.R @@ -218,17 +218,24 @@ observeEvent(input$submit_analyte, priority = 2, { }) # Display the PKNCA data object for the user (concentration records) -output$datatable <- DT::renderDataTable({ +output$datatable <- renderReactable({ req(mydata()) - DT::datatable( - data = mydata()$conc$data, - extensions = "FixedHeader", - options = list( - scrollX = TRUE, - scrollY = TRUE, - lengthMenu = list(c(10, 25, -1), c("10", "25", "All")), - fixedHeader = TRUE - ) + data <- mydata()$conc$data + # Generate column definitions + col_defs <- generate_col_defs(data) + + reactable( + data, + columns = col_defs, + searchable = TRUE, + sortable = TRUE, + highlight = TRUE, + wrap = FALSE, + resizable = TRUE, + showPageSizeOptions = TRUE, + striped = TRUE, + bordered = TRUE, + height = "60vh" ) }) diff --git a/inst/shiny/ui.R b/inst/shiny/ui.R index 3a37e72d..09e0c49d 100644 --- a/inst/shiny/ui.R +++ b/inst/shiny/ui.R @@ -48,7 +48,7 @@ fluidPage( selectInput("analyte", "Choose the analyte :", choices = NULL), br(), actionButton("submit_analyte", "Submit"), - DTOutput("datatable"), + reactableOutput("datatable"), ), tabPanel("Settings", selectInput( diff --git a/man/apply_labels.Rd b/man/apply_labels.Rd new file mode 100644 index 00000000..932505b2 --- /dev/null +++ b/man/apply_labels.Rd @@ -0,0 +1,34 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/label_operators.R +\name{apply_labels} +\alias{apply_labels} +\title{Apply Labels to a dataset} +\usage{ +apply_labels(data, labels_file) +} +\arguments{ +\item{data}{The dataset to which labels will be applied.} + +\item{labels_file}{A data frame with two columns: Variable and Label, +for the dataset you are applying it .} +} +\value{ +The same dataset with label attributes applied to all columns. +If a column is not present in the labels list, it will be assigned the name of the col. +} +\description{ +This function adds "label" attributes to all columns in a dataset +} +\examples{ +\dontrun{ + # Example usage: + data <- data.frame(USUBJID = c(1, 2, 3), AVAL = c(4, 5, 6)) + labels <- data.frame( + Variable = c("USUBJID", "AVAL"), + Label = c("Unique Subject Identifier", "Analysis Value") + ) + data <- apply_labels(data, labels) + print(attr(data$A, "label")) +} + +} diff --git a/tests/testthat/test-apply_labels.R b/tests/testthat/test-apply_labels.R new file mode 100644 index 00000000..9fb0e8e7 --- /dev/null +++ b/tests/testthat/test-apply_labels.R @@ -0,0 +1,29 @@ +describe("apply_labels", { + it("applies labels to matching data", { + data <- data.frame( + USUBJID = c(1, 2, 3), + AVAL = c(4, 5, 6) + ) + labels <- data.frame( + Variable = c("USUBJID", "AVAL"), + Label = c("Unique Subject Identifier", "Analysis Value") + ) + data <- apply_labels(data, labels) + expect_equal(attr(data$USUBJID, "label"), "Unique Subject Identifier") + expect_equal(attr(data$AVAL, "label"), "Analysis Value") + + }) + it("appplies labels to non matching data", { + data <- data.frame( + COL1 = c(1, 2, 3), + COL2 = c(4, 5, 6) + ) + labels <- data.frame( + Variable = c("USUBJID", "AVAL"), + Label = c("Unique Subject Identifier", "Analysis Value") + ) + data <- apply_labels(data, labels) + expect_equal(attr(data$COL1, "label"), "COL1") + expect_equal(attr(data$COL2, "label"), "COL2") + }) +}) diff --git a/tests/testthat/test-generate_col_defs.R b/tests/testthat/test-generate_col_defs.R new file mode 100644 index 00000000..14a5f386 --- /dev/null +++ b/tests/testthat/test-generate_col_defs.R @@ -0,0 +1,17 @@ +source(system.file("shiny/functions/generate_col_defs.R", package = "aNCA")) + +describe("generate_col_defs", { + it("generates a list of column definitions with labels", { + data <- data.frame( + USUBJID = c(1, 2, 3), + AVAL = c(4, 5, 6) + ) + attr(data$USUBJID, "label") <- "Unique Subject Identifier" + attr(data$AVAL, "label") <- "Analysis Value" + col_defs <- generate_col_defs(data) + expect_type(col_defs, "list") + expect_equal(col_defs$USUBJID$header$attribs$title, "Unique Subject Identifier") + expect_equal(col_defs$AVAL$header$attribs$title, "Analysis Value") + }) + +})