Re: [Rd] C Interface
I'm not a windows expert. You have C code file (not cc or cpp): > R CMD SHLIB OrthoFunctions.c and you use g++ compiler... ok, we can use c++ compiler for c.. but it's looks like c++ code with c code inside: > extern "C" { Try it without "extern "C" and with gcc compiler instead g++. regards, daniel 2010/6/18 michael meyer : > Greetings, > > I am trying to call simple C-code from R. > I am on Windows XP with RTools installed. > > The C-function is > > #include > #include > #include > #include > > // prevent name mangling > extern "C" { > > SEXP __cdecl test(SEXP s){ > > SEXP result; > PROTECT(result = NEW_NUMERIC(1)); > double* ptr=NUMERIC_POINTER(result); > double t = *REAL(s); > double u = t-floor(t)-0.5; > if(u>0) *ptr=-1+4*u; else *ptr=-1-4*u; > Rprintf("The value is %f", *ptr); > UNPROTECT(1); > return result; > } > > }; > > It is compiled with > > R CMD SHLIB OrthoFunctions.c > > with flag > > MAKEFLAGS="CC=g++" > > > However when I call this code from R with > > test <- function(t){ > .Call("test",t) > } > dyn.load("./OrthoFunctions.dll") > test(0) > dyn.unload("./OrthoFunctions.dll") > > then R crashes. > > If I compile with the default flags (no extern "C", no __cdecl) I get an > error message about an undefined reference to "__gxx_personality_v0": > > C:\...>R CMD SHLIB OrthoFunctions.c > C:/Programme/R/R-2.10.1/etc/Makeconf:151: warning: overriding commands for > target `.c.o' > C:/Programme/R/R-2.10.1/etc/Makeconf:142: warning: ignoring old commands for > target `.c.o' > C:/Programme/R/R-2.10.1/etc/Makeconf:159: warning: overriding commands for > target `.c.d' > C:/Programme/R/R-2.10.1/etc/Makeconf:144: warning: ignoring old commands for > target `.c.d' > C:/Programme/R/R-2.10.1/etc/Makeconf:169: warning: overriding commands for > target `.m.o' > C:/Programme/R/R-2.10.1/etc/Makeconf:162: warning: ignoring old commands for > target `.m.o' > g++ -I"C:/Programme/R/R-2.10.1/include" -O2 -Wall -c > OrthoFunctions.c -o OrthoFunctions.o > gcc -shared -s -o OrthoFunctions.dll tmp.def OrthoFunctions.o > -LC:/Programme/R/R-2.10.1/bin -lR > OrthoFunctions.o:OrthoFunctions.c:(.eh_frame+0x11): undefined reference to > `__gxx_personality_v0' > collect2: ld returned 1 exit status > > > > I have a vague idea of the issue of calling conventions and was hoping that > the __cdecl > specifier would force the appropriate convention. > I also have Cygwin installed as part of the Python(x,y) distribution but I > am assuming that > R CMD SHLIB source.c > calls the right compiler. > > What could the problem be? > > Many thanks, > > > Michael > > [[alternative HTML version deleted]] > > __ > R-devel@r-project.org mailing list > https://stat.ethz.ch/mailman/listinfo/r-devel > __ R-devel@r-project.org mailing list https://stat.ethz.ch/mailman/listinfo/r-devel
Re: [Rd] [R] Use of .Fortran
Prof Brian Ripley wrote: > > Well, it is not Fortran 77 but Fortran 95, and so needs to be given a > .f95 extension to be sure to work. > I think most compilers only distinguish two fortran file extensions: .f or .f90. .f denotes fixed-form source code while .f90 denotes free-form. Some compilers also take the capitalized versions, .F and .F90, to indicate source code that must be run through a preprocessor. It is a little weird, but Fortran file extensions have nothing to do with the year of the language standard the code is to be compiled against. David Scott wrote: > > file SSFcoef.f > subroutine SSFcoef(nmax,nu,A,nrowA,ncolA) > implicit double precision(a-h,o-z) > implicit integer (i-n) > integer l,i,nmax > double precision nu,A(0:nmax,0:nmax) > A(0,0) = 1D0 > do l=1,nmax > do i=1,l-1 > A(l,i) = (-nu+i+l-1D0)*A(l-1,i)+A(l-1,i-1) > end do > A(l,0) = (-nu+l-1D0)*A(l-1,0) > A(l,l) = 1D0 > end do > return > end > I created a dll (this is windows) using R CMD SHLIB SSFcoef.f > Then my R code is: > > ### Load the compiled shared library in. > dyn.load("SSFcoef.dll") > > ### Write a function that calls the Fortran subroutine > SSFcoef <- function(nmax, nu){ > .Fortran("SSFcoef", >as.integer(nmax), >as.integer(nu) >)$A > } > > SSFcoef(10,2) > > which when run gives > >> SSFcoef(10,2) > NULL > > I am pretty sure the problem is that I am not dealing with the matrix A > properly. I also tried this on linux and got a segfault. > > Can anyone supply the appropriate modification to my call (and possibly to > the subroutine) to make this work? > When calling a Fortran function for R, for each argument that appears in the subroutine declaration: subroutine subName(...arg list...) You *must* provide a matching input to the .Fortran() call: .Fortran("subName", ...arg list...) In the case of arrays that are filled by the Fortran subroutine, just pass an empty vector of the appropriate length- perhaps created using the double() function. -Charlie - Charlie Sharpsteen Undergraduate-- Environmental Resources Engineering Humboldt State University -- View this message in context: http://r.789695.n4.nabble.com/Re-R-Use-of-Fortran-tp2260362p2261266.html Sent from the R devel mailing list archive at Nabble.com. __ R-devel@r-project.org mailing list https://stat.ethz.ch/mailman/listinfo/r-devel
[Rd] more powerful iconv
R community, As you may know, R's iconv doesn't work well converting to and from encodings that allow embedded nulls. For example > iconv("foo", to="UTF-16") Error in iconv("foo", to = "UTF-16") : embedded nul in string: '\xff\xfef\0o\0o\0' However, I don't believe embedded nulls are at issue here, but rather that R's iconv doesn't accept objects of type RAWSXP. The iconv mechanism, after all, operates on encoded binary data, and not necessarily null terminated C strings. I'd like to submit a very small patch (12 lines w/o documentation) that allows R's iconv to operate on raw objects, while not interfering or affecting the behavior of iconv on character vectors. To keep this message terse, I've put additional discussion, description of what the patch does, and examples here: http://biostatmatt.com/archives/456 Also, here is a link to the patch file: http://biostatmatt.com/R/R-devel-iconv-0.0.patch If this change is adopted, I'd be happy to submit a documentation patch also. -Matt Index: src/library/base/R/New-Internal.R === --- src/library/base/R/New-Internal.R (revision 52328) +++ src/library/base/R/New-Internal.R (working copy) @@ -239,7 +239,7 @@ iconv <- function(x, from = "", to = "", sub = NA, mark = TRUE) { -if(!is.character(x)) x <- as.character(x) +if(!is.character(x) && !is.raw(x)) x <- as.character(x) .Internal(iconv(x, from, to, as.character(sub), mark)) } Index: src/main/sysutils.c === --- src/main/sysutils.c (revision 52328) +++ src/main/sysutils.c (working copy) @@ -548,16 +548,17 @@ int mark; const char *from, *to; Rboolean isLatin1 = FALSE, isUTF8 = FALSE; + Rboolean isRawx = (TYPEOF(x) == RAWSXP); - if(TYPEOF(x) != STRSXP) - error(_("'x' must be a character vector")); + if(TYPEOF(x) != STRSXP && !isRawx) + error(_("'x' must be a character vector or raw")); if(!isString(CADR(args)) || length(CADR(args)) != 1) error(_("invalid '%s' argument"), "from"); if(!isString(CADDR(args)) || length(CADDR(args)) != 1) error(_("invalid '%s' argument"), "to"); if(!isString(CADDDR(args)) || length(CADDDR(args)) != 1) error(_("invalid '%s' argument"), "sub"); - if(STRING_ELT(CADDDR(args), 0) == NA_STRING) sub = NULL; + if(STRING_ELT(CADDDR(args), 0) == NA_STRING || isRawx) sub = NULL; else sub = translateChar(STRING_ELT(CADDDR(args), 0)); mark = asLogical(CAD4R(args)); if(mark == NA_LOGICAL) @@ -584,7 +585,7 @@ PROTECT(ans = duplicate(x)); R_AllocStringBuffer(0, &cbuff); /* 0 -> default */ for(i = 0; i < LENGTH(x); i++) { - si = STRING_ELT(x, i); + si = isRawx ? x : STRING_ELT(x, i); top_of_loop: inbuf = CHAR(si); inb = LENGTH(si); outbuf = cbuff.data; outb = cbuff.bufsize - 1; @@ -622,7 +623,7 @@ goto next_char; } - if(res != -1 && inb == 0) { + if(res != -1 && inb == 0 && !isRawx) { cetype_t ienc = CE_NATIVE; nout = cbuff.bufsize - 1 - outb; @@ -632,7 +633,12 @@ } SET_STRING_ELT(ans, i, mkCharLenCE(cbuff.data, nout, ienc)); } - else SET_STRING_ELT(ans, i, NA_STRING); + else if(!isRawx) SET_STRING_ELT(ans, i, NA_STRING); + else { + nout = cbuff.bufsize - 1 - outb; + ans = allocVector(RAWSXP, nout); + memcpy(RAW(ans), cbuff.data, nout); + } } Riconv_close(obj); R_FreeStringBuffer(&cbuff); -- Matthew S. Shotwell Graduate Student Division of Biostatistics and Epidemiology Medical University of South Carolina http://biostatmatt.com __ R-devel@r-project.org mailing list https://stat.ethz.ch/mailman/listinfo/r-devel
Re: [Rd] [R] Use of .Fortran
Thanks very much to all who replied. I went with Brian's approach, and eventually, despite all my attempts to foul it up, I did get it to work successfully. For the record here are the details. The subroutine is: subroutine SSFcoef(nmax,nu,A) implicit double precision(a-h,o-z) implicit integer (i-n) integer k,i,nmax double precision nu,A(0:nmax,0:nmax) A(0,0) = 1D0 do k=1,nmax do i=1,k-1 A(k,i) = (-nu+i+k-1D0)*A(k-1,i)+A(k-1,i-1) end do A(k,0) = (-nu+k-1D0)*A(k-1,0) A(k,k) = 1D0 end do return end This was in the file SSFcoef.f95 and was made into a dll with R CMD SHLIB SSFcoef.f95 Then calling it in R went like this: ### Load the compiled shared library in. dyn.load("SSFcoef.dll") ### Write a function that calls the Fortran subroutine SSFcoef <- function(nmax, nu){ .Fortran("SSFcoef", as.integer(nmax), as.double(nu), A = matrix(0, nmax+1, nmax+1) )$A } SSFcoef(10,2) There are a number of comments I should make. Yes, Brian, should have gone to R-devel. I had forgotten about that. I recognised from my faintly recalled past Fortran experience that the code was different and suspected a later Fortran, so good to be advised it was 95. I actually gave a wrong version of the Fortran subroutine, one I had been messing around with and had added some extra arguments (nrowA and ncolA). As pointed out these were unnecessary. Something which then caused me a bit of grief before I noticed it. Despite the 'implicit integer (i-n)' declaration in the subroutine, nu is later declared to be double so has to be specified as double in the R code. Many thanks again, I at least learnt something about calling other language code from R. David Prof Brian Ripley wrote: On Sat, 19 Jun 2010, David Scott wrote: I have no experience with incorporating Fortran code and am probably doing something pretty stupid. Surely you saw in the posting guide that R-help is not the place for questions about C, C++, Fortran code? Diverting to R-devel. I want to use the following Fortran subroutine (not written by me) in the Well, it is not Fortran 77 but Fortran 95, and so needs to be given a .f95 extension to be sure to work. file SSFcoef.f subroutine SSFcoef(nmax,nu,A,nrowA,ncolA) implicit double precision(a-h,o-z) implicit integer (i-n) integer l,i,nmax double precision nu,A(0:nmax,0:nmax) A(0,0) = 1D0 do l=1,nmax do i=1,l-1 A(l,i) = (-nu+i+l-1D0)*A(l-1,i)+A(l-1,i-1) end do A(l,0) = (-nu+l-1D0)*A(l-1,0) A(l,l) = 1D0 end do return end I created a dll (this is windows) using R CMD SHLIB SSFcoef.f Then my R code is: ### Load the compiled shared library in. dyn.load("SSFcoef.dll") ### Write a function that calls the Fortran subroutine SSFcoef <- function(nmax, nu){ .Fortran("SSFcoef", as.integer(nmax), as.integer(nu) )$A } That does not match. nrowA and ncolA are unused, so you need SSFcoef <- function(nmax, nu){ .Fortran("SSFcoef", as.integer(nmax), as.integer(nu), A = matrix(0, nmax+1, nmax+1), 0L, 0L)$A } SSFcoef(10,2) which when run gives SSFcoef(10,2) NULL I am pretty sure the problem is that I am not dealing with the matrix A properly. I also tried this on linux and got a segfault. Can anyone supply the appropriate modification to my call (and possibly to the subroutine) to make this work? David Scott -- _ David Scott Department of Statistics The University of Auckland, PB 92019 Auckland 1142,NEW ZEALAND Phone: +64 9 923 5055, or +64 9 373 7599 ext 85055 Email: d.sc...@auckland.ac.nz, Fax: +64 9 373 7018 Director of Consulting, Department of Statistics __ R-devel@r-project.org mailing list https://stat.ethz.ch/mailman/listinfo/r-devel