wumpus-basic-0.20.0: Basic objects and system code built on Wumpus-Core.

PortabilityGHC
Stabilityhighly unstable
MaintainerStephen Tetley <stephen.tetley@gmail.com>

Wumpus.Basic.Utils.ParserCombinators

Contents

Description

Two continuation parser combinators.

Synopsis

Documentation

data Result s ans Source

Constructors

Fail String [s] 
Okay ans [s] 

Instances

(Eq s, Eq ans) => Eq (Result s ans) 
(Ord s, Ord ans) => Ord (Result s ans) 
(Show s, Show ans) => Show (Result s ans) 

runParser :: Parser s a -> [s] -> Result s aSource

apply :: Functor f => f a -> (a -> b) -> f bSource

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

lookahead :: Parser s a -> (a -> Parser s b) -> Parser s bSource

This one is from Chris Okasaki's "Even Higher-Order Functions for Parsing".

peek :: Parser s a -> Parser s aSource

Peek tries the supplied parse, but does not consume input ** even when the parse succeeds **.

equals :: Eq s => s -> Parser s sSource

satisfy :: (s -> Bool) -> Parser s sSource

oneOf :: Eq s => [s] -> Parser s sSource

noneOf :: Eq s => [s] -> Parser s sSource

chainl1 :: MonadPlus m => m a -> m (a -> a -> a) -> m aSource

chainr1 :: MonadPlus m => m a -> m (a -> a -> a) -> m aSource

chainl :: MonadPlus m => m a -> m (a -> a -> a) -> a -> m aSource

chainr :: MonadPlus m => m a -> m (a -> a -> a) -> a -> m aSource

choice :: Alternative f => [f a] -> f aSource

count :: Applicative f => Int -> f a -> f [a]Source

between :: Applicative f => f open -> f close -> f a -> f aSource

option :: Alternative f => a -> f a -> f aSource

optionMaybe :: Alternative f => f a -> f (Maybe a)Source

skipOne :: Applicative f => f a -> f ()Source

skipMany :: Alternative f => f a -> f ()Source

skipMany1 :: Alternative f => f a -> f ()Source

many1 :: Alternative f => f a -> f [a]Source

many1 an alias for Control.Applicative some.

sepBy :: Alternative f => f a -> f b -> f [a]Source

sepBy1 :: Alternative f => f a -> f b -> f [a]Source

sepEndBy :: Alternative f => f a -> f b -> f [a]Source

sepEndBy1 :: Alternative f => f a -> f b -> f [a]Source

manyTill :: Alternative f => f a -> f b -> f [a]Source

manyTill1 :: Alternative f => f a -> f b -> f [a]Source

Char parsers