Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Database.Persist.Sql.Types.Internal
Description
Breaking changes to this module are not reflected in the major version number. Prefer to import from Database.Persist.Sql instead. If you neeed something from this module, please file an issue on GitHub.
Synopsis
- class HasPersistBackend backend where
- type BaseBackend backend
- persistBackend :: backend -> BaseBackend backend
- class HasPersistBackend backend => IsPersistBackend backend where
- mkPersistBackend :: BaseBackend backend -> backend
- newtype SqlReadBackend = SqlReadBackend {}
- newtype SqlWriteBackend = 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 IsolationLevel
- makeIsolationLevelStatement :: (Monoid s, IsString s) => IsolationLevel -> s
- data SqlBackend = SqlBackend {
- connPrepare :: Text -> IO Statement
- connInsertSql :: EntityDef -> [PersistValue] -> InsertSqlResult
- connInsertManySql :: Maybe (EntityDef -> [[PersistValue]] -> InsertSqlResult)
- connUpsertSql :: Maybe (EntityDef -> NonEmpty (FieldNameHS, FieldNameDB) -> Text -> Text)
- connPutManySql :: Maybe (EntityDef -> Int -> Text)
- connStmtMap :: StatementCache
- connClose :: IO ()
- connMigrateSql :: [EntityDef] -> (Text -> IO Statement) -> EntityDef -> IO (Either [Text] [(Bool, Text)])
- connBegin :: (Text -> IO Statement) -> Maybe IsolationLevel -> IO ()
- connCommit :: (Text -> IO Statement) -> IO ()
- connRollback :: (Text -> IO Statement) -> IO ()
- connEscapeFieldName :: FieldNameDB -> Text
- connEscapeTableName :: EntityDef -> Text
- connEscapeRawName :: Text -> Text
- connNoLimit :: Text
- connRDBMS :: Text
- connLimitOffset :: (Int, Int) -> Text -> Text
- connLogFunc :: LogFunc
- connMaxParams :: Maybe Int
- connRepsertManySql :: Maybe (EntityDef -> Int -> Text)
- connVault :: Vault
- connHooks :: SqlBackendHooks
- 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)
- newtype SqlBackendHooks = SqlBackendHooks {
- hookGetStatement :: SqlBackend -> Text -> Statement -> IO Statement
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
Associated Types
type BaseBackend backend Source #
Methods
persistBackend :: backend -> BaseBackend backend Source #
Instances
HasPersistBackend SqlReadBackend Source # | |
Defined in Database.Persist.Sql.Types.Internal Associated Types type BaseBackend SqlReadBackend Source # Methods persistBackend :: SqlReadBackend -> BaseBackend SqlReadBackend Source # | |
HasPersistBackend SqlWriteBackend Source # | |
Defined in Database.Persist.Sql.Types.Internal Associated Types Methods persistBackend :: SqlWriteBackend -> BaseBackend SqlWriteBackend Source # | |
HasPersistBackend SqlBackend Source # | |
Defined in Database.Persist.SqlBackend.Internal Associated Types type BaseBackend SqlBackend Source # Methods persistBackend :: SqlBackend -> BaseBackend SqlBackend Source # | |
(BackendCompatible b s, HasPersistBackend b) => HasPersistBackend (Compatible b s) Source # | |
Defined in Database.Persist.Compatible.Types Associated Types type BaseBackend (Compatible b s) Source # Methods persistBackend :: Compatible b s -> BaseBackend (Compatible b s) 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
.
Methods
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.
Instances
IsPersistBackend SqlReadBackend Source # | |
Defined in Database.Persist.Sql.Types.Internal Methods mkPersistBackend :: BaseBackend SqlReadBackend -> SqlReadBackend Source # | |
IsPersistBackend SqlWriteBackend Source # | |
Defined in Database.Persist.Sql.Types.Internal Methods mkPersistBackend :: BaseBackend SqlWriteBackend -> SqlWriteBackend Source # | |
IsPersistBackend SqlBackend Source # | |
Defined in Database.Persist.SqlBackend.Internal Methods mkPersistBackend :: BaseBackend SqlBackend -> SqlBackend Source # |
newtype SqlReadBackend Source #
An SQL backend which can only handle read queries
The constructor was exposed in 2.10.0.
Constructors
SqlReadBackend | |
Fields |
Instances
newtype SqlWriteBackend Source #
An SQL backend which can handle read or write queries
The constructor was exposed in 2.10.0
Constructors
SqlWriteBackend | |
Fields |
Instances
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.
data InsertSqlResult Source #
Constructors
ISRSingle Text | |
ISRInsertGet Text Text | |
ISRManyKeys Text [PersistValue] |
A Statement
is a representation of a database query that has been
prepared and stored on the server side.
Constructors
Statement | |
Fields
|
data IsolationLevel Source #
Please refer to the documentation for the database in question for a full overview of the semantics of the varying isloation levels
Constructors
ReadUncommitted | |
ReadCommitted | |
RepeatableRead | |
Serializable |
Instances
makeIsolationLevelStatement :: (Monoid s, IsString s) => IsolationLevel -> s Source #
data SqlBackend Source #
A SqlBackend
represents a handle or connection to a database. It
contains functions and values that allow databases to have more
optimized implementations, as well as references that benefit
performance and sharing.
Instead of using the SqlBackend
constructor directly, use the
mkSqlBackend
function.
A SqlBackend
is *not* thread-safe. You should not assume that
a SqlBackend
can be shared among threads and run concurrent queries.
This *will* result in problems. Instead, you should create a
, known as a Pool
SqlBackend
ConnectionPool
, and pass that around in
multi-threaded applications.
To run actions in the persistent
library, you should use the
runSqlConn
function. If you're using a multithreaded application, use
the runSqlPool
function.
Constructors
SqlBackend | |
Fields
|
Instances
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
.
newtype SqlBackendHooks Source #
Constructors
SqlBackendHooks | |
Fields
|