[GHC] #8635: GHC optimisation flag ignored when importing a local module with derived type classes

#8635: GHC optimisation flag ignored when importing a local module with derived type classes ------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Keywords: | Operating System: Unknown/Multiple Architecture: Unknown/Multiple | Type of failure: None/Unknown Difficulty: Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | ------------------------------------+------------------------------------- Given Foo.hs and Bar.hs: {{{ module Foo where data Food = Food -- deriving Eq {-# OPTIONS_GHC -O2 -ddump-simpl #-} module Bar where import Foo bar :: Int -> Bool bar x = x == 72 }}} If I run: {{{ ghc --make Bar -fforce-recomp }}} I get (snipped): {{{ Bar.bar = \ (x_afk :: GHC.Types.Int) -> case x_afk of _ { GHC.Types.I# x1_alo -> case x1_alo of _ { __DEFAULT -> GHC.Types.False; 72 -> GHC.Types.True } } }}} `bar` now looks pretty well optimised. However, if I uncomment the `deriving Eq` I get: {{{ Bar.bar1 = GHC.Types.I# 72 Bar.bar2 = GHC.Classes.== @ GHC.Types.Int GHC.Classes.$fEqInt Bar.bar = \ (x_amD :: GHC.Types.Int) -> Bar.bar2 x_amD Bar.bar1 }}} Now `bar` looks like terrible code, using dictionaries, boxing etc. It seems adding `deriving` in the imported and unused module makes it ignore the optimisation level. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8635 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8635: GHC optimisation flag ignored when importing a local module with derived type classes -------------------------------------+------------------------------------ Reporter: NeilMitchell | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by NeilMitchell): * cc: ndmitchell@… (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8635#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8635: GHC optimisation flag ignored when importing a local module with derived type classes -------------------------------------+------------------------------------ Reporter: NeilMitchell | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by simonpj): I agree this is strange behaviour. Here's why it happens. * With `--make` GHC reads each library interface file only once, e.g. that defining equality for `Int`. * Without `-O` (i.e. with `-O0`), GHC sets `-fignore-interface-pragmas`. * When reading an interface file with `-fignore-interface-pragmas`, GHC skips all the unfoldings and other inessential info. * Without the `deriving` stuff, there's no reason to read the crucial interface file when compiling `Foo`. So it's read when compiling `Bar`, and hence when `-O` is set. * With the `deriving` clause, the crucial interface file is read when compiling `Foo`, but the unfoldings are skipped, and hence are unavailable when compiling `Bar`. You can get the behaviour you want by adding `-fno-ignore-interface- pragmas`. Maybe this should be the case with `--make`? But that choice would have the following downside: with `-fno-ignore-interface-pragamas` all unfoldings are read in, and may subsequently get used even by the modest optimisation done with `-O0`. Mind you, that ''might'' conceivably be a win. Maybe compile time and binary size would only increase marginally, but execution time would fall significantly? Would someone like to try the effect on compile times, binary size, and execution time, of using `-fno-ignore-interface-pragmas` with `-O0`? Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8635#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8635: GHC optimisation flag ignored when importing a local module with derived type classes -------------------------------------+------------------------------------ Reporter: NeilMitchell | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by NeilMitchell): Thanks for the explanation. As long as it doesn't happen at `-O1` (which it won't, from your explanation) it won't actually matter to me in practice. It does mean that at `-O0` the effect of things like `-O2` is dependent on what modules you import, what functions they use, what order things are processed by `ghc --make` etc. I suspect that inlining very small things like `$` can only be a win in terms of code size. Seeing them in the output, even at `-O0`, was a little surprising (although entirely understandable). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8635#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8635: GHC optimisation flag ignored when importing a local module with derived type classes -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #9370 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by rwbarton): * related: => #9370 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8635#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8635: GHC optimisation flag ignored when importing a local module with derived type classes -------------------------------------+------------------------------------- Reporter: Neil Mitchell | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #9370 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by Ben Gamari: Old description:
Given Foo.hs and Bar.hs:
{{{ module Foo where data Food = Food -- deriving Eq
{-# OPTIONS_GHC -O2 -ddump-simpl #-} module Bar where import Foo bar :: Int -> Bool bar x = x == 72 }}}
If I run:
{{{ ghc --make Bar -fforce-recomp }}}
I get (snipped):
{{{ Bar.bar = \ (x_afk :: GHC.Types.Int) -> case x_afk of _ { GHC.Types.I# x1_alo -> case x1_alo of _ { __DEFAULT -> GHC.Types.False; 72 -> GHC.Types.True } } }}}
`bar` now looks pretty well optimised. However, if I uncomment the `deriving Eq` I get:
{{{ Bar.bar1 = GHC.Types.I# 72 Bar.bar2 = GHC.Classes.== @ GHC.Types.Int GHC.Classes.$fEqInt Bar.bar = \ (x_amD :: GHC.Types.Int) -> Bar.bar2 x_amD Bar.bar1 }}}
Now `bar` looks like terrible code, using dictionaries, boxing etc. It seems adding `deriving` in the imported and unused module makes it ignore the optimisation level.
New description: Given Foo.hs and Bar.hs: {{{#!hs module Foo where data Food = Food -- deriving Eq {-# OPTIONS_GHC -O2 -ddump-simpl #-} module Bar where import Foo bar :: Int -> Bool bar x = x == 72 }}} If I run: {{{ ghc --make Bar -fforce-recomp }}} I get (snipped): {{{ Bar.bar = \ (x_afk :: GHC.Types.Int) -> case x_afk of _ { GHC.Types.I# x1_alo -> case x1_alo of _ { __DEFAULT -> GHC.Types.False; 72 -> GHC.Types.True } } }}} `bar` now looks pretty well optimised. However, if I uncomment the `deriving Eq` I get: {{{ Bar.bar1 = GHC.Types.I# 72 Bar.bar2 = GHC.Classes.== @ GHC.Types.Int GHC.Classes.$fEqInt Bar.bar = \ (x_amD :: GHC.Types.Int) -> Bar.bar2 x_amD Bar.bar1 }}} Now `bar` looks like terrible code, using dictionaries, boxing etc. It seems adding `deriving` in the imported and unused module makes it ignore the optimisation level. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8635#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8635: GHC optimisation flag ignored when importing a local module with derived type classes -------------------------------------+------------------------------------- Reporter: NeilMitchell | Owner: RolandSenn Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #9370 #13002 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RolandSenn): * owner: (none) => RolandSenn * related: #9370 => #9370 #13002 Comment: [https://ghc.haskell.org/trac/ghc/ticket/13002#comment:18 | See ticket #13002 comment 18] -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8635#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC