uulib-0.9.24: Haskell Utrecht Tools Library

Safe HaskellNone
LanguageHaskell98

UU.Parsing.Interface

Contents

Synopsis

Documentation

data AnaParser state result s p a Source #

Instances
(Ord s, Symbol s, InputState state s p, OutputState result, Applicative (AnaParser state result s p)) => Functor (AnaParser state result s p) Source # 
Instance details

Defined in UU.Parsing.Interface

Methods

fmap :: (a -> b) -> AnaParser state result s p a -> AnaParser state result s p b #

(<$) :: a -> AnaParser state result s p b -> AnaParser state result s p a #

(Ord s, Symbol s, InputState state s p, OutputState result) => Applicative (AnaParser state result s p) Source # 
Instance details

Defined in UU.Parsing.Interface

Methods

pure :: a -> AnaParser state result s p a #

(<*>) :: AnaParser state result s p (a -> b) -> AnaParser state result s p a -> AnaParser state result s p b #

liftA2 :: (a -> b -> c) -> AnaParser state result s p a -> AnaParser state result s p b -> AnaParser state result s p c #

(*>) :: AnaParser state result s p a -> AnaParser state result s p b -> AnaParser state result s p b #

(<*) :: AnaParser state result s p a -> AnaParser state result s p b -> AnaParser state result s p a #

(Ord s, Symbol s, InputState state s p, OutputState result) => Alternative (AnaParser state result s p) Source # 
Instance details

Defined in UU.Parsing.Interface

Methods

empty :: AnaParser state result s p a #

(<|>) :: AnaParser state result s p a -> AnaParser state result s p a -> AnaParser state result s p a #

some :: AnaParser state result s p a -> AnaParser state result s p [a] #

many :: AnaParser state result s p a -> AnaParser state result s p [a] #

(InputState inp s p, OutputState out) => StateParser (AnaParser (inp, st) out s p) st Source # 
Instance details

Defined in UU.Parsing.StateParser

Methods

change :: (st -> st) -> AnaParser (inp, st) out s p st Source #

set :: st -> AnaParser (inp, st) out s p st Source #

get :: AnaParser (inp, st) out s p st Source #

(Ord s, Symbol s, InputState state s p, OutputState result) => IsParser (AnaParser state result s p) s Source #

The fast AnaParser instance of the IsParser class. Note that this requires a functioning Ord for the symbol type s, as tokens are often compared using the compare function in Ord rather than always using == rom Eq. The two do need to be consistent though, that is for any two x1, x2 such that x1 == x2 you must have compare x1 x2 == EQ.

Instance details

Defined in UU.Parsing.Interface

Methods

pSucceed :: a -> AnaParser state result s p a Source #

pLow :: a -> AnaParser state result s p a Source #

pFail :: AnaParser state result s p a Source #

pCostRange :: Int# -> s -> SymbolR s -> AnaParser state result s p s Source #

pCostSym :: Int# -> s -> s -> AnaParser state result s p s Source #

pSym :: s -> AnaParser state result s p s Source #

pRange :: s -> SymbolR s -> AnaParser state result s p s Source #

getfirsts :: AnaParser state result s p v -> Expecting s Source #

setfirsts :: Expecting s -> AnaParser state result s p v -> AnaParser state result s p v Source #

getzerop :: AnaParser state result s p v -> Maybe (AnaParser state result s p v) Source #

getonep :: AnaParser state result s p v -> Maybe (AnaParser state result s p v) Source #

pWrap :: OutputState result => (forall r r''. (b -> r -> r'') -> state -> Steps (a, r) s p -> (state -> Steps r s p) -> (state, Steps r'' s p, state -> Steps r s p)) -> (forall r. state -> Steps r s p -> (state -> Steps r s p) -> (state, Steps r s p, state -> Steps r s p)) -> AnaParser state result s p a -> AnaParser state result s p b Source #

pMap :: OutputState result => (forall r r''. (b -> r -> r'') -> state -> Steps (a, r) s p -> (state, Steps r'' s p)) -> (forall r. state -> Steps r s p -> (state, Steps r s p)) -> AnaParser state result s p a -> AnaParser state result s p b Source #

data Pair a r Source #

Constructors

