client_header_callback Function

private function client_header_callback(ptr, size, nmemb, client_data) bind(c)

This function is a callback function used by the fortran-curl package to handle HTTP headers.


It is called for each header received from the server and stores the header in an header member of response_type object.

Arguments

Type IntentOptional Attributes Name
type(c_ptr), intent(in), value :: ptr

Pointer to the CURL handle. that points to the received header buffer.

integer(kind=c_size_t), intent(in), value :: size

Specifies the size of each header element.

integer(kind=c_size_t), intent(in), value :: nmemb

Specifies the number of header elements received.

type(c_ptr), intent(in), value :: client_data

Pointer to a response_type object.

Return Value integer(kind=c_size_t)

The number of bytes received.


Contents


Source Code

    function client_header_callback(ptr, size, nmemb, client_data) bind(c)
        !!> This function is a `callback` function used by the `fortran-curl` package to handle HTTP headers. 
        !!>_____
        !!> It is called for each header received from the server and stores the header in an `header` member 
        !!> of `response_type` object.
        type(c_ptr), intent(in), value :: ptr 
            !! Pointer to the CURL handle. that points to the received header buffer.
        integer(kind=c_size_t), intent(in), value :: size 
            !!  Specifies the size of each header element.
        integer(kind=c_size_t), intent(in), value :: nmemb
            !! Specifies the number of header elements received.
        type(c_ptr), intent(in), value :: client_data
            !! Pointer to a `response_type` object.
        integer(kind=c_size_t) :: client_header_callback 
            !! The number of bytes received.
        type(response_type), pointer :: response 
        character(len=:), allocatable :: buf, h_name, h_value
        integer :: i
      
        client_header_callback = int(0, kind=c_size_t)
      
        ! Are the passed C pointers associated?
        if (.not. c_associated(ptr)) return
        if (.not. c_associated(client_data)) return
      
        ! Convert C pointer to Fortran pointer.
        call c_f_pointer(client_data, response)
      
        ! Convert C pointer to Fortran allocatable character.
        call c_f_str_ptr(ptr, buf, nmemb)
        if (.not. allocated(buf)) return
        
        ! Parsing Header, and storing in array of pair_type object
        i = index(buf, ':')
        if(i /= 0 .and. len(buf) > 2) then
            h_name = trim(buf(:i-1))
            h_value = buf(i+2 : )
            h_value = h_value( : len(h_value)-2)
            if(len(h_value) > 0 .and. len(h_name) > 0) then
                call append_pair(response%header, h_name, h_value)
                ! response%header = [response%header, pair_type(h_name, h_value)]
            end if
        end if
        deallocate(buf)
        
        ! Return number of received bytes.
        client_header_callback = nmemb

    end function client_header_callback