lots of new stuff
authorcg
Fri, 16 Jan 1998 16:12:55 +0000
changeset 261 d95d5a3cc475
parent 260 fd810b2b7be0
child 262 8edf97e626c8
lots of new stuff
Java.st
JavaBuiltInClassPointerRef.st
JavaClass.st
JavaContext.st
JavaDecompiler.st
JavaMethod.st
JavaProcess.st
JavaUnresolvedClassConstant.st
JavaVM.st
JavaView.st
--- a/Java.st	Mon Jan 12 23:18:07 1998 +0000
+++ b/Java.st	Fri Jan 16 16:12:55 1998 +0000
@@ -1,4 +1,4 @@
-'From Smalltalk/X, Version:3.3.1 on 10-jan-1998 at 4:06:38 pm'                  !
+'From Smalltalk/X, Version:3.3.1 on 16-jan-1998 at 3:08:00 pm'                  !
 
 Object subclass:#Java
 	instanceVariableNames:''
@@ -19,20 +19,20 @@
 
     cls := self at:aString.
     cls isNil ifTrue:[
-        ('JAVA [info]: late class loading: ' , aString) infoPrintCR.
-        loader := JavaClassReader classLoaderQuerySignal raise.
-        loader isNil ifTrue:[
-            "/ load using default (ST/X) loader
-            cls := JavaClassReader loadClass:aString.
-        ] ifFalse:[
-            "/ load using a Java class loader
+	('JAVA [info]: late class loading: ' , aString) infoPrintCR.
+	loader := JavaClassReader classLoaderQuerySignal raise.
+	loader isNil ifTrue:[
+	    "/ load using default (ST/X) loader
+	    cls := JavaClassReader loadClass:aString.
+	] ifFalse:[
+	    "/ load using a Java class loader
 "/            classURL := Java as_URL:('file:' , aString , '.class').
 "/            loader loadClass:classURL.
-            loader perform:#'loadClass(Ljava/lang/String;)Ljava/lang/Class;'
-                with:(Java as_String:aString).
+	    loader perform:#'loadClass(Ljava/lang/String;)Ljava/lang/Class;'
+		with:(Java as_String:aString).
 
-            cls := self at:aString.
-        ]
+	    cls := self at:aString.
+	]
     ].
     ^ cls
 
@@ -72,7 +72,7 @@
 
 threads
     Threads isNil ifTrue:[
-        Threads := WeakIdentityDictionary new.
+	Threads := WeakIdentityDictionary new.
     ].
     ^ Threads
 
@@ -158,6 +158,12 @@
     "
 
 
+!
+
+sourcePath
+    ^ SourceDirectories
+
+    "Created: / 16.1.1998 / 13:26:55 / cg"
 ! !
 
 !Java class methodsFor:'class initialization'!
@@ -169,14 +175,14 @@
 
      system := self classForName:'java.lang.System'.
      system isInitialized ifFalse:[
-         system classInit.
-         self initSystemClass.
+	 system classInit.
+	 self initSystemClass.
      ].
 
      self allClassesDo:[:cls |
-        cls isInitialized ifFalse:[
-            cls classInit
-        ]
+	cls isInitialized ifFalse:[
+	    cls classInit
+	]
      ]
 
     "Modified: / 4.1.1998 / 14:41:12 / cg"
@@ -196,6 +202,10 @@
     system isNil ifTrue:[
         JavaVM initializeVM.
         system := Java at:'java.lang.System'.
+        system isNil ifTrue:[
+            self error:'no ''java.lang.System'' class'.
+            ^ self
+        ].
     ].
     (system implements:#'initializeSystemClass()V') ifTrue:[
         system invokeStatic:#'initializeSystemClass()V'.
@@ -205,11 +215,11 @@
      Java initSystemClass
 
      (Java at:'java.lang.System') 
-        invoke:#'getProperty(Ljava/lang/String;)Ljava/lang/String;'
+        perform:#'getProperty(Ljava/lang/String;)Ljava/lang/String;'
         with:(Java as_String:'java.home')
     "
 
-    "Modified: / 8.1.1998 / 15:43:50 / cg"
+    "Modified: / 15.1.1998 / 00:29:37 / cg"
 !
 
 initialize
@@ -217,7 +227,7 @@
 
     jHome := '/usr/local/java/jdk113'.
     jHome asFilename exists ifFalse:[
-        jHome := '/usr/lib/java'.
+	jHome := '/usr/lib/java'.
     ].
     mozillaHome := '/usr/local/java/moz3_0/lib_unix'.
 
@@ -226,7 +236,7 @@
     self sourceDirectories:(Array with:jHome , '/src').
 
     mozillaHome asFilename exists ifTrue:[
-        Java addToClassPath:(mozillaHome , '/classes').
+	Java addToClassPath:(mozillaHome , '/classes').
     ].
     self initializePrettyPrintStyle.
 
@@ -282,14 +292,14 @@
     "/ check if already running
     "/
     self threads do:[:aJavaThread |
-        aJavaThread name = 'JAVA-Screen Updater' ifTrue:[
-            "/ already running
-            ^ self
-        ]
+	aJavaThread name = 'JAVA-Screen Updater' ifTrue:[
+	    "/ already running
+	    ^ self
+	]
     ].
 
     'JAVA [info]: (re)initializing JAVA environment completely ...' infoPrintCR.
-    JavaInterpreter releaseAllJavaResources.
+    JavaVM releaseAllJavaResources.
     self markAllClassesUninitialized.
 "/    self initAllStaticFields.
 "/    self reinitAllClasses.
@@ -308,19 +318,19 @@
     |myself|
 
     Threads isNil ifTrue:[
-        ^ self
+	^ self
     ].
 
     myself := Processor activeProcess.
 
     Threads do:[:aJavaThread |
-        aJavaThread ~~ myself ifTrue:[
-            (aJavaThread isNil or:[aJavaThread == 0]) ifFalse:[
-                (aJavaThread isMemberOf:JavaProcess) ifTrue:[
-                    aJavaThread terminate
-                ]
-            ]
-        ]
+	aJavaThread ~~ myself ifTrue:[
+	    (aJavaThread isNil or:[aJavaThread == 0]) ifFalse:[
+		(aJavaThread isMemberOf:JavaProcess) ifTrue:[
+		    aJavaThread terminate
+		]
+	    ]
+	]
     ].
     Threads := nil.
 
@@ -354,7 +364,7 @@
     |i|
 
     i := (Java at:'java.lang.Float') new.
-    i invoke:#'<init>(F)V' with:(aNumber asShortFloat).
+    i perform:#'<init>(F)V' with:(aNumber asShortFloat).
     ^ i
 
     "
@@ -367,36 +377,39 @@
 !
 
 as_Hashtable:aDictionary
+    "given a smalltalk dictionary, create and return
+     a Java hashTable for it"
+
     |hashTable|
 
     hashTable := (self classForName:'java.util.Hashtable') new.
     aDictionary keysAndValuesDo:[:k :v |
-        |sk sv jk jv|
+	|sk sv jk jv|
 
-        (sk := k) isSymbol ifTrue:[
-            sk := sk asString
-        ].
-        (sv := v) isSymbol ifTrue:[
-            sv := sv asString
-        ].
-        jk := self as_Object:sk.
-        jv := self as_Object:sv.
+	(sk := k) isSymbol ifTrue:[
+	    sk := sk asString
+	].
+	(sv := v) isSymbol ifTrue:[
+	    sv := sv asString
+	].
+	jk := self as_Object:sk.
+	jv := self as_Object:sv.
 
-        hashTable 
-            invoke:#'put(Ljava/lang/Object;Ljava/lang/Object;)Ljava/lang/Object;'    
-            with:jk
-            with:jv.
+	hashTable 
+	    perform:#'put(Ljava/lang/Object;Ljava/lang/Object;)Ljava/lang/Object;'    
+	    with:jk
+	    with:jv.
     ].
     ^ hashTable
 
     "
      Java as_Hashtable:(Dictionary new
-                           at:'hello' put:'Hallo';
-                           at:'world' put:'Welt';       
-                           yourself)
+			   at:'hello' put:'Hallo';
+			   at:'world' put:'Welt';       
+			   yourself)
     "
 
-    "Modified: / 7.1.1998 / 10:09:23 / cg"
+    "Modified: / 14.1.1998 / 17:02:13 / cg"
 !
 
 as_Integer:anInteger
@@ -405,7 +418,7 @@
     |i|
 
     i := (Java at:'java.lang.Integer') new.
-    i invoke:#'<init>(I)V' with:anInteger.
+    i perform:#'<init>(I)V' with:anInteger.
     ^ i
 
     "
@@ -448,7 +461,7 @@
     str := aJavaString instVarAt:(JavaSlotIndexCache string_slot_value).
 
     str size == count ifTrue:[
-        ^ str
+	^ str
     ].
 
     "/ start := (aJavaString instVarNamed:'offset') + 1.
@@ -459,7 +472,7 @@
 
     "/ ^ ((aJavaString instVarNamed:'value') copyFrom:start to:stop) asString
     ^ ((aJavaString instVarAt:(JavaSlotIndexCache string_slot_value)) 
-                copyFrom:start to:stop) asString
+		copyFrom:start to:stop) asString
 
     "Created: / 8.8.1997 / 12:02:55 / cg"
     "Modified: / 9.1.1998 / 23:55:39 / cg"
@@ -494,7 +507,7 @@
     |u|
 
     u := (self at:'java.net.URL') basicNew.
-    u invoke:#'<init>(Ljava/lang/String;)V' with:(self as_String:aString).
+    u perform:#'<init>(Ljava/lang/String;)V' with:(self as_String:aString).
     ^ u
 
     "
@@ -646,7 +659,7 @@
 	(aKey startsWith:'JAVA::') ifTrue:[ Smalltalk removeKey:aKey ]
     ].
     Java_lang_String := Java_lang_Class := nil.
-    JavaInterpreter releaseAllJavaResources.
+    JavaVM releaseAllJavaResources.
     JavaUnresolvedConstant flushPatchLists.
 
     "
@@ -739,7 +752,8 @@
 !Java class methodsFor:'source management'!
 
 classSourceOf:aClass
-    |package dirName binary sourceFileName sourceFile dirHolder fileName path|
+    |package dirName binary sourceFileName sourceFile dirHolder fileName path
+     loader codeBaseURL protocol dir file|
 
     aClass isNil ifTrue:[
 	^ nil
@@ -754,6 +768,23 @@
 	binary := binary asFilename.
 	sourceFileName := binary withSuffix:'java'.
 	sourceFile := sourceFileName asFilename.
+    ] ifFalse:[
+	"/ maybe it was loaded by a java classLoader ...
+	(loader := aClass classLoader) notNil ifTrue:[
+	    (codeBaseURL := loader instVarNamed:'codeBaseURL') notNil ifTrue:[
+		(protocol := codeBaseURL instVarNamed:'protocol') notNil ifTrue:[
+		    (Java as_ST_String:protocol) = 'file' ifTrue:[
+			dirName := Java as_ST_String:(codeBaseURL instVarNamed:'file').
+			dirName asFilename exists ifTrue:[
+			    aClass sourceFile notNil ifTrue:[
+				sourceFileName := dirName asFilename construct:aClass sourceFile.
+				sourceFile := sourceFileName asFilename.
+			    ]
+			]
+		    ]
+		]
+	    ]
+	]
     ].
 
     sourceFile notNil ifTrue:[
@@ -825,7 +856,7 @@
     ].
     ^ (sourceFile contentsOfEntireFile).
 
-    "Modified: 3.8.1997 / 19:24:28 / cg"
+    "Modified: / 13.1.1998 / 14:56:39 / cg"
 !
 
 findSourceDirOf:fileName inPackage:aPackage
@@ -848,6 +879,27 @@
 
 !Java class methodsFor:'starting apps'!
 
+executeMainOf:aClass
+    "execute main of aClass in a separate thread and wait until that thread
+     has terminated."
+
+    |p|
+
+    p := self javaProcessForMainOf:aClass.
+    p notNil ifTrue:[
+        p resume.
+        Object abortSignal handle:[:ex |
+            p terminate.
+            ex reject.
+        ] do:[
+            p waitUntilTerminated
+        ].
+    ]
+
+    "Modified: / 15.1.1998 / 02:15:13 / cg"
+    "Created: / 15.1.1998 / 17:14:55 / cg"
+!
+
 javaProcessForMainOf:aJavaClass
     "ask for a commandLine, create a java process to invoke
      its main and return it. The process is not scheduled for
@@ -856,9 +908,9 @@
     |args|
 
     args := Dialog 
-                request:'argument string:' 
-                initialAnswer:LastArgumentString ? ''
-                onCancel:nil.
+		request:'argument string:' 
+		initialAnswer:LastArgumentString ? ''
+		onCancel:nil.
     args isNil ifTrue:[^ nil].
 
     LastArgumentString := args.
@@ -875,6 +927,9 @@
 
     |p argStringArray t|
 
+    JavaVM initializeVMIfNoEventThreadRunning.
+    (Java at:'java.lang.System') instVarNamed:'security' put:nil.
+
     argString isEmpty ifTrue:[
         argStringArray := #()
     ] ifFalse:[
@@ -882,11 +937,8 @@
                                 collect:[:s | Java as_String:s].
     ].
 
