json_file Derived Type

type, public :: json_file

type~~json_file~~InheritsGraph type~json_file json_file type~json_value json_value type~json_value->type~json_file p type~json_value->type~json_value previous, next, parent, children, tail
Help


The json_file is the main public class that is used to open a file and get data from it.

Example

    program test
    use json_module
    implicit none
    type(json_file) :: json
    integer :: ival
    real(real64) :: rval
    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.r(3)',rval,found)
    call json%get('var.c',cval,found)
    call json%destroy()
    end program test

Components

TypeVisibility AttributesNameInitial
type(json_value), private, pointer:: p=> null()

the JSON structure read from the file


Constructor

private interface json_file

Structure constructor to initialize a json_file object with an existing json_value object

  • private function initialize_json_file(p) result(file_object)

    Arguments

    Type IntentOptional AttributesName
    type(json_value), intent(in), optional pointer:: p

    json_value object to cast as a json_file object

    Return Value type(json_file)

    Description

    Author
    Izaak Beekman
    Date
    07/23/2015

    Cast a json_value object as a json_file object


Type-Bound Procedures

procedure, public :: load_file => json_file_load

  • private subroutine json_file_load(me, filename, unit)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CDK,len=*), intent(in) :: filename

    the filename to open

    integer(kind=IK), intent(in), optional :: unit

    the unit number to use (if not present, a newunit is used)

    Description

    Author
    Jacob Williams
    Date
    12/9/2013

    Load the JSON data from a file.

generic, public :: load_from_string => json_file_load_from_string

  • private subroutine json_file_load_from_string(me, str)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: str

    string to load JSON data from

    Description

    Author
    Jacob Williams
    Date
    1/13/2015

    Load the JSON data from a string.

procedure, public :: destroy => json_file_destroy

  • private subroutine json_file_destroy(me)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me

    Description

    Author
    Jacob Williams
    Date
    12/9/2013

    Destroy the json_file.

procedure, public :: move => json_file_move_pointer

  • private subroutine json_file_move_pointer(to, from)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: to
    class(json_file), intent(inout) :: from

    Description

    Author
    Jacob Williams
    Date
    12/5/2014

    Move the json_value pointer from one json_file to another. The "from" pointer is then nullified, but not destroyed.

generic, public :: info => json_file_variable_info

  • private subroutine json_file_variable_info(me, path, found, var_type, n_children)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: path

    path to the variable

    logical(kind=LK), intent(out) :: found

    the variable exists in the structure

    integer(kind=IK), intent(out) :: var_type

    variable type

    integer(kind=IK), intent(out) :: n_children

    number of children

    Description

    Author
    Jacob Williams
    Date
    2/3/2014

    Returns information about a variable in a json_file.

