#7295: bad code for Double literals
---------------------------------+------------------------------------------
    Reporter:  jwlato            |       Owner:  igloo           
        Type:  bug               |      Status:  new             
    Priority:  normal            |   Milestone:                  
   Component:  Compiler          |     Version:  7.6.1           
    Keywords:                    |          Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |     Failure:  None/Unknown    
  Difficulty:  Unknown           |    Testcase:                  
   Blockedby:                    |    Blocking:                  
     Related:                    |  
---------------------------------+------------------------------------------
Changes (by simonpj):

  * owner:  => igloo
  * difficulty:  => Unknown


Comment:

 Good point. Here's what is happening.
  * In `map (* (-0.5)) xs :: [Double]`, the typechecker and/or desugarer
 can see a totally mono-typed use of the literal `0.5` at `Double` and so
 genreates exactly that literal.
  * But in your main example, you define a polymorphic function `f`, whose
 type is
 {{{
 f :: Fractional a => a -> a
 }}}
  Sure, `f` has only one call site but the typechecker/desugarer don't know
 that, so they generate `fromRational d (negate d (1 % 2))`, where `d` is
 the fractional dictionary.

 So, good as the typechecker/desugarer short-cut is for literals, your
 example points out that we should do better constant folding for literals
 that start life overloaded, but become specialised. This will also happen
 when we have a top-level overloaded function that gets specialised.

 My solution.  In `GHC.Float` we see
 {{{
 instance Fractional Float where
   fromRational = blah blah blah
 }}}
 Instead we want
 {{{
 instance Fractioal Float where
   {-# INLINE fromRational #-}
   fromRational (a :% b) = rationalToFloat a b

 rationalToFloat :: Integer -> Integer -> Float
 {-# NOINLINE [1] rationalToFloat
 rationalToFloat = blah blah blah   -- As before
 }}}
 AND we want a constant-folding rule in `PrelRules` for `rationalToFloat`
 that spots two `Integer`-literal arguments and produces the right float;
 just like `TcHsSyn.shortCutLit` does.

 Same for `fromRational` at `Double`.

 We already have similar mechanisms for `fromInteger`, so I think that's
 all right.

 Simon

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