[Git][ghc/ghc][wip/T23109] 2 commits: Revert ConLike change

Simon Peyton Jones (@simonpj) gitlab at gitlab.haskell.org
Tue Mar 11 10:24:56 UTC 2025



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


Commits:
a5f8696d by Simon Peyton Jones at 2025-03-11T10:24:15+00:00
Revert ConLike change

I'm not sure why I made this change

- - - - -
ef8709e3 by Simon Peyton Jones at 2025-03-11T10:24:29+00:00
No newtype axioms for unary type classes

- - - - -


5 changed files:

- compiler/GHC/Core/Utils.hs
- testsuite/tests/roles/should_compile/Roles14.stderr
- testsuite/tests/roles/should_compile/Roles3.stderr
- testsuite/tests/roles/should_compile/Roles4.stderr
- testsuite/tests/typecheck/should_compile/T12763.stderr


Changes:

=====================================
compiler/GHC/Core/Utils.hs
=====================================
@@ -2149,7 +2149,17 @@ exprIsHNF = exprIsHNFlike isDataConWorkId isEvaldUnfolding
 -- data constructors. Conlike arguments are considered interesting by the
 -- inliner.
 exprIsConLike :: CoreExpr -> Bool       -- True => lambda, conlike, PAP
--- exprIsConLike = exprIsHNFlike isConLikeId isConLikeUnfolding
+exprIsConLike = exprIsHNFlike isConLikeId isConLikeUnfolding
+
+{- FOR SOME REASON I TRIED THIS VARIANT, BUT I CAN'T REMEMBER WHY
+   It means, for example, that constructors with wappers don't count
+   as con-like:
+    T23307a.$WCons
+      = \ (@a_ahj) (conrep_ai4 [Occ=Once1!] :: Unconsed a_ahj) ->
+        case conrep_ai4 of
+        { Unconsed unbx_ai5 [Occ=Once1] unbx1_ai6 [Occ=Once1] ->
+            T23307a.Cons @a_ahj unbx_ai5 unbx1_ai6  }
+
 -- Trying: just a constructor application
 exprIsConLike (Var v)       = isConLikeId v
 exprIsConLike (Lit l)       = not (isLitRubbish l)
@@ -2165,6 +2175,7 @@ exprIsConLike (Let {})      = False
 exprIsConLike (Case {})     = False
 exprIsConLike (Type {})     = False
 exprIsConLike (Coercion {}) = False
+-}
 
 -- | Returns true for values or value-like expressions. These are lambdas,
 -- constructors / CONLIKE functions (as determined by the function argument)


=====================================
testsuite/tests/roles/should_compile/Roles14.stderr
=====================================
@@ -3,10 +3,8 @@ TYPE SIGNATURES
 TYPE CONSTRUCTORS
   class C2{1} :: * -> Constraint
     roles representational
-COERCION AXIOMS
-  axiom Roles12.N:C2 :: C2 a = a -> a
 Dependent modules: []
-Dependent packages: [base-4.20.0.0]
+Dependent packages: [base-4.21.0.0]
 
 ==================== Typechecker ====================
 Roles12.$tcC2


=====================================
testsuite/tests/roles/should_compile/Roles3.stderr
=====================================
@@ -15,13 +15,8 @@ TYPE CONSTRUCTORS
   type synonym Syn1{1} :: * -> *
     roles nominal
   type synonym Syn2{1} :: * -> *
-COERCION AXIOMS
-  axiom Roles3.N:C1 :: C1 a = a -> a
-  axiom Roles3.N:C2 :: C2 a b = (a ~ b) => a -> b
-  axiom Roles3.N:C3 :: C3 a b = a -> F3 b -> F3 b
-  axiom Roles3.N:C4 :: C4 a b = a -> F4 b -> F4 b
 Dependent modules: []
-Dependent packages: [base-4.20.0.0]
+Dependent packages: [base-4.21.0.0]
 
 ==================== Typechecker ====================
 Roles3.$tcC4


=====================================
testsuite/tests/roles/should_compile/Roles4.stderr
=====================================
@@ -5,11 +5,8 @@ TYPE CONSTRUCTORS
   class C1{1} :: * -> Constraint
   class C3{1} :: * -> Constraint
   type synonym Syn1{1} :: * -> *
-COERCION AXIOMS
-  axiom Roles4.N:C1 :: C1 a = a -> a
-  axiom Roles4.N:C3 :: C3 a = a -> Syn1 a
 Dependent modules: []
-Dependent packages: [base-4.20.0.0]
+Dependent packages: [base-4.21.0.0]
 
 ==================== Typechecker ====================
 Roles4.$tcC3


=====================================
testsuite/tests/typecheck/should_compile/T12763.stderr
=====================================
@@ -3,9 +3,7 @@ TYPE SIGNATURES
   m :: forall a. C a => a -> ()
 TYPE CONSTRUCTORS
   class C{1} :: * -> Constraint
-COERCION AXIOMS
-  axiom T12763.N:C :: C a = a -> ()
 CLASS INSTANCES
   instance C Int -- Defined at T12763.hs:9:10
 Dependent modules: []
-Dependent packages: [base-4.17.0.0]
+Dependent packages: [base-4.21.0.0]



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0b77b97b6df4553dbc98ae8bfceed0994aa97f56...ef8709e3fc15a55702e88b09971af1d20d0b8a95

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0b77b97b6df4553dbc98ae8bfceed0994aa97f56...ef8709e3fc15a55702e88b09971af1d20d0b8a95
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/20250311/746e68f0/attachment-0001.html>


More information about the ghc-commits mailing list