Connecting a file to different units for simultaneous input and output

Modern Fortran Explained: Incorporating Fortran 2018 says on p278

A file already connected to one unit must not be specified for connection to another unit.

The Fortran 2018 standard merely says in section 12.5.4 that the results of doing so are compiler-dependent:

It is processor dependent whether a file can be connected to more than one unit at the same time.

If input/output operations are performed on more than one unit while they are connected to the same external the results are processor dependent.

Below is a code that simultaneously opens a file for reading and writing. The results by compiler are listed in the comments. Gfortran and ifort both allow a file to be read in one unit as it is written in another. Gfortran requires a FLUSH statement for this to work, but ifort does not. Flang and g95 give an error message when a file is connected to more than one unit. I think all of the compilers are standard-conforming.

program flush_file
implicit none
integer :: i,iter
integer, parameter :: n = 10**3, inu = 10, outu = 11
character (len=*), parameter :: data_file = "random.txt"
real, allocatable :: x(:),y(:)
logical :: flushed
allocate (x(n),y(n))
call random_number(x)
print "(6a15)","flushed","minval(x)","maxval(x)","sum(abs(x-y))"
do iter=1,2
   flushed = iter == 1
   open (unit=outu,file=data_file,action="write")
   open (unit=inu,file=data_file,action="read",status="old")
   do i=1,n ! write and read data from same file
      write (outu,*) x(i)
      if (flushed) flush(outu)
      read (inu,*) y(i)
   end do
   print "(l15,5f15.4)",flushed,minval(x),maxval(x),sum(abs(x-y))
   close (outu)
   close (inu)
end do
end program flush_file
! sample ifort output:
!         flushed      minval(x)      maxval(x)  sum(abs(x-y))
!               T         0.0000         0.9957         0.0000
!               F         0.0000         0.9957         0.0000
! sample gfortran output:
!         flushed      minval(x)      maxval(x)  sum(abs(x-y))
!               T         0.0005         0.9993         0.0000
! At line 18 of file flush.f90 (unit = 10, file = 'random.txt')
! Fortran runtime error: End of file
! flang output:
!         flushed      minval(x)      maxval(x)  sum(abs(x-y))
! FIO-F-207/OPEN/unit=10/file is already connected to another unit.
!  File name = random.txt
!  In source file flush.f90, at line number 14
! g95 output: same as flang

Depending on the compilers that you use, maybe it’s ok to connect a file to different units for both input and output?

Reading and writing to the same file at the “same” time is a bit tricky, but how about reading from the file vai two different units? If you want different pieces of information from the same file, it may be useful to have it opened at several units, so that the two tasks can proceed without interfering with each other.

MFE uses prohibitive clause but it makes sense, if the Standard says it is processor-dependent, both the very possibility of doing that and the results. (BTW, in my copy it is page 273).

The preceding paragraph in MFE discusses the open statement operation when the unit used by open is already connected to a file. The rules are somewhat complicated but there is one that I really do not understand.

If the file in question does not exist, but is preconnected to the unit…

It is actually a quote from the Standard, 12.5.6.1.3. How can such a situation possibly happen?

Units that are preconnected include standard input, output and error. They need not be connected to a “physical” file. You do not quote much context, so I presume this is what is meant.

So that would mean reopening stdout etc. and connecting it to a regular file, thus making ‘redirection’ from within the program. Thanks, @Arjen.

Each compiler specifies which units are preconnected. For the NAG compiler, all units (apart from the 3 special ones in ISO_FORTRAN_ENV) are preconnected to files called fort.N (where N is the decimal representation of the unit number). This behaviour is also seen in GNU and Intel compilers.


WRITE(17,'("Hello 17")')
END

will result in a file fort.17 with the contents “Hello 17”.

So you can actually ask for those names via INQUIRE? Or is that the privilege of OPENed files? (I was unaware that it works that way :slight_smile: )

It seems to work for NAG, GNU, Intel.

On some systems you can preassign files external to Fortran. Such commands as assign allowed/allow for preconnecting units, defining their residency (if you used a particular part of a scratch file heavily you could assign part of it to memory, other parts to disk, and assign additional options to the file like compression (handy for large files);
the standard says very little about what a file is and what preassignment is. Some compilers allow you to assign names, usually via environment variables to names that are connected to instead of something like “fort.NNNN” or “ftn.NNNN” that last I tried showed as preconnected on INQUIRE; but it has been a while.

Once a de-facto part of Fortran that never made it into the standard was preassignment via the PROGRAM directive …

PROGRAM(filea=fort10,…)

I don’t think any compilers do that anymore(?)