LR-demo
Safe HaskellNone
LanguageHaskell2010

ParseTable

Description

LR-parser.

Synopsis

Documentation

newtype Stack' x t Source #

A stack is a sentential form (reversed).

Constructors

Stack [Symbol' x t] 

Instances

Instances details
(DebugPrint x, DebugPrint t) => DebugPrint (Stack' x t) Source # 
Instance details

Defined in ParseTable.Pretty

Methods

debugPrint :: Stack' x t -> String Source #

(Show t, Show x) => Show (Stack' x t) Source # 
Instance details

Defined in ParseTable

Methods

showsPrec :: Int -> Stack' x t -> ShowS #

show :: Stack' x t -> String #

showList :: [Stack' x t] -> ShowS #

Eq t => Eq (Stack' x t) Source # 
Instance details

Defined in ParseTable

Methods

(==) :: Stack' x t -> Stack' x t -> Bool #

(/=) :: Stack' x t -> Stack' x t -> Bool #

Ord t => Ord (Stack' x t) Source # 
Instance details

Defined in ParseTable

Methods

compare :: Stack' x t -> Stack' x t -> Ordering #

(<) :: Stack' x t -> Stack' x t -> Bool #

(<=) :: Stack' x t -> Stack' x t -> Bool #

(>) :: Stack' x t -> Stack' x t -> Bool #

(>=) :: Stack' x t -> Stack' x t -> Bool #

max :: Stack' x t -> Stack' x t -> Stack' x t #

min :: Stack' x t -> Stack' x t -> Stack' x t #

type Input' t = [t] Source #

data SRState' x t Source #

The state of a shift-reduce parser consists of a stack and some input.

Constructors

SRState 

Fields

Instances

Instances details
(DebugPrint x, DebugPrint t) => DebugPrint (SRState' x t) Source # 
Instance details

Defined in ParseTable.Pretty

Methods

debugPrint :: SRState' x t -> String Source #

(Show t, Show x) => Show (SRState' x t) Source # 
Instance details

Defined in ParseTable

Methods

showsPrec :: Int -> SRState' x t -> ShowS #

show :: SRState' x t -> String #

showList :: [SRState' x t] -> ShowS #

srInput :: forall x t f. Functor f => (Input' t -> f (Input' t)) -> SRState' x t -> f (SRState' x t) Source #

srStack :: forall x1 t x2 f. Functor f => (Stack' x1 t -> f (Stack' x2 t)) -> SRState' x1 t -> f (SRState' x2 t) Source #

data SRAction' x r t Source #

An action of a shift-reduce parser.

Constructors

Shift

Shift next token onto stack.

Reduce (Rule' x r t)

Reduce with given rule.

Instances

Instances details
(DebugPrint x, DebugPrint r) => DebugPrint (Action' x r t) Source # 
Instance details

Defined in ParseTable.Pretty

Methods

debugPrint :: Action' x r t -> String Source #

(DebugPrint x, DebugPrint r) => DebugPrint (SRAction' x r t) Source # 
Instance details

Defined in ParseTable.Pretty

Methods

debugPrint :: SRAction' x r t -> String Source #

(Show x, Show r, Show t) => Show (SRAction' x r t) Source # 
Instance details

Defined in ParseTable

Methods

showsPrec :: Int -> SRAction' x r t -> ShowS #

show :: SRAction' x r t -> String #

showList :: [SRAction' x r t] -> ShowS #

type Action' x r t Source #

Arguments

 = Maybe (SRAction' x r t)

Nothing means halt.

data Rule' x r t Source #

Constructors

Rule (NT' x) (Alt' x r t) 

Instances

Instances details
(DebugPrint x, DebugPrint r) => DebugPrint (Rule' x r t) Source # 
Instance details

Defined in ParseTable.Pretty

Methods

debugPrint :: Rule' x r t -> String Source #

(Show x, Show r, Show t) => Show (Rule' x r t) Source # 
Instance details

Defined in ParseTable

Methods

showsPrec :: Int -> Rule' x r t -> ShowS #

show :: Rule' x r t -> String #

showList :: [Rule' x r t] -> ShowS #

(Eq r, Eq t) => Eq (Rule' x r t) Source # 
Instance details

Defined in ParseTable

Methods

(==) :: Rule' x r t -> Rule' x r t -> Bool #

(/=) :: Rule' x r t -> Rule' x r t -> Bool #

(Ord r, Ord t) => Ord (Rule' x r t) Source # 
Instance details

Defined in ParseTable

Methods

compare :: Rule' x r t -> Rule' x r t -> Ordering #

(<) :: Rule' x r t -> Rule' x r t -> Bool #

(<=) :: Rule' x r t -> Rule' x r t -> Bool #

(>) :: Rule' x r t -> Rule' x r t -> Bool #

(>=) :: Rule' x r t -> Rule' x r t -> Bool #

max :: Rule' x r t -> Rule' x r t -> Rule' x r t #

min :: Rule' x r t -> Rule' x r t -> Rule' x r t #

data TraceItem' x r t Source #

A trace is a list of pairs of states and actions.

Constructors

TraceItem 

Fields

Instances

Instances details
(DebugPrint x, DebugPrint r, DebugPrint t) => DebugPrint (Trace' x r t) Source # 
Instance details

Defined in ParseTable.Pretty

Methods

debugPrint :: Trace' x r t -> String Source #

(DebugPrint x, DebugPrint r, DebugPrint t) => DebugPrint (TraceItem' x r t) Source # 
Instance details

Defined in ParseTable.Pretty

Methods

debugPrint :: TraceItem' x r t -> String Source #

(Show t, Show x, Show r) => Show (TraceItem' x r t) Source # 
Instance details

Defined in ParseTable

Methods

showsPrec :: Int -> TraceItem' x r t -> ShowS #

show :: TraceItem' x r t -> String #

showList :: [TraceItem' x r t] -> ShowS #

type Trace' x r t = [TraceItem' x r t] Source #

type Control' x r t (m :: Type -> Type) = SRState' x t -> MaybeT m (SRAction' x r t) Source #

The next action is decided by a control function.

runShiftReduceParser :: (Eq t, Monad m) => Control' x r t m -> Input' t -> m (Trace' x r t) Source #

Run a shift-reduce parser given by control function on some input, Returning a trace of states and actions.

data ParseTable' x r t s Source #

A parse table maps pairs of states and symbols to actions.

Non-terminal Nothing is the end of file. For non-terminals, either a shift or a reduce action is returned. For terminals, a goto action (next state) is returned. If Nothing is returned, the parser halts.

Constructors

ParseTable 

Fields

tabGoto :: forall x r t s f. Functor f => ((s -> NT' x -> Maybe s) -> f (s -> NT' x -> Maybe s)) -> ParseTable' x r t s -> f (ParseTable' x r t s) Source #

tabInit :: forall x r t s f. Functor f => (s -> f s) -> ParseTable' x r t s -> f (ParseTable' x r t s) Source #

tabSR :: forall x r1 t1 s r2 t2 f. Functor f => ((s -> Maybe t1 -> Maybe (Either s (Rule' x r1 t1))) -> f (s -> Maybe t2 -> Maybe (Either s (Rule' x r2 t2)))) -> ParseTable' x r1 t1 s -> f (ParseTable' x r2 t2 s) Source #

type LRStack' s = NonEmpty s Source #

A LR control stack is a non-empty list of states. The bottom element is the initial state.

lr1Control :: ParseTable' x r t s -> Control' x r t (State (LRStack' s)) Source #

The LR control function modifies a control stack. It interprets the parse table.

runLR1Parser :: Eq t => ParseTable' x r t s -> Input' t -> Trace' x r t Source #

Run the LR(1) parser with the given parsetable.

LR(1) parsetable generation.

data ParseItem' x r t Source #

A parse item is a dotted rule X → α.β.

Constructors

ParseItem 

Fields

Instances

Instances details
(DebugPrint x, DebugPrint r, DebugPrint t) => DebugPrint (ParseItem' x r t) Source # 
Instance details

Defined in ParseTable.Pretty

Methods

debugPrint :: ParseItem' x r t -> String Source #

(Show x, Show r, Show t) => Show (ParseItem' x r t) Source # 
Instance details

Defined in ParseTable

Methods

showsPrec :: Int -> ParseItem' x r t -> ShowS #

show :: ParseItem' x r t -> String #

showList :: [ParseItem' x r t] -> ShowS #

(Eq r, Eq t) => Eq (ParseItem' x r t) Source # 
Instance details

Defined in ParseTable

Methods

(==) :: ParseItem' x r t -> ParseItem' x r t -> Bool #

(/=) :: ParseItem' x r t -> ParseItem' x r t -> Bool #

(Ord r, Ord t) => Ord (ParseItem' x r t) Source # 
Instance details

Defined in ParseTable

Methods

compare :: ParseItem' x r t -> ParseItem' x r t -> Ordering #

(<) :: ParseItem' x r t -> ParseItem' x r t -> Bool #

(<=) :: ParseItem' x r t -> ParseItem' x r t -> Bool #

(>) :: ParseItem' x r t -> ParseItem' x r t -> Bool #

(>=) :: ParseItem' x r t -> ParseItem' x r t -> Bool #

max :: ParseItem' x r t -> ParseItem' x r t -> ParseItem' x r t #

min :: ParseItem' x r t -> ParseItem' x r t -> ParseItem' x r t #

piRest :: forall x r t f. Functor f => ([Symbol' x t] -> f [Symbol' x t]) -> ParseItem' x r t -> f (ParseItem' x r t) Source #

piRule :: forall x r1 t r2 f. Functor f => (Rule' x r1 t -> f (Rule' x r2 t)) -> ParseItem' x r1 t -> f (ParseItem' x r2 t) Source #

type Lookahead t Source #

Arguments

 = SetMaybe t

The set of lookahead symbols.

newtype ParseState' x r t Source #

A parse state is a map of parse items to lookahead lists.

Constructors

ParseState 

Fields

Instances

Instances details
(DebugPrint x, DebugPrint r, DebugPrint t) => DebugPrint (ParseState' x r t) Source # 
Instance details

Defined in ParseTable.Pretty

Methods

debugPrint :: ParseState' x r t -> String Source #

(Ord r, Ord t) => Monoid (ParseState' x r t) Source # 
Instance details

Defined in ParseTable

Methods

mempty :: ParseState' x r t #

mappend :: ParseState' x r t -> ParseState' x r t -> ParseState' x r t #

mconcat :: [ParseState' x r t] -> ParseState' x r t #

(Ord r, Ord t) => Semigroup (ParseState' x r t) Source # 
Instance details

Defined in ParseTable

Methods

(<>) :: ParseState' x r t -> ParseState' x r t -> ParseState' x r t #

sconcat :: NonEmpty (ParseState' x r t) -> ParseState' x r t #

stimes :: Integral b => b -> ParseState' x r t -> ParseState' x r t #

(Show x, Show r, Show t) => Show (ParseState' x r t) Source # 
Instance details

Defined in ParseTable

Methods

showsPrec :: Int -> ParseState' x r t -> ShowS #

show :: ParseState' x r t -> String #

showList :: [ParseState' x r t] -> ShowS #

(Eq r, Eq t) => Eq (ParseState' x r t) Source # 
Instance details

Defined in ParseTable

Methods

(==) :: ParseState' x r t -> ParseState' x r t -> Bool #

(/=) :: ParseState' x r t -> ParseState' x r t -> Bool #

(Ord r, Ord t) => Ord (ParseState' x r t) Source # 
Instance details

Defined in ParseTable

Methods

compare :: ParseState' x r t -> ParseState' x r t -> Ordering #

(<) :: ParseState' x r t -> ParseState' x r t -> Bool #

(<=) :: ParseState' x r t -> ParseState' x r t -> Bool #

(>) :: ParseState' x r t -> ParseState' x r t -> Bool #

(>=) :: ParseState' x r t -> ParseState' x r t -> Bool #

max :: ParseState' x r t -> ParseState' x r t -> ParseState' x r t #

min :: ParseState' x r t -> ParseState' x r t -> ParseState' x r t #

complete :: (Ord r, Ord t) => EGrammar' x r t -> ParseState' x r t -> ParseState' x r t Source #

Completing a parse state.

For each (X → α.Yβ, ts), add (Y → .γ, FIRST(β)∘ts)). This might add a whole new item or just extend the token list.

completeStep :: forall x r t. (Ord r, Ord t) => EGrammar' x r t -> ParseState' x r t -> Change (ParseState' x r t) Source #

successors :: (Ord r, Ord t) => EGrammar' x r t -> ParseState' x r t -> Map (Symbol' x t) (ParseState' x r t) Source #

Goto action for a parse state.

ParseState dictionary

type LR0State' x r t = Set (ParseItem' x r t) Source #

LALR: LR0 automaton decorated with lookahead. The LR0State is the keysSet of a ParseState.

type PSDict' x r t = Map (LR0State' x r t) (PState, ParseState' x r t) Source #

The dictionary maps LR0 states to state numbers and their best decoration.

data IPT' x r t Source #

Internal parse table.

Constructors

IPT 

Fields

Instances

Instances details
(Ord r, Ord t, DebugPrint x, DebugPrint r, DebugPrint t) => DebugPrint (WithNTNames x (IPT' x r t)) Source # 
Instance details

Defined in ParseTable.Pretty

Methods

debugPrint :: WithNTNames x (IPT' x r t) -> String Source #

(Ord r, Ord t, DebugPrint x, DebugPrint r, DebugPrint t) => DebugPrint (IPT' x r t) Source # 
Instance details

Defined in ParseTable.Pretty

Methods

debugPrint :: IPT' x r t -> String Source #

(Show x, Show r, Show t) => Show (IPT' x r t) Source # 
Instance details

Defined in ParseTable

Methods

showsPrec :: Int -> IPT' x r t -> ShowS #

show :: IPT' x r t -> String #

showList :: [IPT' x r t] -> ShowS #

type IGotoActions = IntMap PState Source #

Goto actions of a state. Mapping non-terminals to successor states.

data ISRActions' x r t Source #

Shift-reduce actions of a state.

Constructors

ISRActions 

Fields

Instances

Instances details
(Ord r, Ord t, DebugPrint x, DebugPrint r, DebugPrint t) => DebugPrint (ISRActions' x r t) Source # 
Instance details

Defined in ParseTable.Pretty

Methods

debugPrint :: ISRActions' x r t -> String Source #

(Ord r, Ord t) => Monoid (ISRActions' x r t) Source # 
Instance details

Defined in ParseTable

Methods

mempty :: ISRActions' x r t #

mappend :: ISRActions' x r t -> ISRActions' x r t -> ISRActions' x r t #

mconcat :: [ISRActions' x r t] -> ISRActions' x r t #

(Ord r, Ord t) => Semigroup (ISRActions' x r t) Source # 
Instance details

Defined in ParseTable

Methods

(<>) :: ISRActions' x r t -> ISRActions' x r t -> ISRActions' x r t #

sconcat :: NonEmpty (ISRActions' x r t) -> ISRActions' x r t #

stimes :: Integral b => b -> ISRActions' x r t -> ISRActions' x r t #

(Show x, Show r, Show t) => Show (ISRActions' x r t) Source # 
Instance details

Defined in ParseTable

Methods

showsPrec :: Int -> ISRActions' x r t -> ShowS #

show :: ISRActions' x r t -> String #

showList :: [ISRActions' x r t] -> ShowS #

(Eq r, Eq t) => Eq (ISRActions' x r t) Source # 
Instance details

Defined in ParseTable

Methods

(==) :: ISRActions' x r t -> ISRActions' x r t -> Bool #

(/=) :: ISRActions' x r t -> ISRActions' x r t -> Bool #

(Ord r, Ord t) => Ord (ISRActions' x r t) Source # 
Instance details

Defined in ParseTable

Methods

compare :: ISRActions' x r t -> ISRActions' x r t -> Ordering #

(<) :: ISRActions' x r t -> ISRActions' x r t -> Bool #

(<=) :: ISRActions' x r t -> ISRActions' x r t -> Bool #

(>) :: ISRActions' x r t -> ISRActions' x r t -> Bool #

(>=) :: ISRActions' x r t -> ISRActions' x r t -> Bool #

max :: ISRActions' x r t -> ISRActions' x r t -> ISRActions' x r t #

min :: ISRActions' x r t -> ISRActions' x r t -> ISRActions' x r t #

shiftActions :: (Ord r, Ord t) => Map t (ISRAction' x r t) -> ISRActions' x r t Source #

data ISRAction' x r t Source #

Entry of a parse table cell: shift and/or reduce action(s).

Constructors

ISRAction 

Fields

Instances

Instances details
(DebugPrint x, DebugPrint r, DebugPrint t) => DebugPrint (ISRAction' x r t) Source # 
Instance details

Defined in ParseTable.Pretty

Methods

debugPrint :: ISRAction' x r t -> String Source #

(Ord r, Ord t) => Monoid (ISRAction' x r t) Source # 
Instance details

Defined in ParseTable

Methods

mempty :: ISRAction' x r t #

mappend :: ISRAction' x r t -> ISRAction' x r t -> ISRAction' x r t #

mconcat :: [ISRAction' x r t] -> ISRAction' x r t #

(Ord r, Ord t) => Semigroup (ISRAction' x r t) Source # 
Instance details

Defined in ParseTable

Methods

(<>) :: ISRAction' x r t -> ISRAction' x r t -> ISRAction' x r t #

sconcat :: NonEmpty (ISRAction' x r t) -> ISRAction' x r t #

stimes :: Integral b => b -> ISRAction' x r t -> ISRAction' x r t #

(Show x, Show r, Show t) => Show (ISRAction' x r t) Source # 
Instance details

Defined in ParseTable

Methods

showsPrec :: Int -> ISRAction' x r t -> ShowS #

show :: ISRAction' x r t -> String #

showList :: [ISRAction' x r t] -> ShowS #

(Eq r, Eq t) => Eq (ISRAction' x r t) Source # 
Instance details

Defined in ParseTable

Methods

(==) :: ISRAction' x r t -> ISRAction' x r t -> Bool #

(/=) :: ISRAction' x r t -> ISRAction' x r t -> Bool #

(Ord r, Ord t) => Ord (ISRAction' x r t) Source # 
Instance details

Defined in ParseTable

Methods

compare :: ISRAction' x r t -> ISRAction' x r t -> Ordering #

(<) :: ISRAction' x r t -> ISRAction' x r t -> Bool #

(<=) :: ISRAction' x r t -> ISRAction' x r t -> Bool #

(>) :: ISRAction' x r t -> ISRAction' x r t -> Bool #

(>=) :: ISRAction' x r t -> ISRAction' x r t -> Bool #

max :: ISRAction' x r t -> ISRAction' x r t -> ISRAction' x r t #

min :: ISRAction' x r t -> ISRAction' x r t -> ISRAction' x r t #

reductions :: (Ord r, Ord t) => ParseState' x r t -> ISRActions' x r t Source #

Compute the reduce actions for a parse state.

data PTGenState' x r t Source #

Parse table generator state

Constructors

PTGenState 

Fields

iactReduce :: forall x1 r1 t1 x2 r2 t2 f. Functor f => (Set (Rule' x1 r1 t1) -> f (Set (Rule' x2 r2 t2))) -> ISRAction' x1 r1 t1 -> f (ISRAction' x2 r2 t2) Source #

iactShift :: forall x r t f. Functor f => (Maybe PState -> f (Maybe PState)) -> ISRAction' x r t -> f (ISRAction' x r t) Source #

iactEof :: forall x r t f. Functor f => (ISRAction' x r t -> f (ISRAction' x r t)) -> ISRActions' x r t -> f (ISRActions' x r t) Source #

iactTerm :: forall x r t f. Functor f => (Map t (ISRAction' x r t) -> f (Map t (ISRAction' x r t))) -> ISRActions' x r t -> f (ISRActions' x r t) Source #

iptGoto :: forall x r t f. Functor f => (IntMap IGotoActions -> f (IntMap IGotoActions)) -> IPT' x r t -> f (IPT' x r t) Source #

iptSR :: forall x1 r1 t1 x2 r2 t2 f. Functor f => (IntMap (ISRActions' x1 r1 t1) -> f (IntMap (ISRActions' x2 r2 t2))) -> IPT' x1 r1 t1 -> f (IPT' x2 r2 t2) Source #

stIPT :: forall x r t f. Functor f => (IPT' x r t -> f (IPT' x r t)) -> PTGenState' x r t -> f (PTGenState' x r t) Source #

stNext :: forall x r t f. Functor f => (Int -> f Int) -> PTGenState' x r t -> f (PTGenState' x r t) Source #

stPSDict :: forall x r t f. Functor f => (PSDict' x r t -> f (PSDict' x r t)) -> PTGenState' x r t -> f (PTGenState' x r t) Source #

ptState0 :: (Ord r, Ord t) => EGrammar' x r t -> ParseState' x r t Source #

ptGen :: forall x r t. (Ord r, Ord t) => EGrammar' x r t -> IPT' x r t Source #

chooseAction :: ISRAction' x r t -> Maybe (Either PState (Rule' x r t)) Source #

Shift over reduce. First reduce action out of several ones.

constructParseTable' :: forall x r t. (Ord r, Ord t) => IPT' x r t -> ParseTable' x r t PState Source #

Construct the extensional parse table.

constructParseTable :: forall x r t. (Ord r, Ord t) => EGrammar' x r t -> ParseTable' x r t PState Source #

Construct the extensional parse table.

addNewStart :: x -> r -> EGrammar' x r t -> EGrammar' x r t Source #

Add rule %start -> S for new start symbol.