aboutsummaryrefslogtreecommitdiff
path: root/captain/db.f90
diff options
context:
space:
mode:
Diffstat (limited to 'captain/db.f90')
-rw-r--r--captain/db.f9077
1 files changed, 77 insertions, 0 deletions
diff --git a/captain/db.f90 b/captain/db.f90
index 90fb4e1..c3f30c4 100644
--- a/captain/db.f90
+++ b/captain/db.f90
@@ -1747,5 +1747,82 @@ contains
end function is_valid_session_db
+ subroutine add_job_upload_db(job_id, category, filename)
+ implicit none
+
+ integer, intent(in)::job_id
+ character(len=*), intent(in)::category, filename
+
+ type(sqlite3_stmt)::stmt
+
+ if(stmt%prepare(db, "INSERT INTO job_uploads(job, category, filename) VALUES(?, ?, ?)") == SQLITE_OK) then
+
+ if(stmt%bind_int(1, job_id) == SQLITE_OK .and. stmt%bind_text(2, category) == SQLITE_OK .and. &
+ stmt%bind_text(3, filename) == SQLITE_OK) &
+ then
+
+ call stmt%step_now()
+
+ end if
+ call stmt%finalize()
+ end if
+
+ end subroutine add_job_upload_db
+
+ function get_job_upload_count_by_category_db(job_id, category) result(entries)
+ implicit none
+
+ integer, intent(in)::job_id
+ character(len=*), intent(in)::category
+ integer::entries
+ type(sqlite3_stmt)::stmt
+
+ entries = 0
+
+ if(stmt%prepare(db, "SELECT COUNT(*) FROM job_uploads WHERE job=? AND category=?") == SQLITE_OK) then
+ if(stmt%bind_int(1, job_id) == SQLITE_OK .and. stmt%bind_text(2, category) == SQLITE_OK) then
+ if(stmt%step() == SQLITE_ROW) then
+ entries = stmt%column_int(0)
+ end if
+ end if
+ call stmt%finalize()
+ end if
+
+ end function get_job_upload_count_by_category_db
+
+ function get_job_uploads_by_category_db(job_id, category, count) result(res)
+ implicit none
+
+ integer, intent(in)::job_id
+ character(len=*), intent(in)::category
+ integer, intent(out), optional::count
+
+ character(len=FILENAME_NAME_LENGTH), dimension(:), pointer::res
+
+ type(sqlite3_stmt)::stmt
+ integer::entries, i
+
+ res => null()
+ entries = get_job_upload_count_by_category_db(job_id, category)
+
+ if(entries > 0) then
+ allocate(res(entries))
+
+ i = 1
+ if(stmt%prepare(db, "SELECT filename FROM job_uploads WHERE job=? AND category=?") == SQLITE_OK) then
+ if(stmt%bind_int(1, job_id) == SQLITE_OK .and. stmt%bind_text(2, category) == SQLITE_OK) then
+ do while(stmt%step() == SQLITE_ROW)
+ call stmt%column_text(0, res(i))
+ i = i + 1
+ end do
+ end if
+ end if
+ end if
+
+ if(present(count)) then
+ count = entries
+ end if
+
+ end function get_job_uploads_by_category_db
end module captain_db