#7295: bad code for Double literals
------------------------------+---------------------------------------------
 Reporter:  jwlato            |          Owner:                  
     Type:  bug               |         Status:  new             
 Priority:  normal            |      Component:  Compiler        
  Version:  7.6.1             |       Keywords:                  
       Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown      |       Testcase:                  
Blockedby:                    |       Blocking:                  
  Related:                    |  
------------------------------+---------------------------------------------
 For this program

 {{{
 module Foo where

 foo :: [Double] -> [Double]
 foo = map f
   where f x = x*(-0.5)
 }}}

 GHC generates the following core:

 {{{
 Foo.foo5 :: GHC.Integer.Type.Integer
 [GblId,
  Str=DmdType,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=0, Value=True,
          ConLike=True, WorkFree=True, Expandable=True,
          Guidance=IF_ARGS [] 100 0}]
 Foo.foo5 = __integer 1

 Foo.foo4 :: GHC.Integer.Type.Integer
 [GblId,
  Str=DmdType,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=0, Value=True,
          ConLike=True, WorkFree=True, Expandable=True,
          Guidance=IF_ARGS [] 100 0}]
 Foo.foo4 = __integer 2

 Foo.foo3 :: GHC.Types.Double
 [GblId,
  Str=DmdType,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=0, Value=False,
          ConLike=False, WorkFree=False, Expandable=False,
          Guidance=IF_ARGS [] 51 20}]
 Foo.foo3 =
   case GHC.Float.$w$cfromRational Foo.foo5 Foo.foo4
   of _ { GHC.Types.D# x_agI ->
   GHC.Types.D# (GHC.Prim.negateDouble# x_agI)
   }

 Foo.foo1 :: GHC.Types.Double -> GHC.Types.Double
 [GblId,
  Arity=1,
  Str=DmdType U(L)m,
  Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True,
          ConLike=True, WorkFree=True, Expandable=True,
          Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False)
          Tmpl= \ (eta_B1 [Occ=Once] :: GHC.Types.Double) ->
                  GHC.Float.timesDouble eta_B1 Foo.foo3}]
 Foo.foo1 =
   \ (eta_B1 :: GHC.Types.Double) ->
     GHC.Float.timesDouble eta_B1 Foo.foo3

 Foo.foo :: [GHC.Types.Double] -> [GHC.Types.Double]
 [GblId,
  Arity=1,
  Str=DmdType,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=0, Value=True,
          ConLike=True, WorkFree=True, Expandable=True,
          Guidance=IF_ARGS [] 20 60}]
 Foo.foo =
   GHC.Base.map @ GHC.Types.Double @ GHC.Types.Double Foo.foo1
 }}}

 which looks pretty bad to me.

 This may be related to #5731, especially as 'foo2 = map (* (-0.5))'
 results in much better code.

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