Direct access file "Non-existing record number"

Hi I am stuck with this error

DO K = 1,KB
             READ (20,REC=(ICOUNTF-1)*KB+K) SCLIM2(K)
             READ (15,REC=(ICOUNTF-1)*KB+K) TCLIM2(K)
         END DO

here’s the open file

inquire(IOLENGTH=rlength) SCLIM1(1)
     open(20, file=Sal_input, form='unformatted', access='direct', recl=rlength)
     write(6,*) 'open 20 done'

and the file is 31x8 temperature values

I don’t have an idea why this problem is recurring

WIthout a working minimal example there are several possibilities. One is that you have not opened the file properly. Perhaps the filename is incorrect and you are opening a new empty file. If the file is supposed to always exist you can specify STATUS=‘OLD’ to ensure the file exists. Another possiblity is you have specified a different RECL than was used to create the file, so the program does not see the correct number of “records”. The third possibility is you have not specified a correct value for the record number. You show unit 20 being opened, but not unit 15, but you are reading from both with no indication of which READ is causing the error; so perhaps the error is occuring on unit 15 instead of 20. Printing the value
of KB, ICOUNTF and/or (ICOUNTF-1)*KB+K will most likely show you are asking for a record number that does not exist in the file. You can use INQUIRE to get the size and record length of the file after the OPEN to validate how many records are in the file to check that you are opening the file successfully and seeing the number of records you expect.

An actual minimal program reproducing the problem would be preferable, or perhaps the actual code itself; but the combination of an INQUIRE of the file and printing the record numbers being calculated will likely show you the cause of the error.

Without seeing the whole code, including declarations, it is just guesswork to determine what might be wrong. The possible problem with units 15 and 20 was already mentioned. Another one is that you inquire the record length using the variable SCLIM1, but then the actual i/o statements use variables SCLIM2 and TCLIM2. Without seeing the declarations of those arrays (real, character, integer, derived type, etc.), it is possible that there is a mismatch of those record lengths. Presumably the records are ordered from 1 to 31, so it is unclear why the complicated expression REC=(ICOUNTF-1)*KB+K is used for the record counter.

What do the iostat and iomsg clauses give you?

Hi All, this is the code of the error file

! !ROUTINE: get_init_TS_IC
!
! !INTERFACE
!
     subroutine get_init_TS_IC
!
!DESCRIPTION
!
! This subroutine opens and reads files containing the T&S initial conditions
! Files are read in direct access mode
! The path to the T&S I.C. file specified in namelist pom_input.
!
!***********************************************************************************
!
!     -----MODULES (USE OF ONLY IS STRONGLY ENCOURAGED)-----
!
      use global_mem, ONLY: error_msg_prn, NML_OPEN, NML_READ
!
      use CPL_VARIABLES, ONLY: Sprofile_input, &
                         Tprofile_input
!    
      use pom, ONLY: KB,T,TB,S,SB
!
!     -----IMPLICIT TYPING IS NEVER ALLOWED-----
!
      IMPLICIT NONE
!
!     -----RECORD LENGTH----
!
!     DATA TO BE READ ARE WRITTEN WITH A F12.5 FORMAT
!     THE  CORRESPONDING RECORD LENGTH IS 12
!
      Integer,Parameter :: recolen=12
!
!     -----LOOP COUNTER-----
!
      INTEGER :: K
!
!      -----RECORD LENGTH-----
!
      INTEGER :: RLENGTH
!
!     -----NAMELIST READING UNIT-----
!
      integer,parameter  :: namlst=10
!
!    -----OPEN FILE WITH SALINITY I.C.----
!
       inquire(IOLENGTH=rlength) SB(1)
       open(29,file=Sprofile_input,form='formatted',access='direct',recl=rlength)
!
!
!    -----OPEN FILE WITH TEMPERATURE I.C.----
!
!
       inquire(IOLENGTH=rlength) TB(1)
       open(10,file=Tprofile_input,form='formatted',access='direct',recl=rlength)
!
!
!    -----READ T&S INITIAL CONDITIONS-----
!
     DO K = 1,KB
!
           READ (29,'(F12.5)',REC=K) SB(K)
           READ (10,'(F12.5)',REC=K) TB(K)
!
     END DO
!
!    -----COLD START: T@(t)=T@(t-dt)-----
!
     T(:)=TB(:)
     S(:)=SB(:)
!
     return
!
!    -----PRINT IF PROBLEMS WITH NML OPENING-----
!
100   call error_msg_prn(NML_OPEN,"get_init_TS_IC.F90","problem opening pom_bfm_settings.nml")
!
!    -----PRINT IF PROBLEMS WITH NML READING-----
!
102   call error_msg_prn(NML_READ,"get_init_TS_IC.F90","pom_input in pom_bfm_settings.nml")
!
      end subroutine get_init_TS_IC

I think I see the problem now. In your original post, you were using unformatted direct access i/o. In the actual code, the records are formatted, but you are using the record length (from the inquire statement) that would be appropriate for unformatted i/o. If you know that the record lengths are 12, then just use that in the open statement, not the value from the inquire statement.

I must admit that I do not often use formatted direct access, so I’m unsure of exactly how line feed characters are handled in this situation (i.e. are they ignored, or included in the record length, or nonexistent in the first place). This might be an issue if the input files are written with a shell script or a C program and not with fortran direct access.

Indeed, it looks to me like you could just read the two arrays each with a single sequential read statement, and skip the do loop entirely. You are reading the elements in sequential order, a single time, so all the functionality of direct access is unused anyway.