FileSelectionTree.st
author ca
Wed, 22 Oct 1997 17:47:35 +0200
changeset 573 f3df9326fdc4
parent 569 2a1014d6697c
child 586 0679203515d2
permissions -rw-r--r--
monitoring process removed

"
 COPYRIGHT (c) 1997 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.
"



SelectionInTreeView subclass:#FileSelectionTree
	instanceVariableNames:'triggerMonitorBlock monitoringDelayTime fileIcons itemClass'
	classVariableNames:''
	poolDictionaries:''
	category:'Views-Text'
!

!FileSelectionTree class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1997 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.
"


!

documentation
"
    somewhat like a FileSelectionInList; but specialized for hierarchical (i.e. tree-like)
    lists and adds the functions to show/hide subtrees. 
    Requires SelectionInTree as model and FileSelectionItem (or compatible) list entries.

    You can define your own TreeItem instead of useing the default class FileSelectionItem
    by seting the class through to #itemClass:

    [see also:]
        FileSelectionItem
        SelectionInTree
        SelectionInTreeView
        SelectionInListView

    [author:]
        Claus Atzkern
"



!

examples
"
    open a FileSelectionTree on current directory
                                                                        [exBegin]
    |top scr|

    top := StandardSystemView new label:'select'; extent:300@500.
    scr := HVScrollableView for:FileSelectionTree origin:(0.0 @ 0.0) corner:(1.0 @ 1.0) in:top.
    scr := scr scrolledView.

    scr directory:Filename currentDirectory.

    scr action:[:anIndex| Transcript showCR:anIndex.
                          Transcript showCR:scr selectedPathname.
               ].
    top open
                                                                        [exEnd]


    open a FileSelectionTree useing a model
                                                                        [exBegin]
    |top scr model|

    top := StandardSystemView new label:'select'; extent:300@500.
    scr := HVScrollableView for:FileSelectionTree origin:(0.0 @ 0.0) corner:(1.0 @ 1.0) in:top.
    scr := scr scrolledView.
    model := (Filename currentDirectory asString) asValue.
    scr rootHolder:model.
    model inspect.

    scr action:[:anIndex| Transcript showCR:anIndex.
                          Transcript showCR:scr selectedPathname.
               ].
    top open
                                                                        [exEnd]


                                                                        [exBegin]
    |top scr|

    top := StandardSystemView new label:'select'; extent:300@500.
    scr := HVScrollableView for:FileSelectionTree origin:(0.0 @ 0.0) corner:(1.0 @ 1.0) in:top.
    scr := scr scrolledView.

    scr directory:Filename currentDirectory.
    scr selectionHolder:nil asValue.
    scr selectionHolder inspect.
    scr multipleSelectOk:true.

    scr action:[:anIndex| Transcript showCR:anIndex.
                          Transcript showCR:scr selectedPathname.
               ].
    top open
                                                                        [exEnd]



    open a FileSelectionTree on root path; show directory
    indication (open/closed), no lines and not the root
                                                                        [exBegin]
    |top scr|

    top := StandardSystemView new label:'select'; extent:300@500.
    scr := HVScrollableView for:FileSelectionTree origin:(0.0 @ 0.0) corner:(1.0 @ 1.0) in:top.
    scr := scr scrolledView.
    scr showDirectoryIndicator:true.
    scr showLines:false.
    scr showRoot:false.

    scr directory:'/'.

    scr action:[:anIndex| Transcript showCR:anIndex.
                          Transcript showCR:scr selectedPathname.
               ].
    top open
                                                                        [exEnd]



    open a FileSelectionTree on root path; showing only files
                                                                        [exBegin]
    |top scr|

    top := StandardSystemView new label:'select'; extent:300@500.
    scr := HVScrollableView for:FileSelectionTree origin:(0.0 @ 0.0) corner:(1.0 @ 1.0) in:top.
    scr := scr scrolledView.
    scr itemClass:(FileSelectionItem directoriesOnly).
    scr directory:'/'.

    scr action:[:anIndex| Transcript showCR:anIndex.
                          Transcript showCR:scr selectedPathname.
               ].
    top open
                                                                        [exEnd]



    open a FileSelectionTree on a specified path
                                                                        [exBegin]
    |top scr|

    top := StandardSystemView new label:'select'; extent:300@500.
    scr := HVScrollableView for:FileSelectionTree origin:(0.0 @ 0.0) corner:(1.0 @ 1.0) in:top.
    scr := scr scrolledView.
    scr directory:'/'.
    scr showLines:false.
    scr action:[:anIndex| Transcript showCR:scr selectedPathname ].
    scr doubleClickAction:[:anIndex| Transcript showCR:scr selectedPathname ].
    top open
                                                                        [exEnd]



    open a FileSelectionTree on a specified path; show or hide
    lines on doubleClick on a file (not a directory)
                                                                        [exBegin]
    |top scr|

    top := StandardSystemView new label:'select'; extent:300@500.
    scr := HVScrollableView for:FileSelectionTree origin:(0.0 @ 0.0) corner:(1.0 @ 1.0) in:top.
    scr := scr scrolledView.
    scr directory:'/'.

    scr action:[:anIndex| Transcript showCR:anIndex.
                          Transcript showCR:scr selectedPathname.
               ].
    scr doubleClickAction:[:anIndex|
        |fn|
        fn := scr selectedPathname asFilename.
        fn isDirectory ifFalse:[
            scr showLines:(scr showLines not)
        ]
    ].
    top open
                                                                        [exEnd]



    example associated with a FileSelectionList
                                                                        [exBegin]
    |top tree list field label|

    top   := StandardSystemView new label:'select'; extent:600@600.
    tree  := HVScrollableView for:FileSelectionTree origin:(0.0 @ 0.0) corner:(0.5 @ 1.0) in:top.
    list  := HVScrollableView for:FileSelectionList origin:(0.5 @  25) corner:(1.0 @ 1.0) in:top.
    label := Label origin:(0.5 @ 2) in:top.
    label label:'pattern:'.
    field := EditField origin:0.5@2 in:top.
    field leftInset:(label preferredExtent x) + 5.
    field width:1.0.
    field editValue:'*'.
    field crAction:[list pattern:field editValue].

    tree  := tree scrolledView.
    list  := list scrolledView.
    list ignoreDirectories:true.
    list pattern:(field editValue).

    tree itemClass:(FileSelectionItem directoriesOnly).
    tree directory:(Filename homeDirectory).
    tree showDirectoryIndicator:true.
    list directory:(tree directory).

    list action:[:index| Transcript showCR:'you selected: ' , list selectedPathname].
    tree action:[:anIndex|
        list directory:(tree selectedPathname).
    ].
    top open
                                                                        [exEnd]



    a more complex example
                                                                        [exBegin]
    |top listD listF field lbl inset|

    top   := StandardSystemView new label:'select'; extent:600@600.
    inset := 26.
    listD := HVScrollableView for:FileSelectionTree origin:(0.0 @ inset) corner:(0.5 @ 1.0) in:top.
    listF := HVScrollableView for:FileSelectionTree origin:(0.5 @ 0.0) corner:(1.0 @ 1.0) in:top.
    listD := listD scrolledView.
    listF := listF scrolledView.

    listD itemClass:(FileSelectionItem directoriesOnly).
    listF itemClass:(FileSelectionItem filesOnly).
    listD showDirectoryIndicator:true.
    listD showLines:false.
    listF showLines:false.
    listF showRoot:false.

    lbl := Label label:'directory:' in:top.
    lbl origin:5 @ ((inset - lbl preferredExtent y) // 2).

    field := FilenameEditField in:top.
    field origin:(4 + lbl corner x) @ ((inset - field preferredExtent y) // 2).
    field width:0.5.
    field rightInset:(field origin x + 4).
    field directoriesOnly.

    field crAction:[|dir|
        dir := field editValue asFilename.

        (dir isDirectory and:[listD directory ~= dir pathName]) ifTrue:[
            listD changeDirectory:dir
        ]
    ].

    listF action:[:anIndex||file|
        (file := listF selectedPathname) notNil ifTrue:[
            Transcript showCR:'selection: ', file
        ]
    ].

    listD directory:(Filename homeDirectory).
    field editValue:listD directory.

    listD doubleClickAction:[:anIndex||path|
        path := listD selectedPathname.
        listF directory:path.
        path notNil ifTrue:[field editValue:path]
    ].
    top open
                                                                        [exEnd]
"

!

test
    |top scr time total max|

    top := StandardSystemView new label:'select'; extent:300@500.
    scr := HVScrollableView for:FileSelectionTree origin:(0.0 @ 0.0) corner:(1.0 @ 1.0) in:top.
    scr := scr scrolledView.

    scr selectionHolder:nil asValue.
    scr multipleSelectOk:true.
    top openAndWait.
    total := 0.

    total ~~ 0 ifTrue:[
        MessageTally spyOn:[
            scr directory:'/home2/cg/st80src2.5.1'
        ].
    ] ifFalse:[
        max := 20.
        max timesRepeat:[|time|
            "/ DirectoryContents releaseResources.
            time  := Time millisecondsToRun:[scr directory:'/home2/cg/st80src2.5.1'].
            total := total + time.
        ].
        Transcript showCR:'----'.
        Transcript showCR:(total // max).
    ].

! !

!FileSelectionTree class methodsFor:'constants'!

monitoringDelayTime
    "default delay time of monitoring task in seconds
    "
    ^ 2
! !

!FileSelectionTree methodsFor:'accessing'!

changeDirectory:aPathname
    "change the root directory; try to reuse old hierarchy list and
     the selection in case of a single selection. The pathname must
     be a directory otherwise the root directory is set to nil
    "
    |oldSel child loc oldPath oldFile newFile newPath node idx|

    (     aPathname notNil
     and:[(newFile := aPathname asFilename) isDirectory
     and:[(oldPath := self directory) notNil]]
    ) ifFalse:[
        ^ self directory:aPathname
    ].
    newPath := newFile pathName.
    oldFile := oldPath asFilename.
    oldSel  := self selectedNode.

    (newPath startsWith:oldPath) ifTrue:[
        node := self detectNode:[:aNode|aNode pathName = newPath].

        node isNil ifTrue:[
            ^ self directory:newFile
        ].
    ] ifFalse:[
        (oldPath startsWith:newPath) ifFalse:[
            ^ self directory:newFile
        ].
        child := model root.

        [newPath = oldPath] whileFalse:[
            oldFile := oldFile directory.
            node    := self itemClass pathName:oldFile.
            node expand.
            loc := node children.
            idx := loc  findFirst:[:el| el pathName = oldPath ].

            idx == 0 ifTrue:[
                ^ self directory:newFile
            ].

            loc at:idx put:child.
            child parent:node.
            child   := node.
            oldPath := oldFile pathName.
        ]
    ].
    selection := nil.
    node parent:nil.
    model root:node.
    self  setSelection:(self indexOfNode:oldSel).
    model setSelection:selection.
!

directory
    "get the full pathname of the root directory
    "
    |root|

    (root := model root) notNil ifTrue:[
        ^ root pathName
    ].
  ^ nil
!

directory:aPath
    "change the root directory of the selection tree to the full pathName,
     aPath. The pathname must be a directory otherwise the root directory
     is set to nil.
    "
    |root path|

    model setSelection:(selection := nil).

    (aPath notNil and:[(path := aPath asFilename) isDirectory]) ifTrue:[
        root := self itemClass pathName:path.
        model root:root.
        model expand:root.
    ] ifFalse:[    
        model root:nil.
    ]

!

itemClass
    "returns current itemClass used
    "
    ^ itemClass
!

itemClass:anItemClass
    "set itemClass to be used
    "
    |directory|

    (anItemClass notNil and:[anItemClass ~~ itemClass]) ifTrue:[
        itemClass := anItemClass.
        computeResources := true.
        self refetchDeviceResources.

        (directory := self directory) notNil ifTrue:[
            self directory:directory                 "/ recompute list
        ].
    ].

!

pathnameAtIndex:anIndex
    "returns pathname at an index or nil
    "
    |node|

    (node := self nodeAtIndex:anIndex) notNil ifTrue:[
        ^ node pathName
    ].
  ^ nil
! !

!FileSelectionTree methodsFor:'accessing monitoring'!

monitoring
    "returns true if monitor process is running
    "
    ^ triggerMonitorBlock notNil 
!

monitoring:aState
    "enable or disable monitoring
    "
    aState ifTrue:[
        triggerMonitorBlock notNil ifTrue:[^ self].
        triggerMonitorBlock := [self sensor pushUserEvent:#monitorCycle for:self].
        Processor addTimedBlock:triggerMonitorBlock afterSeconds:(self monitoringDelayTime).
    ] ifFalse:[
        triggerMonitorBlock isNil ifTrue:[^ self].
        Processor removeTimedBlock:triggerMonitorBlock.
        triggerMonitorBlock := nil.
    ].
!

monitoringDelayTime
    "delay time of monitoring task in seconds
    "
    ^ monitoringDelayTime
!

monitoringDelayTime:seconds
    "delay time of monitoring task in seconds
    "
    seconds > 0 ifTrue:[
        monitoringDelayTime := seconds
    ]
! !

!FileSelectionTree methodsFor:'drawing basics'!

figureFor:aNode
    "get the image used for the node entry.
    "
    ^ fileIcons at:(aNode drawableImageType)
! !

!FileSelectionTree methodsFor:'initialization'!

destroy

    triggerMonitorBlock notNil ifTrue:[
        Processor removeTimedBlock:triggerMonitorBlock.
        triggerMonitorBlock := nil
    ].
    super destroy.

!

fetchImageResources
    "initialize heavily used device resources - to avoid rendering
     images again and again later; returns maximum extent of the images used.
    "
    |y x t|

    fileIcons := self itemClass iconsOn:device.

    t := super fetchImageResources.
    y := t y.
    x := t x.

    fileIcons do:[:anIcon|
        (t := anIcon heightOn:self) > y ifTrue:[y := t].
        (t := anIcon widthOn:self)  > x ifTrue:[x := t].
    ].
  ^ x @ y

!

initialize
    "setup my model and set the default path to the current directory; on default
     multiple selection is disabled.
    "
    super initialize.
    itemClass := FileSelectionItem.
    monitoringDelayTime := self class monitoringDelayTime.
! !

!FileSelectionTree methodsFor:'model'!

rootFromModel
    "update hierarchical list from root model
    "
    |oldPath newPath|

    (newPath := rootHolder value) notNil ifTrue:[
        newPath := newPath asString.
    ].

    self directory = newPath ifFalse:[
        self changeDirectory:newPath
    ]
!

selectionFromModel
    "set the selection derived from the selectionHolder
    "
    |selection value shown|

    selectionHolder isNil ifTrue:[
        ^ self
    ].

    value := selectionHolder value.

    multipleSelectOk ifFalse:[
        value isNil ifTrue:[
            self deselect
        ] ifFalse:[
            value asFilename exists ifFalse:[
                selectionHolder value:nil
            ] ifTrue:[
                self selectPathname:value
            ]
        ].
        ^ self
    ].

    value size == 0 ifTrue:[
        ^ self deselect
    ].

    selection := value select:[:aPath| aPath asFilename exists ].

    selection size ~~ value size ifTrue:[
        selection size ~~ 0 ifTrue:[selectionHolder value:selection]
                     ifFalse:[selectionHolder value:nil].
        ^ self
    ].

    selection size == 1 ifTrue:[
        ^ self selectPathname:(selection first)
    ].
    shown := true.

    selection do:[:el|(self showFile:el) ifFalse:[shown := false]].

    shown ifFalse:[
        model recomputeList.
    ].

    selection := selection collect:[:el|
        listOfNodes findFirst:[:n| n pathName = el]
    ].
    super selection:selection.

!

selectionToModel
    "write selection to selection holder
    "
    |old new|

    old := selectionHolder value.

    multipleSelectOk ifFalse:[
        (new := self pathnameAtIndex:selection) = old ifFalse:[
            selectionHolder value:new
        ]
    ] ifTrue:[
        self numberOfSelections == 0 ifTrue:[
            old size ~~ 0 ifTrue:[
                selectionHolder value:nil
            ]
        ] ifFalse:[
            new := selection collect:[:i|(listOfNodes at:i) pathName].

            new size ~~ old size ifTrue:[
                selectionHolder value:new
            ] ifFalse:[
                new do:[:pN|
                    (old findFirst:[:pO| pO = pN]) == 0 ifTrue:[
                        ^ selectionHolder value:new
                    ]
                ]
            ]
        ]
    ]

! !

!FileSelectionTree methodsFor:'private'!

monitorCycle
    "run monitor cycle
    "
    |sz root sel new old|

    (root := model root) isNil ifFalse:[
        root hasObsoleteNodes ifTrue:[
            (root repairObsoleteNodes) ifTrue:[
                sz := self numberOfSelections.

                sz ~~ 0 ifTrue:[
                    old := self selection.

                    sz == 1 ifTrue:[
                        sel := self selectedNode
                    ] ifFalse:[
                        sel := OrderedCollection new.
                        self selectionDo:[:i| sel add:(listOfNodes at:i) ].
                    ].
                    selection := nil.
                ].
                selection := old.
                model root:root.

                sz ~~ 0 ifTrue:[
                    sz == 1 ifTrue:[   Transcript showCR:'lll'.
                        self selectNode:sel.
                    ] ifFalse:[
                        new := OrderedCollection new.

                        sel do:[:n||i|
                            (i := self indexOfNode:n) ~~ 0 ifTrue:[new add:i]
                        ].
                        self selection:new
                    ]
                ].
            ]
        ]
    ].

    Processor addTimedBlock:triggerMonitorBlock afterSeconds:(self monitoringDelayTime).

!

showFile:aPathname
    "show a file
    "
    |components path size root node shown|

    path  := aPathname asString.
    root  := self directory.
    shown := true.

    (path startsWith:root) ifFalse:[
        self error.
        ^ shown
    ].
    size := root size.
    path size <= (size + 2) ifTrue:[^ shown].
    size == 1 ifFalse:[path := path copyFrom:(size + 2)]
               ifTrue:[path := path copyFrom:2].

    components := Filename components:path.
    node := model root.

    components do:[:el||next|
        next := node detectChild:[:e|e name = el].
        next isNil ifTrue:[
            self error.
            ^ shown
        ].
        node hidden ifTrue:[
            node expand.
            shown := false.
        ].
        node := next.
    ].
    ^ shown
! !

!FileSelectionTree methodsFor:'selection'!

selectPathname:aPath
    "set selection to a path
    "
    |components path|

    (aPath notNil and:[aPath asFilename exists]) ifTrue:[
        ((path := aPath asString) = self selectedPathname) ifTrue:[
            ^ self
        ].
        components := Filename components:(path copyFrom:(self directory size + 1)).
    ].
    self selectFromListOfNames:components.
!

selectedPathname
    "if there is a single selection, the full pathname of the selected
     entry will be returned otherwise nil
    "
    |node|

    (node := self selectedNode) notNil ifTrue:[
        ^ node pathName
    ].
  ^ nil

! !

!FileSelectionTree class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/FileSelectionTree.st,v 1.8 1997-10-22 15:47:35 ca Exp $'
! !