new javaVM stuff & back to pre-stefans changes
authorcg
Mon, 05 Jan 1998 18:49:32 +0000
changeset 252 04b330744577
parent 251 4898461c0cca
child 253 de483f561c9e
new javaVM stuff & back to pre-stefans changes
Java.st
JavaClass.st
JavaClassReader.st
JavaConstantPool.st
JavaContext.st
JavaDecompiler.st
JavaFieldref.st
JavaMethod.st
JavaMethodref.st
JavaObject.st
JavaUnresolvedClassConstant.st
--- a/Java.st	Fri Aug 29 16:03:19 1997 +0000
+++ b/Java.st	Mon Jan 05 18:49:32 1998 +0000
@@ -1,4 +1,4 @@
-'From Smalltalk/X, Version:3.1.9 on 26-aug-1997 at 8:10:05 pm'                  !
+'From Smalltalk/X, Version:3.3.1 on 4-jan-1998 at 7:12:23 pm'                   !
 
 Object subclass:#Java
 	instanceVariableNames:''
@@ -157,17 +157,17 @@
 
      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: 3.8.1997 / 19:42:15 / cg"
+    "Modified: / 4.1.1998 / 14:41:12 / cg"
 !
 
 initAllStaticFields
@@ -240,6 +240,12 @@
 reinitAllClasses
      self markAllClassesUninitialized.
      self initAllClasses
+
+     "
+      Java reinitAllClasses
+     "
+
+    "Modified: / 4.1.1998 / 00:34:29 / cg"
 !
 
 reinitialize
@@ -512,7 +518,7 @@
 
     nm := aJavaName.
     (nm includes:$.) ifTrue:[
-	nm := (nm asString copy replaceAll:$. by:$/).
+	nm := (nm asString copy replaceAll:$. with:$/).
 	sym := nm asSymbolIfInterned.
 	sym notNil ifTrue:[
 	    cls := Classes at:sym ifAbsent:nil.
@@ -656,7 +662,7 @@
 	    "/
 	    "/ try pckg/.../name
 	    "/
-	    nm := (nm asString copy replaceAll:$. by:$/).
+	    nm := (nm asString copy replaceAll:$. with:$/).
 	    sym := nm asSymbolIfInterned.
 	    sym notNil ifTrue:[
 		cls := Classes at:sym ifAbsent:nil.
@@ -837,34 +843,34 @@
     |p argStringArray t|
 
     argString isEmpty ifTrue:[
-	argStringArray := #()
+        argStringArray := #()
     ] ifFalse:[
-	argStringArray := argString asCollectionOfWords asArray 
-				collect:[:s | Java as_String:s].
+        argStringArray := argString asCollectionOfWords asArray 
+                                collect:[:s | Java as_String:s].
     ].
 
     (Java at:'java.lang.System') instVarNamed:'security' put:nil.
 
     p := JavaProcess 
-	    for:[
-
-		    aJavaClass 
-			invoke:#'main'
-			signature:#'([Ljava/lang/String;)V'
-			with:argStringArray
-		]
-	    priority:(Processor activePriority - 1).
+            for:[
+                    Java initSystemClass.
+                    aJavaClass 
+                        invoke:#'main'
+                        signature:#'([Ljava/lang/String;)V'
+                        with:argStringArray
+                ]
+            priority:(Processor activePriority - 1).
 
     p name:(aJavaClass fullName , '::main()').
     ^ p
 
-    "Modified: 7.8.1997 / 21:16:15 / cg"
-    "Created: 15.8.1997 / 04:41:20 / cg"
+    "Created: / 15.8.1997 / 04:41:20 / cg"
+    "Modified: / 4.1.1998 / 16:33:49 / cg"
 ! !
 
 !Java class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/Java.st,v 1.45 1997/08/28 02:33:53 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/Java.st,v 1.46 1998/01/05 18:47:02 cg Exp $'
 ! !
 Java initialize!
--- a/JavaClass.st	Fri Aug 29 16:03:19 1997 +0000
+++ b/JavaClass.st	Mon Jan 05 18:49:32 1998 +0000
@@ -1,8 +1,10 @@
+'From Smalltalk/X, Version:3.3.1 on 4-jan-1998 at 7:11:51 pm'                   !
+
 Class subclass:#JavaClass
-	instanceVariableNames:'fullName accessFlags constantPool sourceFile binaryFilePath
-		fields initialized initValues staticFields hasUnresolvedConstants
-		interfaces'
-	classVariableNames:'InitialValuePerType'
+	instanceVariableNames:'constantPool interfaces accessFlags fullName sourceFile
+		binaryFilePath fields initValues staticFields'
+	classVariableNames:'InitialValuePerType A_OBSOLETE A_INTERFACE A_PUBLIC A_FINAL
+		A_ABSTRACT A_INITIALIZED'
 	poolDictionaries:''
 	category:'Java-Classes'
 !
@@ -19,11 +21,21 @@
 !JavaClass class methodsFor:'initialization'!
 
 initialize
+    "/ those are defined in Java and read from the classFile
+    A_PUBLIC      := 16r000001.
+    A_FINAL       := 16r000010.
+    A_INTERFACE   := 16r000200.
+    A_ABSTRACT    := 16r000400.
+    A_OBSOLETE    := 16r008000.
+
+    "/ those are local to the ST/X implementation
+    A_INITIALIZED := 16r100000.
+
     InitialValuePerType := IdentityDictionary new.
     InitialValuePerType at:$B put:0.
     InitialValuePerType at:$C put:0.
     InitialValuePerType at:$D put:0.0.
-    InitialValuePerType at:$F put:0.0 asShortFloat.
+    InitialValuePerType at:$F put:(0.0 asShortFloat).
     InitialValuePerType at:$I put:0.
     InitialValuePerType at:$J put:0.
     InitialValuePerType at:$S put:0.
@@ -59,6 +71,8 @@
     meta instSize:(JavaClass instSize + nStatic).
 "/    meta setName:(aString , 'class') asSymbol.
 "/    meta setClassVariableString:''.
+    meta flags:(meta flags bitOr:Behavior flagJavaClass).
+"/    meta setSuperclass:JavaObject class.
 
     "then let the new meta create the class"
     cls := meta new.
@@ -102,9 +116,8 @@
 
     ^ cls
 
-    "Created: 15.4.1996 / 15:52:55 / cg"
-    "Modified: 3.8.1997 / 17:01:15 / cg"
-    "Modified: 29.8.1997 / 17:02:56 / stefan"
+    "Created: / 15.4.1996 / 15:52:55 / cg"
+    "Modified: / 3.1.1998 / 22:32:25 / cg"
 !
 
 name:aString
@@ -122,37 +135,37 @@
 
     sel := selector.
     (sel includes:$:) ifTrue:[
-        sel := sel copyTo:(sel indexOf:$:)-1    
+	sel := sel copyTo:(sel indexOf:$:)-1    
     ].
 
     sel := sel asSymbolIfInterned.
     sel notNil ifTrue:[
-        cls := aClass.
+	cls := aClass.
 
-        [cls notNil 
-        and:[cls ~~ JavaObject
-        and:[cls ~~ JavaClass]]] whileTrue:[
-            cls methodDictionary keysAndValuesDo:[:jSel :aMethod |
-                ((jSel == sel)
-                or:[aMethod name = sel 
-                or:[aMethod signatureNameWithoutReturnType = sel]])
-                ifTrue:[
-                    aMethod numArgs == nargs ifTrue:[
-                        staticMethod ifTrue:[
-                            aMethod isStatic ifTrue:[
-                                ^ aMethod
-                            ]
-                        ] ifFalse:[
-                            aMethod isStatic ifFalse:[
-                                ^ aMethod
-                            ]
-                        ]
-                    ]
-                ]
-            ].
+	[cls notNil 
+	and:[cls ~~ JavaObject
+	and:[cls ~~ JavaClass]]] whileTrue:[
+	    cls methodDictionary keysAndValuesDo:[:jSel :aMethod |
+		((jSel == sel)
+		or:[aMethod name = sel 
+		or:[aMethod signatureNameWithoutReturnType = sel]])
+		ifTrue:[
+		    aMethod numArgs == nargs ifTrue:[
+			staticMethod ifTrue:[
+			    aMethod isStatic ifTrue:[
+				^ aMethod
+			    ]
+			] ifFalse:[
+			    aMethod isStatic ifFalse:[
+				^ aMethod
+			    ]
+			]
+		    ]
+		]
+	    ].
 
-            cls := cls superclass.
-        ].
+	    cls := cls superclass.
+	].
     ].
 self halt.
     ^ nil
@@ -220,9 +233,10 @@
 
     nameComponents := fullName asCollectionOfSubstringsSeparatedBy:$/.
     nameComponents size <= 1 ifTrue:[
-        ^ 'java' "/ fullName  
+	^ 'java' "/ fullName  
     ].
-    ^ ((nameComponents asStringWith:$/ from:1 to:(nameComponents size - 1))) replaceAll:$/ by:$.
+    ^ ((nameComponents asStringWith:$/ from:1 to:(nameComponents size - 1))) 
+	replaceAll:$/ with:$.
 
     "Modified: 30.7.1997 / 15:35:22 / cg"
 !
@@ -231,11 +245,11 @@
     "lookup the classes methodDictionary"
 
     methodDictionary keysAndValuesDo:[:mFullSelector :aMethod |
-        aMethod name == name ifTrue:[
-            aMethod signature == sig ifTrue:[
-                ^ aMethod
-            ]
-        ]
+	aMethod name == name ifTrue:[
+	    aMethod signature == sig ifTrue:[
+		^ aMethod
+	    ]
+	]
     ].
     ^ nil
 
@@ -425,18 +439,29 @@
 
     |m|
 
-    initialized := true.
+    (accessFlags bitAnd:A_INITIALIZED) ~~ 0 ifTrue:[^ self].
+
+    accessFlags := accessFlags bitOr:A_INITIALIZED.
+
+    superclass ~~ JavaObject ifTrue:[
+        superclass classInit
+    ].
+"/    "/ also, all referenced classes must be ...
+"/    constantPool classReferencesDo:[:aClass |
+"/        aClass classInit
+"/    ].
 
     m := self compiledMethodAt:#'<clinit>()V'.
     m notNil ifTrue:[
 "/        'calling clinit() of ' print. self fullName printNL.
         [
-            self 
-                invokeJavaMethod:m 
-                sender:thisContext
-                selector:#'<clinit>()V'.
+            m valueWithReceiver:self arguments:#()
+"/            self 
+"/                invokeJavaMethod:m 
+"/                sender:thisContext
+"/                selector:#'<clinit>()V'.
         ] valueOnUnwindDo:[
-            initialized := false
+            accessFlags := accessFlags bitXor:A_INITIALIZED.
         ]
     ] ifFalse:[
 "/        self fullName print. ' has no clinit()' printNL.
@@ -453,14 +478,14 @@
      (Java classNamed:'java.util.Properties') classInit 
     "
 
-    "Modified: 30.7.1997 / 13:28:38 / cg"
+    "Modified: / 4.1.1998 / 16:10:43 / cg"
 !
 
 initializeIfNotYetDone
     "if not yet done, call the classes JAVA clinit function"
 
-    initialized ~~ true ifTrue:[
-        self classInit
+    (accessFlags bitAnd:A_INITIALIZED) ~~ 0 ifTrue:[
+	self classInit
     ]
 
     "Created: 1.8.1997 / 22:37:40 / cg"
@@ -521,7 +546,8 @@
     |newJavaObject|
 
     newJavaObject := self newCleared.
-    newJavaObject invoke:#'<init>()V'.
+    newJavaObject perform:#'<init>()V'.
+"/    newJavaObject invoke:#'<init>()V'.
     ^ newJavaObject
 
     "
@@ -529,7 +555,7 @@
      (Java classNamed:'java.lang.String') new inspect
     "
 
-    "Modified: 30.7.1997 / 17:40:25 / cg"
+    "Modified: / 4.1.1998 / 18:04:25 / cg"
 !
 
 newCleared
@@ -573,77 +599,6 @@
     "Created: 18.3.1997 / 17:33:07 / cg"
 ! !
 
-!JavaClass ignoredMethodsFor:'message sending'!
-
-invokeJava:selector
-    "send javaSelector (name+sig) message, without arguments
-     as a static call to the class"
-
-    ^ self
-	invokeJava:selector sender:thisContext sender
-
-    "Modified: 7.4.1997 / 22:52:30 / cg"
-!
-
-invokeJava:selector sender:aContext
-    "send javaSelector (name+sig) message, without arguments
-     as a static call to the class"
-
-    |method|
-
-    method := self lookupMethodFor:selector.
-    method notNil ifTrue:[
-        ^ self 
-            invokeJavaMethod:method 
-            sender:aContext
-            selector:selector
-    ].
-
-    ^ self doesNotUnderstand:(Message selector:selector)
-
-    "Created: 7.4.1997 / 22:52:10 / cg"
-    "Modified: 30.7.1997 / 13:29:09 / cg"
-!
-
-invokeJava:selector with:arg
-    "send javaSelector (name+sig) message, with 1 argument
-     as a static call to the class"
-
-    |method|
-
-    method := self lookupMethodFor:selector.
-    method notNil ifTrue:[
-        ^ self 
-                invokeJavaMethod:method 
-                sender:thisContext
-                selector:selector
-                with:arg 
-    ].
-    ^ self doesNotUnderstand:(Message selector:selector)
-
-    "Modified: 30.7.1997 / 13:37:58 / cg"
-!
-
-invokeJava:selector with:arg sender:aContext
-    "send javaSelector (name+sig) message, with 1 argument
-     as a static call to the class"
-
-    |method|
-
-    method := self lookupMethodFor:selector.
-    method notNil ifTrue:[
-        ^ self 
-            invokeJavaMethod:method 
-            sender:aContext
-            selector:selector
-            with:arg 
-    ].
-    ^ self doesNotUnderstand:(Message selector:selector)
-
-    "Created: 7.4.1997 / 22:52:51 / cg"
-    "Modified: 30.7.1997 / 13:39:45 / cg"
-! !
-
 !JavaClass methodsFor:'message sending'!
 
 invokeJavaMethod:aJavaMethod interpreter:i sender:aContext selector:sel
@@ -652,10 +607,10 @@
     |val|
 
     aJavaMethod numArgs ~~ 0 ifTrue:[
-        self halt:'argument count'
+	self halt:'argument count'
     ].
     aJavaMethod isStatic ifFalse:[
-        self halt:'non-static function'
+	self halt:'non-static function'
     ].
 
     val := i interpret:aJavaMethod sender:aContext.
@@ -672,10 +627,10 @@
     |val|
 
     aJavaMethod numArgs ~~ 1 ifTrue:[
-        self halt:'argument count'
+	self halt:'argument count'
     ].
     aJavaMethod isStatic ifFalse:[
-        self halt:'non-static function'
+	self halt:'non-static function'
     ].
 
     i push:arg1.
@@ -691,10 +646,10 @@
     "invoke a static java method, without arguments"
 
     ^ self
-        invokeJavaMethod:aJavaMethod
-        interpreter:(JavaInterpreter new)
-        sender:aContext 
-        selector:sel
+	invokeJavaMethod:aJavaMethod
+	interpreter:(JavaInterpreter new)
+	sender:aContext 
+	selector:sel
 
     "Modified: 17.8.1997 / 18:05:35 / cg"
 !
@@ -703,11 +658,11 @@
     "invoke a static java method, with 1 argument"
 
     ^ self
-        invokeJavaMethod:aJavaMethod
-        interpreter:(JavaInterpreter new)
-        sender:aContext 
-        selector:sel 
-        with:arg1
+	invokeJavaMethod:aJavaMethod
+	interpreter:(JavaInterpreter new)
+	sender:aContext 
+	selector:sel 
+	with:arg1
 
     "Modified: 17.8.1997 / 18:04:44 / cg"
 !
@@ -719,23 +674,24 @@
 
     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:[
-                        ^ self 
-                            invokeJavaMethod:aMethod 
-                            sender:thisContext
-                            selector:selector
-                    ]
-                ]
-            ].
-            cls := cls superclass.
-        ].
+		aMethod isStatic ifTrue:[
+		    sel == selector ifTrue:[
+			^ aMethod valueWithReceiver:self arguments:#()
+"/                        ^ self 
+"/                            invokeJavaMethod:aMethod 
+"/                            sender:thisContext
+"/                            selector:selector
+		    ]
+		]
+	    ].
+	    cls := cls superclass.
+	].
     ].
 
     ^ self doesNotUnderstand:(Message selector:selector)
@@ -785,7 +741,7 @@
 !JavaClass methodsFor:'printing & storing'!
 
 displayString
-    ^ (fullName copyFrom:1) replaceAll:$/ by:$.
+    ^ (fullName copyFrom:1) replaceAll:$/ with:$.
 
 "/    ^ 'JAVA-' , name .
 "/    ^ name , '(Java)'  "/ 'JavaClass(' , name , ')'
@@ -834,13 +790,15 @@
 !
 
 makeObsolete
