MethodFinderWindow.st
author Claus Gittinger <cg@exept.de>
Fri, 09 Nov 2001 09:11:59 +0100
changeset 1530 37b18e9a12fb
parent 1529 8c1607c0fbe8
child 1531 9d4f8cd101fa
permissions -rw-r--r--
checkin from browser

"{ Package: 'stx:libtool2' }"

ApplicationModel subclass:#MethodFinderWindow
	instanceVariableNames:'argumentsEditor messageAnswerEditor receiverEditor receiver
		resultSelectors arg2BoxVisible arg1BoxVisible arg4BoxVisible
		arg3BoxVisible argCountHolder argCountList argument1Editor
		argument2Editor argument3Editor argument4Editor resultSelected
		lookAtResultEditor'
	classVariableNames:''
	poolDictionaries:''
	category:'MethodFinder'
!

!MethodFinderWindow class methodsFor:'documentation'!

documentation
"
    ported from Squeak and GUI enhanced by James
"
! !

!MethodFinderWindow class methodsFor:'interface specs'!

windowSpec
    "This resource specification was automatically generated
     by the UIPainter of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the UIPainter may not be able to read the specification."

    "
     UIPainter new openOnClass:MethodFinderWindow andSelector:#windowSpec
     MethodFinderWindow new openInterface:#windowSpec
     MethodFinderWindow open
    "

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'MethodFinder'
          #name: 'MethodFinder'
          #min: #(#Point nil nil)
          #max: #(#Point nil nil)
          #bounds: #(#Rectangle 13 23 563 423)
          #menu: #menu
          #forceRecursiveBackground: false
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#ViewSpec
              #name: 'Box6'
              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
              #level: 1
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#SequenceViewSpec
                    #name: 'List1'
                    #layout: #(#LayoutFrame 0 0 0 0.5 0 0.65 0 1)
                    #hasHorizontalScrollBar: true
                    #hasVerticalScrollBar: true
                    #autoHideScrollBars: true
                    #valueChangeSelector: #updateImplementorsOf:
                    #useIndex: true
                    #sequenceList: #resultHolder
                  )
                 #(#SequenceViewSpec
                    #name: 'List2'
                    #layout: #(#LayoutFrame 0 0.65 0 0 0 1 0 1)
                    #model: #selectedClassOfResultHolder
                    #menu: #implementorListMenu
                    #hasHorizontalScrollBar: true
                    #hasVerticalScrollBar: true
                    #autoHideScrollBars: true
                    #doubleClickSelector: #openBrowserOn:
                    #useIndex: false
                    #sequenceList: #classOfResultHolder
                  )
                 #(#ViewSpec
                    #name: 'Box4'
                    #layout: #(#LayoutFrame 0 0 0 0 0 0.65 -25 0.5)
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#LabelSpec
                          #label: 'Receiver'
                          #name: 'ReceiverLabel'
                          #layout: #(#LayoutFrame -4 0.0162791 0 0 -4 0.293023 24 0)
                          #translateLabel: true
                          #adjust: #left
                        )
                       #(#ComboListSpec
                          #name: 'allowedArgments'
                          #layout: #(#LayoutFrame 0 0.339535 1 0 0 0.653488 23 0)
                          #model: #argCountHolder
                          #comboList: #argCountList
                          #useIndex: true
                        )
                       #(#LabelSpec
                          #label: 'MessageAnswer'
                          #name: 'MessageAnswerLabel'
                          #layout: #(#LayoutFrame 0 0.6693 0 0 0 0.99023 24 0)
                          #translateLabel: true
                          #adjust: #left
                        )
                       #(#HorizontalPanelViewSpec
                          #name: 'HorizontalPanel1'
                          #layout: #(#LayoutFrame 0 0 25 0 0 1 0 1)
                          #horizontalLayout: #fit
                          #verticalLayout: #fit
                          #horizontalSpace: 3
                          #verticalSpace: 3
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#WorkspaceSpec
                                #name: 'ReceiverEditor'
                                #tabable: true
                                #hasHorizontalScrollBar: true
                                #hasVerticalScrollBar: true
                                #miniScrollerHorizontal: true
                                #miniScrollerVertical: true
                                #autoHideScrollBars: true
                                #extent: #(#Point 116 149)
                                #postBuildCallback: #receiverWidgetCreated:
                              )
                             #(#VerticalPanelViewSpec
                                #name: 'VerticalPanel1'
                                #horizontalLayout: #fit
                                #verticalLayout: #fit
                                #horizontalSpace: 3
                                #verticalSpace: 3
                                #component: 
                               #(#SpecCollection
                                  #collection: #(
                                   #(#ViewSpec
                                      #name: 'Box1'
                                      #visibilityChannel: #arg1BoxVisible
                                      #component: 
                                     #(#SpecCollection
                                        #collection: #(
                                         #(#WorkspaceSpec
                                            #name: 'Arg1Editor'
                                            #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
                                            #tabable: true
                                            #hasHorizontalScrollBar: true
                                            #hasVerticalScrollBar: true
                                            #miniScrollerHorizontal: true
                                            #miniScrollerVertical: true
                                            #autoHideScrollBars: true
                                            #postBuildCallback: #argument1WidgetCreated:
                                          )
                                         )
                                       
                                      )
                                      #extent: #(#Point 117 48)
                                    )
                                   #(#ViewSpec
                                      #name: 'Box2'
                                      #visibilityChannel: #arg2BoxVisible
                                      #component: 
                                     #(#SpecCollection
                                        #collection: #(
                                         #(#WorkspaceSpec
                                            #name: 'TextEditor5'
                                            #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
                                            #tabable: true
                                            #hasHorizontalScrollBar: true
                                            #hasVerticalScrollBar: true
                                            #miniScrollerHorizontal: true
                                            #miniScrollerVertical: true
                                            #autoHideScrollBars: true
                                            #postBuildCallback: #argument2WidgetCreated:
                                          )
                                         )
                                       
                                      )
                                      #extent: #(#Point 117 47)
                                    )
                                   #(#ViewSpec
                                      #name: 'Box3'
                                      #visibilityChannel: #arg3BoxVisible
                                      #component: 
                                     #(#SpecCollection
                                        #collection: #(
                                         #(#WorkspaceSpec
                                            #name: 'TextEditor6'
                                            #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
                                            #tabable: true
                                            #hasHorizontalScrollBar: true
                                            #hasVerticalScrollBar: true
                                            #miniScrollerHorizontal: true
                                            #miniScrollerVertical: true
                                            #autoHideScrollBars: true
                                            #postBuildCallback: #argument3WidgetCreated:
                                          )
                                         )
                                       
                                      )
                                      #extent: #(#Point 117 48)
                                    )
                                   )
                                 
                                )
                                #extent: #(#Point 117 149)
                              )
                             #(#WorkspaceSpec
                                #name: 'AnswerEditor'
                                #tabable: true
                                #hasHorizontalScrollBar: true
                                #hasVerticalScrollBar: true
                                #miniScrollerHorizontal: true
                                #miniScrollerVertical: true
                                #autoHideScrollBars: true
                                #extent: #(#Point 117 149)
                                #postBuildCallback: #messageAnswerWidgetCreated:
                              )
                             )
                           
                          )
                        )
                       )
                     
                    )
                  )
                 #(#ViewSpec
                    #name: 'Box5'
                    #layout: #(#LayoutFrame 53 0.224737 -23 0.5 0 0.65 0 0.5)
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#ActionButtonSpec
                          #label: 'Clear'
                          #name: 'Button2'
                          #layout: #(#LayoutFrame 0 0 0 0 -5 0.5 0 1)
                          #translateLabel: true
                          #model: #clear
                        )
                       #(#ActionButtonSpec
                          #label: 'Search'
                          #name: 'Button1'
                          #layout: #(#LayoutFrame 5 0.5 0 0 0 1 0 1)
                          #translateLabel: true
                          #tabable: true
                          #model: #search
                        )
                       )
                     
                    )
                  )
                 )
               
              )
            )
           )
         
        )
      )

    "Modified: / 9.11.2001 / 08:45:48 / cg"
