#5963: Fixed format floating point conversion does not round to even
------------------------------+---------------------------------------------
 Reporter:  augustss          |          Owner:                  
     Type:  bug               |         Status:  new             
 Priority:  normal            |      Component:  libraries/base  
  Version:  7.4.1             |       Keywords:                  
       Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown      |       Testcase:                  
Blockedby:                    |       Blocking:                  
  Related:                    |  
------------------------------+---------------------------------------------
 Conversion of floating point numbers to a fixed numbers of decimals should
 use round-to-even rather that rounding up when the number is right between
 two possible results.

 E.g., printf "%.1f" 0.45 should produce "0.4" rather than "0.5".

 The heart of the problem is in libraries/base/GHC/Float.lhs.
 The roundTo function should be replaced by this

 {{{

 roundTo :: Int -> Int -> [Int] -> (Int,[Int])
 roundTo base d is =
   case f d True is of
     x@(0,_) -> x
     (1,xs)  -> (1, 1:xs)
     _       -> error "roundTo: bad Value"
  where
   b2 = base `quot` 2

   f n _ []     = (0, replicate n 0)
   f 0 e (x:xs) | x == b2 && e && all (== 0) xs = (0, [])   -- Round to
 even when at exactly half the base
                | otherwise = (if x >= b2 then 1 else 0, [])
   f n _ (i:xs)
      | i' == base = (1,0:ds)
      | otherwise  = (0,i':ds)
       where
        (c,ds) = f (n-1) (even i) xs
        i'     = c + i
 }}}

 I also (as the original author of the code) note that the large parts of
 that module was taken verbatim from the hbc libraries without attribution.
 :)

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