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

Database.Persist.Types

Synopsis

Documentation

data Checkmark Source #

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 Locations 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 NULLable 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.

Constructors

Active

When used on a uniqueness constraint, there may be at most one Active record.

Inactive

When used on a uniqueness constraint, there may be any number of Inactive records.

Instances

Instances details
Bounded Checkmark Source # 
Instance details

Defined in Database.Persist.Types.Base

Enum Checkmark Source # 
Instance details

Defined in Database.Persist.Types.Base

Eq Checkmark Source # 
Instance details

Defined in Database.Persist.Types.Base

Ord Checkmark Source # 
Instance details

Defined in Database.Persist.Types.Base

Read Checkmark Source # 
Instance details

Defined in Database.Persist.Types.Base

Show Checkmark Source # 
Instance details

Defined in Database.Persist.Types.Base

ToHttpApiData Checkmark Source # 
Instance details

Defined in Database.Persist.Types.Base

FromHttpApiData Checkmark Source # 
Instance details

Defined in Database.Persist.Types.Base

PathPiece Checkmark Source # 
Instance details

Defined in Database.Persist.Types.Base

PersistField Checkmark Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistFieldSql Checkmark Source # 
Instance details

Defined in Database.Persist.Sql.Class

data IsNullable Source #

Instances

Instances details
Eq IsNullable Source # 
Instance details

Defined in Database.Persist.Types.Base

Show IsNullable Source # 
Instance details

Defined in Database.Persist.Types.Base

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

Instances details
Eq WhyNullable Source # 
Instance details

Defined in Database.Persist.Types.Base

Show WhyNullable Source # 
Instance details

Defined in Database.Persist.Types.Base

data EntityDef Source #

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.

Constructors

EntityDef 

Fields

newtype DBName Source #

Constructors

DBName 

Fields

Instances

Instances details
Eq DBName Source # 
Instance details

Defined in Database.Persist.Types.Base

Methods

(==) :: DBName -> DBName -> Bool #

(/=) :: DBName -> DBName -> Bool #

Ord DBName Source # 
Instance details

Defined in Database.Persist.Types.Base

Read DBName Source # 
Instance details

Defined in Database.Persist.Types.Base

Show DBName Source # 
Instance details

Defined in Database.Persist.Types.Base

type Attr = Text Source #

data FieldAttr Source #

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

data FieldType Source #

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)

Constructors

FTTypeCon (Maybe Text) Text

Optional module and name.

FTApp FieldType FieldType 
FTList FieldType 

data FieldDef Source #

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.

Constructors

FieldDef 

Fields

  • fieldHaskell :: !HaskellName

    The name of the field. Note that this does not corresponds to the record labels generated for the particular entity - record labels are generated with the type name prefixed to the field, so a FieldDef that contains a HaskellName "name" for a type User will have a record field userName.

  • fieldDB :: !DBName

    The name of the field in the database. For SQL databases, this corresponds to the column name.

  • fieldType :: !FieldType

    The type of the field in Haskell.

  • fieldSqlType :: !SqlType

    The type of the field in a SQL database.

  • fieldAttrs :: ![FieldAttr]

    Whether or not the field is gnerated and how. Backend-dependent. ^ User annotations for a field. These are provided with the ! operator.

  • fieldStrict :: !Bool

    If this is True, then the Haskell datatype will have a strict record field. The default value for this is True.

  • fieldReference :: !ReferenceDef
     
  • fieldCascade :: !FieldCascade

    Defines how operations on the field cascade on to the referenced tables. This doesn't have any meaning if the fieldReference is set to NoReference or SelfReference. The cascade option here should be the same as the one obtained in the fieldReference.

    Since: 2.11.0

  • fieldComments :: !(Maybe Text)

    Optional comments for a Field. There is not currently a way to attach comments to a field in the quasiquoter.

    Since: 2.10.0

  • fieldGenerated :: !(Maybe Text)

    Whether or not the field is a GENERATED column, and additionally the expression to use for generation.

    Since: 2.11.0.0

