Safe Haskell | None |
---|---|
Language | Haskell2010 |
Pinchot provides a simple language that you use to write a Haskell program that describes a context-free grammar. When run, this program creates a value that stores your context-free grammar. You can then use Template Haskell to take this value and generate a series of data types that correspond to your context-free grammar. You can also use Template Haskell to create an Earley parser that will parse all strings in the context-free language.
You will need to have
{-# LANGUAGE TypeFamilies #-}
at the top of any module in which you use Template Haskell to splice in the resulting data types.
For examples, please consult Pinchot.Examples.
You should also look at the BNF Converter.
http://bnfc.digitalgrammars.com
Primary differences between BNFC and this library:
- the BNF Converter works as a standalone binary that parses text BNF files. With Pinchot you specify your grammar in Haskell.
- the BNF Converter currently generates many more outputs, such as LaTeX. It also generates code for many languages. Pinchot only works in Haskell.
- the BNF Converter generates input for parser generators like Happy and Bison. Pinchot currently only generates input for the Haskell Earley library.
- Pinchot integrates seamlessly into Haskell using Template Haskell.
- the BNF Converter is GPL. Pinchot is BSD3.
Pinchot grows and harvests syntax trees, so it is named after Gifford Pinchot, first chief of the United States Forest Service.
- data Intervals a
- include :: a -> a -> Intervals a
- exclude :: a -> a -> Intervals a
- solo :: a -> Intervals a
- pariah :: a -> Intervals a
- data Pinchot t a
- type RuleName = String
- type AlternativeName = String
- data Rule t
- terminal :: RuleName -> Intervals t -> Pinchot t (Rule t)
- terminalSeq :: RuleName -> Seq t -> Pinchot t (Rule t)
- nonTerminal :: RuleName -> Seq (AlternativeName, Seq (Rule t)) -> Pinchot t (Rule t)
- union :: RuleName -> Seq (AlternativeName, Rule t) -> Pinchot t (Rule t)
- record :: RuleName -> Seq (Rule t) -> Pinchot t (Rule t)
- list :: RuleName -> Rule t -> Pinchot t (Rule t)
- list1 :: RuleName -> Rule t -> Pinchot t (Rule t)
- option :: RuleName -> Rule t -> Pinchot t (Rule t)
- wrap :: RuleName -> Rule t -> Pinchot t (Rule t)
- label :: String -> Rule t -> Rule t
- (<?>) :: Pinchot t (Rule t) -> String -> Pinchot t (Rule t)
- earleyGrammar :: Lift t => String -> Pinchot t (Rule t) -> Q Exp
- 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
- class Production a where
Intervals
include :: a -> a -> Intervals a Source
Include a range of symbols in the Intervals
. For instance, to
include the characters
, a
, and b
, use c
include
.a
c
Simple production rules
Constructs new Rule
s. 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 Rule
s 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.
Type synonym for the name of a production rule. This will be the name of the type constructor for the corresponding type in the AST, 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 single production rule. It may be a terminal or a non-terminal.
Creates a terminal production rule.
Creates a production for a sequence of terminals. Useful for parsing specific words.
:: 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.
union :: RuleName -> Seq (AlternativeName, Rule t) -> Pinchot t (Rule t) Source
Creates a new non-terminal production rule where each alternative produces only one rule.
:: 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:
_f'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.
Rules that modify other rules
:: RuleName | |
-> Rule t | The resulting |
-> Pinchot t (Rule t) |
Creates a rule for the production of a sequence of other rules.
Creates a rule for a production that appears at least once.
:: RuleName | |
-> Rule t | The resulting |
-> Pinchot t (Rule t) |
Creates a rule for a production that optionally produces another rule.
Creates a newtype wrapper.
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.
Transforming an AST to code
:: Lift t | |
=> String | Module prefix. You have to make sure that the data types you
created with For example, if you used For an example where the types are in the same module, see Pinchot.Examples.PostalAstRuleTree or Pinchot.Examples.PostalAstAllRules. For an example using a qualified import, see Pinchot.Examples.QualifiedImport. |
-> Pinchot t (Rule t) | Creates an Earley parser for the |
-> Q Exp |
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.
type MakeOptics = Bool Source
Should optics be made?
makeOptics :: MakeOptics Source
Creates optics.
pragma at the top of the module in which you splice this in.
Creates the listed optics for each kind of
Rule
, as follows:
terminal
:
, wherePrism'
a ba
is the type of the terminal token (oftenChar
) andb
is the type of this particular production. For an example, see_Comma
.
>>>
',' ^? _Comma
Just (Comma ',')>>>
'a' ^? _Comma
Nothing>>>
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'
(Seq
a) ba
is the type of the terminal token (oftenChar
) andb
is the type of this particular production. As withterminal
this 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
: onePrism
for each data constructor (even if there is only one data constructor)record
: oneLens
for each fieldlist
:Wrapped
, wrapping aSeq
alist1
:Wrapped
, wrapping a pair(a,
Seq
a)option
:Wrapped
, wrapping aMaybe
awrap
:Wrapped
, wrapping the underlying type
Do not make any optics.
:: 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.
:: 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 |
Manipulating productions
class Production a where Source
Typeclass for all productions, which allows you to extract a sequence of terminal symbols from any production.