[Rcpp-commits] r1325 - pkg/Rcpp pkg/Rcpp/R pkg/Rcpp/inst pkg/Rcpp/inst/include/Rcpp pkg/Rcpp/inst/include/Rcpp/module pkg/Rcpp/src scripts

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Wed May 26 16:18:00 CEST 2010


Author: romain
Date: 2010-05-26 16:17:59 +0200 (Wed, 26 May 2010)
New Revision: 1325

Added:
   pkg/Rcpp/inst/include/Rcpp/module/Module_generated_CppMethod.h
   pkg/Rcpp/inst/include/Rcpp/module/Module_generated_method.h
   scripts/generator_Module_CppMethod.R
   scripts/generator_Module_method.R
Modified:
   pkg/Rcpp/NAMESPACE
   pkg/Rcpp/R/Module.R
   pkg/Rcpp/inst/ChangeLog
   pkg/Rcpp/inst/include/Rcpp/Module.h
   pkg/Rcpp/inst/include/Rcpp/config.h
   pkg/Rcpp/src/Module.cpp
Log:
more support for exposing C++ classes to R

Modified: pkg/Rcpp/NAMESPACE
===================================================================
--- pkg/Rcpp/NAMESPACE	2010-05-25 19:52:17 UTC (rev 1324)
+++ pkg/Rcpp/NAMESPACE	2010-05-26 14:17:59 UTC (rev 1325)
@@ -4,9 +4,11 @@
 export(cppfunction)
 
 importFrom( utils, capture.output )
+importFrom( methods, new )
 
 importFrom( inline, cfunction )
 
-# exportClasses( Module )
-# export( Module )
+exportClasses( Module, "C++Class", "C++Object" )
+export( Module )
+exportMethods( new )
 

Modified: pkg/Rcpp/R/Module.R
===================================================================
--- pkg/Rcpp/R/Module.R	2010-05-25 19:52:17 UTC (rev 1324)
+++ pkg/Rcpp/R/Module.R	2010-05-26 14:17:59 UTC (rev 1325)
@@ -15,8 +15,11 @@
 # You should have received a copy of the GNU General Public License
 # along with Rcpp.  If not, see <http://www.gnu.org/licenses/>.
 
-# not yet
+setGeneric( "new" )
+
 setClass( "Module", representation( pointer = "externalptr" ) )
+setClass( "C++Class", representation( module = "externalptr", name = "character" ) )
+setClass( "C++Object", representation( module = "externalptr", cppclass = "externalptr", pointer = "externalptr" ) )
 
 Module <- function( module, PACKAGE ){
 	name <- sprintf( "_rcpp_module_boot_%s", module )
@@ -26,9 +29,15 @@
 }
 
 setMethod( "$", "Module", function(x, name){
-	function( ... ) {
-		res <- .External(  "Module__invoke" , x at pointer, name, ..., PACKAGE = "Rcpp"  )
-		if( isTRUE( res$void ) ) invisible(NULL) else res$result	
+	if( .Call( "Module__has_function", x at pointer, name, PACKAGE = "Rcpp" ) ){
+		function( ... ) {
+			res <- .External(  "Module__invoke" , x at pointer, name, ..., PACKAGE = "Rcpp"  )
+			if( isTRUE( res$void ) ) invisible(NULL) else res$result	
+		}
+	} else if( .Call("Module__has_class", x at pointer, name, PACKAGE = "Rcpp" ) ){
+		.Call( "Module__get_class", x at pointer, name, PACKAGE = "Rcpp" )  
+	} else{
+		stop( "no such method or class in module" )
 	}
 } )
 
@@ -36,10 +45,31 @@
 	info <- .Call( "Module__funtions_arity", object at pointer, PACKAGE = "Rcpp" )
 	name <- .Call( "Module__name", object at pointer )
 	txt <- sprintf( "Rcpp module '%s' \n\t%d functions: ", name, length(info) )
-	writeLines( txt )
+	writeLines( txt )           
 	txt <- sprintf( "%15s : %d arguments", names(info), info )
 	writeLines( txt )
+	                                                     
+	info <- .Call( "Module__classes_info", object at pointer, PACKAGE = "Rcpp" )
+	txt <- sprintf( "\n\t%d classes : ", length(info) )
+	writeLines( txt )
+	txt <- sprintf( "%15s ", names(info) )
+	writeLines( txt )
 } )
 
 #TODO: maybe attach( Module ), with( Module )
 
+setMethod( "new", "C++Class", function(Class, ...){
+	.External( "Module__class__newInstance", Class at module, Class at name, ..., PACKAGE = "Rcpp" )
+} )
+
+setMethod( "$", "C++Object", function(x, name){
+	if( .Call( "Class__has_method", x at cppclass, name, PACKAGE = "Rcpp" ) ){
+		function(...){
+			res <- .External( "Class__invoke_method", x at module, x at cppclass, name, x at pointer, ..., PACKAGE = "Rcpp" )
+			if( isTRUE( res$void ) ) invisible(NULL) else res$result
+		}
+	} else{
+		stop( "no such method" )
+	}
+} )
+

