SelectionInTree.st
author Claus Gittinger <cg@exept.de>
Fri, 28 Jun 2019 09:21:50 +0200
changeset 6078 08c9e2a47dc5
parent 5667 a213756b3b4d
child 6156 2f7f8fc3abe1
permissions -rw-r--r--
#OTHER by cg self class name -> self className

"{ Encoding: utf8 }"

"
 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.
"
"{ Package: 'stx:libwidg2' }"

"{ NameSpace: Smalltalk }"

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 trees etc.

    Especially suited for use with SelectionInTreeView.

    Notice: this class replaces SelectionInHierarchy, 
            which provides similar (but less sophisticated) functionality.

    [See also:]
        TreeItem
        SelectionInTreeView
        SelectionInHierarchy

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

!SelectionInTree class methodsFor:'instance creation'!

new
    ^ self basicNew initialize
! !

!SelectionInTree class methodsFor:'defaults'!

defaultItemClass
    "returns the default item class or nil (the default)"

    ^ nil

    "Modified (comment): / 04-02-2017 / 19:48:09 / cg"
! !

!SelectionInTree methodsFor:'accessing'!

list
    "get the list of currently shown objects"

    ^ list

    "Modified (comment): / 04-02-2017 / 19:38:18 / cg"
!

root
    "get the root node"

    ^ root

    "Modified (comment): / 04-02-2017 / 19:40:07 / cg"
!

root:aRoot
    "set a new root"

    |tree|

    root notNil ifTrue: [
        tree := root tree.
        root tree:nil.
    ] ifFalse:[
        tree := self
    ].
    self stopRunningTasks.

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

    "Modified (comment): / 04-02-2017 / 19:40:12 / cg"
!

value
    ^ list
! !

!SelectionInTree methodsFor:'accessing hierarchy new'!

doMakeVisible:itemOrCollectionOfItems
    "make an item or collection of items visible"

    |anchor parent|

    self each:itemOrCollectionOfItems do:[:anItem|
        parent := anItem.
        anchor := nil.

        parent notNil ifTrue:[
            [(parent := parent parent) notNil] whileTrue:[
                parent hidden ifTrue:[
                    anchor notNil ifTrue:[ anchor expand ].
                    anchor := parent.
                ]
            ].
            anchor notNil ifTrue:[
                self expandItem:anchor do:[anchor expand]
            ]
        ].
    ]

    "Modified (comment): / 18-10-2017 / 11:55:53 / cg"
! !

!SelectionInTree methodsFor:'accessing-behavior'!

childrenAction
    "get the children action block.
     This is called by tree items to retrieve the children of a node"

    ^childrenAction

    "Modified (comment): / 04-02-2017 / 19:31:38 / cg"
!

childrenAction:aBlock
    "set the children action block
     This is called by tree items to retrieve the children of a node"

    childrenAction := aBlock.

    "Modified (comment): / 04-02-2017 / 19:31:51 / cg"
!

contentsAction
    "get contents action block
     This is called by tree items to retrieve the contents of a node"

    ^contentsAction

    "Modified (comment): / 04-02-2017 / 19:32:04 / cg"
!

contentsAction:aBlock
    "set contents action block
     This is called by tree items to retrieve the contents of a node"

    contentsAction := aBlock.

    "Modified (comment): / 04-02-2017 / 19:32:09 / cg"
!

iconAction
    "get icon action block
     This is called by tree items to retrieve the icon of a node"

    ^iconAction

    "Modified (comment): / 04-02-2017 / 19:32:22 / cg"
!

iconAction:aBlock
    "set icon action block
     This is called by tree items to retrieve the icon of a node"

    iconAction := aBlock.

    "Modified (comment): / 04-02-2017 / 19:32:17 / cg"
!

labelAction
    "get label action block
     This is called by tree items to retrieve the label of a node"

    ^labelAction

    "Modified (comment): / 04-02-2017 / 19:32:27 / cg"
!

