Safe Haskell | None |
---|
This API is a slightly lower-level version of Database.SQLite3. Namely:
- open :: Utf8 -> IO (Either (Error, Utf8) Database)
- close :: Database -> IO (Either Error ())
- errmsg :: Database -> IO Utf8
- setTrace :: Database -> Maybe (Utf8 -> IO ()) -> IO ()
- getAutoCommit :: Database -> IO Bool
- exec :: Database -> Utf8 -> IO (Either (Error, Utf8) ())
- execWithCallback :: Database -> Utf8 -> ExecCallback -> IO (Either (Error, Utf8) ())
- type ExecCallback = ColumnCount -> [Utf8] -> [Maybe Utf8] -> IO ()
- prepare :: Database -> Utf8 -> IO (Either Error (Maybe Statement))
- getStatementDatabase :: Statement -> IO Database
- step :: Statement -> IO (Either Error StepResult)
- reset :: Statement -> IO (Either Error ())
- finalize :: Statement -> IO (Either Error ())
- clearBindings :: Statement -> IO ()
- statementSql :: Statement -> IO (Maybe Utf8)
- bindParameterCount :: Statement -> IO ParamIndex
- bindParameterName :: Statement -> ParamIndex -> IO (Maybe Utf8)
- bindParameterIndex :: Statement -> Utf8 -> IO (Maybe ParamIndex)
- columnCount :: Statement -> IO ColumnCount
- columnName :: Statement -> ColumnIndex -> IO (Maybe Utf8)
- bindInt64 :: Statement -> ParamIndex -> Int64 -> IO (Either Error ())
- bindDouble :: Statement -> ParamIndex -> Double -> IO (Either Error ())
- bindText :: Statement -> ParamIndex -> Utf8 -> IO (Either Error ())
- bindBlob :: Statement -> ParamIndex -> ByteString -> IO (Either Error ())
- bindNull :: Statement -> ParamIndex -> IO (Either Error ())
- columnType :: Statement -> ColumnIndex -> IO ColumnType
- columnInt64 :: Statement -> ColumnIndex -> IO Int64
- columnDouble :: Statement -> ColumnIndex -> IO Double
- columnText :: Statement -> ColumnIndex -> IO Utf8
- columnBlob :: Statement -> ColumnIndex -> IO ByteString
- lastInsertRowId :: Database -> IO Int64
- changes :: Database -> IO Int
- totalChanges :: Database -> IO Int
- interrupt :: Database -> IO ()
- newtype Database = Database (Ptr CDatabase)
- newtype Statement = Statement (Ptr CStatement)
- data ColumnType
- = IntegerColumn
- | FloatColumn
- | TextColumn
- | BlobColumn
- | NullColumn
- data StepResult
- data Error
- = ErrorOK
- | ErrorError
- | ErrorInternal
- | ErrorPermission
- | ErrorAbort
- | ErrorBusy
- | ErrorLocked
- | ErrorNoMemory
- | ErrorReadOnly
- | ErrorInterrupt
- | ErrorIO
- | ErrorCorrupt
- | ErrorNotFound
- | ErrorFull
- | ErrorCan'tOpen
- | ErrorProtocol
- | ErrorEmpty
- | ErrorSchema
- | ErrorTooBig
- | ErrorConstraint
- | ErrorMismatch
- | ErrorMisuse
- | ErrorNoLargeFileSupport
- | ErrorAuthorization
- | ErrorFormat
- | ErrorRange
- | ErrorNotADatabase
- | ErrorRow
- | ErrorDone
- newtype Utf8 = Utf8 ByteString
- newtype ParamIndex = ParamIndex Int
- newtype ColumnIndex = ColumnIndex Int
- type ColumnCount = ColumnIndex
Connection management
setTrace :: Database -> Maybe (Utf8 -> IO ()) -> IO ()Source
http://www.sqlite.org/c3ref/profile.html
Enable/disable tracing of SQL execution. Tracing can be disabled
by setting Nothing
as the logger callback.
Warning: If the logger callback throws an exception, your whole program will crash. Enable only for debugging!
getAutoCommit :: Database -> IO BoolSource
http://www.sqlite.org/c3ref/get_autocommit.html
Return True
if the connection is in autocommit mode, or False
if a
transaction started with BEGIN
is still active.
Be warned that some errors roll back the transaction automatically,
and that ROLLBACK
will throw an error if no transaction is active.
Use getAutoCommit
to avoid such an error:
autocommit <-getAutoCommit
connwhen
(not autocommit) $exec
conn "ROLLBACK"
Simple query execution
execWithCallback :: Database -> Utf8 -> ExecCallback -> IO (Either (Error, Utf8) ())Source
Like exec
, but invoke the callback for each result row.
If the callback throws an exception, it will be rethrown by
execWithCallback
.
type ExecCallbackSource
= ColumnCount | Number of columns, which is the number of items in the following lists. This will be the same for every row. |
-> [Utf8] | List of column names. This will be the same for every row. |
-> [Maybe Utf8] | List of column values, as returned by |
-> IO () |
Statement management
prepare :: Database -> Utf8 -> IO (Either Error (Maybe Statement))Source
http://www.sqlite.org/c3ref/prepare.html
If the query contains no SQL statements, this returns
.
Right
Nothing
reset :: Statement -> IO (Either Error ())Source
http://www.sqlite.org/c3ref/reset.html
Warning:
- If the most recent
step
call failed, this will return the corresponding error. - This does not reset the bindings on a prepared statement.
Use
clearBindings
to do that.
finalize :: Statement -> IO (Either Error ())Source
http://www.sqlite.org/c3ref/finalize.html
Warning: If the most recent step
call failed,
this will return the corresponding error.
clearBindings :: Statement -> IO ()Source
http://www.sqlite.org/c3ref/clear_bindings.html
Set all parameters in the prepared statement to null.
statementSql :: Statement -> IO (Maybe Utf8)Source
http://www.sqlite.org/c3ref/sql.html
Return a copy of the original SQL text used to compile the statement.
Parameter and column information
bindParameterCount :: Statement -> IO ParamIndexSource
http://www.sqlite.org/c3ref/bind_parameter_count.html
This returns the index of the largest (rightmost) parameter. Note that this
is not necessarily the number of parameters. If numbered parameters like
?5
are used, there may be gaps in the list.
See ParamIndex
for more information.
bindParameterName :: Statement -> ParamIndex -> IO (Maybe Utf8)Source
bindParameterIndex :: Statement -> Utf8 -> IO (Maybe ParamIndex)Source
columnName :: Statement -> ColumnIndex -> IO (Maybe Utf8)Source
Binding values to a prepared statement
bindDouble :: Statement -> ParamIndex -> Double -> IO (Either Error ())Source
bindBlob :: Statement -> ParamIndex -> ByteString -> IO (Either Error ())Source
Reading the result row
columnType :: Statement -> ColumnIndex -> IO ColumnTypeSource
columnInt64 :: Statement -> ColumnIndex -> IO Int64Source
columnDouble :: Statement -> ColumnIndex -> IO DoubleSource
columnText :: Statement -> ColumnIndex -> IO Utf8Source
columnBlob :: Statement -> ColumnIndex -> IO ByteStringSource
Result statistics
changes :: Database -> IO IntSource
http://www.sqlite.org/c3ref/changes.html
Return the number of rows that were changed, inserted, or deleted
by the most recent INSERT
, DELETE
, or UPDATE
statement.
totalChanges :: Database -> IO IntSource
http://www.sqlite.org/c3ref/total_changes.html
Return the total number of row changes caused by INSERT
, DELETE
,
or UPDATE
statements since the Database
was opened.
Interrupting a long-running query
interrupt :: Database -> IO ()Source
http://www.sqlite.org/c3ref/interrupt.html
Cause any pending operation on the Database
handle to stop at its earliest
opportunity. This simply sets a flag and returns immediately. It does not
wait for the pending operation to finish.
You'll need to compile with -threaded
for this to do any good.
Without -threaded
, FFI calls block the whole RTS, meaning interrupt
would never run at the same time as step
.
Types
data ColumnType Source
Results and errors
ErrorOK | Successful result |
ErrorError | SQL error or missing database |
ErrorInternal | Internal logic error in SQLite |
ErrorPermission | Access permission denied |
ErrorAbort | Callback routine requested an abort |
ErrorBusy | The database file is locked |
ErrorLocked | A table in the database is locked |
ErrorNoMemory | A |
ErrorReadOnly | Attempt to write a readonly database |
ErrorInterrupt | Operation terminated by |
ErrorIO | Some kind of disk I/O error occurred |
ErrorCorrupt | The database disk image is malformed |
ErrorNotFound | Unknown opcode in |
ErrorFull | Insertion failed because database is full |
ErrorCan'tOpen | Unable to open the database file |
ErrorProtocol | Database lock protocol error |
ErrorEmpty | Database is empty |
ErrorSchema | The database schema changed |
ErrorTooBig | String or BLOB exceeds size limit |
ErrorConstraint | Abort due to constraint violation |
ErrorMismatch | Data type mismatch |
ErrorMisuse | Library used incorrectly |
ErrorNoLargeFileSupport | Uses OS features not supported on host |
ErrorAuthorization | Authorization denied |
ErrorFormat | Auxiliary database format error |
ErrorRange | 2nd parameter to sqlite3_bind out of range |
ErrorNotADatabase | File opened that is not a database file |
ErrorRow |
|
ErrorDone |
|
Special types
A ByteString
containing UTF8-encoded text with no NUL characters.
newtype ParamIndex Source
Index of a parameter in a parameterized query. Parameter indices start from 1.
When a query is prepare
d, SQLite allocates an
array indexed from 1 to the highest parameter index. For example:
>Right stmt <- prepare conn "SELECT ?1, ?5, ?3, ?" >bindParameterCount stmt ParamIndex 6
This will allocate an array indexed from 1 to 6 (?
takes the highest
preceding index plus one). The array is initialized with null values.
When you bind a parameter with bindSQLData
, it assigns a
new value to one of these indices.
See http://www.sqlite.org/lang_expr.html#varparam for the syntax of parameter placeholders, and how parameter indices are assigned.
Bounded ParamIndex | Limit min/max bounds to fit into SQLite's native parameter ranges. |
Enum ParamIndex | |
Eq ParamIndex | |
Integral ParamIndex | |
Num ParamIndex | |
Ord ParamIndex | |
Real ParamIndex | |
Show ParamIndex | This just shows the underlying integer, without the data constructor. |
FFIType ParamIndex CParamIndex |
newtype ColumnIndex Source
Index of a column in a result set. Column indices start from 0.
Bounded ColumnIndex | Limit min/max bounds to fit into SQLite's native parameter ranges. |
Enum ColumnIndex | |
Eq ColumnIndex | |
Integral ColumnIndex | |
Num ColumnIndex | |
Ord ColumnIndex | |
Real ColumnIndex | |
Show ColumnIndex | This just shows the underlying integer, without the data constructor. |
FFIType ColumnIndex CColumnIndex |
type ColumnCount = ColumnIndexSource
Number of columns in a result set.