HierarchicalFileList.st
author penk
Thu, 21 Nov 2002 09:52:29 +0100
changeset 2387 206662f654e4
parent 2380 df8d81cebb74
child 2388 151c81f43733
permissions -rw-r--r--
show open icon if expanded again

"
 COPYRIGHT (c) 1999 by eXept Software AG
              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' }"

HierarchicalList subclass:#HierarchicalFileList
	instanceVariableNames:'matchBlock indicatorList indicatorTask sortBlock'
	classVariableNames:''
	poolDictionaries:''
	category:'Views-Support'
!

HierarchicalItem subclass:#HierarchicalFileItem
	instanceVariableNames:'icon contentsItem'
	classVariableNames:'LastUIDToUserNameMapping LastGIDToGroupNameMapping'
	poolDictionaries:''
	privateIn:HierarchicalFileList
!

HierarchicalFileList::HierarchicalFileItem subclass:#File
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:HierarchicalFileList
!

HierarchicalFileList::HierarchicalFileItem subclass:#Directory
	instanceVariableNames:'modificationTime fetchOperation'
	classVariableNames:''
	poolDictionaries:''
	privateIn:HierarchicalFileList
!

HierarchicalFileList::Directory subclass:#RemoteDirectory
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:HierarchicalFileList
!

!HierarchicalFileList class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1999 by eXept Software AG
              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.
"

! !

!HierarchicalFileList class methodsFor:'examples'!

examples
"
    open filebrowser without monitoring cycle

                                                                    [exBegin]
    |top sel list directory|

    list := HierarchicalFileList new.
    list showRoot:false.
    list matchBlock:[:fn :isDir| true ].

    directory := Filename currentDirectory.
    directory := Filename homeDirectory.

    list directory:(directory asAbsoluteFilename).

    top := StandardSystemView new; extent:300@300.
    sel := ScrollableView for:HierarchicalListView miniScroller:true
                       origin:0.0@0.0 corner:1.0@1.0 in:top.

    sel doubleClickAction:[:i| (list at:i) toggleExpand ].
    sel   indicatorAction:[:i| (list at:i) toggleExpand ].

    sel hasConstantHeight:true.
    sel list:list.

    top open.
                                                                [exEnd]


    open filebrowser and monitore contents
                                                                    [exBegin]
    |top sel list directory|

    list := HierarchicalFileList new.
    list showRoot:false.
    list matchBlock:[:fn :isDir| true ].

    directory := Filename currentDirectory.
    directory := Filename homeDirectory.

    list directory:(directory asAbsoluteFilename).

    top := StandardSystemView new; extent:300@300.
    sel := ScrollableView for:HierarchicalListView miniScroller:true
                       origin:0.0@0.0 corner:1.0@1.0 in:top.

    sel doubleClickAction:[:i| (list at:i) toggleExpand ].
    sel   indicatorAction:[:i| (list at:i) toggleExpand ].

    sel hasConstantHeight:true.
    sel list:list.
    list monitoringTaskDelay:0.5.
    top open.
                                                                [exEnd]

"
! !

!HierarchicalFileList class methodsFor:'helpers'!

forInfoItem:aItem
    "instance creation helper
    "
    | info fileType retItem|

    info := aItem info.
    fileType := aItem type.
    retItem := self itemFor:aItem fileName fileType:fileType.
    retItem fileInfo:info.
    ^ retItem
!

itemFor:aFileOrDirectoryName fileType:fileType
    "instance creation helper
    "

    fileType == #directory ifTrue:[
        ^ Directory fileName:aFileOrDirectoryName.
    ].
    fileType == #remoteDirectory ifTrue:[
        ^ RemoteDirectory fileName:aFileOrDirectoryName.
    ].

    ^ File fileName:aFileOrDirectoryName.
! !

!HierarchicalFileList methodsFor:'accessing'!

directory
    "returns the root directory or nil
    "
    ^ root notNil ifTrue:[root fileName] ifFalse:[nil]

!

directory:aDirectory
    "set the root directory or nil
    "
    self directory:aDirectory expand:true
!

directory:aDirectory expand:doExpand
    "set the root directory or nil
    "
    |directory fileInfo current newRootItem|

