
Same happens in HEAD, so nothing to do with your changes.
From your program we get
case (/# 0.0 0.0) of r -> ...(==# r r)... and the (==# r r) rewrites to True. Presumably for Float and Double you don't want that to happen. So you'd better not use mkRelOpRule for Float and Double relops. Better define mkFloatingRelOpRule instead, which doesn't have the equal-args thing. Simon | -----Original Message----- | From: ghc-devs-bounces@haskell.org [mailto:ghc-devs-bounces@haskell.org] | On Behalf Of Jan Stolarek | Sent: 22 April 2013 13:48 | To: ghc-devs@haskell.org | Subject: Handling of NaN | | I need some help with my work on ticket #6135. Consider this program: | | {-# LANGUAGE BangPatterns, MagicHash #-} module Main where | | import GHC.Exts | | main = print $ nan## ==## nan## | where !(D# nan##) = 0.0 / 0.0 | | This prints False, which is a correct implementation of IEEE754 | standard. However when I compile this with my modified compiler that | uses new comparison primops (they return Int# instead of | Bool) I get True, whcih obviously is incorrect. I belive that the | problem lies in this piece of code from prelude/PrelRules.hs: | | mkRelOpRule :: Name -> (forall a . Ord a => a -> a -> Bool) | -> [RuleM CoreExpr] -> Maybe CoreRule mkRelOpRule nm cmp | extra | = mkPrimOpRule nm 2 $ rules ++ extra | where | rules = [ binaryLit (\_ -> cmpOp cmp) | , equalArgs >> | -- x `cmp` x does not depend on x, so | -- compute it for the arbitrary value 'True' | -- and use that result | return (if cmp True True | then trueVal | else falseVal) ] | | It looks that equalArgs suddenly started to return True, whereas it | previously returned False. On the other hand in GHCi I get correct | result (False). Can anyone give me a hint why is this happening? | | Janek | | _______________________________________________ | ghc-devs mailing list | ghc-devs@haskell.org | http://www.haskell.org/mailman/listinfo/ghc-devs