-    accessFlags := accessFlags bitOr:16r8000
+    accessFlags := accessFlags bitOr:A_OBSOLETE
 
     "Created: 7.8.1997 / 19:04:48 / cg"
 !
 
 markUninitialized
-    initialized := false.
+    (accessFlags bitAnd:A_INITIALIZED) ~~ 0 ifTrue:[
+	accessFlags := accessFlags bitXor:A_INITIALIZED
+    ].
 !
 
 setAccessFlags:flags
@@ -855,7 +813,6 @@
 
 setConstantPool:anArray
     constantPool := anArray.
-    hasUnresolvedConstants := true
 
     "Created: 15.4.1996 / 16:42:52 / cg"
 !
@@ -916,21 +873,21 @@
     |iVars numIvars|
 
     aClass isNil ifTrue:[
-        super setSuperclass:JavaObject
+	super setSuperclass:JavaObject
     ] ifFalse:[
-        (aClass isMemberOf:JavaUnresolvedClassConstant) ifTrue:[
-            self halt.
-        ].
-        super setSuperclass:aClass.
+	(aClass isMemberOf:JavaUnresolvedClassConstant) ifTrue:[
+	    self halt.
+	].
+	super setSuperclass:aClass.
     ].
 
     iVars := self instVarNames.
     ((numIvars := iVars size) > 0) ifTrue:[
-        (superclass notNil and:[(superclass isMemberOf:JavaUnresolvedClassConstant) not]) ifTrue:[
-            instSize := superclass instSize + numIvars
-        ] ifFalse:[
-            instSize := numIvars
-        ]
+	(superclass notNil and:[(superclass isMemberOf:JavaUnresolvedClassConstant) not]) ifTrue:[
+	    instSize := superclass instSize + numIvars
+	] ifFalse:[
+	    instSize := numIvars
+	]
     ].
 
     "Created: 15.4.1996 / 16:42:52 / cg"
@@ -944,10 +901,6 @@
      this can be redefined in special classes, to get different browsers"
 
     ^ JavaBrowser
-
-
-
-
 !
 
 hasInterface:aJavaInterface
@@ -970,7 +923,7 @@
 !
 
 isAbstract
-    ^ (accessFlags bitAnd:16r0400) ~~ 0
+    ^ (accessFlags bitAnd:A_ABSTRACT) ~~ 0
 !
 
 isClass
@@ -978,15 +931,15 @@
 !
 
 isFinal
-    ^ (accessFlags bitAnd:16r0010) ~~ 0
+    ^ (accessFlags bitAnd:A_FINAL) ~~ 0
 !
 
 isInitialized
-    ^ initialized == true
+    ^ (accessFlags bitAnd:A_INITIALIZED) ~~ 0
 !
 
 isInterface
-    ^ (accessFlags bitAnd:16r0200) ~~ 0
+    ^ (accessFlags bitAnd:A_INTERFACE) ~~ 0
 !
 
 isJavaClass
@@ -999,14 +952,13 @@
     "return true, if the receiver is obsolete 
      Java classes are never."
 
-    ^ (accessFlags bitAnd:16r8000) ~~ 0.
-    ^ false
+    ^ (accessFlags bitAnd:A_OBSOLETE) ~~ 0.
 
     "Modified: 7.8.1997 / 19:04:28 / cg"
 !
 
 isPublic
-    ^ (accessFlags bitAnd:16r0001) ~~ 0
+    ^ (accessFlags bitAnd:A_PUBLIC) ~~ 0
 !
 
 isUnresolved
@@ -1017,12 +969,6 @@
     ^ self == JavaClass
 
     "Created: 30.7.1997 / 14:58:58 / cg"
-!
-
-useSpecialSuper
-    ^ (accessFlags bitAnd:16r0020) ~~ 0
-
-    "Created: 28.8.1997 / 11:13:27 / stefan"
 ! !
 
 !JavaClass methodsFor:'smalltalk interface'!
@@ -1034,24 +980,24 @@
 
     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 name == selector 
-                or:[aMethod signatureNameWithoutReturnType = selector]) ifTrue:[
-                    aMethod numArgs == 0 ifTrue:[
-                        ^ self 
-                            invokeJavaMethod:aMethod 
-                            sender:thisContext
-                            selector:selector
-                    ]
-                ]
-            ].
-            cls := cls superclass.
-        ].
+		(aMethod name == selector 
+		or:[aMethod signatureNameWithoutReturnType = selector]) ifTrue:[
+		    aMethod numArgs == 0 ifTrue:[
+			^ self 
+			    invokeJavaMethod:aMethod 
+			    sender:thisContext
+			    selector:selector
+		    ]
+		]
+	    ].
+	    cls := cls superclass.
+	].
     ].
 
     ^ self doesNotUnderstand:(Message selector:selector)
@@ -1086,11 +1032,11 @@
 
     method := JavaClass lookupMethod:selector numArgs:0 in:self static:true.
     method notNil ifTrue:[
-        ^ self 
-            invokeJavaMethod:method 
-            interpreter:i 
-            sender:aContext
-            selector:selector
+	^ self 
+	    invokeJavaMethod:method 
+	    interpreter:i 
+	    sender:aContext
+	    selector:selector
     ].
 
     ^ super doesNotUnderstand:(Message selector:selector)
@@ -1106,12 +1052,12 @@
 
     method := JavaClass lookupMethod:selector numArgs:1 in:self static:true.
     method notNil ifTrue:[
-        ^ self 
-            invokeJavaMethod:method 
-            interpreter:i 
-            sender:aContext
-            selector:selector
-            with:arg
+	^ self 
+	    invokeJavaMethod:method 
+	    interpreter:i 
+	    sender:aContext
+	    selector:selector
+	    with:arg
     ].
 
     ^ super doesNotUnderstand:(Message selector:selector)
@@ -1127,20 +1073,20 @@
 
     sel := selector asSymbolIfInterned.
     sel notNil ifTrue:[
-        sig := signature asSymbolIfInterned.
-        sig notNil ifTrue:[
-            cls := self.
-            [cls notNil and:[cls ~~ JavaObject]] whileTrue:[
-                method := cls compiledMethodAt:sel signature:signature.
-                method notNil ifTrue:[
-                    ^ self 
-                        invokeJavaMethod:method 
-                        sender:thisContext
-                        selector:sel
-                ].
-                cls := cls superclass.
-            ].
-        ].
+	sig := signature asSymbolIfInterned.
+	sig notNil ifTrue:[
+	    cls := self.
+	    [cls notNil and:[cls ~~ JavaObject]] whileTrue:[
+		method := cls compiledMethodAt:sel signature:signature.
+		method notNil ifTrue:[
+		    ^ self 
+			invokeJavaMethod:method 
+			sender:thisContext
+			selector:sel
+		].
+		cls := cls superclass.
+	    ].
+	].
     ].
 
     ^ self doesNotUnderstand:(Message selector:selector)
@@ -1181,11 +1127,14 @@
             [cls notNil and:[cls ~~ JavaObject]] whileTrue:[
                 method := cls compiledMethodAt:sel signature:signature.
                 method notNil ifTrue:[
-                    ^ self 
-                        invokeJavaMethod:method 
-                        sender:thisContext
-                        selector:sel
-                        with:arg
+                    ^ method
+                        valueWithReceiver:self
+                        arguments:(Array with:arg)
+"/                    ^ self 
+"/                        invokeJavaMethod:method 
+"/                        sender:thisContext
+"/                        selector:sel
+"/                        with:arg
                 ].
                 cls := cls superclass.
             ].
@@ -1213,8 +1162,8 @@
      stack invoke:#size. 
     "
 
-    "Created: 30.7.1997 / 14:13:30 / cg"
-    "Modified: 1.8.1997 / 00:04:40 / cg"
+    "Created: / 30.7.1997 / 14:13:30 / cg"
+    "Modified: / 4.1.1998 / 16:32:45 / cg"
 !
 
 invoke:selector with:arg
@@ -1224,25 +1173,25 @@
 
     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.
-                (sel == selector
-                or:[aMethod name == selector 
-                or:[aMethod signatureNameWithoutReturnType = selector]]) ifTrue:[
-                    aMethod numArgs == 1 ifTrue:[
-                        ^ self 
-                            invokeJavaMethod:aMethod 
-                            sender:thisContext 
-                            selector:selector    
-                            with:arg
-                    ]
-                ]
-            ].
-            cls := cls superclass.
-        ].
+		(sel == selector
+		or:[aMethod name == selector 
+		or:[aMethod signatureNameWithoutReturnType = selector]]) ifTrue:[
+		    aMethod numArgs == 1 ifTrue:[
+			^ self 
+			    invokeJavaMethod:aMethod 
+			    sender:thisContext 
+			    selector:selector    
+			    with:arg
+		    ]
+		]
+	    ].
+	    cls := cls superclass.
+	].
     ].
 
     ^ self doesNotUnderstand:(Message selector:selector)
@@ -1257,25 +1206,25 @@
 
     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 name == selector 
-                or:[aMethod signatureNameWithoutReturnType = selector]) ifTrue:[
-                    aMethod numArgs == 2 ifTrue:[
-                        ^ self 
-                            invokeJavaMethod:aMethod 
-                            sender:thisContext 
-                            selector:selector    
-                            with:arg1
-                            with:arg2
-                    ]
-                ]
-            ].
-            cls := cls superclass.
-        ].
+		(aMethod name == selector 
+		or:[aMethod signatureNameWithoutReturnType = selector]) ifTrue:[
+		    aMethod numArgs == 2 ifTrue:[
+			^ self 
+			    invokeJavaMethod:aMethod 
+			    sender:thisContext 
+			    selector:selector    
+			    with:arg1
+			    with:arg2
+		    ]
+		]
+	    ].
+	    cls := cls superclass.
+	].
     ].
 
     ^ self doesNotUnderstand:(Message selector:selector)
@@ -1293,24 +1242,24 @@
 
     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 name == selector 
-                or:[aMethod signatureNameWithoutReturnType = selector]) ifTrue:[
-                    aMethod numArgs == numArgGiven ifTrue:[
-                        ^ self 
-                            invokeJavaMethod:aMethod 
-                            sender:thisContext 
-                            selector:selector    
-                            withAll:args
-                    ]
-                ]
-            ].
-            cls := cls superclass.
-        ].
+		(aMethod name == selector 
+		or:[aMethod signatureNameWithoutReturnType = selector]) ifTrue:[
+		    aMethod numArgs == numArgGiven ifTrue:[
+			^ self 
+			    invokeJavaMethod:aMethod 
+			    sender:thisContext 
+			    selector:selector    
+			    withAll:args
+		    ]
+		]
+	    ].
+	    cls := cls superclass.
+	].
     ].
 
     ^ self doesNotUnderstand:(Message selector:selector)
@@ -1326,23 +1275,23 @@
 
     sel := signature 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 signatureName = signature ifTrue:[
-                    aMethod numArgs == 0 ifTrue:[
-                        ^ self 
-                            invokeJavaMethod:aMethod 
-                            sender:thisContext
-                            selector:signature
-                    ]
-                ]
-            ].
-            cls := cls superclass.
-        ].
+		aMethod signatureName = signature ifTrue:[
+		    aMethod numArgs == 0 ifTrue:[
+			^ self 
+			    invokeJavaMethod:aMethod 
+			    sender:thisContext
+			    selector:signature
+		    ]
+		]
+	    ].
+	    cls := cls superclass.
+	].
     ].
 
     ^ self doesNotUnderstand:(Message selector:signature)
@@ -1395,19 +1344,19 @@
 
 updateClassRefsFrom:oldClass to:newClass
     self == oldClass ifTrue:[
-        self makeObsolete.
-        ^ self
+	self makeObsolete.
+	^ self
     ].
 
     constantPool updateClassRefsFrom:oldClass to:newClass.
     interfaces notNil ifTrue:[
-        interfaces := interfaces collect:[:anInterface |
-                                            anInterface == oldClass ifTrue:[
-                                                newClass
-                                            ] ifFalse:[
-                                                anInterface
-                                            ]
-                                         ]
+	interfaces := interfaces collect:[:anInterface |
+					    anInterface == oldClass ifTrue:[
+						newClass
+					    ] ifFalse:[
+						anInterface
+					    ]
+					 ]
     ]
 
     "Modified: 8.8.1997 / 12:19:14 / cg"
@@ -1416,6 +1365,6 @@
 !JavaClass class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaClass.st,v 1.65 1997/08/29 15:59:52 stefan Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaClass.st,v 1.66 1998/01/05 18:47:06 cg Exp $'
 ! !
 JavaClass initialize!
--- a/JavaClassReader.st	Fri Aug 29 16:03:19 1997 +0000
+++ b/JavaClassReader.st	Mon Jan 05 18:49:32 1998 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:3.3.1 on 3-jan-1998 at 10:39:11 pm'                  !
+
 Object subclass:#JavaClassReader
 	instanceVariableNames:'inStream msb constants majorVsn minorVsn constNeeds2Slots
 		constSlot'
@@ -66,10 +68,10 @@
 
     loader := ClassLoaderQuerySignal raise.
     loader isNil ifTrue:[
-        rslt := self loadClassLazy:aClassName ignoring:Set new.
-        rslt notNil ifTrue:[self postLoadActions].
+	rslt := self loadClassLazy:aClassName ignoring:(Set new).
+	rslt notNil ifTrue:[self postLoadActions].
 
-        ^ rslt
+	^ rslt
     ].
 
     ^ loader loadClass:aClassName
@@ -84,8 +86,8 @@
      JavaClassReader loadClass:'java/lang/Thread'
     "
 
-    "Created: 15.4.1996 / 14:58:53 / cg"
-    "Modified: 14.8.1997 / 20:07:33 / cg"
+    "Created: / 15.4.1996 / 14:58:53 / cg"
+    "Modified: / 3.1.1998 / 22:36:13 / cg"
 !
 
 loadClassLazy:aClassName ignoring:classesBeingLoaded
@@ -96,69 +98,69 @@
      This is a partial load (to load other classes):
      - The classes stringConstants are not fixed to be JavaStrings 
        (i.e they are still ST-Strings).
-     - The class is not initialized."
+     - The class is NOT initialized."
 
     |rslt clsName cls loadedClass|
 
     (aClassName endsWith:';') ifTrue:[
-        ('oops - loading of ' , aClassName , ' attempted') printNL.
-        self halt:'should not happen'.
-        ^ nil
+	('oops - loading of ' , aClassName , ' attempted') printNL.
+	self halt:'should not happen'.
+	^ nil
     ].
     (aClassName endsWith:'[]') ifTrue:[
-        ('oops - loading of ' , aClassName , ' attempted') printNL.
-        self halt:'should not happen'.
-        ^ nil
+	('oops - loading of ' , aClassName , ' attempted') printNL.
+	self halt:'should not happen'.
+	^ nil
     ].
 
     clsName := aClassName.
     (clsName includes:$.) ifTrue:[
-        clsName := clsName asString copy replaceAll:$. by:$/
+	clsName := clsName asString copy replaceAll:$. with:$/
     ].
 
     (classesBeingLoaded notNil and:[classesBeingLoaded includes:clsName]) ifTrue:[
-        ('oops - recursive load of ' , clsName , ' attempted') printNL.
-        self halt:'should not happen'.
-        ^ JavaUnresolvedClassConstant fullName:clsName
+	('oops - recursive load of ' , clsName , ' attempted') printNL.
+	self halt:'should not happen'.
+	^ JavaUnresolvedClassConstant fullName:clsName
     ].
 
     (cls := Java at:clsName) notNil ifTrue:[
-        ('oops - ' , clsName , ' is already loaded') printNL.
-        self halt:clsName , ' is already loaded - should not happen'.
-        ^ cls
+	('oops - ' , clsName , ' is already loaded') printNL.
+	self halt:clsName , ' is already loaded - should not happen'.
+	^ cls
     ].
 
     classesBeingLoaded isNil ifTrue:[
-        loadedClass := Set with:clsName
+	loadedClass := Set with:clsName
     ] ifFalse:[
-        loadedClass := Set withAll:classesBeingLoaded.
-        loadedClass add:clsName.
+	loadedClass := Set withAll:classesBeingLoaded.
+	loadedClass add:clsName.
     ].
 
     Java classPath do:[:path |
-        |nm p|
+	|nm p|
 
-        p := path.
-        (p endsWith:Filename separator) ifFalse:[
-            p := p , (Filename separator asString)
-        ].
-        (Array 
-            with:clsName
-            with:clsName asLowercase
-            with:clsName asUppercase) 
-        do:[:tryName |
-            (nm := p , tryName , '.class') asFilename exists ifTrue:[
-                rslt := self loadFileLazy:nm ignoring:loadedClass.
-                rslt notNil ifTrue:[^ rslt].
-            ].
-        ]
+	p := path.
+	(p endsWith:Filename separator) ifFalse:[
+	    p := p , (Filename separator asString)
+	].
+	(Array 
+	    with:clsName
+	    with:clsName asLowercase
+	    with:clsName asUppercase) 
+	do:[:tryName |
+	    (nm := p , tryName , '.class') asFilename exists ifTrue:[
+		rslt := self loadFileLazy:nm ignoring:loadedClass.
+		rslt notNil ifTrue:[^ rslt].
+	    ].
+	]
     ].
 
     ('JAVA: no file found for: ' , clsName) infoPrintCR.
     ^ nil
 
