aboutsummaryrefslogtreecommitdiff
path: root/captain/external.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/external.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/external.f90')
-rw-r--r--captain/external.f90177
1 files changed, 156 insertions, 21 deletions
diff --git a/captain/external.f90 b/captain/external.f90
index 3ec018f..0aefdf8 100644
--- a/captain/external.f90
+++ b/captain/external.f90
@@ -1,7 +1,6 @@
module external_handling
implicit none
-
contains
function generate_players_gemini() result(res)
@@ -44,53 +43,163 @@ contains
new_line(res(1:1))//"=> /players/add.gmi Add Player"
end function generate_players_gemini
-
- function external_request_gemini(request) result(disk_filename)
+
+ pure function is_input_provided_request(req)
+ use server_response, only: request
+ implicit none
+
+ class(request), intent(in)::req
+ logical::is_input_provided_request
+
+ is_input_provided_request = associated(req%query_string)
+
+ end function is_input_provided_request
+
+ pure function is_input_required_request(req)
+ use server_response, only: request
+ implicit none
+
+ class(request), intent(in)::req
+ logical::is_input_required_request
+
+ is_input_required_request = .false.
+ if(req%location == "/players/add.gmi") then
+ is_input_required_request = .true.
+ end if
+
+ end function is_input_required_request
+
+ function external_input_required_gemini(req) result(resp)
+ use server_response
+ implicit none
+
+ class(request), intent(in)::req
+ type(response)::resp
+
+ resp%code = GEMINI_CODE_INPUT
+
+ if(req%location == "/players/add.gmi") then
+ call resp%set_message("Enter name of new player to add")
+ end if
+
+ end function external_input_required_gemini
+
+ function external_input_request_gemini(req) result(resp)
+ use server_response
+ use captain_db
+ implicit none
+
+ class(request), intent(in)::req
+ type(response)::resp
+
+ if(req%location == "/players/add.gmi") then
+ call add_player_db(req%query_string)
+ resp%code = GEMINI_CODE_REDIRECT
+ call resp%set_url("/players.gmi")
+
+ end if
+
+ end function external_input_request_gemini
+
+ function is_request_static(req)
+ use server_response
+ implicit none
+
+ class(request), intent(in)::req
+ logical::is_request_static
+ character(64)::first
+
+ call req%path_component(1, first)
+
+ is_request_static = ((first == "releases") .or. (first == "uploads"))
+
+ end function is_request_static
+
+ function external_request_static(req) result(resp)
+ use logging, only: write_log
+ use config
+ use utilities
+ use server_response
+ implicit none
+
+ class(request), intent(in)::req
+ type(response)::resp
+ character(64)::category
+ character(256)::filename
+ logical::exists
+
+ resp%temporary_file = .false.
+
+ call req%path_component(1, category)
+ call req%last_component(filename)
+
+ if(category == "releases") then
+ allocate(character(len=(len_trim(release_dir)+len_trim(filename)+1)) :: resp%body_filename)
+ call combine_paths(release_dir, filename, resp%body_filename)
+ else if(category == "uploads") then
+ allocate(character(len=(len_trim(release_dir)+len_trim(filename)+1)) :: resp%body_filename)
+ call combine_paths(release_dir, filename, resp%body_filename)
+ end if
+
+ inquire(file=resp%body_filename, exist=exists)
+ if(.not. exists) then
+ resp%code = GEMINI_CODE_PERMFAIL
+ else
+ resp%code = GEMINI_CODE_SUCCESS
+
+ if(index(filename, ".gmi") /= 0) then
+ resp%body_mimetype = "text/gemini"
+
+ else if(index(filename, ".txt") /= 0) then
+ resp%body_mimetype = "text/plain"
+
+ ! Just a catch-all, whatever...
+ else
+ resp%body_mimetype = "application/octet-stream"
+
+ end if
+ end if
+
+ end function external_request_static
+
+ function external_request_templated(req) result(resp)
use page_template
use config, only: template_filepath, project
use logging, only: write_log
+ use server_response
implicit none
- character(*), intent(in)::request
- character(len=:), pointer::disk_filename
+ class(request), intent(in)::req
+ type(response)::resp
character(1024)::template_file
type(template)::page
character(len=:), pointer::contents
! Open the base template
call template_filepath("index.gmi", template_file)
-
call page%init(trim(template_file))
- if(trim(request) == "/" .or. trim(request) == "/index.gmi") then
+ if(trim(req%location) == "/" .or. trim(req%location) == "/index.gmi") then
call page%assign('title', 'Home')
- else if(trim(request) == "/releases.gmi") then
+ else if(trim(req%location) == "/releases.gmi") then
call page%assign('title', 'Releases')
- else if(trim(request) == "/jobs.gmi") then
+ else if(trim(req%location) == "/jobs.gmi") then
call page%assign('title', 'Jobs')
- else if(trim(request) == "/players.gmi") then
+ else if(trim(req%location) == "/players.gmi") then
call page%assign('title', 'Players')
contents => generate_players_gemini()
call page%assign('contents', contents)
- else if(request(1:9) == '/players/') then
+ else if(req%location(1:9) == '/players/') then
- if(trim(request) == "/players/add.gmi") then
-
- ! Need input!
-
- else
-
- end if
-
- else if(trim(request) == "/about.gmi") then
+ else if(trim(req%location) == "/about.gmi") then
call page%assign('title', 'About')
@@ -104,8 +213,34 @@ contains
call page%render()
- disk_filename => page%output_filename
+ resp%temporary_file = .true.
+ resp%body_filename => page%output_filename
+ resp%body_mimetype = "text/gemini"
+ resp%code = GEMINI_CODE_SUCCESS
+
+ end function external_request_templated
+
+ function external_request_gemini(req) result(resp)
+ use server_response
+ implicit none
+
+ class(request), intent(in)::req
+ type(response)::resp
+
+ if(is_input_provided_request(req)) then
+ resp = external_input_request_gemini(req)
+
+ else if(is_input_required_request(req)) then
+ resp = external_input_required_gemini(req)
+ else if(is_request_static(req)) then
+ resp = external_request_static(req)
+
+ else
+ resp = external_request_templated(req)
+
+ end if
+
end function external_request_gemini
end module external_handling \ No newline at end of file