template-haskell-2.4.0.1

Portabilityportable
Stabilityexperimental
Maintainerlibraries@haskell.org

Language.Haskell.TH.Syntax

Description

Abstract syntax definitions for Template Haskell.

Synopsis

Documentation

class (Monad m, Functor m) => Quasi m whereSource

Methods

qNewName :: String -> m NameSource

qReport :: Bool -> String -> m ()Source

qRecover :: m a -> m a -> m aSource

qReify :: Name -> m InfoSource

qLocation :: m LocSource

qRunIO :: IO a -> m aSource

Instances

class Lift t whereSource

Methods

lift :: t -> Q ExpSource

Instances

Lift Bool 
Lift Char 
Lift Int 
Lift Integer 
Lift a => Lift [a] 
Lift a => Lift (Maybe a) 
(Lift a, Lift b) => Lift (Either a b) 
(Lift a, Lift b) => Lift (a, b) 
(Lift a, Lift b, Lift c) => Lift (a, b, c) 
(Lift a, Lift b, Lift c, Lift d) => Lift (a, b, c, d) 
(Lift a, Lift b, Lift c, Lift d, Lift e) => Lift (a, b, c, d, e) 
(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) => Lift (a, b, c, d, e, f) 
(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) => Lift (a, b, c, d, e, f, g) 

data Q a Source

Instances

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

recover :: Q a -> Q a -> Q aSource

reify :: Name -> Q InfoSource

reify looks up information about the Name

location :: Q LocSource

location gives you the Location at which this computation is spliced.

runIO :: IO a -> Q aSource

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 necesarily flushed when the compiler finishes running, so you should flush them yourself.

data NameIs Source

Constructors

Alone 
Applied 
Infix 

data Exp Source

The CompE constructor represents a list comprehension, and takes a [Stmt]. The result expression of the comprehension is the *last* of these, and should be a NoBindS. E.g. [ f x | x <- xs ] is represented by CompE [BindS (VarP x) (VarE xs), NoBindS (AppE (VarE f) (VarE x))]

Instances

data Kind Source

Constructors

StarK 
ArrowK Kind Kind 

type Cxt = [Pred]Source

data Match Source

Constructors

Match Pat Body [Dec] 

data Body Source

Constructors

GuardedB [(Guard, Exp)] 
NormalB Exp 

data Guard Source

Constructors

NormalG Exp 
PatG [Stmt] 

data Stmt Source

Constructors

BindS Pat Exp 
LetS [Dec] 
NoBindS Exp 
ParS [[Stmt]] 

returnQ :: a -> Q aSource

bindQ :: Q a -> (a -> Q b) -> Q bSource

sequenceQ :: [Q a] -> Q [a]Source