Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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
- parse :: PersistSettings -> Text -> [UnboundEntityDef]
- data PersistSettings = PersistSettings {
- psToDBName :: !(Text -> Text)
- psToFKName :: !(EntityNameHS -> ConstraintNameHS -> Text)
- psStrictFields :: !Bool
- psIdName :: !Text
- upperCaseSettings :: PersistSettings
- lowerCaseSettings :: PersistSettings
- toFKNameInfixed :: Text -> EntityNameHS -> ConstraintNameHS -> Text
- data Token
- = Token Text
- | DocComment Text
- data Line = Line {
- lineIndent :: Int
- tokens :: NonEmpty Token
- preparse :: Text -> Maybe (NonEmpty Line)
- parseLine :: Text -> Maybe Line
- parseFieldType :: Text -> Either String FieldType
- associateLines :: NonEmpty Line -> [LinesWithComments]
- data LinesWithComments = LinesWithComments {
- lwcLines :: NonEmpty Line
- lwcComments :: [Text]
- parseEntityFields :: [Line] -> ([[Token]], Map Text [ExtraLine])
- takeColsEx :: PersistSettings -> [Text] -> Maybe UnboundFieldDef
- data UnboundEntityDef = UnboundEntityDef {}
- getUnboundEntityNameHS :: UnboundEntityDef -> EntityNameHS
- unbindEntityDef :: EntityDef -> UnboundEntityDef
- getUnboundFieldDefs :: UnboundEntityDef -> [UnboundFieldDef]
- data UnboundForeignDef = UnboundForeignDef {}
- getSqlNameOr :: FieldNameDB -> [FieldAttr] -> FieldNameDB
- data UnboundFieldDef = UnboundFieldDef {}
- data UnboundCompositeDef = UnboundCompositeDef {}
- data UnboundIdDef = UnboundIdDef {}
- unbindFieldDef :: FieldDef -> UnboundFieldDef
- isUnboundFieldNullable :: UnboundFieldDef -> IsNullable
- unboundIdDefToFieldDef :: FieldNameDB -> EntityNameHS -> UnboundIdDef -> FieldDef
- data PrimarySpec
- mkAutoIdField' :: FieldNameDB -> EntityNameHS -> SqlType -> FieldDef
- data UnboundForeignFieldList
- data ForeignFieldReference = ForeignFieldReference {}
- mkKeyConType :: EntityNameHS -> FieldType
- isHaskellUnboundField :: UnboundFieldDef -> Bool
- data FieldTypeLit
Documentation
parse :: PersistSettings -> Text -> [UnboundEntityDef] Source #
Parses a quasi-quoted syntax into a list of entity definitions.
data PersistSettings Source #
PersistSettings | |
|
toFKNameInfixed :: Text -> EntityNameHS -> ConstraintNameHS -> Text Source #
A token used by the parser.
Token Text |
|
DocComment Text |
|
A line of parsed tokens
associateLines :: NonEmpty Line -> [LinesWithComments] Source #
data LinesWithComments Source #
LinesWithComments | |
|
Instances
Semigroup LinesWithComments Source # | |
Defined in Database.Persist.Quasi.Internal (<>) :: LinesWithComments -> LinesWithComments -> LinesWithComments # sconcat :: NonEmpty LinesWithComments -> LinesWithComments # stimes :: Integral b => b -> LinesWithComments -> LinesWithComments # | |
Show LinesWithComments Source # | |
Defined in Database.Persist.Quasi.Internal showsPrec :: Int -> LinesWithComments -> ShowS # show :: LinesWithComments -> String # showList :: [LinesWithComments] -> ShowS # | |
Eq LinesWithComments Source # | |
Defined in Database.Persist.Quasi.Internal (==) :: LinesWithComments -> LinesWithComments -> Bool # (/=) :: LinesWithComments -> LinesWithComments -> Bool # |
takeColsEx :: PersistSettings -> [Text] -> Maybe UnboundFieldDef Source #
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
UnboundEntityDef | |
|
Instances
getUnboundEntityNameHS :: UnboundEntityDef -> EntityNameHS Source #
Return the EntityNameHS
for an UnboundEntityDef
.
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 [
for an UnboundFieldDef
]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
UnboundForeignDef | |
|
Instances
getSqlNameOr :: FieldNameDB -> [FieldAttr] -> FieldNameDB Source #
data UnboundFieldDef Source #
A representation of a database column, with everything that can be known at parse time.
Since: 2.13.0.0
UnboundFieldDef | |
|
Instances
data UnboundCompositeDef Source #
A definition for a composite primary key.
@since.2.13.0.0
UnboundCompositeDef | |
|
Instances
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
Instances
Show UnboundIdDef Source # | |
Defined in Database.Persist.Quasi.Internal showsPrec :: Int -> UnboundIdDef -> ShowS # show :: UnboundIdDef -> String # showList :: [UnboundIdDef] -> ShowS # | |
Eq UnboundIdDef Source # | |
Defined in Database.Persist.Quasi.Internal (==) :: UnboundIdDef -> UnboundIdDef -> Bool # (/=) :: UnboundIdDef -> UnboundIdDef -> Bool # | |
Ord UnboundIdDef Source # | |
Defined in Database.Persist.Quasi.Internal compare :: UnboundIdDef -> UnboundIdDef -> Ordering # (<) :: UnboundIdDef -> UnboundIdDef -> Bool # (<=) :: UnboundIdDef -> UnboundIdDef -> Bool # (>) :: UnboundIdDef -> UnboundIdDef -> Bool # (>=) :: UnboundIdDef -> UnboundIdDef -> Bool # max :: UnboundIdDef -> UnboundIdDef -> UnboundIdDef # min :: UnboundIdDef -> UnboundIdDef -> UnboundIdDef # | |
Lift UnboundIdDef Source # | |
Defined in Database.Persist.Quasi.Internal lift :: Quote m => UnboundIdDef -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => UnboundIdDef -> Code m UnboundIdDef # |
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
NaturalKey UnboundCompositeDef | A 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 User Id Text name Text Note that you must provide a Since: 2.13.0.0 |
DefaultKey FieldNameDB | The default key for the entity using the settings in
This is implicit - a table without an Since: 2.13.0.0 |
Instances
Show PrimarySpec Source # | |
Defined in Database.Persist.Quasi.Internal showsPrec :: Int -> PrimarySpec -> ShowS # show :: PrimarySpec -> String # showList :: [PrimarySpec] -> ShowS # | |
Eq PrimarySpec Source # | |
Defined in Database.Persist.Quasi.Internal (==) :: PrimarySpec -> PrimarySpec -> Bool # (/=) :: PrimarySpec -> PrimarySpec -> Bool # | |
Ord PrimarySpec Source # | |
Defined in Database.Persist.Quasi.Internal compare :: PrimarySpec -> PrimarySpec -> Ordering # (<) :: PrimarySpec -> PrimarySpec -> Bool # (<=) :: PrimarySpec -> PrimarySpec -> Bool # (>) :: PrimarySpec -> PrimarySpec -> Bool # (>=) :: PrimarySpec -> PrimarySpec -> Bool # max :: PrimarySpec -> PrimarySpec -> PrimarySpec # min :: PrimarySpec -> PrimarySpec -> PrimarySpec # | |
Lift PrimarySpec Source # | |
Defined in Database.Persist.Quasi.Internal lift :: Quote m => PrimarySpec -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => PrimarySpec -> Code m PrimarySpec # |
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.
FieldListImpliedId (NonEmpty FieldNameHS) | If no 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 |
Instances
data ForeignFieldReference Source #
A pairing of the FieldNameHS
for the source table to the FieldNameHS
for the target table.
Since: 2.13.0.0
ForeignFieldReference | |
|
Instances
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
data FieldTypeLit Source #