diff options
Diffstat (limited to 'ghc/compiler/codeGen')
-rw-r--r-- | ghc/compiler/codeGen/CgBindery.lhs | 4 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgClosure.lhs | 6 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CgTailCall.lhs | 4 | ||||
-rw-r--r-- | ghc/compiler/codeGen/CodeGen.lhs | 26 |
4 files changed, 20 insertions, 20 deletions
diff --git a/ghc/compiler/codeGen/CgBindery.lhs b/ghc/compiler/codeGen/CgBindery.lhs index 7414569b28..acac740379 100644 --- a/ghc/compiler/codeGen/CgBindery.lhs +++ b/ghc/compiler/codeGen/CgBindery.lhs @@ -44,7 +44,7 @@ import VarEnv import VarSet ( varSetElems ) import Literal ( Literal ) import Maybes ( catMaybes, maybeToBool, seqMaybe ) -import Name ( isLocalName, NamedThing(..) ) +import Name ( isInternalName, NamedThing(..) ) #ifdef DEBUG import PprAbsC ( pprAmode ) #endif @@ -259,7 +259,7 @@ getCAddrModeAndInfo id case maybe_cg_id_info of -- Nothing => not in the environment, so should be imported - Nothing | isLocalName name -> cgLookupPanic id + Nothing | isInternalName name -> cgLookupPanic id | otherwise -> returnFC (id, global_amode, mkLFImported id) Just (MkCgIdInfo id' volatile_loc stable_loc lf_info) diff --git a/ghc/compiler/codeGen/CgClosure.lhs b/ghc/compiler/codeGen/CgClosure.lhs index 051a0eb9b5..e7d70e4fa5 100644 --- a/ghc/compiler/codeGen/CgClosure.lhs +++ b/ghc/compiler/codeGen/CgClosure.lhs @@ -1,7 +1,7 @@ % % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % -% $Id: CgClosure.lhs,v 1.55 2002/02/14 11:56:03 njn Exp $ +% $Id: CgClosure.lhs,v 1.56 2002/03/14 15:27:17 simonpj Exp $ % \section[CgClosure]{Code generation for closures} @@ -46,7 +46,7 @@ import ClosureInfo -- lots and lots of stuff import CmdLineOpts ( opt_GranMacros, opt_SccProfilingOn, opt_DoTickyProfiling ) import CostCentre import Id ( Id, idName, idType, idPrimRep ) -import Name ( Name, isLocalName ) +import Name ( Name, isInternalName ) import Module ( Module, pprModule ) import ListSetOps ( minusList ) import PrimRep ( PrimRep(..) ) @@ -449,7 +449,7 @@ closureCodeBody binder_info closure_info cc all_args body -- give the module name even for *local* things. We print -- just "x (M)" rather that "M.x" to distinguish them from the global kind. ppr_for_ticky_name mod_name name - | isLocalName name = showSDocDebug (ppr name <+> (parens (ppr mod_name))) + | isInternalName name = showSDocDebug (ppr name <+> (parens (ppr mod_name))) | otherwise = showSDocDebug (ppr name) \end{code} diff --git a/ghc/compiler/codeGen/CgTailCall.lhs b/ghc/compiler/codeGen/CgTailCall.lhs index 8dfd5f484a..73e7aaa93f 100644 --- a/ghc/compiler/codeGen/CgTailCall.lhs +++ b/ghc/compiler/codeGen/CgTailCall.lhs @@ -1,7 +1,7 @@ % % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % -% $Id: CgTailCall.lhs,v 1.31 2001/10/25 05:07:32 sof Exp $ +% $Id: CgTailCall.lhs,v 1.32 2002/03/14 15:27:17 simonpj Exp $ % %******************************************************** %* * @@ -345,7 +345,7 @@ tailCallFun tailCallFun fun fun_amode lf_info arg_amodes pending_assts = nodeMustPointToIt lf_info `thenFC` \ node_points -> -- we use the name of fun', the Id from the environment, rather than - -- fun from the STG tree, in case it is a top-level name that we globalised + -- fun from the STG tree, in case it is a top-level name that we externalised -- (see cgTopRhsClosure). getEntryConvention (idName fun) lf_info (map getAmodeRep arg_amodes) `thenFC` \ entry_conv -> diff --git a/ghc/compiler/codeGen/CodeGen.lhs b/ghc/compiler/codeGen/CodeGen.lhs index b7f01cbc0b..5d08357b73 100644 --- a/ghc/compiler/codeGen/CodeGen.lhs +++ b/ghc/compiler/codeGen/CodeGen.lhs @@ -40,7 +40,7 @@ import CmdLineOpts ( DynFlags, DynFlag(..), opt_SccProfilingOn, opt_EnsureSplittableC ) import CostCentre ( CollectedCCs ) import Id ( Id, idName, setIdName ) -import Name ( nameSrcLoc, nameOccName, nameUnique, isLocalName, mkGlobalName ) +import Name ( nameSrcLoc, nameOccName, nameUnique, isInternalName, mkExternalName ) import OccName ( mkLocalOcc ) import Module ( Module ) import PrimRep ( PrimRep(..) ) @@ -182,14 +182,14 @@ variable. cgTopBinding :: (StgBinding,[Id]) -> Code cgTopBinding (StgNonRec srt_info id rhs, srt) = absC maybeSplitCode `thenC` - maybeGlobaliseId id `thenFC` \ id' -> + maybeExternaliseId id `thenFC` \ id' -> let srt_label = mkSRTLabel (idName id') in mkSRT srt_label srt [] `thenC` setSRTLabel srt_label ( cgTopRhs id' rhs srt_info `thenFC` \ (id, info) -> - addBindC id info -- Add the un-globalised Id to the envt, so we + addBindC id info -- Add the un-externalised Id to the envt, so we -- find it when we look up occurrences ) @@ -198,7 +198,7 @@ cgTopBinding (StgRec srt_info pairs, srt) let (bndrs, rhss) = unzip pairs in - mapFCs maybeGlobaliseId bndrs `thenFC` \ bndrs'@(id:_) -> + mapFCs maybeExternaliseId bndrs `thenFC` \ bndrs'@(id:_) -> let srt_label = mkSRTLabel (idName id) pairs' = zip bndrs' rhss @@ -218,7 +218,7 @@ mkSRT lbl ids these absC (CSRT lbl (map (mkClosureLabel . idName) ids)) where -- sigh, better map all the ids against the environment in case they've - -- been globalised (see maybeGlobaliseId below). + -- been externalised (see maybeExternaliseId below). remap id = case filter (==id) these of [] -> getCAddrModeAndInfo id `thenFC` \ (id, _, _) -> returnFC id @@ -230,7 +230,7 @@ mkSRT lbl ids these cgTopRhs :: Id -> StgRhs -> SRT -> FCode (Id, CgIdInfo) -- The Id is passed along for setting up a binding... - -- It's already been globalised if necessary + -- It's already been externalised if necessary cgTopRhs bndr (StgRhsCon cc con args) srt = forkStatics (cgTopRhsCon bndr con args srt) @@ -250,17 +250,17 @@ cgTopRhs bndr (StgRhsClosure cc bi fvs upd_flag args body) srt %* * %************************************************************************ -If we're splitting the object, we need to globalise all the top-level names -(and then make sure we only use the globalised one in any C label we use +If we're splitting the object, we need to externalise all the top-level names +(and then make sure we only use the externalised one in any C label we use which refers to this name). \begin{code} -maybeGlobaliseId :: Id -> FCode Id -maybeGlobaliseId id - | opt_EnsureSplittableC, -- Globalise the name for -split-objs - isLocalName name +maybeExternaliseId :: Id -> FCode Id +maybeExternaliseId id + | opt_EnsureSplittableC, -- Externalise the name for -split-objs + isInternalName name = moduleName `thenFC` \ mod -> - returnFC (setIdName id (mkGlobalName uniq mod new_occ (nameSrcLoc name))) + returnFC (setIdName id (mkExternalName uniq mod new_occ (nameSrcLoc name))) | otherwise = returnFC id where |