uu-parsinglib-2.1.0: New version of the Utrecht University parser combinator librarySource codeContentsIndex
Text.ParserCombinators.UU.Parsing
Documentation
class (Applicative p, Alternative p) => Parser p Source
class Symbol p symbol token | symbol -> token whereSource
Methods
pSym :: symbol -> p tokenSource
show/hide Instances
Provides state symbol token => Symbol (R state) symbol token
Provides state symbol token => Symbol (P_m state) symbol token
Provides state symbol token => Symbol (P_f state) symbol token
Provides state symbol token => Symbol (P_h state) symbol token
type Strings = [String]Source
type Cost = IntSource
type Progress = IntSource
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
class Eof state whereSource
Methods
eof :: state -> BoolSource
deleteAtEnd :: state -> Maybe (Cost, state)Source
show/hide Instances
Eof (Str a)
class Parse p whereSource
Methods
parse :: Eof state => p state a -> state -> aSource
show/hide Instances
data Steps a whereSource
Constructors
Step :: Progress -> Steps a -> Steps a
Fail :: [String] -> [[String] -> (Int, Steps a)] -> Steps a
Apply :: (b -> a) -> Steps b -> 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
newtype P_h st a Source
Constructors
P_h (forall r. (a -> st -> Steps r) -> st -> Steps r)
show/hide Instances
Switch P_h
Parse P_h
Applicative (P_h state) => Monad (P_h state)
Functor (P_h state)
Applicative (P_h state)
Alternative (P_h state)
Ambiguous (P_h state)
Greedy (P_h state)
ExtApplicative (P_h st) st
(Eof state, Stores state errors) => AsksFor (P_h state) errors
Provides state symbol token => Symbol (P_h state) symbol token
GenMonad (P_h state) (P_f state)
Monad (P_h state) => GenMonad (P_h state) (P_h state)
data Id a Source
Constructors
Id a
show/hide Instances
Show a => Show (Id a)
newtype P_f st a Source
Constructors
P_f (forall r. (st -> Steps r) -> st -> Steps (a, r))
show/hide Instances
Switch P_f
Parse P_f
Functor (P_f st)
Applicative (P_f st)
Alternative (P_f st)
Ambiguous (P_f state)
Greedy (P_f state)
ExtApplicative (P_f st) st
(Eof state, Stores state errors) => AsksFor (P_f state) errors
Provides state symbol token => Symbol (P_f state) symbol token
GenMonad (P_h state) (P_f state)
class GenMonad m_1 m_2 whereSource
Methods
(>>>=) :: m_1 b -> (b -> m_2 a) -> m_2 aSource
show/hide Instances
GenMonad (P_h state) (P_f state)
GenMonad (P_h state) (P_f state)
Monad (P_h state) => GenMonad (P_h state) (P_h state)
newtype P_m state a Source
Constructors
P_m (P_h state a, P_f state a)
show/hide Instances
Switch P_m
Parse P_m
Applicative (P_m st) => Monad (P_m st)
(Functor (P_h st), Functor (P_f st)) => Functor (P_m st)
(Applicative (P_h st), Applicative (P_f st)) => Applicative (P_m st)
(Alternative (P_h st), Alternative (P_f st)) => Alternative (P_m st)
(Ambiguous (P_h state), Ambiguous (P_f state)) => Ambiguous (P_m state)
Greedy (P_m state)
(ExtApplicative (P_h st) st, ExtApplicative (P_f st) st) => ExtApplicative (P_m st) st
(Stores state errors, Eof state) => AsksFor (P_m state) errors
Provides state symbol token => Symbol (P_m state) symbol token
best_gr :: Steps a -> Steps a -> Steps aSource
class Greedy p whereSource
Methods
(<<|>) :: p a -> p a -> p aSource
show/hide Instances
Greedy (P_m state)
Greedy (P_f state)
Greedy (P_h state)
class Ambiguous p whereSource
Methods
amb :: p a -> p [a]Source
show/hide Instances
(Ambiguous (P_h state), Ambiguous (P_f state)) => Ambiguous (P_m state)
Ambiguous (P_f state)
Ambiguous (P_h state)
removeEnd_h :: Steps (a, r) -> Steps rSource
removeEnd_f :: Steps r -> Steps [r]Source
combinevalues :: Steps [(a, r)] -> Steps ([a], r)Source
getCheapest :: Int -> [(Int, Steps a)] -> Steps aSource
traverse :: Int -> Steps a -> Int -> Int -> IntSource
class Stores 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))
class AsksFor p errors whereSource
Methods
pErrors :: p errorsSource
pEnd :: p errorsSource
show/hide Instances
(Stores state errors, Eof state) => AsksFor (P_m state) errors
(Eof state, Stores state errors) => AsksFor (P_f state) errors
(Eof state, Stores state errors) => AsksFor (P_h state) errors
class Switch p whereSource
Methods
pSwitch :: (st1 -> (st2, st2 -> st1)) -> p st2 a -> p st1 aSource
show/hide Instances
newtype R st a Source
Constructors
R (forall r. (st -> Steps r) -> st -> Steps r)
show/hide Instances
Functor (R st)
Applicative (R st)
Alternative (R st)
Provides state symbol token => Symbol (R state) symbol token
class Applicative p => ExtApplicative p st | p -> st whereSource
Methods
(<*) :: p a -> R st b -> p aSource
(*>) :: R st b -> p a -> p aSource
(<$) :: a -> R st b -> p aSource
show/hide Instances
Produced by Haddock version 2.4.2