Simon Peyton Jones pushed to branch wip/T23162-spj at Glasgow Haskell Compiler / GHC

Commits:

2 changed files:

Changes:

  • compiler/GHC/Core/TyCo/FVs.hs
    ... ... @@ -339,9 +339,8 @@ deepTcvFolder = TyCoFolder { tcf_view = noView -- See Note [Free vars and synon
    339 339
                                              acc `extendVarSet` v
    
    340 340
     
    
    341 341
         do_bndr is tcv _ = extendVarSet is tcv
    
    342
    -    do_hole is hole  = do_tcv is (coHoleCoVar hole)
    
    343
    -                       -- See Note [CoercionHoles and coercion free variables]
    
    344
    -                       -- in GHC.Core.TyCo.Rep
    
    342
    +    do_hole _ _  = mempty  -- See (CHFV1) in Note [CoercionHoles and coercion free variables]
    
    343
    +                           -- in GHC.Core.TyCo.Rep
    
    345 344
     
    
    346 345
     {- *********************************************************************
    
    347 346
     *                                                                      *
    
    ... ... @@ -445,6 +444,8 @@ deepCoVarFolder = TyCoFolder { tcf_view = noView
    445 444
           -- the tyvar won't end up in the accumulator, so
    
    446 445
           -- we'd look repeatedly.  Blargh.
    
    447 446
     
    
    447
    +    do_bndr is tcv _ = extendVarSet is tcv
    
    448
    +
    
    448 449
         do_covar is v = Endo do_it
    
    449 450
           where
    
    450 451
             do_it acc | v `elemVarSet` is  = acc
    
    ... ... @@ -452,10 +453,9 @@ deepCoVarFolder = TyCoFolder { tcf_view = noView
    452 453
                       | otherwise          = appEndo (deep_cv_ty (varType v)) $
    
    453 454
                                              acc `extendVarSet` v
    
    454 455
     
    
    455
    -    do_bndr is tcv _ = extendVarSet is tcv
    
    456
    -    do_hole is hole  = do_covar is (coHoleCoVar hole)
    
    457
    -                       -- See Note [CoercionHoles and coercion free variables]
    
    458
    -                       -- in GHC.Core.TyCo.Rep
    
    456
    +    do_hole _ _ = mempty
    
    457
    +      -- See (CHFV1) in Note [CoercionHoles and coercion free variables]
    
    458
    +      -- in GHC.Core.TyCo.Rep
    
    459 459
     
    
    460 460
     ------- Same again, but for DCoVarSet ----------
    
    461 461
     --    But this time the free vars are shallow
    
    ... ... @@ -661,9 +661,8 @@ tyCoFVsOfCo (FunCo { fco_mult = w, fco_arg = co1, fco_res = co2 }) fv_cand in_sc
    661 661
       = (tyCoFVsOfCo co1 `unionFV` tyCoFVsOfCo co2 `unionFV` tyCoFVsOfCo w) fv_cand in_scope acc
    
    662 662
     tyCoFVsOfCo (CoVarCo v) fv_cand in_scope acc
    
    663 663
       = tyCoFVsOfCoVar v fv_cand in_scope acc
    
    664
    -tyCoFVsOfCo (HoleCo h) fv_cand in_scope acc
    
    665
    -  = tyCoFVsOfCoVar (coHoleCoVar h) fv_cand in_scope acc
    
    666
    -    -- See Note [CoercionHoles and coercion free variables]
    
    664
    +tyCoFVsOfCo (HoleCo {}) fv_cand in_scope acc = emptyFV fv_cand in_scope acc
    
    665
    +    -- Ignore holes: see (CHFV1) in Note [CoercionHoles and coercion free variables]
    
    667 666
     tyCoFVsOfCo (AxiomCo _ cs)    fv_cand in_scope acc = tyCoFVsOfCos cs  fv_cand in_scope acc
    
    668 667
     tyCoFVsOfCo (UnivCo { uco_lty = t1, uco_rty = t2, uco_deps = deps}) fv_cand in_scope acc
    
    669 668
       = (tyCoFVsOfCos deps `unionFV` tyCoFVsOfType t1
    

  • compiler/GHC/Core/TyCo/Rep.hs
    ... ... @@ -1803,17 +1803,23 @@ Other notes about HoleCo:
    1803 1803
     
    
    1804 1804
     Note [CoercionHoles and coercion free variables]
    
    1805 1805
     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
    
    1806
    -Why does a CoercionHole contain a CoVar, as well as reference to
    
    1807
    -fill in?  Because we want to treat that CoVar as a free variable of
    
    1808
    -the coercion.  See #14584, and Note [What prevents a
    
    1809
    -constraint from floating] in GHC.Tc.Solver, item (4):
    
    1806
    +Why does a CoercionHole contain a CoVar, as well as reference to fill in?
    
    1807
    +  * It really helps for debug pretty-printing.
    
    1808
    +  * It carries a type which makes `coercionKind` and `coercionRole` work
    
    1809
    +  * It has a Unique, which gives the hole an identity; see calls to `ctEvEvId`
    
    1810
    +
    
    1811
    +(CHFV1) We do not treat a CoercionHole as a free variable of a coercion.
    
    1812
    +  In the past we did: See #14584, and Note [What prevents a constraint from floating]
    
    1813
    +  in GHC.Tc.Solver, item (4):
    
    1810 1814
     
    
    1811 1815
             forall k. [W] co1 :: t1 ~# t2 |> co2
    
    1812 1816
                       [W] co2 :: k ~# *
    
    1813 1817
     
    
    1814
    -Here co2 is a CoercionHole. But we /must/ know that it is free in
    
    1815
    -co1, because that's all that stops it floating outside the
    
    1816
    -implication.
    
    1818
    +   Here co2 is a CoercionHole. But we /must/ know that it is free in
    
    1819
    +   co1, because that's all that stops it floating outside the
    
    1820
    +   implication.
    
    1821
    +
    
    1822
    +   But nowadays this is all irrelevant because we don't float constraints.
    
    1817 1823
     
    
    1818 1824
     Note [CoercionHoles and RewriterSets]
    
    1819 1825
     ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~