#4064: SpecConstr broken for NOINLINE loops in 6.13
---------------------------------+------------------------------------------
    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
---------------------------------+------------------------------------------
 Example:

 {{{
 foo :: Int -> Int -> Int
 {-# NOINLINE foo #-}
 foo n k | n <= 0    = k
         | otherwise = foo (n-1) (k+1)
 }}}

 This is what GHC generates:

 {{{
 Rec {
 X.foo_$sfoo [Occ=LoopBreaker]
   :: GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Types.Int
 [GblId, Arity=2, Caf=NoCafRefs, Str=DmdType LL]
 X.foo_$sfoo =
   \ (sc_sjW :: GHC.Prim.Int#) (sc1_sjX :: GHC.Prim.Int#) ->
     case GHC.Prim.<=# sc1_sjX 0 of _ {
       GHC.Bool.False ->
         X.foo
           (GHC.Types.I# (GHC.Prim.-# sc1_sjX 1))
           (GHC.Types.I# (GHC.Prim.+# sc_sjW 1));
       GHC.Bool.True -> GHC.Types.I# sc_sjW
     }

 X.foo [InlPrag=NOINLINE (sat-args=2), Occ=LoopBreaker]
   :: GHC.Types.Int -> GHC.Types.Int -> GHC.Types.Int
 [GblId, Arity=2, Caf=NoCafRefs, Str=DmdType U(L)U(L)m]
 X.foo =
   \ (n_aaj :: GHC.Types.Int) (k_aak :: GHC.Types.Int) ->
     case n_aaj of _ { GHC.Types.I# x_ajn ->
     case GHC.Prim.<=# x_ajn 0 of _ {
       GHC.Bool.False ->
         case k_aak of _ { GHC.Types.I# x1_aiX ->
         X.foo
           (GHC.Types.I# (GHC.Prim.-# x_ajn 1))
           (GHC.Types.I# (GHC.Prim.+# x1_aiX 1))
         };
       GHC.Bool.True -> k_aak
     }
     }
 end Rec }


 ------ Local rules for imported ids --------
 "SC:X.foo0" [NEVER]
     forall {sc_sjW :: GHC.Prim.Int# sc1_sjX :: GHC.Prim.Int#}
       X.foo (GHC.Types.I# sc1_sjX) (GHC.Types.I# sc_sjW)
       = X.foo_$sfoo sc_sjW sc1_sjX
 }}}

 At the moment, we don't worker/wrapper NOINLINE things because doing so
 would generate a wrapper which wouldn't be inlined. But apparently, we do
 !SpecConstr NOINLINE functions, generating rules and specialisations which
 can never be used, like above.

 The trivial solution is to have !SpecConstr ignore NOINLINE functions.
 Perhaps we could also think about transforming `foo` to this instead:

 {{{
 {-# NOINLINE foo #-}
 foo = foo'

 foo' n k | n <= 0    = k
          | otherwise = foo' (n-1) (k+1)
 }}}

 Now, we can apply worker/wrapper and !SpecConstr to `foo'` without any
 restrictions. One could argue that `foo` has been "inlined" into its own
 rhs but I can't imagine how that could ever be a problem.

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