SelectionInTreeView.st
author Claus Gittinger <cg@exept.de>
Sat, 11 Oct 1997 14:25:11 +0200
changeset 552 1b84811f7c45
parent 551 b9d3ddbc3365
child 569 2a1014d6697c
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1997 by eXept Software AG / 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:#SelectionInTreeView
	instanceVariableNames:'validateDoubleClickBlock selectionHolder rootHolder imageWidth
		showLines listOfNodes imageInset textInset openIndicator
		computeResources closeIndicator showRoot extentOpenIndicator
		extentCloseIndicator showDirectoryIndicator indicatorExtentDiv2
		imageOpened imageClosed imageItem'
	classVariableNames:'ImageOpened ImageClosed ImageItem OpenIndicator CloseIndicator'
	poolDictionaries:''
	category:'Views-Text'
!

!SelectionInTreeView class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1997 by eXept Software AG / 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
"
    somewhat like a SelectionInListView; but specialized for hierarchical (i.e. tree-like)
    lists and adds the functions to show/hide subtrees. 
    Requires SelectionInTree as model and TreeItem (or compatible) list entries.

    This class obsoletes SelectionInTreeView, which is no longer
    maintained but kept for backward compatibility.


    [see also:]
        SelectionInTree
        TreeItem
        SelectionInTreeView
        SelectionInListView
        FileSelectionTree

    [author:]
        Claus Atzkern
"

!

examples
"
    shows the tree of smalltalk classes:
                                                                        [exBegin]
      |top sel|

      top := StandardSystemView new; extent:300@300.
      sel := SelectionInTreeView new.
      sel root:(TreeItem newAsTreeFromSmalltalkClass:Object).
      sel action:[:nr | Transcript show:'selected:'; showCR:nr].
      top add:(ScrollableView forView:sel) in:((0.0 @ 0.0 ) corner:( 1.0 @ 1.0)).
      top open.
                                                                        [exEnd]



    same, including nil-subclasses (i.e. really all classes):
                                                                        [exBegin]
      |top sel|

      top := StandardSystemView new; extent:300@300.
      sel := SelectionInTreeView new.
      sel root:(TreeItem newAsTreeFromSmalltalkClass:nil).
      sel action:[:nr | Transcript show:'selected:'; showCR:nr].

      top add:(ScrollableView forView:sel) in:((0.0 @ 0.0 ) corner:( 1.0 @ 1.0)).
      top open.
                                                                        [exEnd]



    shows the tree of smalltalk classes; show directory indication and no
    lines.
                                                                        [exBegin]
      |top sel|

      top := StandardSystemView new; extent:300@300.
      sel := SelectionInTreeView new.
      sel showLines:false.
      sel showDirectoryIndicator:true.
      sel root:(TreeItem newAsTreeFromSmalltalkClass:Object).
      sel action:[:nr | Transcript show:'selected:'; showCR:nr].
      top add:(ScrollableView forView:sel) in:((0.0 @ 0.0 ) corner:( 1.0 @ 1.0)).
      top open.
                                                                        [exEnd]
"


! !

!SelectionInTreeView class methodsFor:'constants'!

minImageInset
    "returns minimum inset from directory indication to image
    "
  ^ 6


! !

!SelectionInTreeView class methodsFor:'default images'!

closeIndicator
    CloseIndicator isNil ifTrue:[
        CloseIndicator := Image fromFile:('xpmBitmaps/plus.xpm').
    ].
  ^ CloseIndicator
"
CloseIndicator := nil
"
!

imageClosed
    ImageClosed isNil ifTrue:[
        ImageClosed := Image fromFile:('xpmBitmaps/document_images/tiny_yellow_dir.xpm').
    ].
  ^ ImageClosed
"
ImageClosed := nil
"

!

imageItem
    ImageItem isNil ifTrue:[
        ImageItem := Image fromFile:('xpmBitmaps/document_images/tiny_file_plain.xpm')  

    ].
  ^ ImageItem
"
ImageItem := nil
"

!

imageOpened
    ImageOpened isNil ifTrue:[
        ImageOpened := Image fromFile:('xpmBitmaps/document_images/tiny_yellow_dir_open.xpm').

    ].
  ^ ImageOpened
"
ImageOpened := nil
"
!

