[Haskell-cafe] New OpenGL package: efficient way to convert datatypes?

Nick Bowler nbowler at elliptictech.com
Thu Mar 4 13:25:43 EST 2010


On 17:45 Thu 04 Mar     , Daniel Fischer wrote:
> Am Donnerstag 04 März 2010 16:45:03 schrieb Nick Bowler:
> > On 16:20 Thu 04 Mar     , Daniel Fischer wrote:
> > > Yes, without rules, realToFrac = fromRational . toRational.
> >
> > <snip>
> >
> > > I think one would have to add {-# RULES #-} pragmas to
> > > Graphics.Rendering.OpenGL.Raw.Core31.TypesInternal, along the lines of
> > >
> > > {-# RULES
> > > "realToFrac/CDouble->GLdouble"  realToFrac x = GLdouble x
> > > "realToFrac/GLdouble -> CDouble" realToFrac (GLdouble x) = x
> > >   #-}
> >
> > These rules are, alas, *not* equivalent to fromRational . toRational.
> 
> But these rules are probably what one really wants for a [C]Double <-> 
> GLdouble conversion.

I agree that the conversions described by the rules are precisely what
one really wants.  However, this doesn't make them valid rules for
realToFrac, because they do not do the same thing as realToFrac does.
They break referential transparency by allowing to write functions whose
behaviour depends on whether or not realToFrac was inlined by the ghc
(see below for an example).

> > Unfortunately, realToFrac is quite broken with respect to floating point
> > conversions, because fromRational . toRational is entirely the wrong
> > thing to do.
> 
> "entirely"? For
> 
> realToFrac :: (Real a, Fractional b) => a -> b
> 
> I think you can't do much else that gives something more or less 
> reasonable. For (almost?) any concrete conversion, you can do something 
> much better (regarding performance and often values), but I don't think 
> there's a generic solution.

Sorry, I guess I wasn't very clear.  I didn't mean to say that
"fromRational . toRational" is a bad implementation of realToFrac.  I
meant to say that "fromRational . toRational" is not appropriate for
converting values from one floating point type to another floating point
type.  Corollary: realToFrac is not appropriate for converting values
from one floating point type to another floating point type.

The existence of floating point values which are not representable in a
rational causes problems when you use toRational in a conversion.  See
the recent discussion on the haskell-prime mailing list

  http://thread.gmane.org/gmane.comp.lang.haskell.prime/3146

or the trac ticket on the issue

  http://hackage.haskell.org/trac/ghc/ticket/3676

for further details.

> > I've tried to start some discussion on the haskell-prime
> > mailing list about fixing this wart.  In the interim, the OpenGL package
> > could probably provide its own CDouble<=>GLDouble conversions, but sadly
> 
> s/could/should/, IMO.
> 
> > the only way to "correctly" perform Double<=>CDouble is unsafeCoerce.
> 
> Are you sure? In Foreign.C.Types, I find
> 
> {-# RULES
> "realToFrac/a->CFloat"    realToFrac = \x -> CFloat   (realToFrac x)
> "realToFrac/a->CDouble"   realToFrac = \x -> CDouble  (realToFrac x)
> 
> "realToFrac/CFloat->a"    realToFrac = \(CFloat   x) -> realToFrac x
> "realToFrac/CDouble->a"   realToFrac = \(CDouble  x) -> realToFrac x
>  #-}

Even though these are the conversions we actually want to do, these
rules are also invalid.  I'm not at all surprised to see this, since we
have the following:

> {-# RULES
> "realToFrac/Double->Double" realToFrac = id :: Double -> Double
>   #-}
> 
> (why isn't that in GHC.Real, anyway?), it should do the correct thing - not 
> that it's prettier than unsafeCoerce.

This rule does exist, in GHC.Float (at least with 6.12.1), and is
another bug.  It does the wrong thing because fromRational . toRational
:: Double -> Double is *not* the identity function on Doubles.  As
mentioned before, the result is that we can write programs which behave
differently when realToFrac gets inlined.

Try using GHC to compile the following program with and without -O:

  compiledWithOptimisation :: Bool
  compiledWithOptimisation = isNegativeZero . realToFrac $ -0.0

  main :: IO ()
  main = putStrLn $ if compiledWithOptimisation
      then "Optimised :)"
      else "Not optimised :("

-- 
Nick Bowler, Elliptic Technologies (http://www.elliptictech.com/)


More information about the Haskell-Cafe mailing list