[Git][ghc/ghc][wip/t22549] Transfer DFunId-ness onto specialised bindings

Matthew Pickering (@mpickering) gitlab at gitlab.haskell.org
Fri Apr 14 12:04:10 UTC 2023



Matthew Pickering pushed to branch wip/t22549 at Glasgow Haskell Compiler / GHC


Commits:
1efcc6e4 by Matthew Pickering at 2023-04-14T13:03:59+01:00
Transfer DFunId-ness onto specialised bindings

Whether a binding is a DFunId or not has consequences for the `-fdicts-strict`
flag, essentially if we are doing demand analysis for a DFunId then `-fdicts-strict` does
not apply because the constraint solver can create recursive groups of dictionaries.

In #22549 this was fixed for the "normal" case, see Note [Do not strictify the argument dictionaries of a dfun]. However the loop still existed if the DFunId was being specialised.

The problem was that the specialiser would specialise a DFunId and turn it into a
VanillaId and so the demand analyser didn't know to apply special treatment to the binding
anymore and the whole recursive group was optimised to bottom.

The solution is to transfer over the DFunId-ness of the binding in the specialiser so
that the demand analysers knows not to apply the `-fstrict-dicts`

Fixes #22549

- - - - -


1 changed file:

- compiler/GHC/Core/Opt/Specialise.hs


Changes:

=====================================
compiler/GHC/Core/Opt/Specialise.hs
=====================================
@@ -48,11 +48,12 @@ import GHC.Types.Unique.DFM
 import GHC.Types.Name
 import GHC.Types.Tickish
 import GHC.Types.Id.Make  ( voidArgId, voidPrimId )
-import GHC.Types.Var      ( PiTyBinder(..), isLocalVar, isInvisibleFunArg )
+import GHC.Types.Var      ( PiTyBinder(..), isLocalVar, isInvisibleFunArg, setIdDetails )
 import GHC.Types.Var.Set
 import GHC.Types.Var.Env
 import GHC.Types.Id
 import GHC.Types.Error
+import GHC.Types.Id.Info
 
 import GHC.Utils.Error ( mkMCDiagnostic )
 import GHC.Utils.Monad    ( foldlM )
@@ -3444,11 +3445,22 @@ newSpecIdSM :: Id -> Type -> Maybe JoinArity -> SpecM Id
 newSpecIdSM old_id new_ty join_arity_maybe
   = do  { uniq <- getUniqueM
         ; let name    = idName old_id
+              details = idDetails old_id
               new_occ = mkSpecOcc (nameOccName name)
               new_id  = mkUserLocal new_occ uniq ManyTy new_ty (getSrcSpan name)
                           `asJoinId_maybe` join_arity_maybe
+                          -- See Note [Transfer DFunId-ness during specialisation]
+                          `transferDFun` details
         ; return new_id }
 
+
+infixl 1 `transferDFun`
+transferDFun :: Id -> IdDetails -> Id
+transferDFun id id_details =
+  case id_details of
+    DFunId {} -> id `setIdDetails` id_details
+    _ -> id
+
 {-
                 Old (but interesting) stuff about unboxed bindings
                 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -3517,4 +3529,28 @@ Answer: When they at the top-level (where it is necessary) or when
 inlining would duplicate work (or possibly code depending on
 options). However, the _Lifting will still be eliminated if the
 strictness analyser deems the lifted binding strict.
+
+Note [Transfer DFunId-ness during specialisation]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+When creating the binding for a specialisation we need to transfer over the `IdDetails`
+of the original binding in the cases that it applies. These are the cases where the
+specialisation continues to obey the property and these are relied on by further
+passes in the compiler.
+
+* For join points, the arity may decrease but the specialisation will still be a join point
+* For DFunIds, the specialisation is still a DFunId
+
+In particular, whether a binding is a DFunId or not has consequences for the `-fdicts-strict`
+flag, essentially if we are doing demand analysis for a DFunId then `-fdicts-strict` does
+not apply because the constraint solver can create recursive groups of dictionaries.
+
+The problem (in #22549) was that the specialiser would specialise a DFunId and turn it into a
+VanillaId and so the demand analyser didn't know to apply special treatment to the binding
+anymore and the whole recursive group was optimised to bottom.
+
+The solution is to transfer over the DFunId-ness of the binding in the specialiser so
+that the demand analysers knows not to apply the `-fstrict-dicts`
+
+This problem was discussed in #22549
 -}



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1efcc6e47c24796f5779573247dd23ff4bcb3178
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/20230414/04c8227c/attachment-0001.html>


More information about the ghc-commits mailing list