openIndicator
    OpenIndicator isNil ifTrue:[
        OpenIndicator := Image fromFile:('xpmBitmaps/minus.xpm').
    ].
  ^ OpenIndicator
"
OpenIndicator := nil
"

! !

!SelectionInTreeView methodsFor:'accessing'!

nodeAtIndex:anIndex
    "returns node at an index or nil
    "
    (anIndex notNil and:[anIndex ~~ 0 and:[anIndex <= listOfNodes size]]) ifTrue:[
        ^ listOfNodes at:anIndex
    ].
  ^ nil
!

root
    "gets the root of the model; the first item into list.
    "
    ^ self nodeAtIndex:1
!

root:aRoot
    "sets the root of the model; the first item into list.
    "
    aRoot notNil ifTrue:[aRoot expand].
    model root:aRoot
!

textInset
    "get the left inset of the text label
    "
    ^ textInset
!

textInset:anInset
    "set the left inset of the text label
    "
    anInset ~~ textInset ifTrue:[
        anInset >= 0 ifTrue:[
            textInset := anInset.
            self invalidate
        ] ifFalse:[
            self error
        ]
    ].
! !

!SelectionInTreeView methodsFor:'accessing-behavior'!

showDirectoryIndicator
    "returns true if directories has an open/closed indicator
    "
  ^ showDirectoryIndicator
!

showDirectoryIndicator:aState
    "set or clear open/closed indicator for directories
    "
    "show or hide lines
    "
    aState ~~ showDirectoryIndicator ifTrue:[
        showDirectoryIndicator := aState.
        self recomputeDirectoryIndicator.
        self invalidate
    ].
!

showLines
    "returns true if lines are shown
    "
  ^ showLines
!

showLines:aState
    "show or hide lines
    "
    aState ~~ showLines ifTrue:[
        showLines := aState.
        self invalidate
    ].
!

showRoot
    "list with or without root
    "
  ^ showRoot
!

showRoot:aState
    "list with or without root
    "
    showRoot ~~ aState ifTrue:[
        model showRoot:(showRoot := aState)
    ].
!

validateDoubleClickBlock
    "set the conditionBlock; this block is evaluated before a doubleClick action
     on a node will be performed. In case of returning false, the doubleClick will
     not be handled.
   "
   ^ validateDoubleClickBlock


!

validateDoubleClickBlock:aOneArgBlock
    "set the conditionBlock; this block is evaluated before a doubleClick action
     on a node will be performed. In case of returning false, the doubleClick will
     not be handled.
   "
   validateDoubleClickBlock := aOneArgBlock


! !

!SelectionInTreeView methodsFor:'accessing-channels'!

rootHolder
    "get the holder which keeps the hierarchical list entry or nil
    "
    ^ rootHolder
!

rootHolder:aValueHolder
    "set the holder which keeps the hierarchical list entry or nil
    "
    rootHolder notNil ifTrue:[
        rootHolder removeDependent:self
    ].
    (rootHolder := aValueHolder) notNil ifTrue:[
        rootHolder addDependent:self.
        self rootFromModel.
    ].
!

selectionHolder
    "get the holder which keeps a list of selected items or nil
    "
    ^ selectionHolder

!

selectionHolder:aHolder
    "set the holder which keeps a list of selected items or nil
    "
    selectionHolder notNil ifTrue:[
        selectionHolder removeDependent:self
    ].

    (selectionHolder := aHolder) notNil ifTrue:[
        selectionHolder addDependent:self.
        self selectionFromModel
    ].

! !

!SelectionInTreeView methodsFor:'accessing-images'!

imageClosed
    "return the value of the instance variable 'imageClosed' (automatically generated)"

    ^ imageClosed

    "Created: 3.7.1997 / 12:34:31 / cg"
!

imageClosed:anImage
    "set the value of the instance variable 'imageClosed' (automatically generated)"

    imageClosed := anImage onDevice:device.
!

imageItem
    "return the value of the instance variable 'imageItem' (automatically generated)"

    ^ imageItem

    "Created: 3.7.1997 / 12:34:34 / cg"
!

imageItem:anImage
    "set the value of the instance variable 'imageItem' (automatically generated)"

    imageItem := anImage onDevice:device.
!

