Should these various ways of converting anything to an array of bytes not produce the same answer?

I highly doubt you got it to work with IFX. As the Intel forum thread I linked upthread, IFX does not yet support TRANSFER with unlimited polymorphic source, it would throw an internal compiler error.

With other compilers, you can go old-fashioned like so:

module m
   use, intrinsic :: iso_fortran_env, only : CSZ => character_storage_size
   interface to_bytes
      module procedure :: to_bytes_0
      module procedure :: to_bytes_1
   end interface
contains
   function to_bytes_0( a ) result(r)
      class(*), intent(in) :: a
      character(len=1), allocatable :: r(:)
      allocate( r(storage_size(a)/CSZ) )
      r = transfer( source=a, mold=r )
   end function
   function to_bytes_1( a ) result(r)
      class(*), intent(in) :: a(:)
      character(len=1), allocatable :: r(:)
      allocate( r(storage_size(a)*size(a)/CSZ) )
      r = transfer( source=a, mold=r )
   end function
end module
   use m, only : to_bytes
   associate ( n => 42 )
      associate ( t => to_bytes( n ) )
         write(*,'(*(1x,z2.2))') iachar(t)
         write(*,'(*(1x,g0))') transfer( source=t, mold=n )
      end associate
   end associate
   print *
   associate ( n => [(i*i,i=1,10)] )
      associate ( t => to_bytes( n ) )
         write(*,'(*(1x,g0))') iachar(t)
         write(*,'(*(1x,g0))') transfer( source=t, mold=n )
      end associate
   end associate
   print *
   associate ( x => [ 11.11, 22.22, 33.33 ] )
      associate ( t => to_bytes( x ) )
         write(*,'(*(1x,g0))') iachar(t)
         write(*,'(*(1x,g0))') transfer( source=t, mold=x )
      end associate
   end associate
   print *
   associate ( s => 'This is a string' )
      associate ( t => to_bytes( s ) )
         write(*,'(*(1x,g0))') iachar(t)
         write(*,'(*(1x,g0))') transfer( source=t, mold=s )
      end associate
   end associate
end
  • However you will still run into problems with gfortran because of bugs:
C:\temp>gfortran p.f90 -o p.exe

C:\temp>p.exe
 2A 00 00 00
 42

 01 00 00 00 04 00 00 00 09 00 00 00 10 00 00 00 19 00 00 00 24 00 00 00 31 00 00 00 40 00 00 00 51 00 00 00 64 00 00 00 8F C2 31 41 8F C2 B1 41 EC 51 05 42 00 00 00 00 00 00 00 00 00 00 00 00 44 08 00 00 FF 0F 00 00 00 00 00 00 01 00 00 00
 1 4 9 16 25 36 49 64 81 100 1093780111 1102168719 1107644908 0 0 0 2116 4095 0 1

 8F C2 31 41 8F C2 B1 41 EC 51 05 42 00 00 00 00 00 00 00 00 00 00 00 00
 11.1099997 22.2199993 33.3300018 0.00000000 0.00000000 0.00000000

 54
 T┬4▲n☺  P☺4▲n☺
  • But you can cross-check using IFORT
C:\temp>ifort /standard-semantics p.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.8.0 Build 20221119_000000
Copyright (C) 1985-2022 Intel Corporation.  All rights reserved.

Microsoft (R) Incremental Linker Version 14.31.31105.0
Copyright (C) Microsoft Corporation.  All rights reserved.

-out:p.exe
-subsystem:console
p.obj

C:\temp>p.exe
 2A 00 00 00
 42

 01 00 00 00 04 00 00 00 09 00 00 00 10 00 00 00 19 00 00 00 24 00 00 00 31 00 00 00 40 00 00 00 51 00 00 00 64 00 00 00
 1 4 9 16 25 36 49 64 81 100

 8F C2 31 41 8F C2 B1 41 EC 51 05 42
 11.11000 22.22000 33.33000

 54 68 69 73 20 69 73 20 61 20 73 74 72 69 6E 67
 This is a string
  • And try NAG Fortran compiler if you can …