Attachment 'pkgDoc.R'

Download

   1 #' Document Package Using Specified Format
   2 #'
   3 #' Create documentation of packages in text, HTML, Latex, PDF and MoinMoin fomrats using Rd converters from "tools" package and \special{MoinMoin} converter from this package. With \special{MoinMoin} it is possible to convert either a single Rd file (using Rd2moin as a substitute for the converters provided by "tools"), or all Rd files in the package to a combined \special{MoinMoin} page.
   4 #' @param Rd a filename or an Rd object for single Rd file conversion. For package conversion, either an installed package name or a path to package top level directory. Default is working directory.
   5 #' @param type charcter: indicating the selected format. The options are, "text", "html", "latex", "example" (extract R code in the examples), "pdf" and "moin". The default is set to "unknown" so this parameter must be specified.
   6 #' @param ... additional paramaters to pass to the converter. See \code{\link[tools:Rd2HTML]{Rd2HTML}}, \code{\link[rhelium:Rd2moin]{Rd2moin}} and/or \code{\link[rhelium:moinDoc]{moinDoc}} for futher details.
   7 #' @author Ian Riley \email{ian@@riley.asia}
   8 #' @return Fomrated documentation for single or multiple Rd files for R package.
   9 #' @examples
  10 #' pkgDoc("~/R projects/rhelium-package")
  11 #' @export
  12 pkgDoc <- function(Rd = '.', type = "unknown", ...)
  13 {	
  14 	if(is.null(Rd) || is.na(Rd) || Rd == "") stop('argument "Rd" is missing, with no default')
  15 	
  16 	switch(class(Rd),
  17 		"Rd" = {}, # OK so do nothing
  18 		"character" = {
  19 			if (!is.installed(Rd) && !is.Rd_file(Rd) && !has.Rd_man(Rd))
  20 				stop('argument "Rd" is not an Rd folder/file, installed package or package base with "man" folder containing Rd files')
  21 		},
  22 		stop('class "', class(Rd), '" is not sutable for argument "Rd"')
  23 		)
  24 
  25 	# until functionality added for types other than "moin" and "pdf"
  26 	if (!type %in% c("moin", "pdf") && !(is.Rd(Rd) || is.Rd_file(Rd)))
  27 		stop('type "', type, '" only accepts an Rd object or file')
  28 
  29 	switch(type,
  30 		"text"		= Rd2txt(Rd, ...),
  31 		"html"		= Rd2HTML(Rd, ...),
  32 		"latex"		= Rd2latex(Rd, ...),
  33 		"example"	= Rd2ex(Rd, ...),
  34 		"moin"		= ifelse((is.Rd(Rd) || is.Rd_file(Rd)),
  35 			Rd2moin(Rd, ...), 
  36 			moinDoc(Rd, ...)),
  37 		"pdf"		= .Rd2pdf(Rd),
  38 		"unknown" = stop("no 'type' specified", call. = FALSE),
  39 		stop('"type" must be one of "text", "html", "latex", "example" or "moin"')
  40         )
  41     invisible()
  42 }
  43 
  44 #some helper functions
  45 	
  46 RdDir <- function(x) dir(x, ".Rd$")
  47 
  48 # tests
  49 is.Rd <- function(x) (class(x) == "Rd")
  50 
  51 is.Rd_file <- function(x) (file.exists(x) && file_ext(x) == "Rd")
  52 
  53 is.Rd_db <- function(x) (all(vapply(x, is.Rd, logical(1))))
  54 
  55 has.Rd_man <- function(x) {
  56 	x <- suppressWarnings(normalizePath(file.path(x, "/man")))
  57 	(dir.exists(x) && 
  58 		any(vapply(normalizePath(file.path(x, RdDir(x))), is.Rd_file, logical(1))))
  59 }
  60 
  61 RDir <- function(x) dir(x, ".R$")
  62 
  63 is.R_file <- function(x) (file.exists(x) && file_ext(x) == "R")
  64 
  65 get.R_files <- function (x) RDir(normalizePath(file.path(x, "/R")))
  66 
  67 has.R_code <- function(x) {
  68 	x <- suppressWarnings(normalizePath(file.path(x, "/R")))
  69 	(dir.exists(x) && 
  70 		any(vapply(normalizePath(file.path(x, RDir(x))), is.R_file, logical(1))))
  71 }
  72 
  73 is.installed <- function(x) (length(path.package(x, quiet = TRUE)) > 0)
  74 
  75 installed.path <- function(x) path.package(x, quiet = TRUE)[1]
  76 
  77 .Rd2pdf = function(Rd) {
  78 	# wrapper for R CMD Rd2pdf files
  79 	if (is.Rd(Rd)) {
  80 		name <- paste0(x[[grep("\\\\name", RdTags(x))]])
  81 		tempFile <- "./_Rd2pdf.Rd"
  82 		out <- file(tempFile, open= "wt")
  83 		writeLines(paste0(Rd, collapse = ""), out)
  84 		close(out)
  85 		on.exit(if (file.exists(tempFile)) file.remove(tempFile), add = TRUE)
  86 		args <- sprintf('--title="%s" --output="./%s.pdf" %s', name, name, tempFile)
  87 		} 
  88 	else if (is.Rd_file(Rd)) args <- Rd
  89 	else if (!is.installed(Rd) && has.Rd_man(Rd)) { # local takes priority over installed
  90 		args <- sprintf('--output="%s/%s.pdf" %s', Rd, Rd, Rd)
  91 		}
  92 	else args <- sprintf('--output="./%s.pdf" %s', Rd, installed.path(Rd))
  93 	
  94 	err <- tools::Rcmd(paste("Rd2pdf --batch --no-preview --force", args),
  95 		stderr = "Rd2pdf.log")
  96 	
  97 	if (err) stop("Processing error occurred: check log file in working directory")
  98 	else if (file.exists("Rd2pdf.log")) file.remove("Rd2pdf.log")
  99 }

You are not allowed to attach a file to this page.