Replaced throw to throwIO where type is IO

Hello, Attached is a small patch to: Control/Exception/Base.hs which replaces all uses of 'throw' to 'throwIO' where the type is IO. It would be nice if someone can review and apply it. Regards, Bas

I just extended the patch with two more throw-to-throwIO replacements
in GHC/IO.hs.
On Fri, Sep 24, 2010 at 11:46 PM, Bas van Dijk
Hello,
Attached is a small patch to: Control/Exception/Base.hs which replaces all uses of 'throw' to 'throwIO' where the type is IO.
It would be nice if someone can review and apply it.
Regards,
Bas

On 24/09/10 23:20, Bas van Dijk wrote:
I just extended the patch with two more throw-to-throwIO replacements in GHC/IO.hs.
We should be using throwIO rather than throw in an IO context, so if there are no objections I'll test and apply the patch. It's not an API or a functionality change, so I don't think the full libraries proposal process is warranted here. I'm sure none of these are actually bugs, but it's good practice to use throwIO. Unfortunately there's no easy way to get the type system to tell us. Cheers, Simon

On Sun, Sep 26, 2010 at 12:28 PM, Simon Marlow
On 24/09/10 23:20, Bas van Dijk wrote:
I just extended the patch with two more throw-to-throwIO replacements in GHC/IO.hs.
We should be using throwIO rather than throw in an IO context, so if there are no objections I'll test and apply the patch. It's not an API or a functionality change, so I don't think the full libraries proposal process is warranted here.
I'm sure none of these are actually bugs, but it's good practice to use throwIO. Unfortunately there's no easy way to get the type system to tell us.
Cheers, Simon
Thanks Simon, I created a ticket for this so we don't forget: http://hackage.haskell.org/trac/ghc/ticket/4380 Bas

Why is this patch a good thing?
Not that I'm against it, but I am curious.
Thanks,
Antoine
On Sep 24, 2010 4:47 PM, "Bas van Dijk"
Hello,
Attached is a small patch to: Control/Exception/Base.hs which replaces all uses of 'throw' to 'throwIO' where the type is IO.
It would be nice if someone can review and apply it.
Regards,
Bas

On Sat, Sep 25, 2010 at 2:21 AM, Antoine Latter
Why is this patch a good thing?
Maybe it isn't. However the documentation of throwIO states that it should be used in preference of throw because it guarantees ordering with respect to other IO actions: http://haskell.org/ghc/docs/6.12.1/html/libraries/base-4.2.0.0/Control-Excep... Now the question is does it matter whether we use throw or throwIO in (for example): catchJust :: Exception e => (e -> Maybe b) -- ^ Predicate to select exceptions -> IO a -- ^ Computation to run -> (b -> IO a) -- ^ Handler -> IO a catchJust p a handler = catch a handler' where handler' e = case p e of Nothing -> throwIO e Just b -> handler b Maybe I'm missing something obvious. In that case, sorry for the noise. Regards, Bas

Hi Bas, On Fri, Sep 24, 2010 at 11:46:40PM +0200, Bas van Dijk wrote:
Attached is a small patch to: Control/Exception/Base.hs which replaces all uses of 'throw' to 'throwIO' where the type is IO.
It would be nice if someone can review and apply it.
Thanks for your work on this. Please see http://www.haskell.org/haskellwiki/Library_submissions for the process to propose changes to the core libraries. Thanks Ian

On Sat, Sep 25, 2010 at 2:54 PM, Ian Lynagh
Thanks for your work on this. Please see http://www.haskell.org/haskellwiki/Library_submissions for the process to propose changes to the core libraries.
Yes, I know the process. However, consider my mail more as a question if the current use of throw is always equivalent to using throwIO. Take the current onException as an example: onException io what = io `catch` \e -> do _ <- what throw (e :: SomeException) is this always equivalent to: onException io what = io `catch` \e -> do _ <- what throwIO (e :: SomeException) ? Thinking about this some more I can't seem to find a situation where the two are different. So my patch can safely be ignored and I apologize for the noise. However I do wonder why onException is using throw instead of the recommended throwIO. Has this to do with performance since they're both primitive operations: throw :: Exception e => e -> a throw e = raise# (toException e) throwIO :: Exception e => e -> IO a throwIO e = IO (raiseIO# (toException e)) ? Thanks, Bas

