json_value_equals Function

private recursive function json_value_equals(json, p1, p2) result(equals)

Compare two JSON structures for equality.

This function recursively traverses both structures and checks that they have: * The same variable types * The same values (for primitives) * The same number of children (for objects and arrays) * The same structure (recursively)

Example

 type(json_core) :: json
 type(json_value),pointer :: p1, p2
 logical :: are_equal
 call json%load(file='file1.json', p=p1)
 call json%load(file='file2.json', p=p2)
 are_equal = json%equals(p1, p2)
 if (are_equal) then
     write(*,*) 'Files are identical'
 else
     write(*,*) 'Files differ'
 end if

Type Bound

json_core

Arguments

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

first JSON structure

type(json_value), pointer :: p2

second JSON structure

Return Value logical(kind=LK)

true if the structures are equal


Calls

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

Source Code

    recursive function json_value_equals(json, p1, p2) result(equals)

    implicit none

    class(json_core),intent(inout)   :: json
    type(json_value),pointer         :: p1     !! first JSON structure
    type(json_value),pointer         :: p2     !! second JSON structure
    logical(LK)                      :: equals !! true if the structures are equal

    integer(IK) :: n1, n2  !! number of children
    type(json_value),pointer :: child1, child2  !! for iterating children

    ! Initialize
    equals = .false.

    ! Check if both are null
    if (.not. associated(p1) .and. .not. associated(p2)) then
        equals = .true.
        return
    end if

    ! Check if only one is null
    if (.not. associated(p1) .or. .not. associated(p2)) then
        equals = .false.
        return
    end if

    ! Check if variable types match
    if (p1%var_type /= p2%var_type) then
        equals = .false.
        return
    end if

    ! Compare based on type
    select case (p1%var_type)

    case (json_null)
        ! Both are null, already validated by type check
        equals = .true.

    case (json_logical)
        ! Compare logical values
        if (allocated(p1%log_value) .and. allocated(p2%log_value)) then
            equals = (p1%log_value .eqv. p2%log_value)
        else if (.not. allocated(p1%log_value) .and. .not. allocated(p2%log_value)) then
            equals = .true.
        else
            equals = .false.
        end if

    case (json_integer)
        ! Compare integer values
        if (allocated(p1%int_value) .and. allocated(p2%int_value)) then
            equals = (p1%int_value == p2%int_value)
        else if (.not. allocated(p1%int_value) .and. .not. allocated(p2%int_value)) then
            equals = .true.
        else
            equals = .false.
        end if

    case (json_real)
        ! Compare real values with tolerance
        if (allocated(p1%dbl_value) .and. allocated(p2%dbl_value)) then
            associate (r1 => p1%dbl_value, r2 => p2%dbl_value)
                ! Handle special cases: NaN, Inf, -Inf
                if (ieee_is_nan(r1) .and. ieee_is_nan(r2)) then
                    equals = .true.
                else if (ieee_is_nan(r1) .or. ieee_is_nan(r2)) then
                    equals = .false.
                else if (.not. ieee_is_finite(r1) .and. .not. ieee_is_finite(r2)) then
                    ! Both infinite - check if same sign
                    equals = (r1 == r2)
                else if (ieee_is_finite(r1) .and. ieee_is_finite(r2)) then
                    ! Both finite:
                    equals = r1 == r2
                else
                    equals = .false.
                end if
            end associate
        else if (.not. allocated(p1%dbl_value) .and. .not. allocated(p2%dbl_value)) then
            equals = .true.
        else
            equals = .false.
        end if

    case (json_string)
        ! Compare string values
        if (allocated(p1%str_value) .and. allocated(p2%str_value)) then
            equals = (p1%str_value == p2%str_value)
        else if (.not. allocated(p1%str_value) .and. .not. allocated(p2%str_value)) then
            equals = .true.
        else
            equals = .false.
        end if

    case (json_array)
        ! Compare arrays: must have same number of elements in same order
        n1 = json%count(p1)
        n2 = json%count(p2)

        if (n1 /= n2) then
            equals = .false.
            return
        end if

        ! Compare each element
        child1 => p1%children
        child2 => p2%children

        do while (associated(child1) .and. associated(child2))
            ! Recursively compare children
            if (.not. json%equals(child1, child2)) then
                equals = .false.
                return
            end if
            child1 => child1%next
            child2 => child2%next
        end do

        ! If we got here, all elements matched
        equals = .true.

    case (json_object)
        ! Compare objects: must have same keys with same values
        n1 = json%count(p1)
        n2 = json%count(p2)

        if (n1 /= n2) then
            equals = .false.
            return
        end if

        ! For each child in p1, find matching child in p2 by name
        child1 => p1%children

        do while (associated(child1))
            ! Look for child with same name in p2
            nullify(child2)
            if (allocated(child1%name)) then
                call json%get_child(p2, child1%name, child2)

                if (.not. associated(child2)) then
                    ! Key not found in p2
                    equals = .false.
                    return
                end if

                ! Recursively compare values
                if (.not. json%equals(child1, child2)) then
                    equals = .false.
                    return
                end if
            end if

            child1 => child1%next
        end do

        ! If we got here, all keys and values matched
        equals = .true.

    case default
        ! Unknown type
        equals = .false.
    end select

    end function json_value_equals