aboutsummaryrefslogtreecommitdiff
path: root/captain/captain.f90
blob: 3d406938fc6e2bbfd7a7678397eb7e1132575ceb (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
! 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.

program captain
use captain_db
use config
use logging, only: initialize_log => initialize, shutdown_log => shutdown, write_log, LOG_INFO
use gemini, only: handle_gemini => handle_request 
use web, only: handle_web => handle_request 
implicit none

    integer::mode
    integer, parameter::MODE_GEMINI   = 1, &
                        MODE_CGI_HTML = 2

    call random_seed() ! For possible crypto

    call parse_options()

    call initialize_log(log_filename, loglevel)

    call initialize_db(trim(database_filename))
    
    select case(mode)
        case(MODE_GEMINI)
            call handle_gemini()
        case(MODE_CGI_HTML)
            call handle_web()
    end select
    
    call shutdown_db()
    
    call write_log("Process complete", LOG_INFO)
    
    call shutdown_log()
    
contains

    subroutine usage()
    implicit none
    
        character(len=256)::pname
        
        call get_command_argument(0, pname)
    
        Print *, "Usage: "//trim(pname)//" <options>"
        Print *, " "
        
        Print *, "Options:"
        Print *, "    -h              Display this help"
        Print *, "    -c <configfile> Use the specified config file"
        Print *, "    -g              Operate in Gemini mode"
        Print *, "    -w              Operate in CGI mode (default)"
        Print *, "    --new-admin <username> <password>"
        Print *, "                    Add a new administrator to the system"
        Print *, " "
        Print *, "Config file can also be specified via the environment variables:"
        Print *, "    LEVITATING_CONFIG_CGI     Path to config for CGI mode"
        Print *, "    LEVITATING_CONFIG_GEMINI  Path to config for Gemini mode"
        
    end subroutine usage
    
    subroutine parse_options
    use config
    use m_crypt
    use m_uuid, only: generate_uuid4
    use captain_db, only: new_admin_db
    implicit none
    
        character(len=1024)::option, username, password
        character(len=:), pointer::tmp
        logical::config_loaded
        integer::i

        config_loaded = .false.
        mode = MODE_CGI_HTML
        loglevel = 3

        i = 1
        do while(i <= command_argument_count())
            call get_command_argument(i, option)
        
            if(trim(option) == "-h") then
                call usage()
                stop
            
            else if(trim(option) == "-g") then
                mode = MODE_GEMINI
            
            else if(trim(option) == "-c") then
                i = i + 1
                call get_command_argument(i, option)
                call load_configuration(trim(option))
                config_loaded = .true.
                
            ! This option shouldn't be public, and it just verifies the
            ! m_crypt module works...
            else if(trim(option) == "--hash") then
                i = i + 1
                call get_command_argument(i, option)
                tmp => hash(option)
                Print *, "Hash: "//trim(tmp)
                Print *, "Verify: "//trim(option), verify_hash(trim(option), tmp)
                Print *, "Unverify: "//trim(option)//"X", verify_hash(trim(option)//"X", tmp)
                stop

            ! This option shouldn't be public, and it just verifies passwords
            else if(trim(option) == "--verify") then
            
                if(config_loaded) then
                    call initialize_db(trim(database_filename))
                    i = i + 1
                    call get_command_argument(i, username)
                    
                    i = i + 1
                    call get_command_argument(i, password)
                    
                    if(validate_user_db(trim(username), trim(password))) then
                        Print *, "Password accepted!"
                    else
                        Print *, "REJECTED"
                    end if
                    
                else
                
                    Print *, "Please specify the configuration file first"
                    
                end if
                
                stop

            ! This option also shouldn't be public, and it verifies that
            ! uuids can be generated
            else if(trim(option) == "--uuid") then
                if(.not. config_loaded) then
                    ! Look up a directory for temp files - needed below
                    call get_environment_variable("TEMP", temp_dir)
                end if
                    
                option = generate_uuid4()
                print *, trim(option)
                stop

            else if(trim(option) == "--new-admin") then
            
                ! Config better be loaded by now...
                if(config_loaded) then
                    call initialize_db(trim(database_filename))
                    
                    i = i + 1
                    call get_command_argument(i, username)
                    i = i + 1
                    call get_command_argument(i, password)
                    if(new_admin_db(trim(username), trim(password))) then
                        Print *, "Admin '"//trim(username)//"' added successfully!"
                    else
                        Print *, "Operation failed."
                    end if
                else
                    Print *, "Please specify the configuration file first"
                end if
                stop

            end if
            
            i = i + 1
        end do
        
        if(.not. config_loaded) then
            call get_environment_variable("LEVITATING_CONFIG_CGI", value=option, status=i)
            if(i == 0) then
                call load_configuration(trim(option))
                config_loaded = .true.
                mode = MODE_CGI_HTML
            end if
        end if
        
        if(.not. config_loaded) then
            call get_environment_variable("LEVITATING_CONFIG_GEMINI", value=option, status=i)
            if(i == 0) then
                call load_configuration(trim(option))
                config_loaded = .true.
                mode = MODE_GEMINI
            end if
        end if
        
        ! Assign working directory from command if not specified
        if(.not. config_loaded) then
            Print *, "No configuration file specified"
            stop
        end if
                
    end subroutine parse_options
    
end program captain