SelectionInTree.st
author ca
Thu, 09 Apr 1998 13:37:54 +0200
changeset 849 f7d8363fc24f
parent 842 636d8a543c35
child 857 d8e14b853cb7
permissions -rw-r--r--
support more detectItem mechanisms

"
 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 contentsAction labelAction
		childrenAction iconAction indicatorList indicatorTask accessLock'
	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 class methodsFor:'instance creation'!

new
    ^ super new initialize
! !

!SelectionInTree methodsFor:'accessing'!

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

root
    "get the root node
    "
    ^ root
!

root:aRoot
    "set a new root
    "
    root notNil ifTrue: [
        root tree: nil
    ].
    self stopRunningTasks.

    (root := aRoot) notNil ifTrue:[
        root parent:nil.
        root tree: self.
    ]. 
    self recomputeList.

! !

!SelectionInTree methodsFor:'accessing behavior'!

childrenAction
    "get children action block
    "
    ^childrenAction
!

childrenAction:aBlock
    "set children action block
    "
    childrenAction := aBlock.

    self changed:#list.
    
!

contentsAction
    "get contents action block
    "
    ^contentsAction
!

contentsAction:aBlock
    "set contents action block
    "
    contentsAction := aBlock.

    self changed:#list.
    
!

iconAction
    "get icon action block
    "
    ^iconAction
!

iconAction:aBlock
    "set icon action block
    "
    iconAction := aBlock.

    self changed:#list.
    
!

labelAction
    "get label action block
    "
    ^labelAction
!

labelAction:aBlock
    "set label action block
    "
    labelAction := aBlock.

    self changed:#list.
    
!

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
    "expand the root
    "
    self expand:root
!

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|
        self stopIndicatorValidationFor: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.
        self stopIndicatorValidationFor:node.

        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:'change & update'!

invalidate
    "called; something changed what requires a redraw but no recomputation.
     for example a name
    "
    self dependents do:[:aDependent|
        aDependent isView ifTrue:[ aDependent invalidate ]
    ].


!

update:something with:aParameter from:aModel

    self dependents do:[:aDependent|
        aDependent update:something with:aParameter from:aModel
    ]
! !

!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

    showRoot := true.
    indicatorList := OrderedCollection new.
    accessLock    := Semaphore forMutualExclusion.
    list          := OrderedCollection new:128.
    super initialize.

! !

!SelectionInTree methodsFor:'private'!

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

    list clearContents.

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

!SelectionInTree methodsFor:'searching'!

detectItem:aOneArgBlock
    "detect an item the evaluation of the block returns true. The
     argument to the block is the item.
    "
    root notNil ifTrue:[
        ^ root detectChild:aOneArgBlock
    ].
    ^ nil


!

detectItem:aTwoArgBlock arguments:aListOfArgs
    "detect an item the evaluation of the block returns true. The
     first argument to the block is the item, the second argument
     the value derived from the argument list at an index
    "
    root notNil ifTrue:[
        ^ root detectChild:aTwoArgBlock arguments:aListOfArgs index:1
    ].
    ^ nil


! !

!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:#selectionIndex
    ]
!

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 methodsFor:'update indication task'!

startIndicatorValidationFor:aNode
    "add a node to list of updating indications
    "
    |index|

    accessLock critical:[
        index := indicatorList identityIndexOf:aNode.

        index ~~ 0 ifTrue:[
            indicatorList removeIndex:index.    "/ reorganize list to be faster
        ].
        indicatorList addFirst:aNode.

        indicatorTask isNil ifTrue:[
            indicatorTask := [
                [ self taskCycle ] whileTrue:[ Processor yield ]
            ] forkAt:(Processor activePriority - 1)
        ]
    ].
!

stopIndicatorValidationFor:aNodeOrList
    "remove a node or list of nodes from list of updating indications
    "
    accessLock critical:[
        aNodeOrList isCollection ifTrue:[
            aNodeOrList do:[:aNode|
                indicatorList removeIdentical:aNode ifAbsent:nil
            ]
        ] ifFalse:[
            indicatorList removeIdentical:aNodeOrList ifAbsent:nil
        ]
    ]


!

stopRunningTasks
    "stop task
    "
    accessLock critical:[ indicatorList removeAll ]

!

taskCycle
    "run one cycle
    "
    |node|

    accessLock critical:[
        indicatorList isEmpty ifTrue:[          "/ queue is empty; terminate task
            indicatorTask := nil.
            ^ false
        ].
        node := indicatorList removeFirst.      "/ run task on first node

        node hasValidIndicator ifTrue:[         "/ up to date
            ^ true
        ].
        node setShowIndicator:false             "/ disable registry
    ].

    (DirectoryContents directoryNamed:(node fileName) detect:(node matchAction)) ifTrue:[
        node showIndicator:true
    ].
    ^ true
! !

!SelectionInTree class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/SelectionInTree.st,v 1.12 1998-04-09 11:37:54 ca Exp $'
! !