labelAction:aBlock
    "set label action block
     This is called by tree items to retrieve the label of a node"

    labelAction := aBlock.

    "Modified (comment): / 04-02-2017 / 19:32:35 / cg"
!

showRoot
    "controls if the list is shown with or without root.
     Notice that technically, there is always one single root item;
     however, its visibility can be suppressed to make the tree look like a list
     on the top level"

    ^ showRoot

    "Modified (comment): / 04-02-2017 / 19:33:45 / cg"
!

showRoot:aBoolean
    "controls if the list is shown with or without root.
     Notice that technically, there is always one single root item;
     however, its visibility can be suppressed to make the tree look like a list
     on the top level"

    aBoolean ~~ showRoot ifTrue:[
        showRoot := aBoolean.

        root notNil ifTrue:[
            aBoolean ifTrue:[
                list addFirst:root.
                self changed:#insertCollection: with:(Array with:1 with:1 with:nil).
            ] ifFalse:[
                list removeFirst.
                self changed:#removeFrom: with:(Array with:1 with:1 with:nil).
            ].
        ].
    ].

    "Modified (format): / 04-02-2017 / 21:34:26 / cg"
! !

!SelectionInTree methodsFor:'accessing-hierarchy'!

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

    |listChanged|

    listChanged := false.

    self each:something do:[:aNode|
        aNode isCollapsable ifTrue:[
            aNode collapse.
            listChanged := true
        ]
    ].
    listChanged ifTrue:[
        self listFromRoot.
        self changed:#list.
    ]

    "Modified (comment): / 04-02-2017 / 19:34:09 / cg"
!

expand
    "expand the root"

    self expand:root

    "Modified (comment): / 04-02-2017 / 19:34:13 / cg"
!

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

    |listChanged|

    listChanged := false.

    self each:something do:[:aNode|
        aNode isExpandable ifTrue:[
            aNode expand.
            listChanged := true
        ]
    ].
    listChanged ifTrue:[
        self listFromRoot.
        self changed:#list.
    ]

    "Modified (comment): / 04-02-2017 / 19:34:17 / cg"
! !

!SelectionInTree methodsFor:'accessing-hierarchy new'!

doCollapse:something
    "collapse all children under an item or a sequence of items;
     if the list changed, a change notifications are sent"

    self each:something do:[:anItem|
        self collapseItem:anItem do:[ anItem collapse ]
    ]

    "Modified (comment): / 04-02-2017 / 19:36:30 / cg"
!

doCollapseAll:something
    "collapse all children and subChildren under an item or sequence of items;
     if the list changed, a change notifications are sent"

    self each:something do:[:anItem|
        self collapseItem:anItem do:[ anItem collapseAll ]
    ]

    "Modified (comment): / 04-02-2017 / 19:36:39 / cg"
!

doExpand:something
    "expand all children under an item or collection of items;
     if the list changed, a change notifications are sent"

    self each:something do:[:anItem|
        self expandItem:anItem do:[anItem expand]
    ]

    "Modified (comment): / 04-02-2017 / 19:36:44 / cg"
!

doExpandAll:something
    "expand all children and subChildren under an item or sequence of items;
     if the list changed, change notifications are sent"

    self each:something do:[:anItem|
        self expandItem:anItem do:[anItem expandAll]
    ]

    "Modified (comment): / 04-02-2017 / 19:36:55 / cg"
! !

!SelectionInTree methodsFor:'adding & removing'!

add:something after:aChild
    "add a node or collection of nodes to the parent of aChild
     after that child in the sublist"

    |p|

    (aChild notNil and:[(p := aChild parent) notNil]) ifTrue:[
        self add:something afterIndex:(p indexOfChild:aChild) below:p
    ]

    "Modified (comment): / 04-02-2017 / 19:35:11 / cg"
!

add:something afterIndex:anIndex below:aParent
    "add a node or collection of nodes to parent after an index
    "
    self add:something beforeIndex:(anIndex + 1) below:aParent
!

