[Git][ghc/ghc][wip/T23109] Make class datacons be have-no-unfolding

Simon Peyton Jones (@simonpj) gitlab at gitlab.haskell.org
Fri May 3 19:04:10 UTC 2024



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


Commits:
1bb6212a by Simon Peyton Jones at 2024-05-03T20:02:59+01:00
Make class datacons be have-no-unfolding

Fixes the problem reported in #20689 @Mikolaj

- - - - -


2 changed files:

- compiler/GHC/Types/Id.hs
- compiler/GHC/Types/Id/Make.hs


Changes:

=====================================
compiler/GHC/Types/Id.hs
=====================================
@@ -146,22 +146,27 @@ import GHC.Types.Var( Id, CoVar, JoinId,
 import qualified GHC.Types.Var as Var
 
 import GHC.Core.Type
-import GHC.Types.RepType
+import GHC.Core.TyCon( isClassTyCon )
 import GHC.Core.DataCon
+import GHC.Core.Class
+import GHC.Core.Multiplicity
+
+import GHC.Types.RepType
 import GHC.Types.Demand
 import GHC.Types.Cpr
 import GHC.Types.Name
-import GHC.Unit.Module
-import GHC.Core.Class
-import {-# SOURCE #-} GHC.Builtin.PrimOps (PrimOp)
 import GHC.Types.ForeignCall
-import GHC.Data.Maybe
 import GHC.Types.SrcLoc
 import GHC.Types.Unique
-import GHC.Builtin.Uniques (mkBuiltinUnique)
 import GHC.Types.Unique.Supply
+
+import {-# SOURCE #-} GHC.Builtin.PrimOps (PrimOp)
+import GHC.Builtin.Uniques (mkBuiltinUnique)
+
 import GHC.Data.FastString
-import GHC.Core.Multiplicity
+import GHC.Data.Maybe
+
+import GHC.Unit.Module
 
 import GHC.Utils.Misc
 import GHC.Utils.Outputable
@@ -595,8 +600,13 @@ hasNoBinding id = case Var.idDetails id of
 --                        PrimOpId _ lev_poly -> lev_poly    -- TEMPORARILY commented out
 
                         FCallId _        -> True
-                        DataConWorkId dc -> isUnboxedTupleDataCon dc || isUnboxedSumDataCon dc
-                        _                -> isCompulsoryUnfolding (realIdUnfolding id)
+                        DataConWorkId dc -> isUnboxedTupleDataCon dc
+                                            || isUnboxedSumDataCon dc
+                                            || isClassTyCon (dataConTyCon dc)
+                                               -- We don't generate bindings for newtype
+                                               -- classes, so express that here
+                                               -- ToDo explain!
+                  _                -> isCompulsoryUnfolding (realIdUnfolding id)
   -- Note: this function must be very careful not to force
   -- any of the fields that aren't the 'uf_src' field of
   -- the 'Unfolding' of the 'Id'. This is because these fields are computed


=====================================
compiler/GHC/Types/Id/Make.hs
=====================================
@@ -505,11 +505,9 @@ mkDictSelId name clas
     info | new_tycon  -- Same as non-new case; ToDo: explain
          = base_info `setRuleInfo` mkRuleInfo [rule]
                      `setInlinePragInfo` neverInlinePragma
-                     `setUnfoldingInfo`  mkInlineUnfoldingWithArity defaultSimpleOpts
-                                           StableSystemSrc 1
-                                           (mkDictSelRhs clas val_index)
                    -- See Note [Single-method classes] in GHC.Tc.TyCl.Instance
                    -- for why alwaysInlinePragma
+                   -- TODO Fix this comment!
 
          | otherwise
          = base_info `setRuleInfo` mkRuleInfo [rule]



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1bb6212a5787cd5fec0c417ad5168c3ec9397f90
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/20240503/58def308/attachment-0001.html>


More information about the ghc-commits mailing list