MethodSelectionBrowser.st
author tz
Thu, 09 Apr 1998 21:12:59 +0200
changeset 771 905c3b4ba565
parent 680 49c81e9cc6f7
child 773 de5c99bd3078
permissions -rw-r--r--
revised

"
 COPYRIGHT (c) 1997-1998 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.
"



ResourceSelectionBrowser subclass:#MethodSelectionBrowser
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-Dialogs'
!

Object subclass:#Method
	instanceVariableNames:'selector protocol'
	classVariableNames:''
	poolDictionaries:''
	privateIn:MethodSelectionBrowser
!

!MethodSelectionBrowser class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1997-1998 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.
"


!

documentation
"
    The MethodSelectionBrowser allows you to browse in class hierarchies
    for selecting methods for you purposes.

    [start with:]
        MethodSelectionBrowser open

    [author:]
        Thomas Zwick
"

! !

!MethodSelectionBrowser class methodsFor:'instance creation'!

request: aTitle onSuperclass: aSuperclass andClass: aClass andSelector: aSelector withTypes: protocolTypes
    "opens a MethodSelectionBrowser on 
	aSuperclassOrSymbol, 
	and aClassOrSymbol, 
	and aSelector,
	with allowed protocolTypes"

    "
    MethodSelectionBrowser
	request: 'Select a Method'
	onSuperclass: #ApplicationModel 
	andClass: #ToolApplicationModel 
	andSelector: #saveIcon 
	withTypes: #(class)      
    "

    ^self new
	title: aTitle;
	openOnSuperclass: aSuperclass
	andClass: aClass
	andSelector: aSelector
	withTypes: protocolTypes


! !

!MethodSelectionBrowser class methodsFor:'list specs'!

resourceMethodColumns
    "returns the columns for the table of the resource methods"

  ^ #(
   #(#DataSetColumnSpec
      #label: ' Selector'
      #'labelAlignment:' #left
      #model: #selector
      #canSelect: false
  )
   (#DataSetColumnSpec
      #label: ' Protocol'
      #'labelAlignment:' #left
      #model: #protocol
      #canSelect: false
  ))




! !

!MethodSelectionBrowser methodsFor:'callbacks - user'!

classSelected
    "after a class selection, read the class or/and instance methods of the selected class"

    self selectionOfClass value isNil ifTrue: [^nil].
    self withWaitCursorDo:
    [
        |clsName contentsBlock|
        resourceTypes isNil ifTrue: [resourceTypes := #(instance class)].
        clsName := self selectionOfClass value name.
        self valueOfClassName value: clsName.
        self class lastSelection: clsName.
        self listOfResourceMethods removeAll.
        contentsBlock := 
        [:protocol|
            |cls|
            (resourceTypes includes: protocol) 
            ifTrue: 
            [
                cls := Smalltalk at: clsName.
                cls := (protocol = #instance) ifTrue: [cls] ifFalse: [cls class].
                self listOfResourceMethods addAll:
                    (cls selectors asOrderedCollection
                     collect: [:sel| Method new selector: sel; protocol: protocol asString])
            ]
        ].
        contentsBlock value: #instance.
        contentsBlock value: #class.
    ]


! !

!MethodSelectionBrowser methodsFor:'instance creation'!

openOnSuperclass: aSuperclassOrSymbol andClass: aClassOrSymbol andSelector: aSelector withTypes: protocolTypes
    "opens a MethodSelectionBrowser on 
	aSuperclassOrSymbol, 
	and aClassOrSymbol, 
	and aSelector,
	with allowed protocolTypes"

    |message type row|

    message := super openOnSuperclass: aSuperclassOrSymbol 
	andClass: aClassOrSymbol 
	andSelector: aSelector 
	withResourceTypes: protocolTypes.

    (message notNil and:
    [((row := self selectionOfResourceMethod value) notNil and:
    [(type := row protocol) = 'class'])])
    ifTrue:
    [   
	message := message replChar:$  withString: ' class '
    ].
    ^message



! !

!MethodSelectionBrowser methodsFor:'startup / release'!

postBuildWith:aBuilder
    "sets the correct title"

    title := 'Method Selection Browser'.

    ^super postBuildWith:aBuilder

! !

!MethodSelectionBrowser::Method methodsFor:'accessing'!

protocol

    ^protocol


!

protocol: aString

    protocol := aString


!

selector

    ^selector

!

selector: aSymbol

    selector := aSymbol

! !

!MethodSelectionBrowser class methodsFor:'documentation'!

version
    ^ '$Header$'
! !