| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Database.Persist.Class.PersistStore
Synopsis
- class HasPersistBackend backend where- type BaseBackend backend
- persistBackend :: backend -> BaseBackend backend
 
- withBaseBackend :: HasPersistBackend backend => ReaderT (BaseBackend backend) m a -> ReaderT backend m a
- class HasPersistBackend backend => IsPersistBackend backend where- mkPersistBackend :: BaseBackend backend -> backend
 
- type PersistRecordBackend record backend = (PersistEntity record, PersistEntityBackend record ~ BaseBackend backend)
- liftPersist :: (MonadIO m, MonadReader backend m) => ReaderT backend IO b -> m b
- class PersistCore backend where- data BackendKey backend
 
- class (Show (BackendKey backend), Read (BackendKey backend), Eq (BackendKey backend), Ord (BackendKey backend), PersistCore backend, PersistField (BackendKey backend), ToJSON (BackendKey backend), FromJSON (BackendKey backend)) => PersistStoreRead backend where
- class (Show (BackendKey backend), Read (BackendKey backend), Eq (BackendKey backend), Ord (BackendKey backend), PersistStoreRead backend, PersistField (BackendKey backend), ToJSON (BackendKey backend), FromJSON (BackendKey backend)) => PersistStoreWrite backend where- insert :: forall record m. (MonadIO m, PersistRecordBackend record backend, SafeToInsert record) => record -> ReaderT backend m (Key record)
- insert_ :: forall record m. (MonadIO m, PersistRecordBackend record backend, SafeToInsert record) => record -> ReaderT backend m ()
- insertMany :: forall record m. (MonadIO m, PersistRecordBackend record backend, SafeToInsert record) => [record] -> ReaderT backend m [Key record]
- insertMany_ :: forall record m. (MonadIO m, PersistRecordBackend record backend, SafeToInsert record) => [record] -> ReaderT backend m ()
- insertEntityMany :: forall record m. (MonadIO m, PersistRecordBackend record backend) => [Entity record] -> ReaderT backend m ()
- insertKey :: forall record m. (MonadIO m, PersistRecordBackend record backend) => Key record -> record -> ReaderT backend m ()
- repsert :: forall record m. (MonadIO m, PersistRecordBackend record backend) => Key record -> record -> ReaderT backend m ()
- repsertMany :: forall record m. (MonadIO m, PersistRecordBackend record backend) => [(Key record, record)] -> ReaderT backend m ()
- replace :: forall record m. (MonadIO m, PersistRecordBackend record backend) => Key record -> record -> ReaderT backend m ()
- delete :: forall record m. (MonadIO m, PersistRecordBackend record backend) => Key record -> ReaderT backend m ()
- update :: forall record m. (MonadIO m, PersistRecordBackend record backend) => Key record -> [Update record] -> ReaderT backend m ()
- updateGet :: forall record m. (MonadIO m, PersistRecordBackend record backend) => Key record -> [Update record] -> ReaderT backend m record
 
- getEntity :: forall e backend m. (PersistStoreRead backend, PersistRecordBackend e backend, MonadIO m) => Key e -> ReaderT backend m (Maybe (Entity e))
- getJust :: forall record backend m. (PersistStoreRead backend, PersistRecordBackend record backend, MonadIO m) => Key record -> ReaderT backend m record
- getJustEntity :: forall record backend m. (PersistEntityBackend record ~ BaseBackend backend, MonadIO m, PersistEntity record, PersistStoreRead backend) => Key record -> ReaderT backend m (Entity record)
- belongsTo :: forall ent1 ent2 backend m. (PersistStoreRead backend, PersistEntity ent1, PersistRecordBackend ent2 backend, MonadIO m) => (ent1 -> Maybe (Key ent2)) -> ent1 -> ReaderT backend m (Maybe ent2)
- belongsToJust :: forall ent1 ent2 backend m. (PersistStoreRead backend, PersistEntity ent1, PersistRecordBackend ent2 backend, MonadIO m) => (ent1 -> Key ent2) -> ent1 -> ReaderT backend m ent2
- insertEntity :: forall e backend m. (PersistStoreWrite backend, PersistRecordBackend e backend, SafeToInsert e, MonadIO m, HasCallStack) => e -> ReaderT backend m (Entity e)
- insertRecord :: forall record backend m. (PersistEntityBackend record ~ BaseBackend backend, PersistEntity record, MonadIO m, PersistStoreWrite backend, SafeToInsert record, HasCallStack) => record -> ReaderT backend m record
- class (PersistEntity record, PersistEntityBackend record ~ backend, PersistCore backend) => ToBackendKey backend record where- toBackendKey :: Key record -> BackendKey backend
- fromBackendKey :: BackendKey backend -> Key record
 