"/    must explicitly enabled by user: ca
"/    monitoringTaskDelay := 1.

    aDirectory notNil ifTrue:[ directory := aDirectory asFilename ]
                     ifFalse:[ directory := nil ].

    current := self directory.
    current  = directory ifTrue:[^ self].

    (directory isNil or:[directory exists not]) ifTrue:[
        self root:nil.
      ^ self
     ].

     fileInfo := directory info.

     fileInfo notNil ifTrue:[
        fileInfo isDirectory ifFalse:[
            directory := directory directory.
            current = directory ifTrue:[
                ^ self
            ].
            fileInfo := directory info.
        ]
    ].

    newRootItem := HierarchicalFileItem fileName:directory asCanonicalizedFilename.
    doExpand ifTrue:[ newRootItem setExpanded:true ].
    self root:newRootItem.
!

root:aRoot
    "stop update-task
    "
    self criticalDo:[
        indicatorList notNil ifTrue:[
            indicatorList do:[:el| el resetFetchIndicator ].
            indicatorList removeAll.
        ]
    ].
    aRoot notNil ifTrue:[
        self showRoot ifFalse:[aRoot setExpanded:true ]
    ].
    ^ super root:aRoot
! !

!HierarchicalFileList methodsFor:'actions'!

matchBlock
    "set the matchBlock - if non-nil, it controls which files are visible.
    "
    ^ matchBlock
        
!

matchBlock:aBlock
    "set the matchBlock - if non-nil, it controls which files are visible.
    "
    matchBlock := aBlock.

    root notNil ifTrue:[
        self recursionLock critical:[
            self stopMonitoringTask.
            root matchBlockChanged.
        ].
        self startMonitoringTask.
    ].

!

sortBlock
    "set the matchBlock - if non-nil, it controls which files are visible.
    "
    sortBlock notNil ifTrue:[ ^ sortBlock ].

    sortBlock := [:a :b| |aIsDir|
        aIsDir := a isDirectory.
        aIsDir == b isDirectory  ifTrue:[a fileName name <= b fileName name]
                                ifFalse:[aIsDir].
    ].
    ^ sortBlock
!

sortBlock:aBlock
    "set the matchBlock - if non-nil, it controls which files are visible.
    "
    sortBlock := aBlock.

    root notNil ifTrue:[
        self recursionLock critical:[
            self stopMonitoringTask.
            root recursiveSort:aBlock.
        ].
        self startMonitoringTask.
    ].
! !

!HierarchicalFileList methodsFor:'private monitoring task'!

monitoringCycle
    "the block evaluated by the monitoring task; test whether directory is expanded
     otherwise we have not to evaluate the directory contents.
     think about remote file-systems
    "
    |index item|

    item  := root.
    index := showRoot ifTrue:[1] ifFalse:[0].

    item isNil ifTrue:[
        item  := self at:index ifAbsent:nil.
    ].

    [item notNil] whileTrue:[
        dependents size == 0 ifTrue:[ ^ self ].

        item isDirectory ifTrue:[
            item monitoringCycle
        ].
        Processor yield.
        index := index + 1.
        item  := self at:index ifAbsent:nil.
    ].
! !

!HierarchicalFileList methodsFor:'protocol'!

