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

CopyrightEric Mertens 2017
LicenseISC
Maintaineremertens@gmail.com
Safe HaskellNone
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    = [ 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.

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.

Constructors

DatatypeInfo 

Fields

Instances

Eq DatatypeInfo Source # 
Data DatatypeInfo Source # 

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

Associated Types

type Rep DatatypeInfo :: * -> * #

type Rep DatatypeInfo Source # 

data ConstructorInfo Source #

Normalized information about constructors associated with newtypes and data types.

Constructors

ConstructorInfo 

Fields

Instances

Eq ConstructorInfo Source # 
Data ConstructorInfo Source # 

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 # 
Generic ConstructorInfo Source # 
TypeSubstitution ConstructorInfo Source # 
type Rep ConstructorInfo Source # 
type Rep ConstructorInfo = D1 (MetaData "ConstructorInfo" "Language.Haskell.TH.Datatype" "th-abstraction-0.2.1.0-IMJQYeyTtpo7IEtZBIMeEH" False) (C1 (MetaCons "ConstructorInfo" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "constructorName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Name)) ((:*:) (S1 (MetaSel (Just Symbol "constructorVars") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TyVarBndr])) (S1 (MetaSel (Just Symbol "constructorContext") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Cxt)))) ((:*:) (S1 (MetaSel (Just Symbol "constructorFields") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Type])) ((:*:) (S1 (MetaSel (Just Symbol "constructorStrictness") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FieldStrictness])) (S1 (MetaSel (Just Symbol "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 # 
Data DatatypeVariant Source # 

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 # 
Read DatatypeVariant Source # 
Show DatatypeVariant Source # 
Generic DatatypeVariant Source # 
type Rep DatatypeVariant Source # 
type Rep DatatypeVariant = D1 (MetaData "DatatypeVariant" "Language.Haskell.TH.Datatype" "th-abstraction-0.2.1.0-IMJQYeyTtpo7IEtZBIMeEH" False) ((:+:) ((:+:) (C1 (MetaCons "Datatype" PrefixI False) U1) (C1 (MetaCons "Newtype" PrefixI False) U1)) ((:+:) (C1 (MetaCons "DataInstance" PrefixI False) U1) (C1 (MetaCons "NewtypeInstance" PrefixI False) U1)))

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

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 # 
Show ConstructorVariant Source # 
Generic ConstructorVariant Source # 
type Rep ConstructorVariant Source # 
type Rep ConstructorVariant = D1 (MetaData "ConstructorVariant" "Language.Haskell.TH.Datatype" "th-abstraction-0.2.1.0-IMJQYeyTtpo7IEtZBIMeEH" False) ((:+:) (C1 (MetaCons "NormalConstructor" PrefixI False) U1) ((:+:) (C1 (MetaCons "InfixConstructor" PrefixI False) U1) (C1 (MetaCons "RecordConstructor" PrefixI False) (S1 (MetaSel (Nothing 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 Strict
notStrictAnnot = FieldStrictness UnspecifiedUnpackedness UnspecifiedStrictness
unpackedAnnot  = FieldStrictness Unpack Strict

Constructors

FieldStrictness 

Fields

Instances

Eq FieldStrictness Source # 
Data FieldStrictness Source # 

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 # 
Show FieldStrictness Source # 
Generic FieldStrictness Source # 
type Rep FieldStrictness Source # 

Normalization functions

reifyDatatype Source #

Arguments

:: Name

constructor

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

GADT constructors are normalized into datatypes with explicit equality constraints.

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.

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

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

Type variable manipulation

class TypeSubstitution a where Source #

Class for types that support type variable substitution.

Minimal complete definition

applySubstitution, freeVariables

Methods

applySubstitution :: Map Name Type -> a -> a Source #

Apply a type variable substitution

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)

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

Strictness annotations

Type simplification

resolveTypeSynonyms :: Type -> Q Type Source #

Expand all of the type synonyms in a type.

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.

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.