[Haskell-cafe] rewrite rules to specialize function according to type class?
Simon Peyton-Jones
simonpj at microsoft.com
Tue Feb 15 11:37:15 CET 2011
What happens is this. From the (Foo Bool) instance GHC generates
dFooBool :: Foo Bool
dFooBool = DFoo fooBool barBool foo_barBool
barBool :: Bool -> Bool
barBool = not
Now when GHC sees
bar dFooBool
it rewrites it to
barBool
Moreover there is currently no way to say "don't do that rewrite until phase 1". It's an "always-on" rewrite. For all other rewrite rules you can control which phase(s) the rule is active in.
What you want in this case is to avoid doing the bar/dFooBool rewrite until the "foo/bar" rule has had a chance to fire.
There's no fundamental difficulty with doing this, except a syntactic one: since the rule is implicit, how can we control it's phase? You could imagine saying
class Foo a where
bar :: a -> a
{-# NOINLINE [1] bar #-}
but currently any pragmas in a class decl are treated as attaching to the *default method*, not to the method selector:
class Foo a where
bar :: a -> a
bar x = x
{-# NOINLINE [1] bar #-}
So we need another notation for the latter.
As a workaround, you can say
class Foo a where
_bar :: a -> a
_foo :: a -> a
{-# NOINLINE [1] foo #-}
foo = _foo
{- NOINLINE [1] bar #-}
bar = _bar
Given the workaround, and the syntactic question, I wonder whether the feature is worth the cost.
Simon
| -----Original Message-----
| From: haskell-cafe-bounces at haskell.org [mailto:haskell-cafe-
| bounces at haskell.org] On Behalf Of Max Bolingbroke
| Sent: 15 February 2011 09:08
| To: Gábor Lehel
| Cc: Haskell Cafe
| Subject: Re: [Haskell-cafe] rewrite rules to specialize function according to
| type class?
|
| 2011/2/15 Gábor Lehel <illissius at gmail.com>:
| > This is a semi-related question I've been meaning to ask at some
| > point: I suppose this also means it's not possible to write a class,
| > write some rules for the class, and then have the rules be applied to
| > every instance? (I.e. you'd have to write them separately for each?)
|
| This does work, because it doesn't require the simplifier to lookup up
| class instances. However, it's a bit fragile. Here is an example:
|
| """
| class Foo a where
| foo :: a -> a
| bar :: a -> a
| foo_bar :: a -> a
|
| {-# RULES "foo/bar" forall x. foo (bar x) = foo_bar x #-}
|
|
| instance Foo Bool where
| foo = not
| bar = not
| foo_bar = not
|
| instance Foo Int where
| foo = (+1)
| bar x = x - 1
| foo_bar = (+2)
|
|
| {-# NOINLINE foo_barish #-}
| foo_barish :: Foo a => a -> a
| foo_barish x = foo (bar x)
|
|
| main = do
| print $ foo (bar False) -- False if rule not applied, True
| otherwise
| print $ foo (bar (2 :: Int)) -- 2 if rule not applied, 4, otherwise
| print $ foo_barish False -- False if rule not applied, True
| otherwise
| print $ foo_barish (2 :: Int) -- 2 if rule not applied, 4, otherwise
| """
|
| With GHC 7, the RULE successfully rewrites the foo.bar composition
| within foo_barish to use foo_bar. However, it fails to rewrite the two
| foo.bar compositions inlined directly in main. Thus the output is:
|
| """
| False
| 2
| True
| 4
| """
|
| The reason it cannot rewrite the calls in main is (I think) because
| the foo/bar class selectors are inlined before the rule matcher gets
| to spot them. By using NOINLINE on foo_barish, and ensuring that
| foo_barish is overloaded, we prevent the simplifier from doing this
| inlining and hence allow the rule to fire.
|
| What is more interesting is that I can't get the foo (bar x) rule to
| fire on the occurrences within main even if I add NOINLINE pragmas to
| the foo/bar names in both the class and instance declarations.
| Personally I would expect writing NOINLINE on the class declaration
| would prevent the class selector being inlined, allowing the rule to
| fire, but that is not happening for some reason.
|
| Perhaps this is worth a bug report on the GHC trac? It would at least
| give it a chance of being fixed.
|
| Max
|
| _______________________________________________
| Haskell-Cafe mailing list
| Haskell-Cafe at haskell.org
| http://www.haskell.org/mailman/listinfo/haskell-cafe
More information about the Haskell-Cafe
mailing list