aboutsummaryrefslogtreecommitdiff
path: root/captain/sqlite.f90
diff options
context:
space:
mode:
Diffstat (limited to 'captain/sqlite.f90')
-rw-r--r--captain/sqlite.f9022
1 files changed, 22 insertions, 0 deletions
diff --git a/captain/sqlite.f90 b/captain/sqlite.f90
index e7bf6a1..6bad946 100644
--- a/captain/sqlite.f90
+++ b/captain/sqlite.f90
@@ -116,6 +116,13 @@ implicit none
type(c_ptr)::c_sqlite3_column_text
end function c_sqlite3_column_text
+ function c_sqlite3_column_bytes(p, i) bind(c, name="sqlite3_column_bytes")
+ use iso_c_binding
+ type(c_ptr), value::p
+ integer(c_int), value::i
+ integer(c_int)::c_sqlite3_column_bytes
+ end function c_sqlite3_column_bytes
+
end interface
! Good to go
@@ -165,6 +172,7 @@ implicit none
procedure::column_int => stmt_column_int
procedure::column_text => stmt_column_text
procedure::column_type => stmt_column_type
+ procedure::column_text_length => stmt_column_text_length
end type
@@ -375,4 +383,18 @@ contains
end subroutine stmt_column_text
+ function stmt_column_text_length(self, i)
+ implicit none
+
+ class(sqlite3_stmt), intent(inout)::self
+ integer, intent(in)::i
+ integer::stmt_column_text_length
+
+ stmt_column_text_length = 0
+ if(self%column_type(i) /= SQLITE_NULL) then
+ stmt_column_text_length = c_sqlite3_column_bytes(self%stmt, i)
+ end if
+
+ end function stmt_column_text_length
+
end module sqlite \ No newline at end of file