How Cool is Rulz!

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 }