procedure, public :: print_to_string => json_file_print_to_string

  • private subroutine json_file_print_to_string(me, str)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=:), intent(out), allocatable:: str

    string to print JSON data to

    Description

    Author
    Jacob Williams
    Date
    1/11/2015

    Print the JSON file to a string.

  • private subroutine json_file_print_to_console(me)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me

    Description

    Author
    Jacob Williams
    Date
    1/11/2015

    Print the JSON file to the console.

  • private subroutine json_file_print_1(me, iunit)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    integer(kind=IK), intent(in) :: iunit

    file unit number (must not be -1)

    Description

    Author
    Jacob Williams
    Date
    12/9/2013

    Prints the JSON file to the specified file unit number.

  • private subroutine json_file_print_2(me, filename)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CDK,len=*), intent(in) :: filename

    filename to print to

    Description

    Author
    Jacob Williams
    Date
    1/11/2015

    Print the JSON structure to the specified filename. The file is opened, printed, and then closed.

  • private subroutine json_file_get_object(me, path, p, found)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: path

    the path to the variable

    type(json_value), intent(out), pointer:: p

    pointer to the variable

    logical(kind=LK), intent(out), optional :: found

    if it was really found

    Description

    Author
    Jacob Williams
    Date
    2/3/2014

    Get a json_value pointer to an object from a JSON file.

  • private subroutine json_file_get_integer(me, path, val, found)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: path

    the path to the variable

    integer(kind=IK), intent(out) :: val

    value

    logical(kind=LK), intent(out), optional :: found

    if it was really found

    Description

    Author
    Jacob Williams
    Date
    12/9/2013

    Get an integer value from a JSON file.

  • private subroutine json_file_get_double(me, path, val, found)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: path
    real(kind=RK), intent(out) :: val
    logical(kind=LK), intent(out), optional :: found

    Description

    Author
    Jacob Williams
    Date
    12/9/2013

    Get a real(RK) variable value from a JSON file.

  • private subroutine json_file_get_logical(me, path, val, found)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: path
    logical(kind=LK), intent(out) :: val
    logical(kind=LK), intent(out), optional :: found

    Description

    Author
    Jacob Williams
    Date
    12/9/2013

    Get a logical(LK) value from a JSON file.

  • private subroutine json_file_get_string(me, path, val, found)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: path
    character(kind=CK,len=:), intent(out), allocatable:: val
    logical(kind=LK), intent(out), optional :: found

    Description

    Author
    Jacob Williams
    Date
    12/9/2013

    Get a character string from a json file. The output val is an allocatable character string.

  • private subroutine json_file_get_integer_vec(me, path, vec, found)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: path

    the path to the variable

    integer(kind=IK), intent(out), dimension(:), allocatable:: vec

    the value vector

    logical(kind=LK), intent(out), optional :: found

    if it was really found

    Description

    Author
    Jacob Williams
    Date
    1/20/2014

    Get an integer vector from a JSON file.

  • private subroutine json_file_get_double_vec(me, path, vec, found)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: path
    real(kind=RK), intent(out), dimension(:), allocatable:: vec
    logical(kind=LK), intent(out), optional :: found

    Description

    Author
    Jacob Williams
    Date
    1/19/2014

    Get a real(RK) vector from a JSON file.

  • private subroutine json_file_get_logical_vec(me, path, vec, found)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: path
    logical(kind=LK), intent(out), dimension(:), allocatable:: vec
    logical(kind=LK), intent(out), optional :: found

    Description

    Author
    Jacob Williams
    Date
    1/20/2014

    Get a logical(LK) vector from a JSON file.

  • private subroutine json_file_get_string_vec(me, path, vec, found)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: path
    character(kind=CK,len=*), intent(out), dimension(:), allocatable:: vec
    logical(kind=LK), intent(out), optional :: found

    Description

    Author
    Jacob Williams
    Date
    1/19/2014

    Get a string vector from a JSON file.

  • private subroutine json_file_get_root(me, p)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    type(json_value), intent(out), pointer:: p

    pointer to the variable

    Description

    Author
    Izaak Beekman
    Date
    7/23/2015

    Get a json_value pointer to the JSON file root.

  • private subroutine json_file_update_integer(me, name, val, found)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: name
    integer(kind=IK), intent(in) :: val
    logical(kind=LK), intent(out) :: found

    Description

    Author
    Jacob Williams
    Date
    1/10/2015

    Given the path string, if the variable is present in the file, and is a scalar, then update its value. If it is not present, then create it and set its value.

  • private subroutine json_file_update_logical(me, name, val, found)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: name
    logical(kind=LK), intent(in) :: val
    logical(kind=LK), intent(out) :: found

    Description

    Author
    Jacob Williams
    Date
    1/10/2015

    Given the path string, if the variable is present in the file, and is a scalar, then update its value. If it is not present, then create it and set its value.

  • private subroutine json_file_update_real(me, name, val, found)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: name
    real(kind=RK), intent(in) :: val
    logical(kind=LK), intent(out) :: found

    Description

    Author
    Jacob Williams
    Date
    1/10/2015

    Given the path string, if the variable is present in the file, and is a scalar, then update its value. If it is not present, then create it and set its value.

  • private subroutine json_file_update_string(me, name, val, found)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: name
    character(kind=CK,len=*), intent(in) :: val
    logical(kind=LK), intent(out) :: found

    Description

    Author
    Jacob Williams
    Date
    1/10/2015

    Given the path string, if the variable is present in the file, and is a scalar, then update its value. If it is not present, then create it and set its value.

procedure, public :: json_file_load_from_string

  • private subroutine json_file_load_from_string(me, str)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: str

    string to load JSON data from

    Description

    Author
    Jacob Williams
    Date
    1/13/2015

    Load the JSON data from a string.

procedure, public :: json_file_variable_info

  • private subroutine json_file_variable_info(me, path, found, var_type, n_children)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: path

    path to the variable

    logical(kind=LK), intent(out) :: found

    the variable exists in the structure

    integer(kind=IK), intent(out) :: var_type

    variable type

    integer(kind=IK), intent(out) :: n_children

    number of children

    Description

    Author
    Jacob Williams
    Date
    2/3/2014

    Returns information about a variable in a json_file.

