No subject
Wed Apr 10 17:18:51 CEST 2013
case (/# 0.0 0.0) of r -> ...(=3D=3D# r r)...
and the (=3D=3D# r r) rewrites to True. Presumably for Float and Double yo=
u 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 at haskell.org [mailto:ghc-devs-bounces at haskell.org]
| On Behalf Of Jan Stolarek
| Sent: 22 April 2013 13:48
| To: ghc-devs at haskell.org
| Subject: Handling of NaN
|=20
| I need some help with my work on ticket #6135. Consider this program:
|=20
| {-# LANGUAGE BangPatterns, MagicHash #-} module Main where
|=20
| import GHC.Exts
|=20
| main =3D print $ nan## =3D=3D## nan##
| where !(D# nan##) =3D 0.0 / 0.0
|=20
| 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:
|=20
| mkRelOpRule :: Name -> (forall a . Ord a =3D> a -> a -> Bool)
| -> [RuleM CoreExpr] -> Maybe CoreRule mkRelOpRule nm cmp
| extra
| =3D mkPrimOpRule nm 2 $ rules ++ extra
| where
| rules =3D [ 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) ]
|=20
| 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?
|=20
| Janek
|=20
| _______________________________________________
| ghc-devs mailing list
| ghc-devs at haskell.org
| http://www.haskell.org/mailman/listinfo/ghc-devs
More information about the ghc-devs
mailing list