#5327: INLINABLE pragma and newtypes prevents inlining
---------------------------------+------------------------------------------
    Reporter:  reinerp           |       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
---------------------------------+------------------------------------------
 Compile the following code with 'ghc -O2 -ddump-simpl':

 {{{
 module A where

 newtype Size = Size Int

 {-# INLINABLE val2 #-}
 val2 = Size 0

 f n = case val2 of Size s -> s + s > n
 }}}

 With ghc-7.1.20110629, we get the following Core:

 {{{
 A.f1 =
   case A.val2 `cast` (A.NTCo:Size :: A.Size ~ GHC.Types.Int)
   of _ { GHC.Types.I# x_aoz ->
   GHC.Types.I# (GHC.Prim.+# x_aoz x_aoz)
   }

 A.f = \ (n_ab1 :: GHC.Types.Int) -> GHC.Classes.gtInt A.f1 n_ab1
 }}}
 and we get something similar with ghc-7.0.3. In particular, for both
 versions of ghc, the addition {{{s+s}}} should be simplified to {{{0}}},
 but isn't.

 Any of the following changes will let {{{s+s}}} simplify to {{{0}}}:

  * change {{{newtype Size = ...}}} into {{{data Size = ...}}}

  * remove the INLINABLE pragma

  * with ghc-7.0.3, turning the INLINABLE pragma into INLINE. However, with
 ghc-7.1.20110629, the INLINE pragma doesn't fix the problem.

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