parcom-lib-0.8.0.3: A simple parser-combinator library, a bit like Parsec but without the frills

Safe HaskellSafe-Inferred
LanguageHaskell98

Text.Parcom.Core

Description

The core functionality of a Parcom parser: defining and running parsers, lifting, getting tokens and characters from a stream, and the most basic primitive parsers and combinators that cannot easily be expressed in terms of other parsers and combinators.

Synopsis

Documentation

data ParcomError Source

A parser error.

Constructors

ParcomError 

Fields

peErrorDescription :: String

Human-readable description of the error

peSourcePosition :: SourcePosition

Position in the source where the error was found.

Instances

data SourcePosition Source

Represents a position in a source file. Both lines and columns are 1-based.

Constructors

SourcePosition 

Instances

data ParcomT s t m a Source

Parcom as a monad transformer. You can access the underlying monad stack using the usual lifting techniques.

Instances

MonadTrans (ParcomT s t)

ParcomT enables lifting by implementing MonadTrans

Monad m => Alternative (ParcomT s t m) 
Monad m => Monad (ParcomT s t m)

Parcom is a monad. Obviously. Since the Parcom monad handles both failure through Either as well as carrying along its internal state, *and* supporting the transformed parent monad, the implementation is a tiny bit hairy.

Monad m => Functor (ParcomT s t m) 
Monad m => Applicative (ParcomT s t m) 

parseT :: (Stream s t, Token t, Monad m) => ParcomT s t m a -> String -> s -> m (Either ParcomError a) Source

Run a parcom transformer and return the result

type Parcom s t a = ParcomT s t Identity a Source

Parcom as a pure parser

parse :: (Stream s t, Token t) => Parcom s t a -> String -> s -> Either ParcomError a Source

Run a pure parcom parser and return the result

peek :: (Monad m, Stream s t) => ParcomT s t m t Source

Gets the next token from the stream without consuming it. Fails at end-of-input.

next :: (Monad m, Stream s t, Token t) => ParcomT s t m t Source

Gets the next token from the stream and consumes it. Fails at end-of-input.

atEnd :: (Monad m, Stream s t) => ParcomT s t m Bool Source

Checks whether end-of-input has been reached.

try :: Monad m => ParcomT s t m a -> ParcomT s t m a Source

Backtracking modifier; restores the parser state to the previous situation if the wrapped parser fails.

handle :: Monad m => ParcomT s t m a -> (ParcomError -> ParcomT s t m b) -> (a -> ParcomT s t m b) -> ParcomT s t m b Source

Wrap a raw parser to allow handling success and failure. The error and success handlers take the error or parsed value, respectively, and return a parser that should be applied in the error or success case, respectively. No backtracking is performed.

handleB :: Monad m => ParcomT s t m a -> (ParcomError -> ParcomT s t m b) -> (a -> ParcomT s t m b) -> ParcomT s t m b Source

Same as handle, but backtrack on error (that is, if the raw parser fails, any input it has consumed is restored.

notFollowedBy :: (Monad m, Stream s t) => ParcomT s t m a -> ParcomT s t m () Source

Succeeds iff the given parser fails

(<?>) :: (Monad m, Stream s t) => ParcomT s t m a -> String -> ParcomT s t m a infixl 3 Source

Tags a parser with a human-readable description of the expected entity, generating an "Expected {entity}" type error message on failure.

(<|>) :: Alternative f => forall a. f a -> f a -> f a

An associative binary operation

empty :: Alternative f => forall a. f a

The identity of <|>

class Stream s t | s -> t Source

Typeclass for types that are suitable as source streams. Note that implementing just Stream gives you only a small subset of Parcom's features; if you want to implement your own Stream instances, you will most likely also want to implement Token for the corresponding token type, Listish to enable parsers that need to convert to or from lists of tokens, and Textish to enable parsers that work on Unicode text.

Minimal complete definition

peek, atEnd

Instances

Stream ByteString Word8 
Stream ByteString Word8 
Stream Text Char 
Stream Text Char 
Stream [a] a

All lists are instances of Stream, and the corresponding token type is the list element type. Obviously, this also includes String ('[Char]') and '[Word8]'

class Token t Source

This typeclass is pretty much required to do anything useful with Parcom; it is needed for Parcom to detect line endings so that parser errors will report the correct source positions. If you need to parse streams that do not support any meaningful concept of lines, consider implementing a dummy instance, like so: instance Token Foobar where isLineDelimiter _ = False This will treat the entire input as a single line.

Minimal complete definition

isLineDelimiter

Instances

Token Char

Unicode characters are valid tokens.

Token Word8 

class Listish s t | s -> t Source

List-like types.

Minimal complete definition

toList, fromList

Instances

class Textish s Source

Enables parsing on a per-character basis rather than per-token. For stream types where the token type is Char already, this is trivial, but for other streams (e.g., bytestrings), some extra processing is required to perform a conversion to Unicode.

Minimal complete definition

peekChar

peekChar :: (Monad m, Stream s t, Token t, Textish s) => ParcomT s t m Char Source

Get one character from the stream, but do not consume it. Fails when the input stream contains a sequence that does not represent a valid character, or when the end of the input stream has been reached.

nextChar :: (Monad m, Stream s t, Token t, Textish s) => ParcomT s t m Char Source

Get one character from the stream, and consume it. Fails when the input stream contains a sequence that does not represent a valid character, or when the end of the input stream has been reached.