[Haskell-cafe] Simple way to do something like ArrowChoice.right on a Conduit? (version 1.0.0)
Joey Adams
joeyadams3.14159 at gmail.com
Fri Mar 1 03:18:36 CET 2013
Can I transform a conduit so some values are passed through unchanged, but
others go through the conduit? For example:
right :: Conduit i m o -> Conduit (Either x i) m (Either x o)
This is named after the Control.Arrow combinator of the same name:
right :: ArrowChoice a => a b c -> a (Either d b) (Either d c)
Here's my use case (simplified): I want to compress data with zlib-conduit,
which provides:
compress :: Conduit (Flush ByteString) m (Flush ByteString)
The Flush<http://hackage.haskell.org/packages/archive/conduit/latest/doc/html/Data-Conduit.html#t:Flush>wrapper
lets me flush the compressor so it will yield cached data right
away (though hurting compression a little).
But before compressing the data, I want to encode it, using this conduit:
encode :: Conduit Entry m ByteString
I want to combine these, so that if I send a 'Flush', it bypasses 'encode'
and feeds to 'compress':
compressEncode :: Conduit (Flush Entry) m (Flush ByteString)
Thus, I need a variant of 'encode' that passes 'Flush' along:
encode' :: Conduit (Flush Entry) m (Flush ByteString)
In my actual program, I don't use Flush, so providing a Conduit combinator
just for Flush would not help me.
Is something like 'right' possible to implement with Conduit's public API?
Here's an implementation using Data.Conduit.Internal (untested):
import Control.Monad (liftM)
import Data.Conduit.Internal (Pipe(..), ConduitM(..), Conduit)
right :: Monad m => Conduit i m o -> Conduit (Either x i) m (Either x o)
right = ConduitM . rightPipe . unConduitM
rightPipe :: Monad m
=> Pipe i i o () m ()
-> Pipe (Either x i) (Either x i) (Either x o) () m ()
rightPipe p0 = case p0 of
HaveOutput p c o -> HaveOutput (rightPipe p) c (Right o)
NeedInput p c -> NeedInput p' (rightPipe . c)
where p' (Left x) = HaveOutput (rightPipe p0) (return ()) (Left
x)
p' (Right i) = rightPipe $ p i
Done r -> Done r
PipeM mp -> PipeM $ liftM rightPipe mp
Leftover p i -> Leftover (rightPipe p) (Right i)
I'm wondering if we could have a Data.Conduit.Arrow module, which provides
a newtype variant of Conduit that implements Arrow, ArrowChoice, etc.:
import qualified Data.Conduit as C
newtype Conduit m i o = Conduit (C.Conduit i m o)
-- May need Monad constraints for these
instance Category (Conduit m)
instance Arrow (Conduit m)
instance ArrowChoice (Conduit m)
Does 'Conduit' follow Category, Monad, MonadTrans laws* these days? I'm
not talking about Pipe in general, just the special case of it represented
by the 'Conduit' type alias:
Conduit i m o = ConduitM i o m () = Pipe i i o () m ()
Or are there some thorny issues (e.g. leftovers) that make following these
laws impossible in some cases?
Thanks for the input,
-Joey
* Assume functions that use Data.Conduit.Internal do so correctly.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130228/2f2e0e17/attachment.htm>
More information about the Haskell-Cafe
mailing list