Skip to content
Snippets Groups Projects
Commit 9aaa8971 authored by Simon Peyton Jones's avatar Simon Peyton Jones
Browse files

Remove unnecessary free-var-set deletion

In TcSimplify.neededEvVars, in add_implic_seeds we were
deleting the 'givens'; but they are already deleted, so
this is a no-op.  This patch just remove the redundant
delete.
parent ecfe38ef
No related branches found
No related tags found
No related merge requests found
......@@ -399,19 +399,16 @@ data EvBindsVar
-- Some Given, some Wanted
ebv_tcvs :: IORef CoVarSet
-- The free coercion vars of the (rhss of) the coercion bindings
-- All of these are Wanted
--
-- Coercions don't actually have bindings
-- because we plug them in-place (via a mutable
-- variable); but we keep their free variables
-- so that we can report unused given constraints
-- The free Given coercion vars needed by Wanted coercions that
-- are solved by filling in their HoleDest in-place. Since they
-- don't appear in ebv_binds, we keep track of their free
-- variables so that we can report unused given constraints
-- See Note [Tracking redundant constraints] in TcSimplify
}
| CoEvBindsVar { -- See Note [Coercion evidence only]
-- See above for comments on ebv_uniq, evb_tcvs
-- See above for comments on ebv_uniq, ebv_tcvs
ebv_uniq :: Unique,
ebv_tcvs :: IORef CoVarSet
}
......@@ -834,6 +831,8 @@ evTermCoercion tm = case evTermCoercion_maybe tm of
********************************************************************* -}
findNeededEvVars :: EvBindMap -> VarSet -> VarSet
-- Find all the Given evidence needed by seeds,
-- looking transitively through binds
findNeededEvVars ev_binds seeds
= transCloVarSet also_needs seeds
where
......
......@@ -3340,12 +3340,12 @@ setEvBind ev_bind
-- | Mark variables as used filling a coercion hole
useVars :: CoVarSet -> TcS ()
useVars vars
useVars co_vars
= do { ev_binds_var <- getTcEvBindsVar
; let ref = ebv_tcvs ev_binds_var
; wrapTcS $
do { tcvs <- TcM.readTcRef ref
; let tcvs' = tcvs `unionVarSet` vars
; let tcvs' = tcvs `unionVarSet` co_vars
; TcM.writeTcRef ref tcvs' } }
-- | Equalities only
......
......@@ -1775,8 +1775,8 @@ neededEvVars implic@(Implic { ic_given = givens
; return (implic { ic_need_inner = need_inner
, ic_need_outer = need_outer }) }
where
add_implic_seeds (Implic { ic_need_outer = needs, ic_given = givens }) acc
= (needs `delVarSetList` givens) `unionVarSet` acc
add_implic_seeds (Implic { ic_need_outer = needs }) acc
= needs `unionVarSet` acc
needed_ev_bind needed (EvBind { eb_lhs = ev_var
, eb_is_given = is_given })
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment