Working with parameterised derived type containing array of parameterised derived type

Another potential advantage of PDTs is that you can use them in i/o statements, where you cannot do the same thing with allocatable components. Here is a short example of what I mean.

program pdt
   implicit none
   integer, parameter :: lenap = 2
   type data_static_t
      real :: a(lenap)
   end type data_static_t
   type data_alloc_t
      real, allocatable :: a(:)
   end type data_alloc_t
   type data_pdt_t(lena)
      integer, len :: lena
      real :: a(lena)
   end type data_pdt_t
   integer :: lena, lenx, i
   type(data_static_t), allocatable :: x(:)
   type(data_alloc_t), allocatable  :: y(:)
   type(data_pdt_t(:)), allocatable :: z(:)
   character(*), parameter :: fmta = '(*(f6.3))'

   lena = lenap
   lenx = 3

   write(*,*) 'lena=', lena, ' lenx=', lenx
   allocate( x(lenx) )
   allocate( y(lenx) )
   allocate( data_pdt_t(lena) :: z(lenx) )

   do i = 1, lenx
      call random_number( x(i)%a )
      y(i)%a = x(i)%a   ! allocate and assign.
      z(i)%a = x(i)%a
   enddo

   write(*,fmta) x
   write(*,fmta) (y(i)%a, i=1,lenx)
   write(*,fmta) z
end program pdt

$ nagfor pdt.F90 && a.out
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7114
[NAG Fortran Compiler normal termination]
 lena= 2  lenx= 3
 0.138 0.807 0.928 0.384 0.540 0.950
 0.138 0.807 0.928 0.384 0.540 0.950
 0.138 0.807 0.928 0.384 0.540 0.950

There are three derived types, one with static component size, one with allocatable size, and one with parameterized size. With the static and parameterized sizes, you can just put the array in an i/o statement. I used formatted i/o in this example, but the most useful case is when you write and read unformatted i/o, for example to write out checkpoint data, or to transfer data from one run to the next.

However, the straightforward write(*,fmta) y does not work, the programmer must specify the components explicitly. I have long wondered why that limitation was placed on allocatable components in the language, but for whatever reasons, it is there. Imagine the complicated write statements that are required when you have several levels of nesting in the derived type, each with allocatable components.

The write(*,fmta) z is nice because it allows the simple write statement, while also allowing runtime specification of the length of the components. There is no need to bash gfortran any more over this (I’m grateful gfortran does what it can do), but I used nagfor in the example because gfortran does not run this code. Of course, the allocatable version allows each array member to have different lengths, something that I’m not doing here, so in that sense the three versions have some common overlaps in applicability, but they are not all exactly equivalent.