Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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, MonadLoggerIO m) => Text -> Int -> (Pool SqlBackend -> m a) -> m a
- withSqlitePoolInfo :: (MonadUnliftIO m, MonadLoggerIO m) => SqliteConnectionInfo -> Int -> (Pool SqlBackend -> m a) -> m a
- withSqliteConn :: (MonadUnliftIO m, MonadLoggerIO m) => Text -> (SqlBackend -> m a) -> m a
- withSqliteConnInfo :: (MonadUnliftIO m, MonadLoggerIO m) => SqliteConnectionInfo -> (SqlBackend -> m a) -> m a
- createSqlitePool :: (MonadLoggerIO m, MonadUnliftIO m) => Text -> Int -> m (Pool SqlBackend)
- createSqlitePoolFromInfo :: (MonadLoggerIO m, MonadUnliftIO m) => SqliteConnectionInfo -> Int -> m (Pool SqlBackend)
- 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 => Text -> ReaderT SqlBackend (NoLoggingT (ResourceT m)) a -> m a
- runSqliteInfo :: MonadUnliftIO m => SqliteConnectionInfo -> ReaderT SqlBackend (NoLoggingT (ResourceT m)) a -> m a
- wrapConnection :: Connection -> LogFunc -> IO SqlBackend
- wrapConnectionInfo :: SqliteConnectionInfo -> Connection -> LogFunc -> IO SqlBackend
- mockMigration :: Migration -> IO ()
- retryOnBusy :: (MonadUnliftIO m, MonadLoggerIO m) => m a -> m a
- waitForDatabase :: (MonadUnliftIO m, MonadLoggerIO m, BackendCompatible SqlBackend backend) => ReaderT backend m ()
- data ForeignKeyViolation = ForeignKeyViolation {}
- checkForeignKeys :: (MonadResource m, MonadReader env m, BackendCompatible SqlBackend env) => ConduitM () ForeignKeyViolation m ()
- data RawSqlite backend
- persistentBackend :: forall backend backend. Lens (RawSqlite backend) (RawSqlite backend) backend backend
- rawSqliteConnection :: forall backend. Lens' (RawSqlite backend) Connection
- withRawSqliteConnInfo :: (MonadUnliftIO m, MonadLoggerIO m) => SqliteConnectionInfo -> (RawSqlite SqlBackend -> m a) -> m a
- createRawSqlitePoolFromInfo :: (MonadLoggerIO m, MonadUnliftIO m) => SqliteConnectionInfo -> (RawSqlite SqlBackend -> m ()) -> Int -> m (Pool (RawSqlite SqlBackend))
- createRawSqlitePoolFromInfo_ :: (MonadLoggerIO m, MonadUnliftIO m) => SqliteConnectionInfo -> Int -> m (Pool (RawSqlite SqlBackend))
- withRawSqlitePoolInfo :: (MonadUnliftIO m, MonadLoggerIO m) => SqliteConnectionInfo -> (RawSqlite SqlBackend -> m ()) -> Int -> (Pool (RawSqlite SqlBackend) -> m a) -> m a
- withRawSqlitePoolInfo_ :: (MonadUnliftIO m, MonadLoggerIO m) => SqliteConnectionInfo -> Int -> (Pool (RawSqlite SqlBackend) -> m a) -> m a
Documentation
:: (MonadUnliftIO m, MonadLoggerIO m) | |
=> Text | |
-> Int | number of connections to open |
-> (Pool SqlBackend -> m a) | |
-> m a |
Run the given action with a connection pool.
Like createSqlitePool
, this should not be used with :memory:
.
:: (MonadUnliftIO m, MonadLoggerIO m) | |
=> SqliteConnectionInfo | |
-> Int | number of connections to open |
-> (Pool SqlBackend -> 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, MonadLoggerIO m) => Text -> (SqlBackend -> m a) -> m a Source #
withSqliteConnInfo :: (MonadUnliftIO m, MonadLoggerIO m) => SqliteConnectionInfo -> (SqlBackend -> m a) -> m a Source #
Since: 2.6.2
createSqlitePool :: (MonadLoggerIO m, MonadUnliftIO m) => Text -> Int -> m (Pool SqlBackend) 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 :: (MonadLoggerIO m, MonadUnliftIO m) => SqliteConnectionInfo -> Int -> m (Pool SqlBackend) 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.
Instances
FromJSON SqliteConf Source # | |
Defined in Database.Persist.Sqlite parseJSON :: Value -> Parser SqliteConf # parseJSONList :: Value -> Parser [SqliteConf] # | |
Show SqliteConf Source # | |
Defined in Database.Persist.Sqlite showsPrec :: Int -> SqliteConf -> ShowS # show :: SqliteConf -> String # showList :: [SqliteConf] -> ShowS # | |
PersistConfig SqliteConf Source # | |
Defined in Database.Persist.Sqlite type PersistConfigBackend SqliteConf :: (Type -> Type) -> Type -> Type # type PersistConfigPool SqliteConf # 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 PersistConfigBackend SqliteConf Source # | |
Defined in Database.Persist.Sqlite | |
type PersistConfigPool 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
FromJSON SqliteConnectionInfo Source # | |
Defined in Database.Persist.Sqlite parseJSON :: Value -> Parser SqliteConnectionInfo # parseJSONList :: Value -> Parser [SqliteConnectionInfo] # | |
Show SqliteConnectionInfo Source # | |
Defined in Database.Persist.Sqlite showsPrec :: Int -> SqliteConnectionInfo -> ShowS # show :: SqliteConnectionInfo -> String # showList :: [SqliteConnectionInfo] -> ShowS # |
mkSqliteConnectionInfo :: Text -> SqliteConnectionInfo Source #
Creates a SqliteConnectionInfo from a connection string, with the default settings.
Since: 2.6.2
:: MonadUnliftIO m | |
=> Text | connection string |
-> ReaderT SqlBackend (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
:: MonadUnliftIO m | |
=> SqliteConnectionInfo | |
-> ReaderT SqlBackend (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 :: Connection -> LogFunc -> IO SqlBackend 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' backend
On 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 :: SqliteConnectionInfo -> Connection -> LogFunc -> IO SqlBackend 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, MonadLoggerIO m) => m a -> m a Source #
Retry if a Busy is thrown, following an exponential backoff strategy.
Since: 2.9.3
waitForDatabase :: (MonadUnliftIO m, MonadLoggerIO m, 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
data ForeignKeyViolation Source #
Data type for reporting foreign key violations using checkForeignKeys
.
Since: 2.11.1
ForeignKeyViolation | |
|
Instances
Show ForeignKeyViolation Source # | |
Defined in Database.Persist.Sqlite showsPrec :: Int -> ForeignKeyViolation -> ShowS # show :: ForeignKeyViolation -> String # showList :: [ForeignKeyViolation] -> ShowS # | |
Eq ForeignKeyViolation Source # | |
Defined in Database.Persist.Sqlite (==) :: ForeignKeyViolation -> ForeignKeyViolation -> Bool # (/=) :: ForeignKeyViolation -> ForeignKeyViolation -> Bool # | |
Ord ForeignKeyViolation Source # | |
Defined in Database.Persist.Sqlite compare :: ForeignKeyViolation -> ForeignKeyViolation -> Ordering # (<) :: ForeignKeyViolation -> ForeignKeyViolation -> Bool # (<=) :: ForeignKeyViolation -> ForeignKeyViolation -> Bool # (>) :: ForeignKeyViolation -> ForeignKeyViolation -> Bool # (>=) :: ForeignKeyViolation -> ForeignKeyViolation -> Bool # max :: ForeignKeyViolation -> ForeignKeyViolation -> ForeignKeyViolation # min :: ForeignKeyViolation -> ForeignKeyViolation -> ForeignKeyViolation # |
checkForeignKeys :: (MonadResource m, MonadReader env m, BackendCompatible SqlBackend env) => ConduitM () ForeignKeyViolation m () Source #
Outputs all (if any) the violated foreign key constraints in the database.
The main use is to validate that no foreign key constraints were
broken/corrupted by anyone operating on the database with foreign keys
disabled. See fkEnabled
.
Since: 2.11.1
data RawSqlite backend Source #
Wrapper for persistent SqlBackends that carry the corresponding
Connection
.
Since: 2.10.2
Instances
persistentBackend :: forall backend backend. Lens (RawSqlite backend) (RawSqlite backend) backend backend Source #
rawSqliteConnection :: forall backend. Lens' (RawSqlite backend) Connection Source #
withRawSqliteConnInfo :: (MonadUnliftIO m, MonadLoggerIO m) => SqliteConnectionInfo -> (RawSqlite SqlBackend -> m a) -> m a Source #
Like withSqliteConnInfo
, but exposes the internal Connection
.
For power users who want to manually interact with SQLite's C API via
internals exposed by Database.Sqlite.Internal
Since: 2.10.2
createRawSqlitePoolFromInfo Source #
:: (MonadLoggerIO m, MonadUnliftIO m) | |
=> SqliteConnectionInfo | |
-> (RawSqlite SqlBackend -> m ()) | An action that is run whenever a new |
-> Int | |
-> m (Pool (RawSqlite SqlBackend)) |
Like createSqlitePoolFromInfo
, but like withRawSqliteConnInfo
it
exposes the internal Connection
.
For power users who want to manually interact with SQLite's C API via internals exposed by Database.Sqlite.Internal. The callback can be used to run arbitrary actions on the connection upon allocation from the pool.
Since: 2.10.6
createRawSqlitePoolFromInfo_ :: (MonadLoggerIO m, MonadUnliftIO m) => SqliteConnectionInfo -> Int -> m (Pool (RawSqlite SqlBackend)) Source #
Like createRawSqlitePoolFromInfo
, but doesn't require a callback
operating on the connection.
Since: 2.10.6
withRawSqlitePoolInfo Source #
:: (MonadUnliftIO m, MonadLoggerIO m) | |
=> SqliteConnectionInfo | |
-> (RawSqlite SqlBackend -> m ()) | |
-> Int | number of connections to open |
-> (Pool (RawSqlite SqlBackend) -> m a) | |
-> m a |
Like createSqlitePoolInfo
, but based on createRawSqlitePoolFromInfo
.
Since: 2.10.6
withRawSqlitePoolInfo_ Source #
:: (MonadUnliftIO m, MonadLoggerIO m) | |
=> SqliteConnectionInfo | |
-> Int | number of connections to open |
-> (Pool (RawSqlite SqlBackend) -> m a) | |
-> m a |
Like createSqlitePoolInfo
, but based on createRawSqlitePoolFromInfo_
.
Since: 2.10.6