On this page
Language.Haskell.TH.Syntax
Copyright | (c) The University of Glasgow 2003 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | libraries@haskell.org |
Stability | experimental |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Contents
Description
Abstract syntax definitions for Template Haskell.
Instances
Constructors
ForallT [TyVarBndr Specificity] Cxt Type |
|
ForallVisT [TyVarBndr ()] Type |
|
AppT Type Type |
|
AppKindT Type Kind |
|
SigT Type Kind |
|
VarT Name |
|
ConT Name |
|
PromotedT Name |
|
InfixT Type Name Type |
|
UInfixT Type Name Type | |
PromotedInfixT Type Name Type |
|
PromotedUInfixT Type Name Type | |
ParensT Type |
|
TupleT Int |
|
UnboxedTupleT Int |
|
UnboxedSumT SumArity |
|
ArrowT |
|
MulArrowT | Generalised arrow type with multiplicity argument |
EqualityT |
|
ListT |
|
PromotedTupleT Int |
|
PromotedNilT |
|
PromotedConsT |
|
StarT |
|
ConstraintT |
|
LitT TyLit |
|
WildCardT |
|
ImplicitParamT String Type |
|
Instances
Obtained from reifyModule
and thisModule
.
Instances
Data Module Source | |
Defined in Language.Haskell.TH.Syntax Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Module -> c Module Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Module Source toConstr :: Module -> Constr Source dataTypeOf :: Module -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Module) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Module) Source gmapT :: (forall b. Data b => b -> b) -> Module -> Module Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Module -> r Source gmapQ :: (forall d. Data d => d -> u) -> Module -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> Module -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> Module -> m Module Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Module -> m Module Source |
|
Generic Module Source | |
Show Module Source | |
Eq Module Source | |
Ord Module Source | |
Defined in Language.Haskell.TH.Syntax |
|
Ppr Module Source | |
type Rep Module Source | |
Defined in Language.Haskell.TH.Syntax
type Rep Module = D1 ('MetaData "Module" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "Module" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PkgName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ModName)))
|
In PrimTyConI
, is the type constructor unlifted?
data DecidedStrictness Source
Unlike SourceStrictness
and SourceUnpackedness
, DecidedStrictness
refers to the strictness that the compiler chooses for a data constructor field, which may be different from what is written in source code. See reifyConStrictness
for more information.
Constructors
Instances
data SourceStrictness Source
Constructors
NoSourceStrictness |
|
SourceLazy |
|
SourceStrict |
|
Instances
data SourceUnpackedness Source
Constructors
NoSourceUnpackedness |
|
SourceNoUnpack |
|
SourceUnpack |
|
Instances
Constructors
Instances
Data Fixity Source | |
Defined in Language.Haskell.TH.Syntax Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Fixity -> c Fixity Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Fixity Source toConstr :: Fixity -> Constr Source dataTypeOf :: Fixity -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Fixity) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Fixity) Source gmapT :: (forall b. Data b => b -> b) -> Fixity -> Fixity Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Fixity -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Fixity -> r Source gmapQ :: (forall d. Data d => d -> u) -> Fixity -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> Fixity -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity Source |
|
Generic Fixity Source | |
Show Fixity Source | |
Eq Fixity Source | |
Ord Fixity Source | |
Defined in Language.Haskell.TH.Syntax |
|
type Rep Fixity Source | |
Defined in Language.Haskell.TH.Syntax
type Rep Fixity = D1 ('MetaData "Fixity" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "Fixity" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FixityDirection)))
|
A single data constructor.
The constructors for Con
can roughly be divided up into two categories: those for constructors with "vanilla" syntax (NormalC
, RecC
, and InfixC
), and those for constructors with GADT syntax (GadtC
and RecGadtC
). The ForallC
constructor, which quantifies additional type variables and class contexts, can surround either variety of constructor. However, the type variables that it quantifies are different depending on what constructor syntax is used:
- If a
ForallC
surrounds a constructor with vanilla syntax, then theForallC
will only quantify existential type variables. For example:
data Foo a = forall b. MkFoo a b
In MkFoo
, ForallC
will quantify b
, but not a
.
- If a
ForallC
surrounds a constructor with GADT syntax, then theForallC
will quantify all type variables used in the constructor. For example:
data Bar a b where
MkBar :: (a ~ b) => c -> MkBar a b
In MkBar
, ForallC
will quantify a
, b
, and c
.
Multiplicity annotations for data types are currently not supported in Template Haskell (i.e. all fields represented by Template Haskell will be linear).
Constructors
Instances
As of template-haskell-2.11.0.0
, Strict
has been replaced by Bang
.
Instances
class Monad m => Quote m where Source
The Quote
class implements the minimal interface which is necessary for desugaring quotations.
- The
Monad m
superclass is needed to stitch together the different AST fragments. newName
is used when desugaring binding structures such as lambdas to generate fresh names.
Therefore the type of an untyped quotation in GHC is `Quote m => m Exp`
For many years the type of a quotation was fixed to be `Q Exp` but by more precisely specifying the minimal interface it enables the Exp
to be extracted purely from the quotation without interacting with Q
.
Methods
newName :: String -> m Name Source
Generate a fresh name, which cannot be captured.
For example, this:
f = $(do
nm1 <- newName "x"
let nm2 = mkName "x"
return (LamE [VarP nm1] (LamE [VarP nm2] (VarE nm1)))
)
will produce the splice
f = \x0 -> \x -> x0
In particular, the occurrence VarE nm1
refers to the binding VarP nm1
, and is not captured by the binding VarP nm2
.
Although names generated by newName
cannot be captured, they can capture other names. For example, this:
g = $(do
nm1 <- newName "x"
let nm2 = mkName "x"
return (LamE [VarP nm2] (LamE [VarP nm1] (VarE nm2)))
)
will produce the splice
g = \x -> \x0 -> x0
since the occurrence VarE nm2
is captured by the innermost binding of x
, namely VarP nm1
.
Instances
Constructors
Loc | |
Fields
|
Instances
Data Loc Source | |
Defined in Language.Haskell.TH.Syntax Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Loc -> c Loc Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Loc Source toConstr :: Loc -> Constr Source dataTypeOf :: Loc -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Loc) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Loc) Source gmapT :: (forall b. Data b => b -> b) -> Loc -> Loc Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Loc -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Loc -> r Source gmapQ :: (forall d. Data d => d -> u) -> Loc -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> Loc -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> Loc -> m Loc Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Loc -> m Loc Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Loc -> m Loc Source |
|
Generic Loc Source | |
Show Loc Source | |
Eq Loc Source | |
Ord Loc Source | |
Ppr Loc Source | |
type Rep Loc Source | |
Defined in Language.Haskell.TH.Syntax
type Rep Loc = D1 ('MetaData "Loc" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "Loc" 'PrefixI 'True) ((S1 ('MetaSel ('Just "loc_filename") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "loc_package") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :*: (S1 ('MetaSel ('Just "loc_module") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Just "loc_start") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CharPos) :*: S1 ('MetaSel ('Just "loc_end") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CharPos)))))
|
Obtained from reify
in the Q
Monad.
Constructors
ClassI Dec [InstanceDec] | A class, with a list of its visible instances |
ClassOpI Name Type ParentName | A class method |
TyConI Dec | A "plain" type constructor. "Fancier" type constructors are returned using |
FamilyI Dec [InstanceDec] | A type or data family, with a list of its visible instances. A closed type family is returned with 0 instances. |
PrimTyConI Name Arity Unlifted | A "primitive" type constructor, which can't be expressed with a |
DataConI Name Type ParentName | A data constructor |
PatSynI Name PatSynType | A pattern synonym |
VarI Name Type (Maybe Dec) | A "value" variable (as opposed to a type variable, see The |
TyVarI Name Type | A type variable. The |
Instances
data ModuleInfo Source
Obtained from reifyModule
in the Q
Monad.
Constructors
ModuleInfo [Module] | Contains the import list of the module. |
Instances
type InstanceDec = Dec Source
InstanceDec
describes a single instance of a class or type function. It is just a Dec
, but guaranteed to be one of the following:
InstanceD
(with empty[Dec]
)DataInstD
orNewtypeInstD
(with empty derived[Name]
)TySynInstD
type ParentName = Name Source
In ClassOpI
and DataConI
, name of the parent class or type
In UnboxedSumE
and UnboxedSumP
, the number associated with a particular data constructor. SumAlt
s are one-indexed and should never exceed the value of its corresponding SumArity
. For example:
(#_|#)
hasSumAlt
1 (out of a totalSumArity
of 2)(#|_#)
hasSumAlt
2 (out of a totalSumArity
of 2)
In UnboxedSumE
, UnboxedSumT
, and UnboxedSumP
, the total number of SumAlt
s. For example, (#|#)
has a SumArity
of 2.
In PrimTyConI
, arity of the type constructor
Annotation target for reifyAnnotations
Constructors
Instances
Data AnnLookup Source | |
Defined in Language.Haskell.TH.Syntax Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnLookup -> c AnnLookup Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnLookup Source toConstr :: AnnLookup -> Constr Source dataTypeOf :: AnnLookup -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnLookup) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnLookup) Source gmapT :: (forall b. Data b => b -> b) -> AnnLookup -> AnnLookup Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnLookup -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnLookup -> r Source gmapQ :: (forall d. Data d => d -> u) -> AnnLookup -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnLookup -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnLookup -> m AnnLookup Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnLookup -> m AnnLookup Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnLookup -> m AnnLookup Source |
|
Generic AnnLookup Source | |
Show AnnLookup Source | |
Eq AnnLookup Source | |
Ord AnnLookup Source | |
Defined in Language.Haskell.TH.Syntax |
|
type Rep AnnLookup Source | |
Defined in Language.Haskell.TH.Syntax
type Rep AnnLookup = D1 ('MetaData "AnnLookup" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "AnnLookupModule" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Module)) :+: C1 ('MetaCons "AnnLookupName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)))
|
newtype TExp (a :: TYPE (r :: RuntimeRep)) Source
Represents an expression which has type a
. Built on top of Exp
, typed expressions allow for type-safe splicing via:
- typed quotes, written as
[|| ... ||]
where...
is an expression; if that expression has typea
, then the quotation has typeQ (TExp a)
- typed splices inside of typed quotes, written as
$$(...)
where...
is an arbitrary expression of typeQ (TExp a)
Traditional expression quotes and splices let us construct ill-typed expressions:
>>> fmap ppr $ runQ [| True == $( [| "foo" |] ) |]
GHC.Types.True GHC.Classes.== "foo"
>>> GHC.Types.True GHC.Classes.== "foo"
<interactive> error:
• Couldn't match expected type ‘Bool’ with actual type ‘[Char]’
• In the second argument of ‘(==)’, namely ‘"foo"’
In the expression: True == "foo"
In an equation for ‘it’: it = True == "foo"
With typed expressions, the type error occurs when constructing the Template Haskell expression:
>>> fmap ppr $ runQ [|| True == $$( [|| "foo" ||] ) ||]
<interactive> error:
• Couldn't match type ‘[Char]’ with ‘Bool’
Expected type: Q (TExp Bool)
Actual type: Q (TExp [Char])
• In the Template Haskell quotation [|| "foo" ||]
In the expression: [|| "foo" ||]
In the Template Haskell splice $$([|| "foo" ||])
Representation-polymorphic since template-haskell-2.16.0.0.
newtype Code m (a :: TYPE (r :: RuntimeRep)) Source
Constructors
Code | |
Fields
|
An abstract type representing names in the syntax tree.
Name
s can be constructed in several ways, which come with different name-capture guarantees (see Language.Haskell.TH.Syntax for an explanation of name capture):
- the built-in syntax
'f
and''T
can be used to construct names, The expression'f
gives aName
which refers to the valuef
currently in scope, and''T
gives aName
which refers to the typeT
currently in scope. These names can never be captured. lookupValueName
andlookupTypeName
are similar to'f
and''T
respectively, but theName
s are looked up at the point where the current splice is being run. These names can never be captured.newName
monadically generates a new name, which can never be captured.mkName
generates a capturable name.
Names constructed using newName
and mkName
may be used in bindings (such as let x = ...
or x -> ...
), but names constructed using lookupValueName
, lookupTypeName
, 'f
, ''T
may not.
Constructors
Instances
Data Name Source | |
Defined in Language.Haskell.TH.Syntax Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Name -> c Name Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Name Source toConstr :: Name -> Constr Source dataTypeOf :: Name -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Name) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Name) Source gmapT :: (forall b. Data b => b -> b) -> Name -> Name Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r Source gmapQ :: (forall d. Data d => d -> u) -> Name -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> Name -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> Name -> m Name Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name Source |
|
Generic Name Source | |
Show Name Source | |
Eq Name Source | |
Ord Name Source | |
Defined in Language.Haskell.TH.Syntax |
|
Ppr Name Source | |
type Rep Name Source | |
Defined in Language.Haskell.TH.Syntax
type Rep Name = D1 ('MetaData "Name" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "Name" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OccName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NameFlavour)))
|
Constructors
Instances
Data NameSpace Source | |
Defined in Language.Haskell.TH.Syntax Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NameSpace -> c NameSpace Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NameSpace Source toConstr :: NameSpace -> Constr Source dataTypeOf :: NameSpace -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NameSpace) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NameSpace) Source gmapT :: (forall b. Data b => b -> b) -> NameSpace -> NameSpace Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NameSpace -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NameSpace -> r Source gmapQ :: (forall d. Data d => d -> u) -> NameSpace -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> NameSpace -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> NameSpace -> m NameSpace Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NameSpace -> m NameSpace Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NameSpace -> m NameSpace Source |
|
Generic NameSpace Source | |
Show NameSpace Source | |
Eq NameSpace Source | |
Ord NameSpace Source | |
Defined in Language.Haskell.TH.Syntax |
|
type Rep NameSpace Source | |
Defined in Language.Haskell.TH.Syntax
type Rep NameSpace = D1 ('MetaData "NameSpace" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "VarName" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DataName" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TcClsName" 'PrefixI 'False) (U1 :: Type -> Type)))
|
Constructors
FunD Name [Clause] |
|
ValD Pat Body [Dec] |
|
DataD Cxt Name [TyVarBndr ()] (Maybe Kind) [Con] [DerivClause] |
|
NewtypeD Cxt Name [TyVarBndr ()] (Maybe Kind) Con [DerivClause] |
|
TySynD Name [TyVarBndr ()] Type |
|
ClassD Cxt Name [TyVarBndr ()] [FunDep] [Dec] |
|
InstanceD (Maybe Overlap) Cxt Type [Dec] |
|
SigD Name Type |
|
KiSigD Name Kind |
|
ForeignD Foreign |
|
InfixD Fixity Name |
|
DefaultD [Type] |
|
PragmaD | pragmas |
Fields
|
|
DataFamilyD | data families (may also appear in [Dec] of |
DataInstD Cxt (Maybe [TyVarBndr ()]) Type (Maybe Kind) [Con] [DerivClause] |
|
NewtypeInstD Cxt (Maybe [TyVarBndr ()]) Type (Maybe Kind) Con [DerivClause] |
|
TySynInstD TySynEqn |
|
OpenTypeFamilyD | open type families (may also appear in [Dec] of |
Fields
|
|
ClosedTypeFamilyD TypeFamilyHead [TySynEqn] |
|
RoleAnnotD Name [Role] |
|
StandaloneDerivD (Maybe DerivStrategy) Cxt Type |
|
DefaultSigD Name Type |
|
PatSynD | Pattern Synonyms |
Fields
|
|
PatSynSigD Name PatSynType | A pattern synonym's type signature. |
ImplicitParamBindD String Exp | Implicit parameter binding declaration. Can only be used in let and where clauses which consist entirely of implicit bindings. |
Instances
Instances
Data Clause Source | |
Defined in Language.Haskell.TH.Syntax Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Clause -> c Clause Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Clause Source toConstr :: Clause -> Constr Source dataTypeOf :: Clause -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Clause) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Clause) Source gmapT :: (forall b. Data b => b -> b) -> Clause -> Clause Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Clause -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Clause -> r Source gmapQ :: (forall d. Data d => d -> u) -> Clause -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> Clause -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> Clause -> m Clause Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Clause -> m Clause Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Clause -> m Clause Source |
|
Generic Clause Source | |
Show Clause Source | |
Eq Clause Source | |
Ord Clause Source | |
Defined in Language.Haskell.TH.Syntax |
|
Ppr Clause Source | |
type Rep Clause Source | |
Defined in Language.Haskell.TH.Syntax
type Rep Clause = D1 ('MetaData "Clause" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "Clause" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pat]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Body) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Dec]))))
|
Constructors
Bang SourceUnpackedness SourceStrictness |
|
Instances
Data Bang Source | |
Defined in Language.Haskell.TH.Syntax Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bang -> c Bang Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bang Source toConstr :: Bang -> Constr Source dataTypeOf :: Bang -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Bang) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bang) Source gmapT :: (forall b. Data b => b -> b) -> Bang -> Bang Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bang -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bang -> r Source gmapQ :: (forall d. Data d => d -> u) -> Bang -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> Bang -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bang -> m Bang Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bang -> m Bang Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bang -> m Bang Source |
|
Generic Bang Source | |
Show Bang Source | |
Eq Bang Source | |
Ord Bang Source | |
Defined in Language.Haskell.TH.Syntax |
|
Ppr Bang Source | |
type Rep Bang Source | |
Defined in Language.Haskell.TH.Syntax
type Rep Bang = D1 ('MetaData "Bang" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "Bang" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourceUnpackedness) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourceStrictness)))
|
Constructors
Instances
Data Callconv Source | |
Defined in Language.Haskell.TH.Syntax Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Callconv -> c Callconv Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Callconv Source toConstr :: Callconv -> Constr Source dataTypeOf :: Callconv -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Callconv) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Callconv) Source gmapT :: (forall b. Data b => b -> b) -> Callconv -> Callconv Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Callconv -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Callconv -> r Source gmapQ :: (forall d. Data d => d -> u) -> Callconv -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> Callconv -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> Callconv -> m Callconv Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Callconv -> m Callconv Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Callconv -> m Callconv Source |
|
Generic Callconv Source | |
Show Callconv Source | |
Eq Callconv Source | |
Ord Callconv Source | |
Defined in Language.Haskell.TH.Syntax |
|
type Rep Callconv Source | |
Defined in Language.Haskell.TH.Syntax
type Rep Callconv = D1 ('MetaData "Callconv" "Language.Haskell.TH.Syntax" "template-haskell" 'False) ((C1 ('MetaCons "CCall" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StdCall" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CApi" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Prim" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "JavaScript" 'PrefixI 'False) (U1 :: Type -> Type))))
|
Constructors
Instances
Data Safety Source | |
Defined in Language.Haskell.TH.Syntax Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Safety -> c Safety Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Safety Source toConstr :: Safety -> Constr Source dataTypeOf :: Safety -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Safety) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Safety) Source gmapT :: (forall b. Data b => b -> b) -> Safety -> Safety Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Safety -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Safety -> r Source gmapQ :: (forall d. Data d => d -> u) -> Safety -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> Safety -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> Safety -> m Safety Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Safety -> m Safety Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Safety -> m Safety Source |
|
Generic Safety Source | |
Show Safety Source | |
Eq Safety Source | |
Ord Safety Source | |
Defined in Language.Haskell.TH.Syntax |
|
type Rep Safety Source | |
Defined in Language.Haskell.TH.Syntax |
Constructors
Instances
Instances
Data Inline Source | |
Defined in Language.Haskell.TH.Syntax Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Inline -> c Inline Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Inline Source toConstr :: Inline -> Constr Source dataTypeOf :: Inline -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Inline) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Inline) Source gmapT :: (forall b. Data b => b -> b) -> Inline -> Inline Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Inline -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Inline -> r Source gmapQ :: (forall d. Data d => d -> u) -> Inline -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> Inline -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> Inline -> m Inline Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Inline -> m Inline Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Inline -> m Inline Source |
|
Generic Inline Source | |
Show Inline Source | |
Eq Inline Source | |
Ord Inline Source | |
Defined in Language.Haskell.TH.Syntax |
|
Ppr Inline Source | |
type Rep Inline Source | |
Defined in Language.Haskell.TH.Syntax |
Instances
Data RuleMatch Source | |
Defined in Language.Haskell.TH.Syntax Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RuleMatch -> c RuleMatch Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RuleMatch Source toConstr :: RuleMatch -> Constr Source dataTypeOf :: RuleMatch -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RuleMatch) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RuleMatch) Source gmapT :: (forall b. Data b => b -> b) -> RuleMatch -> RuleMatch Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RuleMatch -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RuleMatch -> r Source gmapQ :: (forall d. Data d => d -> u) -> RuleMatch -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> RuleMatch -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> RuleMatch -> m RuleMatch Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleMatch -> m RuleMatch Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RuleMatch -> m RuleMatch Source |
|
Generic RuleMatch Source | |
Show RuleMatch Source | |
Eq RuleMatch Source | |
Ord RuleMatch Source | |
Defined in Language.Haskell.TH.Syntax |
|
Ppr RuleMatch Source | |
type Rep RuleMatch Source | |
Constructors
Instances
Data Phases Source | |
Defined in Language.Haskell.TH.Syntax Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Phases -> c Phases Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Phases Source toConstr :: Phases -> Constr Source dataTypeOf :: Phases -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Phases) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Phases) Source gmapT :: (forall b. Data b => b -> b) -> Phases -> Phases Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Phases -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Phases -> r Source gmapQ :: (forall d. Data d => d -> u) -> Phases -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> Phases -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> Phases -> m Phases Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Phases -> m Phases Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Phases -> m Phases Source |
|
Generic Phases Source | |
Show Phases Source | |
Eq Phases Source | |
Ord Phases Source | |
Defined in Language.Haskell.TH.Syntax |
|
Ppr Phases Source | |
type Rep Phases Source | |
Defined in Language.Haskell.TH.Syntax
type Rep Phases = D1 ('MetaData "Phases" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "AllPhases" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FromPhase" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "BeforePhase" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))
|
Constructors
Instances
Constructors
Instances
Data AnnTarget Source | |
Defined in Language.Haskell.TH.Syntax Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnTarget -> c AnnTarget Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnTarget Source toConstr :: AnnTarget -> Constr Source dataTypeOf :: AnnTarget -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnTarget) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnTarget) Source gmapT :: (forall b. Data b => b -> b) -> AnnTarget -> AnnTarget Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnTarget -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnTarget -> r Source gmapQ :: (forall d. Data d => d -> u) -> AnnTarget -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnTarget -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnTarget -> m AnnTarget Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnTarget -> m AnnTarget Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnTarget -> m AnnTarget Source |
|
Generic AnnTarget Source | |
Show AnnTarget Source | |
Eq AnnTarget Source | |
Ord AnnTarget Source | |
Defined in Language.Haskell.TH.Syntax |
|
type Rep AnnTarget Source | |
Defined in Language.Haskell.TH.Syntax
type Rep AnnTarget = D1 ('MetaData "AnnTarget" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "ModuleAnnotation" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TypeAnnotation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :+: C1 ('MetaCons "ValueAnnotation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))))
|
Instances
Data FunDep Source | |
Defined in Language.Haskell.TH.Syntax Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FunDep -> c FunDep Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FunDep Source toConstr :: FunDep -> Constr Source dataTypeOf :: FunDep -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FunDep) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunDep) Source gmapT :: (forall b. Data b => b -> b) -> FunDep -> FunDep Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunDep -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunDep -> r Source gmapQ :: (forall d. Data d => d -> u) -> FunDep -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> FunDep -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> FunDep -> m FunDep Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FunDep -> m FunDep Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FunDep -> m FunDep Source |
|
Generic FunDep Source | |
Show FunDep Source | |
Eq FunDep Source | |
Ord FunDep Source | |
Defined in Language.Haskell.TH.Syntax |
|
Ppr FunDep Source | |
type Rep FunDep Source | |
Defined in Language.Haskell.TH.Syntax
type Rep FunDep = D1 ('MetaData "FunDep" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "FunDep" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name])))
|
One equation of a type family instance or closed type family. The arguments are the left-hand-side type and the right-hand-side result.
For instance, if you had the following type family:
type family Foo (a :: k) :: k where
forall k (a :: k). Foo @k a = a
The Foo @k a = a
equation would be represented as follows:
TySynEqn (Just [PlainTV k, KindedTV a (VarT k)])
(AppT (AppKindT (ConT ''Foo) (VarT k)) (VarT a))
(VarT a)
Instances
data TypeFamilyHead Source
Common elements of OpenTypeFamilyD
and ClosedTypeFamilyD
. By analogy with "head" for type classes and type class instances as defined in Type classes: an exploration of the design space, the TypeFamilyHead
is defined to be the elements of the declaration between type family
and where
.
Constructors
Instances
data FixityDirection Source
Instances
A pattern synonym's directionality.
Constructors
Instances
Data PatSynDir Source | |
Defined in Language.Haskell.TH.Syntax Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PatSynDir -> c PatSynDir Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PatSynDir Source toConstr :: PatSynDir -> Constr Source dataTypeOf :: PatSynDir -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PatSynDir) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PatSynDir) Source gmapT :: (forall b. Data b => b -> b) -> PatSynDir -> PatSynDir Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PatSynDir -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PatSynDir -> r Source gmapQ :: (forall d. Data d => d -> u) -> PatSynDir -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> PatSynDir -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> PatSynDir -> m PatSynDir Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynDir -> m PatSynDir Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PatSynDir -> m PatSynDir Source |
|
Generic PatSynDir Source | |
Show PatSynDir Source | |
Eq PatSynDir Source | |
Ord PatSynDir Source | |
Defined in Language.Haskell.TH.Syntax |
|
Ppr PatSynDir Source | |
type Rep PatSynDir Source | |
Defined in Language.Haskell.TH.Syntax
type Rep PatSynDir = D1 ('MetaData "PatSynDir" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "Unidir" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ImplBidir" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExplBidir" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Clause]))))
|
data PatSynArgs Source
A pattern synonym's argument type.
Constructors
PrefixPatSyn [Name] |
|
InfixPatSyn Name Name |
|
RecordPatSyn [Name] |
|
Instances
Constructors
VarE Name |
|
ConE Name |
|
LitE Lit |
|
AppE Exp Exp |
|
AppTypeE Exp Type |
|
InfixE (Maybe Exp) Exp (Maybe Exp) |
|
UInfixE Exp Exp Exp | |
ParensE Exp | |
LamE [Pat] Exp |
|
LamCaseE [Match] |
|
LamCasesE [Clause] |
|
TupE [Maybe Exp] | The translates to
|
UnboxedTupE [Maybe Exp] | The translates to
|
UnboxedSumE Exp SumAlt SumArity |
|
CondE Exp Exp Exp |
|
MultiIfE [(Guard, Exp)] |
|
LetE [Dec] Exp |
|
CaseE Exp [Match] |
|
DoE (Maybe ModName) [Stmt] |
|
MDoE (Maybe ModName) [Stmt] |
|
CompE [Stmt] | The result expression of the comprehension is the last of the E.g. translation:
|
ArithSeqE Range |
|
ListE [Exp] |
|
SigE Exp Type |
|
RecConE Name [FieldExp] |
|
RecUpdE Exp [FieldExp] |
|
StaticE Exp |
|
UnboundVarE Name | This is used for holes or unresolved identifiers in AST quotes. Note that it could either have a variable name or constructor name. |
LabelE String |
|
ImplicitParamVarE String |
|
GetFieldE Exp String |
|
ProjectionE (NonEmpty String) |
|
Instances
Instances
Data Match Source | |
Defined in Language.Haskell.TH.Syntax Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Match -> c Match Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Match Source toConstr :: Match -> Constr Source dataTypeOf :: Match -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Match) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Match) Source gmapT :: (forall b. Data b => b -> b) -> Match -> Match Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Match -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Match -> r Source gmapQ :: (forall d. Data d => d -> u) -> Match -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> Match -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> Match -> m Match Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Match -> m Match Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Match -> m Match Source |
|
Generic Match Source | |
Show Match Source | |
Eq Match Source | |
Ord Match Source | |
Defined in Language.Haskell.TH.Syntax |
|
Ppr Match Source | |
type Rep Match Source | |
Defined in Language.Haskell.TH.Syntax
type Rep Match = D1 ('MetaData "Match" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "Match" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Body) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Dec]))))
|
Constructors
Instances
Data Body Source | |
Defined in Language.Haskell.TH.Syntax Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Body -> c Body Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Body Source toConstr :: Body -> Constr Source dataTypeOf :: Body -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Body) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Body) Source gmapT :: (forall b. Data b => b -> b) -> Body -> Body Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Body -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Body -> r Source gmapQ :: (forall d. Data d => d -> u) -> Body -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> Body -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> Body -> m Body Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Body -> m Body Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Body -> m Body Source |
|
Generic Body Source | |
Show Body Source | |
Eq Body Source | |
Ord Body Source | |
Defined in Language.Haskell.TH.Syntax |
|
type Rep Body Source | |
Defined in Language.Haskell.TH.Syntax
type Rep Body = D1 ('MetaData "Body" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "GuardedB" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Guard, Exp)])) :+: C1 ('MetaCons "NormalB" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)))
|
Instances
Data Guard Source | |
Defined in Language.Haskell.TH.Syntax Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Guard -> c Guard Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Guard Source toConstr :: Guard -> Constr Source dataTypeOf :: Guard -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Guard) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Guard) Source gmapT :: (forall b. Data b => b -> b) -> Guard -> Guard Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Guard -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Guard -> r Source gmapQ :: (forall d. Data d => d -> u) -> Guard -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> Guard -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> Guard -> m Guard Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Guard -> m Guard Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Guard -> m Guard Source |
|
Generic Guard Source | |
Show Guard Source | |
Eq Guard Source | |
Ord Guard Source | |
Defined in Language.Haskell.TH.Syntax |
|
type Rep Guard Source | |
Defined in Language.Haskell.TH.Syntax
type Rep Guard = D1 ('MetaData "Guard" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "NormalG" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) :+: C1 ('MetaCons "PatG" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Stmt])))
|
Constructors
Instances
Instances
Constructors
CharL Char | |
StringL String | |
IntegerL Integer | Used for overloaded and non-overloaded literals. We don't have a good way to represent non-overloaded literals at the moment. Maybe that doesn't matter? |
RationalL Rational | |
IntPrimL Integer | |
WordPrimL Integer | |
FloatPrimL Rational | |
DoublePrimL Rational | |
StringPrimL [Word8] | A primitive C-style string, type |
BytesPrimL Bytes | Some raw bytes, type |
CharPrimL Char |
Instances
Pattern in Haskell given in {}
Constructors
LitP Lit |
|
VarP Name |
|
TupP [Pat] |
|
UnboxedTupP [Pat] |
|
UnboxedSumP Pat SumAlt SumArity |
|
ConP Name [Type] [Pat] |
|
InfixP Pat Name Pat |
|
UInfixP Pat Name Pat | |
ParensP Pat | |
TildeP Pat |
|
BangP Pat |
|
AsP Name Pat |
|
WildP |
|
RecP Name [FieldPat] |
|
ListP [Pat] |
|
SigP Pat Type |
|
ViewP Exp Pat |
|
Instances
type FieldExp = (Name, Exp) Source
type FieldPat = (Name, Pat) Source
Instances
Instances
Data TyLit Source | |
Defined in Language.Haskell.TH.Syntax Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TyLit -> c TyLit Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TyLit Source toConstr :: TyLit -> Constr Source dataTypeOf :: TyLit -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TyLit) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TyLit) Source gmapT :: (forall b. Data b => b -> b) -> TyLit -> TyLit Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TyLit -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TyLit -> r Source gmapQ :: (forall d. Data d => d -> u) -> TyLit -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> TyLit -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> TyLit -> m TyLit Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TyLit -> m TyLit Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TyLit -> m TyLit Source |
|
Generic TyLit Source | |
Show TyLit Source | |
Eq TyLit Source | |
Ord TyLit Source | |
Defined in Language.Haskell.TH.Syntax |
|
Ppr TyLit Source | |
type Rep TyLit Source | |
Defined in Language.Haskell.TH.Syntax
type Rep TyLit = D1 ('MetaData "TyLit" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "NumTyLit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)) :+: (C1 ('MetaCons "StrTyLit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "CharTyLit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char))))
|
To avoid duplication between kinds and types, they are defined to be the same. Naturally, you would never have a type be StarT
and you would never have a kind be SigT
, but many of the other constructors are shared. Note that the kind Bool
is denoted with ConT
, not PromotedT
. Similarly, tuple kinds are made with TupleT
, not PromotedTupleT
.
Arguments
= [Pred] |
|
Since the advent of ConstraintKinds
, constraints are really just types. Equality constraints use the EqualityT
constructor. Constraints may also be tuples of other constraints.
Role annotations
Constructors
NominalR |
|
RepresentationalR |
|
PhantomR |
|
InferR |
|
Instances
Data Role Source | |
Defined in Language.Haskell.TH.Syntax Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Role -> c Role Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Role Source toConstr :: Role -> Constr Source dataTypeOf :: Role -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Role) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Role) Source gmapT :: (forall b. Data b => b -> b) -> Role -> Role Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Role -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Role -> r Source gmapQ :: (forall d. Data d => d -> u) -> Role -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> Role -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> Role -> m Role Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Role -> m Role Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Role -> m Role Source |
|
Generic Role Source | |
Show Role Source | |
Eq Role Source | |
Ord Role Source | |
Defined in Language.Haskell.TH.Syntax |
|
Ppr Role Source | |
type Rep Role Source | |
Defined in Language.Haskell.TH.Syntax
type Rep Role = D1 ('MetaData "Role" "Language.Haskell.TH.Syntax" "template-haskell" 'False) ((C1 ('MetaCons "NominalR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RepresentationalR" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PhantomR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InferR" 'PrefixI 'False) (U1 :: Type -> Type)))
|
data Specificity Source
Constructors
SpecifiedSpec |
|
InferredSpec |
|
Instances
data FamilyResultSig Source
Type family result signature
Instances
data InjectivityAnn Source
Injectivity annotation
Constructors
Instances
type PatSynType = Type Source
A pattern synonym's type. Note that a pattern synonym's fully specified type has a peculiar shape coming with two forall quantifiers and two constraint contexts. For example, consider the pattern synonym
pattern P x1 x2 ... xn = <some-pattern>
P's complete type is of the following form
pattern P :: forall universals. required constraints
=> forall existentials. provided constraints
=> t1 -> t2 -> ... -> tn -> t
consisting of four parts:
- the (possibly empty lists of) universally quantified type variables and required constraints on them.
- the (possibly empty lists of) existentially quantified type variables and the provided constraints on them.
- the types
t1
,t2
, ..,tn
ofx1
,x2
, ..,xn
, respectively - the type
t
of<some-pattern>
, mentioning only universals.
Pattern synonym types interact with TH when (a) reifying a pattern synonym, (b) pretty printing, or (c) specifying a pattern synonym's type signature explicitly:
- Reification always returns a pattern synonym's fully specified type in abstract syntax.
- Pretty printing via
pprPatSynType
abbreviates a pattern synonym's type unambiguously in concrete syntax: The rule of thumb is to print initial empty universals and the required context as() =>
, if existentials and a provided context follow. If only universals and their required context, but no existentials are specified, only the universals and their required context are printed. If both or none are specified, so both (or none) are printed. - When specifying a pattern synonym's type explicitly with
PatSynSigD
either one of the universals, the existentials, or their contexts may be left empty.
See the GHC user's guide for more information on pattern synonyms and their types: https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts.html#pattern-synonyms.
type BangType = (Bang, Type) Source
type VarBangType = (Name, Bang, Type) Source
A location at which to attach Haddock documentation. Note that adding documentation to a Name
defined oustide of the current module will cause an error.
Constructors
Instances
data DerivClause Source
A single deriving
clause at the end of a datatype.
Constructors
DerivClause (Maybe DerivStrategy) Cxt |
|
Instances
data DerivStrategy Source
What the user explicitly requests when deriving an instance.
Constructors
StockStrategy | A "standard" derived instance |
AnyclassStrategy |
|
NewtypeStrategy |
|
ViaStrategy Type |
|
Instances
Varieties of allowed instance overlap.
Constructors
Overlappable | May be overlapped by more specific instances |
Overlapping | May overlap a more general instance |
Overlaps | Both |
Incoherent | Both |
Instances
Data Overlap Source | |
Defined in Language.Haskell.TH.Syntax Methodsgfoldl :: (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 | |
Show Overlap Source | |
Eq Overlap Source | |
Ord Overlap Source | |
Defined in Language.Haskell.TH.Syntax |
|
type Rep Overlap Source | |
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)))
|
Uniq
is used by GHC to distinguish names from each other.
data NameFlavour Source
Constructors
NameS | An unqualified name; dynamically bound |
NameQ ModName | A qualified name; dynamically bound |
NameU !Uniq | A unique local name |
NameL !Uniq | Local name bound outside of the TH AST |
NameG NameSpace PkgName ModName | Global name bound outside of the TH AST: An original name (occurrences only, not binders) Need the namespace too to be sure which thing we are naming |
Instances
Raw bytes embedded into the binary.
Avoid using Bytes constructor directly as it is likely to change in the future. Use helpers such as mkBytes
in Language.Haskell.TH.Lib instead.
Constructors
Bytes | |
Fields
|
Instances
Data Bytes Source | |
Defined in Language.Haskell.TH.Syntax Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bytes -> c Bytes Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bytes Source toConstr :: Bytes -> Constr Source dataTypeOf :: Bytes -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Bytes) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bytes) Source gmapT :: (forall b. Data b => b -> b) -> Bytes -> Bytes Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bytes -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bytes -> r Source gmapQ :: (forall d. Data d => d -> u) -> Bytes -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> Bytes -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bytes -> m Bytes Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bytes -> m Bytes Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bytes -> m Bytes Source |
|
Generic Bytes Source | |
Show Bytes Source | |
Eq Bytes Source | |
Ord Bytes Source | |
Defined in Language.Haskell.TH.Syntax |
|
type Rep Bytes Source | |
Defined in Language.Haskell.TH.Syntax
type Rep Bytes = D1 ('MetaData "Bytes" "Language.Haskell.TH.Syntax" "template-haskell" 'False) (C1 ('MetaCons "Bytes" 'PrefixI 'True) (S1 ('MetaSel ('Just "bytesPtr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ForeignPtr Word8)) :*: (S1 ('MetaSel ('Just "bytesOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word) :*: S1 ('MetaSel ('Just "bytesSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word))))
|
class (MonadIO m, MonadFail m) => Quasi m where Source
Minimal complete definition
qNewName, qReport, qRecover, qLookupName, qReify, qReifyFixity, qReifyType, qReifyInstances, qReifyRoles, qReifyAnnotations, qReifyModule, qReifyConStrictness, qLocation, qGetPackageRoot, qAddDependentFile, qAddTempFile, qAddTopDecls, qAddForeignFilePath, qAddModFinalizer, qAddCorePlugin, qGetQ, qPutQ, qIsExtEnabled, qExtsEnabled, qPutDoc, qGetDoc
Methods
Arguments
Arguments
:: m a | the error handler |
-> m a | action which may fail |
-> m a | Recover from the monadic |
qLookupName :: Bool -> String -> m (Maybe Name) Source
qReify :: Name -> m Info Source
qReifyFixity :: Name -> m (Maybe Fixity) Source
qReifyType :: Name -> m Type Source
qReifyInstances :: Name -> [Type] -> m [Dec] Source
qReifyRoles :: Name -> m [Role] Source
qReifyAnnotations :: Data a => AnnLookup -> m [a] Source
qReifyModule :: Module -> m ModuleInfo Source
qReifyConStrictness :: Name -> m [DecidedStrictness] Source
qGetPackageRoot :: m FilePath Source
qAddDependentFile :: FilePath -> m () Source
qAddTempFile :: String -> m FilePath Source
qAddTopDecls :: [Dec] -> m () Source
qAddForeignFilePath :: ForeignSrcLang -> String -> m () Source
qAddModFinalizer :: Q () -> m () Source
qAddCorePlugin :: String -> m () Source
qGetQ :: Typeable a => m (Maybe a) Source
qPutQ :: Typeable a => a -> m () Source
qIsExtEnabled :: Extension -> m Bool Source
qExtsEnabled :: m [Extension] Source
Instances
class Lift (t :: TYPE r) where Source
A Lift
instance can have any of its values turned into a Template Haskell expression. This is needed when a value used within a Template Haskell quotation is bound outside the Oxford brackets ([| ... |]
or [|| ... ||]
) but not at the top level. As an example:
add1 :: Int -> Q (TExp Int)
add1 x = [|| x + 1 ||]
Template Haskell has no way of knowing what value x
will take on at splice-time, so it requires the type of x
to be an instance of Lift
.
A Lift
instance must satisfy $(lift x) ≡ x
and $$(liftTyped x) ≡ x
for all x
, where $(...)
and $$(...)
are Template Haskell splices. It is additionally expected that lift x ≡ unTypeQ (liftTyped x)
.
Lift
instances can be derived automatically by use of the -XDeriveLift
GHC language extension:
{-# LANGUAGE DeriveLift #-}
module Foo where
import Language.Haskell.TH.Syntax
data Bar a = Bar1 a (Bar a) | Bar2 String
deriving Lift
Representation-polymorphic since template-haskell-2.16.0.0.
Minimal complete definition
Methods
lift :: Quote m => t -> m Exp Source
Turn a value into a Template Haskell expression, suitable for use in a splice.
liftTyped :: Quote m => t -> Code m t Source
Turn a value into a Template Haskell typed expression, suitable for use in a typed splice.
Since: template-haskell-2.16.0.0
Instances
Lift Addr# Source | Produces an Since: template-haskell-2.16.0.0 |
Lift Double# Source | Since: template-haskell-2.16.0.0 |
Lift Float# Source | Since: template-haskell-2.16.0.0 |
Lift Int# Source | Since: template-haskell-2.16.0.0 |
Lift ByteArray Source | Since: template-haskell-2.19.0.0 |
Lift Void Source | Since: template-haskell-2.15.0.0 |
Lift Int16 Source | |
Lift Int32 Source | |
Lift Int64 Source | |
Lift Int8 Source | |
Lift Word16 Source | |
Lift Word32 Source | |
Lift Word64 Source | |
Lift Word8 Source | |
Lift Integer Source | |
Lift Natural Source | |
Lift () Source | |
Lift Bool Source | |
Lift Char Source | |
Lift Double Source | |
Lift Float Source | |
Lift Int Source | |
Lift Word Source | |
Lift Char# Source | Since: template-haskell-2.16.0.0 |
Lift Word# Source | Since: template-haskell-2.16.0.0 |
Lift (# #) Source | Since: template-haskell-2.16.0.0 |
Integral a => Lift (Ratio a :: Type) Source | |
Lift a => Lift (NonEmpty a :: Type) Source | Since: template-haskell-2.15.0.0 |
Lift a => Lift (Maybe a :: Type) Source | |
Lift a => Lift ([a] :: Type) Source | |
(Lift a, Lift b) => Lift (Either a b :: Type) Source | |
(Lift a, Lift b) => Lift ((a, b) :: Type) Source | |
(Lift a, Lift b, Lift c) => Lift ((a, b, c) :: Type) Source | |
(Lift a, Lift b, Lift c, Lift d) => Lift ((a, b, c, d) :: Type) Source | |
(Lift a, Lift b, Lift c, Lift d, Lift e) => Lift ((a, b, c, d, e) :: Type) Source | |
(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) => Lift ((a, b, c, d, e, f) :: Type) Source | |
(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) => Lift ((a, b, c, d, e, f, g) :: Type) Source | |
Lift a => Lift ((# a #) :: TYPE ('TupleRep '[LiftedRep])) Source | Since: template-haskell-2.16.0.0 |
(Lift a, Lift b) => Lift ((# a | b #) :: TYPE ('SumRep '[LiftedRep, LiftedRep])) Source | Since: template-haskell-2.16.0.0 |
(Lift a, Lift b) => Lift ((# a, b #) :: TYPE ('TupleRep '[LiftedRep, LiftedRep])) Source | Since: template-haskell-2.16.0.0 |
(Lift a, Lift b, Lift c) => Lift ((# a | b | c #) :: TYPE ('SumRep '[LiftedRep, LiftedRep, LiftedRep])) Source | Since: template-haskell-2.16.0.0 |
(Lift a, Lift b, Lift c) => Lift ((# a, b, c #) :: TYPE ('TupleRep '[LiftedRep, LiftedRep, LiftedRep])) Source | Since: template-haskell-2.16.0.0 |
(Lift a, Lift b, Lift c, Lift d) => Lift ((# a | b | c | d #) :: TYPE ('SumRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep])) Source | Since: template-haskell-2.16.0.0 |
(Lift a, Lift b, Lift c, Lift d) => Lift ((# a, b, c, d #) :: TYPE ('TupleRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep])) Source | Since: template-haskell-2.16.0.0 |
(Lift a, Lift b, Lift c, Lift d, Lift e) => Lift ((# a | b | c | d | e #) :: TYPE ('SumRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep])) Source | Since: template-haskell-2.16.0.0 |
(Lift a, Lift b, Lift c, Lift d, Lift e) => Lift ((# a, b, c, d, e #) :: TYPE ('TupleRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep])) Source | Since: template-haskell-2.16.0.0 |
(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) => Lift ((# a | b | c | d | e | f #) :: TYPE ('SumRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep])) Source | Since: template-haskell-2.16.0.0 |
(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) => Lift ((# a, b, c, d, e, f #) :: TYPE ('TupleRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep])) Source | Since: template-haskell-2.16.0.0 |
(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) => Lift ((# a | b | c | d | e | f | g #) :: TYPE ('SumRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep])) Source | Since: template-haskell-2.16.0.0 |
(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) => Lift ((# a, b, c, d, e, f, g #) :: TYPE ('TupleRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep])) Source | Since: template-haskell-2.16.0.0 |
Instances
Data ModName Source | |
Defined in Language.Haskell.TH.Syntax Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModName -> c ModName Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModName Source toConstr :: ModName -> Constr Source dataTypeOf :: ModName -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ModName) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModName) Source gmapT :: (forall b. Data b => b -> b) -> ModName -> ModName Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModName -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModName -> r Source gmapQ :: (forall d. Data d => d -> u) -> ModName -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> ModName -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModName -> m ModName Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModName -> m ModName Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModName -> m ModName Source |
|
Generic ModName Source | |
Show ModName Source | |
Eq ModName Source | |
Ord ModName Source | |
Defined in Language.Haskell.TH.Syntax |
|
type Rep ModName Source | |
Defined in Language.Haskell.TH.Syntax |
Instances
Data PkgName Source | |
Defined in Language.Haskell.TH.Syntax Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PkgName -> c PkgName Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PkgName Source toConstr :: PkgName -> Constr Source dataTypeOf :: PkgName -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PkgName) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PkgName) Source gmapT :: (forall b. Data b => b -> b) -> PkgName -> PkgName Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PkgName -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PkgName -> r Source gmapQ :: (forall d. Data d => d -> u) -> PkgName -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> PkgName -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> PkgName -> m PkgName Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PkgName -> m PkgName Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PkgName -> m PkgName Source |
|
Generic PkgName Source | |
Show PkgName Source | |
Eq PkgName Source | |
Ord PkgName Source | |
Defined in Language.Haskell.TH.Syntax |
|
type Rep PkgName Source | |
Defined in Language.Haskell.TH.Syntax |
Instances
Data OccName Source | |
Defined in Language.Haskell.TH.Syntax Methodsgfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OccName -> c OccName Source gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OccName Source toConstr :: OccName -> Constr Source dataTypeOf :: OccName -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c OccName) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OccName) Source gmapT :: (forall b. Data b => b -> b) -> OccName -> OccName Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OccName -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OccName -> r Source gmapQ :: (forall d. Data d => d -> u) -> OccName -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> OccName -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> OccName -> m OccName Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OccName -> m OccName Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OccName -> m OccName Source |
|
Generic OccName Source | |
Show OccName Source | |
Eq OccName Source | |
Ord OccName Source | |
Defined in Language.Haskell.TH.Syntax |
|
type Rep OccName Source | |
Defined in Language.Haskell.TH.Syntax |
type StrictType = BangType Source
As of template-haskell-2.11.0.0
, StrictType
has been replaced by BangType
.
type VarStrictType = VarBangType Source
As of template-haskell-2.11.0.0
, VarStrictType
has been replaced by VarBangType
.
Recover from errors raised by reportError
or fail
.
reportError :: String -> Q () Source
Report an error to the user, but allow the current splice's computation to carry on. To abort the computation, use fail
.
The runIO
function lets you run an I/O computation in the Q
monad. Take care: you are guaranteed the ordering of calls to runIO
within a single Q
computation, but not about the order in which splices are run.
Note: for various murky reasons, stdout and stderr handles are not necessarily flushed when the compiler finishes running, so you should flush them yourself.
runQ :: Quasi m => Q a -> m a Source
reportWarning :: String -> Q () Source
Report a warning to the user, and carry on.
report :: Bool -> String -> Q () Source
Deprecated: Use reportError or reportWarning instead
Report an error (True) or warning (False), but carry on; use fail
to stop.
The location at which this computation is spliced.
reify :: Name -> Q Info Source
reify
looks up information about the Name
. It will fail with a compile error if the Name
is not visible. A Name
is visible if it is imported or defined in a prior top-level declaration group. See the documentation for newDeclarationGroup
for more details.
It is sometimes useful to construct the argument name using lookupTypeName
or lookupValueName
to ensure that we are reifying from the right namespace. For instance, in this context:
data D = D
which D
does reify (mkName "D")
return information about? (Answer: D
-the-type, but don't rely on it.) To ensure we get information about D
-the-value, use lookupValueName
:
do
Just nm <- lookupValueName "D"
reify nm
and to get information about D
-the-type, use lookupTypeName
.
reifyModule :: Module -> Q ModuleInfo Source
reifyModule mod
looks up information about module mod
. To look up the current module, call this function with the return value of thisModule
.
newDeclarationGroup :: Q [Dec] Source
Template Haskell is capable of reifying information about types and terms defined in previous declaration groups. Top-level declaration splices break up declaration groups.
For an example, consider this code block. We define a datatype X
and then try to call reify
on the datatype.
module Check where
data X = X
deriving Eq
$(do
info <- reify ''X
runIO $ print info
)
This code fails to compile, noting that X
is not available for reification at the site of reify
. We can fix this by creating a new declaration group using an empty top-level splice:
data X = X
deriving Eq
$(pure [])
$(do
info <- reify ''X
runIO $ print info
)
We provide newDeclarationGroup
as a means of documenting this behavior and providing a name for the pattern.
Since top level splices infer the presence of the $( ... )
brackets, we can also write:
data X = X
deriving Eq
newDeclarationGroup
$(do
info <- reify ''X
runIO $ print info
)
extsEnabled :: Q [Extension] Source
List all enabled language extensions.
isExtEnabled :: Extension -> Q Bool Source
Determine whether the given language extension is enabled in the Q
monad.
lookupTypeName :: String -> Q (Maybe Name) Source
Look up the given name in the (type namespace of the) current splice's scope. See Language.Haskell.TH.Syntax for more details.
lookupValueName :: String -> Q (Maybe Name) Source
Look up the given name in the (value namespace of the) current splice's scope. See Language.Haskell.TH.Syntax for more details.
reifyFixity :: Name -> Q (Maybe Fixity) Source
reifyFixity nm
attempts to find a fixity declaration for nm
. For example, if the function foo
has the fixity declaration infixr 7 foo
, then reifyFixity 'foo
would return Just (Fixity 7 InfixR)
. If the function bar
does not have a fixity declaration, then reifyFixity 'bar
returns Nothing
, so you may assume bar
has defaultFixity
.
reifyType :: Name -> Q Type Source
reifyType nm
attempts to find the type or kind of nm
. For example, reifyType 'not
returns Bool -> Bool
, and reifyType ''Bool
returns Type
. This works even if there's no explicit signature and the type or kind is inferred.
reifyInstances :: Name -> [Type] -> Q [InstanceDec] Source
reifyInstances nm tys
returns a list of visible instances of nm tys
. That is, if nm
is the name of a type class, then all instances of this class at the types tys
are returned. Alternatively, if nm
is the name of a data family or type family, all instances of this family at the types tys
are returned.
Note that this is a "shallow" test; the declarations returned merely have instance heads which unify with nm tys
, they need not actually be satisfiable.
reifyInstances ''Eq [ TupleT 2 `AppT` ConT ''A `AppT` ConT ''B ]
contains theinstance (Eq a, Eq b) => Eq (a, b)
regardless of whetherA
andB
themselves implementEq
reifyInstances ''Show [ VarT (mkName "a") ]
produces every available instance ofEq
There is one edge case: reifyInstances ''Typeable tys
currently always produces an empty list (no matter what tys
are given).
An instance is visible if it is imported or defined in a prior top-level declaration group. See the documentation for newDeclarationGroup
for more details.
isInstance :: Name -> [Type] -> Q Bool Source
Is the list of instances returned by reifyInstances
nonempty?
If you're confused by an instance not being visible despite being defined in the same module and above the splice in question, see the docs for newDeclarationGroup
for a possible explanation.
reifyRoles :: Name -> Q [Role] Source
reifyRoles nm
returns the list of roles associated with the parameters (both visible and invisible) of the tycon nm
. Fails if nm
cannot be found or is not a tycon. The returned list should never contain InferR
.
An invisible parameter to a tycon is often a kind parameter. For example, if we have
type Proxy :: forall k. k -> Type
data Proxy a = MkProxy
and reifyRoles Proxy
, we will get [NominalR, PhantomR]
. The NominalR
is the role of the invisible k
parameter. Kind parameters are always nominal.
reifyAnnotations :: Data a => AnnLookup -> Q [a] Source
reifyAnnotations target
returns the list of annotations associated with target
. Only the annotations that are appropriately typed is returned. So if you have Int
and String
annotations for the same target, you have to call this function twice.
reifyConStrictness :: Name -> Q [DecidedStrictness] Source
reifyConStrictness nm
looks up the strictness information for the fields of the constructor with the name nm
. Note that the strictness information that reifyConStrictness
returns may not correspond to what is written in the source code. For example, in the following data declaration:
data Pair a = Pair a a
reifyConStrictness
would return [DecidedLazy, DecidedLazy]
under most circumstances, but it would return [DecidedStrict, DecidedStrict]
if the -XStrictData
language extension was enabled.
unTypeCode :: forall (r :: RuntimeRep) (a :: TYPE r) m. Quote m => Code m a -> m Exp Source
Extract the untyped representation from the typed representation
unsafeCodeCoerce :: forall (r :: RuntimeRep) (a :: TYPE r) m. Quote m => m Exp -> Code m a Source
Unsafely convert an untyped code representation into a typed code representation.
hoistCode :: forall m n (r :: RuntimeRep) (a :: TYPE r). Monad m => (forall x. m x -> n x) -> Code m a -> Code n a Source
Modify the ambient monad used during code generation. For example, you can use hoistCode
to handle a state effect: handleState :: Code (StateT Int Q) a -> Code Q a handleState = hoistCode (flip runState 0)
bindCode :: forall m a (r :: RuntimeRep) (b :: TYPE r). Monad m => m a -> (a -> Code m b) -> Code m b Source
Variant of (>>=) which allows effectful computations to be injected into code generation.
bindCode_ :: forall m a (r :: RuntimeRep) (b :: TYPE r). Monad m => m a -> Code m b -> Code m b Source
Variant of (>>) which allows effectful computations to be injected into code generation.
joinCode :: forall m (r :: RuntimeRep) (a :: TYPE r). Monad m => m (Code m a) -> Code m a Source
A useful combinator for embedding monadic actions into Code
myCode :: ... => Code m a myCode = joinCode $ do x <- someSideEffect return (makeCodeWith x)
liftCode :: forall (r :: RuntimeRep) (a :: TYPE r) m. m (TExp a) -> Code m a Source
Lift a monadic action producing code into the typed Code
representation
mkName :: String -> Name Source
Generate a capturable name. Occurrences of such names will be resolved according to the Haskell scoping rules at the occurrence site.
For example:
f = [| pi + $(varE (mkName "pi")) |]
...
g = let pi = 3 in $f
In this case, g
is desugared to
g = Prelude.pi + 3
Note that mkName
may be used with qualified names:
mkName "Prelude.pi"
See also dyn
for a useful combinator. The above example could be rewritten using dyn
as
f = [| pi + $(dyn "pi") |]
nameBase :: Name -> String Source
The name without its module prefix.
Examples
>>> nameBase ''Data.Either.Either
"Either"
>>> nameBase (mkName "foo")
"foo"
>>> nameBase (mkName "Module.foo")
"foo"
nameModule :: Name -> Maybe String Source
Module prefix of a name, if it exists.
Examples
>>> nameModule ''Data.Either.Either
Just "Data.Either"
>>> nameModule (mkName "foo")
Nothing
>>> nameModule (mkName "Module.foo")
Just "Module"
namePackage :: Name -> Maybe String Source
A name's package, if it exists.
Examples
>>> namePackage ''Data.Either.Either
Just "base"
>>> namePackage (mkName "foo")
Nothing
>>> namePackage (mkName "Module.foo")
Nothing
nameSpace :: Name -> Maybe NameSpace Source
Returns whether a name represents an occurrence of a top-level variable (VarName
), data constructor (DataName
), type constructor, or type class (TcClsName
). If we can't be sure, it returns Nothing
.
Examples
>>> nameSpace 'Prelude.id
Just VarName
>>> nameSpace (mkName "id")
Nothing -- only works for top-level variable names
>>> nameSpace 'Data.Maybe.Just
Just DataName
>>> nameSpace ''Data.Maybe.Maybe
Just TcClsName
>>> nameSpace ''Data.Ord.Ord
Just TcClsName
tupleTypeName :: Int -> Name Source
Tuple type constructor
tupleDataName :: Int -> Name Source
Tuple data constructor
unboxedTupleTypeName :: Int -> Name Source
Unboxed tuple type constructor
unboxedTupleDataName :: Int -> Name Source
Unboxed tuple data constructor
unboxedSumTypeName :: SumArity -> Name Source
Unboxed sum type constructor
unboxedSumDataName :: SumAlt -> SumArity -> Name Source
Unboxed sum data constructor
defaultFixity :: Fixity Source
Default fixity: infixl 9
Highest allowed operator precedence for Fixity
constructor (answer: 9)
putDoc :: DocLoc -> String -> Q () Source
Add Haddock documentation to the specified location. This will overwrite any documentation at the location if it already exists. This will reify the specified name, so it must be in scope when you call it. If you want to add documentation to something that you are currently splicing, you can use addModFinalizer
e.g.
do
let nm = mkName "x"
addModFinalizer $ putDoc (DeclDoc nm) "Hello"
[d| $(varP nm) = 42 |]
The helper functions withDecDoc
and withDecsDoc
will do this for you, as will the funD_doc
and other _doc
combinators. You most likely want to have the -haddock
flag turned on when using this. Adding documentation to anything outside of the current module will cause an error.
getDoc :: DocLoc -> Q (Maybe String) Source
Retreives the Haddock documentation at the specified location, if one exists. It can be used to read documentation on things defined outside of the current module, provided that those modules were compiled with the -haddock
flag.
showName' :: NameIs -> Name -> String Source
dataToQa :: forall m a k q. (Quote m, Data a) => (Name -> k) -> (Lit -> m q) -> (k -> [m q] -> m q) -> (forall b. Data b => b -> Maybe (m q)) -> a -> m q Source
dataToQa
is an internal utility function for constructing generic conversion functions from types with Data
instances to various quasi-quoting representations. See the source of dataToExpQ
and dataToPatQ
for two example usages: mkCon
, mkLit
and appQ
are overloadable to account for different syntax for expressions and patterns; antiQ
allows you to override type-specific cases, a common usage is just const Nothing
, which results in no overloading.
dataToExpQ :: (Quote m, Data a) => (forall b. Data b => b -> Maybe (m Exp)) -> a -> m Exp Source
dataToExpQ
converts a value to a Exp
representation of the same value, in the SYB style. It is generalized to take a function override type-specific cases; see liftData
for a more commonly used variant.
dataToPatQ :: (Quote m, Data a) => (forall b. Data b => b -> Maybe (m Pat)) -> a -> m Pat Source
dataToPatQ
converts a value to a Pat
representation of the same value, in the SYB style. It takes a function to handle type-specific cases, alternatively, pass const Nothing
to get default behavior.
newNameIO :: String -> IO Name Source
badIO :: String -> IO a Source
mkNameU :: String -> Uniq -> Name Source
Only used internally
unTypeQ :: forall (r :: RuntimeRep) (a :: TYPE r) m. Quote m => m (TExp a) -> m Exp Source
Discard the type annotation and produce a plain Template Haskell expression
Representation-polymorphic since template-haskell-2.16.0.0.
unsafeTExpCoerce :: forall (r :: RuntimeRep) (a :: TYPE r) m. Quote m => m Exp -> m (TExp a) Source
Annotate the Template Haskell expression with a type
This is unsafe because GHC cannot check for you that the expression really does have the type you claim it has.
Representation-polymorphic since template-haskell-2.16.0.0.
lookupName :: Bool -> String -> Q (Maybe Name) Source
getPackageRoot :: Q FilePath Source
Get the package root for the current package which is being compiled. This can be set explicitly with the -package-root flag but is normally just the current working directory.
The motivation for this flag is to provide a principled means to remove the assumption from splices that they will be executed in the directory where the cabal file resides. Projects such as haskell-language-server can't and don't change directory when compiling files but instead set the -package-root flag appropiately.
makeRelativeToProject :: FilePath -> Q FilePath Source
The input is a filepath, which if relative is offset by the package root.
addDependentFile :: FilePath -> Q () Source
Record external files that runIO is using (dependent upon). The compiler can then recognize that it should re-compile the Haskell file when an external file changes.
Expects an absolute file path.
Notes:
- ghc -M does not know about these dependencies - it does not execute TH.
- The dependency is based on file content, not a modification time
addTempFile :: String -> Q FilePath Source
Obtain a temporary file path with the given suffix. The compiler will delete this file after compilation.
addTopDecls :: [Dec] -> Q () Source
Add additional top-level declarations. The added declarations will be type checked along with the current declaration group.
addForeignFile :: ForeignSrcLang -> String -> Q () Source
Deprecated: Use addForeignSource
instead
addForeignSource :: ForeignSrcLang -> String -> Q () Source
Emit a foreign file which will be compiled and linked to the object for the current module. Currently only languages that can be compiled with the C compiler are supported, and the flags passed as part of -optc will be also applied to the C compiler invocation that will compile them.
Note that for non-C languages (for example C++) extern C
directives must be used to get symbols that we can access from Haskell.
To get better errors, it is recommended to use #line pragmas when emitting C files, e.g.
{-# LANGUAGE CPP #-}
...
addForeignSource LangC $ unlines
[ "#line " ++ show (803 + 1) ++ " " ++ show "libraries/template-haskell/Language/Haskell/TH/Syntax.hs"
, ...
]
addForeignFilePath :: ForeignSrcLang -> FilePath -> Q () Source
Same as addForeignSource
, but expects to receive a path pointing to the foreign file instead of a String
of its contents. Consider using this in conjunction with addTempFile
.
This is a good alternative to addForeignSource
when you are trying to directly link in an object file.
addModFinalizer :: Q () -> Q () Source
Add a finalizer that will run in the Q monad after the current module has been type checked. This only makes sense when run within a top-level splice.
The finalizer is given the local type environment at the splice point. Thus reify
is able to find the local definitions when executed inside the finalizer.
addCorePlugin :: String -> Q () Source
Adds a core plugin to the compilation pipeline.
addCorePlugin m
has almost the same effect as passing -fplugin=m
to ghc in the command line. The major difference is that the plugin module m
must not belong to the current package. When TH executes, it is too late to tell the compiler that we needed to compile first a plugin module in the current package.
getQ :: Typeable a => Q (Maybe a) Source
Get state from the Q
monad. Note that the state is local to the Haskell module in which the Template Haskell expression is executed.
putQ :: Typeable a => a -> Q () Source
Replace the state in the Q
monad. Note that the state is local to the Haskell module in which the Template Haskell expression is executed.
sequenceQ :: forall m. Monad m => forall a. [m a] -> m [a] Source
addrToByteArrayName :: Name Source
mkNameG_v :: String -> String -> String -> Name Source
addrToByteArray :: Int -> Addr# -> ByteArray Source
liftString :: Quote m => String -> m Exp Source
mkNameG :: NameSpace -> String -> String -> String -> Name Source
Used for 'x etc, but not available to the programmer
mkOccName :: String -> OccName Source
mkPkgName :: String -> PkgName Source
mkModName :: String -> ModName Source
mkNameG_d :: String -> String -> String -> Name Source
showName :: Name -> String Source
liftData :: (Quote m, Data a) => a -> m Exp Source
liftData
is a variant of lift
in the Lift
type class which works for any type with a Data
instance.
modString :: ModName -> String Source
pkgString :: PkgName -> String Source
occString :: OccName -> String Source
thenCmp :: Ordering -> Ordering -> Ordering Source
mkNameL :: String -> Uniq -> Name Source
Only used internally
mkNameS :: String -> Name Source
mkNameG_tc :: String -> String -> String -> Name Source
mk_tup_name :: Int -> NameSpace -> Bool -> Name Source
eqBytes :: Bytes -> Bytes -> Bool Source
compareBytes :: Bytes -> Bytes -> Ordering Source
memcmp :: Ptr a -> Ptr b -> CSize -> IO CInt Source
cmpEq :: Ordering -> Bool Source
Language extensions
module Language.Haskell.TH.LanguageExtensions
data ForeignSrcLang Source
Foreign formats supported by GHC via TH
Constructors
Instances
© The University of Glasgow and others
Licensed under a BSD-style license (see top of the page).
https://downloads.haskell.org/~ghc/9.4.2/docs/libraries/template-haskell-2.19.0.0/Language-Haskell-TH-Syntax.html