[Rd] is.loaded() and dyn.load()

Prof Brian Ripley ripley at stats.ox.ac.uk
Thu Apr 5 17:23:38 CEST 2007


Did you read the comments under ?.Fortran about this?  What you are doing 
is quite explicitly said not to be supported.

gfortran is not a supported Fortran compiler for R for Windows 2.4.1.
It behaves differently from the supported g77.
The behaviour is adapted to the compiler used when configure is used, and 
on Windows that is what the maintainers used, not you are using.  If you 
follow the advice not to use underscores in names you are much less likely 
to confuse yourself and produce portable code.

On Thu, 5 Apr 2007, Simone Giannerini wrote:

> Dear all,
>
> I am puzzled at the behaviour of is.loaded() when a dyn.load() call to a a
> FORTRAN shared library is included in a file to be sourced.
> A reproducible example is the following:
>
> 1. the attached fortran subroutine try_it.f90 performs a summation of the
> elements of a REAL*8 vector
> compile with
>
> gfortran try_it.f90 -shared -s -otry_it.dll
>
> 2. create a file to be sourced (see the attached try_it.R) containing the
> following commands:
>
> BEGIN try_it.R ************************************
> dyn.load("try_it.dll");
>
>
> try.it <- function(X){
>   N <- length(X);
>   S <- .Fortran("try_it_",as.double(X),as.integer(N),S=as.double(0))$S
>   return(S)
> }
> END try_it.R ************************************
>
>
> 3. Switch to R
>
>> source("try_it.R")
>> try.it(1:10)
> Error in .Fortran("try_it_", as.double(X), as.integer(N), S = as.double(0))
> :
>       Fortran symbol name "try_it_" not in load table
>> is.loaded("try_it_")
> [1] TRUE
>> try.it(1:10)
> [1] 55
>> 
> it looks like is.loaded() triggers the loading, inserting
> is.loaded("try_it_")in
> the file try_it.R does the trick but
> is this behaviour expected?
>
> Thank you,
>
> Regards
>
> Simone
>
>> R.version
>              _
> platform       i386-pc-mingw32
> arch           i386
> os             mingw32
> system         i386, mingw32
> status
> major          2
> minor          4.1
> year           2006
> month          12
> day            18
> svn rev        40228
> language       R
> version.string R version 2.4.1 (2006-12-18)
>

-- 
Brian D. Ripley,                  ripley at stats.ox.ac.uk
Professor of Applied Statistics,  http://www.stats.ox.ac.uk/~ripley/
University of Oxford,             Tel:  +44 1865 272861 (self)
1 South Parks Road,                     +44 1865 272866 (PA)
Oxford OX1 3TG, UK                Fax:  +44 1865 272595



More information about the R-devel mailing list