... |
... |
@@ -443,7 +443,6 @@ ignoreConstraint :: Ct -> Bool |
443
|
443
|
ignoreConstraint ct
|
444
|
444
|
= case ctOrigin ct of
|
445
|
445
|
AssocFamPatOrigin -> True -- See (CIG1)
|
446
|
|
- WantedSuperclassOrigin {} -> True -- See (CIG2)
|
447
|
446
|
_ -> False
|
448
|
447
|
|
449
|
448
|
-- | Makes an error item from a constraint, calculating whether or not
|
... |
... |
@@ -540,7 +539,7 @@ reportWanteds ctxt tc_lvl wc@(WC { wc_simple = simples, wc_impl = implics |
540
|
539
|
; when (null simples) $ reportMultiplicityCoercionErrs ctxt_for_insols mult_co_errs
|
541
|
540
|
|
542
|
541
|
-- See Note [Suppressing confusing errors]
|
543
|
|
- ; let (suppressed_items, items0) = partition suppress tidy_items
|
|
542
|
+ ; let (suppressed_items, items0) = partition suppressItem tidy_items
|
544
|
543
|
; traceTc "reportWanteds suppressed:" (ppr suppressed_items)
|
545
|
544
|
; (ctxt1, items1) <- tryReporters ctxt_for_insols report1 items0
|
546
|
545
|
|
... |
... |
@@ -548,7 +547,7 @@ reportWanteds ctxt tc_lvl wc@(WC { wc_simple = simples, wc_impl = implics |
548
|
547
|
-- any of the first batch failed, or if the enclosing context
|
549
|
548
|
-- says to suppress
|
550
|
549
|
; let ctxt2 = ctxt1 { cec_suppress = cec_suppress ctxt || cec_suppress ctxt1 }
|
551
|
|
- ; (ctxt3, leftovers) <- tryReporters ctxt2 report2 items1
|
|
550
|
+ ; (_, leftovers) <- tryReporters ctxt2 report2 items1
|
552
|
551
|
; massertPpr (null leftovers)
|
553
|
552
|
(text "The following unsolved Wanted constraints \
|
554
|
553
|
\have not been reported to the user:"
|
... |
... |
@@ -559,12 +558,15 @@ reportWanteds ctxt tc_lvl wc@(WC { wc_simple = simples, wc_impl = implics |
559
|
558
|
-- wanted insoluble here; but do suppress inner insolubles
|
560
|
559
|
-- if there's a *given* insoluble here (= inaccessible code)
|
561
|
560
|
|
562
|
|
- -- Only now, if there are no errors, do we report suppressed ones
|
563
|
|
- -- See Note [Suppressing confusing errors]
|
564
|
|
- -- We don't need to update the context further because of the
|
565
|
|
- -- whenNoErrs guard
|
|
561
|
+ -- Only now, if there are no errors, do we report suppressed ones
|
|
562
|
+ -- See Note [Suppressing confusing errors]. We don't need to update
|
|
563
|
+ -- the context further because of the whenNoErrs guard
|
566
|
564
|
; whenNoErrs $
|
567
|
|
- do { (_, more_leftovers) <- tryReporters ctxt3 report3 suppressed_items
|
|
565
|
+ do { (_, more_leftovers) <- tryReporters ctxt_for_insols (report1++report2)
|
|
566
|
+ suppressed_items
|
|
567
|
+ -- ctxt_for_insols: the suppressed errors can be Int~Bool, which
|
|
568
|
+ -- will have made the incoming `ctxt` be True; don't make that suppress
|
|
569
|
+ -- the Int~Bool error!
|
568
|
570
|
; massertPpr (null more_leftovers) (ppr more_leftovers) } }
|
569
|
571
|
where
|
570
|
572
|
env = cec_tidy ctxt
|
... |
... |
@@ -587,14 +589,6 @@ reportWanteds ctxt tc_lvl wc@(WC { wc_simple = simples, wc_impl = implics |
587
|
589
|
DE_Multiplicity mult_co loc
|
588
|
590
|
-> (es1, es2, es3, (mult_co, loc):es4)
|
589
|
591
|
|
590
|
|
- -- See Note [Suppressing confusing errors]
|
591
|
|
- suppress :: ErrorItem -> Bool
|
592
|
|
- suppress item
|
593
|
|
- | Wanted <- ei_flavour item
|
594
|
|
- = is_ww_fundep_item item
|
595
|
|
- | otherwise
|
596
|
|
- = False
|
597
|
|
-
|
598
|
592
|
-- report1: ones that should *not* be suppressed by
|
599
|
593
|
-- an insoluble somewhere else in the tree
|
600
|
594
|
-- It's crucial that anything that is considered insoluble
|
... |
... |
@@ -656,11 +650,6 @@ reportWanteds ctxt tc_lvl wc@(WC { wc_simple = simples, wc_impl = implics |
656
|
650
|
, ("Dicts", is_dict, False, mkGroupReporter mkDictErr)
|
657
|
651
|
, ("Quantified", is_qc, False, mkGroupReporter mkQCErr) ]
|
658
|
652
|
|
659
|
|
- -- report3: suppressed errors should be reported as categorized by either report1
|
660
|
|
- -- or report2. Keep this in sync with the suppress function above
|
661
|
|
- report3 = [ ("wanted/wanted fundeps", is_ww_fundep, True, mkGroupReporter mkEqErr)
|
662
|
|
- ]
|
663
|
|
-
|
664
|
653
|
-- rigid_nom_eq, rigid_nom_tv_eq,
|
665
|
654
|
is_dict, is_equality, is_ip, is_FRR, is_irred :: ErrorItem -> Pred -> Bool
|
666
|
655
|
|
... |
... |
@@ -728,10 +717,6 @@ reportWanteds ctxt tc_lvl wc@(WC { wc_simple = simples, wc_impl = implics |
728
|
717
|
is_qc _ (ForAllPred {}) = True
|
729
|
718
|
is_qc _ _ = False
|
730
|
719
|
|
731
|
|
- -- See situation (1) of Note [Suppressing confusing errors]
|
732
|
|
- is_ww_fundep item _ = is_ww_fundep_item item
|
733
|
|
- is_ww_fundep_item = isWantedWantedFunDepOrigin . errorItemOrigin
|
734
|
|
-
|
735
|
720
|
given_eq_spec -- See Note [Given errors]
|
736
|
721
|
| has_gadt_match_here
|
737
|
722
|
= ("insoluble1a", is_given_eq, True, mkGivenErrorReporter)
|
... |
... |
@@ -757,6 +742,16 @@ reportWanteds ctxt tc_lvl wc@(WC { wc_simple = simples, wc_impl = implics |
757
|
742
|
= has_gadt_match implics
|
758
|
743
|
|
759
|
744
|
---------------
|
|
745
|
+suppressItem :: ErrorItem -> Bool
|
|
746
|
+ -- See Note [Suppressing confusing errors]
|
|
747
|
+suppressItem item
|
|
748
|
+ | Wanted <- ei_flavour item
|
|
749
|
+ , let orig = errorItemOrigin item
|
|
750
|
+ = isWantedSuperclassOrigin orig -- See (SCE1)
|
|
751
|
+ || isWantedWantedFunDepOrigin orig -- See (SCE2)
|
|
752
|
+ | otherwise
|
|
753
|
+ = False
|
|
754
|
+
|
760
|
755
|
isSkolemTy :: TcLevel -> Type -> Bool
|
761
|
756
|
-- The type is a skolem tyvar
|
762
|
757
|
isSkolemTy tc_lvl ty
|
... |
... |
@@ -781,7 +776,23 @@ If there are any other errors to report, at all, we want to suppress these. |
781
|
776
|
|
782
|
777
|
Which errors (only 1 case right now):
|
783
|
778
|
|
784
|
|
-1) Errors which arise from the interaction of two Wanted fun-dep constraints.
|
|
779
|
+(SCE1) Superclasses of Wanteds. These are generated on in case they trigger functional
|
|
780
|
+ dependencies. If such a constraint is unsolved, then its "parent" constraint must
|
|
781
|
+ also be unsolved, and is much more informative to the user. Example (#26255):
|
|
782
|
+ class (MinVersion <= F era) => Era era where { ... }
|
|
783
|
+ f :: forall era. EraFamily era -> IO ()
|
|
784
|
+ f = ..blah... -- [W] Era era
|
|
785
|
+ Here we have simply omitted "Era era =>" from f's type. But we'll end up with
|
|
786
|
+ /two/ Wanted constraints:
|
|
787
|
+ [W] d1 : Era era
|
|
788
|
+ [W] d2 : MinVersion <= F era -- Superclass of d1
|
|
789
|
+ We definitely want to report d1 and not d2! Happily it's easy to filter out those
|
|
790
|
+ superclass-Wanteds, becuase their Origin betrays them.
|
|
791
|
+
|
|
792
|
+ See test T18851 for an example of how it is (just, barely) possible for the /only/
|
|
793
|
+ errors to be superclass-of-Wanted constraints.
|
|
794
|
+
|
|
795
|
+(SCE2) Errors which arise from the interaction of two Wanted fun-dep constraints.
|
785
|
796
|
Example:
|
786
|
797
|
|
787
|
798
|
class C a b | a -> b where
|
... |
... |
@@ -852,18 +863,8 @@ Currently, the constraints to ignore are: |
852
|
863
|
|
853
|
864
|
If there is any trouble, checkValidFamInst bleats, aborting compilation.
|
854
|
865
|
|
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. Example (#26255):
|
858
|
|
- class (MinVersion <= F era) => Era era where { ... }
|
859
|
|
- f :: forall era. EraFamily era -> IO ()
|
860
|
|
- f = ..blah... -- [W] Era era
|
861
|
|
- Here we have simply omitted "Era era =>" from f's type. But we'll end up with
|
862
|
|
- /two/ Wanted constraints:
|
863
|
|
- [W] d1 : Era era
|
864
|
|
- [W] d2 : MinVersion <= F era -- Superclass of d1
|
865
|
|
- We definitely want to report d1 and not d2! Happily it's easy to filter out those
|
866
|
|
- superclass-Wanteds, becuase their Origin betrays them.
|
|
866
|
+(Note: Aug 25: this seems a rather tricky corner;
|
|
867
|
+ c.f. Note [Suppressing confusing errors])
|
867
|
868
|
|
868
|
869
|
Note [Implementation of Unsatisfiable constraints]
|
869
|
870
|
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
|