add:something before:aChild
    "add a node or collection of nodes to before a child"

    |p|

    (aChild notNil and:[(p := aChild parent) notNil]) ifTrue:[
        self add:something beforeIndex:(p indexOfChild:aChild) below:p
    ]

    "Modified (comment): / 04-02-2017 / 19:35:19 / cg"
!

add:something beforeIndex:anIndex below:aParent
    "add a node or collection of nodes to aParents children
     before anIndex (which is a child-index)"

    |children start index size pList|

    (    aParent isNil
     or:[something isNil
     or:[(something isCollection and:[something isEmpty])]]
    ) ifTrue:[
        ^ self
    ].

    (start := self indexOf:aParent) == 0 ifTrue:[
        "/
        "/ parent not visible; list not changed
        "/
        aParent == root ifFalse:[
            aParent add:something beforeIndex:anIndex.
          ^ self
        ]
    ] ifFalse:[
        aParent shown ifFalse:[
            aParent add:something beforeIndex:anIndex.
            self changed:#at: with:start.
            ^ self
        ]
    ].
    children := aParent children.

    (children isEmpty or:[anIndex <= 1]) ifTrue:[
        index := 1.
    ] ifFalse:[
        size  := children size.

        anIndex > size ifTrue:[
            index := size + 1.
            start := aParent numberOfAllVisibleChildren + start.
        ] ifFalse:[
            index := anIndex.
            start := (self indexOf:(children at:index)) - 1.
        ]
    ].
    aParent add:something beforeIndex:index.

    (start := start + 1) == 0 ifTrue:[
        "/
        "/ not visible
        "/
        ^ self
    ].
    pList := OrderedCollection new:2048.

    self each:something do:[:aNode|
        pList add:aNode.
        aNode addVisibleChildrenTo:pList
    ].
    pList isEmpty ifTrue:[
        ^ self
    ].
    list addAll:pList beforeIndex:start.

    self changed:#insertCollection:
            with:(Array with:start with:pList size with:aParent).

    "Modified (comment): / 04-02-2017 / 19:35:23 / cg"
!

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

    aParent notNil ifTrue:[
        self add:something beforeIndex:(aParent numberOfChildren + 1) below:aParent
    ]

    "Modified (comment): / 04-02-2017 / 19:35:28 / cg"
!

remove:something
    "remove a node or collection of nodes.
     Change notifications are sent"

    |node index loNums loItem start size parent stop|

    something isNil ifTrue:[
        ^ something
    ].
    loNums := SortedCollection new.

    self each:something do:[:el|
        node := el isNumber ifTrue:[list at:el ifAbsent:nil]
                           ifFalse:[el].

        node notNil ifTrue:[
            self stopIndicatorValidationFor:node.

            node parent isNil ifTrue:[
                "/ remove all including root
                node == root ifTrue:[ self root:nil ].
              ^ something
            ].
            index := self indexOf:node.

            index == 0 ifTrue:[
                "/ not visible
                node parent removeChild:node
            ] ifFalse:[
                loNums add:index
            ].
        ]
    ].

    loNums isEmpty ifTrue:[
        "/ nothing visible changed
        ^ something
    ].
    loItem := OrderedCollection new.
    loNums do:[:i| loItem add:(list at:i)].

    loItem do:[:aNode|
        start := self indexOf:aNode.

        start ~~ 0 ifTrue:[
            parent := aNode parent.
            size   := 1 + aNode numberOfAllVisibleChildren.
            stop   := start + size - 1.
            parent remove:aNode.
            list removeFromIndex:start toIndex:stop.

            self changed:#removeFrom:
                    with:(Array with:start with:stop with:parent).
        ]
    ].
    ^ something

    "Modified (comment): / 04-02-2017 / 19:39:07 / cg"
!

removeAllOtherThanRoot
    "remove all children from the root
     Change notifications are sent"

    |listChanged|

    root notNil ifTrue:[
        listChanged := root isCollapsable.
        root children:(OrderedCollection new).

        listChanged ifTrue:[
            self listFromRoot.
            self changed:#list
        ]
    ]

    "Modified (comment): / 04-02-2017 / 19:39:31 / cg"
!

