! Copyright (c) 2021 Approximatrix, LLC ! ! 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 config implicit none character(*), parameter::TEMPLATE_DIRECTORY_VARIABLE = "template-directory" character(1024)::template_directory character(*), parameter::DATABASE_VARIABLE = "database" character(1024)::database_filename character(*), parameter::LOGFILE_VARIABLE = "log-filename" character(1024)::log_filename character(*), parameter::LOGLEVEL_VARIABLE = "log-level" integer::loglevel = 3 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 character(*), parameter::RELEASE_DIRECTORY_VARIABLE = "release-directory" character(1024)::release_dir character(*), parameter::UPLOAD_DIRECTORY_VARIABLE = "upload-directory" character(1024)::upload_dir character(*), parameter::RESULTS_DIRECTORY_VARIABLE = "results-directory" character(1024)::results_dir character(*), parameter::STATIC_DIRECTORY_VARIABLE = "static-directory" character(1024)::static_dir character(*), parameter::INSTRUCTIONS_DIRECTORY_VARIABLE = "instructions-directory" character(1024)::instructions_dir character(*), parameter::SCRIPT_DIRECTORY_VARIABLE = "script-directory" character(1024)::script_dir character(*), parameter::TEMP_DIRECTORY_VARIABLE = "temp-directory" character(1024)::temp_dir = "/tmp" character(*), parameter::SALT_VARIABLE = "security-salt" character(1024)::app_salt 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 i = i - 1 ! Remove the equal sign 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) use utilities, only: set_temporary_directory 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 else if(cvariable == RELEASE_DIRECTORY_VARIABLE) then release_dir = cvalue else if(cvariable == UPLOAD_DIRECTORY_VARIABLE) then upload_dir = cvalue else if(cvariable == RESULTS_DIRECTORY_VARIABLE) then results_dir = cvalue else if(cvariable == STATIC_DIRECTORY_VARIABLE) then static_dir = cvalue else if(cvariable == SCRIPT_DIRECTORY_VARIABLE) then script_dir = cvalue else if(cvariable == INSTRUCTIONS_DIRECTORY_VARIABLE) then instructions_dir = cvalue else if(cvariable == LOGLEVEL_VARIABLE) then read(cvalue, '(I3)') loglevel else if(cvariable == TEMP_DIRECTORY_VARIABLE) then call set_temporary_directory(cvalue) else if(cvariable == SALT_VARIABLE) then app_salt = trim(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 subroutine template_filepath(x, res) use utilities, only: combine_paths implicit none character(*), intent(in)::x character(*), intent(out)::res call combine_paths(template_directory, x, res) end subroutine template_filepath end module config