Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
29274 Discussions

how to declare a fortran function that returns a c_ptr

MWind2
New Contributor III
5,545 Views

What does the declaration of a function look like that returns a c_ptr?

0 Kudos
23 Replies
mecej4
Honored Contributor III
4,688 Views
For any function whose return value is not an intrinsic type, you can use the RESULT(var) attribute in the function declaration. For example:

[fortran]function myalloc(nbytes) result(cptr) bind(C) use iso_c_binding integer, value :: nbytes type(c_ptr) :: cptr ... cptr = ... ... end function myalloc[/fortran] Is that what you had in mind?
0 Kudos
MWind2
New Contributor III
4,688 Views
I tried your syntax and got the same result as in my Function f2a where f2a = (what I thought was a good c_ptr) = afb.
I think my real problem is in misunderstanding the result of afb = c_loc(ab) where ab is an integer*1 array that has been filled with values from a read as expected.

My declarations for afb is type (c_ptr):: afb
0 Kudos
onkelhotte
New Contributor II
4,688 Views
Please provide some more code...

Markus
0 Kudos
MWind2
New Contributor III
4,688 Views
[cpp]





! Dllftrn3.f90 ! ! FUNCTIONS/SUBROUTINES exported from Dllftrn3.dll: ! Dllftrn3 - subroutine ! ! DllFtrn3.f90 ! ! FUNCTIONS/SUBROUTINES exported from DllFtrn1.dll: ! DllFtrn3 - subroutine ! !implicit none ! ! MODULE dllvars3 use ifport use iso_c_binding IMPLICIT NONE integer*4, static :: iunit=1024 public iunit contains subroutine DllFtrn3(ifeature) ! Expose subroutine DllFtrn3 to users of this DLL ! !DEC$ ATTRIBUTES DLLEXPORT,REFERENCE,DECORATE,ALIAS:'DllFtrn3' :: DllFtrn3 ! Variables INTEGER, INTENT(IN) :: ifeature end subroutine DllFtrn3 real*8 function x2y(x,y) !DEC$ ATTRIBUTES DLLEXPORT,DECORATE,REFERENCE,ALIAS:'x2y' ::x2y real*8, intent(in) :: x real*8, intent(in) :: y x2y = x**y end function x2y TYPE(c_ptr)function f2a(sfile, ilen) bind(c) !DEC$ ATTRIBUTES DLLEXPORT,DECORATE,ALIAS:'f2a' :: f2a use iso_c_binding type (c_ptr), TARGET :: afb integer*1, dimension(:),pointer ::pf_ab character(len = ilen, kind=c_char), intent(in):: sfile integer*4 ,intent(in) :: ilen integer*1, allocatable, dimension(:), TARGET :: ab integer*4 :: iiostat integer*4 :: isz = -1 integer*4 :: ifdata integer*4 :: iexists integer*4 :: ifN integer*4 :: ireturn = -1 integer*4 statarray(12), istat integer*4 ::iread !character :: charx character(ilen):: sfilef character(80) ::sline !need to validate sfile sfilef = sfile !charx = sfilef(1:1) iFN = 1024 !example, static module level iunit; !iunit= iunit+1 inquire(FILE=sfilef, EXIST=iexists) if (iexists==.true.) then print *,'File Exists' endif !open(iFN, file=sfilef, action='read',IOSTAT=iiostat,status='old')!, status='old', action='read') !read(iFN, *, IOSTAT=iiostat) sline open(iFN,file=sfilef,action='read',IOSTAT=iiostat,FORM='BINARY',ACCESS='SEQUENTIAL') ISTAT = FSTAT (iFN, statarray) if (.NOT. istat) then print *, statarray isz = statarray(8) end if afb = c_null_ptr !close (iFN) if (isz > 0) then ALLOCATE(ab(1:isz)) !open(iFN,file=sfilef,action='read',IOSTAT=iiostat,FORM='BINARY',ACCESS='SEQUENTIAL') read(iFN) ab close (iFN) pf_ab=>ab afb = C_LOC(pf_ab) !cptr = C_LOC(ab) !ireturn = isz else close (iFN) !ireturn = -1 endif !f2a = ireturn f2a = afb !cptr = c_null_ptr end function f2a end module[/cpp]


