Is the use of namelists portable across compilers? Are namelists considered deprecated? They appear to be a useful feature, but I’m curious if there are any serious hidden gotchas…
Thanks
Is the use of namelists portable across compilers? Are namelists considered deprecated? They appear to be a useful feature, but I’m curious if there are any serious hidden gotchas…
Thanks
NAMELIST
is a nice feature that doesn’t get the attention it deserves, in my opinion. They are not obsolescent
(the standard does not use the term deprecated
)…
You should find NAMELIST
input to be portable among conforming compilers and platform-independent barring some circumstances with CHARACTER variables outside of default character set in Fortran with which I do not have much experience.
But NAMELIST
output is unfortunately a different story, please see this thread.
The advantages of namelists over just reading text files are that the input files are self-documenting, the parameters in them can appear in any order, and that reading and writing a namelist can be done in single statements?
Playing with namelist for the first time, the program
implicit none
integer :: nrows,ncol
character (len=100) :: data_file
namelist /param/ nrows,ncol,data_file
open (unit=20,file="param.nml")
read (20,nml=param)
write (*,nml=param)
end'
for param.nml
¶m
data_file = "data.txt"
nrows = 10
ncol = 2
/
gives output
&PARAM
NROWS=10 ,
NCOL=2 ,
DATA_FILE="data.txt ",
/
Nitpicking, but I wish there were an option to print variable names in lower case or the case of the variables declared in the program, and also an option to print trimmed strings. Ideally I could declare character (len=:), allocatable :: data_file
, but the program crashes.
In my parameter files I have lines such as
2 3.1 5.2 ! nx, x(:)
where I read an array size, allocate the array, and then read the array values. I guess namelists cannot handle that.
I agree that namelist
is an excellent IO feature in Fortran. But I think its current state in Fortran is rather primitive, and it is not only me who thinks so. Here is a recent example: Nested namelists in fortran - Stack Overflow
I have also raised the namelist
limitations to the attention of some Fortran committee members in the form questions (which often faced fierce opposition, perhaps due to my lack of understanding of their arguments). I remember reading a post on Julia discourse page that heavily criticized Fortran namelist
(perhaps this one, not sure though).
Whether the namelist
criticisms are valid or not should be judged by Fortran experts. But the number of criticism implies that there is room for improving the namelist
concept in Fortran.
When the data of interest start to have a structure to them along with, say, dependence on some “size” parameters, the “conventional wisdom”, as you will know, with Fortran has long been “custom” IO procedures.
The idea has been carried forward to derived type
s also since Fortran 2003 when the option toward defined input/output
was introduced with user derived types.
Thus if there is value in your “data” to be encapsulated as a derived type, you can consider implementing your custom IO methods and wrap them in defined input/output
data transfer procedures that also support NAMELIST
. There is also the added flexibility here where the child data transfer can be list-directed when the parent is NAMELIST
. This all allows you to do the work once in your data
class and reuse said class in many places. See a trivial illustration below.
module dat_m
type :: dat_t
integer :: nx = 0
real, allocatable :: x(:)
contains
private
procedure, pass(this) :: read_dat
procedure, pass(this) :: write_dat
generic, public :: read(formatted) => read_dat
generic, public :: write(formatted) => write_dat
end type
contains
subroutine read_dat(this, lun, iotype, vlist, istat, imsg)
! Argument list
class(dat_t), intent(inout) :: this
integer, intent(in) :: lun
character(len=*), intent(in) :: iotype
integer, intent(in) :: vlist(:)
integer, intent(out) :: istat
character(len=*),intent(inout) :: imsg
! Local variables
integer :: i
select case ( iotype )
case ( "NAMELIST" )
! Elided are all the checks and error handling
! An option here is to employ list-directed read
read(lun, fmt=*, iostat=istat, iomsg=imsg) this%nx
if ( this%nx > 0 ) then
this%x = [( 0.0, i = 1, this%nx )]
read(lun, fmt=*, iostat=istat, iomsg=imsg) (this%x(i), i=1,this%nx)
end if
case default
! Elided is code for other iotypes
end select
end subroutine read_dat
subroutine write_dat(this, lun, iotype, vlist, istat, imsg)
! argument definitions
class(dat_t), intent(in) :: this
integer, intent(in) :: lun
character(len=*), intent(in) :: iotype
integer, intent(in) :: vlist(:)
integer, intent(out) :: istat
character(len=*), intent(inout) :: imsg
! local variable
character(len=*), parameter :: NML_OFMT = "(*(g0,','))"
select case ( iotype )
case ( "NAMELIST" )
write(lun, fmt=NML_OFMT, iostat=istat, iomsg=imsg) this%nx, this%x
case default
! Not supported in this example
end select
end subroutine
end module
The above data “class” can used with the following simple program
use dat_m, only : dat_t
type(dat_t) :: dat
character(len=:), allocatable :: ifile
namelist / dat_nml / dat
ifile = "&dat_nml dat=3, 1.1, 2.2, 3.3, /"
read( unit=ifile, nml=dat_nml )
print *, "nx = ", dat%nx, "; expected is 3"
print *, "x = ", dat%x, "; expected is [ 1.1, 2.2, 3.3 ]"
end
should produce the output
nx = 3 ; expected is 3
x = 1.100000 2.200000 3.300000 ; expected is [ 1.1, 2.2, 3.3 ]
What this example also shows is a poor Fortranner’s option toward serialization
and deserialazation
of objects in memory using modern Fortran, something that can be quite handy when libraries in Fortran need to work with other apps e.g., on the web/cloud, etc.
The syntax for declaring a namelist and the form of the text in the files containing namelists are specified by the standard and are fairly portable. They are used by some large codes for specifying runtime configuration data, since the visual form of the input file is self-documenting as to what variables are being defined by the namelist READ.
Namelist existed as a compiler extension before the feature was standardized, So there might be some really old instances that are not conforming to the current standard.
Namelists also include an internal structure of meta-data that enables the capabilities associated with namelist. That internal structure is not portable.
I might be wrong but I couldn’t manage to find anything relating to namelist
in the section of obsolescent features (Fortran 2008 Standard).
Some applications, like the popular open source weather forecasting software WRF make heavy use of the namelist feature (In WRF, it has a file called namelist.input
that controls all kinds of parameters.) and I guess the standard committee also recognizes that.
Also, I found this article very interesting so I am sharing it here: Working nicely with Fortran Namelists · The COOP Blog (cerfacs.fr).
PS: The blog post mentions this discourse as well so that would be a cross citation.
NAMELIST groups can be great for simple configuration files, and for passing data between two Fortran programs. They can be really handy in debugging and in unit testing too (especially useful for comparing expected values versus generated values). You can dump out a dozen values nicely labeled with a single write statement instead of having to write a big FORMAT statement to label everything when debugging (now if Fortran only let me specify the namelist in a BLOCK structure right above the WRITE statement …).
Being human-readable and writable and self-describing and standardized as part of the language are great. I can just tell someone the input is in NAMELIST format and most of the documentation is written for me – it is in the nearest Fortran manual.
You can even use them in command line argument parsing,
from allowing for simple (mostly numeric) values to being used with
Unix-like syntax as in M_CLI.
They make for an interesting interactive input
method.
Their support for user-defined types is very powerful, and they are the closest thing to exposed variables that there is in Fortran.
I particularly like being able to have multiple cases and multiple namelist groups in a single file, and the fact that lines outside of the NAMELIST format are ignored (so you can have a markdown file or some other kind of document with a little NAMELIST definition in in that you can read while ignoring the rest of the file). That is great for documenting the data and still being able to use it as input to a program.
We use to use that feature for tracking documents by putting NAMELIST input in comments in *roff, HTML, LaTex and other documents as a tracking mechanism. That, I think, is a surprising use of NAMELIST.
Being able to declare values with array syntax can be exploited to do some interesting things.
On the other hand the output can be a bit ugly (especially the aforementioned problem with strings not being trimmed).
But I almost always get hung up on not being able to have variables declared in the NAMELIST files that are unknown to the program reading it. It would probably be really hard for NAMELIST to support things like user-defined types and arrays if it were allowed, but that is almost always the gotcha for me.
And like a lot of serialized data formats you cannot input expressions, and conditionals and loops are not supported.
And the last issue for some is that (as far as I know) there is not anything that reads and writes NAMELIST files in other languages other than a Python utility (which I have not used, but have seen multiple references to).
So “yea NAMELIST groups”, but for large configuration files that are generated by humans I almost always end up making my own, usually using something like
So on the one hand I have used NAMELIST (far?) more than most, in several different ways; but because of a few basic limitations I almost never use it for something that is going to be manually composed input; unless it is going to be a very structured stable list of variables.
But I don’t use any of those other (semi) standards either! Some of them do not even allow for comments! So NAMELIST is horrible, except for all the others. It really would be nice to have something like NAMELIST in the language that maybe only took intrinsic types as input that was prettier and took expressions and ignored unknown names, and had standard interactive features like printing current values. That might almost be worth writing.
Lots of great ideas in that post. Thanks!
Thanks! Glad you liked it. By the way, you should normally declare a value for all the members of the NAMELIST group before reading it (one of the limitations of a NAMELIST if there is no query function to see if a value was read or not) and if you do, then you can read allocatable variables too. And since allocatable variables can be trimmed, with a little bit of work that earlier example can run and make presentable output with an allocatable CHARACTER variable:
program trimit
implicit none
! perhaps surprisingly, you can grow a namelist
integer :: nrows ;namelist/param/nrows
integer :: ncol ;namelist/param/ncol
character (len=:),allocatable :: data_file ;namelist/param/data_file
open (unit=20,file="param.nml")
nrows=-1 ! at least for the first read you want to set initial values
ncol=-1 ! optionally using an "illegal" value you can use to see if a value was present
! if an allocatable variable is allocated before the READ it is OK
data_file=repeat(' ',4096)
read (20,nml=param)
! of course, now you want to trim it before printing it
data_file=trim(data_file)
write (*,nml=param,delim="quote")
end program trimit
$ gfortran trimit.f90
$ ./a.out
&PARAM
NROWS=10 ,
NCOL=2 ,
DATA_FILE="data.txt",
/
$ ifort trimit.f90
$ ./a.out
&PARAM
NROWS = 10,
NCOL = 2,
DATA_FILE = "data.txt"
/
$ nvfortran trimit.f90
$ ./a.out
&PARAM
NROWS = 10,
NCOL = 2,
DATA_FILE = "data.txt"
Note the slightly different output from different compilers; that is allowed by the standard. Also note use of an explicit DELIM on the write statement. Without that you might get no quotes, quotes or apostrophes as the default is not set by the standard (I am pretty sure).
Note the space in column 1 for gfortran output. I have seen arguments about whether that is supposed to be required or not on output.