parser241-0.1.0.2: An interface to create production rules using augmented grammars

CopyrightSee LICENSE
Maintainerylilarry@gmail.com
StabilityExperimental
PortabilityNon-portable (GHC extensions)
Safe HaskellNone
LanguageHaskell2010

Parser.ProductRule

Contents

Description

Introduction

This module contains everything you need to define an augmented grammar.

This module is a monadic interface to define an augmented grammar. The function productRules defined in this package takes in an abstract syntax tree representation, and produces a production rule table, in which non-terminal and terminal symbols are labeled, and can be further used by you parser project.

For example, given a user-defined symbols,

data MySym = A
           | B
           | C'
         deriving (Eq, Show, Ord)

where A B are non-terminal symbols, 'C 'D are terminal symbols, we can define a production rule table:

table :: [ProductRule MySym]
table = productRules $ do

   Start ---> A & C' & B  -- AC'B concatenation
           |> A
           |> C'

      ; A --> B           -- You might want to use ";" to clarify the indentation in a `do` block.
           |> A & C'
           |/ Null

      ; B --> C'

This will produce:

>>> print $ table
>
>  [    (Start, [NT A, T C', NT B])
>     , (Start, [NT A])
>     , (Start, [T C'])
>     , (NT A, [NT B])
>     , (NT A, [NT A, T C'])
>     , (NT A, [Null])
>     , (NT B, [T C'])
>  ]
>

where NT represents non-terminal type, and T represents terminal type.

This package does not parse the input in any way. It just simplifies the way you can define the grammar.

Synopsis

Documentation

data Symbol a Source

Two provided symbols besides user defined data.

Constructors

Start

represents the starting symbol.

Null

represents the null symbol.

T a

represents a terminal symbol.

NT a

represents a non-terminal symbol.

Instances

Eq a => Eq (Symbol a) Source 
Ord a => Ord (Symbol a) Source 
Show a => Show (Symbol a) Source 

type ProductRule t = (Symbol t, [Symbol t]) Source

productRules :: Ord a => Manager a -> [ProductRule a] Source

Collect the defined syntax and produces a list of production rules.

Production Rule Construction

(--->) :: FromMaker m => Ord a => Symbol a -> a -> m a () Source

Use ---> iff the left side is the Start symbol and the first symbol on the right side is an user-defined symbol.

Only one symbol is allowed on the left hand side.

table :: [ProductRule MySym]
table = productRules $ do
   Start ---> A & B ...
           ...

(-->) :: FromMaker m => Ord a => a -> a -> m a () Source

Use --> iff both the left side and the first symbol on the right side are user-defined symbols.

| Only one symbol is allowed on the left hand side.

| Use & to concatenate two user-defined symbols.

table :: [ProductRule MySym]
table = productRules $ do
   Start ---> ...
           ...
      ; A --> C'
           |/ Null
           ...

(|>) :: FromMaker m => Maker a -> a -> m a () Source

Use |> to represent "or" when the left hand side can produce two different expressions, and the right side in a user-defined type.

table :: [ProductRule MySym]
table = productRules $ do
   Start ---> ...
           ...
           |> C'

(&) :: FromMaker m => Maker a -> a -> m a () Source

Use & to concatenate two user-defined symbols.

table :: [ProductRule MySym]
table = productRules $ do
   Start >>> Null & C'
          |> ...

(|/) :: FromMaker m => Maker a -> Symbol a -> m a () Source

Use |/ iff the right hand side is the Null symbol.

table :: [ProductRule MySym]
table = productRules $ do
   Start ---> C'
           |/ Null
           |> ...

(>>>) :: FromMaker m => Symbol a -> Symbol a -> m a () Source

Use >>> iff the left side is Start and the first symbol on the right side is Null.

table :: [ProductRule MySym]
table = productRules $ do
   Start >>> Null
          |> C'
          ...