fortran-lang / http-client

http-client offers a user-friendly, high-level API to make HTTP requests in Fortran.
https://http-client.fortran-lang.org/
MIT License
58 stars 8 forks source link

Discuss the API to make a GET request #4

Closed milancurcic closed 1 year ago

milancurcic commented 1 year ago

Let's discuss the tentative API:

rajkumardongre commented 1 year ago

For Simple GET request, i have think of this as high level api

use http_client, only: Request, Response
implicit none

type(Request) :: request
type(Response) :: response

request = Request(url='http://example.com', method='GET')

response = request%send()

if(.not. response%error) then 
  print *, response%content
else 
  print *, response%error_message
end if

To achieve this, i have thought of creating 3 derived types Resquest ,Response and Client in our http_client module : here is the definition of the Request type :

type :: Request
    character(len=:), allocatable :: url
    character(len=:), allocatable :: method
    type(fhash_tbl_t) :: headers
    type(fhash_tbl_t) :: params
    character(len=:), allocatable :: data
    character(len=:), allocatable :: json
    type(fhash_tbl_t) :: files
    type(fhash_tbl_t) :: cookies
    integer :: timeout

contains
    procedure :: set_method => set_method_request
    procedure :: set_url => set_url_request
    procedure :: add_header => add_header_request
    procedure :: set_headers => set_headers_request
    procedure :: add_param => add_param_request
    procedure :: set_params => set_params_request
    procedure :: set_data => set_data_request
    procedure :: add_file => add_file_request
    procedure :: set_files => set_files_request
    procedure :: add_cookie => add_cookie_request
    procedure :: set_cookies => set_cookies_request
    procedure :: set_timeout => set_timeout_request
    procedure :: send => send_request 
end type Request

Here is the definition for the Response type:

type :: Response
    integer :: status_code
    type(fhash_tbl_t) :: headers
    character(len=:), allocatable :: content
    type(fhash_tbl_t) :: cookies
    integer :: content_length
    character(len=:), allocatable :: url
    logical :: error
    character(len=:), allocatable :: error_message
contains
    procedure :: set_status_code => set_status_code_response
    procedure :: get_status_code => get_status_code_response
    procedure :: set_header => set_header_response
    procedure :: get_header => get_header_response
    procedure :: set_content => set_content_response
    procedure :: get_content => get_content_response
    procedure :: set_cookie => set_cookie_response
    procedure :: get_cookie => get_cookie_response
    procedure :: get_content_length => get_content_length_response 
    procedure :: is_error => is_error_response 
    procedure :: get_error_message => get_error_message_response 
end type Response

Defination for Client type :

type :: Client
    type(CURL), pointer :: curl_handle
    type(Request) :: request
    type(Response) :: response
contains
    procedure :: set_user_agent => set_user_agent_http_client
    procedure :: set_timeout => set_timeout_http_client
    procedure :: set_follow_redirects => set_follow_redirects_http_client
    procedure :: set_max_redirects => set_max_redirects_http_client
    procedure :: set_cookies => set_cookies_http_client
    procedure :: set_headers => set_headers_http_client
    procedure :: set_params => set_params_http_client
    procedure :: set_data => set_data_http_client
    procedure :: set_files => set_files_http_client
    procedure :: get => get_http_client 
    procedure :: post => post_http_client 
    procedure :: put => put_http_client 
    procedure :: delete => delete_http_client 
    procedure :: head => head_http_client 
    procedure :: options => options_http_client 
    procedure :: get_response => get_response_http_client 
end type Client
interkosmos commented 1 year ago

If you strive for an object-oriented API, you should add a postfix like _class to your type names, for instance:

type, public :: request_class
    character(len=:), allocatable :: url
    character(len=:), allocatable :: method
    ! [...]
end type request_class

Regarding your client class, you have to decide whether to simply store a C pointer to the cURL handle or to encapsulate the handle in a distinct derived type, either:

type, public :: client_class
    type(c_ptr) :: curl_ptr = c_null_ptr
    ! [...]
end type client_class

Or:

type, public :: curl_type
    type(c_ptr) :: curl_ptr = c_null_ptr
end type curl_type

type, public :: client_class
    type(curl_type) :: curl_handle
    ! [...]
end type client_class

Furthermore, you should set default values where applicable.

You may want to declare class methods with a class name prefix. For example, in client_class, instead of:

procedure :: set_user_agent => set_user_agent_http_client

Perhaps, better:

procedure, public :: set_user_agent => client_set_user_agent

This way, it is easier to identify the method declaration client_set_user_agent() as a member of the class client_class.

rajkumardongre commented 1 year ago

