Re: [Rd] Garbage collection of seemingly PROTECTed pairlist
I put your code into a file tmp.R and eliminated the need for a package by compiling this to a shared object R CMD SHLIB tmp.c I'm then able to use a simple script 'tmp.R' dyn.load("/tmp/tmp.so") fullocate <- function(int_mat) .Call("C_fullocate", int_mat) int_mat <- rbind(c(5L, 6L), c(7L, 10L), c(20L, 30L)) while(TRUE) res <- fullocate(int_mat) to generate a segfault. Looking at your code, it seemed like I could get towards a simpler reproducible example by eliminating most of the 'while' loop and then functions and code branches that are not used #include SEXP C_int_mat_nth_row_nrnc(int *int_mat_int, int nr, int nc, int n) { SEXP out = PROTECT(Rf_allocVector(INTSXP, nc)); int *out_int = INTEGER(out); for (int i = 0; i != nr; ++i) { out_int[i] = int_mat_int[n - 1 + i * nr]; } UNPROTECT(1); return out;} SEXP C_fullocate(SEXP int_mat) { int nr = Rf_nrows(int_mat), *int_mat_int = INTEGER(int_mat); int row_num = 2; // row_num will be 1-indexed SEXP prlst0cdr = PROTECT(C_int_mat_nth_row_nrnc(int_mat_int, nr, 2, 1)); SEXP prlst = PROTECT(Rf_list1(prlst0cdr)); SEXP row = PROTECT(C_int_mat_nth_row_nrnc(int_mat_int, nr, 2, row_num)); Rf_PrintValue(prlst); // This is where the error occurs UNPROTECT(3); return R_NilValue; } my script still gives an error, but not a segfault, and the values printed sometimes differ between calls ... [[1]] [1] 5 6 . [[1]] NULL ... Error in FUN(X[[i]], ...) : cannot coerce type 'NULL' to vector of type 'character' Calls: message -> .makeMessage -> lapply Execution halted The differing values in particular, and the limited PROTECTion in the call and small allocations (hence limited need / opportunity for garbage collection), suggest that you're corrupting memory, rather than having a problem with garbage collection. Indeed, SEXP prlst0cdr = PROTECT(C_int_mat_nth_row_nrnc(int_mat_int, nr, 2, 1)); allocates a vector of length 2 at SEXP out = PROTECT(Rf_allocVector(INTSXP, nc)); but writes three elements (the 0th, 1st, and 2nd) at for (int i = 0; i != nr; ++i) { out_int[i] = int_mat_int[n - 1 + i * nr]; } Martin Morgan On 9/11/20, 9:30 PM, "R-devel on behalf of Rory Nolan" wrote: I want to write an R function using R's C interface that takes a 2-column matrix of increasing, non-overlapping integer intervals and returns a list with those intervals plus some added intervals, such that there are no gaps. For example, it should take the matrix rbind(c(5L, 6L), c(7L, 10L), c(20L, 30L)) and return list(c(5L, 6L), c(7L, 10L), c(11L, 19L), c(20L, 30L)). Because the output is of variable length, I use a pairlist (because it is growable) and then I call Rf_PairToVectorList() at the end to make it into a regular list. I'm getting a strange garbage collection error. My PROTECTed pairlist prlst gets garbage collected away and causes a memory leak error when I try to access it. Here's my code. #include SEXP C_int_mat_nth_row_nrnc(int *int_mat_int, int nr, int nc, int n) { SEXP out = PROTECT(Rf_allocVector(INTSXP, nc)); int *out_int = INTEGER(out); if (n <= 0 | n > nr) { for (int i = 0; i != nc; ++i) { out_int[i] = NA_INTEGER; } } else { for (int i = 0; i != nr; ++i) { out_int[i] = int_mat_int[n - 1 + i * nr]; } } UNPROTECT(1); return out;} SEXP C_make_len2_int_vec(int first, int second) { SEXP out = PROTECT(Rf_allocVector(INTSXP, 2)); int *out_int = INTEGER(out); out_int[0] = first; out_int[1] = second; UNPROTECT(1); return out;} SEXP C_fullocate(SEXP int_mat) { int nr = Rf_nrows(int_mat), *int_mat_int = INTEGER(int_mat); int last, row_num; // row_num will be 1-indexed SEXP prlst0cdr = PROTECT(C_int_mat_nth_row_nrnc(int_mat_int, nr, 2, 1)); SEXP prlst = PROTECT(Rf_list1(prlst0cdr)); SEXP prlst_tail = prlst; last = INTEGER(prlst0cdr)[1]; row_num = 2; while (row_num <= nr) { Rprintf("row_num: %i\n", row_num); SEXP row = PROTECT(C_int_mat_nth_row_nrnc(int_mat_int, nr, 2, row_num)); Rf_PrintValue(prlst); // This is where the error occurs int *row_int = INTEGER(row); if (row_int[0] == last + 1) { Rprintf("here1"); SEXP next = PROTECT(Rf_list1(row)); prlst_tail = SETCDR(prlst_tail, next); last = row_int[1]; UNPROTECT(1); ++row_num; } else { Rprintf("here2"); SEXP next_car = PROTECT(C_make_len2_int_vec(last + 1, row_int[0] - 1)); SEXP next = PROTECT(Rf_list1(next_car)); prlst_tail = SETCDR(prlst_tail, next); last = row_int[0] - 1; UNPROTECT(2); } UNPROTECT(1);
Re: [Rd] parRapply and parCapply return a list in corner cases
For the record: I filed a bug report here https://bugs.r-project.org/bugzilla/show_bug.cgi?id=17807 and this is a more polished minimal example library(parallel) nslaves <- 2 cl <- makeCluster(nslaves) X <- matrix(c(1,0,1),1,3) res <- parCapply(cl,X,FUN=function(x){ y <- x[1] if(y==1){ out <- y }else{ out <- double(0) } return(out) }) > res [[1]] [1] 1 [[2]] numeric(0) [[3]] [1] 1 Simone On Mon, May 18, 2020 at 5:23 PM Simone Giannerini wrote: > > According to ?parCapply: > > parRapply and parCapply always return a vector. > > This appears not to be the case in the following minimal reproducible example: > > > library(parallel) > > nslaves <- 2 > > cl <- makeCluster(nslaves) > > X <- matrix(2,nrow=3,ncol=4) > > X <- rbind(c(1,1,0,1),X) > > tv <- parCapply(cl,X,FUN=function(x){ > + ind <- x[1] > + y <- x[-1] > + if(ind==1){ > + r1 <- sum(y) > + }else{ > + r1 <- logical(0) > + } > + return(unlist(as.numeric(c(ind,r1 > + }) > > tv > [[1]] > [1] 1 > > [[2]] > [1] 6 > > [[3]] > [1] 1 > > [[4]] > [1] 6 > > [[5]] > [1] 0 > > [[6]] > [1] 1 6 > > > class(tv) > [1] "list" > > sessionInfo() > R version 4.0.0 (2020-04-24) > Platform: x86_64-w64-mingw32/x64 (64-bit) > Running under: Windows 10 x64 (build 18363) > > Matrix products: default > > locale: > [1] LC_COLLATE=Italian_Italy.1252 LC_CTYPE=Italian_Italy.1252 > [3] LC_MONETARY=Italian_Italy.1252 LC_NUMERIC=C > [5] LC_TIME=Italian_Italy.1252 > > attached base packages: > [1] parallel stats graphics grDevices utils datasets > methods base > > loaded via a namespace (and not attached): > [1] compiler_4.0.0 > > -- > _ > > PHILOSOPHICAL TRANSACTIONS OF THE ROYAL SOCIETY A > Theme issue ‘DNA as information’ > edited by Julyan H.E. Cartwright, Simone Giannerini and Diego L. González > _ > > Simone Giannerini > Dipartimento di Scienze Statistiche "Paolo Fortunati" > Universita' di Bologna > Via delle belle arti 41 - 40126 Bologna, ITALY > Tel: +39 051 2098262 Fax: +39 051 232153 > https://www.unibo.it/sitoweb/simone.giannerini/ > __ -- ___ Simone Giannerini Dipartimento di Scienze Statistiche "Paolo Fortunati" Universita' di Bologna Via delle belle arti 41 - 40126 Bologna, ITALY Tel: +39 051 2098262 Fax: +39 051 232153 https://simonegiannerini.net/ __ R-devel@r-project.org mailing list https://stat.ethz.ch/mailman/listinfo/r-devel
[Rd] Thread-safe R functions
Hi, I am curious about whether there exist thread-safe functions in `Rinternals.h`. I know that R is single-threaded designed, but for the simple and straightforward functions like `DATAPTR` and `INTEGER_GET_REGION`, are these functions safe to call in a multi-thread environment? Best, Jiefei [[alternative HTML version deleted]] __ R-devel@r-project.org mailing list https://stat.ethz.ch/mailman/listinfo/r-devel
Re: [Rd] [External] Thread-safe R functions
You should assume that NO functions or macros in the R API are thread-safe. If some happen to be now, on some platforms, they are not guaranteed to be in the future. Even if you use a global lock you need to keep in mind that any function in the R API can signal an error and execute a longjmp, so you need to make sure you have set a top level context in your thread. Best, luke On Sun, 13 Sep 2020, Jiefei Wang wrote: Hi, I am curious about whether there exist thread-safe functions in `Rinternals.h`. I know that R is single-threaded designed, but for the simple and straightforward functions like `DATAPTR` and `INTEGER_GET_REGION`, are these functions safe to call in a multi-thread environment? Best, Jiefei [[alternative HTML version deleted]] __ R-devel@r-project.org mailing list https://stat.ethz.ch/mailman/listinfo/r-devel -- Luke Tierney Ralph E. Wareham Professor of Mathematical Sciences University of Iowa Phone: 319-335-3386 Department of Statistics andFax: 319-335-3017 Actuarial Science 241 Schaeffer Hall email: luke-tier...@uiowa.edu Iowa City, IA 52242 WWW: http://www.stat.uiowa.edu __ R-devel@r-project.org mailing list https://stat.ethz.ch/mailman/listinfo/r-devel
Re: [Rd] [External] Thread-safe R functions
Jiefei, Beyond the general response that Luke gave, to be a bit more specific to what you said, DATAPTR and INTEGER_GET_REGION involve ALTREP method execution (for ALTREP objects, obviously) so even they are not as simple and straightforward as they were a couple years ago. They should not (any longer) be thought of as being guaranteed to be essentially bare metal data retrieval from memory. Best, ~G On Sun, Sep 13, 2020 at 6:49 AM wrote: > You should assume that NO functions or macros in the R API are > thread-safe. If some happen to be now, on some platforms, they are > not guaranteed to be in the future. Even if you use a global lock you > need to keep in mind that any function in the R API can signal an > error and execute a longjmp, so you need to make sure you have set a > top level context in your thread. > > Best, > > luke > > On Sun, 13 Sep 2020, Jiefei Wang wrote: > > > Hi, > > > > I am curious about whether there exist thread-safe functions in > > `Rinternals.h`. I know that R is single-threaded designed, but for the > > simple and straightforward functions like `DATAPTR` and > `INTEGER_GET_REGION`, > > are these functions safe to call in a multi-thread environment? > > > Best, > > Jiefei > > > > [[alternative HTML version deleted]] > > > > __ > > R-devel@r-project.org mailing list > > https://stat.ethz.ch/mailman/listinfo/r-devel > > > > -- > Luke Tierney > Ralph E. Wareham Professor of Mathematical Sciences > University of Iowa Phone: 319-335-3386 > Department of Statistics andFax: 319-335-3017 > Actuarial Science > 241 Schaeffer Hall email: luke-tier...@uiowa.edu > Iowa City, IA 52242 WWW: http://www.stat.uiowa.edu > > __ > R-devel@r-project.org mailing list > https://stat.ethz.ch/mailman/listinfo/r-devel > [[alternative HTML version deleted]] __ R-devel@r-project.org mailing list https://stat.ethz.ch/mailman/listinfo/r-devel