javaClass now uses its fullName in name
authorcg
Thu, 05 Nov 1998 19:15:59 +0000
changeset 423 08af061c56a8
parent 422 52d7ad2a295d
child 424 6ab47d2f7e8d
javaClass now uses its fullName in name
Java.st
JavaClass.st
JavaClassReader.st
JavaDecompiler.st
JavaFieldref.st
JavaMethod.st
JavaMethodWithHandler.st
JavaObject.st
JavaVM.st
--- a/Java.st	Thu Nov 05 19:13:58 1998 +0000
+++ b/Java.st	Thu Nov 05 19:15:59 1998 +0000
@@ -956,12 +956,13 @@
     JavaVM releaseAllJavaResources.
     JavaUnresolvedConstant flushPatchLists.
     Debugger newDebugger.
+    ObjectMemory flushCaches.
 
     "
      Java flushClasses
     "
 
-    "Modified: / 16.10.1998 / 11:25:36 / cg"
+    "Modified: / 5.11.1998 / 20:12:47 / cg"
 !
 
 markAllClassesUninitialized
@@ -1305,6 +1306,6 @@
 !Java class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/Java.st,v 1.75 1998/11/05 10:41:48 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/Java.st,v 1.76 1998/11/05 19:15:59 cg Exp $'
 ! !
 Java initialize!
--- a/JavaClass.st	Thu Nov 05 19:13:58 1998 +0000
+++ b/JavaClass.st	Thu Nov 05 19:15:59 1998 +0000
@@ -2,7 +2,8 @@
 	instanceVariableNames:'constantPool interfaces accessFlags classLoader fullName
 		sourceFile binaryFilePath fields initValues staticFields'
 	classVariableNames:'InitialValuePerType A_OBSOLETE A_INTERFACE A_PUBLIC A_FINAL
-		A_ABSTRACT A_INITIALIZED A_SMALLTALK'
+		A_ABSTRACT A_INITIALIZED A_SMALLTALK
+		ArgumentConversionErrorSignal'
 	poolDictionaries:''
 	category:'Java-Classes'
 !
@@ -58,11 +59,13 @@
     InitialValuePerType at:$L put:nil.
     InitialValuePerType at:$[ put:nil.
 
+    ArgumentConversionErrorSignal := ErrorSignal newSignal mayProceed:true.
+
     "
      JavaClass initialize
     "
 
-    "Modified: / 16.5.1998 / 01:18:48 / cg"
+    "Modified: / 5.11.1998 / 18:42:28 / cg"
 ! !
 
 !JavaClass class methodsFor:'instance creation'!
@@ -165,31 +168,139 @@
 
 !JavaClass class methodsFor:'method lookup'!
 
-convertArgsToJava:argArray
+canConvertArgsToJava:argArray asSpecifiedIn:argSigSpecArray
+    "given a smalltalk argument array, return true, if these can be converted to java objects as appropriate."
+
+    argArray with:argSigSpecArray do:[:arg :type | self convertArgToJava:arg type:type ifFail:[:msg :default| ^ false]].
+    ^ true
+
+    "Created: / 5.11.1998 / 18:25:05 / cg"
+!
+
+convertArgToJava:arg type:type
+    "given a smalltalk argument, convert to a java object as appropriate."
+
+    ^ self 
+        convertArgToJava:arg 
+        type:type 
+        ifFail:[:msg :default |
+                    ArgumentConversionErrorSignal 
+                        raiseWith:arg
+                        errorString:msg.
+                    default
+               ]
+
+    "Modified: / 5.11.1998 / 18:43:33 / cg"
+!
+
+convertArgToJava:arg type:type ifFail:failBlock
+    "given a smalltalk argument, convert to a java object as appropriate.
+     Currently, only a few types are converted."
+
+    type == #boolean ifTrue:[
+        arg == true ifTrue:[
+            ^ 1
+        ].
+        arg == false ifTrue:[
+            ^ 0
+        ].
+        ^ failBlock value:('cannot convert argument to ' , type) value:0
+    ].
+
+    type == #int ifTrue:[
+        arg isInteger ifTrue:[
+            (arg between:-16r8000000 and:16r7FFFFFFF) ifTrue:[
+                ^ arg
+            ].
+            ^ failBlock value:('integer range; cannot convert argument to ' , type) value:0.
+        ].
+        ^ failBlock value:('cannot convert argument to ' , type) value:0
+    ].
+
+    type == #long ifTrue:[
+        arg isInteger ifTrue:[
+            (arg between:-16r800000000000000 and:16r7FFFFFFFFFFFFFFF) ifTrue:[
+                ^ arg
+            ].
+            ^ failBlock value:('integer range; cannot convert argument to ' , type) value:0
+        ].
+        ^ failBlock value:('cannot convert argument to ' , type) value:0
+    ].
+
+    (type == #float) ifTrue:[
+        arg isReal ifTrue:[
+            ^ arg asShortFloat
+        ].
+        ^ failBlock value:('cannot convert argument to ' , type) value:0.0.
+    ].
+
+    (type == #double) ifTrue:[
+        arg isReal ifTrue:[
+            ^ arg asFloat
+        ].
+        ^ failBlock value:('cannot convert argument to ' , type) value:0.0.
+    ].
+
+    (type == #char) ifTrue:[
+        arg isCharacter ifTrue:[
+            ^ arg asciiValue
+        ].
+        ^ failBlock value:('cannot convert argument to ' , type) value:0
+    ].    
+
+    (type = 'char[]') ifTrue:[
+        arg isString ifTrue:[
+            ^ arg
+        ].
+        ^ failBlock value:('cannot convert argument to ' , type) value:''
+    ].    
+
+    (type = 'java.lang.Object') ifTrue:[
+        "/ matches any
+        ^ arg
+    ].
+    (type = 'java.lang.String') ifTrue:[
+        arg isString ifTrue:[
+            ^ Java as_String:arg
+        ].
+        ^ failBlock value:('cannot convert argument to ' , type) value:''
+    ].
+self halt.
+    ^ failBlock value:('cannot convert argument to ' , type) value:nil
+
+    "Modified: / 5.11.1998 / 19:50:59 / cg"
+!
+
+convertArgsToJava:argArray asSpecifiedIn:argSigSpecArray numArgs:na
     "given a smalltalk argument array, convert to java objects as appropriate.
      Currently, only Strings and booleans are converted."
 
