JavaLookup.st
branchcvs_MAIN
changeset 3360 1a8899091305
parent 3041 7a326f9f8aad
child 3412 df11bb428463
--- a/JavaLookup.st	Fri Feb 14 14:27:26 2014 +0100
+++ b/JavaLookup.st	Wed Jan 28 03:12:08 2015 +0100
@@ -28,7 +28,7 @@
 
 Lookup subclass:#JavaLookup
 	instanceVariableNames:'s2j j2s'
-	classVariableNames:'Instance'
+	classVariableNames:'Instance InvokeRSelectors'
 	poolDictionaries:''
 	category:'Languages-Java-Interop'
 !
@@ -79,6 +79,49 @@
 "
 ! !
 
+!JavaLookup class methodsFor:'initialization'!
+
+initialize
+    "Invoked at system start or when the class is dynamically loaded."
+
+    "/ please change as required (and remove this comment)
+
+    InvokeRSelectors := 
+        #(
+            " 0" #'_INVOKEVIRTUAL_R:_:'
+            " 1" #'_INVOKEVIRTUAL_R:_:_:'
+            " 2" #'_INVOKEVIRTUAL_R:_:_:_:'
+            " 3" #'_INVOKEVIRTUAL_R:_:_:_:_:'
+            " 4" #'_INVOKEVIRTUAL_R:_:_:_:_:_:'
+            " 5" #'_INVOKEVIRTUAL_R:_:_:_:_:_:_:'
+            " 6" #'_INVOKEVIRTUAL_R:_:_:_:_:_:_:_:'
+            " 7" #'_INVOKEVIRTUAL_R:_:_:_:_:_:_:_:_:'
+            " 8" #'_INVOKEVIRTUAL_R:_:_:_:_:_:_:_:_:_:'
+            " 9" #'_INVOKEVIRTUAL_R:_:_:_:_:_:_:_:_:_:_:'
+            "10" #'_INVOKEVIRTUAL_R:_:_:_:_:_:_:_:_:_:_:_:'
+            "11" #'_INVOKEVIRTUAL_R:_:_:_:_:_:_:_:_:_:_:_:_:'
+            "12" #'_INVOKEVIRTUAL_R:_:_:_:_:_:_:_:_:_:_:_:_:_:'
+            "13" #'_INVOKEVIRTUAL_R:_:_:_:_:_:_:_:_:_:_:_:_:_:_:'
+
+            " 0" #'_INVOKEINTERFACE_R:_:'
+            " 1" #'_INVOKEINTERFACE_R:_:_:'
+            " 2" #'_INVOKEINTERFACE_R:_:_:_:'
+            " 3" #'_INVOKEINTERFACE_R:_:_:_:_:'
+            " 4" #'_INVOKEINTERFACE_R:_:_:_:_:_:'
+            " 5" #'_INVOKEINTERFACE_R:_:_:_:_:_:_:'
+            " 6" #'_INVOKEINTERFACE_R:_:_:_:_:_:_:_:'
+            " 7" #'_INVOKEINTERFACE_R:_:_:_:_:_:_:_:_:'
+            " 8" #'_INVOKEINTERFACE_R:_:_:_:_:_:_:_:_:_:'
+            " 9" #'_INVOKEINTERFACE_R:_:_:_:_:_:_:_:_:_:_:'
+            "10" #'_INVOKEINTERFACE_R:_:_:_:_:_:_:_:_:_:_:_:'
+            "11" #'_INVOKEINTERFACE_R:_:_:_:_:_:_:_:_:_:_:_:_:'
+            "12" #'_INVOKEINTERFACE_R:_:_:_:_:_:_:_:_:_:_:_:_:_:'
+            "13" #'_INVOKEINTERFACE_R:_:_:_:_:_:_:_:_:_:_:_:_:_:_:'
+        )
+
+    "Modified (format): / 20-01-2014 / 13:50:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !JavaLookup class methodsFor:'instance creation'!
 
 cleanup
@@ -166,6 +209,9 @@
       Once we will have functinal JIT compiler, we can remove it and Java
       package-private method will be supported correctly in all cases.
      "
+
+     | sender |
+
 %{
     OBJ method;
     method = __lookup(initialSearchClass, selector);
@@ -176,14 +222,37 @@
         RETURN (method);
     }
 %}.