! !

!MethodFinderWindow class methodsFor:'menu specs'!

implementorListMenu
    "This resource specification was automatically generated
     by the MenuEditor of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the MenuEditor may not be able to read the specification."

    "
     MenuEditor new openOnClass:MethodFinderWindow andSelector:#implementorListMenu
     (Menu new fromLiteralArrayEncoding:(MethodFinderWindow implementorListMenu)) startUp
    "

    <resource: #menu>

    ^ 
     #(#Menu
        #(
         #(#MenuItem
            #label: 'Browse'
            #translateLabel: true
            #value: #openBrowserOnSelectedItem
          )
         )
        nil
        nil
      )
!

menu
    "This resource specification was automatically generated
     by the MenuEditor of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the MenuEditor may not be able to read the specification."

    "
     MenuEditor new openOnClass:MethodFinderWindow andSelector:#menu
     (Menu new fromLiteralArrayEncoding:(MethodFinderWindow menu)) startUp
    "

    <resource: #menu>

    ^ 
     #(#Menu
        #(
         #(#MenuItem
            #label: '&File'
            #activeHelpKey: #file
            #submenu: 
           #(#Menu
              #(
               #(#MenuItem
                  #label: 'Exit'
                  #value: #closeRequest
                  #activeHelpKey: #fileExit
                )
               )
              nil
              nil
            )
          )
         #(#MenuItem
            #label: 'Help'
            #startGroup: #right
            #submenu: 
           #(#Menu
              #(
               #(#MenuItem
                  #label: 'Documentation'
                  #value: #openHTMLDocumentation
                  #activeHelpKey: #helpTutorial
                )
               #(#MenuItem
                  #label: 'About MenuEditor...'
                  #value: #openAboutThisApplication
                  #activeHelpKey: #aboutThisAppliaction
                )
               )
              nil
              nil
            )
          )
         )
        nil
        nil
      )