-    (Java at:'java.lang.System') instVarNamed:'security' put:nil.
-
     p := JavaProcess 
             for:[
-                    Java initSystemClass.
                     aJavaClass 
                         invoke:#'main'
                         signature:#'([Ljava/lang/String;)V'
@@ -898,12 +950,12 @@
     ^ p
 
     "Created: / 15.8.1997 / 04:41:20 / cg"
-    "Modified: / 4.1.1998 / 16:33:49 / cg"
+    "Modified: / 15.1.1998 / 17:33:18 / cg"
 ! !
 
 !Java class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/Java.st,v 1.47 1998/01/12 14:24:18 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/Java.st,v 1.48 1998/01/16 16:11:07 cg Exp $'
 ! !
 Java initialize!
--- a/JavaBuiltInClassPointerRef.st	Mon Jan 12 23:18:07 1998 +0000
+++ b/JavaBuiltInClassPointerRef.st	Fri Jan 16 16:12:55 1998 +0000
@@ -20,7 +20,7 @@
         ^ self
     ].
     nameandType = '[I' ifTrue:[     "/ int[]
-        class := IntegerArray.
+        class := SignedIntegerArray.
         ^ self
     ].
     nameandType = '[J' ifTrue:[     "/ long[]
@@ -28,7 +28,7 @@
         ^ self
     ].
     nameandType = '[S' ifTrue:[     "/ short[]
-        class := WordArray.
+        class := SignedWordArray.
         ^ self
     ].
     nameandType = '[C' ifTrue:[     "/ char[]
@@ -118,5 +118,5 @@
 !JavaBuiltInClassPointerRef class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaBuiltInClassPointerRef.st,v 1.4 1998/01/12 23:18:07 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaBuiltInClassPointerRef.st,v 1.5 1998/01/16 16:11:11 cg Exp $'
 ! !
--- a/JavaClass.st	Mon Jan 12 23:18:07 1998 +0000
+++ b/JavaClass.st	Fri Jan 16 16:12:55 1998 +0000
@@ -1,8 +1,8 @@
-'From Smalltalk/X, Version:3.3.1 on 6-jan-1998 at 9:18:43 pm'                   !
+'From Smalltalk/X, Version:3.3.1 on 15-jan-1998 at 7:53:24 pm'                  !
 
 Class subclass:#JavaClass
-	instanceVariableNames:'constantPool interfaces accessFlags classLoader fullName sourceFile
-		binaryFilePath fields initValues staticFields'
+	instanceVariableNames:'constantPool interfaces accessFlags classLoader fullName
+		sourceFile binaryFilePath fields initValues staticFields'
 	classVariableNames:'InitialValuePerType A_OBSOLETE A_INTERFACE A_PUBLIC A_FINAL
 		A_ABSTRACT A_INITIALIZED'
 	poolDictionaries:''
@@ -381,6 +381,26 @@
     "Created: 12.8.1997 / 02:46:51 / cg"
 ! !
 
+!JavaClass methodsFor:'browser interface'!
+
+isVisualStartable
+    "return true, if this is an application class,
+     which can be started via #open"
+
+    ^ (self compiledMethodAt:#'main([Ljava/lang/String;)V') notNil
+
+    "Modified: / 15.1.1998 / 17:20:00 / cg"
+!
+
+open
+    "start a thread for my main method"
+
+    Java executeMainOf:self
+
+    "Created: / 15.1.1998 / 17:18:30 / cg"
+    "Modified: / 15.1.1998 / 17:18:59 / cg"
+! !
+
 !JavaClass methodsFor:'compiler interface'!
 
 compilerClass
@@ -457,7 +477,7 @@
     accessFlags := accessFlags bitOr:A_INITIALIZED.
 
     superclass ~~ JavaObject ifTrue:[
-	superclass classInit
+        superclass classInit
     ].
 "/    "/ also, all referenced classes must be ...
 "/    constantPool classReferencesDo:[:aClass |
@@ -467,22 +487,18 @@
     m := self compiledMethodAt:#'<clinit>()V'.
     m notNil ifTrue:[
 "/        'calling clinit() of ' print. self fullName printNL.
-	[
-	    m valueWithReceiver:self arguments:#()
-"/            self 
-"/                invokeJavaMethod:m 
-"/                sender:thisContext
-"/                selector:#'<clinit>()V'.
-	] valueOnUnwindDo:[
-	    accessFlags := accessFlags bitXor:A_INITIALIZED.
-	]
+        [
+            m valueWithReceiver:self arguments:#()
+        ] valueOnUnwindDo:[
+            accessFlags := accessFlags bitXor:A_INITIALIZED.
+        ]
     ] ifFalse:[
 "/        self fullName print. ' has no clinit()' printNL.
     ].
 
     "
-     JavaInterpreter instructionTrace:true.
-     JavaInterpreter callTrace:true.
+     JavaVM instructionTrace:true.
+     JavaVM callTrace:true.
 
      (Java classNamed:'java.lang.String') classInit
      (Java classNamed:'java.lang.System') classInit
@@ -491,17 +507,7 @@
      (Java classNamed:'java.util.Properties') classInit 
     "
 
-    "Modified: / 4.1.1998 / 16:10:43 / cg"
-!
-
-initializeIfNotYetDone
-    "if not yet done, call the classes JAVA clinit function"
-
-    (accessFlags bitAnd:A_INITIALIZED) ~~ 0 ifTrue:[
-	self classInit
-    ]
-
-    "Created: 1.8.1997 / 22:37:40 / cg"
+    "Modified: / 13.1.1998 / 14:43:11 / cg"
 !
 
 initializeStaticFields
@@ -559,6 +565,12 @@
 
     |newJavaObject sz "{ Class: SmallInteger }"|
 
+    "/ (self isInterface or:[self isAbstract]) ifTrue:[
+    (accessFlags bitAnd:(A_INTERFACE bitOr:A_ABSTRACT)) ~~ 0 ifTrue:[
+        JavaVM throwInstantiationExceptionFor:self.
+        ^ nil
+    ].
+
     newJavaObject := super basicNew.
     initValues notNil ifTrue:[
         "/ newJavaObject initializeFields:initValues
@@ -576,7 +588,7 @@
      (Java classNamed:'java.lang.String') new inspect
     "
 
-    "Modified: / 4.1.1998 / 18:04:25 / cg"
+    "Modified: / 14.1.1998 / 23:16:19 / cg"
 !
 
 newCleared
@@ -586,22 +598,21 @@
 
     |newJavaObject sz "{ Class: SmallInteger }" |
 
-    newJavaObject := super basicNew.
-
-"/    fields isNil ifTrue:[
-"/	'OOPS - no fieldSpec for new object' errorPrintNL.
-"/	newJavaObject initializeToZero.     "/ mhmh
-"/    ] ifFalse:[
+    "/ (self isInterface or:[self isAbstract]) ifTrue:[
+    (accessFlags bitAnd:(A_INTERFACE bitOr:A_ABSTRACT)) ~~ 0 ifTrue:[
+        JavaVM throwInstantiationExceptionFor:self.
+        ^ nil
+    ].
 
-	initValues notNil ifTrue:[
-	    "/ newJavaObject initializeFields:initValues
-            sz := self instSize.
-            1 to:sz do:[:i |
-                newJavaObject instVarAt:i put:(initValues at:i)
-            ].
-	].
+    newJavaObject := super basicNew.
+    initValues notNil ifTrue:[
+        "/ newJavaObject initializeFields:initValues
+        sz := self instSize.
+        1 to:sz do:[:i |
+            newJavaObject instVarAt:i put:(initValues at:i)
+        ].
+    ].
 
-"/    ].
     ^ newJavaObject
 
     "
@@ -610,7 +621,7 @@
      (Java classNamed:'java.lang.String') new inspect
     "
 
-    "Modified: 18.3.1997 / 17:31:18 / cg"
+    "Modified: / 14.1.1998 / 23:16:26 / cg"
 !
 
 newFromInterpreter:anInterpreter sender:aJavaContext
@@ -701,30 +712,26 @@
 
     sel := selector asSymbolIfInterned.
     sel notNil ifTrue:[
-	cls := self.
-	[cls notNil and:[cls ~~ JavaObject]] whileTrue:[
-	    cls methodDictionary keysAndValuesDo:[:sel :aMethod |
+        cls := self.
+        [cls notNil and:[cls ~~ JavaObject]] whileTrue:[
+            cls methodDictionary keysAndValuesDo:[:sel :aMethod |
 
 "/     aMethod name printNL.
         
-		aMethod isStatic ifTrue:[
-		    sel == selector ifTrue:[
-			^ aMethod valueWithReceiver:self arguments:#()
-"/                        ^ self 
-"/                            invokeJavaMethod:aMethod 
-"/                            sender:thisContext
-"/                            selector:selector
-		    ]
-		]
-	    ].
-	    cls := cls superclass.
-	].
+                aMethod isStatic ifTrue:[
+                    sel == selector ifTrue:[
+                        ^ aMethod valueWithReceiver:self arguments:#()
+                    ]
+                ]
+            ].
+            cls := cls superclass.
+        ].
     ].
 
     ^ self doesNotUnderstand:(Message selector:selector)
 
-    "Created: 5.8.1997 / 14:35:34 / cg"
-    "Modified: 5.8.1997 / 14:36:54 / cg"
+    "Created: / 5.8.1997 / 14:35:34 / cg"
+    "Modified: / 15.1.1998 / 00:31:27 / cg"
 !
 
 lookupMethodFor:selector
@@ -1398,6 +1405,6 @@
 !JavaClass class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaClass.st,v 1.67 1998/01/12 14:24:21 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaClass.st,v 1.68 1998/01/16 16:11:12 cg Exp $'
 ! !
 JavaClass initialize!
--- a/JavaContext.st	Mon Jan 12 23:18:07 1998 +0000
+++ b/JavaContext.st	Fri Jan 16 16:12:55 1998 +0000
@@ -1,7 +1,7 @@
-'From Smalltalk/X, Version:3.3.1 on 7-jan-1998 at 9:54:49 pm'                   !
+'From Smalltalk/X, Version:3.3.1 on 15-jan-1998 at 4:28:10 pm'                  !
 
 Context subclass:#JavaContext
-	instanceVariableNames:'exArg byteCode constPool method'
+	instanceVariableNames:'exArg byteCode constPool method monitor'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Java-Support'
@@ -10,29 +10,30 @@
 
 !JavaContext methodsFor:'ST context mimicri'!
 
-argAt:n
-    |arg0Index|
+arg1Index
+    "the java stack contains the receiver in a non-static
+     method, as slot 0. Therefore, the first arg is found at slot2
+     if this is for a non-static method"
 
     self method isStatic ifTrue:[
-	arg0Index := 0
-    ] ifFalse:[
-	arg0Index := 1
+	^ 1
     ].
-    ^ self at:arg0Index+n
+    ^ 2
+!
+
+argAt:n
+    "return the i'th argument (1..nArgs)"
+
+    ^ self at:(self arg1Index - 1 + n)
 
     "Created: / 2.1.1998 / 17:54:13 / cg"
     "Modified: / 2.1.1998 / 21:39:30 / cg"
 !
 
 argAt:n put:value
-    |arg0Index|
+    "change the i'th argument (1..nArgs)"
 
-    self method isStatic ifTrue:[
-	arg0Index := 0
-    ] ifFalse:[
-	arg0Index := 1
-    ].
-    ^ super argAt:arg0Index+n put:value
+    ^ super argAt:(self arg1Index - 1 + n) put:value
 
     "Created: / 2.1.1998 / 17:54:34 / cg"
     "Modified: / 2.1.1998 / 21:35:19 / cg"
@@ -41,20 +42,15 @@
 args
     "return an array filled with the arguments of this context"
 
-    |n arg1Index|
+    |n|
 
     n := self numArgs.
     n == 0 ifTrue:[
-	"/ little optimization here - avaoid creating empty containers
+	"/ little optimization here - avoid creating empty containers
 	^ #()
     ].
 
-    self method isStatic ifTrue:[
-	arg1Index := 1
-    ] ifFalse:[
-	arg1Index := 2
-    ].
-    ^ (Array new:n) replaceFrom:1 to:n with:self startingAt:arg1Index.
+    ^ (Array new:n) replaceFrom:1 to:n with:self startingAt:(self arg1Index).
 
     "Created: / 2.1.1998 / 17:54:57 / cg"
     "Modified: / 2.1.1998 / 21:34:44 / cg"
@@ -63,22 +59,17 @@
 argsAndVars
     "return an array filled with the arguments and variables of this context"
 
-    |n arg1Index|
+    |n|
 
     n := self numArgs + self numVars.
     n == 0 ifTrue:[
-	"/ little optimization here - avaoid creating empty containers
-	^ #()
+        "/ little optimization here - avoid creating empty containers
+        ^ #()
     ].
-    self method isStatic ifTrue:[
-	arg1Index := 1
-    ] ifFalse:[
-	arg1Index := 2
-    ].
-    ^ (Array new:n) replaceFrom:1 to:n with:self startingAt:arg1Index.
+    ^ (Array new:n) replaceFrom:1 to:n with:self startingAt:(self arg1Index).
 
     "Created: / 2.1.1998 / 17:55:14 / cg"
-    "Modified: / 2.1.1998 / 21:35:39 / cg"
+    "Modified: / 13.1.1998 / 15:44:56 / cg"
 !
 
 lineNumber
@@ -88,24 +79,28 @@
 
 "/ 'ask line for pc:' print. pc printCR.
     pc isNil ifTrue:[
-	nr := self lineNumberFromMethod.
-	nr notNil ifTrue:[
-	    ^ nr
-	].
-	" '-> 0 [a]' printCR. " 
-	^0
+        nr := self lineNumberFromMethod.
+        nr notNil ifTrue:[
+            ^ nr
+        ].
+        " '-> 0 [a]' printCR. " 
+        ^0
     ].
 
     nr := self method lineNumberForPC:pc.
     nr isNil ifTrue:[
-	" '-> 0 [b]' printCR. " 
-	^ 0
+        nr := self lineNumberFromMethod.
+        nr notNil ifTrue:[
+            ^ nr
+        ].
+        " '-> 0 [b]' printCR. " 
+        ^ 0
     ].
 "/ '-> ' print. nr printCR.
      ^ nr.
 
     "Created: / 1.5.1996 / 15:05:47 / cg"
-    "Modified: / 6.1.1998 / 19:59:27 / cg"
+    "Modified: / 15.1.1998 / 15:25:29 / cg"
 !
 
 lineNumberFromMethod
@@ -138,7 +133,7 @@
 numArgs
     "return the number of args.
      Redefined since Java keeps the receiver of a non-static method
-     at local slot 0."
+     at local slot 1."
 
     |n|
 
@@ -151,6 +146,34 @@
     "Created: / 2.1.1998 / 22:21:24 / cg"
 !
 
+numTemps
+    "return the number of temporary variables of the Method.
+     Redefined since Java keeps the receiver of a non-static method
+     at local slot 1."
+
+    |n|
+
+    n := self size - super numVars - super numArgs.
+    ^ n
+
+    "Created: / 13.1.1998 / 16:52:32 / cg"
+    "Modified: / 13.1.1998 / 17:23:27 / cg"
+!
+
+numVars
+    "return the number of locals.
+     Redefined since Java keeps the receiver of a non-static method
+     at local slot 0 and holds the args as locals."
+
+    |n|
+
+    n := super numVars.
+    ^ n - self numArgs
+
+    "Created: / 13.1.1998 / 17:03:08 / cg"
+    "Modified: / 13.1.1998 / 17:25:16 / cg"
+!
+
 pc
     lineNr isNil ifTrue:[^ nil].
     ^ super lineNumber
@@ -180,6 +203,44 @@
     lineNr := newPC
 
     "Created: / 5.1.1998 / 00:09:02 / cg"
+!
+
+temporaries
+    "return an array filled with the arguments and variables of this context"
+
+    |n nSkipped|
+
+    "/ the flas-numVars includes the receiver and args
+    nSkipped := super numVars "self numArgs + self numVars".
+    "/ but my context setup is args+numvars.
+    nSkipped := super numArgs + super numVars.
+
+    n := self size - nSkipped.
+    n == 0 ifTrue:[
+        "/ little optimization here - avaoid creating empty containers
+        ^ #()
+    ].
+
+    ^ (Array new:n) replaceFrom:1 to:n with:self startingAt:nSkipped+1.
+
+    "Created: / 13.1.1998 / 15:44:12 / cg"
+    "Modified: / 13.1.1998 / 17:22:54 / cg"
+!
+
+vars 
+    "return an array filled with the local variables of this context"
+
+    |nonVars mySize|
+
+    mySize := self numVars.
+    mySize == 0 ifTrue:[
+        "/ little optimization here - avaoid creating empty containers
+        ^ #()
+    ].
+    nonVars := (self arg1Index-1) + self numArgs.
+    ^ (Array new:mySize) replaceFrom:1 to:mySize with:self startingAt:nonVars+1
+
+    "Created: / 13.1.1998 / 16:48:16 / cg"
 ! !
 
 !JavaContext methodsFor:'exception handler support'!
@@ -261,5 +322,5 @@
 !JavaContext class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaContext.st,v 1.19 1998/01/12 14:24:25 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaContext.st,v 1.20 1998/01/16 16:11:14 cg Exp $'
 ! !
--- a/JavaDecompiler.st	Mon Jan 12 23:18:07 1998 +0000
+++ b/JavaDecompiler.st	Fri Jan 16 16:12:55 1998 +0000
@@ -1,4 +1,4 @@
-'From Smalltalk/X, Version:3.3.1 on 5-jan-1998 at 2:09:45 pm'                   !
+'From Smalltalk/X, Version:3.3.1 on 14-jan-1998 at 12:00:35 am'                 !
 
 Object subclass:#JavaDecompiler
 	instanceVariableNames:'code pc javaMethod outStream classToCompileFor'
@@ -654,8 +654,10 @@
         ].
         outStream 
             show:((pc - 1 - 1) printStringPaddedTo:4); 
-            show:' '; 
-            show:op; 
+            show:' '.
+        outStream
+            show:(wide ifTrue:[op , '(w)'] ifFalse:[op]).
+        outStream
             show:' '.
 
         op == #wide ifTrue:[
@@ -665,7 +667,6 @@
                 spec from:2 to:spec size do:[:what |
                     wide ifTrue:[
                         self perform:(what , '_wide') asSymbol.
-                        wide := false
                     ] ifFalse:[
                         self perform:what
                     ]
@@ -677,7 +678,7 @@
     ]
 
     "Created: / 16.4.1996 / 14:59:29 / cg"
-    "Modified: / 5.1.1998 / 00:04:03 / cg"
+    "Modified: / 13.1.1998 / 23:58:34 / cg"
 ! !
 
 !JavaDecompiler methodsFor:'operand decoding'!
@@ -865,6 +866,12 @@
     "Modified: 16.4.1996 / 15:30:55 / cg"
 !
 
+signedByte_wide
+    self signedShort
+
+    "Created: / 13.1.1998 / 23:56:36 / cg"
+!
+
 signedShort
     |word constants|
 
@@ -950,6 +957,6 @@
 !JavaDecompiler class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaDecompiler.st,v 1.31 1998/01/05 18:47:13 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaDecompiler.st,v 1.32 1998/01/16 16:11:15 cg Exp $'
 ! !
 JavaDecompiler initialize!
--- a/JavaMethod.st	Mon Jan 12 23:18:07 1998 +0000
+++ b/JavaMethod.st	Fri Jan 16 16:12:55 1998 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:3.3.1 on 15-jan-1998 at 2:44:59 pm'                  !
+
 CompiledCode subclass:#JavaMethod
 	instanceVariableNames:'accessFlags selector javaClass exceptionHandlerTable
 		exceptionTable returnType signature lineNumberTable
@@ -677,14 +679,14 @@
     "Modified: / 3.1.1998 / 21:15:38 / cg"
 !
 
-numStack
-    ^super stackSize.
-"/    numStack isNil ifTrue:[^ 0].
-"/    ^ numStack
-!
+numVars
+    |n|
 
-numVars
-    ^ self numLocals - self numArgs
+    "/ a Java-stackframe includes the args in the locals
+    n := self numLocals - self numArgs.
+    ^ n
+
+    "Modified: / 13.1.1998 / 17:34:37 / cg"
 !
 
 previousVersion
@@ -985,6 +987,12 @@
     ^ JavaDecompiler
 
     "Created: 30.7.1997 / 16:36:48 / cg"
+!
+
+originalMethod
+    ^ self
+
+    "Created: / 13.1.1998 / 15:03:05 / cg"
 ! !
 
 !JavaMethod methodsFor:'methodref interchangability'!
@@ -1260,46 +1268,46 @@
 
     ForceByteCodeDisplay == true ifFalse:[
 
-	lineNumberTable notNil ifTrue:[
-	    classSource := javaClass source.
-	    classSource notNil ifTrue:[
-		lineNumberTable pairWiseDo:[:lPc :lNr |
-		    lPc >= pc ifTrue:[
-			"/ lPc == pc ifTrue:[^ lNr].
-			last isNil ifTrue:[^ lNr].
-			^ last.
-		    ].
-		    last := lNr.
-		].
-		last notNil ifTrue:[        
-		    ^ last
-		].
-		^ lineNumberTable at:2
-	    ].
-	].
+        lineNumberTable notNil ifTrue:[
+            classSource := javaClass source.
+            classSource notNil ifTrue:[
+                lineNumberTable pairWiseDo:[:lPc :lNr |
+                    lPc >= pc ifTrue:[
+                        lPc == pc ifTrue:[^ lNr].
+                        last isNil ifTrue:[^ lNr].
+                        ^ last.
+                    ].
+                    last := lNr.
+                ].
+                last notNil ifTrue:[        
+                    ^ last
+                ].
+                ^ lineNumberTable at:2
+            ].
+        ].
     ].
 
     "/ decompile and look which line the pc falls into
 
     ForceByteCodeDisplay == true ifTrue:[
-	text := self decompiledBytecode asCollectionOfLines.
+        text := self decompiledBytecode asCollectionOfLines.
     ] ifFalse:[
-	text := self decompiledSource asCollectionOfLines.
+        text := self decompiledSource asCollectionOfLines.
     ].
 
     text keysAndValuesDo:[:lineNr :line |
-	|nr|
+        |nr|
 
-	(line startsWith:'    ') ifFalse:[
-	    nr := Integer readFrom:line onError:0.
-	    nr >= pc ifTrue:[
-		^ lineNr
-	    ]
-	]
+        (line startsWith:'    ') ifFalse:[
+            nr := Integer readFrom:line onError:0.
+            nr >= pc ifTrue:[
+                ^ lineNr
+            ]
+        ]
     ].
     ^ num
 
-    "Modified: 12.8.1997 / 01:55:24 / cg"
+    "Modified: / 14.1.1998 / 13:30:54 / cg"
 !
 
 package
@@ -1347,6 +1355,41 @@
 
 !JavaMethod methodsFor:'vm support'!
 
+_aaload:arr _:index
+    "this is only invoked, if aaload encounters either a bad index
+     or an unknown array-class."
+
+    |i|
+
+    i := index + 1.
+    (i between:1 and:arr size) ifFalse:[
+        JavaVM throwArrayIndexOutOfBoundsException:index
+    ].
+
+    'Java: warning bad array in aaload' errorPrintCR.
+    ^ arr at:i
+
+    "Modified: / 14.1.1998 / 23:19:59 / cg"
+!
+
+_aastore:arr _:index _:num
+    "this is only invoked, if aastore encounters either a bad index,
+     or an unknown array-class."
+
+    |i|
+
+    i := index + 1.
+    (i between:1 and:arr size) ifFalse:[
+        JavaVM throwArrayIndexOutOfBoundsException:index
+    ].
+
+    'Java: warning bad array in aastore' errorPrintCR.
+    arr at:i put:num
+
+    "Modified: / 14.1.1998 / 23:19:42 / cg"
+    "Created: / 14.1.1998 / 23:22:01 / cg"
+!
+
 _arrayLength:arr
     ^ arr size
 
@@ -1376,11 +1419,17 @@
 
         ^ anObject isArray 
     ].
+    (aClassOrInterface isMemberOf:JavaBuiltInClassPointerRef) ifTrue:[
+        aClassOrInterface arrayClass == anObject class ifTrue:[
+            ^ true
+        ].
+    ].
+
     self halt.
     ^ false.
 
     "Created: / 4.1.1998 / 16:44:59 / cg"
-    "Modified: / 7.1.1998 / 00:01:26 / cg"
+    "Modified: / 13.1.1998 / 13:00:51 / cg"
 !
 
 _ddiv:op1 _:op2
@@ -1393,10 +1442,46 @@
     "Created: / 8.1.1998 / 00:39:23 / cg"
 !
 
+_iaload:arr _:index
+    "this is only invoked, if iaload encounters either a bad index
+     or an unknown array-class."
+
+    |i|
+
+    i := index + 1.
+    (i between:1 and:arr size) ifFalse:[
+        JavaVM throwArrayIndexOutOfBoundsException:index
+    ].
+
+    'Java: warning bad array in iaload' errorPrintCR.
+    ^ (arr at:i) asInteger
+
+    "Modified: / 14.1.1998 / 23:19:42 / cg"
+!
+
+_iastore:arr _:index _:num
+    "this is only invoked, if iastore encounters either a bad index,
+     bad number to store, or an unknown array-class."
+
+    |i|
+
+    i := index + 1.
+    (i between:1 and:arr size) ifFalse:[
+        JavaVM throwArrayIndexOutOfBoundsException:index
+    ].
+
+    'Java: warning bad array in iastore' errorPrintCR.
+    arr at:i put:num
+
+    "Modified: / 14.1.1998 / 23:19:42 / cg"
+    "Created: / 14.1.1998 / 23:21:38 / cg"
+!
+
 _l2d:op1
     ^ op1 asFloat
 
     "Created: / 7.1.1998 / 00:23:28 / cg"
+    "Modified: / 13.1.1998 / 14:31:59 / cg"
 !
 
 _ladd:op1 _:op2
@@ -1425,21 +1510,41 @@
 _ldiv:op1 _:op2
     |quo|
 
-    quo := op1 // op2.
+    quo := op1 quo: op2.
     ^ quo
 
     "Created: / 7.1.1998 / 00:17:23 / cg"
-    "Modified: / 7.1.1998 / 00:55:35 / cg"
+    "Modified: / 14.1.1998 / 13:38:38 / cg"
 !
 
 _lmul:op1 _:op2
-    |prod|
+    |prod o1 o2 sign|
+
+self halt.
+    "/ ST's largeIntegers compute a correct result;
+    "/ but here, we want the overflow to flow into the
+    "/ sign bit ... (sigh)
 
-    prod := (op1 * op2) bitAnd:16rFFFFFFFFFFFFFFFF.
+    sign := 1.
+    (o1 := op1) < 0 ifTrue:[
+        sign := -1.
+        o1 := o1 negated.
+    ].
+    (o2 := op2) < 0 ifTrue:[
+        sign := sign negated.
+        o2 := o2 negated.
+    ].
+
+    prod := (o1 * o2) bitAnd:16rFFFFFFFFFFFFFFFF.
+    (prod bitAnd:16r8000000000000000) ~~ 0 ifTrue:[
+    ].
+    sign == -1 ifTrue:[
+        prod := prod negated
+    ].
     ^ prod
 
     "Created: / 7.1.1998 / 00:17:34 / cg"
-    "Modified: / 9.1.1998 / 03:05:37 / cg"
+    "Modified: / 13.1.1998 / 17:48:51 / cg"
 !
 
 _lor:op1 _:op2
@@ -1538,18 +1643,6 @@
     "Modified: / 7.1.1998 / 21:22:00 / cg"
 !
 
-_monitorEnter:someObject
-    ^ JavaVM monitorEnter:someObject
-
-    "Modified: / 2.1.1998 / 23:45:36 / cg"
-!
-
-_monitorExit:someObject
-    ^ JavaVM monitorExit:someObject
-
-    "Created: / 2.1.1998 / 23:45:44 / cg"
-!
-
 _multiNew:typeRef _:dim1 
     |clsRef cls arr elType elSizes|
 
@@ -1614,18 +1707,47 @@
     "Created: / 5.1.1998 / 02:35:52 / cg"
 !
 
+divisionByZero
+    JavaVM 
+        throwExceptionClassName:'java.lang.ArithmeticException'
+        withMessage:'/ by zero'
+
+    "Created: / 15.1.1998 / 02:27:23 / cg"
+!
+
 enterSynchronized
 
     "Created: / 9.1.1998 / 10:53:10 / cg"
 !
 
+monitorEnter:someObject
+    ^ JavaVM monitorEnter:someObject
+
+    "Modified: / 2.1.1998 / 23:45:36 / cg"
+    "Created: / 14.1.1998 / 20:58:43 / cg"
+!
+
+monitorExit:someObject
+    ^ JavaVM monitorExit:someObject
+
+    "Created: / 14.1.1998 / 20:58:48 / cg"
+!
+
 nativeMethodInvokation
-    ^ JavaVM 
-	perform:('_' , javaClass name , '_' , self name , ':') asSymbol
-	with:thisContext sender.
+    |sel|
+
+    sel := ('_' , javaClass name , '_' , self name , ':') asSymbol.
+"/    (JavaVM respondsTo:sel) ifTrue:[
+        ^ JavaVM 
+            perform:sel
+            with:thisContext sender.
+"/    ].
+"/
+"/    self error:('unimplemented nativeMethod: ' , javaClass name , ' ' , self name).
+    ^ nil
 
     "Created: / 1.1.1998 / 15:16:14 / cg"
-    "Modified: / 4.1.1998 / 14:23:10 / cg"
+    "Modified: / 15.1.1998 / 01:51:03 / cg"
 !
 
 nullPointerException
@@ -1638,6 +1760,6 @@
 !JavaMethod class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaMethod.st,v 1.56 1998/01/12 19:07:18 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaMethod.st,v 1.57 1998/01/16 16:12:35 cg Exp $'
 ! !
 JavaMethod initialize!
--- a/JavaProcess.st	Mon Jan 12 23:18:07 1998 +0000
+++ b/JavaProcess.st	Fri Jan 16 16:12:55 1998 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:3.3.1 on 14-jan-1998 at 12:04:33 am'                 !
+
 Process subclass:#JavaProcess
 	instanceVariableNames:'suspendedContext'
 	classVariableNames:''
@@ -9,13 +11,19 @@
 !JavaProcess methodsFor:'accessing'!
 
 suspendedContext
-"/ ^ super suspendedContext.
+    |con|
+
+    suspendedContext notNil ifTrue:[^ suspendedContext].
 
-    suspendedContext isNil ifTrue:[^ super suspendedContext].
-    ^ suspendedContext
+    con := super suspendedContext.
+    [con notNil] whileTrue:[
+        (con isMemberOf:JavaContext) ifTrue:[^ con].
+        con := con sender.
+    ].
+    ^ super suspendedContext
 
-    "Created: 7.5.1996 / 09:02:03 / cg"
-    "Modified: 8.8.1997 / 00:39:10 / cg"
+    "Created: / 7.5.1996 / 09:02:03 / cg"
+    "Modified: / 13.1.1998 / 09:40:07 / cg"
 !
 
 suspendedContext:aContext
@@ -41,5 +49,5 @@
 !JavaProcess class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaProcess.st,v 1.8 1997/08/14 15:29:58 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaProcess.st,v 1.9 1998/01/16 16:12:38 cg Exp $'
 ! !
--- a/JavaUnresolvedClassConstant.st	Mon Jan 12 23:18:07 1998 +0000
+++ b/JavaUnresolvedClassConstant.st	Fri Jan 16 16:12:55 1998 +0000
@@ -185,7 +185,7 @@
             ^ ref
         ].
         fullName = '[I' ifTrue:[     "/ int[]
-            ref := JavaBuiltInClassPointerRef class:Array nameandType:fullName.
+            ref := JavaBuiltInClassPointerRef class:SignedIntegerArray nameandType:fullName.
             constantPool at:constantPoolIndex put:ref.
             ^ ref
         ].
@@ -195,7 +195,7 @@
             ^ ref
         ].
         fullName = '[S' ifTrue:[     "/ short[]
-            ref := JavaBuiltInClassPointerRef class:WordArray nameandType:fullName.
+            ref := JavaBuiltInClassPointerRef class:SignedWordArray nameandType:fullName.
             constantPool at:constantPoolIndex put:ref.
             ^ ref
         ].
@@ -242,5 +242,5 @@
 !JavaUnresolvedClassConstant class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaUnresolvedClassConstant.st,v 1.23 1998/01/12 14:24:38 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaUnresolvedClassConstant.st,v 1.24 1998/01/16 16:12:39 cg Exp $'
 ! !
--- a/JavaVM.st	Mon Jan 12 23:18:07 1998 +0000
+++ b/JavaVM.st	Fri Jan 16 16:12:55 1998 +0000
@@ -1,4 +1,4 @@
-'From Smalltalk/X, Version:3.3.1 on 12-jan-1998 at 1:26:02 pm'                  !
+'From Smalltalk/X, Version:3.3.1 on 16-jan-1998 at 3:05:32 pm'                  !
 
 Object subclass:#JavaVM
 	instanceVariableNames:''
@@ -13,11 +13,382 @@
 		FileOpenConfirmation FileIOTrace OpenFileTable
 		CachedNativeMethodTable ExceptionDebug JavaConsoleStream
 		StandardThreadGroup EnteredMonitorsPerProcess JavaClasses
-		DUMMY_LONG_HIGHWORD DUMMY_DOUBLE_HIGHWORD'
+		DUMMY_LONG_HIGHWORD DUMMY_DOUBLE_HIGHWORD NoAudio'
 	poolDictionaries:''
 	category:'Java-Support'
 !
 
