Safe Haskell | None |
---|---|
Language | Haskell98 |
- 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
- entityPrimary :: EntityDef -> Maybe CompositeDef
- entityKeyFields :: EntityDef -> [FieldDef]
- keyAndEntityFields :: EntityDef -> [FieldDef]
- type ExtraLine = [Text]
- newtype HaskellName = HaskellName {}
- newtype DBName = DBName {}
- type Attr = Text
- data FieldType
- data FieldDef = FieldDef {
- fieldHaskell :: !HaskellName
- fieldDB :: !DBName
- fieldType :: !FieldType
- fieldSqlType :: !SqlType
- fieldAttrs :: ![Attr]
- fieldStrict :: !Bool
- fieldReference :: !ReferenceDef
- 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 {}
- 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
- | PersistDbSpecific ByteString
- fromPersistValueText :: PersistValue -> Either Text Text
- data SqlType
- data PersistFilter
- data UpdateException
- data OnlyUniqueException = OnlyUniqueException String
- data PersistUpdate
- data SomePersistField = PersistField a => SomePersistField a
- data Update record
- = PersistField typ => Update {
- updateField :: EntityField record typ
- updateValue :: typ
- updateUpdate :: PersistUpdate
- | BackendUpdate (BackendSpecificUpdate (PersistEntityBackend record) record)
- = PersistField typ => Update {
- type family BackendSpecificUpdate backend record
- data SelectOpt record
- = Asc (EntityField record typ)
- | Desc (EntityField record typ)
- | OffsetBy Int
- | LimitTo Int
- data Filter record
- = PersistField typ => Filter {
- filterField :: EntityField record typ
- filterValue :: Either typ [typ]
- filterFilter :: PersistFilter
- | FilterAnd [Filter record]
- | FilterOr [Filter record]
- | BackendFilter (BackendSpecificFilter (PersistEntityBackend record) record)
- = PersistField typ => Filter {
- type family BackendSpecificFilter backend record
- data Entity record = Entity {}
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 |
data IsNullable Source #
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.
EntityDef | |
|
entityKeyFields :: EntityDef -> [FieldDef] Source #
keyAndEntityFields :: EntityDef -> [FieldDef] Source #
newtype HaskellName Source #
FieldDef | |
|
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). |
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
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 | |
|
UniqueDef | |
|
data CompositeDef Source #
CompositeDef | |
|
type ForeignFieldDef = (HaskellName, DBName) Source #
Used instead of FieldDef to generate a smaller amount of code
data ForeignDef Source #
data PersistException Source #
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 |
PersistDbSpecific ByteString | 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) |
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.
data PersistFilter Source #
data UpdateException Source #
data OnlyUniqueException Source #
data PersistUpdate Source #
data SomePersistField Source #
PersistField a => SomePersistField a |
Updating a database entity.
Persistent users use combinators to create these.
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.
Asc (EntityField record 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.
PersistField typ => Filter | |
| |
FilterAnd [Filter record] | convenient for internal use, not needed for the API |
FilterOr [Filter record] | |
BackendFilter (BackendSpecificFilter (PersistEntityBackend record) record) |
type family BackendSpecificFilter backend 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.
(Eq (Key record), Eq record) => Eq (Entity record) Source # | |
(Ord (Key record), Ord record) => Ord (Entity record) Source # | |
(Read (Key record), Read record) => Read (Entity record) Source # | |
(Show (Key record), Show record) => Show (Entity record) Source # | |
(Generic (Key record), Generic record) => Generic (Entity record) Source # | |
(PersistEntity record, PersistField record, PersistField (Key record)) => PersistField (Entity record) Source # | |
(PersistField record, PersistEntity record) => PersistFieldSql (Entity record) Source # | |
(PersistEntity record, (~) * (PersistEntityBackend record) backend, IsPersistBackend backend) => RawSql (Entity record) Source # | |
type Rep (Entity record) Source # | |