summaryrefslogtreecommitdiff
path: root/ghc/compiler/javaGen/JavaGen.lhs
diff options
context:
space:
mode:
authorsimonpj <unknown>2002-03-14 15:27:22 +0000
committersimonpj <unknown>2002-03-14 15:27:22 +0000
commit1553c7788e7f663bfc55813158325d695a21a229 (patch)
treecd776b6e3cd70d71499aeea48335f4261b53c294 /ghc/compiler/javaGen/JavaGen.lhs
parent057e3f0d571845f91178cb0e416566e063696425 (diff)
downloadhaskell-1553c7788e7f663bfc55813158325d695a21a229.tar.gz
[project @ 2002-03-14 15:27:15 by simonpj]
------------------------ Change GlobalName --> ExternalName LocalName -> InternalName ------------------------ For a long time there's been terminological confusion between GlobalName vs LocalName (property of a Name) GlobalId vs LocalId (property of an Id) I've now changed the terminology for Name to be ExternalName vs InternalName I've also added quite a bit of documentation in the Commentary.
Diffstat (limited to 'ghc/compiler/javaGen/JavaGen.lhs')
-rw-r--r--ghc/compiler/javaGen/JavaGen.lhs8
1 files changed, 4 insertions, 4 deletions
diff --git a/ghc/compiler/javaGen/JavaGen.lhs b/ghc/compiler/javaGen/JavaGen.lhs
index 9b5bcba532..b6fbc36811 100644
--- a/ghc/compiler/javaGen/JavaGen.lhs
+++ b/ghc/compiler/javaGen/JavaGen.lhs
@@ -49,7 +49,7 @@ import Java
import Literal ( Literal(..) )
import Id ( Id, isDataConId_maybe, isId, idName, isDeadBinder, idPrimRep
, isPrimOpId_maybe )
-import Name ( NamedThing(..), getOccString, isGlobalName, isLocalName
+import Name ( NamedThing(..), getOccString, isExternalName, isInternalName
, nameModule )
import PrimRep ( PrimRep(..) )
import DataCon ( DataCon, dataConRepArity, dataConRepArgTys, dataConId )
@@ -220,7 +220,7 @@ java_top_bind bndr rhs
\begin{code}
javaVar :: Id -> Expr
-javaVar v | isGlobalName (idName v) = mkNew (javaIdType v) []
+javaVar v | isExternalName (idName v) = mkNew (javaIdType v) []
| otherwise = Var (javaName v)
javaLit :: Literal.Literal -> Expr
@@ -724,7 +724,7 @@ withType (Name n _) t = Name n t
-- using the same string as the Id.
javaName :: Id -> Name
javaName n
- | isGlobalName (idName n) = error "useing javaName on global"
+ | isExternalName (idName n) = error "useing javaName on global"
| otherwise = Name (getOccString n)
(primRepToType (idPrimRep n))
@@ -734,7 +734,7 @@ javaName n
javaIdTypeName :: Id -> TypeName
javaIdTypeName n
- | isLocalName n' = renameForKeywords n'
+ | isInternalName n' = renameForKeywords n'
| otherwise = moduleString (nameModule n') ++ "." ++ renameForKeywords n'
where
n' = getName n