Safe Haskell | None |
---|---|
Language | Haskell2010 |
Implements Ginger's Abstract Syntax Tree.
Synopsis
- type VarName = Text
- data Template a = Template {
- templateBody :: Statement a
- templateBlocks :: HashMap VarName (Block a)
- templateParent :: Maybe (Template a)
- data Macro a = Macro {}
- data Block a = Block {}
- data Statement a
- = MultiS a [Statement a]
- | ScopedS a (Statement a)
- | IndentS a (Expression a) (Statement a)
- | LiteralS a Html
- | InterpolationS a (Expression a)
- | ExpressionS a (Expression a)
- | IfS a (Expression a) (Statement a) (Statement a)
- | SwitchS a (Expression a) [(Expression a, Statement a)] (Statement a)
- | ForS a (Maybe VarName) VarName (Expression a) (Statement a)
- | SetVarS a VarName (Expression a)
- | DefMacroS a VarName (Macro a)
- | BlockRefS a VarName
- | PreprocessedIncludeS a (Template a)
- | NullS a
- | TryCatchS a (Statement a) [CatchBlock a] (Statement a)
- stmtAnnotation :: Statement p -> p
- data CatchBlock a = Catch {}
- data Expression a
- = StringLiteralE a Text
- | NumberLiteralE a Scientific
- | BoolLiteralE a Bool
- | NullLiteralE a
- | VarE a VarName
- | ListE a [Expression a]
- | ObjectE a [(Expression a, Expression a)]
- | MemberLookupE a (Expression a) (Expression a)
- | CallE a (Expression a) [(Maybe Text, Expression a)]
- | LambdaE a [Text] (Expression a)
- | TernaryE a (Expression a) (Expression a) (Expression a)
- | DoE a (Statement a)
- exprAnnotation :: Expression p -> p
- class Annotated f where
- annotation :: f p -> p
Documentation
Top-level data structure, representing a fully parsed template.
Template | |
|
A macro definition ( {% macro %}
)
A block definition ( {% block %}
)
Ginger statements.
MultiS a [Statement a] | A sequence of multiple statements |
ScopedS a (Statement a) | Run wrapped statement in a local scope |
IndentS a (Expression a) (Statement a) | Establish an indented context around the wrapped statement |
LiteralS a Html | Literal output (anything outside of any tag) |
InterpolationS a (Expression a) | {{ expression }} |
ExpressionS a (Expression a) | Evaluate expression |
IfS a (Expression a) (Statement a) (Statement a) | {% if expression %}statement{% else %}statement{% endif %} |
SwitchS a (Expression a) [(Expression a, Statement a)] (Statement a) | {% switch expression %}{% case expression %}statement{% endcase %}...{% default %}statement{% enddefault %}{% endswitch %} |
ForS a (Maybe VarName) VarName (Expression a) (Statement a) | {% for index, varname in expression %}statement{% endfor %} |
SetVarS a VarName (Expression a) | {% set varname = expr %} |
DefMacroS a VarName (Macro a) | {% macro varname %}statements{% endmacro %} |
BlockRefS a VarName | |
PreprocessedIncludeS a (Template a) | {% include "template" %} |
NullS a | The do-nothing statement (NOP) |
TryCatchS a (Statement a) [CatchBlock a] (Statement a) | Try catch finally |
stmtAnnotation :: Statement p -> p Source #
data CatchBlock a Source #
A catch
block
Instances
Functor CatchBlock Source # | |
Defined in Text.Ginger.AST fmap :: (a -> b) -> CatchBlock a -> CatchBlock b # (<$) :: a -> CatchBlock b -> CatchBlock a # | |
Show a => Show (CatchBlock a) Source # | |
Defined in Text.Ginger.AST showsPrec :: Int -> CatchBlock a -> ShowS # show :: CatchBlock a -> String # showList :: [CatchBlock a] -> ShowS # |
data Expression a Source #
Expressions, building blocks for the expression minilanguage.
StringLiteralE a Text | String literal expression: "foobar" |
NumberLiteralE a Scientific | Numeric literal expression: 123.4 |
BoolLiteralE a Bool | Boolean literal expression: true |
NullLiteralE a | Literal null |
VarE a VarName | Variable reference: foobar |
ListE a [Expression a] | List construct: [ expr, expr, expr ] |
ObjectE a [(Expression a, Expression a)] | Object construct: { expr: expr, expr: expr, ... } |
MemberLookupE a (Expression a) (Expression a) | foo[bar] (also dot access) |
CallE a (Expression a) [(Maybe Text, Expression a)] | foo(bar=baz, quux) |
LambdaE a [Text] (Expression a) | (foo, bar) -> expr |
TernaryE a (Expression a) (Expression a) (Expression a) | expr ? expr : expr |
DoE a (Statement a) | do { statement; } |
Instances
Functor Expression Source # | |
Defined in Text.Ginger.AST fmap :: (a -> b) -> Expression a -> Expression b # (<$) :: a -> Expression b -> Expression a # | |
Annotated Expression Source # | |
Defined in Text.Ginger.AST annotation :: Expression p -> p Source # | |
Show a => Show (Expression a) Source # | |
Defined in Text.Ginger.AST showsPrec :: Int -> Expression a -> ShowS # show :: Expression a -> String # showList :: [Expression a] -> ShowS # | |
Optimizable (Expression a) Source # | |
Defined in Text.Ginger.Optimizer optimize :: Expression a -> Expression a Source # |
exprAnnotation :: Expression p -> p Source #
class Annotated f where Source #
annotation :: f p -> p Source #
Instances
Annotated Expression Source # | |
Defined in Text.Ginger.AST annotation :: Expression p -> p Source # | |
Annotated Statement Source # | |
Defined in Text.Ginger.AST annotation :: Statement p -> p Source # | |
Annotated Block Source # | |
Defined in Text.Ginger.AST annotation :: Block p -> p Source # | |
Annotated Macro Source # | |
Defined in Text.Ginger.AST annotation :: Macro p -> p Source # | |
Annotated Template Source # | |
Defined in Text.Ginger.AST annotation :: Template p -> p Source # |