uu-parsinglib-2.9.2: Fast, online, error-correcting, monadic, applicative, merging, permuting, interleaving, idiomatic parser combinators.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.ParserCombinators.UU.Core

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.

Synopsis

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.

Instances

Instances details
IsParser (Gram (P st)) Source # 
Instance details

Defined in Text.ParserCombinators.UU.Interleaved

IsParser (P st) Source # 
Instance details

Defined in Text.ParserCombinators.UU.Core

class Alternative p => ExtAlternative p where Source #

Minimal complete definition

(<<|>), (<?>), must_be_non_empty, must_be_non_empties

Methods

(<<|>) :: p a -> p a -> p a infixl 3 Source #

<<|> 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 a infix 2 Source #

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 -> c Source #

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 -> c Source #

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.

opt :: p a -> a -> p a infixl 2 Source #

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

Instances details
Functor f => ExtAlternative (Gram f) Source # 
Instance details

Defined in Text.ParserCombinators.UU.Interleaved

Methods

(<<|>) :: Gram f a -> Gram f a -> Gram f a Source #

(<?>) :: Gram f a -> String -> Gram f a Source #

must_be_non_empty :: String -> Gram f a -> c -> c Source #

must_be_non_empties :: String -> Gram f a -> Gram f b -> c -> c Source #

opt :: Gram f a -> a -> Gram f a Source #

ExtAlternative (P st) Source # 
Instance details

Defined in Text.ParserCombinators.UU.Core

Methods

(<<|>) :: P st a -> P st a -> P st a Source #

(<?>) :: P st a -> String -> P st a Source #

must_be_non_empty :: String -> P st a -> c -> c Source #

must_be_non_empties :: String -> P st a -> P st b -> c -> c Source #

opt :: P st a -> a -> P st a Source #

class Eof state where Source #

The class Eof contains a function eof which is used to check whether we have reached the end of the input and deletAtEnd should discard any unconsumed input at the end of a successful parse.

Methods

eof :: state -> Bool Source #

deleteAtEnd :: state -> Maybe (Cost, state) Source #

Instances

Instances details
(Show a, ListLike s a) => Eof (Str a s loc) Source # 
Instance details

Defined in Text.ParserCombinators.UU.BasicInstances

Methods

eof :: Str a s loc -> Bool Source #

deleteAtEnd :: Str a s loc -> Maybe (Cost, Str a s loc) Source #

class Show loc => IsLocationUpdatedBy loc str where Source #

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.

Methods

advance Source #

Arguments

:: loc

The current position

-> str

The part which has been removed from the input

-> loc 

class StoresErrors state error | state -> error where Source #

The class StoresErrors is used by the function pErrors which retrieves 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

Instances details
StoresErrors (Str a s loc) (Error loc) Source # 
Instance details

Defined in Text.ParserCombinators.UU.BasicInstances

Methods

getErrors :: Str a s loc -> ([Error loc], Str a s loc) Source #

class HasPosition state pos | state -> pos where Source #

Methods

getPos :: state -> pos Source #

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.

Instances

Instances details
HasPosition (Str a s loc) loc Source # 
Instance details

Defined in Text.ParserCombinators.UU.BasicInstances

Methods

getPos :: Str a s loc -> loc Source #

Types

The parser descriptor

data P st a Source #

Constructors

P (T st a) (Maybe (T st a)) (Maybe a) Nat 

Instances

Instances details
Idiomatic st x (Ii -> P st x) Source # 
Instance details

Defined in Text.ParserCombinators.UU.Idioms

Methods

idiomatic :: P st x -> Ii -> P st x Source #

Idiomatic st f g => Idiomatic st (a -> f) (IF -> Bool -> THEN -> P st a -> ELSE -> P st a -> FI -> g) Source # 
Instance details

Defined in Text.ParserCombinators.UU.Idioms

Methods

idiomatic :: P st (a -> f) -> IF -> Bool -> THEN -> P st a -> ELSE -> P st a -> FI -> g Source #

Idiomatic st f g => Idiomatic st (a -> f) (P st a -> g) Source # 
Instance details

Defined in Text.ParserCombinators.UU.Idioms

Methods

idiomatic :: P st (a -> f) -> P st a -> g Source #

Monad (P st) Source # 
Instance details

Defined in Text.ParserCombinators.UU.Core

Methods

(>>=) :: P st a -> (a -> P st b) -> P st b #

