Skip to content

Commit eee5765

Browse files
Implement functionality to support sending form data in HTTP requests. (#32)
* Implement functionality to support sending form data in HTTP requests. * Implemented tests for POST requests. * Update examples to use httpbin.com domain and dummyjson.com for testing purposes * update docstring
1 parent e172677 commit eee5765

File tree

10 files changed

+314
-56
lines changed

10 files changed

+314
-56
lines changed

example/get.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@ program get_request
55
implicit none
66
type(response_type) :: response
77

8-
response = request(url='https://jsonplaceholder.typicode.com/todos/1')
8+
response = request(url='https://httpbin.org/get')
99
if(.not. response%ok) then
1010
print *,'Error message : ', response%err_msg
1111
else

example/post.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,7 @@ program post_request
77
character(:), allocatable :: json_data
88
type(header_type), allocatable :: req_header(:)
99

10-
req_header = [header_type('Content-Type', 'applicaiton/json')]
10+
req_header = [header_type('Content-Type', 'application/json')]
1111

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

example/post_form_data.f90

Lines changed: 23 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,23 @@
1+
program post_form_data
2+
! This program demonstrates sending Form data using POST request and printing the
3+
! status, length of the body, method, and the body of the response.
4+
use http, only: response_type, request, HTTP_POST, header_type, form_type
5+
implicit none
6+
type(response_type) :: response
7+
type(header_type), allocatable :: req_header(:)
8+
type(form_type), allocatable :: form_data(:)
9+
10+
form_data = [form_type('param1', 'value1'), form_type('param2', 'value2')]
11+
12+
response = request(url='https://httpbin.org/post', method=HTTP_POST, form=form_data)
13+
14+
if(.not. response%ok) then
15+
print *,'Error message : ', response%err_msg
16+
else
17+
print *, 'Response Code : ', response%status_code
18+
print *, 'Response Length : ', response%content_length
19+
print *, 'Response Method : ', response%method
20+
print *, 'Response Content : ', response%content
21+
end if
22+
23+
end program post_form_data

src/http.f90

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -4,4 +4,5 @@ module http
44
use http_response, only: response_type
55
use http_client, only: request
66
use http_header, only : header_type
7+
use http_form, only : form_type
78
end module http

src/http/http_client.f90

Lines changed: 168 additions & 21 deletions
Large diffs are not rendered by default.

src/http/http_form.f90

Lines changed: 15 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,15 @@
1+
module http_form
2+
!! This module contains the definition of a form_type derived type, which represents a
3+
!!single field of an HTTP form.
4+
implicit none
5+
private
6+
public :: form_type
7+
8+
type :: form_type
9+
!! A derived type representing a single field of an HTTP form.
10+
character(:), allocatable :: name
11+
!! The name of the form field
12+
character(:), allocatable :: value
13+
!! The value of the form filed
14+
end type form_type
15+
end module http_form

src/http/http_request.f90

Lines changed: 16 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,9 @@
11
module http_request
2+
3+
!! This module contains the definition of a request_type derived type, which
4+
!! represents an HTTP request.
5+
6+
use http_form , only: form_type
27
use http_header, only: header_type
38
use stdlib_string_type, only: string_type, to_lower, operator(==), char
49

@@ -18,8 +23,18 @@ module http_request
1823

1924
! Request Type
2025
type :: request_type
21-
character(len=:), allocatable :: url, data
26+
!! Representing an HTTP request.
27+
character(len=:), allocatable :: url
28+
!! The URL of the request
29+
character(len=:), allocatable :: data
30+
!! The data to be send with request
31+
character(len=:), allocatable :: form_encoded_str
32+
!! The URL-encoded form data.
2233
integer :: method
34+
!! The HTTP method of the request.
2335
type(header_type), allocatable :: header(:)
36+
!! An Array of request headers.
37+
type(form_type), allocatable :: form(:)
38+
!! An array of fields in an HTTP form.
2439
end type request_type
2540
end module http_request

src/http/http_response.f90

Lines changed: 23 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,8 @@
11
module http_response
2+
3+
!! This module contains the definition of a response_type derived type, which
4+
!! represents an HTTP response.
5+
26
use, intrinsic :: iso_fortran_env, only: int64
37
use http_header, only: header_type, get_header_value
48
use stdlib_string_type, only: string_type, to_lower, operator(==), char
@@ -10,22 +14,38 @@ module http_response
1014

1115
! Response Type
1216
type :: response_type
13-
character(len=:), allocatable :: url, content, method, err_msg
17+
!! Representing an HTTP response.
18+
character(len=:), allocatable :: url
19+
!! The URL of the request
20+
character(len=:), allocatable :: content
21+
!! The content of the response.
22+
character(len=:), allocatable :: method
23+
!! The HTTP method of the request.
24+
character(len=:), allocatable :: err_msg
25+
!! The Error message if the response was not successful.
1426
integer :: status_code = 0
27+
!! The HTTP status code of the response
1528
integer(kind=int64) :: content_length = 0
29+
!! length of the response content.
1630
logical :: ok = .true.
31+
!! true if the response was successful else false.
1732
type(header_type), allocatable :: header(:)
33+
!! An Array of response headers.
1834
contains
1935
procedure :: header_value
2036
end type response_type
2137

2238
contains
23-
! The header_value function takes a key string as input and returns the corresponding
24-
! value as a string from a response_type object's header array.
2539
pure function header_value(this, key) result(val)
40+
!! The header_value function takes a key string as input and returns
41+
!! the corresponding value as a string from a response_type object's
42+
!! header array.
2643
class(response_type), intent(in) :: this
44+
!! An object representing the HTTP response.
2745
character(*), intent(in) :: key
46+
!! The key of the header value to be retrieved.
2847
character(:), allocatable :: val
48+
!! The value of the specified key in the HTTP response header.
2949

3050
val = get_header_value(this%header, key)
3151
end function header_value

test/test_get.f90

Lines changed: 12 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -5,19 +5,16 @@ program test_get
55
implicit none
66
type(response_type) :: res
77
character(:), allocatable :: msg, original_content
8-
character(2), allocatable :: number
98
logical :: ok = .true.
109
type(header_type), allocatable :: request_header(:)
11-
integer :: i, passed_test_case, fail_test_case
10+
integer :: i
1211

13-
passed_test_case = 0
14-
fail_test_case = 0
15-
16-
original_content = '{"data":{"id":1,"email":"george.bluth@reqres.in",&
17-
&"first_name":"George","last_name":"Bluth",&
18-
&"avatar":"https://reqres.in/img/faces/1-image.jpg"},&
19-
&"support":{"url":"https://reqres.in/#support-heading",&
20-
&"text":"To keep ReqRes free, contributions towards server costs are appreciated!"}}'
12+
original_content = '{"id":1,"title":"iPhone 9","description":"An apple mobile which is nothing like &
13+
apple","price":549,"discountPercentage":12.96,"rating":4.69,"stock":94,"brand":"Apple","category":&
14+
"smartphones","thumbnail":"https://i.dummyjson.com/data/products/1/thumbnail.jpg","images":&
15+
["https://i.dummyjson.com/data/products/1/1.jpg","https://i.dummyjson.com/data/products/1/2.jpg",&
16+
"https://i.dummyjson.com/data/products/1/3.jpg","https://i.dummyjson.com/data/products/1/4.jpg",&
17+
"https://i.dummyjson.com/data/products/1/thumbnail.jpg"]}'
2118

