direct-sqlite-2.3.29: Low-level binding to SQLite3. Includes UTF8 and BLOB support.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Database.SQLite3.Direct

Description

This API is a slightly lower-level version of Database.SQLite3. Namely:

  • It returns errors instead of throwing them.
  • It only uses cheap conversions. None of these bindings convert from String or Text.
Synopsis

Connection management

setTrace :: Database -> Maybe (Utf8 -> IO ()) -> IO () Source #

https://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 Bool Source #

https://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 conn
 when (not autocommit) $
     exec conn "ROLLBACK"

setSharedCacheEnabled :: Bool -> IO (Either Error ()) Source #

https://www.sqlite.org/c3ref/enable_shared_cache.html

Enable or disable shared cache for all future connections.

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 ExecCallback Source #

Arguments

 = 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 columnText.

-> IO () 

Statement management

prepare :: Database -> Utf8 -> IO (Either Error (Maybe Statement)) Source #

https://www.sqlite.org/c3ref/prepare.html

If the query contains no SQL statements, this returns Right Nothing.

stepNoCB :: Statement -> IO (Either Error StepResult) Source #

https://www.sqlite.org/c3ref/step.html

Faster step for statements that don't callback to Haskell functions (e.g. by using custom SQL functions).

reset :: Statement -> IO (Either Error ()) Source #

https://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 #

https://www.sqlite.org/c3ref/finalize.html

Warning: If the most recent step call failed, this will return the corresponding error.

clearBindings :: Statement -> IO () Source #

https://www.sqlite.org/c3ref/clear_bindings.html

Set all parameters in the prepared statement to null.

statementSql :: Statement -> IO (Maybe Utf8) Source #

https://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 ParamIndex Source #

https://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.

Binding values to a prepared statement

Reading the result row

control loading of extensions

Result statistics

changes :: Database -> IO Int Source #

https://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 Int Source #

https://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.

Create custom SQL functions

createFunction Source #

Arguments

:: Database 
-> Utf8

Name of the function.

-> Maybe ArgCount

Number of arguments. Nothing means that the function accepts any number of arguments.

-> Bool

Is the function deterministic?

-> (FuncContext -> FuncArgs -> IO ())

Implementation of the function.

-> IO (Either Error ()) 

https://sqlite.org/c3ref/create_function.html

Create a custom SQL function or redefine the behavior of an existing function.

createAggregate Source #

Arguments

:: Database 
-> Utf8

Name of the function.

-> Maybe ArgCount

Number of arguments.

-> a

Initial aggregate state.

-> (FuncContext -> FuncArgs -> a -> IO a)

Process one row and update the aggregate state.

-> (FuncContext -> a -> IO ())

Called after all rows have been processed. Can be used to construct the returned value from the aggregate state.

-> IO (Either Error ()) 

Like createFunction except that it creates an aggregate function.

deleteFunction :: Database -> Utf8 -> Maybe ArgCount -> IO (Either Error ()) Source #

Delete an SQL function (scalar or aggregate).

Extract function arguments

Set the result of a function

Create custom collations

createCollation Source #

Arguments

:: Database 
-> Utf8

Name of the collation.

-> (Utf8 -> Utf8 -> Ordering)

Comparison function.

-> IO (Either Error ()) 

deleteCollation :: Database -> Utf8 -> IO (Either Error ()) Source #

Delete a collation.

Interrupting a long-running query

interrupt :: Database -> IO () Source #

https://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.

Incremental blob I/O

blobOpen Source #

Arguments

:: Database 
-> Utf8

The symbolic name of the database (e.g. "main").

-> Utf8

The table name.

-> Utf8

The column name.

-> Int64

The ROWID of the row.

-> Bool

Open the blob for read-write.

-> IO (Either Error Blob) 

https://www.sqlite.org/c3ref/blob_open.html

Open a blob for incremental I/O.

blobRead Source #

Arguments

:: Blob 
-> Int

Number of bytes to read.

-> Int

Offset within the blob.

