New OpenGL package: efficient way to convert datatypes?

The newest package seems to require using GLdouble/GLfloat. What is the most efficient way to convert Double/Float to GLdouble/GLfloat? I'm currently using realToFrac. But essentially the operation should be a nop on my machine. I haven't looked at the core code yet (on Windows, last time I checked, the ghc-core util did not work, and without it, reading core is even harder) Thanks, Peter

If you are *really* sure that the runtime representation is the same you could use usafeCoerce. You could use a small test function for profiling, something like: convertGLfloat :: GLfloat -> Float convertGLFloat = realToFrac -- convertGLFloat = unsafeCoerce and toggle between the two (assuming you won't get a segmentation fault). Another option is to not convert at all but use the GL types everywhere. Either explicitly or by exploiting polymorphism.

I don't want to use the GL types directly since the OpenGL renderer is not
exposes in the rest of the API.
I was hoping that realToFrac would be a nop in case it would be identical to
an unsafeCoerce.
I guess one could make rules for that, but this tickets makes me wander if
that really works:
http://hackage.haskell.org/trac/ghc/ticket/1434
On Wed, Sep 30, 2009 at 4:58 PM, Roel van Dijk
If you are *really* sure that the runtime representation is the same you could use usafeCoerce. You could use a small test function for profiling, something like:
convertGLfloat :: GLfloat -> Float convertGLFloat = realToFrac -- convertGLFloat = unsafeCoerce
and toggle between the two (assuming you won't get a segmentation fault).
Another option is to not convert at all but use the GL types everywhere. Either explicitly or by exploiting polymorphism.

Peter Verswyvelen wrote:
I don't want to use the GL types directly since the OpenGL renderer is not exposes in the rest of the API. I was hoping that realToFrac would be a nop in case it would be identical to an unsafeCoerce.
This is one of the areas where the H98 spec is broken. Not only is the H98 realToFrac slow, it is also incorrect for Double and Float since those types contain transfinite values which cannot be represented in Rational, but which can be converted successfully when mapping from Double to Float and vice versa. Once you find a suitable function definition, I suggest using the RealToFrac class[1]. I don't know the GL types to know what the definition should be, but there is a class already out there to help deal with this kind of problem both efficiently and correctly.
I guess one could make rules for that, but this tickets makes me wander if that really works: http://hackage.haskell.org/trac/ghc/ticket/1434
The RealToFrac class solves Henning's performance complaint as well. Because of the correctness issues involved here, I strongly advocate *against* the use of rewrite rules for trying to optimize the H98 definition of realToFrac. The semantics of the program where transfinite values are involved should not be contingent on the whims of how the compiler feels today. Even though IEEE-754 is fuzzy to begin with, altering whether things fall into or out of transfinite states is grossly inconsistent. And in case you're worried about "extraneous dependencies", the logfloat package is portable and has negligable dependencies. Moreover it also provides a number of other facilities for dealing with IEEE-754 numbers correctly. Some examples include: * correcting the definitions of isInfinite and isNaN used in Hugs, * defining a class for partial orders (since neither Double nor Float is actually a total order due to NaN), * and a class for types with explicit representations of transfinite values, which in turn allows for a modified definition of log which has log 0 == negativeInfinity (other Floating methods could be extended similarly). [0]http://hackage.haskell.org/cgi-bin/hackage-scripts/package/logfloat [1]http://hackage.haskell.org/packages/archive/logfloat/0.12.0.1/doc/html/Data-... -- Live well, ~wren

wren ng thornton wrote:
I guess one could make rules for that, but this tickets makes me wander if that really works: http://hackage.haskell.org/trac/ghc/ticket/1434
The RealToFrac class solves Henning's performance complaint as well.
Er, I misread his performance problems. The logfloat package doesn't offer any particular support for rounding to integral types. -- Live well, ~wren

Ah, but it takes care of my performance problems, so many thanks from
the lurker :-)
-- Jeff
On Wed, Sep 30, 2009 at 11:37 PM, wren ng thornton
wren ng thornton wrote:
I guess one could make rules for that, but this tickets makes me wander if that really works: http://hackage.haskell.org/trac/ghc/ticket/1434
The RealToFrac class solves Henning's performance complaint as well.
Er, I misread his performance problems. The logfloat package doesn't offer any particular support for rounding to integral types.
-- Live well, ~wren _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I just converted an old HOpenGL application of mine to the new Haskell
OpenGL using GHC 6.12.1, using realToFrac to convert Double to
GLdouble.
The performance dropped from over 800 frames per second to 10 frames
per second... Using unsafeCoerce I got 800 FPS again.
So for all of you using new OpenGL package, be warned about this, it
can really kill performance (it's a known issue to those how already
knew it ;-)
I can't use the logfloat package's realToFrac function since it complains:
ElasticCollision.hs:317:28:
No instance for (Data.Number.Transfinite.Transfinite GL.GLdouble)
arising from a use of `realToFrac' at ElasticCollision.hs:317:28-39
Possible fix:
add an instance declaration for
(Data.Number.Transfinite.Transfinite GL.GLdouble)
In the first argument of `Vertex2', namely `(realToFrac x)'
In the expression: Vertex2 (realToFrac x) (realToFrac y)
In the definition of `glVertex2':
glVertex2 x y = Vertex2 (realToFrac x) (realToFrac y)
On Wed, Sep 30, 2009 at 4:06 PM, Peter Verswyvelen
I don't want to use the GL types directly since the OpenGL renderer is not exposes in the rest of the API. I was hoping that realToFrac would be a nop in case it would be identical to an unsafeCoerce. I guess one could make rules for that, but this tickets makes me wander if that really works: http://hackage.haskell.org/trac/ghc/ticket/1434
On Wed, Sep 30, 2009 at 4:58 PM, Roel van Dijk
wrote: If you are *really* sure that the runtime representation is the same you could use usafeCoerce. You could use a small test function for profiling, something like:
convertGLfloat :: GLfloat -> Float convertGLFloat = realToFrac -- convertGLFloat = unsafeCoerce
and toggle between the two (assuming you won't get a segmentation fault).
Another option is to not convert at all but use the GL types everywhere. Either explicitly or by exploiting polymorphism.

Am Donnerstag 04 März 2010 14:55:30 schrieb Peter Verswyvelen:
I just converted an old HOpenGL application of mine to the new Haskell OpenGL using GHC 6.12.1, using realToFrac to convert Double to GLdouble.
The performance dropped from over 800 frames per second to 10 frames per second... Using unsafeCoerce I got 800 FPS again.
Yes, without rules, realToFrac = fromRational . toRational.
So for all of you using new OpenGL package, be warned about this, it can really kill performance (it's a known issue to those how already knew it ;-)
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 #-} (There are corresponding rules for Double->CDouble and CDouble->Double in Foreign.C.Types, so I think no rules Double->GLdouble are needed).
On Wed, Sep 30, 2009 at 4:06 PM, Peter Verswyvelen
wrote: I don't want to use the GL types directly since the OpenGL renderer is not exposes in the rest of the API. I was hoping that realToFrac would be a nop in case it would be identical to an unsafeCoerce. I guess one could make rules for that, but this tickets makes me wander if that really works: http://hackage.haskell.org/trac/ghc/ticket/1434
Well, someone would have to add the rules.
On Wed, Sep 30, 2009 at 4:58 PM, Roel van Dijk
wrote:
If you are *really* sure that the runtime representation is the same
Yup, CDouble is a newtype wrapper for Double, GLdouble is the same newtype wrapper for CDouble.
you could use usafeCoerce. You could use a small test function for profiling, something like:
convertGLfloat :: GLfloat -> Float convertGLFloat = realToFrac -- convertGLFloat = unsafeCoerce
and toggle between the two (assuming you won't get a segmentation fault).
Another option is to not convert at all but use the GL types everywhere. Either explicitly or by exploiting polymorphism.

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. Unfortunately, realToFrac is quite broken with respect to floating point conversions, because fromRational . toRational is entirely the wrong thing to do. 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 the only way to "correctly" perform Double<=>CDouble is unsafeCoerce. -- Nick Bowler, Elliptic Technologies (http://www.elliptictech.com/)

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.
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.
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 #-} , so if you have a {-# 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.

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/)

Am Donnerstag 04 März 2010 19:25:43 schrieb Nick Bowler:
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).
You're absolutely right, of course. The clean way would be for the modules defining the newtype wrappers to define and export the desired conversion functions. Without that, you can only choose between incorrect-but-working- as-intended rewrite rules and unsafeCoerceButUsedSafelyHere. I don't like either very much.
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.
Agreed.

Nick Bowler
I meant to say that "fromRational . toRational" is not appropriate for converting values from one floating point type to another floating point type.
It gets even worse: My GPU doesn't know about doubles and its floats aren't IEEE, at all (not that Haskell Doubles are guaranteed to be IEEE iirc) I think the situation calls for a split interface: One to satisfy the numericists / scientific IEEE users, and one to satisfy performance. -- (c) this sig last receiving data processing entity. Inspect headers for copyright history. All rights reserved. Copying, hiring, renting, performance and/or quoting of this signature prohibited.

On 14:30 Fri 05 Mar , Achim Schneider wrote:
Nick Bowler
wrote: I meant to say that "fromRational . toRational" is not appropriate for converting values from one floating point type to another floating point type.
It gets even worse: My GPU doesn't know about doubles and its floats aren't IEEE, at all (not that Haskell Doubles are guaranteed to be IEEE iirc)
AFAIK, GLDouble is a newtype wrapper around CDouble, though, and doesn't correspond to a GPU-internal type. Even if it did, if we are converting to a type that doesn't support infinities, then is is reasonable for the conversion to not support them, either. I'd want to see a call to error in this case, but perhaps allowing "unsafe" optimisations (see below).
I think the situation calls for a split interface: One to satisfy the numericists / scientific IEEE users, and one to satisfy performance.
I think this is a job for the compiler rather than the interface. For example, GCC has -ffinite-math-only, -fno-signed-zeros, etc., which allow the compiler to make assumptions about the program that would not normally be valid. Nevertheless, for the issue at hand (Double<=>CDouble<=>GLDouble), there is a conversion interface that should satisfy everyone (both fast and correct): the one that compiles to nothing at all. -- Nick Bowler, Elliptic Technologies (http://www.elliptictech.com/)
participants (7)
-
Achim Schneider
-
Daniel Fischer
-
Jeff Heard
-
Nick Bowler
-
Peter Verswyvelen
-
Roel van Dijk
-
wren ng thornton