json_value_print Subroutine

private recursive subroutine json_value_print(json, p, iunit, str, indent, need_comma, colon, is_array_element, is_compressed_vector)

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.

Arguments

Type IntentOptional AttributesName
class(json_core), intent(inout) :: json
type(json_value), intent(in), pointer:: p
integer(kind=IK), intent(in) :: iunit

file unit to write to (6=console)

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.

integer(kind=IK), intent(in), optional :: indent

indention level

logical(kind=LK), intent(in), optional :: need_comma

if it needs a comma after it

logical(kind=LK), intent(in), optional :: colon

if the colon was just written

logical(kind=LK), intent(in), optional :: is_array_element

if this is an array element

logical(kind=LK), intent(in), optional :: is_compressed_vector

if True, this is an element from an array being printed on one line [default is False]

Calls

proc~~json_value_print~~CallsGraph proc~json_value_print json_value_print proc~integer_to_string integer_to_string proc~json_value_print->proc~integer_to_string proc~real_to_string real_to_string proc~json_value_print->proc~real_to_string proc~compact_real_string compact_real_string proc~real_to_string->proc~compact_real_string
Help

Source Code


Source Code

    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


annotate_invalid_json compact_real_string decode_rfc6901 default_comp_ucs4 default_join_ucs4 default_neq_ucs4 destroy_json_core destroy_json_data encode_rfc6901 escape_string get_current_line_from_file_sequential get_current_line_from_file_stream get_json_core_in_file initialize_json_core initialize_json_core_in_file initialize_json_file initialize_json_file_v2 integer_to_string json_add_double_by_path json_add_double_vec_by_path json_add_integer_by_path json_add_integer_vec_by_path json_add_logical_by_path json_add_logical_vec_by_path json_add_member_by_path json_add_string_by_path json_add_string_by_path_path_ascii json_add_string_by_path_value_ascii json_add_string_vec_by_path json_add_string_vec_by_path_path_ascii json_add_string_vec_by_path_value_ascii json_check_for_errors json_clear_exceptions json_clone json_core json_count json_create_by_path json_failed json_file json_file_add_double json_file_add_double_vec json_file_add_integer json_file_add_integer_vec json_file_add_logical json_file_add_logical_vec json_file_add_object json_file_add_string json_file_add_string_path_ascii json_file_add_string_value_ascii json_file_add_string_vec json_file_add_string_vec_path_ascii json_file_add_string_vec_vec_ascii json_file_check_for_errors json_file_clear_exceptions json_file_destroy json_file_failed json_file_get_alloc_string_vec json_file_get_double json_file_get_double_vec json_file_get_integer json_file_get_integer_vec json_file_get_logical json_file_get_logical_vec json_file_get_object json_file_get_root json_file_get_string json_file_get_string_vec json_file_load json_file_load_from_string json_file_move_pointer json_file_print_1 json_file_print_2 json_file_print_error_message json_file_print_to_console json_file_print_to_string json_file_traverse json_file_update_integer json_file_update_logical json_file_update_real json_file_update_string json_file_update_string_name_ascii json_file_update_string_val_ascii json_file_variable_info json_file_variable_matrix_info json_get_alloc_string_vec json_get_alloc_string_vec_by_path json_get_array json_get_array_by_path json_get_by_path json_get_by_path_default json_get_by_path_rfc6901 json_get_double json_get_double_by_path json_get_double_vec json_get_double_vec_by_path json_get_integer json_get_integer_by_path json_get_integer_vec json_get_integer_vec_by_path json_get_logical json_get_logical_by_path json_get_logical_vec json_get_logical_vec_by_path json_get_next json_get_parent json_get_path json_get_previous json_get_string json_get_string_by_path json_get_string_vec json_get_string_vec_by_path json_get_tail json_info json_info_by_path json_initialize json_matrix_info json_matrix_info_by_path json_parse_file json_parse_string json_print_1 json_print_2 json_print_error_message json_string_info json_throw_exception json_traverse json_update_double json_update_integer json_update_logical json_update_string json_update_string_name_ascii json_update_string_val_ascii json_value_add_double json_value_add_double_vec json_value_add_integer json_value_add_integer_vec json_value_add_logical json_value_add_logical_vec json_value_add_member json_value_add_null json_value_add_string json_value_add_string_name_ascii json_value_add_string_val_ascii json_value_add_string_vec json_value_add_string_vec_name_ascii json_value_add_string_vec_val_ascii json_value_clone_func json_value_create json_value_create_array json_value_create_double json_value_create_integer json_value_create_logical json_value_create_null json_value_create_object json_value_create_string json_value_destroy json_value_get_child json_value_get_child_by_index json_value_get_child_by_name json_value_insert_after json_value_insert_after_child_by_index json_value_is_child_of json_value_print json_value_remove json_value_remove_if_present json_value_rename json_value_replace json_value_swap json_value_to_string json_value_validate lowercase_character lowercase_string name_equal parse_array parse_for_chars parse_number parse_object parse_string parse_value pop_char push_char real_to_string replace_string set_json_core_in_file string_to_dble string_to_int string_to_integer string_to_real to_array to_double to_integer to_logical to_null to_object to_string to_uni to_uni_vec to_unicode ucs4_comp_default ucs4_join_default ucs4_neq_default unescape_string valid_json_hex wrap_json_add_double_by_path wrap_json_add_double_vec_by_path wrap_json_add_integer_by_path wrap_json_add_integer_vec_by_path wrap_json_add_logical_by_path wrap_json_add_logical_vec_by_path wrap_json_add_member_by_path wrap_json_add_string_by_path wrap_json_add_string_vec_by_path wrap_json_create_by_path wrap_json_file_add_double wrap_json_file_add_double_vec wrap_json_file_add_integer wrap_json_file_add_integer_vec wrap_json_file_add_logical wrap_json_file_add_logical_vec wrap_json_file_add_object wrap_json_file_add_string wrap_json_file_add_string_vec wrap_json_file_get_alloc_string_vec wrap_json_file_get_double wrap_json_file_get_double_vec wrap_json_file_get_integer wrap_json_file_get_integer_vec wrap_json_file_get_logical wrap_json_file_get_logical_vec wrap_json_file_get_object wrap_json_file_get_string wrap_json_file_get_string_vec wrap_json_file_load_from_string wrap_json_file_update_integer wrap_json_file_update_logical wrap_json_file_update_real wrap_json_file_update_string wrap_json_file_variable_info wrap_json_file_variable_matrix_info wrap_json_get_alloc_string_vec_by_path wrap_json_get_array_by_path wrap_json_get_by_path wrap_json_get_double_by_path wrap_json_get_double_vec_by_path wrap_json_get_integer_by_path wrap_json_get_integer_vec_by_path wrap_json_get_logical_by_path wrap_json_get_logical_vec_by_path wrap_json_get_path wrap_json_get_string_by_path wrap_json_get_string_vec_by_path wrap_json_info_by_path wrap_json_matrix_info_by_path wrap_json_parse_string wrap_json_throw_exception wrap_json_update_double wrap_json_update_integer wrap_json_update_logical wrap_json_update_string wrap_json_value_add_double wrap_json_value_add_double_vec wrap_json_value_add_integer wrap_json_value_add_integer_vec wrap_json_value_add_logical wrap_json_value_add_logical_vec wrap_json_value_add_null wrap_json_value_add_string wrap_json_value_add_string_vec wrap_json_value_create_array wrap_json_value_create_double wrap_json_value_create_integer wrap_json_value_create_logical wrap_json_value_create_null wrap_json_value_create_object wrap_json_value_create_string wrap_json_value_get_child_by_name wrap_json_value_remove_if_present wrap_json_value_rename