aboutsummaryrefslogtreecommitdiff
path: root/captain/external.f90
diff options
context:
space:
mode:
authorJeffrey Armstrong <jeff@approximatrix.com>2021-03-30 15:09:09 -0400
committerJeffrey Armstrong <jeff@approximatrix.com>2021-03-30 15:09:09 -0400
commitc6a3bdfc5e02b9e35b1e0fc5af2d0bf0319681ac (patch)
treee9714d50e2be010557992708ad92aa93522d3daa /captain/external.f90
parent8da227ca130355332fc92935cfbabc87bd0db078 (diff)
downloadlevitating-c6a3bdfc5e02b9e35b1e0fc5af2d0bf0319681ac.tar.gz
levitating-c6a3bdfc5e02b9e35b1e0fc5af2d0bf0319681ac.zip
Added script to scan and load instructions. Instructions now displayed on a page.
Diffstat (limited to 'captain/external.f90')
-rw-r--r--captain/external.f9096
1 files changed, 94 insertions, 2 deletions
diff --git a/captain/external.f90 b/captain/external.f90
index 5e64bab..78195f8 100644
--- a/captain/external.f90
+++ b/captain/external.f90
@@ -49,6 +49,52 @@ contains
end function generate_players_gemini
+ function generate_instructions_gemini() result(res)
+ use captain_db
+ implicit none
+
+ character(len=:), pointer::res
+ character(len=PLAYER_NAME_LENGTH), dimension(:), pointer::instruction_names
+ integer::n, i, nsize
+
+ character(len=3*PLAYER_NAME_LENGTH)::one_player
+
+ n = get_instuctions_count()
+
+ if(n == 0) then
+
+ allocate(character(len=1024) :: res)
+ res = "None Yet"
+
+ else
+
+ instruction_names => get_instruction_names()
+ nsize = 1024
+ do i = 1, size(instruction_names)
+ nsize = nsize + 16 + 2*len_trim(instruction_names(i))
+ end do
+
+ allocate(character(len=nsize) :: res)
+ res = "## Instructions"
+
+ do i = 1, n
+ one_player = "=> /instructions/"//trim(instruction_names(i))//".json "//trim(instruction_names(i))
+ if(i == 1) then
+ res = trim(res)//new_line(res(1:1))//new_line(res(1:1))//trim(one_player)
+ else
+ res = trim(res)//new_line(res(1:1))//trim(one_player)
+ end if
+ end do
+
+ deallocate(instruction_names)
+
+ end if
+
+ res = trim(res)//new_line(res(1:1))//new_line(res(1:1))//"## Management"// &
+ new_line(res(1:1))//"=> /instructions/scan.gmi Scan for Instructions"
+
+ end function generate_instructions_gemini
+
pure function is_input_provided_request(req)
use server_response, only: request
implicit none
@@ -123,10 +169,43 @@ contains
(trim(first) == "uploads") .or. &
(trim(first) == "results") .or. &
(trim(first) == "static") .or. &
- (trim(first) == "favicon.txt"))
+ (trim(first) == "favicon.txt") .or. &
+ (trim(first) == "instructions"))
end function is_request_static
+ function is_redirect_action(req)
+ use server_response
+ implicit none
+
+ class(request), intent(in)::req
+ logical::is_redirect_action
+
+ is_redirect_action = .false.
+ if(req%location == "/instructions/scan.gmi") then
+ is_redirect_action = .true.
+ end if
+
+ end function is_redirect_action
+
+ function external_redirect_action_request_gemini(req) result(resp)
+ use captain_db
+ use server_response
+ use logging
+ implicit none
+
+ class(request), intent(in)::req
+ type(response)::resp
+
+ resp%code = GEMINI_CODE_REDIRECT
+
+ if(req%location == "/instructions/scan.gmi") then
+ call scan_instructions_for_db()
+ call resp%set_url("/instructions.gmi")
+ end if
+
+ end function external_redirect_action_request_gemini
+
function external_request_static(req) result(resp)
use logging, only: write_log
use config
@@ -177,6 +256,9 @@ contains
else if(index(filename, ".txt") /= 0) then
resp%body_mimetype = "text/plain"
+ else if(index(filename, ".json") /= 0) then
+ resp%body_mimetype = "text/plain"
+
! Just a catch-all, whatever...
else
resp%body_mimetype = "application/octet-stream"
@@ -231,6 +313,12 @@ contains
call page%assign('title', 'About')
+ else if(trim(req%location) == "/instructions.gmi") then
+
+ call page%assign('title', 'Build Instructions')
+ contents => generate_instructions_gemini()
+ call page%assign('contents', contents)
+
else
call page%assign('title', 'Not Found')
@@ -259,7 +347,11 @@ contains
class(request), intent(in)::req
type(response)::resp
- if(is_input_provided_request(req)) then
+ if(is_redirect_action(req)) then
+ call write_log("Action request")
+ resp = external_redirect_action_request_gemini(req)
+
+ else if(is_input_provided_request(req)) then
call write_log("Input request")
resp = external_input_request_gemini(req)