summaryrefslogtreecommitdiff
path: root/ghc/compiler/codeGen
diff options
context:
space:
mode:
authorpartain <unknown>1996-06-11 13:20:53 +0000
committerpartain <unknown>1996-06-11 13:20:53 +0000
commitae45ff0e9831a0dc862a5d68d03e355d7e323c62 (patch)
tree1b9722084a0c2d04f15f3016bb0f03bbf3b41e27 /ghc/compiler/codeGen
parente7498a3ee1d0484d02a9e86633cc179c76ebf36e (diff)
downloadhaskell-ae45ff0e9831a0dc862a5d68d03e355d7e323c62.tar.gz
[project @ 1996-06-11 13:18:54 by partain]
SLPJ changes to 960611
Diffstat (limited to 'ghc/compiler/codeGen')
-rw-r--r--ghc/compiler/codeGen/CgBindery.lhs19
-rw-r--r--ghc/compiler/codeGen/CgConTbls.lhs6
-rw-r--r--ghc/compiler/codeGen/ClosureInfo.lhs6
3 files changed, 16 insertions, 15 deletions
diff --git a/ghc/compiler/codeGen/CgBindery.lhs b/ghc/compiler/codeGen/CgBindery.lhs
index 8edd5bd9dc..92d6af2c5d 100644
--- a/ghc/compiler/codeGen/CgBindery.lhs
+++ b/ghc/compiler/codeGen/CgBindery.lhs
@@ -44,7 +44,7 @@ import Id ( idPrimRep, toplevelishId, isDataCon,
GenId{-instance NamedThing-}
)
import Maybes ( catMaybes )
-import Name ( isLocallyDefined )
+import Name ( isLocallyDefined, oddlyImportedName, Name{-instance NamedThing-} )
#ifdef DEBUG
import PprAbsC ( pprAmode )
#endif
@@ -194,21 +194,22 @@ I {\em think} all looking-up is done through @getCAddrMode(s)@.
\begin{code}
getCAddrModeAndInfo :: Id -> FCode (CAddrMode, LambdaFormInfo)
-getCAddrModeAndInfo name
- | not (isLocallyDefined name)
- = returnFC (global_amode, mkLFImported name)
+getCAddrModeAndInfo id
+ | not (isLocallyDefined name) || oddlyImportedName name
+ = returnFC (global_amode, mkLFImported id)
- | isDataCon name
- = returnFC (global_amode, mkConLFInfo name)
+ | isDataCon id
+ = returnFC (global_amode, mkConLFInfo id)
| otherwise = -- *might* be a nested defn: in any case, it's something whose
-- definition we will know about...
- lookupBindC name `thenFC` \ (MkCgIdInfo _ volatile_loc stable_loc lf_info) ->
+ lookupBindC id `thenFC` \ (MkCgIdInfo _ volatile_loc stable_loc lf_info) ->
idInfoPiecesToAmode kind volatile_loc stable_loc `thenFC` \ amode ->
returnFC (amode, lf_info)
where
- global_amode = CLbl (mkClosureLabel name) kind
- kind = idPrimRep name
+ name = getName id
+ global_amode = CLbl (mkClosureLabel id) kind
+ kind = idPrimRep id
getCAddrMode :: Id -> FCode CAddrMode
getCAddrMode name
diff --git a/ghc/compiler/codeGen/CgConTbls.lhs b/ghc/compiler/codeGen/CgConTbls.lhs
index 7745466706..2083d8fe10 100644
--- a/ghc/compiler/codeGen/CgConTbls.lhs
+++ b/ghc/compiler/codeGen/CgConTbls.lhs
@@ -40,7 +40,7 @@ import Id ( dataConTag, dataConRawArgTys,
emptyIdSet,
GenId{-instance NamedThing-}
)
-import Name ( getLocalName )
+import Name ( nameOf, origName )
import PrelInfo ( maybeIntLikeTyCon )
import PrimRep ( getPrimRepSize, PrimRep(..) )
import TyCon ( tyConDataCons, mkSpecTyCon )
@@ -209,7 +209,7 @@ genConInfo comp_info tycon data_con
body_code))
entry_addr = CLbl entry_label CodePtrRep
- con_descr = _UNPK_ (getLocalName data_con)
+ con_descr = _UNPK_ (nameOf (origName "con_descr" data_con))
closure_code = CClosureInfoAndCode closure_info body Nothing
stdUpd con_descr
@@ -337,7 +337,7 @@ genPhantomUpdInfo comp_info tycon data_con
phantom_ci = layOutPhantomClosure data_con (mkConLFInfo data_con)
- con_descr = _UNPK_ (getLocalName data_con)
+ con_descr = _UNPK_ (nameOf (origName "con_descr2" data_con))
con_arity = dataConArity data_con
diff --git a/ghc/compiler/codeGen/ClosureInfo.lhs b/ghc/compiler/codeGen/ClosureInfo.lhs
index 960e6a9803..d24b55e253 100644
--- a/ghc/compiler/codeGen/ClosureInfo.lhs
+++ b/ghc/compiler/codeGen/ClosureInfo.lhs
@@ -87,7 +87,7 @@ import Id ( idType, idPrimRep, getIdArity,
)
import IdInfo ( arityMaybe )
import Maybes ( assocMaybe, maybeToBool )
-import Name ( isLocallyDefined, getLocalName )
+import Name ( isLocallyDefined, nameOf, origName )
import PprStyle ( PprStyle(..) )
import PprType ( GenType{-instance Outputable-} )
import PrelInfo ( maybeCharLikeTyCon, maybeIntLikeTyCon )
@@ -1320,8 +1320,8 @@ closureKind (MkClosureInfo _ lf _)
closureTypeDescr :: ClosureInfo -> String
closureTypeDescr (MkClosureInfo id lf _)
- = if (isDataCon id) then -- DataCon has function types
- _UNPK_ (getLocalName (dataConTyCon id)) -- We want the TyCon not the ->
+ = if (isDataCon id) then -- DataCon has function types
+ _UNPK_ (nameOf (origName "closureTypeDescr" (dataConTyCon id))) -- We want the TyCon not the ->
else
getTyDescription (idType id)
\end{code}