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

Safe HaskellNone
LanguageHaskell98

Pipes.Transduce.Internal

Synopsis

Documentation

newtype 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.

Constructors

Fold1 

Fields

Instances

Bifunctor (Fold1 b) Source #

first is useful to massage errors.

Methods

bimap :: (a -> b) -> (c -> d) -> Fold1 b a c -> Fold1 b b d #

first :: (a -> b) -> Fold1 b a c -> Fold1 b b c #

second :: (b -> c) -> Fold1 b a b -> Fold1 b a c #

Functor (Fold1 b e) Source # 

Methods

fmap :: (a -> b) -> Fold1 b e a -> Fold1 b e b #

(<$) :: a -> Fold1 b e b -> Fold1 b e a #

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.

Methods

pure :: a -> Fold1 b e a #

(<*>) :: Fold1 b e (a -> b) -> Fold1 b e a -> Fold1 b e b #

liftA2 :: (a -> b -> c) -> Fold1 b e a -> Fold1 b e b -> Fold1 b e c #

(*>) :: Fold1 b e a -> Fold1 b e b -> Fold1 b e b #

(<*) :: Fold1 b e a -> Fold1 b e b -> Fold1 b e a #

Semigroup a => Semigroup (Fold1 b e a) Source # 

Methods

(<>) :: Fold1 b e a -> Fold1 b e a -> Fold1 b e a #

sconcat :: NonEmpty (Fold1 b e a) -> Fold1 b e a #

stimes :: Integral b => b -> Fold1 b e a -> Fold1 b e a #

(Monoid a, Semigroup a) => Monoid (Fold1 b e a) Source # 

Methods

mempty :: Fold1 b e a #

mappend :: Fold1 b e a -> Fold1 b e a -> Fold1 b e a #

mconcat :: [Fold1 b e a] -> Fold1 b e a #

data Fold1_ b e a Source #

Constructors

TrueFold (FoldM (ExceptT e IO) b a) 
ExhaustiveCont (forall r. Producer b IO r -> IO (Either e (a, r))) 
NonexhaustiveCont (Producer b IO () -> IO (Either e a)) 

Instances

Bifunctor (Fold1_ b) Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> Fold1_ b a c -> Fold1_ b b d #

first :: (a -> b) -> Fold1_ b a c -> Fold1_ b b c #

second :: (b -> c) -> Fold1_ b a b -> Fold1_ b a c #

Functor (Fold1_ b e) Source # 

Methods

fmap :: (a -> b) -> Fold1_ b e a -> Fold1_ b e b #

(<$) :: a -> Fold1_ b e b -> Fold1_ b e a #

Applicative (Fold1_ b e) Source # 

Methods

pure :: a -> Fold1_ b e a #

(<*>) :: Fold1_ b e (a -> b) -> Fold1_ b e a -> Fold1_ b e b #

liftA2 :: (a -> b -> c) -> Fold1_ b e a -> Fold1_ b e b -> Fold1_ b e c #

(*>) :: Fold1_ b e a -> Fold1_ b e b -> Fold1_ b e b #

(<*) :: Fold1_ b e a -> Fold1_ b e b -> Fold1_ b e a #

nonexhaustiveCont :: Fold1_ b e a -> Producer b IO () -> IO (Either e a) Source #

exhaustiveCont :: Fold1_ b e a -> Producer b IO r -> IO (Either e (a, r)) Source #

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 

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 

withStreamCont Source #

Arguments

:: (Stream (Of b) IO () -> IO a) 
-> Fold1 b e a 

withStreamCont' Source #

Arguments

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

This function preserves the return type of the Stream and can be more efficient than its counterpart.

withFallibleStreamCont Source #

Arguments

:: (Stream (Of b) IO () -> IO (Either e a)) 
-> Fold1 b e a 

withFallibleStreamCont' Source #

Arguments

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

This function preserves the return type of the Stream and can be more efficient than its counterpart.

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

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

hoistFold :: Monad m => (forall a. m a -> n a) -> FoldM m i r -> FoldM n i r Source #

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 () 

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 

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

Run a Fold1.

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!)

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.

Constructors

M (b -> a) 
F (b -> [a]) 
P (forall r. Producer b IO r -> Producer a IO r) 
PE (forall r. Producer b IO r -> Producer a IO (Either e r)) 
S (forall r. Producer b IO r -> FreeT (Producer a IO) IO r) 
SE (forall r. Producer b IO r -> FreeT (Producer a IO) IO (Either e r)) 

Instances

Bifunctor (Transducer x b) Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> Transducer x b a c -> Transducer x b b d #

