[Haskell-cafe] Thunks

Ketil Malde ketil at malde.org
Fri Oct 15 05:22:14 EDT 2010


Bernie Pope <florbitous at gmail.com> writes:

> You can use side effects to observe the order of evaluation, by
> wrapping observed expressions (thunks) with some IO computation inside
> unsafePerformIO.

Not what OP asks for, but I've used a variant of this as a rather
hackish to provide progress reporting.  I take a list that is lazily
generated, and wrap the elements with an IO action that outputs the
count every 'step' elements.  When the list is evaluated, the IO actions
are executed. Code below.

-k

-- | Output (to stderr) progress while evaluating a lazy list.
--   Useful for generating output while (conceptually, at least) in pure code
countIO :: String -> String -> Int -> [a] -> IO [a]
countIO msg post step xs = sequence' $ map unsafeInterleaveIO ((blank >> outmsg (0::Int) >> c):cs)
   where (c:cs) = ct 0 xs
         output   = hPutStr stderr
         blank    = output ('\r':take 70 (repeat ' '))
         outmsg x = output ('\r':msg++show x) >> hFlush stderr
         ct s ys = let (a,b) = splitAt (step-1) ys
                       next  = s+step
                   in case b of [b1] -> map return a ++ [outmsg (s+step) >> hPutStr stderr post >> return b1]
                                []   -> map return (init a) ++ [outmsg (s+length a) >> hPutStr stderr post >> return (last a)]
                                _ -> map return a ++ [outmsg s >> return (head b)] ++ ct next (tail b)

-- | A lazier version of 'Control.Monad.sequence' in "Control.Monad", needed by 'countIO' above.
sequence' :: [IO a] -> IO [a]
sequence' ms = foldr k (return []) ms
    where k m m' = do { x <- m; xs <- unsafeInterleaveIO m'; return (x:xs) }

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants


More information about the Haskell-Cafe mailing list