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
union
/map
is not standard.sizeof
is not standard.- Accessing values outside the bounds of the array (which is only declared to be length 1) is not standard.
- 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!