Copyright | (c) Galois Inc. 2007 (c) figo GmbH 2016 |
---|---|
License | BSD3 |
Maintainer | figo GmbH <package+haskell@figo.io> |
Stability | provisional |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
A Haskell binding to the SQLCipher database. See:
for more information.
The API is documented at:
- module Database.SQLCipher.Base
- module Database.SQLCipher.Types
- module Database.SQL.Types
- openConnection :: String -> IO SQLiteHandle
- openReadonlyConnection :: String -> IO SQLiteHandle
- closeConnection :: SQLiteHandle -> IO ()
- class SQLiteResultPrivate a => SQLiteResult a
- 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
- 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
- class IsFunctionHandler a where
- 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.SQLCipher.Base
module Database.SQLCipher.Types
module Database.SQL.Types
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 #
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.
defineTableOpt :: SQLiteHandle -> Bool -> SQLTable -> IO (Maybe String) Source #
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 #
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.
data SQLiteHandle Source #
newSQLiteHandle :: SQLite -> IO SQLiteHandle Source #
User-defined callback functions
class IsValue a where Source #
fromSQLiteValue :: SQLiteValue -> IO a Source #
returnSQLiteValue :: SQLiteContext -> a -> IO () Source #
class IsFunctionHandler a where 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 #