aboutsummaryrefslogtreecommitdiff
path: root/captain/sqlite.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/sqlite.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/sqlite.f90')
-rw-r--r--captain/sqlite.f9051
1 files changed, 41 insertions, 10 deletions
diff --git a/captain/sqlite.f90 b/captain/sqlite.f90
index 003bd6f..a1d4a4c 100644
--- a/captain/sqlite.f90
+++ b/captain/sqlite.f90
@@ -7,7 +7,13 @@ implicit none
integer(kind=c_int), parameter::SQLITE_BUSY = 5
integer(kind=c_int), parameter::SQLITE_ROW = 100
integer(kind=c_int), parameter::SQLITE_DONE = 101
-
+
+ integer(kind=c_int), parameter::SQLITE_INTEGER = 1
+ integer(kind=c_int), parameter::SQLITE_FLOAT = 2
+ integer(kind=c_int), parameter::SQLITE_TEXT = 3
+ integer(kind=c_int), parameter::SQLITE_BLOB = 4
+ integer(kind=c_int), parameter::SQLITE_NULL = 5
+
integer, parameter::sqlite3_max_free_strings = 32
interface
@@ -110,6 +116,13 @@ implicit none
integer(c_int)::sqlite3_step
end function sqlite3_step
+ function sqlite3_column_type(p, c) bind(c, name='sqlite3_column_type')
+ use iso_c_binding
+ type(c_ptr), value::p
+ integer(kind=c_int), value::c
+ integer(c_int)::sqlite3_column_type
+ end function sqlite3_column_type
+
end interface
type :: sqlite3_stmt
@@ -129,6 +142,7 @@ implicit none
procedure::step_now => stmt_step_ignore
procedure::column_int => stmt_column_int
procedure::column_text => stmt_column_text
+ procedure::column_type => stmt_column_type
end type
@@ -294,10 +308,25 @@ contains
integer, intent(in)::i
integer::stmt_column_int
- stmt_column_int = c_sqlite3_column_int(self%stmt, i)
+ if(self%column_type(i) /= SQLITE_NULL) then
+ stmt_column_int = c_sqlite3_column_int(self%stmt, i)
+ else
+ stmt_column_int = -1*huge(1)
+ end if
end function stmt_column_int
+ function stmt_column_type(self, i)
+ implicit none
+
+ class(sqlite3_stmt), intent(inout)::self
+ integer, intent(in)::i
+ integer::stmt_column_type
+
+ stmt_column_type = sqlite3_column_type(self%stmt, i)
+
+ end function stmt_column_type
+
subroutine stmt_column_text(self, i, res)
implicit none
@@ -307,17 +336,19 @@ contains
character(kind=c_char), dimension(:), pointer::src
type(c_ptr)::txtcol
- integer::n, i_char
+ integer(kind=8)::n, i_char
- txtcol = c_sqlite3_column_text(self%stmt, i)
res = " "
- if(c_associated(txtcol)) then
- n = c_strlen(txtcol)
- call c_f_pointer(txtcol, src, (/ n /))
- do i_char=1, min(n, len(res))
- res(i_char:i_char) = src(i_char)
- end do
+ if(self%column_type(i) /= SQLITE_NULL) then
+ txtcol = c_sqlite3_column_text(self%stmt, i)
+ if(c_associated(txtcol)) then
+ n = c_strlen(txtcol)
+ call c_f_pointer(txtcol, src, (/ n /))
+ do i_char=1, min(n, len(res))
+ res(i_char:i_char) = src(i_char)
+ end do
+ end if
end if
end subroutine stmt_column_text