Thanks Dan, some useful pointers there.

Looking at the Pipes level, there's

ConduitM i o m r = forall b. (r -> Pipe i i o () m b) -> Pipe i i o () m b
                 = forall b. ContT b (Pipe i i o () m) r

(not sure if the comparison with ContT is helpful yet...)

I see what you mean about the upstream return type u always being () with ConduitM, although it's the r I want to get my hands on, not the u. I think that means a combinator like awaitE can't work in ConduitM as it can't depend on the return type of the upstream ConduitM.

Looking at how (=$=) is defined, I tried this:

fuseEither :: Monad m => ConduitM a b m u -> ConduitM b c m d -> ConduitM a c m (Either u d)
fuseEither (ConduitM left0) (ConduitM right0) = ConduitM $ \rest ->
    let goRight final left right =
            case right of
                HaveOutput p c o  -> HaveOutput (recurse p) (c >> final) o
                NeedInput rp rc   -> goLeft rp rc final left
                Done r2           -> PipeM (final >> return (rest (Right r2)))
                PipeM mp          -> PipeM (liftM recurse mp)
                Leftover right' i -> goRight final (HaveOutput left final i) right'
          where
            recurse = goRight final left

        goLeft rp rc final left =
            case left of
                HaveOutput left' final' o -> goRight final' left' (rp o)
                NeedInput left' lc        -> NeedInput (recurse . left') (recurse . lc)
                Done r1                   -> PipeM (final >> return (rest (Left r1)))
                PipeM mp                  -> PipeM (liftM recurse mp)
                Leftover left' i          -> Leftover (recurse left') i
          where
            recurse = goLeft rp rc final
     in goRight (return ()) (left0 Done) (right0 Done)


The only difference from (=$=) is the two Done cases: the one in goRight now passes Right r2 back to rest instead of r2 itself, and the one in goLeft passes Left r1 back instead of continuing with another call to goRight. Much to my surprise, this actually compiled! But I've no idea whether there are any bad consequences of this - indeed, I've no real idea what's going on here at all, I just took a punt.

Is this horribly broken or is this exactly what I want?

Cheers,


On 13 February 2016 at 01:33, Dan Burton <danburton.email@gmail.com> wrote:
Source m o = ConduitM () o m (); why is Source m o not ConduitM Void o m ()?

I can't think of a really good answer to this, but here's a mediocre answer: you can always "step" a ConduitM that is blocked on trivial input. So the promise of a Source is not that it never blocks, but rather, that it only blocks in such a way that it is trivial to unblock.

You may like the Producer type synonym better:
type Producer m o = forall i. ConduitM i o m ()
When you have a Producer m o, it can be instantiated to ConduitM Void o m (), because you can select i = Void.

Now for your main question...

So the thing about ConduitM composition is that the "upstream result" must be (). If you peel away the ConduitM layer of abstraction and take a look at Data.Conduit.Internal.Pipe, you'll find the operator you're looking for:

http://hackage.haskell.org/package/conduit-1.2.6.1/docs/src/Data-Conduit-Internal-Pipe.html#awaitE

awaitE :: Pipe l i o u m (Either u i)

I'm not quite sure how to surface this into the ConduitM level of abstraction. 

-- Dan Burton

On Fri, Feb 12, 2016 at 12:40 PM, David Turner <dct25-561bs@mythic-beasts.com> wrote:
Hi,

I've got a conduit thing that yields infinitely many values and never exits, which I've given the type ConduitM () o m Void - a bit like Source m o = ConduitM () o m () except that it can't exit due to the Void.

(One side-question: why is Source m o not ConduitM Void o m ()?)

I would now like to get the first item it yields; I'm currently using Data.Conduit.List.head but of course this returns a Maybe o in case the upstream thing exits. Is there a way to do this without that Maybe? I can't see anything obvious, but nor can I think of a terribly good reason why not.

One thing that I was pondering was a kind of fuse operator with a type like ...

ConduitM a b m r1 -> ConduitM b c m r2 -> ConduitM a c m (Either r1 r2)

... which returns the result of whichever thing exits first. Does such a thing exist? Does it even make sense? If it existed, I think I could use it here as it'd specialise to

ConduitM () o m Void -> ConduitM o Void m o -> ConduitM () Void m (Either Void o)

and of course (Either Void o) is isomorphic to o so I'd be home and dry.

Having written this, I'm now also struggling to work out what the thing of type ConduitM o Void m o would be. Maybe I'm going about this all the wrong way, or maybe I'm just confused?

Any help greatly appreciated!

Cheers,

David



_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe