| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Data.Gather
Synopsis
- data Gather g f a = Monoid m => Gather {
- items :: f m
- postProcess :: m -> g a
- type Gather' f = Gather f f
- runGather :: Alternative f => Gather g f a -> f (g a)
- runGather' :: (Alternative f, Monad f) => Gather' f a -> f a
- gather :: Monoid m => (m -> g a) -> f m -> Gather g f a
- zeroOrMore :: (Functor f, Applicative g) => f a -> Gather g f [a]
- zeroOrMore_ :: (Functor f, Applicative g) => f a -> Gather g f ()
- zeroOrOne :: (Functor f, Applicative g) => g (Maybe a) -> f a -> Gather g f (Maybe a)
- oneOrMore :: (Functor f, Applicative g) => g (a, [a]) -> f a -> Gather g f (a, [a])
- exactlyOne :: (Functor f, Applicative g) => g a -> g a -> f a -> Gather g f a
Documentation
Fold over the outcomes of a type that has an Alternative.
Gather embodies two steps.
- Getting data using
manyand<|>fromAlternative - Postprocessing the data in some way.
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 # | |
| (Applicative g, Alternative f) => Applicative (Gather g f) Source # | |
Defined in Data.Gather | |
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 #
runGather' :: (Alternative f, Monad f) => Gather' f a -> 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 #
Arguments
| :: (Functor f, Applicative g) | |
| => g (a, [a]) | |
| -> f a | |
| -> Gather g f (a, [a]) |
Arguments
| :: (Functor f, Applicative g) | |
| => g a | |
| -> g a | |
| -> 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.