Reputation: 30227
The question of how to run a Consumer
inside a Pipe
has already been asked, but the answer that was offered then requires the Consumer'
polymorphic type synonym:
{-# LANGUAGE RankNTypes #-}
import Pipes
toPipe :: Monad m => Consumer' i m o -> Pipe i o m ()
toPipe consumer = consumer >>= yield
Now, the problem I'm having is that in Pipes.Vector
, toVector
uses the monomorphic Consumer
synonym:
toVector :: (PrimMonad m, MVector (Mutable v) e) => Consumer e (ToVector v e m) r
So the toPipe
function from that answer won't work in this case:
{-# LANGUAGE RankNTypes #-}
module VectorPipe where
import Control.Monad.Primitive (PrimMonad)
import qualified Data.Vector.Generic as G
import Pipes
import Pipes.Vector
toPipe :: Monad m => Consumer' i m o -> Pipe i o m ()
toPipe consumer = consumer >>= yield
vectorPipe :: (PrimMonad m, G.Vector v a) => Pipe a (v a) m ()
vectorPipe = toPipe (runToVectorP toVector)
{-
VectorPipe.hs:13:35-42: Could not deduce (y' ~ ()) …
from the context (PrimMonad m, G.Vector v a)
bound by the type signature for
vectorPipe :: (PrimMonad m, G.Vector v a) => Pipe a (v a) m ()
at /Users/casillas/GitHub/tau-sigma/VectorPipe.hs:12:15-62
‘y'’ is a rigid type variable bound by
a type expected by the context: Proxy () a y' y m (v a)
at /Users/casillas/GitHub/tau-sigma/VectorPipe.hs:13:14
Expected type: Proxy () a y' y (ToVector v a m) r0
Actual type: Consumer a (ToVector v a m) r0
In the first argument of ‘runToVectorP’, namely ‘toVector’
In the first argument of ‘toPipe’, namely ‘(runToVectorP toVector)’
VectorPipe.hs:13:35-42: Could not deduce (y ~ X) …
from the context (PrimMonad m, G.Vector v a)
bound by the type signature for
vectorPipe :: (PrimMonad m, G.Vector v a) => Pipe a (v a) m ()
at /Users/casillas/GitHub/tau-sigma/VectorPipe.hs:12:15-62
‘y’ is a rigid type variable bound by
a type expected by the context: Proxy () a y' y m (v a)
at /Users/casillas/GitHub/tau-sigma/VectorPipe.hs:13:14
Expected type: Proxy () a y' y (ToVector v a m) r0
Actual type: Consumer a (ToVector v a m) r0
In the first argument of ‘runToVectorP’, namely ‘toVector’
In the first argument of ‘toPipe’, namely ‘(runToVectorP toVector)’
Compilation failed.
-}
Any suggestions? Is the signature of toVector
unnecessarily narrow, perhaps? (I'm too much of a pipes noob to tell... EDIT: I tried changing the signature in pipes-vector
to Consumer'
; the code compiles, but it looks like vectorPipe
never yields.)
Upvotes: 4
Views: 123
Reputation: 30227
Well, I came up with this after playing around for several days:
import Control.Monad
import Pipes
import Pipes.Core ((//>), (>\\), closed)
-- | Convert a 'Consumer' into a 'Pipe' that 'yield's the consumer's
-- final result.
fromConsumer :: Monad m => Consumer i m r -> Pipe i r m ()
fromConsumer c = c //> closed >>= yield
example1 :: MonadIO m => m ()
example1 = runEffect $ each "abcde" >-> fromConsumer (example' 3) >-> P.print
where
example' :: Monad m => Int -> Consumer a m [a]
example' n = replicateM n await
-- λ> example1
-- "abc"
-- | Convert a 'Producer' into a 'Pipe' that ignores its upstream
-- and sends the producer's contents downstream.
fromProducer :: Monad m => Producer o m r -> Pipe i o m r
fromProducer p = closed >\\ p
example2 :: MonadIO m => m ()
example2 = runEffect $ P.stdinLn >-> fromProducer (each "abcde") >-> P.print
-- Ignores stdin:
--
-- λ> example2
-- 'a'
-- 'b'
-- 'c'
-- 'd'
-- 'e'
Upvotes: 1