summaryrefslogtreecommitdiff
path: root/ghc/compiler/javaGen/PrintJava.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/PrintJava.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/PrintJava.lhs')
-rw-r--r--ghc/compiler/javaGen/PrintJava.lhs13
1 files changed, 7 insertions, 6 deletions
diff --git a/ghc/compiler/javaGen/PrintJava.lhs b/ghc/compiler/javaGen/PrintJava.lhs
index eb0e0f8533..e71e527a47 100644
--- a/ghc/compiler/javaGen/PrintJava.lhs
+++ b/ghc/compiler/javaGen/PrintJava.lhs
@@ -36,7 +36,7 @@ decls (d:ds) = decl d $$ decls ds
decl = \d ->
case d of
- { Import n -> importDecl (name n)
+ { Import n -> importDecl (hcat (punctuate dot (map text n)))
; Field mfs t n e -> field (modifiers mfs) (typ t) (name n) e
; Constructor mfs n as ss -> constructor (modifiers mfs) (name n) (parameters as) (statements ss)
; Method mfs t n as ss -> method (modifiers mfs) (typ t) (name n) (parameters as) (statements ss)
@@ -96,14 +96,15 @@ extends xs = text "extends" <+> hsep (punctuate comma (map name xs))
implements [] = empty
implements xs = text "implements" <+> hsep (punctuate comma (map name xs))
-name ns = hcat (punctuate dot (map text ns))
+name ns = text ns
parameters as = map parameter as
parameter (Parameter mfs t n) = modifiers mfs <+> typ t <+> name n
-typ (Type n) = name n
-typ (Array t) = typ t <> text "[]"
+typ (PrimType s) = text s
+typ (Type n) = hcat (punctuate dot (map text n))
+typ (ArrayType t) = typ t <> text "[]"
statements ss = vcat (map statement ss)
@@ -162,11 +163,11 @@ expr = \e ->
; Cast t e -> cast (typ t) e
; Access e n -> expr e <> text "." <> name n
; Assign l r -> assign (expr l) r
- ; New n es ds -> new (name n) es (maybeClass ds)
+ ; New n es ds -> new (typ n) es (maybeClass ds)
; Call e n es -> call (expr e) (name n) es
; Op e1 o e2 -> op e1 o e2
; InstanceOf e t -> expr e <+> text "instanceof" <+> typ t
- ; NewArray n es -> newArray (name n) es
+ ; NewArray n es -> newArray (typ n) es
}
op = \e1 -> \o -> \e2 ->