-    "Modified: 12.8.1997 / 01:40:29 / cg"
-    "Modified: 14.8.1997 / 11:38:42 / stefan"
+    "Modified: / 14.8.1997 / 11:38:42 / stefan"
+    "Modified: / 3.1.1998 / 22:28:37 / cg"
 !
 
 loadFile:aFilename
@@ -178,11 +180,11 @@
 
     javaClass := self readFile:aFilename ignoring:classesBeingLoaded.
     javaClass notNil ifTrue:[
-        Java at:(javaClass fullName asSymbol) put:javaClass.
+	Java at:(javaClass fullName asSymbol) put:javaClass.
 
-        classesBeingLoaded remove:javaClass fullName ifAbsent:nil.
+	classesBeingLoaded remove:javaClass fullName ifAbsent:nil.
 
-        JavaUnresolvedConstant resolveFor:javaClass.
+	JavaUnresolvedConstant resolveFor:javaClass.
     ].
     ^ javaClass
 
@@ -190,52 +192,52 @@
      JavaClassReader loadFile:'/phys/ibm3/hotjava/classes/browser/AddButton.class'
 
      '/phys/ibm3/java/lib/java/lang' asFilename
-        directoryContents do:[:nm |
-            (nm endsWith:'.class') ifTrue:[
-                ('/phys/ibm3/java/lib/java/lang/' , nm) printNL.
-                JavaClassReader loadFile:'/phys/ibm3/java/lib/java/lang/' , nm
-            ]
-        ].
+	directoryContents do:[:nm |
+	    (nm endsWith:'.class') ifTrue:[
+		('/phys/ibm3/java/lib/java/lang/' , nm) printNL.
+		JavaClassReader loadFile:'/phys/ibm3/java/lib/java/lang/' , nm
+	    ]
+	].
 
      '/phys/ibm3/java/lib/java/io' asFilename
-        directoryContents do:[:nm |
-            (nm endsWith:'.class') ifTrue:[
-                ('/phys/ibm3/java/lib/java/io/' , nm) printNL.
-                JavaClassReader loadFile:'/phys/ibm3/java/lib/java/io/' , nm
-            ]
-        ].
+	directoryContents do:[:nm |
+	    (nm endsWith:'.class') ifTrue:[
+		('/phys/ibm3/java/lib/java/io/' , nm) printNL.
+		JavaClassReader loadFile:'/phys/ibm3/java/lib/java/io/' , nm
+	    ]
+	].
 
      '/phys/ibm3/java/lib/java/net' asFilename
-        directoryContents do:[:nm |
-            (nm endsWith:'.class') ifTrue:[
-                ('/phys/ibm3/java/lib/java/net/' , nm) printNL.
-                JavaClassReader loadFile:'/phys/ibm3/java/lib/java/net/' , nm
-            ]
-        ].
+	directoryContents do:[:nm |
+	    (nm endsWith:'.class') ifTrue:[
+		('/phys/ibm3/java/lib/java/net/' , nm) printNL.
+		JavaClassReader loadFile:'/phys/ibm3/java/lib/java/net/' , nm
+	    ]
+	].
 
      '/phys/ibm3/java/lib/java/util' asFilename
-        directoryContents do:[:nm |
-            (nm endsWith:'.class') ifTrue:[
-                ('/phys/ibm3/java/lib/java/util/' , nm) printNL.
-                JavaClassReader loadFile:'/phys/ibm3/java/lib/java/util/' , nm
-            ]
-        ].
+	directoryContents do:[:nm |
+	    (nm endsWith:'.class') ifTrue:[
+		('/phys/ibm3/java/lib/java/util/' , nm) printNL.
+		JavaClassReader loadFile:'/phys/ibm3/java/lib/java/util/' , nm
+	    ]
+	].
 
      '/phys/ibm3/java/lib/java/awt' asFilename
-        directoryContents do:[:nm |
-            (nm endsWith:'.class') ifTrue:[
-                ('/phys/ibm3/java/lib/java/awt/' , nm) printNL.
-                JavaClassReader loadFile:'/phys/ibm3/java/lib/java/awt/' , nm
-            ]
-        ].
+	directoryContents do:[:nm |
+	    (nm endsWith:'.class') ifTrue:[
+		('/phys/ibm3/java/lib/java/awt/' , nm) printNL.
+		JavaClassReader loadFile:'/phys/ibm3/java/lib/java/awt/' , nm
+	    ]
+	].
 
      '/phys/ibm3/java/lib/java/applet' asFilename
-        directoryContents do:[:nm |
-            (nm endsWith:'.class') ifTrue:[
-                ('/phys/ibm3/java/lib/java/applet/' , nm) printNL.
-                JavaClassReader loadFile:'/phys/ibm3/java/lib/java/applet/' , nm
-            ]
-        ].
+	directoryContents do:[:nm |
+	    (nm endsWith:'.class') ifTrue:[
+		('/phys/ibm3/java/lib/java/applet/' , nm) printNL.
+		JavaClassReader loadFile:'/phys/ibm3/java/lib/java/applet/' , nm
+	    ]
+	].
 
      JavaClassReader loadFile:'/phys/ibm3/java/lib/java/lang/AbstractMethodError.class'
      JavaClassReader loadFile:'/phys/ibm3/java/lib/java/lang/Thread.class'
@@ -256,64 +258,64 @@
 
 postLoadActions:loadUnresolved
     "Resolve all classes' string constants.
-     Perform all class initialization functions (of those which are not
-     yet initialized)."
+     Perform all class initialization functions 
+     (of those which are not yet initialized)."
 
     |classes prevUnresolved newUnresolved loader|
 
     "/ need at least java.lang.String, for valid constants
     Java java_lang_String isNil ifTrue:[
-        self loadClassLazy:'java.lang.String' ignoring:Set new.
+	self loadClassLazy:'java.lang.String' ignoring:(Set new).
     ].
 
     LazyClassLoading ifFalse:[
-        loader := ClassLoaderQuerySignal raise.
+	loader := ClassLoaderQuerySignal raise.
 
-        prevUnresolved := nil.
-        newUnresolved := JavaUnresolvedConstant unresolvedClassNames asArray.
-        loadUnresolved ifTrue:[
-            [prevUnresolved ~= newUnresolved] whileTrue:[
-                newUnresolved do:[:nextUnresolved |
-                    (Java at:nextUnresolved) isNil ifTrue:[ "/ could have been loaded in the meantime
-                        Silent ifFalse:[
-                            'loading unresolved: ' print. nextUnresolved printCR.
-                        ].
-                        loader isNil ifTrue:[
-                            self
-                                loadClassLazy:nextUnresolved
-                                ignoring:Set new.
-                        ] ifFalse:[
-                            loader loadClass:nextUnresolved
-                        ]
-                    ]
-                ].
-                prevUnresolved := newUnresolved.
-                newUnresolved := JavaUnresolvedConstant unresolvedClassNames asArray.
-            ].
-        ].
+	prevUnresolved := nil.
+	newUnresolved := JavaUnresolvedConstant unresolvedClassNames asArray.
+	loadUnresolved ifTrue:[
+	    [prevUnresolved ~= newUnresolved] whileTrue:[
+		newUnresolved do:[:nextUnresolved |
+		    (Java at:nextUnresolved) isNil ifTrue:[ "/ could have been loaded in the meantime
+			Silent ifFalse:[
+			    'loading unresolved: ' print. nextUnresolved printCR.
+			].
+			loader isNil ifTrue:[
+			    self
+				loadClassLazy:nextUnresolved
+				ignoring:(Set new).
+			] ifFalse:[
+			    loader loadClass:nextUnresolved
+			]
+		    ]
+		].
+		prevUnresolved := newUnresolved.
+		newUnresolved := JavaUnresolvedConstant unresolvedClassNames asArray.
+	    ].
+	].
 
-        newUnresolved size == 0 ifTrue:[
-            "/ nothing unresolved
+	newUnresolved size == 0 ifTrue:[
+	    "/ nothing unresolved
 
-            (classes := Java allClasses) notNil ifTrue:[
-                "/ init all new classes
-                "/ fetch again - there could be new ones ...
+	    (classes := Java allClasses) notNil ifTrue:[
+		"/ init all new classes
+		"/ fetch again - there could be new ones ...
 
-                classes := Java allClasses.
-                classes do:[:aJavaClass |
-                    aJavaClass isInitialized ifFalse:[
-                        Silent ifFalse:[
-                            'performing class initialization of ' print. aJavaClass fullName printCR.
-                        ].
-                        aJavaClass classInit
-                    ]
-                ]
-            ]
-        ].
+		classes := Java allClasses.
+		classes do:[:aJavaClass |
+		    aJavaClass isInitialized ifFalse:[
+			Silent ifFalse:[
+			    'performing class initialization of ' print. aJavaClass fullName printCR.
+			].
+			aJavaClass classInit
+		    ]
+		]
+	    ]
+	].
     ]
 
-    "Created: 15.8.1997 / 01:01:44 / cg"
-    "Modified: 17.8.1997 / 20:04:41 / cg"
+    "Created: / 15.8.1997 / 01:01:44 / cg"
+    "Modified: / 3.1.1998 / 22:35:48 / cg"
 !
 
 readFile:aFilename ignoring:classesBeingLoaded
@@ -324,24 +326,24 @@
     |inStream javaClass|
 
     Silent ifFalse:[
-        'reading ' print. aFilename print. ' ...' printNL.
+	'reading ' print. aFilename print. ' ...' printNL.
     ].
 
     inStream := aFilename asFilename readStream.
     inStream isNil ifTrue:[
-        ('no file: ' , aFilename) printCR.
-        self halt.
-        ^ nil
+	('no file: ' , aFilename) printCR.
+	self halt.
+	^ nil
     ].
 
     javaClass := self new readStream:inStream ignoring:classesBeingLoaded.
     javaClass notNil ifTrue:[
-        javaClass setBinaryFilePath:(inStream pathName).
+	javaClass setBinaryFilePath:(inStream pathName).
     ].
     inStream close.
 
     AbsolutelySilent ifFalse:[
-        '  ... loaded ' print. javaClass displayString printNL.
+	'  ... loaded ' print. javaClass displayString printNL.
     ].
 
     ^ javaClass
@@ -381,9 +383,9 @@
      is created."
 
     ^ self
-        readStream:aStream 
-        loader:aClassLoader 
-        loadUnresolved:true
+	readStream:aStream 
+	loader:aClassLoader 
+	loadUnresolved:true
 
     "Modified: 15.8.1997 / 01:00:35 / cg"
 !
@@ -399,12 +401,12 @@
 
     javaClass := self readStream:aStream ignoring:(Set new).
     javaClass notNil ifTrue:[
-        ClassLoaderQuerySignal answer:aClassLoader
-        do:[
-            self postLoadActions:loadUnresolved.
-            Java at:(javaClass fullName asSymbol) put:javaClass.
-            JavaUnresolvedConstant resolveFor:javaClass.
-        ].
+	ClassLoaderQuerySignal answer:aClassLoader
+	do:[
+	    self postLoadActions:loadUnresolved.
+	    Java at:(javaClass fullName asSymbol) put:javaClass.
+	    JavaUnresolvedConstant resolveFor:javaClass.
+	].
     ].
     ^ javaClass
 
@@ -430,14 +432,14 @@
     msb := true.
     magic := inStream nextUnsignedLongMSB:msb.
     magic = 16rCAFEBABE ifFalse:[
-        magic = 16rBEBAFECA ifFalse:[
-            InvalidClassFormatSignal raiseErrorString:'not a java class file'.
-            ^ nil
-        ].
-        msb := false.
-        Verbose ifTrue:[Transcript showCR:'file is lsb'].
+	magic = 16rBEBAFECA ifFalse:[
+	    InvalidClassFormatSignal raiseErrorString:'not a java class file'.
+	    ^ nil
+	].
+	msb := false.
+	Verbose ifTrue:[Transcript showCR:'file is lsb'].
     ] ifTrue:[
-        Verbose ifTrue:[Transcript showCR:'file is msb'].
+	Verbose ifTrue:[Transcript showCR:'file is msb'].
     ].
 
     "/
@@ -447,14 +449,14 @@
     majorVsn := inStream nextUnsignedShortMSB:msb.
 
     (majorVsn ~~ 45 or:[minorVsn ~~ 3]) ifTrue:[
-        Transcript show:'warning this file has version '; show:majorVsn; show:'.'; showCR:minorVsn. 
+	Transcript show:'warning this file has version '; show:majorVsn; show:'.'; showCR:minorVsn. 
     ].
 
     Verbose ifTrue:[
-        Transcript show:'version = '; 
-                   show:(majorVsn printString); 
-                   show:'.';
-                   showCR:(minorVsn printString).
+	Transcript show:'version = '; 
+		   show:(majorVsn printString); 
+		   show:'.';
+		   showCR:(minorVsn printString).
     ].
 
     "/
@@ -470,30 +472,30 @@
     super_class_index := inStream nextUnsignedShortMSB:msb.
 
     super_class_index == 0 ifTrue:[
-        super_class := nil
+	super_class := nil
     ] ifFalse:[
-        super_class := constants at:super_class_index.
-        existingSuperClass := Java classNamed:super_class fullName.
-        existingSuperClass notNil ifTrue:[
-            super_class := existingSuperClass
-        ] ifFalse:[
-            (super_class isMemberOf:JavaUnresolvedClassConstant) ifTrue:[
-                Silent ifFalse:[
-                    'load superClass: ' print. super_class fullName printCR.
-                ].
+	super_class := constants at:super_class_index.
+	existingSuperClass := Java classNamed:super_class fullName.
+	existingSuperClass notNil ifTrue:[
+	    super_class := existingSuperClass
+	] ifFalse:[
+	    (super_class isMemberOf:JavaUnresolvedClassConstant) ifTrue:[
+		Silent ifFalse:[
+		    'load superClass: ' print. super_class fullName printCR.
+		].
 
-                existingSuperClass := self class 
-                                    loadClassLazy:(super_class fullName)
-                                    ignoring:classesbeingLoaded.
+		existingSuperClass := self class 
+				    loadClassLazy:(super_class fullName)
+				    ignoring:classesbeingLoaded.
 
-                existingSuperClass isNil ifTrue:[
-                    self halt:('cannot find superclass: ' , super_class fullName).
-                ].
-                super_class := existingSuperClass
-            ] ifFalse:[
-                self halt:'oops - superclass ?'
-            ]
-        ].
+		existingSuperClass isNil ifTrue:[
+		    self halt:('cannot find superclass: ' , super_class fullName).
+		].
+		super_class := existingSuperClass
+	    ] ifFalse:[
+		self halt:'oops - superclass ?'
+	    ]
+	].
     ].
 
     "/
@@ -517,11 +519,11 @@
     this_class := JavaClass fullName:(this_class_ref fullName) numStatic:nStatic.
 
     nStatic ~~ 0 ifTrue:[
-        fields := fields select:[:f | f isStatic not].
+	fields := fields select:[:f | f isStatic not].
 
-        JavaClass setInstanceVariableStringFromFields:staticFields in:this_class class.
-        this_class setStaticFields:staticFields.
-        this_class initializeStaticFields.
+	JavaClass setInstanceVariableStringFromFields:staticFields in:this_class class.
+	this_class setStaticFields:staticFields.
+	this_class initializeStaticFields.
     ].
 
     this_class setAccessFlags:access_flags.
@@ -551,8 +553,8 @@
      JavaClassReader readFile:'/phys/ibm3/java/lib/java/lang/ArithmeticException.class'
     "
 
-    "Created: 15.4.1996 / 15:02:47 / cg"
-    "Modified: 3.8.1997 / 18:18:56 / cg"
+    "Created: / 15.4.1996 / 15:02:47 / cg"
+    "Modified: / 3.1.1998 / 22:33:16 / cg"
 !
 
 readSourceFileAttributeFor:aJavaClass
@@ -599,28 +601,31 @@
 readAttribute:attributeName for:something
 
     (attributeName = 'Code') ifTrue:[
-        self readCodeAttributeFor:something.
-        ^ true.
+	self readCodeAttributeFor:something.
+	^ true.
     ].
     (attributeName = 'Exceptions') ifTrue:[
-        self readExceptionsAttributeFor:something.
-        ^ true.
+	self readExceptionsAttributeFor:something.
+	^ true.
     ].
     (attributeName = 'LineNumberTable') ifTrue:[
-        self readLineNumberTableAttributeFor:something.
-        ^ true.
+	self readLineNumberTableAttributeFor:something.
+	^ true.
     ].
     (attributeName = 'LocalVariableTable') ifTrue:[
-        self readLocalVariableTableAttributeFor:something.
-        ^ true.
+	self readLocalVariableTableAttributeFor:something.
+	^ true.
     ].
     (attributeName = 'ConstantValue') ifTrue:[
-        self readConstantValueAttributeFor:something.
-        ^ true.
+	self readConstantValueAttributeFor:something.
+	^ true.
     ].
     (attributeName = 'SourceFile') ifTrue:[
-        self readSourceFileAttributeFor:something.
-        ^ true.
+	self readSourceFileAttributeFor:something.
+	^ true.
+    ].
+    (attributeName = 'Deprecated') ifTrue:[
+	^ false.
     ].
 
     ('JAVA: unrecognized attribute: ' , attributeName) infoPrintCR.
