Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Bindings to the SQLite3 C library. This is a very simple library that puts a minimal number of abstractions between the user and the underlying C library. Some notable abstractions that do appear:
- use of
Text
andByteString
in the user-facing API rather than the underlying C types - use of the SQLite3 extended error codes
- all errors indicated with exceptions (embraces the philosophy that exceptions are inevitable in IO)
- extensive contextual information given in exceptions, to help you figure out where the problem arose
Database
andStatement
handles are cleaned up for you, so there is no need to manually de-allocate them
The SQLite library is built along with Squeather, so there is no dependency on a system-wide library and there is nothing else to build. The following run-time loadable extensions are enabled in the build:
However, at this point none of the run-time loadable extensions have been tested.
In addition, the SQLite C library is compiled with the
-DSQLITE_DQS=0
compile-time option, so that double-quoted
string literals in SQL are NOT accepted. Be sure to
single-quote your string literals and double-quote your
identifiers in SQL. For details on what this is about, see
https://sqlite.org/quirks.html#double_quoted_string_literals_are_accepted
The name comes from SQL
and the feather which is used in the
SQLite logo.
Synopsis
- data Database
- open :: Text -> IO Database
- data Create
- data WriteMode
- data ThreadMode
- data CacheMode
- data OpenFlags = OpenFlags {}
- openFlags :: OpenFlags
- openWithFlags :: OpenFlags -> Text -> IO Database
- exec :: Database -> Text -> IO ()
- data SQLData
- execute :: Database -> Text -> IO [[SQLData]]
- executeNamed :: Database -> Text -> [(Text, SQLData)] -> IO [[SQLData]]
- executeNamedWithColumns :: Database -> Text -> [(Text, SQLData)] -> IO ([Text], [[SQLData]])
- lastInsertRowId :: Database -> IO Int64
- changes :: Database -> IO Int
- data Source = Source {}
- data Destination = Destination {}
- backup :: Source -> Destination -> IO ()
- data Statement
- data StepResult
- prepare :: Database -> Text -> IO Statement
- columnCount :: Statement -> IO Int
- columnName :: Statement -> Int -> IO Text
- columnNames :: Statement -> IO [Text]
- bindParams :: Statement -> [(Text, SQLData)] -> IO ()
- step :: Statement -> IO StepResult
- column :: Statement -> Int -> IO SQLData
- columns :: Statement -> IO [SQLData]
- allRows :: Statement -> IO [[SQLData]]
- reset :: Statement -> IO ()
- clearBindings :: Statement -> IO ()
- data ErrorFlag
- = SQLITE_ERROR
- | SQLITE_INTERNAL
- | SQLITE_PERM
- | SQLITE_ABORT
- | SQLITE_BUSY
- | SQLITE_LOCKED
- | SQLITE_NOMEM
- | SQLITE_READONLY
- | SQLITE_INTERRUPT
- | SQLITE_IOERR
- | SQLITE_CORRUPT
- | SQLITE_NOTFOUND
- | SQLITE_FULL
- | SQLITE_CANTOPEN
- | SQLITE_PROTOCOL
- | SQLITE_EMPTY
- | SQLITE_SCHEMA
- | SQLITE_TOOBIG
- | SQLITE_CONSTRAINT
- | SQLITE_MISMATCH
- | SQLITE_MISUSE
- | SQLITE_NOLFS
- | SQLITE_AUTH
- | SQLITE_FORMAT
- | SQLITE_RANGE
- | SQLITE_NOTADB
- | SQLITE_NOTICE
- | SQLITE_WARNING
- | SQLITE_ERROR_MISSING_COLLSEQ
- | SQLITE_ERROR_RETRY
- | SQLITE_ERROR_SNAPSHOT
- | SQLITE_IOERR_READ
- | SQLITE_IOERR_SHORT_READ
- | SQLITE_IOERR_WRITE
- | SQLITE_IOERR_FSYNC
- | SQLITE_IOERR_DIR_FSYNC
- | SQLITE_IOERR_TRUNCATE
- | SQLITE_IOERR_FSTAT
- | SQLITE_IOERR_UNLOCK
- | SQLITE_IOERR_RDLOCK
- | SQLITE_IOERR_DELETE
- | SQLITE_IOERR_BLOCKED
- | SQLITE_IOERR_NOMEM
- | SQLITE_IOERR_ACCESS
- | SQLITE_IOERR_CHECKRESERVEDLOCK
- | SQLITE_IOERR_LOCK
- | SQLITE_IOERR_CLOSE
- | SQLITE_IOERR_DIR_CLOSE
- | SQLITE_IOERR_SHMOPEN
- | SQLITE_IOERR_SHMSIZE
- | SQLITE_IOERR_SHMLOCK
- | SQLITE_IOERR_SHMMAP
- | SQLITE_IOERR_SEEK
- | SQLITE_IOERR_DELETE_NOENT
- | SQLITE_IOERR_MMAP
- | SQLITE_IOERR_GETTEMPPATH
- | SQLITE_IOERR_CONVPATH
- | SQLITE_IOERR_VNODE
- | SQLITE_IOERR_AUTH
- | SQLITE_IOERR_BEGIN_ATOMIC
- | SQLITE_IOERR_COMMIT_ATOMIC
- | SQLITE_IOERR_ROLLBACK_ATOMIC
- | SQLITE_LOCKED_SHAREDCACHE
- | SQLITE_LOCKED_VTAB
- | SQLITE_BUSY_RECOVERY
- | SQLITE_BUSY_SNAPSHOT
- | SQLITE_CANTOPEN_NOTEMPDIR
- | SQLITE_CANTOPEN_ISDIR
- | SQLITE_CANTOPEN_FULLPATH
- | SQLITE_CANTOPEN_CONVPATH
- | SQLITE_CANTOPEN_DIRTYWAL
- | SQLITE_CANTOPEN_SYMLINK
- | SQLITE_CORRUPT_VTAB
- | SQLITE_CORRUPT_SEQUENCE
- | SQLITE_READONLY_RECOVERY
- | SQLITE_READONLY_CANTLOCK
- | SQLITE_READONLY_ROLLBACK
- | SQLITE_READONLY_DBMOVED
- | SQLITE_READONLY_CANTINIT
- | SQLITE_READONLY_DIRECTORY
- | SQLITE_ABORT_ROLLBACK
- | SQLITE_CONSTRAINT_CHECK
- | SQLITE_CONSTRAINT_COMMITHOOK
- | SQLITE_CONSTRAINT_FOREIGNKEY
- | SQLITE_CONSTRAINT_FUNCTION
- | SQLITE_CONSTRAINT_NOTNULL
- | SQLITE_CONSTRAINT_PRIMARYKEY
- | SQLITE_CONSTRAINT_TRIGGER
- | SQLITE_CONSTRAINT_UNIQUE
- | SQLITE_CONSTRAINT_VTAB
- | SQLITE_CONSTRAINT_ROWID
- | SQLITE_CONSTRAINT_PINNED
- | SQLITE_NOTICE_RECOVER_WAL
- | SQLITE_NOTICE_RECOVER_ROLLBACK
- | SQLITE_WARNING_AUTOINDEX
- | SQLITE_AUTH_USER
- | SQLITE_OK_LOAD_PERMANENTLY
- | SQLITE_OK_SYMLINK
- data SqueatherErrorFlag
- data Error = Error {}
- sqliteVersion :: String
Database handles, opening databases
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.
Opening with flags
Whether to create a new database if it does not already exist.
data ThreadMode Source #
Whether to use multi-thread mode or serialized mode, see
https://www.sqlite.org/threadsafe.html
It is not possible to use the SQLite single-thread mode.
Instances
Eq ThreadMode Source # | |
Defined in Squeather.Internal.Types (==) :: ThreadMode -> ThreadMode -> Bool # (/=) :: ThreadMode -> ThreadMode -> Bool # | |
Ord ThreadMode Source # | |
Defined in Squeather.Internal.Types compare :: ThreadMode -> ThreadMode -> Ordering # (<) :: ThreadMode -> ThreadMode -> Bool # (<=) :: ThreadMode -> ThreadMode -> Bool # (>) :: ThreadMode -> ThreadMode -> Bool # (>=) :: ThreadMode -> ThreadMode -> Bool # max :: ThreadMode -> ThreadMode -> ThreadMode # min :: ThreadMode -> ThreadMode -> ThreadMode # | |
Show ThreadMode Source # | |
Defined in Squeather.Internal.Types showsPrec :: Int -> ThreadMode -> ShowS # show :: ThreadMode -> String # showList :: [ThreadMode] -> ShowS # |
Whether to use shared cache or private cache mode, see
Various options when opening a database.
OpenFlags | |
|
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.
Easy execution of statements
Often this is all you will need to execute statements.
:: 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
.
Various types of SQL data; used both when obtaining query results and when providing named parameters.
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.
Statistics
changes :: Database -> IO Int Source #
Count the number of rows modified by the most recent INSERT
,
UPDATE
, or DELETE
statement.
Backups
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.
Statements
For more control over statement execution.
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.
data StepResult Source #
Instances
Eq StepResult Source # | |
Defined in Squeather.Internal.Types (==) :: StepResult -> StepResult -> Bool # (/=) :: StepResult -> StepResult -> Bool # | |
Ord StepResult Source # | |
Defined in Squeather.Internal.Types compare :: StepResult -> StepResult -> Ordering # (<) :: StepResult -> StepResult -> Bool # (<=) :: StepResult -> StepResult -> Bool # (>) :: StepResult -> StepResult -> Bool # (>=) :: StepResult -> StepResult -> Bool # max :: StepResult -> StepResult -> StepResult # min :: StepResult -> StepResult -> StepResult # | |
Show StepResult Source # | |
Defined in Squeather.Internal.Types showsPrec :: Int -> StepResult -> ShowS # show :: StepResult -> String # showList :: [StepResult] -> ShowS # |
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 name of a column. The name is the value of the AS
clause if it exists, or is an undefined string otherwise.
bindParams :: Statement -> [(Text, SQLData)] -> IO () Source #
Bind multiple named parameters to a 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
.
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
.
Errors
Errors produced by the underlying SQLite3 C library.
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 # |
Version
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.