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!