[project @ 2001-09-20 08:47:13 by simonpj]
authorsimonpj <unknown>
Thu, 20 Sep 2001 08:47:13 +0000 (08:47 +0000)
committersimonpj <unknown>
Thu, 20 Sep 2001 08:47:13 +0000 (08:47 +0000)
------------------------------
Fix a scoped-type-variable bug
------------------------------

MERGE WITH STABLE BRANCH

The bug caused an incorrect failure when the same type
variable was used more than once in a collection of patterns:

f (x :: t) (y :: t) = e

On the way, I eliminated bindNakedTyVarsFVRn, which was only
called once.

ghc/compiler/rename/RnEnv.lhs
ghc/compiler/rename/RnExpr.lhs

index ffcd10b..dda823b 100644 (file)
@@ -11,7 +11,7 @@ module RnEnv where            -- Export everything
 import {-# SOURCE #-} RnHiFiles
 
 import HsSyn
-import RdrHsSyn                ( RdrNameIE )
+import RdrHsSyn                ( RdrNameIE, RdrNameHsType, extractHsTyRdrTyVars )
 import RdrName         ( RdrName, rdrNameModule, rdrNameOcc, isQual, isUnqual, isOrig,
                          mkRdrUnqual, mkRdrQual, lookupRdrEnv, foldRdrEnv, rdrEnvToList,
                          unqualifyRdrName
@@ -607,15 +607,28 @@ bindTyVarsFV2Rn doc_str rdr_names enclosed_scope
     enclosed_scope names tyvars                `thenRn` \ (thing, fvs) ->
     returnRn (thing, delListFromNameSet fvs names)
 
-bindNakedTyVarsFVRn :: SDoc -> [RdrName]
-                   -> ([Name] -> RnMS (a, FreeVars))
-                   -> RnMS (a, FreeVars)
-bindNakedTyVarsFVRn doc_str tyvar_names enclosed_scope
-  = getSrcLocRn                                        `thenRn` \ loc ->
+bindPatSigTyVars :: [RdrNameHsType]
+                -> ([Name] -> RnMS (a, FreeVars))
+                -> RnMS (a, FreeVars)
+  -- Find the type variables in the pattern type 
+  -- signatures that must be brought into scope
+
+bindPatSigTyVars tys enclosed_scope
+  = getLocalNameEnv                    `thenRn` \ name_env ->
+    getSrcLocRn                                `thenRn` \ loc ->
     let
-       located_tyvars = [(tv, loc) | tv <- tyvar_names] 
+       forall_tyvars  = nub [ tv | ty <- tys,
+                                   tv <- extractHsTyRdrTyVars ty, 
+                                   not (tv `elemFM` name_env)
+                        ]
+               -- The 'nub' is important.  For example:
+               --      f (x :: t) (y :: t) = ....
+               -- We don't want to complain about binding t twice!
+
+       located_tyvars = [(tv, loc) | tv <- forall_tyvars] 
+       doc_sig        = text "In a pattern type-signature"
     in
-    bindLocatedLocalsRn doc_str located_tyvars $ \ names ->
+    bindLocatedLocalsRn doc_sig located_tyvars $ \ names ->
     enclosed_scope names                       `thenRn` \ (thing, fvs) ->
     returnRn (thing, delListFromNameSet fvs names)
 
index ce22f17..dba30bd 100644 (file)
@@ -199,22 +199,9 @@ rnMatch ctxt match@(Match _ pats maybe_rhs_sig grhss)
     
     returnRn (Match sig_tyvars pats' maybe_rhs_sig' grhss', all_fvs)
        -- The bindLocals and bindTyVars will remove the bound FVs
-
-
-bindPatSigTyVars :: [RdrNameHsType]
-                -> ([Name] -> RnMS (a, FreeVars))
-                -> RnMS (a, FreeVars)
-  -- Find the type variables in the pattern type 
-  -- signatures that must be brought into scope
-bindPatSigTyVars tys thing_inside
-  = getLocalNameEnv                    `thenRn` \ name_env ->
-    let
-       forall_tyvars  = [ tv | ty <- tys, tv <- extractHsTyRdrTyVars ty, not (tv `elemFM` name_env)]
-       doc_sig        = text "In a pattern type-signature"
-    in
-    bindNakedTyVarsFVRn doc_sig forall_tyvars thing_inside
 \end{code}
 
+
 %************************************************************************
 %*                                                                     *
 \subsubsection{Guarded right-hand sides (GRHSs)}