#include #include -- | module Bindings.Sqlite3 where #strict_import #opaque_t sqlite3_context #starttype sqlite3_file #field pMethods , Ptr #stoptype #starttype sqlite3_io_methods #field iVersion , CInt #field xClose , FunPtr (Ptr -> IO CInt) #field xRead , FunPtr (Ptr -> Ptr () -> \ CInt -> Int64 -> IO CInt) #field xWrite , FunPtr (Ptr -> Ptr () -> \ CInt -> Int64 -> IO ()) #field xTruncate , FunPtr (Ptr -> \ Int64 -> IO CInt) #field xSync , FunPtr (Ptr -> CInt -> IO CInt) #field xFileSize , FunPtr (Ptr -> \ Ptr Int64 -> IO CInt) #field xLock , FunPtr (Ptr -> CInt -> IO CInt) #field xUnlock , FunPtr (Ptr -> CInt -> IO CInt) #field xCheckReservedLock , FunPtr (Ptr -> \ Ptr CInt -> IO CInt) #field xFileControl , FunPtr (Ptr -> \ CInt -> Ptr () -> IO CInt) #field xSectorSize , FunPtr (Ptr -> IO CInt) #field xDeviceCharacteristics , FunPtr (Ptr -> \ IO CInt) #stoptype #opaque_t sqlite3_mutex #globalvar sqlite3_temp_directory , CString #starttype sqlite3_vfs #field iVersion , CInt #field szOsFile , CInt #field mxPathname , CInt #field pNext , Ptr #field zName , CString #field pAppData , Ptr () #field xOpen , FunPtr (Ptr -> CString -> \ Ptr -> CInt -> Ptr CInt -> IO CInt) #field xDelete , FunPtr (Ptr -> \ CString -> CInt -> IO CInt) #field xAccess , FunPtr (Ptr -> CString -> \ CInt -> Ptr CInt -> IO CInt) #field xFullPathname , FunPtr (Ptr -> \ CString -> CInt -> CString -> IO CInt) #field xDlOpen , FunPtr (Ptr -> CString -> IO (Ptr ())) #field xDlError , FunPtr (Ptr -> \ CInt -> CString -> IO ()) #field xDlSym , FunPtr (Ptr -> \ Ptr () -> CString -> IO (FunPtr (IO ()))) #field xDlClose , FunPtr (Ptr -> Ptr () -> IO ()) #field xRandomness , FunPtr (Ptr -> \ CInt -> CString -> IO CInt) #field xSleep , FunPtr (Ptr -> CInt -> IO CInt) #field xCurrentTime , FunPtr (Ptr -> \ Ptr CDouble -> IO CInt) #field xGetLastError , FunPtr (Ptr -> \ CInt -> CString -> IO CInt) #stoptype #ccall sqlite3_aggregate_context , Ptr -> \ CInt -> IO (Ptr ()) #ccall sqlite3_auto_extension , FunPtr (IO ()) -> IO CInt #ccall sqlite3_bind_parameter_count , Ptr -> IO CInt #ccall sqlite3_bind_parameter_index , Ptr -> \ CString -> IO CInt #ccall sqlite3_bind_parameter_name , Ptr -> \ CInt -> IO CString #ccall sqlite3_blob_bytes , Ptr -> IO CInt #ccall sqlite3_blob_close , Ptr -> IO CInt #ccall sqlite3_blob_open , Ptr -> CString -> CString -> \ CString -> Int64 -> CInt -> Ptr (Ptr ) -> \ IO CInt #ccall sqlite3_blob_read , Ptr -> Ptr () -> \ CInt -> CInt -> IO CInt #ccall sqlite3_blob_write , Ptr -> Ptr () -> \ CInt -> CInt -> IO CInt #ccall sqlite3_busy_handler , Ptr -> FunPtr (Ptr () -> \ CInt -> IO CInt) -> Ptr () -> IO CInt #ccall sqlite3_busy_timeout , Ptr -> CInt -> IO CInt #ccall sqlite3_changes , Ptr -> IO CInt #ccall sqlite3_clear_bindings , Ptr -> IO CInt #ccall sqlite3_close , Ptr -> IO CInt #ccall sqlite3_column_count , Ptr -> IO CInt #ccall sqlite3_context_db_handle , Ptr -> \ IO (Ptr ) #ccall sqlite3_data_count , Ptr -> IO CInt #ccall sqlite3_db_handle , Ptr -> IO (Ptr ) #ccall sqlite3_db_mutex , Ptr -> IO (Ptr ) #ccall sqlite3_enable_load_extension , Ptr -> CInt -> IO CInt #ccall sqlite3_exec , Ptr -> CString -> FunPtr (Ptr () -> \ CInt -> Ptr CString -> Ptr CString -> IO CInt) -> Ptr () -> \ Ptr CString -> IO CInt #ccall sqlite3_extended_result_codes , Ptr -> CInt -> IO CInt #ccall sqlite3_file_control , Ptr -> CString -> CInt -> \ Ptr () -> IO CInt #ccall sqlite3_finalize , Ptr -> IO CInt #ccall sqlite3_interrupt , Ptr -> IO () #ccall sqlite3_last_insert_rowid , Ptr -> IO Int64 #ccall sqlite3_limit , Ptr -> CInt -> CInt -> IO CInt #ccall sqlite3_load_extension , Ptr -> CString -> \ CString -> Ptr CString -> IO CInt #ccall sqlite3_next_stmt , Ptr -> Ptr -> \ IO (Ptr ) #ccall sqlite3_progress_handler , Ptr -> CInt -> \ FunPtr (Ptr () -> IO CInt) -> Ptr () -> IO () #ccall sqlite3_randomness , CInt -> Ptr () -> IO () #ccall sqlite3_release_memory , CInt -> IO CInt #ccall sqlite3_reset , Ptr -> IO CInt #ccall sqlite3_reset_auto_extension , IO () #ccall sqlite3_set_authorizer , Ptr -> FunPtr (Ptr () -> \ CInt -> CString -> CString -> CString -> CString -> IO CInt) -> \ Ptr () -> IO CInt #ccall sqlite3_sleep , CInt -> IO CInt #ccall sqlite3_soft_heap_limit , CInt -> IO () #ccall sqlite3_sql , Ptr -> IO CString #ccall sqlite3_step , Ptr -> IO CInt #ccall sqlite3_table_column_metadata , Ptr -> CString -> \ CString -> CString -> Ptr CString -> Ptr CString -> Ptr CInt -> \ Ptr CInt -> Ptr CInt -> IO CInt #ccall sqlite3_threadsafe , IO CInt #ccall sqlite3_total_changes , Ptr -> IO CInt #ccall sqlite3_update_hook , Ptr -> FunPtr (Ptr () -> \ CInt -> CString -> CString -> Int64 -> IO ()) -> \ Ptr () -> IO (Ptr ()) #ccall sqlite3_user_data , Ptr -> IO (Ptr ()) #num SQLITE_OK #num SQLITE_ERROR #num SQLITE_INTERNAL #num SQLITE_PERM #num SQLITE_ABORT #num SQLITE_BUSY #num SQLITE_LOCKED #num SQLITE_NOMEM #num SQLITE_READONLY #num SQLITE_INTERRUPT #num SQLITE_IOERR #num SQLITE_CORRUPT #num SQLITE_NOTFOUND #num SQLITE_FULL #num SQLITE_CANTOPEN #num SQLITE_PROTOCOL #num SQLITE_EMPTY #num SQLITE_SCHEMA #num SQLITE_TOOBIG #num SQLITE_CONSTRAINT #num SQLITE_MISMATCH #num SQLITE_MISUSE #num SQLITE_NOLFS #num SQLITE_AUTH #num SQLITE_FORMAT #num SQLITE_RANGE #num SQLITE_NOTADB #num SQLITE_ROW #num SQLITE_DONE #num SQLITE_ACCESS_EXISTS #num SQLITE_ACCESS_READWRITE #num SQLITE_ACCESS_READ #num SQLITE_CREATE_INDEX #num SQLITE_CREATE_TABLE #num SQLITE_CREATE_TEMP_INDEX #num SQLITE_CREATE_TEMP_TABLE #num SQLITE_CREATE_TEMP_TRIGGER #num SQLITE_CREATE_TEMP_VIEW #num SQLITE_CREATE_TRIGGER #num SQLITE_CREATE_VIEW #num SQLITE_DELETE #num SQLITE_DROP_INDEX #num SQLITE_DROP_TABLE #num SQLITE_DROP_TEMP_INDEX #num SQLITE_DROP_TEMP_TABLE #num SQLITE_DROP_TEMP_TRIGGER #num SQLITE_DROP_TEMP_VIEW #num SQLITE_DROP_TRIGGER #num SQLITE_DROP_VIEW #num SQLITE_INSERT #num SQLITE_PRAGMA #num SQLITE_READ #num SQLITE_SELECT #num SQLITE_TRANSACTION #num SQLITE_UPDATE #num SQLITE_ATTACH #num SQLITE_DETACH #num SQLITE_ALTER_TABLE #num SQLITE_REINDEX #num SQLITE_ANALYZE #num SQLITE_CREATE_VTABLE #num SQLITE_DROP_VTABLE #num SQLITE_FUNCTION #num SQLITE_SAVEPOINT #num SQLITE_COPY #num SQLITE_UTF8 #num SQLITE_UTF16LE #num SQLITE_UTF16BE #num SQLITE_UTF16 #num SQLITE_ANY #num SQLITE_UTF16_ALIGNED #num SQLITE_INTEGER #num SQLITE_FLOAT #num SQLITE_BLOB #num SQLITE_NULL #num SQLITE_TEXT #num SQLITE3_TEXT #num SQLITE_DENY #num SQLITE_IGNORE #num SQLITE_FCNTL_LOCKSTATE #num SQLITE_GET_LOCKPROXYFILE #num SQLITE_SET_LOCKPROXYFILE #num SQLITE_LAST_ERRNO #num SQLITE_IOCAP_ATOMIC #num SQLITE_IOCAP_ATOMIC512 #num SQLITE_IOCAP_ATOMIC1K #num SQLITE_IOCAP_ATOMIC2K #num SQLITE_IOCAP_ATOMIC4K #num SQLITE_IOCAP_ATOMIC8K #num SQLITE_IOCAP_ATOMIC16K #num SQLITE_IOCAP_ATOMIC32K #num SQLITE_IOCAP_ATOMIC64K #num SQLITE_IOCAP_SAFE_APPEND #num SQLITE_IOCAP_SEQUENTIAL #num SQLITE_IOERR_READ #num SQLITE_IOERR_SHORT_READ #num SQLITE_IOERR_WRITE #num SQLITE_IOERR_FSYNC #num SQLITE_IOERR_DIR_FSYNC #num SQLITE_IOERR_TRUNCATE #num SQLITE_IOERR_FSTAT #num SQLITE_IOERR_UNLOCK #num SQLITE_IOERR_RDLOCK #num SQLITE_IOERR_DELETE #num SQLITE_IOERR_BLOCKED #num SQLITE_IOERR_NOMEM #num SQLITE_IOERR_ACCESS #num SQLITE_IOERR_CHECKRESERVEDLOCK #num SQLITE_IOERR_LOCK #num SQLITE_IOERR_CLOSE #num SQLITE_IOERR_DIR_CLOSE -- num SQLITE_LOCKED_SHAREDCACHE #num SQLITE_LIMIT_LENGTH #num SQLITE_LIMIT_SQL_LENGTH #num SQLITE_LIMIT_COLUMN #num SQLITE_LIMIT_EXPR_DEPTH #num SQLITE_LIMIT_COMPOUND_SELECT #num SQLITE_LIMIT_VDBE_OP #num SQLITE_LIMIT_FUNCTION_ARG #num SQLITE_LIMIT_ATTACHED #num SQLITE_LIMIT_LIKE_PATTERN_LENGTH #num SQLITE_LIMIT_VARIABLE_NUMBER -- num SQLITE_LIMIT_TRIGGER_DEPTH #num SQLITE_LOCK_NONE #num SQLITE_LOCK_SHARED #num SQLITE_LOCK_RESERVED #num SQLITE_LOCK_PENDING #num SQLITE_LOCK_EXCLUSIVE #num SQLITE_MUTEX_FAST #num SQLITE_MUTEX_RECURSIVE #num SQLITE_MUTEX_STATIC_MASTER #num SQLITE_MUTEX_STATIC_MEM #num SQLITE_MUTEX_STATIC_MEM2 -- num SQLITE_MUTEX_STATIC_OPEN #num SQLITE_MUTEX_STATIC_PRNG #num SQLITE_MUTEX_STATIC_LRU #num SQLITE_MUTEX_STATIC_LRU2 #num SQLITE_OPEN_READONLY #num SQLITE_OPEN_READWRITE #num SQLITE_OPEN_CREATE #num SQLITE_OPEN_DELETEONCLOSE #num SQLITE_OPEN_EXCLUSIVE #num SQLITE_OPEN_MAIN_DB #num SQLITE_OPEN_TEMP_DB #num SQLITE_OPEN_TRANSIENT_DB #num SQLITE_OPEN_MAIN_JOURNAL #num SQLITE_OPEN_TEMP_JOURNAL #num SQLITE_OPEN_SUBJOURNAL #num SQLITE_OPEN_MASTER_JOURNAL #num SQLITE_OPEN_NOMUTEX #num SQLITE_OPEN_FULLMUTEX #num SQLITE_OPEN_SHAREDCACHE #num SQLITE_OPEN_PRIVATECACHE #pointer SQLITE_VERSION #num SQLITE_VERSION_NUMBER #pointer SQLITE_SOURCE_ID -- pointer SQLITE_SOURCE_ID #callback sqlite3_destructor_type , FunPtr (Ptr () -> IO ()) #function_pointer SQLITE_STATIC #function_pointer SQLITE_TRANSIENT #num SQLITE_SYNC_NORMAL #num SQLITE_SYNC_FULL #num SQLITE_SYNC_DATAONLY #num SQLITE_TESTCTRL_PRNG_SAVE #num SQLITE_TESTCTRL_PRNG_RESTORE #num SQLITE_TESTCTRL_PRNG_RESET #num SQLITE_TESTCTRL_BITVEC_TEST #num SQLITE_TESTCTRL_FAULT_INSTALL #num SQLITE_TESTCTRL_BENIGN_MALLOC_HOOKS -- num SQLITE_TESTCTRL_PENDING_BYTE -- num SQLITE_TESTCTRL_ASSERT -- num SQLITE_TESTCTRL_ALWAYS -- num SQLITE_TESTCTRL_RESERVE #opaque_t sqlite3_blob #opaque_t sqlite3 #opaque_t sqlite3_stmt #opaque_t sqlite3_value #ccall sqlite3_collation_needed , Ptr -> \ Ptr () -> FunPtr (Ptr () -> Ptr -> CInt -> \ CString -> IO ()) -> IO CInt #ccall sqlite3_collation_needed16 , Ptr -> \ Ptr () -> FunPtr (Ptr () -> Ptr -> CInt -> \ Ptr () -> IO ()) -> IO CInt #ccall sqlite3_column_database_name , Ptr -> \ CInt -> IO CString #ccall sqlite3_column_database_name16 , Ptr -> \ CInt -> IO (Ptr ()) #ccall sqlite3_column_table_name , Ptr -> \ CInt -> IO CString #ccall sqlite3_column_table_name16 , Ptr -> \ CInt -> IO (Ptr ()) #ccall sqlite3_column_origin_name , Ptr -> \ CInt -> IO CString #ccall sqlite3_column_origin_name16 , Ptr -> \ CInt -> IO (Ptr ()) #ccall sqlite3_column_decltype , Ptr -> \ CInt -> IO CString #ccall sqlite3_column_decltype16 , Ptr -> \ CInt -> IO (Ptr ()) #ccall sqlite3_column_name , Ptr -> CInt -> \ IO CString #ccall sqlite3_column_name16 , Ptr -> CInt -> \ IO (Ptr ()) #ccall sqlite3_commit_hook , Ptr -> FunPtr (Ptr () -> \ IO CInt) -> Ptr () -> IO (Ptr ()) #ccall sqlite3_rollback_hook , Ptr -> FunPtr (Ptr () -> \ IO ()) -> Ptr () -> IO (Ptr ()) #ccall sqlite3_complete , CString -> IO CInt #ccall sqlite3_complete16 , Ptr () -> IO CInt #ccall sqlite3_create_collation , Ptr -> CString -> \ CInt -> Ptr () -> FunPtr (Ptr () -> CInt -> Ptr () -> \ CInt -> Ptr () -> IO CInt) -> IO CInt #ccall sqlite3_create_collation_v2 , Ptr -> CString -> \ CInt -> Ptr () -> FunPtr (Ptr () -> CInt -> Ptr () -> \ CInt -> Ptr () -> IO CInt) -> FunPtr (Ptr () -> IO ()) -> IO CInt #ccall sqlite3_create_collation16 , Ptr -> Ptr () -> \ CInt -> Ptr () -> FunPtr (Ptr () -> CInt -> Ptr () -> \ CInt -> Ptr () -> IO CInt) -> IO CInt #ccall sqlite3_errcode , Ptr -> IO CInt #ccall sqlite3_extended_errcode , Ptr -> IO CInt #ccall sqlite3_errmsg , Ptr -> IO CString #ccall sqlite3_errmsg16 , Ptr -> IO (Ptr ()) #ccall sqlite3_malloc , CInt -> IO (Ptr ()) #ccall sqlite3_realloc , Ptr () -> CInt -> IO (Ptr ()) #ccall sqlite3_free , Ptr () -> IO () #ccall sqlite3_get_table , Ptr -> CString -> \ Ptr (Ptr CString) -> Ptr CInt -> Ptr CInt -> \ Ptr CString -> IO CInt #ccall sqlite3_free_table , Ptr CString -> IO () #ccall sqlite3_get_auxdata , Ptr -> \ CInt -> IO (Ptr ()) #ccall sqlite3_set_auxdata , Ptr -> CInt -> \ Ptr () -> FunPtr (Ptr () -> IO ()) -> IO () #ccall sqlite3_initialize , IO CInt #ccall sqlite3_shutdown , IO CInt #ccall sqlite3_os_init , IO CInt #ccall sqlite3_os_end , IO CInt #globalarray sqlite3_version , CChar #ccall sqlite3_libversion , IO CString #ccall sqlite3_sourceid , IO CString #ccall sqlite3_libversion_number , IO CInt #ccall sqlite3_memory_used , IO Int64 #ccall sqlite3_memory_highwater , CInt -> IO Int64 #ccall sqlite3_mutex_alloc , CInt -> IO (Ptr ) #ccall sqlite3_mutex_free , Ptr -> IO () #ccall sqlite3_mutex_enter , Ptr -> IO () #ccall sqlite3_mutex_try , Ptr -> IO CInt #ccall sqlite3_mutex_leave , Ptr -> IO () -- ccall sqlite3_mutex_held , Ptr -> IO CInt -- ccall sqlite3_mutex_notheld , Ptr -> IO CInt #ccall sqlite3_open , CString -> Ptr (Ptr ) -> IO CInt #ccall sqlite3_open16 , Ptr () -> Ptr (Ptr ) -> IO CInt #ccall sqlite3_open_v2 , CString -> Ptr (Ptr ) -> \ CInt -> CString -> IO CInt #ccall sqlite3_result_blob , Ptr -> Ptr () -> \ CInt -> FunPtr (Ptr () -> IO ()) -> IO () #ccall sqlite3_result_double , Ptr -> \ CDouble -> IO () #ccall sqlite3_result_error , Ptr -> \ CString -> CInt -> IO () #ccall sqlite3_result_error16 , Ptr -> \ Ptr () -> CInt -> IO () #ccall sqlite3_result_error_toobig , Ptr -> IO () #ccall sqlite3_result_error_nomem , Ptr -> IO () #ccall sqlite3_result_error_code , Ptr -> \ CInt -> IO () #ccall sqlite3_result_int , Ptr -> CInt -> IO () #ccall sqlite3_result_int64 , Ptr -> Int64 -> IO () #ccall sqlite3_result_null , Ptr -> IO () #ccall sqlite3_result_text , Ptr -> CString -> \ CInt -> FunPtr (Ptr () -> IO ()) -> IO () #ccall sqlite3_result_text16 , Ptr -> Ptr () -> \ CInt -> FunPtr (Ptr () -> IO ()) -> IO () #ccall sqlite3_result_text16le , Ptr -> Ptr () -> \ CInt -> FunPtr (Ptr () -> IO ()) -> IO () #ccall sqlite3_result_text16be , Ptr -> Ptr () -> \ CInt -> FunPtr (Ptr () -> IO ()) -> IO () #ccall sqlite3_result_value , Ptr -> \ Ptr -> IO () #ccall sqlite3_result_zeroblob , Ptr -> \ CInt -> IO () #ccall sqlite3_value_blob , Ptr -> IO (Ptr ()) #ccall sqlite3_value_bytes , Ptr -> IO CInt #ccall sqlite3_value_bytes16 , Ptr -> IO CInt #ccall sqlite3_value_double , Ptr -> IO CDouble #ccall sqlite3_value_int , Ptr -> IO CInt #ccall sqlite3_value_int64 , Ptr -> IO Int64 #ccall sqlite3_value_text , Ptr -> IO (Ptr CUChar) #ccall sqlite3_value_text16 , Ptr -> IO (Ptr ()) #ccall sqlite3_value_text16le , Ptr -> IO (Ptr ()) #ccall sqlite3_value_text16be , Ptr -> IO (Ptr ()) #ccall sqlite3_value_type , Ptr -> IO CInt #ccall sqlite3_value_numeric_type , Ptr -> IO CInt #ccall sqlite3_vfs_find , CString -> IO (Ptr ) #ccall sqlite3_vfs_register , Ptr -> CInt -> IO CInt #ccall sqlite3_vfs_unregister , Ptr -> IO CInt #ccall sqlite3_bind_blob , Ptr -> CInt -> \ Ptr () -> CInt -> FunPtr (Ptr () -> IO ()) -> IO CInt #ccall sqlite3_bind_double , Ptr -> CInt -> \ CDouble -> IO CInt #ccall sqlite3_bind_int , Ptr -> CInt -> \ CInt -> IO CInt #ccall sqlite3_bind_int64 , Ptr -> CInt -> \ Int64 -> IO CInt #ccall sqlite3_bind_null , Ptr -> CInt -> IO CInt #ccall sqlite3_bind_text , Ptr -> CInt -> \ CString -> CInt -> FunPtr (Ptr () -> IO ()) -> IO CInt #ccall sqlite3_bind_text16 , Ptr -> CInt -> \ Ptr () -> CInt -> FunPtr (Ptr () -> IO ()) -> IO CInt #ccall sqlite3_bind_value , Ptr -> CInt -> \ Ptr -> IO CInt #ccall sqlite3_bind_zeroblob , Ptr -> CInt -> \ CInt -> IO CInt #ccall sqlite3_prepare , Ptr -> CString -> CInt -> \ Ptr (Ptr ) -> Ptr CString -> IO CInt #ccall sqlite3_prepare_v2 , Ptr -> CString -> CInt -> \ Ptr (Ptr ) -> Ptr CString -> IO CInt #ccall sqlite3_prepare16 , Ptr -> Ptr () -> CInt -> \ Ptr (Ptr ) -> Ptr (Ptr ()) -> IO CInt #ccall sqlite3_prepare16_v2 , Ptr -> Ptr () -> CInt -> \ Ptr (Ptr ) -> Ptr (Ptr ()) -> IO CInt #ccall sqlite3_create_function , Ptr -> CString -> \ CInt -> CInt -> Ptr () -> FunPtr (Ptr -> \ CInt -> Ptr (Ptr ) -> IO ()) -> \ FunPtr (Ptr -> CInt -> \ Ptr (Ptr ) -> IO ()) -> \ FunPtr (Ptr -> IO ()) -> IO CInt #ccall sqlite3_create_function16 , Ptr -> Ptr () -> CInt -> \ CInt -> Ptr () -> FunPtr (Ptr -> CInt -> \ Ptr (Ptr ) -> IO ()) -> \ FunPtr (Ptr -> CInt -> \ Ptr (Ptr ) -> IO ()) -> \ FunPtr (Ptr -> IO ()) -> IO CInt #ccall sqlite3_get_autocommit , Ptr -> IO CInt #ccall sqlite3_column_blob , Ptr -> CInt -> IO (Ptr ()) #ccall sqlite3_column_bytes , Ptr -> CInt -> IO CInt #ccall sqlite3_column_bytes16 , Ptr -> CInt -> IO CInt #ccall sqlite3_column_double , Ptr -> CInt -> IO CDouble #ccall sqlite3_column_int , Ptr -> CInt -> IO CInt #ccall sqlite3_column_int64 , Ptr -> \ CInt -> IO Int64 #ccall sqlite3_column_text , Ptr -> \ CInt -> IO (Ptr CUChar) #ccall sqlite3_column_text16 , Ptr -> CInt -> IO (Ptr ()) #ccall sqlite3_column_type , Ptr -> CInt -> IO CInt #ccall sqlite3_column_value , Ptr -> \ CInt -> IO (Ptr ) #ccall sqlite3_enable_shared_cache , CInt -> IO CInt