Safe Haskell | None |
---|---|
Language | Haskell98 |
- class (PersistEntity record, PersistEntityBackend record ~ backend, PersistCore backend) => ToBackendKey backend record where
- class PersistCore backend where
- data BackendKey backend
- 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
- type PersistRecordBackend record backend = (PersistEntity record, PersistEntityBackend record ~ BaseBackend backend)
- getJust :: (PersistStoreRead backend, Show (Key record), PersistRecordBackend record backend, MonadIO m) => Key record -> ReaderT backend m record
- getJustEntity :: (PersistEntityBackend record ~ BaseBackend backend, MonadIO m, PersistEntity record, PersistStoreRead backend) => Key record -> ReaderT backend m (Entity record)
- getEntity :: (PersistStoreRead backend, PersistRecordBackend e backend, MonadIO m) => Key e -> ReaderT backend m (Maybe (Entity e))
- belongsTo :: (PersistStoreRead backend, PersistEntity ent1, PersistRecordBackend ent2 backend, MonadIO m) => (ent1 -> Maybe (Key ent2)) -> ent1 -> ReaderT backend m (Maybe ent2)
- belongsToJust :: (PersistStoreRead backend, PersistEntity ent1, PersistRecordBackend ent2 backend, MonadIO m) => (ent1 -> Key ent2) -> ent1 -> ReaderT backend m ent2
- insertEntity :: (PersistStoreWrite backend, PersistRecordBackend e backend, MonadIO m) => e -> ReaderT backend m (Entity e)
- insertRecord :: (PersistEntityBackend record ~ BaseBackend backend, PersistEntity record, MonadIO m, PersistStoreWrite backend) => record -> ReaderT backend m record
- type PersistUnique a = PersistUniqueWrite a
- class (PersistCore backend, PersistStoreRead backend) => PersistUniqueRead backend where
- class (PersistUniqueRead backend, PersistStoreWrite backend) => PersistUniqueWrite backend where
- getByValue :: (MonadIO m, PersistUniqueRead backend, PersistRecordBackend record backend) => record -> ReaderT backend m (Maybe (Entity record))
- insertBy :: (MonadIO m, PersistUniqueWrite backend, PersistRecordBackend record backend) => record -> ReaderT backend m (Either (Entity record) (Key record))
- insertUniqueEntity :: (MonadIO m, PersistRecordBackend record backend, PersistUniqueWrite backend) => record -> ReaderT backend m (Maybe (Entity record))
- replaceUnique :: (MonadIO m, Eq record, Eq (Unique record), PersistRecordBackend record backend, PersistUniqueWrite backend) => Key record -> record -> ReaderT backend m (Maybe (Unique record))
- checkUnique :: (MonadIO m, PersistRecordBackend record backend, PersistUniqueRead backend) => record -> ReaderT backend m (Maybe (Unique record))
- onlyUnique :: (MonadIO m, PersistUniqueWrite backend, PersistRecordBackend record backend) => record -> ReaderT backend m (Unique record)
- type PersistQuery a = PersistQueryWrite a
- class (PersistCore backend, PersistStoreRead backend) => PersistQueryRead backend where
- class (PersistQueryRead backend, PersistStoreWrite backend) => PersistQueryWrite backend where
- selectSource :: (PersistQueryRead (BaseBackend backend), MonadResource m, PersistEntity record, PersistEntityBackend record ~ BaseBackend (BaseBackend backend), MonadReader backend m, HasPersistBackend backend) => [Filter record] -> [SelectOpt record] -> ConduitM () (Entity record) m ()
- selectKeys :: (PersistQueryRead (BaseBackend backend), MonadResource m, PersistEntity record, BaseBackend (BaseBackend backend) ~ PersistEntityBackend record, MonadReader backend m, HasPersistBackend backend) => [Filter record] -> [SelectOpt record] -> ConduitM () (Key record) m ()
- selectList :: (MonadIO m, PersistQueryRead backend, PersistRecordBackend record backend) => [Filter record] -> [SelectOpt record] -> ReaderT backend m [Entity record]
- selectKeysList :: (MonadIO m, PersistQueryRead backend, PersistRecordBackend record backend) => [Filter record] -> [SelectOpt record] -> ReaderT backend m [Key record]
- class (PersistStoreWrite backend, PersistEntity record, BaseBackend backend ~ PersistEntityBackend record) => DeleteCascade record backend where
- deleteCascadeWhere :: (MonadIO m, DeleteCascade record backend, PersistQueryWrite backend) => [Filter record] -> ReaderT backend m ()
- 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 :: * -> *
- data Unique record
- class PersistField a where
- class PersistConfig c where
- type PersistConfigBackend c :: (* -> *) -> * -> *
- type PersistConfigPool c
- entityValues :: PersistEntity record => Entity record -> [PersistValue]
- class HasPersistBackend backend where
- type BaseBackend backend
- class HasPersistBackend backend => IsPersistBackend backend
- liftPersist :: (MonadIO m, MonadReader backend m, HasPersistBackend backend) => ReaderT (BaseBackend backend) IO b -> m b
- class BackendCompatible sup sub where
- keyValueEntityToJSON :: (PersistEntity record, ToJSON record, ToJSON (Key record)) => Entity record -> Value
- keyValueEntityFromJSON :: (PersistEntity record, FromJSON record, FromJSON (Key record)) => Value -> Parser (Entity record)
- entityIdToJSON :: (PersistEntity record, ToJSON record, ToJSON (Key record)) => Entity record -> Value
- entityIdFromJSON :: (PersistEntity record, FromJSON record, FromJSON (Key record)) => Value -> Parser (Entity record)
- toPersistValueJSON :: ToJSON a => a -> PersistValue
- fromPersistValueJSON :: FromJSON a => PersistValue -> Either Text a
Documentation
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 #
PersistStore
class PersistCore backend Source #
data BackendKey backend Source #
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 :: (MonadIO m, PersistRecordBackend record backend) => Key record -> ReaderT backend m (Maybe record) Source #
Get a record by identifier, if available.
getMany :: (MonadIO m, PersistRecordBackend record backend) => [Key record] -> ReaderT backend m (Map (Key record) record) Source #
Get many records by their respective identifiers, if available.
Since: 2.8.1
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 :: (MonadIO m, PersistRecordBackend record backend) => 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).
insert_ :: (MonadIO m, PersistRecordBackend record backend) => record -> ReaderT backend m () Source #
Same as insert
, but doesn't return a Key
.
insertMany :: (MonadIO m, PersistRecordBackend record backend) => [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
.
insertMany_ :: (MonadIO m, PersistRecordBackend record backend) => [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.
insertEntityMany :: (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.
insertKey :: (MonadIO m, PersistRecordBackend record backend) => Key record -> record -> ReaderT backend m () Source #
Create a new record in the database using the given key.
repsert :: (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.
repsertMany :: (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.
Differs from insertEntityMany
by gracefully skipping
pre-existing records matching key(s).
@since 2.8.1
replace :: (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.
delete :: (MonadIO m, PersistRecordBackend record backend) => Key record -> ReaderT backend m () Source #
Delete a specific record by identifier. Does nothing if record does not exist.
update :: (MonadIO m, PersistRecordBackend record backend) => Key record -> [Update record] -> ReaderT backend m () Source #
Update individual fields on a specific record.
updateGet :: (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.
type PersistRecordBackend record backend = (PersistEntity record, PersistEntityBackend record ~ BaseBackend backend) Source #
A convenient alias for common type signatures
getJust :: (PersistStoreRead backend, Show (Key record), 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.
getJustEntity :: (PersistEntityBackend record ~ BaseBackend backend, MonadIO m, PersistEntity record, PersistStoreRead backend) => Key record -> ReaderT backend m (Entity record) Source #
getEntity :: (PersistStoreRead backend, PersistRecordBackend e backend, MonadIO m) => Key e -> ReaderT backend m (Maybe (Entity e)) Source #
Like get
, but returns the complete Entity
.
belongsTo :: (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 :: (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 :: (PersistStoreWrite backend, PersistRecordBackend e backend, MonadIO m) => e -> ReaderT backend m (Entity e) Source #
Like insert
, but returns the complete Entity
.
insertRecord :: (PersistEntityBackend record ~ BaseBackend backend, PersistEntity record, MonadIO m, PersistStoreWrite backend) => record -> ReaderT backend m record Source #
Like insertEntity
but just returns the record instead of Entity
.
Since: 2.6.1
PersistUnique
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 (PersistCore backend, 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.
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 :: (MonadIO m, PersistRecordBackend record backend) => Unique record -> ReaderT backend m () Source #
Delete a specific record by unique key. Does nothing if no record matches.
insertUnique :: (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.
:: (MonadIO m, PersistRecordBackend record backend) | |
=> record | new record to insert |
-> [Update record] | updates to perform if the record already exists (leaving
this empty is the equivalent of performing a |
-> 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.
Throws an exception if there is more than 1 uniqueness constraint.
:: (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 (leaving
this empty is the equivalent of performing a |
-> 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.
:: (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
getByValue :: (MonadIO m, PersistUniqueRead backend, PersistRecordBackend record backend) => 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.
insertBy :: (MonadIO m, PersistUniqueWrite backend, PersistRecordBackend record backend) => record -> ReaderT backend m (Either (Entity record) (Key record)) Source #
insertUniqueEntity :: (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.
Since: 2.7.1
replaceUnique :: (MonadIO m, Eq record, Eq (Unique record), PersistRecordBackend record backend, PersistUniqueWrite backend) => Key record -> record -> ReaderT backend m (Maybe (Unique record)) Source #
checkUnique :: (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
onlyUnique :: (MonadIO m, PersistUniqueWrite backend, PersistRecordBackend record backend) => record -> ReaderT backend m (Unique record) Source #
Return the single unique key for a record.
PersistQuery
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.
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.
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.
selectSource :: (PersistQueryRead (BaseBackend backend), MonadResource m, PersistEntity record, PersistEntityBackend record ~ BaseBackend (BaseBackend backend), MonadReader backend m, HasPersistBackend backend) => [Filter record] -> [SelectOpt record] -> ConduitM () (Entity record) m () Source #
Get all records matching the given criterion in the specified order. Returns also the identifiers.
selectKeys :: (PersistQueryRead (BaseBackend backend), MonadResource m, PersistEntity record, BaseBackend (BaseBackend backend) ~ PersistEntityBackend record, MonadReader backend m, HasPersistBackend backend) => [Filter record] -> [SelectOpt record] -> ConduitM () (Key record) m () Source #
Get the Key
s of all records matching the given criterion.
selectList :: (MonadIO m, PersistQueryRead backend, PersistRecordBackend record backend) => [Filter record] -> [SelectOpt record] -> ReaderT backend m [Entity record] Source #
Call selectSource
but return the result as a list.
selectKeysList :: (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.
DeleteCascade
class (PersistStoreWrite backend, PersistEntity record, BaseBackend backend ~ PersistEntityBackend record) => DeleteCascade record backend where Source #
For combinations of backends and entities that support cascade-deletion. “Cascade-deletion” means that entries that depend on other entries to be deleted will be deleted as well.
deleteCascadeWhere :: (MonadIO m, DeleteCascade record backend, PersistQueryWrite backend) => [Filter record] -> ReaderT backend m () Source #
Cascade-deletion of entries satisfying given filters.
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, 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 :: * -> * Source #
An EntityField
is parameterised by the Haskell record it belongs to
and the additional type of that field.
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 :: Monad m => m 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 -> [SomePersistField] 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.
persistUniqueKeys :: record -> [Unique record] Source #
A meta operation to retrieve all the Unique
keys.
persistUniqueToFieldNames :: Unique record -> [(HaskellName, DBName)] 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.
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 = SSNText
deriving (Eq, Show, PersistFieldSql) mkSSN ::Text
->Either
Text
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 #
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 :: (* -> *) -> * -> * 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.
(PersistConfig c1, PersistConfig c2, (~) * (PersistConfigPool c1) (PersistConfigPool c2), (~) ((* -> *) -> * -> *) (PersistConfigBackend c1) (PersistConfigBackend c2)) => PersistConfig (Either c1 c2) 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 #
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, HasPersistBackend backend) => ReaderT (BaseBackend 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 ,PeristEntityBackend
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' = withReaderTprojectBackend
asdf
Since: 2.7.1
projectBackend :: sub -> sup Source #
JSON utilities
keyValueEntityToJSON :: (PersistEntity record, ToJSON record, ToJSON (Key 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, FromJSON (Key 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, ToJSON (Key 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, FromJSON (Key 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