-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Support library for Template Haskell -- -- This package provides modules containing facilities for manipulating -- Haskell source code using Template Haskell. -- -- See http://www.haskell.org/haskellwiki/Template_Haskell for -- more information. @package template-haskell @version 2.17.0.0 -- | Language extensions known to GHC module Language.Haskell.TH.LanguageExtensions -- | The language extensions known to GHC. -- -- Note that there is an orphan Binary instance for this type -- supplied by the GHC.LanguageExtensions module provided by -- ghc-boot. We can't provide here as this would require adding -- transitive dependencies to the template-haskell package, -- which must have a minimal dependency set. data Extension Cpp :: Extension OverlappingInstances :: Extension UndecidableInstances :: Extension IncoherentInstances :: Extension UndecidableSuperClasses :: Extension MonomorphismRestriction :: Extension MonoPatBinds :: Extension MonoLocalBinds :: Extension RelaxedPolyRec :: Extension ExtendedDefaultRules :: Extension ForeignFunctionInterface :: Extension UnliftedFFITypes :: Extension InterruptibleFFI :: Extension CApiFFI :: Extension GHCForeignImportPrim :: Extension JavaScriptFFI :: Extension ParallelArrays :: Extension Arrows :: Extension TemplateHaskell :: Extension TemplateHaskellQuotes :: Extension QuasiQuotes :: Extension ImplicitParams :: Extension ImplicitPrelude :: Extension ScopedTypeVariables :: Extension AllowAmbiguousTypes :: Extension UnboxedTuples :: Extension UnboxedSums :: Extension UnliftedNewtypes :: Extension BangPatterns :: Extension TypeFamilies :: Extension TypeFamilyDependencies :: Extension TypeInType :: Extension OverloadedStrings :: Extension OverloadedLists :: Extension NumDecimals :: Extension DisambiguateRecordFields :: Extension RecordWildCards :: Extension RecordPuns :: Extension ViewPatterns :: Extension GADTs :: Extension GADTSyntax :: Extension NPlusKPatterns :: Extension DoAndIfThenElse :: Extension BlockArguments :: Extension RebindableSyntax :: Extension ConstraintKinds :: Extension PolyKinds :: Extension DataKinds :: Extension InstanceSigs :: Extension ApplicativeDo :: Extension StandaloneDeriving :: Extension DeriveDataTypeable :: Extension AutoDeriveTypeable :: Extension DeriveFunctor :: Extension DeriveTraversable :: Extension DeriveFoldable :: Extension DeriveGeneric :: Extension DefaultSignatures :: Extension DeriveAnyClass :: Extension DeriveLift :: Extension DerivingStrategies :: Extension DerivingVia :: Extension TypeSynonymInstances :: Extension FlexibleContexts :: Extension FlexibleInstances :: Extension ConstrainedClassMethods :: Extension MultiParamTypeClasses :: Extension NullaryTypeClasses :: Extension FunctionalDependencies :: Extension UnicodeSyntax :: Extension ExistentialQuantification :: Extension MagicHash :: Extension EmptyDataDecls :: Extension KindSignatures :: Extension RoleAnnotations :: Extension ParallelListComp :: Extension TransformListComp :: Extension MonadComprehensions :: Extension GeneralizedNewtypeDeriving :: Extension RecursiveDo :: Extension PostfixOperators :: Extension TupleSections :: Extension PatternGuards :: Extension LiberalTypeSynonyms :: Extension RankNTypes :: Extension ImpredicativeTypes :: Extension TypeOperators :: Extension ExplicitNamespaces :: Extension PackageImports :: Extension ExplicitForAll :: Extension AlternativeLayoutRule :: Extension AlternativeLayoutRuleTransitional :: Extension DatatypeContexts :: Extension NondecreasingIndentation :: Extension RelaxedLayout :: Extension TraditionalRecordSyntax :: Extension LambdaCase :: Extension MultiWayIf :: Extension BinaryLiterals :: Extension NegativeLiterals :: Extension HexFloatLiterals :: Extension DuplicateRecordFields :: Extension OverloadedLabels :: Extension EmptyCase :: Extension PatternSynonyms :: Extension PartialTypeSignatures :: Extension NamedWildCards :: Extension StaticPointers :: Extension TypeApplications :: Extension Strict :: Extension StrictData :: Extension MonadFailDesugaring :: Extension EmptyDataDeriving :: Extension NumericUnderscores :: Extension QuantifiedConstraints :: Extension StarIsType :: Extension ImportQualifiedPost :: Extension CUSKs :: Extension StandaloneKindSignatures :: Extension -- | Abstract syntax definitions for Template Haskell. module Language.Haskell.TH.Syntax sequenceQ :: forall m. Monad m => forall a. [m a] -> m [a] -- | Generate a capturable name. Occurrences of such names will be resolved -- according to the Haskell scoping rules at the occurrence site. -- -- For example: -- --
--   f = [| pi + $(varE (mkName "pi")) |]
--   ...
--   g = let pi = 3 in $f
--   
-- -- In this case, g is desugared to -- --
--   g = Prelude.pi + 3
--   
-- -- Note that mkName may be used with qualified names: -- --
--   mkName "Prelude.pi"
--   
-- -- See also dyn for a useful combinator. The above example could -- be rewritten using dyn as -- --
--   f = [| pi + $(dyn "pi") |]
--   
mkName :: String -> Name mkNameG_v :: String -> String -> String -> Name mkNameG_d :: String -> String -> String -> Name mkNameG_tc :: String -> String -> String -> Name -- | Only used internally mkNameL :: String -> Uniq -> Name mkNameS :: String -> Name -- | Discard the type annotation and produce a plain Template Haskell -- expression -- -- Levity-polymorphic since template-haskell-2.16.0.0. unTypeQ :: forall (r :: RuntimeRep) (a :: TYPE r) m. Quote m => m (TExp a) -> m Exp -- | Annotate the Template Haskell expression with a type -- -- This is unsafe because GHC cannot check for you that the expression -- really does have the type you claim it has. -- -- Levity-polymorphic since template-haskell-2.16.0.0. unsafeTExpCoerce :: forall (r :: RuntimeRep) (a :: TYPE r) m. Quote m => m Exp -> m (TExp a) liftString :: Quote m => String -> m Exp -- | A Lift instance can have any of its values turned into a -- Template Haskell expression. This is needed when a value used within a -- Template Haskell quotation is bound outside the Oxford brackets -- ([| ... |] or [|| ... ||]) but not at the top level. -- As an example: -- --
--   add1 :: Int -> Q (TExp Int)
--   add1 x = [|| x + 1 ||]
--   
-- -- Template Haskell has no way of knowing what value x will take -- on at splice-time, so it requires the type of x to be an -- instance of Lift. -- -- A Lift instance must satisfy $(lift x) ≡ x and -- $$(liftTyped x) ≡ x for all x, where $(...) -- and $$(...) are Template Haskell splices. It is additionally -- expected that lift x ≡ unTypeQ (liftTyped -- x). -- -- Lift instances can be derived automatically by use of the -- -XDeriveLift GHC language extension: -- --
--   {-# LANGUAGE DeriveLift #-}
--   module Foo where
--   
--   import Language.Haskell.TH.Syntax
--   
--   data Bar a = Bar1 a (Bar a) | Bar2 String
--     deriving Lift
--   
-- -- Levity-polymorphic since template-haskell-2.16.0.0. class Lift (t :: TYPE r) -- | Turn a value into a Template Haskell expression, suitable for use in a -- splice. lift :: (Lift t, Quote m) => t -> m Exp -- | Turn a value into a Template Haskell expression, suitable for use in a -- splice. lift :: (Lift t, r ~ 'LiftedRep, Quote m) => t -> m Exp -- | Turn a value into a Template Haskell typed expression, suitable for -- use in a typed splice. liftTyped :: (Lift t, Quote m) => t -> m (TExp t) -- | The Quote class implements the minimal interface which is -- necessary for desugaring quotations. -- -- -- -- Therefore the type of an untyped quotation in GHC is `Quote m => m -- Exp` -- -- For many years the type of a quotation was fixed to be `Q Exp` but by -- more precisely specifying the minimal interface it enables the -- Exp to be extracted purely from the quotation without -- interacting with Q. class Monad m => Quote m -- | Generate a fresh name, which cannot be captured. -- -- For example, this: -- --
--   f = $(do
--       nm1 <- newName "x"
--       let nm2 = mkName "x"
--       return (LamE [VarP nm1] (LamE [VarP nm2] (VarE nm1)))
--      )
--   
-- -- will produce the splice -- --
--   f = \x0 -> \x -> x0
--   
-- -- In particular, the occurrence VarE nm1 refers to the binding -- VarP nm1, and is not captured by the binding VarP -- nm2. -- -- Although names generated by newName cannot be -- captured, they can capture other names. For example, this: -- --
--   g = $(do
--     nm1 <- newName "x"
--     let nm2 = mkName "x"
--     return (LamE [VarP nm2] (LamE [VarP nm1] (VarE nm2)))
--    )
--   
-- -- will produce the splice -- --
--   g = \x -> \x0 -> x0
--   
-- -- since the occurrence VarE nm2 is captured by the innermost -- binding of x, namely VarP nm1. newName :: Quote m => String -> m Name data Exp -- |
--   { x }
--   
VarE :: Name -> Exp -- |
--   data T1 = C1 t1 t2; p = {C1} e1 e2
--   
ConE :: Name -> Exp -- |
--   { 5 or 'c'}
--   
LitE :: Lit -> Exp -- |
--   { f x }
--   
AppE :: Exp -> Exp -> Exp -- |
--   { f @Int }
--   
AppTypeE :: Exp -> Type -> Exp -- |
--   {x + y} or {(x+)} or {(+ x)} or {(+)}
--   
InfixE :: Maybe Exp -> Exp -> Maybe Exp -> Exp -- |
--   {x + y}
--   
-- -- See Language.Haskell.TH.Syntax#infix UInfixE :: Exp -> Exp -> Exp -> Exp -- |
--   { (e) }
--   
-- -- See Language.Haskell.TH.Syntax#infix ParensE :: Exp -> Exp -- |
--   { \ p1 p2 -> e }
--   
LamE :: [Pat] -> Exp -> Exp -- |
--   { \case m1; m2 }
--   
LamCaseE :: [Match] -> Exp -- |
--   { (e1,e2) }
--   
-- -- The Maybe is necessary for handling tuple sections. -- --
--   (1,)
--   
-- -- translates to -- --
--   TupE [Just (LitE (IntegerL 1)),Nothing]
--   
TupE :: [Maybe Exp] -> Exp -- |
--   { (# e1,e2 #) }
--   
-- -- The Maybe is necessary for handling tuple sections. -- --
--   (# 'c', #)
--   
-- -- translates to -- --
--   UnboxedTupE [Just (LitE (CharL 'c')),Nothing]
--   
UnboxedTupE :: [Maybe Exp] -> Exp -- |
--   { (#|e|#) }
--   
UnboxedSumE :: Exp -> SumAlt -> SumArity -> Exp -- |
--   { if e1 then e2 else e3 }
--   
CondE :: Exp -> Exp -> Exp -> Exp -- |
--   { if | g1 -> e1 | g2 -> e2 }
--   
MultiIfE :: [(Guard, Exp)] -> Exp -- |
--   { let { x=e1; y=e2 } in e3 }
--   
LetE :: [Dec] -> Exp -> Exp -- |
--   { case e of m1; m2 }
--   
CaseE :: Exp -> [Match] -> Exp -- |
--   { do { p <- e1; e2 }  }
--   
DoE :: [Stmt] -> Exp -- |
--   { mdo { x <- e1 y; y <- e2 x; } }
--   
MDoE :: [Stmt] -> Exp -- |
--   { [ (x,y) | x <- xs, y <- ys ] }
--   
-- -- The result expression of the comprehension is the last of the -- Stmts, and should be a NoBindS. -- -- E.g. translation: -- --
--   [ f x | x <- xs ]
--   
-- --
--   CompE [BindS (VarP x) (VarE xs), NoBindS (AppE (VarE f) (VarE x))]
--   
CompE :: [Stmt] -> Exp -- |
--   { [ 1 ,2 .. 10 ] }
--   
ArithSeqE :: Range -> Exp -- |
--   { [1,2,3] }
--   
ListE :: [Exp] -> Exp -- |
--   { e :: t }
--   
SigE :: Exp -> Type -> Exp -- |
--   { T { x = y, z = w } }
--   
RecConE :: Name -> [FieldExp] -> Exp -- |
--   { (f x) { z = w } }
--   
RecUpdE :: Exp -> [FieldExp] -> Exp -- |
--   { static e }
--   
StaticE :: Exp -> Exp -- |
--   { _x }
--   
-- -- This is used for holes or unresolved identifiers in AST quotes. Note -- that it could either have a variable name or constructor name. UnboundVarE :: Name -> Exp -- | { #x } ( Overloaded label ) LabelE :: String -> Exp -- | { ?x } ( Implicit parameter ) ImplicitParamVarE :: String -> Exp data Match -- |
--   case e of { pat -> body where decs }
--   
Match :: Pat -> Body -> [Dec] -> Match data Clause -- |
--   f { p1 p2 = body where decs }
--   
Clause :: [Pat] -> Body -> [Dec] -> Clause newtype Q a Q :: (forall m. Quasi m => m a) -> Q a [unQ] :: Q a -> forall m. Quasi m => m a -- | Pattern in Haskell given in {} data Pat -- |
--   { 5 or 'c' }
--   
LitP :: Lit -> Pat -- |
--   { x }
--   
VarP :: Name -> Pat -- |
--   { (p1,p2) }
--   
TupP :: [Pat] -> Pat -- |
--   { (# p1,p2 #) }
--   
UnboxedTupP :: [Pat] -> Pat -- |
--   { (#|p|#) }
--   
UnboxedSumP :: Pat -> SumAlt -> SumArity -> Pat -- |
--   data T1 = C1 t1 t2; {C1 p1 p1} = e
--   
ConP :: Name -> [Pat] -> Pat -- |
--   foo ({x :+ y}) = e
--   
InfixP :: Pat -> Name -> Pat -> Pat -- |
--   foo ({x :+ y}) = e
--   
-- -- See Language.Haskell.TH.Syntax#infix UInfixP :: Pat -> Name -> Pat -> Pat -- |
--   {(p)}
--   
-- -- See Language.Haskell.TH.Syntax#infix ParensP :: Pat -> Pat -- |
--   { ~p }
--   
TildeP :: Pat -> Pat -- |
--   { !p }
--   
BangP :: Pat -> Pat -- |
--   { x @ p }
--   
AsP :: Name -> Pat -> Pat -- |
--   { _ }
--   
WildP :: Pat -- |
--   f (Pt { pointx = x }) = g x
--   
RecP :: Name -> [FieldPat] -> Pat -- |
--   { [1,2,3] }
--   
ListP :: [Pat] -> Pat -- |
--   { p :: t }
--   
SigP :: Pat -> Type -> Pat -- |
--   { e -> p }
--   
ViewP :: Exp -> Pat -> Pat data Stmt -- |
--   p <- e
--   
BindS :: Pat -> Exp -> Stmt -- |
--   { let { x=e1; y=e2 } }
--   
LetS :: [Dec] -> Stmt -- |
--   e
--   
NoBindS :: Exp -> Stmt -- | x <- e1 | s2, s3 | s4 (in CompE) ParS :: [[Stmt]] -> Stmt -- |
--   rec { s1; s2 }
--   
RecS :: [Stmt] -> Stmt -- | A single data constructor. -- -- The constructors for Con can roughly be divided up into two -- categories: those for constructors with "vanilla" syntax -- (NormalC, RecC, and InfixC), and those for -- constructors with GADT syntax (GadtC and RecGadtC). The -- ForallC constructor, which quantifies additional type variables -- and class contexts, can surround either variety of constructor. -- However, the type variables that it quantifies are different depending -- on what constructor syntax is used: -- -- -- --
--   data Foo a = forall b. MkFoo a b
--   
--   
-- -- In MkFoo, ForallC will quantify b, but not -- a. -- -- -- --
--   data Bar a b where
--     MkBar :: (a ~ b) => c -> MkBar a b
--   
--   
-- -- In MkBar, ForallC will quantify a, -- b, and c. data Con -- |
--   C Int a
--   
NormalC :: Name -> [BangType] -> Con -- |
--   C { v :: Int, w :: a }
--   
RecC :: Name -> [VarBangType] -> Con -- |
--   Int :+ a
--   
InfixC :: BangType -> Name -> BangType -> Con -- |
--   forall a. Eq a => C [a]
--   
ForallC :: [TyVarBndr Specificity] -> Cxt -> Con -> Con -- |
--   C :: a -> b -> T b Int
--   
GadtC :: [Name] -> [BangType] -> Type -> Con -- |
--   C :: { v :: Int } -> T b Int
--   
RecGadtC :: [Name] -> [VarBangType] -> Type -> Con data Type -- |
--   forall <vars>. <ctxt> => <type>
--   
ForallT :: [TyVarBndr Specificity] -> Cxt -> Type -> Type -- |
--   forall <vars> -> <type>
--   
ForallVisT :: [TyVarBndr ()] -> Type -> Type -- |
--   T a b
--   
AppT :: Type -> Type -> Type -- |
--   T @k t
--   
AppKindT :: Type -> Kind -> Type -- |
--   t :: k
--   
SigT :: Type -> Kind -> Type -- |
--   a
--   
VarT :: Name -> Type -- |
--   T
--   
ConT :: Name -> Type -- |
--   'T
--   
PromotedT :: Name -> Type -- |
--   T + T
--   
InfixT :: Type -> Name -> Type -> Type -- |
--   T + T
--   
-- -- See Language.Haskell.TH.Syntax#infix UInfixT :: Type -> Name -> Type -> Type -- |
--   (T)
--   
ParensT :: Type -> Type -- |
--   (,), (,,), etc.
--   
TupleT :: Int -> Type -- |
--   (#,#), (#,,#), etc.
--   
UnboxedTupleT :: Int -> Type -- |
--   (#|#), (#||#), etc.
--   
UnboxedSumT :: SumArity -> Type -- |
--   ->
--   
ArrowT :: Type -- |
--   ~
--   
EqualityT :: Type -- |
--   []
--   
ListT :: Type -- |
--   '(), '(,), '(,,), etc.
--   
PromotedTupleT :: Int -> Type -- |
--   '[]
--   
PromotedNilT :: Type -- |
--   (':)
--   
PromotedConsT :: Type -- |
--   *
--   
StarT :: Type -- |
--   Constraint
--   
ConstraintT :: Type -- |
--   0,1,2, etc.
--   
LitT :: TyLit -> Type -- |
--   _
--   
WildCardT :: Type -- |
--   ?x :: t
--   
ImplicitParamT :: String -> Type -> Type data Dec -- |
--   { f p1 p2 = b where decs }
--   
FunD :: Name -> [Clause] -> Dec -- |
--   { p = b where decs }
--   
ValD :: Pat -> Body -> [Dec] -> Dec -- |
--   { data Cxt x => T x = A x | B (T x)
--          deriving (Z,W)
--          deriving stock Eq }
--   
DataD :: Cxt -> Name -> [TyVarBndr ()] -> Maybe Kind -> [Con] -> [DerivClause] -> Dec -- |
--   { newtype Cxt x => T x = A (B x)
--          deriving (Z,W Q)
--          deriving stock Eq }
--   
NewtypeD :: Cxt -> Name -> [TyVarBndr ()] -> Maybe Kind -> Con -> [DerivClause] -> Dec -- |
--   { type T x = (x,x) }
--   
TySynD :: Name -> [TyVarBndr ()] -> Type -> Dec -- |
--   { class Eq a => Ord a where ds }
--   
ClassD :: Cxt -> Name -> [TyVarBndr ()] -> [FunDep] -> [Dec] -> Dec -- |
--   { instance {-# OVERLAPS #-}
--           Show w => Show [w] where ds }
--   
InstanceD :: Maybe Overlap -> Cxt -> Type -> [Dec] -> Dec -- |
--   { length :: [a] -> Int }
--   
SigD :: Name -> Type -> Dec -- |
--   { type TypeRep :: k -> Type }
--   
KiSigD :: Name -> Kind -> Dec -- |
--   { foreign import ... }
--   { foreign export ... }
--   
ForeignD :: Foreign -> Dec -- |
--   { infix 3 foo }
--   
InfixD :: Fixity -> Name -> Dec -- |
--   { {-# INLINE [1] foo #-} }
--   
PragmaD :: Pragma -> Dec -- |
--   { data family T a b c :: * }
--   
DataFamilyD :: Name -> [TyVarBndr ()] -> Maybe Kind -> Dec -- |
--   { data instance Cxt x => T [x]
--          = A x | B (T x)
--          deriving (Z,W)
--          deriving stock Eq }
--   
DataInstD :: Cxt -> Maybe [TyVarBndr ()] -> Type -> Maybe Kind -> [Con] -> [DerivClause] -> Dec -- |
--   { newtype instance Cxt x => T [x]
--           = A (B x)
--           deriving (Z,W)
--           deriving stock Eq }
--   
NewtypeInstD :: Cxt -> Maybe [TyVarBndr ()] -> Type -> Maybe Kind -> Con -> [DerivClause] -> Dec -- |
--   { type instance ... }
--   
TySynInstD :: TySynEqn -> Dec -- |
--   { type family T a b c = (r :: *) | r -> a b }
--   
OpenTypeFamilyD :: TypeFamilyHead -> Dec -- |
--   { type family F a b = (r :: *) | r -> a where ... }
--   
ClosedTypeFamilyD :: TypeFamilyHead -> [TySynEqn] -> Dec -- |
--   { type role T nominal representational }
--   
RoleAnnotD :: Name -> [Role] -> Dec -- |
--   { deriving stock instance Ord a => Ord (Foo a) }
--   
StandaloneDerivD :: Maybe DerivStrategy -> Cxt -> Type -> Dec -- |
--   { default size :: Data a => a -> Int }
--   
DefaultSigD :: Name -> Type -> Dec -- | { pattern P v1 v2 .. vn <- p } unidirectional or { -- pattern P v1 v2 .. vn = p } implicit bidirectional or { -- pattern P v1 v2 .. vn <- p where P v1 v2 .. vn = e } explicit -- bidirectional -- -- also, besides prefix pattern synonyms, both infix and record pattern -- synonyms are supported. See PatSynArgs for details PatSynD :: Name -> PatSynArgs -> PatSynDir -> Pat -> Dec -- | A pattern synonym's type signature. PatSynSigD :: Name -> PatSynType -> Dec -- |
--   { ?x = expr }
--   
-- -- Implicit parameter binding declaration. Can only be used in let and -- where clauses which consist entirely of implicit bindings. ImplicitParamBindD :: String -> Exp -> Dec type BangType = (Bang, Type) type VarBangType = (Name, Bang, Type) type FieldExp = (Name, Exp) type FieldPat = (Name, Pat) -- | An abstract type representing names in the syntax tree. -- -- Names can be constructed in several ways, which come with -- different name-capture guarantees (see -- Language.Haskell.TH.Syntax#namecapture for an explanation of -- name capture): -- -- -- -- Names constructed using newName and mkName may be -- used in bindings (such as let x = ... or x -> -- ...), but names constructed using lookupValueName, -- lookupTypeName, 'f, ''T may not. data Name Name :: OccName -> NameFlavour -> Name data FunDep FunDep :: [Name] -> [Name] -> FunDep -- | Since the advent of ConstraintKinds, constraints are really -- just types. Equality constraints use the EqualityT constructor. -- Constraints may also be tuples of other constraints. type Pred = Type data RuleBndr RuleVar :: Name -> RuleBndr TypedRuleVar :: Name -> Type -> RuleBndr -- | One equation of a type family instance or closed type family. The -- arguments are the left-hand-side type and the right-hand-side result. -- -- For instance, if you had the following type family: -- --
--   type family Foo (a :: k) :: k where
--     forall k (a :: k). Foo @k a = a
--   
-- -- The Foo @k a = a equation would be represented as follows: -- --
--   TySynEqn (Just [PlainTV k, KindedTV a (VarT k)])
--              (AppT (AppKindT (ConT ''Foo) (VarT k)) (VarT a))
--              (VarT a)
--   
data TySynEqn TySynEqn :: Maybe [TyVarBndr ()] -> Type -> Type -> TySynEqn -- | Represents an expression which has type a. Built on top of -- Exp, typed expressions allow for type-safe splicing via: -- -- -- -- Traditional expression quotes and splices let us construct ill-typed -- expressions: -- --
--   >>> fmap ppr $ runQ [| True == $( [| "foo" |] ) |]
--   GHC.Types.True GHC.Classes.== "foo"
--   
--   >>> GHC.Types.True GHC.Classes.== "foo"
--   <interactive> error:
--       • Couldn't match expected type ‘Bool’ with actual type ‘[Char]’
--       • In the second argument of ‘(==)’, namely ‘"foo"’
--         In the expression: True == "foo"
--         In an equation for ‘it’: it = True == "foo"
--   
-- -- With typed expressions, the type error occurs when constructing -- the Template Haskell expression: -- --
--   >>> fmap ppr $ runQ [|| True == $$( [|| "foo" ||] ) ||]
--   <interactive> error:
--       • Couldn't match type ‘[Char]’ with ‘Bool’
--         Expected type: Q (TExp Bool)
--           Actual type: Q (TExp [Char])
--       • In the Template Haskell quotation [|| "foo" ||]
--         In the expression: [|| "foo" ||]
--         In the Template Haskell splice $$([|| "foo" ||])
--   
newtype TExp (a :: TYPE (r :: RuntimeRep)) TExp :: Exp -> TExp a :: TYPE r :: RuntimeRep -- | Underlying untyped Template Haskell expression [unType] :: TExp a :: TYPE r :: RuntimeRep -> Exp -- | Injectivity annotation data InjectivityAnn InjectivityAnn :: Name -> [Name] -> InjectivityAnn -- | To avoid duplication between kinds and types, they are defined to be -- the same. Naturally, you would never have a type be StarT and -- you would never have a kind be SigT, but many of the other -- constructors are shared. Note that the kind Bool is denoted -- with ConT, not PromotedT. Similarly, tuple kinds are -- made with TupleT, not PromotedTupleT. type Kind = Type -- | Varieties of allowed instance overlap. data Overlap -- | May be overlapped by more specific instances Overlappable :: Overlap -- | May overlap a more general instance Overlapping :: Overlap -- | Both Overlapping and Overlappable Overlaps :: Overlap -- | Both Overlappable and Overlappable, and pick an -- arbitrary one if multiple choices are available. Incoherent :: Overlap -- | A single deriving clause at the end of a datatype. data DerivClause -- |
--   { deriving stock (Eq, Ord) }
--   
DerivClause :: Maybe DerivStrategy -> Cxt -> DerivClause -- | What the user explicitly requests when deriving an instance. data DerivStrategy -- | A "standard" derived instance StockStrategy :: DerivStrategy -- |
--   -XDeriveAnyClass
--   
AnyclassStrategy :: DerivStrategy -- |
--   -XGeneralizedNewtypeDeriving
--   
NewtypeStrategy :: DerivStrategy -- |
--   -XDerivingVia
--   
ViaStrategy :: Type -> DerivStrategy -- | Annotation target for reifyAnnotations data AnnLookup AnnLookupModule :: Module -> AnnLookup AnnLookupName :: Name -> AnnLookup -- | Role annotations data Role -- |
--   nominal
--   
NominalR :: Role -- |
--   representational
--   
RepresentationalR :: Role -- |
--   phantom
--   
PhantomR :: Role -- |
--   _
--   
InferR :: Role data TyLit -- |
--   2
--   
NumTyLit :: Integer -> TyLit -- |
--   "Hello"
--   
StrTyLit :: String -> TyLit -- | Type family result signature data FamilyResultSig -- | no signature NoSig :: FamilyResultSig -- |
--   k
--   
KindSig :: Kind -> FamilyResultSig -- |
--   = r, = (r :: k)
--   
TyVarSig :: TyVarBndr () -> FamilyResultSig data TyVarBndr flag -- |
--   a
--   
PlainTV :: Name -> flag -> TyVarBndr flag -- |
--   (a :: k)
--   
KindedTV :: Name -> flag -> Kind -> TyVarBndr flag data Specificity -- |
--   a
--   
SpecifiedSpec :: Specificity -- |
--   {a}
--   
InferredSpec :: Specificity -- | A pattern synonym's argument type. data PatSynArgs -- |
--   pattern P {x y z} = p
--   
PrefixPatSyn :: [Name] -> PatSynArgs -- |
--   pattern {x P y} = p
--   
InfixPatSyn :: Name -> Name -> PatSynArgs -- |
--   pattern P { {x,y,z} } = p
--   
RecordPatSyn :: [Name] -> PatSynArgs -- | A pattern synonym's directionality. data PatSynDir -- |
--   pattern P x {<-} p
--   
Unidir :: PatSynDir -- |
--   pattern P x {=} p
--   
ImplBidir :: PatSynDir -- |
--   pattern P x {<-} p where P x = e
--   
ExplBidir :: [Clause] -> PatSynDir -- | As of template-haskell-2.11.0.0, VarStrictType has -- been replaced by VarBangType. type VarStrictType = VarBangType -- | As of template-haskell-2.11.0.0, StrictType has been -- replaced by BangType. type StrictType = BangType -- | As of template-haskell-2.11.0.0, Strict has been -- replaced by Bang. type Strict = Bang data Bang -- |
--   C { {-# UNPACK #-} !}a
--   
Bang :: SourceUnpackedness -> SourceStrictness -> Bang -- | Unlike SourceStrictness and SourceUnpackedness, -- DecidedStrictness refers to the strictness that the compiler -- chooses for a data constructor field, which may be different from what -- is written in source code. See reifyConStrictness for more -- information. data DecidedStrictness DecidedLazy :: DecidedStrictness DecidedStrict :: DecidedStrictness DecidedUnpack :: DecidedStrictness data SourceStrictness -- |
--   C a
--   
NoSourceStrictness :: SourceStrictness -- |
--   C {~}a
--   
SourceLazy :: SourceStrictness -- |
--   C {!}a
--   
SourceStrict :: SourceStrictness data SourceUnpackedness -- |
--   C a
--   
NoSourceUnpackedness :: SourceUnpackedness -- |
--   C { {-# NOUNPACK #-} } a
--   
SourceNoUnpack :: SourceUnpackedness -- |
--   C { {-# UNPACK #-} } a
--   
SourceUnpack :: SourceUnpackedness type Cxt = [Pred] " @(Eq a, Ord b)@" data AnnTarget ModuleAnnotation :: AnnTarget TypeAnnotation :: Name -> AnnTarget ValueAnnotation :: Name -> AnnTarget data Phases AllPhases :: Phases FromPhase :: Int -> Phases BeforePhase :: Int -> Phases data RuleMatch ConLike :: RuleMatch FunLike :: RuleMatch data Inline NoInline :: Inline Inline :: Inline Inlinable :: Inline data Pragma InlineP :: Name -> Inline -> RuleMatch -> Phases -> Pragma SpecialiseP :: Name -> Type -> Maybe Inline -> Phases -> Pragma SpecialiseInstP :: Type -> Pragma RuleP :: String -> Maybe [TyVarBndr ()] -> [RuleBndr] -> Exp -> Exp -> Phases -> Pragma AnnP :: AnnTarget -> Exp -> Pragma LineP :: Int -> String -> Pragma -- |
--   { {-# COMPLETE C_1, ..., C_i [ :: T ] #-} }
--   
CompleteP :: [Name] -> Maybe Name -> Pragma data Safety Unsafe :: Safety Safe :: Safety Interruptible :: Safety data Callconv CCall :: Callconv StdCall :: Callconv CApi :: Callconv Prim :: Callconv JavaScript :: Callconv data Foreign ImportF :: Callconv -> Safety -> String -> Name -> Type -> Foreign ExportF :: Callconv -> String -> Name -> Type -> Foreign -- | Common elements of OpenTypeFamilyD and -- ClosedTypeFamilyD. By analogy with "head" for type classes and -- type class instances as defined in Type classes: an exploration of -- the design space, the TypeFamilyHead is defined to be the -- elements of the declaration between type family and -- where. data TypeFamilyHead TypeFamilyHead :: Name -> [TyVarBndr ()] -> FamilyResultSig -> Maybe InjectivityAnn -> TypeFamilyHead -- | A pattern synonym's type. Note that a pattern synonym's fully -- specified type has a peculiar shape coming with two forall quantifiers -- and two constraint contexts. For example, consider the pattern synonym -- --
--   pattern P x1 x2 ... xn = <some-pattern>
--   
-- -- P's complete type is of the following form -- --
--   pattern P :: forall universals.   required constraints
--             => forall existentials. provided constraints
--             => t1 -> t2 -> ... -> tn -> t
--   
-- -- consisting of four parts: -- --
    --
  1. the (possibly empty lists of) universally quantified type -- variables and required constraints on them.
  2. --
  3. the (possibly empty lists of) existentially quantified type -- variables and the provided constraints on them.
  4. --
  5. the types t1, t2, .., tn of -- x1, x2, .., xn, respectively
  6. --
  7. the type t of <some-pattern>, mentioning -- only universals.
  8. --
-- -- Pattern synonym types interact with TH when (a) reifying a pattern -- synonym, (b) pretty printing, or (c) specifying a pattern synonym's -- type signature explicitly: -- -- -- -- See the GHC user's guide for more information on pattern synonyms and -- their types: -- https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts.html#pattern-synonyms. type PatSynType = Type data Range FromR :: Exp -> Range FromThenR :: Exp -> Exp -> Range FromToR :: Exp -> Exp -> Range FromThenToR :: Exp -> Exp -> Exp -> Range data Guard -- |
--   f x { | odd x } = x
--   
NormalG :: Exp -> Guard -- |
--   f x { | Just y <- x, Just z <- y } = z
--   
PatG :: [Stmt] -> Guard data Body -- |
--   f p { | e1 = e2
--         | e3 = e4 }
--    where ds
--   
GuardedB :: [(Guard, Exp)] -> Body -- |
--   f p { = e } where ds
--   
NormalB :: Exp -> Body -- | Raw bytes embedded into the binary. -- -- Avoid using Bytes constructor directly as it is likely to change in -- the future. Use helpers such as mkBytes in -- Language.Haskell.TH.Lib instead. data Bytes Bytes :: ForeignPtr Word8 -> Word -> Word -> Bytes -- | Pointer to the data [bytesPtr] :: Bytes -> ForeignPtr Word8 -- | Offset from the pointer [bytesOffset] :: Bytes -> Word -- | Number of bytes Maybe someday: , bytesAlignement :: Word -- ^ -- Alignement constraint , bytesReadOnly :: Bool -- ^ Shall we embed into -- a read-only -- section or not , bytesInitialized :: Bool -- ^ False: -- only use bytesSize to allocate -- an uninitialized region [bytesSize] :: Bytes -> Word data Lit CharL :: Char -> Lit StringL :: String -> Lit -- | Used for overloaded and non-overloaded literals. We don't have a good -- way to represent non-overloaded literals at the moment. Maybe that -- doesn't matter? IntegerL :: Integer -> Lit RationalL :: Rational -> Lit IntPrimL :: Integer -> Lit WordPrimL :: Integer -> Lit FloatPrimL :: Rational -> Lit DoublePrimL :: Rational -> Lit -- | A primitive C-style string, type Addr# StringPrimL :: [Word8] -> Lit -- | Some raw bytes, type Addr#: BytesPrimL :: Bytes -> Lit CharPrimL :: Char -> Lit data FixityDirection InfixL :: FixityDirection InfixR :: FixityDirection InfixN :: FixityDirection data Fixity Fixity :: Int -> FixityDirection -> Fixity -- | InstanceDec describes a single instance of a class or type -- function. It is just a Dec, but guaranteed to be one of the -- following: -- -- type InstanceDec = Dec -- | In PrimTyConI, is the type constructor unlifted? type Unlifted = Bool -- | In PrimTyConI, arity of the type constructor type Arity = Int -- | In UnboxedSumE, UnboxedSumT, and UnboxedSumP, the -- total number of SumAlts. For example, (#|#) has a -- SumArity of 2. type SumArity = Int -- | In UnboxedSumE and UnboxedSumP, the number associated -- with a particular data constructor. SumAlts are one-indexed and -- should never exceed the value of its corresponding SumArity. -- For example: -- -- type SumAlt = Int -- | In ClassOpI and DataConI, name of the parent class or -- type type ParentName = Name -- | Obtained from reifyModule in the Q Monad. data ModuleInfo -- | Contains the import list of the module. ModuleInfo :: [Module] -> ModuleInfo -- | Obtained from reify in the Q Monad. data Info -- | A class, with a list of its visible instances ClassI :: Dec -> [InstanceDec] -> Info -- | A class method ClassOpI :: Name -> Type -> ParentName -> Info -- | A "plain" type constructor. "Fancier" type constructors are returned -- using PrimTyConI or FamilyI as appropriate. At present, -- this reified declaration will never have derived instances attached to -- it (if you wish to check for an instance, see reifyInstances). TyConI :: Dec -> Info -- | A type or data family, with a list of its visible instances. A closed -- type family is returned with 0 instances. FamilyI :: Dec -> [InstanceDec] -> Info -- | A "primitive" type constructor, which can't be expressed with a -- Dec. Examples: (->), Int#. PrimTyConI :: Name -> Arity -> Unlifted -> Info -- | A data constructor DataConI :: Name -> Type -> ParentName -> Info -- | A pattern synonym PatSynI :: Name -> PatSynType -> Info -- | A "value" variable (as opposed to a type variable, see TyVarI). -- -- The Maybe Dec field contains Just the declaration -- which defined the variable - including the RHS of the declaration - or -- else Nothing, in the case where the RHS is unavailable to the -- compiler. At present, this value is always Nothing: -- returning the RHS has not yet been implemented because of lack of -- interest. VarI :: Name -> Type -> Maybe Dec -> Info -- | A type variable. -- -- The Type field contains the type which underlies the -- variable. At present, this is always VarT theName, but -- future changes may permit refinement of this. TyVarI :: Name -> Type -> Info type CharPos = (Int, Int) " Line and character position" data Loc Loc :: String -> String -> String -> CharPos -> CharPos -> Loc [loc_filename] :: Loc -> String [loc_package] :: Loc -> String [loc_module] :: Loc -> String [loc_start] :: Loc -> CharPos [loc_end] :: Loc -> CharPos data NameIs Alone :: NameIs Applied :: NameIs Infix :: NameIs -- | Uniq is used by GHC to distinguish names from each other. type Uniq = Integer data NameSpace -- | Variables VarName :: NameSpace -- | Data constructors DataName :: NameSpace -- | Type constructors and classes; Haskell has them in the same name space -- for now. TcClsName :: NameSpace data NameFlavour -- | An unqualified name; dynamically bound NameS :: NameFlavour -- | A qualified name; dynamically bound NameQ :: ModName -> NameFlavour -- | A unique local name NameU :: !Uniq -> NameFlavour -- | Local name bound outside of the TH AST NameL :: !Uniq -> NameFlavour -- | Global name bound outside of the TH AST: An original name (occurrences -- only, not binders) Need the namespace too to be sure which thing we -- are naming NameG :: NameSpace -> PkgName -> ModName -> NameFlavour newtype OccName OccName :: String -> OccName -- | Obtained from reifyModule and thisModule. data Module Module :: PkgName -> ModName -> Module newtype PkgName PkgName :: String -> PkgName newtype ModName ModName :: String -> ModName class (MonadIO m, MonadFail m) => Quasi m qNewName :: Quasi m => String -> m Name qReport :: Quasi m => Bool -> String -> m () qRecover :: Quasi m => m a -> m a -> m a qLookupName :: Quasi m => Bool -> String -> m (Maybe Name) qReify :: Quasi m => Name -> m Info qReifyFixity :: Quasi m => Name -> m (Maybe Fixity) qReifyType :: Quasi m => Name -> m Type qReifyInstances :: Quasi m => Name -> [Type] -> m [Dec] qReifyRoles :: Quasi m => Name -> m [Role] qReifyAnnotations :: (Quasi m, Data a) => AnnLookup -> m [a] qReifyModule :: Quasi m => Module -> m ModuleInfo qReifyConStrictness :: Quasi m => Name -> m [DecidedStrictness] qLocation :: Quasi m => m Loc qRunIO :: Quasi m => IO a -> m a qAddDependentFile :: Quasi m => FilePath -> m () qAddTempFile :: Quasi m => String -> m FilePath qAddTopDecls :: Quasi m => [Dec] -> m () qAddForeignFilePath :: Quasi m => ForeignSrcLang -> String -> m () qAddModFinalizer :: Quasi m => Q () -> m () qAddCorePlugin :: Quasi m => String -> m () qGetQ :: (Quasi m, Typeable a) => m (Maybe a) qPutQ :: (Quasi m, Typeable a) => a -> m () qIsExtEnabled :: Quasi m => Extension -> m Bool qExtsEnabled :: Quasi m => m [Extension] memcmp :: Ptr a -> Ptr b -> CSize -> IO CInt newNameIO :: String -> IO Name badIO :: String -> IO a counter :: IORef Uniq runQ :: Quasi m => Q a -> m a -- | Report an error (True) or warning (False), but carry on; use -- fail to stop. -- | Deprecated: Use reportError or reportWarning instead report :: Bool -> String -> Q () -- | Report an error to the user, but allow the current splice's -- computation to carry on. To abort the computation, use fail. reportError :: String -> Q () -- | Report a warning to the user, and carry on. reportWarning :: String -> Q () -- | Recover from errors raised by reportError or fail. recover :: Q a -> Q a -> Q a lookupName :: Bool -> String -> Q (Maybe Name) -- | Look up the given name in the (type namespace of the) current splice's -- scope. See Language.Haskell.TH.Syntax#namelookup for more -- details. lookupTypeName :: String -> Q (Maybe Name) -- | Look up the given name in the (value namespace of the) current -- splice's scope. See Language.Haskell.TH.Syntax#namelookup for -- more details. lookupValueName :: String -> Q (Maybe Name) -- | reify looks up information about the Name. -- -- It is sometimes useful to construct the argument name using -- lookupTypeName or lookupValueName to ensure that we are -- reifying from the right namespace. For instance, in this context: -- --
--   data D = D
--   
-- -- which D does reify (mkName "D") return information -- about? (Answer: D-the-type, but don't rely on it.) To ensure -- we get information about D-the-value, use -- lookupValueName: -- --
--   do
--     Just nm <- lookupValueName "D"
--     reify nm
--   
-- -- and to get information about D-the-type, use -- lookupTypeName. reify :: Name -> Q Info -- | reifyFixity nm attempts to find a fixity declaration for -- nm. For example, if the function foo has the fixity -- declaration infixr 7 foo, then reifyFixity 'foo -- would return Just (Fixity 7 InfixR). If -- the function bar does not have a fixity declaration, then -- reifyFixity 'bar returns Nothing, so you may assume -- bar has defaultFixity. reifyFixity :: Name -> Q (Maybe Fixity) -- | reifyType nm attempts to find the type or kind of -- nm. For example, reifyType 'not returns Bool -- -> Bool, and reifyType ''Bool returns Type. -- This works even if there's no explicit signature and the type or kind -- is inferred. reifyType :: Name -> Q Type -- | reifyInstances nm tys returns a list of visible instances of -- nm tys. That is, if nm is the name of a type class, -- then all instances of this class at the types tys are -- returned. Alternatively, if nm is the name of a data family -- or type family, all instances of this family at the types tys -- are returned. -- -- Note that this is a "shallow" test; the declarations returned merely -- have instance heads which unify with nm tys, they need not -- actually be satisfiable. -- -- -- -- There is one edge case: reifyInstances ''Typeable tys -- currently always produces an empty list (no matter what tys -- are given). reifyInstances :: Name -> [Type] -> Q [InstanceDec] -- | reifyRoles nm returns the list of roles associated with the -- parameters of the tycon nm. Fails if nm cannot be -- found or is not a tycon. The returned list should never contain -- InferR. reifyRoles :: Name -> Q [Role] -- | reifyAnnotations target returns the list of annotations -- associated with target. Only the annotations that are -- appropriately typed is returned. So if you have Int and -- String annotations for the same target, you have to call this -- function twice. reifyAnnotations :: Data a => AnnLookup -> Q [a] -- | reifyModule mod looks up information about module -- mod. To look up the current module, call this function with -- the return value of thisModule. reifyModule :: Module -> Q ModuleInfo -- | reifyConStrictness nm looks up the strictness information for -- the fields of the constructor with the name nm. Note that the -- strictness information that reifyConStrictness returns may not -- correspond to what is written in the source code. For example, in the -- following data declaration: -- --
--   data Pair a = Pair a a
--   
-- -- reifyConStrictness would return [DecidedLazy, -- DecidedLazy] under most circumstances, but it would return -- [DecidedStrict, DecidedStrict] if the -- -XStrictData language extension was enabled. reifyConStrictness :: Name -> Q [DecidedStrictness] -- | Is the list of instances returned by reifyInstances nonempty? isInstance :: Name -> [Type] -> Q Bool -- | The location at which this computation is spliced. location :: Q Loc -- | The runIO function lets you run an I/O computation in the -- Q monad. Take care: you are guaranteed the ordering of calls to -- runIO within a single Q computation, but not about the -- order in which splices are run. -- -- Note: for various murky reasons, stdout and stderr handles are not -- necessarily flushed when the compiler finishes running, so you should -- flush them yourself. runIO :: IO a -> Q a -- | Record external files that runIO is using (dependent upon). The -- compiler can then recognize that it should re-compile the Haskell file -- when an external file changes. -- -- Expects an absolute file path. -- -- Notes: -- -- addDependentFile :: FilePath -> Q () -- | Obtain a temporary file path with the given suffix. The compiler will -- delete this file after compilation. addTempFile :: String -> Q FilePath -- | Add additional top-level declarations. The added declarations will be -- type checked along with the current declaration group. addTopDecls :: [Dec] -> Q () -- | Deprecated: Use addForeignSource instead addForeignFile :: ForeignSrcLang -> String -> Q () -- | Emit a foreign file which will be compiled and linked to the object -- for the current module. Currently only languages that can be compiled -- with the C compiler are supported, and the flags passed as part of -- -optc will be also applied to the C compiler invocation that will -- compile them. -- -- Note that for non-C languages (for example C++) extern -- C directives must be used to get symbols that we can -- access from Haskell. -- -- To get better errors, it is recommended to use #line pragmas when -- emitting C files, e.g. -- --
--   {-# LANGUAGE CPP #-}
--   ...
--   addForeignSource LangC $ unlines
--     [ "#line " ++ show (592 + 1) ++ " " ++ show "libraries/template-haskell/Language/Haskell/TH/Syntax.hs"
--     , ...
--     ]
--   
addForeignSource :: ForeignSrcLang -> String -> Q () -- | Same as addForeignSource, but expects to receive a path -- pointing to the foreign file instead of a String of its -- contents. Consider using this in conjunction with addTempFile. -- -- This is a good alternative to addForeignSource when you are -- trying to directly link in an object file. addForeignFilePath :: ForeignSrcLang -> FilePath -> Q () -- | Add a finalizer that will run in the Q monad after the current module -- has been type checked. This only makes sense when run within a -- top-level splice. -- -- The finalizer is given the local type environment at the splice point. -- Thus reify is able to find the local definitions when executed -- inside the finalizer. addModFinalizer :: Q () -> Q () -- | Adds a core plugin to the compilation pipeline. -- -- addCorePlugin m has almost the same effect as passing -- -fplugin=m to ghc in the command line. The major difference -- is that the plugin module m must not belong to the current -- package. When TH executes, it is too late to tell the compiler that we -- needed to compile first a plugin module in the current package. addCorePlugin :: String -> Q () -- | Get state from the Q monad. Note that the state is local to the -- Haskell module in which the Template Haskell expression is executed. getQ :: Typeable a => Q (Maybe a) -- | Replace the state in the Q monad. Note that the state is local -- to the Haskell module in which the Template Haskell expression is -- executed. putQ :: Typeable a => a -> Q () -- | Determine whether the given language extension is enabled in the -- Q monad. isExtEnabled :: Extension -> Q Bool -- | List all enabled language extensions. extsEnabled :: Q [Extension] trueName :: Name falseName :: Name nothingName :: Name justName :: Name leftName :: Name rightName :: Name nonemptyName :: Name -- | dataToQa is an internal utility function for constructing -- generic conversion functions from types with Data instances to -- various quasi-quoting representations. See the source of -- dataToExpQ and dataToPatQ for two example usages: -- mkCon, mkLit and appQ are overloadable to -- account for different syntax for expressions and patterns; -- antiQ allows you to override type-specific cases, a common -- usage is just const Nothing, which results in no overloading. dataToQa :: forall m a k q. (Quote m, Data a) => (Name -> k) -> (Lit -> m q) -> (k -> [m q] -> m q) -> (forall b. Data b => b -> Maybe (m q)) -> a -> m q -- | dataToExpQ converts a value to a Exp representation of -- the same value, in the SYB style. It is generalized to take a function -- override type-specific cases; see liftData for a more commonly -- used variant. dataToExpQ :: (Quote m, Data a) => (forall b. Data b => b -> Maybe (m Exp)) -> a -> m Exp -- | liftData is a variant of lift in the Lift type -- class which works for any type with a Data instance. liftData :: (Quote m, Data a) => a -> m Exp -- | dataToPatQ converts a value to a Pat representation of -- the same value, in the SYB style. It takes a function to handle -- type-specific cases, alternatively, pass const Nothing to get -- default behavior. dataToPatQ :: (Quote m, Data a) => (forall b. Data b => b -> Maybe (m Pat)) -> a -> m Pat mkModName :: String -> ModName modString :: ModName -> String mkPkgName :: String -> PkgName pkgString :: PkgName -> String mkOccName :: String -> OccName occString :: OccName -> String -- | The name without its module prefix. -- --

Examples

-- --
--   >>> nameBase ''Data.Either.Either
--   "Either"
--   
--   >>> nameBase (mkName "foo")
--   "foo"
--   
--   >>> nameBase (mkName "Module.foo")
--   "foo"
--   
nameBase :: Name -> String -- | Module prefix of a name, if it exists. -- --

Examples

-- --
--   >>> nameModule ''Data.Either.Either
--   Just "Data.Either"
--   
--   >>> nameModule (mkName "foo")
--   Nothing
--   
--   >>> nameModule (mkName "Module.foo")
--   Just "Module"
--   
nameModule :: Name -> Maybe String -- | A name's package, if it exists. -- --

Examples

-- --
--   >>> namePackage ''Data.Either.Either
--   Just "base"
--   
--   >>> namePackage (mkName "foo")
--   Nothing
--   
--   >>> namePackage (mkName "Module.foo")
--   Nothing
--   
namePackage :: Name -> Maybe String -- | Returns whether a name represents an occurrence of a top-level -- variable (VarName), data constructor (DataName), type -- constructor, or type class (TcClsName). If we can't be sure, it -- returns Nothing. -- --

Examples

-- --
--   >>> nameSpace 'Prelude.id
--   Just VarName
--   
--   >>> nameSpace (mkName "id")
--   Nothing -- only works for top-level variable names
--   
--   >>> nameSpace 'Data.Maybe.Just
--   Just DataName
--   
--   >>> nameSpace ''Data.Maybe.Maybe
--   Just TcClsName
--   
--   >>> nameSpace ''Data.Ord.Ord
--   Just TcClsName
--   
nameSpace :: Name -> Maybe NameSpace -- | Only used internally mkNameU :: String -> Uniq -> Name -- | Used for 'x etc, but not available to the programmer mkNameG :: NameSpace -> String -> String -> String -> Name showName :: Name -> String showName' :: NameIs -> Name -> String -- | Tuple data constructor tupleDataName :: Int -> Name -- | Tuple type constructor tupleTypeName :: Int -> Name -- | Unboxed tuple data constructor unboxedTupleDataName :: Int -> Name -- | Unboxed tuple type constructor unboxedTupleTypeName :: Int -> Name mk_tup_name :: Int -> NameSpace -> Bool -> Name -- | Unboxed sum data constructor unboxedSumDataName :: SumAlt -> SumArity -> Name -- | Unboxed sum type constructor unboxedSumTypeName :: SumArity -> Name -- | Highest allowed operator precedence for Fixity constructor -- (answer: 9) maxPrecedence :: Int -- | Default fixity: infixl 9 defaultFixity :: Fixity eqBytes :: Bytes -> Bytes -> Bool compareBytes :: Bytes -> Bytes -> Ordering cmpEq :: Ordering -> Bool thenCmp :: Ordering -> Ordering -> Ordering -- | Foreign formats supported by GHC via TH data ForeignSrcLang -- | C LangC :: ForeignSrcLang -- | C++ LangCxx :: ForeignSrcLang -- | Objective C LangObjc :: ForeignSrcLang -- | Objective C++ LangObjcxx :: ForeignSrcLang -- | Assembly language (.s) LangAsm :: ForeignSrcLang -- | Object (.o) RawObject :: ForeignSrcLang instance GHC.Generics.Generic Language.Haskell.TH.Syntax.ModName instance Data.Data.Data Language.Haskell.TH.Syntax.ModName instance GHC.Classes.Ord Language.Haskell.TH.Syntax.ModName instance GHC.Classes.Eq Language.Haskell.TH.Syntax.ModName instance GHC.Show.Show Language.Haskell.TH.Syntax.ModName instance GHC.Generics.Generic Language.Haskell.TH.Syntax.PkgName instance Data.Data.Data Language.Haskell.TH.Syntax.PkgName instance GHC.Classes.Ord Language.Haskell.TH.Syntax.PkgName instance GHC.Classes.Eq Language.Haskell.TH.Syntax.PkgName instance GHC.Show.Show Language.Haskell.TH.Syntax.PkgName instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Module instance Data.Data.Data Language.Haskell.TH.Syntax.Module instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Module instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Module instance GHC.Show.Show Language.Haskell.TH.Syntax.Module instance GHC.Generics.Generic Language.Haskell.TH.Syntax.OccName instance Data.Data.Data Language.Haskell.TH.Syntax.OccName instance GHC.Classes.Ord Language.Haskell.TH.Syntax.OccName instance GHC.Classes.Eq Language.Haskell.TH.Syntax.OccName instance GHC.Show.Show Language.Haskell.TH.Syntax.OccName instance GHC.Generics.Generic Language.Haskell.TH.Syntax.NameSpace instance Data.Data.Data Language.Haskell.TH.Syntax.NameSpace instance GHC.Show.Show Language.Haskell.TH.Syntax.NameSpace instance GHC.Classes.Ord Language.Haskell.TH.Syntax.NameSpace instance GHC.Classes.Eq Language.Haskell.TH.Syntax.NameSpace instance GHC.Generics.Generic Language.Haskell.TH.Syntax.NameFlavour instance GHC.Show.Show Language.Haskell.TH.Syntax.NameFlavour instance GHC.Classes.Ord Language.Haskell.TH.Syntax.NameFlavour instance GHC.Classes.Eq Language.Haskell.TH.Syntax.NameFlavour instance Data.Data.Data Language.Haskell.TH.Syntax.NameFlavour instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Name instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Name instance Data.Data.Data Language.Haskell.TH.Syntax.Name instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Loc instance Data.Data.Data Language.Haskell.TH.Syntax.Loc instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Loc instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Loc instance GHC.Show.Show Language.Haskell.TH.Syntax.Loc instance GHC.Generics.Generic Language.Haskell.TH.Syntax.ModuleInfo instance Data.Data.Data Language.Haskell.TH.Syntax.ModuleInfo instance GHC.Classes.Ord Language.Haskell.TH.Syntax.ModuleInfo instance GHC.Classes.Eq Language.Haskell.TH.Syntax.ModuleInfo instance GHC.Show.Show Language.Haskell.TH.Syntax.ModuleInfo instance GHC.Generics.Generic Language.Haskell.TH.Syntax.FixityDirection instance Data.Data.Data Language.Haskell.TH.Syntax.FixityDirection instance GHC.Show.Show Language.Haskell.TH.Syntax.FixityDirection instance GHC.Classes.Ord Language.Haskell.TH.Syntax.FixityDirection instance GHC.Classes.Eq Language.Haskell.TH.Syntax.FixityDirection instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Fixity instance Data.Data.Data Language.Haskell.TH.Syntax.Fixity instance GHC.Show.Show Language.Haskell.TH.Syntax.Fixity instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Fixity instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Fixity instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Bytes instance Data.Data.Data Language.Haskell.TH.Syntax.Bytes instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Lit instance Data.Data.Data Language.Haskell.TH.Syntax.Lit instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Lit instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Lit instance GHC.Show.Show Language.Haskell.TH.Syntax.Lit instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Overlap instance Data.Data.Data Language.Haskell.TH.Syntax.Overlap instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Overlap instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Overlap instance GHC.Show.Show Language.Haskell.TH.Syntax.Overlap instance GHC.Generics.Generic Language.Haskell.TH.Syntax.FunDep instance Data.Data.Data Language.Haskell.TH.Syntax.FunDep instance GHC.Classes.Ord Language.Haskell.TH.Syntax.FunDep instance GHC.Classes.Eq Language.Haskell.TH.Syntax.FunDep instance GHC.Show.Show Language.Haskell.TH.Syntax.FunDep instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Callconv instance Data.Data.Data Language.Haskell.TH.Syntax.Callconv instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Callconv instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Callconv instance GHC.Show.Show Language.Haskell.TH.Syntax.Callconv instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Safety instance Data.Data.Data Language.Haskell.TH.Syntax.Safety instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Safety instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Safety instance GHC.Show.Show Language.Haskell.TH.Syntax.Safety instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Inline instance Data.Data.Data Language.Haskell.TH.Syntax.Inline instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Inline instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Inline instance GHC.Show.Show Language.Haskell.TH.Syntax.Inline instance GHC.Generics.Generic Language.Haskell.TH.Syntax.RuleMatch instance Data.Data.Data Language.Haskell.TH.Syntax.RuleMatch instance GHC.Classes.Ord Language.Haskell.TH.Syntax.RuleMatch instance GHC.Classes.Eq Language.Haskell.TH.Syntax.RuleMatch instance GHC.Show.Show Language.Haskell.TH.Syntax.RuleMatch instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Phases instance Data.Data.Data Language.Haskell.TH.Syntax.Phases instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Phases instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Phases instance GHC.Show.Show Language.Haskell.TH.Syntax.Phases instance GHC.Generics.Generic Language.Haskell.TH.Syntax.AnnTarget instance Data.Data.Data Language.Haskell.TH.Syntax.AnnTarget instance GHC.Classes.Ord Language.Haskell.TH.Syntax.AnnTarget instance GHC.Classes.Eq Language.Haskell.TH.Syntax.AnnTarget instance GHC.Show.Show Language.Haskell.TH.Syntax.AnnTarget instance GHC.Generics.Generic Language.Haskell.TH.Syntax.SourceUnpackedness instance Data.Data.Data Language.Haskell.TH.Syntax.SourceUnpackedness instance GHC.Classes.Ord Language.Haskell.TH.Syntax.SourceUnpackedness instance GHC.Classes.Eq Language.Haskell.TH.Syntax.SourceUnpackedness instance GHC.Show.Show Language.Haskell.TH.Syntax.SourceUnpackedness instance GHC.Generics.Generic Language.Haskell.TH.Syntax.SourceStrictness instance Data.Data.Data Language.Haskell.TH.Syntax.SourceStrictness instance GHC.Classes.Ord Language.Haskell.TH.Syntax.SourceStrictness instance GHC.Classes.Eq Language.Haskell.TH.Syntax.SourceStrictness instance GHC.Show.Show Language.Haskell.TH.Syntax.SourceStrictness instance GHC.Generics.Generic Language.Haskell.TH.Syntax.DecidedStrictness instance Data.Data.Data Language.Haskell.TH.Syntax.DecidedStrictness instance GHC.Classes.Ord Language.Haskell.TH.Syntax.DecidedStrictness instance GHC.Classes.Eq Language.Haskell.TH.Syntax.DecidedStrictness instance GHC.Show.Show Language.Haskell.TH.Syntax.DecidedStrictness instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Bang instance Data.Data.Data Language.Haskell.TH.Syntax.Bang instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Bang instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Bang instance GHC.Show.Show Language.Haskell.TH.Syntax.Bang instance GHC.Generics.Generic Language.Haskell.TH.Syntax.PatSynArgs instance Data.Data.Data Language.Haskell.TH.Syntax.PatSynArgs instance GHC.Classes.Ord Language.Haskell.TH.Syntax.PatSynArgs instance GHC.Classes.Eq Language.Haskell.TH.Syntax.PatSynArgs instance GHC.Show.Show Language.Haskell.TH.Syntax.PatSynArgs instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Specificity instance Data.Data.Data Language.Haskell.TH.Syntax.Specificity instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Specificity instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Specificity instance GHC.Show.Show Language.Haskell.TH.Syntax.Specificity instance GHC.Generics.Generic Language.Haskell.TH.Syntax.InjectivityAnn instance Data.Data.Data Language.Haskell.TH.Syntax.InjectivityAnn instance GHC.Classes.Ord Language.Haskell.TH.Syntax.InjectivityAnn instance GHC.Classes.Eq Language.Haskell.TH.Syntax.InjectivityAnn instance GHC.Show.Show Language.Haskell.TH.Syntax.InjectivityAnn instance GHC.Generics.Generic Language.Haskell.TH.Syntax.TyLit instance Data.Data.Data Language.Haskell.TH.Syntax.TyLit instance GHC.Classes.Ord Language.Haskell.TH.Syntax.TyLit instance GHC.Classes.Eq Language.Haskell.TH.Syntax.TyLit instance GHC.Show.Show Language.Haskell.TH.Syntax.TyLit instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Role instance Data.Data.Data Language.Haskell.TH.Syntax.Role instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Role instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Role instance GHC.Show.Show Language.Haskell.TH.Syntax.Role instance GHC.Generics.Generic Language.Haskell.TH.Syntax.AnnLookup instance Data.Data.Data Language.Haskell.TH.Syntax.AnnLookup instance GHC.Classes.Ord Language.Haskell.TH.Syntax.AnnLookup instance GHC.Classes.Eq Language.Haskell.TH.Syntax.AnnLookup instance GHC.Show.Show Language.Haskell.TH.Syntax.AnnLookup instance GHC.Base.Functor Language.Haskell.TH.Syntax.TyVarBndr instance GHC.Generics.Generic (Language.Haskell.TH.Syntax.TyVarBndr flag) instance Data.Data.Data flag => Data.Data.Data (Language.Haskell.TH.Syntax.TyVarBndr flag) instance GHC.Classes.Ord flag => GHC.Classes.Ord (Language.Haskell.TH.Syntax.TyVarBndr flag) instance GHC.Classes.Eq flag => GHC.Classes.Eq (Language.Haskell.TH.Syntax.TyVarBndr flag) instance GHC.Show.Show flag => GHC.Show.Show (Language.Haskell.TH.Syntax.TyVarBndr flag) instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Type instance Data.Data.Data Language.Haskell.TH.Syntax.Type instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Type instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Type instance GHC.Show.Show Language.Haskell.TH.Syntax.Type instance GHC.Generics.Generic Language.Haskell.TH.Syntax.FamilyResultSig instance Data.Data.Data Language.Haskell.TH.Syntax.FamilyResultSig instance GHC.Classes.Ord Language.Haskell.TH.Syntax.FamilyResultSig instance GHC.Classes.Eq Language.Haskell.TH.Syntax.FamilyResultSig instance GHC.Show.Show Language.Haskell.TH.Syntax.FamilyResultSig instance GHC.Generics.Generic Language.Haskell.TH.Syntax.TypeFamilyHead instance Data.Data.Data Language.Haskell.TH.Syntax.TypeFamilyHead instance GHC.Classes.Ord Language.Haskell.TH.Syntax.TypeFamilyHead instance GHC.Classes.Eq Language.Haskell.TH.Syntax.TypeFamilyHead instance GHC.Show.Show Language.Haskell.TH.Syntax.TypeFamilyHead instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Con instance Data.Data.Data Language.Haskell.TH.Syntax.Con instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Con instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Con instance GHC.Show.Show Language.Haskell.TH.Syntax.Con instance GHC.Generics.Generic Language.Haskell.TH.Syntax.RuleBndr instance Data.Data.Data Language.Haskell.TH.Syntax.RuleBndr instance GHC.Classes.Ord Language.Haskell.TH.Syntax.RuleBndr instance GHC.Classes.Eq Language.Haskell.TH.Syntax.RuleBndr instance GHC.Show.Show Language.Haskell.TH.Syntax.RuleBndr instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Foreign instance Data.Data.Data Language.Haskell.TH.Syntax.Foreign instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Foreign instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Foreign instance GHC.Show.Show Language.Haskell.TH.Syntax.Foreign instance GHC.Generics.Generic Language.Haskell.TH.Syntax.TySynEqn instance Data.Data.Data Language.Haskell.TH.Syntax.TySynEqn instance GHC.Classes.Ord Language.Haskell.TH.Syntax.TySynEqn instance GHC.Classes.Eq Language.Haskell.TH.Syntax.TySynEqn instance GHC.Show.Show Language.Haskell.TH.Syntax.TySynEqn instance GHC.Generics.Generic Language.Haskell.TH.Syntax.DerivStrategy instance Data.Data.Data Language.Haskell.TH.Syntax.DerivStrategy instance GHC.Classes.Ord Language.Haskell.TH.Syntax.DerivStrategy instance GHC.Classes.Eq Language.Haskell.TH.Syntax.DerivStrategy instance GHC.Show.Show Language.Haskell.TH.Syntax.DerivStrategy instance GHC.Generics.Generic Language.Haskell.TH.Syntax.DerivClause instance Data.Data.Data Language.Haskell.TH.Syntax.DerivClause instance GHC.Classes.Ord Language.Haskell.TH.Syntax.DerivClause instance GHC.Classes.Eq Language.Haskell.TH.Syntax.DerivClause instance GHC.Show.Show Language.Haskell.TH.Syntax.DerivClause instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Pragma instance Data.Data.Data Language.Haskell.TH.Syntax.Pragma instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Pragma instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Pragma instance GHC.Show.Show Language.Haskell.TH.Syntax.Pragma instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Pat instance Data.Data.Data Language.Haskell.TH.Syntax.Pat instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Pat instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Pat instance GHC.Show.Show Language.Haskell.TH.Syntax.Pat instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Match instance Data.Data.Data Language.Haskell.TH.Syntax.Match instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Match instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Match instance GHC.Show.Show Language.Haskell.TH.Syntax.Match instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Range instance Data.Data.Data Language.Haskell.TH.Syntax.Range instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Range instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Range instance GHC.Show.Show Language.Haskell.TH.Syntax.Range instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Exp instance Data.Data.Data Language.Haskell.TH.Syntax.Exp instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Exp instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Exp instance GHC.Show.Show Language.Haskell.TH.Syntax.Exp instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Stmt instance Data.Data.Data Language.Haskell.TH.Syntax.Stmt instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Stmt instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Stmt instance GHC.Show.Show Language.Haskell.TH.Syntax.Stmt instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Guard instance Data.Data.Data Language.Haskell.TH.Syntax.Guard instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Guard instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Guard instance GHC.Show.Show Language.Haskell.TH.Syntax.Guard instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Body instance Data.Data.Data Language.Haskell.TH.Syntax.Body instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Body instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Body instance GHC.Show.Show Language.Haskell.TH.Syntax.Body instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Clause instance Data.Data.Data Language.Haskell.TH.Syntax.Clause instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Clause instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Clause instance GHC.Show.Show Language.Haskell.TH.Syntax.Clause instance GHC.Generics.Generic Language.Haskell.TH.Syntax.PatSynDir instance Data.Data.Data Language.Haskell.TH.Syntax.PatSynDir instance GHC.Classes.Ord Language.Haskell.TH.Syntax.PatSynDir instance GHC.Classes.Eq Language.Haskell.TH.Syntax.PatSynDir instance GHC.Show.Show Language.Haskell.TH.Syntax.PatSynDir instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Dec instance Data.Data.Data Language.Haskell.TH.Syntax.Dec instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Dec instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Dec instance GHC.Show.Show Language.Haskell.TH.Syntax.Dec instance GHC.Generics.Generic Language.Haskell.TH.Syntax.Info instance Data.Data.Data Language.Haskell.TH.Syntax.Info instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Info instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Info instance GHC.Show.Show Language.Haskell.TH.Syntax.Info instance Language.Haskell.TH.Syntax.Quasi GHC.Types.IO instance GHC.Base.Monad Language.Haskell.TH.Syntax.Q instance Control.Monad.Fail.MonadFail Language.Haskell.TH.Syntax.Q instance GHC.Base.Functor Language.Haskell.TH.Syntax.Q instance GHC.Base.Applicative Language.Haskell.TH.Syntax.Q instance Language.Haskell.TH.Syntax.Quote Language.Haskell.TH.Syntax.Q instance Control.Monad.IO.Class.MonadIO Language.Haskell.TH.Syntax.Q instance Language.Haskell.TH.Syntax.Quasi Language.Haskell.TH.Syntax.Q instance Language.Haskell.TH.Syntax.Lift GHC.Integer.Type.Integer instance Language.Haskell.TH.Syntax.Lift GHC.Types.Int instance Language.Haskell.TH.Syntax.Lift GHC.Prim.Int# instance Language.Haskell.TH.Syntax.Lift GHC.Int.Int8 instance Language.Haskell.TH.Syntax.Lift GHC.Int.Int16 instance Language.Haskell.TH.Syntax.Lift GHC.Int.Int32 instance Language.Haskell.TH.Syntax.Lift GHC.Int.Int64 instance Language.Haskell.TH.Syntax.Lift GHC.Prim.Word# instance Language.Haskell.TH.Syntax.Lift GHC.Types.Word instance Language.Haskell.TH.Syntax.Lift GHC.Word.Word8 instance Language.Haskell.TH.Syntax.Lift GHC.Word.Word16 instance Language.Haskell.TH.Syntax.Lift GHC.Word.Word32 instance Language.Haskell.TH.Syntax.Lift GHC.Word.Word64 instance Language.Haskell.TH.Syntax.Lift GHC.Natural.Natural instance GHC.Real.Integral a => Language.Haskell.TH.Syntax.Lift (GHC.Real.Ratio a) instance Language.Haskell.TH.Syntax.Lift GHC.Types.Float instance Language.Haskell.TH.Syntax.Lift GHC.Prim.Float# instance Language.Haskell.TH.Syntax.Lift GHC.Types.Double instance Language.Haskell.TH.Syntax.Lift GHC.Prim.Double# instance Language.Haskell.TH.Syntax.Lift GHC.Types.Char instance Language.Haskell.TH.Syntax.Lift GHC.Prim.Char# instance Language.Haskell.TH.Syntax.Lift GHC.Types.Bool instance Language.Haskell.TH.Syntax.Lift GHC.Prim.Addr# instance Language.Haskell.TH.Syntax.Lift a => Language.Haskell.TH.Syntax.Lift (GHC.Maybe.Maybe a) instance (Language.Haskell.TH.Syntax.Lift a, Language.Haskell.TH.Syntax.Lift b) => Language.Haskell.TH.Syntax.Lift (Data.Either.Either a b) instance Language.Haskell.TH.Syntax.Lift a => Language.Haskell.TH.Syntax.Lift [a] instance Language.Haskell.TH.Syntax.Lift a => Language.Haskell.TH.Syntax.Lift (GHC.Base.NonEmpty a) instance Language.Haskell.TH.Syntax.Lift Data.Void.Void instance Language.Haskell.TH.Syntax.Lift () instance (Language.Haskell.TH.Syntax.Lift a, Language.Haskell.TH.Syntax.Lift b) => Language.Haskell.TH.Syntax.Lift (a, b) instance (Language.Haskell.TH.Syntax.Lift a, Language.Haskell.TH.Syntax.Lift b, Language.Haskell.TH.Syntax.Lift c) => Language.Haskell.TH.Syntax.Lift (a, b, c) instance (Language.Haskell.TH.Syntax.Lift a, Language.Haskell.TH.Syntax.Lift b, Language.Haskell.TH.Syntax.Lift c, Language.Haskell.TH.Syntax.Lift d) => Language.Haskell.TH.Syntax.Lift (a, b, c, d) instance (Language.Haskell.TH.Syntax.Lift a, Language.Haskell.TH.Syntax.Lift b, Language.Haskell.TH.Syntax.Lift c, Language.Haskell.TH.Syntax.Lift d, Language.Haskell.TH.Syntax.Lift e) => Language.Haskell.TH.Syntax.Lift (a, b, c, d, e) instance (Language.Haskell.TH.Syntax.Lift a, Language.Haskell.TH.Syntax.Lift b, Language.Haskell.TH.Syntax.Lift c, Language.Haskell.TH.Syntax.Lift d, Language.Haskell.TH.Syntax.Lift e, Language.Haskell.TH.Syntax.Lift f) => Language.Haskell.TH.Syntax.Lift (a, b, c, d, e, f) instance (Language.Haskell.TH.Syntax.Lift a, Language.Haskell.TH.Syntax.Lift b, Language.Haskell.TH.Syntax.Lift c, Language.Haskell.TH.Syntax.Lift d, Language.Haskell.TH.Syntax.Lift e, Language.Haskell.TH.Syntax.Lift f, Language.Haskell.TH.Syntax.Lift g) => Language.Haskell.TH.Syntax.Lift (a, b, c, d, e, f, g) instance Language.Haskell.TH.Syntax.Lift (# #) instance Language.Haskell.TH.Syntax.Lift a => Language.Haskell.TH.Syntax.Lift (# a #) instance (Language.Haskell.TH.Syntax.Lift a, Language.Haskell.TH.Syntax.Lift b) => Language.Haskell.TH.Syntax.Lift (# a, b #) instance (Language.Haskell.TH.Syntax.Lift a, Language.Haskell.TH.Syntax.Lift b, Language.Haskell.TH.Syntax.Lift c) => Language.Haskell.TH.Syntax.Lift (# a, b, c #) instance (Language.Haskell.TH.Syntax.Lift a, Language.Haskell.TH.Syntax.Lift b, Language.Haskell.TH.Syntax.Lift c, Language.Haskell.TH.Syntax.Lift d) => Language.Haskell.TH.Syntax.Lift (# a, b, c, d #) instance (Language.Haskell.TH.Syntax.Lift a, Language.Haskell.TH.Syntax.Lift b, Language.Haskell.TH.Syntax.Lift c, Language.Haskell.TH.Syntax.Lift d, Language.Haskell.TH.Syntax.Lift e) => Language.Haskell.TH.Syntax.Lift (# a, b, c, d, e #) instance (Language.Haskell.TH.Syntax.Lift a, Language.Haskell.TH.Syntax.Lift b, Language.Haskell.TH.Syntax.Lift c, Language.Haskell.TH.Syntax.Lift d, Language.Haskell.TH.Syntax.Lift e, Language.Haskell.TH.Syntax.Lift f) => Language.Haskell.TH.Syntax.Lift (# a, b, c, d, e, f #) instance (Language.Haskell.TH.Syntax.Lift a, Language.Haskell.TH.Syntax.Lift b, Language.Haskell.TH.Syntax.Lift c, Language.Haskell.TH.Syntax.Lift d, Language.Haskell.TH.Syntax.Lift e, Language.Haskell.TH.Syntax.Lift f, Language.Haskell.TH.Syntax.Lift g) => Language.Haskell.TH.Syntax.Lift (# a, b, c, d, e, f, g #) instance (Language.Haskell.TH.Syntax.Lift a, Language.Haskell.TH.Syntax.Lift b) => Language.Haskell.TH.Syntax.Lift (# a | b #) instance (Language.Haskell.TH.Syntax.Lift a, Language.Haskell.TH.Syntax.Lift b, Language.Haskell.TH.Syntax.Lift c) => Language.Haskell.TH.Syntax.Lift (# a | b | c #) instance (Language.Haskell.TH.Syntax.Lift a, Language.Haskell.TH.Syntax.Lift b, Language.Haskell.TH.Syntax.Lift c, Language.Haskell.TH.Syntax.Lift d) => Language.Haskell.TH.Syntax.Lift (# a | b | c | d #) instance (Language.Haskell.TH.Syntax.Lift a, Language.Haskell.TH.Syntax.Lift b, Language.Haskell.TH.Syntax.Lift c, Language.Haskell.TH.Syntax.Lift d, Language.Haskell.TH.Syntax.Lift e) => Language.Haskell.TH.Syntax.Lift (# a | b | c | d | e #) instance (Language.Haskell.TH.Syntax.Lift a, Language.Haskell.TH.Syntax.Lift b, Language.Haskell.TH.Syntax.Lift c, Language.Haskell.TH.Syntax.Lift d, Language.Haskell.TH.Syntax.Lift e, Language.Haskell.TH.Syntax.Lift f) => Language.Haskell.TH.Syntax.Lift (# a | b | c | d | e | f #) instance (Language.Haskell.TH.Syntax.Lift a, Language.Haskell.TH.Syntax.Lift b, Language.Haskell.TH.Syntax.Lift c, Language.Haskell.TH.Syntax.Lift d, Language.Haskell.TH.Syntax.Lift e, Language.Haskell.TH.Syntax.Lift f, Language.Haskell.TH.Syntax.Lift g) => Language.Haskell.TH.Syntax.Lift (# a | b | c | d | e | f | g #) instance GHC.Show.Show Language.Haskell.TH.Syntax.Bytes instance GHC.Classes.Eq Language.Haskell.TH.Syntax.Bytes instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Bytes instance Language.Haskell.TH.Syntax.Quote GHC.Types.IO instance GHC.Classes.Ord Language.Haskell.TH.Syntax.Name instance GHC.Show.Show Language.Haskell.TH.Syntax.Name -- | Template Haskell supports quasiquoting, which permits users to -- construct program fragments by directly writing concrete syntax. A -- quasiquoter is essentially a function with takes a string to a -- Template Haskell AST. This module defines the QuasiQuoter -- datatype, which specifies a quasiquoter q which can be -- invoked using the syntax [q| ... string to parse ... |] when -- the QuasiQuotes language extension is enabled, and some -- utility functions for manipulating quasiquoters. Nota bene: this -- package does not define any parsers, that is up to you. module Language.Haskell.TH.Quote -- | The QuasiQuoter type, a value q of this type can be -- used in the syntax [q| ... string to parse ...|]. In fact, -- for convenience, a QuasiQuoter actually defines multiple -- quasiquoters to be used in different splice contexts; if you are only -- interested in defining a quasiquoter to be used for expressions, you -- would define a QuasiQuoter with only quoteExp, and leave -- the other fields stubbed out with errors. data QuasiQuoter QuasiQuoter :: (String -> Q Exp) -> (String -> Q Pat) -> (String -> Q Type) -> (String -> Q [Dec]) -> QuasiQuoter -- | Quasi-quoter for expressions, invoked by quotes like lhs = -- $[q|...] [quoteExp] :: QuasiQuoter -> String -> Q Exp -- | Quasi-quoter for patterns, invoked by quotes like f $[q|...] = -- rhs [quotePat] :: QuasiQuoter -> String -> Q Pat -- | Quasi-quoter for types, invoked by quotes like f :: $[q|...] [quoteType] :: QuasiQuoter -> String -> Q Type -- | Quasi-quoter for declarations, invoked by top-level quotes [quoteDec] :: QuasiQuoter -> String -> Q [Dec] -- | quoteFile takes a QuasiQuoter and lifts it into one that -- read the data out of a file. For example, suppose asmq is an -- assembly-language quoter, so that you can write [asmq| ld r1, r2 |] as -- an expression. Then if you define asmq_f = quoteFile asmq, -- then the quote [asmq_f|foo.s|] will take input from file -- "foo.s" instead of the inline text quoteFile :: QuasiQuoter -> QuasiQuoter -- | dataToQa is an internal utility function for constructing -- generic conversion functions from types with Data instances to -- various quasi-quoting representations. See the source of -- dataToExpQ and dataToPatQ for two example usages: -- mkCon, mkLit and appQ are overloadable to -- account for different syntax for expressions and patterns; -- antiQ allows you to override type-specific cases, a common -- usage is just const Nothing, which results in no overloading. dataToQa :: forall m a k q. (Quote m, Data a) => (Name -> k) -> (Lit -> m q) -> (k -> [m q] -> m q) -> (forall b. Data b => b -> Maybe (m q)) -> a -> m q -- | dataToExpQ converts a value to a Exp representation of -- the same value, in the SYB style. It is generalized to take a function -- override type-specific cases; see liftData for a more commonly -- used variant. dataToExpQ :: (Quote m, Data a) => (forall b. Data b => b -> Maybe (m Exp)) -> a -> m Exp -- | dataToPatQ converts a value to a Pat representation of -- the same value, in the SYB style. It takes a function to handle -- type-specific cases, alternatively, pass const Nothing to get -- default behavior. dataToPatQ :: (Quote m, Data a) => (forall b. Data b => b -> Maybe (m Pat)) -> a -> m Pat -- | Monadic front-end to Text.PrettyPrint module Language.Haskell.TH.PprLib type Doc = PprM Doc data PprM a -- | An empty document empty :: Doc -- | A ';' character semi :: Doc -- | A ',' character comma :: Doc -- | A : character colon :: Doc -- | A "::" string dcolon :: Doc -- | A space character space :: Doc -- | A '=' character equals :: Doc -- | A "->" string arrow :: Doc -- | A '(' character lparen :: Doc -- | A ')' character rparen :: Doc -- | A '[' character lbrack :: Doc -- | A ']' character rbrack :: Doc -- | A '{' character lbrace :: Doc -- | A '}' character rbrace :: Doc text :: String -> Doc char :: Char -> Doc ptext :: String -> Doc int :: Int -> Doc integer :: Integer -> Doc float :: Float -> Doc double :: Double -> Doc rational :: Rational -> Doc -- | Wrap document in (...) parens :: Doc -> Doc -- | Wrap document in [...] brackets :: Doc -> Doc -- | Wrap document in {...} braces :: Doc -> Doc -- | Wrap document in '...' quotes :: Doc -> Doc -- | Wrap document in "..." doubleQuotes :: Doc -> Doc -- | Beside (<>) :: Doc -> Doc -> Doc infixl 6 <> -- | Beside, separated by space (<+>) :: Doc -> Doc -> Doc infixl 6 <+> -- | List version of <> hcat :: [Doc] -> Doc -- | List version of <+> hsep :: [Doc] -> Doc -- | Above; if there is no overlap it "dovetails" the two ($$) :: Doc -> Doc -> Doc infixl 5 $$ -- | Above, without dovetailing. ($+$) :: Doc -> Doc -> Doc infixl 5 $+$ -- | List version of $$ vcat :: [Doc] -> Doc -- | Either hsep or vcat sep :: [Doc] -> Doc -- | Either hcat or vcat cat :: [Doc] -> Doc -- | "Paragraph fill" version of sep fsep :: [Doc] -> Doc -- | "Paragraph fill" version of cat fcat :: [Doc] -> Doc -- | Nested nest :: Int -> Doc -> Doc -- |
--   hang d1 n d2 = sep [d1, nest n d2]
--   
hang :: Doc -> Int -> Doc -> Doc punctuate :: Doc -> [Doc] -> [Doc] -- | Returns True if the document is empty isEmpty :: Doc -> PprM Bool to_HPJ_Doc :: Doc -> Doc pprName :: Name -> Doc pprName' :: NameIs -> Name -> Doc instance GHC.Show.Show Language.Haskell.TH.PprLib.Doc instance GHC.Base.Functor Language.Haskell.TH.PprLib.PprM instance GHC.Base.Applicative Language.Haskell.TH.PprLib.PprM instance GHC.Base.Monad Language.Haskell.TH.PprLib.PprM -- | contains a prettyprinter for the Template Haskell datatypes module Language.Haskell.TH.Ppr nestDepth :: Int type Precedence = Int appPrec :: Precedence opPrec :: Precedence unopPrec :: Precedence sigPrec :: Precedence noPrec :: Precedence parensIf :: Bool -> Doc -> Doc pprint :: Ppr a => a -> String class Ppr a ppr :: Ppr a => a -> Doc ppr_list :: Ppr a => [a] -> Doc ppr_sig :: Name -> Type -> Doc pprFixity :: Name -> Fixity -> Doc -- | Pretty prints a pattern synonym type signature pprPatSynSig :: Name -> PatSynType -> Doc -- | Pretty prints a pattern synonym's type; follows the usual conventions -- to print a pattern synonym type compactly, yet unambiguously. See the -- note on PatSynType and the section on pattern synonyms in the -- GHC user's guide for more information. pprPatSynType :: PatSynType -> Doc pprPrefixOcc :: Name -> Doc isSymOcc :: Name -> Bool pprInfixExp :: Exp -> Doc pprExp :: Precedence -> Exp -> Doc pprFields :: [(Name, Exp)] -> Doc pprMaybeExp :: Precedence -> Maybe Exp -> Doc pprMatchPat :: Pat -> Doc pprGuarded :: Doc -> (Guard, Exp) -> Doc pprBody :: Bool -> Body -> Doc pprLit :: Precedence -> Lit -> Doc bytesToString :: [Word8] -> String pprString :: String -> Doc pprPat :: Precedence -> Pat -> Doc ppr_dec :: Bool -> Dec -> Doc ppr_deriv_strategy :: DerivStrategy -> Doc ppr_overlap :: Overlap -> Doc ppr_data :: Doc -> Cxt -> Maybe Name -> Doc -> Maybe Kind -> [Con] -> [DerivClause] -> Doc ppr_newtype :: Doc -> Cxt -> Maybe Name -> Doc -> Maybe Kind -> Con -> [DerivClause] -> Doc ppr_deriv_clause :: DerivClause -> Doc ppr_tySyn :: Doc -> Maybe Name -> Doc -> Type -> Doc ppr_tf_head :: TypeFamilyHead -> Doc ppr_bndrs :: PprFlag flag => Maybe [TyVarBndr flag] -> Doc commaSepApplied :: [Name] -> Doc pprForall :: [TyVarBndr Specificity] -> Cxt -> Doc pprForallVis :: [TyVarBndr ()] -> Cxt -> Doc pprForall' :: PprFlag flag => ForallVisFlag -> [TyVarBndr flag] -> Cxt -> Doc pprRecFields :: [(Name, Strict, Type)] -> Type -> Doc pprGadtRHS :: [(Strict, Type)] -> Type -> Doc pprVarBangType :: VarBangType -> Doc pprBangType :: BangType -> Doc -- | Deprecated: As of template-haskell-2.11.0.0, -- VarStrictType has been replaced by VarBangType. Please -- use pprVarBangType instead. pprVarStrictType :: (Name, Strict, Type) -> Doc -- | Deprecated: As of template-haskell-2.11.0.0, -- StrictType has been replaced by BangType. Please use -- pprBangType instead. pprStrictType :: (Strict, Type) -> Doc pprParendType :: Type -> Doc pprUInfixT :: Type -> Doc pprParendTypeArg :: TypeArg -> Doc isStarT :: Type -> Bool pprTyApp :: (Type, [TypeArg]) -> Doc fromTANormal :: TypeArg -> Maybe Type pprFunArgType :: Type -> Doc data ForallVisFlag ForallVis :: ForallVisFlag ForallInvis :: ForallVisFlag data TypeArg TANormal :: Type -> TypeArg TyArg :: Kind -> TypeArg split :: Type -> (Type, [TypeArg]) pprTyLit :: TyLit -> Doc class PprFlag flag pprTyVarBndr :: PprFlag flag => TyVarBndr flag -> Doc pprCxt :: Cxt -> Doc ppr_cxt_preds :: Cxt -> Doc where_clause :: [Dec] -> Doc showtextl :: Show a => a -> Doc hashParens :: Doc -> Doc quoteParens :: Doc -> Doc commaSep :: Ppr a => [a] -> Doc commaSepWith :: (a -> Doc) -> [a] -> Doc semiSep :: Ppr a => [a] -> Doc unboxedSumBars :: Doc -> SumAlt -> SumArity -> Doc bar :: Doc instance GHC.Show.Show Language.Haskell.TH.Ppr.ForallVisFlag instance Language.Haskell.TH.Ppr.PprFlag () instance Language.Haskell.TH.Ppr.PprFlag Language.Haskell.TH.Syntax.Specificity instance Language.Haskell.TH.Ppr.PprFlag flag => Language.Haskell.TH.Ppr.Ppr (Language.Haskell.TH.Syntax.TyVarBndr flag) instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Ppr.TypeArg instance Language.Haskell.TH.Ppr.Ppr a => Language.Haskell.TH.Ppr.Ppr [a] instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.Name instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.Info instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.Module instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.ModuleInfo instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.Exp instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.Stmt instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.Match instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.Lit instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.Pat instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.Dec instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.FunDep instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.FamilyResultSig instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.InjectivityAnn instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.Foreign instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.Pragma instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.Inline instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.RuleMatch instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.Phases instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.RuleBndr instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.Clause instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.Con instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.PatSynDir instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.PatSynArgs instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.Bang instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.SourceUnpackedness instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.SourceStrictness instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.DecidedStrictness instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.Type instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.TyLit instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.Role instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.Range instance Language.Haskell.TH.Ppr.Ppr Language.Haskell.TH.Syntax.Loc -- | Language.Haskell.TH.Lib.Internal exposes some additional functionality -- that is used internally in GHC's integration with Template Haskell. -- This is not a part of the public API, and as such, there are no API -- guarantees for this module from version to version. module Language.Haskell.TH.Lib.Internal type InfoQ = Q Info type PatQ = Q Pat type FieldPatQ = Q FieldPat type ExpQ = Q Exp type TExpQ a = Q (TExp a) type DecQ = Q Dec type DecsQ = Q [Dec] type Decs = [Dec] type ConQ = Q Con type TypeQ = Q Type type KindQ = Q Kind type TyLitQ = Q TyLit type CxtQ = Q Cxt type PredQ = Q Pred type DerivClauseQ = Q DerivClause type MatchQ = Q Match type ClauseQ = Q Clause type BodyQ = Q Body type GuardQ = Q Guard type StmtQ = Q Stmt type RangeQ = Q Range type SourceStrictnessQ = Q SourceStrictness type SourceUnpackednessQ = Q SourceUnpackedness type BangQ = Q Bang type BangTypeQ = Q BangType type VarBangTypeQ = Q VarBangType type StrictTypeQ = Q StrictType type VarStrictTypeQ = Q VarStrictType type FieldExpQ = Q FieldExp type RuleBndrQ = Q RuleBndr type TySynEqnQ = Q TySynEqn type PatSynDirQ = Q PatSynDir type PatSynArgsQ = Q PatSynArgs type FamilyResultSigQ = Q FamilyResultSig type DerivStrategyQ = Q DerivStrategy type Role = Role type InjectivityAnn = InjectivityAnn type TyVarBndrUnit = TyVarBndr () type TyVarBndrSpec = TyVarBndr Specificity intPrimL :: Integer -> Lit wordPrimL :: Integer -> Lit floatPrimL :: Rational -> Lit doublePrimL :: Rational -> Lit integerL :: Integer -> Lit charL :: Char -> Lit charPrimL :: Char -> Lit stringL :: String -> Lit stringPrimL :: [Word8] -> Lit bytesPrimL :: Bytes -> Lit rationalL :: Rational -> Lit litP :: Quote m => Lit -> m Pat varP :: Quote m => Name -> m Pat tupP :: Quote m => [m Pat] -> m Pat unboxedTupP :: Quote m => [m Pat] -> m Pat unboxedSumP :: Quote m => m Pat -> SumAlt -> SumArity -> m Pat conP :: Quote m => Name -> [m Pat] -> m Pat infixP :: Quote m => m Pat -> Name -> m Pat -> m Pat uInfixP :: Quote m => m Pat -> Name -> m Pat -> m Pat parensP :: Quote m => m Pat -> m Pat tildeP :: Quote m => m Pat -> m Pat bangP :: Quote m => m Pat -> m Pat asP :: Quote m => Name -> m Pat -> m Pat wildP :: Quote m => m Pat recP :: Quote m => Name -> [m FieldPat] -> m Pat listP :: Quote m => [m Pat] -> m Pat sigP :: Quote m => m Pat -> m Type -> m Pat viewP :: Quote m => m Exp -> m Pat -> m Pat fieldPat :: Quote m => Name -> m Pat -> m FieldPat bindS :: Quote m => m Pat -> m Exp -> m Stmt letS :: Quote m => [m Dec] -> m Stmt noBindS :: Quote m => m Exp -> m Stmt parS :: Quote m => [[m Stmt]] -> m Stmt recS :: Quote m => [m Stmt] -> m Stmt fromR :: Quote m => m Exp -> m Range fromThenR :: Quote m => m Exp -> m Exp -> m Range fromToR :: Quote m => m Exp -> m Exp -> m Range fromThenToR :: Quote m => m Exp -> m Exp -> m Exp -> m Range normalB :: Quote m => m Exp -> m Body guardedB :: Quote m => [m (Guard, Exp)] -> m Body normalG :: Quote m => m Exp -> m Guard normalGE :: Quote m => m Exp -> m Exp -> m (Guard, Exp) patG :: Quote m => [m Stmt] -> m Guard patGE :: Quote m => [m Stmt] -> m Exp -> m (Guard, Exp) -- | Use with caseE match :: Quote m => m Pat -> m Body -> [m Dec] -> m Match -- | Use with funD clause :: Quote m => [m Pat] -> m Body -> [m Dec] -> m Clause -- | Dynamically binding a variable (unhygenic) dyn :: Quote m => String -> m Exp varE :: Quote m => Name -> m Exp conE :: Quote m => Name -> m Exp litE :: Quote m => Lit -> m Exp appE :: Quote m => m Exp -> m Exp -> m Exp appTypeE :: Quote m => m Exp -> m Type -> m Exp parensE :: Quote m => m Exp -> m Exp uInfixE :: Quote m => m Exp -> m Exp -> m Exp -> m Exp infixE :: Quote m => Maybe (m Exp) -> m Exp -> Maybe (m Exp) -> m Exp infixApp :: Quote m => m Exp -> m Exp -> m Exp -> m Exp sectionL :: Quote m => m Exp -> m Exp -> m Exp sectionR :: Quote m => m Exp -> m Exp -> m Exp lamE :: Quote m => [m Pat] -> m Exp -> m Exp -- | Single-arg lambda lam1E :: Quote m => m Pat -> m Exp -> m Exp lamCaseE :: Quote m => [m Match] -> m Exp tupE :: Quote m => [Maybe (m Exp)] -> m Exp unboxedTupE :: Quote m => [Maybe (m Exp)] -> m Exp unboxedSumE :: Quote m => m Exp -> SumAlt -> SumArity -> m Exp condE :: Quote m => m Exp -> m Exp -> m Exp -> m Exp multiIfE :: Quote m => [m (Guard, Exp)] -> m Exp letE :: Quote m => [m Dec] -> m Exp -> m Exp caseE :: Quote m => m Exp -> [m Match] -> m Exp doE :: Quote m => [m Stmt] -> m Exp mdoE :: Quote m => [m Stmt] -> m Exp compE :: Quote m => [m Stmt] -> m Exp arithSeqE :: Quote m => m Range -> m Exp listE :: Quote m => [m Exp] -> m Exp sigE :: Quote m => m Exp -> m Type -> m Exp recConE :: Quote m => Name -> [m (Name, Exp)] -> m Exp recUpdE :: Quote m => m Exp -> [m (Name, Exp)] -> m Exp stringE :: Quote m => String -> m Exp fieldExp :: Quote m => Name -> m Exp -> m (Name, Exp) -- |
--   staticE x = [| static x |]
--   
staticE :: Quote m => m Exp -> m Exp unboundVarE :: Quote m => Name -> m Exp labelE :: Quote m => String -> m Exp implicitParamVarE :: Quote m => String -> m Exp fromE :: Quote m => m Exp -> m Exp fromThenE :: Quote m => m Exp -> m Exp -> m Exp fromToE :: Quote m => m Exp -> m Exp -> m Exp fromThenToE :: Quote m => m Exp -> m Exp -> m Exp -> m Exp valD :: Quote m => m Pat -> m Body -> [m Dec] -> m Dec funD :: Quote m => Name -> [m Clause] -> m Dec tySynD :: Quote m => Name -> [m (TyVarBndr ())] -> m Type -> m Dec dataD :: Quote m => m Cxt -> Name -> [m (TyVarBndr ())] -> Maybe (m Kind) -> [m Con] -> [m DerivClause] -> m Dec newtypeD :: Quote m => m Cxt -> Name -> [m (TyVarBndr ())] -> Maybe (m Kind) -> m Con -> [m DerivClause] -> m Dec classD :: Quote m => m Cxt -> Name -> [m (TyVarBndr ())] -> [FunDep] -> [m Dec] -> m Dec instanceD :: Quote m => m Cxt -> m Type -> [m Dec] -> m Dec instanceWithOverlapD :: Quote m => Maybe Overlap -> m Cxt -> m Type -> [m Dec] -> m Dec sigD :: Quote m => Name -> m Type -> m Dec kiSigD :: Quote m => Name -> m Kind -> m Dec forImpD :: Quote m => Callconv -> Safety -> String -> Name -> m Type -> m Dec infixLD :: Quote m => Int -> Name -> m Dec infixRD :: Quote m => Int -> Name -> m Dec infixND :: Quote m => Int -> Name -> m Dec pragInlD :: Quote m => Name -> Inline -> RuleMatch -> Phases -> m Dec pragSpecD :: Quote m => Name -> m Type -> Phases -> m Dec pragSpecInlD :: Quote m => Name -> m Type -> Inline -> Phases -> m Dec pragSpecInstD :: Quote m => m Type -> m Dec pragRuleD :: Quote m => String -> Maybe [m (TyVarBndr ())] -> [m RuleBndr] -> m Exp -> m Exp -> Phases -> m Dec pragAnnD :: Quote m => AnnTarget -> m Exp -> m Dec pragLineD :: Quote m => Int -> String -> m Dec pragCompleteD :: Quote m => [Name] -> Maybe Name -> m Dec dataInstD :: Quote m => m Cxt -> Maybe [m (TyVarBndr ())] -> m Type -> Maybe (m Kind) -> [m Con] -> [m DerivClause] -> m Dec newtypeInstD :: Quote m => m Cxt -> Maybe [m (TyVarBndr ())] -> m Type -> Maybe (m Kind) -> m Con -> [m DerivClause] -> m Dec tySynInstD :: Quote m => m TySynEqn -> m Dec dataFamilyD :: Quote m => Name -> [m (TyVarBndr ())] -> Maybe (m Kind) -> m Dec openTypeFamilyD :: Quote m => Name -> [m (TyVarBndr ())] -> m FamilyResultSig -> Maybe InjectivityAnn -> m Dec closedTypeFamilyD :: Quote m => Name -> [m (TyVarBndr ())] -> m FamilyResultSig -> Maybe InjectivityAnn -> [m TySynEqn] -> m Dec roleAnnotD :: Quote m => Name -> [Role] -> m Dec standaloneDerivD :: Quote m => m Cxt -> m Type -> m Dec standaloneDerivWithStrategyD :: Quote m => Maybe (m DerivStrategy) -> m Cxt -> m Type -> m Dec defaultSigD :: Quote m => Name -> m Type -> m Dec -- | Pattern synonym declaration patSynD :: Quote m => Name -> m PatSynArgs -> m PatSynDir -> m Pat -> m Dec -- | Pattern synonym type signature patSynSigD :: Quote m => Name -> m Type -> m Dec -- | Implicit parameter binding declaration. Can only be used in let and -- where clauses which consist entirely of implicit bindings. implicitParamBindD :: Quote m => String -> m Exp -> m Dec tySynEqn :: Quote m => Maybe [m (TyVarBndr ())] -> m Type -> m Type -> m TySynEqn cxt :: Quote m => [m Pred] -> m Cxt derivClause :: Quote m => Maybe (m DerivStrategy) -> [m Pred] -> m DerivClause stockStrategy :: Quote m => m DerivStrategy anyclassStrategy :: Quote m => m DerivStrategy newtypeStrategy :: Quote m => m DerivStrategy viaStrategy :: Quote m => m Type -> m DerivStrategy normalC :: Quote m => Name -> [m BangType] -> m Con recC :: Quote m => Name -> [m VarBangType] -> m Con infixC :: Quote m => m (Bang, Type) -> Name -> m (Bang, Type) -> m Con forallC :: Quote m => [m (TyVarBndr Specificity)] -> m Cxt -> m Con -> m Con gadtC :: Quote m => [Name] -> [m StrictType] -> m Type -> m Con recGadtC :: Quote m => [Name] -> [m VarStrictType] -> m Type -> m Con forallT :: Quote m => [m (TyVarBndr Specificity)] -> m Cxt -> m Type -> m Type forallVisT :: Quote m => [m (TyVarBndr ())] -> m Type -> m Type varT :: Quote m => Name -> m Type conT :: Quote m => Name -> m Type infixT :: Quote m => m Type -> Name -> m Type -> m Type uInfixT :: Quote m => m Type -> Name -> m Type -> m Type parensT :: Quote m => m Type -> m Type appT :: Quote m => m Type -> m Type -> m Type appKindT :: Quote m => m Type -> m Kind -> m Type arrowT :: Quote m => m Type listT :: Quote m => m Type litT :: Quote m => m TyLit -> m Type tupleT :: Quote m => Int -> m Type unboxedTupleT :: Quote m => Int -> m Type unboxedSumT :: Quote m => SumArity -> m Type sigT :: Quote m => m Type -> m Kind -> m Type equalityT :: Quote m => m Type wildCardT :: Quote m => m Type implicitParamT :: Quote m => String -> m Type -> m Type -- | Deprecated: As of template-haskell-2.10, constraint predicates -- (Pred) are just types (Type), in keeping with ConstraintKinds. Please -- use conT and appT. classP :: Quote m => Name -> [m Type] -> m Pred -- | Deprecated: As of template-haskell-2.10, constraint predicates -- (Pred) are just types (Type), in keeping with ConstraintKinds. Please -- see equalityT. equalP :: Quote m => m Type -> m Type -> m Pred promotedT :: Quote m => Name -> m Type promotedTupleT :: Quote m => Int -> m Type promotedNilT :: Quote m => m Type promotedConsT :: Quote m => m Type noSourceUnpackedness :: Quote m => m SourceUnpackedness sourceNoUnpack :: Quote m => m SourceUnpackedness sourceUnpack :: Quote m => m SourceUnpackedness noSourceStrictness :: Quote m => m SourceStrictness sourceLazy :: Quote m => m SourceStrictness sourceStrict :: Quote m => m SourceStrictness -- | Deprecated: Use bang. See -- https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. Example -- usage: 'bang noSourceUnpackedness sourceStrict' isStrict :: Quote m => m Strict -- | Deprecated: Use bang. See -- https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. Example -- usage: 'bang noSourceUnpackedness noSourceStrictness' notStrict :: Quote m => m Strict -- | Deprecated: Use bang. See -- https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. Example -- usage: 'bang sourceUnpack sourceStrict' unpacked :: Quote m => m Strict bang :: Quote m => m SourceUnpackedness -> m SourceStrictness -> m Bang bangType :: Quote m => m Bang -> m Type -> m BangType varBangType :: Quote m => Name -> m BangType -> m VarBangType -- | Deprecated: As of template-haskell-2.11.0.0, -- StrictType has been replaced by BangType. Please use -- bangType instead. strictType :: Quote m => m Strict -> m Type -> m StrictType -- | Deprecated: As of template-haskell-2.11.0.0, -- VarStrictType has been replaced by VarBangType. Please -- use varBangType instead. varStrictType :: Quote m => Name -> m StrictType -> m VarStrictType numTyLit :: Quote m => Integer -> m TyLit strTyLit :: Quote m => String -> m TyLit plainTV :: Quote m => Name -> m (TyVarBndr ()) plainInvisTV :: Quote m => Name -> Specificity -> m (TyVarBndr Specificity) kindedTV :: Quote m => Name -> m Kind -> m (TyVarBndr ()) kindedInvisTV :: Quote m => Name -> Specificity -> m Kind -> m (TyVarBndr Specificity) specifiedSpec :: Specificity inferredSpec :: Specificity varK :: Name -> Kind conK :: Name -> Kind tupleK :: Int -> Kind arrowK :: Kind listK :: Kind appK :: Kind -> Kind -> Kind starK :: Quote m => m Kind constraintK :: Quote m => m Kind noSig :: Quote m => m FamilyResultSig kindSig :: Quote m => m Kind -> m FamilyResultSig tyVarSig :: Quote m => m (TyVarBndr ()) -> m FamilyResultSig injectivityAnn :: Name -> [Name] -> InjectivityAnn nominalR :: Role representationalR :: Role phantomR :: Role inferR :: Role cCall :: Callconv stdCall :: Callconv cApi :: Callconv prim :: Callconv javaScript :: Callconv unsafe :: Safety safe :: Safety interruptible :: Safety funDep :: [Name] -> [Name] -> FunDep ruleVar :: Quote m => Name -> m RuleBndr typedRuleVar :: Quote m => Name -> m Type -> m RuleBndr valueAnnotation :: Name -> AnnTarget typeAnnotation :: Name -> AnnTarget moduleAnnotation :: AnnTarget unidir :: Quote m => m PatSynDir implBidir :: Quote m => m PatSynDir explBidir :: Quote m => [m Clause] -> m PatSynDir prefixPatSyn :: Quote m => [Name] -> m PatSynArgs recordPatSyn :: Quote m => [Name] -> m PatSynArgs infixPatSyn :: Quote m => Name -> Name -> m PatSynArgs appsE :: Quote m => [m Exp] -> m Exp -- | pure the Module at the place of splicing. Can be used as an input for -- reifyModule. thisModule :: Q Module -- | Language.Haskell.TH.Lib contains lots of useful helper functions for -- generating and manipulating Template Haskell terms module Language.Haskell.TH.Lib type InfoQ = Q Info type ExpQ = Q Exp type TExpQ a = Q (TExp a) type DecQ = Q Dec type DecsQ = Q [Dec] type ConQ = Q Con type TypeQ = Q Type type KindQ = Q Kind type TyLitQ = Q TyLit type CxtQ = Q Cxt type PredQ = Q Pred type DerivClauseQ = Q DerivClause type MatchQ = Q Match type ClauseQ = Q Clause type BodyQ = Q Body type GuardQ = Q Guard type StmtQ = Q Stmt type RangeQ = Q Range type SourceStrictnessQ = Q SourceStrictness type SourceUnpackednessQ = Q SourceUnpackedness type BangQ = Q Bang type BangTypeQ = Q BangType type VarBangTypeQ = Q VarBangType type StrictTypeQ = Q StrictType type VarStrictTypeQ = Q VarStrictType type FieldExpQ = Q FieldExp type PatQ = Q Pat type FieldPatQ = Q FieldPat type RuleBndrQ = Q RuleBndr type TySynEqnQ = Q TySynEqn type PatSynDirQ = Q PatSynDir type PatSynArgsQ = Q PatSynArgs type FamilyResultSigQ = Q FamilyResultSig type DerivStrategyQ = Q DerivStrategy type TyVarBndrUnit = TyVarBndr () type TyVarBndrSpec = TyVarBndr Specificity intPrimL :: Integer -> Lit wordPrimL :: Integer -> Lit floatPrimL :: Rational -> Lit doublePrimL :: Rational -> Lit integerL :: Integer -> Lit rationalL :: Rational -> Lit charL :: Char -> Lit stringL :: String -> Lit stringPrimL :: [Word8] -> Lit charPrimL :: Char -> Lit bytesPrimL :: Bytes -> Lit -- | Create a Bytes datatype representing raw bytes to be embedded into the -- program/library binary. mkBytes :: ForeignPtr Word8 -> Word -> Word -> Bytes litP :: Quote m => Lit -> m Pat varP :: Quote m => Name -> m Pat tupP :: Quote m => [m Pat] -> m Pat unboxedTupP :: Quote m => [m Pat] -> m Pat unboxedSumP :: Quote m => m Pat -> SumAlt -> SumArity -> m Pat conP :: Quote m => Name -> [m Pat] -> m Pat uInfixP :: Quote m => m Pat -> Name -> m Pat -> m Pat parensP :: Quote m => m Pat -> m Pat infixP :: Quote m => m Pat -> Name -> m Pat -> m Pat tildeP :: Quote m => m Pat -> m Pat bangP :: Quote m => m Pat -> m Pat asP :: Quote m => Name -> m Pat -> m Pat wildP :: Quote m => m Pat recP :: Quote m => Name -> [m FieldPat] -> m Pat listP :: Quote m => [m Pat] -> m Pat sigP :: Quote m => m Pat -> m Type -> m Pat viewP :: Quote m => m Exp -> m Pat -> m Pat fieldPat :: Quote m => Name -> m Pat -> m FieldPat normalB :: Quote m => m Exp -> m Body guardedB :: Quote m => [m (Guard, Exp)] -> m Body normalG :: Quote m => m Exp -> m Guard normalGE :: Quote m => m Exp -> m Exp -> m (Guard, Exp) patG :: Quote m => [m Stmt] -> m Guard patGE :: Quote m => [m Stmt] -> m Exp -> m (Guard, Exp) -- | Use with caseE match :: Quote m => m Pat -> m Body -> [m Dec] -> m Match -- | Use with funD clause :: Quote m => [m Pat] -> m Body -> [m Dec] -> m Clause -- | Dynamically binding a variable (unhygenic) dyn :: Quote m => String -> m Exp varE :: Quote m => Name -> m Exp unboundVarE :: Quote m => Name -> m Exp labelE :: Quote m => String -> m Exp implicitParamVarE :: Quote m => String -> m Exp conE :: Quote m => Name -> m Exp litE :: Quote m => Lit -> m Exp -- |
--   staticE x = [| static x |]
--   
staticE :: Quote m => m Exp -> m Exp appE :: Quote m => m Exp -> m Exp -> m Exp appTypeE :: Quote m => m Exp -> m Type -> m Exp uInfixE :: Quote m => m Exp -> m Exp -> m Exp -> m Exp parensE :: Quote m => m Exp -> m Exp infixE :: Quote m => Maybe (m Exp) -> m Exp -> Maybe (m Exp) -> m Exp infixApp :: Quote m => m Exp -> m Exp -> m Exp -> m Exp sectionL :: Quote m => m Exp -> m Exp -> m Exp sectionR :: Quote m => m Exp -> m Exp -> m Exp lamE :: Quote m => [m Pat] -> m Exp -> m Exp -- | Single-arg lambda lam1E :: Quote m => m Pat -> m Exp -> m Exp lamCaseE :: Quote m => [m Match] -> m Exp tupE :: Quote m => [m Exp] -> m Exp unboxedTupE :: Quote m => [m Exp] -> m Exp unboxedSumE :: Quote m => m Exp -> SumAlt -> SumArity -> m Exp condE :: Quote m => m Exp -> m Exp -> m Exp -> m Exp multiIfE :: Quote m => [m (Guard, Exp)] -> m Exp letE :: Quote m => [m Dec] -> m Exp -> m Exp caseE :: Quote m => m Exp -> [m Match] -> m Exp appsE :: Quote m => [m Exp] -> m Exp listE :: Quote m => [m Exp] -> m Exp sigE :: Quote m => m Exp -> m Type -> m Exp recConE :: Quote m => Name -> [m (Name, Exp)] -> m Exp recUpdE :: Quote m => m Exp -> [m (Name, Exp)] -> m Exp stringE :: Quote m => String -> m Exp fieldExp :: Quote m => Name -> m Exp -> m (Name, Exp) fromE :: Quote m => m Exp -> m Exp fromThenE :: Quote m => m Exp -> m Exp -> m Exp fromToE :: Quote m => m Exp -> m Exp -> m Exp fromThenToE :: Quote m => m Exp -> m Exp -> m Exp -> m Exp arithSeqE :: Quote m => m Range -> m Exp fromR :: Quote m => m Exp -> m Range fromThenR :: Quote m => m Exp -> m Exp -> m Range fromToR :: Quote m => m Exp -> m Exp -> m Range fromThenToR :: Quote m => m Exp -> m Exp -> m Exp -> m Range doE :: Quote m => [m Stmt] -> m Exp mdoE :: Quote m => [m Stmt] -> m Exp compE :: Quote m => [m Stmt] -> m Exp bindS :: Quote m => m Pat -> m Exp -> m Stmt letS :: Quote m => [m Dec] -> m Stmt noBindS :: Quote m => m Exp -> m Stmt parS :: Quote m => [[m Stmt]] -> m Stmt recS :: Quote m => [m Stmt] -> m Stmt forallT :: Quote m => [TyVarBndr Specificity] -> m Cxt -> m Type -> m Type forallVisT :: Quote m => [m (TyVarBndr ())] -> m Type -> m Type varT :: Quote m => Name -> m Type conT :: Quote m => Name -> m Type appT :: Quote m => m Type -> m Type -> m Type appKindT :: Quote m => m Type -> m Kind -> m Type arrowT :: Quote m => m Type infixT :: Quote m => m Type -> Name -> m Type -> m Type uInfixT :: Quote m => m Type -> Name -> m Type -> m Type parensT :: Quote m => m Type -> m Type equalityT :: Quote m => m Type listT :: Quote m => m Type tupleT :: Quote m => Int -> m Type unboxedTupleT :: Quote m => Int -> m Type unboxedSumT :: Quote m => SumArity -> m Type sigT :: Quote m => m Type -> Kind -> m Type litT :: Quote m => m TyLit -> m Type wildCardT :: Quote m => m Type promotedT :: Quote m => Name -> m Type promotedTupleT :: Quote m => Int -> m Type promotedNilT :: Quote m => m Type promotedConsT :: Quote m => m Type implicitParamT :: Quote m => String -> m Type -> m Type numTyLit :: Quote m => Integer -> m TyLit strTyLit :: Quote m => String -> m TyLit noSourceUnpackedness :: Quote m => m SourceUnpackedness sourceNoUnpack :: Quote m => m SourceUnpackedness sourceUnpack :: Quote m => m SourceUnpackedness noSourceStrictness :: Quote m => m SourceStrictness sourceLazy :: Quote m => m SourceStrictness sourceStrict :: Quote m => m SourceStrictness -- | Deprecated: Use bang. See -- https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. Example -- usage: 'bang noSourceUnpackedness sourceStrict' isStrict :: Quote m => m Strict -- | Deprecated: Use bang. See -- https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. Example -- usage: 'bang noSourceUnpackedness noSourceStrictness' notStrict :: Quote m => m Strict -- | Deprecated: Use bang. See -- https://gitlab.haskell.org/ghc/ghc/wikis/migration/8.0. Example -- usage: 'bang sourceUnpack sourceStrict' unpacked :: Quote m => m Strict bang :: Quote m => m SourceUnpackedness -> m SourceStrictness -> m Bang bangType :: Quote m => m Bang -> m Type -> m BangType varBangType :: Quote m => Name -> m BangType -> m VarBangType -- | Deprecated: As of template-haskell-2.11.0.0, -- StrictType has been replaced by BangType. Please use -- bangType instead. strictType :: Quote m => m Strict -> m Type -> m StrictType -- | Deprecated: As of template-haskell-2.11.0.0, -- VarStrictType has been replaced by VarBangType. Please -- use varBangType instead. varStrictType :: Quote m => Name -> m StrictType -> m VarStrictType cxt :: Quote m => [m Pred] -> m Cxt -- | Deprecated: As of template-haskell-2.10, constraint predicates -- (Pred) are just types (Type), in keeping with ConstraintKinds. Please -- use conT and appT. classP :: Quote m => Name -> [m Type] -> m Pred -- | Deprecated: As of template-haskell-2.10, constraint predicates -- (Pred) are just types (Type), in keeping with ConstraintKinds. Please -- see equalityT. equalP :: Quote m => m Type -> m Type -> m Pred normalC :: Quote m => Name -> [m BangType] -> m Con recC :: Quote m => Name -> [m VarBangType] -> m Con infixC :: Quote m => m (Bang, Type) -> Name -> m (Bang, Type) -> m Con forallC :: Quote m => [TyVarBndr Specificity] -> m Cxt -> m Con -> m Con gadtC :: Quote m => [Name] -> [m StrictType] -> m Type -> m Con recGadtC :: Quote m => [Name] -> [m VarStrictType] -> m Type -> m Con varK :: Name -> Kind conK :: Name -> Kind tupleK :: Int -> Kind arrowK :: Kind listK :: Kind appK :: Kind -> Kind -> Kind starK :: Kind constraintK :: Kind plainTV :: Name -> TyVarBndr () kindedTV :: Name -> Kind -> TyVarBndr () plainInvisTV :: Quote m => Name -> Specificity -> m (TyVarBndr Specificity) kindedInvisTV :: Quote m => Name -> Specificity -> m Kind -> m (TyVarBndr Specificity) specifiedSpec :: Specificity inferredSpec :: Specificity nominalR :: Role representationalR :: Role phantomR :: Role inferR :: Role valD :: Quote m => m Pat -> m Body -> [m Dec] -> m Dec funD :: Quote m => Name -> [m Clause] -> m Dec tySynD :: Quote m => Name -> [TyVarBndr ()] -> m Type -> m Dec dataD :: Quote m => m Cxt -> Name -> [TyVarBndr ()] -> Maybe Kind -> [m Con] -> [m DerivClause] -> m Dec newtypeD :: Quote m => m Cxt -> Name -> [TyVarBndr ()] -> Maybe Kind -> m Con -> [m DerivClause] -> m Dec derivClause :: Quote m => Maybe DerivStrategy -> [m Pred] -> m DerivClause -- | A single deriving clause at the end of a datatype. data DerivClause -- |
--   { deriving stock (Eq, Ord) }
--   
DerivClause :: Maybe DerivStrategy -> Cxt -> DerivClause stockStrategy :: Quote m => m DerivStrategy anyclassStrategy :: Quote m => m DerivStrategy newtypeStrategy :: Quote m => m DerivStrategy viaStrategy :: Quote m => m Type -> m DerivStrategy -- | What the user explicitly requests when deriving an instance. data DerivStrategy -- | A "standard" derived instance StockStrategy :: DerivStrategy -- |
--   -XDeriveAnyClass
--   
AnyclassStrategy :: DerivStrategy -- |
--   -XGeneralizedNewtypeDeriving
--   
NewtypeStrategy :: DerivStrategy -- |
--   -XDerivingVia
--   
ViaStrategy :: Type -> DerivStrategy classD :: Quote m => m Cxt -> Name -> [TyVarBndr ()] -> [FunDep] -> [m Dec] -> m Dec instanceD :: Quote m => m Cxt -> m Type -> [m Dec] -> m Dec instanceWithOverlapD :: Quote m => Maybe Overlap -> m Cxt -> m Type -> [m Dec] -> m Dec -- | Varieties of allowed instance overlap. data Overlap -- | May be overlapped by more specific instances Overlappable :: Overlap -- | May overlap a more general instance Overlapping :: Overlap -- | Both Overlapping and Overlappable Overlaps :: Overlap -- | Both Overlappable and Overlappable, and pick an -- arbitrary one if multiple choices are available. Incoherent :: Overlap sigD :: Quote m => Name -> m Type -> m Dec kiSigD :: Quote m => Name -> m Kind -> m Dec standaloneDerivD :: Quote m => m Cxt -> m Type -> m Dec standaloneDerivWithStrategyD :: Quote m => Maybe DerivStrategy -> m Cxt -> m Type -> m Dec defaultSigD :: Quote m => Name -> m Type -> m Dec roleAnnotD :: Quote m => Name -> [Role] -> m Dec dataFamilyD :: Quote m => Name -> [TyVarBndr ()] -> Maybe Kind -> m Dec openTypeFamilyD :: Quote m => Name -> [TyVarBndr ()] -> FamilyResultSig -> Maybe InjectivityAnn -> m Dec closedTypeFamilyD :: Quote m => Name -> [TyVarBndr ()] -> FamilyResultSig -> Maybe InjectivityAnn -> [m TySynEqn] -> m Dec dataInstD :: Quote m => m Cxt -> Name -> [m Type] -> Maybe Kind -> [m Con] -> [m DerivClause] -> m Dec newtypeInstD :: Quote m => m Cxt -> Name -> [m Type] -> Maybe Kind -> m Con -> [m DerivClause] -> m Dec tySynInstD :: Quote m => m TySynEqn -> m Dec tySynEqn :: Quote m => Maybe [TyVarBndr ()] -> m Type -> m Type -> m TySynEqn injectivityAnn :: Name -> [Name] -> InjectivityAnn noSig :: FamilyResultSig kindSig :: Kind -> FamilyResultSig tyVarSig :: TyVarBndr () -> FamilyResultSig infixLD :: Quote m => Int -> Name -> m Dec infixRD :: Quote m => Int -> Name -> m Dec infixND :: Quote m => Int -> Name -> m Dec cCall :: Callconv stdCall :: Callconv cApi :: Callconv prim :: Callconv javaScript :: Callconv unsafe :: Safety safe :: Safety interruptible :: Safety forImpD :: Quote m => Callconv -> Safety -> String -> Name -> m Type -> m Dec funDep :: [Name] -> [Name] -> FunDep ruleVar :: Quote m => Name -> m RuleBndr typedRuleVar :: Quote m => Name -> m Type -> m RuleBndr valueAnnotation :: Name -> AnnTarget typeAnnotation :: Name -> AnnTarget moduleAnnotation :: AnnTarget pragInlD :: Quote m => Name -> Inline -> RuleMatch -> Phases -> m Dec pragSpecD :: Quote m => Name -> m Type -> Phases -> m Dec pragSpecInlD :: Quote m => Name -> m Type -> Inline -> Phases -> m Dec pragSpecInstD :: Quote m => m Type -> m Dec pragRuleD :: Quote m => String -> [m RuleBndr] -> m Exp -> m Exp -> Phases -> m Dec pragAnnD :: Quote m => AnnTarget -> m Exp -> m Dec pragLineD :: Quote m => Int -> String -> m Dec pragCompleteD :: Quote m => [Name] -> Maybe Name -> m Dec -- | Pattern synonym declaration patSynD :: Quote m => Name -> m PatSynArgs -> m PatSynDir -> m Pat -> m Dec -- | Pattern synonym type signature patSynSigD :: Quote m => Name -> m Type -> m Dec unidir :: Quote m => m PatSynDir implBidir :: Quote m => m PatSynDir explBidir :: Quote m => [m Clause] -> m PatSynDir prefixPatSyn :: Quote m => [Name] -> m PatSynArgs infixPatSyn :: Quote m => Name -> Name -> m PatSynArgs recordPatSyn :: Quote m => [Name] -> m PatSynArgs -- | Implicit parameter binding declaration. Can only be used in let and -- where clauses which consist entirely of implicit bindings. implicitParamBindD :: Quote m => String -> m Exp -> m Dec -- | pure the Module at the place of splicing. Can be used as an input for -- reifyModule. thisModule :: Q Module -- | The public face of Template Haskell -- -- For other documentation, refer to: -- http://www.haskell.org/haskellwiki/Template_Haskell module Language.Haskell.TH data Q a runQ :: Quasi m => Q a -> m a -- | The Quote class implements the minimal interface which is -- necessary for desugaring quotations. -- -- -- -- Therefore the type of an untyped quotation in GHC is `Quote m => m -- Exp` -- -- For many years the type of a quotation was fixed to be `Q Exp` but by -- more precisely specifying the minimal interface it enables the -- Exp to be extracted purely from the quotation without -- interacting with Q. class Monad m => Quote m -- | Generate a fresh name, which cannot be captured. -- -- For example, this: -- --
--   f = $(do
--       nm1 <- newName "x"
--       let nm2 = mkName "x"
--       return (LamE [VarP nm1] (LamE [VarP nm2] (VarE nm1)))
--      )
--   
-- -- will produce the splice -- --
--   f = \x0 -> \x -> x0
--   
-- -- In particular, the occurrence VarE nm1 refers to the binding -- VarP nm1, and is not captured by the binding VarP -- nm2. -- -- Although names generated by newName cannot be -- captured, they can capture other names. For example, this: -- --
--   g = $(do
--     nm1 <- newName "x"
--     let nm2 = mkName "x"
--     return (LamE [VarP nm2] (LamE [VarP nm1] (VarE nm2)))
--    )
--   
-- -- will produce the splice -- --
--   g = \x -> \x0 -> x0
--   
-- -- since the occurrence VarE nm2 is captured by the innermost -- binding of x, namely VarP nm1. newName :: Quote m => String -> m Name -- | Report an error to the user, but allow the current splice's -- computation to carry on. To abort the computation, use fail. reportError :: String -> Q () -- | Report a warning to the user, and carry on. reportWarning :: String -> Q () -- | Report an error (True) or warning (False), but carry on; use -- fail to stop. -- | Deprecated: Use reportError or reportWarning instead report :: Bool -> String -> Q () -- | Recover from errors raised by reportError or fail. recover :: Q a -> Q a -> Q a -- | The location at which this computation is spliced. location :: Q Loc data Loc Loc :: String -> String -> String -> CharPos -> CharPos -> Loc [loc_filename] :: Loc -> String [loc_package] :: Loc -> String [loc_module] :: Loc -> String [loc_start] :: Loc -> CharPos [loc_end] :: Loc -> CharPos -- | The runIO function lets you run an I/O computation in the -- Q monad. Take care: you are guaranteed the ordering of calls to -- runIO within a single Q computation, but not about the -- order in which splices are run. -- -- Note: for various murky reasons, stdout and stderr handles are not -- necessarily flushed when the compiler finishes running, so you should -- flush them yourself. runIO :: IO a -> Q a -- | reify looks up information about the Name. -- -- It is sometimes useful to construct the argument name using -- lookupTypeName or lookupValueName to ensure that we are -- reifying from the right namespace. For instance, in this context: -- --
--   data D = D
--   
-- -- which D does reify (mkName "D") return information -- about? (Answer: D-the-type, but don't rely on it.) To ensure -- we get information about D-the-value, use -- lookupValueName: -- --
--   do
--     Just nm <- lookupValueName "D"
--     reify nm
--   
-- -- and to get information about D-the-type, use -- lookupTypeName. reify :: Name -> Q Info -- | reifyModule mod looks up information about module -- mod. To look up the current module, call this function with -- the return value of thisModule. reifyModule :: Module -> Q ModuleInfo -- | Obtained from reify in the Q Monad. data Info -- | A class, with a list of its visible instances ClassI :: Dec -> [InstanceDec] -> Info -- | A class method ClassOpI :: Name -> Type -> ParentName -> Info -- | A "plain" type constructor. "Fancier" type constructors are returned -- using PrimTyConI or FamilyI as appropriate. At present, -- this reified declaration will never have derived instances attached to -- it (if you wish to check for an instance, see reifyInstances). TyConI :: Dec -> Info -- | A type or data family, with a list of its visible instances. A closed -- type family is returned with 0 instances. FamilyI :: Dec -> [InstanceDec] -> Info -- | A "primitive" type constructor, which can't be expressed with a -- Dec. Examples: (->), Int#. PrimTyConI :: Name -> Arity -> Unlifted -> Info -- | A data constructor DataConI :: Name -> Type -> ParentName -> Info -- | A pattern synonym PatSynI :: Name -> PatSynType -> Info -- | A "value" variable (as opposed to a type variable, see TyVarI). -- -- The Maybe Dec field contains Just the declaration -- which defined the variable - including the RHS of the declaration - or -- else Nothing, in the case where the RHS is unavailable to the -- compiler. At present, this value is always Nothing: -- returning the RHS has not yet been implemented because of lack of -- interest. VarI :: Name -> Type -> Maybe Dec -> Info -- | A type variable. -- -- The Type field contains the type which underlies the -- variable. At present, this is always VarT theName, but -- future changes may permit refinement of this. TyVarI :: Name -> Type -> Info -- | Obtained from reifyModule in the Q Monad. data ModuleInfo -- | Contains the import list of the module. ModuleInfo :: [Module] -> ModuleInfo -- | InstanceDec describes a single instance of a class or type -- function. It is just a Dec, but guaranteed to be one of the -- following: -- -- type InstanceDec = Dec -- | In ClassOpI and DataConI, name of the parent class or -- type type ParentName = Name -- | In UnboxedSumE and UnboxedSumP, the number associated -- with a particular data constructor. SumAlts are one-indexed and -- should never exceed the value of its corresponding SumArity. -- For example: -- -- type SumAlt = Int -- | In UnboxedSumE, UnboxedSumT, and UnboxedSumP, the -- total number of SumAlts. For example, (#|#) has a -- SumArity of 2. type SumArity = Int -- | In PrimTyConI, arity of the type constructor type Arity = Int -- | In PrimTyConI, is the type constructor unlifted? type Unlifted = Bool -- | The language extensions known to GHC. -- -- Note that there is an orphan Binary instance for this type -- supplied by the GHC.LanguageExtensions module provided by -- ghc-boot. We can't provide here as this would require adding -- transitive dependencies to the template-haskell package, -- which must have a minimal dependency set. data Extension Cpp :: Extension OverlappingInstances :: Extension UndecidableInstances :: Extension IncoherentInstances :: Extension UndecidableSuperClasses :: Extension MonomorphismRestriction :: Extension MonoPatBinds :: Extension MonoLocalBinds :: Extension RelaxedPolyRec :: Extension ExtendedDefaultRules :: Extension ForeignFunctionInterface :: Extension UnliftedFFITypes :: Extension InterruptibleFFI :: Extension CApiFFI :: Extension GHCForeignImportPrim :: Extension JavaScriptFFI :: Extension ParallelArrays :: Extension Arrows :: Extension TemplateHaskell :: Extension TemplateHaskellQuotes :: Extension QuasiQuotes :: Extension ImplicitParams :: Extension ImplicitPrelude :: Extension ScopedTypeVariables :: Extension AllowAmbiguousTypes :: Extension UnboxedTuples :: Extension UnboxedSums :: Extension UnliftedNewtypes :: Extension BangPatterns :: Extension TypeFamilies :: Extension TypeFamilyDependencies :: Extension TypeInType :: Extension OverloadedStrings :: Extension OverloadedLists :: Extension NumDecimals :: Extension DisambiguateRecordFields :: Extension RecordWildCards :: Extension RecordPuns :: Extension ViewPatterns :: Extension GADTs :: Extension GADTSyntax :: Extension NPlusKPatterns :: Extension DoAndIfThenElse :: Extension BlockArguments :: Extension RebindableSyntax :: Extension ConstraintKinds :: Extension PolyKinds :: Extension DataKinds :: Extension InstanceSigs :: Extension ApplicativeDo :: Extension StandaloneDeriving :: Extension DeriveDataTypeable :: Extension AutoDeriveTypeable :: Extension DeriveFunctor :: Extension DeriveTraversable :: Extension DeriveFoldable :: Extension DeriveGeneric :: Extension DefaultSignatures :: Extension DeriveAnyClass :: Extension DeriveLift :: Extension DerivingStrategies :: Extension DerivingVia :: Extension TypeSynonymInstances :: Extension FlexibleContexts :: Extension FlexibleInstances :: Extension ConstrainedClassMethods :: Extension MultiParamTypeClasses :: Extension NullaryTypeClasses :: Extension FunctionalDependencies :: Extension UnicodeSyntax :: Extension ExistentialQuantification :: Extension MagicHash :: Extension EmptyDataDecls :: Extension KindSignatures :: Extension RoleAnnotations :: Extension ParallelListComp :: Extension TransformListComp :: Extension MonadComprehensions :: Extension GeneralizedNewtypeDeriving :: Extension RecursiveDo :: Extension PostfixOperators :: Extension TupleSections :: Extension PatternGuards :: Extension LiberalTypeSynonyms :: Extension RankNTypes :: Extension ImpredicativeTypes :: Extension TypeOperators :: Extension ExplicitNamespaces :: Extension PackageImports :: Extension ExplicitForAll :: Extension AlternativeLayoutRule :: Extension AlternativeLayoutRuleTransitional :: Extension DatatypeContexts :: Extension NondecreasingIndentation :: Extension RelaxedLayout :: Extension TraditionalRecordSyntax :: Extension LambdaCase :: Extension MultiWayIf :: Extension BinaryLiterals :: Extension NegativeLiterals :: Extension HexFloatLiterals :: Extension DuplicateRecordFields :: Extension OverloadedLabels :: Extension EmptyCase :: Extension PatternSynonyms :: Extension PartialTypeSignatures :: Extension NamedWildCards :: Extension StaticPointers :: Extension TypeApplications :: Extension Strict :: Extension StrictData :: Extension MonadFailDesugaring :: Extension EmptyDataDeriving :: Extension NumericUnderscores :: Extension QuantifiedConstraints :: Extension StarIsType :: Extension ImportQualifiedPost :: Extension CUSKs :: Extension StandaloneKindSignatures :: Extension -- | List all enabled language extensions. extsEnabled :: Q [Extension] -- | Determine whether the given language extension is enabled in the -- Q monad. isExtEnabled :: Extension -> Q Bool -- | Look up the given name in the (type namespace of the) current splice's -- scope. See Language.Haskell.TH.Syntax#namelookup for more -- details. lookupTypeName :: String -> Q (Maybe Name) -- | Look up the given name in the (value namespace of the) current -- splice's scope. See Language.Haskell.TH.Syntax#namelookup for -- more details. lookupValueName :: String -> Q (Maybe Name) -- | reifyFixity nm attempts to find a fixity declaration for -- nm. For example, if the function foo has the fixity -- declaration infixr 7 foo, then reifyFixity 'foo -- would return Just (Fixity 7 InfixR). If -- the function bar does not have a fixity declaration, then -- reifyFixity 'bar returns Nothing, so you may assume -- bar has defaultFixity. reifyFixity :: Name -> Q (Maybe Fixity) -- | reifyType nm attempts to find the type or kind of -- nm. For example, reifyType 'not returns Bool -- -> Bool, and reifyType ''Bool returns Type. -- This works even if there's no explicit signature and the type or kind -- is inferred. reifyType :: Name -> Q Type -- | reifyInstances nm tys returns a list of visible instances of -- nm tys. That is, if nm is the name of a type class, -- then all instances of this class at the types tys are -- returned. Alternatively, if nm is the name of a data family -- or type family, all instances of this family at the types tys -- are returned. -- -- Note that this is a "shallow" test; the declarations returned merely -- have instance heads which unify with nm tys, they need not -- actually be satisfiable. -- -- -- -- There is one edge case: reifyInstances ''Typeable tys -- currently always produces an empty list (no matter what tys -- are given). reifyInstances :: Name -> [Type] -> Q [InstanceDec] -- | Is the list of instances returned by reifyInstances nonempty? isInstance :: Name -> [Type] -> Q Bool -- | reifyRoles nm returns the list of roles associated with the -- parameters of the tycon nm. Fails if nm cannot be -- found or is not a tycon. The returned list should never contain -- InferR. reifyRoles :: Name -> Q [Role] -- | reifyAnnotations target returns the list of annotations -- associated with target. Only the annotations that are -- appropriately typed is returned. So if you have Int and -- String annotations for the same target, you have to call this -- function twice. reifyAnnotations :: Data a => AnnLookup -> Q [a] -- | Annotation target for reifyAnnotations data AnnLookup AnnLookupModule :: Module -> AnnLookup AnnLookupName :: Name -> AnnLookup -- | reifyConStrictness nm looks up the strictness information for -- the fields of the constructor with the name nm. Note that the -- strictness information that reifyConStrictness returns may not -- correspond to what is written in the source code. For example, in the -- following data declaration: -- --
--   data Pair a = Pair a a
--   
-- -- reifyConStrictness would return [DecidedLazy, -- DecidedLazy] under most circumstances, but it would return -- [DecidedStrict, DecidedStrict] if the -- -XStrictData language extension was enabled. reifyConStrictness :: Name -> Q [DecidedStrictness] -- | Represents an expression which has type a. Built on top of -- Exp, typed expressions allow for type-safe splicing via: -- -- -- -- Traditional expression quotes and splices let us construct ill-typed -- expressions: -- --
--   >>> fmap ppr $ runQ [| True == $( [| "foo" |] ) |]
--   GHC.Types.True GHC.Classes.== "foo"
--   
--   >>> GHC.Types.True GHC.Classes.== "foo"
--   <interactive> error:
--       • Couldn't match expected type ‘Bool’ with actual type ‘[Char]’
--       • In the second argument of ‘(==)’, namely ‘"foo"’
--         In the expression: True == "foo"
--         In an equation for ‘it’: it = True == "foo"
--   
-- -- With typed expressions, the type error occurs when constructing -- the Template Haskell expression: -- --
--   >>> fmap ppr $ runQ [|| True == $$( [|| "foo" ||] ) ||]
--   <interactive> error:
--       • Couldn't match type ‘[Char]’ with ‘Bool’
--         Expected type: Q (TExp Bool)
--           Actual type: Q (TExp [Char])
--       • In the Template Haskell quotation [|| "foo" ||]
--         In the expression: [|| "foo" ||]
--         In the Template Haskell splice $$([|| "foo" ||])
--   
data TExp (a :: TYPE (r :: RuntimeRep)) -- | Underlying untyped Template Haskell expression unType :: TExp a -> Exp -- | An abstract type representing names in the syntax tree. -- -- Names can be constructed in several ways, which come with -- different name-capture guarantees (see -- Language.Haskell.TH.Syntax#namecapture for an explanation of -- name capture): -- -- -- -- Names constructed using newName and mkName may be -- used in bindings (such as let x = ... or x -> -- ...), but names constructed using lookupValueName, -- lookupTypeName, 'f, ''T may not. data Name data NameSpace -- | Generate a capturable name. Occurrences of such names will be resolved -- according to the Haskell scoping rules at the occurrence site. -- -- For example: -- --
--   f = [| pi + $(varE (mkName "pi")) |]
--   ...
--   g = let pi = 3 in $f
--   
-- -- In this case, g is desugared to -- --
--   g = Prelude.pi + 3
--   
-- -- Note that mkName may be used with qualified names: -- --
--   mkName "Prelude.pi"
--   
-- -- See also dyn for a useful combinator. The above example could -- be rewritten using dyn as -- --
--   f = [| pi + $(dyn "pi") |]
--   
mkName :: String -> Name -- | The name without its module prefix. -- --

Examples

-- --
--   >>> nameBase ''Data.Either.Either
--   "Either"
--   
--   >>> nameBase (mkName "foo")
--   "foo"
--   
--   >>> nameBase (mkName "Module.foo")
--   "foo"
--   
nameBase :: Name -> String -- | Module prefix of a name, if it exists. -- --

Examples

-- --
--   >>> nameModule ''Data.Either.Either
--   Just "Data.Either"
--   
--   >>> nameModule (mkName "foo")
--   Nothing
--   
--   >>> nameModule (mkName "Module.foo")
--   Just "Module"
--   
nameModule :: Name -> Maybe String -- | A name's package, if it exists. -- --

Examples

-- --
--   >>> namePackage ''Data.Either.Either
--   Just "base"
--   
--   >>> namePackage (mkName "foo")
--   Nothing
--   
--   >>> namePackage (mkName "Module.foo")
--   Nothing
--   
namePackage :: Name -> Maybe String -- | Returns whether a name represents an occurrence of a top-level -- variable (VarName), data constructor (DataName), type -- constructor, or type class (TcClsName). If we can't be sure, it -- returns Nothing. -- --

Examples

-- --
--   >>> nameSpace 'Prelude.id
--   Just VarName
--   
--   >>> nameSpace (mkName "id")
--   Nothing -- only works for top-level variable names
--   
--   >>> nameSpace 'Data.Maybe.Just
--   Just DataName
--   
--   >>> nameSpace ''Data.Maybe.Maybe
--   Just TcClsName
--   
--   >>> nameSpace ''Data.Ord.Ord
--   Just TcClsName
--   
nameSpace :: Name -> Maybe NameSpace -- | Tuple type constructor tupleTypeName :: Int -> Name -- | Tuple data constructor tupleDataName :: Int -> Name -- | Unboxed tuple type constructor unboxedTupleTypeName :: Int -> Name -- | Unboxed tuple data constructor unboxedTupleDataName :: Int -> Name -- | Unboxed sum type constructor unboxedSumTypeName :: SumArity -> Name -- | Unboxed sum data constructor unboxedSumDataName :: SumAlt -> SumArity -> Name data Dec -- |
--   { f p1 p2 = b where decs }
--   
FunD :: Name -> [Clause] -> Dec -- |
--   { p = b where decs }
--   
ValD :: Pat -> Body -> [Dec] -> Dec -- |
--   { data Cxt x => T x = A x | B (T x)
--          deriving (Z,W)
--          deriving stock Eq }
--   
DataD :: Cxt -> Name -> [TyVarBndr ()] -> Maybe Kind -> [Con] -> [DerivClause] -> Dec -- |
--   { newtype Cxt x => T x = A (B x)
--          deriving (Z,W Q)
--          deriving stock Eq }
--   
NewtypeD :: Cxt -> Name -> [TyVarBndr ()] -> Maybe Kind -> Con -> [DerivClause] -> Dec -- |
--   { type T x = (x,x) }
--   
TySynD :: Name -> [TyVarBndr ()] -> Type -> Dec -- |
--   { class Eq a => Ord a where ds }
--   
ClassD :: Cxt -> Name -> [TyVarBndr ()] -> [FunDep] -> [Dec] -> Dec -- |
--   { instance {-# OVERLAPS #-}
--           Show w => Show [w] where ds }
--   
InstanceD :: Maybe Overlap -> Cxt -> Type -> [Dec] -> Dec -- |
--   { length :: [a] -> Int }
--   
SigD :: Name -> Type -> Dec -- |
--   { type TypeRep :: k -> Type }
--   
KiSigD :: Name -> Kind -> Dec -- |
--   { foreign import ... }
--   { foreign export ... }
--   
ForeignD :: Foreign -> Dec -- |
--   { infix 3 foo }
--   
InfixD :: Fixity -> Name -> Dec -- |
--   { {-# INLINE [1] foo #-} }
--   
PragmaD :: Pragma -> Dec -- |
--   { data family T a b c :: * }
--   
DataFamilyD :: Name -> [TyVarBndr ()] -> Maybe Kind -> Dec -- |
--   { data instance Cxt x => T [x]
--          = A x | B (T x)
--          deriving (Z,W)
--          deriving stock Eq }
--   
DataInstD :: Cxt -> Maybe [TyVarBndr ()] -> Type -> Maybe Kind -> [Con] -> [DerivClause] -> Dec -- |
--   { newtype instance Cxt x => T [x]
--           = A (B x)
--           deriving (Z,W)
--           deriving stock Eq }
--   
NewtypeInstD :: Cxt -> Maybe [TyVarBndr ()] -> Type -> Maybe Kind -> Con -> [DerivClause] -> Dec -- |
--   { type instance ... }
--   
TySynInstD :: TySynEqn -> Dec -- |
--   { type family T a b c = (r :: *) | r -> a b }
--   
OpenTypeFamilyD :: TypeFamilyHead -> Dec -- |
--   { type family F a b = (r :: *) | r -> a where ... }
--   
ClosedTypeFamilyD :: TypeFamilyHead -> [TySynEqn] -> Dec -- |
--   { type role T nominal representational }
--   
RoleAnnotD :: Name -> [Role] -> Dec -- |
--   { deriving stock instance Ord a => Ord (Foo a) }
--   
StandaloneDerivD :: Maybe DerivStrategy -> Cxt -> Type -> Dec -- |
--   { default size :: Data a => a -> Int }
--   
DefaultSigD :: Name -> Type -> Dec -- | { pattern P v1 v2 .. vn <- p } unidirectional or { -- pattern P v1 v2 .. vn = p } implicit bidirectional or { -- pattern P v1 v2 .. vn <- p where P v1 v2 .. vn = e } explicit -- bidirectional -- -- also, besides prefix pattern synonyms, both infix and record pattern -- synonyms are supported. See PatSynArgs for details PatSynD :: Name -> PatSynArgs -> PatSynDir -> Pat -> Dec -- | A pattern synonym's type signature. PatSynSigD :: Name -> PatSynType -> Dec -- |
--   { ?x = expr }
--   
-- -- Implicit parameter binding declaration. Can only be used in let and -- where clauses which consist entirely of implicit bindings. ImplicitParamBindD :: String -> Exp -> Dec -- | A single data constructor. -- -- The constructors for Con can roughly be divided up into two -- categories: those for constructors with "vanilla" syntax -- (NormalC, RecC, and InfixC), and those for -- constructors with GADT syntax (GadtC and RecGadtC). The -- ForallC constructor, which quantifies additional type variables -- and class contexts, can surround either variety of constructor. -- However, the type variables that it quantifies are different depending -- on what constructor syntax is used: -- -- -- --
--   data Foo a = forall b. MkFoo a b
--   
--   
-- -- In MkFoo, ForallC will quantify b, but not -- a. -- -- -- --
--   data Bar a b where
--     MkBar :: (a ~ b) => c -> MkBar a b
--   
--   
-- -- In MkBar, ForallC will quantify a, -- b, and c. data Con -- |
--   C Int a
--   
NormalC :: Name -> [BangType] -> Con -- |
--   C { v :: Int, w :: a }
--   
RecC :: Name -> [VarBangType] -> Con -- |
--   Int :+ a
--   
InfixC :: BangType -> Name -> BangType -> Con -- |
--   forall a. Eq a => C [a]
--   
ForallC :: [TyVarBndr Specificity] -> Cxt -> Con -> Con -- |
--   C :: a -> b -> T b Int
--   
GadtC :: [Name] -> [BangType] -> Type -> Con -- |
--   C :: { v :: Int } -> T b Int
--   
RecGadtC :: [Name] -> [VarBangType] -> Type -> Con data Clause -- |
--   f { p1 p2 = body where decs }
--   
Clause :: [Pat] -> Body -> [Dec] -> Clause data SourceUnpackedness -- |
--   C a
--   
NoSourceUnpackedness :: SourceUnpackedness -- |
--   C { {-# NOUNPACK #-} } a
--   
SourceNoUnpack :: SourceUnpackedness -- |
--   C { {-# UNPACK #-} } a
--   
SourceUnpack :: SourceUnpackedness data SourceStrictness -- |
--   C a
--   
NoSourceStrictness :: SourceStrictness -- |
--   C {~}a
--   
SourceLazy :: SourceStrictness -- |
--   C {!}a
--   
SourceStrict :: SourceStrictness -- | Unlike SourceStrictness and SourceUnpackedness, -- DecidedStrictness refers to the strictness that the compiler -- chooses for a data constructor field, which may be different from what -- is written in source code. See reifyConStrictness for more -- information. data DecidedStrictness DecidedLazy :: DecidedStrictness DecidedStrict :: DecidedStrictness DecidedUnpack :: DecidedStrictness data Bang -- |
--   C { {-# UNPACK #-} !}a
--   
Bang :: SourceUnpackedness -> SourceStrictness -> Bang -- | As of template-haskell-2.11.0.0, Strict has been -- replaced by Bang. type Strict = Bang data Foreign ImportF :: Callconv -> Safety -> String -> Name -> Type -> Foreign ExportF :: Callconv -> String -> Name -> Type -> Foreign data Callconv CCall :: Callconv StdCall :: Callconv CApi :: Callconv Prim :: Callconv JavaScript :: Callconv data Safety Unsafe :: Safety Safe :: Safety Interruptible :: Safety data Pragma InlineP :: Name -> Inline -> RuleMatch -> Phases -> Pragma SpecialiseP :: Name -> Type -> Maybe Inline -> Phases -> Pragma SpecialiseInstP :: Type -> Pragma RuleP :: String -> Maybe [TyVarBndr ()] -> [RuleBndr] -> Exp -> Exp -> Phases -> Pragma AnnP :: AnnTarget -> Exp -> Pragma LineP :: Int -> String -> Pragma -- |
--   { {-# COMPLETE C_1, ..., C_i [ :: T ] #-} }
--   
CompleteP :: [Name] -> Maybe Name -> Pragma data Inline NoInline :: Inline Inline :: Inline Inlinable :: Inline data RuleMatch ConLike :: RuleMatch FunLike :: RuleMatch data Phases AllPhases :: Phases FromPhase :: Int -> Phases BeforePhase :: Int -> Phases data RuleBndr RuleVar :: Name -> RuleBndr TypedRuleVar :: Name -> Type -> RuleBndr data AnnTarget ModuleAnnotation :: AnnTarget TypeAnnotation :: Name -> AnnTarget ValueAnnotation :: Name -> AnnTarget data FunDep FunDep :: [Name] -> [Name] -> FunDep -- | One equation of a type family instance or closed type family. The -- arguments are the left-hand-side type and the right-hand-side result. -- -- For instance, if you had the following type family: -- --
--   type family Foo (a :: k) :: k where
--     forall k (a :: k). Foo @k a = a
--   
-- -- The Foo @k a = a equation would be represented as follows: -- --
--   TySynEqn (Just [PlainTV k, KindedTV a (VarT k)])
--              (AppT (AppKindT (ConT ''Foo) (VarT k)) (VarT a))
--              (VarT a)
--   
data TySynEqn TySynEqn :: Maybe [TyVarBndr ()] -> Type -> Type -> TySynEqn -- | Common elements of OpenTypeFamilyD and -- ClosedTypeFamilyD. By analogy with "head" for type classes and -- type class instances as defined in Type classes: an exploration of -- the design space, the TypeFamilyHead is defined to be the -- elements of the declaration between type family and -- where. data TypeFamilyHead TypeFamilyHead :: Name -> [TyVarBndr ()] -> FamilyResultSig -> Maybe InjectivityAnn -> TypeFamilyHead data Fixity Fixity :: Int -> FixityDirection -> Fixity data FixityDirection InfixL :: FixityDirection InfixR :: FixityDirection InfixN :: FixityDirection -- | Default fixity: infixl 9 defaultFixity :: Fixity -- | Highest allowed operator precedence for Fixity constructor -- (answer: 9) maxPrecedence :: Int -- | A pattern synonym's directionality. data PatSynDir -- |
--   pattern P x {<-} p
--   
Unidir :: PatSynDir -- |
--   pattern P x {=} p
--   
ImplBidir :: PatSynDir -- |
--   pattern P x {<-} p where P x = e
--   
ExplBidir :: [Clause] -> PatSynDir -- | A pattern synonym's argument type. data PatSynArgs -- |
--   pattern P {x y z} = p
--   
PrefixPatSyn :: [Name] -> PatSynArgs -- |
--   pattern {x P y} = p
--   
InfixPatSyn :: Name -> Name -> PatSynArgs -- |
--   pattern P { {x,y,z} } = p
--   
RecordPatSyn :: [Name] -> PatSynArgs data Exp -- |
--   { x }
--   
VarE :: Name -> Exp -- |
--   data T1 = C1 t1 t2; p = {C1} e1 e2
--   
ConE :: Name -> Exp -- |
--   { 5 or 'c'}
--   
LitE :: Lit -> Exp -- |
--   { f x }
--   
AppE :: Exp -> Exp -> Exp -- |
--   { f @Int }
--   
AppTypeE :: Exp -> Type -> Exp -- |
--   {x + y} or {(x+)} or {(+ x)} or {(+)}
--   
InfixE :: Maybe Exp -> Exp -> Maybe Exp -> Exp -- |
--   {x + y}
--   
-- -- See Language.Haskell.TH.Syntax#infix UInfixE :: Exp -> Exp -> Exp -> Exp -- |
--   { (e) }
--   
-- -- See Language.Haskell.TH.Syntax#infix ParensE :: Exp -> Exp -- |
--   { \ p1 p2 -> e }
--   
LamE :: [Pat] -> Exp -> Exp -- |
--   { \case m1; m2 }
--   
LamCaseE :: [Match] -> Exp -- |
--   { (e1,e2) }
--   
-- -- The Maybe is necessary for handling tuple sections. -- --
--   (1,)
--   
-- -- translates to -- --
--   TupE [Just (LitE (IntegerL 1)),Nothing]
--   
TupE :: [Maybe Exp] -> Exp -- |
--   { (# e1,e2 #) }
--   
-- -- The Maybe is necessary for handling tuple sections. -- --
--   (# 'c', #)
--   
-- -- translates to -- --
--   UnboxedTupE [Just (LitE (CharL 'c')),Nothing]
--   
UnboxedTupE :: [Maybe Exp] -> Exp -- |
--   { (#|e|#) }
--   
UnboxedSumE :: Exp -> SumAlt -> SumArity -> Exp -- |
--   { if e1 then e2 else e3 }
--   
CondE :: Exp -> Exp -> Exp -> Exp -- |
--   { if | g1 -> e1 | g2 -> e2 }
--   
MultiIfE :: [(Guard, Exp)] -> Exp -- |
--   { let { x=e1; y=e2 } in e3 }
--   
LetE :: [Dec] -> Exp -> Exp -- |
--   { case e of m1; m2 }
--   
CaseE :: Exp -> [Match] -> Exp -- |
--   { do { p <- e1; e2 }  }
--   
DoE :: [Stmt] -> Exp -- |
--   { mdo { x <- e1 y; y <- e2 x; } }
--   
MDoE :: [Stmt] -> Exp -- |
--   { [ (x,y) | x <- xs, y <- ys ] }
--   
-- -- The result expression of the comprehension is the last of the -- Stmts, and should be a NoBindS. -- -- E.g. translation: -- --
--   [ f x | x <- xs ]
--   
-- --
--   CompE [BindS (VarP x) (VarE xs), NoBindS (AppE (VarE f) (VarE x))]
--   
CompE :: [Stmt] -> Exp -- |
--   { [ 1 ,2 .. 10 ] }
--   
ArithSeqE :: Range -> Exp -- |
--   { [1,2,3] }
--   
ListE :: [Exp] -> Exp -- |
--   { e :: t }
--   
SigE :: Exp -> Type -> Exp -- |
--   { T { x = y, z = w } }
--   
RecConE :: Name -> [FieldExp] -> Exp -- |
--   { (f x) { z = w } }
--   
RecUpdE :: Exp -> [FieldExp] -> Exp -- |
--   { static e }
--   
StaticE :: Exp -> Exp -- |
--   { _x }
--   
-- -- This is used for holes or unresolved identifiers in AST quotes. Note -- that it could either have a variable name or constructor name. UnboundVarE :: Name -> Exp -- | { #x } ( Overloaded label ) LabelE :: String -> Exp -- | { ?x } ( Implicit parameter ) ImplicitParamVarE :: String -> Exp data Match -- |
--   case e of { pat -> body where decs }
--   
Match :: Pat -> Body -> [Dec] -> Match data Body -- |
--   f p { | e1 = e2
--         | e3 = e4 }
--    where ds
--   
GuardedB :: [(Guard, Exp)] -> Body -- |
--   f p { = e } where ds
--   
NormalB :: Exp -> Body data Guard -- |
--   f x { | odd x } = x
--   
NormalG :: Exp -> Guard -- |
--   f x { | Just y <- x, Just z <- y } = z
--   
PatG :: [Stmt] -> Guard data Stmt -- |
--   p <- e
--   
BindS :: Pat -> Exp -> Stmt -- |
--   { let { x=e1; y=e2 } }
--   
LetS :: [Dec] -> Stmt -- |
--   e
--   
NoBindS :: Exp -> Stmt -- | x <- e1 | s2, s3 | s4 (in CompE) ParS :: [[Stmt]] -> Stmt -- |
--   rec { s1; s2 }
--   
RecS :: [Stmt] -> Stmt data Range FromR :: Exp -> Range FromThenR :: Exp -> Exp -> Range FromToR :: Exp -> Exp -> Range FromThenToR :: Exp -> Exp -> Exp -> Range data Lit CharL :: Char -> Lit StringL :: String -> Lit -- | Used for overloaded and non-overloaded literals. We don't have a good -- way to represent non-overloaded literals at the moment. Maybe that -- doesn't matter? IntegerL :: Integer -> Lit RationalL :: Rational -> Lit IntPrimL :: Integer -> Lit WordPrimL :: Integer -> Lit FloatPrimL :: Rational -> Lit DoublePrimL :: Rational -> Lit -- | A primitive C-style string, type Addr# StringPrimL :: [Word8] -> Lit -- | Some raw bytes, type Addr#: BytesPrimL :: Bytes -> Lit CharPrimL :: Char -> Lit -- | Pattern in Haskell given in {} data Pat -- |
--   { 5 or 'c' }
--   
LitP :: Lit -> Pat -- |
--   { x }
--   
VarP :: Name -> Pat -- |
--   { (p1,p2) }
--   
TupP :: [Pat] -> Pat -- |
--   { (# p1,p2 #) }
--   
UnboxedTupP :: [Pat] -> Pat -- |
--   { (#|p|#) }
--   
UnboxedSumP :: Pat -> SumAlt -> SumArity -> Pat -- |
--   data T1 = C1 t1 t2; {C1 p1 p1} = e
--   
ConP :: Name -> [Pat] -> Pat -- |
--   foo ({x :+ y}) = e
--   
InfixP :: Pat -> Name -> Pat -> Pat -- |
--   foo ({x :+ y}) = e
--   
-- -- See Language.Haskell.TH.Syntax#infix UInfixP :: Pat -> Name -> Pat -> Pat -- |
--   {(p)}
--   
-- -- See Language.Haskell.TH.Syntax#infix ParensP :: Pat -> Pat -- |
--   { ~p }
--   
TildeP :: Pat -> Pat -- |
--   { !p }
--   
BangP :: Pat -> Pat -- |
--   { x @ p }
--   
AsP :: Name -> Pat -> Pat -- |
--   { _ }
--   
WildP :: Pat -- |
--   f (Pt { pointx = x }) = g x
--   
RecP :: Name -> [FieldPat] -> Pat -- |
--   { [1,2,3] }
--   
ListP :: [Pat] -> Pat -- |
--   { p :: t }
--   
SigP :: Pat -> Type -> Pat -- |
--   { e -> p }
--   
ViewP :: Exp -> Pat -> Pat type FieldExp = (Name, Exp) type FieldPat = (Name, Pat) data Type -- |
--   forall <vars>. <ctxt> => <type>
--   
ForallT :: [TyVarBndr Specificity] -> Cxt -> Type -> Type -- |
--   forall <vars> -> <type>
--   
ForallVisT :: [TyVarBndr ()] -> Type -> Type -- |
--   T a b
--   
AppT :: Type -> Type -> Type -- |
--   T @k t
--   
AppKindT :: Type -> Kind -> Type -- |
--   t :: k
--   
SigT :: Type -> Kind -> Type -- |
--   a
--   
VarT :: Name -> Type -- |
--   T
--   
ConT :: Name -> Type -- |
--   'T
--   
PromotedT :: Name -> Type -- |
--   T + T
--   
InfixT :: Type -> Name -> Type -> Type -- |
--   T + T
--   
-- -- See Language.Haskell.TH.Syntax#infix UInfixT :: Type -> Name -> Type -> Type -- |
--   (T)
--   
ParensT :: Type -> Type -- |
--   (,), (,,), etc.
--   
TupleT :: Int -> Type -- |
--   (#,#), (#,,#), etc.
--   
UnboxedTupleT :: Int -> Type -- |
--   (#|#), (#||#), etc.
--   
UnboxedSumT :: SumArity -> Type -- |
--   ->
--   
ArrowT :: Type -- |
--   ~
--   
EqualityT :: Type -- |
--   []
--   
ListT :: Type -- |
--   '(), '(,), '(,,), etc.
--   
PromotedTupleT :: Int -> Type -- |
--   '[]
--   
PromotedNilT :: Type -- |
--   (':)
--   
PromotedConsT :: Type -- |
--   *
--   
StarT :: Type -- |
--   Constraint
--   
ConstraintT :: Type -- |
--   0,1,2, etc.
--   
LitT :: TyLit -> Type -- |
--   _
--   
WildCardT :: Type -- |
--   ?x :: t
--   
ImplicitParamT :: String -> Type -> Type data TyVarBndr flag -- |
--   a
--   
PlainTV :: Name -> flag -> TyVarBndr flag -- |
--   (a :: k)
--   
KindedTV :: Name -> flag -> Kind -> TyVarBndr flag data TyLit -- |
--   2
--   
NumTyLit :: Integer -> TyLit -- |
--   "Hello"
--   
StrTyLit :: String -> TyLit -- | To avoid duplication between kinds and types, they are defined to be -- the same. Naturally, you would never have a type be StarT and -- you would never have a kind be SigT, but many of the other -- constructors are shared. Note that the kind Bool is denoted -- with ConT, not PromotedT. Similarly, tuple kinds are -- made with TupleT, not PromotedTupleT. type Kind = Type type Cxt = [Pred] " @(Eq a, Ord b)@" -- | Since the advent of ConstraintKinds, constraints are really -- just types. Equality constraints use the EqualityT constructor. -- Constraints may also be tuples of other constraints. type Pred = Type -- | Role annotations data Role -- |
--   nominal
--   
NominalR :: Role -- |
--   representational
--   
RepresentationalR :: Role -- |
--   phantom
--   
PhantomR :: Role -- |
--   _
--   
InferR :: Role data Specificity -- |
--   a
--   
SpecifiedSpec :: Specificity -- |
--   {a}
--   
InferredSpec :: Specificity -- | Type family result signature data FamilyResultSig -- | no signature NoSig :: FamilyResultSig -- |
--   k
--   
KindSig :: Kind -> FamilyResultSig -- |
--   = r, = (r :: k)
--   
TyVarSig :: TyVarBndr () -> FamilyResultSig -- | Injectivity annotation data InjectivityAnn InjectivityAnn :: Name -> [Name] -> InjectivityAnn -- | A pattern synonym's type. Note that a pattern synonym's fully -- specified type has a peculiar shape coming with two forall quantifiers -- and two constraint contexts. For example, consider the pattern synonym -- --
--   pattern P x1 x2 ... xn = <some-pattern>
--   
-- -- P's complete type is of the following form -- --
--   pattern P :: forall universals.   required constraints
--             => forall existentials. provided constraints
--             => t1 -> t2 -> ... -> tn -> t
--   
-- -- consisting of four parts: -- --
    --
  1. the (possibly empty lists of) universally quantified type -- variables and required constraints on them.
  2. --
  3. the (possibly empty lists of) existentially quantified type -- variables and the provided constraints on them.
  4. --
  5. the types t1, t2, .., tn of -- x1, x2, .., xn, respectively
  6. --
  7. the type t of <some-pattern>, mentioning -- only universals.
  8. --
-- -- Pattern synonym types interact with TH when (a) reifying a pattern -- synonym, (b) pretty printing, or (c) specifying a pattern synonym's -- type signature explicitly: -- -- -- -- See the GHC user's guide for more information on pattern synonyms and -- their types: -- https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts.html#pattern-synonyms. type PatSynType = Type type BangType = (Bang, Type) type VarBangType = (Name, Bang, Type) class Ppr a ppr :: Ppr a => a -> Doc ppr_list :: Ppr a => [a] -> Doc pprint :: Ppr a => a -> String pprExp :: Precedence -> Exp -> Doc pprLit :: Precedence -> Lit -> Doc pprPat :: Precedence -> Pat -> Doc pprParendType :: Type -> Doc