- class BackendCompatible sup sub where- projectBackend :: sub -> sup
 
- withCompatibleBackend :: BackendCompatible sup sub => ReaderT sup m a -> ReaderT sub m a
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 # | |
withBaseBackend :: HasPersistBackend backend => ReaderT (BaseBackend backend) m a -> ReaderT backend m a Source #
Run a query against a larger backend by plucking out BaseBackend backend
This is a helper for reusing existing queries when expanding the backend type.
Since: 2.12.0
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 # | |
type PersistRecordBackend record backend = (PersistEntity record, PersistEntityBackend record ~ BaseBackend backend) Source #
A convenient alias for common type signatures
liftPersist :: (MonadIO m, MonadReader backend m) => ReaderT backend IO b -> m b Source #
class PersistCore backend Source #
Associated Types
data BackendKey backend Source #
Instances
| PersistCore SqlReadBackend Source # | |
| Defined in Database.Persist.Sql.Orphan.PersistStore Associated Types data BackendKey SqlReadBackend Source # | |
| PersistCore SqlWriteBackend Source # | |
| Defined in Database.Persist.Sql.Orphan.PersistStore Associated Types data BackendKey SqlWriteBackend Source # | |
| PersistCore SqlBackend Source # | |
| Defined in Database.Persist.Sql.Orphan.PersistStore Associated Types data BackendKey SqlBackend Source # | |
| (BackendCompatible b s, PersistCore b) => PersistCore (Compatible b s) Source # | |
| Defined in Database.Persist.Compatible.Types Associated Types data BackendKey (Compatible b s) Source # | |
class (Show (BackendKey backend), Read (BackendKey backend), Eq (BackendKey backend), Ord (BackendKey backend), PersistCore backend, PersistField (BackendKey backend), ToJSON (BackendKey backend), FromJSON (BackendKey backend)) => PersistStoreRead backend where Source #
Minimal complete definition
Methods
get :: forall record m. (MonadIO m, PersistRecordBackend record backend) => Key record -> ReaderT backend m (Maybe record) Source #
Get a record by identifier, if available.
Example usage
getMany :: forall record m. (MonadIO m, PersistRecordBackend record backend) => [Key record] -> ReaderT backend m (Map (Key record) record) Source #
Get many records by their respective identifiers, if available.
Example usage
getUsers :: MonadIO m => ReaderT SqlBackend m (Map (Key User) User) getUsers = getMany allkeys
musers <- getUsers
The above query when applied on dataset-1, will get these records:
+----+-------+-----+ | id | name | age | +----+-------+-----+ | 1 | SPJ | 40 | +----+-------+-----+ | 2 | Simon | 41 | +----+-------+-----+
Since: 2.8.1
Instances
class (Show (BackendKey backend), Read (BackendKey backend), Eq (BackendKey backend), Ord (BackendKey backend), PersistStoreRead backend, PersistField (BackendKey backend), ToJSON (BackendKey backend), FromJSON (BackendKey backend)) => PersistStoreWrite backend where Source #
Methods
insert :: forall record m. (MonadIO m, PersistRecordBackend record backend, SafeToInsert record) => record -> ReaderT backend m (Key record) Source #
Create a new record in the database, returning an automatically created key (in SQL an auto-increment id).
Example usage
Using schema-1 and dataset-1, let's insert a new user John.
insertJohn :: MonadIO m => ReaderT SqlBackend m (Key User) insertJohn = insert $ User "John" 30
johnId <- insertJohn
The above query when applied on dataset-1, will produce this:
+-----+------+-----+ |id |name |age | +-----+------+-----+ |1 |SPJ |40 | +-----+------+-----+ |2 |Simon |41 | +-----+------+-----+ |3 |John |30 | +-----+------+-----+
insert_ :: forall record m. (MonadIO m, PersistRecordBackend record backend, SafeToInsert record) => record -> ReaderT backend m () Source #
Same as insert, but doesn't return a Key.
Example usage
insertJohn :: MonadIO m => ReaderT SqlBackend m (Key User) insertJohn = insert_ $ User "John" 30
The above query when applied on dataset-1, will produce this:
+-----+------+-----+ |id |name |age | +-----+------+-----+ |1 |SPJ |40 | +-----+------+-----+ |2 |Simon |41 | +-----+------+-----+ |3 |John |30 | +-----+------+-----+
insertMany :: forall record m. (MonadIO m, PersistRecordBackend record backend, SafeToInsert record) => [record] -> ReaderT backend m [Key record] Source #
Create multiple records in the database and return their Keys.
If you don't need the inserted Keys, use insertMany_.
The MongoDB and PostgreSQL backends insert all records and retrieve their keys in one database query.
The SQLite and MySQL backends use the slow, default implementation of
 mapM insert.
