DirectoryTreeBrowser.st
author penk
Fri, 27 Sep 2002 14:04:44 +0200
changeset 3906 8a76cb4f5884
parent 3892 321c1729db5b
child 3907 a06fe9db6195
permissions -rw-r--r--
next stage

"{ Package: 'stx:libtool' }"

AbstractFileBrowser subclass:#DirectoryTreeBrowser
	instanceVariableNames:'rootHolder dirBrowser lastResponse updateToExternFileHolderLock
		oldDropItem expandItemTimedBlock updateTreeSelection'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-Tools-File'
!

HierarchicalFileList subclass:#DirTreeBrowserHFL
	instanceVariableNames:'draggedItem'
	classVariableNames:''
	poolDictionaries:''
	privateIn:DirectoryTreeBrowser
!

!DirectoryTreeBrowser class methodsFor:'documentation'!

documentation
"
    documentation to be added.

    [author:]
        Christian Penk (penk@bierfix)

    [see also:]

    [instance variables:]

    [class variables:]
"
!

examples
"
  Starting the application:
                                                                [exBegin]
    DirectoryTreeBrowser open

                                                                [exEnd]

  more examples to be added:
                                                                [exBegin]
    ... add code fragment for 
    ... executable example here ...
                                                                [exEnd]
"
! !

!DirectoryTreeBrowser class methodsFor:'instance creation'!

open

    ^ super open
"
    DirectoryTreeBrowser open
"
!

openOn:aFileName

    | file |
    file := aFileName asFilename.
    file exists ifTrue:[
        self openOn:aFileName withFiles:(file isDirectory not)
    ]        

"
    DirectoryTreeBrowser openOn:Filename homeDirectory   
    DirectoryTreeBrowser openOn:(Filename homeDirectory construct:'.bashrc')  
"
!

openOn:aFileName withFiles:aBoolean

    | instance|

    instance := DirectoryTreeBrowser new.
    instance open.
    instance viewFilesInDirectoryTree value:aBoolean.
    instance currentFileNameHolder value:(OrderedCollection with:aFileName).
"
    DirectoryTreeBrowser openOn:Filename homeDirectory  
    DirectoryTreeBrowser openOn:(Filename homeDirectory construct:'.bashrc') withFiles:false  
"
! !

!DirectoryTreeBrowser class methodsFor:'defaults'!

timeForExpandOnDropInMilliseconds

    ^ 1500
! !

!DirectoryTreeBrowser class methodsFor:'interface specs'!

windowSpec
    "This resource specification was automatically generated
     by the UIPainter of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the UIPainter may not be able to read the specification."

    "
     UIPainter new openOnClass:DirectoryTreeBrowser andSelector:#windowSpec
     DirectoryTreeBrowser new openInterface:#windowSpec
     DirectoryTreeBrowser open
    "

    <resource: #canvas>

    ^ 
     #(#FullSpec
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'DirectoryTreeBrowser'
          #name: 'DirectoryTreeBrowser'
          #min: #(#Point 10 10)
          #max: #(#Point 1024 768)
          #bounds: #(#Rectangle 16 42 316 342)
          #menu: #mainMenu
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#HierarchicalListViewSpec
              #name: 'HierarchicalListView'
              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
              #model: #treeSelectionHolder
              #menu: #menu
              #hasHorizontalScrollBar: true
              #hasVerticalScrollBar: true
              #miniScrollerHorizontal: false
              #miniScrollerVertical: false
              #listModel: #fileList
              #multipleSelectOk: true
              #highlightMode: #label
              #doubleClickSelector: #doDoubleClick:
              #indicatorSelector: #doIndicatorClick:
              #postBuildCallback: #postBuildDirBrowser:
              #properties: 
             #(#PropertyListDictionary
                #dragArgument: #directoryTreeBrowser
                #startDragSelector: #doStartDrag:in:
                #displayObjectSelector: #getDisplayObjects:
                #dropObjectSelector: #getDropObjects:
                #dropArgument: #directoryTreeBrowser
                #canDropSelector: #canDrop:argument:
                #leaveSelector: #dropLeave:
                #dropSelector: #doDrop:argument:
              )
            )
           )
         
        )
      )