first :: (a -> b) -> Transducer x b a c -> Transducer x b b c #

second :: (b -> c) -> Transducer x b a b -> Transducer x b a c #

Functor (Transducer x b e) Source # 

Methods

fmap :: (a -> b) -> Transducer x b e a -> Transducer x b e b #

(<$) :: a -> Transducer x b e b -> Transducer x b e a #

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 

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.

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

Apply a Transducer to a Fold1.

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 

newtype 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.

Constructors

Fold2 (Lift (Fold2_ b1 b2 e) a) 

Instances

Bifunctor (Fold2 b1 b2) Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> Fold2 b1 b2 a c -> Fold2 b1 b2 b d #

first :: (a -> b) -> Fold2 b1 b2 a c -> Fold2 b1 b2 b c #

second :: (b -> c) -> Fold2 b1 b2 a b -> Fold2 b1 b2 a c #

Functor (Fold2 b1 b2 e) Source # 

Methods

fmap :: (a -> b) -> Fold2 b1 b2 e a -> Fold2 b1 b2 e b #

(<$) :: a -> Fold2 b1 b2 e b -> Fold2 b1 b2 e a #

Applicative (Fold2 b1 b2 e) Source # 

Methods

pure :: a -> Fold2 b1 b2 e a #

(<*>) :: Fold2 b1 b2 e (a -> b) -> Fold2 b1 b2 e a -> Fold2 b1 b2 e b #

liftA2 :: (a -> b -> c) -> Fold2 b1 b2 e a -> Fold2 b1 b2 e b -> Fold2 b1 b2 e c #

(*>) :: Fold2 b1 b2 e a -> Fold2 b1 b2 e b -> Fold2 b1 b2 e b #

(<*) :: Fold2 b1 b2 e a -> Fold2 b1 b2 e b -> Fold2 b1 b2 e a #

Semigroup a => Semigroup (Fold2 b1 b2 e a) Source # 

Methods

(<>) :: Fold2 b1 b2 e a -> Fold2 b1 b2 e a -> Fold2 b1 b2 e a #

sconcat :: NonEmpty (Fold2 b1 b2 e a) -> Fold2 b1 b2 e a #

stimes :: Integral b => b -> Fold2 b1 b2 e a -> Fold2 b1 b2 e a #

(Monoid a, Semigroup a) => Monoid (Fold2 b1 b2 e a) Source # 

Methods

mempty :: Fold2 b1 b2 e a #

mappend :: Fold2 b1 b2 e a -> Fold2 b1 b2 e a -> Fold2 b1 b2 e a #

mconcat :: [Fold2 b1 b2 e a] -> Fold2 b1 b2 e a #

data Fold2_ b1 b2 e a Source #

Constructors

First (Fold1_ b1 e a) 
Second (Fold1_ b2 e a) 
Both (forall r1 r2. Producer b1 IO r1 -> Producer b2 IO r2 -> IO (Either e (a, r1, r2))) 

Instances

Bifunctor (Fold2_ b1 b2) Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> Fold2_ b1 b2 a c -> Fold2_ b1 b2 b d #

first :: (a -> b) -> Fold2_ b1 b2 a c -> Fold2_ b1 b2 b c #

second :: (b -> c) -> Fold2_ b1 b2 a b -> Fold2_ b1 b2 a c #

Functor (Fold2_ b1 b2 e) Source # 

Methods

fmap :: (a -> b) -> Fold2_ b1 b2 e a -> Fold2_ b1 b2 e b #

(<$) :: a -> Fold2_ b1 b2 e b -> Fold2_ b1 b2 e a #

Applicative (Fold2_ b1 b2 e) Source # 

Methods

pure :: a -> Fold2_ b1 b2 e a #

(<*>) :: Fold2_ b1 b2 e (a -> b) -> Fold2_ b1 b2 e a -> Fold2_ b1 b2 e b #

liftA2 :: (a -> b -> c) -> Fold2_ b1 b2 e a -> Fold2_ b1 b2 e b -> Fold2_ b1 b2 e c #

(*>) :: Fold2_ b1 b2 e a -> Fold2_ b1 b2 e b -> Fold2_ b1 b2 e b #

(<*) :: Fold2_ b1 b2 e a -> Fold2_ b1 b2 e b -> Fold2_ b1 b2 e a #

fold2Fallibly_ :: Fold2_ b1 b2 e a -> Producer b1 IO r1 -> Producer b2 IO r2 -> IO (Either e (a, r1, r2)) Source #

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

Run a Fold2.

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!)

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 #

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.