Wonderful!
Can rule writers assume that some simple inlining will be done on LHSs? For
instance, could I rewrite map/map as follows and expect to get as much
coverage?
{-# RULES
"map/map" forall f,g. map f . map g = map (f.g)
#-}
What kind of matching do you support? Higher-order (i.e. modulo alpha,
beta, & eta) is one very useful category, though only semi-decidable.
Second-order is decidable and very useful for program transformation (See
Huet & Lang, Proving and applying Program Transformations Expressed with
Second Order Patterns, Acta Informatica, Vol. 11, pp. 31-55, 1978.)
As we've discussed, I think Fran will be able to make excellent use of an
ability like this, though some of the cases are tricky. Some of these cases
are entirely analogous to simplifications of combinations of the list mapper
functions repeat, map, zipWith, zipWith3, etc:
map f (repeat x) = repeat (f x)
map f (map g xs) = map (f . g) xs
map f (zipWith g xs ys) = zipWith (\ x y -> f (g x y)) xs ys
zipWith f (map g xs) ys = zipWith (\ x y -> f (g x) y) xs ys
But there are so many of these rules! It might help to redefine map,
zipWith, zipWith3, etc, in terms of repeat and "zipApp":
-----Original Message-----
From: Simon Peyton-Jones
Sent: Thursday, April 22, 1999 2:46 AM
To: 'Olaf Chitil'; Josef Sveningsson
Cc: 'GHC users'; Simon Peyton-Jones; Conal Elliott
Subject: RE: foldr/build rule
> There is a very simple reason: ghc doesn't perform
> foldr/build optimisation.
> The source still contains many parts dealing with
> foldr/build, but the main part, `MagicUFs.lhs' is commented out.
This might be a good time to tell GHC users what I've been up to
recently. I'm dreadfully embarassed that GHC doesn't do fusion,
and, partly as a result, has rotten array performance. Motivated
by this, and some other ideas, I have finally bitten the bullet
and added a fairly general mechanism that allows the programmer
to specify rewrite rules. For example:
{-# RULES
"map/map" forall f,g,x. map f (map g x) = map (f.g) x
#-}
The compiler applies the rules left -> right, in the expectation
that each is an optimisation of some kind.
The compiler type-checks these rules, but makes no attempt
to ensure that they are semantically correct (that would
be very ambitious!). Rules survive across separate compilation
boundaries. Rules don't have to be in the same module as the
functions they have on the LHS; in that way they are very like
instance declarations.
Now, the fold/build rule is just one more rule. MagicUFs is not
only dead, but now deleted! Here's are some
rules from my current Prelude:
{-# RULES
"fold/build" forall k,z,g::forall b. (a->b->b) -> b -> b .
foldr k z (build g) = g k z
"foldr/id" foldr (:) [] = \x->x
"foldr/app" forall xs, ys. foldr (:) ys xs = append xs ys
"foldr/cons" forall k,z,x,xs. foldr k z (x:xs) = k x (foldr k z
xs)
"foldr/nil" forall k,z. foldr k z [] = z
#-}
Specialisations are also treated as transformation rules. When
you say
{-# SPECIALISE f :: Int -> Int #-}
f :: Num a => a -> a
f x = ...
the compiler now just figures out a new rule for f.
You used to be able to say
{-# SPECIALISE f :: Int -> Int = myF #-}
to say that 'myF' is to be treated as a specialised
version of f. (If you gave a bogus myF, you'd get a bogus program.)
This never worked well, and doesn't work in 4.xx. But you can now
get it by specifying a new rule:
{-# RULES f :: Int -> Int = myF #-}
This rewrites an instance of f at Int->Int into myF.
Making all this work takes some care. In particular, I have
to be jolly careful about when to inline things. It's just
about working, but I want to make sure list fusion works well
and arrays are a lot more efficient than they were before I
commit it into the repository.
Oh, and I've made 'SPECIALISE instance' work too. It generates
a rule for the dictionary function: dead simple!
I'd be very interested if anyone can think of useful applications
for this kind of thing. Of course you can shoot yourself in the
foot pretty badly -- I think of it as a library-writer's facility
not a programmer's facilty. (Like weak pointers and other such.)
Curiously, I don't know of a *compiler* for any language that
supports this ability.
Simon