aboutsummaryrefslogtreecommitdiff
path: root/captain/db.f90
blob: 1060dbca2d06b7423afb9d1e74d27793f511b416 (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
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
module captain_db
use sqlite
implicit none
    
    integer, parameter::PLAYER_NAME_LENGTH = 128
    integer, parameter::FILENAME_NAME_LENGTH = 1024
    
    integer, parameter::JOB_STATUS_SUCCESS = 1
    integer, parameter::JOB_STATUS_FAILURE = 2
    integer, parameter::JOB_STATUS_WORKING = 3
    
    integer, parameter::PLAYER_STATUS_BUSY = JOB_STATUS_WORKING
    integer, parameter::PLAYER_STATUS_IDLE = 100
    
    character(1024)::database_file
    type(c_ptr)::db
    
    type :: job
    
        integer::id
        integer::instruction
        integer::player
        integer::status
        character(32)::time
        
    end type
    
    interface is_player_busy
        module procedure is_player_busy_by_id
        module procedure is_player_busy_by_name
    end interface is_player_busy
    
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
    
    function get_jobs_count()
    implicit none

        type(sqlite3_stmt)::stmt
        integer::get_jobs_count
        
        get_jobs_count = 0
        if(stmt%prepare(db, "SELECT COUNT(*) FROM jobs") == SQLITE_OK) then
            if(stmt%step() == SQLITE_ROW) then
                get_jobs_count = stmt%column_int(0)
            end if
        end if
        call stmt%finalize()
    
    end function get_jobs_count
    
    subroutine get_player_name(id, str)
    implicit none
    
        integer, intent(in)::id
        character(*), intent(out)::str
        
        type(sqlite3_stmt)::stmt

        str = " "

        if(stmt%prepare(db, "SELECT name FROM players WHERE id=?") == SQLITE_OK) then
            if(stmt%bind_int(1, id) == SQLITE_OK) then
                if(stmt%step() == SQLITE_ROW) then
                    call stmt%column_text(0,str)
                end if
            end if
        end if
        call stmt%finalize()
        
    end subroutine get_player_name
    
    function get_player_id(name)
    implicit none
    
        integer::get_player_id
        character(*), intent(in)::name
        
        type(sqlite3_stmt)::stmt

        get_player_id = -1

        if(stmt%prepare(db, "SELECT id FROM players WHERE name=?") == SQLITE_OK) then
            if(stmt%bind_text(1, name) == SQLITE_OK) then
                if(stmt%step() == SQLITE_ROW) then
                    get_player_id = stmt%column_int(0)
                end if
            end if
        end if
        call stmt%finalize()
        
    end function get_player_id
    
    subroutine get_instruction_name(id, str)
    implicit none
    
        integer, intent(in)::id
        character(*), intent(out)::str
        
        type(sqlite3_stmt)::stmt

        str = " "

        if(stmt%prepare(db, "SELECT name FROM instructions WHERE id=?") == SQLITE_OK) then
            if(stmt%bind_int(1, id) == SQLITE_OK) then
                if(stmt%step() == SQLITE_ROW) then
                    call stmt%column_text(0,str)
                end if
            end if
        end if
        call stmt%finalize()
        
    end subroutine get_instruction_name
    
    function get_instruction_id(name)
    implicit none
    
        integer::get_instruction_id
        character(*), intent(in)::name
        
        type(sqlite3_stmt)::stmt

        get_instruction_id = -1

        if(stmt%prepare(db, "SELECT id FROM instructions WHERE name=?") == SQLITE_OK) then
            if(stmt%bind_text(1, name) == SQLITE_OK) then
                if(stmt%step() == SQLITE_ROW) then
                    get_instruction_id = stmt%column_int(0)
                end if
            end if
        end if
        call stmt%finalize()
        
    end function get_instruction_id
    
    function get_jobs() result(jobs)
    implicit none
    
        type(job), dimension(:), pointer::jobs
        type(sqlite3_stmt)::stmt
        integer::i, n
        
        n = get_jobs_count()
        jobs => null()
        
        if(n > 0) then
            allocate(jobs(n))
            if(stmt%prepare(db, "SELECT id,instruction,player,status,time  FROM jobs ORDER BY id DESC") == SQLITE_OK) then
                i = 1
                do while(stmt%step() == SQLITE_ROW .and. i <= n) 
                    jobs(i)%id = stmt%column_int(0)
                    jobs(i)%instruction = stmt%column_int(1)
                    jobs(i)%player = stmt%column_int(2)
                    jobs(i)%status = stmt%column_int(3)
                    call stmt%column_text(4, jobs(i)%time)
                    i = i + 1
                end do
            end if
            call stmt%finalize()
        end if
    
    end function get_jobs
    
    function get_jobs_for_instruction(id) result(jobs)
    implicit none
    
        type(job), dimension(:), pointer::jobs
        integer, intent(in)::id
        type(sqlite3_stmt)::stmt
    
        integer::n, i
        
        jobs => null()
        n = 0
        if(stmt%prepare(db, "SELECT COUNT(*) FROM jobs WHERE instruction=?") == SQLITE_OK) then
            if(stmt%bind_int(1, id) == SQLITE_OK) then
                if(stmt%step() == SQLITE_ROW) then
                    n = stmt%column_int(0)
                end if
            end if
        end if
        call stmt%finalize()
        
        if(n > 0) then
            allocate(jobs(n))
            if(stmt%prepare(db, &
               "SELECT id,player,status,time FROM jobs WHERE instruction=? ORDER BY id DESC") &
                   == SQLITE_OK) then
                   
                if(stmt%bind_int(1, id) == SQLITE_OK) then
                    i = 1
                    do while(stmt%step() == SQLITE_ROW .and. i <= n) 
                        jobs(i)%id = stmt%column_int(0)
                        jobs(i)%instruction = id
                        jobs(i)%player = stmt%column_int(1)
                        jobs(i)%status = stmt%column_int(2)
                        call stmt%column_text(3, jobs(i)%time)
                        i = i + 1
                    end do
                end if
                
            end if
            call stmt%finalize()
        
        end if
    
    end function get_jobs_for_instruction
    
    function is_player_busy_by_id(id)
    implicit none

        logical::is_player_busy_by_id
        integer, intent(in)::id
        type(sqlite3_stmt)::stmt
        
        is_player_busy_by_id = .false.

        if(stmt%prepare(db, "SELECT COUNT(*) FROM jobs WHERE player=? AND status=?") == SQLITE_OK) then
            if(stmt%bind_int(1, id) == SQLITE_OK .and. stmt%bind_int(2, JOB_STATUS_WORKING) == SQLITE_OK) then
                if(stmt%step() == SQLITE_ROW) then
                    is_player_busy_by_id = (stmt%column_int(0) > 0)
                end if
            end if
        end if
        call stmt%finalize()
    
    end function is_player_busy_by_id
    
    function is_player_busy_by_name(name)
    implicit none

        logical::is_player_busy_by_name
        character(*), intent(in)::name
        integer::id
        
        is_player_busy_by_name = .false.
        id = get_player_id(name)
        is_player_busy_by_name = is_player_busy_by_id(id)
    
    end function is_player_busy_by_name
    
    function get_instruction_players(id) result(res)
    implicit none
    
        integer, dimension(:), pointer::res
        integer, intent(in)::id
        type(sqlite3_stmt)::stmt
        integer::n, i
        
        res => null()
        if(stmt%prepare(db, "SELECT COUNT(*) FROM available WHERE instruction=?") == SQLITE_OK) then
            if(stmt%bind_int(1, id) == SQLITE_OK) then
                if(stmt%step() == SQLITE_ROW) then
                    n = stmt%column_int(0)
                end if
            end if
        end if
        call stmt%finalize()
    
        if(n > 0) then
            allocate(res(n))
            res = -1
            if(stmt%prepare(db, "SELECT player FROM available WHERE instruction=?") == SQLITE_OK) then
                if(stmt%bind_int(1, id) == SQLITE_OK) then
                    i = 1
                    do while(stmt%step() == SQLITE_ROW .and. i <= n)
                        res(i) = stmt%column_int(0)
                        i = i + 1
                    end do
                end if
            end if
            call stmt%finalize()
        end if
    
    end function get_instruction_players
    
    subroutine add_player_for_instruction(instruction, player)
    implicit none
    
        integer, intent(in)::instruction, player
        type(sqlite3_stmt)::stmt
        
        if(stmt%prepare(db, "INSERT OR IGNORE INTO available(instruction, player) VALUES(?,?)") == SQLITE_OK) then
            if(stmt%bind_int(1, instruction) == SQLITE_OK .and. stmt%bind_int(2, player) == SQLITE_OK) then
                call stmt%step_now()
            end if
        end if
        call stmt%finalize()
    
    end subroutine add_player_for_instruction
    
    subroutine remove_player_for_instruction(instruction, player)
    implicit none
    
        integer, intent(in)::instruction, player
        type(sqlite3_stmt)::stmt
        
        if(stmt%prepare(db, "DELETE FROM available WHERE instruction=? AND player=?") == SQLITE_OK) then
            if(stmt%bind_int(1, instruction) == SQLITE_OK .and. stmt%bind_int(2, player) == SQLITE_OK) then
                call stmt%step_now()
            end if
        end if
        call stmt%finalize()
    
    end subroutine remove_player_for_instruction
    
    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