Output to unopened file

This program writes to unit 42 which was not opened. Lfortran writes ‘foobar’ to output_unit. Every other compiler can use (gfortran, g95, ifort, ifx, AMD flang) writes ‘foobar’ to the external file fort.42.
None of the compilers gave an error message in spite of F2023 12.5.3 paragraph 2. The only way I can see for them to be standard-conforming is for their choice of output file to be preconnected (F2023 12.5.5). Of course an OPEN statement could override the preconnection. The program:

  write(42,"(A)") 'foobar'
end program

Should the majority decision be standardized?

It’s better for the programmer to connect files to units explicitly, and writing to unit 42 without having connected it would be a bug in my code. So I’d say “no”. Writing to fort.42 is quasi-standard, as you point out, but the standards committee should not endorse a poor coding practice and require compilers to support it.

I think it would preferable for LFortran to give a run-time error than write to standard output for your code.

This paragraph does not say that the compilers have to report this error. ifx does report it in debug mode if the -check option is present. gfortran doesn’t, even if -fcheck=all is present.

Writing to an unopened file has been a feature of all Fortran compilers .for more than 70 years and removing it would not be setting a good precedent. Removing it from one compiler is not going to make that compiler more attractive to users. some of whom use Fortran only for compiling legacy code and may not have any knowledge of Fortran.

Fortran contains hundreds of features that wouldn’t be in a language designed today - insignificant spaces, implicit typing, double precision (as a type), mutable function arguments and so on. Eliminate them all and very few existing programs would compile. Would it really attract a lot of new users?

Haven’t we all been angered by required dependencies that had both a minimum and a maximum version?

I promise not to comment further on this matter, but I didn’t want it thought that there was general accepance of this notion.

I often write to unopened files while debugging, and in one-off programs.

1 Like

I agree that compilers that have implemented the feature of writing to fort.n by default should not remove it and inconvenience users who rely on it, but I don’t think the standard should mandate this behavior.

There’s some misunderstanding here. 12.5.3 is about units, not files. For example, a processor might not support a unit number above 1000. What this thread is referring to is called preconnection in the standard (12.5.5). Most compilers preconnect all units to some file name (such as fort.42), but the file doesn’t come into existence until the unit is opened with OPEN or is referenced in an I/O statement such as READ or WRITE.

This behavior is absolutely standard-conforming and has been a part of Fortran since the very beginning (OPEN didn’t exist in the standard until F77.)

1 Like

It has bugged me that even with switches like -std=f2018 on many compilers including gfortran do not produce a warning about using a file that is not open.
It does remind me of when an OPEN statement was a rarity and all or almost all files were pre-assigned by the OS like the Cray Operating System (COS) ASSIGN command. I liked the CDC extension that let you rename the program files on the command line

  PROGRAM(INPUT,OUTPUT,TAPE5=INPUT,TAPE6=OUTPUT) 

But being able to automatically open a file with a system-dependent name (although “fort.NN” has become very popular) is now generally a bad idea and not standard-conformant it is very unlikely to go away; sort of like IMPLICIT NONE not being the default nowadays. I personally think it should be a warning, particularly when “enforce standard conformance” switches like -std=f2018 are used.

One of the oddest things lately is related

open(newunit=lun)

usually ends up creating a filename like “fort.-12”. I DO think it should be an error when usiing NEWUNIT as that is using a “new” feature that should not affect “legacy” source.

Files used to be able to be open external to a program execution and even retain their position between being operated on by different programs and contain multiple “files” so there might be more to read after hitting an end-of-file. Not much of that remains. I do not have access to one at the moment, but I think Crays still have an assign command that let you set up pre-assignments for Fortran units.

Why the PROGRAM directive does not allow definition of a NAMELIST group defining command arguments is beyond me. It would give Fortran the most convenient command line argument parsing of any language I can think of.

program foo(a,b,c)
real :: a,b,c 
write(*,nml=args)
end

with flavors of parsing like NAMELIST, CSV, UNIX_LIKE, DOS_LIKE available
would be nice.

foo A=10, B=20, C=30 # NAMELIST syntax; allows user-defined types, ...
foo 10,,30  # CSV format
foo -A 10 -B 20, -C 30  # Unix-like. Single letters are short, others are long, 
foo /A=10/C=30  # DOS-like

just by listing the identifiers in the PROGRAM statement would be so intuitive compared to all the non-standard solutions out there.

I had a ticket open about not getting a warning with several compilers a while back as well as some issues with INQUIRE. Trying it now with gfortran you get an error now with “open(newunit=unum)” which is good, and I only had to comment out PRESENT= on the INQUIRE and the only output that looked wrong was for EXIST when the file did not exist; which is a dramatic improvment. Usually testing INQUIRE generates at least one bug report with each compiler every time I drag out this test procedure.

program main
! gfortran -std=f2018 -Wall -Wextra -fPIC -fmax-errors=1 -g -fcheck=bounds -fcheck=array-temps -fbacktrace
use,intrinsic      ::  iso_fortran_env,  only  :  compiler_version
use,intrinsic      ::  iso_fortran_env,  only  :  compiler_options
integer            ::  iostat                     
integer            ::  tapen                     
integer,parameter  ::  lun=40                     

  print '(4a)', &
     'This file was compiled by ', compiler_version(), &
     ' using the options ',        compiler_options()

  call print_inquire(lun_in=LUN)
  write(40,*)'something new'
  call print_inquire(lun_in=LUN)
  !open(newunit=tapen)  ! Yeah. gfortran now generates an error
  tapen=44
  open(unit=tapen)
  call print_inquire(lun_in=tapen)
  !close(unit=LUN,status='delete',iostat=iostat)
  !close(unit=tapen,status='delete',iostat=iostat)

