Run-time choice of variable name

I had hoped to use namelist to give values to some of the variables in a Fortran program, but which ones would be specified at run time. If stuff is the name of a namelist group there is no problem making a list at run time giving the relevant variables’ names and using the statement read(list,nml=stuff) but the namelist statement seems to require the names at compile time. Must I put all the variables’ names in the namelist statement or is there a better way?

The answer, as far as I know, is no. This has been a very annoying weakness of namelists and I hope the standard committee comes up with a solution in the next standard. The namelist feature of Fortran is very useful but is relatively primitive in its current form. My final resolution to a similar problem was using preprocessing fences to define the namelist names at compile time. Alternatively, as you said, you could mix all variables in a single namelist group (, which I have also done) and ignore the redundant variables. It’s an inferior solution but is minimally harmful and avoids preprocessors.

1 Like

I am not sure whether I’ve understood the topic, but does it possibly help if you use a derived type for input values and specify only the type variable name in a namelist? Then you do not have to specify each component name in the namelist statement even when the definition of that type is updated / expanded. (In my case, many of the derived types have their own “parameter type” inside and read their values via namelist when requested from an input file.)

It would be interesting if a NAMELIST group statement without any
arguments meant all variables currently in scope.

It would also be nice if you could allocate a variable in a NAMELIST
statement instead of having to have everything pre-allocated to assign
values to it. Maybe NAME== instead of NAME= in the input file
would allocate it instead
of assign values to it.

In lieu of those possible proposals for new features I find it useful to
“grow” the namelist in the declarations by adding a namelist statement
to the end of each declaration. It is a bit verbose but I find it easier
to maintain than a single possibly huge NAMELIST declaration.

program namelist_build
implicit none
character(len=2)  :: lines(3)=["Aa","Bb","Cc"]; namelist/args/lines
integer :: i=0;                                 namelist/args/i
real :: a=0.0;                                  namelist/args/a

integer :: iostat

   read(*,nml=args,iostat=iostat)
   write(*,nml=args,delim='quote')

end program namelist_build

A longer version to play with

NAMELIST sample
program demo_attr_mode
implicit none
!NO, but would be nice if added "everything":! namelist/args/ 
!NO because of common compiler bugs! character(len=:), allocatable :: lines(:);      namelist/args/lines
character(len=2)  :: lines(3);                  namelist/args/lines
integer :: i=0;                                 namelist/args/i
real :: a=0.0;                                  namelist/args/a

type manifest
   ! add something here and it is available by name without
   ! additional changes to the namelist group
   real :: a=huge(0)
   integer :: i=huge(0)
   character(len=10) :: str='abcdefghij'
end type
type(manifest) :: stuff;                        namelist/args/ stuff

integer :: iostat

namelist/big/lines,i,a,stuff  ! one big one holding the same

   ! if allocatable must be allocated before call
   lines=[character(len=2) :: 'Xx','Yy','Zz']
   write(*,*,delim='quote')'LINES=',lines
   read(*,nml=args,iostat=iostat)
   write(*,nml=args,delim='quote')

end program demo_attr_mode
program demo_attr_mode

sample input

&args
 a=100.0,
 stuff%a=123.456,
 !NO, but would be nice if dynamically allocated! lines=["aaa","bbb","ccc","ddd"],
 lines="aA","bB","cC",
/

I think you are talking about the namelist read statement, not the namelist statement itself. This has been suggested many times in the past, not just for namelist input, but also in other situations involving both formatted and unformatted i/o. It is currently not allowed for any unallocated entity to appear in a read statement, so extending the language to allow for automatic allocation on read would be backward compatible with no need to change any syntax.

In addition to being convenient for programmers, this feature would also be more efficient than the current conventions. There are now many situations that require multiple reads of the input in order to determine the correct allocation parameters, or reading into, for example, a temporary linked-list structure, before allocating and transferring the contents to the final target array. I think programmers should not be required to keep reinventing that wheel, it should be a standard part of the language.

2 Likes

