Deallocation of arrays passed as c_ptr

Hello everyone,

While testing out the interoperability features between Julia and Fortran I have encountered some unexpected results.

I have some Julia code which makes calls to Fortran code compiled as a shared library, the code is the following:

array_size = 5
ptr_array = @ccall "./lib/new-interface.so".gen_pointer(array_size::Ref{Cint}, 1::Ref{Cint})::Ptr{Cint}
@info("Array obtained from Fortran", ptr_array, unsafe_wrap(Array, ptr_array, array_size, own=false))

array_fort = unsafe_wrap(Array, ptr_array, array_size, own=false)
for _=1:3
    @ccall "./lib/new-interface.so".modify_pointer(ptr_array::Ref{Ptr{Cint}}, array_size::Ref{Cint})::Cvoid
    @info("Array (Fortran) after modification in Fortran", ptr_array, array_fort)
end

@ccall "./lib/new-interface.so".dealloc_array(ptr_array::Ref{Ptr{Cint}}, array_size::Ref{Cint})::Cvoid

The Fortran module looks like this:

module inter

    use iso_c_binding

    contains

    function gen_pointer(size, val) bind(c)
        integer, intent(in) :: size, val
        integer, pointer :: array(:)
        type(c_ptr) :: gen_pointer
        allocate(array(size))
        array = val
        gen_pointer = c_loc(array)
    end function gen_pointer

    subroutine modify_pointer(array_ptr, size) bind(c)
        type(c_ptr), intent(inout) :: array_ptr
        integer, intent(in) :: size
        integer, pointer :: array(:)
        call c_f_pointer(array_ptr, array, (/ size /))
        array = array * 2
    end subroutine modify_pointer

    subroutine dealloc_pointer(array_ptr, size) bind(c)
        type(c_ptr), intent(inout) :: array_ptr
        integer, intent(in) :: size
        integer, pointer :: array(:)
        call c_f_pointer(array_ptr, array, (/ size /))
        deallocate(array)
    end subroutine dealloc_pointer

end module inter

The objective of the test is to see if I can allocate an array in Fortran and pass it to Julia so that i can then be used from there (or within Fortran again later on).

The program works as expected except for the last call, the deallocation:

┌ Info: Array obtained from Fortran
│   ptr_array = Ptr{Int32} @0x0000000000c2bcc0
│   unsafe_wrap(Array, ptr_array, array_size, own = false) =
│    5-element Vector{Int32}:
│     1
│     1
│     1
│     1
â””     1
┌ Info: Array (Fortran) after modification in Fortran
│   ptr_array = Ptr{Int32} @0x0000000000c2bcc0
│   array_fort =
│    5-element Vector{Int32}:
│     2
│     2
│     2
│     2
â””     2
┌ Info: Array (Fortran) after modification in Fortran
│   ptr_array = Ptr{Int32} @0x0000000000c2bcc0
│   array_fort =
│    5-element Vector{Int32}:
│     4
│     4
│     4
│     4
â””     4
┌ Info: Array (Fortran) after modification in Fortran
│   ptr_array = Ptr{Int32} @0x0000000000c2bcc0
│   array_fort =
│    5-element Vector{Int32}:
│     8
│     8
│     8
│     8
â””     8

[1303] signal (11.1): Segmentation fault
in expression starting at /file-path/new-main.jl:21
unknown function (ip: (nil))
Allocations: 2999 (Pool: 2987; Big: 12); GC: 0
Segmentation fault

To test if the issue was on the interoperability between Julia and Fortran, or just on the Fortran side, I tried to execute the same steps within Fortran, obtaining the following result on deallocation:

forrtl: severe (173): A pointer passed to DEALLOCATE points to an object that cannot be deallocated
Image              PC                Routine            Line        Source
main-fortran.out   0000000000405F39  Unknown               Unknown  Unknown
main-fortran.out   00000000004041C9  Unknown               Unknown  Unknown
main-fortran.out   000000000040415D  Unknown               Unknown  Unknown
libc.so.6          00007F4234E00D90  Unknown               Unknown  Unknown
libc.so.6          00007F4234E00E40  __libc_start_main     Unknown  Unknown
main-fortran.out   0000000000404075  Unknown               Unknown  Unknown

So the issue is definitely on the deallocation side and not the interoperability. My question is then, how would you go about deallocating that memory?

Welcome @danmohr

The problem is here:

function gen_pointer(size, val) bind(c)
    integer, intent(in) :: size, val
    integer, pointer :: array(:) !> this variable has a scope limited to the function
    type(c_ptr) :: gen_pointer
    allocate(array(size)) !> allocation on a pointer variable should be
    !> done with extreme care, here is a good example 
    !> of things going wrong silently 
    array = val
    gen_pointer = c_loc(array)
end function gen_pointer

You allocate a pointer within a local scope of a function. Your memory has to be hold somewhere, which is not the case here.

If you want the Fortran shared library to be owner of the memory then you need to define a data container like

module inter

    use iso_c_binding

    integer, allocatable, target :: mydata(:)

    contains

Then you could allocate it, point to it, and go in with crunching it as you want. When you want the memory to be freed, it is this mydata that should be deallocated.

If this is supposed to be a shared library, you’ll be better of owning the data externally by your Julia main program that should then be responsible of destroying the data as well.

If you stick with the Fortran module holding the data (nothing against, I do it also for Python bindings) then you should make sure of keeping track of the pointers being passed between Julia and Fortran.

One of the caveats of pointers in Fortran is that it is quite easy (if not careful) to leave memory hanging.

Side note: you might want to drop this (/ size /)) and use this [ size ]

1 Like

A Fortran pointer is very different object from a C pointer. Basically a C pointer is just a base address, while a Fortran pointer is a complex (and hidden) descriptor. In your dealloc_pointer() routine you are reconstructing a Fortran pointer from a C pointer: it is supposed to have the same characteristics, but this is formally not the same object as the initial pointer that was allocated.

I think that such code might work, but it’s probably not standard compliant. The F2023 standard says in in the 9.7.3.3 section:

Deallocating a pointer that is disassociated or whose target was not created by an ALLOCATE statement causes an error condition in the DEALLOCATE statement

In your code the target is hidden in the c_f_pointer() function, and the runtime cannot determine how it had been initially allocated. This minimal example runs apparently fine with gfortran but crashes with the Intel compiler:

program foo
use iso_c_binding
implicit none

integer, pointer :: p(:), q(:)

allocate( p(1000) )
call c_f_pointer(c_loc(p),q,[1000])
deallocate(q)

end
2 Likes

I’m not sure whether this code is standard conforming, or whether it is conceptually correct in the first place, but I thought “Why not deallocating the c_ptr a la C way, using free()” ?

So, you’d simply write Fotran bindings to the C functions:

program test
   use, intrinsic :: iso_c_binding
   implicit none
   interface
      function malloc_(nbytes) bind(c, name="malloc")
         import c_ptr, c_size_t
         integer(c_size_t), value :: nbytes
         type(c_ptr) :: malloc_
      end function
      subroutine free_(ptr) bind(c, name="free")
         import c_ptr
         type(c_ptr), value :: ptr
      end subroutine
      subroutine printarray_(arr, N_) bind(c, name="printarray")
         import c_ptr, c_int
         type(c_ptr), intent(in), value    :: arr
         integer(c_int), intent(in), value :: N_
      end subroutine
   end interface

   integer(c_size_t), parameter :: N = 1000000_c_size_t
   integer :: i
   type(c_ptr) :: cptr
   integer(c_int), pointer :: fptr(:) => null()

   print *, c_associated(cptr)
   cptr = malloc_(c_sizeof(c_int) * N)
   print *, c_associated(cptr)

   call c_f_pointer(cptr, fptr, [N])
   print *, associated(fptr)
   do i = 1, N
      fptr(i) = i
   enddo
   ! once done on Fortran side, just nullify pointer
   nullify(fptr)

   ! see if Fotran changed C allocated memory
   call printarray_(cptr, 10) ! limit to 10 for conciseness

   ! now free memory
   call free_(cptr)

   ! ! Uncomment to see segfault (mem freed)
   ! call printarray_(cptr, 10)
end program

C code:

#include <stdio.h>

void printarray(const int *arr, const int N)
{
   for (unsigned i=0; i < N; ++i) {
      printf("%d\n", arr[i]);
   }
}
1 Like

I’m not quite familiar enough with Julia or its syntax to know for sure, but you might be misunderstanding how exactly the interfaces to the Fortran functions work, because as written I believe it should work. Anyways, the C equivalents to those interfaces would be

void* gen_pointer(int* size, int* val);

void modify_pointer(void** array_ptr, int* size);

void dealloc_pointer(void** array_ptr, int* size);

Note that arguments without the value attribute are equivalent to pointers.

This is not true. You do not need a variable with the target attribute declared somewhere for any/all allocations. Nor does the variable that deallocates memory need to be the variable that allocated it. It’s just that doing those things makes memory leaks or use after free bugs far easier to create.

1 Like

Maybe I wrote too short or too fast, in no case did I mean he needed target for allocation. He needs both, allocatable and target if he wants to own the data by allocating in the Fortran shared object, be able to point to it, and be able to retrieve its address latter on for destroying it.

He’s module as is, has (AFAIK) unknow behavior and its (seems to me) dangerous Compiler Explorer

