th-abstraction-0.3.2.0: Nicer interface for reified information about data types

CopyrightEric Mertens 2017
LicenseISC
Maintaineremertens@gmail.com
Safe HaskellSafe
LanguageHaskell2010

Language.Haskell.TH.Datatype

Contents

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      = [ KindedTV a_3530822107858468866 StarT ]
 , datatypeInstTypes = [ 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

Types

data DatatypeInfo Source #

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:

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 datatypeVars = [KindedTV k StarT, KindedTV a (VarT k)] (since there are two variables, k and a), whereas datatypeInstTypes = [SigT (VarT a) (VarT k)], since there is only one explicit type argument to Proxy.

  • For data instances and newtype instances of data families, datatypeVars and datatypeInstTypes can 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      = [ KindedTV c StarT
                        , KindedTV f StarT
                        , KindedTV x StarT ]
  datatypeInstTypes = [ AppT (ConT ''Maybe) (VarT c)
                        , AppT (VarT f) (VarT x) ]
  

Constructors

DatatypeInfo 

Fields

Instances
Eq DatatypeInfo Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Data DatatypeInfo Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DatatypeInfo -> c DatatypeInfo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DatatypeInfo #

toConstr :: DatatypeInfo -> Constr #

dataTypeOf :: DatatypeInfo -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DatatypeInfo) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DatatypeInfo) #

gmapT :: (forall b. Data b => b -> b) -> DatatypeInfo -> DatatypeInfo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DatatypeInfo -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DatatypeInfo -> r #

gmapQ :: (forall d. Data d => d -> u) -> DatatypeInfo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DatatypeInfo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DatatypeInfo -> m DatatypeInfo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DatatypeInfo -> m DatatypeInfo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DatatypeInfo -> m DatatypeInfo #

Show DatatypeInfo Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Generic DatatypeInfo Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep DatatypeInfo :: Type -> Type #

type Rep DatatypeInfo Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

data ConstructorInfo Source #

Normalized information about constructors associated with newtypes and data types.

Constructors

ConstructorInfo 

Fields