+    "/ Sigh, here we have to care about different code paths. The new JIT compilation scheme
+    "/ sends JavaVM>>_INVOKE*R:... for sends whose methodref is not yet resolved. Thus the stack
+    "/ (starting with sendingContext) may look like:
+    "/ 
+    "/ (0) real sending context - whoever it is
+    "/ 
+    "/ for resolved/interpreted sends or:
+    "/ 
+    "/ (0) performWith:withArguments:
+    "/ (1) _INVOKEVIRTUAL_R:* / _INVOKEINTERFACE_R:*
+    "/ (2) real sending context - whoever it is
+    "/ 
+    "/ for unresolved sends from JIT-compiled code.
+    "/ In tha latter case we have to skip those 2 'implementation' contexts:
+    sender := sendingContext.
+    sender selector == #perform:withArguments: ifTrue:[
+        sender := sender sender.
+        (sender receiver == JavaVM and: [ InvokeRSelectors includes: sender selector ]) ifTrue:[
+            sender := sender sender.
+        ] ifFalse:[
+            sender := sendingContext.
+        ].
+    ].
 
-    sendingContext programmingLanguage isSmalltalk ifTrue:[
+    sender programmingLanguage isSmalltalk ifTrue:[
         aReceiver class theNonMetaclass programmingLanguage isJavaLike ifTrue:[
             ^s2j lookupMethodForSelector:selector directedTo:initialSearchClass for:aReceiver withArguments:argArrayOrNil from:sendingContext ilc: ilcCache.
         ].
     ].
 
-    sendingContext programmingLanguage isJavaLike ifTrue:[
+    sender programmingLanguage isJavaLike ifTrue:[
         initialSearchClass programmingLanguage isSmalltalk ifTrue:[
             "Java to Smalltalk send"
             ^j2s lookupMethodForSelector:selector directedTo:initialSearchClass for:aReceiver withArguments:argArrayOrNil from:sendingContext ilc: ilcCache.
@@ -204,6 +273,7 @@
 
     "Created: / 01-10-2011 / 13:18:40 / Jan Kurs <kursjan@fit.cvut.cz>"
     "Created: / 15-12-2011 / 23:11:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 20-01-2014 / 13:27:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !JavaLookup::Java2Smalltalk methodsFor:'lookup'!
@@ -309,62 +379,26 @@
 lookupMethodForSelector: selector directedTo: initialSearchClass for: receiver withArguments: argArrayOrNil from: sendingContext ilc: ilc 
     "
      As a courtesy to a Smalltalker, try to map smalltalk selectors to a java ones.
-     Returns JavaMethodDescriptor or nil."
+     Returns a method or nil"
     
-    | name  nameSizePlusOne  candidates  finder  static  cls  m |
+    | name candidates m |
+
     name := selector upTo: $:.
-    nameSizePlusOne := name size + 1.
-    static := receiver isBehavior.
     candidates := OrderedCollection new.
-    finder := [
-        :cls | 
-        cls methodDictionary 
-            keysAndValuesDo: [
-                :sel :mthd | 
-                "candidates may contain a method with same selector ->
-                 do not add super-class's method"
-                (candidates contains: [:each | each selector == sel ]) ifFalse: [
-                    (mthd mclass ~~ ProxyMethod 
-                        and: [
-                            ((sel size >= nameSizePlusOne) 
-                                and: [ (sel at: nameSizePlusOne) == $( and: [ (sel startsWith: name) ] ]) 
-                                    and: [ mthd descriptor numArgs == argArrayOrNil size ]
-                        ]) 
-                            ifTrue: [ candidates add: mthd ]
-                ]
-            ]
-    ].
-     "Search class for method candidates"
-    cls := initialSearchClass theNonMetaclass.
-    static ifTrue: [ finder value: cls ] ifFalse: [
-        [ cls notNil and: [ cls ~~ JavaObject ] ] whileTrue: [
-            finder value: cls.
-            cls := cls superclass.
-        ]
-    ].
+
+    candidates := self lookupMethodsForSelector: selector in: initialSearchClass ? receiver class static: receiver isBehavior.
     candidates notEmpty ifTrue: [
-        "because java compiler generates synthetic method, when overriden
-         method has narrower return type than method from superclass/interface,
-         we don't take these particular synthetic methods as candidates, they just
-         delegate to overridden methods."
-
-        ((candidates size > 1) and:[candidates anySatisfy:[:each|each isSynthetic]]) ifTrue:[
-            | candidatesPerNameAndArg |
-
-            candidatesPerNameAndArg := Dictionary new.
-            candidates do:[:each|
-                | nameAndArgs |
-
-                nameAndArgs := each selector upTo:$).
-                candidatesPerNameAndArg at: nameAndArgs ifAbsentPut:[each]. 
-            ].
-            candidates := candidatesPerNameAndArg values.
-
-        ].        
+        "/ If candidates contains only one method that is not Java method,
+        "/ then return this method. It's either a smalltalk extension or
+        "/ ambiguous method trampoline...
+        (candidates size == 1 and:[ (m := candidates anElement) isJavaMethod not]) ifTrue:[ 
+            ilc notNil ifTrue: [ ilc bindTo: m forClass: receiver class ].
+            ^ m.
+        ].
         m := self 
                 compileProxyWithSelector: selector
                 in: receiver class
-                calling: candidates.
+                candidates: candidates.
         ilc notNil ifTrue: [ ilc bindTo: m forClass: receiver class ].
          "Install the proxy"
         self 
@@ -403,9 +437,125 @@
     "Created: / 19-11-2011 / 13:03:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 01-01-2012 / 19:58:59 / kursjan <kursjan@fit.cvut.cz>"
     "Modified (comment): / 02-01-2012 / 10:35:25 / kursjan <kursjan@fit.cvut.cz>"
-    "Modified: / 17-03-2012 / 17:22:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 18-11-2012 / 18:17:28 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
     "Modified: / 16-12-2012 / 13:59:55 / Marcel Hlopko <marcel.hlopko@fit.cvut.cz>"
+    "Modified: / 19-03-2014 / 17:27:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+lookupMethodsForSelector: selector in: initialSearchClass static: static
+    "Lookup all matching methods for given (Smalltalk) selector starting with
+     `initialSearchClass`. If `static` is true, then search for static methods,
+     otherwise for search instance methods.
+
+     Returns a list of method candidates that match given selector.
+    "
+    
+    | name nameSizePlusOne numArgs candidates  finder1 finder2  cls ifacesQ ifacesSeen |
+
+    name := selector upTo: $:.
+    nameSizePlusOne := name size + 1.
+    numArgs := selector numArgs.
+    candidates := OrderedCollection new.
+    ifacesSeen := Set new.
+
+    "/ Method finder to lookup extension methods in interfaces...
+    finder1 := [:cls |
+        cls interfaces notEmptyOrNil ifTrue:[
+            ifacesQ := OrderedCollection with: (cls interfaces).
+            [ ifacesQ notEmpty ] whileTrue:[
+                | ifaces newIfaces extension |
+
+                ifaces := ifacesQ removeFirst.
+                extension := nil.
+                ifaces do:[:iface |
+                    (ifacesSeen includes: iface) ifFalse:[
+                        | m |
+
+                        ifacesSeen add: iface.
+                        m := iface compiledMethodAt: selector.
+                        m notNil ifTrue:[
+                            extension notNil ifTrue:[
+                                "/ Ambiguous, return error trampoline
+                                | sel |
+
+                                sel :=
+                                    #(  ambiguousMessageSend
+                                        ambiguousMessageSendWith:
+                                        ambiguousMessageSendWith:With:
+                                        ambiguousMessageSendWith:With:With:
+                                        ambiguousMessageSendWith:With:With:With:
+                                        ambiguousMessageSendWith:With:With:With:With:
+                                        ambiguousMessageSendWith:With:With:With:With:With:
+                                        ambiguousMessageSendWith:With:With:With:With:With:With:
+                                        ambiguousMessageSendWith:With:With:With:With:With:With:With:
+                                    ) at: selector numArgs + 1.
+                                ^ Array with: (self class compiledMethodAt: sel).
+                            ] ifFalse:[
+                                extension := m.
+                            ].
+                        ].
+                    ].
+                ].
+                extension notNil ifTrue:[ ^ Array with: extension ].
+                newIfaces := Set new.
+                ifaces do:[:iface| newIfaces addAll: iface interfaces ].
+                newIfaces notEmpty ifTrue:[
+                    ifacesQ add: newIfaces.
+                ].        
+            ].
+        ].
+    ]. 
+
+    "/ Method finder to map Java methods to smalltalk selectors...
+    finder2 := [:cls |
+        cls methodDictionary keysAndValuesDo: [:sel :mthd | 
+            "candidates may contain a method with same selector ->
+             do not add super-class's method"
+            (candidates contains: [:each | each selector == sel ]) ifFalse: [
+                (mthd mclass ~~ ProxyMethod 
+                    and: [
+                        ((sel size >= nameSizePlusOne) 
+                            and: [ (sel at: nameSizePlusOne) == $( and: [ (sel startsWith: name) ] ]) 
+                                and: [ mthd descriptor numArgs == numArgs ]
+                    ]) 
+                        ifTrue: [ candidates add: mthd ]
+            ]
+        ]
+    ].
+    "Search class for method candidates"
+    cls := initialSearchClass theNonMetaclass.
+    static ifTrue: [ 
+        finder2 value: cls 
+    ] ifFalse: [
+        [ cls notNil and: [ cls ~~ JavaObject ] ] whileTrue: [
+            finder1 value: cls.
+            finder2 value: cls.
+            cls := cls superclass.
+        ]
+    ].
+
+    candidates notEmpty ifTrue:[ 
+        "because java compiler generates synthetic method, when overriden
+         method has narrows return type than method from superclass/interface,
+         we don't take these particular synthetic methods as candidates, they just
+         delegate to overridden methods."
+        ((candidates size > 1) and:[candidates anySatisfy:[:each|each isSynthetic]]) ifTrue:[
+            | candidatesPerNameAndArg |
+
+            candidatesPerNameAndArg := Dictionary new.
+            candidates do:[:each|
+                | nameAndArgs |
+
+                nameAndArgs := each selector upTo:$).
+                candidatesPerNameAndArg at: nameAndArgs ifAbsentPut:[each]. 
+            ].
+            candidates := candidatesPerNameAndArg values.
+        ].        
+    ].
+
+    ^ candidates.
+
+    "Created: / 19-03-2014 / 16:24:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !JavaLookup::Smalltalk2Java methodsFor:'lookup (old)'!
@@ -550,6 +700,115 @@
     "Created: / 06-09-2011 / 22:20:34 / Jan Kurs <kursjan@fit.cvut.cz>"
 ! !
 
+!JavaLookup::Smalltalk2Java methodsFor:'trampolines'!
+
+ambiguousMessageSend
+
+    ^self ambiguousMessage:
+        (Message 
+            selector: thisContext selector
+            arguments: #()
+        )
+
+    "Created: / 19-08-2010 / 22:05:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+ambiguousMessageSendWith: a1
+
+    ^self ambiguousMessage:
+        (Message 
+            selector: thisContext selector
+            arguments: (Array with: a1)
+        )
+
+    "Created: / 19-08-2010 / 22:06:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+ambiguousMessageSendWith: a1 with: a2
+
+    ^self ambiguousMessage:
+        (Message 
+            selector: thisContext selector
+            arguments: (Array with: a1 with: a2)
+        )
+
+    "Created: / 19-08-2010 / 22:06:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+ambiguousMessageSendWith: a1 with: a2 with: a3
+
+    ^self ambiguousMessage:
+        (Message 
+            selector: thisContext selector
+            arguments: (Array with: a1 with: a2 with: a3)
+        )
+
+    "Created: / 19-08-2010 / 22:06:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+ambiguousMessageSendWith: a1 with: a2 with: a3 with: a4
+
+    ^self ambiguousMessage:
+        (Message 
+            selector: thisContext selector
+            arguments: (Array with: a1 with: a2 with: a3 with: a4)
+        )
+
+    "Created: / 19-08-2010 / 22:06:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+ambiguousMessageSendWith: a1 with: a2 with: a3 with: a4
+                    with: a5
+
+    ^self ambiguousMessage:
+        (Message 
+            selector: thisContext selector
+            arguments: (Array with: a1 with: a2 with: a3 with: a4
+                              with: a5)
+        )
+
+    "Created: / 19-08-2010 / 22:07:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+ambiguousMessageSendWith: a1 with: a2 with: a3 with: a4
+                    with: a5 with: a6
+
+    ^self ambiguousMessage:
+        (Message 
+            selector: thisContext selector
+            arguments: (Array with: a1 with: a2 with: a3 with: a4
+                              with: a5 with: a6)
+        )
+
+    "Created: / 19-08-2010 / 22:07:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+ambiguousMessageSendWith: a1 with: a2 with: a3 with: a4
+                    with: a5 with: a6 with: a7
+
+    ^self ambiguousMessage:
+        (Message 
+            selector: thisContext selector
+            arguments: (Array with: a1 with: a2 with: a3 with: a4
+                              with: a5 with: a6 with: a7)
+        )
+
+    "Created: / 19-08-2010 / 22:07:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+ambiguousMessageSendWith: a1 with: a2 with: a3 with: a4
+                    with: a5 with: a6 with: a7 with: a8
+
+    ^self ambiguousMessage:
+        (Message 
+            selector: thisContext selector
+            arguments: (Array with: a1 with: a2 with: a3 with: a4
+                              with: a5 with: a6 with: a7 with: a8)
+        )
+
+    "Created: / 19-08-2010 / 22:08:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !JavaLookup::Smalltalk2Java methodsFor:'utilities'!
 
 addSelector:selector withMethod:proxy toClass:class 
@@ -594,7 +853,7 @@
     "Created: / 17-03-2012 / 16:54:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-compileProxyWithSelector:selector in:class calling:methods 
+compileProxyWithSelector:selector in:class candidates:candidates 
     "For given set of methods, create a dispatching proxy with given selector.
      This method performs typechecks on arguments and dispatch to proper method"
     
@@ -604,31 +863,34 @@
     fallback := self 
                 fallbackWithSelector:selector
                 in:class
-                calling:methods
                 compiler:compiler.
      "Generate and install dispatching tree..."
     selector numArgs == 0 ifTrue:[
         "If method has no arguments, no dynamic method dispatch is
-         required. Therefore, no fallback is needed. In theory, there is
-         no need for proxy method at all..."
-        self assert:methods size == 1.
-        body := compiler newJavaMethodInvocation:methods anyOne.
+         required (method cannot be overloaded)  Therefore, no fallback is 
+         needed. In theory, there is no need for proxy method at all..."
+        self assert:candidates size == 1.
+        body := compiler newJavaMethodInvocation:candidates anyOne.
     ] ifFalse:[
         "JV@2012-01-01: Based on discussion with JK, if there is no overloaded method
          DO NOT compile guard, call the method directly. We'll see..."
-        methods size == 1 ifTrue:[
-            body := (compiler newJavaMethodInvocation:methods anElement).
-        ] ifFalse:[
+        "JV@2014-03-19: NO, DON'T DO THAT, that's fundamentally wrong.
+         A new overloaded method may come in future, for example
+         a new subclass may get loaded or a new method is added to
+         some class along the chain..."
+"/        methods size == 1 ifTrue:[
+"/            body := (compiler newJavaMethodInvocation:methods anElement).
+"/        ] ifFalse:[
             "For every method, create a guard and add it"
             body := fallback.
-        ]
+"/        ]
     ].
     
     "/Create and install proxy
     
     proxy := compiler 
                 compile:body
-                arguments:methods anyOne descriptor numPhysicalArgs
+                arguments:selector numArgs
                 selector:selector.
     
 "/    self halt.
@@ -640,16 +902,14 @@
     
     ^ proxy
 
-    "Created: / 16-12-2011 / 23:21:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 30-12-2011 / 14:44:11 / kursjan <kursjan@fit.cvut.cz>"
-    "Modified: / 15-02-2012 / 01:07:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 19-03-2014 / 17:28:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-compileProxyWithSelector: selector in: class calling: methods receiver: receiver arguments: arguments
+compileProxyWithSelector: selector in: class receiver: receiver arguments: arguments
     "For given receiver and arguments, selects apropriate method from methods
      and compile guard"
 
-    | compiler method proxy condition invocation fallback guard |
+    | compiler candidates method proxy condition invocation fallback guard |
 
     compiler := ProxyMethodCompiler new.    
 
@@ -657,10 +917,11 @@
     proxy notNil ifTrue:[
         fallback := proxy body    
     ] ifFalse:[
-        fallback := self fallbackWithSelector: selector in: class calling: methods compiler: compiler.
+        fallback := self fallbackWithSelector: selector in: class compiler: compiler.
     ].
 
-    method := self selectMethodFrom: methods arguments: arguments.
+    candidates := self lookupMethodsForSelector: selector in: receiver class static: receiver isBehavior.    
+    method := self selectMethodFrom: candidates arguments: arguments.
     invocation := compiler newJavaMethodInvocation:method.
 
     condition := nil.
@@ -680,37 +941,40 @@
 
     proxy := compiler 
                 compile:guard
-                arguments:methods anyOne descriptor numPhysicalArgs
+                arguments:selector numArgs
                 selector:selector.
 
     self 
         addSelector:selector
         withMethod:proxy
-        toClass:class.
+        toClass:receiver class.
 
-    "Created: / 03-01-2012 / 22:14:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 19-03-2014 / 17:27:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-fallbackWithSelector:selector in:class calling:methods compiler:compiler 
+fallbackWithSelector:selector in:class compiler:compiler 
     ^ compiler 
         newJavaBlockInvocation:[:receiver :arguments | 
             self 
                 compileProxyWithSelector:selector
                 in:class
-                calling:methods
                 receiver:receiver
                 arguments:arguments.
             "/self breakPoint:#jv.
             receiver perform:selector withArguments:arguments.
         ]
 
-    "Modified: / 04-01-2012 / 21:35:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 19-03-2014 / 17:25:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 selectMethodFrom: methods arguments: arguments
 
     | candidates |
 
+    methods size == 1 ifTrue:[ 
+        ^ methods anElement.
+    ].
+
     candidates := methods.
     arguments withIndexDo:[:arg :index|
         | cls |
@@ -728,12 +992,12 @@
     candidates size == 1 ifTrue:[
         ^candidates anElement
     ].
-
-    self halt: 'Unfinished - ambiguous'
+    self breakPoint: #jv."/ This is a timed bomb...
+    ^ candidates first
 
     "Created: / 03-01-2012 / 21:40:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 03-04-2012 / 13:59:13 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
-    "Modified (format): / 20-04-2012 / 19:58:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 19-03-2014 / 16:41:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 type: actual matches: formal 
@@ -750,19 +1014,34 @@
     ].
      "nil matches any formal type (to follow undocumented
      feature of JVM (also seen in CHECKCAST instruction :))" 
-     actual == UndefinedObject ifTrue: [ ^ true ].
+    actual == UndefinedObject ifTrue: [ ^ true ].
+
+    "char[] matches smalltal string..."
+    formal == Unicode16String ifTrue:[
+        ^ actual inheritsFrom: CharacterArray
+    ].
+
     actual isJavaPrimitiveType ifTrue: [
         ^ formal isJavaWrapperClass and: [ formal == actual javaWrapperClass ]
     ].
-    (actual includesBehavior: String "care about multi-byte strings") ifTrue: [
-        ^ formal name == #'java/lang/String'
+    (actual includesBehavior: String) ifTrue: [
+        ^ formal binaryName == #'java/lang/String'
     ].
+
+    (actual includesBehavior: Unicode16String) ifTrue: [
+        ^ formal binaryName == #'java/lang/String'
+    ].
+
+    (actual includesBehavior: Unicode32String) ifTrue: [
+        ^ formal binaryName == #'java/lang/String'
+    ].
+
     ^ JavaVM canCast: actual to: formal
 
     "Created: / 03-01-2012 / 22:36:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 03-04-2012 / 13:59:28 / Marcel Hlopko <hlopkmar@fel.cvut.cz>"
-    "Modified: / 29-10-2012 / 07:28:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 16-12-2012 / 11:44:17 / Marcel Hlopko <marcel.hlopko@fit.cvut.cz>"
+    "Modified: / 21-01-2014 / 14:42:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !JavaLookup::Smalltalk2Java methodsFor:'utilities (old)'!
@@ -820,7 +1099,7 @@
 !JavaLookup class methodsFor:'documentation'!
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libjava/JavaLookup.st,v 1.6 2013-09-06 00:41:24 vrany Exp $'
+    ^ '$Header: /cvs/stx/stx/libjava/JavaLookup.st,v 1.7 2015-01-28 02:10:50 vrany Exp $'
 !
 
 version_HG
@@ -829,6 +1108,8 @@
 !
 
 version_SVN
-    ^ '§Id§'
+    ^ 'Id'
 ! !
 
+
+JavaLookup initialize!