Save and load derived type with allocatable array

Dear all,

I want to ask, is it possible to quickly save and load a derived type with allocatable arrays in it into a binary file? I was not using derived type before, and I follow Gabriel’s workflow to communicate between fortran and matlab by saving each arrays into an individual binary. Now I have put all arrays into a derived type, could I simply use say one-liner to save the whole derived type into one binary file? Or do I still need to reference each of the arrays inside derived type and save them as individual binary files?

Best regards,

Hui-Jun Chen

1 Like

You can write a user-defined type to a stream opened as unformatted. You can also use NAMELIST output and read the data back in using

https://www.mathworks.com/matlabcentral/fileexchange/30179-read_namelist

which I have not used recently, but found very useful in the past.

It sounds like you are already comfortable with reading the binary data back into matlab?
You can simply write a user-defined type with fixed-size arrays, but if they are allocatable
you need to define an input/output procedure for the type; support for which varies between compilers.

1 Like

Thank you for your reply!

I guess I am wondering the best practice in memory allocation. What I have been taught is that fixed-size arrays use stack memory and allocatable arrays use heap memory. Is it true that a computer has way more heap than stack? So my teacher told me to define most of the arrays using allocatable.

1 Like

You can save them in a single file, but you have to write the different allocatable arrays one by one, you can’t simply write the whole derived type at once if it has an allocatable component. You can factor this by creating a user-defined I/O procedure for this type.

The stack is relatively small by default, but its size can be increased (the method depends on your operating system).

In general, in a DTIO implementation, you’re not restricted to fixed-sized arrays —you just have to be careful, e.g.:

subroutine write_unformatted(this, unit, iostat, iomsg)
    class(mytype), intent(in) :: this
    integer, intent(in) :: unit
    integer, intent(out) :: iostat
    character(*), intent(inout) :: iomsg
    ...
    if (allocated(this%array)) then
        n = size(this%array)

        write (unit, IOSTAT = iostat, IOMSG = iomsg) n
        if (iostat /= 0) return

        write (unit, IOSTAT = iostat, IOMSG = iomsg) this%array(:n)
        if (iostat /= 0) return
    else
        write (unit, IOSTAT = iostat, IOMSG = iomsg) 0
        if (iostat /= 0) return
    endif
    ...
end subroutine

subroutine read_unformatted(this, unit, iostat, iomsg)
    class(mytype), intent(inout) :: this
    integer, intent(in) :: unit
    integer, intent(out) :: iostat
    character(*), intent(inout) :: iomsg
    ...
    read (unit, IOSTAT = iostat, IOMSG = iomsg) n
    if (iostat /= 0) return

    if (allocated(this%array)) deallocate (this%array)
    allocate (this%array(n))

    read (unit, IOSTAT = iostat, IOMSG = iomsg) this%array(:n)
    if (iostat /= 0) return
    ...
end subroutine

2 Likes

An example of this is at FortranTip/dt_stream.f90 at main · Beliavsky/FortranTip · GitHub .

A derived type with allocatable components can be saved efficiently (serialized) by writing its dimensions and components using unformatted stream I/O. Later the dimensions and components (after allocation) can be read from the same file using stream I/O.

This is not really what you asked, @fish830911, but I have written a small module to do I/O based on Gabriel MATLAB/Fortran workflow tips.

module m

    use iso_fortran_env, only: dp=>real64
    implicit none

    interface writeBinary        
        module procedure writeBinary1, writeBinary2
    end interface
    
    interface readBinary        
        module procedure readBinary1, readBinary2
    end interface
    
    contains

    subroutine writeBinary1(x,file_name)
    !Write double precision array x into a BINARY file file_name
    implicit none
    !Declare inputs:
    real(dp), intent(in) :: x(:)
    character(len=*), intent(in) :: file_name
    integer :: unitno,i, ierr
    
    !Note the commands FORM="unformatted", ACCESS="stream"
    !and the fact that write(unitno) instead of write(unitno,*)
    OPEN(NEWUNIT=unitno, FILE=file_name, FORM="unformatted", ACCESS="stream", STATUS="unknown", iostat=ierr)
    if (ierr/=0) then
        error stop "Error: writeBinary: cannot open file"
    endif
    write(unitno) x
    close(unitno)
    
    end subroutine writeBinary1
    
    subroutine writeBinary2(x,file_name)
    !Write double precision array x into a BINARY file file_name
    implicit none
    !Declare inputs:
    real(dp), intent(in) :: x(:,:)
    character(len=*), intent(in) :: file_name
    integer :: unitno,i, ierr
    
    !Note the commands FORM="unformatted", ACCESS="stream"
    !and the fact that write(unitno) instead of write(unitno,*)
    OPEN(NEWUNIT=unitno, FILE=file_name, FORM="unformatted", ACCESS="stream", STATUS="unknown", iostat=ierr)
    if (ierr/=0) then
        error stop "Error: writeBinary: cannot open file"
    endif
    write(unitno) x
    close(unitno)
    
    end subroutine writeBinary2
    
    subroutine readBinary1(x,file_name)
    !Write double precision array x into a BINARY file file_name
    implicit none
    !Declare inputs:
    real(dp), intent(out) :: x(:)
    character(len=*), intent(in) :: file_name
    integer :: unitno,i, ierr
    
    !Note the commands FORM="unformatted", ACCESS="stream"
    !and the fact that write(unitno) instead of write(unitno,*)
    OPEN(NEWUNIT=unitno, FILE=file_name, FORM="unformatted", ACCESS="stream", STATUS="old", iostat=ierr)
    if (ierr/=0) then
        error stop "Error: readBinary: cannot open file"
    endif
    read(unitno) x
    close(unitno)
    
    end subroutine readBinary1
    
    subroutine readBinary2(x,file_name)
    !Write double precision array x into a BINARY file file_name
    implicit none
    !Declare inputs:
    real(dp), intent(out) :: x(:,:)
    character(len=*), intent(in) :: file_name
    integer :: unitno,i, ierr
    
    !Note the commands FORM="unformatted", ACCESS="stream"
    !and the fact that write(unitno) instead of write(unitno,*)
    OPEN(NEWUNIT=unitno, FILE=file_name, FORM="unformatted", ACCESS="stream", STATUS="old", iostat=ierr)
    if (ierr/=0) then
        error stop "Error: readBinary: cannot open file"
    endif
    read(unitno) x
    close(unitno)
    
    end subroutine readBinary2
    