! !

!DirectoryTreeBrowser class methodsFor:'menu specs'!

menu
    "This resource specification was automatically generated
     by the MenuEditor of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the MenuEditor may not be able to read the specification."

    "
     MenuEditor new openOnClass:DirectoryTreeBrowser andSelector:#menu
     (Menu new fromLiteralArrayEncoding:(DirectoryTreeBrowser menu)) startUp
    "

    <resource: #menu>

    ^ 
     #(#Menu
        #(
         #(#MenuItem
            #label: 'Copy'
            #translateLabel: true
            #value: #doCopy
            #shortcutKeyCharacter: #Copy
          )
         #(#MenuItem
            #label: 'Cut'
            #translateLabel: true
            #value: #doCut
            #shortcutKeyCharacter: #Cut
          )
         #(#MenuItem
            #label: 'Paste'
            #translateLabel: true
            #value: #pasteFiles
            #enabled: #canPaste
            #shortcutKeyCharacter: #Paste
          )
         #(#MenuItem
            #label: 'Delete'
            #translateLabel: true
            #nameKey: #delete
            #value: #doDelete
            #shortcutKeyCharacter: #Delete
          )
         #(#MenuItem
            #label: '-'
          )
         #(#MenuItem
            #label: 'Directory Up'
            #translateLabel: true
            #value: #doGoDirectoryUp
            #enabled: #enableDirectoryUp
            #shortcutKeyCharacter: #CursorLeft
          )
         #(#MenuItem
            #label: 'Set Selection Top'
            #translateLabel: true
            #value: #doSetSelectionToTop
            #enabled: #selectedFileIsDirectoryAndNotRoot
          )
         #(#MenuItem
            #label: 'Re-/ Expand Directory'
            #translateLabel: true
            #value: #expandSelectedItem
            #shortcutKeyCharacter: #CursorRight
          )
         #(#MenuItem
            #label: '-'
          )
         #(#MenuItem
            #label: 'View Directory Tree'
            #translateLabel: true
            #isVisible: #masterIsFileBrowser
            #indication: #showDirectoryTreeHolder
          )
         #(#MenuItem
            #label: 'View Files in Directory Tree'
            #translateLabel: true
            #indication: #viewFilesInDirectoryTree
          )
         #(#MenuItem
            #label: '-'
          )
         #(#MenuItem
            #label: 'New'
            #translateLabel: true
            #submenuChannel: #newMenu
          )
         #(#MenuItem
            #label: 'Rename...'
            #translateLabel: true
            #value: #treeViewFileRename
            #shortcutKeyCharacter: #Replace
          )
         )
        nil
        nil
      )
! !

!DirectoryTreeBrowser class methodsFor:'plugIn spec'!

aspectSelectors
    "This resource specification was automatically generated
     by the UIPainter of ST/X."

    "Do not manually edit this. If it is corrupted,
     the UIPainter may not be able to read the specification."

    "Return a description of exported aspects;
     these can be connected to aspects of an embedding application
     (if this app is embedded in a subCanvas)."

    ^ #(
        #selectedDirectoryModel
      ).

! !

!DirectoryTreeBrowser methodsFor:'accessing'!

updateToExternFileHolderLock
    "return the value of the instance variable 'updateToExternFileHolder' (automatically generated)"

    updateToExternFileHolderLock isNil ifTrue:[
        updateToExternFileHolderLock := self class newLock.
    ].
    ^ updateToExternFileHolderLock
!

updateTreeSelection
    "return the value of the instance variable 'updateToExternFileHolder' (automatically generated)"

    updateTreeSelection isNil ifTrue:[
        updateTreeSelection := self class newLock.
    ].
    ^ updateTreeSelection
! !

!DirectoryTreeBrowser methodsFor:'actions'!

doDoubleClick:anIndex 
    "handle a doubleClick on a directory
    "

    |item file isDirectory|

    item := self fileList at:anIndex ifAbsent:nil.
    item notNil ifTrue:[
        isDirectory := item isDirectory.
        file := item fileName.
        isDirectory ifTrue:[
            (file isReadable and:[file isExecutable]) ifTrue:[
                self doExpand:item.
            ]
        ] ifFalse:[
"/            self openApplByFileItem:item.
        ]
    ]
