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

I wanted a function to turn any scalar or vector type to bytes. The last
time I tried it I had to use TRANSFER directly, or specifically have
the type in a SELECT TYPE, which is method 1.

Now ifort 2023 gives me the same answer for all the cases, which is
what I expected. If I use -check all I get an error says CHARS has to
be allocated which is easy to work around but I consider incorrect;
other than that method 3 now does what I want.

gfortran 11 (do not have 12 currently on my platform) still gives me
answers I do not expect.

nvfortran compiles it, but I currently have problems with the loader so
I could not run it.

I have not had a chance to try it with anything else at this time.

I was preparing to search for/report the gfortran results as a bug,
but wondered if anyone sees something not standard-conforming or that
should produce different results?

When I tried this originally several of the features were new and everyone
failed in one way or another to even compile or execute. It is much
better now, but I am using a few features I do not use all that often,
so not totally sure all the methods are truly equivalent as far as the
results are concerned?

Reduce code sample
Module M_bytes
implicit none
private
public to_bytes1, to_bytes2, to_bytes3

interface to_bytes1; module procedure to_bytes1_arr, to_bytes1_scalar; end interface
interface to_bytes2; module procedure to_bytes2_arr, to_bytes2_scalar; end interface
interface to_bytes3; module procedure to_bytes3_arr, to_bytes3_scalar; end interface

contains

! no select type
function to_bytes3_arr(anything) result(chars)
class(*),intent(in)          :: anything(:)
character(len=1),allocatable :: chars(:)
   chars=transfer(anything,chars)
end function to_bytes3_arr
function  to_bytes3_scalar(anything) result(chars)
class(*),intent(in)          :: anything
character(len=1),allocatable :: chars(:)
   chars=transfer(anything,chars)
end function  to_bytes3_scalar

! default of select type
function to_bytes2_arr(anything) result(chars)
class(*),intent(in)          :: anything(:)
character(len=1),allocatable :: chars(:)
   select type(anything)
    class default; chars=transfer(anything,chars)
   end select
end function to_bytes2_arr
function  to_bytes2_scalar(anything) result(chars)
class(*),intent(in)          :: anything
character(len=1),allocatable :: chars(:)
   select type(anything)
    class default; chars=transfer(anything,chars)
   end select
end function  to_bytes2_scalar

! specific
function to_bytes1_arr(anything) result(chars)
class(*),intent(in)          :: anything(:)
character(len=1),allocatable :: chars(:)
   select type(anything)
    type is (integer);          chars=transfer(anything,chars)
    type is (real);             chars=transfer(anything,chars)
    type is (character(len=*)); chars=transfer(anything,chars)
    class default
       stop 'unknown type'
   end select
end function to_bytes1_arr
function  to_bytes1_scalar(anything) result(chars)
class(*),intent(in)          :: anything
character(len=1),allocatable :: chars(:)
   select type(anything)
    type is (integer);          chars=transfer(anything,chars)
    type is (real);             chars=transfer(anything,chars)
    type is (character(len=*)); chars=transfer(anything,chars)
    class default
       stop 'unknown type'
   end select
end function  to_bytes1_scalar

end module M_bytes
program testit
use M_bytes, only : to_bytes1, to_bytes2, to_bytes3
implicit none
integer :: i
character(len=1),allocatable :: chars(:)

   write(*,"('select type and matching case')")
   write(*,'(*(1x,z2.2))')to_bytes1([(i*i,i=1,10)])
   write(*,'(*(1x,z2.2))')to_bytes1([11.11,22.22,33.33])
   write(*,'(*(1x,z2.2))')to_bytes1('This is a string')

   write(*,"('select type default')")
   write(*,'(*(1x,z2.2))')to_bytes2([(i*i,i=1,10)])
   write(*,'(*(1x,z2.2))')to_bytes2([11.11,22.22,33.33])
   write(*,'(*(1x,z2.2))')to_bytes2('This is a string')

   write(*,"('no select type')")
   write(*,'(*(1x,z2.2))')to_bytes3([(i*i,i=1,10)])
   write(*,'(*(1x,z2.2))')to_bytes3([11.11,22.22,33.33])
   write(*,'(*(1x,z2.2))')to_bytes3('This is a string')

   write(*,"('transfer variable array')")
   write(*,'(*(1x,z2.2))')transfer([(i*i,i=1,10)],chars)
   write(*,'(*(1x,z2.2))')transfer([11.11,22.22,33.33],chars)
   write(*,'(*(1x,z2.2))')transfer('This is a string',chars)

   write(*,"('transfer constant array')")
   write(*,'(*(1x,z2.2))')transfer([(i*i,i=1,10)],[' '])
   write(*,'(*(1x,z2.2))')transfer([11.11,22.22,33.33],[' '])
   write(*,'(*(1x,z2.2))')transfer('This is a string',[' '])
