Different results from GHC API and GHCi

I’ve encountered a difference in how some code is being run via the GHC API and GHCi, and am trying to figure out what is causing it. Ideally, I would like to get the GHC API working as GHCi does. I’ve test the below with GHC 9.6.2 and 9.8.1, and get the same results from each.

I have the below Haskell in “Doubles1.hs”:

module Doubles1 where

import Debug.Trace

newtype D = D Double

instance Eq D where
    D d1 == D d2 = trace ("d1 = " ++ show d1 ++ " d2 = " ++ show d2) d1 == d2

This is really just wrapping the normal equality operator on Double’s, so that, via the trace, we can see which Doubles are being equality checked.

The following behavior, from GHCi, is what I would expect:

% ghci
GHCi, version 9.8.1: https://www.haskell.org/ghc/  :? for help
ghci> encodeFloat 1000001 (-1024)
5.56269020895265e-303
ghci> :l Doubles1.hs
[1 of 1] Compiling Doubles1         ( Doubles1.hs, interpreted )
Ok, one module loaded.
ghci> D (encodeFloat 1000001 (-1024)) == D (5.56269020895265e-303)
d1 = 5.56269020895265e-303 d2 = 5.56269020895265e-303
True

We can see that encodeFloat 1000001 (-1024) evaluates to 5.56269020895265e-303. So D (encodeFloat 1000001 (-1024)) == D (5.56269020895265e-303) also evaluates to True.

Now, consider the below program using the GHC API:

module Main where

import GHC
import GHC.Paths
import Unsafe.Coerce
import Control.Monad.IO.Class

main :: IO ()
main = do
    runGhc (Just libdir) (do
        dyn_flags <- getSessionDynFlags
        _ <- setSessionDynFlags dyn_flags
        targets <- guessTarget "Doubles1.hs" Nothing Nothing
        _ <- setTargets [targets]
        _ <- load LoadAllTargets

        setContext $ map (IIDecl . simpleImportDecl . mkModuleName) ["Prelude", "Doubles1"]

        let chck = "D (encodeFloat 1000001 (-1024)) == D (5.56269020895265e-303)"
        v' <- compileExpr chck

        liftIO $ putStrLn chck
        liftIO . print $ (unsafeCoerce v' :: Bool))

This program uses compileExpr to perform the same equality check as I did in GHCi. However, running the program results in:

% cabal run
D (encodeFloat 1000001 (-1024)) == D (5.56269020895265e-303)
d1 = 5.56269020895265e-303 d2 = 5.335595834390497e-303
False

The equality is False, and the trace reveals that the second Double (the one I wrote as a literal?) has been slightly changed (from 5.5…e-303 to 5.3…e-303.)

Does anyone know why the GHC API- but not GHCi- would be turning 5.5…e-303 into 5.3…e-303? (Or, if that’s not what’s happening, what’s wrong with my test that is making it look like that is happening?)

Thanks for any help or advice!

I suggest trying to minimize this failing example by just parsing and printing a Double, and not involving any comparison.

Certainly a reasonable suggestion of a way to minimize- interestingly the already posted code works as I would expect on my home x86 computer (original post was from work on an ARM computer.) That is, both GHCi and the GHC API say the equality is true. So (1) might be an ARM issue (not sure if both behaviors could somehow be defended as correct?) and (2) will have to wait until tomorrow at work to experiment.

Why use anything but the latest minor GHC versions? You might end up diagnosing an issue that has already been fixed.

1 Like

Tried to reprod locally. It worked as expected. What version of GHC API are you using?

Why use anything but the latest minor GHC versions? You might end up diagnosing an issue that has already been fixed.
Also a fair point! (Although I thought this might be more floating point weirdness rather than a bug. I’m increasingly leaning toward it being a bug now though…)

I’ve now tested this program:

module Main where

import GHC
import GHC.Paths
import Unsafe.Coerce
import Control.Monad.IO.Class


main :: IO ()
main = do
    runGhc (Just libdir) (do
        dyn_flags <- getSessionDynFlags
        _ <- setSessionDynFlags dyn_flags

        setContext [IIDecl . simpleImportDecl . mkModuleName $ "Prelude"]

        let chck = "5.56269020895265e-303 :: Double"
        v' <- compileExpr chck

        liftIO $ print (5.56269020895265e-303 :: Double)
        liftIO $ print (unsafeCoerce v' :: Double))

with GHC 9.6.6, 9.8.4, and 9.10.1. All three versions output:

5.56269020895265e-303
5.335595834390497e-303

on my work (ARM) computer.

What version of GHC API are you using?

AFAIK, the GHC API is directly tied to GHC- so I think 9.6.6, 9.8.4, and 9.10.1? Am I misunderstanding how that works? Can I ask what kind of processor you have?

It seems like the lower 4 bytes of the double (Binary64) representation of your desired number are all zeros in their encoded form:

>>> struct.unpack('d',0x012E848200000000.to_bytes(byteorder='little',length=8))
(5.56269020895265e-303,)

Are you also able to reproduce the issue when using e.g. having a one there? Like

>>> struct.unpack('d',0x012E848200000001.to_bytes(byteorder='little',length=8))
(5.5626902089526504e-303,)

What if you try 3.8147010803222656 instead? It has a less intimidating exponent component in its IEEE754 representation, which is 0x400E848200000000.

        let chck = "5.5626902089526504e-303 :: Double"
        v' <- compileExpr chck

        liftIO $ print (unsafeCoerce v' :: Double))

results in
7.416887269295208e-303
being printed.

The float 3.8147010803222656 works correctly (3.8147010803222656 is also printed.)

You should a bug report on Glasgow Haskell Compiler / GHC · GitLab

I couldn’t reproduce this on my ARM box with ghc-9.6 nor the master branch of GHC. Curious what’s going on there.

What CPU are you using exactly? I also second a ghc ticket.

Bug report here:

I couldn’t repro duce this on my ARM box with ghc-9.6 nor the master branch of GHC. Curious what’s going on there.

What CPU are you using exactly? I also second a ghc ticket.

Interesting! Using an M1 Mac.

1 Like

Thanks for the ticket. Might be mac related then.