[project @ 2004-11-10 03:20:31 by wolfgang]
[ghc-hetmet.git] / ghc / compiler / javaGen / JavaGen.lhs
index 9b5bcba..ff0dd91 100644 (file)
@@ -47,12 +47,12 @@ module JavaGen( javaGen ) where
 import Java
 
 import Literal ( Literal(..) )
-import Id      ( Id, isDataConId_maybe, isId, idName, isDeadBinder, idPrimRep
+import Id      ( Id, isDataConWorkId_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 )
+import DataCon ( DataCon, dataConRepArity, dataConRepArgTys, dataConWorkId )
 import qualified Type
 import qualified CoreSyn
 import CoreSyn ( CoreBind, CoreExpr, CoreAlt, CoreBndr,
@@ -66,7 +66,7 @@ import Outputable
 
 import Maybe
 import PrimOp
-import Util     ( lengthIs )
+import Util     ( lengthIs, notNull )
 
 #include "HsVersions.h"
 
@@ -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
@@ -228,7 +228,7 @@ javaLit (MachInt i)  = Literal (IntLit (fromInteger i))
 javaLit (MachChar c) = Literal (CharLit c)
 javaLit (MachStr fs) = Literal (StringLit str)
    where
-       str = concatMap renderString (_UNPK_ fs) ++ "\\000"
+       str = concatMap renderString (unpackFS fs) ++ "\\000"
        -- This should really handle all the chars 0..31.
        renderString '\NUL' = "\\000"
        renderString other  = [other]
@@ -267,7 +267,7 @@ javaCase :: (Expr -> Statement) -> CoreExpr -> Id -> [CoreAlt] -> [Statement]
 -- If we've got the wrong one, this is _|_, and the
 -- casting will catch this with an exception.
 
-javaCase r e x [(DataAlt d,bs,rhs)] | not (null bs)
+javaCase r e x [(DataAlt d,bs,rhs)] | notNull bs
   = java_expr PushExpr e ++
     [ var [Final] (javaName x)
                  (whnf primRep (vmPOP (primRepToType primRep))) ] ++
@@ -420,7 +420,7 @@ javaApp r (CoreSyn.App f a) as
        | isValArg a = javaApp r f (a:as)
        | otherwise  = javaApp r f as
 javaApp r (CoreSyn.Var f) as 
-  = case isDataConId_maybe f of {
+  = case isDataConWorkId_maybe f of {
        Just dc | as `lengthIs` dataConRepArity dc
         -- NOTE: Saturated constructors never returning a primitive at this point
         --
@@ -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
@@ -755,7 +755,7 @@ shortName = reverse . takeWhile (/= '.') . reverse
 -- would return the name "Test.Foo".
 
 javaConstrWkrName :: DataCon -> TypeName
-javaConstrWkrName = javaIdTypeName . dataConId
+javaConstrWkrName = javaIdTypeName . dataConWorkId
 
 -- Makes x_inst for Rec decls
 -- They are *never* is primitive