contains
subroutine print_inquire(lun_in,namein_in) 
integer,intent(in),optional             :: lun_in        
character(len=*),intent(in),optional    :: namein_in
integer                       :: iostat
character(len=256)            :: message
character(len=:),allocatable  :: namein
integer                       :: lun
character(len=20)             :: access         ; namelist/inquire/access
character(len=20)             :: asynchronous   ; namelist/inquire/asynchronous
character(len=20)             :: blank          ; namelist/inquire/blank
character(len=20)             :: decimal        ; namelist/inquire/decimal
character(len=20)             :: delim          ; namelist/inquire/delim
character(len=20)             :: direct         ; namelist/inquire/direct
character(len=20)             :: encoding       ; namelist/inquire/encoding
logical                       :: exist          ; namelist/inquire/exist
character(len=20)             :: form           ; namelist/inquire/form
character(len=20)             :: formatted      ; namelist/inquire/formatted
character(len=20)             :: unformatted    ; namelist/inquire/unformatted
integer                       :: id             ; namelist/inquire/id
character(len=20)             :: name           ; namelist/inquire/name
logical                       :: named          ; namelist/inquire/named
integer                       :: nextrec        ; namelist/inquire/nextrec
integer                       :: number         ; namelist/inquire/number
logical                       :: opened         ; namelist/inquire/opened
character(len=20)             :: pad            ; namelist/inquire/pad
logical                       :: pending        ; namelist/inquire/pending
integer                       :: pos            ; namelist/inquire/pos
character(len=20)             :: position       ; namelist/inquire/position
character(len=20)             :: action         ; namelist/inquire/action
character(len=20)             :: read           ; namelist/inquire/read
character(len=20)             :: readwrite      ; namelist/inquire/readwrite
character(len=20)             :: write          ; namelist/inquire/write
integer                       :: recl           ; namelist/inquire/recl
character(len=20)             :: round          ; namelist/inquire/round
character(len=20)             :: sequential     ; namelist/inquire/sequential
character(len=20)             :: sign           ; namelist/inquire/sign
integer                       :: size           ; namelist/inquire/size
character(len=20)             :: stream         ; namelist/inquire/stream
   if(present(namein_in))then
      namein=namein_in
   else
      namein=repeat(' ',1024)
   endif
   lun=merge(lun_in,-1,present(lun_in))
   name=''
   if(namein == ''.and.lun /= -1)then
         write(*,*)'*print_inquire* checking unit',lun
         inquire(unit=lun,                                                  &
     &   recl=recl,nextrec=nextrec,pos=pos,size=size,                       &
     &   position=position,                                                 &
     &   name=name,                                                         &
     &   form=form,formatted=formatted,unformatted=unformatted,             &
     &   access=access,sequential=sequential,direct=direct,stream=stream,   &
     &   action=action,read=read,write=write,readwrite=readwrite,           &
     &   sign=sign,                                                         &
     &   round=round,                                                       &
     &   blank=blank,decimal=decimal,delim=delim,encoding=encoding,pad=pad, &
     &   named=named, &
     &   opened=opened, &
     &   exist=exist, &
     &   number=number, &
!     &   pending=pending, &
     &   asynchronous=asynchronous,  &
     &   iostat=iostat,err=999,iomsg=message)

    elseif(namein /= '')then
         write(*,*)'*print_inquire* checking file',namein
         inquire(file=namein,                                               &
     &   recl=recl,nextrec=nextrec,pos=pos,size=size,                       &
     &   position=position,                                                 &
     &   name=name,                                                         &
     &   form=form,formatted=formatted,unformatted=unformatted,             &
     &   access=access,sequential=sequential,direct=direct,stream=stream,   &
     &   action=action,read=read,write=write,readwrite=readwrite,           &
     &   sign=sign,                                                         &
     &   round=round,                                                       &
     &   blank=blank,decimal=decimal,delim=delim,encoding=encoding,pad=pad, &
     &   named=named,opened=opened,exist=exist,number=number,               &
     &   pending=pending,asynchronous=asynchronous,                         &
     &   iostat=iostat,err=999,iomsg=message)
     if(name == '')name=namein
    else
       write(*,*)'*print_inquire* must specify either filename or unit number'
    endif
   write(*,nml=inquire,delim='none')
   return
999   continue
   write(*,*)'*print_inquire* bad inquire'
   write(*,*) '*print_inquire* inquire call failed,iostat=',iostat,'message=',message
end subroutine print_inquire
end program main

See my earlier reply. The typical and standard-conforming behavior is to open a new, empty file. If you then read from it, you’ll get an end-of-file condition. Any compiler which considered this nonstandard would have a bug.

You can protect against this by OPENing the unit with status="old".

A bad practice at a minimum. It’s only justification would be to conform to legacy behavior. Creating a file of unknown name, an INQUIRE showing no signs of preconnection, all going back to a time when primary connections were by a number typically mapped to a tape drive before the concept of named files was even well established. The compiler being free to complain about bad practice regardless of whether a standard exists or not it should be warned against. Even if you close the file first to eliminate any preconnection open(unit=LUN) still works on three compilers and that is obviously a bad idea.