http_client Module

This module defines the client_type derived type, which handles the process of making HTTP requests. The actual HTTP requests are executed using the Fortran-curl package as the underlying mechanism.



Contents


Interfaces

private interface client_type

Interface for new_client function.

  • private function new_client(request) result(client)

    This is the constructor for the client_type derived type.

    Arguments

    Type IntentOptional Attributes Name
    type(request_type), intent(in) :: request

    Specifies the HTTP request to send.

    Return Value type(client_type)

    A client_type object containing the request field set to the input request object.

public interface request

Interface for 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.


Derived Types

type, private ::  client_type

A derived type, responsible for making actual HTTP request using fortran-curl at backend.

Read more…

Components

Type Visibility Attributes Name Initial
type(request_type), public :: request

Constructor

Interface for new_client function.

Read more…
private function new_client (request)

This is the constructor for the client_type derived type.

Read more…

Type-Bound Procedures

procedure , public , :: client_get_response Function

Functions

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.

Read more…

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.

private function new_client(request) result(client)

This is the constructor for the client_type derived type.

Read more…

Arguments

Type IntentOptional Attributes Name
type(request_type), intent(in) :: request

Specifies the HTTP request to send.

Return Value type(client_type)

A client_type object containing the request field set to the input request object.

private function client_get_response(this) result(response)

This function sends an HTTP request to a server using the fortran-curl package and stores the server's response in a response_type object.

Read more…

Arguments

Type IntentOptional Attributes Name
class(client_type), intent(inout) :: this

Contains the HTTP request to send.

Return Value type(response_type), target

Contains the server's response.

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.

Read more…

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.

private function set_method(curl_ptr, method, response) result(status)

This function sets the HTTP method for the request.

Read more…

Arguments

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

Pointer to the curl handler.

integer, intent(in) :: method

Specifies the HTTP method to use.

type(response_type), intent(out) :: response

The HTTP response from the server.

Return Value integer

The status of setting HTTP method.

private function set_timeout(curl_ptr, timeout) result(status)

This function sets the timeout value (in seconds).

Read more…

Arguments

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

Pointer to the curl handle.

integer(kind=int64), intent(in) :: timeout

Timeout seconds for request.

Return Value integer

Status code indicating whether the operation was successful.

private function set_body(curl_ptr, request) result(status)

The function sets the request body.

Read more…

Arguments

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

Pointer to the curl handle.

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

The HTTP request

Return Value integer

An integer value representing the status of the function call.

private function set_postfields(curl_ptr, data) result(status)

Set the data to be sent in the HTTP POST request body.

Read more…

Arguments

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

Pointer to the CURL handle.

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

The data to be sent in the request body.

Return Value integer

An integer indicating whether the operation was successful (0) or not (non-zero).

private function set_auth(curl_ptr, request) result(status)

Set the user name and password for Authentication.

Read more…

Arguments

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

Pointer to the CURL handle.

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

The HTTP request

Return Value integer

An integer indicating whether the operation was successful (0) or not (non-zero).

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

This function is a callback function used by the fortran-curl package to handle HTTP responses. It is called for each chunk of data received from the server and appends the data to a response_type object.

Read more…

Arguments

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

Pointer to the CURL handle.

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

Specifies the size of each data element.

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

Specifies the number of data elements received.

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

Points to a response_type object.

Return Value integer(kind=c_size_t)

The number of bytes received.

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.

Read more…

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.


Subroutines

private subroutine prepare_request_header_ptr(header_list_ptr, req_headers)

This subroutine prepares headers in required format(Linked list) for an HTTP request.

Read more…

Arguments

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

A Pointer that is allocated and points to a linked list of headers.

type(pair_type), intent(in), allocatable :: req_headers(:)

The headers to be included in the request.