Example usage
insertUsers :: MonadIO m => ReaderT SqlBackend m [Key User] insertUsers = insertMany [User "John" 30, User "Nick" 32, User "Jane" 20]
userIds <- insertUsers
The above query when applied on dataset-1, will produce this:
+-----+------+-----+ |id |name |age | +-----+------+-----+ |1 |SPJ |40 | +-----+------+-----+ |2 |Simon |41 | +-----+------+-----+ |3 |John |30 | +-----+------+-----+ |4 |Nick |32 | +-----+------+-----+ |5 |Jane |20 | +-----+------+-----+
insertMany_ :: forall record m. (MonadIO m, PersistRecordBackend record backend, SafeToInsert record) => [record] -> ReaderT backend m () Source #
Same as insertMany, but doesn't return any Keys.
The MongoDB, PostgreSQL, SQLite and MySQL backends insert all records in one database query.
Example usage
insertUsers_ :: MonadIO m => ReaderT SqlBackend m () insertUsers_ = insertMany_ [User "John" 30, User "Nick" 32, User "Jane" 20]
The above query when applied on dataset-1, will produce this:
+-----+------+-----+ |id |name |age | +-----+------+-----+ |1 |SPJ |40 | +-----+------+-----+ |2 |Simon |41 | +-----+------+-----+ |3 |John |30 | +-----+------+-----+ |4 |Nick |32 | +-----+------+-----+ |5 |Jane |20 | +-----+------+-----+
insertEntityMany :: forall record m. (MonadIO m, PersistRecordBackend record backend) => [Entity record] -> ReaderT backend m () Source #
Same as insertMany_, but takes an Entity instead of just a record.
Useful when migrating data from one entity to another and want to preserve ids.
The MongoDB, PostgreSQL, SQLite and MySQL backends insert all records in one database query.
Example usage
insertUserEntityMany :: MonadIO m => ReaderT SqlBackend m () insertUserEntityMany = insertEntityMany [SnakeEntity, EvaEntity]
The above query when applied on dataset-1, will produce this:
+-----+------+-----+ |id |name |age | +-----+------+-----+ |1 |SPJ |40 | +-----+------+-----+ |2 |Simon |41 | +-----+------+-----+ |3 |Snake |38 | +-----+------+-----+ |4 |Eva |38 | +-----+------+-----+
insertKey :: forall record m. (MonadIO m, PersistRecordBackend record backend) => Key record -> record -> ReaderT backend m () Source #
Create a new record in the database using the given key.
Example usage
insertAliceKey :: MonadIO m => Key User -> ReaderT SqlBackend m () insertAliceKey key = insertKey key $ User "Alice" 20
insertAliceKey $ UserKey {unUserKey = SqlBackendKey {unSqlBackendKey = 3}}The above query when applied on dataset-1, will produce this:
+-----+------+-----+ |id |name |age | +-----+------+-----+ |1 |SPJ |40 | +-----+------+-----+ |2 |Simon |41 | +-----+------+-----+ |3 |Alice |20 | +-----+------+-----+
repsert :: forall record m. (MonadIO m, PersistRecordBackend record backend) => Key record -> record -> ReaderT backend m () Source #
Put the record in the database with the given key.
 Unlike replace, if a record with the given key does not
 exist then a new record will be inserted.
