template-haskell-2.12.0.0: Support library for Template Haskell

Safe HaskellSafe
LanguageHaskell2010

Language.Haskell.TH.Lib

Contents

Description

TH.Lib contains lots of useful helper functions for generating and manipulating Template Haskell terms

Synopsis

Library functions

Abbreviations

type InfoQ = Q Info #

type ExpQ = Q Exp #

type TExpQ a = Q (TExp a) #

type DecQ = Q Dec #

type DecsQ = Q [Dec] #

type ConQ = Q Con #

type TypeQ = Q Type #

type TyLitQ = Q TyLit #

type CxtQ = Q Cxt #

type PredQ = Q Pred #

type MatchQ = Q Match #

type ClauseQ = Q Clause #

type BodyQ = Q Body #

type GuardQ = Q Guard #

type StmtQ = Q Stmt #

type RangeQ = Q Range #

type BangQ = Q Bang #

type PatQ = Q Pat #

Constructors lifted to Q

Literals

charL :: Char -> Lit #

Patterns

litP :: Lit -> PatQ #

varP :: Name -> PatQ #

tupP :: [PatQ] -> PatQ #

conP :: Name -> [PatQ] -> PatQ #

uInfixP :: PatQ -> Name -> PatQ -> PatQ #

infixP :: PatQ -> Name -> PatQ -> PatQ #

asP :: Name -> PatQ -> PatQ #

recP :: Name -> [FieldPatQ] -> PatQ #

listP :: [PatQ] -> PatQ #

sigP :: PatQ -> TypeQ -> PatQ #

viewP :: ExpQ -> PatQ -> PatQ #

Pattern Guards

guardedB :: [Q (Guard, Exp)] -> BodyQ #

normalGE :: ExpQ -> ExpQ -> Q (Guard, Exp) #

patG :: [StmtQ] -> GuardQ #

patGE :: [StmtQ] -> ExpQ -> Q (Guard, Exp) #

match :: PatQ -> BodyQ -> [DecQ] -> MatchQ #

Use with caseE

clause :: [PatQ] -> BodyQ -> [DecQ] -> ClauseQ #

Use with funD

Expressions

dyn :: String -> ExpQ #

Dynamically binding a variable (unhygenic)

varE :: Name -> ExpQ #

conE :: Name -> ExpQ #

litE :: Lit -> ExpQ #

appE :: ExpQ -> ExpQ -> ExpQ #

uInfixE :: ExpQ -> ExpQ -> ExpQ -> ExpQ #

staticE :: ExpQ -> ExpQ #

staticE x = [| static x |]

infixApp :: ExpQ -> ExpQ -> ExpQ -> ExpQ #

lamE :: [PatQ] -> ExpQ -> ExpQ #

lam1E :: PatQ -> ExpQ -> ExpQ #

Single-arg lambda

tupE :: [ExpQ] -> ExpQ #

condE :: ExpQ -> ExpQ -> ExpQ -> ExpQ #

multiIfE :: [Q (Guard, Exp)] -> ExpQ #

letE :: [DecQ] -> ExpQ -> ExpQ #

caseE :: ExpQ -> [MatchQ] -> ExpQ #

appsE :: [ExpQ] -> ExpQ #

listE :: [ExpQ] -> ExpQ #

sigE :: ExpQ -> TypeQ -> ExpQ #

recConE :: Name -> [Q (Name, Exp)] -> ExpQ #

recUpdE :: ExpQ -> [Q (Name, Exp)] -> ExpQ #

fieldExp :: Name -> ExpQ -> Q (Name, Exp) #

Ranges

Ranges with more indirection

Statements

doE :: [StmtQ] -> ExpQ #

compE :: [StmtQ] -> ExpQ #

bindS :: PatQ -> ExpQ -> StmtQ #

letS :: [DecQ] -> StmtQ #

parS :: [[StmtQ]] -> StmtQ #

Types

sigT :: TypeQ -> Kind -> TypeQ #

Type literals

Strictness

isStrict :: Q Strict #

Deprecated: Use bang. See https://ghc.haskell.org/trac/ghc/wiki/Migration/8.0. Example usage: 'bang noSourceUnpackedness sourceStrict'

notStrict :: Q Strict #

Deprecated: Use bang. See https://ghc.haskell.org/trac/ghc/wiki/Migration/8.0. Example usage: 'bang noSourceUnpackedness noSourceStrictness'

unpacked :: Q Strict #

Deprecated: Use bang. See https://ghc.haskell.org/trac/ghc/wiki/Migration/8.0. Example usage: 'bang sourceUnpack sourceStrict'

strictType :: Q Strict -> TypeQ -> StrictTypeQ #

Deprecated: As of template-haskell-2.11.0.0, StrictType has been replaced by BangType. Please use bangType instead.

varStrictType :: Name -> StrictTypeQ -> VarStrictTypeQ #

Deprecated: As of template-haskell-2.11.0.0, VarStrictType has been replaced by VarBangType. Please use varBangType instead.

Class Contexts

cxt :: [PredQ] -> CxtQ #

classP :: Name -> [Q Type] -> Q Pred #

Deprecated: As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please use conT and appT.

equalP :: TypeQ -> TypeQ -> PredQ #

Deprecated: As of template-haskell-2.10, constraint predicates (Pred) are just types (Type), in keeping with ConstraintKinds. Please see equalityT.

Constructors

infixC :: Q (Bang, Type) -> Name -> Q (Bang, Type) -> ConQ #

