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

Database.Persist.Quasi.Internal

Description

This Internal module may have breaking changes that will not be reflected in major version bumps. Please use Database.Persist.Quasi instead. If you need something in this module, please file an issue on GitHub.

Since: 2.13.0.0

Synopsis

Documentation

parse :: PersistSettings -> Text -> [UnboundEntityDef] Source #

Parses a quasi-quoted syntax into a list of entity definitions.

data PersistSettings Source #

Constructors

PersistSettings 

Fields

data Token Source #

A token used by the parser.

Constructors

Token Text

Token tok is token tok already unquoted.

DocComment Text

DocComment is a documentation comment, unmodified.

Instances

Instances details
Eq Token Source # 
Instance details

Defined in Database.Persist.Quasi.Internal

Methods

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

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

Show Token Source # 
Instance details

Defined in Database.Persist.Quasi.Internal

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

data Line Source #

A line of parsed tokens

Constructors

Line 

Instances

Instances details
Eq Line Source # 
Instance details

Defined in Database.Persist.Quasi.Internal

Methods

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

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

Show Line Source # 
Instance details

Defined in Database.Persist.Quasi.Internal

Methods

showsPrec :: Int -> Line -> ShowS #

show :: Line -> String #

showList :: [Line] -> ShowS #

UnboundEntityDef

data UnboundEntityDef Source #

An EntityDef produced by the QuasiQuoter. It contains information that the QuasiQuoter is capable of knowing about the entities. It is inherently unfinished, though - there are many other Unbound datatypes that also contain partial information.

The unboundEntityDef is not complete or reliable - to know which fields are safe to use, consult the parsing code.

This type was completely internal until 2.13.0.0, when it was exposed as part of the Database.Persist.Quasi.Internal module.

TODO: refactor this so we can expose it for consumers.

Since: 2.13.0.0

Constructors

UnboundEntityDef 

Fields

  • unboundForeignDefs :: [UnboundForeignDef]

    A list of foreign definitions on the parsed entity.

    Since: 2.13.0.0

  • unboundPrimarySpec :: PrimarySpec

    The specification for the primary key of the unbound entity.

    Since: 2.13.0.0

  • unboundEntityDef :: EntityDef

    The incomplete and partial EntityDef that we're defining. We re-use the type here to prevent duplication, but several of the fields are unset and left to defaults.

    Since: 2.13.0.0

  • unboundEntityFields :: [UnboundFieldDef]

    The list of fields for the entity. We're not capable of knowing information like "is this a reference?" or "what's the underlying type of the field?" yet, so we defer those to the Template Haskell execution.

    Since: 2.13.0.0

unbindEntityDef :: EntityDef -> UnboundEntityDef Source #

Convert an EntityDef into an UnboundEntityDef. This "forgets" information about the EntityDef, but it is all kept present on the unboundEntityDef field if necessary.

Since: 2.13.0.0

getUnboundFieldDefs :: UnboundEntityDef -> [UnboundFieldDef] Source #

Returns the [UnboundFieldDef] for an UnboundEntityDef. This returns all fields defined on the entity.

Since: 2.13.0.0

data UnboundForeignDef Source #

Define an explicit foreign key reference.

User
    name Text
    email Text

    Primary name email

Dog
    ownerName Text
    ownerEmail Text

    Foreign User fk_dog_user ownerName ownerEmail

Since: 2.13.0.0

Constructors

UnboundForeignDef 

Fields

data UnboundFieldDef Source #

A representation of a database column, with everything that can be known at parse time.

Since: 2.13.0.0

Constructors

UnboundFieldDef 

Fields

  • unboundFieldNameHS :: FieldNameHS

    The Haskell name of the field. This is parsed directly from the definition, and is used to generate the Haskell record field and the EntityField definition.

    Since: 2.13.0.0

  • unboundFieldNameDB :: FieldNameDB

    The database name of the field. By default, this is determined by the PersistSettings record at parse time. You can customize this with a sql= attribute:

        name Text  sql=foo_name
    

    Since: 2.13.0.0

  • unboundFieldAttrs :: [FieldAttr]

    The attributes present on the field. For rules on parsing and utility, see the comments on the datatype.

    Since: 2.13.0.0

  • unboundFieldStrict :: Bool

    Whether or not the field should be strict in the generated Haskell code.

    Since: 2.13.0.0

  • unboundFieldType :: FieldType

    The type of the field, as far as is known at parse time.

    The TemplateHaskell code will reconstruct a Type out of this, but the names will be imported as-is.

    Since: 2.13.0.0

  • unboundFieldCascade :: FieldCascade

    We parse if there's a FieldCascade on the field. If the field is not a reference, this information is ignored.

    Post
       user UserId OnDeleteCascade
    

    Since: 2.13.0.0

  • unboundFieldGenerated :: Maybe Text

    Contains an expression to generate the column. If this is present, then the column will not be written to the database, but generated by the expression every time.

    Item
        subtotal Int
        taxRate  Rational
        total    Int      generated="subtotal * tax_rate"
    

    Since: 2.13.0.0

  • unboundFieldComments :: Maybe Text

    Any comments present on the field. Documentation comments use a Haskell-like syntax, and must be present before the field in question.

    Post
        -- | This is the blog post title.
        title Text
        -- | You can have multi-line comments.
        -- | But each line must have the pipe character.
        author UserId
    

    Since: 2.13.0.0

