[R] OOP like handling of lists?

Patrick Burns pburns at pburns.seanet.com
Thu Oct 23 14:19:43 CEST 2003


I think what you want to write is:

setParms(lvmodel) <- list(k1=0.5)

which means that you need to define an assignment function.
If you are using S3 style OOP (which you appear to be), then
do something along the lines of:

 'setParms<-' <- function(x, value) UseMethod('setParms<-')
 'setParms<-.odemodel' <- function(x, value) {x$parms <- value; x}

Aside:  You might want to use "on.exit" to reset par in the plot
function.

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 Petzoldt wrote:

> Hello,
>
> I am writing a package with a collection of several models. In order 
> to allow users to play interactively with the models (in contrast to 
> hacking lengthy scripts), I want to put all what is needed to run a 
> particular model into a single list object for each model.
>
> Then there will be a collection of functions to run the model or to 
> modify parameters, time steps, integration method ..., which should 
> *work on the list itself* or make a copy of it.
>
> An example:
>
> the model object may have the name "lvmodel" (see below). so it can be 
> simulated and plotted simply using:
>
> lvmodel <- simulate(lvmodel)
> plot(lvmodel)
>
> Parameters (and other stuff) may be modified with:
>
> getParams(lvmodel)
> lvmodel <- setParms(lvmodel, list(k1=0.5))
>
> ... and then simulated and plotted again.
>
> The problem however is, that for functions which modify list elements 
> an assignement to a new (or the same) variable MUST exist.
>
> I want to write simply:
>
> setParms(lvmodel, list(k1=0.5))
>
> and not
>
> lvmodel <- setParms(lvmodel, list(k1=0.5))
>
> or at least get a warning, if the assignement is missing. I don't want 
> to break the R philosophy of function parameter handling. On the other 
> side the full OOP-approach in R-News 1(2002)3 of Chambers and Lang 
> works, but may be a little bit to complicated to explain it to my 
> collegues and students. So, is there an alternative to do such things, 
> which I may have overlooked?
>
> Thank you!
>
> Thomas Petzoldt
>
>
> #####################################################################
> #A simplified working example
> #####################################################################
>
> library(odesolve)
>
> ## The differential equation model ##################################
> lvmodel<-list(
>     equations = function(t, x, p) {
>       dx1.dt <-   p["k1"] * x[1] - p["k2"] * x[1] * x[2]
>       dx2.dt <- - p["k3"] * x[2] + p["k2"] * x[1] * x[2]
>       list(c(dx1.dt, dx2.dt))
>     },
>     parms  = c(k1=0.2, k2=0.2, k3=0.2),
>     xstart = c(prey=0.5, predator=1)
>     # and some more elements ...
> )
> class(lvmodel) <- "odemodel"
>
> ## Getting and setting parameters ###################################
>
> getParms <- function(model) {
>   model$parms
> }
>
> setParms <- function(model, parmlist) {
>   for (i in 1:length(parmlist)) {
>     model$parms[names(parmlist[i])] <- parmlist[[i]]
>   }
>   invisible(model)
> }
>
> ## Simulation #######################################################
>
> simulate <- function(model, ...) {
>   times <- seq(0, 100, 0.1)
>   res <- lsoda(model$xstart, times, model$equation, model$parms, ...)
>   model$out <- as.data.frame(res)
>   model
> }
>
> ## Plotting
>
> plot.odemodel <- function(model) {
>     oldpar <- par(no.readonly=TRUE)
>     par(mfrow=c(2, 1))
>     nam <- names(model$out)
>     for (i in 2:ncol(model$out)) {
>       plot(model$out[[1]], model$out[[i]],
>            type="l", xlab=nam[1], ylab=nam[i])
>     }
>     par(oldpar)
> }
>
> #### MAIN PROGRAM #########
>
> lvmodel <- simulate(lvmodel)
> plot(lvmodel)
>
> getParms(lvmodel)
> lvmodel <- setParms(lvmodel, list(k1=0.5))
> plot(simulate(lvmodel))
>
> ______________________________________________
> 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