Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data C'sqlite3
- data C'sqlite3_stmt
- data C'void
- data Database = Database {}
- data Statement = Statement {}
- data SqueatherErrorFlag
- data Error = Error {}
- sqlite3_extended_result_codes :: Ptr C'sqlite3 -> Int -> IO CInt
- sqlite3_open_v2 :: Ptr CChar -> Ptr (Ptr C'sqlite3) -> CInt -> Ptr CChar -> IO CInt
- sqlite3_errmsg :: Ptr C'sqlite3 -> IO (Ptr CChar)
- readUtf8 :: Ptr CChar -> IO Text
- writeUtf8 :: Text -> (Ptr CChar -> IO a) -> IO a
- writeUtf8Len :: Text -> ((Ptr CChar, Int) -> IO a) -> IO a
- checkError :: Database -> Text -> CInt -> IO ()
- checkInitError :: Text -> CInt -> IO ()
- checkStepError :: Database -> Text -> CInt -> IO StepResult
- open :: Text -> IO Database
- openWithFlags :: OpenFlags -> Text -> IO Database
- sqlite3_prepare_v2 :: Ptr C'sqlite3 -> Ptr CChar -> CInt -> Ptr (Ptr C'sqlite3_stmt) -> Ptr (Ptr CChar) -> IO CInt
- prepare :: Database -> Text -> IO Statement
- sqlite3_bind_parameter_index :: Ptr C'sqlite3_stmt -> Ptr CChar -> IO CInt
- getParameterIndex :: Statement -> Text -> IO CInt
- sqlite3_bind_blob :: Ptr C'sqlite3_stmt -> CInt -> Ptr a -> CInt -> FunPtr (Ptr a -> IO ()) -> IO CInt
- bindBlob :: Statement -> Text -> ByteString -> IO ()
- sqlite3_bind_double :: Ptr C'sqlite3_stmt -> CInt -> Double -> IO CInt
- bindDouble :: Statement -> Text -> Double -> IO ()
- sqlite3_bind_int64 :: Ptr C'sqlite3_stmt -> CInt -> Int64 -> IO CInt
- bindInt64 :: Statement -> Text -> Int64 -> IO ()
- sqlite3_bind_null :: Ptr C'sqlite3_stmt -> CInt -> IO CInt
- bindNull :: Statement -> Text -> IO ()
- sqlite3_bind_text :: Ptr C'sqlite3_stmt -> CInt -> Ptr CChar -> CInt -> FunPtr (Ptr a -> IO ()) -> IO CInt
- bindText :: Statement -> Text -> Text -> IO ()
- bindSqlData :: Statement -> Text -> SQLData -> IO ()
- sqlite3_step :: Ptr C'sqlite3_stmt -> IO CInt
- step :: Statement -> IO StepResult
- sqlite3_column_count :: Ptr C'sqlite3_stmt -> IO CInt
- sqlite3_column_bytes :: Ptr C'sqlite3_stmt -> CInt -> IO CInt
- sqlite3_column_type :: Ptr C'sqlite3_stmt -> CInt -> IO CInt
- sqlite3_column_blob :: Ptr C'sqlite3_stmt -> CInt -> IO (Ptr a)
- sqlite3_column_double :: Ptr C'sqlite3_stmt -> CInt -> IO Double
- sqlite3_column_int64 :: Ptr C'sqlite3_stmt -> CInt -> IO Int64
- sqlite3_column_text :: Ptr C'sqlite3_stmt -> CInt -> IO (Ptr CUChar)
- column :: Statement -> Int -> IO SQLData
- columnCount :: Statement -> IO Int
- columns :: Statement -> IO [SQLData]
- allRows :: Statement -> IO [[SQLData]]
- bindParams :: Statement -> [(Text, SQLData)] -> IO ()
- execute :: Database -> Text -> IO [[SQLData]]
- executeNamed :: Database -> Text -> [(Text, SQLData)] -> IO [[SQLData]]
- executeNamedWithColumns :: Database -> Text -> [(Text, SQLData)] -> IO ([Text], [[SQLData]])
- sqlite3_reset :: Ptr C'sqlite3_stmt -> IO CInt
- reset :: Statement -> IO ()
- sqlite3_clear_bindings :: Ptr C'sqlite3_stmt -> IO CInt
- clearBindings :: Statement -> IO ()
- sqlite3_finalize :: Ptr C'sqlite3_stmt -> IO CInt
- p_squeather_finalize :: FunPtr (Ptr C'sqlite3_stmt -> IO ())
- sqlite3_close_v2 :: Ptr C'sqlite3 -> IO CInt
- p_squeather_close_v2 :: FunPtr (Ptr C'sqlite3 -> IO ())
- type ExecCallback a = Ptr a -> CInt -> Ptr (Ptr CChar) -> Ptr (Ptr CChar) -> IO CInt
- sqlite3_exec :: Ptr C'sqlite3 -> Ptr CChar -> FunPtr (ExecCallback a) -> Ptr a -> Ptr (Ptr CChar) -> IO CInt
- sqlite3_free :: Ptr a -> IO ()
- exec :: Database -> Text -> IO ()
- sqlite3_last_insert_rowid :: Ptr C'sqlite3 -> IO Int64
- lastInsertRowId :: Database -> IO Int64
- intToCInt :: Text -> Text -> Int -> IO CInt
- intFromCInt :: Text -> Text -> CInt -> IO Int
- sqliteVersion :: String
- openFlags :: OpenFlags
- data C'sqlite3_backup
- sqlite3_backup_init :: Ptr C'sqlite3 -> Ptr CChar -> Ptr C'sqlite3 -> Ptr CChar -> IO (Ptr C'sqlite3_backup)
- sqlite3_backup_step :: Ptr C'sqlite3_backup -> CInt -> IO CInt
- sqlite3_backup_finish :: Ptr C'sqlite3_backup -> IO CInt
- sqlite3_backup_remaining :: Ptr C'sqlite3_backup -> IO CInt
- sqlite3_backup_pagecount :: Ptr C'sqlite3_backup -> IO CInt
- data Source = Source {}
- data Destination = Destination {}
- backup :: Source -> Destination -> IO ()
- sqlite3_changes :: Ptr C'sqlite3 -> IO CInt
- changes :: Database -> IO Int
- sqlite3_column_name :: Ptr C'sqlite3_stmt -> CInt -> IO (Ptr CChar)
- columnName :: Statement -> Int -> IO Text
- columnNames :: Statement -> IO [Text]
- sqlite3_threadsafe :: IO CInt
- sqlite3_initialize :: IO CInt
Documentation
data C'sqlite3_stmt Source #
SQLite3 statement handle
Database handle. To create a database handle, use open
.
The resources behind the handle are automatically destroyed when
there are no remaining references to the Database
, so Squeather
provides no close
function.
Database | |
|
Statement handle. To create a statement handle, use prepare
.
The resources behind the Statement are automatically destroyed
when there are no remaining references to the Statement
, so
Squeather provides no finalize
function.
Statement | |
|
data SqueatherErrorFlag Source #
Errors produced by the Squeather library (as opposed to being caused directly by the underlying SQLite3 C library.)
ParameterNotFound | Named parameter for SQL statement not found |
ExecFailed | The |
IntConversion | Failed to convert an |
UnknownColumnType CInt |
|
UnknownSqliteError CInt | SQLite returned an error code that is uknown to Squeather. |
IncompleteBackup | A backup was started, but it did not finish running. |
Bug | These failures should never happen and indicate a bug in Squeather. |
ColumnNameNull Int | The call to |
Instances
Eq SqueatherErrorFlag Source # | |
Defined in Squeather.Internal (==) :: SqueatherErrorFlag -> SqueatherErrorFlag -> Bool # (/=) :: SqueatherErrorFlag -> SqueatherErrorFlag -> Bool # | |
Ord SqueatherErrorFlag Source # | |
Defined in Squeather.Internal compare :: SqueatherErrorFlag -> SqueatherErrorFlag -> Ordering # (<) :: SqueatherErrorFlag -> SqueatherErrorFlag -> Bool # (<=) :: SqueatherErrorFlag -> SqueatherErrorFlag -> Bool # (>) :: SqueatherErrorFlag -> SqueatherErrorFlag -> Bool # (>=) :: SqueatherErrorFlag -> SqueatherErrorFlag -> Bool # max :: SqueatherErrorFlag -> SqueatherErrorFlag -> SqueatherErrorFlag # min :: SqueatherErrorFlag -> SqueatherErrorFlag -> SqueatherErrorFlag # | |
Show SqueatherErrorFlag Source # | |
Defined in Squeather.Internal showsPrec :: Int -> SqueatherErrorFlag -> ShowS # show :: SqueatherErrorFlag -> String # showList :: [SqueatherErrorFlag] -> ShowS # |
Exceptions. Squeather indicates all errors (even those arising from possible bugs) by throwing exceptions of this type.
Error | |
|
Instances
Eq Error Source # | |
Ord Error Source # | |
Show Error Source # | |
Exception Error Source # | |
Defined in Squeather.Internal toException :: Error -> SomeException # fromException :: SomeException -> Maybe Error # displayException :: Error -> String # |
writeUtf8 :: Text -> (Ptr CChar -> IO a) -> IO a Source #
Writes a UTF-8 text for foreign function use.
writeUtf8Len :: Text -> ((Ptr CChar, Int) -> IO a) -> IO a Source #
Like writeUtf8
but instead returns a CStringLen.
Checks SQLite return code. Throws an exception if the code is
an error. Otherwise, returns successfully. Do not use this
function if checking the return code from a function such as
sqlite3_step
; instead, use checkStepError
.
Like checkError
but for use only when using
sqlite3_initialize
.
:: Database | |
-> Text | Context |
-> CInt | |
-> IO StepResult |
Like checkError
but for use when using sqlite3_step
.
Prepares a statement. The corresponding C SQLite function allows you to pass in a multi-statement SQL text, and retrieve the unused portion for later use. Squeather does not allow this. Squeather will prepare only the first statement.
Gets the index of the parameter that has the given name.
Throws an Error
with ParameterNotFound
if the given parameter
name does not exist for this statement.
:: Ptr C'sqlite3_stmt | |
-> CInt | Index |
-> Ptr a | Blob |
-> CInt | Length |
-> FunPtr (Ptr a -> IO ()) | Callback to dispose of the blob. Use |
-> IO CInt |
:: Ptr C'sqlite3_stmt | |
-> CInt | Index |
-> IO CInt |
:: Ptr C'sqlite3_stmt | |
-> CInt | Index |
-> Ptr CChar | UTF-8 text |
-> CInt | Length |
-> FunPtr (Ptr a -> IO ()) | Callback to dispose of the string. Use |
-> IO CInt |
Binds a parameter with given SQL data to the given Statement
.
step :: Statement -> IO StepResult Source #
Evaluate a prepared statement. Returns Row
if the
Statement
has returned a row of data. In that case, use
column
or columns
to get individual columns or all columns,
respectively. Returns Done
if there is no data to retrieve.
In that case, step
should not be called again without first
calling reset
.
sqlite3_column_count :: Ptr C'sqlite3_stmt -> IO CInt Source #
The number of columns returned by the prepared statement. Can
be zero. However, just because this routine returns a positive
number does not mean that data will be returned. A SELECT
statement will always return a postive column count, but a
particular query might return no rows.
:: Ptr C'sqlite3_stmt | |
-> CInt | Column index |
-> IO CInt | Number of bytes in the column |
:: Ptr C'sqlite3_stmt | |
-> CInt | Index |
-> IO CInt |
:: Ptr C'sqlite3_stmt | |
-> CInt | Index |
-> IO (Ptr a) | Pointer to result |
sqlite3_column_double Source #
:: Ptr C'sqlite3_stmt | |
-> CInt | Index |
-> IO Double |
:: Ptr C'sqlite3_stmt | |
-> CInt | Index |
-> IO Int64 |
bindParams :: Statement -> [(Text, SQLData)] -> IO () Source #
Bind multiple named parameters to a Statement
.
Execute a query without any parameters. Executes only one
query - there is no need to terminate it with a semicolon,
although you can. If you use a semicolon-separated list of
queries, only the first query will be run. There is no way to
use SQL parameters; for that you will need executeNamed
.
:: Database | |
-> Text | SQL text |
-> [(Text, SQLData)] | Pairs, where each |
-> IO [[SQLData]] | All SQL data from the query. |
Execute a query with named parameters. Executes only one query - there is no need to terminate it with a semicolon, although you can. If you use a semicolon-separated list of queries, only the first query will be run.
executeNamedWithColumns Source #
:: Database | |
-> Text | SQL text |
-> [(Text, SQLData)] | Pairs, where each |
-> IO ([Text], [[SQLData]]) | The column names, and all SQL data from the query. |
Like executeNamed
but also returns the names of the columns
in addition to the SQL results.
reset :: Statement -> IO () Source #
Resets a Statement
so it may be re-executed. Does not clear
bindings. In SQLite, sqlite3_reset
returns an error code if
the most recent step statement returned an error. reset
does
not do this. It does not check the error code returned by
sqlite3_reset
.
sqlite3_finalize :: Ptr C'sqlite3_stmt -> IO CInt Source #
p_squeather_finalize :: FunPtr (Ptr C'sqlite3_stmt -> IO ()) Source #
type ExecCallback a Source #
= Ptr a | The fourth argument of |
-> CInt | The number of columns in the result |
-> Ptr (Ptr CChar) | An array of pointers to strings obtained as if from
|
-> Ptr (Ptr CChar) | An array of pointers to strings where each entry represents
the name of the corresponding result column as obtained from
|
-> IO CInt | The function should return zero if successful. If it returns
non-zero, then |
The type of the callback from sqlite3_exec
. This callback is
invoked for every row of data.
:: Database | |
-> Text | SQL to be evaluated. Multiple, semicolon-separated statements will be executed. |
-> IO () |
Evaluate one or more SQL statements. There is no way to obtain
the results; for that you will need execute
or executeNamed
.
There is no way to use SQL parameters; for that you will need
executeNamed
.
:: Text | Context. For error messages only. |
-> Text | Database filename. For error messages only. |
-> Int | |
-> IO CInt |
Convert from an Int to a CInt. Makes sure the conversion fits in the space allotted. Throws an exception if it doesn't fit.
:: Text | Context. For error messages only. |
-> Text | Database filename. For error messages only. |
-> CInt | |
-> IO Int |
Convert from an CInt to a Int. Makes sure the conversion fits in the space allotted. Throws an exception if it doesn't fit.
sqliteVersion :: String Source #
Returns a string which is the version number for SQLite used to build this library. SQLite is embedded into the library, so the only way to change the SQLite version is to recompile the library.
openFlags :: OpenFlags Source #
Default settings for OpenFlags
, where the writeMode
is ReadWrite
Create
, threadMode
is
Serialized
, cacheMode
is Private
, and all
other flags are set to False.
data C'sqlite3_backup Source #
:: Ptr C'sqlite3 | Destination database handle |
-> Ptr CChar | Destination database name - |
-> Ptr C'sqlite3 | Source database handle |
-> Ptr CChar | Source database name |
-> IO (Ptr C'sqlite3_backup) | Returns pointer to backup object |
:: Ptr C'sqlite3_backup | |
-> CInt | Number of pages. If negative, copy all remaining source pages. |
-> IO CInt | Returns error code |
sqlite3_backup_finish Source #
:: Ptr C'sqlite3_backup | |
-> IO CInt | Returns error code |
sqlite3_backup_remaining Source #
:: Ptr C'sqlite3_backup | |
-> IO CInt | Returns number of pages remaining to be backed up |
sqlite3_backup_pagecount Source #
:: Ptr C'sqlite3_backup | |
-> IO CInt | Returns number of pages in source database |
Backup source
Source | |
|
data Destination Source #
Backup destination
Destination | |
|
Instances
Eq Destination Source # | |
Defined in Squeather.Internal (==) :: Destination -> Destination -> Bool # (/=) :: Destination -> Destination -> Bool # | |
Ord Destination Source # | |
Defined in Squeather.Internal compare :: Destination -> Destination -> Ordering # (<) :: Destination -> Destination -> Bool # (<=) :: Destination -> Destination -> Bool # (>) :: Destination -> Destination -> Bool # (>=) :: Destination -> Destination -> Bool # max :: Destination -> Destination -> Destination # min :: Destination -> Destination -> Destination # | |
Show Destination Source # | |
Defined in Squeather.Internal showsPrec :: Int -> Destination -> ShowS # show :: Destination -> String # showList :: [Destination] -> ShowS # |
backup :: Source -> Destination -> IO () Source #
Use the SQLite backup API to copy the content of one database to another. Can be used to safely copy databases while they are in use, or to copy in-memory databases to or from persistent files.
changes :: Database -> IO Int Source #
Count the number of rows modified by the most recent INSERT
,
UPDATE
, or DELETE
statement.
sqlite3_column_name :: Ptr C'sqlite3_stmt -> CInt -> IO (Ptr CChar) Source #
Gets the name of a column. The name is the value of the AS
clause if it exists, or is an undefined string otherwise.
sqlite3_threadsafe :: IO CInt Source #
Returns zero if mutexing code was omitted.
sqlite3_initialize :: IO CInt Source #
Initialize the SQLite library, see