imageOpened
    "return the value of the instance variable 'imageOpened' (automatically generated)"

    ^ imageOpened

    "Created: 3.7.1997 / 12:34:28 / cg"
!

imageOpened:anImage
    "set the value of the instance variable 'imageOpened' (automatically generated)"

    imageOpened := anImage onDevice:device.
! !

!SelectionInTreeView methodsFor:'change & update'!

update:something with:aParameter from:aModel
    "one of my models changed its value
    "
    aModel == rootHolder ifTrue:[
        ^ self rootFromModel
    ].
    aModel == selectionHolder ifTrue:[
        ^ self selectionFromModel
    ].

    ^ super update:something with:aParameter from:aModel.



! !

!SelectionInTreeView methodsFor:'drawing'!

drawLine:line atX:atX inVisible:visLineNr with:fg and:bg
    self drawFromVisibleLine:visLineNr to:visLineNr with:fg and:bg

!

drawLine:line fromX:x inVisible:visLineNr with:fg and:bg
    self drawFromVisibleLine:visLineNr to:visLineNr with:fg and:bg

!

drawLine:line inVisible:visLineNr with:fg and:bg
    self drawFromVisibleLine:visLineNr to:visLineNr with:fg and:bg

!

drawVisibleLine:visLineNr col:col with:fg and:bg
    self drawFromVisibleLine:visLineNr to:visLineNr with:fg and:bg

!

drawVisibleLine:visLineNr from:startCol to:endCol with:fg and:bg
    self drawFromVisibleLine:visLineNr to:visLineNr with:fg and:bg

!

drawVisibleLine:visLineNr from:startCol with:fg and:bg
    self drawFromVisibleLine:visLineNr to:visLineNr with:fg and:bg

! !

!SelectionInTreeView methodsFor:'drawing basics'!

drawFromVisibleLine:startVisLineNr to:endVisLineNr with:fg and:bg

    |size end index yBot yTop yCtr level figWidthDiv2
     x xFig xStr node lv idx image xCross|

    level := nil. "/ to force evaluation of #ifFalse in loop

    index := self visibleLineToAbsoluteLine:startVisLineNr.
    size  := listOfNodes size.
    yTop  := self yOfVisibleLine:startVisLineNr.
    end   := endVisLineNr - startVisLineNr + 1.

