aboutsummaryrefslogtreecommitdiff
path: root/captain/db.f90
diff options
context:
space:
mode:
authorJeffrey Armstrong <jeff@approximatrix.com>2021-04-01 11:38:06 -0400
committerJeffrey Armstrong <jeff@approximatrix.com>2021-04-01 11:38:06 -0400
commitaf084b8acb5ed7e883e422c4626a596eb32fba25 (patch)
tree323cb1c5c0de5ad919d0c932718efaff14a5566b /captain/db.f90
parent9d19023f554dee7d8656a18dd81479decc03b3ee (diff)
downloadlevitating-af084b8acb5ed7e883e422c4626a596eb32fba25.tar.gz
levitating-af084b8acb5ed7e883e422c4626a596eb32fba25.zip
Added support for viewing individual instruction pages, assigning players, and launching instruction jobs
Diffstat (limited to 'captain/db.f90')
-rw-r--r--captain/db.f90283
1 files changed, 283 insertions, 0 deletions
diff --git a/captain/db.f90 b/captain/db.f90
index c61ffc7..1060dbc 100644
--- a/captain/db.f90
+++ b/captain/db.f90
@@ -5,6 +5,13 @@ 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
@@ -18,6 +25,11 @@ implicit none
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)
@@ -185,6 +197,277 @@ contains
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