
Hello, there. I'm writing a Source to supply values from TChan. I wrote three implementations for that goal as follows: ~~~~ import Data.Conduit import qualified Data.Conduit.List as LC import Control.Monad.Trans import Control.Concurrent.STM import Control.Monad sourceTChanRaw :: MonadIO m => TChan a -> Source m a sourceTChanRaw ch = pipe where pipe = PipeM next (return ()) next = do o <- liftIO $ atomically $ readTChan ch return $ HaveOutput pipe (return ()) o sourceTChanState :: MonadIO m => TChan a -> Source m a sourceTChanState ch = sourceState ch puller where puller ch = StateOpen ch `liftM` (liftIO . atomically $ readTChan ch) sourceTChanYield :: MonadIO m => TChan a -> Source m a sourceTChanYield ch = forever $ do ans <- liftIO . atomically $ readTChan ch yield ans ~~~~ Namely, one using raw Pipe constructors directly, using `sourceState` and `yield`. I tested these with GHCi. ~~~~ ghci> ch <- newTChanIO :: IO (TChan ()) ghci> atomically $ replicateM_ 1500 $ writeTChan ch () ghci> sourceTChanRaw ch $$ LC.take 10 [(),(),(),(),(),(),(),(),(),()] ghci> sourceTChanState ch $$ LC.take 10 [(),(),(),(),(),(),(),(),(),()] ghci> sourceTChanYield ch $$ LC.take 10 *thread blocks* ~~~~ First two versions' result is what I exactly expected but the last one not: the source written with `yield` never returns value even if there are much enough value. I also realized that following code runs perfectly as I expected: ~~~~ ghci> ch <- newTChanIO :: IO (TChan ()) ghci> atomically $ replicateM_ 1500 $ writeTChan ch () 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 [(),(),(),(),(),(),(),(),(),()] ~~~~ So, here is the question: Why the Source using `yield` doesn't work as expected with LC.take? Or, might be Semantically, what behaviour should be expected for LC.take? Thanks, -- Hiromi ISHII konn.jinro@gmail.com