sparser-0.6.1: Lightweight parsing library based on partial functions.

Portabilitynon-portable (GNTD, DeriveFunctor, OverloadedStrings)
Stabilityexperimental
Maintainerhans@hanshoglund.se
Safe HaskellNone

Data.Sparser

Contents

Description

Lightweight parsing library based on partial functions.

Synopsis

Sparser

Running

runSparser :: Sparser a -> String -> Maybe aSource

  Run a parser, returning the result.

runSparserT :: SparserT s a b -> s -> [a] -> Maybe bSource

  Run a parser with a custom state, returning the result.

runSparserT' :: SparserT s a b -> s -> [a] -> Maybe (s, [a], b)Source

  Run a parser with a custom state.

This is the most general way to run a parser. It returns the final state, remaining input and the result.

withState :: (s -> t) -> (t -> s) -> SparserT t a b -> SparserT s a bSource

Primitives

stateP :: SparserT s a sSource

 Return the state as result.

headP :: (s -> a -> Bool) -> SparserT s a aSource

Consumes one input element.

Fails if the predicate fails, or if there is no more input.

splitP :: (s -> [a] -> Int) -> SparserT s a [a]Source

Consume one or more input elements.

The given function receives the entire remaining input, and must return the number of consumed elements.

Fails if the predicate return 0 or less, or if there is no more input.

gateP :: (s -> [a] -> Bool) -> SparserT s a ()Source

Succeed based on predicate, but do not consume input.

The given function receives the entire remaining input.

Basic parsers

char :: Eq a => a -> SparserT s a aSource

notChar :: Eq a => a -> SparserT s a aSource

charIf :: (a -> Bool) -> SparserT s a aSource

string :: Eq a => [a] -> SparserT s a [a]Source

stringIf :: Int -> ([a] -> Bool) -> SparserT s a [a]Source

complete :: SparserT s a b -> SparserT s a bSource

ifState :: (s -> Bool) -> SparserT s a b -> SparserT s a bSource

Combinators

between :: Monad m => m a -> m a1 -> m b -> m bSource

skipMany1 :: (Monad m, Alternative m) => m a -> m ()Source

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

many1 :: (Monad m, Alternative m) => m a -> m [a]Source

sepBy :: (Monad f, Alternative f) => f a1 -> f a -> f [a1]Source

sepBy1 :: (Monad m, Alternative m) => m a1 -> m a -> m [a1]Source

sepEndBy1 :: (Monad m, Alternative m) => m a1 -> m a -> m [a1]Source

sepEndBy :: (Monad m, Alternative m) => m a1 -> m a -> m [a1]Source

endBy1 :: (Monad m, Alternative m) => m a -> m a1 -> m [a]Source

endBy :: (Monad f, Alternative f) => f a -> f a1 -> f [a]Source

count :: Monad m => Int -> m a -> m [a]Source