Thank you @interkosmos I will make a note of it.

SRAZKVT commented 1 year ago

wouldn't the method for creating the request be better as a simple enumeration ? the amount of methods is fairly small, doesn't change often, and is simpler (imo) than using strings, as those are case sensitive, and completion engines cannot pick up on them without dedicated engine.

Could also have different oop classes for different kinds of requests, where instead of

request = Request(url='http://example.com', method='GET')

we would just write

request = Get_Request(url='http://example.com')

or something similar

rajkumardongre commented 1 year ago

Thank you, @SRAZKVT . Since my knowledge on enumerations in Fortran is limited, I will read more about it to gain a better understanding.

Regarding passing an HTTP method, an alternative approach is to convert the method to uppercase before storing it in the Request constructor. This is because the Fortran-cURL binding requires the method to be stored as an uppercase string, such as "GET", "POST", "PUT", "PATCH", or "DELETE".

Another approach could be to use the % operator to call the appropriate method for each HTTP method. For instance,

request = Request%get(url="http://example.com") 

would call the get method for the Request class and pass the URL as an argument.

Although it is generally beneficial to create separate object-oriented programming (OOP) classes for different types of requests to enhance code modularity, there are potential drawbacks to consider. Users may be required to remember additional procedures like get_request, post_request, and put_request, which can increase the likelihood of errors. An alternative approach is to employ a single class, wherein an object is instantiated using the constructor and different procedures are called based on the HTTP method argument.

For instance, let's see the execution of following statement:

request = request_class(url="http://example.com", method="GET")
response = request%send()

The request_class is defined as follows, including a send procedure:

type, public :: request_class
   character(len=:), allocatable :: url
   character(len=:), allocatable :: method
   ...
   ! Other variables  
contains
   procedure :: send => request_send 
   !...
   ! Other procedures
end type request_class

The request_send procedure, within the request_class, instantiates an object of the client_class (responsible for making the actual HTTP requests) and calls its get_response procedure, which returns the response object:

function request_send(this) result(response)
    class(request_class), intent(inout) :: this
    type(response_class) :: response
    type(client_class) :: client

    client = client_class(request=this)
    response = client%get_response()
end function request_send

The client_class type is defined as follows, containing procedures for handling appropriate HTTP requests such as get, post, etc.:

type :: client_class
    type(request_class) :: request
contains
    procedure :: get_response => client_get_response 
    procedure :: get => client_get_request
    procedure :: post => client_post_request
    procedure :: put => client_put_request
    procedure :: patch => client_patch_request
    procedure :: delete => client_delete_request
end type client_class

Within the client_get_response procedure, based on the request's method, the corresponding HTTP method procedure is called, resulting in a response object populated with server response details such as content, headers, cookies, and status code:

function client_get_response(this) result(response)
    class(client_class), intent(inout) :: this

    if (this%request%method == "GET") then
        response = this%get()
    if (this%request%method == "POST") then
        response = this%post()
    if (this%request%method == "PUT") then
        response = this%put()
    if (this%request%method == "PATCH") then
        response = this%patch()
    if (this%request%method == "DELETE") then
        response = this%delete()
end function client_get_response

Lastly, the response_class type definition stores server response information, including the status code, content, content length, and other relevant variables:

type, public :: response_class
   integer :: status_code
   character(len=:), allocatable :: content
   integer :: content_length
  ...
  ! Other variables
end type response_class

In summary, the proposed implementation involves three classes: request_class for managing requests, response_class for storing server responses, and client_class responsible for making HTTP requests using the Fortran-cURL module and returning the response.

Please don't hesitate to share any additional suggestions or inquiries you may have.

SRAZKVT commented 1 year ago

@rajkumardongre so if I understand well your idea, it would be having the different OOP classes, and an intermediary class that would be called yo build the actual classes ? sounds reasonable honestly.

rajkumardongre commented 1 year ago

@SRAZKVT , I apologize for the typos in my previous comment that changed the intended meaning of my message. I have now updated it, and I hope it conveys what I meant to say. Please take a look. If you have any further suggestions or questions, please don't hesitate to share them.

SRAZKVT commented 1 year ago

@rajkumardongre sounds good to me, would be nice to have someone else's opinion though.

interkosmos commented 1 year ago

I would prefer enums, but character arguments are common in Fortran project as well. Using integers, argument validation would be simpler, as we just have to check for the value to be within the range of the enum:

! HTTP methods:
integer, parameter, public :: HTTP_GET    = 1
integer, parameter, public :: HTTP_HEAD   = 2
integer, parameter, public :: HTTP_POST   = 3
integer, parameter, public :: HTTP_PUT    = 4
integer, parameter, public :: HTTP_DELETE = 5
! [...]

