Is this a portable way to replace this `union` / `map`?

I have a highly nested data structure in some legacy code compiled with Intel Fortran. It makes use of union and map to have the structure represented as an array of bytes. It exploits this to determine if the structures are equal.

Here’s a simplified example

type foo
  union
    map
      ! lots of stuff
    end map
    map
      integer(1) :: bytes(1)
    end map
  end union
end type

! later
logical function are_equal(x, y)
  type(foo), intent(in) :: x, y
  integer :: i, foo_size

  ! everything in this structure is statically sized, so
  ! you can count on both being the same size
  foo_size = sizeof(x)
  do i = 1, foo_size
    if (x%bytes(i) == y%bytes(i)) then
      are_equal = .false.
      return
    end if
  end do
  are_equal = .true.
end function

Problems I see with this code

  1. union / map is not standard.
  2. sizeof is not standard.
  3. Accessing values outside the bounds of the array (which is only declared to be length 1) is not standard.
  4. It’s not guaranteed that integer(1) represents a byte.

I’d like to make this standard Fortran, mainly to take advantage of fortls which currently doesn’t support union / map, but also in case I need to switch compilers one day.

The obvious correct implementation would be to roll my own equality function, but the real structure is so monstrous that I’m interested in a shortcut for now. For my purposes, it’s okay if I get a false negative: claiming things aren’t equal when they are. A false positive would be bad. This is what I came up with:

logical function are_equal(x, y)
  use, intrinsic :: iso_fortran_env, only : int8
  type(foo), intent(in) :: x, y

  are_equal = all(transfer(x, [1_int8]) == transfer(y, [1_int8]))
end function

One problem I can see is that a structure isn’t guaranteed to be on an 8-bit boundary (I think?). Can this be addressed?

This seems to work, but I’m not sure if it’s “guaranteed” to. Any feedback or suggestions would be greatly appreciated. Thanks!

I threw together a compiler explorer with my implementation working.

By definition, a byte is the smallest addressable atom, and on virtually all machines today, a byte is 8 bits. So, yes, a structure is guaranteed to be aligned on 8 bits boundaries

2 Likes

If you want to make your code more “bullet proof” on the paper, you may transfer the data to the character(kind=c_char) type instead of integer(int8): for, the C char type is guaranteed to be a byte, whatever the size of the byte.

If the size of the type(foo) is known, you could use memcmp through a binding:

logical function are_equal(x, y)
  use, intrinsic :: iso_c_binding, only : c_ptr, c_loc, c_int
  type(foo), intent(in), target :: x, y

  interface
    function memcmp(buf1, buf2, size) bind(c)
      import c_ptr, c_size_t, c_int, c_size_t
      integer(c_int) :: memcmp
      type(c_ptr), value :: buf1, buf2
      integer(c_size_t), value :: size
    end
  end interface

  are_equal = (memcmp(c_loc(x), c_loc(y), size_of_foo) == 0)
end function

I don’t known if that’s any clearer than the transfer-based version (it may for a programer with a C background), plus I don’t know how to determine the size of a Fortran structure.

In addition, this won’t work if the structure contains allocatable fields, as their adress may differ while there contents may be identical.

1 Like

At least it should be faster.

This should do:

character(kind=c_char) :: c

size_of_foo = storage_size( foo ) / storage_size( c )

Sure, but none of the solutions of this thread can work in case of allocatable or pointer components.

1 Like

That’s my gut instinct too.

To get rid of the union / map (a problem I’m facing too), I wonder if a strategy could be to replace fields by functions:

type(foo)
  ! Most used field here
contains
  function bytes(self) result(b)
    class(foo) :: self
    integer(1), allocatable :: b(:)
    allocate(b(size_of_foo ))
    call memcpy(b, self, size_of_foo) ! Something like that, possibly with a C variant taking a CFI_cdesc_t...
  end function
end type

Thus accesses to instance_of_foo%bytes would be replaced by instance_of_foo%bytes(): a minimal change I would say.

Technically transfer should work, but without union or some equivalancing capability you are making a copy. This might be a problem it the structure is large. It is really that hard to make a function that compares all the components? If components are also user-defined types I can see it being cumbersome but I have seen transfer be surprisingly slow as well.

I have also seen where list-directed I/O and namelist output both to regular scratch files and internal files were used, where the outputs are compared.but I think the byte-by-byte compare is better unless you want to know where the difference occurs

