FileSelectionList.st
author claus
Sat, 08 Jan 1994 18:27:56 +0100
changeset 21 9ef599238fea
parent 11 c47dbae39a71
child 24 966098a893f8
permissions -rw-r--r--
*** empty log message ***

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

SelectionInListView subclass:#FileSelectionList
       instanceVariableNames:'pattern directory timeStamp directoryId
                              directoryContents directoryFileTypes
                              realAction fileTypes'
       classVariableNames:''
       poolDictionaries:''
       category:'Views-Text'
!

FileSelectionList comment:'

COPYRIGHT (c) 1993 by Claus Gittinger
              All Rights Reserved

$Header: /cvs/stx/stx/libwidg/FileSelectionList.st,v 1.2 1994-01-08 17:27:17 claus Exp $
written Dec 93 by claus
'!

!FileSelectionList class methodsFor:'documentation'!

documentation
"
this class implements file selection lists - its basically a
selection in list, but remembers the previous position when
changing directories.
Only files matching a pattern (plus directories) are shown.

Instance variables:
        directoryContents       contents of current directory
        directoryFileTypes      file types (symbols) of current directory
        fileTypes               file types as shown in list 
                                (i.e only matching ones)
"
! !

!FileSelectionList methodsFor:'initialization'!

initialize
    directory := FileDirectory currentDirectory.
    super initialize.

    pattern := '*'.

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

    actionBlock := [:lineNr |
        |entry|

        (self selection isKindOf:Collection) ifFalse:[
            entry := self 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:[
                realAction notNil ifTrue:[
                    realAction value:lineNr
                ]
            ]
        ]
    ]

    "FileSelectionList new realize"
!

reinitialize
    directory := FileDirectory currentDirectory.
    super reinitialize
! !

!FileSelectionList methodsFor:'accessing'!

action:aBlock
    "set the action to be performed on a selection"

    realAction := aBlock
!

directory
    "return the shown directory"

    ^ directory
!

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

    |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 - if it changes, update the list."

    pattern ~= aPattern ifTrue:[
        pattern := aPattern.
        realized ifTrue:[
            self updateList
        ].
    ].
! !

!FileSelectionList methodsFor:'drawing'!

redrawFromVisibleLine:startVisLineNr to:endVisLineNr
    "redefined to look for directory in every line"

    startVisLineNr to:endVisLineNr do:[:l |
        self redrawVisibleLine:l
    ]
!

redrawVisibleLine:visLineNr
    "if the line is one for a directory, draw a right arrow"

    |l|

    super redrawVisibleLine:visLineNr.
    l := self visibleLineToListLine:visLineNr.
    l notNil ifTrue:[
        (fileTypes at:l) == #directory ifTrue:[
            self drawRightArrowInVisibleLine:visLineNr
        ]
    ]
! !

!FileSelectionList methodsFor:'private'!

visibleLineNeedsSpecialCare:visLineNr
    |l|

    l := self visibleLineToListLine:visLineNr.
    l notNil ifTrue:[
        (fileTypes at:l) == #directory ifTrue:[^ true].
        ^ super visibleLineNeedsSpecialCare:visLineNr
    ].
    ^ false
!

widthForScrollBetween:firstLine and:lastLine
    "return the width in pixels for a scroll between firstLine and lastLine
     - return full width here since there might be directory marks"

    ^ (width - margin - margin)
!

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

    |oldCursor files newList index|

    oldCursor := cursor.
    self 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.
    newList := OrderedCollection new.
    fileTypes := OrderedCollection new.
    index := 1.
    files do:[:name |
        (directoryFileTypes at:index) == #directory ifTrue:[
            name = '..' ifTrue:[
                newList add:name.
                fileTypes add:(directoryFileTypes at:index)
            ] ifFalse:[
                name = '.' ifTrue:[
                    "ignore"
                ] ifFalse:[
                    newList add:(name ", ' ...'").
                    fileTypes add:(directoryFileTypes at:index)
                ]
            ]
        ] ifFalse:[
            (pattern isEmpty or:[pattern = '*' or:[pattern match:name]]) ifTrue:[
                newList add:name.
                fileTypes add:(directoryFileTypes at:index)
            ]
        ].
        index := index + 1
    ].
    super list:newList.
    self cursor:oldCursor.
! !

!FileSelectionList methodsFor:'realization'!

realize
    "make the view 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 realize
! !