Haskell Core Libraries (haskell-src package)ParentContentsIndex
Language.Haskell.THSyntax
Portability portable
Stability experimental
Maintainer libraries@haskell.org
Description
Abstract syntax definitions for Template Haskell.
newtype Q a
Constructors
Q (IO a)
Instances
Monad Q
qIO :: IO a -> Q a
runQ :: Q a -> IO a
returnQ :: a -> Q a
bindQ :: Q a -> (a -> Q b) -> Q b
sequenceQ :: [Q a] -> Q [a]
counter :: IORef Int
gensym :: String -> Q String
class Lift t where
Methods
lift :: t -> ExpQ
Instances
Lift Integer
Lift Int
Lift Char
(Lift a) => Lift [a]
data Lit
Constructors
Char Char
String String
Integer Integer
IntPrim Integer
FloatPrim Rational
DoublePrim Rational
Rational Rational
Instances
Show Lit
data Pat
Constructors
Plit Lit
Pvar String
Ptup [Pat]
Pcon String [Pat]
Ptilde Pat
Paspat String Pat
Pwild
Prec String [FieldPat]
Instances
Show Pat
type FieldPat = (String, Pat)
data Match
Constructors
Match Pat RightHandSide [Dec]
Instances
Show Match
data Clause
Constructors
Clause [Pat] RightHandSide [Dec]
Instances
Show Clause
data Exp
Constructors
Var String
Con String
Lit Lit
App Exp Exp
Infix (Maybe Exp) Exp (Maybe Exp)
Lam [Pat] Exp
Tup [Exp]
Cond Exp Exp Exp
Let [Dec] Exp
Case Exp [Match]
Do [Statement]
Comp [Statement]
ArithSeq DotDot
ListExp [Exp]
SigExp Exp Typ
RecCon String [FieldExp]
RecUpd Exp [FieldExp]
Instances
Show Exp
type FieldExp = (String, Exp)
data RightHandSide
Constructors
Guarded [(Exp, Exp)]
Normal Exp
Instances
Show RightHandSide
data Statement
Constructors
BindSt Pat Exp
LetSt [Dec]
NoBindSt Exp
ParSt [[Statement]]
Instances
Show Statement
data DotDot
Constructors
From Exp
FromThen Exp Exp
FromTo Exp Exp
FromThenTo Exp Exp Exp
Instances
Show DotDot
data Dec
Constructors
Fun String [Clause]
Val Pat RightHandSide [Dec]
Data Cxt String [String] [Con] [String]
Newtype Cxt String [String] Con [String]
TySyn String [String] Typ
Class Cxt String [String] [Dec]
Instance Cxt Typ [Dec]
Proto String Typ
Foreign Foreign
Instances
Show Dec
data Foreign
Constructors
Import Callconv Safety String String Typ
Instances
Show Foreign
data Callconv
Constructors
CCall
StdCall
Instances
Show Callconv
data Safety
Constructors
Unsafe
Safe
Threadsafe
Instances
Show Safety
type Cxt = [Typ]
data Strictness
Constructors
Strict
NonStrict
Instances
Show Strictness
data Con
Constructors
Constr String [(Strictness, Typ)]
RecConstr String [(String, Strictness, Typ)]
InfixConstr (Strictness, Typ) String (Strictness, Typ)
Instances
Show Con
type StrType = Q (Strictness, Typ)
type VarStrType = Q (String, Strictness, Typ)
data Program
Constructors
Program [Dec]
Instances
Show Program
data Tag
Constructors
Tuple Int
Arrow
List
TconName String
Instances
Eq Tag
Show Tag
data Typ
Constructors
TForall [String] Cxt Typ
Tvar String
Tcon Tag
Tapp Typ Typ
Instances
Show Typ
type ExpQ = Q Exp
type DecQ = Q Dec
type ConQ = Q Con
type TypQ = Q Typ
type CxtQ = Q Cxt
type MatchQ = Q Match
type ClauseQ = Q Clause
type RightHandSideQ = Q RightHandSide
type StatementQ = Q Statement
type DotDotQ = Q DotDot
fieldPat :: String -> Pat -> (String, Pat)
bindSt :: Pat -> ExpQ -> StatementQ
letSt :: [DecQ] -> StatementQ
noBindSt :: ExpQ -> StatementQ
parSt :: [[StatementQ]] -> StatementQ
normal :: ExpQ -> RightHandSideQ
guarded :: [(ExpQ, ExpQ)] -> RightHandSideQ
match :: Pat -> RightHandSideQ -> [DecQ] -> MatchQ
clause :: [Pat] -> RightHandSideQ -> [DecQ] -> ClauseQ
global :: String -> ExpQ
var :: String -> ExpQ
con :: String -> ExpQ
lit :: Lit -> ExpQ
app :: ExpQ -> ExpQ -> ExpQ
infixE :: Maybe ExpQ -> ExpQ -> Maybe ExpQ -> ExpQ
from :: ExpQ -> ExpQ
fromThen :: ExpQ -> ExpQ -> ExpQ
fromTo :: ExpQ -> ExpQ -> ExpQ
fromThenTo :: ExpQ -> ExpQ -> ExpQ -> ExpQ
lam :: [Pat] -> ExpQ -> ExpQ
lam1 :: Pat -> ExpQ -> ExpQ
tup :: [ExpQ] -> ExpQ
cond :: ExpQ -> ExpQ -> ExpQ -> ExpQ
letE :: [DecQ] -> ExpQ -> ExpQ
caseE :: ExpQ -> [MatchQ] -> ExpQ
doE :: [StatementQ] -> ExpQ
comp :: [StatementQ] -> ExpQ
listExp :: [ExpQ] -> ExpQ
sigExp :: ExpQ -> TypQ -> ExpQ
recCon :: String -> [Q (String, Exp)] -> ExpQ
recUpd :: ExpQ -> [Q (String, Exp)] -> ExpQ
string :: String -> ExpQ
fieldExp :: String -> ExpQ -> Q (String, Exp)
val :: Pat -> RightHandSideQ -> [DecQ] -> DecQ
fun :: String -> [ClauseQ] -> DecQ
tySynD :: String -> [String] -> TypQ -> DecQ
dataD :: CxtQ -> String -> [String] -> [ConQ] -> [String] -> DecQ
newtypeD :: CxtQ -> String -> [String] -> ConQ -> [String] -> DecQ
classD :: CxtQ -> String -> [String] -> [DecQ] -> DecQ
inst :: CxtQ -> TypQ -> [DecQ] -> DecQ
proto :: String -> TypQ -> DecQ
cxt :: [TypQ] -> CxtQ
constr :: String -> [Q (Strictness, Typ)] -> ConQ
recConstr :: String -> [Q (String, Strictness, Typ)] -> ConQ
infixConstr :: Q (Strictness, Typ) -> String -> Q (Strictness, Typ) -> ConQ
tforall :: [String] -> CxtQ -> TypQ -> TypQ
tvar :: String -> TypQ
tcon :: Tag -> TypQ
tapp :: TypQ -> TypQ -> TypQ
arrowTyCon :: TypQ
listTyCon :: TypQ
tupleTyCon :: Int -> TypQ
namedTyCon :: String -> TypQ
strict :: Q Strictness
nonstrict :: Q Strictness
strictType :: Q Strictness -> TypQ -> Q (Strictness, Typ)
varStrictType :: String -> Q (Strictness, Typ) -> Q (String, Strictness, Typ)
apps :: [ExpQ] -> ExpQ
simpleM :: Pat -> Exp -> Match
nestDepth :: Int
type Precedence = Int
appPrec :: Precedence
opPrec :: Precedence
noPrec :: Precedence
parensIf :: Bool -> Doc -> Doc
pprExp :: Exp -> Doc
pprExpI :: Precedence -> Exp -> Doc
pprFields :: [(String, Exp)] -> Doc
pprMaybeExp :: Precedence -> Maybe Exp -> Doc
pprStatement :: Statement -> Doc
pprMatch :: Match -> Doc
pprRhs :: Bool -> RightHandSide -> Doc
pprLit :: Precedence -> Lit -> Doc
pprPat :: Pat -> Doc
pprPatI :: Precedence -> Pat -> Doc
pprDec :: Dec -> Doc
pprForeign :: Foreign -> Doc
pprClause :: Clause -> Doc
pprCon :: Con -> Doc
pprVarStrictTyp :: (String, Strictness, Typ) -> Doc
pprStrictTyp :: (Strictness, Typ) -> Doc
pprParendTyp :: Typ -> Doc
pprTyp :: Typ -> Doc
pprTcon :: Tag -> Doc
split :: Typ -> (Typ, [Typ])
pprCxt :: Cxt -> Doc
pprDotDot :: DotDot -> Doc
pprDotDotI :: DotDot -> Doc
where_clause :: [Dec] -> Doc
showtextl :: (Show a) => a -> Doc
Produced by Haddock version 0.4