removeIndex:something
    "remove a node at index or collection of indexed nodes.
     Change notifications are sent"
     
    self remove:something

    "Modified (comment): / 04-02-2017 / 19:39:42 / cg"
!

removeSelection
    "remove selected nodes.
     Change notifications are sent"

    |sel|

    sel := self selectionIndex.
    self selectionIndex:nil.
    self remove:sel.

    "Modified (comment): / 04-02-2017 / 19:39:51 / cg"
!

replaceNode:aNode with:aNewNode
    "replace a node by a new node; if the new node is nil, the node and its
     children are removed. 
     Otherwise the children are taken over to the new node."

    |parent index children|

    (aNode isNil or:[aNode == aNewNode]) ifTrue:[
        ^ self
    ].

    aNewNode isNil ifTrue:[
        ^ self remove:aNode
    ].
    self stopIndicatorValidationFor:aNode.

    aNewNode children:(aNode children).    
    aNode    children:nil.

    aNode == root ifTrue:[
        aNewNode tree:(aNode tree).
        aNewNode parent:nil.
        root := aNewNode.
    ] ifFalse:[
        parent := aNode parent.
        aNewNode tree:nil.
        aNewNode parent:parent.
        children := parent children.
        index := children identityIndexOf:aNode.
        children at:index put:aNewNode.
    ].

    aNode tree:nil.        
    aNode parent:nil.        

    (index := self indexOf:aNode) ~~ 0 ifTrue:[
        list at:index put:aNewNode.
        self changed:#at: with:index
    ].

    "Modified (comment): / 04-02-2017 / 19:40:02 / cg"
! !

!SelectionInTree methodsFor:'change & update'!

invalidate
    "called whenever something changed that requires a redraw but no recomputation.
     For example a name or icon"

    self dependents do:[:aDependent|
        aDependent isView ifTrue:[ aDependent invalidate ]
    ].

    "Modified (comment): / 04-02-2017 / 19:38:06 / cg"
!

update:something with:aParameter from:aModel

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

!SelectionInTree methodsFor:'enumerating'!

each:itemOrCollectionOfItems do:aOneArgBlock
    "evaluate a block for something or in case of a collection for each
     element in the collection"

    itemOrCollectionOfItems notNil ifTrue:[
        itemOrCollectionOfItems isCollection ifTrue:[
            itemOrCollectionOfItems do:aOneArgBlock
        ] ifFalse:[
            aOneArgBlock value:itemOrCollectionOfItems
        ]
    ]

    "Modified (format): / 18-10-2017 / 11:55:36 / cg"
! !

!SelectionInTree methodsFor:'initialization'!

initialize

    showRoot      := true.
    indicatorList := OrderedCollection new.
    accessLock    := Semaphore forMutualExclusion.
    list          := List new.
! !

!SelectionInTree methodsFor:'private'!

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

    self listFromRoot.
    self changed:#list.
! !

!SelectionInTree methodsFor:'private-hierarchy'!

collapseItem:anItem do:collapseBlock
    "collapse all children under an item; 
     send a change notification if the list changed"

    |start stop size|

    anItem isCollapsable ifFalse:[
        ^ self
    ].

    (start := self indexOf:anItem) == 0 ifTrue:[
        "/
        "/ item not visible
        "/
        collapseBlock value.
    ] ifFalse:[
        size := anItem numberOfAllVisibleChildren.
        collapseBlock value.

        size == 0 ifTrue:[
            "/
            "/ no children before; list not changed 
            "/
            self changed:#at: with:start
        ] ifFalse:[        
            stop  := start + size.
            start := start + 1.
            list removeFromIndex:start toIndex:stop.
            self changed:#removeFrom: with:(Array with:start with:stop with:anItem).
        ]
    ]

    "Modified (comment): / 04-02-2017 / 19:35:52 / cg"
!