end program testit
``

gfortran 11

select type and matching case
 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
 54 68 69 73 20 69 73 20 61 20 73 74 72 69 6E 67
select type default
 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 01 00 00 00 04 00 00 00 09 00 00 00 10 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
 54
no select type
 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 01 00 04 09 10 19 24 31 40 51 64 8F C2 41 B1 EC 05 42 54 68 69 73 20 61 74 72 6E 67
 8F C2 31 41 8F C2 B1 41 EC 51 05 42 01 00 04 09 10 19 24 31 40 51 64 8F
 54
transfer variable array
 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
 54 68 69 73 20 69 73 20 61 20 73 74 72 69 6E 67
transfer constant array
 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
 54 68 69 73 20 69 73 20 61 20 73 74 72 69 6E 67

ifort 2023

select type and matching case
 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
 54 68 69 73 20 69 73 20 61 20 73 74 72 69 6E 67
select type default
 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
 54 68 69 73 20 69 73 20 61 20 73 74 72 69 6E 67
no select type
 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
 54 68 69 73 20 69 73 20 61 20 73 74 72 69 6E 67
transfer variable array
 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
 54 68 69 73 20 69 73 20 61 20 73 74 72 69 6E 67
transfer constant array
 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
 54 68 69 73 20 69 73 20 61 20 73 74 72 69 6E 67

There is no fully portably way to do so because the standard does not recognize “bytes”. You can do processor-dependent transfers using CHARACTER intrinsic type but there is of course no requirement the transferred bit streams are going to be consistent with what you expect.

Separately see this thread at Intel Fortran: you do not need the SELECT TYPE guards for the transfer.

But most importantly, your code does not conform: function result of ALLOCATBLE attribute is referenced in instructions such as TRANSER with an undefined allocation status.

For my purposes a character variable of default kind serves as a byte well enough; the Intel
discussion does clarify the questions I had about the metamorphic variables. I had read it as described but at the time it did not work with three compilers. I do not see where it says the MOLD has to be allocated; but even though it works otherwise the Intel compiler option -check all flags that. Very easy to work around but I could only see where the type of the MOLD and its shape were used; I could not find anything indicating it needed allocated. I will allocate it and then ifort works as desired; gfortran (at least up to version 11) does not work with the desired method (method 3) which allows the function to work with arbitrary types; but the discussion on the Intel forum makes it clear it should so I will proceed with reporting that. Thanks for taking a look; several parts were using features I do not use all that often. Combined with the compilers not compiling it in the past and still producing different results I really needed a second pair of eyes on it.

The extended description for TRANSFER in the standard is such the SIZE of the transfer is determined from the MOLD argument, so it is as though a size(chars) instructions take place as part of the transfer which is nonconforming when your chars is not allocated.

Thanks. When I went to update the real code it already had

    if(allocated(chars))deallocate(chars)
   allocate(chars( storage_size(anything)/8) )

which explains why the unit tests ran (the ifort test uses -check all) so I apparently
needed to relearn that :slight_smile:

This is how you can proceed with standard Fortran 2018 with the caveat I mentioned upthread re: “bytes”. Also, how you can do the unit test:

module m
   use, intrinsic :: iso_fortran_env, only : CSZ => character_storage_size
contains
   function to_bytes(a) result(r)
      class(*), intent(in) :: a(..)
      character(len=1), allocatable :: r(:)
      select rank ( o => a )
         rank ( 0 )
            allocate( r(storage_size(o)/CSZ) )
            r = transfer( source=o, mold=r )
         rank ( 1 )
            allocate( r(storage_size(o)*size(o)/CSZ) )
            r = transfer( source=o, mold=r )
      end select
   end function
end module
   use m, only : to_bytes
   associate ( n => 42 )
      associate ( t => to_bytes( n ) ) 
         write(*,'(*(1x,z2.2))') 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,z2.2))') 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,z2.2))') 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,z2.2))') t
         write(*,'(*(1x,g0))') transfer( source=t, mold=s )
      end associate
   end associate
