
Dear cafe, does anyone have an explanation for this?:
error (error "foo") *** Exception: foo
error $ error "foo" *** Exception: *** Exception: foo
-- Steffen

On Thu, Feb 3, 2011 at 2:44 PM, Steffen Schuldenzucker
Dear cafe,
does anyone have an explanation for this?:
error (error "foo") *** Exception: foo
error $ error "foo" *** Exception: *** Exception: foo
I don't know if this is relevant, but I thought that the GHC compiler believes that all exceptions are equivalent and indistinguishable - that is, in the presence of multiple exceptional code-paths it will make optimizations that would not otherwise otherwise be sound. That might not be the issue here, but it is interesting. http://research.microsoft.com/en-us/um/people/simonpj/papers/imprecise-exn.h... Antoine
-- Steffen
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

This is indeed very strange. On my latest GHC 7 (built a couple of days ago) it does the right thing when compiled, but in GHCi it behaves as you describe. I have no idea, frankly. On Thu, Feb 3, 2011 at 8:44 PM, Steffen Schuldenzucker < sschuldenzucker@uni-bonn.de> wrote:
Dear cafe,
does anyone have an explanation for this?:
error (error "foo") *** Exception: foo
error $ error "foo" *** Exception: *** Exception: foo
-- Steffen
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Thu, Feb 3, 2011 at 12:44 PM, Steffen Schuldenzucker
Dear cafe,
does anyone have an explanation for this?:
error (error "foo") *** Exception: foo
error $ error "foo" *** Exception: *** Exception: foo
Have you read the intermediate Core (using -ddump-simpl) for each variation? Cheers, Tim -- Tim Chevalier * http://cs.pdx.edu/~tjc/ * Often in error, never in doubt "an intelligent person fights for lost causes,realizing that others are merely effects" -- E.E. Cummings