expandItem:anItem do:expandBlock
    "expand all children under an item; 
     send out change a notification if the list changed"

    |start size pList|

    anItem isExpandable ifFalse:[
        ^ self
    ].
    expandBlock value.

    (start := self indexOf:anItem) ~~ 0 ifTrue:[
        anItem addVisibleChildrenTo:(pList := OrderedCollection new:2048).

        (size := pList size) ~~ 0 ifTrue:[
            start := 1 + start.
            list addAll:pList beforeIndex:start.

            self changed:#insertCollection:
                    with:(Array with:start with:size with:anItem).
        ] ifFalse:[
            self changed:#at: with:start
        ]
    ]

    "Modified (comment): / 04-02-2017 / 19:37:29 / cg"
!

listFromRoot
    "Traverse the tree and build a new list;
     no change notification are sent"

    list clearContents.

    root notNil ifTrue:[
        showRoot ifTrue:[ list add:root ].
        root addVisibleChildrenTo:list
    ]

    "Modified (comment): / 04-02-2017 / 19:38:29 / cg"
! !

!SelectionInTree methodsFor:'queries'!

indexOf:anItem
    "returns the index of an item or 0"

    ^ anItem notNil 
        ifTrue:[list identityIndexOf:anItem]
        ifFalse:[0]

    "Modified (comment): / 04-02-2017 / 19:37:38 / cg"
! !

!SelectionInTree methodsFor:'searching'!

detectFirstItem:aOneArgBlock
    "detect an item the evaluation of the block returns true. 
     The argument to the block is the item.
     This recursively enumerates the tree for the first item for which
     the block returns true."

    root notNil ifTrue:[
        ^ root detectFirstChild:aOneArgBlock
    ].
    ^ nil

    "Modified (comment): / 04-02-2017 / 19:36:01 / cg"
!

detectItem:aOneArgBlock
    "detect an item the evaluation of the block returns true. 
     The argument to the block is the item.
     This searches top-level items only."

    root notNil ifTrue:[
        ^ root detectChild:aOneArgBlock
    ].
    ^ nil

    "Modified (comment): / 04-02-2017 / 19:36:06 / cg"
!

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 level.
     This recursively walks down the tree up to aListOfArgs size levels;
     i.e. if you pass (1 to:10) as aListOfArgs, the block will get the sub-level
     as second argument and stop the search after 10 levels."

    root notNil ifTrue:[
        ^ root detectChild:aTwoArgBlock arguments:aListOfArgs
    ].
    ^ nil

    "Modified (comment): / 04-02-2017 / 19:36:15 / cg"
! !

!SelectionInTree methodsFor:'selection'!

selectNode:aNode
    "select a given node (by identity - not by index).
     Notice, that the node must be visible - i.e. its parent chain must be
     currently expanded."
    
    |index|

    (index := self indexOf:aNode) ~~ 0 ifTrue:[
        self selectionIndex:index
    ] ifFalse:[
        "/ self halt.
    ]

    "Modified: / 18-10-2017 / 11:56:20 / cg"
!

selectNodes:aCollectionOfNodes
    "select a given set of nodes (by identity - not by index)"

    | indices|

    indices := aCollectionOfNodes 
                    collect:[:aNode | self indexOf:aNode]
                    thenSelect:[:idx | idx ~~ 0].
    indices sort.
    self selectionIndex:indices

    "Created: / 06-03-1999 / 22:37:59 / cg"
    "Modified (comment): / 04-02-2017 / 19:40:55 / cg"
!

selectedNode
    "returns the selected node or nil"

    |nodes|
    (nodes := self selectedNodes) notNil ifTrue: [
        ^nodes first
    ].
    ^nil

    "Modified (comment): / 04-02-2017 / 19:41:04 / cg"
!

selectedNodes
    "returns a collection of selected nodes or nil"

    |node coll|

    selection isNil ifTrue:[
        ^ nil
    ].

    selection isCollection ifFalse:[
        node := list at:selection ifAbsent:nil.
        ^ node notNil ifTrue:[Array with:node] ifFalse:[nil]
    ].

    selection isEmpty ifTrue:[
        ^ nil
    ].

    coll := OrderedCollection new:(selection size).

    selection do:[:idx|
        (node := list at:idx ifAbsent:nil) notNil ifTrue:[
            coll add:node
        ]
    ].
    ^ coll asNilIfEmpty

    "Modified (format): / 04-02-2017 / 19:41:19 / cg"
