[R] type checking --- just a thought
    Gabor Grothendieck 
    ggrothendieck at myway.com
       
    Fri May 14 16:53:47 CEST 2004
    
    
  
If its just arg 1 then you can use S3 generics for this.  Here it is
but we have extended it to data frames too which isn't so easy
if you can only specify one type:
sum.across <- function(x) UseMethod("sum.across")
sum.across.matrix <- function(x) { stopifnot(is.numeric(x)); c(rowMeans(x)) }
sum.across.data.frame <- function(x) 
                           c(sum.across(as.matrix(x[,sapply(x,is.numeric)])))
# test
z1 <- sum.across(matrix(1:4,2))  
data(iris); z2 <- sum.across(iris)   
z3 <- sum.across(1:2) # error
z4 <- sum.across(letters) # error
Also note use of stopifnot in sum.across.matrix .
ivo welch <ivo.welch <at> yale.edu> writes:
: 
: hi:  would it be useful to build into R an optional mechanism that 
: typechecks arguments?  for example,
: 
:     sum.across <- function (  inpmatrix : matrixtype( dim[1]>1, dim[2]>3 
: ) ) : vector { }
:        # this would define a sum.across function that can take matrices 
: or data sets, but not vectors,
:        # and which indicates that it will return a vector.
: 
:     xsum <- sum.across( 1:10 );  # error
: 
:     repeat <- function( series : vector( dim>0 ),  times : scalar( 
: value>0 ) ) : vector;
: 
: similarly, a common input error condition may be calling a function with 
: a NULL vector, or with a vector with fewer than N observations.  many 
: statistical functions have such hard-wired limits.  I know that "if" 
: statements can do this, but this might make for a nice standardized 
: language feature.  on the other hand, the effort and complexity may not 
: be worth the extra functionality.
: 
: and one beg to the language maintainers for something that I hope is simple:
: 
:     in R 1.8.2, please add to the "source" function information where 
: (file:linenumber) dies or ends.
: 
: regards,
: 
: /ivo
    
    
More information about the R-help
mailing list