Example usage
We try to explain upsertBy using schema-1 and dataset-1.
First, we insert Philip to dataset-1.
insertPhilip :: MonadIO m => ReaderT SqlBackend m (Key User) insertPhilip = insert $ User "Philip" 42
philipId <- insertPhilip
This query will produce:
+-----+------+-----+ |id |name |age | +-----+------+-----+ |1 |SPJ |40 | +-----+------+-----+ |2 |Simon |41 | +-----+------+-----+ |3 |Philip|42 | +-----+------+-----+
repsertHaskell :: MonadIO m => Key record -> ReaderT SqlBackend m () repsertHaskell id = repsert id $ User "Haskell" 81
repsertHaskell philipId
This query will replace Philip's record with Haskell's one:
+-----+-----------------+--------+ |id |name |age | +-----+-----------------+--------+ |1 |SPJ |40 | +-----+-----------------+--------+ |2 |Simon |41 | +-----+-----------------+--------+ |3 |Philip -> Haskell|42 -> 81| +-----+-----------------+--------+
repsert inserts the given record if the key doesn't exist.
repsertXToUnknown :: MonadIO m => ReaderT SqlBackend m () repsertXToUnknown = repsert unknownId $ User "X" 999
For example, applying the above query to dataset-1 will produce this:
+-----+------+-----+ |id |name |age | +-----+------+-----+ |1 |SPJ |40 | +-----+------+-----+ |2 |Simon |41 | +-----+------+-----+ |3 |X |999 | +-----+------+-----+
repsertMany :: forall record m. (MonadIO m, PersistRecordBackend record backend) => [(Key record, record)] -> ReaderT backend m () Source #
Put many entities into the database.
Batch version of repsert for SQL backends.
Useful when migrating data from one entity to another and want to preserve ids.
Example usage
repsertManyUsers :: MonadIO m =>ReaderT SqlBackend m () repsertManyusers = repsertMany [(simonId, User "Philip" 20), (unknownId999, User "Mr. X" 999)]
The above query when applied on dataset-1, will produce this:
+-----+----------------+---------+ |id |name |age | +-----+----------------+---------+ |1 |SPJ |40 | +-----+----------------+---------+ |2 |Simon -> Philip |41 -> 20 | +-----+----------------+---------+ |999 |Mr. X |999 | +-----+----------------+---------+
Since: 2.8.1
replace :: forall record m. (MonadIO m, PersistRecordBackend record backend) => Key record -> record -> ReaderT backend m () Source #
Replace the record in the database with the given
 key. Note that the result is undefined if such record does
 not exist, so you must use insertKey or repsert in
 these cases.
