Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class PersistStoreRead backend => PersistUniqueRead backend where
- class (PersistUniqueRead backend, PersistStoreWrite backend) => PersistUniqueWrite backend where
- deleteBy :: forall record m. (MonadIO m, PersistRecordBackend record backend) => Unique record -> ReaderT backend m ()
- insertUnique :: forall record m. (MonadIO m, PersistRecordBackend record backend) => record -> ReaderT backend m (Maybe (Key record))
- upsert :: forall record m. (MonadIO m, PersistRecordBackend record backend, OnlyOneUniqueKey record) => record -> [Update record] -> ReaderT backend m (Entity record)
- upsertBy :: forall record m. (MonadIO m, PersistRecordBackend record backend) => Unique record -> record -> [Update record] -> ReaderT backend m (Entity record)
- putMany :: forall record m. (MonadIO m, PersistRecordBackend record backend) => [record] -> ReaderT backend m ()
- class PersistEntity record => OnlyOneUniqueKey record where
- onlyUniqueP :: record -> Unique record
- onlyOneUniqueDef :: (OnlyOneUniqueKey record, Monad proxy) => proxy record -> UniqueDef
- class PersistEntity record => AtLeastOneUniqueKey record where
- requireUniquesP :: record -> NonEmpty (Unique record)
- atLeastOneUniqueDef :: (AtLeastOneUniqueKey record, Monad proxy) => proxy record -> NonEmpty UniqueDef
- type NoUniqueKeysError ty = (('Text "The entity " :<>: 'ShowType ty) :<>: 'Text " does not have any unique keys.") :$$: ('Text "The function you are trying to call requires a unique key " :<>: 'Text "to be defined on the entity.")
- type MultipleUniqueKeysError ty = ((('Text "The entity " :<>: 'ShowType ty) :<>: 'Text " has multiple unique keys.") :$$: ('Text "The function you are trying to call requires only a single " :<>: 'Text "unique key.")) :$$: (('Text "There is probably a variant of the function with 'By' " :<>: 'Text "appended that will allow you to select a unique key ") :<>: 'Text "for the operation.")
- getByValue :: forall record m backend. (MonadIO m, PersistUniqueRead backend, PersistRecordBackend record backend, AtLeastOneUniqueKey record) => record -> ReaderT backend m (Maybe (Entity record))
- getByValueUniques :: forall record backend m. (MonadIO m, PersistUniqueRead backend, PersistRecordBackend record backend) => [Unique record] -> ReaderT backend m (Maybe (Entity record))
- insertBy :: forall record backend m. (MonadIO m, PersistUniqueWrite backend, PersistRecordBackend record backend, AtLeastOneUniqueKey record) => record -> ReaderT backend m (Either (Entity record) (Key record))
- insertUniqueEntity :: forall record backend m. (MonadIO m, PersistRecordBackend record backend, PersistUniqueWrite backend) => record -> ReaderT backend m (Maybe (Entity record))
- replaceUnique :: forall record backend m. (MonadIO m, Eq (Unique record), PersistRecordBackend record backend, PersistUniqueWrite backend) => Key record -> record -> ReaderT backend m (Maybe (Unique record))
- checkUnique :: forall record backend m. (MonadIO m, PersistRecordBackend record backend, PersistUniqueRead backend) => record -> ReaderT backend m (Maybe (Unique record))
- checkUniqueUpdateable :: forall record backend m. (MonadIO m, PersistRecordBackend record backend, PersistUniqueRead backend) => Entity record -> ReaderT backend m (Maybe (Unique record))
- onlyUnique :: forall record backend m. (MonadIO m, PersistUniqueWrite backend, PersistRecordBackend record backend, OnlyOneUniqueKey record) => record -> ReaderT backend m (Unique record)
- defaultUpsertBy :: (PersistEntityBackend record ~ BaseBackend backend, PersistEntity record, MonadIO m, PersistStoreWrite backend, PersistUniqueRead backend) => Unique record -> record -> [Update record] -> ReaderT backend m (Entity record)
- defaultPutMany :: forall record backend m. (PersistEntityBackend record ~ BaseBackend backend, PersistEntity record, MonadIO m, PersistStoreWrite backend, PersistUniqueRead backend) => [record] -> ReaderT backend m ()
- persistUniqueKeyValues :: PersistEntity record => record -> [PersistValue]
Documentation
class PersistStoreRead backend => PersistUniqueRead backend where Source #
Queries against Unique
keys (other than the id Key
).
Please read the general Persistent documentation to learn how to create
Unique
keys.
Using this with an Entity without a Unique key leads to undefined
behavior. A few of these functions require a single Unique
, so using
an Entity with multiple Unique
s is also undefined. In these cases
persistent's goal is to throw an exception as soon as possible, but
persistent is still transitioning to that.
SQL backends automatically create uniqueness constraints, but for MongoDB you must manually place a unique index on a field to have a uniqueness constraint.
getBy :: forall record m. (MonadIO m, PersistRecordBackend record backend) => Unique record -> ReaderT backend m (Maybe (Entity record)) Source #
Get a record by unique key, if available. Returns also the identifier.
Example usage
getBySpjName :: MonadIO m => ReaderT SqlBackend m (Maybe (Entity User)) getBySpjName = getBy $ UniqueUserName "SPJ"
mSpjEnt <- getBySpjName
The above query when applied on dataset-1, will get this entity:
+----+------+-----+ | id | name | age | +----+------+-----+ | 1 | SPJ | 40 | +----+------+-----+
Instances
class (PersistUniqueRead backend, PersistStoreWrite backend) => PersistUniqueWrite backend where Source #
Some functions in this module (insertUnique
, insertBy
, and
replaceUnique
) first query the unique indexes to check for
conflicts. You could instead optimistically attempt to perform the
operation (e.g. replace
instead of replaceUnique
). However,
- there is some fragility to trying to catch the correct exception and determing the column of failure;
- an exception will automatically abort the current SQL transaction.
deleteBy :: forall record m. (MonadIO m, PersistRecordBackend record backend) => Unique record -> ReaderT backend m () Source #
Delete a specific record by unique key. Does nothing if no record matches.
Example usage
insertUnique :: forall record m. (MonadIO m, PersistRecordBackend record backend) => record -> ReaderT backend m (Maybe (Key record)) Source #
Like insert
, but returns Nothing
when the record
couldn't be inserted because of a uniqueness constraint.
Example usage
With schema-1 and dataset-1, we try to insert the following two records:
linusId <- insertUnique $ User "Linus" 48 spjId <- insertUnique $ User "SPJ" 90
+-----+------+-----+ |id |name |age | +-----+------+-----+ |1 |SPJ |40 | +-----+------+-----+ |2 |Simon |41 | +-----+------+-----+ |3 |Linus |48 | +-----+------+-----+
Linus's record was inserted to dataset-1, while SPJ wasn't because SPJ already exists in dataset-1.
:: forall record m. (MonadIO m, PersistRecordBackend record backend, OnlyOneUniqueKey record) | |
=> record | new record to insert |
-> [Update record] | updates to perform if the record already exists |
-> ReaderT backend m (Entity record) | the record in the database after the operation |
Update based on a uniqueness constraint or insert:
- insert the new record if it does not exist;
- If the record exists (matched via it's uniqueness constraint), then update the existing record with the parameters which is passed on as list to the function.
Example usage
First, we try to explain upsert
using schema-1 and dataset-1.
upsertSpj :: MonadIO m => [Update User] -> ReaderT SqlBackend m (Maybe (Entity User)) upsertSpj updates = upsert (User "SPJ" 999) upadtes
mSpjEnt <- upsertSpj [UserAge +=. 15]
The above query when applied on dataset-1, will produce this:
+-----+-----+--------+ |id |name |age | +-----+-----+--------+ |1 |SPJ |40 -> 55| +-----+-----+--------+ |2 |Simon|41 | +-----+-----+--------+
upsertX :: MonadIO m => [Update User] -> ReaderT SqlBackend m (Maybe (Entity User)) upsertX updates = upsert (User "X" 999) updates
mXEnt <- upsertX [UserAge +=. 15]
The above query when applied on dataset-1, will produce this:
+-----+-----+--------+ |id |name |age | +-----+-----+--------+ |1 |SPJ |40 | +-----+-----+--------+ |2 |Simon|41 | +-----+-----+--------+ |3 |X |999 | +-----+-----+--------+
Next, what if the schema has two uniqueness constraints? Let's check it out using schema-2:
mSpjEnt <- upsertSpj [UserAge +=. 15]
This fails with a compile-time type error alerting us to the fact
that this record has multiple unique keys, and suggests that we look for
upsertBy
to select the unique key we want.
:: forall record m. (MonadIO m, PersistRecordBackend record backend) | |
=> Unique record | uniqueness constraint to find by |
-> record | new record to insert |
-> [Update record] | updates to perform if the record already exists |
-> ReaderT backend m (Entity record) | the record in the database after the operation |
Update based on a given uniqueness constraint or insert:
- insert the new record if it does not exist;
- update the existing record that matches the given uniqueness constraint.
Example usage
We try to explain upsertBy
using schema-2 and dataset-1.
upsertBySpjName :: MonadIO m => User -> [Update User] -> ReaderT SqlBackend m (Entity User) upsertBySpjName record updates = upsertBy (UniqueUserName "SPJ") record updates
mSpjEnt <- upsertBySpjName (Person "X" 999) [PersonAge += .15]
The above query will alter dataset-1 to:
+-----+-----+--------+ |id |name |age | +-----+-----+--------+ |1 |SPJ |40 -> 55| +-----+-----+--------+ |2 |Simon|41 | +-----+-----+--------+
upsertBySimonAge :: MonadIO m => User -> [Update User] -> ReaderT SqlBackend m (Entity User) upsertBySimonAge record updates = upsertBy (UniqueUserName "SPJ") record updates
mPhilipEnt <- upsertBySimonAge (User "X" 999) [UserName =. "Philip"]
The above query will alter dataset-1 to:
+----+-----------------+-----+ | id | name | age | +----+-----------------+-----+ | 1 | SPJ | 40 | +----+-----------------+-----+ | 2 | Simon -> Philip | 41 | +----+-----------------+-----+
upsertByUnknownName :: MonadIO m => User -> [Update User] -> ReaderT SqlBackend m (Entity User) upsertByUnknownName record updates = upsertBy (UniqueUserName "Unknown") record updates
mXEnt <- upsertByUnknownName (User "X" 999) [UserAge +=. 15]
This query will alter dataset-1 to:
+-----+-----+-----+ |id |name |age | +-----+-----+-----+ |1 |SPJ |40 | +-----+-----+-----+ |2 |Simon|41 | +-----+-----+-----+ |3 |X |999 | +-----+-----+-----+
:: forall record m. (MonadIO m, PersistRecordBackend record backend) | |
=> [record] | A list of the records you want to insert or replace. |
-> ReaderT backend m () |
Put many records into db
- insert new records that do not exist (or violate any unique constraints)
- replace existing records (matching any unique constraint)
Since: 2.8.1
Instances
class PersistEntity record => OnlyOneUniqueKey record where Source #
This class is used to ensure that upsert
is only called on records
that have a single Unique
key. The quasiquoter automatically generates
working instances for appropriate records, and generates TypeError
instances for records that have 0 or multiple unique keys.
Since: 2.10.0
onlyUniqueP :: record -> Unique record Source #
onlyOneUniqueDef :: (OnlyOneUniqueKey record, Monad proxy) => proxy record -> UniqueDef Source #
Given a proxy for a PersistEntity
record, this returns the sole
UniqueDef
for that entity.
Since: 2.13.0.0
class PersistEntity record => AtLeastOneUniqueKey record where Source #
This class is used to ensure that functions requring at least one
unique key are not called with records that have 0 unique keys. The
quasiquoter automatically writes working instances for appropriate
entities, and generates TypeError
instances for records that have
0 unique keys.
Since: 2.10.0
requireUniquesP :: record -> NonEmpty (Unique record) Source #
atLeastOneUniqueDef :: (AtLeastOneUniqueKey record, Monad proxy) => proxy record -> NonEmpty UniqueDef Source #
Given a proxy for a record that has an instance of
AtLeastOneUniqueKey
, this returns a NonEmpty
list of the
UniqueDef
s for that entity.
Since: 2.10.0
type NoUniqueKeysError ty = (('Text "The entity " :<>: 'ShowType ty) :<>: 'Text " does not have any unique keys.") :$$: ('Text "The function you are trying to call requires a unique key " :<>: 'Text "to be defined on the entity.") Source #
This is an error message. It is used when writing instances of
OnlyOneUniqueKey
for an entity that has no unique keys.
Since: 2.10.0
type MultipleUniqueKeysError ty = ((('Text "The entity " :<>: 'ShowType ty) :<>: 'Text " has multiple unique keys.") :$$: ('Text "The function you are trying to call requires only a single " :<>: 'Text "unique key.")) :$$: (('Text "There is probably a variant of the function with 'By' " :<>: 'Text "appended that will allow you to select a unique key ") :<>: 'Text "for the operation.") Source #
This is an error message. It is used when an entity has multiple unique keys, and the function expects a single unique key.
Since: 2.10.0
getByValue :: forall record m backend. (MonadIO m, PersistUniqueRead backend, PersistRecordBackend record backend, AtLeastOneUniqueKey record) => record -> ReaderT backend m (Maybe (Entity record)) Source #
A modification of getBy
, which takes the PersistEntity
itself instead
of a Unique
record. Returns a record matching one of the unique keys. This
function makes the most sense on entities with a single Unique
constructor.
Example usage
getByValueUniques :: forall record backend m. (MonadIO m, PersistUniqueRead backend, PersistRecordBackend record backend) => [Unique record] -> ReaderT backend m (Maybe (Entity record)) Source #
insertBy :: forall record backend m. (MonadIO m, PersistUniqueWrite backend, PersistRecordBackend record backend, AtLeastOneUniqueKey record) => record -> ReaderT backend m (Either (Entity record) (Key record)) Source #
Insert a value, checking for conflicts with any unique constraints. If a
duplicate exists in the database, it is returned as Left
. Otherwise, the
new 'Key is returned as Right
.
Example usage
With schema-2 and dataset-1, we have following lines of code:
l1 <- insertBy $ User "SPJ" 20 l2 <- insertBy $ User "XXX" 41 l3 <- insertBy $ User "SPJ" 40 r1 <- insertBy $ User "XXX" 100
First three lines return Left
because there're duplicates in given record's uniqueness constraints. While the last line returns a new key as Right
.
insertUniqueEntity :: forall record backend m. (MonadIO m, PersistRecordBackend record backend, PersistUniqueWrite backend) => record -> ReaderT backend m (Maybe (Entity record)) Source #
Like insertEntity
, but returns Nothing
when the record
couldn't be inserted because of a uniqueness constraint.
Example usage
We use schema-2 and dataset-1 here.
insertUniqueSpjEntity :: MonadIO m => ReaderT SqlBackend m (Maybe (Entity User)) insertUniqueSpjEntity = insertUniqueEntity $ User "SPJ" 50
mSpjEnt <- insertUniqueSpjEntity
The above query results Nothing
as SPJ already exists.
insertUniqueAlexaEntity :: MonadIO m => ReaderT SqlBackend m (Maybe (Entity User)) insertUniqueAlexaEntity = insertUniqueEntity $ User "Alexa" 3
mAlexaEnt <- insertUniqueSpjEntity
Because there's no such unique keywords of the given record, the above query when applied on dataset-1, will produce this:
+----+-------+-----+ | id | name | age | +----+-------+-----+ | 1 | SPJ | 40 | +----+-------+-----+ | 2 | Simon | 41 | +----+-------+-----+ | 3 | Alexa | 3 | +----+-------+-----+
Since: 2.7.1
replaceUnique :: forall record backend m. (MonadIO m, Eq (Unique record), PersistRecordBackend record backend, PersistUniqueWrite backend) => Key record -> record -> ReaderT backend m (Maybe (Unique record)) Source #
checkUnique :: forall record backend m. (MonadIO m, PersistRecordBackend record backend, PersistUniqueRead backend) => record -> ReaderT backend m (Maybe (Unique record)) Source #
Check whether there are any conflicts for unique keys with this entity and existing entities in the database.
Returns Nothing
if the entity would be unique, and could thus safely be inserted.
on a conflict returns the conflicting key
Example usage
checkUniqueUpdateable :: forall record backend m. (MonadIO m, PersistRecordBackend record backend, PersistUniqueRead backend) => Entity record -> ReaderT backend m (Maybe (Unique record)) Source #
Check whether there are any conflicts for unique keys with this entity and existing entities in the database.
Returns Nothing
if the entity would stay unique, and could thus safely be updated.
on a conflict returns the conflicting key
This is similar to checkUnique
, except it's useful for updating - when the
particular entity already exists, it would normally conflict with itself.
This variant ignores those conflicts
Example usage
We use schema-1 and dataset-1 here.
This would be Nothing
:
mAlanConst <- checkUnique $ User "Alan" 70
While this would be Just
because SPJ already exists:
mSpjConst <- checkUnique $ User "SPJ" 60
Since: 2.11.0.0
onlyUnique :: forall record backend m. (MonadIO m, PersistUniqueWrite backend, PersistRecordBackend record backend, OnlyOneUniqueKey record) => record -> ReaderT backend m (Unique record) Source #
Return the single unique key for a record.
Example usage
We use shcema-1 and dataset-1 here.
onlySimonConst :: MonadIO m => ReaderT SqlBackend m (Unique User) onlySimonConst = onlyUnique $ User "Simon" 999
mSimonConst <- onlySimonConst
mSimonConst
would be Simon's uniqueness constraint. Note that
onlyUnique
doesn't work if there're more than two constraints. It will
fail with a type error instead.
:: (PersistEntityBackend record ~ BaseBackend backend, PersistEntity record, MonadIO m, PersistStoreWrite backend, PersistUniqueRead backend) | |
=> Unique record | uniqueness constraint to find by |
-> record | new record to insert |
-> [Update record] | updates to perform if the record already exists |
-> ReaderT backend m (Entity record) | the record in the database after the operation |
The slow but generic upsertBy
implementation for any PersistUniqueRead
.
* Lookup corresponding entities (if any) getBy
.
* If the record exists, update using updateGet
.
* If it does not exist, insert using insertEntity
.
@since 2.11
defaultPutMany :: forall record backend m. (PersistEntityBackend record ~ BaseBackend backend, PersistEntity record, MonadIO m, PersistStoreWrite backend, PersistUniqueRead backend) => [record] -> ReaderT backend m () Source #
The slow but generic putMany
implementation for any PersistUniqueRead
.
* Lookup corresponding entities (if any) for each record using getByValue
* For pre-existing records, issue a replace
for each old key and new record
* For new records, issue a bulk insertMany_
persistUniqueKeyValues :: PersistEntity record => record -> [PersistValue] Source #
This function returns a list of PersistValue
that correspond to the
Unique
keys on that record. This is useful for comparing two record
s
for equality only on the basis of their Unique
keys.