gadtC :: [Name] -> [StrictTypeQ] -> TypeQ -> ConQ #

Kinds

varK :: Name -> Kind #

conK :: Name -> Kind #

appK :: Kind -> Kind -> Kind #

Type variable binders

Roles

nominalR :: Role #

phantomR :: Role #

inferR :: Role #

Top Level Declarations

Data

valD :: PatQ -> BodyQ -> [DecQ] -> DecQ #

funD :: Name -> [ClauseQ] -> DecQ #

dataD :: CxtQ -> Name -> [TyVarBndr] -> Maybe Kind -> [ConQ] -> [DerivClauseQ] -> DecQ #

data DerivClause #

A single deriving clause at the end of a datatype.

Constructors

DerivClause (Maybe DerivStrategy) Cxt
{ deriving stock (Eq, Ord) }

Instances

Eq DerivClause # 
Data DerivClause # 

Methods

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

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

toConstr :: DerivClause -> Constr Source #

dataTypeOf :: DerivClause -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord DerivClause # 
Show DerivClause # 
Generic DerivClause # 

Associated Types

type Rep DerivClause :: * -> * Source #

type Rep DerivClause # 

data DerivStrategy #

What the user explicitly requests when deriving an instance.

Constructors

StockStrategy

A "standard" derived instance

AnyclassStrategy
-XDeriveAnyClass
NewtypeStrategy
-XGeneralizedNewtypeDeriving

Instances

Eq DerivStrategy # 
Data DerivStrategy # 

Methods

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

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

toConstr :: DerivStrategy -> Constr Source #

dataTypeOf :: DerivStrategy -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord DerivStrategy # 
Show DerivStrategy # 
Generic DerivStrategy # 
type Rep DerivStrategy # 
type Rep DerivStrategy = D1 * (MetaData "DerivStrategy" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) * (C1 * (MetaCons "StockStrategy" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "AnyclassStrategy" PrefixI False) (U1 *)) (C1 * (MetaCons "NewtypeStrategy" PrefixI False) (U1 *))))

Class

classD :: CxtQ -> Name -> [TyVarBndr] -> [FunDep] -> [DecQ] -> DecQ #

instanceD :: CxtQ -> TypeQ -> [DecQ] -> DecQ #

data Overlap #

Varieties of allowed instance overlap.

Constructors

Overlappable

May be overlapped by more specific instances

Overlapping

May overlap a more general instance

Overlaps

Both Overlapping and Overlappable

Incoherent

Both Overlappable and Overlappable, and pick an arbitrary one if multiple choices are available.

Instances

Eq Overlap # 

Methods

(==) :: Overlap -> Overlap -> Bool #

(/=) :: Overlap -> Overlap -> Bool #

Data Overlap # 

Methods

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

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

toConstr :: Overlap -> Constr Source #

dataTypeOf :: Overlap -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord Overlap # 
Show Overlap # 
Generic Overlap # 

Associated Types

type Rep Overlap :: * -> * Source #

type Rep Overlap # 
type Rep Overlap = D1 * (MetaData "Overlap" "Language.Haskell.TH.Syntax" "template-haskell" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Overlappable" PrefixI False) (U1 *)) (C1 * (MetaCons "Overlapping" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Overlaps" PrefixI False) (U1 *)) (C1 * (MetaCons "Incoherent" PrefixI False) (U1 *))))

sigD :: Name -> TypeQ -> DecQ #

Role annotations

roleAnnotD :: Name -> [Role] -> DecQ #

Type Family / Data Family

openTypeFamilyD :: Name -> [TyVarBndr] -> FamilyResultSig -> Maybe InjectivityAnn -> DecQ #

closedTypeFamilyD :: Name -> [TyVarBndr] -> FamilyResultSig -> Maybe InjectivityAnn -> [TySynEqnQ] -> DecQ #

dataInstD :: CxtQ -> Name -> [TypeQ] -> Maybe Kind -> [ConQ] -> [DerivClauseQ] -> DecQ #

familyNoKindD :: FamFlavour -> Name -> [TyVarBndr] -> DecQ #

Deprecated: This function will be removed in the next stable release. Use openTypeFamilyD/dataFamilyD instead.

familyKindD :: FamFlavour -> Name -> [TyVarBndr] -> Kind -> DecQ #

Deprecated: This function will be removed in the next stable release. Use openTypeFamilyD/dataFamilyD instead.

closedTypeFamilyNoKindD :: Name -> [TyVarBndr] -> [TySynEqnQ] -> DecQ #

Deprecated: This function will be removed in the next stable release. Use closedTypeFamilyD instead.

closedTypeFamilyKindD :: Name -> [TyVarBndr] -> Kind -> [TySynEqnQ] -> DecQ #

Deprecated: This function will be removed in the next stable release. Use closedTypeFamilyD instead.

injectivityAnn :: Name -> [Name] -> InjectivityAnn #

Fixity

infixLD :: Int -> Name -> DecQ #

infixRD :: Int -> Name -> DecQ #

infixND :: Int -> Name -> DecQ #

Foreign Function Interface (FFI)

Functional dependencies

funDep :: [Name] -> [Name] -> FunDep #

Pragmas

Pattern Synonyms

patSynD :: Name -> PatSynArgsQ -> PatSynDirQ -> PatQ -> DecQ #

Pattern synonym declaration

patSynSigD :: Name -> TypeQ -> DecQ #

Pattern synonym type signature

Reify

thisModule :: Q Module #

Return the Module at the place of splicing. Can be used as an input for reifyModule.