Pair a r 
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 (Applicative p, Alternative p, Functor p) => IsParser p s | p -> s where Source #

The IsParser class contains the base combinators with which to write parsers. A minimal complete instance definition consists of definitions for '(*)', '(|)', pSucceed, pLow, pFail, pCostRange, pCostSym, getfirsts, setfirsts, and getzerop. All operators available through Applicative, 'Functor", and Alternative have the same names suffixed with :.

Minimal complete definition

pLow, pCostRange, pCostSym, getfirsts, setfirsts, getzerop, getonep

Methods

pSucceed :: a -> p a Source #

Two variants of the parser for empty strings. pSucceed parses the empty string, and fully counts as an alternative parse. It returns the value passed to it.

pLow :: a -> p a Source #

pLow parses the empty string, but alternatives to pLow are always preferred over pLow parsing the empty string.

pFail :: p a Source #

This parser always fails, and never returns any value at all.

pCostRange :: Int# -> s -> SymbolR s -> p s Source #

Parses a range of symbols with an associated cost and the symbol to insert if no symbol in the range is present. Returns the actual symbol parsed.

pCostSym :: Int# -> s -> s -> p s Source #

Parses a symbol with an associated cost and the symbol to insert if the symbol to parse isn't present. Returns either the symbol parsed or the symbol inserted.

pSym :: s -> p s Source #

Parses a symbol. Returns the symbol parsed.

pRange :: s -> SymbolR s -> p s Source #

getfirsts :: p v -> Expecting s Source #

Get the firsts set from the parser, i.e. the symbols it expects.

setfirsts :: Expecting s -> p v -> p v Source #

Set the firsts set in the parser.

getzerop :: p v -> Maybe (p v) Source #

getzerop returns Nothing if the parser can not parse the empty string, and returns Just p with p a parser that parses the empty string and returns the appropriate value.

getonep :: p v -> Maybe (p v) Source #

getonep returns Nothing if the parser can only parse the empty string, and returns Just p with p a parser that does not parse any empty string.

Instances
(Ord s, Symbol s, InputState state s p, OutputState result) => IsParser (AnaParser state result s p) s Source #

The fast AnaParser instance of the IsParser class. Note that this requires a functioning Ord for the symbol type s, as tokens are often compared using the compare function in Ord rather than always using == rom Eq. The two do need to be consistent though, that is for any two x1, x2 such that x1 == x2 you must have compare x1 x2 == EQ.

Instance details

Defined in UU.Parsing.Interface

Methods

pSucceed :: a -> AnaParser state result s p a Source #

pLow :: a -> AnaParser state result s p a Source #

pFail :: AnaParser state result s p a Source #

pCostRange :: Int# -> s -> SymbolR s -> AnaParser state result s p s Source #

pCostSym :: Int# -> s -> s -> AnaParser state result s p s Source #

pSym :: s -> AnaParser state result s p s Source #

pRange :: s -> SymbolR s -> AnaParser state result s p s Source #

getfirsts :: AnaParser state result s p v -> Expecting s Source #

setfirsts :: Expecting s -> AnaParser state result s p v -> AnaParser state result s p v Source #

getzerop :: AnaParser state result s p v -> Maybe (AnaParser state result s p v) Source #

getonep :: AnaParser state result s p v -> Maybe (AnaParser state result s p v) Source #

(Symbol s, Ord s, InputState i s p, OutputState o) => IsParser (OffsideParser i o s p) s Source # 
Instance details

Defined in UU.Parsing.Offside

Methods

pSucceed :: a -> OffsideParser i o s p a Source #

pLow :: a -> OffsideParser i o s p a Source #

pFail :: OffsideParser i o s p a Source #

pCostRange :: Int# -> s -> SymbolR s -> OffsideParser i o s p s Source #

pCostSym :: Int# -> s -> s -> OffsideParser i o s p s Source #

pSym :: s -> OffsideParser i o s p s Source #

pRange :: s -> SymbolR s -> OffsideParser i o s p s Source #

getfirsts :: OffsideParser i o s p v -> Expecting s Source #

setfirsts :: Expecting s -> OffsideParser i o s p v -> OffsideParser i o s p v Source #

