[Roxygen-commits] r91 - in pkg: R sandbox

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Fri Jul 25 20:40:08 CEST 2008


Author: pcd
Date: 2008-07-25 20:40:08 +0200 (Fri, 25 Jul 2008)
New Revision: 91

Added:
   pkg/R/roxygenize.R
   pkg/sandbox/roxygenize.R
Modified:
   pkg/R/Rd.R
   pkg/R/parse.R
   pkg/sandbox/Rd.R
Log:
inchoate roxygenize; document parsers;


Modified: pkg/R/Rd.R
===================================================================
--- pkg/R/Rd.R	2008-07-25 05:20:36 UTC (rev 90)
+++ pkg/R/Rd.R	2008-07-25 18:40:08 UTC (rev 91)
@@ -12,9 +12,10 @@
 #' Contains the member function \code{parse} which parses the result
 #' of \code{parse.files}.
 #'
-#' @param stdout whether to cat to standard out (e.g. for testing)
+#' @param subdir directory into which to place the Rd files; if
+#' \code{NULL}, standard out.
 #' @return Rd roclet
-make.Rd.roclet <- function(stdout=FALSE) {
+make.Rd.roclet <- function(subdir=NULL) {
   #' Translate a key and expressions into an Rd expression;
   #' multiple expressions take their own braces.
   #' @param key the expression's key
@@ -35,8 +36,24 @@
   #' @param \dots the arguments
   #' @return \code{NULL}
   parse.expression <- function(key, ...)
-    cat(Rd.expression(key, c(...)))
+    cat(Rd.expression(key, c(...)), file=filename, append=T)
 
+  filename <- ''
+
+  reset.filename <- function()
+    assign.parent('filename', '', environment())
+
+  first.source.line <- function(partitum) {
+    srcfile <- srcfile(partitum$srcref$filename)
+    first.line <- car(partitum$srcref$lloc)
+    getSrcLines(srcfile, first.line, first.line)
+  }
+
+  NULL.STATEMENT <- 'roxygen()'
+
+  is.null.statement <- function(source.line)
+    length(grep(NULL.STATEMENT, source.line) > 0)
+
   #' Reconstruct the \name directive from amongst
   #' \code{@@name}, \code{@@setMethod}, \code{@@setClass},
   #' \code{@@setGeneric}, \code{@@assignee}, etc.
@@ -49,9 +66,29 @@
                          partitum$S4method,
                          partitum$S4generic)
     name <- first.non.null(name, assignee, S4)
-    ## sink(name)
-    if (!is.null(name))
+    if (is.null(name) && !is.null(subdir)) {
+      filename <- partitum$srcref$filename
+      first.line <- car(partitum$srcref$lloc)
+      first.source.line <- first.source.line(partitum)
+      if (!is.null.statement(first.source.line))
+        warning(sprintf(paste('No name found for the',
+                              'following expression in %s',
+                              'line %s:\n  `%s . . .\''),
+                        filename,
+                        first.line,
+                        first.source.line),
+                immediate.=T)
+    } else if (!is.null(name)) {
+      name <- trim(name)
+      if (!is.null(subdir)) {
+        assign.parent('filename',
+                      file.path(subdir, sprintf('%s.Rd', name)),
+                      environment())
+        cat(sprintf('Writing %s to %s\n', name, filename))
+        unlink(filename)
+      }
       parse.expression('name', name)
+    }
   }
   
   #' Turn a list of formal arguments into a human-readable
@@ -109,7 +146,10 @@
   post.parse <- function(partitum) {
     parse.arguments()
     parse.examples(partitum)
-    ## sink(NULL)
+    ## Assuming the previous sink was successful;
+    ## if not, it will destroy the sink stack.
+    ## (Should fail if unwritable, anyway.)
+    reset.filename()
   }
 
   roclet <- make.roclet(parse.expression,

Modified: pkg/R/parse.R
===================================================================
--- pkg/R/parse.R	2008-07-25 05:20:36 UTC (rev 90)
+++ pkg/R/parse.R	2008-07-25 18:40:08 UTC (rev 91)
@@ -151,6 +151,7 @@
 
 #' Possibly NA; in which case, the Roclets can do something more
 #' sophisticated with the srcref.
+#' @name parse.preref.export
 register.preref.parser('export', parse.default)
 
 #' Parse an element with a mandatory value.
@@ -164,6 +165,12 @@
     parse.default(key, rest)
 }
   
+#' Parsers with a mandatory value.
+#' @name value.parsers
+#' @aliases prototype exportClass exportMethod exportPattern S3method
+#' @aliases import importFrom importClassesFrom importMethodsFrom name
+#' @aliases aliases title usage references concept note seealso example
+#' @aliases examples keywords return author include
 register.preref.parsers(parse.value,
                         'prototype',
                         'exportClass',
@@ -206,6 +213,9 @@
                       names=key))
 }
 
