aboutsummaryrefslogtreecommitdiff
path: root/request.f90
diff options
context:
space:
mode:
authorJeffrey Armstrong <jeff@approximatrix.com>2020-05-01 19:08:46 -0400
committerJeffrey Armstrong <jeff@approximatrix.com>2020-05-01 19:08:46 -0400
commit4108ae479d67067789f98267175e127e6a2a61ad (patch)
tree1252e35b507a405a97b077d07e3f3d8277f437e5 /request.f90
parent873ffd8201fd520122d8ec94bdd4230d79d0331c (diff)
downloadLR-87-4108ae479d67067789f98267175e127e6a2a61ad.tar.gz
LR-87-4108ae479d67067789f98267175e127e6a2a61ad.zip
Initial work on a sensible, packaged connection system.
Diffstat (limited to 'request.f90')
-rw-r--r--request.f90134
1 files changed, 134 insertions, 0 deletions
diff --git a/request.f90 b/request.f90
index d470a06..3cc8cbf 100644
--- a/request.f90
+++ b/request.f90
@@ -1,10 +1,144 @@
module request
+use network
+use iso_c_binding
implicit none
integer, parameter::bufsize = 65536
+
+ integer, parameter::CONNECTION_NONE = 0
+ integer, parameter::CONNECTION_CLOSED = 1
+ integer, parameter::CONNECTION_SERVER_NOT_FOUND = 2
+ integer, parameter::CONNECTION_SOCKET_FAILURE = 3
+ integer, parameter::CONNECTION_SSL_SETUP_FAILURE = 4
+ integer, parameter::CONNECTION_SSL_CONN_FAILURE = 5
+ integer, parameter::CONNECTION_OPEN = 6
+
+ type :: connection
+
+ integer::code
+
+ type(simple_hostent)::host
+ integer::socket
+ type(c_ptr)::ssl_ctx
+ type(c_ptr)::ssl
+
+ end type connection
contains
+ function open_connection(server, port) result(conn)
+ use jessl
+ use network
+ implicit none
+
+ character(*), intent(in)::server
+ integer, intent(in), optional::port
+ type(connection)::conn
+
+ type(sockaddr_in), target::sa
+ type(c_ptr)::ssl_method
+
+ conn%code = CONNECTION_NONE
+
+ ! Lookup host
+ conn%host = gethostbyname(server)
+ if((.not. allocated(conn%host%h_name)) .or. (conn%host%h_addr4 == 0)) then
+ conn%code = CONNECTION_SERVER_NOT_FOUND
+ return
+ end if
+
+ ! Build the socket
+ sa%sin_family = AF_INET
+ sa%sin_addr%s_addr = conn%host%h_addr4
+ if(present(port)) then
+ sa%sin_port = htons(port)
+ else
+ sa%sin_port = htons(1965)
+ end if
+ conn%socket = socket(AF_INET, SOCK_STREAM, 0)
+ if(.not. connect(conn%socket, sa)) then
+ conn%code = CONNECTION_SOCKET_FAILURE
+ return
+ end if
+
+ ! Set up ssl now
+ ssl_method = tls_v1_3_client_method()
+ conn%ssl_ctx = ctx_new(ssl_method)
+ conn%ssl = ssl_new(conn%ssl_ctx)
+ if((.not. c_associated(conn%ssl)) .or. (set_fd(conn%ssl, conn%socket) /= 1)) then
+ conn%code = CONNECTION_SSL_SETUP_FAILURE
+ return
+ end if
+
+ ! Connect via ssl
+ if(ssl_connect(conn%ssl) /= 1) then
+ conn%code = CONNECTION_SSL_CONN_FAILURE
+ return
+ end if
+
+ ! Here, the connection is live
+ conn%code = CONNECTION_OPEN
+
+ end function open_connection
+
+ subroutine close_connection(conn)
+ use jessl
+ use network
+ implicit none
+
+ type(connection), intent(inout)::conn
+ integer::res
+
+ if(conn%code >= CONNECTION_OPEN) then
+ res = ssl_shutdown(conn%ssl)
+ end if
+
+ if(conn%code >= CONNECTION_SSL_CONN_FAILURE) then
+ res = ssl_free(conn%ssl)
+ end if
+
+ if(conn%code >= CONNECTION_SSL_SETUP_FAILURE) then
+ res = ctx_free(conn%ssl_ctx)
+ end if
+
+ if(conn%code > CONNECTION_SOCKET_FAILURE) then
+ call close_socket(conn%socket)
+ end if
+
+ if(conn%code > CONNECTION_SERVER_NOT_FOUND) then
+ deallocate(conn%host%h_name)
+ end if
+
+ conn%code = CONNECTION_CLOSED
+
+ end subroutine close_connection
+
+ function get_server_from_url(url) result(server)
+ implicit none
+
+ character(*), intent(in)::url
+ character(:), allocatable::server
+
+ integer::start_server, end_server, length
+
+ start_server = index(url, "://")
+ if(start_server > 0) then
+
+ start_server = start_server + 3
+ end_server = index(url(start_server:len_trim(url)), "/")
+ if(end_server <= 0) then
+ end_server = len_trim(url)
+ else
+ end_server = end_server + start_server - 1
+ end if
+ length = end_server - start_server + 1
+
+ allocate(character(len=length) :: server)
+ server = url(start_server:end_server)
+ end if
+
+ end function get_server_from_url
+
function send_string(ssl, str, trimming) result(success)
use iso_c_binding
use jessl