[Roxygen-commits] r82 - in pkg: . R sandbox
noreply at r-forge.r-project.org
noreply at r-forge.r-project.org
Thu Jul 24 20:16:01 CEST 2008
Author: pcd
Date: 2008-07-24 20:16:01 +0200 (Thu, 24 Jul 2008)
New Revision: 82
Modified:
pkg/DESCRIPTION
pkg/R/Rd.R
pkg/R/parse.R
pkg/sandbox/example-Rd-nlm.R
Log:
example based on file; honest strwrap in usage
Modified: pkg/DESCRIPTION
===================================================================
--- pkg/DESCRIPTION 2008-07-24 04:37:17 UTC (rev 81)
+++ pkg/DESCRIPTION 2008-07-24 18:16:01 UTC (rev 82)
@@ -1,10 +1,10 @@
Package: roxygen
Version: 0.1
License: GPL (>= 2)
-Description: A Doxygen-like in-line documentation system.
+Description: A Doxygen-like in-source documentation system.
Title: Roxygen Documentation System
-Author: Peter Danenberg <r-forge at wikitex.org>,
+Author: Peter Danenberg <pcd at roxygen.org>,
Manuel Eugster <Manuel.Eugster at stat.uni-muenchen.de>
-Maintainer: Peter Danenberg <r-forge at wikitex.org>
+Maintainer: Peter Danenberg <pcd at roxygen.org>
URL: http://roxygen.org
Collate: functional.R string.R parse.R collate.R list.R roclet.R namespace.R Rd.R
Modified: pkg/R/Rd.R
===================================================================
--- pkg/R/Rd.R 2008-07-24 04:37:17 UTC (rev 81)
+++ pkg/R/Rd.R 2008-07-24 18:16:01 UTC (rev 82)
@@ -13,7 +13,7 @@
#' of \code{parse.files}.
#'
#' @return Rd roclet
-make.Rd.roclet <- function() {
+make.Rd.roclet <- function(stdout=FALSE) {
#' Translate a key and expressions into an Rd expression;
#' multiple expressions take their own braces.
#' @param key the expression's key
@@ -72,10 +72,13 @@
},
name.defaults),
sep=', '))
- cat(strwrap(Rd.expression('usage',
- sprintf('%s(%s)', partitum$assignee, args)),
- exdent=4),
- sep='\n')
+ parse.expression('usage',
+ do.call(paste,
+ c(as.list(strwrap(sprintf('%s(%s)',
+ partitum$assignee,
+ args),
+ exdent=4)),
+ sep='\n')))
}
}
@@ -93,7 +96,8 @@
#' @param partitum the pre-parsed elements
#' @return \code{NULL}
pre.parse <- function(partitum) {
- assign.parent('params', nil, environment())
+ assign.parent('params', NULL, environment())
+ assign.parent('examples', NULL, environment())
parse.name(partitum)
parse.usage(partitum)
}
@@ -103,6 +107,7 @@
#' @return \code{NULL}
post.parse <- function(partitum) {
parse.arguments()
+ parse.examples()
## sink(NULL)
}
@@ -115,7 +120,6 @@
'note',
'author',
'seealso',
- 'examples',
'concept')
roclet$register.parser('return',
@@ -158,7 +162,7 @@
roclet$register.parser('description', parse.description)
- params <- nil
+ params <- NULL
#' Add a parameter to the global param list.
#' @param key ignored
@@ -190,5 +194,25 @@
roclet$register.parser('param', parse.param)
+ examples <- NULL
+
+ parse.example <- function(key, expression)
+ assign.parent('examples',
+ append(examples, expression),
+ environment())
+
+ parse.examples <- function() {
+ examples <- Reduce(c, Map(function(file)
+ tryCatch(readLines(trim(file)),
+ error=function(e) NULL),
+ examples),
+ NULL)
+ if (!is.null(examples))
+ cat(Rd.expression('examples',
+ do.call(paste, c(as.list(examples), sep='\n'))))
+ }
+
+ roclet$register.parser('example', parse.example)
+
roclet
}
Modified: pkg/R/parse.R
===================================================================
--- pkg/R/parse.R 2008-07-24 04:37:17 UTC (rev 81)
+++ pkg/R/parse.R 2008-07-24 18:16:01 UTC (rev 82)
@@ -182,7 +182,7 @@
'concept',
'note',
'seealso',
- 'examples',
+ 'example',
'keywords',
'return',
'author',
Modified: pkg/sandbox/example-Rd-nlm.R
===================================================================
--- pkg/sandbox/example-Rd-nlm.R 2008-07-24 04:37:17 UTC (rev 81)
+++ pkg/sandbox/example-Rd-nlm.R 2008-07-24 18:16:01 UTC (rev 82)
@@ -105,26 +105,7 @@
#' \code{\link{deriv}} to calculate analytical derivatives.
#'
#' For nonlinear regression, \code{\link{nls}} may be better.
-#'
-#' @examples
-#' f <- function(x) sum((x-1:length(x))^2)
-#' nlm(f, c(10,10))
-#' nlm(f, c(10,10), print.level = 2)
-#' utils::str(nlm(f, c(5), hessian = TRUE))
-#'
-#' f <- function(x, a) sum((x-a)^2)
-#' nlm(f, c(10,10), a=c(3,5))
-#' f <- function(x, a)
-#' {
-#' res <- sum((x-a)^2)
-#' attr(res, "gradient") <- 2*(x-a)
-#' res
-#' }
-#' nlm(f, c(10,10), a=c(3,5))
-#'
-#' ## more examples, including the use of derivatives.
-#' \dontrun{demo(nlm)}
-#'
+#' @example example-Rd-nlm-test.R
#' @keywords nonlinear optimize
nlm <- function(f, p, ..., hessian=FALSE, typsize=rep(1,length(p)),
fscale=1, print.level=0, ndigit=12, gradtol=1e-6,
More information about the Roxygen-commits
mailing list