Skip to content

Commit

Permalink
(lineplot) Ref value vignette. Show all ref values checkbox.
Browse files Browse the repository at this point in the history
  • Loading branch information
ml-ebs-ext committed Feb 18, 2025
1 parent 9d65774 commit c9e02a9
Show file tree
Hide file tree
Showing 10 changed files with 187 additions and 9 deletions.
45 changes: 36 additions & 9 deletions R/mod_lineplot.R
Original file line number Diff line number Diff line change
Expand Up @@ -30,6 +30,7 @@ LP_ID <- poc(
),
TWEAK_TRANSPARENCY = "transparency",
TWEAK_Y_AXIS_PROJECTION = "y_axis_projection",
SHOW_ALL_REFERENCE_VALUES = "show_all_reference_values",
SELECTED_SUBJECT = "selected_subject",
LINE_HIGHLIGHT_MASK = "line_highlight_mask"
)
Expand All @@ -54,7 +55,8 @@ LP_MSG <- poc(
COUNT_LISTING = "Data Count",
SUMMARY_LISTING = "Summary listing",
TABLE_SIGNIFICANCE = "Data Significance",
TWEAK_TRANSPARENCY = "Transparency"
TWEAK_TRANSPARENCY = "Transparency",
SHOW_ALL_REFERENCE_VALUES = "Show all reference values"
),
VALIDATE = poc(
NO_CAT_SEL = "Select a category",
Expand Down Expand Up @@ -330,6 +332,8 @@ lineplot_chart <- function(data, title = NULL, ref_line_data = NULL, log_project
# because the latter is only supported in ggplot2 >= 3.5.0
fig <- fig + ggplot2::scale_y_continuous(trans = pseudo_log_projection(base = 10))
}
# NOTE: Hook to generate documentation screenshots
# ggplot2::ggsave("/tmp/ggplot.png", plot = fig, width = 2000, height = 1200, unit = "px") # nolint

fig
}
Expand Down Expand Up @@ -493,7 +497,7 @@ lp_median_summary_fns <- list(
#' USUBJID, PARCAT, PARAM, AVISIT and AVAL, respectively.
#'
#' Optional columns specified by `ref_line_vars` should contain the same numeric value for all
#' records of the same parameter.
#' records of the same parameter for any given subject.
#'
#' @param group_dataset `[data.frame()]`
#'
Expand Down Expand Up @@ -539,7 +543,8 @@ lp_median_summary_fns <- list(
#'
#' @param ref_line_vars `[character(n)]`
#'
#' Columns for `bm_dataset` specifying reference values for parameters
#' Columns for `bm_dataset` specifying reference values for parameters.
#' See [this article](../articles/lineplot_reference_values.html) for more details
#'
#' @param on_sbj_click `[function()]`
#'
Expand Down Expand Up @@ -840,21 +845,37 @@ lineplot_server <- function(id,
data_subset(), bm_dataset(), visit_var = input_lp[[LP_ID$PAR_VISIT_COL]](), extra_vars = ref_line_vars
)

# TODO(miguel): This thing needs thorough testing, refactoring or both
show_all_ref_vals <- isTRUE(input[[LP_ID$SHOW_ALL_REFERENCE_VALUES]])

if (CNT$MAIN_GROUP %in% names(ds)) {
ds <- unique(ds[c(CNT$PAR, CNT$MAIN_GROUP, ref_line_vars)])
for (var in ref_line_vars){
entry_name <- get_lbl_robust(ds, var)
if (show_all_ref_vals) entry_name <- paste(entry_name, "\n(all ref. values)")

var_ds <- unique(ds[c(CNT$PAR, CNT$MAIN_GROUP, var)])
names(var_ds)[[3]] <- CNT$VAL
# Introduce extra level to customize color of reference lines that would otherwise overlap
var_ds[[CNT$MAIN_GROUP]] <- factor(var_ds[[CNT$MAIN_GROUP]],
levels = c(levels(var_ds[[CNT$MAIN_GROUP]]),
"Common reference value"))
if (show_all_ref_vals) {
var_ds[[CNT$MAIN_GROUP]] <- factor("Common reference value",
levels = c(levels(var_ds[[CNT$MAIN_GROUP]]),
"Common reference value"))
} else {
# Introduce extra level to customize color of reference lines that would otherwise overlap
var_ds[[CNT$MAIN_GROUP]] <- factor(var_ds[[CNT$MAIN_GROUP]],
levels = c(levels(var_ds[[CNT$MAIN_GROUP]]),
"Common reference value"))
}

res[[entry_name]] <- var_ds[FALSE, ] # data.frame without rows
for (param in unique(ds[[CNT$PAR]])){
var_param_ds <- var_ds[var_ds[[CNT$PAR]] == param, ]
if (length(unique(var_param_ds[[CNT$VAL]])) == 1) {
if (show_all_ref_vals) {
for (group in unique(var_param_ds[[CNT$MAIN_GROUP]])){
mask <- (var_param_ds[[CNT$MAIN_GROUP]] == group)
res[[entry_name]] <- rbind(res[[entry_name]], var_param_ds[mask, ])
}
} else if (length(unique(var_param_ds[[CNT$VAL]])) == 1) {
# All groups share the same ref_line. We take the first one and map it to the artificial "Common" level
row <- var_param_ds[1, ]
row[1, "main_group"] <- "Common reference value"
Expand All @@ -876,12 +897,13 @@ lineplot_server <- function(id,
ds <- unique(ds[c(CNT$PAR, ref_line_vars)])
for (var in ref_line_vars){
entry_name <- get_lbl_robust(ds, var)
if (show_all_ref_vals) entry_name <- paste(entry_name, "\n(all ref. values)")
var_ds <- unique(ds[c(CNT$PAR, var)])
names(var_ds)[[2]] <- CNT$VAL
res[[entry_name]] <- var_ds[FALSE, ] # data.frame without rows
for (param in unique(ds[[CNT$PAR]])) {
var_param_ds <- var_ds[var_ds[[CNT$PAR]] == param, ]
if (nrow(var_param_ds) == 1) {
if (nrow(var_param_ds) == 1 || show_all_ref_vals) {
res[[entry_name]] <- rbind(res[[entry_name]], var_param_ds)
}
}
Expand Down Expand Up @@ -1143,6 +1165,11 @@ lineplot_server <- function(id,
choices = c("Linear", "Logarithmic"),
selected = default_y_axis_projection,
inline = TRUE
),
shiny::checkboxInput(
ns(LP_ID$SHOW_ALL_REFERENCE_VALUES),
LP_MSG$LABEL$SHOW_ALL_REFERENCE_VALUES,
value = FALSE
)
)

Expand Down
Binary file modified vignettes/images/lineplot_menu_04.jpg
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
Binary file added vignettes/images/lineplot_ref_line_00.png
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
Binary file added vignettes/images/lineplot_ref_line_01.png
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
Binary file added vignettes/images/lineplot_ref_line_02.png
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
Binary file added vignettes/images/lineplot_ref_line_03.png
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
Binary file added vignettes/images/lineplot_ref_line_04.png
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
Binary file added vignettes/images/lineplot_ref_line_05.png
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
Binary file added vignettes/images/lineplot_ref_line_06.png
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
151 changes: 151 additions & 0 deletions vignettes/lineplot_reference_values.Rmd
Original file line number Diff line number Diff line change
@@ -0,0 +1,151 @@
---
title: "Lineplot reference values"
output: rmarkdown::html_vignette
vignette: >
%\VignetteIndexEntry{Lineplot reference values}
%\VignetteEngine{knitr::rmarkdown}
%\VignetteEncoding{UTF-8}
---

```{r, include = FALSE}
knitr::opts_chunk$set(
collapse = TRUE,
comment = "#>"
)
```

This article describes how to display reference values in `mod_lineplot` charts and discusses the not-so-intuitive
behavior of reference lines in the presence of grouped data.

# A basic plot

As a starting point, let's imagine we want to inspect the following tiny subject-level (`sl`) and laboratory values (`lb`) datasets (*click to expand*):

<details><summary>Subject-level dataset</summary>
```{r, echo = FALSE}
# Inspired in safetyData:adam_adsl
sl <- data.frame(
SUBJID = c("1015", "1028") |> as.factor(),
SEX = c("F", "M") |> as.factor(),
RACE = c("WHITE", "WHITE") |> as.factor(),
COUNTRY = c("Italy", "Spain") |> as.factor()
)
knitr::kable(sl, format = "markdown")
```
</details>

<details><summary>Laboratory values dataset</summary>
```{r, echo = FALSE}
# Inspired in safetyData:adam_lbc
lb <- data.frame(
SUBJID = c("1015", "1015", "1015", "1028", "1028", "1028") |> as.factor(),
PARCAT1 = rep("CHEM", 6) |> as.factor(),
PARAM = rep("Imaginariol (mmol/L)", 6) |> as.factor(),
AVISITN = c(0, 2, 4, 0, 2, 4),
AVAL = c(5.94780, 5.48232, 4.99098, 4.80996, 4.70652, 4.37034),
A1LO = c(4.03, 4.03, 4.03, 3.85, 3.85, 3.85),
A1HI = c(6.00, 6.00, 6.00, 6.00, 6.00, 6.00)
)
knitr::kable(lb, format = "markdown")
```
</details>

```{r, echo = FALSE, eval = FALSE}
# Run this app to generate the plots
module_list <- list(
lineplot = dv.explorer.parameter::mod_lineplot(
module_id = "lineplot", bm_dataset_name = "lb", group_dataset_name = "sl",
subjid_var = "SUBJID", cat_var = "PARCAT1", par_var = "PARAM", value_vars = "AVAL",
visit_vars = "AVISITN", default_cat = "CHEM", default_par = "Imaginariol (mmol/L)",
#default_main_group = "COUNTRY" # nolint
, ref_line_vars = c("A1LO", "A1HI")
)
)
dv.manager::run_app(
data = list("DS" = list(lb = lb, sl = sl)),
module_list = module_list,
filter_data = "sl",
filter_key = "SUBJID"
)
```

We can do so by configuring `mod_lineplot` thus:

```{r, eval=FALSE}
dv.explorer.parameter::mod_lineplot(
module_id = "lineplot", bm_dataset_name = "lb", group_dataset_name = "sl",
subjid_var = "SUBJID", cat_var = "PARCAT1", par_var = "PARAM",
value_vars = "AVAL", visit_vars = "AVISITN", default_cat = "CHEM",
default_par = "Cholesterol (mmol/L)", default_main_group = "SEX"
)
```

Which generates the following plot:
![](images/lineplot_ref_line_00.png)

# Grouped and ungrouped reference values

We can provide a value for the `ref_line_vars` parameter so that in points to one or more `lb` numerical columns holding reference values:
```{r, eval=FALSE}
dv.explorer.parameter::mod_lineplot(
..., default_main_group = "SEX", ref_line_vars = c("A1LO", "A1HI")
)
```

Which produces:
![](images/lineplot_ref_line_01.png)
Examining this plot we can see the three distinct reference values available in the original `bm` dataset. There is a `A1HI` value
common to all of our (two) subjects. It's indicated with a continuous black line. There are also two `A1LO` values that coincide with
our selected grouping. Since the plot already provides colors for those groups, `mod_lineplot` to also plot those lines in matching colors.

# Which demographic value dictates distinct reference values?

The original `bm` dataset does not tell us anything about origin of the different values of the `A1LO` reference values. It may very well be the case that `SEX` is indeed the variable that dictates which reference value to use but, in the absence of more information, `COUNTRY` would work equally well.

```{r, eval=FALSE}
dv.explorer.parameter::mod_lineplot(
..., default_main_group = "COUNTRY", ref_line_vars = c("A1LO", "A1HI")
)
```
![](images/lineplot_ref_line_02.png)

This plot is still factually correct in the sense that the color of each `AVAL` line is color-matched with the `A1LO` value that accompanies it in the `lb` dataset.

# Disappearing reference lines

What happens then if we don't provide a grouping variable?

```{r, eval=FALSE}
dv.explorer.parameter::mod_lineplot(
..., ref_line_vars = c("A1LO", "A1HI")
)
```
In this case, `mod_lineplot` can't plot the `A1LO` reference values in a way that ties them to each of the two `AVAL` lines, so they are simply dropped:

![](images/lineplot_ref_line_03.png)

Notice however, that the `A1HI` value keeps applying to all `AVAL` lines, so it is kept.

# Inspecting all reference values

Sometimes it's useful to be able to see *all* reference values regardless of whether they can be represented truthfully given some
particular data grouping. In this case, users can override the built-in reference line filter by checking the "Show all reference values"
option under the "Settings" drop-down menu.

![](images/lineplot_ref_line_04.png)

After doing that, all unique reference values are shown in black. The legend is also modified to point out the non-standard nature of the plot.

![](images/lineplot_ref_line_05.png)

# Requirements for reference values

Reference value dataset variables should:

- be numerical
- remain constant across every combination of subject and parameter of the dataset

If one of these conditions is not met during module start-up, `mod_lineplot` produces a suitable message, such as:

![](images/lineplot_ref_line_06.png)

0 comments on commit c9e02a9

Please sign in to comment.