!

doExpand:anItem
" expand the item; return true the item have expanded "

    (anItem notNil and:[anItem isDirectory and:[anItem isExpanded not]]) ifTrue:[
        anItem toggleExpand.
        ^ true.
    ].          
    ^ false
!

doIndicatorClick:anIndex 
    "handle a click on the indicator
    "

    |item|

    item := self fileList at:anIndex ifAbsent:nil.
    self toggleExpand:item
!

doUpdate

    self fileList monitoringCycle.
"/    self updateSelectedItem
!

expandSelectedItem

    |selDir|

    selDir := self getFirstDirectoryItemOfSelection.
    selDir isNil ifTrue:[^ self ].
    self toggleExpand:selDir.
!

setMatchBlock

    |list|

    list := self fileList.
    self setMatchBlockForList:list
!

setMatchBlockForList:list

    self viewFilesInDirectoryTree value ifTrue:[
        list matchBlock:[:fn :isDir| isDir or:[
                            (self showHiddenFiles value ifFalse:[
                                (fn baseName startsWith:'.') not])
                             and:[self filterModel value match:fn baseName]]] 
    ] ifFalse:[
        list matchBlock:[:fn :isDir| isDir ].
    ].
!

toggleExpand:anItem

    (anItem notNil and:[anItem isDirectory]) ifTrue:[
        anItem toggleExpand
    ].
!

treeViewFileRename
    ||

    dirBrowser openEditor.
"/    selectedFiles := self getFilesForSelection.
"/    self renameFiles:selectedFiles.
!

updateSelectedItem

    | sel |

    sel := self getItemsForSelection.
    sel isEmpty ifTrue:[ ^ self].
    sel do:[:item|
        self doExpand:item.
        item invalidateRepairNow:true.
    ]
! !

!DirectoryTreeBrowser methodsFor:'aspects'!

fileList
    "holder, which keeps the current list of file entries shown by the directory-browser
    "

    |list|

    (list := builder bindingAt:#fileList) isNil ifTrue:[
        list := DirTreeBrowserHFL new.
        list application:self.
        list showRoot:true.
        self setMatchBlockForList:list.
        list directory:(self rootHolder value).
        builder aspectAt:#fileList put:list.
        list monitoringTaskDelay:2
    ].
    ^ list
!

rootHolder
    "holder, which keeps the current root directory
    "
    rootHolder isNil ifTrue:[
        rootHolder := ValueHolder new.
        rootHolder addDependent:self.
    ].
    ^ rootHolder.
! !

!DirectoryTreeBrowser methodsFor:'change & update'!

changeCurrentFileNameHolder

    | viewFiles curFiles sel currentFileDir|

    viewFiles := self viewFilesInDirectoryTree value.
    curFiles := self currentFileNameHolder value.
    " if i cant select the files because viewFiles is false i cant take my 
      selction to overwrite currentFileNameHolder
    "        
    sel := self getFilesForSelection.
    viewFiles not ifTrue:[
        (self currentFilesAreInSameDirectory and:[sel size == 1]) ifTrue:[
            currentFileDir := self getDirWithoutFileName:(self currentFileNameHolder value first).
            (sel first = currentFileDir) ifTrue:[
                ^ self.
            ].
        ].
    ].
    self currentFileNameHolder value:sel.
!

