aboutsummaryrefslogtreecommitdiff
path: root/captain/gemini.f90
diff options
context:
space:
mode:
authorJeffrey Armstrong <jeff@approximatrix.com>2021-03-30 10:52:12 -0400
committerJeffrey Armstrong <jeff@approximatrix.com>2021-03-30 10:52:12 -0400
commitfbfd194941de48affaa92522ceaff97010abc1c2 (patch)
tree9be8f652bfaaeb6bc2e11134275098dec23ce92e /captain/gemini.f90
parentfde763f60465b28d33260479b64d9555abc5bcbb (diff)
downloadlevitating-fbfd194941de48affaa92522ceaff97010abc1c2.tar.gz
levitating-fbfd194941de48affaa92522ceaff97010abc1c2.zip
Fixed outstanding issues in template variable assignment and player content building. Removed unnecessary logging calls.
Diffstat (limited to 'captain/gemini.f90')
-rw-r--r--captain/gemini.f9034
1 files changed, 9 insertions, 25 deletions
diff --git a/captain/gemini.f90 b/captain/gemini.f90
index e3b8be6..0930d17 100644
--- a/captain/gemini.f90
+++ b/captain/gemini.f90
@@ -7,28 +7,6 @@ implicit none
contains
- subroutine simplify_request(full_request, local_request)
- use logging, only: write_log
- implicit none
-
- character(*), intent(in)::full_request
- character(*), intent(out)::local_request
-
- integer::i, j
-
- ! Get the file of interest
- i = index(full_request, "://")
- if(i <= 0) then
- local_request = full_request
- else
- j = index(full_request(i+3:len_trim(full_request)), "/")
- local_request = full_request((i+j+2):len_trim(full_request))
- end if
-
- call write_log("Simplified Local Request: "//trim(local_request))
-
- end subroutine simplify_request
-
subroutine read_request(ssl, req)
use jessl, only: ssl_read
use iso_c_binding
@@ -96,6 +74,7 @@ contains
subroutine write_status(ssl, code, meta)
use iso_c_binding, only: c_ptr, c_carriage_return, c_new_line
use jessl, only: ssl_write
+ use logging
implicit none
type(c_ptr)::ssl
@@ -103,9 +82,9 @@ contains
character(*), intent(in)::meta
character(8)::int_text
+ character(1024)::line
- write(int_text, *) code
-
+ write(int_text, '(I8)') code
call write_string(ssl, trim(adjustl(int_text))//" "//trim(meta)//c_carriage_return//c_new_line)
end subroutine write_status
@@ -124,7 +103,6 @@ contains
integer::buflen, written
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)
@@ -273,8 +251,10 @@ contains
! Do the actual protocol nonsense
call read_request(ssl, text_request)
+ call write_log("Initializing object")
call req%init(text_request)
+ call write_log("Request object created")
if(len(req%location) .ge. 4) then
if(req%location(1:4) == '/api') then
!call handle_api_request(request)
@@ -285,6 +265,7 @@ contains
resp = external_request_gemini(req)
end if
+ call write_log("Handling response")
! Handle the response
select case(resp%code)
case(GEMINI_CODE_INPUT)
@@ -297,9 +278,12 @@ contains
call write_failure(ssl)
case(GEMINI_CODE_SUCCESS)
+ call write_log("Sending '"//trim(resp%body_filename)//"' as "//trim(resp%body_mimetype))
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)
+ call write_log("File written")
+
close(rendered_unit)
end select