[R] How to make "<-" generic?

Thomas Koenig thomasio at cs.tu-berlin.de
Sat Jul 26 21:22:28 CEST 2003


Am Samstag, 26. Juli 2003 14:16 schrieb Patrick Burns:
> I think Brian's question --- what are you trying to do? -- should
> be the first order of business.

I don't want to loose the class (for me, some kind of meaning) of my 
variables, so in the first line as ("a little") insurance that my code does 
that what I want.

A first example
setClass("A",...)
setClass("B",...)
setMethod("doSomething",signature="A",function(x) return(1))
setMethod("doSomething",signature="B",function(x) return(2)) ; ## perhaps 
defined in a complete different library, file, etc.
setReplaceMethod("<-",c("A","A"),myAssign.A) ## only A <- A is now allowed
a <- new("A"); ## this is my a ;-)

... lines of code
a <- b ## loosing my type by an error or something else 
           ## should give the error : Error in myAssign(a,b) : No direct or
           ## inherited method for function "myAssign" for this call

## or (perhaps more "ugly")
f <- function(x) {
	if(runif(1) < 0.5) return(new("A"));
	else return(new("B"));	
}
a <- f(1)

.. lines of code
res <- doSomething(a); ## Function call is random. This is not what I want, 
and it is very hard to find the error. All things works fine, but the meaning 
is completly different

A second example with "length<-" (seems to have the same "problem"?), ensuring 
correct lengths:
setClass("A",representation(x = "numeric",y="numeric");
setReplaceMethod("length<-",c("A","integer"),setting x and y to the same 
lengths)
a <- new("A");
length(a) <- 10
ensures always the same lengths.

A third example, ensuring a consistent model
setClass("Cox",representation(coef = "numeric", otherData))
setClass("CoxControl",representation(method ="character",it = "integer", other 
Data))
setClass("CensoredData",representation(time = "numeric", cens = "integer", 
other Data));

## could be useful
setReplaceMethod("<-",c("Cox","CensoredData"),function(x) {do some checks for 
Censored Data  etc. and do perhaps (depends from the author) recalculation or 
delete old results})
setReplaceMethod("<-",c("Cox","CoxControl"),function(x) {setting only the 
"control slots" and do perhaps (depends from the author) recalculation or 
delete old results })

cox <- new("Cox"); ## my cox ;-)
censData <- new("CensoredData");
coxCtrl <- new("CoxControl")
## prepare censData and ControlData
## feeding the model with data
cox <- censData;
## feeding the model with controls
cox <- CoxControl;
## There is a possibility to have a consistent model

I hope that makes my intentions clearer, and is not completely nonsense.

Best regards and thanks for the discussion and your efforts!

Thomas König



>
> Someone can make R do just about anything, but it is better to
> do a few things very well than lots of things in a muddled way.
>
> So.  What is the advantage of using assignment as a generic?
> I'm open-minded about there being such an advantage, but I
> don't see any right off.
>
> Patrick Burns
>
> Burns Statistics
> patrick at burns-stat.com
> +44 (0)20 8525 0696
> http://www.burns-stat.com
> (home of S Poetry and "A Guide for the Unwilling S User")
>
> Thomas Koenig wrote:
> >Am Samstag, 26. Juli 2003 11:38 schrieb Peter Dalgaard BSA:
> >>Peter Dalgaard BSA <p.dalgaard at biostat.ku.dk> writes:
> >>>Prof Brian Ripley <ripley at stats.ox.ac.uk> writes:
> >>>>What are you trying to do with this?  Assignment (<-) is not a
> >>>>function,
> >
> >But what the difference between <- and e.g. the function length or "[<-"?
> > As I understood in "methods" everything has a class. And R says me with
> > is(...) (hope that the results are correct):
> >< is(get("<-"))
> >[1] "function"         "OptionalFunction" "PossibleMethod"
> >< is(get("length"))
> >[1] "function"         "OptionalFunction" "PossibleMethod"
> >
> >>is(get("[<-"))
> >
> >[1] "function"         "OptionalFunction" "PossibleMethod"
> >
> >>## test for the correct result of get(...) ?
> >>x <- 10
> >>is(get("x"))
> >
> >[1] "numeric" "vector"
> >
> >>## and
> >>setGeneric("<-")
> >
> >[1] "<-"
> >Warning message:
> >"<-" is a primitive function; its generic definition is built in and
> >automatically included. in: setGeneric("<-")
> >
> >>>>and the language grammar does not convert a <- b into "<-"(a,
> >>>>b) (as it would with the binary operator functions).  You could call it
> >>>>that way, and then it will probably work.
> >>>
> >>>Eh? Are you sure about that???
> >>>
> >>>>quote("<-"(a,b))
> >>>
> >>>a <- b
> >>
> >>Adding on to this, I think the point is that assignment bypasses the
> >>usual *evaluation* rules, even though it is syntactically a binop.
> >>
> >>I think it basically has to be so: For one thing, it is kind of
> >>difficult to check for a signature match without evaluating the
> >>arguments and the left hand side of an assignment will not in general
> >>exist at that point.
> >
> >In the methods is the class "missing". Could that help?
> >for one thing : signature=c("missing","A") (only allowed for <- ?)
> >for both things: signature=c("A","B")
> >for nothing ;-) : signature=c("missing","missing")
> >
> >Thanks and Best Regards
> >
> >Thomas König
> >
> >______________________________________________
> >R-help at stat.math.ethz.ch mailing list
> >https://www.stat.math.ethz.ch/mailman/listinfo/r-help
>
> ______________________________________________
> R-help at stat.math.ethz.ch mailing list
> https://www.stat.math.ethz.ch/mailman/listinfo/r-help




More information about the R-help mailing list