Copyright | Eric Mertens 2017 |
---|---|
License | ISC |
Maintainer | emertens@gmail.com |
Safe Haskell | Safe |
Language | Haskell2010 |
This module provides a flattened view of information about data types and newtypes that can be supported uniformly across multiple versions of the template-haskell package.
Sample output for reifyDatatype
''Maybe
DatatypeInfo
{datatypeContext
= [] ,datatypeName
= GHC.Base.Maybe ,datatypeVars
= [SigT
(VarT
a_3530822107858468866)StarT
] ,datatypeVariant
=Datatype
,datatypeCons
= [ConstructorInfo
{constructorName
= GHC.Base.Nothing ,constructorVars
= [] ,constructorContext
= [] ,constructorFields
= [] ,constructorStrictness
= [] ,constructorVariant
=NormalConstructor
} ,ConstructorInfo
{constructorName
= GHC.Base.Just ,constructorVars
= [] ,constructorContext
= [] ,constructorFields
= [VarT
a_3530822107858468866 ] ,constructorStrictness
= [FieldStrictness
UnspecifiedUnpackedness
Lazy
] ,constructorVariant
=NormalConstructor
} ] }
Datatypes declared with GADT syntax are normalized to constructors with existentially quantified type variables and equality constraints.
Synopsis
- data DatatypeInfo = DatatypeInfo {}
- data ConstructorInfo = ConstructorInfo {}
- data DatatypeVariant
- data ConstructorVariant
- data FieldStrictness = FieldStrictness {}
- data Unpackedness
- data Strictness
- reifyDatatype :: Name -> Q DatatypeInfo
- reifyConstructor :: Name -> Q ConstructorInfo
- reifyRecord :: Name -> Q ConstructorInfo
- normalizeInfo :: Info -> Q DatatypeInfo
- normalizeDec :: Dec -> Q DatatypeInfo
- normalizeCon :: Name -> [Type] -> DatatypeVariant -> Con -> Q [ConstructorInfo]
- lookupByConstructorName :: Name -> DatatypeInfo -> ConstructorInfo
- lookupByRecordName :: Name -> DatatypeInfo -> ConstructorInfo
- class TypeSubstitution a where
- quantifyType :: Type -> Type
- freshenFreeVariables :: Type -> Q Type
- equalPred :: Type -> Type -> Pred
- classPred :: Name -> [Type] -> Pred
- asEqualPred :: Pred -> Maybe (Type, Type)
- asClassPred :: Pred -> Maybe (Name, [Type])
- dataDCompat :: CxtQ -> Name -> [TyVarBndr] -> [ConQ] -> [Name] -> DecQ
- newtypeDCompat :: CxtQ -> Name -> [TyVarBndr] -> ConQ -> [Name] -> DecQ
- tySynInstDCompat :: Name -> [TypeQ] -> TypeQ -> DecQ
- pragLineDCompat :: Int -> String -> Maybe DecQ
- arrowKCompat :: Kind -> Kind -> Kind
- isStrictAnnot :: FieldStrictness
- notStrictAnnot :: FieldStrictness
- unpackedAnnot :: FieldStrictness
- resolveTypeSynonyms :: Type -> Q Type
- resolvePredSynonyms :: Pred -> Q Pred
- resolveInfixT :: Type -> Q Type
- reifyFixityCompat :: Name -> Q (Maybe Fixity)
- showFixity :: Fixity -> String
- showFixityDirection :: FixityDirection -> String
- unifyTypes :: [Type] -> Q (Map Name Type)
- tvName :: TyVarBndr -> Name
- tvKind :: TyVarBndr -> Kind
- datatypeType :: DatatypeInfo -> Type
Types
data DatatypeInfo Source #
Normalized information about newtypes and data types.
datatypeVars
types will have an outermost SigT
to indicate the
parameter's kind. These types will be simple variables for ADTs
declared with data
and newtype
, but can be more complex for
types declared with data instance
and newtype instance
.
DatatypeInfo | |
|
Instances
data ConstructorInfo Source #
Normalized information about constructors associated with newtypes and data types.
ConstructorInfo | |
|
Instances
data DatatypeVariant Source #
Possible variants of data type declarations.
Datatype | Type declared with |
Newtype | Type declared with |
DataInstance | Type declared with |
NewtypeInstance | Type declared with |
Instances
data ConstructorVariant Source #
Possible variants of data constructors.
NormalConstructor | Constructor without field names |
InfixConstructor | Constructor without field names that is declared infix |
RecordConstructor [Name] | Constructor with field names |
Instances
data FieldStrictness Source #
Normalized information about a constructor field's UNPACK
and
strictness annotations.
Note that the interface for reifying strictness in Template Haskell changed considerably in GHC 8.0. The presentation in this library mirrors that which can be found in GHC 8.0 or later, whereas previously, unpackedness and strictness were represented with a single data type:
data Strict = IsStrict | NotStrict | Unpacked -- On GHC 7.4 or later
For backwards compatibility, we retrofit these constructors onto the following three values, respectively:
isStrictAnnot
=FieldStrictness
UnspecifiedUnpackedness
Strict
notStrictAnnot
=FieldStrictness
UnspecifiedUnpackedness
UnspecifiedStrictness
unpackedAnnot
=FieldStrictness
Unpack
Strict
Instances
data Unpackedness Source #
Information about a constructor field's unpackedness annotation.
UnspecifiedUnpackedness | No annotation whatsoever |
NoUnpack | Annotated with |
Unpack | Annotated with |
Instances
data Strictness Source #
Information about a constructor field's strictness annotation.
UnspecifiedStrictness | No annotation whatsoever |
Lazy | Annotated with |
Strict | Annotated with |
Instances
Normalization functions
:: Name | data type or constructor name |
-> Q DatatypeInfo |
Compute a normalized view of the metadata about a data type or newtype given a constructor.
This function will accept any constructor (value or type) for a type declared with newtype or data. Value constructors must be used to lookup datatype information about data instances and newtype instances, as giving the type constructor of a data family is often not enough to determine a particular data family instance.
In addition, this function will also accept a record selector for a data type with a constructor which uses that record.
GADT constructors are normalized into datatypes with explicit equality constraints. Note that no effort is made to distinguish between equalities of the same (homogeneous) kind and equalities between different (heterogeneous) kinds. For instance, the following GADT's constructors:
data T (a :: k -> *) where MkT1 :: T Proxy MkT2 :: T Maybe
will be normalized to the following equality constraints:
AppT (AppT EqualityT (VarT a)) (ConT Proxy) -- MkT1 AppT (AppT EqualityT (VarT a)) (ConT Maybe) -- MkT2
But only the first equality constraint is well kinded, since in the second
constraint, the kinds of (a :: k -> *)
and (Maybe :: * -> *)
are different.
Trying to categorize which constraints need homogeneous or heterogeneous
equality is tricky, so we leave that task to users of this library.
This function will apply various bug-fixes to the output of the underlying
template-haskell
library in order to provide a view of datatypes in
as uniform a way as possible.
:: Name | constructor name |
-> Q ConstructorInfo |
Compute a normalized view of the metadata about a constructor given its
Name
. This is useful for scenarios when you don't care about the info for
the enclosing data type.
:: Name | record name |
-> Q ConstructorInfo |
Compute a normalized view of the metadata about a constructor given the
Name
of one of its record selectors. This is useful for scenarios when you
don't care about the info for the enclosing data type.
normalizeInfo :: Info -> Q DatatypeInfo Source #
Normalize Info
for a newtype or datatype into a DatatypeInfo
.
Fail in Q
otherwise.
normalizeDec :: Dec -> Q DatatypeInfo Source #
Normalize Dec
for a newtype or datatype into a DatatypeInfo
.
Fail in Q
otherwise.
Beware: normalizeDec
can have surprising behavior when it comes to fixity.
For instance, if you have this quasiquoted data declaration:
[d| infix 5 :^^: data Foo where (:^^:) :: Int -> Int -> Foo |]
Then if you pass the Dec
for Foo
to normalizeDec
without splicing it
in a previous Template Haskell splice, then (:^^:)
will be labeled a NormalConstructor
instead of an InfixConstructor
. This is because Template Haskell has no way to
reify the fixity declaration for (:^^:)
, so it must assume there isn't one. To
work around this behavior, use reifyDatatype
instead.
:: Name | Type constructor |
-> [Type] | Type parameters |
-> DatatypeVariant | Extra information |
-> Con | Constructor |
-> Q [ConstructorInfo] |
Normalize a Con
into a ConstructorInfo
. This requires knowledge of
the type and parameters of the constructor, as well as whether the constructor
is for a data family instance, as extracted from the outer
Dec
.
DatatypeInfo
lookup functions
lookupByConstructorName Source #
:: Name | constructor name |
-> DatatypeInfo | info for the datatype which has that constructor |
-> ConstructorInfo |
Given a DatatypeInfo
, find the ConstructorInfo
corresponding to the
Name
of one of its constructors.
:: Name | record name |
-> DatatypeInfo | info for the datatype which has that constructor |
-> ConstructorInfo |
Given a DatatypeInfo
, find the ConstructorInfo
corresponding to the
Name
of one of its constructors.
Type variable manipulation
class TypeSubstitution a where Source #
Class for types that support type variable substitution.
applySubstitution :: Map Name Type -> a -> a Source #
Apply a type variable substitution.
Note that applySubstitution
is not capture-avoiding. To illustrate
this, observe that if you call this function with the following
substitution:
b :-> a
On the following Type
:
forall a. b
Then it will return:
forall a. a
However, because the same a
type variable was used in the range of the
substitution as was bound by the forall
, the substituted a
is now
captured by the forall
, resulting in a completely different function.
For th-abstraction
's purposes, this is acceptable, as it usually only
deals with globally unique type variable Name
s. If you use
applySubstitution
in a context where the Name
s aren't globally unique,
however, be aware of this potential problem.
freeVariables :: a -> [Name] Source #
Compute the free type variables
Instances
TypeSubstitution Type Source # | |
Defined in Language.Haskell.TH.Datatype | |
TypeSubstitution ConstructorInfo Source # | |
Defined in Language.Haskell.TH.Datatype applySubstitution :: Map Name Type -> ConstructorInfo -> ConstructorInfo Source # freeVariables :: ConstructorInfo -> [Name] Source # | |
TypeSubstitution a => TypeSubstitution [a] Source # | |
Defined in Language.Haskell.TH.Datatype applySubstitution :: Map Name Type -> [a] -> [a] Source # freeVariables :: [a] -> [Name] Source # |
quantifyType :: Type -> Type Source #
Add universal quantifier for all free variables in the type. This is
useful when constructing a type signature for a declaration.
This code is careful to ensure that the order of the variables quantified
is determined by their order of appearance in the type signature. (In
contrast with being dependent upon the Ord instance for Name
)
freshenFreeVariables :: Type -> Q Type Source #
Substitute all of the free variables in a type with fresh ones
Pred
functions
equalPred :: Type -> Type -> Pred Source #
Construct an equality constraint. The implementation of Pred
varies
across versions of Template Haskell.
Construct a typeclass constraint. The implementation of Pred
varies
across versions of Template Haskell.
asEqualPred :: Pred -> Maybe (Type, Type) Source #
Match a Pred
representing an equality constraint. Returns
arguments to the equality constraint if successful.
asClassPred :: Pred -> Maybe (Name, [Type]) Source #
Match a Pred
representing a class constraint.
Returns the classname and parameters if successful.
Backward compatible data definitions
:: CxtQ | context |
-> Name | type constructor |
-> [TyVarBndr] | type parameters |
-> [ConQ] | constructor definitions |
-> [Name] | derived class names |
-> DecQ |
Backward compatible version of dataD
:: CxtQ | context |
-> Name | type constructor |
-> [TyVarBndr] | type parameters |
-> ConQ | constructor definition |
-> [Name] | derived class names |
-> DecQ |
Backward compatible version of newtypeD
Backward compatible version of tySynInstD
Strictness annotations
Type simplification
resolveInfixT :: Type -> Q Type Source #
Resolve any infix type application in a type using the fixities that are currently available. Starting in `template-haskell-2.11` types could contain unresolved infix applications.
Fixities
reifyFixityCompat :: Name -> Q (Maybe Fixity) Source #
Backwards compatibility wrapper for Fixity
lookup.
In template-haskell-2.11.0.0
and later, the answer will always
be Just
of a fixity.
Before template-haskell-2.11.0.0
it was only possible to determine
fixity information for variables, class methods, and data constructors.
In this case for type operators the answer could be Nothing
, which
indicates that the answer is unavailable.
showFixity :: Fixity -> String Source #
Render a Fixity
as it would appear in Haskell source.
Example: infixl 5
showFixityDirection :: FixityDirection -> String Source #
Render a FixityDirection
like it would appear in Haskell source.
Examples: infixl
infixr
infix
Convenience functions
unifyTypes :: [Type] -> Q (Map Name Type) Source #
Compute the type variable substitution that unifies a list of types,
or fail in Q
.
All infix issue should be resolved before using unifyTypes
Alpha equivalent quantified types are not unified.
tvName :: TyVarBndr -> Name Source #
Extract the type variable name from a TyVarBndr
ignoring the
kind signature if one exists.
datatypeType :: DatatypeInfo -> Type Source #
Construct a Type using the datatype's type constructor and type parameters. Kind signatures are removed.