little-earley-0.2.0.0: Simple implementation of Earley parsing
Safe HaskellSafe-Inferred
LanguageHaskell2010

Little.Earley.Internal.Core

Synopsis

Documentation

data Grammar n t c Source #

Grammars with non-terminal symbols n, terminal symbols t, and tokens c.

A grammar defines a language, which is a set of sequences of tokens c.

Two basic choices for t and c are:

  • t = CharT and c = Char, with match = matchCharT: then the input [c] is a String.
  • t = String and c = String, with match = (==): then the input [c] is a [String], which can be produced using words; just remember to put spaces around operators and parentheses.

See also examples in Little.Earley.Examples.

Constructors

Grammar 

Fields

  • rules :: n -> [Rule n t]

    Production rules associated with each non-terminal symbol.

  • match :: t -> c -> Bool

    Match a token c with a terminal symbol t.

  • isNullable :: n -> Bool

    Predicate for non-terminal symbols which may expand to the empty string. This function MUST be correct for the library to work. It can be populated automatically using mkGrammar.

mkGrammar :: (Ord n, Bounded n, Enum n) => (n -> [Rule n t]) -> (t -> c -> Bool) -> Grammar n t c Source #

Construct a grammar given the fields rules and match, implicitly populating isNullable.

nullableSymbols :: Ord n => (n -> [Rule n t]) -> [n] -> Set n Source #

Compute the set of non-terminal symbols which may expand to the empty string, given an enumeration of all non-terminal symbols.

type Rule n t = [Atom n t] Source #

A production rule is a sequence of atoms.

data Atom n t Source #

An atom is either a non-terminal or a terminal.

Constructors

N n 
T t 

Instances

Instances details
(Eq n, Eq t) => Eq (Atom n t) Source # 
Instance details

Defined in Little.Earley.Internal.Core

Methods

(==) :: Atom n t -> Atom n t -> Bool #

(/=) :: Atom n t -> Atom n t -> Bool #

(Ord n, Ord t) => Ord (Atom n t) Source # 
Instance details

Defined in Little.Earley.Internal.Core

Methods

compare :: Atom n t -> Atom n t -> Ordering #

(<) :: Atom n t -> Atom n t -> Bool #

(<=) :: Atom n t -> Atom n t -> Bool #

(>) :: Atom n t -> Atom n t -> Bool #

(>=) :: Atom n t -> Atom n t -> Bool #

max :: Atom n t -> Atom n t -> Atom n t #

min :: Atom n t -> Atom n t -> Atom n t #

(Show n, Show t) => Show (Atom n t) Source # 
Instance details

Defined in Little.Earley.Internal.Core

Methods

showsPrec :: Int -> Atom n t -> ShowS #

show :: Atom n t -> String #

showList :: [Atom n t] -> ShowS #

data RuleId n Source #

A rule can be identified by a non-terminal and an index into all of the associated rules of that non-terminal.

Constructors

RuleId n Int 

Instances

Instances details
Eq n => Eq (RuleId n) Source # 
Instance details

Defined in Little.Earley.Internal.Core

Methods

(==) :: RuleId n -> RuleId n -> Bool #

(/=) :: RuleId n -> RuleId n -> Bool #

Ord n => Ord (RuleId n) Source # 
Instance details

Defined in Little.Earley.Internal.Core

Methods

compare :: RuleId n -> RuleId n -> Ordering #

(<) :: RuleId n -> RuleId n -> Bool #

(<=) :: RuleId n -> RuleId n -> Bool #

(>) :: RuleId n -> RuleId n -> Bool #

(>=) :: RuleId n -> RuleId n -> Bool #

max :: RuleId n -> RuleId n -> RuleId n #

min :: RuleId n -> RuleId n -> RuleId n #

Show n => Show (RuleId n) Source # 
Instance details

Defined in Little.Earley.Internal.Core

Methods

showsPrec :: Int -> RuleId n -> ShowS #

show :: RuleId n -> String #

showList :: [RuleId n] -> ShowS #

data Item n t Source #

Constructors

Item (RuleId n) [Atom n t] Int 

Instances

Instances details
(Eq n, Eq t) => Eq (Item n t) Source # 
Instance details

Defined in Little.Earley.Internal.Core

Methods

(==) :: Item n t -> Item n t -> Bool #

(/=) :: Item n t -> Item n t -> Bool #

(Ord n, Ord t) => Ord (Item n t) Source # 
Instance details

Defined in Little.Earley.Internal.Core

Methods

compare :: Item n t -> Item n t -> Ordering #

(<) :: Item n t -> Item n t -> Bool #

(<=) :: Item n t -> Item n t -> Bool #

(>) :: Item n t -> Item n t -> Bool #

(>=) :: Item n t -> Item n t -> Bool #

max :: Item n t -> Item n t -> Item n t #

min :: Item n t -> Item n t -> Item n t #

(Show n, Show t) => Show (Item n t) Source # 
Instance details

Defined in Little.Earley.Internal.Core

Methods

showsPrec :: Int -> Item n t -> ShowS #

show :: Item n t -> String #

showList :: [Item n t] -> ShowS #

data S n t Source #

Constructors

S 

Fields

Instances

Instances details
(Eq n, Eq t) => Eq (S n t) Source # 
Instance details

Defined in Little.Earley.Internal.Core

Methods

(==) :: S n t -> S n t -> Bool #

(/=) :: S n t -> S n t -> Bool #

(Show n, Show t) => Show (S n t) Source # 
Instance details

Defined in Little.Earley.Internal.Core

Methods

showsPrec :: Int -> S n t -> ShowS #

show :: S n t -> String #

showList :: [S n t] -> ShowS #

emptyS :: S n t Source #

initialS :: (Ord n, Ord t) => Grammar n t c -> n -> S n t Source #

newItems :: Ord n => Grammar n t c -> Int -> n -> [Item n t] Source #

allItemSets :: S n t -> Seq (Set (Item n t)) Source #

type Parser n t = State (S n t) Source #

next :: Parser n t () Source #

addItemCurr :: (Ord n, Ord t) => Item n t -> Parser n t () Source #

lookupItemSet :: Int -> Parser n t (Set (Item n t)) Source #

addItemNext :: (Ord n, Ord t) => Item n t -> Parser n t () Source #

stepItem :: (Ord n, Ord t) => Grammar n t c -> Maybe c -> Item n t -> Parser n t () Source #

step :: (Ord n, Ord t) => Grammar n t c -> Maybe c -> Parser n t () Source #

steps :: (Ord n, Ord t) => Grammar n t c -> [c] -> Parser n t () Source #

data Seq1 a Source #

Constructors

(Seq a) ::> a 

Instances

Instances details
Eq a => Eq (Seq1 a) Source # 
Instance details

Defined in Little.Earley.Internal.Core

Methods

(==) :: Seq1 a -> Seq1 a -> Bool #

(/=) :: Seq1 a -> Seq1 a -> Bool #

Show a => Show (Seq1 a) Source # 
Instance details

Defined in Little.Earley.Internal.Core

Methods

showsPrec :: Int -> Seq1 a -> ShowS #

show :: Seq1 a -> String #

showList :: [Seq1 a] -> ShowS #

preparse :: (Ord n, Ord t) => Grammar n t c -> n -> [c] -> Seq1 (Set (Item n t)) Source #

accepts :: (Ord n, Ord t) => Grammar n t c -> n -> [c] -> Bool Source #

Check whether a grammar matches a chain of character [c] from a starting symbol n.