// dllftr1tstr.cpp : Defines the entry point for the console application. // #include "stdafx.h" #include #include "windows.h" //extern "C" __declspec(dllimport) double x2y(double *d1,double *d2); extern "C" __declspec(dllimport) char * f2a(char* sfn,int* ilen); int _tmain(int argc, _TCHAR* argv[]) { DWORD ilow,ihigh; double da = 3.0; double db = 5.0; double dc = x2y(&da,&db); //double * pdc = x2y(&da,&db); //double dc = *pdc; //wchar_t * fname = L"c:\\c\\05\\DllFtrn1\\dllftr1tstr\\dllftr1tstr.dat"; //HANDLE hf =CreateFile(fname,GENERIC_READ,FILE_SHARE_WRITE,NULL,OPEN_EXISTING,FILE_ATTRIBUTE_NORMAL,NULL); char * fname = "c:\\c\\05\\DllFtrn1\\dllftr1tstr\\dllftr1tstr.dat"; HANDLE hf =CreateFileA(fname,GENERIC_READ,FILE_SHARE_WRITE,NULL,OPEN_EXISTING,FILE_ATTRIBUTE_NORMAL,NULL); int iflen = GetFileSize(hf, &ihigh); CloseHandle(hf); //int i = wcslen(fname); int i = strlen(fname); //int ix = f2a(fname,&i); char *auB = f2a(fname,&i); return 0; }
0 Kudos
MWind2
New Contributor III
4,688 Views
I was stepping throughand watching disassembly
[fortran]if (isz > 0) then ALLOCATE(ab(1:isz)) !open(iFN,file=sfilef,action='read',IOSTAT=iiostat,FORM='BINARY',ACCESS='SEQUENTIAL') read(iFN) ab close (iFN) pf_ab=>ab afb = C_LOC(ab) else close (iFN) endif f2a = afb[/fortran]
and the address afb is correct to the data, but when the function returns to cpp, the memory is all a bunch of 0xee 0xfe 0xee 0xfe .... I think 0xFEEE is the filled pattern used by MS HeapFree API to mark freed heap memory block.
0 Kudos
Steven_L_Intel1
Employee
4,688 Views
You have not shown the whole routine. If ab is a local allocatable array, then it will be deallocated on exit unless given the SAVE attribute. Maybe that's what you need to add. I would perhaps suggest using POINTER rather than ALLOCATABLE in this case, then there is no need for SAVE. You will need to call back into Fortran to deallocate the storage (use C_F_POINTER to turn the C_PTR back to a Fortran pointer.)
0 Kudos
MWind2
New Contributor III
4,688 Views

Replacing the local variable ab with a module level ab_mod preserves the data and works as expected; however, if the function were called from cpp multithreaded it would be useless as is with ab_mod, but that is another problem. I would presume fortran will delete the old memory of ab_mod and reallocate some different new memory with each call to a ab_mod, rendering a previous pointer invalid.

0 Kudos
IanH
Honored Contributor III
4,688 Views
Your one dimensional array is a local variable of the function that is allocatable. When the function returns that variable is deallocated automatically. Pointers that formerly pointed to that deallocated variable are no longer defined.

To match this C++ declaration:

[cpp]extern "C" __declspec(dllimport) char * f2a(char* sfn,int* ilen);[/cpp]
Use this Fortran function signature:

