| ... |
... |
@@ -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
|