persistent-2.13.3.4: Type-safe, multi-backend data serialization.
Safe HaskellNone
LanguageHaskell2010

Database.Persist.Class.PersistEntity

Synopsis

Documentation

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.

Associated Types

type PersistEntityBackend record Source #

Persistent allows multiple different backends (databases).

data Key record Source #

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.

data Unique record Source #

Unique keys besides the Key.

Methods

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 -> [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 -> 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 Key record from a record 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

data Update record Source #

Updating a database entity.

Persistent users use combinators to create these.

Constructors

forall typ.PersistField typ => Update 
BackendUpdate (BackendSpecificUpdate (PersistEntityBackend record) record) 

type family BackendSpecificUpdate backend record Source #

data SelectOpt record Source #

Query options.

Persistent users use these directly.

Constructors

forall typ. Asc (EntityField record typ) 
forall typ. Desc (EntityField record typ) 
OffsetBy Int 
LimitTo Int 

data Filter record Source #

Filters which are available for select, updateWhere and deleteWhere. Each filter constructor specifies the field being filtered on, the type of comparison applied (equals, not equals, etc) and the argument for the comparison.

Persistent users use combinators to create these.

Note that it's important to be careful about the PersistFilter that you are using, if you use this directly. For example, using the In PersistFilter requires that you have an array- or list-shaped EntityField. It is possible to construct values using this that will create malformed runtime values.

Constructors

forall typ.PersistField typ => Filter 
FilterAnd [Filter record]

convenient for internal use, not needed for the API

FilterOr [Filter record] 
BackendFilter (BackendSpecificFilter (PersistEntityBackend record) record) 

data FilterValue typ where Source #

Value to filter with. Highly dependant on the type of filter used.

Since: 2.10.0

Constructors

FilterValue :: typ -> FilterValue typ 
FilterValues :: [typ] -> FilterValue typ 
UnsafeValue :: forall a typ. PersistField a => a -> FilterValue typ 

type family BackendSpecificFilter backend record Source #

data Entity record Source #

Datatype that represents an entity, with both its Key and its Haskell record representation.

When using a SQL-based backend (such as SQLite or PostgreSQL), an Entity may take any number of columns depending on how many fields it has. In order to reconstruct your entity on the Haskell side, persistent needs all of your entity columns and in the right order. Note that you don't need to worry about this when using persistent's API since everything is handled correctly behind the scenes.

However, if you want to issue a raw SQL command that returns an Entity, then you have to be careful with the column order. While you could use SELECT Entity.* WHERE ... and that would work most of the time, there are times when the order of the columns on your database is different from the order that persistent expects (for example, if you add a new field in the middle of you entity definition and then use the migration code -- persistent will expect the column to be in the middle, but your DBMS will put it as the last column). So, instead of using a query like the one above, you may use rawSql (from the Database.Persist.GenericSql module) with its /entity selection placeholder/ (a double question mark ??). Using rawSql the query above must be written as SELECT ?? WHERE ... Then rawSql will replace ?? with the list of all columns that we need from your entity in the right order. If your query returns two entities (i.e. (Entity backend a, Entity backend b)), then you must you use SELECT ??, ?? WHERE ..., and so on.

Constructors

Entity 

Fields

Instances

Instances details
(Eq (Key record), Eq record) => Eq (Entity record) Source # 
Instance details

Defined in Database.Persist.Class.PersistEntity

Methods

(==) :: Entity record -> Entity record -> Bool #

(/=) :: Entity record -> Entity record -> Bool #

(Ord (Key record), Ord record) => Ord (Entity record) Source # 
Instance details

Defined in Database.Persist.Class.PersistEntity

Methods

compare :: Entity record -> Entity record -> Ordering #

(<) :: Entity record -> Entity record -> Bool #

(<=) :: Entity record -> Entity record -> Bool #

(>) :: Entity record -> Entity record -> Bool #

(>=) :: Entity record -> Entity record -> Bool #

max :: Entity record -> Entity record -> Entity record #

min :: Entity record -> Entity record -> Entity record #

(Read (Key record), Read record) => Read (Entity record) Source # 
Instance details

Defined in Database.Persist.Class.PersistEntity

Methods

readsPrec :: Int -> ReadS (Entity record) #

readList :: ReadS [Entity record] #

readPrec :: ReadPrec (Entity record) #

readListPrec :: ReadPrec [Entity record] #

(Show (Key record), Show record) => Show (Entity record) Source # 
Instance details

Defined in Database.Persist.Class.PersistEntity

Methods

showsPrec :: Int -> Entity record -> ShowS #

show :: Entity record -> String #

showList :: [Entity record] -> ShowS #

(Generic (Key record), Generic record) => Generic (Entity record) Source # 
Instance details

Defined in Database.Persist.Class.PersistEntity

Associated Types

type Rep (Entity record) :: Type -> Type #

Methods

from :: Entity record -> Rep (Entity record) x #

to :: Rep (Entity record) x -> Entity record #

(PersistEntity record, PersistField record, PersistField (Key record)) => PersistField (Entity record) Source # 
Instance details

Defined in Database.Persist.Class.PersistEntity

(PersistField record, PersistEntity record) => PersistFieldSql (Entity record) Source # 
Instance details

Defined in Database.Persist.Sql.Class

Methods

sqlType :: Proxy (Entity record) -> SqlType Source #

(PersistEntity record, PersistEntityBackend record ~ backend, IsPersistBackend backend) => RawSql (Entity record) Source # 
Instance details

Defined in Database.Persist.Sql.Class

type Rep (Entity record) Source # 
Instance details

Defined in Database.Persist.Class.PersistEntity

type Rep (Entity record) = D1 ('MetaData "Entity" "Database.Persist.Class.PersistEntity" "persistent-2.13.3.4-5sJaMje8pdyJEXNJV7Cn8v" 'False) (C1 ('MetaCons "Entity" 'PrefixI 'True) (S1 ('MetaSel ('Just "entityKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Key record)) :*: S1 ('MetaSel ('Just "entityVal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 record)))

recordName :: PersistEntity record => record -> Text Source #

Textual representation of the record

entityValues :: PersistEntity record => Entity record -> [PersistValue] Source #

Get list of values corresponding to given entity.

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

PersistField based on other typeclasses

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

toPersistValueEnum :: Enum a => a -> PersistValue Source #

Convenience function for getting a free PersistField instance from a type with an Enum instance. The function derivePersistField from the persistent-template package should generally be preferred. However, if you want to ensure that an ORDER BY clause that uses your field will order rows by the data constructor order, this is a better choice.

Example usage in combination with fromPersistValueEnum:

data SeverityLevel = Low | Medium | Critical | High
  deriving (Enum, Bounded)
instance PersistField SeverityLevel where
  fromPersistValue = fromPersistValueEnum
  toPersistValue = toPersistValueEnum

fromPersistValueEnum :: (Enum a, Bounded a) => PersistValue -> Either Text a Source #

Convenience function for getting a free PersistField instance from a type with an Enum instance. This function also requires a Bounded instance to improve the reporting of errors.

Example usage in combination with toPersistValueEnum:

data SeverityLevel = Low | Medium | Critical | High
  deriving (Enum, Bounded)
instance PersistField SeverityLevel where
  fromPersistValue = fromPersistValueEnum
  toPersistValue = toPersistValueEnum

Support for OverloadedLabels with EntityField

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

Methods

symbolToField :: EntityField rec typ Source #