Namelist attribute for use in variable declaration

To avoid the need for a namelist variable to appear twice, first in a declaration and then in a namelist group definition, would it make sense to add a namelist attribute?

So this:

real :: good, push, it
namelist /snp/ good, push, it

would be equivalent to

real, namelist(snp) :: good, push, it

To support the fact that a variable can appear in multiple namelist groups, maybe the attribute could accept a comma separated list, like so:

real, namelist(snp1, snp2, othernml) :: good, push, it

This is a half baked idea so I’d love to hear some feedback from the community.

1 Like

Welcome to the forum!

I never use namelists (although they are a nice enough feature), but looking at your suggestion, how would you define the order of the variables in the namelist? Here is an example where this is not going to be obvious, as far as I can tell:

real :: good, push, it
integer :: countthem
namelist /snp/ good, countthem, push, it

Wouldn’t your suggestion restrict the ordering?

To avoid restricting the members of a namelist to having a single data type, one could have syntax analogous to a derived type:

namelist :: snp 
   real :: x, y
   integer :: i, j
end namelist

A variable could appear in more than one such namelist declaration, with the restriction that its type must be the same in each. With your proposed syntax, one could allow

real, namelist(snp) :: x, y
...
integer, namelist(snp) :: i, j

but I think it is clearer to have all members of a namelist listed in one place.

4 Likes

It should be simple enough to order the namelist in the same order the variables appear in declarations, just like is done with derived types and enumerators. The following would be equivalent:

real :: good, push, it
integer :: countthem
namelist /snp/ good, countthem, push, it
real, namelist(snp) :: good
integer, namelist(snp) :: countthem
real, namelist(snp) :: push, it

This is an example of what’s called “syntactic sugar” - an alternate way of saying something the language already allows. We tend to look on this with disfavor, and I think that attitude would be stronger for a feature such as NAMELIST.

What I’m trying to improve (IMHO) with this suggestion is to avoid this situation, having every variable appear twice in the declaration section:

real, dimension(10), public, save :: good
integer, public, save :: countthem
real, allocatable, dimension(:,:), public, save :: push
real, pubic, save :: it
! 496 other variable declarations

namelist / snp / good, countthem, push, &
! 495 other variable names manually retyped to appear a second time in the 
! declaration section of this module with a bunch of continuation lines...
! Oops, I forgot 'it' and missed another one somewhere in the middle

sblionel
This is an example of what’s called “syntactic sugar” - an alternate way of saying something the language already allows. We tend to look on this with disfavor, and I think that attitude would be stronger for a feature such as NAMELIST.

Do you view this differently from other “sugar” features Fortran already has? I might not know enough appreciate the distinction. For example,

real :: good
dimension :: good(10)
public :: good
namelist / snp / good
real, dimension(10), public :: good
namelist / snp / good

I do. Fortran 90 added the concept of attributes to a single declaration but did not remove the older statement-style of adding attributes. (New attributes were added as statements for symmetry.) There are other examples of this.

What I see as different here is that there are multiple concepts you’re trying to shoehorn into a feature, none of which add new capabilities. That they are tied to the rarely used NAMELIST feature doesn’t help. Personally, I’d find it confusing to need to identify all the variables in a particular namelist group, given that during namelist input you must first give the group name. It’s not like (obsolescent) COMMON, where a variable can belong to only one common block.

I often say that there are no zero-cost features. Just the standards work alone to come up with specifications and edits for this would not be trivial, not to mention compiler work. I’d prefer to see us focus on adding new capabilities to the language and not keep one-plusing old stuff.

The suggested syntax requires multiple references to the namelist group, so I don’t see this as much of an improvement over the current standard syntax. Consider the common code style of one variable per declaration line with inline documentation of that variable. There is also the problem associated with misspellings of the group name. Consider

real, namelist(snp) :: good
integer, namelist(snnp) :: countthem
real, namelist(snpp) :: push, it

How could a compiler recognize the difference between the two typos and the situation where there are three similarly named groups?

As for code simplification and reduction of programmer errors, the suggestion seems like six of one, half a dozen of the other.

One thing I have wanted in the past is the ability to specify the namelist group and list within the executable statements right before the read statement. The current standard requires that to be in the declaration statements, which is sometimes far removed from the read statement. I think the problem with this is that there are other declaration statements (e.g. public and private) that can refer to the namelist group, so this feature would require the compiler to look ahead more than is currently necessary.

