
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"?

On 7/9/08, Ronald Guida
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"?
Yes, but you won't like it. Since you know that (f xs !! n) only depends on the first (n-1) elements of xs, you have this identity: f xs !! n == f (take (n-1) xs) !! n You can then call f with a new list each time, extracting the desired elements as you build up the source list. This is, of course, terribly inefficient. In order to see why you need an unsafe primitive to solve this function, you may find it enlightening to try to write this function:
data Stream a b = NilStream | Stream b (a -> Stream a b) liftStream :: ([a] -> [b]) -> Stream a b liftStream = ?
(the inverse of this function is trivial to write) The problem is that there is no way to extract the continuation from f (x:??); if you had some way, you'd be able to call the same continuation multiple times with different arguments, effectively "pausing" f partway through and giving it new input. By using unsafeInterleaveIO, you are adding a side-effect to the "pure" argument to f, which allows it to interact with the user. Once that side-effect executes, the value is 'fixed' into place and can't be modified. Another way to look at it is to suppose that f didn't meet your invariant, and tried to access an element out of order. How is the thunk to be evaluated for that element built? If it can't do IO, it must be a pure computation. But it needs to do IO because the element hasn't been determined yet. -- ryan

On Wed, Jul 09, 2008 at 11:05:47PM -0400, Ronald Guida wrote:
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"?
Here's a possibility; you may or may not like it. module Main where import Control.Concurrent import Control.Concurrent.Chan import Control.Concurrent.MVar import Control.Monad {- promptInt, accumulator, makeAccPrompt as before -} main :: IO () main = do inChan <- newChan outMVar <- newEmptyMVar forkIO $ (getChanContents inChan) >>= (mapM_ (putMVar outMVar) . accumulator) let go = do p <- takeMVar outMVar m <- promptInt (makeAccPrompt p) case m of Just n -> do writeChan inChan n ns <- go return $ n:ns Nothing -> return [] xs <- go print xs The unsafeInterleaveIO is now hidden inside getChanContents. (I have an outMVar rather than an outChan just in case accumulator could produce lots of output before consuming much of its input.) Regards, Reid Barton
participants (3)
-
Reid Barton
-
Ronald Guida
-
Ryan Ingram