[fortran]FUNCTION f2a(sfn, ilen) RESULT(pfa) BIND(C,NAME='f2a') !DEC$ ATTRIBUTES DLLEXPORT :: f2a USE, INTRINSIC :: ISO_C_BINDING, ONLY: C_PTR, C_INT, C_CHAR, C_LOC INTEGER(C_INT), INTENT(IN) :: ilen CHARACTER(KIND=C_CHAR), INTENT(IN) :: sfn(ilen) TYPE(C_PTR) :: f2a [/fortran]
Note that it is an array of characters, not a character string - this is the requirement under the standard. You then need to go through the mundane process of converting to a string, perhaps:

[fortran] CHARACTER(ilen) :: sfile INTEGER :: i ... FORALL (i=1:ilen) sfile(i:i) = sfn(i)[/fortran]
To get the address of your one dimensional array, perhaps:

[bash] INTEGER(1), POINTER :: pfa(:) ... ALLOCATE(pfa(some_size)) ... initialise (perhaps by READ) pfa f2a = C_LOC(pfa) [/bash]
Objects that have the pointer attribute are already TARGETs.

You then need to think about how that one dimensional array will be deallocated in future.
0 Kudos
MWind2
New Contributor III
4,688 Views
I realize nowI did not see the the possibility of using POINTER rather than ALLOCATABLE. I had gone off done a different way and was stumped on how to declare an array of POINTERS to ab objects as in
[fortran]! Dllftrn3.f90 ! ! FUNCTIONS/SUBROUTINES exported from Dllftrn3.dll: ! Dllftrn3 - subroutine ! ! DllFtrn3.f90 ! ! FUNCTIONS/SUBROUTINES exported from DllFtrn1.dll: ! DllFtrn3 - subroutine ! !implicit none ! ! MODULE dllvars3 use ifport use iso_c_binding IMPLICIT NONE integer*4, parameter :: IMAXFILES = Z'200' integer*4, parameter :: IFNADDN = Z'400' integer*4, parameter :: IPATHMAX = Z'200' integer*1, parameter :: IODISPOSED = -1 integer*1, parameter :: IOARRAYED = 0 integer*1, parameter :: IOIDD = 1 integer*4, static :: iunit=1024 public iunit integer*4, static :: f_id=0 public f_id integer*1,static :: a_id_disposed(IMAXFILES) integer*8,static :: a_id_size(IMAXFILES) ! ! How to declare array of POINTERS that will be used to store an ab type(integer*1, allocatable, dimension(:),TARGET),POINTER static :: a_id_fptr(IMAXFILES) ! integer*1, allocatable, dimension(:), TARGET :: ab_mod contains !DEC$ ATTRIBUTES DLLEXPORT,DECORATE,ALIAS:'get_f_id' :: get_f_id integer*4 function get_f_id(sfile) character(*, kind=c_char), intent(in):: sfile integer*4 :: f_idx integer*4 :: iFN integer*4 :: iiostat integer*4 statarray(12), istat integer*4 :: if_idx character(IPATHMAX) :: sfilef f_idx = f_id f_id = f_id + 1 iFN = f_idx + IFNADDN sfilef = sfile ! need to validate before assignment open(iFN,file=sfilef,action='read',IOSTAT=iiostat,FORM='BINARY',ACCESS='SEQUENTIAL') ISTAT = FSTAT (iFN, statarray) if (.NOT. istat) then a_id_size(f_idx) = statarray(8) a_id_disposed(f_idx)=IOIDD else a_id_size(f_idx) = IODISPOSED close(iFN) a_id_disposed(f_idx)= IODISPOSED end if get_f_id = a_id_size(f_idx) end function get_f_id !DEC$ ATTRIBUTES DLLEXPORT,DECORATE,ALIAS:'f_id2a' :: f_id2a TYPE (c_ptr) function f_id2a(f_idN) use iso_c_binding type (c_ptr), SAVE :: afb integer*4 ,intent(in) :: f_idN integer*4 iFN integer*1, allocatable, SAVE, dimension(:), TARGET :: ab if ( a_id_disposed(f_idN)==IOIDD) then iFN = f_idN + IFNADDN if (a_id_size(f_idN)> 0) then ALLOCATE(ab(1:a_id_size(f_idN))) a_id_fptr(f_idN)=>ab read(iFN) ab close (iFN) a_id_disposed(f_idN)=IOARRAYED afb = C_LOC(ab) else close (iFN) afb = c_null_ptr endif else afb = c_null_ptr endif f_id2a = afb end function f_id2a !DEC$ ATTRIBUTES DLLEXPORT,DECORATE,ALIAS:'del_f_id' :: del_f_id integer*4 function del_f_id(f_idN) integer*4, intent(in):: f_idN integer*4 :: ideleted = -1 if (a_id_disposed(f_idN)==IOARRAYED)then
! not sure if both needed, nothing done yet on checking on need to associate with c_ptr
! cannot declare a_id_fptr(IMAXFILES) properly DEALLOCATE(a_id_fptr(f_idN)) NULLIFY(a_id_fptr(f_idN)%ptr) a_id_disposed(f_idN)=IODISPOSED ideleted = 1 endif del_f_id = ideleted end function del_f_id TYPE(c_ptr)function f2a(sfile, ilen) bind(c) !DEC$ ATTRIBUTES DLLEXPORT,DECORATE,ALIAS:'f2a' :: f2a use iso_c_binding type (c_ptr) :: afb integer*1, dimension(:),pointer ::pf_ab character(len = ilen, kind=c_char), intent(in):: sfile integer*4 ,intent(in) :: ilen integer*1, allocatable, dimension(:), TARGET :: ab integer*4 :: iiostat integer*4 :: isz = -1 integer*4 :: ifdata integer*4 :: iexists integer*4 :: ifN integer*4 :: ireturn = -1 integer*4 statarray(12), istat integer*4 ::iread !character :: charx character(ilen):: sfilef character(80) ::sline !need to validate sfile sfilef = sfile !charx = sfilef(1:1) iFN = 1024 !example, static module level iunit; !iunit= iunit+1 inquire(FILE=sfilef, EXIST=iexists) if (iexists==.true.) then print *,'File Exists' endif !open(iFN, file=sfilef, action='read',IOSTAT=iiostat,status='old')!, status='old', action='read') !read(iFN, *, IOSTAT=iiostat) sline open(iFN,file=sfilef,action='read',IOSTAT=iiostat,FORM='BINARY',ACCESS='SEQUENTIAL') ISTAT = FSTAT (iFN, statarray) if (.NOT. istat) then print *, statarray isz = statarray(8) end if !afb = c_null_ptr !close (iFN) if (isz > 0) then !ALLOCATE(ab(1:isz)) ALLOCATE(ab_mod(1:isz)) !open(iFN,file=sfilef,action='read',IOSTAT=iiostat,FORM='BINARY',ACCESS='SEQUENTIAL') !read(iFN) ab read(iFN) ab_mod close (iFN) !pf_ab=>ab afb = C_LOC(ab_mod) !ireturn = isz else close (iFN) !ireturn = -1 endif !f2a = ireturn f2a = afb !cptr = c_null_ptr end function f2a end module[/fortran]
0 Kudos
MWind2
New Contributor III
4,688 Views
rethinking my mess, I was trying to make a simple example of a function that would return an c char array pointer and a length, perhapsin a fortranstructure, and when the c program is through with the data, a way to call the fortran unit to dispose of the fortran array and presumably the c array as well. How would I use
"I would perhaps suggest using POINTER rather than ALLOCATABLE in this case, then there is no need for SAVE"?



