Skip to content
Snippets Groups Projects
Commit 90fd2bc7 authored by sof's avatar sof
Browse files

[project @ 1998-04-30 19:44:49 by sof]

When floating in, we have to be careful not to float a specialisation
of a binder past a use of that binder that may later be simplified to
use the specialised version that just floated past (and out of scope.)

Kludgily fix this by including the idSpecVars of a Var in its free
variable set.
parent 3222f2af
No related merge requests found
......@@ -21,8 +21,9 @@ module FreeVars (
import AnnCoreSyn -- output
import CoreSyn
import CoreUtils ( idSpecVars )
import Id ( idType, getIdArity, isBottomingId,
emptyIdSet, unitIdSet, mkIdSet,
emptyIdSet, unitIdSet, mkIdSet, unionIdSets,
elementOfIdSet, minusIdSet, unionManyIdSets,
IdSet, Id
)
......@@ -36,6 +37,7 @@ import TyVar ( emptyTyVarSet, unitTyVarSet, minusTyVarSet,
import BasicTypes ( Unused )
import UniqSet ( unionUniqSets, addOneToUniqSet )
import Util ( panic, assertPanic )
\end{code}
%************************************************************************
......@@ -111,6 +113,7 @@ Main public interface:
freeVars :: CoreExpr -> CoreExprWithFVs
freeVars expr = fvExpr noIdCands noTyVarCands expr
\end{code}
%************************************************************************
......@@ -132,13 +135,18 @@ fvExpr :: IdCands -- In-scope Ids
-> CoreExprWithFVs
fvExpr id_cands tyvar_cands (Var v)
= (FVInfo (if (v `is_among` id_cands)
then aFreeId v
else noFreeIds)
noFreeTyVars
leakiness,
AnnVar v)
= (FVInfo fvs noFreeTyVars leakiness, AnnVar v)
where
{-
ToDo: insert motivating example for why we *need*
to include the idSpecVars in the FV list.
-}
fvs = fvs_v `unionIdSets` mkIdSet (idSpecVars v)
fvs_v
| v `is_among` id_cands = aFreeId v
| otherwise = noFreeIds
leakiness
| isBottomingId v = lEAK_FREE_BIG -- Hack
| otherwise = case getIdArity v of
......@@ -305,9 +313,11 @@ fvExpr id_cands tyvar_cands (Note other_note expr)
-- free vars of the RHS the idSpecVars of the binder,
-- since those are, in truth, free in the definition.
fvRhs id_cands tyvar_cands (bndr,rhs)
= (FVInfo (fvs `unionIdSets` idSpecVars bndr) ftvs leak, rhs')
= (FVInfo fvs' ftvs leak, rhs')
where
(FVInfo fvs ftvs leak, rhs') = fvExpr id_cands tyvar_cands rhs
fvs' = fvs `unionIdSets` mkIdSet (idSpecVars bndr)
\end{code}
\begin{code}
......
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