(>>) :: P st a -> P st b -> P st b #

return :: a -> P st a #

Functor (P state) Source # 
Instance details

Defined in Text.ParserCombinators.UU.Core

Methods

fmap :: (a -> b) -> P state a -> P state b #

(<$) :: a -> P state b -> P state a #

Applicative (P state) Source # 
Instance details

Defined in Text.ParserCombinators.UU.Core

Methods

pure :: a -> P state a #

(<*>) :: P state (a -> b) -> P state a -> P state b #

liftA2 :: (a -> b -> c) -> P state a -> P state b -> P state c #

(*>) :: P state a -> P state b -> P state b #

(<*) :: P state a -> P state b -> P state a #

Alternative (P state) Source # 
Instance details

Defined in Text.ParserCombinators.UU.Core

Methods

empty :: P state a #

(<|>) :: P state a -> P state a -> P state a #

some :: P state a -> P state [a] #

many :: P state a -> P state [a] #

MonadPlus (P st) Source # 
Instance details

Defined in Text.ParserCombinators.UU.Core

Methods

mzero :: P st a #

mplus :: P st a -> P st a -> P st a #

Splittable (P st) Source # 
Instance details

Defined in Text.ParserCombinators.UU.Interleaved

Methods

getNonPure :: P st a -> Maybe (P st a) #

getPure :: P st a -> Maybe a #

ExtAlternative (P st) Source # 
Instance details

Defined in Text.ParserCombinators.UU.Core

Methods

(<<|>) :: P st a -> P st a -> P st a Source #

(<?>) :: P st a -> String -> P st a Source #

must_be_non_empty :: String -> P st a -> c -> c Source #

must_be_non_empties :: String -> P st a -> P st b -> c -> c Source #

opt :: P st a -> a -> P st a Source #

IsParser (Gram (P st)) Source # 
Instance details

Defined in Text.ParserCombinators.UU.Interleaved

IsParser (P st) Source # 
Instance details

Defined in Text.ParserCombinators.UU.Core

Show (P st a) Source # 
Instance details

Defined in Text.ParserCombinators.UU.Core

Methods

showsPrec :: Int -> P st a -> ShowS #

show :: P st a -> String #

showList :: [P st a] -> ShowS #

The progress information

data Steps :: * -> * where Source #

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 Progress, 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 Step constructors is as follows:

Step
A token was succesfully recognised, and as a result the input was advanced by the distance Progress
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.

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 
Done :: a -> Steps a 
End_h :: ([a], [a] -> Steps r) -> Steps (a, r) -> Steps (a, r) 
End_f :: [Steps a] -> Steps a -> Steps a 

Instances

Instances details
Show (Steps a) Source # 
Instance details

Defined in Text.ParserCombinators.UU.Core

Methods

showsPrec :: Int -> Steps a -> ShowS #

show :: Steps a -> String #

showList :: [Steps a] -> ShowS #

type Cost = Int Source #

Auxiliary types

data Nat Source #

The data type Nat 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-add` more than necesssary.

Constructors

Zero 
Succ Nat 
Infinite 
Unspecified 
Hole 

Instances

Instances details
Show Nat Source # 
Instance details

Defined in Text.ParserCombinators.UU.Core

Methods

showsPrec :: Int -> Nat -> ShowS #

show :: Nat -> String #

showList :: [Nat] -> ShowS #

Functions

Basic Parsers

micro :: P state a -> Int -> P state a Source #

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 pos Source #

pPos returns the current input position.

pState :: P st st Source #

pState returns the current input state

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 a Source #

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 value of the original type. For the second argument to pSwitch (say split) we expect the following to hold:

 let (n,f) = split st in f n == st

pSymExt :: (forall a. (token -> state -> Steps a) -> state -> Steps a) -> Nat -> Maybe token -> P state token Source #

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 -> a Source #

The function parse 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 partial result; future parsers are expected to run in less space.

parse_h :: Eof t => P t a -> t -> a Source #

The function parse_h behaves like parse but using the history parser. This parser does not give online results, but might run faster.

Acessing and updating various components

getZeroP :: P t a -> Maybe a Source #

getZeroP retrieves the possibly empty part from a descriptor.

getOneP :: P a b -> Maybe (P a b) Source #

getOneP retrieves the non-zero part from a descriptor.

addLength :: Int -> P st a -> P st a Source #

Evaluating the online result

eval :: Steps a -> a Source #

eval 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).

Re-exported modules