Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- class (Monad p, Alternative p) => IsParser p where
- (<?>) :: IsParser p => p a -> String -> p a
- char :: (IsParser p, Eq (SymbolOf p), Show (SymbolOf p)) => SymbolOf p -> p (SymbolOf p)
- noneOf :: (IsParser p, SymbolOf p ~# Char) => [Char] -> p Char
- oneOf :: (IsParser p, SymbolOf p ~# Char) => [Char] -> p Char
- spaces :: (IsParser p, SymbolOf p ~# Char) => p ()
- space :: (IsParser p, SymbolOf p ~# Char) => p Char
- newline :: (IsParser p, Eq (SymbolOf p), Show (SymbolOf p), SymbolOf p ~# Char) => p Char
- tab :: (IsParser p, Eq (SymbolOf p), Show (SymbolOf p), SymbolOf p ~# Char) => p Char
- upper :: (IsParser p, SymbolOf p ~# Char) => p Char
- lower :: (IsParser p, SymbolOf p ~# Char) => p Char
- alphaNum :: (IsParser p, SymbolOf p ~# Char) => p Char
- letter :: (IsParser p, SymbolOf p ~# Char) => p Char
- digit :: (IsParser p, SymbolOf p ~# Char) => p Char
- hexDigit :: (IsParser p, SymbolOf p ~# Char) => p Char
- octDigit :: (IsParser p, SymbolOf p ~# Char) => p Char
- anySymbol :: IsParser p => p (SymbolOf p)
- string :: (IsParser p, SymbolOf p ~ Char) => String -> p String
- choice :: Alternative f => [f a] -> f a
- option :: Alternative f => a -> f a -> f a
- between :: Applicative m => m x -> m y -> m a -> m a
- manyGreedy :: IsParser m => m a -> m [a]
- skipMany1 :: Alternative f => f a -> f ()
- skipMany :: Alternative f => f a -> f ()
- sepBy :: Alternative f => f a1 -> f a2 -> f [a1]
- sepBy1 :: Alternative f => f a1 -> f a2 -> f [a1]
- count :: Applicative m => Int -> m a -> m [a]
- chainr :: (Alternative f, Monad f) => f a -> f (a -> a -> a) -> a -> f a
- chainl :: (Alternative f, Monad f) => f a -> f (a -> a -> a) -> a -> f a
- chainr1 :: (Monad f, Alternative f) => f t -> f (t -> t -> t) -> f t
- chainl1 :: (Alternative m, Monad m) => m b -> m (b -> b -> b) -> m b
- munch :: IsParser m => (SymbolOf m -> Bool) -> m [SymbolOf m]
- munch1 :: IsParser m => (SymbolOf m -> Bool) -> m [SymbolOf m]
- endOfFile :: IsParser p => p ()
Documentation
class (Monad p, Alternative p) => IsParser p where Source #
Parser class
:: p [SymbolOf p] | access the stream of symbols from the current point |
:: String | |
-> p a | |
-> p a | label the parser |
:: p a | |
-> p a | |
-> p a | Left-biased choice. |
Instances
IsParser Parser Source # | |
Defined in Text.ParserCombinators.Parsek.Position | |
IsParser (Parser s) Source # | |
Defined in Text.ParserCombinators.Parsek |
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 a1 -> f a2 -> f [a1] Source #
sepBy1 :: Alternative f => f a1 -> f a2 -> f [a1] Source #
count :: Applicative m => Int -> m a -> m [a] Source #
chainr :: (Alternative f, Monad f) => f a -> f (a -> a -> a) -> a -> f a Source #
chainl :: (Alternative f, Monad f) => f a -> f (a -> a -> a) -> a -> f a Source #
chainr1 :: (Monad f, Alternative f) => f t -> f (t -> t -> t) -> f t Source #
chainl1 :: (Alternative m, Monad m) => m b -> m (b -> b -> b) -> m b Source #