+!JavaVM class methodsFor:'documentation'!
+
+nativeMethods
+"
+    list of all native methods as in jdk1.1.3:
+
+      X - implemented
+      x - implemented with limited functionality
+      o - implemented as dummy (no functionality)
+
+    X (Math::double sin (double))
+    X (Math::double cos (double))
+      (Math::double tan (double))
+      (Math::double asin (double))
+      (Math::double acos (double))
+      (Math::double atan (double))
+      (Math::double exp (double))
+    X (Math::double log (double))
+    X (Math::double sqrt (double))
+      (Math::double IEEEremainder (double double))
+    X (Math::double ceil (double))
+    X (Math::double floor (double))
+      (Math::double rint (double))
+      (Math::double atan2 (double double))
+    X (Math::double pow (double double))
+
+    X (Class::java.lang.Class forName (java.lang.String))
+    X (Class::java.lang.Object newInstance ())
+      (Class::boolean isInstance (java.lang.Object))
+      (Class::boolean isAssignableFrom (java.lang.Class))
+    X (Class::boolean isInterface ())
+      (Class::boolean isArray ())
+      (Class::boolean isPrimitive ())
+    X (Class::java.lang.String getName ())
+    X (Class::java.lang.ClassLoader getClassLoader ())
+    X (Class::java.lang.Class getSuperclass ())
+      (Class::java.lang.Class[] getInterfaces ())
+      (Class::java.lang.Class getComponentType ())
+      (Class::int getModifiers ())
+      (Class::java.lang.Object[] getSigners ())
+      (Class::void setSigners (java.lang.Object[]))
+    X (Class::java.lang.Class getPrimitiveClass (java.lang.String))
+      (Class::java.lang.reflect.Field[] getFields0 (int))
+      (Class::java.lang.reflect.Method[] getMethods0 (int))
+      (Class::java.lang.reflect.Constructor[] getConstructors0 (int))
+      (Class::java.lang.reflect.Field getField0 (java.lang.String int))
+      (Class::java.lang.reflect.Method getMethod0 (java.lang.String java.lang.Class[] int))
+      (Class::java.lang.reflect.Constructor getConstructor0 (java.lang.Class[] int))
+
+    X (InetAddressImpl::java.lang.String getLocalHostName ())
+    X (InetAddressImpl::void makeAnyLocalAddress (java.net.InetAddress))
+    X (InetAddressImpl::byte[][] lookupAllHostAddr (java.lang.String))
+      (InetAddressImpl::java.lang.String getHostByAddr (int))
+    X (InetAddressImpl::int getInetFamily ())
+
+    X (ResourceBundle::java.lang.Class[] getClassContext ())
+
+    X (System::void setIn0 (java.io.InputStream))
+    X (System::void setOut0 (java.io.PrintStream))
+    X (System::void setErr0 (java.io.PrintStream))
+    X (System::long currentTimeMillis ())
+    X (System::void arraycopy (java.lang.Object int java.lang.Object int int))
+      (System::int identityHashCode (java.lang.Object))
+    X (System::java.util.Properties initProperties (java.util.Properties))
+
+    X (Thread::java.lang.Thread currentThread ())
+    X (Thread::void yield ())
+    X (Thread::void sleep (long))
+    X (Thread::void start ())
+    X (Thread::boolean isInterrupted (boolean))
+    X (Thread::boolean isAlive ())
+      (Thread::int countStackFrames ())
+    X (Thread::void setPriority0 (int))
+    X (Thread::void stop0 (java.lang.Object))
+    X (Thread::void suspend0 ())
+    X (Thread::void resume0 ())
+      (Thread::void interrupt0 ())
+
+    (String::java.lang.String intern ())
+
+    X (Float::int floatToIntBits (float))
+    X (Float::float intBitsToFloat (int))
+
+      (ObjectStreamClass::int getClassAccess (java.lang.Class))
+      (ObjectStreamClass::java.lang.String[] getMethodSignatures (java.lang.Class))
+      (ObjectStreamClass::int getMethodAccess (java.lang.Class java.lang.String))
+      (ObjectStreamClass::java.lang.String[] getFieldSignatures (java.lang.Class))
+      (ObjectStreamClass::int getFieldAccess (java.lang.Class java.lang.String))
+      (ObjectStreamClass::java.io.ObjectStreamField[] getFields0 (java.lang.Class))
+      (ObjectStreamClass::long getSerialVersionUID (java.lang.Class))
+      (ObjectStreamClass::boolean hasWriteObject (java.lang.Class))
+      (ObjectInputStream::java.lang.Class loadClass0 (java.lang.Class java.lang.String))
+      (ObjectInputStream::void inputClassFields (java.lang.Object java.lang.Class int[]))
+      (ObjectInputStream::java.lang.Object allocateNewObject (java.lang.Class java.lang.Class))
+      (ObjectInputStream::java.lang.Object allocateNewArray (java.lang.Class int))
+      (ObjectInputStream::boolean invokeObjectReader (java.lang.Object java.lang.Class))
+
+      (SecurityManager::java.lang.Class[] getClassContext ())
+    X (SecurityManager::java.lang.ClassLoader currentClassLoader ())
+      (SecurityManager::int classDepth (java.lang.String))
+    X (SecurityManager::int classLoaderDepth ())
+      (SecurityManager::java.lang.Class currentLoadedClass0 ())
+
+    X (ClassLoader::void init ())
+    X (ClassLoader::java.lang.Class defineClass0 (java.lang.String byte[] int int))
+    X (ClassLoader::void resolveClass0 (java.lang.Class))
+    X (ClassLoader::java.lang.Class findSystemClass0 (java.lang.String))
+    X (ClassLoader::java.io.InputStream getSystemResourceAsStream0 (java.lang.String))
+      (ClassLoader::java.lang.String getSystemResourceAsName0 (java.lang.String))
+
+      (FileDescriptor::boolean valid ())
+      (FileDescriptor::void sync ())
+    X (FileDescriptor::java.io.FileDescriptor initSystemFD (java.io.FileDescriptor int))
+
+    X (Object::java.lang.Class getClass ())
+    X (Object::int hashCode ())
+    X (Object::java.lang.Object clone ())
+    X (Object::void notify ())
+    X (Object::void notifyAll ())
+    X (Object::void wait (long))
+
+    X (FileOutputStream::void open (java.lang.String))
+      (FileOutputStream::void openAppend (java.lang.String))
+    X (FileOutputStream::void write (int))
+    X (FileOutputStream::void writeBytes (byte[] int int))
+    X (FileOutputStream::void close ())
+    X (FileInputStream::void open (java.lang.String))
+    X (FileInputStream::int read ())
+    X (FileInputStream::int readBytes (byte[] int int))
+      (FileInputStream::long skip (long))
+    X (FileInputStream::int available ())
+    X (FileInputStream::void close ())
+
+      (VM::int getState ())
+      (VM::boolean threadsSuspended ())
+      (VM::void unsuspendThreads ())
+      (VM::void unsuspendSomeThreads ())
+
+    X (File::boolean exists0 ())
+      (File::boolean canWrite0 ())
+    X (File::boolean canRead0 ())
+    X (File::boolean isFile0 ())
+    X (File::boolean isDirectory0 ())
+      (File::long lastModified0 ())
+    X (File::long length0 ())
+      (File::boolean mkdir0 ())
+      (File::boolean renameTo0 (java.io.File))
+      (File::boolean delete0 ())
+      (File::boolean rmdir0 ())
+    X (File::java.lang.String[] list0 ())
+      (File::java.lang.String canonPath (java.lang.String))
+    X (File::boolean isAbsolute ())
+
+      (ObjectOutputStream::void outputClassFields (java.lang.Object java.lang.Class int[]))
+      (ObjectOutputStream::boolean invokeObjectWriter (java.lang.Object java.lang.Class))
+
+    X (Throwable::void printStackTrace0 (java.lang.Object))
+    X (Throwable::java.lang.Throwable fillInStackTrace ())
+
+    X (Double::long doubleToLongBits (double))
+    X (Double::double longBitsToDouble (long))
+    X (Double::double valueOf0 (java.lang.String))
+
+    X (Runtime::void exitInternal (int))
+      (Runtime::void runFinalizersOnExit0 (boolean))
+    o (Runtime::java.lang.Process execInternal (java.lang.String[] java.lang.String[]))
+    X (Runtime::long freeMemory ())
+    X (Runtime::long totalMemory ())
+    X (Runtime::void gc ())
+      (Runtime::void runFinalization ())
+      (Runtime::void traceInstructions (boolean))
+      (Runtime::void traceMethodCalls (boolean))
+    X (Runtime::java.lang.String initializeLinkerInternal ())
+    X (Runtime::java.lang.String buildLibName (java.lang.String java.lang.String))
+    X (Runtime::int loadFileInternal (java.lang.String))
+
+      (WDrawingSurfaceInfo::int lock ())
+      (WDrawingSurfaceInfo::void unlock ())
+      (WDrawingSurfaceInfo::int getHWnd ())
+      (WDrawingSurfaceInfo::int getHBitmap ())
+      (WDrawingSurfaceInfo::int getPBits ())
+      (WDrawingSurfaceInfo::int getHDC ())
+      (WDrawingSurfaceInfo::int getDepth ())
+      (WDrawingSurfaceInfo::int getHPalette ())
+
+    X (WDefaultFontCharset::boolean canConvert (char))
+
+      (ColorModel::void deletepData ())
+    X (WToolkit::void init (java.lang.Thread))
+    X (WToolkit::void eventLoop ())
+      (WToolkit::java.awt.image.ColorModel makeColorModel ())
+      (WToolkit::int getScreenResolution ())
+    X (WToolkit::int getScreenWidth ())
+    X (WToolkit::int getScreenHeight ())
+      (WToolkit::void sync ())
+      (WToolkit::void beep ())
+    X (WToolkit::void loadSystemColors (int[]))
+
+      (WPrintJob::void end ())
+
+    X (WDialogPeer::void create (sun.awt.windows.WComponentPeer))
+    X (WDialogPeer::void _show ())
+    X (WDialogPeer::void _hide ())
+
+      (WWindowPeer::void toFront ())
+      (WWindowPeer::void toBack ())
+      (WWindowPeer::void _setTitle (java.lang.String))
+      (WWindowPeer::void _setResizable (boolean))
+      (WWindowPeer::void create (sun.awt.windows.WComponentPeer))
+      (WWindowPeer::void updateInsets (java.awt.Insets))
+      (WWindowPeer::java.awt.Component getContainerElement (java.awt.Container int))
+
+    X (WCanvasPeer::void create (sun.awt.windows.WComponentPeer))
+
+    X (WTextAreaPeer::void create (sun.awt.windows.WComponentPeer))
+    X (WTextAreaPeer::void insertText (java.lang.String int))
+      (WTextAreaPeer::void replaceText (java.lang.String int int))
+
+    X (WTextComponentPeer::java.lang.String getText ())
+    X (WTextComponentPeer::void setText (java.lang.String))
+    X (WTextComponentPeer::int getSelectionStart ())
+    X (WTextComponentPeer::int getSelectionEnd ())
+    X (WTextComponentPeer::void select (int int))
+    X (WTextComponentPeer::void enableEditing (boolean))
+
+    X (WComponentPeer::void show ())
+    X (WComponentPeer::void hide ())
+    X (WComponentPeer::void enable ())
+    X (WComponentPeer::void disable ())
+      (WComponentPeer::java.awt.Point getLocationOnScreen ())
+    X (WComponentPeer::void reshape (int int int int))
+    o (WComponentPeer::void handleEvent (java.awt.AWTEvent))
+    o (WComponentPeer::void _dispose ())
+    X (WComponentPeer::void _setForeground (int))
+    X (WComponentPeer::void _setBackground (int))
+    o (WComponentPeer::void setFont (java.awt.Font))
+    o (WComponentPeer::void requestFocus ())
+    o (WComponentPeer::void setCursor (java.awt.Cursor))
+    o (WComponentPeer::void start ())
+      (WComponentPeer::void _beginValidate ())
+      (WComponentPeer::void endValidate ())
+    o (WComponentPeer::void setZOrderPosition (sun.awt.windows.WComponentPeer))
+
+    X (WFramePeer::void setMenuBar0 (sun.awt.windows.WMenuBarPeer))
+    X (WFramePeer::void create (sun.awt.windows.WComponentPeer))
+      (WFramePeer::void _setIconImage (sun.awt.image.ImageRepresentation))
+
+    o (WFontMetrics::boolean needsConversion (java.awt.Font sun.awt.FontDescriptor))
+    o (WFontMetrics::int getMFCharSegmentWidth (java.awt.Font sun.awt.FontDescriptor boolean char[] int int byte[] int))
+      (WFontMetrics::int bytesWidth (byte[] int int))
+      (WFontMetrics::void init ())
+
+    o (WChoicePeer::void select (int))
+    o (WChoicePeer::void remove (int))
+    o (WChoicePeer::void addItem (java.lang.String int))
+    X (WChoicePeer::void reshape (int int int int))
+    X (WChoicePeer::void create (sun.awt.windows.WComponentPeer))
+
+    X (WLabelPeer::void setText (java.lang.String))
+    o (WLabelPeer::void setAlignment (int))
+    X (WLabelPeer::void create (sun.awt.windows.WComponentPeer))
+
+    X (WMenuItemPeer::void _setLabel (java.lang.String))
+    X (WMenuItemPeer::void create (sun.awt.windows.WMenuPeer))
+    X (WMenuItemPeer::void enable (boolean))
+      (WMenuItemPeer::void _dispose ())
+      (WMenuPeer::void addSeparator ())
+      (WMenuPeer::void delItem (int))
+    X (WMenuPeer::void createMenu (sun.awt.windows.WMenuBarPeer))
+      (WMenuPeer::void createSubMenu (sun.awt.windows.WMenuPeer))
+
+      (WPopupMenuPeer::void createMenu (sun.awt.windows.WComponentPeer))
+      (WPopupMenuPeer::void _show (java.awt.Event))
+      (WMenuBarPeer::void addMenu (java.awt.Menu))
+      (WMenuBarPeer::void delMenu (int))
+    X (WMenuBarPeer::void create (sun.awt.windows.WFramePeer))
+
+      (WCheckboxMenuItemPeer::void setState (boolean))
+
+    X (WFileDialogPeer::void show ())
+
+    X (WCheckboxPeer::void setState (boolean))
+    X (WCheckboxPeer::void setCheckboxGroup (java.awt.CheckboxGroup))
+      (WCheckboxPeer::void setLabel (java.lang.String))
+    X (WCheckboxPeer::void create (sun.awt.windows.WComponentPeer))
+
+    X (WClipboard::void init ())
+      (WClipboard::void setClipboardText (java.awt.datatransfer.StringSelection))
+      (WClipboard::java.lang.String getClipboardText ())
+
+      (WListPeer::void addItem (java.lang.String int))
+      (WListPeer::void delItems (int int))
+      (WListPeer::void select (int))
+      (WListPeer::void deselect (int))
+      (WListPeer::void makeVisible (int))
+      (WListPeer::void setMultipleSelections (boolean))
+      (WListPeer::void create (sun.awt.windows.WComponentPeer))
+      (WListPeer::boolean isSelected (int))
+
+    o (WScrollbarPeer::void _setValues (int int int int))
+      (WScrollbarPeer::void setLineIncrement (int))
+      (WScrollbarPeer::void setPageIncrement (int))
+    o (WScrollbarPeer::void create (sun.awt.windows.WComponentPeer))
+
+    o (ImageRepresentation::void offscreenInit (java.awt.Color))
+    x (ImageRepresentation::boolean setBytePixels (int int int int java.awt.image.ColorModel byte[] int int))
+      (ImageRepresentation::boolean setIntPixels (int int int int java.awt.image.ColorModel int[] int int))
+    x (ImageRepresentation::boolean finish (boolean))
+    X (ImageRepresentation::void imageDraw (java.awt.Graphics int int java.awt.Color))
+    x (ImageRepresentation::void imageStretch (java.awt.Graphics int int int int int int int int java.awt.Color))
+    x (ImageRepresentation::void disposeImage ())
+
+    X (WTextFieldPeer::void create (sun.awt.windows.WComponentPeer))
+      (WTextFieldPeer::void setEchoCharacter (char))
+
+      (WScrollPanePeer::void create (sun.awt.windows.WComponentPeer))
+      (WScrollPanePeer::int getOffset (int))
+      (WScrollPanePeer::void setInsets ())
+      (WScrollPanePeer::void setScrollPosition (int int))
+      (WScrollPanePeer::int _getHScrollbarHeight ())
+      (WScrollPanePeer::int _getVScrollbarWidth ())
+      (WScrollPanePeer::void setSpans (int int int int))
+      (WScrollPanePeer::java.awt.Component getScrollChild ())
+
+      (WEmbeddedFramePeer::void create (sun.awt.windows.WComponentPeer))
+      (WButtonPeer::void setLabel (java.lang.String))
+    X (WButtonPeer::void create (sun.awt.windows.WComponentPeer))
+
+    x (WColor::java.awt.Color getDefaultColor (int))
+
+    x (GifImageDecoder::boolean parseImage (int int int int boolean int byte[] byte[] java.awt.image.IndexColorModel))
+
+    x (WGraphics::void createFromComponent (sun.awt.windows.WComponentPeer))
+    x (WGraphics::void createFromGraphics (sun.awt.windows.WGraphics))
+      (WGraphics::void createFromPrintJob (sun.awt.windows.WPrintJob))
+      (WGraphics::void createFromHDC (int))
+    x (WGraphics::void imageCreate (sun.awt.image.ImageRepresentation))
+    x (WGraphics::void pSetFont (java.awt.Font))
+    X (WGraphics::void pSetForeground (int))
+      (WGraphics::void _dispose ())
+    x (WGraphics::void dispose ())
+    x (WGraphics::void setPaintMode ())
+      (WGraphics::void setXORMode (java.awt.Color))
+    o (WGraphics::java.awt.Rectangle getClipBounds ())
+    o (WGraphics::void changeClip (int int int int boolean))
+      (WGraphics::void removeClip ())
+    X (WGraphics::void clearRect (int int int int))
+    X (WGraphics::void fillRect (int int int int))
+    X (WGraphics::void drawRect (int int int int))
+      (WGraphics::void drawSFChars (char[] int int int int))
+    x (WGraphics::int drawMFCharsSegment (java.awt.Font sun.awt.FontDescriptor char[] int int int int))
+      (WGraphics::int drawMFCharsConvertedSegment (java.awt.Font sun.awt.FontDescriptor byte[] int int int))
+      (WGraphics::void drawBytes (byte[] int int int int))
+    X (WGraphics::void drawLine (int int int int))
+      (WGraphics::void copyArea (int int int int int int))
+    o (WGraphics::void drawRoundRect (int int int int int int))
+    o (WGraphics::void fillRoundRect (int int int int int int))
+    X (WGraphics::void drawPolygon (int[] int[] int))
+      (WGraphics::void drawPolyline (int[] int[] int))
+    X (WGraphics::void fillPolygon (int[] int[] int))
+    x (WGraphics::void drawOval (int int int int))
+    x (WGraphics::void fillOval (int int int int))
+    x (WGraphics::void drawArc (int int int int int int))
+    x (WGraphics::void fillArc (int int int int int int))
+      (WGraphics::void print (sun.awt.windows.WComponentPeer))
+      (WGraphics::void close (sun.awt.windows.WPrintJob))
+      (JPEGImageDecoder::void readImage (java.io.InputStream byte[]))
+      (OffScreenImageSource::void sendPixels ())
+"
+
+! !
 
 !JavaVM class methodsFor:'initialization'!
 
@@ -51,6 +422,7 @@
     DUMMY_DOUBLE_HIGHWORD := 2.
 
     StandardThreadGroup := nil.
+    NoAudio := true.
 
     JavaConsoleStream := Transcript.
 
@@ -99,7 +471,7 @@
     "
 
     "Created: / 2.1.1998 / 18:02:34 / cg"
-    "Modified: / 7.1.1998 / 23:59:25 / cg"
+    "Modified: / 14.1.1998 / 14:56:50 / cg"
 !
 
 initializeBaseClasses
@@ -119,9 +491,9 @@
 
 initializeOpenFileTable
     OpenFileTable := OrderedCollection 
-                        with:Stdin 
-                        with:(JavaConsoleStream ? Stdout)
-                        with:(JavaConsoleStream ? Stderr).
+			with:Stdin 
+			with:(JavaConsoleStream ? Stdout)
+			with:(JavaConsoleStream ? Stderr).
 
     "
      JavaVM initializeOpenFileTable
@@ -133,32 +505,32 @@
 
 initializePrimitiveClasses
     JavaClasses isNil ifTrue:[
-        JavaClasses := Dictionary new.
+	JavaClasses := Dictionary new.
     ].
 
     #(
-        ('byte'    'B' 1)
-        ('short'   'S' 2)
-        ('int'     'I' 4)
-        ('long'    'J' 8)
-        ('boolean' 'Z' 1)
-        ('char'    'C' 2)
-        ('float'   'F' 4)
-        ('double'  'D' 8)
-        ('void'    'V' 0)
+	('byte'    'B' 1)
+	('short'   'S' 2)
+	('int'     'I' 4)
+	('long'    'J' 8)
+	('boolean' 'Z' 1)
+	('char'    'C' 2)
+	('float'   'F' 4)
+	('double'  'D' 8)
+	('void'    'V' 0)
     ) triplesDo:[:nm :sig :len |
-        |stClass jClass|
-
-        "/
-        "/ create a javaClass for it.
-        "/
-        jClass := (Java at:'java.lang.Class') new.
+	|stClass jClass|
+
+	"/
+	"/ create a javaClass for it.
+	"/
+	jClass := (Java at:'java.lang.Class') new.
 "/        stClass := Class new.
 "/        stClass setName:('JavaBase_' , nm) asSymbol.
 "/        JavaClasses at:stClass put:jClass.
 "/        JavaClasses at:jClass put:stClass.
 
-        JavaClasses at:nm put:jClass
+	JavaClasses at:nm put:jClass
     ].
 
     "
@@ -171,14 +543,14 @@
 initializeSimulatedLibs
     LibPath := #('__builtIn__' '/usr/local/lib' '/usr/local/lib/java'). 
     SimulatedLibs := #('__builtIn__/net' 
-                       '__builtIn__/awt' 
-                       '__builtIn__/tawt' 
-                       '__builtIn__/winawt' 
-                       '__builtIn__/jpeg'
-                       '__builtIn__/mmedia'
-                       '__builtIn__/zip'
-                       '__builtIn__/math'
-                      ).
+		       '__builtIn__/awt' 
+		       '__builtIn__/tawt' 
+		       '__builtIn__/winawt' 
+		       '__builtIn__/jpeg'
+		       '__builtIn__/mmedia'
+		       '__builtIn__/zip'
+		       '__builtIn__/math'
+		      ).
 
     "Created: / 4.1.1998 / 19:05:03 / cg"
 !
@@ -189,7 +561,7 @@
     "/ use JAVA compatible cpu-name
     cpu := OperatingSystem getCPUType.
     cpu = 'i386' ifTrue:[
-        cpu := 'ix86'
+	cpu := 'ix86'
     ].
     os := OperatingSystem getOSType.
     os := os asUppercaseFirst.
@@ -231,12 +603,16 @@
     KnownWindows := nil.
     JavaWindowGroup := nil.
 
+    JavaConsoleStream := Transcript.
+
     self terminateAllThreads.
 
     Java initAllStaticFields.
     Java markAllClassesUninitialized.
 
     self releaseAllMonitors.
+    self releaseAllWindows.
+    self releaseAllStreams.
 
     self initializeSimulatedLibs.
     self initializeOpenFileTable.
@@ -254,7 +630,20 @@
     "
 
     "Created: / 3.1.1998 / 21:29:09 / cg"
-    "Modified: / 9.1.1998 / 10:29:27 / cg"
+    "Modified: / 15.1.1998 / 17:29:34 / cg"
+!
+
+initializeVMIfNoEventThreadRunning
+    (JavaEventThread isNil or:[JavaEventThread isDead]) ifTrue:[
+        self initializeVM
+    ].
+
+    "
+     JavaVM initializeVMIfNoEventThreadRunning
+    "
+
+    "Modified: / 15.1.1998 / 17:29:34 / cg"
+    "Created: / 15.1.1998 / 17:32:27 / cg"
 !
 
 releaseAllJavaResources
@@ -294,7 +683,7 @@
     self initializeOpenFileTable.
 
     "
-     JavaInterpreter releaseAllStreams
+     JavaVM releaseAllStreams
     "
 
     "Modified: / 6.8.1997 / 00:40:55 / cg"
@@ -303,10 +692,10 @@
 
 releaseAllWindows
     KnownWindows notNil ifTrue:[
-        KnownWindows do:[:aView |
-            aView destroy
-        ].
-        KnownWindows := nil.
+	KnownWindows do:[:aView |
+	    aView destroy
+	].
+	KnownWindows := nil.
     ]
 
     "
@@ -324,16 +713,16 @@
     deadProcesses := IdentitySet new.
 
     EnteredMonitorsPerProcess keysAndValuesDo:[:p :monitors |
-        p isDead ifTrue:[
-            monitors do:[:mon |
-                Transcript showCR:'release leftover monitor ...'.
-                mon release
-            ].
-            deadProcesses add:p.
-        ]
+	p isDead ifTrue:[
+	    monitors do:[:mon |
+		Transcript showCR:'release leftover monitor ...'.
+		mon release
+	    ].
+	    deadProcesses add:p.
+	]
     ].
     deadProcesses do:[:p |
-        EnteredMonitorsPerProcess removeKey:p
+	EnteredMonitorsPerProcess removeKey:p
     ].
 
     "
@@ -356,14 +745,16 @@
 !
 
 terminateAllThreads
-    Java terminateAllThreads
+    Java terminateAllThreads.
+    JavaEventThread := nil.
 
     "Created: / 8.1.1998 / 17:43:54 / cg"
+    "Modified: / 15.1.1998 / 17:29:00 / cg"
 !
 
 update:something with:aParameter from:changedObject
     something == #returnFromSnapshot ifTrue:[
-         self initializeVM
+	 self initializeVM
     ].
 
     "
@@ -425,10 +816,10 @@
 
     s := '' writeStream.
     Java classPath do:[:p |
-        s size == 0 ifFalse:[
-            s nextPut:$:
-        ].
-        s nextPutAll:p.
+	s size == 0 ifFalse:[
+	    s nextPut:$:
+	].
+	s nextPutAll:p.
     ].
 
     ^ s contents
@@ -466,7 +857,7 @@
     "/ prefer the windows toolkit ...
 
     (Java classForName:'sun.awt.windows.WToolkit') notNil ifTrue:[
-        ^ 'sun.awt.windows.WToolkit'.
+	^ 'sun.awt.windows.WToolkit'.
     ].
 "/    (Java classForName:'sun.awt.motif.MToolkit') notNil ifTrue:[
 "/        ^ 'sun.awt.motif.MToolkit'.
@@ -486,7 +877,7 @@
     JavaConsoleStream := aStream
 
     "
-     JavaInterpreter javaConsole:Transcript
+     JavaVM javaConsole:Transcript
     "
 
     "Modified: / 6.8.1997 / 00:34:13 / cg"
@@ -517,7 +908,7 @@
 
 setOpenFile:aStream at:idx
     OpenFileTable size < (idx+1) ifTrue:[
-        OpenFileTable grow:idx+1.
+	OpenFileTable grow:idx+1.
     ].
     OpenFileTable at:idx+1 put:aStream.
 
@@ -532,8 +923,8 @@
     p := Processor activeProcess.
     monitors := EnteredMonitorsPerProcess at:p ifAbsent:nil.
     monitors isNil ifTrue:[
-        monitors := OrderedCollection new.
-        EnteredMonitorsPerProcess at:p put:monitors.
+	monitors := OrderedCollection new.
+	EnteredMonitorsPerProcess at:p put:monitors.
     ].
     ^ monitors
 
@@ -545,7 +936,7 @@
 
     t := Java threads keyAtValue:stProcess ifAbsent:nil.
     t == 0 ifTrue:[
-        ^ nil
+	^ nil
     ].
     ^ t
 
@@ -578,7 +969,7 @@
 
     p := Java threads at:jThread ifAbsent:nil.
     p == 0 ifTrue:[
-        ^ nil
+	^ nil
     ].
     ^ p
 
@@ -590,19 +981,19 @@
     |standardGroup threadClass|
 
     StandardThreadGroup isNil ifTrue:[
-        threadClass := Java at:'java.lang.Thread'.
-
-        standardGroup := (Java at:'java.lang.ThreadGroup') new.
-        standardGroup instVarNamed:'parent'      put:nil.
-        standardGroup instVarNamed:'name'        put:(Java as_String:'main').
-        standardGroup instVarNamed:'maxPriority' put:(threadClass instVarNamed:'MAX_PRIORITY').
-        standardGroup instVarNamed:'destroyed'   put:0.
-        standardGroup instVarNamed:'daemon'      put:nil.
-        standardGroup instVarNamed:'vmAllowSuspension' put:0.
-        standardGroup instVarNamed:'nthreads'    put:0.
-        standardGroup instVarNamed:'ngroups'     put:0.
-        standardGroup instVarNamed:'groups'      put:nil.
-        StandardThreadGroup := standardGroup.
+	threadClass := Java at:'java.lang.Thread'.
+
+	standardGroup := (Java at:'java.lang.ThreadGroup') new.
+	standardGroup instVarNamed:'parent'      put:nil.
+	standardGroup instVarNamed:'name'        put:(Java as_String:'main').
+	standardGroup instVarNamed:'maxPriority' put:(threadClass instVarNamed:'MAX_PRIORITY').
+	standardGroup instVarNamed:'destroyed'   put:0.
+	standardGroup instVarNamed:'daemon'      put:nil.
+	standardGroup instVarNamed:'vmAllowSuspension' put:0.
+	standardGroup instVarNamed:'nthreads'    put:0.
+	standardGroup instVarNamed:'ngroups'     put:0.
+	standardGroup instVarNamed:'groups'      put:nil.
+	StandardThreadGroup := standardGroup.
     ].
     ^ StandardThreadGroup
 
@@ -626,7 +1017,7 @@
 !JavaVM class methodsFor:'helpers - awt'!
 
 commonReshapeComponent:nativeContext
-    |jFramePeer view x y width height menu|
+    |jFramePeer view x y width height ext menu|
 
     jFramePeer := nativeContext receiver.
     view := jFramePeer instVarNamed:'pData'.
@@ -635,10 +1026,11 @@
     y := nativeContext argAt:2.
     width := nativeContext argAt:3.
     height := nativeContext argAt:4.
+    ext := width@height.
 
 "/    'pReshape ' print. view print. 
 "/    ' ' print. x print. '/' print. y print.
-"/    ' extent: ' print. width print. '/' print. height printNL.
+"/    ' extent: ' print. ext printNL.
 
     (view isTopView 
     or:[view isMemberOf:JavaEmbeddedFrameView]) ifTrue:[
@@ -648,9 +1040,31 @@
         menu := self topViewsMenu:view.
         menu notNil ifTrue:[
             "/ must add the menus height
-            height := height + menu height
+            height := height + menu height.
+            ext := width@height.
         ].
-        view extent:width@height.
+
+        "/ to prevent a view from not being visible/closable
+        "/ in case Java goes mad ..
+
+        (width < 30
+        or:[height < 10]) ifTrue:[
+            "/ self halt.
+            width := 30.
+            height := 20.
+            ext := width@height.
+        ].
+
+        view extent:ext.
+
+        "/ adjust non-resizable views min/max
+
+        view isTopView ifTrue:[
+            view minExtent notNil ifTrue:[
+                view minExtent:ext.
+                view maxExtent:ext
+            ].
+        ]
     ] ifFalse:[
         (view superView notNil
         and:[view superView isTopView]) ifTrue:[
@@ -659,14 +1073,17 @@
                 "/ must add menus height to yPos
                 y := y + menu height.
             ]
+        ] ifFalse:[
+            "/ post a configuration event
+            'need event' printCR.
         ].
-        view origin:x@y extent:width@height.
+        view origin:x@y extent:ext.
     ].
 
     ^ nil
 
-    "Modified: / 21.8.1997 / 19:34:16 / cg"
     "Created: / 4.1.1998 / 18:00:52 / cg"
+    "Modified: / 15.1.1998 / 17:25:48 / cg"
 !
 
 createdWindowsView:aView for:aJavaPeer
@@ -686,8 +1103,13 @@
     ].
     KnownWindows at:aJavaPeer put:aView.
 
