FBrowser.st
author Claus Gittinger <cg@exept.de>
Wed, 23 Apr 1997 13:30:25 +0200
changeset 1162 08940832d3a8
parent 1160 76bc73e0ab24
child 1166 0029f77ccea7
permissions -rw-r--r--
category changes

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

StandardSystemView subclass:#FileBrowser
	instanceVariableNames:'labelView filterField fileListView subView currentDirectory
		fileList checkBlock checkDelta timeOfLastCheck showLongList
		showDotFiles myName killButton compressTabs lockUpdate
		previousDirectory currentFileName timeOfFileRead tabSpec
		commandView commandIndex fileEncoding tabRulerView scrollView
		icons listUpdateProcess'
	classVariableNames:'DirectoryHistory DirectoryHistoryWhere HistorySize DefaultIcon
		CommandHistory CommandHistorySize Icons DefaultCommandPerSuffix'
	poolDictionaries:''
	category:'Interface-Browsers'
!

!FileBrowser class methodsFor:'documentation'!

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

documentation
"
    this used to be a very simple demo application,
    but migrated into a quite nice tool, includes all kinds of 
    warning and information boxes, background processes for directory-
    reading and internationalized strings. A good example for beginners,
    on how to do things .... (and maybe how not to do things ;-, since some
    stuff is historic and was implemented at times when better mechanisms
    were not available)

    See additional information in 'doc/misc/fbrowser.doc'.

    WARNING: files edited with FileBrowser will have leading spaces (multiple-8)
             being replaced by tabs. If tabs are to be preserved at other
             positions (for example, sendmail-config files) they will be
             corrupt after being written.

    [instance variables]:

        checkDelta      <Integer>       number of seconds of check interval
                                        (looks ever so often if shown directory
                                         has changed). You may make this number
                                        higher, if your network-times are
                                        incorrect and thus, the filebrowser
                                        checks too often.

        compressTabs    <Boolean>       if true, leading spaces will be
                                        replaced by tabs when saving text

    some of the defaults (long/short list etc.) can be set by the resource file;
    see FileBrowser>>initialize for more details..

    [author:]
        Claus Gittinger
"
! !

!FileBrowser class methodsFor:'instance creation'!

openOn:aDirectoryPath
    "start a new FileBrowser in a pathname"

    ^ (self new currentDirectory:aDirectoryPath) open

    "
     FileBrowser openOn:'aDirectoryPath'
     FileBrowser openOn:'/etc'
     FileBrowser openOn:'..'
     FileBrowser openOn:'.'
    "
!

openOnFileNamed:aFilename
    "start a new FileBrowser on a file"

    |f browser|

    f := aFilename asFilename.
    f isDirectory ifTrue:[
        ^ self openOn:aFilename
    ].
    browser := self new.
    browser currentDirectory:f directoryName.
    browser showFile:f baseName.
    ^ browser open

    "
     FileBrowser openOnFileNamed:'Makefile'
     FileBrowser openOnFileNamed:'../Makefile'
     FileBrowser openOnFileNamed:'/tmp/foo'
    "

    "Modified: 6.4.1997 / 14:57:12 / cg"
! !

!FileBrowser class methodsFor:'class initialization'!

initialize
    Icons := IdentityDictionary new.

    #(
        #directory       'tiny_yellow_dir.xpm'
        #directoryLocked 'tiny_yellow_dir_locked.xpm'
        #directoryLink   'tiny_yellow_dir_link.xpm'
        #file            'tiny_file_plain.xpm'
        #fileLink        'tiny_file_link.xpm'
        #fileLocked      'tiny_file_lock.xpm'
        #imageFile       'tiny_file_pix.xpm'

     ) pairWiseDo:[:key :nm |
        
        Icons at:key put:(Image fromFile:'bitmaps/xpmBitmaps/document_images/' , nm).
    ]

    "
     self initialize
    "

    "Modified: 18.4.1997 / 15:09:53 / cg"
! !

!FileBrowser class methodsFor:'command history'!

addToCommandHistory:aCommandString for:aFilename
    |cmd suffix|

    (aCommandString notNil and:[aCommandString notEmpty]) ifTrue:[
        CommandHistory notNil ifTrue:[
            CommandHistory addFirst:aCommandString.
            CommandHistory size > CommandHistorySize ifTrue:[
                CommandHistory removeLast
            ]
        ].
        aFilename notNil ifTrue:[
            cmd := aCommandString copyTo:(aCommandString indexOf:Character space ifAbsent:[aCommandString size + 1])-1.
            DefaultCommandPerSuffix isNil ifTrue:[
                DefaultCommandPerSuffix := Dictionary new.
            ].
            suffix := aFilename asFilename suffix.
            suffix notNil ifTrue:[
                DefaultCommandPerSuffix at:suffix put:cmd.
            ]
        ]
    ]

    "Created: 14.11.1996 / 14:58:13 / cg"
! !

!FileBrowser class methodsFor:'defaults'!

defaultIcon
    "return the file browsers default window icon"

    <resource: #style (#ICON #ICON_FILE)>

    |nm i|

    (i := DefaultIcon) isNil ifTrue:[
        i := self classResources at:'ICON' default:nil.
        i isNil ifTrue:[
            nm := ClassResources at:'ICON_FILE' default:'FBrowser.xbm'.
            i := Image fromFile:nm resolution:100.
            i isNil ifTrue:[
                i := Image fromFile:('bitmaps/' , nm) resolution:100.
                i isNil ifTrue:[
                    i := StandardSystemView defaultIcon
                ]
            ]
        ].
        i notNil ifTrue:[
            DefaultIcon := i := i on:Display
        ]
    ].
    ^ i

    "Modified: 19.3.1997 / 20:48:34 / ca"
    "Modified: 18.4.1997 / 15:16:29 / cg"
! !

!FileBrowser methodsFor:'drag & drop'!

canDrop:aCollectionOfDropObjects
    "I accept fileObjects only"

    aCollectionOfDropObjects do:[:aDropObject |
        aDropObject isFileObject ifFalse:[
            aDropObject isTextObject ifFalse:[^ false].
        ]
    ].
    ^ true

    "Modified: 11.4.1997 / 12:41:59 / cg"
!

drop:aCollectionOfDropObjects at:aPoint
    "handle drops"

    aCollectionOfDropObjects do:[:aDropObject |
        self dropSingleObject:aDropObject at:aPoint
    ]

    "Modified: 11.4.1997 / 12:43:36 / cg"
!

dropSingleObject:someObject at:aPoint
    "handle drops; if its a directory, change to it.
     If its a file, change to its directory and select the file.
     If its text, paste it into the codeView."

    |newDir newFile|

    someObject isFileObject ifTrue:[
        someObject isDirectory ifTrue:[
            newDir := someObject theObject pathName.
        ] ifFalse:[
            newDir := someObject theObject directoryName.
            newFile := someObject theObject baseName.
        ].

        newDir notNil ifTrue:[
            newDir ~= currentDirectory pathName ifTrue:[
                self changeDirectoryTo:newDir.
            ]
        ].
        newFile notNil ifTrue:[
            newFile ~= currentFileName ifTrue:[
                fileListView selection:(fileList indexOf:newFile).
                self doFileGet:false.
            ]
        ].
        ^ self
    ].

    someObject isTextObject ifTrue:[
        subView paste:someObject theObject.
        ^ self
    ].

    "Modified: 6.4.1997 / 14:46:44 / cg"
! !

!FileBrowser methodsFor:'events'!