@@ -641,9 +646,9 @@
     "/ UNDOC feature ?
     "/
     attribute_name_index > constants size ifTrue:[
-        attribute_name_index == 16rb700 ifTrue:[
-            self halt.
-        ]
+	attribute_name_index == 16rb700 ifTrue:[
+	    self halt.
+	]
     ].
 
     attribute_name := constants at:attribute_name_index.
@@ -651,11 +656,11 @@
     Verbose ifTrue:[Transcript show:'attrib name: '; showCR:attribute_name].
 
     (self readAttribute:attribute_name for:something) ifFalse:[
-        attribute_length := inStream nextUnsignedLongMSB:msb.
-        attribute_info := ByteArray new:(attribute_length).
-        inStream nextBytes:attribute_length into:attribute_info startingAt:1.
+	attribute_length := inStream nextUnsignedLongMSB:msb.
+	attribute_info := ByteArray new:(attribute_length).
+	inStream nextBytes:attribute_length into:attribute_info startingAt:1.
 
-        Verbose ifTrue:[Transcript show:'skipped '; show:attribute_name; showCR:'-attribute'].
+	Verbose ifTrue:[Transcript show:'skipped '; show:attribute_name; showCR:'-attribute'].
     ].
 
     "
@@ -672,7 +677,7 @@
     attributes_count := inStream nextUnsignedShortMSB:msb.
 
     1 to:attributes_count do:[:i |
-        self readAttributeFor:something.
+	self readAttributeFor:something.
     ].
 
     "Modified: 15.4.1996 / 15:33:28 / cg"
@@ -694,19 +699,19 @@
     Verbose ifTrue:[Transcript show:'tag = '; showCR:tag].
 
     constReader := #(
-                        readConstant_Asciz              "/ 1  - now called Utf8
-                        readConstant_Unicode            "/ 2
-                        readConstant_Integer            "/ 3
-                        readConstant_Float              "/ 4
-                        readConstant_Long               "/ 5
-                        readConstant_Double             "/ 6
-                        readConstant_Class              "/ 7
-                        readConstant_String             "/ 8
-                        readConstant_Fieldref           "/ 9
-                        readConstant_Methodref          "/ 10
-                        readConstant_InterfaceMethodref "/ 11
-                        readConstant_NameAndType        "/ 12
-                    ) at:tag ifAbsent:[#readConstant_Undef].
+			readConstant_Asciz              "/ 1  - now called Utf8
+			readConstant_Unicode            "/ 2
+			readConstant_Integer            "/ 3
+			readConstant_Float              "/ 4
+			readConstant_Long               "/ 5
+			readConstant_Double             "/ 6
+			readConstant_Class              "/ 7
+			readConstant_String             "/ 8
+			readConstant_Fieldref           "/ 9
+			readConstant_Methodref          "/ 10
+			readConstant_InterfaceMethodref "/ 11
+			readConstant_NameAndType        "/ 12
+		    ) at:tag ifAbsent:[#readConstant_Undef].
 
     ^ self perform:constReader.
 
@@ -731,13 +736,13 @@
 
     constSlot := 1.
     [constSlot < constantPoolCount] whileTrue:[
-        Verbose ifTrue:[Transcript show:'const: '; showCR:constSlot].
-        const := self readConstant.
-        constants at:constSlot put:const.
-        constNeeds2Slots ifTrue:[
-            constSlot := constSlot + 1.
-        ].
-        constSlot := constSlot + 1.
+	Verbose ifTrue:[Transcript show:'const: '; showCR:constSlot].
+	const := self readConstant.
+	constants at:constSlot put:const.
+	constNeeds2Slots ifTrue:[
+	    constSlot := constSlot + 1.
+	].
+	constSlot := constSlot + 1.
     ].
 
     constSlot := -1.
@@ -745,17 +750,17 @@
     "/ preresolve what can be (especially, strings are resolved here)
 
     1 to:constantPoolCount-1 do:[:i |
-        |const value|
+	|const value|
 
-        const := constants at:i.
-        const notNil ifTrue:[   "/ kludge for 2-slot constants (which only take 1 slot in ST/X)
-            (const isKindOf:JavaUnresolvedConstant) ifTrue:[
-                value := const preResolve.
-                value ~~ const ifTrue:[
-                    constants at:i put:value.
-                ]
-            ]
-        ]
+	const := constants at:i.
+	const notNil ifTrue:[   "/ kludge for 2-slot constants (which only take 1 slot in ST/X)
+	    (const isKindOf:JavaUnresolvedConstant) ifTrue:[
+		value := const preResolve.
+		value ~~ const ifTrue:[
+		    constants at:i put:value.
+		]
+	    ]
+	]
     ].
 
     "
@@ -796,14 +801,14 @@
 
     name := constants at:name_index.
     name notNil ifTrue:[
-        Verbose ifTrue:[Transcript showCR:'name in constant_class already resolved'].
-        "/ self halt
+	Verbose ifTrue:[Transcript showCR:'name in constant_class already resolved'].
+	"/ self halt
     ].
 
     ^ JavaUnresolvedClassConstant 
-        pool:constants
-        poolIndex:constSlot
-        nameIndex:name_index
+	pool:constants
+	poolIndex:constSlot
+	nameIndex:name_index
 
     "
      JavaClassReader readFile:'/phys/ibm3/hotjava/classes/browser/AddButton.class'
@@ -821,23 +826,23 @@
 
     aFloat := Float new.
     UninterpretedBytes isBigEndian ifTrue:[
-        aFloat basicAt:1 put:((high bitShift:-24) bitAnd:16rFF).
-        aFloat basicAt:2 put:((high bitShift:-16) bitAnd:16rFF).
-        aFloat basicAt:3 put:((high bitShift:-8) bitAnd:16rFF).
-        aFloat basicAt:4 put:(high bitAnd:16rFF).
-        aFloat basicAt:5 put:((low bitShift:-24) bitAnd:16rFF).
-        aFloat basicAt:6 put:((low bitShift:-16) bitAnd:16rFF).
-        aFloat basicAt:7 put:((low bitShift:-8) bitAnd:16rFF).
-        aFloat basicAt:8 put:(low bitAnd:16rFF).
+	aFloat basicAt:1 put:((high bitShift:-24) bitAnd:16rFF).
+	aFloat basicAt:2 put:((high bitShift:-16) bitAnd:16rFF).
+	aFloat basicAt:3 put:((high bitShift:-8) bitAnd:16rFF).
+	aFloat basicAt:4 put:(high bitAnd:16rFF).
+	aFloat basicAt:5 put:((low bitShift:-24) bitAnd:16rFF).
+	aFloat basicAt:6 put:((low bitShift:-16) bitAnd:16rFF).
+	aFloat basicAt:7 put:((low bitShift:-8) bitAnd:16rFF).
+	aFloat basicAt:8 put:(low bitAnd:16rFF).
     ] ifFalse:[
-        aFloat basicAt:1 put:(low bitAnd:16rFF).
-        aFloat basicAt:2 put:((low bitShift:-8) bitAnd:16rFF).
-        aFloat basicAt:3 put:((low bitShift:-16) bitAnd:16rFF).
-        aFloat basicAt:4 put:((low bitShift:-24) bitAnd:16rFF).
-        aFloat basicAt:5 put:(high bitAnd:16rFF).
-        aFloat basicAt:6 put:((high bitShift:-8) bitAnd:16rFF).
-        aFloat basicAt:7 put:((high bitShift:-16) bitAnd:16rFF).
-        aFloat basicAt:8 put:((high bitShift:-24) bitAnd:16rFF).
+	aFloat basicAt:1 put:(low bitAnd:16rFF).
+	aFloat basicAt:2 put:((low bitShift:-8) bitAnd:16rFF).
+	aFloat basicAt:3 put:((low bitShift:-16) bitAnd:16rFF).
+	aFloat basicAt:4 put:((low bitShift:-24) bitAnd:16rFF).
+	aFloat basicAt:5 put:(high bitAnd:16rFF).
+	aFloat basicAt:6 put:((high bitShift:-8) bitAnd:16rFF).
+	aFloat basicAt:7 put:((high bitShift:-16) bitAnd:16rFF).
+	aFloat basicAt:8 put:((high bitShift:-24) bitAnd:16rFF).
     ].
 
     constNeeds2Slots := true.
@@ -864,10 +869,10 @@
     Verbose ifTrue:[Transcript show:'fieldref; name&typeindex= '; showCR:name_and_type_index].
 
     ^ JavaUnresolvedFieldrefConstant
-                pool:constants
-                poolIndex:constSlot
-                classIndex:class_index
-                nameandTypeIndex:name_and_type_index
+		pool:constants
+		poolIndex:constSlot
+		classIndex:class_index
+		nameandTypeIndex:name_and_type_index
 
     "
      JavaClassReader readFile:'/phys/ibm3/hotjava/classes/browser/AddButton.class'
@@ -884,15 +889,15 @@
 
     aFloat := ShortFloat basicNew.
     UninterpretedBytes isBigEndian ifTrue:[
-        aFloat basicAt:1 put:((high bitShift:-24) bitAnd:16rFF).
-        aFloat basicAt:2 put:((high bitShift:-16) bitAnd:16rFF).
-        aFloat basicAt:3 put:((high bitShift:-8) bitAnd:16rFF).
-        aFloat basicAt:4 put:(high bitAnd:16rFF).
+	aFloat basicAt:1 put:((high bitShift:-24) bitAnd:16rFF).
+	aFloat basicAt:2 put:((high bitShift:-16) bitAnd:16rFF).
+	aFloat basicAt:3 put:((high bitShift:-8) bitAnd:16rFF).
+	aFloat basicAt:4 put:(high bitAnd:16rFF).
     ] ifFalse:[
-        aFloat basicAt:1 put:(high bitAnd:16rFF).
-        aFloat basicAt:2 put:((high bitShift:-8) bitAnd:16rFF).
-        aFloat basicAt:3 put:((high bitShift:-16) bitAnd:16rFF).
-        aFloat basicAt:4 put:((high bitShift:-24) bitAnd:16rFF).
+	aFloat basicAt:1 put:(high bitAnd:16rFF).
+	aFloat basicAt:2 put:((high bitShift:-8) bitAnd:16rFF).
+	aFloat basicAt:3 put:((high bitShift:-16) bitAnd:16rFF).
+	aFloat basicAt:4 put:((high bitShift:-24) bitAnd:16rFF).
     ].
 
     Verbose ifTrue:[Transcript show:'float; value= ';     showCR:aFloat].
@@ -935,10 +940,10 @@
     Verbose ifTrue:[Transcript show:'methodref; name&typeindex= '; showCR:name_and_type_index].
 
     ^ JavaUnresolvedInterfaceMethodrefConstant 
-                pool:constants
-                poolIndex:constSlot
-                classIndex:class_index
-                nameandTypeIndex:name_and_type_index
+		pool:constants
+		poolIndex:constSlot
+		classIndex:class_index
+		nameandTypeIndex:name_and_type_index
 
     "
      JavaClassReader readFile:'/phys/ibm3/hotjava/classes/browser/AddButton.class'
@@ -956,7 +961,7 @@
 
     value := (high bitShift:32) bitOr:low.
     (high bitTest:16r80000000) ifTrue:[
-        value := value - 16r10000000000000000.
+	value := value - 16r10000000000000000.
     ].
     constNeeds2Slots := true.
 
@@ -982,10 +987,10 @@
     Verbose ifTrue:[Transcript show:'methodref; name&typeindex= '; showCR:name_and_type_index].
 
     ^ JavaUnresolvedMethodrefConstant 
-                pool:constants
-                poolIndex:constSlot
-                classIndex:class_index
-                nameandTypeIndex:name_and_type_index
+		pool:constants
+		poolIndex:constSlot
+		classIndex:class_index
+		nameandTypeIndex:name_and_type_index
 
     "
      JavaClassReader readFile:'/phys/ibm3/hotjava/classes/browser/AddButton.class'
@@ -1005,10 +1010,10 @@
     Verbose ifTrue:[Transcript show:'methodref; signatureindex= '; showCR:signature_index].
 
     ^ JavaUnresolvedNameandTypeConstant 
-                pool:constants
-                poolIndex:constSlot
-                nameIndex:name_index
-                signatureIndex:signature_index  
+		pool:constants
+		poolIndex:constSlot
+		nameIndex:name_index
+		signatureIndex:signature_index  
 
     "
      JavaClassReader readFile:'/phys/ibm3/hotjava/classes/browser/AddButton.class'
@@ -1026,9 +1031,9 @@
     Verbose ifTrue:[Transcript show:'string; index= '; showCR:string_index].
 
     ^ JavaUnresolvedStringConstant 
-        pool:constants 
-        poolIndex:constSlot
-        stringIndex:string_index
+	pool:constants 
+	poolIndex:constSlot
+	stringIndex:string_index
 
     "
      Verbose := true.
@@ -1078,11 +1083,11 @@
     attributes_count := inStream nextUnsignedShortMSB:msb.
 
     Verbose ifTrue:[Transcript show:'  field name: '; show:(constants at:name_index);
-                               show:' access: '; show:access_flags;
-                               show:' attrib_cnt: '; showCR:attributes_count].
+			       show:' access: '; show:access_flags;
+			       show:' attrib_cnt: '; showCR:attributes_count].
 
     1 to:attributes_count do:[:i |
-        self readAttributeFor:field.
+	self readAttributeFor:field.
     ].
 
     ^ field
@@ -1107,8 +1112,8 @@
     fields := Array new:nFields.
 
     1 to:nFields do:[:i |
-        Verbose ifTrue:[Transcript show:'field: '; showCR:i].
-        fields at:i put:(self readFieldInfofield)
+	Verbose ifTrue:[Transcript show:'field: '; showCR:i].
+	fields at:i put:(self readFieldInfofield)
     ].
     ^ fields
 
@@ -1134,11 +1139,11 @@
     interfaces := Array new:interfacesCount.
 
     1 to:interfacesCount do:[:i |
-        Verbose ifTrue:[Transcript show:'interface: '; showCR:i].
-        interface_index := inStream nextUnsignedShortMSB:msb.
-        interface := constants at:interface_index.
+	Verbose ifTrue:[Transcript show:'interface: '; showCR:i].
+	interface_index := inStream nextUnsignedShortMSB:msb.
+	interface := constants at:interface_index.
 
-        interfaces at:i put:interface.
+	interfaces at:i put:interface.
     ].
     ^ interfaces
 
@@ -1162,15 +1167,15 @@
     Verbose ifTrue:[Transcript show:'attribute_length: 0x'; showCR:(attribute_length printStringRadix:16)].
 
     minorVsn > 2 ifTrue:[
-        unknown1 := inStream nextByte.
-        max_stack := inStream nextByte.
-        max_locals := inStream nextUnsignedShortMSB:msb.
-        unknown2 := inStream nextUnsignedShortMSB:msb.
-        Verbose ifTrue:[Transcript show:'?1: '; showCR:unknown1].
-        Verbose ifTrue:[Transcript show:'?2: '; showCR:unknown2].
+	unknown1 := inStream nextByte.
+	max_stack := inStream nextByte.
+	max_locals := inStream nextUnsignedShortMSB:msb.
+	unknown2 := inStream nextUnsignedShortMSB:msb.
+	Verbose ifTrue:[Transcript show:'?1: '; showCR:unknown1].
+	Verbose ifTrue:[Transcript show:'?2: '; showCR:unknown2].
     ] ifFalse:[
-        max_stack := inStream nextByte.
-        max_locals := inStream nextByte.
+	max_stack := inStream nextByte.
+	max_locals := inStream nextByte.
     ].
 
     code_length := inStream nextUnsignedShortMSB:msb.
