| Copyright | Eric Mertens 2017-2020 |
|---|---|
| License | ISC |
| Maintainer | emertens@gmail.com |
| Safe Haskell | Safe |
| Language | Haskell2010 |
Language.Haskell.TH.Datatype
Description
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= [KindedTVa_3530822107858468866 ()StarT] ,datatypeInstTypes= [SigT(VarTa_3530822107858468866)StarT] ,datatypeVariant=Datatype,datatypeReturnKind=StarT,datatypeCons= [ConstructorInfo{constructorName= GHC.Base.Nothing ,constructorVars= [] ,constructorContext= [] ,constructorFields= [] ,constructorStrictness= [] ,constructorVariant=NormalConstructor} ,ConstructorInfo{constructorName= GHC.Base.Just ,constructorVars= [] ,constructorContext= [] ,constructorFields= [VarTa_3530822107858468866 ] ,constructorStrictness= [FieldStrictnessUnspecifiedUnpackednessLazy] ,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 -> [TyVarBndrUnit] -> [Type] -> Kind -> DatatypeVariant -> Con -> Q [ConstructorInfo]
- lookupByConstructorName :: Name -> DatatypeInfo -> ConstructorInfo
- lookupByRecordName :: Name -> DatatypeInfo -> ConstructorInfo
- class TypeSubstitution a where
- applySubstitution :: Map Name Type -> a -> a
- freeVariables :: a -> [Name]
- quantifyType :: Type -> Type
- freeVariablesWellScoped :: [Type] -> [TyVarBndrUnit]
- 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 -> [TyVarBndrVis] -> [ConQ] -> [Name] -> DecQ
- newtypeDCompat :: CxtQ -> Name -> [TyVarBndrVis] -> ConQ -> [Name] -> DecQ
- tySynInstDCompat :: Name -> Maybe [Q TyVarBndrUnit] -> [TypeQ] -> TypeQ -> DecQ
- pragLineDCompat :: Int -> String -> Maybe DecQ
- arrowKCompat :: Kind -> Kind -> Kind
- isStrictAnnot :: FieldStrictness
- notStrictAnnot :: FieldStrictness
- unpackedAnnot :: FieldStrictness
- resolveTypeSynonyms :: Type -> Q Type
- resolveKindSynonyms :: Kind -> Q Kind
- 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_ flag -> Name
- tvKind :: TyVarBndr_ flag -> Kind
- datatypeType :: DatatypeInfo -> Type
Types
data DatatypeInfo #
Normalized information about newtypes and data types.
DatatypeInfo contains two fields, datatypeVars and datatypeInstTypes,
which encode information about the argument types. The simplest explanation
is that datatypeVars contains all the type variables bound by the data
type constructor, while datatypeInstTypes contains the type arguments
to the data type constructor. To be more precise:
- For ADTs declared with
dataandnewtype, it will likely be the case thatdatatypeVarsanddatatypeInstTypescoincide. For instance, givennewtype Id a = MkId a, in theDatatypeInfoforIdwe would haveanddatatypeVars= [KindedTVa ()StarT].datatypeInstVars= [SigT(VarTa)StarT]
ADTs that leverage PolyKinds may have more datatypeVars than
datatypeInstTypes. For instance, given data Proxy (a :: k) = MkProxy,
in the DatatypeInfo for Proxy we would have
(since there are two variables, datatypeVars = [KindedTV k () StarT, KindedTV a () (VarT k)]k and a), whereas
, since there is
only one explicit type argument to datatypeInstTypes = [SigT (VarT a) (VarT k)]Proxy.
The same outcome would occur if Proxy were declared using
TypeAbstractions, i.e., if it were declared as
data Proxy @k (a :: k) = MkProxy. The datatypeInstTypes would not
include a separate type for @k.
- For
data instances andnewtype instances of data families,datatypeVarsanddatatypeInstTypescan be quite different. Here is an example to illustrate the difference:
data family F a b data instance F (Maybe c) (f x) = MkF c (f x)
Then in the DatatypeInfo for F's data instance, we would have:
datatypeVars= [KindedTVc ()StarT,KindedTVf ()StarT,KindedTVx ()StarT]datatypeInstTypes= [AppT(ConT''Maybe) (VarTc) ,AppT(VarTf) (VarTx) ]
Constructors
| DatatypeInfo | |
Fields
| |
Instances
data ConstructorInfo #
Normalized information about constructors associated with newtypes and data types.
Constructors
| ConstructorInfo | |
Fields
| |
Instances
| Data ConstructorInfo # | |||||
Defined in Language.Haskell.TH.Datatype Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConstructorInfo -> c ConstructorInfo # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConstructorInfo # toConstr :: ConstructorInfo -> Constr # dataTypeOf :: ConstructorInfo -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ConstructorInfo) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConstructorInfo) # gmapT :: (forall b. Data b => b -> b) -> ConstructorInfo -> ConstructorInfo # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConstructorInfo -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConstructorInfo -> r # gmapQ :: (forall d. Data d => d -> u) -> ConstructorInfo -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConstructorInfo -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConstructorInfo -> m ConstructorInfo # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConstructorInfo -> m ConstructorInfo # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConstructorInfo -> m ConstructorInfo # | |||||
| Generic ConstructorInfo # | |||||
Defined in Language.Haskell.TH.Datatype Associated Types
Methods from :: ConstructorInfo -> Rep ConstructorInfo x # to :: Rep ConstructorInfo x -> ConstructorInfo # | |||||
| Show ConstructorInfo # | |||||
Defined in Language.Haskell.TH.Datatype Methods showsPrec :: Int -> ConstructorInfo -> ShowS # show :: ConstructorInfo -> String # showList :: [ConstructorInfo] -> ShowS # | |||||
| Eq ConstructorInfo # | |||||
Defined in Language.Haskell.TH.Datatype Methods (==) :: ConstructorInfo -> ConstructorInfo -> Bool # (/=) :: ConstructorInfo -> ConstructorInfo -> Bool # | |||||
| TypeSubstitution ConstructorInfo # | |||||
Defined in Language.Haskell.TH.Datatype Methods applySubstitution :: Map Name Type -> ConstructorInfo -> ConstructorInfo # freeVariables :: ConstructorInfo -> [Name] # | |||||
| type Rep ConstructorInfo # | |||||
Defined in Language.Haskell.TH.Datatype type Rep ConstructorInfo = D1 ('MetaData "ConstructorInfo" "Language.Haskell.TH.Datatype" "th-abstraction-0.7.1.0-26pbdb2QUSCHn0B9SqZNC2" 'False) (C1 ('MetaCons "ConstructorInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "constructorName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Just "constructorVars") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndrUnit]) :*: S1 ('MetaSel ('Just "constructorContext") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt))) :*: (S1 ('MetaSel ('Just "constructorFields") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Type]) :*: (S1 ('MetaSel ('Just "constructorStrictness") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FieldStrictness]) :*: S1 ('MetaSel ('Just "constructorVariant") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConstructorVariant))))) | |||||
data DatatypeVariant #
Possible variants of data type declarations.
Constructors
| Datatype | Type declared with |
| Newtype | Type declared with A |
| DataInstance | Type declared with |
| NewtypeInstance | Type declared with A |
| TypeData | Type declared with A
|
Instances
| Data DatatypeVariant # | |||||
Defined in Language.Haskell.TH.Datatype Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DatatypeVariant -> c DatatypeVariant # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DatatypeVariant # toConstr :: DatatypeVariant -> Constr # dataTypeOf :: DatatypeVariant -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DatatypeVariant) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DatatypeVariant) # gmapT :: (forall b. Data b => b -> b) -> DatatypeVariant -> DatatypeVariant # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DatatypeVariant -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DatatypeVariant -> r # gmapQ :: (forall d. Data d => d -> u) -> DatatypeVariant -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DatatypeVariant -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DatatypeVariant -> m DatatypeVariant # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DatatypeVariant -> m DatatypeVariant # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DatatypeVariant -> m DatatypeVariant # | |||||
| Generic DatatypeVariant # | |||||
Defined in Language.Haskell.TH.Datatype Associated Types
Methods from :: DatatypeVariant -> Rep DatatypeVariant x # to :: Rep DatatypeVariant x -> DatatypeVariant # | |||||
| Read DatatypeVariant # | |||||
Defined in Language.Haskell.TH.Datatype Methods readsPrec :: Int -> ReadS DatatypeVariant # readList :: ReadS [DatatypeVariant] # | |||||
| Show DatatypeVariant # | |||||
Defined in Language.Haskell.TH.Datatype Methods showsPrec :: Int -> DatatypeVariant -> ShowS # show :: DatatypeVariant -> String # showList :: [DatatypeVariant] -> ShowS # | |||||
| Eq DatatypeVariant # | |||||
Defined in Language.Haskell.TH.Datatype Methods (==) :: DatatypeVariant -> DatatypeVariant -> Bool # (/=) :: DatatypeVariant -> DatatypeVariant -> Bool # | |||||
| Ord DatatypeVariant # | |||||
Defined in Language.Haskell.TH.Datatype Methods compare :: DatatypeVariant -> DatatypeVariant -> Ordering # (<) :: DatatypeVariant -> DatatypeVariant -> Bool # (<=) :: DatatypeVariant -> DatatypeVariant -> Bool # (>) :: DatatypeVariant -> DatatypeVariant -> Bool # (>=) :: DatatypeVariant -> DatatypeVariant -> Bool # max :: DatatypeVariant -> DatatypeVariant -> DatatypeVariant # min :: DatatypeVariant -> DatatypeVariant -> DatatypeVariant # | |||||
| type Rep DatatypeVariant # | |||||
Defined in Language.Haskell.TH.Datatype type Rep DatatypeVariant = D1 ('MetaData "DatatypeVariant" "Language.Haskell.TH.Datatype" "th-abstraction-0.7.1.0-26pbdb2QUSCHn0B9SqZNC2" 'False) ((C1 ('MetaCons "Datatype" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Newtype" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DataInstance" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NewtypeInstance" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeData" 'PrefixI 'False) (U1 :: Type -> Type)))) | |||||
data ConstructorVariant #
Possible variants of data constructors.
Constructors
| NormalConstructor | Constructor without field names |
| InfixConstructor | Constructor without field names that is declared infix |
| RecordConstructor [Name] | Constructor with field names |
Instances
| Data ConstructorVariant # | |||||
Defined in Language.Haskell.TH.Datatype Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConstructorVariant -> c ConstructorVariant # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConstructorVariant # toConstr :: ConstructorVariant -> Constr # dataTypeOf :: ConstructorVariant -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ConstructorVariant) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConstructorVariant) # gmapT :: (forall b. Data b => b -> b) -> ConstructorVariant -> ConstructorVariant # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConstructorVariant -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConstructorVariant -> r # gmapQ :: (forall d. Data d => d -> u) -> ConstructorVariant -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ConstructorVariant -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConstructorVariant -> m ConstructorVariant # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConstructorVariant -> m ConstructorVariant # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConstructorVariant -> m ConstructorVariant # | |||||
| Generic ConstructorVariant # | |||||
Defined in Language.Haskell.TH.Datatype Associated Types
Methods from :: ConstructorVariant -> Rep ConstructorVariant x # to :: Rep ConstructorVariant x -> ConstructorVariant # | |||||
| Show ConstructorVariant # | |||||
Defined in Language.Haskell.TH.Datatype Methods showsPrec :: Int -> ConstructorVariant -> ShowS # show :: ConstructorVariant -> String # showList :: [ConstructorVariant] -> ShowS # | |||||
| Eq ConstructorVariant # | |||||
Defined in Language.Haskell.TH.Datatype Methods (==) :: ConstructorVariant -> ConstructorVariant -> Bool # (/=) :: ConstructorVariant -> ConstructorVariant -> Bool # | |||||
| Ord ConstructorVariant # | |||||
Defined in Language.Haskell.TH.Datatype Methods compare :: ConstructorVariant -> ConstructorVariant -> Ordering # (<) :: ConstructorVariant -> ConstructorVariant -> Bool # (<=) :: ConstructorVariant -> ConstructorVariant -> Bool # (>) :: ConstructorVariant -> ConstructorVariant -> Bool # (>=) :: ConstructorVariant -> ConstructorVariant -> Bool # max :: ConstructorVariant -> ConstructorVariant -> ConstructorVariant # min :: ConstructorVariant -> ConstructorVariant -> ConstructorVariant # | |||||
| type Rep ConstructorVariant # | |||||
Defined in Language.Haskell.TH.Datatype type Rep ConstructorVariant = D1 ('MetaData "ConstructorVariant" "Language.Haskell.TH.Datatype" "th-abstraction-0.7.1.0-26pbdb2QUSCHn0B9SqZNC2" 'False) (C1 ('MetaCons "NormalConstructor" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "InfixConstructor" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RecordConstructor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name])))) | |||||
data FieldStrictness #
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=FieldStrictnessUnspecifiedUnpackednessStrictnotStrictAnnot=FieldStrictnessUnspecifiedUnpackednessUnspecifiedStrictnessunpackedAnnot=FieldStrictnessUnpackStrict
Constructors
| FieldStrictness | |
Fields | |
Instances
| Data FieldStrictness # | |||||
Defined in Language.Haskell.TH.Datatype Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FieldStrictness -> c FieldStrictness # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FieldStrictness # toConstr :: FieldStrictness -> Constr # dataTypeOf :: FieldStrictness -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FieldStrictness) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FieldStrictness) # gmapT :: (forall b. Data b => b -> b) -> FieldStrictness -> FieldStrictness # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FieldStrictness -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FieldStrictness -> r # gmapQ :: (forall d. Data d => d -> u) -> FieldStrictness -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FieldStrictness -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FieldStrictness -> m FieldStrictness # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldStrictness -> m FieldStrictness # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FieldStrictness -> m FieldStrictness # | |||||
| Generic FieldStrictness # | |||||
Defined in Language.Haskell.TH.Datatype Associated Types
Methods from :: FieldStrictness -> Rep FieldStrictness x # to :: Rep FieldStrictness x -> FieldStrictness # | |||||
| Show FieldStrictness # | |||||
Defined in Language.Haskell.TH.Datatype Methods showsPrec :: Int -> FieldStrictness -> ShowS # show :: FieldStrictness -> String # showList :: [FieldStrictness] -> ShowS # | |||||
| Eq FieldStrictness # | |||||
Defined in Language.Haskell.TH.Datatype Methods (==) :: FieldStrictness -> FieldStrictness -> Bool # (/=) :: FieldStrictness -> FieldStrictness -> Bool # | |||||
| Ord FieldStrictness # | |||||
Defined in Language.Haskell.TH.Datatype Methods compare :: FieldStrictness -> FieldStrictness -> Ordering # (<) :: FieldStrictness -> FieldStrictness -> Bool # (<=) :: FieldStrictness -> FieldStrictness -> Bool # (>) :: FieldStrictness -> FieldStrictness -> Bool # (>=) :: FieldStrictness -> FieldStrictness -> Bool # max :: FieldStrictness -> FieldStrictness -> FieldStrictness # min :: FieldStrictness -> FieldStrictness -> FieldStrictness # | |||||
| type Rep FieldStrictness # | |||||
Defined in Language.Haskell.TH.Datatype type Rep FieldStrictness = D1 ('MetaData "FieldStrictness" "Language.Haskell.TH.Datatype" "th-abstraction-0.7.1.0-26pbdb2QUSCHn0B9SqZNC2" 'False) (C1 ('MetaCons "FieldStrictness" 'PrefixI 'True) (S1 ('MetaSel ('Just "fieldUnpackedness") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Unpackedness) :*: S1 ('MetaSel ('Just "fieldStrictness") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Strictness))) | |||||
data Unpackedness #
Information about a constructor field's unpackedness annotation.
Constructors
| UnspecifiedUnpackedness | No annotation whatsoever |
| NoUnpack | Annotated with |
| Unpack | Annotated with |
Instances
| Data Unpackedness # | |||||
Defined in Language.Haskell.TH.Datatype Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Unpackedness -> c Unpackedness # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Unpackedness # toConstr :: Unpackedness -> Constr # dataTypeOf :: Unpackedness -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Unpackedness) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Unpackedness) # gmapT :: (forall b. Data b => b -> b) -> Unpackedness -> Unpackedness # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Unpackedness -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Unpackedness -> r # gmapQ :: (forall d. Data d => d -> u) -> Unpackedness -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Unpackedness -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Unpackedness -> m Unpackedness # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Unpackedness -> m Unpackedness # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Unpackedness -> m Unpackedness # | |||||
| Generic Unpackedness # | |||||
Defined in Language.Haskell.TH.Datatype Associated Types
| |||||
| Show Unpackedness # | |||||
Defined in Language.Haskell.TH.Datatype Methods showsPrec :: Int -> Unpackedness -> ShowS # show :: Unpackedness -> String # showList :: [Unpackedness] -> ShowS # | |||||
| Eq Unpackedness # | |||||
Defined in Language.Haskell.TH.Datatype | |||||
| Ord Unpackedness # | |||||
Defined in Language.Haskell.TH.Datatype Methods compare :: Unpackedness -> Unpackedness -> Ordering # (<) :: Unpackedness -> Unpackedness -> Bool # (<=) :: Unpackedness -> Unpackedness -> Bool # (>) :: Unpackedness -> Unpackedness -> Bool # (>=) :: Unpackedness -> Unpackedness -> Bool # max :: Unpackedness -> Unpackedness -> Unpackedness # min :: Unpackedness -> Unpackedness -> Unpackedness # | |||||
| type Rep Unpackedness # | |||||
Defined in Language.Haskell.TH.Datatype type Rep Unpackedness = D1 ('MetaData "Unpackedness" "Language.Haskell.TH.Datatype" "th-abstraction-0.7.1.0-26pbdb2QUSCHn0B9SqZNC2" 'False) (C1 ('MetaCons "UnspecifiedUnpackedness" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NoUnpack" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unpack" 'PrefixI 'False) (U1 :: Type -> Type))) | |||||
data Strictness #
Information about a constructor field's strictness annotation.
Constructors
| UnspecifiedStrictness | No annotation whatsoever |
| Lazy | Annotated with |
| Strict | Annotated with |
Instances
| Data Strictness # | |||||
Defined in Language.Haskell.TH.Datatype Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Strictness -> c Strictness # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Strictness # toConstr :: Strictness -> Constr # dataTypeOf :: Strictness -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Strictness) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Strictness) # gmapT :: (forall b. Data b => b -> b) -> Strictness -> Strictness # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Strictness -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Strictness -> r # gmapQ :: (forall d. Data d => d -> u) -> Strictness -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Strictness -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Strictness -> m Strictness # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Strictness -> m Strictness # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Strictness -> m Strictness # | |||||
| Generic Strictness # | |||||
Defined in Language.Haskell.TH.Datatype Associated Types
| |||||
| Show Strictness # | |||||
Defined in Language.Haskell.TH.Datatype Methods showsPrec :: Int -> Strictness -> ShowS # show :: Strictness -> String # showList :: [Strictness] -> ShowS # | |||||
| Eq Strictness # | |||||
Defined in Language.Haskell.TH.Datatype | |||||
| Ord Strictness # | |||||
Defined in Language.Haskell.TH.Datatype Methods compare :: Strictness -> Strictness -> Ordering # (<) :: Strictness -> Strictness -> Bool # (<=) :: Strictness -> Strictness -> Bool # (>) :: Strictness -> Strictness -> Bool # (>=) :: Strictness -> Strictness -> Bool # max :: Strictness -> Strictness -> Strictness # min :: Strictness -> Strictness -> Strictness # | |||||
| type Rep Strictness # | |||||
Defined in Language.Haskell.TH.Datatype type Rep Strictness = D1 ('MetaData "Strictness" "Language.Haskell.TH.Datatype" "th-abstraction-0.7.1.0-26pbdb2QUSCHn0B9SqZNC2" 'False) (C1 ('MetaCons "UnspecifiedStrictness" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Lazy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Strict" 'PrefixI 'False) (U1 :: Type -> Type))) | |||||
Normalization functions
Arguments
| :: 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.
Primitive types (other than unboxed sums and tuples) will have
no datatypeCons in their normalization.
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.
Arguments
| :: 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.
Arguments
| :: 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 #
Normalize Info for a newtype or datatype into a DatatypeInfo.
Fail in Q otherwise.
normalizeDec :: Dec -> Q DatatypeInfo #
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.
Arguments
| :: Name | Type constructor |
| -> [TyVarBndrUnit] | Type parameters |
| -> [Type] | Argument types |
| -> Kind | Result kind |
| -> 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
Arguments
| :: 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.
Arguments
| :: 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 #
Class for types that support type variable substitution.
Methods
applySubstitution :: Map Name Type -> a -> a #
Apply a type variable substitution.
freeVariables :: a -> [Name] #
Compute the free type variables
Instances
| TypeSubstitution Type # | |
Defined in Language.Haskell.TH.Datatype | |
| TypeSubstitution ConstructorInfo # | |
Defined in Language.Haskell.TH.Datatype Methods applySubstitution :: Map Name Type -> ConstructorInfo -> ConstructorInfo # freeVariables :: ConstructorInfo -> [Name] # | |
| TypeSubstitution a => TypeSubstitution [a] # | |
Defined in Language.Haskell.TH.Datatype | |
quantifyType :: Type -> Type #
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)
freeVariablesWellScoped :: [Type] -> [TyVarBndrUnit] #
Take a list of Types, find their free variables, and sort them
according to dependency order.
As an example of how this function works, consider the following type:
Proxy (a :: k)
Calling freeVariables on this type would yield [a, k], since that is
the order in which those variables appear in a left-to-right fashion. But
this order does not preserve the fact that k is the kind of a. Moreover,
if you tried writing the type forall a k. Proxy (a :: k), GHC would reject
this, since GHC would demand that k come before a.
freeVariablesWellScoped orders the free variables of a type in a way that
preserves this dependency ordering. If one were to call
freeVariablesWellScoped on the type above, it would return
[k, (a :: k)]. (This is why freeVariablesWellScoped returns a list of
TyVarBndrs instead of Names, since it must make it explicit that k
is the kind of a.)
freeVariablesWellScoped guarantees the free variables returned will be
ordered such that:
- Whenever an explicit kind signature of the form
(A :: K)is encountered, the free variables ofKwill always appear to the left of the free variables ofAin the returned result. - The constraint in (1) notwithstanding, free variables will appear in left-to-right order of their original appearance.
On older GHCs, this takes measures to avoid returning explicitly bound
kind variables, which was not possible before TypeInType.
freshenFreeVariables :: Type -> Q Type #
Substitute all of the free variables in a type with fresh ones
Pred functions
equalPred :: Type -> Type -> Pred #
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) #
Match a Pred representing an equality constraint. Returns
arguments to the equality constraint if successful.
asClassPred :: Pred -> Maybe (Name, [Type]) #
Match a Pred representing a class constraint.
Returns the classname and parameters if successful.
Backward compatible data definitions
Arguments
| :: CxtQ | context |
| -> Name | type constructor |
| -> [TyVarBndrVis] | type parameters |
| -> [ConQ] | constructor definitions |
| -> [Name] | derived class names |
| -> DecQ |
Backward compatible version of dataD
Arguments
| :: CxtQ | context |
| -> Name | type constructor |
| -> [TyVarBndrVis] | type parameters |
| -> ConQ | constructor definition |
| -> [Name] | derived class names |
| -> DecQ |
Backward compatible version of newtypeD
Arguments
| :: Name | type family name |
| -> Maybe [Q TyVarBndrUnit] | type variable binders |
| -> [TypeQ] | instance parameters |
| -> TypeQ | instance result |
| -> DecQ |
Backward compatible version of tySynInstD
arrowKCompat :: Kind -> Kind -> Kind #
Strictness annotations
Type simplification
resolveTypeSynonyms :: Type -> Q Type #
Expand all of the type synonyms in a type.
Note that this function will drop parentheses as a side effect.
resolveInfixT :: Type -> Q Type #
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) #
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 #
Render a Fixity as it would appear in Haskell source.
Example: infixl 5
showFixityDirection :: FixityDirection -> String #
Render a FixityDirection like it would appear in Haskell source.
Examples: infixl infixr infix
Convenience functions
unifyTypes :: [Type] -> Q (Map Name Type) #
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_ flag -> Name #
Extract the type variable name from a TyVarBndr, ignoring the
kind signature if one exists.
datatypeType :: DatatypeInfo -> Type #
Construct a Type using the datatype's type constructor and type parameters. Kind signatures are removed.