summaryrefslogtreecommitdiff
path: root/ghc/compiler/javaGen/Java.lhs
diff options
context:
space:
mode:
authorandy <unknown>2000-05-11 07:10:11 +0000
committerandy <unknown>2000-05-11 07:10:11 +0000
commit53a7fa7dd4edbf25019cd4764f1b798bd8286975 (patch)
treee825463485752d7de6686270358081690a431cb6 /ghc/compiler/javaGen/Java.lhs
parentfa2efd1ea7fe23ccb8a1b029e3a8c9047b462045 (diff)
downloadhaskell-53a7fa7dd4edbf25019cd4764f1b798bd8286975.tar.gz
[project @ 2000-05-11 07:10:11 by andy]
First attempt at at class lifter for the GHC GOO backend. This included a cleanup of the Java/GOO abstract syntax - Name is now a string, not a list of string - Type is used instead of name in some places (for example, with new) - other minor tweeks. Andy --------- Example for myS f g x = f x (g x) public class myS implements Code { public Object ENTER () { VM.COLLECT(3, this); final Object f = VM.POP(); final Object g = VM.POP(); final Object x = VM.POP(); VM.PUSH(x); VM.PUSH(new Thunk(new Code(g, x))); return f; } } class myS$1 { final Object g; final Object x; public myS$1 (Object _g_, Object _x_) { g = _g_; x = _x_; } public Object ENTER () { VM.PUSH(x); return g; } }
Diffstat (limited to 'ghc/compiler/javaGen/Java.lhs')
-rw-r--r--ghc/compiler/javaGen/Java.lhs33
1 files changed, 23 insertions, 10 deletions
diff --git a/ghc/compiler/javaGen/Java.lhs b/ghc/compiler/javaGen/Java.lhs
index 5de371b618..3151014041 100644
--- a/ghc/compiler/javaGen/Java.lhs
+++ b/ghc/compiler/javaGen/Java.lhs
@@ -1,4 +1,4 @@
-Abstract syntax for Java subset that is the target of Mondrian.
+bstract syntax for Java subset that is the target of Mondrian.
The syntax has been taken from "The Java Language Specification".
(c) Erik Meijer & Arjan van IJzendoorn
@@ -22,9 +22,11 @@ data CompilationUnit
deriving (Show)
data Decl
- = Import Name
+ = Import [Name]
| Field [Modifier] Type Name (Maybe Expr)
| Constructor [Modifier] Name [Parameter] [Statement]
+ -- Add Throws (list of Names)
+ -- to Method
| Method [Modifier] Type Name [Parameter] [Statement]
| Comment [String]
| Interface [Modifier] Name [Name] [Decl]
@@ -54,13 +56,8 @@ data Expr
| InstanceOf Expr Type
| Call Expr Name [Expr]
| Op Expr String Expr
- | New Name [Expr] (Maybe [Decl]) -- anonymous innerclass
- | NewArray Name [Expr]
- deriving (Show)
-
-data Type
- = Type Name
- | Array Type
+ | New Type [Expr] (Maybe [Decl]) -- anonymous innerclass
+ | NewArray Type [Expr]
deriving (Show)
data Modifier
@@ -69,7 +66,15 @@ data Modifier
| Abstract | Final | Native | Synchronized | Transient | Volatile
deriving (Show, Eq, Ord)
-type Name = [String]
+data Type
+ = PrimType String
+ | ArrayType Type
+ | Type [Name]
+ deriving (Show)
+
+-- If you want qualified names, use Access <expr> <name>
+-- Type's are already qualified.
+type Name = String
data Lit
= IntLit Int -- Boxed
@@ -79,6 +84,14 @@ data Lit
| StringLit String
deriving Show
+data OType
+ = ObjectType -- Object *
+ | UnboxedIntType -- int
+ | UnboxedCharType -- char
+
+data OVar = OVar Name OType
+ -- Object x.y
+
addModifier :: Modifier -> Decl -> Decl
addModifier = \m -> \d ->
case d of