1 Like

The memcmp() solution from @nja doesn’t do any copy.

Yes. Not as clear as I thought that I was just pointing out the cost of using TRANSFER specifically. I was thinking of MEMCMP as more like an EQUIVALENCE, which in my experience is always best in FORTRAN but unfortunately is not supported in many circumstances in Fortran, including the extensions often used with EQUIVALENCE.

It is interesting to think about whether a generic .eq. and .ne. support for user-defined types should be standard; like it is for complex values (even though other comparisions are not defined). I was leaning towards that it should be, but some of the points here about unallocated allocatable values and functions and pointers complicate considering it; which are issues that you do not encounter with complex values. At first thought it seemed it was a natural to have those operators pre-defined, and (probably?) a common enough need to be reasonable to add to the language.

How many restrictions would you need to say it is predefined? No pointers perhaps (is something equal if it points to target A but not if it points to another target like target B if A and B are both integers with the same value, for example)?

Seeing how often codes are defining their own == and /= operators and how many are just comparisons of the components without defining other relational operators would be an indication of how needed it is, but that seems like a complicated metric to gather.

1 Like

I think this is a difficult problem in fortran because it relies on low-level assumptions that are purposefully avoided in the fortran language. One of them, which relates to the false negative issue, is that derived types in fortran can have padding in order to make the individual components align on particular address boundaries. Those padding bits are undefined within the language, and they might be set to zero or they might end up with random values from whatever happened to be in those memory locations previously. These random padding bits would show up as differences in either the transfer() or the c_loc() approaches mentioned above.

Another type of issue would arise when the derived type is an extension of another derived type. In this case, the extended type works “as if” all of the components are adjacent in memory, but the actual implementation of the compiler might scatter the various components. You could test this with c_loc() comparisons, but by the time you do this, it would probably have been easier to just write a special-purpose comparison operator. Finally, there is also the issue that your comparison function cannot really be generic using the current language features, you still need to declare the arguments to be a derived type that the compiler knows about at compile time. This gets back to the unspecified low-level representations of derived types and particularly of extended derived types within the language. Part of the high-level power and flexibility of the language requires some of this low-level ambiguity.

Since there is an intrinsic assignment for the derived types, I can’t see any reason why there could’t be intrinsic comparison operators, with the same logic regarding the pointer components:

type foo
   integer, pointer :: a(:)
end type

type(foo) :: x, y
...
print*, x == y 
!should be the same as
print*, associated(x%a,y%a) .or.                        &
        .not.associated(x%a) .and. .not.associated(y%a) )
1 Like

Since type foo is not bound to C rules, you could just use class(*) and be done with it --that should solve the problems you mentioned.

type lots_of_stuff
  ...
end type

type foo
  class(*), allocatable :: union
end type

! later
logical elemental function are_equal(x, y)
  type(foo), intent(in) :: x, y
  are_equal = .false.
  if (.not. all([allocated(x%union), allocated(y%union)])) return
  select type (xu => x%union)
  type is (lots_of_stuff)
    select type (yu => y%union)
    type is (lots_of_stuff)
      are_equal = xu == yu   ! overload operator(==) or compare after transfer
    end select
  type is (integer(1))
    select type (yu => y%union)
    type is (integer(1))
      are_equal = xu == yu
    end select
  end select
end function

But with pointers is it always clear? In the first set of WRITE statements are fighter and pacifist equal? They have the same values but point to different variables. At the second set of rights their components are allocated but does that alone make them equal? They present different values. That seems a little ambigious. If they both point to all the same targets or are both null or undefined they do seem to meet an unambigious definition of equal; but being pointers can be more complicated than that.

program main
implicit none
type foo
   integer, pointer :: guts
end type
type(foo) :: fighter, pacifist
integer,target :: a, b
   fighter%guts => A
   pacifist%guts => B
   A=10
   B=10
   write(*,*) fighter%guts,'fighter'
   write(*,*) pacifist%guts,'pacifist'
   A=11
   B=22
   write(*,*) fighter%guts,'fighter'
   write(*,*) pacifist%guts,'pacifist'
end program main

No it is not. But it is not clear either for the intrinsic assignment with pointer components: the standard has chosen a convention, where the operation for the pointer components is the association =>. Similarly, a convention would have to be chosen for hypothetical comparaison operators, and the user would still have to write its own comparaison routines in the case where this convention would not fit his needs.