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

Safe HaskellNone
LanguageHaskell98

Pipes.Transduce.Internal

Synopsis

Documentation

newtype Fold' 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

Fold' (Lift (Fold'_ b e) a) 

Instances

Bifunctor (Fold' b) Source

first is useful to massage errors.

Functor (Fold' b e) Source 
Applicative (Fold' b e) Source

pure creates a Fold' 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 (Fold' b e a) Source 

data Fold'_ 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)) 

nonexhaustiveCont :: Fold'_ b e a -> Producer b IO () -> IO (Either e a) Source

exhaustiveCont :: Fold'_ b e a -> Producer b IO r -> IO (Either e (a, r)) Source

withFallibleCont Source

Arguments

:: (Producer b IO () -> IO (Either e a)) 
-> Fold' b e a 

withFallibleCont' Source

Arguments

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

withCont Source

Arguments

:: (Producer b IO () -> IO a) 
-> Fold' b e a 

withCont' Source

Arguments

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

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

withFoldIO :: FoldM IO b a -> Fold' b e a Source

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

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

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

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

Builds a Fold' out of a Consumer that never stops by itself.

withConsumerM Source

Arguments

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

withConsumerM' Source

Arguments

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

withSafeConsumer Source

Arguments

:: Consumer b (SafeT IO) Void 
-> Fold' b e () 

withFallibleConsumer Source

Arguments

:: Consumer b (ExceptT e IO) Void 
-> Fold' b e () 

withParser Source

Arguments

:: Parser b IO (Either e a) 
-> Fold' b e a 

withParserM Source

Arguments

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

foldFallibly :: Fold' b e a -> Producer b IO r -> IO (Either e (a, r)) Source

Run a Fold'.

fold :: Fold' b Void a -> Producer b IO r -> IO (a, r) Source

Run a Fold' 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 Fold' 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)) 

mapper Source

Arguments

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

fallibleM Source

Arguments

:: (a -> Either e 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.

transduce :: Transducer' x b e a -> Fold' a e r -> Fold' b e r Source

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

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