aboutsummaryrefslogtreecommitdiff
path: root/captain/security.f90
diff options
context:
space:
mode:
Diffstat (limited to 'captain/security.f90')
-rw-r--r--captain/security.f90107
1 files changed, 107 insertions, 0 deletions
diff --git a/captain/security.f90 b/captain/security.f90
new file mode 100644
index 0000000..2f5fa4c
--- /dev/null
+++ b/captain/security.f90
@@ -0,0 +1,107 @@
+! Copyright (c) 2021 Approximatrix, LLC <support@approximatrix.com>
+!
+! Permission is hereby granted, free of charge, to any person obtaining a copy
+! of this software and associated documentation files (the "Software"), to deal
+! in the Software without restriction, including without limitation the rights
+! to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
+! copies of the Software, and to permit persons to whom the Software is
+! furnished to do so, subject to the following conditions:
+!
+! The above copyright notice and this permission notice shall be included in
+! all copies or substantial portions of the Software.
+!
+! The Software shall be used for Good, not Evil.
+!
+! THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
+! IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
+! FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
+! AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
+! LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
+! OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
+! SOFTWARE.
+
+module security
+implicit none
+
+contains
+
+ function validate_titan_token(token_string, player_name)
+ use captain_db
+ use logging
+ implicit none
+
+ character(*), intent(in)::token_string
+ character(*), intent(in), optional::player_name
+ logical::validate_titan_token
+ character(len=:), pointer::dbtoken, internal_player
+
+ integer::player_id, i, j
+
+ validate_titan_token = .false.
+
+ i = index(token_string, ":")
+ j = len_trim(token_string)
+
+ if(present(player_name)) then
+
+ allocate(character(len=len_trim(player_name)) :: internal_player)
+ internal_player = player_name
+
+ else
+
+ if(i > 0) then
+ allocate(character(len=i-1) :: internal_player)
+ internal_player = token_string(1:i-1)
+ end if
+
+ end if
+
+ if(associated(internal_player)) then
+
+ player_id = get_player_id(internal_player)
+ if(player_id >= 0) then
+
+ if(.not. player_has_token_db(internal_player)) then
+
+ validate_titan_token = .true.
+
+ else
+
+ allocate(character(len=(len_trim(token_string) + 1)) :: dbtoken)
+ dbtoken = " "
+
+ call get_player_token_db(internal_player, dbtoken)
+
+ if(i <= 0) then
+ i = 1
+ else
+ i = i + 1
+ end if
+
+ call write_log("Tokens '"//trim(dbtoken)//"' vs. '"//token_string(i:j)//"'")
+
+ validate_titan_token = (trim(dbtoken) == token_string(i:j))
+
+ deallocate(dbtoken)
+
+ end if
+
+ end if
+
+ if(validate_titan_token) then
+ call write_log("Titan token valid for "//trim(internal_player))
+ else
+ call write_log("Titan token FAILURE for "//trim(internal_player))
+ end if
+
+ deallocate(internal_player)
+
+ else
+
+ call write_log("Titan token did not include a player - REJECTED")
+
+ end if
+
+ end function validate_titan_token
+
+end module security \ No newline at end of file