NamespaceAwareLookup.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Thu, 26 Aug 2010 11:12:57 +0100
branchjv
changeset 17797 71451ae83564
parent 17796 2fe4a1c91aa9
child 17835 67648e9f2814
permissions -rw-r--r--
Merged with /trunk

"
 COPYRIGHT (c) 2006 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
'From Smalltalk/X, Version:6.1.2 on 19-08-2010 at 10:16:13 PM'                  !

"{ Package: 'stx:libbasic' }"

Lookup subclass:#NamespaceAwareLookup
	instanceVariableNames:''
	classVariableNames:'Instance'
	poolDictionaries:''
	category:'Kernel-Extensions'
!

!NamespaceAwareLookup class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2006 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
! !

!NamespaceAwareLookup class methodsFor:'initialization'!

initialize

    Instance := self basicNew

    "Created: / 10-07-2010 / 21:12:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!NamespaceAwareLookup class methodsFor:'accessing'!

instance

    ^Instance

    "Created: / 20-05-2010 / 11:18:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 10-07-2010 / 21:12:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!NamespaceAwareLookup class methodsFor:'lookup'!

lookupMethodForSelector: selector directedTo: initialSearchClass for: receiver withArguments: argArrayOrNil from: sendingContext 

    "JV @ 2010-07-24
     Following C code is just a performance optimization.
     It is not neccessary, however it speeds things in most
     cases. Such optimization significantly speeds up the IDE
     since class browser involves dozens of super-polymorphic
     sends (> 1000 receiver classes per send-site). 
	"

%{	
    OBJ sendingMthd = __ContextInstPtr(sendingContext)->c_method;
	if (__Class(sendingMthd) == Method &&
		__MethodInstPtr(sendingMthd)->m_annotation == nil) {
		OBJ m = __lookup(initialSearchClass, selector);
		if (m != nil) RETURN ( m );
	}
%}.

    ^Instance lookupMethodForSelector: selector directedTo: initialSearchClass
			  for: receiver withArguments: argArrayOrNil 
			  from: sendingContext 

! !

!NamespaceAwareLookup methodsFor:'lookup'!

lookupMethodForSelector: selector directedTo: initialSearchClass for: receiver withArguments: argArrayOrNil from: sendingContext 
    "Invoked by the VM to ask me for a method to fire.
     For details, see comment inLookup>>lookupMethodForSelector:directedTo:for:withArguments:from:"

    | sendingNs sendingMthd queue seen namespaces  methods |

    "JV @ 2010-07-24
     Following C code is just a performance optimization.
     It is not neccessary, however it speeds things in most
     cases. Such optimization significantly speeds up the IDE
     since class browser involves dozens of super-polymorphic
     sends (> 1000 receiver classes per send-site). 
	"
%{	
    sendingMthd = __ContextInstPtr(sendingContext)->c_method;
	if (__Class(sendingMthd) == Method &&
		__MethodInstPtr(sendingMthd)->m_annotation == nil) {
		OBJ m = __lookup(initialSearchClass, selector);
		if (m != nil) RETURN ( m );
	}
%}.
    "If you remove C code above, uncomment the line below."
    "sendingMthd := sendingContext method."
    sendingNs := sendingMthd 
            ifNil:[nil]                
            ifNotNil:[sendingMthd nameSpace].
	sendingNs := sendingNs.

	"Second chance to speed up things (in case sending method
	 has resource or so)"
%{
	if (sendingNs == nil) {
		OBJ m = __lookup(initialSearchClass, selector);
		if (m != nil) RETURN ( m );
    }
%}.
    "
    Stderr
            show: 'sel='; show: selector; show: ' ns='; show: sendingNs printString; 
            show: ' method=', sendingMthd printString; cr.
	"
       
    sendingNs ifNotNil:[

    seen := Set new.
	namespaces := Array with: sendingNs.

    [namespaces notEmpty] whileTrue: 
        [| imports |
        methods := self 
                    lookupMethodsForSelector: selector 
                    directedTo: initialSearchClass
                    inNamespaces: namespaces.
        methods size == 1 ifTrue:
            [^methods anyOne].
        methods size >  1 ifTrue:
            [^self ambiguousMessageSend: selector 
				   withArgs: argArrayOrNil].
        "No method found"
		seen addAll: namespaces.
        imports := Set new.
        namespaces do:
            [:namespace|
            namespace ifNotNil:
                [namespace imports do:
                    [:import|
					(seen includes: import) ifFalse:
						[imports add: import]]]].
        namespaces := imports].
	].
	
    methods := self lookupMethodsForSelector: selector 
	                directedTo: initialSearchClass.
    methods size == 1 ifTrue:[^methods anyOne].
	
    ^nil

    "Modified: / 21-07-2010 / 17:11:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!NamespaceAwareLookup methodsFor:'lookup - helpers'!