data UnboundCompositeDef Source #

A definition for a composite primary key.

@since.2.13.0.0

Constructors

UnboundCompositeDef 

Fields

data UnboundIdDef Source #

This type represents an Id declaration in the QuasiQuoted syntax.

Id

This uses the implied settings, and is equivalent to omitting the Id statement entirely.

Id Text

This will set the field type of the ID to be Text.

Id Text sql=foo_id

This will set the field type of the Id to be Text and the SQL DB name to be foo_id.

Id FooId

This results in a shared primary key - the FooId refers to a Foo table.

Id FooId OnDelete Cascade

You can set a cascade behavior on an ID column.

Since: 2.13.0.0

unbindFieldDef :: FieldDef -> UnboundFieldDef Source #

Forget innformation about a FieldDef so it can beused as an UnboundFieldDef.

Since: 2.13.0.0

unboundIdDefToFieldDef :: FieldNameDB -> EntityNameHS -> UnboundIdDef -> FieldDef Source #

Convert an UnboundIdDef into a FieldDef suitable for use in the EntityIdField constructor.

Since: 2.13.0.0

data PrimarySpec Source #

The specification for how an entity's primary key should be formed.

Persistent requires that every table have a primary key. By default, an implied ID is assigned, based on the mpsImplicitIdDef field on MkPersistSettings. Because we can't access that type at parse-time, we defer that decision until later.

Since: 2.13.0.0

Constructors

NaturalKey UnboundCompositeDef

A NaturalKey contains columns that are defined on the datatype itself. This is defined using the Primary keyword and given a non-empty list of columns.

User
    name    Text
    email   Text

    Primary name email

A natural key may also contain only a single column. A natural key with multiple columns is called a 'composite key'.

Since: 2.13.0.0

SurrogateKey UnboundIdDef

A surrogate key is not part of the domain model for a database table. You can specify a custom surro

You can specify a custom surrogate key using the Id syntax.

User
    Id    Text
    name  Text

Note that you must provide a default= expression when using this in order to use insert or related functions. The insertKey function can be used instead, as it allows you to specify a key directly. Fixing this issue is tracked in #1247 on GitHub.

Since: 2.13.0.0

DefaultKey FieldNameDB

The default key for the entity using the settings in MkPersistSettings.

This is implicit - a table without an Id or Primary declaration will have a DefaultKey.

Since: 2.13.0.0

mkAutoIdField' :: FieldNameDB -> EntityNameHS -> SqlType -> FieldDef Source #

Creates a default ID field.

Since: 2.13.0.0

data UnboundForeignFieldList Source #

A list of fields present on the foreign reference.

Constructors

FieldListImpliedId (NonEmpty FieldNameHS)

If no References keyword is supplied, then it is assumed that you are referring to the Primary key or Id of the target entity.

Since: 2.13.0.0

FieldListHasReferences (NonEmpty ForeignFieldReference)

You can specify the exact columns you're referring to here, if they aren't part of a primary key. Most databases expect a unique index on the columns you refer to, but Persistent doesnt' check that.

User
    Id           UUID default="uuid_generate_v1mc()"
    name         Text

    UniqueName name

Dog
    ownerName    Text

    Foreign User fk_dog_user ownerName References name

Since: 2.13.0.0

data ForeignFieldReference Source #

A pairing of the FieldNameHS for the source table to the FieldNameHS for the target table.

Since: 2.13.0.0

Constructors

ForeignFieldReference 

Fields

mkKeyConType :: EntityNameHS -> FieldType Source #

Convert an EntityNameHS into FieldType that will get parsed into the ID type for the entity.

>>> mkKeyConType (EntityNameHS "Hello)
FTTypeCon Nothing HelloId

Since: 2.13.0.0

isHaskellUnboundField :: UnboundFieldDef -> Bool Source #

Returns True if the UnboundFieldDef does not have a MigrationOnly or SafeToRemove flag from the QuasiQuoter.

Since: 2.13.0.0