[Rcpp-commits] r3855 - in pkg/Rcpp: . R inst/include/Rcpp

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Mon Oct 29 16:38:01 CET 2012


Author: romain
Date: 2012-10-29 16:38:01 +0100 (Mon, 29 Oct 2012)
New Revision: 3855

Modified:
   pkg/Rcpp/ChangeLog
   pkg/Rcpp/R/Module.R
   pkg/Rcpp/inst/include/Rcpp/Module.h
Log:
using converter instead of convert_to

Modified: pkg/Rcpp/ChangeLog
===================================================================
--- pkg/Rcpp/ChangeLog	2012-10-29 13:37:32 UTC (rev 3854)
+++ pkg/Rcpp/ChangeLog	2012-10-29 15:38:01 UTC (rev 3855)
@@ -6,10 +6,10 @@
 
 	* R/Module.R: Taking care of a check warning
 	* include/Rcpp/module/macros.h: adding RCPP_EXPOSED_CLASS_NODECL
-	* include/Rcpp/Module.h: introducing convert_to to facilitate
-	conversion to other class.
-	* R/Module.R: Methods registered internally with convert_to will
-	generate the appropriate as S4 method.
+	* include/Rcpp/Module.h: introducing converter to facilitate
+	conversion between classes.
+	* R/Module.R: Methods registered internally with converter will
+	generate the appropriate "as" S4 method.
 
 2012-10-28  Dirk Eddelbuettel  <edd at debian.org>
 

Modified: pkg/Rcpp/R/Module.R
===================================================================
--- pkg/Rcpp/R/Module.R	2012-10-29 13:37:32 UTC (rev 3854)
+++ pkg/Rcpp/R/Module.R	2012-10-29 15:38:01 UTC (rev 3855)
@@ -249,19 +249,6 @@
             }
         }
         
-        as_rx <- "^[.]___as___(.+)$"
-        if( length( matches <- grep( as_rx, names(CLASS at methods) ) ) ){
-            for( i in matches ){
-                met <- names(CLASS at methods)[i]
-                to <- sub( as_rx, "\\1", met )
-                converter <- function( from ){}
-                body( converter ) <- substitute( { from$CONVERT() }, 
-                    list( CONVERT = met )
-                )
-                setAs( clname, to, converter, where = where)
-            }
-        }
-
     }
     if(length(classes)) {
         module$refClassGenerators <- generators
@@ -289,6 +276,22 @@
     functions <- .Call( Module__functions_names, xp )
     for( fun in functions ){
         storage[[ fun ]] <- .get_Module_function( module, fun, xp )
+        
+        # register as(FROM, TO) methods
+        converter_rx <- "^[.]___converter___(.*)___(.*)$"
+        if( length( matches <- grep( converter_rx, functions ) ) ){
+            for( i in matches ){
+                fun <- functions[i]
+                from <- sub( converter_rx, "\\1", fun )
+                to   <- sub( converter_rx, "\\2", fun )
+                converter <- function( from ){}
+                body( converter ) <- substitute( { CONVERT(from) }, 
+                    list( CONVERT = storage[[fun]] )
+                )
+                setAs( from, to, converter, where = where )
+            }
+        }
+        
     }
 
     assign( "storage", storage, envir = as.environment(module) )

Modified: pkg/Rcpp/inst/include/Rcpp/Module.h
===================================================================
--- pkg/Rcpp/inst/include/Rcpp/Module.h	2012-10-29 13:37:32 UTC (rev 3854)
+++ pkg/Rcpp/inst/include/Rcpp/Module.h	2012-10-29 15:38:01 UTC (rev 3855)
@@ -27,17 +27,27 @@
 namespace Rcpp{
     
     namespace internal{
-        template <typename OUT>
-        std::string get_as_method_name(const char* target){
-            std::string method_name( ".___as___" ) ;
-            typedef typename Rcpp::traits::r_type_traits<OUT>::r_category CATEGORY ;
-            if( Rcpp::traits::same_type< CATEGORY, ::Rcpp::traits::r_type_module_object_tag >::value ){
+        
+        template <typename FROM, typename TO>
+        std::string get_converter_name(const char* from, const char* to){
+            std::string method_name( ".___converter___" ) ;
+            typedef typename Rcpp::traits::r_type_traits< typename Rcpp::traits::remove_const_and_reference<FROM>::type >::r_category FROM_CATEGORY ;
+            if( Rcpp::traits::same_type< FROM_CATEGORY, ::Rcpp::traits::r_type_module_object_tag >::value ){
                 method_name += "Rcpp_" ;    
             }
-            method_name += target ;
+            method_name += from ;
+            method_name += "___" ;
+            typedef typename Rcpp::traits::r_type_traits< typename Rcpp::traits::remove_const_and_reference<TO>::type >::r_category TO_CATEGORY ;
+            if( Rcpp::traits::same_type< TO_CATEGORY, ::Rcpp::traits::r_type_module_object_tag >::value ){
+                method_name += "Rcpp_" ;    
+            }
+            method_name += to ;
+            
             return method_name ;
         }
-    }
+        
+        
+   }
 
     class CppClass ;
     class CppObject ;
@@ -448,7 +458,6 @@
          
         ~class_(){}
         
-        
         self& AddConstructor( constructor_class* ctor, ValidConstructor valid, const char* docstring = 0 ){
             class_pointer->constructors.push_back( new signed_constructor_class( ctor, valid, docstring ) );  
             return *this ;
@@ -606,19 +615,6 @@
 #include <Rcpp/module/Module_generated_method.h>
 #include <Rcpp/module/Module_generated_Pointer_method.h>
         
-        template <typename OUT>
-        self& convert_to( const char* target, OUT (Class::*fun)(void), const char* docstring = 0 ){
-            std::string method_name = internal::get_as_method_name<OUT>(target) ; 
-            method( method_name.c_str() , fun, docstring, &yes ) ;
-            return *this ;
-        }
-        template <typename OUT>
-        self& convert_to( const char* target, OUT (*fun)(Class*), const char* docstring = 0 ){
-            std::string method_name = internal::get_as_method_name<OUT>(target) ; 
-            method( method_name.c_str(), fun, docstring, &yes ) ;
-            return *this ;
-        }
-        
         bool has_method( const std::string& m){
             return vec_methods.find(m) != vec_methods.end() ;
         }
@@ -872,6 +868,19 @@
     // function factories
 #include <Rcpp/module/Module_generated_function.h>
 
+    template <typename FROM, typename TO>
+    void converter( const char* from, const char* to, TO (*fun)(FROM), const char* docstring = 0 ){
+        std::string fun_name = internal::get_converter_name<FROM,TO>( from, to ) ;
+        function( fun_name.c_str(), fun, docstring ) ;
+    }  
+                       
+    template <typename FROM, typename TO>
+    void converter( const char* /* from */ , const char* to, TO (FROM::*fun)(), const char* docstring = 0 ){
+        Rcpp::Module* scope = ::getCurrentScope() ;
+        class_<FROM>().convert_to( to, fun, docstring ) ;
+    }
+    
+    
     class CppClass : public S4{
     public:
         typedef Rcpp::XPtr<Rcpp::Module> XP ;



More information about the Rcpp-commits mailing list