How Cool is Rulz!

I’m trying to learn Rewrite Rules. It looks like GHC-9.8.1 might have some Rewrite Rule improvements.

Say for instance that I have a library, that exports a class called FusedOps, there could be a function called fma with the type of:

fma :: FusedOps a => a -> a -> a -> a

And perhaps there’s good reason to believe that fma is Fused Multiply Add: (a * b) + c, such that only one rounding operation occurs.

How would you write the rule?

{-# RULES
“FusedOps/fma” forall a b c. FusedOps (a, b, c) => (a * b) + c = fma a b c
#-}

As far as I know it is currently not possible to make a rewrite rule depend on whether the types are instances of a certain type class. You’d have to write separate rules for all your types:

{-# RULES
  "FusedOps/fma/Double" forall (a :: Double) (b :: Double) (c :: Double). (a * b) + c = fma a b c
  "FusedOps/fma/Int"    forall (a :: Int)    (b :: Int)    (c :: Int).    (a * b) + c = fma a b c
  #-}

But even those rules generate warnings like this:

T.hs:8:1: warning: [-Winline-rule-shadowing]
    Rule "FusedOps/fma/Double" may never fire
      because rule "Class op *" for ‘*’ might fire first
    Probable fix: add phase [n] or [~n] to the competing rule
  |
8 | "FusedOps/fma/Double" forall (a :: Double) (b :: Double) (c :: Double).  (a * b) + c = fma a b c
  | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^

I think this has to do with what is discussed in this section in the documentation: 6.19.1. Rewrite rules — Glasgow Haskell Compiler 9.6.3 User's Guide.

So you can write a rule like that for your own types or for newtypes around existing types, e.g.:

instance Num MyDouble where
  x + y = plusMyDouble x y
  x * y = timesMyDouble x y

plusMyDouble :: MyDouble -> MyDouble -> MyDouble
{-# NOINLINE [1] plusMyDouble #-}
plusMyDouble (MyDouble x) (MyDouble y) = MyDouble (x + y)

timesMyDouble :: MyDouble -> MyDouble -> MyDouble
{-# NOINLINE [1] timesMyDouble #-}
timesMyDouble (MyDouble x) (MyDouble y) = MyDouble (x * y)

instance FusedOps MyDouble

{-# RULES
"FusedOps/fma/MyDouble" forall a b c. plusMyDouble (timesMyDouble a b) c = fma a b c
   #-}

But now it does not make that much sense to use a separate class for FusedOps at all. You can just as well write it as a custom function:

fmaMyDouble :: MyDouble -> MyDouble -> MyDouble -> MyDouble
fmaMyDouble = ...

{-# RULES
"fma/MyDouble" forall a b c. plusMyDouble (timesMyDouble a b) c = fmaMyDouble a b c
   #-}

Or of course just write out the definition in the rewrite rule.

Oh, okay, so the Num class functions disappear before the rules have a chance to fire.
Thanks for describing the path forward, I will try and pursue that more.

I have two more questions:

  1. Where can I find the “Class op *” rule? I searched the GHC gitlab and the result didn’t popup in any code, but there were several issues associated with it.
  2. For the associative nature of the arithmetic would I have to make two rules, one for (a * b) + c and the other for c + (a * b)?

Thanks,

The class op rule is built into the compiler. Here’s the source code:

    -- This is the built-in rule that goes
    --      op (dfT d1 d2) --->  opT d1 d2
    rule = BuiltinRule { ru_name = fsLit "Class op " `appendFS`
                                     occNameFS (getOccName name)
                       , ru_fn    = name
                       , ru_nargs = n_ty_args + 1
                       , ru_try   = dictSelRule val_index n_ty_args }

So essentially it rewrites polymorphic calls to monomorphic calls if the concrete type (or more accurately the class dictionary) is known.

Yes, I believe GHC doesn’t know about associativity and commutativity at this level.

Thanks for the help and the learning experience.

From what I found is that GHC likes a simpler forall signature, rather than one with types annotations for instance: fma fused multiply add: (a * b) + c

"posit/fma" forall a b c. positADD (positMULT a b) c = fma a b c

This seams to work from GHC 8.10.7 until 9.4.7, but then the rewrite rule fails without warning with GHC 9.6.3!

I searched gitlab about rewrite rules and ghc-9.6.3, but couldn’t find anything. Are there any known issues?

Thanks,

I don’t know of any issues. Can you show your code?

Here is the branch in github:

To test the fused rewrite rules I use this stack command:
stack test posit:test-posit-fusedRewrite --flag posit:do-rewrite

When set to one of the stackage lts’s like lts-21.13, it will print the rules that fire like: Rule fired: posit/fsmSub (Posit) buried in with all of the other rules, but when set to nightly-2023-10-16 for ghc-9.6.3, I don’t see any of my rules fire.

I think I can tell what’s going on, but I don’t know why this happens. In the Core I found this dictionary for Num (Posit es):

Posit.$fNumPosit
  = \ (@(es :: ES)) ($dPositC :: PositC es) ->
      GHC.Num.C:Num
        @(Posit es)
        (Posit.$fNumPosit_$c+ @es $dPositC)
        (Posit.$fNumPosit_$c- @es $dPositC)
        (Posit.$fNumPosit_$c* @es $dPositC)
        (positNEG @es $dPositC)
        (positABS @es $dPositC)
        (positSIGNUM @es $dPositC)
        (Posit.$fNumPosit_$cfromInteger @es $dPositC)

I expected to see positADD there instead of Posit.$fNumPosit_$c+. For some reason GHC creates an intermediate function here that seems to do nothing interesting:

-- RHS size: {terms: 4, types: 4, coercions: 0, joins: 0/0}
Posit.$fNumPosit_$c+ [Occ=LoopBreaker]
  :: forall (es :: ES). PositC es => Posit es -> Posit es -> Posit es
[GblId,
 Arity=3,
 Str=<SP(L,L,SC(S,L),L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L)><1P(A,1L)><MP(A,L)>,
 Cpr=1,
 Unf=OtherCon []]
Posit.$fNumPosit_$c+
  = \ (@(es :: ES)) ($dPositC :: PositC es) -> positADD @es $dPositC
end Rec }

The rewrite rule won’t apply if this function is used instead of positADD directly.

@sgraf is probably better equipped to explain why this happens.

Here’s the Core of positADD:

-- RHS size: {terms: 11, types: 14, coercions: 0, joins: 0/0}
positADD [InlPrag=NOINLINE[final]]
  :: forall (es :: ES). PositC es => Posit es -> Posit es -> Posit es
[GblId,
 Arity=3,
 Str=<SP(L,L,SC(S,L),L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L,L)><1P(A,1L)><MP(A,L)>,
 Cpr=1,
 Unf=Unf{Src=StableSystem, TopLvl=True,
         Value=True, ConLike=True, WorkFree=True, Expandable=True,
         Guidance=ALWAYS_IF(arity=3,unsat_ok=True,boring_ok=False)
         Tmpl= \ (@(es :: ES))
                 ($dPositC [Occ=Once1] :: PositC es)
                 (x [Occ=Once1!] :: Posit es)
                 (y [Occ=Once1] :: Posit es) ->
                 case x of { Posit _ [Occ=Dead] ww1 [Occ=Once1] ->
                 Posit.$wpositADD @es $dPositC ww1 y
                 }}]
positADD
  = \ (@(es :: ES))
      ($dPositC :: PositC es)
      (x :: Posit es)
      (y :: Posit es) ->
      case x of { Posit ww ww1 -> Posit.$wpositADD @es $dPositC ww1 y }

Hmm…
This is unfortunate.

So is this unique to my specific use case? It seems like this would be something that would effect a lot of libraries attempting to use rewrite rules.