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

Commits:

15 changed files:

Changes:

  • compiler/GHC/Tc/Errors/Ppr.hs
    ... ... @@ -4043,9 +4043,13 @@ pprTcSolverReportMsg _ (FixedRuntimeRepError frr_origs) =
    4043 4043
                      Nothing -> empty
    
    4044 4044
                      Just o -> other_context o
    
    4045 4045
                  , case mb_not_conc of
    
    4046
    -                Nothing -> empty
    
    4047
    -                Just (conc_tv, not_conc) ->
    
    4048
    -                  unsolved_concrete_eq_explanation conc_tv not_conc ]
    
    4046
    +                Just (conc_tv, not_conc)
    
    4047
    +                  | conc_tv `elemVarSet` tyCoVarsOfType ty
    
    4048
    +                  -- Only show this message if 'conc_tv' appears somewhere
    
    4049
    +                  -- in the type, otherwise it's not helpful.
    
    4050
    +                  -> unsolved_concrete_eq_explanation conc_tv not_conc
    
    4051
    +                _ -> empty
    
    4052
    +            ]
    
    4049 4053
     
    
    4050 4054
         -- Don't print out the type (only the kind), if the type includes
    
    4051 4055
         -- a confusing cast, unless the user passed -fprint-explicit-coercions.
    

  • compiler/GHC/Tc/Gen/App.hs
    ... ... @@ -2066,18 +2066,22 @@ qlUnify ty1 ty2
    2066 2066
           = go_flexi1 kappa ty2
    
    2067 2067
     
    
    2068 2068
         go_flexi1 kappa ty2  -- ty2 is zonked
    
    2069
    -      | -- See Note [QuickLook unification] (UQL1)
    
    2070
    -        simpleUnifyCheck UC_QuickLook kappa ty2
    
    2071
    -      = do { co <- unifyKind (Just (TypeThing ty2)) ty2_kind kappa_kind
    
    2072
    -                   -- unifyKind: see (UQL2) in Note [QuickLook unification]
    
    2073
    -                   --            and (MIV2) in Note [Monomorphise instantiation variables]
    
    2074
    -           ; let ty2' = mkCastTy ty2 co
    
    2075
    -           ; traceTc "qlUnify:update" $
    
    2076
    -             ppr kappa <+> text ":=" <+> ppr ty2
    
    2077
    -           ; liftZonkM $ writeMetaTyVar kappa ty2' }
    
    2078
    -
    
    2079
    -      | otherwise
    
    2080
    -      = return ()   -- Occurs-check or forall-bound variable
    
    2069
    +      = do { cur_lvl <- getTcLevel
    
    2070
    +              -- See Note [Unification preconditions], (UNTOUCHABLE) wrinkles
    
    2071
    +              -- Here we are in the TcM monad, which does not track enclosing
    
    2072
    +              -- Given equalities; so for quick-look unification we conservatively
    
    2073
    +              -- treat /any/ level outside this one as untouchable. Hence cur_lvl.
    
    2074
    +           ; case simpleUnifyCheck UC_QuickLook cur_lvl kappa ty2 of
    
    2075
    +              SUC_CanUnify ->
    
    2076
    +                do { co <- unifyKind (Just (TypeThing ty2)) ty2_kind kappa_kind
    
    2077
    +                           -- unifyKind: see (UQL2) in Note [QuickLook unification]
    
    2078
    +                           --            and (MIV2) in Note [Monomorphise instantiation variables]
    
    2079
    +                   ; let ty2' = mkCastTy ty2 co
    
    2080
    +                   ; traceTc "qlUnify:update" $
    
    2081
    +                     ppr kappa <+> text ":=" <+> ppr ty2
    
    2082
    +                   ; liftZonkM $ writeMetaTyVar kappa ty2' }
    
    2083
    +              _ -> return () -- e.g. occurs-check or forall-bound variable
    
    2084
    +           }
    
    2081 2085
           where
    
    2082 2086
             kappa_kind = tyVarKind kappa
    
    2083 2087
             ty2_kind   = typeKind ty2
    

  • compiler/GHC/Tc/Solver/Equality.hs
    1 1
     {-# LANGUAGE CPP #-}
    
    2 2
     {-# LANGUAGE DuplicateRecordFields #-}
    
    3
    +{-# LANGUAGE LambdaCase #-}
    
    3 4
     {-# LANGUAGE MultiWayIf #-}
    
    4 5
     
    
    5 6
     module GHC.Tc.Solver.Equality(
    
    ... ... @@ -1888,81 +1889,102 @@ canEqCanLHSFinish_try_unification ev eq_rel swapped lhs rhs
    1888 1889
       | CtWanted wev <- ev         -- See Note [Do not unify Givens]
    
    1889 1890
       , NomEq <- eq_rel            -- See Note [Do not unify representational equalities]
    
    1890 1891
       , wantedCtHasNoRewriters wev -- See Note [Unify only if the rewriter set is empty]
    
    1891
    -  , TyVarLHS tv <- lhs
    
    1892
    -  = do { given_eq_lvl <- getInnermostGivenEqLevel
    
    1893
    -       ; if not (touchabilityAndShapeTest given_eq_lvl tv rhs)
    
    1894
    -         then if | Just can_rhs <- canTyFamEqLHS_maybe rhs
    
    1895
    -                 -> swapAndFinish ev eq_rel swapped (mkTyVarTy tv) can_rhs
    
    1896
    -                    -- See Note [Orienting TyVarLHS/TyFamLHS]
    
    1897
    -
    
    1898
    -                 | otherwise
    
    1899
    -                 -> canEqCanLHSFinish_no_unification ev eq_rel swapped lhs rhs
    
    1900
    -         else
    
    1901
    -
    
    1902
    -    -- We have a touchable unification variable on the left
    
    1903
    -    do { check_result <- checkTouchableTyVarEq ev tv rhs
    
    1904
    -       ; case check_result of {
    
    1905
    -            PuFail reason
    
    1892
    +  , TyVarLHS lhs_tv <- lhs
    
    1893
    +  = do  { given_eq_lvl <- getInnermostGivenEqLevel
    
    1894
    +        ; case simpleUnifyCheck UC_Solver given_eq_lvl lhs_tv rhs of
    
    1895
    +            SUC_CanUnify ->
    
    1896
    +              unify lhs_tv (mkReflRedn Nominal rhs)
    
    1897
    +            SUC_CannotUnify
    
    1906 1898
                   | Just can_rhs <- canTyFamEqLHS_maybe rhs
    
    1907
    -              -> swapAndFinish ev eq_rel swapped (mkTyVarTy tv) can_rhs
    
    1908
    -                -- Swap back: see Note [Orienting TyVarLHS/TyFamLHS]
    
    1909
    -
    
    1910
    -              | reason `cterHasOnlyProblems` do_not_prevent_rewriting
    
    1911
    -              -> canEqCanLHSFinish_no_unification ev eq_rel swapped lhs rhs
    
    1912
    -
    
    1899
    +              -> swap_and_finish lhs_tv can_rhs -- See Note [Orienting TyVarLHS/TyFamLHS]
    
    1913 1900
                   | otherwise
    
    1914
    -              -> tryIrredInstead reason ev eq_rel swapped lhs rhs ;
    
    1915
    -
    
    1916
    -            PuOK _ rhs_redn ->
    
    1917
    -
    
    1918
    -    -- Success: we can solve by unification
    
    1919
    -    do { -- In the common case where rhs_redn is Refl, we don't need to rewrite
    
    1920
    -         -- the evidence, even if swapped=IsSwapped.   Suppose the original was
    
    1921
    -         --     [W] co : Int ~ alpha
    
    1922
    -         -- We unify alpha := Int, and set co := <Int>.  No need to
    
    1923
    -         -- swap to   co = sym co'
    
    1924
    -         --           co' = <Int>
    
    1925
    -         new_ev <- if isReflCo (reductionCoercion rhs_redn)
    
    1926
    -                   then return ev
    
    1927
    -                   else rewriteEqEvidence emptyRewriterSet ev swapped
    
    1928
    -                            (mkReflRedn Nominal (mkTyVarTy tv)) rhs_redn
    
    1929
    -
    
    1930
    -       ; let tv_ty     = mkTyVarTy tv
    
    1931
    -             final_rhs = reductionReducedType rhs_redn
    
    1932
    -
    
    1933
    -       ; traceTcS "Sneaky unification:" $
    
    1934
    -         vcat [text "Unifies:" <+> ppr tv <+> text ":=" <+> ppr final_rhs,
    
    1935
    -               text "Coercion:" <+> pprEq tv_ty final_rhs,
    
    1936
    -               text "Left Kind is:" <+> ppr (typeKind tv_ty),
    
    1937
    -               text "Right Kind is:" <+> ppr (typeKind final_rhs) ]
    
    1938
    -
    
    1939
    -       -- Update the unification variable itself
    
    1940
    -       ; unifyTyVar tv final_rhs
    
    1941
    -
    
    1942
    -       -- Provide Refl evidence for the constraint
    
    1943
    -       -- Ignore 'swapped' because it's Refl!
    
    1944
    -       ; setEvBindIfWanted new_ev EvCanonical $
    
    1945
    -         evCoercion (mkNomReflCo final_rhs)
    
    1946
    -
    
    1947
    -       -- Kick out any constraints that can now be rewritten
    
    1948
    -       ; kickOutAfterUnification [tv]
    
    1949
    -
    
    1950
    -       ; return (Stop new_ev (text "Solved by unification")) }}}}
    
    1951
    -
    
    1901
    +              -> finish_no_unify
    
    1902
    +            SUC_NotSure ->
    
    1903
    +              -- We have a touchable unification variable on the left,
    
    1904
    +              -- and the top-shape check succeeded. These are both guaranteed
    
    1905
    +              -- by the fact that simpleUnifyCheck did not return SUC_CannotUnify.
    
    1906
    +              do  { let flags = unifyingLHSMetaTyVar_TEFTask ev lhs_tv
    
    1907
    +                  ; check_result <- wrapTcS (checkTyEqRhs flags rhs)
    
    1908
    +                  ; case check_result of
    
    1909
    +                      PuOK cts rhs_redn ->
    
    1910
    +                        do { emitWork cts
    
    1911
    +                           ; unify lhs_tv rhs_redn }
    
    1912
    +                      PuFail reason
    
    1913
    +                        | Just can_rhs <- canTyFamEqLHS_maybe rhs
    
    1914
    +                        -> swap_and_finish lhs_tv can_rhs -- See Note [Orienting TyVarLHS/TyFamLHS]
    
    1915
    +                        | reason `cterHasOnlyProblems` do_not_prevent_rewriting
    
    1916
    +                        ->
    
    1917
    +                          -- ContinueWith, to allow using this constraint for
    
    1918
    +                          -- rewriting (e.g. alpha[2] ~ beta[3]).
    
    1919
    +                          do { let role = eqRelRole eq_rel
    
    1920
    +                             ; new_ev <- rewriteEqEvidence emptyRewriterSet ev swapped
    
    1921
    +                                 (mkReflRedn role (canEqLHSType lhs))
    
    1922
    +                                 (mkReflRedn role rhs)
    
    1923
    +                             ; continueWith $ Right $
    
    1924
    +                                 EqCt { eq_ev  = new_ev, eq_eq_rel = eq_rel
    
    1925
    +                                      , eq_lhs = lhs , eq_rhs = rhs }
    
    1926
    +                             }
    
    1927
    +                        | otherwise
    
    1928
    +                        -> try_irred reason
    
    1929
    +                  }
    
    1930
    +         }
    
    1952 1931
       -- Otherwise unification is off the table
    
    1953 1932
       | otherwise
    
    1954
    -  = canEqCanLHSFinish_no_unification ev eq_rel swapped lhs rhs
    
    1933
    +  = finish_no_unify
    
    1955 1934
     
    
    1956 1935
       where
    
    1957
    -    -- Some problems prevent /unification/ but not /rewriting/
    
    1958
    -    -- Skolem-escape: if we have [W] alpha[2] ~ Maybe b[3]
    
    1959
    -    --    we can't unify (skolem-escape); but it /is/ canonical,
    
    1960
    -    --    and hence we /can/ use it for rewriting
    
    1961
    -    -- Concrete-ness:  alpha[conc] ~ b[sk]
    
    1962
    -    --    We can use it to rewrite; we still have to solve the original
    
    1963
    -    do_not_prevent_rewriting :: CheckTyEqResult
    
    1964
    -    do_not_prevent_rewriting = cteProblem cteSkolemEscape S.<>
    
    1965
    -                               cteProblem cteConcrete
    
    1936
    +    -- We can't unify, but this equality can go in the inert set
    
    1937
    +    -- and be used to rewrite other constraints.
    
    1938
    +    finish_no_unify =
    
    1939
    +      canEqCanLHSFinish_no_unification ev eq_rel swapped lhs rhs
    
    1940
    +
    
    1941
    +    -- We can't unify, and this equality should not be used to rewrite
    
    1942
    +    -- other constraints (e.g. because it has an occurs check).
    
    1943
    +    -- So add it to the inert Irreds.
    
    1944
    +    try_irred reason =
    
    1945
    +      tryIrredInstead reason ev eq_rel swapped lhs rhs
    
    1946
    +
    
    1947
    +    -- We can't unify as-is, and want to flip the equality around.
    
    1948
    +    -- Example: alpha ~ F tys, flip it around to become the canonical
    
    1949
    +    -- equality f tys ~ alpha.
    
    1950
    +    swap_and_finish tv can_rhs =
    
    1951
    +      swapAndFinish ev eq_rel swapped (mkTyVarTy tv) can_rhs
    
    1952
    +
    
    1953
    +    -- We can unify; go ahead and do so.
    
    1954
    +    unify tv rhs_redn =
    
    1955
    +
    
    1956
    +      do { -- In the common case where rhs_redn is Refl, we don't need to rewrite
    
    1957
    +           -- the evidence, even if swapped=IsSwapped.   Suppose the original was
    
    1958
    +           --     [W] co : Int ~ alpha
    
    1959
    +           -- We unify alpha := Int, and set co := <Int>.  No need to
    
    1960
    +           -- swap to   co = sym co'
    
    1961
    +           --           co' = <Int>
    
    1962
    +           new_ev <- if isReflCo (reductionCoercion rhs_redn)
    
    1963
    +                     then return ev
    
    1964
    +                     else rewriteEqEvidence emptyRewriterSet ev swapped
    
    1965
    +                              (mkReflRedn Nominal (mkTyVarTy tv)) rhs_redn
    
    1966
    +
    
    1967
    +         ; let tv_ty     = mkTyVarTy tv
    
    1968
    +               final_rhs = reductionReducedType rhs_redn
    
    1969
    +
    
    1970
    +         ; traceTcS "Sneaky unification:" $
    
    1971
    +           vcat [text "Unifies:" <+> ppr tv <+> text ":=" <+> ppr final_rhs,
    
    1972
    +                 text "Coercion:" <+> pprEq tv_ty final_rhs,
    
    1973
    +                 text "Left Kind is:" <+> ppr (typeKind tv_ty),
    
    1974
    +                 text "Right Kind is:" <+> ppr (typeKind final_rhs) ]
    
    1975
    +
    
    1976
    +         -- Update the unification variable itself
    
    1977
    +         ; unifyTyVar tv final_rhs
    
    1978
    +
    
    1979
    +         -- Provide Refl evidence for the constraint
    
    1980
    +         -- Ignore 'swapped' because it's Refl!
    
    1981
    +         ; setEvBindIfWanted new_ev EvCanonical $
    
    1982
    +           evCoercion (mkNomReflCo final_rhs)
    
    1983
    +
    
    1984
    +         -- Kick out any constraints that can now be rewritten
    
    1985
    +         ; kickOutAfterUnification [tv]
    
    1986
    +
    
    1987
    +         ; return (Stop new_ev (text "Solved by unification")) }
    
    1966 1988
     
    
    1967 1989
     ---------------------------
    
    1968 1990
     -- Unification is off the table
    
    ... ... @@ -1989,6 +2011,17 @@ canEqCanLHSFinish_no_unification ev eq_rel swapped lhs rhs
    1989 2011
     --              -> swapAndFinish ev eq_rel swapped lhs_ty can_rhs
    
    1990 2012
     --              | otherwise
    
    1991 2013
     
    
    2014
    +              | reason `cterHasOnlyProblems` do_not_prevent_rewriting
    
    2015
    +              -> do { let role = eqRelRole eq_rel
    
    2016
    +                    ; new_ev <- rewriteEqEvidence emptyRewriterSet ev swapped
    
    2017
    +                        (mkReflRedn role (canEqLHSType lhs))
    
    2018
    +                        (mkReflRedn role rhs)
    
    2019
    +                    ; continueWith $ Right $
    
    2020
    +                        EqCt { eq_ev  = new_ev, eq_eq_rel = eq_rel
    
    2021
    +                             , eq_lhs = lhs , eq_rhs = rhs }
    
    2022
    +                    }
    
    2023
    +
    
    2024
    +              | otherwise
    
    1992 2025
                   -> tryIrredInstead reason ev eq_rel swapped lhs rhs
    
    1993 2026
     
    
    1994 2027
                 PuOK _ rhs_redn
    
    ... ... @@ -2005,6 +2038,18 @@ canEqCanLHSFinish_no_unification ev eq_rel swapped lhs rhs
    2005 2038
                                , eq_lhs = lhs
    
    2006 2039
                                , eq_rhs = reductionReducedType rhs_redn } } }
    
    2007 2040
     
    
    2041
    +-- | Some problems prevent /unification/ but not /rewriting/:
    
    2042
    +--
    
    2043
    +-- Skolem-escape: if we have [W] alpha[2] ~ Maybe b[3]
    
    2044
    +--    we can't unify (skolem-escape); but it /is/ canonical,
    
    2045
    +--    and hence we /can/ use it for rewriting
    
    2046
    +--
    
    2047
    +-- Concrete-ness:  alpha[conc] ~ b[sk]
    
    2048
    +--    We can use it to rewrite; we still have to solve the original
    
    2049
    +do_not_prevent_rewriting :: CheckTyEqResult
    
    2050
    +do_not_prevent_rewriting = cteProblem cteSkolemEscape S.<>
    
    2051
    +                           cteProblem cteConcrete
    
    2052
    +
    
    2008 2053
     ----------------------
    
    2009 2054
     swapAndFinish :: CtEvidence -> EqRel -> SwapFlag
    
    2010 2055
                   -> TcType -> CanEqLHS      -- ty ~ F tys
    
    ... ... @@ -2297,8 +2342,9 @@ and we turn this into
    2297 2342
       [W] Arg alpha ~ cbv1
    
    2298 2343
       [W] Res alpha ~ cbv2
    
    2299 2344
     
    
    2300
    -where cbv1 and cbv2 are fresh TauTvs.  This is actually done by `break_wanted`
    
    2301
    -in `GHC.Tc.Solver.Monad.checkTouchableTyVarEq`.
    
    2345
    +where cbv1 and cbv2 are fresh TauTvs.  This is actually done within checkTyEqRhs,
    
    2346
    +called within canEqCanLHSFinish_try_unification, which will use the BreakWanted
    
    2347
    +FamAppBreaker.
    
    2302 2348
     
    
    2303 2349
     Why TauTvs? See [Why TauTvs] below.
    
    2304 2350
     
    
    ... ... @@ -2307,7 +2353,7 @@ directly instead of calling wrapUnifierTcS. (Otherwise, we'd end up
    2307 2353
     unifying cbv1 and cbv2 immediately, achieving nothing.)  Next, we
    
    2308 2354
     unify alpha := cbv1 -> cbv2, having eliminated the occurs check. This
    
    2309 2355
     unification happens immediately following a successful call to
    
    2310
    -checkTouchableTyVarEq, in canEqCanLHSFinish_try_unification.
    
    2356
    +checkTyEqRhs, in canEqCanLHSFinish_try_unification.
    
    2311 2357
     
    
    2312 2358
     Now, we're here (including further context from our original example,
    
    2313 2359
     from the top of the Note):
    

  • compiler/GHC/Tc/Solver/Monad.hs
    ... ... @@ -129,7 +129,7 @@ module GHC.Tc.Solver.Monad (
    129 129
         pprEq,
    
    130 130
     
    
    131 131
         -- Enforcing invariants for type equalities
    
    132
    -    checkTypeEq, checkTouchableTyVarEq
    
    132
    +    checkTypeEq
    
    133 133
     ) where
    
    134 134
     
    
    135 135
     import GHC.Prelude
    
    ... ... @@ -228,8 +228,6 @@ import GHC.Data.Graph.Directed
    228 228
     import qualified Data.Set as Set
    
    229 229
     import GHC.Unit.Module.Graph
    
    230 230
     
    
    231
    -import GHC.Data.Maybe
    
    232
    -
    
    233 231
     {- *********************************************************************
    
    234 232
     *                                                                      *
    
    235 233
                    SolverStage and StopOrContinue
    
    ... ... @@ -2416,81 +2414,31 @@ wrapUnifierX ev role do_unifications
    2416 2414
     ************************************************************************
    
    2417 2415
     -}
    
    2418 2416
     
    
    2419
    -checkTouchableTyVarEq
    
    2420
    -   :: CtEvidence
    
    2421
    -   -> TcTyVar    -- A touchable meta-tyvar
    
    2422
    -   -> TcType     -- The RHS
    
    2423
    -   -> TcS (PuResult () Reduction)
    
    2424
    --- Used for Nominal, Wanted equalities, with a touchable meta-tyvar on LHS
    
    2425
    --- If checkTouchableTyVarEq tv ty = PuOK cts redn
    
    2426
    ---   then we can unify
    
    2427
    ---       tv := ty |> redn
    
    2428
    ---   with extra wanteds 'cts'
    
    2429
    --- If it returns (PuFail reason) we can't unify, and the reason explains why.
    
    2430
    -checkTouchableTyVarEq ev lhs_tv rhs
    
    2431
    -  | simpleUnifyCheck UC_Solver lhs_tv rhs   -- An (optional) short-cut
    
    2432
    -  = do { traceTcS "checkTouchableTyVarEq: simple-check wins" (ppr lhs_tv $$ ppr rhs)
    
    2433
    -       ; return (pure (mkReflRedn Nominal rhs)) }
    
    2434
    -
    
    2435
    -  | otherwise
    
    2436
    -  = do { traceTcS "checkTouchableTyVarEq {" (ppr lhs_tv $$ ppr rhs)
    
    2437
    -       ; check_result <- wrapTcS (check_rhs rhs)
    
    2438
    -       ; traceTcS "checkTouchableTyVarEq }" (ppr lhs_tv $$ ppr check_result)
    
    2439
    -       ; case check_result of
    
    2440
    -            PuFail reason -> return (PuFail reason)
    
    2441
    -            PuOK cts redn -> do { emitWork cts
    
    2442
    -                                ; return (pure redn) } }
    
    2443
    -
    
    2444
    -  where
    
    2445
    -    lhs_tv_info = metaTyVarInfo lhs_tv -- lhs_tv should be a meta-tyvar
    
    2446
    -
    
    2447
    -    is_concrete_lhs_tv = isJust $ concreteInfo_maybe lhs_tv_info
    
    2448
    -
    
    2449
    -    check_rhs rhs
    
    2450
    -       -- Crucial special case for  alpha ~ F tys
    
    2451
    -       -- We don't want to flatten that (F tys)!
    
    2452
    -       | Just (TyFamLHS tc tys) <- canTyFamEqLHS_maybe rhs
    
    2453
    -       = if is_concrete_lhs_tv
    
    2454
    -         then return $ PuFail (cteProblem cteConcrete)
    
    2455
    -         else recurseIntoFamTyConApp flags tc tys
    
    2456
    -       | otherwise
    
    2457
    -       = checkTyEqRhs flags rhs
    
    2458
    -
    
    2459
    -    flags = unifyingLHSMetaTyVar_TEFTask ev lhs_tv
    
    2460
    -
    
    2461
    -------------------------
    
    2462 2417
     checkTypeEq :: CtEvidence -> EqRel -> CanEqLHS -> TcType
    
    2463 2418
                 -> TcS (PuResult () Reduction)
    
    2464 2419
     -- Used for general CanEqLHSs, ones that do
    
    2465 2420
     -- not have a touchable type variable on the LHS (i.e. not unifying)
    
    2466
    -checkTypeEq ev eq_rel lhs rhs
    
    2467
    -  | isGiven ev
    
    2468
    -  = do { traceTcS "checkTypeEq {" (vcat [ text "lhs:" <+> ppr lhs
    
    2469
    -                                        , text "rhs:" <+> ppr rhs ])
    
    2470
    -       ; check_result <- wrapTcS (check_given_rhs rhs)
    
    2471
    -       ; traceTcS "checkTypeEq }" (ppr check_result)
    
    2472
    -       ; case check_result of
    
    2473
    -            PuFail reason -> return (PuFail reason)
    
    2474
    -            PuOK prs redn -> do { new_givens <- mapBagM mk_new_given prs
    
    2475
    -                                ; emitWork new_givens
    
    2476
    -                                ; updInertSet (addCycleBreakerBindings prs)
    
    2477
    -                                ; return (pure redn) } }
    
    2478
    -
    
    2479
    -  | otherwise  -- Wanted
    
    2480
    -  = do { check_result <- wrapTcS (checkTyEqRhs wanted_flags rhs)
    
    2481
    -       ; case check_result of
    
    2482
    -            PuFail reason -> return (PuFail reason)
    
    2483
    -            PuOK cts redn -> do { emitWork cts
    
    2484
    -                                ; return (pure redn) } }
    
    2421
    +checkTypeEq ev eq_rel lhs rhs =
    
    2422
    +  case ev of
    
    2423
    +    CtGiven {} ->
    
    2424
    +      do { traceTcS "checkTypeEq {" (vcat [ text "lhs:" <+> ppr lhs
    
    2425
    +                                          , text "rhs:" <+> ppr rhs ])
    
    2426
    +         ; check_result <- wrapTcS (checkTyEqRhs given_flags rhs)
    
    2427
    +         ; traceTcS "checkTypeEq }" (ppr check_result)
    
    2428
    +         ; case check_result of
    
    2429
    +              PuFail reason -> return (PuFail reason)
    
    2430
    +              PuOK prs redn -> do { new_givens <- mapBagM mk_new_given prs
    
    2431
    +                                  ; emitWork new_givens
    
    2432
    +                                  ; updInertSet (addCycleBreakerBindings prs)
    
    2433
    +                                  ; return (pure redn) } }
    
    2434
    +    CtWanted {} ->
    
    2435
    +      do { check_result <- wrapTcS (checkTyEqRhs wanted_flags rhs)
    
    2436
    +         ; case check_result of
    
    2437
    +              PuFail reason -> return (PuFail reason)
    
    2438
    +              PuOK cts redn -> do { emitWork cts
    
    2439
    +                                  ; return (pure redn) } }
    
    2485 2440
       where
    
    2486
    -    check_given_rhs :: TcType -> TcM (PuResult (TcTyVar,TcType) Reduction)
    
    2487
    -    check_given_rhs rhs
    
    2488
    -       -- See Note [Special case for top-level of Given equality]
    
    2489
    -       | Just (TyFamLHS tc tys) <- canTyFamEqLHS_maybe rhs
    
    2490
    -       = recurseIntoFamTyConApp given_flags tc tys
    
    2491
    -       | otherwise
    
    2492
    -       = checkTyEqRhs given_flags rhs
    
    2493
    -
    
    2441
    +    wanted_flags :: TyEqFlags TcM Ct
    
    2494 2442
         wanted_flags = notUnifying_TEFTask occ_prob lhs
    
    2495 2443
                        -- checkTypeEq deals only with the non-unifying case
    
    2496 2444
     
    
    ... ... @@ -2532,31 +2480,6 @@ restoreTyVarCycles is
    2532 2480
     (a ~R# b a) is soluble if b later turns out to be Identity
    
    2533 2481
     So we treat this as a "soluble occurs check".
    
    2534 2482
     
    
    2535
    -Note [Special case for top-level of Given equality]
    
    2536
    -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    2537
    -We take care when examining
    
    2538
    -    [G] F ty ~ G (...(F ty)...)
    
    2539
    -where both sides are TyFamLHSs.  We don't want to flatten that RHS to
    
    2540
    -    [G] F ty ~ cbv
    
    2541
    -    [G] G (...(F ty)...) ~ cbv
    
    2542
    -Instead we'd like to say "occurs-check" and swap LHS and RHS, which yields a
    
    2543
    -canonical constraint
    
    2544
    -    [G] G (...(F ty)...) ~ F ty
    
    2545
    -That tends to rewrite a big type to smaller one. This happens in T15703,
    
    2546
    -where we had:
    
    2547
    -    [G] Pure g ~ From1 (To1 (Pure g))
    
    2548
    -Making a loop breaker and rewriting left to right just makes much bigger
    
    2549
    -types than swapping it over.
    
    2550
    -
    
    2551
    -(We might hope to have swapped it over before getting to checkTypeEq,
    
    2552
    -but better safe than sorry.)
    
    2553
    -
    
    2554
    -NB: We never see a TyVarLHS here, such as
    
    2555
    -    [G] a ~ F tys here
    
    2556
    -because we'd have swapped it to
    
    2557
    -   [G] F tys ~ a
    
    2558
    -in canEqCanLHS2, before getting to checkTypeEq.
    
    2559
    -
    
    2560 2483
     Note [Don't cycle-break Wanteds when not unifying]
    
    2561 2484
     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    2562 2485
     Consdier
    

  • compiler/GHC/Tc/Types/Constraint.hs
    ... ... @@ -279,10 +279,10 @@ We thus perform an occurs-check. There is, of course, some subtlety:
    279 279
     
    
    280 280
     * For type variables, the occurs-check looks deeply including kinds of
    
    281 281
       type variables. This is because a CEqCan over a meta-variable is
    
    282
    -  also used to inform unification, in
    
    283
    -  GHC.Tc.Solver.Monad.checkTouchableTyVarEq. If the LHS appears
    
    284
    -  anywhere in the RHS, at all, unification will create an infinite
    
    285
    -  structure which is bad.
    
    282
    +  also used to inform unification, via `checkTyEqRhs`, called in
    
    283
    +  `canEqCanLHSFinish_try_unification`.
    
    284
    +  If the LHS appears anywhere in the RHS, at all, unification will create
    
    285
    +  an infinite structure, which is bad.
    
    286 286
     
    
    287 287
     * For type family applications, the occurs-check is shallow; it looks
    
    288 288
       only in places where we might rewrite. (Specifically, it does not
    

  • compiler/GHC/Tc/Utils/Unify.hs
    ... ... @@ -29,7 +29,7 @@ module GHC.Tc.Utils.Unify (
    29 29
       -- Various unifications
    
    30 30
       unifyType, unifyKind, unifyInvisibleType, unifyExpectedType,
    
    31 31
       unifyExprType, unifyTypeAndEmit, promoteTcType,
    
    32
    -  swapOverTyVars, touchabilityAndShapeTest, checkTopShape, lhsPriority,
    
    32
    +  swapOverTyVars, touchabilityTest, checkTopShape, lhsPriority,
    
    33 33
       UnifyEnv(..), updUEnvLoc, setUEnvRole,
    
    34 34
       uType,
    
    35 35
       mightEqualLater,
    
    ... ... @@ -55,7 +55,7 @@ module GHC.Tc.Utils.Unify (
    55 55
       TyEqFamApp(..), FamAppBreaker(..),
    
    56 56
       checkPromoteFreeVars,
    
    57 57
     
    
    58
    -  simpleUnifyCheck, UnifyCheckCaller(..),
    
    58
    +  simpleUnifyCheck, UnifyCheckCaller(..), SimpleUnifyResult(..),
    
    59 59
     
    
    60 60
       fillInferResult,
    
    61 61
       ) where
    
    ... ... @@ -2482,10 +2482,9 @@ uUnfilledVar2 :: UnifyEnv -- Precondition: u_role==Nominal
    2482 2482
     uUnfilledVar2 env@(UE { u_defer = def_eq_ref }) swapped tv1 ty2
    
    2483 2483
       = do { cur_lvl <- getTcLevel
    
    2484 2484
                -- See Note [Unification preconditions], (UNTOUCHABLE) wrinkles
    
    2485
    -           -- Here we don't know about given equalities here; so we treat
    
    2485
    +           -- Here we don't know about given equalities; so we treat
    
    2486 2486
                -- /any/ level outside this one as untouchable.  Hence cur_lvl.
    
    2487
    -       ; if not (touchabilityAndShapeTest cur_lvl tv1 ty2
    
    2488
    -                 && simpleUnifyCheck UC_OnTheFly tv1 ty2)
    
    2487
    +       ; if simpleUnifyCheck UC_OnTheFly cur_lvl tv1 ty2 /= SUC_CanUnify
    
    2489 2488
              then not_ok_so_defer cur_lvl
    
    2490 2489
              else
    
    2491 2490
         do { def_eqs <- readTcRef def_eq_ref  -- Capture current state of def_eqs
    
    ... ... @@ -2530,8 +2529,8 @@ uUnfilledVar2 env@(UE { u_defer = def_eq_ref }) swapped tv1 ty2
    2530 2529
           do { traceTc "uUnfilledVar2 not ok" $
    
    2531 2530
                  vcat [ text "tv1:" <+> ppr tv1
    
    2532 2531
                       , text "ty2:" <+> ppr ty2
    
    2533
    -                  , text "simple-unify-chk:" <+> ppr (simpleUnifyCheck UC_OnTheFly tv1 ty2)
    
    2534
    -                  , text "touchability:" <+> ppr (touchabilityAndShapeTest cur_lvl tv1 ty2)]
    
    2532
    +                  , text "simple-unify-chk:" <+> ppr (simpleUnifyCheck UC_OnTheFly cur_lvl tv1 ty2)
    
    2533
    +                  ]
    
    2535 2534
                    -- Occurs check or an untouchable: just defer
    
    2536 2535
                    -- NB: occurs check isn't necessarily fatal:
    
    2537 2536
                    --     eg tv1 occurred in type family parameter
    
    ... ... @@ -2590,9 +2589,8 @@ lhsPriority tv
    2590 2589
     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    2591 2590
     Question: given a homogeneous equality (alpha ~# ty), when is it OK to
    
    2592 2591
     unify alpha := ty?
    
    2593
    -
    
    2594
    -This note only applied to /homogeneous/ equalities, in which both
    
    2595
    -sides have the same kind.
    
    2592
    +(This note only applies to /homogeneous/ equalities, in which both
    
    2593
    +sides have the same kind.)
    
    2596 2594
     
    
    2597 2595
     There are five reasons not to unify:
    
    2598 2596
     
    
    ... ... @@ -2688,7 +2686,7 @@ Needless to say, all there are wrinkles:
    2688 2686
     
    
    2689 2687
       * In the constraint solver, we track where Given equalities occur
    
    2690 2688
         and use that to guard unification in
    
    2691
    -    GHC.Tc.Utils.Unify.touchabilityAndShapeTest. More details in
    
    2689
    +    GHC.Tc.Utils.Unify.touchabilityTest. More details in
    
    2692 2690
         Note [Tracking Given equalities] in GHC.Tc.Solver.InertSet
    
    2693 2691
     
    
    2694 2692
         Historical note: in the olden days (pre 2021) the constraint solver
    
    ... ... @@ -2929,12 +2927,34 @@ data UnifyCheckCaller
    2929 2927
       = UC_OnTheFly   -- Called from the on-the-fly unifier
    
    2930 2928
       | UC_QuickLook  -- Called from Quick Look
    
    2931 2929
       | UC_Solver     -- Called from constraint solver
    
    2932
    -  | UC_Defaulting -- Called when doing top-level defaulting
    
    2933 2930
     
    
    2934
    -simpleUnifyCheck :: UnifyCheckCaller -> TcTyVar -> TcType -> Bool
    
    2935
    --- simpleUnifyCheck does a fast check: True <=> unification is OK
    
    2936
    --- If it says 'False' then unification might still be OK, but
    
    2937
    --- it'll take more work to do -- use the full checkTypeEq
    
    2931
    +-- | The result type of 'simpleUnifyCheck'.
    
    2932
    +data SimpleUnifyResult
    
    2933
    +  -- | Definitely cannot unify (untouchable variable or incompatible top-shape)
    
    2934
    +  = SUC_CannotUnify
    
    2935
    +  -- | The variable is touchable and the top-shape test passed, but
    
    2936
    +  -- it may or may not be OK to unify
    
    2937
    +  | SUC_NotSure
    
    2938
    +  -- | Definitely OK to unify
    
    2939
    +  | SUC_CanUnify
    
    2940
    +  deriving stock (Eq, Ord, Show)
    
    2941
    +instance Semigroup SimpleUnifyResult where
    
    2942
    +  no@SUC_CannotUnify <> _ = no
    
    2943
    +  SUC_CanUnify <> r = r
    
    2944
    +  _ <> no@SUC_CannotUnify = no
    
    2945
    +  r <> SUC_CanUnify = r
    
    2946
    +  ns@SUC_NotSure <> SUC_NotSure = ns
    
    2947
    +
    
    2948
    +instance Outputable SimpleUnifyResult where
    
    2949
    +  ppr = \case
    
    2950
    +    SUC_CannotUnify -> text "SUC_CannotUnify"
    
    2951
    +    SUC_NotSure     -> text "SUC_NotSure"
    
    2952
    +    SUC_CanUnify    -> text "SUC_CanUnify"
    
    2953
    +
    
    2954
    +simpleUnifyCheck :: UnifyCheckCaller -> TcLevel -> TcTyVar -> TcType -> SimpleUnifyResult
    
    2955
    +-- ^ A fast check for unification. May return "not sure", in which case
    
    2956
    +-- unification might still be OK, but it'll take more work to do
    
    2957
    +-- (use the full 'checkTypeEq').
    
    2938 2958
     --
    
    2939 2959
     -- * Rejects if lhs_tv occurs in rhs_ty (occurs check)
    
    2940 2960
     -- * Rejects foralls unless
    
    ... ... @@ -2945,9 +2965,17 @@ simpleUnifyCheck :: UnifyCheckCaller -> TcTyVar -> TcType -> Bool
    2945 2965
     -- * Does a level-check for type variables, to avoid skolem escape
    
    2946 2966
     --
    
    2947 2967
     -- This function is pretty heavily used, so it's optimised not to allocate
    
    2948
    -simpleUnifyCheck caller lhs_tv rhs
    
    2949
    -  = go rhs
    
    2968
    +simpleUnifyCheck caller given_eq_lvl lhs_tv rhs
    
    2969
    +  | not $ touchabilityTest given_eq_lvl lhs_tv
    
    2970
    +  = SUC_CannotUnify
    
    2971
    +  | not $ checkTopShape lhs_info rhs
    
    2972
    +  = SUC_CannotUnify
    
    2973
    +  | rhs_is_ok rhs
    
    2974
    +  = SUC_CanUnify
    
    2975
    +  | otherwise
    
    2976
    +  = SUC_NotSure
    
    2950 2977
       where
    
    2978
    +    lhs_info = metaTyVarInfo lhs_tv
    
    2951 2979
     
    
    2952 2980
         !(occ_in_ty, occ_in_co) = mkOccFolders (tyVarName lhs_tv)
    
    2953 2981
     
    
    ... ... @@ -2967,33 +2995,32 @@ simpleUnifyCheck caller lhs_tv rhs
    2967 2995
                    UC_Solver     -> True
    
    2968 2996
                    UC_QuickLook  -> True
    
    2969 2997
                    UC_OnTheFly   -> False
    
    2970
    -               UC_Defaulting -> True
    
    2971 2998
     
    
    2972
    -    go (TyVarTy tv)
    
    2999
    +    rhs_is_ok (TyVarTy tv)
    
    2973 3000
           | lhs_tv == tv                                    = False
    
    2974 3001
           | tcTyVarLevel tv `strictlyDeeperThan` lhs_tv_lvl = False
    
    2975 3002
           | lhs_tv_is_concrete, not (isConcreteTyVar tv)    = False
    
    2976 3003
           | occ_in_ty $! (tyVarKind tv)                     = False
    
    2977 3004
           | otherwise                                       = True
    
    2978 3005
     
    
    2979
    -    go (FunTy {ft_af = af, ft_mult = w, ft_arg = a, ft_res = r})
    
    3006
    +    rhs_is_ok (FunTy {ft_af = af, ft_mult = w, ft_arg = a, ft_res = r})
    
    2980 3007
           | not forall_ok, isInvisibleFunArg af = False
    
    2981
    -      | otherwise                           = go w && go a && go r
    
    3008
    +      | otherwise                           = rhs_is_ok w && rhs_is_ok a && rhs_is_ok r
    
    2982 3009
     
    
    2983
    -    go (TyConApp tc tys)
    
    3010
    +    rhs_is_ok (TyConApp tc tys)
    
    2984 3011
           | lhs_tv_is_concrete, not (isConcreteTyCon tc) = False
    
    2985 3012
           | not forall_ok, not (isTauTyCon tc)           = False
    
    2986 3013
           | not fam_ok,    not (isFamFreeTyCon tc)       = False
    
    2987
    -      | otherwise                                    = all go tys
    
    3014
    +      | otherwise                                    = all rhs_is_ok tys
    
    2988 3015
     
    
    2989
    -    go (ForAllTy (Bndr tv _) ty)
    
    2990
    -      | forall_ok = go (tyVarKind tv) && (tv == lhs_tv || go ty)
    
    3016
    +    rhs_is_ok (ForAllTy (Bndr tv _) ty)
    
    3017
    +      | forall_ok = rhs_is_ok (tyVarKind tv) && (tv == lhs_tv || rhs_is_ok ty)
    
    2991 3018
           | otherwise = False
    
    2992 3019
     
    
    2993
    -    go (AppTy t1 t2)    = go t1 && go t2
    
    2994
    -    go (CastTy ty co)   = not (occ_in_co co) && go ty
    
    2995
    -    go (CoercionTy co)  = not (occ_in_co co)
    
    2996
    -    go (LitTy {})       = True
    
    3020
    +    rhs_is_ok (AppTy t1 t2)    = rhs_is_ok t1 && rhs_is_ok t2
    
    3021
    +    rhs_is_ok (CastTy ty co)   = not (occ_in_co co) && rhs_is_ok ty
    
    3022
    +    rhs_is_ok (CoercionTy co)  = not (occ_in_co co)
    
    3023
    +    rhs_is_ok (LitTy {})       = True
    
    2997 3024
     
    
    2998 3025
     
    
    2999 3026
     mkOccFolders :: Name -> (TcType -> Bool, TcCoercion -> Bool)
    
    ... ... @@ -3078,8 +3105,13 @@ We must jolly well use that reductionReduced type, even though the
    3078 3105
     reductionCoercion is Refl.  See `canEqCanLHSFinish_no_unification`.
    
    3079 3106
     -}
    
    3080 3107
     
    
    3081
    -data PuResult a b = PuFail CheckTyEqResult
    
    3082
    -                  | PuOK (Bag a) b
    
    3108
    +data PuResult a b
    
    3109
    +  -- | Pure unifier failure.
    
    3110
    +  --
    
    3111
    +  -- Invariant: the CheckTyEqResult is not 'cteOK'; that it, it specifies a problem.
    
    3112
    +  = PuFail CheckTyEqResult
    
    3113
    +  -- | Pure unifier success.
    
    3114
    +  | PuOK (Bag a) b
    
    3083 3115
       deriving stock (Functor, Foldable, Traversable)
    
    3084 3116
     
    
    3085 3117
     instance Applicative (PuResult a) where
    
    ... ... @@ -3414,15 +3446,15 @@ famAppBreaker (BreakWanted ev lhs_tv) fam_app
    3414 3446
            ; return (PuOK (singleCt (mkNonCanonical $ CtWanted new_ev))
    
    3415 3447
                           (mkReduction (HoleCo hole) new_tv_ty)) } }
    
    3416 3448
       where
    
    3449
    +    fam_app_kind = typeKind fam_app
    
    3417 3450
         (lhs_tv_info, lhs_tv_lvl) =
    
    3418 3451
           case tcTyVarDetails lhs_tv of
    
    3419 3452
              MetaTv { mtv_info = info, mtv_tclvl = lvl } -> (info,lvl)
    
    3420 3453
              -- lhs_tv should be a meta-tyvar
    
    3421
    -         _ -> pprPanic "checkTouchableTyVarEq" (ppr lhs_tv)
    
    3422
    -    fam_app_kind = typeKind fam_app
    
    3423
    -    -- See Detail (7) of the Note
    
    3454
    +         _ -> pprPanic "famAppBreaker BreakWanted: lhs_tv is not a meta-tyvar"
    
    3455
    +                (ppr lhs_tv)
    
    3424 3456
         cb_loc = updateCtLocOrigin (ctEvLoc ev) CycleBreakerOrigin
    
    3425
    -
    
    3457
    +      -- CycleBreakerOrigin: see Detail (7) of Note [Type equality cycles]
    
    3426 3458
     
    
    3427 3459
     instance Outputable (TyEqFlags m a) where
    
    3428 3460
       ppr = \case
    
    ... ... @@ -3492,12 +3524,95 @@ famAppArgFlags flags = case flags of
    3492 3524
             -> LC_Check { lc_lvlc = lvl, lc_lenient = False }
    
    3493 3525
           lc -> lc
    
    3494 3526
     
    
    3527
    +{- Note [checkTyEqRhs]
    
    3528
    +~~~~~~~~~~~~~~~~~~~~~~
    
    3529
    +The key function `checkTyEqRhs ty_eq_flags rhs` is called on the
    
    3530
    +RHS of a type equality
    
    3531
    +       lhs ~ rhs
    
    3532
    +and checks to see if `rhs` satisfies, or can be made to satisfy,
    
    3533
    +invariants described by `ty_eq_flags`.  It can succeded or fail; in
    
    3534
    +the latter case it returns a `CheckTyEqResult` that describes why it
    
    3535
    +failed.
    
    3536
    +
    
    3537
    +When `lhs` is a touchable type variable, so unification might happen, then
    
    3538
    +`checkTyEqRhs` enforces the unification preconditions of Note [Unification preconditions].
    
    3539
    +
    
    3540
    +Notably, it can check for things like:
    
    3541
    +  * Insoluble occurs check
    
    3542
    +      e.g.  alpha[tau] ~ [alpha]
    
    3543
    +       or   F Int      ~ [F Int]
    
    3544
    +  * Potentially-soluble occurs check
    
    3545
    +      e.g.  alpha[tau] ~ [F alpha beta]
    
    3546
    +  * Impredicativity error:
    
    3547
    +      e.g.  alpha[tau] ~ (forall a. a->a)
    
    3548
    +  * Skolem escape
    
    3549
    +      e.g  alpha[1] ~ (b[sk:2], Int)
    
    3550
    +  * Concreteness error
    
    3551
    +      e.g. alpha[conc] ~ r[sk]
    
    3552
    +
    
    3553
    +Its specific behaviour is governed by the `TyEqFlags` that are passed
    
    3554
    +to it; see Note [TyEqFlags].
    
    3555
    +
    
    3556
    +Note, however, that `checkTyEqRhs` specifically does /not/ check for:
    
    3557
    +  * Touchability of the LHS (in the case of a unification variable)
    
    3558
    +  * Shape of the LHS (e.g. we can't unify Int with a TyVarTv)
    
    3559
    +These things are checked by `simpleUnifyCheck`.
    
    3560
    +-}
    
    3561
    +
    
    3562
    +
    
    3563
    +-- | Perform the checks specified by the 'TyEqFlags' on the RHS, in order to
    
    3564
    +-- enforce the unification preconditions of Note [Unification preconditions].
    
    3565
    +--
    
    3566
    +-- See Note [checkTyEqRhs].
    
    3495 3567
     checkTyEqRhs :: forall m a
    
    3496 3568
                  .  Monad m
    
    3497 3569
                  => TyEqFlags m a
    
    3498 3570
                  -> TcType           -- Already zonked
    
    3499 3571
                  -> m (PuResult a Reduction)
    
    3500
    -checkTyEqRhs flags ty
    
    3572
    +checkTyEqRhs flags rhs
    
    3573
    +  -- Crucial special case for a top-level equality of the form 'alpha ~ F tys'.
    
    3574
    +  -- We don't want to flatten that (F tys), as this gets us right back to where
    
    3575
    +  -- we started!
    
    3576
    +  --
    
    3577
    +  -- See also Note [Special case for top-level of Given equality]
    
    3578
    +  | Just (TyFamLHS tc tys) <- canTyFamEqLHS_maybe rhs
    
    3579
    +  , not $ tefConcrete flags
    
    3580
    +  = recurseIntoFamTyConApp flags tc tys
    
    3581
    +  | otherwise
    
    3582
    +  = check_ty_eq_rhs flags rhs
    
    3583
    +
    
    3584
    +{- Note [Special case for top-level of Given equality]
    
    3585
    +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    3586
    +We take care when examining
    
    3587
    +    [G] F ty ~ G (...(F ty)...)
    
    3588
    +where both sides are TyFamLHSs.  We don't want to flatten that RHS to
    
    3589
    +    [G] F ty ~ cbv
    
    3590
    +    [G] G (...(F ty)...) ~ cbv
    
    3591
    +Instead we'd like to say "occurs-check" and swap LHS and RHS, which yields a
    
    3592
    +canonical constraint
    
    3593
    +    [G] G (...(F ty)...) ~ F ty
    
    3594
    +That tends to rewrite a big type to smaller one. This happens in T15703,
    
    3595
    +where we had:
    
    3596
    +    [G] Pure g ~ From1 (To1 (Pure g))
    
    3597
    +Making a loop breaker and rewriting left to right just makes much bigger
    
    3598
    +types than swapping it over.
    
    3599
    +
    
    3600
    +(We might hope to have swapped it over before getting to checkTypeEq,
    
    3601
    +but better safe than sorry.)
    
    3602
    +
    
    3603
    +NB: We never see a TyVarLHS here, such as
    
    3604
    +    [G] a ~ F tys here
    
    3605
    +because we'd have swapped it to
    
    3606
    +   [G] F tys ~ a
    
    3607
    +in canEqCanLHS2, before getting to checkTypeEq.
    
    3608
    +-}
    
    3609
    +
    
    3610
    +check_ty_eq_rhs :: forall m a
    
    3611
    +                .  Monad m
    
    3612
    +                => TyEqFlags m a
    
    3613
    +                -> TcType           -- Already zonked
    
    3614
    +                -> m (PuResult a Reduction)
    
    3615
    +check_ty_eq_rhs flags ty
    
    3501 3616
       = case ty of
    
    3502 3617
           LitTy {}        -> return $ okCheckRefl ty
    
    3503 3618
           TyConApp tc tys -> checkTyConApp flags ty tc tys
    
    ... ... @@ -3510,16 +3625,16 @@ checkTyEqRhs flags ty
    3510 3625
            | isInvisibleFunArg af  -- e.g.  Num a => blah
    
    3511 3626
            -> return $ PuFail impredicativeProblem -- Not allowed (TyEq:F)
    
    3512 3627
            | otherwise
    
    3513
    -       -> do { w_res <- checkTyEqRhs flags w
    
    3514
    -             ; a_res <- checkTyEqRhs flags a
    
    3515
    -             ; r_res <- checkTyEqRhs flags r
    
    3628
    +       -> do { w_res <- check_ty_eq_rhs flags w
    
    3629
    +             ; a_res <- check_ty_eq_rhs flags a
    
    3630
    +             ; r_res <- check_ty_eq_rhs flags r
    
    3516 3631
                  ; return (mkFunRedn Nominal af <$> w_res <*> a_res <*> r_res) }
    
    3517 3632
     
    
    3518
    -      AppTy fun arg -> do { fun_res <- checkTyEqRhs flags fun
    
    3519
    -                          ; arg_res <- checkTyEqRhs flags arg
    
    3633
    +      AppTy fun arg -> do { fun_res <- check_ty_eq_rhs flags fun
    
    3634
    +                          ; arg_res <- check_ty_eq_rhs flags arg
    
    3520 3635
                               ; return (mkAppRedn <$> fun_res <*> arg_res) }
    
    3521 3636
     
    
    3522
    -      CastTy ty co  -> do { ty_res <- checkTyEqRhs flags ty
    
    3637
    +      CastTy ty co  -> do { ty_res <- check_ty_eq_rhs flags ty
    
    3523 3638
                               ; co_res <- checkCo flags co
    
    3524 3639
                               ; return (mkCastRedn1 Nominal ty <$> co_res <*> ty_res) }
    
    3525 3640
     
    
    ... ... @@ -3527,7 +3642,7 @@ checkTyEqRhs flags ty
    3527 3642
                               ; return (mkReflCoRedn Nominal <$> co_res) }
    
    3528 3643
     
    
    3529 3644
           ForAllTy {}   -> return $ PuFail impredicativeProblem -- Not allowed (TyEq:F)
    
    3530
    -{-# INLINEABLE checkTyEqRhs #-}
    
    3645
    +{-# INLINEABLE check_ty_eq_rhs #-}
    
    3531 3646
     
    
    3532 3647
     -------------------
    
    3533 3648
     checkCo :: Monad m => TyEqFlags m a -> Coercion -> m (PuResult a Coercion)
    
    ... ... @@ -3702,14 +3817,14 @@ checkTyConApp flags tc_app tc tys
    3702 3817
         else do { let (fun_args, extra_args) = splitAt (tyConArity tc) tys
    
    3703 3818
                       fun_app                = mkTyConApp tc fun_args
    
    3704 3819
                 ; fun_res   <- checkFamApp flags fun_app tc fun_args
    
    3705
    -            ; extra_res <- mapCheck (checkTyEqRhs flags) extra_args
    
    3820
    +            ; extra_res <- mapCheck (check_ty_eq_rhs flags) extra_args
    
    3706 3821
                 ; return (mkAppRedns <$> fun_res <*> extra_res) }
    
    3707 3822
     
    
    3708 3823
       | Just ty' <- rewriterView tc_app
    
    3709 3824
            -- e.g. S a  where  type S a = F [a]
    
    3710 3825
            --             or   type S a = Int
    
    3711 3826
            -- See Note [Forgetful synonyms in checkTyConApp]
    
    3712
    -  = checkTyEqRhs flags ty'
    
    3827
    +  = check_ty_eq_rhs flags ty'
    
    3713 3828
     
    
    3714 3829
       | not (isTauTyCon tc)
    
    3715 3830
       = return $ PuFail impredicativeProblem
    
    ... ... @@ -3727,7 +3842,7 @@ recurseIntoTyConApp :: Monad m
    3727 3842
                         -> TyCon -> [TcType]
    
    3728 3843
                         -> m (PuResult a Reduction)
    
    3729 3844
     recurseIntoTyConApp flags tc tys
    
    3730
    -  = do { tys_res <- mapCheck (checkTyEqRhs flags) tys
    
    3845
    +  = do { tys_res <- mapCheck (check_ty_eq_rhs flags) tys
    
    3731 3846
            ; return (mkTyConAppRedn Nominal tc <$> tys_res) }
    
    3732 3847
     
    
    3733 3848
     recurseIntoFamTyConApp :: Monad m
    
    ... ... @@ -3888,7 +4003,7 @@ checkTyVar flags occ_tv
    3888 4003
                --     unfilled meta-tyvar, we need to ensure that the kind of
    
    3889 4004
                --     'occ_tv' is concrete.   Test cases: T23051, T23176.
    
    3890 4005
                ; let occ_kind = tyVarKind occ_tv
    
    3891
    -           ; kind_result <- checkTyEqRhs flags occ_kind
    
    4006
    +           ; kind_result <- check_ty_eq_rhs flags occ_kind
    
    3892 4007
                ; for kind_result $ \ kind_redn ->
    
    3893 4008
             do { let kind_co  = reductionCoercion kind_redn
    
    3894 4009
                      new_kind = reductionReducedType kind_redn
    
    ... ... @@ -4010,16 +4125,15 @@ promote_meta_tyvar info dest_lvl occ_tv
    4010 4125
     
    
    4011 4126
     
    
    4012 4127
     -------------------------
    
    4013
    -touchabilityAndShapeTest :: TcLevel -> TcTyVar -> TcType -> Bool
    
    4014
    --- This is the key test for untouchability:
    
    4128
    +touchabilityTest :: TcLevel -> TcTyVar -> Bool
    
    4129
    +-- ^ This is the key test for untouchability:
    
    4015 4130
     -- See Note [Unification preconditions] in GHC.Tc.Utils.Unify
    
    4016 4131
     -- and Note [Solve by unification] in GHC.Tc.Solver.Equality
    
    4017
    --- True <=> touchability and shape are OK
    
    4018
    -touchabilityAndShapeTest given_eq_lvl tv rhs
    
    4019
    -  | MetaTv { mtv_info = info, mtv_tclvl = tv_lvl } <- tcTyVarDetails tv
    
    4020
    -  , tv_lvl `deeperThanOrSame` given_eq_lvl
    
    4021
    -  , checkTopShape info rhs
    
    4022
    -  = True
    
    4132
    +--
    
    4133
    +-- @True@ <=> the variable is touchable
    
    4134
    +touchabilityTest given_eq_lvl tv
    
    4135
    +  | MetaTv { mtv_tclvl = tv_lvl } <- tcTyVarDetails tv
    
    4136
    +  = tv_lvl `deeperThanOrSame` given_eq_lvl
    
    4023 4137
       | otherwise
    
    4024 4138
       = False
    
    4025 4139
     
    

  • testsuite/tests/rep-poly/RepPolyTuple4.stderr
    ... ... @@ -6,8 +6,6 @@ RepPolyTuple4.hs:8:7: error: [GHC-55287]
    6 6
             When unifying:
    
    7 7
               • a0 -> b0 -> (# a0, b0 #)
    
    8 8
               • a -> a -> (# a, a #)
    
    9
    -        Cannot unify ‘r’ with the type variable ‘w1’
    
    10
    -        because the former is not a concrete ‘RuntimeRep’.
    
    11 9
           • The second component of the unboxed tuple
    
    12 10
             does not have a fixed runtime representation.
    
    13 11
             Its type is:
    
    ... ... @@ -15,8 +13,6 @@ RepPolyTuple4.hs:8:7: error: [GHC-55287]
    15 13
             When unifying:
    
    16 14
               • a0 -> b0 -> (# a0, b0 #)
    
    17 15
               • a -> a -> (# a, a #)
    
    18
    -        Cannot unify ‘r’ with the type variable ‘w0’
    
    19
    -        because the former is not a concrete ‘RuntimeRep’.
    
    20 16
         • In the expression: (#,#) @_ @_
    
    21 17
           In an equation for ‘bar’: bar = (#,#) @_ @_
    
    22 18
     

  • testsuite/tests/rep-poly/T19709b.stderr
    ... ... @@ -2,11 +2,8 @@ T19709b.hs:11:15: error: [GHC-55287]
    2 2
         • The argument ‘(error @Any "e2")’ of ‘levfun’
    
    3 3
           does not have a fixed runtime representation.
    
    4 4
           Its type is:
    
    5
    -        a1 :: TYPE r0
    
    6
    -      When unifying:
    
    7
    -        • a0
    
    8
    -        • a1
    
    9
    -      Cannot unify ‘Any’ with the type variable ‘r0’
    
    5
    +        a1 :: TYPE c0
    
    6
    +      Cannot unify ‘Any’ with the type variable ‘c0’
    
    10 7
           because the former is not a concrete ‘RuntimeRep’.
    
    11 8
         • In the first argument of ‘levfun’, namely ‘(error @Any "e2")’
    
    12 9
           In the first argument of ‘seq’, namely ‘levfun (error @Any "e2")’
    

  • testsuite/tests/rep-poly/T23903.stderr
    ... ... @@ -2,11 +2,8 @@ T23903.hs:21:1: error: [GHC-55287]
    2 2
         • The first pattern in the equation for ‘f’
    
    3 3
           does not have a fixed runtime representation.
    
    4 4
           Its type is:
    
    5
    -        t0 :: TYPE cx0
    
    6
    -      When unifying:
    
    7
    -        • t0 -> ()
    
    8
    -        • a #-> ()
    
    9
    -      Cannot unify ‘Rep a’ with the type variable ‘cx0’
    
    5
    +        t0 :: TYPE c0
    
    6
    +      Cannot unify ‘Rep a’ with the type variable ‘c0’
    
    10 7
           because the former is not a concrete ‘RuntimeRep’.
    
    11 8
         • The equation for ‘f’ has one visible argument,
    
    12 9
             but its type ‘a #-> ()’ has none
    

  • testsuite/tests/simplCore/should_compile/simpl017.stderr
    1
    -simpl017.hs:55:12: error: [GHC-46956]
    
    2
    -    • Couldn't match type ‘v0’ with ‘v’
    
    3
    -      Expected: [E m i] -> E' v m a
    
    4
    -        Actual: [E m i] -> E' v0 m a
    
    5
    -        because type variable ‘v’ would escape its scope
    
    6
    -      This (rigid, skolem) type variable is bound by
    
    7
    -        a type expected by the context:
    
    8
    -          forall v. [E m i] -> E' v m a
    
    9
    -        at simpl017.hs:55:12
    
    10
    -    • In the first argument of ‘return’, namely ‘f’
    
    11
    -      In a stmt of a 'do' block: return f
    
    1
    +simpl017.hs:55:5: error: [GHC-83865]
    
    2
    +    • Couldn't match type: [E m i] -> E' v0 m a
    
    3
    +                     with: forall v. [E m i] -> E' v m a
    
    4
    +      Expected: m (forall v. [E m i] -> E' v m a)
    
    5
    +        Actual: m ([E m i] -> E' v0 m a)
    
    6
    +    • In a stmt of a 'do' block: return f
    
    12 7
           In the first argument of ‘E’, namely
    
    13 8
             ‘(do let ix :: [E m i] -> m i
    
    14 9
                      ix [i] = runE i
    
    15 10
                      {-# INLINE f #-}
    
    16 11
                      ....
    
    17 12
                  return f)’
    
    13
    +      In the expression:
    
    14
    +        E (do let ix :: [E m i] -> m i
    
    15
    +                  ix [i] = runE i
    
    16
    +                  {-# INLINE f #-}
    
    17
    +                  ....
    
    18
    +              return f)
    
    18 19
         • Relevant bindings include
    
    19 20
             f :: [E m i] -> E' v0 m a (bound at simpl017.hs:54:9)
    
    21
    +        ix :: [E m i] -> m i (bound at simpl017.hs:52:9)
    
    22
    +        a :: arr i a (bound at simpl017.hs:50:11)
    
    23
    +        liftArray :: arr i a -> E m (forall v. [E m i] -> E' v m a)
    
    24
    +          (bound at simpl017.hs:50:1)
    
    20 25
     

  • testsuite/tests/typecheck/should_compile/T26030.hs
    1
    +{-# LANGUAGE TypeFamilies #-}
    
    2
    +{-# LANGUAGE GADTs #-}
    
    3
    +
    
    4
    +-- This program was rejected by GHC 9.12 due to a bug with
    
    5
    +-- unification in QuickLook.
    
    6
    +module T26030 where
    
    7
    +
    
    8
    +import Data.Kind
    
    9
    +
    
    10
    +type S :: Type -> Type
    
    11
    +data S a where
    
    12
    +  S1 :: S Bool
    
    13
    +  S2 :: S Char
    
    14
    +
    
    15
    +type F :: Type -> Type
    
    16
    +type family F a where
    
    17
    +  F Bool = Bool
    
    18
    +  F Char = Char
    
    19
    +
    
    20
    +foo :: forall a. S a -> IO (F a)
    
    21
    +foo sa1 = do
    
    22
    +  () <- return ()
    
    23
    +  case sa1 of
    
    24
    +    S1 -> return $ False
    
    25
    +    S2 -> return 'x'

  • testsuite/tests/typecheck/should_compile/all.T
    ... ... @@ -887,6 +887,7 @@ test('T21909b', normal, compile, [''])
    887 887
     test('T21443', normal, compile, [''])
    
    888 888
     test('T22194', normal, compile, [''])
    
    889 889
     test('T25744', normal, compile, [''])
    
    890
    +test('T26030', normal, compile, [''])
    
    890 891
     test('QualifiedRecordUpdate',
    
    891 892
         [ extra_files(['QualifiedRecordUpdate_aux.hs']) ]
    
    892 893
         , multimod_compile, ['QualifiedRecordUpdate', '-v0'])
    

  • testsuite/tests/typecheck/should_fail/T25950.hs
    1
    +{-# LANGUAGE PartialTypeSignatures #-}
    
    2
    +
    
    3
    +module T25950 where
    
    4
    +
    
    5
    +fails :: _ => a
    
    6
    +fails = id $ ()

  • testsuite/tests/typecheck/should_fail/T25950.stderr
    1
    +T25950.hs:6:9: error: [GHC-25897]
    
    2
    +    • Couldn't match expected type ‘a’ with actual type ‘()’
    
    3
    +      ‘a’ is a rigid type variable bound by
    
    4
    +        the inferred type of fails :: a
    
    5
    +        at T25950.hs:5:1-15
    
    6
    +    • In the expression: id $ ()
    
    7
    +      In an equation for ‘fails’: fails = id $ ()
    
    8
    +    • Relevant bindings include fails :: a (bound at T25950.hs:6:1)
    
    9
    +

  • testsuite/tests/typecheck/should_fail/all.T
    ... ... @@ -726,6 +726,7 @@ test('T17594c', normal, compile_fail, [''])
    726 726
     test('T17594d', normal, compile_fail, [''])
    
    727 727
     test('T17594g', normal, compile_fail, [''])
    
    728 728
     
    
    729
    +test('T25950', normal, compile_fail, [''])
    
    729 730
     test('T24470a', normal, compile_fail, [''])
    
    730 731
     test('T24553', normal, compile_fail, [''])
    
    731 732
     test('T23739b', normal, compile_fail, [''])