UIPainterTreeView.st
author ca
Mon, 17 Feb 1997 18:22:30 +0100
changeset 53 d03569a6ff03
parent 49 7f58dd5fc836
child 54 d0b5a33e6df0
permissions -rw-r--r--
checkin from browser

"
 COPYRIGHT (c) 1995 by Claus Gittinger
	      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.
"

SelectionInListView subclass:#UIPainterTreeView
	instanceVariableNames:'builderView'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-UIPainter'
!

!UIPainterTreeView class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1995 by Claus Gittinger
	      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
"
    not yet finished, not yet published, not yet released.
"
! !

!UIPainterTreeView class methodsFor:'constants'!

indent
    "indent for contained element
    "
    ^ 2


! !

!UIPainterTreeView class methodsFor:'defaults'!

defaultMenuMessage   
    "This message is the default yo be sent to the menuHolder to get a menu
    "
    ^ #editMenu


! !

!UIPainterTreeView methodsFor:'accessing'!

builderView:aBuilderView
    builderView := aBuilderView.
    self updateTree.

!

indexOf:aString
    "returns the index of the string entry into my list
    "
    ^ list findFirst:[:aName| aName withoutSeparators = aString ]


! !

!UIPainterTreeView methodsFor:'event handling'!

selectionChanged
    "selection has changed
    "
    |sel|

    selection notNil ifTrue:[
        selection size == 1 ifTrue:[
            sel := (list at:(selection first)) withoutSeparators
        ] ifFalse:[
            sel := OrderedCollection new.
            selection do:[:aNumber|
                aNumber ~~ 1 ifTrue:[
                    sel add:((list at:aNumber) withoutSeparators)
                ]
            ]
        ]
    ].
    builderView selectName:sel

!

update:something

    (something == #tree or:[something == #widgetName]) ifTrue:[
        self updateTree
    ] ifFalse:[
        something == #selection ifFalse:[
            ^ self
        ].
        self setSelection:nil.
    ].

    "update selection
    "
    builderView selectionDo:[:aView||idx|
        idx := self indexOf:(builderView variableNameOf:aView).

        idx ~~ 0 ifTrue:[
            self addToSelection:idx
        ]
    ]
! !

!UIPainterTreeView methodsFor:'initialization'!

initialize
    super initialize.

    list := OrderedCollection new.

    self multipleSelectOk:true.
    self action:[:aSelection| self selectionChanged ].


! !

!UIPainterTreeView methodsFor:'menu & actions'!

editMenu
    |menu ispMenu|

    menu := PopUpMenu labels:#( 'inspect' )
                   selectors:#( #inspect  )
                    receiver:self.

    ispMenu := PopUpMenu labels:#( 'view'        'property'     )
                      selectors:#( #inspectView  #inspectProps  )
                       receiver:self.

    menu subMenuAt:#inspect put:ispMenu.
  ^ menu


!

inspectProps
    builderView inspectAttributes
!

inspectView
    builderView inspectSelection
! !

!UIPainterTreeView methodsFor:'update'!

updateSubTree:aView indent:anIndent
    |name indent|

    name := builderView variableNameOf:aView.

    anIndent ~~ 0 ifTrue:[
        name := (String new:anIndent), name
    ].
    list add:name.

    indent := anIndent + self class indent.

    builderView subviewsOf:aView do:[:subview|
        self updateSubTree:subview indent:indent
    ]


!

updateTree

    selection := nil.
    list      := OrderedCollection new.
    self updateSubTree:builderView indent:0.
    super list:list.

! !

!UIPainterTreeView class methodsFor:'documentation'!

version
    ^ '$Header$'
! !