Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
4 changes: 2 additions & 2 deletions example/simple_get.f90 → example/get.f90
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
program simple_get
program get_request
! This program demonstrates sending a simple GET request and printing the
! status, length of the body, method, and the body of the response.
use http, only: response_type, request
Expand All @@ -15,4 +15,4 @@ program simple_get
print *, 'Response Content : ', response%content
end if

end program simple_get
end program get_request
23 changes: 23 additions & 0 deletions example/post.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,23 @@
program post_request
! This program demonstrates sending JSON data using POST request and printing the
! status, length of the body, method, and the body of the response.
use http, only: response_type, request, HTTP_POST
implicit none
type(response_type) :: response
character(:), allocatable :: json_data

! JSON data we want to send
json_data = '{"name":"Jhon","role":"developer"}'

response = request(url='https://httpbin.org/post', method=HTTP_POST, json=json_data)

if(.not. response%ok) then
print *,'Error message : ', response%err_msg
else
print *, 'Response Code : ', response%status_code
print *, 'Response Length : ', response%content_length
print *, 'Response Method : ', response%method
print *, 'Response Content : ', response%content
end if

end program post_request
4 changes: 3 additions & 1 deletion example/response_header.f90
Original file line number Diff line number Diff line change
Expand Up @@ -17,11 +17,13 @@ program response_header
header_type('User-Agent', 'my user agent') &
]

response = request(url='https://reqres.in/api/users/1', header=req_header)
response = request(url='https://httpbin.org/get', header=req_header)

if (.not. response%ok) then
print *,'Error message : ', response%err_msg
else
print*, '::::::::::::::::: Request send by us :::::::::::::::::'
print *, response%content
print*, '::::::::::::::::: Fetching all response header :::::::::::::::::'
header = response%header
! Iterate over response headers.
Expand Down
39 changes: 30 additions & 9 deletions src/http/http_client.f90
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,8 @@ module http_client
curl_easy_strerror, curl_slist_append, CURLE_OK, &
CURLINFO_RESPONSE_CODE, CURLOPT_CUSTOMREQUEST, CURLOPT_HEADERDATA, &
CURLOPT_HEADERFUNCTION, CURLOPT_HTTPHEADER, CURLOPT_URL, &
CURLOPT_WRITEDATA, CURLOPT_WRITEFUNCTION
CURLOPT_WRITEDATA, CURLOPT_WRITEFUNCTION, &
CURLOPT_POSTFIELDS, CURLOPT_POSTFIELDSIZE_LARGE
use stdlib_optval, only: optval
use http_request, only: request_type
use http_response, only: response_type
Expand Down Expand Up @@ -34,14 +35,18 @@ module http_client

contains
! Constructor for request_type type.
function new_request(url, method, header) result(response)
character(len=*), intent(in) :: url
function new_request(url, method, header, json) result(response)
integer, intent(in), optional :: method
character(len=*), intent(in) :: url
character(len=*), intent(in), optional :: json
type(header_type), intent(in), optional :: header(:)
type(request_type) :: request
type(response_type) :: response
type(client_type) :: client

! setting request url
request%url = url

! Set default HTTP method.
request%method = optval(method, 1)

Expand All @@ -50,9 +55,11 @@ function new_request(url, method, header) result(response)
if(present(header)) then
request%header = [header, request%header]
end if

! setting request url
request%url = url

if(present(json)) then
request%json = json
request%header = [request%header, header_type('Content-Type', 'application/json')]
end if

client = client_type(request=request)

Expand Down Expand Up @@ -96,7 +103,10 @@ & function failed. This can occur due to insufficient memory available in the sy
rc = curl_easy_setopt(curl_ptr, CURLOPT_URL, this%request%url // c_null_char)

! setting request method
rc = client_set_method(curl_ptr, this%request%method, response)
rc = set_method(curl_ptr, this%request%method, response)

! setting request body
rc = set_body(curl_ptr, this%request%json)

! setting request header
rc = curl_easy_setopt(curl_ptr, CURLOPT_HTTPHEADER, header_list_ptr);
Expand Down Expand Up @@ -142,7 +152,7 @@ subroutine prepare_request_header_ptr(header_list_ptr, req_headers)
end do
end subroutine prepare_request_header_ptr

function client_set_method(curl_ptr, method, response) result(status)
function set_method(curl_ptr, method, response) result(status)
type(c_ptr), intent(out) :: curl_ptr
integer, intent(in) :: method
type(response_type), intent(out) :: response
Expand Down Expand Up @@ -170,7 +180,18 @@ function client_set_method(curl_ptr, method, response) result(status)
case default
error stop 'Method argument can be either HTTP_GET, HTTP_HEAD, HTTP_POST, HTTP_PUT, HTTP_DELETE, HTTP_PATCH'
end select
end function client_set_method
end function set_method

function set_body(curl_ptr, json) result(status)
type(c_ptr), intent(out) :: curl_ptr
character(*), intent(in) :: json
integer :: status, json_length
json_length = len(json)
! if(json_length > 0) then
status = curl_easy_setopt(curl_ptr, CURLOPT_POSTFIELDS, json)
status = curl_easy_setopt(curl_ptr, CURLOPT_POSTFIELDSIZE_LARGE, json_length)
! end if
end function set_body

function client_response_callback(ptr, size, nmemb, client_data) bind(c)
type(c_ptr), intent(in), value :: ptr
Expand Down
2 changes: 1 addition & 1 deletion src/http/http_request.f90
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@ module http_request

! Request Type
type :: request_type
character(len=:), allocatable :: url
character(len=:), allocatable :: url, json
integer :: method
type(header_type), allocatable :: header(:)
end type request_type
Expand Down