aboutsummaryrefslogtreecommitdiff
path: root/captain/web.f90
diff options
context:
space:
mode:
Diffstat (limited to 'captain/web.f90')
-rw-r--r--captain/web.f90114
1 files changed, 92 insertions, 22 deletions
diff --git a/captain/web.f90 b/captain/web.f90
index 898551c..b990c1a 100644
--- a/captain/web.f90
+++ b/captain/web.f90
@@ -52,6 +52,24 @@ contains
end function method
+ function request_is_authenticated(req)
+ use captain_db
+ use server_response
+ implicit none
+
+ class(request), intent(in)::req
+ logical::request_is_authenticated
+
+ request_is_authenticated = .false.
+ if(associated(req%token)) then
+ request_is_authenticated = is_valid_session_db(req%token)
+ if(request_is_authenticated) then
+ call update_session_db(req%token)
+ end if
+ end if
+
+ end function request_is_authenticated
+
subroutine handle_basic_template_components(req, page)
use server_response
use page_template
@@ -66,19 +84,12 @@ contains
call page%assign('project', project)
call page%assign('base_url', req%server)
- if(associated(req%token)) then
- if(get_session_auth_db(req%token) > 0) then
-
- call page%assign('user_link_page', "profile")
- call get_session_username_db(req%token, username)
- call page%assign('user_link_text', trim(username))
-
- else
-
- call page%assign('user_link_page', "login")
- call page%assign('user_link_text', "Login")
-
- end if
+ if(request_is_authenticated(req)) then
+
+ call page%assign('user_link_page', "profile")
+ 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('user_link_page', "login")
@@ -90,12 +101,13 @@ contains
subroutine build_request_object(req)
use server_response, only:request
+ use logging
implicit none
type(request), intent(out)::req
- character(len=:), allocatable::url, script_name
+ character(len=:), allocatable::url, script_name, cookie
character(len=4)::method
- integer::url_size
+ integer::url_size, cookie_size
call get_environment_variable("REQUEST_URI", length=url_size)
allocate(character(len=url_size)::url, script_name)
@@ -103,9 +115,21 @@ contains
call get_environment_variable("SCRIPT_NAME", script_name)
call get_environment_variable("REQUEST_METHOD", method)
+
+ call get_environment_variable("HTTP_COOKIE", length=cookie_size)
+ if(cookie_size > 0) then
+ allocate(character(len=cookie_size) :: cookie)
+ call get_environment_variable("HTTP_COOKIE", cookie)
+ call write_log("COOKIE="//cookie, LOG_DEBUG)
+ end if
! If we're in CGI mode, treat the "server" as the script name
- call req%init(url, server_explicit=script_name, protocol_explicit="http", method=method)
+ if(allocated(cookie)) then
+ call req%init(url, server_explicit=script_name, protocol_explicit="http", method=method, cookiestring=cookie)
+ deallocate(cookie)
+ else
+ call req%init(url, server_explicit=script_name, protocol_explicit="http", method=method)
+ end if
deallocate(url)
deallocate(script_name)
@@ -936,7 +960,7 @@ contains
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
- use captain_db, only: scan_instructions_for_db, get_session_auth_db, get_session_username_db
+ use captain_db, only: scan_instructions_for_db, get_session_username_db, destroy_session_db
use utilities, only: build_date
implicit none
@@ -952,6 +976,9 @@ contains
character(128)::job_page_title, username
integer::i
+ logical::authenticated
+
+ authenticated = request_is_authenticated(req)
if(trim(req%location) == "/" .or. &
trim(req%location) == "/index.html" .or. &
@@ -966,7 +993,23 @@ contains
else if(trim(req%location) == "/login.html") then
- template_to_use = "login.html"
+ if(authenticated) then
+ template_to_use = "redirect.html"
+ else
+ template_to_use = "login.html"
+ end if
+
+ else if(trim(req%location) == "/profile.html") then
+
+ if(authenticated) then
+ template_to_use = "profile.html"
+ else
+ template_to_use = "redirect.html"
+ end if
+
+ else if(trim(req%location) == "/logout.html") then
+
+ template_to_use = "redirect.html"
else
@@ -1063,10 +1106,32 @@ contains
else if(trim(first) == "login.html") then
call page%assign('title', 'Login')
- if(associated(req%q%get_value("failed"))) then
- call page%assign('login_message', "Login Failed.")
+ if(authenticated) then
+ call page%assign('destination', 'home.html')
+ else
+ if(associated(req%q%get_value("failed"))) then
+ call page%assign('login_message', "Login Failed.")
+ end if
+ end if
+
+ else if(trim(first) == "profile.html") then
+
+ call page%assign('title', 'User Profile')
+ if(authenticated) then
+ call get_session_username_db(req%token, username)
+ call page%assign('username', username)
+ else
+ call page%assign('destination', 'login.html')
end if
+ else if(trim(first) == "logout.html") then
+
+ call page%assign('title', 'Logout')
+ call page%assign('destination', 'home.html')
+ if(authenticated) then
+ call destroy_session_db(req%token)
+ end if
+
else
call page%assign('title', 'Not Found')
@@ -1150,7 +1215,8 @@ contains
! Determine if logged in
if(validate_user_db(posted%get_value("username"), posted%get_value("password"))) then
- call page%assign('destination', "home.html?token="//create_user_session_db(posted%get_value("username")))
+ call resp%set_cookie("token", create_user_session_db(posted%get_value("username")))
+ call page%assign('destination', "home.html")
else
call page%assign('destination', "login.html?failed=1")
end if
@@ -1220,7 +1286,11 @@ contains
case(HTTP_CODE_SUCCESS)
inquire(file=resp%body_filename, size=response_size)
- call write_response_headers(output_unit, resp%code, response_size, trim(resp%body_mimetype))
+ if(associated(resp%cookiecmd)) then
+ call write_response_headers(output_unit, resp%code, response_size, trim(resp%body_mimetype), resp%cookiecmd)
+ else
+ call write_response_headers(output_unit, resp%code, response_size, trim(resp%body_mimetype))
+ end if
call echo_file_stdout(resp%body_filename)
case(HTTP_CODE_FAILURE)