Dumping double arrays to a character variable using unformatted write

I’m trying to WRITE the content of several double precision arrays of variable length to a character variable just like I would to a physical file using an unformatted write. Writing to a physical file works like I expected it to but I’d like not to rely on a physical file.
Is this possible using Fortran’s WRITE statements? Or do I have to cook up my own writing routines?

This is roughly what I’m doing with the physical file:

INTEGER, PARAMETER :: u = 400
INTEGER :: ios
DOUBLE PRECISION, DIMENSION(:,:), POINTER :: pd_test1
DOUBLE PRECISION, DIMENSION(:), POINTER :: pd_test2

ALLOCATE(pd_test1(3,4))
ALLOCATE(pd_test2(5))

OPEN(UNIT=u, FILE="test.bin", ACCESS='stream', STATUS='replace', ACTION='write', IOSTAT=ios)
WRITE(u, iostat=ios) pd_test1, pd_test2

I’d like to have the contents of that file “test.bin” in a character variable without having to write the file and read from it.

I would use the transfer function for that. I am not aware of the possibility to do that via an internal write - as you never indicate the form of an internal file (unlike a file on disk) there is no way to indicate the unformattedness.

Section 12.4 Internal Files of Fortran 2018 contains this bullet item:

Reading and writing records shall be accomplished only by sequential access formatted data transfer statements.

However, you do not need internal files or I/O statements for copying variables. Just declare a double precision array for the temporary storage and copy into it using an assignment statement.

If you want to do a 1-liner for writing a string character maybe something like this could work

program hello
double precision, pointer :: pd_test1(:,:)
double precision, pointer :: pd_test2(:)
character(len=:), allocatable :: s
integer :: m,n,p

m = 3
n = 4
p = 5
allocate(pd_test1(m,n))
allocate(pd_test2(p))

pd_test1 = reshape( [ ((ix+jx, ix = 1, m), jx = 1, n) ], [ m, n ] )
write(*,*) 'pd_test1: ', pd_test1
write(*,*)

pd_test2 = [ (ix, ix = 1, p) ]
write(*,*) 'pd_test2: ', pd_test2
write(*,*)

allocate(character(8*m*n*p) :: s)
write(s,*) pd_test1(:,:), pd_test2(:)
write(*,*) 's: ' , s

end program hello

You should allocate a dynamic string according to the size of the data you want to write down.

Then, you can adapt it with a specific format.

As mentioned a simple call to transfer(3f) does the job. If you do it a lot this module
has worked with several compilers that converts a scalar, vector, or matrix to “bytes”,
which is a vector of single-character variables.

I had some trouble with some compilers so there is a case for each type, which I thought
should not be required but was by some compilers.

This shows a general wrapper around transfer(3f) that allocates the returned array. If you just
need a call to transfer(3f) it should be easy to reduce it back to just a few statements, but someone might find the module handy.

module and example program
module M_anything
use, intrinsic :: ISO_FORTRAN_ENV, only : INT8, INT16, INT32, INT64       !  1           2           4           8
use, intrinsic :: ISO_FORTRAN_ENV, only : REAL32, REAL64, REAL128         !  4           8          10
use, intrinsic :: ISO_FORTRAN_ENV, only : CSZ => CHARACTER_STORAGE_SIZE
use, intrinsic :: iso_fortran_env, only : stderr => error_unit !! ,input_unit,output_unit
implicit none
private
integer,parameter        :: dp=kind(0.0d0)
public anything_to_bytes
interface anything_to_bytes
   module procedure anything_to_bytes_mat
   module procedure anything_to_bytes_arr
   module procedure anything_to_bytes_scalar
end interface anything_to_bytes
contains

function anything_to_bytes_mat(anything) result(chars)

! ident_1="@(#) M_anything anything_to_bytes_mat(3fp) any vector of intrinsics to bytes (an array of CHARACTER(LEN=1) variables)"

