aboutsummaryrefslogtreecommitdiff
path: root/captain/external.f90
diff options
context:
space:
mode:
authorJeffrey Armstrong <jeff@approximatrix.com>2022-05-06 12:53:08 -0400
committerJeffrey Armstrong <jeff@approximatrix.com>2022-05-06 12:53:08 -0400
commit9917a9882eff675567007194661df57450016c89 (patch)
treee9d81ba6db3ee677a725180ed059cb0981384c34 /captain/external.f90
parentf3b48d0678fe23c8ff4aed8bfdc370b3b8197b9f (diff)
downloadlevitating-9917a9882eff675567007194661df57450016c89.tar.gz
levitating-9917a9882eff675567007194661df57450016c89.zip
Login and session tracking now works via Gemini. Need to restrict operations in Gemini based on request auth levels still.
Diffstat (limited to 'captain/external.f90')
-rw-r--r--captain/external.f90276
1 files changed, 235 insertions, 41 deletions
diff --git a/captain/external.f90 b/captain/external.f90
index 0cdcfdf..4c700ae 100644
--- a/captain/external.f90
+++ b/captain/external.f90
@@ -80,7 +80,8 @@ contains
use server_response
use special_filenames, only: get_task_result_static_filename
use request_utils, only: get_status_utf8, get_player_link => player_link, &
- get_instruction_link => instruction_link
+ get_instruction_link => instruction_link, &
+ build_link
implicit none
type(request), intent(in)::req
@@ -95,7 +96,7 @@ contains
type(task), dimension(:), pointer::tasks
character(32)::task_text, job_text
character(len=:), pointer::task_results_filename
- character(len=:), pointer::player_link, instruction_link
+ character(len=:), pointer::player_link, instruction_link, result_link
res => null()
@@ -135,8 +136,11 @@ contains
write(task_text, '(I8)') i
- res = trim(res)//nl//"=> /results/"//task_results_filename//" "// &
- trim(status)//" - Task "//trim(adjustl(task_text))
+ result_link => build_link("/results/"//task_results_filename, &
+ trim(status)//" - Task "//trim(adjustl(task_text)), &
+ .true., req%token)
+ res = trim(res)//nl//result_link
+ deallocate(result_link)
end do
deallocate(tasks)
@@ -158,6 +162,7 @@ contains
use utilities
use server_response
use config
+ use request_utils, only: build_link
implicit none
type(request), intent(in)::req
@@ -169,6 +174,7 @@ contains
integer::allocation_size, i
character(1)::nl = new_line(' ')
character(4)::folder_icon = char(240)//char(159)//char(147)//char(129)
+ character(len=:), pointer::release_link
if(.not. associated(req%query_string)) then
public_path = "/releases"
@@ -204,10 +210,15 @@ contains
if(trim(public_path) /= "/releases") then
i = index(req%query_string, "/", back=.true.)
if(i > 0) then
- res = trim(res)//nl//"=> /releases.gmi?"//req%query_string(1:(i-1))//" Up a directory"
+ release_link => build_link("/releases.gmi?"//req%query_string(1:(i-1)), &
+ " Up a directory", .true., req%token)
else
- res = trim(res)//nl//"=> /releases.gmi Up a directory"
+ release_link => build_link("/releases.gmi?"//req%query_string(1:(i-1)), &
+ " Up a directory", .true., req%token)
+
end if
+ res = trim(res)//nl//release_link
+ deallocate(release_link)
end if
if(associated(directories)) then
@@ -219,8 +230,13 @@ contains
else
subpath = trim(directories(i))
end if
+
+ release_link => build_link("/releases.gmi?"//trim(subpath), &
+ folder_icon//" "//trim(directories(i)), &
+ .true., req%token)
- res = trim(res)//nl//"=> /releases.gmi?"//trim(subpath)//" "//folder_icon//" "//trim(directories(i))
+ res = trim(res)//nl//release_link
+ deallocate(release_link)
end do
deallocate(directories)
@@ -231,7 +247,9 @@ contains
do i = 1, size(files)
call combine_paths(public_path, trim(files(i)), subpath)
- res = trim(res)//nl//"=> "//trim(subpath)//" "//trim(files(i))
+ release_link => build_link(trim(subpath), trim(files(i)), .true., req%token)
+ res = trim(res)//nl//release_link
+ deallocate(release_link)
end do
deallocate(files)
@@ -240,17 +258,19 @@ contains
end function generate_releases_gemini
- function generate_players_gemini() result(res)
+ function generate_players_gemini(req) result(res)
use captain_db
- use request_utils, only: get_player_status_utf8
+ use request_utils, only: get_player_status_utf8, build_link
+ use server_response, only: request
implicit none
+ type(request), intent(in)::req
character(len=:), pointer::res
character(len=PLAYER_NAME_LENGTH), dimension(:), pointer::players
character(4)::player_status
integer::n, i, nsize
- character(len=3*PLAYER_NAME_LENGTH)::one_player
+ character(len=:), pointer::player_link
n = get_player_count()
if(n == 0) then
@@ -274,27 +294,34 @@ contains
do i = 1, n
player_status = get_player_status_utf8(players(i))
- one_player = "=> /players/"//trim(players(i))//".gmi "//trim(player_status)//" "//trim(players(i))
+ player_link => build_link("/players/"//trim(players(i))//".gmi", &
+ trim(player_status)//" "//trim(players(i)), &
+ .true., req%token)
+
if(i == 1) then
- res = trim(res)//new_line(res(1:1))//new_line(res(1:1))//trim(one_player)
+ res = trim(res)//new_line(res(1:1))//new_line(res(1:1))//player_link
else
- res = trim(res)//new_line(res(1:1))//trim(one_player)
+ res = trim(res)//new_line(res(1:1))//player_link
end if
+ deallocate(player_link)
end do
deallocate(players)
end if
+ player_link => build_link("/players/add.gmi", "Add Player", .true., req%token)
+
res = trim(res)//new_line(res(1:1))//new_line(res(1:1))//"## Management"// &
- new_line(res(1:1))//"=> /players/add.gmi Add Player"
+ new_line(res(1:1))//player_link
+
+ deallocate(player_link)
end function generate_players_gemini
function generate_one_instuction_gemini(req) result(res)
use captain_db
use server_response
- use request_utils, only: get_player_status_utf8
- use request_utils, only: render_jobs_links
+ use request_utils, only: get_player_status_utf8, render_jobs_links, build_link
implicit none
type(request)::req
@@ -307,7 +334,7 @@ contains
character(len=PLAYER_NAME_LENGTH), dimension(:), pointer::all_players
integer::i, j, n_jobs, n_players, nsize
- character(len=:), pointer::job_link_text
+ character(len=:), pointer::job_link_text, raw_link, launch_link, assign_link
character(1)::nl = new_line(' ')
character(PLAYER_NAME_LENGTH)::player_name
character(4)::player_status
@@ -348,7 +375,10 @@ contains
res = nl//"## "//trim(instruction_name)
i = index(req%location, ".gmi", back=.true.)
- res = trim(res)//nl//"=> "//req%location(1:i-1)//".json View Raw"
+
+ raw_link => build_link(req%location(1:i-1)//".json", "View Raw", .true., req%token)
+ res = trim(res)//nl//raw_link
+ deallocate(raw_link)
if(n_players == 0) then
res = trim(res)//nl//nl//"No players currently can run these instructions"
@@ -357,8 +387,13 @@ contains
do i = 1, n_players
call get_player_name(players(i), player_name)
player_status = get_player_status_utf8(players(i))
- res = trim(res)//nl//"=> "//trim(req%location)//"?launch="//trim(player_name)// &
- " "//trim(player_status)//" "//trim(player_name)
+
+ launch_link => build_link(trim(req%location)//"?launch="//trim(player_name), &
+ trim(player_status)//" "//trim(player_name), &
+ .true., req%token)
+
+ res = trim(res)//nl//launch_link
+ deallocate(launch_link)
end do
end if
@@ -380,8 +415,13 @@ contains
cycle
end if
end if
- res = trim(res)//nl//"=> "//trim(req%location)//"?assign="//trim(all_players(i))// &
- " "//trim(all_players(i))
+
+ assign_link => build_link(trim(req%location)//"?assign="//trim(all_players(i)), &
+ trim(all_players(i)), .true., req%token)
+
+ res = trim(res)//nl//assign_link
+
+ deallocate(assign_link)
end do
deallocate(all_players)
end if
@@ -390,22 +430,31 @@ contains
res = trim(res)//nl//nl//"### Remove"//nl//"Remove a player from these instructions"
do i = 1, n_players
call get_player_name(players(i), player_name)
- res = trim(res)//nl//"=> "//trim(req%location)//"?remove="//trim(player_name)// &
- " "//trim(player_name)
+
+ assign_link => build_link(trim(req%location)//"?remove="//trim(player_name), &
+ trim(player_name), .true., req%token)
+
+ res = trim(res)//nl//assign_link
+
+ deallocate(assign_link)
end do
end if
end function generate_one_instuction_gemini
- function generate_instructions_gemini() result(res)
+ function generate_instructions_gemini(req) result(res)
use captain_db
+ use server_response, only: request
+ use request_utils, only: build_link
implicit none
+ class(request), intent(in)::req
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
+ character(len=:), pointer::instruction_link
n = get_instructions_count()
@@ -426,23 +475,73 @@ contains
res = "## Instructions"
do i = 1, n
- one_player = "=> /instructions/"//trim(instruction_names(i))//".gmi "//trim(instruction_names(i))
+
+ instruction_link => build_link("/instructions/"//trim(instruction_names(i))//".gmi", &
+ trim(instruction_names(i)), .true., req%token)
+
if(i == 1) then
- res = trim(res)//new_line(res(1:1))//new_line(res(1:1))//trim(one_player)
+ res = trim(res)//new_line(res(1:1))//new_line(res(1:1))//instruction_link
else
- res = trim(res)//new_line(res(1:1))//trim(one_player)
+ res = trim(res)//new_line(res(1:1))//instruction_link
end if
+
+ deallocate(instruction_link)
end do
deallocate(instruction_names)
end if
+ instruction_link => build_link("/instructions/scan.gmi", "Scan for Instructions", &
+ .true., req%token)
+
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"
+ new_line(res(1:1))//instruction_link
+
+ deallocate(instruction_link)
end function generate_instructions_gemini
+ function generate_profile_gemini(req) result(res)
+ use server_response, only: request
+ use request_utils, only: build_link
+ use captain_db
+ implicit none
+
+ class(request), intent(in)::req
+
+ character(len=:), pointer::res
+ character(len=:), pointer::link
+ character(len=128)::username
+
+ if(.not. associated(req%token)) then
+
+ allocate(character(len=128)::res)
+ res = "Not currently logged in."//new_line(' ')//"=> /login.gmi Login"
+ return
+
+ else if(.not. is_valid_session_db(req%token)) then
+
+ call destroy_session_db(req%token)
+
+ allocate(character(len=128)::res)
+ res = "You need to login again."//new_line(' ')//"=> /login.gmi Login"
+ return
+
+ end if
+
+ allocate(character(len=1024)::res)
+ call get_session_username_db(req%token, username)
+ res = "## "//trim(username)//" Profile"
+
+ link => build_link("/logout.gmi", "Logout", .true., req%token)
+ res = trim(res)//new_line(' ')//link
+ deallocate(link)
+
+ res = trim(res)//new_line(' ')//new_line(' ')//"More to come soon!"
+
+ end function generate_profile_gemini
+
pure function is_input_provided_request(req)
use server_response, only: request
implicit none
@@ -454,15 +553,21 @@ contains
end function is_input_provided_request
- pure function is_input_required_request(req)
+ function is_input_required_request(req)
use server_response, only: request
implicit none
class(request), intent(in)::req
logical::is_input_required_request
+ character(64)::first
+
+ call req%path_component(1, first)
is_input_required_request = .false.
- if(req%location == "/players/add.gmi") then
+ if(req%location == "/players/add.gmi" .or. &
+ req%location == "/login.gmi" .or. &
+ trim(first) == "login") &
+ then
is_input_required_request = .true.
end if
@@ -470,15 +575,25 @@ contains
function external_input_required_gemini(req) result(resp)
use server_response
+ use gemini_codes
implicit none
class(request), intent(in)::req
type(response)::resp
+ character(64)::first
+
+ call req%path_component(1, first)
+
resp%code = GEMINI_CODE_INPUT
if(req%location == "/players/add.gmi") then
call resp%set_message("Enter name of new player to add")
+ else if(req%location == "/login.gmi") then
+ call resp%set_message("Enter username:")
+ else if(trim(first) == "login") then
+ call resp%set_message("Enter password:")
+ resp%code = GEMINI_CODE_INPUT_PW
end if
end function external_input_required_gemini
@@ -487,18 +602,22 @@ contains
use server_response
use captain_db
use request_utils, only: handle_instruction_command
+ use m_uuid, only: UUID_LENGTH
+ use logging
+ use gemini_codes
implicit none
class(request), intent(in)::req
type(response)::resp
- character(64)::first
+ character(64)::first, second
+ character(len=:), pointer::session
call req%path_component(1, first)
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")
+ call resp%set_gemini_session_url("/players.gmi", req%token)
else if(req%location == "/jobs.gmi" .or. req%location == "/releases.gmi") then
! Used for paging (jobs) or subdirs (releases) - send it back
@@ -511,7 +630,28 @@ contains
! Go back to the same location
resp%code = GEMINI_CODE_REDIRECT
call resp%set_url(req%location)
+
+ else if(req%location == "/login.gmi" .and. req%has_query()) then
+
+ resp%code = GEMINI_CODE_REDIRECT
+ call resp%set_url("/login/"//req%query_string//"/password.gmi")
+
+ else if(trim(first) == "login") then
+ call req%path_component(2, second)
+ resp%code = GEMINI_CODE_REDIRECT
+
+ call write_log("Attempting to validate "//trim(second)//":"//trim(req%query_string), LOG_DEBUG)
+
+ if(validate_user_db(trim(second), trim(req%query_string))) then
+ allocate(character(len=UUID_LENGTH)::session)
+ session = create_user_session_db(trim(second))
+ call resp%set_gemini_session_url("/index.gmi", session)
+ deallocate(session)
+ else
+ call resp%set_url("/loginfailed.gmi")
+ end if
+
end if
end function external_input_request_gemini
@@ -524,19 +664,52 @@ contains
logical::is_redirect_action
is_redirect_action = .false.
- if(req%location == "/instructions/scan.gmi") then
+ if(req%location == "instructions/scan.gmi" .or. &
+ req%location == "/logout.gmi") &
+ then
is_redirect_action = .true.
end if
end function is_redirect_action
+ subroutine handle_basic_gemini_template_components(req, page)
+ use server_response
+ use page_template
+ use captain_db
+ use config
+ implicit none
+
+ type(request), intent(in)::req
+ type(template), intent(inout)::page
+ character(len=128)::username
+
+ call page%assign('project', project)
+
+ if(req%is_authenticated_user()) then
+
+ call page%assign("session_flag", "/session-"//req%token)
+
+ call page%assign('user_link_page', "/profile.gmi")
+ call get_session_username_db(req%token, username)
+ call page%assign('user_link_text', achar(240)//achar(159)//achar(152)//achar(128)//" "//trim(username))
+
+ else
+ call page%assign("session_flag", "")
+ call page%assign('user_link_page', "/login.gmi")
+ call page%assign('user_link_text', "Login")
+
+ end if
+
+ end subroutine handle_basic_gemini_template_components
+
function external_redirect_action_request_gemini(req) result(resp)
use captain_db
use server_response
use logging
+ use gemini_codes
implicit none
- class(request), intent(in)::req
+ class(request), intent(inout)::req
type(response)::resp
resp%code = GEMINI_CODE_REDIRECT
@@ -544,6 +717,15 @@ contains
if(req%location == "/instructions/scan.gmi") then
call scan_instructions_for_db()
call resp%set_url("/instructions.gmi")
+
+ else if(req%location == "/logout.gmi") then
+
+ if(associated(req%token)) then
+ call destroy_session_db(req%token)
+ call req%clear_token()
+ end if
+ call resp%set_url("/index.gmi")
+
end if
end function external_redirect_action_request_gemini
@@ -555,6 +737,7 @@ contains
use server_response
use request_utils, only: get_job_page_title
use utilities, only: build_date
+ use gemini_codes
implicit none
class(request), intent(in)::req
@@ -599,7 +782,7 @@ contains
else if(trim(req%location) == "/players.gmi") then
call page%assign('title', 'Players')
- contents => generate_players_gemini()
+ contents => generate_players_gemini(req)
call page%assign('contents', contents)
else if(req%location(1:9) == '/players/') then
@@ -612,7 +795,7 @@ contains
else if(trim(req%location) == "/instructions.gmi") then
call page%assign('title', 'Build Instructions')
- contents => generate_instructions_gemini()
+ contents => generate_instructions_gemini(req)
call page%assign('contents', contents)
else if(trim(first) == "instructions") then
@@ -628,14 +811,24 @@ contains
contents => generate_one_job_gemini(req)
call page%assign('contents', contents)
+ else if(req%location == "/profile.gmi") then
+
+ call page%assign('title', "User Profile")
+ contents => generate_profile_gemini(req)
+ call page%assign('contents', contents)
+
+ else if(req%location == "/loginfailed.gmi") then
+
+ call page%assign('title', "Login Failed")
+ call page%assign("contents", "Bad username and/or password.")
+
else
call page%assign('title', 'Not Found')
end if
- call page%assign('project', project)
-
+ call handle_basic_gemini_template_components(req, page)
call write_log("Rendering page for "//req%location)
call page%render()
@@ -654,7 +847,7 @@ contains
use request_utils, only: is_request_static, request_static
implicit none
- class(request), intent(in)::req
+ class(request), intent(inout)::req ! inout for logout actions, unfortunately...
type(response)::resp
if(is_redirect_action(req)) then
@@ -687,6 +880,7 @@ contains
use query_utilities
use security
use logging
+ use gemini_codes
implicit none
type(titan_request), intent(in)::req