pipes-transduce-0.3.2.0: Interfacing pipes with foldl folds.

Safe HaskellNone
LanguageHaskell98

Pipes.Transduce

Contents

Synopsis

Producer folds

data Fold1 b e a Source

A computation in IO that completely drains a Producer of b values, returning a value of type a, except when it fails early with an error of type e.

Instances

Bifunctor (Fold1 b) Source

first is useful to massage errors.

Functor (Fold1 b e) Source 
Applicative (Fold1 b e) Source

pure creates a Fold1 that does nothing besides draining the Producer.

<*> feeds both folds with the data of the same Producer. If any of them fails the combination fails.

Monoid a => Monoid (Fold1 b e a) Source 

fold1 :: Fold1 b Void a -> Producer b IO r -> IO (a, r) Source

Run a Fold1 that never returns an error value (but which may still throw exceptions!)

fold1Fallibly :: Fold1 b e a -> Producer b IO r -> IO (Either e (a, r)) Source

Run a Fold1.

Building producer folds

From foldl folds

Fold1 values can be created out of the more general folds of the foldl library, which are producer-agnostic.

withFold :: Fold b a -> Fold1 b e a Source

withFoldIO :: FoldM IO b a -> Fold1 b e a Source

withFallibleFold :: FoldM (ExceptT e IO) b a -> Fold1 b e a Source

From consumers

Fold1 values can be created out of Consumers from the pipes library.

withConsumer :: Consumer b IO () -> Fold1 b e () Source

withConsumer' :: Consumer b IO Void -> Fold1 b e () Source

Builds a Fold1 out of a Consumer that never stops by itself.

withConsumerM Source

Arguments

:: MonadIO m 
=> (m () -> IO (Either e a)) 
-> Consumer b m () 
-> Fold1 b e a 

withConsumerM' Source

Arguments

:: MonadIO m 
=> (forall r. m r -> IO (Either e (a, r))) 
-> Consumer b m Void 
-> Fold1 b e a 

withSafeConsumer Source

Arguments

:: Consumer b (SafeT IO) Void 
-> Fold1 b e () 

withFallibleConsumer Source

Arguments

:: Consumer b (ExceptT e IO) Void 
-> Fold1 b e () 

From parsers

Fold1 values can be created out of Parsers from the pipes-parse library.

withParser Source

Arguments

:: Parser b IO (Either e a) 
-> Fold1 b e a 

withParserM Source

Arguments

:: MonadIO m 
=> (forall r. m (a, r) -> IO (Either e (c, r))) 
-> Parser b m a 
-> Fold1 b e c 

From continuations

The most general way of constructing Fold1 values is from an arbitrary function that consumes a Producer.

withCont Source

Arguments

:: (Producer b IO () -> IO a) 
-> Fold1 b e a 

withCont' Source

Arguments

:: (forall r. Producer b IO r -> IO (a, r)) 
-> Fold1 b e a 

withFallibleCont Source

Arguments

:: (Producer b IO () -> IO (Either e a)) 
-> Fold1 b e a 

withFallibleCont' Source

Arguments

:: (forall r. Producer b IO r -> IO (Either e (a, r))) 
-> Fold1 b e a 

Fold transducers

data Transducer x b e a Source

A transformation that takes the inputs of a Fold1 from type a to type b.

Optionally, the transformation may delimit groups of elements in the stream. In that case the phantom type x will be Delimited. Otherwise, it will be Continuous.

transduce1 :: Transducer Continuous b e a -> Fold1 a e r -> Fold1 b e r Source

Apply a Transducer to a Fold1.

Building fold transducers

mapper Source

Arguments

:: (a -> b) 
-> Transducer Continuous a e b 

fallibleMapper Source

Arguments

:: (a -> Either e b) 
-> Transducer Continuous a e b 

mapperFoldable Source

Arguments

:: Foldable f 
=> (a -> f b) 
-> Transducer Continuous a e b 

mapperEnumerable Source

Arguments

:: Enumerable f 
=> (a -> f IO b) 
-> Transducer Continuous a e b 

transducer Source

Arguments

:: (forall r. Producer b IO r -> Producer a IO r) 
-> Transducer Continuous b e a 

fallibleTransducer Source

Arguments

:: (forall r. Producer b IO r -> Producer a IO (Either e r)) 
-> Transducer Continuous b e a 

Transducer group operations

delimit Source

Arguments

:: (forall r. Producer a IO r -> FreeT (Producer a' IO) IO r) 
-> Transducer Continuous b e a 
-> Transducer Delimited b e a' 

Plug splitting functions from pipes-group here.

groups Source

Arguments

:: (forall r. Producer b IO r -> Producer b' IO r) 
-> Transducer Delimited a e b 
-> Transducer Delimited a e b' 

Tweak each of the groups delimited by a Transducer.

folds Source

Arguments

:: Fold1 b Void b' 
-> Transducer Delimited a e b 
-> Transducer Continuous a e b' 

intercalates Source

Arguments

:: Producer b IO () 
-> Transducer Delimited a e b 
-> Transducer Continuous a e b 

Multiple producer folds

data Fold2 b1 b2 e a Source

A computation in IO that completely drains two Producers of b values in a concurrent way, returning a value of type a, except when it fails early with an error of type e.

Instances

Bifunctor (Fold2 b1 b2) Source 
Functor (Fold2 b1 b2 e) Source 
Applicative (Fold2 b1 b2 e) Source 
Monoid a => Monoid (Fold2 b1 b2 e a) Source 

fold2 :: Fold2 b1 b2 Void a -> Producer b1 IO r1 -> Producer b2 IO r2 -> IO (a, r1, r2) Source

Run a Fold2 that never returns an error value (but which may still throw exceptions!)

fold2Fallibly :: Fold2 b1 b2 e a -> Producer b1 IO r1 -> Producer b2 IO r2 -> IO (Either e (a, r1, r2)) Source

Run a Fold2.

Building multiple producer folds

liftFirst :: Fold1 b1 e r1 -> Fold2 b1 b2 e r1 Source

liftSecond :: Fold1 b2 e r1 -> Fold2 b1 b2 e r1 Source

separated :: Fold1 b1 e r1 -> Fold1 b2 e r2 -> Fold2 b1 b2 e (r1, r2) Source

Consume the producers concurrently, each one independently of the other.

combined :: Transducer Delimited b1 e x -> Transducer Delimited b2 e x -> Fold1 x e a -> Fold2 b1 b2 e a Source

Consume the producers concurrently, delimiting groups in each producer, and writing the groups into a common Fold1.

Possible use: find lines in two text producers and combine the lines in a single stream, preserving the integrity of each individual line.

Utilities

trip :: Fold1 b b () Source

Fail if the Producer produces anything at all. The error value is what came out of the Producer.

>>> fold1Fallibly trip (mapM_ yield ['z'])
Left 'z'
>>> fold1Fallibly trip (mapM_ yield [])
Right ((),())

tripx :: Fold1 b e () Source

Throw an exception if the Producer produces anything at all

BEWARE! This 'Transducer may throw AssertionFailed. BEWARE!

>>> fold1Fallibly tripx (mapM_ yield ['z'])
*** Exception: tripx