[Rd] can't get names of R_env

torpedo fisken torpedofisken at gmail.com
Fri Jan 9 09:12:23 CET 2009


Thanks for your reply.

2009/1/5 Prof Brian Ripley <ripley at stats.ox.ac.uk>:
> You will have to read more carefully: an ENVSXP is nothing like a VECSXP,
> and does not have the names of its entries in a names attribute.
>
> You access variables in an environment via findVar() and friends, including
> findVarInFrame: see 'Writing R Extensions'.

Yes, I can see their implementation in src/main/envir.c.
But I'm still somewhat lost concerning the innerworkings of the .R <->
.c interface.
Especially the passing of the R_env parameter from R.

I'll try to explain what puzzles me as concisely as possible
-----------------------------------------------------
i.e
the optim() prototype is
optim <- function(par, fn, gr = NULL, ...,
                  method = c("Nelder-Mead", "BFGS", "CG", "L-BFGS-B", "SANN"),
                  lower = -Inf, upper = Inf,
                  control = list(), hessian = FALSE)

This makes an .Internal method call with
.Internal(optim(par, fn1, gr1, method, con, lower, upper))
This has seven args.

An by "src/names.c" this will use the do_optim() from src/main/optim.c
which has the following protype
SEXP attribute_hidden do_optim(SEXP call, SEXP op, SEXP args, SEXP rho);
This has 4 args.

According to the R-ints all .Internal that calls c-code will call
dispatchOrEval() in src/eval.c
http://cran.r-project.org/doc/manuals/R-ints.html#Argument-evaluation
But the arguments (there are 8), remains quite obscure for me.
And I'm having some problems tracking down the .Internal function
definition in the sourcetree.

Can someone clarify what happens in between .
.Internal(optim(...))  to do_optim(...)

Thanks again.

> On Mon, 5 Jan 2009, torpedo fisken wrote:
>
>> Hi,
>> I'm quite knew in R, so I might not have the R specific jargon.
>>
>> But here is my problem,
>> I'm trying to access and use variabels given by a function environment,
>> more specifically the rho in do_optim in src/main/optim.c
>
> Very likely this is not the way to do whatever it is that you really want to
> do.
>
>> According to the documentation
>> http://cran.r-project.org/doc/manuals/R-ints.html#The-_0027data_0027
>> the envsxp is defined as a tagged pairlist.
>>
>> "ENVSXP: Pointers to the frame, enclosing environment and hash table
>> (NULL or a VECSXP). A frame is a tagged pairlist with tag the symbol
>> and CAR the bound value."
>>
>> But I'm having troubles accessing the data.
>> I've written a small function called printNames that looks like
>> -----------------------
>> void printNames(SEXP list){
>>   SEXP names = getAttrib(list, R_NamesSymbol);
>>   int i;
>>   Rprintf("List is of length:%d\n",length(list));
>>   for (i = 0; i < length(list); i++)
>>     Rprintf("name of id:%d\t%s\n",i,CHAR(STRING_ELT(names, i)));
>> }
>> -----------------------
>> This is basicly just a copy of
>> -----------------------
>> static SEXP getListElement(SEXP list, char *str)
>> {
>>   SEXP elmt = R_NilValue, names = getAttrib(list, R_NamesSymbol);
>>   int i;
>>
>>   for (i = 0; i < length(list); i++)
>>        if (strcmp(CHAR(STRING_ELT(names, i)), str) == 0) {
>>            elmt = VECTOR_ELT(list, i);
>>            break;
>>        }
>>   return elmt;
>> }
>> -----------------------
>> But this crashes and looks like
>> -----------------------
>> List is of length:16
>> name of id:0    Xd???
>> name of id:1    Xd???
>> name of id:2
>> *** caught segfault ***
>> address 0x28, cause 'memory not mapped'
>> ------------------------
>> I've just added printNames(rho) in the very first line of do_optim().
>> Futhermore I've checked that the typeof(rho) corresponds to the
>>
>> #define ENVSXP       4 in Rinternals.h at line 84
>>
>> Can anyone clarify how to access these enviroment variables.
>> I believe my problem lies in the sentence "A frame is a tagged
>> pairlist with tag the symbol and CAR the bound value."
>> Or more precisely, I don't quite understand the struct for env exp
>> --------------------------
>> struct envsxp_struct {
>>   struct SEXPREC *frame;
>>   struct SEXPREC *enclos;
>>   struct SEXPREC *hashtab;
>> };
>> --------------------------
>>
>> thanks in advance.
>> ______________________________________________
>> R-devel at r-project.org mailing list
>> https://stat.ethz.ch/mailman/listinfo/r-devel
>>
>
> --
> Brian D. Ripley,                  ripley at stats.ox.ac.uk
> Professor of Applied Statistics,  http://www.stats.ox.ac.uk/~ripley/
> University of Oxford,             Tel:  +44 1865 272861 (self)
> 1 South Parks Road,                     +44 1865 272866 (PA)
> Oxford OX1 3TG, UK                Fax:  +44 1865 272595
>



More information about the R-devel mailing list