Copyright | (c) Galois Inc. 2007 (c) figo GmbH 2016 |
---|---|
License | BSD3 |
Maintainer | figo GmbH <pacakge+haskell@figo.io> |
Stability | provisional |
Portability | Bindings to the SQLite/SQLCipher C interface. |
Safe Haskell | None |
Language | Haskell98 |
The documentation for these functions is at:
Documentation
sqlite3_exec :: SQLite -> CString -> SQLiteCallback ExecHandler -> SQLiteCallbackUserData -> Ptr CString -> IO Status Source #
sqlite3_interrupt :: SQLite -> IO () Source #
sqlite3_complete16 :: SQLiteUTF16 -> IO Bool Source #
sqlite3_busy_handler :: SQLite -> FunPtr (Ptr () -> CInt -> IO CInt) -> Ptr () -> IO Status Source #
sqlite3_get_table :: SQLite -> CString -> Ptr (Ptr CString) -> Ptr CInt -> Ptr CInt -> Ptr (Ptr CString) -> IO Status Source #
sqlite3_free :: Ptr () -> IO () Source #
sqlite3_set_authorizer :: SQLite -> FunPtr (Ptr () -> CInt -> CString -> CString -> CString -> CString -> IO Status) -> Ptr () -> IO Status Source #
sqlite3_profile :: SQLite -> FunPtr (Ptr () -> CString -> SQLiteInt64 -> IO ()) -> Ptr () -> IO (Ptr ()) Source #
sqlite3_progress_handler :: SQLite -> CInt -> FunPtr (Ptr () -> IO CInt) -> Ptr () -> IO () Source #
sqlite3_open16 :: SQLiteUTF16 -> Ptr SQLite -> IO Status Source #
sqlite3_errstr :: Status -> CString Source #
sqlite3_bind_blob :: SQLiteStmt -> CInt -> Ptr () -> CInt -> FunPtr (Ptr () -> IO ()) -> IO Status Source #
sqlite3_bind_double :: SQLiteStmt -> CInt -> Double -> IO Status Source #
sqlite3_bind_int :: SQLiteStmt -> CInt -> CInt -> IO Status Source #
sqlite3_bind_int64 :: SQLiteStmt -> CInt -> SQLiteInt64 -> IO Status Source #
sqlite3_bind_null :: SQLiteStmt -> CInt -> IO Status Source #
sqlite3_bind_text :: SQLiteStmt -> CInt -> CString -> CInt -> FunPtr (Ptr () -> IO ()) -> IO Status Source #
sqlite3_bind_text64 :: SQLiteStmt -> CInt -> CString -> SQLiteInt64 -> SQLiteCallback FreeHandler -> TextEncodeFlag -> IO Status Source #
sqlite3_bind_value :: SQLiteStmt -> CInt -> SQLiteValue -> IO Status Source #
sqlite3_bind_zeroblob :: SQLiteStmt -> CInt -> CInt -> IO Status Source #
sqlite3_bind_parameter_name :: SQLiteStmt -> CInt -> IO CString Source #
sqlite3_bind_parameter_index :: SQLiteStmt -> CString -> IO CInt Source #
sqlite3_stmt_readonly :: SQLiteStmt -> IO CInt Source #
sqlite3_column_count :: SQLiteStmt -> IO CInt Source #
sqlite3_column_name :: SQLiteStmt -> CInt -> IO CString Source #
sqlite3_column_decltype :: SQLiteStmt -> CInt -> IO CString Source #
sqlite3_step :: SQLiteStmt -> IO Status Source #
sqlite3_data_count :: SQLiteStmt -> IO Status Source #
sqlite3_column_blob :: SQLiteStmt -> CInt -> IO (Ptr ()) Source #
sqlite3_column_bytes :: SQLiteStmt -> CInt -> IO CInt Source #
sqlite3_column_bytes16 :: SQLiteStmt -> CInt -> IO CInt Source #
sqlite3_column_double :: SQLiteStmt -> CInt -> IO Double Source #
sqlite3_column_int :: SQLiteStmt -> CInt -> IO CInt Source #
sqlite3_column_int64 :: SQLiteStmt -> CInt -> IO SQLiteInt64 Source #
sqlite3_column_text :: SQLiteStmt -> CInt -> IO CString Source #
sqlite3_column_text16 :: SQLiteStmt -> CInt -> IO SQLiteUTF16 Source #
sqlite3_column_type :: SQLiteStmt -> CInt -> IO CInt Source #
sqlite3_column_value :: SQLiteStmt -> CInt -> IO SQLiteValue Source #
sqlite3_finalize :: SQLiteStmt -> IO Status Source #
sqlite3_create_function :: SQLite -> CString -> CInt -> TextEncodeFlag -> SQLiteCallbackUserData -> SQLiteCallback StepHandler -> SQLiteCallback StepHandler -> SQLiteCallback FinalizeContextHandler -> IO CInt Source #
sqlite3_value_bytes :: SQLiteValue -> IO CInt Source #
sqlite3_value_int :: SQLiteValue -> IO CInt Source #
sqlite3_user_data :: SQLiteContext -> IO (Ptr ()) Source #
sqlite3_get_auxdata :: SQLiteContext -> CInt -> IO (Ptr ()) Source #
sqlite3_set_auxdata :: SQLiteContext -> CInt -> Ptr () -> SQLiteCallback FreeHandler -> IO () Source #
sqlite3_result_blob :: SQLiteContext -> Ptr () -> CInt -> SQLiteCallback FreeHandler -> IO () Source #
sqlite3_result_double :: SQLiteContext -> Double -> IO () Source #
sqlite3_result_error :: SQLiteContext -> CString -> CInt -> IO () Source #
sqlite3_result_error16 :: SQLiteContext -> SQLiteUTF16 -> CInt -> IO () Source #
sqlite3_result_error_toobig :: SQLiteContext -> IO () Source #
sqlite3_result_int :: SQLiteContext -> CInt -> IO () Source #
sqlite3_result_int64 :: SQLiteContext -> SQLiteInt64 -> IO () Source #
sqlite3_result_null :: SQLiteContext -> IO () Source #
sqlite3_result_text :: SQLiteContext -> CString -> CInt -> SQLiteCallback FreeHandler -> IO () Source #
sqlite3_result_text16 :: SQLiteContext -> SQLiteUTF16 -> CInt -> SQLiteCallback FreeHandler -> IO () Source #
sqlite3_result_text16le :: SQLiteContext -> SQLiteUTF16 -> CInt -> SQLiteCallback FreeHandler -> IO () Source #
sqlite3_result_text16be :: SQLiteContext -> SQLiteUTF16 -> CInt -> SQLiteCallback FreeHandler -> IO () Source #
sqlite3_result_value :: SQLiteContext -> SQLiteValue -> IO () Source #
sqlite3_result_zeroblob :: SQLiteContext -> CInt -> IO () Source #
sqlite3_create_collation :: SQLite -> CString -> TextEncodeFlag -> SQLiteCallbackUserData -> SQLiteCallback CompareHandler -> IO Status Source #
sqlite3_create_collation16 :: SQLite -> SQLiteUTF16 -> TextEncodeFlag -> SQLiteCallbackUserData -> SQLiteCallback CompareHandler -> IO Status Source #
sqlite3_create_collation_v2 :: SQLite -> CString -> TextEncodeFlag -> SQLiteCallbackUserData -> SQLiteCallback CompareHandler -> SQLiteCallback FreeHandler -> IO Status Source #
sqlite3_collation_needed :: SQLite -> SQLiteCallbackUserData -> SQLiteCallback CollationHandler -> IO Status Source #
sqlite3_collation_needed16 :: SQLite -> SQLiteCallbackUserData -> SQLiteCallback CollationHandler16 -> IO Status Source #
sqlite3_set_temp_directory :: CString -> IO () Source #
sqlite3_db_handle :: SQLiteStmt -> IO SQLite Source #
sqlite3_commit_hook :: SQLite -> SQLiteCallback FilterHandler -> SQLiteCallbackUserData -> IO (SQLiteCallback FilterHandler) Source #
sqlite3_rollback_hook :: SQLite -> SQLiteCallback FreeHandler -> SQLiteCallbackUserData -> IO (SQLiteCallback FreeHandler) Source #
sqlite3_update_hook :: SQLite -> SQLiteCallback UpdateHook -> SQLiteCallbackUserData -> IO (SQLiteCallback FreeHandler) Source #
sqlite3_blob_open :: SQLite -> CString -> CString -> CString -> SQLiteInt64 -> Bool -> Ptr SQLiteBLOB -> IO Status Source #
sqlite3_blob_close :: SQLiteBLOB -> IO Status Source #
sqlite3_blob_bytes :: SQLiteBLOB -> IO CInt Source #
sqlite3_blob_read :: SQLiteBLOB -> Ptr () -> CInt -> CInt -> IO Status Source #
sqlite3_blob_write :: SQLiteBLOB -> Ptr () -> CInt -> CInt -> IO Status Source #
type ExecHandler = SQLiteCallbackUserData -> CInt -> Ptr CString -> Ptr CString -> IO Status Source #
type FreeHandler = SQLiteCallbackUserData -> IO () Source #
type UpdateHook = SQLiteCallbackUserData -> CInt -> CString -> CString -> SQLiteInt64 -> IO () Source #
type FilterHandler = SQLiteCallbackUserData -> IO Status Source #
type StepHandler = SQLiteContext -> CInt -> Ptr SQLiteValue -> IO () Source #
type FinalizeContextHandler = SQLiteContext -> IO () Source #
type CompareHandler = SQLiteCallbackUserData -> CInt -> Ptr () -> CInt -> Ptr () -> IO CInt Source #
type CollationHandler = SQLiteCallbackUserData -> SQLite -> TextEncodeFlag -> CString -> IO () Source #
type CollationHandler16 = SQLiteCallbackUserData -> SQLite -> TextEncodeFlag -> SQLiteUTF16 -> IO () Source #
mkUpdateHook :: UpdateHook -> IO (SQLiteCallback UpdateHook) Source #