changeSelection

    |currentHolder newItem directoryName directory oldSel index viewFiles newSel newColOfItems bestFile dir|

    newSel := OrderedCollection new.
    currentHolder := self currentFileNameHolder value.
    currentHolder isEmpty ifTrue:[
        self treeSelectionHolder value:newSel withoutNotifying:self.
        ^ self
    ].
    bestFile := self getBestFile.
    directory := self getDirWithoutFileName:bestFile.
    directoryName := directory asString.
    viewFiles := self viewFilesInDirectoryTree value.

    
    ((rootHolder value isNil) or:[((self fileName:directoryName startsWith:rootHolder value)) not]) ifTrue:[
        self setNewRoot:directory.
    ].
    newColOfItems := Set new.
    oldSel := self getItemsForSelection.
    currentHolder do:[ : file |
        oldSel notEmpty ifTrue:[
            newItem := oldSel detect:[: item| item fileName = file] ifNone:[nil].
        ].
        newItem isNil ifTrue:[
            ((viewFiles not) and:[file isDirectory not]) ifTrue:[
                "/ select directory because cant select filename - if is not in tree
                dir := self getDirWithoutFileName:file.
                newItem := self recursiveGetItemFor:dir.
            ] ifFalse:[
                newItem := self recursiveGetItemFor:file.
            ].
        ].
        newItem notNil ifTrue:[
            newColOfItems add:newItem.
        ].
    ].
    newSel := OrderedCollection new.
    newColOfItems do:[ : item |
        index := self fileList indexOf:item.
        newSel add:index.
    ].
    self treeSelectionHolder value:newSel.
    newColOfItems size == 1 ifTrue:[
        | item |
        item := newColOfItems first.
        item isDirectory ifTrue:[
            self doExpand:item.
        ]
    ]
!

recursiveGetItemFor:aDirectory

    ^ self recursiveGetItemFor:aDirectory fromIndex:1
!

recursiveGetItemFor:aFile fromIndex:aStartIndex 
    |list aFileNameString startIndex retItem|

    list := self fileList.
    aFileNameString := aFile asString.
    retItem := nil.
    list from:aStartIndex
        do:[:item | 
            |filename |

            filename := item fileName asString.
            (self fileName:aFileNameString startsWith:filename) ifTrue:[
                (filename asFilename pathName = aFileNameString asFilename pathName) ifTrue:[
                    ^ item
                ].
                (item isExpanded not and:[item canExpand]) ifTrue:[
                    item toggleExpand.
                    startIndex := list indexOf:item.
                    retItem := self recursiveGetItemFor:aFile fromIndex:startIndex.
                    ^ retItem
                ]
            ]
        ].
    ^ retItem
!

setNewRoot:directoryPath

    | rootItem|

    "/ EXPAND THE ROOT DIR
    self rootHolder value:directoryPath.
    rootItem := self fileList root.    
    rootItem notNil ifTrue:[
        rootItem expand.
    ].
!

update:something with:aParameter from:aModel 
    "one of my models changed
    "

    |list file|

    " the execution of changeSelection and changeCurrentFileNameHolder must
      lock against each other because values dont must be the same (e.g. no files
      in tree view)
    "

    aModel == self currentFileNameHolder ifTrue:[
        self updateTreeSelection doIfUnLocked:[
            self updateToExternFileHolderLock doLocked:[
                self changeSelection.
            ].
        ].
        " do not return here because the AbstractFileBrowserComponent have to do something
          for every application "  
"/        ^ self.
    ].
    aModel == self treeSelectionHolder ifTrue:[
        self updateToExternFileHolderLock doIfUnLocked:[
            self updateTreeSelection doLocked:[
                self changeCurrentFileNameHolder.
            ]
        ].
        ^ self
    ].
    aModel == rootHolder ifTrue:[
        list := self fileList.
        file := aModel value.
        file notNil ifTrue:[
            file := Filename named:(file asString).
            (file isDirectory and:[file isReadable and:[file isExecutable]]) ifTrue:[
                list directory:file
            ]
        ].
        aModel value:(list directory asString) withoutNotifying:self.
        ^ self.
    ].
    aModel == self viewFilesInDirectoryTree ifTrue:[
        self setMatchBlock.
        "/ if changed to true select the files in currentFilenameHolder in treeview 
        aModel value ifTrue:[
            self changeSelection.
        ].
        ^ self.
    ].
    aModel == self filterModel ifTrue:[
        self setMatchBlock.
    ].
    super update:something with:aParameter from:aModel.
    ^ self
! !

!DirectoryTreeBrowser methodsFor:'drag & drop'!

