ResourceSelectionBrowser.st
author tz
Tue, 24 Feb 1998 21:28:25 +0100
changeset 675 25a770a729fc
parent 664 6ed67e67d321
child 680 49c81e9cc6f7
permissions -rw-r--r--
some help text changed

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


SelectionBrowser subclass:#ResourceSelectionBrowser
	instanceVariableNames:'resourceMethod resourceClass resourceSuperclass resourceTypes
		allClasses'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-Dialogs'
!

Object subclass:#Row
	instanceVariableNames:'method icon resourceType selector'
	classVariableNames:''
	poolDictionaries:''
	privateIn:ResourceSelectionBrowser
!

!ResourceSelectionBrowser class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1997 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
"
    [start with:]
        ResourceSelectionBrowser open

    [author:]
        Thomas Zwick
"
! !

!ResourceSelectionBrowser class methodsFor:'instance creation'!

request: aTitle onSuperclass: aSuperclass andClass: aClass andSelector: aSelector withResourceTypes: resourceTypes

    "
    ResourceSelectionBrowser
        request: 'Select a Resource Selector'
        onSuperclass: #ApplicationModel 
        andClass: #ToolApplicationModel 
        andSelector: #saveIcon 
        withResourceTypes: #(image) 
    "

    ^self new
        title: aTitle;
        openOnSuperclass: aSuperclass
        andClass: aClass
        andSelector: aSelector
        withResourceTypes: resourceTypes
! !

!ResourceSelectionBrowser class methodsFor:'callbacks - default'!

treeViewChildren

    ^[:aTreeItem| aTreeItem contents subclasses asSortedCollection: [:i1 :i2| i1 name < i2 name]]

!

treeViewContents

    ^Smalltalk at: #Object




!

treeViewIcon

    ^[:aTreeItem|  
        aTreeItem contents subclasses notEmpty 
        ifTrue: 
        [
            aTreeItem hide 
                ifTrue:  [self iconHidingSubclasses] 
                ifFalse: [self iconShowingSubclasses]] 
        ifFalse: 
        [
            self iconClass
        ]
     ]

!

treeViewLabel

    ^[:aTreeItem|aTreeItem contents name]
! !

!ResourceSelectionBrowser class methodsFor:'interface specs'!

windowSpec
    "this window spec was automatically generated by the ST/X UIPainter"

    "do not manually edit this - the painter/builder may not be able to
     handle the specification if its corrupted."

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

    <resource: #canvas>

    ^
     
       #(#FullSpec
          #window: 
           #(#WindowSpec
              #name: 'Resource Selection Browser'
              #layout: #(#LayoutFrame 155 0 154 0 754 0 503 0)
              #label: 'Resource Selection Browser'
              #min: #(#Point 400 300)
              #max: #(#Point 1152 864)
              #bounds: #(#Rectangle 155 154 755 504)
              #usePreferredExtent: false
          )
          #component: 
           #(#SpecCollection
              #collection: 
               #(
                 #(#VariableHorizontalPanelSpec
                    #name: 'variableHorizontalPanel'
                    #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 -40 1.0)
                    #component: 
                     #(#SpecCollection
                        #collection: 
                         #(
                           #(#ViewSpec
                              #name: 'view1'
                              #component: 
                               #(#SpecCollection
                                  #collection: 
                                   #(
                                     #(#SelectionInTreeViewSpec
                                        #name: 'listOfClassesView'
                                        #layout: #(#LayoutFrame 0 0.0 22 0.0 0 1.0 -22 1.0)
                                        #model: #selectionOfClass
                                        #hasHorizontalScrollBar: true
                                        #hasVerticalScrollBar: true
                                        #miniScrollerHorizontal: true
                                        #showDirectoryIndicatorForRoot: false
                                        #showDirectoryIndicator: true
                                        #valueChangeSelector: #classSelected:
                                        #hierarchicalList: #listOfClasses
                                        #contentsSelector: #treeViewContents
                                        #labelSelector: #treeViewLabel
                                        #childrenSelector: #treeViewChildren
                                        #iconSelector: #treeViewIcon
                                    )
                                     #(#InputFieldSpec
                                        #name: 'classNameInputField'
                                        #layout: #(#LayoutFrame 2 0.0 -22 1 -1 1.0 0 1)
                                        #model: #valueOfClassName
                                    )
                                     #(#LabelSpec
                                        #name: 'Label1'
                                        #layout: #(#LayoutFrame 0 0 0 0 297 0 22 0)
                                        #label: ' Class Hierarchy'
                                        #level: 1
                                        #adjust: #left
                                    )
                                  )
                              )
                          )
                           #(#ViewSpec
                              #name: 'view2'
                              #component: 
                               #(#SpecCollection
                                  #collection: 
                                   #(
                                     #(#DataSetSpec
                                        #name: 'resourcesDataSetView'
                                        #layout: #(#LayoutFrame 2 0.0 0 0.0 -2 1.0 -22 1.0)
                                        #model: #selectionOfResource
                                        #hasHorizontalScrollBar: true
                                        #hasVerticalScrollBar: true
                                        #miniScrollerHorizontal: true
                                        #rowClassName: 'ResourceSelectionBrowser::Row'
                                        #dataList: #listOfResources
                                        #useIndex: false
                                        #has3Dsepartors: true
                                        #doubleClickSelector: #resourceDoubleClicked
                                        #columnHolder: #columnsOfDataSetView
                                        #valueChangeSelector: #resourceSelected
                                        #verticalSpacing: 1
                                    )
                                     #(#InputFieldSpec
                                        #name: 'selectorInputField'
                                        #layout: #(#LayoutFrame 2 0.0 -22 1 -2 1.0 0 1)
                                        #model: #valueOfSelector
                                    )
                                  )
                              )
                          )
                        )
                    )
                    #handles: #(#Any 0.5 1.0)
                )
                 #(#UISubSpecification
                    #name: 'SubSpecification'
                    #layout: #(#LayoutFrame 2 0.0 -32 1 -2 1.0 -8 1.0)
                    #majorKey: #ToolApplicationModel
                    #minorKey: #windowSpecForCommitWithoutChannels
                )
              )
          )
      )
