[Haskell-cafe] Lazy IO

Ronald Guida oddron at gmail.com
Wed Jul 9 23:05:47 EDT 2008


Suppose I have a lazy function f :: [Int] -> [Int], and I happen to
know that for all n, the n-th element of the output may only depend on
the first (n-1) elements of the input.

I want to print a number from f's output list, and then ask the user
for the next number in f's input list, and then loop until the user
stops providing valid numbers.  I also need to be able to do IO after
my loop exits.

Consider the following code:
----------------------------------------------
module Main
    where

import Control.Monad.Fix
import System.IO.Unsafe

promptInt :: String -> IO (Maybe Int)
promptInt p = do
  putStr p
  s <- getLine
  let rs =  reads s
  if not $ null rs
    then return $ Just $ fst $ head rs
    else return $ Nothing

promptInts :: [String] -> IO [Int]
promptInts [] = return []
promptInts (p:ps) = do
  m <- promptInt p
  case m of
    Just n -> do
           ns <- unsafeInterleaveIO $ promptInts ps
           return $ n:ns
    Nothing -> return []

-- assume accumulator is an opaque function
accumulator :: [Int] -> [Int]
accumulator = scanl (+) 0

makeAccPrompt :: Int -> String
makeAccPrompt n = "[Acc = " ++ show n ++ "] ? "

main :: IO ()
main = do
  xs <- mfix $ promptInts . map makeAccPrompt . accumulator
  seq (length xs) $ print xs
----------------------------------------------

Question: If I can't change my function f (in this case, accumulator),
then is it possible to get the effect I want without having to resort
to "unsafeInterleaveIO"?


More information about the Haskell-Cafe mailing list