#5767: Integer inefficiencies
--------------------------------------+-------------------------------------
  Reporter:  rl                       |          Owner:  igloo           
      Type:  bug                      |         Status:  new             
  Priority:  highest                  |      Milestone:  7.4.1           
 Component:  Compiler                 |        Version:  7.5             
Resolution:                           |       Keywords:                  
        Os:  Unknown/Multiple         |   Architecture:  Unknown/Multiple
   Failure:  Runtime performance bug  |     Difficulty:  Unknown         
  Testcase:                           |      Blockedby:                  
  Blocking:                           |        Related:                  
--------------------------------------+-------------------------------------

Comment(by rl):

 I finally found a small test case for the missing
 `integerToInt/smallInteger` rule:

 {{{
 foo :: (Integral a, Num a) => a -> a
 {-# INLINE foo #-}
 foo x = fromIntegral x

 bar :: Int -> Int
 bar x = foo x
 }}}

 The head generates this:

 {{{
 foo_$sfoo =
   \ (eta_B1 :: Int) ->
     case eta_B1 of _ { I# i_ara ->
     case integerToInt (smallInteger i_ara) of wild1_ard { __DEFAULT ->
     I# wild1_ard
     }
     }

 bar = foo_$sfoo
 }}}

 Whereas 7.2.2 generates this:

 {{{
 bar_$sfoo = \ (eta_B1 :: Int) -> eta_B1

 bar = bar_$sfoo
 }}}

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