[Haskell-beginners] The cost of generality, or how expensive is realToFrac?

Greg greglists at me.com
Tue Sep 14 20:51:01 EDT 2010


First, to anyone who recognizes me by name, thanks to the help I've been getting here I've managed to put together a fairly complex set of code files that all compile together nicely, run, and do exactly what I wanted them to do.  Success!

The trouble is that my implementation is dog slow

Fortunately, this isn't the first time I've been in over my head and I started by putting up some simpler scaffolding- which runs much more quickly.  Working backwards, it looks like the real bottle neck is in the data types I've created, the type variables I've introduced, and the conversion code I needed to insert to make it all happy.

I'm not sure it helps, but I've attached a trimmed down version of the relevant code.  What should be happening is my pair  is being converted to the canonical form for Coord2D which is Cartesian2D and then converted again to Vertex2.  There shouldn't be any change made to the values, they're only being handed from one container to another in this case (Polar coordinates would require computation, but I've stripped that out for the time being).  However, those handoffs require calls to realToFrac to make the type system happy, and that has to be what is eating up all my CPU.

I think there are probably 4 calls to realToFrac.  If I walk through the  code, the result, given the pair p, should be:
Vertex2 (realToFrac (realToFrac (fst p)))  (realToFrac (realToFrac (snd p)))

I'd like to maintain type independence if possible, but I expect most uses of this code to feed Doubles in for processing and probably feed GLclampf (Floats, I believe) to the OpenGL layer.  If there's a way to do so, I wouldn't mind optimizing for that particular set of types.  I've tried GLdouble, and it doesn't really improve things with the current code.

Is there a way to short circuit those realToFrac calls if we know the input and output are the same type?  Is there a way merge the nested calls?

Any other thoughts on what I can do here?  The slow down between the two implementations is at least 20x, which seems like a steep penalty to pay.

And while I'm at it, is turning on FlexibleInstances the only way to create an instance for (a,a)?

Thanks--
 Greg




--I want to scatter plot a list of pairs of Doubles
data ScatterPlot = ScatterPlot {scatterPoints :: [(Double,Double)] }   

--this way is plenty fast
    GL.renderPrimitive GL.Points $ mapM_ GL.vertex (map pair2vertex $ scatterPoints plot)

--using this function in the map
pair2vertex :: (a,a) -> GL.Vertex2 a
pair2vertex (x,y) = GL.Vertex2 x y 

--then I started to get fancy and build custom types for coordinates, hoping to start developing a library useful for 
--cartesian, polar, 3D, etc.  I needed to create this trivial function to resolve a type ambiguity

coordToVertex2 :: Coord2D a => a -> (GL.Vertex2  GL.GLclampf)
coordToVertex2 = coordToCoord2D

--which I call instead of pair2vertex
    GL.renderPrimitive GL.Points $ mapM_ GL.vertex (map coordToVertex2 $ scatterPoints plot)

--Coord2D is a typeclass I created to hold 2D data
data Cartesian2D a = Cartesian2D a a deriving (Show, Eq, Read)  

class Coord2D a where
  xComponent :: (RealFloat b) => a -> b
  yComponent :: (RealFloat b) => a -> b
  toCartesian2D :: (RealFloat b) => a -> Cartesian2D b
  toCartesian2D p = Cartesian2D (xComponent p) (yComponent p)
  fromCartesian2D :: (RealFloat b) => Cartesian2D b -> a

--and this function allows conversion between coordinate representations
coordToCoord2D :: (Coord2D a, Coord2D b) => a -> b
coordToCoord2D = fromCartesian2D . toCartesian2D


--I think the only other interesting bit of code is the instance definitions:

{- Pair instances -}
instance (RealFloat a, RealFloat b) => Coord2D (a,b) where
  xComponent = realToFrac . fst
  yComponent = realToFrac . snd
  fromCartesian2D p = ((xComponent p),(yComponent p))

{- Cartesian 2D instances -}
instance (RealFloat a) => Coord2D (Cartesian2D a) where
  xComponent (Cartesian2D x _) = realToFrac x
  yComponent (Cartesian2D _ y) = realToFrac y
  fromCartesian2D p = Cartesian2D (xComponent p) (yComponent p)

{- Vertex2 instance -}
instance (RealFloat a) => Coord2D (Vertex2 a) where
  xComponent (Vertex2 x _) = realToFrac x
  yComponent (Vertex2 _ y) = realToFrac y
  fromCartesian2D p = Vertex2 (xComponent p) (yComponent p)

-------------- next part --------------
Skipped content of type multipart/related


More information about the Beginners mailing list