Text.ParserCombinators.UU.Core
Contents
Description
The module Core contains the basic functionality of the parser library.
It defines the types and implementations of the elementary parsers and recognisers involved.
- class (Alternative p, Applicative p, ExtAlternative p) => IsParser p
- class Alternative p => ExtAlternative p where
- (<<|>) :: p a -> p a -> p a
- (<?>) :: p a -> String -> p a
- doNotInterpret :: p a -> p a
- must_be_non_empty :: String -> p a -> c -> c
- must_be_non_empties :: String -> p a -> p b -> c -> c
- opt :: p a -> a -> p a
- class Eof state where
- eof :: state -> Bool
- deleteAtEnd :: state -> Maybe (Cost, state)
- class Show loc => IsLocationUpdatedBy loc str where
- advance :: loc -> str -> loc
- class StoresErrors state error | state -> error where
- getErrors :: state -> ([error], state)
- class HasPosition state pos | state -> pos where
- getPos :: state -> pos
- data P st a
- data Steps a where
- type Cost = Int
- type Progress = Int
- data Nat
- type Strings = [String]
- micro :: P state a -> Int -> P state a
- amb :: P st a -> P st [a]
- pErrors :: StoresErrors st error => P st [error]
- pPos :: HasPosition st pos => P st pos
- pEnd :: (StoresErrors st error, Eof st) => P st [error]
- pSwitch :: (st1 -> (st2, st2 -> st1)) -> P st2 a -> P st1 a
- pSymExt :: (forall a. (token -> state -> Steps a) -> state -> Steps a) -> Nat -> Maybe token -> P state token
- parse :: Eof t => P t a -> t -> a
- parse_h :: Eof t => P t a -> t -> a
- getZeroP :: P t a -> Maybe a
- getOneP :: P a b -> Maybe (P a b)
- eval :: Steps a -> a
Classes
class (Alternative p, Applicative p, ExtAlternative p) => IsParser p Source
In the class IsParser we assemble the basic properties we expect parsers to have. The class itself does not have any methods.
Most properties come directly from the standard
Control.Applicative module. The class ExtAlternative contains some extra methods we expect our parsers to have.
class Alternative p => ExtAlternative p whereSource
Methods
(<<|>) :: p a -> p a -> p aSource
<<|> is the greedy version of <|>. If its left hand side parser can
make any progress that alternative is committed. Can be used to make
parsers faster, and even get a complete Parsec equivalent behaviour, with
all its (dis)advantages. Intended use p <<|> q <<|> r <|> x <|> y <?> string. Use with care!
(<?>) :: p a -> String -> p 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 the string argument.
doNotInterpret :: p a -> p aSource
doNotInterpret makes a parser opaque for abstract interpretation; used when permuting parsers
where we do not want to compare lengths
must_be_non_empty :: String -> p a -> c -> cSource
must_be_non_empty checks whether its second argument
is a parser which can recognise the empty input. If so, an error message is
given using the String parameter. If not, then the third argument is
returned. This is useful in testing for illogical combinations. For its use see
the module Text.ParserCombinators.UU.Derived.
must_be_non_empties :: String -> p a -> p b -> c -> cSource
must_be_non_empties is similar to must_be_non_empty, 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.
If p can be recognized, the return value of p is used. Otherwise,
the value v is used. Note that opt by default is greedy. If you do not want
this use ...<|> pure v instead. Furthermore, p should not
recognise the empty string, since this would make the parser ambiguous!!
Instances
| ExtAlternative (P st) | |
| Functor f => ExtAlternative (Gram f) |
class Show loc => IsLocationUpdatedBy loc str whereSource
The input state may maintain a location which can be used in generating 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 this location by passing information about the part recognised. This function is typically
called in the splitState functions.
Instances
| IsLocationUpdatedBy Int Char | The first parameter is the current position, and the second parameter the part which has been removed from the input. |
| IsLocationUpdatedBy Int Word8 | |
| IsLocationUpdatedBy LineColPos Char | |
| IsLocationUpdatedBy LineCol Char | |
| IsLocationUpdatedBy loc a => IsLocationUpdatedBy loc [a] |
class StoresErrors state error | state -> error whereSource
The class StoresErrors is used by the function pErrors which retreives the generated
correction steps since the last time it was called.
Methods
getErrors :: state -> ([error], state)Source
getErrors retrieves the correcting steps made since the last time the function was called. The result can,
by using it in a monad, be used to control how to proceed with the parsing process.
Instances
| StoresErrors (Str a s loc) (Error loc) |
class HasPosition state pos | state -> pos whereSource
Methods
getPos retreives the correcting steps made since the last time the function was called. The result can,
by usingit as the left hand sie of a mondaic bind, be used to control how to proceed with the parsing process.
Instances
| HasPosition (Str a s loc) loc |
Types
The parser descriptor
Instances
| Monad (P st) | |
| Functor (P state) | |
| MonadPlus (P st) | |
| Applicative (P state) | |
| Alternative (P state) | |
| ExtAlternative (P st) | |
| IsParser (P st) | |
| Show (P st a) | |
| Idiomatic (Str Char state loc) x (Ii -> P (Str Char state loc) x) | |
| (Idiomatic (Str Char state loc) f g, IsLocationUpdatedBy loc Char, ListLike state Char) => Idiomatic (Str Char state loc) (a -> f) (P (Str Char state loc) a -> g) |
The progress information
The data type Steps 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 ,
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 :: Int -> Steps a -> Steps a | |
| End_h :: ([a], [a] -> Steps r) -> Steps (a, r) -> Steps (a, r) | |
| End_f :: [Steps a] -> Steps a -> Steps a |
Auxiliary types
The 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 function Nat`nat-add` more than necesssary.
Functions
Basic Parsers
micro :: P state a -> Int -> P state aSource
micro inserts a Cost step into the sequence representing the progress the parser is making;
for its use see `Text.ParserCombinators.UU.Demos.Examples`
amb :: P st a -> P st [a]Source
For the precise functioning of the amb combinators see the paper cited in the Text.ParserCombinators.UU.README;
it converts an ambiguous parser into a parser which returns a list of possible recognitions,
pErrors :: StoresErrors st error => P st [error]Source
pErrors returns the error messages that were generated since its last call
pPos :: HasPosition st pos => P st posSource
pPos returns the current input position
pEnd :: (StoresErrors st error, Eof st) => P st [error]Source
The function pEnd should be called at the end of the parsing process. It deletes any unconsumed input, turning them into error messages
pSwitch :: (st1 -> (st2, st2 -> st1)) -> P st2 a -> P st1 aSource
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.
For the second argumnet to pSwitch (say split) we expect the following to hold:
pSwitch
let (n,f) = split st in f n to be equal to st
pSymExt :: (forall a. (token -> state -> Steps a) -> state -> Steps a) -> Nat -> Maybe token -> P state tokenSource
The function pSymExt converts a very basic parser, passed to at as the function splitState,
the minmal number of tokens recognised by the function and and empty descriptor, and builds a P parser out of this,
i.e. lift the behaviour to a fture pareser, a histroy parser and a recogniser.
Calling Parsers
parse :: Eof t => P t a -> t -> aSource
The function shows the prototypical way of running a parser on
some specific input.
By default we use the future parser, since this gives us access to partal
result; future parsers are expected to run in less space.
parse