Degenerate Conic

Algorithms • Modern Fortran Programming • Orbital Mechanics

May 07, 2017

Fortran Configuration File Formats

formats3

String and file manipulation in Fortran isn't as bad as you've heard (OK, it's bad, but it's getting better). Sure, modern Fortran only provides the bare minimum of features for this sort of thing out of the box, but various libraries are starting to appear that the modern Fortran programmer can use to deal with a range of different file formats including JSON, INI, CSV, XML, etc. The Fortran user community has been late to the game on this opensource thing. But it does exist and I encourage all Fortraners to use it. You don't have to roll your own file format or write your own parser. If the existing libraries don't have what you need, then help to improve them.

The following is a look at a few different options for configuration files in your Fortran program. It is limited to text files. For binary files, I would highly recommend a standard cross-platform format (such as HDF5). For goodness' sake, do not invent your own binary file format.

Namelists

Fortran namelists are very old-school, but are still part of the standard (indeed this is the only high-level file read/write feature that is built into Fortran). Namelist have a few advantages, but they are generally outweighed by their many disadvantages. Some advantages include:

  • It is super easy to use. The reading and writing of the file is automatically handled by the compiler. A namelist is declared like so:
integer :: a
real :: b
character(len=5) :: c
integer :: iunit,istat

namelist /blah/ a,b,c

!set values:
a = 1
b = 2.0
c = 'three'

and can be written by:

write(unit=iunit, nml=blah, iostat=istat)

Which produces a file like this:

&BLAH
A= 1,
B= 2.00000000 ,
C="three",
/

The file can be read by:

read(unit=iunit, nml=blah, iostat=istat)
  • It automatically handles any Fortran variables you throw at it (including multidimensional arrays and derived data types).
  • Variables in the file can be optional. Any variable not present in the file retains the value it had before the namelist was read.

