| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Pinchot.Rules
- label :: Rule t -> String -> Rule t
- (<?>) :: Rule t -> String -> Rule t
- rule :: RuleName -> RuleType t -> Rule t
- terminal :: RuleName -> Q (TExp (t -> Bool)) -> Rule t
- nonTerminal :: RuleName -> [(BranchName, [Rule t])] -> Rule t
- union :: RuleName -> [Rule t] -> Rule t
- series :: RuleName -> [t] -> Rule t
- wrap :: RuleName -> Rule t -> Rule t
- record :: RuleName -> [Rule t] -> Rule t
- opt :: Rule t -> Rule t
- star :: Rule t -> Rule t
- plus :: Rule t -> Rule t
- getAncestors :: Rule t -> State (Set RuleName) [Rule t]
- family :: Rule t -> [Rule t]
- families :: [Rule t] -> [Rule t]
Documentation
label :: Rule t -> String -> Rule t Source #
Name a Rule for use in error messages. If you do not name a
rule using this combinator, the rule's type name will be used in
error messages.
Arguments
| :: RuleName | |
| -> Q (TExp (t -> Bool)) | Valid terminal symbols. This is a typed Template Haskell expression. To use it, make sure you have {-# LANGUAGE TemplateHaskell #-}at the top of your module, and then use the Template Haskell quotes, like this: terminal "AtoZ" [|| (\c -> c >= 'A' && c <= 'Z') ||] |
| -> Rule t |
Creates a terminal production rule. Example:
rLetter.
Arguments
| :: RuleName | Will be used for the name of the resulting type |
| -> [(BranchName, [Rule t])] | Branches of the non-terminal production rule. This list must have at least one element; otherwise, an error will result. |
| -> Rule t |
Creates a non-terminal production rule. This is the most
flexible way to create non-terminals. You can even create a
non-terminal that depends on itself. Example:
rLetters.
Arguments
| :: RuleName | Will be used for the name of the resulting type |
| -> [Rule t] | List of branches. There must be at least one branch; otherwise a compile-time error will occur. |
| -> Rule t |
Creates a non-terminal production rule where each branch has
only one production. This function ultimately uses
nonTerminal. Each branch is assigned a BranchName that is
RULE_NAME'PRODUCTION_NAME
where RULE_NAME is the name of the rule itself, and
PRODUCTION_NAME is the rule name for what is being produced.
Example: rDirection.
Arguments
| :: RuleName | Will be used for the name of the resulting type, and for the name of the sole data constructor |
| -> [t] | The list of tokens to use. This must have at least one item;
otherwise this function will apply |
| -> Rule t |
Creates a production for a sequence of terminals. Useful for
parsing specific words. When used with syntaxTrees, the
resulting data type is a newtype that wraps a , where NonEmpty
(t, a)t is the type of the token (often Char) and a
is an arbitrary metadata type.
Examples: rBoulevard.
Arguments
| :: RuleName | Will be used for the name of the resulting data type, and for the name of the sole data constructor |
| -> Rule t | |
| -> Rule t |
Creates a newtype wrapper. Example:
rCity.
Arguments
| :: RuleName | The name of this rule, which is used both as the type name and for the name of the sole data constructor |
| -> [Rule t] | The right-hand side of this rule. This sequence can be empty, which results in an epsilon production. |
| -> Rule t |
Creates a new non-terminal production rule with only one alternative where each field has a record name. The name of each record is:
_r'RULE_NAME'INDEX'FIELD_TYPE
where RULE_NAME is the name of this rule, INDEX is the index number
for this field (starting with 0), and FIELD_TYPE is the type of the
field itself.
Currently there is no way to change the names of the record fields.
Example: rAddress.
opt :: Rule t -> Rule t Source #
Creates a rule for a production that optionally produces another
rule. The name for the created Rule is the name of the Rule to
which this function is applied, with 'Opt appended to the end.
Example: rOptNewline.
star :: Rule t -> Rule t Source #
Creates a rule for the production of a sequence of other rules.
The name for the created Rule is the name of the Rule to which
this function is applied, with 'Star appended.
Example: rPreSpacedWord.
getAncestors :: Rule t -> State (Set RuleName) [Rule t] Source #
Gets all ancestor rules to this Rule. Includes the current
rule if it has not already been seen.