[oops -- I sent this incomplete by mistake]

I've looked into this a bit.  It's all rather delicate. The bottom line
is that it's a fluke that it woks when it does! 

Here is what is happening.  The RULE ends up looking like this:
     forall $dEq :: base:GHC.Base.Eq base:GHC.Word.Word8
           x :: base:GHC.Word.Word8
     break (base:GHC.Base.== @ base:GHC.Word.Word8 $dEq x) 
        = breakByte x

Notice the LHS: an application of the selector to a (suitably-typed) Eq
dictionary.  GHC does very little simplification on LHSs, because if it
does too much, the LHS doesn't look like you thought it did.  Here it
might perhaps be better to simplify to GHC.Word.Word8.==, by selecting
from the dictionary, but GHC does not do that.

OK, now in the case that works, GHC generates exactly that pattern; we
get

        eq = (==) deq
        main = ... break (\x. eq x y) ...

GHC is anxious about substituting eq inside the lambda, but it does it
because (==) is just a record selector, and hence is very cheap.  

But when you put the literal inline, we get an (Eq a)
constraint and a (Num a) constraint (from the literal).  Ultimately, 'a'
turns out to be Int, by defaulting, but we don't know that yet.  So GHC
picks the Eq dictionary from the Num dictionary:
        eq = (==) ($p1 dnum)
        main = ... break (\x. eq x y) ...

Now the 'eq' doesn't look quite so cheap, and it isn't inlined, so the
rule does not fire.  In fact, though $p1 is just a selector too (the
superclass selector) and I've just modified GHC to make it believe that
nested selection is also cheap.  So that makes the rule fire both times.


The underlying lesson is this: the only robust way to make rules fire is
if the LHS is a normal form.  Otherwise GHC may miss the fleeting moment
at which (an instance of) the rule LHS appears in the program.   The way
you ensure this is with inline phases: don't inline LHS stuff until
later, so that the LHS stuff appears in the program more than
fleetingly.

But in this case you have (==) on the LHS, and you have no phase control
there. So it gets inlined right away, so the rule doesn't match any
more.  The only way the rule "works" is because GHC catches the pattern
right away, before (==) is inlined.  Not very robust.  

To make this robust,  you'd have to say something like
        instance Eq Word 8 where
          (==) = eqWord8

        eqWord8 = ..
        {-# NOINLINE [1] eqWord8 #-}

        
        {-# RULES
         "FPS specialise break (x==)" forall x.
            break (x`eqWord8`) = breakByte x
        #-}



Would you like to add some words to
http://haskell.org/haskellwiki/GHC/Using_Rules to explain this ?

Simon


| -----Original Message-----
| From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED]
On Behalf Of Donald Bruce
| Stewart
| Sent: 24 August 2006 07:46
| To: [EMAIL PROTECTED]
| Subject: (== <literal>) not matching in rules
| 
| 
| With the new liberalised rule syntax, I can write:
| 
|     {-# RULES
|         "FPS specialise break (x==)" forall x.
|             break (x==) = breakByte x
|         "FPS specialise break (==x)" forall x.
|             break (==x) = breakByte x
|       #-}
| 
| Which is very useful (Data.ByteString can detect these an substitute
in a
| memchr, must faster). The following works nicely:
| 
|     import qualified Data.ByteString as P
|     main = do
|         ps <- P.getContents
|         print $ P.break (==c) ps
|     c = 50
| 
| 3 RuleFired
|     1 FPS specialise break (==x)
|     1 int2Word#
|     1 narrow8Word#
| 
| However, if I inline the constant, the rule refuses to fire:
| 
|     import qualified Data.ByteString as P
|     main = do
|         ps <- P.getContents
|         print $ P.break (==50) ps
| 
|     2 RuleFired
|         1 int2Word#
|         1 narrow8Word#
| 
| Rewriting without sections and it still fails:
| 
|     import qualified Data.ByteString as P
|     main = do
|         ps <- P.getContents
|         print $ P.break ((==) 50) ps
| 
| The Core looks like:
|     print_a13O (Data.ByteString.break (==_a1tG lit_a1tF) ps_aBu))
| 
|     ==_a1tG :: GHC.Word.Word8 -> GHC.Word.Word8 -> GHC.Base.Bool
|     ==_a1tG = GHC.Base.== @ GHC.Word.Word8 (GHC.Num.$p1Num @
GHC.Word.Word8
| GHC.Word.$f37)
| 
| Could this funny ==_a1tG be getting in the way?
| 
| This is with today's HEAD including the ByteString patches I just
pushed:
|     Thu Aug 24 11:26:11 EST 2006  Don Stewart <[EMAIL PROTECTED]>
|   * Add spec rules for sections in Data.ByteString
| 
| -- Don
| _______________________________________________
| Cvs-ghc mailing list
| [EMAIL PROTECTED]
| http://www.haskell.org/mailman/listinfo/cvs-ghc
_______________________________________________
Cvs-ghc mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/cvs-ghc
_______________________________________________
Cvs-ghc mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to