Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.

unformatted write of allocatable data structure

Guthrie_M_
Beginner
450 Views

This is confusing, because it seems to work with the Intel compiler (2015) when the write is done in the same program before the read.

The compile fails with G95 giving the error message

         write(1)TestData
                 1
Error: Data transfer element at (1) cannot have ALLOCATABLE components

Here is the example code. Invoke with "test" to write first and "test 1" to attempt to read the old file, which fails. Why?

      implicit none
      
      integer::i
      character(len=1)::buf
      logical::WriteFileFirst=.false.
      
      type TestType
         real*8,dimension(:),allocatable::a
      end type TestType
       
      type(TestType),dimension(:),allocatable::TestData
      
      call getarg(1,buf)
      if(buf.ne."")then
         write(*,*)'using old file'
      else
         WriteFileFirst=.true.
         write(*,*)'Writing file first'
      endif
       
      allocate(TestData(3))
      do i=1,3
         allocate(TestData(i)%a(2))
      enddo
      
      if(WriteFileFirst)then
         do i=1,3
            TestData(i)%a(1)=3
            TestData(i)%a(2)=4
         enddo
         
         open(1,file='TestData',form='unformatted')
         write(1)TestData
         close(1)
      endif
      
      open(1,file='TestData',form='unformatted')
      read(1)TestData
      close(1)
      write(*,*)'TestData(1)=',TestData(1)
      end
     

0 Kudos
9 Replies
IanH
Honored Contributor II
450 Views

