[project @ 2002-03-14 15:27:15 by simonpj]
[ghc-hetmet.git] / ghc / compiler / basicTypes / Name.lhs
index 79c9625..e3708ca 100644 (file)
@@ -10,19 +10,19 @@ module Name (
 
        -- The Name type
        Name,                                   -- Abstract
-       mkLocalName, mkSysLocalName, mkFCallName,
+       mkInternalName, mkSystemName, mkFCallName,
        mkIPName,
-       mkGlobalName, mkKnownKeyGlobal, mkWiredInName,
+       mkExternalName, mkKnownKeyExternalName, mkWiredInName,
 
        nameUnique, setNameUnique,
        nameOccName, nameModule, nameModule_maybe,
        setNameOcc, nameRdrName, setNameModuleAndLoc, 
        toRdrName, hashName, 
-       globaliseName, localiseName,
+       externaliseName, localiseName,
 
        nameSrcLoc, 
 
-       isSystemName, isLocalName, isGlobalName, isExternallyVisibleName,
+       isSystemName, isInternalName, isExternalName,
        isTyVarName, isDllName, 
        nameIsLocalOrFrom, isHomePackageName,
        
@@ -64,12 +64,12 @@ data Name = Name {
 -- the SrcLoc in a Name all that often.
 
 data NameSort
-  = Global Module      -- (a) TyCon, Class, their derived Ids, dfun Id
+  = External Module    -- (a) TyCon, Class, their derived Ids, dfun Id
                        -- (b) Imported Id
                        -- (c) Top-level Id in the original source, even if
                        --      locally defined
 
-  | Local              -- A user-defined Id or TyVar
+  | Internal           -- A user-defined Id or TyVar
                        -- defined in the module being compiled
 
   | System             -- A system-defined Id or TyVar.  Typically the
@@ -78,16 +78,16 @@ data NameSort
 
 Notes about the NameSorts:
 
-1.  Initially, top-level Ids (including locally-defined ones) get Global names, 
-    and all other local Ids get Local names
+1.  Initially, top-level Ids (including locally-defined ones) get External names, 
+    and all other local Ids get Internal names
 
-2.  Things with a @Global@ name are given C static labels, so they finally
+2.  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 @Global@ first.
+    must be made @External@ first.
 
-3.  In the tidy-core phase, a Global that is not visible to an importer
-    is changed to Local, and a Local that is visible is changed to Global
+3.  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:
        a) has unique attached when printing dumps
@@ -109,31 +109,30 @@ nameUnique  name = n_uniq name
 nameOccName name = n_occ  name
 nameSrcLoc  name = n_loc  name
 
-nameModule (Name { n_sort = Global mod }) = mod
+nameModule (Name { n_sort = External mod }) = mod
 nameModule name                                  = pprPanic "nameModule" (ppr name)
 
-nameModule_maybe (Name { n_sort = Global mod }) = Just mod
+nameModule_maybe (Name { n_sort = External mod }) = Just mod
 nameModule_maybe name                          = Nothing
 \end{code}
 
 \begin{code}
-nameIsLocalOrFrom      :: Module -> Name -> Bool
-isLocalName            :: Name -> Bool         -- Not globals
-isGlobalName           :: Name -> Bool
-isSystemName           :: Name -> Bool
-isExternallyVisibleName :: Name -> Bool
-isHomePackageName      :: Name -> Bool
+nameIsLocalOrFrom :: Module -> Name -> Bool
+isInternalName   :: Name -> Bool
+isExternalName   :: Name -> Bool
+isSystemName     :: Name -> Bool
+isHomePackageName :: Name -> Bool
 
-isGlobalName (Name {n_sort = Global _}) = True
-isGlobalName other                     = False
+isExternalName (Name {n_sort = External _}) = True
+isExternalName other                   = False
 
-isLocalName name = not (isGlobalName name)
+isInternalName name = not (isExternalName name)
 
-nameIsLocalOrFrom from (Name {n_sort = Global mod}) = mod == from
-nameIsLocalOrFrom from other                       = True
+nameIsLocalOrFrom from (Name {n_sort = External mod}) = mod == from
+nameIsLocalOrFrom from other                         = True
 
-isHomePackageName (Name {n_sort = Global mod}) = isHomeModule mod
-isHomePackageName other                               = True   -- Local and system names
+isHomePackageName (Name {n_sort = External mod}) = isHomeModule mod
+isHomePackageName other                                 = True         -- Internal and system names
 
 isDllName :: Name -> Bool      -- Does this name refer to something in a different DLL?
 isDllName nm = not opt_Static && not (isHomePackageName nm)
@@ -141,11 +140,6 @@ isDllName nm = not opt_Static && not (isHomePackageName nm)
 isTyVarName :: Name -> Bool
 isTyVarName name = isTvOcc (nameOccName name)
 
--- Global names are by definition those that are visible
--- outside the module, *as seen by the linker*.  Externally visible
--- does not mean visible at the source level
-isExternallyVisibleName name = isGlobalName name
-
 isSystemName (Name {n_sort = System}) = True
 isSystemName other                   = False
 \end{code}
@@ -158,8 +152,8 @@ isSystemName other                = False
 %************************************************************************
 
 \begin{code}
-mkLocalName :: Unique -> OccName -> SrcLoc -> Name
-mkLocalName uniq occ loc = Name { n_uniq = uniq, n_sort = Local, n_occ = occ, n_loc = loc }
+mkInternalName :: Unique -> OccName -> SrcLoc -> Name
+mkInternalName uniq occ loc = Name { n_uniq = uniq, n_sort = Internal, n_occ = occ, n_loc = loc }
        -- NB: You might worry that after lots of huffing and
        -- puffing we might end up with two local names with distinct
        -- uniques, but the same OccName.  Indeed we can, but that's ok
@@ -169,32 +163,32 @@ mkLocalName uniq occ loc = Name { n_uniq = uniq, n_sort = Local, n_occ = occ, n_
        --      * for interface files we tidyCore first, which puts the uniques
        --        into the print name (see setNameVisibility below)
 
-mkGlobalName :: Unique -> Module -> OccName -> SrcLoc -> Name
-mkGlobalName uniq mod occ loc = Name { n_uniq = uniq, n_sort = Global mod,
+mkExternalName :: Unique -> Module -> OccName -> SrcLoc -> Name
+mkExternalName uniq mod occ loc = Name { n_uniq = uniq, n_sort = External mod,
                                       n_occ = occ, n_loc = loc }
 
-mkKnownKeyGlobal :: RdrName -> Unique -> Name
-mkKnownKeyGlobal rdr_name uniq
-  = mkGlobalName uniq (mkVanillaModule (rdrNameModule rdr_name))
+mkKnownKeyExternalName :: RdrName -> Unique -> Name
+mkKnownKeyExternalName rdr_name uniq
+  = mkExternalName uniq (mkVanillaModule (rdrNameModule rdr_name))
                      (rdrNameOcc rdr_name)
                      builtinSrcLoc
 
 mkWiredInName :: Module -> OccName -> Unique -> Name
-mkWiredInName mod occ uniq = mkGlobalName uniq mod occ builtinSrcLoc
+mkWiredInName mod occ uniq = mkExternalName uniq mod occ builtinSrcLoc
 
-mkSysLocalName :: Unique -> EncodedFS -> Name
-mkSysLocalName uniq fs = Name { n_uniq = uniq, n_sort = System, 
+mkSystemName :: Unique -> EncodedFS -> Name
+mkSystemName uniq fs = Name { n_uniq = uniq, n_sort = System, 
                                n_occ = mkVarOcc fs, n_loc = noSrcLoc }
 
 mkFCallName :: Unique -> EncodedString -> Name
        -- The encoded string completely describes the ccall
-mkFCallName uniq str =  Name { n_uniq = uniq, n_sort = Local, 
+mkFCallName uniq str =  Name { n_uniq = uniq, n_sort = Internal, 
                               n_occ = mkFCallOcc str, n_loc = noSrcLoc }
 
 mkIPName :: Unique -> OccName -> Name
 mkIPName uniq occ
   = Name { n_uniq = uniq,
-          n_sort = Local,
+          n_sort = Internal,
           n_occ  = occ,
           n_loc = noSrcLoc }
 \end{code}
@@ -208,16 +202,16 @@ setNameUnique name uniq = name {n_uniq = uniq}
 setNameOcc :: Name -> OccName -> Name
 setNameOcc name occ = name {n_occ = occ}
 
-globaliseName :: Name -> Module -> Name
-globaliseName n mod = n { n_sort = Global mod }
+externaliseName :: Name -> Module -> Name
+externaliseName n mod = n { n_sort = External mod }
                                
 localiseName :: Name -> Name
-localiseName n = n { n_sort = Local }
+localiseName n = n { n_sort = Internal }
                                
 setNameModuleAndLoc :: Name -> Module -> SrcLoc -> Name
 setNameModuleAndLoc name mod loc = name {n_sort = set (n_sort name), n_loc = loc}
                       where
-                        set (Global _) = Global mod
+                        set (External _) = External mod
 \end{code}
 
 
@@ -233,10 +227,10 @@ hashName name = iBox (u2i (nameUnique name))
 
 
 nameRdrName :: Name -> RdrName
--- Makes a qualified name for top-level (Global) names, whether locally defined or not
--- and an unqualified name just for Locals
-nameRdrName (Name { n_occ = occ, n_sort = Global mod }) = mkRdrOrig (moduleName mod) occ
-nameRdrName (Name { n_occ = occ })                     = mkRdrUnqual occ
+-- Makes a qualified name for top-level (External) names, 
+-- whether locally defined or not and an unqualified name just for Internals
+nameRdrName (Name { n_occ = occ, n_sort = External mod }) = mkRdrOrig (moduleName mod) occ
+nameRdrName (Name { n_occ = occ })                       = mkRdrUnqual occ
 \end{code}
 
 
@@ -280,7 +274,7 @@ instance Binary Name where
   -- we must print these as RdrNames, because that's how they will be read in
   put_ bh Name {n_sort = sort, n_uniq = uniq, n_occ = occ} =
    case sort of
-    Global mod
+    External mod
        | this_mod == mod -> put_ bh (mkRdrUnqual occ)
        | otherwise       -> put_ bh (mkRdrOrig (moduleName mod) occ)
         where (this_mod,_,_,_) = getUserData bh
@@ -298,17 +292,17 @@ instance Binary Name where
 
 \begin{code}
 instance Outputable Name where
-       -- When printing interfaces, all Locals have been given nice print-names
+       -- When printing interfaces, all Internals have been given nice print-names
     ppr name = pprName name
 
 pprName name@(Name {n_sort = sort, n_uniq = uniq, n_occ = occ})
   = getPprStyle $ \ sty ->
     case sort of
-      Global mod -> pprGlobal sty name uniq mod occ
-      System     -> pprSysLocal sty uniq occ
-      Local      -> pprLocal sty uniq occ
+      External mod -> pprExternal sty name uniq mod occ
+      System       -> pprSystem sty uniq occ
+      Internal     -> pprInternal sty uniq occ
 
-pprGlobal sty name uniq mod occ
+pprExternal sty name uniq mod occ
   | codeStyle sty        = ppr (moduleName mod) <> char '_' <> pprOccName occ
 
   | debugStyle sty       = ppr (moduleName mod) <> dot <> pprOccName occ <> 
@@ -317,14 +311,14 @@ pprGlobal sty name uniq mod occ
   | unqualStyle sty name = pprOccName occ
   | otherwise           = ppr (moduleName mod) <> dot <> pprOccName occ
 
-pprLocal sty uniq occ
+pprInternal sty uniq occ
   | codeStyle sty  = pprUnique uniq
   | debugStyle sty = pprOccName occ <> 
                     text "{-" <> pprUnique uniq <> text "-}"
   | otherwise      = pprOccName occ    -- User and Iface styles
 
--- Like Local, except that we only omit the unique in Iface style
-pprSysLocal sty uniq occ
+-- Like Internal, except that we only omit the unique in Iface style
+pprSystem sty uniq occ
   | codeStyle sty  = pprUnique uniq
   | ifaceStyle sty = pprOccName occ    -- The tidy phase has ensured 
                                        -- that OccNames are enough