[Haskell-cafe] How to write Source for TChan working with LC.take?
Hiromi ISHII
konn.jinro at gmail.com
Thu May 31 07:16:05 CEST 2012
Thanks!
I just read your article. I think your proposal is rational, useful and so brilliant!
The new yield/await style would make writing conduits much easier.
Thank you again for taking so much time for this problem!
On 2012/05/29, at 22:14, Michael Snoyman wrote:
> OK, after thinking on this for the past week, I've come up with a
> proposal to make this kind of code easier to write (and more of an
> explanation on why the behavior was unintuitive in the first place).
>
> http://www.yesodweb.com/blog/2012/05/next-conduit-changes
>
> Do you think the modified yield/await would be a good solution to the problem?
>
> Michael
>
> On Mon, May 21, 2012 at 6:07 AM, Michael Snoyman <michael at snoyman.com> wrote:
>> I agree that this behavior is non-intuitive, but still believe it's
>> the necessary approach. The short answer to why it's happening is that
>> there's no exit path in the yield version of the function. To
>> understand why, let's expand the code a little bit. Realizing that
>>
>> liftIO = lift . liftIO
>>
>> and
>>
>> lift mr = PipeM (Done Nothing `liftM` mr) (Finalize mr)
>>
>> we can expand the yield version into:
>>
>> sourceTChanYield2 ch = forever $ do
>> let action = liftIO . atomically $ readTChan ch
>> ans <- PipeM (Done Nothing `liftM` action) (FinalizeM action)
>> yield ans
>>
>> So the first hint that something is wrong is that the finalize
>> function is calling the action. If you try to change that finalize
>> action into a no-op, e.g.:
>>
>> sourceTChanYield3 :: MonadIO m => TChan a -> Source m a
>> sourceTChanYield3 ch = forever $ do
>> let action = liftIO . atomically $ readTChan ch
>> ans <- PipeM (Done Nothing `liftM` action) (return ())
>> yield ans
>>
>> then you get an error message:
>>
>> test.hs:36:53:
>> Could not deduce (a ~ ())
>>
>> The problem is that, as the monadic binding is set up here, the code
>> says "after running the PipeM, I want you to continue by yielding, and
>> then start over again." If you want to expand it further, you can
>> change `forever` into a recursive call, expand `yield`, and then
>> expand all the monadic binding. Every finalization call is forcing
>> things to keep running.
>>
>> And remember: all of this is the desired behavior of conduit, since we
>> want to guarantee finalizers are always called. Imagine that, instead
>> of reading data from a TChan, you were reading from a Handle. In the
>> code above, there was no way to call out to the finalizers.
>>
>> Not sure if all of that rambling was coherent, but here's my
>> recommended solution. What we need is a helper function that allows
>> you to branch based on whether or not it's time to clean up. `lift`,
>> `liftIO`, and monadic bind all perform the same actions regardless of
>> whether or not finalization is being called. The following code,
>> however, works correctly:
>>
>> liftFinal :: Monad m => m a -> Finalize m () -> (a -> Source m a) -> Source m a
>> liftFinal action final f = PipeM (liftM f action) final
>>
>> sourceTChanYield :: Show a => MonadIO m => TChan a -> Source m a
>> sourceTChanYield ch = liftFinal
>> (liftIO . atomically $ readTChan ch)
>> (return ())
>> $ \ans -> do
>> yield ans
>> sourceTChanYield ch
>>
>> Michael
>>
>> On Sun, May 20, 2012 at 4:22 PM, Hiromi ISHII <konn.jinro at gmail.com> wrote:
>>> Oops, sorry.
>>> The last case's behaviour was not as I expected... A correct log is below:
>>>
>>> ~~~~
>>> ghci> sourceTChanRaw ch $$ LC.isolate 10 =$= LC.mapM_ print
>>> ()
>>> ()
>>> ()
>>> ()
>>> ()
>>> ()
>>> ()
>>> ()
>>> ()
>>> ()
>>> ghci> sourceTChanState ch $$ LC.isolate 10 =$= LC.mapM_ print
>>> ()
>>> ()
>>> ()
>>> ()
>>> ()
>>> ()
>>> ()
>>> ()
>>> ()
>>> ()
>>> ghci> sourceTChanYield ch $$ LC.isolate 10 =$= LC.mapM_ print
>>> ()
>>> ()
>>> ()
>>> ()
>>> ()
>>> ()
>>> ()
>>> ()
>>> ()
>>> ()
>>> *blocks*
>>> ~~~~
>>>
>>> So again, sourceTChanYield blocks here even if it is already supplied with enough values!
>>>
>>> -- Hiromi ISHII
>>> konn.jinro at gmail.com
>>>
>>>
>>>
>>>
>>> _______________________________________________
>>> Haskell-Cafe mailing list
>>> Haskell-Cafe at haskell.org
>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Hiromi ISHII
konn.jinro at gmail.com
More information about the Haskell-Cafe
mailing list