
There's a big difference between getContents and Takusen: getContents has a non-trivial implementation (using unsafeInterleaveIO) that allows it to return data lazily. Takusen has no such implementation. I'm not sure if it would be possible. I don't really understand how getContents works; is there any advice or guidelines as to how to use (or abuse) unsafeInterleaveIO? Some googling has found: http://therning.org/magnus/archives/249 http://www.haskell.org/pipermail/haskell-cafe/2007-January/021373.html http://www.haskell.org/pipermail/haskell-cafe/2007-January/021407.html
http://haskell.org/haskellwiki/IO_inside#unsafePerformIO_and_unsafeInter leaveIO
I contributed to one of those threads, the code in my message http://www.haskell.org/pipermail/haskell-cafe/2007-January/021382.html has a useful example to compile and play with. And if you want generator co-routines that perform IO (such as with a database):
import Control.Monad.Cont import System.IO.Unsafe
yield :: a -> ContT [a] IO () yield x = mapContT (fmap (x:)) (return ())
unsafeYield :: a -> ContT [a] IO () unsafeYield x = mapContT (fmap (x:) . unsafeInterleaveIO) (return ())
execGen :: ContT [a] IO v -> IO [a] execGen m = m `runContT` \_ -> return []
test :: IO [Integer] test = execGen $ mapM_ (\x -> liftIO (putStr $ "<" ++ show x ++ ">") >> if even x then unsafeYield x else yield x) [1..]
main = do z <- test print (take 1 z) print (take 2 z) print (take 3 z) print (take 4 z) print (take 5 z)
When run:
<1><2>[1] [1,2] [1,2<3><4>,3] [1,2,3,4] [1,2,3,4<5><6>,5]
Note that test returns an infinite list of integers, but the even ones are returned lazily with unsafeInterleaveIO. The use of ContT simplifies the control flow, since one can put yield / unsafeYield statements in the middle of other operations. The computation is shown by the <> bracket numbers, and always computes until an even one is reached. In particular, both <5> and <6> are computed when returning 5. So I think this is a reasonable toy model where two numbers are fetched at a time from IO (standing in for a database), but only as the lazy list is demanded. -- Chris module Main where import Data.Char import System.IO import System.IO.Unsafe newtype Stream a = Stream {next:: (IO (Maybe (a,Stream a)))} -- Run this "main" (e.g. in GHCI) and type several lines of text. -- The program ends when a line of text contains 'q' for the second time -- main = do hSetBuffering stdin NoBuffering hSetBuffering stdout NoBuffering print "Test of strict" opWith =<< strict untilQ print "Test of unsafeStrict" opWith $ unsafeStrict untilQ print "Test of lazy" opWith =<< lazy untilQ print "Test of unsafeLazy" opWith $ unsafeLazy untilQ -- Shorthand for test above. Processing the input through toUpper opWith = mapM_ print . lines . map toUpper untilQ :: Stream Char untilQ = Stream $ do c <- getChar if c == 'q' then return Nothing else return (Just (c,untilQ)) strict :: Stream a -> IO [a] strict s = do mc <- next s case mc of Nothing -> return [] Just (c,s') -> do rest <- strict s' return (c:rest) lazy :: Stream a -> IO [a] lazy s = unsafeInterleaveIO $ do mc <- next s case mc of Nothing -> return [] Just (c,s') -> do rest <- lazy s' return (c:rest) unsafeStrict :: Stream a -> [a] unsafeStrict s = unsafePerformIO (strict s) unsafeLazy :: Stream a -> [a] unsafeLazy s = unsafePerformIO (lazy s)