aboutsummaryrefslogtreecommitdiff
path: root/captain/config.f90
diff options
context:
space:
mode:
Diffstat (limited to 'captain/config.f90')
-rw-r--r--captain/config.f9092
1 files changed, 92 insertions, 0 deletions
diff --git a/captain/config.f90 b/captain/config.f90
index 509c489..2d67adf 100644
--- a/captain/config.f90
+++ b/captain/config.f90
@@ -71,6 +71,24 @@ implicit none
character(*), parameter::SALT_VARIABLE = "security-salt"
character(1024)::app_salt
+ character(*), parameter::PERMISSIONS_FILE_VARIABLE = "permissions_file"
+ character(1024)::perm_filename
+
+ integer, parameter::MAX_PERMISSIONS = 16
+
+ type::permissions
+ character(len=40), dimension(MAX_PERMISSIONS)::k
+ integer, dimension(MAX_PERMISSIONS)::v
+
+ contains
+
+ procedure :: load => load_permissions
+ procedure :: get => get_permission
+
+ end type permissions
+
+ type(permissions)::global_permissions
+
contains
subroutine get_variable(str, v)
@@ -162,6 +180,9 @@ contains
else if(cvariable == SALT_VARIABLE) then
app_salt = trim(cvalue)
+
+ else if(cvariable == PERMISSIONS_FILE_VARIABLE) then
+ perm_filename = trim(cvalue)
end if
@@ -174,6 +195,7 @@ contains
integer::unit_number, istatus
character(1024)::line, cvalue
character(64)::cvariable
+ integer::i
open(newunit=unit_number, file=trim(filename), status='old', &
action="read", iostat=istatus)
@@ -195,6 +217,16 @@ contains
close(unit_number)
+ if(len_trim(perm_filename) > 0) then
+ if(perm_filename(1:1) /= "/") then
+ i = index(filename, "/", back=.true.)
+ if(i > 1) then
+ perm_filename = filename(1:i)//trim(perm_filename)
+ end if
+ end if
+ call global_permissions%load(perm_filename)
+ end if
+
end subroutine load_configuration
subroutine template_filepath(x, res)
@@ -207,5 +239,65 @@ contains
call combine_paths(template_directory, x, res)
end subroutine template_filepath
+
+ subroutine load_permissions(self, filename)
+ implicit none
+
+ class(permissions), intent(out)::self
+ character(*), intent(in)::filename
+
+ integer::unit_number, istatus
+ character(1024)::line, cvalue
+ character(64)::cvariable
+ integer::i
+
+ self%k = " "
+
+ open(newunit=unit_number, file=trim(filename), status='old', &
+ action="read", iostat=istatus)
+
+ i = 1
+
+ read(unit_number, '(A)', iostat=istatus) line
+ do while(istatus == 0 .and. i <= MAX_PERMISSIONS)
+
+ if(len_trim(line) > 0 .and. line(1:1) /= '#') then
+
+ call get_variable(line, cvariable)
+ call get_value(line, cvalue)
+
+ self%k(i) = cvariable
+ read(cvalue, *, iostat=istatus) self%v(i)
+
+ i = i + 1
+ end if
+
+ read(unit_number, '(A)', iostat=istatus) line
+ end do
+
+ close(unit_number)
+
+ end subroutine load_permissions
+
+ pure function get_permission(self, key)
+ use auth_levels, only: AUTH_ADMIN_USER
+ implicit none
+
+ class(permissions), intent(in)::self
+ character(len=*), intent(in)::key
+ integer::get_permission
+
+ integer::i
+
+ get_permission = AUTH_ADMIN_USER
+
+ do i = 1, MAX_PERMISSIONS
+ if(trim(self%k(i)) == trim(key)) then
+ get_permission = self%v(i)
+ exit
+ end if
+ end do
+
+ end function get_permission
end module config