handlesKeyPress:key inView:view
    "this method is reached via delegation: are we prepared to handle
     a keyPress in some other view ?"

    <resource: #keyboard (#GotoLine #InspectIt #CmdI #Cmdu #DoIt #Delete #BackSpace #Accept)>

    view == fileListView ifTrue:[
        (key == #Delete 
        or:[key == #BackSpace
        or:[key == #Accept
        or:[key == #CmdI
        or:[key == #Cmdu
        or:[key == #InspectIt
        or:[key == #GotoLine
        or:[key == #DoIt]]]]]]]) ifTrue:[^ true].
    ].
    ^ false

    "Created: 28.1.1997 / 14:03:20 / stefan"
    "Modified: 28.1.1997 / 15:03:30 / stefan"
!

keyPress:key x:x y:y view:view
    "this method is reached via delegation from the fileListView"

    <resource: #keyboard (#GotoLine #InspectIt #CmdI #Cmdu #DoIt #Delete #BackSpace #Accept)>

    (key == #Delete or:[key == #BackSpace]) ifTrue:[
        self fileRemove.
        ^ self
    ].
    (key == #Accept) ifTrue:[
        self fileFileIn.
        ^ self
    ].
    (key == #GotoLine) ifTrue:[
        self fileGet.
        ^ self
    ].
    (key == #DoIt) ifTrue:[
        self fileExecute.
        ^ self
    ].
    (key == #InspectIt) ifTrue:[
        self fileGetInfo.
        ^ self
    ].
    (key == #CmdI) ifTrue:[
        self fileGetLongInfo.
        ^ self
    ].
    (key == #Cmdu) ifTrue:[
        self updateCurrentDirectory.
        ^ self
    ].
    fileListView keyPress:key x:x y:y

    "Created: 28.1.1997 / 14:03:56 / stefan"
    "Modified: 28.1.1997 / 15:03:56 / stefan"
!

mapped 
    super mapped.
    "
     whant to know about changed history
    "
    self updateCurrentDirectory
!

visibilityChange:how
    |wasVisible|

    wasVisible := shown.
    super visibilityChange:how.
    (wasVisible not and:[shown]) ifTrue:[
        "
         start checking again
        "
        Processor removeTimedBlock:checkBlock.
        Processor addTimedBlock:checkBlock afterSeconds:checkDelta.
    ]
! !

!FileBrowser methodsFor:'fileList user interaction'!

changeDisplayMode
    "toggle from long to short listing (and vice-versa)"

    showLongList := showLongList not.
    self showOrHideTabView.
    self updateCurrentDirectory

    "Modified: 19.4.1997 / 09:50:14 / cg"
!

changeDotFileVisibility
    "turn on/off visibility of files whose name starts with '.'"

    showDotFiles := showDotFiles not.
    self updateCurrentDirectory
!

fileEncoding
    "open a dialog to allow change of the files character encoding.
     Files are converted to internal encoding when read, and converted back
     to this encoding when saved.
     The default encoding is nil, which means that files are already in
     the internal encoding (which is iso8859).
     Notice: currently, not too many encodings are supported by the system."

    |dialog list descr encodings encodingNames idx|

    list := SelectionInList new.

    descr := CharacterArray supportedExternalEncodings.
    encodings := descr at:2.
    encodingNames := descr at:1.

    list list:encodingNames.
    list selectionIndex:(encodings indexOf:fileEncoding ifAbsent:1).

    dialog := Dialog new.

    dialog addTextLabel:(resources string:'ENCODING_MSG') withCRs.
    dialog addVerticalSpace.
    dialog addListBoxOn:list withNumberOfLines:5.

    dialog addAbortButton; addOkButton.
    dialog open.

    dialog accepted ifTrue:[
        idx := list selectionIndex.
        fileEncoding := encodings at:idx.

        self validateFontEncodingFor:fileEncoding ask:true.
    ].

    "Modified: 31.10.1996 / 16:47:47 / cg"
!

fileExecute
    "if text was modified show a queryBox,
     otherwise pop up execute box immediately"

    |action sel fileName|

    "
     this replaces everything by the commands output ...
    "
    action := [:command | 
                self class addToCommandHistory:command for:fileName.
                self doExecuteCommand:command replace:true
              ].

    (self askIfModified:'contents has not been saved.\\Modifications will be lost when command is executed.'
              yesButton:'execute') ifFalse:[^ self].

"/    "
"/     this inserts the commands output ...
"/    "
"/    action := [:command| self doExecuteCommand:command replace:false].
"/

    sel := fileListView selection.
    sel size == 1 ifTrue:[
        fileName := fileList at:sel first
    ].
    self askForCommandFor:fileName thenDo:action

    "Modified: 14.11.1996 / 14:59:34 / cg"
!

fileFileIn
    "fileIn the selected file(s)"

    self fileFileInLazy:false 
!

fileFileInLazy
    "fileIn the selected file(s). Do a quick load (no compilation)"

    self fileFileInLazy:true 
!

fileFileInLazy:lazy
    "fileIn the selected file(s)"

    |aStream here oldPath wasLazy bos|

    self selectedFilesDo:[:fileName |
        ((currentDirectory typeOf:fileName) == #regular) ifTrue:[
            here := currentDirectory pathName.

            ((fileName endsWith:'.o') 
            or:[(fileName endsWith:'.so')
            or:[fileName endsWith:'.obj']]) ifTrue:[
                Object abortSignal catch:[
                    |p|

                    p := (here , '/' ,fileName).
                    "/
                    "/ look if already loaded ...  then unload first
                    "/
                    (ObjectFileLoader loadedObjectFiles includes:p) ifTrue:[
                        (Dialog confirm:(resources 
                                            string:'%1 is already loaded; load anyway ?'
                                            with:p)) ifFalse:[
                            ^ self
                        ].
                        Transcript showCR:'unloading old ' , p , ' ...'.
                        ObjectFileLoader unloadObjectFile:p. 
                    ].

                    Transcript showCR:'loading ' , p , ' ...'.
                    ObjectFileLoader loadObjectFile:p.
                    Class addInfoRecord:('fileIn ' , fileName) 
                ]
            ] ifFalse:[
                (fileName endsWith:'.cls') ifTrue:[
                    aStream := FileStream readonlyFileNamed:fileName in:currentDirectory.
                    aStream notNil ifTrue:[
                        bos := BinaryObjectStorage onOld:aStream.
                        Class nameSpaceQuerySignal 
                            answer:Smalltalk
                            do:[
                                bos next.
                            ].
                        bos close
                    ]
                ] ifFalse:[
                    ((fileName endsWith:'.class')
                    or:[(fileName endsWith:'.cla')
                    or:[(fileName endsWith:'.CLA')]]) ifTrue:[
                        JavaClassReader notNil ifTrue:[
                            JavaClassReader loadFile:(currentDirectory pathName , '/' , fileName)
                        ]
                    ] ifFalse:[
                        aStream := FileStream readonlyFileNamed:fileName in:currentDirectory.
                        aStream notNil ifTrue:[
                            [
                                Class withoutUpdatingChangesDo:[
                                    oldPath := Smalltalk systemPath.
                                    Smalltalk systemPath:(oldPath copy addFirst:here; yourself).
                                    wasLazy := Compiler compileLazy:lazy.
                                    aStream fileIn.
                                ].
                                Class addInfoRecord:('fileIn ' , fileName) 
                            ] valueNowOrOnUnwindDo:[
                                Compiler compileLazy:wasLazy.
                                Smalltalk systemPath:oldPath.
                                aStream close
                            ]
                        ]
                    ]
                ]
            ]
        ]
    ]

    "Modified: 5.11.1996 / 22:01:14 / cg"
!

fileGet
    "get contents of selected file into subView.
     If text was modified show a queryBox,
     otherwise get it immediately"

    self fileGet:false

    "Modified: 19.6.1996 / 09:38:45 / cg"
!

fileGet:viaDoubleClick
    "get contents of selected file into subView.
     If text was modified show a queryBox,
     otherwise get it immediately"

    |fileName msg label|

    (subView modified not or:[subView contentsWasSaved]) ifTrue:[
        self doFileGet:viaDoubleClick.
        ^ self
    ].
    fileName := self getSelectedFileName.
    fileName notNil ifTrue:[
        (currentDirectory isDirectory:fileName) ifTrue:[
            msg := 'contents has not been saved.\\Modifications will be lost when directory is changed.'.
            label := 'change'.
        ] ifFalse:[
            msg := 'contents has not been saved.\\Modifications will be lost when new file is read.'.
            label := 'get'.
        ].
        (self ask:(resources at:msg) yesButton:label) ifTrue:[
            subView modified:false.
            self doFileGet:viaDoubleClick
        ]
    ]

    "Created: 19.6.1996 / 09:38:35 / cg"
    "Modified: 23.4.1997 / 13:04:11 / cg"
!

fileGetInfo
    "show short file (stat)-info"

    self fileGetInfo:false
!

fileGetInfo:longInfo
    "get info on selected file - show it in a box"

    |string|

    string := self getFileInfoString:longInfo.
    string notNil ifTrue:[
        self information:string
    ]
!

fileGetLongInfo
    "show long stat (file)-info"

    self fileGetInfo:true
!

fileInsert
    "insert contents of file at the cursor position"

    |fileName|

    fileName := self getSelectedFileName.
    fileName notNil ifTrue:[
        self showFile:fileName insert:true encoding:fileEncoding
    ]

    "Modified: 23.4.1997 / 13:06:06 / cg"
!

fileListMenu
    "return the menu to show in the fileList"

    <resource: #menu>

    |labels shorties selectors m sel|

    labels := #(
                 'spawn'                   
                 '-'                               
                 'get contents'                    
                 'insert contents'                    
                 'show info'             
                 'show full info'          
                 'fileIn'                 
                 'quick fileIn (lazy)'                 
                 '-'                               
                 'update'                 
                 '-'                               
                 'execute unix command ...'                
                 'st/x tools'                
                 '-'                               
                 'remove'                 
                 'rename ...'                 
                 '-'                               
                 'display long list'           
                 'show all files'           
                 'encoding ...'           
                 '-'                               
                 'create directory ...'         
                 'create file ...'
               ).             

    selectors := #(
                 fileSpawn
                 nil
                 fileGet
                 fileInsert
                 fileGetInfo
                 fileGetLongInfo
                 fileFileIn
                 fileFileInLazy
                 nil
                 updateCurrentDirectory
                 nil
                 fileExecute
                 stxTools
                 nil
                 fileRemove
                 fileRename
                 nil
                 changeDisplayMode
                 changeDotFileVisibility
                 fileEncoding
                 nil
                 newDirectory
                 newFile
                ).

    shorties := #(
                 nil
                 nil
                 GotoLine
                 nil
                 InspectIt
                 CmdI
                 Accept
                 nil
                 nil
                 Cmdu
                 nil
                 DoIt
                 nil
                 nil
                 Delete
                 nil
                 nil
                 nil
                 nil
                 nil
                 nil
                 nil
                 nil
                ).

    m := PopUpMenu 
            labels:(resources array:labels)
            selectors:selectors
            accelerators:shorties
            receiver:self.

    showDotFiles ifTrue:[
        m labelAt:#changeDotFileVisibility put:(resources string:'hide hidden files')
    ].
    showLongList ifTrue:[
        m labelAt:#changeDisplayMode put:(resources string:'display short list')
    ].

    m subMenuAt:#stxTools 
            put:(PopUpMenu
                    labels:(resources array:
                           #(
                              'Changes browser'
                              'Editor'
                              'HTML reader'
                              'Image inspect'
                              'show file differences'
                            ))
                    selectors:#(
                              openChangesBrowser
                              openEditor
                              openHTMLReader
                              openImageInspector
                              openDiffView
                              )
                    receiver:self).

    ((sel := fileListView selection) isNil or:[sel isEmpty]) ifTrue:[
        m disableAll:#(fileGet fileInsert
                       fileGetInfo fileGetLongInfo
                       fileFileIn fileFileInLazy
                       fileRemove fileRename).
        (m subMenuAt:#stxTools)
            disableAll:#(openChangesBrowser openEditor openHTMLReader openImageInspector)
    ] ifFalse:[
        fileListView selection size > 1 ifTrue:[
            m disableAll:#( fileGet fileInsert fileGetInfo fileGetLongInfo fileRename )
        ]
    ].

    ^m

    "Modified: 28.1.1997 / 15:04:42 / stefan"
    "Modified: 25.2.1997 / 20:15:06 / cg"
!

filePrint
    "send a files contents to the printer (not in the menu)"

    |fileName inStream printStream line|

    self withWaitCursorDo:[
        fileName := self getSelectedFileName.
        fileName notNil ifTrue:[
            ((currentDirectory typeOf:fileName) == #regular) ifTrue:[
                inStream := FileStream readonlyFileNamed:fileName
                                                      in:currentDirectory.
                inStream isNil ifFalse:[
                    printStream := PrinterStream new.
                    printStream notNil ifTrue:[
                        [inStream atEnd] whileFalse:[
                            line := inStream nextLine.
                            printStream nextPutLine:line.
                        ].
                        printStream close
                    ].
                    inStream close
                ]
            ]
        ].
        0 "compiler hint"
    ]

    "Modified: 23.4.1997 / 13:05:40 / cg"
!

fileRemove
    "remove the selected file(s).
     Query if user really wants to remove the file.
     - should be enhanced, to look for a ~/.trash directory 
     and move files there if it exists (without asking in this case)."

    |sel q|

    sel := fileListView selection.
    sel notNil ifTrue:[
        sel size > 1 ifTrue:[
            q := resources string:'remove selected files ?'
        ] ifFalse:[
            q := resources string:'remove ''%1'' ?' with:(fileList at:sel first)
        ].
        (self ask:q yesButton:'remove') ifTrue:[self doRemove]
    ]
!

fileRename
    "rename the selected file(s)"

    |queryBox|

    queryBox := FilenameEnterBox new.
    queryBox okText:(resources at:'rename').
    self selectedFilesDo:[:oldName |
        queryBox title:(resources string:'rename ''%1'' to:' with:oldName).
        queryBox initialText:oldName.
        queryBox action:[:newName | self doRename:oldName to:newName].
        queryBox showAtPointer
    ]
!

fileSelect:lineNr
    "selected a file - do nothing here"

    ^ self

    "Modified: 23.4.1997 / 13:04:55 / cg"
!

fileSpawn
    "start another FileBrowser on the selected directory or
     on the same directory if none is selected."

    |any|

    any := false.
    self selectedFilesDo:[:fileName |
        (currentDirectory isDirectory:fileName) ifTrue:[
            self class openOn:(currentDirectory pathName , '/' , fileName).
            any := true
        ]
    ].
    any ifFalse:[
        self class openOn:currentDirectory pathName
    ]
!

newDirectory
    "ask for and create a new directory"

    |queryBox|

    queryBox := FilenameEnterBox 
                    title:(resources at:'create new directory:') withCRs
                    okText:(resources at:'create')
                    action:[:newName | self doCreateDirectory:newName].
    queryBox showAtPointer

    "Modified: 23.4.1997 / 13:04:27 / cg"
!

newFile
    "ask for and create a new file"

    |sel queryBox|

    queryBox := FilenameEnterBox 
                    title:(resources at:'create new file:') withCRs
                    okText:(resources at:'create')
                    action:[:newName | self doCreateFile:newName].
    sel := subView selection.
    sel notNil ifTrue:[
        queryBox initialText:(sel asString)
    ].
    queryBox showAtPointer

    "Modified: 23.4.1997 / 13:04:38 / cg"
!

openChangesBrowser
    "open a change browser on the selected file(s)"

    self openTool:ChangesBrowser
!

openDiffView
    "open a diff-view"

    |box name1 name2 text1 text2 d err nm here l1|

    name1 := ValueHolder newString.
    name2 := self getSelectedFileName asValue.
    here := currentDirectory pathName.

    box := DialogBox new.
    box addTextLabel:'show difference between:'.
    box addFilenameInputFieldOn:name1 in:here tabable:true.
    box addTextLabel:'and:'.
    box addFilenameInputFieldOn:name2 in:here tabable:true.

    box addAbortButton; addOkButton.

    box showAtPointer.

    box accepted ifTrue:[
        name1 := name1 value.
        name1 isEmpty ifTrue:[
            text1 := subView contents.
            name1 := nil.
            l1 := 'browser contents'
        ] ifFalse:[
            (name1 := name1 value asFilename) isAbsolute ifFalse:[
                name1 := here asFilename construct:name1
            ].
            name1 isReadable ifFalse:[
                nm := name1.
                name1 exists ifFalse:[
                    err := '%1 does not exist'.
                ] ifTrue:[
                    err := '%1 is not readable'
                ].
            ].
            l1 := name1 pathName
        ].

        (name2 := name2 value asFilename) isAbsolute ifFalse:[
            name2 := here asFilename construct:name2
        ].
        err isNil ifTrue:[
            name2 isReadable ifFalse:[
                nm := name2.
                name2 exists ifFalse:[
                    err := '%1 does not exist'.
                ] ifTrue:[
                    err := '%1 is not readable'
                ].
            ].
        ].
        err notNil ifTrue:[
            self warn:(resources string:err with:nm pathName).
            ^ self
        ].

        self withWaitCursorDo:[
            name1 notNil ifTrue:[
                text1 := name1 contents.
            ].
            text2 := name2 contents.
            d := DiffTextView 
                    openOn:text1 label:l1
                    and:text2 label:name2 pathName.
            d label:'file differences'.
        ]
    ].

    "Created: 7.12.1995 / 20:33:58 / cg"
    "Modified: 16.1.1997 / 00:51:22 / cg"
!

openEditor
    self openTool:EditTextView
!

openHTMLReader
    self openTool:HTMLDocumentView

    "Modified: 20.5.1996 / 20:30:58 / cg"
!

openImageInspector
    |img|

    self selectedFilesDo:[:fileName |
        (currentDirectory isDirectory:fileName) ifFalse:[
            img := Image fromFile:(currentDirectory pathName , '/' , fileName).
            img notNil ifTrue:[
                img inspect
            ] ifFalse:[
                self warn:'unknown format: ' , fileName
            ]
        ]
    ].

    "Modified: 17.9.1995 / 17:41:24 / claus"
!

openTool:aToolClass
    "open a tool on the selected file(s)"

    |numItems|

    (numItems := fileListView selection size) > 2 ifTrue:[
        (self 
            confirm:(resources string:'open for each of the %1 items ?' 
                                 with:numItems)) ifFalse:[^ self].
    ].

    self selectedFilesDo:[:fileName |
        (currentDirectory isDirectory:fileName) ifFalse:[
            aToolClass openOn:(currentDirectory pathName , '/' , fileName).
        ]
    ].

    "Modified: 14.11.1996 / 16:01:32 / cg"
!

showOrHideTabView
    "depending on the showLongList setting, show or hde the tabSpec view"

    showLongList ifTrue:[
        false "self is3D" ifTrue:[
            scrollView topInset:(tabRulerView superView height).
            tabRulerView superView leftInset:(fileListView originRelativeTo:scrollView) x.
        ] ifFalse:[
            scrollView topInset:(tabRulerView height).
            tabRulerView leftInset:(fileListView originRelativeTo:scrollView) x.
        ].
        tabRulerView hiddenTabs:#(1).
        tabRulerView fixedTabs:#(1).
    ] ifFalse:[
        scrollView topInset:0
    ].
    tabSpec := nil.

    "Created: 19.4.1997 / 09:50:02 / cg"
! !

!FileBrowser methodsFor:'help '!

helpTextFor:aComponent
    |s|

    aComponent == subView ifTrue:[
        s := 'HELP_SUBVIEW'
    ].
    aComponent == fileListView ifTrue:[
        s := 'HELP_FILELIST'
    ].
    aComponent == filterField ifTrue:[
        s := 'HELP_FILTER'
    ].
    aComponent == labelView ifTrue:[
        s := 'HELP_PATHFIELD'
    ].
    aComponent == commandView ifTrue:[
        s := 'HELP_COMMANDVIEW'
    ].
    s notNil ifTrue:[
        ^ resources string:s
    ].
    ^ nil
! !

!FileBrowser methodsFor:'initialization'!

currentDirectory:aDirectoryPath
    "set the directory to be browsed"

    currentDirectory := FileDirectory directoryNamed:aDirectoryPath.
    self changed:#path.
    "
     tell my subview (whatever that is) to start its file-dialog
     (i.e. save-as etc.) in that directory
    "
    (subView respondsTo:#directoryForFileDialog:) ifTrue:[
        subView directoryForFileDialog:currentDirectory
    ]
!

focusSequence
    "return the sequence in which ALT-CursorRight steps focus"

    |fs|

    fs := Array 
        with:filterField 
        with:fileListView 
        with:subView.

    commandView notNil ifTrue:[
        fs := fs copyWith:commandView
    ].
    ^fs
!

initEvents
    super initEvents.
    self enableEvent:#visibilityChange.
!

initialize
    |frame spacing halfSpacing v topFrame labelFrame filterModel
     |

    super initialize.

    fileEncoding := #iso8859.        "/ native ST/X encoding

    "if true, will replace leading spaces by tabs on
     file write. If false, they will be written as spaces
    "
    compressTabs := resources at:'COMPRESS_TABS' default:true.

    "
     showing long or short by default
    "
    showLongList := resources at:'LONG_LIST' default:true.

    "
     show hidden files or not ?
    "
    showDotFiles := resources at:'SHOW_DOT_FILES' default:false.


    lockUpdate := false.

    CommandHistory isNil ifTrue:[
        CommandHistory := OrderedCollection new.
        CommandHistorySize := 50
    ].
    DirectoryHistory isNil ifTrue:[
        DirectoryHistory := OrderedCollection new.
        DirectoryHistoryWhere := OrderedCollection new.
        HistorySize := 15.
    ].
    commandIndex := 0.

    myName := (resources string:self class name).
    self label:myName.

    labelFrame := View 
                        origin:(0.0 @ 0.0)
                        corner:(1.0 @ (font height * 2))
                        in:self.

    styleSheet name = #st80 ifTrue:[
        labelFrame level:1
    ].

    spacing := ViewSpacing.
    halfSpacing := spacing // 2.

    "
      checkBlock is executed by the Processor every checkDelta seconds.
      We use #pushEvent: to perform the directory update
      in our windowgroups process.
    "
    checkBlock := [self pushEvent:#checkIfDirectoryHasChanged].
    checkDelta := resources at:'CHECK_DELTA' default:10.

    currentDirectory := FileDirectory directoryNamed:'.'.

    filterModel := '*' asValue.
    filterField := EditField in:labelFrame.
    filterField 
        origin:[((width // 4 * 3) + halfSpacing) @ halfSpacing]
        corner:(1.0 @ (filterField heightIncludingBorder + halfSpacing + halfSpacing) ).
    filterField rightInset:halfSpacing.
    filterField model:filterModel.

    self initializeFilterPattern.
    filterModel onChangeSend:#filterPatternChanged to:self.
"/    filterField leaveAction:[:key | fileListView scrollToTop. self updateCurrentDirectory].

    labelView := Label in:labelFrame.
    labelView origin:(halfSpacing @ halfSpacing)
              extent:[((width // 4 * 3) - spacing - borderWidth)
                       @
                       (filterField heightIncludingBorder)
                       "(font height + font descent)"
                     ].
    labelView adjust:#right.
    labelView borderWidth:0.
    labelView model:self; menu:#labelMenu; aspect:#path; labelMessage:#path.
    labelFrame model:self; menu:#labelMenu.

    killButton := Button label:(resources string:'kill') in:self.
    killButton origin:(halfSpacing @ halfSpacing)
               extent:(killButton width @ filterField height).
    killButton beInvisible.

    self initializeCommandViewIn:self.

"/    frame := VariableVerticalPanel
"/                 origin:[frame borderWidth negated 
"/                         @ 
"/                         labelFrame height
"/                         "/ (labelView height + labelView origin y + spacing)
"/                        ]
"/                 corner:(1.0 @ 1.0)
"/                     in:self.

    frame := VariableVerticalPanel origin:0.0@0.0 corner:1.0@1.0 in:self.
    frame topInset:labelFrame height.
    commandView notNil ifTrue:[
        frame bottomInset:(commandView height + spacing + spacing)
    ].

    topFrame := View in:frame.
    topFrame origin:(0.0 @ 0.0) corner:(1.0 @ 0.3).

    false "self is3D" ifTrue:[
        v := View in:topFrame.
        v level:-1.
        tabRulerView := TabSpecRuler in:v.
        tabRulerView level:1.
        v origin:(0.0@0.0) corner:(1.0@10).
        tabRulerView origin:(0.0@0.0) corner:(1.0@1.0).
    ] ifFalse:[
        tabRulerView := TabSpecRuler in:topFrame.
        tabRulerView origin:(0.0@0.0) corner:(1.0@10).
    ].
    tabRulerView borderWidth:0.
    tabRulerView synchronousOperation:true.

    scrollView := ScrollableView in:topFrame.
    scrollView origin:(0.0 @ 0.0) corner:(1.0 @ 1.0).

    fileListView := SelectionInListView new.
    scrollView scrolledView:fileListView.
    fileListView action:[:lineNr | self fileSelect:lineNr].
    fileListView doubleClickAction:[:lineNr | self fileSelect:lineNr.
                                              self fileGet:true].
    fileListView multipleSelectOk:true.
    fileListView delegate:self.
    fileListView menuHolder:self; menuPerformer:self; menuMessage:#fileListMenu.
    fileListView allowDrag:true.
    fileListView dragObjectConverter:[:obj | 
                                        |dir nm path idx|
obj printCR.
                                        nm := obj theObject asString.
                                        idx := fileListView list indexOf:nm.
idx printCR.
                                        idx == 0 ifTrue:[
                                            "/ cannot happen ...
                                            nil
                                        ] ifFalse:[
                                            nm := fileList at:idx.
nm printCR.
                                            dir := currentDirectory pathName asFilename.
                                            path := dir constructString:nm.
path printCR.
                                            DropObject newFile:path.
                                        ]
                                     ].

    "/ sigh - must be delayed - origin is not yet fixe
"/    tabRulerView leftInset:(fileListView originRelativeTo:scrollView) x.
"/    self showOrHideTabView.

    v := self initializeSubViewIn:frame.

    v origin:(0.0 @ 0.3) corner:(1.0 @ 1.0).
    subView := v scrolledView.
    (subView respondsTo:#directoryForFileDialog:) ifTrue:[
        subView directoryForFileDialog:currentDirectory
    ].

    ObjectMemory addDependent:self.

    "Modified: 6.9.1995 / 20:26:06 / claus"
    "Modified: 27.3.1997 / 11:04:31 / stefan"
    "Modified: 19.4.1997 / 17:37:37 / cg"
!

initializeCommandViewIn:frame
    "set up the command view - can be redefined in subclasses as empty,
     if no commandView is wanted"


    commandView := EditField origin:0.0@1.0 corner:1.0@1.0 in:frame.
    commandView allInset:ViewSpacing.
    commandView topInset:(commandView preferredExtent y negated - ViewSpacing).

"/    commandView contents:'** no commands which require input here **'.

    commandView entryCompletionBlock:[:contents |
        |newString|

        newString := Filename 
                        filenameCompletionFor:contents 
                        directory:currentDirectory pathName asFilename 
                        directoriesOnly:false 
                        filesOnly:false 
                        ifMultiple:[:dir | commandView flash.].
        commandView contents:newString.
        commandView cursorToEndOfLine.
    ].
    commandView leaveAction:[:key | 
        |cmd nCmd empty|

        (key == #CursorDown 
        or:[key == #CursorUp]) ifTrue:[
            nCmd := CommandHistory size.
            nCmd == 0 ifTrue:[
                empty := true
            ] ifFalse:[
                key == #CursorUp ifTrue:[
                    commandIndex == nCmd ifTrue:[
                        commandView flash.
                    ].
                    commandIndex := (commandIndex + 1) min:nCmd
                ] ifFalse:[
                    commandIndex == 1 ifTrue:[
                        commandView flash.
                        empty := true.
                    ].
                    commandIndex := (commandIndex - 1) max:1.
                ].
            ].
            empty == true ifTrue:[
                commandView contents:nil
            ] ifFalse:[
                commandView contents:(CommandHistory at:commandIndex).
            ]        
        ].
        key == #Return ifTrue:[
            cmd := commandView contents.

            subView insertLine:(
                                Text string:('>> ' , cmd)
                                     emphasis:(Array with:#bold with:#underline with:(#color->Color blue))
"/                                ColoredListEntry string:('>> ' , cmd) color:Color blue
                                )
                    before:(subView cursorLine).
            subView cursorDown:1.

"/            subView insertStringAtCursor:cmd.
"/            subView insertCharAtCursor:(Character cr).

            (cmd notNil and:[cmd notEmpty]) ifTrue:[
                self class addToCommandHistory:cmd for:nil.
                self doExecuteCommand:cmd replace:false.
                commandView contents:nil.
                commandIndex := 0
            ]
        ]
    ].

    "Modified: 7.9.1995 / 15:48:45 / claus"
    "Modified: 14.11.1996 / 14:58:38 / cg"
!

initializeFilterPattern
    "set an initial matchpattern - can be redefined in subclasses"

    filterField model value:'*'
!

initializeSubViewIn:frame
    "set up the contents view - can be redefined in subclasses for
     different view types (SoundFileBrowser/ImageBrowsers etc.)"

    ^ HVScrollableView for:CodeView miniScrollerH:true miniScrollerV:false in:frame.
!

realize
    super realize.
    self showOrHideTabView.

    "Created: 19.4.1997 / 17:36:15 / cg"
! !

!FileBrowser methodsFor:'misc user interaction'!

destroy
    "destroy view and boxes"

    ObjectMemory removeDependent:self.
    self stopUpdateProcess.
    checkBlock := nil.
    super destroy

    "Modified: 19.4.1997 / 13:51:48 / cg"
!

filterPatternChanged
    fileListView scrollToTop. 
    self updateCurrentDirectory
!

terminate
    "exit FileBrowser"

    (self askIfModified:'contents has not been saved.\\Modifications will be lost when FileBrowser is closed.'
              yesButton:'close') ifTrue:[self destroy]
!

update:what with:someArgument from:changedObject
    realized ifFalse:[^ self].

    (what == #aboutToExit) ifTrue:[
        "system wants to shut down this
         - if text was modified, pop up, and ask user and save if requested."

        (subView modified and:[subView contentsWasSaved not]) ifTrue:[
            self raiseDeiconified.

            (self 
                ask:(resources at:'FileBrowser:\\contents has not been saved.\\Save before exiting ?')
                yesButton:'save'
                noButton:'don''t save')
            ifTrue:[
                subView acceptAction notNil ifTrue:[
                    subView accept
                ] ifFalse:[
                    subView save
                ]
            ]
        ].
        ^ self
    ].
    changedObject == tabSpec ifTrue:[
        fileListView invalidate
    ].

    "Modified: 29.5.1996 / 16:13:43 / cg"
! !

!FileBrowser methodsFor:'pathField user interaction'!

changeCurrentDirectory
    "if text was modified show a queryBox, 
     otherwise change immediately to directory"

    (self askIfModified:'contents has not been saved.\\Modifications will be lost when directory is changed.'
              yesButton:'change') ifTrue:[
        self queryForDirectoryToChange
    ]
!

changeDirectoryTo:aDirectoryName
    "sent from label menu to change back to a previous directory"

    self doChangeCurrentDirectoryTo:aDirectoryName updateHistory:false
!

changeToHomeDirectory
    "if text was modified show a queryBox, 
     otherwise change immediately to directory"

    (self askIfModified:'contents has not been saved.\\Modifications will be lost when directory is changed.'
              yesButton:'change') ifTrue:[
         self doChangeToHomeDirectory
    ]
!

changeToParentDirectory
    "if text was modified show a queryBox, 
     otherwise change immediately to directory"

    (self askIfModified:'contents has not been saved.\\Modifications will be lost when directory is changed.'
              yesButton:'change') ifTrue:[
         self doChangeToParentDirectory
    ]
!

copyPath
    "copy current path into cut & paste buffer"

    self setTextSelection:currentDirectory pathName

    "Modified: 14.12.1996 / 15:37:47 / cg"
!

labelMenu
    "return the popUpMenu for the path label"

    <resource: #menu>

    |labels selectors args menu|

    labels := #(
                   'copy path'
                   '-'                               
                   'up'
                   'back'
                   'change to home-directory'
                   'change directory ...'
               ).             

    selectors := #(
                    copyPath
                    nil
                    changeToParentDirectory
                    changeToPreviousDirectory
                    changeToHomeDirectory
                    changeCurrentDirectory
                  ).

    args := Array new:(labels size).

    DirectoryHistory size > 0 ifTrue:[
        labels := labels copyWith:'-'.
        selectors := selectors copyWith:nil.
        args := args copyWith:nil.

        DirectoryHistory do:[:dirName |
            labels := labels copyWith:dirName.
            selectors := selectors copyWith:#changeDirectoryTo:.
            args := args copyWith:dirName
        ]
    ].

    menu := PopUpMenu 
                labels:(resources array:labels)
                selectors:selectors
                args:args
                receiver:self.

    previousDirectory isNil ifTrue:[
        menu disable:#changeToPreviousDirectory.
    ].
    ^menu.

    "Modified: 25.2.1997 / 20:14:58 / cg"
!

queryForDirectoryToChange
    "query for new directory"

    |queryBox|

    queryBox := FilenameEnterBox 
                    title:(resources at:'change directory to:') withCRs
                    okText:(resources at:'change')
                    action:[:newName | self doChangeCurrentDirectoryTo:newName updateHistory:true].
"/    queryBox initialText:''.
    queryBox showAtPointer
! !

!FileBrowser methodsFor:'private'!

ask:question yesButton:yesButtonText
    "common method to ask a yes/no question; return true or false"

    ^ self ask:question yesButton:yesButtonText noButton:'cancel' 
!

ask:question yesButton:yesButtonText noButton:noButtonText
    "common method to ask a yes/no question"

    ^ Dialog 
        confirm:question withCRs
        yesLabel:(resources at:yesButtonText)
        noLabel:(resources at:noButtonText)

    "Modified: 21.2.1996 / 01:19:21 / cg"
!

askForCommandFor:fileName thenDo:aBlock
    "setup and launch a querybox to ask for unix command.
     Then evaluate aBlock passing the command-string as argument."

    |sel box|

    box := FilenameEnterBox 
                title:(resources at:'execute unix command:')
               okText:(resources at:'execute')
               action:aBlock.

    fileName notNil ifTrue:[
        self initialCommandFor:fileName into:box.
    ].
    box directory:currentDirectory pathName asFilename.
    box showAtPointer.
    box destroy.

    "Modified: 7.9.1995 / 10:31:54 / claus"
!

askIfModified:question yesButton:yesButtonText
    "tell user, that code has been modified - let her confirm"

    (subView modified not or:[subView contentsWasSaved]) ifTrue:[
        ^ true
    ].
    ^ self 
        ask:(resources string:question)
        yesButton:yesButtonText
!

getSelectedFileName
    "returns the currently selected file; shows an error if
     multiple files are selected"

    |sel|

    sel := fileListView selection.
    (sel size > 1) ifTrue:[
        self onlyOneSelection
    ] ifFalse:[
        sel notNil ifTrue:[
            ^ fileList at:sel first
        ]
    ].
    ^ nil
!

onlyOneSelection
    "show a warning, that only one file must be selected for
     this operation"

    self warn:'exactly one file must be selected !!'
!

selectedFilesDo:aBlock
    "evaluate aBlock on all selected files;
     show a wait cursor while doing this"

    |sel|

    sel := fileListView selection.
    sel notNil ifTrue:[
        self withWaitCursorDo:[
            sel do:[:aSelectionIndex |
                aBlock value:(fileList at:aSelectionIndex )
            ]
        ]
    ]

!

show:something
    "show something in subview and undef acceptAction"

    subView contents:something.
    subView acceptAction:nil.
    subView modified:false.
    currentFileName := nil
!

showAlert:aString with:anErrorString
    "show an alertbox, displaying the last Unix-error"

    |msg|

    anErrorString isNil ifTrue:[
        msg := aString
    ] ifFalse:[
        msg := aString , '\\(' , anErrorString , ')'
    ].
    self warn:msg withCRs
!

withoutHiddenFiles:aCollection
    "remove hidden files (i.e. those that start with '.') from
     the list in aCollection"

    |newCollection|

    newCollection := aCollection species new.
    aCollection do:[:fname |
        |ignore|

        ignore := false.

        ((fname startsWith:'.') and:[fname ~= '..']) ifTrue:[
            showDotFiles ifFalse:[
                ignore := true
            ]
        ].
        ignore ifFalse:[
            newCollection add:fname
        ]
    ].
    ^ newCollection

    "Modified: 21.2.1996 / 01:33:18 / cg"
! !

!FileBrowser methodsFor:'private - actions & command execution'!

binaryFileAction:aFilename
    "for some binary files, if double clicked, we can do some useful
     action ..."

    (currentDirectory pathName , '/' , aFilename) asFilename isExecutable ifTrue:[
        (OperatingSystem executeCommand:'cd ',currentDirectory pathName, '; ',aFilename)
        ifTrue:[^true].
    ].
    ^ self imageAction:aFilename

    "Modified: 19.6.1996 / 09:44:07 / cg"
!

doExecuteCommand:command replace:replace
    "execute a unix command inserting the output of the command.
     If replace is true, all text is replaced by the commands output;
     otherwise, its inserted as selected text at the cursor position."

    |stream line lnr myProcess myPriority startLine startCol stopSignal
     access stillReplacing|

    access := Semaphore forMutualExclusion name:'accessLock'.
    stopSignal := Signal new.

    "
     must take killButton out of my group
    "
    windowGroup removeView:killButton.
    "
     bring it to front, and turn hidden-mode off
    "
    killButton raise.
    killButton beVisible.
    "
     it will make me raise stopSignal when pressed
    "
    killButton 
        action:[
            stream notNil ifTrue:[
                access critical:[
                    myProcess interruptWith:[stopSignal raise].
                ]
            ]
        ].
    "
     start it up under its own windowgroup
    "
    killButton openAutonomous.

    "
     go fork a pipe and read it
    "
    self label:(myName , ': executing ' , (command copyTo:(20 min:command size)) , ' ...').
    [
      self withWaitCursorDo:[
        stopSignal catch:[
            startLine := subView cursorLine.
            startCol := subView cursorCol.

            "
             this can be a time consuming operation; therefore lower my priority
            "
            myProcess := Processor activeProcess.
            myPriority := myProcess priority.
            myProcess priority:(Processor userBackgroundPriority).

            stream := PipeStream readingFrom:('cd '
                                              , currentDirectory pathName
                                              , '; '
                                              , command
                                              , ' 2>&1' ).
            stream notNil ifTrue:[
                [
                    |codeView lines|

                    stream buffered:true.
                    codeView := subView.

                    replace ifTrue:[
                        codeView list:nil.
                        lnr := 1.
                    ].

                   stillReplacing := replace.

                   [stream atEnd] whileFalse:[
                        (stream readWaitWithTimeoutMs:50) ifFalse:[
                            "
                             data available; read up to 100 lines
                             and insert as a single junk. This speeds up
                             display of long output (less line-scrolling).
                            "
                            lines := OrderedCollection new:100.
                            line := stream nextLine.
                            line notNil ifTrue:[lines add:line].

                            [stream atEnd not
                            and:[stream canReadWithoutBlocking
                            and:[lines size < 100]]] whileTrue:[
                                line := stream nextLine.
                                line notNil ifTrue:[lines add:line].
                            ].

                            "
                             need this critical section; otherwise,
                             we could get the signal while waiting for
                             an expose event ...
                            "
                            access critical:[                        
                                lines size > 0 ifTrue:[
                                    stillReplacing ifTrue:[
                                        lines do:[:line |
                                            codeView at:lnr put:line withTabsExpanded.
                                            codeView cursorToBottom; cursorDown:1.
                                            lnr := lnr + 1.
                                            lnr > codeView list size ifTrue:[
                                                stillReplacing := false
                                            ]
                                        ].
                                    ] ifFalse:[
                                        codeView insertLines:lines before:codeView cursorLine.
                                        codeView cursorDown:lines size.
                                    ]
                                ].
                            ].
                        ].

                        shown ifTrue:[windowGroup processExposeEvents].
                        "
                         give others running at same prio a chance too
                         (especially other FileBrowsers doing the same)
                        "
                        Processor yield
                    ].
                ] valueNowOrOnUnwindDo:[
                    stream shutDown "close". stream := nil.
                ].

                self updateCurrentDirectoryIfChanged

            ].
            replace ifTrue:[
                subView modified:false.
            ].
        ]
      ]
    ] valueNowOrOnUnwindDo:[
        |wg|

        self label:myName; iconLabel:myName.
        myProcess notNil ifTrue:[myProcess priority:myPriority].

        "
         remove the killButton from its group
         (otherwise, it will be destroyed when we shut down the group)
        "
        wg := killButton windowGroup.
        killButton windowGroup:nil.
        "
         shut down the windowgroup
        "
        wg notNil ifTrue:[
            wg process terminate.
        ].
        "
         hide the button, and make sure it will stay
         hidden when we are realized again
        "
        killButton beInvisible.
        "
         clear its action (actually not needed, but
         releases reference to thisContext earlier)
        "
        killButton action:nil.
    ].

    currentFileName isNil ifTrue:[
        subView modified:false.
    ].

    subView size > 10000 ifTrue:[
        self warn:'text quite large now - please cut off some lines'
    ]

    "Modified: 21.9.1995 / 11:18:46 / claus"
    "Modified: 19.4.1997 / 15:29:54 / cg"
!

imageAction:aFilename
    "for some image files, if double clicked, we can do some useful
     action ..."

    |img|

    (Image isImageFileSuffix:(aFilename asFilename suffix))
    ifTrue:[
        img := Image fromFile:(currentDirectory pathName , '/' , aFilename).
        img notNil ifTrue:[
            img inspect.
            ^ true
        ]
    ].
    ^ false

    "Created: 19.6.1996 / 09:43:50 / cg"
    "Modified: 18.4.1997 / 14:56:04 / cg"
!

initialCommandFor:fileName into:aBox
    "set a useful initial command for execute box."

    |lcFilename cmd select|

    "/ XXX should be changed to take stuff from a config file
    "/ XXX or from resources.

    ((currentDirectory typeOf:fileName) == #regular) ifTrue:[

        (currentDirectory isExecutable:fileName) ifTrue:[
            aBox initialText:(fileName , ' <arguments>').
            ^ self
        ].

        lcFilename := fileName asLowercase.

        select := true.

        "some heuristics - my personal preferences ...
         (actually this should come from a configfile)"

        (fileName endsWith:'akefile') ifTrue:[
            aBox initialText:'make target' selectFrom:6 to:11.
            ^ self
        ].
        (lcFilename endsWith:'tar.z') ifTrue:[
            cmd := 'zcat %1 | tar tvf -'.
            select := false.
        ].
        (fileName endsWith:'.taz') ifTrue:[
            aBox initialText:'zcat %1 | tar tvf -'.
            select := false.
        ].
        (fileName endsWith:'.tar') ifTrue:[
            cmd := 'tar tvf %1'.
            select := 7.
        ].
        (fileName endsWith:'.zoo') ifTrue:[
            cmd := 'zoo -list %1'.
            select := 9.
        ].
        (lcFilename endsWith:'.zip') ifTrue:[
            cmd := 'unzip -l %1'.
            select := 8.
        ].
        (lcFilename endsWith:'.z') ifTrue:[
            cmd := 'uncompress %1'
        ].
        (fileName endsWith:'tar.gz') ifTrue:[
            cmd := ('gunzip < %1 | tar tvf -' ).
            select := false.
        ].
        (fileName endsWith:'.tgz') ifTrue:[
            cmd := ('gunzip < %1 | tar tvf -' ).
            select := false.
        ].
        (fileName endsWith:'.gz') ifTrue:[
            cmd := 'gunzip %1'.
        ].
        (lcFilename endsWith:'.html') ifTrue:[
            cmd := 'netscape %1'
        ].
        (lcFilename endsWith:'.htm') ifTrue:[
            cmd := 'netscape %1'
        ].
        (fileName endsWith:'.uue') ifTrue:[
            cmd := 'uudecode %1'
        ].
        (fileName endsWith:'.c') ifTrue:[
            cmd := 'cc -c %1'.
            select := 5.
        ].
        (fileName endsWith:'.cc') ifTrue:[
            cmd := 'g++ -c %1'.
            select := 6.
        ].
        (fileName endsWith:'.C') ifTrue:[
            cmd := 'g++ -c %1'.
            select := 6.
        ].
        (fileName endsWith:'.xbm') ifTrue:[
            cmd := 'bitmap %1'
        ].
        (lcFilename endsWith:'.ps') ifTrue:[
            cmd := 'ghostview %1'
        ].
        ((fileName endsWith:'.1') 
        or:[fileName endsWith:'.man']) ifTrue:[
            cmd := 'nroff -man %1'.
            select := 10.
        ].

        cmd isNil ifTrue:[
            DefaultCommandPerSuffix isNil ifTrue:[
                cmd := '<cmd>'
            ] ifFalse:[
                cmd := DefaultCommandPerSuffix 
                        at:(lcFilename asFilename suffix)
                        ifAbsent:'<cmd>'.
            ].
            cmd := cmd , ' %1'.
        ].

        cmd := cmd bindWith:fileName.
        select == false ifTrue:[
            aBox initialText:cmd
        ] ifFalse:[
            select isInteger ifFalse:[
                select := (cmd indexOf:Character space ifAbsent:[cmd size + 1]) - 1.
            ].
            aBox initialText:cmd selectFrom:1 to:select
        ]
    ]

    "Modified: 4.4.1997 / 12:26:40 / cg"
!

nonBinaryFileAction:aFilename
    "for some nonBinary files, if double clicked, we can do some useful
     action ..."

    |fullPath lcName|

    fullPath := currentDirectory pathName , '/' , aFilename.
    lcName := aFilename asLowercase.
    ((lcName endsWith:'.htm') or:[lcName endsWith:'.html']) ifTrue:[
        HTMLDocumentView openOn:fullPath.
        ^ true
    ].

    OperatingSystem isUNIXlike ifTrue:[
        (#('.man' '.1' '.2' '.3') findFirst:[:suff | aFilename endsWith:suff]) ~~ 0 
        ifTrue:[
             HTMLDocumentView openFullOnText:(HTMLDocGenerator manPageForFile:fullPath).
            ^ true
        ]
    ].
    ^ self imageAction:aFilename

    "Created: 19.6.1996 / 09:36:38 / cg"
    "Modified: 4.4.1997 / 10:49:00 / cg"
! !

!FileBrowser methodsFor:'private - directory stuff'!

changeToPreviousDirectory
    "if text was modified show a queryBox, 
     otherwise change immediately to previous directory."

    previousDirectory isNil ifTrue:[^ self].
    (self askIfModified:'contents has not been saved.\\Modifications will be lost when directory is changed.'
              yesButton:'change') ifTrue:[
        self doChangeCurrentDirectoryTo:previousDirectory updateHistory:false 
    ]
!

checkIfDirectoryHasChanged
    "every checkDelta secs, check if directoy has changed and update the list if so.
     Also, we check if the file shown has been touched in the meanwhile (for example,
     from another browser) and say 'outdated' in the label if so. 
     This avoids confusion if the same file is being edited by two browsers. (or other editors).
     If the text shown in the codeView has been edited, 'modified' is shown.
    "

    |oldSelection nOld here newState msg newLabel|

    shown ifTrue:[
        currentDirectory notNil ifTrue:[
            lockUpdate ifTrue:[
                Processor removeTimedBlock:checkBlock.
                Processor addTimedBlock:checkBlock afterSeconds:checkDelta.
                ^ self
            ].

            subView modified ifTrue:[
                newState := ' (modified)'
            ].

            here := currentDirectory pathName.
            (OperatingSystem isReadable:here) ifTrue:[
                Processor removeTimedBlock:checkBlock.

                (currentDirectory timeOfLastChange > timeOfLastCheck) ifTrue:[
                    nOld := fileListView numberOfSelections.
                    oldSelection := fileListView selectionValue.
                    self updateCurrentDirectory.
                    nOld ~~ 0 ifTrue:[
                        nOld > 1 ifTrue:[
                            oldSelection do:[:element  |
                                fileListView addElementToSelection:element
                            ]
                        ] ifFalse:[
                            fileListView selectElementWithoutScroll:oldSelection
                        ]
                    ].
                ] ifFalse:[
                    Processor addTimedBlock:checkBlock afterSeconds:checkDelta
                ].

                currentFileName notNil ifTrue:[
                    (currentDirectory exists:currentFileName) ifFalse:[
                        newState := ' (removed)'.
                    ] ifTrue:[
                        (currentDirectory timeOfLastChange:currentFileName) > timeOfFileRead ifTrue:[
                            newState := ' (outdated)'.
                            subView modified ifTrue:[
                                newState := ' (modified & outdated)'
                            ]
                        ].
                    ].
                ].

            ] ifFalse:[         
                "
                 if the directory has been deleted, or is not readable ...
                "
                (OperatingSystem isValidPath:here) ifFalse:[
                    msg := 'FileBrowser:\\directory %1 is gone ?!!?'
                ] ifTrue:[
                    msg := 'FileBrowser:\\directory %1 is no longer readable ?!!?'
                ].
                self warn:(resources string:msg with:here) withCRs.

                fileListView contents:nil.
                newLabel := myName , ': directory is gone !!'.
                "/ Processor addTimedBlock:checkBlock afterSeconds:checkDelta
            ].

            newState notNil ifTrue:[
                newLabel := myName.
                currentFileName notNil ifTrue:[
                    newLabel := newLabel , ': ' , currentFileName
                ].
                newLabel := newLabel , newState.
            ].
            newLabel notNil ifTrue:[
                self label:newLabel.
            ]
        ]
    ]
!

doChangeCurrentDirectoryTo:fileName updateHistory:updateHistory 
    "verify argument is name of a readable & executable directory
     and if so, go there"

    |msg path idx|

    self label:myName; iconLabel:myName.
    fileName notNil ifTrue:[
        (currentDirectory isDirectory:fileName) ifTrue:[
            (currentDirectory isReadable:fileName) ifTrue:[
                (currentDirectory isExecutable:fileName) ifTrue:[

                    path := currentDirectory pathName.
                    previousDirectory := path.

                    "
                     remember where we are in the fileList
                     (in case we want to return)
                    "
                    idx := DirectoryHistory indexOf:path.
                    idx ~~ 0 ifTrue:[
                        DirectoryHistoryWhere at:idx put:fileListView firstLineShown
                    ].

                    self setCurrentDirectory:fileName.

                    path := currentDirectory pathName.

                    "
                     if we have already been there, look for the
                     position offset, and scroll the fileList
                    "
                    idx := DirectoryHistory indexOf:path.
                    idx ~~ 0 ifTrue:[
                        |pos|

                        pos := DirectoryHistoryWhere at:idx.
                        pos notNil ifTrue:[
                            fileListView scrollToLine:pos
                        ]
                    ].

                    updateHistory ifTrue:[
                        |pos|

                        (DirectoryHistory includes:path) ifFalse:[
                            DirectoryHistory size >= HistorySize ifTrue:[
                                DirectoryHistory removeLast.
                                DirectoryHistoryWhere removeLast
                            ]
                        ] ifTrue:[
                            "already been there before; move the entry to
                             the beginning, so it will fall out later."

                            idx := DirectoryHistory indexOf:path.
                            DirectoryHistory removeIndex:idx.
                            pos := DirectoryHistoryWhere at:idx.
                            DirectoryHistoryWhere removeIndex:idx.
                        ].
                        DirectoryHistory addFirst:path.
                        DirectoryHistoryWhere addFirst:pos.
                    ].

                    ^ self
                ].
                msg := 'cannot change directory to ''%1'' !!'
            ] ifFalse:[
                msg := 'cannot read directory ''%1'' !!'
            ]
        ] ifFalse:[
            msg := '''%1'' is not a directory !!'
        ].
        self showAlert:(resources string:msg with:fileName) with:nil
    ]
!

doChangeToHomeDirectory
    "go to home directory"

    self doChangeCurrentDirectoryTo:(OperatingSystem getHomeDirectory) updateHistory:true
!

doChangeToParentDirectory
    "go to home directory"

    self doChangeCurrentDirectoryTo:'..' updateHistory:true
!

doCreateDirectory:newName
    (currentDirectory includes:newName) ifTrue:[
        self warn:'%1 already exists.' with:newName.
        ^ self
    ].

    (currentDirectory createDirectory:newName) ifTrue:[
        self updateCurrentDirectoryIfChanged
    ] ifFalse:[
        self showAlert:(resources string:'cannot create directory ''%1'' !!' with:newName)
                  with:(OperatingSystem lastErrorString)
    ]

    "Modified: 19.4.1997 / 15:30:32 / cg"
!

setCurrentDirectory:aPathName
    "setup for another directory"

    |newDirectory|

    aPathName isEmpty ifTrue:[^ self].
    (currentDirectory isDirectory:aPathName) ifTrue:[
        newDirectory := FileDirectory directoryNamed:aPathName in:currentDirectory.
        newDirectory notNil ifTrue:[
            self currentDirectory:newDirectory pathName.
            currentFileName notNil ifTrue:[
                fileListView contents:nil.
                currentFileName := nil.
            ] ifFalse:[
                fileListView setSelection:nil.
                fileListView scrollToTop.
            ].
            self updateCurrentDirectory.
            self showInfo.
        ]
    ]

    "Modified: 21.9.1995 / 11:22:45 / claus"
    "Modified: 25.5.1996 / 12:27:01 / cg"
!

updateCurrentDirectoryIfChanged
    (currentDirectory timeOfLastChange > timeOfLastCheck) ifTrue:[
        self updateCurrentDirectory
    ]

    "Modified: 19.4.1997 / 15:30:03 / cg"
! !

!FileBrowser methodsFor:'private - encoding'!

guessEncodingFrom:aBuffer
    "look for a string
        encoding #name
     or:
        encoding: name
     within the given buffer (which is usually the first few
     bytes of a textFile"

    |n "{Class: SmallInteger }"
     binary idx s w w2|

    binary := false.
    n := aBuffer size.

    (idx := aBuffer findString:'encoding') ~~ 0 ifTrue:[
        s := ReadStream on:aBuffer.
        s position:idx + 8.
        s skipSeparators.
        s peek == $: ifTrue:[
            s next.
            s skipSeparators. 
        ] ifFalse:[
            s peek == $# ifTrue:[s next].
        ].
        w := s upToSeparator.
        w notNil ifTrue:[
            ^ w asSymbol
        ].
    ].

    1 to:n do:[:i |
        (aBuffer at:i) isPrintable ifFalse:[binary := true].
    ].

    binary ifTrue:[
        "/ look for JIS7 / EUC encoding

        (aBuffer findString:(JISEncodedString jis7KanjiEscapeSequence)) ~~ 0 ifTrue:[
            ^ #jis7
        ].
        (aBuffer findString:(JISEncodedString oldJis7KanjiEscapeSequence)) ~~ 0 ifTrue:[
            ^ #jis7
        ].
        ^ #binary
    ].
    ^ #ascii

    "Created: 26.2.1996 / 17:43:08 / cg"
    "Modified: 23.1.1997 / 20:39:25 / cg"
!

validateFontEncodingFor:newEncoding ask:ask
    "if required, query user if he/she wants to change to another font,
     which is able to display text encoded as specified by newEncoding"

    |fontsEncoding msg filter f defaultFont|

    fontsEncoding := subView font encoding.

    ((newEncoding == #jis7) or:[newEncoding == #euc]) ifTrue:[
        (fontsEncoding notNil and:[fontsEncoding startsWith:'jis']) ifFalse:[
            msg := 'switch to a JIS encoded font ?'.
            filter := [:f | |coding|
                            (coding := f encoding) notNil 
                            and:['jis*' match:coding]].
        ]
    ].
    (newEncoding == #gb) ifTrue:[
        (fontsEncoding notNil and:[fontsEncoding startsWith:'gb']) ifFalse:[
            msg := 'switch to a GB encoded font ?'.
            filter := [:f | |coding|
                            (coding := f encoding) notNil 
                            and:['gb*' match:coding]].
        ]
    ].
    (newEncoding == #big5) ifTrue:[
        (fontsEncoding notNil and:[fontsEncoding startsWith:'big5']) ifFalse:[
            msg := 'switch to a BIG-5 encoded font ?'.
            filter := [:f | |coding|
                            (coding := f encoding) notNil 
                            and:['big5*' match:coding]].
        ]
    ].
    (newEncoding == #ksc) ifTrue:[
        (fontsEncoding notNil and:[fontsEncoding startsWith:'ksc']) ifFalse:[
            msg := 'switch to a KSC encoded font ?'.
            filter := [:f | |coding|
                            (coding := f encoding) notNil 
                            and:['ksc*' match:coding]].
        ]
    ] ifFalse:[
        fontsEncoding notNil ifTrue:[
            ((fontsEncoding startsWith:'jis')
            or:[(fontsEncoding startsWith:'gb')
            or:[(fontsEncoding startsWith:'ksc')
            or:[(fontsEncoding startsWith:'big5')]]])
            ifTrue:[
                msg := 'switch back to an ASCII encoded font ?'.
                filter := [:f | |coding|
                                (coding := f encoding) notNil 
                                and:[('ascii' match:coding)
                                     or:['iso*' match:coding]]].
                defaultFont := TextView defaultFont
            ] ifFalse:[
                (fontsEncoding notNil and:[fontsEncoding startsWith:'iso8859']) ifTrue:[
                    msg := 'switch to a ''' , newEncoding , ''' encoded font ?'.
                    filter := [:f | |coding|
                                    (coding := f encoding) notNil 
                                    and:[newEncoding asLowercase = coding asLowercase]].
                ].
            ].
        ]
    ].

    msg isNil ifTrue:[
        "/ mhmh - can be represented in current font
    ].

    msg notNil ifTrue:[
        defaultFont isNil ifTrue:[
            defaultFont := device 
                                listOfAvailableFonts 
                                    detect:[:f | filter value:f]
                                    ifNone:nil.
            defaultFont isNil ifTrue:[
                self warn:'your display does not seem to provide any ' , newEncoding , '-encoded font.'.
                ^ self.
            ]
        ].

        (ask not or:[self confirm:(resources string:msg) withCRs])
        ifTrue:[
            f := FontPanel 
                fontFromUserInitial:defaultFont
                              title:(resources string:'font selection')
                             filter:filter.
            f notNil ifTrue:[
                subView font:f
            ]
        ]
    ]

    "Created: 26.10.1996 / 12:06:54 / cg"
! !

!FileBrowser methodsFor:'private - file stuff'!

doCreateFile:newName
    "create an empty file"

    |aStream|

    (currentDirectory includes:newName) ifTrue:[
        (self
            ask:(resources string:'%1 already exists\\truncate ?' with:newName)
            yesButton:'truncate'
        ) ifFalse:[^ self].
    ].

    aStream := FileStream newFileNamed:newName in:currentDirectory.
    aStream notNil ifTrue:[
        aStream close.
        self updateCurrentDirectoryIfChanged
    ] ifFalse:[
        self showAlert:(resources string:'cannot create file ''%1'' !!' with:newName)
                  with:(FileStream lastErrorString)
    ]

    "Modified: 23.4.1997 / 13:19:12 / cg"
!

doFileGet:viaDoubleClick
    "get selected file - show contents in subView.
     This is invoked either by the 'get file' menu item, or via double click.
     When invoked via the menu (viaDoubleClick argument is false),
     the automatic file action is not performed - instead, the file is always
     shown in the codeView (if possible).
     This distinction was done to allow xpm or xbm files (which ahve an automatic
     action) to be edited."

    |fileName iconLbl winLbl|

    self withReadCursorDo:[
        fileName := self getSelectedFileName.
        fileName notNil ifTrue:[
            (currentDirectory isDirectory:fileName) ifTrue:[
                self doChangeCurrentDirectoryTo:fileName updateHistory:true.
                winLbl := myName.
                iconLbl := myName
            ] ifFalse:[
                (currentDirectory exists:fileName) ifFalse:[
                    self warn:(resources string:'oops, ''%1'' is gone' with:fileName).
                    ^ self
                ].
                timeOfFileRead := currentDirectory timeOfLastChange:fileName.
                self showFile:fileName insert:false encoding:fileEncoding doubleClick:viaDoubleClick.
                currentFileName := fileName.

                self fileTypeSpecificActions.

                subView acceptAction:[:theCode |
                    self withCursor:(Cursor write) do:[
                        self writeFile:fileName text:theCode encoding:fileEncoding.
                        timeOfFileRead := currentDirectory timeOfLastChange:fileName.
                        self label:myName , ': ' , currentFileName
                    ]
                ].

                winLbl := myName , ': ' , fileName.
                (currentDirectory isWritable:fileName) ifFalse:[
                    winLbl := winLbl , ' (readonly)'
                ].
                iconLbl := fileName
            ].
            self label:winLbl.
            self iconLabel:iconLbl.
        ]
    ]

    "Created: 19.6.1996 / 09:39:07 / cg"
    "Modified: 23.4.1997 / 13:19:01 / cg"
!

doRemove
    "remove the selected file(s) - no questions asked"

    |ok msg dir idx needUpdate toRemove updateRunning|

    updateRunning := listUpdateProcess notNil.
    self stopUpdateProcess.
    toRemove := OrderedCollection new.

    "/
    "/ did the directory change in the meanwhile ?
    "/
    needUpdate := (currentDirectory timeOfLastChange > timeOfLastCheck).

    lockUpdate := true.
    [
        self selectedFilesDo:[:fileName |
            ok := false.
            (currentDirectory isDirectory:fileName) ifTrue:[
                dir := FileDirectory directoryNamed:fileName in:currentDirectory.
                dir isEmpty ifTrue:[
                    ok := currentDirectory removeDirectory:fileName
                ] ifFalse:[
                    (self 
                        ask:(resources string:'directory ''%1'' is not empty\remove anyway ?' with:fileName)
                        yesButton:'remove')
                    ifFalse:[
                        ^ self
                    ].
                    ok := currentDirectory removeDirectory:fileName
                ].
            ] ifFalse:[
                ok := currentDirectory remove:fileName.
            ].
            ok ifFalse:[
                "was not able to remove it"
                msg := (resources string:'cannot remove ''%1'' !!' with:fileName).
                self showAlert:msg with:(OperatingSystem lastErrorString)
            ] ifTrue:[
"
                self show:nil
"
                idx := fileList indexOf:fileName.
                idx ~~ 0 ifTrue:[
                    toRemove add:idx.
                ]
            ]
        ].
    ] valueNowOrOnUnwindDo:[
        lockUpdate := false.
        fileListView setSelection:nil.

        "/
        "/ remove reverse - otherwise indices are wrong
        "/
        toRemove sort.
        toRemove reverseDo:[:idx |
            fileList removeIndex:idx.
            fileListView removeIndex:idx.
        ].

        updateRunning ifTrue:[
            self updateCurrentDirectory
        ] ifFalse:[
            "
             install a new check after some time
            "
            needUpdate ifFalse:[timeOfLastCheck := AbsoluteTime now].
            Processor addTimedBlock:checkBlock afterSeconds:checkDelta
        ]
    ]

    "Modified: 19.4.1997 / 14:03:55 / cg"
!

doRename:oldName to:newName
    "rename file(s) (or directories)"

    (oldName notNil and:[newName notNil]) ifTrue:[
        (oldName isBlank or:[newName isBlank]) ifFalse:[
            currentDirectory renameFile:oldName newName:newName.
            self updateCurrentDirectoryIfChanged.
        ]
    ]

    "Modified: 23.4.1997 / 13:19:37 / cg"
! !

!FileBrowser methodsFor:'private - file type & info'!

fileCommentStrings
    "return a useful comment definition; based upon the fileName for now"

    "/ for now,
    "/ define comment strings, by heuristics;
    "/ (should look for some mode= or similar string
    "/  found in the file itself - like emacs does it)

    (currentFileName = 'Make.proto'
    or:[currentFileName = 'Makefile'
    or:[currentFileName = 'makefile']]) ifTrue:[
        ^ #('#' (nil nil)).
    ].
    ((currentFileName endsWith:'.c')
    or:[(currentFileName endsWith:'.C')]) ifTrue:[
        ^ #(nil ('/*' '*/')).
    ].
    ((currentFileName endsWith:'.cc')
    or:[(currentFileName endsWith:'.CC')]) ifTrue:[
        ^ #('//' ('/*' '*/')).
    ].
    (currentFileName endsWith:'.java') ifTrue:[
        ^ #('//' (nil nil)).
    ].

    "/ smalltalk comments

    ^ #('"/' ('"' '"')).

    "Created: 7.1.1997 / 20:30:00 / cg"
    "Modified: 23.4.1997 / 13:11:49 / cg"
!

fileTypeSpecificActions
    "any special fileTypeSpecific actions are done here,
     when a new file is selected"

    |commentStrings|

    commentStrings := self fileCommentStrings.
    commentStrings notNil ifTrue:[
        subView
            commentStrings:#('#' (nil nil)).
    ].

    "Modified: 7.1.1997 / 20:30:54 / cg"
!

getFileInfoString:longInfo
    "get stat info on selected file - return a string which can be
     shown in a box"

    |fileName f fullPath text info fileOutput type modeBits modeString s ts|

    fileName := self getSelectedFileName.
    fileName isNil ifTrue:[^ nil].

    f := currentDirectory pathName asFilename construct:fileName.
    info := f info.

"/    info := currentDirectory infoOf:fileName.
    info isNil ifTrue:[
        self showAlert:(resources string:'cannot get info of ''%1'' !!' with:fileName)
                  with:(OperatingSystem lastErrorString).
        ^ nil
    ].

    text := StringCollection new.
    f isSymbolicLink ifTrue:[
        text add:(resources string:'symbolic link to: %1' with:(f linkInfo path))
    ].

    type := info type.
    (longInfo and:[type == #regular]) ifTrue:[
        fullPath := currentDirectory pathName , '/' , fileName.
        fileOutput := fullPath asFilename fileType.
    ].

    s := (resources at:'type:   ').
    fileOutput isNil ifTrue:[
        s := s ,  type asString
    ] ifFalse:[
        s := s , 'regular (' , fileOutput , ')'
    ].
    text add:s.
    text add:(resources string:'size:   %1' with:(info size) printString).

    modeBits := info mode.
    modeString := self getModeString:modeBits.
    longInfo ifTrue:[
        text add:(resources string:'access: %1 (%2)'
                              with:modeString 
                              with:(modeBits printStringRadix:8))
    ] ifFalse:[
        text add:(resources string:'access: %1' with:modeString)
    ].
    text add:(resources string:'owner:  %1'
                          with:(OperatingSystem getUserNameFromID:(info uid))).
    longInfo ifTrue:[
        text add:(resources string:'group:  %1'
                              with:(OperatingSystem getGroupNameFromID:(info gid))).

        ts := info accessed.
        text add:(resources string:'last access:       %1 %2' 
                              with:(ts asTime printString)
                              with:(ts asDate printString)).

        ts := info modified.
        text add:(resources string:'last modification: %1 %2'
                              with:(ts asTime printString)
                              with:(ts asDate printString)).
    ].
    ^ text asString

    "Modified: 8.9.1995 / 11:59:28 / claus"
    "Modified: 1.11.1996 / 20:47:52 / cg"
!

getInfoFile
    "get filename of a description-file (.dir.info, README etc.);
     This file is automatically shown when a directory is enterred.
     You can add more names below if you like."

    #( 
       '.dir.info'
       'README'
       'ReadMe'
       'Readme'
       'readme'
       'read.me'
       'Read.me'
       'READ.ME'
    ) do:[:f |
        (currentDirectory isReadable:f) ifTrue:[
            (currentDirectory isDirectory:f) ifFalse:[^ f].
        ]
    ].
    ^ nil

    "Modified: 23.4.1997 / 13:12:36 / cg"
!

getModeString:modeBits
    "convert file-mode bits into a more user-friendly string.
     This is wrong here - should be moved into OperatingSystem."

    ^ self getModeString:modeBits 
                    with:#( 'owner:' $r $w $x 
                            ' group:' $r $w $x 
                            ' others:' $r $w $x )
!

getModeString:modeBits with:texts
    "convert file-mode bits into a more user-friendly string.
     This is wrong here - should be moved into OperatingSystem."

    |bits modeString|

    bits := modeBits bitAnd:8r777.
    modeString := ''.

    #( nil 8r400 8r200 8r100 nil 8r040 8r020 8r010 nil 8r004 8r002 8r001 ) 
    with: texts do:[:bitMask :access |
        |ch|

        bitMask isNil ifTrue:[
            modeString := modeString , (resources string:access)
        ] ifFalse:[
            (bits bitAnd:bitMask) == 0 ifTrue:[
                ch := $-
            ] ifFalse:[
                ch := access
            ].
            modeString := modeString copyWith:ch 
        ]
    ].
    ^ modeString
!

showInfo
    "show directory info when dir has changed"

    |info txt|

    info := self getInfoFile.
    info notNil ifTrue:[
        txt := self readFile:info
    ].
    self show:txt.
!

sizePrintString:size
    "helper for update-directory to return a string with a files size.
     This one gives the size in byte, Kb or Mb depending on size.
     If you dont like this, just uncomment the first statement below."

    |unitString n|

"
    ^ size printString.
"
    unitString := ''.
    size < (500 * 1024) ifTrue:[
        size < 1024 ifTrue:[
            n := size
        ] ifFalse:[
            n := (size * 10 // 1024 / 10.0).
            unitString := ' Kb'
        ]
    ] ifFalse:[
        n := (size * 10 // 1024 // 1024 / 10.0).
        unitString := ' Mb'
    ].
    ^ (n printStringLeftPaddedTo:5) , unitString.
! !

!FileBrowser methodsFor:'private - file-I/O'!

readFile:fileName
    "read in the file, answer its contents as StringCollection"

    ^ self readFile:fileName lineDelimiter:Character cr encoding:nil

    "Modified: 22.2.1996 / 14:57:08 / cg"
!

readFile:fileName lineDelimiter:aCharacter encoding:encoding
    "read in the file, return its contents as StringCollection. 
     The files lines are delimited by aCharacter.
     If encoding is nonNil, the file is assumed to be coded according to
     that symbol, and #decodeString: should be able to convert it."

    |stream text msg sz|

    stream := FileStream readonlyFileNamed:fileName in:currentDirectory.
    stream isNil ifTrue:[
        msg := (resources string:'cannot read file ''%1'' !!' with:fileName).
        self showAlert:msg with:(FileStream lastErrorString).
        ^ nil
    ].

    "
     for very big files, give ObjectMemory a hint, to preallocate more
    "
    (sz := stream size) > 1000000 ifTrue:[
        Processor activeProcess withPriority:Processor userBackgroundPriority do:[
            ObjectMemory announceSpaceNeed:(sz + (sz // 5)) "/ add 20% for tab expansion
        ].
    ].

    text := self readStream:stream lineDelimiter:aCharacter encoding:encoding.
    stream close.
    ^ text

    "Created: 22.2.1996 / 14:56:48 / cg"
    "Modified: 8.10.1996 / 21:01:57 / cg"
!

readStream:aStream
    "read in from aStream, answer its contents as StringCollection"

    ^ self readStream:aStream lineDelimiter:Character cr encoding:nil

    "Modified: 22.2.1996 / 14:58:40 / cg"
!

readStream:aStream lineDelimiter:aCharacter encoding:encoding 
    "read from aStream, answer its contents as StringCollection. 
     The files lines are delimited by aCharacter.
     If encoding is nonNil, the file is assumed to be coded according to
     that symbol, and #decodeString: should be able to convert it."

    |text line enc|

    text := StringCollection new.

    enc := encoding.
    enc == #iso8859 ifTrue:[
        enc := nil
    ].

    aCharacter == Character cr ifTrue:[
        [aStream atEnd] whileFalse:[
            line := aStream nextLine withTabsExpanded.
            enc notNil ifTrue:[
                line := line decodeFrom:enc
            ].
            text add:line
        ].
    ] ifFalse:[
        [aStream atEnd] whileFalse:[
            line := (aStream upTo:aCharacter) withTabsExpanded.
            enc notNil ifTrue:[
                line := line decodeFrom:enc
            ].
            text add:line
        ].
    ].
    ^ text

    "Created: 22.2.1996 / 14:58:25 / cg"
    "Modified: 2.4.1997 / 21:31:36 / cg"
!

showFile:fileName
    "show contents of fileName in subView"

    self showFile:fileName insert:false encoding:fileEncoding

    "Modified: 22.2.1996 / 14:47:10 / cg"
!

showFile:fileName insert:insert encoding:encoding
    "show/insert contents of fileName in subView"

    ^ self 
        showFile:fileName insert:insert encoding:encoding doubleClick:false

    "Modified: 19.6.1996 / 09:40:19 / cg"
!

showFile:fileName insert:insert encoding:encoding doubleClick:viaDoubleClick
    "show/insert contents of fileName in subView"

    |buffer s n i ok convert text msg eol guess action enc|

    ((currentDirectory typeOf:fileName) == #regular) ifFalse:[
        "asked for a non-file  - ignore it ..."
        (currentDirectory exists:fileName) ifFalse:[
            msg := '''%1'' does not exist !!'.
        ] ifTrue:[
            msg := '''%1'' is not a regular file !!'.
        ].
        self warn:(resources string:msg with:fileName).
        ^ self
    ].

    "/
    "/ check if file is a text file
    "/
    s := FileStream readonlyFileNamed:fileName in:currentDirectory.
    s isNil ifTrue:[
        self showAlert:(resources string:'cannot read file ''%1'' !!' with:fileName)
                  with:(FileStream lastErrorString).
        ^ nil
    ].

    buffer := String new:300.
    n := s nextBytes:300 into:buffer.
    s close.

    enc := encoding.
    ok := true.
    guess := self guessEncodingFrom:buffer.

    guess == #binary ifTrue:[
        ok := false.
        viaDoubleClick ifTrue:[
            (self binaryFileAction:fileName) ifTrue:[^ self].
        ].
        (self confirm:(resources string:'''%1'' seems to be a binary file - show anyway ?' with:fileName))
        ifFalse:[^ self]
    ] ifFalse:[
        viaDoubleClick ifTrue:[
            (self nonBinaryFileAction:fileName) ifTrue:[^ self].
        ].

        "/ ascii should work in any font ...

        guess ~~ #ascii ifTrue:[
            fileEncoding ~~ guess ifTrue:[
                action := Dialog choose:(resources string:'''%1'' seems to be ' , guess , ' encoded.' with:fileName)
                               labels:(resources array:#('cancel' 'show' 'change font'))
                               values:#(nil #show #encoding)
                               default:#encoding.
                action isNil ifTrue:[^ self].
                action == #encoding ifTrue:[
                    fileEncoding := guess asSymbol.
                    self validateFontEncodingFor:fileEncoding ask:false.
                    enc := fileEncoding.
                ]
            ]    
        ].
    ].

    convert := false.
    ok ifTrue:[
        "/
        "/ check if line delimiter is a cr
        "/
        i := buffer indexOf:Character cr.
        i == 0 ifTrue:[
            "/
            "/ no newline found - try cr
            "/
            i := buffer indexOf:(Character value:13).
            i ~~ 0 ifTrue:[
                convert := self confirm:(resources string:'''%1'' seems to have CR as line delimiter - convert to NL ?' with:fileName).
            ]
        ]
    ].

    insert ifFalse:[
        "/ release old text first 
        "/ - we might need the memory in case of huge files
        "/  (helps if you have a 4Mb file in the view, 
        "/   and click on another biggy)

        subView contents:nil.
    ].

    convert ifTrue:[
        eol := Character value:13
    ] ifFalse:[
        eol := Character cr
    ].
    text := self readFile:fileName lineDelimiter:eol encoding:enc.

    insert ifFalse:[
        self show:text
    ] ifTrue:[
        subView insertSelectedStringAtCursor:text asString
    ].

    "Created: 19.6.1996 / 09:39:52 / cg"
    "Modified: 23.1.1997 / 20:31:43 / cg"
!

writeFile:fileName text:someText encoding:encoding
    |stream msg startNr nLines string|

    stream := FileStream newFileNamed:fileName in:currentDirectory.
    stream isNil ifTrue:[
        msg := (resources string:'cannot write file ''%1'' !!' with:fileName).
        self showAlert:msg with:(FileStream lastErrorString)
    ] ifFalse:[
        someText isString ifTrue:[
            stream nextPutAll:someText.
        ] ifFalse:[
            "
             on some systems, writing linewise is very slow (via NFS)
             therefore we convert to a string and write it in chunks
             to avoid creating huge strings, we do it in blocks of 1000 lines
            "
            startNr := 1.
            nLines := someText size.
            [startNr <= nLines] whileTrue:[
                string := someText asStringWithCRsFrom:startNr
                                                    to:((startNr + 1000) min:nLines)
                                          compressTabs:compressTabs.
                encoding notNil ifTrue:[
                    string := string encodeInto:encoding
                ].
                stream nextPutAll:string.
                startNr := startNr + 1000 + 1.
            ].
"/                someText do:[:line |
"/                  line notNil ifTrue:[
"/                      stream nextPutAll:line.
"/                  ].
"/                  stream cr.
"/              ]
        ].
        stream close.
        subView modified:false
    ]

    "Created: 22.2.1996 / 15:03:10 / cg"
    "Modified: 22.2.1996 / 15:08:31 / cg"
! !

!FileBrowser methodsFor:'private - presentation'!

defineTabulatorsForLongList
    "define the tabs for the long list"

    tabSpec := TabulatorSpecification new.
    tabSpec unit:#inch.
"/  tabSpec positions:#(0     0.25    2.3   4.3    5.3    6.0      6.5).
    tabSpec widths:   #(0.25   2      2.0     1      0.5  0.5      1"any").
    "                   icon  name   mode  owner  group  size     type"
    tabSpec align:    #(#left #left  #left #right #right #decimal #left).
    tabSpec addDependent:self.

    tabRulerView tabulatorSpecification:tabSpec.

    "Modified: 17.4.1997 / 02:56:07 / cg"
!

defineTabulatorsForShortList
    "define the tabs for the short list"

    tabSpec := TabulatorSpecification new.
    tabSpec unit:#inch.
"/  tabSpec positions:#(0     0.25 ).
    tabSpec widths:   #(0.25   2   ).
    "                   icon  name"
    tabSpec align:    #(#left #left).
    tabSpec addDependent:self.

    tabRulerView tabulatorSpecification:tabSpec.

    "Created: 17.4.1997 / 02:51:41 / cg"
    "Modified: 17.4.1997 / 02:55:17 / cg"
!

iconForFile:aFilenameString
    "given a fileName, return an appropriate icon"

    |f suff i key|

    f := currentDirectory asFilename construct:aFilenameString.
    f isDirectory ifTrue:[
        f isSymbolicLink ifTrue:[
            key := #directoryLink
        ] ifFalse:[
            key := #directory.
            (f isReadable not
            or:[f isExecutable not]) ifTrue:[
                key := #directoryLocked
            ].
        ]
    ] ifFalse:[
        f isSymbolicLink ifTrue:[
            key := #fileLink
        ] ifFalse:[
            key := #file.
            (f isReadable not) ifTrue:[
                key := #fileLocked
            ] ifFalse:[
                (Image isImageFileSuffix:(f suffix)) ifTrue:[
                    key := #imageFile
                ]
            ].
        ].
    ].

    icons isNil ifTrue:[
        icons := IdentityDictionary new
    ].

    i := icons at:key ifAbsent:nil.
    i isNil ifTrue:[
        i := Icons at:key ifAbsent:nil.
        i notNil ifTrue:[
            i := i on:device.
            icons at:key put:i.
        ]
    ].
    ^ i

    "Modified: 18.4.1997 / 15:18:38 / cg"
!

stopUpdateProcess
    Processor removeTimedBlock:checkBlock.
    listUpdateProcess notNil ifTrue:[
        listUpdateProcess terminate.
        listUpdateProcess := nil.
    ].

    "Created: 19.4.1997 / 13:51:34 / cg"
!

updateCurrentDirectory
    "update listView with directory contents"

    "the code below may look somewhat complex -
     it reads the directory first for the names,
     then (in followup sweeps over the files) gets the
     files type, info and icon in a forked subprocess. 
     This makes the Filebrowsers list update faster, since the fileInfo 
     (i.e. stat-calls) may take long - especially on NFS-mounted directories.
     The file reading is done at lower priority, to let user continue
     his work in other views. However, to be fair to other fileBrowser,
     which may also read directories at low prio, give up the processor
     after every entry. This shares the cpu among all fileBrowsers;
     Therefore, browsers which read short directories will finish first.
     ST/X users love this behavior ;-)
    "

    self withReadCursorDo:[
        |files matchPattern|

        self stopUpdateProcess.

        timeOfLastCheck := AbsoluteTime now.

        files := currentDirectory asOrderedCollection.

        "/ show files which are either directories
        "/ or match the current pattern

        matchPattern := filterField contents.
        (matchPattern notNil and:[
         matchPattern isEmpty not and:[
         matchPattern ~= '*']]) ifTrue:[
             files := files select:[:aName | 
                         ((currentDirectory typeOf:aName) == #directory)
                         or:[matchPattern compoundMatch:aName]
                      ].
        ].

        files sort.

        files size == 0 ifTrue:[
            self information:('directory ', currentDirectory pathName, ' vanished').
            ^ self
        ].
        files := self withoutHiddenFiles:files.
        fileList := files copy.

        "
         this is a time consuming operation (especially, if reading an
         NFS-mounted directory); therefore, start a low prio process,
         which fills in the remaining fields in the fileList ...
        "

        listUpdateProcess := [
            |prevUid prevGid fileNameString nameString groupString 
             modeString info line len list
             anyImages passDone lineIndex aFileName
             entry typ f p typeString done endIndex 
             state stopAtEnd nextState img prevFirstLine prevLastLine
             numVisible|

            tabSpec isNil ifTrue:[
                showLongList ifTrue:[
                    self defineTabulatorsForLongList
                ] ifFalse:[
                    self defineTabulatorsForShortList
                ].
            ].

            "/
            "/ first show all the names - this can be done fast ...
            "/
            list := files collect:[:fileName |
                        |entry|

                        entry := MultiColListEntry new.
                        entry tabulatorSpecification:tabSpec.
                        entry colAt:1 put:nil.
                        entry colAt:2 put:fileName.
                    ].

            fileListView setList:list expandTabs:false.
            passDone := Array new:list size withAll:0.

            "/
            "/ then walk over the files, adding more info
            "/ (since we have to stat each file, this may take a while longer)
            "/ Visible items are always filled first.

            "/
            "/ the state machine
            "/
            nextState := IdentityDictionary new.
            showLongList ifTrue:[
                nextState add:(#visibleIcons -> #visibleAttributes).
                nextState add:(#visibleAttributes -> #visibleTypes).
                nextState add:(#visibleTypes -> #visibleImages).
                nextState add:(#visibleImages -> #nextPageIcons).

                nextState add:(#nextPageIcons -> #nextPageAttributes).
                nextState add:(#nextPageAttributes -> #nextPageTypes).
                nextState add:(#nextPageTypes -> #nextPageImages).
                nextState add:(#nextPageImages -> #previousPageIcons).

                nextState add:(#previousPageIcons -> #previousPageAttributes).
                nextState add:(#previousPageAttributes -> #previousPageTypes).
                nextState add:(#previousPageTypes -> #previousPageImages).
                nextState add:(#previousPageImages -> #remainingIcons).

                nextState add:(#remainingIcons -> #remainingAttributes).
                nextState add:(#remainingAttributes -> #remainingTypes).
                nextState add:(#remainingTypes -> #remainingImages).
                nextState add:(#remainingImages -> nil).
            ] ifFalse:[
                nextState add:(#visibleIcons -> #nextPageIcons).
                nextState add:(#nextPageIcons -> #previousPageIcons).
                nextState add:(#previousPageIcons -> #remainingIcons).
                nextState add:(#remainingIcons -> nil).
            ].

            anyImages := false.

            lineIndex := prevFirstLine := fileListView firstLineShown.
            endIndex := prevLastLine := fileListView lastLineShown.
            endIndex := endIndex min:(files size).
            state := #visibleIcons.

            done := false.
            [done] whileFalse:[
                "/
                "/ if multiple FileBrowsers are reading, let others
                "/ make some progress too
                "/
                Processor yield.

                "/
                "/ could be destroyed in the meanwhile ...
                "/
                realized ifFalse:[
                    listUpdateProcess := nil.
                    Processor activeProcess terminate
                ].

                ((prevFirstLine ~~ fileListView firstLineShown)
                or:[prevLastLine ~~ fileListView lastLineShown]) ifTrue:[
                    "/ start all over again
                    lineIndex := prevFirstLine := fileListView firstLineShown.
                    endIndex := prevLastLine := fileListView lastLineShown.
                    endIndex := endIndex min:(files size).
                    state := #visibleIcons.
                ].

                (lineIndex between:1 and:(files size)) ifTrue:[

                    "/
                    "/ expand the next entry ...
                    "/
                    aFileName := files at:lineIndex.
                    entry := fileListView at:lineIndex.

                    (state endsWith:'Icons') ifTrue:[
                        "/
                        "/ pass 1 - icons
                        "/
                        (passDone at:lineIndex) < 1 ifTrue:[
                            ((currentDirectory isDirectory:aFileName) and:[
                            (aFileName ~= '..') and:[aFileName ~= '.']]) ifTrue:[
                                fileNameString := aFileName , ' ...'
                            ] ifFalse:[
                                fileNameString := aFileName
                            ].

                            showLongList ifTrue:[
                                len := fileNameString size.
                                (len > 20) ifTrue:[
                                    fileNameString := (fileNameString contractTo:20)
                                ].
                            ].

                            entry colAt:1 put:(self iconForFile:aFileName).
                            entry colAt:2 put:fileNameString.

                            fileListView at:lineIndex put:entry.

                            anyImages ifFalse:[
                                (Image isImageFileSuffix:(aFileName asFilename suffix))
                                ifTrue:[
                                    anyImages := true
                                ]
                            ].
                            passDone at:lineIndex put:1
                        ]
                    ].

                    (state endsWith:'Attributes') ifTrue:[
                        "/
                        "/ pass 2 - everything except fileType (which takes very long)
                        "/
                        (passDone at:lineIndex) < 2 ifTrue:[

                            info := currentDirectory infoOf:aFileName.
                            info isNil ifTrue:[
                                "not accessable - usually a symlink,
                                 to a nonexisting/nonreadable file
                                "
                                f := currentDirectory asFilename:aFileName.
                                f isSymbolicLink ifTrue:[
                                    p := f linkInfo path.    
                                    typeString := 'broken symbolic link to ' , p
                                ] ifFalse:[
                                    typeString := 'unknwon (bad symbolic link ?)'
                                ].
                                entry colAt:7 put:typeString.
                            ] ifFalse:[
                                typ := (info type).

                                modeString := self getModeString:(info at:#mode)
                                                            with:#( '' $r $w $x 
                                                                    '  ' $r $w $x 
                                                                    '  ' $r $w $x ).
                                entry colAt:3 put:modeString.

                                ((info uid) ~~ prevUid) ifTrue:[
                                    prevUid := (info uid).
                                    nameString := OperatingSystem getUserNameFromID:prevUid.
                                    nameString := nameString , (String new:(10 - nameString size))
                                ].
                                entry colAt:4 put:nameString withoutSpaces.

                                ((info gid) ~~ prevGid) ifTrue:[
                                    prevGid := (info gid).
                                    groupString := OperatingSystem getGroupNameFromID:prevGid.
                                    groupString := groupString , (String new:(10 - groupString size))
                                ].
                                entry colAt:5 put:groupString withoutSpaces.

                                (typ == #regular) ifTrue:[
                                    entry colAt:6 put:(self sizePrintString:(info size)).
                                ].

                                f := currentDirectory asFilename:aFileName.
                                f isSymbolicLink ifTrue:[
                                    p := f linkInfo path.    
                                    typeString := 'symbolic link to ' , p
                                ] ifFalse:[
                                    typeString := typ asString
                                ].
                                entry colAt:7 put:typeString
                            ].
                            fileListView at:lineIndex put:entry.
                            passDone at:lineIndex put:2.
                        ].
                    ].

                    (state endsWith:'Types') ifTrue:[
                        "/
                        "/ pass 3: add fileType
                        "/
                        (passDone at:lineIndex) < 3 ifTrue:[
                            info := currentDirectory infoOf:aFileName.
                            info notNil ifTrue:[
                                f := currentDirectory asFilename:aFileName.
                                f isSymbolicLink ifFalse:[
                                    (Image isImageFileSuffix:(f suffix)) ifFalse:[
                                        typeString := f fileType.

                                        entry colAt:7 put:typeString.
                                        fileListView at:lineIndex put:entry
                                    ].
                                ].
                            ].

                            passDone at:lineIndex put:3
                        ].
                    ].

                    (state endsWith:'Images') ifTrue:[
                        "/
                        "/ pass 4: read images
                        "/
                        (passDone at:lineIndex) < 4 ifTrue:[
                            f := currentDirectory asFilename construct:aFileName.
                            (Image isImageFileSuffix:(f suffix)) ifTrue:[
                                f isDirectory ifFalse:[
                                    img := Image fromFile:(f pathName).
                                    img notNil ifTrue:[
                                        img := img magnifiedTo:16@16.
                                        img := img on:self device.
                                        entry colAt:7 put:img.
                                        fileListView at:lineIndex put:entry
                                    ]
                                ]
                            ].
                            passDone at:lineIndex put:4
                        ].
                    ].
                ].

                "/
                "/ advance to the next line
                "/
                lineIndex := lineIndex + 1.
                lineIndex > endIndex ifTrue:[
                    "/ finished this round ...
                    "/ see what we are going for ...
                    numVisible := (fileListView lastLineShown - fileListView firstLineShown + 1).

                    state := nextState at:state ifAbsent:nil.

                    state isNil ifTrue:[
                        done := true
                    ] ifFalse:[
                        (state startsWith:'visible') ifTrue:[
                            lineIndex := fileListView firstLineShown.
                            endIndex := fileListView lastLineShown.
                            endIndex := endIndex min:(files size).
                        ] ifFalse:[
                            (state startsWith:'nextPage') ifTrue:[
                                lineIndex := fileListView lastLineShown + 1.
                                endIndex := lineIndex + numVisible.
                                endIndex := endIndex min:(files size).
                                lineIndex := lineIndex min:(files size).
                            ] ifFalse:[
                                (state startsWith:'previousPage') ifTrue:[
                                    endIndex := fileListView firstLineShown - 1.
                                    lineIndex := endIndex - numVisible.
                                    lineIndex := lineIndex max:1.
                                    endIndex := endIndex min:(files size).
                                    endIndex := endIndex max:1.
                                ] ifFalse:[ 
                                    "/ remaining
                                    lineIndex := 1.
                                    endIndex := files size.
                                ]
                            ]
                        ]
                    ]
                ]
            ].

            listUpdateProcess := nil.

        ] forkAt:(Processor activePriority - 1).

        "
         install a new check after some time
        "
        Processor addTimedBlock:checkBlock afterSeconds:checkDelta
    ]

    "Modified: 21.9.1995 / 11:40:23 / claus"
    "Modified: 21.4.1997 / 15:01:27 / cg"
! !

!FileBrowser methodsFor:'queries'!

path
    "return my currentDirectories pathName;
     sent from the pathField label to aquire pathname when I changed directory"

    ^ currentDirectory pathName
! !

!FileBrowser class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libtool/Attic/FBrowser.st,v 1.152 1997-04-23 11:30:25 cg Exp $'
! !
FileBrowser initialize!