sqlite-0.5.5: Haskell binding to sqlite3

Copyright(c) Galois, Inc. 2007
LicenseBSD3
Maintainerdocserver-dev-team@galois.com
Stabilityprovisional
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Database.SQLite

Contents

Description

A Haskell binding to the sqlite3 database. See:

for more information.

The api is documented at:

Synopsis

Documentation

Opening and closing a database

openConnection :: String -> IO SQLiteHandle Source #

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.

openReadonlyConnection :: String -> IO SQLiteHandle Source #

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

An exception is thrown if the database does not exist, or 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

class SQLiteResultPrivate a => SQLiteResult a Source #

Minimal complete definition

get_sqlite_val

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.

getLastRowID :: SQLiteHandle -> IO Integer Source #

Return the rowid (as an Integer) of the most recent successful INSERT into the database.

type Row a = [(ColumnName, a)] Source #

data Value Source #

Instances

Data Value Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Value -> c Value #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Value #

toConstr :: Value -> Constr #

dataTypeOf :: Value -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Value) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Value) #

gmapT :: (forall b. Data b => b -> b) -> Value -> Value #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r #

gmapQ :: (forall d. Data d => d -> u) -> Value -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Value -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Value -> m Value #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value #

Show Value Source # 

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

IsValue Value Source # 
SQLiteResult Value Source # 

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

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.

User-defined callback functions

class IsValue a where Source #

Minimal complete definition

fromSQLiteValue, returnSQLiteValue

Instances

IsValue Double Source # 
IsValue Int Source # 
IsValue Int64 Source # 
IsValue () Source # 
IsValue CStringLen Source # 
IsValue CInt Source # 
IsValue String Source # 
IsValue ByteString Source # 
IsValue SQLiteValue Source # 
IsValue Value Source # 
IsValue a => IsValue (Maybe a) Source # 

class IsFunctionHandler a where Source #

Minimal complete definition

funcArity, funcHandler

Methods

funcArity :: a -> Arity Source #

funcHandler :: a -> FunctionHandler Source #

Instances

IsValue r => IsFunctionHandler r Source # 

Methods

funcArity :: r -> Arity Source #

funcHandler :: r -> FunctionHandler Source #

IsValue r => IsFunctionHandler (IO r) Source # 

Methods

funcArity :: IO r -> Arity Source #

funcHandler :: IO r -> FunctionHandler Source #

(IsValue a, IsValue r) => IsFunctionHandler ([a] -> IO r) Source # 

Methods

funcArity :: ([a] -> IO r) -> Arity Source #

funcHandler :: ([a] -> IO r) -> FunctionHandler Source #

(IsValue a, IsValue r) => IsFunctionHandler ([a] -> r) Source # 

Methods

funcArity :: ([a] -> r) -> Arity Source #

funcHandler :: ([a] -> r) -> FunctionHandler Source #

(IsValue a, IsValue b, IsValue c, IsValue d, IsValue r) => IsFunctionHandler (a -> b -> c -> d -> IO r) Source # 

Methods

funcArity :: (a -> b -> c -> d -> IO r) -> Arity Source #

funcHandler :: (a -> b -> c -> d -> IO r) -> FunctionHandler Source #

(IsValue a, IsValue b, IsValue c, IsValue r) => IsFunctionHandler (a -> b -> c -> IO r) Source # 

Methods

funcArity :: (a -> b -> c -> IO r) -> Arity Source #

funcHandler :: (a -> b -> c -> IO r) -> FunctionHandler Source #

(IsValue a, IsValue b, IsValue r) => IsFunctionHandler (a -> b -> IO r) Source # 

Methods

funcArity :: (a -> b -> IO r) -> Arity Source #

funcHandler :: (a -> b -> IO r) -> FunctionHandler Source #

(IsValue a, IsValue r) => IsFunctionHandler (a -> IO r) Source # 

Methods

funcArity :: (a -> IO r) -> Arity Source #

funcHandler :: (a -> IO r) -> FunctionHandler Source #

(IsValue a, IsValue b, IsValue c, IsValue d, IsValue r) => IsFunctionHandler (a -> b -> c -> d -> r) Source # 

Methods

funcArity :: (a -> b -> c -> d -> r) -> Arity Source #

funcHandler :: (a -> b -> c -> d -> r) -> FunctionHandler Source #

(IsValue a, IsValue b, IsValue c, IsValue r) => IsFunctionHandler (a -> b -> c -> r) Source # 

Methods

funcArity :: (a -> b -> c -> r) -> Arity Source #

funcHandler :: (a -> b -> c -> r) -> FunctionHandler Source #

(IsValue a, IsValue b, IsValue r) => IsFunctionHandler (a -> b -> r) Source # 

Methods

funcArity :: (a -> b -> r) -> Arity Source #

funcHandler :: (a -> b -> r) -> FunctionHandler Source #

(IsValue a, IsValue r) => IsFunctionHandler (a -> r) Source # 

Methods

funcArity :: (a -> r) -> Arity Source #

funcHandler :: (a -> r) -> FunctionHandler Source #

IsValue r => IsFunctionHandler (String -> IO r) Source # 

Methods

funcArity :: (String -> IO r) -> Arity Source #

funcHandler :: (String -> IO r) -> FunctionHandler Source #

IsValue r => IsFunctionHandler (String -> r) Source # 

Methods

funcArity :: (String -> r) -> Arity Source #

funcHandler :: (String -> r) -> FunctionHandler Source #

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 #