canDrop:aContext argument:arg2 
    |source lineNr archivListDrop destinationItem dropToFile|

    source := aContext dropSource.
    source isNil ifTrue:[^ false ].
    archivListDrop := (source argument == #archivApplication).
    lineNr := self getLineNumberFor:aContext.
    lineNr notNil ifTrue:[
        destinationItem := self fileList at:lineNr ifAbsent:nil.
    ].
    destinationItem isNil ifTrue:[
        oldDropItem notNil ifTrue:[
            self removeExpandItemTimedBlock.
            self enqueueChangeDraggedItem:nil with:aContext.
            oldDropItem := nil.
        ].
        ^ false
    ].
    (destinationItem ~~ oldDropItem) ifTrue:[
        oldDropItem := destinationItem.
        self enqueueChangeDraggedItem:nil with:aContext.
        destinationItem isDirectory ifTrue:[
            self enqueueChangeDraggedItem:destinationItem with:aContext.
        ].
        self removeExpandItemTimedBlock.
        (destinationItem notNil and:[destinationItem isDirectory and:[destinationItem fileName isWritable]]) ifTrue:[
            expandItemTimedBlock := [
                    self enqueueExpandForDrop:destinationItem with:aContext    
            ].
            Processor addTimedBlock:expandItemTimedBlock
                afterMilliseconds:(self class timeForExpandOnDropInMilliseconds).
            dropToFile := destinationItem fileName.
            archivListDrop ifTrue:[
                lastResponse := self canDropArchiv:(aContext dropObjects) for:dropToFile
            ] ifFalse:[
                lastResponse := self canDropFiles:(aContext dropObjects) for:dropToFile
            ]
        ] ifFalse:[
            lastResponse := false
        ]
    ].
    ^ lastResponse
!

changeDraggedItem:anItem with:aDropContext

    self changeDraggedItem:anItem with:aDropContext saveDraw:true
!

changeDraggedItem:anItem with:aDropContext saveDraw:saveDraw

    saveDraw ifTrue:[
        aDropContext saveDraw:[
            self fileList draggedItem:anItem.
            self windowGroup processExposeEvents.
        ]
    ] ifFalse:[
        self fileList draggedItem:anItem.
        self windowGroup processExposeEvents.
    ]
!

doDrop:aContext 
    |col destination destinationPath lineNr source receiver|

    source := aContext dropSource.
    lineNr := self getLineNumberFor:aContext.
    lineNr isNil ifTrue:[
        ^ false
    ].
    destination := self fileList at:lineNr.
    destinationPath := destination fileName.
    source argument == #archivApplication ifTrue:[
        receiver := source receiver.
        receiver extractSelectedFilesTo:destinationPath askForExtractOptions:true.
        ^ true
    ].
    col := OrderedCollection new.
    aContext dropObjects do:[:obj | 
        col add:(obj theObject)
    ].
    self enqueueCopyOrMoveFiles:col to:destinationPath.
    ^ true
!

doDrop:aContext argument:arg2 

    | aBoolean |

    aBoolean := self doDrop:aContext.
    self dropLeave:aContext.
    ^ aBoolean.
!

dropLeave:aDropContext 
    "send the last time, when leaving the widget
    "
    self removeExpandItemTimedBlock.
    oldDropItem := nil.
    self changeDraggedItem:nil with:aDropContext saveDraw:false.
    lastResponse := nil.
!

enqueueChangeDraggedItem:anItem with:aContext 

    self enqueueMessage:#'changeDraggedItem:with:' for:self arguments:(Array with:anItem with:aContext) 
!

enqueueCopyOrMoveFiles:col to:destinationPath 

    self enqueueMessage:#'copyOrMoveFiles:to:' for:self arguments:(Array with:col with:destinationPath) 
!

enqueueExpandForDrop:item with:aDropContext

    self enqueueMessage:#'expandForDrop:with:' for:self arguments:(Array with:item with:aDropContext) 
!

expandForDrop:item with:aDropContext

    aDropContext saveDraw:[
        (self doExpand:item) ifTrue:[
            self windowGroup processExposeEvents
        ].
    ]
!

