Degenerate Conic

Algorithms • Modern Fortran Programming • Orbital Mechanics

Jun 13, 2021

JSON

json-fortran-logo

There are a lot a JSON libraries available for Fortran nowadays. The complete list, as far as I know is:

  • fson Fortran 95 JSON Parser. JSON-Fortran is a fork of this library. (started 2012).
  • YAJL-Fort A Modern Fortran Interface to YAJL. This one is an interface to a C library, and not pure Fortran. See also petaca. (started 2013).
  • JSON-Fortran A Fortran 2008 JSON API. This is my library. As far as I know, this was the first production-ready JSON parser written in modern Fortran. (started 2014).
  • fortjson JSON library written in Fortran 2003. Designed with portability across HPC architectures in mind. (started 2018).
  • jsonff JSON for Fortran. (started 2019).

Example

Here's an example of using JSON-Fortran to read in some data from a JSON string:

program test

 use json_module, wp => json_RK, ip => json_IK

 implicit none

 type(json_file) :: json
 integer(ip) :: t
 real(wp),dimension(:),allocatable :: x

 call json%deserialize('{"t": 1, "x": [2.0, 3.0, 4.0]}')

 call json%get('t', t); write(*,*) t
 call json%get('x', x); write(*,*) x

end program test

This prints:

           1
   2.00000000000000        3.00000000000000        4.00000000000000

Note that JSON-Fortran has all sorts of options for:

  • Using different real (real32, real64, and real128) and integer kinds (int8, int16, int32, and int64).
  • Controlling the JSON format for printing, including number of spaces for indenting, printing vectors on one line only, or full minification with no extra whitespace or line breaks.
  • Support for comments in a JSON file.
  • Multiple ways to get data from a JSON structure, such as RFC 6901 "JSON Pointer" paths or JSONPath) "bracket-notation".
  • Graceful handing of unusual inputs such as NaN or Infinity.
  • Thread safe error handling.

See also

Feb 05, 2018

JSON + SPICE

NAIF

I have mentioned various kinds of configuration file formats used in Fortran here before. One that I haven't mentioned is the text PCK file format used by the NAIF SPICE Toolkit. This is a format that is similar in some ways to Fortran namelists, but with a better API for reading the file and querying the contents. Variables read from a PCK file are inserted into the SPICE variable pool. An example PCK file (pck00010.tpc) can be found here.

The PCK file format has some limitations. It doesn't allow inline comments (only block comments separate from the variable declarations). Integers are stored as rounded doubles, and logical variables are not supported at all (you have to use 0.0 or 1.0 for this). One particular annoyance is that the files are not cross platform (the line breaks must match the platform they are being used on). However, SPICELIB also provides routines to programmatically enter variables into the pool. This allows us to create files in other formats that can be used in a SPICE application. For example, we can use JSON-Fortran to read variables in JSON files and insert them into the SPICE pool.

First, let's declare the interfaces to the SPICE routines we need (since SPICELIB is straight up Fortran 77, they are not in a module):

interface
    subroutine pcpool ( name, n, cvals )
    implicit none
    character(len=*) :: name
    integer :: n
    character(len=*) :: cvals ( * )
    end subroutine pcpool

    subroutine pdpool ( name, n, values )
    import :: wp
    implicit none
    character(len=*) :: name
    integer :: n
    real(wp) :: values ( * )
    end subroutine pdpool

    subroutine pipool ( name, n, ivals )
    implicit none
    character(len=*) :: name
    integer :: n
    integer :: ivals ( * )
    end subroutine pipool

    subroutine setmsg ( msg )
    implicit none
    character(len=*) :: msg
    end subroutine setmsg

    subroutine sigerr ( msg )
    implicit none
    character(len=*) :: msg
    end subroutine sigerr
end interface

Then, we can use the following routine:

subroutine json_to_spice(jsonfile)

implicit none

