gll-0.4.0.5: GLL parser with simple combinator interface

Safe HaskellSafe
LanguageHaskell2010

GLL.Types.Derivations

Synopsis

Documentation

type SlotL t = (Slot t, Int) Source #

type PrL t = (Prod t, Int) Source #

type NtL = (Nt, Int) Source #

type SPPF t = (SymbMap t, ImdMap t, PackMap t, EdgeMap t) Source #

An SPPF contains symbol nodes, intermediate nodes, packed nodes and edges between them. See Scott and Johnstone (2013) for an explanation of the SPPF.

type PackMap t = IntMap (IntMap (IntMap (Map (Prod t) IntSet))) Source #

Stores packed nodes using nested Data.IntMaps, nesting is as follows:

  • left extent
  • right extent
  • dot position (from left to right)
  • mapping from productions to set of pivots

type SymbMap t = IntMap (IntMap (Set (Symbol t))) Source #

Stores symbol nodes using nested Data.IntMaps, nesting is as follows:

  • left extent
  • right extent
  • set of symbols

type ImdMap t = IntMap (IntMap (Set (Slot t))) Source #

Stores intermediate nodes using nested Data.IntMaps, nesting is as follows:

  • left extent
  • right extent
  • set of slots

type EdgeMap t = Map (SPPFNode t) (Set (SPPFNode t)) Source #

Stores edges, potentially costly.

data SPPFNode t Source #

An SPPFNode is either a symbol node, an intermediate node, a packed node or a dummy.

Constructors

SNode (Symbol t, Int, Int) 
INode (Slot t, Int, Int) 
PNode (Slot t, Int, Int, Int) 
Dummy 

Instances

Eq t => Eq (SPPFNode t) Source # 

Methods

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

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

Ord t => Ord (SPPFNode t) Source # 

Methods

compare :: SPPFNode t -> SPPFNode t -> Ordering #

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

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

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

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

max :: SPPFNode t -> SPPFNode t -> SPPFNode t #

min :: SPPFNode t -> SPPFNode t -> SPPFNode t #

type SNode t = (Symbol t, Int, Int) Source #

type PNode t = (Prod t, [Int]) Source #

type SEdge t = Map (SNode t) (Set (PNode t)) Source #

type PEdge t = Map (PNode t) (Set (SNode t)) Source #

pNodeLookup :: Ord t => SPPF t -> ((Prod t, Int), Int, Int) -> Maybe [Int] Source #

pMapInsert :: Ord t => SPPFNode t -> SPPFNode t -> SPPF t -> SPPF t Source #

sNodeLookup :: Ord t => SPPF t -> (Symbol t, Int, Int) -> Bool Source #

sNodeInsert :: Ord t => SPPFNode t -> SPPFNode t -> SPPF t -> SPPF t Source #

sNodeRemove :: Ord t => SPPF t -> (Symbol t, Int, Int) -> SPPF t Source #

iNodeLookup :: Ord t => SPPF t -> (Slot t, Int, Int) -> Bool Source #

iNodeInsert :: Ord t => SPPFNode t -> SPPFNode t -> SPPF t -> SPPF t Source #

iNodeRemove :: Ord t => SPPF t -> (Slot t, Int, Int) -> SPPF t Source #

eMapInsert :: Ord t => SPPFNode t -> SPPFNode t -> SPPF t -> SPPF t Source #

inU :: Ord a => (a, Key, Key) -> IntMap (IntMap (Set a)) -> Bool Source #

toU :: Ord a => (a, Key, Key) -> IntMap (IntMap (Set a)) -> IntMap (IntMap (Set a)) Source #

showD :: (Show a2, Show a1) => Map a1 [a2] -> String Source #

showG :: (Show a2, Show a1) => Map a1 [a2] -> String Source #

showP :: (Show a2, Show a1) => IntMap (IntMap (IntMap (Map a1 a2))) -> String Source #

type ProdMap t = Map Nt [Prod t] Source #

type PrefixMap t = Map (Prod t, Int) ([t], Maybe Nt) Source #

type SelectMap t = Map (Nt, [Symbol t]) (Set t) Source #

type FirstMap t = Map Nt (Set t) Source #

type FollowMap t = Map Nt (Set t) Source #

fixedMaps :: (Eq t, Ord t, Parseable t) => Nt -> [Prod t] -> (ProdMap t, PrefixMap t, FirstMap t, FollowMap t, SelectMap t) Source #