[fortran]! Dllftrn3.f90 ! ! FUNCTIONS/SUBROUTINES exported from Dllftrn3.dll: ! Dllftrn3 - subroutine ! ! DllFtrn3.f90 ! ! FUNCTIONS/SUBROUTINES exported from DllFtrn1.dll: ! DllFtrn3 - subroutine ! !implicit none ! ! MODULE dllvars3 use ifport use iso_c_binding IMPLICIT NONE type pfi1 integer*1, dimension(:),pointer :: pf_ab endtype integer*4, static :: iunit = 1024 contains !DEC$ ATTRIBUTES DLLEXPORT,DECORATE,ALIAS:'f2a' :: f2a TYPE(c_ptr)function f2a(sfile, ilen) bind(c) type (c_ptr), save :: afb character(len = ilen, kind=c_char), intent(in):: sfile integer*4 ,intent(in) :: ilen integer*1, allocatable, dimension(:), save, TARGET :: ab integer*4 :: iiostat integer*4 :: isz = -1 integer*4 :: ifdata integer*4 :: iexists integer*4 :: ifN integer*4 statarray(12), istat !character :: charx character(ilen):: sfilef !need to validate sfile sfilef = sfile iFN = iunit !example, static module level iunit; iunit= iunit+1 inquire(FILE=sfilef, EXIST=iexists) open(iFN,file=sfilef,action='read',IOSTAT=iiostat,FORM='BINARY',ACCESS='SEQUENTIAL') ISTAT = FSTAT (iFN, statarray) if (.NOT. istat) then print *, statarray isz = statarray(8) end if if (isz > 0) then ALLOCATE(ab(1:isz)) !open(iFN,file=sfilef,action='read',IOSTAT=iiostat,FORM='BINARY',ACCESS='SEQUENTIAL') !read(iFN) ab read(iFN) ab close (iFN) !pf_ab=>ab afb = C_LOC(ab) else close (iFN) endif f2a = afb end function f2a integer*4 function del_array(cptr0) type(c_ptr),intent(in) :: cptr0 integer*4 :: iout = -1 ! The details.... del_array = iout end function del_array end module[/fortran]


