Does Fortran make guarantees on type memory layout?

In C we have some guarantees about the memory layout of a struct, namely that a pointer to a structure object points to its first member. This allows to access the first member of any struct by casting if you know its length.

Do we have a similar rule in Fortran? Is it correct that in two derived types having the same first member we will find the correct value regardless of which actual type is present?

For example with the two types shown below, we could expect that accessing %id for either types will work, e.g. when cast to a type(c_ptr) and converted back to the wrong type using c_f_pointer (by accident) and using the access to a common element to catch this before accessing the second component.

type :: a
  integer :: id = 0
  character(len=:), allocatable :: raw
end type

type :: b
  integer :: id = 1
  real, allocatable :: array(:)
end type
3 Likes

I know that adding either bind(c) or sequence to the derived types would guarantee this behavior. But not all types we want to send to C and retrieve back are C compatible, in most cases it is sufficient to just have a void* handle in C for this purpose rather than a fully intercompatible representation.

Outside of the cases involving BIND(C) and SEQUENCE, the standard essentially places the memory layout of derived types in processor-dependent category, so in effect there are no guarantees whatsoever across different processors.

3 Likes

If the purpose is to pass both type-ID and Fortran derived-type data in a packed manner (?), another option may be to make a “thin” wrapper with type(c_ptr) so that both C/Fortran can access id, while Fortran can get the derived type data via c_f_pointer()? (though I think direct access of id in the original code would be much more convenient…)

    type, bind(c) :: wrapper_t
        integer(c_int) :: id = 0       !! type-id
        type(c_ptr) :: ptr             !! address of Fortran object
    end type
program main
    use iso_c_binding
    implicit none

    type, bind(c) :: wrapper_t
        integer(c_int) :: id = 0
        type(c_ptr) :: ptr
    end type

    type Foo_t; integer, allocatable :: a(:); endtype
    type Baa_t; real,    allocatable :: b(:); endtype

    type(Foo_t), allocatable, target :: x
    type(Baa_t), allocatable, target :: y
    type(wrapper_t) :: w( 2 )

    allocate( x ); w( 1 ) = wrapper_t( id= 100, ptr= c_loc( x ) )
    allocate( y ); w( 2 ) = wrapper_t( id= 200, ptr= c_loc( y ) )

    print *, w( 1 )% ptr
    print *, w( 2 )% ptr

    !! etc...
end

The wrapper type is a good idea, however the second component might be neither bind(c) nor sequence compatible and having a pointer component in a derived type tends to become messy.

A similar Fortran-only example would be something like a global procedure with an explicit interface, where two type definitions are required unless type would be defined in a module.

subroutine sub_a(a)
  implicit none
  type :: a_t
    integer :: id
  end type
  type(a_t), intent(in) :: a

  print *, a%id
end subroutine sub_a

program demo
  implicit none(type, external)
  type :: b_t
    integer :: id = 1
  end type
  interface
    subroutine sub_a(b)
      import :: b_t
      type(b_t), intent(in) :: b
    end subroutine sub_a
  end interface
  type(b_t) :: b

  call sub_a(b)
end program demo

The name of the type is different, which is bad practice, but doesn’t make it invalid Fortran. The question is whether this enables us to pass another type to the same procedure (while lying in the explicit interface to the compiler) and expect it work

type c_t
  integer :: id = 2
  character(len=:), allocatable :: raw
end type c_t

The situation is not so much different from the casting via type(c_ptr), but now in hacky, yet infinitely backwards compatible, legacy Fortran.

You likely know the answer to your question which is generally, no.