FileSelectionBox.st
author claus
Sat, 11 Dec 1993 02:51:34 +0100
changeset 7 15a9291b9bd0
parent 5 7b4fb1b170e5
child 12 1c8e8c53e8cf
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1990 by Claus Gittinger
              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.
"

ListSelectionBox subclass:#FileSelectionBox
       instanceVariableNames:'patternField directory timeStamp directoryId
                              directoryContents directoryFileTypes'
       classVariableNames:''
       poolDictionaries:''
       category:'Views-Interactors'
!

FileSelectionBox comment:'

COPYRIGHT (c) 1990 by Claus Gittinger
              All Rights Reserved

$Header: /cvs/stx/stx/libwidg/FileSelectionBox.st,v 1.4 1993-12-11 01:44:10 claus Exp $
written Jan 90 by claus
'!

!FileSelectionBox class methodsFor:'documentation'!

documentation
"
this class implements file selection boxes. They show a list of
files, and perform an action block with the selected pathname as
argument when ok is clicked.
There is an optional PatternField, which shows itself when a pattern
is defined. If there is such a pattern, only files matching the pattern
will be shown in the list (and directories).
"
! !

!FileSelectionBox methodsFor:'initialization'!

initialize
    directory := FileDirectory currentDirectory.
    super initialize.

    labelField extent:(0.7 @ labelField height).
    labelField label:(resources string:'select a file:').
    labelField adjust:#left.

    patternField := EditField
                        origin:(0.7 @ labelField origin y)
                        corner:(1.0 @ labelField corner y)
                            in:self.
    patternField initialText:'*'.
    patternField leaveAction:[:p | self updateList].
    patternField hidden:true.

    "selections in list get forwarded to enterfield if not a directory;
     otherwise directory is changed"

    selectionList action:[:lineNr |
        |entry|

        entry := selectionList selectionValue.
        (entry endsWith:' ...') ifTrue:[
            entry := entry copyTo:(entry size - 4).
        ].
        ((directory typeOf:entry) == #directory) ifTrue:[
            (directory isReadable:entry) ifFalse:[
                self warn:(resources string:'not allowed to read directory %1' with:entry)
            ] ifTrue:[
                (directory isExecutable:entry) ifFalse:[
                    self warn:(resources string:'not allowed to change to directory %1' with:entry)
                ] ifTrue:[
                    self directory:(directory pathName , Filename separator asString , entry)
                ]
            ].
        ] ifFalse:[
            enterField contents:entry
        ]
    ]

    "FileSelectionBox new show"
!

reinitialize
    directory := FileDirectory currentDirectory.
    super reinitialize
! !

!FileSelectionBox methodsFor:'accessing'!

directory:nameOrDirectory
    "set the lists contents to the filenames in the directory name"

    |oldPath name|

    (nameOrDirectory isKindOf:String) ifTrue:[
        name := nameOrDirectory
    ] ifFalse:[
        name := nameOrDirectory pathName
    ].
    oldPath := directory pathName.
    directory pathName:name.
    (directory pathName = oldPath) ifFalse:[
        self updateList
    ]
!

pattern:aPattern
    "set the pattern - this enables the PatternField."

    patternField initialText:aPattern.
    patternField hidden:false.
    realized ifTrue:[
        patternField realize.
        self updateList
    ].
! !

!FileSelectionBox methodsFor:'private'!

updateList
    "set the lists contents to the filenames in the directory"

    |oldCursor oldListCursor files pattern newList index|

    oldCursor := cursor.
    oldListCursor := selectionList cursor.
    self cursor:(Cursor read).
    selectionList cursor:(Cursor read).
    directoryId == directory id ifFalse:[
        timeStamp := directory timeOfLastChange.
        directoryId := directory id.
        directoryContents := directory asText sort.
        directoryFileTypes := OrderedCollection new.
        directoryContents do:[:name | directoryFileTypes add:(directory typeOf:name)].
    ].
    files := directoryContents.
    pattern := patternField contents.
    newList := OrderedCollection new.
    index := 1.
    files do:[:name |
        (directoryFileTypes at:index) == #directory ifTrue:[
            name = '..' ifTrue:[
                newList add:name
            ] ifFalse:[
                name = '.' ifTrue:[
                ] ifFalse:[
                    newList add:(name , ' ...')
                ]
            ]
        ] ifFalse:[
            (pattern isEmpty or:[pattern match:name]) ifTrue:[
                newList add:name
            ]
        ].
        index := index + 1
    ].
    self list:newList.
    self cursor:oldCursor.
    selectionList cursor:oldListCursor
! !

!FileSelectionBox methodsFor:'events'!

show
    "make the box visible; redefined to check if directory is still 
     valid (using timestamp and inode numbers) - reread if not"

    (timeStamp isNil 
     or:[(directory timeOfLastChange > timeStamp) 
     or:[(directoryId isNil)
     or:[directoryId ~~ directory id]]]) ifTrue:[
        directoryId := nil.
        self updateList
    ].
    super show
! !

!FileSelectionBox methodsFor:'user interaction'!

okPressed
    "redefined, since action will be evaluated with full path as argument
     (instead of enterfields contents only as inherited by EnterBox"

    |absPath|

    self hideAndEvaluate:[:string |
        okAction notNil ifTrue:[
            (string startsWith:(Filename separator)) ifTrue:[
                absPath := string
            ] ifFalse:[
                absPath := directory pathName , Filename separator asString , string
            ].
            okAction value:absPath
        ]
    ]
! !