! !

!MethodFinderWindow methodsFor:'accessing'!

receiver
    "Return a copy of the value of the instance variable 'receiver' "

    ^ receiver copy
! !

!MethodFinderWindow methodsFor:'actions'!

argumentEditorsContents

"Determine how many text editors of the arguments are used and store the result
as argCounter. The result being the minimum between how many editors have
expressions in and how many are displayed.

Add each argument string (key)and the evaluated version (value) to an Ordered Dictionary
from each of the text editors.

Return the OrderedDictionary with the expressions from all the text editors. "

     | tempArguments argCounter tempArgument1Editor tempArgument2Editor tempArgument3Editor tempArgument4Editor
associationKey associationValue|

argCounter:=0.

tempArgument1Editor:= (self cleanInputs: argument1Editor contents).
tempArgument2Editor:=  (self cleanInputs: argument2Editor contents).
tempArgument3Editor:= (self cleanInputs: argument3Editor contents).

tempArgument1Editor = '' ifFalse:[argCounter:=argCounter +1].
tempArgument2Editor = '' ifFalse:[argCounter:=argCounter +1].
tempArgument3Editor = '' ifFalse:[argCounter:=argCounter +1].


argCounter:= (argCounter min: (self argCountHolder value -1)).
tempArguments:= OrderedDictionary new:argCounter. 

(argCounter value >= 1) 
                ifTrue:[associationValue:= (Compiler evaluate: tempArgument1Editor).
                        ((self isExpression:tempArgument1Editor) or:[ associationValue isNil]) ifTrue:[                  "looks if an expression is typed in"
                                        associationKey:=associationValue printString]
                                                          ifFalse:[
                                        associationKey:=tempArgument1Editor].

                        tempArguments add: associationKey-> associationValue.
                        ].
