aboutsummaryrefslogtreecommitdiff
path: root/captain/db.f90
diff options
context:
space:
mode:
authorJeffrey Armstrong <jeff@approximatrix.com>2021-04-02 13:08:37 -0400
committerJeffrey Armstrong <jeff@approximatrix.com>2021-04-02 13:08:37 -0400
commitb27bd7cfa58eb82fc2a6c76aaa848e07a6fa7c24 (patch)
treef611937418d1ea5416431715ab1f6a44d42d1905 /captain/db.f90
parentda47fdfddc46e35a939b7771eda21debec50c094 (diff)
downloadlevitating-b27bd7cfa58eb82fc2a6c76aaa848e07a6fa7c24.tar.gz
levitating-b27bd7cfa58eb82fc2a6c76aaa848e07a6fa7c24.zip
API calls to the gemini interface should work. API calls to the titan interface need implementation.
Diffstat (limited to 'captain/db.f90')
-rw-r--r--captain/db.f90129
1 files changed, 129 insertions, 0 deletions
diff --git a/captain/db.f90 b/captain/db.f90
index c23b770..fa53774 100644
--- a/captain/db.f90
+++ b/captain/db.f90
@@ -568,6 +568,135 @@ contains
end function get_job_tasks
+ subroutine update_job_status(job_id, status)
+ implicit none
+
+ integer, intent(in)::job_id, status
+ type(sqlite3_stmt)::stmt
+
+ if(stmt%prepare(db, "UPDATE jobs SET status=? WHERE id=?") == SQLITE_OK) then
+ if(stmt%bind_int(1, status) == SQLITE_OK .and. stmt%bind_int(2, job_id) == SQLITE_OK) then
+ call stmt%step_now()
+ end if
+ end if
+ call stmt%finalize()
+
+ call update_job_time(job_id)
+
+ end subroutine update_job_status
+
+ subroutine update_job_time(job_id)
+ implicit none
+
+ integer, intent(in)::job_id
+ character(8)::update_date
+ character(10)::update_time
+ type(sqlite3_stmt)::stmt
+
+ call date_and_time(date=update_date, time=update_time)
+
+ if(stmt%prepare(db, "UPDATE jobs SET time=? WHERE id=?") == SQLITE_OK) then
+ if(stmt%bind_text(1, update_date//" "//update_time) == SQLITE_OK .and. &
+ stmt%bind_int(2, job_id) == SQLITE_OK) then
+ call stmt%step_now()
+ end if
+ end if
+ call stmt%finalize()
+
+ end subroutine update_job_time
+
+ subroutine update_task_status(job_id, task_id, status)
+ implicit none
+
+ integer, intent(in)::job_id, task_id, status
+ type(sqlite3_stmt)::stmt
+
+ if(stmt%prepare(db, "UPDATE jobs SET status=? WHERE job=? AND task=?") == SQLITE_OK) then
+ if(stmt%bind_int(1, status) == SQLITE_OK .and. &
+ stmt%bind_int(2, job_id) == SQLITE_OK .and. &
+ stmt%bind_int(3, task_id) == SQLITE_OK) then
+ call stmt%step_now()
+ end if
+ end if
+ call stmt%finalize()
+
+ call update_job_time(job_id)
+
+ end subroutine update_task_status
+
+ function is_final_job_status(job_id)
+ implicit none
+
+ integer, intent(in)::job_id
+ logical::is_final_job_status
+ integer::i
+
+ i = get_job_status(job_id)
+
+ is_final_job_status = (i == JOB_STATUS_SUCCESS .or. i == JOB_STATUS_FAILURE)
+
+ end function is_final_job_status
+
+ function get_job_status(job_id) result(status)
+ implicit none
+
+ integer, intent(in)::job_id
+ integer::status
+ type(sqlite3_stmt)::stmt
+
+ status = -1
+
+ if(stmt%prepare(db, "SELECT status FROM jobs WHERE id=? LIMIT 1") == SQLITE_OK) then
+ if(stmt%bind_int(1, job_id) == SQLITE_OK) then
+ if(stmt%step() == SQLITE_ROW) then
+ status = stmt%column_int(0)
+ end if
+ end if
+ end if
+ call stmt%finalize()
+
+ end function get_job_status
+
+ function get_job_instruction(job_id) result(status)
+ implicit none
+
+ integer, intent(in)::job_id
+ integer::status
+ type(sqlite3_stmt)::stmt
+
+ status = -1
+
+ if(stmt%prepare(db, "SELECT instruction FROM jobs WHERE id=? LIMIT 1") == SQLITE_OK) then
+ if(stmt%bind_int(1, job_id) == SQLITE_OK) then
+ if(stmt%step() == SQLITE_ROW) then
+ status = stmt%column_int(0)
+ end if
+ end if
+ end if
+ call stmt%finalize()
+
+ end function get_job_instruction
+
+ function get_pending_job_for_player(player) result(job)
+ implicit none
+
+ integer, intent(in)::player
+ integer::job
+ type(sqlite3_stmt)::stmt
+
+ job = -1
+
+ if(stmt%prepare(db, "SELECT id FROM jobs WHERE player=? AND status=? LIMIT 1") == SQLITE_OK) then
+ if(stmt%bind_int(1, player) == SQLITE_OK .and. stmt%bind_int(2, JOB_STATUS_PENDING) == SQLITE_OK) then
+ if(stmt%step() == SQLITE_ROW) then
+ job = stmt%column_int(0)
+ end if
+ end if
+ end if
+ call stmt%finalize()
+
+ end function get_pending_job_for_player
+
subroutine scan_instructions_for_db()
use config
use utilities