[R] A way to list only variables or functions?

Petr Pikal petr.pikal at precheza.cz
Mon Jun 21 17:01:10 CEST 2004



On 21 Jun 2004 at 10:39, Duncan Murdoch wrote:

> On Mon, 21 Jun 2004 09:53:35 -0400, "Shin, Daehyok"
> <sdhyok at email.unc.edu> wrote :
> 
> >Glad to know useful functions.
> >How about adding lsv.str function to list only variables bound to
> >values? In my opinion, we are more interested in values than
> >functions in the process of data analysis.
> 
> In R, functions often contain useful information about data (in their
> attached environments).  For example, the result of a smoothing fit
> could include a function that calculates the fitted value at any
> point.  So the distinction between functions and values isn't as clear
> as you seem to be thinking.
> 
> However, it would be useful to get a slightly more informative version
> of ls(), that returned a data.frame containing the name, length,
> class, and other useful information for each object. Then if you
> didn't want to see functions, you'd just select based on the class (or
> mode, or some other column).
> 
> I seem to recall that S-PLUS has such a function, but I forget the
> name of it.   Probably R does too, on CRAN if not in the base
> packages.

Some time ago there was a thread about such matter too and from 
that time i use a function

> ls.objects
function (pos = 1, pattern, order.by) 
{
    napply <- function(names, fn) sapply(names, function(x) 
fn(get(x, 
        pos = pos)))
    names <- ls(pos = pos, pattern = pattern)
    obj.class <- napply(names, function(x) as.character(class(x))[1])
    obj.mode <- napply(names, mode)
    obj.type <- ifelse(is.na(obj.class), obj.mode, obj.class)
    obj.size <- napply(names, object.size)
    obj.dim <- t(napply(names, function(x) 
as.numeric(dim(x))[1:2]))
    vec <- is.na(obj.dim)[, 1] & (obj.type != "function")
    obj.dim[vec, 1] <- napply(names, length)[vec]
    out <- data.frame(obj.type, obj.size, obj.dim)
    names(out) <- c("Type", "Size", "Rows", "Columns")
    if (!missing(order.by)) 
        out <- out[order(out[[order.by]]), ]
    out
}

which gives some more information about objects than plain ls()

Cheers
Petr

> 
> Duncan Murdoch
> 
> ______________________________________________
> R-help at stat.math.ethz.ch mailing list
> https://www.stat.math.ethz.ch/mailman/listinfo/r-help
> PLEASE do read the posting guide!
> http://www.R-project.org/posting-guide.html

Petr Pikal
petr.pikal at precheza.cz




More information about the R-help mailing list