!***************************************************************************************** !> author: Jacob Williams ! license: BSD ! ! This module provides a low-level interface for manipulation of JSON data. ! The two public entities are [[json_value]], and [[json_core(type)]]. ! The [[json_file_module]] provides a higher-level interface to some ! of these routines. ! !## License ! * JSON-Fortran is released under a BSD-style license. ! See the [LICENSE](https://github.com/jacobwilliams/json-fortran/blob/master/LICENSE) ! file for details. module json_value_module use,intrinsic :: iso_fortran_env, only: iostat_end,error_unit,output_unit use json_kinds use json_parameters use json_string_utilities implicit none private #include "json_macros.inc" !********************************************************* !> ! If Unicode is not enabled, then ! JSON files are opened using access='STREAM' and ! form='UNFORMATTED'. This allows the file to ! be read faster. ! #ifdef USE_UCS4 logical,parameter :: use_unformatted_stream = .false. #else logical,parameter :: use_unformatted_stream = .true. #endif !********************************************************* !********************************************************* !> ! If Unicode is not enabled, then ! JSON files are opened using access='STREAM' and ! form='UNFORMATTED'. This allows the file to ! be read faster. ! #ifdef USE_UCS4 character(kind=CDK,len=*),parameter :: access_spec = 'SEQUENTIAL' #else character(kind=CDK,len=*),parameter :: access_spec = 'STREAM' #endif !********************************************************* !********************************************************* !> ! If Unicode is not enabled, then ! JSON files are opened using access='STREAM' and ! form='UNFORMATTED'. This allows the file to ! be read faster. ! #ifdef USE_UCS4 character(kind=CDK,len=*),parameter :: form_spec = 'FORMATTED' #else character(kind=CDK,len=*),parameter :: form_spec = 'UNFORMATTED' #endif !********************************************************* !********************************************************* !> ! Type used to construct the linked-list JSON structure. ! Normally, this should always be a pointer variable. ! This type should only be used by an instance of [[json_core(type)]]. ! !### Example ! ! The following test program: ! !````fortran ! program test ! use json_module ! implicit none ! type(json_core) :: json ! type(json_value),pointer :: p ! call json%create_object(p,'') !create the root ! call json%add(p,'year',1805) !add some data ! call json%add(p,'value',1.0_RK) !add some data ! call json%print(p,'test.json') !write it to a file ! call json%destroy(p) !cleanup ! end program test !```` ! ! Produces the JSON file **test.json**: ! !````json ! { ! "year": 1805, ! "value": 0.1E+1 ! } !```` type,public :: json_value !force the constituents to be stored contiguously ![note: on Intel, the order of the variables below ! is significant to avoid the misaligned field warnings] sequence private !for the linked list: type(json_value),pointer :: previous => null() !! previous item in the list type(json_value),pointer :: next => null() !! next item in the list type(json_value),pointer :: parent => null() !! parent item of this type(json_value),pointer :: children => null() !! first child item of this type(json_value),pointer :: tail => null() !! last child item of this character(kind=CK,len=:),allocatable :: name !! variable name real(RK),allocatable :: dbl_value !! real data for this variable logical(LK),allocatable :: log_value !! logical data for this variable character(kind=CK,len=:),allocatable :: str_value !! string data for this variable integer(IK),allocatable :: int_value !! integer data for this variable integer(IK) :: var_type = json_unknown !! variable type integer(IK),private :: n_children = 0 !! number of children end type json_value !********************************************************* !********************************************************* !> ! To access the core routines for manipulation ! of [[json_value]] pointer variables. This class allows ! for thread safe use of the module. ! !### Usage !````fortran ! program test ! use json_module ! implicit none ! type(json_core) :: json !<--have to declare this ! type(json_value),pointer :: p ! call json%create_object(p,'') !create the root ! call json%add(p,'year',1805) !add some data ! call json%add(p,'value',1.0_RK) !add some data ! call json%print(p,'test.json') !write it to a file ! call json%destroy(p) !cleanup ! end program test !```` type,public :: json_core private integer(IK) :: spaces_per_tab = 2 !! number of spaces for indenting logical(LK) :: compact_real = .true. !! to use the "compact" form of real !! numbers for output character(kind=CDK,len=:),allocatable :: real_fmt !! the format string to use !! for converting real numbers to strings. !! It can be set in [[json_initialize]], !! and used in [[json_value_print]] !! If not set, then `default_real_fmt` !! is used instead. logical(LK) :: is_verbose = .false. !! if true, all exceptions are !! immediately printed to console. logical(LK) :: exception_thrown = .false. !! The error flag. Will be set to true !! when an error is thrown in the class. !! Many of the methods will check this !! and return immediately if it is true. character(kind=CK,len=:),allocatable :: err_message !! the error message integer(IK) :: char_count = 0 !! character position in the current line integer(IK) :: line_count = 1 !! lines read counter integer(IK) :: pushed_index = 0 !! used when parsing lines in file character(kind=CK,len=pushed_char_size) :: pushed_char = CK_'' !! used when parsing !! lines in file integer(IK) :: ipos = 1 !! for allocatable strings: next character to read logical(LK) :: strict_type_checking = .false. !! if true, then no type conversions are done !! in the `get` routines if the actual variable !! type is different from the return type (for !! example, integer to double). logical(LK) :: trailing_spaces_significant = .false. !! for name and path comparisons, is trailing !! space to be considered significant. logical(LK) :: case_sensitive_keys = .true. !! for name and path comparisons, are they !! case sensitive. logical(LK) :: no_whitespace = .false. !! when printing a JSON string, don't include !! non-significant spaces or line breaks. !! If true, the entire structure will be !! printed on one line. logical(LK) :: unescaped_strings = .true. !! If false, then the raw escaped !! string is returned from [[json_get_string]] !! and similar routines. If true [default], !! then the string is returned unescaped. logical(LK) :: allow_comments = .true. !! if true, any comments will be ignored when !! parsing a file. The comment token is defined !! by the `comment_char` string. character(kind=CK,len=1) :: comment_char = CK_'!' !! comment token when !! `allow_comments` is true. !! Examples: '`!`' or '`#`'. integer(IK) :: path_mode = 1_IK !! How the path strings are interpreted in the !! `get_by_path` routines: !! !! * 1 -- Default mode (see [[json_get_by_path_default]]) !! * 2 -- as RFC 6901 "JSON Pointer" paths !! (see [[json_get_by_path_rfc6901]]) character(kind=CK,len=1) :: path_separator = dot !! The `path` separator to use !! in the "default" mode for !! the paths in the various !! `get_by_path` routines. !! Note: if `path_mode/=1` !! then this is ignored. logical(LK) :: compress_vectors = .false. !! If true, then arrays of integers, !! nulls, doubles, & logicals are !! printed all on one line. !! [Note: `no_whitespace` will !! override this option if necessary] contains private !> ! Return a child of a [[json_value]] structure. generic,public :: get_child => json_value_get_child_by_index, & json_value_get_child,& MAYBEWRAP(json_value_get_child_by_name) procedure,private :: json_value_get_child_by_index procedure,private :: MAYBEWRAP(json_value_get_child_by_name) procedure,private :: json_value_get_child !> ! Add objects to a linked list of [[json_value]]s. ! !@note It might make more sense to call this `add_child`. generic,public :: add => json_value_add_member, & MAYBEWRAP(json_value_add_null), & MAYBEWRAP(json_value_add_integer), & MAYBEWRAP(json_value_add_integer_vec), & MAYBEWRAP(json_value_add_double), & MAYBEWRAP(json_value_add_double_vec), & MAYBEWRAP(json_value_add_logical), & MAYBEWRAP(json_value_add_logical_vec), & MAYBEWRAP(json_value_add_string), & MAYBEWRAP(json_value_add_string_vec) #ifdef USE_UCS4 generic,public :: add => json_value_add_string_name_ascii, & json_value_add_string_val_ascii, & json_value_add_string_vec_name_ascii, & json_value_add_string_vec_val_ascii #endif procedure,private :: json_value_add_member procedure,private :: MAYBEWRAP(json_value_add_integer) procedure,private :: MAYBEWRAP(json_value_add_null) procedure,private :: MAYBEWRAP(json_value_add_integer_vec) procedure,private :: MAYBEWRAP(json_value_add_double) procedure,private :: MAYBEWRAP(json_value_add_double_vec) procedure,private :: MAYBEWRAP(json_value_add_logical) procedure,private :: MAYBEWRAP(json_value_add_logical_vec) procedure,private :: MAYBEWRAP(json_value_add_string) procedure,private :: MAYBEWRAP(json_value_add_string_vec) #ifdef USE_UCS4 procedure,private :: json_value_add_string_name_ascii procedure,private :: json_value_add_string_val_ascii procedure,private :: json_value_add_string_vec_name_ascii procedure,private :: json_value_add_string_vec_val_ascii #endif !> ! These are like the `add` methods, except if a variable with the ! same path is already present, then its value is simply updated. ! Note that currently, these only work for scalar variables. ! These routines can also change the variable's type (but an error will be ! thrown if the existing variable is not a scalar). ! !### See also ! * [[add_by_path]] - this one can be used to change ! arrays and objects to scalars if so desired. ! !@note Unlike some routines, the `found` output is not optional, ! so it doesn't present exceptions from being thrown. ! !@note These have been mostly supplanted by the [[add_by_path]] ! methods, which do a similar thing (and can be used for ! scalars and vectors, etc.) generic,public :: update => MAYBEWRAP(json_update_logical),& MAYBEWRAP(json_update_double),& MAYBEWRAP(json_update_integer),& MAYBEWRAP(json_update_string) #ifdef USE_UCS4 generic,public :: update => json_update_string_name_ascii,& json_update_string_val_ascii #endif procedure,private :: MAYBEWRAP(json_update_logical) procedure,private :: MAYBEWRAP(json_update_double) procedure,private :: MAYBEWRAP(json_update_integer) procedure,private :: MAYBEWRAP(json_update_string) #ifdef USE_UCS4 procedure,private :: json_update_string_name_ascii procedure,private :: json_update_string_val_ascii #endif !> ! Add variables to a [[json_value]] linked list ! by specifying their paths. ! !### Example ! !````fortran ! use, intrinsic :: iso_fortran_env, only: output_unit, wp=>real64 ! use json_module ! type(json_core) :: json ! type(json_value) :: p ! call json%create_object(p,'root') ! create the root ! ! now add some variables using the paths: ! call json%add_by_path(p,'inputs.t', 0.0_wp ) ! call json%add_by_path(p,'inputs.x(1)', 100.0_wp) ! call json%add_by_path(p,'inputs.x(2)', 200.0_wp) ! call json%print(p,output_unit) ! now print to console !```` ! !### Notes ! * This uses [[json_create_by_path]] ! !### See also ! * The `json_core%update` methods. ! * [[json_create_by_path]] generic,public :: add_by_path => MAYBEWRAP(json_add_member_by_path),& MAYBEWRAP(json_add_integer_by_path),& MAYBEWRAP(json_add_double_by_path),& MAYBEWRAP(json_add_logical_by_path),& MAYBEWRAP(json_add_string_by_path),& MAYBEWRAP(json_add_integer_vec_by_path),& MAYBEWRAP(json_add_double_vec_by_path),& MAYBEWRAP(json_add_logical_vec_by_path),& MAYBEWRAP(json_add_string_vec_by_path) #ifdef USE_UCS4 generic,public :: add_by_path => json_add_string_by_path_value_ascii,& json_add_string_by_path_path_ascii,& json_add_string_vec_by_path_value_ascii,& json_add_string_vec_by_path_path_ascii #endif procedure :: MAYBEWRAP(json_add_member_by_path) procedure :: MAYBEWRAP(json_add_integer_by_path) procedure :: MAYBEWRAP(json_add_double_by_path) procedure :: MAYBEWRAP(json_add_logical_by_path) procedure :: MAYBEWRAP(json_add_string_by_path) procedure :: MAYBEWRAP(json_add_integer_vec_by_path) procedure :: MAYBEWRAP(json_add_double_vec_by_path) procedure :: MAYBEWRAP(json_add_logical_vec_by_path) procedure :: MAYBEWRAP(json_add_string_vec_by_path) #ifdef USE_UCS4 procedure :: json_add_string_by_path_value_ascii procedure :: json_add_string_by_path_path_ascii procedure :: json_add_string_vec_by_path_value_ascii procedure :: json_add_string_vec_by_path_path_ascii #endif !> ! Create a [[json_value]] linked list using the ! path to the variables. Optionally return a ! pointer to the variable. ! ! (This will create a `null` variable) ! !### See also ! * [[add_by_path]] generic,public :: create => MAYBEWRAP(json_create_by_path) procedure :: MAYBEWRAP(json_create_by_path) !> ! Get data from a [[json_value]] linked list. ! !@note There are two versions (e.g. [[json_get_integer]] and [[json_get_integer_by_path]]). ! The first one gets the value from the [[json_value]] passed into the routine, ! while the second one gets the value from the [[json_value]] found by parsing the ! path. The path version is split up into unicode and non-unicode versions. generic,public :: get => & MAYBEWRAP(json_get_by_path), & json_get_integer, MAYBEWRAP(json_get_integer_by_path), & json_get_integer_vec, MAYBEWRAP(json_get_integer_vec_by_path), & json_get_double, MAYBEWRAP(json_get_double_by_path), & json_get_double_vec, MAYBEWRAP(json_get_double_vec_by_path), & json_get_logical, MAYBEWRAP(json_get_logical_by_path), & json_get_logical_vec, MAYBEWRAP(json_get_logical_vec_by_path), & json_get_string, MAYBEWRAP(json_get_string_by_path), & json_get_string_vec, MAYBEWRAP(json_get_string_vec_by_path), & json_get_alloc_string_vec,MAYBEWRAP(json_get_alloc_string_vec_by_path),& json_get_array, MAYBEWRAP(json_get_array_by_path) procedure,private :: json_get_integer procedure,private :: json_get_integer_vec procedure,private :: json_get_double procedure,private :: json_get_double_vec procedure,private :: json_get_logical procedure,private :: json_get_logical_vec procedure,private :: json_get_string procedure,private :: json_get_string_vec procedure,private :: json_get_alloc_string_vec procedure,private :: json_get_array procedure,private :: MAYBEWRAP(json_get_by_path) procedure,private :: MAYBEWRAP(json_get_integer_by_path) procedure,private :: MAYBEWRAP(json_get_integer_vec_by_path) procedure,private :: MAYBEWRAP(json_get_double_by_path) procedure,private :: MAYBEWRAP(json_get_double_vec_by_path) procedure,private :: MAYBEWRAP(json_get_logical_by_path) procedure,private :: MAYBEWRAP(json_get_logical_vec_by_path) procedure,private :: MAYBEWRAP(json_get_string_by_path) procedure,private :: MAYBEWRAP(json_get_string_vec_by_path) procedure,private :: MAYBEWRAP(json_get_array_by_path) procedure,private :: MAYBEWRAP(json_get_alloc_string_vec_by_path) procedure,private :: json_get_by_path_default procedure,private :: json_get_by_path_rfc6901 procedure,public :: print_to_string => json_value_to_string !! Print the [[json_value]] !! structure to an allocatable !! string !> ! Print the [[json_value]] to a file. ! !### Example ! !````fortran ! type(json_core) :: json ! type(json_value) :: p ! !... ! call json%print(p,'test.json') !this is [[json_print_2]] !```` generic,public :: print => json_print_1,json_print_2 procedure :: json_print_1 procedure :: json_print_2 !> ! Destructor routine for a [[json_value]] pointer. ! This must be called explicitly if it is no longer needed, ! before it goes out of scope. Otherwise, a memory leak will result. ! !### Example ! ! Destroy the [[json_value]] pointer before the variable goes out of scope: !````fortran ! subroutine example1() ! type(json_core) :: json ! type(json_value),pointer :: p ! call json%create_object(p,'') ! call json%add(p,'year',2015) ! call json%print(p) ! call json%destroy(p) ! end subroutine example1 !```` ! ! Note: it should NOT be called for a [[json_value]] pointer than has already been ! added to another [[json_value]] structure, since doing so may render the ! other structure invalid. Consider the following example: !````fortran ! subroutine example2(p) ! type(json_core) :: json ! type(json_value),pointer,intent(out) :: p ! type(json_value),pointer :: q ! call json%create_object(p,'') ! call json%add(p,'year',2015) ! call json%create_object(q,'q') ! call json%add(q,'val',1) ! call json%add(p, q) !add q to p structure ! ! do NOT call json%destroy(q) here, because q is ! ! now part of the output structure p. p should be destroyed ! ! somewhere upstream by the caller of this routine. ! nullify(q) !OK, but not strictly necessary ! end subroutine example2 !```` generic,public :: destroy => json_value_destroy,destroy_json_core procedure :: json_value_destroy procedure :: destroy_json_core !> ! If the child variable is present, then remove it. generic,public :: remove_if_present => MAYBEWRAP(json_value_remove_if_present) procedure :: MAYBEWRAP(json_value_remove_if_present) !> ! Allocate a [[json_value]] pointer and make it a double variable. ! The pointer should not already be allocated. ! !### Example ! !````fortran ! type(json_core) :: json ! type(json_value),pointer :: p ! call json%create_double(p,'value',1.0_RK) !```` generic,public :: create_double => MAYBEWRAP(json_value_create_double) procedure :: MAYBEWRAP(json_value_create_double) !> ! Allocate a [[json_value]] pointer and make it an array variable. ! The pointer should not already be allocated. ! !### Example ! !````fortran ! type(json_core) :: json ! type(json_value),pointer :: p ! call json%create_array(p,'arrayname') !```` generic,public :: create_array => MAYBEWRAP(json_value_create_array) procedure :: MAYBEWRAP(json_value_create_array) !> ! Allocate a [[json_value]] pointer and make it an object variable. ! The pointer should not already be allocated. ! !### Example ! !````fortran ! type(json_core) :: json ! type(json_value),pointer :: p ! call json%create_object(p,'objectname') !```` ! !@note The name is not significant for the root structure or an array element. ! In those cases, an empty string can be used. generic,public :: create_object => MAYBEWRAP(json_value_create_object) procedure :: MAYBEWRAP(json_value_create_object) !> ! Allocate a json_value pointer and make it a null variable. ! The pointer should not already be allocated. ! !### Example ! !````fortran ! type(json_core) :: json ! type(json_value),pointer :: p ! call json%create_null(p,'value') !```` generic,public :: create_null => MAYBEWRAP(json_value_create_null) procedure :: MAYBEWRAP(json_value_create_null) !> ! Allocate a json_value pointer and make it a string variable. ! The pointer should not already be allocated. ! !### Example ! !````fortran ! type(json_core) :: json ! type(json_value),pointer :: p ! call json%create_string(p,'value','foobar') !```` generic,public :: create_string => MAYBEWRAP(json_value_create_string) procedure :: MAYBEWRAP(json_value_create_string) !> ! Allocate a json_value pointer and make it an integer variable. ! The pointer should not already be allocated. ! !### Example ! !````fortran ! type(json_core) :: json ! type(json_value),pointer :: p ! call json%create_integer(p,42,'value') !```` generic,public :: create_integer => MAYBEWRAP(json_value_create_integer) procedure :: MAYBEWRAP(json_value_create_integer) !> ! Allocate a json_value pointer and make it a logical variable. ! The pointer should not already be allocated. ! !### Example ! !````fortran ! type(json_core) :: json ! type(json_value),pointer :: p ! call json%create_logical(p,'value',.true.) !```` generic,public :: create_logical => MAYBEWRAP(json_value_create_logical) procedure :: MAYBEWRAP(json_value_create_logical) !> ! Parse the JSON file and populate the [[json_value]] tree. generic,public :: parse => json_parse_file, MAYBEWRAP(json_parse_string) procedure :: json_parse_file procedure :: MAYBEWRAP(json_parse_string) !> ! Throw an exception. generic,public :: throw_exception => MAYBEWRAP(json_throw_exception) procedure :: MAYBEWRAP(json_throw_exception) !> ! Rename a [[json_value]] variable. generic,public :: rename => MAYBEWRAP(json_value_rename) procedure :: MAYBEWRAP(json_value_rename) !> ! get info about a [[json_value]] generic,public :: info => json_info, MAYBEWRAP(json_info_by_path) procedure :: json_info procedure :: MAYBEWRAP(json_info_by_path) !> ! get string info about a [[json_value]] generic,public :: string_info => json_string_info procedure :: json_string_info !> ! get matrix info about a [[json_value]] generic,public :: matrix_info => json_matrix_info, MAYBEWRAP(json_matrix_info_by_path) procedure :: json_matrix_info procedure :: MAYBEWRAP(json_matrix_info_by_path) !> ! insert a new element after an existing one, ! updating the JSON structure accordingly generic,public :: insert_after => json_value_insert_after, & json_value_insert_after_child_by_index procedure :: json_value_insert_after procedure :: json_value_insert_after_child_by_index !> ! get the path to a JSON variable in a structure: generic,public :: get_path => MAYBEWRAP(json_get_path) procedure :: MAYBEWRAP(json_get_path) procedure,public :: remove => json_value_remove !! Remove a [[json_value]] from a linked-list structure. procedure,public :: replace => json_value_replace !! Replace a [[json_value]] in a linked-list structure. procedure,public :: check_for_errors => json_check_for_errors !! check for error and get error message procedure,public :: clear_exceptions => json_clear_exceptions !! clear exceptions procedure,public :: count => json_count !! count the number of children procedure,public :: clone => json_clone !! clone a JSON structure (deep copy) procedure,public :: failed => json_failed !! check for error procedure,public :: get_parent => json_get_parent !! get pointer to json_value parent procedure,public :: get_next => json_get_next !! get pointer to json_value next procedure,public :: get_previous => json_get_previous !! get pointer to json_value previous procedure,public :: get_tail => json_get_tail !! get pointer to json_value tail procedure,public :: initialize => json_initialize !! to initialize some parsing parameters procedure,public :: traverse => json_traverse !! to traverse all elements of a JSON structure procedure,public :: print_error_message => json_print_error_message !! simply routine to print error messages procedure,public :: swap => json_value_swap !! Swap two [[json_value]] pointers !! in a structure (or two different structures). procedure,public :: is_child_of => json_value_is_child_of !! Check if a [[json_value]] is a descendant of another. procedure,public :: validate => json_value_validate !! Check that a [[json_value]] linked list is valid !! (i.e., is properly constructed). This may be !! useful if it has been constructed externally. !other private routines: procedure :: name_equal procedure :: json_value_print procedure :: string_to_int procedure :: string_to_dble procedure :: parse_value procedure :: parse_number procedure :: parse_string procedure :: parse_for_chars procedure :: parse_object procedure :: parse_array procedure :: annotate_invalid_json procedure :: pop_char procedure :: push_char procedure :: get_current_line_from_file_stream procedure :: get_current_line_from_file_sequential end type json_core !********************************************************* !********************************************************* !> ! Structure constructor to initialize a ! [[json_core(type)]] object ! !### Example ! !```fortran ! type(json_file) :: json_core ! json_core = json_core() !``` interface json_core module procedure initialize_json_core end interface !********************************************************* !************************************************************************************* abstract interface subroutine json_array_callback_func(json, element, i, count) !! Array element callback function. Used by [[json_get_array]] import :: json_value,json_core,IK implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: element integer(IK),intent(in) :: i !! index integer(IK),intent(in) :: count !! size of array end subroutine json_array_callback_func subroutine json_traverse_callback_func(json,p,finished) !! Callback function used by [[json_traverse]] import :: json_value,json_core,LK implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: p logical(LK),intent(out) :: finished !! set true to stop traversing end subroutine json_traverse_callback_func end interface public :: json_array_callback_func public :: json_traverse_callback_func !************************************************************************************* contains !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 4/17/2016 ! ! Destructor for the [[json_core(type)]] type. subroutine destroy_json_core(me) implicit none class(json_core),intent(out) :: me end subroutine destroy_json_core !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 4/26/2016 ! ! Function constructor for a [[json_core(type)]]. ! This is just a wrapper for [[json_initialize]]. ! !@note [[initialize_json_core]], [[json_initialize]], ! [[initialize_json_core_in_file]], and [[initialize_json_file]] ! all have a similar interface. function initialize_json_core(verbose,compact_reals,& print_signs,real_format,spaces_per_tab,& strict_type_checking,& trailing_spaces_significant,& case_sensitive_keys,& no_whitespace,& unescape_strings,& comment_char,& path_mode,& path_separator,& compress_vectors) result(json_core_object) implicit none type(json_core) :: json_core_object #include "json_initialize_arguments.inc" call json_core_object%initialize(verbose,compact_reals,& print_signs,real_format,spaces_per_tab,& strict_type_checking,& trailing_spaces_significant,& case_sensitive_keys,& no_whitespace,& unescape_strings,& comment_char,& path_mode,& path_separator,& compress_vectors) end function initialize_json_core !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 12/4/2013 ! ! Initialize the [[json_core(type)]] instance. ! ! The routine may be called before any of the [[json_core(type)]] methods are used in ! order to specify certain parameters. If it is not called, then the defaults ! are used. This routine is also called internally by various routines. ! It can also be called to clear exceptions, or to reset some ! of the variables (note that only the arguments present are changed). ! !### Modified ! * Izaak Beekman : 02/24/2015 ! !@note [[initialize_json_core]], [[json_initialize]], ! [[initialize_json_core_in_file]], and [[initialize_json_file]] ! all have a similar interface. subroutine json_initialize(me,verbose,compact_reals,& print_signs,real_format,spaces_per_tab,& strict_type_checking,& trailing_spaces_significant,& case_sensitive_keys,& no_whitespace,& unescape_strings,& comment_char,& path_mode,& path_separator,& compress_vectors) implicit none class(json_core),intent(inout) :: me #include "json_initialize_arguments.inc" character(kind=CDK,len=10) :: w !! max string length character(kind=CDK,len=10) :: d !! real precision digits character(kind=CDK,len=10) :: e !! real exponent digits character(kind=CDK,len=2) :: sgn !! sign flag: `ss` or `sp` character(kind=CDK,len=2) :: rl_edit_desc !! `G`, `E`, `EN`, or `ES` integer(IK) :: istat !! `iostat` flag for write statements logical(LK) :: sgn_prnt !! print sign flag !reset exception to false: call me%clear_exceptions() !Just in case, clear these global variables also: me%pushed_index = 0 me%pushed_char = CK_'' me%char_count = 0 me%line_count = 1 me%ipos = 1 #ifdef USE_UCS4 ! reopen stdout and stderr with utf-8 encoding open(output_unit,encoding='utf-8') open(error_unit, encoding='utf-8') #endif !various optional inputs: if (present(spaces_per_tab)) & me%spaces_per_tab = spaces_per_tab if (present(verbose)) & me%is_verbose = verbose if (present(strict_type_checking)) & me%strict_type_checking = strict_type_checking if (present(trailing_spaces_significant)) & me%trailing_spaces_significant = trailing_spaces_significant if (present(case_sensitive_keys)) & me%case_sensitive_keys = case_sensitive_keys if (present(no_whitespace)) & me%no_whitespace = no_whitespace if (present(unescape_strings)) & me%unescaped_strings = unescape_strings if (present(path_mode)) then if (path_mode==1_IK .or. path_mode==2_IK) then me%path_mode = path_mode else me%path_mode = 1_IK ! just to have a valid value call me%throw_exception('Invalid path_mode.') end if end if ! if we are allowing comments in the file: ! [an empty string disables comments] if (present(comment_char)) then me%allow_comments = comment_char/=CK_'' me%comment_char = comment_char end if ! path separator: if (present(path_separator)) then me%path_separator = path_separator end if ! printing vectors in compressed form: if (present(compress_vectors)) then me%compress_vectors = compress_vectors end if !Set the format for real numbers: ! [if not changing it, then it remains the same] if ( (.not. allocated(me%real_fmt)) .or. & ! if this hasn't been done yet present(compact_reals) .or. & present(print_signs) .or. & present(real_format) ) then !allow the special case where real format is '*': ! [this overrides the other options] if (present(real_format)) then if (real_format==star) then if (present(compact_reals)) then ! we will also allow for compact reals with ! '*' format, if both arguments are present. me%compact_real = compact_reals else me%compact_real = .false. end if me%real_fmt = star return end if end if if (present(compact_reals)) me%compact_real = compact_reals !set defaults sgn_prnt = .false. if ( present( print_signs) ) sgn_prnt = print_signs if ( sgn_prnt ) then sgn = 'sp' else sgn = 'ss' end if rl_edit_desc = 'E' if ( present( real_format ) ) then select case ( real_format ) case ('g','G','e','E','en','EN','es','ES') rl_edit_desc = real_format case default call me%throw_exception('Invalid real format, "' // & trim(real_format) // '", passed to json_initialize.'// & new_line('a') // 'Acceptable formats are: "G", "E", "EN", and "ES".' ) end select end if ! set the default output/input format for reals: write(w,'(ss,I0)',iostat=istat) max_numeric_str_len if (istat==0) write(d,'(ss,I0)',iostat=istat) real_precision if (istat==0) write(e,'(ss,I0)',iostat=istat) real_exponent_digits if (istat==0) then me%real_fmt = '(' // sgn // ',' // trim(rl_edit_desc) //& trim(w) // '.' // trim(d) // 'E' // trim(e) // ')' else me%real_fmt = '(' // sgn // ',' // trim(rl_edit_desc) // & '27.17E4)' !just use this one (should never happen) end if end if end subroutine json_initialize !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 4/30/2016 ! ! Returns true if `name` is equal to `p%name`, using the specified ! settings for case sensitivity and trailing whitespace. function name_equal(json,p,name) result(is_equal) implicit none class(json_core),intent(inout) :: json type(json_value),intent(in) :: p !! the json object character(kind=CK,len=*),intent(in) :: name !! the name to check for logical(LK) :: is_equal !! true if the string are lexically equal if (allocated(p%name)) then !must be the same length if we are treating !trailing spaces as significant, so do a !quick test of this first: if (json%trailing_spaces_significant) then is_equal = len(p%name) == len(name) if (.not. is_equal) return end if if (json%case_sensitive_keys) then is_equal = p%name == name else is_equal = lowercase_string(p%name) == lowercase_string(name) end if else is_equal = name == CK_'' ! check a blank name end if end function name_equal !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 10/31/2015 ! ! Create a deep copy of a [[json_value]] linked-list structure. ! !### Example ! !````fortran ! program test ! use json_module ! implicit none ! type(json_core) :: json ! type(json_value),pointer :: j1, j2 ! call json%parse('../files/inputs/test1.json',j1) ! call json%clone(j1,j2) !now have two independent copies ! call json%destroy(j1) !destroys j1, but j2 remains ! call json%print(j2,'j2.json') ! call json%destroy(j2) ! end program test !```` subroutine json_clone(json,from,to) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: from !! this is the structure to clone type(json_value),pointer :: to !! the clone is put here !! (it must not already be associated) !call the main function: ! [note: this is not part of json_core class] call json_value_clone_func(from,to) end subroutine json_clone !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 10/31/2015 ! ! Recursive deep copy function called by [[json_clone]]. ! !@note If new data is added to the [[json_value]] type, ! then this would need to be updated. recursive subroutine json_value_clone_func(from,to,parent,previous,next,children,tail) implicit none type(json_value),pointer :: from !! this is the structure to clone type(json_value),pointer :: to !! the clone is put here !! (it must not already be associated) type(json_value),pointer,optional :: parent !! to%parent type(json_value),pointer,optional :: previous !! to%previous type(json_value),pointer,optional :: next !! to%next type(json_value),pointer,optional :: children !! to%children logical,optional :: tail !! if "to" is the tail of its parent's children nullify(to) if (associated(from)) then allocate(to) !copy over the data variables: ! [note: the allocate() statements don't work here for the ! deferred-length characters in gfortran-4.9] if (allocated(from%name)) to%name = from%name if (allocated(from%dbl_value)) allocate(to%dbl_value,source=from%dbl_value) if (allocated(from%log_value)) allocate(to%log_value,source=from%log_value) if (allocated(from%str_value)) to%str_value = from%str_value if (allocated(from%int_value)) allocate(to%int_value,source=from%int_value) to%var_type = from%var_type to%n_children = from%n_children !allocate and associate the pointers as necessary: if (present(parent)) to%parent => parent if (present(previous)) to%previous => previous if (present(next)) to%next => next if (present(children)) to%children => children if (present(tail)) then if (tail) to%parent%tail => to end if if (associated(from%next)) then allocate(to%next) call json_value_clone_func(from%next,& to%next,& previous=to,& parent=to%parent,& tail=(.not. associated(from%next%next))) end if if (associated(from%children)) then allocate(to%children) call json_value_clone_func(from%children,& to%children,& parent=to,& tail=(.not. associated(from%children%next))) end if end if end subroutine json_value_clone_func !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! ! Destroy the data within a [[json_value]], and reset type to `json_unknown`. subroutine destroy_json_data(d) implicit none type(json_value),intent(inout) :: d d%var_type = json_unknown if (allocated(d%log_value)) deallocate(d%log_value) if (allocated(d%int_value)) deallocate(d%int_value) if (allocated(d%dbl_value)) deallocate(d%dbl_value) if (allocated(d%str_value)) deallocate(d%str_value) end subroutine destroy_json_data !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 2/13/2014 ! ! Returns information about a [[json_value]]. subroutine json_info(json,p,var_type,n_children,name) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p integer(IK),intent(out),optional :: var_type !! variable type integer(IK),intent(out),optional :: n_children !! number of children character(kind=CK,len=:),allocatable,intent(out),optional :: name !! variable name if (present(var_type)) var_type = p%var_type if (present(n_children)) n_children = json%count(p) if (present(name)) then if (allocated(p%name)) then name = p%name else name = CK_'' end if end if end subroutine json_info !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 12/18/2016 ! ! Returns information about character strings returned from a [[json_value]]. subroutine json_string_info(json,p,ilen,max_str_len,found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p integer(IK),dimension(:),allocatable,intent(out),optional :: ilen !! if `p` is an array, this !! is the actual length !! of each character !! string in the array. !! if not an array, this !! is returned unallocated. integer(IK),intent(out),optional :: max_str_len !! The maximum length required to !! hold the string representation returned !! by a call to a `get` routine. If a scalar, !! this is just the length of the scalar. If !! a vector, this is the maximum length of !! any element. logical(LK),intent(out),optional :: found !! true if there were no errors. !! if not present, an error will !! throw an exception character(kind=CK,len=:),allocatable :: cval !! for getting values as strings. logical(LK) :: initialized !! if the output array has been sized logical(LK) :: get_max_len !! if we are returning the `max_str_len` logical(LK) :: get_ilen !! if we are returning the `ilen` array integer(IK) :: var_type !! variable type get_max_len = present(max_str_len) get_ilen = present(ilen) if (.not. json%exception_thrown) then if (present(found)) found = .true. initialized = .false. if (get_max_len) max_str_len = 0 select case (p%var_type) case (json_array) ! it's an array ! call routine for each element call json%get(p, array_callback=get_string_lengths) case default ! not an array if (json%strict_type_checking) then ! only allowing strings to be returned ! as strings, so we can check size directly call json%info(p,var_type=var_type) if (var_type==json_string) then if (allocated(p%str_value) .and. get_max_len) & max_str_len = len(p%str_value) else ! it isn't a string, so there is no length call json%throw_exception('Error in json_string_info: '//& 'When strict_type_checking is true '//& 'the variable must be a character string.') end if else ! in this case, we have to get the value ! as a string to know what size it is. call json%get(p, value=cval) if (.not. json%exception_thrown) then if (allocated(cval) .and. get_max_len) & max_str_len = len(cval) end if end if end select end if if (json%exception_thrown) then if (present(found)) then call json%clear_exceptions() found = .false. end if if (get_max_len) max_str_len = 0 if (get_ilen) then if (allocated(ilen)) deallocate(ilen) end if end if contains subroutine get_string_lengths(json, element, i, count) !! callback function to call for each element in the array. implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: element integer(IK),intent(in) :: i !! index integer(IK),intent(in) :: count !! size of array character(kind=CK,len=:),allocatable :: cval integer(IK) :: var_type if (json%exception_thrown) return if (.not. initialized) then if (get_ilen) allocate(ilen(count)) initialized = .true. end if if (json%strict_type_checking) then ! only allowing strings to be returned ! as strings, so we can check size directly call json%info(element,var_type=var_type) if (var_type==json_string) then if (allocated(element%str_value)) then if (get_max_len) then if (len(element%str_value)>max_str_len) & max_str_len = len(element%str_value) end if if (get_ilen) ilen(i) = len(element%str_value) else if (get_ilen) ilen(i) = 0 end if else ! it isn't a string, so there is no length call json%throw_exception('Error in json_string_info: '//& 'When strict_type_checking is true '//& 'the array must contain only '//& 'character strings.') end if else ! in this case, we have to get the value ! as a string to know what size it is. call json%get(element, value=cval) if (json%exception_thrown) return if (allocated(cval)) then if (get_max_len) then if (len(cval)>max_str_len) max_str_len = len(cval) end if if (get_ilen) ilen(i) = len(cval) else if (get_ilen) ilen(i) = 0 end if end if end subroutine get_string_lengths end subroutine json_string_info !***************************************************************************************** !***************************************************************************************** ! ! Returns information about a [[json_value]], given the path. ! !### See also ! * [[json_info]] ! !@note If `found` is present, no exceptions will be thrown if an ! error occurs. Otherwise, an exception will be thrown if the ! variable is not found. subroutine json_info_by_path(json,p,path,found,var_type,n_children,name) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: p !! a JSON linked list character(kind=CK,len=*),intent(in) :: path !! path to the variable logical(LK),intent(out),optional :: found !! true if it was found integer(IK),intent(out),optional :: var_type !! variable type integer(IK),intent(out),optional :: n_children !! number of children character(kind=CK,len=:),allocatable,intent(out),optional :: name !! variable name type(json_value),pointer :: p_var !! temporary pointer logical(LK) :: ok !! if the variable was found #if defined __GFORTRAN__ character(kind=CK,len=:),allocatable :: p_name !! temporary variable for getting name #endif call json%get(p,path,p_var,found) !check if it was found: if (present(found)) then ok = found else ok = .not. json%exception_thrown end if if (.not. ok) then if (present(var_type)) var_type = json_unknown if (present(n_children)) n_children = 0 if (present(name)) name = CK_'' else !get info: #if defined __GFORTRAN__ call json%info(p_var,var_type,n_children) if (present(name)) then !workaround for gfortran bug if (allocated(p_var%name)) then p_name = p_var%name name = p_name else name = CK_'' end if end if #else call json%info(p_var,var_type,n_children,name) #endif end if end subroutine json_info_by_path !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_info_by_path]] where "path" is kind=CDK. subroutine wrap_json_info_by_path(json,p,path,found,var_type,n_children,name) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: p !! a JSON linked list character(kind=CDK,len=*),intent(in) :: path !! path to the variable logical(LK),intent(out),optional :: found !! true if it was found integer(IK),intent(out),optional :: var_type !! variable type integer(IK),intent(out),optional :: n_children !! number of children character(kind=CK,len=:),allocatable,intent(out),optional :: name !! variable name call json%info(p,to_unicode(path),found,var_type,n_children,name) end subroutine wrap_json_info_by_path !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 10/16/2015 ! ! Alternate version of [[json_info]] that returns matrix ! information about a [[json_value]]. ! ! A [[json_value]] is a valid rank 2 matrix if all of the following are true: ! ! * The var_type is *json_array* ! * Each child is also a *json_array*, each of which has the same number of elements ! * Each individual element has the same variable type (integer, logical, etc.) ! ! The idea here is that if it is a valid matrix, it can be interoperable with ! a Fortran rank 2 array of the same type. ! !### Example ! ! The following example is an array with `var_type=json_integer`, `n_sets=3`, and `set_size=4` ! !```json ! { ! "matrix": [ ! [1,2,3,4], ! [5,6,7,8], ! [9,10,11,12] ! ] ! } !``` subroutine json_matrix_info(json,p,is_matrix,var_type,n_sets,set_size,name) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p !! a JSON linked list logical(LK),intent(out) :: is_matrix !! true if it is a valid matrix integer(IK),intent(out),optional :: var_type !! variable type of data in the matrix (if all elements have the same type) integer(IK),intent(out),optional :: n_sets !! number of data sets (i.e., matrix rows if using row-major order) integer(IK),intent(out),optional :: set_size !! size of each data set (i.e., matrix cols if using row-major order) character(kind=CK,len=:),allocatable,intent(out),optional :: name !! variable name type(json_value),pointer :: p_row !! for getting a set type(json_value),pointer :: p_element !! for getting an element in a set integer(IK) :: vartype !! json variable type of `p` integer(IK) :: row_vartype !! json variable type of a row integer(IK) :: element_vartype !! json variable type of an element in a row integer(IK) :: nr !! number of children of `p` integer(IK) :: nc !! number of elements in first child of `p` integer(IK) :: icount !! number of elements in a set integer :: i !! counter integer :: j !! counter #if defined __GFORTRAN__ character(kind=CK,len=:),allocatable :: p_name !! temporary variable for getting name #endif !get info about the variable: #if defined __GFORTRAN__ call json%info(p,vartype,nr) if (present(name)) then !workaround for gfortran bug if (allocated(p%name)) then p_name = p%name name = p_name else name = CK_'' end if end if #else call json%info(p,vartype,nr,name) #endif is_matrix = (vartype==json_array) if (is_matrix) then main : do i=1,nr nullify(p_row) call json%get_child(p,i,p_row) if (.not. associated(p_row)) then is_matrix = .false. call json%throw_exception('Error in json_matrix_info: '//& 'Malformed JSON linked list') exit main end if call json%info(p_row,var_type=row_vartype,n_children=icount) if (row_vartype==json_array) then if (i==1) nc = icount !number of columns in first row if (icount==nc) then !make sure each row has the same number of columns !see if all the variables in this row are the same type: do j=1,icount nullify(p_element) call json%get_child(p_row,j,p_element) if (.not. associated(p_element)) then is_matrix = .false. call json%throw_exception('Error in json_matrix_info: '//& 'Malformed JSON linked list') exit main end if call json%info(p_element,var_type=element_vartype) if (i==1 .and. j==1) vartype = element_vartype !type of first element !in the row if (vartype/=element_vartype) then !not all variables are the same time is_matrix = .false. exit main end if end do else is_matrix = .false. exit main end if else is_matrix = .false. exit main end if end do main end if if (is_matrix) then if (present(var_type)) var_type = vartype if (present(n_sets)) n_sets = nr if (present(set_size)) set_size = nc else if (present(var_type)) var_type = json_unknown if (present(n_sets)) n_sets = 0 if (present(set_size)) set_size = 0 end if end subroutine json_matrix_info !***************************************************************************************** !***************************************************************************************** !> ! Returns matrix information about a [[json_value]], given the path. ! !### See also ! * [[json_matrix_info]] ! !@note If `found` is present, no exceptions will be thrown if an ! error occurs. Otherwise, an exception will be thrown if the ! variable is not found. subroutine json_matrix_info_by_path(json,p,path,is_matrix,found,& var_type,n_sets,set_size,name) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p !! a JSON linked list character(kind=CK,len=*),intent(in) :: path !! path to the variable logical(LK),intent(out) :: is_matrix !! true if it is a valid matrix logical(LK),intent(out),optional :: found !! true if it was found integer(IK),intent(out),optional :: var_type !! variable type of data in !! the matrix (if all elements have !! the same type) integer(IK),intent(out),optional :: n_sets !! number of data sets (i.e., matrix !! rows if using row-major order) integer(IK),intent(out),optional :: set_size !! size of each data set (i.e., matrix !! cols if using row-major order) character(kind=CK,len=:),allocatable,intent(out),optional :: name !! variable name type(json_value),pointer :: p_var logical(LK) :: ok #if defined __GFORTRAN__ character(kind=CK,len=:),allocatable :: p_name !! temporary variable for getting name #endif call json%get(p,path,p_var,found) !check if it was found: if (present(found)) then ok = found else ok = .not. json%exception_thrown end if if (.not. ok) then if (present(var_type)) var_type = json_unknown if (present(n_sets)) n_sets = 0 if (present(set_size)) set_size = 0 if (present(name)) name = CK_'' else !get info about the variable: #if defined __GFORTRAN__ call json%matrix_info(p_var,is_matrix,var_type,n_sets,set_size) if (present(name)) then !workaround for gfortran bug if (allocated(p_var%name)) then p_name = p_var%name name = p_name else name = CK_'' end if end if #else call json%matrix_info(p_var,is_matrix,var_type,n_sets,set_size,name) #endif if (json%exception_thrown .and. present(found)) then found = .false. call json%clear_exceptions() end if end if end subroutine json_matrix_info_by_path !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_matrix_info_by_path]] where "path" is kind=CDK. subroutine wrap_json_matrix_info_by_path(json,p,path,is_matrix,found,& var_type,n_sets,set_size,name) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p !! a JSON linked list character(kind=CDK,len=*),intent(in) :: path !! path to the variable logical(LK),intent(out) :: is_matrix !! true if it is a valid matrix logical(LK),intent(out),optional :: found !! true if it was found integer(IK),intent(out),optional :: var_type !! variable type of data in !! the matrix (if all elements have !! the same type) integer(IK),intent(out),optional :: n_sets !! number of data sets (i.e., matrix !! rows if using row-major order) integer(IK),intent(out),optional :: set_size !! size of each data set (i.e., matrix !! cols if using row-major order) character(kind=CK,len=:),allocatable,intent(out),optional :: name !! variable name call json%matrix_info(p,to_unicode(path),is_matrix,found,var_type,n_sets,set_size,name) end subroutine wrap_json_matrix_info_by_path !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 4/29/2016 ! ! Rename a [[json_value]]. subroutine json_value_rename(json,p,name) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: p character(kind=CK,len=*),intent(in) :: name !! new variable name p%name = name end subroutine json_value_rename !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 4/29/2016 ! ! Alternate version of [[json_value_rename]], where `name` is kind=CDK. subroutine wrap_json_value_rename(json,p,name) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: p character(kind=CDK,len=*),intent(in) :: name !! new variable name call json%rename(p,to_unicode(name)) end subroutine wrap_json_value_rename !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 12/4/2013 ! ! Clear exceptions in the [[json_core(type)]]. pure subroutine json_clear_exceptions(json) implicit none class(json_core),intent(inout) :: json !clear the flag and message: json%exception_thrown = .false. json%err_message = CK_'' end subroutine json_clear_exceptions !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 12/4/2013 ! ! Throw an exception in the [[json_core(type)]]. ! This routine sets the error flag, and prevents any subsequent routine ! from doing anything, until [[json_clear_exceptions]] is called. ! !@note If `is_verbose` is true, this will also print a ! traceback if the Intel compiler is used. subroutine json_throw_exception(json,msg) #ifdef __INTEL_COMPILER use ifcore, only: tracebackqq #endif implicit none class(json_core),intent(inout) :: json character(kind=CK,len=*),intent(in) :: msg !! the error message json%exception_thrown = .true. json%err_message = trim(msg) if (json%is_verbose) then write(output_unit,'(A)') '***********************' write(output_unit,'(A)') 'JSON-Fortran Exception: '//trim(msg) !call backtrace() ! gfortran (use -fbacktrace -fall-intrinsics flags) #ifdef __INTEL_COMPILER call tracebackqq(user_exit_code=-1) ! print a traceback and return #endif write(output_unit,'(A)') '***********************' end if end subroutine json_throw_exception !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_throw_exception]], where `msg` is kind=CDK. subroutine wrap_json_throw_exception(json,msg) implicit none class(json_core),intent(inout) :: json character(kind=CDK,len=*),intent(in) :: msg !! the error message call json%throw_exception(to_unicode(msg)) end subroutine wrap_json_throw_exception !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 12/4/2013 ! ! Retrieve error code from the [[json_core(type)]]. ! This should be called after `parse` to check for errors. ! If an error is thrown, before using the class again, [[json_initialize]] ! should be called to clean up before it is used again. ! !### Example ! !````fortran ! type(json_file) :: json ! logical :: status_ok ! character(kind=CK,len=:),allocatable :: error_msg ! call json%load_file(filename='myfile.json') ! call json%check_for_errors(status_ok, error_msg) ! if (.not. status_ok) then ! write(*,*) 'Error: '//error_msg ! call json%clear_exceptions() ! call json%destroy() ! end if !```` ! !### See also ! * [[json_failed]] subroutine json_check_for_errors(json,status_ok,error_msg) implicit none class(json_core),intent(inout) :: json logical(LK),intent(out) :: status_ok !! true if there were no errors character(kind=CK,len=:),allocatable,intent(out) :: error_msg !! the error message (if there were errors) status_ok = .not. json%exception_thrown if (.not. status_ok) then if (allocated(json%err_message)) then error_msg = json%err_message else error_msg = 'Unknown error.' end if else error_msg = CK_'' end if end subroutine json_check_for_errors !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 12/5/2013 ! ! Logical function to indicate if an exception has been thrown in a [[json_core(type)]]. ! !### Example ! !````fortran ! type(json_core) :: json ! type(json_value),pointer :: p ! logical :: status_ok ! character(len=:),allocatable :: error_msg ! call json%parse(filename='myfile.json',p) ! if (json%failed()) then ! call json%check_for_errors(status_ok, error_msg) ! write(*,*) 'Error: '//error_msg ! call json%clear_exceptions() ! call json%destroy(p) ! end if !```` ! ! Note that [[json_file]] contains a wrapper for this routine, which is used like: !````fortran ! type(json_file) :: f ! logical :: status_ok ! character(len=:),allocatable :: error_msg ! call f%load_file(filename='myfile.json') ! if (f%failed()) then ! call f%check_for_errors(status_ok, error_msg) ! write(*,*) 'Error: '//error_msg ! call f%clear_exceptions() ! call f%destroy() ! end if !```` ! !### See also ! * [[json_check_for_errors]] pure function json_failed(json) result(failed) implicit none class(json_core),intent(in) :: json logical(LK) :: failed !! will be true if an exception !! has been thrown. failed = json%exception_thrown end function json_failed !***************************************************************************************** !***************************************************************************************** !> ! Allocate a [[json_value]] pointer variable. ! This should be called before adding data to it. ! !### Example ! !````fortran ! type(json_value),pointer :: var ! call json_value_create(var) ! call to_double(var,1.0_RK) !```` ! !### Notes ! 1. This routine does not check for exceptions. ! 2. The pointer should not already be allocated, or a memory leak will occur. subroutine json_value_create(p) implicit none type(json_value),pointer :: p nullify(p) allocate(p) end subroutine json_value_create !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 1/22/2014 ! ! Destroy a [[json_value]] linked-list structure. ! !@note The original FSON version of this ! routine was not properly freeing the memory. ! It was rewritten. recursive subroutine json_value_destroy(json,p,destroy_next) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p !! variable to destroy logical(LK),intent(in),optional :: destroy_next !! if true, then `p%next` !! is also destroyed (default is true) logical(LK) :: des_next type(json_value), pointer :: child if (associated(p)) then if (present(destroy_next)) then des_next = destroy_next else des_next = .true. end if if (allocated(p%name)) deallocate(p%name) call destroy_json_data(p) if (associated(p%children)) then do while (p%n_children > 0) child => p%children if (associated(child)) then p%children => p%children%next p%n_children = p%n_children - 1 call json_value_destroy(json,child,.false.) else call json%throw_exception('Error in json_value_destroy: '//& 'Malformed JSON linked list') exit end if end do nullify(p%children) nullify(child) end if if (associated(p%next) .and. des_next) call json_value_destroy(json,p%next) if (associated(p%previous)) nullify(p%previous) if (associated(p%parent)) nullify(p%parent) if (associated(p%tail)) nullify(p%tail) deallocate(p) nullify(p) end if end subroutine json_value_destroy !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 9/9/2014 ! ! Remove a [[json_value]] (and all its children) ! from a linked-list structure, preserving the rest of the structure. ! !### Examples ! ! To extract an object from one JSON structure, and add it to another: !````fortran ! type(json_core) :: json ! type(json_value),pointer :: json1,json2,p ! logical :: found ! !create and populate json1 and json2 ! call json%get(json1,'name',p,found) ! get pointer to name element of json1 ! call json%remove(p,destroy=.false.) ! remove it from json1 (don't destroy) ! call json%add(json2,p) ! add it to json2 !```` ! ! To remove an object from a JSON structure (and destroy it): !````fortran ! type(json_core) :: json ! type(json_value),pointer :: json1,p ! logical :: found ! !create and populate json1 ! call json%get(json1,'name',p,found) ! get pointer to name element of json1 ! call json%remove(p) ! remove and destroy it !```` ! !### History ! * Jacob Williams : 12/28/2014 : added destroy optional argument. subroutine json_value_remove(json,p,destroy) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p logical(LK),intent(in),optional :: destroy !! If destroy is not present, it is also destroyed. !! If destroy is present and true, it is destroyed. !! If destroy is present and false, it is not destroyed. type(json_value),pointer :: parent,previous,next logical(LK) :: destroy_it if (associated(p)) then !optional input argument: if (present(destroy)) then destroy_it = destroy else destroy_it = .true. end if if (associated(p%parent)) then parent => p%parent if (associated(p%next)) then !there are later items in the list: next => p%next nullify(p%next) if (associated(p%previous)) then !there are earlier items in the list previous => p%previous previous%next => next next%previous => previous else !this is the first item in the list parent%children => next nullify(next%previous) end if else if (associated(p%previous)) then !there are earlier items in the list: previous => p%previous nullify(previous%next) parent%tail => previous else !this is the only item in the list: nullify(parent%children) nullify(parent%tail) end if end if parent%n_children = parent%n_children - 1 end if if (destroy_it) call json%destroy(p) end if end subroutine json_value_remove !***************************************************************************************** !***************************************************************************************** !> ! Replace `p1` with `p2` in a JSON structure. ! !@note The replacement is done using an insert and remove ! See [[json_value_insert_after]] and [[json_value_remove]] ! for details. subroutine json_value_replace(json,p1,p2,destroy) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p1 !! the item to replace type(json_value),pointer :: p2 !! item to take the place of `p1` logical(LK),intent(in),optional :: destroy !! Should `p1` also be destroyed !! (default is True). Normally, !! this should be true to avoid !! a memory leak. logical(LK) :: destroy_p1 !! if `p1` is to be destroyed if (present(destroy)) then destroy_p1 = destroy else destroy_p1 = .true. ! default end if call json%insert_after(p1,p2) call json%remove(p1,destroy_p1) end subroutine json_value_replace !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 4/26/2016 ! ! Swap two elements in a JSON structure. ! All of the children are carried along as well. ! !@note If both are not associated, then an error is thrown. ! !@note The assumption here is that both variables are part of a valid ! [[json_value]] linked list (so the normal `parent`, `previous`, ! `next`, etc. pointers are properly associated if necessary). ! !@warning This cannot be used to swap a parent/child pair, since that ! could lead to a circular linkage. An exception is thrown if ! this is tried. ! !@warning There are also other situations where using this routine may ! produce a malformed JSON structure, such as moving an array ! element outside of an array. This is not checked for. ! !@note If `p1` and `p2` have a common parent, it is always safe to swap them. subroutine json_value_swap(json,p1,p2) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p1 type(json_value),pointer :: p2 logical :: same_parent,first_last,adjacent type(json_value),pointer :: a,b if (json%exception_thrown) return !both have to be associated: if (associated(p1) .and. associated(p2)) then !simple check to make sure that they both !aren't pointing to the same thing: if (.not. associated(p1,p2)) then !we will not allow swapping an item with one of its descendants: if (json%is_child_of(p1,p2) .or. json%is_child_of(p2,p1)) then call json%throw_exception('Error in json_value_swap: '//& 'cannot swap an item with one of its descendants') else same_parent = ( associated(p1%parent) .and. & associated(p2%parent) .and. & associated(p1%parent,p2%parent) ) if (same_parent) then !if p1,p2 are the first,last or last,first !children of a common parent first_last = (associated(p1%parent%children,p1) .and. & associated(p2%parent%tail,p2)) .or. & (associated(p1%parent%tail,p1) .and. & associated(p2%parent%children,p2)) else first_last = .false. end if !first, we fix children,tail pointers: if (same_parent .and. first_last) then !this is all we have to do for the parent in this case: call swap_pointers(p1%parent%children,p2%parent%tail) else if (same_parent .and. .not. first_last) then if (associated(p1%parent%children,p1)) then p1%parent%children => p2 ! p1 is the first child of the parent else if (associated(p1%parent%children,p2)) then p1%parent%children => p1 ! p2 is the first child of the parent end if if (associated(p1%parent%tail,p1)) then p1%parent%tail => p2 ! p1 is the last child of the parent else if (associated(p1%parent%tail,p2)) then p1%parent%tail => p1 ! p2 is the last child of the parent end if else ! general case: different parents if (associated(p1%parent)) then if (associated(p1%parent%children,p1)) p1%parent%children => p2 if (associated(p1%parent%tail,p1)) p1%parent%tail => p2 end if if (associated(p2%parent)) then if (associated(p2%parent%children,p2)) p2%parent%children => p1 if (associated(p2%parent%tail,p2)) p2%parent%tail => p1 end if call swap_pointers(p1%parent, p2%parent) end if !now, have to fix previous,next pointers: !first, see if they are adjacent: adjacent = associated(p1%next,p2) .or. & associated(p2%next,p1) if (associated(p2%next,p1)) then !p2,p1 a => p2 b => p1 else !p1,p2 (or not adjacent) a => p1 b => p2 end if if (associated(a%previous)) a%previous%next => b if (associated(b%next)) b%next%previous => a if (adjacent) then !a comes before b in the original list b%previous => a%previous a%next => b%next a%previous => b b%next => a else if (associated(a%next)) a%next%previous => b if (associated(b%previous)) b%previous%next => a call swap_pointers(a%previous,b%previous) call swap_pointers(a%next, b%next) end if end if else call json%throw_exception('Error in json_value_swap: '//& 'both pointers must be associated') end if end if contains pure subroutine swap_pointers(s1,s2) implicit none type(json_value),pointer,intent(inout) :: s1 type(json_value),pointer,intent(inout) :: s2 type(json_value),pointer :: tmp !! temporary pointer if (.not. associated(s1,s2)) then tmp => s1 s1 => s2 s2 => tmp end if end subroutine swap_pointers end subroutine json_value_swap !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 4/28/2016 ! ! Returns True if `p2` is a descendant of `p1` ! (i.e, a child, or a child of child, etc.) function json_value_is_child_of(json,p1,p2) result(is_child_of) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p1 type(json_value),pointer :: p2 logical(LK) :: is_child_of is_child_of = .false. if (json%exception_thrown) return if (associated(p1) .and. associated(p2)) then if (associated(p1%children)) then call json%traverse(p1%children,is_child_of_callback) end if end if contains subroutine is_child_of_callback(json,p,finished) !! Traverse until `p` is `p2`. implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: p logical(LK),intent(out) :: finished is_child_of = associated(p,p2) finished = is_child_of ! stop searching if found end subroutine is_child_of_callback end function json_value_is_child_of !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 5/2/2016 ! ! Validate a [[json_value]] linked list by checking to make sure ! all the pointers are properly associated, arrays and objects ! have the correct number of children, and the correct data is ! allocated for the variable types. ! ! It recursively traverses the entire structure and checks every element. ! !@note This routine does not check or throw any exceptions. subroutine json_value_validate(json,p,is_valid,error_msg) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: p logical(LK),intent(out) :: is_valid !! True if the structure is valid. character(kind=CK,len=:),allocatable,intent(out) :: error_msg !! if not valid, this will contain !! a description of the problem if (associated(p)) then is_valid = .true. call check_if_valid(p,require_parent=associated(p%parent)) else error_msg = 'The pointer is not associated' is_valid = .false. end if contains recursive subroutine check_if_valid(p,require_parent) implicit none type(json_value),pointer,intent(in) :: p logical,intent(in) :: require_parent !! the first one may be a root (so no parent), !! but all descendants must have a parent. integer :: i !! counter type(json_value),pointer :: element type(json_value),pointer :: previous if (is_valid .and. associated(p)) then ! data type: select case (p%var_type) case(json_null,json_object,json_array) if (allocated(p%log_value) .or. allocated(p%int_value) .or. & allocated(p%dbl_value) .or. allocated(p%str_value)) then error_msg = 'incorrect data allocated for '//& 'json_null, json_object, or json_array variable type' is_valid = .false. return end if case(json_logical) if (.not. allocated(p%log_value)) then error_msg = 'log_value should be allocated for json_logical variable type' is_valid = .false. return else if (allocated(p%int_value) .or. & allocated(p%dbl_value) .or. allocated(p%str_value)) then error_msg = 'incorrect data allocated for json_logical variable type' is_valid = .false. return end if case(json_integer) if (.not. allocated(p%int_value)) then error_msg = 'int_value should be allocated for json_integer variable type' is_valid = .false. return else if (allocated(p%log_value) .or. & allocated(p%dbl_value) .or. allocated(p%str_value)) then error_msg = 'incorrect data allocated for json_integer variable type' is_valid = .false. return end if case(json_double) if (.not. allocated(p%dbl_value)) then error_msg = 'dbl_value should be allocated for json_double variable type' is_valid = .false. return else if (allocated(p%log_value) .or. allocated(p%int_value) .or. & allocated(p%str_value)) then error_msg = 'incorrect data allocated for json_double variable type' is_valid = .false. return end if case(json_string) if (.not. allocated(p%str_value)) then error_msg = 'str_value should be allocated for json_string variable type' is_valid = .false. return else if (allocated(p%log_value) .or. allocated(p%int_value) .or. & allocated(p%dbl_value)) then error_msg = 'incorrect data allocated for json_string variable type' is_valid = .false. return end if case default error_msg = 'invalid JSON variable type' is_valid = .false. return end select if (require_parent .and. .not. associated(p%parent)) then error_msg = 'parent pointer is not associated' is_valid = .false. return end if if (.not. allocated(p%name)) then if (associated(p%parent)) then if (p%parent%var_type/=json_array) then error_msg = 'JSON variable must have a name if not an '//& 'array element or the root' is_valid = .false. return end if end if end if if (associated(p%children) .neqv. associated(p%tail)) then error_msg = 'both children and tail pointers must be associated' is_valid = .false. return end if ! now, check next one: if (associated(p%next)) then call check_if_valid(p%next,require_parent=require_parent) end if if (associated(p%children)) then if (p%var_type/=json_array .and. p%var_type/=json_object) then error_msg = 'only arrays and objects can have children' is_valid = .false. return end if ! first validate children pointers: previous => null() element => p%children do i = 1, p%n_children if (.not. associated(element%parent,p)) then error_msg = 'child''s parent pointer not properly associated' is_valid = .false. return end if if (i==1 .and. associated(element%previous)) then error_msg = 'first child shouldn''t have a previous' is_valid = .false. return end if if (i<p%n_children .and. .not. associated(element%next)) then error_msg = 'not enough children' is_valid = .false. return end if if (i==p%n_children .and. associated(element%next)) then error_msg = 'too many children' is_valid = .false. return end if if (i>1) then if (.not. associated(previous,element%previous)) then error_msg = 'previous pointer not properly associated' is_valid = .false. return end if end if if (i==p%n_children .and. & .not. associated(element%parent%tail,element)) then error_msg = 'parent''s tail pointer not properly associated' is_valid = .false. return end if if (i<p%n_children) then !setup next case: previous => element element => element%next end if end do !now check all the children: call check_if_valid(p%children,require_parent=.true.) end if end if end subroutine check_if_valid end subroutine json_value_validate !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 12/6/2014 ! ! Given the path string, remove the variable from ! the [[json_value]] structure, if it exists. subroutine json_value_remove_if_present(json,p,name) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CK,len=*),intent(in) :: name type(json_value),pointer :: p_var logical(LK) :: found call json%get(p,name,p_var,found) if (found) call json%remove(p_var) end subroutine json_value_remove_if_present !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_value_remove_if_present]], where `name` is kind=CDK. subroutine wrap_json_value_remove_if_present(json,p,name) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CDK,len=*),intent(in) :: name call json%remove_if_present(p,to_unicode(name)) end subroutine wrap_json_value_remove_if_present !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 12/6/2014 ! ! Given the path string, if the variable is present, ! and is a scalar, then update its value. ! If it is not present, then create it and set its value. subroutine json_update_logical(json,p,path,val,found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CK,len=*),intent(in) :: path logical(LK),intent(in) :: val logical(LK),intent(out) :: found type(json_value),pointer :: p_var integer(IK) :: var_type call json%get(p,path,p_var,found) if (found) then call json%info(p_var,var_type) select case (var_type) case (json_null,json_logical,json_integer,json_double,json_string) call to_logical(p_var,val) !update the value case default found = .false. call json%throw_exception('Error in json_update_logical: '//& 'the variable is not a scalar value') end select else call json%add_by_path(p,path,val) !add the new element end if end subroutine json_update_logical !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_update_logical]], where `path` is kind=CDK. subroutine wrap_json_update_logical(json,p,path,val,found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CDK,len=*),intent(in) :: path logical(LK),intent(in) :: val logical(LK),intent(out) :: found call json%update(p,to_unicode(path),val,found) end subroutine wrap_json_update_logical !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 12/6/2014 ! ! Given the path string, if the variable is present, ! and is a scalar, then update its value. ! If it is not present, then create it and set its value. subroutine json_update_double(json,p,path,val,found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CK,len=*),intent(in) :: path real(RK),intent(in) :: val logical(LK),intent(out) :: found type(json_value),pointer :: p_var integer(IK) :: var_type call json%get(p,path,p_var,found) if (found) then call json%info(p_var,var_type) select case (var_type) case (json_null,json_logical,json_integer,json_double,json_string) call to_double(p_var,val) !update the value case default found = .false. call json%throw_exception('Error in json_update_double: '//& 'the variable is not a scalar value') end select else call json%add_by_path(p,path,val) !add the new element end if end subroutine json_update_double !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_update_double]], where `path` is kind=CDK. subroutine wrap_json_update_double(json,p,path,val,found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CDK,len=*),intent(in) :: path real(RK),intent(in) :: val logical(LK),intent(out) :: found call json%update(p,to_unicode(path),val,found) end subroutine wrap_json_update_double !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 12/6/2014 ! ! Given the path string, if the variable is present, ! and is a scalar, then update its value. ! If it is not present, then create it and set its value. subroutine json_update_integer(json,p,path,val,found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CK,len=*),intent(in) :: path integer(IK),intent(in) :: val logical(LK),intent(out) :: found type(json_value),pointer :: p_var integer(IK) :: var_type call json%get(p,path,p_var,found) if (found) then call json%info(p_var,var_type) select case (var_type) case (json_null,json_logical,json_integer,json_double,json_string) call to_integer(p_var,val) !update the value case default found = .false. call json%throw_exception('Error in json_update_integer: '//& 'the variable is not a scalar value') end select else call json%add_by_path(p,path,val) !add the new element end if end subroutine json_update_integer !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_update_integer]], where `path` is kind=CDK. subroutine wrap_json_update_integer(json,p,path,val,found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CDK,len=*),intent(in) :: path integer(IK),intent(in) :: val logical(LK),intent(out) :: found call json%update(p,to_unicode(path),val,found) end subroutine wrap_json_update_integer !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 12/6/2014 ! ! Given the path string, if the variable is present, ! and is a scalar, then update its value. ! If it is not present, then create it and set its value. subroutine json_update_string(json,p,path,val,found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CK,len=*),intent(in) :: path character(kind=CK,len=*),intent(in) :: val logical(LK),intent(out) :: found type(json_value),pointer :: p_var integer(IK) :: var_type call json%get(p,path,p_var,found) if (found) then call json%info(p_var,var_type) select case (var_type) case (json_null,json_logical,json_integer,json_double,json_string) call to_string(p_var,val) !update the value case default found = .false. call json%throw_exception('Error in json_update_string: '//& 'the variable is not a scalar value') end select else call json%add_by_path(p,path,val) !add the new element end if end subroutine json_update_string !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_update_string]], where `path` and `value` are kind=CDK. subroutine wrap_json_update_string(json,p,path,val,found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CDK,len=*),intent(in) :: path character(kind=CDK,len=*),intent(in) :: val logical(LK),intent(out) :: found call json%update(p,to_unicode(path),to_unicode(val),found) end subroutine wrap_json_update_string !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_update_string]], where `path` is kind=CDK. subroutine json_update_string_name_ascii(json,p,path,val,found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CDK,len=*),intent(in) :: path character(kind=CK, len=*),intent(in) :: val logical(LK),intent(out) :: found call json%update(p,to_unicode(path),val,found) end subroutine json_update_string_name_ascii !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_update_string]], where `val` is kind=CDK. subroutine json_update_string_val_ascii(json,p,path,val,found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CK, len=*),intent(in) :: path character(kind=CDK,len=*),intent(in) :: val logical(LK),intent(out) :: found call json%update(p,path,to_unicode(val),found) end subroutine json_update_string_val_ascii !***************************************************************************************** !***************************************************************************************** !> ! Adds `member` as a child of `p`. subroutine json_value_add_member(json,p,member) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p type(json_value),pointer :: member !! the child member !! to add to `p` if (.not. json%exception_thrown) then ! associate the parent member%parent => p ! add to linked list if (associated(p%children)) then p%tail%next => member member%previous => p%tail else p%children => member member%previous => null() !first in the list end if ! new member is now the last one in the list p%tail => member p%n_children = p%n_children + 1 end if end subroutine json_value_add_member !***************************************************************************************** !***************************************************************************************** !> ! Inserts `element` after `p`, and updates the JSON structure accordingly. ! !### Example ! !````fortran ! program test ! use json_module ! implicit none ! logical(json_LK) :: found ! type(json_core) :: json ! type(json_value),pointer :: p,new,element ! call json%parse(file='myfile.json', p=p) ! call json%get(p,'x(3)',element,found) ! get pointer to an array element in the file ! call json%create_integer(new,1,'') ! create a new element ! call json%insert_after(element,new) ! insert new element after x(3) ! call json%print(p,'myfile2.json') ! write it to a file ! call json%destroy(p) ! cleanup ! end program test !```` ! !### Details ! ! * This routine can be used to insert a new element (or set of elements) ! into an array or object at a specific index. ! See [[json_value_insert_after_child_by_index]] ! * Children and subsequent elements of `element` are carried along. ! * If the inserted elements are part of an existing list, then ! they are removed from that list. ! !```` ! p ! [1] - [2] - [3] - [4] ! | ! [5] - [6] - [7] n=3 elements inserted ! element last ! ! Result is: ! ! [1] - [2] - [5] - [6] - [7] - [3] - [4] ! !```` subroutine json_value_insert_after(json,p,element) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p !! a value from a JSON structure !! (presumably, this is a child of !! an object or array). type(json_value),pointer :: element !! the element to insert after `p` type(json_value),pointer :: parent !! the parent of `p` type(json_value),pointer :: next !! temp pointer for traversing structure type(json_value),pointer :: last !! the last of the items being inserted integer :: n !! number of items being inserted if (.not. json%exception_thrown) then parent => p%parent ! set first parent of inserted list: element%parent => parent ! Count the number of inserted elements. ! and set their parents. n = 1 ! initialize counter next => element%next last => element do if (.not. associated(next)) exit n = n + 1 next%parent => parent last => next next => next%next end do if (associated(parent)) then ! update parent's child counter: parent%n_children = parent%n_children + n ! if p is last of parents children then ! also have to update parent tail pointer: if (associated(parent%tail,p)) then parent%tail => last end if end if if (associated(element%previous)) then ! element is apparently part of an existing list, ! so have to update that as well. if (associated(element%previous%parent)) then element%previous%parent%n_children = & element%previous%parent%n_children - n element%previous%parent%tail => & element%previous ! now the last one in the list else ! this would be a memory leak if the previous entries ! are not otherwise being pointed too ! [throw an error in this case???] end if !remove element from the other list: element%previous%next => null() end if element%previous => p if (associated(p%next)) then ! if there are any in the list after p: last%next => p%next last%next%previous => element else last%next => null() end if p%next => element end if end subroutine json_value_insert_after !***************************************************************************************** !***************************************************************************************** !> ! Inserts `element` after the `idx`-th child of `p`, ! and updates the JSON structure accordingly. This is just ! a wrapper for [[json_value_insert_after]]. subroutine json_value_insert_after_child_by_index(json,p,idx,element) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p !! a JSON object or array. integer(IK),intent(in) :: idx !! the index of the child of `p` to !! insert the new element after !! (this is a 1-based Fortran !! style array index) type(json_value),pointer :: element !! the element to insert type(json_value),pointer :: tmp !! for getting the `idx`-th child of `p` if (.not. json%exception_thrown) then ! get the idx-th child of p: call json%get_child(p,idx,tmp) ! call json_value_insert_after: if (.not. json%exception_thrown) call json%insert_after(tmp,element) end if end subroutine json_value_insert_after_child_by_index !***************************************************************************************** !***************************************************************************************** !> ! Add a new member (`json_value` pointer) to a JSON structure, given the path. ! !@warning If the path points to an existing variable in the structure, ! then this routine will destroy it and replace it with the ! new value. subroutine json_add_member_by_path(json,me,path,p,found,was_created) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me !! the JSON structure character(kind=CK,len=*),intent(in) :: path !! the path to the variable type(json_value),pointer,intent(in) :: p !! the value to add logical(LK),intent(out),optional :: found !! if the variable was found logical(LK),intent(out),optional :: was_created !! if the variable had to be created type(json_value),pointer :: tmp character(kind=CK,len=:),allocatable :: name !! name of the variable if ( .not. json%exception_thrown ) then if (.not. associated(p)) then call json%throw_exception('Error in json_add_member_by_path:'//& ' Input pointer p is not associated.') if (present(found)) then found = .false. call json%clear_exceptions() end if if ( present(was_created) ) was_created = .false. else ! return a pointer to the path (possibly creating it) call json%create(me,path,tmp,found,was_created) if (.not. associated(tmp)) then call json%throw_exception('Error in json_add_member_by_path:'//& ' Unable to resolve path: '//trim(path)) if (present(found)) then found = .false. call json%clear_exceptions() end if else call json%info(tmp,name=name) ! replace it with the new one: call json%replace(tmp,p,destroy=.true.) call json%rename(p,name) end if end if else if ( present(found) ) found = .false. if ( present(was_created) ) was_created = .false. end if end subroutine json_add_member_by_path !***************************************************************************************** !***************************************************************************************** !> ! Wrapper to [[json_add_member_by_path]] where "path" is kind=CDK. subroutine wrap_json_add_member_by_path(json,me,path,p,found,was_created) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me !! the JSON structure character(kind=CDK,len=*),intent(in) :: path !! the path to the variable type(json_value),pointer,intent(in) :: p !! the value to add logical(LK),intent(out),optional :: found !! if the variable was found logical(LK),intent(out),optional :: was_created !! if the variable had to be created call json%json_add_member_by_path(me,to_unicode(path),p,found,was_created) end subroutine wrap_json_add_member_by_path !***************************************************************************************** !***************************************************************************************** !> ! Add an integer value to a [[json_value]], given the path. ! !@warning If the path points to an existing variable in the structure, ! then this routine will destroy it and replace it with the ! new value. subroutine json_add_integer_by_path(json,me,path,value,found,was_created) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me !! the JSON structure character(kind=CK,len=*),intent(in) :: path !! the path to the variable integer(IK),intent(in) :: value !! the value to add logical(LK),intent(out),optional :: found !! if the variable was found logical(LK),intent(out),optional :: was_created !! if the variable had to be created type(json_value),pointer :: p type(json_value),pointer :: tmp character(kind=CK,len=:),allocatable :: name !! variable name if ( .not. json%exception_thrown ) then nullify(p) ! return a pointer to the path (possibly creating it) ! If the variable had to be created, then ! it will be a json_null variable. call json%create(me,path,p,found,was_created) if (.not. associated(p)) then call json%throw_exception('Error in json_add_integer_by_path:'//& ' Unable to resolve path: '//trim(path)) if (present(found)) then found = .false. call json%clear_exceptions() end if else !NOTE: a new object is created, and the old one ! is replaced and destroyed. This is to ! prevent memory leaks if the type is ! being changed (for example, if an array ! is being replaced with a scalar). if (p%var_type==json_integer) then p%int_value = value else call json%info(p,name=name) call json%create_integer(tmp,value,name) call json%replace(p,tmp,destroy=.true.) end if end if else if ( present(found) ) found = .false. if ( present(was_created) ) was_created = .false. end if end subroutine json_add_integer_by_path !***************************************************************************************** !***************************************************************************************** !> ! Wrapper to [[json_add_integer_by_path]] where "path" is kind=CDK. subroutine wrap_json_add_integer_by_path(json,me,path,value,found,was_created) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me !! the JSON structure character(kind=CDK,len=*),intent(in) :: path !! the path to the variable integer(IK),intent(in) :: value !! the value to add logical(LK),intent(out),optional :: found !! if the variable was found logical(LK),intent(out),optional :: was_created !! if the variable had to be created call json%json_add_integer_by_path(me,to_unicode(path),value,found,was_created) end subroutine wrap_json_add_integer_by_path !***************************************************************************************** !***************************************************************************************** !> ! Add an double value to a [[json_value]], given the path. ! !@warning If the path points to an existing variable in the structure, ! then this routine will destroy it and replace it with the ! new value. subroutine json_add_double_by_path(json,me,path,value,found,was_created) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me !! the JSON structure character(kind=CK,len=*),intent(in) :: path !! the path to the variable real(RK),intent(in) :: value !! the value to add logical(LK),intent(out),optional :: found !! if the variable was found logical(LK),intent(out),optional :: was_created !! if the variable had to be created type(json_value),pointer :: p type(json_value),pointer :: tmp character(kind=CK,len=:),allocatable :: name !! variable name if ( .not. json%exception_thrown ) then nullify(p) ! return a pointer to the path (possibly creating it) ! If the variable had to be created, then ! it will be a json_null variable. call json%create(me,path,p,found,was_created) if (.not. associated(p)) then call json%throw_exception('Error in json_add_double_by_path:'//& ' Unable to resolve path: '//trim(path)) if (present(found)) then found = .false. call json%clear_exceptions() end if else !NOTE: a new object is created, and the old one ! is replaced and destroyed. This is to ! prevent memory leaks if the type is ! being changed (for example, if an array ! is being replaced with a scalar). if (p%var_type==json_double) then p%dbl_value = value else call json%info(p,name=name) call json%create_double(tmp,value,name) call json%replace(p,tmp,destroy=.true.) end if end if else if ( present(found) ) found = .false. if ( present(was_created) ) was_created = .false. end if end subroutine json_add_double_by_path !***************************************************************************************** !***************************************************************************************** !> ! Wrapper to [[json_add_double_by_path]] where "path" is kind=CDK. subroutine wrap_json_add_double_by_path(json,me,path,value,found,was_created) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me !! the JSON structure character(kind=CDK,len=*),intent(in) :: path !! the path to the variable real(RK),intent(in) :: value !! the value to add logical(LK),intent(out),optional :: found !! if the variable was found logical(LK),intent(out),optional :: was_created !! if the variable had to be created call json%json_add_double_by_path(me,to_unicode(path),value,found,was_created) end subroutine wrap_json_add_double_by_path !***************************************************************************************** !***************************************************************************************** !> ! Add a logical value to a [[json_value]], given the path. ! !@warning If the path points to an existing variable in the structure, ! then this routine will destroy it and replace it with the ! new value. subroutine json_add_logical_by_path(json,me,path,value,found,was_created) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me !! the JSON structure character(kind=CK,len=*),intent(in) :: path !! the path to the variable logical(LK),intent(in) :: value !! the value to add logical(LK),intent(out),optional :: found !! if the variable was found logical(LK),intent(out),optional :: was_created !! if the variable had to be created type(json_value),pointer :: p type(json_value),pointer :: tmp character(kind=CK,len=:),allocatable :: name !! variable name if ( .not. json%exception_thrown ) then nullify(p) ! return a pointer to the path (possibly creating it) ! If the variable had to be created, then ! it will be a json_null variable. call json%create(me,path,p,found,was_created) if (.not. associated(p)) then call json%throw_exception('Error in json_add_logical_by_path:'//& ' Unable to resolve path: '//trim(path)) if (present(found)) then found = .false. call json%clear_exceptions() end if else !NOTE: a new object is created, and the old one ! is replaced and destroyed. This is to ! prevent memory leaks if the type is ! being changed (for example, if an array ! is being replaced with a scalar). if (p%var_type==json_logical) then p%log_value = value else call json%info(p,name=name) call json%create_logical(tmp,value,name) call json%replace(p,tmp,destroy=.true.) end if end if else if ( present(found) ) found = .false. if ( present(was_created) ) was_created = .false. end if end subroutine json_add_logical_by_path !***************************************************************************************** !***************************************************************************************** !> ! Wrapper to [[json_add_logical_by_path]] where "path" is kind=CDK. subroutine wrap_json_add_logical_by_path(json,me,path,value,found,was_created) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me !! the JSON structure character(kind=CDK,len=*),intent(in) :: path !! the path to the variable logical(LK),intent(in) :: value !! the value to add logical(LK),intent(out),optional :: found !! if the variable was found logical(LK),intent(out),optional :: was_created !! if the variable had to be created call json%json_add_logical_by_path(me,to_unicode(path),value,found,was_created) end subroutine wrap_json_add_logical_by_path !***************************************************************************************** !***************************************************************************************** !> ! Add a string value to a [[json_value]], given the path. ! !@warning If the path points to an existing variable in the structure, ! then this routine will destroy it and replace it with the ! new value. subroutine json_add_string_by_path(json,me,path,value,found,was_created) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me !! the JSON structure character(kind=CK,len=*),intent(in) :: path !! the path to the variable character(kind=CK,len=*),intent(in) :: value !! the value to add logical(LK),intent(out),optional :: found !! if the variable was found logical(LK),intent(out),optional :: was_created !! if the variable had to be created type(json_value),pointer :: p type(json_value),pointer :: tmp character(kind=CK,len=:),allocatable :: name !! variable name if ( .not. json%exception_thrown ) then nullify(p) ! return a pointer to the path (possibly creating it) ! If the variable had to be created, then ! it will be a json_null variable. call json%create(me,path,p,found,was_created) if (.not. associated(p)) then call json%throw_exception('Error in json_add_string_by_path:'//& ' Unable to resolve path: '//trim(path)) if (present(found)) then found = .false. call json%clear_exceptions() end if else !NOTE: a new object is created, and the old one ! is replaced and destroyed. This is to ! prevent memory leaks if the type is ! being changed (for example, if an array ! is being replaced with a scalar). if (p%var_type==json_string) then p%str_value = value else call json%info(p,name=name) call json%create_string(tmp,value,name) call json%replace(p,tmp,destroy=.true.) end if end if else if ( present(found) ) found = .false. if ( present(was_created) ) was_created = .false. end if end subroutine json_add_string_by_path !***************************************************************************************** !***************************************************************************************** !> ! Wrapper to [[json_add_string_by_path]] where "path" is kind=CDK. subroutine wrap_json_add_string_by_path(json,me,path,value,found,was_created) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me !! the JSON structure character(kind=CDK,len=*),intent(in) :: path !! the path to the variable character(kind=CDK,len=*),intent(in) :: value !! the value to add logical(LK),intent(out),optional :: found !! if the variable was found logical(LK),intent(out),optional :: was_created !! if the variable had to be created call json%json_add_string_by_path(me,to_unicode(path),to_unicode(value),found,was_created) end subroutine wrap_json_add_string_by_path !***************************************************************************************** !***************************************************************************************** !> ! Wrapper for [[json_add_string_by_path]] where "path" is kind=CDK. subroutine json_add_string_by_path_path_ascii(json,me,path,value,found,was_created) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me !! the JSON structure character(kind=CDK,len=*),intent(in) :: path !! the path to the variable character(kind=CK,len=*),intent(in) :: value !! the value to add logical(LK),intent(out),optional :: found !! if the variable was found logical(LK),intent(out),optional :: was_created !! if the variable had to be created call json%json_add_string_by_path(me,to_unicode(path),value,found,was_created) end subroutine json_add_string_by_path_path_ascii !***************************************************************************************** !***************************************************************************************** !> ! Wrapper for [[json_add_string_by_path]] where "value" is kind=CDK. subroutine json_add_string_by_path_value_ascii(json,me,path,value,found,was_created) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me !! the JSON structure character(kind=CK,len=*),intent(in) :: path !! the path to the variable character(kind=CDK,len=*),intent(in) :: value !! the value to add logical(LK),intent(out),optional :: found !! if the variable was found logical(LK),intent(out),optional :: was_created !! if the variable had to be created call json%json_add_string_by_path(me,path,to_unicode(value),found,was_created) end subroutine json_add_string_by_path_value_ascii !***************************************************************************************** !***************************************************************************************** !> ! Wrapper to [[json_add_integer_by_path]] for adding an integer vector by path. subroutine json_add_integer_vec_by_path(json,me,path,value,found,was_created) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me !! the JSON structure character(kind=CK,len=*),intent(in) :: path !! the path to the variable integer(IK),dimension(:),intent(in) :: value !! the vector to add logical(LK),intent(out),optional :: found !! if the variable was found logical(LK),intent(out),optional :: was_created !! if the variable had to be created type(json_value),pointer :: p !! pointer to path (which may exist) type(json_value),pointer :: var !! new variable that is created integer(IK) :: i !! counter character(kind=CK,len=:),allocatable :: name !! the variable name logical(LK) :: p_found !! if the path was successfully found (or created) if ( .not. json%exception_thrown ) then !get a pointer to the variable !(creating it if necessary) call json%create(me,path,p,found=p_found) if (p_found) then call json%info(p,name=name) ! want to keep the existing name call json%create_array(var,name) ! create a new array variable call json%replace(p,var,destroy=.true.) ! replace p with this array (destroy p) !populate each element of the array: do i=1,size(value) call json%add(var, CK_'', value(i)) end do end if else if ( present(found) ) found = .false. if ( present(was_created) ) was_created = .false. end if end subroutine json_add_integer_vec_by_path !***************************************************************************************** !***************************************************************************************** !> ! Wrapper for [[json_add_integer_vec_by_path]] where "path" is kind=CDK). subroutine wrap_json_add_integer_vec_by_path(json,me,path,value,found,was_created) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me !! the JSON structure character(kind=CDK,len=*),intent(in) :: path !! the path to the variable integer(IK),dimension(:),intent(in) :: value !! the vector to add logical(LK),intent(out),optional :: found !! if the variable was found logical(LK),intent(out),optional :: was_created !! if the variable had to be created call json%json_add_integer_vec_by_path(me,to_unicode(path),value,found,was_created) end subroutine wrap_json_add_integer_vec_by_path !***************************************************************************************** !***************************************************************************************** !> ! Wrapper to [[json_add_logical_by_path]] for adding a logical vector by path. subroutine json_add_logical_vec_by_path(json,me,path,value,found,was_created) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me !! the JSON structure character(kind=CK,len=*),intent(in) :: path !! the path to the variable logical(LK),dimension(:),intent(in) :: value !! the vector to add logical(LK),intent(out),optional :: found !! if the variable was found logical(LK),intent(out),optional :: was_created !! if the variable had to be created type(json_value),pointer :: p !! pointer to path (which may exist) type(json_value),pointer :: var !! new variable that is created integer(IK) :: i !! counter character(kind=CK,len=:),allocatable :: name !! the variable name logical(LK) :: p_found !! if the path was successfully found (or created) if ( .not. json%exception_thrown ) then !get a pointer to the variable !(creating it if necessary) call json%create(me,path,p,found=p_found) if (p_found) then call json%info(p,name=name) ! want to keep the existing name call json%create_array(var,name) ! create a new array variable call json%replace(p,var,destroy=.true.) ! replace p with this array (destroy p) !populate each element of the array: do i=1,size(value) call json%add(var, CK_'', value(i)) end do end if else if ( present(found) ) found = .false. if ( present(was_created) ) was_created = .false. end if end subroutine json_add_logical_vec_by_path !***************************************************************************************** !***************************************************************************************** !> ! Wrapper for [[json_add_logical_vec_by_path]] where "path" is kind=CDK). subroutine wrap_json_add_logical_vec_by_path(json,me,path,value,found,was_created) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me !! the JSON structure character(kind=CDK,len=*),intent(in) :: path !! the path to the variable logical(LK),dimension(:),intent(in) :: value !! the vector to add logical(LK),intent(out),optional :: found !! if the variable was found logical(LK),intent(out),optional :: was_created !! if the variable had to be created call json%json_add_logical_vec_by_path(me,to_unicode(path),value,found,was_created) end subroutine wrap_json_add_logical_vec_by_path !***************************************************************************************** !***************************************************************************************** !> ! Wrapper to [[json_add_double_by_path]] for adding a double vector by path. subroutine json_add_double_vec_by_path(json,me,path,value,found,was_created) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me !! the JSON structure character(kind=CK,len=*),intent(in) :: path !! the path to the variable real(RK),dimension(:),intent(in) :: value !! the vector to add logical(LK),intent(out),optional :: found !! if the variable was found logical(LK),intent(out),optional :: was_created !! if the variable had to be created type(json_value),pointer :: p !! pointer to path (which may exist) type(json_value),pointer :: var !! new variable that is created integer(IK) :: i !! counter character(kind=CK,len=:),allocatable :: name !! the variable name logical(LK) :: p_found !! if the path was successfully found (or created) if ( .not. json%exception_thrown ) then !get a pointer to the variable !(creating it if necessary) call json%create(me,path,p,found=p_found) if (p_found) then call json%info(p,name=name) ! want to keep the existing name call json%create_array(var,name) ! create a new array variable call json%replace(p,var,destroy=.true.) ! replace p with this array (destroy p) !populate each element of the array: do i=1,size(value) call json%add(var, CK_'', value(i)) end do end if else if ( present(found) ) found = .false. if ( present(was_created) ) was_created = .false. end if end subroutine json_add_double_vec_by_path !***************************************************************************************** !***************************************************************************************** !> ! Wrapper for [[json_add_double_vec_by_path]] where "path" is kind=CDK). subroutine wrap_json_add_double_vec_by_path(json,me,path,value,found,was_created) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me !! the JSON structure character(kind=CDK,len=*),intent(in) :: path !! the path to the variable real(RK),dimension(:),intent(in) :: value !! the vector to add logical(LK),intent(out),optional :: found !! if the variable was found logical(LK),intent(out),optional :: was_created !! if the variable had to be created call json%json_add_double_vec_by_path(me,to_unicode(path),value,found,was_created) end subroutine wrap_json_add_double_vec_by_path !***************************************************************************************** !***************************************************************************************** !> ! Wrapper to [[json_add_string_by_path]] for adding a string vector by path. ! !@note The `ilen` input can be used to specify the actual lengths of the ! the strings in the array. They must all be `<= len(value)`. subroutine json_add_string_vec_by_path(json,me,path,value,found,was_created,ilen) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me !! the JSON structure character(kind=CK,len=*),intent(in) :: path !! the path to the variable character(kind=CK,len=*),dimension(:),intent(in) :: value !! the vector to add logical(LK),intent(out),optional :: found !! if the variable was found logical(LK),intent(out),optional :: was_created !! if the variable had to be created integer(IK),dimension(:),intent(in),optional :: ilen !! the string lengths of each !! element in `value`. If not present, !! the full `len(value)` string is added !! for each element. type(json_value),pointer :: p !! pointer to path (which may exist) type(json_value),pointer :: var !! new variable that is created integer(IK) :: i !! counter character(kind=CK,len=:),allocatable :: name !! the variable name logical(LK) :: p_found !! if the path was successfully found (or created) if ( .not. json%exception_thrown ) then ! validate ilen array if present: if (present(ilen)) then if (size(ilen)/=size(value)) then call json%throw_exception('Error in json_add_string_vec_by_path: '//& 'Invalid size of ilen input vector.') if (present(found)) then found = .false. call json%clear_exceptions() end if if (present(was_created)) was_created = .false. return else ! also have to validate the specified lengths. ! (must not be greater than input string length) do i = 1, size(value) if (ilen(i)>len(value)) then call json%throw_exception('Error in json_add_string_vec_by_path: '//& 'Invalid ilen element.') if (present(found)) then found = .false. call json%clear_exceptions() end if if (present(was_created)) was_created = .false. return end if end do end if end if !get a pointer to the variable !(creating it if necessary) call json%create(me,path,p,found=p_found) if (p_found) then call json%info(p,name=name) ! want to keep the existing name call json%create_array(var,name) ! create a new array variable call json%replace(p,var,destroy=.true.) ! replace p with this array (destroy p) !populate each element of the array: do i=1,size(value) if (present(ilen)) then call json%add(var, CK_'', value(i)(1:ilen(i))) else call json%add(var, CK_'', value(i)) end if end do end if else if ( present(found) ) found = .false. if ( present(was_created) ) was_created = .false. end if end subroutine json_add_string_vec_by_path !***************************************************************************************** !***************************************************************************************** !> ! Wrapper for [[json_add_string_vec_by_path]] where "path" and "value" are kind=CDK). subroutine wrap_json_add_string_vec_by_path(json,me,path,value,& found,was_created,ilen) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me !! the JSON structure character(kind=CDK,len=*),intent(in) :: path !! the path to the variable character(kind=CDK,len=*),dimension(:),intent(in):: value !! the vector to add logical(LK),intent(out),optional :: found !! if the variable was found logical(LK),intent(out),optional :: was_created !! if the variable had to be created integer(IK),dimension(:),intent(in),optional :: ilen !! the string lengths of each !! element in `value`. If not present, !! the full `len(value)` string is added !! for each element. call json%json_add_string_vec_by_path(me,to_unicode(path),to_unicode(value),& found,was_created,ilen) end subroutine wrap_json_add_string_vec_by_path !***************************************************************************************** !***************************************************************************************** !> ! Wrapper for [[json_add_string_vec_by_path]] where "value" is kind=CDK). subroutine json_add_string_vec_by_path_value_ascii(json,me,path,value,& found,was_created,ilen) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me !! the JSON structure character(kind=CK,len=*),intent(in) :: path !! the path to the variable character(kind=CDK,len=*),dimension(:),intent(in):: value !! the vector to add logical(LK),intent(out),optional :: found !! if the variable was found logical(LK),intent(out),optional :: was_created !! if the variable had to be created integer(IK),dimension(:),intent(in),optional :: ilen !! the string lengths of each !! element in `value`. If not present, !! the full `len(value)` string is added !! for each element. call json%json_add_string_vec_by_path(me,path,to_unicode(value),& found,was_created,ilen) end subroutine json_add_string_vec_by_path_value_ascii !***************************************************************************************** !***************************************************************************************** !> ! Wrapper for [[json_add_string_vec_by_path]] where "path" is kind=CDK). subroutine json_add_string_vec_by_path_path_ascii(json,me,path,value,& found,was_created,ilen) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me !! the JSON structure character(kind=CDK,len=*),intent(in) :: path !! the path to the variable character(kind=CK,len=*),dimension(:),intent(in) :: value !! the vector to add logical(LK),intent(out),optional :: found !! if the variable was found logical(LK),intent(out),optional :: was_created !! if the variable had to be created integer(IK),dimension(:),intent(in),optional :: ilen !! the string lengths of each !! element in `value`. If not present, !! the full `len(value)` string is added !! for each element. call json%json_add_string_vec_by_path(me,to_unicode(path),value,& found,was_created,ilen) end subroutine json_add_string_vec_by_path_path_ascii !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 1/19/2014 ! ! Add a real value child to the [[json_value]] variable ! !@note This routine is part of the public API that can be ! used to build a JSON structure using [[json_value]] pointers. subroutine json_value_add_double(json,p,name,val) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CK,len=*),intent(in) :: name !! variable name real(RK),intent(in) :: val !! real value type(json_value),pointer :: var !create the variable: call json%create_double(var,val,name) !add it: call json%add(p, var) end subroutine json_value_add_double !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_value_add_double]] where `name` is kind=CDK. subroutine wrap_json_value_add_double(json,p,name,val) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CDK,len=*),intent(in) :: name !! variable name real(RK),intent(in) :: val !! real value call json%add(p, to_unicode(name), val) end subroutine wrap_json_value_add_double !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 1/20/2014 ! ! Add a real vector to the structure. ! !@note This routine is part of the public API that can be ! used to build a JSON structure using [[json_value]] pointers. subroutine json_value_add_double_vec(json, p, name, val) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CK,len=*),intent(in) :: name real(RK),dimension(:),intent(in) :: val type(json_value),pointer :: var integer(IK) :: i !! counter !create the variable as an array: call json%create_array(var,name) !populate the array: do i=1,size(val) call json%add(var, CK_'', val(i)) end do !add it: call json%add(p, var) end subroutine json_value_add_double_vec !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_value_add_double_vec]] where `name` is kind=CDK. subroutine wrap_json_value_add_double_vec(json, p, name, val) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CDK,len=*),intent(in) :: name real(RK),dimension(:),intent(in) :: val call json%add(p, to_unicode(name), val) end subroutine wrap_json_value_add_double_vec !***************************************************************************************** !***************************************************************************************** !> ! Add a NULL value child to the [[json_value]] variable ! !@note This routine is part of the public API that can be ! used to build a JSON structure using [[json_value]] pointers. subroutine json_value_add_null(json, p, name) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CK,len=*),intent(in) :: name type(json_value),pointer :: var !create the variable: call json%create_null(var,name) !add it: call json%add(p, var) end subroutine json_value_add_null !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_value_add_null]] where `name` is kind=CDK. subroutine wrap_json_value_add_null(json, p, name) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CDK,len=*),intent(in) :: name !! name of the variable call json%add(p, to_unicode(name)) end subroutine wrap_json_value_add_null !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 1/20/2014 ! ! Add an integer value child to the [[json_value]] variable ! !@note This routine is part of the public API that can be ! used to build a JSON structure using [[json_value]] pointers. subroutine json_value_add_integer(json, p, name, val) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CK,len=*),intent(in) :: name integer(IK),intent(in) :: val type(json_value),pointer :: var !create the variable: call json%create_integer(var,val,name) !add it: call json%add(p, var) end subroutine json_value_add_integer !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_value_add_integer]] where `name` is kind=CDK. subroutine wrap_json_value_add_integer(json, p, name, val) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CDK,len=*),intent(in) :: name !! name of the variable integer(IK),intent(in) :: val !! value call json%add(p, to_unicode(name), val) end subroutine wrap_json_value_add_integer !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 1/20/2014 ! ! Add an integer vector to the structure. ! !@note This routine is part of the public API that can be ! used to build a JSON structure using [[json_value]] pointers. subroutine json_value_add_integer_vec(json, p, name, val) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CK,len=*),intent(in) :: name !! name of the variable integer(IK),dimension(:),intent(in) :: val !! value type(json_value),pointer :: var integer(IK) :: i !! counter !create a variable as an array: call json%create_array(var,name) !populate the array: do i=1,size(val) call json%add(var, CK_'', val(i)) end do !add it: call json%add(p, var) end subroutine json_value_add_integer_vec !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_value_add_integer_vec]] where `name` is kind=CDK. subroutine wrap_json_value_add_integer_vec(json, p, name, val) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CDK,len=*),intent(in) :: name !! name of the variable integer(IK),dimension(:),intent(in) :: val !! value call json%add(p, to_unicode(name), val) end subroutine wrap_json_value_add_integer_vec !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 1/20/2014 ! ! Add a logical value child to the [[json_value]] variable ! !@note This routine is part of the public API that can be ! used to build a JSON structure using [[json_value]] pointers. subroutine json_value_add_logical(json, p, name, val) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CK,len=*),intent(in) :: name !! name of the variable logical(LK),intent(in) :: val !! value type(json_value),pointer :: var !create the variable: call json%create_logical(var,val,name) !add it: call json%add(p, var) end subroutine json_value_add_logical !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_value_add_logical]] where `name` is kind=CDK. subroutine wrap_json_value_add_logical(json, p, name, val) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CDK,len=*),intent(in) :: name !! name of the variable logical(LK),intent(in) :: val !! value call json%add(p, to_unicode(name), val) end subroutine wrap_json_value_add_logical !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 1/20/2014 ! ! Add a logical vector to the structure. ! !@note This routine is part of the public API that can be ! used to build a JSON structure using [[json_value]] pointers. subroutine json_value_add_logical_vec(json, p, name, val) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CK,len=*),intent(in) :: name !! name of the vector logical(LK),dimension(:),intent(in) :: val !! value type(json_value),pointer :: var integer(IK) :: i !! counter !create the variable as an array: call json%create_array(var,name) !populate the array: do i=1,size(val) call json%add(var, CK_'', val(i)) end do !add it: call json%add(p, var) end subroutine json_value_add_logical_vec !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_value_add_logical_vec]] where `name` is kind=CDK. subroutine wrap_json_value_add_logical_vec(json, p, name, val) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CDK,len=*),intent(in) :: name !! name of the variable logical(LK),dimension(:),intent(in) :: val !! value call json%add(p, to_unicode(name), val) end subroutine wrap_json_value_add_logical_vec !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 1/19/2014 ! ! Add a character string child to the [[json_value]] variable. ! !@note This routine is part of the public API that can be ! used to build a JSON structure using [[json_value]] pointers. subroutine json_value_add_string(json, p, name, val) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CK,len=*),intent(in) :: name !! name of the variable character(kind=CK,len=*),intent(in) :: val !! value type(json_value),pointer :: var character(kind=CK,len=:),allocatable :: str !add escape characters if necessary: call escape_string(val, str) !create the variable: call json%create_string(var,str,name) !add it: call json%add(p, var) end subroutine json_value_add_string !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_value_add_string]] where `name` and `val` are kind=CDK. subroutine wrap_json_value_add_string(json, p, name, val) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CDK,len=*),intent(in) :: name !! name of the variable character(kind=CDK,len=*),intent(in) :: val !! value call json%add(p, to_unicode(name), to_unicode(val)) end subroutine wrap_json_value_add_string !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_value_add_string]] where `name` is kind=CDK. subroutine json_value_add_string_name_ascii(json, p, name, val) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CDK,len=*),intent(in) :: name !! name of the variable character(kind=CK, len=*),intent(in) :: val !! value call json%add(p, to_unicode(name), val) end subroutine json_value_add_string_name_ascii !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_value_add_string]] where `val` is kind=CDK. subroutine json_value_add_string_val_ascii(json, p, name, val) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CK, len=*),intent(in) :: name !! name of the variable character(kind=CDK,len=*),intent(in) :: val !! value call json%add(p, name, to_unicode(val)) end subroutine json_value_add_string_val_ascii !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 1/19/2014 ! ! Add an array of character strings to the structure. ! !@note This routine is part of the public API that can be ! used to build a JSON structure using [[json_value]] pointers. subroutine json_value_add_string_vec(json, p, name, val, trim_str, adjustl_str) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CK,len=*),intent(in) :: name !! variable name character(kind=CK,len=*),dimension(:),intent(in) :: val !! array of strings logical(LK),intent(in),optional :: trim_str !! if TRIM() should be called for each element logical(LK),intent(in),optional :: adjustl_str !! if ADJUSTL() should be called for each element type(json_value),pointer :: var integer(IK) :: i logical(LK) :: trim_string, adjustl_string character(kind=CK,len=:),allocatable :: str !if the string is to be trimmed or not: if (present(trim_str)) then trim_string = trim_str else trim_string = .false. end if if (present(adjustl_str)) then adjustl_string = adjustl_str else adjustl_string = .false. end if !create the variable as an array: call json%create_array(var,name) !populate the array: do i=1,size(val) !the string to write: str = val(i) if (adjustl_string) str = adjustl(str) if (trim_string) str = trim(str) !write it: call json%add(var, CK_'', str) !cleanup deallocate(str) end do !add it: call json%add(p, var) end subroutine json_value_add_string_vec !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_value_add_string_vec]] where `name` and `val` are kind=CDK. subroutine wrap_json_value_add_string_vec(json, p, name, val, trim_str, adjustl_str) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CDK,len=*),intent(in) :: name character(kind=CDK,len=*),dimension(:),intent(in) :: val logical(LK),intent(in),optional :: trim_str logical(LK),intent(in),optional :: adjustl_str call json%add(p, to_unicode(name), to_unicode(val), trim_str, adjustl_str) end subroutine wrap_json_value_add_string_vec !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_value_add_string_vec]] where `name` is kind=CDK. subroutine json_value_add_string_vec_name_ascii(json, p, name, val, trim_str, adjustl_str) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CDK,len=*),intent(in) :: name character(kind=CK, len=*),dimension(:),intent(in) :: val logical(LK),intent(in),optional :: trim_str logical(LK),intent(in),optional :: adjustl_str call json%add(p, to_unicode(name), val, trim_str, adjustl_str) end subroutine json_value_add_string_vec_name_ascii !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_value_add_string_vec]] where `val` is kind=CDK. subroutine json_value_add_string_vec_val_ascii(json, p, name, val, trim_str, adjustl_str) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: p character(kind=CK, len=*),intent(in) :: name character(kind=CDK,len=*),dimension(:),intent(in) :: val logical(LK),intent(in),optional :: trim_str logical(LK),intent(in),optional :: adjustl_str call json%add(p, name, to_unicode(val), trim_str, adjustl_str) end subroutine json_value_add_string_vec_val_ascii !***************************************************************************************** !***************************************************************************************** !> ! Count the number of children. ! !### History ! * JW : 1/4/2014 : Original routine removed. ! Now using `n_children` variable. ! Renamed from `json_value_count`. function json_count(json,p) result(count) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: p integer(IK) :: count !! number of children if (associated(p)) then count = p%n_children else call json%throw_exception('Error in json_count: '//& 'pointer is not associated.') end if end function json_count !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 10/16/2015 ! ! Returns a pointer to the parent of a [[json_value]]. ! If there is no parent, then a `null()` pointer is returned. subroutine json_get_parent(json,p,parent) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: p !! JSON object type(json_value),pointer,intent(out) :: parent !! pointer to `parent` if (associated(p)) then parent => p%parent else nullify(parent) call json%throw_exception('Error in json_get_parent: '//& 'pointer is not associated.') end if end subroutine json_get_parent !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 10/31/2015 ! ! Returns a pointer to the next of a [[json_value]]. ! If there is no next, then a `null()` pointer is returned. subroutine json_get_next(json,p,next) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: p !! JSON object type(json_value),pointer,intent(out) :: next !! pointer to `next` if (associated(p)) then next => p%next else nullify(next) call json%throw_exception('Error in json_get_next: '//& 'pointer is not associated.') end if end subroutine json_get_next !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 10/31/2015 ! ! Returns a pointer to the previous of a [[json_value]]. ! If there is no previous, then a `null()` pointer is returned. subroutine json_get_previous(json,p,previous) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: p !! JSON object type(json_value),pointer,intent(out) :: previous !! pointer to `previous` if (associated(p)) then previous => p%previous else nullify(previous) call json%throw_exception('Error in json_get_previous: '//& 'pointer is not associated.') end if end subroutine json_get_previous !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 10/31/2015 ! ! Returns a pointer to the tail of a [[json_value]] ! (the last child of an array of object). ! If there is no tail, then a `null()` pointer is returned. subroutine json_get_tail(json,p,tail) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: p !! JSON object type(json_value),pointer,intent(out) :: tail !! pointer to `tail` if (associated(p)) then tail => p%tail else nullify(tail) call json%throw_exception('Error in json_get_tail: '//& 'pointer is not associated.') end if end subroutine json_get_tail !***************************************************************************************** !***************************************************************************************** !> ! Returns a child in the object or array given the index. subroutine json_value_get_child_by_index(json, p, idx, child, found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: p !! object or array JSON data integer(IK),intent(in) :: idx !! index of the child !! (this is a 1-based Fortran !! style array index). type(json_value),pointer :: child !! pointer to the child logical(LK),intent(out),optional :: found !! true if the value was found !! (if not present, an exception !! will be thrown if it was not !! found. If present and not !! found, no exception will be !! thrown). integer(IK) :: i !! counter nullify(child) if (.not. json%exception_thrown) then if (associated(p%children)) then child => p%children do i = 1, idx - 1 if (associated(child%next)) then child => child%next else call json%throw_exception('Error in json_value_get_child_by_index:'//& ' child%next is not associated.') nullify(child) exit end if end do else call json%throw_exception('Error in json_value_get_child_by_index:'//& ' p%children is not associated.') end if ! found output: if (json%exception_thrown) then if (present(found)) then call json%clear_exceptions() found = .false. end if else if (present(found)) found = .true. end if else if (present(found)) found = .false. end if end subroutine json_value_get_child_by_index !***************************************************************************************** !***************************************************************************************** !> ! Returns pointer to the first child of the object ! (or `null()` if it is not associated). subroutine json_value_get_child(json, p, child) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: p !! object or array JSON data type(json_value),pointer :: child !! pointer to the child if (associated(p)) then child => p%children else nullify(child) call json%throw_exception('Error in json_value_get_child: '//& 'pointer is not associated.') end if end subroutine json_value_get_child !***************************************************************************************** !***************************************************************************************** !> ! Returns a child in the object or array given the name string. ! ! The name search can be case-sensitive or not, and can have significant trailing ! whitespace or not, depending on the settings in the [[json_core(type)]] class. ! !@note The `name` input is not a path, and is not parsed like it is in [[json_get_by_path]]. subroutine json_value_get_child_by_name(json, p, name, child, found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: p character(kind=CK,len=*),intent(in) :: name !! the name of a child of `p` type(json_value),pointer :: child !! pointer to the child logical(LK),intent(out),optional :: found !! true if the value was found !! (if not present, an exception !! will be thrown if it was not !! found. If present and not !! found, no exception will be !! thrown). integer(IK) :: i,n_children logical :: error nullify(child) if (.not. json%exception_thrown) then if (associated(p)) then error = .true. ! will be false if it is found if (p%var_type==json_object) then n_children = json%count(p) child => p%children !start with first one do i=1, n_children if (.not. associated(child)) then call json%throw_exception('Error in json_value_get_child_by_name: '//& 'Malformed JSON linked list') exit end if if (allocated(child%name)) then !name string matching routine: if (json%name_equal(child,name)) then error = .false. exit end if end if child => child%next end do end if if (error) then !did not find anything: call json%throw_exception('Error in json_value_get_child_by_name: '//& 'child variable '//trim(name)//' was not found.') nullify(child) end if else call json%throw_exception('Error in json_value_get_child_by_name: '//& 'pointer is not associated.') end if ! found output: if (json%exception_thrown) then if (present(found)) then call json%clear_exceptions() found = .false. end if else if (present(found)) found = .true. end if else if (present(found)) found = .false. end if end subroutine json_value_get_child_by_name !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_value_get_child_by_name]] where `name` is kind=CDK. subroutine wrap_json_value_get_child_by_name(json, p, name, child, found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: p character(kind=CDK,len=*),intent(in) :: name type(json_value),pointer :: child logical(LK),intent(out),optional :: found call json%get(p,to_unicode(name),child,found) end subroutine wrap_json_value_get_child_by_name !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 2/12/2014 ! ! Print the [[json_value]] structure to an allocatable string. subroutine json_value_to_string(json,p,str) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: p character(kind=CK,len=:),intent(out),allocatable :: str !! prints structure to this string str = CK_'' call json%json_value_print(p, iunit=unit2str, str=str, indent=1_IK, colon=.true.) end subroutine json_value_to_string !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 6/20/2014 ! ! Print the [[json_value]] structure to a file. subroutine json_print_1(json,p,iunit) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: p integer(IK),intent(in) :: iunit !! the file unit (the file must !! already have been opened, can't be -1). character(kind=CK,len=:),allocatable :: dummy if (iunit/=unit2str) then call json%json_value_print(p,iunit,str=dummy, indent=1_IK, colon=.true.) else call json%throw_exception('Error in json_print_1: iunit must not be -1.') end if end subroutine json_print_1 !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 12/23/2014 ! ! Print the [[json_value]] structure to a file. subroutine json_print_2(json,p,filename) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: p character(kind=CDK,len=*),intent(in) :: filename !! the filename to print to !! (should not already be open) integer(IK) :: iunit,istat open(newunit=iunit,file=filename,status='REPLACE',iostat=istat FILE_ENCODING ) if (istat==0) then call json%print(p,iunit) close(iunit,iostat=istat) else call json%throw_exception('Error in json_print_2: could not open file: '//& trim(filename)) end if end subroutine json_print_2 !***************************************************************************************** !***************************************************************************************** !> ! Print the JSON structure to a string or a file. ! !### Notes ! * This is an internal routine called by the various wrapper routines. ! * The reason the `str` argument is non-optional is because of a ! bug in v4.9 of the gfortran compiler. recursive subroutine json_value_print(json,p,iunit,str,indent,& need_comma,colon,is_array_element,& is_compressed_vector) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: p integer(IK),intent(in) :: iunit !! file unit to write to (6=console) integer(IK),intent(in),optional :: indent !! indention level logical(LK),intent(in),optional :: is_array_element !! if this is an array element logical(LK),intent(in),optional :: need_comma !! if it needs a comma after it logical(LK),intent(in),optional :: colon !! if the colon was just written character(kind=CK,len=:),intent(inout),allocatable :: str !! if iunit==unit2str (-1) then the structure is !! printed to this string rather than !! a file. This mode is used by !! [[json_value_to_string]]. logical(LK),intent(in),optional :: is_compressed_vector !! if True, this is an element !! from an array being printed !! on one line [default is False] character(kind=CK,len=max_numeric_str_len) :: tmp !! for val to string conversions character(kind=CK,len=:),allocatable :: s type(json_value),pointer :: element integer(IK) :: tab, i, count, spaces logical(LK) :: print_comma logical(LK) :: write_file, write_string logical(LK) :: is_array integer(IK) :: var_type,var_type_prev logical(LK) :: is_vector !! if all elements of a vector !! are scalars of the same type if (.not. json%exception_thrown) then if (present(is_compressed_vector)) then is_vector = is_compressed_vector else is_vector = .false. end if !whether to write a string or a file (one or the other): write_string = (iunit==unit2str) write_file = .not. write_string !if the comma will be printed after the value ! [comma not printed for the last elements] if (present(need_comma)) then print_comma = need_comma else print_comma = .false. end if !number of "tabs" to indent: if (present(indent) .and. .not. json%no_whitespace) then tab = indent else tab = 0 end if !convert to number of spaces: spaces = tab*json%spaces_per_tab !if this is an element in an array: if (present(is_array_element)) then is_array = is_array_element else is_array = .false. end if !if the colon was the last thing written if (present(colon)) then s = CK_'' else s = repeat(space, spaces) end if select case (p%var_type) case (json_object) count = json%count(p) if (count==0) then !special case for empty object call write_it( s//start_object//end_object, comma=print_comma ) else call write_it( s//start_object ) !if an object is in an array, there is an extra tab: if (is_array) then if ( .not. json%no_whitespace) tab = tab+1 spaces = tab*json%spaces_per_tab end if nullify(element) element => p%children do i = 1, count if (.not. associated(element)) then call json%throw_exception('Error in json_value_print: '//& 'Malformed JSON linked list') return end if ! print the name if (allocated(element%name)) then if (json%no_whitespace) then !compact printing - no extra space call write_it(repeat(space, spaces)//quotation_mark//& element%name//quotation_mark//colon_char,& advance=.false.) else call write_it(repeat(space, spaces)//quotation_mark//& element%name//quotation_mark//colon_char//space,& advance=.false.) end if else call json%throw_exception('Error in json_value_print:'//& ' element%name not allocated') nullify(element) return end if ! recursive print of the element call json%json_value_print(element, iunit=iunit, indent=tab + 1, & need_comma=i<count, colon=.true., str=str) ! get the next child the list: element => element%next end do ! [one fewer tab if it isn't an array element] if (.not. is_array) s = repeat(space, max(0,spaces-json%spaces_per_tab)) call write_it( s//end_object, comma=print_comma ) nullify(element) end if case (json_array) count = json%count(p) if (json%compress_vectors) then ! check to see if every child is the same type, ! and a scalar: is_vector = .true. var_type_prev = -1 ! an invalid value nullify(element) element => p%children do i = 1, count if (.not. associated(element)) then call json%throw_exception('Error in json_value_print: '//& 'Malformed JSON linked list') return end if ! check variable type of all the children. ! They must all be the same, and a scalar. call json%info(element,var_type=var_type) if (var_type==json_object .or. & var_type==json_array .or. & (i>1 .and. var_type/=var_type_prev)) then is_vector = .false. exit end if var_type_prev = var_type ! get the next child the list: element => element%next end do else is_vector = .false. end if if (count==0) then !special case for empty array call write_it( s//start_array//end_array, comma=print_comma ) else call write_it( s//start_array, advance=(.not. is_vector) ) !if an array is in an array, there is an extra tab: if (is_array) then if ( .not. json%no_whitespace) tab = tab+1 spaces = tab*json%spaces_per_tab end if nullify(element) element => p%children do i = 1, count if (.not. associated(element)) then call json%throw_exception('Error in json_value_print: '//& 'Malformed JSON linked list') return end if ! recursive print of the element if (is_vector) then call json%json_value_print(element, iunit=iunit, indent=0,& need_comma=i<count, is_array_element=.false., str=str,& is_compressed_vector = .true.) else call json%json_value_print(element, iunit=iunit, indent=tab,& need_comma=i<count, is_array_element=.true., str=str) end if ! get the next child the list: element => element%next end do !indent the closing array character: if (is_vector) then call write_it( end_array,comma=print_comma ) else call write_it( repeat(space, max(0,spaces-json%spaces_per_tab))//end_array,& comma=print_comma ) end if nullify(element) end if case (json_null) call write_it( s//null_str, comma=print_comma, & advance=(.not. is_vector),& space_after_comma=is_vector ) case (json_string) if (allocated(p%str_value)) then call write_it( s//quotation_mark// & p%str_value//quotation_mark, & comma=print_comma, & advance=(.not. is_vector),& space_after_comma=is_vector ) else call json%throw_exception('Error in json_value_print:'//& ' p%value_string not allocated') return end if case (json_logical) if (p%log_value) then call write_it( s//true_str, comma=print_comma, & advance=(.not. is_vector),& space_after_comma=is_vector ) else call write_it( s//false_str, comma=print_comma, & advance=(.not. is_vector),& space_after_comma=is_vector ) end if case (json_integer) call integer_to_string(p%int_value,int_fmt,tmp) call write_it( s//trim(tmp), comma=print_comma, & advance=(.not. is_vector),& space_after_comma=is_vector ) case (json_double) if (allocated(json%real_fmt)) then call real_to_string(p%dbl_value,json%real_fmt,json%compact_real,tmp) else !use the default format (user has not called initialize() or specified one): call real_to_string(p%dbl_value,default_real_fmt,json%compact_real,tmp) end if call write_it( s//trim(tmp), comma=print_comma, & advance=(.not. is_vector),& space_after_comma=is_vector ) case default call json%throw_exception('Error in json_value_print: unknown data type') end select !cleanup: if (allocated(s)) deallocate(s) end if contains subroutine write_it(s,advance,comma,space_after_comma) !! write the string to the file (or the output string) implicit none character(kind=CK,len=*),intent(in) :: s !! string to print logical(LK),intent(in),optional :: advance !! to add line break or not logical(LK),intent(in),optional :: comma !! print comma after the string logical(LK),intent(in),optional :: space_after_comma !! print a space after the comma logical(LK) :: add_comma !! if a delimiter is to be added after string logical(LK) :: add_line_break !! if a line break is to be added after string logical(LK) :: add_space !! if a space is to be added after the comma character(kind=CK,len=:),allocatable :: s2 !! temporary string if (present(comma)) then add_comma = comma else add_comma = .false. !default is not to add comma end if if (json%no_whitespace) then add_space = .false. else if (present(space_after_comma)) then add_space = space_after_comma else add_space = .false. !default is not to add space end if end if if (present(advance)) then add_line_break = advance else add_line_break = .not. json%no_whitespace ! default is to advance if ! we are printing whitespace end if !string to print: s2 = s if (add_comma) then s2 = s2 // delimiter if (add_space) s2 = s2 // space end if if (write_file) then if (add_line_break) then write(iunit,fmt='(A)') s2 else write(iunit,fmt='(A)',advance='NO') s2 end if else !write string str = str // s2 if (add_line_break) str = str // newline end if !cleanup: if (allocated(s2)) deallocate(s2) end subroutine write_it end subroutine json_value_print !***************************************************************************************** !***************************************************************************************** !> ! Returns the [[json_value]] pointer given the path string. ! ! It uses either of two methods: ! ! * The original JSON-Fortran defaults ! * [RFC 6901](https://tools.ietf.org/html/rfc6901) subroutine json_get_by_path(json, me, path, p, found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: me !! a JSON linked list character(kind=CK,len=*),intent(in) :: path !! path to the variable type(json_value),pointer,intent(out) :: p !! pointer to the variable !! specify by `path` logical(LK),intent(out),optional :: found !! true if it was found nullify(p) if (.not. json%exception_thrown) then ! note: it can only be 1 or 2 (which was checked in initialize) select case (json%path_mode) case(1_IK) call json%json_get_by_path_default(me, path, p, found) case(2_IK) call json%json_get_by_path_rfc6901(me, path, p, found) end select else if (present(found)) found = .false. end if end subroutine json_get_by_path !***************************************************************************************** !***************************************************************************************** !> ! Returns the [[json_value]] pointer given the path string, ! If necessary, by creating the variables as needed. ! ! By default, the leaf node and any empty array elements ! are created as `json_null` values. ! ! It only works for the default path mode. An error will be ! thrown if RFC 6901 mode is enabled. ! !### See also ! * [[json_get_by_path]] subroutine json_create_by_path(json,me,path,p,found,was_created) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: me !! a JSON linked list character(kind=CK,len=*),intent(in) :: path !! path to the variable type(json_value),pointer,intent(out),optional :: p !! pointer to the variable !! specify by `path` logical(LK),intent(out),optional :: found !! true if there were no errors !! (variable found or created) logical(LK),intent(out),optional :: was_created !! true if it was actually created !! (as opposed to already being there) type(json_value),pointer :: tmp if (present(p)) nullify(p) if (.not. json%exception_thrown) then ! note: path_mode can only be 1 or 2 (which was checked in initialize) select case (json%path_mode) case(1_IK) call json%json_get_by_path_default(me,path,tmp,found,& create_it=.true.,& was_created=was_created) if (present(p)) p => tmp case(2_IK) ! the problem here is there isn't really a way to disambiguate ! the array elements, so '/a/0' could be 'a(1)' or 'a.0'. call json%throw_exception('Create by path not supported in RFC 6901 path mode.') if (present(found)) then call json%clear_exceptions() found = .false. end if if (present(was_created)) was_created = .false. end select else if (present(was_created)) was_created = .false. if (present(found)) found = .false. end if end subroutine json_create_by_path !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_create_by_path]] where "path" is kind=CDK. subroutine wrap_json_create_by_path(json,me,path,p,found,was_created) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: me !! a JSON linked list character(kind=CDK,len=*),intent(in) :: path !! path to the variable type(json_value),pointer,intent(out),optional :: p !! pointer to the variable !! specify by `path` logical(LK),intent(out),optional :: found !! true if there were no errors !! (variable found or created) logical(LK),intent(out),optional :: was_created !! true if it was actually created !! (as opposed to already being there) call json%create(me,to_unicode(path),p,found,was_created) end subroutine wrap_json_create_by_path !***************************************************************************************** !***************************************************************************************** !> ! Returns the [[json_value]] pointer given the path string. ! !### Example ! !````fortran ! type(json_value),pointer :: dat,p ! logical :: found ! !... ! call json%get(dat,'data(2).version',p,found) !```` ! !### Notes ! The following special characters are used to denote paths: ! ! * `$` - root ! * `@` - this ! * `.` - child object member (note this can be changed using `json%path_separator`) ! * `[]` or `()` - child array element (note that indices are 1-based) ! ! Thus, if any of these characters are present in the name key, ! this routine cannot be used to get the value. ! In that case, the `get_child` methods would need to be used. ! Or, the alternate [[json_get_by_path_rfc6901]] could be used. ! !### See also ! * [[json_get_by_path_rfc6901]] - alternate version with different path convention. ! !@note JSON `null` values are used here for unknown variables when `create_it` is True. ! So, it is possible that an existing null variable can be converted to another ! type (object or array) if a child is specified in the path. Doing it this way ! to avoid having to use another type (say `json_unknown`) that would have to be ! converted to null once all the variables have been created (user would have ! had to do this). subroutine json_get_by_path_default(json,me,path,p,found,create_it,was_created) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: me !! a JSON linked list character(kind=CK,len=*),intent(in) :: path !! path to the variable type(json_value),pointer,intent(out) :: p !! pointer to the variable !! specify by `path` logical(LK),intent(out),optional :: found !! true if it was found logical(LK),intent(in),optional :: create_it !! if a variable is not present !! in the path, then it is created. !! the leaf node is returned as !! a `null` json type and can be !! changed by the caller. logical(LK),intent(out),optional :: was_created !! if `create_it` is true, this !! will be true if the variable !! was actually created. Otherwise !! it will be false. integer(IK) :: i !! counter of characters in `path` integer(IK) :: length !! significant length of `path` integer(IK) :: child_i !! index for getting children character(kind=CK,len=1) :: c !! a character in the `path` logical(LK) :: array !! flag when searching for array index in `path` type(json_value),pointer :: tmp !! temp variables for getting child objects logical(LK) :: child_found !! if the child value was found logical(LK) :: create !! if the object is to be created logical(LK) :: created !! if `create` is true, then this will be !! true if the leaf object had to be created integer(IK) :: j !! counter of children when creating object nullify(p) if (.not. json%exception_thrown) then if (present(create_it)) then create = create_it else create = .false. end if ! default to assuming relative to me p => me child_i = 1 array = .false. created = .false. !keep trailing space or not: if (json%trailing_spaces_significant) then length = len(path) else length = len_trim(path) end if do i=1, length c = path(i:i) select case (c) case (root) ! root do while (associated (p%parent)) p => p%parent end do child_i = i + 1 if (create) created = .false. ! should always exist case (this) ! this p => me child_i = i + 1 if (create) created = .false. ! should always exist case (start_array,start_array_alt) ! start looking for the array element index array = .true. ! get child member from p if (child_i < i) then nullify(tmp) if (create) then ! Example: ! 'aaa.bbb(1)' ! -> and aaa is a null, need to make it an object ! ! What about the case: aaa.bbb(1)(3) ? ! Is that already handled? if (p%var_type==json_null) then ! if p was also created, then we need to ! convert it into an object here: p%var_type = json_object end if ! don't want to throw exceptions in this case call json%get_child(p, path(child_i:i-1), tmp, child_found) if (.not. child_found) then ! have to create this child ! [make it an array] call json_value_create(tmp) call to_array(tmp,path(child_i:i-1)) call json%add(p,tmp) created = .true. else created = .false. end if else ! call the normal way call json%get_child(p, path(child_i:i-1), tmp) end if p => tmp else child_i = i + 1 ! say, '@(' cycle end if if (.not. associated(p)) then call json%throw_exception('Error in json_get_by_path_default:'//& ' Error getting array element') exit end if child_i = i + 1 case (end_array,end_array_alt) if (.not. array) then call json%throw_exception('Error in json_get_by_path_default: Unexpected '//c) exit end if array = .false. child_i = json%string_to_int(path(child_i:i-1)) nullify(tmp) if (create) then ! don't want to throw exceptions in this case call json%get_child(p, child_i, tmp, child_found) if (.not. child_found) then if (p%var_type==json_null) then ! if p was also created, then we need to ! convert it into an array here: p%var_type = json_array end if ! have to create this element ! [make it a null] ! (and any missing ones before it) do j = 1, child_i nullify(tmp) call json%get_child(p, j, tmp, child_found) if (.not. child_found) then call json_value_create(tmp) call to_null(tmp) ! array element doesn't need a name call json%add(p,tmp) if (j==child_i) created = .true. else if (j==child_i) created = .false. end if end do else created = .false. end if else ! call the normal way: call json%get_child(p, child_i, tmp) end if p => tmp child_i = i + 1 case default if (c==json%path_separator) then ! get child member from p if (child_i < i) then nullify(tmp) if (create) then if (p%var_type==json_null) then ! if p was also created, then we need to ! convert it into an object here: p%var_type = json_object end if ! don't want to throw exceptions in this case call json%get_child(p, path(child_i:i-1), tmp, child_found) if (.not. child_found) then ! have to create this child ! [make it an object] call json_value_create(tmp) call to_object(tmp,path(child_i:i-1)) call json%add(p,tmp) created = .true. else created = .false. end if else ! call the normal way call json%get_child(p, path(child_i:i-1), tmp) end if p => tmp else child_i = i + 1 ! say '$.', '@.', or ').' cycle end if if (.not. associated(p)) then call json%throw_exception('Error in json_get_by_path_default:'//& ' Error getting child member.') exit end if child_i = i + 1 end if end select end do if (json%exception_thrown) then if (present(found)) then nullify(p) ! just in case found = .false. call json%clear_exceptions() end if else ! grab the last child if present in the path if (child_i <= length) then nullify(tmp) if (create) then if (p%var_type==json_null) then ! if p was also created, then we need to ! convert it into an object here: p%var_type = json_object end if call json%get_child(p, path(child_i:i-1), tmp, child_found) if (.not. child_found) then ! have to create this child ! (make it a null since it is the leaf) call json_value_create(tmp) call to_null(tmp,path(child_i:i-1)) call json%add(p,tmp) created = .true. else created = .false. end if else ! call the normal way call json%get_child(p, path(child_i:i-1), tmp) end if p => tmp else ! we already have p if (create .and. created) then ! make leaf p a null, but only ! if it wasn't there call to_null(p) end if end if ! error checking if (associated(p)) then if (present(found)) found = .true. !everything seems to be ok else call json%throw_exception('Error in json_get_by_path_default:'//& ' variable not found: '//trim(path)) if (present(found)) then found = .false. call json%clear_exceptions() end if end if end if ! if it had to be created: if (present(was_created)) was_created = created else if (present(found)) found = .false. if (present(was_created)) was_created = .false. end if end subroutine json_get_by_path_default !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 2/4/2017 ! ! Returns the [[json_value]] pointer given the path string, ! using the "JSON Pointer" path specification defined by RFC 6901. ! ! Note that trailing whitespace significance and case sensitivity ! are user-specified. To fully conform to the RFC 6901 standard, ! should probably set (via `initialize`): ! ! * `trailing_spaces_significant` = .true. [this is not the default setting] ! * `case_sensitive_keys` = .true. [this is the default setting] ! !### Example ! !````fortran ! type(json_value),pointer :: dat,p ! logical :: found ! !... ! call json%get(dat,'/data/2/version',p,found) !```` ! !### See also ! * [[json_get_by_path_default]] - alternate version with different path convention. ! !### Reference ! * [JavaScript Object Notation (JSON) Pointer](https://tools.ietf.org/html/rfc6901) ! !@note Not doing anything special about the `-` character to index an array. ! This is considered a normal error. ! !@note Unlike in the default path mode, the array indices here are 0-based ! (in accordance with the RFC 6901 standard) ! !@warning Not checking if the member that is referenced is unique. ! (according to the standard, evaluation of non-unique references ! should fail). Like [[json_get_by_path_default]], this one will just return ! the first instance it encounters. This might be changed in the future. subroutine json_get_by_path_rfc6901(json, me, path, p, found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: me !! a JSON linked list character(kind=CK,len=*),intent(in) :: path !! path to the variable !! (an RFC 6901 "JSON Pointer") type(json_value),pointer,intent(out) :: p !! pointer to the variable !! specify by `path` logical(LK),intent(out),optional :: found !! true if it was found character(kind=CK,len=:),allocatable :: token !! a token in the path (between the `/` characters) integer(IK) :: i !! counter integer(IK) :: islash_curr !! location of current '/' character in the path integer(IK) :: islash_next !! location of next '/' character in the path integer(IK) :: ilen !! length of `path` string type(json_value),pointer :: tmp !! temporary variable for traversing the structure integer(IK) :: ival !! integer array index value (0-based) logical(LK) :: status_ok !! error flag logical(LK) :: child_found !! for getting child values nullify(p) if (.not. json%exception_thrown) then p => me ! initialize if (path/=CK_'') then if (path(1:1)==slash) then ! the first character must be a slash islash_curr = 1 ! initialize current slash index !keep trailing space or not: if (json%trailing_spaces_significant) then ilen = len(path) else ilen = len_trim(path) end if do ! get the next token by finding the slashes ! ! 1 2 3 ! /abc/d/efg if (islash_curr==ilen) then !the last token is an empty string token = CK_'' islash_next = 0 ! will signal to stop else ! . ! '/123/567/' ! index in remaining string: islash_next = index(path(islash_curr+1:ilen),slash) if (islash_next<=0) then !last token: token = path(islash_curr+1:ilen) else ! convert to actual index in path: islash_next = islash_curr + index(path(islash_curr+1:ilen),slash) if (islash_next>islash_curr+1) then token = path(islash_curr+1:islash_next-1) else !empty token: token = CK_'' end if end if end if ! remove trailing spaces in the token here if necessary: if (.not. json%trailing_spaces_significant) & token = trim(token) ! decode the token: token = decode_rfc6901(token) ! now, parse the token: ! first see if there is a child with this name call json%get_child(p,token,tmp,child_found) if (child_found) then ! it was found p => tmp else ! No key with this name. ! Is it an integer? If so, ! it might be an array index. status_ok = (len(token)>0) if (status_ok) then do i=1,len(token) ! It must only contain (0..9) characters ! (it must be unsigned) if (scan(token(i:i),CK_'0123456789')<1) then status_ok = .false. exit end if end do if (status_ok) then if (len(token)>1 .and. token(1:1)==CK_'0') then ! leading zeros not allowed for some reason status_ok = .false. end if end if if (status_ok) then ! if we make it this far, it should be ! convertable to an integer, so do it. call string_to_integer(token,ival,status_ok) end if end if if (status_ok) then ! ival is an array index (0-based) call json%get_child(p,ival+1,tmp,child_found) if (child_found) then p => tmp else ! not found status_ok = .false. end if end if if (.not. status_ok) then call json%throw_exception('Error in json_get_by_path_rfc6901: '//& 'invalid path specification: '//trim(path)) exit end if end if if (islash_next<=0) exit ! finished ! set up for next token: islash_curr = islash_next end do else call json%throw_exception('Error in json_get_by_path_rfc6901: '//& 'invalid path specification: '//trim(path)) end if end if if (json%exception_thrown) then nullify(p) if (present(found)) then found = .false. call json%clear_exceptions() end if else if (present(found)) found = .true. end if else if (present(found)) found = .false. end if end subroutine json_get_by_path_rfc6901 !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_get_by_path]] where "path" is kind=CDK. subroutine wrap_json_get_by_path(json, me, path, p, found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: me character(kind=CDK,len=*),intent(in) :: path type(json_value),pointer,intent(out) :: p logical(LK),intent(out),optional :: found call json%get(me, to_unicode(path), p, found) end subroutine wrap_json_get_by_path !***************************************************************************************** !***************************************************************************************** !> ! Returns the path to a JSON object that is part ! of a linked list structure. ! ! The path returned would be suitable for input to ! [[json_get_by_path]] and related routines. ! !@note If an error occurs (which in this case means a malformed ! JSON structure) then an exception will be thrown, unless ! `found` is present, which will be set to `false`. `path` ! will be a blank string. ! !@note If `json%path_mode/=1`, then the `use_alt_array_tokens` ! and `path_sep` inputs are ignored if present. subroutine json_get_path(json, p, path, found, use_alt_array_tokens, path_sep) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: p !! a JSON linked list object character(kind=CK,len=:),allocatable,intent(out) :: path !! path to the variable logical(LK),intent(out),optional :: found !! true if there were no problems logical(LK),intent(in),optional :: use_alt_array_tokens !! if true, then '()' are used for array elements !! otherwise, '[]' are used [default] character(kind=CK,len=1),intent(in),optional :: path_sep !! character to use for path separator !! (otherwise use `json%path_separator`) type(json_value),pointer :: tmp !! for traversing the structure type(json_value),pointer :: element !! for traversing the structure integer(IK) :: var_type !! JSON variable type flag character(kind=CK,len=:),allocatable :: name !! variable name character(kind=CK,len=:),allocatable :: parent_name !! variable's parent name character(kind=CK,len=max_integer_str_len) :: istr !! for integer to string conversion (array indices) integer(IK) :: i !! counter integer(IK) :: n_children !! number of children for parent logical(LK) :: use_brackets !! to use '[]' characters for arrays logical(LK) :: parent_is_root !! if the parent is the root !optional input: if (present(use_alt_array_tokens)) then use_brackets = .not. use_alt_array_tokens else use_brackets = .true. end if if (associated(p)) then !traverse the structure via parents up to the root tmp => p do if (.not. associated(tmp)) exit !finished !get info about the current variable: call json%info(tmp,name=name) if (json%path_mode==2) then name = encode_rfc6901(name) end if ! if tmp a child of an object, or an element of an array if (associated(tmp%parent)) then !get info about the parent: call json%info(tmp%parent,var_type=var_type,& n_children=n_children,name=parent_name) if (json%path_mode==2) then parent_name = encode_rfc6901(parent_name) end if select case (var_type) case (json_array) !get array index of this element: element => tmp%parent%children do i = 1, n_children if (.not. associated(element)) then call json%throw_exception('Error in json_get_path: '//& 'malformed JSON structure. ') exit end if if (associated(element,tmp)) then exit else element => element%next end if if (i==n_children) then ! it wasn't found (should never happen) call json%throw_exception('Error in json_get_path: '//& 'malformed JSON structure. ') exit end if end do select case(json%path_mode) case(2) call integer_to_string(i-1,int_fmt,istr) ! 0-based index call add_to_path(parent_name//slash//trim(adjustl(istr))) case(1) call integer_to_string(i,int_fmt,istr) if (use_brackets) then call add_to_path(parent_name//start_array//& trim(adjustl(istr))//end_array,path_sep) else call add_to_path(parent_name//start_array_alt//& trim(adjustl(istr))//end_array_alt,path_sep) end if end select tmp => tmp%parent ! already added parent name case (json_object) !process parent on the next pass call add_to_path(name,path_sep) case default call json%throw_exception('Error in json_get_path: '//& 'malformed JSON structure. '//& 'A variable that is not an object '//& 'or array should not have a child.') exit end select else !the last one: call add_to_path(name,path_sep) end if if (associated(tmp%parent)) then !check if the parent is the root: parent_is_root = (.not. associated(tmp%parent%parent)) if (parent_is_root) exit end if !go to parent: tmp => tmp%parent end do else call json%throw_exception('Error in json_get_path: '//& 'input pointer is not associated') end if !for errors, return blank string: if (json%exception_thrown .or. .not. allocated(path)) then path = CK_'' else if (json%path_mode==2) then ! add the root slash: path = slash//path end if end if !optional output: if (present(found)) then if (json%exception_thrown) then found = .false. call json%clear_exceptions() else found = .true. end if end if contains subroutine add_to_path(str,path_sep) !! prepend the string to the path implicit none character(kind=CK,len=*),intent(in) :: str !! string to prepend to `path` character(kind=CK,len=1),intent(in),optional :: path_sep !! path separator (default is '.'). !! (ignored if `json%path_mode/=1`) select case (json%path_mode) case(2) ! in this case, the options are ignored if (.not. allocated(path)) then path = str else path = str//slash//path end if case(1) ! default path format if (.not. allocated(path)) then path = str else if (present(path_sep)) then ! use user specified: path = str//path_sep//path else ! use the default: path = str//json%path_separator//path end if end if end select end subroutine add_to_path end subroutine json_get_path !***************************************************************************************** !***************************************************************************************** !> ! Wrapper for [[json_get_path]] where "path" and "path_sep" are kind=CDK. subroutine wrap_json_get_path(json, p, path, found, use_alt_array_tokens, path_sep) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: p !! a JSON linked list object character(kind=CDK,len=:),allocatable,intent(out) :: path !! path to the variable logical(LK),intent(out),optional :: found !! true if there were no problems logical(LK),intent(in),optional :: use_alt_array_tokens !! if true, then '()' are used for array elements !! otherwise, '[]' are used [default] character(kind=CDK,len=1),intent(in),optional :: path_sep !! character to use for path separator !! (default is '.') character(kind=CK,len=:),allocatable :: ck_path !! path to the variable character(kind=CK,len=1) :: sep ! from unicode: sep = path_sep ! call the main routine: call json_get_path(json,p,ck_path,found,use_alt_array_tokens,sep) ! from unicode: path = ck_path end subroutine wrap_json_get_path !***************************************************************************************** !***************************************************************************************** !> ! Convert a string into an integer. ! !@note Replacement for the `parse_integer` function in the original code. function string_to_int(json,str) result(ival) implicit none class(json_core),intent(inout) :: json character(kind=CK,len=*),intent(in) :: str integer(IK) :: ival logical(LK) :: status_ok !! error flag if (.not. json%exception_thrown) then ! call the core routine: call string_to_integer(str,ival,status_ok) if (.not. status_ok) then ival = 0 call json%throw_exception('Error in string_to_int: '//& 'string cannot be converted to an integer: '//& trim(str)) end if else ival = 0 end if end function string_to_int !***************************************************************************************** !***************************************************************************************** !> ! Convert a string into a double. function string_to_dble(json,str) result(rval) implicit none class(json_core),intent(inout) :: json character(kind=CK,len=*),intent(in) :: str real(RK) :: rval logical(LK) :: status_ok !! error flag if (.not. json%exception_thrown) then call string_to_real(str,rval,status_ok) if (.not. status_ok) then !if there was an error rval = 0.0_RK call json%throw_exception('Error in string_to_dble: '//& 'string cannot be converted to a double: '//& trim(str)) end if else rval = 0.0_RK end if end function string_to_dble !***************************************************************************************** !***************************************************************************************** !> ! Get an integer value from a [[json_value]]. subroutine json_get_integer(json, me, value) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: me integer(IK),intent(out) :: value value = 0 if ( json%exception_thrown ) return if (me%var_type == json_integer) then value = me%int_value else if (json%strict_type_checking) then call json%throw_exception('Error in get_integer:'//& ' Unable to resolve value to integer: '//me%name) else !type conversions select case(me%var_type) case (json_double) value = int(me%dbl_value) case (json_logical) if (me%log_value) then value = 1 else value = 0 end if case default call json%throw_exception('Error in get_integer:'//& ' Unable to resolve value to integer: '//me%name) end select end if end if end subroutine json_get_integer !***************************************************************************************** !***************************************************************************************** !> ! Get an integer value from a [[json_value]], given the path string. subroutine json_get_integer_by_path(json, me, path, value, found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: me character(kind=CK,len=*),intent(in) :: path integer(IK),intent(out) :: value logical(LK),intent(out),optional :: found type(json_value),pointer :: p value = 0 if ( json%exception_thrown ) then if ( present(found) ) found = .false. return end if nullify(p) call json%get(me=me, path=path, p=p) if (.not. associated(p)) then call json%throw_exception('Error in json_get_integer:'//& ' Unable to resolve path: '// trim(path)) else call json%get(p,value) nullify(p) end if if ( json%exception_thrown ) then if ( present(found) ) then found = .false. call json%clear_exceptions() end if else if ( present(found) ) found = .true. end if end subroutine json_get_integer_by_path !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_get_integer_by_path]], where "path" is kind=CDK. subroutine wrap_json_get_integer_by_path(json, me, path, value, found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: me character(kind=CDK,len=*),intent(in) :: path integer(IK),intent(out) :: value logical(LK),intent(out),optional :: found call json%get(me, to_unicode(path), value, found) end subroutine wrap_json_get_integer_by_path !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 5/14/2014 ! ! Get an integer vector from a [[json_value]]. subroutine json_get_integer_vec(json, me, vec) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me integer(IK),dimension(:),allocatable,intent(out) :: vec logical(LK) :: initialized ! check for 0-length arrays first: select case (me%var_type) case (json_array) if (json%count(me)==0) then allocate(vec(0)) return end if end select initialized = .false. !the callback function is called for each element of the array: call json%get(me, array_callback=get_int_from_array) contains subroutine get_int_from_array(json, element, i, count) !! callback function for integer implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: element integer(IK),intent(in) :: i !! index integer(IK),intent(in) :: count !! size of array !size the output array: if (.not. initialized) then allocate(vec(count)) initialized = .true. end if !populate the elements: call json%get(element, value=vec(i)) end subroutine get_int_from_array end subroutine json_get_integer_vec !***************************************************************************************** !***************************************************************************************** !> ! Get an integer vector from a [[json_value]], given the path string. subroutine json_get_integer_vec_by_path(json, me, path, vec, found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: me character(kind=CK,len=*),intent(in) :: path integer(IK),dimension(:),allocatable,intent(out) :: vec logical(LK),intent(out),optional :: found type(json_value),pointer :: p call json%get(me, path, p, found) if (present(found)) then if (.not. found) return else if (json%exception_thrown) return end if call json%get(p, vec) if (present(found) .and. json%exception_thrown) then call json%clear_exceptions() found = .false. end if end subroutine json_get_integer_vec_by_path !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_get_integer_vec_by_path]], where "path" is kind=CDK subroutine wrap_json_get_integer_vec_by_path(json, me, path, vec, found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me character(kind=CDK,len=*),intent(in) :: path integer(IK),dimension(:),allocatable,intent(out) :: vec logical(LK),intent(out),optional :: found call json%get(me,path=to_unicode(path),vec=vec,found=found) end subroutine wrap_json_get_integer_vec_by_path !***************************************************************************************** !***************************************************************************************** !> ! Get a double value from a [[json_value]]. subroutine json_get_double(json, me, value) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me real(RK),intent(out) :: value value = 0.0_RK if ( json%exception_thrown ) return if (me%var_type == json_double) then value = me%dbl_value else if (json%strict_type_checking) then call json%throw_exception('Error in json_get_double:'//& ' Unable to resolve value to double: '//me%name) else !type conversions select case (me%var_type) case (json_integer) value = me%int_value case (json_logical) if (me%log_value) then value = 1.0_RK else value = 0.0_RK end if case default call json%throw_exception('Error in json_get_double:'//& ' Unable to resolve value to double: '//me%name) end select end if end if end subroutine json_get_double !***************************************************************************************** !***************************************************************************************** !> ! Get a double value from a [[json_value]], given the path. subroutine json_get_double_by_path(json, me, path, value, found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me character(kind=CK,len=*),intent(in) :: path real(RK),intent(out) :: value logical(LK),intent(out),optional :: found type(json_value),pointer :: p value = 0.0_RK if ( json%exception_thrown ) then if ( present(found) ) found = .false. return end if nullify(p) call json%get(me=me, path=path, p=p) if (.not. associated(p)) then call json%throw_exception('Error in json_get_double:'//& ' Unable to resolve path: '//trim(path)) else call json%get(p,value) nullify(p) end if if (json%exception_thrown) then if (present(found)) then found = .false. call json%clear_exceptions() end if else if (present(found)) found = .true. end if end subroutine json_get_double_by_path !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_get_double_by_path]], where "path" is kind=CDK subroutine wrap_json_get_double_by_path(json, me, path, value, found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me character(kind=CDK,len=*),intent(in) :: path real(RK),intent(out) :: value logical(LK),intent(out),optional :: found call json%get(me,to_unicode(path),value,found) end subroutine wrap_json_get_double_by_path !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 5/14/2014 ! ! Get a double vector from a [[json_value]]. subroutine json_get_double_vec(json, me, vec) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me real(RK),dimension(:),allocatable,intent(out) :: vec logical(LK) :: initialized ! check for 0-length arrays first: select case (me%var_type) case (json_array) if (json%count(me)==0) then allocate(vec(0)) return end if end select initialized = .false. !the callback function is called for each element of the array: call json%get(me, array_callback=get_double_from_array) contains subroutine get_double_from_array(json, element, i, count) !! callback function for double implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: element integer(IK),intent(in) :: i !! index integer(IK),intent(in) :: count !! size of array !size the output array: if (.not. initialized) then allocate(vec(count)) initialized = .true. end if !populate the elements: call json%get(element, value=vec(i)) end subroutine get_double_from_array end subroutine json_get_double_vec !***************************************************************************************** !***************************************************************************************** !> ! Get a double vector from a [[json_value]], given the path. subroutine json_get_double_vec_by_path(json, me, path, vec, found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: me character(kind=CK,len=*),intent(in) :: path real(RK),dimension(:),allocatable,intent(out) :: vec logical(LK),intent(out),optional :: found type(json_value),pointer :: p call json%get(me, path, p, found) if (present(found)) then if (.not. found) return else if (json%exception_thrown) return end if call json%get(p, vec) if (present(found) .and. json%exception_thrown) then call json%clear_exceptions() found = .false. end if end subroutine json_get_double_vec_by_path !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_get_double_vec_by_path]], where "path" is kind=CDK subroutine wrap_json_get_double_vec_by_path(json, me, path, vec, found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer :: me character(kind=CDK,len=*),intent(in) :: path real(RK),dimension(:),allocatable,intent(out) :: vec logical(LK),intent(out),optional :: found call json%get(me, to_unicode(path), vec, found) end subroutine wrap_json_get_double_vec_by_path !***************************************************************************************** !***************************************************************************************** !> ! Get a logical value from a [[json_value]]. subroutine json_get_logical(json, me, value) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: me logical(LK),intent(out) :: value value = .false. if ( json%exception_thrown ) return if (me%var_type == json_logical) then value = me%log_value else if (json%strict_type_checking) then call json%throw_exception('Error in json_get_logical: '//& 'Unable to resolve value to logical: '//& me%name) else !type conversions select case (me%var_type) case (json_integer) value = (me%int_value > 0) case default call json%throw_exception('Error in json_get_logical: '//& 'Unable to resolve value to logical: '//& me%name) end select end if end if end subroutine json_get_logical !***************************************************************************************** !***************************************************************************************** !> ! Get a logical value from a [[json_value]], given the path. subroutine json_get_logical_by_path(json, me, path, value, found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: me character(kind=CK,len=*),intent(in) :: path logical(LK),intent(out) :: value logical(LK),intent(out),optional :: found type(json_value),pointer :: p value = .false. if ( json%exception_thrown) then if ( present(found) ) found = .false. return end if nullify(p) call json%get(me=me, path=path, p=p) if (.not. associated(p)) then call json%throw_exception('Error in json_get_logical:'//& ' Unable to resolve path: '//trim(path)) else call json%get(p,value) nullify(p) end if if (json%exception_thrown) then if (present(found)) then found = .false. call json%clear_exceptions() end if else if (present(found)) found = .true. end if end subroutine json_get_logical_by_path !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_get_logical_by_path]], where "path" is kind=CDK subroutine wrap_json_get_logical_by_path(json, me, path, value, found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: me character(kind=CDK,len=*),intent(in) :: path logical(LK),intent(out) :: value logical(LK),intent(out),optional :: found call json%get(me,to_unicode(path),value,found) end subroutine wrap_json_get_logical_by_path !***************************************************************************************** !***************************************************************************************** !> author: Jacob Williams ! date: 5/14/2014 ! ! Get a logical vector from [[json_value]]. subroutine json_get_logical_vec(json, me, vec) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: me logical(LK),dimension(:),allocatable,intent(out) :: vec logical(LK) :: initialized ! check for 0-length arrays first: select case (me%var_type) case (json_array) if (json%count(me)==0) then allocate(vec(0)) return end if end select initialized = .false. !the callback function is called for each element of the array: call json%get(me, array_callback=get_logical_from_array) contains subroutine get_logical_from_array(json, element, i, count) !! callback function for logical implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: element integer(IK),intent(in) :: i !! index integer(IK),intent(in) :: count !! size of array !size the output array: if (.not. initialized) then allocate(vec(count)) initialized = .true. end if !populate the elements: call json%get(element, value=vec(i)) end subroutine get_logical_from_array end subroutine json_get_logical_vec !***************************************************************************************** !***************************************************************************************** !> ! Get a logical vector from a [[json_value]], given the path. subroutine json_get_logical_vec_by_path(json, me, path, vec, found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: me character(kind=CK,len=*),intent(in) :: path logical(LK),dimension(:),allocatable,intent(out) :: vec logical(LK),intent(out),optional :: found type(json_value),pointer :: p call json%get(me, path, p, found) if (present(found)) then if (.not. found) return else if (json%exception_thrown) return end if call json%get(p, vec) if (present(found) .and. json%exception_thrown) then call json%clear_exceptions() found = .false. end if end subroutine json_get_logical_vec_by_path !***************************************************************************************** !***************************************************************************************** !> ! Alternate version of [[json_get_logical_vec_by_path]], where "path" is kind=CDK subroutine wrap_json_get_logical_vec_by_path(json, me, path, vec, found) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: me character(kind=CDK,len=*),intent(in) :: path logical(LK),dimension(:),allocatable,intent(out) :: vec logical(LK),intent(out),optional :: found call json%get(me,to_unicode(path),vec,found) end subroutine wrap_json_get_logical_vec_by_path !***************************************************************************************** !***************************************************************************************** !> ! Get a character string from a [[json_value]]. subroutine json_get_string(json, me, value) implicit none class(json_core),intent(inout) :: json type(json_value),pointer,intent(in) :: me character(kind=CK,len=:),allocatable,intent(out) :: value character(kind=CK,len=:),allocatable :: error_message !! for [[unescape_string]] value = CK_'' if (.not. json%exception_thrown) then if (me%var_type == json_string) <