"/  clear rectangle line and set background color
    self paint:bg.
    self fillRectangleX:0 y:yTop width:width height:(end * fontHeight).

    index isNil ifTrue:[^ self].
    figWidthDiv2 := imageWidth // 2.
    yCtr := yTop - (fontHeight // 2).

    self paint:fg on:bg.
    (end := index + end) > size ifTrue:[end := size + 1].

    [index < end] whileTrue:[
        node := listOfNodes at:index.
        yBot := yTop + fontHeight.
        yCtr := yCtr + fontHeight.

        (lv := node level) == level ifFalse:[
            level  := lv.
            xFig   := self xOfFigureLevel:lv.
            xStr   := self xOfStringLevel:lv.
            xCross := (self xOfFigureLevel:(lv-1)) + figWidthDiv2.
        ].

        showLines ifTrue:[
            (node isCollapsable and:[node numberOfChildren ~~ 0]) ifTrue:[
                x := xFig + figWidthDiv2.
                self displayLineFromX:x y:yCtr  toX:x y:yBot
            ].
            (level ~~ 1 and:[node parent children last == node]) ifTrue:[
                self displayLineFromX:xCross y:yTop toX:xCross y:yCtr . "/ vertical
            ].
            self displayLineFromX:xCross y:yCtr toX:xFig y:yCtr .       "/ horizontal

        "/  draw vertical lines
            idx := index.

            [(lv > 0 and:[(idx := idx + 1) <= size])] whileTrue:[
                (x := (listOfNodes at:idx) level) <= lv ifTrue:[
                    lv := x - 1.
                    x  := (self xOfFigureLevel:lv) + figWidthDiv2.
                    self displayLineFromX:x y:yTop toX:x y:yBot.
                ]
            ]
        ].

        "/ draw image
        image := self figureFor:node.
        image notNil ifTrue:[
            self displayForm:image x:xFig y:(yCtr - (image height // 2)).
        ].

        "/ draw text label
        self drawLabelIndex:index atX:xStr y:yCtr .

        "/ draw directory indicator
        (showDirectoryIndicator and:[node hasChildren]) ifTrue:[
            node isCollapsable ifTrue:[
                image := openIndicator.
                x := extentOpenIndicator.
            ] ifFalse:[
                image := closeIndicator.
                x := extentCloseIndicator.
            ].
            self displayForm:image x:(xCross - x x)
                                   y:(yCtr   - x y)
        ].
        "/ setup next line
        index := index + 1.
        yTop  := yBot.
    ].

    "Modified: 6.10.1997 / 13:31:51 / cg"
!

drawLabelIndex:anIndex atX:x y:yCenter
    "draw text label at x and y centered
    "
    |y lbl|

    lbl := (listOfNodes at:anIndex) name.

    lbl notNil ifTrue:[
        y := yCenter - ((lbl heightOn:self) // 2).

        (lbl respondsTo:#string) ifTrue:[
            y := y + fontAscent.
        ].
        self displayOpaqueString:lbl x:x y:y.
    ]    
! !

!SelectionInTreeView methodsFor:'enumerating'!

detectNode:aOneArgBlock
    "evaluate the argument, aBlock for each node in the list until
     the block returns true; in this case return the node which caused
     the true evaluation. If none node is detected, nil is returned.
    "
  ^ listOfNodes detect:aOneArgBlock ifNone:nil
!

selectedNodesDo:aOneArgBlock
    "evaluate the block on each node selected
    "
    self selectionDo:[:i| aOneArgBlock value:(listOfNodes at:i) ]
! !

!SelectionInTreeView methodsFor:'initialization'!

destroy
    "remove dependencies
    "
    rootHolder notNil ifTrue:[
        rootHolder removeDependent:self
    ].
    selectionHolder notNil ifTrue:[
        selectionHolder removeDependent:self
    ].
    super destroy.


!

fetchDeviceResources
    "initialize heavily used device resources - to avoid rendering
     images again and again later"

    super fetchDeviceResources.
    self refetchDeviceResources
!

fetchImageResources
    "initialize heavily used device resources - to avoid rendering
     images again and again later; returns maximum extent of the images used.
     Could be redefined by subclass
    "
    |extent|

    extent := 0@0.

    imageOpened isNil ifTrue:[
        imageOpened := self class imageOpened.
        imageOpened notNil ifTrue:[
            imageOpened := imageOpened onDevice:device.
        ]
    ].
    imageOpened notNil ifTrue:[
        extent := extent max:(imageOpened extent)
    ].

    imageClosed isNil ifTrue:[
        imageClosed := self class imageClosed.
        imageClosed notNil ifTrue:[
            imageClosed := imageClosed onDevice:device.
        ].
    ].
    imageClosed notNil ifTrue:[
        extent := extent max:(imageClosed extent)
    ].

    imageItem isNil ifTrue:[
        imageItem := self class imageItem.
        imageItem notNil ifTrue:[
            imageItem := imageItem onDevice:device.
        ].
    ].
    imageItem notNil ifTrue:[
        extent := extent max:(imageItem extent)
    ].

    ^ extent

    "Modified: 19.9.1997 / 17:14:54 / stefan"
!

getFontParameters
    "save old computed height derived from images
    "
    |lineHeight|

    lineHeight := fontHeight ? 0.
    super getFontParameters.

    lineHeight > fontHeight ifTrue:[
        fontHeight := lineHeight
    ].
!

initialize
    "setup instance attributes
    "
    super initialize.
    showLines := true.
    showRoot  := true.
    computeResources := true.
    showDirectoryIndicator := false.
    textInset  := 2.
    imageInset := 0.    "/ set during indication enabled
    imageWidth := 8.    "/ default: will change during startup
    self model:nil.     "/ creates a default model.
!

refetchDeviceResources
    "reinitialize heavily used device resources - to avoid rendering
     images again and again later
    "
    |extent|

    (computeResources and:[listOfNodes size ~~ 0]) ifTrue:[
        computeResources := false.
        extent := self fetchImageResources.

        extent y >= fontHeight ifTrue:[
            fontHeight := 1 + extent y.
        ].
        imageWidth := extent x.
        self recomputeDirectoryIndicator.
    ]
! !

!SelectionInTreeView methodsFor:'model'!

getListFromModel
    "if I have a model, get my list from it using the listMessage.
     If listMessage is nil, try aspectMessage for backward compatibilty.
    "
    super list:(self listFromModel) keepSelection:true
!

listFromModel
    "get list from model and return the new list.
     If listMessage is nil, try aspectMessage for backward compatibilty.
    "
    |msg|

    widthOfWidestLine := nil.

    (msg := listMsg ? aspectMsg) notNil ifTrue:[
        listOfNodes := model perform:msg.
        listOfNodes size ~~ 0 ifTrue:[
            self refetchDeviceResources.
            ^ listOfNodes collect:[:n|n name]
        ]
    ].
    listOfNodes := #().
  ^ #()
!

model:aModel
    "check whether model is nil; than a default model is created
    "
    |model|

    model := aModel ? (SelectionInTree new).
    model showRoot:showRoot.
    super model:model.
!

rootFromModel
    "update hierarchical list from root model; 'rootHolder'
    "
    |root|

    root := rootHolder value.

    self root == root ifFalse:[
        self selection:nil.
        self root:root.
    ]
!

selectionFromModel
    "set the selection derived from the selectionHolder
    "
    |coll value sz|

    (value := selectionHolder value) isNil ifTrue:[
        ^ self deselect
    ].

    multipleSelectOk ifFalse:[
        self selectNode:value
    ] ifTrue:[
        (sz := value size) ~~ 0 ifTrue:[
            coll := OrderedCollection new:sz.

            value do:[:aNode||i|
                (i := self indexOfNode:aNode) notNil ifTrue:[
                    coll add:i
                ]
            ]
        ].
        coll size == 0 ifTrue:[self deselect]
                      ifFalse:[self selection:coll]
    ]
!

selectionToModel
    "write selection to selection holder
    "
    |newSel oldSel|

    oldSel := selectionHolder value.

    multipleSelectOk ifFalse:[
        (newSel := self selectedNode) ~~ oldSel ifTrue:[
            selectionHolder value:newSel
        ]
    ] ifTrue:[
        selection size == 0 ifTrue:[
            oldSel notNil ifTrue:[
                selectionHolder value:nil
            ]
        ] ifFalse:[
            newSel := selection collect:[:i| listOfNodes at:i].

            newSel size ~~ oldSel size ifTrue:[
                selectionHolder value:newSel.
            ] ifFalse:[
                newSel do:[:aNode|
                    (oldSel includes:aNode) ifFalse:[
                        ^ selectionHolder value:newSel
                    ]
                ]
            ]
        ]
    ]
! !

!SelectionInTreeView methodsFor:'private'!

list:aList keepSelection:keepSelection
    |list|

    list := aList.

    list size == 0 ifTrue:[
        listOfNodes := #()
    ] ifFalse:[
        (list first respondsTo:#hasChildren) ifTrue:[
            listOfNodes := aList.
            self refetchDeviceResources.
            list := listOfNodes collect:[:aNode| aNode name ].
        ]
    ].
    super list:list keepSelection:keepSelection
!

recomputeDirectoryIndicator
    "setup attributes used by directory indicator
    "
    |x1 x2 y|

    imageInset := 0.

    (showDirectoryIndicator and:[computeResources not]) ifFalse:[
        ^ self
    ].
    openIndicator  isNil ifTrue:[openIndicator  := (self class openIndicator) onDevice:device].
    closeIndicator isNil ifTrue:[closeIndicator := (self class closeIndicator) onDevice:device].

    x1 := (openIndicator widthOn:self) // 2.
    y  := openIndicator heightOn:self.
    extentOpenIndicator := Point x:x1 y:(y // 2).
    x2 := (closeIndicator widthOn:self) // 2.
    y  := closeIndicator heightOn:self.
    extentCloseIndicator := Point x:x2 y:(y // 2).

    x2 > x1 ifTrue:[x1 := x2].

    (x1 := x1 + self class minImageInset) > (imageWidth // 2) ifTrue:[
        imageInset := x1 - (imageWidth // 2).
    ].

! !

!SelectionInTreeView methodsFor:'private queries'!

lengthOfLongestLineBetween:firstLine and:lastLine
    "return the length (in characters) of the longest line in a line-range
    "
    |max|

    max := self widthOfContents:firstLine and:lastLine.
  ^ (max // fontWidth) + 1
!

widthOfContents
    "return the width of the contents in pixels
     - used for scrollbar interface"

    list isNil ifTrue:[^ 0].

    (widthOfWidestLine isNil or:[widthOfWidestLine == 0]) ifTrue:[
        widthOfWidestLine := self widthOfContents:1 and:(self size).
    ].
  ^ widthOfWidestLine + (leftMargin * 2)

!

widthOfContents:firstLine and:lastLine
    "return the length (in pixels) of the longest line in a line-range
    "
    |max      "{ Class: SmallInteger }"
     thisLen  "{ Class: SmallInteger }"
     first    "{ Class: SmallInteger }"
     last     "{ Class: SmallInteger }" |

    listOfNodes size == 0 ifTrue:[^ 0].

    last  := listOfNodes size.
    first := firstLine.

    (first > last) ifTrue:[^ 0].

    (lastLine < last) ifTrue:[
        last := lastLine
    ].
    max  := 0.

    listOfNodes from:first to:last do:[:anItem||name|
        thisLen := self xOfStringNode:anItem.

        (name := anItem name) notNil ifTrue:[
            thisLen := thisLen + (name widthOn:self).
        ].
        (thisLen > max) ifTrue:[
            max := thisLen.
        ]
    ].
  ^ max + leftOffset.
!

withoutRedrawAt:anIndex put:aString
    "change a line without redisplay"

    |width|

    width := widthOfWidestLine.
    widthOfWidestLine := nil.

    super withoutRedrawAt:anIndex put:aString.

    (widthOfWidestLine := width) notNil ifTrue:[
        width := self widthOfContents:anIndex and:anIndex.

        width > widthOfWidestLine ifTrue:[
            widthOfWidestLine := width
        ] ifFalse:[
            widthOfWidestLine := nil "/ means: unknown
        ]
    ].


! !

!SelectionInTreeView methodsFor:'queries'!

figureFor:aNode
    "access figure for a node
    "
    aNode hasChildren ifTrue:[
        aNode isExpandable ifTrue:[ ^ imageClosed ]
                          ifFalse:[ ^ imageOpened ]
    ].
  ^ imageItem
!

indexOfNode:aNode
    "returns index of a node
    "
    ^ listOfNodes findFirst:[:n| n == aNode ]
!

xOfFigureLevel:aLevel
    "origin x where to draw the icon
    "
    |l|

    showRoot ifTrue:[l := aLevel]
            ifFalse:[l := aLevel - 1].

    showDirectoryIndicator ifFalse:[l := l - 1].
  ^ (l * (imageInset + imageWidth)) + imageInset - leftOffset + leftMargin

!

xOfFigureNode:aNode
    "origin x where to draw the icon
    "
    ^ self xOfFigureLevel:(aNode level)
!

xOfStringLevel:aLevel
    "origin x where to draw the text( label )
    "
    ^ (self xOfFigureLevel:aLevel) + imageWidth + textInset

!

xOfStringNode:aNode
    "origin x where to draw the text( label )
    "
    ^ self xOfStringLevel:(aNode level)

! !

!SelectionInTreeView methodsFor:'selection'!

doubleClicked
    "handle a double click; collapse or expand selected entry
     in case of having children
    "
    |node|

    (node := self selectedNode) notNil ifTrue:[
        (     validateDoubleClickBlock isNil
         or:[(validateDoubleClickBlock value:node) ~~ false]
        ) ifTrue:[
            self selectedNodeExpand:(node isExpandable).
            super doubleClicked
        ]
    ]

!

selectFromListOfNames:aListOfNames
    "set selection from a list of names
    "
    |node rdwNd|

    aListOfNames size < 1 ifTrue:[
        ^ self selection:nil
    ].

    node := model root.

    aListOfNames do:[:el||next|
        next := node detectChild:[:e|e name = el].

        next notNil ifTrue:[
            node hidden ifTrue:[
                rdwNd isNil ifTrue:[
                    rdwNd := node.
                    self selectNode:node.
                ].
                node expand
            ].
            node := next
        ]
    ].

    rdwNd notNil ifTrue:[
        model updateList.
        list := self listFromModel.
        self redrawFromLine:(self indexOfNode:rdwNd).
        self contentsChanged.
    ].
    self selectNode:node.

!

selectNode:aNode
    "change selection to a node
    "
    self selection:(self indexOfNode:aNode)


!

selectedIndex
    "get single selected index or 0
    "
    selection size == 1 ifTrue:[^ selection first].
    selection isNumber  ifTrue:[^ selection].
  ^ 0
!

selectedNode
    "get the single selected node or nil
    "
    |idx|

    (idx := self selectedIndex) ~~ 0 ifTrue:[
        ^ listOfNodes at:idx
    ].
  ^ nil
!

selectionChangedFrom:oldSelection
    "update selectionHolder if not nil
    "
    super selectionChangedFrom:oldSelection.

    selectionHolder notNil ifTrue:[
        self selectionToModel.
    ].

! !

!SelectionInTreeView methodsFor:'selection-actions'!

selectedNodeAdd:something
    "add a node or collection of nodes after selected node
    "
    |node|

    something notNil ifTrue:[
        (node := self selectedNode) notNil ifTrue:[
            node parent notNil ifTrue:[
                node isCollapsable ifTrue:[
                    model add:something beforeIndex:1 below:node
                ] ifFalse:[
                    model add:something after:node
                ]
            ] ifFalse:[
                model add:something beforeIndex:1 below:(self root)
            ]
        ]
    ]

!

selectedNodeBecomeChildOfNext
    "become node a child of followd node
    "
    |idx node cprt nprt|

    ((node := self selectedNode) isNil or:[(cprt := node parent) isNil]) ifFalse:[
        idx := cprt indexOfChild:node.

        idx == cprt children size ifFalse:[
            nprt := cprt childAt:(idx + 1).

            nprt notNil ifTrue:[
                model removeDependent:self.
                model removeSelection.
                selection := nil.
                model collapse:nprt.
                model add:node beforeIndex:1 below:nprt.
                model addDependent:self.
                model expand:nprt.

                self selectNode:node.
            ]
        ]
    ]
!

selectedNodeBecomeSisterOfParent
    "become node a sister of its current parent
    "
    |node cprt nprt|

    (    (node := self selectedNode) isNil
     or:[(cprt := node parent) isNil
     or:[(nprt := cprt parent) isNil]]
    ) ifFalse:[
        model removeDependent:self.
        model removeSelection.
        selection := nil.
        model addDependent:self.

        model add:node afterIndex:(nprt indexOfChild:cprt) below:nprt.
        self selectNode:node.
    ]

!

selectedNodeChangeSequenceOrder:anOffset
    "move child 'anOffset' forward or backward in list of children
    "
    |idx node size parent|

    (      (node   := self selectedNode) notNil
      and:[(parent := node parent) notNil
      and:[(size   := parent children size) > 1]]
    ) ifTrue:[
        idx := parent indexOfChild:node.

        model removeDependent:self.
        model removeSelection.
        selection := nil.
        model addDependent:self.

        (idx := idx + anOffset) < 1 ifTrue:[
            idx := size
        ] ifFalse:[
            idx > size ifTrue:[idx := 1]
        ].
        model add:node beforeIndex:idx below:parent.
        self selectNode:node.
    ]
!

selectedNodeExpand:doExpand
    "collapse or expand selected node
    "
    |node index|

    (index := self selectedIndex) ~~ 0 ifTrue:[
        node := listOfNodes at:index.

        node hasChildren ifTrue:[
            node isExpandable ifTrue:[
                doExpand ifFalse:[^ self].
                node expand
            ] ifFalse:[
                doExpand ifTrue:[^ self].
                node collapse
            ].

            node numberOfChildren == 0 ifTrue:[
                "/ no children; redraw selected line (image might change)
                self redrawLine:index.
            ] ifFalse:[
                "/ with children; update list and redraw to end.
                model updateList.
                list := self listFromModel.
                self redrawFromLine:index.
                self contentsChanged.
            ]
        ]
    ].
!

selectedNodesRemove
    "remove selected nodes
    "
    model removeSelection.
    self selection:nil.

! !

!SelectionInTreeView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/SelectionInTreeView.st,v 1.27 1997-10-11 12:25:11 cg Exp $'
! !