[Haskell-cafe] IO in lists
Chris Kuklewicz
haskell at list.mightyreason.com
Tue Jan 16 16:15:08 EST 2007
Try the code below. It is a fairly structured way to get exactly the behavior
you asked for. The lazy and unsafeLazy versions are the ones you are interested in.
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)
More information about the Haskell-Cafe
mailing list