diff --git a/src/library/utils/R/citation.R b/src/library/utils/R/citation.R index 5508d651813..16b9abda731 100644 --- a/src/library/utils/R/citation.R +++ b/src/library/utils/R/citation.R @@ -427,7 +427,7 @@ function(x, if(style == "R") return(.format_person_as_R_code(x)) args <- c("given", "family", "email", "role", "comment") - include <- sapply(include, match.arg, args) + include <- vapply(include, match.arg, "", args) ## process defaults braces <- braces[args] @@ -482,7 +482,7 @@ function(x, paste(do.call(c, rval), collapse = " ") } - sapply(x, format_person1) + vapply(x, format_person1, "") } as.character.person <- @@ -492,7 +492,7 @@ function(x, ...) toBibtex.person <- function(object, escape = FALSE, ...) { - object <- sapply(object, function(p) { + object <- vapply(object, function(p) { br <- if(is.null(p$family)) c("{", "}") else c("", "") s <- format(p, include = c("family", "given"), braces = list(given = br, family = c("", ","))) @@ -500,7 +500,7 @@ function(object, escape = FALSE, ...) (Encoding(s <- enc2utf8(s)) == "UTF-8")) tools::encoded_text_to_latex(s, "UTF-8") else s - }) + }, "") paste(object[nzchar(object)], collapse = " and ") } @@ -736,7 +736,7 @@ function(x, style = "text", .bibstyle = NULL, else if(is.character(macros)) macros <- tools::loadRdMacros(macros, tools:::initialRdMacros()) - sapply(.bibentry_expand_crossrefs(x), + vapply(.bibentry_expand_crossrefs(x), function(y) { txt <- tools::toRd(y, style = .bibstyle) ## @@ -757,7 +757,8 @@ function(x, style = "text", .bibstyle = NULL, outputEncoding = "UTF-8", ...) paste(readLines(out, encoding = "UTF-8"), collapse = "\n") - }) + }, + "") } format_as_citation <- function(x, msg) { # also (.., bibtex) @@ -1121,7 +1122,7 @@ function(..., recursive = FALSE) toBibtex.bibentry <- function(object, escape = FALSE, ...) { - format_author <- function(author) paste(sapply(author, function(p) { + format_author <- function(author) paste(vapply(author, function(p) { fnms <- p$family only_given_or_family <- (is.null(fnms) || is.null(p$given)) && @@ -1132,7 +1133,7 @@ function(object, escape = FALSE, ...) gbrc <- if(only_given_or_family) c("{", "}") else "" format(p, include = c("given", "family"), braces = list(given = gbrc, family = fbrc)) - }), collapse = " and ") + }, ""), collapse = " and ") format_bibentry1 <- function(object) { object <- unclass(object)[[1L]] @@ -1143,8 +1144,10 @@ function(object, escape = FALSE, ...) object$editor <- format_author(object$editor) rval <- c(rval, - sapply(names(object), function (n) - paste0(" ", n, " = {", object[[n]], "},")), + vapply(names(object), + function (n) + paste0(" ", n, " = {", object[[n]], "},"), + ""), "}", "") if(isTRUE(escape)) { rval <- enc2utf8(rval) @@ -1535,7 +1538,7 @@ function(x) x <- .read_authors_at_R_field(x) header <- attr(x, "header") footer <- attr(x, "footer") - x <- sapply(x, .format_person_for_plain_author_spec) + x <- vapply(x, .format_person_for_plain_author_spec, "") ## Drop persons with irrelevant roles. x <- x[nzchar(x)] ## And format. @@ -1622,7 +1625,7 @@ local({ } authorList <- function(paper) - sapply(paper$author, shortName) + vapply(paper$author, shortName, "") if (!missing(previous)) cited <<- previous