[R] getAttrib() and setAttrib()

Richards, Tom richards at pci.upmc.edu
Wed Jul 12 11:22:16 CEST 2000


Hello:
 
I am looking at "Writing R Extensions", subsection 3.6.4, using R 1.1.0,
under NT4.0, with VC++ 6.0.  Under these conditions I can use the first
method given for coding the out() function, but not the second, which uses
getAttrib() and setAttrib().  I hope that someone will tell me how this
second method can also be made to work.  Details follow, for anyone kind
enough to help.  I include the actual code lifted from the manual, so that
you can compile, dyn.load() and tell me that it works fine for you!
 
The R function of interest is the outer product of two vectors:
 
out <- function(x, y) .Call("out", as.double(x), as.double(y))
 
Define out() as simply (straight from the text):
 
SEXP out(SEXP x, SEXP y)
{
 int i, j, nx, ny;
 double tmp;
 SEXP ans;
 nx = length(x); ny = length(y);
 PROTECT(ans = allocMatrix(REALSXP, nx, ny));
 for(i = 0; i < nx; i++) {
  tmp = REAL(x)[i];
  for(j = 0; j < ny; j++)
   REAL(ans)[i + nx*j] = tmp * REAL(y)[j];
 }
 UNPROTECT(1);
 return(ans);
}
 
Compiling, I get a correct answer,
 
> out(c(1,2),c(3,4))
 
     [,1] [,2]
[1,]    3    4
[2,]    6    8

All is well.  The following function (second method with lines commented)
also works:
 
SEXP out(SEXP x, SEXP y)
{
 int i, j, nx, ny;
 double tmp;
 SEXP ans, dim, dimnames;
 nx = length(x); ny = length(y);
 PROTECT(ans = allocVector(REALSXP, nx*ny));
 for(i = 0; i < nx; i++) {
  tmp = REAL(x)[i];
  for(j = 0; j < ny; j++)
   REAL(ans)[i + nx*j] = tmp * REAL(y)[j];
 }
 PROTECT(dim = allocVector(INTSXP, 2));
 INTEGER(dim)[0] = nx; INTEGER(dim)[1] = ny;
// setAttrib(ans, R_DimSymbol, dim);
 PROTECT(dimnames = allocVector(VECSXP, 2));
// VECTOR(dimnames)[0] = getAttrib(x, R_NamesSymbol);
// VECTOR(dimnames)[1] = getAttrib(y, R_NamesSymbol);
// setAttrib(ans, R_DimNamesSymbol, dimnames);
 UNPROTECT(3);
 return(ans);
}

Here is the output, a vector:
 
> out(c(1,2),c(3,4))

[1] 3 6 4 8
 
But when I uncomment any one of the 4 lines which use getAttrib() or
setAttrib(), R crashes for me, with a Windows message box.  Uncommenting the
first such line, for example, crashes R, with a message box:
 
The instruction at "0x<HEX address>" refernced memory at "0x<another
address>".  The memory could not be "read".
 
Is there anything I can do differently to make these attribute functions
work?  thanks in advance for your help.
 
                                                        Tom Richards
 
 
-------------- next part --------------
An HTML attachment was scrubbed...
URL: https://stat.ethz.ch/pipermail/r-help/attachments/20000712/9cba9879/attachment.html


More information about the R-help mailing list