#3738: INLINE function loses unfolding
---------------------------------+------------------------------------------
    Reporter:  rl                |       Owner:                         
        Type:  bug               |      Status:  new                    
    Priority:  normal            |   Component:  Compiler               
     Version:  6.13              |    Keywords:                         
          Os:  Unknown/Multiple  |    Testcase:                         
Architecture:  Unknown/Multiple  |     Failure:  Runtime performance bug
---------------------------------+------------------------------------------
 Small program:
 {{{
 foo :: Num a => [a] -> a
 {-# INLINE foo #-}
 foo = go 0
   where
     go m (n:ns) = m `seq` go (m+n) ns
     go m []     = m

 bar :: [Int] -> Int
 {-# INLINE bar #-}
 bar = foo
 }}}
 Here is what `bar` looks like in the interface file:
 {{{
 a6de4c46e53e565ed25ab5a38910e9cb
   $wgo :: GHC.Prim.Int# -> [GHC.Types.Int] -> GHC.Prim.Int#
     {- Arity: 2, HasNoCafRefs, Strictness: LS -}
 6838e3faa095285614477ebc92f54987
   bar :: [GHC.Types.Int] -> GHC.Types.Int
     {- Arity: 1, HasNoCafRefs, Strictness: Sm, Inline: INLINE,
        Unfolding: InlineRule: (arity 0 False) (Foo.bar_foo) -}
 5d06906ae99b9aefa1c6d251c3f2fc46
   bar_foo :: [GHC.Types.Int] -> GHC.Types.Int
     {- Arity: 1, HasNoCafRefs, Strictness: Sm,
        Unfolding: InlineRule: (arity 0 True) (\ w :: [GHC.Types.Int] ->
                                               case @ GHC.Types.Int
 Foo.$wgo 0 w of ww { DEFAULT ->
                                               GHC.Types.I# ww }) -}
 }}}
 Note that the loop has disappeared from `bar`'s unfolding. Also, `bar_foo`
 doesn't have an INLINE pragma.

 Incidentally, GHC specialises `foo` here and the specialisation doesn't
 get an INLINE pragma, either:
 {{{
   foo :: forall a. GHC.Num.Num a => [a] -> a
     {- Arity: 1, HasNoCafRefs, Strictness: L, Inline: INLINE,
        Unfolding: InlineRule: (arity 1 False) ... -}

  foo_$sfoo :: [GHC.Types.Int] -> GHC.Types.Int
     {- Arity: 1, HasNoCafRefs, Strictness: Sm,
        Unfolding: InlineRule: (arity 0 False) ... -}

 "SPEC Foo.foo [GHC.Types.Int]" ALWAYS forall $dNum :: GHC.Num.Num
 GHC.Types.Int
   Foo.foo @ GHC.Types.Int $dNum = Foo.foo_$sfoo
 }}}

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