Skip to content

Commit

Permalink
tweak and bug fix for r72149; new bibtex argument to print() and fo…
Browse files Browse the repository at this point in the history
…rmat()

git-svn-id: https://svn.r-project.org/R/trunk@72478 00db46b3-68df-0310-9c12-caf00c1e9a41
  • Loading branch information
maechler committed Apr 4, 2017
1 parent fac428f commit 15d3c23
Show file tree
Hide file tree
Showing 5 changed files with 64 additions and 38 deletions.
10 changes: 6 additions & 4 deletions doc/NEWS.Rd
Expand Up @@ -467,10 +467,12 @@
the help page.

\item Formatting and printing of bibliography entries
(\code{bibentry}) now by default shows the bibtex code also when
there is more than one entry. This also affects \code{citation()}:
use \code{options(citation.bibtex.max = 1)} to revert to previous
behavior.
(\code{bibentry}) is more flexible and better documented. Apart
from setting \code{options(citation.bibtex.max = 99)} you can also
use \code{print(<citation>, bibtex=TRUE)} (or \code{format(..)})
to get the BibTeX entries in the case of more than one entry.
This also affects \code{citation()}.
Contributions to enable \code{style = "html+bibtex"} are welcome.
}
}

Expand Down
1 change: 1 addition & 0 deletions src/library/utils/NAMESPACE
Expand Up @@ -136,6 +136,7 @@ S3method("[[", "person")
S3method("c", "bibentry")
S3method("c", "person")
S3method("format", "bibentry")
S3method("format", "citation")
S3method("format", "person")
S3method("print", "bibentry")
S3method("print", "citation")
Expand Down
45 changes: 22 additions & 23 deletions src/library/utils/R/citation.R
Expand Up @@ -664,6 +664,7 @@ function(style)
format.bibentry <-
function(x, style = "text", .bibstyle = NULL,
citation.bibtex.max = getOption("citation.bibtex.max", Inf),
bibtex = length(x) <= citation.bibtex.max,
sort = FALSE, ...)
{
if(!length(x)) return(character())
Expand All @@ -672,8 +673,11 @@ function(x, style = "text", .bibstyle = NULL,

if(sort) x <- sort(x, .bibstyle = .bibstyle)
x$.index <- as.list(seq_along(x))
if(!missing(citation.bibtex.max))
warning(gettextf("Argument '%s' is deprecated; rather set '%s' instead.",
"citation.bibtex.max", "bibtex=*"), domain=NA)

.format_bibentry_via_Rd <- function(f) {
format_via_Rd <- function(f) {
out <- file()
saveopt <- tools::Rd2txt_options(width = getOption("width"))
on.exit({tools::Rd2txt_options(saveopt); close(out)})
Expand All @@ -698,12 +702,8 @@ function(x, style = "text", .bibstyle = NULL,
})
}

.format_bibentry_as_citation <- function(x) {
bibtex <- length(x) <= citation.bibtex.max
if(!bibtex && missing(citation.bibtex.max))
message("there are additional BiBTeX citations. Use 'citation(*, citation.bibtex.max=Inf)' to see them all.")

c(paste(strwrap(attr(x, "mheader")), collapse = "\n"),
format_as_citation <- function(x, msg) {
c(paste(strwrap(attr(x, "mheader")), collapse = "\n"),
unlist(lapply(x, function(y) {
paste(c(if(!is.null(y$header))
c(strwrap(y$header), ""),
Expand All @@ -720,15 +720,19 @@ function(x, style = "text", .bibstyle = NULL,
c("", strwrap(y$footer))),
collapse = "\n")
})),
paste(strwrap(attr(x, "mfooter")), collapse = "\n")
paste(strwrap(c(attr(x, "mfooter"),
if(!bibtex && msg)
c("To see these entries in BibTeX format, use 'print(<citation>, bibtex=TRUE)', ",
"'toBibtex(.)', or set 'options(citation.bibtex.max=999)'.")
)), collapse = "\n")
)
}

out <-
switch(style,
"text" = .format_bibentry_via_Rd(tools::Rd2txt),
"html" = .format_bibentry_via_Rd(tools::Rd2HTML),
"latex" = .format_bibentry_via_Rd(tools::Rd2latex),
"text" = format_via_Rd(tools::Rd2txt),
"html" = format_via_Rd(tools::Rd2HTML),
"latex" = format_via_Rd(tools::Rd2latex),
"Bibtex" = {
unlist(lapply(x,
function(y)
Expand All @@ -739,7 +743,9 @@ function(x, style = "text", .bibstyle = NULL,
out[!lengths(out)] <- ""
unlist(out)
},
"citation" = .format_bibentry_as_citation(x),
"citation" = format_as_citation(x,
msg = missing(bibtex) &&
missing(citation.bibtex.max)),
"R" = .format_bibentry_as_R_code(x, ...)
)
as.character(out)
Expand Down Expand Up @@ -1300,12 +1306,7 @@ function(package = "base", lib.loc = NULL, auto = NULL)
.citation(rval)
}

.citation <-
function(x)
{
class(x) <- c("citation", "bibentry")
x
}
.citation <- function(x) structure(x, class = c("citation", "bibentry"))

.read_authors_at_R_field <-
function(x)
Expand Down Expand Up @@ -1338,12 +1339,10 @@ function(x)
"aut" %in% x$role
}

format.citation <-
function(x, style = "citation", ...) format.bibentry(x, style = style, ...)
print.citation <-
function(x, style = "citation", ...)
{
NextMethod("print", x, style = style, ...)
invisible(x)
}
function(x, style = "citation", ...) print.bibentry(x, style = style, ...)

as.bibentry <-
function(x)
Expand Down
30 changes: 21 additions & 9 deletions src/library/utils/man/bibentry.Rd
Expand Up @@ -9,22 +9,28 @@
\alias{print.bibentry}
\alias{format.bibentry}
\alias{sort.bibentry}
\alias{print.citation}
\alias{format.citation}
\description{
Functionality for representing and manipulating bibliographic
information in enhanced BibTeX style.
}
\usage{
bibentry(bibtype, textVersion = NULL, header = NULL, footer = NULL,
key = NULL, ..., other = list(),
key = NULL, \dots, other = list(),
mheader = NULL, mfooter = NULL)

\method{print}{bibentry}(x, style = "text", .bibstyle, ...)
\method{print}{bibentry}(x, style = "text", .bibstyle, \dots)

\method{format}{bibentry}(x, style = "text", .bibstyle = NULL,
citation.bibtex.max = getOption("citation.bibtex.max", Inf),
sort = FALSE, ...)
bibtex = length(x) <= citation.bibtex.max,
sort = FALSE, \dots)

\method{sort}{bibentry}(x, decreasing = FALSE, .bibstyle = NULL, drop = FALSE, \dots)

\method{print}{citation}(x, style = "citation", \dots)
\method{format}{citation}(x, style = "citation", \dots)
}
\arguments{
\item{bibtype}{a character string with a BibTeX entry type.
Expand All @@ -35,15 +41,19 @@ bibentry(bibtype, textVersion = NULL, header = NULL, footer = NULL,
\item{header}{a character string with optional header text.}
\item{footer}{a character string with optional footer text.}
\item{key}{a character string giving the citation key for the entry.}
\item{...}{for \code{bibentry}: arguments of the form
\item{\dots}{for \code{bibentry}: arguments of the form
\code{\var{tag}=\var{value}} giving the fields of the entry, with
\var{tag} and \var{value} the name and value of the field,
respectively. Arguments with empty values are dropped.
See \bold{Entry Fields} for details.

For the \code{print} method, extra parameters to pass to the
renderer.}
\item{other}{a list of arguments as in \code{...} (useful in
renderer.

For the \code{citation} class methods, parameters passed to the next
i.e., the corresponding \code{bibentry} method.
}
\item{other}{a list of arguments as in \code{\dots} (useful in
particular for fields named the same as formals of
\code{bibentry}).}
\item{mheader}{a character string with optional \dQuote{outer} header
Expand All @@ -57,15 +67,17 @@ bibentry(bibtype, textVersion = NULL, header = NULL, footer = NULL,
\item{decreasing}{logical, passed to \code{\link{order}} indicating
the sort direction.}
\item{.bibstyle}{a character string naming a bibliography style.}
\item{citation.bibtex.max}{a number, say \eqn{m}, indicating that the
\item{citation.bibtex.max}{(\emph{deprecated}, use \code{bibtex =
T|F} instead!) a number, say \eqn{m}, indicating that the
bibtex code should be given in addition to the formatted tex
\emph{when} there are not more than \eqn{m} entries. The default is
taken as \code{\link{getOption}("citation.bibtex.max", Inf)}. In \R
versions before 3.4.0, the default was \code{1} such that bibtex code
was shown only for a single entry. For example, to see no bibtex at
all, you can change the default by
\code{\link{options}(citation.bibtex.max = 0)}.}

\item{bibtex}{logical indicating if bibtex code should be given
additionally. Currently applies only to \code{style = "citation"}.}
\item{sort}{logical indicating if bibentries should be sorted, using
\code{\link[tools]{bibstyle}(.bibstyle)$sortKeys(x)}.}
\item{drop}{logical used as \code{x[ ..., drop=drop]} inside the
Expand Down Expand Up @@ -110,7 +122,7 @@ bibentry(bibtype, textVersion = NULL, header = NULL, footer = NULL,
\code{citation.bibtex.max} (with default
\code{\link{getOption}("citation.bibtex.max")} which defaults to 1)
determines for up to how many citation bibentries text style is shown
together with with bibtex, automatically.
together with bibtex, automatically.
It is possible to subscript bibentry objects by their keys (which are
used for character subscripts if the names are \code{NULL}).
Expand Down
16 changes: 14 additions & 2 deletions src/library/utils/man/citation.Rd
@@ -1,6 +1,6 @@
% File src/library/utils/man/citation.Rd
% Part of the R package, https://www.R-project.org
% Copyright 1995-2014 R Core Team
% Copyright 1995-2017 R Core Team
% Distributed under GPL 2 or later

\name{citation}
Expand Down Expand Up @@ -88,7 +88,9 @@ readCitationFile(file, meta = NULL)
any) of \code{meta} to determine the encoding of the file.
}
\value{
An object inheriting from class \code{"\link{bibentry}"}.
An object of class \code{"citation"}, inheriting from class
\code{"\link{bibentry}"}; see there, notably for the
\code{\link{print}} and \code{\link{format}} methods.
}
\seealso{
\code{\link{bibentry}}
Expand All @@ -105,4 +107,14 @@ if(nchar(system.file(package = "foreign"))) citation("foreign")
## extract the bibtex entry from the return value
x <- citation()
toBibtex(x)

\donttest{
## A citation with more than one bibentry:
cm <- tryCatch(citation("mgcv"),
error = function(e) {
warning("Recommended package 'mgcv' is not installed properly")
stop(e$message) })
cm # short entries (2-3 lines each)
print(cm, bibtex = TRUE) # each showing its bibtex code
}%dont
}

0 comments on commit 15d3c23

Please sign in to comment.