Skip to content

Commit 20fa99e

Browse files
Implement timeout feature (#45)
* Implement timeout feature * Add test for timeout, and doc string for set_timeout * reduce timeout time in timeout_test * Added CURLOPT_CONNECTTIMEOUT option along with CURLOPT_TIMEOUT * change test url for auth * update postman-echo/basic-auth url
1 parent 979ed85 commit 20fa99e

File tree

5 files changed

+87
-6
lines changed

5 files changed

+87
-6
lines changed

example/timeout.f90

Lines changed: 18 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,18 @@
1+
program timeout
2+
! This program demonstrates the use of the timeout option. The request below is designed
3+
! to take more than 10 seconds to complete, but we set the timeout value to 5 seconds.
4+
! As a result, the request will fail with an error message that says "Timeout was reached".
5+
use http, only: response_type, request
6+
implicit none
7+
type(response_type) :: response
8+
9+
! Delay in response for 10 seconds
10+
response = request(url='https://httpbin.org/delay/10', timeout=5)
11+
if(.not. response%ok) then
12+
print *,'Error message : ', response%err_msg
13+
else
14+
print *, 'Response Code : ', response%status_code
15+
print *, 'Response Content : ', response%content
16+
end if
17+
18+
end program timeout

src/http/http_client.f90

Lines changed: 29 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -20,6 +20,7 @@ module http_client
2020
CURLOPT_POSTFIELDS, CURLOPT_POSTFIELDSIZE_LARGE, curl_easy_escape, &
2121
curl_mime_init, curl_mime_addpart, curl_mime_filedata,curl_mime_name, &
2222
CURLOPT_MIMEPOST,curl_mime_data, CURL_ZERO_TERMINATED, &
23+
CURLOPT_TIMEOUT, CURLOPT_CONNECTTIMEOUT, &
2324
CURLOPT_HTTPAUTH, CURLAUTH_BASIC, CURLOPT_USERNAME, CURLOPT_PASSWORD
2425
use stdlib_optval, only: optval
2526
use http_request, only: request_type
@@ -54,7 +55,7 @@ module http_client
5455
! new client_type object using the request object as a parameter and sends the request to the server
5556
! using the client_get_response method. The function returns the response_type object containing the
5657
! server's response.
57-
function new_request(url, method, header, data, form, file, auth) result(response)
58+
function new_request(url, method, header, data, form, file, timeout, auth) result(response)
5859
!! This function creates a new HTTP request object of the request_type type and sends
5960
!! the request to the server using the client_type object. The function takes the URL,
6061
!! HTTP method, request headers, request data, and form data as input arguments and returns
@@ -72,6 +73,8 @@ function new_request(url, method, header, data, form, file, auth) result(respons
7273
!! An optional array of pair_type objects that specifies the form data to send in the request body.
7374
type(pair_type), intent(in), optional :: file
7475
!! An optional pair_type object that specifies the file data to send in the request body.
76+
integer, intent(in), optional :: timeout
77+
!! Timeout value for the request in seconds
7578
type(pair_type), intent(in), optional :: auth
7679
!! An optional pair_type object that stores the username and password for Authentication
7780
type(response_type) :: response
@@ -112,6 +115,9 @@ function new_request(url, method, header, data, form, file, auth) result(respons
112115
request%file = file
113116
end if
114117

118+
! Set request timeout.
119+
request%timeout = optval(timeout, -1)
120+
115121
! setting username and password for Authentication
116122
if(present(auth)) then
117123
request%auth = auth
@@ -168,6 +174,9 @@ & function failed. This can occur due to insufficient memory available in the sy
168174
! setting request method
169175
rc = set_method(curl_ptr, this%request%method, response)
170176

177+
! setting request timeout
178+
rc = set_timeout(curl_ptr, this%request%timeout)
179+
171180
! setting request body
172181
rc = set_body(curl_ptr, this%request)
173182

@@ -300,6 +309,25 @@ function set_method(curl_ptr, method, response) result(status)
300309
end select
301310
end function set_method
302311

312+
function set_timeout(curl_ptr, timeout) result(status)
313+
!! This function sets the timeout value (in seconds). If the timeout value
314+
!! is less than zero, it is ignored and a success status is returned.
315+
type(c_ptr), intent(out) :: curl_ptr
316+
!! Pointer to the curl handle.
317+
integer(kind=int64), intent(in) :: timeout
318+
!! Timeout seconds for request.
319+
integer :: status
320+
!! Status code indicating whether the operation was successful.
321+
if(timeout < 0) then
322+
status = 0
323+
else
324+
! setting the maximum time allowed for the connection to established.(in seconds)
325+
status = curl_easy_setopt(curl_ptr, CURLOPT_CONNECTTIMEOUT, timeout)
326+
! setting maximum time allowed for transfer operation.(in seconds)
327+
status = curl_easy_setopt(curl_ptr, CURLOPT_TIMEOUT, timeout)
328+
end if
329+
end function set_timeout
330+
303331
! The set_body function determines the type of data to include in the request body
304332
! based on the inputs provided. If data is provided, it is sent as the body of the
305333
! request. If form is provided without a file, the form data is URL encoded and sent

src/http/http_request.f90

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@ module http_request
33
!! This module contains the definition of a request_type derived type, which
44
!! represents an HTTP request.
55

6-
! use http_form , only: pair_type
6+
use iso_fortran_env, only: int64
77
use http_pair, only: pair_type
88
use stdlib_string_type, only: string_type, to_lower, operator(==), char
99

@@ -38,6 +38,7 @@ module http_request
3838
!! An array of fields in an HTTP form.
3939
type(pair_type), allocatable :: file
4040
!! Used to store information about files to be sent in HTTP requests.
41+
integer(kind=int64) :: timeout
4142
type(pair_type), allocatable :: auth
4243
!! Stores the username and password for Authentication
4344
end type request_type

test/test_auth.f90

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -9,8 +9,8 @@ program test_auth
99
type(pair_type) :: auth
1010

1111
! setting username and password
12-
auth = pair_type('user', 'passwd')
13-
res = request(url='https://httpbin.org/basic-auth/user/passwd', auth=auth)
12+
auth = pair_type('postman', 'password')
13+
res = request(url='https://postman-echo.com/basic-auth', auth=auth)
1414

1515
msg = 'test_auth: '
1616

@@ -28,8 +28,8 @@ program test_auth
2828
end if
2929

3030
! Content Length Validation
31-
if (res%content_length /= 47 .or. &
32-
len(res%content) /= 47) then
31+
if (res%content_length /= 27 .or. &
32+
len(res%content) /= 27) then
3333
ok = .false.
3434
print '(a)', 'Failed : Content Length Validation'
3535
end if

test/test_timeout.f90

Lines changed: 34 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,34 @@
1+
program test_timeout
2+
use iso_fortran_env, only: stderr => error_unit
3+
use http, only : response_type, request
4+
5+
implicit none
6+
type(response_type) :: res
7+
character(:), allocatable :: msg
8+
logical :: ok = .true.
9+
10+
11+
res = request(url='https://httpbin.org/delay/10', timeout=1)
12+
13+
msg = 'test_timeout: '
14+
15+
if(res%err_msg /= 'Timeout was reached') then
16+
ok = .false.
17+
print '(a)', 'Failed : Timeout not reached'
18+
end if
19+
20+
! Status Code Validation
21+
if (res%status_code /= 0) then
22+
ok = .false.
23+
print '(a)', 'Failed : Status Code Validation'
24+
end if
25+
26+
if (.not. ok) then
27+
msg = msg // 'Test Case Failed'
28+
write(stderr, '(a)'), msg
29+
error stop 1
30+
else
31+
msg = msg // 'All tests passed.'
32+
print '(a)', msg
33+
end if
34+
end program test_timeout

0 commit comments

Comments
 (0)