| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
UU.Parsing.MachineInterface
Synopsis
- class InputState state s pos | state -> s, state -> pos where- splitStateE :: state -> Either' state s
- splitState :: state -> (#s, state#)
- getPosition :: state -> pos
- reportError :: Message s pos -> state -> state
- insertSymbol :: s -> state -> state
- deleteSymbol :: s -> state -> state
 
- class OutputState r where
- class Symbol s where- deleteCost :: s -> Int#
- symBefore :: s -> s
- symAfter :: s -> s
 
- data Either' state s
- data Steps val s p
- data Action s
- val :: (a -> b) -> Steps a s p -> Steps b s p
- evalSteps :: Steps a s p -> a
- getMsgs :: Steps a s p -> [Message s p]
- data Message sym pos = Msg (Expecting sym) !pos (Action sym)
- data Expecting s
- data SymbolR s
- mk_range :: Ord s => s -> s -> SymbolR s
- symInRange :: Ord a => SymbolR a -> a -> Bool
- symRS :: Ord a => SymbolR a -> a -> Ordering
- except :: (Foldable t, Ord s, Symbol s) => SymbolR s -> t s -> [SymbolR s]
- usererror :: [Char] -> a
- systemerror :: [Char] -> [Char] -> a
Documentation
class InputState state s pos | state -> s, state -> pos where Source #
The InputState class contains the interface that the AnaParser
 parsers expect for the input. A minimal complete instance definition
 consists of splitStateE, splitState and getPosition.
Minimal complete definition
Methods
splitStateE :: state -> Either' state s Source #
Splits the state in a strict variant of Either, with Left' if a symbol
   can be split off and Right' if none can
splitState :: state -> (#s, state#) Source #
Splits the state in the first symbol and the remaining state
getPosition :: state -> pos Source #
Gets the current position in the input
reportError :: Message s pos -> state -> state Source #
Reports an error
insertSymbol :: s -> state -> state Source #
Modify the state as the result of inserting a symbol s in the input.
 The symbol that has already been considered as having been inserted 
 is passed. It should normally not be added to the state.
deleteSymbol :: s -> state -> state Source #
Modify the state as the result of deleting a symbol s from the input.
 The symbol that has already been deleted from the input state is passed.
 It should normally not be deleted from the state.
Instances
class OutputState r where Source #
Minimal complete definition
Nothing
Instances
| Symbol Char Source # | |
| Symbol s => Symbol (OffsideSymbol s) Source # | |
| Defined in UU.Parsing.Offside Methods deleteCost :: OffsideSymbol s -> Int# Source # symBefore :: OffsideSymbol s -> OffsideSymbol s Source # symAfter :: OffsideSymbol s -> OffsideSymbol s Source # | |
| Symbol (GenToken key tp val) Source # | |
Instances
| Eq s => Eq (Expecting s) Source # | |
| Ord s => Ord (Expecting s) Source # | |
| Defined in UU.Parsing.MachineInterface | |
| (Eq s, Show s) => Show (Expecting s) Source # | |
Instances
| Eq s => Eq (SymbolR s) Source # | |
| Ord s => Ord (SymbolR s) Source # | |
| (Eq s, Show s) => Show (SymbolR s) Source # | |
systemerror :: [Char] -> [Char] -> a Source #