Handling of NaN
Simon Peyton-Jones
simonpj at microsoft.com
Tue Apr 23 10:21:32 CEST 2013
Well, you can write whatever rule you like! The rule can test for NaNs, but behave as before for non-NaNs. That might be best, no?
Simon
| -----Original Message-----
| From: Jan Stolarek [mailto:jan.stolarek at p.lodz.pl]
| Sent: 22 April 2013 15:51
| To: Simon Peyton-Jones
| Cc: ghc-devs at haskell.org
| Subject: Re: Handling of NaN
|
| > Same happens in HEAD, so nothing to do with your changes.
| I didn't notice that, I was comparing against 7.6.2 :/
|
| > Better define mkFloatingRelOpRule instead, which doesn't have the
| equal-args thing.
| That's what I did initially, but I wasn't sure if that's acceptable
| because some optimisations will be gone, e.g. ==# 3.0 3.0 will not
| rewrite to #1 (perhaps this isn't that bad, because comparing floating
| point numbers for equality isn't a good idea anyway).
|
| Janek
|
| >
| > 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
| > |
| > | 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 at haskell.org
| > | http://www.haskell.org/mailman/listinfo/ghc-devs
|
More information about the ghc-devs
mailing list