Text.ParserCombinators.UU.Core
Contents
ProvidesEofLocation- The triples containg a history, a future parser and a recogniser:
T - The descriptor
of a parser, including the tupled parser corresponding to this descriptorP - Additional useful combinators
- Controlling the text of error reporting:
<?> - Parsers can be disambiguated using micro-steps:
micro - Dealing with (non-empty) Ambigous parsers:
amb - Parse errors can be retreived from the state:
pErrors - The current position can be retreived from the state:
pPos - Starting and finalising the parsing process:
andpEndparse - The state may be temporarily change type:
pSwitch
- Controlling the text of error reporting:
- Maintaining Progress Information
- Auxiliary functions and types
Description
The module Core contains the basic functionality of the parser library.
It uses the breadth-first module to realise online generation of results, the error
correction administration, dealing with ambigous grammars; it defines the types of the elementary parsers
and recognisers involved.For typical use cases of the libray see the module Text.ParserCombinators.UU.Examples
- class Provides state symbol token | state symbol -> token where
- splitState :: symbol -> (token -> state -> Steps a) -> state -> Steps a
- class Eof state where
- eof :: state -> Bool
- deleteAtEnd :: state -> Maybe (Cost, state)
- class IsLocationUpdatedBy loc a where
- advance :: loc -> a -> loc
- class ExtAlternative p where
- (<<|>) :: p a -> p a -> p a
- data T st a = T (forall r. (a -> st -> Steps r) -> st -> Steps r) (forall r. (st -> Steps r) -> st -> Steps (a, r)) (forall r. (st -> Steps r) -> st -> Steps r)
- choose :: (forall a. Steps a -> Steps a -> Steps a) -> T st a -> T st a -> T st a
- data P st a = P (T st a) (Maybe (T st a)) Nat (Maybe a)
- pSymExt :: Provides state symbol token => Nat -> Maybe token -> symbol -> P state token
- pSym :: Provides state symbol token => symbol -> P state token
- (<?>) :: P state a -> String -> P state a
- amb :: P st a -> P st [a]
- class Stores state error | state -> error where
- getErrors :: state -> ([error], state)
- pErrors :: Stores st error => P st [error]
- class HasPosition state pos | state -> pos where
- getPos :: state -> pos
- pPos :: HasPosition st pos => P st pos
- pEnd :: (Stores st error, Eof st) => P st [error]
- parse :: Eof t => P t a -> t -> a
- pSwitch :: (st1 -> (st2, st2 -> st1)) -> P st2 a -> P st1 a
- type Cost = Int
- type Progress = Int
- type Strings = [String]
- data Steps a where
- eval :: Steps a -> a
- push :: v -> Steps r -> Steps (v, r)
- apply :: Steps (b -> a, (b, r)) -> Steps (a, r)
- pushapply :: (b -> a) -> Steps (b, r) -> Steps (a, r)
- norm :: Steps a -> Steps a
- best :: Steps a -> Steps a -> Steps a
- best' :: Steps b -> Steps b -> Steps b
- getCheapest :: Int -> [(Int, Steps a)] -> Steps a
- traverse :: Int -> Steps a -> Int -> Int -> Int
- removeEnd_h :: Steps (a, r) -> Steps r
- removeEnd_f :: Steps r -> Steps [r]
- must_be_non_empty :: [Char] -> P t t1 -> t2 -> t2
- must_be_non_empties :: [Char] -> P t1 t -> P t3 t2 -> t4 -> t4
- data Nat
- module Control.Applicative
Provides
class Provides state symbol token | state symbol -> token whereSource
The function splitState playes a crucial role in splitting up the state. The symbol parameter tells us what kind of thing, and even which value of that kind, is expected from the input.
The state and and the symbol type together determine what kind of token has to be returned. Since the function is overloaded we do not have to invent
all kind of different names for our elementary parsers.
Methods
splitState :: symbol -> (token -> state -> Steps a) -> state -> Steps aSource
Instances
| (Eq a, Show a, IsLocationUpdatedBy loc a) => Provides (Str a loc) a a | |
| (Show a, Eq a, IsLocationUpdatedBy loc [a]) => Provides (Str a loc) (Token a) [a] | |
| (Show a, IsLocationUpdatedBy loc [a]) => Provides (Str a loc) (Munch a) [a] | |
| (Ord a, Show a, IsLocationUpdatedBy loc a) => Provides (Str a loc) (a, a) a | |
| (Show a, IsLocationUpdatedBy loc a) => Provides (Str a loc) (a -> Bool, String, a) a |
Eof
Location
class IsLocationUpdatedBy loc a whereSource
The input state may contain a location which can be used in error messages. Since we do not want to fix our input to be just a String we provide an interface
which can be used to advance the location by passing its information in the function splitState
Instances
class ExtAlternative p whereSource
In order to be able to describe greedy parsers we introduce an extra operator, whch indicates a biased choice
Instances
| ExtAlternative Maybe | |
| ExtAlternative (P st) |
|
The triples containg a history, a future parser and a recogniser: T
TConstructors
| T (forall r. (a -> st -> Steps r) -> st -> Steps r) (forall r. (st -> Steps r) -> st -> Steps (a, r)) (forall r. (st -> Steps r) -> st -> Steps r) |
Instances
| Functor (T st) | |
| Applicative (T state) | |
| Alternative (T state) |
Triples are Applicative: <*>, <*, *> and pure
<*><**>pureThe descriptor P of a parser, including the tupled parser corresponding to this descriptor
PInstances
| Monad (P st) | |
| Functor (P state) | |
| MonadPlus (P st) | |
| Applicative (P state) | |
| Alternative (P state) | |
| ExtAlternative (P st) |
|
Parsers are functors: fmap
fmapParsers are Applicative: <*>, <*, *> and pure
<*><**>pureParsers are Alternative: <|> and empty
<|>emptyAn alternative for the Alternative, which is greedy: <<|>
<<|>Parsers can recognise single tokens: pSym and pSymExt
pSympSymExtpSymExt :: Provides state symbol token => Nat -> Maybe token -> symbol -> P state tokenSource
Since pSymExt is overloaded both the type and the value of symbol determine how to decompose the input in a token
and the remaining input.
pSymExt takes two extra parameters: one describing the minimal number of tokens recognised,
and the second whether the symbol can recognise the empty string and the value which is to be returned in that case
pSym :: Provides state symbol token => symbol -> P state tokenSource
covers the most common case of recognsiing a symbol: a single token is removed form the input,
and it cannot recognise the empty string
pSym
Parsers are Monads: >>= and return
>>=returnAdditional useful combinators
Controlling the text of error reporting: <?>
<?>(<?>) :: P state a -> String -> P state aSource
The parsers build a list of symbols which are expected at a specific point.
This list is used to report errors.
Quite often it is more informative to get e.g. the name of the non-terminal.
The combinator replaces this list of symbols by it's righ-hand side argument.
<?>
Parsers can be disambiguated using micro-steps: micro
microDealing with (non-empty) Ambigous parsers: amb
ambParse errors can be retreived from the state: pErrors
pErrorsclass Stores state error | state -> error whereSource
getErrors retreives the correcting steps made since the last time the function was called. The result can,
using a monad, be used to control how to-- proceed with the parsing process.
The current position can be retreived from the state: pPos
pPosclass HasPosition state pos | state -> pos whereSource
pPos retreives the correcting steps made since the last time the function was called. The result can,
using a monad, be used to control how to-- proceed with the parsing process.
Instances
| HasPosition (Str a loc) loc |
pPos :: HasPosition st pos => P st posSource
Starting and finalising the parsing process: pEnd and parse
pEndparsepEnd :: (Stores st error, Eof st) => P st [error]Source
The function pEnd should be called at the end of the parsing process. It deletes any unsonsumed input, and reports its preence as an eror.
The state may be temporarily change type: pSwitch
pSwitchpSwitch :: (st1 -> (st2, st2 -> st1)) -> P st2 a -> P st1 aSource
pSwitch takes the current state and modifies it to a different type of state to which its argument parser is applied.
The second component of the result is a function which converts the remaining state of this parser back into a valuee of the original type.
Maintaining Progress Information
The data type is the core data type around which the parsers are constructed.
It is a describes a tree structure of streams containing (in an interleaved way) both the online result of the parsing process,
and progress information. Recognising an input token should correspond to a certain amount of Steps,
which tells how much of the input state was consumed.
The Progress is used to implement the breadth-first search process, in which alternatives are
examined in a more-or-less synchonised way. The meaning of the various Progress constructors is as follows:
Step
Step- A token was succesfully recognised, and as a result the input was
advancedby the distanceProgress Apply- The type of value represented by the
Stepschanges by applying the function parameter. Fail- A correcting step has to made to the input; the first parameter contains information about what was expected in the input,
and the second parameter describes the various corrected alternatives, each with an associated
Cost Micro- A small cost is inserted in the sequence, which is used to disambiguate. Use with care!
The last two alternatives play a role in recognising ambigous non-terminals. For a full description see the technical report referred to from the README file..
Constructors
| Step :: Progress -> Steps a -> Steps a | |
| Apply :: forall a b. (b -> a) -> Steps b -> Steps a | |
| Fail :: Strings -> [Strings -> (Cost, Steps a)] -> Steps a | |
| Micro :: Cost -> Steps a -> Steps a | |
| End_h :: ([a], [a] -> Steps r) -> Steps (a, r) -> Steps (a, r) | |
| End_f :: [Steps a] -> Steps a -> Steps a |
removeEnd_h :: Steps (a, r) -> Steps rSource
removeEnd_f :: Steps r -> Steps [r]Source
Auxiliary functions and types
Checking for non-sensical combinations: must_be_non_empty and must_be_non_empties
must_be_non_emptymust_be_non_emptiesmust_be_non_empty :: [Char] -> P t t1 -> t2 -> t2Source
The function checks wehther its second argument is a parser which can recognise the mety sequence. If so an error message is given using the name of the context. If not then the third argument is returned. This is useful in testing for loogical combinations. For its use see the module Text>parserCombinators.UU.Derived
must_be_non_empties :: [Char] -> P t1 t -> P t3 t2 -> t4 -> t4Source
This function is similar to the above, but can be used in situations where we recognise a sequence of elements separated by other elements. This does not make sense if both parsers can recognise the empty string. Your grammar is then highly ambiguous.
The type Nat for describing the minimal number of tokens consumed
NatThe data type is used to represent the minimal length of a parser.
Care should be taken in order to not evaluate the right hand side of the binary functions Nat and nat_min`nat-add` more than necesssary.
module Control.Applicative