end 
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.34.31937.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
1 Like
$ gfortran bytes.f90
bytes.f90:12:54:

   12 |             allocate( r(storage_size(o)*size(o)/CSZ) )
      |                                                      1
internal compiler error: Segmentation fault
0x151caeb6908f ???
        /build/glibc-SzIz7B/glibc-2.31/signal/../sysdeps/unix/sysv/linux/x86_64/sigaction.c:0
0x151caeb4a082 __libc_start_main
        ../csu/libc-start.c:308
**Please submit a full bug report,**
with preprocessed source if appropriate.
Please include the complete backtrace with any bug report.
See <file:///usr/share/doc/gcc-11/README.Bugs> for instructions.
urbanjs@mercury:~/github$ 
urbanjs@mercury:~/github$ nvfortran bytes.f90
NVFORTRAN-S-0034-Syntax error at or near identifier rank (bytes.f90: 7)
NVFORTRAN-S-0034-Syntax error at or near end of line (bytes.f90: 8)
NVFORTRAN-S-0034-Syntax error at or near end of line (bytes.f90: 11)
  0 inform,   0 warnings,   ****3 severes**, fatal for to_bytes
   end associate

Thanks! Unfortunately, I need this to work with other compilers not quite as far along. I will keep this for the right time though. Works nicely with ifort/ifx 2023.

This program also fails with NAG. Upon trying to debug it, one gets errors like:

Bus error: 10

and

Segmentation fault: 11

If I sprinkle write statements in the code to try to see what is wrong, then it appears that the storage_size() intrinsic does not work correctly with the class(*) argument. I think that is a compiler error, not a code error, but I’m not certain.

Is NAG encountering a run-time error with the write instructions?

Technically the lines should be write(*,'(*(1x,z2.2))') iachar(t) to conform, and NAG being pedantic by default (from what I’ve heard) may be throwing an error because the standard technically does not permit Z editing with CHARACTER io-list items.

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 …

If I make just that iachar() change then I get

$ nagfor -f2018 tobytes.f90 && a.out
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7114
[NAG Fortran Compiler normal termination]
Segmentation fault: 11

I then sprinkled some write statements around and it appears that it is the storage_size() intrinsic that is failing. For example,

         rank ( 0 )
            write(*,*) 'storage_size(o) =', storage_size(o)
            allocate( r(storage_size(o)/CSZ) )
            r = transfer( source=o, mold=r )

gives

$ nagfor -f2018 tobytes.f90 && a.out
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7114
[NAG Fortran Compiler normal termination]
 storage_size(o) = 558760704
Segmentation fault: 11

Unless there is some specific restriction about the combination of class(*) and assumed rank declarations, that looks like a compiler error. I’m assuming the actual reported error is because stack size is exceeded due to the incorrect storage_size() value.

No, not with a SELECT RANK guard are there restrictions relevant to the usage here. And that is what I show. I too think it’s a compiler bug.

Anyways, you can try out the example in this comment with NAG.

NAG seems to compile and run that version correctly. That version still uses class(*), but it does not use assumed rank declarations. So it seems like the combination of those two things is what causes the problems with NAG. As you said in that link, gfortran compiles but produces incorrect results – that is what I see too.

That is basically what I have been using, except with a SELECT TYPE for the intrinsic types,
which for those types works with gfortran. I also did not know about the CSZ usage, and just hardcoded 8. It works with no conditionals with gfortran and ifort, but needed conditionals for character and real128 types for nvfortran. nvfortran does not support 128-bit floats; and the select type would not take character(len=*) last time I tried with nvfortran; although that was something I had questions about anyway. It is interesting that TRANSFER with the [’ '] argument worked directly in a lot of places; I am guessing that whether the size is taken from the mold or not is compiler-dependent.
The old procedures have worked for enough real cases I have been using it for a number of codes; but the original idea was that it should work for even user-defined types like a simple alias for TRANSFER with a character MOLD, but as this discussion shows, it was not that simple. I am updating the related procedures in places like M_anything.F90 in a collection of modules I have and some similar private functions per this discussion; but either the concept or the compilers need some fixes,
apparently. The differences between the compilers had been making me uncertain about whether such a function could be written successfully using standard Fortran (at least, without interfacing with C); resulting the uncertainty about what was my bug and what was a compiler bug – hence the post.