This function sends an HTTP
request
to a server using the fortran-curl package and stores the server's response in aresponse_type
object.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
class(client_type), | intent(inout) | :: | this |
Contains the HTTP |
Contains the server's response.
function client_get_response(this) result(response)
!!> This function sends an HTTP `request` to a server using the
!!> [fortran-curl](https://github.com/interkosmos/fortran-curl) package
!!> and stores the server's response in a `response_type`
!!> object.
class(client_type), intent(inout) :: this
!! Contains the HTTP `request` to send.
type(response_type), target :: response
!! Contains the **server's response**.
type(c_ptr) :: curl_ptr, header_list_ptr
integer :: rc, i
curl_ptr = c_null_ptr
header_list_ptr = c_null_ptr
response%url = this%request%url
curl_ptr = curl_easy_init()
if (.not. c_associated(curl_ptr)) then
response%ok = .false.
response%err_msg = "The initialization of a new easy handle using the 'curl_easy_init()'&
& function failed. This can occur due to insufficient memory available in the system. &
& Additionally, if libcurl is not installed or configured properly on the system"
return
end if
! setting request URL
rc = curl_easy_setopt(curl_ptr, CURLOPT_URL, this%request%url)
! setting request method
rc = set_method(curl_ptr, this%request%method, response)
! setting request timeout
rc = set_timeout(curl_ptr, this%request%timeout)
! setting request body
rc = set_body(curl_ptr, this%request)
! setting request authentication
rc = set_auth(curl_ptr, this%request)
! prepare headers for curl
call prepare_request_header_ptr(header_list_ptr, this%request%header)
! setting request header
rc = curl_easy_setopt(curl_ptr, CURLOPT_HTTPHEADER, header_list_ptr);
! setting callback for writing received data
rc = curl_easy_setopt(curl_ptr, CURLOPT_WRITEFUNCTION, c_funloc(client_response_callback))
! setting response content pointer to write callback
rc = curl_easy_setopt(curl_ptr, CURLOPT_WRITEDATA, c_loc(response))
! setting callback for writing received headers
rc = curl_easy_setopt(curl_ptr, CURLOPT_HEADERFUNCTION, c_funloc(client_header_callback))
! setting response header pointer to write callback
rc = curl_easy_setopt(curl_ptr, CURLOPT_HEADERDATA, c_loc(response))
! Send request.
rc = curl_easy_perform(curl_ptr)
if (rc /= CURLE_OK) then
response%ok = .false.
response%err_msg = curl_easy_strerror(rc)
end if
! setting response status_code
rc = curl_easy_getinfo(curl_ptr, CURLINFO_RESPONSE_CODE, response%status_code)
call curl_easy_cleanup(curl_ptr)
end function client_get_response