-    |newArgs|
+    |sigIndex newArgIndex newArgArray|
+
+    sigIndex := newArgIndex := 1.
+
+    newArgArray := Array new:na.
+    argArray do:[:arg |
+        |type newArg|
 
-    newArgs := argArray copy.
-    newArgs keysAndValuesDo:[:idx :arg |
-        arg isString ifTrue:[
-            newArgs at:idx put:(Java as_String:arg)
-        ] ifFalse:[
-            arg == true ifTrue:[
-                newArgs at:idx put:1
-            ] ifFalse:[
-                arg == false ifTrue:[
-                    newArgs at:idx put:0
-                ]
-            ]
+        type := argSigSpecArray at:sigIndex.
+        sigIndex := sigIndex + 1.
+        newArg := self convertArgToJava:arg type:type.
+        newArgArray at:newArgIndex put:newArg.
+        newArgIndex := newArgIndex + 1.
+        (type == #long or:[type == #double]) ifTrue:[
+            newArgIndex > na ifTrue:[
+                self halt:'should not happen'
+            ].
+            newArgArray at:newArgIndex put:nil.
+            newArgIndex := newArgIndex + 1.
         ]
     ].
 
-    ^ newArgs
+    ^ newArgArray
 
-    "Created: / 9.4.1998 / 21:40:23 / cg"
-    "Modified: / 4.11.1998 / 17:14:36 / cg"
+    "Created: / 5.11.1998 / 18:30:57 / cg"
+    "Modified: / 5.11.1998 / 18:50:52 / cg"
 !
 
 lookupMethod:selector numArgs:nargs in:aClass static:staticMethod
@@ -277,6 +388,21 @@
     "Modified: / 4.11.1998 / 19:31:33 / cg"
 ! !
 
+!JavaClass class methodsFor:'queries'!
+
+canBeSubclassed
+    "return true, if its allowed to create subclasses of the receiver."
+
+    self == JavaClass ifTrue:[
+        ^ super canBeSubclassed
+    ].
+    self isFinal ifTrue:[^ false].
+    self isInterface ifTrue:[^ false].
+    ^ true
+
+    "Modified: / 5.11.1998 / 16:12:50 / cg"
+! !
+
 !JavaClass class methodsFor:'signature parsing'!
 
 initialValueFromSignature:aSignature
@@ -394,6 +520,12 @@
     ^ self
 !
 
+lastName
+    ^ fullName copyFrom:(fullName lastIndexOf:$/)+1
+
+    "Created: / 5.11.1998 / 19:16:00 / cg"
+!
+
 name
     ^ name "/ fullName
 !
@@ -828,18 +960,9 @@
     "as a courtesy to the smalltalker, try to map static methods as
      Smalltalk-class methods"
 
-    |r args numArgs methods javaMethod sel eMsg argType
+    |r args numArgs methods javaMethod sel anyMethodsFound argType
      argSignature newArgs oArgIdx nArgIdx canConvert|
 
-"/    r := thisContext sender receiver.
-"/
-"/    r isJavaClass ifTrue:[
-"/        self halt:'should not happen from within java code'.
-"/    ].
-"/    r class isJavaClass ifTrue:[
-"/        self halt:'should not happen from within java code'.
-"/    ].
-
     args := aMessage arguments.
     numArgs := args size.
     sel := aMessage selector.
@@ -850,144 +973,75 @@
         "/ there is only one - try that one.
     ] ifFalse:[
         methods size > 1 ifTrue:[
-            "/ more than one - select the best fit.
-            "/ first, look for an exact match ...
-            methods do:[:aMethod |
-                |argSignature doesMatch|
-
-                doesMatch := true.
-                argSignature := aMethod argSignature.
-                argSignature keysAndValuesDo:[:i :argType |
-                    |arg|
+            "/ more than one - select the ones that could be used.
+            methods := methods select:[:aMethod |
+                |argSignature|
 
-                    arg := args at:i.
-                    argType == #int ifTrue:[
-                        (arg isInteger 
-                        and:[arg between:-16r8000000 and:16r7FFFFFFF]) ifFalse:[
-                            doesMatch := false
-                        ]
-                    ] ifFalse:[
-                        argType == #float ifTrue:[
-                            arg isReal ifFalse:[
-                                doesMatch := false
-                            ]
-                        ] ifFalse:[
-                            self halt
-                        ]
-                    ]
-                ].
-                doesMatch ifTrue:[
-                    javaMethod notNil ifTrue:[
-                        self halt:'more than one matching methods'
-                    ].
-                    javaMethod := aMethod
-                ]
+                argSignature := aMethod argSignature.
+                (JavaClass canConvertArgsToJava:args asSpecifiedIn:argSignature) 
             ].
+            methods size == 1 ifTrue:[
+                javaMethod := methods first.
+            ]
         ]
     ].
 
     javaMethod notNil ifTrue:[
-        args notNil ifTrue:[
-            args := JavaClass convertArgsToJava:args.
+        (ArgumentConversionErrorSignal catch:[
+            args notNil ifTrue:[
+                args := JavaClass 
+                            convertArgsToJava:args 
+                            asSpecifiedIn:(javaMethod argSignature)
+                            numArgs:numArgs.
+            ].
+        ]) ifFalse:[
+            ^ javaMethod 
+                valueWithReceiver:(javaMethod javaClass) 
+                arguments:args
+                selector:(javaMethod selector)
+                search:(javaMethod javaClass class)
+                sender:nil
         ].
-        ^ javaMethod 
-            valueWithReceiver:self 
-            arguments:args
-            selector:sel 
-            search:nil
-            sender:nil
+        ^ MessageNotUnderstoodSignal
+                    raiseRequestWith:aMessage
+                         errorString:'no method for given argument(s)'
+                                  in:thisContext "sender"
     ].
 
-    methods size > 1 ifTrue:[
-        eMsg := 'no ''' , sel , '''-function for given argument type(s)'
-    ] ifFalse:[
+    anyMethodsFound := false.
+    args size > 0 ifTrue:[
+        "/ try all with that name (the number of args could be different ...
 
         methods := JavaClass lookupMethods:sel numArgs:nil in:self static:true.
         methods size > 0 ifTrue:[
-            methods size == 1 ifTrue:[
-                javaMethod := methods first.
-                argSignature := javaMethod argSignature.
-
-                (javaMethod numArgs > numArgs
-                and:[argSignature size == numArgs]) ifTrue:[
-                    "/ try again - may have to add dummy slots for float/long
-                    "/ args ...
-                    canConvert := true.
-                    oArgIdx := 1.
-                    nArgIdx := 1.
-                    newArgs := Array new:javaMethod numArgs.
-                    argSignature do:[:argSig |
-                        |arg|
-
-                        arg := args at:oArgIdx.
-                        oArgIdx := oArgIdx + 1.
-                        argSig == #double ifTrue:[
-                            arg isReal ifTrue:[
-                                newArgs at:nArgIdx put:arg.
-                                nArgIdx := nArgIdx + 1.
-                                newArgs at:nArgIdx put:nil. "/ dummy double high
-                                nArgIdx := nArgIdx + 1.
-                            ] ifFalse:[
-                                canConvert := false.
-                            ]
-                        ] ifFalse:[
-                            argSig == #long ifTrue:[
-                                arg isInteger ifTrue:[
-                                    newArgs at:nArgIdx put:arg.
-                                    nArgIdx := nArgIdx + 1.
-                                    newArgs at:nArgIdx put:nil. "/ dummy long high
-                                    nArgIdx := nArgIdx + 1.
-                                ] ifFalse:[
-                                    canConvert := false.
-                                ]
-                            ] ifFalse:[
-                                argSig == #int ifTrue:[
-                                    arg isInteger ifTrue:[
-                                        newArgs at:nArgIdx put:arg.
-                                    ] ifFalse:[
-                                        canConvert := false.
-                                    ]
-                                ] ifFalse:[
-                                    canConvert := false
-                                ]
-                            ]
-                        ].
-                    ].
-                    canConvert ifTrue:[
-                        ^ javaMethod 
-                            valueWithReceiver:self 
-                            arguments:newArgs
-                            selector:sel 
-                            search:nil
-                            sender:nil
-                    ].
-                ].
-
-                argSignature size == 1 ifTrue:[
-                    argType := argSignature first printString.
-                    eMsg := '''' , sel , '''-function expects ' , argType , ' as argument'.
-                ] ifFalse:[
-                    eMsg := '''' , sel , '''-function expects ' , argSignature size printString , ' argument(s)'
-                ].
-            ] ifFalse:[
-                numArgs == 0 ifTrue:[
-                    eMsg := 'no ''' , sel , '''-function without arguments'
-                ] ifFalse:[
-                    eMsg := 'no ''' , sel , '''-function for given number of arguments'
+            anyMethodsFound := true.
+            methods do:[:methodToTry |
+                (ArgumentConversionErrorSignal catch:[
+                    newArgs := JavaClass 
+                                convertArgsToJava:args 
+                                asSpecifiedIn:(methodToTry argSignature)
+                                numArgs:methodToTry numArgs.
+                ]) ifFalse:[
+                    ^ methodToTry 
+                        valueWithReceiver:(javaMethod javaClassd) 
+                        arguments:newArgs
+                        selector:(methodToTry selector)
+                        search:(javaMethod javaClass class)
+                        sender:nil
                 ].
             ].
         ].
     ].
 
-    eMsg notNil ifTrue:[
+    anyMethodsFound ifTrue:[
         ^ MessageNotUnderstoodSignal
                     raiseRequestWith:aMessage
-                         errorString:eMsg
+                         errorString:'no method for given argument(s)'
                                   in:thisContext "sender"
     ].
     ^ super doesNotUnderstand:aMessage
 
-    "Modified: / 4.11.1998 / 21:49:20 / cg"
+    "Modified: / 5.11.1998 / 19:12:52 / cg"
 !
 
 invokeJavaMethod:aJavaMethod interpreter:i sender:aContext selector:sel with:arg1
@@ -1177,9 +1231,11 @@
 
     fullName := aString asSymbol.
     nameComponents := aString asCollectionOfSubstringsSeparatedBy:$/.
-    name := nameComponents last asSymbol
+    name := nameComponents last asSymbol.
+name := fullName.
 
-    "Created: 15.4.1996 / 16:42:52 / cg"
+    "Created: / 15.4.1996 / 16:42:52 / cg"
+    "Modified: / 5.11.1998 / 19:14:39 / cg"
 !
 
 setInterfaces:i
@@ -1424,9 +1480,7 @@
 
     "Created: / 30.7.1997 / 14:06:50 / cg"
     "Modified: / 6.1.1998 / 18:21:34 / cg"
-! !
-
-!JavaClass ignoredMethodsFor:'smalltalk interface'!
+!
 
 invoke:selector interpreter:i sender:aContext with:arg
     "send a message, with 1 arg"
@@ -1604,9 +1658,7 @@
 
     "Modified: 30.7.1997 / 13:39:15 / cg"
     "Created: 30.7.1997 / 14:00:53 / cg"
-! !
-
-!JavaClass methodsFor:'smalltalk interface'!
+!
 
 methodMatching:aSmalltalkSelector
     |numArgs cls|
@@ -1658,6 +1710,6 @@
 !JavaClass class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaClass.st,v 1.84 1998/11/04 20:55:47 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaClass.st,v 1.85 1998/11/05 19:13:22 cg Exp $'
 ! !
 JavaClass initialize!
--- a/JavaClassReader.st	Thu Nov 05 19:13:58 1998 +0000
+++ b/JavaClassReader.st	Thu Nov 05 19:15:59 1998 +0000
@@ -1970,9 +1970,12 @@
             m code:nil.
             m byteCode:nil.
         ].
-        (m exceptionHandlerTable isNil
-        and:[m exceptionTable isNil]) ifTrue:[
-            m := JavaMethod fromMethod:m
+        (m exceptionHandlerTable isNil) ifTrue:[
+            m exceptionTable isNil ifTrue:[
+                m := JavaMethod fromMethod:m
+            ] ifFalse:[
+                m := JavaMethodWithException fromMethod:m
+            ]
         ].
         aClass addMethod:m name:name signature:signature.
     ] ifFalse:[
@@ -1990,7 +1993,7 @@
     "
 
     "Created: / 15.4.1996 / 16:48:49 / cg"
-    "Modified: / 16.10.1998 / 01:24:09 / cg"
+    "Modified: / 5.11.1998 / 20:01:43 / cg"
 !
 
 readMethodsFor:aJavaClass
@@ -2098,6 +2101,6 @@
 !JavaClassReader class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaClassReader.st,v 1.75 1998/10/22 18:09:45 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaClassReader.st,v 1.76 1998/11/05 19:15:02 cg Exp $'
 ! !
 JavaClassReader initialize!
--- a/JavaDecompiler.st	Thu Nov 05 19:13:58 1998 +0000
+++ b/JavaDecompiler.st	Thu Nov 05 19:15:59 1998 +0000
@@ -358,7 +358,7 @@
        s nextPutAll:'class '.
     ].
     s emphasis:classNameStyle; 
-      nextPutAll:aJavaClass name; 
+      nextPutAll:aJavaClass lastName; 
       emphasis:codeStyle; 
       space.
     superClass := aJavaClass superclass.
@@ -370,7 +370,7 @@
         and:[superClass package ~= pckgName]) ifTrue:[
             s nextPutAll:(superClass displayString). 
         ] ifFalse:[
-            s nextPutAll:(superClass name).
+            s nextPutAll:(superClass lastName).
         ].
         s emphasis:codeStyle.
         s space.
@@ -519,7 +519,7 @@
     s nextPutAll:'}'; cr.
 
     "Created: / 22.3.1997 / 14:29:37 / cg"
-    "Modified: / 18.7.1998 / 22:56:46 / cg"
+    "Modified: / 5.11.1998 / 19:46:41 / cg"
 !
 
 methodDefinitionOf:aMethod inPackage:pckgName on:s
@@ -555,7 +555,7 @@
     s emphasis:codeStyle.
 
     (nm := aMethod name) = '<init>' ifTrue:[
-        nm := aMethod javaClass name.
+        nm := aMethod javaClass lastName.
     ].
     specComponents := JavaMethod
                           specComponentsWithArgsFromSignature:(aMethod signature)
@@ -594,7 +594,7 @@
     s nextPutAll:';'; cr.
 
     "Created: / 1.8.1997 / 12:24:11 / cg"
-    "Modified: / 18.7.1998 / 22:56:54 / cg"
+    "Modified: / 5.11.1998 / 19:44:19 / cg"
 ! !
 
 !JavaDecompiler class methodsFor:'decompiling'!
@@ -955,6 +955,6 @@
 !JavaDecompiler class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaDecompiler.st,v 1.34 1998/07/20 11:28:43 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaDecompiler.st,v 1.35 1998/11/05 19:14:51 cg Exp $'
 ! !
 JavaDecompiler initialize!
--- a/JavaFieldref.st	Thu Nov 05 19:13:58 1998 +0000
+++ b/JavaFieldref.st	Thu Nov 05 19:15:59 1998 +0000
@@ -28,19 +28,25 @@
 !
 
 nameandType:aJavaNameandType
-    nameandType := aJavaNameandType
+    nameandType := aJavaNameandType.
+    self resolveType.
 
-    "Created: 19.8.1997 / 14:01:27 / cg"
+    "Created: / 19.8.1997 / 14:01:27 / cg"
+    "Modified: / 5.11.1998 / 17:11:51 / cg"
 ! !
 
 !JavaFieldref methodsFor:'printing & storing'!
 
 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 
+                       , ' offs=' , offset printString
+                       , ')'
+
+    "Modified: / 5.11.1998 / 16:29:51 / cg"
 ! !
 
 !JavaFieldref methodsFor:'resolving'!
@@ -147,7 +153,7 @@
 !JavaFieldref class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaFieldref.st,v 1.17 1998/01/17 14:43:39 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaFieldref.st,v 1.18 1998/11/05 19:14:42 cg Exp $'
 
 ! !
 JavaFieldref initialize!
--- a/JavaMethod.st	Thu Nov 05 19:13:58 1998 +0000
+++ b/JavaMethod.st	Thu Nov 05 19:15:59 1998 +0000
@@ -1233,9 +1233,9 @@
     javaClass isNil ifTrue:[
         ^ 'JavaMethod(???)'
     ].
-    ^ 'JavaMethod(' , javaClass fullName , '::' , self signatureName , ')'
-
-    "Modified: / 3.11.1998 / 00:09:50 / cg"
+    ^ 'JavaMethod(' , javaClass displayString , '::' , self signatureName , ')'
+
+    "Modified: / 5.11.1998 / 19:49:07 / cg"
 !
 
 printStringForBrowserWithSelector:dummySelector
@@ -1247,11 +1247,11 @@
 "/    ].
 
     self name = #'<init>' ifTrue:[
-	^ self class specTextFromSignature:signature withName:(javaClass name).
+        ^ self class specTextFromSignature:signature withName:(javaClass lastName).
     ].
     ^ self signatureNameText
 
-    "Modified: 30.7.1997 / 14:40:42 / cg"
+    "Modified: / 5.11.1998 / 19:44:55 / cg"
 !
 
 shortDisplayString
@@ -1957,7 +1957,7 @@
 nativeMethodInvokation
     |sel|
 
-    sel := ('_' , javaClass name , '_' , self name , ':') asSymbol.
+    sel := ('_' , javaClass lastName , '_' , self name , ':') asSymbol.
 "/    (JavaVM respondsTo:sel) ifTrue:[
         ^ JavaVM 
             perform:sel
@@ -1968,7 +1968,7 @@
     ^ nil
 
     "Created: / 1.1.1998 / 15:16:14 / cg"
-    "Modified: / 15.1.1998 / 01:51:03 / cg"
+    "Modified: / 5.11.1998 / 19:16:12 / cg"
 !
 
 nullPointerException
@@ -1981,6 +1981,6 @@
 !JavaMethod class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaMethod.st,v 1.74 1998/11/03 14:58:11 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaMethod.st,v 1.75 1998/11/05 19:14:05 cg Exp $'
 ! !
 JavaMethod initialize!
--- a/JavaMethodWithHandler.st	Thu Nov 05 19:13:58 1998 +0000
+++ b/JavaMethodWithHandler.st	Thu Nov 05 19:15:59 1998 +0000
@@ -1,5 +1,5 @@
-JavaMethod subclass:#JavaMethodWithHandler
-	instanceVariableNames:'exceptionHandlerTable exceptionTable'
+JavaMethodWithException subclass:#JavaMethodWithHandler
+	instanceVariableNames:'exceptionHandlerTable'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Java-Classes'
@@ -15,23 +15,10 @@
     "Created: / 16.10.1998 / 01:18:28 / cg"
 !
 
-exceptionTable
-    ^ exceptionTable
-
-    "Modified: / 16.4.1996 / 12:49:06 / cg"
-    "Created: / 16.10.1998 / 01:18:47 / cg"
-!
-
 setExceptionHandlerTable:anArray
     exceptionHandlerTable := anArray.
 
     "Created: / 16.10.1998 / 01:19:00 / cg"
-!
-
-setExceptionTable:anArray
-    exceptionTable := anArray.
-
-    "Created: / 16.10.1998 / 01:19:05 / cg"
 ! !
 
 !JavaMethodWithHandler methodsFor:'queries'!
@@ -53,5 +40,5 @@
 !JavaMethodWithHandler class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaMethodWithHandler.st,v 1.1 1998/10/17 12:45:31 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaMethodWithHandler.st,v 1.2 1998/11/05 19:13:37 cg Exp $'
 ! !
--- a/JavaObject.st	Thu Nov 05 19:13:58 1998 +0000
+++ b/JavaObject.st	Thu Nov 05 19:15:59 1998 +0000
@@ -200,18 +200,21 @@
     javaMethod := JavaClass lookupMethod:sel numArgs:numArgs in:self class static:false.
     javaMethod notNil ifTrue:[
         args notNil ifTrue:[
-            args := JavaClass convertArgsToJava:args.
+            args := JavaClass 
+                        convertArgsToJava:args 
+                        asSpecifiedIn:(javaMethod argSignature)
+                        numArgs:numArgs.
         ].
         ^ javaMethod 
             valueWithReceiver:self 
             arguments:args
             selector:sel 
-            search:nil
+            search:(javaMethod javaClass)
             sender:nil
     ].
     ^ super doesNotUnderstand:aMessage
 
-    "Modified: / 4.11.1998 / 17:10:43 / cg"
+    "Modified: / 5.11.1998 / 19:21:01 / cg"
 !
 
 invokeJavaMethod:aJavaMethod interpreter:i sender:s selector:sel
@@ -689,5 +692,5 @@
 !JavaObject class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaObject.st,v 1.41 1998/11/04 20:58:03 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaObject.st,v 1.42 1998/11/05 19:13:32 cg Exp $'
 ! !
--- a/JavaVM.st	Thu Nov 05 19:13:58 1998 +0000
+++ b/JavaVM.st	Thu Nov 05 19:15:59 1998 +0000
@@ -392,6 +392,30 @@
 
 !JavaVM class methodsFor:'initialization'!
 
+compile:source selector:smalltalkSelector asJavaMethod:javaSelector fakedSource:fakedSource in:aClass
+    "install additional java protocol in smalltalk classes, req'd for java programs"
+
+    |cloneCode|
+
+    (aClass implements:javaSelector) ifFalse:[
+        aClass
+            compile:source
+            classified:'java support'
+            logged:false.
+
+        cloneCode := aClass compiledMethodAt:smalltalkSelector.
+        cloneCode source:fakedSource.
+
+        Class withoutUpdatingChangesDo:[
+            aClass removeSelector:smalltalkSelector.
+            aClass addSelector:javaSelector withMethod:cloneCode.
+        ]
+    ].
+
+    "Created: / 5.11.1998 / 19:30:22 / cg"
+    "Modified: / 5.11.1998 / 19:37:57 / cg"
+!
+
 deinitialize
     |table|
 
@@ -492,33 +516,42 @@
 initializeAdditionalJavaProtocol
     "install additional java protocol in smalltalk classes, req'd for java programs"
 
-    |cloneCode|
-
     "/ since we use smalltalk Arrays for JavaArray, some
     "/ additional (java-) protocol is required.
-
-    (Object implements:#'clone()Ljava/lang/Object;') ifFalse:[
-        Object 
-            compile:'__clone
+    "/ This is also useful, when Smalltalk objects are passed to
+    "/ java ...
+    "/ We should implement all of the java.lang.Object protocol in
+    "/ Object, to be on the bright side of life; more of this later ...
+
+    self
+        compile:'__clone
     "this is smalltalk code with a java selector ...
      Has been added by JavaVM>>initializeAdditionalJavaProtocol"
 
     ^ self shallowCopy'
-            classified:'java support'
-            logged:false.
-
-        cloneCode := Object compiledMethodAt:#'__clone'.
-        cloneCode source:'#''clone()Ljava/lang/Object;''
+        selector:#'__clone' 
+        asJavaMethod:#'clone()Ljava/lang/Object;' 
+        fakedSource:'#''clone()Ljava/lang/Object;''
     "this is smalltalk code with a java selector ...
      Has been added by JavaVM>>initializeAdditionalJavaProtocol"
 
-    ^ self shallowCopy'.
-
-        Class withoutUpdatingChangesDo:[
-            Object removeSelector:#'__clone'.
-            Object addSelector:#'clone()Ljava/lang/Object;' withMethod:cloneCode.
-        ]
-    ].
+    ^ self shallowCopy'
+        in:Object.
+
+    self
+        compile:'__toString
+    "this is smalltalk code with a java selector ...
+     Has been added by JavaVM>>initializeAdditionalJavaProtocol"
+
+    ^ Java as_String:(self displayString)'
+        selector:#'__toString' 
+        asJavaMethod:#'toString()Ljava/lang/String;' 
+        fakedSource:'#''toString()Ljava/lang/String;''
+    "this is smalltalk code with a java selector ...
+     Has been added by JavaVM>>initializeAdditionalJavaProtocol"
+
+    ^ Java as_String:(self displayString)'
+        in:Object
 
     "
      self initializeAdditionalJavaProtocol
@@ -527,7 +560,7 @@
     "Modified: / 28.1.1997 / 19:38:58 / stefan"
     "Modified: / 22.1.1998 / 21:23:40 / av"
     "Created: / 4.2.1998 / 21:35:46 / cg"
-    "Modified: / 4.2.1998 / 21:42:47 / cg"
+    "Modified: / 5.11.1998 / 19:40:17 / cg"
 !
 
 initializeBaseClasses
@@ -739,6 +772,7 @@
     self deinitialize.
 
     FirstWindowCreationSemaphore := Semaphore new.
+    ScreenUpdaterProcess := nil.
 
     LoadedLibs := nil.             "/ gc will reclaim them ...
     LoadedNativeLibs := nil.       "/ gc will reclaim them ...
@@ -755,7 +789,7 @@
     "
 
     "Created: / 7.1.1998 / 22:49:42 / cg"
-    "Modified: / 16.10.1998 / 00:11:37 / cg"
+    "Modified: / 5.11.1998 / 20:07:02 / cg"
 !
 
 releaseAllMonitors
@@ -3137,7 +3171,7 @@
     dVal := nativeContext argAt:1.
     (nativeContext argAt:2) ~~ DUMMY_DOUBLE_HIGHWORD ifTrue:[
         dVal isReal ifTrue:[
-            'JAVAVM [info]: missing double flag' infoPrintCR.
+            'JAVAVM [info]: missing double flag in Math>>acos' infoPrintCR.
         ] ifFalse:[
             self halt:'expected double arg'
         ]
@@ -3145,7 +3179,7 @@
     ^ dVal arcCos
 
     "Created: / 7.5.1998 / 00:34:50 / cg"
-    "Modified: / 4.11.1998 / 17:23:05 / cg"
+    "Modified: / 4.11.1998 / 22:08:36 / cg"
 !
 
 _Math_asin:nativeContext
@@ -3156,7 +3190,7 @@
     dVal := nativeContext argAt:1.
     (nativeContext argAt:2) ~~ DUMMY_DOUBLE_HIGHWORD ifTrue:[
         dVal isReal ifTrue:[
-            'JAVAVM [info]: missing double flag' infoPrintCR.
+            'JAVAVM [info]: missing double flag in Math>>asin' infoPrintCR.
         ] ifFalse:[
             self halt:'expected double arg'
         ]
@@ -3164,7 +3198,7 @@
     ^ dVal arcSin
 
     "Created: / 7.5.1998 / 00:34:26 / cg"
-    "Modified: / 4.11.1998 / 17:23:15 / cg"
+    "Modified: / 4.11.1998 / 22:08:48 / cg"
 !
 
 _Math_atan:nativeContext
@@ -3175,7 +3209,7 @@
     dVal := nativeContext argAt:1.
     (nativeContext argAt:2) ~~ DUMMY_DOUBLE_HIGHWORD ifTrue:[
         dVal isReal ifTrue:[
-            'JAVAVM [info]: missing double flag' infoPrintCR.
+            'JAVAVM [info]: missing double flag in Math>>atan' infoPrintCR.
         ] ifFalse:[
             self halt:'expected double arg'
         ]
@@ -3183,7 +3217,7 @@
     ^ dVal arcTan
 
     "Created: / 6.2.1998 / 01:24:12 / cg"
-    "Modified: / 4.11.1998 / 17:23:19 / cg"
+    "Modified: / 4.11.1998 / 22:08:44 / cg"
 !
 
 _Math_ceil:nativeContext
@@ -3194,7 +3228,7 @@
     dVal := nativeContext argAt:1.
     (nativeContext argAt:2) ~~ DUMMY_DOUBLE_HIGHWORD ifTrue:[
         dVal isReal ifTrue:[
-            'JAVAVM [info]: missing double flag' infoPrintCR.
+            'JAVAVM [info]: missing double flag in Math>>ceil' infoPrintCR.
         ] ifFalse:[
             self halt:'expected double arg'
         ]
@@ -3202,7 +3236,7 @@
     ^ dVal ceilingAsFloat
 
     "Created: / 7.1.1998 / 15:43:00 / cg"
-    "Modified: / 4.11.1998 / 17:23:24 / cg"
+    "Modified: / 4.11.1998 / 22:08:59 / cg"
 !
 
 _Math_cos:nativeContext
@@ -3213,7 +3247,7 @@
     dVal := nativeContext argAt:1.
     (nativeContext argAt:2) ~~ DUMMY_DOUBLE_HIGHWORD ifTrue:[
         dVal isReal ifTrue:[
-            'JAVAVM [info]: missing double flag' infoPrintCR.
+            'JAVAVM [info]: missing double flag in Math>>cos' infoPrintCR.
         ] ifFalse:[
             self halt:'expected double arg'
         ]
@@ -3221,7 +3255,7 @@
     ^ dVal cos
 
     "Created: / 7.1.1998 / 15:41:30 / cg"
-    "Modified: / 4.11.1998 / 17:23:29 / cg"
+    "Modified: / 4.11.1998 / 22:08:32 / cg"
 !
 
 _Math_exp:nativeContext
@@ -3232,7 +3266,7 @@
     dVal := nativeContext argAt:1.
     (nativeContext argAt:2) ~~ DUMMY_DOUBLE_HIGHWORD ifTrue:[
         dVal isReal ifTrue:[
-            'JAVAVM [info]: missing double flag' infoPrintCR.
+            'JAVAVM [info]: missing double flag in Math>>exp' infoPrintCR.
         ] ifFalse:[
             self halt:'expected double arg'
         ]
@@ -3240,7 +3274,7 @@
     ^ dVal exp
 
     "Created: / 7.5.1998 / 00:36:19 / cg"
-    "Modified: / 4.11.1998 / 17:23:33 / cg"
+    "Modified: / 4.11.1998 / 22:09:05 / cg"
 !
 
 _Math_floor:nativeContext
@@ -3251,7 +3285,7 @@
     dVal := nativeContext argAt:1.
     (nativeContext argAt:2) ~~ DUMMY_DOUBLE_HIGHWORD ifTrue:[
         dVal isReal ifTrue:[
-            'JAVAVM [info]: missing double flag' infoPrintCR.
+            'JAVAVM [info]: missing double flag in Math>>floor' infoPrintCR.
         ] ifFalse:[
             self halt:'expected double arg'
         ]
@@ -3259,7 +3293,7 @@
     ^ dVal floorAsFloat
 
     "Created: / 7.1.1998 / 19:09:21 / cg"
-    "Modified: / 4.11.1998 / 17:23:37 / cg"
+    "Modified: / 4.11.1998 / 22:09:10 / cg"
 !
 
 _Math_log:nativeContext
@@ -3270,7 +3304,7 @@
     dVal := nativeContext argAt:1.
     (nativeContext argAt:2) ~~ DUMMY_DOUBLE_HIGHWORD ifTrue:[
         dVal isReal ifTrue:[
-            'JAVAVM [info]: missing double flag' infoPrintCR.
+            'JAVAVM [info]: missing double flag in Math>>log' infoPrintCR.
         ] ifFalse:[
             self halt:'expected double arg'
         ]
@@ -3278,7 +3312,7 @@
     ^ dVal log
 
     "Created: / 7.1.1998 / 15:42:19 / cg"
-    "Modified: / 4.11.1998 / 17:23:41 / cg"
+    "Modified: / 4.11.1998 / 22:09:16 / cg"
 !
 
 _Math_pow:nativeContext
@@ -3289,7 +3323,7 @@
     dVal1 := nativeContext argAt:1.
     (nativeContext argAt:2) ~~ DUMMY_DOUBLE_HIGHWORD ifTrue:[
         dVal1 isReal ifTrue:[
-            'JAVAVM [info]: missing double flag' infoPrintCR.
+            'JAVAVM [info]: missing double flag in Math>>pow' infoPrintCR.
         ] ifFalse:[
             self halt:'expected double arg'
         ]
@@ -3297,7 +3331,7 @@
     dVal2 := nativeContext argAt:3.
     (nativeContext argAt:4) ~~ DUMMY_DOUBLE_HIGHWORD ifTrue:[
         dVal2 isReal ifTrue:[
-            'JAVAVM [info]: missing double flag' infoPrintCR.
+            'JAVAVM [info]: missing double flag in Math>>pow' infoPrintCR.
         ] ifFalse:[
             self halt:'expected double arg'
         ]
@@ -3305,7 +3339,7 @@
     ^ dVal1 raisedTo:dVal2
 
     "Created: / 7.1.1998 / 15:44:13 / cg"
-    "Modified: / 4.11.1998 / 17:24:01 / cg"
+    "Modified: / 4.11.1998 / 22:09:26 / cg"
 !
 
 _Math_sin:nativeContext
@@ -3316,7 +3350,7 @@
     dVal := nativeContext argAt:1.
     (nativeContext argAt:2) ~~ DUMMY_DOUBLE_HIGHWORD ifTrue:[
         dVal isReal ifTrue:[
-            'JAVAVM [info]: missing double flag' infoPrintCR.
+            'JAVAVM [info]: missing double flag in Math>>sin' infoPrintCR.
         ] ifFalse:[
             self halt:'expected double arg'
         ]
@@ -3324,7 +3358,7 @@
     ^ dVal sin
 
     "Created: / 7.1.1998 / 15:41:40 / cg"
-    "Modified: / 4.11.1998 / 17:24:09 / cg"
+    "Modified: / 4.11.1998 / 22:09:30 / cg"
 !
 
 _Math_sqrt:nativeContext
@@ -3335,7 +3369,7 @@
     dVal := nativeContext argAt:1.
     (nativeContext argAt:2) ~~ DUMMY_DOUBLE_HIGHWORD ifTrue:[
         dVal isReal ifTrue:[
-            'JAVAVM [info]: missing double flag' infoPrintCR.
+            'JAVAVM [info]: missing double flag in Math>>sqrt' infoPrintCR.
         ] ifFalse:[
             self halt:'expected double arg'
         ]
@@ -3343,7 +3377,7 @@
     ^ dVal sqrt
 
     "Created: / 7.1.1998 / 15:42:40 / cg"
-    "Modified: / 4.11.1998 / 17:24:24 / cg"
+    "Modified: / 4.11.1998 / 22:09:35 / cg"
 !
 
 _Math_tan:nativeContext
@@ -3354,7 +3388,7 @@
     dVal := nativeContext argAt:1.
     (nativeContext argAt:2) ~~ DUMMY_DOUBLE_HIGHWORD ifTrue:[
         dVal isReal ifTrue:[
-            'JAVAVM [info]: missing double flag' infoPrintCR.
+            'JAVAVM [info]: missing double flag in Math>>tan' infoPrintCR.
         ] ifFalse:[
             self halt:'expected double arg'
         ]
@@ -3362,7 +3396,7 @@
     ^ dVal tan
 
     "Created: / 7.5.1998 / 00:34:03 / cg"
-    "Modified: / 4.11.1998 / 17:24:28 / cg"
+    "Modified: / 4.11.1998 / 22:09:40 / cg"
 !
 
 _Method_getModifiers:nativeContext
@@ -8235,6 +8269,6 @@
 !JavaVM class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaVM.st,v 1.54 1998/11/04 20:57:18 cg Exp $'
+    ^ '$Header: /home/jv/Projects/SmalltalkX/repositories/cvs/stx/libjava/JavaVM.st,v 1.55 1998/11/05 19:15:31 cg Exp $'
 ! !
 JavaVM initialize!