json_check_children_for_duplicate_keys Subroutine

private subroutine json_check_children_for_duplicate_keys(json, p, has_duplicate, name, path)

Checks a JSON object for duplicate child names.

It uses the specified settings for name matching (see name_strings_equal).

Note

This will only check for one duplicate, it will return the first one that it finds.

Type Bound

json_core

Arguments

Type IntentOptional Attributes Name
class(json_core), intent(inout) :: json
type(json_value), intent(in), pointer :: p

the object to search. If p is not a json_object, then has_duplicate will be false.

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

true if there is at least two children have duplicate name values.

character(kind=CK, len=:), intent(out), optional, allocatable :: name

the duplicate name (unallocated if no duplicate was found)

character(kind=CK, len=:), intent(out), optional, allocatable :: path

the full path to the duplicate name (unallocated if no duplicate was found)


Calls

proc~~json_check_children_for_duplicate_keys~~CallsGraph proc~json_check_children_for_duplicate_keys json_value_module::json_core%json_check_children_for_duplicate_keys none~get_child json_value_module::json_core%get_child proc~json_check_children_for_duplicate_keys->none~get_child none~get_path json_value_module::json_core%get_path proc~json_check_children_for_duplicate_keys->none~get_path none~throw_exception json_value_module::json_core%throw_exception proc~json_check_children_for_duplicate_keys->none~throw_exception proc~name_strings_equal json_value_module::json_core%name_strings_equal proc~json_check_children_for_duplicate_keys->proc~name_strings_equal proc~json_value_get_child json_value_module::json_core%json_value_get_child none~get_child->proc~json_value_get_child proc~json_value_get_child_by_index json_value_module::json_core%json_value_get_child_by_index none~get_child->proc~json_value_get_child_by_index proc~json_value_get_child_by_name json_value_module::json_core%json_value_get_child_by_name none~get_child->proc~json_value_get_child_by_name proc~wrap_json_value_get_child_by_name json_value_module::json_core%wrap_json_value_get_child_by_name none~get_child->proc~wrap_json_value_get_child_by_name proc~json_get_path json_value_module::json_core%json_get_path none~get_path->proc~json_get_path proc~wrap_json_get_path json_value_module::json_core%wrap_json_get_path none~get_path->proc~wrap_json_get_path proc~json_throw_exception json_value_module::json_core%json_throw_exception none~throw_exception->proc~json_throw_exception proc~wrap_json_throw_exception json_value_module::json_core%wrap_json_throw_exception none~throw_exception->proc~wrap_json_throw_exception proc~lowercase_string json_string_utilities::lowercase_string proc~name_strings_equal->proc~lowercase_string proc~json_get_path->none~throw_exception none~info json_value_module::json_core%info proc~json_get_path->none~info proc~encode_rfc6901 json_string_utilities::encode_rfc6901 proc~json_get_path->proc~encode_rfc6901 proc~integer_to_string json_string_utilities::integer_to_string proc~json_get_path->proc~integer_to_string proc~json_clear_exceptions json_value_module::json_core%json_clear_exceptions proc~json_get_path->proc~json_clear_exceptions proc~json_value_get_child->none~throw_exception proc~json_value_get_child_by_index->none~throw_exception proc~json_value_get_child_by_index->proc~json_clear_exceptions proc~json_value_get_child_by_name->none~throw_exception proc~json_value_get_child_by_name->proc~json_clear_exceptions proc~name_equal json_value_module::json_core%name_equal proc~json_value_get_child_by_name->proc~name_equal proc~wrap_json_get_path->none~get_path interface~to_unicode json_string_utilities::to_unicode proc~wrap_json_get_path->interface~to_unicode proc~wrap_json_throw_exception->none~throw_exception proc~wrap_json_throw_exception->interface~to_unicode proc~wrap_json_value_get_child_by_name->interface~to_unicode none~get json_value_module::json_core%get proc~wrap_json_value_get_child_by_name->none~get proc~to_uni json_string_utilities::to_uni interface~to_unicode->proc~to_uni proc~to_uni_vec json_string_utilities::to_uni_vec interface~to_unicode->proc~to_uni_vec proc~json_get_alloc_string_vec json_value_module::json_core%json_get_alloc_string_vec none~get->proc~json_get_alloc_string_vec proc~json_get_alloc_string_vec_by_path json_value_module::json_core%json_get_alloc_string_vec_by_path none~get->proc~json_get_alloc_string_vec_by_path proc~json_get_array json_value_module::json_core%json_get_array none~get->proc~json_get_array proc~json_get_array_by_path json_value_module::json_core%json_get_array_by_path none~get->proc~json_get_array_by_path proc~json_get_by_path json_value_module::json_core%json_get_by_path none~get->proc~json_get_by_path proc~json_get_integer json_value_module::json_core%json_get_integer none~get->proc~json_get_integer proc~json_get_integer_by_path json_value_module::json_core%json_get_integer_by_path none~get->proc~json_get_integer_by_path proc~json_get_integer_vec json_value_module::json_core%json_get_integer_vec none~get->proc~json_get_integer_vec proc~json_get_integer_vec_by_path json_value_module::json_core%json_get_integer_vec_by_path none~get->proc~json_get_integer_vec_by_path proc~json_get_logical json_value_module::json_core%json_get_logical none~get->proc~json_get_logical proc~json_get_logical_by_path json_value_module::json_core%json_get_logical_by_path none~get->proc~json_get_logical_by_path proc~json_get_logical_vec json_value_module::json_core%json_get_logical_vec none~get->proc~json_get_logical_vec proc~json_get_logical_vec_by_path json_value_module::json_core%json_get_logical_vec_by_path none~get->proc~json_get_logical_vec_by_path proc~json_get_real json_value_module::json_core%json_get_real none~get->proc~json_get_real proc~json_get_real32 json_value_module::json_core%json_get_real32 none~get->proc~json_get_real32 proc~json_get_real32_by_path json_value_module::json_core%json_get_real32_by_path none~get->proc~json_get_real32_by_path proc~json_get_real32_vec json_value_module::json_core%json_get_real32_vec none~get->proc~json_get_real32_vec proc~json_get_real32_vec_by_path json_value_module::json_core%json_get_real32_vec_by_path none~get->proc~json_get_real32_vec_by_path proc~json_get_real_by_path json_value_module::json_core%json_get_real_by_path none~get->proc~json_get_real_by_path proc~json_get_real_vec json_value_module::json_core%json_get_real_vec none~get->proc~json_get_real_vec proc~json_get_real_vec_by_path json_value_module::json_core%json_get_real_vec_by_path none~get->proc~json_get_real_vec_by_path proc~json_get_string json_value_module::json_core%json_get_string none~get->proc~json_get_string proc~json_get_string_by_path json_value_module::json_core%json_get_string_by_path none~get->proc~json_get_string_by_path proc~json_get_string_vec json_value_module::json_core%json_get_string_vec none~get->proc~json_get_string_vec proc~json_get_string_vec_by_path json_value_module::json_core%json_get_string_vec_by_path none~get->proc~json_get_string_vec_by_path proc~wrap_json_get_alloc_string_vec_by_path json_value_module::json_core%wrap_json_get_alloc_string_vec_by_path none~get->proc~wrap_json_get_alloc_string_vec_by_path proc~wrap_json_get_array_by_path json_value_module::json_core%wrap_json_get_array_by_path none~get->proc~wrap_json_get_array_by_path proc~wrap_json_get_by_path json_value_module::json_core%wrap_json_get_by_path none~get->proc~wrap_json_get_by_path proc~wrap_json_get_integer_by_path json_value_module::json_core%wrap_json_get_integer_by_path none~get->proc~wrap_json_get_integer_by_path proc~wrap_json_get_integer_vec_by_path json_value_module::json_core%wrap_json_get_integer_vec_by_path none~get->proc~wrap_json_get_integer_vec_by_path proc~wrap_json_get_logical_by_path json_value_module::json_core%wrap_json_get_logical_by_path none~get->proc~wrap_json_get_logical_by_path proc~wrap_json_get_logical_vec_by_path json_value_module::json_core%wrap_json_get_logical_vec_by_path none~get->proc~wrap_json_get_logical_vec_by_path proc~wrap_json_get_real32_by_path json_value_module::json_core%wrap_json_get_real32_by_path none~get->proc~wrap_json_get_real32_by_path proc~wrap_json_get_real32_vec_by_path json_value_module::json_core%wrap_json_get_real32_vec_by_path none~get->proc~wrap_json_get_real32_vec_by_path proc~wrap_json_get_real_by_path json_value_module::json_core%wrap_json_get_real_by_path none~get->proc~wrap_json_get_real_by_path proc~wrap_json_get_real_vec_by_path json_value_module::json_core%wrap_json_get_real_vec_by_path none~get->proc~wrap_json_get_real_vec_by_path proc~wrap_json_get_string_by_path json_value_module::json_core%wrap_json_get_string_by_path none~get->proc~wrap_json_get_string_by_path proc~wrap_json_get_string_vec_by_path json_value_module::json_core%wrap_json_get_string_vec_by_path none~get->proc~wrap_json_get_string_vec_by_path proc~json_info json_value_module::json_core%json_info none~info->proc~json_info proc~json_info_by_path json_value_module::json_core%json_info_by_path none~info->proc~json_info_by_path proc~wrap_json_info_by_path json_value_module::json_core%wrap_json_info_by_path none~info->proc~wrap_json_info_by_path proc~replace_string json_string_utilities::replace_string proc~encode_rfc6901->proc~replace_string proc~name_equal->proc~name_strings_equal proc~json_get_alloc_string_vec->none~get none~string_info json_value_module::json_core%string_info proc~json_get_alloc_string_vec->none~string_info proc~json_get_alloc_string_vec_by_path->none~throw_exception proc~json_get_alloc_string_vec_by_path->none~get proc~json_get_alloc_string_vec_by_path->proc~json_clear_exceptions proc~flag_not_found json_value_module::flag_not_found proc~json_get_alloc_string_vec_by_path->proc~flag_not_found proc~json_get_array->none~throw_exception proc~json_get_array_by_path->none~throw_exception proc~json_get_array_by_path->none~get proc~json_get_array_by_path->proc~json_clear_exceptions proc~json_get_by_path->none~throw_exception proc~json_get_by_path->proc~integer_to_string proc~json_get_by_path->proc~json_clear_exceptions proc~json_get_by_path_default json_value_module::json_core%json_get_by_path_default proc~json_get_by_path->proc~json_get_by_path_default proc~json_get_by_path_jsonpath_bracket json_value_module::json_core%json_get_by_path_jsonpath_bracket proc~json_get_by_path->proc~json_get_by_path_jsonpath_bracket proc~json_get_by_path_rfc6901 json_value_module::json_core%json_get_by_path_rfc6901 proc~json_get_by_path->proc~json_get_by_path_rfc6901 proc~json_get_integer->none~throw_exception proc~string_to_integer json_string_utilities::string_to_integer proc~json_get_integer->proc~string_to_integer proc~json_get_integer_by_path->none~throw_exception proc~json_get_integer_by_path->none~get proc~json_get_integer_by_path->proc~json_clear_exceptions proc~json_get_integer_by_path->proc~flag_not_found proc~json_get_integer_vec->none~get proc~json_get_integer_vec_by_path->none~throw_exception proc~json_get_integer_vec_by_path->none~get proc~json_get_integer_vec_by_path->proc~json_clear_exceptions proc~json_get_integer_vec_by_path->proc~flag_not_found proc~json_get_logical->none~throw_exception proc~json_get_logical_by_path->none~throw_exception proc~json_get_logical_by_path->none~get proc~json_get_logical_by_path->proc~json_clear_exceptions proc~json_get_logical_by_path->proc~flag_not_found proc~json_get_logical_vec->none~get proc~json_get_logical_vec_by_path->none~throw_exception proc~json_get_logical_vec_by_path->none~get proc~json_get_logical_vec_by_path->proc~json_clear_exceptions proc~json_get_logical_vec_by_path->proc~flag_not_found proc~json_get_real->none~throw_exception proc~string_to_real json_string_utilities::string_to_real proc~json_get_real->proc~string_to_real proc~json_get_real32->none~get proc~json_get_real32_by_path->none~get proc~json_get_real32_vec->none~get proc~json_get_real32_vec_by_path->none~get proc~json_get_real_by_path->none~throw_exception proc~json_get_real_by_path->none~get proc~json_get_real_by_path->proc~json_clear_exceptions proc~json_get_real_by_path->proc~flag_not_found proc~json_get_real_vec->none~get proc~json_get_real_vec_by_path->none~throw_exception proc~json_get_real_vec_by_path->none~get proc~json_get_real_vec_by_path->proc~json_clear_exceptions proc~json_get_real_vec_by_path->proc~flag_not_found proc~json_get_string->none~throw_exception proc~json_get_string->proc~integer_to_string proc~escape_string json_string_utilities::escape_string proc~json_get_string->proc~escape_string proc~real_to_string json_string_utilities::real_to_string proc~json_get_string->proc~real_to_string proc~json_get_string_by_path->none~throw_exception proc~json_get_string_by_path->none~get proc~json_get_string_by_path->proc~json_clear_exceptions proc~json_get_string_by_path->proc~flag_not_found proc~json_get_string_vec->none~get proc~json_get_string_vec_by_path->none~throw_exception proc~json_get_string_vec_by_path->none~get proc~json_get_string_vec_by_path->proc~json_clear_exceptions proc~json_get_string_vec_by_path->proc~flag_not_found proc~json_info->none~throw_exception proc~json_info_by_path->none~get proc~json_info_by_path->none~info proc~wrap_json_get_alloc_string_vec_by_path->interface~to_unicode proc~wrap_json_get_alloc_string_vec_by_path->none~get proc~wrap_json_get_array_by_path->interface~to_unicode proc~wrap_json_get_array_by_path->none~get proc~wrap_json_get_by_path->interface~to_unicode proc~wrap_json_get_by_path->none~get proc~wrap_json_get_integer_by_path->interface~to_unicode proc~wrap_json_get_integer_by_path->none~get proc~wrap_json_get_integer_vec_by_path->interface~to_unicode proc~wrap_json_get_integer_vec_by_path->none~get proc~wrap_json_get_logical_by_path->interface~to_unicode proc~wrap_json_get_logical_by_path->none~get proc~wrap_json_get_logical_vec_by_path->interface~to_unicode proc~wrap_json_get_logical_vec_by_path->none~get proc~wrap_json_get_real32_by_path->interface~to_unicode proc~wrap_json_get_real32_by_path->none~get proc~wrap_json_get_real32_vec_by_path->interface~to_unicode proc~wrap_json_get_real32_vec_by_path->none~get proc~wrap_json_get_real_by_path->interface~to_unicode proc~wrap_json_get_real_by_path->none~get proc~wrap_json_get_real_vec_by_path->interface~to_unicode proc~wrap_json_get_real_vec_by_path->none~get proc~wrap_json_get_string_by_path->interface~to_unicode proc~wrap_json_get_string_by_path->none~get proc~wrap_json_get_string_vec_by_path->interface~to_unicode proc~wrap_json_get_string_vec_by_path->none~get proc~wrap_json_info_by_path->interface~to_unicode proc~wrap_json_info_by_path->none~info proc~json_string_info json_value_module::json_core%json_string_info none~string_info->proc~json_string_info proc~valid_json_hex json_string_utilities::valid_json_hex proc~escape_string->proc~valid_json_hex proc~json_get_by_path_default->none~get_child proc~json_get_by_path_default->none~throw_exception proc~json_get_by_path_default->proc~json_clear_exceptions proc~json_get_by_path_default->proc~string_to_integer none~add~2 json_value_module::json_core%add proc~json_get_by_path_default->none~add~2 proc~json_value_create json_value_module::json_value_create proc~json_get_by_path_default->proc~json_value_create proc~to_array json_value_module::json_core%to_array proc~json_get_by_path_default->proc~to_array proc~to_null json_value_module::json_core%to_null proc~json_get_by_path_default->proc~to_null proc~to_object json_value_module::json_core%to_object proc~json_get_by_path_default->proc~to_object proc~json_get_by_path_jsonpath_bracket->none~get_child proc~json_get_by_path_jsonpath_bracket->none~throw_exception proc~json_get_by_path_jsonpath_bracket->proc~json_clear_exceptions proc~json_get_by_path_jsonpath_bracket->proc~string_to_integer proc~json_get_by_path_jsonpath_bracket->none~add~2 proc~convert json_value_module::json_core%convert proc~json_get_by_path_jsonpath_bracket->proc~convert proc~json_get_by_path_jsonpath_bracket->proc~json_value_create proc~json_get_by_path_jsonpath_bracket->proc~to_null proc~json_get_by_path_rfc6901->none~get_child proc~json_get_by_path_rfc6901->none~throw_exception proc~json_get_by_path_rfc6901->proc~json_clear_exceptions proc~json_get_by_path_rfc6901->proc~string_to_integer proc~decode_rfc6901 json_string_utilities::decode_rfc6901 proc~json_get_by_path_rfc6901->proc~decode_rfc6901 proc~compact_real_string json_string_utilities::compact_real_string proc~real_to_string->proc~compact_real_string proc~json_value_add_string_name_ascii json_value_module::json_core%json_value_add_string_name_ascii none~add~2->proc~json_value_add_string_name_ascii proc~json_value_add_string_val_ascii json_value_module::json_core%json_value_add_string_val_ascii none~add~2->proc~json_value_add_string_val_ascii proc~json_value_add_string_vec_name_ascii json_value_module::json_core%json_value_add_string_vec_name_ascii none~add~2->proc~json_value_add_string_vec_name_ascii proc~json_value_add_string_vec_val_ascii json_value_module::json_core%json_value_add_string_vec_val_ascii none~add~2->proc~json_value_add_string_vec_val_ascii proc~convert->none~throw_exception proc~convert->none~info none~create_array json_value_module::json_core%create_array proc~convert->none~create_array none~create_null json_value_module::json_core%create_null proc~convert->none~create_null none~create_object json_value_module::json_core%create_object proc~convert->none~create_object proc~json_value_replace json_value_module::json_core%json_value_replace proc~convert->proc~json_value_replace proc~decode_rfc6901->proc~replace_string proc~json_string_info->none~throw_exception proc~json_string_info->none~get proc~json_string_info->none~info proc~json_string_info->proc~json_clear_exceptions proc~destroy_json_data json_value_module::destroy_json_data proc~to_array->proc~destroy_json_data proc~to_null->proc~destroy_json_data proc~to_object->proc~destroy_json_data proc~json_value_create_array json_value_module::json_core%json_value_create_array none~create_array->proc~json_value_create_array proc~wrap_json_value_create_array json_value_module::json_core%wrap_json_value_create_array none~create_array->proc~wrap_json_value_create_array proc~json_value_create_null json_value_module::json_core%json_value_create_null none~create_null->proc~json_value_create_null proc~wrap_json_value_create_null json_value_module::json_core%wrap_json_value_create_null none~create_null->proc~wrap_json_value_create_null proc~json_value_create_object json_value_module::json_core%json_value_create_object none~create_object->proc~json_value_create_object proc~wrap_json_value_create_object json_value_module::json_core%wrap_json_value_create_object none~create_object->proc~wrap_json_value_create_object proc~json_value_add_string_name_ascii->interface~to_unicode proc~json_value_add_string_name_ascii->none~add~2 proc~json_value_add_string_val_ascii->interface~to_unicode proc~json_value_add_string_val_ascii->none~add~2 proc~json_value_add_string_vec_name_ascii->interface~to_unicode proc~json_value_add_string_vec_name_ascii->none~add~2 proc~json_value_add_string_vec_val_ascii->interface~to_unicode proc~json_value_add_string_vec_val_ascii->none~add~2 none~insert_after json_value_module::json_core%insert_after proc~json_value_replace->none~insert_after proc~json_value_remove json_value_module::json_core%json_value_remove proc~json_value_replace->proc~json_value_remove proc~json_value_insert_after json_value_module::json_core%json_value_insert_after none~insert_after->proc~json_value_insert_after proc~json_value_insert_after_child_by_index json_value_module::json_core%json_value_insert_after_child_by_index none~insert_after->proc~json_value_insert_after_child_by_index proc~json_value_create_array->proc~json_value_create proc~json_value_create_array->proc~to_array proc~json_value_create_null->proc~json_value_create proc~json_value_create_null->proc~to_null proc~json_value_create_object->proc~json_value_create proc~json_value_create_object->proc~to_object none~destroy json_value_module::json_core%destroy proc~json_value_remove->none~destroy proc~wrap_json_value_create_array->interface~to_unicode proc~wrap_json_value_create_array->none~create_array proc~wrap_json_value_create_null->interface~to_unicode proc~wrap_json_value_create_null->none~create_null proc~wrap_json_value_create_object->interface~to_unicode proc~wrap_json_value_create_object->none~create_object proc~destroy_json_core json_value_module::json_core%destroy_json_core none~destroy->proc~destroy_json_core proc~json_value_destroy json_value_module::json_core%json_value_destroy none~destroy->proc~json_value_destroy proc~json_value_insert_after_child_by_index->none~get_child proc~json_value_insert_after_child_by_index->none~insert_after proc~json_value_destroy->proc~destroy_json_data proc~json_value_destroy->none~destroy