Many thanks for those constructive suggestions. Another possibility that I thought of is to put the NAMELIST stuff in a subroutine, with an actual argument being [a,b,c] if those are the variables one wants namelisted, and the corresponding dummy argument being an array of the appropriate type, because the NAMELIST statement need only mention the dummy argument’s name. In the current state of the Fortran standard there would have to be another argument which is a character array of the names of the actual variables. Clearly I have some experimenting to do.

This description of compile time and run time isn’t clear. Could you give a small example to demonstrate what you mean?

Back when namelist was a f77 (or earlier) extension, it was typically very limited. Only common block and local variables were allowed. In particular, dummy arguments were not allowed, which was an inconvenience to say the least. But now, namelist is very flexible, allowing module variables, dummy arguments, and local variables. And when combined with associate blocks, it seems very flexible, for example, to now have different external and internal variable names.

Well, actually I was inferring from the OP that literally just a statement like

NAMELIST/ARGS/

would be useful (which is currently not allowed so no backward-compatibility issues) that would automatically create a group that contained all variable names in scope. I have participated in several other discussions regarding NAMELIST enhancements and do not remember that being proposed. It would be symmetric in some ways with the SAVE attribute/SAVE statement. If you simply enter

SAVE

everything in scope that meets the criteria for being allowed to be saved is saved.

NAMELIST not allowing for a subset to be printed, not being allowed in a BLOCK, not supporting automatic allocation, failing if it encounters a variable declaration not in the group, auto-skipping being an almost universally supported extension not being part of the standard, … I would like several changes to NAMELIST groups but I do not ever remember seeing that “put everything in the group” option proposed and it seems like it would be useful.

I am actually a fan of NAMELIST but just a few tweaks would make it far more useful. There have been proposals to allow expressions, to allow conditional processing like cpp(1)/fpp(1) and many others I find intriguing, but I think this is a new one that would solve at least part of the Original Post, seems like it might be easy to implement as there is an existing feature that at least on the surface feels like it is doing something similar, and I think I would use. Of course truly exposing the namespace like many interpreted languages do would be even better but I suspect that would be very difficult to implement in a compiled language like Fortran without writing something like a built-in debugger into executables. NAMELIST is probably a bear to implement as-is, I would guess.

Maybe to align it even more with modern syntax, a namelist could be an attribute like SAVE as well.

  real,namelist(args) :: a,b,c

instead of

  real :: a,b,c  ;  namelist/args/ a,b,c

Of course several people might know my personal favorite would be that you be able to designate a namelist as an argument on the PROGRAM statement such as

  PROGRAM  myprog(ARGS)
  REAL a=0.0,b=0.0,c =0.0; NAMELIST/ARGS/ a,b,c

  and that the variables could automatically be specified on the command line as arguments using NAMELIST syntax, with a STYLE="option_name"  argument that would allow for Unix-style parsing,  and MSWindows CMD-style parsing as two standard options, with the vendor free to provide others as well.  That would allow for the easiest command-line parsing of any language I know of.  The above would allow the program to be called like

myprog a=10.0, b=20.0e2

