th-abstraction-0.4.5.0: Nicer interface for reified information about data types
CopyrightEric Mertens 2020
LicenseISC
Maintaineremertens@gmail.com
Safe HaskellSafe
LanguageHaskell2010

Language.Haskell.TH.Datatype.TyVarBndr

Description

This module provides a backwards-compatible API for constructing and manipulating TyVarBndrs across multiple versions of the template-haskell package.

Synopsis

TyVarBndr-related types

type TyVarBndr_ flag = TyVarBndr flag Source #

A type synonym for TyVarBndr. This is the recommended way to refer to TyVarBndrs if you wish to achieve backwards compatibility with older versions of template-haskell, where TyVarBndr lacked a flag type parameter representing its specificity (if it has one).

data Specificity #

Instances

Instances details
Data Specificity 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

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

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

toConstr :: Specificity -> Constr #

dataTypeOf :: Specificity -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Specificity 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Specificity :: Type -> Type #

Show Specificity 
Instance details

Defined in Language.Haskell.TH.Syntax

Eq Specificity 
Instance details

Defined in Language.Haskell.TH.Syntax

Ord Specificity 
Instance details

Defined in Language.Haskell.TH.Syntax

PprFlag Specificity 
Instance details

Defined in Language.Haskell.TH.Ppr

type Rep Specificity 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep Specificity = D1 ('MetaData "Specificity" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "SpecifiedSpec" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InferredSpec" 'PrefixI 'False) (U1 :: Type -> Type))

Constructing TyVarBndrs

flag-polymorphic

plainTVFlag :: Name -> flag -> TyVarBndr_ flag Source #

Construct a PlainTV with the given flag.

kindedTVFlag :: Name -> flag -> Kind -> TyVarBndr_ flag Source #

Construct a KindedTV with the given flag.

TyVarBndrUnit

TyVarBndrSpec

Constructing Specificity

Modifying TyVarBndrs

elimTV :: (Name -> r) -> (Name -> Kind -> r) -> TyVarBndr_ flag -> r Source #

Case analysis for a TyVarBndr. If the value is a PlainTV n _, apply the first function to n; if it is KindedTV n _ k, apply the second function to n and k.

mapTV :: (Name -> Name) -> (flag -> flag') -> (Kind -> Kind) -> TyVarBndr_ flag -> TyVarBndr_ flag' Source #

Map over the components of a TyVarBndr.

mapTVName :: (Name -> Name) -> TyVarBndr_ flag -> TyVarBndr_ flag Source #

Map over the Name of a TyVarBndr.

mapTVFlag :: (flag -> flag') -> TyVarBndr_ flag -> TyVarBndr_ flag' Source #

Map over the flag of a TyVarBndr.

mapTVKind :: (Kind -> Kind) -> TyVarBndr_ flag -> TyVarBndr_ flag Source #

Map over the Kind of a TyVarBndr.

traverseTV :: Applicative f => (Name -> f Name) -> (flag -> f flag') -> (Kind -> f Kind) -> TyVarBndr_ flag -> f (TyVarBndr_ flag') Source #

Traverse the components of a TyVarBndr.

traverseTVName :: Functor f => (Name -> f Name) -> TyVarBndr_ flag -> f (TyVarBndr_ flag) Source #

Traverse the Name of a TyVarBndr.

traverseTVFlag :: Applicative f => (flag -> f flag') -> TyVarBndr_ flag -> f (TyVarBndr_ flag') Source #

Traverse the flag of a TyVarBndr.

traverseTVKind :: Applicative f => (Kind -> f Kind) -> TyVarBndr_ flag -> f (TyVarBndr_ flag) Source #

Traverse the Kind of a TyVarBndr.

mapMTV :: Monad m => (Name -> m Name) -> (flag -> m flag') -> (Kind -> m Kind) -> TyVarBndr_ flag -> m (TyVarBndr_ flag') Source #

Map over the components of a TyVarBndr in a monadic fashion.

This is the same as traverseTV, but with a Monad constraint. This is mainly useful for use with old versions of base where Applicative was not a superclass of Monad.

mapMTVName :: Monad m => (Name -> m Name) -> TyVarBndr_ flag -> m (TyVarBndr_ flag) Source #

Map over the Name of a TyVarBndr in a monadic fashion.

This is the same as traverseTVName, but with a Monad constraint. This is mainly useful for use with old versions of base where Applicative was not a superclass of Monad.

mapMTVFlag :: Monad m => (flag -> m flag') -> TyVarBndr_ flag -> m (TyVarBndr_ flag') Source #

Map over the flag of a TyVarBndr in a monadic fashion.

This is the same as traverseTVFlag, but with a Monad constraint. This is mainly useful for use with old versions of base where Applicative was not a superclass of Monad.

mapMTVKind :: Monad m => (Kind -> m Kind) -> TyVarBndr_ flag -> m (TyVarBndr_ flag) Source #

Map over the Kind of a TyVarBndr in a monadic fashion.

This is the same as traverseTVKind, but with a Monad constraint. This is mainly useful for use with old versions of base where Applicative was not a superclass of Monad.

changeTVFlags :: newFlag -> [TyVarBndr_ oldFlag] -> [TyVarBndr_ newFlag] Source #

Set the flag in a list of TyVarBndrs. This is often useful in contexts where one needs to re-use a list of TyVarBndrs from one flag setting to another flag setting. For example, in order to re-use the TyVarBndrs bound by a DataD in a ForallT, one can do the following:

case x of
  DataD _ _ tvbs _ _ _ ->
    ForallT (changeTVFlags SpecifiedSpec tvbs) ...

Properties of TyVarBndrs

tvName :: TyVarBndr_ flag -> Name Source #

Extract the type variable name from a TyVarBndr, ignoring the kind signature if one exists.

tvKind :: TyVarBndr_ flag -> Kind Source #

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