aboutsummaryrefslogtreecommitdiff
path: root/captain/db.f90
diff options
context:
space:
mode:
authorJeffrey Armstrong <jeff@approximatrix.com>2021-04-01 16:49:20 -0400
committerJeffrey Armstrong <jeff@approximatrix.com>2021-04-01 16:49:20 -0400
commit3e58313bde5e3e572d84fe014d9902dfb04712c3 (patch)
tree336884dbbfc441c437bda3f6b5121b4b3d2ef225 /captain/db.f90
parentb125906018d0d3d09baeebb096db56ca052902eb (diff)
downloadlevitating-3e58313bde5e3e572d84fe014d9902dfb04712c3.tar.gz
levitating-3e58313bde5e3e572d84fe014d9902dfb04712c3.zip
Jobs are now inserted into the database when launched. Job listings work.
Diffstat (limited to 'captain/db.f90')
-rw-r--r--captain/db.f90102
1 files changed, 101 insertions, 1 deletions
diff --git a/captain/db.f90 b/captain/db.f90
index 1060dbc..c23b770 100644
--- a/captain/db.f90
+++ b/captain/db.f90
@@ -8,6 +8,7 @@ implicit none
integer, parameter::JOB_STATUS_SUCCESS = 1
integer, parameter::JOB_STATUS_FAILURE = 2
integer, parameter::JOB_STATUS_WORKING = 3
+ integer, parameter::JOB_STATUS_PENDING = 0
integer, parameter::PLAYER_STATUS_BUSY = JOB_STATUS_WORKING
integer, parameter::PLAYER_STATUS_IDLE = 100
@@ -25,6 +26,14 @@ implicit none
end type
+ type :: task
+
+ integer::job
+ integer::number
+ integer::status
+
+ end type
+
interface is_player_busy
module procedure is_player_busy_by_id
module procedure is_player_busy_by_name
@@ -358,7 +367,11 @@ contains
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)
+ if(stmt%column_type(3) == SQLITE_NULL) then
+ jobs(i)%time = "Not started"
+ else
+ call stmt%column_text(3, jobs(i)%time)
+ end if
i = i + 1
end do
end if
@@ -468,6 +481,93 @@ contains
end subroutine remove_player_for_instruction
+ subroutine add_new_job(instruction, player)
+ implicit none
+
+ integer, intent(in)::instruction, player
+ type(sqlite3_stmt)::stmt
+
+ if(stmt%prepare(db, "INSERT INTO jobs(instruction, player, status) VALUES(?, ?, ?)") == SQLITE_OK) then
+ if(stmt%bind_int(1, instruction) == SQLITE_OK .and. &
+ stmt%bind_int(2, player) == SQLITE_OK .and. &
+ stmt%bind_int(3, JOB_STATUS_PENDING) == SQLITE_OK) then
+ call stmt%step_now()
+ end if
+ end if
+ call stmt%finalize()
+
+ end subroutine add_new_job
+
+ function get_job(id)
+ implicit none
+
+ integer, intent(in)::id
+ type(job)::get_job
+ type(sqlite3_stmt)::stmt
+
+ get_job%id = -1
+
+ if(stmt%prepare(db, "SELECT instruction,player,status,time FROM jobs WHERE id=?") == SQLITE_OK) then
+ if(stmt%bind_int(1, id) == SQLITE_OK) then
+ if(stmt%step() == SQLITE_ROW) then
+ get_job%instruction = stmt%column_int(0)
+ get_job%player = stmt%column_int(1)
+ get_job%player = stmt%column_int(2)
+ if(stmt%column_type(3) == SQLITE_NULL) then
+ get_job%time = "Not started"
+ else
+ call stmt%column_text(3,get_job%time)
+ end if
+ get_job%id = id
+ end if
+ end if
+ end if
+ call stmt%finalize()
+
+ end function get_job
+
+ function get_job_tasks(job) result(res)
+ implicit none
+
+ integer, intent(in)::job
+ type(task), dimension(:), pointer::res
+
+ type(sqlite3_stmt)::stmt
+ integer::n, i
+
+ n = 0
+ if(stmt%prepare(db, "SELECT COUNT(*) FROM tasks WHERE job=?") == SQLITE_OK) then
+ if(stmt%bind_int(1, job) == 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
+ res => null()
+
+ else
+ allocate(res(n))
+ res%number = 0
+ res%status = JOB_STATUS_PENDING
+ if(stmt%prepare(db, "SELECT task, status FROM tasks WHERE job=? ORDER BY task ASC") == SQLITE_OK) then
+ if(stmt%bind_int(1, job) == SQLITE_OK) then
+ i = 1
+ do while(stmt%step() == SQLITE_ROW .and. i <= n)
+ res(i)%number = stmt%column_int(0)
+ res(i)%status = stmt%column_int(1)
+ res(i)%job = job
+ i = i + 1
+ end do
+ end if
+ end if
+ call stmt%finalize()
+ end if
+
+ end function get_job_tasks
+
subroutine scan_instructions_for_db()
use config
use utilities