[Haskell-cafe] Re: Re: Waiting for thread to finish

Ben Franksen ben.franksen at online.de
Tue Nov 27 20:17:36 EST 2007


Don Stewart wrote:
> Beautiful code can be very efficient.

Indeed, as I recently the opportunity to demonstrate to my co-workers by
re-implementing a script written in Perl that turned out to be just a bit
too slow to be useful in practice. My version was not only one tenth the
code size and about 20 times faster, it also revealed bugs in the original
implementation as well as in the specification.

It was fun, too. For instance, the OP's question reminded me of a little
generic wrapper I wrote  -- more or less for my own amusement -- during the
course of this project. It outputs dots during an operation that might take
a little longer to finish (a database query in my case)... just so the user
doesn't get nervous ;-) And because I enjoyed it so much (and to show off)
I threw in the timing measurement...

module Gimmick where

import Control.Concurrent
import Control.Exception
import System.CPUTime
import System.IO

tickWhileDoing :: String -> IO a -> IO a
tickWhileDoing msg act = do
  hPutStr stderr msg >> hPutChar stderr ' ' >> hFlush stderr
  start_time <- getCPUTime
  tickerId <- forkIO ticker
  res <- act `finally` killThread tickerId
  stop_time <- getCPUTime
  let time_diff = realToFrac (stop_time - start_time) / 1e12
  hPutStrLn stderr $ " done (took us " ++ show time_diff ++ " seconds)"
  return res
  where
    ticker = do
      hPutChar stderr '.' >> hFlush stderr
      threadDelay 100000 {-microsec-}
      ticker

I think nobody in his right mind would even try to do something like that in
C or Perl or whatever, at least not if it wasn't strictly a requirement and
correct operation is important (the script gets executed as part of our
build process and a subtle concurrency bug could lead to a wrong
configuration for the target control system). In Haskell it was so easy to
do that I just couldn't resist.

Cheers
Ben

PS (completely off-topic, sorry): I've been using the collections library
throughout the project & I must say it is a lot nicer to work with than the
base library mumble-jumble of duplicate interfaces, qualified imports and
whatnot. The only disadvantages are that the API is not yet as complete as
e.g. Data.Map, and that I have to manually hide name-clashing Prelude
functions in almost every module. Many thanks to Jean-Philippe Bernardy for
pioneering this work.



More information about the Haskell-Cafe mailing list