summaryrefslogtreecommitdiff
path: root/ghc/compiler/javaGen/Java.lhs
diff options
context:
space:
mode:
authorandy <unknown>2000-06-12 06:01:03 +0000
committerandy <unknown>2000-06-12 06:01:03 +0000
commit4d0f4a6957c00b3e54c2d468feb3ecf3e00e469e (patch)
treea942b822fb4803baf29b2203a41c080d2d3aa64a /ghc/compiler/javaGen/Java.lhs
parent07ac1f9fe37e35c5564524ab79ba643f776df422 (diff)
downloadhaskell-4d0f4a6957c00b3e54c2d468feb3ecf3e00e469e.tar.gz
[project @ 2000-06-12 06:01:03 by andy]
Commiting version of STG -> GOO that seems to compile PrelBase successfully. Many other wibbles; esp. String handling.
Diffstat (limited to 'ghc/compiler/javaGen/Java.lhs')
-rw-r--r--ghc/compiler/javaGen/Java.lhs16
1 files changed, 12 insertions, 4 deletions
diff --git a/ghc/compiler/javaGen/Java.lhs b/ghc/compiler/javaGen/Java.lhs
index ede6ac28e4..de16154543 100644
--- a/ghc/compiler/javaGen/Java.lhs
+++ b/ghc/compiler/javaGen/Java.lhs
@@ -63,6 +63,7 @@ data Expr
| InstanceOf Expr Type
| Call Expr Name [Expr]
| Op Expr String Expr
+ | Raise TypeName [Expr]
| New Type [Expr] (Maybe [Decl]) -- anonymous innerclass
deriving (Show)
@@ -80,7 +81,7 @@ data Type
= PrimType PrimType
| ArrayType Type
| Type TypeName
- deriving (Show)
+ deriving (Show, Eq)
data PrimType
= PrimInt
@@ -91,7 +92,7 @@ data PrimType
| PrimDouble
| PrimByte
| PrimVoid
- deriving (Show)
+ deriving (Show, Eq)
type PackageName = String -- A package name
-- like "java.awt.Button"
@@ -112,14 +113,21 @@ data Name = Name String Type
-- So variables might be Int or Object.
-- ** method calls store the returned
- -- ** type, not a complete.
+ -- ** type, not a complete arg x result type.
--
-- Thinking:
-- ... foo1.foo2(...).foo3 ...
-- here you want to know the *result*
- -- after callling foo1, then foo2,
+ -- after calling foo1, then foo2,
-- then foo3.
+instance Eq Name where
+ (Name nm _) == (Name nm' _) = nm == nm'
+
+
+instance Ord Name where
+ (Name nm _) `compare` (Name nm' _) = nm `compare` nm'
+
data Lit
= IntLit Integer -- unboxed