#2092: Quadratic amount of code generated
-----------------------------------------+----------------------------------
    Reporter:  igloo                     |       Owner:             
        Type:  run-time performance bug  |      Status:  new        
    Priority:  normal                    |   Milestone:  6.10 branch
   Component:  Compiler                  |     Version:  6.9        
    Severity:  normal                    |    Keywords:             
  Difficulty:  Unknown                   |    Testcase:             
Architecture:  Unknown                   |          Os:  Unknown    
-----------------------------------------+----------------------------------
 Originally discovered by Twan van Laarhoven, here:
 http://www.haskell.org/pipermail/cvs-ghc/2008-February/040981.html

 On the HEAD, compiling this module:
 {{{
 {-# LANGUAGE MagicHash #-}

 module M1 where

 import GHC.Exts

 type FastInt = Int#

 data U = Mk1 { a :: (), b :: FastInt, c :: () }
        | Mk2 { a :: (), b :: FastInt, c :: () }

 instance Eq U where
     x == y = b x ==# b y
 }}}
 with
 {{{
 ghc -c M1.hs -O -ddump-simpl
 }}}
 we see
 {{{
 M1.== :: M1.U -> M1.U -> GHC.Base.Bool
 [GlobalId]
 [Arity 2
  NoCafRefs
  Str: DmdType SS]
 M1.== =
   \ (x_a5J :: M1.U) (y_a5L :: M1.U) ->
     case case y_a5L of tpl_B2 {
            M1.Mk1 ipv_B3 ipv1_B4 ipv2_B5 -> ipv1_B4;
            M1.Mk2 ipv_B3 ipv1_B4 ipv2_B5 -> ipv1_B4
          }
     of wild_B1 { __DEFAULT ->
     case case x_a5J of tpl_B2 {
            M1.Mk1 ipv_B3 ipv1_B4 ipv2_B5 -> ipv1_B4;
            M1.Mk2 ipv_B3 ipv1_B4 ipv2_B5 -> ipv1_B4
          }
     of wild1_Xk { __DEFAULT ->
     GHC.Prim.==# wild1_Xk wild_B1
     }
     }
 }}}
 which looks good: Extract the !FastInt from one value, then the other,
 then compare.

 However, if we have this module instead:
 {{{
 module M2 where

 import GHC.Exts

 newtype FastInt = FastInt Int
     deriving Eq

 data U = Mk1 { a :: (), b :: {-# UNPACK #-} !FastInt, c :: () }
        | Mk2 { a :: (), b :: {-# UNPACK #-} !FastInt, c :: () }

 instance Eq U where
     x == y = b x == b y
 }}}
 again compiling with
 {{{
 ghc -c M2.hs -O -ddump-simpl
 }}}
 we see
 {{{
 M2.== :: M2.U -> M2.U -> GHC.Base.Bool
 [GlobalId]
 [Arity 2
  NoCafRefs
  Str: DmdType SS]
 M2.== =
   \ (x_a5M :: M2.U) (y_a5O :: M2.U) ->
     case x_a5M of tpl_Xj {
       M2.Mk1 ipv_Xn rb_B6 ipv1_B5 ->
         case y_a5O of tpl1_Xl {
           M2.Mk1 ipv2_Xp rb1_Xw ipv3_XX -> GHC.Prim.==# rb_B6 rb1_Xw;
           M2.Mk2 ipv2_Xp rb1_Xw ipv3_XX -> GHC.Prim.==# rb_B6 rb1_Xw
         };
       M2.Mk2 ipv_Xn rb_B6 ipv1_B5 ->
         case y_a5O of tpl1_Xl {
           M2.Mk1 ipv2_Xp rb1_Xw ipv3_XX -> GHC.Prim.==# rb_B6 rb1_Xw;
           M2.Mk2 ipv2_Xp rb1_Xw ipv3_XX -> GHC.Prim.==# rb_B6 rb1_Xw
         }
     }
 }}}
 where the extraction of the second !FastInt happens inside the branches of
 the extraction of the first !FastInt, giving a quadratic (in the number of
 constructors) amount of code. We would expect to get code like that in the
 first example.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/2092>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to