Silverfrost Forums

Welcome to our forums

Puzzling error reports for short correct program

24 Feb 2024 5:53 #31145

The short program below was constructed to display a problem that I had with building and running the Hydrotherm program ( https://volcanoes.usgs.gov/software/hydrotherm/ ) with FTN95, 32 or 64 bit.

The problem concerns a section of code that takes an input text file, strips out lines beginning with '#' (in col. 1), and displays the lines that remain.

program rcomment
  !     Purpose:  Reads the input file,
  !        strips out the comment lines (# in col. 1), and
  !        displays the remaining lines
  IMPLICIT NONE
  integer, parameter :: fuinc=11!, fuins=12
  CHARACTER(10) :: buffer
  CHARACTER(len=:), ALLOCATABLE :: aline
  INTEGER :: record_length
  INTEGER :: string_size, lno
  !     ------------------------------------------------------------------------
  !
  open(fuinc,file='dat.in' , form='formatted', status='old')
  lno=0
  DO
    ! Determine the length of a record (a line of the input data file) by
    ! reading 10 characters at a time (without advancing to next record)
    ! until end of record (EOR) is reached.
    record_length = 0
    DO
      READ (fuinc, '(a)', ADVANCE='NO', SIZE=string_size, EOR=10,   &
            END=20) buffer ! read is done only to find line size, buffer discarded
      record_length = record_length + 10
    END DO
    10 record_length = record_length + string_size
! If the record is not empty, allocate a character string and reread
! the record into the character string.
    IF (record_length > 0) THEN
      ALLOCATE (CHARACTER(LEN=record_length) :: aline)
      BACKSPACE (fuinc)
      READ (fuinc, '(a)') aline
      ! If the line is not a comment line, write it to the temporary
      ! input file
      lno=lno+1
      IF (aline(1:1) /= '#') THEN
        print 100,lno,record_length,aline
 100 format(2i4,'  |',A,'|')
      END IF
      DEALLOCATE (aline)
    END IF
  END DO
  20 close(fuinc)
END program

The input data file, 'dat.in':

# ..  VER3.2:  title line 2
TITLE  One-Cell Problem - Constant-Enthalpy Injection
VER3.2
# DIMENSIONS
# ..  nx[I],ny[I],nz[I],tmstr,iyear[I]
1,     1,    1,      0.0,      1
# TIME STEP

The expected output (correctly delivered by Gfortran, etc.):

   2  53  |TITLE  One-Cell Problem - Constant-Enthalpy Injection|
   3   6  |VER3.2|
   6  32  |1,     1,    1,      0.0,      1|

With /check, the FTN95-compiled EXE reports ' RCOMMENT - Error 69, Invalid record length in file stripcmt.f90 at line 31 [+0298]'. With /check /64, the error message is similar.

I recognise that the method used by the original authors in the large code- read an input line in chunks of 10 characters with ADVANCE='NO' until EOL to find the length of the input line, allocate a character variable of just the right length, then BACKSPACE and reread the same line into the newly allocated variable -- can be replaced by something more efficient as well as simple, but that is not the point of this post.

26 Feb 2024 8:36 #31148

mecej4

Thank you for the feedback. At first sight it looks like BACKSPACE for FTN95 is not working in the same way as BACKSPACE for gFortran in this context.

At the moment I don't know what the Standard has to say about this but I will make a note that this needs investigating.

5 Mar 2025 3:25 #31973

A preliminary investigation reveals that there are two issues to fix here.

  1. The field width of aline is not passed correctly when aline is ALLOCATEd. A temporary work-around is to avoid ALLOCATE in this context.

  2. READ(END=20) is not working when the final line of the data file is not terminated with a carriage return.

11 Mar 2025 12:20 #31989

Both of these issues have now been fixed for the next release of FTN95 and the DLLs.

Please login to reply.