Great discussion, I will add my .02$.
There are many layers, but the common ground is that Fortran only talks to C by default (maybe other languages in the future).
So if you have a nice C interface, you can talk to any other language relatively easily.
Just note that there will be a lot of boilerplate if you use object-oriented patterns, that C doesn’t have.
So try to understand your scope: if you’re just trying to just speed up some code chunk, just go for a simple bind(C)
subroutine and try to minimize the interface:
subroutine fast_code_chunk(a,b,c,z) bind(C,name='fast_code_chunk')
use iso_c_binding, only: RK => c_float, IK => c_int, etc.
real(RK), intent(inout) :: a(etc.)
end subroutine
you can just compile it as a single source, easy stuff.
If you start having large amounts of Fortran, I suggest to wrap everything (including temporary memory, pointers, etc). into a derived type and write a C API to the derived type itself. The way you do it is a matter of preference. I wrap a pointer into another bind(C)
derived type, because for me it’s safer and the code is more clear:
type :: my_fortran_code
real, allocatable :: whatever(:,:,:,:)
contains
! Fortran interface
procedure :: new
procedure :: destroy
end type
type, bind(C) :: my_fortran_code_c
type(c_ptr) :: cptr = c_null_ptr
end type
! C api
function f_associate(self) result(fself)
type(my_fortran_code_c), value :: self
type(my_fortran_code), pointer :: fself
if (c_associated(self%cptr)) then
call c_f_pointer(self%cptr,fself)
else
nullify(fself)
endif
end function
! void do_something(my_fortran_code_c self);
subroutine do_something(self) bind(C)
! Anywhere you're not allocating/deallocating, you can pass `self` by value
type(my_fortran_code_c), value :: self
type(my_fortran_code), pointer :: fself
fself => f_associate(self)
if (.not.associated(fself)) stop 'variable does not exist'
! Use fself
call fself%blabla
end subroutine do_something
! void new(my_fortran_code_c* self);
subroutine new(self) bind(C)
type(my_fortran_code_c), intent(inout) :: self
type(my_fortran_code), pointer :: fself
fself => f_associate(self)
! Allocate if necessary
if (.not.associated(fself)) then
allocate(fself)
self%cptr = c_loc(fself)
endif
call fself%destroy()
end subroutine
! void destroy(my_fortran_code_c* self);
subroutine destroy(self) bind(C)
type(my_fortran_code_c), intent(inout) :: self
type(my_fortran_code), pointer :: fself
fself => f_associate(self)
! Allocate if necessary
if (associated(fself)) then
! Finalize Fortran
call fself%destroy()
! Clear pointer
deallocate(fself)
self%cptr = c_null_ptr
endif
end subroutine
And remember to always free the memory when you need the variable no more.