From: Bastian on
Hello,
I just switched to a 64-bit system and now the mex-files which did fine on a 32-bit are now causing a segmentation fault. I DID re-compile the fortran source files on the 64-bit system without any errors but apparently something needs adjustment.
Here is one of the short examples:

#include <fintrf.h>
SUBROUTINE MEXFUNCTION(NLHS, PLHS, NRHS, PRHS)
USE module_astron_constants
implicit none
MWPOINTER PLHS(*), PRHS(*)
INTEGER NLHS, NRHS
MWPOINTER MXCREATEDOUBLEMATRIX, MXGETPR
MWSIZE MXGETM, MXGETN

MWPOINTER out1_P
MWPOINTER in1_P
MWSIZE M, N, NEL
INTEGER::R_in1_P
DOUBLE PRECISION :: R_in1_P_real
DOUBLE PRECISION::out1
integer*4 mxIsDouble, mxIsComplex
mwSize mxGetNumberOfElements

! Check input/output
if( NLHS > 1 ) then
call mexErrMsgTxt("Too many outputs.")
endif
if( NRHS /=1 ) then
call mexErrMsgTxt("Incorrect number of inputs.")
endif
if( mxIsComplex(prhs(1)) /= 0 ) then
call mexErrMsgTxt("Inputs cannot be complex.")
endif
if( mxGetNumberOfElements(prhs(1)) /= 1 ) then
call mexErrMsgTxt("1st input must be an integer scalar.");
endif

! Matlab INPUT parameters
in1_P = MXGETPR(PRHS(1))

! COPY RIGHT HAND ARGUMENTS TO LOCAL ARRAYS OR VARIABLES
NEL = 1
CALL MXCOPYPTRTOREAL8(in1_P, R_in1_P_real, NEL)
R_in1_P=int(R_in1_P_real)

! ============DO THE ACTUAL COMPUTATIONS IN A SUBROUTINE !
out1=astron_constants(R_in1_P)

! Assign Matlab output
PLHS(1) = MXCREATEDOUBLEMATRIX(1,1,0) ! CREATE A scalar FOR RETURN ARGUMENT
out1_P = MXGETPR(PLHS(1)) ! initialize Matlab output parameter 1
CALL MXCOPYREAL8TOPTR(out1, out1_P, 1) ! copy value into Matlab output parameter

RETURN
END
From: James Tursa on
"Bastian " <nwmath.15.mage(a)spamgourmet.com> wrote in message <hjcfou$m4s$1(a)fred.mathworks.com>...
>
> PLHS(1) = MXCREATEDOUBLEMATRIX(1,1,0) ! CREATE A scalar FOR RETURN ARGUMENT

The interface in the MATLAB doc is as follows:

mwPointer mxCreateDoubleMatrix(m, n, ComplexFlag)
mwSize m, n
integer*4 ComplexFlag

It is possible that mwSize on your 64-bit system is an 8-byte integer, whereas the default integer type for your compiler is a 4-byte integer. If that is the case, the above call would not work for your hard coded constants in the argument list because of the mismatch. I would try the following:

integer*4 ComplexFlag
:
M = 1
N = 1
ComplexFlag = 0
PLHS(1) = MXCREATEDOUBLEMATRIX(M,N,ComplexFlag)

You might scrub your code and change all hard coded constant arguments to variables of the correct type.

I would also point out that these lines:

in1_P = MXGETPR(PRHS(1))
! COPY RIGHT HAND ARGUMENTS TO LOCAL ARRAYS OR VARIABLES
NEL = 1
CALL MXCOPYPTRTOREAL8(in1_P, R_in1_P_real, NEL)
R_in1_P=int(R_in1_P_real)

can be accomplished more simply as:

real*8, external :: mxGetScalar
:
R_in1_P = mxGetScalar(PRHS(1))

and these lines:

! Assign Matlab output
PLHS(1) = MXCREATEDOUBLEMATRIX(1,1,0) ! CREATE A scalar FOR RETURN ARGUMENT
out1_P = MXGETPR(PLHS(1)) ! initialize Matlab output parameter 1
CALL MXCOPYREAL8TOPTR(out1, out1_P, 1) ! copy value into Matlab output parameter

can be accomplished much more simply as:

mwPointer, external :: mxCreateDoubleScalar
:
PLHS(1) = mxCreateDoubleScalar(out1_P)

James Tursa
From: James Tursa on

P.S. One way to detect these types of errors is to download my Fortran 95 interface routines from here:

http://www.mathworks.com/matlabcentral/fileexchange/25934-fortran-95-interface-to-matlab-api-with-extras

In my code I have an explicit interface defined for *every* MATLAB API function, so if there is ever a integer*4 vs integer*8 mismatch (or any other type mismatch in the argument list for that matter) in the call it will be caught by the compiler. You simply compile up my supplied modules and then use them. This also eliminates the need to individually type all of the MATLAB API functions that you use in your code (like mxCreateDoubleMatrix, mxGetM, etc.) since that is already included in my modules.

James Tursa
From: Bastian on
Unfortunately the modified code also results in a segmentation fault. I've been trying to track the crash by inserting warning messages in the code but it does not seem to drop out at the same point consistently.
From: Bastian on
In the meantime I commented out almost everything in the gateway function. The moment I uncomment
PLHS(1) = MXCREATEDOUBLESCALAR(out1_P)
the crash occurs.
I also tried a different compiler (g95 instead of gfortran) and it seems to work fine. @James: Regarding the suggested API package, see my email.