[GHC] #9035: ghci sometimes displays Word32 as Word64
GHC
ghc-devs at haskell.org
Thu Apr 24 18:13:16 UTC 2014
#9035: ghci sometimes displays Word32 as Word64
--------------------------+------------------------------------------------
Reporter: | Owner:
MikeIzbicki | Status: new
Type: bug | Milestone:
Priority: normal | Version: 7.8.2
Component: GHCi | Operating System: Linux
Keywords: | Type of failure: Incorrect result at runtime
Architecture: x86_64 | Test Case:
(amd64) | Blocking:
Difficulty: |
Unknown |
Blocked By: |
Related Tickets: |
--------------------------+------------------------------------------------
Given this code:
{{{
module Main
where
import Data.Word
import Unsafe.Coerce
import System.IO
nanFloat :: Float
nanFloat = unsafeCoerce (maxBound :: Word32)
float2word32 :: Float -> Word32
float2word32 = unsafeCoerce
nanDouble :: Double
nanDouble = unsafeCoerce (maxBound :: Word64)
double2word64 :: Double -> Word64
double2word64 = unsafeCoerce
main = do
putStrLn $ "nanFloat = " ++ show (float2word32 nanFloat)
putStrLn $ "nanFloat = " ++ show (float2word32 $ nanFloat + 1)
putStrLn $ "nanDouble = " ++ show (double2word64 nanDouble)
putStrLn $ "nanDouble = " ++ show (double2word64 $ nanDouble + 1)
}}}
If we compile with GHC and run, we correctly output:
{{{
nanFloat = 4294967295
nanFloat = 4294967295
nanDouble = 18446744073709551615
nanDouble = 18446744073709551615
}}}
But if we instead load in ghci, we get the following output:
{{{
nanFloat = 4294967295
nanFloat = 140247862083583
nanDouble = 18446744073709551615
nanDouble = 18446744073709551615
}}}
For some reason, ghci is displaying (nanFloat+1) as having significantly
more digits than can possibly stored in a Word32 value.
Test system: Intel Core 2 Duo running Debian with GHC 7.8.2
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9035>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list