(argCounter value >= 2) 
                ifTrue:[ associationValue:= (Compiler evaluate: tempArgument2Editor).
                        (((self isExpression:tempArgument2Editor) or:[ associationValue isNil])) ifTrue:[                  "looks if an expression is typed in"
                                        associationKey:=associationValue printString]
                                                          ifFalse:[
                                        associationKey:=tempArgument2Editor].

                        tempArguments add: associationKey-> associationValue].

(argCounter value >= 3)
                ifTrue:[ associationValue:= (Compiler evaluate: tempArgument3Editor).
                        ((self isExpression:tempArgument3Editor) or:[ associationValue isNil]) ifTrue:[                  "looks if an expression is typed in"
                                        associationKey:=associationValue printString]
                                                          ifFalse:[
                                        associationKey:=tempArgument3Editor].

                        tempArguments add: associationKey-> associationValue].


^tempArguments
!

clear
    "Reset the contents of all the outputs. Return the receiver."

    receiverEditor contents:nil.
    argument1Editor contents:nil.
    argument2Editor contents:nil.
    argument3Editor contents:nil.
    messageAnswerEditor contents:nil.
    self resultHolder value:nil.
    self classOfResultHolder value: nil.
!

isExpression: aString
      "Return true or false depending on if the subString includes certain characters"
(aString includesSubString:': ') ifTrue:[^true].
(aString includesSubString:'+') ifTrue:[^true].
(aString includesSubString:'-') ifTrue:[^true].
(aString includesSubString:'*') ifTrue:[^true].
(aString includesSubString:'/') ifTrue:[^true].
(aString includesSubString:'>') ifTrue:[^true].
(aString includesSubString:'<') ifTrue:[^true].
(aString includesSubString:' new') ifTrue:[^true].
(aString includesSubString:'[') &  (aString includesSubString:']') & (aString includesSubString:'.')
                                ifTrue:[^false].
(aString includesSubString:'.') ifTrue:[^true].

 ^false
!

messageAnswerEditorContents
   "Return a cleaned up version of message answer taken from the messageAnswerEditor
    as an association. The association has cleanedAnswerString as a key and the 
    compiledAnswer as value."

    |   aCleanedAnswerString   compiledAnswer  |

aCleanedAnswerString:=self cleanInputs: (messageAnswerEditor contents). 

compiledAnswer:=Compiler evaluate: aCleanedAnswerString.
((self isExpression:aCleanedAnswerString) or:[compiledAnswer isNil]) ifTrue:[
                        aCleanedAnswerString:=compiledAnswer printString].

^aCleanedAnswerString->compiledAnswer.
!

openBrowserOn:anArgument 
    "Opens browser on theArgument of a specific class. anArgument being a string with the
       Class and the selector upon which the browser is to be opened. Return the receiver."

    |aClass aSelector x theArgument|

    anArgument isNil ifTrue:[
        ^ self
    ].
    (anArgument at:1) == $* ifTrue:[
        theArgument := anArgument copyFrom:2
    ] ifFalse:[
        theArgument := anArgument
    ].
    aClass := theArgument copyUpTo:(Character space).
    x := aClass size + 2.
    aSelector := theArgument copyFrom:x.
    aClass := Smalltalk classNamed:aClass.
    SystemBrowser openInClass:(aClass) selector:(aSelector asSymbol)   

"
MethodFinderWindow new openBrowserOn: '*SmallInteger +'
MethodFinderWindow new openBrowserOn: 'String ,'
MethodFinderWindow new openBrowserOn: 'Number detentBy:atMultiplesOf:snap:' 


"
!

openBrowserOnSelectedItem 
    |sel|

    sel := self selectedClassOfResultHolder value.
    sel isNil ifTrue:[^ self].
    self openBrowserOn:sel
!

