HierarchicalList.st
author Claus Gittinger <cg@exept.de>
Tue, 06 Jul 1999 15:40:09 +0200
changeset 1430 ae9e48cc7b9d
parent 1390 62dc950b9140
child 1431 0cc20a8f2f7c
permissions -rw-r--r--
*** empty log message ***

List subclass:#HierarchicalList
	instanceVariableNames:'root showRoot application monitoringTask monitoringTaskDelay'
	classVariableNames:''
	poolDictionaries:''
	category:'Views-Support'
!

!HierarchicalList class methodsFor:'documentation'!

documentation
"
    Hierarchical Lists are mostly like List, but adding and removing
    elements are handled by the items itself.
    Special change notifications are emitted, whenever the list
    changed.

    [Instance variables:]
        root        <HierarchicalItem>  first item into list
        showRoot    <Boolean>           show or hide root item
        application <Application>       the user is able to set an application
                                        which can be accessed by an item.
    [author:]
        Claus Atzkern

    [see also:]
        HierarchicalItem
        HierarchicalListView
"


! !

!HierarchicalList methodsFor:'accessing look'!

showRoot
    "show or hide root item
    "
    ^ showRoot ? true


!

showRoot:aBoolean
    "show or hide root item
    "
    aBoolean ~~ self showRoot ifTrue:[
        showRoot := aBoolean.

        root notNil ifTrue:[
            showRoot ifTrue:[super addFirst:root]
                    ifFalse:[super removeFirst]
        ]
    ]

! !

!HierarchicalList methodsFor:'accessing monitoring task'!

monitoringTaskDelay
    "get the delay time of the monitoring task measured  in seconds
     or nil( monitoring disabled ). The task runs through all items 
     of the list performing #monitoringCycle and than at end of the
     list the task is suspended for monitoringTaskDelay seconds.
    "
    ^ monitoringTaskDelay
!

monitoringTaskDelay:inSecondsOrNil
    "set the delay time of the monitoring task measured  in seconds
     or nil( monitoring disabled ). The task runs through all items 
     of the list performing #monitoringCycle and than at end of the
     list the task is suspended for monitoringTaskDelay seconds.
    "
    monitoringTaskDelay := inSecondsOrNil.

    inSecondsOrNil isNil ifTrue:[
        self stopMonitoringTask
    ] ifFalse:[
        self startMonitoringTask
    ].
! !

!HierarchicalList methodsFor:'accessing mvc'!

application
    "returns the responsible application; if no application is defined,
     nil is returned
    "
    ^ application
!

application:anApplication
    "set the responsible application
    "
    application := anApplication
!

applicationsDo:aOneArgBlock
    "evaluate the block on each dependent application
    "
    |appl|

    dependents notNil ifTrue:[
        dependents do:[:aDep|
            appl := aDep perform:#application ifNotUnderstood:nil.

            appl notNil ifTrue:[
                aOneArgBlock value:appl
            ]
        ]
    ]
! !

!HierarchicalList methodsFor:'accessing root'!

root
    "get the root item
    "
    ^ root

!

root:aRoot
    "set the root item
    "
    |children monitoring|

    self stopMonitoringTask.

    root notNil ifTrue:[
        root parent:nil.
        root := nil.
        super removeAll.
    ].

    (root := aRoot) notNil ifTrue:[
        root parent:self.
        children := OrderedCollection new.
        self showRoot ifTrue:[children add:root].
        root addVisibleChildrenTo:children.
        super addAll:children beforeIndex:1
    ].
    self startMonitoringTask.
! !

!HierarchicalList methodsFor:'private'!

isHierarchicalItem
    "used to decide if the parent is a hierarchical item
     or the model
    "
    ^ false
!

itemAddAll:aListOfItems beforeIndex:anIndex
    "insert all items before an index
    "
    super addAll:aListOfItems beforeIndex:anIndex
!

itemChanged:what with:aPara from:anItem
    "catch notification from item; throw changeNotifications
     to dependencies;
     **** don't know what to do with a parameter and argument what
     **** list protocol ****
    "
    |index arrIdx "{ Class: SmallInteger }"|

    (index := super identityIndexOf:anItem) ~~ 0 ifTrue:[
        arrIdx := index + firstIndex - 1.
        contentsArray basicAt:arrIdx put:anItem.

        dependents size ~~ 0 ifTrue:[
            what isNil ifTrue:[self changed:#at: with:index]
                      ifFalse:[self changed:#at: with:(Array with:index with:what)]
        ]
    ]
!

itemRemoveFromIndex:start toIndex:stop
    "remove the items stored under startIndex up to and including
     the items under stopIndex.
    "
    ^ super removeFromIndex:start toIndex:stop
!

parentOrModel
    "always returns nil
    "
    ^ nil
! !

!HierarchicalList methodsFor:'private monitoring task'!

addDependent:anObject
    "restart the monitoringTask if neccessary
    "
    super addDependent:anObject.
    self  startMonitoringTask.

!

removeDependent:anObject
    "stop the monitoringTask if no more dependencies exists
    "
    super removeDependent:anObject.

    dependents size == 0 ifTrue:[
        self stopMonitoringTask
    ].

!

startMonitoringTask
    "start the monitoring task; success only if dependencies exists
    "
    |task|

    (     monitoringTask      isNil
     and:[monitoringTaskDelay notNil
     and:[dependents size ~~ 0]]
    ) ifTrue:[
        task := monitoringTask := [|index item delay|
            index := showRoot ifTrue:[1] ifFalse:[0].

            [true] whileTrue:[
                item := index == 0 ifTrue:[root]
                                  ifFalse:[self at:index ifAbsent:nil].

                item isNil ifTrue:[
                    delay := self monitoringTaskDelay.

                    delay isNil ifTrue:[                "/ process might terminate
                        task ~~ monitoringTask ifTrue:[
                            self terminate
                        ].
                        Processor yield
                    ] ifFalse:[
                        Delay waitForSeconds:delay.

                        task ~~ monitoringTask ifTrue:[ "/ task has changed
                            self terminate
                        ]
                    ].
                    index := showRoot ifTrue:[1] ifFalse:[0].
                ] ifFalse:[
                    item monitoringCycle.
                    Processor yield.
                    index := index + 1.
                ]
            ]
        ] forkAt:4.
    ].
    ^ true.



!

stopMonitoringTask
    "stop the monitoring task
    "
    |task|

    (task := monitoringTask) notNil ifTrue:[
        monitoringTask := nil.
        task terminate
    ]


! !

!HierarchicalList methodsFor:'protocol'!

childrenFor:anItem
    "returns the children for an item or an empty list
    "
    ^ #()
!

iconFor:anItem
    "returns the icon for an item or nil
    "
    ^ nil
!

labelFor:anItem
    "returns the label for an item or nil
    "
    ^ nil


!

middleButtonMenuFor:anItem
    "returns the middleButton menu for an item or nil
    "
    ^ nil


! !

!HierarchicalList class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/HierarchicalList.st,v 1.2 1999-07-06 13:40:08 cg Exp $'
! !