Skip to content

Commit

Permalink
Added 'ilab.lab' argument to the various forest() functions.
Browse files Browse the repository at this point in the history
  • Loading branch information
wviechtb committed Jun 7, 2024
1 parent c805881 commit feacbe6
Show file tree
Hide file tree
Showing 131 changed files with 268 additions and 256 deletions.
4 changes: 2 additions & 2 deletions DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Package: metafor
Version: 4.7-13
Date: 2024-05-31
Version: 4.7-14
Date: 2024-06-07
Title: Meta-Analysis Package for R
Authors@R: person(given = "Wolfgang", family = "Viechtbauer", role = c("aut","cre"), email = "[email protected]", comment = c(ORCID = "0000-0003-3463-4063"))
Depends: R (>= 4.0.0), methods, Matrix, metadat, numDeriv
Expand Down
4 changes: 3 additions & 1 deletion NEWS.md
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
# metafor 4.7-13 (2024-05-31)
# metafor 4.7-14 (2024-06-07)

- `rma.mv()` now counts the number of levels of a random effect more appropriately; this may trigger more often the check whether the number of levels is equal to 1, in which case the corresponding variance component is automatically fixed to 0; this check can be omitted with `control=list(check.k.gtr.1=FALSE)`

Expand All @@ -10,6 +10,8 @@

- added `lim`, `ci`, `pi`, `legend`, and `flip` arguments to `labbe()`

- added `ilab.lab` argument to the various `forest()` functions

- `fsn(..., type="General")` now computes the final estimates after rounding the fail-safe N value (not before)

- added more tests
Expand Down
23 changes: 15 additions & 8 deletions R/forest.cumul.rma.r
Original file line number Diff line number Diff line change
@@ -1,9 +1,9 @@
forest.cumul.rma <- function(x,
annotate=TRUE, header=FALSE,
xlim, alim, olim, ylim, at, steps=5, level=x$level, refline=0, digits=2L, width,
xlab, ilab, ilab.xpos, ilab.pos,
xlab, ilab, ilab.lab, ilab.xpos, ilab.pos,
transf, atransf, targs, rows,
efac=1, pch, psize, col, shade, colshade,
efac=1, pch, psize, col, shade, colshade,
lty, fonts, cex, cex.lab, cex.axis, ...) {

#########################################################################
Expand Down Expand Up @@ -47,6 +47,9 @@ lty, fonts, cex, cex.lab, cex.axis, ...) {
ilab <- .getx("ilab", mf=mf, data=x$data)
}

if (missing(ilab.lab))
ilab.lab <- NULL

if (missing(ilab.xpos))
ilab.xpos <- NULL

