| Safe Haskell | None |
|---|---|
| Language | Haskell98 |
Database.Persist.Sqlite
Description
A sqlite backend for persistent.
Note: If you prepend WAL=off to your connection string, it will disable
the write-ahead log. This functionality is now deprecated in favour of using SqliteConnectionInfo.
Synopsis
- withSqlitePool :: (MonadUnliftIO m, MonadLogger m, IsSqlBackend backend) => Text -> Int -> (Pool backend -> m a) -> m a
- withSqlitePoolInfo :: (MonadUnliftIO m, MonadLogger m, IsSqlBackend backend) => SqliteConnectionInfo -> Int -> (Pool backend -> m a) -> m a
- withSqliteConn :: (MonadUnliftIO m, MonadLogger m, IsSqlBackend backend) => Text -> (backend -> m a) -> m a
- withSqliteConnInfo :: (MonadUnliftIO m, MonadLogger m, IsSqlBackend backend) => SqliteConnectionInfo -> (backend -> m a) -> m a
- createSqlitePool :: (MonadLogger m, MonadUnliftIO m, IsSqlBackend backend) => Text -> Int -> m (Pool backend)
- createSqlitePoolFromInfo :: (MonadLogger m, MonadUnliftIO m, IsSqlBackend backend) => SqliteConnectionInfo -> Int -> m (Pool backend)
- module Database.Persist.Sql
- data SqliteConf
- = SqliteConf {
- sqlDatabase :: Text
- sqlPoolSize :: Int
- | SqliteConfInfo { }
- = SqliteConf {
- data SqliteConnectionInfo
- mkSqliteConnectionInfo :: Text -> SqliteConnectionInfo
- sqlConnectionStr :: Lens' SqliteConnectionInfo Text
- walEnabled :: Lens' SqliteConnectionInfo Bool
- fkEnabled :: Lens' SqliteConnectionInfo Bool
- extraPragmas :: Lens' SqliteConnectionInfo [Text]
- runSqlite :: (MonadUnliftIO m, IsSqlBackend backend) => Text -> ReaderT backend (NoLoggingT (ResourceT m)) a -> m a
- runSqliteInfo :: (MonadUnliftIO m, IsSqlBackend backend) => SqliteConnectionInfo -> ReaderT backend (NoLoggingT (ResourceT m)) a -> m a
- wrapConnection :: IsSqlBackend backend => Connection -> LogFunc -> IO backend
- wrapConnectionInfo :: IsSqlBackend backend => SqliteConnectionInfo -> Connection -> LogFunc -> IO backend
- mockMigration :: Migration -> IO ()
- retryOnBusy :: (MonadUnliftIO m, MonadLogger m) => m a -> m a
- waitForDatabase :: (MonadUnliftIO m, MonadLogger m, IsSqlBackend backend, BackendCompatible SqlBackend backend) => ReaderT backend m ()
Documentation
Arguments
| :: (MonadUnliftIO m, MonadLogger m, IsSqlBackend backend) | |
| => Text | |
| -> Int | number of connections to open |
| -> (Pool backend -> m a) | |
| -> m a |
Run the given action with a connection pool.
Like createSqlitePool, this should not be used with :memory:.
Arguments
| :: (MonadUnliftIO m, MonadLogger m, IsSqlBackend backend) | |
| => SqliteConnectionInfo | |
| -> Int | number of connections to open |
| -> (Pool backend -> m a) | |
| -> m a |
Run the given action with a connection pool.
Like createSqlitePool, this should not be used with :memory:.
Since: 2.6.2
withSqliteConn :: (MonadUnliftIO m, MonadLogger m, IsSqlBackend backend) => Text -> (backend -> m a) -> m a Source #
withSqliteConnInfo :: (MonadUnliftIO m, MonadLogger m, IsSqlBackend backend) => SqliteConnectionInfo -> (backend -> m a) -> m a Source #
Since: 2.6.2
createSqlitePool :: (MonadLogger m, MonadUnliftIO m, IsSqlBackend backend) => Text -> Int -> m (Pool backend) Source #
Create a pool of SQLite connections.
Note that this should not be used with the :memory: connection string, as
the pool will regularly remove connections, destroying your database.
Instead, use withSqliteConn.
createSqlitePoolFromInfo :: (MonadLogger m, MonadUnliftIO m, IsSqlBackend backend) => SqliteConnectionInfo -> Int -> m (Pool backend) Source #
Create a pool of SQLite connections.
Note that this should not be used with the :memory: connection string, as
the pool will regularly remove connections, destroying your database.
Instead, use withSqliteConn.
Since: 2.6.2
module Database.Persist.Sql
data SqliteConf Source #
Information required to setup a connection pool.
Constructors
| SqliteConf | |
Fields
| |
| SqliteConfInfo | |
Fields | |
Instances
| Show SqliteConf Source # | |
Defined in Database.Persist.Sqlite Methods showsPrec :: Int -> SqliteConf -> ShowS # show :: SqliteConf -> String # showList :: [SqliteConf] -> ShowS # | |
| FromJSON SqliteConf Source # | |
Defined in Database.Persist.Sqlite | |
| PersistConfig SqliteConf Source # | |
Defined in Database.Persist.Sqlite Associated Types type PersistConfigBackend SqliteConf :: (Type -> Type) -> Type -> Type # type PersistConfigPool SqliteConf :: Type # Methods loadConfig :: Value -> Parser SqliteConf # applyEnv :: SqliteConf -> IO SqliteConf # createPoolConfig :: SqliteConf -> IO (PersistConfigPool SqliteConf) # runPool :: MonadUnliftIO m => SqliteConf -> PersistConfigBackend SqliteConf m a -> PersistConfigPool SqliteConf -> m a # | |
| type PersistConfigPool SqliteConf Source # | |
Defined in Database.Persist.Sqlite | |
| type PersistConfigBackend SqliteConf Source # | |
Defined in Database.Persist.Sqlite | |
data SqliteConnectionInfo Source #
Information required to connect to a sqlite database. We export lenses instead of fields to avoid being limited to the current implementation.
Since: 2.6.2
Instances
| Show SqliteConnectionInfo Source # | |
Defined in Database.Persist.Sqlite Methods showsPrec :: Int -> SqliteConnectionInfo -> ShowS # show :: SqliteConnectionInfo -> String # showList :: [SqliteConnectionInfo] -> ShowS # | |
| FromJSON SqliteConnectionInfo Source # | |
Defined in Database.Persist.Sqlite Methods parseJSON :: Value -> Parser SqliteConnectionInfo # parseJSONList :: Value -> Parser [SqliteConnectionInfo] # | |
mkSqliteConnectionInfo :: Text -> SqliteConnectionInfo Source #
Creates a SqliteConnectionInfo from a connection string, with the default settings.
Since: 2.6.2
Arguments
| :: (MonadUnliftIO m, IsSqlBackend backend) | |
| => Text | connection string |
| -> ReaderT backend (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
Arguments
| :: (MonadUnliftIO m, IsSqlBackend backend) | |
| => SqliteConnectionInfo | |
| -> ReaderT backend (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: 2.6.2
wrapConnection :: IsSqlBackend backend => Connection -> LogFunc -> IO backend Source #
Wrap up a raw Connection as a Persistent SQL Connection.
Example usage
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
import Control.Monad.IO.Class (liftIO)
import Database.Persist
import Database.Sqlite
import Database.Persist.Sqlite
import Database.Persist.TH
share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase|
Person
name String
age Int Maybe
deriving Show
|]
main :: IO ()
main = do
conn <- open "/home/sibi/test.db"
(backend :: SqlBackend) <- wrapConnection conn (\_ _ _ _ -> return ())
flip runSqlPersistM backend $ do
runMigration migrateAll
insert_ $ Person "John doe" $ Just 35
insert_ $ Person "Hema" $ Just 36
(pers :: [Entity Person]) <- selectList [] []
liftIO $ print pers
close' backendOn executing it, you get this output:
Migrating: CREATE TABLE "person"("id" INTEGER PRIMARY KEY,"name" VARCHAR NOT NULL,"age" INTEGER NULL)
[Entity {entityKey = PersonKey {unPersonKey = SqlBackendKey {unSqlBackendKey = 1}}, entityVal = Person {personName = "John doe", personAge = Just 35}},Entity {entityKey = PersonKey {unPersonKey = SqlBackendKey {unSqlBackendKey = 2}}, entityVal = Person {personName = "Hema", personAge = Just 36}}]Since: 1.1.5
wrapConnectionInfo :: IsSqlBackend backend => SqliteConnectionInfo -> Connection -> LogFunc -> IO backend Source #
Wrap up a raw Connection as a Persistent SQL
Connection, allowing full control over WAL and FK constraints.
Since: 2.6.2
mockMigration :: Migration -> IO () Source #
Mock a migration even when the database is not present.
This function performs the same functionality of printMigration
with the difference that an actual database isn't needed for it.
retryOnBusy :: (MonadUnliftIO m, MonadLogger m) => m a -> m a Source #
Retry if a Busy is thrown, following an exponential backoff strategy.
Since: 2.9.3
waitForDatabase :: (MonadUnliftIO m, MonadLogger m, IsSqlBackend backend, BackendCompatible SqlBackend backend) => ReaderT backend m () Source #
Wait until some noop action on the database does not return an ErrorBusy. See retryOnBusy.
Since: 2.9.3