receiverEditorContents
   "Return a cleaned up version of receiver taken from the receiverEditor
    as an association. The association has aCleanedRecieverString as a key and the 
    compiledReceiver as value."

    |   aCleanedRecieverString   compiledReceiver  |

aCleanedRecieverString:=self cleanInputs: (receiverEditor contents). 

compiledReceiver:=Compiler evaluate: aCleanedRecieverString.

((self isExpression:aCleanedRecieverString) or:[compiledReceiver isNil]) ifTrue:[
                        aCleanedRecieverString:=compiledReceiver printString].
^aCleanedRecieverString->compiledReceiver.
!

search
"Do a search based on the input in the various text editors. Return the receiver."
| tempReceiver tempAnswer tempArguments anArray resultArray receiverWithArgument mf|
self resultHolder value: nil.               "reset the result list"
self classOfResultHolder value: nil.        "reset the implementorOf list"

tempArguments:=self argumentEditorsContents.
tempReceiver :=self receiverEditorContents .  
tempAnswer:= self messageAnswerEditorContents.   

"self cleanInputRec:tempReceiver arg:tempArguments ans:tempAnswer."


anArray:=Array new:2.  "creates an array which is to be used as input for the method finder."

receiverWithArgument:=self mergReciever: (tempReceiver value) WithArgument: (tempArguments values).

anArray at:1 put:receiverWithArgument;
        at:2 put: tempAnswer value.             

"an array now holds the following array #(#(receiver argument) answer) or #(#(reciever) answer). which should
be suitable input for the method finder."
mf:= MethodFinder new.
resultArray:= mf load: anArray; findMessage. 

((resultArray at:  1 )includesSubString: 'no single') ifTrue:[
                                self warn: (resultArray at:  1 ).
                                ^self
                                                              ].  

"the following then replaces data1 and data2 created by the method finder to the appropriate arguments"
resultArray keysAndValuesDo:[:key :value |   | newValue | 
      newValue:= value replString: 'data1' withString:(tempReceiver key).
(tempArguments size) >= 1 ifTrue:[
      newValue:= newValue replString: 'data2' withString:(tempArguments keyAt:1)].

(tempArguments size) > 1 ifTrue:[
      newValue:= newValue replString: 'data3' withString:(tempArguments keyAt:2).].

(tempArguments size) > 2 ifTrue:[
      newValue:= newValue replString: 'data4' withString:(tempArguments keyAt:3).].


                        "    newValue:= value replString: 'data3' withString:(self messageAnswer key). " 

      newValue:=newValue, ' --> ', (tempAnswer key).

      resultArray at: key put: newValue.

              ].

self resultHolder value: resultArray.
resultSelectors:= mf selectors.   "used to find implementors so we do not have to "
receiver:=tempReceiver            "search the string for the selector found. Stored as an ordered collection"
!

updateImplementorsOf:anInteger 
    "Request the implementors of the selected argument provided by aNumber.
     Return the receiver. "
      |methods classList aNumber|


       (anInteger isNil) ifTrue:[^self].
      anInteger isNil ifTrue:[aNumber:=1]
                      ifFalse:[aNumber:=anInteger].  
      methods:=SystemBrowser findImplementorsOf: (resultSelectors at:aNumber) in:Smalltalk allClasses ignoreCase:false.
      classList:=methods asOrderedCollection collect:[:m | m mclass name , ' ' , m selector].

      classList:=(self markMatchingClasses:(resultSelectors at:aNumber) classesWithSelector:classList).

    self classOfResultHolder value: classList.
! !

!MethodFinderWindow methodsFor:'aspects'!

arg1BoxVisible
"Determines if the box should be visble or not. Return true or false"
    arg1BoxVisible isNil ifTrue:[
        arg1BoxVisible := BlockValue
                              with:[:vh | vh value >= 2 ]
                              argument:(self argCountHolder)
    ].
    ^ arg1BoxVisible.
!