If there’s no appetite for syntactic sugar, let alone namelist enhancements, I suppose the rest of this conversation is just a thought experiment.

Can you please expand on this statement – “confusing to need to identify”? I could easily be misinterpreting what you mean.

@RonShepard, RE repetition and possible typo of namelist-group names, @Beliavsky already suggested a different approach above, which looks nice (to me):

@sblionel, @RonShepard I wonder what both of you think about the redundancy of declaring a lot of variable names both in the declaration and namelist statements (as suggested by @Machalot above), because I also have similar problems (for which I use derived types as a workaround). Also, because Fortran lacks introspection, even the use of TOML or other modern formats requires further redundant works for setting variable values from input data (e.g., as discussed in the following thread). Because of the lack of introspection in Fortran, I use namelist everyday (as opposed to the “rarely used NAMELIST feature doesn’t help” assumption by @sblionel).

1 Like

I don’t see this as a different class of problem than mistyping similar variable names or procedure names (such as xi, xii, xix, xlix, xilx). It is already the programmer’s responsibility to choose good names that are distinct enough so a typo is unlikely to compile into a wrong program. As we know, disabling implicit typing makes this much better.

I suppose there should be a namelist declaration statement so the compiler can catch typos that don’t match the name of any other namelist group.

namelist :: snp
namelist :: snpp ! try choosing more distinct names to avoid problems with typos

real, namelist(snp) :: good           ! valid
integer, namelist(snnp) :: countthem  ! compiler error: nonexistent namelist group snnp
real, namelist(snpp) :: push, it      ! valid

But as I said above, sounds like this is DOA so any further discussion is just a thought experiment. Thanks for engaging on my first post!

I meant that if I am scanning the code trying to figure out which variables are in which namelist, scattering the namelist group names across various declarations makes it difficult.

I prefer @Beliavsky 's idea as well. To me a more ideal case is to make namelist an attribute of the derive type. In the current Fortran standard, both derived type and parameterized derived type are allowed, and to me that is an advantage of using namelist over TOML/JSON libraries since I don’t have to write an extra layer to convert parameters to my customized derived types. But reading a derived type from a namelist is painful (especially when allocatable components are involved). I guess namelist can be a lot more useful if we could do something like the following:

type :: color
  integer :: r, g, b
end type

type, namelist :: window
  integer :: width 
  integer :: height
  type(color) :: default_color
end type window

contains
!...
read(unit=unit, nml=window)

read a namelist

&window
  width=800
  height=600
  default_color=color(255, 255, 255)
/
1 Like

One of the few places where I use semi-colons is when building namelists

integer :: i;   namelist /args/i
real    :: r;   namelist /args/r

which comes a little close to the original OP request while conforming to the current standard. I like the suggested syntax by @Beliavsky but I have not though out whether it covers all the interesting aspects of building upon an existing namelist; particularly when imported from a module or in multiple contained procedures or if that meets the restrictions like not building a namelist in a block structure (I think). I seem to recall wanting to create a namelist for debugging using something like

block
namelist /debug/ a,b,c
write(*,nml=debug)
endblock

and being disappointed that was not allowed if I remember correctly (did not verify that).

1 Like

This is exactly the reason why I use namelist with derived types, even though there are a lot of historical pitfalls (like strange treatments of *, /, etc). Indeed, the combination of namelist + derived type provides a capability somewhat similar to the examples in the Swift and Rust libraries below (to some extent), thanks to the builtin “introspection” by Fortran compilers.

In my case, I often create a new derived type by separating a parameter set that describes “static” information of a simulation from other “dynamic” data , via composition of derived types. Something like…

type FooParam_t
   !! various params here...
endtype
type Foo_t
  type(FooParam_t) :: par
  !! other dynamic data follow...
endtype

Then, I can pass foo%par to a reader routine like

subroutine read_params( par )
    type(FooParam_t) :: par
    namelist /foo_inp/ par
    ...
    read( file, nml=foo_inp )
    ...
end

(which is in my case wrapped as a method of Foo_t). When I use Foo_t in other routines, I also use associate at the top of the routine if some params are referenced very often:

subroutine blah( foo, ...)
let( num => foo% par% num, &
     val => foo% par% val )
... body of the routine ....
endlet
end subroutine

(I define “let” = associate via C preprocessor because I feel the keyword too long…). I guess if future Fortran has some auto-forwarding mechanism (e.g, foo%par%num is forwarded to foo%num), the use of such a composite type may become simpler (rather than using inheritance).

EDIT: I’ve just tried using inheritance for separating parameters (for namelist read), and it seems to work… I’ve never used this up to now, but it may be useful to remove “par” when accessing parameters.

program main
    implicit none

    type FooParam   !! "static" info
        integer :: num = 0
    endtype
    type, extends(FooParam) :: Foo   !! "dynamic" info
        integer, allocatable :: arr(:)
    endtype
    type(Foo) :: f

    call read_inp( f % FooParam )

    print *, "params = ", f % FooParam   !! 100
    print *, "f % num = ", f % num       !! 100
contains

subroutine read_inp( par )
    type(FooParam) :: par
    namelist /foo_inp/ par

    open( 10, file="foo.inp", status="old" )
    read( 10, nml=foo_inp )
    close( 10 )
end

end program

!! foo.inp
&foo_inp
  par%num = 100
/
1 Like

By the way, the “color” code also works:

!! test.f90
program main
    implicit none
    type :: color
        integer :: r = 1, g = 2, b = 3
    end type
    type :: window
        integer :: width = -1
        integer :: height = -1
        type(color) :: default_color
    end type

    type(window) :: win
    namelist /window_inp/ win

    open( 10, file="test.inp", status="old" )
    read( 10, nml=window_inp )
    close( 10 )

    print *, "win = ", win
end

!! test.inp
&window_inp
win%width  = 100
win%height = 200
win%default_color%b = 777
/

$ gfortran test.f90 && ./a.out
 win =       100      200        1        2      777
1 Like

Thank you for clarifying. In the case of my own workflow, this becomes far easier with the proposed syntax. With each variable declared on a separate line, grep namelist_groupname returns a compact list of the variable declarations of all its members, to be viewed on-screen or redirected to a pipe or a file for further searching or analysis. As a bonus I can see all their types, kinds, dimensions, and other attributes at a glance.

$ grep snp # my namelist is called snp
# or a more precise search
$ grep 'namelist(snp)' # my namelist is called snp
my_module.f90: real, namelist(snp), public                :: good
my_module.f90: real, namelist(snp), dimension(10), public :: push
my_module.f90: real, namelist(snp), public                :: it
my_module.f90: integer, namelist(snp)                     :: countthem

In contrast, with the current namelist syntax I have to open the file or have grep print a large number of context lines to see the namelist members.

$ grep snp # my namelist is called snp
my_module.f90: namelist / snp / good, countthem, push, it & ! only the first few members

In reverse, if I grep for a variable name using my proposed syntax, I would immediately see its declaration including all its namelist groups directly in the result (assuming it fits on one line):

$ grep good
my_module.f90: real, namelist(snp1, snp2, othernml) :: good

In contrast, with the current namelist / groupname / varnames ... syntax, I would see its declaration but it’s unlikely the namelist group name would appear in a search for a variable name since they are generally on separate lines. Most likely I would see a slice of the namelist membership without the actual group name, such as

$ grep good
my_module.f90: real :: good
my_module.f90: good, countthem, push, it, & ! no sign of the namelist group name

I saw you post this in another thread, and it is the direct inspiration for this post.

1 Like

It’s a pity that the standard committee and a significant part of the community show so much apathy toward improving and using namelists. It’s a useful flexible IO feature, but the current implementation of namelist has several weaknesses, including

  1. the inability to specify the namelist group name as a string in IO statements.
  2. lack of support for derived types with allocatable components.
  3. lack of support specifying multiple namelist group names for variable names.

The last one is similar to your last enhancement request. These limitations have led to complex hacks using preprocessor flags in our codebase, which may also be the only solution for you in light of the standard committee’s lack of interest in enhancements to namelists.
An example of such an approach is here where the namelists are included in the main file, while the actual implementation is fenced via a preprocessor flag in a separate file. Without preprocessing, maintaining all these separate namelist groups with so many common variables would be an infernal nightmare.

3 Likes