[GHC] #8635: GHC optimisation flag ignored when importing a local module with derived type classes
GHC
ghc-devs at haskell.org
Fri Dec 27 21:20:54 UTC 2013
#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
More information about the ghc-tickets
mailing list