Error 'file does not exist' when using OPEN

Hello everyone:

Today I encountered a problem.

First of all, I have two files, File1.dat includes the name of another file File2.dat.

Content of File1.dat:
./File2.dat

I use a character variable to read the file name in File1.dat such as:

CHARACTER(LEN=1024) :: filename

OPEN( UNIT = 100 , FILE = ‘File1.dat’ , STATUS = ‘OLD’ )
READ(100,‘(A1024)’) filename
CLOSE(100)

And then I want to use filename to open the second file:

OPEN ( UNIT = 101 , FILE = TRIM(filename) , STATUS=‘OLD’ )

But I got an error:

FIO-F-209/OPEN/unit=101/‘OLD’ specified for file which does not exist.
File name = ./File2.dat
In source file main.f90, at line number 855

The same main.f90 can execute correctly if I use intel fortran compiler on my PC.

But the cluster only provide PGI compiler.

Did any one have the same problem?

Thanks in advance.

Hi Rex K-S Liu,

Does the file exist in the local directory? If so can you please post a reproducing example of the failing code and more information about the system (i.e are you using Linux? x86? Power?) and the compiler version?

I tried to write a reproducer, but I’m not able to recreate the error.

% cat test.F90

program  foo

CHARACTER(LEN=1024) :: filename
integer :: val
OPEN( UNIT = 100 , FILE = 'File1.dat' , STATUS = 'OLD' )
READ(100,'(A1024)') filename
CLOSE(100)

OPEN ( UNIT = 101 , FILE = TRIM(filename) , STATUS='OLD' )
READ(101,'(I)') val
close(101)

print *, val

end program foo
% pgfortran -fast -V18.4 test.F90
% cat File1.dat
./File2.dat
% cat File2.dat
100
% a.out
          100

-Mat

Hi Mat

Thanks for your reply.
As you did, I test a smaller program and it worked well.
But my original program is large.
The following is the essential part which produced the problem.
Also, contents of the file input.dat are shown below.

My PC:
OS : CentOS Linux release 7.5.1804
PGI version : PGI 17.10 community

Thanks for your help!!

MODULE DoublePrecision
  IMPLICIT NONE
  
  INTEGER,PARAMETER :: DP = SELECTED_REAL_KIND( P=15 )
  
END MODULE DoublePrecision
!=============================================================================================
!=============================================================================================
MODULE fileIndex
  IMPLICIT NONE
  
  INTEGER,PARAMETER :: IO1 = 101 ! input.dat
  INTEGER,PARAMETER :: IO2 = 102 ! body file
  
END MODULE fileIndex
!=============================================================================================
!=============================================================================================
MODULE IBMPar
  USE DoublePrecision
  IMPLICIT NONE

  ! nBody : number of bodies
  INTEGER :: nBody

  ! BodyPar : variable type of a body
  TYPE BodyPar
    ! fileName : file name of the body data
    CHARACTER(LEN=1024) :: fileName

    ! disX, disY : displacement vector of the original body
    REAL(KIND=DP)       :: disX, disY

    ! nMesh : number of grids of the body
    INTEGER :: nGrid

    ! xG, yG : coordinates of the body grids
    REAL(KIND=DP),DIMENSION(:),ALLOCATABLE :: xG, yG
  END TYPE BodyPar

  TYPE(BodyPar),DIMENSION(:),ALLOCATABLE :: IBBody

END MODULE IBMPar
!=============================================================================================
!=============================================================================================
PROGRAM MAIN
  IMPLICIT NONE
  
  ! fileIn =========================================================================
  CALL fileIn()
  
END PROGRAM MAIN
!=============================================================================================
!=============================================================================================
SUBROUTINE fileIn()
  USE fileIndex
  USE IBMPar
  IMPLICIT NONE
  
  ! local variable =================================================================
  INTEGER :: i, j
  
  ! open input.dat =================================================================
  OPEN( UNIT = IO1 , FILE = 'input.dat' , STATUS = 'OLD' )

  READ(IO1,*) nBody
  
  ALLOCATE( IBBody(nBody) )

  DO i = 1 , nBody
    READ(IO1,'(A1024)') IBBody(i)%fileName
    READ(IO1,*) IBBody(i)%disX, IBBody(i)%disY
  ENDDO
  CLOSE(IO1)
  
  ! read body files ================================================================
  CALL IBM_BodyIn()
  
  RETURN
END SUBROUTINE fileIn
!=============================================================================================
!=============================================================================================
SUBROUTINE IBM_BodyIn()
  USE fileIndex
  USE IBMPar
  IMPLICIT NONE
  
  ! local variables =====================================================================
  INTEGER :: i, j
  
  DO i = 1 , nBody

    OPEN( UNIT = IO2 , FILE = TRIM(IBBody(i)%fileName) , STATUS = 'OLD' )

    READ(IO2,*) IBBody(i)%nGrid

    ALLOCATE( IBBody(i)%xG(IBBody(i)%nGrid) , IBBody(i)%yG(IBBody(i)%nGrid) )

    DO j = 1 , IBBody(i)%nGrid
      READ(IO2,*) IBBody(i)%xG(j) , IBBody(i)%yG(j)
    ENDDO

    IBBody(i)%xG = IBBody(i)%xG + IBBody(i)%disX
    IBBody(i)%yG = IBBody(i)%yG + IBBody(i)%disY

    CLOSE(IO2)

  ENDDO
  
  RETURN
END SUBROUTINE IBM_BodyIn



4     nBody  number of geometry files
./SCCS/text1.dat
5.0  6.5
./SCCS/text2.dat
7.0  6.5
./SCCS/text3.dat
9.0  6.5
./SCCS/text4.dat
11.0  6.5

One way this could happen is if “input1.txt” was created on a Window’s system in which case the text file uses different characters for newlines.

For example, if I use Notepad on Windows to create “File1.dat”, I can recreate your error using my little test program:

% a.out
FIO-F-209/OPEN/unit=101/'OLD' specified for file which does not exist.
 File name = ./SCCS/File2.dat
 In source file test.F90, at line number 10

Running the “dos2unix” utility on the file to convert the newline characters to UNIX style, fixes the issue:

% a.out
FIO-F-209/OPEN/unit=101/'OLD' specified for file which does not exist.
 File name = ./SCCS/File2.dat
 In source file test.F90, at line number 10
% dos2unix File1a.dat
dos2unix: converting file File1a.dat to Unix format ...
% a.out
          100

How was your “input1.txt” file created? Could something similar be happening here?

-Mat

Hi Mat

Yes my *.dat files were created in Windows PC.
And the command dos2unix works well.

Thanks for your help!!

Rex