procedure, public :: json_file_get_object

  • private subroutine json_file_get_object(me, path, p, found)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: path

    the path to the variable

    type(json_value), intent(out), pointer:: p

    pointer to the variable

    logical(kind=LK), intent(out), optional :: found

    if it was really found

    Description

    Author
    Jacob Williams
    Date
    2/3/2014

    Get a json_value pointer to an object from a JSON file.

procedure, public :: json_file_get_integer

  • private subroutine json_file_get_integer(me, path, val, found)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: path

    the path to the variable

    integer(kind=IK), intent(out) :: val

    value

    logical(kind=LK), intent(out), optional :: found

    if it was really found

    Description

    Author
    Jacob Williams
    Date
    12/9/2013

    Get an integer value from a JSON file.

procedure, public :: json_file_get_double

  • private subroutine json_file_get_double(me, path, val, found)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: path
    real(kind=RK), intent(out) :: val
    logical(kind=LK), intent(out), optional :: found

    Description

    Author
    Jacob Williams
    Date
    12/9/2013

    Get a real(RK) variable value from a JSON file.

procedure, public :: json_file_get_logical

  • private subroutine json_file_get_logical(me, path, val, found)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: path
    logical(kind=LK), intent(out) :: val
    logical(kind=LK), intent(out), optional :: found

    Description

    Author
    Jacob Williams
    Date
    12/9/2013

    Get a logical(LK) value from a JSON file.

procedure, public :: json_file_get_string

  • private subroutine json_file_get_string(me, path, val, found)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: path
    character(kind=CK,len=:), intent(out), allocatable:: val
    logical(kind=LK), intent(out), optional :: found

    Description

    Author
    Jacob Williams
    Date
    12/9/2013

    Get a character string from a json file. The output val is an allocatable character string.

procedure, public :: json_file_get_integer_vec

  • private subroutine json_file_get_integer_vec(me, path, vec, found)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: path

    the path to the variable

    integer(kind=IK), intent(out), dimension(:), allocatable:: vec

    the value vector

    logical(kind=LK), intent(out), optional :: found

    if it was really found

    Description

    Author
    Jacob Williams
    Date
    1/20/2014

    Get an integer vector from a JSON file.

procedure, public :: json_file_get_double_vec

  • private subroutine json_file_get_double_vec(me, path, vec, found)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: path
    real(kind=RK), intent(out), dimension(:), allocatable:: vec
    logical(kind=LK), intent(out), optional :: found

    Description

    Author
    Jacob Williams
    Date
    1/19/2014

    Get a real(RK) vector from a JSON file.

procedure, public :: json_file_get_logical_vec

  • private subroutine json_file_get_logical_vec(me, path, vec, found)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: path
    logical(kind=LK), intent(out), dimension(:), allocatable:: vec
    logical(kind=LK), intent(out), optional :: found

    Description

    Author
    Jacob Williams
    Date
    1/20/2014

    Get a logical(LK) vector from a JSON file.

procedure, public :: json_file_get_string_vec

  • private subroutine json_file_get_string_vec(me, path, vec, found)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: path
    character(kind=CK,len=*), intent(out), dimension(:), allocatable:: vec
    logical(kind=LK), intent(out), optional :: found

    Description

    Author
    Jacob Williams
    Date
    1/19/2014

    Get a string vector from a JSON file.

procedure, public :: json_file_get_root

  • private subroutine json_file_get_root(me, p)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    type(json_value), intent(out), pointer:: p

    pointer to the variable

    Description

    Author
    Izaak Beekman
    Date
    7/23/2015

    Get a json_value pointer to the JSON file root.

procedure, public :: json_file_update_integer

  • private subroutine json_file_update_integer(me, name, val, found)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: name
    integer(kind=IK), intent(in) :: val
    logical(kind=LK), intent(out) :: found

    Description

    Author
    Jacob Williams
    Date
    1/10/2015

    Given the path string, if the variable is present in the file, and is a scalar, then update its value. If it is not present, then create it and set its value.

procedure, public :: json_file_update_logical

  • private subroutine json_file_update_logical(me, name, val, found)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: name
    logical(kind=LK), intent(in) :: val
    logical(kind=LK), intent(out) :: found

    Description

    Author
    Jacob Williams
    Date
    1/10/2015

    Given the path string, if the variable is present in the file, and is a scalar, then update its value. If it is not present, then create it and set its value.

procedure, public :: json_file_update_real

  • private subroutine json_file_update_real(me, name, val, found)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: name
    real(kind=RK), intent(in) :: val
    logical(kind=LK), intent(out) :: found

    Description

    Author
    Jacob Williams
    Date
    1/10/2015

    Given the path string, if the variable is present in the file, and is a scalar, then update its value. If it is not present, then create it and set its value.

