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

Mixed language: convert from a integer(int_ptr_kind()) to a 'real' F90 pointer

gjhaarsma
Beginner
886 Views

We have a need to write mixed language code in which we call a Fortran DLL from C code. We need to perform memory allocation in the Fortran code. We have been able to successfully allocate and access the memory, but cannot seem to figure out how to deallocate.

Could somebody help me figuring out how to convert from a integer(int_ptr_kind()) to a 'real' F90 pointer. Any help or pointers (no pun indented) are appreciated.

I have put together some sample code (see attachment). The full application will have a much more complex data structure.

Kind regards,

Gabe Haarsma

int KernelCall(int i,void *P2);
int KernelAlloc(int i,void **P2);
int KernelDeAlloc(int i,void **P2);
0 Kudos
12 Replies
Jugoslav_Dujic
Valued Contributor II
886 Views
Your attachment didn't get through (I'm not sure if it was your fault or just another Forum quirk -- it has frequent issues of similar kind). So, it's difficult to tell exactly what you're trying to do.

Based on what you said, you use Fortran subroutines as allocators/deallocators (and probably number crunching); you return the addresses of allocated arrays to a C shell, (probably for input/output purposes), right?

The problem you're encountering now is that, once you allocate in Fortran and return only the address of the array, you lose the information which is contained in Fortran array descriptor. That information is needed for later deallocation; thus, you should pass it back as well.

I wrote a C++ template class which implements VF arrays/pointers/assumed-shape arrays in C++ (keeping much of Fortran semantics), so I could post it here with a sample code, but I'd prefer your reply first before I send it, (as it's kind of work-in-progress so it's not exactly tidied up).

Jugoslav
0 Kudos
gjhaarsma
Beginner
886 Views
Since the attachment did not make it, I will post the sample code below. An addidional complication is that the caller C function is written by another company. It is unlikely that they are willing to move from C to C++ and we need to keep the C side of the interface as simple as possible.

Once again thanks for any help.


!**********************************************************************
module SMOCPROWRAPPER_MODULE
!**********************************************************************
contains
!**********************************************************************
integer(4) function KernelCallWrapper(i,Vector)
implicit none

integer(4) :: i
real(8) :: Vector(i)

integer(4) :: j

do j=1,i
Vector(j)=j+j/10.0
end do


KernelCallWrapper=0

endfunction KernelCallWrapper
!**********************************************************************
integer(4) function KernelAllocWrapper(i,PtrVector)
implicit none

integer(4) :: i
integer(int_ptr_kind()) PtrVector

real(8), pointer :: F90_PointerVector(:)

allocate(F90_PointerVector(1:i))

PtrVector=%LOC(F90_PointerVector)

KernelAllocWrapper=0

endfunction KernelAllocWrapper
!**********************************************************************
integer(4) function KernelDeAllocWrapper(i,PtrVector)
implicit none

integer(4):: i
integer(int_ptr_kind()) PtrVector

! How to deallocate PointerVector.
! How to go back from a integer(int_ptr_kind()) to a 'real' F90 Pointer,
! so we can write:

! deallocate(F90_PointerVector)

KernelDeAllocWrapper=0

endfunction KernelDeAllocWrapper
!**********************************************************************

endmodule SMOCPROWRAPPER_MODULE
!**********************************************************************
!**********************************************************************
integer(4) function KernelCall(i,PtrVector)
use SMOCPROWRAPPER_MODULE
implicit none
!**********************************************************************
!DEC$ ATTRIBUTES C,ALIAS:'_KernelCall' ::KernelCall
!DEC$ ATTRIBUTES DLLEXPORT::KernelCall
!**********************************************************************
integer(4) :: i
integer(int_ptr_kind()) :: PtrVector

KernelCall=KernelCallWrapper(i,%val(PtrVector))

endfunction KernelCall

!**********************************************************************
integer(4) function KernelAlloc(i,PtrVector)
use SMOCPROWRAPPER_MODULE
implicit none
!**********************************************************************
!DEC$ ATTRIBUTES C,ALIAS:'_KernelAlloc' ::KernelAlloc
!DEC$ ATTRIBUTES DLLEXPORT::KernelAlloc
!**********************************************************************
integer(4) :: i
integer(int_ptr_kind()) :: PtrVector

KernelAlloc=KernelAllocWrapper(i,%val(PtrVector))

endfunction KernelAlloc

!**********************************************************************
integer(4) function KernelDeAlloc(i,PtrVector)
use SMOCPROWRAPPER_MODULE
implicit none
!**********************************************************************
!DEC$ ATTRIBUTES C,ALIAS:'_KernelDeAlloc' ::KernelDeAlloc
!DEC$ ATTRIBUTES DLLEXPORT::KernelDeAlloc
!**********************************************************************
integer(4):: i
intege r(int_ptr_kind()) PtrVector

KernelDeAlloc=KernelDeAllocWrapper(i,%val(PtrVector))