!

selectedNodesDo:aOneArgBlock
    "evaluate the block on each node selected"

    |node|

    selection isNil ifTrue:[
        ^ nil
    ].

    selection isCollection ifFalse:[
        node := list at:selection ifAbsent:nil.
        node notNil ifTrue:[
            aOneArgBlock value:node
        ].
        ^ self
    ].

    selection do:[:i|
        node := list at:i ifAbsent:nil.

        node notNil ifTrue:[
            aOneArgBlock value:node
        ].
    ].

    "Modified (comment): / 04-02-2017 / 19:41:54 / cg"
!

selection
    "get the selection index or nil"

    ^ self selectionIndex

    "Modified (comment): / 04-02-2017 / 19:42:40 / cg"
!

selection:indexesOrNil
    "set the selection index"

    self selectionIndex:indexesOrNil

    "Modified (comment): / 04-02-2017 / 19:42:45 / cg"
!

selectionIndex
    "get the selection index or nil"

    ^ selection

    "Modified (comment): / 04-02-2017 / 19:42:59 / cg"
!

selectionIndex:indexesOrNil
    "set the selection index (or nil to deselect)"

    |oldSel|

    oldSel := selection.
    self setSelectionIndex:indexesOrNil.

    oldSel = selection ifFalse:[
        self changed:#selectionIndex.

        self selectedNodesDo:[:aNode|
            aNode changedSelected
        ]
    ]

    "Modified (comment): / 04-02-2017 / 19:43:12 / cg"
!

setSelection:indexesOrNil
    "set the selection index without sending out change notifications"

    self setSelectionIndex:indexesOrNil

    "Modified (comment): / 04-02-2017 / 19:43:41 / cg"
!

setSelectionIndex:indexesOrNil
    "set the selection index without sending out change notifications"

    |indexes|

    indexes := indexesOrNil.

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

    "Modified (comment): / 04-02-2017 / 19:43:37 / cg"
! !

!SelectionInTree methodsFor:'update indication task'!

startIndicatorValidationFor:aNode
    "add a node to the list of nodes which are automatically
     monitored for changes in their children list (by a background task),
     and which will then update their 'has-children' arrow indicator icon.
     This is typically used to check for changed folders in file trees,
     data in databases etc."

    |index|

    accessLock critical:[
        |prio|

        index := indicatorList identityIndexOf:aNode.

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

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

    "Modified: / 26-09-1998 / 15:20:44 / cg"
    "Modified (comment): / 04-02-2017 / 19:47:28 / cg"
!

stopIndicatorValidationFor:aNodeOrList
    "remove a node or list of nodes from the list of automatically monitored nodes."

    accessLock critical:[
        aNodeOrList isCollection ifTrue:[
            aNodeOrList do:[:aNode|
                indicatorList removeIdentical:aNode ifAbsent:nil
            ]
        ] ifFalse:[
            indicatorList removeIdentical:aNodeOrList ifAbsent:nil
        ]
    ]

    "Modified (comment): / 04-02-2017 / 19:46:18 / cg"
!

stopRunningTasks
    "stop the running update task"

    accessLock critical:[ indicatorList removeAll ]

    "Modified (comment): / 04-02-2017 / 19:46:33 / cg"
!

taskCycle
    "run one cycle fetching indicator state.
     This is done in the background to avoid long startup
     delays, in case the indicator information takes long to
     gather (i.e. when reading network directories)"

    |node flag|

    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:(node defaultShowSeparator).      "/ disable registry
    ].

    flag := DirectoryContents directoryNamed:(node fileName) detect:(node matchAction).
    node showIndicator:flag.
    ^ true

    "Modified: / 26-09-1998 / 15:11:16 / cg"
    "Modified (comment): / 04-02-2017 / 19:47:51 / cg"
! !

!SelectionInTree class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !