[Git][ghc/ghc][wip/T24359] Constant dictionaries can depend on /type/ variables

Simon Peyton Jones (@simonpj) gitlab at gitlab.haskell.org
Thu Nov 28 22:41:26 UTC 2024



Simon Peyton Jones pushed to branch wip/T24359 at Glasgow Haskell Compiler / GHC


Commits:
a8625e28 by Simon Peyton Jones at 2024-11-28T22:40:46+00:00
Constant dictionaries can depend on /type/ variables

- - - - -


1 changed file:

- compiler/GHC/HsToCore/Binds.hs


Changes:

=====================================
compiler/GHC/HsToCore/Binds.hs
=====================================
@@ -785,6 +785,52 @@ The restrictions are:
 
   4. Unlifted binds may not be recursive. Checked in second clause of ds_val_bind.
 
+Note [Desugaring SPECIALISE pragmas]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+Suppose we have f :: forall a b. (Ord a, Eq b) => a -> b -> b, and a pragma
+
+  {-# SPECIALISE forall x. f @[a] @[Int] x 3 #-}
+
+The SPECIALISE pragma has an expression that desugars to something like
+
+    forall @a (d:Ord a) (x:[a]).
+      let d2:Ord [a] = $dfOrdList d
+          d3:Eq [Int] = $dfEqList $dfEqInt
+      in f @[a] @[Int] d2 d3 x 3
+
+We want to get
+
+    RULE  forall a (d2:Ord a) (d3:Eq [Int]) (x:[a]).
+             f @[a] @[Int] d2 d3 x 3 = $sf d2 x
+
+    $sf :: forall a. Ord [a] => a -> Int
+    $sf = /\a. d2 x.
+             let d3 = $dfEqList $dfEqInt
+             in <f-rhs> @[a] @[Int] d2 d3 x 3
+
+Notice that
+* We want to quantify the RULE over the free vars of the /call/ inside all
+  those dictionary bindings.
+
+* The LHS of the RULE wants to mention that call, again shorn of the dictionary
+  bindings
+
+* Where the dictionary binding depends only on constants, we move it to the specialised
+  function body.  That is crucial -- it makes those specialised methods available in the
+  specialised body. This are the `const_dict_binds`.
+
+* Where the dicionary binding depends on locally-quanitified dictionries, we just discard
+  the binding, and pass the dictionary to the specialised function directly. No type-class
+  specialisation arises thereby.
+
+Some wrinkles:
+
+(DS1) The `const-dict_binds` /can/ depend on locally-quantifed type vaiables.
+  For example, if we have
+      instance Monad (ST s) where ...
+  the the dictionary for (Monad (ST s)) is effectlvely a constant dictionary.  This
+  is important to get specialisation for such types.  Emxample in test T8331.
+
 -}
 
 ------------------------
@@ -863,6 +909,7 @@ dsSpec poly_rhs (SpecPragE { spe_poly_id   = poly_id
 
 prepareSpecLHS :: Id -> [EvVar] -> CoreExpr
                -> Maybe (VarSet, [CoreBind], [CoreExpr])
+-- See Note [Desugaring SPECIALISE pragmas]
 prepareSpecLHS poly_id evs the_call
   = go (mkVarSet evs) [] the_call
   where
@@ -875,7 +922,7 @@ prepareSpecLHS poly_id evs the_call
     go qevs acc (Let bind e)
       | not (all isDictId bndrs)   -- A normal 'let' is too complicated
       = Nothing
-      | all (isEmptyVarSet . exprSomeFreeVars (`elemVarSet` qevs)) $
+      | all (isEmptyVarSet . exprSomeFreeVars (is_quant_id qevs)) $
         rhssOfBind bind
       = go qevs (bind:acc) e
       | otherwise
@@ -890,6 +937,9 @@ prepareSpecLHS poly_id evs the_call
       | otherwise
       = Nothing
 
+    is_quant_id qevs v = isId v && v `elemVarSet` qevs
+      -- See Note [Desugaring SPECIALISE pragmas] wrinkle (DS1)
+
 finishSpecPrag :: CoreExpr                            -- RHS to specialise
                -> [Var] -> Id -> [CoreExpr]           -- RULE LHS pattern
                -> [Var] -> (CoreExpr -> CoreExpr) -> InlinePragma   -- Specialised form



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a8625e2829d038038fc1dbb1d4a035a5d23ee925

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a8625e2829d038038fc1dbb1d4a035a5d23ee925
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20241128/1732e7d8/attachment-0001.html>


More information about the ghc-commits mailing list