getDisplayObjects:anArgument

    | string fnName sel size stream|
    sel := self getFilesForSelection.
    size := sel size.
    size == 0  ifTrue:[^ ''].
    stream := WriteStream on:''.
    stream nextPutAll:sel first baseName.
    size == 1 ifTrue:[
        fnName := 'ui_menuitem.xpm'.
    ] ifFalse:[
        fnName := 'ui_submenu_open.xpm'.
        stream nextPutAll:' ... '.
        stream nextPutAll:sel last baseName.
    ].
    string := stream contents.
    stream close.

    fnName := 'ui_menuitem.xpm'.
    ^ Array with:(LabelAndIcon icon:(Image fromFile:fnName)
                             string:(Text string:string emphasis:#bold)
                 )
!

getDropObjects:anArgument

    | sel ret|

    sel := self getFilesForSelection.
    sel isEmpty ifTrue:[ ^ self ].
    ret := sel collect:[:file| 
        DropObject newFile:file
    ].
    ^ ret
!

getLineNumberFor:aDropContext
    | yVisible|

    yVisible := (aDropContext targetPoint y).
    ^ dirBrowser yVisibleToLineNr:yVisible.
!

removeExpandItemTimedBlock
    expandItemTimedBlock notNil ifTrue:[
        Processor removeTimedBlock:expandItemTimedBlock.
        expandItemTimedBlock := nil
    ]
! !

!DirectoryTreeBrowser methodsFor:'event handling'!

processEvent:anEvent
    "filter keyboard events.
     Return true, if I have eaten the event"

    |focusView key rawKey|

    anEvent isKeyPressEvent ifTrue:[
        focusView := anEvent targetView.
        key := anEvent key.
        rawKey := anEvent rawKey.

        (focusView isSameOrComponentOf:self window) ifTrue:[

            focusView name = 'editField' ifTrue:[ ^ false].

            (key == #FocusPrevious) ifTrue:[
                "go to last selection in selection history"
                self doBack.
                ^ true
            ].
            (key == #FocusNext) ifTrue:[
                "go to next selection in selection history"
                self doForward.
                ^ true
            ].
            (key == #Replace) ifTrue:[
                self treeViewFileRename.
                ^ true
            ].
            (key == #Delete) ifTrue:[
                self doDelete.
                ^ true
            ].
            (key == #Cut) ifTrue:[
                self doCut.
                ^ true
            ].
            (key == #Paste) ifTrue:[
                self pasteFiles.
                ^ true
            ].
            (key == #Copy) ifTrue:[
                self doCopy.
                ^ true
            ].
        ]
    ].
    ^ false
! !

!DirectoryTreeBrowser methodsFor:'menu - actions'!

doSetSelectionToTop
    | selDir|

    selDir := self getFirstDirectoryOfSelection.
    selDir notNil ifTrue:[
        self rootHolder value asFilename = selDir ifTrue:[ ^ self].
        self setNewRoot:selDir.
        self currentFileNameHolder value:(OrderedCollection with:selDir).
    ].
! !

!DirectoryTreeBrowser methodsFor:'queries'!

getFilesForSelection

    | list sel colOfFiles|

    list := self fileList.
    colOfFiles := OrderedCollection new.
    list isEmpty ifTrue:[ ^ colOfFiles].
    sel := self treeSelectionHolder value.
    sel isNil ifTrue:[ ^ colOfFiles].

    sel do:[: index |
        colOfFiles add:((list at:index) fileName)
    ].
    ^ colOfFiles.
!

getFirstDirectoryItemOfSelection

    | sel dir |
    sel := self getItemsForSelection.
    sel isEmpty ifTrue:[ ^ nil].
    ^ dir := sel detect:[: el | el isDirectory ] ifNone:[nil].
!

getFirstDirectoryOfSelection

    | sel dirItem |
    sel := self getItemsForSelection.
    sel isEmpty ifTrue:[ ^ nil].
    dirItem := sel detect:[: el | el isDirectory ] ifNone:[nil].
    dirItem isNil ifTrue:[^ nil].
    ^ dirItem fileName.
!

getItemsForSelection

    | list sel colOfItems|

    list := self fileList.
    colOfItems := OrderedCollection new.
    list isEmpty ifTrue:[ ^ colOfItems].
    sel := self treeSelectionHolder value.
    sel isNil ifTrue:[ ^ colOfItems].

    sel do:[: index |
        colOfItems add:(list at:index)
    ].
    ^ colOfItems.
!

masterIsFileBrowser

    ^ self masterApplication class = FileBrowserV2
!

selectedFileIsDirectoryAndNotRoot

    | dir|

    dir := self getFirstDirectoryOfSelection.
    dir isNil ifTrue:[^ false].
    ^  [(dir asString) ~= (self rootHolder value)]
! !

!DirectoryTreeBrowser methodsFor:'startup & release'!

makeDependent

    self currentFileNameHolder addDependent:self.
    self notifyChannel addDependent:self.
    self viewFilesInDirectoryTree addDependent:self.
    self treeSelectionHolder addDependent:self.
    self filterModel addDependent:self.
!

postBuildAsSubcanvasWith:aBuilder

    super postBuildAsSubcanvasWith:aBuilder.
!

postBuildDirBrowser:aWidget

    dirBrowser := aWidget scrolledView.
    dirBrowser openEditorAction:[:ln :aGC| |field item filename newFileString rename newFilename|
        item  := self fileList at:ln.

        item label isString ifFalse:[
            field := nil
        ] ifTrue:[
            field := EditField new.
            field level:0.
            field acceptOnReturn:true.
            field acceptAction:[:x| 
                filename := item fileName.
                newFileString := x at:1.
                filename baseName = newFileString ifFalse:[ 
                    (self renameFile:filename to:newFileString update:false) ifTrue:[ 
                        newFilename := filename directory construct:newFileString.
                        item fileName:newFilename.
                        self updateAndSelect:(OrderedCollection with:newFilename).
                    ].
                ].
                aGC closeEditor.
            ].
            field font:(aGC font).
            field contents:(item label).
        ].
        field
    ].
!

postBuildWith:aBuilder

    super postBuildWith:aBuilder.
!

postOpenAsSubcanvasWith:aBuilder

    self currentFileNameHolder changed.
    self windowGroup addPreEventHook:self.
    ^ super postOpenAsSubcanvasWith:aBuilder.
!

postOpenWith:aBuilder

    "
    only invoked if the application not started from a master
    "
    self currentFileNameHolder changed.
    self windowGroup addPreEventHook:self.
    ^ super postOpenWith:aBuilder
!

preBuildWith:aBuilder

    self masterApplication isNil ifTrue:[
        self masterApplication:nil.
    ].
    ^ super preBuildWith:aBuilder.
!

release

    self fileList stopMonitoringTask.
    ^ super release.
! !

!DirectoryTreeBrowser methodsFor:'user actions'!

doCopy
    "copy current selected files/directories
    "

    self copyFilesToClipBoard:self getFilesForSelection.
!

doCut
    "cut current selected files/directories
    "
    self cutFilesToClipBoard:self getFilesForSelection.
!

doDelete
    "delete current selected files/directories
    "

    self deleteFiles:self getFilesForSelection.
! !

!DirectoryTreeBrowser::DirTreeBrowserHFL methodsFor:'accessing'!

draggedItem:anItemOrNil
" change the item icon ; return true if changed otherwise false"

    |oldItem|

    (anItemOrNil isNil or:[draggedItem ~~ anItemOrNil]) ifTrue:[
        oldItem     := draggedItem.
        draggedItem := anItemOrNil.

        oldItem     ifNotNil:[ oldItem     iconChanged ].
        draggedItem ifNotNil:[ draggedItem iconChanged ].
        ^ true
    ].
    ^ false
! !

!DirectoryTreeBrowser::DirTreeBrowserHFL methodsFor:'protocol'!

validateIcon:icon for:anItem

    draggedItem == anItem ifTrue:[
        ^ (FileBrowser iconForKeyMatching:#directoryOpenGray) ? icon.
    ].
    ^ icon
! !

!DirectoryTreeBrowser class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libtool/DirectoryTreeBrowser.st,v 1.2 2002-09-27 12:04:22 penk Exp $'
! !