UIPainterTreeView.st
author ca
Sat, 01 Mar 1997 13:44:39 +0100
changeset 72 a5a7054e2b7d
parent 62 0e8573b4329a
child 78 a0a00603a8b6
permissions -rw-r--r--
*** empty log message ***

"
 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
    "
    ^ #menu


! !

!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 string withoutSeparators = aString ]


! !

!UIPainterTreeView methodsFor:'event handling'!

builderViewChanged:what
    "something changed in the builder view
    "
    (what == #tree or:[what == #widgetName]) ifTrue:[
        self updateTree
    ] ifFalse:[
        what ~~ #selection ifTrue:[
            ^ self
        ].
        self disableMaster:selection.
        self setSelection:nil.
    ].

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

        idx ~~ 0 ifTrue:[
            selection isNil ifTrue:[
                |m i|

                m := list at:idx.
                i := m indexOfNonSeparatorStartingAt:1.
                i == 0 ifTrue:[ i := 1 ].
                m := Text string:m.
                m emphasizeFrom:i with:#(#bold #underline).
                list at:idx put:m
            ].
            self addToSelection:idx
        ]
    ].
    selection isNil ifTrue:[
        self setSelection:1
    ]
!

selectionChanged
    "selection has changed
    "
    |sel|

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

!

selectionChangedFrom:oldSelection
    "redraw master
    "
    oldSelection ~= selection ifTrue:[
        self disableMaster:oldSelection.
        super selectionChangedFrom:oldSelection
    ]
! !

!UIPainterTreeView methodsFor:'initialization'!

initialize
    super initialize.

    list := OrderedCollection new.

    self multipleSelectOk:true.
    self action:[:aSelection| self selectionChanged ].
    self doubleClickAction:[:aSelection| builderView selectSubComponents].
! !

!UIPainterTreeView methodsFor:'menu & actions'!

inspectProps
    builderView inspectAttributes
!

inspectSpec
    builderView inspectSpec
!

inspectView
    builderView inspectSelection
!

menu
    |menu|

    (menu := builderView menu) notNil ifTrue:[
        menu addLabels:(
            resources array:#(
                                '-'
                                'misc'
                            )
                        )
             selectors:#(       
                                nil
                                #treeMisc
                        ).

        (builderView numberOfSelections) == 1 ifTrue:[
            menu subMenuAt:#treeMisc put:(self menuMisc)
        ] ifFalse:[
            menu disable:#treeMisc
        ]
    ].
    ^ menu
!

menuMisc

    |menu ispMenu|

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

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

    menu subMenuAt:#inspect put:ispMenu.
  ^ menu


!

ordering
    "change selected view to an index in its subview subviews collection
    "
    |myIdx view spView index names values|

    view := builderView singleSelection.
    view isNil ifTrue:[^ self].

    spView := view superView.
    names  := OrderedCollection new.
    values := OrderedCollection new.
    index  := 1.

    spView allSubViewsDo:[:aView||props|
        aView ~~ view ifTrue:[
            props := builderView propertyOfView:aView.

            props notNil ifTrue:[
                names  add:(props name).
                values add:index
            ]
        ] ifFalse:[
            myIdx := index
        ].
        index := index + 1
    ].

    names isEmpty ifTrue:[
        ^ self
    ].

    index := Dialog choose:'before name:' 
                  fromList:names
                    values:values
                     lines:20
                    cancel:[nil].

    index isNil ifTrue:[
        ^ self
    ].
    myIdx < index ifTrue:[
        index := index - 1
    ].
    (spView changeSequenceOrderFor:view to:index) ifTrue:[
        self builderViewChanged:#tree
    ]
! !

!UIPainterTreeView methodsFor:'redrawing'!

disableMaster:aLineNrOrCollection
    "find and redraw line from master as no master
    "
    |line|

    aLineNrOrCollection notNil ifTrue:[
        aLineNrOrCollection isCollection ifFalse:[
            (line := list at:aLineNrOrCollection) isText ifTrue:[
                list at:aLineNrOrCollection put:(line string).
                self redrawLine:aLineNrOrCollection.
            ]
        ] ifTrue:[
            aLineNrOrCollection do:[:aNumber|
                (line := list at:aNumber) isText ifTrue:[
                    list at:aNumber put:(line string).
                  ^ self redrawLine:aNumber.
                ]
            ]
        ]
    ]
! !

!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$'
! !