Degenerate Conic

Algorithms • Modern Fortran Programming • Orbital Mechanics

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