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

UDDTIO: unexpected end-of-file error with repeat specification in DT edit descriptor

FortranFan
Honored Contributor II
459 Views

The following simple code runs into an unexpected end-of-file error:

module string_m

   implicit none

   private

   type, public :: string_t
      private
      character(len=:), allocatable :: m_s
   contains
      !private
      procedure, pass(this), private :: assign_s
      procedure, pass(this), private :: read_s
      procedure, pass(this), private :: write_s
      generic, public :: assignment(=) => assign_s
      generic :: read(formatted) => read_s
      generic :: write(formatted) => write_s
   end type string_t

   !.. Named constants
   integer, parameter :: MAXLENS = 256

contains

   subroutine assign_s( this, rhs )

      class(string_t), intent(inout) :: this
      character(len=*), intent(in)   :: rhs

      this%m_s = rhs

      return

   end subroutine assign_s

   subroutine read_s(this, lun, iotype, vlist, istat, imsg)

      !.. Argument list
      class(string_t), intent(inout)  :: this
      integer, intent(in)             :: lun
      character(len=*), intent(in)    :: iotype
      integer, intent(in)             :: vlist(:)
      integer, intent(out)            :: istat
      character(len=*), intent(inout) :: imsg

      !.. Local variables
      character(len=MAXLENS) :: sfmt
      character(len=:), allocatable :: word
      integer :: wordsize

      sfmt = "(A)"
      wordsize = MAXLENS
      if ( (iotype == "DT").and.(size(vlist) >= 1) ) then

         ! vlist(1) to be used as the field width of the character component.
         if ( vlist(1) < MAXLENS ) then
            wordsize = vlist(1)
            write(sfmt,"(A,I0,A)", iostat=istat, iomsg=imsg ) "(A", wordsize, ")"
            if (istat /= 0) return
         end if

      end if

      allocate( character(len=wordsize) :: word, stat=istat, errmsg=imsg )
      if (istat /= 0) return

      ! read in the string
      read (unit=lun, fmt=sfmt, iostat=istat, iomsg=imsg) word
      if (istat /= 0) return

      this%m_s = word

      return

   end subroutine read_s

   subroutine write_s(this, lun, iotype, vlist, istat, imsg)

      ! argument definitions
      class(string_t), intent(in)     :: this
      integer, intent(in)             :: lun
      character(len=*), intent(in)    :: iotype
      integer, intent(in)             :: vlist(:)
      integer, intent(out)            :: istat
      character(len=*), intent(inout) :: imsg

      ! local variable
      character(len=MAXLENS) :: sfmt

      sfmt = "(A)"
      if ( (iotype == "DT").and.(size(vlist) >= 1) ) then

         ! vlist(1) to be used as the field width of the character component.
         write(sfmt,"(A,I2,A)", iostat=istat, iomsg=imsg ) "(A", vlist(1), ")"
         if (istat /= 0) return

      end if

      write(lun, fmt=sfmt, iostat=istat, iomsg=imsg) this%m_s

      return

   end subroutine write_s

end module string_m
program p

   use string_m, only : string_t

   implicit none

   type(string_t) :: word1
   type(string_t) :: word2
   character(len=:), allocatable :: msg
   integer :: istat
   character(len=256) :: imsg

   msg = "Hello World!"
   read( msg, "(*(DT(6)))", iostat=istat, iomsg=imsg ) word1, word2
   if ( istat /= 0 ) then
      print *, "read statement failed: iostat = ", istat
      print *, trim(imsg)
      stop
   end if

   print *,  word1, word2

   stop

end program p
C:\..>ifort /c /standard-semantics /stand /warn:all m.f90
Intel(R) Visual Fortran Intel(R) 64 Compiler for applications running on Intel(R
) 64, Version 17.0.0.109 Build 20160721
Copyright (C) 1985-2016 Intel Corporation.  All rights reserved.


C:\..>ifort /c /standard-semantics /stand /warn:all p.f90
Intel(R) Visual Fortran Intel(R) 64 Compiler for applications running on Intel(R
) 64, Version 17.0.0.109 Build 20160721
Copyright (C) 1985-2016 Intel Corporation.  All rights reserved.


C:\..>link /out:p.exe /subsystem:console p.obj m.obj
Microsoft (R) Incremental Linker Version 12.00.40629.0
Copyright (C) Microsoft Corporation.  All rights reserved.


C:\..>p.exe
 read statement failed: iostat =  -1
 end-of-file during read, unit -5, file Internal Formatted Read

C:\..>

 

0 Kudos
4 Replies
Steven_L_Intel1
Employee
459 Views

Thanks - escalated as issue DPD200414909. If instead of the group repeat you use "(DT(6),DT(6))" it will work in 17.0.1 (but not 17.0.0.) What I find is that your UDIO routine is called only once instead of twice.

0 Kudos
FortranFan
Honored Contributor II
459 Views

Steve Lionel (Intel) wrote:

Thanks - escalated as issue DPD200414909. If instead of the group repeat you use "(DT(6),DT(6))" it will work in 17.0.1 (but not 17.0.0.) What I find is that your UDIO routine is called only once instead of twice.

Steve,

Thanks for your follow-up.

You indicate, "'(DT(6),DT(6))' it will work in 17.0.1 (but not 17.0.0.)" but then it does work for me with 17.0.0.109 version!  What I intended to state in the original post, but I now see I forgot to do so, is that '(2(DT(6)))' repeat specification also results in the end-of-file message.

Also, interestingly perhaps, if the code is changed to use an implied do-loop, it works:

program p

   use string_m, only : string_t

   implicit none

   type(string_t), allocatable :: words(:)
   character(len=:), allocatable :: msg
   character(len=256) :: imsg
   integer :: istat
   integer :: i
   
   allocate( words(2) )

   msg = "Hello World!"
   read( msg, "(*(DT(6)))", iostat=istat, iomsg=imsg ) ( words(i), i=1, size(words) )
   if ( istat /= 0 ) then
      print *, "read statement failed: iostat = ", istat
      print *, trim(imsg)
      stop
   end if

   print *, ( words(i), i=1, size(words) )

   stop

end program p

 

0 Kudos
Steven_L_Intel1
Employee
459 Views

I think you'll find it doesn't work consistently in 17.0.0. We have a bug where the vlist isn't passed properly for a second and subsequent DT, passing an unpredictable value instead.

0 Kudos
Steven_L_Intel1
Employee
459 Views

This bug has been fixed in our sources. I expect the fix to appear in Update 2 to Parallel Studio XE 2017.

0 Kudos
Reply