
In a "normal" programming language, you might write something like this: for x = 1 to 1000000 print x ...do slow complex stuff... next x In Haskell, you're more likely to write something like result k = filter my_weird_condition $ map strange_conversion $ unfoldr ... That means that when you try to process the result, lots of processing happens, and your program just appears to lock up until a result is produced. So, like, how do you make it so that some kind of progress information is output while it's working? (Aside from dunking everything into the IO monad and ruining all your beautiful abstractions.) There doesn't seem to be a clean solution to this one...

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
t.
Andrew Coppin

On Wed, Nov 28, 2007 at 05:58:07PM -0500, Thomas Hartman wrote:
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

This might be a little less invasive. You could add any unsafe* stuff
as you desire.
-- every hundred elements generates a trace marker
addTrace xs = addTrace' 100 0 where
addTrace' 0 !cnt xs = Left cnt : addTrace' 100 cnt xs
addTrace' n !cnt (x:xs) = Right x : addTrace' (n - 1) (cnt + 1) xs
separateTrace = partition isLeft
-- result k = filter my_weird_condition $ map strange_conversion $ unfoldr ...
observe k = do
let (trace, result) = (filter my_weird_condition >< id) $
separateTrace . addTrace $
map strange_conversion $ unfoldr...
print trace
return result
On Nov 28, 2007 5:16 PM, David Roundy
On Wed, Nov 28, 2007 at 05:58:07PM -0500, Thomas Hartman wrote:
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

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.

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.

Lazy evaluation can sometimes be helpful here. I once wrote a
raytracer that computed the resulting image using a pure function that
returned a list of the RGB colors of the pixels: [(Word8, Word8,
Word8)]
When plotting the pixels to the screen in the IO monad, the value of
each pixel would be computed on demand, and so the image was shown
progressively as the calculations were performed.
I was new to haskell when I made this program and when I ran the
program for this first time I was expecting to experience a long pause
and then a display of the final image. I was very surprised to see
progressive rendering!
On Nov 29, 2007 12:03 AM, Andrew Coppin
In a "normal" programming language, you might write something like this:
for x = 1 to 1000000 print x ...do slow complex stuff... next x
In Haskell, you're more likely to write something like
result k = filter my_weird_condition $ map strange_conversion $ unfoldr ...
That means that when you try to process the result, lots of processing happens, and your program just appears to lock up until a result is produced. So, like, how do you make it so that some kind of progress information is output while it's working? (Aside from dunking everything into the IO monad and ruining all your beautiful abstractions.) There doesn't seem to be a clean solution to this one...
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Bit Connor wrote:
I was new to haskell when I made this program and when I ran the program for this first time I was expecting to experience a long pause and then a display of the final image. I was very surprised to see progressive rendering!
Neat, isn't it? :-) On the other hand, if you do something like sort a list, you cannot see the first element of the result until the entire unsorted list has been computed... which can take a heck of a long time, depending on what the computation is. And since it's all calls to map and filter et al., it's not immediately clear how to provide any feedback on how much longer there is to wait. It seems unsafePerformIO is the way to go here. (BTW, what's the difference between unsafePerformIO and unsafeInterleaveIO?)

Bit Connor wrote:
computation is. And since it's all calls to map and filter et al., it's ...it's not immediately clear how to provide any feedback on how much longer there is to wait.
Andrew Coppin wrote:
It seems unsafePerformIO is the way to go here. ...unsafeInterleaveIO
I disagree. The unsafe... functions are called that for a reason, and their use should be highly discouraged, except in cases where there is absolutely no other reasonable way. I don't believe that this is one of those cases. A better approach is to use pure monads. Instead of f :: ... -> a write functions whose type is something like f :: ... -> MyMonad a where MyMonad is defined in one and only one place in your program. Or, better yet, polymorphic things like f :: Monad m => ... -> m a f :: MyMonadClass m => ... -> m a Then when you later need to add something like progress indicators, you just add that to the capabilities of your monad, and add some updateProgress calls to your functions. By using "do" notation wisely, you can keep your abstractions just as clear as they were, and cleanly separated from the progress logic. Other things you may need to add later in real-world programs are exception handling, logging, trace, etc. All of these are easy if you started out in a monad. -Yitz

but there's no risk using trace is there? t.
The unsafe... functions are called that for a reason, and their use should be highly discouraged, except in cases where there is absolutely no other reasonable way.
"Yitzchak Gale"
computation is. And since it's all calls to map and filter et al., it's ...it's not immediately clear how to provide any feedback on how much longer there is to wait.
Andrew Coppin wrote:
It seems unsafePerformIO is the way to go here. ...unsafeInterleaveIO
I disagree. The unsafe... functions are called that for a reason, and their use should be highly discouraged, except in cases where there is absolutely no other reasonable way. I don't believe that this is one of those cases. A better approach is to use pure monads. Instead of f :: ... -> a write functions whose type is something like f :: ... -> MyMonad a where MyMonad is defined in one and only one place in your program. Or, better yet, polymorphic things like f :: Monad m => ... -> m a f :: MyMonadClass m => ... -> m a Then when you later need to add something like progress indicators, you just add that to the capabilities of your monad, and add some updateProgress calls to your functions. By using "do" notation wisely, you can keep your abstractions just as clear as they were, and cleanly separated from the progress logic. Other things you may need to add later in real-world programs are exception handling, logging, trace, etc. All of these are easy if you started out in a monad. -Yitz _______________________________________________ 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.

On Nov 29, 2007, at 17:13 , Thomas Hartman wrote:
but there's no risk using trace is there?
If you're doing any other I/O, you may be surprised by where the trace output shows up relative to it. -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

Brandon S. Allbery KF8NH wrote:
On Nov 29, 2007, at 17:13 , Thomas Hartman wrote:
but there's no risk using trace is there?
If you're doing any other I/O, you may be surprised by where the trace output shows up relative to it.
How about if the "I/O" is to write to a different stream? Then it wouldn't matter too much. Or perhaps updating a real progress bar widget on a GUI. Or - better still - frobnicate an MVar or something. (Then you can handle what you do with these "update" signals somewhere else without cluttering the main algorithm too much...)

Andrew Coppin
(BTW, what's the difference between unsafePerformIO and unsafeInterleaveIO?)
Prelude> :m + System.IO.Unsafe Prelude System.IO.Unsafe> :t unsafePerformIO unsafePerformIO :: IO a -> a Prelude System.IO.Unsafe> :t unsafeInterleaveIO unsafeInterleaveIO :: IO a -> IO a The former lets you cheat by pretending an IO action is a pure function, the latter, which really should be called 'notQuiteAsUnsafeInterleaveIO', just makes a strict IO action lazier, deferring it to when the result is demanded. -k -- If I haven't seen further, it is by standing in the footprints of giants
participants (9)
-
Andrew Coppin
-
Bit Connor
-
Brandon S. Allbery KF8NH
-
David Roundy
-
Henning Thielemann
-
Ketil Malde
-
Nicolas Frisby
-
Thomas Hartman
-
Yitzchak Gale