RE [R] workspace vs. image

Cliff Lunneborg lunneborg at attbi.com
Fri Dec 20 10:30:04 CET 2002


As an alternative to the use of multiple shortcus to gain entry to different
R environments on WIndows platforms I would like to suggest the use of two R
functions written by my colleague John Miyamoto. I have taken the liberty of
attaching their definitions to this message. Their efficient use is based on
adopting the following regimen or something like it: (1) at startup attach
an .Rdata workspace containing the two functions, say to position 2. This I
do in my etc/Rprofile file. (2) then attach one or more .Rdata workspaces to
additional positions in the search path. These contain data and/or
user-defined functions relevant to the current problem. Position 1 of the
search, .GlobalEnv is then used only for sctratchwork.

move(obj,pos=3) moves obj from .GlobalEnv to the environent of position 3,
saves that environment to the associated .Rdata file, and removes obj from
.GlobalEnv.

rm.sv(obj,pos=3) removes obj from the environment at position 3 and then
saves the remaining objects to the associated .Rdata file.

The use of the two keeps the .Rdata files updated.

##Here is the first function

move<-
function(x, pos=NA, dir="c:/directory name/file name", replace=F)  {
    if (is.na(pos)) dirL _ paste("file:", dir, sep="") else dirL _
search()[pos]
    if (mode(x) != "character")  name _ deparse(substitute(x)) else name _ x
# Assign the correct number to tmpos = pos, if it is not already assigned.
    if (is.na(pos)) {
        tmp _ search() == dirL
        if (sum(tmp) < 1) stop(message=paste(dir, "not in search path."))
        if (sum(tmp) > 1)  {
            cat("There is more than one directory named",
                dir, "in the search path.\n",
                "Set the destination with the pos argument.\n")
            stop(message = "Execution of move terminated.")
            } #end of if (sum(tmp) > 1)
        tmpos _ (1:length(search()))[tmp]
        }   else tmpos _ pos        #End of if (is.na(pos))
# Assign the correct directory name to dirN if it is not already assigned.
    tms _ search()[tmpos]
    dirN _ substring(tms, 6, nchar(tms))
#--------------------------------------------------
# The next if carries out the move, if this is possible.
    e.test _ NULL;  for (i in 1:length(name))
        e.test _ c(e.test, !exists(name[i], env=pos.to.env(tmpos)) )
    if ( all(e.test) | replace)   {
        for (i in 1:length(name)) assign(name[i], get(name[i],
envir=.GlobalEnv),
            pos=tmpos)
        save(list=objects(pos=tmpos, all=T), file=dirN )
        rm(list=name, envir=.GlobalEnv)
        }   else    {   #end if, start else
#--------------------------------------------------
# The next code gives warning messages if the move could not be carried out.
# Case I: The target directory was specified by dir.
        if (is.na(pos)) {
        cat("\n No movement of object was carried out!\n Object(s) ",
        name[!e.test], " exists in ", dir,".\n\n",
        'Add "replace=T" to the move command in order to replace',
        name[!e.test],"\nin", dir,".\n\n") } else
        {
# Case II: The target directory was specified by pos.
        cat("\n No movement of object was carried out!\n Object(s) ",
        name[!e.test], " exists in pos =", pos,".\n\n",
        'Add "replace=T" to the move command in order to replace',
        name[!e.test],"\nin pos =", pos,".\n\n") }
    } #end of case where object exists in destination directory
} #end of function
definition --------------------------------------------------

# and here is the second function:

rm.sv<-
function(x, pos=NA, dir="e:/r/jmm/jmfuns.rda")  {
    if (is.na(pos)) dirL _ paste("file:", dir, sep="") else dirL _
search()[pos]
    if (mode(x) != "character")  name _ deparse(substitute(x)) else name _ x
# Assign the correct number to tmpos = pos, if it is not already assigned.
    if (is.na(pos)) {
        tmp _ search() == dirL
        if (sum(tmp) < 1) stop(message=paste(dir, "not in search path."))
        if (sum(tmp) > 1)  {
            cat("There is more than one directory named",
                dir, "in the search path.\n",
                "Set the destination with the pos argument.\n")
            stop(message = "Execution of move terminated.")
            } #end of if (sum(tmp) > 1)
        tmpos _ (1:length(search()))[tmp]
        }   else tmpos _ pos        #End of if (is.na(pos))
# Assign the correct directory name to dirN if it is not already assigned.
    tms _ search()[tmpos]
    dirN _ substring(tms, 6, nchar(tms))
#--------------------------------------------------
# The next if carries out the deletion, if this is possible.
    e.test _ NULL;  for (i in 1:length(name))
        e.test _ c(e.test, exists(name[i], env=pos.to.env(tmpos)) )
    if ( all(e.test) )
        {
        rm(list=name, pos=tmpos)
        save(list=objects(pos=tmpos, all=T), file=dirN)
        cat(paste("Deletion completed.  Current objects in",
            dirN, "are:\n") )
        print(objects(pos=tmpos, all=T))
        }   else    {   #end if, start else
#--------------------------------------------------
# The next code gives warning messages if the object does not exist in the
target directory.
# Case I: The target directory was specified by dir.
        if (is.na(pos)) {
        cat("\n No deletion of object was carried out!\n Object ",
        name[!e.test], " does not exist in ", dir,".\n\n") } else
        {
# Case II: The target directory was specified by pos.
        cat("\n No deletion of object was carried out!\n Object ",
        name[!e.test], " does not exist in pos =", pos,".\n\n") }
    } #end of case where object does not exist in target directory
} #end of function
definition --------------------------------------------------



**********************************************************
Cliff and/or Pat Lunneborg
Temporarily in Salobrena
Costa Granada, ESPANA
Nov 2002 thru Jan 2003

cliff at ms.washington.edu
or
lunneborg at attbi.com




More information about the R-help mailing list