-> IO (Either Error ByteString) 

blobReadBuf :: Blob -> Ptr a -> Int -> Int -> IO (Either Error ()) Source #

Online Backup API

backupInit Source #

Arguments

:: Database

Destination database handle.

-> Utf8

Destination database name.

-> Database

Source database handle.

-> Utf8

Source database name.

-> IO (Either Error Backup) 

backupStep Source #

Arguments

:: Backup 
-> Int

Number of pages to copy; if negative, all remaining source pages are copied.

-> IO (Either Error BackupStepResult) 

Types

newtype Database Source #

Constructors

Database (Ptr CDatabase) 

Instances

Instances details
Show Database Source # 
Instance details

Defined in Database.SQLite3.Direct

Eq Database Source # 
Instance details

Defined in Database.SQLite3.Direct

newtype Statement Source #

Constructors

Statement (Ptr CStatement) 

Instances

Instances details
Show Statement Source # 
Instance details

Defined in Database.SQLite3.Direct

Eq Statement Source # 
Instance details

Defined in Database.SQLite3.Direct

newtype FuncContext Source #

The context in which a custom SQL function is executed.

Constructors

FuncContext (Ptr CContext) 

Instances

Instances details
Show FuncContext Source # 
Instance details

Defined in Database.SQLite3.Direct

Eq FuncContext Source # 
Instance details

Defined in Database.SQLite3.Direct

data FuncArgs Source #

The arguments of a custom SQL function.

Constructors

FuncArgs CArgCount (Ptr (Ptr CValue)) 

data Blob Source #

The type of blob handles used for incremental blob I/O

Constructors

Blob Database (Ptr CBlob) 

Instances

Instances details
Show Blob Source # 
Instance details

Defined in Database.SQLite3.Direct

Methods

showsPrec :: Int -> Blob -> ShowS #

show :: Blob -> String #

showList :: [Blob] -> ShowS #

Eq Blob Source # 
Instance details

Defined in Database.SQLite3.Direct

Methods

(==) :: Blob -> Blob -> Bool #

(/=) :: Blob -> Blob -> Bool #

data Backup Source #

A handle for an online backup process.

Constructors

Backup Database (Ptr CBackup) 

Instances

Instances details
Show Backup Source # 
Instance details

Defined in Database.SQLite3.Direct

Eq Backup Source # 
Instance details

Defined in Database.SQLite3.Direct

Methods

(==) :: Backup -> Backup -> Bool #

(/=) :: Backup -> Backup -> Bool #

Results and errors

data StepResult Source #

Constructors

Row 
Done 

Instances

Instances details
Show StepResult Source # 
Instance details

Defined in Database.SQLite3.Direct

Eq StepResult Source # 
Instance details

Defined in Database.SQLite3.Direct

data BackupStepResult Source #

Constructors

BackupOK

There are still more pages to be copied.

BackupDone

All pages were successfully copied.

data Error Source #

Constructors

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 malloc() failed

ErrorReadOnly

Attempt to write a readonly database

ErrorInterrupt

Operation terminated by sqlite3_interrupt()

ErrorIO

Some kind of disk I/O error occurred

ErrorCorrupt

The database disk image is malformed

ErrorNotFound

Unknown opcode in sqlite3_file_control()

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

ErrorNotice

Notifications from sqlite3_log()

ErrorWarning

Warnings from sqlite3_log()

ErrorRow

sqlite3_step() has another row ready

ErrorDone

sqlite3_step() has finished executing