0 Kudos
IanH
Honored Contributor III
4,688 Views
You can still use an allocatable - the variable could be a (saved) allocatable module variable, which will retains its allocation status after a call to a procedure in the module completes. If you are going to apply C_LOC to such a variable (after it has been allocated) then it would also need to explicitly have the TARGET attribute.

I don't follow what you are trying to do with your most recent chunk of code. There is no "static" attribute in standard fortran. If you want an array of fortran pointers (as opposed to a fortran pointer to an array) then you need to wrap a pointer component in a derived type.

TYPE PtrToInteger
INTEGER, POINTER :: item
END TYPE PtrToInteger

would then let you build an arrays of fortran pointers to integer scalars:

INTEGER, TARGET :: a, b, c
TYPE(PtrToInteger) :: pointer_array(3)

pointer_array(1)%item => a
pointer_array(2)%item => b
pointer_array(3)%item => c

If you wanted an array of fortran pointers to integer arrays, then you would make the item pointer component an array as well. None of this has necessarily anything to do with C pointers, C_LOC, etc.

(I recommend that you lose the habit of declaring variables with the non-standard type*n (integer*4, etc) syntax. The f90 syntax has been around for two decades now! You are using the F90 syntax with your character variable declarations, why not be consistent?)

0 Kudos
MWind2
New Contributor III
4,688 Views

What I am trying to accomplish is to be able to delete the array ab when the cpp part is done with it. I don't get how to implement that in del_array. I have changed the content of the array by putting its size in bytes at the front to make things easier to use in cpp. Presumably one would like to call into f2a several times with different files being read into an array that would persist. Then, as needed, a call back to del_array with the appropriate values would result in the particular array being deleted. I would not mind even putting more data in the array that goes to cpp that would enable such.

