haskell-tools-ast-0.2.0.0: Haskell AST for efficient tooling

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Tools.AST.TH

Description

Representation of Template Haskell AST elements

Synopsis

Documentation

data Splice dom stage Source #

A template haskell splice

Constructors

IdSplice

A simple name splice: $generateX

Fields

ParenSplice

A splice with parentheses: $(generate input)

Fields

Instances

type Rep (Splice dom stage) Source # 
type Rep (Splice dom stage) = D1 (MetaData "Splice" "Language.Haskell.Tools.AST.TH" "haskell-tools-ast-0.2.0.0-5y5XIph7fmGIUhHQZ35OfD" False) ((:+:) (C1 (MetaCons "IdSplice" PrefixI True) (S1 (MetaSel (Just Symbol "_spliceId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann Name dom stage)))) (C1 (MetaCons "ParenSplice" PrefixI True) (S1 (MetaSel (Just Symbol "_spliceExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann Expr dom stage)))))

data QuasiQuote dom stage Source #

Template haskell quasi-quotation: [quoter|str]

Constructors

QuasiQuote 

Fields

Instances

type Rep (QuasiQuote dom stage) Source # 
type Rep (QuasiQuote dom stage) = D1 (MetaData "QuasiQuote" "Language.Haskell.Tools.AST.TH" "haskell-tools-ast-0.2.0.0-5y5XIph7fmGIUhHQZ35OfD" False) (C1 (MetaCons "QuasiQuote" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_qqExprName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann Name dom stage))) (S1 (MetaSel (Just Symbol "_qqExprBody") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann QQString dom stage)))))

data QQString dom stage Source #

Template Haskell Quasi-quotation content

Constructors

QQString 

Fields

Instances

type Rep (QQString dom stage) Source # 
type Rep (QQString dom stage) = D1 (MetaData "QQString" "Language.Haskell.Tools.AST.TH" "haskell-tools-ast-0.2.0.0-5y5XIph7fmGIUhHQZ35OfD" False) (C1 (MetaCons "QQString" PrefixI True) (S1 (MetaSel (Just Symbol "_qqString") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

data Bracket dom stage Source #

Template Haskell bracket expressions

Constructors

ExprBracket

Expression bracket ( [| x + y |] )

Fields

PatternBracket

Pattern bracket ( [| Point x y |] )

Fields

TypeBracket

Pattern bracket ( [| (Int,Int) |] )

Fields

DeclsBracket

Declaration bracket ( [| _f :: Int -> Int; f x = x*x |] )

Fields

Instances

type Rep (Bracket dom stage) Source # 
type Rep (Bracket dom stage) = D1 (MetaData "Bracket" "Language.Haskell.Tools.AST.TH" "haskell-tools-ast-0.2.0.0-5y5XIph7fmGIUhHQZ35OfD" False) ((:+:) ((:+:) (C1 (MetaCons "ExprBracket" PrefixI True) (S1 (MetaSel (Just Symbol "_bracketExpr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann Expr dom stage)))) (C1 (MetaCons "PatternBracket" PrefixI True) (S1 (MetaSel (Just Symbol "_bracketPattern") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann Pattern dom stage))))) ((:+:) (C1 (MetaCons "TypeBracket" PrefixI True) (S1 (MetaSel (Just Symbol "_bracketType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Ann Type dom stage)))) (C1 (MetaCons "DeclsBracket" PrefixI True) (S1 (MetaSel (Just Symbol "_bracketDecl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (AnnList Decl dom stage))))))