[R] making changes to global variables in functions
William Dunlap
wdunlap at tibco.com
Wed Dec 7 18:31:07 CET 2011
A third option is to put your state objects in a list
and write a replacement function to modify the state
of each. E.g.,
`n<-` <- function(state, value) {
state[["n"]] <- value
state
}
n <- function(state) state[["n"]]
states <- list( list(n=100, won=0), list(n=101, won=1) )
for(i in seq_along(states)) {
n(states[[i]]) <- i*1000
}
invisible(lapply(states, dput))
# that should show:
# structure(list(n = 1000, won = 0), .Names = c("n", "won"))
# structure(list(n = 2000, won = 1), .Names = c("n", "won"))
This can make it easier to understand the flow of data.
Bill Dunlap
Spotfire, TIBCO Software
wdunlap tibco.com
> -----Original Message-----
> From: r-help-bounces at r-project.org [mailto:r-help-bounces at r-project.org] On Behalf Of Janko Thyson
> Sent: Wednesday, December 07, 2011 4:34 AM
> To: R. Michael Weylandt
> Cc: r-help at r-project.org; Yev
> Subject: Re: [R] making changes to global variables in functions
>
> Basically, I see two options here:
>
> 1) Using environments
>
> # Temp environment
> env <- new.env(parent=emptyenv())
> env$state1 <- list(n=100, won=0)
> env$state2 <- list(n=100, won=0)
>
> fight2 <- function(stateA, stateB, envir){
> # get(stateA, envir=envir)$n <- 50
> # The above is what you would want to do, but
> # 'get<-' is not defined, so:
> temp <- get(stateA, envir=envir)
> temp$n <- 50
> assign(stateA, value=temp, envir=envir)
>
> # Same for stateB
> temp <- get(stateB, envir=envir)
> temp$n <- 50
> assign(stateA, value=temp, envir=envir)
>
> return(TRUE)
> }
>
> fight2(stateA="state1", stateB="state2", envir=env)
>
> # Extract from environment
> state1 <- env$state1
> state1
> state2 <- env$state2
> state2
>
> 2) Using Reference Classes
>
> # Class Def
> setRefClass("State",
> fields=list(n="numeric", won="numeric"),
> methods=list(
> fight2=function(...){
> fight2Ref(.self=.self, ...)
> }
> )
> )
> # Set Generic
> setGeneric(name="fight2Ref", signature=".self", def=function(.self, ...)
> standardGeneric("fight2Ref"))
> # Set Method
> setMethod(f="fight2Ref", signature="State",
> definition=function(
> .self,
> value,
> ...
> ){
> .self$n <- value
> }
> )
> # Note:
> # You could also put the code inside 'fight2Ref' directly inside the
> class def,
> # but I don't want them to be too crowded, so I go by 'divide and conquer'
>
> # Instantiate objects
> state1 <- new("State", n=100, won=0)
> state1
> state2 <- new("State", n=100, won=0)
> state2
>
> # Apply method
> state1$fight2(value=50)
> state1
> state2$fight2(value=50)
> state2
>
> # Back to list
> stateToList <- function(obj, ...){
> fields <- names(getRefClass("State")$fields())
> out <- lapply(fields, function(x.field){
> obj$field(x.field)
> })
> names(out) <- fields
> return(out)
> }
> state1 <- stateToList(state1)
> state1
> state2 <- stateToList(state2)
> state2
>
> HTH,
> Janko
>
> On 06.12.2011 22:06, R. Michael Weylandt wrote:
> > No pointer functionality in R (that I know of), but if you want to
> > return two objects as one the standard way is to put them in a list
> > and to return that list.
> >
> > Michael
> >
> > On Tue, Dec 6, 2011 at 2:35 PM, Yev<kirpich at gmail.com> wrote:
> >> I'm trying to write a function that takes several objects with many
> >> different attributes and then changes their attributes. So what I wanted to
> >> happen in the simplified example below is for the function to change the
> >> attributes of the objects state1 and state2 that are passed to it. But
> >> because stateA and stateB are local, this isn't working. Are there any easy
> >> solutions?
> >>
> >> e.g., if I could combine the two objects stateA and stateB into a single
> >> object, I could return it and then assign it back to objects state1 and
> >> state2. Or if I could pass a pointer to the original object.. But I cannot
> >> find an easy way of doing either. Thanks in advance..
> >>
> >> state1<- list(n=100, won=0)
> >> state2<- list(n=100, won=0)
> >>
> >> fight2<- function(stateA, stateB){
> >> stateA$n<- 50
> >> stateB$n<-50
> >> }
> >>
> >> fight2(state1,state2)
> >>
> >> state1$n
> >> state2$n
> >>
> >> [[alternative HTML version deleted]]
> >>
> >> ______________________________________________
> >> R-help at r-project.org mailing list
> >> https://stat.ethz.ch/mailman/listinfo/r-help
> >> PLEASE do read the posting guidehttp://www.R-project.org/posting-guide.html
> >> and provide commented, minimal, self-contained, reproducible code.
> > ______________________________________________
> > R-help at r-project.org mailing list
> > https://stat.ethz.ch/mailman/listinfo/r-help
> > PLEASE do read the posting guidehttp://www.R-project.org/posting-guide.html
> > and provide commented, minimal, self-contained, reproducible code.
> >
>
>
> --
> ------------------------------------------------------------------------
>
> *Janko Thyson*
> janko.thyson at ku-eichstaett.de <mailto:janko.thyson at ku-eichstaett.de>
>
> Catholic University of Eichstätt-Ingolstadt
> Ingolstadt School of Management
> Statistics and Quantitative Methods
> Auf der Schanz 49
> D-85049 Ingolstadt
>
> www.wfi.edu/lsqm <http://www.wfi.edu/lsqm>
>
> Fon: +49 841 937-1923
> Fax: +49 841 937-1965
>
> This e-mail and any attachment is for authorized use by the intended
> recipient(s) only. It may contain proprietary material, confidential
> information and/or be subject to legal privilege. It should not be
> copied, disclosed to, retained or used by any other party.
> If you are not an intended recipient then please promptly delete this
> e-mail and any attachment and all copies and inform the sender.
>
>
> [[alternative HTML version deleted]]
More information about the R-help
mailing list