Safe Haskell | None |
---|---|
Language | Haskell98 |
- class (PersistEntity record, PersistEntityBackend record ~ backend, PersistStore backend) => ToBackendKey backend record where
- toBackendKey :: Key record -> BackendKey backend
- fromBackendKey :: BackendKey backend -> Key record
- class (Show (BackendKey backend), Read (BackendKey backend), Eq (BackendKey backend), Ord (BackendKey backend), PersistField (BackendKey backend), ToJSON (BackendKey backend), FromJSON (BackendKey backend)) => PersistStore backend where
- data BackendKey backend
- get :: (MonadIO m, backend ~ PersistEntityBackend val, PersistEntity val) => Key val -> ReaderT backend m (Maybe val)
- insert :: (MonadIO m, backend ~ PersistEntityBackend val, PersistEntity val) => val -> ReaderT backend m (Key val)
- insert_ :: (MonadIO m, backend ~ PersistEntityBackend val, PersistEntity val) => val -> ReaderT backend m ()
- insertMany :: (MonadIO m, backend ~ PersistEntityBackend val, PersistEntity val) => [val] -> ReaderT backend m [Key val]
- insertMany_ :: (MonadIO m, backend ~ PersistEntityBackend val, PersistEntity val) => [val] -> ReaderT backend m ()
- insertEntityMany :: (MonadIO m, backend ~ PersistEntityBackend val, PersistEntity val) => [Entity val] -> ReaderT backend m ()
- insertKey :: (MonadIO m, backend ~ PersistEntityBackend val, PersistEntity val) => Key val -> val -> ReaderT backend m ()
- repsert :: (MonadIO m, backend ~ PersistEntityBackend val, PersistEntity val) => Key val -> val -> ReaderT backend m ()
- replace :: (MonadIO m, backend ~ PersistEntityBackend val, PersistEntity val) => Key val -> val -> ReaderT backend m ()
- delete :: (MonadIO m, backend ~ PersistEntityBackend val, PersistEntity val) => Key val -> ReaderT backend m ()
- update :: (MonadIO m, PersistEntity val, backend ~ PersistEntityBackend val) => Key val -> [Update val] -> ReaderT backend m ()
- updateGet :: (MonadIO m, PersistEntity val, backend ~ PersistEntityBackend val) => Key val -> [Update val] -> ReaderT backend m val
- getJust :: (PersistStore backend, PersistEntity val, Show (Key val), backend ~ PersistEntityBackend val, MonadIO m) => Key val -> ReaderT backend m val
- belongsTo :: (PersistStore backend, PersistEntity ent1, PersistEntity ent2, backend ~ PersistEntityBackend ent2, MonadIO m) => (ent1 -> Maybe (Key ent2)) -> ent1 -> ReaderT backend m (Maybe ent2)
- belongsToJust :: (PersistStore backend, PersistEntity ent1, PersistEntity ent2, backend ~ PersistEntityBackend ent2, MonadIO m) => (ent1 -> Key ent2) -> ent1 -> ReaderT backend m ent2
- insertEntity :: (PersistStore backend, PersistEntity e, backend ~ PersistEntityBackend e, MonadIO m) => e -> ReaderT backend m (Entity e)
- class PersistStore backend => PersistUnique backend where
- getBy :: (MonadIO m, backend ~ PersistEntityBackend val, PersistEntity val) => Unique val -> ReaderT backend m (Maybe (Entity val))
- deleteBy :: (MonadIO m, PersistEntityBackend val ~ backend, PersistEntity val) => Unique val -> ReaderT backend m ()
- insertUnique :: (MonadIO m, PersistEntityBackend val ~ backend, PersistEntity val) => val -> ReaderT backend m (Maybe (Key val))
- upsert :: (MonadIO m, PersistEntityBackend val ~ backend, PersistEntity val) => val -> [Update val] -> ReaderT backend m (Entity val)
- getByValue :: (MonadIO m, PersistEntity record, PersistUnique backend, PersistEntityBackend record ~ backend) => record -> ReaderT backend m (Maybe (Entity record))
- insertBy :: (MonadIO m, PersistEntity val, PersistUnique backend, PersistEntityBackend val ~ backend) => val -> ReaderT backend m (Either (Entity val) (Key val))
- replaceUnique :: (MonadIO m, Eq record, Eq (Unique record), PersistEntityBackend record ~ backend, PersistEntity record, PersistUnique backend) => Key record -> record -> ReaderT backend m (Maybe (Unique record))
- checkUnique :: (MonadIO m, PersistEntityBackend record ~ backend, PersistEntity record, PersistUnique backend) => record -> ReaderT backend m (Maybe (Unique record))
- onlyUnique :: (MonadIO m, PersistEntity val, PersistUnique backend, PersistEntityBackend val ~ backend) => val -> ReaderT backend m (Unique val)
- class PersistStore backend => PersistQuery backend where
- updateWhere :: (MonadIO m, PersistEntity val, backend ~ PersistEntityBackend val) => [Filter val] -> [Update val] -> ReaderT backend m ()
- deleteWhere :: (MonadIO m, PersistEntity val, backend ~ PersistEntityBackend val) => [Filter val] -> ReaderT backend m ()
- selectSourceRes :: (PersistEntity val, PersistEntityBackend val ~ backend, MonadIO m1, MonadIO m2) => [Filter val] -> [SelectOpt val] -> ReaderT backend m1 (Acquire (Source m2 (Entity val)))
- selectFirst :: (MonadIO m, PersistEntity val, backend ~ PersistEntityBackend val) => [Filter val] -> [SelectOpt val] -> ReaderT backend m (Maybe (Entity val))
- selectKeysRes :: (MonadIO m1, MonadIO m2, PersistEntity val, backend ~ PersistEntityBackend val) => [Filter val] -> [SelectOpt val] -> ReaderT backend m1 (Acquire (Source m2 (Key val)))
- count :: (MonadIO m, PersistEntity val, backend ~ PersistEntityBackend val) => [Filter val] -> ReaderT backend m Int
- selectSource :: (PersistQuery backend, MonadResource m, PersistEntity val, PersistEntityBackend val ~ backend, MonadReader env m, HasPersistBackend env backend) => [Filter val] -> [SelectOpt val] -> Source m (Entity val)
- selectKeys :: (PersistQuery backend, MonadResource m, PersistEntity val, backend ~ PersistEntityBackend val, MonadReader env m, HasPersistBackend env backend) => [Filter val] -> [SelectOpt val] -> Source m (Key val)
- selectList :: (MonadIO m, PersistEntity val, PersistQuery backend, PersistEntityBackend val ~ backend) => [Filter val] -> [SelectOpt val] -> ReaderT backend m [Entity val]
- selectKeysList :: (MonadIO m, PersistEntity val, PersistQuery backend, PersistEntityBackend val ~ backend) => [Filter val] -> [SelectOpt val] -> ReaderT backend m [Key val]
- class (PersistStore backend, PersistEntity record, backend ~ PersistEntityBackend record) => DeleteCascade record backend where
- deleteCascade :: MonadIO m => Key record -> ReaderT backend m ()
- deleteCascadeWhere :: (MonadIO m, DeleteCascade record backend, PersistQuery 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
- keyToValues :: Key record -> [PersistValue]
- keyFromValues :: [PersistValue] -> Either Text (Key record)
- persistIdField :: EntityField record (Key record)
- entityDef :: Monad m => m record -> EntityDef
- persistFieldDef :: EntityField record typ -> FieldDef
- toPersistFields :: record -> [SomePersistField]
- fromPersistValues :: [PersistValue] -> Either Text record
- persistUniqueKeys :: record -> [Unique record]
- persistUniqueToFieldNames :: Unique record -> [(HaskellName, DBName)]
- persistUniqueToValues :: Unique record -> [PersistValue]
- fieldLens :: EntityField record field -> forall f. Functor f => (field -> f field) -> Entity record -> f (Entity record)
- class PersistField a where
- toPersistValue :: a -> PersistValue
- fromPersistValue :: PersistValue -> Either Text a
- class PersistConfig c where
- type PersistConfigBackend c :: (* -> *) -> * -> *
- type PersistConfigPool c
- loadConfig :: Value -> Parser c
- applyEnv :: c -> IO c
- createPoolConfig :: c -> IO (PersistConfigPool c)
- runPool :: (MonadBaseControl IO m, MonadIO m) => c -> PersistConfigBackend c m a -> PersistConfigPool c -> m a
- entityValues :: PersistEntity record => Entity record -> [PersistValue]
- class HasPersistBackend env backend | env -> backend where
- persistBackend :: env -> backend
- liftPersist :: (MonadReader env m, HasPersistBackend env backend, MonadIO m) => ReaderT backend IO a -> m a
- 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, PersistStore 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 (Show (BackendKey backend), Read (BackendKey backend), Eq (BackendKey backend), Ord (BackendKey backend), PersistField (BackendKey backend), ToJSON (BackendKey backend), FromJSON (BackendKey backend)) => PersistStore backend where Source
data BackendKey backend Source
get :: (MonadIO m, backend ~ PersistEntityBackend val, PersistEntity val) => Key val -> ReaderT backend m (Maybe val) Source
Get a record by identifier, if available.
insert :: (MonadIO m, backend ~ PersistEntityBackend val, PersistEntity val) => val -> ReaderT backend m (Key val) Source
Create a new record in the database, returning an automatically created key (in SQL an auto-increment id).
insert_ :: (MonadIO m, backend ~ PersistEntityBackend val, PersistEntity val) => val -> ReaderT backend m () Source
Same as insert
, but doesn't return a Key
.
insertMany :: (MonadIO m, backend ~ PersistEntityBackend val, PersistEntity val) => [val] -> ReaderT backend m [Key val] 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, backend ~ PersistEntityBackend val, PersistEntity val) => [val] -> 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, backend ~ PersistEntityBackend val, PersistEntity val) => [Entity val] -> 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 backend inserts all the entities in one database query.
The SQL backends use the slow, default implementation of
mapM_ insertKey
.
insertKey :: (MonadIO m, backend ~ PersistEntityBackend val, PersistEntity val) => Key val -> val -> ReaderT backend m () Source
Create a new record in the database using the given key.
repsert :: (MonadIO m, backend ~ PersistEntityBackend val, PersistEntity val) => Key val -> val -> 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.
replace :: (MonadIO m, backend ~ PersistEntityBackend val, PersistEntity val) => Key val -> val -> 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, backend ~ PersistEntityBackend val, PersistEntity val) => Key val -> ReaderT backend m () Source
Delete a specific record by identifier. Does nothing if record does not exist.
update :: (MonadIO m, PersistEntity val, backend ~ PersistEntityBackend val) => Key val -> [Update val] -> ReaderT backend m () Source
Update individual fields on a specific record.
updateGet :: (MonadIO m, PersistEntity val, backend ~ PersistEntityBackend val) => Key val -> [Update val] -> ReaderT backend m val 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.
getJust :: (PersistStore backend, PersistEntity val, Show (Key val), backend ~ PersistEntityBackend val, MonadIO m) => Key val -> ReaderT backend m val 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
belongsTo :: (PersistStore backend, PersistEntity ent1, PersistEntity ent2, backend ~ PersistEntityBackend ent2, 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 foerignId
belongsToJust :: (PersistStore backend, PersistEntity ent1, PersistEntity ent2, backend ~ PersistEntityBackend ent2, MonadIO m) => (ent1 -> Key ent2) -> ent1 -> ReaderT backend m ent2 Source
same as belongsTo, but uses getJust
and therefore is similarly unsafe
insertEntity :: (PersistStore backend, PersistEntity e, backend ~ PersistEntityBackend e, MonadIO m) => e -> ReaderT backend m (Entity e) Source
like insert
, but returns the complete Entity
PersistUnique
class PersistStore backend => PersistUnique 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.
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
getBy :: (MonadIO m, backend ~ PersistEntityBackend val, PersistEntity val) => Unique val -> ReaderT backend m (Maybe (Entity val)) Source
Get a record by unique key, if available. Returns also the identifier.
deleteBy :: (MonadIO m, PersistEntityBackend val ~ backend, PersistEntity val) => Unique val -> ReaderT backend m () Source
Delete a specific record by unique key. Does nothing if no record matches.
insertUnique :: (MonadIO m, PersistEntityBackend val ~ backend, PersistEntity val) => val -> ReaderT backend m (Maybe (Key val)) Source
Like insert
, but returns Nothing
when the record
couldn't be inserted because of a uniqueness constraint.
:: (MonadIO m, PersistEntityBackend val ~ backend, PersistEntity val) | |
=> val | new record to insert |
-> [Update val] | updates to perform if the record already exists.
leaving this empty is the equivalent of performing a |
-> ReaderT backend m (Entity val) | the record in the database after the operation |
update based on a uniquness constraint or insert
insert the new record if it does not exist update the existing record that matches the uniqueness contraint
Throws an exception if there is more than 1 uniqueness contraint
getByValue :: (MonadIO m, PersistEntity record, PersistUnique backend, PersistEntityBackend 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, PersistEntity val, PersistUnique backend, PersistEntityBackend val ~ backend) => val -> ReaderT backend m (Either (Entity val) (Key val)) Source
replaceUnique :: (MonadIO m, Eq record, Eq (Unique record), PersistEntityBackend record ~ backend, PersistEntity record, PersistUnique backend) => Key record -> record -> ReaderT backend m (Maybe (Unique record)) Source
checkUnique :: (MonadIO m, PersistEntityBackend record ~ backend, PersistEntity record, PersistUnique 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, PersistEntity val, PersistUnique backend, PersistEntityBackend val ~ backend) => val -> ReaderT backend m (Unique val) Source
Return the single unique key for a record
PersistQuery
class PersistStore backend => PersistQuery backend where Source
updateWhere :: (MonadIO m, PersistEntity val, backend ~ PersistEntityBackend val) => [Filter val] -> [Update val] -> ReaderT backend m () Source
Update individual fields on any record matching the given criterion.
deleteWhere :: (MonadIO m, PersistEntity val, backend ~ PersistEntityBackend val) => [Filter val] -> ReaderT backend m () Source
Delete all records matching the given criterion.
selectSourceRes :: (PersistEntity val, PersistEntityBackend val ~ backend, MonadIO m1, MonadIO m2) => [Filter val] -> [SelectOpt val] -> ReaderT backend m1 (Acquire (Source m2 (Entity val))) Source
Get all records matching the given criterion in the specified order. Returns also the identifiers.
selectFirst :: (MonadIO m, PersistEntity val, backend ~ PersistEntityBackend val) => [Filter val] -> [SelectOpt val] -> ReaderT backend m (Maybe (Entity val)) Source
get just the first record for the criterion
selectKeysRes :: (MonadIO m1, MonadIO m2, PersistEntity val, backend ~ PersistEntityBackend val) => [Filter val] -> [SelectOpt val] -> ReaderT backend m1 (Acquire (Source m2 (Key val))) Source
Get the Key
s of all records matching the given criterion.
count :: (MonadIO m, PersistEntity val, backend ~ PersistEntityBackend val) => [Filter val] -> ReaderT backend m Int Source
The total number of records fulfilling the given criterion.
selectSource :: (PersistQuery backend, MonadResource m, PersistEntity val, PersistEntityBackend val ~ backend, MonadReader env m, HasPersistBackend env backend) => [Filter val] -> [SelectOpt val] -> Source m (Entity val) Source
Get all records matching the given criterion in the specified order. Returns also the identifiers.
selectKeys :: (PersistQuery backend, MonadResource m, PersistEntity val, backend ~ PersistEntityBackend val, MonadReader env m, HasPersistBackend env backend) => [Filter val] -> [SelectOpt val] -> Source m (Key val) Source
Get the Key
s of all records matching the given criterion.
selectList :: (MonadIO m, PersistEntity val, PersistQuery backend, PersistEntityBackend val ~ backend) => [Filter val] -> [SelectOpt val] -> ReaderT backend m [Entity val] Source
Call selectSource
but return the result as a list.
selectKeysList :: (MonadIO m, PersistEntity val, PersistQuery backend, PersistEntityBackend val ~ backend) => [Filter val] -> [SelectOpt val] -> ReaderT backend m [Key val] Source
Call selectKeys
but return the result as a list.
DeleteCascade
class (PersistStore backend, PersistEntity record, backend ~ PersistEntityBackend record) => DeleteCascade record backend where Source
deleteCascade :: MonadIO m => Key record -> ReaderT backend m () Source
deleteCascadeWhere :: (MonadIO m, DeleteCascade record backend, PersistQuery backend) => [Filter record] -> ReaderT backend m () Source
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.
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
A value which can be marshalled to and from a PersistValue
.
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.
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 :: (MonadBaseControl IO m, MonadIO 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
Lifting
class HasPersistBackend env backend | env -> backend where Source
persistBackend :: env -> backend Source
liftPersist :: (MonadReader env m, HasPersistBackend env backend, MonadIO m) => ReaderT backend IO a -> m a 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 withfromPersistValueJSON
:
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 withtoPersistValueJSON
:
instance PersistField MyData where fromPersistValue = fromPersistValueJSON toPersistValue = toPersistValueJSON