lookupMethodsForSelector: selector directedTo: initialSearchClass 

    "Searches initialSearchClass for a methods with in any namespace"
    ^self 
        lookupMethodsForSelector: selector
        directedTo: initialSearchClass
        suchThat:[:sel :mthd|true].

    "Created: / 19-07-2010 / 15:37:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

lookupMethodsForSelector: selector directedTo: initialSearchClass inNamespaces: namespaces

    "Searches initialSearchClass for a methods with given selector in given namespaces."
    ^self 
        lookupMethodsForSelector: selector
        directedTo: initialSearchClass
        suchThat:[:sel :mthd|namespaces includes: mthd nameSpace].

    "Created: / 19-07-2010 / 15:13:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

lookupMethodsForSelector: selector directedTo: initialSearchClass suchThat: block

    "Searches initialSearchClass for a method with given selector in given nameSpace.
     if no method in given namespace is found, returns nil"

    | searchClass methods seen |

    searchClass := initialSearchClass.
    methods := Set new.
    seen := OrderedCollection new.
    [ searchClass notNil ] whileTrue:        
        [searchClass selectorsAndMethodsDo:
            [:sel :mthd|
            (sel selector = selector 
                and:[(seen includes: mthd nameSpace) not
                    and:[block value: sel value: mthd]]) ifTrue:
                        [methods add: mthd.
                        seen add: mthd nameSpace]].
        searchClass := searchClass superclass].
    ^methods

    "Created: / 19-07-2010 / 15:34:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 20-07-2010 / 10:42:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!NamespaceAwareLookup methodsFor:'trampolines'!

ambiguousMessageSend

    ^self ambiguousMessage:
        (Message 
            selector: #__placeholder__
            arguments: #()
        )

    "Created: / 19-08-2010 / 22:05:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

ambiguousMessageSend: selector withArgs: argArrayOrNil

    | trampoline |

    trampoline := self class methodDictionary at:
                     (#(" 0"ambiguousMessageSend
                        " 1"ambiguousMessageSendWith:
                        " 2"ambiguousMessageSendWith:with:
                        " 3"ambiguousMessageSendWith:with:with:
                        " 4"ambiguousMessageSendWith:with:with:with:
                        " 5"ambiguousMessageSendWith:with:with:with:with:
                        " 6"ambiguousMessageSendWith:with:with:with:with:with:
                        " 7"ambiguousMessageSendWith:with:with:with:with:with:with:
                        " 8"ambiguousMessageSendWith:with:with:with:with:with:with:with:
                        )
                        at: argArrayOrNil size + 1).
    trampoline := trampoline asByteCodeMethod.
    1 to: trampoline numLiterals do:
        [:litNr|
        (trampoline literalAt: litNr) == #__placeholder__
            ifTrue:[(trampoline literalAt: litNr put: selector)]].
    ^trampoline

    "Created: / 19-08-2010 / 22:09:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

ambiguousMessageSendWith: a1

    ^self ambiguousMessage:
        (Message 
            selector: #__placeholder__
            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: #__placeholder__
            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: #__placeholder__
            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: #__placeholder__
            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: #__placeholder__
            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: #__placeholder__
            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: #__placeholder__
            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: #__placeholder__
            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>"
! !

!NamespaceAwareLookup class methodsFor:'documentation'!

version_SVN
    ^ '$Id: NamespaceAwareLookup.st 10570 2010-08-26 10:12:57Z vranyj1 $'
! !

NamespaceAwareLookup initialize!