| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Pinchot.Internal
Description
Pinchot internals. Ordinarily the Pinchot module should have everything you need.
- type RuleName = String
- type AlternativeName = String
- data Branch t = Branch String (Seq (Rule t))
- data RuleType t
- data Rule t = Rule String (Maybe String) (RuleType t)
- label :: String -> Rule t -> Rule t
- (<?>) :: Pinchot t (Rule t) -> String -> Pinchot t (Rule t)
- data Names t = Names {}
- data Error
- newtype Pinchot t a = Pinchot {
- runPinchot :: ExceptT Error (State (Names t)) a
- goPinchot :: Pinchot t a -> Q (Names t, a)
- addRuleName :: RuleName -> Pinchot t ()
- addDataConName :: AlternativeName -> Pinchot t ()
- newRule :: RuleName -> RuleType t -> Pinchot t (Rule t)
- terminal :: RuleName -> Intervals t -> Pinchot t (Rule t)
- splitNonTerminal :: String -> Seq (String, Seq (Rule t)) -> Pinchot t ((String, Seq (Rule t)), Seq (String, Seq (Rule t)))
- terminalSeq :: RuleName -> Seq t -> Pinchot t (Rule t)
- nonTerminal :: RuleName -> Seq (AlternativeName, Seq (Rule t)) -> Pinchot t (Rule t)
- ruleConstructorNames :: Rule t -> Seq AlternativeName
- unionBranchName :: RuleName -> RuleName -> AlternativeName
- addDataConNames :: Rule t -> Pinchot t ()
- union :: RuleName -> Seq (Rule t) -> Pinchot t (Rule t)
- record :: RuleName -> Seq (Rule t) -> Pinchot t (Rule t)
- list :: Rule t -> Pinchot t (Rule t)
- list1 :: Rule t -> Pinchot t (Rule t)
- option :: Rule t -> Pinchot t (Rule t)
- wrap :: RuleName -> Rule t -> Pinchot t (Rule t)
- getAncestors :: Rule t -> State (Set String) (Seq (Rule t))
- ruleAndAncestors :: Rule t -> Seq (Rule t)
- rulesDemandedBeforeDefined :: Foldable f => f (Rule t) -> Set Name
- thBranch :: Branch t -> ConQ
- thUnionBranch :: RuleName -> Rule t -> ConQ
- thRule :: Lift t => Bool -> Name -> Seq Name -> Rule t -> Q [Dec]
- makeType :: Name -> Seq Name -> String -> RuleType t -> Q Dec
- fieldName :: Int -> String -> String -> String
- thAllRules :: Lift t => Bool -> Name -> Seq Name -> Map Int (Rule t) -> DecsQ
- makeWrapped :: Type -> String -> Dec
- dynP :: String -> PatQ
- seqTermToOptics :: Lift t => Name -> String -> Seq t -> Q [Dec]
- terminalToOptics :: Lift t => Name -> String -> Intervals t -> Q [Dec]
- optionalToOptics :: String -> String -> Dec
- many1ToOptics :: String -> String -> Dec
- manyToOptics :: String -> String -> Dec
- wrapToOptics :: String -> String -> Dec
- terminalSeqToOptics :: Name -> String -> Dec
- branchesToOptics :: String -> Branch t -> Seq (Branch t) -> [Dec]
- unionToOptics :: String -> Rule t -> Seq (Rule t) -> DecsQ
- recordsToOptics :: String -> Seq (Rule t) -> [Dec]
- ruleToOptics :: Lift t => Name -> String -> RuleType t -> DecsQ
- type MakeOptics = Bool
- makeOptics :: MakeOptics
- noOptics :: MakeOptics
- allRulesToTypes :: Lift t => MakeOptics -> Name -> Seq Name -> Pinchot t a -> DecsQ
- ruleTreeToTypes :: Lift t => MakeOptics -> Name -> Seq Name -> Pinchot t (Rule t) -> DecsQ
- addPrefix :: String -> String -> String
- ruleToParser :: Lift t => String -> Rule t -> [(Name, ExpQ)]
- constructorName :: String -> String -> ExpQ
- ruleName :: String -> Name
- helperName :: String -> Name
- branchToParser :: Lift t => String -> Branch t -> ExpQ
- lazyPattern :: Foldable c => c Name -> Q Pat
- bigTuple :: Foldable c => ExpQ -> c ExpQ -> ExpQ
- earleyGrammar :: Lift t => Qualifier -> Pinchot t (Rule t) -> Q Exp
- recursiveDo :: [(Name, ExpQ)] -> ExpQ -> ExpQ
- earleyGrammarFromRule :: Lift t => String -> Rule t -> Q Exp
- allEarleyGrammars :: Lift t => Qualifier -> Name -> Pinchot t a -> DecsQ
- prodDeclName :: String -> Name
- prodFn :: String -> ExpQ
- addIndices :: Foldable c => c a -> [(Int, a)]
- productionDecl :: String -> Name -> RuleType t -> DecsQ
- branchToClause :: Branch t -> ClauseQ
- type Qualifier = String
- allRulesRecord :: Qualifier -> Name -> Pinchot t a -> DecsQ
- earleyProduct :: Lift t => Qualifier -> Qualifier -> Pinchot t a -> ExpQ
Documentation
Type synonym for the name of a production rule. This will be the name of the type constructor for the corresponding type that will be created, so this must be a valid Haskell type constructor name.
If you are creating a terminal, option, list, list1, or
wrap, the RuleName will also be used for the name of the single
data construtor. If you are creating a nonTerminal, you will
specify the name of each data constructor with AlternativeName.
type AlternativeName = String Source
Type synonym the the name of an alternative in a nonTerminal.
This name must not conflict with any other data constructor, either
one specified as an AlternativeName or one that was created using
terminal, option, list, or list1.
A branch in a sum rule. In Branch s ls, s is the name of the
data constructor, and ls is the list of rules that this branch
produces.
A single production rule. It may be a terminal or a non-terminal.
label :: String -> Rule t -> 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.
Constructors
| Names | |
Errors that may arise when constructing an AST.
Constructors
| InvalidName String | A name was invalid. The field is the invalid name. The name might be invalid because it was already used, or because it does not begin with a capital letter. |
| EmptyNonTerminal String | A non-terminal must have at least one summand. The field is the name of the empty non-terminal. |
Constructs new Rules. t is the type of the token; often this
will be Char.
Pinchot is a Monad and an Applicative so you can combine
computations using the usual methods of those classes. Also,
Pinchot is a MonadFix. This allows you to construct a Rule
that depends on itself, and to construct sets of Rules that have
mutually recursive dependencies. MonadFix also allows you to use
the GHC RecursiveDo extension. Put
{-# LANGUAGE RecursiveDo #-}
at the top of your module, then use mdo instead of do. Because
an mdo block is recursive, you can use a binding before it is
defined, just as you can in a set of let bindings.
goPinchot :: Pinchot t a -> Q (Names t, a) Source
Runs a Pinchot with a starting empty state. Fails in the Q
monad if the grammar is bad.
addRuleName :: RuleName -> Pinchot t () Source
addDataConName :: AlternativeName -> Pinchot t () Source
Creates a terminal production rule.
splitNonTerminal :: String -> Seq (String, Seq (Rule t)) -> Pinchot t ((String, Seq (Rule t)), Seq (String, Seq (Rule t))) Source
Creates a production for a sequence of terminals. Useful for parsing specific words.
Arguments
| :: RuleName | |
| -> Seq (AlternativeName, Seq (Rule t)) | Alternatives. There must be at least one alternative;
otherwise, an error will result. In each pair |
| -> Pinchot t (Rule t) |
Creates a new non-terminal production rule.
ruleConstructorNames :: Rule t -> Seq AlternativeName Source
Arguments
| :: RuleName | Name of the parent rule |
| -> RuleName | Name of the branch rule |
| -> AlternativeName |
addDataConNames :: Rule t -> Pinchot t () Source
Arguments
| :: RuleName | |
| -> Seq (Rule t) | List of alternatives. There must be at least one alternative; otherwise a compile-time error will occur. |
| -> Pinchot t (Rule t) |
Creates a new non-terminal production rule where each alternative produces only one rule. The constructor name for each alternative 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. For
an example, see Suffix.
Currently there is no way to change the names of the constructors;
however, you can use nonTerminal, which is more flexible.
Arguments
| :: RuleName | The name of this rule, which is used both as the type name and the name of the sole data constructor. |
| -> Seq (Rule t) | The right-hand side of this rule. This sequence can be empty, which results in an epsilon production. |
| -> Pinchot t (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. For an example, see
Address.
Currently there is no way to change the names of the record fields.
Creates a newtype wrapper.
getAncestors :: Rule t -> State (Set String) (Seq (Rule t)) Source
Gets all ancestor Rules. Skips duplicates.
ruleAndAncestors :: Rule t -> Seq (Rule t) Source
rulesDemandedBeforeDefined :: Foldable f => f (Rule t) -> Set Name Source
Given a sequence of Rule, determine which rules are on a
right-hand side before they are defined.
Field name - without a leading underscore
Creates a prism for a terminal type. Although a newtype wraps each terminal, do not make a Wrapped or an Iso, because the relationship between the outer type and the type that it wraps typically is not isometric. Thus, use a Prism instead, which captures this relationship properly.
type MakeOptics = Bool Source
Should optics be made?
makeOptics :: MakeOptics Source
Creates optics.
If you use this option, you will need
{-# LANGUAGE TypeFamilies #-}
at the top of the module into which you splice in the
declarations, because you will get instances of Wrapped.
Creates the listed optics for each kind of
Rule, as follows:
terminal:, wherePrism'a bais the type of the terminal token (oftenChar) andbis the type of this particular production. For an example, see_Comma.
>>>',' ^? _CommaJust (Comma ',')>>>'a' ^? _CommaNothing>>>Comma ',' ^. re _Comma','
Thus this gives you a safe way to insert tokens into types made
with terminal (useful if you want to construct a syntax tree.)
terminalSeq:, wherePrism'(Seqa) bais the type of the terminal token (oftenChar) andbis the type of this particular production. As withterminalthis gives you a safe way to insert values into the types made withterminalSeq.nonTerminal: onePrism'for each data constructor (even if there is only one data constructor)union: onePrismfor each data constructor (even if there is only one data constructor)record: oneLensfor each fieldlist:Wrapped, wrapping aSeqalist1:Wrapped, wrapping a pair(a,Seqa)option:Wrapped, wrapping aMaybeawrap:Wrapped, wrapping the underlying type
Do not make any optics.
Arguments
| :: Lift t | |
| => MakeOptics | |
| -> Name | Terminal type constructor name. Typically you will use the Template Haskell quoting mechanism to get this. |
| -> Seq Name | What to derive. For instance, you might use |
| -> Pinchot t a | The return value from the |
| -> DecsQ |
Creates data types for every Rule created in the Pinchot. The data
types are created in the same order in which they were created in
the Pinchot. When spliced, the DecsQ is a list of
declarations, each of which is an appropriate data or newtype.
For an example use of allRulesToTypes, see
Pinchot.Examples.PostalAstAllRules.
Also creates bindings whose names are prefixed with t'. Each
of these is a function that, when given a particular production,
reduces it to a sequence of terminal symbols.
Arguments
| :: Lift t | |
| => MakeOptics | |
| -> Name | Terminal type constructor name. Typically you will use the Template Haskell quoting mechanism to get this. |
| -> Seq Name | What to derive. For instance, you might use |
| -> Pinchot t (Rule t) | A data type is created for the |
| -> DecsQ |
helperName :: String -> Name Source
lazyPattern :: Foldable c => c Name -> Q Pat Source
Creates a lazy pattern for all the given names. Adds an empty
pattern onto the front. This is the counterpart of bigTuple.
All of the given names are bound. In addition, a single,
wildcard pattern is bound to the front.
For example, lazyPattern (map mkName ["x", "y", "z"]) gives a
pattern that looks like
~(_, (x, (y, (z, ()))))
The idea is that the named patterns are needed so that the
recursive do notation works, and that the wildcard pattern is
the return value, which is not needed here.
Arguments
| :: Foldable c | |
| => ExpQ | This expression will be the first one in the tuple. |
| -> c ExpQ | Remaining expressions in the tuple. |
| -> ExpQ |
Creates a big tuple. It is nested in the second element, such as (1, (2, (3, (4, ())))). Thus, the big tuple is terminated with a unit value. It resembles a list where each tuple is a cons cell and the terminator is unit.
Arguments
| :: Lift t | |
| => Qualifier | Qualifier for data types crated with |
| -> Pinchot t (Rule t) | Creates an Earley parser for the |
| -> Q Exp | When spliced, this expression has type
where
|
Creates an Earley grammar for a given Rule. For examples of how
to use this, see the source code for
Pinchot.Examples.PostalAstRuleTree and for
Pinchot.Examples.PostalAstAllRules.
Arguments
| :: [(Name, ExpQ)] | Binding statements |
| -> ExpQ | Final return value from |
| -> ExpQ | Returns an expression whose value is the final return value
from the |
Builds a recursive do expression (because TH has no support
for mdo notation).
Arguments
| :: Lift t | |
| => Qualifier | Qualifier for data types created with |
| -> Name | Name for the terminal type; often this is |
| -> Pinchot t a | Creates an Earley grammar for each |
| -> DecsQ | When spliced, this is a list of declarations. Each
declaration has type
where
The name of each declaration is g'TYPE_NAME where TYPE_NAME is the name of the type defined in the
corresponding |
Creates an Earley grammar for each Rule created in a
Pinchot. For a Pinchot with a large number of Rules, this
can create a large number of declarations that can take a long
time to compile--sometimes several minutes. For lower
compilation times, try earleyProduct.
prodDeclName :: String -> Name Source
addIndices :: Foldable c => c a -> [(Int, a)] Source
Creates a production declaration for a Rule.
branchToClause :: Branch t -> ClauseQ Source
type Qualifier = String Source
Many functions take an argument that holds the name qualifier
for the module that contains the data types created by applying
ruleTreeToTypes or allRulesToTypes to the 'Pinchot.'
You have to make sure that the data types you created with
ruleTreeToTypes, allRulesToTypes, or allRulesRecord are in
scope. The spliced Template Haskell code has to know where to
look for these data types. If you did an unqualified import or
if the types are in the same module as is the splice of
earleyParser, just pass the empty string here. If you did a
qualified import, use the appropriate qualifier here.
For example, if you used import qualified MyAst, pass
"MyAst" here. If you used import qualified
Data.MyLibrary.MyAst as MyLibrary.MyAst, pass
"MyLibrary.MyAst" here.
I recommend that you always create a new module and that all you
do in that module is apply ruleTreeToTypes or
allRulesToTypes, and that you then perform an import
qualified to bring those names into scope in the module in which
you use a function that takes a Qualifier argument. This
avoids unlikely, but possible, issues that could otherwise arise
due to naming conflicts.
Arguments
| :: Qualifier | Qualifier for data types created with |
| -> Name | Name of terminal type. Typically you will get this through
the Template Haskell quoting mechanism, such as |
| -> Pinchot t a | A record is created that holds a value for each |
| -> DecsQ | When spliced, this will create a single declaration that is a
record with the name a'NAME where |
Creates a record data type that holds a value of type
ProdrStringt a
for every rule created in the Pinchot. r is left
universally quantified, t is the token type (typically Char)
and a is the type of the rule.
This always creates a single product type whose name is
Productions; currently the name cannot be configured.
For an example of the use of allRulesRecord, please see
Pinchot.Examples.AllRulesRecord.
Arguments
| :: Lift t | |
| => Qualifier | Qualifier for data types created with |
| -> Qualifier | Module prefix for the type created with |
| -> Pinchot t a | Creates an Earley grammar that contains a |
| -> ExpQ | When spliced, |