Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module exports all of the type classes in persistent
for operating
on the database backends.
persistent
offers methods that are abstract in the specific backend
type.
For SQL databases, this wil be SqlBackend
.
Other database backends will define their own types.
Methods and functions in this module have examples documented under an "Example Usage" thing, that you need to click on to expand.
Synopsis
- type PersistStore a = PersistStoreWrite a
- 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
- type PersistRecordBackend record backend = (PersistEntity record, PersistEntityBackend record ~ BaseBackend backend)
- 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)
- getEntity :: forall e backend m. (PersistStoreRead backend, PersistRecordBackend e backend, MonadIO m) => Key e -> ReaderT backend m (Maybe (Entity e))
- 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
- class SafeToInsert a
- 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
- type PersistUnique a = PersistUniqueWrite a
- 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, SafeToInsert record) => record -> ReaderT backend m (Maybe (Key record))
- insertUnique_ :: forall record m. (MonadIO m, PersistRecordBackend record backend, SafeToInsert record) => record -> ReaderT backend m (Maybe ())
- upsert :: forall record m. (MonadIO m, PersistRecordBackend record backend, OnlyOneUniqueKey record, SafeToInsert record) => record -> [Update record] -> ReaderT backend m (Entity record)
- upsertBy :: forall record m. (MonadIO m, PersistRecordBackend record backend, SafeToInsert record) => Unique record -> record -> [Update record] -> ReaderT backend m (Entity record)
- putMany :: forall record m. (MonadIO m, PersistRecordBackend record backend, SafeToInsert record) => [record] -> ReaderT backend m ()
- class PersistEntity record => OnlyOneUniqueKey record where
- onlyUniqueP :: record -> Unique record
- class PersistEntity record => AtLeastOneUniqueKey record where
- requireUniquesP :: record -> NonEmpty (Unique record)
- onlyOneUniqueDef :: (OnlyOneUniqueKey record, Monad proxy) => proxy record -> 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))
- insertBy :: forall record backend m. (MonadIO m, PersistUniqueWrite backend, PersistRecordBackend record backend, AtLeastOneUniqueKey record, SafeToInsert record) => record -> ReaderT backend m (Either (Entity record) (Key record))
- insertUniqueEntity :: forall record backend m. (MonadIO m, PersistRecordBackend record backend, PersistUniqueWrite backend, SafeToInsert record) => 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)
- selectList :: forall record backend m. (MonadIO m, PersistQueryRead backend, PersistRecordBackend record backend) => [Filter record] -> [SelectOpt record] -> ReaderT backend m [Entity record]
- selectKeys :: forall record backend m. (PersistQueryRead backend, MonadResource m, PersistRecordBackend record backend, MonadReader backend m) => [Filter record] -> [SelectOpt record] -> ConduitM () (Key record) m ()
- type PersistQuery a = PersistQueryWrite a
- class (PersistCore backend, PersistStoreRead backend) => PersistQueryRead backend where
- selectSourceRes :: (PersistRecordBackend record backend, MonadIO m1, MonadIO m2) => [Filter record] -> [SelectOpt record] -> ReaderT backend m1 (Acquire (ConduitM () (Entity record) m2 ()))
- selectFirst :: (MonadIO m, PersistRecordBackend record backend) => [Filter record] -> [SelectOpt record] -> ReaderT backend m (Maybe (Entity record))
- selectKeysRes :: (MonadIO m1, MonadIO m2, PersistRecordBackend record backend) => [Filter record] -> [SelectOpt record] -> ReaderT backend m1 (Acquire (ConduitM () (Key record) m2 ()))
- count :: (MonadIO m, PersistRecordBackend record backend) => [Filter record] -> ReaderT backend m Int
- exists :: (MonadIO m, PersistRecordBackend record backend) => [Filter record] -> ReaderT backend m Bool
- class (PersistQueryRead backend, PersistStoreWrite backend) => PersistQueryWrite backend where
- updateWhere :: (MonadIO m, PersistRecordBackend record backend) => [Filter record] -> [Update record] -> ReaderT backend m ()
- deleteWhere :: (MonadIO m, PersistRecordBackend record backend) => [Filter record] -> ReaderT backend m ()
- selectSource :: forall record backend m. (PersistQueryRead backend, MonadResource m, PersistRecordBackend record backend, MonadReader backend m) => [Filter record] -> [SelectOpt record] -> ConduitM () (Entity record) m ()
- selectKeysList :: forall record backend m. (MonadIO m, PersistQueryRead backend, PersistRecordBackend record backend) => [Filter record] -> [SelectOpt record] -> ReaderT backend m [Key record]
- class (PersistField (Key record), ToJSON (Key record), FromJSON (Key record), Show (Key record), Read (Key record), Eq (Key record), Ord (Key record)) => PersistEntity record where
- type PersistEntityBackend record
- data Key record
- data EntityField record :: Type -> Type
- data Unique record
- keyToValues :: Key record -> [PersistValue]
- keyFromValues :: [PersistValue] -> Either Text (Key record)
- persistIdField :: EntityField record (Key record)
- entityDef :: proxy record -> EntityDef
- persistFieldDef :: EntityField record typ -> FieldDef
- toPersistFields :: record -> [PersistValue]
- fromPersistValues :: [PersistValue] -> Either Text record
- tabulateEntityA :: Applicative f => (forall a. EntityField record a -> f a) -> f (Entity record)
- persistUniqueKeys :: record -> [Unique record]
- persistUniqueToFieldNames :: Unique record -> NonEmpty (FieldNameHS, FieldNameDB)
- persistUniqueToValues :: Unique record -> [PersistValue]
- fieldLens :: EntityField record field -> forall f. Functor f => (field -> f field) -> Entity record -> f (Entity record)
- keyFromRecordM :: Maybe (record -> Key record)
- tabulateEntity :: PersistEntity record => (forall a. EntityField record a -> a) -> Entity record
- class SymbolToField (sym :: Symbol) rec typ | sym rec -> typ where
- symbolToField :: EntityField rec typ
- class PersistField a where
- toPersistValue :: a -> PersistValue
- fromPersistValue :: PersistValue -> Either Text a
- class PersistConfig c where
- type PersistConfigBackend c :: (Type -> Type) -> Type -> Type
- type PersistConfigPool c
- loadConfig :: Value -> Parser c
- applyEnv :: c -> IO c
- createPoolConfig :: c -> IO (PersistConfigPool c)
- runPool :: MonadUnliftIO m => c -> PersistConfigBackend c m a -> PersistConfigPool c -> m a
- entityValues :: PersistEntity record => Entity record -> [PersistValue]
- 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
- liftPersist :: (MonadIO m, MonadReader backend m) => ReaderT backend IO b -> m b
- class BackendCompatible sup sub where
- projectBackend :: sub -> sup
- withCompatibleBackend :: BackendCompatible sup sub => ReaderT sup m a -> ReaderT sub m a
- class PersistCore backend where
- data BackendKey backend
- class (PersistEntity record, PersistEntityBackend record ~ backend, PersistCore backend) => ToBackendKey backend record where
- toBackendKey :: Key record -> BackendKey backend
- fromBackendKey :: BackendKey backend -> Key record
- keyValueEntityToJSON :: (PersistEntity record, ToJSON record) => Entity record -> Value
- keyValueEntityFromJSON :: (PersistEntity record, FromJSON record) => Value -> Parser (Entity record)
- entityIdToJSON :: (PersistEntity record, ToJSON record) => Entity record -> Value
- entityIdFromJSON :: (PersistEntity record, FromJSON record) => Value -> Parser (Entity record)
- toPersistValueJSON :: ToJSON a => a -> PersistValue
- fromPersistValueJSON :: FromJSON a => PersistValue -> Either Text a
PersistStore
The PersistStore
, PersistStoreRead
, and PersistStoreWrite
type
classes are used to define basic operations on the database. A database
that implements these classes is capable of being used as a simple
key-value store.
All the examples present here will be explained based on these schemas, datasets and functions:
schema-1
share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase| User name String age Int deriving Show |]
dataset-1
+----+-------+-----+ | id | name | age | +----+-------+-----+ | 1 | SPJ | 40 | +----+-------+-----+ | 2 | Simon | 41 | +----+-------+-----+
type PersistStore a = PersistStoreWrite a Source #
A backwards-compatible alias for those that don't care about distinguishing between read and write queries. It signifies the assumption that, by default, a backend can write as well as read.
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 #
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 #
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 Key
s.
If you don't need the inserted Key
s, 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 Key
s.
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
type PersistRecordBackend record backend = (PersistEntity record, PersistEntityBackend record ~ BaseBackend backend) Source #
A convenient alias for common type signatures
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
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 | +----+------+-----+
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.
class SafeToInsert a Source #
A type class which is used to witness that a type is safe to insert into the database without providing a primary key.
The TemplateHaskell
function mkPersist
will generate instances of this
class for any entity that it works on. If the entity has a default primary
key, then it provides a regular instance. If the entity has a Primary
natural key, then this works fine. But if the entity has an Id
column with
no default=
, then this does a TypeError
and forces the user to use
insertKey
.
Since: 2.14.0.0
Instances
(TypeError (EntityErrorMessage a) :: Constraint) => SafeToInsert (Entity a) Source # | |
Defined in Database.Persist.Class.PersistEntity | |
(TypeError (FunctionErrorMessage a b) :: Constraint) => SafeToInsert (a -> b) Source # | |
Defined in Database.Persist.Class.PersistEntity |
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
PersistUnique
The PersistUnique
type class is relevant for database backends that
offer uniqueness keys. Uniquenes keys allow us to perform operations like
getBy
, deleteBy
, as well as upsert
and putMany
.
All the examples present here will be explained based on these two schemas and the dataset:
schema-1
This schema has single unique constraint.
share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase| User name String age Int UniqueUserName name deriving Show |]
schema-2
This schema has two unique constraints.
share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase| User name String age Int UniqueUserName name UniqueUserAge age deriving Show |]
dataset-1
+-----+-----+-----+ |id |name |age | +-----+-----+-----+ |1 |SPJ |40 | +-----+-----+-----+ |2 |Simon|41 | +-----+-----+-----+
type PersistUnique a = PersistUniqueWrite a Source #
A backwards-compatible alias for those that don't care about distinguishing between read and write queries. It signifies the assumption that, by default, a backend can write as well as read.
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 | +----+------+-----+
existsBy :: forall record m. (MonadIO m, PersistRecordBackend record backend) => Unique record -> ReaderT backend m Bool Source #
Returns True if a record with this unique key exists, otherwise False.
Example usage
existsBySpjName :: MonadIO m => ReaderT SqlBackend m Bool existsBySpjName = existsBy $ UniqueUserName "SPJ"
spjEntExists <- existsBySpjName
The above query when applied on dataset-1, will return the value True.
Since: 2.14.5
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, SafeToInsert record) => 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.
insertUnique_ :: forall record m. (MonadIO m, PersistRecordBackend record backend, SafeToInsert record) => record -> ReaderT backend m (Maybe ()) Source #
Same as insertUnique
but doesn't return a Key
.
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.
Since: 2.14.5.0
:: forall record m. (MonadIO m, PersistRecordBackend record backend, OnlyOneUniqueKey record, SafeToInsert 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) updates
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, SafeToInsert record) | |
=> 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, SafeToInsert record) | |
=> [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 #
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 #
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
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
insertBy :: forall record backend m. (MonadIO m, PersistUniqueWrite backend, PersistRecordBackend record backend, AtLeastOneUniqueKey record, SafeToInsert 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, SafeToInsert record) => 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.
PersistQuery
The PersistQuery
type class allows us to select lists and filter
database models. selectList
is the canonical read operation, and we
can write updateWhere
and deleteWhere
to modify based on filters.
selectList :: forall record backend m. (MonadIO m, PersistQueryRead backend, PersistRecordBackend record backend) => [Filter record] -> [SelectOpt record] -> ReaderT backend m [Entity record] Source #
Returns a [
corresponding to the filters and options
provided.Entity
record]
Filters are constructed using the operators defined in Database.Persist (and re-exported from Database.Persist.Sql). Let's look at some examples:
usersWithAgeOver40 ::SqlPersistT
IO
[Entity
User] usersWithAgeOver40 =selectList
[UserAge>=.
40] []
If you provide multiple values in the list, the conditions are AND
ed
together.
usersWithAgeBetween30And50 ::SqlPersistT
IO
[Entity
User] usersWithAgeBetween30And50 =selectList
[ UserAge>=.
30 , UserAge<=.
50 ] []
The second list contains the SelectOpt
for a record. We can select the
first ten records with LimitTo
firstTenUsers =selectList
[] [LimitTo
10]
And we can select the second ten users with OffsetBy
.
secondTenUsers =selectList
[] [LimitTo
10,OffsetBy
10]
Warning that LIMIT/OFFSET is bad for pagination!
The type of record can usually be infered from the types of the provided filters and select options. In the previous two examples, though, you'll notice that the select options are polymorphic, applying to any record type. In order to help type inference in such situations, or simply as an enhancement to readability, you might find type application useful, illustrated below.
{-# LANGUAGE TypeApplications #-} ... firstTenUsers =selectList
User [] [
User [] [LimitTo
10] secondTenUsers =selectList
LimitTo
10,OffsetBy
10]
With Asc
and Desc
, we can provide the field we want to sort on. We can
provide multiple sort orders - later ones are used to sort records that are
equal on the first field.
newestUsers = selectList [] [Desc
UserCreatedAt,LimitTo
10] oldestUsers = selectList [] [Asc
UserCreatedAt,LimitTo
10]
selectKeys :: forall record backend m. (PersistQueryRead backend, MonadResource m, PersistRecordBackend record backend, MonadReader backend m) => [Filter record] -> [SelectOpt record] -> ConduitM () (Key record) m () Source #
Get the Key
s of all records matching the given criterion.
For an example, see selectList
.
type PersistQuery a = PersistQueryWrite a Source #
A backwards-compatible alias for those that don't care about distinguishing between read and write queries. It signifies the assumption that, by default, a backend can write as well as read.
class (PersistCore backend, PersistStoreRead backend) => PersistQueryRead backend where Source #
Backends supporting conditional read operations.
selectSourceRes :: (PersistRecordBackend record backend, MonadIO m1, MonadIO m2) => [Filter record] -> [SelectOpt record] -> ReaderT backend m1 (Acquire (ConduitM () (Entity record) m2 ())) Source #
Get all records matching the given criterion in the specified order. Returns also the identifiers.
NOTE: This function returns an Acquire
and a ConduitM
, which implies
that it streams from the database. It does not. Please use selectList
to simplify the code. If you want streaming behavior, consider
persistent-pagination
which efficiently chunks a query into ranges, or
investigate a backend-specific streaming solution.
selectFirst :: (MonadIO m, PersistRecordBackend record backend) => [Filter record] -> [SelectOpt record] -> ReaderT backend m (Maybe (Entity record)) Source #
Get just the first record for the criterion.
selectKeysRes :: (MonadIO m1, MonadIO m2, PersistRecordBackend record backend) => [Filter record] -> [SelectOpt record] -> ReaderT backend m1 (Acquire (ConduitM () (Key record) m2 ())) Source #
Get the Key
s of all records matching the given criterion.
count :: (MonadIO m, PersistRecordBackend record backend) => [Filter record] -> ReaderT backend m Int Source #
The total number of records fulfilling the given criterion.
exists :: (MonadIO m, PersistRecordBackend record backend) => [Filter record] -> ReaderT backend m Bool Source #
Check if there is at least one record fulfilling the given criterion.
Since: 2.11
Instances
class (PersistQueryRead backend, PersistStoreWrite backend) => PersistQueryWrite backend where Source #
Backends supporting conditional write operations
updateWhere :: (MonadIO m, PersistRecordBackend record backend) => [Filter record] -> [Update record] -> ReaderT backend m () Source #
Update individual fields on any record matching the given criterion.
deleteWhere :: (MonadIO m, PersistRecordBackend record backend) => [Filter record] -> ReaderT backend m () Source #
Delete all records matching the given criterion.
Instances
selectSource :: forall record backend m. (PersistQueryRead backend, MonadResource m, PersistRecordBackend record backend, MonadReader backend m) => [Filter record] -> [SelectOpt record] -> ConduitM () (Entity record) m () Source #
Get all records matching the given criterion in the specified order. Returns also the identifiers.
WARNING: This function returns a ConduitM
, which suggests that it streams
the results. It does not stream results on most backends. If you need
streaming, see persistent-pagination
for a means of chunking results based
on indexed ranges.
selectKeysList :: forall record backend m. (MonadIO m, PersistQueryRead backend, PersistRecordBackend record backend) => [Filter record] -> [SelectOpt record] -> ReaderT backend m [Key record] Source #
Call selectKeys
but return the result as a list.
PersistEntity
class (PersistField (Key record), ToJSON (Key record), FromJSON (Key record), Show (Key record), Read (Key record), Eq (Key record), Ord (Key record)) => PersistEntity record where Source #
Persistent serialized Haskell records to the database.
A Database Entity
(A row in SQL, a document in MongoDB, etc)
corresponds to a Key
plus a Haskell record.
For every Haskell record type stored in the database there is a
corresponding PersistEntity
instance. An instance of PersistEntity
contains meta-data for the record. PersistEntity also helps abstract
over different record types. That way the same query interface can return
a PersistEntity
, with each query returning different types of Haskell
records.
Some advanced type system capabilities are used to make this process type-safe. Persistent users usually don't need to understand the class associated data and functions.
keyToValues, keyFromValues, persistIdField, entityDef, persistFieldDef, toPersistFields, fromPersistValues, tabulateEntityA, persistUniqueKeys, persistUniqueToFieldNames, persistUniqueToValues, fieldLens
type PersistEntityBackend record Source #
Persistent allows multiple different backends (databases).
By default, a backend will automatically generate the key Instead you can specify a Primary key made up of unique values.
data EntityField record :: Type -> Type Source #
An EntityField
is parameterised by the Haskell record it belongs to
and the additional type of that field.
As of persistent-2.11.0.0
, it's possible to use the OverloadedLabels
language extension to refer to EntityField
values polymorphically. See
the documentation on SymbolToField
for more information.
Unique keys besides the Key
.
keyToValues :: Key record -> [PersistValue] Source #
A lower-level key operation.
keyFromValues :: [PersistValue] -> Either Text (Key record) Source #
A lower-level key operation.
persistIdField :: EntityField record (Key record) Source #
A meta-operation to retrieve the Key
EntityField
.
entityDef :: proxy record -> EntityDef Source #
Retrieve the EntityDef
meta-data for the record.
persistFieldDef :: EntityField record typ -> FieldDef Source #
Return meta-data for a given EntityField
.
toPersistFields :: record -> [PersistValue] Source #
A meta-operation to get the database fields of a record.
fromPersistValues :: [PersistValue] -> Either Text record Source #
A lower-level operation to convert from database values to a Haskell record.
:: Applicative f | |
=> (forall a. EntityField record a -> f a) | A function that builds a fragment of a record in an
|
-> f (Entity record) |
This function allows you to build an
by specifying an
action that returns a value for the field in the callback function.
Let's look at an example.Entity
a
parseFromEnvironmentVariables :: IO (Entity User) parseFromEnvironmentVariables = tabulateEntityA $ \userField -> case userField of UserName -> getEnv USER_NAME UserAge -> do ageVar <- getEnv USER_AGE case readMaybe ageVar of Just age -> pure age Nothing -> error $ "Failed to parse Age from: " <> ageVar UserAddressId -> do addressVar <- getEnv USER_ADDRESS_ID pure $ AddressKey addressVar
Since: 2.14.0.0
persistUniqueKeys :: record -> [Unique record] Source #
A meta operation to retrieve all the Unique
keys.
persistUniqueToFieldNames :: Unique record -> NonEmpty (FieldNameHS, FieldNameDB) Source #
A lower level operation.
persistUniqueToValues :: Unique record -> [PersistValue] Source #
A lower level operation.
fieldLens :: EntityField record field -> forall f. Functor f => (field -> f field) -> Entity record -> f (Entity record) Source #
Use a PersistField
as a lens.
keyFromRecordM :: Maybe (record -> Key record) Source #
Extract a
from a Key
recordrecord
value. Currently, this is
only defined for entities using the Primary
syntax for
natural/composite keys. In a future version of persistent
which
incorporates the ID directly into the entity, this will always be Just.
Since: 2.11.0.0
tabulateEntity :: PersistEntity record => (forall a. EntityField record a -> a) -> Entity record Source #
Construct an
by providing a value for each of the
record's fields.Entity
record
These constructions are equivalent:
entityMattConstructor, entityMattTabulate :: Entity User entityMattConstructor = Entity { entityKey = toSqlKey 123 , entityVal = User { userName = Matt , userAge = 33 } } entityMattTabulate = tabulateEntity $ \case UserId -> toSqlKey 123 UserName -> Matt UserAge -> 33
This is a specialization of tabulateEntityA
, which allows you to
construct an Entity
by providing an Applicative
action for each
field instead of a regular function.
Since: 2.14.0.0
class SymbolToField (sym :: Symbol) rec typ | sym rec -> typ where Source #
This type class is used with the OverloadedLabels
extension to
provide a more convenient means of using the EntityField
type.
EntityField
definitions are prefixed with the type name to avoid
ambiguity, but this ambiguity can result in verbose code.
If you have a table User
with a name Text
field, then the
corresponding EntityField
is UserName
. With this, we can write
#name ::
.EntityField
User Text
What's more fun is that the type is more general: it's actually
#name
:: (
SymbolToField
"name" rec typ)
=> EntityField rec typ
Which means it is *polymorphic* over the actual record. This allows you to write code that can be generic over the tables, provided they have the right fields.
Since: 2.11.0.0
symbolToField :: EntityField rec typ Source #
PersistField
class PersistField a where Source #
This class teaches Persistent how to take a custom type and marshal it to and from a PersistValue
, allowing it to be stored in a database.
Examples
Simple Newtype
You can use newtype
to add more type safety/readability to a basis type like ByteString
. In these cases, just derive PersistField
and PersistFieldSql
:
{-# LANGUAGE GeneralizedNewtypeDeriving #-} newtype HashedPassword = HashedPasswordByteString
deriving (Eq, Show,PersistField
, PersistFieldSql)
Smart Constructor Newtype
In this example, we create a PersistField
instance for a newtype following the "Smart Constructor" pattern.
{-# LANGUAGE GeneralizedNewtypeDeriving #-} import qualified Data.Text as T import qualified Data.Char as C -- | An American Social Security Number newtype SSN = SSNErrorMessage
deriving (Eq, Show, PersistFieldSql) mkSSN ::ErrorMessage
->Either
ErrorMessage
SSN mkSSN t = if (T.length t == 9) && (T.all C.isDigit t) thenRight
$ SSN t elseLeft
$ "Invalid SSN: " <> t instancePersistField
SSN wheretoPersistValue
(SSN t) =PersistText
tfromPersistValue
(PersistText
t) = mkSSN t -- Handle cases where the database does not give us PersistTextfromPersistValue
x =Left
$ "File.hs: When trying to deserialize an SSN: expected PersistText, received: " <> T.pack (show x)
Tips:
- This file contain dozens of
PersistField
instances you can look at for examples. - Typically custom
PersistField
instances will only accept a singlePersistValue
constructor infromPersistValue
. - Internal
PersistField
instances accept a wide variety ofPersistValue
s to accomodate e.g. storing booleans as integers, booleans or strings. - If you're making a custom instance and using a SQL database, you'll also need
PersistFieldSql
to specify the type of the database column.
toPersistValue :: a -> PersistValue Source #
fromPersistValue :: PersistValue -> Either Text a Source #
Instances
PersistConfig
class PersistConfig c where Source #
Represents a value containing all the configuration options for a specific backend. This abstraction makes it easier to write code that can easily swap backends.
type PersistConfigBackend c :: (Type -> Type) -> Type -> Type Source #
type PersistConfigPool c Source #
loadConfig :: Value -> Parser c Source #
Load the config settings from a Value
, most likely taken from a YAML
config file.
applyEnv :: c -> IO c Source #
Modify the config settings based on environment variables.
createPoolConfig :: c -> IO (PersistConfigPool c) Source #
Create a new connection pool based on the given config settings.
runPool :: MonadUnliftIO m => c -> PersistConfigBackend c m a -> PersistConfigPool c -> m a Source #
Run a database action by taking a connection from the pool.
Instances
(PersistConfig c1, PersistConfig c2, PersistConfigPool c1 ~ PersistConfigPool c2, PersistConfigBackend c1 ~ PersistConfigBackend c2) => PersistConfig (Either c1 c2) Source # | |
Defined in Database.Persist.Class.PersistConfig type PersistConfigBackend (Either c1 c2) :: (Type -> Type) -> Type -> Type Source # type PersistConfigPool (Either c1 c2) Source # loadConfig :: Value -> Parser (Either c1 c2) Source # applyEnv :: Either c1 c2 -> IO (Either c1 c2) Source # createPoolConfig :: Either c1 c2 -> IO (PersistConfigPool (Either c1 c2)) Source # runPool :: MonadUnliftIO m => Either c1 c2 -> PersistConfigBackend (Either c1 c2) m a -> PersistConfigPool (Either c1 c2) -> m a Source # |
entityValues :: PersistEntity record => Entity record -> [PersistValue] Source #
Get list of values corresponding to given entity.
Lifting
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 #
Instances
HasPersistBackend SqlReadBackend Source # | |
Defined in Database.Persist.Sql.Types.Internal type BaseBackend SqlReadBackend Source # | |
HasPersistBackend SqlWriteBackend Source # | |
HasPersistBackend SqlBackend Source # | |
Defined in Database.Persist.SqlBackend.Internal type BaseBackend SqlBackend Source # | |
(BackendCompatible b s, HasPersistBackend b) => HasPersistBackend (Compatible b s) Source # | |
Defined in Database.Persist.Compatible.Types type BaseBackend (Compatible b s) Source # 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 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
.
liftPersist :: (MonadIO m, MonadReader backend m) => ReaderT backend IO b -> m b 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 :: (PersistEntity
record ,PersistEntityBackend
record ~BaseBackend
backend ,IsSqlBackend
backend )
this can be replaced with:
foo :: (PersistEntity
record, ,PersistEntityBackend
record ~ backend ,BackendCompatible
SqlBackend
backend )
This works for SqlReadBackend
because of the instance
, without needing to go through the BackendCompatible
SqlBackend
SqlReadBackend
BaseBackend
type family.
Likewise, functions that are currently hardcoded to use SqlBackend
can be generalized:
-- before: asdf ::ReaderT
SqlBackend
m () asdf = pure () -- after: asdf' ::BackendCompatible
SqlBackend backend => ReaderT backend m () asdf' =withCompatibleBackend
asdf
Since: 2.7.1
projectBackend :: sub -> sup Source #
Instances
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
PersistCore
PersistCore
is a type class that defines a default database
BackendKey
type. For SQL databases, this is currently an
auto-incrementing inteer primary key. For MongoDB, it is the default
ObjectID.
class PersistCore backend Source #
data BackendKey backend Source #
Instances
PersistCore SqlReadBackend Source # | |
Defined in Database.Persist.Sql.Orphan.PersistStore data BackendKey SqlReadBackend Source # | |
PersistCore SqlWriteBackend Source # | |
Defined in Database.Persist.Sql.Orphan.PersistStore data BackendKey SqlWriteBackend Source # | |
PersistCore SqlBackend Source # | |
Defined in Database.Persist.Sql.Orphan.PersistStore data BackendKey SqlBackend Source # | |
(BackendCompatible b s, PersistCore b) => PersistCore (Compatible b s) Source # | |
Defined in Database.Persist.Compatible.Types data BackendKey (Compatible b s) Source # |
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
.
toBackendKey :: Key record -> BackendKey backend Source #
fromBackendKey :: BackendKey backend -> Key record Source #
JSON utilities
keyValueEntityToJSON :: (PersistEntity record, ToJSON record) => Entity record -> Value Source #
Predefined toJSON
. The resulting JSON looks like
{"key": 1, "value": {"name": ...}}
.
The typical usage is:
instance ToJSON (Entity User) where toJSON = keyValueEntityToJSON
keyValueEntityFromJSON :: (PersistEntity record, FromJSON record) => Value -> Parser (Entity record) Source #
Predefined parseJSON
. The input JSON looks like
{"key": 1, "value": {"name": ...}}
.
The typical usage is:
instance FromJSON (Entity User) where parseJSON = keyValueEntityFromJSON
entityIdToJSON :: (PersistEntity record, ToJSON record) => Entity record -> Value Source #
Predefined toJSON
. The resulting JSON looks like
{"id": 1, "name": ...}
.
The typical usage is:
instance ToJSON (Entity User) where toJSON = entityIdToJSON
entityIdFromJSON :: (PersistEntity record, FromJSON record) => Value -> Parser (Entity record) Source #
Predefined parseJSON
. The input JSON looks like
{"id": 1, "name": ...}
.
The typical usage is:
instance FromJSON (Entity User) where parseJSON = entityIdFromJSON
toPersistValueJSON :: ToJSON a => a -> PersistValue Source #
Convenience function for getting a free PersistField
instance
from a type with JSON instances.
Example usage in combination with fromPersistValueJSON
:
instance PersistField MyData where fromPersistValue = fromPersistValueJSON toPersistValue = toPersistValueJSON
fromPersistValueJSON :: FromJSON a => PersistValue -> Either Text a Source #
Convenience function for getting a free PersistField
instance
from a type with JSON instances. The JSON parser used will accept JSON
values other that object and arrays. So, if your instance serializes the
data to a JSON string, this will still work.
Example usage in combination with toPersistValueJSON
:
instance PersistField MyData where fromPersistValue = fromPersistValueJSON toPersistValue = toPersistValueJSON