Source Code

    subroutine json_check_children_for_duplicate_keys(json,p,has_duplicate,name,path)

    implicit none

    class(json_core),intent(inout) :: json
    type(json_value),pointer,intent(in) :: p  !! the object to search. If `p` is
                                              !! not a `json_object`, then `has_duplicate`
                                              !! will be false.
    logical(LK),intent(out) :: has_duplicate  !! true if there is at least
                                              !! two children have duplicate
                                              !! `name` values.
    character(kind=CK,len=:),allocatable,intent(out),optional :: name !! the duplicate name
                                                                      !! (unallocated if no
                                                                      !! duplicate was found)
    character(kind=CK,len=:),allocatable,intent(out),optional :: path !! the full path to the
                                                                      !! duplicate name
                                                                      !! (unallocated if no
                                                                      !! duplicate was found)

    integer(IK)              :: i           !! counter
    integer(IK)              :: j           !! counter
    type(json_value),pointer :: child       !! pointer to a child of `p`
    integer(IK)              :: n_children  !! number of children of `p`
    logical(LK)              :: found       !! flag for `get_child`

    type :: alloc_str
        !! so we can have an array of allocatable strings
        character(kind=CK,len=:),allocatable :: str  !! name string
    end type alloc_str
    type(alloc_str),dimension(:),allocatable :: names !! array of all the
                                                      !! child name strings

    ! initialize:
    has_duplicate =.false.

    if (.not. json%exception_thrown) then

        if (associated(p)) then

            if (p%var_type==json_object) then

                ! number of items to check:
                n_children = json%count(p)
                allocate(names(n_children))

                ! first get a list of all the name keys:
                do i=1, n_children
                    call json%get_child(p,i,child,found) ! get by index
                    if (.not. found) then
                        call json%throw_exception(&
                            'Error in json_check_children_for_duplicate_keys: '//&
                            'Malformed JSON linked list')
                        exit
                    end if
                    if (allocated(child%name)) then
                        names(i)%str = child%name
                    else
                        call json%throw_exception(&
                            'Error in json_check_children_for_duplicate_keys: '//&
                            'Object child name is not allocated')
                        exit
                    end if
                end do

                if (.not. json%exception_thrown) then
                    ! now check the list for duplicates:
                    main: do i=1,n_children
                        do j=1,i-1
                            if (json%name_strings_equal(names(i)%str,names(j)%str)) then
                                has_duplicate = .true.
                                if (present(name)) then
                                    name = names(i)%str
                                end if
                                if (present(path)) then
                                    call json%get_child(p,names(i)%str,child,found) ! get by name
                                    if (found) then
                                        call json%get_path(child,path,found)
                                        if (.not. found) then
                                            ! should never happen since we know it is there
                                            call json%throw_exception(&
                                                    'Error in json_check_children_for_duplicate_keys: '//&
                                                    'Could not get path')
                                        end if
                                    else
                                        ! should never happen since we know it is there
                                        call json%throw_exception(&
                                            'Error in json_check_children_for_duplicate_keys: '//&
                                            'Could not get child: '//trim(names(i)%str))
                                    end if
                                end if
                                exit main
                            end if
                        end do
                    end do main
                end if

                ! cleanup
                do i=1,n_children
                    if (allocated(names(i)%str)) deallocate(names(i)%str)
                end do
                if (allocated(names)) deallocate(names)

            end if

        end if

    end if

    end subroutine json_check_children_for_duplicate_keys