
However, when I actually tried this out, I couldn't get it to compile. So I wound up back with trace. This does compile, and I think it does pretty much what we want in a "noninvasive" way, using unsafePerformIO via trace. import Debug.Trace t = foldr (+) 0 ( monitorprogress f [1..10000] ) monitorprogress f xs = map g $ zip [1..] xs where g (i,a) | f i == True = trace (show i) a | otherwise = a f x | x `mod` 1000 == 0 = True | otherwise = False Thomas Hartman/ext/dbcom@DBAmericas Sent by: haskell-cafe-bounces@haskell.org 11/29/2007 10:43 AM To haskell-cafe@haskell.org, droundy@darcs.net cc Subject Re: [Haskell-cafe] Progress indications Obviously heaps better than what I initially proposed. However, I would argue to go boldly with unsafePerformIO, which is the same thing Debug.Trace uses http://darcs.haskell.org/ghc-6.6/packages/base/Debug/Trace.hs since we are after debug.trace -like behavior. In particular, you wouldn't be able to use the unsafeInterleaveIO version to do a progress indicator for the function I initially proposed
t = foldr (+) 0 [1..10000]
since your lift would wind up being lifted into IO. But you would be able
to use the unsafePerformIO version, just like in what I initially proposed
you could use trace.
t = foldr (+) 0 ( lessSafeMonitoryProgress f [1..10000] )
where f i | i mod 1000 == 0 = (putStrLn . show ) i
| otherwise = return ()
Make sense?
thomas.
David Roundy
maybe Debug.Trace? like...
import Debug.Trace
t = foldr debugf 0 [1..10000]
f :: Int -> Int -> Int f = (+)
-- same typesig as f debugf :: Int -> Int -> Int debugf x y | y `mod` 1000 == 0 = x + (trace (show y) y) debugf x y = x + y
Or, more flexibly: import System.IO.Unsafe ( unsafeInterleaveIO ) monitorProgress :: (Int -> IO ()) -> [a] -> IO [a] monitorProgress f xs = mapM f' $ zip [0..] xs where f' (n,x) = unsafeInterleaveIO (f n >> return x) You could, of course, make this a function lessSafeMonitoryProgress :: (Int -> IO ()) -> [a] -> [a] by using unsafePerformIO instead of unsafeInterleaveIO, but that seems slightly scary to me. In any case, you can stick this on whichever of the lists you want to monitor the progress of. -- David Roundy Department of Physics Oregon State University _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe --- This e-mail may contain confidential and/or privileged information. If you are not the intended recipient (or have received this e-mail in error) please notify the sender immediately and destroy this e-mail. Any unauthorized copying, disclosure or distribution of the material in this e-mail is strictly forbidden. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe --- This e-mail may contain confidential and/or privileged information. If you are not the intended recipient (or have received this e-mail in error) please notify the sender immediately and destroy this e-mail. Any unauthorized copying, disclosure or distribution of the material in this e-mail is strictly forbidden.