Handling of NaN

Simon Marlow marlowsd at gmail.com
Fri May 10 10:07:14 CEST 2013


On 24/04/13 07:52, Jan Stolarek wrote:
> Is there a way of measuring how often such a rule is triggered? I think no programmer will write a
> program which explicitly compares two floating point literals, but I'd like to know how often
> such cases result from program transformation.

Cases like this tend to happen a lot as a result of inlining.  The 
programmer doesn't intentionally write 3.0 == 3.0, but the expression 
might appear during optimisation as a result of inlining some function 
definition that contained the (==).  Indeed, this is one of the main 
reasons we need constant folding at all.

Cheers,
	Simon


> Janek
>
> Dnia wtorek, 23 kwietnia 2013, Simon Peyton-Jones napisał:
>> Just so.  You could make a float rule that constant-folded
>> 	lit1 == lit2
>> to True if lit1 and lit2 were the same, and were not NaNs.
>>
>> As you point out, being syntactically equal expressions isn't enough.
>>
>> Simon
>>
>> | -----Original Message-----
>> | From: Jan Stolarek [mailto:jan.stolarek at p.lodz.pl]
>> | Sent: 23 April 2013 09:46
>> | To: Simon Peyton-Jones
>> | Cc: ghc-devs at haskell.org
>> | Subject: Re: Handling of NaN
>> |
>> | > The rule can test for NaNs, but behave as before for non-NaNs.  That
>> |
>> | might be best, no?
>> | I was thinking about that, but then I thought about such code:
>> |
>> | f :: Bool
>> | f = go 1 == go 2
>> |   where nan = 0.0 / 0.0 :: Double
>> |         go n = if not (isPrime (n * n - n + 41))
>> |                then nan
>> |                else go (n + 1)
>> |
>> | The compiler would not be able to tell whether 'go' reduces to NaN or
>> | not (perhaps not the best possible example because the alternative value
>> | is _|_). It would be possible to test for NaNs in some trivial cases
>> | where one of the operands really is a NaN, but in general I believe it
>> | is impossible to test whether the expression reduces to NaN or not. And
>> | the rules need to be correct
>> | *always* not *sometimes*. Am I missing something? The only thing that
>> | comes to my mind is writing a rule that works only on literals, because
>> | for literals we can be sure they are not NaNs (on the other hand I doubt
>> | this rule would trigger often).
>> |
>> | Janek
>> |
>> | > 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
>
>
>
> _______________________________________________
> 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