X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2FbasicTypes%2FName.lhs;h=1a0e155c8ad3e8603e4f59f7eb83c2f001a4e2e8;hb=8dc4c737e119c8c1b803942020c399ffb300a8a2;hp=bfdd645c9cbde1887ecdf6ceed59108ac31d2fc0;hpb=b70e2f9494a0206e5102a54de39c3c7f78554095;p=ghc-hetmet.git diff --git a/ghc/compiler/basicTypes/Name.lhs b/ghc/compiler/basicTypes/Name.lhs index bfdd645..1a0e155 100644 --- a/ghc/compiler/basicTypes/Name.lhs +++ b/ghc/compiler/basicTypes/Name.lhs @@ -10,49 +10,49 @@ module Name ( -- The Name type Name, -- Abstract - mkLocalName, mkSysLocalName, mkTopName, - mkDerivedName, mkGlobalName, - mkWiredInIdName, mkWiredInTyConName, - maybeWiredInIdName, maybeWiredInTyConName, - isWiredInName, + mkLocalName, mkSysLocalName, mkCCallName, + mkTopName, mkIPName, + mkDerivedName, mkGlobalName, mkKnownKeyGlobal, mkWiredInName, - nameUnique, setNameUnique, setNameProvenance, getNameProvenance, setNameImportReason, + nameUnique, setNameUnique, tidyTopName, - nameOccName, nameModule, setNameOcc, nameRdrName, setNameModule, + nameOccName, nameModule, nameModule_maybe, + setNameOcc, nameRdrName, setNameModuleAndLoc, + toRdrName, hashName, - isExportedName, nameSrcLoc, - isLocallyDefinedName, + nameSrcLoc, nameIsLocallyDefined, isDllName, nameIsFrom, nameIsLocalOrFrom, isSystemName, isLocalName, isGlobalName, isExternallyVisibleName, + isTyVarName, + + -- Environment + NameEnv, mkNameEnv, + emptyNameEnv, unitNameEnv, nameEnvElts, + extendNameEnv_C, extendNameEnv, foldNameEnv, + plusNameEnv, plusNameEnv_C, extendNameEnv, extendNameEnvList, + lookupNameEnv, lookupNameEnv_NF, delFromNameEnv, elemNameEnv, - -- Provenance - Provenance(..), ImportReason(..), pprProvenance, - ExportFlag(..), PrintUnqualified, - pprNameProvenance, systemProvenance, - -- Class NamedThing and overloaded friends NamedThing(..), - isExported, - getSrcLoc, isLocallyDefined, getOccString + getSrcLoc, getOccString, toRdrName, + isFrom, isLocalOrFrom ) where #include "HsVersions.h" -import {-# SOURCE #-} Var ( Id, setIdName ) -import {-# SOURCE #-} TyCon ( TyCon, setTyConName ) - import OccName -- All of it -import RdrName ( RdrName, mkRdrQual, mkRdrUnqual ) -import CmdLineOpts ( opt_PprStyle_NoPrags, opt_OmitInterfacePragmas, opt_EnsureSplittableC ) - -import SrcLoc ( noSrcLoc, mkBuiltinSrcLoc, SrcLoc ) -import Unique ( pprUnique, Unique, Uniquable(..) ) +import Module ( Module, moduleName, mkVanillaModule, isModuleInThisPackage ) +import RdrName ( RdrName, mkRdrOrig, mkRdrUnqual, rdrNameOcc, rdrNameModule ) +import CmdLineOpts ( opt_Static, opt_OmitInterfacePragmas, opt_EnsureSplittableC ) +import SrcLoc ( builtinSrcLoc, noSrcLoc, SrcLoc ) +import Unique ( Unique, Uniquable(..), u2i, pprUnique, pprUnique10 ) +import FastTypes +import Maybes ( expectJust ) +import UniqFM import Outputable -import GlaExts \end{code} - %************************************************************************ %* * \subsection[Name-datatype]{The @Name@ datatype, and name construction} @@ -62,27 +62,105 @@ import GlaExts \begin{code} data Name = Name { n_sort :: NameSort, -- What sort of name it is - n_uniq :: Unique, n_occ :: OccName, -- Its occurrence name - n_prov :: Provenance -- How it was made + n_uniq :: Unique, + n_loc :: SrcLoc -- Definition site } data NameSort - = Local - | Global Module - | WiredInId Module Id - | WiredInTyCon Module TyCon + = Global 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 + -- defined in the module being compiled + + | System -- A system-defined Id or TyVar. Typically the + -- OccName is very uninformative (like 's') \end{code} -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. +Notes about the NameSorts: + +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. 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 + + Before anything gets printed in interface files or output code, it's + fed through a 'tidy' processor, which zaps the OccNames to have + unique names; and converts all sys-locals to user locals + If any desugarer sys-locals have survived that far, they get changed to + "ds1", "ds2", etc. + +\begin{code} +nameUnique :: Name -> Unique +nameOccName :: Name -> OccName +nameModule :: Name -> Module +nameSrcLoc :: Name -> SrcLoc + +nameUnique name = n_uniq name +nameOccName name = n_occ name +nameSrcLoc name = n_loc name + +nameModule (Name { n_sort = Global mod }) = mod +nameModule name = pprPanic "nameModule" (ppr name) + +nameModule_maybe (Name { n_sort = Global mod }) = Just mod +nameModule_maybe name = Nothing +\end{code} + +\begin{code} +nameIsLocallyDefined :: Name -> Bool +nameIsFrom :: Module -> Name -> Bool +nameIsLocalOrFrom :: Module -> Name -> Bool +isLocalName :: Name -> Bool -- Not globals +isGlobalName :: Name -> Bool +isSystemName :: Name -> Bool +isExternallyVisibleName :: 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) + +-- 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} + + +%************************************************************************ +%* * +\subsection{Making names} +%* * +%************************************************************************ \begin{code} mkLocalName :: Unique -> OccName -> SrcLoc -> Name -mkLocalName uniq occ loc = Name { n_uniq = uniq, n_sort = Local, n_occ = occ, - n_prov = LocalDef loc NotExported } +mkLocalName uniq occ loc = Name { n_uniq = uniq, n_sort = Local, 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 @@ -92,44 +170,35 @@ mkLocalName uniq occ loc = Name { n_uniq = uniq, n_sort = Local, n_occ = occ, -- * for interface files we tidyCore first, which puts the uniques -- into the print name (see setNameVisibility below) -mkGlobalName :: Unique -> Module -> OccName -> Provenance -> Name -mkGlobalName uniq mod occ prov = Name { n_uniq = uniq, n_sort = Global mod, - n_occ = occ, n_prov = prov } +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 } -mkSysLocalName :: Unique -> FAST_STRING -> Name -mkSysLocalName uniq fs = Name { n_uniq = uniq, n_sort = Local, - n_occ = mkSrcVarOcc fs, n_prov = SystemProv } - -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! -mkTopName uniq mod fs - = Name { n_uniq = uniq, - n_sort = mk_top_sort mod, - n_occ = mkSrcVarOcc (_PK_ ((_UNPK_ fs) ++ show uniq)), - n_prov = LocalDef noSrcLoc NotExported } +mkKnownKeyGlobal :: RdrName -> Unique -> Name +mkKnownKeyGlobal rdr_name uniq + = mkGlobalName uniq (mkVanillaModule (rdrNameModule rdr_name)) + (rdrNameOcc rdr_name) + builtinSrcLoc -------------------------- Wired in names ------------------------- +mkWiredInName :: Module -> OccName -> Unique -> Name +mkWiredInName mod occ uniq = mkGlobalName uniq mod occ builtinSrcLoc -mkWiredInIdName :: Unique -> Module -> OccName -> Id -> Name -mkWiredInIdName uniq mod occ id = Name { n_uniq = uniq, n_sort = WiredInId mod id, - n_occ = occ, n_prov = SystemProv } +mkSysLocalName :: Unique -> UserFS -> Name +mkSysLocalName uniq fs = Name { n_uniq = uniq, n_sort = System, + n_occ = mkVarOcc fs, n_loc = noSrcLoc } --- mkWiredInTyConName takes a FAST_STRING instead of --- an OccName, which is a bit yukky but that's what the --- clients find easiest. -mkWiredInTyConName :: Unique -> Module -> FAST_STRING -> TyCon -> Name -mkWiredInTyConName uniq mod fs tycon - = Name { n_uniq = uniq, n_sort = WiredInTyCon mod tycon, - n_occ = mkSrcOccFS tcName fs, n_prov = SystemProv } +mkCCallName :: 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 } +mkIPName :: Unique -> OccName -> Name +mkIPName uniq occ + = Name { n_uniq = uniq, + n_sort = Local, + n_occ = occ, + n_loc = noSrcLoc } --------------------------------------------------------------------- mkDerivedName :: (OccName -> OccName) @@ -138,7 +207,9 @@ mkDerivedName :: (OccName -> OccName) -> 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} -- When we renumber/rename things, we need to be -- able to change a Name's Unique to match the cached -- one in the thing it's the name of. If you know what I mean. @@ -150,27 +221,26 @@ setNameOcc :: Name -> OccName -> Name -- This is used by the tidy-up pass setNameOcc name occ = name {n_occ = occ} -setNameModule :: Name -> Module -> Name -setNameModule name mod = name {n_sort = set (n_sort name)} +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 (WiredInId _ id) = WiredInId mod id - set (WiredInTyCon _ tycon) = WiredInTyCon mod tycon + set (Global _) = Global mod \end{code} %************************************************************************ %* * -\subsection{Setting provenance and visibility +\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) +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. @@ -199,146 +269,48 @@ are exported. But also: top-level defns externally visible \begin{code} -tidyTopName :: Module -> TidyOccEnv -> Name -> (TidyOccEnv, Name) -tidyTopName mod env name - | isExported name = (env, name) -- Don't fiddle with an exported name - -- It should be in the TidyOccEnv already - | otherwise = (env', name') +tidyTopName :: Module -> TidyOccEnv -> Bool -> Name -> (TidyOccEnv, Name) +tidyTopName mod env is_exported + name@(Name { n_occ = occ, n_sort = sort, n_uniq = uniq, n_loc = loc }) + = case sort of + Global _ | is_exported -> (env, name) + | otherwise -> (env, name { n_sort = new_sort }) + -- Don't change the occurrnce names of globals, because many of them + -- are bound by either a class declaration or a data declaration + -- or an explicit user export. + + other | is_exported -> (env', name { n_sort = Global mod, n_occ = occ' }) + | otherwise -> (env', name { n_sort = new_sort, n_occ = occ' }) where - (env', occ') = tidyOccName env (n_occ name) - - name' = Name { n_uniq = n_uniq name, n_sort = mk_top_sort mod, - n_occ = occ', n_prov = LocalDef noSrcLoc NotExported } - -mk_top_sort mod | all_toplev_ids_visible = Global mod - | otherwise = Local + (env', occ') = tidyOccName env occ + new_sort = mkLocalTopSort mod -all_toplev_ids_visible = - not opt_OmitInterfacePragmas || -- Pragmas can make them visible - opt_EnsureSplittableC -- Splitting requires visiblilty -\end{code} - -\begin{code} -setNameProvenance :: Name -> Provenance -> Name - -- setNameProvenance used to only change the provenance of - -- Implicit-provenance things, but that gives bad error messages - -- for names defined twice in the same module, so I changed it to - -- set the provenance of *any* global (SLPJ Jun 97) -setNameProvenance name prov = name {n_prov = prov} - -getNameProvenance :: Name -> Provenance -getNameProvenance name = n_prov name - -setNameImportReason :: Name -> ImportReason -> Name -setNameImportReason name reason - = name { n_prov = new_prov } - where - -- It's important that we don't do the pattern matching - -- in the top-level clause, else we get a black hole in - -- the renamer. Rather a yukky constraint. There's only - -- one call, in RnNames - old_prov = n_prov name - new_prov = case old_prov of - NonLocalDef _ omit -> NonLocalDef reason omit - other -> old_prov -\end{code} - - -%************************************************************************ -%* * -\subsection{Provenance and export info} -%* * -%************************************************************************ - -\begin{code} -data Provenance - = LocalDef -- Defined locally - SrcLoc -- Defn site - ExportFlag -- Whether it's exported - - | NonLocalDef -- Defined non-locally - ImportReason - PrintUnqualified - - | SystemProv -- Either (a) a system-generated local with - -- a v short name OccName - -- or (b) a known-key global which should have a proper - -- provenance attached by the renamer -\end{code} - -Sys-provs are only used internally. When the compiler generates (say) -a fresh desguar variable it always calls it "ds", and of course it gets -a fresh unique. But when printing -ddump-xx dumps, we must print it with -its unique, because there'll be a lot of "ds" variables. - -Names with SystemProv differ in the following ways: - a) locals have unique attached when printing dumps - b) unifier eliminates sys tyvars in favour of user provs where possible - c) renamer replaces SystemProv with a better one - -Before anything gets printed in interface files or output code, it's -fed through a 'tidy' processor, which zaps the OccNames to have -unique names; and converts all sys-locals to user locals -If any desugarer sys-locals have survived that far, they get changed to -"ds1", "ds2", etc. - -\begin{code} -data ImportReason - = UserImport Module SrcLoc Bool -- Imported from module M on line L - -- Note the M may well not be the defining module - -- for this thing! - -- The Bool is true iff the thing was named *explicitly* in the import spec, - -- rather than being imported as part of a group; e.g. - -- import B - -- import C( T(..) ) - -- Here, everything imported by B, and the constructors of T - -- are not named explicitly; only T is named explicitly. - -- This info is used when warning of unused names. - - | ImplicitImport -- Imported implicitly for some other reason - - -type PrintUnqualified = Bool -- True <=> the unqualified name of this thing is - -- in scope in this module, so print it - -- unqualified in error messages - -data ExportFlag = Exported | NotExported +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} -Something is "Exported" if it may be mentioned by another module without -warning. The crucial thing about Exported things is that they must -never be dropped as dead code, even if they aren't used in this module. -Furthermore, being Exported means that we can't see all call sites of the thing. - -Exported things include: - - - explicitly exported Ids, including data constructors, - class method selectors - - - dfuns from instance decls - -Being Exported is *not* the same as finally appearing in the .o file's -symbol table. For example, a local Id may be mentioned in an Exported -Id's unfolding in the interface file, in which case the local Id goes -out too. - - -\begin{code} -systemProvenance :: Provenance -systemProvenance = SystemProv - --- pprNameProvenance is used in error messages to say where a name came from -pprNameProvenance :: Name -> SDoc -pprNameProvenance name = pprProvenance (getNameProvenance name) - -pprProvenance :: Provenance -> SDoc -pprProvenance SystemProv = ptext SLIT("System") -pprProvenance (LocalDef loc _) = ptext SLIT("defined at") <+> ppr loc -pprProvenance (NonLocalDef ImplicitImport _) - = ptext SLIT("implicitly imported") -pprProvenance (NonLocalDef (UserImport mod loc _) _) - = ptext SLIT("imported from") <+> ppr mod <+> ptext SLIT("at") <+> ppr loc -\end{code} %************************************************************************ @@ -348,75 +320,27 @@ pprProvenance (NonLocalDef (UserImport mod loc _) _) %************************************************************************ \begin{code} -nameUnique :: Name -> Unique -nameOccName :: Name -> OccName -nameModule :: Name -> Module -nameSrcLoc :: Name -> SrcLoc -isLocallyDefinedName :: Name -> Bool -isExportedName :: Name -> Bool -isWiredInName :: Name -> Bool -isLocalName :: Name -> Bool -isGlobalName :: Name -> Bool -isExternallyVisibleName :: Name -> Bool - - +hashName :: Name -> Int +hashName name = iBox (u2i (nameUnique name)) -nameUnique name = n_uniq name -nameOccName name = n_occ name - -nameModule name = nameSortModule (n_sort name) - -nameSortModule (Global mod) = mod -nameSortModule (WiredInId mod _) = mod -nameSortModule (WiredInTyCon mod _) = mod nameRdrName :: Name -> RdrName -nameRdrName (Name { n_sort = Local, n_occ = occ }) = mkRdrUnqual occ -nameRdrName (Name { n_sort = sort, n_occ = occ }) = mkRdrQual (nameSortModule sort) occ - -isExportedName (Name { n_prov = LocalDef _ Exported }) = True -isExportedName other = False - -nameSrcLoc name = provSrcLoc (n_prov name) +-- 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 -provSrcLoc (LocalDef loc _) = loc -provSrcLoc (NonLocalDef (UserImport _ loc _) _) = loc -provSrcLoc SystemProv = noSrcLoc - -isLocallyDefinedName (Name {n_sort = Local}) = True -- Local (might have SystemProv) -isLocallyDefinedName (Name {n_prov = LocalDef _ _}) = True -- Global, but defined here -isLocallyDefinedName other = False -- Other +isDllName :: Name -> Bool + -- Does this name refer to something in a different DLL? +isDllName nm = not opt_Static && + not (isLocalName nm) && -- isLocalName test needed 'cos + not (isModuleInThisPackage (nameModule nm)) -- nameModule won't work on local names --- Things the compiler "knows about" are in some sense --- "imported". When we are compiling the module where --- the entities are defined, we need to be able to pick --- them out, often in combination with isLocallyDefined. -isWiredInName (Name {n_sort = WiredInTyCon _ _}) = True -isWiredInName (Name {n_sort = WiredInId _ _}) = True -isWiredInName _ = False -maybeWiredInIdName :: Name -> Maybe Id -maybeWiredInIdName (Name {n_sort = WiredInId _ id}) = Just id -maybeWiredInIdName other = Nothing -maybeWiredInTyConName :: Name -> Maybe TyCon -maybeWiredInTyConName (Name {n_sort = WiredInTyCon _ tc}) = Just tc -maybeWiredInTyConName other = Nothing +isTyVarName :: Name -> Bool +isTyVarName name = isTvOcc (nameOccName name) - -isLocalName (Name {n_sort = Local}) = True -isLocalName _ = False - -isGlobalName (Name {n_sort = Local}) = False -isGlobalName other = True - --- 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 isExported). -isExternallyVisibleName name = isGlobalName name - -isSystemName (Name {n_prov = SystemProv}) = True -isSystemName other = False \end{code} @@ -436,8 +360,8 @@ instance Eq Name where a /= b = case (a `compare` b) of { EQ -> False; _ -> True } instance Ord Name where - a <= b = case (a `compare` b) of { LT -> True; EQ -> True; GT -> False } - a < b = case (a `compare` b) of { LT -> True; EQ -> False; GT -> False } + a <= b = case (a `compare` b) of { LT -> True; EQ -> True; GT -> False } + a < b = case (a `compare` b) of { LT -> True; EQ -> False; GT -> False } a >= b = case (a `compare` b) of { LT -> False; EQ -> True; GT -> True } a > b = case (a `compare` b) of { LT -> False; EQ -> False; GT -> True } compare a b = cmpName a b @@ -452,6 +376,50 @@ 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} %* * %************************************************************************ @@ -461,76 +429,31 @@ instance Outputable Name where -- When printing interfaces, all Locals have been given nice print-names ppr name = pprName name -pprName (Name {n_sort = Local, n_uniq = uniq, n_occ = occ, n_prov = prov}) - -- Locals +pprName name@(Name {n_sort = sort, n_uniq = uniq, n_occ = occ}) = getPprStyle $ \ sty -> - if codeStyle sty then - pprUnique uniq -- When printing in code we required all names to - -- be globally unique; for example, we use this identifier - -- for the closure name. So we just print the unique alone. - else - pprOccName occ <> pp_local_extra sty uniq - where - sys_local = case prov of - SystemProv -> True - other -> False + case sort of + Global mod -> pprGlobal sty name uniq mod occ + System -> pprSysLocal sty uniq occ + Local -> pprLocal sty uniq occ - pp_local_extra sty uniq - | sys_local = underscore <> pprUnique uniq -- Must print uniques for sys_locals - | debugStyle sty = text "{-" <> pprUnique uniq <> text "-}" - | otherwise = empty +pprLocal sty uniq occ + | codeStyle sty = pprUnique uniq + | debugStyle sty = pprOccName occ <> + text "{-" <> pprUnique10 uniq <> text "-}" + | otherwise = pprOccName occ +pprGlobal sty name uniq mod occ + | codeStyle sty = ppr (moduleName mod) <> char '_' <> pprOccName occ -pprName (Name {n_sort = sort, n_uniq = uniq, n_occ = occ, n_prov = prov}) - -- Globals, and wired in things - = getPprStyle $ \ sty -> - if codeStyle sty then - ppr mod <> underscore <> ppr occ - else - pp_mod_dot sty <> ppr occ <> pp_global_debug sty uniq prov - where - mod = nameSortModule sort - - pp_mod_dot sty - = case prov of - SystemProv -> pp_qual mod dot user_sty - -- Hack alert! Omit the qualifier on SystemProv things, which I claim - -- will also be WiredIn things. We can't get the omit flag right - -- on wired in tycons etc (sigh) so we just leave it out in user style, - -- and hope that leaving it out isn't too consfusing. - -- (e.g. if the programmer hides Bool and redefines it. If so, use -dppr-debug.) - - LocalDef _ _ -> pp_qual mod dot (user_sty || iface_sty) - - NonLocalDef (UserImport imp_mod _ _) omit - | user_sty -> pp_qual imp_mod pp_sep omit - | otherwise -> pp_qual mod pp_sep False - NonLocalDef ImplicitImport omit -> pp_qual mod pp_sep (user_sty && omit) - where - user_sty = userStyle sty - iface_sty = ifaceStyle sty - - pp_qual mod sep omit_qual - | omit_qual = empty - | otherwise = pprModule mod <> sep - - pp_sep | bootFlavour (moduleIfaceFlavour mod) = text "!" -- M!t indicates a name imported - -- from a .hi-boot interface - | otherwise = dot -- Vanilla case - - pp_global_debug sty uniq prov - | debugStyle sty = hcat [text "{-", pprUnique uniq, prov_p prov, text "-}"] - | otherwise = empty - - prov_p prov | opt_PprStyle_NoPrags = empty - | otherwise = comma <> pp_prov prov - -pp_prov (LocalDef _ Exported) = char 'x' -pp_prov (LocalDef _ NotExported) = char 'l' -pp_prov (NonLocalDef ImplicitImport _) = char 'j' -pp_prov (NonLocalDef (UserImport _ _ True ) _) = char 'I' -- Imported by name -pp_prov (NonLocalDef (UserImport _ _ False) _) = char 'i' -- Imported by .. -pp_prov SystemProv = char 's' + | debugStyle sty = ppr (moduleName mod) <> dot <> pprOccName occ <> + text "{-" <> pprUnique10 uniq <> text "-}" + + | unqualStyle sty name = pprOccName occ + | otherwise = ppr (moduleName mod) <> dot <> pprOccName occ + +pprSysLocal sty uniq occ + | codeStyle sty = pprUnique uniq + | otherwise = pprOccName occ <> char '_' <> pprUnique uniq \end{code} @@ -550,16 +473,15 @@ class NamedThing a where \begin{code} getSrcLoc :: NamedThing a => a -> SrcLoc -isLocallyDefined :: NamedThing a => a -> Bool -isExported :: 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 -isExported = isExportedName . getName getSrcLoc = nameSrcLoc . getName -isLocallyDefined = isLocallyDefinedName . getName -getOccString x = occNameString (getOccName x) +getOccString = occNameString . getOccName +toRdrName = nameRdrName . getName +isFrom mod x = nameIsFrom mod (getName x) +isLocalOrFrom mod x = nameIsLocalOrFrom mod ( getName x) \end{code} -\begin{code} -{-# SPECIALIZE isLocallyDefined :: Name -> Bool #-} -\end{code}