@@ -1185,31 +1190,31 @@
     exception_table_length := inStream nextUnsignedShortMSB:msb.
     Verbose ifTrue:[Transcript show:'exception_table_length: '; showCR:(exception_table_length printStringRadix:16)].
     exception_table_length ~~ 0 ifTrue:[
-        Verbose ifTrue:[Transcript show:'exceptionTable length:'; showCR:exception_table_length.].
+	Verbose ifTrue:[Transcript show:'exceptionTable length:'; showCR:exception_table_length.].
 
-        exception_table := Array new:exception_table_length.
-        1 to:exception_table_length do:[:i |
-            |start_pc end_pc handler_pc catch_type|
+	exception_table := Array new:exception_table_length.
+	1 to:exception_table_length do:[:i |
+	    |start_pc end_pc handler_pc catch_type|
 
-            start_pc := inStream nextUnsignedShortMSB:msb.
-            end_pc := inStream nextUnsignedShortMSB:msb.
-            handler_pc := inStream nextUnsignedShortMSB:msb.
-            catch_type := constants at:(inStream nextUnsignedShortMSB:msb).
-            exception_table at:i put:(JavaExceptionTableEntry
-                                            startPC:start_pc
-                                            endPC:end_pc
-                                            handlerPC:handler_pc
-                                            catchType:catch_type).
-        ].
-        aJavaMethod setExceptionHandlerTable:exception_table.
+	    start_pc := inStream nextUnsignedShortMSB:msb.
+	    end_pc := inStream nextUnsignedShortMSB:msb.
+	    handler_pc := inStream nextUnsignedShortMSB:msb.
+	    catch_type := constants at:(inStream nextUnsignedShortMSB:msb).
+	    exception_table at:i put:(JavaExceptionTableEntry
+					    startPC:start_pc
+					    endPC:end_pc
+					    handlerPC:handler_pc
+					    catchType:catch_type).
+	].
+	aJavaMethod setExceptionHandlerTable:exception_table.
     ].
 
     aJavaMethod 
-        setCode:code 
-        maxStack:max_stack 
-        maxLocals:max_locals 
-        u1:unknown1 
-        u2:unknown2.
+	setCode:code 
+	maxStack:max_stack 
+	maxLocals:max_locals 
+	u1:unknown1 
+	u2:unknown2.
 
     self readAttributesFor:aJavaMethod.
     ^ true
@@ -1230,14 +1235,14 @@
 
     exception_table_length := inStream nextUnsignedShortMSB:msb.
     exception_table_length ~~ 0 ifTrue:[
-        exception_table := Array new:exception_table_length.
-        1 to:exception_table_length do:[:i |
-            |idx ex|
+	exception_table := Array new:exception_table_length.
+	1 to:exception_table_length do:[:i |
+	    |idx ex|
 
-            idx := inStream nextUnsignedShortMSB:msb.
-            ex := constants at:idx.
-            exception_table at:i put:ex.
-        ].
+	    idx := inStream nextUnsignedShortMSB:msb.
+	    ex := constants at:idx.
+	    exception_table at:i put:ex.
+	].
     ].
 
     Verbose ifTrue:[Transcript showCR:'method has an exceptionTable'].
@@ -1256,14 +1261,14 @@
 
     line_number_table_length := inStream nextUnsignedShortMSB:msb.
     line_number_table_length ~~ 0 ifTrue:[
-        line_number_table := Array new:line_number_table_length.
-        1 to:line_number_table_length do:[:i |
-            |start_pc line_number|
+	line_number_table := Array new:line_number_table_length.
+	1 to:line_number_table_length do:[:i |
+	    |start_pc line_number|
 
-            start_pc := inStream nextUnsignedShortMSB:msb.
-            line_number := inStream nextUnsignedShortMSB:msb.
-            line_number_table at:i put:(start_pc -> line_number).
-        ].
+	    start_pc := inStream nextUnsignedShortMSB:msb.
+	    line_number := inStream nextUnsignedShortMSB:msb.
+	    line_number_table at:i put:(start_pc -> line_number).
+	].
     ].
 
     Verbose ifTrue:[Transcript showCR:'method has a lineNumberTable'].
@@ -1287,25 +1292,25 @@
 
     local_variable_table_length := inStream nextUnsignedShortMSB:msb.
     local_variable_table_length ~~ 0 ifTrue:[
-        local_variable_table := JavaLocalVariableTable new:local_variable_table_length.
-        1 to:local_variable_table_length do:[:i |
-            |start_pc length name_index sig_index slot name signature|
+	local_variable_table := JavaLocalVariableTable new:local_variable_table_length.
+	1 to:local_variable_table_length do:[:i |
+	    |start_pc length name_index sig_index slot name signature|
 
-            start_pc := inStream nextUnsignedShortMSB:msb.
-            length := inStream nextUnsignedShortMSB:msb.
-            name_index := inStream nextUnsignedShortMSB:msb.
-            name := constants at:name_index.
-            sig_index := inStream nextUnsignedShortMSB:msb.
-            signature := constants at:sig_index.
-            slot := inStream nextUnsignedShortMSB:msb.
+	    start_pc := inStream nextUnsignedShortMSB:msb.
+	    length := inStream nextUnsignedShortMSB:msb.
+	    name_index := inStream nextUnsignedShortMSB:msb.
+	    name := constants at:name_index.
+	    sig_index := inStream nextUnsignedShortMSB:msb.
+	    signature := constants at:sig_index.
+	    slot := inStream nextUnsignedShortMSB:msb.
 
-            local_variable_table at:i put:(JavaLocalVariableTableEntry new 
-                                                startPC:start_pc 
-                                                length:length
-                                                name:name
-                                                signature:signature
-                                                slot:slot)
-        ].
+	    local_variable_table at:i put:(JavaLocalVariableTableEntry new 
+						startPC:start_pc 
+						length:length
+						name:name
+						signature:signature
+						slot:slot)
+	].
     ].
 
     Verbose ifTrue:[Transcript showCR:'method has a localvariableTable'].
@@ -1336,12 +1341,11 @@
     signature := constants at:signature_index.
 
     Verbose ifTrue:[Transcript show:'method name:'; showCR:name.
-                    Transcript show:'signature:'; showCR:signature.].
+		    Transcript show:'signature:'; showCR:signature.].
 
     m := JavaMethod new.
     m setAccessFlags:access_flags.
-    m setSignature:signature.
-    m setName:name.
+    m setName:name signature:signature.
     m setJavaClass:aJavaClass.
 
     self readAttributesFor:m.
@@ -1367,8 +1371,8 @@
     Verbose ifTrue:[Transcript show:'methodsCount = '; showCR:methodsCount].
 
     1 to:methodsCount do:[:i |
-        Verbose ifTrue:[Transcript show:'method: '; showCR:i].
-        method := self readMethodFor:aJavaClass
+	Verbose ifTrue:[Transcript show:'method: '; showCR:i].
+	method := self readMethodFor:aJavaClass
     ].
 
     "
@@ -1382,6 +1386,6 @@
 !JavaClassReader class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaClassReader.st,v 1.48 1997/08/18 10:41:22 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaClassReader.st,v 1.49 1998/01/05 18:47:08 cg Exp $'
 ! !
 JavaClassReader initialize!
--- a/JavaConstantPool.st	Fri Aug 29 16:03:19 1997 +0000
+++ b/JavaConstantPool.st	Mon Jan 05 18:49:32 1998 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:3.3.1 on 4-jan-1998 at 4:22:53 pm'                   !
+
 Array subclass:#JavaConstantPool
 	instanceVariableNames:'owner'
 	classVariableNames:''
@@ -146,6 +148,17 @@
 
 !JavaConstantPool methodsFor:'special'!
 
