simple-parser-0.2.1: Simple parser combinators
Safe HaskellNone
LanguageHaskell2010

SimpleParser.Input

Description

Useful combinators for ParserT and Stream.

Synopsis

Documentation

peekToken :: (Stream s, Monad m) => ParserT e s m (Maybe (Token s)) Source #

Return the next token, if any, but don't consume it.

popToken :: (Stream s, Monad m) => ParserT e s m (Maybe (Token s)) Source #

Return the next token, if any, and consume it.

peekChunk :: (Stream s, Monad m) => Int -> ParserT e s m (Maybe (Chunk s)) Source #

Return the next chunk of the given size, if any, but don't consume it. May return a smaller chunk at end of stream, but never returns an empty chunk.

popChunk :: (Stream s, Monad m) => Int -> ParserT e s m (Maybe (Chunk s)) Source #

Return the next chunk of the given size, if any, and consume it. May return a smaller chunk at end of stream, but never returns an empty chunk.

dropChunk :: (Stream s, Monad m) => Int -> ParserT e s m (Maybe Int) Source #

Drop the next chunk of the given size, if any, and consume it. May return a smaller size at end of stream, but never returns size 0.

isEnd :: (Stream s, Monad m) => ParserT e s m Bool Source #

Is this the end of the stream?

matchEnd :: (Stream s, Monad m) => ParserT e s m () Source #

Match the end of the stream or terminate the parser.

anyToken :: (Stream s, Monad m) => ParserT e s m (Token s) Source #

Return the next token or terminate the parser at end of stream.

anyChunk :: (Stream s, Monad m) => Int -> ParserT e s m (Chunk s) Source #

Return the next chunk of the given size or terminate the parser at end of stream. May return a smaller chunk at end of stream, but never returns an empty chunk.

satisfyToken :: (Stream s, Monad m) => (Token s -> Bool) -> ParserT e s m (Token s) Source #

Match the next token with the given predicate or terminate the parser at predicate false or end of stream.

foldTokensWhile :: (Stream s, Monad m) => (Token s -> x -> (Bool, x)) -> (x -> x) -> x -> ParserT e s m x Source #

Folds over a stream of tokens while the boolean value is true. Always succeeds, even at end of stream.

takeTokensWhile :: (Stream s, Monad m) => (Token s -> Bool) -> ParserT e s m (Chunk s) Source #

Take tokens into a chunk while they satisfy the given predicate. Always succeeds, even at end of stream. May return an empty chunk.

takeTokensWhile1 :: (Stream s, Monad m) => (Token s -> Bool) -> ParserT e s m (Chunk s) Source #

Take tokens into a chunk while they satisfy the given predicate. Only succeeds if 1 or more tokens are taken, so it never returns an empty chunk.

dropTokensWhile :: (Stream s, Monad m) => (Token s -> Bool) -> ParserT e s m Int Source #

Drop tokens and return chunk size while they satisfy the given predicate. Always succeeds, even at end of stream. May return empty chunk size 0.

dropTokensWhile1 :: (Stream s, Monad m) => (Token s -> Bool) -> ParserT e s m Int Source #

Drop tokens and return chunk size while they satisfy the given predicate. Only succeeds if 1 or more tokens are dropped.

matchToken :: (Stream s, Monad m, Eq (Token s)) => Token s -> ParserT e s m (Token s) Source #

Match token with equality or terminate the parser at inequality or end of stream.

matchChunk :: (Stream s, Monad m, Eq (Chunk s)) => Chunk s -> ParserT e s m (Chunk s) Source #

Match chunk with equality or terminate the parser at inequality or end of stream.