summaryrefslogtreecommitdiff
path: root/ghc/compiler/rename
diff options
context:
space:
mode:
authorsimonpj <unknown>2001-08-14 06:35:58 +0000
committersimonpj <unknown>2001-08-14 06:35:58 +0000
commit2767767f7b4acf89f56d18231f143b60429631f6 (patch)
tree1ddb3b9e3d5b2407eab87d4dd872779aa094b1c1 /ghc/compiler/rename
parent76d4cbb3378450af575236be994b95ffcc6da3c8 (diff)
downloadhaskell-2767767f7b4acf89f56d18231f143b60429631f6.tar.gz
[project @ 2001-08-14 06:35:56 by simonpj]
1. Arrange that w/w records unfoldings And that the simplifier preserves them 2. Greatly improve structure of checking user types in the typechecker Main changes: TcMType.checkValidType checks for a valid type TcMonoType.tcHsSigType uses checkValidType Type and class decls use TcMonoType.tcHsType (which does not check for validity) inside the knot in TcTyClsDecls, and then runs TcTyDecls.checkValidTyCon or TcClassDcl.checkValidClass to check for validity once the knot is tied
Diffstat (limited to 'ghc/compiler/rename')
-rw-r--r--ghc/compiler/rename/RnNames.lhs5
-rw-r--r--ghc/compiler/rename/RnSource.lhs9
2 files changed, 4 insertions, 10 deletions
diff --git a/ghc/compiler/rename/RnNames.lhs b/ghc/compiler/rename/RnNames.lhs
index 7c65a96e25..a0613ab3ab 100644
--- a/ghc/compiler/rename/RnNames.lhs
+++ b/ghc/compiler/rename/RnNames.lhs
@@ -272,8 +272,9 @@ filterImports :: ModuleName -- The module being imported
-> WhereFrom -- Tells whether it's a {-# SOURCE #-} import
-> Maybe (Bool, [RdrNameIE]) -- Import spec; True => hiding
-> [AvailInfo] -- What's available
- -> RnMG ([AvailInfo], -- What's actually imported
- [AvailInfo], -- What's to be hidden
+ -> RnMG ([AvailInfo], -- "chosens"
+ [AvailInfo], -- "hides"
+ -- The true imports are "chosens" - "hides"
-- (It's convenient to return both the above sets, because
-- the substraction can be done more efficiently when
-- building the environment.)
diff --git a/ghc/compiler/rename/RnSource.lhs b/ghc/compiler/rename/RnSource.lhs
index 50c9ee59a4..28e5447f9f 100644
--- a/ghc/compiler/rename/RnSource.lhs
+++ b/ghc/compiler/rename/RnSource.lhs
@@ -322,20 +322,13 @@ rnTyClDecl (TyData {tcdND = new_or_data, tcdCtxt = context, tcdName = tycon,
rnTyClDecl (TySynonym {tcdName = name, tcdTyVars = tyvars, tcdSynRhs = ty, tcdLoc = src_loc})
= pushSrcLocRn src_loc $
- doptRn Opt_GlasgowExts `thenRn` \ glaExts ->
lookupTopBndrRn name `thenRn` \ name' ->
bindTyVarsRn syn_doc tyvars $ \ tyvars' ->
- rnHsType syn_doc (unquantify glaExts ty) `thenRn` \ ty' ->
+ rnHsType syn_doc ty `thenRn` \ ty' ->
returnRn (TySynonym {tcdName = name', tcdTyVars = tyvars', tcdSynRhs = ty', tcdLoc = src_loc})
where
syn_doc = text "In the declaration for type synonym" <+> quotes (ppr name)
- -- For H98 we do *not* universally quantify on the RHS of a synonym
- -- Silently discard context... but the tyvars in the rest won't be in scope
- -- In interface files all types are quantified, so this is a no-op
- unquantify glaExts (HsForAllTy Nothing ctxt ty) | glaExts = ty
- unquantify glaExts ty = ty
-
rnTyClDecl (ClassDecl {tcdCtxt = context, tcdName = cname,
tcdTyVars = tyvars, tcdFDs = fds, tcdSigs = sigs,
tcdSysNames = names, tcdLoc = src_loc})