[Git][ghc/ghc][master] Add an error origin for impedance matching (#23427)

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Tue May 23 00:24:05 UTC 2023



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
9db0eadd by Krzysztof Gogolewski at 2023-05-22T20:23:47-04:00
Add an error origin for impedance matching (#23427)

- - - - -


5 changed files:

- compiler/GHC/Tc/Gen/Bind.hs
- compiler/GHC/Tc/Types/Origin.hs
- + testsuite/tests/typecheck/should_fail/T23427.hs
- + testsuite/tests/typecheck/should_fail/T23427.stderr
- testsuite/tests/typecheck/should_fail/all.T


Changes:

=====================================
compiler/GHC/Tc/Gen/Bind.hs
=====================================
@@ -899,7 +899,7 @@ mkExport prag_fn residual insoluble qtvs theta
                   then return idHsWrapper  -- Fast path; also avoids complaint when we infer
                                            -- an ambiguous type and have AllowAmbiguousType
                                            -- e..g infer  x :: forall a. F a -> Int
-                  else tcSubTypeSigma (Shouldn'tHappenOrigin "mkExport")
+                  else tcSubTypeSigma (ImpedanceMatching poly_id)
                                       sig_ctxt sel_poly_ty poly_ty
                        -- See Note [Impedance matching]
 
@@ -1254,11 +1254,9 @@ Then we want to check that
      forall qtvs. theta => f_mono_ty   is more polymorphic than   f's polytype
 and the proof is the impedance matcher.
 
-Notice that the impedance matcher may do defaulting.  See #7173.
-
-If we've gotten the constraints right during inference (and we assume we have),
-this sub-type check should never fail. It's not really a check -- it's more of
-a procedure to produce the right wrapper.
+The impedance matcher can do defaulting: in the above example, we default
+to Integer because of Num. See #7173. If we're dealing with a nondefaultable
+class, impedance matching can fail. See #23427.
 
 Note [SPECIALISE pragmas]
 ~~~~~~~~~~~~~~~~~~~~~~~~~


=====================================
compiler/GHC/Tc/Types/Origin.hs
=====================================
@@ -591,6 +591,7 @@ data CtOrigin
   | IfThenElseOrigin    -- An if-then-else expression
   | BracketOrigin       -- An overloaded quotation bracket
   | StaticOrigin        -- A static form
+  | ImpedanceMatching Id   -- See Note [Impedance matching] in GHC.Tc.Gen.Bind
   | Shouldn'tHappenOrigin String  -- The user should never see this one
 
   -- | Testing whether the constraint associated with an instance declaration
@@ -826,6 +827,10 @@ pprCtOrigin (InstProvidedOrigin mod cls_inst)
          , ppr cls_inst
          , text "is provided by" <+> quotes (ppr mod)]
 
+pprCtOrigin (ImpedanceMatching x)
+  = vcat [ text "arising when matching required constraints"
+         , text "in a recursive group involving" <+> quotes (ppr x)]
+
 pprCtOrigin (CycleBreakerOrigin orig)
   = pprCtOrigin orig
 
@@ -921,6 +926,8 @@ pprCtO (FRROrigin {})               = text "a representation-polymorphism check"
 pprCtO (WantedSuperclassOrigin {})  = text "a superclass constraint"
 pprCtO (InstanceSigOrigin {})       = text "a type signature in an instance"
 pprCtO (AmbiguityCheckOrigin {})    = text "a type ambiguity check"
+pprCtO (ImpedanceMatching {})       = text "combining required constraints"
+
 
 {- *********************************************************************
 *                                                                      *


=====================================
testsuite/tests/typecheck/should_fail/T23427.hs
=====================================
@@ -0,0 +1,10 @@
+module T23427 where
+
+class C a where
+    f :: a -> a
+
+indent :: C a => a -> a
+indent n = doText n
+    where
+      doText x = const (f x) doTail
+      doTail _ = const n doText


=====================================
testsuite/tests/typecheck/should_fail/T23427.stderr
=====================================
@@ -0,0 +1,16 @@
+
+T23427.hs:9:7: error: [GHC-39999]
+    • Could not deduce ‘C a0’
+        arising when matching required constraints
+        in a recursive group involving ‘doTail’
+      from the context: C a
+        bound by the type signature for:
+                   indent :: forall a. C a => a -> a
+        at T23427.hs:6:1-23
+      The type variable ‘a0’ is ambiguous
+    • In an equation for ‘indent’:
+          indent n
+            = doText n
+            where
+                doText x = const (f x) doTail
+                doTail _ = const n doText


=====================================
testsuite/tests/typecheck/should_fail/all.T
=====================================
@@ -683,3 +683,4 @@ test('TyfamsDisabled', normal, compile_fail, [''])
 test('CommonFieldResultTypeMismatch', normal, compile_fail, [''])
 test('CommonFieldTypeMismatch', normal, compile_fail, [''])
 test('T17284', normal, compile_fail, [''])
+test('T23427', normal, compile_fail, [''])



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9db0eadd05da2f807b9a5fdcdec50ba1feedde15
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/20230522/e0b7a977/attachment-0001.html>


More information about the ghc-commits mailing list