endfunction KernelDeAlloc
0 Kudos
Jugoslav_Dujic
Valued Contributor II
886 Views
The problem is, if you want to allocate and deallocate later in Fortran code, you have to store the descriptor somewhere. If you return only the LOC() of allocated arrays to C++, you lose it forever. In (hopefully) attached code, I used the simplest approach of letting the ultimate caller (C/C++ file) to do it. That doesn't exactly match your requirement of "keeping it as simple as possible", but other options are quite a complication (you can recreate it on the basis of address and size on Fortran side in wrappers, but that involves a lot more reverse-engineering of descriptors that I used).

So, I used standard F90 pointers and assumed-shape arrays in the interface and let the C code to take care of descriptors (their storage and dereferencing lpAddress).

Too bad that C is a requirement. C++ code based on the wrapper class I mention would be as simple as:

#include "VFArray.h"
...

VFArray A.allocate(10);
for (i=0; i10; i++) A = i;
KernelCall(A);
for (i=0; i10; i++) printf("%10.6f", A);
A.deallocate();

If you're using Intel Fortran, note that it has an additional member in CVF_1D_DESCRIPTOR, so take care about it in C caller.

HTH
Jugoslav

Message Edited by JugoslavDujic on 10-12-2005 11:56 AM

Message Edited by JugoslavDujic on 10-12-2005 11:57 AM

0 Kudos
jim_dempsey
Beginner
886 Views

A simple linked lists of array descriptors would work

Code:

module myModule
    type Real8Array1
        real(8), pointer :: array(:)
    end type Real8Array1

    type Real8Array2
        real(8), pointer :: array(:,:)
    end type Real8Array2

    type F90_allocateNode
        type(F90_allocateNode), pointer :: next
        union
            map
                type(Real8Array1) :: dim1
            end map
            map
                type(Real8Array2) :: dim2
            end map
             ! other types and dimensions here
        end union
    end type F90_allocateNode
    
    type(F90_allocateNode), pointer :: F90_allocateNodeHead
    
    contains
    subroutine myModule_init
        F90_allocateNodeHead => NULL()
    end subroutine myModule_init
end module myModule
! allocate single dimension of REAL(8)
! returns pointer on success or NULL on failure

function F90_Real8allocate1(N)
    use myModule
    implicit none
    integer(int_ptr_kind()) :: F90_Real8allocate1
    integer(4) :: N, iStat
    type(F90_allocateNode), pointer :: Node
    
    F90_Real8allocate1 = 0
    ! allocate a new node
    allocate(Node, STAT=iStat)
    if(iStat .ne. 0) then
        ! failed, return NULL pointer
        return
    endif
    allocate(Node.dim1.array(N), STAT=iStat)
    if(iStat .ne. 0) then
        deallocate(Node)
        ! failed, return NULL pointer
        return
    endif
    Node.next => F90_allocateNodeHead
    F90_allocateNodeHead => Node
    F90_Real8allocate1 = LOC(Node.dim1.array)
end function F90_Real8allocate1

subroutine F90_free(P)
    use myModule
    implicit none
    integer(int_ptr_kind()) :: P
    integer(4) :: iStat
    type(F90_allocateNode), pointer :: Node, PriorNode
    PriorNode => NULL()
    Node => F90_allocateNodeHead
    do while(associated(Node))
        if(LOC(Node.dim1.array) .eq. P) then
            ! unlink the node
            if(associated(PriorNode)) then
                PriorNode.next => Node.next
            else
                F90_allocateNodeHead => Node.next
            endif
            deallocate(Node.dim1.array)
            deallocate(Node)
            return
        endif
        PriorNode => Node
        Node => Node.next
    end do
    ! ??? node not found
end subroutine F90_free

program foo
    use myModule
    call myModule_init
!    ...
end program foo



The above is untested but should give you an idea.

Jim Dempsey

0 Kudos
durisinm
Novice
886 Views

Are these array descriptors something new that came into being with CVF or IVF or with Fortran 90/95/2003? I've seen several mentions of them in this forum, and I was always under the impression that Fortran arrays were just simple lists of the addresses of the array elements. When and why did array descriptors come about?

Mike D.

0 Kudos
Jugoslav_Dujic
Valued Contributor II
886 Views
Actually, with F90.

Fortran arrays used to be simple lists of array elements. However, with f90, an array (pointer, allocatable or array section) apart from starting address can have few additional properties:

- size
- stride for an assumed-shape array (call Foo(X(1:10:2))) or a pointer (P=>X(1:10:2))
- allocated/associated status

The Standard does not specify how these properties should be implemented, but only how they should behave (and passing these properties into routines is probably the most complex issue). Most (all?) F9x compilers use descriptors (aka "dope vectors") to store & pass these data. The programmer should not (nor care) about how they're implemented, unless (s)he deals with mixed-language issues. Alas, they're not compatible accross compilers, (e.g. you can't pass a VF array section to a routine expecting an assumed-shape/pointer argument in an .obj file compiled with g95).

HTH,
Jugoslav
0 Kudos
jim_dempsey
Beginner
886 Views

Think of an array in .F90 as a C++ class with private members that are inaccessible (the rank,range, extent, and pointer to memory block)andonepublic member - the base address of the data portion of the array. Fortran allocate filles in the private members as well as the public member. When your C/C++ program calls the FORTRAN proxy allocate routine you return the pointer to the block of memory. It is your responsibility to maintain the inaccessible members of the array if you ever intend to return the memory block. This is a similar analogy to the CSTRING class where your code should delete the class object and not the string to which it points.

Jim Dempsey

0 Kudos
Jugoslav_Dujic
Valued Contributor II
886 Views
Indeed. That's exactly how I implemented it.

Attached is the mixed-language CVF workspace/IVF9 solution I mentioned in this thread. As I said, it's kind of incomplete & untidy, but it demonstrates how it is possible to interface C++ and Fortran arrays, where arrays in C++ are implemented "Fortran" way, i.e. "I wrote Fortran in C++". It also kind of demonstrates inner workings of Fortran compiler -- apart from calling VF routine for testing purposes, the C++ code is pretty much standalone.

It currently works only for 1-D arrays (I probably made a design flaw in implementing rank as a template argument, so it's not so easy to expand it to 2-D as-is).

VFArray template class behaves much like F90 pointers/allocatables, with slight semantic changes:

- A VFArray can be both a "POINTER" and an "ALLOCATABLE", i.e. you can both allocate it and point to a target with it (operator >> is overloaded). It's (hopefully) memory-leak safe (any allocation frees old memory if "owned" by the object).
- Indices are "C-style", i.e. they range from 0 ... size(X)-1. When passed to Fortran, they behave as 1 ... size(X)
- If 2-D case (commented out) worked, it would use row-major order (seen from Fortran callee as column-major).

I'll make it available on www.xeffort.com once I complete it.

Jugoslav
0 Kudos
jim_dempsey
Beginner
886 Views

Do you wish to perform all of the memory allocations in the F90 code?

If so, I would suggest you consider writing your own newhandler verses using templates like jugoslav suggests. The C++ code permits user code to replace what is called by new and delete. This little routine would then call the fortran code for the allocation and deallocation. If your code is C as you state then consider using the cpp to replace the malloc, alloc, alloca, ... with #defines.

Are you using C or C++?

Jim Dempsey

Jim Dempsey

0 Kudos
jim_dempsey
Beginner
886 Views
Code:
integer(4) function KernelAllocWrapper(i,PtrVector)
implicit none

integer(4) :: i
integer(int_ptr_kind()) PtrVector

real(8), pointer :: F90_PointerVector(:)

allocate(F90_PointerVector(1:i))

PtrVector=%LOC(F90_PointerVector)

KernelAllocWrapper=0

endfunction KernelAllocWrapper


The
real(8), pointer :: F90_PointerVector(:)
contains more data then simply an integer(4) address.
Depending on your compiler options the structure forF90_PointerVector(:)
is either created on the stack or in global memory with a mangled name which usualy contains the function name with other stuff. This may create reentrancy issues.
In order to return the memory you not only require the address of the data block for the real(8)'s that were allocated but you also require the hidden stuff that was placed into the structure that constituted all members of the pointer just after allocation.
This requires that your allocation must maintain these hidden data structures and do so without knowledge of what is stored in the hidden data structures.
One way to do this is to maintain a table of FORTRAN pointers where the table is larger than the number of concurrentallocations you intend to use in your application. A second way is to allocate and construct a linked list of pointers (such as was suggested by me earlier).
As a side note, if you look at how C and C++ allocate memory everything they allocate is zero based and the type checking enforces fixed rank and extents. This means they do not need to keep this information stored away someplace. What is remaining for C/C++ as bookkeeping is the size of the memory block and some reserved dwords for integrity checking (see your C documentation on heapwalk). C/C++ stores this bookkeeping information immediately preceeding the first memory location of the block allocated.
Due to these extra requirements of FORTRAN the bookkeeping information is kept seperate from the block of data. In particulare consider that the pointer can point into the middle of an array allocated elsewhere.
There is no requirements in the FORTRAN standard to inform the programmer how to access or maintain the allocation bookkeeping information. And there is no requirement for it not to change from version to version. Therefore the simplest and safest way is to maintain an object in FORTRAN that contains the hidden data.
Jim Dempsey
0 Kudos
wolfgang_trautenberg
886 Views
Hi Jugoslav,

we would like to allocate and deallocate memory in C/C++ und use the arrays / structures
allocated and populated in C7C++ on the Fortran side where FORTRAn should be able to obtain
a "pointer" to the data by calling a C function and operate on the data.
Are your the mixed-language allocate in C use in Fortran (with getting pointer in FORTRAN ...)
examples still available somewhere for download?

Thanks for all your insight

Wolfgang
0 Kudos
Steven_L_Intel1
Employee
886 Views
A lot has happened in the past three years. One of them is the support for the Fortran 2003 ISO_C_BINDING intrinsic module with its C_F_PTR procedure. This converts a C "pointer" (as in, address) to a full Fortran 90-style pointer. This is what I would recommend using - see the compiler documentation for information.
0 Kudos
Reply