@@ -436,6 +436,7 @@ module json_value_module
436436 procedure ,private :: MAYBEWRAP(json_get_alloc_string_vec_by_path)
437437 procedure ,private :: json_get_by_path_default
438438 procedure ,private :: json_get_by_path_rfc6901
439+ procedure ,private :: json_get_by_path_jsonpath_bracket
439440
440441 procedure ,public :: print_to_string = > json_value_to_string ! ! Print the [[json_value]]
441442 ! ! structure to an allocatable
@@ -5530,7 +5531,7 @@ subroutine json_get_by_path(json, me, path, p, found)
55305531 logical (LK),intent (out ),optional :: found ! ! true if it was found
55315532
55325533 character (kind= CK,len= max_integer_str_len),allocatable :: path_mode_str ! ! string version
5533- ! ! of `json%path_mode`
5534+ ! ! of `json%path_mode`
55345535
55355536 nullify(p)
55365537
@@ -5542,6 +5543,8 @@ subroutine json_get_by_path(json, me, path, p, found)
55425543 call json% json_get_by_path_default(me, path, p, found)
55435544 case (2_IK )
55445545 call json% json_get_by_path_rfc6901(me, path, p, found)
5546+ case (3_IK )
5547+ call json% json_get_by_path_jsonpath_bracket(me, path, p, found)
55455548 case default
55465549 call integer_to_string(json% path_mode,int_fmt,path_mode_str)
55475550 call json% throw_exception(' Error in json_get_by_path: Unsupported path_mode: ' // &
@@ -5586,13 +5589,12 @@ subroutine json_create_by_path(json,me,path,p,found,was_created)
55865589
55875590 type (json_value),pointer :: tmp
55885591 character (kind= CK,len= max_integer_str_len) :: path_mode_str ! ! string version
5589- ! ! of `json%path_mode`
5592+ ! ! of `json%path_mode`
55905593
55915594 if (present (p)) nullify(p)
55925595
55935596 if (.not. json% exception_thrown) then
55945597
5595- ! note: path_mode can only be 1 or 2 (which was checked in initialize)
55965598 select case (json% path_mode)
55975599 case (1_IK )
55985600 call json% json_get_by_path_default(me,path,tmp,found,&
@@ -5609,6 +5611,11 @@ subroutine json_create_by_path(json,me,path,p,found,was_created)
56095611 found = .false.
56105612 end if
56115613 if (present (was_created)) was_created = .false.
5614+ ! case(3_IK)
5615+ ! call json%json_get_by_path_jsonpath_bracket(me,path,tmp,found,&
5616+ ! create_it=.true.,&
5617+ ! was_created=was_created)
5618+ ! if (present(p)) p => tmp
56125619 case default
56135620 call integer_to_string(json% path_mode,int_fmt,path_mode_str)
56145621 call json% throw_exception(' Error in json_create_by_path: Unsupported path_mode: ' // &
@@ -5658,6 +5665,7 @@ end subroutine wrap_json_create_by_path
56585665! ### Example
56595666!
56605667! ````fortran
5668+ ! type(json_core) :: json
56615669! type(json_value),pointer :: dat,p
56625670! logical :: found
56635671! !...
@@ -5709,17 +5717,17 @@ subroutine json_get_by_path_default(json,me,path,p,found,create_it,was_created)
57095717 ! ! was actually created. Otherwise
57105718 ! ! it will be false.
57115719
5712- integer (IK) :: i ! ! counter of characters in `path`
5713- integer (IK) :: length ! ! significant length of `path`
5714- integer (IK) :: child_i ! ! index for getting children
5715- character (kind= CK,len= 1 ) :: c ! ! a character in the `path`
5716- logical (LK) :: array ! ! flag when searching for array index in `path`
5717- type (json_value),pointer :: tmp ! ! temp variables for getting child objects
5718- logical (LK) :: child_found ! ! if the child value was found
5719- logical (LK) :: create ! ! if the object is to be created
5720- logical (LK) :: created ! ! if `create` is true, then this will be
5721- ! ! true if the leaf object had to be created
5722- integer (IK) :: j ! ! counter of children when creating object
5720+ integer (IK) :: i ! ! counter of characters in `path`
5721+ integer (IK) :: length ! ! significant length of `path`
5722+ integer (IK) :: child_i ! ! index for getting children
5723+ character (kind= CK,len= 1 ) :: c ! ! a character in the `path`
5724+ logical (LK) :: array ! ! flag when searching for array index in `path`
5725+ type (json_value),pointer :: tmp ! ! temp variables for getting child objects
5726+ logical (LK) :: child_found ! ! if the child value was found
5727+ logical (LK) :: create ! ! if the object is to be created
5728+ logical (LK) :: created ! ! if `create` is true, then this will be
5729+ ! ! true if the leaf object had to be created
5730+ integer (IK) :: j ! ! counter of children when creating object
57235731
57245732 nullify(p)
57255733
@@ -6190,6 +6198,283 @@ subroutine json_get_by_path_rfc6901(json, me, path, p, found)
61906198 end subroutine json_get_by_path_rfc6901
61916199! *****************************************************************************************
61926200
6201+ ! *****************************************************************************************
6202+ ! > author: Jacob Williams
6203+ ! date: 9/2/2017
6204+ !
6205+ ! Returns the [[json_value]] pointer given the path string,
6206+ ! using the "JSON Pointer" path specification defined by the
6207+ ! JSONPath "bracket-notation".
6208+ !
6209+ ! ### Example
6210+ !
6211+ ! ````fortran
6212+ ! type(json_core) :: json
6213+ ! type(json_value),pointer :: dat,p
6214+ ! logical :: found
6215+ ! !...
6216+ ! call json%get(dat,"$['store']['book'][1]['title']",p,found)
6217+ ! ````
6218+ !
6219+ ! The first character `$` is optional, and signifies the root
6220+ ! of the structure. If it is not present, the the first key is
6221+ ! taken to be in the `me` object.
6222+ !
6223+ ! ### See also
6224+ ! * [[json_get_by_path_default]] - subset of JSONPath "dot-notation"
6225+ ! * [[json_get_by_path_rfc6901]] - RFC6901 "JSON pointer"
6226+ !
6227+ ! ### Reference
6228+ ! * [JSONPath](http://goessner.net/articles/JsonPath/)
6229+ !
6230+ ! @note Uses 1-based array indices (same as [[json_get_by_path_default]],
6231+ ! but unlike [[json_get_by_path_rfc6901]] which uses 0-based indices).
6232+ !
6233+ ! @warning The `create` logic hasn't been added yet !!!
6234+
6235+ subroutine json_get_by_path_jsonpath_bracket (json ,me ,path ,p ,found ,create_it ,was_created )
6236+
6237+ implicit none
6238+
6239+ class(json_core),intent (inout ) :: json
6240+ type (json_value),pointer ,intent (in ) :: me ! ! a JSON linked list
6241+ character (kind= CK,len=* ),intent (in ) :: path ! ! path to the variable
6242+ ! ! (using JSONPath
6243+ ! ! "bracket-notation")
6244+ type (json_value),pointer ,intent (out ) :: p ! ! pointer to the variable
6245+ ! ! specify by `path`
6246+ logical (LK),intent (out ),optional :: found ! ! true if it was found
6247+ logical (LK),intent (in ),optional :: create_it ! ! if a variable is not present
6248+ ! ! in the path, then it is created.
6249+ ! ! the leaf node is returned as
6250+ ! ! a `null` json type and can be
6251+ ! ! changed by the caller.
6252+ logical (LK),intent (out ),optional :: was_created ! ! if `create_it` is true, this
6253+ ! ! will be true if the variable
6254+ ! ! was actually created. Otherwise
6255+ ! ! it will be false.
6256+
6257+ character (kind= CK,len= :),allocatable :: token ! ! a token in the path
6258+ ! ! (between the `['']` or
6259+ ! ! `[]` characters)
6260+ integer (IK) :: istart ! ! location of current '['
6261+ ! ! character in the path
6262+ integer (IK) :: iend ! ! location of current ']'
6263+ ! ! character in the path
6264+ integer (IK) :: ival ! ! integer array index value
6265+ logical (LK) :: status_ok ! ! error flag
6266+ type (json_value),pointer :: tmp ! ! temporary variable for
6267+ ! ! traversing the structure
6268+ integer (IK) :: i ! ! counter
6269+ integer (IK) :: ilen ! ! length of `path` string
6270+ logical (LK) :: create ! ! if the object is to be created
6271+ logical (LK) :: created ! ! if `create` is true, then this will be
6272+ ! ! true if the leaf object had to be created
6273+ integer (IK) :: j ! ! counter of children when creating object
6274+
6275+ ! TODO instead of reallocating `token` all the time, just
6276+ ! allocate a big size and keep track of the length,
6277+ ! then just reallocate only if necessary.
6278+ ! [would probably be inefficient if there was a very large token,
6279+ ! and then a bunch of small ones... but for similarly-sized ones
6280+ ! it should be way more efficient since it would avoid most
6281+ ! reallocations.]
6282+
6283+ nullify(p)
6284+
6285+ if (.not. json% exception_thrown) then
6286+
6287+ if (present (create_it)) then
6288+ create = create_it
6289+ else
6290+ create = .false.
6291+ end if
6292+
6293+ p = > me ! initialize
6294+ created = .false.
6295+
6296+ if (path== CK_' ' ) then
6297+ call json% throw_exception(' Error in json_get_by_path_jsonpath_bracket: ' // &
6298+ ' invalid path specification: ' // trim (path))
6299+ else
6300+
6301+ if (path(1 :1 )==root .or. path(1 :1 )==start_array) then ! the first character must be
6302+ ! a `$` (root) or a `[`
6303+ ! (element of `me`)
6304+
6305+ if (path(1 :1 )==root) then
6306+ ! go to the root
6307+ do while (associated (p% parent))
6308+ p = > p% parent
6309+ end do
6310+ end if
6311+
6312+ ! keep trailing space or not:
6313+ if (json% trailing_spaces_significant) then
6314+ ilen = len (path)
6315+ else
6316+ ilen = len_trim (path)
6317+ end if
6318+
6319+ if (ilen> 1 ) then
6320+
6321+ istart = 2 ! initialize first '[' location index
6322+
6323+ do
6324+
6325+ if (istart> ilen) exit ! finished
6326+
6327+ ! must be the next start bracket:
6328+ if (path(istart:istart) /= start_array) then
6329+ call json% throw_exception(&
6330+ ' Error in json_get_by_path_jsonpath_bracket: ' // &
6331+ ' expecting "[", found: "' // trim (path(istart:istart))// &
6332+ ' " in path: ' // trim (path))
6333+ exit
6334+ end if
6335+
6336+ ! get the next token by checking:
6337+ !
6338+ ! * is the token after istart a quote?
6339+ ! if so, then search for the next `']`
6340+ ! ['']
6341+ !
6342+ ! * if not, then maybe it is a number,
6343+ ! so search for the next `]`
6344+ ! [1]
6345+ !
6346+ ! istart iend
6347+ ! | |
6348+ ! [abcdefg][h][ijk]
6349+
6350+ ! verify length of remaining string
6351+ if (istart+2 <= ilen) then
6352+ if (path(istart+1 :istart+1 ) == single_quote) then ! ['
6353+ istart = istart + 1 ! move to ' index
6354+ ! it should be a key value
6355+ iend = istart + index (path(istart+1 :ilen),&
6356+ single_quote// end_array) ! ']
6357+ if (iend> istart) then
6358+ if (iend> istart+1 ) then
6359+ token = path(istart+1 :iend-1 )
6360+ else
6361+ token = CK_' ' ! blank string
6362+ end if
6363+ ! remove trailing spaces in
6364+ ! the token here if necessary:
6365+ if (.not. json% trailing_spaces_significant) &
6366+ token = trim (token)
6367+ ! have a token, see if it is valid:
6368+ call json% get_child(p,token,tmp,status_ok)
6369+ if (status_ok) then
6370+ ! it was found
6371+ p = > tmp
6372+ else
6373+ call json% throw_exception(&
6374+ ' Error in json_get_by_path_jsonpath_bracket: ' // &
6375+ ' invalid token found: "' // token// &
6376+ ' " in path: ' // trim (path))
6377+ exit
6378+ end if
6379+ iend = iend + 1 ! move to ]
6380+ else
6381+ call json% throw_exception(&
6382+ ' Error in json_get_by_path_jsonpath_bracket: ' // &
6383+ ' invalid path: ' // trim (path))
6384+ exit
6385+ end if
6386+ else
6387+ ! it might be an integer value
6388+ iend = istart + index (path(istart+1 :ilen),end_array) ! ]
6389+ if (iend> istart+1 ) then
6390+
6391+ ! this should be an integer:
6392+ token = path(istart+1 :iend-1 )
6393+
6394+ ! verify that there are no spaces or other
6395+ ! characters in the string:
6396+ do i= 1 ,len (token)
6397+ ! It must only contain (0..9) characters
6398+ ! (it must be unsigned)
6399+ if (scan (token(i:i),CK_' 0123456789' )<1 ) then
6400+ status_ok = .false.
6401+ exit
6402+ end if
6403+ end do
6404+ if (status_ok) then
6405+ call string_to_integer(token,ival,status_ok)
6406+ if (status_ok) status_ok = ival> 0 ! assuming 1-based array indices
6407+ end if
6408+ if (status_ok) then
6409+ ! have a valid integer to use as an index, so
6410+ ! see if this element is really there:
6411+ call json% get_child(p,ival,tmp,status_ok)
6412+ if (status_ok) then
6413+ ! found it
6414+ p = > tmp
6415+ else
6416+ ! not found
6417+ call json% throw_exception(&
6418+ ' Error in json_get_by_path_jsonpath_bracket: ' // &
6419+ ' invalid array index found: "' // token// &
6420+ ' " in path: ' // trim (path))
6421+ exit
6422+ end if
6423+ else
6424+ call json% throw_exception(&
6425+ ' Error in json_get_by_path_jsonpath_bracket: ' // &
6426+ ' invalid token: "' // token// &
6427+ ' " in path: ' // trim (path))
6428+ exit
6429+ end if
6430+
6431+ else
6432+ call json% throw_exception(&
6433+ ' Error in json_get_by_path_jsonpath_bracket: ' // &
6434+ ' invalid path: ' // trim (path))
6435+ exit
6436+ end if
6437+ end if
6438+ else
6439+ call json% throw_exception(&
6440+ ' Error in json_get_by_path_jsonpath_bracket: ' // &
6441+ ' invalid path: ' // trim (path))
6442+ exit
6443+ end if
6444+
6445+ ! set up for next token:
6446+ istart = iend + 1
6447+
6448+ end do
6449+
6450+ end if
6451+
6452+ else
6453+ call json% throw_exception(&
6454+ ' Error in json_get_by_path_jsonpath_bracket: ' // &
6455+ ' expecting "' // root// ' ", found: "' // path(1 :1 )// &
6456+ ' " in path: ' // trim (path))
6457+ end if
6458+
6459+ end if
6460+
6461+ if (json% exception_thrown) then
6462+ nullify(p)
6463+ if (present (found)) then
6464+ found = .false.
6465+ call json% clear_exceptions()
6466+ end if
6467+ else
6468+ if (present (found)) found = .true.
6469+ end if
6470+
6471+ else
6472+ if (present (found)) found = .false.
6473+ end if
6474+
6475+ end subroutine json_get_by_path_jsonpath_bracket
6476+ ! *****************************************************************************************
6477+
61936478! *****************************************************************************************
61946479! >
61956480! Alternate version of [[json_get_by_path]] where "path" is kind=CDK.
0 commit comments