getzerop :: OffsideParser i o s p v -> Maybe (OffsideParser i o s p v) Source #

getonep :: OffsideParser i o s p v -> Maybe (OffsideParser i o s p v) Source #

type Parser s = AnaParser [s] Pair s (Maybe s) Source #

pCost :: (OutputState out, InputState inp sym pos, Symbol sym, Ord sym) => Int# -> AnaParser inp out sym pos () Source #

getInputState :: (InputState a c d, Symbol c, Ord c, OutputState b) => AnaParser a b c d a Source #

handleEof :: (InputState a s p, Symbol s) => a -> Steps (Pair a ()) s p Source #

parse :: (Symbol s, InputState inp s pos) => AnaParser inp Pair s pos a -> inp -> Steps (Pair a (Pair inp ())) s pos Source #

parseIOMessage :: (Symbol s, InputState inp s p) => (Message s p -> String) -> AnaParser inp Pair s p a -> inp -> IO a Source #

parseIOMessageN :: (Symbol s, InputState inp s p) => (Message s p -> String) -> Int -> AnaParser inp Pair s p a -> inp -> IO a Source #

evalStepsIO :: (Message s p -> String) -> Steps b s p -> IO b Source #

evalStepsIO' :: (Message s p -> String) -> Int -> Steps b s p -> IO b Source #

(<*>) :: Applicative f => f (a -> b) -> f a -> f b infixl 4 #

Sequential application.

A few functors support an implementation of <*> that is more efficient than the default one.

(<*) :: Applicative f => f a -> f b -> f a infixl 4 #

Sequence actions, discarding the value of the second argument.

(*>) :: Applicative f => f a -> f b -> f b infixl 4 #

Sequence actions, discarding the value of the first argument.

(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 #

An infix synonym for fmap.

The name of this operator is an allusion to $. Note the similarities between their types:

 ($)  ::              (a -> b) ->   a ->   b
(<$>) :: Functor f => (a -> b) -> f a -> f b

Whereas $ is function application, <$> is function application lifted over a Functor.

Examples

Expand

Convert from a Maybe Int to a Maybe String using show:

>>> show <$> Nothing
Nothing
>>> show <$> Just 3
Just "3"

Convert from an Either Int Int to an Either Int String using show:

>>> show <$> Left 17
Left 17
>>> show <$> Right 17
Right "17"

Double each element of a list:

>>> (*2) <$> [1,2,3]
[2,4,6]

Apply even to the second element of a pair:

>>> even <$> (2,2)
(2,True)

(<$) :: Functor f => a -> f b -> f a infixl 4 #

Replace all locations in the input with the same value. The default definition is fmap . const, but this may be overridden with a more efficient version.

(<|>) :: Alternative f => f a -> f a -> f a infixl 3 #

An associative binary operation

Orphan instances

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

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 #

(Ord s, Symbol s, InputState state s p, OutputState result, Applicative (AnaParser state result s p)) => Functor (AnaParser state result s p) Source # 
Instance details

Methods

fmap :: (a -> b) -> AnaParser state result s p a -> AnaParser state result s p b #

(<$) :: a -> AnaParser state result s p b -> AnaParser state result s p a #

(Ord s, Symbol s, InputState state s p, OutputState result) => Applicative (AnaParser state result s p) Source # 
Instance details

Methods

pure :: a -> AnaParser state result s p a #

(<*>) :: AnaParser state result s p (a -> b) -> AnaParser state result s p a -> AnaParser state result s p b #

liftA2 :: (a -> b -> c) -> AnaParser state result s p a -> AnaParser state result s p b -> AnaParser state result s p c #

(*>) :: AnaParser state result s p a -> AnaParser state result s p b -> AnaParser state result s p b #

(<*) :: AnaParser state result s p a -> AnaParser state result s p b -> AnaParser state result s p a #

(Ord s, Symbol s, InputState state s p, OutputState result) => Alternative (AnaParser state result s p) Source # 
Instance details

Methods

empty :: AnaParser state result s p a #

(<|>) :: AnaParser state result s p a -> AnaParser state result s p a -> AnaParser state result s p a #

some :: AnaParser state result s p a -> AnaParser state result s p [a] #

many :: AnaParser state result s p a -> AnaParser state result s p [a] #