trifecta-0.45: A modern parser combinator library with convenient diagnostics

Portabilitynon-portable
Stabilityexperimental
Maintainerekmett@gmail.com

Text.Trifecta.Parser.Class

Description

 

Synopsis

Documentation

class (Alternative m, MonadPlus m) => MonadParser m whereSource

Methods

try :: m a -> m aSource

Take a parser that may consume input, and on failure, go back to where we started and fail as if we didn't consume input.

labels :: m a -> [String] -> m aSource

skipMany :: m a -> m ()Source

A version of many that discards its input. Specialized because it can often be implemented more cheaply.

satisfy :: (Char -> Bool) -> m CharSource

Parse a single character of the input, with UTF-8 decoding

satisfy8 :: (Word8 -> Bool) -> m Word8Source

Parse a single byte of the input, without UTF-8 decoding

someSpace :: m ()Source

Usually, someSpace consists of one or more occurrences of a space. Some parsers may choose to recognize line comments or block (multi line) comments as white space as well.

nesting :: m a -> m aSource

Called when we enter a nested pair of symbols. Overloadable to disable layout or highlight nested contexts.

semi :: m CharSource

Lexeme parser |semi| parses the character ';' and skips any trailing white space. Returns the character ';'.

unexpected :: String -> m aSource

Used to emit an error on an unexpected token

line :: m ByteStringSource

Retrieve the contents of the current line (from the beginning of the line)

skipping :: Delta -> m ()Source

highlightInterval :: Highlight -> Delta -> Delta -> m ()Source

highlightInterval is called internally in the token parsers. It delimits ranges of the input recognized by certain parsers that are useful for syntax highlighting. An interested monad could choose to listen to these events and construct an interval tree for later pretty printing purposes.

position :: m DeltaSource

slicedWith :: (a -> ByteString -> r) -> m a -> m rSource

run a parser, grabbing all of the text between its start and end points

lookAhead :: m a -> m aSource

lookAhead p parses p without consuming any input.

restOfLine :: MonadParser m => m ByteStringSource

grab the remainder of the current line

(<?>) :: MonadParser m => m a -> String -> m aSource

label a parser with a name

sliced :: MonadParser m => m a -> m ByteStringSource

run a parser, grabbing all of the text between its start and end points and discarding the original result

whiteSpace :: MonadParser m => m ()Source

Skip zero or more bytes worth of white space. More complex parsers are free to consider comments as white space.

highlight :: MonadParser m => Highlight -> m a -> m aSource

run a parser, highlighting all of the text between its start and end points.