2219
! setting request header
2320
request_header = [ &
@@ -27,7 +24,8 @@ program test_get
2724
header_type('User-Agent', 'my user agent') &
2825
]
2926

30-
res = request(url='https://reqres.in/api/users/1', header=request_header)
27+
! res = request(url='https://reqres.in/api/users/1', header=request_header)
28+
res = request(url='https://dummyjson.com/products/1', header=request_header)
3129

3230
msg = 'test_get: '
3331

@@ -42,51 +40,36 @@ program test_get
4240
if (res%status_code /= 200) then
4341
ok = .false.
4442
print '(a)', 'Failed : Status Code Validation'
45-
fail_test_case = fail_test_case + 1
46-
else
47-
passed_test_case = passed_test_case + 1
4843
end if
4944

5045
! Content Length Validation
5146
if (res%content_length /= len(original_content) .or. &
5247
len(res%content) /= len(original_content)) then
5348
ok = .false.
5449
print '(a)', 'Failed : Content Length Validation'
55-
fail_test_case = fail_test_case + 1
56-
else
57-
passed_test_case = passed_test_case + 1
5850
end if
5951

6052
! Content Validation
6153
if (res%content /= original_content) then
6254
ok = .false.
6355
print '(a)', 'Failed : Content Validation'
64-
fail_test_case = fail_test_case + 1
65-
else
66-
passed_test_case = passed_test_case + 1
6756
end if
6857

