#4495: GHC fails to inline methods of single-method classes
---------------------------------+------------------------------------------
    Reporter:  diatchki          |       Owner:                         
        Type:  bug               |      Status:  new                    
    Priority:  normal            |   Component:  Compiler               
     Version:  7.1               |    Keywords:                         
    Testcase:                    |   Blockedby:                         
          Os:  Unknown/Multiple  |    Blocking:                         
Architecture:  Unknown/Multiple  |     Failure:  Runtime performance bug
---------------------------------+------------------------------------------
 Consider the following module:
 {{{
 module A where

 class C a where
   f :: a

 g :: C a => (a,a)
 g = (f,f)
 }}}

 GHC has a nice optimization where the dictionaries for classes with
 just a single method (and no super-classes) are represented with a
 newtype.
 This means that, essentially, the "dictionary" is the method itself,
 and the code that "extracts" a method from a dictionary is just the
 identity
 function.  For this reason, we can completely eliminate the extraction
 code
 by always inlining the method.

 This works as expected in GHC 6.12.2 but something seems to have changed
 in
 the current HEAD, so that the "extraction code" (i.e., the method "f")
 does
 not seem to get eliminated:


 [GHC 6.12.2]
 {{{
 f :: forall a. (C a) => a
 GblId[ClassOp]

 f = \ (@ a) (tpl [ALWAYS Once Nothing] :: C a) -> tpl `cast` ...

 g :: forall a. (C a) => (a, a)
 GblId

 g = __inline_me (\ (@ a) (d :: C a) -> (d `cast` ..., d `cast` ...)
 }}}

 [HEAD as of Nov 14 2010]
 {{{
 f [InlPrag=[NEVER]] :: forall a. C a => a
 [GblId[ClassOp],
  Arity=1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=1, Value=True,
          ConLike=True, Cheap=True, Expandable=True,
          Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=True)},
  RULES: Built in rule for f: "Class op f"]
 f = \ (@ a) (tpl [Occ=Once] :: C a) -> tpl `cast` ...


 g :: forall a. C a => (a, a)
 [GblId,
  Arity=1,
  Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True,
          ConLike=True, Cheap=True, Expandable=True,
          Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False)
          Tmpl= \ (@ a) (d :: C a) -> (f @ a d, f @ a d)}]

 g = \ (@ a) (d :: C a) -> (f @ a d, f @ a d)
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4495>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to