SelectionInTree.st
author ca
Fri, 15 Aug 1997 11:26:23 +0200
changeset 496 d511fde77222
parent 491 c7d57a5e7a21
child 509 c6c9f5ecb977
permissions -rw-r--r--
show or hide root directory

"
 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.
"



Model subclass:#SelectionInTree
	instanceVariableNames:'root list selection showRoot'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-Support-Models'
!

!SelectionInTree 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
"
    list and selection holder for hierarchical list structures. Used
    to buildup file-trees, class tress etc.

    Especially suited for use with SelectionInTreeView.

    [See also:]
        TreeItem
        SelectionInTreeView

    [Author:]
        W. Olberding
        Claus Atzkern
"
! !

!SelectionInTree methodsFor:'accessing'!

list
    "get list oc currently shown objects
    "
    ^ list
!

root
    "get the root node
    "
    ^ root
!

root:aRootNode
    "set a new root and recompute list
    "
    root := aRootNode.
    self recomputeList.

! !

!SelectionInTree methodsFor:'accessing behavior'!

showRoot
    "list with or without root
    "
    ^ showRoot
!

showRoot:aState
    "list with or without root
    "
    aState ~~ showRoot ifTrue:[
        showRoot := aState.

        root notNil ifTrue:[
            aState ifTrue:[list addFirst:root]
                  ifFalse:[list removeFirst].

            self changed:#list.
        ].
    ].
! !

!SelectionInTree methodsFor:'accessing hierarchy'!

collapse:something 
    "collapse a node or collection of nodes
    "
    |invalidate|

    self each:something do:[:aNode|
        aNode isCollapsable ifTrue:[
            aNode collapse.
            invalidate := true
        ]
    ].
    invalidate == true ifTrue:[self recomputeList]
!

expand:something 
    "expand a node or collection of nodes
    "
    |invalidate|

    self each:something do:[:aNode|
        aNode isExpandable ifTrue:[
            aNode expand.
            invalidate := true
        ]
    ].
    invalidate == true ifTrue:[self recomputeList]
! !

!SelectionInTree methodsFor:'adding & removing'!

add:something after:aChild
    "add a node or collection of nodes to parent after a child
    "
    "add a node or collection of nodes to after a child
    "
    aChild notNil ifTrue:[
        aChild parent add:something after:aChild.
        self recomputeList
    ]
!

add:something afterIndex:anIndex below:aParent
    "add a node or collection of nodes to parent after an index
    "
    aParent add:something afterIndex:anIndex.
    self recomputeList

!

add:something before:aChild
    "add a node or collection of nodes to before a child
    "
    aChild notNil ifTrue:[
        aChild parent add:something before:aChild.
        self recomputeList
    ]
!

add:something beforeIndex:anIndex below:aParent
    "add a node or collection of nodes to parent before an index
    "
    aParent add:something beforeIndex:anIndex.
    self recomputeList

!

add:something below:aParent
    "add a node or collection of nodes to parent
    "
    aParent add:something.
    self recomputeList

!

remove:something
    "remove a node or collection of nodes
    "
    |invalidate|

    self each:something do:[:aNode|
        aNode parent notNil ifTrue:[
            aNode parent remove:aNode.
            invalidate := true
        ]
    ].
    invalidate == true ifTrue:[self recomputeList].
  ^ something
!

removeIndex:something
    "remove a node at index or collection of indexed nodes
    "
    |invalidate node|

    something isCollection ifFalse:[
        (something isNil or:[something == 0]) ifFalse:[
            ^ self remove:(list at:something)
        ].
      ^ nil
    ].

    (SortedCollection withAll:something) reverseDo:[:anIndex|
        node := list at:anIndex.

        node parent notNil ifTrue:[
            node parent remove:node.
            invalidate := true
        ]
    ].
    invalidate == true ifTrue:[self recomputeList].
!

removeSelection
    "remove selected nodes
    "
    self removeIndex:(self selectionIndex).
    self selectionIndex:nil
! !

!SelectionInTree methodsFor:'enumerating'!

each:something do:aBlock
    "evaluate a block for something or in case of a collection for each
     element in the collection
    "
    something notNil ifTrue:[
        something isCollection ifTrue:[something do:[:el|aBlock value:el]]
                              ifFalse:[aBlock value:something]
    ]

! !

!SelectionInTree methodsFor:'initialization'!

initialize
    super initialize.
    showRoot := true.
! !

!SelectionInTree methodsFor:'private'!

recomputeList
    "Travers the tree and build a new list."

    self updateList.
    self changed:#list.
!

updateList
    "Travers the tree and build a new list.; no notification raised"

    list := OrderedCollection new.

    root notNil ifTrue:[
        showRoot ifTrue:[
            list add:root
        ].
        root recomputeList:list
    ].
! !

!SelectionInTree methodsFor:'selection'!

selection
    "get the selection or nil
    "
    ^ self selectionIndex
!

selection:indexesOrNil
    "set the selection
    "
    self selectionIndex:indexesOrNil
!

selectionIndex
    "get the selection or nil
    "
    ^ selection
!

selectionIndex:indexesOrNil
    "set the selection
    "
    |oldSel|

    oldSel := selection.
    self setSelectionIndex:indexesOrNil.

    oldSel = selection ifFalse:[
        self changed:#selection
    ]
!

setSelection:indexesOrNil
    "set the selection without raising a notification
    "
    self setSelectionIndex:indexesOrNil
!

setSelectionIndex:indexesOrNil
    "set the selection without raising a notification
    "
    |indexes|

    indexes := indexesOrNil.

    indexes size == 0 ifTrue:[
        (indexes isCollection or:[indexes == 0]) ifTrue:[
            indexes := nil
        ]
    ].
    selection := indexes

! !

!SelectionInTree class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/SelectionInTree.st,v 1.4 1997-08-15 09:26:23 ca Exp $'
! !