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
7 changes: 5 additions & 2 deletions example/post.f90
Original file line number Diff line number Diff line change
@@ -1,15 +1,18 @@
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
use http, only: response_type, request, HTTP_POST, header_type
implicit none
type(response_type) :: response
character(:), allocatable :: json_data
type(header_type), allocatable :: req_header(:)

req_header = [header_type('Content-Type', 'applicaiton/json')]

! 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)
response = request(url='https://httpbin.org/post', method=HTTP_POST, data=json_data, header=req_header)

if(.not. response%ok) then
print *,'Error message : ', response%err_msg
Expand Down
25 changes: 11 additions & 14 deletions src/http/http_client.f90
Original file line number Diff line number Diff line change
Expand Up @@ -35,10 +35,10 @@ module http_client

contains
! Constructor for request_type type.
function new_request(url, method, header, json) result(response)
function new_request(url, method, header, data) result(response)
integer, intent(in), optional :: method
character(len=*), intent(in) :: url
character(len=*), intent(in), optional :: json
character(len=*), intent(in), optional :: data
type(header_type), intent(in), optional :: header(:)
type(request_type) :: request
type(response_type) :: response
Expand All @@ -62,9 +62,9 @@ function new_request(url, method, header, json) result(response)
request%header = [header_type('user-agent', 'fortran-http/0.1.0')]
end if

if(present(json)) then
request%json = json
request%header = [request%header, header_type('Content-Type', 'application/json')]
! setting the request data to be send
if(present(data)) then
request%data = data
end if

! Populates the response
Expand Down Expand Up @@ -111,7 +111,7 @@ & function failed. This can occur due to insufficient memory available in the sy
rc = set_method(curl_ptr, this%request%method, response)

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

! setting request header
rc = curl_easy_setopt(curl_ptr, CURLOPT_HTTPHEADER, header_list_ptr);
Expand Down Expand Up @@ -187,15 +187,12 @@ function set_method(curl_ptr, method, response) result(status)
end select
end function set_method

function set_body(curl_ptr, json) result(status)
function set_body(curl_ptr, data) 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
character(*), intent(in) :: data
integer :: status
status = curl_easy_setopt(curl_ptr, CURLOPT_POSTFIELDS, data)
status = curl_easy_setopt(curl_ptr, CURLOPT_POSTFIELDSIZE_LARGE, len(data))
end function set_body

function client_response_callback(ptr, size, nmemb, client_data) bind(c)
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 @@ -18,7 +18,7 @@ module http_request

! Request Type
type :: request_type
character(len=:), allocatable :: url, json
character(len=:), allocatable :: url, data
integer :: method
type(header_type), allocatable :: header(:)
end type request_type
Expand Down
5 changes: 0 additions & 5 deletions test/test_get.f90
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,6 @@ program test_get
print '(a)', 'Failed : Status Code Validation'
fail_test_case = fail_test_case + 1
else
print '(a)', 'Passed : Status Code Validation'
passed_test_case = passed_test_case + 1
end if

Expand All @@ -55,7 +54,6 @@ program test_get
print '(a)', 'Failed : Content Length Validation'
fail_test_case = fail_test_case + 1
else
print '(a)', 'Passed : Content Length Validation'
passed_test_case = passed_test_case + 1
end if

Expand All @@ -65,7 +63,6 @@ program test_get
print '(a)', 'Failed : Content Validation'
fail_test_case = fail_test_case + 1
else
print '(a)', 'Passed : Content Validation'
passed_test_case = passed_test_case + 1
end if

Expand All @@ -75,7 +72,6 @@ program test_get
print '(a)', 'Failed : Header Size Validation'
fail_test_case = fail_test_case + 1
else
print '(a)', 'Passed : Header Size Validation'
passed_test_case = passed_test_case + 1
end if

Expand All @@ -85,7 +81,6 @@ program test_get
print '(a)', 'Failed : Header Value Validation'
fail_test_case = fail_test_case + 1
else
print '(a)', 'Passed : Header Value Validation'
passed_test_case = passed_test_case + 1
end if

Expand Down