Example usage
With schema-1 schama-1 and dataset-1,
replaceSpj :: MonadIO m => User -> ReaderT SqlBackend m () replaceSpj record = replace spjId record
The above query when applied on dataset-1, will produce this:
+-----+------+-----+ |id |name |age | +-----+------+-----+ |1 |Mike |45 | +-----+------+-----+ |2 |Simon |41 | +-----+------+-----+
delete :: forall record m. (MonadIO m, PersistRecordBackend record backend) => Key record -> ReaderT backend m () Source #
Delete a specific record by identifier. Does nothing if record does not exist.
Example usage
update :: forall record m. (MonadIO m, PersistRecordBackend record backend) => Key record -> [Update record] -> ReaderT backend m () Source #
Update individual fields on a specific record.
Example usage
updateSpj :: MonadIO m => [Update User] -> ReaderT SqlBackend m () updateSpj updates = update spjId updates
updateSpj [UserAge +=. 100]
The above query when applied on dataset-1, will produce this:
+-----+------+-----+ |id |name |age | +-----+------+-----+ |1 |SPJ |140 | +-----+------+-----+ |2 |Simon |41 | +-----+------+-----+
updateGet :: forall record m. (MonadIO m, PersistRecordBackend record backend) => Key record -> [Update record] -> ReaderT backend m record Source #
Update individual fields on a specific record, and retrieve the updated value from the database.
Note that this function will throw an exception if the given key is not found in the database.
Example usage
updateGetSpj :: MonadIO m => [Update User] -> ReaderT SqlBackend m User updateGetSpj updates = updateGet spjId updates
spj <- updateGetSpj [UserAge +=. 100]
The above query when applied on dataset-1, will produce this:
+-----+------+-----+ |id |name |age | +-----+------+-----+ |1 |SPJ |140 | +-----+------+-----+ |2 |Simon |41 | +-----+------+-----+
Instances
getEntity :: forall e backend m. (PersistStoreRead backend, PersistRecordBackend e backend, MonadIO m) => Key e -> ReaderT backend m (Maybe (Entity e)) Source #
Like get, but returns the complete Entity.
Example usage
getSpjEntity :: MonadIO m => ReaderT SqlBackend m (Maybe (Entity User)) getSpjEntity = getEntity spjId
mSpjEnt <- getSpjEntity
The above query when applied on dataset-1, will get this entity:
+----+------+-----+ | id | name | age | +----+------+-----+ | 1 | SPJ | 40 | +----+------+-----+
getJust :: forall record backend m. (PersistStoreRead backend, PersistRecordBackend record backend, MonadIO m) => Key record -> ReaderT backend m record Source #
Same as get, but for a non-null (not Maybe) foreign key.
 Unsafe unless your database is enforcing that the foreign key is valid.
Example usage
getJustSpj :: MonadIO m => ReaderT SqlBackend m User getJustSpj = getJust spjId
spj <- getJust spjId
The above query when applied on dataset-1, will get this record:
+----+------+-----+ | id | name | age | +----+------+-----+ | 1 | SPJ | 40 | +----+------+-----+
getJustUnknown :: MonadIO m => ReaderT SqlBackend m User getJustUnknown = getJust unknownId
mrx <- getJustUnknown
This just throws an error.
getJustEntity :: forall record backend m. (PersistEntityBackend record ~ BaseBackend backend, MonadIO m, PersistEntity record, PersistStoreRead backend) => Key record -> ReaderT backend m (Entity record) Source #
Same as getJust, but returns an Entity instead of just the record.
Example usage
getJustEntitySpj :: MonadIO m => ReaderT SqlBackend m (Entity User) getJustEntitySpj = getJustEntity spjId
spjEnt <- getJustEntitySpj
The above query when applied on dataset-1, will get this entity:
+----+------+-----+ | id | name | age | +----+------+-----+ | 1 | SPJ | 40 | +----+------+-----+
Since: 2.6.1
belongsTo :: forall ent1 ent2 backend m. (PersistStoreRead backend, PersistEntity ent1, PersistRecordBackend ent2 backend, MonadIO m) => (ent1 -> Maybe (Key ent2)) -> ent1 -> ReaderT backend m (Maybe ent2) Source #
Curry this to make a convenience function that loads an associated model.
foreign = belongsTo foreignId
belongsToJust :: forall ent1 ent2 backend m. (PersistStoreRead backend, PersistEntity ent1, PersistRecordBackend ent2 backend, MonadIO m) => (ent1 -> Key ent2) -> ent1 -> ReaderT backend m ent2 Source #
Same as belongsTo, but uses getJust and therefore is similarly unsafe.
insertEntity :: forall e backend m. (PersistStoreWrite backend, PersistRecordBackend e backend, SafeToInsert e, MonadIO m, HasCallStack) => e -> ReaderT backend m (Entity e) Source #
Like insert, but returns the complete Entity.
Example usage
insertHaskellEntity :: MonadIO m => ReaderT SqlBackend m (Entity User) insertHaskellEntity = insertEntity $ User "Haskell" 81
haskellEnt <- insertHaskellEntity
The above query when applied on dataset-1, will produce this:
+----+---------+-----+ | id | name | age | +----+---------+-----+ | 1 | SPJ | 40 | +----+---------+-----+ | 2 | Simon | 41 | +----+---------+-----+ | 3 | Haskell | 81 | +----+---------+-----+
insertRecord :: forall record backend m. (PersistEntityBackend record ~ BaseBackend backend, PersistEntity record, MonadIO m, PersistStoreWrite backend, SafeToInsert record, HasCallStack) => record -> ReaderT backend m record Source #
Like insertEntity but just returns the record instead of Entity.
Example usage
insertDaveRecord :: MonadIO m => ReaderT SqlBackend m User insertDaveRecord = insertRecord $ User "Dave" 50
dave <- insertDaveRecord
The above query when applied on dataset-1, will produce this:
+-----+------+-----+ |id |name |age | +-----+------+-----+ |1 |SPJ |40 | +-----+------+-----+ |2 |Simon |41 | +-----+------+-----+ |3 |Dave |50 | +-----+------+-----+
Since: 2.6.1
class (PersistEntity record, PersistEntityBackend record ~ backend, PersistCore backend) => ToBackendKey backend record where Source #
ToBackendKey converts a PersistEntity Key into a BackendKey
 This can be used by each backend to convert between a Key and a plain
 Haskell type. For Sql, that is done with toSqlKey and fromSqlKey.
