Skip to content

Commit 979ed85

Browse files
Added HTTP authentication (#44)
1 parent 80af507 commit 979ed85

File tree

5 files changed

+99
-4
lines changed

5 files changed

+99
-4
lines changed

example/basic_auth.f90

Lines changed: 19 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,19 @@
1+
program basic_auth
2+
! Making request with HTTP Basic Auth
3+
use http, only: response_type, request, pair_type
4+
implicit none
5+
type(response_type) :: response
6+
type(pair_type) :: auth
7+
8+
! setting username and password
9+
auth = pair_type('user', 'passwd')
10+
11+
response = request(url='https://httpbin.org/basic-auth/user/passwd', auth=auth)
12+
if(.not. response%ok) then
13+
print *,'Error message : ', response%err_msg
14+
else
15+
print *, 'Response Code : ', response%status_code
16+
print *, 'Response Content : ', response%content
17+
end if
18+
19+
end program basic_auth

example/post_form_data.f90

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,6 @@ program post_form_data
44
use http, only: response_type, request, HTTP_POST, pair_type
55
implicit none
66
type(response_type) :: response
7-
type(pair_type), allocatable :: req_header(:)
87
type(pair_type), allocatable :: form_data(:)
98

109
! Storing form data in a array of pair_type object, each pair_type object

src/http/http_client.f90

Lines changed: 33 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,8 @@ module http_client
1919
CURLOPT_WRITEDATA, CURLOPT_WRITEFUNCTION, &
2020
CURLOPT_POSTFIELDS, CURLOPT_POSTFIELDSIZE_LARGE, curl_easy_escape, &
2121
curl_mime_init, curl_mime_addpart, curl_mime_filedata,curl_mime_name, &
22-
CURLOPT_MIMEPOST,curl_mime_data, CURL_ZERO_TERMINATED
22+
CURLOPT_MIMEPOST,curl_mime_data, CURL_ZERO_TERMINATED, &
23+
CURLOPT_HTTPAUTH, CURLAUTH_BASIC, CURLOPT_USERNAME, CURLOPT_PASSWORD
2324
use stdlib_optval, only: optval
2425
use http_request, only: request_type
2526
use http_response, only: response_type
@@ -53,7 +54,7 @@ module http_client
5354
! new client_type object using the request object as a parameter and sends the request to the server
5455
! using the client_get_response method. The function returns the response_type object containing the
5556
! server's response.
56-
function new_request(url, method, header, data, form, file) result(response)
57+
function new_request(url, method, header, data, form, file, auth) result(response)
5758
!! This function creates a new HTTP request object of the request_type type and sends
5859
!! the request to the server using the client_type object. The function takes the URL,
5960
!! HTTP method, request headers, request data, and form data as input arguments and returns
@@ -71,6 +72,8 @@ function new_request(url, method, header, data, form, file) result(response)
7172
!! An optional array of pair_type objects that specifies the form data to send in the request body.
7273
type(pair_type), intent(in), optional :: file
7374
!! An optional pair_type object that specifies the file data to send in the request body.
75+
type(pair_type), intent(in), optional :: auth
76+
!! An optional pair_type object that stores the username and password for Authentication
7477
type(response_type) :: response
7578
!! A response_type object containing the server's response.
7679
type(request_type) :: request
@@ -109,6 +112,11 @@ function new_request(url, method, header, data, form, file) result(response)
109112
request%file = file
110113
end if
111114

115+
! setting username and password for Authentication
116+
if(present(auth)) then
117+
request%auth = auth
118+
end if
119+
112120
! Populates the response
113121
client = client_type(request=request)
114122
response = client%client_get_response()
@@ -163,6 +171,9 @@ & function failed. This can occur due to insufficient memory available in the sy
163171
! setting request body
164172
rc = set_body(curl_ptr, this%request)
165173

174+
! setting request authentication
175+
rc = set_auth(curl_ptr, this%request)
176+
166177
! prepare headers for curl
167178
call prepare_request_header_ptr(header_list_ptr, this%request%header)
168179

@@ -315,7 +326,6 @@ function set_body(curl_ptr, request) result(status)
315326
!! An integer value representing the status of the curl_easy_setopt function call.
316327

317328
integer :: i
318-
character(len=:), allocatable :: form_encoded_str
319329
type(c_ptr) :: mime_ptr, part_ptr
320330

321331
! if only data is passed
@@ -374,6 +384,26 @@ function set_postfields(curl_ptr, data) result(status)
374384

375385
end function set_postfields
376386

387+
function set_auth(curl_ptr, request) result(status)
388+
!! Set the user name and password for Authentication. It sends the user name
389+
!! and password over the network in plain text, easily captured by others.
390+
type(c_ptr), intent(out) :: curl_ptr
391+
!! An out argument of type c_ptr that is set to point to a new curl handle.
392+
type(request_type), intent(inout) :: request
393+
!! The HTTP request
394+
integer :: status
395+
!! An integer value representing the status of the curl_easy_setopt function call.
396+
397+
if(allocated(request%auth)) then
398+
status = curl_easy_setopt(curl_ptr, CURLOPT_HTTPAUTH, CURLAUTH_BASIC)
399+
status = curl_easy_setopt(curl_ptr, CURLOPT_USERNAME, request%auth%name)
400+
status = curl_easy_setopt(curl_ptr, CURLOPT_PASSWORD, request%auth%value)
401+
else
402+
! No curl function was called so set status to zero.
403+
status = 0
404+
end if
405+
end function set_auth
406+
377407
! This function is a callback function used by the libcurl library to handle HTTP responses. It is
378408
! called for each chunk of data received from the server and appends the data to a response_type object.
379409
! The function takes four input arguments: ptr, size, nmemb, and client_data. ptr is a pointer to the

src/http/http_request.f90

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -38,5 +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+
type(pair_type), allocatable :: auth
42+
!! Stores the username and password for Authentication
4143
end type request_type
4244
end module http_request

test/test_auth.f90

Lines changed: 45 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,45 @@
1+
program test_auth
2+
use iso_fortran_env, only: stderr => error_unit
3+
use http, only : response_type, request, pair_type
4+
5+
implicit none
6+
type(response_type) :: res
7+
character(:), allocatable :: msg
8+
logical :: ok = .true.
9+
type(pair_type) :: auth
10+
11+
! setting username and password
12+
auth = pair_type('user', 'passwd')
13+
res = request(url='https://httpbin.org/basic-auth/user/passwd', auth=auth)
14+
15+
msg = 'test_auth: '
16+
17+
if (.not. res%ok) then
18+
ok = .false.
19+
msg = msg // res%err_msg
20+
write(stderr, '(a)') msg
21+
error stop 1
22+
end if
23+
24+
! Status Code Validation
25+
if (res%status_code /= 200) then
26+
ok = .false.
27+
print '(a)', 'Failed : Status Code Validation'
28+
end if
29+
30+
! Content Length Validation
31+
if (res%content_length /= 47 .or. &
32+
len(res%content) /= 47) then
33+
ok = .false.
34+
print '(a)', 'Failed : Content Length Validation'
35+
end if
36+
37+
if (.not. ok) then
38+
msg = msg // 'Test Case Failed'
39+
write(stderr, '(a)'), msg
40+
error stop 1
41+
else
42+
msg = msg // 'All tests passed.'
43+
print '(a)', msg
44+
end if
45+
end program test_auth

0 commit comments

Comments
 (0)