catamorphism:
On Thu, Feb 3, 2011 at 12:44 PM, Steffen Schuldenzucker
wrote: Dear cafe,
does anyone have an explanation for this?:
error (error "foo") *** Exception: foo
error $ error "foo" *** Exception: *** Exception: foo
Have you read the intermediate Core (using -ddump-simpl) for each variation?
A. GHC.Base.bindIO @ GHC.Prim.Any @ [()] ((GHC.Err.error @ [GHC.Types.Char] (GHC.Base.unpackCString# "foo")) `cast` (CoUnsafe [GHC.Types.Char] (GHC.Types.IO GHC.Prim.Any) :: [GHC.Types.Char] ~ GHC.Types.IO GHC.Prim.Any)) ((\ (it_ade :: GHC.Prim.Any) (eta_B1 :: GHC.Prim.State# GHC.Prim.RealWorld) -> ((GHC.Base.returnIO @ [()] (GHC.Types.: @ () (it_ade `cast` (CoUnsafe GHC.Prim.Any () :: GHC.Prim.Any ~ ())) (GHC.Types.[] @ ()))) `cast` (GHC.Types.NTCo:IO [()] :: GHC.Types.IO [()] ~ (GHC.Prim.State# GHC.Prim.RealWorld -> (# GHC.Prim.State# GHC.Prim.RealWorld, [()] #)))) eta_B1) `cast` (GHC.Prim.Any -> sym (GHC.Types.NTCo:IO [()]) :: (GHC.Prim.Any -> GHC.Prim.State# GHC.Prim.RealWorld -> (# GHC.Prim.State# GHC.Prim.RealWorld, [()] #)) ~ (GHC.Prim.Any -> GHC.Types.IO [()]))) B. GHC.Base.bindIO @ GHC.Prim.Any @ [()] (GHC.Base.$ @ [GHC.Types.Char] @ (GHC.Types.IO GHC.Prim.Any) (GHC.Err.error @ (GHC.Types.IO GHC.Prim.Any)) (GHC.Err.error @ [GHC.Types.Char] (GHC.Base.unpackCString# "foo"))) ((\ (it_aib :: GHC.Prim.Any) (eta_B1 :: GHC.Prim.State# GHC.Prim.RealWorld) -> ((GHC.Base.returnIO @ [()] (GHC.Types.: @ () (it_aib `cast` (CoUnsafe GHC.Prim.Any () :: GHC.Prim.Any ~ ())) (GHC.Types.[] @ ()))) `cast` (GHC.Types.NTCo:IO [()] :: GHC.Types.IO [()] ~ (GHC.Prim.State# GHC.Prim.RealWorld -> (# GHC.Prim.State# GHC.Prim.RealWorld, [()] #)))) eta_B1) `cast` (GHC.Prim.Any -> sym (GHC.Types.NTCo:IO [()]) :: (GHC.Prim.Any -> GHC.Prim.State# GHC.Prim.RealWorld -> (# GHC.Prim.State# GHC.Prim.RealWorld, [()] #)) ~ (GHC.Prim.Any -> GHC.Types.IO [()])))

This is probably a result of strictness analysis. error is
technically strict, so it is reasonable to optimize to:
let e = error "foo" in e `seq` error e
On Thu, Feb 3, 2011 at 1:44 PM, Steffen Schuldenzucker
Dear cafe,
does anyone have an explanation for this?:
error (error "foo") *** Exception: foo
error $ error "foo" *** Exception: *** Exception: foo
-- Steffen
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Thu, Feb 3, 2011 at 2:03 PM, Luke Palmer
This is probably a result of strictness analysis. error is technically strict, so it is reasonable to optimize to:
let e = error "foo" in e `seq` error e
Yes, and you can see this in the Core code that Don posted: in version (A), GHC optimized away the outer call to error. But in version (B), the demand analyzer only knows that ($) is strict in its first argument -- it's not strict in its second. So it's not obviously safe to do the same optimization: the demand analyzer doesn't "look through" higher-order function arguments IIRC. (You can confirm this for yourself if you also want to read the demand analyzer output.) If ($) were getting inlined, the code would look the same coming into demand analysis in both cases, so you wouldn't see a difference. So I'm guessing you're compiling with -O0. Cheers, Tim -- Tim Chevalier * http://cs.pdx.edu/~tjc/ * Often in error, never in doubt "an intelligent person fights for lost causes,realizing that others are merely effects" -- E.E. Cummings

On Thursday 03 February 2011 5:12:54 PM Tim Chevalier wrote:
On Thu, Feb 3, 2011 at 2:03 PM, Luke Palmer
wrote: This is probably a result of strictness analysis. error is technically strict, so it is reasonable to optimize to:
let e = error "foo" in e `seq` error e
Yes, and you can see this in the Core code that Don posted: in version (A), GHC optimized away the outer call to error. But in version (B), the demand analyzer only knows that ($) is strict in its first argument -- it's not strict in its second. So it's not obviously safe to do the same optimization: the demand analyzer doesn't "look through" higher-order function arguments IIRC. (You can confirm this for yourself if you also want to read the demand analyzer output.)
If ($) were getting inlined, the code would look the same coming into demand analysis in both cases, so you wouldn't see a difference. So I'm guessing you're compiling with -O0.
Whatever is going on, it has to be active during ghci, because all these differences can be seen during interpretation (in 7.0.1, at least). Prelude> error (error "foo") *** Exception: foo Prelude> error $ error "foo" *** Exception: *** Exception: foo Prelude> let g :: (a -> b) -> a -> b ; g f x = f x in g error (error "foo") *** Exception: foo Prelude> let g :: (a -> b) -> a -> b ; g f x = f x Prelude> g error (error "foo") *** Exception: *** Exception: foo Prelude> let foo = error "foo" in error foo *** Exception: foo Prelude> let foo = error "foo" Prelude> error foo *** Exception: *** Exception: foo Actually compiling seems to remove the difference in 7.0.1, at least, because the output is always: Foo: foo regardless of ($) or not ('fix error' hangs without output as well, which isn't what I thought would happen). Anyhow, that rules out most general-purpose optimizations (including strictness analysis, I thought). - Dan

In general, errors are always interchangeable with another. An
exception in haskell is a value, rather than an event. Haskell
prescribes no evaluation order other than if the result is defined it
must be equivalant to the one generated by a normal-order reduction
strategy. Since error is not a valid value, any behavior including
just locking up is a completely acceptable (if not very friendly)
thing for a compiler to do.
In practice, we like writing compilers that help us find our errors
and using compilers that don't obfuscate them so compilers tend to
behave more or less like youd expect when presented with error, but
not at the expense of optimization or other necessary transformations.
GHC has stronger guarentees in order to support its imprecise
exceptions extension in that the exceptional value returned is
guarenteed to be (non-deterministically) selected from the set of all
possible errors for every possible evaluation order of the expression.
So It won't just conjure up something new out of thin air, but neither
can you expect any particular exception when your code can produce
more than one.
John
On Thu, Feb 3, 2011 at 2:42 PM, Dan Doel
On Thursday 03 February 2011 5:12:54 PM Tim Chevalier wrote:
On Thu, Feb 3, 2011 at 2:03 PM, Luke Palmer
wrote: This is probably a result of strictness analysis. error is technically strict, so it is reasonable to optimize to:
let e = error "foo" in e `seq` error e
Yes, and you can see this in the Core code that Don posted: in version (A), GHC optimized away the outer call to error. But in version (B), the demand analyzer only knows that ($) is strict in its first argument -- it's not strict in its second. So it's not obviously safe to do the same optimization: the demand analyzer doesn't "look through" higher-order function arguments IIRC. (You can confirm this for yourself if you also want to read the demand analyzer output.)
If ($) were getting inlined, the code would look the same coming into demand analysis in both cases, so you wouldn't see a difference. So I'm guessing you're compiling with -O0.
Whatever is going on, it has to be active during ghci, because all these differences can be seen during interpretation (in 7.0.1, at least).
Prelude> error (error "foo") *** Exception: foo Prelude> error $ error "foo" *** Exception: *** Exception: foo Prelude> let g :: (a -> b) -> a -> b ; g f x = f x in g error (error "foo") *** Exception: foo Prelude> let g :: (a -> b) -> a -> b ; g f x = f x Prelude> g error (error "foo") *** Exception: *** Exception: foo Prelude> let foo = error "foo" in error foo *** Exception: foo Prelude> let foo = error "foo" Prelude> error foo *** Exception: *** Exception: foo
Actually compiling seems to remove the difference in 7.0.1, at least, because the output is always:
Foo: foo
regardless of ($) or not ('fix error' hangs without output as well, which isn't what I thought would happen).
Anyhow, that rules out most general-purpose optimizations (including strictness analysis, I thought).
- Dan
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Thursday 03 February 2011 23:03:36, Luke Palmer wrote:
This is probably a result of strictness analysis. error is technically strict, so it is reasonable to optimize to:
let e = error "foo" in e `seq` error e
I think so too. Unoptimised, module Errors where foo = error (error "foo") bar = error $ error "bar" produces the core ======================================== Errors.bar :: forall a_aaN. a_aaN [GblId] Errors.bar = \ (@ a_aaN) -> GHC.Base.$ @ [GHC.Types.Char] @ a_aaN (GHC.Err.error @ a_aaN) (GHC.Err.error @ [GHC.Types.Char] (GHC.Base.unpackCString# "bar")) a_rb8 :: [GHC.Types.Char] [GblId, Str=DmdType b] a_rb8 = GHC.Err.error @ [GHC.Types.Char] (GHC.Base.unpackCString# "foo") Errors.foo :: forall a_aaP. a_aaP [GblId] Errors.foo = (\ (@ a_aaP) -> a_rb8) `cast` (forall a_aaP. CoUnsafe [GHC.Types.Char] a_aaP :: (forall a_aaP. [GHC.Types.Char]) ~ (forall a_aaP. a_aaP)) ============================================== The first argument to ($) is evaluated before the second [because the function may be lazy), resulting in the start of the error message "***Exception: ", then that error-call must evaluate its argument, error "bar", which results in "***Exception: bar" (and terminates the thread) and two "***Exception: " being printed. If I interpret the core correctly, error is so well known to the compiler that it strips off the outer `error' in foo even without optimisations (which surprises me a bit). With optimisations, ($) is inlined and `error $ error "bar"' is transformed to error (error "bar"), from then on both have identical structure and arrive at (mutatis mutandis) the same core (which is nearly the same as foo got without optimisations).

Thanks to all of you for making GHC's behaviour yet a bit clearer to me. On 02/03/2011 11:25 PM, Daniel Fischer wrote:
On Thursday 03 February 2011 23:03:36, Luke Palmer wrote:
This is probably a result of strictness analysis. error is technically strict, so it is reasonable to optimize to:
let e = error "foo" in e `seq` error e
I think so too. Unoptimised,
module Errors where
foo = error (error "foo")
bar = error $ error "bar"
produces the core ======================================== Errors.bar :: forall a_aaN. a_aaN [GblId] Errors.bar = \ (@ a_aaN) -> GHC.Base.$ @ [GHC.Types.Char] @ a_aaN (GHC.Err.error @ a_aaN) (GHC.Err.error @ [GHC.Types.Char] (GHC.Base.unpackCString# "bar"))
a_rb8 :: [GHC.Types.Char] [GblId, Str=DmdType b] a_rb8 = GHC.Err.error @ [GHC.Types.Char] (GHC.Base.unpackCString# "foo")
Errors.foo :: forall a_aaP. a_aaP [GblId] Errors.foo = (\ (@ a_aaP) -> a_rb8) `cast` (forall a_aaP. CoUnsafe [GHC.Types.Char] a_aaP :: (forall a_aaP. [GHC.Types.Char]) ~ (forall a_aaP. a_aaP)) ==============================================
The first argument to ($) is evaluated before the second [because the function may be lazy), resulting in the start of the error message "***Exception: ", then that error-call must evaluate its argument, error "bar", which results in "***Exception: bar" (and terminates the thread) and two "***Exception: " being printed. If I interpret the core correctly, error is so well known to the compiler that it strips off the outer `error' in foo even without optimisations (which surprises me a bit).
With optimisations, ($) is inlined and `error $ error "bar"' is transformed to error (error "bar"), from then on both have identical structure and arrive at (mutatis mutandis) the same core (which is nearly the same as foo got without optimisations).
participants (9)
-
Antoine Latter
-
Dan Doel
-
Daniel Fischer
-
Daniel Peebles
-
Don Stewart
-
John Meacham
-
Luke Palmer
-
Steffen Schuldenzucker
-
Tim Chevalier