Replaced throw to throwIO where type is IO

Bas van Dijk v.dijk.bas at gmail.com
Sat Sep 25 14:05:06 EDT 2010


Here's an even simpler benchmark that shows the difference between
throw and throwIO:


{-# LANGUAGE ScopedTypeVariables #-}

import Control.Exception
import Prelude hiding (catch)

import Criterion.Main

ignoreExceptions :: IO () -> IO ()
ignoreExceptions m = m `catch` \(_ :: SomeException) -> return ()

main :: IO ()
main = defaultMain
       [ bench "throw"   $ ignoreExceptions (throw   DivideByZero)
       , bench "throwIO" $ ignoreExceptions (throwIO DivideByZero)
       ]


$ ghc --make Throwing.hs -O2 -fforce-recomp -o throwing
[1 of 1] Compiling Main             ( Throwing.hs, Throwing.o )
Linking throwing ...


$ ./throwing
warming up
estimating clock resolution...
mean is 21.65454 us (40001 iterations)
found 1884 outliers among 39999 samples (4.7%)
  412 (1.0%) high mild
  1462 (3.7%) high severe
estimating cost of a clock call...
mean is 1.893442 us (42 iterations)
found 4 outliers among 42 samples (9.5%)
  1 (2.4%) high mild
  3 (7.1%) high severe

benchmarking throw
collecting 100 samples, 258616 iterations each, in estimated 2.165460 s
bootstrapping with 100000 resamples
mean: 85.76940 ns, lb 85.20807 ns, ub 86.40616 ns, ci 0.950
std dev: 3.047974 ns, lb 2.681299 ns, ub 3.679702 ns, ci 0.950
found 1 outliers among 100 samples (1.0%)
variance introduced by outliers: 0.999%
variance is unaffected by outliers

benchmarking throwIO
collecting 100 samples, 319584 iterations each, in estimated 2.165460 s
bootstrapping with 100000 resamples
mean: 62.71774 ns, lb 62.41275 ns, ub 63.45298 ns, ci 0.950
std dev: 2.274746 ns, lb 1.130328 ns, ub 4.596054 ns, ci 0.950
found 9 outliers among 100 samples (9.0%)
  4 (4.0%) high mild
  5 (5.0%) high severe
variance introduced by outliers: 0.999%
variance is unaffected by outliers


Regards,

Bas


More information about the Libraries mailing list