... |
... |
@@ -50,6 +50,8 @@ import GHC.Types.Name.Env |
50
|
50
|
import GHC.Types.SrcLoc
|
51
|
51
|
import GHC.Types.Basic
|
52
|
52
|
import GHC.Types.Error
|
|
53
|
+import GHC.Types.Unique( hasKey )
|
|
54
|
+import GHC.Builtin.Names( errorMessageTypeErrorFamKey )
|
53
|
55
|
import qualified GHC.Types.Unique.Map as UM
|
54
|
56
|
|
55
|
57
|
import GHC.Unit.Module
|
... |
... |
@@ -439,10 +441,10 @@ reportBadTelescope _ _ skol_info skols |
439
|
441
|
-- See Note [Constraints to ignore].
|
440
|
442
|
ignoreConstraint :: Ct -> Bool
|
441
|
443
|
ignoreConstraint ct
|
442
|
|
- | AssocFamPatOrigin <- ctOrigin ct
|
443
|
|
- = True
|
444
|
|
- | otherwise
|
445
|
|
- = False
|
|
444
|
+ = case ctOrigin ct of
|
|
445
|
+ AssocFamPatOrigin -> True -- See (CIG1)
|
|
446
|
+ WantedSuperclassOrigin {} -> True -- See (CIG2)
|
|
447
|
+ _ -> False
|
446
|
448
|
|
447
|
449
|
-- | Makes an error item from a constraint, calculating whether or not
|
448
|
450
|
-- the item should be suppressed. See Note [Wanteds rewrite Wanteds]
|
... |
... |
@@ -612,14 +614,14 @@ reportWanteds ctxt tc_lvl wc@(WC { wc_simple = simples, wc_impl = implics |
612
|
614
|
, ("skolem eq2", skolem_eq, True, mkSkolReporter)
|
613
|
615
|
|
614
|
616
|
-- Next, family applications like (F t1 t2 ~ rigid_ty)
|
615
|
|
- -- These can be solved by doing a type-family reduction for F
|
|
617
|
+ -- These could be solved by doing a type-family reduction for F
|
616
|
618
|
-- which probably means fixing a unfication variable in t1/t2
|
617
|
619
|
-- See discussion in #26255, where F had an injectivity annotation,
|
618
|
620
|
-- and we had [W] F alpha ~ "foo"
|
619
|
621
|
-- The real error is that the "foo" should be "bar", because there is
|
620
|
622
|
-- type instance F Int = "bar"
|
621
|
|
- -- We could additionally filter on the injectivty annotation, but
|
622
|
|
- -- currenlty we don't.
|
|
623
|
+ -- We could additionally filter on the injectivty annotation,
|
|
624
|
+ -- but currently we don't.
|
623
|
625
|
, ("fam app", is_fam_app_eq, True, mkGroupReporter mkEqErr)
|
624
|
626
|
|
625
|
627
|
-- Put custom type errors after solid equality errors. In #26255 we
|
... |
... |
@@ -680,8 +682,11 @@ reportWanteds ctxt tc_lvl wc@(WC { wc_simple = simples, wc_impl = implics |
680
|
682
|
is_FRR item _ = isJust $ fixedRuntimeRepOrigin_maybe item
|
681
|
683
|
|
682
|
684
|
-- Things like (F t1 t2 ~N Maybe s)
|
683
|
|
- is_fam_app_eq _ (EqPred NomEq ty1 ty2) = isJust (isSatTyFamApp ty1) && isRigidTy ty2
|
684
|
|
- is_fam_app_eq _ _ = False
|
|
685
|
+ -- But only proper type families; not (TypeError t1 t2 ~N blah)
|
|
686
|
+ is_fam_app_eq _ (EqPred NomEq ty1 ty2)
|
|
687
|
+ | Just (tc,_) <- isSatTyFamApp ty1
|
|
688
|
+ = not (tc `hasKey` errorMessageTypeErrorFamKey) && isRigidTy ty2
|
|
689
|
+ is_fam_app_eq _ _ = False
|
685
|
690
|
|
686
|
691
|
-- Things like (a ~N b) or (a ~N F Bool)
|
687
|
692
|
skolem_eq _ (EqPred NomEq ty1 _) = isSkolemTy tc_lvl ty1
|
... |
... |
@@ -819,7 +824,7 @@ they will remain unfilled, and might have been used to rewrite another constrain |
819
|
824
|
|
820
|
825
|
Currently, the constraints to ignore are:
|
821
|
826
|
|
822
|
|
-1) Constraints generated in order to unify associated type instance parameters
|
|
827
|
+(CIG1) Constraints generated in order to unify associated type instance parameters
|
823
|
828
|
with class parameters. Here are two illustrative examples:
|
824
|
829
|
|
825
|
830
|
class C (a :: k) where
|
... |
... |
@@ -847,6 +852,10 @@ Currently, the constraints to ignore are: |
847
|
852
|
|
848
|
853
|
If there is any trouble, checkValidFamInst bleats, aborting compilation.
|
849
|
854
|
|
|
855
|
+(CIG2) Superclasses of Wanteds. These are generated on in case they trigger functional
|
|
856
|
+ dependencies. If such a constraint is unsolved, then its "parent" constraint must
|
|
857
|
+ also be unsolved, and is much more informative to the user (#26255).
|
|
858
|
+
|
850
|
859
|
Note [Implementation of Unsatisfiable constraints]
|
851
|
860
|
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|
852
|
861
|
The Unsatisfiable constraint was introduced in GHC proposal #433 (https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0433-unsatisfiable.rst).
|