Copyright | Copyright 2017 Awake Security |
---|---|
License | Apache-2.0 |
Maintainer | opensource@awakesecurity.com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
This module contains a type representing a string that potentially contains variable references in the parsed Ninja AST, along with any supporting or related types.
Since: 0.1.0
- data Expr ann
- _Exprs :: Prism' (Expr ann) (ann, [Expr ann])
- _Lit :: Prism' (Expr ann) (ann, Text)
- _Var :: Prism' (Expr ann) (ann, Text)
- askVar :: Env Text Text -> Text -> Text
- askExpr :: Env Text Text -> Expr ann -> Text
- addBind :: Text -> Expr ann -> Env Text Text -> Env Text Text
- addBinds :: [(Text, Expr ann)] -> Env Text Text -> Env Text Text
- normalizeExpr :: forall ann. Monoid ann => Expr ann -> Expr ann
- type ExprConstraint c ann = (c Text, c ann)
Expr
An expression containing variable references in the Ninja language.
Since: 0.1.0
Exprs !ann ![Expr ann] | Sequencing of expressions. Since: 0.1.0 |
Lit !ann !Text | A literal string. Since: 0.1.0 |
Var !ann !Text | A variable reference. Since: 0.1.0 |
Functor Expr Source # | |
Foldable Expr Source # | |
Traversable Expr Source # | |
Annotated Expr Source # | The usual definition for Since: 0.1.0 |
(Monad m, ExprConstraint (Serial m) ann) => Serial m (Expr ann) Source # | Default Since: 0.1.0 |
(Monad m, ExprConstraint (CoSerial m) ann) => CoSerial m (Expr ann) Source # | Default Since: 0.1.0 |
Eq ann => Eq (Expr ann) Source # | |
Data ann => Data (Expr ann) Source # | |
Show ann => Show (Expr ann) Source # | |
Generic (Expr ann) Source # | |
(Arbitrary ann, ExprConstraint Arbitrary ann) => Arbitrary (Expr ann) Source # | Reasonable Since: 0.2.0 |
Hashable ann => Hashable (Expr ann) Source # | Default Since: 0.1.0 |
ToJSON ann => ToJSON (Expr ann) Source # | Converts Since: 0.1.0 |
FromJSON ann => FromJSON (Expr ann) Source # | Inverse of the Since: 0.1.0 |
NFData ann => NFData (Expr ann) Source # | Default Since: 0.1.0 |
Data ann => Plated (Expr ann) Source # | The usual definition for Since: 0.1.0 |
type Rep (Expr ann) Source # | |
_Exprs :: Prism' (Expr ann) (ann, [Expr ann]) Source #
A prism for the Exprs
constructor.
Since: 0.1.0
askVar :: Env Text Text -> Text -> Text Source #
Look up the given variable in the given context, returning the empty string if the variable was not found.
Since: 0.1.0
addBinds :: [(Text, Expr ann)] -> Env Text Text -> Env Text Text Source #
Add bindings from a list. Note that this function evaluates all the right-hand-sides first, and then adds them all to the environment.
For example:
>>>
:set -XOverloadedStrings
>>>
let binds = [("x", Lit () "5"), ("y", Var () "x")]
>>>
AST.headEnv (addBinds binds AST.makeEnv)
fromList [("x","5"),("y","")]
Since: 0.1.0
normalizeExpr :: forall ann. Monoid ann => Expr ann -> Expr ann Source #
Normalize an Expr
by recursively flattening any Exprs
nodes, removing
empty Lit
nodes, combining adjacent Lit
nodes, and pulling out the
interior of the top-level Exprs
node if it has only one subnode.
The number of Exprs
nodes in the output is guaranteed to be 0 or 1.
If it is 0, then there is exactly one node of any type in the output.
The output is thus isomorphic to (Maybe ann, [(ann, Either Text Text)])
,
where the Maybe ann
represents the annotation of the top-level Exprs
node if it exists.
Since: 0.1.0
type ExprConstraint c ann = (c Text, c ann) Source #
The set of constraints required for a given constraint to be automatically
computed for a Expr
.
Since: 0.1.0