arg2BoxVisible
"Determines if the box should be visble or not. Return true or false"
    arg2BoxVisible isNil ifTrue:[
        arg2BoxVisible := BlockValue
                              with:[:vh | vh value >= 3 ]
                              argument:(self argCountHolder)
    ].
    ^ arg2BoxVisible.
!

arg3BoxVisible
"Determines if the box should be visble or not. Return true or false"
    arg3BoxVisible isNil ifTrue:[
        arg3BoxVisible := BlockValue
                              with:[:vh | vh value >= 4 ]
                              argument:(self argCountHolder)
    ].
    ^ arg3BoxVisible.
!

arg4BoxVisible
"Determines if the box should be visble or not. Return true or false"
    arg4BoxVisible isNil ifTrue:[
        arg4BoxVisible := BlockValue
                              with:[:vh | vh value >= 5 ]
                              argument:(self argCountHolder)
    ].
    ^ arg4BoxVisible.
!

argCountHolder
"Return the value of argCounterHolder which is initialized at 2."
    argCountHolder isNil ifTrue:[
        argCountHolder := 2 asValue.
    ].     
    ^ argCountHolder.
!

argCountList
"Return the argCountList"
    argCountList isNil ifTrue:[
        argCountList := #('0 arguments' '1 argument' '2 arguments' '3 arguments') asValue  
    ].
    ^ argCountList.
!

classOfResultHolder
    "Return a valueHolder which contains a collection with the names of the 
     implementors of a specific message.   "

    |holder|
    (holder := builder bindingAt:#classOfResultHolder) isNil ifTrue:[
        holder := ValueHolder new.
        builder aspectAt:#classOfResultHolder put:holder
    ].
    ^ holder
!

resultHolder
    "Return a value holder which contains the results of a search as a collection."

    |holder|
    (holder := builder bindingAt:#resultHolder) isNil ifTrue:[
        holder := ValueHolder new.
        builder aspectAt:#resultHolder put:holder.
    ].
    ^ holder.
!

selectedClassOfResultHolder
    "Return a valueHolder which contains the index of the selected result class
     (right list)"

    |holder|
    (holder := builder bindingAt:#selectedClassOfResultHolder) isNil ifTrue:[
        holder := ValueHolder new.
        builder aspectAt:#selectedClassOfResultHolder put:holder
    ].
    ^ holder
! !

!MethodFinderWindow methodsFor:'callBacks'!

argument1WidgetCreated: aWidget
"Store the widget as an instance variable. Return the receiver"


        argument1Editor := aWidget scrolledView.
!

argument2WidgetCreated: aWidget
"Store the widget as an instance variable. Return the receiver"


        argument2Editor := aWidget scrolledView.
!

argument3WidgetCreated: aWidget
"Store the widget as an instance variable. Return the receiver"


        argument3Editor := aWidget scrolledView.
!

messageAnswerWidgetCreated: aWidget
"Store the widget as an instance variable. Return the receiver"

        messageAnswerEditor := aWidget scrolledView.
!

openHTMLDocumentation
    HTMLDocumentView openFullOnDocumentationFile:'tools/misc/TOP.html#METHODFINDER'
!

receiverWidgetCreated: aWidget
"Store the widget as an instance variable. Return the receiver"

        receiverEditor := aWidget scrolledView.
! !

!MethodFinderWindow methodsFor:'controlInput'!

cleanInputs: aDirtyString
     "Find and remove common mistakes made by the user. Return the 
     'aStringToBeCleaned' variable"
       | aStringToBeCleaned rs position|

   aStringToBeCleaned:=aDirtyString.

(aStringToBeCleaned endsWith:(Character cr)) ifTrue:[
                        aStringToBeCleaned:=aStringToBeCleaned copyFrom:1 to: (aStringToBeCleaned size -1).].
aStringToBeCleaned:= aStringToBeCleaned withoutSeparators.


