Returns information about character strings returned from a json_value.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(json_core), | intent(inout) | :: | json | |||
type(json_value), | pointer | :: | p | |||
integer(kind=IK), | intent(out), | optional | dimension(:), allocatable | :: | ilen | if |
integer(kind=IK), | intent(out), | optional | :: | max_str_len | The maximum length required to
hold the string representation returned
by a call to a |
|
logical(kind=LK), | intent(out), | optional | :: | found | true if there were no errors. if not present, an error will throw an exception |
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