# File src/library/utils/R/help.R
# Part of the R package, http://www.R-project.org
#
# Copyright (C) 1995-2012 The R Core Team
#
# This program is free software; you can redistribute it and/or modify
# it under the terms of the GNU General Public License as published by
# the Free Software Foundation; either version 2 of the License, or
# (at your option) any later version.
#
# This program is distributed in the hope that it will be useful,
# but WITHOUT ANY WARRANTY; without even the implied warranty of
# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
# GNU General Public License for more details.
#
# A copy of the GNU General Public License is available at
# http://www.r-project.org/Licenses/
help <-
function(topic, package = NULL, lib.loc = NULL,
verbose = getOption("verbose"),
try.all.packages = getOption("help.try.all.packages"),
help_type = getOption("help_type"))
{
types <- c("text", "html", "pdf")
if(!missing(package)) # Don't check for NULL; may be nonstandard eval
if(is.name(y <- substitute(package)))
package <- as.character(y)
## If no topic was given ...
if(missing(topic)) {
if(!is.null(package)) { # "Help" on package.
help_type <- if(!length(help_type)) "text"
else match.arg(tolower(help_type), types)
## Carter Butts and others misuse 'help(package=)' in startup
if (interactive() && help_type == "html") {
if (tools:::httpdPort == 0L) tools::startDynamicHelp()
if (tools:::httpdPort <= 0L) # fallback to text help
return(library(help = package, lib.loc = lib.loc,
character.only = TRUE))
browser <- if (.Platform$GUI == "AQUA") {
get("aqua.browser", envir = as.environment("tools:RGUI"))
} else getOption("browser")
browseURL(paste0("http://127.0.0.1:", tools:::httpdPort,
"/library/", package, "/html/00Index.html"),
browser)
return(invisible())
} else return(library(help = package, lib.loc = lib.loc,
character.only = TRUE))
}
if(!is.null(lib.loc)) # text "Help" on library.
return(library(lib.loc = lib.loc))
## ultimate default is to give help on help()
topic <- "help"; package <- "utils"; lib.loc <- .Library
}
ischar <- tryCatch(is.character(topic) && length(topic) == 1L,
error = identity)
if(inherits(ischar, "error")) ischar <- FALSE
## if this was not a length-one character vector, try for the name.
if(!ischar) {
## the reserved words that could be parsed as a help arg:
reserved <-
c("TRUE", "FALSE", "NULL", "Inf", "NaN", "NA", "NA_integer_",
"NA_real_", "NA_complex_", "NA_character_")
stopic <- deparse(substitute(topic))
if(!is.name(substitute(topic)) && ! stopic %in% reserved)
stop("'topic' should be a name, length-one character vector or reserved word")
topic <- stopic
}
help_type <- if(!length(help_type)) "text"
else match.arg(tolower(help_type), types)
paths <- index.search(topic,
find.package(if (is.null(package)) loadedNamespaces() else package,
lib.loc, verbose = verbose))
tried_all_packages <- FALSE
if(!length(paths)
&& is.logical(try.all.packages) && !is.na(try.all.packages)
&& try.all.packages && is.null(package) && is.null(lib.loc)) {
## Try all the remaining packages.
for(lib in .libPaths()) {
packages <- .packages(TRUE, lib)
packages <- packages[is.na(match(packages, .packages()))]
paths <- c(paths, index.search(topic, file.path(lib, packages)))
}
paths <- paths[paths != ""]
tried_all_packages <- TRUE
}
paths <- unique(paths)
attributes(paths) <-
list(call = match.call(), topic = topic,
tried_all_packages = tried_all_packages, type = help_type)
class(paths) <- "help_files_with_topic"
paths
}
print.help_files_with_topic <- function(x, ...)
{
browser <- getOption("browser")
topic <- attr(x, "topic")
type <- attr(x, "type")
if (.Platform$GUI == "AQUA" && type == "html")
browser <- get("aqua.browser", envir = as.environment("tools:RGUI"))
paths <- as.character(x)
if(!length(paths)) {
writeLines(c(gettextf("No documentation for %s in specified packages and libraries:",
sQuote(topic)),
gettextf("you could try %s",
sQuote(paste0("??", topic)))))
return(invisible(x))
}
if(type == "html")
if (tools:::httpdPort == 0L) tools::startDynamicHelp()
if(attr(x, "tried_all_packages")) {
paths <- unique(dirname(dirname(paths)))
msg <- gettextf("Help for topic %s is not in any loaded package but can be found in the following packages:",
sQuote(topic))
if (type == "html" && tools:::httpdPort > 0L) {
path <- file.path(tempdir(), ".R/doc/html")
dir.create(path, recursive = TRUE, showWarnings = FALSE)
out <- paste0('\n',
'