aboutsummaryrefslogtreecommitdiff
path: root/captain/db.f90
blob: c61ffc729b4e1903e6300fb2fe18a70993eb4a79 (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
module captain_db
use sqlite
implicit none
    
    integer, parameter::PLAYER_NAME_LENGTH = 128
    integer, parameter::FILENAME_NAME_LENGTH = 1024
    
    character(1024)::database_file
    type(c_ptr)::db
    
    type :: job
    
        integer::id
        integer::instruction
        integer::player
        integer::status
        character(32)::time
        
    end type
    
contains

    subroutine initialize_db(filename)
    use logging
    implicit none
    
        character(*), intent(in)::filename
        logical::exists
        
        inquire(file=filename, exist=exists)
        if(.not. exists) then
            call write_log("Database does not exist, exiting")
            call shutdown()
            stop
        end if
        
        if(sqlite3_open(filename, db) == SQLITE_OK) then
            database_file = filename
        else
            Print *, "ERROR: Could not open db"
            stop
        end if
        
    end subroutine initialize_db
    
    subroutine shutdown_db()
    implicit none
    
        integer::i
    
        i = sqlite3_close(db)
        
    end subroutine shutdown_db
    
    subroutine add_player_db(name, token)
    implicit none
    
        character(*), intent(in)::name
        character(*), intent(in), optional::token
        type(sqlite3_stmt)::stmt
        
        character(64)::my_token
        
        if(present(token)) then
            my_token = token
        else
            my_token = "None"
        end if

        if(stmt%prepare(db, "INSERT INTO players(name, token) VALUES(?, ?)") == SQLITE_OK) then
            if(stmt%bind_text(1, name) == SQLITE_OK .and. stmt%bind_text(2, my_token) == SQLITE_OK) then
                call stmt%step_now()
            end if
        end if
        call stmt%finalize()
    
    end subroutine add_player_db
    
    subroutine update_player_token_db(name, token)
    implicit none
    
        character(*), intent(in)::name
        character(*), intent(in)::token
        type(sqlite3_stmt)::stmt
        
        if(stmt%prepare(db, "UPDATE players SET token=? WHERE name=?") == SQLITE_OK) then
            if(stmt%bind_text(2, name) == SQLITE_OK .and. stmt%bind_text(1, token) == SQLITE_OK) then
                call stmt%step_now()
            end if
        end if
        call stmt%finalize()
    
    end subroutine update_player_token_db
    
    subroutine remove_player_db(name)
    implicit none
    
        character(*), intent(in)::name
        type(sqlite3_stmt)::stmt
        
        if(stmt%prepare(db, "DELETE FROM players WHERE name=?") == SQLITE_OK) then
            if(stmt%bind_text(1, name) == SQLITE_OK) then
                call stmt%step_now()
            end if
        end if
        call stmt%finalize()
    
    end subroutine remove_player_db
    
    function get_player_count()
    implicit none
        
        type(sqlite3_stmt)::stmt
        integer::get_player_count
        
        get_player_count = 0
        if(stmt%prepare(db, "SELECT COUNT(*) FROM players") == SQLITE_OK) then
            if(stmt%step() == SQLITE_ROW) then
                get_player_count = stmt%column_int(0)
            end if
        end if
        call stmt%finalize()
        
    end function get_player_count
    
    function get_player_names() result(res)
    implicit none
        
        type(sqlite3_stmt)::stmt
        character(len=PLAYER_NAME_LENGTH), dimension(:), pointer::res
        integer::i,n
        
        n = get_player_count()
        if(n > 0) then
            allocate(res(n))
            if(stmt%prepare(db, "SELECT name FROM players ORDER BY name") == SQLITE_OK) then
                i = 1
                do while(stmt%step() == SQLITE_ROW .and. i <= n) 
                    call stmt%column_text(0, res(i))
                    i = i + 1
                end do
            end if
            call stmt%finalize()
            
        end if
        
    end function get_player_names
    
    function get_instuctions_count()
    implicit none
        
        type(sqlite3_stmt)::stmt
        integer::get_instuctions_count
        
        get_instuctions_count = 0
        if(stmt%prepare(db, "SELECT COUNT(*) FROM instructions") == SQLITE_OK) then
            if(stmt%step() == SQLITE_ROW) then
                get_instuctions_count = stmt%column_int(0)
            end if
        end if
        call stmt%finalize()
        
    end function get_instuctions_count
    
    function get_instruction_names() result(res)
    implicit none
        
        type(sqlite3_stmt)::stmt
        character(len=PLAYER_NAME_LENGTH), dimension(:), pointer::res
        integer::i,n
        
        n = get_instuctions_count()
        if(n > 0) then
            allocate(res(n))
            if(stmt%prepare(db, "SELECT name FROM instructions ORDER BY name") == SQLITE_OK) then
                i = 1
                do while(stmt%step() == SQLITE_ROW .and. i <= n) 
                    call stmt%column_text(0, res(i))
                    i = i + 1
                end do
            end if
            call stmt%finalize()
            
        end if
        
    end function get_instruction_names
    
    subroutine scan_instructions_for_db()
    use config
    use utilities
    use logging
    implicit none
        
        character(len=2048)::cmdline
        
        call combine_paths(script_dir, "scan_instructions.sh", cmdline)
        cmdline = trim(cmdline)//" "//trim(database_file)//" "//trim(instructions_dir)//" 1>/dev/null 2>/dev/null"
        
        call write_log("Scan Command: "//trim(cmdline))
        call execute_command_line(trim(cmdline), wait=.true.)
        
    end subroutine scan_instructions_for_db
    
end module captain_db