5

Recently I had a bug and when fixing it I wondered if it is possible to return a VECSXP (i.e. an R list type), where the elements are named. This c++ code:

SEXP do_bla() 
{
   int prtCnt = 0;
   SEXP a = PROTECT(allocMatrix(REALSXP, 5, 5));
   prtCnt++;
   SEXP b = PROTECT(allocVector(REALSXP, 5));
   prtCnt++;
   SEXP OS = PROTECT(allocVector(VECSXP, 2));
   prtCnt++;
   SET_VECTOR_ELT(OS, 0, a);
   SET_VECTOR_ELT(OS, 1, b);
   UNPROTECT(prtCnt);
   return OS;
}

would give me a list of two elements (matrix and vector) in R:

s <- .Call("do_bla", ....)

which can be indexed like this:

 s[[1]]; s[[2]]

What would I have to change to make this possible:

s$a; s$b

Or is this not possible?

nrussell
  • 18,382
  • 4
  • 47
  • 60

2 Answers2

11

See section 5.9.4 of Writing R Extensions. Allocate and populate a vector of names, and set the names attribute on the list.

library(inline)
named <- cfunction(signature(), '
    /* allocate and populate list */
    SEXP OS = PROTECT(allocVector(VECSXP, 2));
    SET_VECTOR_ELT(OS, 0, allocMatrix(REALSXP, 5, 5));
    SET_VECTOR_ELT(OS, 1, allocVector(REALSXP, 5));

    /* create names */
    SEXP nms = PROTECT(allocVector(STRSXP, 2));
    SET_STRING_ELT(nms, 0, mkChar("foo"));
    SET_STRING_ELT(nms, 1, mkChar("bar"));

    /* assign names to list */
    setAttrib(OS, R_NamesSymbol, nms);

    /* cleanup and return */
    UNPROTECT(2);
    return OS;')
Martin Morgan
  • 45,935
  • 7
  • 84
  • 112
5

There may be a more idiomatic way to do this using R's C API functions -- I tend stick with C++ via Rcpp as it is safer and more concise -- but adding the following should work:

 SEXP n = PROTECT(Rf_allocVector(STRSXP, 2));
 prtCnt++;
 SET_STRING_ELT(n, 0, Rf_mkChar("a"));
 SET_STRING_ELT(n, 1, Rf_mkChar("b"));
 Rf_setAttrib(OS, R_NamesSymbol, n);

However, I strongly suggest using Rcpp because you can eliminate much of the boilerplate that comes with R's C functions. Here are two alternatives, along with a modified version of your original function:

#include <Rcpp.h>

// [[Rcpp::export]]
SEXP do_bla() {
   int prtCnt = 0;
   SEXP a = PROTECT(Rf_allocMatrix(REALSXP, 5, 5));
   prtCnt++;
   SEXP b = PROTECT(Rf_allocVector(REALSXP, 5));
   prtCnt++;
   SEXP OS = PROTECT(Rf_allocVector(VECSXP, 2));
   prtCnt++;
   SET_VECTOR_ELT(OS, 0, a);
   SET_VECTOR_ELT(OS, 1, b);

   SEXP n = PROTECT(Rf_allocVector(STRSXP, 2));
   prtCnt++;
   SET_STRING_ELT(n, 0, Rf_mkChar("a"));
   SET_STRING_ELT(n, 1, Rf_mkChar("b"));
   Rf_setAttrib(OS, R_NamesSymbol, n);

   UNPROTECT(prtCnt);
   return OS;
}

// [[Rcpp::export]]
SEXP do_bla2() {
    return Rcpp::List::create(
        Rcpp::Named("a") = Rcpp::NumericMatrix(5, 5),
        Rcpp::Named("b") = Rcpp::NumericVector(5));
}

// [[Rcpp::export]]
SEXP do_bla3() {
    Rcpp::NumericMatrix m(5, 5);
    Rcpp::NumericVector v(5);
    Rcpp::List res = Rcpp::List::create(m, v);
    res.names() = Rcpp::CharacterVector::create("a", "b");
    return res;
}

You may need to use mkChar and setAttrib instead of Rf_mkChar and Rf_setAttrib if you using <Rinternals.h> directly.


do_bla()
# $a
#               [,1]          [,2]          [,3]          [,4]          [,5]
# [1,] 2.371515e-322 4.743030e-322 9.654277e-315 8.695555e-322 6.518868e-310
# [2,] 2.794759e-316 2.371515e-322 6.763004e-317 2.371515e-322 6.952759e-310
# [3,] 3.458460e-323 2.797257e-316 1.630417e-322 2.852530e-316 1.630417e-322
# [4,] 6.441834e+170 1.976263e-323 4.092581e-316 1.976263e-323 4.125824e-316
# [5,] 1.818440e-306 6.952931e-310 4.008825e-316 2.121996e-314 2.154669e-316
# 
# $b
# [1] 2.144130e-316 2.168146e-316 3.468674e-316 2.155101e-316 2.172224e-316
# 
do_bla2()
# $a
#      [,1] [,2] [,3] [,4] [,5]
# [1,]    0    0    0    0    0
# [2,]    0    0    0    0    0
# [3,]    0    0    0    0    0
# [4,]    0    0    0    0    0
# [5,]    0    0    0    0    0
# 
# $b
#[1] 0 0 0 0 0

do_bla3()
# $a
#      [,1] [,2] [,3] [,4] [,5]
# [1,]    0    0    0    0    0
# [2,]    0    0    0    0    0
# [3,]    0    0    0    0    0
# [4,]    0    0    0    0    0
# [5,]    0    0    0    0    0
# 
# $b
#[1] 0 0 0 0 0
nrussell
  • 18,382
  • 4
  • 47
  • 60