summaryrefslogtreecommitdiff
path: root/ghc/compiler/javaGen/JavaGen.lhs
diff options
context:
space:
mode:
authorandy <unknown>2000-05-11 07:20:36 +0000
committerandy <unknown>2000-05-11 07:20:36 +0000
commit189393d1f22d7d62d74a7de7f253c67e21a28bb9 (patch)
treef02ce982a4104b3f46f6ce7c0f9ba366af17f550 /ghc/compiler/javaGen/JavaGen.lhs
parent53a7fa7dd4edbf25019cd4764f1b798bd8286975 (diff)
downloadhaskell-189393d1f22d7d62d74a7de7f253c67e21a28bb9.tar.gz
[project @ 2000-05-11 07:20:36 by andy]
Wibble... The corrected example is as follows: myS :: (forall t t1 t2. (t -> t2 -> t1) -> (t -> t2) -> t -> t1) [NoDiscard] __AL 3 myS = \ @ t @ t1 @ t2 f :: (t -> t2 -> t1) g :: (t -> t2) x :: t -> 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 myS$1(g, x))); return f; } } class myS$1 extends Code { 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/JavaGen.lhs')
-rw-r--r--ghc/compiler/javaGen/JavaGen.lhs7
1 files changed, 5 insertions, 2 deletions
diff --git a/ghc/compiler/javaGen/JavaGen.lhs b/ghc/compiler/javaGen/JavaGen.lhs
index 0fd4b9e9c1..513d99a16b 100644
--- a/ghc/compiler/javaGen/JavaGen.lhs
+++ b/ghc/compiler/javaGen/JavaGen.lhs
@@ -599,9 +599,12 @@ new env@(Env _ pairs) typ args Nothing =
new env typ [] (Just inner) =
-- anon. inner class
do { innerName <- genAnonInnerClassName
- ; frees <- liftClass env innerName inner [] []
- ; return (mkNew env typ [ Var name | name <- frees ])
+ ; frees <- liftClass env innerName inner [unType typ] []
+ ; return (New (Type [innerName]) [ Var name | name <- frees ] Nothing)
}
+ where unType (Type [name]) = name
+ unType _ = error "incorrect type style"
+
new env typ _ (Just inner) = error "cant handle inner class with args"
liftClass :: Env -> Name -> [Decl] -> [Name] -> [Name] -> LifterM [ Name ]