summaryrefslogtreecommitdiff
path: root/ghc/compiler/deSugar
diff options
context:
space:
mode:
authorsimonpj <unknown>2001-07-20 16:48:21 +0000
committersimonpj <unknown>2001-07-20 16:48:21 +0000
commit5d095cc1308afc5e539174f33fd3ff2bd9788bbd (patch)
tree0f18125d2d44db43074fa757cd6173628c2779d5 /ghc/compiler/deSugar
parente3defabc698eb976504f750eee1258fe400a8352 (diff)
downloadhaskell-5d095cc1308afc5e539174f33fd3ff2bd9788bbd.tar.gz
[project @ 2001-07-20 16:48:20 by simonpj]
This commit adds the very convenient function Subst.substTyWith :: [TyVar] -> [Type] -> Type -> Type and uses it in various places.
Diffstat (limited to 'ghc/compiler/deSugar')
-rw-r--r--ghc/compiler/deSugar/DsBinds.lhs10
1 files changed, 5 insertions, 5 deletions
diff --git a/ghc/compiler/deSugar/DsBinds.lhs b/ghc/compiler/deSugar/DsBinds.lhs
index fce09c1bc4..ddfbd6c187 100644
--- a/ghc/compiler/deSugar/DsBinds.lhs
+++ b/ghc/compiler/deSugar/DsBinds.lhs
@@ -30,7 +30,7 @@ import Id ( idType, idName, isExportedId, isSpecPragmaId, Id )
import NameSet
import VarSet
import TcType ( mkTyVarTy )
-import Subst ( mkTyVarSubst, substTy )
+import Subst ( substTyWith )
import TysWiredIn ( voidTy )
import Outputable
import Maybe ( isJust )
@@ -132,16 +132,16 @@ dsMonoBinds auto_scc (AbsBinds all_tyvars dicts exports inlines binds) rest
mk_bind (tyvars, global, local) n -- locals !! n == local
= -- Need to make fresh locals to bind in the selector, because
-- some of the tyvars will be bound to voidTy
- newSysLocalsDs (map (substTy env) local_tys) `thenDs` \ locals' ->
- newSysLocalDs (substTy env tup_ty) `thenDs` \ tup_id ->
+ newSysLocalsDs (map substitute local_tys) `thenDs` \ locals' ->
+ newSysLocalDs (substitute tup_ty) `thenDs` \ tup_id ->
returnDs (global, mkLams tyvars $ mkLams dicts $
mkTupleSelector locals' (locals' !! n) tup_id $
mkApps (mkTyApps (Var poly_tup_id) ty_args) dict_args)
where
mk_ty_arg all_tyvar | all_tyvar `elem` tyvars = mkTyVarTy all_tyvar
| otherwise = voidTy
- ty_args = map mk_ty_arg all_tyvars
- env = mkTyVarSubst all_tyvars ty_args
+ ty_args = map mk_ty_arg all_tyvars
+ substitute = substTyWith all_tyvars ty_args
in
zipWithDs mk_bind exports [0..] `thenDs` \ export_binds ->
-- don't scc (auto-)annotate the tuple itself.