program main
    use inter

    type(c_ptr) :: array
    integer, pointer :: ptr(:)

    array = gen_pointer(10,1)
    call c_f_pointer(array,ptr,[10])
    print *, ptr

    call dealloc_pointer(array,10)
    print *, ptr
end program

ifort

Program stdout
           1           1           1           1           1           1
           1           1           1           1
Program stderr
forrtl: severe (173): A pointer passed to DEALLOCATE points to an object that cannot be deallocated
Image              PC                Routine            Line        Source             
output.s           0000000000404619  Unknown               Unknown  Unknown
output.s           000000000040415D  Unknown               Unknown  Unknown
libc.so.6          00007FD2CB629D90  Unknown               Unknown  Unknown
libc.so.6          00007FD2CB629E40  __libc_start_main     Unknown  Unknown
output.s           0000000000404075  Unknown               Unknown  Unknown

gfortran

Program stdout
           1           1           1           1           1           1           1           1           1           1
        6976           0  1192534655   432068720           1           1           1           1           1           1
1 Like

I contend that the following is a standard conforming program, and that the error is an Intel bug.

module inter

    use iso_c_binding

    implicit none
    private
    public :: gen_pointer, modify_pointer, dealloc_pointer

    contains

    function gen_pointer(size, val) bind(c)
        integer, intent(in) :: size, val
        integer, pointer :: array(:)
        type(c_ptr) :: gen_pointer
        allocate(array(size))
        array = val
        gen_pointer = c_loc(array)
    end function gen_pointer

    subroutine modify_pointer(array_ptr, size) bind(c)
        type(c_ptr), intent(in) :: array_ptr
        integer, intent(in) :: size
        integer, pointer :: array(:)
        call c_f_pointer(array_ptr, array, (/ size /))
        array = array * 2
    end subroutine modify_pointer

    subroutine dealloc_pointer(array_ptr, size) bind(c)
        type(c_ptr), intent(in) :: array_ptr
        integer, intent(in) :: size
        integer, pointer :: array(:)
        call c_f_pointer(array_ptr, array, (/ size /))
        deallocate(array)
    end subroutine dealloc_pointer

end module inter

program example
    use inter
    use iso_c_binding

    implicit none

    type(c_ptr) :: array
    integer, pointer :: ptr(:)

    array = gen_pointer(10,1)
    call c_f_pointer(array,ptr,[10])
    print *, ptr

    call modify_pointer(c_loc(ptr),10)
    print *, ptr

    call dealloc_pointer(c_loc(ptr),10)
    ! print *, ptr ! would be invalid, as pointer is no longer associated with valid target
end program
(base) [stray:~/scratch/alloc-in-fortran] nagfor -f2018 -C=all example.f90
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7144
[NAG Fortran Compiler normal termination]
(base) [stray:~/scratch/alloc-in-fortran] ./a.out 
 1 1 1 1 1 1 1 1 1 1
 2 2 2 2 2 2 2 2 2 2
(base) [stray:~/scratch/alloc-in-fortran] gfortran -std=f2018 -fcheck=all example.f90 
(base) [stray:~/scratch/alloc-in-fortran] ./a.out 
           1           1           1           1           1           1           1           1           1           1
           2           2           2           2           2           2           2           2           2           2
(base) [stray:~/scratch/alloc-in-fortran] ifx -check all,nouninit -standard-semantics -stand f18 example.f90
(base) [stray:~/scratch/alloc-in-fortran] ./a.out 
 1 1 1 1 1 1
 1 1 1 1
 2 2 2 2 2 2
 2 2 2 2
forrtl: severe (173): A pointer passed to DEALLOCATE points to an object that cannot be deallocated
Image              PC                Routine            Line        Source             
a.out              0000000000405B84  Unknown               Unknown  Unknown
a.out              0000000000406339  Unknown               Unknown  Unknown
a.out              000000000040515D  Unknown               Unknown  Unknown
libc.so.6          00007B8B6CE45CD0  Unknown               Unknown  Unknown
libc.so.6          00007B8B6CE45D8A  __libc_start_main     Unknown  Unknown
a.out              0000000000405075  Unknown               Unknown  Unknown

No, you don’t. If you allocate through a pointer it creates an anonymous object. If you lose it’s address that’s a memory leak, but its perfectly valid to change what’s holding on to that address, including giving it to some other language and coming back again.

Edit: change intent of c_ptr args, and use c_loc in main program to make it even more clear that the intended use case is valid.

1 Like

Any particular reason for using allocatable, target instead of pointer here? I’ve tried it with both options and the new approach seems to work fine for pointer variables, but in general allocatable variables give a lot of problems during interoperability. In my case for example I’m able to allocate the array and get access to it from Julia but have problems when modifying it again in Fortran. I’m guessing because of the “reconstruction” of the array using c_f_pointer().

