template-haskell-2.2.0.0

Language.Haskell.TH

Synopsis

Documentation

data Q a Source

Instances

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

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

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

reify :: Name -> Q Info Source

reify looks up information about the Name

currentModule :: Q String Source

currentModule gives you the name of the module in 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 Name Source

Instances

mkName :: String -> Name Source

newName :: String -> Q Name Source

nameBase :: Name -> String Source

nameModule :: Name -> Maybe String Source

tupleTypeName :: Int -> Name Source

tupleDataName :: Int -> Name Source

data Dec Source

Constructors

Instances

data Exp Source

Constructors

TupE [Exp]
DoE [Stmt]

Instances

data Con Source

Constructors

Instances

data Type Source

Constructors

Instances

type Cxt = [Type]Source

data Match Source

Constructors

Instances

data Clause Source

Constructors

Instances

data Body Source

Constructors

Instances

data Guard Source

Constructors

Instances

data Stmt Source

Constructors

LetS [Dec]
ParS [[Stmt]]

Instances

data Range Source

Constructors

Instances

data Lit Source

Constructors

Instances

data Pat Source

Constructors

TupP [Pat]

Instances

type FieldExp = (Name, Exp)Source

type FieldPat = (Name, Pat)Source

data Strict Source

Constructors

Instances

data Foreign Source

Constructors

Instances

data Callconv Source

Constructors

Instances

data Safety Source

Constructors

Instances

data FunDep Source

Constructors

Instances

data Info Source

Constructors

Instances

data Fixity Source

Constructors

Instances

data FixityDirection Source

Constructors

Instances

defaultFixity :: Fixity Source

maxPrecedence :: Int Source

type InfoQ = Q Info Source

type ExpQ = Q Exp Source

type DecQ = Q Dec Source

type ConQ = Q Con Source

type TypeQ = Q Type Source

type CxtQ = Q Cxt Source

type MatchQ = Q Match Source

type ClauseQ = Q Clause Source

type BodyQ = Q Body Source

type GuardQ = Q Guard Source

type StmtQ = Q Stmt Source

type RangeQ = Q Range Source

type StrictTypeQ = Q StrictType Source

type VarStrictTypeQ = Q VarStrictType Source

type PatQ = Q Pat Source

type FieldPatQ = Q FieldPat Source

intPrimL :: Integer -> Lit Source

floatPrimL :: Rational -> Lit Source

doublePrimL :: Rational -> Lit Source

integerL :: Integer -> Lit Source

charL :: Char -> Lit Source

stringL :: String -> Lit Source

rationalL :: Rational -> Lit Source

litP :: Lit -> PatQ Source

varP :: Name -> PatQ Source

tupP :: [PatQ] -> PatQ Source

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

infixP :: PatQ -> Name -> PatQ -> PatQ Source

tildeP :: PatQ -> PatQ Source

asP :: Name -> PatQ -> PatQ Source

wildP :: PatQ Source

recP :: Name -> [FieldPatQ] -> PatQ Source

listP :: [PatQ] -> PatQ Source

sigP :: PatQ -> TypeQ -> PatQ Source

fieldPat :: Name -> PatQ -> FieldPatQ Source

bindS :: PatQ -> ExpQ -> StmtQ Source

letS :: [DecQ] -> StmtQ Source

noBindS :: ExpQ -> StmtQ Source

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

fromR :: ExpQ -> RangeQ Source

fromThenR :: ExpQ -> ExpQ -> RangeQ Source

fromToR :: ExpQ -> ExpQ -> RangeQ Source

fromThenToR :: ExpQ -> ExpQ -> ExpQ -> RangeQ Source

normalB :: ExpQ -> BodyQ Source

guardedB :: [Q (Guard, Exp)] -> BodyQ Source

normalG :: ExpQ -> GuardQ Source

normalGE :: ExpQ -> ExpQ -> Q (Guard, Exp)Source

patG :: [StmtQ] -> GuardQ Source

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

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

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

dyn :: String -> Q Exp Source

global :: Name -> ExpQ Source

varE :: Name -> ExpQ Source

conE :: Name -> ExpQ Source

litE :: Lit -> ExpQ Source

appE :: ExpQ -> ExpQ -> ExpQ Source

infixE :: Maybe ExpQ -> ExpQ -> Maybe ExpQ -> ExpQ Source

infixApp :: ExpQ -> ExpQ -> ExpQ -> ExpQ Source

sectionL :: ExpQ -> ExpQ -> ExpQ Source

sectionR :: ExpQ -> ExpQ -> ExpQ Source

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

lam1E :: PatQ -> ExpQ -> ExpQ Source

tupE :: [ExpQ] -> ExpQ Source

condE :: ExpQ -> ExpQ -> ExpQ -> ExpQ Source

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

caseE :: ExpQ -> [MatchQ] -> ExpQ Source

doE :: [StmtQ] -> ExpQ Source

compE :: [StmtQ] -> ExpQ Source

arithSeqE :: RangeQ -> ExpQ Source

appsE :: [ExpQ] -> ExpQ Source

fromE :: ExpQ -> ExpQ Source

fromThenE :: ExpQ -> ExpQ -> ExpQ Source

fromToE :: ExpQ -> ExpQ -> ExpQ Source

fromThenToE :: ExpQ -> ExpQ -> ExpQ -> ExpQ Source

listE :: [ExpQ] -> ExpQ Source

sigE :: ExpQ -> TypeQ -> ExpQ Source

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

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

stringE :: String -> ExpQ Source

fieldExp :: Name -> ExpQ -> Q (Name, Exp)Source

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

funD :: Name -> [ClauseQ] -> DecQ Source

tySynD :: Name -> [Name] -> TypeQ -> DecQ Source

dataD :: CxtQ -> Name -> [Name] -> [ConQ] -> [Name] -> DecQ Source

newtypeD :: CxtQ -> Name -> [Name] -> ConQ -> [Name] -> DecQ Source

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

instanceD :: CxtQ -> TypeQ -> [DecQ] -> DecQ Source

sigD :: Name -> TypeQ -> DecQ Source

forImpD :: Callconv -> Safety -> String -> Name -> TypeQ -> DecQ Source

cxt :: [TypeQ] -> CxtQ Source

normalC :: Name -> [StrictTypeQ] -> ConQ Source

recC :: Name -> [VarStrictTypeQ] -> ConQ Source

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

forallT :: [Name] -> CxtQ -> TypeQ -> TypeQ Source

varT :: Name -> TypeQ Source

conT :: Name -> TypeQ Source

appT :: TypeQ -> TypeQ -> TypeQ Source

arrowT :: TypeQ Source

listT :: TypeQ Source

tupleT :: Int -> TypeQ Source

isStrict :: Q Strict Source

notStrict :: Q Strict Source

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

varStrictType :: Name -> StrictTypeQ -> VarStrictTypeQ Source

cCall :: Callconv Source

stdCall :: Callconv Source

unsafe :: Safety Source

safe :: Safety Source

threadsafe :: Safety Source

class Ppr a whereSource

Methods

ppr :: a -> Doc Source

ppr_list :: [a] -> Doc Source

Instances

pprint :: Ppr a => a -> String Source

pprExp :: Precedence -> Exp -> Doc Source

pprLit :: Precedence -> Lit -> Doc Source

pprPat :: Precedence -> Pat -> Doc Source

pprParendType :: Type -> Doc Source

AltStyle によって変換されたページ (->オリジナル) /