-    "Modified: / 19.8.1997 / 01:45:25 / cg"
+"/'*** ' print. aJavaPeer print. ' -> ' print. aView printCR.
+"/(aView isKindOf:ModalBox) ifTrue:[
+"/    self halt.
+"/].
+
     "Created: / 4.1.1998 / 17:57:16 / cg"
+    "Modified: / 15.1.1998 / 15:32:49 / cg"
 !
 
 gcForWGraphics:nativeContext
@@ -701,6 +1123,13 @@
     "Modified: / 8.1.1998 / 00:17:44 / cg"
 !
 
+jPeerForView:aView
+    ^ KnownWindows keyAtValue:aView ifAbsent:nil
+
+    "Created: / 15.1.1998 / 13:48:01 / cg"
+    "Modified: / 15.1.1998 / 13:48:43 / cg"
+!
+
 pReshape:nativeContext
     |jFramePeer view x y width height menu|
 
@@ -718,25 +1147,25 @@
 
     (view isTopView 
     or:[view isMemberOf:JavaEmbeddedFrameView]) ifTrue:[
-        "/
-        "/ dont allow setting the origin
-        "/
-        menu := self topViewsMenu:view.
-        menu notNil ifTrue:[
-            "/ must add the menus height
-            height := height + menu height
-        ].
-        view extent:width@height.
+	"/
+	"/ dont allow setting the origin
+	"/
+	menu := self topViewsMenu:view.
+	menu notNil ifTrue:[
+	    "/ must add the menus height
+	    height := height + menu height
+	].
+	view extent:width@height.
     ] ifFalse:[
-        (view superView notNil
-        and:[view superView isTopView]) ifTrue:[
-            menu := self topViewsMenu:view superView.
-            menu notNil ifTrue:[
-                "/ must add menus height to yPos
-                y := y + menu height.
-            ]
-        ].
-        view origin:x@y extent:width@height.
+	(view superView notNil
+	and:[view superView isTopView]) ifTrue:[
+	    menu := self topViewsMenu:view superView.
+	    menu notNil ifTrue:[
+		"/ must add menus height to yPos
+		y := y + menu height.
+	    ]
+	].
+	view origin:x@y extent:width@height.
     ].
 
     ^ nil
@@ -749,12 +1178,12 @@
     |idx|
 
     view isTopView ifTrue:[
-        view subViews size > 0 ifTrue:[
-            (idx := view subViews findFirst:[:v | v isMemberOf:MenuPanel]) ~~ 0 ifTrue:[
-                "/ must add the menus height
-                ^ view subViews at:idx
-            ]
-        ].
+	view subViews size > 0 ifTrue:[
+	    (idx := view subViews findFirst:[:v | v isMemberOf:MenuPanel]) ~~ 0 ifTrue:[
+		"/ must add the menus height
+		^ view subViews at:idx
+	    ]
+	].
     ].
     ^ nil
 
@@ -780,25 +1209,42 @@
 
     con := thisContext sender.
     [con notNil] whileTrue:[
-        (con isMemberOf:JavaContext) ifTrue:[
-            method := con method.
-            pc := con pc.
-            (hPC := method handlerFor:aJavaException at:pc) notNil ifTrue:[
-                con setPC:hPC.
-                ^ con
-            ].
-        ].
-        con := con sender.
+	(con isMemberOf:JavaContext) ifTrue:[
+	    method := con method.
+	    pc := con pc.
+	    (hPC := method handlerFor:aJavaException at:pc) notNil ifTrue:[
+		con setPC:hPC.
+		^ con
+	    ].
+	].
+	con := con sender.
     ].
     ^ nil
 
     "Modified: / 5.1.1998 / 00:16:52 / cg"
 !
 
+throwArrayIndexOutOfBoundsException:badIndex
+    |exClass ex|
+
+"/    self 
+"/        throwExceptionClassName:'java.lang.ArrayIndexOutOfBoundsException' 
+"/        withMessage:'bad array index: ' , badIndex printString
+
+    exClass := Java classForName:'java.lang.ArrayIndexOutOfBoundsException'.
+    ex := exClass newCleared.
+    ex perform:#'<init>(I)V' with:badIndex.
+
+    self throwException:ex
+
+    "Created: / 14.1.1998 / 21:36:05 / cg"
+    "Modified: / 14.1.1998 / 23:32:52 / cg"
+!
+
 throwClassNotFoundException
     self 
-        throwExceptionClassName:'java.lang.ClassNotFoundException' 
-        withMessage:'no such class'
+	throwExceptionClassName:'java.lang.ClassNotFoundException' 
+	withMessage:'no such class'
 
     "Created: / 4.1.1998 / 22:25:26 / cg"
     "Modified: / 7.1.1998 / 15:25:35 / cg"
@@ -806,15 +1252,15 @@
 
 throwClassNotFoundException:className
     self 
-        throwExceptionClassName:'java.lang.ClassNotFoundException' 
-        withMessage:'no such class: ' , className
+	throwExceptionClassName:'java.lang.ClassNotFoundException' 
+	withMessage:'no such class: ' , className
 
     "Created: / 4.1.1998 / 22:26:09 / cg"
     "Modified: / 7.1.1998 / 15:25:58 / cg"
 !
 
 throwException:aJavaException
-    |con|
+    |con jMsg msg|
 
     ExceptionTrace ifTrue:[
         'JAVA: exception: ' print. aJavaException class fullName printCR.
@@ -826,11 +1272,34 @@
 
     con := self findJavaHandlerFor:aJavaException.
     con isNil ifTrue:[
+        jMsg := aJavaException instVarNamed:'detailMessage'.
+        jMsg notNil ifTrue:[
+            msg := Java as_ST_String:jMsg.
+            msg := 'Java exception: ' , msg.
+        ] ifFalse:[
+            msg := 'Java exception'.
+        ].
+
+        "/ for our convenience: skip ST contexts
+        con := thisContext sender.
+        [con isNil or:[con isMemberOf:JavaContext]] whileFalse:[
+            con := con sender
+        ].
+        con isNil ifTrue:[con := thisContext sender].
+
+        "/
         "/ no JavaHandler ... let smalltalk handle it
-        JavaVM javaExceptionSignal raiseWith:aJavaException.
-        self halt:'here after exception'.
+        "/
+        JavaVM javaExceptionSignal 
+                raiseWith:aJavaException
+                errorString:msg
+                in:con.
         Processor activeProcess terminate.
     ].
+
+    "/
+    "/ found a java exceptionHandler
+    "/
     con exceptionArg:aJavaException.
     con markForException.
     con unwindAndRestart.
@@ -839,64 +1308,65 @@
     Processor activeProcess terminate.
 
     "Created: / 7.1.1998 / 15:28:22 / cg"
-    "Modified: / 9.1.1998 / 02:27:49 / cg"
-!
-
-throwException:aJavaExceptionClass withMessage:someMessage
-    |ex con|
-
-self halt.
-
-    ExceptionTrace ifTrue:[
-        'JAVA: exception: ' print. aJavaExceptionClass name printCR.
-    ].
-    ExceptionDebug ifTrue:[
-        self halt:('JAVA: exception: ' , aJavaExceptionClass name).
-        self internalError:('JAVA: exception: ' , aJavaExceptionClass name).
-    ].
-
-    ex := aJavaExceptionClass new.
-    ex instVarNamed:'detailMessage' put:(Java as_String:someMessage).
-
-    con := self findJavaHandlerFor:ex.
-    con isNil ifTrue:[
-        "/ no JavaHandler ... let smalltalk handle it
-        ^ JavaVM javaExceptionSignal raiseWith:ex.
-    ].
-    con markForException.
-    con unwindAndRestart.
-
-    self halt:'should not be reached'.
-
-    "Created: / 4.1.1998 / 22:29:26 / cg"
-    "Modified: / 7.1.1998 / 21:35:51 / cg"
+    "Modified: / 15.1.1998 / 00:19:06 / cg"
 !
 
 throwExceptionClassName:aJavaExceptionClassName withMessage:someMessage
-    |aJavaExceptionClass ex|
-
-    aJavaExceptionClass := Java classForName:aJavaExceptionClassName.
-    ex := aJavaExceptionClass new.
-    ex instVarNamed:'detailMessage' put:(Java as_String:someMessage).
+    |exClass ex|
+
+    exClass := Java classForName:aJavaExceptionClassName.
+    ex := exClass newCleared.
+    ex perform:#'<init>(Ljava/lang/String;)V' with:(Java as_String:someMessage).
+
+    "/ ex := exClass new.
+    "/ ex instVarNamed:'detailMessage' put:(Java as_String:someMessage).
 
     self throwException:ex
 
     "Created: / 7.1.1998 / 15:25:09 / cg"
+    "Modified: / 14.1.1998 / 23:38:30 / cg"
 !
 
 throwIOExceptionWithMessage:message
     self 
-        throwExceptionClassName:'java.io.IOException' 
-        withMessage:message
+	throwExceptionClassName:'java.io.IOException' 
+	withMessage:message
 
     "Created: / 7.1.1998 / 10:34:24 / cg"
     "Modified: / 7.1.1998 / 15:26:25 / cg"
 !
 
+throwIllegalAccessException
+    self 
+        throwExceptionClassName:'java.lang.IllegalAccessException' 
+        withMessage:'illegal access'
+
+    "Modified: / 7.1.1998 / 15:25:35 / cg"
+    "Created: / 14.1.1998 / 23:13:44 / cg"
+!
+
+throwInstantiationException
+    self 
+        throwExceptionClassName:'java.lang.InstantiationException' 
+        withMessage:'cannot instantiate'
+
+    "Modified: / 7.1.1998 / 15:25:35 / cg"
+    "Created: / 14.1.1998 / 23:15:01 / cg"
+!
+
+throwInstantiationExceptionFor:aJavaClass
+    self 
+        throwExceptionClassName:'java.lang.InstantiationException' 
+        withMessage:('cannot instantiate ' , aJavaClass fullName)
+
+    "Modified: / 7.1.1998 / 15:25:35 / cg"
+    "Created: / 14.1.1998 / 23:17:02 / cg"
+!
+
 throwNullPointerException
     self 
-        throwExceptionClassName:'java.lang.NullPointerException' 
-        withMessage:'null pointer'
+	throwExceptionClassName:'java.lang.NullPointerException' 
+	withMessage:'null pointer'
 
     "Modified: / 7.1.1998 / 15:25:35 / cg"
     "Created: / 9.1.1998 / 02:26:08 / cg"
@@ -904,8 +1374,8 @@
 
 throwNumberFormatException 
     self 
-        throwExceptionClassName:'java.lang.NumberFormatException' 
-        withMessage:'bad number format'
+	throwExceptionClassName:'java.lang.NumberFormatException' 
+	withMessage:'bad number format'
 
     "Modified: / 7.1.1998 / 15:25:35 / cg"
     "Created: / 11.1.1998 / 16:08:22 / cg"
@@ -917,12 +1387,15 @@
     |fileNo file|
 
     fileNo := self validateFileNo:javaStream.
-
+    fileNo == 0 ifTrue:[
+	'JAVA: file is already closed' errorPrintCR.
+	^ self    "/ already closed
+    ].
     file := self getOpenFileAt:fileNo.
     file isNil ifTrue:[
-        self halt:'invalid fileNo in close'.
-        self internalError:'invalid fileNo in close'.
-        ^ self
+	self halt:'invalid fileNo in close'.
+	self internalError:'invalid fileNo in close'.
+	^ self
     ].
 
     "/ should always be bytes
@@ -930,12 +1403,60 @@
     (file ~~ Stdin
     and:[file ~~ Stdout
     and:[file ~~ Stderr]]) ifTrue:[
-        file close.
+	file close.
     ].
     self setOpenFile:nil at:fileNo.
 
-    "Modified: / 2.1.1998 / 18:30:49 / cg"
+    fileNo := javaStream instVarNamed:'fd'.
+    fileNo isInteger ifFalse:[
+	"/ JDK 1.1.3
+	fileNo instVarNamed:'fd' put:0.
+    ] ifTrue:[
+	"/ JDK 1.0
+	javaStream instVarNamed:'fd' put:0
+    ].
+
     "Created: / 4.1.1998 / 17:47:03 / cg"
+    "Modified: / 13.1.1998 / 14:09:12 / cg"
+!
+
+fileStreamForReading:name
+    |fn stream tryAlongClassPath|
+
+    fn := name asFilename.
+    stream := fn readStream.
+    stream notNil ifTrue:[^ stream].
+
+    fn isAbsolute ifFalse:[
+        "/ if not absolute, try along classPath
+        "/ This allows classes to open local files (JEdit)
+        "/ even if they have NOT been loaded by a Java classLoader.
+        "/ Only do this for image files 
+        "/ (and maybe some other config files in the future),
+        "/ to avoid security holes.
+
+        tryAlongClassPath := false.
+        (fn hasSuffix:'gif') ifTrue:[
+            tryAlongClassPath := true.
+        ].
+        (fn hasSuffix:'jpg') ifTrue:[
+            tryAlongClassPath := true.
+        ].
+
+        tryAlongClassPath ifTrue:[
+            Java classPath do:[:dirName |
+                |fn|
+
+                (fn := dirName asFilename construct:name) exists ifTrue:[
+                    stream := fn readStream.
+                    stream notNil ifTrue:[^ stream].
+                ]
+            ]
+        ]
+    ].
+    ^ nil.
+
+    "Modified: / 15.1.1998 / 13:01:34 / cg"
 !
 
 validateFile:javaStream
@@ -945,8 +1466,8 @@
     fileNo isNil ifTrue:[
 "/        self halt:'invalid fileNo in read'.
 "/        self internalError:'invalid fileNo in read'.
-        self throwIOExceptionWithMessage:'invalid fileNo in read'.
-        ^ nil
+	self throwIOExceptionWithMessage:'invalid fileNo in read'.
+	^ nil
     ].
 
     file := self getOpenFileAt:fileNo.
@@ -954,8 +1475,8 @@
     file isNil ifTrue:[
 "/        self halt:'invalid fileNo in read'.
 "/        self internalError:'invalid fileNo in read'.
-        self throwIOExceptionWithMessage:'invalid fileNo in read'.
-        ^ nil
+	self throwIOExceptionWithMessage:'invalid fileNo in read'.
+	^ nil
     ].
 
     ^ file
@@ -967,27 +1488,26 @@
 validateFileNo:javaStream
     |fileNo file descriptor|
 
-    "/ thats what I'd expect from reading the code ...
-"/    descriptor := stream instVarNamed:'fd'.
-"/    fileNo := descriptor instVarNamed:'fd'.
-
-    "/ thats what actually arrives ...
+    "/ JDK 1.1.3 has fileDescriptor wrapped
+    "/ JDK 1.0 has it directly as integer
+
     fileNo := javaStream instVarNamed:'fd'.
     fileNo isInteger ifFalse:[
-        descriptor := fileNo.
-        fileNo := descriptor instVarNamed:'fd'.
+	descriptor := fileNo.
+	fileNo := descriptor instVarNamed:'fd'.
     ].
 
     fileNo isInteger ifFalse:[
 "/        self halt:'invalid fileNo in read'.
 "/        self internalError:'invalid fileNo in read'.
-        self throwIOExceptionWithMessage:'invalid fileNo in read'.
-        ^ nil
+	self throwIOExceptionWithMessage:'invalid fileNo in read'.
+	^ nil
     ].
 
     ^ fileNo.
 
     "Created: / 4.1.1998 / 17:49:08 / cg"
+    "Modified: / 13.1.1998 / 14:07:47 / cg"
 ! !
 
 !JavaVM class methodsFor:'native - awt.windows'!
@@ -1004,24 +1524,22 @@
 
     button := Button in:frame.
     button action:[
-                        jButtonPeer invoke:#handleAction.
-                  ].
+			jButtonPeer invoke:#handleAction.
+		  ].
 
     lbl := jButton instVarNamed:'label'.
     lbl notNil ifTrue:[
-        lbl := Java as_ST_String:lbl.
-        button label:lbl
+	lbl := Java as_ST_String:lbl.
+	button label:lbl
     ].
     self createdWindowsView:button for:jButtonPeer.
 
     WindowCreationTrace == true ifTrue:[
-        'WButtonPeer_create: ' print. frame print. ' -> ' print. button printNL.
-    ].
-
-    ^ nil
+	'WButtonPeer_create: ' print. frame print. ' -> ' print. button printNL.
+    ].
 
     "Created: / 5.1.1998 / 01:53:30 / cg"
-    "Modified: / 8.1.1998 / 22:02:43 / cg"
+    "Modified: / 13.1.1998 / 22:09:15 / cg"
 !
 
 _WCanvasPeer_create:nativeContext
@@ -1039,6 +1557,7 @@
 
     subView := JavaView in:frame.
     subView delegate:self.
+    subView javaPeer:jCanvasPeer.
 
     self createdWindowsView:subView for:jCanvasPeer.
 
@@ -1046,10 +1565,8 @@
         'WCanvasPeer_create: ' print. frame print. ' -> ' print. subView printNL.
     ].
 
-    ^ nil
-
     "Created: / 5.1.1998 / 00:59:19 / cg"
-    "Modified: / 5.1.1998 / 01:24:13 / cg"
+    "Modified: / 16.1.1998 / 13:40:00 / cg"
 !
 
 _WCheckboxPeer_create:nativeContext
@@ -1062,10 +1579,11 @@
     frame := jFrame instVarNamed:'pData'.
 
     checkBox := CheckBox in:frame.
-    checkBox action:[jCheckboxPeer 
-                        invoke:#'handleAction(Z)V' 
-                        with:(checkBox isOn ifTrue:[1] ifFalse:[0])
-                  ].
+    checkBox action:[
+                        jCheckboxPeer 
+                            perform:#'handleAction(Z)V' 
+                            with:(checkBox isOn ifTrue:[1] ifFalse:[0])
+                    ].
 
     lbl := jCheckbox instVarNamed:'label'.
     lbl notNil ifTrue:[
@@ -1079,10 +1597,8 @@
         'WCheckboxPeer_create: ' print. frame print. ' -> ' print. checkBox printNL.
     ].
 
-    ^ nil
-
-    "Modified: / 19.8.1997 / 01:46:58 / cg"
     "Created: / 7.1.1998 / 21:48:03 / cg"
+    "Modified: / 15.1.1998 / 12:27:04 / cg"
 !
 
 _WCheckboxPeer_setCheckboxGroup:nativeContext
@@ -1137,13 +1653,11 @@
     self createdWindowsView:comboBox for:jChoicePeer.
 
     WindowCreationTrace == true ifTrue:[
-        'WChoicePeer_create: ' print. frame print. ' -> ' print. comboBox printNL.
-    ].
-
-    ^ nil
-
-    "Modified: / 19.8.1997 / 01:47:05 / cg"
+	'WChoicePeer_create: ' print. frame print. ' -> ' print. comboBox printNL.
+    ].
+
     "Created: / 7.1.1998 / 21:44:31 / cg"
+    "Modified: / 13.1.1998 / 22:09:39 / cg"
 !
 
 _WChoicePeer_reshape:nativeContext
@@ -1181,18 +1695,18 @@
     "/  1: view background
 
     clrIndex == 1 ifTrue:[
-        clr := View defaultViewBackgroundColor.
-        clr isColor ifFalse:[
-            clr := Color gray:50.
-        ].
+	clr := View defaultViewBackgroundColor.
+	clr isColor ifFalse:[
+	    clr := Color gray:50.
+	].
     ].
     clrIndex == 2 ifTrue:[
-        clr := Color black.
+	clr := Color black.
     ].
     clr isNil ifTrue:[
-        self halt.
-        self internalError:'breakpoint'.
-        ^ nil.
+	self halt.
+	self internalError:'breakpoint'.
+	^ nil.
     ].
 
     clr := clr on:(Screen current).
@@ -1213,13 +1727,13 @@
 
     view := self viewForWPeer:nativeContext.
 
-    Object errorSignal handle:[:ex |
-    ] do:[
-        view destroy
-    ]
+    Object errorSignal catch:[
+        view destroy.
+    ].
+    JavaWindowGroup removeView:view.
 
     "Created: / 7.1.1998 / 22:36:25 / cg"
-    "Modified: / 8.1.1998 / 17:32:08 / cg"
+    "Modified: / 15.1.1998 / 16:08:28 / cg"
 !
 
 _WComponentPeer__setBackground:nativeContext
@@ -1245,11 +1759,14 @@
 "/        ]
 "/    ].
 
+    (view isKindOf:ScrollableView) ifTrue:[
+        view := view scrolledView
+    ].
     view viewBackground:clr.
     view backgroundPaint:clr.
 
     "Created: / 4.1.1998 / 18:07:39 / cg"
-    "Modified: / 8.1.1998 / 17:32:34 / cg"
+    "Modified: / 15.1.1998 / 13:06:44 / cg"
 !
 
 _WComponentPeer__setForeground:nativeContext
@@ -1278,18 +1795,51 @@
 
     Object errorSignal handle:[:ex |
     ] do:[
-        view disable
+	view disable
     ]
 
     "Created: / 6.1.1998 / 18:26:36 / cg"
     "Modified: / 8.1.1998 / 17:32:53 / cg"
 !
 
+_WComponentPeer_enable:nativeContext
+    |view|
+
+    view := self viewForWPeer:nativeContext.
+
+    Object errorSignal handle:[:ex |
+    ] do:[
+	view enable
+    ]
+
+    "Modified: / 8.1.1998 / 17:32:53 / cg"
+    "Created: / 13.1.1998 / 23:08:05 / cg"
+!
+
 _WComponentPeer_handleEvent:nativeContext
-"/ 'JAVA: WComponent - handleEvent ignored' infoPrintCR.
-
-    "Modified: / 21.8.1997 / 17:13:27 / cg"
+    "this is invoked by java, to let a widget handle any event which
+     was not consumed (eaten) by java.
+     If the view in question is some ST-widget, forward it.
+     Ignore for JavaViews."
+
+    |view jEv stEv|
+
+    view := self viewForWPeer:nativeContext.
+    view notNil ifTrue:[
+        (view isKindOf:JavaView) ifFalse:[
+            jEv := nativeContext argAt:1.
+            stEv := jEv instVarNamed:'data'.
+            (stEv notNil and:[stEv ~~ 0]) ifTrue:[
+('JAVA: WComponent - handleEvent: ' , stEv type , ' for ' , view printString) infoPrintCR.
+                stEv sendEventWithFocusOn:nil.
+                ^ self.
+            ]
+        ]
+    ].
+('JAVA: WComponent - handleEvent ignored') infoPrintCR.
+
     "Created: / 6.1.1998 / 21:10:17 / cg"
+    "Modified: / 16.1.1998 / 14:35:33 / cg"
 !
 
 _WComponentPeer_hide:nativeContext
@@ -1299,7 +1849,7 @@
 
     Object errorSignal handle:[:ex |
     ] do:[
-        view beInvisible
+	view beInvisible
     ]
 
     "Created: / 7.1.1998 / 22:35:32 / cg"
@@ -1310,11 +1860,12 @@
     |view|
 
     view := self viewForWPeer:nativeContext.
+'getFocus - ' print. view displayString printCR.
 
     view getKeyboardFocus
 
     "Created: / 7.1.1998 / 22:30:03 / cg"
-    "Modified: / 8.1.1998 / 17:33:18 / cg"
+    "Modified: / 16.1.1998 / 14:42:32 / cg"
 !
 
 _WComponentPeer_reshape:nativeContext
@@ -1368,7 +1919,7 @@
 "/ self halt.
 
     "Created: / 5.1.1998 / 01:26:22 / cg"
-    "Modified: / 8.1.1998 / 17:33:48 / cg"
+    "Modified: / 15.1.1998 / 15:37:17 / cg"
 !
 
 _WComponentPeer_start:nativeContext
@@ -1400,11 +1951,14 @@
     |dialog|
 
     dialog := self viewForWPeer:nativeContext.
-
+"/
+"/ show does not work (yet); must setup windowgroup
+"/ for it to get events ...
+"/    dialog show.
     dialog realize.
 
     "Created: / 7.1.1998 / 21:52:15 / cg"
-    "Modified: / 8.1.1998 / 17:34:22 / cg"
+    "Modified: / 15.1.1998 / 15:57:03 / cg"
 !
 
 _WDialogPeer_create:nativeContext
@@ -1415,35 +1969,67 @@
     dialog := ModalBox new.
     jDialogPeer instVarNamed:'pData' put:dialog.
 
+    self createdWindowsView:dialog for:jDialogPeer.
+    dialog windowGroup:JavaWindowGroup.
+    JavaWindowGroup addTopView:dialog.
+
     WindowCreationTrace == true ifTrue:[
         'WDialogPeer_create: ' print. dialog printNL.
     ].
 
     "Created: / 7.1.1998 / 21:51:00 / cg"
-    "Modified: / 7.1.1998 / 22:34:32 / cg"
+    "Modified: / 15.1.1998 / 16:12:44 / cg"
 !
 
 _WFileDialogPeer_show:nativeContext
-    |jDialogPeer dialog dialogView stDialog f|
+    |jDialogPeer jDialog dialogView stDialog 
+     title dir pattern f|
 
     jDialogPeer := nativeContext receiver.
-    dialog := jDialogPeer instVarNamed:'target'.
+    jDialog := jDialogPeer instVarNamed:'target'.
     dialogView := jDialogPeer instVarNamed:'pData'.
 
     stDialog := FileSelectionBox new.
-    stDialog label:(Java as_ST_String:(dialog instVarNamed:'title')).
+
+    dir := jDialog instVarNamed:'dir'.
+    dir notNil ifTrue:[
+        stDialog directory:(Java as_ST_String:dir).
+    ].
+    pattern := jDialog instVarNamed:'file'.
+    pattern notNil ifTrue:[
+        stDialog pattern:(Java as_ST_String:pattern).
+    ].
+    title := jDialog instVarNamed:'title'.
+    title notNil ifTrue:[
+        stDialog title:(Java as_ST_String:title).
+        stDialog label:(Java as_ST_String:title).
+    ].
+
     stDialog show.
 
     stDialog accepted ifTrue:[
         f := stDialog pathName.
-        jDialogPeer perform:#'handleSelected(Ljava/lang/String;)V' with:(Java as_String:f).
+
+        "/ cannot use the one below - it has a builtIn fileSeparator if '\' (sigh)
+        "/ jDialogPeer perform:#'handleSelected(Ljava/lang/String;)V' with:(Java as_String:f).
+
+        jDialog 
+            perform:#'setFile(Ljava/lang/String;)V' 
+            with:(Java as_String:(f asFilename baseName)).
+        jDialog 
+            perform:#'setDirectory(Ljava/lang/String;)V'
+            with:(Java as_String:(f asFilename directoryName , Filename separator asString)).
+        jDialog 
+            perform:#'setVisible(Z)V'
+            with:0.
     ] ifFalse:[
-        jDialogPeer perform:#'handleCancel()V'
+        jDialogPeer 
+            perform:#'handleCancel()V'
     ].
 "/ self halt.
 
     "Created: / 7.1.1998 / 22:38:45 / cg"
