uu-parsinglib-2.3.0: New version of the Utrecht University parser combinator librarySource codeContentsIndex
Text.ParserCombinators.UU.Core
Contents
The Classes Defining the Interface
IsParser
ExtApplicative
Symbol
Provides
Eof
Progress Information
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
class (Applicative p, ExtApplicative p, Alternative p) => IsParser p
class ExtApplicative p where
(<*) :: p a -> p b -> p a
(*>) :: p b -> p a -> p a
(<$) :: a -> p b -> p a
class Symbol p symbol token | p symbol -> token where
pSym :: symbol -> p token
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)
type Cost = Int
type Progress = Int
data Steps a where
Step :: Progress -> Steps a -> Steps a
Apply :: (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 -> a
push :: v -> Steps r -> Steps (v, r)
apply :: Steps (b -> a, (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
newtype P st a = 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)
data Id a = Id a
best_gr :: Steps a -> Steps a -> Steps a
amb :: P st a -> P st [a]
removeEnd_h :: Steps (a, r) -> Steps r
removeEnd_f :: Steps r -> Steps [r]
combinevalues :: Steps [(a, r)] -> Steps ([a], r)
class Stores state errors | state -> errors where
getErrors :: state -> (errors, state)
pErrors :: Stores st errors => P st errors
pEnd :: (Stores st errors, Eof st) => P st errors
pSwitch :: (st1 -> (st2, st2 -> st1)) -> P st2 a -> P st1 a
type Strings = [String]
module Control.Applicative
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
show/hide 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
show/hide 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
show/hide Instances
(Eq a, Show a) => Provides (Str a) a a
(Ord a, Show a) => Provides (Str a) ((,) a a) a
(Ord a, Show a) => Provides (Str a) ((,) a a) a
Show a => Provides (Str a) ((,,) (a -> Bool) String 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
show/hide 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.

type Progress = IntSource
data Steps a whereSource
Constructors
Step :: Progress -> Steps a -> Steps a
Apply :: (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
norm :: Steps a -> Steps aSource
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)
show/hide 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
show/hide Instances
Show a => Show (Id a)
best_gr :: Steps a -> Steps a -> Steps aSource
amb :: P st a -> P st [a]Source
removeEnd_h :: Steps (a, r) -> Steps rSource
removeEnd_f :: Steps r -> Steps [r]Source
combinevalues :: Steps [(a, r)] -> Steps ([a], r)Source
class Stores state errors | state -> errors whereSource
Methods
getErrors :: state -> (errors, state)Source
show/hide Instances
Stores (Str a) ([] (Error a a Int))
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
type Strings = [String]Source
module Control.Applicative
Produced by Haddock version 2.4.2