aboutsummaryrefslogtreecommitdiff
path: root/captain/web.f90
diff options
context:
space:
mode:
authorJeffrey Armstrong <jeff@approximatrix.com>2021-05-11 20:09:08 -0400
committerJeffrey Armstrong <jeff@approximatrix.com>2021-05-11 20:09:08 -0400
commita25527272916f342875809d7c3606ba0ebd350b4 (patch)
tree4a4767bd07d181509535a2cc397a5a057b3503ef /captain/web.f90
parent0f31824a5e4969d56d88678e05274163be3d8b77 (diff)
downloadlevitating-a25527272916f342875809d7c3606ba0ebd350b4.tar.gz
levitating-a25527272916f342875809d7c3606ba0ebd350b4.zip
Moved some command handling into requtils to share with web and gemini modes. Started work on handling post requests to add players.
Diffstat (limited to 'captain/web.f90')
-rw-r--r--captain/web.f9055
1 files changed, 47 insertions, 8 deletions
diff --git a/captain/web.f90 b/captain/web.f90
index 55f12a0..0f741d8 100644
--- a/captain/web.f90
+++ b/captain/web.f90
@@ -35,15 +35,18 @@ contains
type(request), intent(out)::req
character(len=:), allocatable::url, script_name
+ character(len=4)::method
integer::url_size
call get_environment_variable("REQUEST_URI", length=url_size)
allocate(character(len=url_size)::url, script_name)
call get_environment_variable("REQUEST_URI", url)
call get_environment_variable("SCRIPT_NAME", script_name)
+
+ call get_environment_variable("REQUEST_METHOD", method)
! If we're in CGI mode, treat the "server" as the script name
- call req%init(url, server_explicit=script_name, protocol_explicit="http")
+ call req%init(url, server_explicit=script_name, protocol_explicit="http", method=method)
deallocate(url)
deallocate(script_name)
@@ -193,15 +196,17 @@ contains
end function generate_one_instuction_html
- function generate_instructions_html() result(res)
+ function generate_instructions_html(req) result(res)
use captain_db
+ use server_response, only:request
implicit none
+ type(request)::req
character(len=:), pointer::res
character(len=PLAYER_NAME_LENGTH), dimension(:), pointer::instruction_names
integer::n, i, nsize
- character(len=:), pointer::one_player
+ character(len=:), pointer::one_player, scanlink
n = get_instuctions_count()
@@ -225,6 +230,7 @@ contains
one_player => html_link("instructions/"//trim(instruction_names(i))//".html", &
trim(instruction_names(i)))
res = trim(res)//new_line(' ')//"<li>"//trim(one_player)//"</li>"
+ deallocate(one_player)
end do
res = trim(res)//new_line(' ')//"</ul>"
@@ -233,8 +239,11 @@ contains
end if
- res = trim(res)//new_line(' ')//"<h2>Management</h2>"// &
- new_line(' ')//"coming soon (Scan for Instructions)"
+ res = trim(res)//new_line(' ')//"<h2>Management</h2>"
+
+ scanlink => html_link(req%page//"?scan", "Scan for instructions now")
+ res = trim(res)//new_line(' ')//"<p>"//scanlink//"</p>"
+ deallocate(scanlink)
end function generate_instructions_html
@@ -279,7 +288,8 @@ contains
end if
res = trim(res)//new_line(' ')//"<h2>Management</h2>"// &
- new_line(' ')//"<p>coming soon (add player)</p>"
+ new_line(' ')//'<form action="players/add.html" method="post"><label for="name">Name:</label>'// &
+ '<input name="name" id="name" /><input type="submit" value="Add"/></form>'
end function generate_players_html
@@ -535,7 +545,7 @@ contains
use logging
use server_response, only:request, response
use http, only: HTTP_CODE_SUCCESS, HTTP_CODE_NOTFOUND
- use request_utils, only: get_job_page_title
+ use request_utils, only: get_job_page_title, handle_instruction_command
implicit none
type(request), intent(in)::req
@@ -586,12 +596,22 @@ contains
else if(trim(req%location) == "/instructions.html") then
+ if(associated(req%query_string) .and. len_trim(req%query_string) > 0) then
+ if(trim(req%query_string) == "scan") then
+
+ end if
+ end if
+
call page%assign('title', 'Build Instructions')
- contents => generate_instructions_html()
+ contents => generate_instructions_html(req)
call page%assign('contents', contents)
else if(trim(first) == "instructions") then
+ if(associated(req%query_string) .and. len_trim(req%query_string) > 0) then
+ call handle_instruction_command(req)
+ end if
+
call page%assign('title', 'Build Instructions')
contents => generate_one_instuction_html(req)
call page%assign('contents', contents)
@@ -622,6 +642,22 @@ contains
resp%body_mimetype = "text/html"
end function request_templated
+
+ function handle_post(req) result(resp)
+ use page_template
+ use config, only: template_filepath, project
+ use logging
+ use server_response, only:request, response
+ use http, only: HTTP_CODE_SUCCESS, HTTP_CODE_NOTFOUND
+ use request_utils, only: get_job_page_title, handle_instruction_command
+ implicit none
+
+ type(request), intent(in)::req
+ type(response)::resp
+
+
+
+ end function handle_post
subroutine handle_request()
use server_response, only:request, response
@@ -644,6 +680,9 @@ contains
call write_log("Req static", LOG_INFO)
resp = request_static(req)
+ else if(req%is_post()) then
+ resp = handle_post(req)
+
else
call write_log("Req template", LOG_INFO)
resp = request_templated(req)