[R] Pass an optional argument from Fortran subroutine to a R wrapper
Erin Hodgess
erinm.hodgess at gmail.com
Wed Sep 7 11:56:03 CEST 2016
Hello!
You can't really pass the matrix as a matrix. Send it as a vector,
re-construct it in the Fortran program.
Actually, if it's a covariance matrix and symmetric, you may be able to get
away with just sending part of the matrix. For example, if you have the
following:
covmat<- matrix(c(1,0.9,0.81,0.9,1,0.9,0.81,0.9,1),nrow=3,ncol=3,byrow=TRUE)
cov1 <- covmat[1:3]
Then pass cov1 as a numeric.
It's easier and faster to manipulate your covariance matrix in the Fortran
program.
Hope this helps.
Sincerely,
Erin
On Tue, Sep 6, 2016 at 2:51 PM, Kodalore Vijayan, Vineetha W <vwkv13 at mun.ca>
wrote:
> Hello,
>
> I have a Fortran subroutine which uses an optional argument in the call.
>
> subroutine data (n,ns,alpha,covmat,x,y)
>
> integer, intent(in):: n,ns
> double precision, intent(in) :: alpha
> double precision, intent(in), optional ::covmat(n,ns)
> double precision, intent(out) :: x(n),y(n)
> ....
> end subroutine data
>
> I tried the following R wrapper for this subroutine and got an error
> saying,
>
> Error in array(x, c(length(x), 1L), if (!is.null(names(x)))
> list(names(x), :
> 'data' must be of a vector type, was 'NULL'
>
> I'm not sure if I passed the arguments correctly in the .Fortran() call. I
> couldn't find anything helpful online. I would really appreciate any
> help/comments.
>
> data1 <- function(n,ns,alpha,covmat=NULL){
>
> tmp <- .Fortran("data",
> n = as.integer(n),ns= as.integer(ns)
> alpha=as.numeric(alpha),covmat=as.matrix(covmat),
> x=as.double(rep(0,n)),y=as.double(rep(0,n)))
> )
> }
> result <- list(x=tmp$x, y=tmp$y)
>
> return(result)
> }
>
> Thanks,
> Vineetha
>
> [[alternative HTML version deleted]]
>
> ______________________________________________
> R-help at r-project.org mailing list -- To UNSUBSCRIBE and more, see
> https://stat.ethz.ch/mailman/listinfo/r-help
> PLEASE do read the posting guide http://www.R-project.org/
> posting-guide.html
> and provide commented, minimal, self-contained, reproducible code.
>
--
Erin Hodgess
Associate Professor
Department of Mathematical and Statistics
University of Houston - Downtown
mailto: erinm.hodgess at gmail.com
[[alternative HTML version deleted]]
More information about the R-help
mailing list