Safe Haskell | None |
---|
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
- 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 = P (T st a) (Maybe (T st a)) (Maybe a) Nat
- data Steps 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
- pState :: P st st
- 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)
- addLength :: Int -> P st a -> P st a
- eval :: Steps a -> a
- module Control.Applicative
- module Control.Monad
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
(<<|>) :: p a -> p a -> p aSource
<<|>
is the greedy version of <|>
. If its left hand side parser can
make any progress then it commits to that alternative. 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.
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!!
Functor f => ExtAlternative (Gram f) | |
ExtAlternative (P st) |
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.
class StoresErrors state error | state -> error whereSource
The class StoresErrors
is used by the function pErrors
which retrieves the generated
correction steps since the last time it was called.
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.
StoresErrors (Str a s loc) (Error loc) |
class HasPosition state pos | state -> pos whereSource
getPos
retrieves the correcting steps made since the last time the function was called. The result can,
by using it as the left hand side of a monadic bind, be used to control how to proceed with the parsing process.
HasPosition (Str a s loc) loc |
Types
The parser descriptor
Idiomatic st x (Ii -> P st x) | |
Idiomatic st f g => Idiomatic st (a -> f) (IF -> Bool -> THEN -> P st a -> ELSE -> P st a -> FI -> g) | |
Idiomatic st f g => Idiomatic st (a -> f) (P st a -> g) | |
Monad (P st) | |
Functor (P state) | |
MonadPlus (P st) | |
Applicative (P state) | |
Alternative (P state) | |
Splittable (P st) | |
ExtAlternative (P st) | |
IsParser (Gram (P st)) | |
IsParser (P st) | |
Show (P st a) |
The progress information
The data type Steps
is the core data type around which the parsers are constructed.
It 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 synchronised 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
advanced
by the distanceProgress
Apply
- The type of value represented by the
Steps
changes by applying the function parameter. Fail
- A correcting step has to be 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 Text.ParserCombinators.UU.README.
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 all 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 it 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 value of the original type.
For the second argument to pSwitch
(say split) we expect the following to hold:
pSwitch
let (n,f) = split st in f n == st
pSymExt :: (forall a. (token -> state -> Steps a) -> state -> Steps a) -> Nat -> Maybe token -> P state tokenSource
The basic recognisers are written elsewhere (e.g. in our module Text.ParserCombinataors.UU.BasicInstances;
they (i.e. the parameter splitState
) are lifted to ourP
descriptors by the function pSymExt
which also takes
the minimal number of tokens recognised by the parameter splitState
and an Maybe
value describing the possibly empty value.
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
Acessing and updating various components
Evaluating the online result
removes the progress information from a sequence of steps,
and constructs the value embedded in it.
If you are really desparate to see how your parsers are making progress
(e.g. when you have written an ambiguous parser, and you cannot find
the cause of the exponential blow-up of your parsing process),
you may switch on the trace in the function eval
(you will need to edit the library source code).
eval
Re-exported modules
module Control.Applicative
module Control.Monad