Safe Haskell | None |
---|---|
Language | Haskell98 |
- class HasPersistBackend backend where
- type BaseBackend backend
- class HasPersistBackend backend => IsPersistBackend backend where
- data SqlReadBackend
- data SqlWriteBackend
- readToUnknown :: Monad m => ReaderT SqlReadBackend m a -> ReaderT SqlBackend m a
- readToWrite :: Monad m => ReaderT SqlReadBackend m a -> ReaderT SqlWriteBackend m a
- writeToUnknown :: Monad m => ReaderT SqlWriteBackend m a -> ReaderT SqlBackend m a
- type LogFunc = Loc -> LogSource -> LogLevel -> LogStr -> IO ()
- data InsertSqlResult
- data Statement = Statement {
- stmtFinalize :: IO ()
- stmtReset :: IO ()
- stmtExecute :: [PersistValue] -> IO Int64
- stmtQuery :: forall m. MonadIO m => [PersistValue] -> Acquire (ConduitM () [PersistValue] m ())
- data SqlBackend = SqlBackend {
- connPrepare :: Text -> IO Statement
- connInsertSql :: EntityDef -> [PersistValue] -> InsertSqlResult
- connInsertManySql :: Maybe (EntityDef -> [[PersistValue]] -> InsertSqlResult)
- connUpsertSql :: Maybe (EntityDef -> Text -> Text)
- connPutManySql :: Maybe (EntityDef -> Int -> Text)
- connStmtMap :: IORef (Map Text Statement)
- connClose :: IO ()
- connMigrateSql :: [EntityDef] -> (Text -> IO Statement) -> EntityDef -> IO (Either [Text] [(Bool, Text)])
- connBegin :: (Text -> IO Statement) -> IO ()
- connCommit :: (Text -> IO Statement) -> IO ()
- connRollback :: (Text -> IO Statement) -> IO ()
- connEscapeName :: DBName -> Text
- connNoLimit :: Text
- connRDBMS :: Text
- connLimitOffset :: (Int, Int) -> Bool -> Text -> Text
- connLogFunc :: LogFunc
- connMaxParams :: Maybe Int
- type SqlBackendCanRead backend = (BackendCompatible SqlBackend backend, PersistQueryRead backend, PersistStoreRead backend, PersistUniqueRead backend)
- type SqlBackendCanWrite backend = (SqlBackendCanRead backend, PersistQueryWrite backend, PersistStoreWrite backend, PersistUniqueWrite backend)
- type SqlReadT m a = forall backend. SqlBackendCanRead backend => ReaderT backend m a
- type SqlWriteT m a = forall backend. SqlBackendCanWrite backend => ReaderT backend m a
- type IsSqlBackend backend = (IsPersistBackend backend, BaseBackend backend ~ SqlBackend)
Documentation
class HasPersistBackend backend where Source #
Class which allows the plucking of a BaseBackend backend
from some larger type.
For example,
instance HasPersistBackend (SqlReadBackend, Int) where
type BaseBackend (SqlReadBackend, Int) = SqlBackend
persistBackend = unSqlReadBackend . fst
type BaseBackend backend Source #
persistBackend :: backend -> BaseBackend backend Source #
class HasPersistBackend backend => IsPersistBackend backend where Source #
Class which witnesses that backend
is essentially the same as BaseBackend backend
.
That is, they're isomorphic and backend
is just some wrapper over BaseBackend backend
.
mkPersistBackend :: BaseBackend backend -> backend Source #
This function is how we actually construct and tag a backend as having read or write capabilities.
It should be used carefully and only when actually constructing a backend
. Careless use allows us
to accidentally run a write query against a read-only database.
data SqlReadBackend Source #
An SQL backend which can only handle read queries
data SqlWriteBackend Source #
An SQL backend which can handle read or write queries
readToUnknown :: Monad m => ReaderT SqlReadBackend m a -> ReaderT SqlBackend m a Source #
Useful for running a read query against a backend with unknown capabilities.
readToWrite :: Monad m => ReaderT SqlReadBackend m a -> ReaderT SqlWriteBackend m a Source #
Useful for running a read query against a backend with read and write capabilities.
writeToUnknown :: Monad m => ReaderT SqlWriteBackend m a -> ReaderT SqlBackend m a Source #
Useful for running a write query against an untagged backend with unknown capabilities.
Statement | |
|
data SqlBackend Source #
SqlBackend | |
|
type SqlBackendCanRead backend = (BackendCompatible SqlBackend backend, PersistQueryRead backend, PersistStoreRead backend, PersistUniqueRead backend) Source #
A constraint synonym which witnesses that a backend is SQL and can run read queries.
type SqlBackendCanWrite backend = (SqlBackendCanRead backend, PersistQueryWrite backend, PersistStoreWrite backend, PersistUniqueWrite backend) Source #
A constraint synonym which witnesses that a backend is SQL and can run read and write queries.
type SqlReadT m a = forall backend. SqlBackendCanRead backend => ReaderT backend m a Source #
Like SqlPersistT
but compatible with any SQL backend which can handle read queries.
type SqlWriteT m a = forall backend. SqlBackendCanWrite backend => ReaderT backend m a Source #
Like SqlPersistT
but compatible with any SQL backend which can handle read and write queries.
type IsSqlBackend backend = (IsPersistBackend backend, BaseBackend backend ~ SqlBackend) Source #
A backend which is a wrapper around SqlBackend
.