#4441: NCG miscompiles Double -> Float -> Double
---------------------------------+------------------------------------------
Reporter: dterei | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler (NCG)
Version: 7.1 | Keywords:
Testcase: | Blockedby:
Os: Unknown/Multiple | Blocking:
Architecture: x86 | Failure: Incorrect result at runtime
---------------------------------+------------------------------------------
I have a need to truncate a double to only float precision but then store
it back in a double as I'm printing from the double to a hexadecimal
representation.
To achieve this I basically do two calls to realToFrac. A test case for
this is below. When I compile it with -fasm -O it appears as if
'(realToFrac . realToFrac)' is changed to 'id'. (Not what actually happens
as bug occurs in NCG, after Core stage, but thats how the programs
behaviour is changed). This bug is specific to -fasm, compiling the
program below with -fllvm or -fvia-C produces the correct results.
Test Case:
{{{
module Main where
import Data.Array.ST
import Control.Monad.ST
import Data.Word
import Data.Char
import Numeric
import System.IO
-- Test runner
main = do
putStr "Enter a double: "
hFlush stdout
d <- double
print $ "Float Version : " ++ (fToStr $ realToFrac d)
print $ "Double Version: " ++ (dToStr d)
double :: IO Double
double = do
x <- getLine
return $ read x
-----------------------------------------------------------------------------
-- * Floating point conversion
--
dToStr :: Double -> String
dToStr d
= let bs = doubleToBytes d
hex d' = case showHex d' "" of
[] -> error "dToStr: too few hex digits for float"
[x] -> ['0',x]
[x,y] -> [x,y]
_ -> error "dToStr: too many hex digits for float"
str = map toUpper $ concat . reverse . (map hex) $ bs
in "0x" ++ str
fToStr :: Float -> String
fToStr = (dToStr . realToFrac)
--
-----------------------------------------------------------------------------
-- Converting floating-point literals to integrals for printing
castDoubleToWord8Array :: STUArray s Int Double -> ST s (STUArray s Int
Word8)
castDoubleToWord8Array = castSTUArray
doubleToBytes :: Double -> [Int]
doubleToBytes d
= runST (do
arr <- newArray_ ((0::Int),7)
writeArray arr 0 d
arr <- castDoubleToWord8Array arr
i0 <- readArray arr 0
i1 <- readArray arr 1
i2 <- readArray arr 2
i3 <- readArray arr 3
i4 <- readArray arr 4
i5 <- readArray arr 5
i6 <- readArray arr 6
i7 <- readArray arr 7
return (map fromIntegral [i0,i1,i2,i3,i4,i5,i6,i7])
)
}}}
Output with '-fasm -O':
{{{
$ ./TestCase
Enter a double: 2.0e-2
Float Version : 0x3F947AE147AE147B
Double Version: 0x3F947AE147AE147B
}}}
Output with '-fvia-C -O':
{{{
$ ./TestCase
Enter a double: 2.0e-2
Float Version : 0x3F947AE140000000
Double Version: 0x3F947AE147AE147B
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4441>
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