Safe Haskell | None |
---|---|
Language | Haskell2010 |
- terminalizers :: Qualifier -> [Rule t] -> Q [Dec]
- terminalizer :: Qualifier -> Rule t -> Q [Dec]
- terminalizeRuleExp :: Qualifier -> Rule t -> Q Exp
- ruleLookupMap :: Foldable c => c (Rule t) -> Q (Map RuleName Name)
- lookupName :: Map RuleName Name -> RuleName -> Name
- terminalizeSingleRule :: Qualifier -> Map RuleName Name -> Rule t -> Q Exp
- terminalizeProductAllowsZero :: Qualifier -> Map RuleName Name -> String -> [Rule t] -> Q (PatQ, ExpQ)
- prependList :: [a] -> NonEmpty a -> NonEmpty a
- appendList :: NonEmpty a -> [a] -> NonEmpty a
- terminalizeProductAtLeastOne :: Qualifier -> Map RuleName Name -> String -> [Rule t] -> Q (PatQ, ExpQ)
- terminalizeProductRule :: Map RuleName Name -> Rule t -> Q (Rule t, (Q Pat, Q Exp))
- atLeastOne :: Rule t -> Bool
Documentation
:: Qualifier | Qualifier for the module containing the data types created
from the |
-> [Rule t] | |
-> Q [Dec] |
For all the given rules and their ancestors, creates
declarations that reduce the rule and all its ancestors to
terminal symbols. Each rule gets a declaration named
t'RULE_NAME
where RULE_NAME
is the name of the rule. The
type of the declaration is either
Production a -> [(t, a)]
or
Production a -> NonEmpty (t, a)
where Production
is the production corresponding to the given
Rule
, t
is the terminal token type (often Char
), and a
is
arbitrary metadata about each token (often Loc
). NonEmpty
is
returned for productions that must always contain at least one
terminal symbol; for those that can be empty, Seq
is returned.
Example: Pinchot.Examples.Terminalize.
:: Qualifier | Qualifier for the module containing the data types created
from the |
-> Rule t | |
-> Q [Dec] |
For the given rule, creates declarations that reduce the rule
to terminal symbols. No ancestors are handled. Each rule gets a
declaration named t'RULE_NAME
where RULE_NAME
is the name of
the rule. The
type of the declaration is either
Production a -> [(t, a)]
or
Production a -> NonEmpty (t, a)
where Production
is the production corresponding to the given
Rule
, t
is the terminal token type (often Char
), and a
is
arbitrary metadata about each token (often Loc
). NonEmpty
is
returned for productions that must always contain at least one
terminal symbol; for those that can be empty, Seq
is returned.
terminalizeRuleExp :: Qualifier -> Rule t -> Q Exp Source #
For the given rule, returns an expression that has type of either
Production a -> [(t, a)]
or
Production a -> NonEmpty (t, a)
where Production
is the production corresponding to the given
Rule
, and t
is the terminal token type. NonEmpty
is
returned for productions that must always contain at least one
terminal symbol; for those that can be empty, Seq
is returned.
Example: terminalizeAddress
.
terminalizeSingleRule Source #
:: Qualifier | Module qualifier for module containing the generated types
corresponding to all |
-> Map RuleName Name | For a given Rule, looks up the name of the expression that will terminalize that rule. |
-> Rule t | |
-> Q Exp |
For the given rule, returns an expression that has type of either
Production a -> [(t, a)]
or
Production a -> NonEmpty (t, a)
where Production
is the production corresponding to the given
Rule
, and t
is the terminal token type. NonEmpty
is
returned for productions that must always contain at least one
terminal symbol; for those that can be empty, Seq
is returned.
Gets no ancestors.
prependList :: [a] -> NonEmpty a -> NonEmpty a Source #
appendList :: NonEmpty a -> [a] -> NonEmpty a Source #
Examines a rule to determine whether when terminalizing it will always return at least one terminal symbol.