Fortran calling R

@Beliavsky, @edsterjo,

I have created a small example using RInside to call R from Fortran at: GitHub - ivan-pi/Fortran-RInside: Demonstration of Fortran interface to Rinside

Adapting your example it becomes as simple as:

program xcall_r
! Demonstrate Fortran calling R, passing data with binary file
use RInside_interface
implicit none
integer :: iter
integer, parameter :: n = 100000, bin_unit = 20, niter = 3
real(kind=kind(1.0d0)) :: x(n)
character (len=*), parameter :: bin_file = "double.bin"
logical, parameter :: call_r = .true.

call setupRinC()

do iter = 1, niter
  call random_number(x)
  write (*,"(a,f11.7)") "mean = ",sum(x)/n
  if (call_r) then
    open (unit=bin_unit,file=bin_file,action="write",access="stream",form="unformatted",status="replace")
    write (bin_unit) x
    close (bin_unit)
    call xread_bin()
  end if
end do

call teardownRinC()

contains

  subroutine xread_bin()
    type(SEXP) :: res
    type(SEXP) :: inp, x
    res = evalInR('inp = file("double.bin","rb")')

    res = evalInR('x = readBin(inp, "double",n=100000)') ! n is max number of values to read -- can read fewer
    res = evalInR('cat("from R: ",mean(x),"\n\n")')
    res = evalInR('close(inp)')
  end subroutine

end program xcall_r

and produces the output:

mean =   0.4990118
from R:  0.4990118 

mean =   0.4982012
from R:  0.4982012 

mean =   0.4998608
from R:  0.4998608 

For some reason if the array is too large (1000000 values) I get errors such as:

Error: C stack usage  8009524 is too close to the limit
Error: C stack usage  8009572 is too close to the limit
Error: C stack usage  8009460 is too close to the limit
Fatal error: unable to initialize the JIT

which seems to be related to the stack size settings of the R binary.

2 Likes