Instances
Eq ConstructorInfo Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Data ConstructorInfo Source # 
Instance details

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 :: (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 #

Show ConstructorInfo Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Generic ConstructorInfo Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep ConstructorInfo :: Type -> Type #

TypeSubstitution ConstructorInfo Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

type Rep ConstructorInfo Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

type Rep ConstructorInfo = D1 (MetaData "ConstructorInfo" "Language.Haskell.TH.Datatype" "th-abstraction-0.3.2.0-IMP6eLYdIDnDdqwlZXmzr4" False) (C1 (MetaCons "ConstructorInfo" PrefixI True) ((S1 (MetaSel (Just "constructorName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name) :*: (S1 (MetaSel (Just "constructorVars") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TyVarBndr]) :*: 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 Source #

Possible variants of data type declarations.

Constructors

Datatype

Type declared with data

Newtype

Type declared with newtype

DataInstance

Type declared with data instance

NewtypeInstance

Type declared with newtype instance

Instances
Eq DatatypeVariant Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Data DatatypeVariant Source # 
Instance details

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 :: (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 #

Ord DatatypeVariant Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Read DatatypeVariant Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Show DatatypeVariant Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Generic DatatypeVariant Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep DatatypeVariant :: Type -> Type #

type Rep DatatypeVariant Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

type Rep DatatypeVariant = D1 (MetaData "DatatypeVariant" "Language.Haskell.TH.Datatype" "th-abstraction-0.3.2.0-IMP6eLYdIDnDdqwlZXmzr4" 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)))

data ConstructorVariant Source #

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
Eq ConstructorVariant Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Data ConstructorVariant Source # 
Instance details

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 :: (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 #

Ord ConstructorVariant Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Show ConstructorVariant Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Generic ConstructorVariant Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep ConstructorVariant :: Type -> Type #

type Rep ConstructorVariant Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

type Rep ConstructorVariant = D1 (MetaData "ConstructorVariant" "Language.Haskell.TH.Datatype" "th-abstraction-0.3.2.0-IMP6eLYdIDnDdqwlZXmzr4" 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 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 Strictness
notStrictAnnot = FieldStrictness UnspecifiedUnpackedness UnspecifiedStrictness
unpackedAnnot  = FieldStrictness Unpack Strictness
Instances
Eq FieldStrictness Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Data FieldStrictness Source # 
Instance details

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 :: (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 #

Ord FieldStrictness Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Show FieldStrictness Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Generic FieldStrictness Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep FieldStrictness :: Type -> Type #

type Rep FieldStrictness Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

type Rep FieldStrictness = D1 (MetaData "FieldStrictness" "Language.Haskell.TH.Datatype" "th-abstraction-0.3.2.0-IMP6eLYdIDnDdqwlZXmzr4" 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 Source #

Information about a constructor field's unpackedness annotation.

Constructors

UnspecifiedUnpackedness

No annotation whatsoever

NoUnpack

Annotated with {-# NOUNPACK #-}

Unpack

Annotated with {-# UNPACK #-}

Instances
Eq Unpackedness Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Data Unpackedness Source # 
Instance details

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 :: (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 #

Ord Unpackedness Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Show Unpackedness Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Generic Unpackedness Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep Unpackedness :: Type -> Type #

type Rep Unpackedness Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

type Rep Unpackedness = D1 (MetaData "Unpackedness" "Language.Haskell.TH.Datatype" "th-abstraction-0.3.2.0-IMP6eLYdIDnDdqwlZXmzr4" 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 Source #

Information about a constructor field's strictness annotation.

Constructors

UnspecifiedStrictness

No annotation whatsoever

Lazy

Annotated with ~

Strict

Annotated with !

Instances
Eq Strictness Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Data Strictness Source # 
Instance details

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 :: (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 #

Ord Strictness Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Show Strictness Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Generic Strictness Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

Associated Types

type Rep Strictness :: Type -> Type #

type Rep Strictness Source # 
Instance details

Defined in Language.Haskell.TH.Datatype

type Rep Strictness = D1 (MetaData "Strictness" "Language.Haskell.TH.Datatype" "th-abstraction-0.3.2.0-IMP6eLYdIDnDdqwlZXmzr4" 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

reifyDatatype Source #

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.

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.

reifyConstructor Source #

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.

reifyRecord Source #

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

normalizeCon Source #

Arguments

:: Name

Type constructor

-> [TyVarBndr]

Type parameters

-> [Type]

Argument types

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

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.

lookupByRecordName Source #

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

Class for types that support type variable substitution.

Methods

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 Names. If you use applySubstitution in a context where the Names aren't globally unique, however, be aware of this potential problem.

freeVariables :: a -> [Name] Source #

Compute the free type variables

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)

freeVariablesWellScoped :: [Type] -> [TyVarBndr] Source #

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:

  1. Whenever an explicit kind signature of the form (A :: K) is encountered, the free variables of K will always appear to the left of the free variables of A in the returned result.
  2. 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 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.

classPred Source #

Arguments

:: Name

class

-> [Type]

parameters

-> Pred 

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

dataDCompat Source #

Arguments

:: CxtQ

context

-> Name

type constructor

-> [TyVarBndr]

type parameters

-> [ConQ]

constructor definitions

-> [Name]

derived class names

-> DecQ 

Backward compatible version of dataD

newtypeDCompat Source #

Arguments

:: CxtQ

context

-> Name

type constructor

-> [TyVarBndr]

type parameters

-> ConQ

constructor definition

-> [Name]

derived class names

-> DecQ 

Backward compatible version of newtypeD

tySynInstDCompat Source #

Arguments

:: Name

type family name

-> Maybe [Q TyVarBndr]

type variable binders

-> [TypeQ]

instance parameters

-> TypeQ

instance result

-> DecQ 

Backward compatible version of tySynInstD

pragLineDCompat Source #

Arguments

:: Int

line number

-> String

file name

-> Maybe DecQ 

Backward compatible version of pragLineD. Returns Nothing if line pragmas are not suported.

Strictness annotations

Type simplification

resolveTypeSynonyms :: Type -> Q Type Source #

Expand all of the type synonyms in a type.

Note that this function will drop parentheses as a side effect.

resolveKindSynonyms :: Kind -> Q Kind Source #

Expand all of the type synonyms in a Kind.

resolvePredSynonyms :: Pred -> Q Pred Source #

Expand all of the type synonyms in a Pred.

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.

tvKind :: TyVarBndr -> Kind Source #

Extract the kind from a TyVarBndr. Assumes PlainTV has kind *.

datatypeType :: DatatypeInfo -> Type Source #

Construct a Type using the datatype's type constructor and type parameters. Kind signatures are removed.