hpp-0.4.1: A Haskell pre-processor

Safe HaskellNone
LanguageHaskell2010

Hpp.Parser

Description

Parsers over streaming input.

Synopsis

Documentation

type Parser m i = ParserT m (RopeM m [i]) i Source #

type ParserT m src i = StateT (Headspring m src i, src) m Source #

A Parser is a bit of state carrying a source of input.

parse :: Monad m => Parser m i o -> [i] -> m (o, RopeM m [i]) Source #

Run a Parser with a given input stream.

evalParse :: Monad m => Parser m i o -> [i] -> m o Source #

await :: Monad m => ParserT m src i (Maybe i) Source #

awaitJust :: (Monad m, HasError m) => String -> ParserT m src 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.

replace :: Monad m => i -> ParserT m src i () Source #

Push a value back into a parser's source.

droppingWhile :: Monad m => (i -> Bool) -> ParserT m src 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.

precede :: Monad m => [i] -> ParserT m src i () Source #

Push a stream of values back into a parser's source.

takingWhile :: Monad m => (i -> Bool) -> ParserT m src 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.

onChunks :: Monad m => ParserT m (RopeM m [i]) [i] r -> Parser m i r Source #

onElements :: Monad m => ParserT m (RopeM m [[i]]) i r -> Parser m [i] r Source #

onInputSegment :: Monad m => (src -> src) -> ParserT m (RopeM m src) i () Source #

insertInputSegment :: Monad m => src -> m () -> ParserT m (RopeM m src) i () Source #

onIsomorphism :: forall m a b src r. Monad m => (a -> b) -> (b -> Maybe a) -> ParserT m ([b], src) b r -> ParserT m src a r Source #

runParser :: Monad m => Parser m i o -> RopeM m [i] -> m (o, RopeM m [i]) Source #