{-| Sqlite is a database API with direct file access, instead of network access. You can find information and documentation about it at: Translation notes: * Although the general rule is to type preprocessor constant definitions as CInt, _STATIC and _TRANSIENT have been typed as pointers to @'Foreign.ForeignPtr.FinalizerPtr' ()@ to be consistent with their use. * These compile time macros have been defined: @SQLITE_ENABLE_FTS3@, @SQLITE_ENABLE_FTS3_PARENTHESIS@, @SQLITE_ENABLE_LOCKING_STYLE@, @SQLITE_ENABLE_MEMORY_MANAGEMENT@, @SQLITE_ENABLE_MEMSYS5@ and @SQLITE_ENABLE_RTREE@. -} module Bindings.Sqlite3 where import Bindings.Utilities import Bindings.StandardC import Foreign import Foreign.C -- * Objects data Sqlite3 = Sqlite3 data Blob = Blob data Context = Context data File = File data IoMethods = IoMethods data Mutex = Mutex data Stmt = Stmt data Value = Value data Vfs = Vfs foreign import ccall "&sqlite3_temp_directory" temp_directory :: GlobalVar CString -- * Error codes _OK, _ERROR, _INTERNAL, _PERM, _ABORT, _BUSY, _LOCKED, _NOMEM, _READONLY, _INTERRUPT, _IOERR, _CORRUPT, _NOTFOUND, _FULL, _CANTOPEN, _PROTOCOL, _EMPTY, _SCHEMA, _TOOBIG, _CONSTRAINT, _MISMATCH, _MISUSE, _NOLFS, _AUTH, _FORMAT, _RANGE, _NOTADB, _ROW, _DONE :: CInt [_OK, _ERROR, _INTERNAL, _PERM, _ABORT, _BUSY, _LOCKED, _NOMEM, _READONLY, _INTERRUPT, _IOERR, _CORRUPT, _NOTFOUND, _FULL, _CANTOPEN, _PROTOCOL, _EMPTY, _SCHEMA, _TOOBIG, _CONSTRAINT, _MISMATCH, _MISUSE, _NOLFS, _AUTH, _FORMAT, _RANGE, _NOTADB, _ROW, _DONE] = [0..26] ++ [100,101] -- * Flags for the xAccess VFS method _ACCESS_EXISTS, _ACCESS_READWRITE, _ACCESS_READ :: CInt [_ACCESS_EXISTS, _ACCESS_READWRITE, _ACCESS_READ] = [0..2] -- * Authorizer Action Codes _CREATE_INDEX, _CREATE_TABLE, _CREATE_TEMP_INDEX, _CREATE_TEMP_TABLE, _CREATE_TEMP_TRIGGER, _CREATE_TEMP_VIEW, _CREATE_TRIGGER, _CREATE_VIEW, _DELETE, _DROP_INDEX, _DROP_TABLE, _DROP_TEMP_INDEX, _DROP_TEMP_TABLE, _DROP_TEMP_TRIGGER, _DROP_TEMP_VIEW, _DROP_TRIGGER, _DROP_VIEW, _INSERT, _PRAGMA, _READ, _SELECT, _TRANSACTION, _UPDATE, _ATTACH, _DETACH, _ALTERTABLE, _REINDEX, _ANALYZE, _CREATE_VTABLE, _DROP_VTABLE, _FUNCTION :: CInt [_CREATE_INDEX, _CREATE_TABLE, _CREATE_TEMP_INDEX, _CREATE_TEMP_TABLE, _CREATE_TEMP_TRIGGER, _CREATE_TEMP_VIEW, _CREATE_TRIGGER, _CREATE_VIEW, _DELETE, _DROP_INDEX, _DROP_TABLE, _DROP_TEMP_INDEX, _DROP_TEMP_TABLE, _DROP_TEMP_TRIGGER, _DROP_TEMP_VIEW, _DROP_TRIGGER, _DROP_VIEW, _INSERT, _PRAGMA, _READ, _SELECT, _TRANSACTION, _UPDATE, _ATTACH, _DETACH, _ALTERTABLE, _REINDEX, _ANALYZE, _CREATE_VTABLE, _DROP_VTABLE, _FUNCTION] = [1..31] -- * Text Encodings _UTF8, _UTF16LE, _UTF16BE, _UTF16, _ANY, _UTF16_ALIGNED :: CInt [_UTF8, _UTF16LE, _UTF16BE, _UTF16, _ANY, _UTF16_ALIGNED] = [1..5]++[8] -- * Fundamental Datatypes _INTEGER, _FLOAT, _TEXT, _BLOB, _NULL :: CInt [_INTEGER, _FLOAT, _TEXT, _BLOB, _NULL] = [1..5] -- * Authorizer Return Codes _DENY, _IGNORE :: CInt [_DENY, _IGNORE] = [1,2] -- * Standard File Control Opcodes _FCNTL_LOCKSTATE, _GET_LOCKPROXYFILE, _SET_LOCKPROXYFILE, _LAST_ERRNO :: CInt [_FCNTL_LOCKSTATE, _GET_LOCKPROXYFILE, _SET_LOCKPROXYFILE, _LAST_ERRNO] = [1..4] -- * Device Characteristics _IOCAP_ATOMIC, _IOCAP_ATOMIC512, _IOCAP_ATOMIC1K, _IOCAP_ATOMIC2K, _IOCAP_ATOMIC4K, _IOCAP_ATOMIC8K, _IOCAP_ATOMIC16K, _IOCAP_ATOMIC32K, _IOCAP_ATOMIC64K, _IOCAP_SAFE_APPEND, _IOCAP_SEQUENTIAL :: CInt [_IOCAP_ATOMIC, _IOCAP_ATOMIC512, _IOCAP_ATOMIC1K, _IOCAP_ATOMIC2K, _IOCAP_ATOMIC4K, _IOCAP_ATOMIC8K, _IOCAP_ATOMIC16K, _IOCAP_ATOMIC32K, _IOCAP_ATOMIC64K, _IOCAP_SAFE_APPEND, _IOCAP_SEQUENTIAL] = take 11 $ iterate (* 2) 1 -- * Extended Result Codes _IOERR_READ, _IOERR_SHORT_READ, _IOERR_WRITE, _IOERR_FSYNC, _IOERR_DIR_FSYNC, _IOERR_TRUNCATE, _IOERR_FSTAT, _IOERR_UNLOCK, _IOERR_RDLOCK, _IOERR_DELETE, _IOERR_BLOCKED, _IOERR_NOMEM, _IOERR_ACCESS, _IOERR_CHECKRESERVEDLOCK, _IOERR_LOCK, _IOERR_CLOSE, _IOERR_DIR_CLOSE :: CInt [_IOERR_READ, _IOERR_SHORT_READ, _IOERR_WRITE, _IOERR_FSYNC, _IOERR_DIR_FSYNC, _IOERR_TRUNCATE, _IOERR_FSTAT, _IOERR_UNLOCK, _IOERR_RDLOCK, _IOERR_DELETE, _IOERR_BLOCKED, _IOERR_NOMEM, _IOERR_ACCESS, _IOERR_CHECKRESERVEDLOCK, _IOERR_LOCK, _IOERR_CLOSE, _IOERR_DIR_CLOSE] = map ( (+ _IOERR) . (* 256) ) [1..17] -- * Run-Time Limit Categories _LIMIT_LENGTH, _LIMIT_SQL_LENGTH, _LIMIT_COLUMN, _LIMIT_EXPR_DEPTH, _LIMIT_COMPOUND_SELECT, _LIMIT_VDBE_OP, _LIMIT_FUNCTION_ARG, _LIMIT_ATTACHED, _LIMIT_LIKE_PATTERN_LENGTH, _LIMIT_VARIABLE_NUMBER :: CInt [_LIMIT_LENGTH, _LIMIT_SQL_LENGTH, _LIMIT_COLUMN, _LIMIT_EXPR_DEPTH, _LIMIT_COMPOUND_SELECT, _LIMIT_VDBE_OP, _LIMIT_FUNCTION_ARG, _LIMIT_ATTACHED, _LIMIT_LIKE_PATTERN_LENGTH, _LIMIT_VARIABLE_NUMBER] = [0..9] -- * File Locking Levels _LOCK_NONE, _LOCK_SHARED, _LOCK_RESERVED, _LOCK_PENDING, _LOCK_EXCLUSIVE :: CInt [_LOCK_NONE, _LOCK_SHARED, _LOCK_RESERVED, _LOCK_PENDING, _LOCK_EXCLUSIVE] = [0..4] -- * Mutex Types _MUTEX_FAST, _MUTEX_RECURSIVE, _MUTEX_STATIC_MASTER, _MUTEX_STATIC_MEM, _MUTEX_STATIC_MEM2, _MUTEX_STATIC_PRNG, _MUTEX_STATIC_LRU, _MUTEX_STATIC_LRU2 :: CInt [_MUTEX_FAST, _MUTEX_RECURSIVE, _MUTEX_STATIC_MASTER, _MUTEX_STATIC_MEM, _MUTEX_STATIC_MEM2, _MUTEX_STATIC_PRNG, _MUTEX_STATIC_LRU, _MUTEX_STATIC_LRU2] = [0..7] -- * Flags For File Open Operations _OPEN_READONLY, _OPEN_READWRITE, _OPEN_CREATE, _OPEN_DELETEONCLOSE, _OPEN_EXCLUSIVE, _OPEN_MAIN_DB, _OPEN_TEMP_DB, _OPEN_TRANSIENT_DB, _OPEN_MAIN_JOURNAL, _OPEN_TEMP_JOURNAL, _OPEN_SUBJOURNAL, _OPEN_MASTER_JOURNAL, _OPEN_NOMUTEX, _OPEN_FULLMUTEX :: CInt [_OPEN_READONLY, _OPEN_READWRITE, _OPEN_CREATE, _OPEN_DELETEONCLOSE, _OPEN_EXCLUSIVE, _OPEN_MAIN_DB, _OPEN_TEMP_DB, _OPEN_TRANSIENT_DB, _OPEN_MAIN_JOURNAL, _OPEN_TEMP_JOURNAL, _OPEN_SUBJOURNAL, _OPEN_MASTER_JOURNAL, _OPEN_NOMUTEX, _OPEN_FULLMUTEX] = map bit $ [0..4] ++ [8..16] -- * Constants Defining Special Destructor Behavior _STATIC, _TRANSIENT :: FinalizerPtr () [_STATIC, _TRANSIENT] = map cast [0,(-1)] where cast :: IntPtr -> FinalizerPtr () cast n = castPtrToFunPtr $ intPtrToPtr n -- * Synchronization Type Flags _SYNC_NORMAL, _SYNC_FULL, _SYNC_DATAONLY :: CInt [_SYNC_NORMAL, _SYNC_FULL, _SYNC_DATAONLY] = [0x2, 0x3, 0x10] -- * Compile-Time Library Version Numbers foreign import ccall "bindings_sqlite3_version" version :: CString foreign import ccall "bindings_SQLITE_VERSION" _VERSION :: CString foreign import ccall "bindings_VERSION_NUMBER" _VERSION_NUMBER :: CInt -- * Functions foreign import ccall "sqlite3_aggregate_context" aggregate_context :: Ptr Context -> CInt -> IO (Ptr a) foreign import ccall "sqlite3_auto_extension" auto_extension :: Ptr a -> IO CInt foreign import ccall "sqlite3_bind_blob" bind_blob :: Ptr Stmt -> CInt -> Ptr a -> CInt -> FinalizerPtr a -> IO CInt foreign import ccall "sqlite3_bind_double" bind_double :: Ptr Stmt -> CInt -> CDouble -> IO CInt foreign import ccall "sqlite3_bind_int" bind_int :: Ptr Stmt -> CInt -> CInt -> IO CInt foreign import ccall "sqlite3_bind_int64" bind_int64 :: Ptr Stmt -> CInt -> CInt64 -> IO CInt foreign import ccall "sqlite3_bind_null" bind_null :: Ptr Stmt -> CInt -> IO CInt foreign import ccall "sqlite3_bind_parameter_count" bind_parameter_count :: Ptr Stmt -> IO CInt foreign import ccall "sqlite3_bind_parameter_index" bind_parameter_index :: Ptr Stmt -> CString -> IO CInt foreign import ccall "sqlite3_bind_parameter_name" bind_parameter_name :: Ptr Stmt -> CInt -> IO CString foreign import ccall "sqlite3_bind_text" bind_text :: Ptr Stmt -> CInt -> CString -> CInt -> FinalizerPtr CString -> IO CInt foreign import ccall "sqlite3_bind_text16" bind_text16 :: Ptr Stmt -> CInt -> CString -> CInt -> FinalizerPtr CString -> IO CInt foreign import ccall "sqlite3_bind_value" bind_value :: Ptr Stmt -> CInt -> Ptr Value -> IO CInt foreign import ccall "sqlite3_bind_zeroblob" bind_zeroblob :: Ptr Stmt -> CInt -> CInt -> IO CInt foreign import ccall "sqlite3_blob_bytes" blob_bytes :: Ptr Blob -> IO CInt foreign import ccall "sqlite3_blob_close" blob_close :: Ptr Blob -> IO CInt foreign import ccall "sqlite3_blob_open" blob_open :: Ptr Sqlite3 -> CString -> CString -> CString -> CInt64 -> CInt -> Ptr (Ptr Blob) -> IO CInt foreign import ccall "sqlite3_blob_read" blob_read :: Ptr Blob -> Ptr a -> CInt -> CInt -> IO CInt foreign import ccall "sqlite3_blob_write" blob_write :: Ptr Blob -> Ptr a -> CInt -> CInt -> IO CInt foreign import ccall "sqlite3_busy_handler" busy_handler :: Ptr Sqlite3 -> FunPtr (CB0003 a) -> Ptr a -> IO CInt foreign import ccall "sqlite3_busy_timeout" busy_timeout :: Ptr Sqlite3 -> CInt -> IO CInt foreign import ccall "sqlite3_changes" changes :: Ptr Sqlite3 -> IO CInt foreign import ccall "sqlite3_clear_bindings" clear_bindings :: Ptr Stmt -> IO CInt foreign import ccall "sqlite3_close" close :: Ptr Sqlite3 -> IO CInt foreign import ccall "sqlite3_collation_needed" collation_needed :: Ptr Sqlite3 -> Ptr a -> FunPtr (CB0004 a Sqlite3) -> IO CInt foreign import ccall "sqlite3_collation_needed16" collation_needed16 :: Ptr Sqlite3 -> Ptr a -> FunPtr (CB0004 a Sqlite3) -> IO CInt foreign import ccall "sqlite3_column_blob" column_blob :: Ptr Stmt -> CInt -> IO (Ptr a) foreign import ccall "sqlite3_column_bytes" column_bytes :: Ptr Stmt -> CInt -> IO CInt foreign import ccall "sqlite3_column_bytes16" column_bytes16 :: Ptr Stmt -> CInt -> IO CInt foreign import ccall "sqlite3_column_count" column_count :: Ptr Stmt -> IO CInt foreign import ccall "sqlite3_column_decltype" column_decltype :: Ptr Stmt -> CInt -> IO CString foreign import ccall "sqlite3_column_decltype16" column_decltype16 :: Ptr Stmt -> CInt -> IO CString foreign import ccall "sqlite3_column_double" column_double :: Ptr Stmt -> CInt -> IO Double foreign import ccall "sqlite3_column_int" column_int :: Ptr Stmt -> CInt -> IO CInt foreign import ccall "sqlite3_column_int64" column_int64 :: Ptr Stmt -> CInt -> IO CInt64 foreign import ccall "sqlite3_column_name" column_name :: Ptr Stmt -> CInt -> IO CString foreign import ccall "sqlite3_column_name16" column_name16 :: Ptr Stmt -> CInt -> IO CString foreign import ccall "sqlite3_column_text" column_text :: Ptr Stmt -> CInt -> IO CString foreign import ccall "sqlite3_column_text16" column_text16 :: Ptr Stmt -> CInt -> IO CString foreign import ccall "sqlite3_column_type" column_type :: Ptr Stmt -> CInt -> IO CInt foreign import ccall "sqlite3_column_value" column_value :: Ptr Stmt -> CInt -> IO (Ptr Value) foreign import ccall "sqlite3_commit_hook" commit_hook :: Ptr Stmt -> FunPtr (CB0005 a) -> Ptr a -> IO (Ptr b) foreign import ccall "sqlite3_complete" complete :: CString -> IO CInt foreign import ccall "sqlite3_complete16" complete16 :: CString -> IO CInt foreign import ccall "sqlite3_context_db_handle" context_db_handle :: Ptr Context -> IO (Ptr Sqlite3) foreign import ccall "sqlite3_create_collation" create_collation :: Ptr Sqlite3 -> CString -> CInt -> Ptr a -> FunPtr (CB0006 a) -> IO CInt foreign import ccall "sqlite3_create_collation16" create_collation16 :: Ptr Sqlite3 -> CString -> CInt -> Ptr a -> FunPtr (CB0006 a) -> IO CInt foreign import ccall "sqlite3_create_collation_v2" create_collation_v2 :: Ptr Sqlite3 -> CString -> CInt -> Ptr a -> FunPtr (CB0006 a) -> FinalizerPtr a -> IO CInt foreign import ccall "sqlite3_create_function" create_function :: Ptr Sqlite3 -> CString -> CInt -> CInt -> Ptr a -> FunPtr (CB0007 Context Value) -> FunPtr (CB0007 Context Value) -> FunPtr (CB0008 Context) -> IO CInt foreign import ccall "sqlite3_create_function16" createFunction16 :: Ptr Sqlite3 -> CString -> CInt -> CInt -> Ptr a -> FunPtr (CB0007 Context Value) -> FunPtr (CB0007 Context Value) -> FunPtr (CB0008 Context) -> IO CInt foreign import ccall "sqlite3_data_count" data_count :: Ptr Stmt -> IO CInt foreign import ccall "sqlite3_db_handle" db_handle :: Ptr Stmt -> IO (Ptr Sqlite3) foreign import ccall "sqlite3_db_mutex" db_mutex :: Ptr Sqlite3 -> IO (Ptr Mutex) foreign import ccall "sqlite3_enable_load_extension" enable_load_extension :: Ptr Sqlite3 -> CInt -> IO CInt foreign import ccall "sqlite3_enable_shared_cache" enable_shared_cache :: CInt -> IO CInt foreign import ccall "sqlite3_errcode" errcode :: Ptr Sqlite3 -> IO CInt foreign import ccall "sqlite3_errmsg" errmsg :: Ptr Sqlite3 -> IO CString foreign import ccall "sqlite3_errmsg16" errmsg16 :: Ptr Sqlite3 -> IO CString foreign import ccall "sqlite3_exec" exec :: Ptr Sqlite3 -> CString -> FunPtr (CB0001 a) -> Ptr a -> Ptr CString -> IO CInt foreign import ccall "sqlite3_extended_result_codes" extended_result_codes :: Ptr Sqlite3 -> CInt -> IO CInt foreign import ccall "sqlite3_file_control" file_control :: Ptr Sqlite3 -> CString -> CInt -> Ptr a -> IO CInt foreign import ccall "sqlite3_finalize" finalize :: Ptr Stmt -> IO CInt foreign import ccall "sqlite3_free" free :: Ptr a -> IO () foreign import ccall "sqlite3_free_table" free_table :: Ptr CString -> IO () foreign import ccall "sqlite3_get_autocommit" get_autocommit :: Ptr Sqlite3 -> IO CInt foreign import ccall "sqlite3_get_auxdata" get_aux_data :: Ptr Sqlite3 -> CInt -> IO (Ptr a) foreign import ccall "sqlite3_get_table" get_table :: Ptr Sqlite3 -> CString -> Ptr (Ptr CString) -> Ptr CInt -> Ptr CInt -> Ptr CString foreign import ccall "sqlite3_interrupt" interrupt :: Ptr Sqlite3 -> IO () foreign import ccall "sqlite3_last_insert_rowid" last_insert_rowid :: Ptr Sqlite3 -> IO CInt64 foreign import ccall "sqlite3_libversion" libversion :: IO CString foreign import ccall "sqlite3_libversion_number" libversion_number :: IO CInt foreign import ccall "sqlite3_limit" limit :: Ptr Sqlite3 -> CInt -> CInt -> IO CInt foreign import ccall "sqlite3_load_extension" load_extension :: Ptr Sqlite3 -> CString -> CString -> Ptr CString -> IO CInt foreign import ccall "sqlite3_malloc" malloc :: CInt -> IO (Ptr a) foreign import ccall "sqlite3_memory_highwater" memory_highwater :: CInt -> IO CInt64 foreign import ccall "sqlite3_memory_used" memory_used :: IO CInt64 foreign import ccall "sqlite3_mutex_alloc" mutex_alloc :: CInt -> IO (Ptr Mutex) foreign import ccall "sqlite3_mutex_enter" mutex_enter :: Ptr Mutex -> IO () foreign import ccall "sqlite3_mutex_free" mutex_free :: Ptr Mutex -> IO () foreign import ccall "sqlite3_mutex_leave" mutex_leave :: Ptr Mutex -> IO () foreign import ccall "sqlite3_mutex_try" mutex_try :: Ptr Mutex -> IO CInt foreign import ccall "sqlite3_next_stmt" next_stmt :: Ptr Sqlite3 -> Ptr Stmt -> IO (Ptr Stmt) foreign import ccall "sqlite3_open" open :: CString -> Ptr (Ptr Sqlite3) -> IO CInt foreign import ccall "sqlite3_open16" open16 :: CString -> Ptr (Ptr Sqlite3) -> IO CInt foreign import ccall "sqlite3_open_v2" open_v2 :: CString -> Ptr (Ptr Sqlite3) -> CInt -> CString -> IO CInt foreign import ccall "sqlite3_prepare" prepare :: Ptr Sqlite3 -> CString -> CInt -> Ptr (Ptr Stmt) -> Ptr CString -> IO CInt foreign import ccall "sqlite3_prepare16" prepare16 :: Ptr Sqlite3 -> CString -> CInt -> Ptr (Ptr Stmt) -> Ptr CString -> IO CInt foreign import ccall "sqlite3_prepare16_v2" prepare16_v2 :: Ptr Sqlite3 -> CString -> CInt -> Ptr (Ptr Stmt) -> Ptr CString -> IO CInt foreign import ccall "sqlite3_prepare_v2" prepare_v2 :: Ptr Sqlite3 -> CString -> CInt -> Ptr (Ptr Stmt) -> Ptr CString -> IO CInt foreign import ccall "sqlite3_progress_handler" progress_handler :: Ptr Sqlite3 -> CInt -> FunPtr (CB0005 a) -> Ptr a -> IO () foreign import ccall "sqlite3_randomness" randomness :: CInt -> Ptr a -> IO () foreign import ccall "sqlite3_realloc" realloc :: Ptr a -> CInt -> IO (Ptr a) foreign import ccall "sqlite3_release_memory" release_memory :: CInt -> IO CInt foreign import ccall "sqlite3_reset" reset :: Ptr Stmt -> IO CInt foreign import ccall "sqlite3_reset_auto_extension" reset_auto_extension :: IO () foreign import ccall "sqlite3_result_blob" result_blob :: Ptr Context -> Ptr a -> CInt -> FinalizerPtr a -> IO () foreign import ccall "sqlite3_result_double" result_double :: Ptr Context -> CDouble -> IO () foreign import ccall "sqlite3_result_error" result_error :: Ptr Context -> CString -> IO () foreign import ccall "sqlite3_result_error16" result_error16 :: Ptr Context -> CString -> IO () foreign import ccall "sqlite3_result_error_code" result_error_code :: Ptr Context -> CInt -> IO () foreign import ccall "sqlite3_result_error_nomem" result_error_nomem :: Ptr Context -> IO () foreign import ccall "sqlite3_result_error_toobig" result_error_toobig :: Ptr Context -> IO () foreign import ccall "sqlite3_result_int" result_int :: Ptr Context -> CInt -> IO () foreign import ccall "sqlite3_result_int64" result_int64 :: Ptr Context -> CInt64 -> IO () foreign import ccall "sqlite3_result_null" result_null :: Ptr Context -> IO () foreign import ccall "sqlite3_result_text" result_text :: Ptr Context -> CString -> CInt -> FinalizerPtr CString -> IO () foreign import ccall "sqlite3_result_text16" result_text16 :: Ptr Context -> CString -> CInt -> FinalizerPtr CString -> IO () foreign import ccall "sqlite3_result_text16be" result_text16be :: Ptr Context -> CString -> CInt -> FinalizerPtr CString -> IO () foreign import ccall "sqlite3_result_text16le" result_text16le :: Ptr Context -> CString -> CInt -> FinalizerPtr CString -> IO () foreign import ccall "sqlite3_result_value" result_value :: Ptr Context -> Ptr Value -> IO () foreign import ccall "sqlite3_result_zeroblob" result_zeroblob :: Ptr Context -> CInt -> IO () foreign import ccall "sqlite3_rollback_hook" rollback_hook :: Ptr Sqlite3 -> FunPtr (CB0008 a) -> Ptr a -> IO (Ptr a) foreign import ccall "sqlite3_set_authorizer" set_authorizer :: Ptr Sqlite3 -> FunPtr (CB0009 a) -> Ptr a -> IO CInt foreign import ccall "sqlite3_set_auxdata" set_auxdata :: Ptr Context -> CInt -> Ptr a -> FinalizerPtr a -> IO () foreign import ccall "sqlite3_sleep" sleep :: CInt -> IO CInt foreign import ccall "sqlite3_soft_heap_limit" soft_heap_limit :: CInt -> IO () foreign import ccall "sqlite3_sql" sql :: Ptr Stmt -> IO CString foreign import ccall "sqlite3_step" step :: Ptr Stmt -> IO CInt foreign import ccall "sqlite3_threadsafe" threadsafe :: IO CInt foreign import ccall "sqlite3_total_changes" total_changes :: Ptr Sqlite3 -> IO CInt foreign import ccall "sqlite3_update_hook" update_hook :: Ptr Sqlite3 -> FunPtr (CB000A a) -> Ptr a -> IO (Ptr a) foreign import ccall "sqlite3_user_data" user_data :: Ptr Context -> IO (Ptr a) foreign import ccall "sqlite3_value_blob" value_blob :: Ptr Value -> IO (Ptr a) foreign import ccall "sqlite3_value_bytes" value_bytes :: Ptr Value -> IO CInt foreign import ccall "sqlite3_value_bytes16" value_bytes16 :: Ptr Value -> IO CInt foreign import ccall "sqlite3_value_double" value_double :: Ptr Value -> IO CDouble foreign import ccall "sqlite3_value_int" value_int :: Ptr Value -> IO CInt foreign import ccall "sqlite3_value_int64" value_int64 :: Ptr Value -> IO CInt64 foreign import ccall "sqlite3_value_numeric_type" value_numeric_type :: Ptr Value -> IO CInt foreign import ccall "sqlite3_value_text" value_text :: Ptr Value -> IO CString foreign import ccall "sqlite3_value_text16" value_text16 :: Ptr Value -> IO CString foreign import ccall "sqlite3_value_text16be" value_text16be :: Ptr Value -> IO CString foreign import ccall "sqlite3_value_text16le" value_text16le :: Ptr Value -> IO CString foreign import ccall "sqlite3_value_type" value_type :: Ptr Value -> IO CInt foreign import ccall "sqlite3_vfs_find" vfs_find :: CString -> IO (Ptr Vfs) foreign import ccall "sqlite3_vfs_register" vfs_register :: Ptr Vfs -> CInt -> IO CInt foreign import ccall "sqlite3_vfs_unregister" vfs_unregister :: Ptr Vfs -> IO CInt