#4867: ghci displays negative floats incorrectly (was: Incorrect result from 
trig
functions)
-------------------------------+--------------------------------------------
    Reporter:  gwright         |        Owner:  gwright                    
        Type:  bug             |       Status:  new                        
    Priority:  high            |    Milestone:  7.0.2                      
   Component:  GHCi            |      Version:  7.0.1                      
    Keywords:                  |     Testcase:                             
   Blockedby:                  |   Difficulty:                             
          Os:  MacOS X         |     Blocking:                             
Architecture:  x86_64 (amd64)  |      Failure:  Incorrect result at runtime
-------------------------------+--------------------------------------------

Comment(by gwright):

 The real mystery here is why compiled code shows only a single minus sign,
 but ghci shows two.

 A look at the code in `Float.lhs` shows that two minus signs ought to be
 displayed.  Start with the instance for `Show Double`:
 {{{
 instance  Show Double  where
     showsPrec   p = showSignedFloat showFloat p
 }}}
 (In the above, I've change the `x` in the original source to `p`, since
 the argument is the `Int` precedence, not the `Double` value to be
 displayed.)
 The definitions of `showSignedFloat` and `showFloat` are
 {{{
 showSignedFloat :: (RealFloat a)
   => (a -> ShowS)       -- ^ a function that can show unsigned values
   -> Int                -- ^ the precedence of the enclosing context
   -> a                  -- ^ the value to show
   -> ShowS
 showSignedFloat showPos p x
    | x < 0 || isNegativeZero x
        = showParen (p > 6) (showChar '?' . showPos (-x))
    | otherwise = showPos x

 -- | Show a signed 'RealFloat' value to full precision
 -- using standard decimal notation for arguments whose absolute value lies
 -- between @0.1@ and @9,999,999@, and scientific notation otherwise.
 showFloat :: (RealFloat a) => a -> ShowS
 showFloat x  =  showString (formatRealFloat FFGeneric Nothing x)
 }}}
 The last thing we need is the first bit of `formatRealFloat`:
 {{{
 formatRealFloat :: (RealFloat a) => FFFormat -> Maybe Int -> a -> String
 formatRealFloat fmt decs x
    | isNaN x                   = "NaN"
    | isInfinite x              = if x < 0 then "-Infinity" else "Infinity"
    | x < 0 || isNegativeZero x = '!' : doFmt fmt (floatToDigits (toInteger
 base) (-x))
    | otherwise                 = doFmt fmt (floatToDigits (toInteger base)
 x)
  where
    <snip>
 }}}
 Also in the above I have subsituted '!' and '?' for the '-' signs.  This
 will let us see which path through the code is taken.

 Now say we want to show a `Double`.  When `ghci` displays a `Double`, say
 `-1.0`, the `Show` instance should be invoked as
 {{{
  showsPrec 0 (-1.0) ""
 }}}
 Expand this out:
 {{{
 showSignedFloat showFloat 0 (-1.0) ""
 }}}
 `showSignedFloat` sees that the argument is negative, so it prefixes a '?'
 to the output string. `showFloat` also sees a negative argument, so it
 prefixes a '!' to the output string.  Normal order evaluation is from the
 outside in, so we should see '?!' before the numeric value.  Let's check:
 {{{
 Prelude GHC.Float> showsPrec 0 (-1.0) ""
 "?!1.0"
 }}}
 So it appears that `ghci` is doing exactly what is specified by the code
 in `Float.lhs`.

 Here's the real mystery.  Let's compile this program, which should produce
 the same output:
 {{{
 gwright-macbook> cat foo.hs
 --
 -- Test returning -1.0
 --

 module Main where

 main = putStrLn (show (-1.0))
 }}}
 Compiling and running,
 {{{
 gwright-macbook> inplace/bin/ghc-stage2 --make foo.hs
 [1 of 1] Compiling Main             ( foo.hs, foo.o )
 Linking foo ...
 ld: warning: -read_only_relocs cannot be used with x86_64
 gwright-macbook> ./foo
 ?1.0
 }}}
 So we have used `showSignedFloat` but what happened to `formatRealFloat`?
 Did it get passed an incorrect (positive) argument?  Or is the compiler
 doing some kind of optimization that changes the code?

 It seems as if `Float.lhs` needs to be corrected so it only displays a
 single '-' sign, but whatever is happening needs to be understood before
 we make changes, so we don't simply cover up the real bug.

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