ErrorErrorMissingCollatingSquence 
ErrorErrorRetry 
ErrorErrorSnapshot 
ErrorIORead 
ErrorIOShortRead 
ErrorIOWrite 
ErrorIOFsync 
ErrorIODirectoryFsync 
ErrorIOTruncate 
ErrorIOFstat 
ErrorIOUnlock 
ErrorIOReadLock 
ErrorIOBlocked 
ErrorIODelete 
ErrorIONoMemory 
ErrorIOAccess 
ErrorIOCheckReservedLock 
ErrorIOLock 
ErrorIOClose 
ErrorIODirectoryClose 
ErrorIOShmOpen 
ErrorIOShmSize 
ErrorIOShmLock 
ErrorIOShmMap 
ErrorIOSeek 
ErrorIODeleteNoEntity 
ErrorIOMmap 
ErrorIOGetTempPath 
ErrorIOConvertedPath 
ErrorIOVNode 
ErrorIOAuth 
ErrorIOBeginAtomic 
ErrorIOCommitAtomic 
ErrorIORollbackAtomic 
ErrorIOData 
ErrorIOCorruptFilesystem 
ErrorLockedSharedCache 
ErrorLockedVirtualTable 
ErrorBusyRecovery 
ErrorBusySnapshot 
ErrorBusyTimeout 
ErrorCan'tOpenNotTempDirectory 
ErrorCan'tOpenIsDirectory 
ErrorCan'tOpenFullPath 
ErrorCan'tOpenConvertedPath 
ErrorCan'tOpenDirtyWriteAheadLog 
ErrorCan'tOpenSymlink 
ErrorCorruptVirtualTable 
ErrorCorruptSequence 
ErrorCorruptIndex 
ErrorReadOnlyRecovery 
ErrorReadOnlyCan'tLock 
ErrorReadOnlyRollback 
ErrorReadOnlyDatabaseMoved 
ErrorReadOnlyCan'tInit 
ErrorReadOnlyDirectory 
ErrorAbortRollback 
ErrorConstraintCheck 
ErrorConstraintCommitHook 
ErrorConstraintForeignKey 
ErrorConstraintFunction 
ErrorConstraintNotNull 
ErrorConstraintPrimaryKey 
ErrorConstraintTrigger 
ErrorConstraintUnique 
ErrorConstraintVirtualTable 
ErrorConstraintRowId 
ErrorConstraintPinned 
ErrorConstraintDataType 
ErrorNoticeRecoverWriteAheadLog 
ErrorNoticeRecoverRollback 
ErrorWarningAutoIndex 
ErrorAuthUser 
ErrorOkLoadPermanently 

Instances

Instances details
Generic Error Source # 
Instance details

Defined in Database.SQLite3.Bindings.Types

Associated Types

type Rep Error :: Type -> Type #

Methods

from :: Error -> Rep Error x #

to :: Rep Error x -> Error #

Show Error Source # 
Instance details

Defined in Database.SQLite3.Bindings.Types

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

Eq Error Source # 
Instance details

Defined in Database.SQLite3.Bindings.Types

Methods

(==) :: Error -> Error -> Bool #

(/=) :: Error -> Error -> Bool #

FFIType Error CError Source # 
Instance details

Defined in Database.SQLite3.Bindings.Types

type Rep Error Source # 
Instance details

Defined in Database.SQLite3.Bindings.Types

