Writing a large derived type variable with many components

I have a number of derived types in my code with many (dozens) of components, some of which are allocatable. I am writing the user-defined subroutines for unformatted reading and writing. Is there a way that I can indicate that I want all components of the variable written out or read in without having to list the components explicitly. For example, if this is my write routine

subroutine wall_write(w,unit,iostat,iomsg)
class(wall_type), intent(in) :: w
integer, intent(in) :: unit
integer, intent(out) :: iostat
character(*), intent(inout) :: iomsg
write(unit=unit,iostat=iostat,iomsg=iomsg) w%i,w%j,w%k,w%itmp
end subroutine wall_write

is there a way to indicate that I want to write out everything, i.e. i, j, k, itmp, without explicitly listing them. This is a simple case, but I have dozens and potentially hundreds of components.

1 Like

Since the derived types are allocatable, I think you need to list the components individually, as you have done. You could write a Python script that reads the definitions of the derived types and writes the components. To make it easier to write such a Python script, you could declare each component of a derived type on a separate line, for example

type, public :: array_3d
   integer, allocatable :: ix(:) 
   integer, allocatable :: iy(:) 
   integer, allocatable :: iz(:) 
   real   , allocatable :: val(:)
end type array_3d

Then to get the component names you just need to pick out the non-blank characters after :: and before ( if present. An advantage of a script is that you just run it again when components of the type are added or removed. You may also need a subroutine to read a derived type, which can be written by a similar script. To check that a type is properly written, you could write code to check that when a type is written and read back in, it is the same as the original.

Thanks, but my goal here is to write out the contents of derived type variables in a Fortran code to a file, to be read in again with similar Fortran code. The purpose of this is to enable a dump of all variables to enable a restart of the code. It seems to me from what I am reading that I have no choice but to list all the derived type components in my write and read subroutines.

Right. My suggestion was to write a Python code that reads the Fortran code defining the derived type and then writes Fortran code for appropriate read and write statements. Since the derived type has allocatable components, your subroutine to write the derived type should also write the dimensions of those components at the beginning. The subroutine to read the derived type can read the dimensions, allocate the components, and then read the values of the components.

@mcgratta, welcome to this forum, glad you followed up on my suggestion over at the Intel Fortran forum and posted here also.

Readers can see my suggestion to @mcgratta re: the derived-type IO question by following this link.

I personally am not at all fond of using another language such as Python or Perl, etc. to script a Fortran solution, so I never recommend that myself but to each their own.

1 Like

@mcgratta , your post quoted above and your subsequent post at the Intel forum appear incongruent at first glance to me. Perhaps readers may be able to provide you with better guidance if you can expend some effort toward a simple prototype that reflects the kind of facility (the “requirements”) you seek and share it some place.

Your statement, “As for your suggestion, I worry about making the sub-sub components of this derived type more complicated,” is surprising to me. My suggestion was clearly meant to give you a workaround in the absence of any direct feature in the language. And the idea was to use organization to help with this. If you have “potentially hundreds of components,” many readers of your code, including yourself in a future incarnation, will very likely find it difficult to manage. Chances are good any organization you pursue will also help with maintenance and enhancement of your code.

As to “I was wondering if there’s some way to automatically list the components in the order that they are listed in the type declaration,” what I suggested earlier with “a combination of intrinsic derived-type IO plus user-defined IO” will go a long way toward this.

See if you can use something like the following to offer up an example to readers of what you are looking for: (it uses formatted IO for illustration purposes, you can change it to unformatted)

module m
   type :: x_t
      ! Group x: may be the "inputs"
      integer :: i=1, j=2, k=3
   end type 
   type :: y_t
      ! Group y: may be the "intermediate data", the temporaries?
      integer :: itmp=0
   end type 
   type :: z_t
      ! Group z: perhaps the "outputs"
      integer :: l=-1, m=-2, n=-3
   end type
   type :: w_t
      type(x_t) :: x
      type(y_t) :: y
      type(z_t) :: z
   contains
      private
      procedure :: write_w
      generic, public :: write(formatted) => write_w 
   end type
contains
   subroutine write_w( dtv, lun, iotype, vlist, istat, imsg )
      ! Argument list
      class(w_t), intent(in)           :: dtv
      integer, intent(in)              :: lun
      character(len=*), intent(in)     :: iotype
      integer, intent(in)              :: vlist(:)
      integer, intent(out)             :: istat
      character (len=*), intent(inout) :: imsg
      istat = 0
      select case ( iotype )
         case ( "LISTDIRECTED" )
            ! Adapt as needed
            write( lun, fmt=*, iostat=istat, iomsg=imsg ) dtv%x, dtv%y, dtv%z
         case ( "DT" )
            ! Elided
            if ( size(vlist) == 0 ) istat = 1
         case ( "NAMELIST" )
            ! Elided
      end select
   end subroutine
end module
   use m
   type(w_t) :: w
   print *, w
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.3.0 Build 20210609_000000
Copyright (C) 1985-2021 Intel Corporation. All rights reserved.

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

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

C:\Temp>p.exe
1 2 3 0 -1 -2 -3

C:\Temp>

1 Like

This might not be the kind of solution you are hoping to get. But being in a similar situation to yours a while ago (where the code had to read and write tens of scalar and allocatable variables of intrinsic types for restart functionality), I ended up converting the type with allocatable components to a namelist. Once all are in a namelist, IO becomes fairly easy and automatic, although you still have to preallocate any allocatable before namelist IO.

Thanks for the advice. Given that I am not familiar with many of these newer features of Fortran, the safest thing for me to do is to just write all the components out to a 1-D array and read them back in the same way. I was just trying to find out if there is a new Fortran feature that would help. My biggest concern is not the scalar components, but rather the allocatable ones. I could reorganize the scalars into derived types, but the problem remains for the allocatables. I think there is no way around just writing them out. I do use NAMELIST for the input of parameters, but I’m not conversant in NAMELIST I/O.

Thanks again.

@mcgratta , you will know there are a lot of online (and hardcopy) resources available on modern Fortran. If you are interested, take a look at this page at this Fortran-lang site: Learn — Fortran Programming Language.

Do note, since you are already familiar with polymorphic arguments and type-bound procedures and user-defined IO, etc. as seen clearly here, you are much further along that most when it comes to learning newer features.

Going with “just write all the components out to a 1-D array and read them back in the same way” would be a significant step back relative to what you have shown, not at all a good advertisement for Fortran.

Re: “My biggest concern is … the allocatable ones,” no, you need not see it as a “big… concern”. ALLOCATABLE components including those of rank greater than 0 can be managed with just a little more attention and note “defined IO” fits well with this.

1 Like