gather-0.1.0.0: An applicative for parsing unordered things, heterogenous sorting

Safe HaskellSafe
LanguageHaskell2010

Data.Gather

Synopsis

Documentation

data Gather g f a Source #

Fold over the outcomes of a type that has an Alternative.

Gather embodies two steps.

For example, Gather (Either String) Parser is a type that helps you parse a sequence of mixed production, similar to many (p1 | p2 | p3) but then it also lets you specify what to do with the aggregate result p1 and the aggregate result of p2 and so on.

Example:

data Vehicle = Vehicle { wheels :: [Wheel], seats :: (Seat, [Seat]) }

-- | Parse vehicle parts in any order
parseVehicle = join $ runGather (
  Vehicle <$> zeroOrMore parseWheel
          <*> oneOrMore (fail "A vehicle requires at least one seat.") parseSeat
)

Constructors

Monoid m => Gather 

Fields

Instances
(Functor g, Functor f) => Functor (Gather g f) Source # 
Instance details

Defined in Data.Gather

Methods

fmap :: (a -> b) -> Gather g f a -> Gather g f b #

(<$) :: a -> Gather g f b -> Gather g f a #

(Applicative g, Alternative f) => Applicative (Gather g f) Source # 
Instance details

Defined in Data.Gather

Methods

pure :: a -> Gather g f a #

(<*>) :: Gather g f (a -> b) -> Gather g f a -> Gather g f b #

liftA2 :: (a -> b -> c) -> Gather g f a -> Gather g f b -> Gather g f c #

(*>) :: Gather g f a -> Gather g f b -> Gather g f b #

(<*) :: Gather g f a -> Gather g f b -> Gather g f a #

type Gather' f = Gather f f Source #

Simple type for parsing monads that also take care of error handling or other postProcess concerns.

runGather :: Alternative f => Gather g f a -> f (g a) Source #

gather :: Monoid m => (m -> g a) -> f m -> Gather g f a Source #

zeroOrMore :: (Functor f, Applicative g) => f a -> Gather g f [a] Source #

zeroOrMore_ :: (Functor f, Applicative g) => f a -> Gather g f () Source #

zeroOrOne Source #

Arguments

:: (Functor f, Applicative g) 
=> g (Maybe a)

on many, typically a fail, Left or similar

-> f a 
-> Gather g f (Maybe a) 

oneOrMore Source #

Arguments

:: (Functor f, Applicative g) 
=> g (a, [a])

on zero, typically a fail, Left or similar

-> f a 
-> Gather g f (a, [a]) 

exactlyOne Source #

Arguments

:: (Functor f, Applicative g) 
=> g a

on zero, typically a fail, Left or similar

-> g a

on many, typically a fail, Left or similar

-> f a 
-> Gather g f a 

Naive implementation that does not backtrack after the item has been parsed once. This may change in the future.