pinchot-0.4.0.0: Build parsers and ASTs for context-free grammars

Safe HaskellNone
LanguageHaskell2010

Pinchot.Internal

Description

Pinchot internals. Ordinarily the Pinchot module should have everything you need.

Synopsis

Documentation

type RuleName = String Source

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.

data Branch t Source

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.

Constructors

Branch String (Seq (Rule t)) 

Instances

Eq t => Eq (Branch t) Source 
Ord t => Ord (Branch t) Source 
Show t => Show (Branch t) Source 

data RuleType t Source

Constructors

RTerminal (Intervals t) 
RBranch (Branch t, Seq (Branch t)) 
RSeqTerm (Seq t) 
ROptional (Rule t) 
RMany (Rule t) 
RMany1 (Rule t) 
RWrap (Rule t) 
RRecord (Seq (Rule t)) 

Instances

Eq t => Eq (RuleType t) Source 
Ord t => Ord (RuleType t) Source 
Show t => Show (RuleType t) Source 

data Rule t Source

A single production rule. It may be a terminal or a non-terminal.

Constructors

Rule String (Maybe String) (RuleType t) 

Instances

Eq t => Eq (Rule t) Source 
Ord t => Ord (Rule t) Source 
Show t => Show (Rule t) Source 

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.

(<?>) :: Pinchot t (Rule t) -> String -> Pinchot t (Rule t) infixr 0 Source

Infix form of label for use in a Pinchot; handy for use in do or mdo notation.

data Names t Source

Constructors

Names 

Instances

Eq t => Eq (Names t) Source 
Ord t => Ord (Names t) Source 
Show t => Show (Names t) Source 

data Error Source

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.

newtype Pinchot t a Source

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.

Constructors

Pinchot 

Fields

runPinchot :: ExceptT Error (State (Names t)) a
 

terminal Source

Arguments

:: RuleName 
-> Intervals t

Valid terminal symbols

-> Pinchot t (Rule t) 

Creates a terminal production rule.

terminalSeq Source

Arguments

:: RuleName 
-> Seq t

Sequence of terminal symbols to recognize

-> Pinchot t (Rule t) 

Creates a production for a sequence of terminals. Useful for parsing specific words.

nonTerminal Source

Arguments

:: RuleName 
-> Seq (AlternativeName, Seq (Rule t))

Alternatives. There must be at least one alternative; otherwise, an error will result. In each pair (a, b), a will be the data constructor, so this must be a valid Haskell data constructor name. b is the sequence of production rules, which can be empty (this is how to create an epsilon production).

-> 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.

record Source

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:

_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.

list Source

Arguments

:: RuleName 
-> Rule t

The resulting Rule is a sequence of productions of this Rule; that is, this Rule may appear zero or more times.

-> Pinchot t (Rule t) 

Creates a rule for the production of a sequence of other rules.

list1 Source

Arguments

:: RuleName 
-> Rule t

The resulting Rule produces this Rule at least once.

-> Pinchot t (Rule t) 

Creates a rule for a production that appears at least once.

option Source

Arguments

:: RuleName 
-> Rule t

The resulting Rule optionally produces this Rule; that is, this Rule may appear once or not at all.

-> Pinchot t (Rule t) 

Creates a rule for a production that optionally produces another rule.

wrap Source

Arguments

:: RuleName 
-> Rule t

The resulting Rule simply wraps this Rule.

-> Pinchot t (Rule t) 

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

Returns both this Rule and any Rules that are ancestors.

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.

thRule Source

Arguments

:: Bool

If True, make lenses.

-> Name

Name of terminal type

-> Seq Name

What to derive

-> Rule t 
-> Q [Dec] 

makeType Source

Arguments

:: Name

Name of terminal type

-> Seq Name

What to derive

-> String

Name of rule

-> RuleType t 
-> Q Dec 

fieldName Source

Arguments

:: Int

Index

-> String

Parent type name

-> String

Inner type name

-> String 

Field name - without a leading underscore

thAllRules Source

Arguments

:: Bool

If True, make optics as well.

-> Name

Terminal type constructor name

-> Seq Name

What to derive

-> Map Int (Rule t) 
-> DecsQ 

makeWrapped Source

Arguments

:: Type

Name of wrapped type

-> String

Name of wrapper type

-> Dec 

terminalToOptics Source

Arguments

:: Name

Terminal type name

-> String

Rule name

-> Dec 

optionalToOptics Source

Arguments

:: String

Wrapped rule name

-> String

Wrapping Rule name

-> Dec 

many1ToOptics Source

Arguments

:: String

Wrapped rule name

-> String

Wrapping Rule name

-> Dec 

manyToOptics Source

Arguments

:: String

Wrapped rule name

-> String

Wrapping Rule name

-> Dec 

wrapToOptics Source

Arguments

:: String

Wrapped rule name

-> String

Wrapping Rule name

-> Dec 

terminalSeqToOptics Source

Arguments

:: Name

Terminal type name

-> String

Rule name

-> Dec 

branchesToOptics Source

Arguments

:: String

Rule name

-> Branch t 
-> Seq (Branch t) 
-> [Dec] 

recordsToOptics Source

Arguments

:: String

Rule name

-> Seq (Rule t) 
-> [Dec] 

ruleToOptics Source

Arguments

:: Name

Terminal type name

-> String

Rule name

-> RuleType t 
-> [Dec] 

type MakeOptics = Bool Source

Should optics be made?

makeOptics :: MakeOptics Source

Creates optics. If you use this option you will need to have a

{-# LANGUAGE TypeFamilies #-}

pragma at the top of the module in which you splice this in.

Creates the listed optics for each kind of Rule, as follows:

noOptics :: MakeOptics Source

Do not make any optics.

allRulesToTypes Source

Arguments

:: 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 Eq, Ord, and Show here. Each created data type will derive these instances.

-> Pinchot t a

The return value from the Pinchot is ignored.

-> 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.

ruleTreeToTypes Source

Arguments

:: 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 Eq, Ord, and Show here. Each created data type will derive these instances.

-> Pinchot t (Rule t)

A data type is created for the Rule that the Pinchot returns, and for the ancestors of the Rule.

-> DecsQ 

Creates data types only for the Rule returned from the Pinchot, and for its ancestors.

ruleToParser Source

Arguments

:: Lift t 
=> String

Module prefix

-> Rule t 
-> Q [Stmt] 

constructorName Source

Arguments

:: String

Module prefix

-> String

Name of constructor

-> ExpQ 

branchToParser Source

Arguments

:: Lift t 
=> String

Module prefix

-> Branch t 
-> ExpQ 

lazyPattern :: Foldable c => c Name -> Q Pat Source

Creates a lazy pattern for all the given names. Adds an empty pattern onto the front.

earleyGrammar Source

Arguments

:: Lift t 
=> String

Module prefix. You have to make sure that the data types you created with ruleTreeToTypes or with allRulesToTypes are in scope, either because they were spliced into the same module that earleyParser is spliced into, or because they are imported into 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, pass the appropriate namespace 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.

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 Rule that the Pinchot returns.

-> 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.