procedure, public :: json_file_update_string

  • private subroutine json_file_update_string(me, name, val, found)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CK,len=*), intent(in) :: name
    character(kind=CK,len=*), intent(in) :: val
    logical(kind=LK), intent(out) :: found

    Description

    Author
    Jacob Williams
    Date
    1/10/2015

    Given the path string, if the variable is present in the file, and is a scalar, then update its value. If it is not present, then create it and set its value.

procedure, public :: json_file_print_to_console

  • private subroutine json_file_print_to_console(me)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me

    Description

    Author
    Jacob Williams
    Date
    1/11/2015

    Print the JSON file to the console.

procedure, public :: json_file_print_1

  • private subroutine json_file_print_1(me, iunit)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    integer(kind=IK), intent(in) :: iunit

    file unit number (must not be -1)

    Description

    Author
    Jacob Williams
    Date
    12/9/2013

    Prints the JSON file to the specified file unit number.

procedure, public :: json_file_print_2

  • private subroutine json_file_print_2(me, filename)

    Arguments

    Type IntentOptional AttributesName
    class(json_file), intent(inout) :: me
    character(kind=CDK,len=*), intent(in) :: filename

    filename to print to

    Description

    Author
    Jacob Williams
    Date
    1/11/2015

    Print the JSON structure to the specified filename. The file is opened, printed, and then closed.

Source Code

    type,public :: json_file

        private

        type(json_value),pointer :: p => null()  !! the JSON structure read from the file

    contains

        procedure,public :: load_file => json_file_load

        generic,  public :: load_from_string => MAYBEWRAP(json_file_load_from_string)

        procedure,public :: destroy => json_file_destroy
        procedure,public :: move    => json_file_move_pointer
        generic,public   :: info    => MAYBEWRAP(json_file_variable_info)

        procedure,public :: print_to_string => json_file_print_to_string

        generic,public :: print_file => json_file_print_to_console, &
                                        json_file_print_1, &
                                        json_file_print_2

        generic,public :: get => MAYBEWRAP(json_file_get_object),      &
                                 MAYBEWRAP(json_file_get_integer),     &
                                 MAYBEWRAP(json_file_get_double),      &
                                 MAYBEWRAP(json_file_get_logical),     &
                                 MAYBEWRAP(json_file_get_string),      &
                                 MAYBEWRAP(json_file_get_integer_vec), &
                                 MAYBEWRAP(json_file_get_double_vec),  &
                                 MAYBEWRAP(json_file_get_logical_vec), &
                                 MAYBEWRAP(json_file_get_string_vec),  &
                                 json_file_get_root

        generic,public :: update =>  MAYBEWRAP(json_file_update_integer),  &
                                     MAYBEWRAP(json_file_update_logical),  &
                                     MAYBEWRAP(json_file_update_real),     &
                                     MAYBEWRAP(json_file_update_string)
#     ifdef USE_UCS4
        generic,public :: update => json_file_update_string_name_ascii, &
                                    json_file_update_string_val_ascii
#     endif

        !load from string:
        procedure :: MAYBEWRAP(json_file_load_from_string)

        !git info:
        procedure :: MAYBEWRAP(json_file_variable_info)

        !get:
        procedure :: MAYBEWRAP(json_file_get_object)
        procedure :: MAYBEWRAP(json_file_get_integer)
        procedure :: MAYBEWRAP(json_file_get_double)
        procedure :: MAYBEWRAP(json_file_get_logical)
        procedure :: MAYBEWRAP(json_file_get_string)
        procedure :: MAYBEWRAP(json_file_get_integer_vec)
        procedure :: MAYBEWRAP(json_file_get_double_vec)
        procedure :: MAYBEWRAP(json_file_get_logical_vec)
        procedure :: MAYBEWRAP(json_file_get_string_vec)
        procedure :: json_file_get_root

        !update:
        procedure :: MAYBEWRAP(json_file_update_integer)
        procedure :: MAYBEWRAP(json_file_update_logical)
        procedure :: MAYBEWRAP(json_file_update_real)
        procedure :: MAYBEWRAP(json_file_update_string)
#     ifdef USE_UCS4
        procedure :: json_file_update_string_name_ascii
        procedure :: json_file_update_string_val_ascii
#     endif

        !print_file:
        procedure :: json_file_print_to_console
        procedure :: json_file_print_1
        procedure :: json_file_print_2

    end type json_file