By default, a PersistEntity uses the default BackendKey for its Key
 and is an instance of ToBackendKey
A Key that instead uses a custom type will not be an instance of
 ToBackendKey.
Methods
toBackendKey :: Key record -> BackendKey backend Source #
fromBackendKey :: BackendKey backend -> Key record Source #
class BackendCompatible sup sub where Source #
This class witnesses that two backend are compatible, and that you can
 convert from the sub backend into the sup backend. This is similar
 to the HasPersistBackend and IsPersistBackend classes, but where you
 don't want to fix the type associated with the PersistEntityBackend of
 a record.
Generally speaking, where you might have:
foo :: (PersistEntityrecord ,PersistEntityBackendrecord ~BaseBackendbackend ,IsSqlBackendbackend )
this can be replaced with:
foo :: (PersistEntityrecord, ,PersistEntityBackendrecord ~ backend ,BackendCompatibleSqlBackendbackend )
This works for SqlReadBackend because of the instance , without needing to go through the BackendCompatible SqlBackend SqlReadBackendBaseBackend type family.
Likewise, functions that are currently hardcoded to use SqlBackend can be generalized:
-- before: asdf ::ReaderTSqlBackendm () asdf = pure () -- after: asdf' ::BackendCompatibleSqlBackend backend => ReaderT backend m () asdf' =withCompatibleBackendasdf
Since: 2.7.1
Methods
projectBackend :: sub -> sup Source #
Instances
| BackendCompatible SqlBackend SqlReadBackend Source # | |
| Defined in Database.Persist.Sql.Orphan.PersistStore Methods | |
| BackendCompatible SqlBackend SqlWriteBackend Source # | |
| Defined in Database.Persist.Sql.Orphan.PersistStore Methods | |
| BackendCompatible SqlBackend SqlBackend Source # | |
| Defined in Database.Persist.Sql.Orphan.PersistStore Methods | |
withCompatibleBackend :: BackendCompatible sup sub => ReaderT sup m a -> ReaderT sub m a Source #
Run a query against a compatible backend, by projecting the backend
This is a helper for using queries which run against a specific backend type that your backend is compatible with.
Since: 2.12.0