[fortran]! Dllftrn3.f90 ! ! FUNCTIONS/SUBROUTINES exported from Dllftrn3.dll: ! Dllftrn3 - subroutine ! ! DllFtrn3.f90 ! ! FUNCTIONS/SUBROUTINES exported from DllFtrn1.dll: ! DllFtrn3 - subroutine ! !implicit none ! ! MODULE dllvars3 use ifport use, intrinsic :: iso_c_binding IMPLICIT NONE !type pfi1 ! integer*1, dimension(:),pointer :: pf_ab !endtype integer :: iunit = 1024 contains !DEC$ ATTRIBUTES DLLEXPORT,DECORATE,ALIAS:'f2a' :: f2a TYPE(c_ptr)function f2a(sfile, ilen) bind(c) type (c_ptr), save :: afb character(len = ilen, kind=c_char), intent(in):: sfile integer ,intent(in) :: ilen integer(1), allocatable, dimension(:), save, TARGET :: ab integer(1), dimension(:),pointer :: pf_ab integer :: indx, itemp0, itemp1 integer :: iiostat integer :: isz = -1 integer :: ifdata integer :: iexists integer :: ifN integer statarray(12), istat character(ilen):: sfilef !need to validate sfile sfilef = sfile iFN = iunit !example, static module level iunit; iunit= iunit+1 inquire(FILE=sfilef, EXIST=iexists) open(iFN,file=sfilef,action='read',IOSTAT=iiostat,FORM='BINARY',ACCESS='SEQUENTIAL') ISTAT = FSTAT (iFN, statarray) if (.NOT. istat) then print *, statarray isz = statarray(8) end if if (isz > 0) then ALLOCATE(ab(1:isz+8)) !open(iFN,file=sfilef,action='read',IOSTAT=iiostat,FORM='BINARY',ACCESS='SEQUENTIAL') !read(iFN) ab itemp0 = isz do indx = 0,3,1 itemp1 = ibits(itemp0,indx*8,8) ab(indx+1)= itemp1 enddo read(iFN) (ab(indx),indx=5,isz+4,1) close (iFN) pf_ab=>ab afb = C_LOC(ab) else close (iFN) endif f2a = afb end function f2a !DEC$ ATTRIBUTES DLLEXPORT,DECORATE,ALIAS:'del_array' :: del_array integer function del_array(cptr0, ilen) type(c_ptr),intent(in) :: cptr0 integer, intent(in) :: ilen integer(1), dimension(:),pointer :: fptr0 integer :: iout = -1 ! The details.... !call C_F_POINTER(cptr0,fptr0) !deallocate(fptr0) !nullify(fptr0) del_array = iout end function del_array end module
#include "stdafx.h"
#include  
#include 
#include "windows.h"
//extern "C" __declspec(dllimport) double x2y(double *d1,double *d2);
extern "C"  __declspec(dllimport) char *  f2a(char* sfn,int* ilen);
extern "C"  __declspec(dllimport) int *  del_array(char** paB, int* ilen);