+classReferencesDo:aBlock
+    self do:[:constItem |
+        constItem isJavaClass ifTrue:[
+            aBlock value:constItem
+        ] 
+    ]
+
+    "Modified: / 7.8.1997 / 19:17:38 / cg"
+    "Created: / 4.1.1998 / 00:40:11 / cg"
+!
+
 updateClassRefsFrom:oldClass to:newClass
 owner == oldClass ifTrue:[
     self halt.
@@ -186,5 +199,5 @@
 !JavaConstantPool class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaConstantPool.st,v 1.6 1997/08/19 13:29:23 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaConstantPool.st,v 1.7 1998/01/05 18:47:11 cg Exp $'
 ! !
--- a/JavaContext.st	Fri Aug 29 16:03:19 1997 +0000
+++ b/JavaContext.st	Mon Jan 05 18:49:32 1998 +0000
@@ -1,5 +1,7 @@
-Object subclass:#JavaContext
-	instanceVariableNames:'method class sender stack frameBase pc sp'
+'From Smalltalk/X, Version:3.3.1 on 5-jan-1998 at 2:09:56 pm'                   !
+
+Context subclass:#JavaContext
+	instanceVariableNames:'exArg byteCode constPool method'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Java-Support'
@@ -8,25 +10,75 @@
 
 !JavaContext methodsFor:'ST context mimicri'!
 
-argsAndVars
-    |nArgs nVars|
+argAt:n
+    |arg0Index|
+
+    self method isStatic ifTrue:[
+        arg0Index := 0
+    ] ifFalse:[
+        arg0Index := 1
+    ].
+    ^ self at:arg0Index+n
+
+    "Created: / 2.1.1998 / 17:54:13 / cg"
+    "Modified: / 2.1.1998 / 21:39:30 / cg"
+!
 
-    stack isNil ifTrue:[^ #()].
-    frameBase isNil ifTrue:[^ #()].
+argAt:n put:value
+    |arg0Index|
 
-    nArgs := method numArgs.
-    nVars := method numVars.
+    self method isStatic ifTrue:[
+        arg0Index := 0
+    ] ifFalse:[
+        arg0Index := 1
+    ].
+    ^ super argAt:arg0Index+n put:value
+
+    "Created: / 2.1.1998 / 17:54:34 / cg"
+    "Modified: / 2.1.1998 / 21:35:19 / cg"
+!
+
+args
+    "return an array filled with the arguments of this context"
+
+    |n arg1Index|
 
-    method isStatic ifTrue:[
-        (nArgs + nVars) == 0 ifTrue:[
-            ^ #()
-        ].
-        ^ (stack copyFrom:frameBase to:(frameBase + nArgs + nVars - 1)) asArray
+    n := self numArgs.
+    n == 0 ifTrue:[
+        "/ little optimization here - avaoid creating empty containers
+        ^ #()
+    ].
+
+    self method isStatic ifTrue:[
+        arg1Index := 1
+    ] ifFalse:[
+        arg1Index := 2
     ].
-    ^ (stack copyFrom:(frameBase+1) to:(frameBase + nArgs + nVars)) asArray
+    ^ (Array new:n) replaceFrom:1 to:n with:self startingAt:arg1Index.
+
+    "Created: / 2.1.1998 / 17:54:57 / cg"
+    "Modified: / 2.1.1998 / 21:34:44 / cg"
+!
+
+argsAndVars
+    "return an array filled with the arguments and variables of this context"
+
+    |n arg1Index|
 
-    "Created: 1.5.1996 / 17:32:44 / cg"
-    "Modified: 12.8.1997 / 22:04:39 / cg"
+    n := self numArgs + self numVars.
+    n == 0 ifTrue:[
+        "/ little optimization here - avaoid creating empty containers
+        ^ #()
+    ].
+    self method isStatic ifTrue:[
+        arg1Index := 1
+    ] ifFalse:[
+        arg1Index := 2
+    ].
+    ^ (Array new:n) replaceFrom:1 to:n with:self startingAt:arg1Index.
+
+    "Created: / 2.1.1998 / 17:55:14 / cg"
+    "Modified: / 2.1.1998 / 21:35:39 / cg"
 !
 
 canReturn
@@ -35,237 +87,169 @@
     "Created: 1.5.1996 / 15:05:36 / cg"
 !
 
-findNextContextWithSelector:sel1 or:sel2
-    sender isNil ifTrue:[^ nil].
-    ^ sender findNextContextWithSelector:sel1 or:sel2
-
-    "Created: 20.3.1997 / 13:54:01 / cg"
-!
+lineNumber
+    |nr pc|
 
-hasStackToShow
-    ^ true
-!
-
-isBlockContext
-    ^ false
-
-    "Created: 1.5.1996 / 15:05:26 / cg"
-!
-
-lineNumber
-    |nr|
+    pc := self pc.
 
 "/ 'ask line for pc:' print. pc printCR.
     pc isNil ifTrue:[" '-> 0 [a]' printCR. " ^0].
 
-    nr := method lineNumberForPC:pc.
+    nr := self method lineNumberForPC:pc.
     nr isNil ifTrue:[" '-> 0 [b]' printCR. " ^ 0].
 "/ '-> ' print. nr printCR.
      ^ nr.
 
-    "Created: 1.5.1996 / 15:05:47 / cg"
-    "Modified: 12.8.1997 / 02:39:44 / cg"
+    "Created: / 1.5.1996 / 15:05:47 / cg"
+    "Modified: / 4.1.1998 / 23:35:38 / cg"
 !
 
-methodClass
-    ^ class
+lineNumberFromMethod
+    |m|
+
+    m := self method.
+    m notNil ifTrue:[
+        ^ m lineNumber
+    ].
+    ^ nil
 
-    "Created: 1.5.1996 / 15:04:17 / cg"
+    "Created: / 4.1.1998 / 23:34:45 / cg"
+    "Modified: / 4.1.1998 / 23:35:55 / cg"
+!
+
+method
+    "the method may be found in the interpreter temps ..."
+
+    (method isMemberOf:JavaMethod) ifTrue:[^ method].
+    ^ super method
+
+    "Created: / 1.5.1996 / 15:03:43 / cg"
+    "Modified: / 2.1.1998 / 21:38:00 / cg"
 !
 
 methodHome
     ^ self
-
-    "Created: 1.5.1996 / 15:03:43 / cg"
 !
 
 numArgs
-    ^ method numArgs
-
-    "Created: 1.5.1996 / 15:04:35 / cg"
-!
-
-numVars
-    ^ 0
-
-    "Created: 1.5.1996 / 15:05:03 / cg"
-!
+    "return the number of args.
+     Redefined since Java keeps the receiver of a non-static method
+     at local slot 0."
 
-receiver
-    method isStatic ifTrue:[
-        ^ method javaClass
-    ].
-    frameBase > stack size ifTrue:[
-        ^ nil
-    ].
-"/ method displayString printCR.
-"/ frameBase print. ' -> ' print. (stack at:frameBase) printCR.
-    ^ stack at:frameBase
-
-    "Created: 1.5.1996 / 15:04:03 / cg"
-    "Modified: 4.8.1997 / 23:39:01 / cg"
-!
-
-selector            
-    ^ (method name , method signature) asSymbol "/ signatureName
-
-    "Created: 1.5.1996 / 15:03:03 / cg"
-!
-
-stack
-    ^ stack 
-!
-
-stackFrame
-sp < frameBase ifTrue:[
- 'oops - negative stackFrame' errorPrintCR.
- ^ #()
-].
-stack isNil ifTrue:[^ #()].
+    |n|
 
-"/ method displayString printCR.
-"/ frameBase print. ' ... ' print. (sp-1) printCR.
-"/ (stack collect:[:e | e class name]) printCR.
-
-"/    method isStatic ifFalse:[
-"/        ^ stack copyFrom:frameBase+1 to:(sp-1)
-"/    ].
-    ^ stack copyFrom:frameBase to:(sp-1)
-
-    "Modified: 12.8.1997 / 21:55:47 / cg"
-! !
-
-!JavaContext methodsFor:'accessing'!
-
-class:aJavaClass method:aJavaMethod sender:aContext stack:s frameBase:f
-    class := aJavaClass.
-    method := aJavaMethod.
-    sender := aContext.
-    stack := s.
-    frameBase := f
+    n := super numArgs.
+    self method isStatic ifFalse:[
+        n := n - 1
+    ].
+    ^ n
 
-    "Modified: 1.5.1996 / 17:39:34 / cg"
-    "Created: 1.5.1996 / 17:42:27 / cg"
-!
-
-class:aJavaClass method:aJavaMethod sender:aContext stack:s stackPointer:spp frameBase:f
-    class := aJavaClass.
-    method := aJavaMethod.
-    sender := aContext.
-    stack := s.
-    sp := spp.
-    frameBase := f
-
-    "Modified: 1.5.1996 / 17:39:34 / cg"
-    "Created: 1.5.1996 / 17:42:27 / cg"
-!
-
-method
-    ^ method.
-
-    "Created: 1.5.1996 / 15:00:23 / cg"
-    "Modified: 1.5.1996 / 15:00:47 / cg"
+    "Created: / 2.1.1998 / 22:21:24 / cg"
 !
 
 pc
-    ^ pc
-!
-
-sender
-    ^ sender.
+    lineNr isNil ifTrue:[^ nil].
+    ^ super lineNumber
 
-    "Modified: 1.5.1996 / 15:00:47 / cg"
-    "Created: 1.5.1996 / 15:01:18 / cg"
-!
-
-setPC:anInteger
-    pc := anInteger
+    "Created: / 4.1.1998 / 23:33:48 / cg"
 !
 
-setPC:pcInteger SP:spInteger
-    pc := pcInteger.
-    sp := spInteger.
+selector
+    "the selector can be extracted from the method.
+     the method may be found in the interpreter temps ..."
+
+    |s m|
+
+    selector isNil ifTrue:[
+	m := self method.
+	m notNil ifTrue:[
+	    ^ m name
+	]
+    ].
+    ^ super selector
+
+    "Modified: / 30.12.1997 / 17:22:06 / cg"
+    "Created: / 30.12.1997 / 17:23:47 / cg"
 !
 
-setSP:anInteger
-    sp := anInteger
-!
+setPC:newPC
+    lineNr := newPC
+
+    "Created: / 5.1.1998 / 00:09:02 / cg"
+! !
+
+!JavaContext methodsFor:'exception handler support'!
 
-setStack:aCollection
-    stack := aCollection
-!
+markForException
+    "set the exception handler flag in the receiver.
+     The JVM needs this to enter an exception handler instead of restarting
+     from the beginning (when the context is restarted).
+     - a highly internal mechanism and not for public use."
 
-sp
-    ^ sp
+%{  /* NOCONTEXT */
+     __INST(flags) = (OBJ)((INT)__INST(flags) | __MASKSMALLINT(__JAVA_EX_PEND));
+%}
+
+    "Modified: 13.12.1995 / 19:05:22 / cg"
 ! !
 
 !JavaContext methodsFor:'printing & storing'!
 
-printString
-    |nm mS recCls rec recClsName rnm|
+receiverPrintString
+    "return a string describing the receiver of the context" 
 
-    "/ the methods class
-    nm := class fullName.
-    (nm startsWith:'java/lang/') ifTrue:[
-        nm := class name
-    ] ifFalse:[
-        (nm startsWith:'java.lang.') ifTrue:[
-            nm := class name
-        ].
-    ].
-    "/ to avoid confusion with corresponding smalltalk classes ...
-    (Smalltalk includesKey:(nm asSymbol)) ifTrue:[
-        nm := class fullName "/ 'JAVA-' , nm
-    ].
-    nm := nm asString copy replaceAll:$/ by:$..
-
-    "/ the receivers class
-    rec := self receiver.
-    recCls := rec class.
+    |receiverClass receiverClassName newString implementorClass|
 
-    (rec isKindOf:JavaObject) ifFalse:[
-        (rec isKindOf:JavaClass) ifTrue:[
-            "/ static message
-            rnm := recCls name , '[static]'
-        ] ifFalse:[
-            rnm := '[' , recCls name , ']'
-        ]
-    ] ifTrue:[
-        recClsName := recCls name.
-        (Smalltalk includesKey:(recClsName asSymbol)) ifTrue:[
-            rnm := recCls fullName "/ 'JAVA-' , recClsName
-        ] ifFalse:[
-            (recCls fullName startsWith:'java/lang/') ifTrue:[
-                rnm := recClsName
-            ] ifFalse:[
-                rnm := recCls fullName
-            ].
-        ].
-    ].
-    rnm := rnm asString copy replaceAll:$/ by:$..
+%{
+    /*
+     * special handling for (invalid) free objects.
+     * these only appear if some primitiveCode does not correctly use SEND macros,
+     * which may lead to sends to free objects. In normal operation, this 'cannot' happen.
+     */ 
+    if (__isNonNilObject(__INST(receiver)) && (__qClass(__INST(receiver))==nil)) {
+	receiverClassName = __MKSTRING("FreeObject");
+    }
+%}.
+    receiverClassName notNil ifTrue:[^ receiverClassName].
 
-    recCls ~~ class ifTrue:[
-        ^ rnm , '>>' , nm , '::' , method signatureName
+    receiverClass := receiver class.
+    receiverClassName := receiverClass name.
+    (receiverClass == SmallInteger) ifTrue:[
+	newString := '(' , receiver printString , ') ' , receiverClassName
     ] ifFalse:[
-        ^ rnm , '::' , method signatureName
+	newString := receiverClassName
     ].
 
-"/ OLD:
-    mS := nm , '::' , method signatureName.
-
-    (rnm ~= nm) ifTrue:[
-        rnm := rnm asString copy replaceAll:$/ by:$..
-        ^ rnm , '>>' , mS
+    "
+     kludge to avoid slow search for containing class
+    "
+    (selector ~~ #doIt and:[selector ~~ #doIt:]) ifTrue:[
+	implementorClass := self methodClass. 
+    ].
+    implementorClass notNil ifTrue: [
+	(implementorClass ~~ receiverClass) ifTrue: [
+	    newString := newString , '>>>',
+			 implementorClass name printString
+	]
+    ] ifFalse:[
+	self searchClass ~~ receiverClass ifTrue:[
+	    newString := newString , '>>>' , self searchClass name
+	].
+"/        "
+"/         kludge for doIt - these unbound methods are not
+"/         found in the classes methodDictionary
+"/        "
+"/        (selector ~~ #doIt and:[selector ~~ #doIt:]) ifTrue:[
+"/            newString := newString , '>>>**NONE**'
+"/        ]
     ].
 
-    ^ mS
+    ^ newString
 
-    "Created: 1.5.1996 / 15:07:43 / cg"
-    "Modified: 16.8.1997 / 01:44:50 / cg"
 ! !
 
 !JavaContext class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaContext.st,v 1.17 1997/08/18 10:38:22 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaContext.st,v 1.18 1998/01/05 18:47:12 cg Exp $'
 ! !
--- a/JavaDecompiler.st	Fri Aug 29 16:03:19 1997 +0000
+++ b/JavaDecompiler.st	Mon Jan 05 18:49:32 1998 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:3.3.1 on 5-jan-1998 at 2:09:45 pm'                   !
+
 Object subclass:#JavaDecompiler
 	instanceVariableNames:'code pc javaMethod outStream classToCompileFor'
 	classVariableNames:'DecoderTable'
@@ -328,7 +330,7 @@
 
     pckgName := aJavaClass package.
     pckgName ~= aJavaClass name ifTrue:[
-        s nextPutAll:'package ' , (pckgName copy replaceAll:$/ by:$.).
+        s nextPutAll:'package ' , (pckgName copy replaceAll:$/ with:$.).
         s nextPutAll:';'; cr; cr.
     ].
 
@@ -651,7 +653,7 @@
             op := spec at:1
         ].
         outStream 
-            show:((pc - 1) printStringPaddedTo:4); 
+            show:((pc - 1 - 1) printStringPaddedTo:4); 
             show:' '; 
             show:op; 
             show:' '.
@@ -674,8 +676,8 @@
         outStream cr.
     ]
 
-    "Created: 16.4.1996 / 14:59:29 / cg"
-    "Modified: 4.8.1997 / 19:14:04 / cg"
+    "Created: / 16.4.1996 / 14:59:29 / cg"
+    "Modified: / 5.1.1998 / 00:04:03 / cg"
 ! !
 
 !JavaDecompiler methodsFor:'operand decoding'!
@@ -791,7 +793,7 @@
                   show:' -> ';
                   show:delta;
                   show:' [';
-                  show:(pc0 + delta);
+                  show:(pc0 - 1 + delta);
                   show:']';
                   cr.
     ].
@@ -801,8 +803,10 @@
               show:' -> ';
               show:defaultOffset;
               show:' [';
-              show:(pc0 + defaultOffset);
+              show:(pc0 - 1 + defaultOffset);
               show:']'.
+
+    "Modified: / 5.1.1998 / 00:33:57 / cg"
 !
 
 nargsByte
@@ -839,13 +843,13 @@
     outStream
         show:index; 
         show:' ['; 
-        show:(pc + index - 1); 
+        show:(pc - 1 + index - 1); 
         show:']'.
 
     pc := pc + 2.
 
-    "Created: 16.4.1996 / 15:00:04 / cg"
-    "Modified: 16.4.1996 / 15:30:55 / cg"
+    "Created: / 16.4.1996 / 15:00:04 / cg"
+    "Modified: / 5.1.1998 / 00:34:14 / cg"
 !
 
 signedByte
@@ -900,7 +904,7 @@
                   show:' -> ';
                   show:delta;
                   show:' [';
-                  show:(pc0 + delta);
+                  show:(pc0 - 1 + delta);
                   show:']';
                   cr.
     ].
@@ -910,10 +914,10 @@
               show:' -> ';
               show:defaultOffset;
               show:' [';
-              show:(pc0 + defaultOffset);
+              show:(pc0 - 1 + defaultOffset);
               show:']'.
 
-
+    "Modified: / 5.1.1998 / 00:33:46 / cg"
 !
 
 unsignedByte
@@ -946,6 +950,6 @@
 !JavaDecompiler class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaDecompiler.st,v 1.30 1997/08/18 10:39:14 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaDecompiler.st,v 1.31 1998/01/05 18:47:13 cg Exp $'
 ! !
 JavaDecompiler initialize!
--- a/JavaFieldref.st	Fri Aug 29 16:03:19 1997 +0000
+++ b/JavaFieldref.st	Mon Jan 05 18:49:32 1998 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:3.3.1 on 2-jan-1998 at 6:37:23 pm'                   !
+
 JavaRef subclass:#JavaFieldref
 	instanceVariableNames:'offset type'
 	classVariableNames:''
@@ -24,10 +26,10 @@
 
 displayString
     class isNil ifTrue:[
-        ^ 'JavaFieldRef ( ** unknown class ** ''' , nameandType displayString , ''')'
+	^ 'JavaFieldRef ( ** unknown class ** ''' , nameandType displayString , ''')'
     ].
     ^ 'JavaFieldRef (' , class fullName , ' ' 
-                        , '''' , nameandType name , '''' , nameandType signature , ')'
+			, '''' , nameandType name , '''' , nameandType signature , ')'
 ! !
 
 !JavaFieldref methodsFor:'resolving'!
@@ -45,6 +47,64 @@
 !
 
 offset
+    offset notNil ifTrue:[^ offset].
+    self resolve.
+    ^ offset.
+
+    "Modified: / 1.1.1998 / 19:20:23 / cg"
+!
+
+resolve
+    |nm sig cls|
+
+    class isUnresolved ifTrue:[
+	self halt:'unresolved class'.
+    ].
+
+    nm := nameandType name asSymbol.
+    sig := nameandType signature.
+
+    type := JavaMethod typeFromSignature:sig.
+    offset := class instVarOffsetOf:nm.
+
+    "Modified: / 1.1.1998 / 19:19:52 / cg"
+!
+
+resolveStatic
+    |nm sig mthd cls|
+
+    cls := class javaClass.
+    cls ~~ class ifTrue:[
+        class := cls.
+    ].
+
+    nm := nameandType name asSymbol.
+    sig := nameandType signature.
+
+    type := JavaMethod typeFromSignature:sig.
+    offset := class class instVarOffsetOf:nm.
+
+    "Created: / 2.1.1998 / 17:16:55 / cg"
+    "Modified: / 2.1.1998 / 17:17:22 / cg"
+!
+
+staticOffset
+    offset notNil ifTrue:[^ offset].
+    self resolveStatic.
+    ^ offset.
+
+    "Modified: / 2.1.1998 / 17:17:47 / cg"
+!
+
+type
+    type notNil ifTrue:[^ type].
+    self resolve.
+    ^ type.
+
+    "Modified: / 1.1.1998 / 19:20:37 / cg"
+!
+
+xxoffset
     |nm sig cls|
 
     offset notNil ifTrue:[^ offset].
@@ -58,7 +118,7 @@
 "/        ].
 "/    ].
     class isUnresolved ifTrue:[
-        self halt:'unresolved class'.
+	self halt:'unresolved class'.
     ].
 
     nm := nameandType name asSymbol.
@@ -69,33 +129,7 @@
     ^ offset.
 !
 
-staticOffset
-    |nm sig mthd cls|
-
-    offset notNil ifTrue:[^ offset].
-
-    cls := class javaClass.
-    cls ~~ class ifTrue:[
-        class := cls.
-    ].
-"/    (class isMemberOf:JavaUnresolvedClassConstant) ifTrue:[
-"/        cls := class resolve.
-"/        cls notNil ifTrue:[
-"/            class := cls
-"/        ]
-"/    ].
-"/    (class isMemberOf:JavaUnresolvedClassConstant) ifTrue:[
-"/        self halt:'unresolved class'.
-"/    ].
-
-    nm := nameandType name asSymbol.
-    sig := nameandType signature.
-
-    offset := class class instVarOffsetOf:nm.
-    ^ offset.
-!
-
-type
+xxtype
     |sig cls|
 
     type notNil ifTrue:[^ type].
@@ -109,7 +143,7 @@
 "/        ]
 "/    ].
     class isUnresolved ifTrue:[
-        self halt:'unresolved class'.
+	self halt:'unresolved class'.
     ].
 
     sig := nameandType signature.
@@ -120,5 +154,5 @@
 !JavaFieldref class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaFieldref.st,v 1.14 1997/08/19 13:29:42 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaFieldref.st,v 1.15 1998/01/05 18:47:25 cg Exp $'
 ! !
--- a/JavaMethod.st	Fri Aug 29 16:03:19 1997 +0000
+++ b/JavaMethod.st	Mon Jan 05 18:49:32 1998 +0000
@@ -1,8 +1,12 @@
+'From Smalltalk/X, Version:3.3.1 on 5-jan-1998 at 3:01:18 pm'                   !
+
 CompiledCode subclass:#JavaMethod
-	instanceVariableNames:'numArgs numLocals returnType accessFlags name signature
-		exceptionHandlerTable exceptionTable lineNumberTable
-		localVariableTable javaClass numStack isNOOPMethod'
-	classVariableNames:'SignatureTypeCodes ForceByteCodeDisplay'
+	instanceVariableNames:'accessFlags selector javaClass exceptionHandlerTable
+		exceptionTable numLocals returnType signature lineNumberTable
+		localVariableTable isNOOPMethod'
+	classVariableNames:'SignatureTypeCodes ForceByteCodeDisplay A_PUBLIC A_PRIVATE
+		A_PROTECTED A_STATIC A_FINAL A_SYNCHRONIZED A_ABSTRACT A_NATIVE
+		R_VOID R_LONG R_DOUBLE'
 	poolDictionaries:''
 	category:'Java-Classes'
 !
@@ -11,6 +15,19 @@
 !JavaMethod class methodsFor:'initialization'!
 
 initialize
+    A_PUBLIC       := 16r0001.
+    A_PRIVATE      := 16r0002.
+    A_PROTECTED    := 16r0004.
+    A_STATIC       := 16r0008.
+    A_FINAL        := 16r0010.
+    A_SYNCHRONIZED := 16r0020.
+    A_NATIVE       := 16r0100.
+    A_ABSTRACT     := 16r0400.
+
+    R_VOID         := 16r100000.
+    R_LONG         := 16r200000.
+    R_DOUBLE       := 16r300000.
+
     self flags:(self flags bitOr:Behavior flagJavaMethod).
 
     SignatureTypeCodes := IdentityDictionary new.
@@ -72,8 +89,8 @@
 "/        s peek == Character space ifTrue:[
 "/            s next
 "/        ] ifFalse:[
-            argSpec := self fieldTypeFromStream:s.
-            spec := spec copyWith:argSpec.
+	    argSpec := self fieldTypeFromStream:s.
+	    spec := spec copyWith:argSpec.
 "/        ]
     ].
     ^ spec
@@ -113,11 +130,11 @@
 "/        s peek == Character space ifTrue:[
 "/            s next
 "/        ] ifFalse:[
-            argSpec := self fieldTypeFromStream:s.
-            spec size ~~ 0 ifTrue:[
-                spec := spec , ' '
-            ].
-            spec := spec , argSpec.
+	    argSpec := self fieldTypeFromStream:s.
+	    spec size ~~ 0 ifTrue:[
+		spec := spec , ' '
+	    ].
+	    spec := spec , argSpec.
 "/        ]
     ].
     ^ spec
@@ -135,11 +152,11 @@
 "/        s peek == Character space ifTrue:[
 "/            s next
 "/        ] ifFalse:[
-            argSpec := self fieldTypeFromStream:s in:aPackage.
-            spec size ~~ 0 ifTrue:[
-                spec := spec , ' '
-            ].
-            spec := spec , argSpec.
+	    argSpec := self fieldTypeFromStream:s in:aPackage.
+	    spec size ~~ 0 ifTrue:[
+		spec := spec , ' '
+	    ].
+	    spec := spec , argSpec.
 "/        ]
     ].
     ^ spec
@@ -155,13 +172,13 @@
     argNr := 1.
     spec := ''.
     [s atEnd or:[s peek == $)]] whileFalse:[
-        argSpec := self fieldTypeFromStream:s in:aPackage.
-        spec size ~~ 0 ifTrue:[
-            spec := spec , ', '
-        ].
-        spec := spec , argSpec.
-        spec := spec , ' arg' , argNr printString.
-        argNr := argNr + 1.
+	argSpec := self fieldTypeFromStream:s in:aPackage.
+	spec size ~~ 0 ifTrue:[
+	    spec := spec , ', '
+	].
+	spec := spec , argSpec.
+	spec := spec , ' arg' , argNr printString.
+	argNr := argNr + 1.
     ].
     ^ spec
 
@@ -181,24 +198,24 @@
     typeSym := SignatureTypeCodes at:typeChar ifAbsent:#unknown.
 
     typeSym == #unknown ifTrue:[
-        ^ typeSym
+	^ typeSym
     ].
     typeSym == #object ifTrue:[
-        className := s upTo:$;.
-        "/ strip off default
+	className := s upTo:$;.
+	"/ strip off default
 "/        (className startsWith:'java/lang/') ifTrue:[
 "/            ^ className copyFrom:11
 "/        ].
-        ^ className copy replaceAll:$/ by:$.
+	^ className copy replaceAll:$/ with:$.
     ].
     typeSym == #array ifTrue:[
-        s peek isDigit ifTrue:[
-            size := Integer readFrom:s.
-            elType := self fieldTypeFromStream:s.
-            ^ elType , '[' , size printString , ']'
-        ].
-        elType := self fieldTypeFromStream:s.
-        ^ elType , '[]'
+	s peek isDigit ifTrue:[
+	    size := Integer readFrom:s.
+	    elType := self fieldTypeFromStream:s.
+	    ^ elType , '[' , size printString , ']'
+	].
+	elType := self fieldTypeFromStream:s.
+	^ elType , '[]'
     ].
     ^ typeSym
 
@@ -215,31 +232,31 @@
     typeSym := SignatureTypeCodes at:typeChar ifAbsent:#unknown.
 
     typeSym == #unknown ifTrue:[
-        ^ typeSym
+	^ typeSym
     ].
     typeSym == #object ifTrue:[
-        className := s upTo:$;.
-        "/ strip off default
+	className := s upTo:$;.
+	"/ strip off default
 
-        nm := className.
-        aPackage notNil ifTrue:[
-            (nm startsWith:aPackage) ifTrue:[
-                nm := nm copyFrom:(aPackage size + 2).
-            ].
-        ].
+	nm := className.
+	aPackage notNil ifTrue:[
+	    (nm startsWith:aPackage) ifTrue:[
+		nm := nm copyFrom:(aPackage size + 2).
+	    ].
+	].
         
-        nm := nm copy replaceAll:$/ by:$..
-        ^ nm
+	nm := nm copy replaceAll:$/ with:$..
+	^ nm
     ].
 
     typeSym == #array ifTrue:[
-        s peek isDigit ifTrue:[
-            size := Integer readFrom:s.
-            elType := self fieldTypeFromStream:s in:aPackage.
-            ^ elType , '[' , size printString , ']'
-        ].
-        elType := self fieldTypeFromStream:s in:aPackage.
-        ^ elType , '[]'
+	s peek isDigit ifTrue:[
+	    size := Integer readFrom:s.
+	    elType := self fieldTypeFromStream:s in:aPackage.
+	    ^ elType , '[' , size printString , ']'
+	].
+	elType := self fieldTypeFromStream:s in:aPackage.
+	^ elType , '[]'
     ].
 
     ^ typeSym
@@ -272,19 +289,19 @@
 
     n := 0.
     [s atEnd or:[s peek == $)]] whileFalse:[
-        t := self fieldTypeFromStream:s.
-        "/
-        "/ some args count as 2
-        "/
-        t == #long ifTrue:[
-            n := n + 2.
-        ] ifFalse:[
-            t == #double ifTrue:[
-                n := n + 2
-            ] ifFalse:[
-                n := n + 1.
-            ]
-        ]
+	t := self fieldTypeFromStream:s.
+	"/
+	"/ some args count as 2
+	"/
+	t == #long ifTrue:[
+	    n := n + 2.
+	] ifFalse:[
+	    t == #double ifTrue:[
+		n := n + 2
+	    ] ifFalse:[
+		n := n + 1.
+	    ]
+	]
     ].
     ^ n
 !
@@ -349,12 +366,12 @@
 
     s := aSignature readStream.
     (c := s peek) ~~ $( ifTrue:[
-        c == $' ifTrue:[
-           [s peek ~= $'] whileTrue:[s next].
-           s next.
-           ^ (self retvalSpecFromStream:s)
-        ].
-        ^ (self retvalSpecFromStream:s)
+	c == $' ifTrue:[
+	   [s peek ~= $'] whileTrue:[s next].
+	   s next.
+	   ^ (self retvalSpecFromStream:s)
+	].
+	^ (self retvalSpecFromStream:s)
     ].
 
     s next.
@@ -380,12 +397,12 @@
 
     s := aSignature readStream.
     (c := s peek) ~~ $( ifTrue:[
-        c == $' ifTrue:[
-           [s peek ~= $'] whileTrue:[s next].
-           s next.
-           ^ (self retvalSpecFromStream:s in:aPackage)
-        ].
-        ^ (self retvalSpecFromStream:s in:aPackage)
+	c == $' ifTrue:[
+	   [s peek ~= $'] whileTrue:[s next].
+	   s next.
+	   ^ (self retvalSpecFromStream:s in:aPackage)
+	].
+	^ (self retvalSpecFromStream:s in:aPackage)
     ].
 
     s next.
@@ -589,13 +606,13 @@
 
     s := aSignature readStream.
     (c := s peek) ~~ $( ifTrue:[
-        c == $' ifTrue:[
-           s next.
-           [s peek ~= $'] whileTrue:[s next].
-           s next.
-           ^ (self retvalSpecFromStream:s)
-        ].
-        ^ (self retvalSpecFromStream:s)
+	c == $' ifTrue:[
+	   s next.
+	   [s peek ~= $'] whileTrue:[s next].
+	   s next.
+	   ^ (self retvalSpecFromStream:s)
+	].
+	^ (self retvalSpecFromStream:s)
     ].
 
     s next.
@@ -623,13 +640,13 @@
 
     s := aSignature readStream.
     (c := s peek) ~~ $( ifTrue:[
-        c == $' ifTrue:[
-           s next.
-           [s peek ~= $'] whileTrue:[s next].
-           s next.
-           ^ (self retvalSpecFromStream:s in:package)
-        ].
-        ^ (self retvalSpecFromStream:s in:package)
+	c == $' ifTrue:[
+	   s next.
+	   [s peek ~= $'] whileTrue:[s next].
+	   s next.
+	   ^ (self retvalSpecFromStream:s in:package)
+	].
+	^ (self retvalSpecFromStream:s in:package)
     ].
 
     s next.
@@ -728,6 +745,7 @@
 !
 
 lineNumber
+    lineNumberTable isNil ifTrue:[^ nil].
     ^ lineNumberTable at:2
 
     "Created: 16.4.1996 / 12:34:04 / cg"
@@ -757,61 +775,54 @@
 !
 
 methodArgNames
+    |nA|
+
+    nA := self numArgs.
     localVariableTable notNil ifTrue:[
-        ^ (1 to:self numArgs) collect:
-            [:argIndex | |slot name|
-                "/ search for an entry with that index (slot),
-                "/ which has is valid at PC 0
+	^ (1 to:nA) collect:
+	    [:argIndex | 
+		|slot name|
+		"/ search for an entry with that index (slot),
+		"/ which has is valid at PC 0
 
-                self isStatic ifTrue:[
-                    slot := argIndex
-                ] ifFalse:[
-                    slot := argIndex + 1
-                ].
-                name := localVariableTable nameForSlot:slot atPC:0.
-                name isNil ifTrue:[
-                    'arg' , argIndex printString
-                ] ifFalse:[
-                    name
-                ].
-            ]
+		self isStatic ifTrue:[
+		    slot := argIndex
+		] ifFalse:[
+		    slot := argIndex + 1
+		].
+		name := localVariableTable nameForSlot:slot atPC:0.
+		name isNil ifTrue:[
+		    'arg' , argIndex printString
+		] ifFalse:[
+		    name
+		].
+	    ]
     ].
-    ^ (1 to:self numArgs) collect:[:i | 'arg' , i printString]
+    ^ (1 to:nA) collect:[:i | 'arg' , i printString]
 !
 
 name
-    ^ name
+    ^ (selector copyWithoutLast:signature size) asSymbol
 
     "Created: 16.4.1996 / 11:34:22 / cg"
 !
 
-numArgs
-    numArgs isNil ifTrue:[^ 0].
-    ^ numArgs
-!
+numLocals
+    ^super numVars.
+"/    numLocals isNil ifTrue:[^ 0].
+"/    ^ numLocals
 
-numLocals
-    numLocals isNil ifTrue:[^ 0].
-    ^ numLocals
+    "Modified: / 3.1.1998 / 21:15:38 / cg"
 !
 
 numStack
-    numStack isNil ifTrue:[^ 0].
-    ^ numStack
+    ^super stackSize.
+"/    numStack isNil ifTrue:[^ 0].
+"/    ^ numStack
 !
 
 numVars
-    numLocals isNil ifTrue:[^ 0].
-    numArgs isNil ifTrue:[^ numLocals].
-    ^ numLocals - numArgs
-!
-
-numberOfArgs:n
-    super numberOfArgs:n.
-    numArgs := n
-
-    "Modified: 30.7.1997 / 12:43:00 / cg"
-    "Created: 1.8.1997 / 00:26:24 / cg"
+    ^ self numLocals - self numArgs
 !
 
 previousVersion
@@ -850,8 +861,10 @@
 setCode:codeBytes maxStack:max_stack maxLocals:max_locals u1:unknown1 u2:unknown2
 "/    javaByteCode := codeBytes.
     byteCode := codeBytes.
-    numStack := max_stack.
-    numLocals := max_locals.
+    "/ numStack := max_stack.
+    "/ numLocals := max_locals.
+    super numberOfVars:max_locals.
+    super stackSize:max_stack.
 
 "/    self displayString printNL.
 "/    '   nStack: ' print. numStack print. 
@@ -889,34 +902,34 @@
     allBytes := allWords := true.
 
     anArrayOfPCtoLineAssociations do:[:assoc |
-        assoc key > 255 ifTrue:[
-            allBytes := false.
-            assoc key > 16rFFFF ifTrue:[
-                allWords := false.
-            ].
-        ].
-        assoc value > 255 ifTrue:[
-            allBytes := false.
-            assoc value > 16rFFFF ifTrue:[
-                allWords := false
-            ].
-        ].
+	assoc key > 255 ifTrue:[
+	    allBytes := false.
+	    assoc key > 16rFFFF ifTrue:[
+		allWords := false.
+	    ].
+	].
+	assoc value > 255 ifTrue:[
+	    allBytes := false.
+	    assoc value > 16rFFFF ifTrue:[
+		allWords := false
+	    ].
+	].
     ].
     allBytes ifTrue:[
-        lineNumberTable := ByteArray new:(anArrayOfPCtoLineAssociations size * 2).
+	lineNumberTable := ByteArray new:(anArrayOfPCtoLineAssociations size * 2).
     ] ifFalse:[
-        allWords ifTrue:[
-            lineNumberTable := WordArray new:(anArrayOfPCtoLineAssociations size * 2).
-        ] ifFalse:[
-            lineNumberTable := Array new:(anArrayOfPCtoLineAssociations size * 2).
-        ]
+	allWords ifTrue:[
+	    lineNumberTable := WordArray new:(anArrayOfPCtoLineAssociations size * 2).
+	] ifFalse:[
+	    lineNumberTable := Array new:(anArrayOfPCtoLineAssociations size * 2).
+	]
     ].
 
     idx := 1.
     anArrayOfPCtoLineAssociations do:[:assoc |
-        lineNumberTable at:idx   put:assoc key.
-        lineNumberTable at:idx+1 put:assoc value.
-        idx := idx + 2.
+	lineNumberTable at:idx   put:assoc key.
+	lineNumberTable at:idx+1 put:assoc value.
+	idx := idx + 2.
     ].
 
     "Created: 16.4.1996 / 12:34:04 / cg"
@@ -927,10 +940,9 @@
      localVariableTable := anArray.
 !
 
-setName:aString
-    name := aString asSymbol.
-
-    "Created: 16.4.1996 / 11:34:22 / cg"
+setName:nameString signature:signatureString
+    selector := (nameString , signatureString) asSymbol.
+    self setSignature:signatureString
 !
 
 setSignature:aString
@@ -939,6 +951,21 @@
     self numberOfArgs:(self class numArgsFromSignature:aString).
     returnType := self class typeFromSignature:aString.
 
+    "/ for the convenience of the VM, also mirror the return type in
+    "/ the flags ...
+
+    returnType == #void ifTrue:[
+	accessFlags := accessFlags bitOr:R_VOID
+    ] ifFalse:[
+	returnType == #long ifTrue:[
+	    accessFlags := accessFlags bitOr:R_LONG
+	] ifFalse:[
+	    returnType == #double ifTrue:[
+		accessFlags := accessFlags bitOr:R_DOUBLE
+	    ]
+	]
+    ].
+
     "Created: 16.4.1996 / 11:34:29 / cg"
     "Modified: 1.8.1997 / 00:26:16 / cg"
 !
@@ -952,9 +979,9 @@
 source
     |classSource|
 
-    self isNative ifTrue:[
-        ^ 'native method'
-    ].
+"/    self isNative ifTrue:[
+"/        ^ 'native method'
+"/    ].
 
     ForceByteCodeDisplay == true ifTrue:[
         ^ self decompiledBytecode
@@ -967,7 +994,7 @@
 
     ^ self decompiledSource
 
-    "Modified: 14.8.1997 / 04:34:15 / cg"
+    "Modified: / 4.1.1998 / 13:48:35 / cg"
 !
 
 sourceFilename
@@ -976,11 +1003,11 @@
 
 sourceLineNumber
     ForceByteCodeDisplay == true ifTrue:[
-        ^ 1
+	^ 1
     ].
 
     lineNumberTable notNil ifTrue:[
-        ^ lineNumberTable at:2
+	^ lineNumberTable at:2
     ].
 
     ^ 1
@@ -992,8 +1019,8 @@
 !JavaMethod methodsFor:'decompiling'!
 
 decompileSourceTo:aStream
-    self isNative ifFalse:[
-        self isAbstract ifFalse:[
+"/    self isNative ifFalse:[
+"/        self isAbstract ifFalse:[
             aStream cr; cr.
             aStream nextPutAll:'decompiled source:'; cr; cr.
             SignalSet anySignal handle:[:ex |
@@ -1006,12 +1033,11 @@
             ] do:[
                 aStream nextPutAll:(JavaDeparser decompile:self).
             ].
-        ].
-    ].
-    ^ true
+"/        ].
+"/    ].
 
-    "Modified: 30.7.1997 / 16:19:28 / cg"
-    "Created: 30.7.1997 / 16:28:09 / cg"
+    "Created: / 30.7.1997 / 16:28:09 / cg"
+    "Modified: / 4.1.1998 / 13:50:25 / cg"
 !
 
 decompiler
@@ -1035,31 +1061,31 @@
 
     code := self javaByteCode.
     code notNil ifTrue:[
-        insn1 := code at:1.
-        insn1 == 177 "RETURN" ifTrue:[
-            'JAVA [info]: dummy static method: ' print. self displayString printCR.
-            isNOOPMethod := true.
-            ^ self
-        ].
+	insn1 := code at:1.
+	insn1 == 177 "RETURN" ifTrue:[
+	    'JAVA [info]: dummy static method: ' print. self displayString printCR.
+	    isNOOPMethod := true.
+	    ^ self
+	].
 
-        insn1 == 42 "ALOAD_0" ifTrue:[
-            insn2 := code at:2.
-            insn2 == 183 "INVOKENONVIRTUAL" ifTrue:[
-                insn3 := code at:5.
-                insn3 == 177 "RETURN" ifTrue:[
-                    idx := code wordAt:3 MSB:true.
-                    ref := javaClass constantPool at:idx.
-                    mthd := ref method.
-                    mthd isNOOPMethod ifTrue:[
-                        'JAVA [info]: dummy method (calls dummy): ' print. self displayString printCR.
-                        isNOOPMethod := true.
-                    ] ifFalse:[
-                        isNOOPMethod := false.
-                    ].
-                    ^ self
-                ]
-            ].
-        ].
+	insn1 == 42 "ALOAD_0" ifTrue:[
+	    insn2 := code at:2.
+	    insn2 == 183 "INVOKENONVIRTUAL" ifTrue:[
+		insn3 := code at:5.
+		insn3 == 177 "RETURN" ifTrue:[
+		    idx := code wordAt:3 MSB:true.
+		    ref := javaClass constantPool at:idx.
+		    mthd := ref method.
+		    mthd isNOOPMethod ifTrue:[
+			'JAVA [info]: dummy method (calls dummy): ' print. self displayString printCR.
+			isNOOPMethod := true.
+		    ] ifFalse:[
+			isNOOPMethod := false.
+		    ].
+		    ^ self
+		]
+	    ].
+	].
     ].
     isNOOPMethod := false.
     ^ self
@@ -1068,18 +1094,29 @@
     "Modified: 1.8.1997 / 00:09:42 / cg"
 ! !
 
+!JavaMethod methodsFor:'native methods'!
+
+nativeMethodInvokation
+    ^ JavaVM 
+        perform:('_' , self javaClass name , '_' , self method name , ':') asSymbol
+        with:thisContext sender.
+
+    "Created: / 1.1.1998 / 15:16:14 / cg"
+    "Modified: / 4.1.1998 / 14:23:10 / cg"
+! !
+
 !JavaMethod methodsFor:'printing & storing'!
 
 displayString
     javaClass isNil ifTrue:[
-        ^ 'JavaMethod(???)'
+	^ 'JavaMethod(???)'
     ].
     ^ 'JavaMethod(' , javaClass name , '::' , self signatureName , ')'
 
     "Modified: 7.4.1997 / 15:54:10 / cg"
 !
 
-printStringForBrowserWithSelector:selector
+printStringForBrowserWithSelector:dummySelector
 "/    self isStatic ifTrue:[
 "/        ^ 'static ' , self signatureName
 "/    ].
@@ -1087,8 +1124,8 @@
 "/        ^ (LabelAndIcon '!! ' , self signatureName
 "/    ].
 
-    name = #'<init>' ifTrue:[
-        ^ self class specTextFromSignature:signature withName:(javaClass name).
+    self name = #'<init>' ifTrue:[
+	^ self class specTextFromSignature:signature withName:(javaClass name).
     ].
     ^ self signatureNameText
 
@@ -1102,7 +1139,7 @@
 signatureName
     "return a string to be used when browsing"
 
-    ^ self class specFromSignature:signature withName:name
+    ^ self class specFromSignature:signature withName:(self name)
 !
 
 signatureNameFor:name withArgsIn:aPackage
@@ -1116,7 +1153,7 @@
 signatureNameIn:aPackage
     "return a string to be used when browsing"
 
-    ^ self class specFromSignature:signature withName:name in:aPackage
+    ^ self class specFromSignature:signature withName:(self name) in:aPackage
 
     "Created: 18.3.1997 / 11:11:01 / cg"
 !
@@ -1124,7 +1161,7 @@
 signatureNameText
     "return a text to be used when browsing"
 
-    ^ self class specTextFromSignature:signature withName:name
+    ^ self class specTextFromSignature:signature withName:(self name)
 
     "Created: 30.7.1997 / 14:40:29 / cg"
 !
@@ -1141,7 +1178,7 @@
 signatureNameWithArgsIn:aPackage
     "return a string to be used when browsing"
 
-    ^ self class specWithArgsFromSignature:signature withName:name in:aPackage
+    ^ self class specWithArgsFromSignature:signature withName:(self name) in:aPackage
 
     "Created: 20.3.1997 / 12:44:17 / cg"
 !
@@ -1149,7 +1186,7 @@
 signatureNameWithoutReturnType
     "return a string to be used when browsing"
 
-    ^ self class argSpecFromSignature:signature withName:name
+    ^ self class argSpecFromSignature:signature withName:(self name)
 
 ! !
 
@@ -1158,10 +1195,10 @@
 handlerFor:anException at:pc
     exceptionHandlerTable isNil ifTrue:[^ nil].
     exceptionHandlerTable do:[:entry |
-        |hpc|
+	|hpc|
 
-        hpc := entry handlerPCFor:anException at:pc in:self.
-        hpc notNil ifTrue:[^ hpc].
+	hpc := entry handlerPCFor:anException at:pc in:self.
+	hpc notNil ifTrue:[^ hpc].
     ].
 
     ^ nil
@@ -1172,7 +1209,7 @@
 !
 
 isAbstract
-    ^ (accessFlags bitAnd:16r0400) ~~ 0
+    ^ (accessFlags bitAnd:A_ABSTRACT) ~~ 0
 !
 
 isBreakpointed
@@ -1180,7 +1217,7 @@
 !
 
 isFinal
-    ^ (accessFlags bitAnd:16r0010) ~~ 0
+    ^ (accessFlags bitAnd:A_FINAL) ~~ 0
 !
 
 isIgnored
@@ -1194,7 +1231,7 @@
 
 isNOOPMethod
     isNOOPMethod isNil ifTrue:[
-        self checkForNOOPMethod
+	self checkForNOOPMethod
     ].
     ^ isNOOPMethod
 
@@ -1202,29 +1239,27 @@
 !
 
 isNative
-    ^ (accessFlags bitAnd:16r0100) ~~ 0
+    ^ (accessFlags bitAnd:A_NATIVE) ~~ 0
 !
 
 isPrivate
-    ^ (accessFlags bitAnd:16r0002) ~~ 0
-
+    ^ (accessFlags bitAnd:A_PRIVATE) ~~ 0
 !
 
 isProtected
-    ^ (accessFlags bitAnd:16r0004) ~~ 0
+    ^ (accessFlags bitAnd:A_PROTECTED) ~~ 0
 !
 
 isPublic
-    ^ (accessFlags bitAnd:16r0001) ~~ 0
-
+    ^ (accessFlags bitAnd:A_PUBLIC) ~~ 0
 !
 
 isStatic
-    ^ (accessFlags bitAnd:16r0008) ~~ 0
+    ^ (accessFlags bitAnd:A_STATIC) ~~ 0
 !
 
 isSynchronized
-    ^ (accessFlags bitAnd:16r0020) ~~ 0
+    ^ (accessFlags bitAnd:A_SYNCHRONIZED) ~~ 0
 !
 
 isUnloaded
@@ -1238,42 +1273,42 @@
 
     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
 
@@ -1291,6 +1326,7 @@
 
     |sel|
 
+    javaClass isNil ifTrue:[^ nil].
     sel := javaClass methodDictionary keyAtValue:self ifAbsent:nil.
     sel isNil ifTrue:[^ nil].
     ^ Method::MethodWhoInfo class:javaClass selector:sel.
@@ -1322,9 +1358,64 @@
     "Created: 20.3.1997 / 12:44:36 / cg"
 ! !
 
+!JavaMethod methodsFor:'vm support'!
+
+arrayLength:arr
+    ^ arr size
+
+    "Created: / 5.1.1998 / 02:40:01 / cg"
+!
+
+athrow:aJavaException
+    JavaVM javaExceptionSignal raiseWith:aJavaException in:thisContext sender.
+    self halt:'here after throw'.
+
+    "Created: / 4.1.1998 / 14:37:04 / cg"
+    "Modified: / 4.1.1998 / 14:38:32 / cg"
+!
+
+checkCast:anObject forClass:aClassOrInterface
+    "trampouline for unhandled cases ..."
+
+    aClassOrInterface isInterface ifTrue:[
+        (anObject class hasInterface:aClassOrInterface) ifTrue:[
+            ^ true
+        ]
+    ].
+    self halt.
+    ^ false.
+
+    "Created: / 4.1.1998 / 16:44:59 / cg"
+    "Modified: / 4.1.1998 / 16:51:40 / 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"
+!
+
+saload:arr _:index 
+    ^ arr at:index+1
+
+    "Created: / 5.1.1998 / 02:44:40 / cg"
+!
+
+sastore:arr _:index _:val
+    arr at:index+1 put:val
+
+    "Created: / 5.1.1998 / 02:35:52 / cg"
+! !
+
 !JavaMethod class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaMethod.st,v 1.52 1997/08/18 18:35:10 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaMethod.st,v 1.53 1998/01/05 18:49:27 cg Exp $'
 ! !
 JavaMethod initialize!
--- a/JavaMethodref.st	Fri Aug 29 16:03:19 1997 +0000
+++ b/JavaMethodref.st	Mon Jan 05 18:49:32 1998 +0000
@@ -96,40 +96,43 @@
 !
 
 method
-    "resolve the methodRef in its class.
-     Used for invokenonvirtual and to get a method prototype
-     for virtual invokes."
-
     |nm sig mthd cls|
 
     method notNil ifTrue:[^ method].
 
-    "/ resolve the possibly unresolved class
     cls := class javaClass.
     cls ~~ class ifTrue:[
         class := cls.
     ].
 
+"/    (class isMemberOf:JavaUnresolvedClassConstant) ifTrue:[
+"/        cls := class resolve.
+"/        cls notNil ifTrue:[
+"/            class := cls
+"/        ]
+"/    ].
+"/    (class isMemberOf:JavaUnresolvedClassConstant) ifTrue:[
+"/        self halt:'unresolved class'.
+"/    ].
+
     sel isNil ifTrue:[
-        nm := nameandType name.
+        nm := nameandType name asSymbol.
         sig := nameandType signature.
         sel := (nm , sig) asSymbol.
     ].
 
 "/ 'search in: ' print. class fullName print. ' for ' print. nm print. ' sig: ' print. sig printNL.
 
-    mthd := cls compiledMethodAt:sel.
+    mthd := class compiledMethodAt:sel.
     mthd isNil ifTrue:[
 "/        self halt:'no method found for: ' , self displayString.
-"/ old:   ^ self.
         ^ nil.
+"/ old:        ^ self.
     ].
     mthd checkForNOOPMethod.
-    method := mthd.
     ^ mthd
 
     "Modified: 31.7.1997 / 22:16:24 / cg"
-    "Modified: 28.8.1997 / 12:15:50 / stefan"
 !
 
 methodFor:aClass
@@ -180,33 +183,6 @@
     ^ nil
 
     "Modified: 26.3.1997 / 13:32:39 / cg"
-!
-
-specialMethod:classOfCurrentMethod
-    "resolve a method for invokespecial"
-
-    |mthd|
-
-    mthd := self method.
-    mthd isNil ifTrue:[
-        ^ nil.
-    ].
-    (((mthd isPrivate not 
-     and:[class useSpecialSuper]) 
-     and:[mthd name ~~ #'<init>'])
-     and:[classOfCurrentMethod isSubclassOf:class]) ifTrue:[
-        |cls superMethod|
-        cls := class.
-        [superMethod isNil and:[(cls := cls superclass) notNil]] whileTrue:[
-            superMethod := cls compiledMethodAt:sel.
-        ].
-        (superMethod notNil and:[superMethod isAbstract not]) ifTrue:[
-            mthd := superMethod.
-        ].
-    ].
-    ^ mthd
-
-    "Modified: 28.8.1997 / 14:30:30 / stefan"
 ! !
 
 !JavaMethodref methodsFor:'special'!
@@ -222,5 +198,5 @@
 !JavaMethodref class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaMethodref.st,v 1.28 1997/08/29 16:01:35 stefan Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaMethodref.st,v 1.29 1998/01/05 18:49:29 cg Exp $'
 ! !
--- a/JavaObject.st	Fri Aug 29 16:03:19 1997 +0000
+++ b/JavaObject.st	Mon Jan 05 18:49:32 1998 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:3.3.1 on 5-jan-1998 at 3:01:23 pm'                   !
+
 Object subclass:#JavaObject
 	instanceVariableNames:''
 	classVariableNames:''
@@ -108,11 +110,14 @@
     method := JavaClass lookupMethod:selector numArgs:0 in:self class static:false.
 "/    method := self lookupMethod:selector numArgs:0.
     method notNil ifTrue:[
-        ^ self 
-            invokeJavaMethod:method 
-            interpreter:i 
-            sender:aContext
-            selector:selector
+        ^ method
+            valueWithReceiver:self
+            arguments:#().
+"/        ^ self 
+"/            invokeJavaMethod:method 
+"/            interpreter:i 
+"/            sender:aContext
+"/            selector:selector
     ].
 
     ^ super doesNotUnderstand:(Message selector:selector)
@@ -136,7 +141,7 @@
      stack invoke:#size. 
     "
 
-    "Modified: 17.8.1997 / 18:26:15 / cg"
+    "Modified: / 5.1.1998 / 02:20:30 / cg"
 !
 
 invoke:selector interpreter:i sender:aContext with:argument
@@ -172,12 +177,15 @@
         method := JavaClass lookupMethod:sel numArgs:1 in:self class static:false.
         "/ method := self lookupMethod:sel numArgs:1.
         method notNil ifTrue:[
-            ^ self 
-                invokeJavaMethod:method 
-                interpreter:i 
-                sender:aContext 
-                selector:sel
-                with:argument
+            ^ method
+                valueWithReceiver:self
+                arguments:(Array with:argument)
+"/            ^ self 
+"/                invokeJavaMethod:method 
+"/                interpreter:i 
+"/                sender:aContext 
+"/                selector:sel
+"/                with:argument
         ].
 
 "/        cls := self class.
@@ -219,7 +227,7 @@
      stack invoke:#pop. 
     "
 
-    "Modified: 17.8.1997 / 18:26:22 / cg"
+    "Modified: / 5.1.1998 / 02:21:22 / cg"
 !
 
 invoke:selector interpreter:i sender:aContext with:arg1 with:arg2 
@@ -233,18 +241,21 @@
         method := JavaClass lookupMethod:sel numArgs:2 in:self class static:false.
         "/ method := self lookupMethod:sel numArgs:2.
         method notNil ifTrue:[
-            ^ self 
-                invokeJavaMethod:method 
-                interpreter:i 
-                sender:aContext
-                selector:selector
-                with:arg1 with:arg2
+            ^ method    
+                valueWithReceiver:self
+                arguments:(Array with:arg1 with:arg2)
+"/            ^ self 
+"/                invokeJavaMethod:method 
+"/                interpreter:i 
+"/                sender:aContext
+"/                selector:selector
+"/                with:arg1 with:arg2
         ].
     ].
 
     ^ super doesNotUnderstand:(Message selector:selector)
 
-    "Modified: 17.8.1997 / 18:26:24 / cg"
+    "Modified: / 5.1.1998 / 02:28:34 / cg"
 !
 
 invoke:selector interpreter:i sender:aContext with:arg1 with:arg2 with:arg3
@@ -967,5 +978,5 @@
 !JavaObject class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaObject.st,v 1.33 1997/08/18 10:40:24 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaObject.st,v 1.34 1998/01/05 18:49:30 cg Exp $'
 ! !
--- a/JavaUnresolvedClassConstant.st	Fri Aug 29 16:03:19 1997 +0000
+++ b/JavaUnresolvedClassConstant.st	Mon Jan 05 18:49:32 1998 +0000
@@ -1,3 +1,5 @@
+'From Smalltalk/X, Version:3.3.1 on 3-jan-1998 at 10:39:32 pm'                  !
+
 JavaUnresolvedConstant subclass:#JavaUnresolvedClassConstant
 	instanceVariableNames:'nameIndex fullName'
 	classVariableNames:''
@@ -105,9 +107,6 @@
     (fullName startsWith:'[[') ifTrue:[
         ^ JavaClassPointerRef class:Array nameandType:fullName
     ].
-    (fullName startsWith:'[L') ifTrue:[
-        ^ JavaClassPointerRef class:Array nameandType:fullName
-    ].
     (fullName startsWith:'[F') ifTrue:[
         ^ JavaClassPointerRef class:FloatArray nameandType:fullName
     ].
@@ -117,7 +116,6 @@
     self halt.
 
     "Created: 7.4.1997 / 13:40:29 / cg"
-    "Modified: 28.8.1997 / 14:05:22 / stefan"
 ! !
 
 !JavaUnresolvedClassConstant methodsFor:'printing & storing'!
@@ -126,7 +124,7 @@
     fullName isNil ifTrue:[
         ^ 'UnresolvedClass(** nil **)'
     ].
-    ^ 'UnresolvedClass(' , (fullName copy replaceAll:$/ by:$.) , ')'
+    ^ 'UnresolvedClass(' , (fullName copy replaceAll:$/ with:$.) , ')'
 ! !
 
 !JavaUnresolvedClassConstant methodsFor:'resolving'!
@@ -180,11 +178,37 @@
             constantPool at:constantPoolIndex put:ref.
             ^ ref
         ].
+        fullName = '[Z' ifTrue:[    "/ boolean[]
+            ref := JavaBuiltInClassPointerRef class:ByteArray nameandType:fullName.
+            constantPool at:constantPoolIndex put:ref.
+            ^ ref
+        ].
         fullName = '[I' ifTrue:[     "/ int[]
             ref := JavaBuiltInClassPointerRef class:Array nameandType:fullName.
             constantPool at:constantPoolIndex put:ref.
             ^ ref
         ].
+        fullName = '[J' ifTrue:[     "/ long[]
+            ref := JavaBuiltInClassPointerRef class:Array nameandType:fullName.
+            constantPool at:constantPoolIndex put:ref.
+            ^ ref
+        ].
+        fullName = '[S' ifTrue:[     "/ short[]
+            ref := JavaBuiltInClassPointerRef class:WordArray nameandType:fullName.
+            constantPool at:constantPoolIndex put:ref.
+            ^ ref
+        ].
+        fullName = '[C' ifTrue:[     "/ char[]
+            "/ should be TwoByteString ...
+            ref := JavaBuiltInClassPointerRef class:String nameandType:fullName.
+            constantPool at:constantPoolIndex put:ref.
+            ^ ref
+        ].
+        fullName = '[F' ifTrue:[     "/ float[]
+            ref := JavaBuiltInClassPointerRef class:FloatArray nameandType:fullName.
+            constantPool at:constantPoolIndex put:ref.
+            ^ ref
+        ].
         fullName = '[D' ifTrue:[     "/ double[]
             ref := JavaBuiltInClassPointerRef class:Array nameandType:fullName.
             constantPool at:constantPoolIndex put:ref.
@@ -210,12 +234,12 @@
     self rememberForResolveWith:nm.
     ^ self
 
-    "Created: 15.4.1996 / 15:51:42 / cg"
-    "Modified: 15.4.1996 / 16:26:05 / cg"
+    "Created: / 15.4.1996 / 15:51:42 / cg"
+    "Modified: / 3.1.1998 / 22:10:05 / cg"
 ! !
 
 !JavaUnresolvedClassConstant class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaUnresolvedClassConstant.st,v 1.21 1997/08/29 16:03:19 stefan Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaUnresolvedClassConstant.st,v 1.22 1998/01/05 18:49:32 cg Exp $'
 ! !