[Haskell-cafe] Faster timeout but is it correct?

Bas van Dijk v.dijk.bas at gmail.com
Sat Feb 19 00:04:15 CET 2011


I have some more results:

The willTimeout and wontTimeout benchmarks are a bit unfair:

willTimeout = shouldTimeout    $ timeout      1 (threadDelay oneSec)
wontTimeout = shouldNotTimeout $ timeout oneSec (return ())

Nobody ever writes code like this. So I wrote some benchmarks that
hopefully better reflect some real-world code:

busyWillTimeout = do
  r <- newIORef 10000000
  shouldTimeout $ timeout 100 $ busy r
  n <- readIORef r
  when (n==0) $ error "n == 0 !!!"

busyWontTimeout = do
  r <- newIORef 1000
  shouldNotTimeout $ timeout oneSec $ busy r
  n <- readIORef r
  when (n/=0) $ error "n /= 0 !!!"

busy r = do
  n <- readIORef r
  if n == 0
    then return ()
    else writeIORef r (n - 1) >> busy r

shouldTimeout :: IO (Maybe a) -> IO ()
shouldTimeout m = do mb <- m
                     case mb of
                       Nothing -> return ()
                       _       -> error "Should have timed out!"

shouldNotTimeout :: IO (Maybe a) -> IO a
shouldNotTimeout m = do mb <- m
                        case mb of
                          Just x -> return x
                          _      -> error "Should not have timed out!"

The busyWontTimeout is the most representative benchmark. It performs
a busy computation and gives it enough time to complete.

This time I ren the benchmarks with +RTS -N2:

willTimeout/old       22.78159 us  1.0 x
willTimeout/new       22.34967 us  1.0 x
willTimeout/event     10.05289 us  2.3 x

busyWillTimeout/old   10.58061 ms  1.0 x (std dev: 4.6)
busyWillTimeout/new   11.89530 ms  0.9 x (std dev: 4.6)
busyWillTimeout/event 9.983601 ms  1.1 x (std dev: 1.2)

wontTimeout/old       13.78843 us  1.0  x
wontTimeout/new       832.4918 ns  16.6 x
wontTimeout/event     1.042921 us  13.2 x

busyWontTimeout/old   57.10021 us  1.0 x
busyWontTimeout/new   56.85652 us  1.0 x
busyWontTimeout/event 35.67142 us  1.6 x

The willTimeout benchmark is slightly faster with -N2 while the
wontTimeout is slightly slower. All timeouts score similarly in the
busyWillTimeout benchmark.

The most representative busyWontTimeout benchmark is the interesting
one. Both the old and new score similarly while the event-manager
based timeout is a modest 1.6 x faster. Since this is the most
representative benchmark I'm beginning to favour this implementation.

While writing this email I was doing another run of the benchmarks.
Suddenly the willTimeout/new benchmark crashed with the message:

benchmarking willTimeout/new
collecting 100 samples, 211 iterations each, in estimated 654.8272 ms
bench_timeouts_threaded: <<timeout>>

Oops! That "<<timeout>>" is the Timeout exception not getting caught
by my exception handler while it should. This is a major bug. I
believe it is caused by this piece of code:

  ...
  uninterruptibleMask $ \restore -> do
    tid <- unsafeUnmask $ forkIO $ do
             tid <- myThreadId
             threadDelay n
             throwTo myTid $ Timeout tid
  ...

While I uninterruptibly mask asynchronous exceptions I need to
temporarily unmask them so that the forked thread can be killed
lateron.

I think the bug is that I first call unsafeUnmask and then fork the
thread which throws the Timeout exception. I can imagine there's a
brief period after the forkIO call where we're still in the unmasked
state. If the timeout thread then immediately throws the Timeout
exception (which is the case in the willTimeout benchmark) it will be
received by our thread and won't get caught.

The solution is probably to reverse the order of: "unsafeUnmask $
forkIO" to "forkIO $ unsafeUnmask". Or just use "forkIOUnmasked". The
reason I didn't used that in the first place was that it was much
slower for some reason.

So, since the new implementation is not really faster in a
representative benchmark and above all is buggy, I'm planning to ditch
it in favour of the event-manager based timeout.

Thanks for reading my rambling,

Bas



More information about the Haskell-Cafe mailing list