[commit: ghc] master: Comments about the Name Cache (507c897)
Simon Peyton Jones
simonpj at microsoft.com
Thu Jun 6 15:30:18 CEST 2013
Repository : http://darcs.haskell.org/ghc.git/
On branch : master
https://github.com/ghc/ghc/commit/507c89704aaab2ff6dff0bab850c625adf30115f
>---------------------------------------------------------------
commit 507c89704aaab2ff6dff0bab850c625adf30115f
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date: Thu May 9 18:10:08 2013 +0100
Comments about the Name Cache
>---------------------------------------------------------------
compiler/basicTypes/Name.lhs | 13 ++++++++++---
compiler/iface/IfaceEnv.lhs | 20 ++++++++++++++++++++
2 files changed, 30 insertions(+), 3 deletions(-)
diff --git a/compiler/basicTypes/Name.lhs b/compiler/basicTypes/Name.lhs
index e112625..55edc8d 100644
--- a/compiler/basicTypes/Name.lhs
+++ b/compiler/basicTypes/Name.lhs
@@ -135,15 +135,19 @@ Notes about the NameSorts:
1. Initially, top-level Ids (including locally-defined ones) get External names,
and all other local Ids get Internal names
-2. Things with a External name are given C static labels, so they finally
+2. In any invocation of GHC, an External Name for "M.x" has one and only one
+ unique. This unique association is ensured via the Name Cache;
+ see Note [The Name Cache] in IfaceEnv.
+
+3. Things with a External name are given C static labels, so they finally
appear in the .o file's symbol table. They appear in the symbol table
in the form M.n. If originally-local things have this property they
must be made @External@ first.
-3. In the tidy-core phase, a External that is not visible to an importer
+4. In the tidy-core phase, a External that is not visible to an importer
is changed to Internal, and a Internal that is visible is changed to External
-4. A System Name differs in the following ways:
+5. A System Name differs in the following ways:
a) has unique attached when printing dumps
b) unifier eliminates sys tyvars in favour of user provs where possible
@@ -272,6 +276,9 @@ mkDerivedInternalName derive_occ uniq (Name { n_occ = occ, n_loc = loc })
-- | Create a name which definitely originates in the given module
mkExternalName :: Unique -> Module -> OccName -> SrcSpan -> Name
+-- WATCH OUT! External Names should be in the Name Cache
+-- (see Note [The Name Cache] in IfaceEnv), so don't just call mkExternalName
+-- with some fresh unique without populating the Name Cache
mkExternalName uniq mod occ loc
= Name { n_uniq = getKeyFastInt uniq, n_sort = External mod,
n_occ = occ, n_loc = loc }
diff --git a/compiler/iface/IfaceEnv.lhs b/compiler/iface/IfaceEnv.lhs
index 20a21c3..0441fdb 100644
--- a/compiler/iface/IfaceEnv.lhs
+++ b/compiler/iface/IfaceEnv.lhs
@@ -55,10 +55,27 @@ import Data.IORef ( atomicModifyIORef, readIORef )
%* *
%*********************************************************
+Note [The Name Cache]
+~~~~~~~~~~~~~~~~~~~~~
+The Name Cache makes sure that, during any invovcation of GHC, each
+External Name "M.x" has one, and only one globally-agreed Unique.
+
+* The first time we come across M.x we make up a Unique and record that
+ association in the Name Cache.
+
+* When we come across "M.x" again, we look it up in the Name Cache,
+ and get a hit.
+
+The functions newGlobalBinder, allocateGlobalBinder do the main work.
+When you make an External name, you should probably be calling one
+of them.
+
+
\begin{code}
newGlobalBinder :: Module -> OccName -> SrcSpan -> TcRnIf a b Name
-- Used for source code and interface files, to make the
-- Name for a thing, given its Module and OccName
+-- See Note [The Name Cache]
--
-- The cache may already already have a binding for this thing,
-- because we may have seen an occurrence before, but now is the
@@ -74,6 +91,7 @@ allocateGlobalBinder
:: NameCache
-> Module -> OccName -> SrcSpan
-> (NameCache, Name)
+-- See Note [The Name Cache]
allocateGlobalBinder name_supply mod occ loc
= case lookupOrigNameCache (nsNames name_supply) mod occ of
-- A hit in the cache! We are at the binding site of the name.
@@ -171,6 +189,8 @@ lookupOrig mod occ
%* *
%************************************************************************
+See Note [The Name Cache] above.
+
\begin{code}
lookupOrigNameCache :: OrigNameCache -> Module -> OccName -> Maybe Name
lookupOrigNameCache _ mod occ
More information about the ghc-commits
mailing list