type Rep Error = D1 ('MetaData "Error" "Database.SQLite3.Bindings.Types" "direct-sqlite-2.3.29-2L5GhZ6SNrD5GJ9vI8wbDw" 'False) ((((((C1 ('MetaCons "ErrorOK" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ErrorError" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorInternal" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "ErrorPermission" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ErrorAbort" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorBusy" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ErrorLocked" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ErrorNoMemory" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorReadOnly" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ErrorInterrupt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorIO" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ErrorCorrupt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorNotFound" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "ErrorFull" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ErrorCan'tOpen" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorProtocol" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "ErrorEmpty" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ErrorSchema" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorTooBig" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ErrorConstraint" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ErrorMismatch" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorMisuse" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ErrorNoLargeFileSupport" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorAuthorization" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ErrorFormat" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorRange" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "ErrorNotADatabase" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ErrorNotice" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorWarning" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "ErrorRow" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ErrorDone" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorErrorMissingCollatingSquence" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ErrorErrorRetry" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ErrorErrorSnapshot" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorIORead" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ErrorIOShortRead" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorIOWrite" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ErrorIOFsync" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorIODirectoryFsync" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "ErrorIOTruncate" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ErrorIOFstat" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorIOUnlock" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "ErrorIOReadLock" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ErrorIOBlocked" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorIODelete" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ErrorIONoMemory" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ErrorIOAccess" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorIOCheckReservedLock" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ErrorIOLock" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorIOClose" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ErrorIODirectoryClose" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorIOShmOpen" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "ErrorIOShmSize" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ErrorIOShmLock" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorIOShmMap" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "ErrorIOSeek" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ErrorIODeleteNoEntity" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorIOMmap" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ErrorIOGetTempPath" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ErrorIOConvertedPath" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorIOVNode" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ErrorIOAuth" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorIOBeginAtomic" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ErrorIOCommitAtomic" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorIORollbackAtomic" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "ErrorIOData" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ErrorIOCorruptFilesystem" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorLockedSharedCache" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "ErrorLockedVirtualTable" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ErrorBusyRecovery" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorBusySnapshot" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ErrorBusyTimeout" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ErrorCan'tOpenNotTempDirectory" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorCan'tOpenIsDirectory" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ErrorCan'tOpenFullPath" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorCan'tOpenConvertedPath" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ErrorCan'tOpenDirtyWriteAheadLog" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorCan'tOpenSymlink" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "ErrorCorruptVirtualTable" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ErrorCorruptSequence" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorCorruptIndex" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "ErrorReadOnlyRecovery" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ErrorReadOnlyCan'tLock" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorReadOnlyRollback" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ErrorReadOnlyDatabaseMoved" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ErrorReadOnlyCan'tInit" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorReadOnlyDirectory" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ErrorAbortRollback" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorConstraintCheck" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ErrorConstraintCommitHook" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorConstraintForeignKey" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "ErrorConstraintFunction" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ErrorConstraintNotNull" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorConstraintPrimaryKey" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ErrorConstraintTrigger" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorConstraintUnique" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ErrorConstraintVirtualTable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorConstraintRowId" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ErrorConstraintPinned" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ErrorConstraintDataType" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorNoticeRecoverWriteAheadLog" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ErrorNoticeRecoverRollback" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorWarningAutoIndex" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ErrorAuthUser" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ErrorOkLoadPermanently" 'PrefixI 'False) (U1 :: Type -> Type))))))))

Special types

newtype Utf8 Source #

A ByteString containing UTF8-encoded text with no NUL characters.

Constructors

Utf8 ByteString 

Instances

Instances details
IsString Utf8 Source #
fromString = Utf8 . encodeUtf8 . pack
Instance details

Defined in Database.SQLite3.Direct

Methods

fromString :: String -> Utf8 #

Monoid Utf8 Source # 
Instance details

Defined in Database.SQLite3.Direct

Methods

mempty :: Utf8 #

mappend :: Utf8 -> Utf8 -> Utf8 #

mconcat :: [Utf8] -> Utf8 #

Semigroup Utf8 Source # 
Instance details

Defined in Database.SQLite3.Direct

Methods

(<>) :: Utf8 -> Utf8 -> Utf8 #

sconcat :: NonEmpty Utf8 -> Utf8 #

stimes :: Integral b => b -> Utf8 -> Utf8 #

Show Utf8 Source # 
Instance details

Defined in Database.SQLite3.Direct

Methods

showsPrec :: Int -> Utf8 -> ShowS #

show :: Utf8 -> String #

showList :: [Utf8] -> ShowS #

Eq Utf8 Source # 
Instance details

Defined in Database.SQLite3.Direct

Methods

(==) :: Utf8 -> Utf8 -> Bool #

(/=) :: Utf8 -> Utf8 -> Bool #

Ord Utf8 Source # 
Instance details

Defined in Database.SQLite3.Direct

Methods

compare :: Utf8 -> Utf8 -> Ordering #

(<) :: Utf8 -> Utf8 -> Bool #

(<=) :: Utf8 -> Utf8 -> Bool #

(>) :: Utf8 -> Utf8 -> Bool #

(>=) :: Utf8 -> Utf8 -> Bool #

max :: Utf8 -> Utf8 -> Utf8 #

min :: Utf8 -> Utf8 -> Utf8 #

newtype ParamIndex Source #

Index of a parameter in a parameterized query. Parameter indices start from 1.

When a query is prepared, 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 https://www.sqlite.org/lang_expr.html#varparam for the syntax of parameter placeholders, and how parameter indices are assigned.

Constructors

ParamIndex Int 

Instances

Instances details
Bounded ParamIndex Source #

Limit min/max bounds to fit into SQLite's native parameter ranges.

Instance details

Defined in Database.SQLite3.Bindings.Types

Enum ParamIndex Source # 
Instance details

Defined in Database.SQLite3.Bindings.Types

Num ParamIndex Source # 
Instance details

Defined in Database.SQLite3.Bindings.Types

Integral ParamIndex Source # 
Instance details

Defined in Database.SQLite3.Bindings.Types

Real ParamIndex Source # 
Instance details

Defined in Database.SQLite3.Bindings.Types

Show ParamIndex Source #

This just shows the underlying integer, without the data constructor.

Instance details

Defined in Database.SQLite3.Bindings.Types

Eq ParamIndex Source # 
Instance details

Defined in Database.SQLite3.Bindings.Types

Ord ParamIndex Source # 
Instance details

Defined in Database.SQLite3.Bindings.Types

FFIType ParamIndex CParamIndex Source # 
Instance details

Defined in Database.SQLite3.Bindings.Types

newtype ColumnIndex Source #

Index of a column in a result set. Column indices start from 0.

Constructors

ColumnIndex Int 

Instances

Instances details
Bounded ColumnIndex Source #

Limit min/max bounds to fit into SQLite's native parameter ranges.

Instance details

Defined in Database.SQLite3.Bindings.Types

Enum ColumnIndex Source # 
Instance details

Defined in Database.SQLite3.Bindings.Types

Num ColumnIndex Source # 
Instance details

Defined in Database.SQLite3.Bindings.Types

Integral ColumnIndex Source # 
Instance details

Defined in Database.SQLite3.Bindings.Types

Real ColumnIndex Source # 
Instance details

Defined in Database.SQLite3.Bindings.Types

Show ColumnIndex Source #

This just shows the underlying integer, without the data constructor.

Instance details

Defined in Database.SQLite3.Bindings.Types

Eq ColumnIndex Source # 
Instance details

Defined in Database.SQLite3.Bindings.Types

Ord ColumnIndex Source # 
Instance details

Defined in Database.SQLite3.Bindings.Types

FFIType ColumnIndex CColumnIndex Source # 
Instance details

Defined in Database.SQLite3.Bindings.Types

type ColumnCount = ColumnIndex Source #

Number of columns in a result set.

newtype ArgCount Source #

Number of arguments of a user defined SQL function.

Constructors

ArgCount Int 

Instances

Instances details
Bounded ArgCount Source # 
Instance details

Defined in Database.SQLite3.Bindings.Types

Enum ArgCount Source # 
Instance details

Defined in Database.SQLite3.Bindings.Types

Num ArgCount Source # 
Instance details

Defined in Database.SQLite3.Bindings.Types

Integral ArgCount Source # 
Instance details

Defined in Database.SQLite3.Bindings.Types

Real ArgCount Source # 
Instance details

Defined in Database.SQLite3.Bindings.Types

Show ArgCount Source #

This just shows the underlying integer, without the data constructor.

Instance details

Defined in Database.SQLite3.Bindings.Types

Eq ArgCount Source # 
Instance details

Defined in Database.SQLite3.Bindings.Types

Ord ArgCount Source # 
Instance details

Defined in Database.SQLite3.Bindings.Types

FFIType ArgCount CArgCount Source # 
Instance details

Defined in Database.SQLite3.Bindings.Types

type ArgIndex = ArgCount Source #

Index of an argument to a custom function. Indices start from 0.