| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
ParseTable
Description
LR-parser.
Synopsis
- newtype Stack' x t = Stack [Symbol' x t]
- type Input' t = [t]
- data SRState' x t = SRState {}
- srInput :: forall x t f. Functor f => (Input' t -> f (Input' t)) -> SRState' x t -> f (SRState' x t)
- srStack :: forall x1 t x2 f. Functor f => (Stack' x1 t -> f (Stack' x2 t)) -> SRState' x1 t -> f (SRState' x2 t)
- data SRAction' x r t
- type Action' x r t = Maybe (SRAction' x r t)
- data Rule' x r t = Rule (NT' x) (Alt' x r t)
- data TraceItem' x r t = TraceItem {}
- type Trace' x r t = [TraceItem' x r t]
- type Control' x r t (m :: Type -> Type) = SRState' x t -> MaybeT m (SRAction' x r t)
- runShiftReduceParser :: (Eq t, Monad m) => Control' x r t m -> Input' t -> m (Trace' x r t)
- data ParseTable' x r t s = ParseTable {}
- 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)
- tabInit :: forall x r t s f. Functor f => (s -> f s) -> ParseTable' x r t s -> f (ParseTable' x r t s)
- 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)
- type LRStack' s = NonEmpty s
- lr1Control :: ParseTable' x r t s -> Control' x r t (State (LRStack' s))
- runLR1Parser :: Eq t => ParseTable' x r t s -> Input' t -> Trace' x r t
- data ParseItem' x r t = ParseItem {}
- piRest :: forall x r t f. Functor f => ([Symbol' x t] -> f [Symbol' x t]) -> ParseItem' x r t -> f (ParseItem' x r t)
- 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)
- type Lookahead t = SetMaybe t
- newtype ParseState' x r t = ParseState {
- theParseState :: Map (ParseItem' x r t) (Lookahead t)
- complete :: (Ord r, Ord t) => EGrammar' x r t -> ParseState' x r t -> ParseState' x r t
- completeStep :: forall x r t. (Ord r, Ord t) => EGrammar' x r t -> ParseState' x r t -> Change (ParseState' x r t)
- successors :: (Ord r, Ord t) => EGrammar' x r t -> ParseState' x r t -> Map (Symbol' x t) (ParseState' x r t)
- type PState = Int
- initPState :: Integer
- type LR0State' x r t = Set (ParseItem' x r t)
- lr0state :: ParseState' x r t -> LR0State' x r t
- type PSDict' x r t = Map (LR0State' x r t) (PState, ParseState' x r t)
- data IPT' x r t = IPT {
- _iptSR :: IntMap (ISRActions' x r t)
- _iptGoto :: IntMap IGotoActions
- type IGotoActions = IntMap PState
- data ISRActions' x r t = ISRActions {
- _iactEof :: ISRAction' x r t
- _iactTerm :: Map t (ISRAction' x r t)
- shiftActions :: (Ord r, Ord t) => Map t (ISRAction' x r t) -> ISRActions' x r t
- data ISRAction' x r t = ISRAction {
- _iactShift :: Maybe PState
- _iactReduce :: Set (Rule' x r t)
- emptyAction :: ISRAction' x r t
- shiftAction :: PState -> ISRAction' x r t
- reduceAction :: Rule' x r t -> ISRAction' x r t
- reductions :: (Ord r, Ord t) => ParseState' x r t -> ISRActions' x r t
- data PTGenState' x r t = PTGenState {}
- 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)
- iactShift :: forall x r t f. Functor f => (Maybe PState -> f (Maybe PState)) -> ISRAction' x r t -> f (ISRAction' x r t)
- 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)
- 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)
- iptGoto :: forall x r t f. Functor f => (IntMap IGotoActions -> f (IntMap IGotoActions)) -> IPT' x r t -> f (IPT' x r t)
- 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)
- 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)
- stNext :: forall x r t f. Functor f => (Int -> f Int) -> PTGenState' x r t -> f (PTGenState' x r t)
- 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)
- ptState0 :: (Ord r, Ord t) => EGrammar' x r t -> ParseState' x r t
- ptGen :: forall x r t. (Ord r, Ord t) => EGrammar' x r t -> IPT' x r t
- chooseAction :: ISRAction' x r t -> Maybe (Either PState (Rule' x r t))
- constructParseTable' :: forall x r t. (Ord r, Ord t) => IPT' x r t -> ParseTable' x r t PState
- constructParseTable :: forall x r t. (Ord r, Ord t) => EGrammar' x r t -> ParseTable' x r t PState
- addNewStart :: x -> r -> EGrammar' x r t -> EGrammar' x r t
Documentation
A stack is a sentential form (reversed).
Instances
| (DebugPrint x, DebugPrint t) => DebugPrint (Stack' x t) Source # | |
Defined in ParseTable.Pretty Methods debugPrint :: Stack' x t -> String Source # | |
| (Show t, Show x) => Show (Stack' x t) Source # | |
| Eq t => Eq (Stack' x t) Source # | |
| Ord t => Ord (Stack' x t) Source # | |
The state of a shift-reduce parser consists of a stack and some input.
Instances
| (DebugPrint x, DebugPrint t) => DebugPrint (SRState' x t) Source # | |
Defined in ParseTable.Pretty Methods debugPrint :: SRState' x t -> String Source # | |
| (Show t, Show x) => Show (SRState' x t) Source # | |
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 #
An action of a shift-reduce parser.
Instances
| (DebugPrint x, DebugPrint r) => DebugPrint (Action' x r t) Source # | |
Defined in ParseTable.Pretty Methods debugPrint :: Action' x r t -> String Source # | |
| (DebugPrint x, DebugPrint r) => DebugPrint (SRAction' x r t) Source # | |
Defined in ParseTable.Pretty Methods debugPrint :: SRAction' x r t -> String Source # | |
| (Show x, Show r, Show t) => Show (SRAction' x r t) Source # | |
Instances
| (DebugPrint x, DebugPrint r) => DebugPrint (Rule' x r t) Source # | |
Defined in ParseTable.Pretty Methods debugPrint :: Rule' x r t -> String Source # | |
| (Show x, Show r, Show t) => Show (Rule' x r t) Source # | |
| (Eq r, Eq t) => Eq (Rule' x r t) Source # | |
| (Ord r, Ord t) => Ord (Rule' x r t) Source # | |
Defined in ParseTable | |
data TraceItem' x r t Source #
A trace is a list of pairs of states and actions.
Instances
| (DebugPrint x, DebugPrint r, DebugPrint t) => DebugPrint (Trace' x r t) Source # | |
Defined in ParseTable.Pretty Methods debugPrint :: Trace' x r t -> String Source # | |
| (DebugPrint x, DebugPrint r, DebugPrint t) => DebugPrint (TraceItem' x r t) Source # | |
Defined in ParseTable.Pretty Methods debugPrint :: TraceItem' x r t -> String Source # | |
| (Show t, Show x, Show r) => Show (TraceItem' x r t) Source # | |
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 #
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 | |
Instances
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 #
newtype ParseState' x r t Source #
A parse state is a map of parse items to lookahead lists.
Constructors
| ParseState | |
Fields
| |
Instances
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
initPState :: Integer Source #
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.
lr0state :: ParseState' x r t -> LR0State' x r t Source #
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.
Internal parse table.
Constructors
| IPT | |
Fields
| |
Instances
| (Ord r, Ord t, DebugPrint x, DebugPrint r, DebugPrint t) => DebugPrint (WithNTNames x (IPT' x r t)) Source # | |
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 # | |
Defined in ParseTable.Pretty Methods debugPrint :: IPT' x r t -> String Source # | |
| (Show x, Show r, Show t) => Show (IPT' x r t) Source # | |
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
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
emptyAction :: ISRAction' x r t Source #
shiftAction :: PState -> ISRAction' x r t Source #
reduceAction :: Rule' x r t -> ISRAction' x r t Source #
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
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 #
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.