uulib-0.9.24: Haskell Utrecht Tools Library

Safe HaskellNone
LanguageHaskell98

UU.Parsing.MachineInterface

Synopsis

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

splitStateE, splitState, getPosition

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
InputState Input Char Pos Source # 
Instance details

Defined in UU.Parsing.CharParser

InputState [s] s (Maybe s) Source # 
Instance details

Defined in UU.Parsing.Interface

Methods

splitStateE :: [s] -> Either' [s] s Source #

splitState :: [s] -> (#s, [s]#) Source #

getPosition :: [s] -> Maybe s Source #

reportError :: Message s (Maybe s) -> [s] -> [s] Source #

insertSymbol :: s -> [s] -> [s] Source #

deleteSymbol :: s -> [s] -> [s] Source #

InputState inp s p => InputState (inp, state) s p Source # 
Instance details

Defined in UU.Parsing.StateParser

Methods

splitStateE :: (inp, state) -> Either' (inp, state) s Source #

splitState :: (inp, state) -> (#s, (inp, state)#) Source #

getPosition :: (inp, state) -> p Source #

reportError :: Message s p -> (inp, state) -> (inp, state) Source #

insertSymbol :: s -> (inp, state) -> (inp, state) Source #

deleteSymbol :: s -> (inp, state) -> (inp, state) Source #

InputState inp s p => InputState (OffsideInput inp s p) (OffsideSymbol s) p Source # 
Instance details

Defined in UU.Parsing.Offside

class OutputState r where Source #

Methods

acceptR :: v -> rest -> r v rest Source #

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

Instances
OutputState Pair Source # 
Instance details

Defined in UU.Parsing.Interface

Methods

acceptR :: v -> rest -> Pair v rest Source #

nextR :: (a -> rest -> rest') -> (b -> a) -> Pair b rest -> rest' Source #

class Symbol s where Source #

Minimal complete definition

Nothing

Methods

deleteCost :: s -> Int# Source #

symBefore :: s -> s Source #

symAfter :: s -> s Source #

Instances
Symbol Char Source # 
Instance details

Defined in UU.Parsing.CharParser

Symbol s => Symbol (OffsideSymbol s) Source # 
Instance details

Defined in UU.Parsing.Offside

Symbol (GenToken key tp val) Source # 
Instance details

Defined in UU.Scanner.GenTokenSymbol

Methods

deleteCost :: GenToken key tp val -> Int# Source #

symBefore :: GenToken key tp val -> GenToken key tp val Source #

symAfter :: GenToken key tp val -> GenToken key tp val Source #

data Either' state s Source #

Constructors

Left' !s state 
Right' state 

data Steps val s p Source #

Constructors

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

Fields

Cost 

Fields

StRepair 

Fields

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) Source # 
Instance details

Defined in UU.Parsing.MachineInterface

Methods

showsPrec :: Int -> Action s -> ShowS #

show :: Action s -> String #

showList :: [Action s] -> ShowS #

val :: (a -> b) -> Steps a s p -> Steps b s p Source #

evalSteps :: Steps a s p -> a Source #

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) Source # 
Instance details

Defined in UU.Parsing.MachineInterface

Methods

showsPrec :: Int -> Message s p -> ShowS #

show :: Message s p -> String #

showList :: [Message s p] -> ShowS #

data Expecting s Source #

Constructors

ESym (SymbolR s) 
EStr String 
EOr [Expecting s] 
ESeq [Expecting s] 
Instances
Eq s => Eq (Expecting s) Source # 
Instance details

Defined in UU.Parsing.MachineInterface

Methods

(==) :: Expecting s -> Expecting s -> Bool #

(/=) :: Expecting s -> Expecting s -> Bool #

Ord s => Ord (Expecting s) Source # 
Instance details

Defined in UU.Parsing.MachineInterface

(Eq s, Show s) => Show (Expecting s) Source # 
Instance details

Defined in UU.Parsing.MachineInterface

data SymbolR s Source #

Constructors

Range !s !s 
EmptyR 
Instances
Eq s => Eq (SymbolR s) Source # 
Instance details

Defined in UU.Parsing.MachineInterface

Methods

(==) :: SymbolR s -> SymbolR s -> Bool #

(/=) :: SymbolR s -> SymbolR s -> Bool #

Ord s => Ord (SymbolR s) Source # 
Instance details

Defined in UU.Parsing.MachineInterface

Methods

compare :: SymbolR s -> SymbolR s -> Ordering #

(<) :: SymbolR s -> SymbolR s -> Bool #

(<=) :: SymbolR s -> SymbolR s -> Bool #

(>) :: SymbolR s -> SymbolR s -> Bool #

(>=) :: SymbolR s -> SymbolR s -> Bool #

max :: SymbolR s -> SymbolR s -> SymbolR s #

min :: SymbolR s -> SymbolR s -> SymbolR s #

(Eq s, Show s) => Show (SymbolR s) Source # 
Instance details

Defined in UU.Parsing.MachineInterface

Methods

showsPrec :: Int -> SymbolR s -> ShowS #

show :: SymbolR s -> String #

showList :: [SymbolR s] -> ShowS #

mk_range :: Ord s => s -> s -> SymbolR s Source #

symInRange :: Ord a => SymbolR a -> a -> Bool Source #

symRS :: Ord a => SymbolR a -> a -> Ordering Source #

except :: (Foldable t, Ord s, Symbol s) => SymbolR s -> t s -> [SymbolR s] Source #

systemerror :: [Char] -> [Char] -> a Source #