FileSelectionTree.st
author ca
Mon, 11 Aug 1997 13:02:30 +0200
changeset 492 0b6a6bc3f1cb
parent 488 bb017dc6df4f
child 495 e34c13af578d
permissions -rw-r--r--
set pathname ...

"
 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:'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 on root path; show directory
    indication (open/closed) and no lines
                                                                        [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 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]
    |action top tree slvw file tgD tgF button hzPn|

    top  := StandardSystemView new label:'select'; extent:600@600.
    tree := HVScrollableView for:FileSelectionTree origin:(0.0 @ 0.0) corner:(0.5 @ 1.0) in:top.
    slvw := HVScrollableView for:FileSelectionTree origin:(0.5 @  30) corner:(1.0 @ 1.0) in:top.
    hzPn := HorizontalPanelView origin:(0.5 @  0.0) corner:(1.0 @ 30) in:top.
    tree := tree scrolledView.
    slvw := slvw scrolledView.

    tree itemClass:(FileSelectionItem directoriesOnly).
    tree directory:(Filename homeDirectory).

    slvw doubleClickSelectionBlock:[:anIndex|
        (file := slvw selectedPathname asFilename) isDirectory ifTrue:[
            anIndex == 1 ifTrue:[file := file directory].
            tree selectPathname:file
        ].
        false
    ].
    slvw showLines:false.

    tree action:[:anIndex|
        slvw directory:(tree selectedPathname)
    ].
    action := [:tg||cls|
        tgF isOn ifTrue:[
            tgD isOn ifTrue:[cls := FileSelectionItem]
                    ifFalse:[cls := FileSelectionItem filesOnly]
        ] ifFalse:[
            tgD isOn ifTrue:[
                cls := FileSelectionItem directoriesOnly
            ] ifFalse:[
                tg turnOn.
                tg == tgD ifTrue:[cls := FileSelectionItem directoriesOnly]
                         ifFalse:[cls := FileSelectionItem filesOnly]
            ]
        ].
        slvw itemClass:cls.
    ].
    hzPn verticalLayout:#fitSpace.            
    hzPn horizontalLayout:#fitSpace.            
    tgD    := CheckBox label:'directory'    in:hzPn.
    tgF    := CheckBox label:'file'         in:hzPn.
    button := Button   label:'File Browser' in:hzPn.

    button action:[
        (file := slvw selectedPathname) isNil ifTrue:[
            file := tree selectedPathname
        ].
        file notNil ifTrue:[
            file asFilename isDirectory ifTrue:[FileBrowser openOn:file]
                                       ifFalse:[FileBrowser openOnFileNamed:file]
        ]
    ].

    tgD turnOn.
    tgF turnOn.
    tgD action:[:v| action value:tgF].
    tgF action:[:v| action value:tgD].

    top open
                                                                        [exEnd]
"

! !

!FileSelectionTree methodsFor:'accessing'!

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

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

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

    (aPathname notNil and:[(path := aPathname asFilename) isDirectory]) ifFalse:[
        model root:nil.
      ^ self selection:nil
    ].

    (dir := self directory) notNil ifTrue:[
        dir  := dir asFilename.
        keep := path pathName = dir directory pathName.
    ] ifFalse:[
        keep := false
    ].
    self selection:nil.

    root := self itemClass pathName:path.
    model root:root keepRoot:keep.
    model expand:root.

    keep ifTrue:[
        self selectPathname:(dir pathName)
    ].

!

itemClass
    "returns current itemClass used
    "
    ^ itemClass
!

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

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

        (directory := self directory) notNil ifTrue:[
            self directory:directory
        ].
    ].

!

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

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

!FileSelectionTree methodsFor:'drawing basics'!

figureFor:aNode
    "get the image used for the node entry.
    "
    |keyOrImage|

    aNode == self selectedNode ifFalse:[keyOrImage := aNode imageUnselected]
                                ifTrue:[keyOrImage := aNode imageSelected].

    keyOrImage isSymbol ifTrue:[^ fileIcons at:keyOrImage].
  ^ keyOrImage
! !

!FileSelectionTree methodsFor:'initialization'!

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.
    self model:(SelectionInTree new).

! !

!FileSelectionTree methodsFor:'selection'!

selectPathname:aPath
    "set selection to a path
    "
    |node comp rdwNd path|

    (aPath notNil and:[aPath asFilename exists]) ifFalse:[
        ^ self selection:nil
    ].
    ((path := aPath asString) = self selectedPathname) ifTrue:[
        "/ already selected
        ^ self
    ].

    comp := Filename components:(path copyFrom:(self directory size + 1)).
    node := model root.

    comp do:[:el||next|
        next := node detectChild:[:e|e name = el].

        next notNil ifTrue:[
            node hidden ifTrue:[
                rdwNd isNil ifTrue:[
                    rdwNd := node.
                    self selectNode:node.
                ].
                node expand
            ].
            node := next
        ]
    ].

    rdwNd notNil ifTrue:[
        model updateList.
        list := self listFromModel.
        self redrawFromLine:(self indexOfNode:rdwNd).
        self contentsChanged.
    ].
    self selectNode:node.
!

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.3 1997-08-11 11:02:30 ca Exp $'
! !