rs:=ReadStream on: aStringToBeCleaned.
[rs upToAll: '#true'.  rs atEnd] whileFalse: [
                        position:= rs position. 
                        aStringToBeCleaned:=aStringToBeCleaned copyReplaceFrom: position to: position with: ''. "remove #"
                        rs:=ReadStream on: aStringToBeCleaned.
                        ].

rs:=ReadStream on: aStringToBeCleaned.
[rs upToAll: '#false'.  rs atEnd] whileFalse: [
                        position:= rs position. 
                        aStringToBeCleaned:=aStringToBeCleaned copyReplaceFrom: position to: position with: ''. "remove #"
                        rs:=ReadStream on: aStringToBeCleaned.
                        rs:=ReadStream on: aStringToBeCleaned. ].

[rs upToAll: '#nil'.  rs atEnd] whileFalse: [
                        position:= rs position. 
                        aStringToBeCleaned:=aStringToBeCleaned copyReplaceFrom: position to: position with: ''. "remove #"
                        rs:=ReadStream on: aStringToBeCleaned.  ].
                   ^aStringToBeCleaned    
!

markMatchingClasses: aSelector  classesWithSelector:anOrderedCollection
   " Matches the class of the receiver with all the elements in anOrderedCollection
    (which are classes with selectors). If a match is found it is marked with an asterisk. 
    The classes are then sorted so the the asterisk appears first. Return the 
    markedClassList."

        | unmarkedClassList firstPartOfSelector markedClassList|

        unmarkedClassList:=anOrderedCollection copy.

        unmarkedClassList do:
                [:classAndMethod | | class |
                class:=Compiler evaluate:
                                ((ReadStream on: classAndMethod) upToAll: aSelector).
                (receiver value class == class) ifTrue:
                        [unmarkedClassList add: '*', classAndMethod.
                        unmarkedClassList remove: classAndMethod]].

      unmarkedClassList sort:[:a :b | |rawA rawB|
                    rawA := (a startsWith:'*') ifTrue:[a copyFrom:2] ifFalse:[a].
                    rawB := (b startsWith:'*') ifTrue:[b copyFrom:2] ifFalse:[b].
                    rawA > rawB.  ].
      markedClassList:= unmarkedClassList. 

         ^markedClassList
!

mergReciever: aReceiver WithArgument: arguments

"Puts the receiver and arguments into an array so it can be of a suitable input for the
 MethodFinder. Return an array."

| tempReceiver tempArguments receiverWithArgument|

  tempReceiver:= aReceiver.
 tempArguments :=  arguments.

(tempArguments isEmpty or:[(tempArguments) isNil])
                ifTrue:[  receiverWithArgument:=Array new:1."no argument"
                          receiverWithArgument at:1 put: tempReceiver.     
                        ]
                ifFalse:[
        (tempArguments size = 1)
                        ifTrue:[ receiverWithArgument:=Array new:2.
                                  receiverWithArgument at:1 put: tempReceiver.      
                                  receiverWithArgument at:2 put: (tempArguments at:1)
                                ].  "a receiver with an argument"

        (tempArguments size = 2)
                        ifTrue:[ receiverWithArgument:=Array new:3.
                                  receiverWithArgument at:1 put: tempReceiver.      
                                  (receiverWithArgument at:2 put: (tempArguments at:1)).
                                  (receiverWithArgument at:3 put: (tempArguments at:2))
                                ].  "a receiver with an argument"
        (tempArguments size = 3)
                        ifTrue:[ receiverWithArgument:=Array new:4.
                                  receiverWithArgument at:1 put: tempReceiver.      
                                  (receiverWithArgument at:2 put: (tempArguments at:1)).
                                  (receiverWithArgument at:3 put: (tempArguments at:2)).
                                  (receiverWithArgument at:4 put: (tempArguments at:3)).

                                ].  "a receiver with an argument"

                        ].
^receiverWithArgument
! !

!MethodFinderWindow class methodsFor:'documentation'!

version
    ^ '$Header$'
! !