Skip to content

Commit

Permalink
Make relative_effects() work
Browse files Browse the repository at this point in the history
  • Loading branch information
ndunnewind committed Apr 24, 2024
1 parent 690f7d3 commit 5f03f37
Show file tree
Hide file tree
Showing 2 changed files with 24 additions and 20 deletions.
34 changes: 17 additions & 17 deletions R/nma.R
Original file line number Diff line number Diff line change
Expand Up @@ -697,6 +697,22 @@ nma <- function(network,
}
}

if (".mu" %in% all.vars(regression)) {
if (".mu" %in% colnames(data)) {
warn("Overwriting '.mu'. Special name. Use different name.")
}

ref_trt <- levels(idat_agd_arm$.trt)[1L]

idat_agd_arm <- idat_agd_arm %>%
dplyr::group_by(.data$.study) %>%
dplyr::mutate(.mu = dplyr::if_else(
.data$.trt != ref_trt & ref_trt %in% .data$.trt,
as.numeric(.data$.study), 0
)) %>%
dplyr::ungroup()
}

# Only take necessary columns
idat_agd_arm <- get_model_data_columns(idat_agd_arm,
regression = regression,
Expand Down Expand Up @@ -1452,7 +1468,7 @@ nma.fit <- function(ipd_x, ipd_y,
col_trt <- grepl("^(\\.trt|\\.contr)[^:]+$", x_names)
col_omega <- x_names == ".omegaTRUE"
col_reg <- !col_study & !col_trt & !col_omega
col_br <- col_reg & grepl("^\\.mu", x_names)
col_br <- col_reg & grepl("\\.mu", x_names)

n_trt <- sum(col_trt) + 1

Expand Down Expand Up @@ -3046,22 +3062,6 @@ get_model_data_columns <- function(data, regression = NULL, aux_regression = NUL
auxregvars <- NULL

if (!is.null(regression)) {
if (".mu" %in% all.vars(regression)) {
if (".mu" %in% colnames(data)) {
warn("Overwriting '.mu'. Special name. Use different name.")
}

ref_trt <- levels(data$.trt)[1L]

data <- data %>%
dplyr::group_by(.data$.study) %>%
dplyr::mutate(.mu = dplyr::if_else(
.data$.trt != ref_trt & ref_trt %in% .data$.trt,
as.numeric(.data$.study), 0
)) %>%
dplyr::ungroup()
}

regvars <- setdiff(all.vars(regression), c(".trt", ".trtclass", ".study", ".contr", ".omega"))
badvars <- setdiff(regvars, colnames(data))
if (length(badvars)) {
Expand Down
10 changes: 7 additions & 3 deletions tests/testthat/test-example_certolizumab.R
Original file line number Diff line number Diff line change
@@ -1,9 +1,13 @@
test_that("TSD3 Certolizumab example can be reproduced", {
net <- set_agd_arm(certolizumab, study = study, trt = trt, n = n, r = r)
net <- set_agd_arm(
certolizumab,
study = study, trt = trt, n = n, r = r,
trt_class = dplyr::if_else(trt == "Placebo", "Placebo", "Treatment")
)

fit_fe <- nma(
net,
regression = ~.mu,
regression = ~.mu:.trt,
prior_intercept = normal(scale = sqrt(1000)),
prior_trt = normal(scale = 100),
prior_reg = normal(scale = 100),
Expand All @@ -24,7 +28,7 @@ test_that("TSD3 Certolizumab example can be reproduced", {
fit_re <- nma(
net,
trt_effects = "random",
regression = ~.mu,
regression = ~.mu:.trt,
prior_intercept = normal(scale = sqrt(1000)),
prior_trt = normal(scale = 100),
prior_reg = normal(scale = 100),
Expand Down

0 comments on commit 5f03f37

Please sign in to comment.