template-haskell-2.19.0.0: Support library for Template Haskell
Safe HaskellSafe
LanguageHaskell2010

Language.Haskell.TH.Lib

Description

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

Synopsis

Library functions

Abbreviations

type ExpQ = Q Exp Source #

type TExpQ a = Q (TExp a) Source #

Representation-polymorphic since template-haskell-2.17.0.0.

type DecQ = Q Dec Source #

type DecsQ = Q [Dec] Source #

type ConQ = Q Con Source #

type CxtQ = Q Cxt Source #

type PatQ = Q Pat Source #

Constructors lifted to Q

Literals

mkBytes Source #

Arguments

:: ForeignPtr Word8

Pointer to the data

-> Word

Offset from the pointer

-> Word

Number of bytes

-> Bytes 

Create a Bytes datatype representing raw bytes to be embedded into the program/library binary.

Since: template-haskell-2.16.0.0

Patterns

litP :: Quote m => Lit -> m Pat Source #

varP :: Quote m => Name -> m Pat Source #

tupP :: Quote m => [m Pat] -> m Pat Source #

unboxedTupP :: Quote m => [m Pat] -> m Pat Source #

conP :: Quote m => Name -> [m Pat] -> m Pat Source #

uInfixP :: Quote m => m Pat -> Name -> m Pat -> m Pat Source #

parensP :: Quote m => m Pat -> m Pat Source #

infixP :: Quote m => m Pat -> Name -> m Pat -> m Pat Source #

tildeP :: Quote m => m Pat -> m Pat Source #

bangP :: Quote m => m Pat -> m Pat Source #

asP :: Quote m => Name -> m Pat -> m Pat Source #

wildP :: Quote m => m Pat Source #

recP :: Quote m => Name -> [m FieldPat] -> m Pat Source #

listP :: Quote m => [m Pat] -> m Pat Source #

sigP :: Quote m => m Pat -> m Type -> m Pat Source #

viewP :: Quote m => m Exp -> m Pat -> m Pat Source #

fieldPat :: Quote m => Name -> m Pat -> m FieldPat Source #

Pattern Guards

normalB :: Quote m => m Exp -> m Body Source #

guardedB :: Quote m => [m (Guard, Exp)] -> m Body Source #

normalG :: Quote m => m Exp -> m Guard Source #

normalGE :: Quote m => m Exp -> m Exp -> m (Guard, Exp) Source #

patG :: Quote m => [m Stmt] -> m Guard Source #

patGE :: Quote m => [m Stmt] -> m Exp -> m (Guard, Exp) Source #

match :: Quote m => m Pat -> m Body -> [m Dec] -> m Match Source #

Use with caseE

clause :: Quote m => [m Pat] -> m Body -> [m Dec] -> m Clause Source #

Use with funD

Expressions

dyn :: Quote m => String -> m Exp Source #

Dynamically binding a variable (unhygenic)

varE :: Quote m => Name -> m Exp Source #

labelE :: Quote m => String -> m Exp Source #

conE :: Quote m => Name -> m Exp Source #

litE :: Quote m => Lit -> m Exp Source #

staticE :: Quote m => m Exp -> m Exp Source #

staticE x = [| static x |]

appE :: Quote m => m Exp -> m Exp -> m Exp Source #

appTypeE :: Quote m => m Exp -> m Type -> m Exp Source #

uInfixE :: Quote m => m Exp -> m Exp -> m Exp -> m Exp Source #

parensE :: Quote m => m Exp -> m Exp Source #

infixE :: Quote m => Maybe (m Exp) -> m Exp -> Maybe (m Exp) -> m Exp Source #

infixApp :: Quote m => m Exp -> m Exp -> m Exp -> m Exp Source #

sectionL :: Quote m => m Exp -> m Exp -> m Exp Source #

sectionR :: Quote m => m Exp -> m Exp -> m Exp Source #

lamE :: Quote m => [m Pat] -> m Exp -> m Exp Source #

lam1E :: Quote m => m Pat -> m Exp -> m Exp Source #

Single-arg lambda

lamCaseE :: Quote m => [m Match] -> m Exp Source #

Lambda-case (case)

lamCasesE :: Quote m => [m Clause] -> m Exp Source #

Lambda-cases (cases)

tupE :: Quote m => [m Exp] -> m Exp Source #

unboxedTupE :: Quote m => [m Exp] -> m Exp Source #

condE :: Quote m => m Exp -> m Exp -> m Exp -> m Exp Source #

multiIfE :: Quote m => [m (Guard, Exp)] -> m Exp Source #

letE :: Quote m => [m Dec] -> m Exp -> m Exp Source #

caseE :: Quote m => m Exp -> [m Match] -> m Exp Source #

appsE :: Quote m => [m Exp] -> m Exp Source #

listE :: Quote m => [m Exp] -> m Exp Source #

sigE :: Quote m => m Exp -> m Type -> m Exp Source #

recConE :: Quote m => Name -> [m (Name, Exp)] -> m Exp Source #

recUpdE :: Quote m => m Exp -> [m (Name, Exp)] -> m Exp Source #

fieldExp :: Quote m => Name -> m Exp -> m (Name, Exp) Source #

getFieldE :: Quote m => m Exp -> String -> m Exp Source #

Ranges

fromE :: Quote m => m Exp -> m Exp Source #

fromThenE :: Quote m => m Exp -> m Exp -> m Exp Source #

fromToE :: Quote m => m Exp -> m Exp -> m Exp Source #

fromThenToE :: Quote m => m Exp -> m Exp -> m Exp -> m Exp Source #

Ranges with more indirection

arithSeqE :: Quote m => m Range -> m Exp Source #

fromR :: Quote m => m Exp -> m Range Source #

fromThenR :: Quote m => m Exp -> m Exp -> m Range Source #

fromToR :: Quote m => m Exp -> m Exp -> m Range Source #

fromThenToR :: Quote m => m Exp -> m Exp -> m Exp -> m Range Source #

Statements

doE :: Quote m => [m Stmt] -> m Exp Source #

mdoE :: Quote m => [m Stmt] -> m Exp Source #

compE :: Quote m => [m Stmt] -> m Exp Source #

bindS :: Quote m => m Pat -> m Exp -> m Stmt Source #

letS :: Quote m => [m Dec] -> m Stmt Source #

noBindS :: Quote m => m Exp -> m Stmt Source #

parS :: Quote m => [[m Stmt]] -> m Stmt Source #

recS :: Quote m => [m Stmt] -> m Stmt Source #

Types

forallVisT :: Quote m => [m (TyVarBndr ())] -> m Type -> m Type Source #

varT :: Quote m => Name -> m Type Source #

conT :: Quote m => Name -> m Type Source #

appT :: Quote m => m Type -> m Type -> m Type Source #

appKindT :: Quote m => m Type -> m Kind -> m Type Source #

infixT :: Quote m => m Type -> Name -> m Type -> m Type Source #

uInfixT :: Quote m => m Type -> Name -> m Type -> m Type Source #

promotedInfixT :: Quote m => m Type -> Name -> m Type -> m Type Source #

promotedUInfixT :: Quote m => m Type -> Name -> m Type -> m Type Source #

parensT :: Quote m => m Type -> m Type Source #

listT :: Quote m => m Type Source #

tupleT :: Quote m => Int -> m Type Source #

sigT :: Quote m => m Type -> Kind -> m Type Source #

litT :: Quote m => m TyLit -> m Type Source #

Type literals

Strictness

isStrict :: Quote m => m Strict Source #

Deprecated: Use bang. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. Example usage: 'bang noSourceUnpackedness sourceStrict'

notStrict :: Quote m => m Strict Source #

Deprecated: Use bang. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. Example usage: 'bang noSourceUnpackedness noSourceStrictness'

unpacked :: Quote m => m Strict Source #

Deprecated: Use bang. See https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. Example usage: 'bang sourceUnpack sourceStrict'

bangType :: Quote m => m Bang -> m Type -> m BangType Source #

strictType :: Quote m => m Strict -> m Type -> m StrictType Source #

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

varStrictType :: Quote m => Name -> m StrictType -> m VarStrictType Source #

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

Class Contexts

cxt :: Quote m => [m Pred] -> m Cxt Source #

classP :: Quote m => Name -> [m Type] -> m Pred Source #

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

equalP :: Quote m => m Type -> m Type -> m Pred Source #

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

Constructors

normalC :: Quote m => Name -> [m BangType] -> m Con Source #

recC :: Quote m => Name -> [m VarBangType] -> m Con Source #

infixC :: Quote m => m (Bang, Type) -> Name -> m (Bang, Type) -> m Con Source #

forallC :: Quote m => [TyVarBndr Specificity] -> m Cxt -> m Con -> m Con Source #

gadtC :: Quote m => [Name] -> [m StrictType] -> m Type -> m Con Source #

