uu-tc-2015.1.1: Haskell 98 parser combinators for INFOB3TC at Utrecht University

Safe HaskellSafe
LanguageHaskell98

ParseLib.Parallel.Core

Contents

Synopsis

The type of parsers

data Parser s r Source #

The parser is a CPS version of Parser'

Instances
Monad (Parser s) Source # 
Instance details

Defined in ParseLib.Parallel.Core

Methods

(>>=) :: Parser s a -> (a -> Parser s b) -> Parser s b #

(>>) :: Parser s a -> Parser s b -> Parser s b #

return :: a -> Parser s a #

fail :: String -> Parser s a #

Functor (Parser s) Source # 
Instance details

Defined in ParseLib.Parallel.Core

Methods

fmap :: (a -> b) -> Parser s a -> Parser s b #

(<$) :: a -> Parser s b -> Parser s a #

Applicative (Parser s) Source # 
Instance details

Defined in ParseLib.Parallel.Core

Methods

pure :: a -> Parser s a #

(<*>) :: Parser s (a -> b) -> Parser s a -> Parser s b #

liftA2 :: (a -> b -> c) -> Parser s a -> Parser s b -> Parser s c #

(*>) :: Parser s a -> Parser s b -> Parser s b #

(<*) :: Parser s a -> Parser s b -> Parser s a #

Alternative (Parser s) Source # 
Instance details

Defined in ParseLib.Parallel.Core

Methods

empty :: Parser s a #

(<|>) :: Parser s a -> Parser s a -> Parser s a #

some :: Parser s a -> Parser s [a] #

many :: Parser s a -> Parser s [a] #

MonadPlus (Parser s) Source # 
Instance details

Defined in ParseLib.Parallel.Core

Methods

mzero :: Parser s a #

mplus :: Parser s a -> Parser s a -> Parser s a #

Elementary parsers

anySymbol :: Parser s s Source #

Parses any single symbol.

satisfy :: (s -> Bool) -> Parser s s Source #

Takes a predicate and returns a parser that parses a single symbol satisfying that predicate.

empty :: Alternative f => f a #

The identity of <|>

failp :: Parser s a Source #

Same as empty; provided for compatibility with the lecture notes.

succeed :: a -> Parser s a Source #

Parser that always succeeds, i.e., for epsilon.

pure :: Applicative f => a -> f a #

Lift a value.

Parser combinators

(<|>) :: Alternative f => f a -> f a -> f a infixl 3 #

An associative binary operation

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

Biased choice. Not implemented by the parallel parser combinators. Just maps to parallel choice.

(<*>) :: Applicative f => f (a -> b) -> f a -> f b infixl 4 #

Sequential application.

A few functors support an implementation of <*> that is more efficient than the default one.

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

An infix synonym for fmap.

The name of this operator is an allusion to $. Note the similarities between their types:

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

Whereas $ is function application, <$> is function application lifted over a Functor.

Examples

Expand

Convert from a Maybe Int to a Maybe String using show:

>>> show <$> Nothing
Nothing
>>> show <$> Just 3
Just "3"

Convert from an Either Int Int to an Either Int String using show:

>>> show <$> Left 17
Left 17
>>> show <$> Right 17
Right "17"

Double each element of a list:

>>> (*2) <$> [1,2,3]
[2,4,6]

Apply even to the second element of a pair:

>>> even <$> (2,2)
(2,True)

(>>=) :: Monad m => m a -> (a -> m b) -> m b infixl 1 #

Sequentially compose two actions, passing any value produced by the first as an argument to the second.

Lookahead

look :: Parser s [s] Source #

Returns the rest of the input without consuming anything.

Running parsers

parse :: Parser s a -> [s] -> [(a, [s])] Source #

Runs a parser to a given string.