aboutsummaryrefslogtreecommitdiff
path: root/captain/db.f90
diff options
context:
space:
mode:
Diffstat (limited to 'captain/db.f90')
-rw-r--r--captain/db.f9047
1 files changed, 47 insertions, 0 deletions
diff --git a/captain/db.f90 b/captain/db.f90
index 44bc473..90fb4e1 100644
--- a/captain/db.f90
+++ b/captain/db.f90
@@ -794,6 +794,53 @@ contains
end subroutine update_task_status
+ subroutine update_task_type(job_id, task_id, task_type)
+ implicit none
+
+ integer, intent(in)::job_id, task_id
+ character(len=*), intent(in)::task_type
+ type(sqlite3_stmt)::stmt
+
+ if(stmt%prepare(db, "UPDATE tasks SET type=? WHERE job=? AND task=?") == SQLITE_OK) then
+ if(stmt%bind_text(1, task_type) == 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()
+
+ end subroutine update_task_type
+
+ function get_task_type(job_id, task_id, task_type) result(ret)
+ implicit none
+
+ integer, intent(in)::job_id, task_id
+ character(len=*), intent(out), optional::task_type
+ logical::ret
+ type(sqlite3_stmt)::stmt
+
+ ret = .false.
+
+ if(stmt%prepare(db, "SELECT type FROM tasks WHERE job=? AND task=?") == SQLITE_OK) then
+ if(stmt%bind_int(1, job_id) == SQLITE_OK .and. &
+ stmt%bind_int(2, task_id) == SQLITE_OK) &
+ then
+ if(stmt%step() == SQLITE_ROW) then
+ if(.not. stmt%column_is_null(0)) then
+ ret = .true.
+ if(present(task_type)) then
+ call stmt%column_text(0, task_type)
+ end if
+ end if
+ end if
+ end if
+ end if
+ call stmt%finalize()
+
+ end function get_task_type
+
function is_final_job_status(job_id)
implicit none