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?