Add a specifier to namelist read that requires all members to be read

A namelist READ will read the members present in the namelist file or string and leave the other members unchanged. If those members were not set before, they may be inadvertently used before being set. For example, the following program

implicit none
real :: x, y, z
character (len=100) :: nml_string
namelist /xyz/ x, y, z
nml_string = "&xyz x=1.2, y=2.5/" ! z is missing
read (nml_string, nml=xyz)
print*,x,y,z
end

can give output of

1.200000 2.500000 5.7615271E+21

with ifort. I suggest that an optional read_all specifier be added to the namelist READ so that the absence of a namelist member in a namelist file or string causes a run-time error. For example if the program above had the line

read (nml_string, nml=xyz, read_all=.true.)

it would fail with a message such as could not read namelist member z.

2 Likes

This is quite a departure from the design of Namelist and list-directed input. In such cases, you could preset the variables to a sentinel value and then check for it.

With list-directed input I get an error message with

read (string, *) x, y, z

if z cannot be read, rather than have the program continue with z unchanged. I think the read_all specifier would make namelist input act more like list-directed input.

Not necessarily.

D:\Projects>type t.f90
real :: x,y,z
character(80) :: string = "3,4/"
read (string, *) x, y, z
print *, x,y,z
end
D:\Projects>ifx t.f90
Intel(R) Fortran Compiler for applications running on Intel(R) 64, Version 2024.0.2 Build 20231213
Copyright (C) 1985-2023 Intel Corporation. All rights reserved.

Microsoft (R) Incremental Linker Version 14.39.33519.0
Copyright (C) Microsoft Corporation.  All rights reserved.

-out:t.exe
-subsystem:console
t.obj

D:\Projects>t.exe
   3.000000       4.000000      0.0000000E+00

Different strokes for different folks, I suppose. I have wanted NAMELIST to be able to read from a file that defines values not in the namelist group for a long time; which would make NAMELIST far more flexible for use in reading configuration files. That is, if the namelist file set x, y, and z I would like to read the file with a namelist group that only contained a subset of those values. Otherwise, if I add a value to a NAMELIST file I have to make sure to change any program that reads the file to handle the new variable;
or break the file up so it has multiple NAMELIST groups defined in it; and although very very common in the past as part of the many NAMELIST extensions wheh NAMELIST was standardized I am not sure of the top of my head whether auto-scanning for different NAMELIST names and/or multiple NAMELIST defintions made it into the standard; although I still have NAMELIST files like that that have not caused problems.

Yes, often two programs share some but not all parameters. Maybe the namelist READ could add an

allow_extra=.true.

specifier to allow a namelist file to have members not present in the namelist of the program.

The “alliow_extra” is not really feasible, as it would require the compiler to pass names and info on every single variable mentioned in the program unit. rather than just those in the namelist. (I implemented namelist in the VAX Fortran run-time library so I know how this works.) I think this need is better suited to one of the XML parsing libraries.

The specifier allow_extra = .true. would cause the program to ignore data in the namelist file that was not in the namelist of the program. The program would not read variables not in the namelist from the namelist file.

I was asking that variables be ignored that were not in the NAMELIST
group; not that all the variables in a program unit be exposed; but that
would indeed be a terrific option as well!

I can understand how difficult that would be in a compiled language but
it must be feasible (perhaps at a very high performance cost) as debuggers
allow it; as well as changing values via expressions. Allowing expressions
in NAMELIST input would be another great future; as well as conditionals
that I think would be another game-changer for NAMELIST input.

But I was just suggest that if I had a number of programs that already
read and shared NAMELIST files having GRP2 in them and I then changed on
program to have a new variable “N” that I would not have to change all the
programs to have N to continue using the same files.

The work-around in some cases is to put N into a new NAMELIST group so the
file has two groups instead of one in it, which is less than ideal and at
least in the past used to have problems with some compilers that did not
support multi-group and multi-case NAMELIST files.

An artificial single-file program that illustrates what I wish would run
successfully:

program testit
implicit none
real    x; namelist /grp1/ x; namelist /grp2/ x
real    y; namelist /grp1/ y; namelist /grp2/ y
integer n; namelist /grp1/ n
integer :: io, iostat
character(len=256) :: iomsg
   x = tiny(0.0)
   y = huge(0.0)
   n = digits(0.0)
   open  (newunit=io,          &
   &     status='scratch',     &
   &     form='formatted',     &
   &     access='sequential',  &
   &     iostat=iostat,        &
   &     iomsg=iomsg,          &
   &     action='readwrite')
   if(iostat.ne.0)then
       write(*,'(*(g0))')'<ERROR>',iomsg
       stop 1
   endif
   write (io, nml=grp1)
   write (*, nml=grp1)
   rewind (io, iostat=iostat)
   x=-0.0
   y=-0.0
   write (*, nml=grp1)
   !read (io, nml=grp1)  ! this would work 
   read (io, nml=grp2)  ! file has x,y,z values but just want to read x,y
   write (*, nml=grp1)
end program testit

so the suggestion for allow_extra = .true. would do what I want; albeit I would probably use it with all NAMELIST group I/O!

This is one of the big reasons I stopped using list directed and namelist read for user inputs. There is no way in the general case to determine if the user provided the inputs or not. I always recommend that user inputs be formatted and read in one of a handful of more standardized formats (i.e. json, yaml, toml, etc.). Even still, writing the specifications defining what user options are required, especially in the cases where the are conditional on other inputs, what default values there are, what options should not be present, etc., is a hard problem™.

5 Likes

Personally namelist has always felt like an ultra-obsolescent feature to me, just like a common block. So the best improvement would be its removal from the language, in my opinion. Luckily with improving Fortran ecosystem we are able to read json, tomls and other members of the “four letter key-value formats” gang! :slight_smile:

2 Likes

FWIW, NAMELIST was a feature from IBM FORTRAN in the mid-1970s that eventually got added (with slight changes) to Fortran 90. The original intent was to permit a program to save and restore its state, it wasn’t really intended to be for user interactive input, though DEC and others extended it in that direction. I agree with @everythingfunctional that it has largely outlived its usefulness, and don’t recommend it in cases where you want to place additional demands on the user. (Like list-directed, namelist-directed input can accept things you may not want it to.)

3 Likes

NAMELIST is still very useful during code development for writing small driver routines to do unit tests on individual routines or modules. I find it easier than list directed input/output and lets you delay writing the usually much larger IO routines you will need for your final production code when you only need to specify a few variables for the unit test.

Also, according to my 1970 copy of Fredrick Stuarts “Fortran Programming” book, namelist was implemented in a handful of compilers prior to 1970 including one for your old employers PDP-10 systems.

I use namelist i/o all the time in my codes, so I think it is very useful. If you have many input variables, but only a few of them need to be specified on any particular run, then namelist is optimal. This is, of course, the opposite use case from the thread title.

If it were to be improved, I would like it to be able to allocate arrays to the correct size automatically. This feature would be nice for list-directed i/o too, but it would be even more useful for namelist. Otherwise, you need to read in the scalar dimensions in one read, then allocate the arrays, then read in the arrays in another read, which is unnecessarily complicated.

This would permit typos

Removing features is very anti-fortran. Breaks backwards compatibility at the least.

You do understand permitting extra would permit errors and typos , right? Right now you mistype and fortran catches it. With this feature it would be considered extra. Unless you want to require all inputs in the namelist which is basically the opposite of current behavior.

typed, name/value pairs in arbitrary order, with partial use and defaults and comments is very powerful. Most languages don’t have it write libraries to provide that functionality. Apple is developing PKL for typed input right now. Though it also includes validation - which I think belongs in the code anyway. or see C++ libconfig

Yes. many namelist files I have used are programmatically generated so spelling errors are not a major issue, and the feature (particularly if only available via an optional flag) would be well worth typoed names being allowed. This would be the same case as with Fortran that has the risk of typos without IMPLICIT NONE. The check is highly desirable in many cases, but not all. In this case it would be easy to maintain a small program that checked all names for verifying files. I often see file validation checkers for XML files as one example of how this can be handled.

That small program could be simply a namelist read with all the variables and without the allow_extra=.true. flag.

1 Like

(Even though I used to hangout a lot at comp.lang.fortran back in the day, this is my first post at fortran-lang.discourse.group)

I also use namelists all the time, mostly for config input, as in

type :: app_config
    logical :: fallback_to_x = .false.
    integer :: max_retries = 5
    integer :: timeout_ms = 60000
    character(63) :: default_prefix = ''
end type
type(app_config) :: config
namelist /nml_config/config
...

Since config values have a default, and input must be sanitized anyway, the “unexpected input values” argument might not hold.

Besides the automatic allocation of arrays feature mentioned by @RonShepard , allowing namelists in the specification part of a (not-in-do-concurrent) block construct would also be a great addition.