set_body Function

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

The function sets the request body.


This function determines and set the type of data to include in the request body based on the inputs provided to the request() procedure.

The function handles different combinations of data, file, and form members to decide the content and the default header for the request body.

  • If data member is provided, it takes the highest priority and is sent as the body of the request. Any other provided file or form members will be ignored, and only the data member will be included in the request body.

  • If only the file member is provided, the file is sent as the body of the request. If no Content-type header is provided, a default Content-type header with value multipart/form-data will be set.

  • If only the form member is provided, the form data is URL encoded and sent as the body of the request. If no Content-type header is provided, a default Content-type header with value application/x-www-form-urlencoded will be set.

  • If both form and file members are provided, both form and file data are included as part of the request body. A default Content-type header with value multipart/form-data will be set if no Content-type header is provided.

  • If data, form, and file are all provided, only data is sent, and the form and file inputs are ignored.

Combination Behavior Table

Passed Arguments Request Body Default Header Behavior
data data None The data is sent as the body of the request.
file file multipart/form-data The file is sent as the body of the request with the default header.
form Form data URL encoded application/x-www-form-urlencoded The form data is sent as the body of the request with the default header.
data + file data (file ignored) None The file member is ignored, and the data is sent as the body of the request.
data + form data (form ignored) None The form member is ignored, and the data is sent as the body of the request.
file + form both file and form multipart/form-data Both form and file are sent as part of the request.
data + file + form data (form and file ignored) None Both form and file members are ignored, and only the data is sent as the body of the request.

Note: If custom headers are provided in the headers parameter, they will be used. Otherwise, default headers will be applied as mentioned in the table.

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.


Contents

Source Code


Source Code

    function set_body(curl_ptr, request) result(status)
        !!> The function sets the request `body`.
        !!____

        !!> This function determines and set the type of data to include in the `request body` 
        !!> based on the inputs provided to the `request()` procedure.

        !!> The function handles different combinations of `data`, `file`, and `form` members 
        !!> to decide the content and the default header for the request body.

        !!> - If `data` member is provided, it takes the highest priority and is sent as the 
        !!> body of the request. Any other provided `file` or `form` members will be ignored, 
        !!> and only the `data` member will be included in the request body.

        !!> - If only the `file` member is provided, the `file` is sent as the body of the request. 
        !!> If no `Content-type` header is provided, a default `Content-type` header with value 
        !!> `multipart/form-data` will be set.

        !!> - If only the `form` member is provided, the `form` data is URL encoded and sent as 
        !!> the body of the request. If no `Content-type` header is provided, a default `Content-type` 
        !!> header with value `application/x-www-form-urlencoded` will be set.

        !!> - If both `form` and `file` members are provided, both `form` and `file` data are included 
        !!> as part of the request body. A default `Content-type` header with value `multipart/form-data` 
        !!> will be set if no `Content-type` header is provided.

        !!> - If `data`, `form`, and `file` are all provided, only `data` is sent, and the `form` and `file`
        !!> inputs are ignored.

        !!> ### **Combination Behavior Table**


        !!> | Passed Arguments   | Request Body                    | Default Header                | Behavior                                                |
        !! |--------------------|---------------------------------|-------------------------------|---------------------------------------------------------|
        !! | data               | data                            | None                          | The `data` is sent as the body of the request.         |
        !! | file               | file                            | multipart/form-data           | The `file` is sent as the body of the request with the default header.  |
        !! | form               | Form data URL encoded           | application/x-www-form-urlencoded | The `form` data is sent as the body of the request with the default header. |
        !! | data + file        | data (file ignored)             | None                          | The `file` member is ignored, and the `data` is sent as the body of the request. |
        !! | data + form        | data (form ignored)             | None                          | The `form` member is ignored, and the `data` is sent as the body of the request. |
        !! | file + form        | both file and form              | multipart/form-data           | Both `form` and `file` are sent as part of the request. |
        !! | data + file + form | data (form and file ignored)    | None                          | Both `form` and `file` members are ignored, and only the `data` is sent as the body of the request. |
        
        !!> Note: If custom headers are provided in the `headers` parameter, they will be used. Otherwise, default headers will be applied as mentioned in the table.

        type(c_ptr), intent(out) :: curl_ptr
            !! Pointer to the `curl` handle.
        type(request_type), intent(inout) :: request
            !! The HTTP request
        integer :: status
            !! An integer value representing the status of the function call.
        
        integer :: i
        type(c_ptr) :: mime_ptr, part_ptr

        ! if only data is passed
        if (allocated(request%data)) then
            status = set_postfields(curl_ptr, request%data)
        
        ! if file is passsed
        else if (allocated(request%file)) then
            mime_ptr = curl_mime_init(curl_ptr)
            part_ptr = curl_mime_addpart(mime_ptr)
            status = curl_mime_filedata(part_ptr, request%file%value)
            status = curl_mime_name(part_ptr, request%file%name)
            
            ! if both file and form are passed
            if(allocated(request%form)) then 
                do i=1, size(request%form)
                    part_ptr = curl_mime_addpart(mime_ptr)
                    status = curl_mime_data(part_ptr, request%form(i)%value, CURL_ZERO_TERMINATED)
                    status = curl_mime_name(part_ptr, request%form(i)%name)
                end do
            end if
            status = curl_easy_setopt(curl_ptr, CURLOPT_MIMEPOST, mime_ptr)
            
            ! setting the Content-Type header to multipart/form-data, used for sending  binary data
            if (.not. pair_has_name(request%header, 'Content-Type')) then
                call append_pair(request%header, 'Content-Type', 'multipart/form-data')
            end if
        
        ! if only form is passed
        else if (allocated(request%form)) then
            request%form_encoded_str = prepare_form_encoded_str(curl_ptr, request)
            status = set_postfields(curl_ptr, request%form_encoded_str)
           
            ! setting the Content-Type header to application/x-www-form-urlencoded, used for sending form data
            if (.not. pair_has_name(request%header, 'Content-Type')) then
                call append_pair(request%header, 'Content-Type', 'application/x-www-form-urlencoded')
            end if
        else
            ! No curl function was called so set status to zero.
            status = 0
        end if
        
    end function set_body