With characters, we have to normalise the argument to upper or lower case first.

The HTTP method could be made optional, with HTTP_GET being the default.

milancurcic commented 1 year ago

Do you anticipate the need for the user to maintain and change the state of the request instance? In other words, do we need a call to request % send that is separate from the request constructor?

If not, why not design a more functional constructor approach where a request function returns a response type, like in Python requests?

use http_client, only: http_request, http_response_type, HTTP_GET

type(http_response_type) :: response

response = http_request("http://example.com")
! response = http_request("http://example.com", method=HTTP_GET) ! Same thing as above

print *, response % status_code ! 200 if ok
print *, response % headers ! array of key-val pairs
print *, response % body ! character string

I suggest adopting a small set of principles to stick to, and only relax them when necessary. These could be:

In summary, start small and simple, and only add complexity when needed.

rajkumardongre commented 1 year ago

I would prefer enums, but character arguments are common in Fortran project as well. Using integers, argument validation would be simpler, as we just have to check for the value to be within the range of the enum:

! HTTP methods:
integer, parameter, public :: HTTP_GET    = 1
integer, parameter, public :: HTTP_HEAD   = 2
integer, parameter, public :: HTTP_POST   = 3
integer, parameter, public :: HTTP_PUT    = 4
integer, parameter, public :: HTTP_DELETE = 5
! [...]

With characters, we have to normalise the argument to upper or lower case first.

The HTTP method could be made optional, with HTTP_GET being the default.

Okay, so by using this, we will expect an integer in the range of 1 to 5 as the method argument in our request constructor.

rajkumardongre commented 1 year ago
use http_client, only: http_request, http_response_type, HTTP_GET

type(http_response_type) :: response

response = http_request("http://example.com")
! response = http_request("http://example.com", method=HTTP_GET) ! Same thing as above

print *, response % status_code ! 200 if ok
print *, response % headers ! array of key-val pairs
print *, response % body ! character string

I agree, it's a good idea. I will proceed with making the necessary changes and post the updated version.

rajkumardongre commented 1 year ago

Based on our previous discussion, I have updated the API. Please review it and let me know if there is anything I may have missed.

module http_client
  implicit none
  private
  ! HTTP methods:
  integer, parameter, public :: HTTP_GET    = 1
  integer, parameter, public :: HTTP_HEAD   = 2
  integer, parameter, public :: HTTP_POST   = 3
  integer, parameter, public :: HTTP_PUT    = 4
  integer, parameter, public :: HTTP_DELETE = 5
  integer, parameter, public :: HTTP_PATCH  = 6

  ! Request Type
  type, public :: request_class
    character(len=:), allocatable :: url
    character(len=:), allocatable :: method
  end type request_class

  ! Response Type
  type, public :: response_class
    integer :: status_code
    character(len=:), allocatable :: content
    integer :: content_length
  end type response_class

  ! http_client Type
  type :: client_class
    type(request_class) :: request
  contains
    procedure :: client_get_response 
  end type client_class

  interface http_request
    module procedure new_request
  end interface http_request

  interface client_class
    module procedure new_client
  end interface client_class

contains

! Constructor for request_class type.
function new_request(url, method) result(response)
  character(len=*) :: url
  integer, optional :: method
  type(request_class) :: request
  type(response_class) :: response
  type(client_class) :: client

  if(.not. present(method)) then
    select case (method)
    case (1)
      request%method = 'GET'  
    case (2)
      request%method = 'HEAD'  
    case (3)
      request%method = 'POST'  
    case (4)
      request%method = 'PUT'  
    case (5)
      request%method = 'DELETE'  
    case (6)
      request%method = 'PATCH'       
    end select
  else
    request%method = 'GET'
  end if
  request%url = url

  client = client_class(request=request)
  response = client%client_get_response()

end function new_request

function client_get_response(this) result(response)
  class(client_class) :: this
  type(response_class) :: response
  ! logic for populating response using fortran-curl
end function client_get_response

! Constructor for client_class type.
  function new_client(request) result(client)
    type(client_class) :: client
    type(request_class) :: request

    client%request = request
  end function new_client

end module http_client
milancurcic commented 1 year ago

Thanks @rajkumardongre. I suggest a more idiomatic _type suffix for type names (instead of _class), which is also consistent with the stdlib style.

For the function new_request, I suggest just request as all requests will be new if they are read-only.

rajkumardongre commented 1 year ago

Alright, I will proceed with making the changes.

milancurcic commented 1 year ago

We got the basic API down with the PRs so far. I'll close and we can re-open if needed.