new_request Function

private function new_request(url, method, header, data, form, file, timeout, auth) result(response)

This function create a request_type object and populates it. The function returns the response_type object containing the server's response.


Note :

If the header argument is not provided, default user-agent header is set to http-client/0.1.

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: url

Specifies the URL of the server.

integer, intent(in), optional :: method

Specifies the HTTP method to use for the request. The default value is 1, which corresponds to the HTTP_GET method.

type(pair_type), intent(in), optional :: header(:)

Specifies the request headers that need to be sent to the server.

character(len=*), intent(in), optional :: data

Specifies the data that needs to be sent to the server.

type(pair_type), intent(in), optional :: form(:)

Specifies the form data that needs to be sent to the server.

type(pair_type), intent(in), optional :: file

Specifies the file that needs to be sent to the server.

integer, intent(in), optional :: timeout

Timeout value for the request in seconds.

type(pair_type), intent(in), optional :: auth

stores the username and password for authentication purposes.

Return Value type(response_type)

Stores the server's response.


Contents

Source Code


Source Code

    function new_request(url, method, header, data, form, file, timeout, auth) result(response)
    
        !!> This function create a `request_type` object and populates it.
        !!> The function returns the `response_type` object containing the
        !!> **server's response**.
        !!____
        !!> #### Note :
        !!> If the `header` argument is not provided, **default `user-agent`
        !!> header is set to `http-client/0.1`**.
    
        integer, intent(in), optional :: method
            !! Specifies the HTTP `method` to use for the request. 
            !! The **default value is 1**, which corresponds to the **`HTTP_GET`** method.
        character(len=*), intent(in) :: url
            !! Specifies the **`URL`** of the server.
        character(len=*), intent(in), optional :: data
            !! Specifies the **`data`** that needs to be sent to the server.
        type(pair_type), intent(in), optional :: header(:)
            !! Specifies the **request `headers`** that need to be sent to the server.
        type(pair_type), intent(in), optional :: form(:)
            !! Specifies the **`form data`** that needs to be sent to the server.
        type(pair_type), intent(in), optional :: file
            !! Specifies the **`file`** that needs to be sent to the server.
        integer, intent(in), optional :: timeout
            !! **`Timeout`** value for the request in **seconds**.
        type(pair_type), intent(in), optional :: auth
            !! stores the `username` and `password` for **`authentication`** purposes.
        type(response_type) :: response
            !! Stores the server's **`response`**.

        type(request_type) :: request
        type(client_type) :: client
        integer :: i

        ! setting request url
        request%url = url

        ! Set default HTTP method.
        request%method = optval(method, 1)
        
        ! Set request header
        if (present(header)) then
            request%header = header
            ! Set default request headers.
            if (.not. pair_has_name(header, 'user-agent')) then
              call append_pair(request%header, 'user-agent', 'http-client/'//VERSION_STRING)
            end if
        else
            ! Set default request headers.
            request%header = [pair_type('user-agent', 'http-client/'//VERSION_STRING)]
        end if

        ! setting the request data to be send
        if(present(data)) then
            request%data = data
        end if
        
        ! setting request form
        if(present(form)) then
            request%form = form
        end if

        ! setting request file
        if(present(file)) then
            request%file = file
        end if

        ! Set request timeout.
        request%timeout = optval(timeout, -1)
                
        ! setting username and password for Authentication
        if(present(auth)) then
            request%auth = auth
        end if

        ! Populates the response 
        client = client_type(request=request)
        response = client%client_get_response()
    end function new_request