Modified: pkg/Rcpp/inst/ChangeLog
===================================================================
--- pkg/Rcpp/inst/ChangeLog	2010-05-25 19:52:17 UTC (rev 1324)
+++ pkg/Rcpp/inst/ChangeLog	2010-05-26 14:17:59 UTC (rev 1325)
@@ -1,3 +1,11 @@
+2010-05-26  Romain Francois <romain at r-enthusiasts.com>
+
+	* inst/include/Rcpp/Module.h: 
+	* src/Module.cpp : limited support for exposing c++ classes in Rcpp modules
+	
+	* R/Module.R : classes "C++Class", "C++Object" holding external pointers
+	and $ method dispatching internally
+
 2010-05-24  Dirk Eddelbuettel  <edd at debian.org>
 
 	* src/Rcpp*.cpp: Moved template code from the older API to headers

Modified: pkg/Rcpp/inst/include/Rcpp/Module.h
===================================================================
--- pkg/Rcpp/inst/include/Rcpp/Module.h	2010-05-25 19:52:17 UTC (rev 1324)
+++ pkg/Rcpp/inst/include/Rcpp/Module.h	2010-05-26 14:17:59 UTC (rev 1325)
@@ -27,6 +27,9 @@
 
 namespace Rcpp{
 
+class CppClass ;
+class CppObject ;
+
 class CppFunction {
 	public:
 		CppFunction() {}
@@ -45,11 +48,16 @@
 
 class class_Base {
 public:
+	class_Base() :name(){} ;
 	class_Base(const char* name_) : name(name_){} ;
 	
-	virtual SEXP invoke( const std::string& method_name, SEXP *args, int nargs ) = 0 ;
+	virtual bool has_method( const std::string& m ){ return false ; }
+	virtual SEXP newInstance(SEXP *args, int nargs){  return R_NilValue; }
+	virtual SEXP invoke( const std::string& method_name, SEXP obj, SEXP *args, int nargs ){ 
+		return R_NilValue ;
+	}
+	virtual ~class_Base(){}
 	
-private:
 	std::string name ;
 } ;
 
@@ -61,32 +69,16 @@
 		typedef std::map<std::string,class_Base*> CLASS_MAP ;
 		typedef std::pair<const std::string,class_Base*> CLASS_PAIR ;
 	
-		Module() : name(), functions() {}
-		Module(const char* name_) : name(name_), functions(), classes() {}
+		Module()  ;
+		Module(const char* name_)  ;
 		      
-		SEXP invoke( const std::string& name, SEXP* args, int nargs){
-			try{
-				MAP::iterator it = functions.find( name );
-				if( it == functions.end() ){
-					throw std::range_error( "no such function" ) ; 
-				}
-				CppFunction* fun = it->second ;
-				if( fun->nargs() > nargs ){
-					throw std::range_error( "incorrect number of arguments" ) ; 	
-				}
-				 
-				return Rcpp::List::create( 
-					Rcpp::Named("result") = fun->operator()( args ), 
-					Rcpp::Named("void")   = fun->is_void() 
-				) ;
-			} catch( std::exception& __ex__ ){
-				forward_exception_to_r( __ex__ ); 
-			}
-			return R_NilValue ; // -Wall
-		}                                                                                  
+		SEXP invoke( const std::string& name, SEXP* args, int nargs) ;                        
+		SEXP newClassInstance( const std::string& clazz, SEXP* args, int nargs) ;                        
+		SEXP invokeMethod( const std::string& clazz, const std::string& meth, SEXP obj, SEXP* args, int nargs ) ;
 		
 		Rcpp::IntegerVector functions_arity() ;
 		Rcpp::CharacterVector class_names() ;
+		Rcpp::List classes_info() ;
 		
 		inline void Add( const char* name, CppFunction* ptr){
 			functions.insert( FUNCTION_PAIR( name, ptr ) ) ;
@@ -96,6 +88,16 @@
 			classes.insert( CLASS_PAIR( name, cptr ) ) ;
 		}
 
+		inline bool has_function( const std::string& m){
+			return functions.find(m) != functions.end() ;
+		}
+		
+		inline bool has_class( const std::string& m){
+			return classes.find(m) != classes.end() ;
+		}
+		
+		Rcpp::CppClass get_class(const std::string& ) ;
+		
 		std::string name ;
 		
 	private:
@@ -113,55 +115,96 @@
 template <typename Class>
 class CppMethod {
 	public:
+		typedef Rcpp::XPtr<Class> XP ;   
+	
 		CppMethod() {}
-		virtual SEXP operator()(SEXP* args) { return R_NilValue ; }
+		virtual SEXP operator()(Class* object, SEXP* args) { return R_NilValue ; }
 		virtual ~CppMethod(){}
 		virtual int nargs(){ return 0 ; }
 		virtual bool is_void(){ return false ; }
 	
 } ;
 
+#include <Rcpp/module/Module_generated_CppMethod.h>
+
+
 template <typename Class>
 class class_ : public class_Base {
 public:
-	typedef class_ self ;
-	typedef CppMethod<Class> method ;
-	typedef std::map<std::string,method*> METHOD_MAP ;
-	typedef std::pair<const std::string,method*> PAIR ;
+	typedef class_<Class> self ;
+	typedef CppMethod<Class> method_class ;
+	typedef std::map<std::string,method_class*> METHOD_MAP ;
+	typedef std::pair<const std::string,method_class*> PAIR ;
+	typedef Rcpp::XPtr<Class> XP ;   
 	
 	class_( const char* name_ ) : class_Base(name_), methods() {
-		getCurrentScope()->AddClass( name_, this ) ;
+		if( !singleton ){
+			singleton = new self ;
+			singleton->name = name_ ;
+			getCurrentScope()->AddClass( name_, singleton ) ;
+		}
 	}
 	
-	SEXP invoke( const std::string& method_name, SEXP *args, int nargs ){ 
+	SEXP newInstance( SEXP* args, int nargs ){
+		SEXP out = XP( new Class, true ) ;
+		return out ;
+	}
+	
+	SEXP invoke( const std::string& method_name, SEXP object, SEXP *args, int nargs ){ 
 		BEGIN_RCPP
-			typename METHOD_MAP::iterator it = methods.find( method_name ) ;
-			if( it == methods.end() ){
-				throw std::range_error( "no such method" ) ; 
-			}
-			method* met =  it->second ;
-			if( met->nargs() > nargs ){
-				throw std::range_error( "incorrect number of arguments" ) ; 	
-			}
-			return Rcpp::List::create( 
-					Rcpp::Named("result") = met->operator()( args ), 
-					Rcpp::Named("void")   = met->is_void() 
-				) ;
+		typename METHOD_MAP::iterator it = methods.find( method_name ) ;
+		if( it == methods.end() ){
+			throw std::range_error( "no such method" ) ; 
+		}
+		method_class* met =  it->second ;
+		if( met->nargs() > nargs ){
+			throw std::range_error( "incorrect number of arguments" ) ; 	
+		}
+		return Rcpp::List::create( 
+				Rcpp::Named("result") = met->operator()( XP(object), args ), 
+				Rcpp::Named("void")   = met->is_void() 
+			) ;
 		END_RCPP	
 	}
 	
-	self& AddMethod( const char* name, method* m){
-		methods.insert( PAIR( name,m ) ) ;  
+	self& AddMethod( const char* name, method_class* m){
+		singleton->methods.insert( PAIR( name,m ) ) ;  
 		return *this ;
 	}
+
+#include <Rcpp/module/Module_generated_method.h>
+		
+	inline bool has_method( const std::string& m){
+		return methods.find(m) != methods.end() ;
+	}
 	
 private:
 	METHOD_MAP methods ;
-} ;
+	static self* singleton ;
+	
+	class_( ) : class_Base(), methods(){}; 
+	
+} ;   
 
+template <typename Class> 
+class_<Class>* class_<Class>::singleton ;
+
+
 // function factories
 #include <Rcpp/module/Module_generated_function.h>
 
+class CppClass : public S4{
+public:
+	typedef Rcpp::XPtr<Rcpp::Module> XP ;
+	CppClass( Module* p, const std::string& name ) ;
+} ;
+
+class CppObject : public S4{
+public:
+	typedef Rcpp::XPtr<Rcpp::Module> XP ;
+	CppObject( Module* p, class_Base*, SEXP xp ) ;
+} ;
+
 }
 
 

Modified: pkg/Rcpp/inst/include/Rcpp/config.h
===================================================================
--- pkg/Rcpp/inst/include/Rcpp/config.h	2010-05-25 19:52:17 UTC (rev 1324)
+++ pkg/Rcpp/inst/include/Rcpp/config.h	2010-05-26 14:17:59 UTC (rev 1325)
@@ -23,7 +23,7 @@
 #define RCPP__CONFIG_H
 
 // comment to disable Rcpp modules
-// #define RCPP_ENABLE_MODULES
+#define RCPP_ENABLE_MODULES
 
 #endif
 

Added: pkg/Rcpp/inst/include/Rcpp/module/Module_generated_CppMethod.h
===================================================================
--- pkg/Rcpp/inst/include/Rcpp/module/Module_generated_CppMethod.h	                        (rev 0)
+++ pkg/Rcpp/inst/include/Rcpp/module/Module_generated_CppMethod.h	2010-05-26 14:17:59 UTC (rev 1325)
@@ -0,0 +1,2331 @@
+// -*- mode: C++; c-indent-level: 4; c-basic-offset: 4; tab-width: 8 -*-
+//
+// Module_generated_CppMethod.h: Rcpp R/C++ interface class library -- Rcpp modules
+//
+// Copyright (C) 2010	Dirk Eddelbuettel and Romain Francois
+//
+// This file is part of Rcpp.
+//
+// Rcpp is free software: you can redistribute it and/or modify it
+// under the terms of the GNU General Public License as published by
+// the Free Software Foundation, either version 2 of the License, or
+// (at your option) any later version.
+//
+// Rcpp is distributed in the hope that it will be useful, but
+// WITHOUT ANY WARRANTY; without even the implied warranty of
+// MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
+// GNU General Public License for more details.
+//
+// You should have received a copy of the GNU General Public License
+// along with Rcpp.  If not, see <http://www.gnu.org/licenses/>.
+
+#ifndef Rcpp_Module_generated_CppMethod_h
+#define Rcpp_Module_generated_CppMethod_h
+
+	template <typename Class, typename OUT> class CppMethod0 : public CppMethod<Class> {
+	public:
+		typedef OUT (Class::*Method)(void) ;
+		typedef CppMethod<Class> method_class ;
+		CppMethod0( Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			return Rcpp::wrap( (object->*met)( ) ) ;
+		}
+		inline int nargs(){ return 0 ; }
+		inline bool is_void(){ return false ; }
+	private:
+		Method met ;
+	} ;
+	
+	template <typename Class> class CppMethod0<Class,void> : public CppMethod<Class> {
+	public:
+		typedef void (Class::*Method)(void) ;
+		typedef CppMethod<Class> method_class ;
+		CppMethod0( Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			(object->*met)( ) ;
+			return R_NilValue ;
+		}
+		inline int nargs(){ return 0 ; }
+		inline bool is_void(){ return true ; }
+	private:
+		Method met ;
+	} ;
+
+
+
+	template < typename Class, typename OUT, typename U0 > class CppMethod1 : public CppMethod<Class> {
+	public:
+		typedef OUT (Class::*Method)(U0 u0) ;
+		typedef CppMethod<Class> method_class ;
+		
+		CppMethod1(Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			return Rcpp::wrap( (object->*met)( Rcpp::as<U0>( args[0] ) ) ) ;
+		}
+		inline int nargs(){ return 1 ; }
+		inline bool is_void(){ return false ; }
+	private:
+		Method met ;
+	} ;
+	
+	template < typename Class, typename U0 > class CppMethod1<Class,void,U0> : public CppMethod<Class> {
+	public:
+		typedef void (Class::*Method)(U0 u0) ;
+		typedef CppMethod<Class> method_class ;
+		
+		CppMethod1( Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			(object->*met)( Rcpp::as<U0>( args[0] ) ) ;
+			return R_NilValue ;
+		}
+		inline int nargs(){ return 1 ; }
+		inline bool is_void(){ return true ; }
+	private:
+		Method met ;
+	} ;
+
+
+
+
+
+	template < typename Class, typename OUT, typename U0, typename U1 > class CppMethod2 : public CppMethod<Class> {
+	public:
+		typedef OUT (Class::*Method)(U0 u0, U1 u1) ;
+		typedef CppMethod<Class> method_class ;
+		
+		CppMethod2(Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			return Rcpp::wrap( (object->*met)( Rcpp::as<U0>( args[0] ), Rcpp::as<U1>( args[1] ) ) ) ;
+		}
+		inline int nargs(){ return 2 ; }
+		inline bool is_void(){ return false ; }
+	private:
+		Method met ;
+	} ;
+	
+	template < typename Class, typename U0, typename U1 > class CppMethod2<Class,void,U0, U1> : public CppMethod<Class> {
+	public:
+		typedef void (Class::*Method)(U0 u0, U1 u1) ;
+		typedef CppMethod<Class> method_class ;
+		
+		CppMethod2( Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			(object->*met)( Rcpp::as<U0>( args[0] ), Rcpp::as<U1>( args[1] ) ) ;
+			return R_NilValue ;
+		}
+		inline int nargs(){ return 2 ; }
+		inline bool is_void(){ return true ; }
+	private:
+		Method met ;
+	} ;
+
+
+
+
+
+	template < typename Class, typename OUT, typename U0, typename U1, typename U2 > class CppMethod3 : public CppMethod<Class> {
+	public:
+		typedef OUT (Class::*Method)(U0 u0, U1 u1, U2 u2) ;
+		typedef CppMethod<Class> method_class ;
+		
+		CppMethod3(Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			return Rcpp::wrap( (object->*met)( Rcpp::as<U0>( args[0] ), Rcpp::as<U1>( args[1] ), Rcpp::as<U2>( args[2] ) ) ) ;
+		}
+		inline int nargs(){ return 3 ; }
+		inline bool is_void(){ return false ; }
+	private:
+		Method met ;
+	} ;
+	
+	template < typename Class, typename U0, typename U1, typename U2 > class CppMethod3<Class,void,U0, U1, U2> : public CppMethod<Class> {
+	public:
+		typedef void (Class::*Method)(U0 u0, U1 u1, U2 u2) ;
+		typedef CppMethod<Class> method_class ;
+		
+		CppMethod3( Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			(object->*met)( Rcpp::as<U0>( args[0] ), Rcpp::as<U1>( args[1] ), Rcpp::as<U2>( args[2] ) ) ;
+			return R_NilValue ;
+		}
+		inline int nargs(){ return 3 ; }
+		inline bool is_void(){ return true ; }
+	private:
+		Method met ;
+	} ;
+
+
+
+
+
+	template < typename Class, typename OUT, typename U0, typename U1, typename U2, typename U3 > class CppMethod4 : public CppMethod<Class> {
+	public:
+		typedef OUT (Class::*Method)(U0 u0, U1 u1, U2 u2, U3 u3) ;
+		typedef CppMethod<Class> method_class ;
+		
+		CppMethod4(Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			return Rcpp::wrap( (object->*met)( Rcpp::as<U0>( args[0] ), Rcpp::as<U1>( args[1] ), Rcpp::as<U2>( args[2] ), Rcpp::as<U3>( args[3] ) ) ) ;
+		}
+		inline int nargs(){ return 4 ; }
+		inline bool is_void(){ return false ; }
+	private:
+		Method met ;
+	} ;
+	
+	template < typename Class, typename U0, typename U1, typename U2, typename U3 > class CppMethod4<Class,void,U0, U1, U2, U3> : public CppMethod<Class> {
+	public:
+		typedef void (Class::*Method)(U0 u0, U1 u1, U2 u2, U3 u3) ;
+		typedef CppMethod<Class> method_class ;
+		
+		CppMethod4( Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			(object->*met)( Rcpp::as<U0>( args[0] ), Rcpp::as<U1>( args[1] ), Rcpp::as<U2>( args[2] ), Rcpp::as<U3>( args[3] ) ) ;
+			return R_NilValue ;
+		}
+		inline int nargs(){ return 4 ; }
+		inline bool is_void(){ return true ; }
+	private:
+		Method met ;
+	} ;
+
+
+
+
+
+	template < typename Class, typename OUT, typename U0, typename U1, typename U2, typename U3, typename U4 > class CppMethod5 : public CppMethod<Class> {
+	public:
+		typedef OUT (Class::*Method)(U0 u0, U1 u1, U2 u2, U3 u3, U4 u4) ;
+		typedef CppMethod<Class> method_class ;
+		
+		CppMethod5(Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			return Rcpp::wrap( (object->*met)( Rcpp::as<U0>( args[0] ), Rcpp::as<U1>( args[1] ), Rcpp::as<U2>( args[2] ), Rcpp::as<U3>( args[3] ), Rcpp::as<U4>( args[4] ) ) ) ;
+		}
+		inline int nargs(){ return 5 ; }
+		inline bool is_void(){ return false ; }
+	private:
+		Method met ;
+	} ;
+	
+	template < typename Class, typename U0, typename U1, typename U2, typename U3, typename U4 > class CppMethod5<Class,void,U0, U1, U2, U3, U4> : public CppMethod<Class> {
+	public:
+		typedef void (Class::*Method)(U0 u0, U1 u1, U2 u2, U3 u3, U4 u4) ;
+		typedef CppMethod<Class> method_class ;
+		
+		CppMethod5( Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			(object->*met)( Rcpp::as<U0>( args[0] ), Rcpp::as<U1>( args[1] ), Rcpp::as<U2>( args[2] ), Rcpp::as<U3>( args[3] ), Rcpp::as<U4>( args[4] ) ) ;
+			return R_NilValue ;
+		}
+		inline int nargs(){ return 5 ; }
+		inline bool is_void(){ return true ; }
+	private:
+		Method met ;
+	} ;
+
+
+
+
+
+	template < typename Class, typename OUT, typename U0, typename U1, typename U2, typename U3, typename U4, typename U5 > class CppMethod6 : public CppMethod<Class> {
+	public:
+		typedef OUT (Class::*Method)(U0 u0, U1 u1, U2 u2, U3 u3, U4 u4, U5 u5) ;
+		typedef CppMethod<Class> method_class ;
+		
+		CppMethod6(Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			return Rcpp::wrap( (object->*met)( Rcpp::as<U0>( args[0] ), Rcpp::as<U1>( args[1] ), Rcpp::as<U2>( args[2] ), Rcpp::as<U3>( args[3] ), Rcpp::as<U4>( args[4] ), Rcpp::as<U5>( args[5] ) ) ) ;
+		}
+		inline int nargs(){ return 6 ; }
+		inline bool is_void(){ return false ; }
+	private:
+		Method met ;
+	} ;
+	
+	template < typename Class, typename U0, typename U1, typename U2, typename U3, typename U4, typename U5 > class CppMethod6<Class,void,U0, U1, U2, U3, U4, U5> : public CppMethod<Class> {
+	public:
+		typedef void (Class::*Method)(U0 u0, U1 u1, U2 u2, U3 u3, U4 u4, U5 u5) ;
+		typedef CppMethod<Class> method_class ;
+		
+		CppMethod6( Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			(object->*met)( Rcpp::as<U0>( args[0] ), Rcpp::as<U1>( args[1] ), Rcpp::as<U2>( args[2] ), Rcpp::as<U3>( args[3] ), Rcpp::as<U4>( args[4] ), Rcpp::as<U5>( args[5] ) ) ;
+			return R_NilValue ;
+		}
+		inline int nargs(){ return 6 ; }
+		inline bool is_void(){ return true ; }
+	private:
+		Method met ;
+	} ;
+
+
+
+
+
+	template < typename Class, typename OUT, typename U0, typename U1, typename U2, typename U3, typename U4, typename U5, typename U6 > class CppMethod7 : public CppMethod<Class> {
+	public:
+		typedef OUT (Class::*Method)(U0 u0, U1 u1, U2 u2, U3 u3, U4 u4, U5 u5, U6 u6) ;
+		typedef CppMethod<Class> method_class ;
+		
+		CppMethod7(Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			return Rcpp::wrap( (object->*met)( Rcpp::as<U0>( args[0] ), Rcpp::as<U1>( args[1] ), Rcpp::as<U2>( args[2] ), Rcpp::as<U3>( args[3] ), Rcpp::as<U4>( args[4] ), Rcpp::as<U5>( args[5] ), Rcpp::as<U6>( args[6] ) ) ) ;
+		}
+		inline int nargs(){ return 7 ; }
+		inline bool is_void(){ return false ; }
+	private:
+		Method met ;
+	} ;
+	
+	template < typename Class, typename U0, typename U1, typename U2, typename U3, typename U4, typename U5, typename U6 > class CppMethod7<Class,void,U0, U1, U2, U3, U4, U5, U6> : public CppMethod<Class> {
+	public:
+		typedef void (Class::*Method)(U0 u0, U1 u1, U2 u2, U3 u3, U4 u4, U5 u5, U6 u6) ;
+		typedef CppMethod<Class> method_class ;
+		
+		CppMethod7( Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			(object->*met)( Rcpp::as<U0>( args[0] ), Rcpp::as<U1>( args[1] ), Rcpp::as<U2>( args[2] ), Rcpp::as<U3>( args[3] ), Rcpp::as<U4>( args[4] ), Rcpp::as<U5>( args[5] ), Rcpp::as<U6>( args[6] ) ) ;
+			return R_NilValue ;
+		}
+		inline int nargs(){ return 7 ; }
+		inline bool is_void(){ return true ; }
+	private:
+		Method met ;
+	} ;
+
+
+
+
+
+	template < typename Class, typename OUT, typename U0, typename U1, typename U2, typename U3, typename U4, typename U5, typename U6, typename U7 > class CppMethod8 : public CppMethod<Class> {
+	public:
+		typedef OUT (Class::*Method)(U0 u0, U1 u1, U2 u2, U3 u3, U4 u4, U5 u5, U6 u6, U7 u7) ;
+		typedef CppMethod<Class> method_class ;
+		
+		CppMethod8(Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			return Rcpp::wrap( (object->*met)( Rcpp::as<U0>( args[0] ), Rcpp::as<U1>( args[1] ), Rcpp::as<U2>( args[2] ), Rcpp::as<U3>( args[3] ), Rcpp::as<U4>( args[4] ), Rcpp::as<U5>( args[5] ), Rcpp::as<U6>( args[6] ), Rcpp::as<U7>( args[7] ) ) ) ;
+		}
+		inline int nargs(){ return 8 ; }
+		inline bool is_void(){ return false ; }
+	private:
+		Method met ;
+	} ;
+	
+	template < typename Class, typename U0, typename U1, typename U2, typename U3, typename U4, typename U5, typename U6, typename U7 > class CppMethod8<Class,void,U0, U1, U2, U3, U4, U5, U6, U7> : public CppMethod<Class> {
+	public:
+		typedef void (Class::*Method)(U0 u0, U1 u1, U2 u2, U3 u3, U4 u4, U5 u5, U6 u6, U7 u7) ;
+		typedef CppMethod<Class> method_class ;
+		
+		CppMethod8( Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			(object->*met)( Rcpp::as<U0>( args[0] ), Rcpp::as<U1>( args[1] ), Rcpp::as<U2>( args[2] ), Rcpp::as<U3>( args[3] ), Rcpp::as<U4>( args[4] ), Rcpp::as<U5>( args[5] ), Rcpp::as<U6>( args[6] ), Rcpp::as<U7>( args[7] ) ) ;
+			return R_NilValue ;
+		}
+		inline int nargs(){ return 8 ; }
+		inline bool is_void(){ return true ; }
+	private:
+		Method met ;
+	} ;
+
+
+
+
+
+	template < typename Class, typename OUT, typename U0, typename U1, typename U2, typename U3, typename U4, typename U5, typename U6, typename U7, typename U8 > class CppMethod9 : public CppMethod<Class> {
+	public:
+		typedef OUT (Class::*Method)(U0 u0, U1 u1, U2 u2, U3 u3, U4 u4, U5 u5, U6 u6, U7 u7, U8 u8) ;
+		typedef CppMethod<Class> method_class ;
+		
+		CppMethod9(Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			return Rcpp::wrap( (object->*met)( Rcpp::as<U0>( args[0] ), Rcpp::as<U1>( args[1] ), Rcpp::as<U2>( args[2] ), Rcpp::as<U3>( args[3] ), Rcpp::as<U4>( args[4] ), Rcpp::as<U5>( args[5] ), Rcpp::as<U6>( args[6] ), Rcpp::as<U7>( args[7] ), Rcpp::as<U8>( args[8] ) ) ) ;
+		}
+		inline int nargs(){ return 9 ; }
+		inline bool is_void(){ return false ; }
+	private:
+		Method met ;
+	} ;
+	
+	template < typename Class, typename U0, typename U1, typename U2, typename U3, typename U4, typename U5, typename U6, typename U7, typename U8 > class CppMethod9<Class,void,U0, U1, U2, U3, U4, U5, U6, U7, U8> : public CppMethod<Class> {
+	public:
+		typedef void (Class::*Method)(U0 u0, U1 u1, U2 u2, U3 u3, U4 u4, U5 u5, U6 u6, U7 u7, U8 u8) ;
+		typedef CppMethod<Class> method_class ;
+		
+		CppMethod9( Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			(object->*met)( Rcpp::as<U0>( args[0] ), Rcpp::as<U1>( args[1] ), Rcpp::as<U2>( args[2] ), Rcpp::as<U3>( args[3] ), Rcpp::as<U4>( args[4] ), Rcpp::as<U5>( args[5] ), Rcpp::as<U6>( args[6] ), Rcpp::as<U7>( args[7] ), Rcpp::as<U8>( args[8] ) ) ;
+			return R_NilValue ;
+		}
+		inline int nargs(){ return 9 ; }
+		inline bool is_void(){ return true ; }
+	private:
+		Method met ;
+	} ;
+
+
+
+
+
+	template < typename Class, typename OUT, typename U0, typename U1, typename U2, typename U3, typename U4, typename U5, typename U6, typename U7, typename U8, typename U9 > class CppMethod10 : public CppMethod<Class> {
+	public:
+		typedef OUT (Class::*Method)(U0 u0, U1 u1, U2 u2, U3 u3, U4 u4, U5 u5, U6 u6, U7 u7, U8 u8, U9 u9) ;
+		typedef CppMethod<Class> method_class ;
+		
+		CppMethod10(Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			return Rcpp::wrap( (object->*met)( Rcpp::as<U0>( args[0] ), Rcpp::as<U1>( args[1] ), Rcpp::as<U2>( args[2] ), Rcpp::as<U3>( args[3] ), Rcpp::as<U4>( args[4] ), Rcpp::as<U5>( args[5] ), Rcpp::as<U6>( args[6] ), Rcpp::as<U7>( args[7] ), Rcpp::as<U8>( args[8] ), Rcpp::as<U9>( args[9] ) ) ) ;
+		}
+		inline int nargs(){ return 10 ; }
+		inline bool is_void(){ return false ; }
+	private:
+		Method met ;
+	} ;
+	
+	template < typename Class, typename U0, typename U1, typename U2, typename U3, typename U4, typename U5, typename U6, typename U7, typename U8, typename U9 > class CppMethod10<Class,void,U0, U1, U2, U3, U4, U5, U6, U7, U8, U9> : public CppMethod<Class> {
+	public:
+		typedef void (Class::*Method)(U0 u0, U1 u1, U2 u2, U3 u3, U4 u4, U5 u5, U6 u6, U7 u7, U8 u8, U9 u9) ;
+		typedef CppMethod<Class> method_class ;
+		
+		CppMethod10( Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			(object->*met)( Rcpp::as<U0>( args[0] ), Rcpp::as<U1>( args[1] ), Rcpp::as<U2>( args[2] ), Rcpp::as<U3>( args[3] ), Rcpp::as<U4>( args[4] ), Rcpp::as<U5>( args[5] ), Rcpp::as<U6>( args[6] ), Rcpp::as<U7>( args[7] ), Rcpp::as<U8>( args[8] ), Rcpp::as<U9>( args[9] ) ) ;
+			return R_NilValue ;
+		}
+		inline int nargs(){ return 10 ; }
+		inline bool is_void(){ return true ; }
+	private:
+		Method met ;
+	} ;
+
+
+
+
+
+	template < typename Class, typename OUT, typename U0, typename U1, typename U2, typename U3, typename U4, typename U5, typename U6, typename U7, typename U8, typename U9, typename U10 > class CppMethod11 : public CppMethod<Class> {
+	public:
+		typedef OUT (Class::*Method)(U0 u0, U1 u1, U2 u2, U3 u3, U4 u4, U5 u5, U6 u6, U7 u7, U8 u8, U9 u9, U10 u10) ;
+		typedef CppMethod<Class> method_class ;
+		
+		CppMethod11(Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			return Rcpp::wrap( (object->*met)( Rcpp::as<U0>( args[0] ), Rcpp::as<U1>( args[1] ), Rcpp::as<U2>( args[2] ), Rcpp::as<U3>( args[3] ), Rcpp::as<U4>( args[4] ), Rcpp::as<U5>( args[5] ), Rcpp::as<U6>( args[6] ), Rcpp::as<U7>( args[7] ), Rcpp::as<U8>( args[8] ), Rcpp::as<U9>( args[9] ), Rcpp::as<U10>( args[10] ) ) ) ;
+		}
+		inline int nargs(){ return 11 ; }
+		inline bool is_void(){ return false ; }
+	private:
+		Method met ;
+	} ;
+	
+	template < typename Class, typename U0, typename U1, typename U2, typename U3, typename U4, typename U5, typename U6, typename U7, typename U8, typename U9, typename U10 > class CppMethod11<Class,void,U0, U1, U2, U3, U4, U5, U6, U7, U8, U9, U10> : public CppMethod<Class> {
+	public:
+		typedef void (Class::*Method)(U0 u0, U1 u1, U2 u2, U3 u3, U4 u4, U5 u5, U6 u6, U7 u7, U8 u8, U9 u9, U10 u10) ;
+		typedef CppMethod<Class> method_class ;
+		
+		CppMethod11( Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			(object->*met)( Rcpp::as<U0>( args[0] ), Rcpp::as<U1>( args[1] ), Rcpp::as<U2>( args[2] ), Rcpp::as<U3>( args[3] ), Rcpp::as<U4>( args[4] ), Rcpp::as<U5>( args[5] ), Rcpp::as<U6>( args[6] ), Rcpp::as<U7>( args[7] ), Rcpp::as<U8>( args[8] ), Rcpp::as<U9>( args[9] ), Rcpp::as<U10>( args[10] ) ) ;
+			return R_NilValue ;
+		}
+		inline int nargs(){ return 11 ; }
+		inline bool is_void(){ return true ; }
+	private:
+		Method met ;
+	} ;
+
+
+
+
+
+	template < typename Class, typename OUT, typename U0, typename U1, typename U2, typename U3, typename U4, typename U5, typename U6, typename U7, typename U8, typename U9, typename U10, typename U11 > class CppMethod12 : public CppMethod<Class> {
+	public:
+		typedef OUT (Class::*Method)(U0 u0, U1 u1, U2 u2, U3 u3, U4 u4, U5 u5, U6 u6, U7 u7, U8 u8, U9 u9, U10 u10, U11 u11) ;
+		typedef CppMethod<Class> method_class ;
+		
+		CppMethod12(Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			return Rcpp::wrap( (object->*met)( Rcpp::as<U0>( args[0] ), Rcpp::as<U1>( args[1] ), Rcpp::as<U2>( args[2] ), Rcpp::as<U3>( args[3] ), Rcpp::as<U4>( args[4] ), Rcpp::as<U5>( args[5] ), Rcpp::as<U6>( args[6] ), Rcpp::as<U7>( args[7] ), Rcpp::as<U8>( args[8] ), Rcpp::as<U9>( args[9] ), Rcpp::as<U10>( args[10] ), Rcpp::as<U11>( args[11] ) ) ) ;
+		}
+		inline int nargs(){ return 12 ; }
+		inline bool is_void(){ return false ; }
+	private:
+		Method met ;
+	} ;
+	
+	template < typename Class, typename U0, typename U1, typename U2, typename U3, typename U4, typename U5, typename U6, typename U7, typename U8, typename U9, typename U10, typename U11 > class CppMethod12<Class,void,U0, U1, U2, U3, U4, U5, U6, U7, U8, U9, U10, U11> : public CppMethod<Class> {
+	public:
+		typedef void (Class::*Method)(U0 u0, U1 u1, U2 u2, U3 u3, U4 u4, U5 u5, U6 u6, U7 u7, U8 u8, U9 u9, U10 u10, U11 u11) ;
+		typedef CppMethod<Class> method_class ;
+		
+		CppMethod12( Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			(object->*met)( Rcpp::as<U0>( args[0] ), Rcpp::as<U1>( args[1] ), Rcpp::as<U2>( args[2] ), Rcpp::as<U3>( args[3] ), Rcpp::as<U4>( args[4] ), Rcpp::as<U5>( args[5] ), Rcpp::as<U6>( args[6] ), Rcpp::as<U7>( args[7] ), Rcpp::as<U8>( args[8] ), Rcpp::as<U9>( args[9] ), Rcpp::as<U10>( args[10] ), Rcpp::as<U11>( args[11] ) ) ;
+			return R_NilValue ;
+		}
+		inline int nargs(){ return 12 ; }
+		inline bool is_void(){ return true ; }
+	private:
+		Method met ;
+	} ;
+
+
+
+
+
+	template < typename Class, typename OUT, typename U0, typename U1, typename U2, typename U3, typename U4, typename U5, typename U6, typename U7, typename U8, typename U9, typename U10, typename U11, typename U12 > class CppMethod13 : public CppMethod<Class> {
+	public:
+		typedef OUT (Class::*Method)(U0 u0, U1 u1, U2 u2, U3 u3, U4 u4, U5 u5, U6 u6, U7 u7, U8 u8, U9 u9, U10 u10, U11 u11, U12 u12) ;
+		typedef CppMethod<Class> method_class ;
+		
+		CppMethod13(Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			return Rcpp::wrap( (object->*met)( Rcpp::as<U0>( args[0] ), Rcpp::as<U1>( args[1] ), Rcpp::as<U2>( args[2] ), Rcpp::as<U3>( args[3] ), Rcpp::as<U4>( args[4] ), Rcpp::as<U5>( args[5] ), Rcpp::as<U6>( args[6] ), Rcpp::as<U7>( args[7] ), Rcpp::as<U8>( args[8] ), Rcpp::as<U9>( args[9] ), Rcpp::as<U10>( args[10] ), Rcpp::as<U11>( args[11] ), Rcpp::as<U12>( args[12] ) ) ) ;
+		}
+		inline int nargs(){ return 13 ; }
+		inline bool is_void(){ return false ; }
+	private:
+		Method met ;
+	} ;
+	
+	template < typename Class, typename U0, typename U1, typename U2, typename U3, typename U4, typename U5, typename U6, typename U7, typename U8, typename U9, typename U10, typename U11, typename U12 > class CppMethod13<Class,void,U0, U1, U2, U3, U4, U5, U6, U7, U8, U9, U10, U11, U12> : public CppMethod<Class> {
+	public:
+		typedef void (Class::*Method)(U0 u0, U1 u1, U2 u2, U3 u3, U4 u4, U5 u5, U6 u6, U7 u7, U8 u8, U9 u9, U10 u10, U11 u11, U12 u12) ;
+		typedef CppMethod<Class> method_class ;
+		
+		CppMethod13( Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
+			(object->*met)( Rcpp::as<U0>( args[0] ), Rcpp::as<U1>( args[1] ), Rcpp::as<U2>( args[2] ), Rcpp::as<U3>( args[3] ), Rcpp::as<U4>( args[4] ), Rcpp::as<U5>( args[5] ), Rcpp::as<U6>( args[6] ), Rcpp::as<U7>( args[7] ), Rcpp::as<U8>( args[8] ), Rcpp::as<U9>( args[9] ), Rcpp::as<U10>( args[10] ), Rcpp::as<U11>( args[11] ), Rcpp::as<U12>( args[12] ) ) ;
+			return R_NilValue ;
+		}
+		inline int nargs(){ return 13 ; }
+		inline bool is_void(){ return true ; }
+	private:
+		Method met ;
+	} ;
+
+
+
+
+
+	template < typename Class, typename OUT, typename U0, typename U1, typename U2, typename U3, typename U4, typename U5, typename U6, typename U7, typename U8, typename U9, typename U10, typename U11, typename U12, typename U13 > class CppMethod14 : public CppMethod<Class> {
+	public:
+		typedef OUT (Class::*Method)(U0 u0, U1 u1, U2 u2, U3 u3, U4 u4, U5 u5, U6 u6, U7 u7, U8 u8, U9 u9, U10 u10, U11 u11, U12 u12, U13 u13) ;
+		typedef CppMethod<Class> method_class ;
+		
+		CppMethod14(Method m) : method_class(), met(m){} 
+		SEXP operator()( Class* object, SEXP* args){
[TRUNCATED]

To get the complete diff run:
    svnlook diff /svnroot/rcpp -r 1325


More information about the Rcpp-commits mailing list