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

Commits:

1 changed file:

Changes:

  • compiler/GHC/Tc/Errors.hs
    ... ... @@ -600,11 +600,32 @@ reportWanteds ctxt tc_lvl wc@(WC { wc_simple = simples, wc_impl = implics
    600 600
         -- (see GHC.Tc.Utils.insolublWantedCt) is caught here, otherwise
    
    601 601
         -- we might suppress its error message, and proceed on past
    
    602 602
         -- type checking to get a Lint error later
    
    603
    -    report1 = [ given_eq_spec
    
    603
    +    report1 = [ -- We put implicit lifting errors first, because are solid errors
    
    604
    +                -- See "Implicit lifting" in GHC.Tc.Gen.Splice
    
    605
    +                -- Note [Lifecycle of an untyped splice, and PendingRnSplice]
    
    606
    +                ("implicit lifting", is_implicit_lifting, True, mkImplicitLiftingReporter)
    
    607
    +
    
    608
    +                -- Next, solid equality errors
    
    609
    +              , given_eq_spec
    
    604 610
                   , ("insoluble2",      utterly_wrong,  True, mkGroupReporter mkEqErr)
    
    605 611
                   , ("skolem eq1",      very_wrong,     True, mkSkolReporter)
    
    606 612
                   , ("FixedRuntimeRep", is_FRR,         True, mkGroupReporter mkFRRErr)
    
    607 613
                   , ("skolem eq2",      skolem_eq,      True, mkSkolReporter)
    
    614
    +
    
    615
    +              -- Put custom type errors after solid equality errors.  In #26255 we
    
    616
    +              -- had a custom error (T <= F alpha) which was suppressing a far more
    
    617
    +              -- informative (K Int ~ [K alpha]). That mismatch between K and [] is
    
    618
    +              -- definitely wrong; and if it was fixed we'd know alpha:=Int, and hence
    
    619
    +              -- perhaps be able to solve T <= F alpha, by reducing F Int.
    
    620
    +              --
    
    621
    +              -- Custom errors should precede "non-tv eq", becuase if we have
    
    622
    +              --     () ~ TypeError blah
    
    623
    +              -- we want to report it as a custom error, /not/ as a mis-match
    
    624
    +              -- between TypeError and ()!
    
    625
    +              , ("custom_error", is_user_type_error, True,  mkUserTypeErrorReporter)
    
    626
    +                 -- (Handles TypeError and Unsatisfiable)
    
    627
    +
    
    628
    +              -- "non-tv-eq": equalities (ty1 ~ ty2) where ty1 is not a tyvar
    
    608 629
                   , ("non-tv eq",       non_tv_eq,      True, mkSkolReporter)
    
    609 630
     
    
    610 631
                       -- The only remaining equalities are alpha ~ ty,
    
    ... ... @@ -615,14 +636,6 @@ reportWanteds ctxt tc_lvl wc@(WC { wc_simple = simples, wc_impl = implics
    615 636
                   , ("Homo eqs",      is_homo_equality,  True,  mkGroupReporter mkEqErr)
    
    616 637
                   , ("Other eqs",     is_equality,       True,  mkGroupReporter mkEqErr)
    
    617 638
     
    
    618
    -              -- Put custom type errors after solid equality errors.  In #26255 we
    
    619
    -              -- had a custom error (T <= F alpha) which was suppressing a far more
    
    620
    -              -- informative (K Int ~ [K alpha]). That mismatch between K and [] is
    
    621
    -              -- definitely wrong; and if it was fixed we'd know alpha:=Int, and hence
    
    622
    -              -- perhaps be able to solve T <= F alpha, by reducing F Int.
    
    623
    -              , ("custom_error", is_user_type_error, True,  mkUserTypeErrorReporter)
    
    624
    -                 -- (Handles TypeError and Unsatisfiable)
    
    625
    -              , ("implicit lifting", is_implicit_lifting, True, mkImplicitLiftingReporter)
    
    626 639
                   ]
    
    627 640
     
    
    628 641
         -- report2: we suppress these if there are insolubles elsewhere in the tree