| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Hpp.Parser
Description
Parsers over streaming input.
- newtype Parser m i o = Parser {
- runParser :: forall r. ParserR m r i o
- parse :: Monad m => Parser m i o -> Source m i r -> m o
- awaitP :: Monad m => Parser m i (Maybe i)
- awaitJust :: (Monad m, HasError m) => String -> Parser m i i
- replace :: Monad m => i -> Parser m i ()
- droppingWhile :: Monad m => (i -> Bool) -> Parser m i ()
- liftP :: Monad m => m o -> Parser m i o
- onParserSource :: Monad m => Streamer m i i () -> Parser m i ()
- precede :: Monad m => Source m i r -> Parser m i ()
- takingWhile :: Monad m => (i -> Bool) -> Parser m i [i]
- zoomParse :: Monad m => (forall r. Source m a r -> Source m b (Source m a r)) -> Parser m b o -> Parser m a o
- zoomParseChunks :: Monad m => Parser m i r -> Parser m [i] r
Documentation
Instances
| Monad m => Monad (Parser m i) Source | |
| Functor m => Functor (Parser m i) Source | |
| Monad m => Applicative (Parser m i) Source | |
| MonadPlus m => Alternative (Parser m i) Source | |
| MonadIO m => MonadIO (Parser m i) Source | |
| (Monad m, HasHppState m) => HasHppState (Parser m i) Source | |
| (Monad m, HasError m) => HasError (Parser m i) Source |
parse :: Monad m => Parser m i o -> Source m i r -> m o Source
Run a Parser with a given input stream.
awaitP :: Monad m => Parser m i (Maybe i) Source
Waits for a value from upstream. Returns Nothing if upstream is
empty.
awaitJust :: (Monad m, HasError m) => String -> Parser m i i Source
awaitP that throws an error with the given message if no more
input is available. This may be used to locate where in a
processing pipeline input was unexpectedly exhausted.
droppingWhile :: Monad m => (i -> Bool) -> Parser m i () Source
Discard all values until one fails to satisfy a predicate. At
that point, the failing value is replaced, and the
droppingWhile stream stops.
onParserSource :: Monad m => Streamer m i i () -> Parser m i () Source
onParserSource proc feeds the Parser source through proc
using processPrefix. This means that when proc finishes, the
remaining source continues unmodified.
precede :: Monad m => Source m i r -> Parser m i () Source
Push a stream of values back into a parser's source.
takingWhile :: Monad m => (i -> Bool) -> Parser m i [i] Source
Echo all values until one fails to satisfy a predicate. At that
point, the failing value is replaced, and the takingWhile
stream stops.
zoomParse :: Monad m => (forall r. Source m a r -> Source m b (Source m a r)) -> Parser m b o -> Parser m a o Source
This is rather like a Lens zoom, but quite fragile. The idea is
that we run a Parser on a transformation of the original
source. The transformation of the source is responsible for
yielding transformed values, and ending on demand with the rest
of the original source. We additionally scoop up any leftover
transformed values and prepend them onto the remaining source after
inverting the original transformation.