diff --git a/DESCRIPTION b/DESCRIPTION index e37be1625..f8c061501 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: metafor -Version: 4.7-23 -Date: 2024-07-02 +Version: 4.7-24 +Date: 2024-07-09 Title: Meta-Analysis Package for R Authors@R: person(given = "Wolfgang", family = "Viechtbauer", role = c("aut","cre"), email = "wvb@metafor-project.org", comment = c(ORCID = "0000-0003-3463-4063")) Depends: R (>= 4.0.0), methods, Matrix, metadat, numDeriv @@ -12,5 +12,6 @@ ByteCompile: TRUE Encoding: UTF-8 RdMacros: mathjaxr VignetteBuilder: R.rsp +BuildManual: TRUE URL: https://www.metafor-project.org https://github.com/wviechtb/metafor https://wviechtb.github.io/metafor/ https://www.wvbauer.com BugReports: https://github.com/wviechtb/metafor/issues diff --git a/NEWS.md b/NEWS.md index ea8740d98..8ceca6a4f 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,4 +1,6 @@ -# metafor 4.7-23 (2024-07-02) +# metafor 4.7-24 (2024-07-09) + +- added `collapse` argument to the various `cumul()` functions - the `predict.rma()` and `predict.rma.ls()` functions now also accept a matrix as input that includes a column for the intercept term (in which case the `intercept` argument is ignored) diff --git a/R/cumul.rma.mh.r b/R/cumul.rma.mh.r index 1b58e6350..95c120c63 100644 --- a/R/cumul.rma.mh.r +++ b/R/cumul.rma.mh.r @@ -1,4 +1,4 @@ -cumul.rma.mh <- function(x, order, digits, transf, targs, progbar=FALSE, ...) { +cumul.rma.mh <- function(x, order, digits, transf, targs, collapse=FALSE, progbar=FALSE, ...) { mstyle <- .get.mstyle() @@ -9,6 +9,8 @@ cumul.rma.mh <- function(x, order, digits, transf, targs, progbar=FALSE, ...) { if (!is.element(na.act, c("na.omit", "na.exclude", "na.fail", "na.pass"))) stop(mstyle$stop("Unknown 'na.action' specified under options().")) + if (na.act == "na.fail" && any(!x$not.na)) + stop(mstyle$stop("Missing values in data.")) if (missing(digits)) { digits <- .get.digits(xdigits=x$digits, dmiss=TRUE) @@ -34,85 +36,122 @@ cumul.rma.mh <- function(x, order, digits, transf, targs, progbar=FALSE, ...) { ######################################################################### if (grepl("^order\\(", deparse1(substitute(order)))) - warning(mstyle$warning("Use of order() in 'order' argument is probably erroneous."), call.=FALSE) + warning(mstyle$warning("Use of order() in the 'order' argument is probably erroneous."), call.=FALSE) if (missing(order)) { - order <- seq_len(x$k.all) + + orvar <- seq_len(x$k.all) + collapse <- FALSE + } else { + mf <- match.call() - order <- .getx("order", mf=mf, data=x$data) - } + orvar <- .getx("order", mf=mf, data=x$data) + + if (length(orvar) != x$k.all) + stop(mstyle$stop(paste0("Length of the 'order' argument (", length(orvar), ") does not correspond to the size of the original dataset (", x$k.all, ")."))) - if (length(order) != x$k.all) - stop(mstyle$stop(paste0("Length of the 'order' argument (", length(order), ") does not correspond to the size of the original dataset (", x$k.all, ")."))) + } ### note: order variable must be of the same length as the original dataset - ### so we have to apply the same subsetting (if necessary) - ### as was done during model fitting - - order <- .getsubset(order, x$subset) - - order <- order(order, decreasing=decreasing) - - ai.f <- x$outdat.f$ai[order] - bi.f <- x$outdat.f$bi[order] - ci.f <- x$outdat.f$ci[order] - di.f <- x$outdat.f$di[order] - x1i.f <- x$outdat.f$x1i[order] - x2i.f <- x$outdat.f$x2i[order] - t1i.f <- x$outdat.f$t1i[order] - t2i.f <- x$outdat.f$t2i[order] - yi.f <- x$yi.f[order] - vi.f <- x$vi.f[order] + ### so apply the same subsetting as was done during the model fitting + + orvar <- .getsubset(orvar, x$subset) + + ### order data by the order variable (NAs in order variable are dropped) + + order <- base::order(orvar, decreasing=decreasing, na.last=NA) + + ai <- x$outdat.f$ai[order] + bi <- x$outdat.f$bi[order] + ci <- x$outdat.f$ci[order] + di <- x$outdat.f$di[order] + x1i <- x$outdat.f$x1i[order] + x2i <- x$outdat.f$x2i[order] + t1i <- x$outdat.f$t1i[order] + t2i <- x$outdat.f$t2i[order] + yi <- x$yi.f[order] + vi <- x$vi.f[order] not.na <- x$not.na[order] slab <- x$slab[order] ids <- x$ids[order] + orvar <- orvar[order] + if (inherits(x$data, "environment")) { data <- NULL } else { data <- x$data[order,] } - beta <- rep(NA_real_, x$k.f) - se <- rep(NA_real_, x$k.f) - zval <- rep(NA_real_, x$k.f) - pval <- rep(NA_real_, x$k.f) - ci.lb <- rep(NA_real_, x$k.f) - ci.ub <- rep(NA_real_, x$k.f) - QE <- rep(NA_real_, x$k.f) - QEp <- rep(NA_real_, x$k.f) - I2 <- rep(NA_real_, x$k.f) - H2 <- rep(NA_real_, x$k.f) + if (collapse) { + uorvar <- unique(orvar) + } else { + uorvar <- orvar + } - ### elements that need to be returned + k.o <- length(uorvar) + + k <- rep(NA_integer_, k.o) + beta <- rep(NA_real_, k.o) + se <- rep(NA_real_, k.o) + zval <- rep(NA_real_, k.o) + pval <- rep(NA_real_, k.o) + ci.lb <- rep(NA_real_, k.o) + ci.ub <- rep(NA_real_, k.o) + QE <- rep(NA_real_, k.o) + QEp <- rep(NA_real_, k.o) + I2 <- rep(NA_real_, k.o) + H2 <- rep(NA_real_, k.o) + show <- rep(TRUE, k.o) - outlist <- "beta=beta, se=se, zval=zval, pval=pval, ci.lb=ci.lb, ci.ub=ci.ub, QE=QE, QEp=QEp, tau2=tau2, I2=I2, H2=H2" + ### elements that need to be returned - ### note: skipping NA cases + outlist <- "k=k, beta=beta, se=se, zval=zval, pval=pval, ci.lb=ci.lb, ci.ub=ci.ub, QE=QE, QEp=QEp, I2=I2, H2=H2" if (progbar) - pbar <- pbapply::startpb(min=0, max=x$k.f) + pbar <- pbapply::startpb(min=0, max=k.o) - for (i in seq_len(x$k.f)) { + for (i in seq_len(k.o)) { if (progbar) pbapply::setpb(pbar, i) - if (!not.na[i]) - next + if (collapse) { + + if (all(!not.na[is.element(orvar, uorvar[i])])) { + if (na.act == "na.omit") + show[i] <- FALSE # if all studies to be added are !not.na, don't show (but a fit failure is still shown) + next + } + + incl <- is.element(orvar, uorvar[1:i]) + + } else { + + if (!not.na[i]) { + if (na.act == "na.omit") + show[i] <- FALSE # if study to be added is !not.na, don't show (but a fit failure is still shown) + next + } + + incl <- 1:i + + } if (is.element(x$measure, c("RR","OR","RD"))) { - args <- list(ai=ai.f, bi=bi.f, ci=ci.f, di=di.f, measure=x$measure, add=x$add, to=x$to, drop00=x$drop00, - correct=x$correct, level=x$level, subset=seq_len(i), outlist=outlist) + args <- list(ai=ai, bi=bi, ci=ci, di=di, measure=x$measure, add=x$add, to=x$to, drop00=x$drop00, + correct=x$correct, level=x$level, subset=incl, outlist=outlist) } else { - args <- list(x1i=x1i.f, x2i=x2i.f, t1i=t1i.f, t2i=t2i.f, measure=x$measure, add=x$add, to=x$to, drop00=x$drop00, - correct=x$correct, level=x$level, subset=seq_len(i), outlist=outlist) + args <- list(x1i=x1i, x2i=x2i, t1i=t1i, t2i=t2i, measure=x$measure, add=x$add, to=x$to, drop00=x$drop00, + correct=x$correct, level=x$level, subset=incl, outlist=outlist) } + res <- try(suppressWarnings(.do.call(rma.mh, args)), silent=TRUE) if (inherits(res, "try-error")) next + k[i] <- res$k beta[i] <- res$beta se[i] <- res$se zval[i] <- res$zval @@ -139,12 +178,12 @@ cumul.rma.mh <- function(x, order, digits, transf, targs, progbar=FALSE, ...) { if (is.function(transf)) { if (is.null(targs)) { beta <- sapply(beta, transf) - se <- rep(NA_real_, x$k.f) + se <- rep(NA_real_, k.o) ci.lb <- sapply(ci.lb, transf) ci.ub <- sapply(ci.ub, transf) } else { beta <- sapply(beta, transf, targs) - se <- rep(NA_real_, x$k.f) + se <- rep(NA_real_, k.o) ci.lb <- sapply(ci.lb, transf, targs) ci.ub <- sapply(ci.ub, transf, targs) } @@ -159,31 +198,29 @@ cumul.rma.mh <- function(x, order, digits, transf, targs, progbar=FALSE, ...) { ######################################################################### - if (na.act == "na.omit") { - out <- list(estimate=beta[not.na], se=se[not.na], zval=zval[not.na], pval=pval[not.na], ci.lb=ci.lb[not.na], ci.ub=ci.ub[not.na], Q=QE[not.na], Qp=QEp[not.na], I2=I2[not.na], H2=H2[not.na]) - out$slab <- slab[not.na] - out$ids <- ids[not.na] - out$data <- data[not.na,] - } + out <- list(k=k[show], estimate=beta[show], se=se[show], zval=zval[show], pval=pval[show], ci.lb=ci.lb[show], ci.ub=ci.ub[show], Q=QE[show], Qp=QEp[show], I2=I2[show], H2=H2[show]) - if (na.act == "na.exclude" || na.act == "na.pass") { - out <- list(estimate=beta, se=se, zval=zval, pval=pval, ci.lb=ci.lb, ci.ub=ci.ub, Q=QE, Qp=QEp, I2=I2, H2=H2) - out$slab <- slab - out$ids <- ids - out$data <- data + if (collapse) { + out$slab <- uorvar[show] + out$slab.null <- FALSE + } else { + out$slab <- slab[show] + out$ids <- ids[show] + out$data <- data[show,,drop=FALSE] + out$slab.null <- x$slab.null } - if (na.act == "na.fail" && any(!x$not.na)) - stop(mstyle$stop("Missing values in results.")) + out$order <- uorvar[show] - out$digits <- digits - out$transf <- transf - out$slab.null <- x$slab.null - out$level <- x$level - out$measure <- x$measure - out$test <- x$test + out$digits <- digits + out$transf <- transf + out$level <- x$level + out$test <- x$test - attr(out$estimate, "measure") <- x$measure + if (!transf) { + out$measure <- x$measure + attr(out$estimate, "measure") <- x$measure + } if (.isTRUE(ddd$time)) { time.end <- proc.time() diff --git a/R/cumul.rma.peto.r b/R/cumul.rma.peto.r index 11b1501da..917fe70d5 100644 --- a/R/cumul.rma.peto.r +++ b/R/cumul.rma.peto.r @@ -1,4 +1,4 @@ -cumul.rma.peto <- function(x, order, digits, transf, targs, progbar=FALSE, ...) { +cumul.rma.peto <- function(x, order, digits, transf, targs, collapse=FALSE, progbar=FALSE, ...) { mstyle <- .get.mstyle() @@ -9,6 +9,8 @@ cumul.rma.peto <- function(x, order, digits, transf, targs, progbar=FALSE, ...) if (!is.element(na.act, c("na.omit", "na.exclude", "na.fail", "na.pass"))) stop(mstyle$stop("Unknown 'na.action' specified under options().")) + if (na.act == "na.fail" && any(!x$not.na)) + stop(mstyle$stop("Missing values in data.")) if (missing(digits)) { digits <- .get.digits(xdigits=x$digits, dmiss=TRUE) @@ -34,75 +36,112 @@ cumul.rma.peto <- function(x, order, digits, transf, targs, progbar=FALSE, ...) ######################################################################### if (grepl("^order\\(", deparse1(substitute(order)))) - warning(mstyle$warning("Use of order() in 'order' argument is probably erroneous."), call.=FALSE) + warning(mstyle$warning("Use of order() in the 'order' argument is probably erroneous."), call.=FALSE) if (missing(order)) { - order <- seq_len(x$k.all) + + orvar <- seq_len(x$k.all) + collapse <- FALSE + } else { + mf <- match.call() - order <- .getx("order", mf=mf, data=x$data) - } + orvar <- .getx("order", mf=mf, data=x$data) + + if (length(orvar) != x$k.all) + stop(mstyle$stop(paste0("Length of the 'order' argument (", length(orvar), ") does not correspond to the size of the original dataset (", x$k.all, ")."))) - if (length(order) != x$k.all) - stop(mstyle$stop(paste0("Length of the 'order' argument (", length(order), ") does not correspond to the size of the original dataset (", x$k.all, ")."))) + } ### note: order variable must be of the same length as the original dataset - ### so we have to apply the same subsetting (if necessary) - ### as was done during model fitting + ### so apply the same subsetting as was done during the model fitting - order <- .getsubset(order, x$subset) + orvar <- .getsubset(orvar, x$subset) - order <- order(order, decreasing=decreasing) + ### order data by the order variable (NAs in order variable are dropped) - ai.f <- x$outdat.f$ai[order] - bi.f <- x$outdat.f$bi[order] - ci.f <- x$outdat.f$ci[order] - di.f <- x$outdat.f$di[order] - yi.f <- x$yi.f[order] - vi.f <- x$vi.f[order] + order <- base::order(orvar, decreasing=decreasing, na.last=NA) + + ai <- x$outdat.f$ai[order] + bi <- x$outdat.f$bi[order] + ci <- x$outdat.f$ci[order] + di <- x$outdat.f$di[order] + yi <- x$yi.f[order] + vi <- x$vi.f[order] not.na <- x$not.na[order] slab <- x$slab[order] ids <- x$ids[order] + orvar <- orvar[order] + if (inherits(x$data, "environment")) { data <- NULL } else { data <- x$data[order,] } - beta <- rep(NA_real_, x$k.f) - se <- rep(NA_real_, x$k.f) - zval <- rep(NA_real_, x$k.f) - pval <- rep(NA_real_, x$k.f) - ci.lb <- rep(NA_real_, x$k.f) - ci.ub <- rep(NA_real_, x$k.f) - QE <- rep(NA_real_, x$k.f) - QEp <- rep(NA_real_, x$k.f) - I2 <- rep(NA_real_, x$k.f) - H2 <- rep(NA_real_, x$k.f) + if (collapse) { + uorvar <- unique(orvar) + } else { + uorvar <- orvar + } - ### elements that need to be returned + k.o <- length(uorvar) + + k <- rep(NA_integer_, k.o) + beta <- rep(NA_real_, k.o) + se <- rep(NA_real_, k.o) + zval <- rep(NA_real_, k.o) + pval <- rep(NA_real_, k.o) + ci.lb <- rep(NA_real_, k.o) + ci.ub <- rep(NA_real_, k.o) + QE <- rep(NA_real_, k.o) + QEp <- rep(NA_real_, k.o) + I2 <- rep(NA_real_, k.o) + H2 <- rep(NA_real_, k.o) + show <- rep(TRUE, k.o) - outlist <- "beta=beta, se=se, zval=zval, pval=pval, ci.lb=ci.lb, ci.ub=ci.ub, QE=QE, QEp=QEp, tau2=tau2, I2=I2, H2=H2" + ### elements that need to be returned - ### note: skipping NA cases + outlist <- "k=k, beta=beta, se=se, zval=zval, pval=pval, ci.lb=ci.lb, ci.ub=ci.ub, QE=QE, QEp=QEp, I2=I2, H2=H2" if (progbar) - pbar <- pbapply::startpb(min=0, max=x$k.f) + pbar <- pbapply::startpb(min=0, max=k.o) - for (i in seq_len(x$k.f)) { + for (i in seq_len(k.o)) { if (progbar) pbapply::setpb(pbar, i) - if (!not.na[i]) - next + if (collapse) { + + if (all(!not.na[is.element(orvar, uorvar[i])])) { + if (na.act == "na.omit") + show[i] <- FALSE # if all studies to be added are !not.na, don't show (but a fit failure is still shown) + next + } + + incl <- is.element(orvar, uorvar[1:i]) + + } else { + + if (!not.na[i]) { + if (na.act == "na.omit") + show[i] <- FALSE # if study to be added is !not.na, don't show (but a fit failure is still shown) + next + } + + incl <- 1:i + + } + + args <- list(ai=ai, bi=bi, ci=ci, di=di, add=x$add, to=x$to, drop00=x$drop00, level=x$level, subset=incl, outlist=outlist) - args <- list(ai=ai.f, bi=bi.f, ci=ci.f, di=di.f, add=x$add, to=x$to, drop00=x$drop00, level=x$level, subset=seq_len(i), outlist=outlist) res <- try(suppressWarnings(.do.call(rma.peto, args)), silent=TRUE) if (inherits(res, "try-error")) next + k[i] <- res$k beta[i] <- res$beta se[i] <- res$se zval[i] <- res$zval @@ -129,12 +168,12 @@ cumul.rma.peto <- function(x, order, digits, transf, targs, progbar=FALSE, ...) if (is.function(transf)) { if (is.null(targs)) { beta <- sapply(beta, transf) - se <- rep(NA_real_, x$k.f) + se <- rep(NA_real_, k.o) ci.lb <- sapply(ci.lb, transf) ci.ub <- sapply(ci.ub, transf) } else { beta <- sapply(beta, transf, targs) - se <- rep(NA_real_, x$k.f) + se <- rep(NA_real_, k.o) ci.lb <- sapply(ci.lb, transf, targs) ci.ub <- sapply(ci.ub, transf, targs) } @@ -149,31 +188,29 @@ cumul.rma.peto <- function(x, order, digits, transf, targs, progbar=FALSE, ...) ######################################################################### - if (na.act == "na.omit") { - out <- list(estimate=beta[not.na], se=se[not.na], zval=zval[not.na], pval=pval[not.na], ci.lb=ci.lb[not.na], ci.ub=ci.ub[not.na], Q=QE[not.na], Qp=QEp[not.na], I2=I2[not.na], H2=H2[not.na]) - out$slab <- slab[not.na] - out$ids <- ids[not.na] - out$data <- data[not.na,] - } + out <- list(k=k[show], estimate=beta[show], se=se[show], zval=zval[show], pval=pval[show], ci.lb=ci.lb[show], ci.ub=ci.ub[show], Q=QE[show], Qp=QEp[show], I2=I2[show], H2=H2[show]) - if (na.act == "na.exclude" || na.act == "na.pass") { - out <- list(estimate=beta, se=se, zval=zval, pval=pval, ci.lb=ci.lb, ci.ub=ci.ub, Q=QE, Qp=QEp, I2=I2, H2=H2) - out$slab <- slab - out$ids <- ids - out$data <- data + if (collapse) { + out$slab <- uorvar[show] + out$slab.null <- FALSE + } else { + out$slab <- slab[show] + out$ids <- ids[show] + out$data <- data[show,,drop=FALSE] + out$slab.null <- x$slab.null } - if (na.act == "na.fail" && any(!x$not.na)) - stop(mstyle$stop("Missing values in results.")) + out$order <- uorvar[show] - out$digits <- digits - out$transf <- transf - out$slab.null <- x$slab.null - out$level <- x$level - out$measure <- x$measure - out$test <- x$test + out$digits <- digits + out$transf <- transf + out$level <- x$level + out$test <- x$test - attr(out$estimate, "measure") <- x$measure + if (!transf) { + out$measure <- x$measure + attr(out$estimate, "measure") <- x$measure + } if (.isTRUE(ddd$time)) { time.end <- proc.time() diff --git a/R/cumul.rma.uni.r b/R/cumul.rma.uni.r index ec4a2284b..3888e999d 100644 --- a/R/cumul.rma.uni.r +++ b/R/cumul.rma.uni.r @@ -1,4 +1,4 @@ -cumul.rma.uni <- function(x, order, digits, transf, targs, progbar=FALSE, ...) { +cumul.rma.uni <- function(x, order, digits, transf, targs, collapse=FALSE, progbar=FALSE, ...) { mstyle <- .get.mstyle() @@ -9,6 +9,9 @@ cumul.rma.uni <- function(x, order, digits, transf, targs, progbar=FALSE, ...) { if (!is.element(na.act, c("na.omit", "na.exclude", "na.fail", "na.pass"))) stop(mstyle$stop("Unknown 'na.action' specified under options().")) + if (na.act == "na.fail" && any(!x$not.na)) + stop(mstyle$stop("Missing values in data.")) + if (!x$int.only) stop(mstyle$stop("Method only applicable to models without moderators.")) @@ -36,75 +39,111 @@ cumul.rma.uni <- function(x, order, digits, transf, targs, progbar=FALSE, ...) { ######################################################################### if (grepl("^order\\(", deparse1(substitute(order)))) - warning(mstyle$warning("Use of order() in 'order' argument is probably erroneous."), call.=FALSE) + warning(mstyle$warning("Use of order() in the 'order' argument is probably erroneous."), call.=FALSE) if (missing(order)) { - order <- seq_len(x$k.all) + + orvar <- seq_len(x$k.all) + collapse <- FALSE + } else { + mf <- match.call() - order <- .getx("order", mf=mf, data=x$data) - } + orvar <- .getx("order", mf=mf, data=x$data) + + if (length(orvar) != x$k.all) + stop(mstyle$stop(paste0("Length of the 'order' argument (", length(orvar), ") does not correspond to the size of the original dataset (", x$k.all, ")."))) - if (length(order) != x$k.all) - stop(mstyle$stop(paste0("Length of the 'order' argument (", length(order), ") does not correspond to the size of the original dataset (", x$k.all, ")."))) + } ### note: order variable must be of the same length as the original dataset - ### so we have to apply the same subsetting (if necessary) - ### as was done during model fitting + ### so apply the same subsetting as was done during the model fitting + + orvar <- .getsubset(orvar, x$subset) - order <- .getsubset(order, x$subset) + ### order data by the order variable (NAs in order variable are dropped) - order <- order(order, decreasing=decreasing) + order <- base::order(orvar, decreasing=decreasing, na.last=NA) + + yi <- x$yi.f[order] + vi <- x$vi.f[order] + weights <- x$weights.f[order] + not.na <- x$not.na[order] + slab <- x$slab[order] + ids <- x$ids[order] + orvar <- orvar[order] - yi.f <- x$yi.f[order] - vi.f <- x$vi.f[order] - weights.f <- x$weights.f[order] - not.na <- x$not.na[order] - slab <- x$slab[order] - ids <- x$ids[order] if (inherits(x$data, "environment")) { data <- NULL } else { - data <- x$data[order,] + data <- x$data[order,,drop=FALSE] } - beta <- rep(NA_real_, x$k.f) - se <- rep(NA_real_, x$k.f) - zval <- rep(NA_real_, x$k.f) - pval <- rep(NA_real_, x$k.f) - ci.lb <- rep(NA_real_, x$k.f) - ci.ub <- rep(NA_real_, x$k.f) - QE <- rep(NA_real_, x$k.f) - QEp <- rep(NA_real_, x$k.f) - tau2 <- rep(NA_real_, x$k.f) - I2 <- rep(NA_real_, x$k.f) - H2 <- rep(NA_real_, x$k.f) + if (collapse) { + uorvar <- unique(orvar) + } else { + uorvar <- orvar + } - ### elements that need to be returned + k.o <- length(uorvar) + + k <- rep(NA_integer_, k.o) + beta <- rep(NA_real_, k.o) + se <- rep(NA_real_, k.o) + zval <- rep(NA_real_, k.o) + pval <- rep(NA_real_, k.o) + ci.lb <- rep(NA_real_, k.o) + ci.ub <- rep(NA_real_, k.o) + QE <- rep(NA_real_, k.o) + QEp <- rep(NA_real_, k.o) + tau2 <- rep(NA_real_, k.o) + I2 <- rep(NA_real_, k.o) + H2 <- rep(NA_real_, k.o) + show <- rep(TRUE, k.o) - outlist <- "beta=beta, se=se, zval=zval, pval=pval, ci.lb=ci.lb, ci.ub=ci.ub, QE=QE, QEp=QEp, tau2=tau2, I2=I2, H2=H2" + ### elements that need to be returned - ### note: skipping NA cases - ### also: it is possible that model fitting fails, so that generates more NAs (these NAs will always be shown in output) + outlist <- "k=k, beta=beta, se=se, zval=zval, pval=pval, ci.lb=ci.lb, ci.ub=ci.ub, QE=QE, QEp=QEp, tau2=tau2, I2=I2, H2=H2" if (progbar) - pbar <- pbapply::startpb(min=0, max=x$k.f) + pbar <- pbapply::startpb(min=0, max=k.o) - for (i in seq_len(x$k.f)) { + for (i in seq_len(k.o)) { if (progbar) pbapply::setpb(pbar, i) - if (!not.na[i]) - next + if (collapse) { + + if (all(!not.na[is.element(orvar, uorvar[i])])) { + if (na.act == "na.omit") + show[i] <- FALSE # if all studies to be added are !not.na, don't show (but a fit failure is still shown) + next + } + + incl <- is.element(orvar, uorvar[1:i]) + + } else { + + if (!not.na[i]) { + if (na.act == "na.omit") + show[i] <- FALSE # if study to be added is !not.na, don't show (but a fit failure is still shown) + next + } + + incl <- 1:i + + } + + args <- list(yi=yi, vi=vi, weights=weights, intercept=TRUE, method=x$method, weighted=x$weighted, + test=x$test, level=x$level, tau2=ifelse(x$tau2.fix, x$tau2, NA), control=x$control, subset=incl, outlist=outlist) - args <- list(yi=yi.f, vi=vi.f, weights=weights.f, intercept=TRUE, method=x$method, weighted=x$weighted, - test=x$test, level=x$level, tau2=ifelse(x$tau2.fix, x$tau2, NA), control=x$control, subset=seq_len(i), outlist=outlist) res <- try(suppressWarnings(.do.call(rma.uni, args)), silent=TRUE) if (inherits(res, "try-error")) next + k[i] <- res$k beta[i] <- res$beta se[i] <- res$se zval[i] <- res$zval @@ -129,12 +168,12 @@ cumul.rma.uni <- function(x, order, digits, transf, targs, progbar=FALSE, ...) { if (is.function(transf)) { if (is.null(targs)) { beta <- sapply(beta, transf) - se <- rep(NA_real_, x$k.f) + se <- rep(NA_real_, k.o) ci.lb <- sapply(ci.lb, transf) ci.ub <- sapply(ci.ub, transf) } else { beta <- sapply(beta, transf, targs) - se <- rep(NA_real_, x$k.f) + se <- rep(NA_real_, k.o) ci.lb <- sapply(ci.lb, transf, targs) ci.ub <- sapply(ci.ub, transf, targs) } @@ -149,39 +188,37 @@ cumul.rma.uni <- function(x, order, digits, transf, targs, progbar=FALSE, ...) { ######################################################################### - if (na.act == "na.omit") { - out <- list(estimate=beta[not.na], se=se[not.na], zval=zval[not.na], pvals=pval[not.na], ci.lb=ci.lb[not.na], ci.ub=ci.ub[not.na], Q=QE[not.na], Qp=QEp[not.na], tau2=tau2[not.na], I2=I2[not.na], H2=H2[not.na]) - out$slab <- slab[not.na] - out$ids <- ids[not.na] - out$data <- data[not.na,] - } + out <- list(k=k[show], estimate=beta[show], se=se[show], zval=zval[show], pval=pval[show], ci.lb=ci.lb[show], ci.ub=ci.ub[show], Q=QE[show], Qp=QEp[show], tau2=tau2[show], I2=I2[show], H2=H2[show]) - if (na.act == "na.exclude" || na.act == "na.pass") { - out <- list(estimate=beta, se=se, zval=zval, pvals=pval, ci.lb=ci.lb, ci.ub=ci.ub, Q=QE, Qp=QEp, tau2=tau2, I2=I2, H2=H2) - out$slab <- slab - out$ids <- ids - out$data <- data + if (collapse) { + out$slab <- uorvar[show] + out$slab.null <- FALSE + } else { + out$slab <- slab[show] + out$ids <- ids[show] + out$data <- data[show,,drop=FALSE] + out$slab.null <- x$slab.null } - if (na.act == "na.fail" && any(!x$not.na)) - stop(mstyle$stop("Missing values in results.")) + out$order <- uorvar[show] if (is.element(x$test, c("knha","adhoc","t"))) - names(out)[3] <- "tval" + names(out)[4] <- "tval" ### remove tau2 for FE/EE/CE models if (is.element(x$method, c("FE","EE","CE"))) - out <- out[-9] + out <- out[-10] - out$digits <- digits - out$transf <- transf - out$slab.null <- x$slab.null - out$level <- x$level - out$measure <- x$measure - out$test <- x$test + out$digits <- digits + out$transf <- transf + out$level <- x$level + out$test <- x$test - attr(out$estimate, "measure") <- x$measure + if (!transf) { + out$measure <- x$measure + attr(out$estimate, "measure") <- x$measure + } if (.isTRUE(ddd$time)) { time.end <- proc.time() diff --git a/R/forest.cumul.rma.r b/R/forest.cumul.rma.r index c217744b8..01fdff287 100644 --- a/R/forest.cumul.rma.r +++ b/R/forest.cumul.rma.r @@ -1,6 +1,6 @@ forest.cumul.rma <- function(x, annotate=TRUE, header=FALSE, -xlim, alim, olim, ylim, at, steps=5, level=x$level, refline=0, digits=2L, width, +xlim, alim, olim, ylim, at, steps=5, refline=0, digits=2L, width, xlab, ilab, ilab.lab, ilab.xpos, ilab.pos, transf, atransf, targs, rows, efac=1, pch, psize, col, shade, colshade, @@ -17,6 +17,9 @@ lty, fonts, cex, cex.lab, cex.axis, ...) { if (!is.element(na.act, c("na.omit", "na.exclude", "na.fail", "na.pass"))) stop(mstyle$stop("Unknown 'na.action' specified under options().")) + if (x$transf) # if results were transformed, need x$se not be missing below (not really used anyway) + x$se <- rep(0, length(x$estimate)) + if (missing(transf)) transf <- FALSE @@ -92,7 +95,7 @@ lty, fonts, cex, cex.lab, cex.axis, ...) { if (missing(cex.axis)) cex.axis <- NULL - level <- .level(level) + level <- .level(x$level) ### digits[1] for annotations, digits[2] for x-axis labels ### note: digits can also be a list (e.g., digits=list(2,3L)); trailing 0's on the x-axis labels @@ -230,7 +233,7 @@ lty, fonts, cex, cex.lab, cex.axis, ...) { ### note: ilab, pch, psize, col must be of the same length as yi (which may ### or may not contain NAs; this is different than the other forest() - ### functions but it would be tricky to make this fully consistent now + ### functions but it would be tricky to make this fully consistent now) if (x$slab.null) { slab <- paste("+ Study", x$ids) # cumul() removes the studies with NAs when na.action="na.omit" diff --git a/R/misc.func.hidden.r b/R/misc.func.hidden.r index bb4d57fa2..c4b4012f1 100644 --- a/R/misc.func.hidden.r +++ b/R/misc.func.hidden.r @@ -444,7 +444,8 @@ ux <- unique(x) for (i in seq_along(ux)) { - xiTF <- x == ux[i] + #xiTF <- x == ux[i] + xiTF <- x %in% ux[i] # works also with NAs in vector (multiple NAs are then NA.1, NA.2, ...) xi <- x[xiTF] if (length(xi) == 1L) next diff --git a/R/print.list.rma.r b/R/print.list.rma.r index 674e3d9fe..68b3f0253 100644 --- a/R/print.list.rma.r +++ b/R/print.list.rma.r @@ -65,7 +65,7 @@ print.list.rma <- function(x, digits=x$digits, ...) { out[,i] <- fmtx(out[,i], digits[["se"]]) if (names(out)[i] %in% c("ci.lb", "ci.ub", "cr.lb", "cr.ub", "pi.lb", "pi.ub")) out[,i] <- fmtx(out[,i], digits[["ci"]]) - if (names(out)[i] %in% c("zval", "Q", "z", "X2")) + if (names(out)[i] %in% c("zval", "tval", "Q", "z", "X2")) out[,i] <- fmtx(out[,i], digits[["test"]]) if (names(out)[i] %in% c("pval", "Qp")) out[,i] <- fmtx(out[,i], digits[["pval"]]) @@ -73,6 +73,8 @@ print.list.rma <- function(x, digits=x$digits, ...) { out[,i] <- fmtx(out[,i], digits[["het"]]) if (names(out)[i] %in% c("tau2")) out[,i] <- fmtx(out[,i], digits[["var"]]) + if (names(out)[i] %in% c("k")) + out[,i] <- fmtx(out[,i], 0) # if (names(out)[i] == "rstudent") # out[,i] <- fmtx(out[,i], digits[["test"]]) # if (names(out)[i] == "dffits") diff --git a/R/zzz.r b/R/zzz.r index eaceeb75a..d4f8f983e 100644 --- a/R/zzz.r +++ b/R/zzz.r @@ -1,6 +1,6 @@ .onAttach <- function(libname, pkgname) { - ver <- "4.7-23" + ver <- "4.7-24" loadmsg <- paste0("\nLoading the 'metafor' package (version ", ver, "). For an\nintroduction to the package please type: help(metafor)\n") diff --git a/README.md b/README.md index 05aaaa830..85d6a5690 100644 --- a/README.md +++ b/README.md @@ -5,7 +5,7 @@ metafor: A Meta-Analysis Package for R [![R build status](https://github.com/wviechtb/metafor/workflows/R-CMD-check/badge.svg)](https://github.com/wviechtb/metafor/actions) [![Code Coverage](https://codecov.io/gh/wviechtb/metafor/branch/master/graph/badge.svg)](https://app.codecov.io/gh/wviechtb/metafor) [![CRAN Version](https://www.r-pkg.org/badges/version/metafor)](https://cran.r-project.org/package=metafor) -[![devel Version](https://img.shields.io/badge/devel-4.7--23-brightgreen.svg)](https://www.metafor-project.org/doku.php/installation#development_version) +[![devel Version](https://img.shields.io/badge/devel-4.7--24-brightgreen.svg)](https://www.metafor-project.org/doku.php/installation#development_version) [![Monthly Downloads](https://cranlogs.r-pkg.org/badges/metafor)](https://cranlogs.r-pkg.org/badges/metafor) [![Total Downloads](https://cranlogs.r-pkg.org/badges/grand-total/metafor)](https://cranlogs.r-pkg.org/badges/grand-total/metafor) diff --git a/docs/404.html b/docs/404.html index 75fca6f9d..f664f35b8 100644 --- a/docs/404.html +++ b/docs/404.html @@ -40,7 +40,7 @@
- + - + @@ -113,7 +113,7 @@ - +The diagram below shows the various functions in the metafor package (and how they are related to each other). If the package is installed, you should also be able to open this diagram directly from R with the command vignette("diagram")
. The image below should also be clickable (to see a larger version of it).
The diagram below shows the various functions in the metafor package (and how they are related to each other). If the package is installed, you should also be able to open this diagram directly from R with the command vignette("diagram")
. The image below should also be clickable (to see a larger version of it).
the predict.rma()
and predict.rma.ls()
functions now also accept a matrix as input that includes a column for the intercept term (in which case the intercept
argument is ignored)
added collapse
argument to the various cumul()
functions
the predict.rma()
and predict.rma.ls()
functions now also accept a matrix as input that includes a column for the intercept term (in which case the intercept
argument is ignored)
added pairwise()
function to construct a matrix of pairwise contrasts
anova()
and predict()
gain adjust
argument for adjusting p-values / interval bounds for multiple testing
print.anova.rma()
and print.list.anova.rma()
also print significance stars for some types of outcomes (unless getOption("show.signif.stars")
is FALSE
)
addpoly.default.Rd
# S3 method for default
+ # Default S3 method
addpoly(x, vi, sei, ci.lb, ci.ub, pi.lb, pi.ub,
rows=-1, level, annotate, digits, width, mlab,
transf, atransf, targs, efac, col, border, lty, fonts, cex,
@@ -104,76 +104,77 @@ Add Polygons to Forest Plots (Default Method)
Arguments
- - x
+
+- x
vector with the values at which the polygons should be drawn.
- - vi
+ - vi
vector with the corresponding variances.
- - sei
+ - sei
vector with the corresponding standard errors (note: only one of the two, vi
or sei
, needs to be specified).
- - ci.lb
+ - ci.lb
vector with the corresponding lower confidence interval bounds. Not needed if vi
or sei
is specified. See ‘Details’.
- - ci.ub
+ - ci.ub
vector with the corresponding upper confidence interval bounds. Not needed if vi
or sei
is specified. See ‘Details’.
- - pi.lb
+ - pi.lb
optional vector with the corresponding lower prediction interval bounds.
- - pi.ub
+ - pi.ub
optional vector with the corresponding upper prediction interval bounds.
- - rows
+ - rows
vector to specify the rows (or more generally, the horizontal positions) for plotting the polygons (defaults is -1
). Can also be a single value to specify the row (horizontal position) of the first polygon (the remaining polygons are then plotted below this starting row).
- - level
+ - level
optional numeric value between 0 and 100 to specify the confidence interval level (see here for details).
- - annotate
+ - annotate
optional logical to specify whether annotations should be added to the plot for the polygons that are drawn.
- - digits
+ - digits
optional integer to specify the number of decimal places to which the annotations should be rounded.
- - width
+ - width
optional integer to manually adjust the width of the columns for the annotations.
- - mlab
+ - mlab
optional character vector with the same length as x
giving labels for the polygons that are drawn.
- - transf
+ - transf
optional argument to specify a function to transform the x
values and confidence interval bounds (e.g., transf=exp
; see also transf).
- - atransf
+ - atransf
optional argument to specify a function to transform the annotations (e.g., atransf=exp
; see also transf).
- - targs
+ - targs
optional arguments needed by the function specified via transf
or atransf
.
- - efac
+ - efac
optional vertical expansion factor for the polygons.
- - col
+ - col
optional character string to specify the color of the polygons.
- - border
+ - border
optional character string to specify the border color of the polygons.
- - lty
+ - lty
optional character string to specify the line type for the prediction interval.
- - fonts
+ - fonts
optional character string to specify the font for the labels and annotations.
- - cex
+ - cex
optional symbol expansion factor.
- - constarea
+ - constarea
logical to specify whether the height of the polygons (when adding multiple) should be adjusted so that the area of the polygons is constant (the default is FALSE
).
- - ...
+ - ...
other arguments.
@@ -231,17 +232,17 @@ Examples
addpoly.Rd
addpoly.predict.rma.Rd
# S3 method for predict.rma
+ # S3 method for class 'predict.rma'
addpoly(x, rows=-2, annotate,
addpred=FALSE, digits, width, mlab, transf, atransf, targs,
efac, col, border, lty, fonts, cex, constarea=FALSE, ...)
@@ -103,58 +103,59 @@ Add Polygons to Forest Plots (Method for 'predict.rma' Objects)
Arguments
- - x
+
+- x
an object of class "predict.rma"
.
- - rows
+ - rows
vector to specify the rows (or more generally, the horizontal positions) for plotting the polygons (defaults is -2
). Can also be a single value to specify the row (horizontal position) of the first polygon (the remaining polygons are then plotted below this starting row).
- - annotate
+ - annotate
optional logical to specify whether annotations should be added to the plot for the polygons that are drawn.
- - addpred
+ - addpred
logical to specify whether the bounds of the prediction interval should be added to the plot (the default is FALSE
).
- - digits
+ - digits
optional integer to specify the number of decimal places to which the annotations should be rounded.
- - width
+ - width
optional integer to manually adjust the width of the columns for the annotations.
- - mlab
+ - mlab
optional character vector with the same length as x
giving labels for the polygons that are drawn.
- - transf
+ - transf
optional argument to specify a function to transform the x
values and confidence interval bounds (e.g., transf=exp
; see also transf).
- - atransf
+ - atransf
optional argument to specify a function to transform the annotations (e.g., atransf=exp
; see also transf).
- - targs
+ - targs
optional arguments needed by the function specified via transf
or atransf
.
- - efac
+ - efac
optional vertical expansion factor for the polygons.
- - col
+ - col
optional character string to specify the color of the polygons.
- - border
+ - border
optional character string to specify the border color of the polygons.
- - lty
+ - lty
optional character string to specify the line type for the prediction interval.
- - fonts
+ - fonts
optional character string to specify the font for the labels and annotations.
- - cex
+ - cex
optional symbol expansion factor.
- - constarea
+ - constarea
logical to specify whether the height of the polygons (when adding multiple) should be adjusted so that the area of the polygons is constant (the default is FALSE
).
- - ...
+ - ...
other arguments.
@@ -215,17 +216,17 @@ Examples
addpoly.rma.Rd
# S3 method for rma
+ # S3 method for class 'rma'
addpoly(x, row=-2, level=x$level, annotate,
addpred=FALSE, digits, width, mlab, transf, atransf, targs,
efac, col, border, lty, fonts, cex, ...)
@@ -103,58 +103,59 @@ Add Polygons to Forest Plots (Method for 'rma' Objects)
Arguments
- - x
+
+- x
an object of class "rma"
.
- - row
+ - row
numeric value to specify the row (or more generally, the horizontal position) for plotting the polygon (the default is -2
).
- - level
+ - level
numeric value between 0 and 100 to specify the confidence interval level (see here for details). The default is to take the value from the object.
- - annotate
+ - annotate
optional logical to specify whether annotations for the summary estimate should be added to the plot.
- - addpred
+ - addpred
logical to specify whether the bounds of the prediction interval should be added to the plot (the default is FALSE
).
- - digits
+ - digits
optional integer to specify the number of decimal places to which the annotations should be rounded.
- - width
+ - width
optional integer to manually adjust the width of the columns for the annotations.
- - mlab
+ - mlab
optional character string giving a label for the summary estimate polygon. If unspecified, the function sets a default label.
- - transf
+ - transf
optional argument to specify a function to transform the summary estimate and confidence interval bound (e.g., transf=exp
; see also transf).
- - atransf
+ - atransf
optional argument to specify a function to transform the annotations (e.g., atransf=exp
; see also transf).
- - targs
+ - targs
optional arguments needed by the function specified via transf
or atransf
.
- - efac
+ - efac
optional vertical expansion factor for the polygon.
- - col
+ - col
optional character string to specify the color of the polygon.
- - border
+ - border
optional character string to specify the border color of the polygon.
- - lty
+ - lty
optional character string to specify the line type for the prediction interval.
- - fonts
+ - fonts
optional character string to specify the font for the label and annotations.
- - cex
+ - cex
optional symbol expansion factor.
- - ...
+ - ...
other arguments.
@@ -227,17 +228,17 @@ Examples
aggregate.escalc.Rd
# S3 method for escalc
+ # S3 method for class 'escalc'
aggregate(x, cluster, time, obs, V, struct="CS", rho, phi,
weighted=TRUE, checkpd=TRUE, fun, na.rm=TRUE,
addk=FALSE, subset, select, digits, var.names, ...)
@@ -103,58 +103,59 @@ Aggregate Multiple Effect Sizes or Outcomes Within Studies
Arguments
- - x
+
+- x
an object of class "escalc"
.
- - cluster
+ - cluster
vector to specify the clustering variable (e.g., study).
- - time
+ - time
optional vector to specify the time points (only relevant when struct="CAR"
, "CS+CAR"
, or "CS*CAR"
).
- - obs
+ - obs
optional vector to distinguish different observed effect sizes or outcomes measured at the same time point (only relevant when struct="CS*CAR"
).
- - V
+ - V
optional argument to specify the variance-covariance matrix of the sampling errors. If unspecified, argument struct
is used to specify the variance-covariance structure.
- - struct
+ - struct
character string to specify the variance-covariance structure of the sampling errors within the same cluster (either "ID"
, "CS"
, "CAR"
, "CS+CAR"
, or "CS*CAR"
). See ‘Details’.
- - rho
+ - rho
value of the correlation of the sampling errors within clusters (when struct="CS"
, "CS+CAR"
, or "CS*CAR"
). Can also be a vector with the value of the correlation for each cluster.
- - phi
+ - phi
value of the autocorrelation of the sampling errors within clusters (when struct="CAR"
, "CS+CAR"
, or "CS*CAR"
). Can also be a vector with the value of the autocorrelation for each cluster.
- - weighted
+ - weighted
logical to specify whether estimates within clusters should be aggregated using inverse-variance weighting (the default is TRUE
). If set to FALSE
, unweighted averages are computed.
- - checkpd
+ - checkpd
logical to specify whether to check that the variance-covariance matrices of the sampling errors within clusters are positive definite (the default is TRUE
).
- - fun
+ - fun
optional list with three functions for aggregating other variables besides the effect sizes or outcomes within clusters (for numeric/integer variables, for logicals, and for all other types, respectively).
- - na.rm
+ - na.rm
logical to specify whether NA
values should be removed before aggregating values within clusters (the default is TRUE
). Can also be a vector with two logicals (the first pertaining to the effect sizes or outcomes, the second to all other variables).
- - addk
+ - addk
logical to specify whether to add the cluster size as a new variable (called ki
) to the dataset (the default is FALSE
).
- - subset
+ - subset
optional (logical or numeric) vector to specify the subset of rows to include when aggregating the effect sizes or outcomes.
- - select
+ - select
optional vector to specify the names of the variables to include in the aggregated dataset.
- - digits
+ - digits
optional integer to specify the number of decimal places to which the printed results should be rounded (the default is to take the value from the object).
- - var.names
+ - var.names
optional character vector with two elements to specify the name of the variable that contains the observed effect sizes or outcomes and the name of the variable with the corresponding sampling variances (when unspecified, the function attempts to set these automatically based on the object).
- - ...
+ - ...
other arguments.
@@ -175,11 +176,7 @@ Details
An object of class c("escalc","data.frame")
that contains the (selected) variables aggregated to the cluster level.
An object of class c("escalc","data.frame")
that contains the (selected) variables aggregated to the cluster level.
The object is formatted and printed with the print
function.
anova.rma.Rd
# S3 method for rma
+ # S3 method for class 'rma'
anova(object, object2, btt, X, att, Z, rhs, adjust, digits, refit=FALSE, ...)
an object of class "rma.uni"
or "rma.mv"
.
an (optional) object of class "rma.uni"
or "rma.mv"
. Only relevant when conducting a model comparison and likelihood ratio test. See ‘Details’.
optional vector of indices (or list thereof) to specify which coefficients should be included in the Wald-type test. Can also be a string to grep
for. See ‘Details’.
optional numeric vector or matrix to specify one or more linear combinations of the coefficients in the model that should be tested. See ‘Details’.
optional vector of indices (or list thereof) to specify which scale coefficients should be included in the Wald-type test. Can also be a string to grep
for. See ‘Details’. Only relevant for location-scale models (see rma.uni
).
optional numeric vector or matrix to specify one or more linear combinations of the scale coefficients in the model that should be tested. See ‘Details’. Only relevant for location-scale models (see rma.uni
).
optional scalar or vector of values for the right-hand side of the null hypothesis when testing a set of coefficients (via btt
or att
) or linear combinations thereof (via X
or Z
). If unspecified, this defaults to a vector of zeros of the appropriate length. See ‘Details’.
optional argument to specify (as a character string) a method for adjusting the p-values of Wald-type tests for multiple testing. See p.adjust
for possible options. Can be abbreviated. Can also be a logical and if TRUE
, then a Bonferroni correction is used.
optional integer to specify the number of decimal places to which the printed results should be rounded. If unspecified, the default is to take the value from the object.
logical to specify whether models fitted with REML estimation and differing in their fixed effects should be refitted with ML estimation when conducting a likelihood ratio test (the default is FALSE
).
other arguments.
An object of class "anova.rma"
. When a single model is specified (without any further arguments or together with the btt
or att
argument), the object is a list containing the following components:
An object of class "anova.rma"
. When a single model is specified (without any further arguments or together with the btt
or att
argument), the object is a list containing the following components:
test statistic of the Wald-type test of the model coefficients.
some additional elements/values.
When btt
or att
was a list, then the object is a list of class "list.anova.rma"
, where each element is an "anova.rma"
object as described above.
When argument X
is used, the object is a list containing the following components:
test statistic of the omnibus Wald-type test of all linear combinations.
baujat.Rd
baujat(x, ...)
-# S3 method for rma
+# S3 method for class 'rma'
baujat(x, xlim, ylim, xlab, ylab, cex, symbol="ids", grid=TRUE, progbar=FALSE, ...)
an object of class "rma"
.
x-axis limits. If unspecified, the function sets the x-axis limits to some sensible values.
y-axis limits. If unspecified, the function sets the y-axis limits to some sensible values.
title for the x-axis. If unspecified, the function sets an appropriate axis title.
title for the y-axis. If unspecified, the function sets an appropriate axis title.
symbol/character expansion factor.
either an integer to specify the pch
value (i.e., plotting symbol), or "slab"
to plot the study labels, or "ids"
(the default) to plot the study id numbers.
logical to specify whether a grid should be added to the plot. Can also be a color name.
logical to specify whether a progress bar should be shown (the default is FALSE
).
other arguments.
A data frame with components:
+A data frame with components:
the x-axis coordinates of the points that were plotted.
bldiag.Rd
blsplit.Rd
a block diagonal matrix.
vector to specify the clustering variable to use for splitting.
optional argument to specify a function to apply to each sub-matrix.
optional argument to specify any additional argument(s) for the function specified via fun
.
logical to specify whether to sort the list by the unique cluster values (the default is FALSE
).
A list of one or more sub-matrices.
+A list of one or more sub-matrices.
blup.Rd
blup(x, ...)
-# S3 method for rma.uni
+# S3 method for class 'rma.uni'
blup(x, level, digits, transf, targs, ...)
an object of class "rma.uni"
.
numeric value between 0 and 100 to specify the prediction interval level (see here for details). If unspecified, the default is to take the value from the object.
optional integer to specify the number of decimal places to which the printed results should be rounded. If unspecified, the default is to take the value from the object.
optional argument to specify a function to transform the predicted values and interval bounds (e.g., transf=exp
; see also transf). If unspecified, no transformation is used.
optional arguments needed by the function specified under transf
.
other arguments.
An object of class "list.rma"
. The object is a list containing the following components:
An object of class "list.rma"
. The object is a list containing the following components:
predicted values.
coef.permutest.rma.uni.Rd
# S3 method for permutest.rma.uni
+ # S3 method for class 'permutest.rma.uni'
coef(object, ...)
A data frame with the following elements:
+A data frame with the following elements:
estimated model coefficient(s).
coef.rma.Rd
# S3 method for rma
+ # S3 method for class 'rma'
coef(object, ...)
-# S3 method for summary.rma
+# S3 method for class 'summary.rma'
coef(object, ...)
Either a vector with the estimated model coefficient(s) or a data frame with the following elements:
+Either a vector with the estimated model coefficient(s) or a data frame with the following elements:
estimated model coefficient(s).
confint.rma.Rd
# S3 method for rma.uni
+ # S3 method for class 'rma.uni'
confint(object, parm, level, fixed=FALSE, random=TRUE, type,
digits, transf, targs, verbose=FALSE, control, ...)
-# S3 method for rma.mh
+# S3 method for class 'rma.mh'
confint(object, parm, level, digits, transf, targs, ...)
-# S3 method for rma.peto
+# S3 method for class 'rma.peto'
confint(object, parm, level, digits, transf, targs, ...)
-# S3 method for rma.glmm
+# S3 method for class 'rma.glmm'
confint(object, parm, level, digits, transf, targs, ...)
-# S3 method for rma.mv
+# S3 method for class 'rma.mv'
confint(object, parm, level, fixed=FALSE, sigma2, tau2, rho, gamma2, phi,
digits, transf, targs, verbose=FALSE, control, ...)
-# S3 method for rma.uni.selmodel
+# S3 method for class 'rma.uni.selmodel'
confint(object, parm, level, fixed=FALSE, tau2, delta,
digits, transf, targs, verbose=FALSE, control, ...)
-# S3 method for rma.ls
+# S3 method for class 'rma.ls'
confint(object, parm, level, fixed=FALSE, alpha,
digits, transf, targs, verbose=FALSE, control, ...)
an object of class "rma.uni"
, "rma.mh"
, "rma.peto"
, "rma.mv"
, "rma.uni.selmodel"
, or "rma.ls"
. The method is not yet implemented for objects of class "rma.glmm"
.
this argument is here for compatibility with the generic function confint
, but is (currently) ignored.
logical to specify whether confidence intervals for the model coefficients should be returned.
logical to specify whether a confidence interval for the amount of (residual) heterogeneity should be returned.
optional character string to specify the method for computing the confidence interval for the amount of (residual) heterogeneity (either "QP"
, "GENQ"
, "PL"
, or "HT"
).
integer to specify for which \(\sigma^2\) parameter a confidence interval should be obtained.
integer to specify for which \(\tau^2\) parameter a confidence interval should be obtained.
integer to specify for which \(\rho\) parameter the confidence interval should be obtained.
integer to specify for which \(\gamma^2\) parameter a confidence interval should be obtained.
integer to specify for which \(\phi\) parameter a confidence interval should be obtained.
integer to specify for which \(\delta\) parameter a confidence interval should be obtained.
integer to specify for which \(\alpha\) parameter a confidence interval should be obtained.
numeric value between 0 and 100 to specify the confidence interval level (see here for details). If unspecified, the default is to take the value from the object.
optional integer to specify the number of decimal places to which the results should be rounded. If unspecified, the default is to take the value from the object.
optional argument to specify a function to transform the model coefficients and interval bounds (e.g., transf=exp
; see also transf). If unspecified, no transformation is used.
optional arguments needed by the function specified under transf
.
logical to specify whether output should be generated on the progress of the iterative algorithms used to obtain the confidence intervals (the default is FALSE
). See ‘Details’.
list of control values for the iterative algorithms. If unspecified, default values are used. See ‘Note’.
other arguments.
An object of class "confint.rma"
. The object is a list with either one or two elements (named fixed
and random
) with the following elements:
An object of class "confint.rma"
. The object is a list with either one or two elements (named fixed
and random
) with the following elements:
estimate of the model coefficient, variance/correlation component, or selection model parameter.
When obtaining confidence intervals for multiple components, the object is a list of class "list.confint.rma"
, where each element is a "confint.rma"
object as described above.
The results are formatted and printed with the print
function. To format the results as a data frame, one can use the as.data.frame
function.
contrmat.Rd
a data frame in wide format.
either the name (given as a character string) or the position (given as a single number) of the first group variable in the data frame.
either the name (given as a character string) or the position (given as a single number) of the second group variable in the data frame.
optional character string to specify which group will be placed in the last column of the matrix (must be one of the groups in the group variables). If not given, the most frequently occurring second group is placed last.
logical to specify whether the variable names corresponding to the group names should be shortened (the default is FALSE
).
integer to specify the minimum length of the shortened variable names (the default is 2).
logical to specify whether the variables names should be checked to ensure that they are syntactically valid variable names and if not, they are adjusted (by make.names
) so that they are (the default is TRUE
).
logical to specify whether the contrast matrix should be appended to the data frame specified via the data
argument (the default is TRUE
). If append=FALSE
, only the contrast matrix is returned.
A matrix with as many variables as there are groups.
+A matrix with as many variables as there are groups.
conv.2x2.Rd
optional vector with the odds ratios corresponding to the tables.
optional vector with the phi coefficients corresponding to the tables.
optional vector with the (signed) chi-square statistics corresponding to the tables.
vector with the total sample sizes.
vector with the marginal counts for the outcome of interest on the first variable.
vector with the marginal counts for the outcome of interest on the second variable.
optional logical (or vector thereof) to specify whether chi-square statistics were computed using Yates's correction for continuity (the default is TRUE
).
optional data frame containing the variables given to the arguments above.
optional (logical or numeric) vector to specify the subset of studies for which the cell frequencies should be reconstructed.
character vector with four elements to specify the names of the variables for the reconstructed cell frequencies (the default is c("ai","bi","ci","di")
).
logical to specify whether the data frame provided via the data
argument should be returned together with the reconstructed values (the default is TRUE
).
character string or logical to specify how values in var.names
should be replaced (only relevant when using the data
argument and if variables in var.names
already exist in the data frame). See the ‘Value’ section for more details.
If the data
argument was not specified or append=FALSE
, a data frame with four variables called var.names
with the reconstructed cell frequencies.
If the data
argument was not specified or append=FALSE
, a data frame with four variables called var.names
with the reconstructed cell frequencies.
If data
was specified and append=TRUE
, then the original data frame is returned. If var.names[j]
(for \(\textrm{j} \in \{1, \ldots, 4\}\)) is a variable in data
and replace="ifna"
(or replace=FALSE
), then only missing values in this variable are replaced with the estimated frequencies (where possible) and otherwise a new variable called var.names[j]
is added to the data frame.
If replace="all"
(or replace=TRUE
), then all values in var.names[j]
where a reconstructed cell frequency can be computed are replaced, even for cases where the value in var.names[j]
is not missing.
conv.delta.Rd
vector with the observed effect sizes or outcomes.
vector with the corresponding sampling variances.
vector with the total sample sizes of the studies.
optional data frame containing the variables given to the arguments above.
optional (logical or numeric) vector to specify the subset of studies for which the transformation should be carried out.
a function which should be used for the transformation.
character vector with two elements to specify the name of the variable for the transformed effect sizes or outcomes and the name of the variable for the corresponding sampling variances (if data
is an object of class "escalc"
, the var.names
are taken from the object; otherwise the defaults are "yi"
and "vi"
).
logical to specify whether the data frame provided via the data
argument should be returned together with the estimated values (the default is TRUE
).
character string or logical to specify how values in var.names
should be replaced (only relevant when using the data
argument and if variables in var.names
already exist in the data frame). See the ‘Value’ section for more details.
other arguments for the transformation function.
If the data
argument was not specified or append=FALSE
, a data frame of class c("escalc","data.frame")
with two variables called var.names[1]
(by default "yi"
) and var.names[2]
(by default "vi"
) with the transformed observed effect sizes or outcomes and the corresponding sampling variances (computed as described above).
If the data
argument was not specified or append=FALSE
, a data frame of class c("escalc","data.frame")
with two variables called var.names[1]
(by default "yi"
) and var.names[2]
(by default "vi"
) with the transformed observed effect sizes or outcomes and the corresponding sampling variances (computed as described above).
If data
was specified and append=TRUE
, then the original data frame is returned. If var.names[1]
is a variable in data
and replace="ifna"
(or replace=FALSE
), then only missing values in this variable are replaced with the transformed observed effect sizes or outcomes (where possible) and otherwise a new variable called var.names[1]
is added to the data frame. Similarly, if var.names[2]
is a variable in data
and replace="ifna"
(or replace=FALSE
), then only missing values in this variable are replaced with the sampling variances calculated as described above (where possible) and otherwise a new variable called var.names[2]
is added to the data frame.
If replace="all"
(or replace=TRUE
), then all values in var.names[1]
and var.names[2]
are replaced, even for cases where the value in var.names[1]
and var.names[2]
is not missing.
conv.fivenum.Rd
vector with the minimum values.
vector with the lower/first quartile values.
vector with the median values.
vector with the upper/third quartile values.
vector with the maximum values.
vector with the sample sizes.
optional data frame containing the variables given to the arguments above.
optional (logical or numeric) vector to specify the subset of studies for which means and standard deviations should be estimated.
character string to specify the method to use. Either "default"
(same as "luo/wan/shi"
which is the current default), "qe"
, "bc"
, "mln"
, or "blue"
. Can be abbreviated. See ‘Details’.
character string to specify the assumed distribution for the underlying data (either "norm"
for a normal distribution or "lnorm"
for a log-normal distribution). Can also be a string vector if different distributions are assumed for different studies. Only relevant when method="default"
.
logical to specify whether the estimated means and standard deviations of the log-transformed data should be back-transformed as described by Shi et al. (2020b) (the default is TRUE
). Only relevant when dist="lnorm"
and when method="default"
.
logical to specify whether a study should be excluded from the estimation if the test for skewness is significant (the default is TRUE
, but whether this is applicable depends on the method; see ‘Details’).
character vector with two elements to specify the name of the variable for the estimated means and the name of the variable for the estimated standard deviations (the defaults are "mean"
and "sd"
).
logical to specify whether the data frame provided via the data
argument should be returned together with the estimated values (the default is TRUE
).
character string or logical to specify how values in var.names
should be replaced (only relevant when using the data
argument and if variables in var.names
already exist in the data frame). See the ‘Value’ section for more details.
other arguments.
If the data
argument was not specified or append=FALSE
, a data frame with two variables called var.names[1]
(by default "mean"
) and var.names[2]
(by default "sd"
) with the estimated means and SDs.
If the data
argument was not specified or append=FALSE
, a data frame with two variables called var.names[1]
(by default "mean"
) and var.names[2]
(by default "sd"
) with the estimated means and SDs.
If data
was specified and append=TRUE
, then the original data frame is returned. If var.names[1]
is a variable in data
and replace="ifna"
(or replace=FALSE
), then only missing values in this variable are replaced with the estimated means (where possible) and otherwise a new variable called var.names[1]
is added to the data frame. Similarly, if var.names[2]
is a variable in data
and replace="ifna"
(or replace=FALSE
), then only missing values in this variable are replaced with the estimated SDs (where possible) and otherwise a new variable called var.names[2]
is added to the data frame.
If replace="all"
(or replace=TRUE
), then all values in var.names[1]
and var.names[2]
where an estimated mean and SD can be computed are replaced, even for cases where the value in var.names[1]
and var.names[2]
is not missing.
When missing values in var.names[1]
are replaced, an attribute called "est"
is added to the variable, which is a logical vector that is TRUE
for values that were estimated. The same is done when missing values in var.names[2]
are replaced.
Attributes called "tval"
, "crit"
, "sig"
, and "dist"
are also added to var.names[1]
corresponding to the test statistic and critical value for the test for skewness, whether the test was significant, and the assumed distribution (for the quantile estimation method, this is the distribution that provides the best fit to the given values).
conv.wald.Rd
vector with the observed effect sizes or outcomes.
vector with the lower bounds of the corresponding Wald-type CIs.
vector with the upper bounds of the corresponding Wald-type CIs.
vector with the Wald-type test statistics.
vector with the p-values of the Wald-type tests.
vector with the total sample sizes of the studies.
optional data frame containing the variables given to the arguments above.
optional (logical or numeric) vector to specify the subset of studies for which the conversion should be carried out.
numeric value (or vector) to specify the confidence interval level(s) (the default is 95; see here for details).
optional argument to specify a function to transform out
, ci.lb
, and ci.ub
(e.g., transf=log
). If unspecified, no transformation is used.
logical to specify whether the function should carry out a check to examine if the point estimates fall (approximately) halfway between the CI bounds (the default is TRUE
).
character vector with two elements to specify the name of the variable for the observed effect sizes or outcomes and the name of the variable for the corresponding sampling variances (if data
is an object of class "escalc"
, the var.names
are taken from the object; otherwise the defaults are "yi"
and "vi"
).
logical to specify whether the data frame provided via the data
argument should be returned together with the estimated values (the default is TRUE
).
character string or logical to specify how values in var.names
should be replaced (only relevant when using the data
argument and if variables in var.names
already exist in the data frame). See the ‘Value’ section for more details.
other arguments.
Similarly, study authors may report the test statistic and/or p-value from a Wald-type test of the form \(\textrm{zval} = y_i / \sqrt{v_i}\) (on the transformed scale if transf
is specified), with the corresponding two-sided p-value given by \(\textrm{pval} = 2(1 - \Phi(\textrm{|zval|}))\), where \(\Phi(\cdot)\) denotes the cumulative distribution function of a standard normal distribution (i.e., pnorm
). Test statistics and/or corresponding p-values of this form can be supplied via arguments zval
and pval
.
A given p-value can be back-transformed into the corresponding test statistic (if it is not already available) with \(\textrm{zval} = \Phi^{-1}(1 - \textrm{pval}/2)\), where \(\Phi^{-1}(\cdot)\) denotes the quantile function (i.e., the inverse of the cumulative distribution function) of a standard normal distribution (i.e., qnorm
). Then \[v_i = \left(\frac{y_i}{\textrm{zval}}\right)^2\] is used to back-calculate a missing vi
value in the dataset.
Note that the conversion of a p-value to the corresponding test statistic (which is then converted into sampling variance) as shown above assumes that the exact p-value is reported. If authors only report that the p-value fell below a certain threshold (e.g., \(p < .01\) or if authors only state that the test was significant -- which typically implies \(p < .05\)), then a common approach is to use the value of the cutoff reported (e.g., if \(p < .01\) is reported, then assume \(p = .01\)), which is conservative (since the actual p-value was below that assumed value by some unknown amount). The conversion will therefore tend to be much less accurate.
+Note that the conversion of a p-value to the corresponding test statistic (which is then converted into sampling variance) as shown above assumes that the exact p-value is reported. If authors only report that the p-value fell below a certain threshold (e.g., \(p < .01\) or if authors only state that the test was significant – which typically implies \(p < .05\)), then a common approach is to use the value of the cutoff reported (e.g., if \(p < .01\) is reported, then assume \(p = .01\)), which is conservative (since the actual p-value was below that assumed value by some unknown amount). The conversion will therefore tend to be much less accurate.
Using the earlier example, suppose that only the odds ratio and the corresponding two-sided p-value from a Wald-type test (whether the log odds ratio differs significantly from zero) is reported for study 2.
dat <- data.frame(study = 1:3,
@@ -227,14 +228,8 @@ Converting Test Statistics and
If the data
argument was not specified or append=FALSE
, a data frame of class c("escalc","data.frame")
with two variables called var.names[1]
(by default "yi"
) and var.names[2]
(by default "vi"
) with the (transformed) observed effect sizes or outcomes and the corresponding sampling variances (computed as described above).
If the data
argument was not specified or append=FALSE
, a data frame of class c("escalc","data.frame")
with two variables called var.names[1]
(by default "yi"
) and var.names[2]
(by default "vi"
) with the (transformed) observed effect sizes or outcomes and the corresponding sampling variances (computed as described above).
If data
was specified and append=TRUE
, then the original data frame is returned. If var.names[1]
is a variable in data
and replace="ifna"
(or replace=FALSE
), then only missing values in this variable are replaced with the (possibly transformed) observed effect sizes or outcomes from out
(where possible) and otherwise a new variable called var.names[1]
is added to the data frame. Similarly, if var.names[2]
is a variable in data
and replace="ifna"
(or replace=FALSE
), then only missing values in this variable are replaced with the sampling variances back-calculated as described above (where possible) and otherwise a new variable called var.names[2]
is added to the data frame.
If replace="all"
(or replace=TRUE
), then all values in var.names[1]
and var.names[2]
are replaced, even for cases where the value in var.names[1]
and var.names[2]
is not missing.
cumul.Rd
cumul(x, ...)
-# S3 method for rma.uni
-cumul(x, order, digits, transf, targs, progbar=FALSE, ...)
-# S3 method for rma.mh
-cumul(x, order, digits, transf, targs, progbar=FALSE, ...)
-# S3 method for rma.peto
-cumul(x, order, digits, transf, targs, progbar=FALSE, ...)
an object of class "rma.uni"
, "rma.mh"
, or "rma.peto"
.
optional argument to specify a variable based on which the studies will be ordered for the cumulative meta-analysis.
optional integer to specify the number of decimal places to which the printed results should be rounded. If unspecified, the default is to take the value from the object.
optional argument to specify a function to transform the model coefficients and interval bounds (e.g., transf=exp
; see also transf). If unspecified, no transformation is used.
optional arguments needed by the function specified under transf
.
logical to specify whether studies with the same value of the order
variable should be added simultaneously (the default is FALSE
).
logical to specify whether a progress bar should be shown (the default is FALSE
).
other arguments.
For "rma.uni"
objects, the model specified via x
must be a model without moderators (i.e., either an equal- or a random-effects model).
If argument order
is not specified, the studies are added according to their order in the original dataset.
When a variable is specified for order
, the variable is assumed to be of the same length as the original dataset that was used in the model fitting (and if the data
argument was used in the original model fit, then the variable will be searched for within this data frame first). Any subsetting and removal of studies with missing values that was applied during the model fitting is also automatically applied to the variable specified via the order
argument. See ‘Examples’.
When a variable is specified for order
, the variable is assumed to be of the same length as the original dataset that was used in the model fitting (and if the data
argument was used in the original model fit, then the variable will be searched for within this data frame first). Any subsetting and removal of studies with missing values that was applied during the model fitting is also automatically applied to the variable specified via the order
argument.
By default, studies are added one at a time. However, if a variable is specified for the order
argument and collapse=TRUE
, then studies with the same value of the order
variable are added simultaneously.
An object of class c("list.rma","cumul.rma")
. The object is a list containing the following components:
number of studies included in the analysis.
An object of class c("list.rma","cumul.rma")
. The object is a list containing the following components:
estimated (average) outcomes.
When the model was fitted with test="t"
, test="knha"
, test="hksj"
, or test="adhoc"
, then zval
is called tval
in the object that is returned by the function.
The object is formatted and printed with the print
function. To format the results as a data frame, one can use the as.data.frame
function. A forest plot showing the results from the cumulative meta-analysis can be obtained with forest
. Alternatively, plot
can also be used to visualize the results.
### calculate log risk ratios and corresponding sampling variances
-dat <- escalc(measure="RR", ai=tpos, bi=tneg, ci=cpos, di=cneg, data=dat.bcg)
+dat <- escalc(measure="RR", ai=tpos, bi=tneg, ci=cpos, di=cneg,
+ data=dat.bcg, slab=paste0(author, ", ", year))
### fit random-effects model
-res <- rma(yi, vi, data=dat)
+res <- rma(yi, vi, data=dat, digits=3)
### cumulative meta-analysis (in the order of publication year)
-cumul(res, transf=exp, order=year)
+cumul(res, order=year)
#>
-#> estimate zval pvals ci.lb ci.ub Q Qp tau2 I2 H2
-#> 1 0.4109 -1.5586 0.1191 0.1343 1.2574 0.0000 1.0000 0.0000 0.0000 1.0000
-#> 2 0.2658 -3.7967 0.0001 0.1341 0.5268 0.9315 0.3345 0.0000 0.0000 1.0000
-#> 6 0.3783 -3.9602 0.0001 0.2338 0.6120 3.1879 0.2031 0.0872 40.7090 1.6866
-#> 3 0.3675 -4.5037 0.0000 0.2377 0.5681 3.8614 0.2768 0.0763 33.9750 1.5146
-#> 10 0.3324 -5.5164 0.0000 0.2248 0.4916 7.6415 0.1056 0.0858 48.4120 1.9384
-#> 9 0.3778 -5.1875 0.0000 0.2615 0.5457 10.1854 0.0702 0.1046 60.0008 2.5000
-#> 12 0.4061 -4.7250 0.0000 0.2794 0.5901 13.2116 0.0398 0.1205 59.9982 2.4999
-#> 5 0.4545 -4.0039 0.0001 0.3089 0.6686 19.5749 0.0066 0.1780 72.3904 3.6219
-#> 7 0.4208 -4.4107 0.0000 0.2864 0.6182 22.8208 0.0036 0.2023 73.5065 3.7745
-#> 11 0.4560 -4.3588 0.0000 0.3204 0.6491 34.1203 0.0001 0.2005 81.4029 5.3772
-#> 13 0.4925 -3.9701 0.0001 0.3472 0.6987 39.6122 0.0000 0.2281 83.0110 5.8862
-#> 4 0.4517 -4.4184 0.0000 0.3175 0.6426 67.9858 0.0000 0.2732 87.0314 7.7109
-#> 8 0.4894 -3.9744 0.0001 0.3441 0.6962 152.2330 0.0000 0.3132 92.2214 12.8558
+#> k estimate se zval pval ci.lb ci.ub Q Qp tau2 I2
+#> Aronson, 1948 1 -0.889 0.571 -1.559 0.119 -2.008 0.229 0.000 1.000 0.000 0.000
+#> Ferguson & Simes, 1949 2 -1.325 0.349 -3.797 0.000 -2.009 -0.641 0.931 0.334 0.000 0.000
+#> Stein & Aronson, 1953 3 -0.972 0.245 -3.960 0.000 -1.453 -0.491 3.188 0.203 0.087 40.709
+#> Rosenthal et al, 1960 4 -1.001 0.222 -4.504 0.000 -1.437 -0.565 3.861 0.277 0.076 33.975
+#> Rosenthal et al, 1961 5 -1.101 0.200 -5.516 0.000 -1.493 -0.710 7.642 0.106 0.086 48.412
+#> Coetzee & Berjak, 1968 6 -0.973 0.188 -5.188 0.000 -1.341 -0.606 10.185 0.070 0.105 60.001
+#> Comstock & Webster, 1969 7 -0.901 0.191 -4.725 0.000 -1.275 -0.527 13.212 0.040 0.120 59.998
+#> Frimodt-Moller et al, 1973 8 -0.789 0.197 -4.004 0.000 -1.175 -0.403 19.575 0.007 0.178 72.390
+#> Vandiviere et al, 1973 9 -0.866 0.196 -4.411 0.000 -1.250 -0.481 22.821 0.004 0.202 73.506
+#> Comstock et al, 1974 10 -0.785 0.180 -4.359 0.000 -1.138 -0.432 34.120 0.000 0.201 81.403
+#> Comstock et al, 1976 11 -0.708 0.178 -3.970 0.000 -1.058 -0.359 39.612 0.000 0.228 83.011
+#> Hart & Sutherland, 1977 12 -0.795 0.180 -4.418 0.000 -1.147 -0.442 67.986 0.000 0.273 87.031
+#> TPT Madras, 1980 13 -0.715 0.180 -3.974 0.000 -1.067 -0.362 152.233 0.000 0.313 92.221
+#> H2
+#> Aronson, 1948 1.000
+#> Ferguson & Simes, 1949 1.000
+#> Stein & Aronson, 1953 1.687
+#> Rosenthal et al, 1960 1.515
+#> Rosenthal et al, 1961 1.938
+#> Coetzee & Berjak, 1968 2.500
+#> Comstock & Webster, 1969 2.500
+#> Frimodt-Moller et al, 1973 3.622
+#> Vandiviere et al, 1973 3.775
+#> Comstock et al, 1974 5.377
+#> Comstock et al, 1976 5.886
+#> Hart & Sutherland, 1977 7.711
+#> TPT Madras, 1980 12.856
+#>
+cumul(res, order=year, transf=exp)
+#>
+#> k estimate zval pval ci.lb ci.ub Q Qp tau2 I2 H2
+#> Aronson, 1948 1 0.411 -1.559 0.119 0.134 1.257 0.000 1.000 0.000 0.000 1.000
+#> Ferguson & Simes, 1949 2 0.266 -3.797 0.000 0.134 0.527 0.931 0.334 0.000 0.000 1.000
+#> Stein & Aronson, 1953 3 0.378 -3.960 0.000 0.234 0.612 3.188 0.203 0.087 40.709 1.687
+#> Rosenthal et al, 1960 4 0.367 -4.504 0.000 0.238 0.568 3.861 0.277 0.076 33.975 1.515
+#> Rosenthal et al, 1961 5 0.332 -5.516 0.000 0.225 0.492 7.642 0.106 0.086 48.412 1.938
+#> Coetzee & Berjak, 1968 6 0.378 -5.188 0.000 0.262 0.546 10.185 0.070 0.105 60.001 2.500
+#> Comstock & Webster, 1969 7 0.406 -4.725 0.000 0.279 0.590 13.212 0.040 0.120 59.998 2.500
+#> Frimodt-Moller et al, 1973 8 0.454 -4.004 0.000 0.309 0.669 19.575 0.007 0.178 72.390 3.622
+#> Vandiviere et al, 1973 9 0.421 -4.411 0.000 0.286 0.618 22.821 0.004 0.202 73.506 3.775
+#> Comstock et al, 1974 10 0.456 -4.359 0.000 0.320 0.649 34.120 0.000 0.201 81.403 5.377
+#> Comstock et al, 1976 11 0.493 -3.970 0.000 0.347 0.699 39.612 0.000 0.228 83.011 5.886
+#> Hart & Sutherland, 1977 12 0.452 -4.418 0.000 0.317 0.643 67.986 0.000 0.273 87.031 7.711
+#> TPT Madras, 1980 13 0.489 -3.974 0.000 0.344 0.696 152.233 0.000 0.313 92.221 12.856
+#>
+
+### add studies with the same publication year simultaneously
+cumul(res, order=year, transf=exp, collapse=TRUE)
+#>
+#> k estimate zval pval ci.lb ci.ub Q Qp tau2 I2 H2
+#> 1948 1 0.411 -1.559 0.119 0.134 1.257 0.000 1.000 0.000 0.000 1.000
+#> 1949 2 0.266 -3.797 0.000 0.134 0.527 0.931 0.334 0.000 0.000 1.000
+#> 1953 3 0.378 -3.960 0.000 0.234 0.612 3.188 0.203 0.087 40.709 1.687
+#> 1960 4 0.367 -4.504 0.000 0.238 0.568 3.861 0.277 0.076 33.975 1.515
+#> 1961 5 0.332 -5.516 0.000 0.225 0.492 7.642 0.106 0.086 48.412 1.938
+#> 1968 6 0.378 -5.188 0.000 0.262 0.546 10.185 0.070 0.105 60.001 2.500
+#> 1969 7 0.406 -4.725 0.000 0.279 0.590 13.212 0.040 0.120 59.998 2.500
+#> 1973 9 0.421 -4.411 0.000 0.286 0.618 22.821 0.004 0.202 73.506 3.775
+#> 1974 10 0.456 -4.359 0.000 0.320 0.649 34.120 0.000 0.201 81.403 5.377
+#> 1976 11 0.493 -3.970 0.000 0.347 0.699 39.612 0.000 0.228 83.011 5.886
+#> 1977 12 0.452 -4.418 0.000 0.317 0.643 67.986 0.000 0.273 87.031 7.711
+#> 1980 13 0.489 -3.974 0.000 0.344 0.696 152.233 0.000 0.313 92.221 12.856
#>
### meta-analysis of the (log) risk ratios using the Mantel-Haenszel method
-res <- rma.mh(measure="RR", ai=tpos, bi=tneg, ci=cpos, di=cneg, data=dat.bcg)
+res <- rma.mh(measure="RR", ai=tpos, bi=tneg, ci=cpos, di=cneg,
+ data=dat.bcg, slab=paste0(author, ", ", year), digits=3)
### cumulative meta-analysis
cumul(res, order=year)
#>
-#> estimate se zval pval ci.lb ci.ub Q Qp I2 H2
-#> 1 -0.8893 0.5706 -1.5586 0.1191 -2.0077 0.2290 0.0000 1.0000 0.0000 1.0000
-#> 2 -1.3517 0.3455 -3.9124 0.0001 -2.0289 -0.6746 0.9373 0.3330 0.0000 0.9373
-#> 6 -0.8273 0.0808 -10.2371 0.0000 -0.9857 -0.6689 3.2109 0.2008 37.7127 1.6055
-#> 3 -0.8379 0.0802 -10.4490 0.0000 -0.9951 -0.6807 3.8945 0.2731 22.9687 1.2982
-#> 10 -0.8940 0.0769 -11.6254 0.0000 -1.0447 -0.7433 7.7589 0.1008 48.4460 1.9397
-#> 9 -0.8507 0.0730 -11.6480 0.0000 -0.9938 -0.7075 10.2660 0.0680 51.2956 2.0532
-#> 12 -0.8358 0.0725 -11.5275 0.0000 -0.9779 -0.6937 13.2768 0.0388 54.8084 2.2128
-#> 5 -0.7744 0.0688 -11.2623 0.0000 -0.9092 -0.6397 19.6127 0.0065 64.3088 2.8018
-#> 7 -0.7896 0.0680 -11.6188 0.0000 -0.9228 -0.6564 22.8443 0.0036 64.9803 2.8555
-#> 11 -0.6660 0.0577 -11.5373 0.0000 -0.7792 -0.5529 34.1377 0.0001 73.6362 3.7931
-#> 13 -0.6351 0.0563 -11.2811 0.0000 -0.7454 -0.5247 39.6232 0.0000 74.7622 3.9623
-#> 4 -0.7758 0.0520 -14.9267 0.0000 -0.8777 -0.6739 68.3763 0.0000 83.9126 6.2160
-#> 8 -0.4537 0.0393 -11.5338 0.0000 -0.5308 -0.3766 152.5676 0.0000 92.1346 12.7140
+#> k estimate se zval pval ci.lb ci.ub Q Qp I2 H2
+#> Aronson, 1948 1 -0.889 0.571 -1.559 0.119 -2.008 0.229 0.000 1.000 0.000 1.000
+#> Ferguson & Simes, 1949 2 -1.352 0.346 -3.912 0.000 -2.029 -0.675 0.937 0.333 0.000 0.937
+#> Stein & Aronson, 1953 3 -0.827 0.081 -10.237 0.000 -0.986 -0.669 3.211 0.201 37.713 1.605
+#> Rosenthal et al, 1960 4 -0.838 0.080 -10.449 0.000 -0.995 -0.681 3.895 0.273 22.969 1.298
+#> Rosenthal et al, 1961 5 -0.894 0.077 -11.625 0.000 -1.045 -0.743 7.759 0.101 48.446 1.940
+#> Coetzee & Berjak, 1968 6 -0.851 0.073 -11.648 0.000 -0.994 -0.708 10.266 0.068 51.296 2.053
+#> Comstock & Webster, 1969 7 -0.836 0.073 -11.528 0.000 -0.978 -0.694 13.277 0.039 54.808 2.213
+#> Frimodt-Moller et al, 1973 8 -0.774 0.069 -11.262 0.000 -0.909 -0.640 19.613 0.006 64.309 2.802
+#> Vandiviere et al, 1973 9 -0.790 0.068 -11.619 0.000 -0.923 -0.656 22.844 0.004 64.980 2.856
+#> Comstock et al, 1974 10 -0.666 0.058 -11.537 0.000 -0.779 -0.553 34.138 0.000 73.636 3.793
+#> Comstock et al, 1976 11 -0.635 0.056 -11.281 0.000 -0.745 -0.525 39.623 0.000 74.762 3.962
+#> Hart & Sutherland, 1977 12 -0.776 0.052 -14.927 0.000 -0.878 -0.674 68.376 0.000 83.913 6.216
+#> TPT Madras, 1980 13 -0.454 0.039 -11.534 0.000 -0.531 -0.377 152.568 0.000 92.135 12.714
#>
-cumul(res, order=year, transf=TRUE)
+cumul(res, order=year, transf=exp)
#>
-#> estimate zval pval ci.lb ci.ub Q Qp I2 H2
-#> 1 0.4109 -1.5586 0.1191 0.1343 1.2574 0.0000 1.0000 0.0000 1.0000
-#> 2 0.2588 -3.9124 0.0001 0.1315 0.5094 0.9373 0.3330 0.0000 0.9373
-#> 6 0.4372 -10.2371 0.0000 0.3732 0.5123 3.2109 0.2008 37.7127 1.6055
-#> 3 0.4326 -10.4490 0.0000 0.3697 0.5062 3.8945 0.2731 22.9687 1.2982
-#> 10 0.4090 -11.6254 0.0000 0.3518 0.4756 7.7589 0.1008 48.4460 1.9397
-#> 9 0.4271 -11.6480 0.0000 0.3702 0.4929 10.2660 0.0680 51.2956 2.0532
-#> 12 0.4335 -11.5275 0.0000 0.3761 0.4997 13.2768 0.0388 54.8084 2.2128
-#> 5 0.4610 -11.2623 0.0000 0.4028 0.5275 19.6127 0.0065 64.3088 2.8018
-#> 7 0.4540 -11.6188 0.0000 0.3974 0.5187 22.8443 0.0036 64.9803 2.8555
-#> 11 0.5138 -11.5373 0.0000 0.4588 0.5753 34.1377 0.0001 73.6362 3.7931
-#> 13 0.5299 -11.2811 0.0000 0.4745 0.5917 39.6232 0.0000 74.7622 3.9623
-#> 4 0.4603 -14.9267 0.0000 0.4158 0.5097 68.3763 0.0000 83.9126 6.2160
-#> 8 0.6353 -11.5338 0.0000 0.5881 0.6862 152.5676 0.0000 92.1346 12.7140
+#> k estimate zval pval ci.lb ci.ub Q Qp I2 H2
+#> Aronson, 1948 1 0.411 -1.559 0.119 0.134 1.257 0.000 1.000 0.000 1.000
+#> Ferguson & Simes, 1949 2 0.259 -3.912 0.000 0.131 0.509 0.937 0.333 0.000 0.937
+#> Stein & Aronson, 1953 3 0.437 -10.237 0.000 0.373 0.512 3.211 0.201 37.713 1.605
+#> Rosenthal et al, 1960 4 0.433 -10.449 0.000 0.370 0.506 3.895 0.273 22.969 1.298
+#> Rosenthal et al, 1961 5 0.409 -11.625 0.000 0.352 0.476 7.759 0.101 48.446 1.940
+#> Coetzee & Berjak, 1968 6 0.427 -11.648 0.000 0.370 0.493 10.266 0.068 51.296 2.053
+#> Comstock & Webster, 1969 7 0.434 -11.528 0.000 0.376 0.500 13.277 0.039 54.808 2.213
+#> Frimodt-Moller et al, 1973 8 0.461 -11.262 0.000 0.403 0.527 19.613 0.006 64.309 2.802
+#> Vandiviere et al, 1973 9 0.454 -11.619 0.000 0.397 0.519 22.844 0.004 64.980 2.856
+#> Comstock et al, 1974 10 0.514 -11.537 0.000 0.459 0.575 34.138 0.000 73.636 3.793
+#> Comstock et al, 1976 11 0.530 -11.281 0.000 0.475 0.592 39.623 0.000 74.762 3.962
+#> Hart & Sutherland, 1977 12 0.460 -14.927 0.000 0.416 0.510 68.376 0.000 83.913 6.216
+#> TPT Madras, 1980 13 0.635 -11.534 0.000 0.588 0.686 152.568 0.000 92.135 12.714
+#>
+
+### add studies with the same publication year simultaneously
+cumul(res, order=year, transf=exp, collapse=TRUE)
+#>
+#> k estimate zval pval ci.lb ci.ub Q Qp I2 H2
+#> 1948 1 0.411 -1.559 0.119 0.134 1.257 0.000 1.000 0.000 1.000
+#> 1949 2 0.259 -3.912 0.000 0.131 0.509 0.937 0.333 0.000 0.937
+#> 1953 3 0.437 -10.237 0.000 0.373 0.512 3.211 0.201 37.713 1.605
+#> 1960 4 0.433 -10.449 0.000 0.370 0.506 3.895 0.273 22.969 1.298
+#> 1961 5 0.409 -11.625 0.000 0.352 0.476 7.759 0.101 48.446 1.940
+#> 1968 6 0.427 -11.648 0.000 0.370 0.493 10.266 0.068 51.296 2.053
+#> 1969 7 0.434 -11.528 0.000 0.376 0.500 13.277 0.039 54.808 2.213
+#> 1973 9 0.454 -11.619 0.000 0.397 0.519 22.844 0.004 64.980 2.856
+#> 1974 10 0.514 -11.537 0.000 0.459 0.575 34.138 0.000 73.636 3.793
+#> 1976 11 0.530 -11.281 0.000 0.475 0.592 39.623 0.000 74.762 3.962
+#> 1977 12 0.460 -14.927 0.000 0.416 0.510 68.376 0.000 83.913 6.216
+#> 1980 13 0.635 -11.534 0.000 0.588 0.686 152.568 0.000 92.135 12.714
#>
### meta-analysis of the (log) odds ratios using Peto's method
-res <- rma.peto(ai=tpos, bi=tneg, ci=cpos, di=cneg, data=dat.bcg)
+res <- rma.peto(ai=tpos, bi=tneg, ci=cpos, di=cneg,
+ data=dat.bcg, slab=paste0(author, ", ", year), digits=3)
### cumulative meta-analysis
cumul(res, order=year)
#>
-#> estimate se zval pval ci.lb ci.ub Q Qp I2 H2
-#> 1 -0.8604 0.5318 -1.6178 0.1057 -1.9027 0.1820 0.0000 1.0000 0.0000 1.0000
-#> 2 -1.2401 0.2912 -4.2591 0.0000 -1.8107 -0.6694 0.7279 0.3936 0.0000 0.7279
-#> 6 -0.9570 0.0897 -10.6686 0.0000 -1.1328 -0.7812 1.7723 0.4122 0.0000 0.8861
-#> 3 -0.9642 0.0885 -10.8948 0.0000 -1.1377 -0.7908 2.0147 0.5694 0.0000 0.6716
-#> 10 -1.0003 0.0823 -12.1559 0.0000 -1.1616 -0.8390 3.2425 0.5181 0.0000 0.8106
-#> 9 -0.9410 0.0776 -12.1265 0.0000 -1.0931 -0.7889 7.9341 0.1599 36.9810 1.5868
-#> 12 -0.9246 0.0771 -11.9872 0.0000 -1.0758 -0.7735 11.6730 0.0697 48.5992 1.9455
-#> 5 -0.8501 0.0730 -11.6515 0.0000 -0.9932 -0.7071 20.5359 0.0045 65.9133 2.9337
-#> 7 -0.8712 0.0724 -12.0301 0.0000 -1.0131 -0.7293 26.1159 0.0010 69.3673 3.2645
-#> 11 -0.7268 0.0615 -11.8273 0.0000 -0.8472 -0.6064 40.3188 0.0000 77.6779 4.4799
-#> 13 -0.6912 0.0599 -11.5417 0.0000 -0.8086 -0.5739 46.9968 0.0000 78.7220 4.6997
-#> 4 -0.8161 0.0531 -15.3842 0.0000 -0.9201 -0.7122 67.1837 0.0000 83.6270 6.1076
-#> 8 -0.4744 0.0407 -11.6689 0.0000 -0.5541 -0.3948 167.7302 0.0000 92.8457 13.9775
+#> k estimate se zval pval ci.lb ci.ub Q Qp I2 H2
+#> Aronson, 1948 1 -0.860 0.532 -1.618 0.106 -1.903 0.182 0.000 1.000 0.000 1.000
+#> Ferguson & Simes, 1949 2 -1.240 0.291 -4.259 0.000 -1.811 -0.669 0.728 0.394 0.000 0.728
+#> Stein & Aronson, 1953 3 -0.957 0.090 -10.669 0.000 -1.133 -0.781 1.772 0.412 0.000 0.886
+#> Rosenthal et al, 1960 4 -0.964 0.089 -10.895 0.000 -1.138 -0.791 2.015 0.569 0.000 0.672
+#> Rosenthal et al, 1961 5 -1.000 0.082 -12.156 0.000 -1.162 -0.839 3.243 0.518 0.000 0.811
+#> Coetzee & Berjak, 1968 6 -0.941 0.078 -12.126 0.000 -1.093 -0.789 7.934 0.160 36.981 1.587
+#> Comstock & Webster, 1969 7 -0.925 0.077 -11.987 0.000 -1.076 -0.773 11.673 0.070 48.599 1.945
+#> Frimodt-Moller et al, 1973 8 -0.850 0.073 -11.652 0.000 -0.993 -0.707 20.536 0.005 65.913 2.934
+#> Vandiviere et al, 1973 9 -0.871 0.072 -12.030 0.000 -1.013 -0.729 26.116 0.001 69.367 3.264
+#> Comstock et al, 1974 10 -0.727 0.061 -11.827 0.000 -0.847 -0.606 40.319 0.000 77.678 4.480
+#> Comstock et al, 1976 11 -0.691 0.060 -11.542 0.000 -0.809 -0.574 46.997 0.000 78.722 4.700
+#> Hart & Sutherland, 1977 12 -0.816 0.053 -15.384 0.000 -0.920 -0.712 67.184 0.000 83.627 6.108
+#> TPT Madras, 1980 13 -0.474 0.041 -11.669 0.000 -0.554 -0.395 167.730 0.000 92.846 13.978
+#>
+cumul(res, order=year, transf=exp)
+#>
+#> k estimate zval pval ci.lb ci.ub Q Qp I2 H2
+#> Aronson, 1948 1 0.423 -1.618 0.106 0.149 1.200 0.000 1.000 0.000 1.000
+#> Ferguson & Simes, 1949 2 0.289 -4.259 0.000 0.164 0.512 0.728 0.394 0.000 0.728
+#> Stein & Aronson, 1953 3 0.384 -10.669 0.000 0.322 0.458 1.772 0.412 0.000 0.886
+#> Rosenthal et al, 1960 4 0.381 -10.895 0.000 0.321 0.454 2.015 0.569 0.000 0.672
+#> Rosenthal et al, 1961 5 0.368 -12.156 0.000 0.313 0.432 3.243 0.518 0.000 0.811
+#> Coetzee & Berjak, 1968 6 0.390 -12.126 0.000 0.335 0.454 7.934 0.160 36.981 1.587
+#> Comstock & Webster, 1969 7 0.397 -11.987 0.000 0.341 0.461 11.673 0.070 48.599 1.945
+#> Frimodt-Moller et al, 1973 8 0.427 -11.652 0.000 0.370 0.493 20.536 0.005 65.913 2.934
+#> Vandiviere et al, 1973 9 0.418 -12.030 0.000 0.363 0.482 26.116 0.001 69.367 3.264
+#> Comstock et al, 1974 10 0.483 -11.827 0.000 0.429 0.545 40.319 0.000 77.678 4.480
+#> Comstock et al, 1976 11 0.501 -11.542 0.000 0.445 0.563 46.997 0.000 78.722 4.700
+#> Hart & Sutherland, 1977 12 0.442 -15.384 0.000 0.398 0.491 67.184 0.000 83.627 6.108
+#> TPT Madras, 1980 13 0.622 -11.669 0.000 0.575 0.674 167.730 0.000 92.846 13.978
#>
-cumul(res, order=year, transf=TRUE)
+
+### add studies with the same publication year simultaneously
+cumul(res, order=year, transf=exp, collapse=TRUE)
#>
-#> estimate zval pval ci.lb ci.ub Q Qp I2 H2
-#> 1 0.4230 -1.6178 0.1057 0.1492 1.1996 0.0000 1.0000 0.0000 1.0000
-#> 2 0.2894 -4.2591 0.0000 0.1635 0.5120 0.7279 0.3936 0.0000 0.7279
-#> 6 0.3840 -10.6686 0.0000 0.3221 0.4579 1.7723 0.4122 0.0000 0.8861
-#> 3 0.3813 -10.8948 0.0000 0.3206 0.4535 2.0147 0.5694 0.0000 0.6716
-#> 10 0.3678 -12.1559 0.0000 0.3130 0.4321 3.2425 0.5181 0.0000 0.8106
-#> 9 0.3902 -12.1265 0.0000 0.3352 0.4543 7.9341 0.1599 36.9810 1.5868
-#> 12 0.3967 -11.9872 0.0000 0.3410 0.4614 11.6730 0.0697 48.5992 1.9455
-#> 5 0.4274 -11.6515 0.0000 0.3704 0.4931 20.5359 0.0045 65.9133 2.9337
-#> 7 0.4184 -12.0301 0.0000 0.3631 0.4823 26.1159 0.0010 69.3673 3.2645
-#> 11 0.4835 -11.8273 0.0000 0.4286 0.5453 40.3188 0.0000 77.6779 4.4799
-#> 13 0.5010 -11.5417 0.0000 0.4455 0.5633 46.9968 0.0000 78.7220 4.6997
-#> 4 0.4421 -15.3842 0.0000 0.3985 0.4906 67.1837 0.0000 83.6270 6.1076
-#> 8 0.6222 -11.6689 0.0000 0.5746 0.6738 167.7302 0.0000 92.8457 13.9775
+#> k estimate zval pval ci.lb ci.ub Q Qp I2 H2
+#> 1948 1 0.423 -1.618 0.106 0.149 1.200 0.000 1.000 0.000 1.000
+#> 1949 2 0.289 -4.259 0.000 0.164 0.512 0.728 0.394 0.000 0.728
+#> 1953 3 0.384 -10.669 0.000 0.322 0.458 1.772 0.412 0.000 0.886
+#> 1960 4 0.381 -10.895 0.000 0.321 0.454 2.015 0.569 0.000 0.672
+#> 1961 5 0.368 -12.156 0.000 0.313 0.432 3.243 0.518 0.000 0.811
+#> 1968 6 0.390 -12.126 0.000 0.335 0.454 7.934 0.160 36.981 1.587
+#> 1969 7 0.397 -11.987 0.000 0.341 0.461 11.673 0.070 48.599 1.945
+#> 1973 9 0.418 -12.030 0.000 0.363 0.482 26.116 0.001 69.367 3.264
+#> 1974 10 0.483 -11.827 0.000 0.429 0.545 40.319 0.000 77.678 4.480
+#> 1976 11 0.501 -11.542 0.000 0.445 0.563 46.997 0.000 78.722 4.700
+#> 1977 12 0.442 -15.384 0.000 0.398 0.491 67.184 0.000 83.627 6.108
+#> 1980 13 0.622 -11.669 0.000 0.575 0.674 167.730 0.000 92.846 13.978
#>
-### make first log risk ratio missing and fit model without study 2; then the
-### variable specified via 'order' should still be of the same length as the
-### original dataset; subsetting and removal of studies with missing values is
-### automatically done by the cumul() function
+### make the first log risk ratio missing and fit the model without study 2;
+### then the variable specified via 'order' should still be of the same length
+### as the original dataset; subsetting and removal of studies with missing
+### values is automatically done by the cumul() function
dat$yi[1] <- NA
-res <- rma(yi, vi, data=dat, subset=-2)
+res <- rma(yi, vi, data=dat, subset=-2, digits=3)
#> Warning: 1 study with NAs omitted from model fitting.
cumul(res, transf=exp, order=year)
#>
-#> estimate zval pvals ci.lb ci.ub Q Qp tau2 I2 H2
-#> 6 0.4556 -9.4599 0.0000 0.3871 0.5362 0.0000 1.0000 0.0000 0.0000 1.0000
-#> 3 0.4514 -9.6497 0.0000 0.3841 0.5306 0.7478 0.3872 0.0000 0.0000 1.0000
-#> 10 0.3504 -4.3207 0.0000 0.2178 0.5639 4.9051 0.0861 0.1008 59.6906 2.4808
-#> 9 0.4100 -4.2685 0.0000 0.2722 0.6174 7.1487 0.0673 0.1034 66.8114 3.0131
-#> 12 0.4480 -3.6703 0.0002 0.2918 0.6878 10.0666 0.0393 0.1304 66.7246 3.0052
-#> 5 0.5075 -3.1669 0.0015 0.3335 0.7722 15.9241 0.0071 0.1704 75.5631 4.0922
-#> 7 0.4584 -3.5536 0.0004 0.2981 0.7048 19.3442 0.0036 0.2132 77.6086 4.4660
-#> 11 0.4970 -3.6803 0.0002 0.3425 0.7212 29.4342 0.0001 0.1880 83.2856 5.9829
-#> 13 0.5390 -3.3443 0.0008 0.3752 0.7743 34.5952 0.0000 0.2077 84.0877 6.2845
-#> 4 0.4835 -3.7288 0.0002 0.3300 0.7084 64.2052 0.0000 0.2831 89.1076 9.1808
-#> 8 0.5262 -3.3578 0.0008 0.3618 0.7655 144.6390 0.0000 0.3139 93.3044 14.9352
+#> k estimate zval pval ci.lb ci.ub Q Qp tau2 I2 H2
+#> Stein & Aronson, 1953 1 0.456 -9.460 0.000 0.387 0.536 0.000 1.000 0.000 0.000 1.000
+#> Rosenthal et al, 1960 2 0.451 -9.650 0.000 0.384 0.531 0.748 0.387 0.000 0.000 1.000
+#> Rosenthal et al, 1961 3 0.350 -4.321 0.000 0.218 0.564 4.905 0.086 0.101 59.691 2.481
+#> Coetzee & Berjak, 1968 4 0.410 -4.268 0.000 0.272 0.617 7.149 0.067 0.103 66.811 3.013
+#> Comstock & Webster, 1969 5 0.448 -3.670 0.000 0.292 0.688 10.067 0.039 0.130 66.725 3.005
+#> Frimodt-Moller et al, 1973 6 0.507 -3.167 0.002 0.334 0.772 15.924 0.007 0.170 75.563 4.092
+#> Vandiviere et al, 1973 7 0.458 -3.554 0.000 0.298 0.705 19.344 0.004 0.213 77.609 4.466
+#> Comstock et al, 1974 8 0.497 -3.680 0.000 0.342 0.721 29.434 0.000 0.188 83.286 5.983
+#> Comstock et al, 1976 9 0.539 -3.344 0.001 0.375 0.774 34.595 0.000 0.208 84.088 6.284
+#> Hart & Sutherland, 1977 10 0.484 -3.729 0.000 0.330 0.708 64.205 0.000 0.283 89.108 9.181
+#> TPT Madras, 1980 11 0.526 -3.358 0.001 0.362 0.765 144.639 0.000 0.314 93.304 14.935
#>
dfround.Rd
Returns the data frame with variables rounded as specified.
+Returns the data frame with variables rounded as specified.
emmprep.Rd
an object of class "rma"
.
logical to specify whether information on some (extracted) settings should be printed when creating the reference grid (the default is FALSE
).
other arguments that will be passed on to the qdrg
function.
An "emmGrid"
object as created by the qdrg
function from the emmeans
package.
An "emmGrid"
object as created by the qdrg
function from the emmeans
package.
The resulting object will typically be used in combination with the emmeans
function.
escalc.Rd
a character string to specify which effect size or outcome measure should be calculated. See ‘Details’ for possible options and how the data needed to compute the selected effect size or outcome measure should then be specified (i.e., which of the following arguments need to be used).
vector with the \(2 \times 2\) table frequencies (upper left cell).
vector with the \(2 \times 2\) table frequencies (upper right cell).
vector with the \(2 \times 2\) table frequencies (lower left cell).
vector with the \(2 \times 2\) table frequencies (lower right cell).
vector with the group sizes or row totals (first group/row).
vector with the group sizes or row totals (second group/row).
vector with the number of events (first group).
vector with the number of events (second group).
vector with the total person-times (first group).
vector with the total person-times (second group).
vector with the means (first group or time point).
vector with the means (second group or time point).
vector with the standard deviations (first group or time point).
vector with the standard deviations (second group or time point).
vector with the frequencies of the event of interest.
vector with the frequencies of the complement of the event of interest or the group means.
vector with the raw correlation coefficients.
vector with the total person-times or t-test statistics.
vector with the F-test statistics.
vector with the (signed) p-values.
vector with the standard deviations.
vector with the \(R^2\) values.
vector with the sample/group sizes.
vector with the observed effect sizes or outcomes.
vector with the corresponding sampling variances.
vector with the corresponding standard errors.
optional data frame containing the variables given to the arguments above.
optional vector with labels for the studies.
optional (logical or numeric) vector to specify the subset of studies that will be included in the data frame returned by the function.
optional (logical or numeric) vector to specify the subset of studies for which the measure should be calculated. See the ‘Value’ section for more details.
a non-negative number to specify the amount to add to zero cells, counts, or frequencies. See ‘Details’.
a character string to specify when the values under add
should be added (either "all"
, "only0"
, "if0all"
, or "none"
). See ‘Details’.
logical to specify whether studies with no cases/events (or only cases) in both groups should be dropped when calculating the observed effect sizes or outcomes. See ‘Details’.
a character string to specify the type of sampling variances to calculate. See ‘Details’.
character vector with two elements to specify the name of the variable for the observed effect sizes or outcomes and the name of the variable for the corresponding sampling variances (the defaults are "yi"
and "vi"
).
logical to specify whether a variable should be added to the data frame (with default name "measure"
) that indicates the type of outcome measure computed. When using this option, var.names
can have a third element to change this variable name.
logical to specify whether the data frame provided via the data
argument should be returned together with the observed effect sizes or outcomes and corresponding sampling variances (the default is TRUE
).
logical to specify whether existing values for yi
and vi
in the data frame should be replaced. Only relevant when append=TRUE
and the data frame already contains the yi
and vi
variables. If replace=TRUE
(the default), all of the existing values will be overwritten. If replace=FALSE
, only NA
values will be replaced. See the ‘Value’ section for more details.
optional integer to specify the number of decimal places to which the printed results should be rounded. If unspecified, the default is 4. Note that the values are stored without rounding in the returned object. See also here for further details on how to control the number of digits in the output.
other arguments.
An object of class c("escalc","data.frame")
. The object is a data frame containing the following components:
An object of class c("escalc","data.frame")
. The object is a data frame containing the following components:
vector with the observed effect sizes or outcomes.
If a data frame was specified via the data
argument and append=TRUE
, then variables yi
and vi
are appended to this data frame. Note that the var.names
argument actually specifies the names of these two variables ("yi"
and "vi"
are the defaults).
If the data frame already contains two variables with names as specified by the var.names
argument, the values for these two variables will be overwritten when replace=TRUE
(which is the default). By setting replace=FALSE
, only values that are NA
will be replaced.
The subset
argument can be used to select the studies that will be included in the data frame returned by the function. On the other hand, the include
argument simply selects for which studies the measure will be computed (if it shouldn't be computed for all of them).
The object is formatted and printed with the print
function. The summary
function can be used to obtain confidence intervals for the individual outcomes. See methods.escalc
for some additional method functions for "escalc"
objects.
With the aggregate
function, one can aggregate multiple effect sizes or outcomes belonging to the same study (or some other clustering variable) into a single combined effect size or outcome.
fitstats.Rd
fitstats(object, ...)
-# S3 method for rma
+# S3 method for class 'rma'
fitstats(object, ..., REML)
-# S3 method for rma
+# S3 method for class 'rma'
logLik(object, REML, ...)
-# S3 method for rma
+# S3 method for class 'rma'
deviance(object, REML, ...)
-# S3 method for rma
+# S3 method for class 'rma'
AIC(object, ..., k=2, correct=FALSE)
-# S3 method for rma
+# S3 method for class 'rma'
BIC(object, ...)
an object of class "rma"
.
optionally more fitted model objects (only for fitstats()
, AIC()
, and BIC()
).
logical to specify whether the regular or restricted likelihood function should be used to obtain the fit statistics and information criteria. Defaults to the method of estimation used (i.e., TRUE
if object
was fitted with method="REML"
and FALSE
otherwise).
numeric value to specify the penalty per parameter. The default (k=2
) is the classical AIC. See AIC
for more details.
logical to specify whether the regular (default) or corrected (i.e., AICc) should be extracted.
For fitstats
, a data frame with the (restricted) log-likelihood, deviance, AIC, BIC, and AICc values for each model passed to the function.
For fitstats
, a data frame with the (restricted) log-likelihood, deviance, AIC, BIC, and AICc values for each model passed to the function.
For logLik
, an object of class "logLik"
, providing the (restricted) log-likelihood of the model evaluated at the estimated coefficient(s).
For deviance
, a numeric value with the corresponding deviance.
For AIC
and BIC
, either a numeric value with the corresponding AIC, AICc, or BIC or a data frame with rows corresponding to the models and columns representing the number of parameters in the model (df
) and the AIC, AICc, or BIC.
fitted.rma.Rd
# S3 method for rma
+ # S3 method for class 'rma'
fitted(object, ...)
A vector with the fitted values.
+A vector with the fitted values.
forest.cumul.rma.Rd
# S3 method for cumul.rma
+ # S3 method for class 'cumul.rma'
forest(x, annotate=TRUE, header=FALSE,
xlim, alim, olim, ylim, at, steps=5,
- level=x$level, refline=0, digits=2L, width,
+ refline=0, digits=2L, width,
xlab, ilab, ilab.lab, ilab.xpos, ilab.pos,
transf, atransf, targs, rows,
efac=1, pch, psize, col, shade, colshade,
@@ -107,106 +107,104 @@ Forest Plots (Method for 'cumul.rma' Objects)
Arguments
- - x
+
+- x
an object of class "cumul.rma"
obtained with cumul
.
- - annotate
+ - annotate
logical to specify whether annotations should be added to the plot (the default is TRUE
).
- - header
+ - header
logical to specify whether column headings should be added to the plot (the default is FALSE
). Can also be a character vector to specify the left and right headings (or only the left one).
- - xlim
+ - xlim
horizontal limits of the plot region. If unspecified, the function sets the horizontal plot limits to some sensible values.
- - alim
+ - alim
the x-axis limits. If unspecified, the function sets the x-axis limits to some sensible values.
- - olim
+ - olim
optional argument to specify observation/outcome limits. If unspecified, no limits are used.
- - ylim
+ - ylim
the y-axis limits of the plot. If unspecified, the function sets the y-axis limits to some sensible values. Can also be a single value to set the lower bound (while the upper bound is still set automatically).
- - at
+ - at
position of the x-axis tick marks and corresponding labels. If unspecified, the function sets the tick mark positions/labels to some sensible values.
- - steps
+ - steps
the number of tick marks for the x-axis (the default is 5). Ignored when the positions are specified via the at
argument.
- - level
-numeric value between 0 and 100 to specify the confidence interval level (see here for details). The default is to take the value from the object.
-
- - refline
+ - refline
numeric value to specify the location of the vertical ‘reference’ line (the default is 0). The line can be suppressed by setting this argument to NA
. Can also be a vector to add multiple lines.
- - digits
+ - digits
integer to specify the number of decimal places to which the tick mark labels of the x-axis and the annotations should be rounded (the default is 2L
). Can also be a vector of two integers, the first to specify the number of decimal places for the annotations, the second for the x-axis labels. When specifying an integer (e.g., 2L
), trailing zeros after the decimal mark are dropped for the x-axis labels. When specifying a numeric value (e.g., 2
), trailing zeros are retained.
- - width
+ - width
optional integer to manually adjust the width of the columns for the annotations (either a single integer or a vector of the same length as the number of annotation columns).
- - xlab
+ - xlab
title for the x-axis. If unspecified, the function sets an appropriate axis title. Can also be a vector of three/two values (to also/only add labels at the end points of the x-axis limits).
- - ilab
+ - ilab
optional vector, matrix, or data frame providing additional information about the studies that should be added to the plot.
- - ilab.lab
+ - ilab.lab
optional character vector with (column) labels for the variable(s) given via ilab
.
- - ilab.xpos
+ - ilab.xpos
optional numeric vector to specify the horizontal position(s) of the variable(s) given via ilab
.
- - ilab.pos
+ - ilab.pos
integer(s) (either 1, 2, 3, or 4) to specify the alignment of the variable(s) given via ilab
(2 means right, 4 means left aligned). If unspecified, the default is to center the values.
- - transf
+ - transf
optional argument to specify a function to transform the estimates and confidence interval bounds (e.g., transf=exp
; see also transf). If unspecified, no transformation is used.
- - atransf
+ - atransf
optional argument to specify a function to transform the x-axis labels and annotations (e.g., atransf=exp
; see also transf). If unspecified, no transformation is used.
- - targs
+ - targs
optional arguments needed by the function specified via transf
or atransf
.
- - rows
+ - rows
optional vector to specify the rows (or more generally, the horizontal positions) for plotting the outcomes. Can also be a single value to specify the row (horizontal position) of the first outcome (the remaining outcomes are then plotted below this starting row).
- - efac
+ - efac
vertical expansion factor for confidence interval limits and arrows. The default value of 1 should usually work okay. Can also be a vector of two numbers, the first for CI limits, the second for arrows.
- - pch
+ - pch
plotting symbol to use for the estimates. By default, a filled square is used. See points
for other options. Can also be a vector of values.
- - psize
+ - psize
numeric value to specify the point sizes for the estimates (the default is 1). Can also be a vector of values.
- - col
+ - col
optional character string to specify the color of the estimates. Can also be a vector.
- - shade
+ - shade
optional character string or a (logical or numeric) vector for shading rows of the plot.
- - colshade
+ - colshade
optional argument to specify the color for the shading.
- - lty
+ - lty
optional character string to specify the line type for the confidence intervals. If unspecified, the function sets this to "solid"
by default.
- - fonts
+ - fonts
optional character string to specify the font for the study labels, annotations, and the extra information (if specified via ilab
). If unspecified, the default font is used.
- - cex
+ - cex
optional character and symbol expansion factor. If unspecified, the function sets this to a sensible value.
- - cex.lab
+ - cex.lab
optional expansion factor for the x-axis title. If unspecified, the function sets this to a sensible value.
- - cex.axis
+ - cex.axis
optional expansion factor for the x-axis labels. If unspecified, the function sets this to a sensible value.
- - ...
+ - ...
other arguments.
@@ -278,17 +276,17 @@ Examples
forest.default.Rd
# S3 method for default
+ # Default S3 method
forest(x, vi, sei, ci.lb, ci.ub,
annotate=TRUE, showweights=FALSE, header=FALSE,
xlim, alim, olim, ylim, at, steps=5,
@@ -108,133 +108,134 @@ Forest Plots (Default Method)
Arguments
- - x
+
+- x
vector of length \(k\) with the observed effect sizes or outcomes.
- - vi
+ - vi
vector of length \(k\) with the corresponding sampling variances.
- - sei
+ - sei
vector of length \(k\) with the corresponding standard errors (note: only one of the two, vi
or sei
, needs to be specified).
- - ci.lb
+ - ci.lb
vector of length \(k\) with the corresponding lower confidence interval bounds. Not needed if vi
or sei
is specified. See ‘Details’.
- - ci.ub
+ - ci.ub
vector of length \(k\) with the corresponding upper confidence interval bounds. Not needed if vi
or sei
is specified. See ‘Details’.
- - annotate
+ - annotate
logical to specify whether annotations should be added to the plot (the default is TRUE
).
- - showweights
+ - showweights
logical to specify whether the annotations should also include the inverse variance weights (the default is FALSE
).
- - header
+ - header
logical to specify whether column headings should be added to the plot (the default is FALSE
). Can also be a character vector to specify the left and right headings (or only the left one).
- - xlim
+ - xlim
horizontal limits of the plot region. If unspecified, the function sets the horizontal plot limits to some sensible values.
- - alim
+ - alim
the x-axis limits. If unspecified, the function sets the x-axis limits to some sensible values.
- - olim
+ - olim
optional argument to specify observation/outcome limits. If unspecified, no limits are used.
- - ylim
+ - ylim
the y-axis limits of the plot. If unspecified, the function sets the y-axis limits to some sensible values. Can also be a single value to set the lower bound (while the upper bound is still set automatically).
- - at
+ - at
position of the x-axis tick marks and corresponding labels. If unspecified, the function sets the tick mark positions/labels to some sensible values.
- - steps
+ - steps
the number of tick marks for the x-axis (the default is 5). Ignored when the positions are specified via the at
argument.
- - level
+ - level
numeric value between 0 and 100 to specify the confidence interval level (the default is 95; see here for details).
- - refline
+ - refline
numeric value to specify the location of the vertical ‘reference’ line (the default is 0). The line can be suppressed by setting this argument to NA
. Can also be a vector to add multiple lines.
- - digits
+ - digits
integer to specify the number of decimal places to which the tick mark labels of the x-axis and the annotations should be rounded (the default is 2L
). Can also be a vector of two integers, the first to specify the number of decimal places for the annotations, the second for the x-axis labels (when showweights=TRUE
, can also specify a third value for the weights). When specifying an integer (e.g., 2L
), trailing zeros after the decimal mark are dropped for the x-axis labels. When specifying a numeric value (e.g., 2
), trailing zeros are retained.
- - width
+ - width
optional integer to manually adjust the width of the columns for the annotations (either a single integer or a vector of the same length as the number of annotation columns).
- - xlab
+ - xlab
title for the x-axis. If unspecified, the function sets an appropriate axis title. Can also be a vector of three/two values (to also/only add labels at the end points of the x-axis limits).
- - slab
+ - slab
optional vector with labels for the \(k\) studies. If unspecified, the function tries to extract study labels from x
and otherwise simple labels are created within the function. To suppress labels, set this argument to NA
.
- - ilab
+ - ilab
optional vector, matrix, or data frame providing additional information about the studies that should be added to the plot.
- - ilab.lab
+ - ilab.lab
optional character vector with (column) labels for the variable(s) given via ilab
.
- - ilab.xpos
+ - ilab.xpos
optional numeric vector to specify the horizontal position(s) of the variable(s) given via ilab
.
- - ilab.pos
+ - ilab.pos
integer(s) (either 1, 2, 3, or 4) to specify the alignment of the variable(s) given via ilab
(2 means right, 4 means left aligned). If unspecified, the default is to center the values.
- - order
+ - order
optional character string to specify how the studies should be ordered. Can also be a variable based on which the studies will be ordered. See ‘Details’.
- - subset
+ - subset
optional (logical or numeric) vector to specify the subset of studies that should be included in the plot.
- - transf
+ - transf
optional argument to specify a function to transform the observed outcomes and corresponding confidence interval bounds (e.g., transf=exp
; see also transf). If unspecified, no transformation is used.
- - atransf
+ - atransf
optional argument to specify a function to transform the x-axis labels and annotations (e.g., atransf=exp
; see also transf). If unspecified, no transformation is used.
- - targs
+ - targs
optional arguments needed by the function specified via transf
or atransf
.
- - rows
+ - rows
optional vector to specify the rows (or more generally, the horizontal positions) for plotting the outcomes. Can also be a single value to specify the row (horizontal position) of the first outcome (the remaining outcomes are then plotted below this starting row).
- - efac
+ - efac
vertical expansion factor for confidence interval limits and arrows. The default value of 1 should usually work okay. Can also be a vector of two numbers, the first for CI limits, the second for arrows.
- - pch
+ - pch
plotting symbol to use for the observed outcomes. By default, a filled square is used. See points
for other options. Can also be a vector of values.
- - psize
+ - psize
optional numeric value to specify the point sizes for the observed outcomes. If unspecified, the point sizes are a function of the precision of the estimates. Can also be a vector of values.
- - plim
+ - plim
numeric vector of length 2 to scale the point sizes (ignored when psize
is specified). See ‘Details’.
- - col
+ - col
optional character string to specify the color of the observed outcomes. Can also be a vector.
- - shade
+ - shade
optional character string or a (logical or numeric) vector for shading rows of the plot. See ‘Details’.
- - colshade
+ - colshade
optional argument to specify the color for the shading.
- - lty
+ - lty
optional character string to specify the line type for the confidence intervals. If unspecified, the function sets this to "solid"
by default.
- - fonts
+ - fonts
optional character string to specify the font for the study labels, annotations, and the extra information (if specified via ilab
). If unspecified, the default font is used.
- - cex
+ - cex
optional character and symbol expansion factor. If unspecified, the function sets this to a sensible value.
- - cex.lab
+ - cex.lab
optional expansion factor for the x-axis title. If unspecified, the function sets this to a sensible value.
- - cex.axis
+ - cex.axis
optional expansion factor for the x-axis labels. If unspecified, the function sets this to a sensible value.
- - ...
+ - ...
other arguments.
@@ -276,7 +277,7 @@ Additional Optional Arguments
rowadj
numeric vector of length 3 to vertically adjust the position of the study labels, the annotations, and the extra information (if specified via ilab
). This is useful for fine-tuning the position of text added with different positional alignments (i.e., argument pos
in the text
function).
-
+
forest.Rd
forest.rma.Rd
# S3 method for rma
+ # S3 method for class 'rma'
forest(x, annotate=TRUE, addfit=TRUE, addpred=FALSE,
showweights=FALSE, header=FALSE,
xlim, alim, olim, ylim, at, steps=5,
@@ -108,133 +108,134 @@ Forest Plots (Method for 'rma' Objects)
Arguments
- - x
+
+- x
an object of class "rma"
.
- - annotate
+ - annotate
logical to specify whether annotations should be added to the plot (the default is TRUE
).
- - addfit
+ - addfit
logical to specify whether the summary estimate (for models without moderators) or fitted values (for models with moderators) should be added to the plot (the default is TRUE
). See ‘Details’.
- - addpred
+ - addpred
logical to specify whether the bounds of the prediction interval should be added to the plot (the default is FALSE
). See ‘Details’.
- - showweights
+ - showweights
logical to specify whether the annotations should also include the weights given to the observed outcomes during the model fitting (the default is FALSE
). See ‘Details’.
- - header
+ - header
logical to specify whether column headings should be added to the plot (the default is FALSE
). Can also be a character vector to specify the left and right headings (or only the left one).
- - xlim
+ - xlim
horizontal limits of the plot region. If unspecified, the function sets the horizontal plot limits to some sensible values.
- - alim
+ - alim
the x-axis limits. If unspecified, the function sets the x-axis limits to some sensible values.
- - olim
+ - olim
optional argument to specify observation/outcome limits. If unspecified, no limits are used.
- - ylim
+ - ylim
the y-axis limits of the plot. If unspecified, the function sets the y-axis limits to some sensible values. Can also be a single value to set the lower bound (while the upper bound is still set automatically).
- - at
+ - at
position of the x-axis tick marks and corresponding labels. If unspecified, the function sets the tick mark positions/labels to some sensible values.
- - steps
+ - steps
the number of tick marks for the x-axis (the default is 5). Ignored when the positions are specified via the at
argument.
- - level
+ - level
numeric value between 0 and 100 to specify the confidence interval level (see here for details). The default is to take the value from the object.
- - refline
+ - refline
numeric value to specify the location of the vertical ‘reference’ line (the default is 0). The line can be suppressed by setting this argument to NA
. Can also be a vector to add multiple lines.
- - digits
+ - digits
integer to specify the number of decimal places to which the tick mark labels of the x-axis and the annotations should be rounded (the default is 2L
). Can also be a vector of two integers, the first to specify the number of decimal places for the annotations, the second for the x-axis labels (when showweights=TRUE
, can also specify a third value for the weights). When specifying an integer (e.g., 2L
), trailing zeros after the decimal mark are dropped for the x-axis labels. When specifying a numeric value (e.g., 2
), trailing zeros are retained.
- - width
+ - width
optional integer to manually adjust the width of the columns for the annotations (either a single integer or a vector of the same length as the number of annotation columns).
- - xlab
+ - xlab
title for the x-axis. If unspecified, the function sets an appropriate axis title. Can also be a vector of three/two values (to also/only add labels at the end points of the x-axis limits).
- - slab
+ - slab
optional vector with labels for the \(k\) studies. If unspecified, the function tries to extract study labels from x
or simple labels are created within the function. To suppress labels, set this argument to NA
.
- - mlab
+ - mlab
optional character string giving a label to the summary estimate from an equal- or a random-effects model. If unspecified, the label is created within the function.
- - ilab
+ - ilab
optional vector, matrix, or data frame providing additional information about the studies that should be added to the plot.
- - ilab.lab
+ - ilab.lab
optional character vector with (column) labels for the variable(s) given via ilab
.
- - ilab.xpos
+ - ilab.xpos
optional numeric vector to specify the horizontal position(s) of the variable(s) given via ilab
.
- - ilab.pos
+ - ilab.pos
integer(s) (either 1, 2, 3, or 4) to specify the alignment of the variable(s) given via ilab
(2 means right, 4 means left aligned). If unspecified, the default is to center the values.
- - order
+ - order
optional character string to specify how the studies should be ordered. Can also be a variable based on which the studies will be ordered. See ‘Details’.
- - transf
+ - transf
optional argument to specify a function to transform the observed outcomes, summary estimates, fitted values, and confidence interval bounds (e.g., transf=exp
; see also transf). If unspecified, no transformation is used.
- - atransf
+ - atransf
optional argument to specify a function to transform the x-axis labels and annotations (e.g., atransf=exp
; see also transf). If unspecified, no transformation is used.
- - targs
+ - targs
optional arguments needed by the function specified via transf
or atransf
.
- - rows
+ - rows
optional vector to specify the rows (or more generally, the horizontal positions) for plotting the outcomes. Can also be a single value to specify the row (horizontal position) of the first outcome (the remaining outcomes are then plotted below this starting row).
- - efac
+ - efac
vertical expansion factor for confidence interval limits, arrows, and the symbol used to denote summary estimates. The default value of 1 should usually work okay. Can also be a vector of two numbers, the first for CI limits and arrows, the second for summary estimates. Can also be a vector of three numbers, the first for CI limits, the second for arrows, the third for summary estimates.
- - pch
+ - pch
plotting symbol to use for the observed outcomes. By default, a filled square is used. See points
for other options. Can also be a vector of values.
- - psize
+ - psize
optional numeric value to specify the point sizes for the observed outcomes. If unspecified, the point sizes are a function of the model weights. Can also be a vector of values.
- - plim
+ - plim
numeric vector of length 2 to scale the point sizes (ignored when psize
is specified). See ‘Details’.
- - colout
+ - colout
optional character string to specify the color of the observed outcomes. Can also be a vector.
- - col
+ - col
optional character string to specify the color of the summary polygon or fitted values.
- - border
+ - border
optional character string to specify the border color of the summary polygon or fitted values.
- - shade
+ - shade
optional character string or a (logical or numeric) vector for shading rows of the plot. See ‘Details’.
- - colshade
+ - colshade
optional argument to specify the color for the shading.
- - lty
+ - lty
optional character string to specify the line type for the confidence intervals. If unspecified, the function sets this to "solid"
by default.
- - fonts
+ - fonts
optional character string to specify the font for the study labels, annotations, and the extra information (if specified via ilab
). If unspecified, the default font is used.
- - cex
+ - cex
optional character and symbol expansion factor. If unspecified, the function sets this to a sensible value.
- - cex.lab
+ - cex.lab
optional expansion factor for the x-axis title. If unspecified, the function sets this to a sensible value.
- - cex.axis
+ - cex.axis
optional expansion factor for the x-axis labels. If unspecified, the function sets this to a sensible value.
- - ...
+ - ...
other arguments.
@@ -297,7 +298,7 @@ Additional Optional Arguments
rowadj
numeric vector of length 3 to vertically adjust the position of the study labels, the annotations, and the extra information (if specified via ilab
). This is useful for fine-tuning the position of text added with different positional alignments (i.e., argument pos
in the text
function).
-
+
formatters.Rd
Arguments for fmtp
:
Arguments for fmtp
:
vector of p-values to be formatted.
integer to specify the number of decimal places to which the values should be rounded. For fmmt
, can be a vector of length 2, to specify the number of digits for the test statistic and the p-value, respectively.
string to add as a prefix to the p-value (e.g., something like "p-val"
or just "p"
).
logical to specify whether an equal symbol should be shown before the p-value (when it is larger than the rounding cutoff).
logical to specify whether a space should be added between pname
, the equal/lesser symbol, and the p-value.
logical to specify whether a 0 should be shown before the decimal point when the p-value is below the rounding cutoff.
logical to specify whether formatted strings should be quoted when printed.
Arguments specific for fmtx
:
vector of numeric values to be formatted.
a character string giving a format modifier as defined for formatC
.
Arguments specific for fmtt
:
test statistic value to be formatted.
character string for the name of the test statistic.
optional value for the degrees of freedom of the test statistic.
optional value for the numerator degrees of freedom of the test statistic.
optional value for the denominator degrees of freedom of the test statistic.
the p-value corresponding to the test statistic.
either 1
or 2
to denote whether the degrees of freedom should be given before the test statistic (in parentheses) or after the test statistic.
logical to specify whether the formatted test result should be returned as a call or not.
other arguments.
A character vector with the formatted values. By default (i.e., when quote=FALSE
), formatted strings are not quoted when printed.
A character vector with the formatted values. By default (i.e., when quote=FALSE
), formatted strings are not quoted when printed.
formula.rma.Rd
# S3 method for rma
+ # S3 method for class 'rma'
formula(x, type="mods", ...)
The requested formula.
+The requested formula.
fsn.Rd
a vector with the observed effect sizes or outcomes or an object of class "rma"
.
vector with the corresponding sampling variances (ignored if x
is an object of class "rma"
).
vector with the corresponding standard errors (note: only one of the two, vi
or sei
, needs to be specified).
optional (logical or numeric) vector to specify the subset of studies that should be used for the calculation (ignored if x
is an object of class "rma"
).
optional data frame containing the variables given to the arguments above.
optional character string to specify the type of method to use for the calculation of the fail-safe N. Possible options are "Rosenthal"
(the default when x
is a vector with the observed effect sizes or outcomes), "Orwin"
, "Rosenberg"
, or "General"
(the default when x
is an object of class "rma"
). Can be abbreviated. See ‘Details’.
target alpha level for the Rosenthal, Rosenberg, and General methods (the default is .05).
target average effect size or outcome for the Orwin and General methods.
optional character string to specify the model fitting method for type="General"
(if unspecified, either "REML"
by default or the method that was used in fitting the "rma"
model). See rma.uni
for options.
logical to specify whether the general method should be based on exact (but slower) or approximate (but faster) calculations.
logical to specify whether output should be generated on the progress of the calculations for type="General"
(the default is FALSE
).
optional integer to specify the number of decimal places to which the printed results should be rounded.
other arguments.
An object of class "fsn"
. The object is a list containing the following components (some of which may be NA
if they are not applicable to the chosen method):
An object of class "fsn"
. The object is a list containing the following components (some of which may be NA
if they are not applicable to the chosen method):
the type of method used.
funnel.Rd
funnel(x, ...)
-# S3 method for rma
+# S3 method for class 'rma'
funnel(x, yaxis="sei",
xlim, ylim, xlab, ylab, slab,
steps=5, at, atransf, targs, digits, level=x$level,
@@ -106,7 +106,7 @@ Funnel Plots
refline, lty=3, pch, pch.fill, col, bg,
label=FALSE, offset=0.4, legend=FALSE, ...)
-# S3 method for default
+# Default S3 method
funnel(x, vi, sei, ni, subset, yaxis="sei",
xlim, ylim, xlab, ylab, slab,
steps=5, at, atransf, targs, digits, level=95,
@@ -117,100 +117,101 @@ Funnel Plots
Arguments
- - x
+
+- x
an object of class "rma"
or a vector with the observed effect sizes or outcomes.
- - vi
+ - vi
vector with the corresponding sampling variances (needed if x
is a vector with the observed effect sizes or outcomes).
- - sei
+ - sei
vector with the corresponding standard errors (note: only one of the two, vi
or sei
, needs to be specified).
- - ni
+ - ni
vector with the corresponding sample sizes. Only relevant when passing a vector via x
.
- - subset
+ - subset
optional (logical or numeric) vector to specify the subset of studies that should be included in the plot. Only relevant when passing a vector via x
.
- - yaxis
+ - yaxis
either "sei"
, "vi"
, "seinv"
, "vinv"
, "ni"
, "ninv"
, "sqrtni"
, "sqrtninv"
, "lni"
, or "wi"
to specify what values should be placed on the y-axis. See ‘Details’.
- - xlim
+ - xlim
x-axis limits. If unspecified, the function sets the x-axis limits to some sensible values.
- - ylim
+ - ylim
y-axis limits. If unspecified, the function sets the y-axis limits to some sensible values.
- - xlab
+ - xlab
title for the x-axis. If unspecified, the function sets an appropriate axis title.
- - ylab
+ - ylab
title for the y-axis. If unspecified, the function sets an appropriate axis title.
- - slab
+ - slab
optional vector with labels for the \(k\) studies. If unspecified, the function tries to extract study labels from x
.
- - steps
+ - steps
the number of tick marks for the y-axis (the default is 5).
- - at
+ - at
position of the x-axis tick marks and corresponding labels. If unspecified, the function sets the tick mark positions/labels to some sensible values.
- - atransf
+ - atransf
optional argument to specify a function to transform the x-axis labels (e.g., atransf=exp
; see also transf). If unspecified, no transformation is used.
- - targs
+ - targs
optional arguments needed by the function specified via atransf
.
- - digits
+ - digits
optional integer to specify the number of decimal places to which the tick mark labels of the x- and y-axis should be rounded. Can also be a vector of two integers, the first to specify the number of decimal places for the x-axis, the second for the y-axis labels (e.g., digits=c(2,3)
). If unspecified, the function tries to set the argument to some sensible values.
- - level
+ - level
numeric value between 0 and 100 to specify the level of the pseudo confidence interval region (see here for details). For "rma"
objects, the default is to take the value from the object. May also be a vector of values to obtain multiple regions. See ‘Examples’.
- - addtau2
+ - addtau2
logical to specify whether the amount of heterogeneity should be accounted for when drawing the pseudo confidence interval region (the default is FALSE
). Ignored when x
is a meta-regression model and residuals are plotted. See ‘Details’.
- - type
+ - type
either "rstandard"
(default) or "rstudent"
to specify whether the usual or deleted residuals should be used in creating the funnel plot when x
is a meta-regression model. See ‘Details’.
- - back
+ - back
optional character string to specify the color of the plotting region background.
- - shade
+ - shade
optional character string to specify the color of the pseudo confidence interval region. When level
is a vector of values, different shading colors can be specified for each region.
- - hlines
+ - hlines
optional character string to specify the color of the horizontal reference lines.
- - refline
+ - refline
numeric value to specify the location of the vertical ‘reference’ line and where the pseudo confidence interval should be centered. If unspecified, the reference line is drawn at the equal- or random-effects model estimate and at zero for meta-regression models (in which case the residuals are plotted) or when directly plotting observed outcomes.
- - lty
+ - lty
line type for the pseudo confidence interval region and the reference line. The default is to draw dotted lines (see par
for other options). Can also be a vector to specify the two line types separately.
- - pch
+ - pch
plotting symbol to use for the observed outcomes. By default, a filled circle is used. Can also be a vector of values. See points
for other options.
- - pch.fill
+ - pch.fill
plotting symbol to use for the outcomes filled in by the trim and fill method. By default, an open circle is used. Only relevant when plotting an object created by the trimfill
function.
- - col
+ - col
optional character string to specify the (border) color of the points. Can also be a vector.
- - bg
+ - bg
optional character string to specify the background color of open plot symbols. Can also be a vector.
- - label
+ - label
argument to control the labeling of the points (the default is FALSE
). See ‘Details’.
- - offset
+ - offset
argument to control the distance between the points and the corresponding labels.
- - legend
+ - legend
logical to specify whether a legend should be added to the plot (the default is FALSE
). See ‘Details’.
- - ...
+ - ...
other arguments.
@@ -244,9 +245,7 @@ Note
A data frame with components:
+A data frame with components:
the x-axis coordinates of the points that were plotted.
gosh.Rd
gosh(x, ...)
-# S3 method for rma
+# S3 method for class 'rma'
gosh(x, subsets, progbar=TRUE, parallel="no", ncpus=1, cl, ...)
an object of class "rma"
.
optional integer to specify the number of subsets.
logical to specify whether a progress bar should be shown (the default is TRUE
).
character string to specify whether parallel processing should be used (the default is "no"
). For parallel processing, set to either "snow"
or "multicore"
. See ‘Note’.
integer to specify the number of processes to use in the parallel processing.
optional cluster to use if parallel="snow"
. If unspecified, a cluster on the local machine is created for the duration of the call.
other arguments.
An object of class "gosh.rma"
. The object is a list containing the following components:
An object of class "gosh.rma"
. The object is a list containing the following components:
a data frame with the results for each subset (including various heterogeneity statistics and the model coefficient(s)).
hc.Rd
hc(object, ...)
-# S3 method for rma.uni
+# S3 method for class 'rma.uni'
hc(object, digits, transf, targs, control, ...)
an object of class "rma.uni"
.
optional integer to specify the number of decimal places to which the printed results should be rounded. If unspecified, the default is to take the value from the object.
optional argument to specify a function to transform the estimate and the corresponding interval bounds (e.g., transf=exp
; see also transf). If unspecified, no transformation is used.
optional arguments needed by the function specified under transf
.
list of control values for the iterative algorithm. If unspecified, default values are used. See ‘Note’.
other arguments.
An object of class "hc.rma.uni"
. The object is a list containing the following components:
An object of class "hc.rma.uni"
. The object is a list containing the following components:
estimated average true outcome.
influence.rma.mv.Rd
# S3 method for rma.mv
+ # S3 method for class 'rma.mv'
cooks.distance(model, progbar=FALSE, cluster,
reestimate=TRUE, parallel="no", ncpus=1, cl, ...)
-# S3 method for rma.mv
+# S3 method for class 'rma.mv'
dfbetas(model, progbar=FALSE, cluster,
reestimate=TRUE, parallel="no", ncpus=1, cl, ...)
-# S3 method for rma.mv
+# S3 method for class 'rma.mv'
hatvalues(model, type="diagonal", ...)
an object of class "rma.mv"
.
logical to specify whether a progress bar should be shown (the default is FALSE
).
optional vector to specify a clustering variable to use for computing the Cook's distances or DFBETAS values. If unspecified, these measures are computed for the individual observed effect sizes or outcomes.
logical to specify whether variance/correlation components should be re-estimated after deletion of the \(i\textrm{th}\) case (the default is TRUE
).
character string to specify whether parallel processing should be used (the default is "no"
). For parallel processing, set to either "snow"
or "multicore"
. See ‘Note’.
integer to specify the number of processes to use in the parallel processing.
optional cluster to use if parallel="snow"
. If unspecified, a cluster on the local machine is created for the duration of the call.
character string to specify whether only the diagonal of the hat matrix ("diagonal"
) or the entire hat matrix ("matrix"
) should be returned.
other arguments.
The cooks.distance
function returns a vector. The dfbetas
function returns a data frame. The hatvalues
function returns either a vector with the diagonal elements of the hat matrix or the entire hat matrix.
The cooks.distance
function returns a vector. The dfbetas
function returns a data frame. The hatvalues
function returns either a vector with the diagonal elements of the hat matrix or the entire hat matrix.
influence.rma.uni.Rd
# S3 method for rma.uni
+ # S3 method for class 'rma.uni'
influence(model, digits, progbar=FALSE, ...)
-# S3 method for infl.rma.uni
+# S3 method for class 'infl.rma.uni'
print(x, digits=x$digits, infonly=FALSE, ...)
-# S3 method for rma.uni
+# S3 method for class 'rma.uni'
cooks.distance(model, progbar=FALSE, ...)
-# S3 method for rma.uni
+# S3 method for class 'rma.uni'
dfbetas(model, progbar=FALSE, ...)
-# S3 method for rma.uni
+# S3 method for class 'rma.uni'
hatvalues(model, type="diagonal", ...)
an object of class "rma.uni"
.
an object of class "infl.rma.uni"
(for print
).
optional integer to specify the number of decimal places to which the printed results should be rounded. If unspecified, the default is to take the value from the object.
logical to specify whether a progress bar should be shown (the default is FALSE
).
logical to specify whether only the influential cases should be printed (the default is FALSE
).
character string to specify whether only the diagonal of the hat matrix ("diagonal"
) or the entire hat matrix ("matrix"
) should be returned.
other arguments.
An object of class "infl.rma.uni"
, which is a list containing the following components:
An object of class "infl.rma.uni"
, which is a list containing the following components:
an element of class "list.rma"
with the externally standardized residuals, DFFITS values, Cook's distances, covariance ratios, leave-one-out \(\tau^2\) estimates, leave-one-out (residual) heterogeneity test statistics, hat values, weights, and an indicator whether a case is influential.
labbe.Rd
labbe(x, ...)
-# S3 method for rma
+# S3 method for class 'rma'
labbe(x, xlim, ylim, lim, xlab, ylab, flip=FALSE,
ci=FALSE, pi=FALSE, grid=FALSE, legend=FALSE,
add=x$add, to=x$to, transf, targs,
@@ -107,70 +107,71 @@ L'Abbe Plots for 'rma' Objects
Arguments
- - x
+
+- x
an object of class "rma"
.
- - xlim
+ - xlim
x-axis limits. If unspecified, the function sets the x-axis limits to some sensible values.
- - ylim
+ - ylim
y-axis limits. If unspecified, the function sets the y-axis limits to some sensible values.
- - lim
+ - lim
axis limits. If specified, this is used for both xlim
and ylim
.
- - xlab
+ - xlab
title for the x-axis. If unspecified, the function sets an appropriate axis title.
- - ylab
+ - ylab
title for the y-axis. If unspecified, the function sets an appropriate axis title.
- - flip
+ - flip
logical to specify whether the groups to plot on the x- and y-axis should be flipped (the default is FALSE
).
- - ci
+ - ci
logical to specify whether the confidence interval region should be shown in the plot (the default is FALSE
). Can also be a color name.
- - pi
+ - pi
logical to specify whether the prediction interval region should be shown in the plot (the default is FALSE
). Can also be a color name.
- - grid
+ - grid
logical to specify whether a grid should be added to the plot (the default is FALSE
). Can also be a color name.
- - legend
+ - legend
logical to specify whether a legend should be added to the plot (the default is FALSE
). Can also be a keyword to specify the position of the legend (see legend
).
- - add
+ - add
See the documentation of the escalc
function for more details.
- - to
+ - to
See the documentation of the escalc
function for more details.
- - transf
+ - transf
optional argument to specify a function to transform the outcomes (e.g., transf=exp
; see also transf). If unspecified, no transformation is used.
- - targs
+ - targs
optional arguments needed by the function specified under transf
.
- - pch
+ - pch
plotting symbol to use for the outcomes. By default, an open circle is used. Can also be a vector of values. See points
for other options.
- - psize
+ - psize
optional numeric vector to specify the point sizes for the outcomes. If unspecified, the point sizes are a function of the precision of the outcomes. Can also be a vector of values.
- - plim
+ - plim
numeric vector of length 2 to scale the point sizes (ignored when psize
is specified). See ‘Details’.
- - col
+ - col
optional character string to specify the (border) color of the points. Can also be a vector.
- - bg
+ - bg
optional character string to specify the background color of open plot symbols. Can also be a vector. Set to NA
to make the plotting symbols transparent.
- - lty
+ - lty
optional character vector to specify the line type for the diagonal reference line of no effect and the line that indicates the estimated effect based on the fitted model. If unspecified, the function sets this to c("solid","dashed")
by default (use "blank"
to suppress a line).
- - ...
+ - ...
other arguments.
@@ -184,9 +185,7 @@ Details
A data frame with components:
+A data frame with components:
the x-axis coordinates of the points that were plotted.
leave1out.Rd
leave1out(x, ...)
-# S3 method for rma.uni
+# S3 method for class 'rma.uni'
leave1out(x, digits, transf, targs, progbar=FALSE, ...)
-# S3 method for rma.mh
+# S3 method for class 'rma.mh'
leave1out(x, digits, transf, targs, progbar=FALSE, ...)
-# S3 method for rma.peto
+# S3 method for class 'rma.peto'
leave1out(x, digits, transf, targs, progbar=FALSE, ...)
an object of class "rma.uni"
, "rma.mh"
, or "rma.peto"
.
optional integer to specify the number of decimal places to which the printed results should be rounded. If unspecified, the default is to take the value from the object.
optional argument to specify a function to transform the model coefficients and interval bounds (e.g., transf=exp
; see also transf). If unspecified, no transformation is used.
optional arguments needed by the function specified under transf
.
logical to specify whether a progress bar should be shown (the default is FALSE
).
other arguments.
An object of class "list.rma"
. The object is a list containing the following components:
An object of class "list.rma"
. The object is a list containing the following components:
estimated (average) outcomes.
When the model was fitted with test="t"
, test="knha"
, test="hksj"
, or test="adhoc"
, then zval
is called tval
in the object that is returned by the function.
The object is formatted and printed with the print
function. To format the results as a data frame, one can use the as.data.frame
function.
llplot.Rd
a character string to specify for which effect size or outcome measure the likelihoods should be calculated. See ‘Details’ for possible options and how the data should then be specified.
vector with the observed effect sizes or outcomes.
vector with the corresponding sampling variances.
vector to specify the corresponding standard.
vector to specify the \(2 \times 2\) table frequencies (upper left cell).
vector to specify the \(2 \times 2\) table frequencies (upper right cell).
vector to specify the \(2 \times 2\) table frequencies (lower left cell).
vector to specify the \(2 \times 2\) table frequencies (lower right cell).
vector to specify the group sizes or row totals (first group/row).
vector to specify the group sizes or row totals (second group/row).
optional data frame containing the variables given to the arguments above.
optional (logical or numeric) vector to specify the subset of studies that should be included in the plot.
logical to specify whether studies with no cases (or only cases) in both groups should be dropped. See ‘Details’.
integer to specify for how many distinct values the likelihood should be evaluated.
x-axis limits. If unspecified, the function sets the x-axis limits to some sensible values.
y-axis limits. If unspecified, the function sets the y-axis limits to some sensible values.
title for the x-axis. If unspecified, the function sets an appropriate axis title.
title for the y-axis. If unspecified, the function sets an appropriate axis title.
logical to specify whether the likelihood values should be scaled, so that the total area under each curve is (approximately) equal to 1.
the line types (either a single value or a vector of length \(k\)). If unspecified, the function sets the line types according to some characteristics of the likelihood function. See ‘Details’.
the line widths (either a single value or a vector of length \(k\)). If unspecified, the function sets the widths according to the sampling variances (so that the line is thicker for more precise studies and vice-versa).
the line colors (either a single value or a vector of length \(k\)). If unspecified, the function uses various shades of gray according to the sampling variances (so that darker shades are used for more precise studies and vice-versa).
numeric value between 0 and 100 to specify the plotting limits for each likelihood line in terms of the confidence interval (the default is 99.99).
numeric value to specify the location of the vertical ‘reference’ line (the default is 0). The line can be suppressed by setting this argument to NA
.
other arguments.
matreg.Rd
index (or name given as a character string) of the outcome variable.
indices (or names given as a character vector) of the predictor variables.
correlation or covariance matrix (or only the lower triangular part including the diagonal).
sample size based on which the elements in the correlation/covariance matrix were computed.
variance-covariance matrix of the lower triangular elements of the correlation/covariance matrix. Either V
or n
should be specified, not both. See ‘Details’.
logical to specify whether R
is a covariance matrix (the default is FALSE
).
optional vector to specify the means of the variables (only relevant when cov=TRUE
).
logical to specify whether R
is a matrix of r-to-z transformed correlations and hence should be back-transformed to raw correlations (the default is FALSE
). See ‘Details’.
logical to specify whether the nearPD
function from the Matrix package should be used when the \(R_{x,x}\) matrix cannot be inverted. See ‘Note’.
numeric value between 0 and 100 to specify the confidence interval level (the default is 95; see here for details).
optional integer to specify the number of decimal places to which the printed results should be rounded.
other arguments.
An object of class "matreg"
. The object is a list containing the following components:
An object of class "matreg"
. The object is a list containing the following components:
a data frame with the estimated model coefficients, standard errors, test statistics, degrees of freedom (only for t-tests), p-values, and lower/upper confidence interval bounds.
metafor-package.Rd
The paper mentioned above is a good starting place for those interested in using the package. The purpose of the article is to provide a general overview of the package and its capabilities (as of version 1.4-0). Not all of the functions and options are described in the paper, but it should provide a useful introduction to the package. The paper can be freely downloaded from the URL given above or can be directly loaded with the command vignette("metafor")
.
In addition to reading the paper, carefully read this page and then the help pages for the escalc
and the rma.uni
functions (or the rma.mh
, rma.peto
, rma.glmm
, and/or rma.mv
functions if you intend to use these methods). The help pages for these functions provide links to many additional functions, which can be used after fitting a model. You can also read the entire documentation online at https://wviechtb.github.io/metafor/ (where it is nicely formatted and the output from all examples is provided).
A (pdf) diagram showing the various functions in the metafor package (and how they are related to each other) can be opened with the command vignette("diagram", package="metafor")
.
A (pdf) diagram showing the various functions in the metafor package (and how they are related to each other) can be opened with the command vignette("diagram", package="metafor")
.
Finally, additional information about the package, several detailed analysis examples, examples of plots and figures provided by the package (with the corresponding code), some additional tips and notes, and a FAQ can be found on the package website at https://www.metafor-project.org.
metafor.news.Rd
# \dontrun{
metafor.news()
-#> Changes in version 4.7-23 (2024-07-02)
+#> Changes in version 4.7-24 (2024-07-09)
+#>
+#> - added collapse argument to the various cumul() functions
#>
#> - the predict.rma() and predict.rma.ls() functions now also accept a
#> matrix as input that includes a column for the intercept term (in
@@ -2394,17 +2396,17 @@ Examples
methods.anova.rma.Rd
# S3 method for anova.rma
+ # S3 method for class 'anova.rma'
as.data.frame(x, ...)
-# S3 method for list.anova.rma
+# S3 method for class 'list.anova.rma'
as.data.frame(x, ...)
methods.confint.rma.Rd
# S3 method for confint.rma
+ # S3 method for class 'confint.rma'
as.data.frame(x, ...)
-# S3 method for list.confint.rma
+# S3 method for class 'list.confint.rma'
as.data.frame(x, ...)
methods.escalc.Rd
# S3 method for escalc
-[(x, i, ...)
-# S3 method for escalc
-$(x, name) <- value
-# S3 method for escalc
-cbind(..., deparse.level=1)
-# S3 method for escalc
-rbind(..., deparse.level=1)
methods.list.rma.Rd
# S3 method for list.rma
-as.data.frame(x, ...)
-# S3 method for list.rma
-as.matrix(x, ...)
-# S3 method for list.rma
-[(x, i, ...)
-# S3 method for list.rma
-head(x, n=6L, ...)
-# S3 method for list.rma
-tail(x, n=6L, ...)
-# S3 method for list.rma
-$(x, name) <- value
# S3 method for class 'list.rma'
+as.data.frame(x, ...)
+# S3 method for class 'list.rma'
+as.matrix(x, ...)
+# S3 method for class 'list.rma'
+x[i, ...]
+# S3 method for class 'list.rma'
+head(x, n=6L, ...)
+# S3 method for class 'list.rma'
+tail(x, n=6L, ...)
+# S3 method for class 'list.rma'
+x$name <- value
methods.matreg.Rd
# S3 method for matreg
+
Either a vector with the estimated model coefficients or a variance-covariance matrix.
+Either a vector with the estimated model coefficients or a variance-covariance matrix.
methods.vif.rma.Rd
# S3 method for vif.rma
+ # S3 method for class 'vif.rma'
as.data.frame(x, ...)
mfopt.Rd
theme
character string to specify how plots created by the package should be themed. The default is "default"
, which means that the default foreground and background colors of plotting devices are used. Alternative options are "light"
and "dark"
, which forces plots to be drawn with a light or dark background, respectively. See here for further details. RStudio users can also set this to "auto"
, in which case plotting colors are chosen depending on the RStudio theme used (for some themes, using "auto2"
might be aesthetically more pleasing). One can also use setmfopt(theme="custom", fg=<color>, bg=<color>)
to set the foreground and background colors to custom choices (depending on the colors chosen, using "custom2"
might be aesthetically more pleasing).
Either a vector with the value for the chosen option or a list with all options.
+Either a vector with the value for the chosen option or a list with all options.
misc-models.Rd
misc-options.Rd
misc-recs.Rd
model.matrix.rma.Rd
# S3 method for rma
+ # S3 method for class 'rma'
model.matrix(object, asdf, ...)
The model matrix.
+The model matrix.
pairwise.Rd
an object of class "rma"
.
vector of indices to specify for which coefficients pairwise contrasts should be constructed. Can also be a string to grep
for. See ‘Details’.
optional argument to specify a second set of coefficients that should also be included in the contrast matrix.
other arguments.
When a meta-regression model includes a categorical moderator variable (i.e., a factor), there is often interest in testing whether the coefficients representing the various levels of the factor differ significantly from each other. The present function constructs the pairwise contrast matrix between all factor levels for a particular factor, which can be used together with the anova
function to carry out such tests and the predict
function to obtain corresponding confidence intervals.
When a meta-regression model includes a categorical moderator variable (i.e., a factor), there is often interest in testing whether the coefficients representing the various levels of the factor differ significantly from each other. The present function constructs the pairwise contrast matrix between all factor levels for a particular factor, which can be used together with the anova
function to carry out such tests and the predict
function to obtain corresponding confidence intervals.
The x
argument is used to specify a meta-regression model and the btt
argument the indices of the coefficients for which pairwise contrasts should be constructed. For example, with btt=2:4
, contrasts are formed based on the second, third, and fourth coefficient of the model. Instead of specifying the coefficient numbers, one can specify a string for btt
. In that case, grep
will be used to search for all coefficient names that match the string.
At times, it may be useful to include a second set of coefficients in the contrast matrix (not as pairwise contrasts, but as ‘main effects’). This can be done via the btt2
argument.
When using the present function in a call to the anova
or predict
functions, argument x
does not need to specified, as the function will then automatically construct the contrast matrix based on the model object passed to the anova
or predict
function. See below for examples.
permutest.Rd
permutest(x, ...)
-# S3 method for rma.uni
+# S3 method for class 'rma.uni'
permutest(x, exact=FALSE, iter=1000, btt=x$btt,
permci=FALSE, progbar=TRUE, digits, control, ...)
-# S3 method for rma.ls
+# S3 method for class 'rma.ls'
permutest(x, exact=FALSE, iter=1000, btt=x$btt, att=x$att,
progbar=TRUE, digits, control, ...)
an object of class "rma.uni"
or "rma.ls"
.
logical to specify whether an exact permutation test should be carried out (the default is FALSE
). See ‘Details’.
integer to specify the number of iterations for the permutation test when not doing an exact test (the default is 1000
).
optional vector of indices (or list thereof) to specify which coefficients should be included in the Wald-type test. Can also be a string to grep
for.
optional vector of indices (or list thereof) to specify which scale coefficients should be included in the Wald-type test. Can also be a string to grep
for.
logical to specify whether permutation-based confidence intervals (CIs) should also be constructed (the default is FALSE
). Can also be a vector of indices to specify for which coefficients a permutation-based CI should be obtained.
logical to specify whether a progress bar should be shown (the default is TRUE
).
optional integer to specify the number of decimal places to which the printed results should be rounded. If unspecified, the default is to take the value from the object.
list of control values for numerical comparisons (comptol
) and for uniroot
(i.e., tol
and maxiter
). The latter is only relevant when permci=TRUE
. See ‘Note’.
other arguments.
An object of class "permutest.rma.uni"
. The object is a list containing the following components:
An object of class "permutest.rma.uni"
. The object is a list containing the following components:
p-value(s) based on the permutation test.
plot.cumul.rma.Rd
# S3 method for cumul.rma
+ # S3 method for class 'cumul.rma'
plot(x, yaxis, xlim, ylim, xlab, ylab,
at, transf, atransf, targs, digits, cols,
grid=TRUE, pch=19, cex=1, lwd=2, ...)
@@ -103,55 +103,56 @@ Plot Method for 'cumul.rma' Objects
Arguments
- - x
+
+- x
an object of class "cumul.rma"
obtained with cumul
.
- - yaxis
+ - yaxis
either "tau2"
, "I2"
, or "H2"
to specify what values should be placed on the y-axis. See ‘Details’.
- - xlim
+ - xlim
x-axis limits. If unspecified, the function sets the x-axis limits to some sensible values.
- - ylim
+ - ylim
y-axis limits. If unspecified, the function sets the y-axis limits to some sensible values.
- - xlab
+ - xlab
title for the x-axis. If unspecified, the function sets an appropriate axis title.
- - ylab
+ - ylab
title for the y-axis. If unspecified, the function sets an appropriate axis title.
- - at
+ - at
position of the x-axis tick marks and corresponding labels. If unspecified, the function sets the tick mark positions/labels to some sensible values.
- - transf
+ - transf
optional argument to specify a function to transform the summary estimates (e.g., transf=exp
; see also transf). If unspecified, no transformation is used.
- - atransf
+ - atransf
optional argument to specify a function to transform the x-axis labels (e.g., atransf=exp
; see also transf). If unspecified, no transformation is used.
- - targs
+ - targs
optional arguments needed by the function specified via transf
or atransf
.
- - digits
+ - digits
optional integer to specify the number of decimal places to which the tick mark labels of the x- and y-axis should be rounded. Can also be a vector of two integers, the first to specify the number of decimal places for the x-axis, the second for the y-axis labels (e.g., digits=c(2,3)
). If unspecified, the function tries to set the argument to some sensible values.
- - cols
+ - cols
vector with two or more colors for visualizing the order of the cumulative results.
- - grid
+ - grid
logical to specify whether a grid should be added to the plot. Can also be a color name.
- - pch
+ - pch
plotting symbol to use. By default, a filled circle is used. See points
for other options.
- - cex
+ - cex
symbol expansion factor.
- - lwd
+ - lwd
line width.
- - ...
+ - ...
other arguments.
@@ -207,17 +208,17 @@ Examples
plot.gosh.rma.Rd
# S3 method for gosh.rma
+ # S3 method for class 'gosh.rma'
plot(x, het="I2", pch=16, cex, out, col, alpha, border,
xlim, ylim, xhist=TRUE, yhist=TRUE, hh=0.3, breaks,
adjust, lwd, labels, ...)
@@ -103,58 +103,59 @@ Plot Method for 'gosh.rma' Objects
Arguments
- - x
+
+- x
an object of class "gosh.rma"
obtained with gosh
.
- - het
+ - het
character string to specify the heterogeneity measure to plot. Either "I2"
, "H2"
, "QE"
, "tau2"
, or "tau"
(the last two only for random/mixed-effects models).
- - pch
+ - pch
plotting symbol to use. By default, a borderless filled circle is used. See points
for other options.
- - cex
+ - cex
symbol expansion factor.
- - out
+ - out
optional integer to specify the number of a study that may be a potential outlier. If specified, subsets containing the specified study are drawn in a different color than those not containing the study.
- - col
+ - col
optional character string to specify the color of the points (if unspecified, points are drawn in black). When out
is used, two colors should be specified (if unspecified, red is used for subsets containing the specified study and blue otherwise).
- - alpha
+ - alpha
optional alpha transparency value for the points (0 means fully transparent and 1 means opaque). If unspecified, the function sets this to a sensible value.
- - border
+ - border
optional character string to specify the color of the borders of the histogram bars. Set to FALSE
to omit the borders.
- - xlim
+ - xlim
x-axis limits. If unspecified, the function sets the x-axis limits to some sensible values.
- - ylim
+ - ylim
y-axis limits. If unspecified, the function sets the y-axis limits to some sensible values.
- - xhist
+ - xhist
logical to specify whether a histogram should be drawn for the x-axis (the default is TRUE
).
- - yhist
+ - yhist
logical to specify whether a histogram should be drawn for the y-axis (the default is TRUE
).
- - hh
+ - hh
numeric value (or vector of two values) to adjust the height of the histogram(s). Must be between 0 and 1, but should not be too close to 0 or 1, as otherwise the plot cannot be drawn.
- - breaks
+ - breaks
optional argument passed on to hist
for choosing the (number of) breakpoints of the histogram(s).
- - adjust
+ - adjust
optional argument passed on to density
for adjusting the bandwidth of the kernel density estimate(s) (values larger than 1 result in more smoothing).
- - lwd
+ - lwd
optional numeric value to specify the line width of the estimated densities. Set to 0
to omit the line(s).
- - labels
+ - labels
optional argument to specify the x-axis and y-axis labels (or passed on to pairs
to specify the names of the variables in the scatter plot matrix).
- - ...
+ - ...
other arguments.
@@ -208,17 +209,17 @@ Examples
plot.infl.rma.uni.Rd
# S3 method for infl.rma.uni
+ # S3 method for class 'infl.rma.uni'
plot(x, plotinf=TRUE, plotdfbs=FALSE, dfbsnew=FALSE, logcov=TRUE,
layout, slab.style=1, las=0, pch=21, bg, bg.infl, col.na, ...)
an object of class "infl.rma.uni"
obtained with influence
.
logical to specify whether the various case diagnostics should be plotted (the default is TRUE
). Can also be a vector of up to 8 integers to specify which plots to draw. See ‘Details’ for the numbers corresponding to the various plots.
logical to specify whether the DFBETAS values should be plotted (the default is FALSE
). Can also be a vector of integers to specify for which coefficient(s) to plot the DFBETAS values.
logical to specify whether a new device should be opened for plotting the DFBETAS values (the default is FALSE
).
logical to specify whether the covariance ratios should be plotted on a log scale (the default is TRUE
).
optional vector of two numbers to specify the number of rows and columns for the layout of the figure.
integer to specify the style of the x-axis labels: 1 = study number, 2 = study label, 3 = abbreviated study label. Note that study labels, even when abbreviated, may be too long to fit in the margins (see argument mar
for par
to adjust the margin sizes).
integer between 0 and 3 to specify the alignment of the axis labels (see par
). The most useful alternative to 0 is 3, so that the x-axis labels are drawn vertical to the axis.
plotting symbol to use. By default, an open circle is used. See points
for other options.
optional character string to specify the background color of open plotting symbols. If unspecified, gray is used by default.
optional character string to specify the background color when the point is considered influential. If unspecified, red is used by default.
optional character string to specify the color for lines connecting two points with NA
values in between. If unspecified, a light shade of gray is used by default.
other arguments.
plot.permutest.rma.uni.Rd
# S3 method for permutest.rma.uni
+ # S3 method for class 'permutest.rma.uni'
plot(x, beta, alpha, QM=FALSE, QS=FALSE,
breaks="Scott", freq=FALSE, col, border, col.out, col.ref, col.density,
trim=0, adjust=1, lwd=c(2,0,0,4), layout, legend=FALSE, ...)
@@ -103,58 +103,59 @@ Plot Method for 'permutest.rma.uni' Objects
Arguments
- - x
+
+- x
an object of class "permutest.rma.uni"
obtained with permutest
.
- - beta
+ - beta
optional vector of indices to specify which (location) coefficients should be plotted.
- - alpha
+ - alpha
optional vector of indices to specify which scale coefficients should be plotted. Only relevant for location-scale models (see rma.uni
).
- - QM
+ - QM
logical to specify whether the permutation distribution of the omnibus test of the (location) coefficients should be plotted (the default is FALSE
).
- - QS
+ - QS
logical to specify whether the permutation distribution of the omnibus test of the scale coefficients should be plotted (the default is FALSE
). Only relevant for location-scale models (see rma.uni
).
- - breaks
+ - breaks
argument to be passed on to the corresponding argument of hist
to set (the method for determining) the (number of) breakpoints.
- - freq
+ - freq
logical to specify whether frequencies or probability densities should be plotted (the default is FALSE
to plot densities).
- - col
+ - col
optional character string to specify the color of the histogram bars.
- - border
+ - border
optional character string to specify the color of the borders around the bars.
- - col.out
+ - col.out
optional character string to specify the color of the bars that are more extreme than the observed test statistic (the default is a semi-transparent shade of red).
- - col.ref
+ - col.ref
optional character string to specify the color of the theoretical reference/null distribution that is superimposed on top of the histogram (the default is a dark shade of gray).
- - col.density
+ - col.density
optional character string to specify the color of the kernel density estimate of the permutation distribution that is superimposed on top of the histogram (the default is blue).
- - trim
+ - trim
the fraction (up to 0.5) of observations to be trimmed from the tails of each permutation distribution before its histogram is plotted.
- - adjust
+ - adjust
numeric value to be passed on to the corresponding argument of density
(for adjusting the bandwidth of the kernel density estimate).
- - lwd
+ - lwd
numeric vector to specify the width of the vertical lines corresponding to the value of the observed test statistic, of the theoretical reference/null distribution, of the density estimate, and of the vertical line at 0 (note: by default, the theoretical reference/null distribution and the density estimate both have a line width of 0 and are therefore not plotted).
- - layout
+ - layout
optional vector of two numbers to specify the number of rows and columns for the layout of the figure.
- - legend
+ - legend
logical to specify whether a legend should be added to the plot (the default is FALSE
). Can also be a keyword to specify the position of the legend (see legend
).
- - ...
+ - ...
other arguments.
@@ -305,17 +306,17 @@ Examples
plot.rma.Rd
# S3 method for rma.uni
+ # S3 method for class 'rma.uni'
plot(x, qqplot=FALSE, ...)
-# S3 method for rma.mh
+# S3 method for class 'rma.mh'
plot(x, qqplot=FALSE, ...)
-# S3 method for rma.peto
+# S3 method for class 'rma.peto'
plot(x, qqplot=FALSE, ...)
-# S3 method for rma.glmm
+# S3 method for class 'rma.glmm'
plot(x, qqplot=FALSE, ...)
plot.rma.uni.selmodel.Rd
# S3 method for rma.uni.selmodel
+ # S3 method for class 'rma.uni.selmodel'
plot(x, xlim, ylim, n=1000, prec="max", scale=FALSE,
ci=FALSE, reps=1000, shade=TRUE, rug=TRUE, add=FALSE,
lty=c("solid","dotted"), lwd=c(2,1), ...)
@@ -103,46 +103,47 @@ Plot Method for 'plot.rma.uni.selmodel' Objects
Arguments
- - x
+
+- x
an object of class "rma.uni.selmodel"
obtained with selmodel
.
- - xlim
+ - xlim
x-axis limits. Essentially the range of p-values for which the selection function should be drawn. If unspecified, the function sets the limits automatically.
- - ylim
+ - ylim
y-axis limits. If unspecified, the function sets the limits automatically.
- - n
+ - n
numeric value to specify for how many p-values within the x-axis limits the function value should be computed (the default is 1000).
- - prec
+ - prec
either a character string (with options "max"
, "min"
, "mean"
, or "median"
) or a numeric value. See ‘Details’.
- - scale
+ - scale
logical to specify whether the function values should be rescaled to a 0 to 1 range (the default is FALSE
).
- - ci
+ - ci
logical to specify whether a confidence interval should be drawn around the selection function (the default is FALSE
). Can also be a string (with options "boot"
or "wald"
). See ‘Details’.
- - reps
+ - reps
numeric value to specify the number of bootstrap samples to draw for generating the confidence interval bounds (the default is 1000).
- - shade
+ - shade
logical to specify whether the confidence interval region should be shaded (the default is TRUE
). Can also be a character vector to specify the color for the shading.
- - rug
+ - rug
logical to specify whether the observed p-values should be added as tick marks on the x-axis (the default is TRUE
).
- - add
+ - add
logical to specify whether the function should be added to an existing plot (the default is FALSE
).
- - lty
+ - lty
the line types for the selection function and the confidence interval bounds.
- - lwd
+ - lwd
the line widths for the selection function and the confidence interval bounds.
- - ...
+ - ...
other arguments.
@@ -228,17 +229,17 @@ Examples
plot.vif.rma.Rd
# S3 method for vif.rma
+
an object of class "vif.rma"
obtained with vif
.
argument to be passed on to the corresponding argument of hist
to set (the method for determining) the (number of) breakpoints.
logical to specify whether frequencies (if TRUE
) or probability densities should be plotted (the default is FALSE
).
optional character string to specify the color of the histogram bars.
optional character string to specify the color of the borders around the bars.
optional character string to specify the color of the bars that are more extreme than the observed (G)VIF value (the default is a semi-transparent shade of red).
optional character string to specify the color of the kernel density estimate of the distribution that is superimposed on top of the histogram (the default is blue).
the fraction (up to 0.5) of observations to be trimmed from the upper tail of each distribution before its histogram is plotted.
numeric value to be passed on to the corresponding argument of density
(for adjusting the bandwidth of the kernel density estimate).
numeric vector to specify the width of the vertical lines corresponding to the value of the observed (G)VIFs and of the density estimate (note: by default, the density estimate has a line width of 0 and is therefore not plotted).
optional vector of two numbers to specify the number of rows and columns for the layout of the figure.
other arguments.
predict.rma.Rd
# S3 method for rma
+ # S3 method for class 'rma'
predict(object, newmods, intercept, tau2.levels, gamma2.levels, addx=FALSE,
level, adjust=FALSE, digits, transf, targs, vcov=FALSE, ...)
-# S3 method for rma.ls
+# S3 method for class 'rma.ls'
predict(object, newmods, intercept, addx=FALSE, newscale, addz=FALSE,
level, adjust=FALSE, digits, transf, targs, vcov=FALSE, ...)
an object of class "rma"
or "rma.ls"
.
optional vector or matrix to specify the values of the moderator values for which the predicted values should be calculated. See ‘Details’.
logical to specify whether the intercept should be included when calculating the predicted values for newmods
. If unspecified, the intercept is automatically added when the original model also included an intercept.
vector to specify the levels of the inner factor when computing prediction intervals. Only relevant for models of class "rma.mv"
(see rma.mv
) and when the model includes more than a single \(\tau^2\) value. See ‘Details’.
vector to specify the levels of the inner factor when computing prediction intervals. Only relevant for models of class "rma.mv"
(see rma.mv
) and when the model includes more than a single \(\gamma^2\) value. See ‘Details’.
logical to specify whether the values of the moderator variables should be added to the returned object. See ‘Examples’.
optional vector or matrix to specify the values of the scale variables for which the predicted values should be calculated. Only relevant for location-scale models (see rma.uni
). See ‘Details’.
logical to specify whether the values of the scale variables should be added to the returned object.
numeric value between 0 and 100 to specify the confidence and prediction interval level (see here for details). If unspecified, the default is to take the value from the object.
logical to specify whether the width of confidence/prediction intervals should be adjusted using a Bonferroni correction (the default is FALSE
).
optional integer to specify the number of decimal places to which the printed results should be rounded.
optional argument to specify a function to transform the predicted values and interval bounds (e.g., transf=exp
; see also transf). If unspecified, no transformation is used.
optional arguments needed by the function specified under transf
.
logical to specify whether the variance-covariance matrix of the predicted values should also be returned (the default is FALSE
).
other arguments.
An object of class c("predict.rma","list.rma")
. The object is a list containing the following components:
An object of class c("predict.rma","list.rma")
. The object is a list containing the following components:
predicted value(s).
If vcov=TRUE
, then the returned object is a list with the first element equal to the one as described above and the second element equal to the variance-covariance matrix of the predicted values.
The object is formatted and printed with the print
function. To format the results as a data frame, one can use the as.data.frame
function.
print.anova.rma.Rd
# S3 method for anova.rma
+
an object of class "anova.rma"
or "list.anova.rma"
obtained with anova
.
integer to specify the number of decimal places to which the printed results should be rounded (the default is to take the value from the object).
other arguments.
The function does not return an object.
+The function does not return an object.
print.confint.rma.Rd
# S3 method for confint.rma
+
an object of class "confint.rma"
or "list.confint.rma"
obtained with confint
.
integer to specify the number of decimal places to which the printed results should be rounded (the default is to take the value from the object).
other arguments.
The function does not return an object.
+The function does not return an object.
print.escalc.Rd
# S3 method for escalc
+
an object of class "escalc"
obtained with escalc
.
an object of class "escalc"
obtained with escalc
.
integer to specify the number of decimal places to which the printed results should be rounded (the default is to take the value from the object).
character string with four elements to specify the variable names for the standard errors, test statistics, and lower/upper confidence interval bounds.
character string with two elements to specify the variable names for the observed effect sizes or outcomes and the sampling variances (the default is to take the value from the object if possible).
numeric value to specify the value of the effect size or outcome under the null hypothesis (the default is 0).
logical to specify whether the data frame specified via the object
argument should be returned together with the additional variables that are calculated by the summary
function (the default is TRUE
).
logical to specify whether existing values for sei
, zi
, ci.lb
, and ci.ub
in the data frame should be replaced. Only relevant when the data frame already contains these variables. If replace=TRUE
(the default), all of the existing values will be overwritten. If replace=FALSE
, only NA
values will be replaced.
numeric value between 0 and 100 to specify the confidence interval level (the default is 95; see here for details).
optional argument to specify observation/outcome limits. If unspecified, no limits are used.
optional argument to specify a function to transform the observed effect sizes or outcomes and interval bounds (e.g., transf=exp
; see also transf). If unspecified, no transformation is used. Any additional arguments needed for the function specified here can be passed via ...
.
other arguments.
The print.escalc
function formats and prints the data frame, so that the observed effect sizes or outcomes and sampling variances are rounded (to the number of digits specified).
The print.escalc
function formats and prints the data frame, so that the observed effect sizes or outcomes and sampling variances are rounded (to the number of digits specified).
The summary.escalc
function creates an object that is a data frame containing the original data (if append=TRUE
) and the following components:
observed effect sizes or outcomes (transformed if transf
is specified).
When the transf
argument is specified, elements vi
, sei
, zi
, and pval
are not included (since these only apply to the untransformed effect sizes or outcomes).
Note that the actual variable names above depend on the out.names
(and var.names
) arguments. If the data frame already contains variables with names as specified by the out.names
argument, the values for these variables will be overwritten when replace=TRUE
(which is the default). By setting replace=FALSE
, only values that are NA
will be replaced.
The print.escalc
function again formats and prints the data frame, rounding the added variables to the number of digits specified.
print.fsn.Rd
# S3 method for fsn
+ # S3 method for class 'fsn'
print(x, digits=x$digits, ...)
an object of class "fsn"
obtained with fsn
.
integer to specify the number of decimal places to which the printed results should be rounded (the default is to take the value from the object).
other arguments.
The function does not return an object.
+The function does not return an object.
print.gosh.rma.Rd
# S3 method for gosh.rma
+ # S3 method for class 'gosh.rma'
print(x, digits=x$digits, ...)
an object of class "gosh.rma"
obtained with gosh
.
integer to specify the number of decimal places to which the printed results should be rounded (the default is to take the value from the object).
other arguments.
The function does not return an object.
+The function does not return an object.
print.hc.rma.uni.Rd
# S3 method for hc.rma.uni
+ # S3 method for class 'hc.rma.uni'
print(x, digits=x$digits, ...)
an object of class "hc.rma.uni"
obtained with hc
.
integer to specify the number of decimal places to which the printed results should be rounded (the default is to take the value from the object).
other arguments.
The function returns the data frame invisibly.
+The function returns the data frame invisibly.
print.list.rma.Rd
# S3 method for list.rma
+ # S3 method for class 'list.rma'
print(x, digits=x$digits, ...)
See the documentation of the function that creates the "list.rma"
object for details on what is printed. Regardless of what is printed, a data frame with the results is also returned invisibly.
See the documentation of the function that creates the "list.rma"
object for details on what is printed. Regardless of what is printed, a data frame with the results is also returned invisibly.
See methods.list.rma
for some additional method functions for "list.rma"
objects.
print.matreg.Rd
# S3 method for matreg
+ # S3 method for class 'matreg'
print(x, digits, signif.stars=getOption("show.signif.stars"),
signif.legend=signif.stars, ...)
-# S3 method for matreg
+# S3 method for class 'matreg'
summary(object, digits, ...)
-# S3 method for summary.matreg
+# S3 method for class 'summary.matreg'
print(x, digits, signif.stars=getOption("show.signif.stars"),
signif.legend=signif.stars, ...)
an object of class "matreg"
or "summary.matreg"
(for print
).
an object of class "matreg"
(for summary
).
integer to specify the number of decimal places to which the printed results should be rounded. If unspecified, the default is to take the value from the object.
logical to specify whether p-values should be encoded visually with ‘significance stars’. Defaults to the show.signif.stars
slot of options
.
logical to specify whether the legend for the ‘significance stars’ should be printed. Defaults to the value for signif.stars
.
other arguments.
The function does not return an object.
+The function does not return an object.
print.permutest.rma.uni.Rd
# S3 method for permutest.rma.uni
+
an object of class "permutest.rma.uni"
obtained with permutest
.
integer to specify the number of decimal places to which the printed results should be rounded (the default is to take the value from the object).
logical to specify whether p-values should be encoded visually with ‘significance stars’. Defaults to the show.signif.stars
slot of options
.
logical to specify whether the legend for the ‘significance stars’ should be printed. Defaults to the value for signif.stars
.
other arguments.
The function does not return an object.
+The function does not return an object.
print.ranktest.rma.Rd
# S3 method for ranktest
+ # S3 method for class 'ranktest'
print(x, digits=x$digits, ...)
an object of class "ranktest"
obtained with ranktest
.
integer to specify the number of decimal places to which the printed results should be rounded (the default is to take the value from the object).
other arguments.
The function does not return an object.
+The function does not return an object.
print.regtest.rma.Rd
# S3 method for regtest
+ # S3 method for class 'regtest'
print(x, digits=x$digits, ret.fit=x$ret.fit, ...)
an object of class "regtest"
obtained with regtest
.
integer to specify the number of decimal places to which the printed results should be rounded (the default is to take the value from the object).
logical to specify whether the full results from the fitted model should also be returned. If unspecified, the default is to take the value from the object.
other arguments.
The function does not return an object.
+The function does not return an object.
print.rma.Rd
# S3 method for rma.uni
+ # S3 method for class 'rma.uni'
print(x, digits, showfit=FALSE, signif.stars=getOption("show.signif.stars"),
signif.legend=signif.stars, ...)
-# S3 method for rma.mh
+# S3 method for class 'rma.mh'
print(x, digits, showfit=FALSE, ...)
-# S3 method for rma.peto
+# S3 method for class 'rma.peto'
print(x, digits, showfit=FALSE, ...)
-# S3 method for rma.glmm
+# S3 method for class 'rma.glmm'
print(x, digits, showfit=FALSE, signif.stars=getOption("show.signif.stars"),
signif.legend=signif.stars, ...)
-# S3 method for rma.mv
+# S3 method for class 'rma.mv'
print(x, digits, showfit=FALSE, signif.stars=getOption("show.signif.stars"),
signif.legend=signif.stars, ...)
-# S3 method for rma
+# S3 method for class 'rma'
summary(object, digits, ...)
-# S3 method for summary.rma
+# S3 method for class 'summary.rma'
print(x, digits, showfit=TRUE, signif.stars=getOption("show.signif.stars"),
signif.legend=signif.stars, ...)
an object of class "rma.uni"
, "rma.mh"
, "rma.peto"
, "rma.glmm"
, "rma.mv"
, or "summary.rma"
(for print
).
an object of class "rma"
(for summary
).
integer to specify the number of decimal places to which the printed results should be rounded. If unspecified, the default is to take the value from the object. See also here for further details on how to control the number of digits in the output.
logical to specify whether the fit statistics and information criteria should be printed (the default is FALSE
for print
and TRUE
for summary
).
logical to specify whether p-values should be encoded visually with ‘significance stars’. Defaults to the show.signif.stars
slot of options
.
logical to specify whether the legend for the ‘significance stars’ should be printed. Defaults to the value for signif.stars
.
other arguments.
The print
functions do not return an object. The summary
function returns the object passed to it (with additional class "summary.rma"
).
The print
functions do not return an object. The summary
function returns the object passed to it (with additional class "summary.rma"
).
profile.rma.Rd
# S3 method for rma.uni
+ # S3 method for class 'rma.uni'
profile(fitted, xlim, ylim, steps=20, lltol=1e-03,
progbar=TRUE, parallel="no", ncpus=1, cl, plot=TRUE, ...)
-# S3 method for rma.mv
+# S3 method for class 'rma.mv'
profile(fitted, sigma2, tau2, rho, gamma2, phi, xlim, ylim, steps=20, lltol=1e-03,
progbar=TRUE, parallel="no", ncpus=1, cl, plot=TRUE, ...)
-# S3 method for rma.uni.selmodel
+# S3 method for class 'rma.uni.selmodel'
profile(fitted, tau2, delta, xlim, ylim, steps=20, lltol=1e-03,
progbar=TRUE, parallel="no", ncpus=1, cl, plot=TRUE, ...)
-# S3 method for rma.ls
+# S3 method for class 'rma.ls'
profile(fitted, alpha, xlim, ylim, steps=20, lltol=1e-03,
progbar=TRUE, parallel="no", ncpus=1, cl, plot=TRUE, ...)
-# S3 method for profile.rma
+# S3 method for class 'profile.rma'
print(x, ...)
-# S3 method for profile.rma
+# S3 method for class 'profile.rma'
plot(x, xlim, ylim, pch=19, xlab, ylab, main, refline=TRUE, cline=FALSE, ...)
an object of class "rma.uni"
, "rma.mv"
, "rma.uni.selmodel"
, or "rma.ls"
.
an object of class "profile.rma"
(for plot
and print
).
optional integer to specify for which \(\sigma^2\) parameter the likelihood should be profiled.
optional integer to specify for which \(\tau^2\) parameter the likelihood should be profiled.
optional integer to specify for which \(\rho\) parameter the likelihood should be profiled.
optional integer to specify for which \(\gamma^2\) parameter the likelihood should be profiled.
optional integer to specify for which \(\phi\) parameter the likelihood should be profiled.
optional integer to specify for which \(\delta\) parameter the likelihood should be profiled.
optional integer to specify for which \(\alpha\) parameter the likelihood should be profiled.
optional vector to specify the lower and upper limit of the parameter over which the profiling should be done. If unspecified, the function sets these limits automatically.
optional vector to specify the y-axis limits when plotting the profiled likelihood. If unspecified, the function sets these limits automatically.
number of points between xlim[1]
and xlim[2]
(inclusive) for which the likelihood should be evaluated (the default is 20). Can also be a numeric vector of length 2 or longer to specify for which parameter values the likelihood should be evaluated (in this case, xlim
is automatically set to range(steps)
if unspecified).
numerical tolerance used when comparing values of the profiled log-likelihood with the log-likelihood of the fitted model (the default is 1e-03).
logical to specify whether a progress bar should be shown (the default is TRUE
).
character string to specify whether parallel processing should be used (the default is "no"
). For parallel processing, set to either "snow"
or "multicore"
. See ‘Details’.
integer to specify the number of processes to use in the parallel processing.
optional cluster to use if parallel="snow"
. If unspecified, a cluster on the local machine is created for the duration of the call.
logical to specify whether the profile plot should be drawn after profiling is finished (the default is TRUE
).
plotting symbol to use. By default, a filled circle is used. See points
for other options.
logical to specify whether the value of the parameter estimate should be indicated by a dotted vertical line and its log-likelihood value by a dotted horizontal line (the default is TRUE
).
logical to specify whether a horizontal reference line should be added to the plot that indicates the log-likelihood value corresponding to the 95% profile confidence interval (the default is FALSE
). Can also be a numeric value between 0 and 100 to specify the confidence interval level.
title for the x-axis. If unspecified, the function sets an appropriate axis title.
title for the y-axis. If unspecified, the function sets an appropriate axis title.
title for the plot. If unspecified, the function sets an appropriate title.
other arguments.
An object of class "profile.rma"
. The object is a list (or list of such lists) containing the following components:
An object of class "profile.rma"
. The object is a list (or list of such lists) containing the following components:
One of the following (depending on the parameter that was actually profiled):
values of \(\sigma^2\) over which the likelihood was profiled.
qqnorm.rma.Rd
# S3 method for rma.uni
+ # S3 method for class 'rma.uni'
qqnorm(y, type="rstandard", pch=21, col, bg,
envelope=TRUE, level=y$level, bonferroni=FALSE, reps=1000, smooth=TRUE, bass=0,
label=FALSE, offset=0.3, pos=13, lty, ...)
-# S3 method for rma.mh
+# S3 method for class 'rma.mh'
qqnorm(y, type="rstandard", pch=21, col, bg, label=FALSE, offset=0.3, pos=13, ...)
-# S3 method for rma.peto
+# S3 method for class 'rma.peto'
qqnorm(y, type="rstandard", pch=21, col, bg, label=FALSE, offset=0.3, pos=13, ...)
-# S3 method for rma.glmm
+# S3 method for class 'rma.glmm'
qqnorm(y, ...)
-# S3 method for rma.mv
+# S3 method for class 'rma.mv'
qqnorm(y, ...)
an object of class "rma.uni"
, "rma.mh"
, or "rma.peto"
. The method is not yet implemented for objects of class "rma.glmm"
or "rma.mv"
.
character string (either "rstandard"
(default) or "rstudent"
) to specify whether standardized residuals or studentized deleted residuals should be used in creating the plot. See ‘Details’.
plotting symbol to use for the observed outcomes. By default, an open circle is used. See points
for other options.
optional character string to specify the (border) color of the points.
optional character string to specify the background color of open plot symbols.
logical to specify whether a pseudo confidence envelope should be simulated and added to the plot (the default is TRUE
)). Only for objects of class "rma.uni"
. See ‘Details’.
numeric value between 0 and 100 to specify the level of the pseudo confidence envelope (see here for details). The default is to take the value from the object.
logical to specify whether the bounds of the envelope should be Bonferroni corrected.
numeric value to specify the number of iterations for simulating the pseudo confidence envelope (the default is 1000).
logical to specify whether the results from the simulation should be smoothed (the default is TRUE
).
numeric value that controls the degree of smoothing (the default is 0).
argument to control the labeling of the points (the default is FALSE
). See ‘Details’.
argument to control the distance between the points and the corresponding labels.
argument to control the position of the labels.
optional character string to specify the line type for the diagonal line and the pseudo confidence envelope. If unspecified, the function sets this to c("solid", "dotted")
by default.
other arguments.
A list with components:
+A list with components:
the x-axis coordinates of the points that were plotted.
radial.Rd
radial(x, ...)
galbraith(x, ...)
-# S3 method for rma
+# S3 method for class 'rma'
radial(x, center=FALSE, xlim, zlim, xlab, zlab,
atz, aty, steps=7, level=x$level, digits=2,
transf, targs, pch=21, col, bg, back, arc.res=100,
@@ -107,70 +107,71 @@ Radial (Galbraith) Plots for 'rma' Objects
Arguments
- - x
+
+- x
an object of class "rma"
.
- - center
+ - center
logical to specify whether the plot should be centered horizontally at the model estimate (the default is FALSE
).
- - xlim
+ - xlim
x-axis limits. If unspecified, the function sets the x-axis limits to some sensible values.
- - zlim
+ - zlim
z-axis limits. If unspecified, the function sets the z-axis limits to some sensible values (note that the z-axis limits are the actual vertical limit of the plotting region).
- - xlab
+ - xlab
title for the x-axis. If unspecified, the function sets an appropriate axis title.
- - zlab
+ - zlab
title for the z-axis. If unspecified, the function sets an appropriate axis title.
- - atz
+ - atz
position for the z-axis tick marks and labels. If unspecified, these values are set by the function.
- - aty
+ - aty
position for the y-axis tick marks and labels. If unspecified, these values are set by the function.
- - steps
+ - steps
the number of tick marks for the y-axis (the default is 7). Ignored when argument aty
is used.
- - level
+ - level
numeric value between 0 and 100 to specify the level of the z-axis error region. The default is to take the value from the object.
- - digits
+ - digits
integer to specify the number of decimal places to which the tick mark labels of the y-axis should be rounded (the default is 2).
- - transf
+ - transf
argument to specify a function to transform the y-axis labels (e.g., transf=exp
; see also transf). If unspecified, no transformation is used.
- - targs
+ - targs
optional arguments needed by the function specified via transf
.
- - pch
+ - pch
plotting symbol. By default, an open circle is used. See points
for other options.
- - col
+ - col
character string to specify the (border) color of the points.
- - bg
+ - bg
character string to specify the background color of open plot symbols.
- - back
+ - back
character string to specify the background color of the z-axis error region. If unspecified, a shade of gray is used. Set to NA
to suppress shading of the region.
- - arc.res
+ - arc.res
integer to specify the number of line segments (i.e., the resolution) when drawing the y-axis and confidence interval arcs (the default is 100).
- - cex
+ - cex
symbol expansion factor.
- - cex.lab
+ - cex.lab
character expansion factor for axis labels.
- - cex.axis
+ - cex.axis
character expansion factor for axis annotations.
- - ...
+ - ...
other arguments.
@@ -186,9 +187,7 @@ Details
A data frame with components:
+A data frame with components:
the x-axis coordinates of the points that were plotted.
ranef.Rd
# S3 method for rma.uni
+ # S3 method for class 'rma.uni'
ranef(object, level, digits, transf, targs, ...)
-# S3 method for rma.mv
+# S3 method for class 'rma.mv'
ranef(object, level, digits, transf, targs, verbose=FALSE, ...)
an object of class "rma.uni"
or "rma.mv"
.
numeric value between 0 and 100 to specify the prediction interval level (see here for details). If unspecified, the default is to take the value from the object.
optional integer to specify the number of decimal places to which the printed results should be rounded. If unspecified, the default is to take the value from the object.
optional argument to specify a function to transform the predicted values and interval bounds (e.g., transf=exp
; see also transf). If unspecified, no transformation is used.
optional arguments needed by the function specified under transf
.
logical to specify whether output should be generated on the progress of the computations (the default is FALSE
).
other arguments.
For objects of class "rma.uni"
, an object of class "list.rma"
. The object is a list containing the following components:
For objects of class "rma.uni"
, an object of class "list.rma"
. The object is a list containing the following components:
predicted values.
The object is formatted and printed with the print
function. To format the results as a data frame, one can use the as.data.frame
function.
For objects of class "rma.mv"
, a list of data frames with the same components as described above.
ranktest.Rd
a vector with the observed effect sizes or outcomes or an object of class "rma"
.
vector with the corresponding sampling variances (ignored if x
is an object of class "rma"
).
vector with the corresponding standard errors (note: only one of the two, vi
or sei
, needs to be specified).
optional (logical or numeric) vector to specify the subset of studies that should be included in the test (ignored if x
is an object of class "rma"
).
optional data frame containing the variables given to the arguments above.
optional integer to specify the number of decimal places to which the printed results should be rounded.
other arguments.
An object of class "ranktest"
. The object is a list containing the following components:
An object of class "ranktest"
. The object is a list containing the following components:
the estimated value of Kendall's tau rank correlation coefficient.
rcalc.Rd
a formula of the form ri ~ var1 + var2 | study
. Can also be a correlation matrix or list thereof. See ‘Details’.
vector to specify the sample sizes based on which the correlations were computed.
data frame containing the variables specified via the formula (and the sample sizes).
logical to specify whether to transform the correlations via Fisher's r-to-z transformation (the default is FALSE
).
a character string to specify how the ‘common’ sample size within each study should be computed. Possible options are "min"
(for the minimum), "harmonic"
(for the harmonic mean), or "mean"
(for the arithmetic mean). Can also be a function. See ‘Details’.
logical to specify whether the variance-covariance matrix should be returned as a sparse matrix (the default is FALSE
).
other arguments.
A list containing the following components:
+A list containing the following components:
a data frame with the study identifier, the two variable identifiers, a variable pair identifier, the correlation coefficients (possibly transformed with Fisher's r-to-z transformation), and the (common) sample sizes.
regplot.Rd
regplot(x, ...)
-# S3 method for rma
+# S3 method for class 'rma'
regplot(x, mod, pred=TRUE, ci=TRUE, pi=FALSE, shade=TRUE,
xlim, ylim, predlim, olim, xlab, ylab, at, digits=2L,
transf, atransf, targs, level=x$level,
@@ -105,115 +105,116 @@ Scatter Plots / Bubble Plots
grid=FALSE, refline, label=FALSE, offset=c(1,1), labsize=1,
lcol, lwd, lty, legend=FALSE, xvals, ...)
-# S3 method for regplot
+# S3 method for class 'regplot'
points(x, ...)
an object of class "rma.uni"
, "rma.mv"
, or "rma.glmm"
including one or multiple moderators (or an object of class "regplot"
for points
).
either a scalar to specify the position of the moderator variable in the model or a character string to specify the name of the moderator variable.
logical to specify whether the (marginal) regression line based on the moderator should be added to the plot (the default is TRUE
). Can also be an object from predict
. See ‘Details’.
logical to specify whether the corresponding confidence interval bounds should be added to the plot (the default is TRUE
).
logical to specify whether the corresponding prediction interval bounds should be added to the plot (the default is FALSE
).
logical to specify whether the confidence/prediction interval regions should be shaded (the default is TRUE
). Can also be a two-element character vector to specify the colors for shading the confidence and prediction interval regions (if shading only the former, a single color can also be specified).
x-axis limits. If unspecified, the function sets the x-axis limits to some sensible values.
y-axis limits. If unspecified, the function sets the y-axis limits to some sensible values.
optional argument to specify the limits of the (marginal) regression line. If unspecified, the limits are based on the range of the moderator variable.
optional argument to specify observation/outcome limits. If unspecified, no limits are used.
title for the x-axis. If unspecified, the function sets an appropriate axis title.
title for the y-axis. If unspecified, the function sets an appropriate axis title.
position of the y-axis tick marks and corresponding labels. If unspecified, the function sets the tick mark positions/labels to some sensible values.
integer to specify the number of decimal places to which the tick mark labels of the y-axis should be rounded. When specifying an integer (e.g., 2L
), trailing zeros after the decimal mark are dropped for the y-axis labels. When specifying a numeric value (e.g., 2
), trailing zeros are retained.
optional argument to specify a function to transform the observed outcomes, predicted values, and confidence/prediction interval bounds (e.g., transf=exp
; see also transf). If unspecified, no transformation is used.
optional argument to specify a function to transform the y-axis labels (e.g., atransf=exp
; see also transf). If unspecified, no transformation is used.
optional arguments needed by the function specified via transf
or atransf
.
numeric value between 0 and 100 to specify the confidence/prediction interval level (see here for details). The default is to take the value from the object.
plotting symbol to use for the observed outcomes. By default, an open circle is used. Can also be a vector of values. See points
for other options.
optional numeric value to specify the point sizes for the observed outcomes. If unspecified, the point sizes are a function of the model weights. Can also be a vector of values. Can also be a character string (either "seinv"
or "vinv"
) to make the point sizes proportional to the inverse standard errors or inverse sampling variances.
numeric vector of length 2 to scale the point sizes (ignored when a numeric value or vector is specified for psize
). See ‘Details’.
character string to specify the (border) color of the points. Can also be a vector.
character string to specify the background color of open plot symbols. Can also be a vector.
optional vector with labels for the \(k\) studies. If unspecified, the function tries to extract study labels from x
.
logical to specify whether a grid should be added to the plot. Can also be a color name for the grid.
optional numeric value to specify the location of a horizontal reference line that should be added to the plot.
argument to control the labeling of the points (the default is FALSE
). See ‘Details’.
argument to control the distance between the points and the corresponding labels. See ‘Details’.
numeric value to control the size of the labels.
optional vector of (up to) four elements to specify the color of the regression line, of the confidence interval bounds, of the prediction interval bounds, and of the horizontal reference line.
optional vector of (up to) four elements to specify the line type of the regression line, of the confidence interval bounds, of the prediction interval bounds, and of the horizontal reference line.
optional vector of (up to) four elements to specify the line width of the regression line, of the confidence interval bounds, of the prediction interval bounds, and of the horizontal reference line.
logical to specify whether a legend should be added to the plot (the default is FALSE
). Can also be a keyword to specify the position of the legend (see legend
).
optional numeric vector to specify the values of the moderator for which predicted values should be computed. Needs to be specified when passing an object from predict
to the pred
argument. See ‘Details’.
other arguments.
An object of class "regplot"
with components:
An object of class "regplot"
with components:
the study labels
regtest.Rd
a vector with the observed effect sizes or outcomes or an object of class "rma"
.
vector with the corresponding sampling variances (ignored if x
is an object of class "rma"
).
vector with the corresponding standard errors (note: only one of the two, vi
or sei
, needs to be specified).
optional vector with the corresponding sample sizes (only relevant when using the sample sizes (or a transformation thereof) as predictor).
optional (logical or numeric) vector to specify the subset of studies that should be included in the test (ignored if x
is an object of class "rma"
).
optional data frame containing the variables given to the arguments above.
either "rma"
or "lm"
to specify the type of model to use for the regression test. See ‘Details’.
either "sei"
"vi"
, "ni"
, "ninv"
, "sqrtni"
, or "sqrtninv"
to specify the predictor to use for the regression test. See ‘Details’.
logical to specify whether the full results from the fitted model should also be returned.
optional integer to specify the number of decimal places to which the printed results should be rounded.
other arguments.
An object of class "regtest"
. The object is a list containing the following components:
An object of class "regtest"
. The object is a list containing the following components:
the model used for the regression test.
replmiss.Rd
Vector x
with the missing values replaced based on the scalar or vector y
.
Vector x
with the missing values replaced based on the scalar or vector y
.
reporter.Rd
reporter(x, ...)
-# S3 method for rma.uni
+# S3 method for class 'rma.uni'
reporter(x, dir, filename, format="html_document", open=TRUE,
digits, forest, funnel, footnotes=FALSE, verbose=TRUE, ...)
an object of class "rma.uni"
.
optional character string to specify the directory for creating the report. If unspecified, tempdir
will be used.
optional character string to specify the filename (without file extension) for the report. If unspecified, the function sets a filename automatically.
output format for the report (either html_document
, pdf_document
, or word_document
). Can be abbreviated. See ‘Note’.
logical to specify whether the report should be opened after it has been generated (the default is TRUE
). See ‘Note’.
optional integer to specify the number of decimal places to which the printed results should be rounded. If unspecified, the default is to take the value from the object.
either a logical which will suppress the drawing of the forest plot when set to FALSE
or a character string with arguments to be added to the call to forest
for generating the forest plot.
either a logical which will suppress the drawing of the funnel plot when set to FALSE
or a character string with arguments to be added to the call to funnel
for generating the funnel plot.
logical to specify whether additional explanatory footnotes should be added to the report (the default is FALSE
).
logical to specify whether information on the progress of the report generation should be provided (the default is TRUE
).
other arguments.
The function generates either a html, pdf, or docx file and returns (invisibly) the path to the generated document.
+The function generates either a html, pdf, or docx file and returns (invisibly) the path to the generated document.
residuals.rma.Rd
# S3 method for rma
+ # S3 method for class 'rma'
residuals(object, type="response", ...)
-# S3 method for rma.uni
+# S3 method for class 'rma.uni'
rstandard(model, digits, type="marginal", ...)
-# S3 method for rma.mh
+# S3 method for class 'rma.mh'
rstandard(model, digits, ...)
-# S3 method for rma.peto
+# S3 method for class 'rma.peto'
rstandard(model, digits, ...)
-# S3 method for rma.mv
+# S3 method for class 'rma.mv'
rstandard(model, digits, cluster, ...)
-# S3 method for rma.uni
+# S3 method for class 'rma.uni'
rstudent(model, digits, progbar=FALSE, ...)
-# S3 method for rma.mh
+# S3 method for class 'rma.mh'
rstudent(model, digits, progbar=FALSE, ...)
-# S3 method for rma.peto
+# S3 method for class 'rma.peto'
rstudent(model, digits, progbar=FALSE, ...)
-# S3 method for rma.mv
+# S3 method for class 'rma.mv'
rstudent(model, digits, progbar=FALSE, cluster,
reestimate=TRUE, parallel="no", ncpus=1, cl, ...)
an object of class "rma"
(for residuals
).
the type of residuals which should be returned. For residuals
, the alternatives are: "response"
(default), "rstandard"
, "rstudent"
, and "pearson"
. For rstandard.rma.uni
, the alternatives are: "marginal"
(default) and "conditional"
. See ‘Details’.
an object of class "rma"
(for residuals
) or an object of class "rma.uni"
, "rma.mh"
, "rma.peto"
, or "rma.mv"
(for rstandard
and rstudent
).
optional vector to specify a clustering variable to use for computing cluster-level multivariate standardized residuals (only for "rma.mv"
objects).
logical to specify whether variance/correlation components should be re-estimated after deletion of the \(i\textrm{th}\) case when computing externally standardized residuals for "rma.mv"
objects (the default is TRUE
).
character string to specify whether parallel processing should be used (the default is "no"
). For parallel processing, set to either "snow"
or "multicore"
. See ‘Note’.
integer to specify the number of processes to use in the parallel processing.
optional cluster to use if parallel="snow"
. If unspecified, a cluster on the local machine is created for the duration of the call.
optional integer to specify the number of decimal places to which the printed results should be rounded. If unspecified, the default is to take the value from the object.
logical to specify whether a progress bar should be shown (only for rstudent
) (the default is FALSE
).
other arguments.
Either a vector with the residuals of the requested type (for residuals
) or an object of class "list.rma"
, which is a list containing the following components:
Either a vector with the residuals of the requested type (for residuals
) or an object of class "list.rma"
, which is a list containing the following components:
observed residuals (for rstandard
) or deleted residuals (for rstudent
).
rma.glmm.Rd
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
optional argument to include one or more moderators in the model. A single moderator can be given as a vector of length \(k\) specifying the values of the moderator. Multiple moderators are specified by giving a matrix with \(k\) rows and as many columns as there are moderator variables. Alternatively, a model formula
can be used to specify the model. See ‘Details’.
character string to specify the outcome measure to use for the meta-analysis. Possible options are "OR"
for the (log transformed) odds ratio, "IRR"
for the (log transformed) incidence rate ratio, "PLO"
for the (logit transformed) proportion, or "IRLN"
for the (log transformed) incidence rate.
logical to specify whether an intercept should be added to the model (the default is TRUE
).
optional data frame containing the data supplied to the function.
optional vector with labels for the \(k\) studies.
optional (logical or numeric) vector to specify the subset of studies that should be used for the analysis.
non-negative number to specify the amount to add to zero cells, counts, or frequencies when calculating the observed effect sizes or outcomes of the individual studies. See below and the documentation of the escalc
function for more details.
character string to specify when the values under add
should be added (either "only0"
, "all"
, "if0all"
, or "none"
). See below and the documentation of the escalc
function for more details.
logical to specify whether studies with no cases/events (or only cases) in both groups should be dropped. See the documentation of the escalc
function for more details.
character string to specify the type of sampling variances to calculate when calculating the observed effect sizes or outcomes. See the documentation of the escalc
function for more details.
character string to specify the general model type for the analysis. Either "UM.FS"
(the default), "UM.RS"
, "CM.EL"
, or "CM.AL"
. See ‘Details’.
character string to specify whether an equal- or a random-effects model should be fitted. An equal-effects model is fitted when using method="EE"
. A random-effects model is fitted by setting method="ML"
(the default). See ‘Details’.
numeric scalar to specify how the group variable should be coded in the random effects structure for random/mixed-effects models (the default is 1/2
). See ‘Note’.
logical to specify whether the random study effects should be allowed to be correlated with the random group effects for random/mixed-effects models when model="UM.RS"
(the default is FALSE
). See ‘Note’.
character string to specify how test statistics and confidence intervals for the fixed effects should be computed. By default (test="z"
), Wald-type tests and CIs are obtained, which are based on a standard normal distribution. When test="t"
, a t-distribution is used instead. See ‘Details’ and also here for some recommended practices.
numeric value between 0 and 100 to specify the confidence interval level (the default is 95; see here for details).
optional vector of indices to specify which coefficients to include in the omnibus test of moderators. Can also be a string to grep
for. See ‘Details’.
positive integer to specify the number of points per axis for evaluating the adaptive Gauss-Hermite approximation to the log-likelihood. The default is 7. Setting this to 1 corresponds to the Laplacian approximation. See ‘Note’.
logical to specify whether output should be generated on the progress of the model fitting (the default is FALSE
). Can also be an integer. Values > 1 generate more verbose output. See ‘Note’.
optional integer to specify the number of decimal places to which the printed results should be rounded. If unspecified, the default is 4. See also here for further details on how to control the number of digits in the output.
optional list of control values for the estimation algorithms. If unspecified, default values are defined inside the function. See ‘Note’.
additional arguments.
An object of class c("rma.glmm","rma")
. The object is a list containing the following components:
An object of class c("rma.glmm","rma")
. The object is a list containing the following components:
estimated coefficients of the model.
rma.mh.Rd
vector with the \(2 \times 2\) table frequencies (upper left cell). See below and the documentation of the escalc
function for more details.
vector with the \(2 \times 2\) table frequencies (upper right cell). See below and the documentation of the escalc
function for more details.
vector with the \(2 \times 2\) table frequencies (lower left cell). See below and the documentation of the escalc
function for more details.
vector with the \(2 \times 2\) table frequencies (lower right cell). See below and the documentation of the escalc
function for more details.
vector with the group sizes or row totals (first group). See below and the documentation of the escalc
function for more details.
vector with the group sizes or row totals (second group). See below and the documentation of the escalc
function for more details.
vector with the number of events (first group). See below and the documentation of the escalc
function for more details.
vector with the number of events (second group). See below and the documentation of the escalc
function for more details.
vector with the total person-times (first group). See below and the documentation of the escalc
function for more details.
vector with the total person-times (second group). See below and the documentation of the escalc
function for more details.
character string to specify the outcome measure to use for the meta-analysis. Possible options are "RR"
for the (log transformed) risk ratio, "OR"
for the (log transformed) odds ratio, "RD"
for the risk difference, "IRR"
for the (log transformed) incidence rate ratio, or "IRD"
for the incidence rate difference.
optional data frame containing the data supplied to the function.
optional vector with labels for the \(k\) studies.
optional (logical or numeric) vector to specify the subset of studies that should be used for the analysis.
non-negative number to specify the amount to add to zero cells or even counts when calculating the observed effect sizes of the individual studies. Can also be a vector of two numbers, where the first number is used in the calculation of the observed effect sizes and the second number is used when applying the Mantel-Haenszel method. See below and the documentation of the escalc
function for more details.
character string to specify when the values under add
should be added (either "only0"
, "all"
, "if0all"
, or "none"
). Can also be a character vector, where the first string again applies when calculating the observed effect sizes or outcomes and the second string when applying the Mantel-Haenszel method. See below and the documentation of the escalc
function for more details.
logical to specify whether studies with no cases/events (or only cases) in both groups should be dropped when calculating the observed effect sizes or outcomes (the outcomes for such studies are set to NA
). Can also be a vector of two logicals, where the first applies to the calculation of the observed effect sizes or outcomes and the second when applying the Mantel-Haenszel method. See below and the documentation of the escalc
function for more details.
logical to specify whether to apply a continuity correction when computing the Cochran-Mantel-Haenszel test statistic.
numeric value between 0 and 100 to specify the confidence interval level (the default is 95; see here for details).
logical to specify whether output should be generated on the progress of the model fitting (the default is FALSE
).
optional integer to specify the number of decimal places to which the printed results should be rounded. If unspecified, the default is 4. See also here for further details on how to control the number of digits in the output.
additional arguments.
An object of class c("rma.mh","rma")
. The object is a list containing the following components:
An object of class c("rma.mh","rma")
. The object is a list containing the following components:
aggregated log risk ratio, log odds ratio, risk difference, log rate ratio, or rate difference.
rma.mv.Rd
vector of length \(k\) with the observed effect sizes or outcomes. See ‘Details’.
vector of length \(k\) with the corresponding sampling variances or a \(k \times k\) variance-covariance matrix of the sampling errors. See ‘Details’.
optional argument to specify a vector of length \(k\) with user-defined weights or a \(k \times k\) user-defined weight matrix. See ‘Details’.
optional argument to include one or more moderators in the model. A single moderator can be given as a vector of length \(k\) specifying the values of the moderator. Multiple moderators are specified by giving a matrix with \(k\) rows and as many columns as there are moderator variables. Alternatively, a model formula
can be used to specify the model. See ‘Details’.
either a single one-sided formula or list of one-sided formulas to specify the random-effects structure of the model. See ‘Details’.
character string to specify the variance structure of an ~ inner | outer
formula in the random
argument. Either "CS"
for compound symmetry, "HCS"
for heteroscedastic compound symmetry, "UN"
or "GEN"
for an unstructured variance-covariance matrix, "ID"
for a scaled identity matrix, "DIAG"
for a diagonal matrix, "AR"
for an AR(1) autoregressive structure, "HAR"
for a heteroscedastic AR(1) autoregressive structure, "CAR"
for a continuous-time autoregressive structure, or one of "SPEXP"
, "SPGAU"
, "SPLIN"
, "SPRAT"
, or "SPSPH"
for one of the spatial correlation structures. See ‘Details’.
logical to specify whether an intercept should be added to the model (the default is TRUE
). Ignored when mods
is a formula.
optional data frame containing the data supplied to the function.
optional vector with labels for the \(k\) outcomes/studies.
optional (logical or numeric) vector to specify the subset of studies (or more precisely, rows of the dataset) that should be used for the analysis.
character string to specify whether the model should be fitted via maximum likelihood ("ML"
) or via restricted maximum likelihood ("REML"
) estimation (the default is "REML"
).
character string to specify how test statistics and confidence intervals for the fixed effects should be computed. By default (test="z"
), Wald-type tests and CIs are obtained, which are based on a standard normal distribution. When test="t"
, a t-distribution is used instead. See ‘Details’ and also here for some recommended practices.
character string to specify how the (denominator) degrees of freedom should be calculated when test="t"
. Either dfs="residual"
or dfs="contain"
. Can also be a numeric vector with the degrees of freedom for each model coefficient. See ‘Details’.
numeric value between 0 and 100 to specify the confidence interval level (the default is 95; see here for details).
optional vector of indices to specify which coefficients to include in the omnibus test of moderators. Can also be a string to grep
for. See ‘Details’.
an optional named list of known correlation matrices corresponding to (some of) the components specified via the random
argument. See ‘Details’.
character string, integer, or logical to specify how matrices specified via the R
argument should be scaled. See ‘Details’.
optional numeric vector (of the same length as the number of random intercept components specified via the random
argument) to fix the corresponding \(\sigma^2\) value(s). A specific \(\sigma^2\) value can be fixed by setting the corresponding element of this argument to the desired value. A specific \(\sigma^2\) value will be estimated if the corresponding element is set equal to NA
. See ‘Details’.
optional numeric value (for struct="CS"
, "AR"
, "CAR"
, or a spatial correlation structure) or vector (for struct="HCS"
, "UN"
, or "HAR"
) to fix the amount of (residual) heterogeneity for the levels of the inner
factor corresponding to an ~ inner | outer
formula specified in the random
argument. A numeric value fixes a particular \(\tau^2\) value, while NA
means that the value should be estimated. See ‘Details’.
optional numeric value (for struct="CS"
, "HCS"
, "AR"
, "HAR"
, "CAR"
, or a spatial correlation structure) or vector (for struct="UN"
) to fix the correlation between the levels of the inner
factor corresponding to an ~ inner | outer
formula specified in the random
argument. A numeric value fixes a particular \(\rho\) value, while NA
means that the value should be estimated. See ‘Details’.
as tau2
argument, but for a second ~ inner | outer
formula specified in the random
argument. See ‘Details’.
as rho
argument, but for a second ~ inner | outer
formula specified in the random
argument. See ‘Details’.
logical to specify whether to calculate the variance-covariance matrix of the variance/correlation component estimates (can also be set to "varcov"
or "varcor"
). See ‘Details’.
logical to specify whether the function should use sparse matrix objects to the extent possible (can speed up model fitting substantially for certain models). See ‘Note’.
logical to specify whether output should be generated on the progress of the model fitting (the default is FALSE
). Can also be an integer. Values > 1 generate more verbose output. See ‘Note’.
optional integer to specify the number of decimal places to which the printed results should be rounded. If unspecified, the default is 4. See also here for further details on how to control the number of digits in the output.
optional list of control values for the estimation algorithms. If unspecified, default values are defined inside the function. See ‘Note’.
additional arguments.
An object of class c("rma.mv","rma")
. The object is a list containing the following components:
An object of class c("rma.mv","rma")
. The object is a list containing the following components:
estimated coefficients of the model.
rma.peto.Rd
vector with the \(2 \times 2\) table frequencies (upper left cell). See below and the documentation of the escalc
function for more details.
vector with the \(2 \times 2\) table frequencies (upper right cell). See below and the documentation of the escalc
function for more details.
vector with the \(2 \times 2\) table frequencies (lower left cell). See below and the documentation of the escalc
function for more details.
vector with the \(2 \times 2\) table frequencies (lower right cell). See below and the documentation of the escalc
function for more details.
vector with the group sizes or row totals (first group). See below and the documentation of the escalc
function for more details.
vector with the group sizes or row totals (second group). See below and the documentation of the escalc
function for more details.
optional data frame containing the data supplied to the function.
optional vector with labels for the \(k\) studies.
optional (logical or numeric) vector to specify the subset of studies that should be used for the analysis.
non-negative number to specify the amount to add to zero cells when calculating the observed effect sizes of the individual studies. Can also be a vector of two numbers, where the first number is used in the calculation of the observed effect sizes and the second number is used when applying Peto's method. See below and the documentation of the escalc
function for more details.
character string to specify when the values under add
should be added (either "only0"
, "all"
, "if0all"
, or "none"
). Can also be a character vector, where the first string again applies when calculating the observed effect sizes or outcomes and the second string when applying Peto's method. See below and the documentation of the escalc
function for more details.
logical to specify whether studies with no cases (or only cases) in both groups should be dropped when calculating the observed effect sizes or outcomes (the outcomes for such studies are set to NA
). Can also be a vector of two logicals, where the first applies to the calculation of the observed effect sizes or outcomes and the second when applying Peto's method. See below and the documentation of the escalc
function for more details.
numeric value between 0 and 100 to specify the confidence interval level (the default is 95; see here for details).
logical to specify whether output should be generated on the progress of the model fitting (the default is FALSE
).
optional integer to specify the number of decimal places to which the printed results should be rounded. If unspecified, the default is 4. See also here for further details on how to control the number of digits in the output.
additional arguments.
An object of class c("rma.peto","rma")
. The object is a list containing the following components:
An object of class c("rma.peto","rma")
. The object is a list containing the following components:
aggregated log odds ratio.
rma.uni.Rd
vector of length \(k\) with the observed effect sizes or outcomes. See ‘Details’.
vector of length \(k\) with the corresponding sampling variances. See ‘Details’.
vector of length \(k\) with the corresponding standard errors (only relevant when not using vi
). See ‘Details’.
optional argument to specify a vector of length \(k\) with user-defined weights. See ‘Details’.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
see below and the documentation of the escalc
function for more details.
optional argument to include one or more moderators in the model. A single moderator can be given as a vector of length \(k\) specifying the values of the moderator. Multiple moderators are specified by giving a matrix with \(k\) rows and as many columns as there are moderator variables. Alternatively, a model formula
can be used to specify the model. See ‘Details’.
optional argument to include one or more predictors for the scale part in a location-scale model. See ‘Details’.
character string to specify the type of data supplied to the function. When measure="GEN"
(default), the observed effect sizes or outcomes and corresponding sampling variances should be supplied to the function via the yi
and vi
arguments, respectively (instead of the sampling variances, one can supply the standard errors via the sei
argument). Alternatively, one can set measure
to one of the effect sizes or outcome measures described under the documentation for the escalc
function in which case one must specify the required data via the appropriate arguments (see escalc
).
logical to specify whether an intercept should be added to the model (the default is TRUE
). Ignored when mods
is a formula.
optional data frame containing the data supplied to the function.
optional vector with labels for the \(k\) studies.
optional (logical or numeric) vector to specify the subset of studies that should be used for the analysis.
see the documentation of the escalc
function.
see the documentation of the escalc
function.
see the documentation of the escalc
function.
see the documentation of the escalc
function.
character string to specify whether an equal- or a random-effects model should be fitted. An equal-effects model is fitted when using method="EE"
. A random-effects model is fitted by setting method
equal to one of the following: "DL"
, "HE"
, "HS"
, "HSk"
, "SJ"
, "ML"
, "REML"
, "EB"
, "PM"
, "GENQ"
, "PMM"
, or "GENQM"
. The default is "REML"
. See ‘Details’.
logical to specify whether weighted (default) or unweighted estimation should be used to fit the model (the default is TRUE
).
character string to specify how test statistics and confidence intervals for the fixed effects should be computed. By default (test="z"
), Wald-type tests and CIs are obtained, which are based on a standard normal distribution. When test="t"
, a t-distribution is used instead. When test="knha"
, the method by Knapp and Hartung (2003) is used. See ‘Details’ and also here for some recommended practices.
numeric value between 0 and 100 to specify the confidence interval level (the default is 95; see here for details).
optional vector of indices to specify which coefficients to include in the omnibus test of moderators. Can also be a string to grep
for. See ‘Details’.
optional vector of indices to specify which scale coefficients to include in the omnibus test. Only relevant for location-scale models. See ‘Details’.
optional numeric value to specify the amount of (residual) heterogeneity in a random- or mixed-effects model (instead of estimating it). Useful for sensitivity analyses (e.g., for plotting results as a function of \(\tau^2\)). If unspecified, the value of \(\tau^2\) is estimated from the data.
logical to specify whether output should be generated on the progress of the model fitting (the default is FALSE
). Can also be an integer. Values > 1 generate more verbose output. See ‘Note’.
optional integer to specify the number of decimal places to which the printed results should be rounded. If unspecified, the default is 4. See also here for further details on how to control the number of digits in the output.
optional list of control values for the iterative estimation algorithms. If unspecified, default values are defined inside the function. See ‘Note’.
additional arguments.
An object of class c("rma.uni","rma")
. The object is a list containing the following components:
An object of class c("rma.uni","rma")
. The object is a list containing the following components:
estimated coefficients of the model.
robust.Rd
robust(x, cluster, ...)
-# S3 method for rma.uni
+# S3 method for class 'rma.uni'
robust(x, cluster, adjust=TRUE, clubSandwich=FALSE, digits, ...)
-# S3 method for rma.mv
+# S3 method for class 'rma.mv'
robust(x, cluster, adjust=TRUE, clubSandwich=FALSE, digits, ...)
an object of class "rma.uni"
or "rma.mv"
.
vector to specify the clustering variable to use for constructing the sandwich estimator of the variance-covariance matrix.
logical to specify whether a small-sample correction should be applied to the variance-covariance matrix.
logical to specify whether the clubSandwich package should be used to obtain the cluster-robust tests and confidence intervals.
optional integer to specify the number of decimal places to which the printed results should be rounded. If unspecified, the default is to take the value from the object.
other arguments.
An object of class "robust.rma"
. The object is a list containing the following components:
An object of class "robust.rma"
. The object is a list containing the following components:
estimated coefficients of the model.
The results are formatted and printed with the print.rma.uni
and print.rma.mv
functions (depending on the type of model).
Predicted/fitted values based on "robust.rma"
objects can be obtained with the predict
function. Tests for sets of model coefficients or linear combinations thereof can be obtained with the anova
function.
se.Rd
se(object, ...)
-# S3 method for default
+# Default S3 method
se(object, ...)
-# S3 method for rma
+# S3 method for class 'rma'
se(object, ...)
A vector with the standard errors.
+A vector with the standard errors.
selmodel.Rd
selmodel(x, ...)
-# S3 method for rma.uni
+# S3 method for class 'rma.uni'
selmodel(x, type, alternative="greater", prec, subset, delta,
steps, decreasing=FALSE, verbose=FALSE, digits, control, ...)
an object of class "rma.uni"
.
character string to specify the type of selection model. Possible options are "beta"
, "halfnorm"
, "negexp"
, "logistic"
, "power"
, "negexppow"
, "stepfun"
, "trunc"
, and "truncest"
. Can be abbreviated.
character string to specify the sidedness of the hypothesis when testing the observed outcomes. Possible options are "greater"
(the default), "less"
, or "two.sided"
. Can be abbreviated.
optional character string to specify the measure of precision (only relevant for selection models that can incorporate this into the selection function). Possible options are "sei"
, "vi"
, "ninv"
, or "sqrtninv"
.
optional (logical or numeric) vector to specify the subset of studies to which the selection function applies.
optional numeric vector (of the same length as the number of selection model parameters) to fix the corresponding \(\delta\) value(s). A \(\delta\) value can be fixed by setting the corresponding element of this argument to the desired value. A \(\delta\) value will be estimated if the corresponding element is set equal to NA
.
numeric vector of one or more values that can or must be specified for certain selection functions.
logical to specify whether the \(\delta\) values in a step function selection model must be a monotonically decreasing function of the p-values (the default is FALSE
). Only relevant when type="stepfun"
.
logical to specify whether output should be generated on the progress of the model fitting (the default is FALSE
). Can also be an integer. Values > 1 generate more verbose output. See ‘Note’.
optional integer to specify the number of decimal places to which the printed results should be rounded. If unspecified, the default is to take the value from the object.
optional list of control values for the estimation algorithm. See ‘Note’.
other arguments.
An object of class c("rma.uni","rma")
. The object is a list containing the same components as a regular c("rma.uni","rma")
object, but the parameter estimates are based on the selection model. Most importantly, the following elements are modified based on the selection model:
An object of class c("rma.uni","rma")
. The object is a list containing the same components as a regular c("rma.uni","rma")
object, but the parameter estimates are based on the selection model. Most importantly, the following elements are modified based on the selection model:
estimated coefficients of the model.
simulate.rma.Rd
# S3 method for rma
+ # S3 method for class 'rma'
simulate(object, nsim=1, seed=NULL, olim, ...)
an object of class "rma"
.
number of response vectors to simulate (defaults to 1).
an object to specify if and how the random number generator should be initialized (‘seeded’). Either NULL
or an integer that will be used in a call to set.seed
before simulating the response vectors. If set, the value is saved as the "seed"
attribute of the returned value. The default, NULL
will not change the random generator state, and return .Random.seed
as the "seed"
attribute; see ‘Value’.
optional argument to specify observation/outcome limits for the simulated values. If unspecified, no limits are used.
other arguments.
A data frame with nsim
columns with the simulated effect sizes or outcomes.
A data frame with nsim
columns with the simulated effect sizes or outcomes.
The data frame comes with an attribute "seed"
. If argument seed
is NULL
, the attribute is the value of .Random.seed
before the simulation was started; otherwise it is the value of the seed
argument with a "kind"
attribute with value as.list(RNGkind())
.
tes.Rd
tes(x, vi, sei, subset, data, H0=0, alternative="two.sided", alpha=.05, theta, tau2,
test, tes.alternative="greater", progbar=TRUE, tes.alpha=.10, digits, ...)
-# S3 method for tes
+# S3 method for class 'tes'
print(x, digits=x$digits, ...)
These arguments pertain to data input:
-These arguments pertain to data input:
+ +a vector with the observed effect sizes or outcomes or an object of class "rma"
.
vector with the corresponding sampling variances (ignored if x
is an object of class "rma"
).
vector with the corresponding standard errors (note: only one of the two, vi
or sei
, needs to be specified).
optional (logical or numeric) vector to specify the subset of studies that should be included (ignored if x
is an object of class "rma"
).
optional data frame containing the variables given to the arguments above.
These arguments pertain to the tests of the observed effect sizes or outcomes:
-numeric value to specify the value of the effect size or outcome under the null hypothesis (the default is 0).
character string to specify the sidedness of the hypothesis when testing the observed effect sizes or outcomes. Possible options are "two.sided"
(the default), "greater"
, or "less"
. Can be abbreviated.
alpha level for testing the observed effect sizes or outcomes (the default is .05).
These arguments pertain to the power of the tests:
-optional numeric value to specify the value of the true effect size or outcome under the alternative hypothesis. If unspecified, it will be estimated based on the data or the value is taken from the "rma"
object.
optional numeric value to specify the amount of heterogeneity in the true effect sizes or outcomes. If unspecified, the true effect sizes or outcomes are assumed to be homogeneous or the value is taken from the "rma"
object.
These arguments pertain to the test of excess significance:
-optional character string to specify the type of test to use for conducting the test of excess significance. Possible options are "chi2"
, "binom"
, or "exact"
. Can be abbreviated. If unspecified, the function chooses the type of test based on the data.
character string to specify the sidedness of the hypothesis for the test of excess significance. Possible options are "greater"
(the default), "two.sided"
, or "less"
. Can be abbreviated.
logical to specify whether a progress bar should be shown (the default is TRUE
). Only relevant when conducting an exact test.
alpha level for the test of excess significance (the default is .10). Only relevant for finding the ‘limit estimate’.
Miscellaneous arguments:
-An object of class "tes"
. The object is a list containing the following components:
An object of class "tes"
. The object is a list containing the following components:
the number of studies included in the analysis.
to.long.Rd
a character string to specify the effect size or outcome measure corresponding to the summary data supplied. See ‘Details’ and the documentation of the escalc
function for possible options.
vector with the \(2 \times 2\) table frequencies (upper left cell).
vector with the \(2 \times 2\) table frequencies (upper right cell).
vector with the \(2 \times 2\) table frequencies (lower left cell).
vector with the \(2 \times 2\) table frequencies (lower right cell).
vector with the group sizes or row totals (first group/row).
vector with the group sizes or row totals (second group/row).
vector with the number of events (first group).
vector with the number of events (second group).
vector with the total person-times (first group).
vector with the total person-times (second group).
vector with the means (first group or time point).
vector with the means (second group or time point).
vector with the standard deviations (first group or time point).
vector with the standard deviations (second group or time point).
vector with the frequencies of the event of interest.
vector with the frequencies of the complement of the event of interest or the group means.
vector with the raw correlation coefficients.
vector with the total person-times.
vector with the standard deviations.
vector with the sample/group sizes.
optional data frame containing the variables given to the arguments above.
optional vector with labels for the studies.
optional (logical or numeric) vector to specify the subset of studies that should included in the data frame returned by the function.
see the documentation of the escalc
function.
see the documentation of the escalc
function.
see the documentation of the escalc
function.
optional logical whether a very long format should be used (only relevant for \(2 \times 2\) or \(1 \times 2\) table data).
logical to specify whether the data frame specified via the data
argument (if one has been specified) should be returned together with the long format data (the default is TRUE
). Can also be a character or numeric vector to specify which variables from data
to append.
optional character vector with variable names (the length depends on the data type). If unspecified, the function sets appropriate variable names by default.
A data frame with either \(k\), \(2 \times k\), or \(4 \times k\) rows and an appropriate number of columns (depending on the data type) with the data in long format. If append=TRUE
and a data frame was specified via the data
argument, then the data in long format are appended to the original data frame (with rows repeated an appropriate number of times).
A data frame with either \(k\), \(2 \times k\), or \(4 \times k\) rows and an appropriate number of columns (depending on the data type) with the data in long format. If append=TRUE
and a data frame was specified via the data
argument, then the data in long format are appended to the original data frame (with rows repeated an appropriate number of times).
to.table.Rd
a character string to specify the effect size or outcome measure corresponding to the summary data supplied. See ‘Details’ and the documentation of the escalc
function for possible options.
vector with the \(2 \times 2\) table frequencies (upper left cell).
vector with the \(2 \times 2\) table frequencies (upper right cell).
vector with the \(2 \times 2\) table frequencies (lower left cell).
vector with the \(2 \times 2\) table frequencies (lower right cell).
vector with the group sizes or row totals (first group/row).
vector with the group sizes or row totals (second group/row).
vector with the number of events (first group).
vector with the number of events (second group).
vector with the total person-times (first group).
vector with the total person-times (second group).
vector with the means (first group or time point).
vector with the means (second group or time point).
vector with the standard deviations (first group or time point).
vector with the standard deviations (second group or time point).
vector with the frequencies of the event of interest.
vector with the frequencies of the complement of the event of interest or the group means.
vector with the raw correlation coefficients.
vector with the total person-times.
vector with the standard deviations.
vector with the sample/group sizes.
optional data frame containing the variables given to the arguments above.
optional vector with labels for the studies.
optional (logical or numeric) vector to specify the subset of studies that should be included in the array returned by the function.
see the documentation of the escalc
function.
see the documentation of the escalc
function.
see the documentation of the escalc
function.
optional vector with row/group names.
optional vector with column/outcome names.
An array with \(k\) elements each consisting of either 1 or 2 rows and an appropriate number of columns.
+An array with \(k\) elements each consisting of either 1 or 2 rows and an appropriate number of columns.
to.wide.Rd
a data frame in long format.
either the name (given as a character string) or the position (given as a single number) of the study variable in the data frame.
either the name (given as a character string) or the position (given as a single number) of the group variable in the data frame.
optional character string to specify the reference group (must be one of the groups in the group variable). If not given, the most frequently occurring group is used as the reference group.
either the names (given as a character vector) or the positions (given as a numeric vector) of the group-level variables.
a character string of length 2 giving the affix that is placed after the names of the group-level variables for the first and second group.
logical to specify whether a row id variable should be added to the data frame (the default is TRUE
).
logical to specify whether a comparison id variable should be added to the data frame (the default is TRUE
).
logical to specify whether a design id variable should be added to the data frame (the default is TRUE
).
integer to specify the minimum length of the shortened group names for the comparison and design id variables (the default is 2).
character vector with three elements to specify the name of the id, comparison, and design variables (the defaults are "id"
, "comp"
, and "design"
, respectively).
A data frame with rows contrasting groups against a reference group and an appropriate number of columns (depending on the number of group-level outcome variables).
+A data frame with rows contrasting groups against a reference group and an appropriate number of columns (depending on the number of group-level outcome variables).
transf.Rd
vector of values to be transformed.
vector of sample sizes.
vector of sample sizes for the first group.
vector of sample sizes for the second group.
vector of person-times at risk.
control group risk (either a single value or a vector).
proportion of individuals falling into the first of the two groups that is created by the dichotomization.
list with additional arguments for the transformation function. See ‘Details’.
A vector with the transformed values.
+A vector with the transformed values.
trimfill.Rd
trimfill(x, ...)
-# S3 method for rma.uni
+# S3 method for class 'rma.uni'
trimfill(x, side, estimator="L0", maxiter=100, verbose=FALSE, ilim, ...)
an object of class "rma.uni"
.
optional character string (either "left"
or "right"
) to specify on which side of the funnel plot the missing studies should be imputed. If left unspecified, the side is chosen within the function depending on the results of the regression test (see regtest
for details on this test).
character string (either "L0"
, "R0"
, or "Q0"
) to specify the estimator for the number of missing studies (the default is "L0"
).
integer to specify the maximum number of iterations for the trim and fill method (the default is 100
).
logical to specify whether output should be generated on the progress of the iterative algorithm used as part of the trim and fill method (the default is FALSE
).
limits for the imputed values. If unspecified, no limits are used.
other arguments.
An object of class c("rma.uni.trimfill","rma.uni","rma")
. The object is a list containing the same components as objects created by rma.uni
, except that the data are augmented by the trim and fill method. The following components are also added:
An object of class c("rma.uni.trimfill","rma.uni","rma")
. The object is a list containing the same components as objects created by rma.uni
, except that the data are augmented by the trim and fill method. The following components are also added:
estimated number of missing studies.
update.rma.Rd
# S3 method for rma
+ # S3 method for class 'rma'
update(object, formula., ..., evaluate=TRUE)
If evaluate=TRUE
the fitted object, otherwise the updated call.
If evaluate=TRUE
the fitted object, otherwise the updated call.
vcalc.Rd
numeric vector to specify the sampling variances of the observed effect sizes or outcomes.
vector to specify the clustering variable (e.g., study).
optional vector to specify different (independent) subgroups within clusters.
optional vector to distinguish different observed effect sizes or outcomes corresponding to the same construct or response/dependent variable.
optional vector to distinguish different types of constructs or response/dependent variables underlying the observed effect sizes or outcomes.
optional numeric vector to specify the time points when the observed effect sizes or outcomes were obtained (in the first condition if the observed effect sizes or outcomes represent contrasts between two conditions).
optional numeric vector to specify the time points when the observed effect sizes or outcomes were obtained in the second condition (only relevant when the observed effect sizes or outcomes represent contrasts between two conditions).
optional vector to specify the group of the first condition when the observed effect sizes or outcomes represent contrasts between two conditions.
optional vector to specify the group of the second condition when the observed effect sizes or outcomes represent contrasts between two conditions.
optional numeric vector to specify the size of the group (or more generally, the inverse-sampling variance weight) of the first condition when the observed effect sizes or outcomes represent contrasts between two conditions.
optional numeric vector to specify the size of the group (or more generally, the inverse-sampling variance weight) of the second condition when the observed effect sizes or outcomes represent contrasts between two conditions.
optional data frame containing the variables given to the arguments above.
argument to specify the correlation(s) of observed effect sizes or outcomes measured concurrently. See ‘Details’.
argument to specify the autocorrelation of observed effect sizes or outcomes measured at different time points. See ‘Details’.
optional argument for specifying the variables that correspond to the correlation matrices of the studies (if this is specified, all arguments above except for cluster
and subgroup
are ignored). See ‘Details’.
logical to specify whether to check that the variance-covariance matrices within clusters are positive definite (the default is TRUE
). See ‘Note’.
logical to specify whether the nearPD
function from the Matrix package should be used on variance-covariance matrices that are not positive definite. See ‘Note’.
logical to specify whether the variance-covariance matrix should be returned as a sparse matrix (the default is FALSE
).
other arguments.
rvars
Argument
A \(k \times k\) variance-covariance matrix (given as a sparse matrix when sparse=TRUE
), where \(k\) denotes the length of the vi
variable (i.e., the number of rows in the dataset).
A \(k \times k\) variance-covariance matrix (given as a sparse matrix when sparse=TRUE
), where \(k\) denotes the length of the vi
variable (i.e., the number of rows in the dataset).
vcov.rma.Rd
# S3 method for rma
+ # S3 method for class 'rma'
vcov(object, type="fixed", ...)
an object of class "rma"
.
character string to specify the type of variance-covariance matrix to return: type="fixed"
returns the variance-covariance matrix of the fixed effects (the default), type="obs"
returns the marginal variance-covariance matrix of the observed effect sizes or outcomes, type="fitted"
returns the variance-covariance matrix of the fitted values, type="resid"
returns the variance-covariance matrix of the residuals.
other arguments.
A matrix corresponding to the requested variance-covariance matrix.
+A matrix corresponding to the requested variance-covariance matrix.
vec2mat.Rd
a vector of the correct length.
logical to specify whether the vector also contains the diagonal values of the lower triangular part of the matrix (the default is FALSE
).
logical to specify whether the diagonal of the matrix should be replaced with 1's (the default is to do this when diag=FALSE
).
optional vector of the correct length with the dimension names of the matrix.
A matrix.
+A matrix.
vif.Rd
vif(x, ...)
-# S3 method for rma
+# S3 method for class 'rma'
vif(x, btt, att, table=FALSE, reestimate=FALSE, sim=FALSE, progbar=TRUE,
seed=NULL, parallel="no", ncpus=1, cl, digits, ...)
-# S3 method for vif.rma
+# S3 method for class 'vif.rma'
print(x, digits=x$digits, ...)
an object of class "rma"
(for vif
) or "vif.rma"
(for print
).
optional vector of indices (or list thereof) to specify a set of coefficients for which a generalized variance inflation factor (GVIF) should be computed. Can also be a string to grep
for.
optional vector of indices (or list thereof) to specify a set of scale coefficients for which a generalized variance inflation factor (GVIF) should be computed. Can also be a string to grep
for. Only relevant for location-scale models (see rma.uni
).
logical to specify whether the VIFs should be added to the model coefficient table (the default is FALSE
). Only relevant when btt
(or att
) is not specified.
logical to specify whether the model should be reestimated when removing moderator variables from the model for computing a (G)VIF (the default is FALSE
).
logical to specify whether the distribution of each (G)VIF under independence should be simulated (the default is FALSE
). Can also be an integer to specify how many values to simulate (when sim=TRUE
, the default is 1000
).
logical to specify whether a progress bar should be shown when sim=TRUE
(the default is TRUE
).
optional value to specify the seed of the random number generator when sim=TRUE
(for reproducibility).
character string to specify whether parallel processing should be used (the default is "no"
). For parallel processing, set to either "snow"
or "multicore"
. See ‘Note’.
integer to specify the number of processes to use in the parallel processing.
optional cluster to use if parallel="snow"
. If unspecified, a cluster on the local machine is created for the duration of the call.
optional integer to specify the number of decimal places to which the printed results should be rounded. If unspecified, the default is to take the value from the object.
other arguments.
An object of class "vif.rma"
. The object is a list containing the following components:
An object of class "vif.rma"
. The object is a list containing the following components:
a list of data frames with the (G)VIFs and (G)SIFs and some additional information.
When x
was a location-scale model object and (G)VIFs can be computed for both the location and the scale coefficients, then the object is a list with elements beta
and alpha
, where each element is an "vif.rma"
object as described above.
The results are formatted and printed with the print
function. To format the results as a data frame, one can use the as.data.frame
function. When sim=TRUE
, the distribution of each (G)VIF can be plotted with the plot
function.
weights.rma.Rd
# S3 method for rma.uni
+ # S3 method for class 'rma.uni'
weights(object, type="diagonal", ...)
-# S3 method for rma.mh
+# S3 method for class 'rma.mh'
weights(object, type="diagonal", ...)
-# S3 method for rma.peto
+# S3 method for class 'rma.peto'
weights(object, type="diagonal", ...)
-# S3 method for rma.glmm
+# S3 method for class 'rma.glmm'
weights(object, ...)
-# S3 method for rma.mv
+# S3 method for class 'rma.mv'
weights(object, type="diagonal", ...)
an object of class "rma.uni"
, "rma.mh"
, "rma.peto"
, or "rma.mv"
. The method is not yet implemented for objects of class "rma.glmm"
.
character string to specify whether to return only the diagonal of the weight matrix ("diagonal"
) or the entire weight matrix ("matrix"
). For "rma.mv"
, this can also be "rowsum"
for ‘row-sum weights’ (for intercept-only models).
other arguments.
Either a vector with the diagonal elements of the weight matrix or the entire weight matrix. When only the diagonal elements are returned, they are given in % (and they add up to 100%).
- - +Either a vector with the diagonal elements of the weight matrix or the entire weight matrix. When only the diagonal elements are returned, they are given in % (and they add up to 100%).
When the entire weight matrix is requested, this is always a diagonal matrix for objects of class "rma.uni"
, "rma.mh"
, "rma.peto"
.
For "rma.mv"
, the structure of the weight matrix depends on the model fitted (i.e., the random effects included and the variance-covariance matrix of the sampling errors) but is often more complex and not just diagonal.
For intercept-only "rma.mv"
models, one can also take the sum over the rows in the weight matrix, which are actually the weights assigned to the observed effect sizes or outcomes when estimating the model intercept. These weights can be obtained with type="rowsum"
(as with type="diagonal"
, they are also given in %). See here for a discussion of this.