+#' Parsers with name and description
+#' @name name.description.parsers
+#' @aliases slot param
 register.preref.parsers(parse.name.description,
                         'slot',
                         'param')
@@ -223,6 +233,9 @@
   parse.default(key, strcar(name))
 }
 
+#' Parsers taking a name
+#' @name name.parsers
+#' @aliases S3class returnType
 register.preref.parsers(parse.name,
                         'S3class',
                         'returnType')
@@ -234,6 +247,9 @@
 parse.toggle <- function(key, rest)
   as.list(structure(TRUE, names=key))
 
+#' Toggling parsers
+#' @name toggle.parsers
+#' @aliases listObject attributeObject environmentObject
 register.preref.parsers(parse.toggle,
                         'listObject',
                         'attributeObject',
@@ -246,6 +262,7 @@
 parse.srcref <- function(pivot, expression) nil
 
 #' Parse S4 \code{setClass} method.
+#' @name parse.srcref.setClass
 #' @param pivot the parsing pivot
 #' @param expression the expression to be parsed
 #' @return An list containing the class to be set
@@ -254,6 +271,7 @@
                        list(S4class=car(expression)))
 
 #' Parse S4 \code{setGeneric} method.
+#' @name parse.srcref.setGeneric
 #' @param pivot the parsing pivot
 #' @param expression the expression to be parsed
 #' @return A list containing the generic
@@ -262,6 +280,7 @@
                        list(S4generic=car(expression)))
 
 #' Parse S4 \code{setMethod} method.
+#' @name parse.srcref.setMethod
 #' @param pivot the parsing pivot
 #' @param expression the expression to be parsed
 #' @return A list containing the method to be set
@@ -411,7 +430,8 @@
   }
   if (is.null(formals)) formals
   else list(formals=Map(function(formal)
-              if (is.call(formal)) capture.output(formal)
+              if (is.null(formal)) ''
+              else if (is.call(formal)) capture.output(formal)
               else as.character(formal), formals))
 }
 

Added: pkg/R/roxygenize.R
===================================================================
--- pkg/R/roxygenize.R	                        (rev 0)
+++ pkg/R/roxygenize.R	2008-07-25 18:40:08 UTC (rev 91)
@@ -0,0 +1,17 @@
+#' @include Rd.R
+#' @include namespace.R
+#' @include collate.R
+ROXYGEN.DIR <- '%s.roxygen'
+MAN.DIR <- 'man'
+R.DIR <- 'R'
+
+roxygenize <- function(package.dir) {
+  roxygen.dir <- sprintf(ROXYGEN.DIR, package.dir)
+  man.dir <- file.path(roxygen.dir, MAN.DIR)
+  skeleton <- c(roxygen.dir, man.dir)
+  for (dir in skeleton) dir.create(dir, showWarnings=F)
+  r.dir <- file.path(package.dir, R.DIR)
+  source.files <- list.files(r.dir, recursive=T, full.names=T)
+  Rd <- make.Rd.roclet(man.dir)
+  do.call(Rd$parse, as.list(source.files))
+}

Modified: pkg/sandbox/Rd.R
===================================================================
--- pkg/sandbox/Rd.R	2008-07-25 05:20:36 UTC (rev 90)
+++ pkg/sandbox/Rd.R	2008-07-25 18:40:08 UTC (rev 91)
@@ -5,7 +5,8 @@
 source('../R/roclet.R')
 source('../R/Rd.R')
 
-FILES <- list('example-Rd-nlm.R')
+## FILES <- list('example-Rd-nlm.R')
+FILES <- list('../R/Rd.R')
 
 argv <- commandArgs(trailingOnly=T)
 argc <- length(argv)

Added: pkg/sandbox/roxygenize.R
===================================================================
--- pkg/sandbox/roxygenize.R	                        (rev 0)
+++ pkg/sandbox/roxygenize.R	2008-07-25 18:40:08 UTC (rev 91)
@@ -0,0 +1,20 @@
+if (!file.exists('pkg/R/parse.R'))
+  stop('Run one directory above `pkg\'.')
+
+source('pkg/R/functional.R')
+source('pkg/R/list.R')
+source('pkg/R/parse.R')
+source('pkg/R/string.R')
+source('pkg/R/roclet.R')
+source('pkg/R/Rd.R')
+source('pkg/R/namespace.R')
+source('pkg/R/collate.R')
+source('pkg/R/roxygenize.R')
+
+PKG.DIR <- 'pkg'
+
+argv <- commandArgs(trailingOnly=T)
+argc <- length(argv)
+pkg.dir <- if (argc > 0) car(argv) else PKG.DIR
+
+roxygenize(pkg.dir)



More information about the Roxygen-commits mailing list