I am indeed using the Intel compiler, and as some other people have pointed out too, it might be the problem here, ignoring the fact that the functionality itself might not be standard compliant.

As @everythingfunctional has pointed out, it is standard conforming to create and destroy the object from Fortran as he shows. I might be biased by the intel bug, thus my usual practice when doing interoperability is that creation/destruction of the data should be done by the language that holds it. The other should just operate on it. Otherwise I have ran into quite some ugly bugs, specially memory leaks.

When working with pointers that I need to allocate for holding the data and interoperating, I put the pointer in a derived type together with a logical to indicate wether the object holds the data or is just a normal pointer, such that I can then properly call deallocate or nullify

I’m really not sure. It assumes that c_f_pointer(c_loc(p),q,[size(p)]) is able reconstruct the exact same internal descriptor of q as in q => p.

The semantics of c_loc and c_f_pointer basically require this, at least at the basic level.

CPTR shall be … the result of a reference to C_LOC

Now if the implementation is carrying around extra information besides address and shape it may not be able to, but the standard doesn’t really require anything else.

What if p is a pointer to a non-contiguous chunk of memory?

@everythingfunctional

I do not doubt at all that c_f_pointer(c_loc(p),q,[size(p)]) is perfectly legal (under some conditions). My questioning is about the “deallocabilty” of q afterwards.

Strangely the association will “work”, but q(2) won’t be associated to p(2). I can’t find in the standard any constraint on the contiguity :thinking:

gfortran uses malloc/free to allocate pointer arrays, which likely means it only needs the address of the first element to deallocate the memory correctly. Since nagfor works as a Fortran → C transpiler, I would assume it also uses malloc and free under the hood (but I don’t have access to check).

In contrast, ifx appears to use a different array descriptor (dope vector), created and destroyed using functions from the Intel Fortran runtime library: for_allocate_handle and for_dealloc_allocatable_handle.

It’s certainly an interesting question if the round-trip from Fortran pointer array to the “tuple” of void * and dimensions is sufficient to recreate the descriptor or not. I’m looking forward to an answer.


As a side-note, a standard-conforming way to do this is using the Fortran 2018 enhanced interoperability for pointer arrays:

! void gen_pointer(int size, int val, CFI_cdesc_t *ptr);
subroutine gen_pointer(size,val,ptr) bind(c)
   integer(c_int), value :: size, val
   integer(c_int), pointer, intent(out) :: ptr(:)
end subroutine

! void modify_pointer(const CFI_cdesc_t *ptr);
subroutine modify_pointer(ptr) bind(c)
   integer(c_int), pointer, intent(in) :: ptr(:)
end subroutine

! void dealloc_pointer(CFI_cdesc_t *ptr);
subroutine dealloc_pointer(ptr) bind(c)
   integer(c_int), pointer, intent(inout) :: ptr(:)
end subroutine

I have zero experience working with Julia, but I imagine you would use this as follows:

p = Ref{Ptr{Cvoid}}()  # descriptor handle (we use void * in-place of CFI_cdesc_t *)

ccall((:gen_pointer, "libpointer.so"), Cvoid, (Cint, Cint, Ptr{Cvoid}), size::Cint, val::Cint, p[])
ccall((:modify_pointer, "libpointer.so"), Cvoid, (Ptr{Cvoid},), p[])
ccall((:dealloc_pointer, "libpointer.so"), Cvoid, (Ptr{Cvoid},), p[])
2 Likes

I was not doubting about that, instead the fact the the resulting behaviour could be not the expected one. So, I was wondering whether something that could potentially result in “unexpected” behaviour, can be considered standard conforming. Probably yes, based on the current standard. Or, maybe the standard is missing some aspects in this matter.

In this case you should use the facilities from ISO_Fortran_binding.h. The C array descriptor (CFI_cdesc_t *) stores information about the rank and strides.

Then it violates the constraint on c_loc:

If it is an array, it shall be contiguous and have nonzero size

You can deallocate either p or q, but at that point neither have a defined association status, and it is invalid to reference either one.

1 Like

Here is a MWE of what we are talking about:

program mwe
use, intrinsic :: iso_c_binding
implicit none
integer(c_int), pointer :: p(:), q(:)
allocate(p(5))
p = 42
call c_f_pointer(c_loc(p),q,[size(p)])
deallocate(q)    ! Is it legal to deallocate q instead of p?
end program

Thanks for the reminder of “carefully read the standard!” :laughing:
But, so why is c_loc not made to throw even a warning when a pointer to non-contiguous memory is passed as argument? Shouldn’t be this info available within its implementation? (Ready to take a right uppercut, right after that good left hook :boxing_glove:)