comparse-0.2.0.0: A highly generic parser combinators library.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Monad.Parser.Class

Synopsis

Documentation

class (Monad m, Stream (Input m)) => MonadParser m where Source #

A monad with parsing capabilities.

Associated Types

type Input m :: Type Source #

Methods

parseStream :: m (Input m) Source #

The current input stream.

setParseStream :: Input m -> m () Source #

Replace the input stream.

noParse :: m a Source #

A parser that always fails.

item :: m (Item (Input m)) Source #

A parser that returns the next item.

followedBy :: m a -> m () Source #

followedBy p is a parser that succeeds if p succeeds, but it does not consume any input.

notFollowedBy :: m a -> m () Source #

notFollowedBy p is a parser that only succeeds if p fails. This parser will not consume any input.

try :: m a -> m a Source #

try p is a parser that does everything like p, except it forcefully resets the position of any error reported by p to the current position.

(<|>) :: m a -> m a -> m a infixl 3 Source #

p | q is a parser that is equivalent to p when p succeeds and q when p fails to parse anything.

(<?>) :: m a -> String -> m a infixl 1 Source #

p ? msg is a parser that behaves like p, but when p fails, it reports an error indicating that msg was the expected input.

Instances

Instances details
(Monad m, Stream s) => MonadParser (ParserT s m) Source # 
Instance details

Defined in Control.Monad.Trans.Parser

Associated Types

type Input (ParserT s m) Source #

Methods

parseStream :: ParserT s m (Input (ParserT s m)) Source #

setParseStream :: Input (ParserT s m) -> ParserT s m () Source #

noParse :: ParserT s m a Source #

item :: ParserT s m (Item (Input (ParserT s m))) Source #

followedBy :: ParserT s m a -> ParserT s m () Source #

notFollowedBy :: ParserT s m a -> ParserT s m () Source #

try :: ParserT s m a -> ParserT s m a Source #

(<|>) :: ParserT s m a -> ParserT s m a -> ParserT s m a Source #

(<?>) :: ParserT s m a -> String -> ParserT s m a Source #

eof :: MonadParser m => m () Source #

Parser that succeeds if the stream is empty. Does not consume any items.

expected :: MonadParser m => String -> m a Source #

Fail with an "expected" message.

satisfy :: MonadParser m => m a -> (a -> Bool) -> m a Source #

Succeeds only if the value parsed by the parser satisfies the predicate.

match :: MonadParser m => (Item (Input m) -> Bool) -> m (Item (Input m)) Source #

Parse a single item satisfying the given predicate.

optional :: MonadParser m => m a -> m (Maybe a) Source #

Make a parser optional.

choice :: MonadParser m => [m a] -> m a Source #

Try a series of parsers in order, returning the first one that succeeds.

many :: MonadParser m => m a -> m [a] Source #

Try to run the given parser as many times as possible.

many1 :: MonadParser m => m a -> m [a] Source #

Try to run the given parser as many times as possible, but at least once. The result is returned as a regular list, but is guaranteed to be non-empty.

some :: MonadParser m => m a -> m (NonEmpty a) Source #

Try to run the given parser as many times as possible, but at least once.

sepBy1 :: MonadParser m => m a -> m b -> m (NonEmpty a) Source #

Parse a non-empty series of a separated by bs (without a trailing b).

sepBy :: MonadParser m => m a -> m b -> m [a] Source #

Parse a potentially empty series of a separated by bs (without a trailing b).

like :: (MonadParser m, Eq (Item (Input m)), Show (Item (Input m))) => Item (Input m) -> m (Item (Input m)) Source #

Parse any value equal to a.

unlike :: (MonadParser m, Eq (Item (Input m)), Show (Item (Input m))) => Item (Input m) -> m (Item (Input m)) Source #

Parse any value not equal to a.

string :: (MonadParser m, Eq (Item (Input m)), Show (Item (Input m))) => [Item (Input m)] -> m [Item (Input m)] Source #

Parse a continuous sequence of items equal to the given one.

oneOf :: (MonadParser m, Eq (Item (Input m)), Show (Item (Input m))) => [Item (Input m)] -> m (Item (Input m)) Source #

Parse any value equal to at least one element of the given list.

noneOf :: (MonadParser m, Eq (Item (Input m)), Show (Item (Input m))) => [Item (Input m)] -> m (Item (Input m)) Source #

Parse any value not equivalent to any element of the given list. For a version that accepts non-Show items, see noneOf'.

chainl1 :: MonadParser m => m a -> m (a -> a -> a) -> m a Source #

chainl1 p op Parse a chain of *one* or more occurrences of p, separated by op. Return a value obtained by a left associative application of all functions returned by op to the values returned by p.

This is particularly useful for parsing left associative infix operators.

chainr1 :: MonadParser m => m a -> m (a -> a -> a) -> m a Source #

chainr1 p op Parse a chain of *one* or more occurrences of p, separated by op. Return a value obtained by a right associative application of all functions returned by op to the values returned by p.

This is particularly useful for parsing right associative infix operators.

withInput :: MonadParser m => Input m -> m a -> m (a, Input m) Source #

Run a parser on a different stream of items.