gll-0.4.1.0: GLL parser with simple combinator interface
Safe HaskellSafe-Inferred
LanguageHaskell2010

GLL.Types.Grammar

Synopsis

Documentation

type Nt = Text Source #

Identifier for nonterminals.

data Prod t Source #

A production binds a nonterminal identifier (left-hand side) to a list of symbols (the right-hand side of the production).

Constructors

Prod Nt (Symbols t) 

Instances

Instances details
Show t => Show (Prod t) Source # 
Instance details

Defined in GLL.Types.Grammar

Methods

showsPrec :: Int -> Prod t -> ShowS #

show :: Prod t -> String #

showList :: [Prod t] -> ShowS #

Eq t => Eq (Prod t) Source # 
Instance details

Defined in GLL.Types.Grammar

Methods

(==) :: Prod t -> Prod t -> Bool #

(/=) :: Prod t -> Prod t -> Bool #

Ord t => Ord (Prod t) Source # 
Instance details

Defined in GLL.Types.Grammar

Methods

compare :: Prod t -> Prod t -> Ordering #

(<) :: Prod t -> Prod t -> Bool #

(<=) :: Prod t -> Prod t -> Bool #

(>) :: Prod t -> Prod t -> Bool #

(>=) :: Prod t -> Prod t -> Bool #

max :: Prod t -> Prod t -> Prod t #

min :: Prod t -> Prod t -> Prod t #

type Prods t = [Prod t] Source #

A list of Prods.

type Grammar t = (Nt, Prods t) Source #

A grammar is a start symbol and a list of productions.

data Slot t Source #

A grammar slot acts as a label to identify progress of matching a production. As such, a slot is a Prod with its right-hand side split in two: a part before and a part after 'the dot'. The dot indicates which part of the right-hand side has been processed thus far.

Constructors

Slot Nt [Symbol t] [Symbol t] 

Instances

Instances details
Show t => Show (Slot t) Source # 
Instance details

Defined in GLL.Types.Grammar

Methods

showsPrec :: Int -> Slot t -> ShowS #

show :: Slot t -> String #

showList :: [Slot t] -> ShowS #

Eq t => Eq (Slot t) Source # 
Instance details

Defined in GLL.Types.Grammar

Methods

(==) :: Slot t -> Slot t -> Bool #

(/=) :: Slot t -> Slot t -> Bool #

Ord t => Ord (Slot t) Source # 
Instance details

Defined in GLL.Types.Grammar

Methods

compare :: Slot t -> Slot t -> Ordering #

(<) :: Slot t -> Slot t -> Bool #

(<=) :: Slot t -> Slot t -> Bool #

(>) :: Slot t -> Slot t -> Bool #

(>=) :: Slot t -> Slot t -> Bool #

max :: Slot t -> Slot t -> Slot t #

min :: Slot t -> Slot t -> Slot t #

data Symbol t Source #

A Symbol is either a nonterminal or a terminal, where a terminal contains some arbitrary token.

Constructors

Nt Nt 
Term t 

Instances

Instances details
Show t => Show (Symbol t) Source # 
Instance details

Defined in GLL.Types.Grammar

Methods

showsPrec :: Int -> Symbol t -> ShowS #

show :: Symbol t -> String #

showList :: [Symbol t] -> ShowS #

Eq t => Eq (Symbol t) Source # 
Instance details

Defined in GLL.Types.Grammar

Methods

(==) :: Symbol t -> Symbol t -> Bool #

(/=) :: Symbol t -> Symbol t -> Bool #

Ord t => Ord (Symbol t) Source # 
Instance details

Defined in GLL.Types.Grammar

Methods

compare :: Symbol t -> Symbol t -> Ordering #

(<) :: Symbol t -> Symbol t -> Bool #

(<=) :: Symbol t -> Symbol t -> Bool #

(>) :: Symbol t -> Symbol t -> Bool #

(>=) :: Symbol t -> Symbol t -> Bool #

max :: Symbol t -> Symbol t -> Symbol t #

min :: Symbol t -> Symbol t -> Symbol t #

type Symbols t = [Symbol t] Source #

A list of Symbols

data Token Source #

A datatype for representing tokens with some builtins and an aribitrary Token constructor. This datatype stores (optional) lexemes.

Constructors

Char Char 
Keyword String 
EOS 
Epsilon 
IntLit (Maybe Int) 
FloatLit (Maybe Double) 
BoolLit (Maybe Bool) 
StringLit (Maybe String) 
CharLit (Maybe Char) 
IDLit (Maybe String) 
AltIDLit (Maybe String)

alternative identifiers, for example functions vs. constructors (as in Haskell).

Token String (Maybe String) 

Instances

Instances details
Show Token Source # 
Instance details

Defined in GLL.Types.Grammar

Methods

showsPrec :: Int -> Token -> ShowS #

show :: Token -> String #

showList :: [Token] -> ShowS #

Eq Token Source # 
Instance details

Defined in GLL.Types.Grammar

Methods

(==) :: Token -> Token -> Bool #

(/=) :: Token -> Token -> Bool #

Ord Token Source # 
Instance details

Defined in GLL.Types.Grammar

Methods

compare :: Token -> Token -> Ordering #

(<) :: Token -> Token -> Bool #

(<=) :: Token -> Token -> Bool #

(>) :: Token -> Token -> Bool #

(>=) :: Token -> Token -> Bool #

max :: Token -> Token -> Token #

min :: Token -> Token -> Token #

Parseable Token Source # 
Instance details

Defined in GLL.Types.Grammar

SubsumesToken Token Source # 
Instance details

Defined in GLL.Types.Grammar

type Tokens = [Token] Source #

A list of Tokens

class (Ord a, Eq a, Show a) => Parseable a where Source #

Class that captures elements of an input string (tokens).

  • eos is the end-of-string symbol
  • eps is the empty-string symbol

Both eos and eps must be distinct from eachother and from all tokens in the input string. The show instance is required to throw error messages.

Minimal complete definition

eos, eps, matches

Methods

eos :: a Source #

eps :: a Source #

matches :: a -> a -> Bool Source #

This function is used for matching grammar tokens and input tokens. Override this method if, for example, your input tokens store lexemes while the grammar tokens do not

unlex :: a -> String Source #

This function pretty-prints the Parseable type by displaying its lexeme. Default implementation is show, which should be replaced for prettier error messages.

Instances

Instances details
Parseable Token Source # 
Instance details

Defined in GLL.Types.Grammar

Parseable Char Source #

Assumes $ and # never appear in the input string.

Instance details

Defined in GLL.Parseable.Char

class SubsumesToken a where Source #

Class whose members are super-types of Token.

Methods

upcast :: Token -> a Source #

downcast :: a -> Maybe Token Source #

Instances

Instances details
SubsumesToken Token Source # 
Instance details

Defined in GLL.Types.Grammar

unlexTokens :: [Token] -> String Source #

Pretty-prints a list of Tokens as a concatenation of their lexemes.