Trimming a file and advance='no'

I want to trim a text file to a given number of lines. To this end I use a readline routine (pretty much like the getline_char in stdlib) and endfile to cut off remaining lines. See code and test.dat file below.
This works as expected in ifort and ifx, but not with gfortran. Somehow the endfile marker is written after the fifth line. Writing an empty line and doing a rewind (to remove this empty line) before the endfile statement fixes the problem with gfortran. This is strange and looks like a bug?
(BTW: the endfile is still necessary, as the backspace leaves an empty line. Looks like endfile removes the newline (=end-of-record) marker to signal end of file).

Trying to understand the advance=‘no’ statement, I could not find any hint of why advance=‘no’ advances the position to the next record if the record has been completely read, including the newline (which is dropped, though). Obviously, when the readline routine reads the last (possibly empty) portion of the line in the loop, it signals an eor and advances to the next record. Why does it advance at all? I could not find any hint to that in the standard.

module mod_rl

   implicit none
   private

   public readline

   contains

   subroutine readline(line, end_of_file, funit)
      character(len=:), allocatable, intent(out) :: line
      logical, intent(out) :: end_of_file
      integer, intent(in) :: funit

      integer :: sizeBuf, stat
      logical :: end_of_record
      character(len=4) :: buffer

      line = ''
      end_of_file = .false.
      end_of_record = .false.
      stat = 0
      do while (stat == 0)
         read(funit, '(a)', advance='no', iostat=stat, size=sizeBuf) buffer
         end_of_file = is_iostat_end(stat)
         end_of_record = is_iostat_eor(stat)

         if (.not. end_of_file) then
            if (sizeBuf > 0) then
               line = line // buffer(1:sizeBuf)
            end if
         end if
      end do
   end subroutine readline

end module mod_rl


program rw_advance

   use mod_rl
   implicit none

   integer :: funit, i
   character(len=:), allocatable :: line
   logical :: end_of_file

   open(newunit=funit, &
         file='test.dat', &
         access='sequential', &
         action='readwrite', &
         status='old', &
         form='formatted', &
         position='rewind')

   ! reads the whole file as expected
!   end_of_file = .false.
!   do while (.not. end_of_file)
!      call readline(line, end_of_file, funit)
!      write(*,'(a)') 'line: "'//line//'"'
!   end do

   ! trimming to 4 lines and appending a new line
   do i = 1,4
      call readline(line, end_of_file, funit)
   end do

   ! fixes gfortran, unnecessary with ifort
!   write(funit,'(a)') ''
!   backspace(funit)

   endfile(unit=funit)
   close(funit)

   open(newunit=funit, &
         file='test.dat', &
         access='sequential', &
         action='readwrite', &
         status='old', &
         form='formatted', &
         position='append')
   write(funit,'(a)') 'something new at line 5'
   close(funit)

end program rw_advance

test.dat:

line number 1
line number 22
line number 333
line number 4444
line number 55555
line number 666666
line number 7777777
line number 88888888
line number 999999999

In “Modern Fortran Explained” (F2018 edition) one can read p.239 (10.11 Non-advancing I/O):

A non-advancing I/O statement leaves the file positioned within the record, except if it attempts to read data from beyond the end of the current record, an end-of-record condition occurs and the file is repositioned to follow the record.

Not sure what it precisely implies, though.

Thanks for looking it up. I just found the section in the standard (final draft 08), which specifies this behavious. It is 9.3.4.4. (4)

  1. For nonadvancing input, if no error condition or end-of-file condition occurred, but an end-of-record condition (9.11) occurred, the file is positioned after the record just read. If no error condition, end-of-file condition, or end-of-record condition occurred in a nonadvancing input statement, the file position is not changed. If no error condition occurred in a nonadvancing output statement, the file position is not changed.

This implies that the read statements in the read routine exactly behave like they should. However, the endfile statement after the non-advancing read does not look to behave properly for gfortran. There is C.6.2(4) (final draft 08), which says:

(4) If the next I/O operation on a file after a nonadvancing write is a rewind, backspace, end file or close operation, the file is positioned implicitly after the current record before an ENDFILE record is written to the file, that is, a REWIND, BACKSPACE, or ENDFILE statement following a nonadvancing WRITE statement causes the fileto be positioned at the end of the current output record before the endfile record is written to the file.

But this explicitly refers to a WRITE, not a READ. It looks like gfortran jumps to the end of current record (before executing endfile) as if the previous statement has been a nonadvancing write, where in fact it was a nonadvancing read (which however, did advance due to the eor condition).

Note that gfortran 14 behaves like ifx.

Thanks for checking out. Indeed, this has recently been fixed: bug with endfile

I still use gfortran-13 as 14 has a fatal regression.

BTW: the discussion in the bug tracker shows that this was not even a bug, but due to different interpretations of the standard…

PS: and for some reason, despite a search, I somehow missed this one: clarification on expected behavior of endfile