and with something like PROGRAM(myprog(ARGS,STYLE=“sunstd”)
you could automatically do

 myprog -a 10.0  --b=20e2  

I think that would be a terrific extension of NAMELIST. I think that would be the easiest built-in command line interface of any language. Maybe there would be a few less NAMELIST-haters if it could be used that way.

But the only way to do what the OP wants now that I can think of is to compile with debug flags and evoke the program with gdb(1). That lets you print and specify just about any value.

Sorry if I wasn’t clear enough. Here is a small example using namelist which I wrote to see if a variable in a namelist group could be an allocatable array with various sizes on various occasions. I thought of the namelist statement as being compile-time because it’s a specification statement, and the name of the variable numbers in it can’t be changed at run time, but read(stuff,nml=list) is executable, and list may be different at different times when that reading is done at run time. The program compiled and ran with ifort and gfortran even though I think the shape of numbers, which was set in an executable statement, is contrary to the standard.
.

program nmltest
  implicit none
  integer:: i,j,n
  integer,allocatable::numbers(:)
  character:: list*80
  namelist /stuff/ numbers ! specification statement
  do
     print *,'Enter n>0 to make size(numbers)=n'
     read *,n
     if (n<=0) stop 'Your n<=0'
     numbers = [(0,i=1,n)]
     print *,'Enter integer j where 1<=j<=n to reset numbers(j)' 
     read  *,j
     if (j<1.or.j>n) stop 'Your j is not in 1<=j<=n'
     print *,'Before namelist numbers = ',numbers
     write(list,"(A,I0,A)") '&stuff numbers(',j,')=666 /'
     read(list,nml=stuff)  ! executable statement
     print *,'After namelist numbers = ',numbers
  end do
end program nmltest

I said I thought that my recent program using NAMELIST with an allocatable array was nonstandard. I should have said which version of the standard I had in mind. F95 explicitly forbade allocatable arrays in a namelist group. F2003 and F2008 did not, but the word ‘shape’ in F2003 5.4 or F2008 5.6 would seem to exclude them.

Both standards said “A namelist group object shall either be accessed by use or host association or shall have its type, type parameters, and shape specified by previous specification statements or the procedure heading in the same scoping unit or by the implicit typing rules in effect for the scoping unit.” But F2018 8.9 para 5 replaced “shape” by “rank”, which would allow an allocatable array.

I looked up the standards because g95, which is F95 with some F2003 features, refused to compile my program: it was right. But gfortran and ifort are F2018 compilers; they were right to compile and run it.

Almost all aspects of allocatable arrays were inadequate in f95. The “allocatable TR” was released simultaneously with the f95 standard, which mostly fixed all of the major problems. But that timing allowed compilers to claim “f95 compliance” even with all of the missing functionality of the TR, and several of them that I used at the time did exactly that. It was a frustrating time for programmers trying to write clean portable code. I think all of us would have been better off if the TR had been merged into the f95 language standard, even if it would have taken another couple of months to do so. This was finally reconciled in f2003, so the fix did not come quickly.

IMHO the fix allowing allocatable arrays in a namelist group didn’t come in f2003 or even f2008 but had to wait until f2018 .

As you know, the current practice of Fortran is with static typing. Also, toward the use case of interest to you, there isn’t any suitable introspection facility in the language that can enable “Run-time choice of variable name.” Considering everything, you may be better off keeping things simple and doing as you’re thinking, " put all the variables’ names in the namelist statement."

With objects of ALLOCATABLE attribute, as you pointed out, you will need to pay close attention to SHAPE because a processor is not required to detect and report any nonconformance with any mismatch and with any incomplete definition of the array objects, the onus lies on the programmer. In the following, a reference to the 3rd element of the array object makes the program nonconforming but a processor is not required to detect and report it and chances are most compilers will not do so:

   integer, allocatable :: x(:)
   namelist / num / x
   character(len=:), allocatable :: dat
   dat = "&num x=2*1, /"
   allocate( x(3) )
   read( dat, nml=num )
   print *, x !<-- processor-dependent as to what happens with the undefined element 3 in x
end 

I was wrong about f2018. Thanks are due to the WG5 convenor at the relevant time, who has pointed out that an allocatable array in a namelist group was already allowed by Corrigendum 2 to f2008: see
https://wg5-fortran.org/N1951-N2000/N1958.pdf

So playing around with an interactive program that lets me define a matrix and resize
it as the OP was describing and read values in using NAMELIST syntax I am seeing
that if I have a 3x4 integer array with elements all set to 999 and
using gfortran 11.1.0 read in the statement

&group x(2,3)=1,2,3,4, /

I get

&GROUP X= 7*999 ,1 ,2 ,999 ,3 , 4 , /

while with ifort 2021.8.0 I get what I think is the more reasonable

&GROUP X = 7*999, 1, 2, 3, 4, 999 /

Does anyone disagree that it is gfortran that is incorrect?

If anyone has a newer (12.2+) compiler I would be interested in knowing if
that is fixed,

A minimal example program is

program testit
implicit none
integer, allocatable :: x(:,:)
character(len=80) :: input(3)
namelist / group / x
   allocate( x(3,4),source=999)
   input(1)='&group'
   input(2)='  x(2,3)=1,2,3,4,'
   input(3)='/'
   read( input, nml=group)
   write(*,group)
end program testit

The actual program which prints things prettier follows.
The minimum input to the interactive program to print the array is

   v
   x(2,3)=1,2,3,4
   stop
Interactive program
program testit
integer, allocatable :: x(:,:); namelist / group / x
integer :: rc(2)        ; namelist / group / rc
integer :: oldshape(2)
logical :: verbose=.false.
character(len=4096) :: line
   allocate( x(3,4),source=999)
   rc=shape(x)
   oldshape=rc
   call try('help')
   INFINITE : do
      read(*,'(a)')line
      call try(trim(line))
   enddo INFINITE
contains
subroutine try(string)
character(len=*),intent(in) :: string
character(len=max(len(string)+1,6)) :: input(3)
integer :: iostat
character(len=4096) :: iomsg
select case(string)
case('h','help')
   write(*,*)'p|print               # print x matrix'
   write(*,*)'d|dump                # print namelist'
   write(*,*)'rc=rows,cols          # change shape of x'
   write(*,*)'h|help                # print this message'
   write(*,*)'v|verbose             # toggle verbose mode'
   write(*,*)'.|stop                # stop program'
   write(*,*)'anything else is assumed to be defining values of x'
case('.','stop')
   stop
case('p','print')
   call printi(x)
case('d','dump')
   write(*,nml=group,delim="quote")
case('v','verbose')
   verbose=.not.verbose
case default
   input(1)='&group'
   input(2)=' '//string//','
   input(3)='/'
   if(verbose)then
      write( *, '(a)')input
   endif
   read( input, nml=group ,iostat=iostat,iomsg=iomsg)
   if(iostat.ne.0)then
      write(*,*)trim(iomsg)
      call printi(x)
   elseif(verbose)then
      call printi(x)
   endif
   if(any(rc.ne.oldshape))then
      deallocate(x)
      allocate( x(rc(1),rc(2)),source=999)
      oldshape=rc
      write(*,*)'new shape is ',shape(x)
   endif
end select
end subroutine 

subroutine printi(arr)                                           !@(#) print small 2d integer arrays in row-column format
character(len=*),parameter :: all='(*(g0,1x))'                   ! a handy format
integer,intent(in)         :: arr(:,:)
character(len=20)          :: biggest
integer                    :: i
   print all
   print all, 'shape:(',shape(arr),')'  
   ! find how many characters to use for integers and create format for row
   write(biggest,'(a,i0,a)') '(" > [",*(i',ceiling(log10(real(maxval(abs(arr)))))+2,':,","))' 
   do i=1,size(arr,dim=1)                                        ! print one row of array at a time
      write(*,fmt=biggest,advance='no')arr(i,:)
      write(*,'(" ]")')
   enddo
end subroutine printi

end program testit

I’ve tried a slightly modified version of the above code

program test1
    implicit none
    integer, allocatable :: x(:,:)
    character(80) :: str
    namelist /group/ x

    allocate( x(3,4), source=999 )
    str = "&group x(3,1)=1,2,3,4, /"        !! L-1
    !! str = "&group x(3:,1:)=1,2,3,4, /"   !! L-2
    read( str, nml=group )
    write( *, nml=group )
end

which gives (with gfortran-12)

&GROUP
 X= 2*999        ,1          , 2*999        ,2          , 2*999        ,
 3          , 2*999        ,4          ,
 /

I get the same result if I comment the line L-1 and uncomment L-2. So, the compiler interprets x(3,1) as x(3:,1:) in the case of 2D array?
(I’ve never used this kind of 2D array input in a namelist file, so not sure what is
the “correct” behavior.)

FYI, the following code also gives the same result, so it seems the behavior is related to the interpretation of x(3,1) = 1,2,3,4 in the namelist input file (rather than whether x is allocatable or not).

program test2
    implicit none
    integer :: x(3,4)
    character(80) :: str
    namelist /group/ x

    x(:,:) = 999
    str = "&group x(3,1)=1,2,3,4, /"        !! L-1
    !! str = "&group x(3:,1:)=1,2,3,4, /"   !! L-2
    read( str, nml=group )
    write( *, nml=group )
end

I’m not sure either, but this looks like a gfortran error. I think the x(3,1) reference should be to storage sequence order within the full (1:3,1:4) array, while the x(3:,1:) reference should be to the storage sequence order within the (3:3,1:4) subblock. Here is a modification of the test program that does both reads.

program test1
   implicit none
   integer, allocatable :: x(:,:)
   character(80) :: str
   namelist /group/ x

   allocate( x(3,4), source=999 )
   str = "&group x(3,1)=1,2,3,4, /"        !! L-1
   read( str, nml=group )
   write( *, '(a/*(i0,1x))' ) 'x(3,1)', x
   x = 999
   str = "&group x(3:,1:)=1,2,3,4, /"   !! L-2
   read( str, nml=group )
   write( *, '(a/*(i0,1x))' ) 'x(3:,1:)', x
end program test1

$ ifort  nml.F90 && a.out
x(3,1)
999 999 1 2 3 4 999 999 999 999 999 999
x(3:,1:)
999 999 1 999 999 2 999 999 3 999 999 4

I think that ifort output is correct.

If I’m reading that description correctly, that would not work. An actual argument [a,b,c] is an array expression, and it cannot be modified through association with a dummy argument. There are some dummy argument declarations (e.g. intent(out)) where the compiler is required to catch the argument mismatch error at compile time. There are other declarations (e.g. no intent), where the compiler cannot catch the error, but it is still an error to modify the argument nonetheless, and it may or may not be detected later at run time.

After filing a bug report, I now think “x(2,3)=1,2,3,4” is an extension, so I cannot complain about
what a compiler does with it except that it should produce a warning if asking for checks for conforming to the standard. I can still do what I wanted originally to do using “x=*7,1,2,3,4” or getting fancier and mixing a block always starting with row one and/or using null values to get down to the desired row to start with; which is not as nice a syntax as I want; but I now think the standard requires for “x(2,3)=” to only be followed by a single value. So the following should all be standard except for the one
marked “extension”, I think …

>->m(2:,3:)=1,2,3,4 ! ok to fill subblock
 > [  999,   999,   999,   999 ]
 > [  999,   999,     1,     3 ]
 > [  999,   999,     2,     4 ]

>->m(2,3)=1 ! ok for single value only; but could do a bunch of them
 > [  999,   999,   999,   999 ]
 > [  999,   999,     1,   999 ]
 > [  999,   999,   999,   999 ]

>->m(2,3)=1,2,3,4 ! extension, varies per compiler
 > [  999,   999,   999,   999 ]
 > [  999,   999,     1,     3 ]
 > [  999,   999,     2,     4 ]

>->! null value skips to desired starting position and then goes in array order
>->m(1:,3:)=,1,2,3,4
 > [  999,   999,   999,     3 ]
 > [  999,   999,     1,     4 ]
 > [  999,   999,     2,   999 ]

>->! fill in array order regardless of shape
>->m=,,,,,,,1,2,3,4
 > [  999,   999,   999,     3 ]
 > [  999,   999,     1,     4 ]
 > [  999,   999,     2,   999 ]

>->! fill in array order regardless of shape using repeat
>->m=7*,1,2,3,4
 > [  999,   999,   999,     3 ]
 > [  999,   999,     1,     4 ]
 > [  999,   999,     2,   999 ]

Looking at the standard, I reckon a x(3,1) reference per standard is only to that element, not the sequence.

I do not think a namelist read instruction of "&group x(3,1)=1,2,3,4, /" conforms.

Compilers such as Intel Fortran appear to support it as an extension and when it comes to namelist, it’s likely there are several such extensions spread across compilers.