recGadtC :: Quote m => [Name] -> [m VarStrictType] -> m Type -> m Con Source #

Kinds

Type variable binders

Roles

Top Level Declarations

Data

valD :: Quote m => m Pat -> m Body -> [m Dec] -> m Dec Source #

funD :: Quote m => Name -> [m Clause] -> m Dec Source #

tySynD :: Quote m => Name -> [TyVarBndr ()] -> m Type -> m Dec Source #

dataD :: Quote m => m Cxt -> Name -> [TyVarBndr ()] -> Maybe Kind -> [m Con] -> [m DerivClause] -> m Dec Source #

newtypeD :: Quote m => m Cxt -> Name -> [TyVarBndr ()] -> Maybe Kind -> m Con -> [m DerivClause] -> m Dec Source #

data DerivClause Source #

A single deriving clause at the end of a datatype.

Constructors

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

Instances

Instances details
Data DerivClause Source # 
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) -> 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 :: forall r r'. (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 #

Generic DerivClause Source # 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivClause :: Type -> Type Source #

Show DerivClause Source # 
Instance details

Defined in Language.Haskell.TH.Syntax

Eq DerivClause Source # 
Instance details

Defined in Language.Haskell.TH.Syntax

Ord DerivClause Source # 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep DerivClause Source # 
Instance details

Defined in Language.Haskell.TH.Syntax

data DerivStrategy Source #

What the user explicitly requests when deriving an instance.

Constructors

StockStrategy

A "standard" derived instance

AnyclassStrategy
-XDeriveAnyClass
NewtypeStrategy
-XGeneralizedNewtypeDeriving
ViaStrategy Type
-XDerivingVia

Instances

Instances details
Data DerivStrategy Source # 
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) -> 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 :: forall r r'. (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 #

Generic DerivStrategy Source # 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivStrategy :: Type -> Type Source #

Show DerivStrategy Source # 
Instance details

Defined in Language.Haskell.TH.Syntax

Eq DerivStrategy Source # 
Instance details

Defined in Language.Haskell.TH.Syntax

Ord DerivStrategy Source # 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep DerivStrategy Source # 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep DerivStrategy = D1 ('MetaData "DerivStrategy" "Language.Haskell.TH.Syntax" "template-haskell" 'False) ((C1 ('MetaCons "StockStrategy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AnyclassStrategy" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NewtypeStrategy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ViaStrategy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))))

Class

classD :: Quote m => m Cxt -> Name -> [TyVarBndr ()] -> [FunDep] -> [m Dec] -> m Dec Source #

instanceD :: Quote m => m Cxt -> m Type -> [m Dec] -> m Dec Source #

instanceWithOverlapD :: Quote m => Maybe Overlap -> m Cxt -> m Type -> [m Dec] -> m Dec Source #

data Overlap Source #

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 Overlapping and Overlappable, and pick an arbitrary one if multiple choices are available.

Instances

Instances details
Data Overlap Source # 
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) -> 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 :: forall r r'. (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 #

Generic Overlap Source # 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Overlap :: Type -> Type Source #

Show Overlap Source # 
Instance details

Defined in Language.Haskell.TH.Syntax

Eq Overlap Source # 
Instance details

Defined in Language.Haskell.TH.Syntax

Ord Overlap Source # 
Instance details

Defined in Language.Haskell.TH.Syntax

type Rep Overlap Source # 
Instance details

Defined in Language.Haskell.TH.Syntax

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

sigD :: Quote m => Name -> m Type -> m Dec Source #

kiSigD :: Quote m => Name -> m Kind -> m Dec Source #

standaloneDerivD :: Quote m => m Cxt -> m Type -> m Dec Source #

defaultSigD :: Quote m => Name -> m Type -> m Dec Source #

Role annotations

roleAnnotD :: Quote m => Name -> [Role] -> m Dec Source #

Type Family / Data Family

dataFamilyD :: Quote m => Name -> [TyVarBndr ()] -> Maybe Kind -> m Dec Source #

dataInstD :: Quote m => m Cxt -> Name -> [m Type] -> Maybe Kind -> [m Con] -> [m DerivClause] -> m Dec Source #

newtypeInstD :: Quote m => m Cxt -> Name -> [m Type] -> Maybe Kind -> m Con -> [m DerivClause] -> m Dec Source #

tySynEqn :: Quote m => Maybe [TyVarBndr ()] -> m Type -> m Type -> m TySynEqn Source #

