Skip to content

Commit

Permalink
svytableone edit
Browse files Browse the repository at this point in the history
  • Loading branch information
sl-eeper committed Nov 12, 2024
1 parent f853ab0 commit c9bc654
Show file tree
Hide file tree
Showing 3 changed files with 83 additions and 6 deletions.
2 changes: 1 addition & 1 deletion NEWS.md
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
# jstable 1.3.6
* Update: Add event, count_by option in TableSubgroupCox, TableSubgroupMultiCox
* Update: Add pairwise option in CreateTableOne2, CreateTableOneJS
* Update: Add pairwise option in CreateTableOne2, CreateTableOneJS, svyCreateTableOne2, svyCreateTableOneJS

# jstable 1.3.5
* Fix: error in `TableSubgroupMultiGLM` when covariates
Expand Down
3 changes: 2 additions & 1 deletion R/CreateTableOneJS.R
Original file line number Diff line number Diff line change
Expand Up @@ -31,6 +31,7 @@
#' @param minMax Whether to use [min,max] instead of [p25,p75] for nonnormal variables. The default is FALSE.
#' @param showpm Logical, show normal distributed continuous variables as Mean ± SD. Default: T
#' @param addOverall (optional, only used if strata are supplied) Adds an overall column to the table. Smd and p-value calculations are performed using only the stratifed clolumns. Default: F
#' @param pairwise (optional, only used if strata are supplied) When there are three or more strata, it displays the p-values for pairwise comparisons. Default: F
#' @return A matrix object containing what you see is also invisibly returned. This can be assinged a name and exported via write.csv.
#' @details DETAILS
#' @examples
Expand Down Expand Up @@ -258,7 +259,7 @@ CreateTableOne2 <- function(data, strata, vars, factorVars, includeNA = F, test
#' @param showpm Logical, show normal distributed continuous variables as Mean ± SD. Default: T
#' @param addOverall (optional, only used if strata are supplied) Adds an overall column to the table. Smd and p-value calculations are performed using only the stratifed clolumns. Default: F
#' @param normalityTest Logical, perform the Shapiro test for all variables. Default: F
#' @return A matrix object containing what you see is also invisibly returned. This can be assinged a name and exported via write.csv.
#' @param pairwise (optional, only used if strata are supplied) When there are three or more strata, it displays the p-values for pairwise comparisons. Default: F#' @return A matrix object containing what you see is also invisibly returned. This can be assinged a name and exported via write.csv.
#' @details DETAILS
#' @examples
#' library(survival)
Expand Down
84 changes: 80 additions & 4 deletions R/svyCreateTableOneJS.R
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,7 @@
#' @param minMax Whether to use [min,max] instead of [p25,p75] for nonnormal variables. The default is FALSE.
#' @param showpm Logical, show normal distributed continuous variables as Mean ± SD. Default: T
#' @param addOverall (optional, only used if strata are supplied) Adds an overall column to the table. Smd and p-value calculations are performed using only the stratifed clolumns. Default: F
#' @param pairwise (optional, only used if strata are supplied) When there are three or more strata, it displays the p-values for pairwise comparisons. Default: F
#' @return A matrix object containing what you see is also invisibly returned. This can be assinged a name and exported via write.csv.
#' @details DETAILS
#' @examples
Expand All @@ -46,7 +47,7 @@
svyCreateTableOne2 <- function(data, strata, vars, factorVars, includeNA = F, test = T,
showAllLevels = T, printToggle = F, quote = F, smd = F, nonnormal = NULL,
catDigits = 1, contDigits = 2, pDigits = 3, Labels = F, labeldata = NULL, minMax = F, showpm = T,
addOverall = F) {
addOverall = F, pairwise = F) {
setkey <- variable <- level <- . <- val_label <- NULL

if (length(strata) != 1) {
Expand Down Expand Up @@ -122,14 +123,88 @@ svyCreateTableOne2 <- function(data, strata, vars, factorVars, includeNA = F, te
}
}

if (pairwise && length(unique(data$variables[[strata]])) > 2) {
print('enter')
pairwise_comparisons <- combn(
colnames(ptb1)[(which(colnames(ptb1) == "level") + 1):(which(colnames(ptb1) == "p") - 1)], 2, simplify = FALSE)
pairwise_pvalues_list <- list()
for (x in vars) {
pairwise_pvalues_list[[x]] <- list()
is_continuous <- !(x %in% factorVars) && !is.factor(data$variables[[x]])
for (pair in pairwise_comparisons) {
subset_data <- subset(data, data$variables[[strata]] %in% pair)
if (is_continuous) {
test_result <- if (x %in% nonnormal) {
tryCatch({
test <- svyranktest(as.formula(paste(x, "~", strata)), design = subset_data)
list(p_value = test$p.value, test_used = "svyranktest")
}, error = function(e) {
list(p_value = NA, test_used = NA)
})
} else {
tryCatch({
test <- svyttest(as.formula(paste(x, "~", strata)), design = subset_data)
list(p_value = test$p.value, test_used = "svyttest")
}, error = function(e) {
list(p_value = NA, test_used = NA)
})
}
} else {
test_result <- tryCatch({
test <- svychisq(as.formula(paste("~", x, "+", strata)), design = subset_data, method = "RaoScott")
list(p_value = test$p.value, test_used = "svychisq")
}, error = function(e) {
list(p_value = NA, test_used = NA)
})
}
pairwise_pvalues_list[[x]][[paste(pair, collapse = "_")]] <- test_result
}
}
for (i in seq_along(pairwise_comparisons)) {
col_name <- paste0("p(", pairwise_comparisons[[i]][1], " vs ", pairwise_comparisons[[i]][2], ")")
test_name <- paste0("test(", pairwise_comparisons[[i]][1], " vs ", pairwise_comparisons[[i]][2], ")")
ptb1 <- cbind(ptb1, col_name = "", test_name = "")
colnames(ptb1)[ncol(ptb1) - 1] <- col_name
colnames(ptb1)[ncol(ptb1)] <- test_name
}
for (x in vars) {
cleaned_var_name <- gsub("\\s+|\\(\\%\\)", "", x)
first_row <- which(gsub("\\s+|\\(\\%\\)", "", rownames(ptb1)) == cleaned_var_name)[1]

for (i in seq_along(pairwise_comparisons)) {
pair_key <- paste(pairwise_comparisons[[i]], collapse = "_")
p_value <- pairwise_pvalues_list[[x]][[pair_key]]$p_value
test_used <- pairwise_pvalues_list[[x]][[pair_key]]$test_used
col_name <- paste0("p(", pairwise_comparisons[[i]][1], " vs ", pairwise_comparisons[[i]][2], ")")
test_name <- paste0("test(", pairwise_comparisons[[i]][1], " vs ", pairwise_comparisons[[i]][2], ")")
p_value <- ifelse(p_value < 0.001, "<0.001", as.character(round(p_value, 2)))
ptb1[first_row, col_name] <- p_value
ptb1[first_row, test_name] <- test_used
}
}
cols_to_remove <- grep("^test\\(", colnames(ptb1))
ptb1 <- ptb1[, -cols_to_remove]
}


sig <- ifelse(ptb1[, "p"] == "<0.001", "0", ptb1[, "p"])
sig <- as.numeric(as.vector(sig))
sig <- ifelse(sig <= 0.05, "**", "")
ptb1 <- cbind(ptb1, sig)
return(ptb1)
}


nhanes$SDMVPSU <- as.factor(nhanes$SDMVPSU)
nhanesSvy <- svydesign(
ids = ~SDMVPSU, strata = ~SDMVSTRA, weights = ~WTMEC2YR,
nest = TRUE, data = nhanes
)
svyCreateTableOneJS(
vars = c("HI_CHOL", "race", "agecat", "RIAGENDR"),
strata = "race", data = nhanesSvy,
factorVars = c("HI_CHOL", "race", "RIAGENDR"), pairwise = T
)
names(nhanes)

#' @title svyCreateTableOneJS: Modified CreateTableOne function in tableone package
#' @description Combine svyCreateTableOne & print function in tableone package
Expand All @@ -154,6 +229,7 @@ svyCreateTableOne2 <- function(data, strata, vars, factorVars, includeNA = F, te
#' @param minMax Whether to use [min,max] instead of [p25,p75] for nonnormal variables. The default is FALSE.
#' @param showpm Logical, show normal distributed continuous variables as Mean ± SD. Default: T
#' @param addOverall (optional, only used if strata are supplied) Adds an overall column to the table. Smd and p-value calculations are performed using only the stratifed clolumns. Default: F
#' @param pairwise (optional, only used if strata are supplied) When there are three or more strata, it displays the p-values for pairwise comparisons. Default: F
#' @return A matrix object containing what you see is also invisibly returned. This can be assinged a name and exported via write.csv.
#' @details DETAILS
#' @examples
Expand All @@ -179,7 +255,7 @@ svyCreateTableOne2 <- function(data, strata, vars, factorVars, includeNA = F, te
svyCreateTableOneJS <- function(vars, strata = NULL, strata2 = NULL, data, factorVars = NULL, includeNA = F, test = T,
showAllLevels = T, printToggle = F, quote = F, smd = F, Labels = F, nonnormal = NULL,
catDigits = 1, contDigits = 2, pDigits = 3, labeldata = NULL, psub = T, minMax = F, showpm = T,
addOverall = F) {
addOverall = F, pairwise = F) {
. <- level <- variable <- val_label <- V1 <- V2 <- NULL

# if (Labels & !is.null(labeldata)){
Expand Down Expand Up @@ -231,7 +307,7 @@ svyCreateTableOneJS <- function(vars, strata = NULL, strata2 = NULL, data, facto
strata = strata, vars = vars, data = data, factorVars = factorVars, includeNA = includeNA, test = test, smd = smd,
showAllLevels = showAllLevels, printToggle = printToggle, quote = quote, Labels = Labels, nonnormal = nonnormal,
catDigits = catDigits, contDigits = contDigits, pDigits = pDigits, labeldata = labeldata, minMax = minMax, showpm = showpm,
addOverall = addOverall
addOverall = addOverall, pairwise = pairwise
)

cap.tb1 <- paste("Stratified by ", strata, "- weighted data", sep = "")
Expand Down

0 comments on commit c9bc654

Please sign in to comment.