How to read only some values from a namelist?

Consider this namelist stored in a file called numbers.nml:

&numbers one=1, two=2 /

and the program:

program read_numbers
  implicit none
  integer :: iounit
  integer :: one
  namelist /numbers/ one
  open(newunit=iounit, file='numbers.nml', status='old', &
       action='read', form='formatted', access='sequential')
  read(iounit, nml=numbers)
  close(iounit)
end program read_numbers

Building and running this with gfortran-9.2.0 gives me:

At line 8 of file read_numbers.f90
Fortran runtime error: Cannot match namelist object name two

Error termination. Backtrace:
#0  0x7f523f117e57 in finalize_transfer
	at ../.././libgfortran/io/transfer.c:4072
#1  0x4012f8 in ???
#2  0x401366 in ???
#3  0x7f523eb0609a in ???
#4  0x4010c9 in ???
#5  0xffffffffffffffff in ???

Question: Is there a way for me to read one or some but not all values from a namelist?

I’m reading Section 10.10 of MRC2018 and I can’t find a statement saying this in neither allowed nor disallowed. In practice, I have dozens of namelist variables that I want to ignore.

I’m sad. On to manual parsing. Thanks, @pmk.

Cannot you read the variables and ignore them?

That has been a frustration at many levels. Two solutions that admittedly are not ideal but are still NAMELIST-group oriented (and only meet certain situations) are to break the namelist up into multiple namelist groups in the same input file, and to have a program that has everything defined that can be called that then writes out the specific variables you want. There is a JSON file parser in github. I believe the Fortran TOML parser does the same. I have parsers that read Fortran-like expressions and unix-like commands that can be used in configuration files in the github GPF (General Purpose Fortran) repository that I would use a lot less frequenctly if NAMELIST did not have this limitation, but because any user-defined type can be in a NAMELIST as well as arrays and unallocated allocatable arrays cannot be read I do not easily see how the limitation could be removed unless some way of defining types could also be included in NAMELIST.

@milancurcic,

You and the readers will know code can go the other way, meaning the NAMELIST definition in code can have more members than normally used and that default values can be set for them while the data file ordinarily does not include values for all the members, as is often the case with user input for many numerical calculations. And that such an approach was for the longest time employed, especially on IBM computers, as JSON-like object = value approach toward input into Fortran programs running simulations:

   character(len=:), allocatable :: my_data
   integer :: x, y
   namelist / dat / x, y
   x = 1 ; y = 2
   my_data = "&dat x=42 /"
   read( unit=my_data, nml=dat )
   print *, "x = ", x, "; expected is 42"
   print *, "y = ", y, "; expected is 2"
end

Program output with a commercial compiler:

x = 42 ; expected is 42
y = 2 ; expected is 2

Maybe an example of multiple NAMELIST groups in the same file would be helpful too. So picture in the following example that the array “file” is actually a file. NAMELIST files can have multiple NAMELIST groups in them; although you might have to do some rewinds if you are not careful about the order you read the different names. Then you could have programs that read both NAMELIST groups or just one of them:

program testit
integer :: red,green,blue ; namelist/nml_color/red,green,blue
real :: width,height,depth; namelist/nml_size/width,height,depth
namelist/nml_all/ red,green,blue,width,height,depth
character(len=*),parameter :: file(*)=[character(len=80) :: &
   & ' The values specifying the color of the model', &
   & '&NML_COLOR', &
   & ' RED=255,', &
   & ' GREEN=255,', &
   & ' BLUE=0,', &
   & ' /', &
   & ' The values specifying the geometry ', &
   & ' of the model', &
   & '&NML_SIZE', &
   & ' WIDTH=  10.0000000,', &
   & ' HEIGHT=  20.0000000,', &
   & ' DEPTH=  30.0000000,', &
   & ' /', &
   & '']
read(file,nml=nml_color) ! can just read colors
read(file,nml=nml_size)
write(*,nml=nml_all)
end program testit
groups or only a subset of them:

xxx
&NML_ALL
 RED=255        ,
 GREEN=255        ,
 BLUE=0          ,
 WIDTH=  10.0000000    ,
 HEIGHT=  20.0000000    ,
 DEPTH=  30.0000000    ,
/



Fortran standard can definitely include better support for NAMELIST but this useful feature is not seen favorably, quite sadly in my opinion. Anyways, proposals will now have to wait for Fortran 202Y and will likely need to be very targeted, limited in scope, and clearly laid out for success, I feel. GitHub Fortran site is the best place for ideas: GitHub - j3-fortran/fortran_proposals: Proposals for the Fortran Standard Committee.

In the meantime, users with derived type needs can consider defined IO facility in the current Fortran standard even though it can get very verbose and there appear to be bugs with it in the gfortran implementation. Here’s an example I think is conforming (but I’m open to be proven wrong) and which works with a commercial compiler:

A test driver program:

   use m, only : t

   character(len=:), allocatable :: s
   type(t) :: foo
   namelist / nml_t / foo

   foo = "Hello World!"
   allocate( character(len=80) :: s ) ! Set the string to some suitable length
   write( unit=s, nml=nml_t )

   foo = ""
   read( unit=s, nml=nml_t )
   print *, "foo%s = ", foo%s()

end

Library code for a simple-minded ''string class" in Fortran

module m

   use, intrinsic :: iso_fortran_env, only : iostat_end, iostat_eor

   type :: t
      private
      character(len=:), allocatable :: m_s
   contains
      private
      procedure, pass(this) :: assign_t
      procedure, pass(this) :: read_t
      procedure, pass(this) :: write_t
      procedure, pass(this), public :: s => get_s
      generic, public :: read(formatted) => read_t
      generic, public :: write(formatted) => write_t
      generic, public :: assignment(=) => assign_t
   end type t
   
   character(len=1), parameter :: QUOTE = '"'
   character(len=1), parameter :: SLASH = '/'
   character(len=1), parameter :: COMMA = ','

contains

   subroutine assign_t( this, s )
   
      class(t), intent(inout) :: this
      character(len=*), intent(in) :: s
      
      this%m_s = s
      
   end subroutine assign_t
   
   subroutine read_t(this, lun, iotype, vlist, iostat, iomsg)

      ! Argument list
      class(t), intent(inout)        :: this
      integer, intent(in)            :: lun
      character(len=*), intent(in)   :: iotype
      integer, intent(in)            :: vlist(:)
      integer, intent(out)           :: iostat
      character(len=*),intent(inout) :: iomsg

      ! Local variables
      character(len=:), allocatable :: s
      integer, parameter :: SLEN = 10
      integer :: lens
      integer :: istat
      logical :: begin_quote

      iostat = 0
      lens = 0
      if (iotype == "NAMELIST") then
         s = repeat( " ", ncopies=SLEN )
         begin_quote = .false.
         loop_read: do
            lens = lens + 1
            read(lun, fmt='(a1)', advance="no", iostat=istat) s(lens:lens)
            select case ( istat )
               case ( 0 )
                  select case ( s(lens:lens) )
                     case ( QUOTE )
                        if ( begin_quote ) then
                           lens = lens - 1
                           exit loop_read
                        else
                           begin_quote = .true.
                           s(lens:lens) = " "
                        end if
                     case ( COMMA, SLASH )
                        lens = lens - 1
                        exit loop_read
                     case default
                  end select
               case ( iostat_end, iostat_eor )
                  exit loop_read
               case default
                  iostat = istat
                  exit loop_read
            end select
            if ( lens == len(s) ) then
               ! increment length
               s = s // repeat( " ", ncopies=SLEN )
            end if
         end do loop_read
         this%m_s = trim( s(1:lens) )
      end if
      ! elided are the instructions for other IOTYPE values
      
      return

   end subroutine read_t

   subroutine write_t(this, lun, iotype, vlist, istat, imsg)

      ! Argument list
      class(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

      if (iotype == "NAMELIST") then
         write(lun, fmt="(g0)", iostat=istat, iomsg=imsg) QUOTE // trim(this%m_s) // QUOTE
      end if
      ! elided are the instructions for other IOTYPE values

      return

   end subroutine write_t

   function get_s( this ) result( s )

      class(t), intent(in) :: this
      character(len=:), allocatable :: s

      if ( allocated(this%m_s) ) then
         s = this%m_s
      else
         s = ""
      end if

   end function
   
end module

Execution of program built with a commercial compiler gives me the expected output:

foo%s = Hello World!

I’ve never been particularly fond of any of the built in “parsing” of Fortran when it comes to user input. It is quite nice if you have reasonable defaults for all your inputs and don’t particularly care if a user omitted something. But anything other than that is quite… awkward.

For example, did the user omit a particular value, or just happen to input the default? What about any inputs that are more complicated than just a list of values? Maybe an arbitrarily sized array? And how long is big enough for a string?

For anything where I’d like to provide a nice user experience, I do my own parsing and validation.

Thank you, all.

@certik I can do that but I prefer not. There’s a few dozen of the variables of various types. Plus, manually parsing gives me a reusable solution.

@urbanjost I can’t re-organize the namelist groups because the namelist is input to another application that I’m wrapping around.

@FortranFan Thank you but unfortunately none of that really applies to my case.

Not a pure Fortran approach, but it might be possible to use “f90nml” to
read the original namelist file, modify the “Namelist” object in Python,
and write it into another temporary namelist file for
use in the Fortran program. Such a “filtering” script may be written
in a general way, but I’m not sure if it’s possible because no experience…
(I guess the author of the package might have a nice idea :slight_smile:

1 Like

Thanks, @septc. I use f90nml a lot in production and love it, but for this specific task it’s overkill IMO.