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

[project @ 1997-07-25 22:48:28 by sof]

rnExprs made stricter
parent c2dcbe16
No related merge requests found
......@@ -44,7 +44,7 @@ import Id ( GenId )
import ErrUtils ( addErrLoc, addShortErrLocLine )
import Name
import Pretty
import UniqFM ( lookupUFM{-, ufmToList ToDo:rm-} )
import UniqFM ( lookupUFM, {- ToDo:rm-} isNullUFM )
import UniqSet ( emptyUniqSet, unitUniqSet,
unionUniqSets, unionManyUniqSets,
SYN_IE(UniqSet)
......@@ -225,15 +225,23 @@ rnGRHSsAndBinds (GRHSsAndBindsIn grhss binds)
\begin{code}
rnExprs :: [RdrNameHsExpr] -> RnMS s ([RenamedHsExpr], FreeVars)
rnExprs ls =
rnExprs' ls [] `thenRn` \ (exprs, fvExprs) ->
returnRn (exprs, unionManyNameSets fvExprs)
rnExprs' [] acc = returnRn ([], acc)
rnExprs' (expr:exprs) acc
= rnExpr expr `thenRn` \ (expr', fvExpr) ->
rnExprs' exprs (fvExpr:acc) `thenRn` \ (exprs', fvExprs) ->
rnExprs ls = rnExprs' ls emptyUniqSet
where
rnExprs' [] acc = returnRn ([], acc)
rnExprs' (expr:exprs) acc
= rnExpr expr `thenRn` \ (expr', fvExpr) ->
-- Now we do a "seq" on the free vars because typically it's small
-- or empty, especially in very long lists of constants
let
acc' = acc `unionNameSets` fvExpr
in
(grubby_seqNameSet acc' rnExprs') exprs acc' `thenRn` \ (exprs', fvExprs) ->
returnRn (expr':exprs', fvExprs)
-- Grubby little function to do "seq" on namesets; replace by proper seq when GHC can do seq
grubby_seqNameSet ns result | isNullUFM ns = result
| otherwise = result
\end{code}
Variables. We look up the variable and return the resulting name. The
......
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