Attachment 'moinDoc.R'

Download

   1 #' Create MoinMoin Page to Document Package
   2 #'
   3 #' See \url{http://moinmo.in} for details on \special{MoinMoin} markup.
   4 #' @param x a filename or Rd object to use as input for single Rd file conversion, or a package name, a path to package top level directory for combined file conversion. Default is working directory.
   5 #' @param out out a filename (with or without a path) or connection object to which to write the output. If there is no path, then the file will written to the current directory. If \code{out} is not specified, a file will be written to the current directory as "name.moin", where name is the package name.
   6 #' @param silent logical: if \code{TRUE}, messages are suppressed.
   7 #' @param internals logical: if \code{TRUE}, Rd files with a keyword set to "internal" are also included, rather than being skipped by default.
   8 #' @param ... additional paramaters to pass to the \code{Rd2moin} converter. See \code{\link[tools:Rd2HTML]{Rd2HTML}} and/or \code{\link[rhelium:Rd2moin]{Rd2moin}} for furhter details.
   9 #' @author Ian Riley (ian@riley.asia)
  10 #' @return Documentation in \special{MoinMoin} format for either an entire R package or a single Rd file.
  11 #' @examples
  12 #' moinDoc("./rhelium-package")
  13 #' @export
  14 moinDoc <- function(x = ".", out = "", silent = FALSE, internals = FALSE, ...)
  15 {
  16 	if (is.null(x) || is.na(x) || x == "") stop('argument "x" is missing, with no default')
  17 
  18 	moinDoc_out = NULL
  19 	if ("connection" %in% class(out)) {
  20 		if (!isOpen(out, "write")) stop("connection is not write enabled")
  21 		else {
  22 			 moinDoc_out = summary(out)
  23 			 switch(class(out)[[1]],
  24 			 	"file" = {
  25 			 		out <- moinDoc_out$description
  26 			 	},
  27 			 	"terminal" = {
  28 			 		out < stdout()
  29 			 	},
  30 			 	stop("cannot handle connection type:", class(out)[[1]])
  31 			 )
  32 		}
  33 	} else {
  34 		if (class(out) != "character") {
  35 			stop('class "', class(out), '" is not sutable for opening output connection')
  36 		}
  37 	}
  38 		
  39 	#desc <- list()
  40 	fromInstalled <- FALSE
  41 	pgk_path <- path.package(x, quiet = TRUE)
  42 	if (length(pgk_path)) {
  43 		fromInstalled <- TRUE
  44 		x <- pgk_path[1]
  45 	}
  46 	if (!fromInstalled && !has.Rd_man(x)) {
  47 		stop('argument "x" is neither an existing package nor a "man" folder with Rd files')
  48 	} 
  49 	base_path <- normalizePath(x)
  50 
  51 	local::as.object(get_pkg_docs(path = base_path), envir = environment())
  52 	pkg <- desc['Package']
  53 		
  54 	options(moinDoc_pkg = pkg)
  55 	options(moinDoc_path = base_path)
  56 	options(moinDoc_silent = silent)
  57 	options(moinDoc_internals = internals)
  58 	options(moinDoc_fromInstalled = fromInstalled)
  59 	on.exit(options(moinDoc_pkg = NULL), add = TRUE)
  60 	on.exit(options(moinDoc_path = NULL), add = TRUE)
  61 	on.exit(options(moinDoc_silent = NULL), add = TRUE)
  62 	on.exit(options(moinDoc_internals = NULL), add = TRUE)
  63 	on.exit(options(moinDoc_fromInstalled = NULL), add = TRUE)
  64 
  65 	if (is.null(moinDoc_out) && out == "") {
  66 		if (fromInstalled) out <- file.path('.', paste0(pkg, ".moin"))
  67 		else out <- file.path(base_path, paste0(pkg, ".moin"))
  68 	}
  69 		
  70 	if (out == stdout()) writeMessage(out, "Constructing MoinMoin page: stdout")
  71 	else writeMessage(out, "Constructing MoinMoin page: ", out)
  72 
  73 	.moinDoc <- pageHead(desc, out)
  74 
  75 	for (doc in docs[docOrder(docs)])
  76 		.moinDoc <- paste(.moinDoc, pageEntry(doc, out, ...), sep = "\n", collapse = "")
  77 
  78 	.moinDoc <- paste0(.moinDoc, pageFoot(desc, out), collapse = "")
  79 	
  80 }
  81 
  82 get_pkg_docs <- function(pkg = "", path = NULL) {
  83 	
  84 	unpack <- function(desc) {
  85 		fields <- desc$fields()
  86 		vapply(fields, desc$get, "")
  87 	}
  88 	
  89 	if (is.null(path)) {
  90 		desc <- unpack(desc::desc(package = pkg))
  91 		docs <- Rd_db(package = pkg)
  92 	} else {
  93 		desc <- unpack(desc::desc(file = path))
  94 		docs <- tools::Rd_db(package = desc['Package'], dir = path)
  95 	}
  96 	list(desc = desc, docs = docs)	
  97 }
  98 
  99 docOrder <- function(x, type = ".Rd") {
 100 	entries <- sort(names(x))
 101 	pkg <- options()$moinDoc_pkg
 102 	pkgDoc1 <- paste0(pkg, type)
 103 	pkgDoc2 <- paste0(pkg, "-package", type)
 104 	if (pkgDoc1 %in% entries)
 105 		entries <- c(pkgDoc1, entries[entries != pkgDoc1])
 106 	else if (pkgDoc2 %in% entries) 
 107 		entries <- c(pkgDoc2, entries[entries != pkgDoc2])
 108 	return(entries)
 109 }
 110 
 111 writeContent <- function(out, content, add=TRUE) 
 112 {
 113 	if (out == stdout()) {
 114 		cat(content)
 115 		cat("\n")
 116 	} else {
 117 		output <- file(out, open = ifelse(add, "at", "wt"))
 118 		writeLines(content, output)
 119 		close(output)
 120 	}
 121 }
 122 
 123 writeMessage <- function(out, ...) {
 124 	if (!options()$moinDoc_silent && out != stdout()) message(...)
 125 }
 126 
 127 pageHead <- function(x, out)
 128 {
 129 	local::as.object(x, envir = environment())
 130 	moinUser <- options()$moinUser
 131 	if (is.null(moinUser)) moinUser <- "UserName"
 132 	content <- paste(
 133 		"## Generated by ‘rhelium’ from Rd files: do not edit here",
 134 		sprintf("## Edit documentation in ‘%s’ source files", Package),
 135 		"#format wiki",
 136 		"#language en",
 137 		"#pragma section-numbers off",
 138 		sprintf("#acl %s:read,write,delete,revert,admin All:read", moinUser),
 139 		sprintf("#pragma keywords %s R-project package rhelium roxygen2 devtools", moinUser),
 140 		"#pragma supplementation-page on\n",
 141 		sep = "\n", collapse = "")
 142 	writeContent(out, content, add = FALSE)
 143 	content <- paste(
 144 		markup(sprintf("R Package ‘%s’", Package), "heading", 1L),
 145 		sprintf("Documentation for package ‘%s’ version %s. [[attachment:desc.txt|DESCRIPTION|target='_blank']]",
 146 			Package, Version),
 147 		"<<TableOfContents(2)>>",
 148 		markup("", "hozline", 3L),
 149 		sep = "\n\n", collapse = "")
 150 	writeContent(out, content, add = TRUE)
 151 	writeMessage(out, "\t- page processing instructions, heading and table of contents added")
 152 }
 153 
 154 pageEntry <- function(x, out, ...)
 155 {
 156 	if (!options()$moinDoc_internals && 
 157 		"internal" %in% .Rd_get_metadata(x, "keyword"))
 158 		 return()
 159 
 160 	pkg <- options()$moinDoc_pkg
 161 	docName <- "package documentation"
 162 	entry <- x[[2L]][[1L]][1]
 163 	if (entry == pkg) {
 164 		x[[2L]][[1L]][1] <- paste0(entry, "-package")
 165 	} else {
 166 		docName <- entry
 167 	}	
 168 
 169 	x <<- x
 170 	Rd2moin(x, out = out, append = TRUE, depth = 2, ...)
 171 	content <- "------\n"
 172 	writeContent(out, content, add = TRUE)
 173 	
 174 	sections <- RdTags(x)
 175 	sections <- sections[!(sections %in% c("\\alias", "\\concept", "\\encoding", "\\keyword"))]
 176 	writeMessage(out, sprintf("\t- %s section added...", docName))
 177 	writeMessage(out, "\t\t-- with subsections: ", toString(sub("\\\\", "", sections)))
 178 }
 179 
 180 pageFoot <- function(x, out)
 181 {
 182 	local::as.object(x, envir = environment())
 183 	path <- options()$moinDoc_path
 184 	if (!options()$moinDoc_fromInstalled) {
 185 		if (!has.R_code(path)) {
 186 			writeMessage(out, "\t- warning: no code links written: no R folder or code found")
 187 		} else {
 188 			files <- get.R_files(path)
 189 			files <- docOrder(setNames(files, files), type = ".R")
 190 			links <- paste(
 191 				vapply(files, markup, "linkAttach", FUN.VALUE = ""),
 192 				sep = "", collapse = "\n\n")
 193 			content <- paste(
 194 				markup("Code", "heading" , 1L),
 195 				"",
 196 				links,
 197 				"",
 198 				sep = "\n", collapse = "")
 199 			writeContent(out, content, add = TRUE)
 200 		}
 201 	} else {
 202 		writeMessage(out, "\t- warning: no code links written: request is for installed package")
 203 	}
 204 	
 205 	content <- paste(
 206 		markup("References", "heading", 1L),
 207 		markup(citation(Package)$textVersion, "itemNumeric"),
 208 		markup(citation("roxygen2")$textVersion, "itemNumeric"),
 209 		markup(citation("tools")$textVersion, "itemNumeric"),
 210 		markup("", "hozline", 3L),
 211 		"<<ViewLog()>>",
 212 		markup("", "hozline", 3L),
 213 		"CategoryRcoding CategoryRpackage",
 214 		sep = "\n\n", collapse = "")
 215 	writeContent(out, content, add = TRUE)
 216 	writeMessage(out, "\t- page footer added")
 217 }

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