Disadvantages include:

  • Different compilers can and will output slightly different formats, and you have absolutely no control over that.
  • If you want to generate or manipulate your input files using a different language, you'll probably have to write your own parser to do it. Hardly any other programming language will have a decent namelist parser or writer available. A notable exception is f90nml, a great Python library for reading and writing namelists.
  • The variables in the file must exactly correspond (in name, type, and size) to variables in the code. This turn out to be very restrictive for a lot of reasons. For one thing, it is quite annoying for strings, since it requires you to specify a maximum string length in the variable declaration.
  • It can be difficult to diagnose errors when reading the file (e.g, a syntax error, an unrecognized variable, or an array size or string length larger than the Fortran variable). The compiler will usually just throw an I/O error if anything goes wrong. However, it is possible on some compilers to retrieve the line where the error occurred by rewinding one line and then reading it with a normal READ statement.
  • It is difficult to tell if a variable is actually present in the file (if one isn't there, then the corresponding variable in the code will just retain whatever value it had before the read was attempted. Thus, the only real way to check if a variable was present or not is to initialize them all to unusual values, and then check for this after the read.)

In my view, there is little reason to start using namelists at this point, since there are now better options available. Unless you have a legacy code that is using them which can't be changed, I would recommend using something else.

JSON

JSON stands for JavaScript Object Notation, and is a very popular and lightweight data-interchange format. There is an interface for practically all known programming languages, including modern Fortran. My JSON-Fortran library was built on an older Fortran 95 library, which I forked in order to be able to use some of the newer Fortran 2003/2008 features. With JSON-Fortran, the example above would be:

type(json_file) :: json
call json%add('blah.a',1)
call json%add('blah.b',2.0)
call json%add('blah.c','three')

Which produces the JSON file:

{
    "blah": {
        "a": 1,
        "b": 2.0,
        "c": "three"
    }
}

Note that f90nml can also be used to transition away from namelists by converting them to JSON using Python. To go from a namelist to JSON, all you have to do is this:

import f90nml
import json
n = f90nml.read('my_namelist.nml')
with open('my_namelist.json', 'w') as outfile:
json.dump(n, outfile, sort_keys = True, indent = 4)

Using my JSON-Fortran library, you can even convert a JSON file back into a Namelist if that sort of thing is your bag (as shown in a previous post). One disadvantage of JSON is that the standard does not allow for comments in the file. However, some parsers include support for comments (including JSON-Fortran).

INI

INI is a simple, easy-to-write format. Although not really standardized, it is based on the old MS-DOS initialization files. For modern Fortran, the FiNeR library provides a Fortran interface. The INI version of the above file would be:

[blah]
a=1
b=2.0
c=three

Here's an example of converting an INI file to a JSON file (using FiNeR and JSON-Fortran):

subroutine ini2json(ini_filename, json)

use json_module
use finer

implicit none

character(len=*),intent(in) :: ini_filename
type(json_file),intent(out) :: json

type(file_ini) :: ini
integer :: ierr
integer :: i
character(len=:),dimension(:),allocatable :: secs
character(len=:),dimension(:),allocatable :: opts

call ini%load(filename=ini_filename,error=ierr)
call ini%get_sections_list(secs)
do i=1,size(secs)
    do
        if (.not. ini%loop(trim(secs(i)),opts)) exit
        call json%add(trim(secs(i))//'.'&
                    trim(opts(1)),trim(opts(2)))
    end do
end do
call ini%free()

end subroutine ini2json

You could call this routine like so:

program main
use ini2json_module
use json_module
implicit none
type(json_file) :: json
call ini2json('test.ini',json)
call json%print_file()
call json%destroy()
end program main

And it would produce the following result for the file above:

{
    "blah": {
        "a": "1",
        "b": "2.0",
        "c": "three"
    }
}

Note that, in this example, all the variables are returned as strings (getting the numerical values as numbers is left as an exercise to the reader).

Others

file_extensions

  • XML (Extensible Markup Language) -- I never really liked this one because it is not easily human readable or editable. There are some Fortran XML parsers out there, though.
  • YAML (YAML Ain't Markup Language) -- I'm not as familiar with this one (also I hate recursive acronyms). There is a Fortran interface to it called fortran-yaml, but I haven't tried it.
  • TOML (Tom's Obvious, Minimal Language) - I'm not aware of a Fortran parser for this one. This one was created by one of the founders of GitHub.
  • Lua - Another interesting possibility is for your configuration file to be written in a full-up scripting language. There are a couple of Lua-Fortran interfaces out there (e.g., AOTUS).

See also

Aug 27, 2016

JSON-Fortran 5.1

json-fortran

JSON-Fortran 5.1 is out. There are several new features in this release. I added a get_path() routine that can be used to return the path of a variable in a JSON structure. This can be used along with the traverse() routine to do something pseudointeresting: convert a JSON file into a Fortran namelist file. Why would anyone want to do that, you ask? Who knows. Consider the following example:

program why

    use json_module

    implicit none

    type(json_core) :: json
    type(json_value), pointer :: p
    integer :: iunit !! file unit

    open (newunit=iunit, file='data.nml', status='REPLACE')
    write (iunit, '(A)') '&DATA'
    call json%initialize()
    call json%parse(file='data.json', p=p)
    call json%traverse(p, print_json_variable)
    write (iunit, '(A)') '/'
    close (iunit)

contains

    subroutine print_json_variable(json, p, finished)

        !! A `traverse` routine for printing out all
        !! the variables in a JSON structure.

        implicit none

        class(json_core), intent(inout) :: json
        type(json_value), pointer, intent(in) :: p
        logical(json_LK), intent(out) :: finished

        character(kind=json_CK, len=:), allocatable :: path
        character(kind=json_CK, len=:), allocatable :: value
        logical(json_LK) :: found
        type(json_value), pointer :: child
        integer(json_IK) :: var_type

        call json%get_child(p, child)
        finished = .false.

        !only print the leafs:
        if (.not. associated(child)) then
            !fortran-style:
            call json%get_path(p, path, found, &
                               use_alt_array_tokens=.true., &
                               path_sep=json_CK_'%')
            if (found) then
                call json%info(p, var_type=var_type)
                select case (var_type)
                case (json_array, json_object)
                    !an empty array or object
                    !don't print anything
                    return
                case (json_string)
                    ! note: strings are returned escaped
                    ! without quotes
                    call json%get(p, value)
                    value = '"'//value//'"'
                case default
                    ! get the value as a string
                    ! [assumes strict_type_checking=false]
                    call json%get(p, value)
                end select
                !check for errors:
                if (json%failed()) then
                    finished = .true.
                else
                    write (iunit, '(A)') &
                        path//json_CK_' = '//value//','
                end if
            else
                finished = .true.
            end if
        end if

    end subroutine print_json_variable

end program why

Here, we are simply traversing the entire JSON structure, and printing out the paths of the leaf nodes using a namelist-style syntax. For the example JSON file:

{
    "t": 0.0,
    "x": [1.0, 2.0, 3.0],
    "m": 2000.0,
    "name": "foo"
}

This program will produce the following namelist file:

&DATA
t = 0.0E+0,
x(1) = 0.1E+1,
x(2) = 0.2E+1,
x(3) = 0.3E+1,
m = 0.2E+4,
name = "foo",
/

Which could be read using the following Fortran program:

program namelist_test

use iso_fortran_env, only: wp => real64

implicit none

real(wp) :: t,m,x(3)
integer :: iunit,istat
character(len=10) :: name

! define the namelist:
namelist /DATA/ t,x,m,name

! read the namelist:
open(newunit=iunit,file='data.nml',status='OLD')
read(unit=iunit,nml=DATA,iostat=istat)
close(unit=iunit)

end program namelist_test

There is also a new minification option for printing a JSON structure with no extra whitespace. For example:

{"t":0.0E+0,"x":[0.1E+1,0.2E+1,0.3E+1],"m":0.2E+4,"name":"foo"}

See also

  • f90nml -- A Python module for parsing Fortran namelist files

Mar 14, 2016

Namelist Error Checking

Fortran namelists are a quick and dirty way of reading and writing variables to and from a file. It is actually the only high-level file access feature built into the Fortran language, in the sense of being able to read and write a complex formatted file with one line of code. Nowadays, I would recommend against using this feature since the format is not really a standard and varies from compiler to compiler, and there aren't good parsers available for other languages (with the notable exception of Python). There are better configuration file formats available today such as JSON. However, namelists can still be encountered in legacy applications, and may still be useful to the lazy programmer.

One of the problems with namelists is that all the variables in the file have to correspond exactly in name, type, rank, and size to variables declared in your code. Syntax errors in the file are not easily detected and a failed read due to an unexpected variable will usually just return a non-zero status code that isn't really much help in diagnosing the problem.

However, there is a way to output the line where the failure occurred on a namelist read, which can be quite useful for debugging. Say your code is expecting a namelist containing three real variables a, b, and c. However, the file contains the unexpected variable d like so:

&my_namelist
 a = 1.0,
 b = 2.0,
 d = 3.0,
 c = 4.0
/

Now consider the following Fortran code to read it:

program namelist_test

use iso_fortran_env, wp => real64

implicit none

real(wp) :: a,b,c ! namelist variables
integer :: istat,iunit
character(len=1000) :: line

namelist /my_namelist/ a,b,c

open(newunit=iunit,file='my_namelist.nml',&
    status='OLD')

read(iunit, nml=my_namelist, iostat=istat)

if (istat/=0) then
    backspace(iunit)
    read(iunit,fmt='(A)') line
    write(error_unit,'(A)') &
        'Invalid line in namelist: '//trim(line)
end if

close(iunit)

end program namelist_test

The READ statement will fail with a non-zero istat code. Then we simply use the BACKSPACE function, which moves the file position back one record (the record where the read failed). Then we can simply read this line and print it. This code produces the following error message:

 Invalid line in namelist: d = 3.0,