[Rcpp-commits] r217 - in pkg: . R inst/examples/RcppInline man
noreply at r-forge.r-project.org
noreply at r-forge.r-project.org
Sun Dec 27 22:14:34 CET 2009
Author: edd
Date: 2009-12-27 22:14:32 +0100 (Sun, 27 Dec 2009)
New Revision: 217
Removed:
pkg/R/RcppInline.R
pkg/man/RcppInline.Rd
pkg/man/internals.Rd
Modified:
pkg/DESCRIPTION
pkg/NAMESPACE
pkg/inst/examples/RcppInline/RcppInlineExample.r
pkg/inst/examples/RcppInline/RcppInlineWithLibsExamples.r
pkg/inst/examples/RcppInline/RcppSexpTests.r
pkg/inst/examples/RcppInline/RcppSimpleExample.r
pkg/inst/examples/RcppInline/RcppSimpleTests.r
pkg/inst/examples/RcppInline/UncaughtExceptions.r
Log:
removes inline support from Rcpp:
- added Suggests: inline (>= 0.3.4) to DESCRIPTION
- remove R/RcppInline.R
- remove man/RcppInline.Rd and man/internals.Rd
- remove NAMESPACE entries
- update inst/examples/RcppInline/* with library(inline) or require(inline)
all examples still run against the patched new inline-0.3.4
Modified: pkg/DESCRIPTION
===================================================================
--- pkg/DESCRIPTION 2009-12-27 17:16:28 UTC (rev 216)
+++ pkg/DESCRIPTION 2009-12-27 21:14:32 UTC (rev 217)
@@ -1,6 +1,6 @@
Package: Rcpp
Title: Rcpp R/C++ interface package
-Version: 0.7.0.2
+Version: 0.7.0.3
Date: $Date$
Author: Dirk Eddelbuettel and Romain Francois, with contributions
by Simon Urbanek and David Reiss; based on code written during
@@ -13,12 +13,13 @@
from simple SEXP objects is particular easy. Calling R functions from C++ is
also supported.
.
- C++ code can be 'inlined' and a helper function (from the 'inline' package)
- will create a C++ function and compile, link and load it which makes C++
- integration easy.
+ C++ code can be 'inlined' by using the 'inline' package which will create a
+ C++ function and compile, link and load it given the 'inlined' character
+ argument which makes C++ integration very easy.
.
Several examples are included.
-Depends: R (>= 2.0.0), methods
+Depends: R (>= 2.0.0)
+Suggests: inline (>= 0.3.4)
SystemRequirements: None
URL: http://dirk.eddelbuettel.com/code/rcpp.html
License: GPL (>= 2)
Modified: pkg/NAMESPACE
===================================================================
--- pkg/NAMESPACE 2009-12-27 17:16:28 UTC (rev 216)
+++ pkg/NAMESPACE 2009-12-27 21:14:32 UTC (rev 217)
@@ -4,10 +4,5 @@
print.RcppExample,
RcppDateExample,
RcppParamsExample,
- RcppVectorExample,
- cfunction ## from inline and adapted
+ RcppVectorExample
)
-
-exportMethods(
- setCMethod
-)
Deleted: pkg/R/RcppInline.R
===================================================================
--- pkg/R/RcppInline.R 2009-12-27 17:16:28 UTC (rev 216)
+++ pkg/R/RcppInline.R 2009-12-27 21:14:32 UTC (rev 217)
@@ -1,302 +0,0 @@
-## Taken from inline 0.3.3, and includes the patch I sent to Oleg with a request for inclusion
-
-## - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
-## CFunc is an S4 class derived from 'function'. This inheritance allows objects
-## to behave exactly as functions do, but it provides a slot @code that keeps the
-## source C or Fortran code used to create the inline call
-setClass("CFunc",
- representation(
- code="character"
- ),
- contains="function"
-)
-
-# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
-cfunction <- function(sig=character(), body=character(), includes=character(), otherdefs=character(),
- language=c("C++", "C", "Fortran", "F95", "ObjectiveC", "ObjectiveC++"),
- verbose=FALSE, convention=c(".Call", ".C", ".Fortran"), Rcpp=FALSE,
- cppargs=character(), cxxargs=character(), libargs=character()) {
-
- convention <- match.arg(convention)
-
- if ( missing(language) ) language <- ifelse(convention == ".Fortran", "Fortran", "C++")
- else language <- match.arg(language)
-
- language <- switch(EXPR=tolower(language), cpp="C++", f="Fortran", f95="F95",
- objc="ObjectiveC", objcpp= ,"objc++"="ObjectiveC++", language)
-
- f <- basename(tempfile())
-
- if ( !is.list(sig) ) {
- sig <- list(sig)
- names(sig) <- f
- names(body) <- f
- }
- if( length(sig) != length(body) )
- stop("mismatch between the number of functions declared in 'sig' and the number of function bodies provided in 'body'")
-
- if (Rcpp) {
- cxxargs <- c(Rcpp:::RcppCxxFlags(), cxxargs) # prepend information from Rcpp
- libargs <- c(Rcpp:::RcppLdFlags(), libargs) # prepend information from Rcpp
- }
- if (length(cppargs) != 0) {
- args <- paste(cppargs, collapse=" ")
- if (verbose) cat("Setting PKG_CPPFLAGS to", args, "\n")
- Sys.setenv(PKG_CPPFLAGS=args)
- }
- if (length(cxxargs) != 0) {
- args <- paste(cxxargs, collapse=" ")
- if (verbose) cat("Setting PKG_CXXFLAGS to", args, "\n")
- Sys.setenv(PKG_CXXFLAGS=args)
- }
- if (length(libargs) != 0) {
- args <- paste(libargs, collapse=" ")
- if (verbose) cat("Setting PKG_LIBS to", args, "\n")
- Sys.setenv(PKG_LIBS=args)
- }
-
- ## GENERATE THE CODE
- for ( i in seq_along(sig) ) {
- ## C/C++ with .Call convention *********************************************
- if ( convention == ".Call" ) {
- ## include R includes, also error
- if (i == 1) {
- code <- ifelse(Rcpp,
- "#include <Rcpp.h>\n",
- paste("#include <R.h>\n#include <Rdefines.h>\n",
- "#include <R_ext/Error.h>\n", sep=""));
- ## include further includes
- code <- paste(c(code, includes, ""), collapse="\n")
- ## include further definitions
- code <- paste(c(code, otherdefs, ""), collapse="\n")
- }
- ## generate C-function sig from the original sig
- if ( length(sig[[i]]) > 0 ) {
- funCsig <- paste("SEXP", names(sig[[i]]), collapse=", " )
- }
- else funCsig <- ""
- funCsig <- paste("SEXP", names(sig)[i], "(", funCsig, ")", sep=" ")
- ## add C export of the function
- if ( language == "C++" || language == "ObjectiveC++")
- code <- paste( code, "extern \"C\" {\n ", funCsig, ";\n}\n\n", sep="")
- ## OPEN function
- code <- paste( code, funCsig, " {\n", sep="")
- ## add code, split lines
- code <- paste( code, paste(body[[i]], collapse="\n"), sep="")
- ## CLOSE function, add return and warning in case the user forgot it
- code <- paste(code, "\n ",
- ifelse(Rcpp, "Rf_warning", "warning"),
- "(\"your C program does not return anything!\");\n return R_NilValue;\n}\n", sep="");
- }
-
- ## C/C++ with .C convention ************************************************
- else if ( convention == ".C" ) {
- if (i == 1) {
- ## include only basic R includes
- code <- ifelse(Rcpp,"#include <Rcpp.h>\n", "#include <R.h>\n")
- ## include further includes
- code <- paste(c(code, includes, ""), collapse="\n")
- ## include further definitions
- code <- paste(c(code, otherdefs, ""), collapse="\n")
- }
- ## determine function header
- if ( length(sig[[i]]) > 0 ) {
- types <- pmatch(sig[[i]], c("logical", "integer", "double", "complex",
- "character", "raw", "numeric"), duplicates.ok = TRUE)
- if ( any(is.na(types)) ) stop( paste("Unrecognized type", sig[[i]][is.na(types)]) )
- decls <- c("int *", "int *", "double *", "Rcomplex *", "char **",
- "unsigned char *", "double *")[types]
- funCsig <- paste(decls, names(sig[[i]]), collapse=", ")
- }
- else funCsig <- ""
- funCsig <- paste("void", names(sig)[i], "(", funCsig, ")", sep=" ")
- if ( language == "C++" || language == "ObjectiveC++" )
- code <- paste( code, "extern \"C\" {\n ", funCsig, ";\n}\n\n", sep="")
- ## OPEN function
- code <- paste( code, funCsig, " {\n", sep="")
- ## add code, split lines
- code <- paste( code, paste(body[[i]], collapse="\n"), sep="")
- ## CLOSE function
- code <- paste( code, "\n}\n", sep="")
- }
- ## .Fortran convention *****************************************************
- else {
- if (i == 1) {
- ## no default includes, include further includes
- code <- paste(includes, collapse="\n")
- ## include further definitions
- code <- paste(c(code, otherdefs, ""), collapse="\n")
- }
- ## determine function header
- if ( length(sig[[i]]) > 0 ) {
- types <- pmatch(sig[[i]], c("logical", "integer", "double", "complex",
- "character", "raw", "numeric"), duplicates.ok = TRUE)
- if ( any(is.na(types)) ) stop( paste("Unrecognized type", sig[[i]][is.na(types)]) )
- if (6 %in% types) stop( "raw type unsupported by .Fortran()" )
- decls <- c("INTEGER", "INTEGER", "DOUBLE PRECISION", "DOUBLE COMPLEX",
- "CHARACTER*255", "Unsupported", "DOUBLE PRECISION")[types]
- decls <- paste(" ", decls, " ", names(sig[[i]]), "(*)", sep="", collapse="\n")
- funCsig <- paste(names(sig[[i]]), collapse=", ")
- }
- else {
- decls <- ""
- funCsig <- ""
- }
- funCsig <- paste(" SUBROUTINE", names(sig)[i], "(", funCsig, ")\n", sep=" ")
- ## OPEN function
- code <- paste( code, funCsig, decls, collapse="\n")
- ## add code, split lines
- code <- paste( code, paste(body[[i]], collapse="\n"), sep="")
- ## CLOSE function
- code <- paste( code, "\n RETURN\n END\n", sep="")
- }
- } ## for along signatures
-
- ## WRITE AND COMPILE THE CODE
- libLFile <- compileCode(f, code, language, verbose)
-
- ## SET A FINALIZER TO PERFORM CLEANUP
- cleanup <- function(env) {
- if ( f %in% names(getLoadedDLLs()) ) dyn.unload(libLFile)
- unlink(libLFile)
- }
- reg.finalizer(environment(), cleanup, onexit=TRUE)
-
- res <- vector("list", length(sig))
- names(res) <- names(sig)
-
- ## GENERATE R FUNCTIONS
- for ( i in seq_along(sig) ) {
- ## Create new objects of class CFunc, each containing the code of ALL inline
- ## functions. This will be used to recompile the whole shared lib when needed
- res[[i]] <- new("CFunc", code = code)
-
- ## this is the skeleton of the function, the external call is added below using 'body'
- ## important here: all variables are kept in the local environment
- fn <- function(arg) {
- if ( !file.exists(libLFile) )
- libLFile <<- compileCode(f, code, language, verbose)
- if ( !( f %in% names(getLoadedDLLs()) ) ) dyn.load(libLFile)
- }
-
- ## Modify the function formals to give the right argument list
- args <- formals(fn)[ rep(1, length(sig[[i]])) ]
- names(args) <- names(sig[[i]])
- formals(fn) <- args
-
- ## create .C/.Call function call that will be added to 'fn'
- if (convention == ".Call") {
- body <- quote( CONVENTION("EXTERNALNAME", PACKAGE=f, ARG) )[ c(1:3, rep(4, length(sig[[i]]))) ]
- for ( j in seq(along = sig[[i]]) ) body[[j+3]] <- as.name(names(sig[[i]])[j])
- }
- else {
- body <- quote( CONVENTION("EXTERNALNAME", PACKAGE=f, as.logical(ARG), as.integer(ARG),
- as.double(ARG), as.complex(ARG), as.character(ARG),
- as.character(ARG), as.double(ARG)) )[ c(1:3,types+3) ]
- names(body) <- c( NA, "name", "PACKAGE", names(sig[[i]]) )
- for ( j in seq(along = sig[[i]]) ) body[[j+3]][[2]] <- as.name(names(sig[[i]])[j])
- }
- body[[1]] <- as.name(convention)
- body[[2]] <- names(sig)[i]
- ## update the body of 'fn'
- body(fn)[[4]] <- body
- ## set fn as THE function in CFunc of res[[i]]
- res[[i]]@.Data <- fn
- }
-
- ## OUTPUT PROGRAM CODE IF DESIRED
- if ( verbose ) {
- cat("Program source:\n")
- lines <- strsplit(code, "\n")
- for ( i in 1:length(lines[[1]]) )
- cat(format(i,width=3), ": ", lines[[1]][i], "\n", sep="")
- }
-
- ## Remove unnecessary objects from the local environment
- remove(list = c("args", "body", "convention", "fn", "funCsig", "i", "includes", "j"))
-
- ## RETURN THE FUNCTION
- if (length(res) == 1 && names(res) == f) return( res[[1]] )
- else return( res )
-}
-
-# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
-compileCode <- function(f, code, language, verbose) {
- ## Prepare temp file names
- if ( .Platform$OS.type == "windows" ) {
- ## windows files
- dir <- gsub("\\\\", "/", tempdir())
- libCFile <- paste(dir, "/", f, ".EXT", sep="")
- libLFile <- paste(dir, "/", f, ".dll", sep="")
- libLFile2 <- paste(dir, "/", f, ".dll", sep="")
- }
- else {
- ## UNIX-alike build
- libCFile <- paste(tempdir(), "/", f, ".EXT", sep="")
- libLFile <- paste(tempdir(), "/", f, ".so", sep="")
- libLFile2 <- paste(tempdir(), "/", f, ".sl", sep="")
- }
- extension <- switch(language, "C++"=".cpp", C=".c", Fortran=".f", F95=".f95",
- ObjectiveC=".m", "ObjectiveC++"=".mm")
- libCFile <- sub(".EXT$", extension, libCFile)
-
- ## Write the code to the temp file for compilation
- write(code, libCFile)
-
- ## Compile the code using the running version of R if several available
- if ( file.exists(libLFile) ) file.remove( libLFile )
- if ( file.exists(libLFile2) ) file.remove( libLFile2 )
-
- cmd <- paste(R.home(component="bin"), "/R CMD SHLIB ", libCFile, sep="")
- if (verbose) cat("Compilation argument:\n", cmd, "\n")
- compiled <- system(cmd, intern=!verbose)
-
- if ( !file.exists(libLFile) && file.exists(libLFile2) ) libLFile <- libLFile2
- if ( !file.exists(libLFile) ) {
- cat("\nERROR(s) during compilation: source code errors or compiler configuration errors!\n")
- cat("\nProgram source:\n")
- code <- strsplit(code, "\n")
- for (i in 1:length(code[[1]])) cat(format(i,width=3), ": ", code[[1]][i], "\n", sep="")
- stop( "Compilation ERROR, function(s)/method(s) not created!" )
- }
- return( libLFile )
-}
-
-
-## -- also include cmethods.R here
-# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
-setGeneric( "setCMethod", function(f, sig, body, ...) standardGeneric("setCMethod") )
-
-# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
-setMethod( "setCMethod", signature(f="character", sig="list", body="list"),
- function(f, sig, body, includes="", otherdefs="",
- language=c("C++", "C", "Fortran", "F95", "ObjectiveC", "ObjectiveC++"),
- verbose=FALSE, convention=c(".Call", ".C", ".Fortran"),
- where=topenv(.GlobalEnv), ...) {
- if ( length(f) != length(sig) || length(sig) != length(body) )
- stop("number of signatures does not correspond to the number of code chunks")
-
- names(sig) <- f
- fns <- cfunction(sig, body, includes, otherdefs, language, verbose, convention)
-
- if ( verbose )
- cat("\nThe following methods are now defined:\n")
- ## Let's try to create generics
- for ( i in 1:length(f) ) {
- generic <- paste( "setGeneric(\"", f[i], "\", function(",
- paste(names(sig[[i]]),collapse=", "), ") standardGeneric(\"",
- f[i], "\"),where=where )", sep="")
- eval(parse(text=generic))
- setMethod(f[i], sig[[i]], fns[[i]], where=where)
- if ( verbose ) showMethods(f[i])
- }
- }
-)
-
-# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
-setMethod( "setCMethod", signature(f="character", sig="character", body="character"),
- function(f, sig, body, includes="", otherdefs="", language=c("C++", "C", "Fortran", "F95", "ObjectiveC", "ObjectiveC++"),
- verbose=FALSE, convention=c(".Call", ".C", ".Fortran"), where=topenv(.GlobalEnv), ...)
- setCMethod(f, list(sig), list(body), includes, otherdefs, language, verbose, convention, where=topenv(.GlobalEnv), ...)
-)
-
Modified: pkg/inst/examples/RcppInline/RcppInlineExample.r
===================================================================
--- pkg/inst/examples/RcppInline/RcppInlineExample.r 2009-12-27 17:16:28 UTC (rev 216)
+++ pkg/inst/examples/RcppInline/RcppInlineExample.r 2009-12-27 21:14:32 UTC (rev 217)
@@ -1,6 +1,7 @@
#!/usr/bin/r
suppressMessages(library(Rcpp))
+suppressMessages(library(inline))
foo <- '
SEXP rl = R_NilValue; // Use this when there is nothing to be returned.
Modified: pkg/inst/examples/RcppInline/RcppInlineWithLibsExamples.r
===================================================================
--- pkg/inst/examples/RcppInline/RcppInlineWithLibsExamples.r 2009-12-27 17:16:28 UTC (rev 216)
+++ pkg/inst/examples/RcppInline/RcppInlineWithLibsExamples.r 2009-12-27 21:14:32 UTC (rev 217)
@@ -1,6 +1,7 @@
#!/usr/bin/r -t
suppressMessages(library(Rcpp))
+suppressMessages(library(inline))
firstExample <- function() {
## a really simple C program calling three functions from the GSL
Modified: pkg/inst/examples/RcppInline/RcppSexpTests.r
===================================================================
--- pkg/inst/examples/RcppInline/RcppSexpTests.r 2009-12-27 17:16:28 UTC (rev 216)
+++ pkg/inst/examples/RcppInline/RcppSexpTests.r 2009-12-27 21:14:32 UTC (rev 217)
@@ -1,7 +1,6 @@
#!/usr/bin/r -t
#
-# Copyright (C) 2009 Dirk Eddelbuettel
-# Copyright (C) 2009 Romain Francois
+# Copyright (C) 2009 Dirk Eddelbuettel and Romain Francois
#
# This file is part of Rcpp.
#
@@ -19,6 +18,7 @@
# along with Rcpp. If not, see <http://www.gnu.org/licenses/>.
suppressMessages(library(Rcpp))
+suppressMessages(library(inline))
cat("===Doubles\n")
foo <- '
@@ -201,7 +201,7 @@
cat("\n=== set<double>\n")
foo <- '
std::set<double> ds;
-ds.insert( 0.0 );
+ds.insert( 0.0 );
ds.insert( 1.0 );
ds.insert( 0.0 );
return(RcppSexp( iv ).asSexp()); '
@@ -232,7 +232,7 @@
stopifnot( identical( res, c("bar","foo")) )
-#========= attributes
+#========= attributes
funx <- cfunction(
signature(x="data.frame"), '
Modified: pkg/inst/examples/RcppInline/RcppSimpleExample.r
===================================================================
--- pkg/inst/examples/RcppInline/RcppSimpleExample.r 2009-12-27 17:16:28 UTC (rev 216)
+++ pkg/inst/examples/RcppInline/RcppSimpleExample.r 2009-12-27 21:14:32 UTC (rev 217)
@@ -2,6 +2,7 @@
suppressMessages(library(Rcpp))
+suppressMessages(library(inline))
foo <- '
Modified: pkg/inst/examples/RcppInline/RcppSimpleTests.r
===================================================================
--- pkg/inst/examples/RcppInline/RcppSimpleTests.r 2009-12-27 17:16:28 UTC (rev 216)
+++ pkg/inst/examples/RcppInline/RcppSimpleTests.r 2009-12-27 21:14:32 UTC (rev 217)
@@ -1,6 +1,7 @@
#!/usr/bin/r
suppressMessages(library(Rcpp))
+suppressMessages(library(inline))
foo <- '
Modified: pkg/inst/examples/RcppInline/UncaughtExceptions.r
===================================================================
--- pkg/inst/examples/RcppInline/UncaughtExceptions.r 2009-12-27 17:16:28 UTC (rev 216)
+++ pkg/inst/examples/RcppInline/UncaughtExceptions.r 2009-12-27 21:14:32 UTC (rev 217)
@@ -17,7 +17,8 @@
# You should have received a copy of the GNU General Public License
# along with Rcpp. If not, see <http://www.gnu.org/licenses/>.
-require( Rcpp)
+require(Rcpp)
+require(inline)
funx <- cfunction(signature(), '
throw std::range_error("boom") ;
return R_NilValue ;
Deleted: pkg/man/RcppInline.Rd
===================================================================
--- pkg/man/RcppInline.Rd 2009-12-27 17:16:28 UTC (rev 216)
+++ pkg/man/RcppInline.Rd 2009-12-27 21:14:32 UTC (rev 217)
@@ -1,240 +0,0 @@
-\name{cfunction}
-
-\alias{cfunction}
-\alias{setCMethod}
-\alias{inline}
-
-\concept{inline function call}
-
-\title{ Inline C, C++, Fortran function calls from R }
-
-\description{
- Functionality to dynamically define R functions and S4 methods with in-lined C,
- C++ or Fortran code supporting .C and .Call calling conventions.
-}
-
-\usage{
- cfunction(sig=character(), body=character(), includes=character(),
- otherdefs=character(),
- language=c("C++", "C", "Fortran", "F95", "ObjectiveC", "ObjectiveC++"),
- verbose=FALSE,
- convention=c(".Call", ".C", ".Fortran"),
- Rcpp=FALSE,
- cppargs=character(), cxxargs=character(), libargs=character())
-
- ## S4 methods for signatures
- # f='character', sig='list', body='list'
- # f='character', sig='character', body='character'
-
- setCMethod(f, sig, body, ...)
-
- ## Further arguments:
- # setCMethod(f, sig, body, includes="", otherdefs="", cpp=TRUE, verbose=FALSE, where=topenv(.GlobalEnv), ...)
-}
-
-\arguments{
- \item{f}{A single character value if \code{sig} and \code{body} are character vectors
- or a character vector of the same length and the length of \code{sig} or
- \code{body} with the name(s) of methods to create.}
-
- \item{sig}{A match of formal argument names for the function with the
- character-string names of corresponding classes. Alternatively,
- a list of such character vectors. }
-
- \item{body}{ A character vector with C, C++ or Fortran code omitting function
- declaration (only the body, i.e. in case of C starting after the function
- opening curly bracket and ending before the closing curly bracket,
- brackets excluded). In case of \code{setCMethod} with signature
- \code{list} -- a list of such character vectors. }
-
- \item{includes}{ A character vector of additional includes and preprocessor
- statements etc that will be put between the R includes and the user function(s).}
-
- \item{otherdefs}{ A characted vector with the code for any further definitions of
- functions, classes, types, forward declarations, namespace usage clauses etc
- which is inserted between the includes and the declarations of the functions
- defined in \code{sig}.}
-
- \item{language}{ A character value that specifies the source language of the
- inline code. The possible values for \code{language} include all those
- supported by \code{R CMD SHLIB} on any platform, which are currently C,
- C++, Fortran, F95, ObjectiveC and ObjectiveC++; they may not all be supported
- on your platform. One can specify the language either in full as above, or
- using any of the following case insensitive shortened forms: \code{c, cpp,
- c++, f, f95, objc, objcpp, objc++}. Defaults to \code{C++}.}
-
- \item{verbose}{ If \code{TRUE} prints the compilation output, the source
- code of the resulting program and the definitions of all declared
- methods. If \code{FALSE}, the function is silent, but it prints compiler
- warning and error messages and the source code if compilation fails. }
-
- \item{convention}{ Which calling convention to use? See the Details section.}
-
- \item{Rcpp}{If \code{TRUE} adds inclusion of \code{Rcpp.h} to
- \code{includes}, also queries the \code{Rcpp} package about
- the location of header and library files and sets environment
- variables \code{PKG_CXXFLAGS} and \code{PKG_LIBS} accordingly so that
- the R / C++ interface provided by the \code{Rcpp} package can be
- used. Default value is \code{FALSE}.}
-
- \item{cppargs}{Optional character vector of tokens to be passed to
- the compiler via the \code{PKG_CPPFLAGS} environment
- variable. Elements should be fully formed as for example
- \code{c("-I/usr/local/lib/foo", "-DDEBUG")} and are passed along verbatim.}
-
- \item{cxxargs}{Optional character vector of tokens to be passed to
- the compiler via the \code{PKG_CXXFLAGS} environment
- variable. Elements should be fully formed as for example
- \code{c("-I/usr/local/lib/foo", "-DDEBUG")} and are passed along verbatim.}
-
- \item{libargs}{Optional character vector of tokens to be passed to the
- compiler via the \code{PKG_LIBS} environment variable. Elements should
- be fully formed as for example \code{c("-L/usr/local/lib/foo -lfoo",
- "--lpthread")} and are passed along verbatim.}
-
- \item{...}{ Reserved.}
-}
-
-\value{
- If \code{sig} is a single character vector, \code{cfunction} returns a single
- \code{\link{function}}; if it is a list, it returns a list of functions.
-
- \code{setCMethod} declares new methods with given names and signatures and
- returns invisible \code{NULL}.
-}
-
-\details{
-
- To declare multiple functions in the same library one can use \code{setCMethod}
- supplying lists of signatures and implementations. In this case, provide as
- many method names in \code{f} as you define methods. Avoid clashes when selecting
- names of the methods to declare, i.e. if you provide the same name several times
- you must ensure that signatures are different but can share the same generic!
-
- The source code in the \code{body} should not include the header or
- "front-matter" of the function or the close, e.g. in C or C++ it
- must start after the C-function opening curly bracket and end before
- the C-function closing curly bracket, brackets should not be
- included. The header will be automatically generated from the R-\code{signature}
- argument. Arguments will will carry the same name as used in the signature,
- so avoid variable names that are not legal in the target language
- (e.g. names with dots).
-
- C/C++: If \code{convention == ".Call"} (the default), the \code{\link{.Call}} mechanism
- is used and its result is returned directly as the result of the call of the
- generated function. As the last line of the generated C/C++ code a
- \code{return R_NilValue;} is added in this case and a warning is generated
- in case the user has forgotten to provide a return value. To suppress the
- warning and still return NULL, add \code{return R_NilValue;} explicitly.
-
- Special care is needed with types, memory allocation and protection
- -- exactly the same as if the code was not inline: see the
- Writing R Extension manual for information on \code{\link{.Call}}.
-
- If \code{convention == ".C"} or \code{convention == ".Fortran"}, the
- \code{\link{.C}} or \code{\link{.Fortran}} mechanism respectively is
- used, and the return value is a list containing all arguments.
-
- Attached R includes include \code{R.h} for \code{".C"}, and
- additionally \code{Rdefines.h} and \code{R_ext\\Error.h} for
- \code{".Call"}.
-
- Note: This has been adapted from the \code{inline} package, and a
- patch has been submitted to Oleg Sklyar, its principal author. If the
- patch is included in \code{inline} the functionality will likely be
- removed here.
-}
-
-\seealso{ \code{
- \link{Foreign} Function Interface
-}}
-
-\examples{
-
-## A simple Fortran example
-code <- "
- integer i
- do 1 i=1, n(1)
- 1 x(i) = x(i)**3
-"
-cubefn <- cfunction(signature(n="integer", x="numeric"), code, convention=".Fortran")
-
-x <- as.numeric(1:10)
-n <- as.integer(10)
-cubefn(n, x)$x
-
-## Use of .C convention with C code
-## Defining two functions, one of which calls the other
-sigSq <- signature(n="integer", x="numeric")
-codeSq <- "
- for (int i=0; i < *n; i++) {
- x[i] = x[i]*x[i];
- }"
-sigQd <- signature(n="integer", x="numeric")
-codeQd <- "
- squarefn(n, x);
- squarefn(n, x);
-"
-
-fns <- cfunction( list(squarefn=sigSq, quadfn=sigQd),
- list(codeSq, codeQd),
- convention=".C")
-
-squarefn <- fns[["squarefn"]]
-quadfn <- fns[["quadfn"]]
-
-squarefn(n, x)$x
-quadfn(n, x)$x
-
-## Alternative declaration using 'setCMethod'
-setCMethod(c("squarefn", "quadfn"), list(sigSq, sigQd),
- list(codeSq, codeQd), convention=".C")
-
-squarefn(n, x)$x
-quadfn(n, x)$x
-
-## Use of .Call convention with C code
-## Multyplying each image in a stack with a 2D Gaussian at a given position
-code <- "
- SEXP res;
- int nprotect = 0, nx, ny, nz, x, y;
- PROTECT(res = Rf_duplicate(a)); nprotect++;
- nx = INTEGER(GET_DIM(a))[0];
- ny = INTEGER(GET_DIM(a))[1];
- nz = INTEGER(GET_DIM(a))[2];
- double sigma2 = REAL(s)[0] * REAL(s)[0], d2 ;
- double cx = REAL(centre)[0], cy = REAL(centre)[1], *data, *rdata;
- for (int im = 0; im < nz; im++) {
- data = &(REAL(a)[im*nx*ny]); rdata = &(REAL(res)[im*nx*ny]);
- for (x = 0; x < nx; x++)
- for (y = 0; y < ny; y++) {
- d2 = (x-cx)*(x-cx) + (y-cy)*(y-cy);
- rdata[x + y*nx] = data[x + y*nx] * exp(-d2/sigma2);
- }
- }
- UNPROTECT(nprotect);
- return res;
-"
-funx <- cfunction(signature(a="array", s="numeric", centre="numeric"), code)
-
-x <- array(runif(50*50), c(50,50,1))
-res <- funx(a=x, s=10, centre=c(25,15))
-if (interactive()) image(res[,,1])
-
-## Same but done by registering an S4 method
-setCMethod("funy", signature(a="array", s="numeric", centre="numeric"), code, verbose=TRUE)
-
-res <- funy(x, 10, c(35,35))
-if (interactive()) { x11(); image(res[,,1]) }
-
-}
-
-\author{
- Oleg Sklyar <\email{osklyar at ebi.ac.uk}>
- Duncan Murdoch
- Mike Smith;
- Dirk Eddelbuettel for the Rcpp adatation
-}
-
-\keyword{file}
-
Deleted: pkg/man/internals.Rd
===================================================================
--- pkg/man/internals.Rd 2009-12-27 17:16:28 UTC (rev 216)
+++ pkg/man/internals.Rd 2009-12-27 21:14:32 UTC (rev 217)
@@ -1,15 +0,0 @@
-\name{internals}
-\alias{internals}
-
-\alias{setCMethod,character,list,list-method}
-\alias{setCMethod,character,character,character-method}
-
-\title{ Internals }
-
-\description{
- Aliases required for 'R CMD check' but those noone will ever search for.
- Here to prevent the mess of the index. The corresponding items have help
- aliases without method signature!
-}
-
-\keyword{internal}
More information about the Rcpp-commits
mailing list