prepare_form_encoded_str Function

private function prepare_form_encoded_str(curl_ptr, request) result(form_encoded_str)

This subroutine converts the request%form into a URL-encoded name-value string and returns it.

Arguments

Type IntentOptional Attributes Name
type(c_ptr), intent(out) :: curl_ptr

Pointer to the curl handler.

type(request_type), intent(inout) :: request

The HTTP request to send, which includes the form data to be encoded.

Return Value character(len=:), allocatable

Stores the URL Encoded string.


Contents


Source Code

    function prepare_form_encoded_str(curl_ptr, request) result(form_encoded_str)
        
        !!> This subroutine converts the `request%form` into a **URL-encoded name-value 
        !!> string** and returns it.

        ! This subroutine takes a request object containing a list of name-value pairs 
        ! representing the form data. It iterates over the list and URL-encodes each 
        ! name and value using the curl_easy_escape function, which replaces special 
        ! characters with their corresponding escape sequences.
        ! The encoded name-value pairs are concatenated into a single string, separated 
        ! by '&' characters. The resulting string is returned

        type(c_ptr), intent(out) :: curl_ptr
            !! Pointer to the `curl` handler.
        type(request_type), intent(inout) :: request
            !! The HTTP `request` to send, which includes the `form` data to be encoded.
        character(:), allocatable :: form_encoded_str
            !! Stores the **URL Encoded string**.
        
        integer :: i
        if(allocated(request%form)) then
            do i=1, size(request%form)
                if(.not. allocated(form_encoded_str)) then
                    form_encoded_str = curl_easy_escape(curl_ptr, request%form(i)%name, &
                    len(request%form(i)%name)) // '=' // curl_easy_escape(curl_ptr, &
                    request%form(i)%value, len(request%form(i)%value))
                else
                    form_encoded_str = form_encoded_str // '&' // &
                    curl_easy_escape(curl_ptr, request%form(i)%name, len(request%form(i)%name))&
                    // '=' // curl_easy_escape(curl_ptr, request%form(i)%value, len(request%form(i)%value))
                end if
            end do
        end if
    end function prepare_form_encoded_str