-    "Modified: / 12.1.1998 / 12:32:03 / cg"
+    "Modified: / 15.1.1998 / 13:04:05 / cg"
 !
 
 _WFontMetrics_getMFCharSegmentWidth:nativeContext
@@ -1451,32 +2037,32 @@
      Not yet supported - use standard strings width"
 
     |jMetrics jFont jFontDescr stFont w
-     bool1 cp start stop bp int1|
+     bool1 cp offs lenght bp int1|
 
     jMetrics := nativeContext receiver.
     jFont := nativeContext argAt:1.
     jFontDescr := nativeContext argAt:2.
     bool1 := nativeContext argAt:3.
     cp := nativeContext argAt:4.
-    start := nativeContext argAt:5.
-    stop := nativeContext argAt:6.
+    offs := nativeContext argAt:5.
+    lenght := nativeContext argAt:6.
     bp := nativeContext argAt:7.
     int1 := nativeContext argAt:8.
 
     stFont := jFont instVarNamed:'pData'.
-    stFont isNil ifTrue:[
-        self halt
-    ].
+    (stFont isNil or:[stFont == 0]) ifTrue:[
+	self halt
+    ].
+
     stFont device isNil ifTrue:[
-        stFont := stFont on:Display.
-        jFont instVarNamed:'pData' put:stFont.
-    ].
-
-    w := stFont widthOf:cp from:start to:stop-1.
+	stFont := stFont on:Display.
+	jFont instVarNamed:'pData' put:stFont.
+    ].
+    w := stFont widthOf:cp from:offs+1 to:offs+lenght.
     ^ w.
 
-    "Modified: / 17.8.1997 / 17:34:27 / cg"
     "Created: / 5.1.1998 / 01:57:45 / cg"
+    "Modified: / 13.1.1998 / 23:44:03 / cg"
 !
 
 _WFontMetrics_init:nativeContext
@@ -1496,7 +2082,7 @@
 
     stFont := Font family:family size:size.
     stFont isNil ifTrue:[
-        stFont := Font family:'helvetica' size:size.
+	stFont := Font family:'helvetica' size:size.
     ].
     stFont := stFont on:Display.
 
@@ -1519,7 +2105,7 @@
 
     widths := Array new:256.
     0 to:255 do:[:i |
-        widths at:(i+1) put:(stFont widthOf:(Character value:i))
+	widths at:(i+1) put:(stFont widthOf:(Character value:i))
     ].
     jMetrics instVarNamed:'widths' put:widths.
 "/ self halt.
@@ -1577,6 +2163,7 @@
     ] ifFalse:[
         frame := StandardSystemView new.
         self createdWindowsView:frame for:jFramePeer.
+        JavaWindowGroup addTopView:frame.
     ].
 
     WindowCreationTrace == true ifTrue:[
@@ -1584,10 +2171,8 @@
         ' frame: ' print. frame printNL.
     ].
 
-    ^ nil
-
-    "Modified: / 21.8.1997 / 17:01:58 / cg"
     "Created: / 4.1.1998 / 17:56:39 / cg"
+    "Modified: / 15.1.1998 / 16:02:46 / cg"
 !
 
 _WFramePeer_setMenuBar0:nativeContext
@@ -1597,19 +2182,19 @@
 
     jMenuBarPeer := nativeContext argAt:1.
     jMenuBarPeer isNil ifTrue:[
-        "/ mhmh - JAVA wants to remove the frames menuPanel.
-        "/ but I have no handle on it (for destroy).
-        "/ search it in subViews of the frame.
-        frame subViews copy do:[:v |
-            (v isKindOf:MenuPanel) ifTrue:[
-                v destroy
-            ]
-        ]
+	"/ mhmh - JAVA wants to remove the frames menuPanel.
+	"/ but I have no handle on it (for destroy).
+	"/ search it in subViews of the frame.
+	frame subViews copy do:[:v |
+	    (v isKindOf:MenuPanel) ifTrue:[
+		v destroy
+	    ]
+	]
     ] ifFalse:[
-        menuPanel := jMenuBarPeer instVarNamed:'pData'.
-
-        menuPanel origin:0.0@0.0 corner:1.0@(menuPanel preferredExtent y).
-        frame addSubView:menuPanel.
+	menuPanel := jMenuBarPeer instVarNamed:'pData'.
+
+	menuPanel origin:0.0@0.0 corner:1.0@(menuPanel preferredExtent y).
+	frame addSubView:menuPanel.
     ].
     ^ nil
 
@@ -1635,8 +2220,8 @@
 "/    gc isNil ifTrue:[^ self].
 
     gc realized ifFalse:[
-        'JAVA: drawing on unrealized gc - ignored' infoPrintCR.
-        ^ self
+	'JAVA: drawing on unrealized gc - ignored' infoPrintCR.
+	^ self
     ].
 
     x := nativeContext argAt:1.
@@ -1654,26 +2239,26 @@
 !
 
 _WGraphics_createFromComponent:nativeContext
-    |jGraphics win view|
+    |jGraphics jWin view|
 
     jGraphics := nativeContext receiver.
-    win := nativeContext argAt:1.
-
-    view := KnownWindows at:win ifAbsent:nil.
+    jWin := nativeContext argAt:1.
+
+    view := KnownWindows at:jWin ifAbsent:nil.
     view isNil ifTrue:[
         self halt.
         ^ self
     ].
 
 "/    "/ just a consistency check ...
-"/    (win instVarNamed:'xid') ~~ view ifTrue:[
+"/    (jWin instVarNamed:'xid') ~~ view ifTrue:[
 "/        self halt:'consistency check'
 "/    ].
 
     jGraphics instVarNamed:'pData' put:view.
 
-    "Modified: / 13.8.1997 / 20:37:47 / cg"
     "Created: / 6.1.1998 / 20:55:18 / cg"
+    "Modified: / 15.1.1998 / 13:49:56 / cg"
 !
 
 _WGraphics_createFromGraphics:nativeContext
@@ -1714,9 +2299,9 @@
     endAngle := nativeContext argAt:6.
 
     DrawOPTrace ifTrue:[
-        'drawArc x/y= ' print. x print. '@' print. y print. 
-               ' w/h= ' print. w print. '@' print. h print.
-               ' startAngle= ' print. startAngle print. ' endAngle= ' print. endAngle printCR.
+	'drawArc x/y= ' print. x print. '@' print. y print. 
+	       ' w/h= ' print. w print. '@' print. h print.
+	       ' startAngle= ' print. startAngle print. ' endAngle= ' print. endAngle printCR.
     ].
     gc displayArcX:x y:y width:w height:h from:startAngle angle:(endAngle - startAngle)
 
@@ -1737,7 +2322,7 @@
     y2 := nativeContext argAt:4.
 
     DrawOPTrace ifTrue:[
-        'drawLine x/y= ' print. x print. '@' print. y print. ' x2/y2= ' print. x2 print. '@' print. y2 printCR.
+	'drawLine x/y= ' print. x print. '@' print. y print. ' x2/y2= ' print. x2 print. '@' print. y2 printCR.
     ].
     gc displayLineFromX:x y:y toX:x2 y:y2
 
@@ -1749,26 +2334,24 @@
     |jFont jFontDescr s gc x y offs len|
 
     gc := self gcForWGraphics:nativeContext.
-"/    gc isNil ifTrue:[^ self].
     gc realized ifFalse:[^ self].
 
     jFont := nativeContext argAt:1.
     jFontDescr := nativeContext argAt:2.
     s := nativeContext argAt:3.
-    "/ s := Java as_ST_String:s.
     offs := nativeContext argAt:4.
     len := nativeContext argAt:5.
     x := nativeContext argAt:6.
     y := nativeContext argAt:7.
 
     DrawOPTrace ifTrue:[
-        'drawMFCharsSegment x/y= ' print. x print. '@' print. y print. ' s= ' print. s printCR.
+	'drawMFCharsSegment x/y= ' print. x print. '@' print. y print. ' s= ' print. s printCR.
     ].
     gc displayString:s from:offs+1 to:offs+len x:x y:y.
     ^ (gc font widthOf:s).
 
     "Created: / 6.1.1998 / 21:01:07 / cg"
-    "Modified: / 8.1.1998 / 00:34:06 / cg"
+    "Modified: / 13.1.1998 / 23:43:43 / cg"
 !
 
 _WGraphics_drawOval:nativeContext
@@ -1784,8 +2367,8 @@
     h := nativeContext argAt:4.
 
     DrawOPTrace ifTrue:[
-        'drawOval x/y= ' print. x print. '@' print. y print. 
-                ' w/h= ' print. w print. '@' print. h printCR.
+	'drawOval x/y= ' print. x print. '@' print. y print. 
+		' w/h= ' print. w print. '@' print. h printCR.
     ].
     gc displayArcX:x y:y width:w height:h from:0 angle:360
 
@@ -1805,7 +2388,7 @@
     count := nativeContext argAt:3.
 
     DrawOPTrace ifTrue:[
-        'drawPolgon' printCR.
+	'drawPolgon' printCR.
     ].
 
     points := (1 to:count) collect:[:i | (xVector at:i) @ (yVector at:i)].
@@ -1872,9 +2455,9 @@
     endAngle := nativeContext argAt:6.
 
     DrawOPTrace ifTrue:[
-        'fillArc x/y= ' print. x print. '@' print. y print. 
-               ' w/h= ' print. w print. '@' print. h print.
-               ' startAngle= ' print. startAngle print. ' endAngle= ' print. endAngle printCR.
+	'fillArc x/y= ' print. x print. '@' print. y print. 
+	       ' w/h= ' print. w print. '@' print. h print.
+	       ' startAngle= ' print. startAngle print. ' endAngle= ' print. endAngle printCR.
     ].
     gc fillArcX:x y:y width:w height:h from:startAngle angle:(endAngle - startAngle)
 
@@ -1895,8 +2478,8 @@
     h := nativeContext argAt:4.
 
     DrawOPTrace ifTrue:[
-        'drawOval x/y= ' print. x print. '@' print. y print. 
-                ' w/h= ' print. w print. '@' print. h printCR.
+	'drawOval x/y= ' print. x print. '@' print. y print. 
+		' w/h= ' print. w print. '@' print. h printCR.
     ].
     gc fillArcX:x y:y width:w height:h from:0 angle:360
 
@@ -1916,7 +2499,7 @@
     count := nativeContext argAt:3.
 
     DrawOPTrace ifTrue:[
-        'fillPolgon' printCR.
+	'fillPolgon' printCR.
     ].
 
     points := (1 to:count) collect:[:i | (xVector at:i) @ (yVector at:i)].
@@ -1977,23 +2560,23 @@
     rect := (Java classForName:'java.awt.Rectangle') basicNew.
 
     (gc isMemberOf:JavaView) ifTrue:[
-        r := gc getNextUpdateRectangle.
-        r isNil ifTrue:[
-            rect instVarNamed:'x' put:0.
-            rect instVarNamed:'y' put:0.
-            rect instVarNamed:'width' put:(gc width).
-            rect instVarNamed:'height' put:(gc height).
-        ] ifFalse:[
-            rect instVarNamed:'x' put:(r left).
-            rect instVarNamed:'y' put:(r top).
-            rect instVarNamed:'width' put:(r width).
-            rect instVarNamed:'height' put:(r height).
-        ]
+	r := gc getNextUpdateRectangle.
+	r isNil ifTrue:[
+	    rect instVarNamed:'x' put:0.
+	    rect instVarNamed:'y' put:0.
+	    rect instVarNamed:'width' put:(gc width).
+	    rect instVarNamed:'height' put:(gc height).
+	] ifFalse:[
+	    rect instVarNamed:'x' put:(r left).
+	    rect instVarNamed:'y' put:(r top).
+	    rect instVarNamed:'width' put:(r width).
+	    rect instVarNamed:'height' put:(r height).
+	]
     ] ifFalse:[
-        rect instVarNamed:'x' put:0.
-        rect instVarNamed:'y' put:0.
-        rect instVarNamed:'width' put:9999.
-        rect instVarNamed:'height' put:9999.
+	rect instVarNamed:'x' put:0.
+	rect instVarNamed:'y' put:0.
+	rect instVarNamed:'width' put:9999.
+	rect instVarNamed:'height' put:9999.
     ].
 
 "/ 'JAVA: getClipBounds' infoPrintCR.
@@ -2015,13 +2598,20 @@
 !
 
 _WGraphics_pSetFont:nativeContext
-    |gc|
+    |gc jFont stFont|
 
     gc := self gcForWGraphics:nativeContext.
+    jFont := nativeContext argAt:1.
+
+    stFont := jFont instVarNamed:'pData'.
+    (stFont isNil or:[stFont == 0]) ifTrue:[
 "/ self halt.
+    ] ifFalse:[
+        gc font:stFont
+    ].
 
     "Created: / 6.1.1998 / 20:56:47 / cg"
-    "Modified: / 8.1.1998 / 00:34:44 / cg"
+    "Modified: / 15.1.1998 / 12:31:20 / cg"
 !
 
 _WGraphics_pSetForeground:nativeContext
@@ -2072,7 +2662,7 @@
 
     lbl := jLabel instVarNamed:'text'.
     lbl notNil ifTrue:[
-        lbl := Java as_ST_String:lbl
+	lbl := Java as_ST_String:lbl
     ].
 
     jFrame := nativeContext argAt:1.
@@ -2080,18 +2670,16 @@
 
     label := Label in:frame.
     lbl notNil ifTrue:[
-        label label:lbl
+	label label:lbl
     ].
     self createdWindowsView:label for:jLabelPeer.
 
     WindowCreationTrace == true ifTrue:[
-        'WLabelPeer_create: ' print. frame print. ' -> ' print. label printNL.
-    ].
-
-    ^ nil
-
-    "Modified: / 19.8.1997 / 01:47:29 / cg"
+	'WLabelPeer_create: ' print. frame print. ' -> ' print. label printNL.
+    ].
+
     "Created: / 7.1.1998 / 21:42:31 / cg"
+    "Modified: / 13.1.1998 / 22:10:47 / cg"
 !
 
 _WLabelPeer_setAlignment:nativeContext
@@ -2133,13 +2721,11 @@
     self createdWindowsView:menuBar for:jMenuBarPeer.
 
     WindowCreationTrace == true ifTrue:[
-        'WMenuBarPeer_create: ' print. frame print. ' -> ' print. menuBar printNL.
-    ].
-
-    ^ nil
-
-    "Modified: / 19.8.1997 / 01:47:36 / cg"
+	'WMenuBarPeer_create: ' print. frame print. ' -> ' print. menuBar printNL.
+    ].
+
     "Created: / 7.1.1998 / 21:38:31 / cg"
+    "Modified: / 13.1.1998 / 22:10:54 / cg"
 !
 
 _WMenuItemPeer_create:nativeContext
@@ -2152,23 +2738,22 @@
     menu := jMenuPeer instVarNamed:'pData'.
 
     item := menu createAtIndex:nil.
-    item value:[jMenuItemPeer invoke:#'handleAction(I)V' with:0].
+    item value:[jMenuItemPeer perform:#'handleAction(I)V' with:0].
 
     lbl := jMenuItem instVarNamed:'label'.
     lbl notNil ifTrue:[
-        lbl := Java as_ST_String:lbl.
-        item label:lbl
+	lbl := Java as_ST_String:lbl.
+	item label:lbl
     ].
 
     jMenuItemPeer instVarNamed:'pData' put:item.
 
     WindowOPTrace == true ifTrue:[
-        'WMenuItem_create: ' print. menu print. ' -> ' print. item printNL.
-    ].
-    ^ nil
+	'WMenuItem_create: ' print. menu print. ' -> ' print. item printNL.
+    ].
 
     "Created: / 7.1.1998 / 21:40:44 / cg"
-    "Modified: / 7.1.1998 / 23:07:42 / cg"
+    "Modified: / 14.1.1998 / 17:55:01 / cg"
 !
 
 _WMenuItemPeer_enable:nativeContext
@@ -2197,8 +2782,8 @@
     item := menuPanel createAtIndex:nil.
     lbl := jMenu instVarNamed:'label'.
     lbl notNil ifTrue:[
-        lbl := Java as_ST_String:lbl.
-        item label:lbl
+	lbl := Java as_ST_String:lbl.
+	item label:lbl
     ].
 
     menu := MenuPanel new.
@@ -2207,10 +2792,63 @@
     jMenuPeer instVarNamed:'pData' put:menu.
 
 'createMenuPeer: ' print. menuPanel print. ' -> ' print. menu printNL.
-    ^ nil
-
-    "Modified: / 8.8.1997 / 12:07:06 / cg"
+
     "Created: / 7.1.1998 / 21:39:50 / cg"
+    "Modified: / 13.1.1998 / 22:11:09 / cg"
+!
+
+_WScrollbarPeer__setValues:nativeContext
+    |jScrollbarPeer jScrollbar scrollBar value visibleAmount min max|
+
+    scrollBar := self viewForWPeer:nativeContext.
+
+    jScrollbarPeer := nativeContext receiver.
+    jScrollbar := jScrollbarPeer instVarNamed:'target'.
+
+    value := nativeContext argAt:1.
+    visibleAmount := nativeContext argAt:2.
+    min := nativeContext argAt:3.
+    max := nativeContext argAt:4.
+
+    (min ~~ 0
+    or:[max ~~ 100]) ifTrue:[
+	self halt
+    ].
+
+    scrollBar thumbOrigin:value thumbHeight:visibleAmount.
+self halt.
+
+    "Created: / 13.1.1998 / 22:13:57 / cg"
+    "Modified: / 13.1.1998 / 22:17:23 / cg"
+!
+
+_WScrollbarPeer_create:nativeContext
+    |jScrollbarPeer jScrollbar jFrame frame scrollBar
+     lbl min max|
+
+self halt.
+    jScrollbarPeer := nativeContext receiver.
+    jScrollbar := jScrollbarPeer instVarNamed:'target'.
+
+    jFrame := nativeContext argAt:1.
+    frame := jFrame instVarNamed:'pData'.
+
+    (jScrollbar instVarNamed:'orientation') == 0 "HORIZONTAL" ifTrue:[
+	scrollBar := HorizontalScrollBar in:frame.
+    ] ifFalse:[
+	scrollBar := ScrollBar in:frame.
+    ].
+    min := jScrollbar instVarNamed:'minimum'.
+    max := jScrollbar instVarNamed:'maximum'.
+
+    self createdWindowsView:scrollBar for:jScrollbarPeer.
+
+    WindowCreationTrace == true ifTrue:[
+	'WScrollbarPeer_create: ' print. frame print. ' -> ' print. scrollBar printNL.
+    ].
+
+    "Created: / 5.1.1998 / 01:53:30 / cg"
+    "Modified: / 13.1.1998 / 22:09:07 / cg"
 !
 
 _WTextAreaPeer_create:nativeContext
@@ -2221,7 +2859,7 @@
     jFrame := nativeContext argAt:1.
     frame := jFrame instVarNamed:'pData'.
 
-    editTextView := EditTextView in:frame.
+    editTextView := HVScrollableView for:EditTextView in:frame.
 
     self createdWindowsView:editTextView for:jTextAreaPeer.
 
@@ -2229,10 +2867,8 @@
         'WTextAreaPeer_create: ' print. frame print. ' -> ' print. editTextView printNL.
     ].
 
-    ^ nil
-
-    "Modified: / 19.8.1997 / 01:47:44 / cg"
     "Created: / 7.1.1998 / 21:49:49 / cg"
+    "Modified: / 15.1.1998 / 12:56:18 / cg"
 !
 
 _WTextAreaPeer_insertText:nativeContext
@@ -2270,6 +2906,7 @@
     ^ textView characterPositionOfSelectionEnd
 
     "Created: / 8.1.1998 / 17:41:56 / cg"
+    "Modified: / 15.1.1998 / 15:47:18 / cg"
 !
 
 _WTextComponentPeer_getSelectionStart:nativeContext
@@ -2277,10 +2914,10 @@
 
     textView := self viewForWPeer:nativeContext.
 
-    ^ textView characterPositionOfSelection
+    ^ textView characterPositionOfSelection - 1
 
     "Created: / 15.8.1997 / 15:45:45 / cg"
-    "Modified: / 8.1.1998 / 17:36:43 / cg"
+    "Modified: / 15.1.1998 / 15:46:51 / cg"
 !
 
 _WTextComponentPeer_getText:nativeContext
@@ -2297,15 +2934,24 @@
 !
 
 _WTextComponentPeer_select:nativeContext
-    |textView|
+    |textView selStart selEnd|
 
     textView := self viewForWPeer:nativeContext.
-
-"/ self halt.
-"/     self unimplementedNativeMethod.
+    selStart := nativeContext argAt:1.
+    selEnd := nativeContext argAt:2.
+
+    selStart == selEnd ifTrue:[
+        "/ clear selection
+        textView unselect.
+        "/ and set caret
+        textView cursorToCharacterPosition:selStart + 1
+    ] ifFalse:[
+        "/ change selection
+        textView selectFromCharacterPosition:selStart+1 to:selEnd
+    ].
 
     "Created: / 15.8.1997 / 15:45:58 / cg"
-    "Modified: / 8.1.1998 / 17:37:01 / cg"
+    "Modified: / 15.1.1998 / 21:55:57 / cg"
 !
 
 _WTextComponentPeer_setText:nativeContext
@@ -2317,10 +2963,9 @@
     string := Java as_ST_String:jstring.
 
     textView contents:string.
-"/ self halt.
 
     "Created: / 5.1.1998 / 01:28:23 / cg"
-    "Modified: / 8.1.1998 / 17:37:15 / cg"
+    "Modified: / 15.1.1998 / 15:59:57 / cg"
 !
 
 _WTextFieldPeer_create:nativeContext
@@ -2336,26 +2981,43 @@
     self createdWindowsView:editField for:jTextFieldPeer.
 
     WindowCreationTrace == true ifTrue:[
-        'WTextFieldPeer_create: ' print. frame print. ' -> ' print. editField printNL.
-    ].
-
-    ^ nil
-
-    "Modified: / 19.8.1997 / 01:47:51 / cg"
+	'WTextFieldPeer_create: ' print. frame print. ' -> ' print. editField printNL.
+    ].
+
     "Created: / 5.1.1998 / 01:27:37 / cg"
+    "Modified: / 13.1.1998 / 22:11:29 / cg"
 !
 
 _WToolkit_eventLoop:nativeContext
-    [true] whileTrue:[
-        AbortSignal handle:[:ex |
-            ex return
-        ] do:[
-            self doWindowsEventThread.
-        ]
-    ].
-
-    "Modified: / 17.8.1997 / 20:13:13 / cg"
+    JavaEventThread := Processor activeProcess.
+    [
+        [true] whileTrue:[
+            AbortSignal handle:[:ex |
+                ex return
+            ] do:[
+                self doWindowsEventThread.
+            ]
+        ].
+    ] valueNowOrOnUnwindDo:[
+        JavaEventThread := nil.
+    ].
+
     "Created: / 6.1.1998 / 21:01:44 / cg"
+    "Modified: / 15.1.1998 / 19:48:55 / cg"
+!
+
+_WToolkit_getScreenHeight:nativeContext
+    ^ Screen current height
+
+    "Modified: / 20.3.1997 / 13:50:04 / cg"
+    "Created: / 13.1.1998 / 09:24:45 / cg"
+!
+
+_WToolkit_getScreenWidth:nativeContext
+    ^ Screen current width
+
+    "Modified: / 20.3.1997 / 13:50:04 / cg"
+    "Created: / 13.1.1998 / 09:24:37 / cg"
 !
 
 _WToolkit_init:nativeContext
@@ -2375,14 +3037,25 @@
 
     view := self viewForWPeer:nativeContext.
 
-    onOff := nativeContext argAt:1.
+    onOff := (nativeContext argAt:1) == 1.
+    view isTopView ifTrue:[
+	onOff ifTrue:[
+	    view minExtent:10@10.
+	    view maxExtent:(Screen current extent).
+	] ifFalse:[
+	    view minExtent:view extent.
+	    view maxExtent:view extent.
+	]
+    ] ifFalse:[
+	self halt.
+    ].
 
 "/ 'JAVA: WWindowPeer_setResizable: ' print. view print. ' yes/no: ' print. onOff printNL.
 
     ^ nil
 
     "Created: / 5.1.1998 / 00:57:59 / cg"
-    "Modified: / 8.1.1998 / 17:37:31 / cg"
+    "Modified: / 14.1.1998 / 18:04:07 / cg"
 !
 
 _WWindowPeer__setTitle:nativeContext
@@ -2418,18 +3091,18 @@
     fileNo := nativeContext argAt:2.
 
     fileNo == 0 ifTrue:[
-        myStream := Stdin
+	myStream := Stdin
     ] ifFalse:[
-        fileNo == 1 ifTrue:[
-           myStream := JavaConsoleStream ? Stdout
-        ] ifFalse:[
-            fileNo == 2 ifTrue:[
-                myStream := JavaConsoleStream ? Stderr
-            ] ifFalse:[
-                self halt:'invalid fileNo given'.
-                self internalError:'invalid fileNo given'.
-            ]
-        ]
+	fileNo == 1 ifTrue:[
+	   myStream := JavaConsoleStream ? Stdout
+	] ifFalse:[
+	    fileNo == 2 ifTrue:[
+		myStream := JavaConsoleStream ? Stderr
+	    ] ifFalse:[
+		self halt:'invalid fileNo given'.
+		self internalError:'invalid fileNo given'.
+	    ]
+	]
     ].
 
     self setOpenFile:myStream at:fileNo.
@@ -2440,6 +3113,26 @@
     "Modified: / 3.1.1998 / 14:52:02 / cg"
 !
 
