Skip to content

Commit

Permalink
Comments about the Name Cache
Browse files Browse the repository at this point in the history
  • Loading branch information
Simon Peyton Jones committed Jun 6, 2013
1 parent 99d4e5b commit 507c897
Show file tree
Hide file tree
Showing 2 changed files with 30 additions and 3 deletions.
13 changes: 10 additions & 3 deletions compiler/basicTypes/Name.lhs
Expand Up @@ -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

Expand Down Expand Up @@ -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 }
Expand Down
20 changes: 20 additions & 0 deletions compiler/iface/IfaceEnv.lhs
Expand Up @@ -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
Expand All @@ -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.
Expand Down Expand Up @@ -171,6 +189,8 @@ lookupOrig mod occ
%* *
%************************************************************************

See Note [The Name Cache] above.

\begin{code}
lookupOrigNameCache :: OrigNameCache -> Module -> OccName -> Maybe Name
lookupOrigNameCache _ mod occ
Expand Down

0 comments on commit 507c897

Please sign in to comment.