No idea, your code (now that you're not using as.double) kinda works for me.

> source("test.R")
     [,1] [,2]
[1,]   21   20
[2,]   30    0
[3,]   40    0
verifie taille: 4
verifie de X: 4.000000 - 2.000000 - 3.000000 - 2.000000
verifie dX: 2 1 1
verifie de Z
4 1
40.000000 0.000000
21.000000 0.000000
30.000000 0.000000
> 

The only thing is that your code is very messy (for me at least), and it's
true that you print the value of ZT and it is a 3x3 matrix, but if you print
its value just before the .Call it is just a vector of length 4. Then
as.matrix() creates a 4x1 matrix of this. 

Look at this simple R code, it works with your test.c file fine:

##########################
dyn.load("test.so")

f.check <- function(a) a
XT <- 1:4
ZT <- matrix( c(21,30,40,20,0,0), nr=3, nc=2)
dXT <- 1:3
tailleS <- 5

.Call("VPCEfron",body(f.check),as.double(XT),as.matrix(ZT),as.integer(dXT),
      as.integer(tailleS),new.env()) 
#########################      

Gabor

On Fri, Feb 03, 2006 at 11:45:24AM +0100, [EMAIL PROTECTED] wrote:
> I correct a little my code, in R code, i use "as.matrix" for ZT, so i haven't
> got "segment fault" but it seems that i transmit only the first colon and
> because "ncol" gives "1" and not "2".
> 
> So what happen ?
> 
> Programs
> 
> ==== R CODE - test.R =====
> X<-c(4,2,3,2)
> Z<-c(40,21,30,20)
> dX<-c(2,1,1)
> 
> dyn.load("test.so")
> 
> Phi<-function(z,a,b)
> {
>       Phi<-z
> }
> 
> VPEfron<-function(XType,ZType,dXType,G,c0,c1)
> {
>       ####################
>       ZT<-matrix(0,3,2)
>       ZT[1,1]<-Z[2]
>       ZT[1,2]<-Z[4]
>       ZT[2,1]<-Z[3]
>       ZT[3,1]<-Z[1]
>       ####################
>       
>       print(ZT)
>       # A OPTIMISER
>       VPCEfron<-function(f,XT,ZT,dXT,tailleS)
>       {
>               f.check<-function(x) {
>             x<-f(x)
>             }
>      
> .Call("VPCEfron",body(f.check),as.double(XT),as.matrix(ZT),as.integer(dXT),as.integer(tailleS),new.env())
>       }
> 
>       GG<-function(z) G(z,c0,c1)
> 
> VPEfron<-VPCEfron(GG,XType,ZType,dXType,length(XType))
> }
> 
> resultat<-VPEfron(X,Z,dX,Phi,0,0)
> ==== END R CODE ==========
> 
> ==== C CODE of test.c ============
> #include <R.h>
> #include <Rdefines.h>
> #include <Rinternals.h>
> 
> #define RMATRIX(m,i,j) (REAL(m)[ INTEGER(GET_DIM(m))[0]*(j)+(i) ])
> 
> SEXP mkans(double x)
> {
>       SEXP ans;
>       PROTECT(ans = allocVector(REALSXP,1));
>       REAL(ans)[0]=x;
>       UNPROTECT(1);
>       return ans;
> }
> 
> SEXP VPCEfron(SEXP f, SEXP XR, SEXP ZR, SEXP DIR, SEXP tailleR, SEXP rho)
> {
>       double* X=REAL(XR);
>       int* DI=INTEGER(DIR);
>       int taille=INTEGER(tailleR)[0];
>       int nligne=INTEGER(GET_DIM(ZR))[0];
>       int ncol=INTEGER(GET_DIM(ZR))[1];
> 
>       printf("verifie taille: %d\n",taille);
>       printf("verifie de X: %f - %f - %f - %f\n",X[0],X[1],X[2],X[3]);
>       printf("verifie dX: %d %d %d\n",DI[0],DI[1],DI[2]);
> 
>       printf("verifie de Z\n");
>       printf("%d %d\n",nligne,ncol);
>       printf("%f %f\n",RMATRIX(ZR,0,0),RMATRIX(ZR,0,1));
>       printf("%f %f\n",RMATRIX(ZR,1,0),RMATRIX(ZR,1,1));
>       printf("%f %f\n",RMATRIX(ZR,2,0),RMATRIX(ZR,2,1));
> 
>       return mkans(0.0);
> }
> ==== END CODE =====
> 
> ----------------------------------------------------------------
> This message was sent using IMP, the Internet Messaging Program.

-- 
Csardi Gabor <[EMAIL PROTECTED]>    MTA RMKI, ELTE TTK

______________________________________________
[email protected] mailing list
https://stat.ethz.ch/mailman/listinfo/r-help
PLEASE do read the posting guide! http://www.R-project.org/posting-guide.html

Reply via email to