template-haskell-2.14.0.0: Support library for Template Haskell

Safe HaskellSafe
LanguageHaskell2010

Language.Haskell.TH.Lib

Contents

Description

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

Synopsis

Library functions

Abbreviations

type ExpQ = Q Exp Source #

type TExpQ a = Q (TExp a) Source #

type DecQ = Q Dec Source #

type DecsQ = Q [Dec] Source #

type ConQ = Q Con Source #

type CxtQ = Q Cxt Source #

type PatQ = Q Pat Source #

Constructors lifted to Q

Literals

Patterns

conP :: Name -> [PatQ] -> PatQ Source #

Pattern Guards

patGE :: [StmtQ] -> ExpQ -> Q (Guard, Exp) Source #

match :: PatQ -> BodyQ -> [DecQ] -> MatchQ Source #

Use with caseE

clause :: [PatQ] -> BodyQ -> [DecQ] -> ClauseQ Source #

Use with funD

Expressions

dyn :: String -> ExpQ Source #

Dynamically binding a variable (unhygenic)

staticE :: ExpQ -> ExpQ Source #

staticE x = [| static x |]

lamE :: [PatQ] -> ExpQ -> ExpQ Source #

lam1E :: PatQ -> ExpQ -> ExpQ Source #

Single-arg lambda

letE :: [DecQ] -> ExpQ -> ExpQ Source #

recConE :: Name -> [Q (Name, Exp)] -> ExpQ Source #

recUpdE :: ExpQ -> [Q (Name, Exp)] -> ExpQ Source #

Ranges

Ranges with more indirection

Statements

parS :: [[StmtQ]] -> StmtQ Source #

Types

Type literals

Strictness

isStrict :: Q Strict Source #

Deprecated: Use bang. See https://ghc.haskell.org/trac/ghc/wiki/Migration/8.0. Example usage: 'bang noSourceUnpackedness sourceStrict'

notStrict :: Q Strict Source #

Deprecated: Use bang. See https://ghc.haskell.org/trac/ghc/wiki/Migration/8.0. Example usage: 'bang noSourceUnpackedness noSourceStrictness'

unpacked :: Q Strict Source #

Deprecated: Use bang. See https://ghc.haskell.org/trac/ghc/wiki/Migration/8.0. Example usage: 'bang sourceUnpack sourceStrict'

strictType :: Q Strict -> TypeQ -> StrictTypeQ Source #

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

varStrictType :: Name -> StrictTypeQ -> VarStrictTypeQ Source #

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

Class Contexts

classP :: Name -> [Q Type] -> Q Pred Source #

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

equalP :: TypeQ -> TypeQ -> PredQ Source #

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

Constructors

infixC :: Q (Bang, Type) -> Name -> Q (Bang, Type) -> ConQ Source #

Kinds

Type variable binders

Roles

Top Level Declarations

Data

valD :: PatQ -> BodyQ -> [DecQ] -> DecQ Source #

data DerivClause Source #

A single deriving clause at the end of a datatype.

Constructors

DerivClause (Maybe DerivStrategy) Cxt
{ deriving stock (Eq, Ord) }
Instances
Eq DerivClause # 
Instance details

Defined in Language.Haskell.TH.Syntax

Data DerivClause # 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

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

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

toConstr :: DerivClause -> Constr Source #

dataTypeOf :: DerivClause -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord DerivClause # 
Instance details

Defined in Language.Haskell.TH.Syntax

Show DerivClause # 
Instance details

Defined in Language.Haskell.TH.Syntax

Generic DerivClause # 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivClause :: Type -> Type Source #

type Rep DerivClause # 
Instance details

Defined in Language.Haskell.TH.Syntax

data DerivStrategy Source #

What the user explicitly requests when deriving an instance.

Constructors

StockStrategy

A "standard" derived instance

AnyclassStrategy
-XDeriveAnyClass
NewtypeStrategy
-XGeneralizedNewtypeDeriving
ViaStrategy Type
-XDerivingVia
Instances
Eq DerivStrategy # 
Instance details

Defined in Language.Haskell.TH.Syntax

Data DerivStrategy # 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

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

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

toConstr :: DerivStrategy -> Constr Source #

dataTypeOf :: DerivStrategy -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord DerivStrategy # 
Instance details

Defined in Language.Haskell.TH.Syntax

Show DerivStrategy # 
Instance details

Defined in Language.Haskell.TH.Syntax

Generic DerivStrategy # 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivStrategy :: Type -> Type Source #

type Rep DerivStrategy # 
Instance details

Defined in Language.Haskell.TH.Syntax

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

Class

classD :: CxtQ -> Name -> [TyVarBndr] -> [FunDep] -> [DecQ] -> DecQ Source #

data Overlap Source #

Varieties of allowed instance overlap.

Constructors

Overlappable

May be overlapped by more specific instances

Overlapping

May overlap a more general instance

Overlaps

Both Overlapping and Overlappable

Incoherent

Both Overlappable and Overlappable, and pick an arbitrary one if multiple choices are available.

Instances
Eq Overlap # 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

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

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

Data Overlap # 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

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

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

toConstr :: Overlap -> Constr Source #

dataTypeOf :: Overlap -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord Overlap # 
Instance details

Defined in Language.Haskell.TH.Syntax

Show Overlap # 
Instance details

Defined in Language.Haskell.TH.Syntax

Generic Overlap # 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Overlap :: Type -> Type Source #

type Rep Overlap # 
Instance details

Defined in Language.Haskell.TH.Syntax

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

Role annotations

Type Family / Data Family

Fixity

Foreign Function Interface (FFI)

Functional dependencies

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

Pragmas

Pattern Synonyms

patSynD :: Name -> PatSynArgsQ -> PatSynDirQ -> PatQ -> DecQ Source #

Pattern synonym declaration

patSynSigD :: Name -> TypeQ -> DecQ Source #

Pattern synonym type signature

Reify

thisModule :: Q Module Source #

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