Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Checkmark
- data IsNullable
- data WhyNullable
- data EntityDef = EntityDef {
- entityHaskell :: !HaskellName
- entityDB :: !DBName
- entityId :: !FieldDef
- entityAttrs :: ![Attr]
- entityFields :: ![FieldDef]
- entityUniques :: ![UniqueDef]
- entityForeigns :: ![ForeignDef]
- entityDerives :: ![Text]
- entityExtra :: !(Map Text [ExtraLine])
- entitySum :: !Bool
- entityComments :: !(Maybe Text)
- entitiesPrimary :: EntityDef -> Maybe [FieldDef]
- entityPrimary :: EntityDef -> Maybe CompositeDef
- entityKeyFields :: EntityDef -> [FieldDef]
- keyAndEntityFields :: EntityDef -> [FieldDef]
- type ExtraLine = [Text]
- newtype HaskellName = HaskellName {}
- newtype DBName = DBName {}
- type Attr = Text
- data FieldAttr
- parseFieldAttrs :: [Text] -> [FieldAttr]
- data FieldType
- data FieldDef = FieldDef {
- fieldHaskell :: !HaskellName
- fieldDB :: !DBName
- fieldType :: !FieldType
- fieldSqlType :: !SqlType
- fieldAttrs :: ![FieldAttr]
- fieldStrict :: !Bool
- fieldReference :: !ReferenceDef
- fieldCascade :: !FieldCascade
- fieldComments :: !(Maybe Text)
- fieldGenerated :: !(Maybe Text)
- isFieldNotGenerated :: FieldDef -> Bool
- data ReferenceDef
- data EmbedEntityDef = EmbedEntityDef {}
- data EmbedFieldDef = EmbedFieldDef {}
- toEmbedEntityDef :: EntityDef -> EmbedEntityDef
- data UniqueDef = UniqueDef {
- uniqueHaskell :: !HaskellName
- uniqueDBName :: !DBName
- uniqueFields :: ![(HaskellName, DBName)]
- uniqueAttrs :: ![Attr]
- data CompositeDef = CompositeDef {
- compositeFields :: ![FieldDef]
- compositeAttrs :: ![Attr]
- type ForeignFieldDef = (HaskellName, DBName)
- data ForeignDef = ForeignDef {
- foreignRefTableHaskell :: !HaskellName
- foreignRefTableDBName :: !DBName
- foreignConstraintNameHaskell :: !HaskellName
- foreignConstraintNameDBName :: !DBName
- foreignFieldCascade :: !FieldCascade
- foreignFields :: ![(ForeignFieldDef, ForeignFieldDef)]
- foreignAttrs :: ![Attr]
- foreignNullable :: Bool
- foreignToPrimary :: Bool
- data FieldCascade = FieldCascade {
- fcOnUpdate :: !(Maybe CascadeAction)
- fcOnDelete :: !(Maybe CascadeAction)
- noCascade :: FieldCascade
- renderFieldCascade :: FieldCascade -> Text
- data CascadeAction
- = Cascade
- | Restrict
- | SetNull
- | SetDefault
- renderCascadeAction :: CascadeAction -> Text
- data PersistException
- data PersistValue
- = PersistText Text
- | PersistByteString ByteString
- | PersistInt64 Int64
- | PersistDouble Double
- | PersistRational Rational
- | PersistBool Bool
- | PersistDay Day
- | PersistTimeOfDay TimeOfDay
- | PersistUTCTime UTCTime
- | PersistNull
- | PersistList [PersistValue]
- | PersistMap [(Text, PersistValue)]
- | PersistObjectId ByteString
- | PersistArray [PersistValue]
- | PersistLiteral ByteString
- | PersistLiteralEscaped ByteString
- | PersistDbSpecific ByteString
- fromPersistValueText :: PersistValue -> Either Text Text
- data SqlType
- data PersistFilter
- data UpdateException
- data OnlyUniqueException = OnlyUniqueException String
- data PersistUpdate
- data SomePersistField = forall a.PersistField a => SomePersistField a
- data Update record
- = forall typ.PersistField typ => Update {
- updateField :: EntityField record typ
- updateValue :: typ
- updateUpdate :: PersistUpdate
- | BackendUpdate (BackendSpecificUpdate (PersistEntityBackend record) record)
- = forall typ.PersistField typ => Update {
- type family BackendSpecificUpdate backend record
- data SelectOpt record
- = forall typ. Asc (EntityField record typ)
- | forall typ. Desc (EntityField record typ)
- | OffsetBy Int
- | LimitTo Int
- data Filter record
- = forall typ.PersistField typ => Filter {
- filterField :: EntityField record typ
- filterValue :: FilterValue typ
- filterFilter :: PersistFilter
- | FilterAnd [Filter record]
- | FilterOr [Filter record]
- | BackendFilter (BackendSpecificFilter (PersistEntityBackend record) record)
- = forall typ.PersistField typ => Filter {
- data FilterValue typ where
- FilterValue :: typ -> FilterValue typ
- FilterValues :: [typ] -> FilterValue typ
- UnsafeValue :: forall a typ. PersistField a => a -> FilterValue typ
- type family BackendSpecificFilter backend record
- data family Key record
- data Entity record = Entity {}
- newtype OverflowNatural = OverflowNatural {}
Documentation
A Checkmark
should be used as a field type whenever a
uniqueness constraint should guarantee that a certain kind of
record may appear at most once, but other kinds of records may
appear any number of times.
NOTE: You need to mark any Checkmark
fields as nullable
(see the following example).
For example, suppose there's a Location
entity that
represents where a user has lived:
Location user UserId name Text current Checkmark nullable UniqueLocation user current
The UniqueLocation
constraint allows any number of
Inactive
Location
s to be current
. However, there may be
at most one current
Location
per user (i.e., either zero
or one per user).
This data type works because of the way that SQL treats
NULL
able fields within uniqueness constraints. The SQL
standard says that NULL
values should be considered
different, so we represent Inactive
as SQL NULL
, thus
allowing any number of Inactive
records. On the other hand,
we represent Active
as TRUE
, so the uniqueness constraint
will disallow more than one Active
record.
Note: There may be DBMSs that do not respect the SQL
standard's treatment of NULL
values on uniqueness
constraints, please check if this data type works before
relying on it.
The SQL BOOLEAN
type is used because it's the smallest data
type available. Note that we never use FALSE
, just TRUE
and NULL
. Provides the same behavior Maybe ()
would if
()
was a valid PersistField
.
Active | When used on a uniqueness constraint, there
may be at most one |
Inactive | When used on a uniqueness constraint, there
may be any number of |
Instances
data IsNullable Source #
Instances
Eq IsNullable Source # | |
Defined in Database.Persist.Types.Base (==) :: IsNullable -> IsNullable -> Bool # (/=) :: IsNullable -> IsNullable -> Bool # | |
Show IsNullable Source # | |
Defined in Database.Persist.Types.Base showsPrec :: Int -> IsNullable -> ShowS # show :: IsNullable -> String # showList :: [IsNullable] -> ShowS # |
data WhyNullable Source #
The reason why a field is nullable
is very important. A
field that is nullable because of a Maybe
tag will have its
type changed from A
to Maybe A
. OTOH, a field that is
nullable because of a nullable
tag will remain with the same
type.
Instances
Eq WhyNullable Source # | |
Defined in Database.Persist.Types.Base (==) :: WhyNullable -> WhyNullable -> Bool # (/=) :: WhyNullable -> WhyNullable -> Bool # | |
Show WhyNullable Source # | |
Defined in Database.Persist.Types.Base showsPrec :: Int -> WhyNullable -> ShowS # show :: WhyNullable -> String # showList :: [WhyNullable] -> ShowS # |
An EntityDef
represents the information that persistent
knows
about an Entity. It uses this information to generate the Haskell
datatype, the SQL migrations, and other relevant conversions.
EntityDef | |
|
entityKeyFields :: EntityDef -> [FieldDef] Source #
keyAndEntityFields :: EntityDef -> [FieldDef] Source #
newtype HaskellName Source #
Instances
Eq HaskellName Source # | |
Defined in Database.Persist.Types.Base (==) :: HaskellName -> HaskellName -> Bool # (/=) :: HaskellName -> HaskellName -> Bool # | |
Ord HaskellName Source # | |
Defined in Database.Persist.Types.Base compare :: HaskellName -> HaskellName -> Ordering # (<) :: HaskellName -> HaskellName -> Bool # (<=) :: HaskellName -> HaskellName -> Bool # (>) :: HaskellName -> HaskellName -> Bool # (>=) :: HaskellName -> HaskellName -> Bool # max :: HaskellName -> HaskellName -> HaskellName # min :: HaskellName -> HaskellName -> HaskellName # | |
Read HaskellName Source # | |
Defined in Database.Persist.Types.Base readsPrec :: Int -> ReadS HaskellName # readList :: ReadS [HaskellName] # readPrec :: ReadPrec HaskellName # readListPrec :: ReadPrec [HaskellName] # | |
Show HaskellName Source # | |
Defined in Database.Persist.Types.Base showsPrec :: Int -> HaskellName -> ShowS # show :: HaskellName -> String # showList :: [HaskellName] -> ShowS # |
Attributes that may be attached to fields that can affect migrations and serialization in backend-specific ways.
While we endeavor to, we can't forsee all use cases for all backends,
and so FieldAttr
is extensible through its constructor FieldAttrOther
.
Since: 2.11.0.0
parseFieldAttrs :: [Text] -> [FieldAttr] Source #
Parse raw field attributes into structured form. Any unrecognized
attributes will be preserved, identically as they are encountered,
as FieldAttrOther
values.
Since: 2.11.0.0
A FieldType
describes a field parsed from the QuasiQuoter and is
used to determine the Haskell type in the generated code.
name Text
parses into FTTypeCon Nothing Text
name T.Text
parses into FTTypeCon (Just T Text)
name (Jsonb User)
parses into:
FTApp (FTTypeCon Nothing Jsonb) (FTTypeCon Nothing User)
A FieldDef
represents the information that persistent
knows about
a field of a datatype. This includes information used to parse the field
out of the database and what the field corresponds to.
FieldDef | |
|
isFieldNotGenerated :: FieldDef -> Bool Source #
data ReferenceDef Source #
There are 3 kinds of references 1) composite (to fields that exist in the record) 2) single field 3) embedded
NoReference | |
ForeignRef !HaskellName !FieldType | A ForeignRef has a late binding to the EntityDef it references via HaskellName and has the Haskell type of the foreign key in the form of FieldType |
EmbedRef EmbedEntityDef | |
CompositeRef CompositeDef | |
SelfReference | A SelfReference stops an immediate cycle which causes non-termination at compile-time (issue #311). |
Instances
Eq ReferenceDef Source # | |
Defined in Database.Persist.Types.Base (==) :: ReferenceDef -> ReferenceDef -> Bool # (/=) :: ReferenceDef -> ReferenceDef -> Bool # | |
Ord ReferenceDef Source # | |
Defined in Database.Persist.Types.Base compare :: ReferenceDef -> ReferenceDef -> Ordering # (<) :: ReferenceDef -> ReferenceDef -> Bool # (<=) :: ReferenceDef -> ReferenceDef -> Bool # (>) :: ReferenceDef -> ReferenceDef -> Bool # (>=) :: ReferenceDef -> ReferenceDef -> Bool # max :: ReferenceDef -> ReferenceDef -> ReferenceDef # min :: ReferenceDef -> ReferenceDef -> ReferenceDef # | |
Read ReferenceDef Source # | |
Defined in Database.Persist.Types.Base readsPrec :: Int -> ReadS ReferenceDef # readList :: ReadS [ReferenceDef] # | |
Show ReferenceDef Source # | |
Defined in Database.Persist.Types.Base showsPrec :: Int -> ReferenceDef -> ShowS # show :: ReferenceDef -> String # showList :: [ReferenceDef] -> ShowS # |
data EmbedEntityDef Source #
An EmbedEntityDef is the same as an EntityDef But it is only used for fieldReference so it only has data needed for embedding
Instances
Eq EmbedEntityDef Source # | |
Defined in Database.Persist.Types.Base (==) :: EmbedEntityDef -> EmbedEntityDef -> Bool # (/=) :: EmbedEntityDef -> EmbedEntityDef -> Bool # | |
Ord EmbedEntityDef Source # | |
Defined in Database.Persist.Types.Base compare :: EmbedEntityDef -> EmbedEntityDef -> Ordering # (<) :: EmbedEntityDef -> EmbedEntityDef -> Bool # (<=) :: EmbedEntityDef -> EmbedEntityDef -> Bool # (>) :: EmbedEntityDef -> EmbedEntityDef -> Bool # (>=) :: EmbedEntityDef -> EmbedEntityDef -> Bool # max :: EmbedEntityDef -> EmbedEntityDef -> EmbedEntityDef # min :: EmbedEntityDef -> EmbedEntityDef -> EmbedEntityDef # | |
Read EmbedEntityDef Source # | |
Defined in Database.Persist.Types.Base readsPrec :: Int -> ReadS EmbedEntityDef # readList :: ReadS [EmbedEntityDef] # | |
Show EmbedEntityDef Source # | |
Defined in Database.Persist.Types.Base showsPrec :: Int -> EmbedEntityDef -> ShowS # show :: EmbedEntityDef -> String # showList :: [EmbedEntityDef] -> ShowS # |
data EmbedFieldDef Source #
An EmbedFieldDef is the same as a FieldDef But it is only used for embeddedFields so it only has data needed for embedding
EmbedFieldDef | |
|
Instances
Eq EmbedFieldDef Source # | |
Defined in Database.Persist.Types.Base (==) :: EmbedFieldDef -> EmbedFieldDef -> Bool # (/=) :: EmbedFieldDef -> EmbedFieldDef -> Bool # | |
Ord EmbedFieldDef Source # | |
Defined in Database.Persist.Types.Base compare :: EmbedFieldDef -> EmbedFieldDef -> Ordering # (<) :: EmbedFieldDef -> EmbedFieldDef -> Bool # (<=) :: EmbedFieldDef -> EmbedFieldDef -> Bool # (>) :: EmbedFieldDef -> EmbedFieldDef -> Bool # (>=) :: EmbedFieldDef -> EmbedFieldDef -> Bool # max :: EmbedFieldDef -> EmbedFieldDef -> EmbedFieldDef # min :: EmbedFieldDef -> EmbedFieldDef -> EmbedFieldDef # | |
Read EmbedFieldDef Source # | |
Defined in Database.Persist.Types.Base readsPrec :: Int -> ReadS EmbedFieldDef # readList :: ReadS [EmbedFieldDef] # | |
Show EmbedFieldDef Source # | |
Defined in Database.Persist.Types.Base showsPrec :: Int -> EmbedFieldDef -> ShowS # show :: EmbedFieldDef -> String # showList :: [EmbedFieldDef] -> ShowS # |
UniqueDef | |
|
data CompositeDef Source #
CompositeDef | |
|
Instances
Eq CompositeDef Source # | |
Defined in Database.Persist.Types.Base (==) :: CompositeDef -> CompositeDef -> Bool # (/=) :: CompositeDef -> CompositeDef -> Bool # | |
Ord CompositeDef Source # | |
Defined in Database.Persist.Types.Base compare :: CompositeDef -> CompositeDef -> Ordering # (<) :: CompositeDef -> CompositeDef -> Bool # (<=) :: CompositeDef -> CompositeDef -> Bool # (>) :: CompositeDef -> CompositeDef -> Bool # (>=) :: CompositeDef -> CompositeDef -> Bool # max :: CompositeDef -> CompositeDef -> CompositeDef # min :: CompositeDef -> CompositeDef -> CompositeDef # | |
Read CompositeDef Source # | |
Defined in Database.Persist.Types.Base readsPrec :: Int -> ReadS CompositeDef # readList :: ReadS [CompositeDef] # | |
Show CompositeDef Source # | |
Defined in Database.Persist.Types.Base showsPrec :: Int -> CompositeDef -> ShowS # show :: CompositeDef -> String # showList :: [CompositeDef] -> ShowS # |
type ForeignFieldDef = (HaskellName, DBName) Source #
Used instead of FieldDef to generate a smaller amount of code
data ForeignDef Source #
ForeignDef | |
|
Instances
Eq ForeignDef Source # | |
Defined in Database.Persist.Types.Base (==) :: ForeignDef -> ForeignDef -> Bool # (/=) :: ForeignDef -> ForeignDef -> Bool # | |
Ord ForeignDef Source # | |
Defined in Database.Persist.Types.Base compare :: ForeignDef -> ForeignDef -> Ordering # (<) :: ForeignDef -> ForeignDef -> Bool # (<=) :: ForeignDef -> ForeignDef -> Bool # (>) :: ForeignDef -> ForeignDef -> Bool # (>=) :: ForeignDef -> ForeignDef -> Bool # max :: ForeignDef -> ForeignDef -> ForeignDef # min :: ForeignDef -> ForeignDef -> ForeignDef # | |
Read ForeignDef Source # | |
Defined in Database.Persist.Types.Base readsPrec :: Int -> ReadS ForeignDef # readList :: ReadS [ForeignDef] # readPrec :: ReadPrec ForeignDef # readListPrec :: ReadPrec [ForeignDef] # | |
Show ForeignDef Source # | |
Defined in Database.Persist.Types.Base showsPrec :: Int -> ForeignDef -> ShowS # show :: ForeignDef -> String # showList :: [ForeignDef] -> ShowS # |
data FieldCascade Source #
This datatype describes how a foreign reference field cascades deletes or updates.
This type is used in both parsing the model definitions and performing
migrations. A Nothing
in either of the field values means that the
user has not specified a CascadeAction
. An unspecified CascadeAction
is defaulted to Restrict
when doing migrations.
Since: 2.11.0
FieldCascade | |
|
Instances
Eq FieldCascade Source # | |
Defined in Database.Persist.Types.Base (==) :: FieldCascade -> FieldCascade -> Bool # (/=) :: FieldCascade -> FieldCascade -> Bool # | |
Ord FieldCascade Source # | |
Defined in Database.Persist.Types.Base compare :: FieldCascade -> FieldCascade -> Ordering # (<) :: FieldCascade -> FieldCascade -> Bool # (<=) :: FieldCascade -> FieldCascade -> Bool # (>) :: FieldCascade -> FieldCascade -> Bool # (>=) :: FieldCascade -> FieldCascade -> Bool # max :: FieldCascade -> FieldCascade -> FieldCascade # min :: FieldCascade -> FieldCascade -> FieldCascade # | |
Read FieldCascade Source # | |
Defined in Database.Persist.Types.Base readsPrec :: Int -> ReadS FieldCascade # readList :: ReadS [FieldCascade] # | |
Show FieldCascade Source # | |
Defined in Database.Persist.Types.Base showsPrec :: Int -> FieldCascade -> ShowS # show :: FieldCascade -> String # showList :: [FieldCascade] -> ShowS # |
noCascade :: FieldCascade Source #
A FieldCascade
that does nothing.
Since: 2.11.0
renderFieldCascade :: FieldCascade -> Text Source #
Renders a FieldCascade
value such that it can be used in SQL
migrations.
Since: 2.11.0
data CascadeAction Source #
An action that might happen on a deletion or update on a foreign key change.
Since: 2.11.0
Instances
Eq CascadeAction Source # | |
Defined in Database.Persist.Types.Base (==) :: CascadeAction -> CascadeAction -> Bool # (/=) :: CascadeAction -> CascadeAction -> Bool # | |
Ord CascadeAction Source # | |
Defined in Database.Persist.Types.Base compare :: CascadeAction -> CascadeAction -> Ordering # (<) :: CascadeAction -> CascadeAction -> Bool # (<=) :: CascadeAction -> CascadeAction -> Bool # (>) :: CascadeAction -> CascadeAction -> Bool # (>=) :: CascadeAction -> CascadeAction -> Bool # max :: CascadeAction -> CascadeAction -> CascadeAction # min :: CascadeAction -> CascadeAction -> CascadeAction # | |
Read CascadeAction Source # | |
Defined in Database.Persist.Types.Base readsPrec :: Int -> ReadS CascadeAction # readList :: ReadS [CascadeAction] # | |
Show CascadeAction Source # | |
Defined in Database.Persist.Types.Base showsPrec :: Int -> CascadeAction -> ShowS # show :: CascadeAction -> String # showList :: [CascadeAction] -> ShowS # |
renderCascadeAction :: CascadeAction -> Text Source #
Render a CascadeAction
to Text
such that it can be used in a SQL
command.
Since: 2.11.0
data PersistException Source #
PersistError Text | Generic Exception |
PersistMarshalError Text | |
PersistInvalidField Text | |
PersistForeignConstraintUnmet Text | |
PersistMongoDBError Text | |
PersistMongoDBUnsupported Text |
Instances
Show PersistException Source # | |
Defined in Database.Persist.Types.Base showsPrec :: Int -> PersistException -> ShowS # show :: PersistException -> String # showList :: [PersistException] -> ShowS # | |
Exception PersistException Source # | |
Defined in Database.Persist.Types.Base | |
Error PersistException Source # | |
Defined in Database.Persist.Types.Base strMsg :: String -> PersistException # |
data PersistValue Source #
A raw value which can be stored in any backend and can be marshalled to
and from a PersistField
.
PersistText Text | |
PersistByteString ByteString | |
PersistInt64 Int64 | |
PersistDouble Double | |
PersistRational Rational | |
PersistBool Bool | |
PersistDay Day | |
PersistTimeOfDay TimeOfDay | |
PersistUTCTime UTCTime | |
PersistNull | |
PersistList [PersistValue] | |
PersistMap [(Text, PersistValue)] | |
PersistObjectId ByteString | Intended especially for MongoDB backend |
PersistArray [PersistValue] | Intended especially for PostgreSQL backend for text arrays |
PersistLiteral ByteString | Using |
PersistLiteralEscaped ByteString | Similar to |
PersistDbSpecific ByteString | Deprecated: Deprecated since 2.11 because of inconsistent escaping behavior across backends. The Postgres backend escapes these values, while the MySQL backend does not. If you are using this, please switch to Using data Geo = Geo ByteString instance PersistField Geo where toPersistValue (Geo t) = PersistDbSpecific t fromPersistValue (PersistDbSpecific t) = Right $ Geo $ Data.ByteString.concat ["'", t, "'"] fromPersistValue _ = Left "Geo values must be converted from PersistDbSpecific" instance PersistFieldSql Geo where sqlType _ = SqlOther "GEOGRAPHY(POINT,4326)" toPoint :: Double -> Double -> Geo toPoint lat lon = Geo $ Data.ByteString.concat ["'POINT(", ps $ lon, " ", ps $ lat, ")'"] where ps = Data.Text.pack . show If Foo has a geography field, we can then perform insertions like the following: insert $ Foo (toPoint 44 44) |
Instances
A SQL data type. Naming attempts to reflect the underlying Haskell datatypes, eg SqlString instead of SqlVarchar. Different SQL databases may have different translations for these types.
SqlString | |
SqlInt32 | |
SqlInt64 | |
SqlReal | |
SqlNumeric Word32 Word32 | |
SqlBool | |
SqlDay | |
SqlTime | |
SqlDayTime | Always uses UTC timezone |
SqlBlob | |
SqlOther Text | a backend-specific name |
data PersistFilter Source #
Instances
Read PersistFilter Source # | |
Defined in Database.Persist.Types.Base readsPrec :: Int -> ReadS PersistFilter # readList :: ReadS [PersistFilter] # | |
Show PersistFilter Source # | |
Defined in Database.Persist.Types.Base showsPrec :: Int -> PersistFilter -> ShowS # show :: PersistFilter -> String # showList :: [PersistFilter] -> ShowS # |
data UpdateException Source #
Instances
Show UpdateException Source # | |
Defined in Database.Persist.Types.Base showsPrec :: Int -> UpdateException -> ShowS # show :: UpdateException -> String # showList :: [UpdateException] -> ShowS # | |
Exception UpdateException Source # | |
Defined in Database.Persist.Types.Base |
data OnlyUniqueException Source #
Instances
Show OnlyUniqueException Source # | |
Defined in Database.Persist.Types.Base showsPrec :: Int -> OnlyUniqueException -> ShowS # show :: OnlyUniqueException -> String # showList :: [OnlyUniqueException] -> ShowS # | |
Exception OnlyUniqueException Source # | |
data PersistUpdate Source #
Instances
Read PersistUpdate Source # | |
Defined in Database.Persist.Types.Base readsPrec :: Int -> ReadS PersistUpdate # readList :: ReadS [PersistUpdate] # | |
Show PersistUpdate Source # | |
Defined in Database.Persist.Types.Base showsPrec :: Int -> PersistUpdate -> ShowS # show :: PersistUpdate -> String # showList :: [PersistUpdate] -> ShowS # |
Updating a database entity.
Persistent users use combinators to create these.
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.
forall typ. Asc (EntityField record typ) | |
forall typ. Desc (EntityField record typ) | |
OffsetBy Int | |
LimitTo Int |
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.
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
FilterValue :: typ -> FilterValue typ | |
FilterValues :: [typ] -> FilterValue typ | |
UnsafeValue :: forall a typ. PersistField a => a -> FilterValue typ |
type family BackendSpecificFilter backend record Source #
data family Key record Source #
By default, a backend will automatically generate the key Instead you can specify a Primary key made up of unique values.
Instances
(PersistEntity a, PersistEntityBackend a ~ backend, IsPersistBackend backend) => RawSql (Key a) Source # | |
Defined in Database.Persist.Sql.Class rawSqlCols :: (DBName -> Text) -> Key a -> (Int, [Text]) Source # rawSqlColCountReason :: Key a -> String Source # rawSqlProcessRow :: [PersistValue] -> Either Text (Key a) 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.
Instances
newtype OverflowNatural Source #
Prior to persistent-2.11.0
, we provided an instance of
PersistField
for the Natural
type. This was in error, because
Natural
represents an infinite value, and databases don't have
reasonable types for this.
The instance for Natural
used the Int64
underlying type, which will
cause underflow and overflow errors. This type has the exact same code
in the instances, and will work seamlessly.
A more appropriate type for this is the Word
series of types from
Data.Word. These have a bounded size, are guaranteed to be
non-negative, and are quite efficient for the database to store.
Since: 2.11.0