sqlite-0.4.2: Haskell binding to sqlite3Source codeContentsIndex
Database.SQLite
Portabilityportable
Stabilityprovisional
Maintainerdocserver-dev-team@galois.com
Contents
Opening and closing a database
Executing SQL queries on the database
Basic insertion operations
User-defined callback functions
Description

A Haskell binding to the sqlite3 database. See:

for more information.

The api is documented at:

Synopsis
module Database.SQLite.Base
module Database.SQLite.Types
module Database.SQL.Types
openConnection :: String -> IO SQLiteHandle
closeConnection :: SQLiteHandle -> IO ()
execStatement :: SQLiteResult a => SQLiteHandle -> String -> IO (Either String [[Row a]])
execStatement_ :: SQLiteHandle -> String -> IO (Maybe String)
execParamStatement :: SQLiteResult a => SQLiteHandle -> String -> [(String, Value)] -> IO (Either String [[Row a]])
execParamStatement_ :: SQLiteHandle -> String -> [(String, Value)] -> IO (Maybe String)
insertRow :: SQLiteHandle -> TableName -> Row String -> IO (Maybe String)
defineTable :: SQLiteHandle -> SQLTable -> IO (Maybe String)
defineTableOpt :: SQLiteHandle -> Bool -> SQLTable -> IO (Maybe String)
getLastRowID :: SQLiteHandle -> IO Integer
type Row a = [(ColumnName, a)]
data Value
= Double Double
| Int Int64
| Text String
| Blob ByteString
| Null
addRegexpSupport :: SQLiteHandle -> RegexpHandler -> IO ()
type RegexpHandler = ByteString -> ByteString -> IO Bool
withPrim :: SQLiteHandle -> (SQLite -> IO a) -> IO a
data SQLiteHandle
newSQLiteHandle :: SQLite -> IO SQLiteHandle
class IsValue a where
fromSQLiteValue :: SQLiteValue -> IO a
returnSQLiteValue :: SQLiteContext -> a -> IO ()
class IsFunctionHandler a where
funcArity :: a -> Arity
funcHandler :: a -> FunctionHandler
createFunction :: IsFunctionHandler a => SQLiteHandle -> FunctionName -> a -> IO ()
createFunctionPrim :: SQLiteHandle -> FunctionName -> Arity -> FunctionHandler -> IO ()
createAggregatePrim :: (IsValue i, IsValue o) => SQLiteHandle -> FunctionName -> Arity -> (a -> [i] -> IO a) -> a -> (a -> IO o) -> IO ()
Documentation
module Database.SQLite.Base
module Database.SQLite.Types
module Database.SQL.Types
Opening and closing a database
openConnection :: String -> IO SQLiteHandleSource

Open a new database connection, whose name is given by the dbName argument. A sqlite3 handle is returned.

An exception is thrown if the database could not be opened.

closeConnection :: SQLiteHandle -> IO ()Source
Close a database connection. Destroys the SQLite value associated with a database, closes all open files relating to the database, and releases all resources.
Executing SQL queries on the database
execStatement :: SQLiteResult a => SQLiteHandle -> String -> IO (Either String [[Row a]])Source
Evaluate the SQL statement specified by sqlStmt
execStatement_ :: SQLiteHandle -> String -> IO (Maybe String)Source
Returns an error, or Nothing if everything was OK.
execParamStatement :: SQLiteResult a => SQLiteHandle -> String -> [(String, Value)] -> IO (Either String [[Row a]])Source
Prepare and execute a parameterized statment. Statement parameter names start with a colon (for example, :col_id). Note that for the moment, column names should not contain 0 characters because that part of the column name will be ignored.
execParamStatement_ :: SQLiteHandle -> String -> [(String, Value)] -> IO (Maybe String)Source
Prepare and execute a parameterized statment, ignoring the result. See also execParamStatement.
Basic insertion operations
insertRow :: SQLiteHandle -> TableName -> Row String -> IO (Maybe String)Source
Insert a row into the table tab.
defineTable :: SQLiteHandle -> SQLTable -> IO (Maybe String)Source
Define a new table, populated from tab in the database.
defineTableOpt :: SQLiteHandle -> Bool -> SQLTable -> IO (Maybe String)Source
getLastRowID :: SQLiteHandle -> IO IntegerSource
Return the rowid (as an Integer) of the most recent successful INSERT into the database.
type Row a = [(ColumnName, a)]Source
data Value Source
Constructors
Double Double
Int Int64
Text String
Blob ByteString
Null
show/hide Instances
addRegexpSupport :: SQLiteHandle -> RegexpHandler -> IO ()Source
This function registers a RegexpHandler to be called when REGEXP(regexp,str) is used in an SQL query.
type RegexpHandler = ByteString -> ByteString -> IO BoolSource
This is the type of the function supported by the addRegexpSupport function. The first argument is the regular expression to match with and the second argument is the string to match. The result shall be True for successful match and False otherwise.
withPrim :: SQLiteHandle -> (SQLite -> IO a) -> IO aSource
data SQLiteHandle Source
newSQLiteHandle :: SQLite -> IO SQLiteHandleSource
User-defined callback functions
class IsValue a whereSource
Methods
fromSQLiteValue :: SQLiteValue -> IO aSource
returnSQLiteValue :: SQLiteContext -> a -> IO ()Source
show/hide Instances
class IsFunctionHandler a whereSource
Methods
funcArity :: a -> AritySource
funcHandler :: a -> FunctionHandlerSource
show/hide Instances
IsValue r => IsFunctionHandler (IO r)
(IsValue a, IsValue r) => IsFunctionHandler ([] a -> IO r)
(IsValue a, IsValue r) => IsFunctionHandler ([] a -> r)
IsValue r => IsFunctionHandler (String -> IO r)
IsValue r => IsFunctionHandler (String -> r)
(IsValue a, IsValue b, IsValue c, IsValue d, IsValue r) => IsFunctionHandler (a -> b -> c -> d -> IO r)
(IsValue a, IsValue b, IsValue c, IsValue r) => IsFunctionHandler (a -> b -> c -> IO r)
(IsValue a, IsValue b, IsValue r) => IsFunctionHandler (a -> b -> IO r)
(IsValue a, IsValue r) => IsFunctionHandler (a -> IO r)
(IsValue a, IsValue b, IsValue c, IsValue d, IsValue r) => IsFunctionHandler (a -> b -> c -> d -> r)
(IsValue a, IsValue b, IsValue c, IsValue r) => IsFunctionHandler (a -> b -> c -> r)
(IsValue a, IsValue b, IsValue r) => IsFunctionHandler (a -> b -> r)
(IsValue a, IsValue r) => IsFunctionHandler (a -> r)
createFunction :: IsFunctionHandler a => SQLiteHandle -> FunctionName -> a -> IO ()Source
createFunctionPrim :: SQLiteHandle -> FunctionName -> Arity -> FunctionHandler -> IO ()Source
createAggregatePrim :: (IsValue i, IsValue o) => SQLiteHandle -> FunctionName -> Arity -> (a -> [i] -> IO a) -> a -> (a -> IO o) -> IO ()Source
Produced by Haddock version 2.4.2