LParse-0.1.1.1: A continuation-based parser library

Copyright(c) Marcus Völker 2017
LicenseMIT
Maintainermarcus.voelker@rwth-aachen.de
Safe HaskellSafe
LanguageHaskell2010

Text.LParse.Parser

Description

This module implements LParse's core: The parser data structure, instances of the important typeclasses and functions to run the parser

Synopsis

Documentation

data Parser r t a Source #

The Parser structure itself wraps a function from a collection of tokens (collectively of type t) to a double continuation giving back a string in case of an error (the error message) and a pair (a,t) in case of a success (the parsing result and rest of the input)

Constructors

Parser 

Fields

Instances

Arrow (Parser r) Source #

Lifting a function to an arrow applies the function to the input. (***) executes two parsers in parallel, giving both results as a pair (but only if both succeed)

Methods

arr :: (b -> c) -> Parser r b c #

first :: Parser r b c -> Parser r (b, d) (c, d) #

second :: Parser r b c -> Parser r (d, b) (d, c) #

(***) :: Parser r b c -> Parser r b' c' -> Parser r (b, b') (c, c') #

(&&&) :: Parser r b c -> Parser r b c' -> Parser r b (c, c') #

Category * (Parser r) Source #

The identity parser returns the input. Concatenating two parsers means using the parsing result of the first as tokens for the second

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

Monad (Parser r t) Source #

returning a value means building a parser that consumes no input and just gives back the value (i.e. always succeeds) the bind operator means using the parser, creating a second parser from the result (with the given function) and then parsing with that. Both parsers successively consume input, i.e. consume "a" >>= (const $ consume "b") will consume the string "ab"

Methods

(>>=) :: Parser r t a -> (a -> Parser r t b) -> Parser r t b #

(>>) :: Parser r t a -> Parser r t b -> Parser r t b #

return :: a -> Parser r t a #

fail :: String -> Parser r t a #

Functor (Parser r t) Source #

via Monad/Functor laws

Methods

fmap :: (a -> b) -> Parser r t a -> Parser r t b #

(<$) :: a -> Parser r t b -> Parser r t a #

Applicative (Parser r t) Source #

via Monad/Applicative laws

Methods

pure :: a -> Parser r t a #

(<*>) :: Parser r t (a -> b) -> Parser r t a -> Parser r t b #

(*>) :: Parser r t a -> Parser r t b -> Parser r t b #

(<*) :: Parser r t a -> Parser r t b -> Parser r t a #

Alternative (Parser r t) Source #

an empty parser in the sense of Alternative always fails and throws nothing. Branching between parsers means trying both in a row and taking the first one that succeeds

Methods

empty :: Parser r t a #

(<|>) :: Parser r t a -> Parser r t a -> Parser r t a #

some :: Parser r t a -> Parser r t [a] #

many :: Parser r t a -> Parser r t [a] #

MonadPlus (Parser r t) Source #

Defined via Alternative

Methods

mzero :: Parser r t a #

mplus :: Parser r t a -> Parser r t a -> Parser r t a #

parse :: Parser r t a -> t -> (a -> r) -> (String -> r) -> r Source #

Runs the parser on the tokens, using two functions to run the contained continuation

doParse :: Parser (Either String a) t a -> t -> Either String a Source #

Same as parse, but giving back the results via Either

debugParse :: Show a => Parser (IO ()) t a -> t -> IO () Source #

Runs the parser and prints the results

debugParse' :: Parser (IO ()) t a -> t -> (a -> IO ()) -> IO () Source #

Runs the parser and prints the results via a custom printing function