summaryrefslogtreecommitdiff
path: root/ghc/compiler/javaGen
diff options
context:
space:
mode:
Diffstat (limited to 'ghc/compiler/javaGen')
-rw-r--r--ghc/compiler/javaGen/Java.lhs2
-rw-r--r--ghc/compiler/javaGen/JavaGen.lhs6
-rw-r--r--ghc/compiler/javaGen/PrintJava.lhs2
3 files changed, 8 insertions, 2 deletions
diff --git a/ghc/compiler/javaGen/Java.lhs b/ghc/compiler/javaGen/Java.lhs
index de16154543..ec2c5061d3 100644
--- a/ghc/compiler/javaGen/Java.lhs
+++ b/ghc/compiler/javaGen/Java.lhs
@@ -131,7 +131,7 @@ instance Ord Name where
data Lit
= IntLit Integer -- unboxed
- | CharLit Char -- unboxed
+ | CharLit Int -- unboxed
| StringLit String -- java string
deriving Show
diff --git a/ghc/compiler/javaGen/JavaGen.lhs b/ghc/compiler/javaGen/JavaGen.lhs
index 6093a807ba..6278a70d8e 100644
--- a/ghc/compiler/javaGen/JavaGen.lhs
+++ b/ghc/compiler/javaGen/JavaGen.lhs
@@ -605,6 +605,7 @@ suffix _ = ""
primName :: PrimType -> String
primName PrimInt = "int"
primName PrimChar = "char"
+primName PrimByte = "byte"
primName PrimBoolean = "boolean"
primName _ = error "unsupported primitive"
@@ -803,6 +804,9 @@ inttype = PrimType PrimInt
chartype :: Type
chartype = PrimType PrimChar
+bytetype :: Type
+bytetype = PrimType PrimByte
+
-- This lets you get inside a possible "Value" type,
-- to access the internal unboxed object.
access :: Expr -> Type -> Expr
@@ -811,6 +815,7 @@ access expr other = expr
accessPrim expr PrimInt = Call expr (Name "intValue" inttype) []
accessPrim expr PrimChar = Call expr (Name "charValue" chartype) []
+accessPrim expr PrimByte = Call expr (Name "byteValue" bytetype) []
accessPrim expr other = pprPanic "accessPrim" (text (show other))
-- This is where we map from typename to types,
@@ -831,6 +836,7 @@ primRepToType ::PrimRep -> Type
primRepToType PtrRep = objectType
primRepToType IntRep = inttype
primRepToType CharRep = chartype
+primRepToType Int8Rep = bytetype
primRepToType AddrRep = objectType
primRepToType other = pprPanic "primRepToType" (ppr other)
diff --git a/ghc/compiler/javaGen/PrintJava.lhs b/ghc/compiler/javaGen/PrintJava.lhs
index 0db596d489..edaf8e594f 100644
--- a/ghc/compiler/javaGen/PrintJava.lhs
+++ b/ghc/compiler/javaGen/PrintJava.lhs
@@ -220,7 +220,7 @@ call e n es = e <> dot <> n <> parens (hsep (punctuate comma (map expr es)))
literal = \l ->
case l of
{ IntLit i -> text (show i)
- ; CharLit c -> text (show c)
+ ; CharLit c -> text "(char)" <+> text (show c)
; StringLit s -> text ("\"" ++ s ++ "\"") -- strings are already printable
}