Safe Haskell | None |
---|
Database.Persist.Sqlite
Description
A sqlite backend for persistent.
- withSqlitePool :: (MonadBaseControl IO m, MonadIO m) => Text -> Int -> (ConnectionPool -> m a) -> m a
- withSqliteConn :: (MonadBaseControl IO m, MonadIO m) => Text -> (Connection -> m a) -> m a
- createSqlitePool :: MonadIO m => Text -> Int -> m ConnectionPool
- module Database.Persist.Sql
- data SqliteConf = SqliteConf {
- sqlDatabase :: Text
- sqlPoolSize :: Int
- runSqlite :: (MonadBaseControl IO m, MonadIO m) => Text -> SqlPersistT (NoLoggingT (ResourceT m)) a -> m a
- wrapConnection :: Connection -> IO Connection
Documentation
Arguments
:: (MonadBaseControl IO m, MonadIO m) | |
=> Text | |
-> Int | number of connections to open |
-> (ConnectionPool -> m a) | |
-> m a |
withSqliteConn :: (MonadBaseControl IO m, MonadIO m) => Text -> (Connection -> m a) -> m aSource
createSqlitePool :: MonadIO m => Text -> Int -> m ConnectionPoolSource
module Database.Persist.Sql
data SqliteConf Source
Information required to connect to a sqlite database
Constructors
SqliteConf | |
Fields
|
Instances
Arguments
:: (MonadBaseControl IO m, MonadIO m) | |
=> Text | connection string |
-> SqlPersistT (NoLoggingT (ResourceT m)) a | database action |
-> m a |
A convenience helper which creates a new database connection and runs the
given block, handling MonadResource
and MonadLogger
requirements. Note
that all log messages are discarded.
Since 1.1.4
wrapConnection :: Connection -> IO ConnectionSource
Wrap up a raw Connection
as a Persistent SQL Connection
.
Since 1.1.5