childrenFor:anItem
    "returns all visible children derived from the physical
     directory contents.
    "
    |contents list matchBlock|

    anItem isDirectory ifFalse:[^ #()].

    contents := DirectoryContents directoryNamed:anItem fileName.
    contents isNil ifTrue:[ ^ #() ].

    list := OrderedCollection new.
    matchBlock := self matchBlockFor:anItem.

    contents itemsDo:[:anItem|
        (matchBlock isNil or:[matchBlock value:(anItem fileName) value:(anItem isDirectory)]) ifTrue:[
            list add:(HierarchicalFileItem forContentsItem:anItem).
        ]
    ].

    list isEmpty ifTrue:[^ #()].
    list sort:self sortBlock.
    ^ list
!

hasChildrenFor:anItem
    "returns true if the physical directory contains at least
     one visible item otherwise false.
    "
    |block|

    anItem isDirectory ifFalse:[
        ^ false
    ].

    (block := self matchBlockFor:anItem) isNil ifTrue:[
        block := [:aFilename :isDirectory| true ]
    ].
    ^ DirectoryContents directoryNamed:(anItem fileName) detect:block
!

matchBlockFor:anItem
    "get the matchBlock - if non-nil, it controls which files are
     visible within the physical directory
    "
    ^ matchBlock        
! !

!HierarchicalFileList methodsFor:'searching'!

findLastForFile:aPathOrFile
    "find last item which matches the path or file
     returns the item or nil if not contained in self
    "
    |file searchItem rootDir rootComponents searchComponents|

    (aPathOrFile isNil or:[root isNil]) ifTrue:[
        ^ nil
    ].

    file := aPathOrFile asFilename.
    file exists ifFalse:[ ^ nil ].

    rootDir := root fileName asAbsoluteFilename.
"/    file    := file asAbsoluteFilename.


"/    (file pathName startsWith:(rootDir pathName)) ifFalse:[
    (file asString startsWith:(rootDir pathName)) ifFalse:[
        "not included"
        ^ nil
    ].
    rootComponents   := rootDir components.
    searchComponents := file asCanonicalizedFilename components.
    searchItem       := root.

    searchComponents from:(rootComponents size + 1) do:[:aName| |child|
        child := searchItem detect:[:el| el baseName = aName ] ifNone:nil.

        child isNil ifTrue:[ ^ searchItem ].
        searchItem := child.
    ].
    ^ searchItem
! !

!HierarchicalFileList methodsFor:'update'!

startIndicatorValidationFor:anItem
    "an item will be registered for an indication update
    "
    |prio|

    self criticalDo:[
        indicatorList size == 0 ifTrue:[
            indicatorList := OrderedCollection new.
        ] ifFalse:[
            indicatorList removeIdentical:anItem ifAbsent:nil.
        ].
        "/ indicatorList addFirst:anItem.
        indicatorList add:anItem.

        indicatorTask isNil ifTrue:[
            prio := Processor activePriority.
            indicatorTask := [ self updateIndicatorCycle. ] forkAt:(prio - 1).
            indicatorTask priorityRange:(prio-1 to:prio).
        ]
    ].
!

stopIndicatorValidationFor:anItem
    "stop the indicator validation for an item
    "
    self criticalDo:[
        indicatorList notNil ifTrue:[
            indicatorList removeIdentical:anItem ifAbsent:nil.
            anItem resetFetchIndicator.
        ]
    ].
!

updateIndicatorCycle
    "run fetching indicator task cycle.
     This is done in the background to avoid long startup
     delays, in case the indicator information takes long to
     gather (i.e. when reading directories)
    "
    |repeat task item|

    repeat := true.
    task   := indicatorTask.

    [ [ task notNil ] whileTrue:[
        self criticalDo:[
            (     dependents    size ~~ 0       "/ no dependencies (stop task)
             and:[indicatorList size ~~ 0]      "/ nothing to do
            ) ifTrue:[
                item := indicatorList removeFirst.

                (self includesIdentical:item) ifFalse:[
                    "/ no longer visible
                    item resetFetchIndicator.
                    item := nil
                ]
            ] ifFalse:[
                item := indicatorTask := task := nil
            ]
        ].
        item notNil ifTrue:[
            item fetchIndicator.
            Processor yield.
        ].
     ]
    ] valueNowOrOnUnwindDo:[
        task notNil ifTrue:[
            "/ oops, process terminated
            self criticalDo:[
                "/ test whether a new task already started
                indicatorTask == task ifTrue:[
                    indicatorTask := nil
                ]
            ]
        ]
    ].
! !

!HierarchicalFileList::HierarchicalFileItem class methodsFor:'instance creation'!

fileName:aFileName
    ^ self forContentsItem:(DirectoryContents contentsItemForFileName:aFileName)
!

forContentsItem:aContentsItem
    |item cls|

    cls := HierarchicalFileList::File.

    aContentsItem notNil ifTrue:[
        aContentsItem isRemoteDirectory ifTrue:[
            cls := HierarchicalFileList::RemoteDirectory
        ] ifFalse:[
            aContentsItem isDirectory ifTrue:[
                cls := HierarchicalFileList::Directory
            ]
        ].
    ].
    item := cls basicNew initialize.
    item contentsItem:aContentsItem.
    ^ item
!

new
    self error.
! !

!HierarchicalFileList::HierarchicalFileItem methodsFor:'accessing'!

baseName
    "returns the baseName
    "
    ^ contentsItem fileName baseName.
!

contentsItem:aContentsItem
    contentsItem := aContentsItem
!

fileName
    "returns the fileName
    "
    ^ contentsItem fileName
!

fileName:aFilename
self halt.
    contentsItem :=  DirectoryContents contentsItemForFileName:aFilename

"/    fileName = aFilename ifFalse:[
"/        fileName := aFilename.
"/        self changed:#label
"/    ].
!

fileSize
    "returns the fileSize
    "
    |fileInfo|

    fileInfo := contentsItem info.
    fileInfo isNil ifTrue:[^ nil].
  ^ fileInfo fileSize
!

group
    "returns the printable group
    "
    |fileInfo gid group|

    fileInfo := contentsItem info.
    fileInfo notNil ifTrue:[
        gid := fileInfo gid.

        gid notNil ifTrue:[
            (LastGIDToGroupNameMapping notNil and:[gid == LastGIDToGroupNameMapping key]) ifTrue:[
                ^ LastGIDToGroupNameMapping value
            ].
            group := OperatingSystem getGroupNameFromID:gid.
            LastGIDToGroupNameMapping := gid -> group.
          ^ group
        ]
    ].
    ^ '???'
!

icon
    "returns the icon key
    "
    icon isNil ifTrue:[
        self isRemoteDirectory ifTrue:[
            icon := FileBrowser iconForKeyMatching:#directoryNetwork
        ] ifFalse:[
            icon := FileBrowser iconForFile:(self fileName).
        ]
    ].
    ^ icon.
!

label
    "returns the printable name, the baseName
    "
    ^ contentsItem fileName baseName
!

modificationTime
    "returns the absolute time of modification
    "

    |fileInfo|

    fileInfo := contentsItem info.
    fileInfo isNil ifTrue:[^ nil].
    ^ fileInfo modificationTime
!

owner
    "returns the printable owner
    "
    |fileInfo uid owner|

    fileInfo := contentsItem info.
    fileInfo notNil ifTrue:[
        uid := fileInfo uid.

        uid notNil ifTrue:[
            (LastUIDToUserNameMapping notNil and:[uid == LastUIDToUserNameMapping key]) ifTrue:[
                ^ LastUIDToUserNameMapping value
            ].
            owner := OperatingSystem getUserNameFromID:uid.
            LastUIDToUserNameMapping := uid -> owner.
          ^ owner
        ]
    ].

    ^ '???'
!

pathName
    "returns the pathName
    "
    ^ contentsItem fileName pathName
!

permissions
    "returns the permissions as printable string
    "
    |fileInfo mode perms|

    fileInfo := contentsItem info.
    fileInfo notNil ifTrue:[
        mode := fileInfo mode.

        mode notNil ifTrue:[
            perms := String new:9 withAll:$-.

            1 to:9 by:3 do:[:i|
                (mode bitAt:i    ) == 1 ifTrue:[perms at:10 - i put:$x].
                (mode bitAt:i + 1) == 1 ifTrue:[perms at:9  - i put:$w].
                (mode bitAt:i + 2) == 1 ifTrue:[perms at:8  - i put:$r].
            ].
            ^ perms
        ]
    ].
    ^ '???'
!

suffix
    "returns the suffix of the file
    "
    (OperatingSystem isUNIXlike and:[(self baseName at:1) == $.]) ifTrue:[
        ^ ''
    ].
    ^ contentsItem fileName suffix
! !

!HierarchicalFileList::HierarchicalFileItem methodsFor:'change & update'!

changed:aParameter
    "the item changed; raise change notification
    "
    aParameter == #icon ifTrue:[ icon := nil ].
    super changed:aParameter.
! !

!HierarchicalFileList::HierarchicalFileItem methodsFor:'instance creation'!

fileName:aFilename fileInfo:aFileInfoOrNil
self halt.
"/    fileName := aFilename.
"/    fileInfo := aFileInfoOrNil.
! !

!HierarchicalFileList::HierarchicalFileItem methodsFor:'invalidate'!

invalidate
    "invalidate the contents
    "
    self invalidateRepairNow:false

!

invalidateRepairNow
    "invalidate the contents; repair now
    "
    self invalidateRepairNow:true

!

invalidateRepairNow:doRepair
    "invalidate the contents; dependent on the boolean
     do repair immediately
    "


!

matchBlockChanged
    "called if the matchBlock changed
    "

! !

!HierarchicalFileList::HierarchicalFileItem methodsFor:'printing'!

printString

    ^ super printString, ' for: ', self fileName asString
! !

!HierarchicalFileList::HierarchicalFileItem methodsFor:'protocol'!

flushChildren
    "flush the children because node not visible ....
     canbe redefined by subclass
    "
    children := nil.
! !

!HierarchicalFileList::HierarchicalFileItem methodsFor:'queries'!

isDirectory
    ^ false
!

isRemoteDirectory
    ^ false
!

time

    ^ self valueAt:#modified
! !

!HierarchicalFileList::File methodsFor:'accessing'!

children
    "always returns an empty list
    "
    ^ #()
! !

!HierarchicalFileList::File methodsFor:'queries'!

hasChildren
    "always returns false
    "
    ^ false
! !

!HierarchicalFileList::Directory class methodsFor:'documentation'!

documentation
"
    [Instance variables:]

        fetchOperation  <Symbol/Boolean>    nil             if children is nil, no information about has children
                                            #fetching       registered in list to be updated for indication
                                            #hasChildren    registered in list to be updated for indication
                                            #hasNoChildren  has children but children list might be nil (remote)
"
! !

!HierarchicalFileList::Directory methodsFor:'accessing'!

children
    "returns the list of children
    "
    |model|

    children notNil ifTrue:[ ^ children ].

    model := self model.
    model isNil ifTrue:[ ^ nil ].

    model criticalDo:[
        children isNil ifTrue:[ self readChildren ].
    ].
    ^ children
!

flushChildren
    "flush the children because node not visible ....
    "
    children notNil ifTrue:[
        "keep hasChildren information
        "
        children size ~~ 0 ifTrue:[ fetchOperation := #hasChildren ]
                          ifFalse:[ fetchOperation := #hasNoChildren ].
        children := nil.
    ].
!

icon
    "returns the icon key
    "
    isExpanded ifTrue:[
        ^ FileBrowser iconForKeyMatching:#directoryOpen
    ].
    icon isNil ifTrue:[
        ^ super icon
    ].
    ^ icon
!

readChildren
    "reads the list of children
    "
    |model list hadChildren hasChildren|

    model := self model.

    model isNil ifTrue:[
        "/ must reread later
        fetchOperation := modificationTime := children := nil.
      ^ nil
    ].

    hadChildren := children size ~~ 0.

    "/ set to suppress reading of children
    children := #().
    fetchOperation   := nil.
    modificationTime := self fileName modificationTime.
    model stopIndicatorValidationFor:self.

    list := model childrenFor:self.

    list size ~~ 0 ifTrue:[
        list do:[:aChild| aChild parent:self].
        children := list.
    ].
    hasChildren := children size ~~ 0.

    hasChildren ~~ hadChildren ifTrue:[
        self changed:#redraw
    ].
    ^ children
! !

!HierarchicalFileList::Directory methodsFor:'accessing-hierarchy'!

collapse

    super collapse.

    children notNil ifTrue:[
        children do:[:el| el flushChildren ]
    ].
!

expand
    "expand children; must redefine to raise a notification
     if children are not yet initialized and after initialization empty.
    "

    super expand.
!

recursiveCollapse

    super recursiveCollapse.
!

recursiveExpand
    "redefined to expand
    "
    self expand


! !

!HierarchicalFileList::Directory methodsFor:'fetching'!

basicFetchIndicator
    |hasChildren|

    hasChildren := DirectoryContents directoryNamed:self fileName detect:(self model matchBlock).
    hasChildren ifTrue:[
        fetchOperation := #hasChildren
    ] ifFalse:[
        fetchOperation := #hasNoChildren
    ].
    children isNil ifTrue:[
        "setup modification time to suppress monitorCycle
        "
        modificationTime := self fileName modificationTime.
    ].
!

fetchIndicator
    "fetch the indicator value which indicates whether children exists or not
     called by the list
    "
    children notNil ifTrue:[
        "/ children already read
        fetchOperation := nil.
      ^ self
    ].

    fetchOperation ~~ #fetching ifTrue:[
        "/ children will be updated ....
        ^ self
    ].
    "/ suppress restart of fetchIndicator

    self basicFetchIndicator.

    children notNil ifTrue:[
        fetchOperation := nil.
        children notEmpty ifTrue:[ self changed:#redraw ].
    ] ifFalse:[
        "/ is a remote or very slow file system
        fetchOperation == #hasChildren ifTrue:[
            self changed:#redraw
        ].
    ].
!

resetFetchIndicator
    "update indication cycle has deregistered the item
    "
    fetchOperation := nil.
! !

!HierarchicalFileList::Directory methodsFor:'queries'!

hasChildren
    "returns true if children exists
    "
    |model|

    children notNil ifTrue:[
        fetchOperation := nil.
      ^ children size ~~ 0
    ].

    fetchOperation notNil ifTrue:[
        ^ fetchOperation == #hasChildren
    ].

    model := self model.

    model notNil ifTrue:[
        fetchOperation := #fetching.
        model startIndicatorValidationFor:self.
    ] ifFalse:[
        self error:'should not happen' mayProceed:true.
        fetchOperation := nil
    ].
    ^ children size ~~ 0
!

isDirectory
    "always returns true
    "
    ^ true


! !

!HierarchicalFileList::Directory methodsFor:'validation'!

invalidateRepairNow:doRepair
    "invalidate contents
    "
    fetchOperation := modificationTime := nil.

    isExpanded ifFalse:[
        children := nil
    ] ifTrue:[
        doRepair ifTrue:[
            self monitoringCycle
        ] ifFalse:[
            children size == 0 ifTrue:[
                "/ expanded but no children added, thus can reset the children
                children := nil
            ]
        ]
    ].
!

matchBlockChanged
    "called if the matchBlock changed
    "
    modificationTime := nil.

    isExpanded ifFalse:[
        fetchOperation := children := nil.
    ] ifTrue:[
        self monitoringCycle.

        children size ~~ 0 ifTrue:[
            children do:[:aChild| aChild matchBlockChanged ]
        ]
    ].
!

monitoringCycle
    "run monitoring cycle
        !!!!!!!! called by the HierarchicalList only !!!!!!!!
    "
    |unusedDict addedItems mergedList size modifyTime model timeChanged|

    modifyTime := self fileName modificationTime.
    modifyTime isNil ifTrue:[^ self].

    timeChanged := (modificationTime isNil or:[modifyTime > modificationTime]).
    modificationTime := modifyTime.

    children notNil ifTrue:[
        timeChanged ifFalse:[
            ^ self
        ].
    ].

    isExpanded ifFalse:[
        timeChanged ifTrue:[
             fetchOperation := children := nil.
             self changed:#redraw.
        ].
        ^ self
    ].
    model := self model.
    children isNil ifTrue:[ children := #() ].         "/ disable update during merge


    fetchOperation := nil.
    mergedList     := model childrenFor:self.

    mergedList size == 0 ifTrue:[
        self removeAll.
      ^ self
    ].

    size := children size.

    size == 0 ifTrue:[
        self addAll:mergedList.
      ^ self
    ].

    model criticalDo:[
        addedItems := OrderedCollection new:128.
        unusedDict := Dictionary new:size.

        children do:[:el| unusedDict at:(el fileName) put:el ].

        mergedList keysAndValuesDo:[:anIndex :anItem| |item|
            item := unusedDict removeKey:(anItem fileName) ifAbsent:nil.

            item notNil ifTrue:[
                mergedList at:anIndex put:item
            ] ifFalse:[
                addedItems add:anItem.
                anItem parent:self.
            ].
        ].
        "/ 12 is hardcoded !!!!!!!!

        (unusedDict size + addedItems size) > 12 ifTrue:[
            "/ generate two nofifications: collapse and expand
            self collapse.
            children := mergedList.
            self expand.
        ] ifFalse:[
            unusedDict do:[:el| self remove:el ].

            addedItems notEmpty ifTrue:[
                self addAll:addedItems
            ].
            "/ children order changed test
            children := mergedList.
            self childrenOrderChanged.
        ].
    ].
! !

!HierarchicalFileList::RemoteDirectory methodsFor:'queries'!

hasChildren
    "returns true if children exists
    "
    children notNil ifTrue:[
        fetchOperation := nil.
        ^ children size ~~ 0
    ].
    fetchOperation := #hasChildren.
  ^ true
!

isRemoteDirectory
    ^ true
! !

!HierarchicalFileList class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/HierarchicalFileList.st,v 1.38 2002-11-21 08:52:29 penk Exp $'
! !