
On 31 January 2011 14:17, Leon Smith
Is there some subtle semantic difference? Is there a performance difference? It seems like a trivial thing, but I am genuinely curious.
According to my understanding the two should have equivalent semantics. As for performance, I whipped up a trivial Criterion microbenchmark and the version that doesn't use "finally" seems to consistently benchmark 32ns (33%) faster than the version that does use it, likely because it avoids a useless mask/restore pair. (Note that this result is reversed if you compile without -O2, I guess because -O2 optimises the library "finally" enough to overcome the fact that it does an extra mask). Code in the appendix. Cheers, Max === {-# LANGUAGE Rank2Types #-} import Control.Exception import Criterion.Main {-# NOINLINE bracket_no_finally #-} bracket_no_finally :: IO a -> (a -> IO b) -> (a -> IO c) -> IO c bracket_no_finally before after thing = mask $ \restore -> do a <- before r <- restore (thing a) `onException` after a _ <- after a return r {-# NOINLINE bracket_finally #-} bracket_finally :: IO a -> (a -> IO b) -> (a -> IO c) -> IO c bracket_finally before after thing = mask $ \restore -> do a <- before r <- restore (thing a) `finally` after a return r {-# NOINLINE test_bracket #-} test_bracket :: (forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c) -> IO () test_bracket bracket = bracket (return ()) (\() -> return ()) (\() -> return ()) main = defaultMain [ bench "finally" $ test_bracket bracket_finally , bench "no finally" $ test_bracket bracket_no_finally ]