aboutsummaryrefslogtreecommitdiff
path: root/captain/config.f90
diff options
context:
space:
mode:
authorJeffrey Armstrong <jeff@approximatrix.com>2021-03-27 16:50:20 -0400
committerJeffrey Armstrong <jeff@approximatrix.com>2021-03-27 16:50:20 -0400
commitfd9077056f7f33c60b218636ead0644d42e75a09 (patch)
tree9010b2d5ed8d22fa1e571cdec79f8a6f0c30d66c /captain/config.f90
parent0b8ec300ca4f2f2c3ce09d14ac1eed5478ea6420 (diff)
downloadlevitating-fd9077056f7f33c60b218636ead0644d42e75a09.tar.gz
levitating-fd9077056f7f33c60b218636ead0644d42e75a09.zip
Minor cleanup of the template code. Started on main program handling requests.
Diffstat (limited to 'captain/config.f90')
-rw-r--r--captain/config.f90106
1 files changed, 104 insertions, 2 deletions
diff --git a/captain/config.f90 b/captain/config.f90
index 9daee6b..e66d42f 100644
--- a/captain/config.f90
+++ b/captain/config.f90
@@ -1,18 +1,120 @@
module config
implicit none
+ character(*), parameter::TEMPLATE_DIRECTORY_VARIABLE = "template-directory"
character(1024)::template_directory
+
+ character(*), parameter::DATABASE_VARIABLE = "database"
character(1024)::database_filename
- character(1024)::description_filename
+
+ character(*), parameter::LOGFILE_VARIABLE = "log-filename"
+ character(1024)::log_filename
+
+ character(*), parameter::PROJECT_NAME_VARIABLE = "project"
+ character(32)::project
+
+ character(*), parameter::DESCRIPTION_VARIABLE = "description"
+ character(1024)::description
+
+ character(*), parameter::PUBLIC_CERT_VARIABLE = "public-cert"
+ character(1024)::pubcert
+
+ character(*), parameter::PRIVATE_CERT_VARIABLE = "private-cert"
+ character(1024)::privcert
contains
+ subroutine get_variable(str, v)
+ implicit none
+
+ character(*), intent(in)::str
+ character(*), intent(out)::v
+
+ integer::i
+
+ v = " "
+
+ i = index(str, '=')
+ if(i > 0) then
+ v = adjustl(str(1:i))
+ end if
+
+ end subroutine get_variable
+
+ subroutine get_value(str, v)
+ implicit none
+
+ character(*), intent(in)::str
+ character(*), intent(out)::v
+
+ integer::i,n
+
+ v = " "
+
+ i = index(str, '=')
+ n = len_trim(str)
+ if(i > 0) then
+ v = adjustl(str(i+1:n))
+ end if
+
+ end subroutine get_value
+
+ subroutine assign_config(cvariable, cvalue)
+ implicit none
+
+ character(*), intent(in)::cvariable, cvalue
+
+ if(cvariable == TEMPLATE_DIRECTORY_VARIABLE) then
+ template_directory = cvalue
+
+ else if(cvariable == DATABASE_VARIABLE) then
+ database_filename = cvalue
+
+ else if(cvariable == PROJECT_NAME_VARIABLE) then
+ project = cvalue
+
+ else if(cvariable == DESCRIPTION_VARIABLE) then
+ description = cvalue
+
+ else if(cvariable == PUBLIC_CERT_VARIABLE) then
+ pubcert = cvalue
+
+ else if(cvariable == PRIVATE_CERT_VARIABLE) then
+ privcert = cvalue
+
+ else if(cvariable == LOGFILE_VARIABLE) then
+ log_filename = cvalue
+
+ end if
+
+ end subroutine assign_config
+
subroutine load_configuration(filename)
implicit none
character(*), intent(in)::filename
+ integer::unit_number, istatus
+ character(1024)::line, cvalue
+ character(64)::cvariable
-
+ open(newunit=unit_number, file=trim(filename), status='old', &
+ action="read", iostat=istatus)
+
+ read(unit_number, '(A)', iostat=istatus) line
+ do while(istatus == 0)
+
+ if(len_trim(line) > 0 .and. line(1:1) /= '#') then
+
+ call get_variable(line, cvariable)
+ call get_value(line, cvalue)
+ call assign_config(trim(cvariable), trim(cvalue))
+
+ end if
+
+ read(unit_number, '(A)', iostat=istatus) line
+ end do
+
+ close(unit_number)
end subroutine load_configuration