aboutsummaryrefslogtreecommitdiff
path: root/captain/web.f90
diff options
context:
space:
mode:
Diffstat (limited to 'captain/web.f90')
-rw-r--r--captain/web.f90226
1 files changed, 140 insertions, 86 deletions
diff --git a/captain/web.f90 b/captain/web.f90
index b990c1a..9d8fc3c 100644
--- a/captain/web.f90
+++ b/captain/web.f90
@@ -70,6 +70,17 @@ contains
end function request_is_authenticated
+ subroutine echo_error_stdout(error_code)
+ implicit none
+
+ integer, intent(in)::error_code
+
+ Print *, "<html><head><title>Falling...</title></head><body><p>An Error Occurred:"
+ Print *, error_code
+ Print *, "</p></body></html>"
+
+ end subroutine echo_error_stdout
+
subroutine handle_basic_template_components(req, page)
use server_response
use page_template
@@ -151,6 +162,7 @@ contains
use captain_db
use server_response
use request_utils, only: get_player_status_utf8, render_jobs_links, generate_simple_pager
+ use config, only: global_permissions
implicit none
type(request)::req
@@ -219,14 +231,17 @@ contains
res = "<h2>"//trim(instruction_name)//"</h2>"
- one_link => html_link(trim(instruction_name)//".json", &
- "View Raw")
- res = trim(res)//nl//"<p><em>"//one_link//"</em></p>"
- deallocate(one_link)
+ if(req%auth_level >= global_permissions%get("view-raw-instructions")) then
+ one_link => html_link(trim(instruction_name)//".json", &
+ "View Raw")
+ res = trim(res)//nl//"<p><em>"//one_link//"</em></p>"
+ deallocate(one_link)
+ end if
if(n_players == 0) then
res = trim(res)//nl//"<p>No players currently can run these instructions</p>"
- else
+
+ else if(req%auth_level >= global_permissions%get("launch-job")) then
res = trim(res)//nl//"<h3>Launch Now</h3>"//nl//"<ul>"
do i = 1, n_players
@@ -260,39 +275,41 @@ contains
end if
- all_players => get_player_names()
- if(associated(all_players)) then
- res = trim(res)//nl//"<h3>Assign</h3>"//nl//"<p>Assign a player to these instructions</p>"//nl//"<ul>"
- do i = 1, size(all_players)
- if(n_players > 0) then
- j = get_player_id(all_players(i))
- if(any(j == players)) then
- cycle
+ if(req%auth_level >= global_permissions%get("assign-instructions")) then
+ all_players => get_player_names()
+ if(associated(all_players)) then
+ res = trim(res)//nl//"<h3>Assign</h3>"//nl//"<p>Assign a player to these instructions</p>"//nl//"<ul>"
+ do i = 1, size(all_players)
+ if(n_players > 0) then
+ j = get_player_id(all_players(i))
+ if(any(j == players)) then
+ cycle
+ end if
end if
- end if
-
- one_link => html_link(req%page//"?assign="//trim(all_players(i)), &
- trim(all_players(i)))
-
- res = trim(res)//nl//"<li>"//one_link//"</li>"
- deallocate(one_link)
- end do
- res = trim(res)//nl//"</ul>"
- deallocate(all_players)
- end if
-
- if(n_players > 0) then
- res = trim(res)//nl//"<h3>Remove</h3>"//nl//"<p>Remove a player from these instructions</p>"//nl//"<ul>"
- do i = 1, n_players
- call get_player_name(players(i), player_name)
-
- one_link => html_link(req%page//"?remove="//trim(player_name), &
- trim(player_name))
-
- res = trim(res)//nl//"<li>"//one_link//"</li>"
- deallocate(one_link)
- end do
- res = trim(res)//nl//"</ul>"
+
+ one_link => html_link(req%page//"?assign="//trim(all_players(i)), &
+ trim(all_players(i)))
+
+ res = trim(res)//nl//"<li>"//one_link//"</li>"
+ deallocate(one_link)
+ end do
+ res = trim(res)//nl//"</ul>"
+ deallocate(all_players)
+ end if
+
+ if(n_players > 0) then
+ res = trim(res)//nl//"<h3>Remove</h3>"//nl//"<p>Remove a player from these instructions</p>"//nl//"<ul>"
+ do i = 1, n_players
+ call get_player_name(players(i), player_name)
+
+ one_link => html_link(req%page//"?remove="//trim(player_name), &
+ trim(player_name))
+
+ res = trim(res)//nl//"<li>"//one_link//"</li>"
+ deallocate(one_link)
+ end do
+ res = trim(res)//nl//"</ul>"
+ end if
end if
end function generate_one_instuction_html
@@ -300,6 +317,7 @@ contains
function generate_instructions_html(req) result(res)
use captain_db
use server_response, only:request
+ use config, only: global_permissions
implicit none
type(request)::req
@@ -340,17 +358,20 @@ contains
end if
- 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)
+ if(req%auth_level >= global_permissions%get("scan-instructions")) then
+ 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 if
end function generate_instructions_html
function generate_groups_html(req) result(res)
use captain_db
use server_response, only:request
+ use config, only: global_permissions
implicit none
type(request)::req
@@ -389,11 +410,13 @@ contains
end if
- res = trim(res)//new_line(' ')//"<h2>Management</h2>"
-
- res = trim(res)//new_line(' ')// &
- '<form action="groups/add.html" method="POST"><label for="name">Name:</label>'// &
- '<input name="name" id="name" /><input type="submit" value="Add"/></form>'
+ if(req%auth_level >= global_permissions%get("add-groups")) then
+ res = trim(res)//new_line(' ')//"<h2>Management</h2>"
+
+ res = trim(res)//new_line(' ')// &
+ '<form action="groups/add.html" method="POST"><label for="name">Name:</label>'// &
+ '<input name="name" id="name" /><input type="submit" value="Add"/></form>'
+ end if
end function generate_groups_html
@@ -404,6 +427,7 @@ contains
use query_utilities
use logging
use remote_launch, only: launch_group
+ use config, only: global_permissions
implicit none
type(request)::req
@@ -437,7 +461,7 @@ contains
call q%init(req%query_string)
qreq => q%get_value("add")
- if(associated(qreq)) then
+ if(associated(qreq) .and. req%auth_level >= global_permissions%get("add-groups")) then
call write_log("ADD: "//trim(qreq))
@@ -454,7 +478,7 @@ contains
qreq => q%get_value("delete")
- if(associated(qreq)) then
+ if(associated(qreq) .and. req%auth_level >= global_permissions%get("modify-groups")) then
i = index(qreq, ',')
player_name = qreq(i+1:len(qreq))
@@ -465,12 +489,12 @@ contains
call remove_entry_from_group_db(id, i, j)
- else if(trim(req%query_string) == "launch") then
+ else if(trim(req%query_string) == "launch" .and. req%auth_level >= global_permissions%get("launch-job")) then
call launch_group(id)
write(launch_msg, '(I4, 1X, A13)') get_group_entries_count_db(id), "jobs launched"
- else if(trim(req%query_string) == "destroy") then
+ else if(trim(req%query_string) == "destroy" .and. req%auth_level >= global_permissions%get("modify-groups")) then
call delete_group_db(id)
@@ -511,15 +535,22 @@ contains
one_link => html_link("../instructions/"//trim(instruction_name)//".html", trim(instruction_name))
play_link => html_link("../players/"//trim(player_name)//".html", trim(player_name))
- delete_link => html_link(trim(group_name)//".html?delete="// &
- trim(instruction_name)//","//trim(player_name), &
- "<em>Remove</em>")
- res = trim(res)//new_line(' ')//"<li>"//one_link//" on "//play_link//" - "//delete_link//"</li>"
+
+ res = trim(res)//new_line(' ')//"<li>"//one_link//" on "//play_link
+
+ if(req%auth_level >= global_permissions%get("modify-groups")) then
+ delete_link => html_link(trim(group_name)//".html?delete="// &
+ trim(instruction_name)//","//trim(player_name), &
+ "<em>Remove</em>")
+ res = trim(res)//" - "//delete_link
+ deallocate(delete_link)
+ end if
+
+ res = trim(res)//"</li>"
deallocate(one_link)
deallocate(play_link)
- deallocate(delete_link)
end do
@@ -527,7 +558,7 @@ contains
end if
- if(n_instructions_total > 0) then
+ if(n_instructions_total > 0 .and. req%auth_level >= global_permissions%get("modify-groups")) then
res = trim(res)//new_line(' ')//"<h3>Add Instructions</h3>"
@@ -559,16 +590,22 @@ contains
end if
end if
- res = trim(res)//new_line(' ')//'<h3>Destroy This Group</h3>'//new_line(' ')// &
- '<p><a href="'//req%page//'?destroy">&#x1f4a3; Destroy</a></p>'//new_line(' ')// &
- '<p><em>This operation will not destroy any instructions</em></p>'
+ if(req%auth_level >= global_permissions%get("modify-groups")) then
+ res = trim(res)//new_line(' ')//'<h3>Destroy This Group</h3>'//new_line(' ')// &
+ '<p><a href="'//req%page//'?destroy">&#x1f4a3; Destroy</a></p>'//new_line(' ')// &
+ '<p><em>This operation will not destroy any instructions</em></p>'
+ end if
end function generate_one_group_html
- function generate_players_html() result(res)
+ function generate_players_html(req) result(res)
use captain_db
use request_utils, only: get_status_utf8
+ use server_response, only: request
+ use config, only: global_permissions
implicit none
+
+ type(request), intent(in)::req
character(len=:), pointer::res
character(len=PLAYER_NAME_LENGTH), dimension(:), pointer::players
@@ -619,9 +656,11 @@ contains
deallocate(players)
end if
- res = trim(res)//new_line(' ')//"<h2>Management</h2>"// &
- 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>'
+ if(req%auth_level >= global_permissions%get("add-players")) then
+ res = trim(res)//new_line(' ')//"<h2>Management</h2>"// &
+ 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 if
end function generate_players_html
@@ -629,6 +668,7 @@ contains
use captain_db
use server_response
use request_utils
+ use config, only: global_permissions
implicit none
type(request), intent(in)::req
@@ -683,24 +723,26 @@ contains
res = trim(res)//"<p>None Yet</p>"
end if
- ! Token assignment
- res = trim(res)//new_line(' ')//"<h3>Security</h3>"//new_line(' ')//"<p>"
-
- if(player_has_token_db(trim(player_name))) then
- res = trim(res)//"Player currently has a token assigned."
- else
- res = trim(res)//"<em>Player is insecure! Please assign a token!</em>"
+ if(req%auth_level >= global_permissions%get("modify-players")) then
+ ! Token assignment
+ res = trim(res)//new_line(' ')//"<h3>Security</h3>"//new_line(' ')//"<p>"
+
+ if(player_has_token_db(trim(player_name))) then
+ res = trim(res)//"Player currently has a token assigned."
+ else
+ res = trim(res)//"<em>Player is insecure! Please assign a token!</em>"
+ end if
+
+ res = trim(res)//"</p>"
+
+ res = trim(res)//new_line(' ')// &
+ '<form action="assign_token.html" method="POST">'//new_line(' ')// &
+ '<label for="token">Token:</label>'// &
+ '<input name="token" id="token" />'//new_line(' ')// &
+ '<input type="hidden" name="player" id="player" value="'//trim(player_name)//'"/>'//new_line(' ')// &
+ '<input type="submit" value="Set"/></form>'
end if
- res = trim(res)//"</p>"
-
- res = trim(res)//new_line(' ')// &
- '<form action="assign_token.html" method="POST">'//new_line(' ')// &
- '<label for="token">Token:</label>'// &
- '<input name="token" id="token" />'//new_line(' ')// &
- '<input type="hidden" name="player" id="player" value="'//trim(player_name)//'"/>'//new_line(' ')// &
- '<input type="submit" value="Set"/></form>'
-
end function generate_one_player_html
function generate_one_job_html(req) result(res)
@@ -827,6 +869,17 @@ contains
res => null()
+ ! Auth check
+ if(req%auth_level < global_permissions%get("access-releases")) then
+ allocate(character(len=64)::res)
+ if(req%auth_level == 0) then
+ res = "Login required."
+ else
+ res = "Unacceptable permissions"
+ end if
+ return
+ end if
+
! Easy safety check - no relative paths
if(index(local_path, '..') > 0) then
allocate(character(len=64)::res)
@@ -1045,7 +1098,7 @@ contains
else if(trim(req%location) == "/players.html") then
call page%assign('title', 'Players')
- contents => generate_players_html()
+ contents => generate_players_html(req)
call page%assign('contents', contents)
else if(req%location(1:9) == '/players/') then
@@ -1155,7 +1208,7 @@ contains
use captain_db, only: add_player_db, add_group_db, update_player_token_db, create_user_session_db, &
validate_user_db
use page_template
- use config, only: template_filepath
+ use config, only: template_filepath, global_permissions
use logging
use server_response, only:request, response
use http, only: HTTP_CODE_FAILURE, HTTP_CODE_SUCCESS
@@ -1187,12 +1240,12 @@ contains
call req%path_component(2, second)
! Add a player
- if(trim(second) == "add.html") then
+ if(trim(second) == "add.html" .and. req%auth_level >= global_permissions%get("add-players")) then
call add_player_db(posted%get_value("name"))
call page%assign('destination', 'players.html')
- else if(trim(second) == "assign_token.html") then
+ else if(trim(second) == "assign_token.html" .and. req%auth_level >= global_permissions%get("modify-players")) then
call update_player_token_db(posted%get_value("player"), posted%get_value("token"))
call page%assign('destination', "players/"//posted%get_value("player")//".html")
@@ -1204,7 +1257,7 @@ contains
call req%path_component(2, second)
! Add a group
- if(trim(second) == "add.html") then
+ if(trim(second) == "add.html" .and. req%auth_level >= global_permissions%get("add-groups")) then
call add_group_db(posted%get_value("name"))
call page%assign('destination', 'groups.html')
@@ -1293,8 +1346,9 @@ contains
end if
call echo_file_stdout(resp%body_filename)
- case(HTTP_CODE_FAILURE)
+ case default
call write_log("Failure reported for location: "//trim(req%location), LOG_NORMAL)
+ call echo_error_stdout(resp%code)
! Need some more...
end select