6958
! Header Size Validation
70-
if (size(res%header) /= 14 .and. size(res%header) /= 15) then
59+
if (size(res%header) /= 16) then
7160
ok = .false.
7261
print '(a)', 'Failed : Header Size Validation'
73-
fail_test_case = fail_test_case + 1
74-
else
75-
passed_test_case = passed_test_case + 1
7662
end if
7763

7864
! Header Value Validation
7965
if (res%header_value('content-type') /= 'application/json; charset=utf-8') then
8066
ok = .false.
8167
print '(a)', 'Failed : Header Value Validation'
82-
fail_test_case = fail_test_case + 1
83-
else
84-
passed_test_case = passed_test_case + 1
8568
end if
8669

8770
if (.not. ok) then
88-
write(stderr, '(a i2 a i2 a)'), msg, fail_test_case,'/',fail_test_case+passed_test_case,&
89-
& ' Test Case Failed'
71+
msg = msg // 'Test Case Failed'
72+
write(stderr, '(a)'), msg
9073
error stop 1
9174
else
9275
msg = msg // 'All tests passed.'

test/test_post.f90

Lines changed: 54 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,54 @@
1+
program test_post
2+
use iso_fortran_env, only: stderr => error_unit
3+
use http, only: request, header_type, HTTP_POST, response_type
4+
implicit none
5+
type(response_type) :: res
6+
character(:), allocatable :: json_data, original_content, msg
7+
type(header_type), allocatable :: req_header(:)
8+
logical :: ok = .true.
9+
10+
original_content = '{"id":101,"title":"BMW","description":"A luxurious and high-performance vehicle"}'
11+
req_header = [header_type('Content-Type', 'application/json')]
12+
13+
json_data = '{"title":"BMW","description":"A luxurious and high-performance vehicle"}'
14+
15+
res = request(url='https://dummyjson.com/products/add', method=HTTP_POST, data=json_data, header=req_header)
16+
17+
msg = 'test_post: '
18+
19+
if (.not. res%ok) then
20+
ok = .false.
21+
msg = msg // res%err_msg
22+
write(stderr, '(a)') msg
23+
error stop 1
24+
end if
25+
26+
! Status Code Validation
27+
if (res%status_code /= 200) then
28+
ok = .false.
29+
print '(a)', 'Failed : Status Code Validation'
30+
end if
31+
32+
! Content Length Validation
33+
if (res%content_length /= len(original_content) .or. &
34+
len(res%content) /= len(original_content)) then
35+
ok = .false.
36+
print '(a)', 'Failed : Content Length Validation'
37+
end if
38+
39+
! Content Validation
40+
if (res%content /= original_content) then
41+
ok = .false.
42+
print '(a)', 'Failed : Content Validation'
43+
end if
44+
45+
if (.not. ok) then
46+
msg = msg // 'Test Case Failed'
47+
write(stderr, '(a)'), msg
48+
error stop 1
49+
else
50+
msg = msg // 'All tests passed.'
51+
print '(a)', msg
52+
end if
53+
54+
end program test_post

0 commit comments

Comments
 (0)