#5298: Inlined functions aren't fully specialised
---------------------------------+------------------------------------------
    Reporter:  reinerp           |       Owner:                         
        Type:  bug               |      Status:  new                    
    Priority:  normal            |   Component:  Compiler               
     Version:  7.0.3             |    Keywords:                         
    Testcase:                    |   Blockedby:                         
          Os:  Unknown/Multiple  |    Blocking:                         
Architecture:  Unknown/Multiple  |     Failure:  Runtime performance bug
---------------------------------+------------------------------------------
 When a function is inlined, it can expose other functions as candidates
 for specialisation, but GHC doesn't specialise them.

 For instance, given the two modules

 {{{
 module A where

 {-# INLINABLE fac #-}
 fac :: Num a => a -> a
 fac 0 = 1
 fac n = n * fac (n-1)

 {-# INLINE f #-}
 f :: Num a => a -> a
 f a = fac a
 }}}


 {{{
 module B where

 import A

 g :: Int -> Int
 g x = f x
 }}}

 we see that f is inlined, but fac isn't specialised for Ints:

 {{{
 B.g :: Int -> Int
 [GblId,
  Arity=1,

  Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=1, Value=True,
          ConLike=True, Cheap=True, Expandable=True,
          Guidance=IF_ARGS [0] 30 0}]
 B.g =
   \ (x_ary :: Int) ->
     A.fac @ Int $fNumInt x_ary
 }}}

 Removing the INLINE pragma on f doesn't help.

 Either of the following changes will cause fac to be specialised:

  * adding {-# SPECIALISE f :: Int -> Int #-} to module B
  * defining "g x = fac x" instead

 This happens with both GHC 7.0.3 and GHC HEAD

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5298>
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