Fixity

infixLD :: Quote m => Int -> Name -> m Dec Source #

infixRD :: Quote m => Int -> Name -> m Dec Source #

infixND :: Quote m => Int -> Name -> m Dec Source #

Default declaration

defaultD :: Quote m => [m Type] -> m Dec Source #

Foreign Function Interface (FFI)

forImpD :: Quote m => Callconv -> Safety -> String -> Name -> m Type -> m Dec Source #

Functional dependencies

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

Pragmas

pragSpecD :: Quote m => Name -> m Type -> Phases -> m Dec Source #

pragSpecInlD :: Quote m => Name -> m Type -> Inline -> Phases -> m Dec Source #

pragRuleD :: Quote m => String -> [m RuleBndr] -> m Exp -> m Exp -> Phases -> m Dec Source #

pragAnnD :: Quote m => AnnTarget -> m Exp -> m Dec Source #

pragLineD :: Quote m => Int -> String -> m Dec Source #

Pattern Synonyms

patSynD :: Quote m => Name -> m PatSynArgs -> m PatSynDir -> m Pat -> m Dec Source #

Pattern synonym declaration

patSynSigD :: Quote m => Name -> m Type -> m Dec Source #

Pattern synonym type signature

Implicit Parameters

implicitParamBindD :: Quote m => String -> m Exp -> m Dec Source #

Implicit parameter binding declaration. Can only be used in let and where clauses which consist entirely of implicit bindings.

Reify

thisModule :: Q Module Source #

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

Documentation

withDecDoc :: String -> Q Dec -> Q Dec Source #

Attaches Haddock documentation to the declaration provided. Unlike putDoc, the names do not need to be in scope when calling this function so it can be used for quoted declarations and anything else currently being spliced. Not all declarations can have documentation attached to them. For those that can't, withDecDoc will return it unchanged without any side effects.

withDecsDoc :: String -> Q [Dec] -> Q [Dec] Source #

Variant of withDecDoc that applies the same documentation to multiple declarations. Useful for documenting quoted declarations.

funD_doc Source #

Arguments

:: Name 
-> [Q Clause] 
-> Maybe String

Documentation to attach to function

-> [Maybe String]

Documentation to attach to arguments

-> Q Dec 

Variant of funD that attaches Haddock documentation.

dataD_doc Source #

Arguments

:: Q Cxt 
-> Name 
-> [Q (TyVarBndr ())] 
-> Maybe (Q Kind) 
-> [(Q Con, Maybe String, [Maybe String])]

List of constructors, documentation for the constructor, and documentation for the arguments

-> [Q DerivClause] 
-> Maybe String

Documentation to attach to the data declaration

-> Q Dec 

Variant of dataD that attaches Haddock documentation.

newtypeD_doc Source #

Arguments

:: Q Cxt 
-> Name 
-> [Q (TyVarBndr ())] 
-> Maybe (Q Kind) 
-> (Q Con, Maybe String, [Maybe String])

The constructor, documentation for the constructor, and documentation for the arguments

-> [Q DerivClause] 
-> Maybe String

Documentation to attach to the newtype declaration

-> Q Dec 

Variant of newtypeD that attaches Haddock documentation.

dataInstD_doc Source #

Arguments

:: Q Cxt 
-> Maybe [Q (TyVarBndr ())] 
-> Q Type 
-> Maybe (Q Kind) 
-> [(Q Con, Maybe String, [Maybe String])]

List of constructors, documentation for the constructor, and documentation for the arguments

-> [Q DerivClause] 
-> Maybe String

Documentation to attach to the instance declaration

-> Q Dec 

Variant of dataInstD that attaches Haddock documentation.

newtypeInstD_doc Source #

Arguments

:: Q Cxt 
-> Maybe [Q (TyVarBndr ())] 
-> Q Type 
-> Maybe (Q Kind) 
-> (Q Con, Maybe String, [Maybe String])

The constructor, documentation for the constructor, and documentation for the arguments

-> [Q DerivClause] 
-> Maybe String

Documentation to attach to the instance declaration

-> Q Dec 

Variant of newtypeInstD that attaches Haddock documentation.

patSynD_doc Source #

Arguments

:: Name 
-> Q PatSynArgs 
-> Q PatSynDir 
-> Q Pat 
-> Maybe String

Documentation to attach to the pattern synonym

-> [Maybe String]

Documentation to attach to the pattern arguments

-> Q Dec 

Variant of patSynD that attaches Haddock documentation.