class(*),intent(in)          :: anything(:)
character(len=1),allocatable :: chars(:)

   if(allocated(chars))deallocate(chars)
   allocate(chars( storage_size(anything)/CSZ * size(anything) ) )

   select type(anything)
    type is (character(len=*));     chars=transfer(anything,chars)
    type is (complex);              chars=transfer(anything,chars)
    type is (complex(kind=dp));     chars=transfer(anything,chars)
    type is (integer(kind=int8));   chars=transfer(anything,chars)
    type is (integer(kind=int16));  chars=transfer(anything,chars)
    type is (integer(kind=int32));  chars=transfer(anything,chars)
    type is (integer(kind=int64));  chars=transfer(anything,chars)
    type is (real(kind=real32));    chars=transfer(anything,chars)
    type is (real(kind=real64));    chars=transfer(anything,chars)
    type is (real(kind=real128));   chars=transfer(anything,chars)
    type is (logical);              chars=transfer(anything,chars)
    class default
      chars=transfer(anything,chars) ! should work for everything, does not with some compilers
      !stop 'crud. anything_to_bytes_mat(1) does not know about this type'
   end select

end function anything_to_bytes_mat

function anything_to_bytes_arr(anything) result(chars)

! ident_1="@(#) M_anything anything_to_bytes_arr(3fp) any vector of intrinsics to bytes (an array of CHARACTER(LEN=1) variables)"

class(*),intent(in)          :: anything(:,:)
character(len=1),allocatable :: chars(:)

   if(allocated(chars))deallocate(chars)
   allocate(chars( storage_size(anything)/CSZ * size(anything) ) )

   select type(anything)
    type is (character(len=*));     chars=transfer(anything,chars)
    type is (complex);              chars=transfer(anything,chars)
    type is (complex(kind=dp));     chars=transfer(anything,chars)
    type is (integer(kind=int8));   chars=transfer(anything,chars)
    type is (integer(kind=int16));  chars=transfer(anything,chars)
    type is (integer(kind=int32));  chars=transfer(anything,chars)
    type is (integer(kind=int64));  chars=transfer(anything,chars)
    type is (real(kind=real32));    chars=transfer(anything,chars)
    type is (real(kind=real64));    chars=transfer(anything,chars)
    type is (real(kind=real128));   chars=transfer(anything,chars)
    type is (logical);              chars=transfer(anything,chars)
    class default
      chars=transfer(anything,chars) ! should work for everything, does not with some compilers
      !stop 'crud. anything_to_bytes_arr(1) does not know about this type'
   end select

end function anything_to_bytes_arr

function  anything_to_bytes_scalar(anything) result(chars)

! ident_2="@(#) M_anything anything_to_bytes_scalar(3fp) anything to bytes (an array of CHARACTER(LEN=1) variables)"

class(*),intent(in)          :: anything
character(len=1),allocatable :: chars(:)
   if(allocated(chars))deallocate(chars)
   allocate(chars( storage_size(anything)/CSZ) )

   select type(anything)
    type is (character(len=*));     chars=transfer(anything,chars)
    type is (complex);              chars=transfer(anything,chars)
    type is (complex(kind=dp));     chars=transfer(anything,chars)
    type is (integer(kind=int8));   chars=transfer(anything,chars)
    type is (integer(kind=int16));  chars=transfer(anything,chars)
    type is (integer(kind=int32));  chars=transfer(anything,chars)
    type is (integer(kind=int64));  chars=transfer(anything,chars)
    type is (real(kind=real32));    chars=transfer(anything,chars)
    type is (real(kind=real64));    chars=transfer(anything,chars)
    type is (real(kind=real128));   chars=transfer(anything,chars)
    type is (logical);              chars=transfer(anything,chars)
    class default
      chars=transfer(anything,chars) ! should work for everything, does not with some compilers
      !stop 'crud. anything_to_bytes_scalar(1) does not know about this type'
   end select

end function  anything_to_bytes_scalar
end module M_anything
program demo_anything_to_bytes
use M_anything,      only : anything_to_bytes
implicit none
character(len=1),allocatable :: chars(:)
integer :: i
integer :: ints(10)=[(i*i,i=1,size(ints))]
doubleprecision :: x(10),y(10),xy(2,10)
   x=sin(dble(ints))
   y=cos(dble(ints))
   xy(1,:)=x
   xy(2,:)=y
   chars=anything_to_bytes([x,y,xy])
   write(*,'(/,4(1x,z2.2))')chars
