X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2FbasicTypes%2FName.lhs;h=303e0c749ac4cf2956a045aa77c1c5d5a4678dd0;hb=f6007733dc8e9a3f58c36e2bab97d2858d2b569a;hp=554c3bdc6ce65c68f50272f31c97d1712f37317a;hpb=5f67848a9c686f64bd4960a40a0e109f286df74b;p=ghc-hetmet.git diff --git a/ghc/compiler/basicTypes/Name.lhs b/ghc/compiler/basicTypes/Name.lhs index 554c3bd..303e0c7 100644 --- a/ghc/compiler/basicTypes/Name.lhs +++ b/ghc/compiler/basicTypes/Name.lhs @@ -10,48 +10,36 @@ module Name ( -- The Name type Name, -- Abstract - mkLocalName, mkImportedLocalName, mkSysLocalName, mkCCallName, - mkTopName, mkIPName, - mkDerivedName, mkGlobalName, mkKnownKeyGlobal, mkWiredInName, + mkLocalName, mkSysLocalName, mkFCallName, + mkIPName, + mkGlobalName, mkKnownKeyGlobal, mkWiredInName, - nameUnique, setNameUnique, setLocalNameSort, - tidyTopName, + nameUnique, setNameUnique, nameOccName, nameModule, nameModule_maybe, setNameOcc, nameRdrName, setNameModuleAndLoc, - toRdrName, hashName, + toRdrName, hashName, + globaliseName, localiseName, - isUserExportedName, - nameSrcLoc, nameIsLocallyDefined, isDllName, nameIsFrom, nameIsLocalOrFrom, + nameSrcLoc, isSystemName, isLocalName, isGlobalName, isExternallyVisibleName, - isTyVarName, + isTyVarName, isDllName, + nameIsLocalOrFrom, isHomePackageName, - -- Environment - NameEnv, mkNameEnv, - emptyNameEnv, unitNameEnv, nameEnvElts, - extendNameEnv_C, extendNameEnv, foldNameEnv, - plusNameEnv, plusNameEnv_C, extendNameEnv, extendNameEnvList, - lookupNameEnv, lookupNameEnv_NF, delFromNameEnv, elemNameEnv, - - -- Class NamedThing and overloaded friends NamedThing(..), - getSrcLoc, isLocallyDefined, getOccString, toRdrName, - isFrom, isLocalOrFrom + getSrcLoc, getOccString, toRdrName ) where #include "HsVersions.h" import OccName -- All of it -import Module ( Module, moduleName, mkVanillaModule, - printModulePrefix, isModuleInThisPackage ) -import RdrName ( RdrName, mkRdrQual, mkRdrUnqual, rdrNameOcc, rdrNameModule ) -import CmdLineOpts ( opt_Static, opt_OmitInterfacePragmas, opt_EnsureSplittableC ) +import Module ( Module, moduleName, mkVanillaModule, isHomeModule ) +import RdrName ( RdrName, mkRdrOrig, mkRdrUnqual, rdrNameOcc, rdrNameModule ) +import CmdLineOpts ( opt_Static ) import SrcLoc ( builtinSrcLoc, noSrcLoc, SrcLoc ) -import Unique ( Unique, Uniquable(..), u2i, pprUnique, pprUnique10 ) +import Unique ( Unique, Uniquable(..), u2i, pprUnique ) import FastTypes -import Maybes ( expectJust ) -import UniqFM import Outputable \end{code} @@ -71,11 +59,11 @@ data Name = Name { data NameSort = Global Module -- (a) TyCon, Class, their derived Ids, dfun Id - -- (b) imported Id + -- (b) Imported Id + -- (c) Top-level Id in the original source, even if + -- locally defined - | Exported -- An exported Ids defined in the module being compiled - - | Local -- A user-defined, but non-exported Id or TyVar, + | Local -- A user-defined Id or TyVar -- defined in the module being compiled | System -- A system-defined Id or TyVar. Typically the @@ -84,17 +72,18 @@ data NameSort Notes about the NameSorts: -1. An Exported Id is changed to Global right at the - end in the tidyCore pass, so that an importer sees a Global - Similarly, Local Ids that are visible to an importer (e.g. when - optimisation is on) are changed to Globals. +1. Initially, top-level Ids (including locally-defined ones) get Global names, + and all other local Ids get Local names 2. Things with a @Global@ 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. -3. A System Name differs in the following ways: +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 + +4. 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 @@ -122,39 +111,35 @@ nameModule_maybe name = Nothing \end{code} \begin{code} -nameIsLocallyDefined :: Name -> Bool -nameIsFrom :: Module -> Name -> Bool nameIsLocalOrFrom :: Module -> Name -> Bool -isUserExportedName :: Name -> Bool isLocalName :: Name -> Bool -- Not globals isGlobalName :: Name -> Bool isSystemName :: Name -> Bool isExternallyVisibleName :: Name -> Bool +isHomePackageName :: Name -> Bool isGlobalName (Name {n_sort = Global _}) = True isGlobalName other = False isLocalName name = not (isGlobalName name) -nameIsLocallyDefined name = isLocalName name - nameIsLocalOrFrom from (Name {n_sort = Global mod}) = mod == from nameIsLocalOrFrom from other = True -nameIsFrom from (Name {n_sort = Global mod}) = mod == from -nameIsFrom from other = pprPanic "nameIsFrom" (ppr other) +isHomePackageName (Name {n_sort = Global mod}) = isHomeModule mod +isHomePackageName other = True -- Local and system names + +isDllName :: Name -> Bool -- Does this name refer to something in a different DLL? +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 (that's isUserExported). +-- does not mean visible at the source level isExternallyVisibleName name = isGlobalName name --- Constructors, selectors and suchlike Globals, and are all exported --- Other Local things may or may not be exported -isUserExportedName (Name { n_sort = Exported }) = True -isUserExportedName (Name { n_sort = Global _ }) = True -isUserExportedName other = False - isSystemName (Name {n_sort = System}) = True isSystemName other = False \end{code} @@ -178,22 +163,9 @@ 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) -mkImportedLocalName :: Unique -> OccName -> SrcLoc -> Name - -- Just the same as mkLocalName, except the provenance is different - -- Reason: this flags the name as one that came in from an interface - -- file. This is useful when trying to decide which of two type - -- variables should 'win' when unifying them. - -- NB: this is only for non-top-level names, so we use ImplicitImport - -- - -- Oct 00: now that Names lack Provenances, mkImportedLocalName doesn't make - -- sense any more, so it's just the same as mkLocalName -mkImportedLocalName uniq occ loc = mkLocalName uniq occ loc - - mkGlobalName :: Unique -> Module -> OccName -> SrcLoc -> Name mkGlobalName uniq mod occ loc = Name { n_uniq = uniq, n_sort = Global mod, n_occ = occ, n_loc = loc } - mkKnownKeyGlobal :: RdrName -> Unique -> Name mkKnownKeyGlobal rdr_name uniq @@ -208,10 +180,10 @@ mkSysLocalName :: Unique -> UserFS -> Name mkSysLocalName uniq fs = Name { n_uniq = uniq, n_sort = System, n_occ = mkVarOcc fs, n_loc = noSrcLoc } -mkCCallName :: Unique -> EncodedString -> Name +mkFCallName :: Unique -> EncodedString -> Name -- The encoded string completely describes the ccall -mkCCallName uniq str = Name { n_uniq = uniq, n_sort = Local, - n_occ = mkCCallOcc str, n_loc = noSrcLoc } +mkFCallName uniq str = Name { n_uniq = uniq, n_sort = Local, + n_occ = mkFCallOcc str, n_loc = noSrcLoc } mkIPName :: Unique -> OccName -> Name mkIPName uniq occ @@ -219,14 +191,6 @@ mkIPName uniq occ n_sort = Local, n_occ = occ, n_loc = noSrcLoc } - ---------------------------------------------------------------------- -mkDerivedName :: (OccName -> OccName) - -> Name -- Base name - -> Unique -- New unique - -> Name -- Result is always a value name - -mkDerivedName f name uniq = name {n_uniq = uniq, n_occ = f (n_occ name)} \end{code} \begin{code} @@ -236,110 +200,21 @@ mkDerivedName f name uniq = name {n_uniq = uniq, n_occ = f (n_occ name)} setNameUnique name uniq = name {n_uniq = uniq} setNameOcc :: Name -> OccName -> Name - -- Give the thing a new OccName, *and* - -- record that it's no longer a sys-local - -- This is used by the tidy-up pass setNameOcc name occ = name {n_occ = occ} +globaliseName :: Name -> Module -> Name +globaliseName n mod = n { n_sort = Global mod } + +localiseName :: Name -> Name +localiseName n = n { n_sort = Local } + setNameModuleAndLoc :: Name -> Module -> SrcLoc -> Name setNameModuleAndLoc name mod loc = name {n_sort = set (n_sort name), n_loc = loc} where set (Global _) = Global mod - -setLocalNameSort :: Name -> Bool -> Name - -- Set the name's sort to Local or Exported, depending on the boolean -setLocalNameSort name is_exported = name { n_sort = if is_exported then Exported - else Local } -\end{code} - - -%************************************************************************ -%* * -\subsection{Tidying a name} -%* * -%************************************************************************ - -tidyTopName is applied to top-level names in the final program - -For top-level things, - it globalises Local names - (if all top-level things should be visible) - and localises non-exported Global names - (if only exported things should be visible) - -In all cases except an exported global, it gives it a new occurrence name. - -The "visibility" here concerns whether the .o file's symbol table -mentions the thing; if so, it needs a module name in its symbol. -The Global things are "visible" and the Local ones are not - -Why should things be "visible"? Certainly they must be if they -are exported. But also: - -(a) In certain (prelude only) modules we split up the .hc file into - lots of separate little files, which are separately compiled by the C - compiler. That gives lots of little .o files. The idea is that if - you happen to mention one of them you don't necessarily pull them all - in. (Pulling in a piece you don't need can be v bad, because it may - mention other pieces you don't need either, and so on.) - - Sadly, splitting up .hc files means that local names (like s234) are - now globally visible, which can lead to clashes between two .hc - files. So unlocaliseWhatnot goes through making all the local things - into global things, essentially by giving them full names so when they - are printed they'll have their module name too. Pretty revolting - really. - -(b) When optimisation is on we want to make all the internal - top-level defns externally visible - -\begin{code} -tidyTopName :: Module -> TidyOccEnv -> Name -> (TidyOccEnv, Name) -tidyTopName mod env - name@(Name { n_occ = occ, n_sort = sort, n_uniq = uniq, n_loc = loc }) - = case sort of - System -> localise -- System local Ids - Local -> localise -- User non-exported Ids - Exported -> globalise -- User-exported things - Global _ -> no_op -- Constructors, class selectors etc - - where - no_op = (env, name) - - globalise = (env, name { n_sort = Global mod }) -- Don't change occurrence name - - localise = (env', name') - (env', occ') = tidyOccName env occ - name' = name { n_occ = occ', n_sort = mkLocalTopSort mod } - -mkTopName :: Unique -> Module -> FAST_STRING -> Name - -- Make a top-level name; make it Global if top-level - -- things should be externally visible; Local otherwise - -- This chap is only used *after* the tidyCore phase - -- Notably, it is used during STG lambda lifting - -- - -- We have to make sure that the name is globally unique - -- and we don't have tidyCore to help us. So we append - -- the unique. Hack! Hack! - -- (Used only by the STG lambda lifter.) -mkTopName uniq mod fs - = Name { n_uniq = uniq, - n_sort = mkLocalTopSort mod, - n_occ = mkVarOcc (_PK_ ((_UNPK_ fs) ++ show uniq)), - n_loc = noSrcLoc } - -mkLocalTopSort :: Module -> NameSort -mkLocalTopSort mod - | all_toplev_ids_visible = Global mod - | otherwise = Local - -all_toplev_ids_visible - = not opt_OmitInterfacePragmas || -- Pragmas can make them visible - opt_EnsureSplittableC -- Splitting requires visiblilty \end{code} - %************************************************************************ %* * \subsection{Predicates and selectors} @@ -354,26 +229,8 @@ 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 }) = mkRdrQual (moduleName mod) occ +nameRdrName (Name { n_occ = occ, n_sort = Global mod }) = mkRdrOrig (moduleName mod) occ nameRdrName (Name { n_occ = occ }) = mkRdrUnqual occ - -ifaceNameRdrName :: Name -> RdrName --- Makes a qualified naem for imported things, --- and an unqualified one for local things -ifaceNameRdrName n | isLocallyDefined n = mkRdrUnqual (nameOccName n) - | otherwise = mkRdrQual (moduleName (nameModule n)) (nameOccName n) - -isDllName :: Name -> Bool - -- Does this name refer to something in a different DLL? -isDllName nm = not opt_Static && - not (nameIsLocallyDefined nm) && -- isLocallyDefinedName test needed 'cos - not (isModuleInThisPackage (nameModule nm)) -- nameModule won't work on local names - - - -isTyVarName :: Name -> Bool -isTyVarName name = isTvOcc (nameOccName name) - \end{code} @@ -409,50 +266,6 @@ instance NamedThing Name where %************************************************************************ %* * -\subsection{Name environment} -%* * -%************************************************************************ - -\begin{code} -type NameEnv a = UniqFM a -- Domain is Name - -emptyNameEnv :: NameEnv a -mkNameEnv :: [(Name,a)] -> NameEnv a -nameEnvElts :: NameEnv a -> [a] -extendNameEnv_C :: (a->a->a) -> NameEnv a -> Name -> a -> NameEnv a -extendNameEnv :: NameEnv a -> Name -> a -> NameEnv a -plusNameEnv :: NameEnv a -> NameEnv a -> NameEnv a -plusNameEnv_C :: (a->a->a) -> NameEnv a -> NameEnv a -> NameEnv a -extendNameEnvList:: NameEnv a -> [(Name,a)] -> NameEnv a -delFromNameEnv :: NameEnv a -> Name -> NameEnv a -elemNameEnv :: Name -> NameEnv a -> Bool -unitNameEnv :: Name -> a -> NameEnv a -lookupNameEnv :: NameEnv a -> Name -> Maybe a -lookupNameEnv_NF :: NameEnv a -> Name -> a -mapNameEnv :: (a->b) -> NameEnv a -> NameEnv b -foldNameEnv :: (a -> b -> b) -> b -> NameEnv a -> b - -emptyNameEnv = emptyUFM -foldNameEnv = foldUFM -mkNameEnv = listToUFM -nameEnvElts = eltsUFM -extendNameEnv_C = addToUFM_C -extendNameEnv = addToUFM -plusNameEnv = plusUFM -plusNameEnv_C = plusUFM_C -extendNameEnvList= addListToUFM -delFromNameEnv = delFromUFM -elemNameEnv = elemUFM -mapNameEnv = mapUFM -unitNameEnv = unitUFM - -lookupNameEnv = lookupUFM -lookupNameEnv_NF env n = expectJust "lookupNameEnv_NF" (lookupUFM env n) -\end{code} - - -%************************************************************************ -%* * \subsection{Pretty printing} %* * %************************************************************************ @@ -462,33 +275,39 @@ instance Outputable Name where -- When printing interfaces, all Locals have been given nice print-names ppr name = pprName name -pprName (Name {n_sort = sort, n_uniq = uniq, n_occ = occ}) +pprName name@(Name {n_sort = sort, n_uniq = uniq, n_occ = occ}) = getPprStyle $ \ sty -> case sort of - Global mod -> pprGlobal sty uniq mod occ + Global mod -> pprGlobal sty name uniq mod occ System -> pprSysLocal sty uniq occ - Local -> pprLocal sty uniq occ empty - Exported -> pprLocal sty uniq occ (char 'x') + Local -> pprLocal sty uniq occ -pprLocal sty uniq occ pp_export +pprGlobal sty name uniq mod occ + | codeStyle sty = ppr (moduleName mod) <> char '_' <> pprOccName occ + + | debugStyle sty = ppr (moduleName mod) <> dot <> pprOccName occ <> + text "{-" <> pprUnique uniq <> text "-}" + + | unqualStyle sty name = pprOccName occ + | otherwise = ppr (moduleName mod) <> dot <> pprOccName occ + +pprLocal sty uniq occ | codeStyle sty = pprUnique uniq | debugStyle sty = pprOccName occ <> - text "{-" <> pp_export <+> pprUnique10 uniq <> text "-}" - | otherwise = pprOccName occ - -pprGlobal sty uniq mod occ - | codeStyle sty = ppr (moduleName mod) <> char '_' <> pprOccName occ - | debugStyle sty = ppr (moduleName mod) <> dot <> pprOccName occ <> - text "{-" <> pprUnique10 uniq <> text "-}" - | printModulePrefix mod = ppr (moduleName mod) <> dot <> pprOccName occ - | otherwise = 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 | codeStyle sty = pprUnique uniq + | ifaceStyle sty = pprOccName occ -- The tidy phase has ensured that OccNames + -- are enough | otherwise = pprOccName occ <> char '_' <> pprUnique uniq + -- If the tidy phase hasn't run, the OccName + -- is unlikely to be informative (like 's'), + -- so print the unique \end{code} - %************************************************************************ %* * \subsection{Overloaded functions related to Names} @@ -505,20 +324,11 @@ class NamedThing a where \begin{code} getSrcLoc :: NamedThing a => a -> SrcLoc -isLocallyDefined :: NamedThing a => a -> Bool getOccString :: NamedThing a => a -> String toRdrName :: NamedThing a => a -> RdrName -isFrom :: NamedThing a => Module -> a -> Bool -isLocalOrFrom :: NamedThing a => Module -> a -> Bool getSrcLoc = nameSrcLoc . getName -isLocallyDefined = nameIsLocallyDefined . getName getOccString = occNameString . getOccName -toRdrName = ifaceNameRdrName . getName -isFrom mod x = nameIsFrom mod (getName x) -isLocalOrFrom mod x = nameIsLocalOrFrom mod ( getName x) +toRdrName = nameRdrName . getName \end{code} -\begin{code} -{-# SPECIALIZE isLocallyDefined :: Name -> Bool #-} -\end{code}