end module m
    
program main
    use m, only: writeBinary, readBinary, dp
    implicit none
    real(dp), allocatable :: x(:,:), x_out(:,:)
    integer :: ii,i
    
    write(*,*) "This program writes a binary file containing a 1D array of double precision numbers"
    
    allocate(x(10,2))
    x(:,1) = [1.0_dp,2.0_dp,3.0_dp,4.0_dp,5.0_dp,6.0_dp,7.0_dp,8.0_dp,9.0_dp,10.0_dp]
    x(:,2) = [1.0_dp,2.0_dp,3.0_dp,4.0_dp,5.0_dp,6.0_dp,7.0_dp,8.0_dp,9.0_dp,10.0_dp]+10.0_dp
    
    write(*,*) "Array to be written:"
    do ii=1,size(x,1)
        write(*,*) x(ii,:) 
    enddo
    
    write(*,*) "Writing array to binary..."
    
    call writeBinary(x,'x_array.bin')
    
    write(*,*) "Reading array from binary file..."
    allocate( x_out(size(x,1),size(x,2)) )
    call readBinary(x_out,'x_array.bin')
    
    write(*,*) "Display array read from binary file"
    do ii=1,size(x_out,1)
        write(*,*) x_out(ii,:) 
    enddo
    
end program main
    

The generic procedures writeBinary and readBinary (should) work with double-precision arrays with arbitrary shape. As of now, they work only with 1 dim and 2 dim arrays. Indeed, I wrote a generic interface as follows:

interface writeBinary        
        module procedure writeBinary1, writeBinary2, etc UHMMMM
end interface
    
interface readBinary        
        module procedure readBinary1, readBinary2
end interface

but it is a bit tedious… In principle I should write many versions of the same routine, just to accomodate 2-dim, 3-dim, etc arrays.

My question: Is there a way to do this in a cleaner way i.e. to avoid repeating my code so many times? In my work sometimes I have arrays with 6 or 7 state variables

Thanks!

P.S. One trick would be to reshape the possibly multi-dim array I want to write as a 1-dim array:

x_1dim = reshape(x,size(x))

and then pass x1_dim to writeBinary. But I prefer not to do this since for large arrays reshape gives me a runtime error in Windows.

Is it like writing the binary file bit by bit basically?

Thanks!

1 Like

I wrote a module that has savebin and loadbin subroutines up to dimension 6 lol. I just use module procedure to hide the clutter from myself.

1 Like

I have never understood why not, but no, simple statements like

write(unit) my_type
read(unit) my_type

do work by default when the components are ordinary arrays but not when the components are allocatable arrays. This is just a choice made in the design of the language, and it has been that way for over two decades, so it is unlikely that it will ever change. However, you can write i/o procedures specific to that derived type that do allow the above statements to work, and you can invoke those procedures also in the regular way with a call statement. If the object is a parameterized derived type, then the above statements also work by default (without the programmer doing anything special), but PDTs are not yet well supported by compilers, so the programmer must beware if code portability is critical. This has been an issue only since f2003 when components of a derived type were first allowed to be allocatable.

1 Like

And you wrote

interface writeBinary        
module procedure writeBinary1, writeBinary2, writeBinary3,writeBinary4,writeBinary5, writeBinary6
end interface

with the corresponding subroutines after the contains statement?

Yes, basically. That’s a Fortran 2003 feature, to provide custom I/O for a derived type:

type :: mytype
    ...
    real, allocatable :: array(:)
    ...
contains
    generic :: write(unformatted) => write_unformatted
    procedure :: write_unformatted

    generic :: read(unformatted) => read_unformatted
    procedure :: read_unformatted
end type

There’s also an equivalent for formatted i/O, that requires two additional arguments for the implementation subroutines, and uses “dt” as the format edit descriptor.

2 Likes

Note that you could do “write(unit) transfer(my_type,[‘A’])”. But it would suffer some of the same portability issues as other possibilities, particularly because it would probably literally transfer bytes used for padding and alignment. To read it back you would have to know that information even if you read it as bytes and did a transfer back to the user-defined type with at least some compilers, I suspect. So unless you are using just one compiler and it is likely to be stable it is probably not the way you want to go, just an interesting possibility.

1 Like