[[project @ 2002-03-14 15:26:53 by simonpj] simonpj**20020314152654 Lots of stuff about external and internal names ] { addfile ./ghc/docs/comm/the-beast/names.html hunk ./ghc/docs/comm/index.html 59 +
+
+
+Every entity (type constructor, class, identifier, type variable) has
+a Name
. The Name
type is pervasive in GHC,
+and is defined in basicTypes/Name.lhs
. Here is what a Name looks like,
+though it is private to the Name module.
+
+ data Name = Name { + n_sort :: NameSort, -- What sort of name it is + n_occ :: !OccName, -- Its occurrence name + n_uniq :: Unique, -- Its identity + n_loc :: !SrcLoc -- Definition site + } ++ +
n_sort
field says what sort of name this is: see
+NameSort below.
+n_occ
field gives the "occurrence name" of the Name; see
+OccName below.
+n_uniq
field allows fast tests for equality of Names.
+n_loc
field gives some indication of where the name was bound.
+NameSort
of a Name
Name
:
++ data NameSort + = External Module + | Internal + | System ++ +
ExternalName
has a globally-unique
+(module name,occurrence name) pair, namely the
+original name of the entity,
+describing where the thing was originally defined. So for example,
+if we have
++ module M where + f = e1 + g = e2 + + module A where + import qualified M as Q + import M + a = Q.f + g ++then the RdrNames for "a", "Q.f" and "g" get replaced (by the Renamer) +by the Names "A.a", "M.f", and "M.g" respectively. + +
InternalName
+has only an occurrence name. Distinct InternalNames may have the same occurrence
+name; use the Unique to distinguish them.
+
+
ExternalName
has a unique that never changes. It is never
+cloned. This is important, because the simplifier invents new names pretty freely,
+but we don't want to lose the connnection with the type environment (constructed earlier).
+An InternalName
name can be cloned freely.
+
+ExternalNames
, whereas extra
+top-level bindings generated (say) by the type checker get InternalNames
.
+This distinction is occasionally useful for filtering diagnostic output; e.g.
+for -ddump-types.
+
+ExternalName
will generate symbols that
+appear as external symbols in the object file. An Id with an InternalName
+cannot be referenced from outside the module, and so generates a local symbol in
+the object file. The CoreTidy pass makes the decision about which names should
+be External and which Internal.
+
+System
name is for the most part the same as an
+Internal
. Indeed, the differences are purely cosmetic:
+OccName
OccName
is more-or-less just a string, like "foo" or "Tree",
+giving the (unqualified) name of an entity.
+
+Well, not quite just a string, because in Haskell a name like "C" could mean a type
+constructor or data constructor, depending on context. So GHC defines a type
+OccName (defined in basicTypes/OccName.lhs) that is a pair of
+a FastString and a NameSpace indicating which name space the
+name is drawn from:
++ data OccName = OccName NameSpace EncodedFS ++The EncodedFS is a synonym for FastString indicating that the +string is Z-encoded. (Details in OccName.lhs.) Z-encoding encodes +funny characters like '%' and '$' into alphabetic characters, like "zp" and "zd", +so that they can be used in object-file symbol tables without confusing linkers +and suchlike. + +
+The name spaces are: +
- data OccName = OccName NameSpace EncodedFS --The EncodedFS is a synonym for FastString indicating that the -string is Z-encoded. (Details in OccName.lhs.) -
-The name spaces are: -
hunk ./ghc/docs/comm/the-beast/renamer.html 43 -
-On the other hand, a Name: -
- module M where - f = e1 - g = e2 - - module A where - import qualified M as Q - import M - a = Q.f + g --then the RdrNames for "a", "Q.f" and "g" get replaced by the Names -"A.a", "M.f", and "M.g" respectively. -
-Names come in two flavours: Local and Global. The Global kind contain
-both a Module and an OccName
-Not all Names are qualifed. Local (e.g. lambda-bound) names are given Local Names
hunk ./ghc/docs/comm/the-beast/vars.html 29
-its unique number, and its print-name. The unique number is cached in the
-realUnique
field, just to make comparison of Var
s a little faster.
+its unique number, and its print-name. See "The truth about names".
hunk ./ghc/docs/comm/the-beast/vars.html 31
-
Type
field gives the type of a term variable, or the kind of a
+realUnique
field caches the unique number in the
+varName
field, just to make comparison of Var
s a little faster.
+
+varType
field gives the type of a term variable, or the kind of a
hunk ./ghc/docs/comm/the-beast/vars.html 62
+
hunk ./ghc/docs/comm/the-beast/vars.html 212
-Name
sLocal
or Global
Name
:
+not the same as whether the Id has an ExternaName
or an InternalName
+(see "The truth about Names"):
hunk ./ghc/docs/comm/the-beast/vars.html 218
-GlobalId
has a Global
Name
.
+GlobalId
has an ExternalName
.
hunk ./ghc/docs/comm/the-beast/vars.html 221
-The significance of Global vs Local names is this:
-Global
Name has a module and occurrence name; a Local
-has only an occurrence name.
-
Global
Name has a unique that never changes. It is never
-cloned. This is important, because the simplifier invents new names pretty freely,
-but we don't want to lose the connnection with the type environment (constructed earlier).
-A Local
name can be cloned freely.
-