template-haskell-2.22.1.0: Support library for Template Haskell
Safe HaskellTrustworthy
LanguageHaskell2010

Language.Haskell.TH.Syntax

Synopsis

Documentation

addModFinalizer :: Q () -> Q () #

addTopDecls :: [Dec] -> Q () #

badIO :: String -> IO a #

bindCode :: Monad m => m a -> (a -> Code m b) -> Code m b #

bindCode_ :: Monad m => m a -> Code m b -> Code m b #

getQ :: Typeable a => Q (Maybe a) #

hoistCode :: Monad m => (forall x. m x -> n x) -> Code m a -> Code n a #

isInstance :: Name -> [Type] -> Q Bool #

joinCode :: Monad m => m (Code m a) -> Code m a #

liftCode :: forall a m. m (TExp a) -> Code m a #

memcmp :: Ptr a -> Ptr b -> CSize -> IO CInt #

putDoc :: DocLoc -> String -> Q () #

putQ :: Typeable a => a -> Q () #

recover :: Q a -> Q a -> Q a #

reify :: Name -> Q Info #

report :: Bool -> String -> Q () #

runIO :: IO a -> Q a #

runQ :: Quasi m => Q a -> m a #

sequenceQ :: Monad m => forall a. [m a] -> m [a] #

unTypeCode :: forall a m. Quote m => Code m a -> m Exp #

unTypeQ :: forall a m. Quote m => m (TExp a) -> m Exp #

unsafeCodeCoerce :: forall a m. Quote m => m Exp -> Code m a #

unsafeTExpCoerce :: forall a m. Quote m => m Exp -> m (TExp a) #

data ForeignSrcLang #

Instances

Instances details
Generic ForeignSrcLang # 
Instance details

Defined in GHC.Internal.ForeignSrcLang

Associated Types

type Rep ForeignSrcLang 
Instance details

Defined in GHC.Internal.ForeignSrcLang