! !

!ResourceSelectionBrowser class methodsFor:'list specs'!

columnsOfDataSetView

  ^ #(#(#DataSetColumnSpec
      #width: 20
      #height: 20
      #printSelector: #iconOn:
      #canSelect: false
  )
   #(#DataSetColumnSpec
      #label: ' Selector'
      #'labelAlignment:' #left
      #model: #selector
      #canSelect: false
  )
   (#DataSetColumnSpec
      #label: ' Resource Type'
      #'labelAlignment:' #left
      #model: #resourceType
      #canSelect: false
  ))
! !

!ResourceSelectionBrowser class methodsFor:'resources'!

iconClass
    "Generated by the Image Editor"
    "
    ImageEditor openOnClass:self andSelector:#iconClass
    "

    <resource: #image>

    ^Icon
        constantNamed:#'ResourceSelectionBrowser iconClass'
        ifAbsentPut:[(Depth2Image new) width: 18; height: 16; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(#[0 0 0 0 0 21 85 85 85 5 26 170 170 170 0 26 170 170 170 0 26 170 170 170 0 26 170 170 170 0 26 170 170 170 0 26 170 170 170 0 26 170 170 170 12 26 170 170 170 5 26 170 170 170 0 26 170 170 170 0 26 170 170 170 0 26 170 170 170 0 0 0 0 0 0 0 0 0 0 0]) ; colorMap:((OrderedCollection new add:(Color black); add:(Color white); add:(Color grey:66.9978); add:(Color red:100.0 green:0.0 blue:0.0); yourself)); mask:((Depth1Image new) width: 18; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(#[127 255 128 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 127 255 128]) ; yourself); yourself]!

iconHidingSubclasses
    "Generated by the Image Editor"
    "
    ImageEditor openOnClass:self andSelector:#iconHidingSubclasses
    "

    <resource: #image>

    ^Icon
        constantNamed:#'ResourceSelectionBrowser iconHidingSubclasses'
        ifAbsentPut:[(Depth4Image new) width: 18; height: 16; photometric:(#palette); bitsPerSample:(#(4 )); samplesPerPixel:(1); bits:(#[0 0 0 0 0 0 0 0 0 1 17 17 17 17 17 17 17 48 1 51 51 51 51 51 51 51 32 1 48 0 0 0 51 51 51 32 1 48 68 68 64 51 51 51 32 1 48 0 0 0 51 51 51 32 1 51 50 51 51 51 51 51 32 1 51 50 51 0 0 0 3 32 1 51 50 34 2 34 34 3 32 1 51 50 51 0 0 0 3 32 1 51 50 51 51 51 51 51 32 1 51 50 51 0 0 0 3 32 1 51 50 34 2 34 34 3 32 1 51 51 51 0 0 0 3 32 3 34 34 34 34 34 34 34 32 0 0 0 0 0 0 0 0 0]) ; colorMap:((OrderedCollection new add:(Color black); add:(Color white); add:(Color grey:49.9962); add:(Color grey:66.9978); add:(Color red:100.0 green:0.0 blue:0.0); add:(Color red:0.0 green:100.0 blue:0.0); add:(Color red:0.0 green:0.0 blue:100.0); add:(Color red:0.0 green:100.0 blue:100.0); add:(Color red:100.0 green:100.0 blue:0.0); add:(Color red:100.0 green:0.0 blue:100.0); add:(Color red:49.9962 green:0.0 blue:0.0); add:(Color red:0.0 green:49.9962 blue:0.0); add:(Color red:0.0 green:0.0 blue:49.9962); add:(Color red:0.0 green:49.9962 blue:49.9962); add:(Color red:49.9962 green:49.9962 blue:0.0); add:(Color red:49.9962 green:0.0 blue:49.9962); yourself)); mask:((Depth1Image new) width: 18; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(#[127 255 128 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 127 255 128]) ; yourself); yourself]!

iconShowingSubclasses
    "Generated by the Image Editor"
    "
    ImageEditor openOnClass:self andSelector:#iconShowingSubclasses
    "

    <resource: #image>

    ^Icon
        constantNamed:#'ResourceSelectionBrowser iconShowingSubclasses'
        ifAbsentPut:[(Depth4Image new) width: 18; height: 16; photometric:(#palette); bitsPerSample:(#(4 )); samplesPerPixel:(1); bits:(#[0 0 0 0 0 0 0 0 0 1 17 17 17 17 17 17 17 48 1 51 51 51 51 51 51 51 32 1 48 0 0 0 51 51 51 32 1 48 68 68 64 51 51 51 32 1 48 0 0 0 51 51 51 32 1 51 50 51 51 51 51 51 32 1 51 50 51 0 0 0 3 32 1 51 50 34 5 85 85 3 32 1 51 50 51 0 0 0 3 32 1 51 50 51 51 51 51 51 32 1 51 50 51 0 0 0 3 32 1 51 50 34 8 136 136 3 32 1 51 51 51 0 0 0 3 32 3 34 34 34 34 34 34 34 32 0 0 0 0 0 0 0 0 0]) ; colorMap:((OrderedCollection new add:(Color black); add:(Color white); add:(Color grey:49.9962); add:(Color grey:66.9978); add:(Color red:100.0 green:0.0 blue:0.0); add:(Color red:0.0 green:100.0 blue:0.0); add:(Color red:0.0 green:0.0 blue:100.0); add:(Color red:0.0 green:100.0 blue:100.0); add:(Color red:100.0 green:100.0 blue:0.0); add:(Color red:100.0 green:0.0 blue:100.0); add:(Color red:49.9962 green:0.0 blue:0.0); add:(Color red:0.0 green:49.9962 blue:0.0); add:(Color red:0.0 green:0.0 blue:49.9962); add:(Color red:0.0 green:49.9962 blue:49.9962); add:(Color red:49.9962 green:49.9962 blue:0.0); add:(Color red:49.9962 green:0.0 blue:49.9962); yourself)); mask:((Depth1Image new) width: 18; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(#[127 255 128 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 255 255 192 127 255 128]) ; yourself); yourself]! !

!ResourceSelectionBrowser methodsFor:'accessing - views'!

classNameInputField

    ^builder componentAt: #classNameInputField
!

listOfClassesView

    ^builder componentAt: #listOfClassesView
! !

!ResourceSelectionBrowser methodsFor:'aspects'!

columnsOfDataSetView

    |holder|
    (holder := builder bindingAt:#columnsOfDataSetView) isNil ifTrue:[
        builder aspectAt:#columnsOfDataSetView put:(holder := List new).
        holder addAll: (self class columnsOfDataSetView collect: [:i| i decodeAsLiteralArray]).
    ].
    ^ holder


!

listOfClasses

    |holder|
    (holder := builder bindingAt:#listOfClasses) isNil ifTrue:[
        builder aspectAt:#listOfClasses put: (holder := TreeItem new)
    ].
    ^ holder


!

listOfResources

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

selectionOfClass

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

selectionOfResource

    |holder|
    (holder := builder bindingAt:#selectionOfResource) isNil ifTrue:[
        builder aspectAt:#selectionOfResource put:(holder :=  '' asValue).
    ].
    ^ holder
!

valueOfClassName

    |holder|
    (holder := builder bindingAt:#valueOfClassName) isNil ifTrue:[
        builder aspectAt:#valueOfClassName put:(holder :=  '' asValue).
    ].
    ^ holder
!

valueOfSelector

    |holder|
    (holder := builder bindingAt:#valueOfSelector) isNil ifTrue:[
        builder aspectAt:#valueOfSelector put:(holder :=  '' asValue).
    ].
    ^ holder
! !

!ResourceSelectionBrowser methodsFor:'callbacks - tree view'!

treeViewContents

    ^(Smalltalk at: resourceSuperclass) ? self class treeViewContents


!

treeViewIcon

    ^self class treeViewIcon
!

treeViewLabel

    ^self class treeViewLabel

! !

!ResourceSelectionBrowser methodsFor:'callbacks - user'!

classSelected: anIndex
    
    self selectionOfClass value isNil ifTrue: [^nil].
    self withWaitCursorDo:
    [
        |clsName|
        resourceTypes isNil ifTrue: [resourceTypes := Method resourceTypes].
        clsName := self listOfClassesView list at: anIndex.
        self valueOfClassName value: clsName.
        self class lastSelection: clsName.
        self listOfResources contents:
            ((((Smalltalk at: clsName) 
                class methodDictionary
                asOrderedCollection select: 
                    [:m| m resources notNil and: [resourceTypes includes: m resourceType]]))
             collect: [:m| Row new method: m]).
    ]
!

resourceDoubleClicked

    resourceMethod := self selectionOfResource value.
    accept value: true.
    self close
!

resourceSelected

    resourceMethod := self selectionOfResource value.
    self selectionOfResource value notNil
        ifTrue: [self valueOfSelector value: self selectionOfResource value selector]
! !

!ResourceSelectionBrowser methodsFor:'instance creation'!

openOnSuperclass: aSuperclassOrSymbol andClass: aClassOrSymbol andSelector: aSelector withResourceTypes: aResourceTypes

    |cls sel|
    resourceMethod := aSelector.
    resourceTypes := aResourceTypes.
    resourceSuperclass := aSuperclassOrSymbol isClass ifTrue: [aSuperclassOrSymbol name] ifFalse: [aSuperclassOrSymbol].
    resourceClass := aClassOrSymbol isClass ifTrue: [aClassOrSymbol name] ifFalse: [aClassOrSymbol].
    self valueOfSelector value:(aSelector ? '').

    self open.

    (self selectionOfClass value notNil and:
    [(cls := Smalltalk at: self selectionOfClass value name) isClass and:
    [accept value]]) 
    ifTrue:
    [
        ^cls name, ' ', self valueOfSelector value
    ].
    ^nil
! !

!ResourceSelectionBrowser methodsFor:'startup / release'!

closeCancel

    resourceMethod := nil.
    super closeCancel



!

postBuildWith:aBuilder

    |classSelection classSelectionBlock|
    allClasses := Object withAllSubclasses.
    classSelection :=  resourceClass ? self class lastSelection ? #Object.
    classSelectionBlock := 
    [:clsPattern|                                  
        |foundClass classes|         
        ((foundClass := Smalltalk at: clsPattern printString asSymbol) isClass not or:
        [foundClass name ~= clsPattern])
        ifTrue:
        [
            classes := allClasses select: [:cls| cls name size >= clsPattern size].
            1 to: clsPattern size do: 
            [:i|    
                 classes := classes select: [:cls| (cls name at: i) == (clsPattern at: i)].
            ].    
            foundClass := classes at: 1 ifAbsent: [nil] 
        ].
        foundClass notNil
        ifTrue:
        [
            self listOfClassesView 
                selectFromListOfNames: (foundClass 
                    withAllSuperclasses reverse collect: [:cls| cls name asString]);
                selectedNodeExpand: true
        ].
        self valueOfClassName value: clsPattern
    ].
    self valueOfClassName value: classSelection.  
    self classNameInputField entryCompletionBlock:
    [:value|
        |what|
        what := Smalltalk classnameCompletion: value withoutSpaces.
        self classNameInputField contents:what first.
        (what at:2) size ~~ 1 ifTrue:[Display beep].
        classSelectionBlock value: self classNameInputField contents
    ].
    self listOfClassesView validateDoubleClickBlock: [:aTreeItem | aTreeItem contents ~~ self treeViewContents].
    self listOfClassesView selectedNodeExpand: true.

    [[classSelectionBlock value: classSelection] value.
    self selectionOfResource value: (self listOfResources detect: [:m| m selector == resourceMethod] ifNone: nil)]
    forkAt: 4.

    ^super postBuildWith:aBuilder

! !

!ResourceSelectionBrowser::Row methodsFor:'accessing'!

iconOn:aGC

    icon isNil ifTrue: [icon := method iconOn: aGC].
    ^icon
!

method: aMethod

    method := aMethod
!

resourceType

    resourceType isNil ifTrue: [resourceType := method resourceType].
    ^resourceType
!

selector

    selector isNil ifTrue: [selector := method who methodSelector].
    ^selector
! !

!ResourceSelectionBrowser class methodsFor:'documentation'!

version
    ^ '$Header$'
! !