Difference between revisions of "GHC/Using rules"

From HaskellWiki
< GHC
Jump to navigation Jump to search
(Add map example)
(what order do rules match (top-down or bottom-up)?)
Line 49: Line 49:
 
"mapFB" forall c f g. mapFB (mapFB c f) g = mapFB c (f.g)
 
"mapFB" forall c f g. mapFB (mapFB c f) g = mapFB c (f.g)
 
#-}
 
#-}
  +
  +
== Questions ==
  +
  +
=== Order of rule-matching ===
  +
  +
For example, let's say we have two rules
  +
"f->g" forall x y . f x (h y) = g x y
  +
"h->g" forall x . h x = g 0 x
  +
and a fragment of the AST corresponding to
  +
f a (h b)
  +
  +
Which rule will fire? "f->g" or "h->g"? (Each rule disables the other.)
  +
  +
Answer: rules are matched against the AST for expressions basically ''bottom-up'' rather than top-down. In this example, "h->g" is the rule that fires. But due to the nature of inlining and so on, there are absolutely no guarantees about this kind of behaviour. If you really need to control the order of matching, phase control is the only reliable mechanism.

Revision as of 12:15, 18 July 2006

Using Rules in GHC

GHC's rewrite rules (invoked by the RULES pragma) offer a powerful way to optimise your program. This page is a place for people who use rewrite rules to collect thoughts about how to use them.

If you aren't already familiar with RULES, read this stuff first:

Advice about using rewrite rules

  • Remember to use the flag -fglasgow-exts and the optimisation flag -O
  • Use the flag -ddump-simpl-stats to see how many rules actually fired.
  • For even more detail use -ddump-simpl-stats -ddump-simpl-iterations to see the core code at each iteration of the simplifer. Note that this produces lots of output so you'll want to direct the output to a file or pipe it to less. Looking at the output of this can help you figure out why rules are not firing when you expect them to do so.
  • You need to be careful that your identifiers aren't inlined before your RULES have a chance to fire. To control this we add an INLINE [1] pragma to identifiers we want to match in rules, to ensure they haven't disappeared by the time the rule matching comes around.

Example: map

(This example code is taken from GHC's base/GHC/Base.lhs module.)

map :: (a -> b) -> [a] -> [b]
map _ []     = []
map f (x:xs) = f x : map f xs
mapFB ::  (elt -> lst -> lst) -> (a -> elt) -> a -> lst -> lst
{-# INLINE [0] mapFB #-}
mapFB c f x ys = c (f x) ys

The rules for map work like this.

Up to (but not including) phase 1, we use the "map" rule to rewrite all saturated applications of map with its build/fold form, hoping for fusion to happen. In phase 1 and 0, we switch off that rule, inline build, and switch on the "mapList" rule, which rewrites the foldr/mapFB thing back into plain map.

It's important that these two rules aren't both active at once (along with build's unfolding) else we'd get an infinite loop in the rules. Hence the activation control below.

The "mapFB" rule optimises compositions of map.

This same pattern is followed by many other functions: e.g. append, filter, iterate, repeat, etc.

{-# RULES
"map"       [~1] forall f xs.   map f xs                = build (\c n -> foldr (mapFB c f) n xs)
"mapList"   [1]  forall f.      foldr (mapFB (:) f) []  = map f
"mapFB"     forall c f g.       mapFB (mapFB c f) g     = mapFB c (f.g)
#-}

Questions

Order of rule-matching

For example, let's say we have two rules

   "f->g" forall x y .    f x (h y) = g x y
   "h->g" forall x   .    h x = g 0 x

and a fragment of the AST corresponding to

   f a (h b)

Which rule will fire? "f->g" or "h->g"? (Each rule disables the other.)

Answer: rules are matched against the AST for expressions basically bottom-up rather than top-down. In this example, "h->g" is the rule that fires. But due to the nature of inlining and so on, there are absolutely no guarantees about this kind of behaviour. If you really need to control the order of matching, phase control is the only reliable mechanism.