type Rep ForeignSrcLang = D1 ('MetaData "ForeignSrcLang" "GHC.Internal.ForeignSrcLang" "ghc-internal" 'False) ((C1 ('MetaCons "LangC" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LangCxx" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LangObjc" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "LangObjcxx" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LangAsm" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LangJs" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RawObject" 'PrefixI 'False) (U1 :: Type -> Type))))
Show ForeignSrcLang # 
Instance details

Defined in GHC.Internal.ForeignSrcLang

Eq ForeignSrcLang # 
Instance details

Defined in GHC.Internal.ForeignSrcLang

Lift ForeignSrcLang # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => ForeignSrcLang -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => ForeignSrcLang -> Code m ForeignSrcLang #

type Rep ForeignSrcLang # 
Instance details

Defined in GHC.Internal.ForeignSrcLang

type Rep ForeignSrcLang = D1 ('MetaData "ForeignSrcLang" "GHC.Internal.ForeignSrcLang" "ghc-internal" 'False) ((C1 ('MetaCons "LangC" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LangCxx" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LangObjc" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "LangObjcxx" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LangAsm" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LangJs" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RawObject" 'PrefixI 'False) (U1 :: Type -> Type))))

data Extension #

Constructors

Cpp 
OverlappingInstances 
UndecidableInstances 
IncoherentInstances 
UndecidableSuperClasses 
MonomorphismRestriction 
MonoLocalBinds 
DeepSubsumption 
RelaxedPolyRec 
ExtendedDefaultRules 
NamedDefaults 
ForeignFunctionInterface 
UnliftedFFITypes 
InterruptibleFFI 
CApiFFI 
GHCForeignImportPrim 
JavaScriptFFI 
ParallelArrays 
Arrows 
TemplateHaskell 
TemplateHaskellQuotes 
QualifiedDo 
QuasiQuotes 
ImplicitParams 
ImplicitPrelude 
ScopedTypeVariables 
AllowAmbiguousTypes 
UnboxedTuples 
UnboxedSums 
UnliftedNewtypes 
UnliftedDatatypes 
BangPatterns 
TypeFamilies 
TypeFamilyDependencies 
TypeInType 
OverloadedStrings 
OverloadedLists 
NumDecimals 
DisambiguateRecordFields 
RecordWildCards 
NamedFieldPuns 
ViewPatterns 
OrPatterns 
GADTs 
GADTSyntax 
NPlusKPatterns 
DoAndIfThenElse 
BlockArguments 
RebindableSyntax 
ConstraintKinds 
PolyKinds 
DataKinds 
TypeData 
InstanceSigs 
ApplicativeDo 
LinearTypes 
RequiredTypeArguments 
StandaloneDeriving 
DeriveDataTypeable 
AutoDeriveTypeable 
DeriveFunctor 
DeriveTraversable 
DeriveFoldable 
DeriveGeneric 
DefaultSignatures 
DeriveAnyClass 
DeriveLift 
DerivingStrategies 
DerivingVia 
TypeSynonymInstances 
FlexibleContexts 
FlexibleInstances 
ConstrainedClassMethods 
MultiParamTypeClasses 
NullaryTypeClasses 
FunctionalDependencies 
UnicodeSyntax 
ExistentialQuantification 
MagicHash 
EmptyDataDecls 
KindSignatures 
RoleAnnotations 
ParallelListComp 
TransformListComp 
MonadComprehensions 
GeneralizedNewtypeDeriving 
RecursiveDo 
PostfixOperators 
TupleSections 
PatternGuards 
LiberalTypeSynonyms 
RankNTypes 
ImpredicativeTypes 
TypeOperators 
ExplicitNamespaces 
PackageImports 
ExplicitForAll 
AlternativeLayoutRule 
AlternativeLayoutRuleTransitional 
DatatypeContexts 
NondecreasingIndentation 
RelaxedLayout 
TraditionalRecordSyntax 
LambdaCase 
MultiWayIf 
BinaryLiterals 
NegativeLiterals 
HexFloatLiterals 
DuplicateRecordFields 
OverloadedLabels 
EmptyCase 
PatternSynonyms 
PartialTypeSignatures 
NamedWildCards 
StaticPointers 
TypeApplications 
Strict 
StrictData 
EmptyDataDeriving 
NumericUnderscores 
QuantifiedConstraints 
StarIsType 
ImportQualifiedPost 
CUSKs 
StandaloneKindSignatures 
LexicalNegation 
FieldSelectors 
OverloadedRecordDot 
OverloadedRecordUpdate 
TypeAbstractions 
ExtendedLiterals 
ListTuplePuns 
MultilineStrings 

Instances

Instances details
Bounded Extension # 
Instance details

Defined in GHC.Internal.LanguageExtensions

Enum Extension # 
Instance details

Defined in GHC.Internal.LanguageExtensions

Generic Extension # 
Instance details

Defined in GHC.Internal.LanguageExtensions

Associated Types

type Rep Extension 
Instance details

Defined in GHC.Internal.LanguageExtensions

type Rep Extension = D1 ('MetaData "Extension" "GHC.Internal.LanguageExtensions" "ghc-internal" 'False) (((((((C1 ('MetaCons "Cpp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OverlappingInstances" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UndecidableInstances" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IncoherentInstances" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "UndecidableSuperClasses" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MonomorphismRestriction" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MonoLocalBinds" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeepSubsumption" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "RelaxedPolyRec" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExtendedDefaultRules" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NamedDefaults" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ForeignFunctionInterface" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "UnliftedFFITypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InterruptibleFFI" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CApiFFI" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GHCForeignImportPrim" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "JavaScriptFFI" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ParallelArrays" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Arrows" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TemplateHaskell" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TemplateHaskellQuotes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "QualifiedDo" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "QuasiQuotes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ImplicitParams" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "ImplicitPrelude" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ScopedTypeVariables" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AllowAmbiguousTypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnboxedTuples" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "UnboxedSums" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnliftedNewtypes" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UnliftedDatatypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BangPatterns" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeFamilies" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "TypeFamilyDependencies" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeInType" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OverloadedStrings" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OverloadedLists" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "NumDecimals" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DisambiguateRecordFields" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RecordWildCards" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NamedFieldPuns" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "ViewPatterns" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OrPatterns" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GADTs" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GADTSyntax" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "NPlusKPatterns" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DoAndIfThenElse" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BlockArguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RebindableSyntax" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "ConstraintKinds" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PolyKinds" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DataKinds" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeData" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "InstanceSigs" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ApplicativeDo" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LinearTypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RequiredTypeArguments" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "StandaloneDeriving" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeriveDataTypeable" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AutoDeriveTypeable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeriveFunctor" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DeriveTraversable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeriveFoldable" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DeriveGeneric" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DefaultSignatures" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeriveAnyClass" 'PrefixI 'False) (U1 :: Type -> Type)))))))) :+: ((((((C1 ('MetaCons "DeriveLift" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DerivingStrategies" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DerivingVia" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeSynonymInstances" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "FlexibleContexts" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FlexibleInstances" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ConstrainedClassMethods" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MultiParamTypeClasses" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "NullaryTypeClasses" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FunctionalDependencies" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UnicodeSyntax" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExistentialQuantification" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MagicHash" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EmptyDataDecls" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "KindSignatures" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RoleAnnotations" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "ParallelListComp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TransformListComp" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MonadComprehensions" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GeneralizedNewtypeDeriving" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "RecursiveDo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PostfixOperators" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TupleSections" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PatternGuards" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "LiberalTypeSynonyms" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RankNTypes" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ImpredicativeTypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeOperators" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ExplicitNamespaces" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PackageImports" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ExplicitForAll" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AlternativeLayoutRule" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AlternativeLayoutRuleTransitional" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "DatatypeContexts" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NondecreasingIndentation" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RelaxedLayout" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TraditionalRecordSyntax" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "LambdaCase" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MultiWayIf" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BinaryLiterals" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NegativeLiterals" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "HexFloatLiterals" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DuplicateRecordFields" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OverloadedLabels" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EmptyCase" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PatternSynonyms" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PartialTypeSignatures" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NamedWildCards" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "StaticPointers" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeApplications" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "Strict" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StrictData" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EmptyDataDeriving" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NumericUnderscores" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "QuantifiedConstraints" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StarIsType" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ImportQualifiedPost" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CUSKs" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "StandaloneKindSignatures" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LexicalNegation" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FieldSelectors" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OverloadedRecordDot" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "OverloadedRecordUpdate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeAbstractions" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ExtendedLiterals" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ListTuplePuns" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MultilineStrings" 'PrefixI 'False) (U1 :: Type -> Type)))))))))
Show Extension # 
Instance details

Defined in GHC.Internal.LanguageExtensions

Eq Extension # 
Instance details

Defined in GHC.Internal.LanguageExtensions

Ord Extension # 
Instance details

Defined in GHC.Internal.LanguageExtensions

Lift Extension # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Extension -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Extension -> Code m Extension #

type Rep Extension # 
Instance details

Defined in GHC.Internal.LanguageExtensions

type Rep Extension = D1 ('MetaData "Extension" "GHC.Internal.LanguageExtensions" "ghc-internal" 'False) (((((((C1 ('MetaCons "Cpp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OverlappingInstances" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UndecidableInstances" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IncoherentInstances" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "UndecidableSuperClasses" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MonomorphismRestriction" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MonoLocalBinds" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeepSubsumption" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "RelaxedPolyRec" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExtendedDefaultRules" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NamedDefaults" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ForeignFunctionInterface" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "UnliftedFFITypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InterruptibleFFI" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CApiFFI" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GHCForeignImportPrim" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "JavaScriptFFI" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ParallelArrays" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Arrows" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TemplateHaskell" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TemplateHaskellQuotes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "QualifiedDo" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "QuasiQuotes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ImplicitParams" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "ImplicitPrelude" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ScopedTypeVariables" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AllowAmbiguousTypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnboxedTuples" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "UnboxedSums" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnliftedNewtypes" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UnliftedDatatypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BangPatterns" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeFamilies" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "TypeFamilyDependencies" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeInType" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OverloadedStrings" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OverloadedLists" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "NumDecimals" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DisambiguateRecordFields" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RecordWildCards" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NamedFieldPuns" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "ViewPatterns" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OrPatterns" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GADTs" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GADTSyntax" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "NPlusKPatterns" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DoAndIfThenElse" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BlockArguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RebindableSyntax" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "ConstraintKinds" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PolyKinds" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DataKinds" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeData" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "InstanceSigs" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ApplicativeDo" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LinearTypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RequiredTypeArguments" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "StandaloneDeriving" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeriveDataTypeable" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AutoDeriveTypeable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeriveFunctor" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "DeriveTraversable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeriveFoldable" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DeriveGeneric" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DefaultSignatures" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DeriveAnyClass" 'PrefixI 'False) (U1 :: Type -> Type)))))))) :+: ((((((C1 ('MetaCons "DeriveLift" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DerivingStrategies" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DerivingVia" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeSynonymInstances" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "FlexibleContexts" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FlexibleInstances" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ConstrainedClassMethods" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MultiParamTypeClasses" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "NullaryTypeClasses" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FunctionalDependencies" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UnicodeSyntax" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExistentialQuantification" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MagicHash" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EmptyDataDecls" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "KindSignatures" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RoleAnnotations" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "ParallelListComp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TransformListComp" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MonadComprehensions" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GeneralizedNewtypeDeriving" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "RecursiveDo" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PostfixOperators" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TupleSections" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PatternGuards" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "LiberalTypeSynonyms" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RankNTypes" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ImpredicativeTypes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeOperators" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ExplicitNamespaces" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PackageImports" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ExplicitForAll" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AlternativeLayoutRule" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AlternativeLayoutRuleTransitional" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "DatatypeContexts" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NondecreasingIndentation" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RelaxedLayout" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TraditionalRecordSyntax" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "LambdaCase" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MultiWayIf" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BinaryLiterals" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NegativeLiterals" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "HexFloatLiterals" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DuplicateRecordFields" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OverloadedLabels" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EmptyCase" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PatternSynonyms" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PartialTypeSignatures" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NamedWildCards" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "StaticPointers" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeApplications" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "Strict" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StrictData" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EmptyDataDeriving" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NumericUnderscores" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "QuantifiedConstraints" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StarIsType" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ImportQualifiedPost" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CUSKs" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "StandaloneKindSignatures" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LexicalNegation" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FieldSelectors" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OverloadedRecordDot" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "OverloadedRecordUpdate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TypeAbstractions" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ExtendedLiterals" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ListTuplePuns" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MultilineStrings" 'PrefixI 'False) (U1 :: Type -> Type)))))))))

data AnnLookup #

Instances

Instances details
Data AnnLookup # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: AnnLookup -> Constr #

dataTypeOf :: AnnLookup -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic AnnLookup # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep AnnLookup 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep AnnLookup = D1 ('MetaData "AnnLookup" "GHC.Internal.TH.Syntax" "ghc-internal" '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)))
Show AnnLookup # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq AnnLookup # 
Instance details

Defined in GHC.Internal.TH.Syntax

Ord AnnLookup # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift AnnLookup # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => AnnLookup -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => AnnLookup -> Code m AnnLookup #

type Rep AnnLookup # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep AnnLookup = D1 ('MetaData "AnnLookup" "GHC.Internal.TH.Syntax" "ghc-internal" '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)))

data AnnTarget #

Instances

Instances details
Data AnnTarget # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: AnnTarget -> Constr #

dataTypeOf :: AnnTarget -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic AnnTarget # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep AnnTarget 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep AnnTarget = D1 ('MetaData "AnnTarget" "GHC.Internal.TH.Syntax" "ghc-internal" '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))))
Show AnnTarget # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq AnnTarget # 
Instance details

Defined in GHC.Internal.TH.Syntax

Ord AnnTarget # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift AnnTarget # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => AnnTarget -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => AnnTarget -> Code m AnnTarget #

type Rep AnnTarget # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep AnnTarget = D1 ('MetaData "AnnTarget" "GHC.Internal.TH.Syntax" "ghc-internal" '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))))

type Arity = Int #

data Bang #

Instances

Instances details
Ppr Bang Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Methods

ppr :: Bang -> Doc Source #

ppr_list :: [Bang] -> Doc Source #

Data Bang # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Bang -> Constr #

dataTypeOf :: Bang -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Bang # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep Bang 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

from :: Bang -> Rep Bang x #

to :: Rep Bang x -> Bang #

Show Bang # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

showsPrec :: Int -> Bang -> ShowS #

show :: Bang -> String #

showList :: [Bang] -> ShowS #

Eq Bang # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord Bang # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

compare :: Bang -> Bang -> Ordering #

(<) :: Bang -> Bang -> Bool #

(<=) :: Bang -> Bang -> Bool #

(>) :: Bang -> Bang -> Bool #

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

max :: Bang -> Bang -> Bang #

min :: Bang -> Bang -> Bang #

Lift Bang # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Bang -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Bang -> Code m Bang #

type Rep Bang # 
Instance details

Defined in GHC.Internal.TH.Syntax

type BangType = (Bang, Type) #

data BndrVis #

Constructors

BndrReq 
BndrInvis 

Instances

Instances details
PprFlag BndrVis Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Data BndrVis # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: BndrVis -> Constr #

dataTypeOf :: BndrVis -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic BndrVis # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep BndrVis 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep BndrVis = D1 ('MetaData "BndrVis" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (C1 ('MetaCons "BndrReq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BndrInvis" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: BndrVis -> Rep BndrVis x #

to :: Rep BndrVis x -> BndrVis #

Show BndrVis # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq BndrVis # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord BndrVis # 
Instance details

Defined in GHC.Internal.TH.Syntax

DefaultBndrFlag BndrVis Source # 
Instance details

Defined in Language.Haskell.TH.Lib

Lift BndrVis # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => BndrVis -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => BndrVis -> Code m BndrVis #

type Rep BndrVis # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep BndrVis = D1 ('MetaData "BndrVis" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (C1 ('MetaCons "BndrReq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BndrInvis" 'PrefixI 'False) (U1 :: Type -> Type))

data Body #

Constructors

GuardedB [(Guard, Exp)] 
NormalB Exp 

Instances

Instances details
Data Body # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Body -> Constr #

dataTypeOf :: Body -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Body # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep Body 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Body = D1 ('MetaData "Body" "GHC.Internal.TH.Syntax" "ghc-internal" '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)))

Methods

from :: Body -> Rep Body x #

to :: Rep Body x -> Body #

Show Body # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

showsPrec :: Int -> Body -> ShowS #

show :: Body -> String #

showList :: [Body] -> ShowS #

Eq Body # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord Body # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

compare :: Body -> Body -> Ordering #

(<) :: Body -> Body -> Bool #

(<=) :: Body -> Body -> Bool #

(>) :: Body -> Body -> Bool #

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

max :: Body -> Body -> Body #

min :: Body -> Body -> Body #

Lift Body # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Body -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Body -> Code m Body #

type Rep Body # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Body = D1 ('MetaData "Body" "GHC.Internal.TH.Syntax" "ghc-internal" '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)))

data Bytes #

Constructors

Bytes 

Instances

Instances details
Data Bytes # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Bytes -> Constr #

dataTypeOf :: Bytes -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Bytes # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep Bytes 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Bytes = D1 ('MetaData "Bytes" "GHC.Internal.TH.Syntax" "ghc-internal" '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))))

Methods

from :: Bytes -> Rep Bytes x #

to :: Rep Bytes x -> Bytes #

Show Bytes # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

showsPrec :: Int -> Bytes -> ShowS #

show :: Bytes -> String #

showList :: [Bytes] -> ShowS #

Eq Bytes # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord Bytes # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

compare :: Bytes -> Bytes -> Ordering #

(<) :: Bytes -> Bytes -> Bool #

(<=) :: Bytes -> Bytes -> Bool #

(>) :: Bytes -> Bytes -> Bool #

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

max :: Bytes -> Bytes -> Bytes #

min :: Bytes -> Bytes -> Bytes #

Lift Bytes # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Bytes -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Bytes -> Code m Bytes #

type Rep Bytes # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Bytes = D1 ('MetaData "Bytes" "GHC.Internal.TH.Syntax" "ghc-internal" '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))))

data Callconv #

Constructors

CCall 
StdCall 
CApi 
Prim 
JavaScript 

Instances

Instances details
Data Callconv # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Callconv -> Constr #

dataTypeOf :: Callconv -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Callconv # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep Callconv 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Callconv = D1 ('MetaData "Callconv" "GHC.Internal.TH.Syntax" "ghc-internal" '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))))

Methods

from :: Callconv -> Rep Callconv x #

to :: Rep Callconv x -> Callconv #

Show Callconv # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Callconv # 
Instance details

Defined in GHC.Internal.TH.Syntax

Ord Callconv # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift Callconv # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Callconv -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Callconv -> Code m Callconv #

type Rep Callconv # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Callconv = D1 ('MetaData "Callconv" "GHC.Internal.TH.Syntax" "ghc-internal" '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))))

type CharPos = (Int, Int) #

data Clause #

Constructors

Clause [Pat] Body [Dec] 

Instances

Instances details
Ppr Clause Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Methods

ppr :: Clause -> Doc Source #

ppr_list :: [Clause] -> Doc Source #

Data Clause # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Clause -> Constr #

dataTypeOf :: Clause -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Clause # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

from :: Clause -> Rep Clause x #

to :: Rep Clause x -> Clause #

Show Clause # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Clause # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord Clause # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift Clause # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Clause -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Clause -> Code m Clause #

type Rep Clause # 
Instance details

Defined in GHC.Internal.TH.Syntax

newtype Code (m :: Type -> Type) (a :: TYPE r) #

Constructors

Code 

Fields

data Con #

Instances

Instances details
Ppr Con Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Methods

ppr :: Con -> Doc Source #

ppr_list :: [Con] -> Doc Source #

Data Con # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Con -> Constr #

dataTypeOf :: Con -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Con # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep Con 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Con = D1 ('MetaData "Con" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) ((C1 ('MetaCons "NormalC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BangType])) :+: (C1 ('MetaCons "RecC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [VarBangType])) :+: C1 ('MetaCons "InfixC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BangType) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BangType))))) :+: (C1 ('MetaCons "ForallC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr Specificity]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Con))) :+: (C1 ('MetaCons "GadtC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BangType]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))) :+: C1 ('MetaCons "RecGadtC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [VarBangType]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))))))

Methods

from :: Con -> Rep Con x #

to :: Rep Con x -> Con #

Show Con # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

showsPrec :: Int -> Con -> ShowS #

show :: Con -> String #

showList :: [Con] -> ShowS #

Eq Con # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord Con # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

compare :: Con -> Con -> Ordering #

(<) :: Con -> Con -> Bool #

(<=) :: Con -> Con -> Bool #

(>) :: Con -> Con -> Bool #

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

max :: Con -> Con -> Con #

min :: Con -> Con -> Con #

Lift Con # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Con -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Con -> Code m Con #

type Rep Con # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Con = D1 ('MetaData "Con" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) ((C1 ('MetaCons "NormalC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BangType])) :+: (C1 ('MetaCons "RecC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [VarBangType])) :+: C1 ('MetaCons "InfixC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BangType) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BangType))))) :+: (C1 ('MetaCons "ForallC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr Specificity]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Con))) :+: (C1 ('MetaCons "GadtC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BangType]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))) :+: C1 ('MetaCons "RecGadtC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [VarBangType]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))))))

type Cxt = [Pred] #

data Dec #

Instances

Instances details
Ppr Dec Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Methods

ppr :: Dec -> Doc Source #

ppr_list :: [Dec] -> Doc Source #

Data Dec # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Dec -> Constr #

dataTypeOf :: Dec -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Dec # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep Dec 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Dec = D1 ('MetaData "Dec" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) ((((C1 ('MetaCons "FunD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Clause])) :+: (C1 ('MetaCons "ValD" '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]))) :+: C1 ('MetaCons "DataD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr BndrVis]))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Kind)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Con]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DerivClause])))))) :+: (C1 ('MetaCons "NewtypeD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr BndrVis]))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Kind)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Con) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DerivClause])))) :+: (C1 ('MetaCons "TypeDataD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr BndrVis])) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Kind)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Con]))) :+: C1 ('MetaCons "TySynD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr BndrVis]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)))))) :+: ((C1 ('MetaCons "ClassD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr BndrVis]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FunDep]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Dec])))) :+: (C1 ('MetaCons "InstanceD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Overlap)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Dec]))) :+: C1 ('MetaCons "SigD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)))) :+: ((C1 ('MetaCons "KiSigD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind)) :+: C1 ('MetaCons "ForeignD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Foreign))) :+: (C1 ('MetaCons "InfixD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Fixity) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NamespaceSpecifier) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))) :+: C1 ('MetaCons "DefaultD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Type])))))) :+: (((C1 ('MetaCons "PragmaD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pragma)) :+: (C1 ('MetaCons "DataFamilyD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr BndrVis]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Kind)))) :+: C1 ('MetaCons "DataInstD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [TyVarBndr ()])) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Kind)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Con]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DerivClause])))))) :+: (C1 ('MetaCons "NewtypeInstD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [TyVarBndr ()])) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Kind)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Con) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DerivClause])))) :+: (C1 ('MetaCons "TySynInstD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TySynEqn)) :+: C1 ('MetaCons "OpenTypeFamilyD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TypeFamilyHead))))) :+: ((C1 ('MetaCons "ClosedTypeFamilyD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TypeFamilyHead) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TySynEqn])) :+: (C1 ('MetaCons "RoleAnnotD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Role])) :+: C1 ('MetaCons "StandaloneDerivD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DerivStrategy)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))))) :+: ((C1 ('MetaCons "DefaultSigD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :+: C1 ('MetaCons "PatSynD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PatSynArgs)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PatSynDir) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat)))) :+: (C1 ('MetaCons "PatSynSigD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PatSynType)) :+: C1 ('MetaCons "ImplicitParamBindD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)))))))

Methods

from :: Dec -> Rep Dec x #

to :: Rep Dec x -> Dec #

Show Dec # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

showsPrec :: Int -> Dec -> ShowS #

show :: Dec -> String #

showList :: [Dec] -> ShowS #

Eq Dec # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord Dec # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

compare :: Dec -> Dec -> Ordering #

(<) :: Dec -> Dec -> Bool #

(<=) :: Dec -> Dec -> Bool #

(>) :: Dec -> Dec -> Bool #

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

max :: Dec -> Dec -> Dec #

min :: Dec -> Dec -> Dec #

Lift Dec # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Dec -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Dec -> Code m Dec #

type Rep Dec # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Dec = D1 ('MetaData "Dec" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) ((((C1 ('MetaCons "FunD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Clause])) :+: (C1 ('MetaCons "ValD" '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]))) :+: C1 ('MetaCons "DataD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr BndrVis]))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Kind)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Con]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DerivClause])))))) :+: (C1 ('MetaCons "NewtypeD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr BndrVis]))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Kind)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Con) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DerivClause])))) :+: (C1 ('MetaCons "TypeDataD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr BndrVis])) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Kind)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Con]))) :+: C1 ('MetaCons "TySynD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr BndrVis]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)))))) :+: ((C1 ('MetaCons "ClassD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr BndrVis]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FunDep]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Dec])))) :+: (C1 ('MetaCons "InstanceD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Overlap)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Dec]))) :+: C1 ('MetaCons "SigD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)))) :+: ((C1 ('MetaCons "KiSigD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind)) :+: C1 ('MetaCons "ForeignD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Foreign))) :+: (C1 ('MetaCons "InfixD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Fixity) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NamespaceSpecifier) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))) :+: C1 ('MetaCons "DefaultD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Type])))))) :+: (((C1 ('MetaCons "PragmaD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pragma)) :+: (C1 ('MetaCons "DataFamilyD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr BndrVis]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Kind)))) :+: C1 ('MetaCons "DataInstD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [TyVarBndr ()])) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Kind)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Con]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DerivClause])))))) :+: (C1 ('MetaCons "NewtypeInstD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [TyVarBndr ()])) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Kind)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Con) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [DerivClause])))) :+: (C1 ('MetaCons "TySynInstD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TySynEqn)) :+: C1 ('MetaCons "OpenTypeFamilyD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TypeFamilyHead))))) :+: ((C1 ('MetaCons "ClosedTypeFamilyD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TypeFamilyHead) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TySynEqn])) :+: (C1 ('MetaCons "RoleAnnotD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Role])) :+: C1 ('MetaCons "StandaloneDerivD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe DerivStrategy)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))))) :+: ((C1 ('MetaCons "DefaultSigD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :+: C1 ('MetaCons "PatSynD" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PatSynArgs)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PatSynDir) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat)))) :+: (C1 ('MetaCons "PatSynSigD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PatSynType)) :+: C1 ('MetaCons "ImplicitParamBindD" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)))))))

data DecidedStrictness #

Instances

Instances details
Ppr DecidedStrictness Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Data DecidedStrictness # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: DecidedStrictness -> Constr #

dataTypeOf :: DecidedStrictness -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic DecidedStrictness # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep DecidedStrictness 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep DecidedStrictness = D1 ('MetaData "DecidedStrictness" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (C1 ('MetaCons "DecidedLazy" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DecidedStrict" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DecidedUnpack" 'PrefixI 'False) (U1 :: Type -> Type)))
Show DecidedStrictness # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq DecidedStrictness # 
Instance details

Defined in GHC.Internal.TH.Syntax

Ord DecidedStrictness # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift DecidedStrictness # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => DecidedStrictness -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => DecidedStrictness -> Code m DecidedStrictness #

type Rep DecidedStrictness # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep DecidedStrictness = D1 ('MetaData "DecidedStrictness" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (C1 ('MetaCons "DecidedLazy" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DecidedStrict" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DecidedUnpack" 'PrefixI 'False) (U1 :: Type -> Type)))

data DerivClause #

Instances

Instances details
Data DerivClause # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: DerivClause -> Constr #

dataTypeOf :: DerivClause -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic DerivClause # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep DerivClause 
Instance details

Defined in GHC.Internal.TH.Syntax

Show DerivClause # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq DerivClause # 
Instance details

Defined in GHC.Internal.TH.Syntax

Ord DerivClause # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift DerivClause # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => DerivClause -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => DerivClause -> Code m DerivClause #

type Rep DerivClause # 
Instance details

Defined in GHC.Internal.TH.Syntax

data DerivStrategy #

Instances

Instances details
Data DerivStrategy # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: DerivStrategy -> Constr #

dataTypeOf :: DerivStrategy -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic DerivStrategy # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep DerivStrategy 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep DerivStrategy = D1 ('MetaData "DerivStrategy" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) ((C1 ('MetaCons "StockStrategy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AnyclassStrategy" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NewtypeStrategy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ViaStrategy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))))
Show DerivStrategy # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq DerivStrategy # 
Instance details

Defined in GHC.Internal.TH.Syntax

Ord DerivStrategy # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift DerivStrategy # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => DerivStrategy -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => DerivStrategy -> Code m DerivStrategy #

type Rep DerivStrategy # 
Instance details

Defined in GHC.Internal.TH.Syntax

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

data DocLoc #

Instances

Instances details
Data DocLoc # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: DocLoc -> Constr #

dataTypeOf :: DocLoc -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic DocLoc # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

from :: DocLoc -> Rep DocLoc x #

to :: Rep DocLoc x -> DocLoc #

Show DocLoc # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq DocLoc # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord DocLoc # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift DocLoc # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => DocLoc -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => DocLoc -> Code m DocLoc #

type Rep DocLoc # 
Instance details

Defined in GHC.Internal.TH.Syntax

data Exp #

Instances

Instances details
Ppr Exp Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Methods

ppr :: Exp -> Doc Source #

ppr_list :: [Exp] -> Doc Source #

Data Exp # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Exp -> Constr #

dataTypeOf :: Exp -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Exp # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep Exp 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Exp = D1 ('MetaData "Exp" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (((((C1 ('MetaCons "VarE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :+: C1 ('MetaCons "ConE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))) :+: (C1 ('MetaCons "LitE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Lit)) :+: C1 ('MetaCons "AppE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)))) :+: ((C1 ('MetaCons "AppTypeE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :+: C1 ('MetaCons "InfixE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Exp)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Exp))))) :+: (C1 ('MetaCons "UInfixE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp))) :+: (C1 ('MetaCons "ParensE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) :+: C1 ('MetaCons "LamE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pat]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)))))) :+: (((C1 ('MetaCons "LamCaseE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Match])) :+: C1 ('MetaCons "LamCasesE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Clause]))) :+: (C1 ('MetaCons "TupE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Maybe Exp])) :+: (C1 ('MetaCons "UnboxedTupE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Maybe Exp])) :+: C1 ('MetaCons "UnboxedSumE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SumAlt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SumArity)))))) :+: ((C1 ('MetaCons "CondE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp))) :+: C1 ('MetaCons "MultiIfE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Guard, Exp)]))) :+: (C1 ('MetaCons "LetE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Dec]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) :+: (C1 ('MetaCons "CaseE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Match])) :+: C1 ('MetaCons "DoE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ModName)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Stmt]))))))) :+: ((((C1 ('MetaCons "MDoE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ModName)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Stmt])) :+: C1 ('MetaCons "CompE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Stmt]))) :+: (C1 ('MetaCons "ArithSeqE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range)) :+: C1 ('MetaCons "ListE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Exp])))) :+: ((C1 ('MetaCons "SigE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :+: C1 ('MetaCons "RecConE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FieldExp]))) :+: (C1 ('MetaCons "RecUpdE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FieldExp])) :+: (C1 ('MetaCons "StaticE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) :+: C1 ('MetaCons "UnboundVarE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)))))) :+: (((C1 ('MetaCons "LabelE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "ImplicitParamVarE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "GetFieldE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: (C1 ('MetaCons "ProjectionE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty String))) :+: C1 ('MetaCons "TypedBracketE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp))))) :+: ((C1 ('MetaCons "TypedSpliceE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) :+: C1 ('MetaCons "TypeE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))) :+: (C1 ('MetaCons "ForallE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr Specificity]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) :+: (C1 ('MetaCons "ForallVisE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr ()]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) :+: C1 ('MetaCons "ConstrainedE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Exp]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp))))))))

Methods

from :: Exp -> Rep Exp x #

to :: Rep Exp x -> Exp #

Show Exp # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

showsPrec :: Int -> Exp -> ShowS #

show :: Exp -> String #

showList :: [Exp] -> ShowS #

Eq Exp # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord Exp # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

compare :: Exp -> Exp -> Ordering #

(<) :: Exp -> Exp -> Bool #

(<=) :: Exp -> Exp -> Bool #

(>) :: Exp -> Exp -> Bool #

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

max :: Exp -> Exp -> Exp #

min :: Exp -> Exp -> Exp #

Lift Exp # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Exp -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Exp -> Code m Exp #

type Rep Exp # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Exp = D1 ('MetaData "Exp" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (((((C1 ('MetaCons "VarE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :+: C1 ('MetaCons "ConE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))) :+: (C1 ('MetaCons "LitE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Lit)) :+: C1 ('MetaCons "AppE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)))) :+: ((C1 ('MetaCons "AppTypeE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :+: C1 ('MetaCons "InfixE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Exp)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Exp))))) :+: (C1 ('MetaCons "UInfixE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp))) :+: (C1 ('MetaCons "ParensE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) :+: C1 ('MetaCons "LamE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pat]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)))))) :+: (((C1 ('MetaCons "LamCaseE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Match])) :+: C1 ('MetaCons "LamCasesE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Clause]))) :+: (C1 ('MetaCons "TupE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Maybe Exp])) :+: (C1 ('MetaCons "UnboxedTupE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Maybe Exp])) :+: C1 ('MetaCons "UnboxedSumE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SumAlt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SumArity)))))) :+: ((C1 ('MetaCons "CondE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp))) :+: C1 ('MetaCons "MultiIfE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Guard, Exp)]))) :+: (C1 ('MetaCons "LetE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Dec]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) :+: (C1 ('MetaCons "CaseE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Match])) :+: C1 ('MetaCons "DoE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ModName)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Stmt]))))))) :+: ((((C1 ('MetaCons "MDoE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ModName)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Stmt])) :+: C1 ('MetaCons "CompE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Stmt]))) :+: (C1 ('MetaCons "ArithSeqE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range)) :+: C1 ('MetaCons "ListE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Exp])))) :+: ((C1 ('MetaCons "SigE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :+: C1 ('MetaCons "RecConE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FieldExp]))) :+: (C1 ('MetaCons "RecUpdE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FieldExp])) :+: (C1 ('MetaCons "StaticE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) :+: C1 ('MetaCons "UnboundVarE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)))))) :+: (((C1 ('MetaCons "LabelE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "ImplicitParamVarE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "GetFieldE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: (C1 ('MetaCons "ProjectionE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty String))) :+: C1 ('MetaCons "TypedBracketE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp))))) :+: ((C1 ('MetaCons "TypedSpliceE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) :+: C1 ('MetaCons "TypeE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))) :+: (C1 ('MetaCons "ForallE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr Specificity]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) :+: (C1 ('MetaCons "ForallVisE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr ()]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) :+: C1 ('MetaCons "ConstrainedE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Exp]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp))))))))

data FamilyResultSig #

Constructors

NoSig 
KindSig Kind 
TyVarSig (TyVarBndr ()) 

Instances

Instances details
Ppr FamilyResultSig Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Data FamilyResultSig # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: FamilyResultSig -> Constr #

dataTypeOf :: FamilyResultSig -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic FamilyResultSig # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep FamilyResultSig 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep FamilyResultSig = D1 ('MetaData "FamilyResultSig" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (C1 ('MetaCons "NoSig" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KindSig" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind)) :+: C1 ('MetaCons "TyVarSig" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TyVarBndr ())))))
Show FamilyResultSig # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq FamilyResultSig # 
Instance details

Defined in GHC.Internal.TH.Syntax

Ord FamilyResultSig # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift FamilyResultSig # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => FamilyResultSig -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => FamilyResultSig -> Code m FamilyResultSig #

type Rep FamilyResultSig # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep FamilyResultSig = D1 ('MetaData "FamilyResultSig" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (C1 ('MetaCons "NoSig" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KindSig" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind)) :+: C1 ('MetaCons "TyVarSig" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TyVarBndr ())))))

type FieldExp = (Name, Exp) #

type FieldPat = (Name, Pat) #

data Fixity #

Constructors

Fixity Int FixityDirection 

Instances

Instances details
Data Fixity # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Fixity -> Constr #

dataTypeOf :: Fixity -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Fixity # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep Fixity 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Show Fixity # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Fixity # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord Fixity # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift Fixity # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Fixity -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Fixity -> Code m Fixity #

type Rep Fixity # 
Instance details

Defined in GHC.Internal.TH.Syntax

data FixityDirection #

Constructors

InfixL 
InfixR 
InfixN 

Instances

Instances details
Data FixityDirection # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: FixityDirection -> Constr #

dataTypeOf :: FixityDirection -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic FixityDirection # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep FixityDirection 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep FixityDirection = D1 ('MetaData "FixityDirection" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (C1 ('MetaCons "InfixL" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "InfixR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InfixN" 'PrefixI 'False) (U1 :: Type -> Type)))
Show FixityDirection # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq FixityDirection # 
Instance details

Defined in GHC.Internal.TH.Syntax

Ord FixityDirection # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift FixityDirection # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => FixityDirection -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => FixityDirection -> Code m FixityDirection #

type Rep FixityDirection # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep FixityDirection = D1 ('MetaData "FixityDirection" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (C1 ('MetaCons "InfixL" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "InfixR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InfixN" 'PrefixI 'False) (U1 :: Type -> Type)))

data Foreign #

Instances

Instances details
Ppr Foreign Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Data Foreign # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Foreign -> Constr #

dataTypeOf :: Foreign -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Foreign # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

from :: Foreign -> Rep Foreign x #

to :: Rep Foreign x -> Foreign #

Show Foreign # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Foreign # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord Foreign # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift Foreign # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Foreign -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Foreign -> Code m Foreign #

type Rep Foreign # 
Instance details

Defined in GHC.Internal.TH.Syntax

data FunDep #

Constructors

FunDep [Name] [Name] 

Instances

Instances details
Ppr FunDep Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Methods

ppr :: FunDep -> Doc Source #

ppr_list :: [FunDep] -> Doc Source #

Data FunDep # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: FunDep -> Constr #

dataTypeOf :: FunDep -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic FunDep # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep FunDep 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

from :: FunDep -> Rep FunDep x #

to :: Rep FunDep x -> FunDep #

Show FunDep # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq FunDep # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord FunDep # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift FunDep # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => FunDep -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => FunDep -> Code m FunDep #

type Rep FunDep # 
Instance details

Defined in GHC.Internal.TH.Syntax

data Guard #

Constructors

NormalG Exp 
PatG [Stmt] 

Instances

Instances details
Data Guard # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Guard -> Constr #

dataTypeOf :: Guard -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Guard # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep Guard 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

from :: Guard -> Rep Guard x #

to :: Rep Guard x -> Guard #

Show Guard # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

showsPrec :: Int -> Guard -> ShowS #

show :: Guard -> String #

showList :: [Guard] -> ShowS #

Eq Guard # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord Guard # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

compare :: Guard -> Guard -> Ordering #

(<) :: Guard -> Guard -> Bool #

(<=) :: Guard -> Guard -> Bool #

(>) :: Guard -> Guard -> Bool #

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

max :: Guard -> Guard -> Guard #

min :: Guard -> Guard -> Guard #

Lift Guard # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Guard -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Guard -> Code m Guard #

type Rep Guard # 
Instance details

Defined in GHC.Internal.TH.Syntax

data Info #

Instances

Instances details
Ppr Info Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Methods

ppr :: Info -> Doc Source #

ppr_list :: [Info] -> Doc Source #

Data Info # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Info -> Constr #

dataTypeOf :: Info -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Info # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep Info 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Info = D1 ('MetaData "Info" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (((C1 ('MetaCons "ClassI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Dec) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [InstanceDec])) :+: C1 ('MetaCons "ClassOpI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ParentName)))) :+: (C1 ('MetaCons "TyConI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Dec)) :+: C1 ('MetaCons "FamilyI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Dec) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [InstanceDec])))) :+: ((C1 ('MetaCons "PrimTyConI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Arity) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Unlifted))) :+: C1 ('MetaCons "DataConI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ParentName)))) :+: (C1 ('MetaCons "PatSynI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PatSynType)) :+: (C1 ('MetaCons "VarI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Dec)))) :+: C1 ('MetaCons "TyVarI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))))))

Methods

from :: Info -> Rep Info x #

to :: Rep Info x -> Info #

Show Info # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

showsPrec :: Int -> Info -> ShowS #

show :: Info -> String #

showList :: [Info] -> ShowS #

Eq Info # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord Info # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

compare :: Info -> Info -> Ordering #

(<) :: Info -> Info -> Bool #

(<=) :: Info -> Info -> Bool #

(>) :: Info -> Info -> Bool #

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

max :: Info -> Info -> Info #

min :: Info -> Info -> Info #

Lift Info # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Info -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Info -> Code m Info #

type Rep Info # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Info = D1 ('MetaData "Info" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (((C1 ('MetaCons "ClassI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Dec) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [InstanceDec])) :+: C1 ('MetaCons "ClassOpI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ParentName)))) :+: (C1 ('MetaCons "TyConI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Dec)) :+: C1 ('MetaCons "FamilyI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Dec) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [InstanceDec])))) :+: ((C1 ('MetaCons "PrimTyConI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Arity) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Unlifted))) :+: C1 ('MetaCons "DataConI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ParentName)))) :+: (C1 ('MetaCons "PatSynI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PatSynType)) :+: (C1 ('MetaCons "VarI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Dec)))) :+: C1 ('MetaCons "TyVarI" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))))))

data InjectivityAnn #

Constructors

InjectivityAnn Name [Name] 

Instances

Instances details
Ppr InjectivityAnn Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Data InjectivityAnn # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: InjectivityAnn -> Constr #

dataTypeOf :: InjectivityAnn -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic InjectivityAnn # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep InjectivityAnn 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep InjectivityAnn = D1 ('MetaData "InjectivityAnn" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (C1 ('MetaCons "InjectivityAnn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name])))
Show InjectivityAnn # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq InjectivityAnn # 
Instance details

Defined in GHC.Internal.TH.Syntax

Ord InjectivityAnn # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift InjectivityAnn # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => InjectivityAnn -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => InjectivityAnn -> Code m InjectivityAnn #

type Rep InjectivityAnn # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep InjectivityAnn = D1 ('MetaData "InjectivityAnn" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (C1 ('MetaCons "InjectivityAnn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name])))

data Inline #

Constructors

NoInline 
Inline 
Inlinable 

Instances

Instances details
Ppr Inline Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Methods

ppr :: Inline -> Doc Source #

ppr_list :: [Inline] -> Doc Source #

Data Inline # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Inline -> Constr #

dataTypeOf :: Inline -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Inline # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep Inline 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Inline = D1 ('MetaData "Inline" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (C1 ('MetaCons "NoInline" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Inline" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Inlinable" 'PrefixI 'False) (U1 :: Type -> Type)))

Methods

from :: Inline -> Rep Inline x #

to :: Rep Inline x -> Inline #

Show Inline # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Inline # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord Inline # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift Inline # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Inline -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Inline -> Code m Inline #

type Rep Inline # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Inline = D1 ('MetaData "Inline" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (C1 ('MetaCons "NoInline" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Inline" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Inlinable" 'PrefixI 'False) (U1 :: Type -> Type)))

type Kind = Type #

data Lit #

Instances

Instances details
Ppr Lit Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Methods

ppr :: Lit -> Doc Source #

ppr_list :: [Lit] -> Doc Source #

Data Lit # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Lit -> Constr #

dataTypeOf :: Lit -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Lit # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep Lit 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Lit = D1 ('MetaData "Lit" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (((C1 ('MetaCons "CharL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char)) :+: C1 ('MetaCons "StringL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "IntegerL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)) :+: (C1 ('MetaCons "RationalL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational)) :+: C1 ('MetaCons "IntPrimL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer))))) :+: ((C1 ('MetaCons "WordPrimL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)) :+: (C1 ('MetaCons "FloatPrimL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational)) :+: C1 ('MetaCons "DoublePrimL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational)))) :+: (C1 ('MetaCons "StringPrimL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Word8])) :+: (C1 ('MetaCons "BytesPrimL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bytes)) :+: C1 ('MetaCons "CharPrimL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char))))))

Methods

from :: Lit -> Rep Lit x #

to :: Rep Lit x -> Lit #

Show Lit # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

showsPrec :: Int -> Lit -> ShowS #

show :: Lit -> String #

showList :: [Lit] -> ShowS #

Eq Lit # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord Lit # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

compare :: Lit -> Lit -> Ordering #

(<) :: Lit -> Lit -> Bool #

(<=) :: Lit -> Lit -> Bool #

(>) :: Lit -> Lit -> Bool #

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

max :: Lit -> Lit -> Lit #

min :: Lit -> Lit -> Lit #

Lift Lit # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Lit -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Lit -> Code m Lit #

type Rep Lit # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Lit = D1 ('MetaData "Lit" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (((C1 ('MetaCons "CharL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char)) :+: C1 ('MetaCons "StringL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :+: (C1 ('MetaCons "IntegerL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)) :+: (C1 ('MetaCons "RationalL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational)) :+: C1 ('MetaCons "IntPrimL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer))))) :+: ((C1 ('MetaCons "WordPrimL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)) :+: (C1 ('MetaCons "FloatPrimL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational)) :+: C1 ('MetaCons "DoublePrimL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational)))) :+: (C1 ('MetaCons "StringPrimL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Word8])) :+: (C1 ('MetaCons "BytesPrimL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bytes)) :+: C1 ('MetaCons "CharPrimL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char))))))

data Loc #

Instances

Instances details
Ppr Loc Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Methods

ppr :: Loc -> Doc Source #

ppr_list :: [Loc] -> Doc Source #

Data Loc # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Loc -> Constr #

dataTypeOf :: Loc -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Loc # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep Loc 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

from :: Loc -> Rep Loc x #

to :: Rep Loc x -> Loc #

Show Loc # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

showsPrec :: Int -> Loc -> ShowS #

show :: Loc -> String #

showList :: [Loc] -> ShowS #

Eq Loc # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord Loc # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

compare :: Loc -> Loc -> Ordering #

(<) :: Loc -> Loc -> Bool #

(<=) :: Loc -> Loc -> Bool #

(>) :: Loc -> Loc -> Bool #

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

max :: Loc -> Loc -> Loc #

min :: Loc -> Loc -> Loc #

Lift Loc # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Loc -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Loc -> Code m Loc #

type Rep Loc # 
Instance details

Defined in GHC.Internal.TH.Syntax

data Match #

Constructors

Match Pat Body [Dec] 

Instances

Instances details
Ppr Match Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Methods

ppr :: Match -> Doc Source #

ppr_list :: [Match] -> Doc Source #

Data Match # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Match -> Constr #

dataTypeOf :: Match -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Match # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

from :: Match -> Rep Match x #

to :: Rep Match x -> Match #

Show Match # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

showsPrec :: Int -> Match -> ShowS #

show :: Match -> String #

showList :: [Match] -> ShowS #

Eq Match # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord Match # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

compare :: Match -> Match -> Ordering #

(<) :: Match -> Match -> Bool #

(<=) :: Match -> Match -> Bool #

(>) :: Match -> Match -> Bool #

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

max :: Match -> Match -> Match #

min :: Match -> Match -> Match #

Lift Match # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Match -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Match -> Code m Match #

type Rep Match # 
Instance details

Defined in GHC.Internal.TH.Syntax

newtype ModName #

Constructors

ModName String 

Instances

Instances details
Data ModName # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: ModName -> Constr #

dataTypeOf :: ModName -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic ModName # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep ModName 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep ModName = D1 ('MetaData "ModName" "GHC.Internal.TH.Syntax" "ghc-internal" 'True) (C1 ('MetaCons "ModName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

Methods

from :: ModName -> Rep ModName x #

to :: Rep ModName x -> ModName #

Show ModName # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq ModName # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord ModName # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift ModName # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => ModName -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => ModName -> Code m ModName #

type Rep ModName # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep ModName = D1 ('MetaData "ModName" "GHC.Internal.TH.Syntax" "ghc-internal" 'True) (C1 ('MetaCons "ModName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

data Module #

Constructors

Module PkgName ModName 

Instances

Instances details
Ppr Module Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Methods

ppr :: Module -> Doc Source #

ppr_list :: [Module] -> Doc Source #

Data Module # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Module -> Constr #

dataTypeOf :: Module -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Module # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep Module 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

from :: Module -> Rep Module x #

to :: Rep Module x -> Module #

Show Module # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Module # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord Module # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift Module # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Module -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Module -> Code m Module #

type Rep Module # 
Instance details

Defined in GHC.Internal.TH.Syntax

data ModuleInfo #

Constructors

ModuleInfo [Module] 

Instances

Instances details
Ppr ModuleInfo Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Data ModuleInfo # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: ModuleInfo -> Constr #

dataTypeOf :: ModuleInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic ModuleInfo # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep ModuleInfo 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep ModuleInfo = D1 ('MetaData "ModuleInfo" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (C1 ('MetaCons "ModuleInfo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Module])))
Show ModuleInfo # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq ModuleInfo # 
Instance details

Defined in GHC.Internal.TH.Syntax

Ord ModuleInfo # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep ModuleInfo # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep ModuleInfo = D1 ('MetaData "ModuleInfo" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (C1 ('MetaCons "ModuleInfo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Module])))

data Name #

Constructors

Name OccName NameFlavour 

Instances

Instances details
Ppr Name Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Methods

ppr :: Name -> Doc Source #

ppr_list :: [Name] -> Doc Source #

Data Name # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Name -> Constr #

dataTypeOf :: Name -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Name # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep Name 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

Show Name # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Eq Name # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord Name # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

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

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Lift Name # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Name -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Name -> Code m Name #

type Rep Name # 
Instance details

Defined in GHC.Internal.TH.Syntax

data NameFlavour #

Instances

Instances details
Data NameFlavour # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: NameFlavour -> Constr #

dataTypeOf :: NameFlavour -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic NameFlavour # 
Instance details

Defined in GHC.Internal.TH.Syntax

Show NameFlavour # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq NameFlavour # 
Instance details

Defined in GHC.Internal.TH.Syntax

Ord NameFlavour # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift NameFlavour # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => NameFlavour -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => NameFlavour -> Code m NameFlavour #

type Rep NameFlavour # 
Instance details

Defined in GHC.Internal.TH.Syntax

data NameIs #

Constructors

Alone 
Applied 
Infix 

Instances

Instances details
Lift NameIs # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => NameIs -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => NameIs -> Code m NameIs #

data NameSpace #

Constructors

VarName 
DataName 
TcClsName 
FldName 

Fields

Instances

Instances details
Data NameSpace # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: NameSpace -> Constr #

dataTypeOf :: NameSpace -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic NameSpace # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep NameSpace 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep NameSpace = D1 ('MetaData "NameSpace" "GHC.Internal.TH.Syntax" "ghc-internal" '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) :+: C1 ('MetaCons "FldName" 'PrefixI 'True) (S1 ('MetaSel ('Just "fldParent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String))))
Show NameSpace # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq NameSpace # 
Instance details

Defined in GHC.Internal.TH.Syntax

Ord NameSpace # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift NameSpace # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => NameSpace -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => NameSpace -> Code m NameSpace #

type Rep NameSpace # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep NameSpace = D1 ('MetaData "NameSpace" "GHC.Internal.TH.Syntax" "ghc-internal" '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) :+: C1 ('MetaCons "FldName" 'PrefixI 'True) (S1 ('MetaSel ('Just "fldParent") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String))))

data NamespaceSpecifier #

Instances

Instances details
Data NamespaceSpecifier # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: NamespaceSpecifier -> Constr #

dataTypeOf :: NamespaceSpecifier -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic NamespaceSpecifier # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep NamespaceSpecifier 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep NamespaceSpecifier = D1 ('MetaData "NamespaceSpecifier" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (C1 ('MetaCons "NoNamespaceSpecifier" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TypeNamespaceSpecifier" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DataNamespaceSpecifier" 'PrefixI 'False) (U1 :: Type -> Type)))
Show NamespaceSpecifier # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq NamespaceSpecifier # 
Instance details

Defined in GHC.Internal.TH.Syntax

Ord NamespaceSpecifier # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift NamespaceSpecifier # 
Instance details

Defined in GHC.Internal.TH.Lift

type Rep NamespaceSpecifier # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep NamespaceSpecifier = D1 ('MetaData "NamespaceSpecifier" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (C1 ('MetaCons "NoNamespaceSpecifier" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TypeNamespaceSpecifier" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DataNamespaceSpecifier" 'PrefixI 'False) (U1 :: Type -> Type)))

newtype OccName #

Constructors

OccName String 

Instances

Instances details
Data OccName # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: OccName -> Constr #

dataTypeOf :: OccName -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic OccName # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep OccName 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep OccName = D1 ('MetaData "OccName" "GHC.Internal.TH.Syntax" "ghc-internal" 'True) (C1 ('MetaCons "OccName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

Methods

from :: OccName -> Rep OccName x #

to :: Rep OccName x -> OccName #

Show OccName # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq OccName # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord OccName # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift OccName # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => OccName -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => OccName -> Code m OccName #

type Rep OccName # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep OccName = D1 ('MetaData "OccName" "GHC.Internal.TH.Syntax" "ghc-internal" 'True) (C1 ('MetaCons "OccName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

data Overlap #

Instances

Instances details
Data Overlap # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Overlap -> Constr #

dataTypeOf :: Overlap -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Overlap # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep Overlap 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Overlap = D1 ('MetaData "Overlap" "GHC.Internal.TH.Syntax" "ghc-internal" '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)))

Methods

from :: Overlap -> Rep Overlap x #

to :: Rep Overlap x -> Overlap #

Show Overlap # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Overlap # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord Overlap # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift Overlap # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Overlap -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Overlap -> Code m Overlap #

type Rep Overlap # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Overlap = D1 ('MetaData "Overlap" "GHC.Internal.TH.Syntax" "ghc-internal" '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)))

data Pat #

Instances

Instances details
Ppr Pat Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Methods

ppr :: Pat -> Doc Source #

ppr_list :: [Pat] -> Doc Source #

Data Pat # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Pat -> Constr #

dataTypeOf :: Pat -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Pat # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep Pat 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Pat = D1 ('MetaData "Pat" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) ((((C1 ('MetaCons "LitP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Lit)) :+: C1 ('MetaCons "VarP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))) :+: (C1 ('MetaCons "TupP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pat])) :+: (C1 ('MetaCons "UnboxedTupP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pat])) :+: C1 ('MetaCons "UnboxedSumP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SumAlt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SumArity)))))) :+: ((C1 ('MetaCons "ConP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Type]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pat]))) :+: C1 ('MetaCons "InfixP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat)))) :+: (C1 ('MetaCons "UInfixP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat))) :+: (C1 ('MetaCons "ParensP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat)) :+: C1 ('MetaCons "TildeP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat)))))) :+: (((C1 ('MetaCons "BangP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat)) :+: C1 ('MetaCons "AsP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat))) :+: (C1 ('MetaCons "WildP" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RecP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FieldPat])) :+: C1 ('MetaCons "ListP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pat]))))) :+: ((C1 ('MetaCons "SigP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :+: C1 ('MetaCons "ViewP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat))) :+: (C1 ('MetaCons "TypeP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :+: (C1 ('MetaCons "InvisP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :+: C1 ('MetaCons "OrP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Pat))))))))

Methods

from :: Pat -> Rep Pat x #

to :: Rep Pat x -> Pat #

Show Pat # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

showsPrec :: Int -> Pat -> ShowS #

show :: Pat -> String #

showList :: [Pat] -> ShowS #

Eq Pat # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord Pat # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

compare :: Pat -> Pat -> Ordering #

(<) :: Pat -> Pat -> Bool #

(<=) :: Pat -> Pat -> Bool #

(>) :: Pat -> Pat -> Bool #

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

max :: Pat -> Pat -> Pat #

min :: Pat -> Pat -> Pat #

Lift Pat # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Pat -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Pat -> Code m Pat #

type Rep Pat # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Pat = D1 ('MetaData "Pat" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) ((((C1 ('MetaCons "LitP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Lit)) :+: C1 ('MetaCons "VarP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))) :+: (C1 ('MetaCons "TupP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pat])) :+: (C1 ('MetaCons "UnboxedTupP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pat])) :+: C1 ('MetaCons "UnboxedSumP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SumAlt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SumArity)))))) :+: ((C1 ('MetaCons "ConP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Type]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pat]))) :+: C1 ('MetaCons "InfixP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat)))) :+: (C1 ('MetaCons "UInfixP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat))) :+: (C1 ('MetaCons "ParensP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat)) :+: C1 ('MetaCons "TildeP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat)))))) :+: (((C1 ('MetaCons "BangP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat)) :+: C1 ('MetaCons "AsP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat))) :+: (C1 ('MetaCons "WildP" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RecP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FieldPat])) :+: C1 ('MetaCons "ListP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Pat]))))) :+: ((C1 ('MetaCons "SigP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :+: C1 ('MetaCons "ViewP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Pat))) :+: (C1 ('MetaCons "TypeP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :+: (C1 ('MetaCons "InvisP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :+: C1 ('MetaCons "OrP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Pat))))))))

data PatSynArgs #

Instances

Instances details
Ppr PatSynArgs Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Data PatSynArgs # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: PatSynArgs -> Constr #

dataTypeOf :: PatSynArgs -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic PatSynArgs # 
Instance details

Defined in GHC.Internal.TH.Syntax

Show PatSynArgs # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq PatSynArgs # 
Instance details

Defined in GHC.Internal.TH.Syntax

Ord PatSynArgs # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift PatSynArgs # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => PatSynArgs -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => PatSynArgs -> Code m PatSynArgs #

type Rep PatSynArgs # 
Instance details

Defined in GHC.Internal.TH.Syntax

data PatSynDir #

Constructors

Unidir 
ImplBidir 
ExplBidir [Clause] 

Instances

Instances details
Ppr PatSynDir Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Data PatSynDir # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: PatSynDir -> Constr #

dataTypeOf :: PatSynDir -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic PatSynDir # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep PatSynDir 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep PatSynDir = D1 ('MetaData "PatSynDir" "GHC.Internal.TH.Syntax" "ghc-internal" '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]))))
Show PatSynDir # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq PatSynDir # 
Instance details

Defined in GHC.Internal.TH.Syntax

Ord PatSynDir # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift PatSynDir # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => PatSynDir -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => PatSynDir -> Code m PatSynDir #

type Rep PatSynDir # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep PatSynDir = D1 ('MetaData "PatSynDir" "GHC.Internal.TH.Syntax" "ghc-internal" '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 Phases #

Instances

Instances details
Ppr Phases Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Methods

ppr :: Phases -> Doc Source #

ppr_list :: [Phases] -> Doc Source #

Data Phases # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Phases -> Constr #

dataTypeOf :: Phases -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Phases # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep Phases 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Phases = D1 ('MetaData "Phases" "GHC.Internal.TH.Syntax" "ghc-internal" '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))))

Methods

from :: Phases -> Rep Phases x #

to :: Rep Phases x -> Phases #

Show Phases # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Phases # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord Phases # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift Phases # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Phases -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Phases -> Code m Phases #

type Rep Phases # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Phases = D1 ('MetaData "Phases" "GHC.Internal.TH.Syntax" "ghc-internal" '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))))

newtype PkgName #

Constructors

PkgName String 

Instances

Instances details
Data PkgName # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: PkgName -> Constr #

dataTypeOf :: PkgName -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic PkgName # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep PkgName 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep PkgName = D1 ('MetaData "PkgName" "GHC.Internal.TH.Syntax" "ghc-internal" 'True) (C1 ('MetaCons "PkgName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

Methods

from :: PkgName -> Rep PkgName x #

to :: Rep PkgName x -> PkgName #

Show PkgName # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq PkgName # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord PkgName # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift PkgName # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => PkgName -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => PkgName -> Code m PkgName #

type Rep PkgName # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep PkgName = D1 ('MetaData "PkgName" "GHC.Internal.TH.Syntax" "ghc-internal" 'True) (C1 ('MetaCons "PkgName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))

data Pragma #

Instances

Instances details
Ppr Pragma Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Methods

ppr :: Pragma -> Doc Source #

ppr_list :: [Pragma] -> Doc Source #

Data Pragma # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Pragma -> Constr #

dataTypeOf :: Pragma -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Pragma # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep Pragma 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Pragma = D1 ('MetaData "Pragma" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (((C1 ('MetaCons "InlineP" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Inline)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RuleMatch) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Phases))) :+: C1 ('MetaCons "OpaqueP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))) :+: (C1 ('MetaCons "SpecialiseP" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Inline)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Phases))) :+: C1 ('MetaCons "SpecialiseInstP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)))) :+: ((C1 ('MetaCons "RuleP" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [TyVarBndr ()])) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RuleBndr]))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Phases)))) :+: C1 ('MetaCons "AnnP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AnnTarget) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp))) :+: (C1 ('MetaCons "LineP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: (C1 ('MetaCons "CompleteP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Name))) :+: C1 ('MetaCons "SCCP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)))))))

Methods

from :: Pragma -> Rep Pragma x #

to :: Rep Pragma x -> Pragma #

Show Pragma # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Pragma # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord Pragma # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift Pragma # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Pragma -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Pragma -> Code m Pragma #

type Rep Pragma # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Pragma = D1 ('MetaData "Pragma" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (((C1 ('MetaCons "InlineP" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Inline)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RuleMatch) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Phases))) :+: C1 ('MetaCons "OpaqueP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))) :+: (C1 ('MetaCons "SpecialiseP" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Inline)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Phases))) :+: C1 ('MetaCons "SpecialiseInstP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)))) :+: ((C1 ('MetaCons "RuleP" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [TyVarBndr ()])) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [RuleBndr]))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Phases)))) :+: C1 ('MetaCons "AnnP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AnnTarget) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp))) :+: (C1 ('MetaCons "LineP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: (C1 ('MetaCons "CompleteP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Name))) :+: C1 ('MetaCons "SCCP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)))))))

type Pred = Type #

newtype Q a #

Constructors

Q 

Fields

Instances

Instances details
Applicative Q # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

pure :: a -> Q a #

(<*>) :: Q (a -> b) -> Q a -> Q b #

liftA2 :: (a -> b -> c) -> Q a -> Q b -> Q c #

(*>) :: Q a -> Q b -> Q b #

(<*) :: Q a -> Q b -> Q a #

Functor Q # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

fmap :: (a -> b) -> Q a -> Q b #

(<$) :: a -> Q b -> Q a #

Monad Q # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

(>>=) :: Q a -> (a -> Q b) -> Q b #

(>>) :: Q a -> Q b -> Q b #

return :: a -> Q a #

MonadFail Q # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

fail :: String -> Q a #

MonadFix Q # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

mfix :: (a -> Q a) -> Q a #

MonadIO Q # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

liftIO :: IO a -> Q a #

Quasi Q # 
Instance details

Defined in GHC.Internal.TH.Syntax

Quote Q # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

newName :: String -> Q Name #

Monoid a => Monoid (Q a) # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

mempty :: Q a #

mappend :: Q a -> Q a -> Q a #

mconcat :: [Q a] -> Q a #

Semigroup a => Semigroup (Q a) # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

(<>) :: Q a -> Q a -> Q a #

sconcat :: NonEmpty (Q a) -> Q a #

stimes :: Integral b => b -> Q a -> Q a #

class (MonadIO m, MonadFail m) => Quasi (m :: Type -> Type) where #

Instances

Instances details
Quasi Q # 
Instance details

Defined in GHC.Internal.TH.Syntax

Quasi IO # 
Instance details

Defined in GHC.Internal.TH.Syntax

class Monad m => Quote (m :: Type -> Type) where #

Methods

newName :: String -> m Name #

Instances

Instances details
Quote Q # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

newName :: String -> Q Name #

Quote IO # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

newName :: String -> IO Name #

data Range #

Instances

Instances details
Ppr Range Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Methods

ppr :: Range -> Doc Source #

ppr_list :: [Range] -> Doc Source #

Data Range # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Range -> Constr #

dataTypeOf :: Range -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Range # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

from :: Range -> Rep Range x #

to :: Rep Range x -> Range #

Show Range # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

showsPrec :: Int -> Range -> ShowS #

show :: Range -> String #

showList :: [Range] -> ShowS #

Eq Range # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord Range # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

compare :: Range -> Range -> Ordering #

(<) :: Range -> Range -> Bool #

(<=) :: Range -> Range -> Bool #

(>) :: Range -> Range -> Bool #

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

max :: Range -> Range -> Range #

min :: Range -> Range -> Range #

Lift Range # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Range -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Range -> Code m Range #

type Rep Range # 
Instance details

Defined in GHC.Internal.TH.Syntax

data Role #

Instances

Instances details
Ppr Role Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Methods

ppr :: Role -> Doc Source #

ppr_list :: [Role] -> Doc Source #

Data Role # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Role -> Constr #

dataTypeOf :: Role -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Role # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep Role 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Role = D1 ('MetaData "Role" "GHC.Internal.TH.Syntax" "ghc-internal" '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)))

Methods

from :: Role -> Rep Role x #

to :: Rep Role x -> Role #

Show Role # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

showsPrec :: Int -> Role -> ShowS #

show :: Role -> String #

showList :: [Role] -> ShowS #

Eq Role # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord Role # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

compare :: Role -> Role -> Ordering #

(<) :: Role -> Role -> Bool #

(<=) :: Role -> Role -> Bool #

(>) :: Role -> Role -> Bool #

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

max :: Role -> Role -> Role #

min :: Role -> Role -> Role #

Lift Role # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Role -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Role -> Code m Role #

type Rep Role # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Role = D1 ('MetaData "Role" "GHC.Internal.TH.Syntax" "ghc-internal" '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 RuleBndr #

Instances

Instances details
Ppr RuleBndr Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Data RuleBndr # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: RuleBndr -> Constr #

dataTypeOf :: RuleBndr -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic RuleBndr # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep RuleBndr 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

from :: RuleBndr -> Rep RuleBndr x #

to :: Rep RuleBndr x -> RuleBndr #

Show RuleBndr # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq RuleBndr # 
Instance details

Defined in GHC.Internal.TH.Syntax

Ord RuleBndr # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift RuleBndr # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => RuleBndr -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => RuleBndr -> Code m RuleBndr #

type Rep RuleBndr # 
Instance details

Defined in GHC.Internal.TH.Syntax

data RuleMatch #

Constructors

ConLike 
FunLike 

Instances

Instances details
Ppr RuleMatch Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Data RuleMatch # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: RuleMatch -> Constr #

dataTypeOf :: RuleMatch -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic RuleMatch # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep RuleMatch 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep RuleMatch = D1 ('MetaData "RuleMatch" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (C1 ('MetaCons "ConLike" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FunLike" 'PrefixI 'False) (U1 :: Type -> Type))
Show RuleMatch # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq RuleMatch # 
Instance details

Defined in GHC.Internal.TH.Syntax

Ord RuleMatch # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift RuleMatch # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => RuleMatch -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => RuleMatch -> Code m RuleMatch #

type Rep RuleMatch # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep RuleMatch = D1 ('MetaData "RuleMatch" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (C1 ('MetaCons "ConLike" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FunLike" 'PrefixI 'False) (U1 :: Type -> Type))

data Safety #

Constructors

Unsafe 
Safe 
Interruptible 

Instances

Instances details
Data Safety # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Safety -> Constr #

dataTypeOf :: Safety -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Safety # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep Safety 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Safety = D1 ('MetaData "Safety" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (C1 ('MetaCons "Unsafe" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Safe" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Interruptible" 'PrefixI 'False) (U1 :: Type -> Type)))

Methods

from :: Safety -> Rep Safety x #

to :: Rep Safety x -> Safety #

Show Safety # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Safety # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord Safety # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift Safety # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Safety -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Safety -> Code m Safety #

type Rep Safety # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Safety = D1 ('MetaData "Safety" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (C1 ('MetaCons "Unsafe" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Safe" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Interruptible" 'PrefixI 'False) (U1 :: Type -> Type)))

data SourceStrictness #

Instances

Instances details
Ppr SourceStrictness Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Data SourceStrictness # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: SourceStrictness -> Constr #

dataTypeOf :: SourceStrictness -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic SourceStrictness # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep SourceStrictness 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep SourceStrictness = D1 ('MetaData "SourceStrictness" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (C1 ('MetaCons "NoSourceStrictness" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SourceLazy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SourceStrict" 'PrefixI 'False) (U1 :: Type -> Type)))
Show SourceStrictness # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq SourceStrictness # 
Instance details

Defined in GHC.Internal.TH.Syntax

Ord SourceStrictness # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift SourceStrictness # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => SourceStrictness -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => SourceStrictness -> Code m SourceStrictness #

type Rep SourceStrictness # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep SourceStrictness = D1 ('MetaData "SourceStrictness" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (C1 ('MetaCons "NoSourceStrictness" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SourceLazy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SourceStrict" 'PrefixI 'False) (U1 :: Type -> Type)))

data SourceUnpackedness #

Instances

Instances details
Ppr SourceUnpackedness Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Data SourceUnpackedness # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: SourceUnpackedness -> Constr #

dataTypeOf :: SourceUnpackedness -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic SourceUnpackedness # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep SourceUnpackedness 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep SourceUnpackedness = D1 ('MetaData "SourceUnpackedness" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (C1 ('MetaCons "NoSourceUnpackedness" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SourceNoUnpack" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SourceUnpack" 'PrefixI 'False) (U1 :: Type -> Type)))
Show SourceUnpackedness # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq SourceUnpackedness # 
Instance details

Defined in GHC.Internal.TH.Syntax

Ord SourceUnpackedness # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift SourceUnpackedness # 
Instance details

Defined in GHC.Internal.TH.Lift

type Rep SourceUnpackedness # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep SourceUnpackedness = D1 ('MetaData "SourceUnpackedness" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (C1 ('MetaCons "NoSourceUnpackedness" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SourceNoUnpack" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SourceUnpack" 'PrefixI 'False) (U1 :: Type -> Type)))

data Specificity #

Instances

Instances details
PprFlag Specificity Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Data Specificity # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Specificity -> Constr #

dataTypeOf :: Specificity -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Specificity # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep Specificity 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Specificity = D1 ('MetaData "Specificity" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (C1 ('MetaCons "SpecifiedSpec" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InferredSpec" 'PrefixI 'False) (U1 :: Type -> Type))
Show Specificity # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq Specificity # 
Instance details

Defined in GHC.Internal.TH.Syntax

Ord Specificity # 
Instance details

Defined in GHC.Internal.TH.Syntax

DefaultBndrFlag Specificity Source # 
Instance details

Defined in Language.Haskell.TH.Lib

Lift Specificity # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Specificity -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Specificity -> Code m Specificity #

type Rep Specificity # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Specificity = D1 ('MetaData "Specificity" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) (C1 ('MetaCons "SpecifiedSpec" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InferredSpec" 'PrefixI 'False) (U1 :: Type -> Type))

data Stmt #

Constructors

BindS Pat Exp 
LetS [Dec] 
NoBindS Exp 
ParS [[Stmt]] 
RecS [Stmt] 

Instances

Instances details
Ppr Stmt Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Methods

ppr :: Stmt -> Doc Source #

ppr_list :: [Stmt] -> Doc Source #

Data Stmt # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Stmt -> Constr #

dataTypeOf :: Stmt -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Stmt # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

from :: Stmt -> Rep Stmt x #

to :: Rep Stmt x -> Stmt #

Show Stmt # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

showsPrec :: Int -> Stmt -> ShowS #

show :: Stmt -> String #

showList :: [Stmt] -> ShowS #

Eq Stmt # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord Stmt # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

compare :: Stmt -> Stmt -> Ordering #

(<) :: Stmt -> Stmt -> Bool #

(<=) :: Stmt -> Stmt -> Bool #

(>) :: Stmt -> Stmt -> Bool #

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

max :: Stmt -> Stmt -> Stmt #

min :: Stmt -> Stmt -> Stmt #

Lift Stmt # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Stmt -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Stmt -> Code m Stmt #

type Rep Stmt # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Strict = Bang #

type SumAlt = Int #

type SumArity = Int #

newtype TExp (a :: TYPE r) #

Constructors

TExp 

Fields

Instances

Instances details
Lift (TExp a :: Type) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => TExp a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => TExp a -> Code m (TExp a) #

data TyLit #

Instances

Instances details
Ppr TyLit Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Methods

ppr :: TyLit -> Doc Source #

ppr_list :: [TyLit] -> Doc Source #

Data TyLit # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: TyLit -> Constr #

dataTypeOf :: TyLit -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic TyLit # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep TyLit 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

from :: TyLit -> Rep TyLit x #

to :: Rep TyLit x -> TyLit #

Show TyLit # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

showsPrec :: Int -> TyLit -> ShowS #

show :: TyLit -> String #

showList :: [TyLit] -> ShowS #

Eq TyLit # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord TyLit # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

compare :: TyLit -> TyLit -> Ordering #

(<) :: TyLit -> TyLit -> Bool #

(<=) :: TyLit -> TyLit -> Bool #

(>) :: TyLit -> TyLit -> Bool #

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

max :: TyLit -> TyLit -> TyLit #

min :: TyLit -> TyLit -> TyLit #

Lift TyLit # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => TyLit -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => TyLit -> Code m TyLit #

type Rep TyLit # 
Instance details

Defined in GHC.Internal.TH.Syntax

data TySynEqn #

Constructors

TySynEqn (Maybe [TyVarBndr ()]) Type Type 

Instances

Instances details
Data TySynEqn # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: TySynEqn -> Constr #

dataTypeOf :: TySynEqn -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic TySynEqn # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

from :: TySynEqn -> Rep TySynEqn x #

to :: Rep TySynEqn x -> TySynEqn #

Show TySynEqn # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq TySynEqn # 
Instance details

Defined in GHC.Internal.TH.Syntax

Ord TySynEqn # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift TySynEqn # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => TySynEqn -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => TySynEqn -> Code m TySynEqn #

type Rep TySynEqn # 
Instance details

Defined in GHC.Internal.TH.Syntax

data TyVarBndr flag #

Constructors

PlainTV Name flag 
KindedTV Name flag Kind 

Instances

Instances details
Functor TyVarBndr # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

fmap :: (a -> b) -> TyVarBndr a -> TyVarBndr b #

(<$) :: a -> TyVarBndr b -> TyVarBndr a #

Foldable TyVarBndr # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

fold :: Monoid m => TyVarBndr m -> m #

foldMap :: Monoid m => (a -> m) -> TyVarBndr a -> m #

foldMap' :: Monoid m => (a -> m) -> TyVarBndr a -> m #

foldr :: (a -> b -> b) -> b -> TyVarBndr a -> b #

foldr' :: (a -> b -> b) -> b -> TyVarBndr a -> b #

foldl :: (b -> a -> b) -> b -> TyVarBndr a -> b #

foldl' :: (b -> a -> b) -> b -> TyVarBndr a -> b #

foldr1 :: (a -> a -> a) -> TyVarBndr a -> a #

foldl1 :: (a -> a -> a) -> TyVarBndr a -> a #

toList :: TyVarBndr a -> [a] #

null :: TyVarBndr a -> Bool #

length :: TyVarBndr a -> Int #

elem :: Eq a => a -> TyVarBndr a -> Bool #

maximum :: Ord a => TyVarBndr a -> a #

minimum :: Ord a => TyVarBndr a -> a #

sum :: Num a => TyVarBndr a -> a #

product :: Num a => TyVarBndr a -> a #

Traversable TyVarBndr # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

traverse :: Applicative f => (a -> f b) -> TyVarBndr a -> f (TyVarBndr b) #

sequenceA :: Applicative f => TyVarBndr (f a) -> f (TyVarBndr a) #

mapM :: Monad m => (a -> m b) -> TyVarBndr a -> m (TyVarBndr b) #

sequence :: Monad m => TyVarBndr (m a) -> m (TyVarBndr a) #

Lift a => Lift (TyVarBndr a :: Type) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => TyVarBndr a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => TyVarBndr a -> Code m (TyVarBndr a) #

PprFlag flag => Ppr (TyVarBndr flag) Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Methods

ppr :: TyVarBndr flag -> Doc Source #

ppr_list :: [TyVarBndr flag] -> Doc Source #

Data flag => Data (TyVarBndr flag) # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: TyVarBndr flag -> Constr #

dataTypeOf :: TyVarBndr flag -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic (TyVarBndr flag) # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

from :: TyVarBndr flag -> Rep (TyVarBndr flag) x #

to :: Rep (TyVarBndr flag) x -> TyVarBndr flag #

Show flag => Show (TyVarBndr flag) # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

showsPrec :: Int -> TyVarBndr flag -> ShowS #

show :: TyVarBndr flag -> String #

showList :: [TyVarBndr flag] -> ShowS #

Eq flag => Eq (TyVarBndr flag) # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

(==) :: TyVarBndr flag -> TyVarBndr flag -> Bool #

(/=) :: TyVarBndr flag -> TyVarBndr flag -> Bool #

Ord flag => Ord (TyVarBndr flag) # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

compare :: TyVarBndr flag -> TyVarBndr flag -> Ordering #

(<) :: TyVarBndr flag -> TyVarBndr flag -> Bool #

(<=) :: TyVarBndr flag -> TyVarBndr flag -> Bool #

(>) :: TyVarBndr flag -> TyVarBndr flag -> Bool #

(>=) :: TyVarBndr flag -> TyVarBndr flag -> Bool #

max :: TyVarBndr flag -> TyVarBndr flag -> TyVarBndr flag #

min :: TyVarBndr flag -> TyVarBndr flag -> TyVarBndr flag #

type Rep (TyVarBndr flag) # 
Instance details

Defined in GHC.Internal.TH.Syntax

data Type #

Instances

Instances details
Ppr Type Source # 
Instance details

Defined in GHC.Internal.TH.Ppr

Methods

ppr :: Type -> Doc Source #

ppr_list :: [Type] -> Doc Source #

Data Type # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: Type -> Constr #

dataTypeOf :: Type -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Type # 
Instance details

Defined in GHC.Internal.TH.Syntax

Associated Types

type Rep Type 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Type = D1 ('MetaData "Type" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) ((((C1 ('MetaCons "ForallT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr Specificity]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))) :+: (C1 ('MetaCons "ForallVisT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr ()]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :+: C1 ('MetaCons "AppT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)))) :+: ((C1 ('MetaCons "AppKindT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind)) :+: C1 ('MetaCons "SigT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind))) :+: (C1 ('MetaCons "VarT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :+: C1 ('MetaCons "ConT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))))) :+: ((C1 ('MetaCons "PromotedT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :+: (C1 ('MetaCons "InfixT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))) :+: C1 ('MetaCons "UInfixT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))))) :+: ((C1 ('MetaCons "PromotedInfixT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))) :+: C1 ('MetaCons "PromotedUInfixT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)))) :+: (C1 ('MetaCons "ParensT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :+: C1 ('MetaCons "TupleT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))))) :+: (((C1 ('MetaCons "UnboxedTupleT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: (C1 ('MetaCons "UnboxedSumT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SumArity)) :+: C1 ('MetaCons "ArrowT" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MulArrowT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EqualityT" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ListT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PromotedTupleT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))) :+: ((C1 ('MetaCons "PromotedNilT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PromotedConsT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StarT" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ConstraintT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LitT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TyLit))) :+: (C1 ('MetaCons "WildCardT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ImplicitParamT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)))))))

Methods

from :: Type -> Rep Type x #

to :: Rep Type x -> Type #

Show Type # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Eq Type # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

Ord Type # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

compare :: Type -> Type -> Ordering #

(<) :: Type -> Type -> Bool #

(<=) :: Type -> Type -> Bool #

(>) :: Type -> Type -> Bool #

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

max :: Type -> Type -> Type #

min :: Type -> Type -> Type #

Lift Type # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Type -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Type -> Code m Type #

type Rep Type # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Rep Type = D1 ('MetaData "Type" "GHC.Internal.TH.Syntax" "ghc-internal" 'False) ((((C1 ('MetaCons "ForallT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr Specificity]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cxt) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))) :+: (C1 ('MetaCons "ForallVisT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TyVarBndr ()]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :+: C1 ('MetaCons "AppT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)))) :+: ((C1 ('MetaCons "AppKindT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind)) :+: C1 ('MetaCons "SigT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Kind))) :+: (C1 ('MetaCons "VarT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :+: C1 ('MetaCons "ConT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))))) :+: ((C1 ('MetaCons "PromotedT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :+: (C1 ('MetaCons "InfixT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))) :+: C1 ('MetaCons "UInfixT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))))) :+: ((C1 ('MetaCons "PromotedInfixT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type))) :+: C1 ('MetaCons "PromotedUInfixT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)))) :+: (C1 ('MetaCons "ParensT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)) :+: C1 ('MetaCons "TupleT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))))) :+: (((C1 ('MetaCons "UnboxedTupleT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: (C1 ('MetaCons "UnboxedSumT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SumArity)) :+: C1 ('MetaCons "ArrowT" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MulArrowT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EqualityT" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ListT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PromotedTupleT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))) :+: ((C1 ('MetaCons "PromotedNilT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PromotedConsT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "StarT" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ConstraintT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LitT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TyLit))) :+: (C1 ('MetaCons "WildCardT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ImplicitParamT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Type)))))))

data TypeFamilyHead #

Instances

Instances details
Data TypeFamilyHead # 
Instance details

Defined in GHC.Internal.TH.Syntax

Methods

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

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

toConstr :: TypeFamilyHead -> Constr #

dataTypeOf :: TypeFamilyHead -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic TypeFamilyHead # 
Instance details

Defined in GHC.Internal.TH.Syntax

Show TypeFamilyHead # 
Instance details

Defined in GHC.Internal.TH.Syntax

Eq TypeFamilyHead # 
Instance details

Defined in GHC.Internal.TH.Syntax

Ord TypeFamilyHead # 
Instance details

Defined in GHC.Internal.TH.Syntax

Lift TypeFamilyHead # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => TypeFamilyHead -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => TypeFamilyHead -> Code m TypeFamilyHead #

type Rep TypeFamilyHead # 
Instance details

Defined in GHC.Internal.TH.Syntax

type Uniq = Integer #

type Unlifted = Bool #

makeRelativeToProject :: FilePath -> Q FilePath Source #

The input is a filepath, which if relative is offset by the package root.

dataToExpQ :: (Quote m, Data a) => (forall b. Data b => b -> Maybe (m Exp)) -> a -> m Exp #

dataToPatQ :: (Quote m, Data a) => (forall b. Data b => b -> Maybe (m Pat)) -> a -> m Pat #

dataToQa :: (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 #

liftData :: (Quote m, Data a) => a -> m Exp #

liftString :: Quote m => String -> m Exp #

class Lift (t :: TYPE r) where #

Minimal complete definition

liftTyped

Methods

lift :: Quote m => t -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => t -> Code m t #

Instances

Instances details
Lift Addr# # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Addr# -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Addr# -> Code m Addr# #

Lift Double# # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Double# -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Double# -> Code m Double# #

Lift Float# # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Float# -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Float# -> Code m Float# #

Lift Int# # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Int# -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Int# -> Code m Int# #

Lift ByteArray Source # 
Instance details

Defined in Data.Array.Byte

Methods

lift :: Quote m => ByteArray -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => ByteArray -> Code m ByteArray #

Lift Void # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Void -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Void -> Code m Void #

Lift ForeignSrcLang # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => ForeignSrcLang -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => ForeignSrcLang -> Code m ForeignSrcLang #

Lift Int16 # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Int16 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Int16 -> Code m Int16 #

Lift Int32 # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Int32 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Int32 -> Code m Int32 #

Lift Int64 # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Int64 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Int64 -> Code m Int64 #

Lift Int8 # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Int8 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Int8 -> Code m Int8 #

Lift Extension # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Extension -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Extension -> Code m Extension #

Lift AnnLookup # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => AnnLookup -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => AnnLookup -> Code m AnnLookup #

Lift AnnTarget # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => AnnTarget -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => AnnTarget -> Code m AnnTarget #

Lift Bang # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Bang -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Bang -> Code m Bang #

Lift BndrVis # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => BndrVis -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => BndrVis -> Code m BndrVis #

Lift Body # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Body -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Body -> Code m Body #

Lift Bytes # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Bytes -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Bytes -> Code m Bytes #

Lift Callconv # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Callconv -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Callconv -> Code m Callconv #

Lift Clause # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Clause -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Clause -> Code m Clause #

Lift Con # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Con -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Con -> Code m Con #

Lift Dec # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Dec -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Dec -> Code m Dec #

Lift DecidedStrictness # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => DecidedStrictness -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => DecidedStrictness -> Code m DecidedStrictness #

Lift DerivClause # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => DerivClause -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => DerivClause -> Code m DerivClause #

Lift DerivStrategy # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => DerivStrategy -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => DerivStrategy -> Code m DerivStrategy #

Lift DocLoc # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => DocLoc -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => DocLoc -> Code m DocLoc #

Lift Exp # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Exp -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Exp -> Code m Exp #

Lift FamilyResultSig # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => FamilyResultSig -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => FamilyResultSig -> Code m FamilyResultSig #

Lift Fixity # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Fixity -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Fixity -> Code m Fixity #

Lift FixityDirection # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => FixityDirection -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => FixityDirection -> Code m FixityDirection #

Lift Foreign # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Foreign -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Foreign -> Code m Foreign #

Lift FunDep # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => FunDep -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => FunDep -> Code m FunDep #

Lift Guard # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Guard -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Guard -> Code m Guard #

Lift Info # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Info -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Info -> Code m Info #

Lift InjectivityAnn # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => InjectivityAnn -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => InjectivityAnn -> Code m InjectivityAnn #

Lift Inline # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Inline -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Inline -> Code m Inline #

Lift Lit # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Lit -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Lit -> Code m Lit #

Lift Loc # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Loc -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Loc -> Code m Loc #

Lift Match # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Match -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Match -> Code m Match #

Lift ModName # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => ModName -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => ModName -> Code m ModName #

Lift Module # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Module -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Module -> Code m Module #

Lift Name # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Name -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Name -> Code m Name #

Lift NameFlavour # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => NameFlavour -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => NameFlavour -> Code m NameFlavour #

Lift NameIs # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => NameIs -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => NameIs -> Code m NameIs #

Lift NameSpace # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => NameSpace -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => NameSpace -> Code m NameSpace #

Lift NamespaceSpecifier # 
Instance details

Defined in GHC.Internal.TH.Lift

Lift OccName # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => OccName -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => OccName -> Code m OccName #

Lift Overlap # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Overlap -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Overlap -> Code m Overlap #

Lift Pat # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Pat -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Pat -> Code m Pat #

Lift PatSynArgs # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => PatSynArgs -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => PatSynArgs -> Code m PatSynArgs #

Lift PatSynDir # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => PatSynDir -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => PatSynDir -> Code m PatSynDir #

Lift Phases # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Phases -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Phases -> Code m Phases #

Lift PkgName # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => PkgName -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => PkgName -> Code m PkgName #

Lift Pragma # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Pragma -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Pragma -> Code m Pragma #

Lift Range # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Range -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Range -> Code m Range #

Lift Role # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Role -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Role -> Code m Role #

Lift RuleBndr # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => RuleBndr -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => RuleBndr -> Code m RuleBndr #

Lift RuleMatch # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => RuleMatch -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => RuleMatch -> Code m RuleMatch #

Lift Safety # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Safety -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Safety -> Code m Safety #

Lift SourceStrictness # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => SourceStrictness -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => SourceStrictness -> Code m SourceStrictness #

Lift SourceUnpackedness # 
Instance details

Defined in GHC.Internal.TH.Lift

Lift Specificity # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Specificity -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Specificity -> Code m Specificity #

Lift Stmt # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Stmt -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Stmt -> Code m Stmt #

Lift TyLit # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => TyLit -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => TyLit -> Code m TyLit #

Lift TySynEqn # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => TySynEqn -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => TySynEqn -> Code m TySynEqn #

Lift Type # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Type -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Type -> Code m Type #

Lift TypeFamilyHead # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => TypeFamilyHead -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => TypeFamilyHead -> Code m TypeFamilyHead #

Lift Word16 # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Word16 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Word16 -> Code m Word16 #

Lift Word32 # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Word32 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Word32 -> Code m Word32 #

Lift Word64 # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Word64 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Word64 -> Code m Word64 #

Lift Word8 # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Word8 -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Word8 -> Code m Word8 #

Lift Integer # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Integer -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Integer -> Code m Integer #

Lift Natural # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Natural -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Natural -> Code m Natural #

Lift () # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => () -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => () -> Code m () #

Lift Bool # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Bool -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Bool -> Code m Bool #

Lift Char # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Char -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Char -> Code m Char #

Lift Double # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Double -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Double -> Code m Double #

Lift Float # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Float -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Float -> Code m Float #

Lift Int # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Int -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Int -> Code m Int #

Lift Word # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Word -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Word -> Code m Word #

Lift Char# # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Char# -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Char# -> Code m Char# #

Lift Word# # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Word# -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Word# -> Code m Word# #

Lift (# #) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => (# #) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (# #) -> Code m (# #) #

Lift a => Lift (NonEmpty a :: Type) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => NonEmpty a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => NonEmpty a -> Code m (NonEmpty a) #

Integral a => Lift (Ratio a :: Type) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Ratio a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Ratio a -> Code m (Ratio a) #

Lift a => Lift (TyVarBndr a :: Type) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => TyVarBndr a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => TyVarBndr a -> Code m (TyVarBndr a) #

Lift a => Lift (Maybe a :: Type) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Maybe a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Maybe a -> Code m (Maybe a) #

Lift a => Lift ([a] :: Type) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => [a] -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => [a] -> Code m [a] #

Lift (Fixed a :: Type) Source #

Since: base-4.21.0.0

Instance details

Defined in Data.Fixed

Methods

lift :: Quote m => Fixed a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Fixed a -> Code m (Fixed a) #

(Lift a, Lift b) => Lift (Either a b :: Type) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => Either a b -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Either a b -> Code m (Either a b) #

Lift (TExp a :: Type) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => TExp a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => TExp a -> Code m (TExp a) #

(Lift a, Lift b) => Lift ((a, b) :: Type) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => (a, b) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (a, b) -> Code m (a, b) #

(Lift a, Lift b, Lift c) => Lift ((a, b, c) :: Type) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => (a, b, c) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (a, b, c) -> Code m (a, b, c) #

(Lift a, Lift b, Lift c, Lift d) => Lift ((a, b, c, d) :: Type) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => (a, b, c, d) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (a, b, c, d) -> Code m (a, b, c, d) #

(Lift a, Lift b, Lift c, Lift d, Lift e) => Lift ((a, b, c, d, e) :: Type) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => (a, b, c, d, e) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (a, b, c, d, e) -> Code m (a, b, c, d, e) #

(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) => Lift ((a, b, c, d, e, f) :: Type) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => (a, b, c, d, e, f) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (a, b, c, d, e, f) -> Code m (a, b, c, d, e, f) #

(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) => Lift ((a, b, c, d, e, f, g) :: Type) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => (a, b, c, d, e, f, g) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (a, b, c, d, e, f, g) -> Code m (a, b, c, d, e, f, g) #

Lift a => Lift ((# a #) :: TYPE ('TupleRep '[LiftedRep])) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => (# a #) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (# a #) -> Code m (# a #) #

(Lift a, Lift b) => Lift ((# a | b #) :: TYPE ('SumRep '[LiftedRep, LiftedRep])) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => (# a | b #) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (# a | b #) -> Code m (# a | b #) #

(Lift a, Lift b) => Lift ((# a, b #) :: TYPE ('TupleRep '[LiftedRep, LiftedRep])) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => (# a, b #) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (# a, b #) -> Code m (# a, b #) #

(Lift a, Lift b, Lift c) => Lift ((# a | b | c #) :: TYPE ('SumRep '[LiftedRep, LiftedRep, LiftedRep])) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => (# a | b | c #) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (# a | b | c #) -> Code m (# a | b | c #) #

(Lift a, Lift b, Lift c) => Lift ((# a, b, c #) :: TYPE ('TupleRep '[LiftedRep, LiftedRep, LiftedRep])) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => (# a, b, c #) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (# a, b, c #) -> Code m (# a, b, c #) #

(Lift a, Lift b, Lift c, Lift d) => Lift ((# a | b | c | d #) :: TYPE ('SumRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep])) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => (# a | b | c | d #) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (# a | b | c | d #) -> Code m (# a | b | c | d #) #

(Lift a, Lift b, Lift c, Lift d) => Lift ((# a, b, c, d #) :: TYPE ('TupleRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep])) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => (# a, b, c, d #) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (# a, b, c, d #) -> Code m (# a, b, c, d #) #

(Lift a, Lift b, Lift c, Lift d, Lift e) => Lift ((# a | b | c | d | e #) :: TYPE ('SumRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep])) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => (# a | b | c | d | e #) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (# a | b | c | d | e #) -> Code m (# a | b | c | d | e #) #

(Lift a, Lift b, Lift c, Lift d, Lift e) => Lift ((# a, b, c, d, e #) :: TYPE ('TupleRep '[LiftedRep, LiftedRep, LiftedRep, LiftedRep, LiftedRep])) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => (# a, b, c, d, e #) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (# a, b, c, d, e #) -> Code m (# a, b, c, d, e #) #

(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])) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => (# a | b | c | d | e | f #) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (# a | b | c | d | e | f #) -> Code m (# a | b | c | d | e | f #) #

(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])) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => (# a, b, c, d, e, f #) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (# a, b, c, d, e, f #) -> Code m (# a, b, c, d, e, f #) #

(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])) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => (# a | b | c | d | e | f | g #) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (# a | b | c | d | e | f | g #) -> Code m (# a | b | c | d | e | f | g #) #

(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])) # 
Instance details

Defined in GHC.Internal.TH.Lift

Methods

lift :: Quote m => (# a, b, c, d, e, f, g #) -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => (# a, b, c, d, e, f, g #) -> Code m (# a, b, c, d, e, f, g #) #