Topic: Error in OPEN FILE Statement - Bug or user error

Hi All,

I am trying to pass filename as string variable in OPEN FILE statement as follows:

      Program TestFileIOPgm
         
      IMPLICIT NONE
     
      CHARACTER*12 :: DATE, TIME
      CHARACTER*10 :: OMSDATE, OMSTIME
      CHARACTER (LEN=256) :: FILENAMEPATH
     
      INTEGER :: DBGLUN,TESTDATA, IDFILE
      CHARACTER(LEN=60) ::   FILEPATH
      CHARACTER*20 :: TESTDATANAME
      CHARACTER(LEN=20) :: FLNAME
     
     
      TESTDATA=15
      DBGLUN=25

C         
      FILEPATH='G:\oms-Development\Version-VB6\Interfaces\omsLPIntf\'
      FILEPATH=TRIM(FILEPATH)
     
      FILENAMEPATH=REPEAT(' ',256)
     
      OPEN (UNIT=TESTDATA,
     1FILE='G:\oms-Development\Version-VB6\Interfaces\omsLPIntf\'
     2// 'Input\' // 'TESTCASES.DAT', STATUS='OLD',ACCESS='SEQUENTIAL',
     3 FORM='FORMATTED')
     
         
C     OPEN (UNIT=TESTDATA,
C    1FILE=FILEPATH// 'Input\TESTCASES.DAT', STATUS='OLD',
C    2 ACCESS='SEQUENTIAL', FORM='FORMATTED')
     
      OPEN (UNIT=DBGLUN,
     1FILE='G:\oms-Development\Version-VB6\Interfaces\omsLPIntf\'
     2// 'Debug\' // 'DEBUG-TEST.DAT' , STATUS='REPLACE')
     
     
      DO 8000 IDFILE = 1, 100
         
          READ (TESTDATA,8001) TESTDATANAME
          WRITE(*,*) TESTDATANAME
8001     FORMAT(A20)

          FLNAME=TRIM(TESTDATANAME)
          FILENAMEPATH='G:\oms-Development\Version-VB6\Interfaces\'
     1    // 'omsLPIntf\' // 'Input\' // FLNAME
         
       
          IF (FLNAME .EQ. '') GO TO 8002
     
      CALL DATE_AND_TIME(DATE,TIME)
     
      OMSDATE = DATE(1:4) // "/" // DATE(5:6) // "/" // DATE(7:8)
      OMSTIME = TIME(1:2) // ":" // TIME(3:4) // ":" // TIME(5:6)
     

      WRITE (DBGLUN,50) FILEPATH,FLNAME,DATE(1:8),TIME(1:6)
     
8002  CONTINUE

8000  CONTINUE

      CLOSE(TESTDATA)
      CLOSE(DBGLUN)

*
*---- FORMAT STATTEMENTS
*
   50 FORMAT(2x,'Input Data File Opened Successfully ', A60,2X, A20,2X,
     1 " AT DATE/TIME  ", A8,2X,A6)

      END PROGRAM TestFileIOPgm
     
The above code when the filepath is hradcoded but if pass the variable as 

 
  OPEN (UNIT=TESTDATA,
1FILE=FILEPATH// 'Input\TESTCASES.DAT', STATUS='OLD',
2 ACCESS='SEQUENTIAL', FORM='FORMATTED')

I get this error

  At line 32 of file .\TestFileIOPgm.FOR (unit = 15, file = '° ')
Fortran runtime error: File 'G:\oms-Development\Version-VB6\Interfaces\omsLPIntf\        Input\TESTCASES.DAT' does not exist

It does not pickup the FullFileName in the file=?

What am I missing here.  New user at learning f90 and had worked with Visual fortran with no problem.  Please guide me.  Would appreciate it.

Suresh Agrawal
s.agrawal@earthlink.net

2 (edited by davidb 2015-04-22 20:28:53)

Re: Error in OPEN FILE Statement - Bug or user error

It is difficult to see what you are trying to do.

The line  FILEPATH=TRIM(FILEPATH) does not strip out trailing blanks. This is because when the assignment is done, the compiler adds trailing blanks up to the dimension size, so you get back to where you started. Similarly there is no need to use repeat to get a string of blanks, just use  FILENAMEPATH=' '.

So the following doesn't work as there are blanks in the file name

  FILEPATH=TRIM(FILEPATH)
  OPEN (UNIT=TESTDATA,
1FILE=FILEPATH// 'Input\TESTCASES.DAT', STATUS='OLD',
2 ACCESS='SEQUENTIAL', FORM='FORMATTED')

Instead, try the following with TRIM included in the open statement.

  OPEN (UNIT=TESTDATA,
1FILE=TRIM(FILEPATH)// 'Input\TESTCASES.DAT', STATUS='OLD',
2 ACCESS='SEQUENTIAL', FORM='FORMATTED')

--
David

Re: Error in OPEN FILE Statement - Bug or user error

Thanks David,

That worked.  However, I have another second step problem.  I conect and open the datafile in main program and
pass the FORTRAN File Unit parameter via subroutine DLL argument and tried to read the file in the subroutine and it gives end file error like

COASTAL1.DAT       
TestGEDataDll Main Program           1 G:\oms-Development\Version-VB6\Interfaces\omsLPIntf\Input\COASTAL1.DAT                                                                                                                                                                                         
Entering GEDATA DLL          20          25          30           1 G:\oms-Development\Version-VB6\Interfaces\omsLPIntf\Input\COASTAL1.DAT                             
At line 89 of file .\GEDATA.For (unit = 20, file = 'fort.20')
Fortran runtime error: End of file

Does it mean I can not just pass the unit no in DLL but must pass the file name and connect in subroutine DLL and not connect in main progarm.

Suresh Agrawal
s.agrawal@earthlink.net

Re: Error in OPEN FILE Statement - Bug or user error

Your main program and your DLL have separate run-time environments. You cannot therefore pass the unit number. It won't work unfortunately.

You can pass the file name and use open in the DLL but the usual rule is to read your files in the main program and pass the values to the DLL.

--
David

Re: Error in OPEN FILE Statement - Bug or user error

Thanks Davidb, It makes sense.  I modified DLL to open the file in DLL (program logic requires that). However I get compilation error for DLL subroutine as follows in the open statement as follows:

Generating Makefile... Okay
==============================================================================
Compiling .\GEDATA.For
.\GEDATA.For:71.28:

      FULLFILENAMEPATH=TRIM(FULLFILENAMEPATH)                           
                            1
Error: 'string' argument of 'trim' intrinsic at (1) must be a scalar
.\GEDATA.For:83.31:

        OPEN (UNIT=OFFLUN,FILE=FULLFILENAMEPATH, STATUS='OLD')         
                               1
Error: FILE tag at (1) must be scalar
.\GEDATA.For:213.29:

      OPEN (UNIT=DATPRT,FILE=FULLFILENAMEPATH, STATUS='REPLACE')       
                             1
Error: FILE tag at (1) must be scalar
Error(E42): Last command making (build\GEDATA.o) returned a bad status
Error(E02): Make execution terminated

* Failed *

I am passing the filename and declaring as follows:

      SUBROUTINE  GEDATA ( OFFLUN, DBGLUN, DATPRT, FULLFILENAMEPATH,
     1IRDWR,  NRMAX, NCMAX,  NROWS,  NCOLS,
     2STRROWNAM, STRCOLNAM, MATRIX, ROWRHS,
     3LOWBND, UPPBND, OBJCOF, PSBASE, SOLN ) bind(c)

..
CHARACTER*1, DIMENSION(100) :: FULLFILENAMEPATH

OPEN (UNIT=OFFLUN,FILE=FULLFILENAMEPATH, STATUS='OLD')

I would appreciate any feedback as to why am I getting this error.
C

Suresh Agrawal
s.agrawal@earthlink.net

Re: Error in OPEN FILE Statement - Bug or user error

Suresh,

The problem you're seeing is because your strings are arrays of characters:

CHARACTER*1, DIMENSION(100) :: FULLFILENAMEPATH

and the OPEN statement actually expects a Fortran string, something like:

CHARACTER(100) ::  FULLPATHSTR

The reason you're seeing this incompatibility issue is because you're interfacing via a DLL using the ISO_C_BINDING features.  The C language only defines strings as arrays of characters.  Therefore, if receiving a string from C, it will be an array.  To use this array as a string in Fortran, it would have to be converted using some custom functions.  Some example functions are defined here:

PURE FUNCTION Copy_a2s(a)  RESULT (s)    ! copy char array to string
    CHARACTER,INTENT(IN) :: a(:)
    CHARACTER(SIZE(a)) :: s
    INTEGER :: i
    DO i = 1,SIZE(a)
       s(i:i) = a(i)
    END DO
END FUNCTION Copy_a2s

There would be an equivalent operation for copying the string (in Fortran) back to C, although, thanks to how Fortran stores strings, you normally don't have to actually perform this operation.

Moving string back and forth via a DLL can be a pain because Fortran simply handles strings differently than C.

Jeff Armstrong
Approximatrix, LLC

Re: Error in OPEN FILE Statement - Bug or user error

Thanks Jeff, It worked.  Moving ahead inch by inch with your help and others in this forum.  Thanks again.  Next I will be doing to interface this DLL in Excel VBA (my ultimate goal)

Suresh Agrawal
s.agrawal@earthlink.net