diff options
Diffstat (limited to 'captain/response.f90')
-rw-r--r-- | captain/response.f90 | 149 |
1 files changed, 142 insertions, 7 deletions
diff --git a/captain/response.f90 b/captain/response.f90 index e172cc1..03d420e 100644 --- a/captain/response.f90 +++ b/captain/response.f90 @@ -25,13 +25,6 @@ use iso_c_binding use query_utilities implicit none - integer, parameter::GEMINI_CODE_INPUT = 10 - integer, parameter::GEMINI_CODE_SUCCESS = 20 - integer, parameter::GEMINI_CODE_REDIRECT = 30 - integer, parameter::GEMINI_CODE_TEMPFAIL = 40 - integer, parameter::GEMINI_CODE_PERMFAIL = 50 - integer, parameter::GEMINI_CODE_BAD_REQUEST = 59 - character(*), parameter::RESPONSE_JSON_OKAY = '{"status": "okay"}' type :: response @@ -55,6 +48,7 @@ implicit none procedure :: destroy => response_destroy procedure :: set_message => response_set_message procedure :: set_url => response_set_url + procedure :: set_gemini_session_url => reponse_set_gemini_session_url procedure :: set_body_contents => response_temp_file_contents procedure :: set_filename => response_set_filename_using_allocation procedure :: set_cookie_cmd => response_set_cookie_cmd @@ -90,6 +84,10 @@ implicit none procedure :: is_get => request_is_get procedure :: is_post => request_is_post procedure :: has_query => request_has_query + procedure :: is_authenticated_user => request_is_authenticated_user + procedure :: set_token => request_set_token + procedure :: remove_first_path_component => request_remove_first_path_component + procedure :: clear_token => request_clear_token end type request @@ -110,6 +108,37 @@ implicit none contains + function gemini_session_link_url(link, session_token) result(res) + implicit none + + character(*), intent(in)::link + character(len=:), pointer, intent(in), optional::session_token + character(len=:), pointer::res + logical::prepend_session + integer::nl + + nl = len_trim(link) + + prepend_session = .false. + if(link(1:1) == "/") then + if(present(session_token)) then + if(associated(session_token)) then + nl = nl + 9 + len_trim(session_token) + prepend_session = .true. + end if + end if + end if + + allocate(character(len=nl)::res) + + if(prepend_session) then + res = "/session-"//trim(session_token)//trim(link) + else + res = link + end if + + end function gemini_session_link_url + subroutine request_init(self, str, server_explicit, protocol_explicit, method, cookiestring) use logging use utilities, only: toupper @@ -269,6 +298,23 @@ contains end function request_component_start_location + function request_is_authenticated_user(self) + use captain_db + implicit none + + class(request), intent(in)::self + logical::request_is_authenticated_user + + request_is_authenticated_user = .false. + if(associated(self%token)) then + request_is_authenticated_user = is_valid_session_db(self%token) + if(request_is_authenticated_user) then + call update_session_db(self%token) + end if + end if + + end function request_is_authenticated_user + subroutine request_component(self, i_component, res) use logging implicit none @@ -414,6 +460,73 @@ contains end function request_has_query + subroutine request_set_token(self, token) + implicit none + + class(request), intent(inout)::self + character(len=*), intent(in)::token + + allocate(character(len=len_trim(token)) :: self%token) + self%token = token + + end subroutine request_set_token + + subroutine request_clear_token(self) + implicit none + + class(request), intent(inout)::self + logical::safe_to_deallocate + + if(associated(self%token)) then + safe_to_deallocate = .not. (associated(self%c%get_value("token"), self%token) .or. & + associated(self%q%get_value("token"), self%token)) + + if(safe_to_deallocate) then + deallocate(self%token) + end if + + self%token => null() + + end if + + end subroutine request_clear_token + + ! This routine is needed if we're stripping session identifiers + ! in Gemini URLs + subroutine request_remove_first_path_component(self) + implicit none + + class(request), intent(inout)::self + character(len=:), pointer::first, newloc + + integer::i, j, n + + i = 1 + if(self%location(1:1) == "/") then + i = i + 1 + end if + + n = len_trim(self%location) + j = index(self%location(i:n), "/") + (i-1) + if(j == 0) then + j = n + end if + + ! First component should be self%location(i:j) + n = n - (j-i+1) + + allocate(character(len=n)::newloc) + if(i > 1) then + newloc(1:1) = self%location(1:1) + end if + + newloc(2:n) = self%location(j+1:len_trim(self%location)) + deallocate(self%location) + self%location => newloc + newloc => null() + + end subroutine request_remove_first_path_component + subroutine request_destroy(self) implicit none @@ -443,6 +556,9 @@ contains deallocate(self%page) end if + ! Needs to happen before we destroy the cookies and query string + call self%clear_token() + call self%q%destroy() call self%c%destroy() @@ -546,6 +662,25 @@ contains end subroutine response_set_url + subroutine reponse_set_gemini_session_url(resp, str, session_token) + !use request_utils, only: gemini_session_link_url + implicit none + + class(response), intent(inout)::resp + character(*), intent(in)::str + character(len=:), pointer, intent(in)::session_token + character(len=:), pointer::session_url + + if(associated(session_token)) then + session_url => gemini_session_link_url(str, session_token) + call resp%set_url(session_url) + deallocate(session_url) + else + call resp%set_url(str) + end if + + end subroutine reponse_set_gemini_session_url + subroutine response_temp_file_contents(resp, str, mimetype) use utilities, only: generate_temporary_filename implicit none |