uu-parsinglib-2.3.1: New version of the Utrecht University parser combinator library

Text.ParserCombinators.UU.Core

Contents

Description

The module Core contains the basic functionality of the parser library. It takes care of the breadth-first search, the online generation of results, the core error correction administration, dealing with ambigous grammars, and the type for both kinds of parsers involved and the recognisers.

Synopsis

The Classes Defining the Interface

IsParser

class (Applicative p, ExtApplicative p, Alternative p) => IsParser p Source

This class collects a number of classes which together defines what a Parser should provide. Since it is just a predicate we have prefixed the name by the phrase Is

ExtApplicative

class ExtApplicative p whereSource

The module Control.Applicative contains definitions for <$, *> and <* which cannot be changed. Since we want to give optimised implementations of these combinators, we hide those definitions, and define a class containing their signatures.

Methods

(<*) :: p a -> p b -> p aSource

(*>) :: p b -> p a -> p aSource

(<$) :: a -> p b -> p aSource

Instances

Symbol

class Symbol p symbol token | p symbol -> token whereSource

Many parsing libraries do not make a distinction between the terminal symbols of the language recognised and the tokens actually constructed from the input. This happens e.g. if we want to recognise an integer or an identifier: we are also interested in which integer occurred in the input, or which identifier. Note that if the alternative later fails repair will take place, instead of trying the other altrenatives at the greedy choice point.

The function pSym takes as argument a value of some type symbol, and returns a value of type token. The parser will in general depend on some state which is maintained holding the input. The functional dependency fixes the token type, based on the symbol type and the type of the parser p. Since pSym is overloaded both the type and the value of symbol determine how to decompose the input in a token and the remaining input.

Methods

pSym :: symbol -> p tokenSource

Instances

Provides state symbol token => Symbol (P state) symbol token 

Provides

class Provides state symbol token | state symbol -> token whereSource

Methods

splitState :: symbol -> (token -> state -> Steps a) -> state -> Steps aSource

Instances

(Eq a, Show a) => Provides (Str a) a a 
(Ord a, Show a) => Provides (Str a) (a, a) a 
Show a => Provides (Str a) (a -> Bool, String, a) a 

Eof

class Eof state whereSource

Methods

eof :: state -> BoolSource

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

Instances

Eof (Str a) 

Progress Information

type Cost = IntSource

The data type Steps is the core data type around which the parsers are constructed. It is a stream containing both the result of the parsing process, albeit often in a fragmented way, and progress information. Recognising a token should correspond to a certain amount of Progress, which for the time being in an Int.

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 made to the input; the first parameter contains the error messages coresponding to the possible correcting steps, and the second parameter generated the various corrected alternatives, each with an associated Cost

The last two alternatives play a role in recognising ambigous non-terminals. For a full description see the technical report.

data Steps a whereSource

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

eval :: Steps a -> aSource

push :: v -> Steps r -> Steps (v, r)Source

apply :: Steps (b -> a, (b, r)) -> Steps (a, r)Source

best :: Steps a -> Steps a -> Steps aSource

best' :: Steps b -> Steps b -> Steps bSource

getCheapest :: Int -> [(Int, Steps a)] -> Steps aSource

traverse :: Int -> Steps a -> Int -> Int -> IntSource

newtype P st a Source

Constructors

P (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

Monad (P st) 
Functor (P state) 
Applicative (P state) 
Alternative (P state) 
ExtApplicative (P st) 
Provides state symbol token => Symbol (P state) symbol token 

data Id a Source

Constructors

Id a 

Instances

Show a => Show (Id a) 

amb :: P st a -> P st [a]Source

combinevalues :: Steps [(a, r)] -> Steps ([a], r)Source

class Stores state errors | state -> errors whereSource

Methods

getErrors :: state -> (errors, state)Source

Instances

Stores (Str a) [Error a a Int] 

pErrors :: Stores st errors => P st errorsSource

pEnd :: (Stores st errors, Eof st) => P st errorsSource

pSwitch :: (st1 -> (st2, st2 -> st1)) -> P st2 a -> P st1 aSource