end program demo_anything_to_bytes

A shorter example for both an array of single characters and one big character variable.
Not sure which you wanted:

program demo_anything_to_bytes
use, intrinsic :: iso_fortran_env, only : CSZ => character_storage_size
implicit none
character(len=1),allocatable :: chars(:)
character(len=256) :: iomsg
character(len=:),allocatable :: bigline, bigline2
integer :: i, isize, lun, iostat
integer :: ints(5)=[(i*i,i=1,size(ints))]
doubleprecision :: xy(2,5), yx(5,2)
   ! make up some arrays
   xy(1,:)=sin(dble(ints))
   xy(2,:)=cos(dble(ints))
   yx=transpose(xy)
   isize=storage_size(0.0d0)/CSZ * (size(xy)+size(yx) )

   ! array of single characters
   if(allocated(chars))deallocate(chars)
   allocate(chars(isize) )
   chars=transfer([xy,yx],chars)
   write(*,'(/,8(1x,z2.2))')chars

   ! single character variable
   if(allocated(bigline))deallocate(bigline)
   allocate (character(len=isize) :: bigline)
   bigline(:)=transfer([xy,yx],bigline)
   write(*,'(/,*(z2.2))')(bigline(i:i),i=1,len(bigline))

   ! write and then read a file into character variable to confirm
   OPEN(NEWUNIT=lun, FILE="test.bin",ACCESS='stream',STATUS='replace',ACTION='readwrite', IOSTAT=iostat)
   WRITE(lun, iostat=iostat,iomsg=iomsg) xy, yx
   if(iostat.ne.0)write(*,*)trim(iomsg)
   REWIND(lun,iostat=iostat)
   if(iostat.ne.0)write(*,*)trim(iomsg)
   if(allocated(bigline2))deallocate(bigline2)
   allocate (character(len=isize) :: bigline2)
   read(lun,iostat=iostat,iomsg=iomsg)bigline2
   if(iostat.ne.0)write(*,*)trim(iomsg)

   write(*,'(/,a)')'print chars, bigline, bigline2'
   write(*,'(/,*(z2.2))')chars
   write(*,'(/,*(z2.2))')(bigline(i:i),i=1,len(bigline))
   write(*,'(/,*(z2.2))')(bigline2(i:i),i=1,len(bigline2))

   write(*,'(a)')merge('YEAH!','BOOH!',bigline.eq.bigline2)

end program demo_anything_to_bytes

This seems to work as expected, at least judging from my memory inspections with the debugger with a simple test case.
I now wrote convenience dump functions like this one for different variable types:

SUBROUTINE DUMP_VECTOR(vec, c, offset)
   IMPLICIT NONE
   DOUBLE PRECISION, DIMENSION(:), INTENT(IN) :: vec
   CHARACTER(LEN=*), INTENT(INOUT) :: c
   INTEGER, INTENT(INOUT) :: offset
   INTEGER :: l1, bytes
   l1 = SIZE(vec)
   bytes = l1 * 8
   c(offset:) = TRANSFER(vec, c(1:bytes))
   offset = offset + bytes
END SUBROUTINE DUMP_VECTOR

Still have to test those, though.

If you are concerned about portability, namely writing data on one machine and reading it on another, then you might have to worry about little- and big-endian issues. That is, does the first character in the output array get the low-order bits of the vec(1) array element or the high-order bits. Most machines these days are little-endian, but there are some exceptions. The other minor concern might be the assumption of 8 characters for each vec(:) element. You might consider replacing that literal value with something like storage_size(vec)/storage_size(c). That should compile to a constant value (especially if it is a parameter expression, typically 8 of course), so it should not affect efficiency, but it would be there just in case you ever compile your code with options for 128-bit double precision or for 16-bit characters.

OK, thanks for the hints! Portability in this case is not an issue, so I need not worry about the endianness. As for the size of the elements, I did in fact use storage_size(some_double_var)/8 (times the number of elements in the vector for the characters). Concerning the character width, I must make sure that stays 8 bits on the Fortran side as I actually need to pass byte vectors between Fortran and C.