parsek-1.0.1.3: Parallel Parsing Processes

Safe HaskellSafe-Inferred
LanguageHaskell2010

Text.ParserCombinators.Class

Synopsis

Documentation

class (Monad p, Alternative p) => IsParser p where Source

Parser class

Associated Types

type SymbolOf p Source

Methods

satisfy Source

Arguments

:: (SymbolOf p -> Bool) 
-> p (SymbolOf p)

accept a symbol satisfying a given predicate

look Source

Arguments

:: p [SymbolOf p]

access the stream of symbols from the current point

label Source

Arguments

:: String 
-> p a 
-> p a

label the parser

(<<|>) infixr 3 Source

Arguments

:: p a 
-> p a 
-> p a

Left-biased choice.

Instances

(<?>) :: IsParser p => p a -> String -> p a infix 2 Source

Label a parser

char :: (IsParser p, Show (SymbolOf p), Eq (SymbolOf p)) => SymbolOf p -> p (SymbolOf p) Source

noneOf :: (IsParser p, (~) * (SymbolOf p) Char) => [Char] -> p Char Source

oneOf :: (IsParser p, (~) * (SymbolOf p) Char) => [Char] -> p Char Source

spaces :: (IsParser p, (~) * (SymbolOf p) Char) => p () Source

space :: (IsParser p, (~) * (SymbolOf p) Char) => p Char Source

newline :: (IsParser p, (~) * (SymbolOf p) Char) => p Char Source

tab :: (IsParser p, (~) * (SymbolOf p) Char) => p Char Source

upper :: (IsParser p, (~) * (SymbolOf p) Char) => p Char Source

lower :: (IsParser p, (~) * (SymbolOf p) Char) => p Char Source

alphaNum :: (IsParser p, (~) * (SymbolOf p) Char) => p Char Source

letter :: (IsParser p, (~) * (SymbolOf p) Char) => p Char Source

digit :: (IsParser p, (~) * (SymbolOf p) Char) => p Char Source

hexDigit :: (IsParser p, (~) * (SymbolOf p) Char) => p Char Source

octDigit :: (IsParser p, (~) * (SymbolOf p) Char) => p Char Source

choice :: Alternative f => [f a] -> f a Source

option :: Alternative f => a -> f a -> f a Source

between :: Applicative m => m x -> m y -> m a -> m a Source

manyGreedy :: IsParser m => m a -> m [a] Source

Greedy repetition: match as many occurences as possible of the argument.

skipMany1 :: Alternative f => f a -> f () Source

skipMany :: Alternative f => f a -> f () Source

sepBy :: Alternative f => f a -> f a1 -> f [a] Source

sepBy1 :: Alternative f => f a -> f a1 -> f [a] Source

count :: Applicative m => Int -> m a -> m [a] Source

chainr :: (Monad f, Alternative f) => f a -> f (a -> a -> a) -> a -> f a Source

chainl :: (Monad f, Alternative f) => f a -> f (a -> a -> a) -> a -> f a Source

chainr1 :: (Monad m, Alternative m) => m t -> m (t -> t -> t) -> m t Source

chainl1 :: (Monad m, Alternative m) => m b -> m (b -> b -> b) -> m b Source

munch :: IsParser m => (SymbolOf m -> Bool) -> m [SymbolOf m] Source

munch1 :: IsParser m => (SymbolOf m -> Bool) -> m [SymbolOf m] Source