[Git][ghc/ghc][wip/int-index/term-capture] Fix bindHsQTyVars implicit variables scoping

Andrei Borzenkov (@sand-witch) gitlab at gitlab.haskell.org
Wed Aug 2 15:05:19 UTC 2023



Andrei Borzenkov pushed to branch wip/int-index/term-capture at Glasgow Haskell Compiler / GHC


Commits:
b24d9a71 by Andrei Borzenkov at 2023-08-02T19:04:50+04:00
Fix bindHsQTyVars implicit variables scoping

- - - - -


2 changed files:

- compiler/GHC/Rename/HsType.hs
- compiler/GHC/Rename/Module.hs


Changes:

=====================================
compiler/GHC/Rename/HsType.hs
=====================================
@@ -866,7 +866,7 @@ bindSigTyVarsFV tvs thing_inside
 ---------------
 bindHsQTyVars :: forall a b.
                  HsDocContext
-              -> Maybe a            -- Just _  => an associated type decl
+              -> Maybe (a, [Name])  -- Just _  => an associated type decl
               -> FreeKiTyVars       -- Kind variables from scope
               -> LHsQTyVars GhcPs
               -> (LHsQTyVars GhcRn -> FreeKiTyVars -> RnM (b, FreeVars))
@@ -887,14 +887,22 @@ bindHsQTyVars doc mb_assoc body_kv_occs hsq_bndrs thing_inside
 
        ; let -- See Note [bindHsQTyVars examples] for what
              -- all these various things are doing
-             bndrs, implicit_kvs' :: [LocatedN RdrName]
+             bndrs, all_implicit_kvs :: [LocatedN RdrName]
              bndrs        = map hsLTyVarLocName hs_tv_bndrs
-             implicit_kvs' = filterFreeVarsToBind bndrs $
+             all_implicit_kvs = filterFreeVarsToBind bndrs $
                bndr_kv_occs ++ body_kv_occs
              body_remaining = filterFreeVarsToBind bndr_kv_occs $
               filterFreeVarsToBind bndrs body_kv_occs
 
-       ; implicit_kvs <- filterInScopeM implicit_kvs'
+             tycl_bndrs = case mb_assoc of
+                Nothing -> emptyOccSet
+                Just (_, bndrs') -> mkOccSet (map nameOccName bndrs')
+             mentioned_tycl_bndrs = filter (\(L _ n) -> occName n `elemOccSet` tycl_bndrs) all_implicit_kvs
+
+
+       ; implicit_kvs' <- filterInScopeM all_implicit_kvs
+
+       ; let implicit_kvs = mentioned_tycl_bndrs ++ implicit_kvs'
 
        ; traceRn "checkMixedVars3" $
            vcat [ text "bndrs"   <+> ppr hs_tv_bndrs


=====================================
compiler/GHC/Rename/Module.hs
=====================================
@@ -850,10 +850,11 @@ rnDataFamInstDecl atfi (DataFamInstDecl { dfid_eqn =
 
 -- Rename associated type family decl in class
 rnATDecls :: Name      -- Class
+          -> [Name]
           -> [LFamilyDecl GhcPs]
           -> RnM ([LFamilyDecl GhcRn], FreeVars)
-rnATDecls cls at_decls
-  = rnList (rnFamDecl (Just cls)) at_decls
+rnATDecls cls bnrds at_decls
+  = rnList (rnFamDecl (Just (cls, bnrds))) at_decls
 
 rnATInstDecls :: (AssocTyFamInfo ->           -- The function that renames
                   decl GhcPs ->               -- an instance. rnTyFamInstDecl
@@ -1740,7 +1741,7 @@ rnTyClDecl (ClassDecl { tcdLayout = layout,
              { (context', cxt_fvs) <- rnMaybeContext cls_doc context
              ; fds'  <- rnFds fds
                          -- The fundeps have no free variables
-             ; (ats', fv_ats) <- rnATDecls cls' ats
+             ; (ats', fv_ats) <- rnATDecls cls' (hsAllLTyVarNames tyvars') ats
              ; let fvs = cxt_fvs     `plusFV`
                          fv_ats
              ; return ((tyvars', context', fds', ats'), fvs) }
@@ -2187,7 +2188,7 @@ rnLDerivStrategy doc mds thing_inside
       (thing, fvs) <- thing_inside
       pure (ds, thing, fvs)
 
-rnFamDecl :: Maybe Name -- Just cls => this FamilyDecl is nested
+rnFamDecl :: Maybe (Name, [Name]) -- Just cls => this FamilyDecl is nested
                         --             inside an *class decl* for cls
                         --             used for associated types
           -> FamilyDecl GhcPs



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b24d9a71e8e2d486eea6d7e8881d4debfe6fc9a5

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b24d9a71e8e2d486eea6d7e8881d4debfe6fc9a5
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230802/bf12cca4/attachment-0001.html>


More information about the ghc-commits mailing list