+_FileInputStream_available:nativeContext
+    |file|
+
+    file := self validateFile:(nativeContext receiver).
+    file isNil ifTrue:[
+	self throwIOExceptionWithMessage:'invalid fileNo in available'.
+	^ self
+    ].
+    file isFileStream ifTrue:[
+	^ file size - file position + 1
+    ].
+    file atEnd ifTrue:[
+	^ 0.
+    ].
+    self halt.
+    ^ 1
+
+    "Modified: / 14.1.1998 / 15:12:52 / cg"
+!
+
 _FileInputStream_close:nativeContext
     ^ self anyFileStream_close:(nativeContext receiver)
 
@@ -2448,7 +3141,7 @@
 !
 
 _FileInputStream_open:nativeContext
-    |fs fd name stream fileNo|
+    |fs fd fn name stream fileNo|
 
     fs := nativeContext receiver.
     fd := fs instVarNamed:'fd'.
@@ -2465,7 +3158,7 @@
         ('JAVA: opening ' , name) infoPrintCR.
     ].
 
-    stream := name asFilename readStream.
+    stream := self fileStreamForReading:name.
     stream isNil ifTrue:[
         FileOpenTrace ifTrue:[
             ('JAVA: failed to open ' , name , ' for reading.') infoPrintCR.
@@ -2476,6 +3169,14 @@
         ^ self.
     ].
 
+"/    FileOpenConfirmation ifTrue:[
+"/        (self confirm:('JAVA Security check\\Opening ''' , name , ''' for reading.\Grant permission ?') withCRs)
+"/        ifFalse:[
+"/            self throwIOExceptionWithMessage:('no permission to open ' , name , ' for reading').
+"/            ^ self
+"/        ]
+"/    ].
+
     fileNo := self addOpenFile:stream.
 
     FileOpenTrace ifTrue:[
@@ -2484,8 +3185,8 @@
 
     fd instVarNamed:'fd' put:fileNo.
 
-    "Modified: / 2.1.1998 / 18:34:05 / cg"
     "Created: / 4.1.1998 / 16:47:12 / cg"
+    "Modified: / 16.1.1998 / 13:35:27 / cg"
 !
 
 _FileInputStream_read:nativeContext
@@ -2494,12 +3195,12 @@
     file := self validateFile:(nativeContext receiver).
 
     FileIOTrace ifTrue:[
-        ('JAVA: read 1 byte from ' , file pathName) infoPrintCR.
+	('JAVA: read 1 byte from ' , file pathName) infoPrintCR.
     ].
 
     byte := file nextByte.
     byte isNil ifTrue:[
-        ^ -1
+	^ -1
     ].
     ^ byte
 
@@ -2517,30 +3218,109 @@
     stream := self validateFile:(nativeContext receiver).
 
     "/ should always be bytes
+    bytes class isBytes ifFalse:[
+	self halt.
+    ].
 
     FileIOTrace ifTrue:[
-        ('JAVA: read ' , count printString , ' bytes from ' , stream pathName) infoPrintCR.
-    ].
-
-    stream readWait.
+	('JAVA: read ' , count printString , ' bytes from ' , stream pathName) infoPrintCR.
+    ].
+
+"/    stream readWait.
     nRead := stream nextBytes:count into:bytes startingAt:offset+1.
     nRead == 0 ifTrue:[
-        stream atEnd ifTrue:[
-            FileIOTrace ifTrue:[
-                ('JAVA: at EOF ' , nRead printString) infoPrintCR.
-            ].
-            ^ -1
-        ].
+	stream atEnd ifTrue:[
+	    FileIOTrace ifTrue:[
+		('JAVA: at EOF ' , nRead printString) infoPrintCR.
+	    ].
+	    ^ -1
+	].
     ].
     count ~~ nRead ifTrue:[
-        FileIOTrace ifTrue:[
-            ('JAVA: only got ' , nRead printString) infoPrintCR.
-        ]
+	FileIOTrace ifTrue:[
+	    ('JAVA: only got ' , nRead printString) infoPrintCR.
+	]
     ].
     ^ nRead
 
     "Created: / 4.1.1998 / 16:49:09 / cg"
-    "Modified: / 4.1.1998 / 16:51:26 / cg"
+    "Modified: / 14.1.1998 / 15:15:01 / cg"
+!
+
+_FileOutputStream_close:nativeContext
+    ^ self anyFileStream_close:(nativeContext receiver)
+
+    "Modified: / 15.8.1997 / 16:59:56 / cg"
+    "Created: / 13.1.1998 / 09:33:16 / cg"
+!
+
+_FileOutputStream_open:nativeContext
+    |fs fd name stream fileNo|
+
+    fs := nativeContext receiver.
+    fd := fs instVarNamed:'fd'.
+    (fd instVarNamed:'fd') ~~ 0 ifTrue:[
+        self halt:'file already open'.
+        self internalError:'file already open'.
+        ^ self.
+    ].
+
+    name := nativeContext argAt:1.
+    name := Java as_ST_String:name.
+
+    FileOpenTrace ifTrue:[
+        ('JAVA: opening ' , name) infoPrintCR.
+    ].
+
+    FileOpenConfirmation ifTrue:[
+        (self confirm:('JAVA Security check\\Opening ''' , name , ''' for writing.\Grant permission ?') withCRs)
+        ifFalse:[
+            self throwIOExceptionWithMessage:('no permission to open ' , name , ' for writing').
+            ^ self
+        ]
+    ].
+
+    stream := name asFilename writeStream.
+    stream isNil ifTrue:[
+        self throwIOExceptionWithMessage:('cannot open ' , name , ' for writing').
+    ].
+
+    fileNo := self addOpenFile:stream.
+
+    FileOpenTrace ifTrue:[
+        ('JAVA: opened ' , name , ' as FD ' , fileNo printString , ' for writing') infoPrintCR.
+    ].
+
+    fd instVarNamed:'fd' put:fileNo.
+
+    "Modified: / 16.1.1998 / 13:32:58 / cg"
+!
+
+_FileOutputStream_write:nativeContext
+    |byte file|
+
+    byte := nativeContext argAt:1.
+
+    file := self validateFile:(nativeContext receiver).
+
+    FileIOTrace ifTrue:[
+	file isFileStream ifTrue:[
+	    ('JAVA: write 1 byte to ' , file pathName) infoPrintCR.
+	] ifFalse:[
+	    file ~~ Stdout ifTrue:[
+		file ~~ Stderr ifTrue:[
+		    ('JAVA: write 1 byte to ' , file displayString) infoPrintCR.
+		]
+	    ]
+	]
+    ].
+
+    "/ should always be bytes
+
+    file nextPutByte:byte
+
+    "Created: / 13.1.1998 / 09:32:13 / cg"
+    "Modified: / 13.1.1998 / 09:32:31 / cg"
 !
 
 _FileOutputStream_writeBytes:nativeContext
@@ -2553,15 +3333,15 @@
     stream := self validateFile:(nativeContext receiver).
 
     FileIOTrace ifTrue:[
-        stream isFileStream ifTrue:[
-            ('JAVA: write ' , count printString , ' bytes to ' , stream pathName) infoPrintCR.
-        ] ifFalse:[
-            stream ~~ Stdout ifTrue:[
-                stream ~~ Stderr ifTrue:[
-                    ('JAVA: write ' , count printString , ' bytes to ' , stream displayString) infoPrintCR.
-                ]
-            ]
-        ]
+	stream isFileStream ifTrue:[
+	    ('JAVA: write ' , count printString , ' bytes to ' , stream pathName) infoPrintCR.
+	] ifFalse:[
+	    stream ~~ Stdout ifTrue:[
+		stream ~~ Stderr ifTrue:[
+		    ('JAVA: write ' , count printString , ' bytes to ' , stream displayString) infoPrintCR.
+		]
+	    ]
+	]
     ].
 
     "/ should always be bytes
@@ -2586,7 +3366,7 @@
     ^ 0 "/ FALSE
 
     "Created: / 4.1.1998 / 18:09:55 / cg"
-    "Modified: / 7.1.1998 / 10:31:52 / cg"
+    "Modified: / 15.1.1998 / 12:10:34 / cg"
 !
 
 _File_exists0:nativeContext
@@ -2603,7 +3383,7 @@
     ^ 0 "FALSE"
 
     "Created: / 5.1.1998 / 02:07:48 / cg"
-    "Modified: / 7.1.1998 / 10:32:15 / cg"
+    "Modified: / 15.1.1998 / 12:10:27 / cg"
 !
 
 _File_isAbsolute:nativeContext
@@ -2612,10 +3392,10 @@
     file := nativeContext receiver.
     path := file instVarNamed:'path'.
     path notNil ifTrue:[
-        path := Java as_ST_String:path.
-        (f := path asFilename) isAbsolute ifTrue:[
-            ^ 1 "/ TRUE
-        ]
+	path := Java as_ST_String:path.
+	(f := path asFilename) isAbsolute ifTrue:[
+	    ^ 1 "/ TRUE
+	]
     ].
     ^ 0 "/ FALSE
 
@@ -2636,8 +3416,8 @@
     ].
     ^ 0 "FALSE"
 
-    "Modified: / 19.8.1997 / 16:34:32 / cg"
     "Created: / 7.1.1998 / 10:31:37 / cg"
+    "Modified: / 15.1.1998 / 12:10:20 / cg"
 !
 
 _File_isFile0:nativeContext
@@ -2653,8 +3433,8 @@
     ].
     ^ 0 "/ FALSE
 
-    "Modified: / 19.8.1997 / 16:34:42 / cg"
     "Created: / 11.1.1998 / 11:40:22 / cg"
+    "Modified: / 15.1.1998 / 12:10:13 / cg"
 !
 
 _File_length0:nativeContext
@@ -2668,10 +3448,31 @@
             ^ f fileSize
         ]
     ].
-    ^ 0
-
-    "Modified: / 8.8.1997 / 12:04:05 / cg"
+    ^ -1
+
     "Created: / 7.1.1998 / 12:18:57 / cg"
+    "Modified: / 15.1.1998 / 12:10:06 / cg"
+!
+
+_File_list0:nativeContext
+    |file path f files|
+
+    file := nativeContext receiver.
+    path := file instVarNamed:'path'.
+    path notNil ifTrue:[
+        path := Java as_ST_String:path.
+        (f := path asFilename) exists ifTrue:[
+            f isDirectory ifTrue:[
+                files := f directoryContents asArray.
+                files := files collect:[:nm | Java as_String:nm].
+                ^ files
+            ]
+        ]
+    ].
+    ^ nil
+
+    "Created: / 14.1.1998 / 21:30:22 / cg"
+    "Modified: / 14.1.1998 / 21:32:09 / cg"
 ! !
 
 !JavaVM class methodsFor:'native - java.lang'!
@@ -2736,7 +3537,7 @@
     jClass := JavaClasses at:newClass ifAbsent:nil.
     jClass isNil ifTrue:[
         "/ class must be initialized (with all of its superclasses ?).
-        newClass initializeIfNotYetDone.
+        newClass classInit.
 
         JavaClasses at:newClass put:(jClass := (Java at:'java.lang.Class') new).
         JavaClasses at:jClass put:newClass.
@@ -2745,7 +3546,7 @@
     ^ jClass
 
     "Created: / 7.1.1998 / 12:35:10 / cg"
-    "Modified: / 8.1.1998 / 16:14:27 / cg"
+    "Modified: / 15.1.1998 / 00:57:08 / cg"
 !
 
 _ClassLoader_findSystemClass0:nativeContext
@@ -2781,7 +3582,7 @@
     jClass := JavaClasses at:class ifAbsent:nil.
     jClass isNil ifTrue:[
         "/ class must be initialized (with all of its superclasses ?).
-        class initializeIfNotYetDone.
+        class classInit.
 
         JavaClasses at:class put:(jClass := (Java at:'java.lang.Class') new).
         JavaClasses at:jClass put:class.
@@ -2789,7 +3590,7 @@
     ^ jClass
 
     "Created: / 5.1.1998 / 02:53:04 / cg"
-    "Modified: / 9.1.1998 / 22:32:50 / cg"
+    "Modified: / 15.1.1998 / 00:57:14 / cg"
 !
 
 _ClassLoader_getSystemResourceAsStream0:nativeContext
@@ -2798,21 +3599,21 @@
     jString := nativeContext argAt:1.
     rString := Java as_ST_String:jString.
     Java classPath do:[:aPath |
-        (dir := aPath asFilename) exists ifTrue:[
-            (file := dir construct:rString) exists ifTrue:[
-                text := file contents asString.
-
-                "/ Copy data from returned buffer into Java byte array. 
-
-                data := text asByteArray.
-
-                "/ Create input stream using byte array 
-
-                inStream := (Java classForName:'java.io.ByteArrayInputStream') basicNew.
-                inStream invoke:'<init>([B)V' with:data.
-                ^ inStream.
-            ]
-        ]
+	(dir := aPath asFilename) exists ifTrue:[
+	    (file := dir construct:rString) exists ifTrue:[
+		text := file contents asString.
+
+		"/ Copy data from returned buffer into Java byte array. 
+
+		data := text asByteArray.
+
+		"/ Create input stream using byte array 
+
+		inStream := (Java classForName:'java.io.ByteArrayInputStream') basicNew.
+		inStream invoke:'<init>([B)V' with:data.
+		^ inStream.
+	    ]
+	]
     ].
     ^ nil
 
@@ -2834,26 +3635,26 @@
     jClassLoader := nativeContext receiver.
     jCls := nativeContext argAt:1.
     jCls isNil ifTrue:[
-        self halt.
-        ^ nil
+	self halt.
+	^ nil
     ].
     cls := JavaClasses at:jCls ifAbsent:nil.
     cls isNil ifTrue:[
-        self halt.
-        ^ nil
+	self halt.
+	^ nil
     ].
     Transcript showCR:('resolving class ' , cls fullName , ' ...').
 
     JavaClassReader classLoaderQuerySignal answer:jClassLoader 
     do:[
-        JavaClassReader postLoadActions:true.
-        cls constantPool do:[:entry |
-            (entry isMemberOf:JavaUnresolvedClassConstant) ifTrue:[
-                self halt:'debugHalt'.
-                entry preResolve.
-                self halt:'debugHalt'.
-            ]
-        ]
+	JavaClassReader postLoadActions:true.
+	cls constantPool do:[:entry |
+	    (entry isMemberOf:JavaUnresolvedClassConstant) ifTrue:[
+		self halt:'debugHalt'.
+		entry preResolve.
+		self halt:'debugHalt'.
+	    ]
+	]
     ].
 
     "Created: / 7.1.1998 / 13:12:27 / cg"
@@ -2898,10 +3699,11 @@
         ^ self
     ].
 
+    cls classInit.
+
     jClass := JavaClasses at:cls ifAbsent:nil.
     jClass isNil ifTrue:[
         "/ class must be initialized (with all of its superclasses ?).
-        cls initializeIfNotYetDone.
 
         JavaClasses at:cls put:(jClass := (Java at:'java.lang.Class') new).
         JavaClasses at:jClass put:cls.
@@ -2909,7 +3711,7 @@
 
     ^ jClass
 
-    "Modified: / 9.1.1998 / 03:08:39 / cg"
+    "Modified: / 15.1.1998 / 00:57:22 / cg"
 !
 
 _Class_getClassLoader:nativeContext
@@ -2948,7 +3750,7 @@
     className := Java as_ST_String:jClassName.
 
     JavaClasses isNil ifTrue:[
-        self initializePrimitiveClasses
+	self initializePrimitiveClasses
     ].
     cls := JavaClasses at:className.
 
@@ -2995,7 +3797,7 @@
     jClass := JavaClasses at:cls ifAbsent:nil.
     jClass isNil ifTrue:[
         "/ class must be initialized (with all of its superclasses ?).
-        cls initializeIfNotYetDone.
+        cls classInit.
 
         JavaClasses at:cls put:(jClass := (Java at:'java.lang.Class') new).
         JavaClasses at:jClass put:cls.
@@ -3003,7 +3805,7 @@
     ^ jClass
 
     "Created: / 12.1.1998 / 12:38:36 / cg"
-    "Modified: / 12.1.1998 / 12:39:00 / cg"
+    "Modified: / 15.1.1998 / 00:57:34 / cg"
 !
 
 _Class_isInterface:nativeContext
@@ -3026,14 +3828,14 @@
 
     jClass := nativeContext receiver.
     cls := JavaClasses at:jClass.
-    cls initializeIfNotYetDone.
+    cls classInit.
     newInst := cls newCleared.
     newInst perform:#'<init>()V'.
 
     ^ newInst
 
     "Created: / 2.1.1998 / 22:41:38 / cg"
-    "Modified: / 7.1.1998 / 14:41:34 / cg"
+    "Modified: / 15.1.1998 / 00:57:37 / cg"
 !
 
 _Double_doubleToLongBits:nativeContext
@@ -3042,23 +3844,23 @@
     f := nativeContext argAt:1.
 
     UninterpretedBytes isBigEndian ifTrue:[
-        i := f basicAt:8. 
-        i := i bitOr:((f basicAt:7) bitShift:8).
-        i := i bitOr:((f basicAt:6) bitShift:16).
-        i := i bitOr:((f basicAt:5) bitShift:24).
-        i := i bitOr:((f basicAt:4) bitShift:32).
-        i := i bitOr:((f basicAt:3) bitShift:40).
-        i := i bitOr:((f basicAt:2) bitShift:48).
-        i := i bitOr:((f basicAt:1) bitShift:56).
+	i := f basicAt:8. 
+	i := i bitOr:((f basicAt:7) bitShift:8).
+	i := i bitOr:((f basicAt:6) bitShift:16).
+	i := i bitOr:((f basicAt:5) bitShift:24).
+	i := i bitOr:((f basicAt:4) bitShift:32).
+	i := i bitOr:((f basicAt:3) bitShift:40).
+	i := i bitOr:((f basicAt:2) bitShift:48).
+	i := i bitOr:((f basicAt:1) bitShift:56).
     ] ifFalse:[
-        i := f basicAt:1. 
-        i := i bitOr:((f basicAt:2) bitShift:8).
-        i := i bitOr:((f basicAt:3) bitShift:16).
-        i := i bitOr:((f basicAt:4) bitShift:24).
-        i := i bitOr:((f basicAt:5) bitShift:32).
-        i := i bitOr:((f basicAt:6) bitShift:40).
-        i := i bitOr:((f basicAt:7) bitShift:48).
-        i := i bitOr:((f basicAt:8) bitShift:56).
+	i := f basicAt:1. 
+	i := i bitOr:((f basicAt:2) bitShift:8).
+	i := i bitOr:((f basicAt:3) bitShift:16).
+	i := i bitOr:((f basicAt:4) bitShift:24).
+	i := i bitOr:((f basicAt:5) bitShift:32).
+	i := i bitOr:((f basicAt:6) bitShift:40).
+	i := i bitOr:((f basicAt:7) bitShift:48).
+	i := i bitOr:((f basicAt:8) bitShift:56).
     ].
 
     ^ i.
@@ -3073,23 +3875,23 @@
 
     aFloat := Float new.
     UninterpretedBytes isBigEndian ifTrue:[
-        aFloat basicAt:1 put:((i bitShift:-56) bitAnd:16rFF).
-        aFloat basicAt:2 put:((i bitShift:-48) bitAnd:16rFF).
-        aFloat basicAt:3 put:((i bitShift:-40) bitAnd:16rFF).
-        aFloat basicAt:4 put:((i bitShift:-32) bitAnd:16rFF).
-        aFloat basicAt:5 put:((i bitShift:-24) bitAnd:16rFF).
-        aFloat basicAt:6 put:((i bitShift:-16) bitAnd:16rFF).
-        aFloat basicAt:7 put:((i bitShift:-8) bitAnd:16rFF).
-        aFloat basicAt:8 put:(i bitAnd:16rFF).
+	aFloat basicAt:1 put:((i bitShift:-56) bitAnd:16rFF).
+	aFloat basicAt:2 put:((i bitShift:-48) bitAnd:16rFF).
+	aFloat basicAt:3 put:((i bitShift:-40) bitAnd:16rFF).
+	aFloat basicAt:4 put:((i bitShift:-32) bitAnd:16rFF).
+	aFloat basicAt:5 put:((i bitShift:-24) bitAnd:16rFF).
+	aFloat basicAt:6 put:((i bitShift:-16) bitAnd:16rFF).
+	aFloat basicAt:7 put:((i bitShift:-8) bitAnd:16rFF).
+	aFloat basicAt:8 put:(i bitAnd:16rFF).
     ] ifFalse:[
-        aFloat basicAt:1 put:(i bitAnd:16rFF).
-        aFloat basicAt:2 put:((i bitShift:-8) bitAnd:16rFF).
-        aFloat basicAt:3 put:((i bitShift:-16) bitAnd:16rFF).
-        aFloat basicAt:4 put:((i bitShift:-24) bitAnd:16rFF).
-        aFloat basicAt:5 put:((i bitShift:-32) bitAnd:16rFF).
-        aFloat basicAt:6 put:((i bitShift:-40) bitAnd:16rFF).
-        aFloat basicAt:7 put:((i bitShift:-48) bitAnd:16rFF).
-        aFloat basicAt:8 put:((i bitShift:-56) bitAnd:16rFF).
+	aFloat basicAt:1 put:(i bitAnd:16rFF).
+	aFloat basicAt:2 put:((i bitShift:-8) bitAnd:16rFF).
+	aFloat basicAt:3 put:((i bitShift:-16) bitAnd:16rFF).
+	aFloat basicAt:4 put:((i bitShift:-24) bitAnd:16rFF).
+	aFloat basicAt:5 put:((i bitShift:-32) bitAnd:16rFF).
+	aFloat basicAt:6 put:((i bitShift:-40) bitAnd:16rFF).
+	aFloat basicAt:7 put:((i bitShift:-48) bitAnd:16rFF).
+	aFloat basicAt:8 put:((i bitShift:-56) bitAnd:16rFF).
     ].
 
     ^ aFloat.
@@ -3102,12 +3904,12 @@
 
     s := nativeContext argAt:1.
     s notNil ifTrue:[
-        s := Java as_ST_String:s.
-        d := Float readFrom:s onError:nil.
+	s := Java as_ST_String:s.
+	d := Float readFrom:s onError:nil.
     ].
     d isNil ifTrue:[
-        self throwNumberFormatException.
-        "/ not reached
+	self throwNumberFormatException.
+	"/ not reached
     ].
 
     ^ d
@@ -3122,15 +3924,15 @@
     f := nativeContext argAt:1.
 
     UninterpretedBytes isBigEndian ifTrue:[
-        i := f basicAt:4. 
-        i := i bitOr:((f basicAt:3) bitShift:8).
-        i := i bitOr:((f basicAt:2) bitShift:16).
-        i := i bitOr:((f basicAt:1) bitShift:24).
+	i := f basicAt:4. 
+	i := i bitOr:((f basicAt:3) bitShift:8).
+	i := i bitOr:((f basicAt:2) bitShift:16).
+	i := i bitOr:((f basicAt:1) bitShift:24).
     ] ifFalse:[
-        i := f basicAt:1. 
-        i := i bitOr:((f basicAt:2) bitShift:8).
-        i := i bitOr:((f basicAt:3) bitShift:16).
-        i := i bitOr:((f basicAt:4) bitShift:24).
+	i := f basicAt:1. 
+	i := i bitOr:((f basicAt:2) bitShift:8).
+	i := i bitOr:((f basicAt:3) bitShift:16).
+	i := i bitOr:((f basicAt:4) bitShift:24).
     ].
 
     ^ i.
@@ -3138,6 +3940,30 @@
     "Created: / 4.1.1998 / 01:25:50 / cg"
 !
 
+_Float_intBitsToFloat:nativeContet
+    |i aFloat|
+
+    i := nativeContet argAt:1.
+
+    aFloat := ShortFloat basicNew.
+    UninterpretedBytes isBigEndian ifTrue:[
+	aFloat basicAt:1 put:((i bitShift:-24) bitAnd:16rFF).
+	aFloat basicAt:2 put:((i bitShift:-16) bitAnd:16rFF).
+	aFloat basicAt:3 put:((i bitShift:-8) bitAnd:16rFF).
+	aFloat basicAt:4 put:(i bitAnd:16rFF).
+    ] ifFalse:[
+	aFloat basicAt:1 put:(i bitAnd:16rFF).
+	aFloat basicAt:2 put:((i bitShift:-8) bitAnd:16rFF).
+	aFloat basicAt:3 put:((i bitShift:-16) bitAnd:16rFF).
+	aFloat basicAt:4 put:((i bitShift:-24) bitAnd:16rFF).
+    ].
+
+    ^ aFloat.
+
+    "Created: / 13.1.1998 / 23:03:36 / cg"
+    "Modified: / 13.1.1998 / 23:05:01 / cg"
+!
+
 _Math_ceil:nativeContext
     "ceiling"
 
@@ -3145,7 +3971,7 @@
 
     dVal := nativeContext argAt:1.
     (nativeContext argAt:2) ~~ DUMMY_DOUBLE_HIGHWORD ifTrue:[
-        self halt:'expected double arg'
+	self halt:'expected double arg'
     ].
     ^ dVal ceilingAsFloat
 
@@ -3159,7 +3985,7 @@
 
     dVal := nativeContext argAt:1.
     (nativeContext argAt:2) ~~ DUMMY_DOUBLE_HIGHWORD ifTrue:[
-        self halt:'expected double arg'
+	self halt:'expected double arg'
     ].
     ^ dVal cos
 
@@ -3173,7 +3999,7 @@
 
     dVal := nativeContext argAt:1.
     (nativeContext argAt:2) ~~ DUMMY_DOUBLE_HIGHWORD ifTrue:[
-        self halt:'expected double arg'
+	self halt:'expected double arg'
     ].
     ^ dVal floorAsFloat
 
@@ -3187,7 +4013,7 @@
 
     dVal := nativeContext argAt:1.
     (nativeContext argAt:2) ~~ DUMMY_DOUBLE_HIGHWORD ifTrue:[
-        self halt:'expected double arg'
+	self halt:'expected double arg'
     ].
     ^ dVal log
 
@@ -3201,11 +4027,11 @@
 
     dVal1 := nativeContext argAt:1.
     (nativeContext argAt:2) ~~ DUMMY_DOUBLE_HIGHWORD ifTrue:[
-        self halt:'expected double arg'
+	self halt:'expected double arg'
     ].
     dVal2 := nativeContext argAt:3.
     (nativeContext argAt:4) ~~ DUMMY_DOUBLE_HIGHWORD ifTrue:[
-        self halt:'expected double arg'
+	self halt:'expected double arg'
     ].
     ^ dVal1 raisedTo:dVal2
 
@@ -3220,7 +4046,7 @@
 
     dVal := nativeContext argAt:1.
     (nativeContext argAt:2) ~~ DUMMY_DOUBLE_HIGHWORD ifTrue:[
-        self halt:'expected double arg'
+	self halt:'expected double arg'
     ].
     ^ dVal sin
 
@@ -3234,7 +4060,7 @@
 
     dVal := nativeContext argAt:1.
     (nativeContext argAt:2) ~~ DUMMY_DOUBLE_HIGHWORD ifTrue:[
-        self halt:'expected double arg'
+	self halt:'expected double arg'
     ].
     ^ dVal sqrt
 
@@ -3264,7 +4090,7 @@
     jClass := JavaClasses at:cls ifAbsent:nil.
     jClass isNil ifTrue:[
         "/ class must be initialized (with all of its superclasses ?).
-        cls initializeIfNotYetDone.
+        cls classInit.
 
         JavaClasses at:cls put:(jClass := (Java at:'java.lang.Class') new).
         JavaClasses at:jClass put:cls.
@@ -3272,7 +4098,7 @@
     ^ jClass
 
     "Created: / 6.1.1998 / 18:28:27 / cg"
-    "Modified: / 6.1.1998 / 18:28:56 / cg"
+    "Modified: / 15.1.1998 / 00:57:39 / cg"
 !
 
 _Object_hashCode:nativeContext
@@ -3311,7 +4137,7 @@
 
 "/ DEBUG BEGIN
     (nativeMethodContext argAt:2) == DUMMY_LONG_HIGHWORD ifFalse:[
-        self halt:'expected long arg'
+	self halt:'expected long arg'
     ].
 "/ DEBUG END
 
@@ -3322,62 +4148,62 @@
     enteredMonitors := self enteredMonitors.
 
     enteredMonitors size > 0 ifTrue:[
-        MonitorTrace ifTrue:[
-            ('====> wait - exit ' , enteredMonitors size printString , ' monitors in ' , Processor activeProcess name , ' ...') infoPrintCR.
-        ].
-        enteredMonitors do:[:handle | 
-            |mon|
-
-            mon := LockTable at:handle ifAbsent:nil.
-            mon isNil ifTrue:[
-                self halt:'no monitor in wait'.
-            ] ifFalse:[
-                MonitorTrace ifTrue:[
-                    ('====> wait - exit monitor for ' , handle displayString , ' in ' , Processor activeProcess name , ' ...') infoPrintCR. 
-                ].
-                mon exit.
-            ].
-        ].
+	MonitorTrace ifTrue:[
+	    ('====> wait - exit ' , enteredMonitors size printString , ' monitors in ' , Processor activeProcess name , ' ...') infoPrintCR.
+	].
+	enteredMonitors do:[:handle | 
+	    |mon|
+
+	    mon := LockTable at:handle ifAbsent:nil.
+	    mon isNil ifTrue:[
+		self halt:'no monitor in wait'.
+	    ] ifFalse:[
+		MonitorTrace ifTrue:[
+		    ('====> wait - exit monitor for ' , handle displayString , ' in ' , Processor activeProcess name , ' ...') infoPrintCR. 
+		].
+		mon exit.
+	    ].
+	].
     ].
 
     [
-        ThreadTrace ifTrue:[
-            ('====> thread ' , Processor activeProcess name , ' waiting ...') infoPrintCR.
-        ].
-        tmo = 0 ifTrue:[
-            Processor activeProcess state:#javaWait.
-            sema wait.
-        ] ifFalse:[
-            sema waitWithTimeout:tmo / 1000.
-        ].
+	ThreadTrace ifTrue:[
+	    ('====> thread ' , Processor activeProcess name , ' waiting ...') infoPrintCR.
+	].
+	tmo = 0 ifTrue:[
+	    Processor activeProcess state:#javaWait.
+	    sema wait.
+	] ifFalse:[
+	    sema waitWithTimeout:tmo / 1000.
+	].
     ] valueNowOrOnUnwindDo:[
-        JavaVM releaseSemaphoreFor:handle.
+	JavaVM releaseSemaphoreFor:handle.
     ].
 
     "/ re-enter monitors.
 
     enteredMonitors size > 0 ifTrue:[
-        MonitorTrace ifTrue:[
-            ('====> wait - reenter ' , enteredMonitors size printString , ' monitors in ' , Processor activeProcess name , ' ...') infoPrintCR.
-        ].
-        enteredMonitors do:[:handle | 
-            |mon|
-
-            LockTableAccess critical:[
-                mon := LockTable at:handle ifAbsent:nil.
-                mon isNil ifTrue:[
-                    LockTable at:handle put:(mon := Monitor new)
-                ]
-            ].
-            MonitorTrace ifTrue:[
-                ('====> wait - reenter monitor for ' , handle displayString , ' in ' , Processor activeProcess name , ' ...') infoPrintCR. 
-            ].
-            mon enter.
-        ]
+	MonitorTrace ifTrue:[
+	    ('====> wait - reenter ' , enteredMonitors size printString , ' monitors in ' , Processor activeProcess name , ' ...') infoPrintCR.
+	].
+	enteredMonitors do:[:handle | 
+	    |mon|
+
+	    LockTableAccess critical:[
+		mon := LockTable at:handle ifAbsent:nil.
+		mon isNil ifTrue:[
+		    LockTable at:handle put:(mon := Monitor new)
+		]
+	    ].
+	    MonitorTrace ifTrue:[
+		('====> wait - reenter monitor for ' , handle displayString , ' in ' , Processor activeProcess name , ' ...') infoPrintCR. 
+	    ].
+	    mon enter.
+	]
     ].
 
     ThreadTrace ifTrue:[
-        '====> thread continues ...' printCR.
+	'====> thread continues ...' printCR.
     ]
 
     "Modified: / 9.1.1998 / 10:41:47 / cg"
@@ -3393,9 +4219,9 @@
     fileName := Java as_ST_String:jFileName.
 
     path = '__builtIn__' ifTrue:[
-        libName := path , '/' , fileName
+	libName := path , '/' , fileName
     ] ifFalse:[
-        libName := path , '/lib' , fileName , '.so'.
+	libName := path , '/lib' , fileName , '.so'.
     ].
     ^ Java as_String:libName.
 
@@ -3403,28 +4229,54 @@
     "Created: / 4.1.1998 / 19:07:14 / cg"
 !
 
+_Runtime_execInternal:nativeContext
+    "Run a unix-command; return a process object."
+
+    |cmdAndArgArray envArray cmd jProcessClass jProcess|
+
+"/    cmdAndArgArray := nativeContext argAt:1.
+"/    envArray := nativeContext argAt:2.
+"/
+"/    cmd := cmdAndArgArray at:1.
+"/
+"/    jProcessClass := Java classForName:'java.lang.UNIXProcess'.
+"/    jProcessClass notNil ifTrue:[
+"/        jProcess := jProcessClass newCleared.
+"/        jProcess
+"/            perform:#'<init>([Ljava/lang/String;[Ljava/lang/String;)V'
+"/            with:cmdAndArgArray
+"/            with:envArray.
+"/        ^ jProcess
+"/    ].
+    self throwIOExceptionWithMessage:'Process execution disabled/unimplemented'.
+    ^ nil
+
+    "Created: / 15.1.1998 / 01:50:31 / cg"
+    "Modified: / 15.1.1998 / 02:09:29 / cg"
+!
+
 _Runtime_exitInternal:nativeContext
     "exit - here, we only shut down java threads"
 
     |enteredMonitors|
 
     (enteredMonitors := self enteredMonitors) size > 0 ifTrue:[
-        enteredMonitors do:[:handle | 
-            | mon |
-
-            mon := LockTable at:handle ifAbsent:nil.
-            mon isNil ifTrue:[
-                self halt:'no monitor in exitInternal'.
-            ] ifFalse:[
-                mon exit.
+	enteredMonitors do:[:handle | 
+	    | mon |
+
+	    mon := LockTable at:handle ifAbsent:nil.
+	    mon isNil ifTrue:[
+		self halt:'no monitor in exitInternal'.
+	    ] ifFalse:[
+		mon exit.
 ('====> terminateThread - exit monitor for ' , handle displayString , ' in ' , Processor activeProcess name , ' ...') infoPrintCR. 
 "/                LockTableAccess critical:[
 "/                    mon isFree ifTrue:[
 "/                        LockTable removeKey:handle
 "/                    ]
 "/                ]
-            ].
-        ].
+	    ].
+	].
     ].
 
     JavaVM releaseAllJavaResources.
@@ -3461,11 +4313,11 @@
 
     path := ''.
     LibPath do:[:comp | path size == 0 ifTrue:[
-                            path := path , comp
-                        ] ifFalse:[
-                            path := path , ':' , comp
-                        ]
-               ].
+			    path := path , comp
+			] ifFalse:[
+			    path := path , ':' , comp
+			]
+	       ].
 
     ^ Java as_String:path
 
@@ -3489,9 +4341,9 @@
 _Runtime_loadFileInternalI:nativeContext
     "1.1b3 change; load a sharedLib like 'loadFileInternal',
      but return integer:
-        -1   outOfMemory error
-        0    failed to load
-        1    loaded or already loaded (i.e. ok)"
+	-1   outOfMemory error
+	0    failed to load
+	1    loaded or already loaded (i.e. ok)"
 
     |jLibName libName libHandle|
 
@@ -3499,27 +4351,27 @@
     libName := Java as_ST_String:jLibName.
 
     (SimulatedLibs includes:libName) ifTrue:[
-        ('JAVA: builtIn libLoad simulated: ' , libName) printNL.
-        ^ 1
+	('JAVA: builtIn libLoad simulated: ' , libName) printNL.
+	^ 1
     ].
     (LoadedLibs notNil and:[LoadedLibs includesKey:libName]) ifTrue:[
-        ('JAVA: already loaded: ' , libName) printNL.
-        ^ 1
+	('JAVA: already loaded: ' , libName) printNL.
+	^ 1
     ].
 
     libName asFilename exists ifFalse:[
-        ('JAVA: no file to load: ' , libName) printNL.
-        ^ 0
+	('JAVA: no file to load: ' , libName) printNL.
+	^ 0
     ].
 
     libHandle := ObjectFileLoader loadLibrary:libName.
     libHandle isNil ifTrue:[
-        ('JAVA: failed to load: ' , libName) printNL.
-        ^ 0
+	('JAVA: failed to load: ' , libName) printNL.
+	^ 0
     ].
 
     LoadedLibs isNil ifTrue:[
-        LoadedLibs := Dictionary new.
+	LoadedLibs := Dictionary new.
     ].
 
     LoadedLibs at:libName put:libHandle.
@@ -3537,6 +4389,36 @@
     "Created: / 12.1.1998 / 12:59:23 / cg"
 !
 
+_SecurityManager_classLoaderDepth:nativeContext
+    |con depth|
+
+    con := thisContext sender.
+    depth := 1.
+    [con notNil] whileTrue:[
+	con receiver == JavaClassReader classLoaderQuerySignal ifTrue:[
+	    con selector == #handle:do: ifTrue:[
+		depth := depth + 1
+	    ]
+	].
+	con := con sender.
+    ].
+'JAVA: classLoaderDepth -> ' infoPrint. depth infoPrintCR.
+    ^ depth.
+
+    "Created: / 13.1.1998 / 09:21:46 / cg"
+    "Modified: / 13.1.1998 / 09:33:43 / cg"
+!
+
+_SecurityManager_currentClassLoader:nativeContext
+    |loader|
+
+    loader := JavaClassReader classLoaderQuerySignal raise.
+'JAVA: currentClassLoader -> ' infoPrint. loader displayString infoPrintCR.
+    ^ loader.
+
+    "Created: / 13.1.1998 / 09:23:28 / cg"
+!
+
 _System_arraycopy:nativeContext
     |srcArray srcIdx dstArray dstIdx count|
 
@@ -3547,12 +4429,12 @@
     count := nativeContext argAt:5.
 
     srcArray class isBytes ifTrue:[
-        dstArray class isBytes ifFalse:[
-            self halt:'incompatible arraycopy collections'.
-        ].
-        dstArray replaceBytesFrom:(dstIdx+1) to:(dstIdx+count) with:srcArray startingAt:(srcIdx+1).
+	dstArray class isBytes ifFalse:[
+	    self halt:'incompatible arraycopy collections'.
+	].
+	dstArray replaceBytesFrom:(dstIdx+1) to:(dstIdx+count) with:srcArray startingAt:(srcIdx+1).
     ] ifFalse:[
-        dstArray replaceFrom:(dstIdx+1) to:(dstIdx+count) with:srcArray startingAt:(srcIdx+1).
+	dstArray replaceFrom:(dstIdx+1) to:(dstIdx+count) with:srcArray startingAt:(srcIdx+1).
     ].
     ^ nil.
 
@@ -3644,7 +4526,7 @@
     p := Processor activeProcess.
     t := self javaThreadForSTProcess:p.
     t notNil ifTrue:[
-        ^ t
+	^ t
     ].
     t := self newThread:'main'.
     Java threads at:t put:p.
@@ -3662,8 +4544,8 @@
     jThread := nativeContext receiver.
     stProcess := JavaVM stProcessForJavaThread:jThread.
     stProcess isNil ifTrue:[
-        ('JAVA: no stProcess for javaThread: ' , jThread displayString) printNL.
-        ^ 0 "FALSE"
+	('JAVA: no stProcess for javaThread: ' , jThread displayString) printNL.
+	^ 0 "FALSE"
     ].
     stProcess isDead ifTrue:[^ 0 "FALSE"].
     ^ 1 "TRUE"
@@ -3680,8 +4562,8 @@
     jThread := nativeContext receiver.
     stProcess := self stProcessForJavaThread:jThread.
     stProcess isNil ifTrue:[
-        self halt.
-        ^ 0
+	self halt.
+	^ 0
     ].
 
     clearInterrupt := nativeContext argAt:1.
@@ -3701,8 +4583,8 @@
     jThread := nativeContext receiver.
     stProcess := JavaVM stProcessForJavaThread:jThread.
     stProcess isNil ifTrue:[
-        ('JAVA: no stProcess for javaThread: ' , jThread displayString) printNL.
-        ^ nil "void"
+	('JAVA: no stProcess for javaThread: ' , jThread displayString) printNL.
+	^ nil "void"
     ].
     stProcess resume
 
@@ -3718,12 +4600,12 @@
     prio := nativeMethodContext argAt:1.
 
     p isNil ifTrue:[
-        'JAVA [info]: no process yet (in setPriority)' infoPrintCR.
-        ^ nil
+	'JAVA [info]: no process yet (in setPriority)' infoPrintCR.
+	^ nil
     ].
 
     ThreadTrace ifTrue:[
-        'JAVA [info]: setPrio: ' print. t print. ' pri= ' print. prio print. ' p= ' print. p printNL.
+	'JAVA [info]: setPrio: ' print. t print. ' pri= ' print. prio print. ' p= ' print. p printNL.
     ].
     ^ nil
 
@@ -3737,14 +4619,14 @@
     |millis|
 
     (nativeContext argAt:2) ~~ DUMMY_LONG_HIGHWORD ifTrue:[
-        self internalError:'expected long arg'.
+	self internalError:'expected long arg'.
     ] ifFalse:[
-        millis := nativeContext argAt:1.
-        Delay waitForMilliseconds:(millis max:200)
+	millis := nativeContext argAt:1.
+	Delay waitForMilliseconds:(millis max:50)
     ].
 
     "Created: / 7.1.1998 / 15:34:23 / cg"
-    "Modified: / 7.1.1998 / 15:34:36 / cg"
+    "Modified: / 13.1.1998 / 13:48:25 / cg"
 !
 
 _Thread_start:nativeContext
@@ -3787,7 +4669,7 @@
     ^ nil
 
     "Created: / 3.1.1998 / 02:05:52 / cg"
-    "Modified: / 9.1.1998 / 03:39:54 / cg"
+    "Modified: / 15.1.1998 / 19:26:38 / cg"
 !
 
 _Thread_stop0:nativeContext
@@ -3833,8 +4715,8 @@
     jThread := nativeContext receiver.
     stProcess := JavaVM stProcessForJavaThread:jThread.
     stProcess isNil ifTrue:[
-        ('JAVA: no stProcess for javaThread: ' , jThread displayString) printNL.
-        ^ nil "void"
+	('JAVA: no stProcess for javaThread: ' , jThread displayString) printNL.
+	^ nil "void"
     ].
     stProcess suspend
 
@@ -3850,13 +4732,13 @@
     jThread := nativeContext receiver.
     stProcess := JavaVM stProcessForJavaThread:jThread.
     stProcess isNil ifTrue:[
-        ('JAVA: no stProcess for javaThread: ' , jThread displayString) printNL.
-        ^ nil "void"
+	('JAVA: no stProcess for javaThread: ' , jThread displayString) printNL.
+	^ nil "void"
     ].
     stProcess == Processor activeProcess ifTrue:[
-        Processor yield.
+	Processor yield.
     ] ifFalse:[
-        self halt.
+	self halt.
     ].
 
     "Created: / 5.1.1998 / 02:03:51 / cg"
@@ -3883,8 +4765,12 @@
     "/ we are not interrested in all intermediate Exception frames ...
     "/
     FullExceptionTrace ifFalse:[
-        [(con receiver isKindOf:exClass)
-         or:[con receiver == self]] whileTrue:[
+        "/ first, skip any JavaVM contexts
+        [con receiver == exceptionObject] whileFalse:[
+            con := con sender
+        ].
+        "/ then, all exception-init contexts
+        [con receiver == exceptionObject] whileTrue:[
             con := con sender
         ].
     ].
@@ -3892,7 +4778,9 @@
     list := OrderedCollection new.
     [con notNil] whileTrue:[
         (con isKindOf:JavaContext) ifTrue:[
-            list add:con
+            "/ add a copy, in case the context continues with some
+            "/ cleanup ...
+            list add:con shallowCopy
         ].
         con := con sender
     ].
@@ -3902,27 +4790,38 @@
     ^ nil.
 
     "Created: / 4.1.1998 / 14:27:40 / cg"
-    "Modified: / 8.1.1998 / 03:06:03 / cg"
+    "Modified: / 14.1.1998 / 23:57:51 / cg"
 !
 
 _Throwable_printStackTrace0:nativeContext
-    |outStream exceptionObject contextList|
+    |out outStream exceptionObject contextList|
 
     outStream := nativeContext argAt:1.
     exceptionObject := nativeContext receiver.
 
     contextList := exceptionObject instVarNamed:'backtrace'.
 
-    self javaConsoleStream cr.
-    self javaConsoleStream nextPutLine:'JAVA: stackTrace:'.
+    out := self javaConsoleStream.
+    out cr.
+    out nextPutLine:'JAVA: stackTrace:'.
 
     contextList do:[:con |
-        self javaConsoleStream nextPutLine:('    ' , con displayString).
-    ].
-    self javaConsoleStream nextPutLine:'----------------------------------------------------'
+        out 
+            nextPutAll:'  '; 
+            nextPutAll:(con method javaClass fullName);
+            nextPutAll:'.';
+            nextPutAll:(con method selector);
+            nextPutAll:' ['; 
+            nextPutAll:(con method javaClass sourceFile); 
+            nextPutAll:' '; 
+            nextPutAll:(con lineNumber displayString); 
+            nextPutAll:']'.
+        out cr
+    ].
+    out nextPutLine:'----------------------------------------------------'
 
     "Created: / 4.1.1998 / 14:27:40 / cg"
-    "Modified: / 8.1.1998 / 14:34:34 / cg"
+    "Modified: / 15.1.1998 / 00:14:40 / cg"
 ! !
 
 !JavaVM class methodsFor:'native - java.math'!
@@ -3967,7 +4866,7 @@
     hostName := Java as_ST_String:jHostName.
     addrBytes := Socket ipAddressOfHost:hostName.
     addrBytes isNil ifTrue:[
-        addrBytes := #[0 0 0 0] copy
+	addrBytes := #[0 0 0 0] copy
     ].
     ^ Array with:addrBytes
 
@@ -4017,20 +4916,20 @@
     chain := OrderedCollection new.
     con := thisContext sender.
     [con notNil] whileTrue:[
-        (con isMemberOf:JavaContext) ifTrue:[
-            cls := con receiver class.
-            cls isMeta ifTrue:[
-                "/ t'was a static method
-                cls := cls soleInstance
-            ].
-            jClass := JavaClasses at:cls ifAbsent:nil.
-            jClass isNil ifTrue:[
-                JavaClasses at:cls put:(jClass := (Java at:'java.lang.Class') new).
-                JavaClasses at:jClass put:cls.
-            ].
-            chain add:jClass.
-        ].
-        con := con sender.
+	(con isMemberOf:JavaContext) ifTrue:[
+	    cls := con receiver class.
+	    cls isMeta ifTrue:[
+		"/ t'was a static method
+		cls := cls soleInstance
+	    ].
+	    jClass := JavaClasses at:cls ifAbsent:nil.
+	    jClass isNil ifTrue:[
+		JavaClasses at:cls put:(jClass := (Java at:'java.lang.Class') new).
+		JavaClasses at:jClass put:cls.
+	    ].
+	    chain add:jClass.
+	].
+	con := con sender.
     ].
     ^ chain asArray
 
@@ -4074,20 +4973,89 @@
 !JavaVM class methodsFor:'native - sun.audio'!
 
 _AudioDevice_audioClose:nativeContext
+    |device fd stream|
+
+    device := nativeContext receiver.
+    device notNil ifTrue:[
+	fd := device instVarNamed:'dev'.
+	(fd notNil and:[fd > 0]) ifTrue:[
+	    stream := self getOpenFileAt:fd.
+	    stream notNil ifTrue:[
+		stream close.
+		device instVarNamed:'dev' put:0.
+	    ]
+	]
+    ]
 
     "Created: / 10.1.1998 / 15:45:16 / cg"
+    "Modified: / 13.1.1998 / 18:08:20 / cg"
 !
 
 _AudioDevice_audioOpen:nativeContext
-    ^ -1
+    |f stream fileNo|
+
+    NoAudio ifTrue:[
+	^ -1
+    ].
+
+    f := '/dev/audio' asFilename.
+"/    stream := f readWriteStream.
+    Stream streamErrorSignal handle:[:ex |
+	Stream streamErrorSignal handle:[:ex |
+	    stream := nil.
+	    ex return.
+	] do:[
+	    stream := SoundStream writing.
+	].
+    ] do:[
+	stream := SoundStream writing.
+    ].
+    stream isNil ifTrue:[
+	f exists ifTrue:[
+	   ^ 0
+	].
+	^ -1
+    ].
+
+    stream setSampleRate:8000.
+    fileNo := self addOpenFile:stream.
+
+    FileOpenTrace ifTrue:[
+	('JAVA: opened audioDevice as FD ' , fileNo printString) infoPrintCR.
+    ].
+
+    ^ fileNo
 
     "Created: / 10.1.1998 / 15:45:30 / cg"
+    "Modified: / 14.1.1998 / 14:57:16 / cg"
+!
+
+_AudioDevice_audioWrite:nativeContext
+    |device fd stream bytes count|
+
+    device := nativeContext receiver.
+    device notNil ifTrue:[
+	fd := device instVarNamed:'dev'.
+	(fd notNil and:[fd > 0]) ifTrue:[
+	    stream := self getOpenFileAt:fd.
+	    stream notNil ifTrue:[
+		bytes := nativeContext argAt:1.
+		count := nativeContext argAt:2.
+		stream nextPutBytes:count from:bytes startingAt:1
+	    ]
+	]
+    ]
+
+    "Created: / 10.1.1998 / 15:45:16 / cg"
+    "Modified: / 13.1.1998 / 18:07:20 / cg"
 ! !
 
 !JavaVM class methodsFor:'native - sun.awt'!
 
 _GifImageDecoder_parseImage:nativeContext
-    |decoder width height bool1 depth srcBytes dstBytes i1 i2 colorModel|
+    |decoder width height bool1 depth subHdrBytes dstBytes i1 i2 colorModel
+     stream byte compressedData compressedSize index count data 
+     leftOffs topOffs codeLen flags pixelStore clrModel t buffSize|
 
     decoder := nativeContext receiver.
 
@@ -4097,26 +5065,94 @@
     height := nativeContext argAt:4.
     bool1 := nativeContext argAt:5.
     depth := nativeContext argAt:6.
-    srcBytes := nativeContext argAt:7.
+    subHdrBytes := nativeContext argAt:7.
     dstBytes := nativeContext argAt:8.
     colorModel := nativeContext argAt:9.
 
-'JAVA: GIF parseImage ignored for now' infoPrintCR.
-
-self halt.
+    leftOffs := subHdrBytes wordAt:1 MSB:false.
+    topOffs := subHdrBytes wordAt:3 MSB:false.
+    width := subHdrBytes wordAt:5 MSB:false.
+    height := subHdrBytes wordAt:7 MSB:false.
+    flags := subHdrBytes at:9.
+    codeLen := subHdrBytes at:10.
+
+    stream := decoder instVarNamed:'input'.
+    pixelStore := decoder instVarNamed:'store'.
+
+    buffSize := (width * height // 2) max:4096.
+    compressedData := ByteArray uninitializedNew:buffSize.
+
+    "get compressed data"
+    index := 1.
+    count := stream perform:#read.
+
+    [count notNil and:[count > 0]] whileTrue:[
+        (index + count) > buffSize ifTrue:[
+            t := ByteArray uninitializedNew:(buffSize * 2).
+            t replaceFrom:1 to:buffSize with:compressedData startingAt:1.
+            compressedData := t.
+            buffSize := buffSize * 2.
+        ].
+        count := stream 
+                    perform:#'read([BII)I' 
+                    with:compressedData
+                    with:index-1
+                    with:count.
+        count > 0 ifTrue:[
+            index := index + count.
+            count := stream perform:#read.
+        ]
+    ].
+    compressedSize := index - 1.
+
+    data := pixelStore perform:#'allocateLines(I)Ljava/lang/Object;' with:height.
+    (data isMemberOf:ByteArray) ifFalse:[
+        self halt.
+        ^ 0.
+    ].
+"/    'GIFReader: decompressing ...' infoPrintCR.
+
+
+    GIFReader 
+        decompressGIFFrom:compressedData
+        count:compressedSize
+        into:data
+        startingAt:1
+        codeLen:(codeLen + 1).
+
+    clrModel := pixelStore instVarNamed:'colormodel'.
+
+    pixelStore 
+        perform:#'setPixels(IIII[BII)Z'
+        withArguments:
+            (Array 
+                with:0        "/ x
+                with:0        "/ y
+                with:width    "/ w
+                with:height   "/ h
+                with:data
+                with:0        "/ offs
+                with:width).   "/ scanSize
+
+    pixelStore  perform:#'imageComplete()V'.
+"/        perform:#'imageComplete(I)V' 
+"/        with:((Java at:'java.awt.image.ImageConsumer') instVarNamed:'STATICIMAGEDONE').
+
 "/ self internalError:'breakPoint'.
     ^ 1 "/ true
 
-    "Modified: / 11.1.1998 / 16:00:34 / cg"
+    "Modified: / 14.1.1998 / 15:10:59 / cg"
 !
 
 _ImageRepresentation_disposeImage:nativeContext
     |imgRep|
 
     imgRep := nativeContext receiver.
+    imgRep instVarNamed:'pData' put:0.
+"/    self halt.
 
     "Created: / 7.1.1998 / 22:31:46 / cg"
-    "Modified: / 7.1.1998 / 23:00:07 / cg"
+    "Modified: / 14.1.1998 / 17:58:31 / cg"
 !
 
 _ImageRepresentation_finish:nativeContext
@@ -4124,23 +5160,174 @@
 
     imgRep := nativeContext receiver.
     bool := nativeContext argAt:1.
-
+"/ self halt.
     'JAVA: ImageRepresentation_finish ignored for now' infoPrintCR.
 
     ^ 1 "/ true
 
-    "Modified: / 21.8.1997 / 17:07:13 / cg"
     "Created: / 8.1.1998 / 00:11:40 / cg"
+    "Modified: / 13.1.1998 / 13:41:35 / cg"
+!
+
+_ImageRepresentation_imageDraw:nativeContext
+    |imgRep x y img deviceImage jGraphics gc clr|
+
+    imgRep := nativeContext receiver.
+    img := imgRep instVarNamed:'pData'.
+    (img isNil or:[img == 0]) ifTrue:[
+        "/ self halt.
+        ^ self.
+    ].
+    jGraphics := nativeContext argAt:1.
+    gc := jGraphics instVarNamed:'pData'.
+    gc realized ifFalse:[^ self].
+
+    x := nativeContext argAt:2.
+    y := nativeContext argAt:3.
+    clr := nativeContext argAt:4.
+    deviceImage := img onDevice:gc device.
+    deviceImage ~~ img ifTrue:[
+        imgRep instVarNamed:'pData' put:deviceImage.
+    ].
+    deviceImage displayOn:gc x:x y:y.
+    ^ 1.
+
+    "Created: / 13.1.1998 / 13:32:28 / cg"
+    "Modified: / 15.1.1998 / 12:21:27 / cg"
+!
+
+_ImageRepresentation_imageStretch:nativeContext
+    |imgRep x1 y1 x2 y2 srcX1 srcY1 w h 
+     img deviceImage jGraphics gc clr stretchWidth stretchHeight|
+
+    imgRep := nativeContext receiver.
+    img := imgRep instVarNamed:'pData'.
+    (img isNil or:[img == 0]) ifTrue:[
+        "/ self halt.
+        ^ self.
+    ].
+
+    jGraphics := nativeContext argAt:1.
+    gc := jGraphics instVarNamed:'pData'.
+    gc realized ifFalse:[^ self].
+
+    x1 := nativeContext argAt:2.
+    y1 := nativeContext argAt:3.
+    x2 := nativeContext argAt:4.
+    y2:= nativeContext argAt:5.
+    srcX1 := nativeContext argAt:6.
+    srcY1 := nativeContext argAt:7.
+    w := nativeContext argAt:8.
+    h := nativeContext argAt:9.
+    clr := nativeContext argAt:10.
+
+    (srcX1 ~~ 0 or:[srcY1 ~~ 0]) ifTrue:[
+        self halt.
+        ^ self.
+    ].
+    (w ~~ img width or:[h ~~ img height]) ifTrue:[
+        self halt.
+        ^ self
+    ].
+
+    "/ TODO: remember magnified images somewhere for a while,
+    "/ to avoid repeated action ...
+
+    stretchWidth := (x2-x1).
+    stretchHeight := (y2-y1).
+
+    (stretchWidth == img width
+    and:[stretchHeight == img height]) ifTrue:[
+        deviceImage := img onDevice:gc device.
+        deviceImage ~~ img ifTrue:[
+            imgRep instVarNamed:'pData' put:deviceImage.
+        ].
+    ] ifFalse:[
+        ImageStretchCache notNil ifTrue:[
+            deviceImage := ImageStretchCache at:img ifAbsent:nil.
+        ].
+        (deviceImage isNil 
+        or:[deviceImage width ~~ stretchWidth
+        or:[deviceImage height ~~ stretchHeight]]) ifTrue:[
+            deviceImage := (img magnifiedTo:stretchWidth@stretchHeight) onDevice:gc device.
+            ImageStretchCache isNil ifTrue:[
+                ImageStretchCache := WeakIdentityDictionary new.
+            ].
+            ImageStretchCache at:img put:deviceImage
+        ].
+    ].
+    deviceImage displayOn:gc x:x1 y:y1
+
+    "Created: / 13.1.1998 / 13:32:28 / cg"
+    "Modified: / 15.1.1998 / 13:14:47 / cg"
 !
 
 _ImageRepresentation_offscreenInit:nativeContext
     |imgRep jclr|
 
     imgRep := nativeContext receiver.
-    jclr := nativeContext argAt:1
+    jclr := nativeContext argAt:1.
+    self halt.
 
     "Created: / 7.1.1998 / 22:31:46 / cg"
-    "Modified: / 11.1.1998 / 16:32:29 / cg"
+    "Modified: / 13.1.1998 / 13:08:40 / cg"
+!
+
+_ImageRepresentation_setBytePixels:nativeContext
+    |imgRep x y w h clrModel bytes i1 i2
+     img depth cmap rgbMap opaque transparentColorIndex|
+
+    imgRep := nativeContext receiver.
+    x := nativeContext argAt:1.
+    y := nativeContext argAt:2.
+    w := nativeContext argAt:3.
+    h := nativeContext argAt:4.
+    clrModel := nativeContext argAt:5.
+    bytes := nativeContext argAt:6.
+    i1 := nativeContext argAt:7.  "/ offset ??
+    i2 := nativeContext argAt:8.  "/ scanLineWidth ??
+
+"/    self halt.
+
+    depth := clrModel instVarNamed:'pixel_bits'.
+    (clrModel instVarNamed:'map_size') ~~ 0 ifTrue:[
+	rgbMap := clrModel instVarNamed:'rgb'.
+	cmap := Array new:rgbMap size.
+	rgbMap 
+	    keysAndValuesDo:[:idx :rgb |
+		cmap at:idx put:(Color rgbValue:(rgb bitAnd:16rFFFFFF))
+	    ].        
+    ].
+
+    opaque := (clrModel instVarNamed:'opaque') ~~ 0.
+    opaque ifFalse:[
+	transparentColorIndex := clrModel instVarNamed:'transparent_index'
+    ].
+
+    img := imgRep instVarNamed:'pData'.
+    (img isNil or:[img == 0]) ifTrue:[
+	img := Image width:w height:h depth:depth fromArray:bytes.
+	cmap notNil ifTrue:[
+	    img colorMap:cmap.
+	    img photometric:#palette
+	].
+	opaque ifFalse:[
+	    img mask:(ImageReader 
+			buildMaskFromColor:transparentColorIndex 
+			for:bytes
+			width:w
+			height:h)
+	].
+
+	imgRep instVarNamed:'pData' put:img.
+
+    ] ifFalse:[
+	self halt.
+    ].
+    ^ 1.
+
+    "Created: / 7.1.1998 / 22:31:46 / cg"
+    "Modified: / 14.1.1998 / 14:51:44 / cg"
 ! !
 
 !JavaVM class methodsFor:'semaphores & monitors'!
@@ -4149,10 +5336,10 @@
     |mon|
 
     LockTableAccess critical:[
-        mon := LockTable at:someObject ifAbsent:nil.
-        mon isNil ifTrue:[
-            LockTable at:someObject put:(mon := Monitor new)
-        ]
+	mon := LockTable at:someObject ifAbsent:nil.
+	mon isNil ifTrue:[
+	    LockTable at:someObject put:(mon := Monitor new)
+	]
     ].
     ^ mon
 
@@ -4163,14 +5350,14 @@
     |sema|
 
     WaitTableAccess critical:[
-        sema := WaitTable at:someObject ifAbsent:nil.
-        sema notNil ifTrue:[
-            WaitTable removeKey:someObject
-        ]
+	sema := WaitTable at:someObject ifAbsent:nil.
+	sema notNil ifTrue:[
+	    WaitTable removeKey:someObject
+	]
     ].
 
     sema notNil ifTrue:[
-        sema signalForAll
+	sema signalForAll
     ]
 
     "Created: / 2.1.1998 / 18:21:51 / cg"
@@ -4180,14 +5367,14 @@
     |sema|
 
     WaitTableAccess critical:[
-        sema := WaitTable at:someObject ifAbsent:nil.
-        sema notNil ifTrue:[
-            WaitTable removeKey:someObject
-        ]
+	sema := WaitTable at:someObject ifAbsent:nil.
+	sema notNil ifTrue:[
+	    WaitTable removeKey:someObject
+	]
     ].
 
     sema notNil ifTrue:[
-        sema signal
+	sema signal
     ]
 
     "Created: / 2.1.1998 / 18:20:20 / cg"
@@ -4195,7 +5382,7 @@
 
 releaseSemaphoreFor:someObject
     WaitTableAccess critical:[
-        WaitTable removeKey:someObject ifAbsent:nil
+	WaitTable removeKey:someObject ifAbsent:nil
     ]
 
     "Created: / 2.1.1998 / 18:17:14 / cg"
@@ -4206,10 +5393,10 @@
     |sema|
 
     WaitTableAccess critical:[
-        sema := WaitTable at:someObject ifAbsent:nil.
-        sema isNil ifTrue:[
-            WaitTable at:someObject put:(sema := Semaphore new)
-        ]
+	sema := WaitTable at:someObject ifAbsent:nil.
+	sema isNil ifTrue:[
+	    WaitTable at:someObject put:(sema := Semaphore new)
+	]
     ].
     ^ sema
 
@@ -4223,17 +5410,17 @@
     | mon thisProcess|
 
     someObject isNil ifTrue:[
-        self halt
+	self halt
     ].
 
     mon := self monitorFor:someObject.
 
     MonitorTrace ifTrue:[
-        ('====> entering monitor for ' , someObject displayString , ' in ' , Processor activeProcess name , ' ...') printCR.
+	('====> entering monitor for ' , someObject displayString , ' in ' , Processor activeProcess name , ' ...') printCR.
     ].
     mon enter.
     MonitorTrace ifTrue:[
-        ('====> entered it in ' , Processor activeProcess name , ' ...') printCR.
+	('====> entered it in ' , Processor activeProcess name , ' ...') printCR.
     ].
 
     self enteredMonitors add:someObject.
@@ -4246,17 +5433,17 @@
     | mon thisProcess|
 
     someObject isNil ifTrue:[
-        self halt
+	self halt
     ].
 
     mon := self monitorFor:someObject.
 
     MonitorTrace ifTrue:[
-        ('====> leaving monitor for ' , someObject displayString , ' in ' , Processor activeProcess name , ' ...') printCR.
+	('====> leaving monitor for ' , someObject displayString , ' in ' , Processor activeProcess name , ' ...') printCR.
     ].
     mon exit.
     MonitorTrace ifTrue:[
-        ('====> left it in ' , Processor activeProcess name , ' ...') printCR.
+	('====> left it in ' , Processor activeProcess name , ' ...') printCR.
     ].
 
 "/    enteredMonitorHandles isNil ifTrue:[
@@ -4264,7 +5451,7 @@
 "/    ].
 
     self enteredMonitors removeLast ~~ someObject ifTrue:[
-        self halt:'oops - monitor enter/exit nesting wrong'
+	self halt:'oops - monitor enter/exit nesting wrong'
     ].
 
     "Created: / 2.1.1998 / 23:47:28 / cg"
@@ -4277,7 +5464,8 @@
     "given an ST/X event, create corresponding AWT event(s) for it"
 
     |jEv jEv1 jEv2
-     modifiers key keyChar untranslatedKey id type x y w h 
+     modifiers key keyChar untranslatedKey id 
+     type x y w h view menu
      eventArgs clickCount jRect
      jKeyEventClass jInputEventClass jMouseEventClass
      jWindowEventClass jPaintEventClass jComponentEventClass|
@@ -4383,7 +5571,7 @@
         ] ifFalse:[
             id := jKeyEventClass instVarNamed:'KEY_RELEASED'
         ].
-        jEv := jKeyEventClass basicNew.
+        jEv := jKeyEventClass newCleared "basicNew".
         jEv instVarNamed:'modifiers' put:modifiers.
         jEv instVarNamed:'keyCode'   put:key.
         jEv instVarNamed:'keyChar'   put:keyChar.
@@ -4429,7 +5617,7 @@
                 ]
             ]
         ].
-        jEv := jMouseEventClass basicNew.
+        jEv := jMouseEventClass newCleared "basicNew".
         jEv instVarNamed:'modifiers' put:modifiers.
         jEv instVarNamed:'id'        put:id.
         jEv instVarNamed:'x'         put:x.
@@ -4444,8 +5632,8 @@
     or:[(type == #damage)]]) ifTrue:[
         jPaintEventClass := Java classForName:'java.awt.event.PaintEvent'.
         jWindowEventClass := Java classForName:'java.awt.event.WindowEvent'.
-        id := (jPaintEventClass instVarNamed:'PAINT').
-"/        id := (jPaintEventClass instVarNamed:'UPDATE').
+"/        id := (jPaintEventClass instVarNamed:'PAINT').
+        id := (jPaintEventClass instVarNamed:'UPDATE').
 
         ((type == #'exposeX:y:width:height:') 
         or:[(type == #'graphicExposeX:y:width:height:')]) ifTrue:[
@@ -4465,60 +5653,84 @@
         jRect instVarNamed:'width' put:w.
         jRect instVarNamed:'height' put:h.
 
-        jEv := jPaintEventClass basicNew.
+        jEv := jPaintEventClass newCleared "basicNew".
         jEv instVarNamed:'id'        put:id.
         jEv instVarNamed:'updateRect' put:jRect.
 
 "/        jEv instVarNamed:'g'         put:jWin.
+
         ^ Array with:jEv.
     ].
 
     (type == #'configureX:y:width:height:') ifTrue:[
+"/        x := eventArgs at:1.
+"/        y := eventArgs at:2.
+
+        view := anEvent view.
+        w := eventArgs at:3.
+        h := eventArgs at:4.
+
+        "/
+        "/ must change the components extent
+        "/ is there no cleaner way to do this ?
+        "/
+        view isTopView ifTrue:[
+            "/
+            "/ sigh - don't include the menu.
+            "/
+            menu := self topViewsMenu:view.
+            menu notNil ifTrue:[
+                "/ must add the menus height
+                h := h - menu height
+            ]
+        ].
+        jWin instVarNamed:'width' put:w.
+        jWin instVarNamed:'height' put:h.
+
         jComponentEventClass := Java classForName:'java.awt.event.ComponentEvent'.
         id := (jComponentEventClass instVarNamed:'COMPONENT_MOVED').
-"/        x := eventArgs at:1.
-"/        y := eventArgs at:2.
-        jEv1 := jComponentEventClass basicNew.
+        jEv1 := jComponentEventClass newCleared "basicNew".
         jEv1 instVarNamed:'id'        put:id.
 
         id := (jComponentEventClass instVarNamed:'COMPONENT_RESIZED').
-        jEv2 := jComponentEventClass basicNew.
+        jEv2 := jComponentEventClass newCleared "basicNew".
         jEv2 instVarNamed:'id'        put:id.
+
         ^ Array with:jEv1 with:jEv2.
     ].
     (type == #'focusIn') ifTrue:[
-'shown' printCR.
+'focusIn' printCR.
         jComponentEventClass := Java classForName:'java.awt.event.FocusEvent'.
         id := (jComponentEventClass instVarNamed:'FOCUS_GAINED').
-        jEv := jComponentEventClass basicNew.
+        jEv := jComponentEventClass newCleared "basicNew".
         jEv instVarNamed:'id'        put:id.
         ^ Array with:jEv.
     ].
     (type == #'focusOut') ifTrue:[
-'shown' printCR.
+'focusOut' printCR.
         jComponentEventClass := Java classForName:'java.awt.event.FocusEvent'.
         id := (jComponentEventClass instVarNamed:'FOCUS_LOST').
-        jEv := jComponentEventClass basicNew.
+        jEv := jComponentEventClass newCleared "basicNew".
         jEv instVarNamed:'id'        put:id.
         ^ Array with:jEv.
     ].
     (type == #'mapped') ifTrue:[
-'shown' printCR.
+'mapped' printCR.
         jComponentEventClass := Java classForName:'java.awt.event.ComponentEvent'.
         id := (jComponentEventClass instVarNamed:'COMPONENT_SHOWN').
 "/        x := eventArgs at:1.
 "/        y := eventArgs at:2.
-        jEv := jComponentEventClass basicNew.
+        jEv := jComponentEventClass newCleared "basicNew".
         jEv instVarNamed:'id'        put:id.
         ^ Array with:jEv.
     ].
     (type == #'unmapped') ifTrue:[
-'hidden' printCR.
+'unmapped' printCR.
         jComponentEventClass := Java classForName:'java.awt.event.ComponentEvent'.
         id := (jComponentEventClass instVarNamed:'COMPONENT_HIDDEN').
 "/        x := eventArgs at:1.
 "/        y := eventArgs at:2.
-        jEv := jComponentEventClass basicNew.
+        jEv := jComponentEventClass newCleared "basicNew".
         jEv instVarNamed:'id'        put:id.
         ^ Array with:jEv.
     ].
@@ -4526,7 +5738,7 @@
     (type == #terminate) ifTrue:[
         jWindowEventClass := Java classForName:'java.awt.event.WindowEvent'.
         id := (jWindowEventClass instVarNamed:'WINDOW_CLOSED').
-        jEv := jWindowEventClass basicNew.
+        jEv := jWindowEventClass newCleared "basicNew".
         jEv instVarNamed:'id'        put:id.
         ^ Array with:jEv.
     ].
@@ -4534,7 +5746,7 @@
     ^ nil.
 
     "Created: / 6.1.1998 / 20:38:58 / cg"
-    "Modified: / 11.1.1998 / 12:11:07 / cg"
+    "Modified: / 16.1.1998 / 14:25:02 / cg"
 !
 
 doWindowsEventThread
@@ -4544,45 +5756,45 @@
     |sensor event|
 
     JavaWindowGroup isNil ifTrue:[
-        "/ '*** eventThread: no windowGroup ...' printCR.
-        Delay waitForSeconds:0.1.
-        ^ self
+	"/ '*** eventThread: no windowGroup ...' printCR.
+	Delay waitForSeconds:0.1.
+	^ self
     ].
 
     KnownWindows isNil ifTrue:[
-        "/ '*** eventThread: no views ...' printCR.
-        Delay waitForSeconds:0.1.
-        ^ self
+	"/ '*** eventThread: no views ...' printCR.
+	Delay waitForSeconds:0.1.
+	^ self
     ].
 
     "/ wait for an event to arrive ...
 
     sensor := JavaWindowGroup sensor.
     (sensor hasEvents or:[sensor hasDamage]) ifFalse:[
-        EventTrace ifTrue:[
-            '*** eventThread waiting ...' printCR.
-        ].
-        Processor activeProcess state:#eventWait.
-        sensor eventSemaphore wait.
-        ^ self.
+	EventTrace ifTrue:[
+	    '*** eventThread waiting ...' printCR.
+	].
+	Processor activeProcess state:#eventWait.
+	sensor eventSemaphore wait.
+	^ self.
     ].
 
     EventTrace ifTrue:[
-        '*** eventThread event arrived ...' printCR.
+	'*** eventThread event arrived ...' printCR.
     ].
 
     "/ EventTrace := true
     sensor hasDamage ifTrue:[
-        EventTrace ifTrue:[
-            '*** eventThread: damage arrived ...' printCR.
-        ].
-        event := sensor nextDamage.
+	EventTrace ifTrue:[
+	    '*** eventThread: damage arrived ...' printCR.
+	].
+	event := sensor nextDamage.
     ] ifFalse:[
-        event := sensor nextEvent.
+	event := sensor nextEvent.
     ].
     event isNil ifTrue:[
-        '*** eventThread: nil event ignored' printCR.
-        ^ self
+	'*** eventThread: nil event ignored' printCR.
+	^ self
     ].
 
     self processEvent:event
@@ -4592,35 +5804,92 @@
 !
 
 processEvent:event
-    |evQ jEvents jWToolKit jWinPeer jWin v|
+    |evQ jEvents jWToolKit jWinPeer jWin v eventConsumed|
 
     KnownWindows isNil ifTrue:[
         ^ self
     ].
 
     v := event view.
-    jWinPeer := KnownWindows keyAtValue:v.
+    jWinPeer := self jPeerForView:v.
     jWinPeer isNil ifTrue:[
-        EventTrace ifTrue:[
-            ('*** eventThread: ' , event type , '-event for unknown java-view - passed to view.') printCR.
-        ].
-        event sendEventWithFocusOn:nil.
-        ^ self
-    ].
-
-    "/ most views handle their events themself (being ST/X views) ...
-
-    v class ~~ JavaView ifTrue:[
-        v class ~~ StandardSystemView ifTrue:[
+        (v isKindOf:JavaView) ifTrue:[
+            "/ mhmh - an event for a JavaView,
+            "/ which has no peer (anyMore ?)
+            "/ should not happen.
+        ] ifFalse:[
+            "/ mhmh - an event for a subcomponent of an ST widget.
+            "/ let it be handled normally.
             EventTrace ifTrue:[
-                    ('*** eventThread: event handled by view itself (' , v class name , ')') printCR.
+                ('*** eventThread: ' , event type , '-event for unknown java-view - passed to view.') printCR.
             ].
             event sendEventWithFocusOn:nil.
-            ^ self.
         ].
-        "/ send to view, but also handle in JAVA
+        ^ self
+    ].
+
+    "/ change:
+    "/ in the previous version, events for ST/X widgets (i.e. buttons etc)
+    "/ where not passed to java, but instead forwarded directly to the widget
+    "/ by the code below.
+    "/ This has changed, to pass it to Java, which eventually passes it to the
+    "/ peer via the handleEvent native method (unless the event got consumed).
+    "/ This is req'd to let java keep track of keyboard/mouse input for widgets.
+
+false ifTrue:[
+"/    "/ most views handle their events themself (being ST/X views) ...
+"/
+"/    v class ~~ JavaView ifTrue:[
+"/"/        v class ~~ StandardSystemView ifTrue:[
+"/"/            EventTrace ifTrue:[
+"/"/                    ('*** eventThread: event handled by view itself (' , v class name , ')') printCR.
+"/"/            ].
+"/"/            event sendEventWithFocusOn:nil.
+"/"/            ^ self.
+"/"/        ].
+"/        (event type == #'exposeX:y:width:height'
+"/        or:[event type == #'graphicsExposeX:y:width:height']) ifTrue:[
+"/            "/ send to view, but also handle in JAVA
+"/            event sendEventWithFocusOn:nil.
+"/        ]
+"/    ].
+
+    (#(
+        #'mapped'
+        #'unmapped'
+        #'configureX:y:width:height:'
+        #'exposeX:y:width:height:'
+        #'graphicsExposeX:y:width:height:'
+     ) includes:event type) ifTrue:[
         event sendEventWithFocusOn:nil.
     ].
+].
+
+    "/ what a kludge - some events are passed back to
+    "/ ST via the WComponent-handleEvent native method.
+    "/ However, repaints are not.
+    "/ In order to let ST widgets do the drawing,
+    "/ selectively filter exposeEvents from Java ...
+
+    eventConsumed := false.
+    v class == JavaView ifTrue:[
+        "/ all events handled by Java ...
+    ] ifFalse:[
+        eventConsumed := true.
+
+        "/ let widget handle it.
+        event sendEventWithFocusOn:nil.
+
+        "/ some are not passed to Java ...
+        event isDamage ifTrue:[
+            (v isKindOf:TextView) ifTrue:[
+                ^ self
+            ].
+            (v isKindOf:Label) ifTrue:[
+                ^ self
+            ].
+        ].
+    ].
 
     jWin := jWinPeer instVarNamed:'target'.
 
@@ -4650,6 +5919,11 @@
     jEvents do:[:jEv |
         jEv instVarNamed:'source'   put:jWin.
         jEv instVarNamed:'consumed' put:0.
+        eventConsumed ifFalse:[
+            "/ the first gets the original event as data
+            jEv instVarNamed:'data' put:event.
+            eventConsumed := true
+        ].
 
         "/ post it (them) to the event queue
 
@@ -4659,12 +5933,12 @@
     ].
 
     "Created: / 6.1.1998 / 20:36:36 / cg"
-    "Modified: / 9.1.1998 / 10:39:01 / cg"
+    "Modified: / 16.1.1998 / 14:56:51 / cg"
 ! !
 
 !JavaVM class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaVM.st,v 1.2 1998/01/12 14:24:40 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaVM.st,v 1.3 1998/01/16 16:12:41 cg Exp $'
 ! !
 JavaVM initialize!
--- a/JavaView.st	Mon Jan 12 23:18:07 1998 +0000
+++ b/JavaView.st	Fri Jan 16 16:12:55 1998 +0000
@@ -1,4 +1,4 @@
-'From Smalltalk/X, Version:3.3.1 on 8-jan-1998 at 9:38:55 pm'                   !
+'From Smalltalk/X, Version:3.3.1 on 14-jan-1998 at 12:04:12 am'                 !
 
 View subclass:#JavaView
 	instanceVariableNames:'eventReceiver updateRegions javaPeer'
@@ -158,16 +158,19 @@
 
 initialize
     super initialize.
+
+    self enableMotionEvents.
     (superView notNil and:[superView isMemberOf:JavaEmbeddedFrameView])
     ifTrue:[
         self viewBackground:superView viewBackground
     ]
 
-    "Created: 21.8.1997 / 16:37:45 / cg"
+    "Created: / 21.8.1997 / 16:37:45 / cg"
+    "Modified: / 13.1.1998 / 14:29:30 / cg"
 ! !
 
 !JavaView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaView.st,v 1.7 1998/01/12 14:24:46 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaView.st,v 1.8 1998/01/16 16:12:55 cg Exp $'
 ! !