parsimony-1.0.1: Monadic parser combinators derived from Parsec

Stabilityprovisional
Maintaineriavor.diatchki@gmail.com

Parsimony

Contents

Description

The basics of the Parsimony library.

Synopsis

Basic Types

data Parser t a Source

A parser constructing values of type a, with an input buffer of type t.

Applying Parsers

parseSource

Arguments

:: Parser t a

The parser to apply

-> t

The input

-> Either ParseError a 

Apply a parser to the given input.

parseSourceSource

Arguments

:: Parser t a

The parser to apply

-> SourceName

A name for the input (used in errors)

-> t

The input

-> Either ParseError a 

Apply a parser to the given named input.

runParser :: Parser t a -> PrimParser t aSource

Convert a parser into a PrimParser.

Choices

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

An associative binary operation

try :: Parser t a -> Parser t aSource

Allow a parser to back-track. The resulting parser behaves like the input parser unless it fails. In that case, we backtrack without consuming any input. Because we may have to back-track, we keep a hold of the parser input so over-use of this function may result in memory leaks.

choice :: [Parser t a] -> Parser t aSource

The resulting parser behaves like one of the parsers in the list. The chosen parser is the first one that (i) consumes some input, or (ii) succeeds with a result.

Repetition

many :: Parser t a -> Parser t [a]Source

Apply a parser repeatedly, and collect the results in a list.

many1 :: Parser t a -> Parser t [a]Source

Apply a parser repeatedly, and collect the results in a list. The resulting list is guaranteed to be at leats of length one.

skipMany1 :: Parser t a -> Parser t ()Source

Skip at leats one occurance of input recognized by the parser.

match :: Eq a => (a -> String) -> [a] -> Parser t a -> Parser t ()Source

Produces a parser that succeeds if it can extract the list of values specified by the list. The function argument specifies how to show the expectations in error messages.

sepBy :: Parser t a -> Parser t sep -> Parser t [a]Source

sepBy1 :: Parser t a -> Parser t sep -> Parser t [a]Source

endBy :: Parser t a -> Parser t sep -> Parser t [a]Source

endBy1 :: Parser t a -> Parser t sep -> Parser t [a]Source

sepEndBy :: Parser t a -> Parser t sep -> Parser t [a]Source

sepEndBy1 :: Parser t a -> Parser t sep -> Parser t [a]Source

manyTill :: Parser t a -> Parser t end -> Parser t [a]Source

Parse a list of values recognized by the given parser. The sequence of values should be terminated by a pattern recognized by the terminator patser. The terminator is tried before the value pattern, so if there is overlap between the two, the terminator is recognized.

count :: Int -> Parser t a -> Parser t [a]Source

foldMany :: (b -> a -> b) -> b -> Parser t a -> Parser t bSource

Apply a parser repeatedly, combining the results with the given functions. This function is similar to the strict foldl. We stop when an application of the parser fails without consuming any input. If the parser fails after it has consumed some input, then the repeated parser will also fail.

Optoinal content

option :: a -> Parser t a -> Parser t aSource

Behaves like the parameter parser, unless it fails without consuming any input. In that case we succeed with the given value.

optional :: Alternative f => f a -> f (Maybe a)

One or none.

Delimeters and Combinators

(<*>) :: Applicative f => forall a b. f (a -> b) -> f a -> f b

Sequential application.

(<*) :: Applicative f => forall a b. f a -> f b -> f a

Sequence actions, discarding the value of the second argument.

(*>) :: Applicative f => forall a b. f a -> f b -> f b

Sequence actions, discarding the value of the first argument.

(<$>) :: Functor f => (a -> b) -> f a -> f b

An infix synonym for fmap.

(<$) :: Functor f => forall a b. a -> f b -> f a

Replace all locations in the input with the same value. The default definition is fmap . const, but this may be overridden with a more efficient version.

pure :: Applicative f => forall a. a -> f a

Lift a value.

between :: Parser t open -> Parser t close -> Parser t a -> Parser t aSource

eof :: Stream s t => Parser s ()Source

Matches the end of the input (i.e., when there are no more tokens to extract).

Look Ahead

notFollowedBy :: Show a => Parser t a -> Parser t ()Source

Succeeds if the given parser fails. Uses the Show instance of the result type in error messages.

notFollowedBy' :: (a -> String) -> Parser t a -> Parser t ()Source

Succeeds if the given parser fails. The function is used to display the result in error messages.

lookAhead :: Parser t a -> Parser t aSource

Applies the given parser without consuming any input.

anyToken :: Stream s t => Parser s tSource

Matches any token. Fails if there are no more tokens left.

Errors

(<?>) :: Parser t a -> String -> Parser t aSource

Specify the name to be used if the given parser fails.

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

The identity of <|>

parseError :: (SourcePos -> ParseError) -> Parser t aSource

Fail with the given parser error without consuming any input. The error is applied to the current source position.

labels :: Parser t a -> [String] -> Parser t aSource

The resulting parser behaves like the input parser, except that in case of failure we use the given expectation messages.

Parser State

data State t Source

The parser state.

Constructors

State 

Fields

stateInput :: !t

Token source

statePos :: !SourcePos

Current position

updateState :: (State s -> State s) -> Parser s ()Source

Modify the current parser state. Returns the old state. Does not consume input.

mapState :: (State big -> (State small, extra)) -> (State small -> extra -> State big) -> Parser small a -> Parser big aSource

Change the input stream of a parser. This is useful for extending the input stream with extra information. The first function splits the extended state into a state suitable for use by the given parser and some additional information. The second function combines the extra infomration of the original state with the new partial state, to compute a new extended state.

updateInput :: (t -> t) -> Parser t ()Source

Primitive Parsers

type PrimParser s a = State s -> Reply s aSource

primParser :: PrimParser t a -> Parser t aSource

Define a primitive parser. Consumes input on success.