aboutsummaryrefslogtreecommitdiff
path: root/captain/gemini.f90
diff options
context:
space:
mode:
authorJeffrey Armstrong <jeff@approximatrix.com>2021-03-30 09:49:58 -0400
committerJeffrey Armstrong <jeff@approximatrix.com>2021-03-30 09:49:58 -0400
commitfde763f60465b28d33260479b64d9555abc5bcbb (patch)
treecd7691013d8538ac47567675b933b939979ec28b /captain/gemini.f90
parent342df3430218d5fd3be8ceca606330964b6f098b (diff)
downloadlevitating-fde763f60465b28d33260479b64d9555abc5bcbb.tar.gz
levitating-fde763f60465b28d33260479b64d9555abc5bcbb.zip
Reworked requests and responses with some derived types so that things make sense.
Diffstat (limited to 'captain/gemini.f90')
-rw-r--r--captain/gemini.f90120
1 files changed, 89 insertions, 31 deletions
diff --git a/captain/gemini.f90 b/captain/gemini.f90
index 841bcc4..e3b8be6 100644
--- a/captain/gemini.f90
+++ b/captain/gemini.f90
@@ -93,10 +93,28 @@ contains
end function read_into_buffer
- subroutine write_file(ssl, unit_number, mimetype)
+ subroutine write_status(ssl, code, meta)
use iso_c_binding, only: c_ptr, c_carriage_return, c_new_line
use jessl, only: ssl_write
+ implicit none
+
+ type(c_ptr)::ssl
+ integer, intent(in)::code
+ character(*), intent(in)::meta
+
+ character(8)::int_text
+
+ write(int_text, *) code
+
+ call write_string(ssl, trim(adjustl(int_text))//" "//trim(meta)//c_carriage_return//c_new_line)
+
+ end subroutine write_status
+
+ subroutine write_file(ssl, unit_number, mimetype)
+ use iso_c_binding, only: c_ptr
+ use jessl, only: ssl_write
use logging
+ use server_response, only: GEMINI_CODE_SUCCESS
implicit none
type(c_ptr)::ssl
@@ -105,7 +123,8 @@ contains
character, dimension(64)::buf
integer::buflen, written
- call write_string(ssl, "20 "//trim(mimetype)//c_carriage_return//c_new_line)
+ call write_status(ssl, GEMINI_CODE_SUCCESS, mimetype)
+ !call write_string(ssl, "20 "//trim(mimetype)//c_carriage_return//c_new_line)
buflen = read_into_buffer(unit_number, buf)
do while(buflen > 0)
@@ -115,6 +134,41 @@ contains
end subroutine write_file
+ subroutine write_redirect(ssl, url)
+ use iso_c_binding, only: c_ptr
+ use server_response, only: GEMINI_CODE_REDIRECT
+ implicit none
+
+ type(c_ptr)::ssl
+ character(*), intent(in)::url
+
+ call write_status(ssl, GEMINI_CODE_REDIRECT, url)
+
+ end subroutine write_redirect
+
+ subroutine write_input_request(ssl, msg)
+ use iso_c_binding, only: c_ptr
+ use server_response, only: GEMINI_CODE_INPUT
+ implicit none
+
+ type(c_ptr)::ssl
+ character(*), intent(in)::msg
+
+ call write_status(ssl, GEMINI_CODE_INPUT, msg)
+
+ end subroutine write_input_request
+
+ subroutine write_failure(ssl)
+ use iso_c_binding, only: c_ptr
+ use server_response, only: GEMINI_CODE_PERMFAIL
+ implicit none
+
+ type(c_ptr)::ssl
+
+ call write_status(ssl, GEMINI_CODE_PERMFAIL, "Not Found")
+
+ end subroutine write_failure
+
subroutine write_string(ssl, string)
use jessl, only: ssl_write
use iso_c_binding, only: c_ptr
@@ -144,6 +198,7 @@ contains
use iso_fortran_env
use external_handling, only: external_request_gemini
use logging, only: write_log
+ use server_response
implicit none
! For our TLS connection
@@ -152,18 +207,16 @@ contains
type(c_ptr)::ssl
integer(kind=c_long)::res
- ! Requested file
- character(1024)::request, local_request
- character(512)::mimetype
+ type(request)::req
+ type(response)::resp
- character(len=:), pointer::filename_ptr
+ ! Requested file
+ character(1024)::text_request
integer::rendered_unit, ioerror
call library_init()
-
- filename_ptr => null()
-
+
method = tls_server_method()
ctx = ctx_new(method)
@@ -218,36 +271,41 @@ contains
call write_log("Handling read_request")
! Do the actual protocol nonsense
- call read_request(ssl, request)
-
- call write_log("Request is "//trim(request))
+ call read_request(ssl, text_request)
- call simplify_request(request, local_request)
+ call req%init(text_request)
- if(len_trim(local_request) .ge. 4) then
- if(local_request(1:4) == '/api') then
+ if(len(req%location) .ge. 4) then
+ if(req%location(1:4) == '/api') then
!call handle_api_request(request)
else
- filename_ptr => external_request_gemini(local_request)
+ resp = external_request_gemini(req)
end if
else
- filename_ptr => external_request_gemini(local_request)
+ resp = external_request_gemini(req)
end if
- if(associated(filename_ptr)) then
- open(newunit=rendered_unit, file=trim(filename_ptr), status="old", &
- form="unformatted", iostat=ioerror, access="stream")
-
- call write_log("transferring "//trim(filename_ptr))
- call write_file(ssl, rendered_unit, "text/gemini")
-
- close(rendered_unit)
-
- if(filename_ptr(1:5) == '/tmp/') then
- call unlink(filename_ptr)
- end if
- deallocate(filename_ptr)
- end if
+ ! Handle the response
+ select case(resp%code)
+ case(GEMINI_CODE_INPUT)
+ call write_input_request(ssl, resp%message)
+
+ case(GEMINI_CODE_REDIRECT)
+ call write_redirect(ssl, resp%url)
+
+ case(GEMINI_CODE_PERMFAIL)
+ call write_failure(ssl)
+
+ case(GEMINI_CODE_SUCCESS)
+ open(newunit=rendered_unit, file=resp%body_filename, status="old", &
+ form="unformatted", iostat=ioerror, access="stream")
+ call write_file(ssl, rendered_unit, resp%body_mimetype)
+ close(rendered_unit)
+
+ end select
+
+ call req%destroy()
+ call resp%destroy()
end subroutine handle_request