On Sat, Sep 25, 2010 at 4:41 PM, Bas van Dijk
However I do wonder why onException is using throw instead of the recommended throwIO. Has this to do with performance since they're both primitive operations:
throw :: Exception e => e -> a throw e = raise# (toException e)
throwIO :: Exception e => e -> IO a throwIO e = IO (raiseIO# (toException e))
I think I found the answer myself. I see that raiseIO# is implemented as jumping to the implementation of raise#: rts/Exception.cmm line: 588 stg_raiseIOzh { /* Args :: R1 :: Exception */ jump stg_raisezh; } So I guess using #raise directly is faster since it doesn't need to perform the jump. I'll see if I can make some Criterion benchmarks to see if it's actually faster. Bas

On Sat, Sep 25, 2010 at 5:12 PM, Bas van Dijk
I'll see if I can make some Criterion benchmarks to see if it's actually faster.
And it's faster indeed: ------------------------------------------------------------------------------------------------------ import Control.Exception import Prelude hiding (catch) import Criterion.Main throws :: Int -> IO () throws 0 = return () throws n = throw DivideByZero `catch` \DivideByZero -> throws (n-1) throwIOs :: Int -> IO () throwIOs 0 = return () throwIOs n = throwIO DivideByZero `catch` \DivideByZero -> throws (n-1) n :: Int n = 1000000 main = defaultMain [ bench "throw" (throws n) , bench "throwIO" (throwIOs n) ] ------------------------------------------------------------------------------------------------------ $ ghc --make Throwing.hs -O2 -o throwing [1 of 1] Compiling Main ( Throwing.hs, Throwing.o ) Linking throwing ... $ ./throwing warming up estimating clock resolution... mean is 24.38796 us (40001 iterations) found 1669 outliers among 39999 samples (4.2%) 1 (2.5e-3%) low severe 1446 (3.6%) high severe estimating cost of a clock call... mean is 1.814127 us (46 iterations) found 7 outliers among 46 samples (15.2%) 5 (10.9%) high mild 2 (4.3%) high severe benchmarking throw collecting 100 samples, 1 iterations each, in estimated 21.14298 s bootstrapping with 100000 resamples mean: 207.5380 ms, lb 207.1919 ms, ub 207.9817 ms, ci 0.950 std dev: 2.002210 ms, lb 1.645117 ms, ub 2.496120 ms, ci 0.950 found 6 outliers among 100 samples (6.0%) 5 (5.0%) high mild 1 (1.0%) high severe variance introduced by outliers: 0.990% variance is unaffected by outliers benchmarking throwIO collecting 100 samples, 1 iterations each, in estimated 20.68932 s bootstrapping with 100000 resamples mean: 211.1240 ms, lb 210.8239 ms, ub 211.5199 ms, ci 0.950 std dev: 1.752349 ms, lb 1.389534 ms, ub 2.311696 ms, ci 0.950 found 9 outliers among 100 samples (9.0%) 5 (5.0%) high mild 4 (4.0%) high severe variance introduced by outliers: 0.990% variance is unaffected by outliers Regards, Bas

On Sat, Sep 25, 2010 at 5:34 PM, Gregory Collins
Bas van Dijk
writes: throwIOs :: Int -> IO () throwIOs 0 = return () throwIOs n = throwIO DivideByZero `catch` \DivideByZero -> throws (n-1)
Should that perhaps be "throwIOs (n-1)" in the recursive case?
Oops! Good catch. Rerunning it with the correct definition: $ ./throwing warming up estimating clock resolution... mean is 21.03730 us (40001 iterations) found 1716 outliers among 39999 samples (4.3%) 1402 (3.5%) high severe estimating cost of a clock call... mean is 1.902708 us (43 iterations) found 2 outliers among 43 samples (4.7%) 2 (4.7%) high severe benchmarking throw collecting 100 samples, 1 iterations each, in estimated 21.07508 s bootstrapping with 100000 resamples mean: 212.2662 ms, lb 211.7532 ms, ub 213.0318 ms, ci 0.950 std dev: 3.153136 ms, lb 2.307677 ms, ub 4.915720 ms, ci 0.950 found 10 outliers among 100 samples (10.0%) 1 (1.0%) low severe 5 (5.0%) high mild 4 (4.0%) high severe variance introduced by outliers: 0.993% variance is unaffected by outliers benchmarking throwIO collecting 100 samples, 1 iterations each, in estimated 17.07039 s bootstrapping with 100000 resamples mean: 174.1298 ms, lb 172.5284 ms, ub 178.3283 ms, ci 0.950 std dev: 12.27940 ms, lb 5.843075 ms, ub 25.16350 ms, ci 0.950 found 9 outliers among 100 samples (9.0%) 2 (2.0%) high mild 7 (7.0%) high severe variance introduced by outliers: 1.000% variance is unaffected by outliers Now this is surprising, throwIO is actually faster than throw. I'll see if the core sheds any light on this. Bas

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
participants (5)
-
Antoine Latter
-
Bas van Dijk
-
Gregory Collins
-
Ian Lynagh
-
Simon Marlow