[Git][ghc/ghc][wip/spj-wibbles] Remove an incorrect WARN in extendLocalRdrEnv
Simon Peyton Jones
gitlab at gitlab.haskell.org
Thu Jul 23 13:01:24 UTC 2020
Simon Peyton Jones pushed to branch wip/spj-wibbles at Glasgow Haskell Compiler / GHC
Commits:
a81a9a72 by Simon Peyton Jones at 2020-07-23T14:00:19+01:00
Remove an incorrect WARN in extendLocalRdrEnv
I noticed this warning going off, and discovered that it's
really fine. This small patch removes the warning, and docments
what is going on.
- - - - -
2 changed files:
- compiler/GHC/Rename/Pat.hs
- compiler/GHC/Types/Name/Reader.hs
Changes:
=====================================
compiler/GHC/Rename/Pat.hs
=====================================
@@ -236,19 +236,25 @@ newPatName (LetMk is_top fix_env) rdr_name
do { name <- case is_top of
NotTopLevel -> newLocalBndrRn rdr_name
TopLevel -> newTopSrcBinder rdr_name
- ; bindLocalNames [name] $ -- Do *not* use bindLocalNameFV here
- -- See Note [View pattern usage]
+ ; bindLocalNames [name] $
+ -- Do *not* use bindLocalNameFV here;
+ -- see Note [View pattern usage]
+ -- For the TopLevel case
+ -- see Note [bindLocalNames for an External name]
addLocalFixities fix_env [name] $
thing_inside name })
- -- Note: the bindLocalNames is somewhat suspicious
- -- because it binds a top-level name as a local name.
- -- however, this binding seems to work, and it only exists for
- -- the duration of the patterns and the continuation;
- -- then the top-level name is added to the global env
- -- before going on to the RHSes (see GHC.Rename.Module).
+{- Note [bindLocalNames for an External name]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+The use of bindLocalNames is somewhat suspicious
+ because it binds a top-level External name in the LocalRdrEnv.
+ c.f. Note [LocalRdrEnv] in GHC.Types.Name.Reader.
+
+ However, this odd binding seems to work, and it only exists for
+ the duration of the patterns and the continuation;
+ then the top-level name is added to the global env
+ before going on to the RHSes (see GHC.Rename.Module).
-{-
Note [View pattern usage]
~~~~~~~~~~~~~~~~~~~~~~~~~
Consider
=====================================
compiler/GHC/Types/Name/Reader.hs
=====================================
@@ -338,13 +338,24 @@ instance Ord RdrName where
************************************************************************
-}
+{- Note [LocalRdrEnv]
+~~~~~~~~~~~~~~~~~~~~~
+The LocalRdrEnv is used to store local bindings (let, where, lambda, case).
+
+* It is keyed by OccName, because we never use it for qualified names.
+
+* It maps the OccName to a Name. That Name is almost always an
+ Internal Name, but (hackily) it can be External too for top-level
+ pattern bindings. See Note [bindLocalNames for an External name]
+ in GHC.Rename.Pat
+
+* We keep the current mapping (lre_env), *and* the set of all Names in
+ scope (lre_in_scope). Reason: see Note [Splicing Exact names] in
+ GHC.Rename.Env.
+-}
+
-- | Local Reader Environment
---
--- This environment is used to store local bindings
--- (@let@, @where@, lambda, @case@).
--- It is keyed by OccName, because we never use it for qualified names
--- We keep the current mapping, *and* the set of all Names in scope
--- Reason: see Note [Splicing Exact names] in "GHC.Rename.Env"
+-- See Note [LocalRdrEnv]
data LocalRdrEnv = LRE { lre_env :: OccEnv Name
, lre_in_scope :: NameSet }
@@ -364,16 +375,15 @@ emptyLocalRdrEnv = LRE { lre_env = emptyOccEnv
, lre_in_scope = emptyNameSet }
extendLocalRdrEnv :: LocalRdrEnv -> Name -> LocalRdrEnv
--- The Name should be a non-top-level thing
+-- See Note [LocalRdrEnv]
extendLocalRdrEnv lre@(LRE { lre_env = env, lre_in_scope = ns }) name
- = WARN( isExternalName name, ppr name )
- lre { lre_env = extendOccEnv env (nameOccName name) name
+ = lre { lre_env = extendOccEnv env (nameOccName name) name
, lre_in_scope = extendNameSet ns name }
extendLocalRdrEnvList :: LocalRdrEnv -> [Name] -> LocalRdrEnv
+-- See Note [LocalRdrEnv]
extendLocalRdrEnvList lre@(LRE { lre_env = env, lre_in_scope = ns }) names
- = WARN( any isExternalName names, ppr names )
- lre { lre_env = extendOccEnvList env [(nameOccName n, n) | n <- names]
+ = lre { lre_env = extendOccEnvList env [(nameOccName n, n) | n <- names]
, lre_in_scope = extendNameSetList ns names }
lookupLocalRdrEnv :: LocalRdrEnv -> RdrName -> Maybe Name
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a81a9a729f9d18d2576d4026ff955fce1253dbd2
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a81a9a729f9d18d2576d4026ff955fce1253dbd2
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/20200723/05953f8d/attachment-0001.html>
More information about the ghc-commits
mailing list