Objects of a type that has pointer or allocatable components have to be handled by a defined input/output procedure for the type (that's the culmination of a series of rules in F2008 9.6.3p7 around how items in an input/output list are expanded).  There is no such procedure in your code.

I'd expect a diagnostic from the compiler for this code, though the standard doesn't formally require such a diagnostic.

0 Kudos
Steven_L_Intel1
Employee
450 Views

Indeed, Intel Fortran ought to give an error for this program. I will let the developers know.

0 Kudos
Guthrie_M_
Beginner
450 Views

Thanks for the quick replies. And, how could I fix this example code so it would work?

0 Kudos
IanH
Honored Contributor II
450 Views

You could provide defined input/output procedures for your type with allocatable components.

An example attached, with the unformatted and formatted representations chosen arbitrarily.

(While writing this I see that the compiler should also be complaining about the formatted output of the object as well as the unformatted input/output operations.)

module TestTypes
  implicit none
  private
  
  integer, parameter :: rk = KIND(1.0D0)
  
  type, public :: TestType
     real(rk),dimension(:),allocatable::a
  end type TestType
  
  public :: write(formatted)
  public :: read(unformatted)
  public :: write(unformatted)
  
  interface write(formatted)
    procedure write_formatted
  end interface write(formatted)
  
  interface read(unformatted)
    procedure read_unformatted
  end interface read(unformatted)
  
  interface write(unformatted)
    procedure write_unformatted
  end interface write(unformatted)
contains
  subroutine write_formatted(dtv, unit, iotype, v_list, iostat, iomsg)
    class(TestType), intent(in) :: dtv
    integer, intent(in) :: unit
    character(*), intent(in) :: iotype
    integer, intent(in) :: v_list(:)
    integer, intent(out) :: iostat
    character(*), intent(inout) :: iomsg
    
    write (unit, "(L1,1X)", IOSTAT=iostat, IOMSG=iomsg) allocated(dtv%a)
    if (iostat /= 0) return
    
    if (allocated(dtv%a)) then
      write (unit, *, IOSTAT=iostat, IOMSG=iomsg)  &
          lbound(dtv%a), ubound(dtv%a), dtv%a
    end if
  end subroutine write_formatted
  
  subroutine write_unformatted(dtv, unit, iostat, iomsg)
    class(TestType), intent(in) :: dtv
    integer, intent(in) :: unit
    integer, intent(out) :: iostat
    character(*), intent(inout) :: iomsg
    
    write (unit, IOSTAT=iostat, IOMSG=iomsg) allocated(dtv%a)
    if (iostat /= 0) return
    
    if (allocated(dtv%a)) then
      write (unit, IOSTAT=iostat, IOMSG=iomsg)  &
          lbound(dtv%a), ubound(dtv%a), dtv%a
    end if
  end subroutine write_unformatted
  
  subroutine read_unformatted(dtv, unit, iostat, iomsg)
    class(TestType), intent(inout) :: dtv
    integer, intent(in) :: unit
    integer, intent(out) :: iostat
    character(*), intent(inout) :: iomsg
    
    logical :: alloc
    integer :: lower
    integer :: upper
    
    if (allocated(dtv%a)) deallocate(dtv%a)
    
    read (unit, IOSTAT=iostat, IOMSG=iomsg) alloc
    if (iostat /= 0) return
    
    if (alloc) then
      read (unit, IOSTAT=iostat, IOMSG=iomsg) lower, upper
      if (iostat /= 0) return
      allocate(dtv%a(lower:upper))
      read (unit, IOSTAT=iostat, IOMSG=iomsg) dtv%a
    end if
  end subroutine read_unformatted
end module TestTypes


  use TestTypes
  implicit none
  
  integer::i
  character(len=1)::buf
  logical::WriteFileFirst=.false.
   
  type(TestType),dimension(:),allocatable::TestData
  
  call getarg(1,buf)
  if(buf.ne."")then
     write(*,*)'using old file'
  else
     WriteFileFirst=.true.
     write(*,*)'Writing file first'
  endif
   
  allocate(TestData(3))
  do i=1,3
     allocate(TestData(i)%a(2))
  enddo
  
  if(WriteFileFirst)then
     do i=1,3
        TestData(i)%a(1)=3
        TestData(i)%a(2)=4
     enddo
     
     open(1,file='TestData',form='unformatted')
     write(1)TestData
     close(1)
  endif
  
  open(1,file='TestData',form='unformatted')
  read(1)TestData
  close(1)
  write(*,*)'TestData(1)=',TestData(1)
end

 

0 Kudos
Guthrie_M_
Beginner
450 Views

Wow! Many cool things. Thanks for all that. Your code didn't compile with Intel or G95 right off, but I'm working on it.

In my experimenting I discovered that while write(1)TestData does not produce a file that is readable outside the program itself (by read(1)TestData), the following does work

         open(1,file='TestData',form='unformatted')
         write(1)(TestData(i)%a,i=1,3)
         close(1)

which can be read using

      open(1,file='TestData',form='unformatted')
      read(1)(TestData(i)%a,i=1,3)
      close(1)

So it looks like a quick and dirty work around for read/wirte involving data structures is to explicitly refer to the elements of the structure.

 

0 Kudos
Steven_L_Intel1
Employee
450 Views

G95 won't support user-defined derived type I/O. I don't think gfortran has that yet either.

0 Kudos
Steven_L_Intel1
Employee
450 Views

Missing errors escalated as issue DPD200408497.

0 Kudos
JohnNichols
Valued Contributor III
450 Views

 

Thanks - I will use this if that is ok.

Which is better rk = KIND(1.0D0) or the kind(15,307)?


 

John

ianh wrote:

You could provide defined input/output procedures for your type with allocatable components.

An example attached, with the unformatted and formatted representations chosen arbitrarily.

(While writing this I see that the compiler should also be complaining about the formatted output of the object as well as the unformatted input/output operations.)

module TestTypes
  implicit none
  private
  
  integer, parameter :: rk = KIND(1.0D0)
  
  type, public :: TestType
     real(rk),dimension(:),allocatable::a
  end type TestType
  
  public :: write(formatted)
  public :: read(unformatted)
  public :: write(unformatted)
  
  interface write(formatted)
    procedure write_formatted
  end interface write(formatted)
  
  interface read(unformatted)
    procedure read_unformatted
  end interface read(unformatted)
  
  interface write(unformatted)
    procedure write_unformatted
  end interface write(unformatted)
contains
  subroutine write_formatted(dtv, unit, iotype, v_list, iostat, iomsg)
    class(TestType), intent(in) :: dtv
    integer, intent(in) :: unit
    character(*), intent(in) :: iotype
    integer, intent(in) :: v_list(:)
    integer, intent(out) :: iostat
    character(*), intent(inout) :: iomsg
    
    write (unit, "(L1,1X)", IOSTAT=iostat, IOMSG=iomsg) allocated(dtv%a)
    if (iostat /= 0) return
    
    if (allocated(dtv%a)) then
      write (unit, *, IOSTAT=iostat, IOMSG=iomsg)  &
          lbound(dtv%a), ubound(dtv%a), dtv%a
    end if
  end subroutine write_formatted
  
  subroutine write_unformatted(dtv, unit, iostat, iomsg)
    class(TestType), intent(in) :: dtv
    integer, intent(in) :: unit
    integer, intent(out) :: iostat
    character(*), intent(inout) :: iomsg
    
    write (unit, IOSTAT=iostat, IOMSG=iomsg) allocated(dtv%a)
    if (iostat /= 0) return
    
    if (allocated(dtv%a)) then
      write (unit, IOSTAT=iostat, IOMSG=iomsg)  &
          lbound(dtv%a), ubound(dtv%a), dtv%a
    end if
  end subroutine write_unformatted
  
  subroutine read_unformatted(dtv, unit, iostat, iomsg)
    class(TestType), intent(inout) :: dtv
    integer, intent(in) :: unit
    integer, intent(out) :: iostat
    character(*), intent(inout) :: iomsg
    
    logical :: alloc
    integer :: lower
    integer :: upper
    
    if (allocated(dtv%a)) deallocate(dtv%a)
    
    read (unit, IOSTAT=iostat, IOMSG=iomsg) alloc
    if (iostat /= 0) return
    
    if (alloc) then
      read (unit, IOSTAT=iostat, IOMSG=iomsg) lower, upper
      if (iostat /= 0) return
      allocate(dtv%a(lower:upper))
      read (unit, IOSTAT=iostat, IOMSG=iomsg) dtv%a
    end if
  end subroutine read_unformatted
end module TestTypes


  use TestTypes
  implicit none
  
  integer::i
  character(len=1)::buf
  logical::WriteFileFirst=.false.
   
  type(TestType),dimension(:),allocatable::TestData
  
  call getarg(1,buf)
  if(buf.ne."")then
     write(*,*)'using old file'
  else
     WriteFileFirst=.true.
     write(*,*)'Writing file first'
  endif
   
  allocate(TestData(3))
  do i=1,3
     allocate(TestData(i)%a(2))
  enddo
  
  if(WriteFileFirst)then
     do i=1,3
        TestData(i)%a(1)=3
        TestData(i)%a(2)=4
     enddo
     
     open(1,file='TestData',form='unformatted')
     write(1)TestData
     close(1)
  endif
  
  open(1,file='TestData',form='unformatted')
  read(1)TestData
  close(1)
  write(*,*)'TestData(1)=',TestData(1)
end

 

0 Kudos
Steven_L_Intel1
Employee
450 Views

The missing errors will be fixed in a future major release of the compiler (not the one this year.)

0 Kudos
Reply