#4081: Strict constructor fields inspected in loop
---------------------------------+------------------------------------------
    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
---------------------------------+------------------------------------------
 Here is a small example to illustrate the problem:

 {{{
 module T where

 data S a b = S !a !b

 class C a where
  make :: a -> S a a

 instance C Int where
  {-# NOINLINE make #-}
  make n = S n n

 foo :: (C a, Num a) => a -> Int -> a
 {-# INLINE foo #-}
 foo x k = k `seq` m `seq` go k 0
  where
    S m n = make x

    go 0 i = i
    go k i = go (k-1) (i + m)
 }}}

 {{{
 module U where

 import T

 bar :: Int -> Int -> Int
 bar s k = foo s k + 1
 }}}

 Relying on !LiberateCase seems to be the only way to unbox `m` outside of
 the loop in `bar`. The seq in `foo` doesn't help because it gets
 eliminated immediately.

 GHC does have enough information to do this:

 {{{
 U.bar =
  \ (s_aaw [Dmd=Just S(A)] :: GHC.Types.Int)
    (k_aax [Dmd=Just U(L)] :: GHC.Types.Int) ->
    case k_aax
    of k1_ajh [Dmd=Just U(L)] { GHC.Types.I# ipv_ajj [Dmd=Just A] ->
    case T.$fCInt_$cmake s_aaw of _ { T.S m_ajy [Dmd=Just U(T)] _ ->
    ...
 }}}

 Note the demand on `m`. If it was an argument instead of a local binding,
 it would be unboxed by w/w.

 Also, the seq does help if we use lazy pairs instead of strict ones.

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