character(len=*),intent(in) :: jsonfile
!! the JSON file to load

integer :: i,j
type(json_core) :: json
type(json_value),pointer :: p,p_var,p_element
real(wp) :: real_val
integer :: var_type,int_val,n_vars,n_children,element_var_type
logical :: found
integer,dimension(:),allocatable :: int_vec
real(wp),dimension(:),allocatable :: real_vec
character(len=:),dimension(:),allocatable :: char_vec
character(len=:),allocatable :: char_val,name
integer,dimension(:),allocatable :: ilen

nullify(p)

! allow for // style comments:
call json%initialize(comment_char='/')

! read the file:
call json%parse(file=jsonfile, p=p)

if (json%failed()) then
    ! we will use the SPICE error handler:
    call setmsg ( 'json_to_spice: Could not load file: '&
                  trim(jsonfile) )
    call sigerr ( 'SPICE(INVALIDJSONFILE)' )
else

    ! how many variables are in the file:
    call json%info(p,n_children=n_vars)
    main : do i = 1, n_vars
        call json%get_child(p, i, p_var, found)

        ! what kind of variable is it?:
        call json%info(p_var,var_type=var_type,name=name)
        if (var_type == json_array) then

            ! how many elements in this array?:
            call json%info(p_var,n_children=n_children)

            ! first make sure all the variables are the same type
            ! [must be integer, real, or character]
            do j = 1, n_children
                call json%get_child(p_var, j, p_element, found)
                call json%info(p_element,var_type=element_var_type)
                if (j==1) then
                    var_type = element_var_type
                else
                    if (var_type /= element_var_type) then
                        call setmsg ( 'json_to_spice: Invalid array ('&
                                      trim(name)//') in file: '//trim(jsonfile) )
                                      call sigerr ( 'SPICE(INVALIDJSONVAR)' )
                        exit main
                    end if
                end if
            end do

            ! now we know the var type, so get as a vector:
            select case (var_type)
            case(json_integer); call json%get(p_var,int_vec)
            case(json_double ); call json%get(p_var,real_vec)
            case(json_string ); call json%get(p_var,char_vec,ilen)
            case default
                call setmsg ( 'json_to_spice: Invalid array ('&
                              trim(name)//') in file: '//trim(jsonfile) )
                call sigerr ( 'SPICE(INVALIDJSONVAR)' )
                exit main
            end select

        else

            ! scalar:
            n_children = 1
            select case (var_type)
            case(json_integer)
                call json%get(p_var,int_val); int_vec = [int_val]
            case(json_double )
                call json%get(p_var,real_val); real_vec = [real_val]
            case(json_string )
                call json%get(p_var,char_val); char_vec = [char_val]
            case default
                call setmsg ( 'json_to_spice: Invalid variable ('&
                              trim(name)//') in file: '//trim(jsonfile) )
                call sigerr ( 'SPICE(INVALIDJSONVAR)' )
                exit main
            end select

        end if

        ! now, add them to the pool:
        select case (var_type)
        case(json_integer)
            call pipool ( name, n_children, int_vec )
        case(json_double )
            call pdpool ( name, n_children, real_vec )
        case(json_string )
            call pcpool ( name, n_children, char_vec )
        end select

    end do main

end if

call json%destroy(p)

end subroutine json_to_spice

Here we are using the SPICE routines PIPOOL, PDPOOL, and PCPOOL to insert variables into the pool. We are also using the built-in SPICE error handling routines (SETMSG and SIGERR) to manage errors. The code works for scalar and array variables. It can be used to read the following example JSON file:

{
    "str": "qwerty", // a scalar string
    "strings": ["a", "ab", "abc", "d"], // a vector of strings
    "i": 8, // a scalar integer
    "ints": [255,127,0], // a vector of integers
    "r": 123.345, // a scalar real
    "reals": [999.345, 5671.8] // a vector of reals
}

After reading it, we can verify that the variables were added to the pool by printing the pool contents using the routine WRPOOL. This produces:

\begindata

str     = 'qwerty'
i       = 0.80000000000000000D+01
strings = ( 'a',
            'ab',
            'abc',
            'd' )
ints    = ( 0.25500000000000000D+03,
            0.12700000000000000D+03,
            0.00000000000000000D+00 )
r       = 0.12334500000000000D+03
reals   = ( 0.99934500000000003D+03,
            0.56718000000000002D+04 )

\begintext

See also

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

Apr 08, 2017

JSON-Fortran 5.3.0

json-fortran

JSON-Fortran 5.3.0 is out. This release includes a few minor bug fixes and a couple of new features. For one thing, it is now possible to easily build or modify a JSON structure without using pointer variables. Here's an example:

program test

use json_module, rk=>json_rk

implicit none

type(json_file) :: f

call f%initialize()

call f%add('name', 'test')
call f%add('inputs.t', 0.0_rk)
call f%add('inputs.x', [1.0_rk,2.0_rk,3.0_rk])
call f%add('outputs.t', 10.0_rk)
call f%add('outputs.x(1)', 11.0_rk)
call f%add('outputs.x(2)', 22.0_rk)
call f%add('outputs.x(3)', 33.0_rk)

call f%print_file()

call f%destroy()

end program test

As shown, the structure can be built by specifying the variable paths. This way, objects, vectors, vector elements, etc. can all be added. The result of this example is:

{
    "name": "test",
    "inputs": {
        "t": 0.0E+0,
        "x": [
            0.1E+1,
            0.2E+1,
            0.3E+1
        ]
    },
    "outputs": {
        "t": 0.1E+2,
        "x": [
            0.11E+2,
            0.22E+2,
            0.33E+3
        ]
    }
}

So now, in addition to the previous methods of building a JSON structure (reading it from a file, reading it from a string, or building it yourself using pointer variables), there is now another way. Each method has its uses for different applications. Building it from the path strings can be very convenient and also opens up the possibility of easy conversion between a Fortran namelist and a JSON file. I'll show an example of this in a future post. In a previous post, I showed how to do the reverse (JSON to namelist).

JSON-Fortran is my most popular GitHub project (70 stars as of today). It usually makes it to GitHub's monthly "trending" Fortran projects page. I'm always interested to hear about what people are using it for. I added a page on the wiki to list some of the projects that use it, so if you're using it, feel free to add your project to the list.

Mar 05, 2017

Latest Library Updates

I just released some updates to my two most popular Fortran libraries on GitHub: JSON-Fortran and bspline-fortran. Coincidently, both are now at v5.2.0. Details of the updates are:

JSON-Fortran

json-fortran

There are several new features in this release. The biggest update is that now the code can parse JSON files that include comments (it just ignores them). You can even specify the character that identifies a comment. For example, if using # as a comment character, the following file can now be parsed just fine:

{
    "t": 0.12345,  # this is the time
    "x": 123.7173  # this is the state
}

Technically, comments are not part of the JSON standard. Douglas Crockford, the creator of JSON, had his reasons [1] for not including them, which I admit I don't understand (something about parsing directives and interoperability?) I mainly use JSON for configuration files, where it is nice to have comments. Crockford's suggestion for this use case is to pipe your commented JSON files through something called JSMin before parsing, a solution which seems somewhat ridiculous for Fortran users. So, never fear, now we can have comments in our JSON files and continue not using JavaScript for anything.

Another big change is the addition of support for the RFC 6901 "JSON Pointer" path specification [2]. This can be used to retrieve data from a JSON structure using its path. Formerly, JSON-Fortran used a simple path specification syntax, which broke down if the keys contained special characters such as ( or ). The new way works for all keys.

Bspline-Fortran

bspline_extrap_test

A minor update to Bspline-Fortran is the addition of an extrapolation mode. Formerly, if an interpolation was requested outside the bounds of the data, an error was returned. Now, the user has the option of enabling extrapolation.

See also

  1. D. Crockford, "Comments in JSON", Apr 30, 2012 [Google Plus]
  2. JavaScript Object Notation (JSON) Pointer, RFC 6901, April 2013 [IETF]

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

May 09, 2016

JSON-Fortran 5.0

json-fortran

JSON-Fortran 5.0 is out. This release finally brings thread-safety to the library. Note that it does break backward compatibility with previous versions, but hopefully it isn't too much trouble to modify your code to be compatible with the new release. I've provided a short guide describing what you need to do.

JSON-Fortran is a Fortran 2008 JSON API, based on an earlier project called FSON (which was written in Fortran 95). FSON was not thread-safe, and so neither was JSON-Fortran at first. This was mainly due to the use of various global settings, and global variables used during parsing and for keeping track of errors.

In the transition from FSON to JSON-Fortran, I added a high-level json_file class that is used to do a lot of common operations (e.g. open a JSON file and read data from it). However, building a JSON structure from scratch is done using lower-level json_value pointers. In the 5.0 release, there is a new factory class called json_core that is now the interface for manipulating json_value variables. Thus, each instance of this class can exist independently of any others (each with potentially different settings), and so provides thread-safe operation and error handling. The json_file class simply contains an instance of json_core, which contains all the variables and settings that were formerly global to the entire module.

A very simple example of the pre-5.0 usage would be:

program test
use json_module
implicit none
type(json_file) :: json
integer :: ival
character(len=:),allocatable :: cval
logical :: found
call json_initialize()
call json%load_file(filename='myfile.json')
call json%print_file() !print to the console
call json%get('var.i',ival,found)
call json%get('var.c',cval,found)
call json%destroy()
end program test

For 5.0, all you have to do is change:

call json_initialize()

to

call json%initialize()

and you're done. All global variables have been eliminated and the only entities that are user-accessible are three public types and their methods.

There are also a ton of other new features in JSON-Fortran 5.0, including new APIs, such as:

  • json_core%validate() -- test the validity of a JSON structure (i.e., a json_value linked list).
  • json_core%is_child_of() -- test if one json_value is a child of another.
  • json_core%swap() -- swap two json_value elements in a JSON structure (this may be useful for sorting purposes).
  • json_core%rename() -- rename a json_value variable in a JSON structure.

And new settings (set during the call to initialize()) such as:

  • Trailing spaces can now be significant for name comparisons.
  • Name comparisons can now be case sensitive or case insensitive.
  • Can enable strict type checking to avoid automatic conversion of numeric data (say, integer to double) when getting data from a JSON structure.
  • Can set the number of spaces for indenting when writing JSON data to a file.

See also

Aug 05, 2015

JSON-Fortran 4.2

json-fortran

The 4.2.0 release of the JSON-Fortran library is now available on GitHub. This version has a few new features and a couple of minor bug fixes. The source code documentation is also now produced by FORD, which is a great new tool for modern Fortran documentation. It has been out for less than a year and is already far better than other tools that have been around for years. See an example of the output here.

Mar 16, 2015

json-fortran 4.0.0

json-fortran-logo-250px

I just tagged the 4.0.0 release of json-fortran. This is the first release with Unicode support (thanks to Izaak Beekman). Who says there are no good open source Fortran projects on the internet?

The Unicode build of the library is optional (and only enabled using the preprocessor directive USE_UCS4). Currently, this only works with Gfortran. It doesn't yet work with the Intel Fortran Compiler, which is lagging behind on Unicode support. The Fortran standard supports Unicode via the selected_char_kind function, which can be used to specify the character set used for a character string, like so:

integer,parameter :: u = selected_char_kind('ISO_10646')
character(kind=u,len=11) :: string = u_'Hello World'

Jul 23, 2014

Next → Page 1 of 2