specialization using RULES

Scott Dillard sedillard at ucdavis.edu
Mon Jun 4 16:28:36 EDT 2007


Hello,

This is somewhat related to this thread:

http://www.haskell.org/pipermail/glasgow-haskell-users/2007-May/012646.html

In that email I asked about the performance of gaussian elimination on
small matrices represented by unboxed arrays, because I noticed that
unsafeRead was unexpectedly slower than readArray (the cause of this
is still unknown.) Mirko Rahn replied with an indexless algorithm
where unboxed arrays are replaced by lists-of-lists.

http://www.haskell.org/pipermail/glasgow-haskell-users/2007-May/012648.html

Besides being infinitely more elegant, I noticed this was considerably
faster than my array-based functions, perhaps because of
inlining/deforestation/list fusion or some other crazy GHC
optimization. So I re-wrote my little affine geometry library
representing vectors as lists and matrices as list-of-lists.

One thing I wanted this library to do was to enforce dimensionality of
the vectors at the type level, so you could not add a two-vector to a
three-vector, even though both functions are just "zipWith (+)".
After trying to tune my library I came across the SPECIALIZATION/RULES
pagmas in the GHC manual, and thought that this phantom dimensionality
type would be great for specializing the vector functions, and indeed
it speeds things up quite a bit. For instance, if I define

> zipWithV :: (Dim d) => (s->s->s) -> Vec d s -> Vec d s -> Vec d s
> zipWithV f (Vec u) (Vec v) = Vec( zipWith f u v )

then I can specialize

> zipWithV3 :: (s->s->s) -> Vec Three s -> Vec Three s -> Vec Three s
> zipWithV3 f (Vec [x,y,z]) (Vec [i,j,k]) = Vec [ f x i, f y j, f k z ]
> {-# RULES "zipWith3" zipWithV = zipWithV3 #-}

and it makes a nice improvement to the performance of this function.
But here comes my problem: Ideally, I should only have to specialize
zipWith, map and foldr like this, because everything you could want to
do with a vector can be implemented with these functions. (Well,
everything I want to do, anyway.) But unfortunately, if I define,
say...

> instance (Num s) => Num (Vec d s ) where ... (-) = zipWithV (-)
> sqrNorm v = sumV ( mapV sqr v ) where sqr x = x*x

And I use this as

> distance u v = sqrt ( sqrNorm (u-v) )
> doSomethingWith (distance (u :: Vec Three Double) v)

The rules do not fire. They only seem to fire if the specialized
function is called directly, such as

> doSomethingWith ( zipWith (-) (u :: Vec Three Double) v )

I surely do not want to have to specialize all of my vector functions.
Just the building blocks.  Can anyone shed some light on my situation?
Under what conditions do the rules fire? As I understand it, they fire
whenever the types are the same. As far as I can tell, this is the
case. How can I change things to make the rules fire more often?

Thanks,
Scott


More information about the Glasgow-haskell-users mailing list