int _tmain(int argc, _TCHAR* argv[])
{
	DWORD ilow,ihigh;
	double da = 3.0;
	double db = 5.0;
    //double dc = x2y(&da,&db);
	//wchar_t * fname = L"c:\c\05\DllFtrn1\dllftr1tstr\dllftr1tstr.dat";
	//HANDLE hf =CreateFile(fname,GENERIC_READ,FILE_SHARE_WRITE,NULL,OPEN_EXISTING,FILE_ATTRIBUTE_NORMAL,NULL);
	char * fname = "c:\c\05\DllFtrn1\dllftr1tstr\dllftr1tstr.dat";
	HANDLE hf =CreateFileA(fname,GENERIC_READ,FILE_SHARE_WRITE,NULL,OPEN_EXISTING,FILE_ATTRIBUTE_NORMAL,NULL);
	int iflen = GetFileSize(hf, &ihigh);
	CloseHandle(hf);
	//int i = wcslen(fname);
	int i = strlen(fname);
	//int ix = f2a(fname,&i);
	char *auB = f2a(fname,&i);
	int ilen = *((int *) auB);
	for (int i = 0; i 
0 Kudos
MWind2
New Contributor III
4,688 Views
Would you take a look at post 12 please, and show me the proper way to associate the cptr with the fptr in the del_array?
0 Kudos
MWind2
New Contributor III
4,688 Views
Gettingcloser. I was passing the wrong length for the shape and always getting a nullptr.

But now, with the array ab showing up in the debugger when delete_array called, I get

forrtl: severe (173): A pointer passed to DEALLOCATE points to an array that can

not be deallocated

[fortran]integer function del_array(cptr0, ilen) type(c_ptr),intent(in) :: cptr0 integer, intent(in) :: ilen integer(1), dimension(:),pointer :: fptr0 integer :: iout = -1 ! The details.... call C_F_POINTER(cptr0,fptr0,[ilen]) deallocate(fptr0) del_array = iout end function del_array[/fortran]
where the c part has changed to
[cpp] int ilen = *((int *) auB); int iaUBlen = ilen+4; for (int i = 0; i
0 Kudos
MWind2
New Contributor III
4,688 Views
Changed all references to ab to pf_ab which is as below, but now the error is

forrtl: severe (173): A pointer passed to DEALLOCATE points to an array that can

not be deallocated


[fortran]!DEC$ ATTRIBUTES DLLEXPORT,DECORATE,ALIAS:'f2a' :: f2a TYPE(c_ptr)function f2a(sfile, ilen) bind(c) type (c_ptr), save :: afb character(len = ilen, kind=c_char), intent(in):: sfile integer ,intent(in) :: ilen ! integer(1), allocatable, dimension(:),save, TARGET :: ab integer(1), dimension(:),pointer :: pf_ab integer :: indx, itemp0, itemp1 integer :: iiostat integer :: isz = -1 integer :: ifdata integer :: iexists integer :: ifN integer statarray(12), istat character(ilen):: sfilef !need to validate sfile sfilef = sfile iFN = iunit !example, static module level iunit; iunit= iunit+1 inquire(FILE=sfilef, EXIST=iexists) open(iFN,file=sfilef,action='read',IOSTAT=iiostat,FORM='BINARY',ACCESS='SEQUENTIAL') ISTAT = FSTAT (iFN, statarray) if (.NOT. istat) then print *, statarray isz = statarray(8) end if if (isz > 0) then !ALLOCATE(ab(1:isz+8)) ALLOCATE(pf_ab(1:isz+8)) !open(iFN,file=sfilef,action='read',IOSTAT=iiostat,FORM='BINARY',ACCESS='SEQUENTIAL') !read(iFN) ab itemp0 = isz do indx = 0,3,1 itemp1 = ibits(itemp0,indx*8,8) !ab(indx+1)= itemp1 pf_ab(indx+1) = itemp1 enddo !read(iFN) (ab(indx),indx=5,isz+4,1) read(iFN) (pf_ab(indx),indx=5,isz+4,1) close (iFN) !afb = C_LOC(ab) afb = C_LOC(pf_ab) else close (iFN) endif f2a = afb end function f2a !DEC$ ATTRIBUTES DLLEXPORT,DECORATE,ALIAS:'del_array' :: del_array integer function del_array(cptr0, ilen) type(c_ptr),intent(in) :: cptr0 integer, intent(in) :: ilen integer(1), dimension(:),pointer :: fptr0 integer :: iout = -1 ! The details.... call C_F_POINTER(cptr0,fptr0,[ilen]) deallocate(fptr0) del_array = iout end function del_array[/fortran]
0 Kudos
MWind2
New Contributor III
4,688 Views
Tried changing afb from save to not, same error.

0 Kudos
IanH
Honored Contributor III
4,688 Views
(Note your replies are coming faster than I can write a single reply... this may be out of date)

You are taking the address of an allocatable, and then later on trying to deallocate it through a fortran pointer to the same object. That's not permitted in Fortran (see 6.7.3.3 in F2008) - otherwise the compiler may lose track of the status of the allocatable variable. (My previous comments about using an allocatable were in the context of stopping the object from disappearing when the procedure terminates.)

Switch back to a pointer declaration for the ab array in the f2a procedure and see what happens.

Note that the BIND attribute on a function or procedure (which seemed to be missing from your del_array procedure) allows you to specify its alias using standard syntax. Rather than:

[fortran]function f2a(...) bind(c) !DEC$ ATTRIBUTES DLLEXPORT, ALIAS:'f2a' :: f2a [/fortran]
you can just have:

[fortran]function f2a(...) bind(c,NAME='f2a') !DEC$ ATTRIBUTES DLLEXPORT :: f2a [/fortran]
(Without the name clause on bind there is some default, but I can never remember what it is (I just looked it up - it is lower case, which wasn't my initial guess...) so I always specifiy the binding name explicitly.)

If you ever have to move to a different compiler you will appreciate that you used the standard syntax.

(You can get rid of the !DEC$ ... DLLEXPORT line completely if you use a DEF file in linking that nominates the exports, but there's an argument for keeping that in the source to clarify your intent, plus things like DLL's and DLLEXPORT are inherently system specific, so if you move to a different processor then you'll probably need to rethink things anyway.)

Planning ahead again... it is not guaranteed by any means that a fortran default integer will always line up with a C integer (it is easy to find systems or even just compile options with the intel compiler which break that). Where you have integers that "interoperate" I would always be explicit about their kind, using the constants out of the iso_c_binding module.

While it is not an error, at the moment the arguments to the del_array are being passed by reference (the C declaration looks appropriate for that). However del_array never modifies those arguments (it modifies things those arguments point to, but not the arguments themselves). In this case I'd consider passing the arguments by value, just to make your intent clearer to those reading the C source.

[fortran]function del_array(cptr0, ilen) bind(c,name='del_array') use, intrinsic :: iso_c_binding, only: c_int, c_ptr, c_f_pointer type(c_ptr), intent(in), value :: cptr0 integer(c_int), intent(in), value :: ilen integer(c_int) :: del_array ... [/fortran]
[cpp]extern "C" __declspec(dllimport) int del_array(char* pab, int ilen); ... del_array(auB, ilen); [/cpp]
(Alternatively, you could have del_array do something like set the c_ptr to C_NULL_PTR to indicate that the object has been deallocated back in the C code. In this case stay with pass by reference and make the c_ptr argument INTENT(INOUT).)
0 Kudos
MWind2
New Contributor III
4,688 Views
Thanks for the information. I decided to try putting the pointer variable pf_ab at the module level and the error is gone, the array is deallocated and marked with 0xfeee upon return after del_array2. I don't know the cause of this behavior, but it would seem the easier path might be to use the module level variable with a management system like an id in the array that can be used tolink toa fp_ab array to be deallocated.
0 Kudos
MWind2
New Contributor III
4,688 Views
[fortran]ALLOCATE(apfi1(indx_fptr)%pf_ab(1:isz+8))[/fortran]

If I have

[fortran]type pfi1 integer*1, dimension(:),pointer :: pf_ab integer :: istate = -1 endtype TYPE(pfi1):: apfi1(256)[/fortran]

allocated it as

and now plan to compare as

[fortran]call C_F_POINTER(cptr0,fptr0,[ilen]) FIND_FINDX: do indx = 1, 256,1 if (apfi1(indx)%istate == 1) then if ( apfi1(indx)%pf_ab == fptr0) then deallocate(apfi1(indx)%pf_ab) apfi1(indx)%istate = -1 iout = indx exit FIND_FINDX endif endif enddo FIND_FINDX del_array3 = iout end function del_array3[/fortran]

I get an error I don't expect at

if ( apfi1(indx)%pf_ab) == fptr0) then

as

Error 1 Error: A scalar-valued expression is required in this context. C:\c\05\DllFtrn1\Dllftrn3\Dllftrn3.f90 227

How does one compare pointers for equality?

0 Kudos
JVanB
Valued Contributor II
4,377 Views
if(associated(apfi1(indx)%pf_ab, fptr0)) then
0 Kudos
Reply