Expand Down Expand Up @@ -706,13 +709,17 @@ lty, fonts, cex, cex.lab, cex.axis, ...) {
if (ncol.ilab >= 4L)
ilab.xpos <- seq(xlim[1] + dist*0.5, xlim[1] + dist*0.9, length.out=ncol.ilab)
}
if (length(ilab.xpos) != ncol(ilab))
stop(mstyle$stop(paste0("Number of 'ilab' columns (", ncol(ilab), ") does not match length of 'ilab.xpos' argument (", length(ilab.xpos), ").")))
if (length(ilab.xpos) != ncol.ilab)
stop(mstyle$stop(paste0("Number of 'ilab' columns (", ncol.ilab, ") does not match length of 'ilab.xpos' argument (", length(ilab.xpos), ").")))
if (!is.null(ilab.pos) && length(ilab.pos) == 1L)
ilab.pos <- rep(ilab.pos, ncol(ilab))
ilab.pos <- rep(ilab.pos, ncol.ilab)
if (!is.null(ilab.lab) && length(ilab.lab) != ncol.ilab)
stop(mstyle$stop(paste0("Number of 'ilab' columns (", ncol.ilab, ") does not match length of 'ilab.lab' argument (", length(ilab.lab), ").")))
par(family=names(fonts)[3], font=fonts[3])
for (l in seq_len(ncol(ilab))) {
for (l in seq_len(ncol.ilab)) {
ltext(ilab.xpos[l], rows+rowadj[3], ilab[,l], pos=ilab.pos[l], cex=cex, ...)
if (!is.null(ilab.lab))
ltext(ilab.xpos[l], ylim[2]-(top-1)+1+rowadj[3], ilab.lab[l], pos=ilab.pos[l], font=2, cex=cex, ...)
}
par(family=names(fonts)[1], font=fonts[1])
}
Expand Down Expand Up @@ -785,8 +792,8 @@ lty, fonts, cex, cex.lab, cex.axis, ...) {

### add header

ltext(textpos[1], ylim[2]-(top-1)+1, header.left, pos=4, font=2, cex=cex, ...)
ltext(textpos[2], ylim[2]-(top-1)+1, header.right, pos=2, font=2, cex=cex, ...)
ltext(textpos[1], ylim[2]-(top-1)+1+rowadj[1], header.left, pos=4, font=2, cex=cex, ...)
ltext(textpos[2], ylim[2]-(top-1)+1+rowadj[2], header.right, pos=2, font=2, cex=cex, ...)

#########################################################################

Expand Down
21 changes: 14 additions & 7 deletions R/forest.default.r
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
forest.default <- function(x, vi, sei, ci.lb, ci.ub,
annotate=TRUE, showweights=FALSE, header=FALSE,
xlim, alim, olim, ylim, at, steps=5, level=95, refline=0, digits=2L, width,
xlab, slab, ilab, ilab.xpos, ilab.pos, order, subset,
xlab, slab, ilab, ilab.lab, ilab.xpos, ilab.pos, order, subset,
transf, atransf, targs, rows,
efac=1, pch, psize, plim=c(0.5,1.5), col, shade, colshade,
lty, fonts, cex, cex.lab, cex.axis, ...) {
Expand Down Expand Up @@ -40,6 +40,9 @@ lty, fonts, cex, cex.lab, cex.axis, ...) {
if (missing(ilab))
ilab <- NULL

if (missing(ilab.lab))
ilab.lab <- NULL

if (missing(ilab.xpos))
ilab.xpos <- NULL

Expand Down Expand Up @@ -847,13 +850,17 @@ lty, fonts, cex, cex.lab, cex.axis, ...) {
if (ncol.ilab >= 4L)
ilab.xpos <- seq(xlim[1] + dist*0.5, xlim[1] + dist*0.9, length.out=ncol.ilab)
}
if (length(ilab.xpos) != ncol(ilab))
stop(mstyle$stop(paste0("Number of 'ilab' columns (", ncol(ilab), ") does not match length of 'ilab.xpos' argument (", length(ilab.xpos), ").")))
if (length(ilab.xpos) != ncol.ilab)
stop(mstyle$stop(paste0("Number of 'ilab' columns (", ncol.ilab, ") does not match length of 'ilab.xpos' argument (", length(ilab.xpos), ").")))
if (!is.null(ilab.pos) && length(ilab.pos) == 1L)
ilab.pos <- rep(ilab.pos, ncol(ilab))
ilab.pos <- rep(ilab.pos, ncol.ilab)
if (!is.null(ilab.lab) && length(ilab.lab) != ncol.ilab)
stop(mstyle$stop(paste0("Number of 'ilab' columns (", ncol.ilab, ") does not match length of 'ilab.lab' argument (", length(ilab.lab), ").")))
par(family=names(fonts)[3], font=fonts[3])
for (l in seq_len(ncol(ilab))) {
for (l in seq_len(ncol.ilab)) {
ltext(ilab.xpos[l], rows+rowadj[3], ilab[,l], pos=ilab.pos[l], cex=cex, ...)
if (!is.null(ilab.lab))
ltext(ilab.xpos[l], ylim[2]-(top-1)+1+rowadj[3], ilab.lab[l], pos=ilab.pos[l], font=2, cex=cex, ...)
}
par(family=names(fonts)[1], font=fonts[1])
}
Expand Down Expand Up @@ -935,8 +942,8 @@ lty, fonts, cex, cex.lab, cex.axis, ...) {

### add header

ltext(textpos[1], ylim[2]-(top-1)+1, header.left, pos=4, font=2, cex=cex, ...)
ltext(textpos[2], ylim[2]-(top-1)+1, header.right, pos=2, font=2, cex=cex, ...)
ltext(textpos[1], ylim[2]-(top-1)+1+rowadj[1], header.left, pos=4, font=2, cex=cex, ...)
ltext(textpos[2], ylim[2]-(top-1)+1+rowadj[2], header.right, pos=2, font=2, cex=cex, ...)

#########################################################################

Expand Down
13 changes: 10 additions & 3 deletions R/forest.rma.r
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
forest.rma <- function(x,
annotate=TRUE, addfit=TRUE, addpred=FALSE, showweights=FALSE, header=FALSE,
xlim, alim, olim, ylim, at, steps=5, level=x$level, refline=0, digits=2L, width,
xlab, slab, mlab, ilab, ilab.xpos, ilab.pos, order,
xlab, slab, mlab, ilab, ilab.lab, ilab.xpos, ilab.pos, order,
transf, atransf, targs, rows,
efac=1, pch, psize, plim=c(0.5,1.5), colout, col, border, shade, colshade,
lty, fonts, cex, cex.lab, cex.axis, ...) {
Expand Down Expand Up @@ -46,6 +46,9 @@ lty, fonts, cex, cex.lab, cex.axis, ...) {
ilab <- .getx("ilab", mf=mf, data=x$data)
}

if (missing(ilab.lab))
ilab.lab <- NULL

if (missing(ilab.xpos))
ilab.xpos <- NULL

Expand Down Expand Up @@ -1097,9 +1100,13 @@ lty, fonts, cex, cex.lab, cex.axis, ...) {
stop(mstyle$stop(paste0("Number of 'ilab' columns (", ncol.ilab, ") does not match length of 'ilab.xpos' argument (", length(ilab.xpos), ").")))
if (!is.null(ilab.pos) && length(ilab.pos) == 1L)
ilab.pos <- rep(ilab.pos, ncol.ilab)
if (!is.null(ilab.lab) && length(ilab.lab) != ncol.ilab)
stop(mstyle$stop(paste0("Number of 'ilab' columns (", ncol.ilab, ") does not match length of 'ilab.lab' argument (", length(ilab.lab), ").")))
par(family=names(fonts)[3], font=fonts[3])
for (l in seq_len(ncol.ilab)) {
ltext(ilab.xpos[l], rows+rowadj[3], ilab[,l], pos=ilab.pos[l], cex=cex, ...)
if (!is.null(ilab.lab))
ltext(ilab.xpos[l], ylim[2]-(top-1)+1+rowadj[3], ilab.lab[l], pos=ilab.pos[l], font=2, cex=cex, ...)
}
par(family=names(fonts)[1], font=fonts[1])
}
Expand Down Expand Up @@ -1216,8 +1223,8 @@ lty, fonts, cex, cex.lab, cex.axis, ...) {

### add header

ltext(textpos[1], ylim[2]-(top-1)+1, header.left, pos=4, font=2, cex=cex, ...)
ltext(textpos[2], ylim[2]-(top-1)+1, header.right, pos=2, font=2, cex=cex, ...)
ltext(textpos[1], ylim[2]-(top-1)+1+rowadj[1], header.left, pos=4, font=2, cex=cex, ...)
ltext(textpos[2], ylim[2]-(top-1)+1+rowadj[2], header.right, pos=2, font=2, cex=cex, ...)

#########################################################################

Expand Down
2 changes: 1 addition & 1 deletion R/zzz.r
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
.onAttach <- function(libname, pkgname) {

ver <- "4.7-13"
ver <- "4.7-14"

loadmsg <- paste0("\nLoading the 'metafor' package (version ", ver, "). For an\nintroduction to the package please type: help(metafor)\n")

Expand Down
2 changes: 1 addition & 1 deletion README.md
Original file line number Diff line number Diff line change
Expand Up @@ -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--13-brightgreen.svg)](https://www.metafor-project.org/doku.php/installation#development_version)
[![devel Version](https://img.shields.io/badge/devel-4.7--14-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)

Expand Down
2 changes: 1 addition & 1 deletion docs/404.html

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion docs/ISSUE_TEMPLATE.html

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion docs/articles/index.html

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion docs/articles/pkgdown/diagram.html

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion docs/authors.html

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

4 changes: 2 additions & 2 deletions docs/index.html

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

5 changes: 3 additions & 2 deletions docs/news/index.html

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion docs/pkgdown.yml
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ pkgdown: 2.0.9
pkgdown_sha: ~
articles:
diagram: pkgdown/diagram.html
last_built: 2024-05-31T10:15Z
last_built: 2024-06-07T12:42Z
urls:
reference: https://wviechtb.github.io/metafor/reference
article: https://wviechtb.github.io/metafor/articles
Expand Down
Binary file modified docs/reference/addpoly.default-1.png
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
Loading

0 comments on commit feacbe6

Please sign in to comment.