uulib-0.9.8: Haskell Utrecht Tools Library

UU.Parsing.MachineInterface

Synopsis

Documentation

class InputState state s pos | state -> s, state -> pos whereSource

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.

Methods

splitStateE :: state -> Either' state sSource

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 -> posSource

Gets the current position in the input

reportError :: Message s pos -> state -> stateSource

Reports an error

insertSymbol :: s -> state -> stateSource

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 -> stateSource

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

InputState Input Char Pos 
InputState [s] s (Maybe s) 
InputState inp s p => InputState (inp, state) s p 
InputState inp s p => InputState (OffsideInput inp s p) (OffsideSymbol s) p 

class OutputState r whereSource

Methods

acceptR :: v -> rest -> r v restSource

nextR :: (a -> rest -> rest') -> (b -> a) -> r b rest -> rest'Source

Instances

class Symbol s whereSource

Methods

deleteCost :: s -> Int#Source

symBefore :: s -> sSource

symAfter :: s -> sSource

Instances

data Either' state s Source

Constructors

Left' !s state 
Right' state 

data Steps val s p Source

Constructors

forall a . OkVal (a -> val) (Steps a s p) 
Ok 

Fields

rest :: Steps val s p
 
Cost 

Fields

costing :: Int#
 
rest :: Steps val s p
 
StRepair 

Fields

costing :: Int#
 
m :: !(Message s p)
 
rest :: Steps val s p
 
Best (Steps val s p) (Steps val s p) (Steps val s p) 
NoMoreSteps val 

data Action s Source

Constructors

Insert s 
Delete s 
Other String 

Instances

Show s => Show (Action s) 

val :: (a -> b) -> Steps a s p -> Steps b s pSource

evalSteps :: Steps a s p -> aSource

getMsgs :: Steps a s p -> [Message s p]Source

data Message sym pos Source

Constructors

Msg (Expecting sym) !pos (Action sym) 

Instances

(Eq s, Show s, Show p) => Show (Message s p) 

data Expecting s Source

Constructors

ESym (SymbolR s) 
EStr String 
EOr [Expecting s] 
ESeq [Expecting s] 

Instances

Eq s => Eq (Expecting s) 
Ord s => Ord (Expecting s) 
(Eq s, Show s) => Show (Expecting s) 

data SymbolR s Source

Constructors

Range !s !s 
EmptyR 

Instances

Eq s => Eq (SymbolR s) 
Ord s => Ord (SymbolR s) 
(Eq s, Show s) => Show (SymbolR s)