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 |