Skip to content

Commit 0671d08

Browse files
author
maechler
committed
internal latex-help utils: modularize + msg argument
git-svn-id: https://svn.r-project.org/R/trunk@88132 00db46b3-68df-0310-9c12-caf00c1e9a41
1 parent 436cb64 commit 0671d08

File tree

1 file changed

+33
-28
lines changed

1 file changed

+33
-28
lines changed

src/library/utils/R/help.R

Lines changed: 33 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
# File src/library/utils/R/help.R
22
# Part of the R package, https://www.R-project.org
33
#
4-
# Copyright (C) 1995-2016 The R Core Team
4+
# Copyright (C) 1995-2025 The R Core Team
55
#
66
# This program is free software; you can redistribute it and/or modify
77
# it under the terms of the GNU General Public License as published by
@@ -88,13 +88,15 @@ function(topic, package = NULL, lib.loc = NULL,
8888
class = "help_files_with_topic")
8989
}
9090

91-
print.help_files_with_topic <- function(x, ...)
91+
print.help_files_with_topic <- function(x, ...) # ... may contain msg=FALSE
9292
{
93-
browser <- getOption("browser")
9493
topic <- attr(x, "topic")
95-
type <- attr(x, "type")
96-
if (.Platform$GUI == "AQUA" && type == "html")
97-
browser <- get("aqua.browser", envir = as.environment("tools:RGUI"))
94+
type <- attr(x, "type")
95+
if(type == "html")
96+
browser <-
97+
if (.Platform$GUI == "AQUA" && type == "html")
98+
get("aqua.browser", envir = as.environment("tools:RGUI"))
99+
else getOption("browser")
98100
paths <- as.character(x)
99101
if(!length(paths)) {
100102
writeLines(c(gettextf("No documentation for %s in specified packages and libraries:",
@@ -104,7 +106,7 @@ print.help_files_with_topic <- function(x, ...)
104106
return(invisible(x))
105107
}
106108

107-
port <- if(type == "html") tools::startDynamicHelp(NA) else NULL
109+
if(type == "html") port <- tools::startDynamicHelp(NA)
108110

109111
if(attr(x, "tried_all_packages")) {
110112
paths <- unique(dirname(dirname(paths)))
@@ -174,7 +176,7 @@ print.help_files_with_topic <- function(x, ...)
174176
tmp[tools::file_path_sans_ext(tmp$File) == tp[i], "Title"]
175177
}
176178
txt <- paste0(titles, " {", basename(paths), "}")
177-
## the default on menu() is currtently graphics = FALSE
179+
## the default on menu() is currently graphics = FALSE
178180
res <- menu(txt, title = gettext("Choose one"),
179181
graphics = getOption("menu.graphics"))
180182
if(res > 0) file <- p[res]
@@ -215,25 +217,21 @@ print.help_files_with_topic <- function(x, ...)
215217
texinputs <- file.path(dirpath, "help", "figures")
216218
tf2 <- tempfile("Rlatex")
217219
tools::Rd2latex(.getHelpFile(file), out = tf2)
218-
.show_help_on_topic_offline(tf2, topic, type, texinputs)
220+
.show_help_on_topic_offline(tf2, topic, type, texinputs, ...)
219221
unlink(tf2)
220222
}
221223
}
222-
223224
invisible(x)
224225
}
225226

226-
.show_help_on_topic_offline <-
227-
function(file, topic, type = "pdf", texinputs = NULL)
228-
{
229-
encoding <-""
227+
.help_topic_latex <- function(file, topic) { # Side effect: creates file <topic>.tex in working directory
230228
lines <- readLines(file)
231229
encpatt <- "^\\\\inputencoding\\{(.*)\\}$"
232-
if(length(res <- grep(encpatt, lines, perl = TRUE, useBytes = TRUE)))
233-
encoding <- sub(encpatt, "\\1", lines[res],
234-
perl = TRUE, useBytes = TRUE)
230+
encoding <- if(length(res <- grep(encpatt, lines,
231+
perl = TRUE, useBytes = TRUE, value = TRUE)))
232+
sub(encpatt, "\\1", res, perl = TRUE, useBytes = TRUE)
233+
else ""
235234
texfile <- paste0(topic, ".tex")
236-
on.exit(unlink(texfile)) ## ? leave to helper
237235
if(nzchar(opt <- Sys.getenv("R_RD4PDF"))) opt else "times,inconsolata"
238236
has_figure <- any(grepl("\\Figure", lines))
239237
cat("\\documentclass[", getOption("papersize"), "paper]{article}\n",
@@ -245,11 +243,19 @@ print.help_files_with_topic <- function(x, ...)
245243
file = texfile, sep = "")
246244
file.append(texfile, file)
247245
cat("\\end{document}\n", file = texfile, append = TRUE)
248-
helper <- if (exists("offline_help_helper", envir = .GlobalEnv))
249-
get("offline_help_helper", envir = .GlobalEnv)
250-
else offline_help_helper
251-
if (has_figure) helper(texfile, type, texinputs)
252-
else helper(texfile, type)
246+
texfile
247+
}
248+
249+
## "static": _only_ called once above for type == "pdf" : currently "offline" <==> {latex -> pdf}
250+
.show_help_on_topic_offline <-
251+
function(file, topic, type = "pdf", texinputs = NULL, msg = TRUE)
252+
{
253+
texfile <- .help_topic_latex(file, topic)
254+
on.exit(unlink(texfile)) ## ? leave to helper
255+
helper <- get0("offline_help_helper", envir = .GlobalEnv) %||% offline_help_helper # <-> below
256+
if (has_figure)
257+
helper(texfile, type, texinputs=texinputs, msg=msg)
258+
else helper(texfile, type, msg=msg)
253259
invisible()
254260
}
255261

@@ -268,7 +274,7 @@ print.help_files_with_topic <- function(x, ...)
268274
}
269275

270276

271-
offline_help_helper <- function(texfile, type, texinputs = NULL)
277+
offline_help_helper <- function(texfile, type, texinputs = NULL, msg = TRUE)
272278
{
273279
## Some systems have problems with texfile names like ".C.tex"
274280
tf <- tempfile("tex", tmpdir = ".", fileext = ".tex"); on.exit(unlink(tf))
@@ -280,11 +286,10 @@ offline_help_helper <- function(texfile, type, texinputs = NULL)
280286
stop(gettextf("creation of %s failed", sQuote(ofile2)), domain = NA)
281287
if(file.copy(ofile, ofile2, overwrite = TRUE)) {
282288
unlink(ofile)
283-
message(gettextf("Saving help page to %s", sQuote(basename(ofile2))),
284-
domain = NA)
285-
} else {
286-
message(gettextf("Saving help page to %s", sQuote(ofile)), domain = NA)
289+
if(msg) ofile <- basename(ofile2)
287290
}
291+
if(msg)
292+
message(gettextf("Saving help page to %s", sQuote(ofile)), domain = NA)
288293
invisible()
289294
}
290295

0 commit comments

Comments
 (0)