| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Language.Ginger.AST
Synopsis
- newtype Identifier = Identifier {}
- isValidIdentifier :: Text -> Bool
- identifierLeadChars :: [Char]
- identifierChars :: [Char]
- newtype Encoded = Encoded {}
- data Template = Template {
- templateParent :: !(Maybe Text)
- templateBody :: !Statement
- data Block = Block {
- blockBody :: !Statement
- blockScoped :: !Scoped
- blockRequired :: !Required
- data SetTarget
- data Statement
- = PositionedS !SourcePosition !Statement
- | ImmediateS !Encoded
- | InterpolationS !Expr
- | CommentS !Text
- | ForS !(Maybe Identifier) !Identifier !Expr !(Maybe Expr) !Recursivity !Statement !(Maybe Statement)
- | IfS !Expr !Statement !(Maybe Statement)
- | MacroS !Identifier ![MacroArg] !Statement
- | CallS !Identifier ![Expr] ![(Identifier, Expr)] !Statement
- | FilterS !Identifier ![Expr] ![(Identifier, Expr)] !Statement
- | SetS !SetTarget !Expr
- | SetBlockS !SetTarget !Statement !(Maybe Expr)
- | IncludeS !Expr !IncludeMissingPolicy !IncludeContextPolicy
- | ImportS !Expr !(Maybe Identifier) !(Maybe [(Identifier, Maybe Identifier)]) !IncludeMissingPolicy !IncludeContextPolicy
- | BlockS !Identifier !Block
- | WithS ![(Identifier, Expr)] !Statement
- | GroupS ![Statement]
- data IncludeMissingPolicy
- data IncludeContextPolicy
- escapeComment :: Statement -> Statement
- arbitraryStatement :: Set Identifier -> Gen Statement
- class Boolish a where
- isNot :: Boolish a => a -> Bool
- data Scoped
- data Required
- data Recursivity
- type MacroArg = (Identifier, Maybe Expr)
- data Expr
- = PositionedE !SourcePosition !Expr
- | NoneE
- | BoolE !Bool
- | StringLitE !Text
- | IntLitE !Integer
- | FloatLitE !Double
- | StatementE !Statement
- | ListE !(Vector Expr)
- | DictE ![(Expr, Expr)]
- | UnaryE !UnaryOperator !Expr
- | BinaryE !BinaryOperator !Expr !Expr
- | SliceE !Expr !(Maybe Expr) !(Maybe Expr)
- | DotE !Expr !Identifier
- | IsE !Expr !Expr ![Expr] ![(Identifier, Expr)]
- | CallE !Expr ![Expr] ![(Identifier, Expr)]
- | FilterE !Expr !Expr ![Expr] ![(Identifier, Expr)]
- | TernaryE !Expr !Expr !Expr
- | VarE !Identifier
- pattern TrueE :: Expr
- pattern FalseE :: Expr
- arbitraryExpr :: Set Identifier -> Gen Expr
- data UnaryOperator
- pattern NotE :: Expr -> Expr
- pattern NegateE :: Expr -> Expr
- data BinaryOperator
- pattern PlusE :: Expr -> Expr -> Expr
- pattern MinusE :: Expr -> Expr -> Expr
- pattern DivE :: Expr -> Expr -> Expr
- pattern IntDivE :: Expr -> Expr -> Expr
- pattern ModE :: Expr -> Expr -> Expr
- pattern MulE :: Expr -> Expr -> Expr
- pattern PowerE :: Expr -> Expr -> Expr
- pattern EqualE :: Expr -> Expr -> Expr
- pattern NotEqualE :: Expr -> Expr -> Expr
- pattern GT_E :: Expr -> Expr -> Expr
- pattern GTE_E :: Expr -> Expr -> Expr
- pattern LT_E :: Expr -> Expr -> Expr
- pattern LTE_E :: Expr -> Expr -> Expr
- pattern AndE :: Expr -> Expr -> Expr
- pattern OrE :: Expr -> Expr -> Expr
- pattern InE :: Expr -> Expr -> Expr
- pattern IndexE :: Expr -> Expr -> Expr
- pattern ConcatE :: Expr -> Expr -> Expr
- fuelledList :: Gen a -> Gen [a]
- traverseS :: (Statement -> Statement) -> (Expr -> Expr) -> Statement -> Statement
- traverseE :: (Expr -> Expr) -> (Statement -> Statement) -> Expr -> Expr
Documentation
newtype Identifier Source #
Identifiers are used to represent variable names and object fields.
Constructors
| Identifier | |
Fields | |
Instances
isValidIdentifier :: Text -> Bool Source #
identifierLeadChars :: [Char] Source #
identifierChars :: [Char] Source #
Represents an encoded string value, as opposed to a raw (unencoded) string,
which we represent as a plain Text.
A template consists of an optional parent template (specified in the
source using the {% extends %} construct), and a body statement.
Constructors
| Template | |
Fields
| |
A block represents a section of a template that can be overridden in derived templates ("template inheritance").
Constructors
| Block | |
Fields
| |
Constructors
| SetVar !Identifier | |
| SetMutable !Identifier !Identifier |
Instances
| Show SetTarget Source # | |
| Eq SetTarget Source # | |
| Ord SetTarget Source # | |
| RenderSyntax SetTarget Source # | |
Defined in Language.Ginger.Render Methods renderSyntax :: SetTarget -> Builder Source # | |
A statement in the template language.
Constructors
| PositionedS !SourcePosition !Statement | Statement tagged with a source position |
| ImmediateS !Encoded | Bare text written in the template, outside of any curly braces |
| InterpolationS !Expr | An expression interpolation: |
| CommentS !Text | Comment: |
| ForS !(Maybe Identifier) !Identifier !Expr !(Maybe Expr) !Recursivity !Statement !(Maybe Statement) | @@ |
| IfS !Expr !Statement !(Maybe Statement) | {% if condition %}yes branch{% else %}no branch{% endif %} |
| MacroS !Identifier ![MacroArg] !Statement | {% macro name(args) %}body{% endmacro %} |
| CallS !Identifier ![Expr] ![(Identifier, Expr)] !Statement | {% call macroName(args) %}body{% endcall %} |
| FilterS !Identifier ![Expr] ![(Identifier, Expr)] !Statement | {% filter filterName(args, kwargs) %}body{% endfilter %} |
| SetS !SetTarget !Expr | {% set name=expr %} |
| SetBlockS !SetTarget !Statement !(Maybe Expr) | {% set name %}body{% endset %} |
| IncludeS !Expr !IncludeMissingPolicy !IncludeContextPolicy | {% include includee ignore missing with context %} |
| ImportS !Expr !(Maybe Identifier) !(Maybe [(Identifier, Maybe Identifier)]) !IncludeMissingPolicy !IncludeContextPolicy | {% import importee as localName item, other_item as other ignore missing with context %} |
| BlockS !Identifier !Block | {% block name with scope required %}body{% endblock %} |
| WithS ![(Identifier, Expr)] !Statement | {% with defs %}body{% endwith %} |
| GroupS ![Statement] | Group of statements; not parsed, but needed for combining statements sequentially. |
Instances
| Arbitrary Statement Source # | |
| Show Statement Source # | |
| Eq Statement Source # | |
| Ord Statement Source # | |
| RenderSyntax Statement Source # | |
Defined in Language.Ginger.Render Methods renderSyntax :: Statement -> Builder Source # | |
| Monad m => Eval m Statement Source # | |
data IncludeMissingPolicy Source #
Constructors
| RequireMissing | |
| IgnoreMissing |
Instances
data IncludeContextPolicy Source #
Constructors
| WithContext | |
| WithoutContext |
Instances
escapeComment :: Statement -> Statement Source #
Instances
| Arbitrary Scoped Source # | |
| Bounded Scoped Source # | |
| Enum Scoped Source # | |
Defined in Language.Ginger.AST | |
| Read Scoped Source # | |
| Show Scoped Source # | |
| Eq Scoped Source # | |
| Ord Scoped Source # | |
| Boolish Scoped Source # | |
| RenderSyntax Scoped Source # | |
Defined in Language.Ginger.Render Methods renderSyntax :: Scoped -> Builder Source # | |
Instances
| Arbitrary Required Source # | |
| Bounded Required Source # | |
| Enum Required Source # | |
Defined in Language.Ginger.AST | |
| Read Required Source # | |
| Show Required Source # | |
| Eq Required Source # | |
| Ord Required Source # | |
Defined in Language.Ginger.AST | |
| Boolish Required Source # | |
| RenderSyntax Required Source # | |
Defined in Language.Ginger.Render Methods renderSyntax :: Required -> Builder Source # | |
data Recursivity Source #
Constructors
| NotRecursive | |
| Recursive |
Instances
An expression. Expressions can occur in interpolations ({{ ... }}), and
in various places inside statements.
Constructors
| PositionedE !SourcePosition !Expr | |
| NoneE | |
| BoolE !Bool | |
| StringLitE !Text | |
| IntLitE !Integer | |
| FloatLitE !Double | |
| StatementE !Statement | |
| ListE !(Vector Expr) | |
| DictE ![(Expr, Expr)] | |
| UnaryE !UnaryOperator !Expr | @UnaryE op rhs |
| BinaryE !BinaryOperator !Expr !Expr | @BinaryE op lhs rhs |
| SliceE !Expr !(Maybe Expr) !(Maybe Expr) | @SliceE slicee start length |
| DotE !Expr !Identifier | @DotE lhs rhs |
| IsE !Expr !Expr ![Expr] ![(Identifier, Expr)] | IsE scrutinee test args kwargs |
| CallE !Expr ![Expr] ![(Identifier, Expr)] | CallE callee args kwargs |
| FilterE !Expr !Expr ![Expr] ![(Identifier, Expr)] | FilterE arg0 filter args kwargs |
| TernaryE !Expr !Expr !Expr | TernaryE cond yes no |
| VarE !Identifier |
arbitraryExpr :: Set Identifier -> Gen Expr Source #
data UnaryOperator Source #
Constructors
| UnopNot | |
| UnopNegate |
Instances
data BinaryOperator Source #
Constructors
| BinopPlus | |
| BinopMinus | |
| BinopDiv | |
| BinopIntDiv | |
| BinopMod | |
| BinopMul | |
| BinopPower | |
| BinopEqual | |
| BinopNotEqual | |
| BinopGT | |
| BinopGTE | |
| BinopLT | |
| BinopLTE | |
| BinopAnd | |
| BinopOr | |
| BinopIn | |
| BinopIndex | |
| BinopConcat |
Instances
fuelledList :: Gen a -> Gen [a] Source #