data ReferenceDef Source #

There are 3 kinds of references 1) composite (to fields that exist in the record) 2) single field 3) embedded

Constructors

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 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

Constructors

EmbedFieldDef 

Fields

type ForeignFieldDef = (HaskellName, DBName) Source #

Used instead of FieldDef to generate a smaller amount of code

data ForeignDef Source #

Constructors

ForeignDef 

Fields

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

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

renderCascadeAction :: CascadeAction -> Text Source #

Render a CascadeAction to Text such that it can be used in a SQL command.

Since: 2.11.0

data PersistValue Source #

A raw value which can be stored in any backend and can be marshalled to and from a PersistField.

Constructors

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 PersistLiteral allows you to use types or keywords specific to a particular backend.

PersistLiteralEscaped ByteString

Similar to PersistLiteral, but escapes the ByteString.

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 PersistLiteral or PersistLiteralEscaped based on your needs.

Using PersistDbSpecific allows you to use types specific to a particular backend. For example, below is a simple example of the PostGIS geography type:

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

Instances details
Eq PersistValue Source # 
Instance details

Defined in Database.Persist.Types.Base

Ord PersistValue Source # 
Instance details

Defined in Database.Persist.Types.Base

Read PersistValue Source # 
Instance details

Defined in Database.Persist.Types.Base

Show PersistValue Source # 
Instance details

Defined in Database.Persist.Types.Base

ToJSON PersistValue Source # 
Instance details

Defined in Database.Persist.Types.Base

FromJSON PersistValue Source # 
Instance details

Defined in Database.Persist.Types.Base

ToHttpApiData PersistValue Source # 
Instance details

Defined in Database.Persist.Types.Base

FromHttpApiData PersistValue Source # 
Instance details

Defined in Database.Persist.Types.Base

PathPiece PersistValue Source # 
Instance details

Defined in Database.Persist.Types.Base

PersistField PersistValue Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistFieldSql PersistValue Source # 
Instance details

Defined in Database.Persist.Sql.Class

data SqlType Source #

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.

Constructors

SqlString 
SqlInt32 
SqlInt64 
SqlReal 
SqlNumeric Word32 Word32 
SqlBool 
SqlDay 
SqlTime 
SqlDayTime

Always uses UTC timezone

SqlBlob 
SqlOther Text

a backend-specific name

Instances

Instances details
Eq SqlType Source # 
Instance details

Defined in Database.Persist.Types.Base

Methods

(==) :: SqlType -> SqlType -> Bool #

(/=) :: SqlType -> SqlType -> Bool #

Ord SqlType Source # 
Instance details

Defined in Database.Persist.Types.Base

Read SqlType Source # 
Instance details

Defined in Database.Persist.Types.Base

Show SqlType Source # 
Instance details

Defined in Database.Persist.Types.Base

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 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

Instances details
(PersistEntity a, PersistEntityBackend a ~ backend, IsPersistBackend backend) => RawSql (Key a) Source # 
Instance details

Defined in Database.Persist.Sql.Class

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.11.0.0-7MZ4QawVRfZ1UMDL6jceVl" '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)))

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

Constructors

OverflowNatural 

Instances

Instances details
Eq OverflowNatural Source # 
Instance details

Defined in Database.Persist.Class.PersistField

Ord OverflowNatural Source # 
Instance details

Defined in Database.Persist.Class.PersistField

Show OverflowNatural Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistField OverflowNatural Source # 
Instance details

Defined in Database.Persist.Class.PersistField

PersistFieldSql OverflowNatural Source #

This type uses the SqlInt64 version, which will exhibit overflow and underflow behavior. Additionally, it permits negative values in the database, which isn't ideal.

Since: 2.11.0

Instance details

Defined in Database.Persist.Sql.Class