mostly filename changes
authorClaus Gittinger <cg@exept.de>
Mon, 15 Sep 1997 23:22:40 +0200
changeset 1317 da5150d4d2ec
parent 1316 3fefcc2e9b16
child 1318 4e11a4c48ace
mostly filename changes
FBrowser.st
FileBrowser.st
--- a/FBrowser.st	Mon Sep 15 23:06:52 1997 +0200
+++ b/FBrowser.st	Mon Sep 15 23:22:40 1997 +0200
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1991 by Claus Gittinger
-              All Rights Reserved
+	      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
@@ -30,7 +30,7 @@
 copyright
 "
  COPYRIGHT (c) 1991 by Claus Gittinger
-              All Rights Reserved
+	      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
@@ -54,27 +54,27 @@
     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.
+	     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
+	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
+	Claus Gittinger
 "
 ! !
 
@@ -100,7 +100,7 @@
 
     f := aFilename asFilename.
     f isDirectory ifTrue:[
-        ^ self openOn:aFilename
+	^ self openOn:aFilename
     ].
     browser := self new.
     browser currentDirectory:f directoryName.
@@ -126,27 +126,27 @@
     Icons := IdentityDictionary new.
 
     #(
-        (#directory       'ICON_DIRECTORY'        'tiny_yellow_dir.xpm'       )
-        (#directoryLocked 'ICON_DIRECTORY_LOCKED' 'tiny_yellow_dir_locked.xpm')
-        (#directoryLink   'ICON_DIRECTORY_LINK'   'tiny_yellow_dir_link.xpm'  )
-        (#file            'ICON_FILE'             'tiny_file_plain.xpm'       )
-        (#fileLink        'ICON_FILE_LINK'        'tiny_file_link.xpm'        )
-        (#fileLocked      'ICON_FILE_LOCKED'      'tiny_file_lock.xpm'        )
-        (#imageFile       'ICON_IMAGE_FILE'       'tiny_file_pix.xpm'         )
-        (#textFile        'ICON_TEXT_FILE'        'tiny_file_text.xpm'         )
+	(#directory       'ICON_DIRECTORY'        'tiny_yellow_dir.xpm'       )
+	(#directoryLocked 'ICON_DIRECTORY_LOCKED' 'tiny_yellow_dir_locked.xpm')
+	(#directoryLink   'ICON_DIRECTORY_LINK'   'tiny_yellow_dir_link.xpm'  )
+	(#file            'ICON_FILE'             'tiny_file_plain.xpm'       )
+	(#fileLink        'ICON_FILE_LINK'        'tiny_file_link.xpm'        )
+	(#fileLocked      'ICON_FILE_LOCKED'      'tiny_file_lock.xpm'        )
+	(#imageFile       'ICON_IMAGE_FILE'       'tiny_file_pix.xpm'         )
+	(#textFile        'ICON_TEXT_FILE'        'tiny_file_text.xpm'         )
 
      ) do:[:entry |
-        |key resource defaultName nm|
-
-        key := entry at:1.
-        resource := entry at:2.
-        defaultName := entry at:3.
-
-        nm := resources at:resource default:nil.
-        nm isNil ifTrue:[
-            nm := 'bitmaps/xpmBitmaps/document_images/' , defaultName
-        ].
-        Icons at:key put:(Image fromFile:nm).
+	|key resource defaultName nm|
+
+	key := entry at:1.
+	resource := entry at:2.
+	defaultName := entry at:3.
+
+	nm := resources at:resource default:nil.
+	nm isNil ifTrue:[
+	    nm := 'bitmaps/xpmBitmaps/document_images/' , defaultName
+	].
+	Icons at:key put:(Image fromFile:nm).
     ]
 
     "
@@ -162,22 +162,22 @@
     |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.
-            ]
-        ]
+	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"
@@ -193,21 +193,21 @@
     |nm i res|
 
     (i := DefaultIcon) isNil ifTrue:[
-        res := self classResources.
-        i := res at:'FILEBROWSER_ICON' default:nil.
-        i isNil ifTrue:[
-            nm := res at:'FILEBROWSER_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
-        ]
+	res := self classResources.
+	i := res at:'FILEBROWSER_ICON' default:nil.
+	i isNil ifTrue:[
+	    nm := res at:'FILEBROWSER_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
 
@@ -221,9 +221,9 @@
     "I accept fileObjects only"
 
     aCollectionOfDropObjects do:[:aDropObject |
-        aDropObject isFileObject ifFalse:[
-            aDropObject isTextObject ifFalse:[^ false].
-        ]
+	aDropObject isFileObject ifFalse:[
+	    aDropObject isTextObject ifFalse:[^ false].
+	]
     ].
     ^ true
 
@@ -234,7 +234,7 @@
     "handle drops"
 
     aCollectionOfDropObjects do:[:aDropObject |
-        self dropSingleObject:aDropObject at:aPoint
+	self dropSingleObject:aDropObject at:aPoint
     ]
 
     "Modified: 11.4.1997 / 12:43:36 / cg"
@@ -248,30 +248,30 @@
     |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 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
+	subView paste:someObject theObject.
+	^ self
     ].
 
     "Modified: 6.4.1997 / 14:46:44 / cg"
@@ -286,14 +286,14 @@
     <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].
+	(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
 
@@ -308,32 +308,32 @@
     <resource: #keyboard (#GotoLine #InspectIt #CmdI #Cmdu #DoIt #Delete #BackSpace #Accept)>
 
     (key == #Delete or:[key == #BackSpace]) ifTrue:[
-        self fileRemove.
-        ^ self
+	self fileRemove.
+	^ self
     ].
     (key == #Accept) ifTrue:[
-        self fileFileIn.
-        ^ self
+	self fileFileIn.
+	^ self
     ].
     (key == #GotoLine) ifTrue:[
-        self fileGet.
-        ^ self
+	self fileGet.
+	^ self
     ].
     (key == #DoIt) ifTrue:[
-        self fileExecute.
-        ^ self
+	self fileExecute.
+	^ self
     ].
     (key == #InspectIt) ifTrue:[
-        self fileGetInfo.
-        ^ self
+	self fileGetInfo.
+	^ self
     ].
     (key == #CmdI) ifTrue:[
-        self fileGetLongInfo.
-        ^ self
+	self fileGetLongInfo.
+	^ self
     ].
     (key == #Cmdu) ifTrue:[
-        self updateCurrentDirectory.
-        ^ self
+	self updateCurrentDirectory.
+	^ self
     ].
     fileListView keyPress:key x:x y:y
 
@@ -356,11 +356,11 @@
     wasVisible := shown.
     super visibilityChange:how.
     (wasVisible not and:[shown]) ifTrue:[
-        "
-         start checking again
-        "
-        Processor removeTimedBlock:checkBlock.
-        Processor addTimedBlock:checkBlock afterSeconds:checkDelta.
+	"
+	 start checking again
+	"
+	Processor removeTimedBlock:checkBlock.
+	Processor addTimedBlock:checkBlock afterSeconds:checkDelta.
     ]
 ! !
 
@@ -412,11 +412,11 @@
     dialog open.
 
     dialog accepted ifTrue:[
-        idx := list selectionIndex.
-        fileEncoding := encodings at:idx.
-        subView externalEncoding:fileEncoding.
-
-        self validateFontEncodingFor:fileEncoding ask:true.
+	idx := list selectionIndex.
+	fileEncoding := encodings at:idx.
+	subView externalEncoding:fileEncoding.
+
+	self validateFontEncodingFor:fileEncoding ask:true.
     ].
 
     "Modified: 30.6.1997 / 14:41:12 / cg"
@@ -432,12 +432,12 @@
      this replaces everything by the commands output ...
     "
     action := [:command | 
-                self class addToCommandHistory:command for:fileName.
-                self doExecuteCommand:command replace:true
-              ].
+		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].
+	      yesButton:'execute') ifFalse:[^ self].
 
 "/    "
 "/     this inserts the commands output ...
@@ -447,7 +447,7 @@
 
     sel := fileListView selection.
     sel size == 1 ifTrue:[
-        fileName := fileList at:sel first
+	fileName := fileList at:sel first
     ].
     self askForCommandFor:fileName thenDo:action
 
@@ -472,72 +472,72 @@
     |aStream here oldPath wasLazy bos|
 
     self selectedFilesDo:[:fileName |
-        ((currentDirectory typeOf:fileName) == #regular) ifTrue:[
-            here := currentDirectory pathName.
-
-            (ObjectFileLoader notNil
-            and:[ObjectFileLoader hasValidBinaryExtension:fileName]) ifTrue:[
-                Object abortSignal catch:[
-                    |p|
-
-                    p := here asFilename constructString: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 asFilename constructString: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
-                            ]
-                        ]
-                    ]
-                ]
-            ]
-        ]
+	((currentDirectory typeOf:fileName) == #regular) ifTrue:[
+	    here := currentDirectory pathName.
+
+	    (ObjectFileLoader notNil
+	    and:[ObjectFileLoader hasValidBinaryExtension:fileName]) ifTrue:[
+		Object abortSignal catch:[
+		    |p|
+
+		    p := here asFilename constructString: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 asFilename constructString: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: 29.4.1997 / 21:56:24 / cg"
@@ -561,22 +561,22 @@
     |fileName msg label|
 
     (subView modified not or:[subView contentsWasSaved]) ifTrue:[
-        self doFileGet:viaDoubleClick.
-        ^ self
+	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
-        ]
+	(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"
@@ -596,7 +596,7 @@
 
     string := self getFileInfoString:longInfo.
     string notNil ifTrue:[
-        self information:string
+	self information:string
     ]
 !
 
@@ -613,7 +613,7 @@
 
     fileName := self getSelectedFileName.
     fileName notNil ifTrue:[
-        self showFile:fileName insert:true encoding:fileEncoding
+	self showFile:fileName insert:true encoding:fileEncoding
     ]
 
     "Modified: 23.4.1997 / 13:06:06 / cg"
@@ -627,140 +627,140 @@
     |labels shorties selectors m sel ns subLabels subSelectors|
 
     labels := #(
-                 'spawn'                   
-                 '-'                               
-                 'get contents'                    
-                 'insert contents'                    
-                 'show info'             
-                 'show full info'
-               ).
+		 'spawn'                   
+		 '-'                               
+		 'get contents'                    
+		 'insert contents'                    
+		 'show info'             
+		 'show full info'
+	       ).
 
     ((ns := Project current defaultNameSpace) notNil 
     and:[ns ~~ Smalltalk]) ifTrue:[
-        labels := labels copyWith:'fileIn (into ''' , Project current defaultNameSpace name , ''')'
+	labels := labels copyWith:'fileIn (into ''' , Project current defaultNameSpace name , ''')'
     ] ifFalse:[
-        labels := labels copyWith:'fileIn'
+	labels := labels copyWith:'fileIn'
     ].
 
     labels := labels , #(
-                 '-'                               
-                 'update'                 
-                 '-'                               
-                 'execute unix command ...'                
-                 'st/x tools'                
-                 '-'                               
-                 'remove'                 
-                 'rename ...'                 
-                 '-'                               
-                 'display long list'           
-                 'show all files'           
-                 'encoding ...'           
-                 '-'                               
-                 'create directory ...'         
-                 'create file ...'
-               ).             
+		 '-'                               
+		 '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
-                 nil
-                 updateCurrentDirectory
-                 nil
-                 fileExecute
-                 stxTools
-                 nil
-                 fileRemove
-                 fileRename
-                 nil
-                 changeDisplayMode
-                 changeDotFileVisibility
-                 fileEncoding
-                 nil
-                 newDirectory
-                 newFile
-                ).
+		 fileSpawn
+		 nil
+		 fileGet
+		 fileInsert
+		 fileGetInfo
+		 fileGetLongInfo
+		 fileFileIn
+		 nil
+		 updateCurrentDirectory
+		 nil
+		 fileExecute
+		 stxTools
+		 nil
+		 fileRemove
+		 fileRename
+		 nil
+		 changeDisplayMode
+		 changeDotFileVisibility
+		 fileEncoding
+		 nil
+		 newDirectory
+		 newFile
+		).
 
     shorties := #(
-                 nil
-                 nil
-                 GotoLine
-                 nil
-                 InspectIt
-                 CmdI
-                 Cmdf
-                 nil
-                 nil
-                 Cmdu
-                 nil
-                 DoIt
-                 nil
-                 Delete
-                 nil
-                 nil
-                 nil
-                 nil
-                 nil
-                 nil
-                 nil
-                 nil
-                ).
+		 nil
+		 nil
+		 GotoLine
+		 nil
+		 InspectIt
+		 CmdI
+		 Cmdf
+		 nil
+		 nil
+		 Cmdu
+		 nil
+		 DoIt
+		 nil
+		 Delete
+		 nil
+		 nil
+		 nil
+		 nil
+		 nil
+		 nil
+		 nil
+		 nil
+		).
 
     m := PopUpMenu 
-            labels:(resources array:labels)
-            selectors:selectors
-            accelerators:shorties
-            receiver:self.
+	    labels:(resources array:labels)
+	    selectors:selectors
+	    accelerators:shorties
+	    receiver:self.
 
     showDotFiles ifTrue:[
-        m labelAt:#changeDotFileVisibility put:(resources string:'hide hidden files')
+	m labelAt:#changeDotFileVisibility put:(resources string:'hide hidden files')
     ].
     showLongList ifTrue:[
-        m labelAt:#changeDisplayMode put:(resources string:'display short list')
+	m labelAt:#changeDisplayMode put:(resources string:'display short list')
     ].
 
     subLabels := #(
-                              'Changes browser'
-                              'Editor'
-                              'HTML reader'
-                              'Image inspect'
-                              'show file differences'
-                  ).
+			      'Changes browser'
+			      'Editor'
+			      'HTML reader'
+			      'Image inspect'
+			      'show file differences'
+		  ).
 
     subSelectors := #(
-                              openChangesBrowser
-                              openEditor
-                              openHTMLReader
-                              openImageInspector
-                              openDiffView
-                     ).
+			      openChangesBrowser
+			      openEditor
+			      openHTMLReader
+			      openImageInspector
+			      openDiffView
+		     ).
 
     JavaInterpreter notNil ifTrue:[
-        subLabels := subLabels , #('Java Applet Viewer').
-        subSelectors := subSelectors , #(openAppletViewer).
+	subLabels := subLabels , #('Java Applet Viewer').
+	subSelectors := subSelectors , #(openAppletViewer).
     ].
 
     m subMenuAt:#stxTools 
-            put:(PopUpMenu
-                    labels:(resources array:subLabels)
-                    selectors:subSelectors
-                    receiver:self).
+	    put:(PopUpMenu
+		    labels:(resources array:subLabels)
+		    selectors:subSelectors
+		    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)
+	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 )
-        ]
+	fileListView selection size > 1 ifTrue:[
+	    m disableAll:#( fileGet fileInsert fileGetInfo fileGetLongInfo fileRename )
+	]
     ].
 
     ^m
@@ -775,25 +775,25 @@
     |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"
+	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"
@@ -809,12 +809,12 @@
 
     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]
+	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]
     ]
 !
 
@@ -826,10 +826,10 @@
     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
+	queryBox title:(resources string:'rename ''%1'' to:' with:oldName).
+	queryBox initialText:oldName.
+	queryBox action:[:newName | self doRename:oldName to:newName].
+	queryBox showAtPointer
     ]
 !
 
@@ -849,13 +849,13 @@
 
     any := false.
     self selectedFilesDo:[:fileName |
-        (currentDirectory isDirectory:fileName) ifTrue:[
-            self class openOn:(currentDirectory pathName asFilename constructString:fileName).
-            any := true
-        ]
+	(currentDirectory isDirectory:fileName) ifTrue:[
+	    self class openOn:(currentDirectory pathName asFilename constructString:fileName).
+	    any := true
+	]
     ].
     any ifFalse:[
-        self class openOn:currentDirectory pathName
+	self class openOn:currentDirectory pathName
     ]
 !
 
@@ -865,9 +865,9 @@
     |queryBox|
 
     queryBox := FilenameEnterBox 
-                    title:(resources at:'create new directory:') withCRs
-                    okText:(resources at:'create')
-                    action:[:newName | self doCreateDirectory:newName].
+		    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"
@@ -879,12 +879,12 @@
     |sel queryBox|
 
     queryBox := FilenameEnterBox 
-                    title:(resources at:'create new file:') withCRs
-                    okText:(resources at:'create')
-                    action:[:newName | self doCreateFile:newName].
+		    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 initialText:(sel asString)
     ].
     queryBox showAtPointer
 
@@ -895,9 +895,9 @@
     |numItems|
 
     (numItems := fileListView selection size) > 2 ifTrue:[
-        (self 
-            confirm:(resources string:'open for each of the %1 items ?' 
-                                 with:numItems)) ifFalse:[^ self].
+	(self 
+	    confirm:(resources string:'open for each of the %1 items ?' 
+				 with:numItems)) ifFalse:[^ self].
     ].
 
     JavaInterpreter releaseAllJavaResources.
@@ -906,16 +906,16 @@
     Java initAllClasses.
 
     self selectedFilesDo:[:fileName |
-        |p path|
-
-        (currentDirectory isDirectory:fileName) ifFalse:[
-            path := currentDirectory pathName asFilename constructString:fileName.
-
-            p := Java 
-                    javaProcessForMainOf:(Java classForName:'sun.applet.AppletViewer')
-                    argumentString:path.
-            p resume.
-        ]
+	|p path|
+
+	(currentDirectory isDirectory:fileName) ifFalse:[
+	    path := currentDirectory pathName asFilename constructString:fileName.
+
+	    p := Java 
+		    javaProcessForMainOf:(Java classForName:'sun.applet.AppletViewer')
+		    argumentString:path.
+	    p resume.
+	]
     ].
 
     "Modified: 15.8.1997 / 05:03:02 / cg"
@@ -947,54 +947,54 @@
     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'.
-        ]
+	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"
@@ -1015,14 +1015,14 @@
     |img|
 
     self selectedFilesDo:[:fileName |
-        (currentDirectory isDirectory:fileName) ifFalse:[
-            img := Image fromFile:(currentDirectory pathName asFilename constructString:fileName).
-            img notNil ifTrue:[
-                img inspect
-            ] ifFalse:[
-                self warn:'unknown format: ' , fileName
-            ]
-        ]
+	(currentDirectory isDirectory:fileName) ifFalse:[
+	    img := Image fromFile:(currentDirectory pathName asFilename constructString:fileName).
+	    img notNil ifTrue:[
+		img inspect
+	    ] ifFalse:[
+		self warn:'unknown format: ' , fileName
+	    ]
+	]
     ].
 
     "Modified: 17.9.1995 / 17:41:24 / claus"
@@ -1034,15 +1034,15 @@
     |numItems|
 
     (numItems := fileListView selection size) > 2 ifTrue:[
-        (self 
-            confirm:(resources string:'open for each of the %1 items ?' 
-                                 with:numItems)) ifFalse:[^ self].
+	(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 asFilename constructString:fileName).
-        ]
+	(currentDirectory isDirectory:fileName) ifFalse:[
+	    aToolClass openOn:(currentDirectory pathName asFilename constructString:fileName).
+	]
     ].
 
     "Modified: 14.11.1996 / 16:01:32 / cg"
@@ -1052,17 +1052,17 @@
     "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).
+	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
+	scrollView topInset:0
     ].
     tabSpec := nil.
 
@@ -1075,22 +1075,22 @@
     |s|
 
     aComponent == subView ifTrue:[
-        s := 'HELP_SUBVIEW'
+	s := 'HELP_SUBVIEW'
     ].
     aComponent == fileListView ifTrue:[
-        s := 'HELP_FILELIST'
+	s := 'HELP_FILELIST'
     ].
     aComponent == filterField ifTrue:[
-        s := 'HELP_FILTER'
+	s := 'HELP_FILTER'
     ].
     aComponent == labelView ifTrue:[
-        s := 'HELP_PATHFIELD'
+	s := 'HELP_PATHFIELD'
     ].
     aComponent == commandView ifTrue:[
-        s := 'HELP_COMMANDVIEW'
+	s := 'HELP_COMMANDVIEW'
     ].
     s notNil ifTrue:[
-        ^ resources string:s
+	^ resources string:s
     ].
     ^ nil
 ! !
@@ -1107,7 +1107,7 @@
      (i.e. save-as etc.) in that directory
     "
     (subView respondsTo:#directoryForFileDialog:) ifTrue:[
-        subView directoryForFileDialog:currentDirectory
+	subView directoryForFileDialog:currentDirectory
     ]
 !
 
@@ -1117,12 +1117,12 @@
     |fs|
 
     fs := Array 
-        with:filterField 
-        with:fileListView 
-        with:subView.
+	with:filterField 
+	with:fileListView 
+	with:subView.
 
     commandView notNil ifTrue:[
-        fs := fs copyWith:commandView
+	fs := fs copyWith:commandView
     ].
     ^fs
 !
@@ -1159,13 +1159,13 @@
     lockUpdate := false.
 
     CommandHistory isNil ifTrue:[
-        CommandHistory := OrderedCollection new.
-        CommandHistorySize := 50
+	CommandHistory := OrderedCollection new.
+	CommandHistorySize := 50
     ].
     DirectoryHistory isNil ifTrue:[
-        DirectoryHistory := OrderedCollection new.
-        DirectoryHistoryWhere := OrderedCollection new.
-        HistorySize := 15.
+	DirectoryHistory := OrderedCollection new.
+	DirectoryHistoryWhere := OrderedCollection new.
+	HistorySize := 15.
     ].
     commandIndex := 0.
 
@@ -1173,12 +1173,12 @@
     self label:myName.
 
     labelFrame := View 
-                        origin:(0.0 @ 0.0)
-                        corner:(1.0 @ (font height * 2))
-                        in:self.
+			origin:(0.0 @ 0.0)
+			corner:(1.0 @ (font height * 2))
+			in:self.
 
     styleSheet name = #st80 ifTrue:[
-        labelFrame level:1
+	labelFrame level:1
     ].
 
     spacing := ViewSpacing.
@@ -1197,8 +1197,8 @@
     filterModel := '*' asValue.
     filterField := EditField in:labelFrame.
     filterField 
-        origin:[((width // 4 * 3) + halfSpacing) @ halfSpacing]
-        corner:(1.0 @ (filterField heightIncludingBorder + halfSpacing + halfSpacing) ).
+	origin:[((width // 4 * 3) + halfSpacing) @ halfSpacing]
+	corner:(1.0 @ (filterField heightIncludingBorder + halfSpacing + halfSpacing) ).
     filterField rightInset:halfSpacing.
     filterField model:filterModel.
 
@@ -1208,11 +1208,11 @@
 
     labelView := Label in:labelFrame.
     labelView origin:(halfSpacing @ halfSpacing)
-              extent:[((width // 4 * 3) - spacing - borderWidth)
-                       @
-                       (filterField heightIncludingBorder)
-                       "(font height + font descent)"
-                     ].
+	      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.
@@ -1220,12 +1220,12 @@
 
     killButton := Button label:(resources string:'kill') in:self.
     killButton origin:(halfSpacing @ halfSpacing)
-               extent:(killButton width @ filterField height).
+	       extent:(killButton width @ filterField height).
     killButton beInvisible.
 
     pauseToggle := Toggle label:(resources string:'pause') in:self.
     pauseToggle origin:((killButton corner x + 50) @ halfSpacing)
-                extent:(pauseToggle width @ filterField height).
+		extent:(pauseToggle width @ filterField height).
     pauseToggle beInvisible.
 
     self initializeCommandViewIn:self.
@@ -1242,22 +1242,22 @@
     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)
+	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).
+	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 := TabSpecRuler in:topFrame.
+	tabRulerView origin:(0.0@0.0) corner:(1.0@10).
     ].
     tabRulerView borderWidth:0.
     tabRulerView synchronousOperation:true.
@@ -1269,29 +1269,29 @@
     scrollView scrolledView:fileListView.
     fileListView action:[:lineNr | self fileSelect:lineNr].
     fileListView doubleClickAction:[:lineNr | self fileSelect:lineNr.
-                                              self fileGet:true].
+					      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|
+					|dir nm path idx|
 obj printCR.
-                                        nm := obj theObject asString.
-                                        idx := fileListView list indexOf:nm.
+					nm := obj theObject asString.
+					idx := fileListView list indexOf:nm.
 idx printCR.
-                                        idx == 0 ifTrue:[
-                                            "/ cannot happen ...
-                                            nil
-                                        ] ifFalse:[
-                                            nm := fileList at:idx.
+					idx == 0 ifTrue:[
+					    "/ cannot happen ...
+					    nil
+					] ifFalse:[
+					    nm := fileList at:idx.
 nm printCR.
-                                            dir := currentDirectory pathName asFilename.
-                                            path := dir constructString:nm.
+					    dir := currentDirectory pathName asFilename.
+					    path := dir constructString:nm.
 path printCR.
-                                            DropObject newFile:path.
-                                        ]
-                                     ].
+					    DropObject newFile:path.
+					]
+				     ].
 
     "/ sigh - must be delayed - origin is not yet fixe
 "/    tabRulerView leftInset:(fileListView originRelativeTo:scrollView) x.
@@ -1302,7 +1302,7 @@
     v origin:(0.0 @ 0.3) corner:(1.0 @ 1.0).
     subView := v scrolledView.
     (subView respondsTo:#directoryForFileDialog:) ifTrue:[
-        subView directoryForFileDialog:currentDirectory
+	subView directoryForFileDialog:currentDirectory
     ].
 
     ObjectMemory addDependent:self.
@@ -1324,66 +1324,66 @@
 "/    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.
+	|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))
+	|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.
+				)
+		    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
-            ]
-        ]
+	    (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"
@@ -1432,35 +1432,35 @@
     "exit FileBrowser"
 
     (self askIfModified:'contents has not been saved.\\Modifications will be lost when FileBrowser is closed.'
-              yesButton:'close') ifTrue:[self destroy]
+	      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
+	"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
+	fileListView invalidate
     ].
 
     "Modified: 29.5.1996 / 16:13:43 / cg"
@@ -1493,8 +1493,8 @@
      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
+	      yesButton:'change') ifTrue:[
+	self queryForDirectoryToChange
     ]
 !
 
@@ -1509,8 +1509,8 @@
      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
+	      yesButton:'change') ifTrue:[
+	 self doChangeToHomeDirectory
     ]
 !
 
@@ -1519,8 +1519,8 @@
      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
+	      yesButton:'change') ifTrue:[
+	 self doChangeToParentDirectory
     ]
 !
 
@@ -1540,50 +1540,50 @@
     |labels selectors args menu|
 
     labels := #(
-                   'copy path'
-                   '-'                               
-                   'up'
-                   'back'
-                   'change to home-directory'
-                   'change directory ...'
-               ).             
+		   'copy path'
+		   '-'                               
+		   'up'
+		   'back'
+		   'change to home-directory'
+		   'change directory ...'
+	       ).             
 
     selectors := #(
-                    copyPath
-                    nil
-                    changeToParentDirectory
-                    changeToPreviousDirectory
-                    changeToHomeDirectory
-                    changeCurrentDirectory
-                  ).
+		    copyPath
+		    nil
+		    changeToParentDirectory
+		    changeToPreviousDirectory
+		    changeToHomeDirectory
+		    changeCurrentDirectory
+		  ).
 
     JavaClassReader notNil ifTrue:[
-        labels := labels , #('-' 'add to JavaClassPath' 'add to JavaSourcePath' 'remove from JavaClassPath' 'remove from JavaSourcePath').
-        selectors := selectors , #(nil #addDirToJavaClassPath #addDirToJavaSourcePath #removeDirFromJavaClassPath #removeDirFromJavaSourcePath).
+	labels := labels , #('-' 'add to JavaClassPath' 'add to JavaSourcePath' 'remove from JavaClassPath' 'remove from JavaSourcePath').
+	selectors := selectors , #(nil #addDirToJavaClassPath #addDirToJavaSourcePath #removeDirFromJavaClassPath #removeDirFromJavaSourcePath).
     ].
 
     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
-        ]
+	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.
+		labels:(resources array:labels)
+		selectors:selectors
+		args:args
+		receiver:self.
 
     previousDirectory isNil ifTrue:[
-        menu disable:#changeToPreviousDirectory.
+	menu disable:#changeToPreviousDirectory.
     ].
     ^menu.
 
@@ -1596,9 +1596,9 @@
     |queryBox dirName|
 
     queryBox := FilenameEnterBox 
-                    title:(resources at:'change directory to:') withCRs
-                    okText:(resources at:'change')
-                    action:[:newName | dirName := newName].
+		    title:(resources at:'change directory to:') withCRs
+		    okText:(resources at:'change')
+		    action:[:newName | dirName := newName].
 "/    queryBox initialText:''.
     queryBox showAtPointer.
     queryBox destroy.
@@ -1640,9 +1640,9 @@
     "common method to ask a yes/no question"
 
     ^ Dialog 
-        confirm:question withCRs
-        yesLabel:(resources at:yesButtonText)
-        noLabel:(resources at:noButtonText)
+	confirm:question withCRs
+	yesLabel:(resources at:yesButtonText)
+	noLabel:(resources at:noButtonText)
 
     "Modified: 21.2.1996 / 01:19:21 / cg"
 !
@@ -1654,12 +1654,12 @@
     |box|
 
     box := FilenameEnterBox 
-                title:(resources at:'execute unix command:')
-               okText:(resources at:'execute')
-               action:aBlock.
+		title:(resources at:'execute unix command:')
+	       okText:(resources at:'execute')
+	       action:aBlock.
 
     fileName notNil ifTrue:[
-        self initialCommandFor:fileName into:box.
+	self initialCommandFor:fileName into:box.
     ].
     box directory:currentDirectory pathName asFilename.
     box showAtPointer.
@@ -1672,11 +1672,11 @@
     "tell user, that code has been modified - let her confirm"
 
     (subView modified not or:[subView contentsWasSaved]) ifTrue:[
-        ^ true
+	^ true
     ].
     ^ self 
-        ask:(resources string:question)
-        yesButton:yesButtonText
+	ask:(resources string:question)
+	yesButton:yesButtonText
 !
 
 getSelectedFileName
@@ -1687,11 +1687,11 @@
 
     sel := fileListView selection.
     (sel size > 1) ifTrue:[
-        self onlyOneSelection
+	self onlyOneSelection
     ] ifFalse:[
-        sel notNil ifTrue:[
-            ^ fileList at:sel first
-        ]
+	sel notNil ifTrue:[
+	    ^ fileList at:sel first
+	]
     ].
     ^ nil
 !
@@ -1711,11 +1711,11 @@
 
     sel := fileListView selection.
     sel notNil ifTrue:[
-        self withWaitCursorDo:[
-            sel do:[:aSelectionIndex |
-                aBlock value:(fileList at:aSelectionIndex )
-            ]
-        ]
+	self withWaitCursorDo:[
+	    sel do:[:aSelectionIndex |
+		aBlock value:(fileList at:aSelectionIndex )
+	    ]
+	]
     ]
 
 !
@@ -1735,9 +1735,9 @@
     |msg|
 
     anErrorString isNil ifTrue:[
-        msg := aString
+	msg := aString
     ] ifFalse:[
-        msg := aString , '\\(' , anErrorString , ')'
+	msg := aString , '\\(' , anErrorString , ')'
     ].
     self warn:msg withCRs
 !
@@ -1750,18 +1750,18 @@
 
     newCollection := aCollection species new.
     aCollection do:[:fname |
-        |ignore|
-
-        ignore := false.
-
-        ((fname startsWith:'.') and:[fname ~= '..']) ifTrue:[
-            showDotFiles ifFalse:[
-                ignore := true
-            ]
-        ].
-        ignore ifFalse:[
-            newCollection add:fname
-        ]
+	|ignore|
+
+	ignore := false.
+
+	((fname startsWith:'.') and:[fname ~= '..']) ifTrue:[
+	    showDotFiles ifFalse:[
+		ignore := true
+	    ]
+	].
+	ignore ifFalse:[
+	    newCollection add:fname
+	]
     ].
     ^ newCollection
 
@@ -1775,8 +1775,8 @@
      action ..."
 
     (currentDirectory pathName asFilename construct:aFilename) isExecutable ifTrue:[
-        (OperatingSystem executeCommand:'cd ',currentDirectory pathName, '; ',aFilename)
-        ifTrue:[^true].
+	(OperatingSystem executeCommand:'cd ',currentDirectory pathName, '; ',aFilename)
+	ifTrue:[^true].
     ].
     ^ self imageAction:aFilename
 
@@ -1818,13 +1818,13 @@
      kill will make me raise the stopSignal when pressed
     "
     killButton 
-        action:[
-            stream notNil ifTrue:[
-                access critical:[
-                    myProcess interruptWith:[stopSignal raise].
-                ]
-            ]
-        ].
+	action:[
+	    stream notNil ifTrue:[
+		access critical:[
+		    myProcess interruptWith:[stopSignal raise].
+		]
+	    ]
+	].
 
     "
      pause makes me stop reading the commands output
@@ -1852,166 +1852,166 @@
     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 noPauseSema|
-
-                    stream buffered:true.
-                    codeView := subView.
-                    codeView unselect.
+	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 noPauseSema|
+
+		    stream buffered:true.
+		    codeView := subView.
+		    codeView unselect.
                 
-                    replace ifTrue:[
-                        codeView list:nil.
-                        lnr := 1.
-                    ].
-
-                    stillReplacing := replace.
-
-                    [stream atEnd] whileFalse:[
-                        pauseHolder value ifTrue:[
-                            "/    
-                            "/ allow interaction with
-                            "/ the codeView via the other windowGroup
-                            "/
-                            lowerFrameView windowGroup:(killButton windowGroup).
-
-                            "/
-                            "/ wait for pause to be turned off
-                            "/
-                            noPauseSema := Semaphore new.
-                            pauseHolder onChangeSend:#signal to:noPauseSema.
-                            noPauseSema wait.
-
-                            "/    
-                            "/ no interaction with the codeView ...
-                            "/
-                            lowerFrameView windowGroup:(self windowGroup).
-
-                        ] ifFalse:[
-                            (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.
-                                        ]
-                                    ].
-                                ].
-                            ].
-                        ].
-
-                        "
-                         give others running at same prio a chance too
-                         (especially other FileBrowsers doing the same)
-                        "
-                        Processor yield
-                    ].
-                ] valueNowOrOnUnwindDo:[
-                    stream shutDown "close". stream := nil.
-                ].
-
-                "/
-                "/ the command could have changed the directory
-                "/
-                self updateCurrentDirectoryIfChanged
-            ].
-            replace ifTrue:[
-                subView modified:false.
-            ].
-        ]
+		    replace ifTrue:[
+			codeView list:nil.
+			lnr := 1.
+		    ].
+
+		    stillReplacing := replace.
+
+		    [stream atEnd] whileFalse:[
+			pauseHolder value ifTrue:[
+			    "/    
+			    "/ allow interaction with
+			    "/ the codeView via the other windowGroup
+			    "/
+			    lowerFrameView windowGroup:(killButton windowGroup).
+
+			    "/
+			    "/ wait for pause to be turned off
+			    "/
+			    noPauseSema := Semaphore new.
+			    pauseHolder onChangeSend:#signal to:noPauseSema.
+			    noPauseSema wait.
+
+			    "/    
+			    "/ no interaction with the codeView ...
+			    "/
+			    lowerFrameView windowGroup:(self windowGroup).
+
+			] ifFalse:[
+			    (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.
+					]
+				    ].
+				].
+			    ].
+			].
+
+			"
+			 give others running at same prio a chance too
+			 (especially other FileBrowsers doing the same)
+			"
+			Processor yield
+		    ].
+		] valueNowOrOnUnwindDo:[
+		    stream shutDown "close". stream := nil.
+		].
+
+		"/
+		"/ the command could have changed the directory
+		"/
+		self updateCurrentDirectoryIfChanged
+	    ].
+	    replace ifTrue:[
+		subView modified:false.
+	    ].
+	]
       ]
     ] valueNowOrOnUnwindDo:[
-        |wg|
-
-        self label:myName; iconLabel:myName.
-        myProcess notNil ifTrue:[myProcess priority:myPriority].
-
-        "
-         hide the button, and make sure it will stay
-         hidden when we are realized again
-        "
-        killButton beInvisible.
-        pauseToggle beInvisible.
-
-        "
-         remove the killButton from its group
-         (otherwise, it will be destroyed when we shut down the group)
-        "
-        wg := killButton windowGroup.
-        killButton windowGroup:nil.
-        pauseToggle windowGroup:nil.
-
-        "
-         shut down the kill buttons windowgroup
-        "
-        wg notNil ifTrue:[
-            wg process terminate.
-        ].
-        "
-         clear its action (actually not needed, but
-         releases reference to thisContext earlier)
-        "
-        killButton action:nil.
-
-        "/    
-        "/ allow interaction with the codeView
-        "/ (bring it back into my group)
-        "/
-        lowerFrameView windowGroup:(self windowGroup).
+	|wg|
+
+	self label:myName; iconLabel:myName.
+	myProcess notNil ifTrue:[myProcess priority:myPriority].
+
+	"
+	 hide the button, and make sure it will stay
+	 hidden when we are realized again
+	"
+	killButton beInvisible.
+	pauseToggle beInvisible.
+
+	"
+	 remove the killButton from its group
+	 (otherwise, it will be destroyed when we shut down the group)
+	"
+	wg := killButton windowGroup.
+	killButton windowGroup:nil.
+	pauseToggle windowGroup:nil.
+
+	"
+	 shut down the kill buttons windowgroup
+	"
+	wg notNil ifTrue:[
+	    wg process terminate.
+	].
+	"
+	 clear its action (actually not needed, but
+	 releases reference to thisContext earlier)
+	"
+	killButton action:nil.
+
+	"/    
+	"/ allow interaction with the codeView
+	"/ (bring it back into my group)
+	"/
+	lowerFrameView windowGroup:(self windowGroup).
     ].
 
     currentFileName isNil ifTrue:[
-        subView modified:false.
+	subView modified:false.
     ].
 
     subView size > 10000 ifTrue:[
-        self warn:'text quite large now - please cut off some lines'
+	self warn:'text quite large now - please cut off some lines'
     ]
 
     "Modified: 21.9.1995 / 11:18:46 / claus"
@@ -2026,11 +2026,11 @@
 
     (Image isImageFileSuffix:(aFilename asFilename suffix))
     ifTrue:[
-        img := Image fromFile:(currentDirectory pathName asFilename construct:aFilename).
-        img notNil ifTrue:[
-            img inspect.
-            ^ true
-        ]
+	img := Image fromFile:(currentDirectory pathName asFilename construct:aFilename).
+	img notNil ifTrue:[
+	    img inspect.
+	    ^ true
+	]
     ].
     ^ false
 
@@ -2048,109 +2048,109 @@
 
     ((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
-        ].
-        (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'
-        ].
-        (lcFilename endsWith:'tar.z') ifTrue:[
-            cmd := 'zcat %1 | tar tvf -'.
-            select := false.
-        ].
-        (fileName endsWith:'.gz') ifTrue:[
-            cmd := 'gunzip %1'.
-        ].
-        (fileName endsWith:'tar.gz') ifTrue:[
-            cmd := ('gunzip < %1 | tar tvf -' ).
-            select := false.
-        ].
-        (fileName endsWith:'.tgz') ifTrue:[
-            cmd := ('gunzip < %1 | tar tvf -' ).
-            select := false.
-        ].
-        (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
-        ]
+	(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
+	].
+	(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'
+	].
+	(lcFilename endsWith:'tar.z') ifTrue:[
+	    cmd := 'zcat %1 | tar tvf -'.
+	    select := false.
+	].
+	(fileName endsWith:'.gz') ifTrue:[
+	    cmd := 'gunzip %1'.
+	].
+	(fileName endsWith:'tar.gz') ifTrue:[
+	    cmd := ('gunzip < %1 | tar tvf -' ).
+	    select := false.
+	].
+	(fileName endsWith:'.tgz') ifTrue:[
+	    cmd := ('gunzip < %1 | tar tvf -' ).
+	    select := false.
+	].
+	(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: 3.8.1997 / 16:55:26 / cg"
@@ -2165,16 +2165,16 @@
     fullPath := currentDirectory pathName asFilename constructString:aFilename.
     lcName := aFilename asLowercase.
     ((lcName endsWith:'.htm') or:[lcName endsWith:'.html']) ifTrue:[
-        HTMLDocumentView openOn:fullPath.
-        ^ true
+	HTMLDocumentView openOn:fullPath.
+	^ true
     ].
 
     OperatingSystem isUNIXlike ifTrue:[
-        (#('.man' '.1' '.2' '.3') findFirst:[:suff | aFilename endsWith:suff]) ~~ 0 
-        ifTrue:[
-             HTMLDocumentView openFullOnText:(HTMLDocGenerator manPageForFile:fullPath).
-            ^ true
-        ]
+	(#('.man' '.1' '.2' '.3') findFirst:[:suff | aFilename endsWith:suff]) ~~ 0 
+	ifTrue:[
+	     HTMLDocumentView openFullOnText:(HTMLDocGenerator manPageForFile:fullPath).
+	    ^ true
+	]
     ].
     ^ self imageAction:aFilename
 
@@ -2190,8 +2190,8 @@
 
     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 
+	      yesButton:'change') ifTrue:[
+	self doChangeCurrentDirectoryTo:previousDirectory updateHistory:false 
     ]
 !
 
@@ -2206,78 +2206,78 @@
     |oldSelection nOld here newState msg newLabel t|
 
     shown ifTrue:[
-        currentDirectory notNil ifTrue:[
-            lockUpdate ifTrue:[
-                Processor removeTimedBlock:checkBlock.
-                Processor addTimedBlock:checkBlock afterSeconds:checkDelta.
-                ^ self
-            ].
-
-            subView modified ifTrue:[
-                newState := ' (modified)'
-            ].
-
-            here := currentDirectory pathName.
-            (here asFilename isReadable) ifTrue:[
-                Processor removeTimedBlock:checkBlock.
-
-                t := currentDirectory timeOfLastChange.
-                (t notNil and:[t > 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 ...
-                "
-                (here asFilename exists) 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.
-            ]
-        ]
+	currentDirectory notNil ifTrue:[
+	    lockUpdate ifTrue:[
+		Processor removeTimedBlock:checkBlock.
+		Processor addTimedBlock:checkBlock afterSeconds:checkDelta.
+		^ self
+	    ].
+
+	    subView modified ifTrue:[
+		newState := ' (modified)'
+	    ].
+
+	    here := currentDirectory pathName.
+	    (here asFilename isReadable) ifTrue:[
+		Processor removeTimedBlock:checkBlock.
+
+		t := currentDirectory timeOfLastChange.
+		(t notNil and:[t > 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 ...
+		"
+		(here asFilename exists) 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.
+	    ]
+	]
     ]
 
     "Modified: 28.4.1997 / 19:40:34 / cg"
@@ -2288,75 +2288,78 @@
     "verify argument is name of a readable & executable directory
      and if so, go there"
 
-    |msg path idx|
+    |msg path idx f|
 
     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
+	path := currentDirectory pathName.
+	(f := fileName asFilename) isAbsolute ifFalse:[
+	    f := currentDirectory asFilename construct:fileName.
+	].
+	(f isDirectory) ifTrue:[
+	    (f isReadable) ifTrue:[
+		(f isExecutable) ifTrue:[
+		    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.
+
+		    "/ fetch the new path.
+		    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
     ]
 
     "Modified: 24.4.1997 / 22:41:46 / cg"
@@ -2369,22 +2372,22 @@
 !
 
 doChangeToParentDirectory
-    "go to home directory"
+    "go to parent directory"
 
     self doChangeCurrentDirectoryTo:'..' updateHistory:true
 !
 
 doCreateDirectory:newName
     (currentDirectory includes:newName) ifTrue:[
-        self warn:'%1 already exists.' with:newName.
-        ^ self
+	self warn:'%1 already exists.' with:newName.
+	^ self
     ].
 
     (currentDirectory createDirectory:newName) ifTrue:[
-        self updateCurrentDirectoryIfChanged
+	self updateCurrentDirectoryIfChanged
     ] ifFalse:[
-        self showAlert:(resources string:'cannot create directory ''%1'' !!' with:newName)
-                  with:(OperatingSystem lastErrorString)
+	self showAlert:(resources string:'cannot create directory ''%1'' !!' with:newName)
+		  with:(OperatingSystem lastErrorString)
     ]
 
     "Modified: 19.4.1997 / 15:30:32 / cg"
@@ -2397,19 +2400,19 @@
 
     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.
-        ]
+	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"
@@ -2418,7 +2421,7 @@
 
 updateCurrentDirectoryIfChanged
     (currentDirectory timeOfLastChange > timeOfLastCheck) ifTrue:[
-        self updateCurrentDirectory
+	self updateCurrentDirectory
     ]
 
     "Modified: 19.4.1997 / 15:30:03 / cg"
@@ -2428,9 +2431,9 @@
 
 guessEncodingFrom:aBuffer
     "look for a string
-        encoding #name
+	encoding #name
      or:
-        encoding: name
+	encoding: name
      within the given buffer 
      (which is usually the first few bytes of a textFile).
      If thats not found, use heuristics (in CharacterArray) to guess."
@@ -2442,55 +2445,55 @@
     n := aBuffer size.
 
     (idx := aBuffer findString:'charset=') ~~ 0 ifTrue:[
-        s := ReadStream on:aBuffer.
-        s position:idx + 8.
-        s skipSeparators.
-        w := s upToSeparator.
-        w notNil ifTrue:[
-            (idx := w indexOf:$") ~~ 0 ifTrue:[
-                w := w copyTo:idx-1
-            ].
-            ^ w asSymbol
-        ].
+	s := ReadStream on:aBuffer.
+	s position:idx + 8.
+	s skipSeparators.
+	w := s upToSeparator.
+	w notNil ifTrue:[
+	    (idx := w indexOf:$") ~~ 0 ifTrue:[
+		w := w copyTo:idx-1
+	    ].
+	    ^ w asSymbol
+	].
     ].
     (idx := aBuffer findString:'encoding') ~~ 0 ifTrue:[
-        s := ReadStream on:aBuffer.
-        s position:idx + 8.
-        s skipSeparators.
-        s peek == $: ifTrue:[
-            s next.
-            s skipSeparators. 
-        ].
-
-        s peek == $# ifTrue:[
-            s next.
-            s skipSeparators. 
-        ].
-        w := s upToSeparator.
-        w notNil ifTrue:[
-            ^ w asSymbol
-        ].
+	s := ReadStream on:aBuffer.
+	s position:idx + 8.
+	s skipSeparators.
+	s peek == $: ifTrue:[
+	    s next.
+	    s skipSeparators. 
+	].
+
+	s peek == $# ifTrue:[
+	    s next.
+	    s skipSeparators. 
+	].
+	w := s upToSeparator.
+	w notNil ifTrue:[
+	    ^ w asSymbol
+	].
     ].
 
     1 to:n do:[:i |
-        (aBuffer at:i) isPrintable ifFalse:[binary := true].
+	(aBuffer at:i) isPrintable ifFalse:[binary := true].
     ].
 
     binary ifTrue:[
-        "/ look for JIS7 / EUC encoding
-
-        enc := CharacterArray guessEncodingFrom:aBuffer.
-        enc notNil ifTrue:[
-            ^ enc
-        ].
-
-        "/ if the encoding has been set to any non iso setting,
-        "/ assume its what we defined ...
-
-        (('iso*' match:fileEncoding) or:['ascii*' match:fileEncoding]) ifTrue:[
-            ^ #binary
-        ].
-        ^ fileEncoding ? #binary
+	"/ look for JIS7 / EUC encoding
+
+	enc := CharacterArray guessEncodingFrom:aBuffer.
+	enc notNil ifTrue:[
+	    ^ enc
+	].
+
+	"/ if the encoding has been set to any non iso setting,
+	"/ assume its what we defined ...
+
+	(('iso*' match:fileEncoding) or:['ascii*' match:fileEncoding]) ifTrue:[
+	    ^ #binary
+	].
+	^ fileEncoding ? #binary
     ].
     ^ #ascii
 
@@ -2523,66 +2526,66 @@
     pref := self preferredFontEncodingFor:newEncoding.
 
     (pref match:fontsEncoding) ifTrue:[
-        ^ self
+	^ self
     ].
     "/ stupid ...
     pref = 'ascii*' ifTrue:[
-        (fontsEncoding match:'iso8859*') ifTrue:[
-            ^ self
-        ]
+	(fontsEncoding match:'iso8859*') ifTrue:[
+	    ^ self
+	]
     ].
 
     filter := [:f | |coding|
-                    (coding := f encoding) notNil 
-                    and:[pref match:coding]].
+		    (coding := f encoding) notNil 
+		    and:[pref match:coding]].
 
     defaultFont := TextView defaultFont onDevice:device.
     (pref match:(defaultFont encoding)) ifFalse:[
-        defaultFont := nil.
+	defaultFont := nil.
     ].
 
     defaultFont isNil ifTrue:[
-        (pref = 'ascii*'
-        or:[pref = 'iso8859*']) ifTrue:[
-            defaultFont := FontDescription family:'courier' face:'medium' style:'roman' size:12
-        ]
+	(pref = 'ascii*'
+	or:[pref = 'iso8859*']) ifTrue:[
+	    defaultFont := FontDescription family:'courier' face:'medium' style:'roman' size:12
+	]
     ].
 
     defaultFont isNil ifTrue:[
-        defaultFont := device 
-                            listOfAvailableFonts 
-                                detect:[:f | filter value:f]
-                                ifNone:nil.
-        defaultFont isNil ifTrue:[
-
-            "/ flush list, and refetch font list
-            "/ (in case someone just changed the font path ...)
-
-            device flushListOfAvailableFonts.
-            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.
-        ]
+	defaultFont := device 
+			    listOfAvailableFonts 
+				detect:[:f | filter value:f]
+				ifNone:nil.
+	defaultFont isNil ifTrue:[
+
+	    "/ flush list, and refetch font list
+	    "/ (in case someone just changed the font path ...)
+
+	    device flushListOfAvailableFonts.
+	    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.
+	]
     ].
 
     msg := 'switch to a %1 encoded font ?'.
     (ask not or:[self confirm:(resources string:msg with:pref) withCRs])
     ifTrue:[
-        self withWaitCursorDo:[
-            f := FontPanel 
-                fontFromUserInitial:defaultFont
-                              title:(resources string:'font selection')
-                             filter:filter.
-            f notNil ifTrue:[
-                subView font:f
-            ]
-        ]
+	self withWaitCursorDo:[
+	    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"
@@ -2597,19 +2600,19 @@
     |aStream|
 
     (currentDirectory includes:newName) ifTrue:[
-        (self
-            ask:(resources string:'%1 already exists\\truncate ?' with:newName)
-            yesButton:'truncate'
-        ) ifFalse:[^ self].
+	(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
+	aStream close.
+	self updateCurrentDirectoryIfChanged
     ] ifFalse:[
-        self showAlert:(resources string:'cannot create file ''%1'' !!' with:newName)
-                  with:(FileStream lastErrorString)
+	self showAlert:(resources string:'cannot create file ''%1'' !!' with:newName)
+		  with:(FileStream lastErrorString)
     ]
 
     "Modified: 23.4.1997 / 13:19:12 / cg"
@@ -2627,40 +2630,40 @@
     |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.
-        ]
+	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"
@@ -2683,60 +2686,60 @@
 
     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 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
+		self show:nil
 "
-                idx := fileList indexOf:fileName.
-                idx ~~ 0 ifTrue:[
-                    toRemove add:idx.
-                ]
-            ]
-        ].
+		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
-        ]
+	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"
@@ -2746,10 +2749,10 @@
     "rename file(s) (or directories)"
 
     (oldName notNil and:[newName notNil]) ifTrue:[
-        (oldName isBlank or:[newName isBlank]) ifFalse:[
-            currentDirectory renameFile:oldName newName:newName.
-            self updateCurrentDirectoryIfChanged.
-        ]
+	(oldName isBlank or:[newName isBlank]) ifFalse:[
+	    currentDirectory renameFile:oldName newName:newName.
+	    self updateCurrentDirectoryIfChanged.
+	]
     ]
 
     "Modified: 23.4.1997 / 13:19:37 / cg"
@@ -2768,18 +2771,18 @@
     (currentFileName = 'Make.proto'
     or:[currentFileName = 'Makefile'
     or:[currentFileName = 'makefile']]) ifTrue:[
-        ^ #('#' (nil nil)).
+	^ #('#' (nil nil)).
     ].
     ((currentFileName endsWith:'.c')
     or:[(currentFileName endsWith:'.C')]) ifTrue:[
-        ^ #(nil ('/*' '*/')).
+	^ #(nil ('/*' '*/')).
     ].
     ((currentFileName endsWith:'.cc')
     or:[(currentFileName endsWith:'.CC')]) ifTrue:[
-        ^ #('//' ('/*' '*/')).
+	^ #('//' ('/*' '*/')).
     ].
     (currentFileName endsWith:'.java') ifTrue:[
-        ^ #('//' (nil nil)).
+	^ #('//' (nil nil)).
     ].
 
     "/ smalltalk comments
@@ -2798,8 +2801,8 @@
 
     commentStrings := self fileCommentStrings.
     commentStrings notNil ifTrue:[
-        subView
-            commentStrings:#('#' (nil nil)).
+	subView
+	    commentStrings:#('#' (nil nil)).
     ].
 
     "Modified: 7.1.1997 / 20:30:54 / cg"
@@ -2819,27 +2822,27 @@
 
 "/    info := currentDirectory infoOf:fileName.
     info isNil ifTrue:[
-        self showAlert:(resources string:'cannot get info of ''%1'' !!' with:fileName)
-                  with:(OperatingSystem lastErrorString).
-        ^ nil
+	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))
+	text add:(resources string:'symbolic link to: %1' with:(f linkInfo path))
     ].
 
     type := info type.
     (longInfo and:[type == #regular]) ifTrue:[
-        fullPath := currentDirectory pathName asFilename constructString:fileName.
-        fileOutput := fullPath asFilename fileType.
+	fullPath := currentDirectory pathName asFilename constructString:fileName.
+	fileOutput := fullPath asFilename fileType.
     ].
 
     s := (resources at:'type:   ').
     fileOutput isNil ifTrue:[
-        s := s ,  type asString
+	s := s ,  type asString
     ] ifFalse:[
-        s := s , 'regular (' , fileOutput , ')'
+	s := s , 'regular (' , fileOutput , ')'
     ].
     text add:s.
     text add:(resources string:'size:   %1' with:(info size) printString).
@@ -2847,27 +2850,27 @@
     modeBits := info mode.
     modeString := self getModeString:modeBits.
     longInfo ifTrue:[
-        text add:(resources string:'access: %1 (%2)'
-                              with:modeString 
-                              with:(modeBits printStringRadix:8))
+	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:'access: %1' with:modeString)
     ].
     text add:(resources string:'owner:  %1'
-                          with:(OperatingSystem getUserNameFromID:(info uid))).
+			  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 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
 
@@ -2896,9 +2899,9 @@
        'info.txt'
        'INFO.TXT'
     ) do:[:f |
-        (currentDirectory isReadable:f) ifTrue:[
-            (currentDirectory isDirectory:f) ifFalse:[^ f].
-        ]
+	(currentDirectory isReadable:f) ifTrue:[
+	    (currentDirectory isDirectory:f) ifFalse:[^ f].
+	]
     ].
     ^ nil
 
@@ -2910,9 +2913,9 @@
      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 )
+		    with:#( 'owner:' $r $w $x 
+			    ' group:' $r $w $x 
+			    ' others:' $r $w $x )
 !
 
 getModeString:modeBits with:texts
@@ -2926,18 +2929,18 @@
 
     #( 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 
-        ]
+	|ch|
+
+	bitMask isNil ifTrue:[
+	    modeString := modeString , (resources string:access)
+	] ifFalse:[
+	    (bits bitAnd:bitMask) == 0 ifTrue:[
+		ch := $-
+	    ] ifFalse:[
+		ch := access
+	    ].
+	    modeString := modeString copyWith:ch 
+	]
     ].
     ^ modeString
 !
@@ -2949,7 +2952,7 @@
 
     info := self getInfoFile.
     info notNil ifTrue:[
-        txt := self readFile:info
+	txt := self readFile:info
     ].
     self show:txt.
 !
@@ -2966,15 +2969,15 @@
 "
     unitString := ''.
     size < (500 * 1024) ifTrue:[
-        size < 1024 ifTrue:[
-            n := size
-        ] ifFalse:[
-            n := (size * 10 // 1024 / 10.0).
-            unitString := ' Kb'
-        ]
+	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 := (size * 10 // 1024 // 1024 / 10.0).
+	unitString := ' Mb'
     ].
     ^ (n printStringLeftPaddedTo:5) , unitString.
 ! !
@@ -2999,18 +3002,18 @@
 
     stream := (currentDirectory asFilename construct:fileName) readStream.
     stream isNil ifTrue:[
-        msg := (resources string:'cannot read file ''%1'' !!' with:fileName).
-        self showAlert:msg with:(FileStream lastErrorString).
-        ^ nil
+	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 fileSize) > 1000000 ifTrue:[
-        Processor activeProcess withPriority:Processor userBackgroundPriority do:[
-            ObjectMemory announceSpaceNeed:(sz + (sz // 5)) "/ add 20% for tab expansion
-        ].
+	Processor activeProcess withPriority:Processor userBackgroundPriority do:[
+	    ObjectMemory announceSpaceNeed:(sz + (sz // 5)) "/ add 20% for tab expansion
+	].
     ].
 
     text := self readStream:stream lineDelimiter:aCharacter encoding:encoding.
@@ -3041,25 +3044,25 @@
 
     enc := encoding.
     enc == #iso8859 ifTrue:[
-        enc := nil
+	enc := nil
     ].
 
     aCharacter == Character cr ifTrue:[
-        [aStream atEnd] whileFalse:[
-            line := aStream nextLine withTabsExpanded.
-            enc notNil ifTrue:[
-                line := line decodeFrom:enc
-            ].
-            text add:line
-        ].
+	[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
-        ].
+	[aStream atEnd] whileFalse:[
+	    line := (aStream upTo:aCharacter) withTabsExpanded.
+	    enc notNil ifTrue:[
+		line := line decodeFrom:enc
+	    ].
+	    text add:line
+	].
     ].
     ^ text
 
@@ -3079,7 +3082,7 @@
     "show/insert contents of fileName in subView"
 
     ^ self 
-        showFile:fileName insert:insert encoding:encoding doubleClick:false
+	showFile:fileName insert:insert encoding:encoding doubleClick:false
 
     "Modified: 19.6.1996 / 09:40:19 / cg"
 !
@@ -3091,14 +3094,14 @@
      fontsEncoding pref failWarning|
 
     ((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
+	"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
     ].
 
     "/
@@ -3106,9 +3109,9 @@
     "/
     s := FileStream readonlyFileNamed:fileName in:currentDirectory.
     s isNil ifTrue:[
-        self showAlert:(resources string:'cannot read file ''%1'' !!' with:fileName)
-                  with:(FileStream lastErrorString).
-        ^ nil
+	self showAlert:(resources string:'cannot read file ''%1'' !!' with:fileName)
+		  with:(FileStream lastErrorString).
+	^ nil
     ].
 
     buffer := String new:4096.
@@ -3120,101 +3123,101 @@
     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]
+	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].
-        ].
-
-        fontsEncoding := subView font encoding.
-        pref := self preferredFontEncodingFor:guess.
-
-        ok := pref match:fontsEncoding.
-        ok ifFalse:[
-            pref = 'iso8859*' ifTrue:[
-                ok := 'ascii*' match:fontsEncoding
-            ]
-        ].
-        ok ifTrue:[
-            fileEncoding := guess.    
-            enc := guess.
-        ] ifFalse:[
-            action := Dialog choose:(resources string:'''%1'' seems to require a %2 font.' with:fileName with:pref)
-                           labels:(resources array:#('cancel' 'show' 'change font'))
-                           values:#(nil #show #encoding)
-                           default:#encoding.
-            action isNil ifTrue:[^ self].
-            action == #encoding ifTrue:[
-                fileEncoding := guess asSymbol.
-                subView externalEncoding:fileEncoding.
-                self validateFontEncodingFor:fileEncoding ask:false.
-            ] ifFalse:[
-                self information:(resources string:'Individual characters may be invisible/wrong in this font.')
-            ].
-            enc := fileEncoding.
-        ].
+	viaDoubleClick ifTrue:[
+	    (self nonBinaryFileAction:fileName) ifTrue:[^ self].
+	].
+
+	fontsEncoding := subView font encoding.
+	pref := self preferredFontEncodingFor:guess.
+
+	ok := pref match:fontsEncoding.
+	ok ifFalse:[
+	    pref = 'iso8859*' ifTrue:[
+		ok := 'ascii*' match:fontsEncoding
+	    ]
+	].
+	ok ifTrue:[
+	    fileEncoding := guess.    
+	    enc := guess.
+	] ifFalse:[
+	    action := Dialog choose:(resources string:'''%1'' seems to require a %2 font.' with:fileName with:pref)
+			   labels:(resources array:#('cancel' 'show' 'change font'))
+			   values:#(nil #show #encoding)
+			   default:#encoding.
+	    action isNil ifTrue:[^ self].
+	    action == #encoding ifTrue:[
+		fileEncoding := guess asSymbol.
+		subView externalEncoding:fileEncoding.
+		self validateFontEncodingFor:fileEncoding ask:false.
+	    ] ifFalse:[
+		self information:(resources string:'Individual characters may be invisible/wrong in this font.')
+	    ].
+	    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).
-            ]
-        ]
+	"/
+	"/ 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.
+	"/ 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
+	eol := Character value:13
     ] ifFalse:[
-        eol := Character cr
+	eol := Character cr
     ].
 
     failWarning := false.
     CharacterArray decodingFailedSignal handle:[:ex |
-        |errStr|
-
-        failWarning ifFalse:[
-            errStr := resources string:ex errorString.
-            (self confirm:(resources 
-                                string:'An error occurred while decoding:\%1\\The file has either a different encoding or is corrupted.\\Continue ?'
-                                with:errStr) withCRs)
-            ifFalse:[
-                ^ self
-            ].
-            failWarning := true.
-        ].
-        ex proceed.
+	|errStr|
+
+	failWarning ifFalse:[
+	    errStr := resources string:ex errorString.
+	    (self confirm:(resources 
+				string:'An error occurred while decoding:\%1\\The file has either a different encoding or is corrupted.\\Continue ?'
+				with:errStr) withCRs)
+	    ifFalse:[
+		^ self
+	    ].
+	    failWarning := true.
+	].
+	ex proceed.
     ] do:[
-        text := self readFile:fileName lineDelimiter:eol encoding:enc.
+	text := self readFile:fileName lineDelimiter:eol encoding:enc.
     ].
 
     insert ifFalse:[
-        self show:text
+	self show:text
     ] ifTrue:[
-        subView insertSelectedStringAtCursor:text asString
+	subView insertSelectedStringAtCursor:text asString
     ].
 
     "Created: 19.6.1996 / 09:39:52 / cg"
@@ -3226,38 +3229,38 @@
 
     stream := FileStream newFileNamed:fileName in:currentDirectory.
     stream isNil ifTrue:[
-        msg := (resources string:'cannot write file ''%1'' !!' with:fileName).
-        self showAlert:msg with:(FileStream lastErrorString)
+	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 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
+	].
+	stream close.
+	subView modified:false
     ]
 
     "Created: 22.2.1996 / 15:03:10 / cg"
@@ -3306,67 +3309,67 @@
 
     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
-            ].
-        ]
+	f isSymbolicLink ifTrue:[
+	    key := #directoryLink
+	] ifFalse:[
+	    key := #directory.
+	    (f isReadable not or:[f isExecutable not]) ifTrue:[
+		key := #directoryLocked
+	    ].
+	]
     ] ifFalse:[
-        f isSymbolicLink ifTrue:[
-            f isReadable not ifTrue:[
-                key := #fileLocked
-            ] ifFalse:[
-                key := #fileLink
-            ]
-        ] ifFalse:[
-            key := key2 := #file.
-            (f isReadable not) ifTrue:[
-                key := #fileLocked
-            ] ifFalse:[
-                suff := f suffix.
-                mime := MIMETypes mimeTypeForSuffix:suff.
-                mime notNil ifTrue:[
-                    (mime startsWith:'image/') ifTrue:[
-                        key := #imageFile
-                    ] ifFalse:[
-                        (mime startsWith:'text/') ifTrue:[
-                            key := #textFile
-                        ]
-                    ]
-                ].
-            ].
-        ].
+	f isSymbolicLink ifTrue:[
+	    f isReadable not ifTrue:[
+		key := #fileLocked
+	    ] ifFalse:[
+		key := #fileLink
+	    ]
+	] ifFalse:[
+	    key := key2 := #file.
+	    (f isReadable not) ifTrue:[
+		key := #fileLocked
+	    ] ifFalse:[
+		suff := f suffix.
+		mime := MIMETypes mimeTypeForSuffix:suff.
+		mime notNil ifTrue:[
+		    (mime startsWith:'image/') ifTrue:[
+			key := #imageFile
+		    ] ifFalse:[
+			(mime startsWith:'text/') ifTrue:[
+			    key := #textFile
+			]
+		    ]
+		].
+	    ].
+	].
     ].
 
     icons isNil ifTrue:[
-        icons := IdentityDictionary new
+	icons := IdentityDictionary new
     ].
 
     icn := icons at:key ifAbsent:nil.
     icn isNil ifTrue:[
-        Icons isNil ifTrue:[
-            self class initializeIcons
-        ].
-        icn := Icons at:key ifAbsent:nil.
-        icn notNil ifTrue:[
-            icn := icn on:device.
-            icons at:key put:icn.
-        ]
+	Icons isNil ifTrue:[
+	    self class initializeIcons
+	].
+	icn := Icons at:key ifAbsent:nil.
+	icn notNil ifTrue:[
+	    icn := icn on:device.
+	    icons at:key put:icn.
+	]
     ].
     icn isNil ifTrue:[
-        key2 notNil ifTrue:[
-            icn := icons at:key2 ifAbsent:nil.
-            icn isNil ifTrue:[
-                icn := Icons at:key2 ifAbsent:nil.
-                icn notNil ifTrue:[
-                    icn := icn on:device.
-                    icons at:key2 put:icn.
-                ]
-            ]
-        ]
+	key2 notNil ifTrue:[
+	    icn := icons at:key2 ifAbsent:nil.
+	    icn isNil ifTrue:[
+		icn := Icons at:key2 ifAbsent:nil.
+		icn notNil ifTrue:[
+		    icn := icn on:device.
+		    icons at:key2 put:icn.
+		]
+	    ]
+	]
     ].
     ^ icn
 
@@ -3376,8 +3379,8 @@
 stopUpdateProcess
     Processor removeTimedBlock:checkBlock.
     listUpdateProcess notNil ifTrue:[
-        listUpdateProcess terminate.
-        listUpdateProcess := nil.
+	listUpdateProcess terminate.
+	listUpdateProcess := nil.
     ].
 
     "Created: 19.4.1997 / 13:51:34 / cg"
@@ -3401,341 +3404,341 @@
     "
 
     self withReadCursorDo:[
-        |files matchPattern list passDone|
-
-        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.
-
-        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.
-
-        "
-         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
-             anyImages lineIndex aFileName
-             entry typ f p typeString done endIndex 
-             state stopAtEnd nextState img prevFirstLine prevLastLine
-             numVisible|
-
-            "/
-            "/ 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 := 'unknown'
-                                ].
-                            ] 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.
+	|files matchPattern list passDone|
+
+	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.
+
+	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.
+
+	"
+	 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
+	     anyImages lineIndex aFileName
+	     entry typ f p typeString done endIndex 
+	     state stopAtEnd nextState img prevFirstLine prevLastLine
+	     numVisible|
+
+	    "/
+	    "/ 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 := 'unknown'
+				].
+			    ] 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 contractTo:10.
-                                    nameString := nameString , (String new:(10 - nameString size))
-                                ].
-                                nameString isNil ifTrue:[nameString := '???'].
-                                entry colAt:4 put:nameString withoutSpaces.
-
-                                ((info gid) ~~ prevGid) ifTrue:[
-                                    prevGid := (info gid).
-                                    groupString := OperatingSystem getGroupNameFromID:prevGid.
+				    nameString := nameString , (String new:(10 - nameString size))
+				].
+				nameString isNil ifTrue:[nameString := '???'].
+				entry colAt:4 put:nameString withoutSpaces.
+
+				((info gid) ~~ prevGid) ifTrue:[
+				    prevGid := (info gid).
+				    groupString := OperatingSystem getGroupNameFromID:prevGid.
 				    groupString := groupString contractTo:10.
-                                    groupString := groupString , (String new:(10 - groupString size))
-                                ].
-                                groupString isNil ifTrue:[groupString := '???'].
-                                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
+				    groupString := groupString , (String new:(10 - groupString size))
+				].
+				groupString isNil ifTrue:[groupString := '???'].
+				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"
@@ -3755,5 +3758,5 @@
 !FileBrowser class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/Attic/FBrowser.st,v 1.188 1997-09-10 21:35:00 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/Attic/FBrowser.st,v 1.189 1997-09-15 21:22:40 cg Exp $'
 ! !
--- a/FileBrowser.st	Mon Sep 15 23:06:52 1997 +0200
+++ b/FileBrowser.st	Mon Sep 15 23:22:40 1997 +0200
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1991 by Claus Gittinger
-              All Rights Reserved
+	      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
@@ -30,7 +30,7 @@
 copyright
 "
  COPYRIGHT (c) 1991 by Claus Gittinger
-              All Rights Reserved
+	      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
@@ -54,27 +54,27 @@
     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.
+	     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
+	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
+	Claus Gittinger
 "
 ! !
 
@@ -100,7 +100,7 @@
 
     f := aFilename asFilename.
     f isDirectory ifTrue:[
-        ^ self openOn:aFilename
+	^ self openOn:aFilename
     ].
     browser := self new.
     browser currentDirectory:f directoryName.
@@ -126,27 +126,27 @@
     Icons := IdentityDictionary new.
 
     #(
-        (#directory       'ICON_DIRECTORY'        'tiny_yellow_dir.xpm'       )
-        (#directoryLocked 'ICON_DIRECTORY_LOCKED' 'tiny_yellow_dir_locked.xpm')
-        (#directoryLink   'ICON_DIRECTORY_LINK'   'tiny_yellow_dir_link.xpm'  )
-        (#file            'ICON_FILE'             'tiny_file_plain.xpm'       )
-        (#fileLink        'ICON_FILE_LINK'        'tiny_file_link.xpm'        )
-        (#fileLocked      'ICON_FILE_LOCKED'      'tiny_file_lock.xpm'        )
-        (#imageFile       'ICON_IMAGE_FILE'       'tiny_file_pix.xpm'         )
-        (#textFile        'ICON_TEXT_FILE'        'tiny_file_text.xpm'         )
+	(#directory       'ICON_DIRECTORY'        'tiny_yellow_dir.xpm'       )
+	(#directoryLocked 'ICON_DIRECTORY_LOCKED' 'tiny_yellow_dir_locked.xpm')
+	(#directoryLink   'ICON_DIRECTORY_LINK'   'tiny_yellow_dir_link.xpm'  )
+	(#file            'ICON_FILE'             'tiny_file_plain.xpm'       )
+	(#fileLink        'ICON_FILE_LINK'        'tiny_file_link.xpm'        )
+	(#fileLocked      'ICON_FILE_LOCKED'      'tiny_file_lock.xpm'        )
+	(#imageFile       'ICON_IMAGE_FILE'       'tiny_file_pix.xpm'         )
+	(#textFile        'ICON_TEXT_FILE'        'tiny_file_text.xpm'         )
 
      ) do:[:entry |
-        |key resource defaultName nm|
-
-        key := entry at:1.
-        resource := entry at:2.
-        defaultName := entry at:3.
-
-        nm := resources at:resource default:nil.
-        nm isNil ifTrue:[
-            nm := 'bitmaps/xpmBitmaps/document_images/' , defaultName
-        ].
-        Icons at:key put:(Image fromFile:nm).
+	|key resource defaultName nm|
+
+	key := entry at:1.
+	resource := entry at:2.
+	defaultName := entry at:3.
+
+	nm := resources at:resource default:nil.
+	nm isNil ifTrue:[
+	    nm := 'bitmaps/xpmBitmaps/document_images/' , defaultName
+	].
+	Icons at:key put:(Image fromFile:nm).
     ]
 
     "
@@ -162,22 +162,22 @@
     |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.
-            ]
-        ]
+	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"
@@ -193,21 +193,21 @@
     |nm i res|
 
     (i := DefaultIcon) isNil ifTrue:[
-        res := self classResources.
-        i := res at:'FILEBROWSER_ICON' default:nil.
-        i isNil ifTrue:[
-            nm := res at:'FILEBROWSER_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
-        ]
+	res := self classResources.
+	i := res at:'FILEBROWSER_ICON' default:nil.
+	i isNil ifTrue:[
+	    nm := res at:'FILEBROWSER_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
 
@@ -221,9 +221,9 @@
     "I accept fileObjects only"
 
     aCollectionOfDropObjects do:[:aDropObject |
-        aDropObject isFileObject ifFalse:[
-            aDropObject isTextObject ifFalse:[^ false].
-        ]
+	aDropObject isFileObject ifFalse:[
+	    aDropObject isTextObject ifFalse:[^ false].
+	]
     ].
     ^ true
 
@@ -234,7 +234,7 @@
     "handle drops"
 
     aCollectionOfDropObjects do:[:aDropObject |
-        self dropSingleObject:aDropObject at:aPoint
+	self dropSingleObject:aDropObject at:aPoint
     ]
 
     "Modified: 11.4.1997 / 12:43:36 / cg"
@@ -248,30 +248,30 @@
     |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 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
+	subView paste:someObject theObject.
+	^ self
     ].
 
     "Modified: 6.4.1997 / 14:46:44 / cg"
@@ -286,14 +286,14 @@
     <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].
+	(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
 
@@ -308,32 +308,32 @@
     <resource: #keyboard (#GotoLine #InspectIt #CmdI #Cmdu #DoIt #Delete #BackSpace #Accept)>
 
     (key == #Delete or:[key == #BackSpace]) ifTrue:[
-        self fileRemove.
-        ^ self
+	self fileRemove.
+	^ self
     ].
     (key == #Accept) ifTrue:[
-        self fileFileIn.
-        ^ self
+	self fileFileIn.
+	^ self
     ].
     (key == #GotoLine) ifTrue:[
-        self fileGet.
-        ^ self
+	self fileGet.
+	^ self
     ].
     (key == #DoIt) ifTrue:[
-        self fileExecute.
-        ^ self
+	self fileExecute.
+	^ self
     ].
     (key == #InspectIt) ifTrue:[
-        self fileGetInfo.
-        ^ self
+	self fileGetInfo.
+	^ self
     ].
     (key == #CmdI) ifTrue:[
-        self fileGetLongInfo.
-        ^ self
+	self fileGetLongInfo.
+	^ self
     ].
     (key == #Cmdu) ifTrue:[
-        self updateCurrentDirectory.
-        ^ self
+	self updateCurrentDirectory.
+	^ self
     ].
     fileListView keyPress:key x:x y:y
 
@@ -356,11 +356,11 @@
     wasVisible := shown.
     super visibilityChange:how.
     (wasVisible not and:[shown]) ifTrue:[
-        "
-         start checking again
-        "
-        Processor removeTimedBlock:checkBlock.
-        Processor addTimedBlock:checkBlock afterSeconds:checkDelta.
+	"
+	 start checking again
+	"
+	Processor removeTimedBlock:checkBlock.
+	Processor addTimedBlock:checkBlock afterSeconds:checkDelta.
     ]
 ! !
 
@@ -412,11 +412,11 @@
     dialog open.
 
     dialog accepted ifTrue:[
-        idx := list selectionIndex.
-        fileEncoding := encodings at:idx.
-        subView externalEncoding:fileEncoding.
-
-        self validateFontEncodingFor:fileEncoding ask:true.
+	idx := list selectionIndex.
+	fileEncoding := encodings at:idx.
+	subView externalEncoding:fileEncoding.
+
+	self validateFontEncodingFor:fileEncoding ask:true.
     ].
 
     "Modified: 30.6.1997 / 14:41:12 / cg"
@@ -432,12 +432,12 @@
      this replaces everything by the commands output ...
     "
     action := [:command | 
-                self class addToCommandHistory:command for:fileName.
-                self doExecuteCommand:command replace:true
-              ].
+		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].
+	      yesButton:'execute') ifFalse:[^ self].
 
 "/    "
 "/     this inserts the commands output ...
@@ -447,7 +447,7 @@
 
     sel := fileListView selection.
     sel size == 1 ifTrue:[
-        fileName := fileList at:sel first
+	fileName := fileList at:sel first
     ].
     self askForCommandFor:fileName thenDo:action
 
@@ -472,72 +472,72 @@
     |aStream here oldPath wasLazy bos|
 
     self selectedFilesDo:[:fileName |
-        ((currentDirectory typeOf:fileName) == #regular) ifTrue:[
-            here := currentDirectory pathName.
-
-            (ObjectFileLoader notNil
-            and:[ObjectFileLoader hasValidBinaryExtension:fileName]) ifTrue:[
-                Object abortSignal catch:[
-                    |p|
-
-                    p := here asFilename constructString: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 asFilename constructString: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
-                            ]
-                        ]
-                    ]
-                ]
-            ]
-        ]
+	((currentDirectory typeOf:fileName) == #regular) ifTrue:[
+	    here := currentDirectory pathName.
+
+	    (ObjectFileLoader notNil
+	    and:[ObjectFileLoader hasValidBinaryExtension:fileName]) ifTrue:[
+		Object abortSignal catch:[
+		    |p|
+
+		    p := here asFilename constructString: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 asFilename constructString: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: 29.4.1997 / 21:56:24 / cg"
@@ -561,22 +561,22 @@
     |fileName msg label|
 
     (subView modified not or:[subView contentsWasSaved]) ifTrue:[
-        self doFileGet:viaDoubleClick.
-        ^ self
+	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
-        ]
+	(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"
@@ -596,7 +596,7 @@
 
     string := self getFileInfoString:longInfo.
     string notNil ifTrue:[
-        self information:string
+	self information:string
     ]
 !
 
@@ -613,7 +613,7 @@
 
     fileName := self getSelectedFileName.
     fileName notNil ifTrue:[
-        self showFile:fileName insert:true encoding:fileEncoding
+	self showFile:fileName insert:true encoding:fileEncoding
     ]
 
     "Modified: 23.4.1997 / 13:06:06 / cg"
@@ -627,140 +627,140 @@
     |labels shorties selectors m sel ns subLabels subSelectors|
 
     labels := #(
-                 'spawn'                   
-                 '-'                               
-                 'get contents'                    
-                 'insert contents'                    
-                 'show info'             
-                 'show full info'
-               ).
+		 'spawn'                   
+		 '-'                               
+		 'get contents'                    
+		 'insert contents'                    
+		 'show info'             
+		 'show full info'
+	       ).
 
     ((ns := Project current defaultNameSpace) notNil 
     and:[ns ~~ Smalltalk]) ifTrue:[
-        labels := labels copyWith:'fileIn (into ''' , Project current defaultNameSpace name , ''')'
+	labels := labels copyWith:'fileIn (into ''' , Project current defaultNameSpace name , ''')'
     ] ifFalse:[
-        labels := labels copyWith:'fileIn'
+	labels := labels copyWith:'fileIn'
     ].
 
     labels := labels , #(
-                 '-'                               
-                 'update'                 
-                 '-'                               
-                 'execute unix command ...'                
-                 'st/x tools'                
-                 '-'                               
-                 'remove'                 
-                 'rename ...'                 
-                 '-'                               
-                 'display long list'           
-                 'show all files'           
-                 'encoding ...'           
-                 '-'                               
-                 'create directory ...'         
-                 'create file ...'
-               ).             
+		 '-'                               
+		 '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
-                 nil
-                 updateCurrentDirectory
-                 nil
-                 fileExecute
-                 stxTools
-                 nil
-                 fileRemove
-                 fileRename
-                 nil
-                 changeDisplayMode
-                 changeDotFileVisibility
-                 fileEncoding
-                 nil
-                 newDirectory
-                 newFile
-                ).
+		 fileSpawn
+		 nil
+		 fileGet
+		 fileInsert
+		 fileGetInfo
+		 fileGetLongInfo
+		 fileFileIn
+		 nil
+		 updateCurrentDirectory
+		 nil
+		 fileExecute
+		 stxTools
+		 nil
+		 fileRemove
+		 fileRename
+		 nil
+		 changeDisplayMode
+		 changeDotFileVisibility
+		 fileEncoding
+		 nil
+		 newDirectory
+		 newFile
+		).
 
     shorties := #(
-                 nil
-                 nil
-                 GotoLine
-                 nil
-                 InspectIt
-                 CmdI
-                 Cmdf
-                 nil
-                 nil
-                 Cmdu
-                 nil
-                 DoIt
-                 nil
-                 Delete
-                 nil
-                 nil
-                 nil
-                 nil
-                 nil
-                 nil
-                 nil
-                 nil
-                ).
+		 nil
+		 nil
+		 GotoLine
+		 nil
+		 InspectIt
+		 CmdI
+		 Cmdf
+		 nil
+		 nil
+		 Cmdu
+		 nil
+		 DoIt
+		 nil
+		 Delete
+		 nil
+		 nil
+		 nil
+		 nil
+		 nil
+		 nil
+		 nil
+		 nil
+		).
 
     m := PopUpMenu 
-            labels:(resources array:labels)
-            selectors:selectors
-            accelerators:shorties
-            receiver:self.
+	    labels:(resources array:labels)
+	    selectors:selectors
+	    accelerators:shorties
+	    receiver:self.
 
     showDotFiles ifTrue:[
-        m labelAt:#changeDotFileVisibility put:(resources string:'hide hidden files')
+	m labelAt:#changeDotFileVisibility put:(resources string:'hide hidden files')
     ].
     showLongList ifTrue:[
-        m labelAt:#changeDisplayMode put:(resources string:'display short list')
+	m labelAt:#changeDisplayMode put:(resources string:'display short list')
     ].
 
     subLabels := #(
-                              'Changes browser'
-                              'Editor'
-                              'HTML reader'
-                              'Image inspect'
-                              'show file differences'
-                  ).
+			      'Changes browser'
+			      'Editor'
+			      'HTML reader'
+			      'Image inspect'
+			      'show file differences'
+		  ).
 
     subSelectors := #(
-                              openChangesBrowser
-                              openEditor
-                              openHTMLReader
-                              openImageInspector
-                              openDiffView
-                     ).
+			      openChangesBrowser
+			      openEditor
+			      openHTMLReader
+			      openImageInspector
+			      openDiffView
+		     ).
 
     JavaInterpreter notNil ifTrue:[
-        subLabels := subLabels , #('Java Applet Viewer').
-        subSelectors := subSelectors , #(openAppletViewer).
+	subLabels := subLabels , #('Java Applet Viewer').
+	subSelectors := subSelectors , #(openAppletViewer).
     ].
 
     m subMenuAt:#stxTools 
-            put:(PopUpMenu
-                    labels:(resources array:subLabels)
-                    selectors:subSelectors
-                    receiver:self).
+	    put:(PopUpMenu
+		    labels:(resources array:subLabels)
+		    selectors:subSelectors
+		    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)
+	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 )
-        ]
+	fileListView selection size > 1 ifTrue:[
+	    m disableAll:#( fileGet fileInsert fileGetInfo fileGetLongInfo fileRename )
+	]
     ].
 
     ^m
@@ -775,25 +775,25 @@
     |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"
+	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"
@@ -809,12 +809,12 @@
 
     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]
+	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]
     ]
 !
 
@@ -826,10 +826,10 @@
     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
+	queryBox title:(resources string:'rename ''%1'' to:' with:oldName).
+	queryBox initialText:oldName.
+	queryBox action:[:newName | self doRename:oldName to:newName].
+	queryBox showAtPointer
     ]
 !
 
@@ -849,13 +849,13 @@
 
     any := false.
     self selectedFilesDo:[:fileName |
-        (currentDirectory isDirectory:fileName) ifTrue:[
-            self class openOn:(currentDirectory pathName asFilename constructString:fileName).
-            any := true
-        ]
+	(currentDirectory isDirectory:fileName) ifTrue:[
+	    self class openOn:(currentDirectory pathName asFilename constructString:fileName).
+	    any := true
+	]
     ].
     any ifFalse:[
-        self class openOn:currentDirectory pathName
+	self class openOn:currentDirectory pathName
     ]
 !
 
@@ -865,9 +865,9 @@
     |queryBox|
 
     queryBox := FilenameEnterBox 
-                    title:(resources at:'create new directory:') withCRs
-                    okText:(resources at:'create')
-                    action:[:newName | self doCreateDirectory:newName].
+		    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"
@@ -879,12 +879,12 @@
     |sel queryBox|
 
     queryBox := FilenameEnterBox 
-                    title:(resources at:'create new file:') withCRs
-                    okText:(resources at:'create')
-                    action:[:newName | self doCreateFile:newName].
+		    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 initialText:(sel asString)
     ].
     queryBox showAtPointer
 
@@ -895,9 +895,9 @@
     |numItems|
 
     (numItems := fileListView selection size) > 2 ifTrue:[
-        (self 
-            confirm:(resources string:'open for each of the %1 items ?' 
-                                 with:numItems)) ifFalse:[^ self].
+	(self 
+	    confirm:(resources string:'open for each of the %1 items ?' 
+				 with:numItems)) ifFalse:[^ self].
     ].
 
     JavaInterpreter releaseAllJavaResources.
@@ -906,16 +906,16 @@
     Java initAllClasses.
 
     self selectedFilesDo:[:fileName |
-        |p path|
-
-        (currentDirectory isDirectory:fileName) ifFalse:[
-            path := currentDirectory pathName asFilename constructString:fileName.
-
-            p := Java 
-                    javaProcessForMainOf:(Java classForName:'sun.applet.AppletViewer')
-                    argumentString:path.
-            p resume.
-        ]
+	|p path|
+
+	(currentDirectory isDirectory:fileName) ifFalse:[
+	    path := currentDirectory pathName asFilename constructString:fileName.
+
+	    p := Java 
+		    javaProcessForMainOf:(Java classForName:'sun.applet.AppletViewer')
+		    argumentString:path.
+	    p resume.
+	]
     ].
 
     "Modified: 15.8.1997 / 05:03:02 / cg"
@@ -947,54 +947,54 @@
     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'.
-        ]
+	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"
@@ -1015,14 +1015,14 @@
     |img|
 
     self selectedFilesDo:[:fileName |
-        (currentDirectory isDirectory:fileName) ifFalse:[
-            img := Image fromFile:(currentDirectory pathName asFilename constructString:fileName).
-            img notNil ifTrue:[
-                img inspect
-            ] ifFalse:[
-                self warn:'unknown format: ' , fileName
-            ]
-        ]
+	(currentDirectory isDirectory:fileName) ifFalse:[
+	    img := Image fromFile:(currentDirectory pathName asFilename constructString:fileName).
+	    img notNil ifTrue:[
+		img inspect
+	    ] ifFalse:[
+		self warn:'unknown format: ' , fileName
+	    ]
+	]
     ].
 
     "Modified: 17.9.1995 / 17:41:24 / claus"
@@ -1034,15 +1034,15 @@
     |numItems|
 
     (numItems := fileListView selection size) > 2 ifTrue:[
-        (self 
-            confirm:(resources string:'open for each of the %1 items ?' 
-                                 with:numItems)) ifFalse:[^ self].
+	(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 asFilename constructString:fileName).
-        ]
+	(currentDirectory isDirectory:fileName) ifFalse:[
+	    aToolClass openOn:(currentDirectory pathName asFilename constructString:fileName).
+	]
     ].
 
     "Modified: 14.11.1996 / 16:01:32 / cg"
@@ -1052,17 +1052,17 @@
     "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).
+	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
+	scrollView topInset:0
     ].
     tabSpec := nil.
 
@@ -1075,22 +1075,22 @@
     |s|
 
     aComponent == subView ifTrue:[
-        s := 'HELP_SUBVIEW'
+	s := 'HELP_SUBVIEW'
     ].
     aComponent == fileListView ifTrue:[
-        s := 'HELP_FILELIST'
+	s := 'HELP_FILELIST'
     ].
     aComponent == filterField ifTrue:[
-        s := 'HELP_FILTER'
+	s := 'HELP_FILTER'
     ].
     aComponent == labelView ifTrue:[
-        s := 'HELP_PATHFIELD'
+	s := 'HELP_PATHFIELD'
     ].
     aComponent == commandView ifTrue:[
-        s := 'HELP_COMMANDVIEW'
+	s := 'HELP_COMMANDVIEW'
     ].
     s notNil ifTrue:[
-        ^ resources string:s
+	^ resources string:s
     ].
     ^ nil
 ! !
@@ -1107,7 +1107,7 @@
      (i.e. save-as etc.) in that directory
     "
     (subView respondsTo:#directoryForFileDialog:) ifTrue:[
-        subView directoryForFileDialog:currentDirectory
+	subView directoryForFileDialog:currentDirectory
     ]
 !
 
@@ -1117,12 +1117,12 @@
     |fs|
 
     fs := Array 
-        with:filterField 
-        with:fileListView 
-        with:subView.
+	with:filterField 
+	with:fileListView 
+	with:subView.
 
     commandView notNil ifTrue:[
-        fs := fs copyWith:commandView
+	fs := fs copyWith:commandView
     ].
     ^fs
 !
@@ -1159,13 +1159,13 @@
     lockUpdate := false.
 
     CommandHistory isNil ifTrue:[
-        CommandHistory := OrderedCollection new.
-        CommandHistorySize := 50
+	CommandHistory := OrderedCollection new.
+	CommandHistorySize := 50
     ].
     DirectoryHistory isNil ifTrue:[
-        DirectoryHistory := OrderedCollection new.
-        DirectoryHistoryWhere := OrderedCollection new.
-        HistorySize := 15.
+	DirectoryHistory := OrderedCollection new.
+	DirectoryHistoryWhere := OrderedCollection new.
+	HistorySize := 15.
     ].
     commandIndex := 0.
 
@@ -1173,12 +1173,12 @@
     self label:myName.
 
     labelFrame := View 
-                        origin:(0.0 @ 0.0)
-                        corner:(1.0 @ (font height * 2))
-                        in:self.
+			origin:(0.0 @ 0.0)
+			corner:(1.0 @ (font height * 2))
+			in:self.
 
     styleSheet name = #st80 ifTrue:[
-        labelFrame level:1
+	labelFrame level:1
     ].
 
     spacing := ViewSpacing.
@@ -1197,8 +1197,8 @@
     filterModel := '*' asValue.
     filterField := EditField in:labelFrame.
     filterField 
-        origin:[((width // 4 * 3) + halfSpacing) @ halfSpacing]
-        corner:(1.0 @ (filterField heightIncludingBorder + halfSpacing + halfSpacing) ).
+	origin:[((width // 4 * 3) + halfSpacing) @ halfSpacing]
+	corner:(1.0 @ (filterField heightIncludingBorder + halfSpacing + halfSpacing) ).
     filterField rightInset:halfSpacing.
     filterField model:filterModel.
 
@@ -1208,11 +1208,11 @@
 
     labelView := Label in:labelFrame.
     labelView origin:(halfSpacing @ halfSpacing)
-              extent:[((width // 4 * 3) - spacing - borderWidth)
-                       @
-                       (filterField heightIncludingBorder)
-                       "(font height + font descent)"
-                     ].
+	      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.
@@ -1220,12 +1220,12 @@
 
     killButton := Button label:(resources string:'kill') in:self.
     killButton origin:(halfSpacing @ halfSpacing)
-               extent:(killButton width @ filterField height).
+	       extent:(killButton width @ filterField height).
     killButton beInvisible.
 
     pauseToggle := Toggle label:(resources string:'pause') in:self.
     pauseToggle origin:((killButton corner x + 50) @ halfSpacing)
-                extent:(pauseToggle width @ filterField height).
+		extent:(pauseToggle width @ filterField height).
     pauseToggle beInvisible.
 
     self initializeCommandViewIn:self.
@@ -1242,22 +1242,22 @@
     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)
+	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).
+	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 := TabSpecRuler in:topFrame.
+	tabRulerView origin:(0.0@0.0) corner:(1.0@10).
     ].
     tabRulerView borderWidth:0.
     tabRulerView synchronousOperation:true.
@@ -1269,29 +1269,29 @@
     scrollView scrolledView:fileListView.
     fileListView action:[:lineNr | self fileSelect:lineNr].
     fileListView doubleClickAction:[:lineNr | self fileSelect:lineNr.
-                                              self fileGet:true].
+					      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|
+					|dir nm path idx|
 obj printCR.
-                                        nm := obj theObject asString.
-                                        idx := fileListView list indexOf:nm.
+					nm := obj theObject asString.
+					idx := fileListView list indexOf:nm.
 idx printCR.
-                                        idx == 0 ifTrue:[
-                                            "/ cannot happen ...
-                                            nil
-                                        ] ifFalse:[
-                                            nm := fileList at:idx.
+					idx == 0 ifTrue:[
+					    "/ cannot happen ...
+					    nil
+					] ifFalse:[
+					    nm := fileList at:idx.
 nm printCR.
-                                            dir := currentDirectory pathName asFilename.
-                                            path := dir constructString:nm.
+					    dir := currentDirectory pathName asFilename.
+					    path := dir constructString:nm.
 path printCR.
-                                            DropObject newFile:path.
-                                        ]
-                                     ].
+					    DropObject newFile:path.
+					]
+				     ].
 
     "/ sigh - must be delayed - origin is not yet fixe
 "/    tabRulerView leftInset:(fileListView originRelativeTo:scrollView) x.
@@ -1302,7 +1302,7 @@
     v origin:(0.0 @ 0.3) corner:(1.0 @ 1.0).
     subView := v scrolledView.
     (subView respondsTo:#directoryForFileDialog:) ifTrue:[
-        subView directoryForFileDialog:currentDirectory
+	subView directoryForFileDialog:currentDirectory
     ].
 
     ObjectMemory addDependent:self.
@@ -1324,66 +1324,66 @@
 "/    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.
+	|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))
+	|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.
+				)
+		    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
-            ]
-        ]
+	    (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"
@@ -1432,35 +1432,35 @@
     "exit FileBrowser"
 
     (self askIfModified:'contents has not been saved.\\Modifications will be lost when FileBrowser is closed.'
-              yesButton:'close') ifTrue:[self destroy]
+	      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
+	"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
+	fileListView invalidate
     ].
 
     "Modified: 29.5.1996 / 16:13:43 / cg"
@@ -1493,8 +1493,8 @@
      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
+	      yesButton:'change') ifTrue:[
+	self queryForDirectoryToChange
     ]
 !
 
@@ -1509,8 +1509,8 @@
      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
+	      yesButton:'change') ifTrue:[
+	 self doChangeToHomeDirectory
     ]
 !
 
@@ -1519,8 +1519,8 @@
      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
+	      yesButton:'change') ifTrue:[
+	 self doChangeToParentDirectory
     ]
 !
 
@@ -1540,50 +1540,50 @@
     |labels selectors args menu|
 
     labels := #(
-                   'copy path'
-                   '-'                               
-                   'up'
-                   'back'
-                   'change to home-directory'
-                   'change directory ...'
-               ).             
+		   'copy path'
+		   '-'                               
+		   'up'
+		   'back'
+		   'change to home-directory'
+		   'change directory ...'
+	       ).             
 
     selectors := #(
-                    copyPath
-                    nil
-                    changeToParentDirectory
-                    changeToPreviousDirectory
-                    changeToHomeDirectory
-                    changeCurrentDirectory
-                  ).
+		    copyPath
+		    nil
+		    changeToParentDirectory
+		    changeToPreviousDirectory
+		    changeToHomeDirectory
+		    changeCurrentDirectory
+		  ).
 
     JavaClassReader notNil ifTrue:[
-        labels := labels , #('-' 'add to JavaClassPath' 'add to JavaSourcePath' 'remove from JavaClassPath' 'remove from JavaSourcePath').
-        selectors := selectors , #(nil #addDirToJavaClassPath #addDirToJavaSourcePath #removeDirFromJavaClassPath #removeDirFromJavaSourcePath).
+	labels := labels , #('-' 'add to JavaClassPath' 'add to JavaSourcePath' 'remove from JavaClassPath' 'remove from JavaSourcePath').
+	selectors := selectors , #(nil #addDirToJavaClassPath #addDirToJavaSourcePath #removeDirFromJavaClassPath #removeDirFromJavaSourcePath).
     ].
 
     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
-        ]
+	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.
+		labels:(resources array:labels)
+		selectors:selectors
+		args:args
+		receiver:self.
 
     previousDirectory isNil ifTrue:[
-        menu disable:#changeToPreviousDirectory.
+	menu disable:#changeToPreviousDirectory.
     ].
     ^menu.
 
@@ -1596,9 +1596,9 @@
     |queryBox dirName|
 
     queryBox := FilenameEnterBox 
-                    title:(resources at:'change directory to:') withCRs
-                    okText:(resources at:'change')
-                    action:[:newName | dirName := newName].
+		    title:(resources at:'change directory to:') withCRs
+		    okText:(resources at:'change')
+		    action:[:newName | dirName := newName].
 "/    queryBox initialText:''.
     queryBox showAtPointer.
     queryBox destroy.
@@ -1640,9 +1640,9 @@
     "common method to ask a yes/no question"
 
     ^ Dialog 
-        confirm:question withCRs
-        yesLabel:(resources at:yesButtonText)
-        noLabel:(resources at:noButtonText)
+	confirm:question withCRs
+	yesLabel:(resources at:yesButtonText)
+	noLabel:(resources at:noButtonText)
 
     "Modified: 21.2.1996 / 01:19:21 / cg"
 !
@@ -1654,12 +1654,12 @@
     |box|
 
     box := FilenameEnterBox 
-                title:(resources at:'execute unix command:')
-               okText:(resources at:'execute')
-               action:aBlock.
+		title:(resources at:'execute unix command:')
+	       okText:(resources at:'execute')
+	       action:aBlock.
 
     fileName notNil ifTrue:[
-        self initialCommandFor:fileName into:box.
+	self initialCommandFor:fileName into:box.
     ].
     box directory:currentDirectory pathName asFilename.
     box showAtPointer.
@@ -1672,11 +1672,11 @@
     "tell user, that code has been modified - let her confirm"
 
     (subView modified not or:[subView contentsWasSaved]) ifTrue:[
-        ^ true
+	^ true
     ].
     ^ self 
-        ask:(resources string:question)
-        yesButton:yesButtonText
+	ask:(resources string:question)
+	yesButton:yesButtonText
 !
 
 getSelectedFileName
@@ -1687,11 +1687,11 @@
 
     sel := fileListView selection.
     (sel size > 1) ifTrue:[
-        self onlyOneSelection
+	self onlyOneSelection
     ] ifFalse:[
-        sel notNil ifTrue:[
-            ^ fileList at:sel first
-        ]
+	sel notNil ifTrue:[
+	    ^ fileList at:sel first
+	]
     ].
     ^ nil
 !
@@ -1711,11 +1711,11 @@
 
     sel := fileListView selection.
     sel notNil ifTrue:[
-        self withWaitCursorDo:[
-            sel do:[:aSelectionIndex |
-                aBlock value:(fileList at:aSelectionIndex )
-            ]
-        ]
+	self withWaitCursorDo:[
+	    sel do:[:aSelectionIndex |
+		aBlock value:(fileList at:aSelectionIndex )
+	    ]
+	]
     ]
 
 !
@@ -1735,9 +1735,9 @@
     |msg|
 
     anErrorString isNil ifTrue:[
-        msg := aString
+	msg := aString
     ] ifFalse:[
-        msg := aString , '\\(' , anErrorString , ')'
+	msg := aString , '\\(' , anErrorString , ')'
     ].
     self warn:msg withCRs
 !
@@ -1750,18 +1750,18 @@
 
     newCollection := aCollection species new.
     aCollection do:[:fname |
-        |ignore|
-
-        ignore := false.
-
-        ((fname startsWith:'.') and:[fname ~= '..']) ifTrue:[
-            showDotFiles ifFalse:[
-                ignore := true
-            ]
-        ].
-        ignore ifFalse:[
-            newCollection add:fname
-        ]
+	|ignore|
+
+	ignore := false.
+
+	((fname startsWith:'.') and:[fname ~= '..']) ifTrue:[
+	    showDotFiles ifFalse:[
+		ignore := true
+	    ]
+	].
+	ignore ifFalse:[
+	    newCollection add:fname
+	]
     ].
     ^ newCollection
 
@@ -1775,8 +1775,8 @@
      action ..."
 
     (currentDirectory pathName asFilename construct:aFilename) isExecutable ifTrue:[
-        (OperatingSystem executeCommand:'cd ',currentDirectory pathName, '; ',aFilename)
-        ifTrue:[^true].
+	(OperatingSystem executeCommand:'cd ',currentDirectory pathName, '; ',aFilename)
+	ifTrue:[^true].
     ].
     ^ self imageAction:aFilename
 
@@ -1818,13 +1818,13 @@
      kill will make me raise the stopSignal when pressed
     "
     killButton 
-        action:[
-            stream notNil ifTrue:[
-                access critical:[
-                    myProcess interruptWith:[stopSignal raise].
-                ]
-            ]
-        ].
+	action:[
+	    stream notNil ifTrue:[
+		access critical:[
+		    myProcess interruptWith:[stopSignal raise].
+		]
+	    ]
+	].
 
     "
      pause makes me stop reading the commands output
@@ -1852,166 +1852,166 @@
     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 noPauseSema|
-
-                    stream buffered:true.
-                    codeView := subView.
-                    codeView unselect.
+	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 noPauseSema|
+
+		    stream buffered:true.
+		    codeView := subView.
+		    codeView unselect.
                 
-                    replace ifTrue:[
-                        codeView list:nil.
-                        lnr := 1.
-                    ].
-
-                    stillReplacing := replace.
-
-                    [stream atEnd] whileFalse:[
-                        pauseHolder value ifTrue:[
-                            "/    
-                            "/ allow interaction with
-                            "/ the codeView via the other windowGroup
-                            "/
-                            lowerFrameView windowGroup:(killButton windowGroup).
-
-                            "/
-                            "/ wait for pause to be turned off
-                            "/
-                            noPauseSema := Semaphore new.
-                            pauseHolder onChangeSend:#signal to:noPauseSema.
-                            noPauseSema wait.
-
-                            "/    
-                            "/ no interaction with the codeView ...
-                            "/
-                            lowerFrameView windowGroup:(self windowGroup).
-
-                        ] ifFalse:[
-                            (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.
-                                        ]
-                                    ].
-                                ].
-                            ].
-                        ].
-
-                        "
-                         give others running at same prio a chance too
-                         (especially other FileBrowsers doing the same)
-                        "
-                        Processor yield
-                    ].
-                ] valueNowOrOnUnwindDo:[
-                    stream shutDown "close". stream := nil.
-                ].
-
-                "/
-                "/ the command could have changed the directory
-                "/
-                self updateCurrentDirectoryIfChanged
-            ].
-            replace ifTrue:[
-                subView modified:false.
-            ].
-        ]
+		    replace ifTrue:[
+			codeView list:nil.
+			lnr := 1.
+		    ].
+
+		    stillReplacing := replace.
+
+		    [stream atEnd] whileFalse:[
+			pauseHolder value ifTrue:[
+			    "/    
+			    "/ allow interaction with
+			    "/ the codeView via the other windowGroup
+			    "/
+			    lowerFrameView windowGroup:(killButton windowGroup).
+
+			    "/
+			    "/ wait for pause to be turned off
+			    "/
+			    noPauseSema := Semaphore new.
+			    pauseHolder onChangeSend:#signal to:noPauseSema.
+			    noPauseSema wait.
+
+			    "/    
+			    "/ no interaction with the codeView ...
+			    "/
+			    lowerFrameView windowGroup:(self windowGroup).
+
+			] ifFalse:[
+			    (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.
+					]
+				    ].
+				].
+			    ].
+			].
+
+			"
+			 give others running at same prio a chance too
+			 (especially other FileBrowsers doing the same)
+			"
+			Processor yield
+		    ].
+		] valueNowOrOnUnwindDo:[
+		    stream shutDown "close". stream := nil.
+		].
+
+		"/
+		"/ the command could have changed the directory
+		"/
+		self updateCurrentDirectoryIfChanged
+	    ].
+	    replace ifTrue:[
+		subView modified:false.
+	    ].
+	]
       ]
     ] valueNowOrOnUnwindDo:[
-        |wg|
-
-        self label:myName; iconLabel:myName.
-        myProcess notNil ifTrue:[myProcess priority:myPriority].
-
-        "
-         hide the button, and make sure it will stay
-         hidden when we are realized again
-        "
-        killButton beInvisible.
-        pauseToggle beInvisible.
-
-        "
-         remove the killButton from its group
-         (otherwise, it will be destroyed when we shut down the group)
-        "
-        wg := killButton windowGroup.
-        killButton windowGroup:nil.
-        pauseToggle windowGroup:nil.
-
-        "
-         shut down the kill buttons windowgroup
-        "
-        wg notNil ifTrue:[
-            wg process terminate.
-        ].
-        "
-         clear its action (actually not needed, but
-         releases reference to thisContext earlier)
-        "
-        killButton action:nil.
-
-        "/    
-        "/ allow interaction with the codeView
-        "/ (bring it back into my group)
-        "/
-        lowerFrameView windowGroup:(self windowGroup).
+	|wg|
+
+	self label:myName; iconLabel:myName.
+	myProcess notNil ifTrue:[myProcess priority:myPriority].
+
+	"
+	 hide the button, and make sure it will stay
+	 hidden when we are realized again
+	"
+	killButton beInvisible.
+	pauseToggle beInvisible.
+
+	"
+	 remove the killButton from its group
+	 (otherwise, it will be destroyed when we shut down the group)
+	"
+	wg := killButton windowGroup.
+	killButton windowGroup:nil.
+	pauseToggle windowGroup:nil.
+
+	"
+	 shut down the kill buttons windowgroup
+	"
+	wg notNil ifTrue:[
+	    wg process terminate.
+	].
+	"
+	 clear its action (actually not needed, but
+	 releases reference to thisContext earlier)
+	"
+	killButton action:nil.
+
+	"/    
+	"/ allow interaction with the codeView
+	"/ (bring it back into my group)
+	"/
+	lowerFrameView windowGroup:(self windowGroup).
     ].
 
     currentFileName isNil ifTrue:[
-        subView modified:false.
+	subView modified:false.
     ].
 
     subView size > 10000 ifTrue:[
-        self warn:'text quite large now - please cut off some lines'
+	self warn:'text quite large now - please cut off some lines'
     ]
 
     "Modified: 21.9.1995 / 11:18:46 / claus"
@@ -2026,11 +2026,11 @@
 
     (Image isImageFileSuffix:(aFilename asFilename suffix))
     ifTrue:[
-        img := Image fromFile:(currentDirectory pathName asFilename construct:aFilename).
-        img notNil ifTrue:[
-            img inspect.
-            ^ true
-        ]
+	img := Image fromFile:(currentDirectory pathName asFilename construct:aFilename).
+	img notNil ifTrue:[
+	    img inspect.
+	    ^ true
+	]
     ].
     ^ false
 
@@ -2048,109 +2048,109 @@
 
     ((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
-        ].
-        (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'
-        ].
-        (lcFilename endsWith:'tar.z') ifTrue:[
-            cmd := 'zcat %1 | tar tvf -'.
-            select := false.
-        ].
-        (fileName endsWith:'.gz') ifTrue:[
-            cmd := 'gunzip %1'.
-        ].
-        (fileName endsWith:'tar.gz') ifTrue:[
-            cmd := ('gunzip < %1 | tar tvf -' ).
-            select := false.
-        ].
-        (fileName endsWith:'.tgz') ifTrue:[
-            cmd := ('gunzip < %1 | tar tvf -' ).
-            select := false.
-        ].
-        (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
-        ]
+	(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
+	].
+	(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'
+	].
+	(lcFilename endsWith:'tar.z') ifTrue:[
+	    cmd := 'zcat %1 | tar tvf -'.
+	    select := false.
+	].
+	(fileName endsWith:'.gz') ifTrue:[
+	    cmd := 'gunzip %1'.
+	].
+	(fileName endsWith:'tar.gz') ifTrue:[
+	    cmd := ('gunzip < %1 | tar tvf -' ).
+	    select := false.
+	].
+	(fileName endsWith:'.tgz') ifTrue:[
+	    cmd := ('gunzip < %1 | tar tvf -' ).
+	    select := false.
+	].
+	(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: 3.8.1997 / 16:55:26 / cg"
@@ -2165,16 +2165,16 @@
     fullPath := currentDirectory pathName asFilename constructString:aFilename.
     lcName := aFilename asLowercase.
     ((lcName endsWith:'.htm') or:[lcName endsWith:'.html']) ifTrue:[
-        HTMLDocumentView openOn:fullPath.
-        ^ true
+	HTMLDocumentView openOn:fullPath.
+	^ true
     ].
 
     OperatingSystem isUNIXlike ifTrue:[
-        (#('.man' '.1' '.2' '.3') findFirst:[:suff | aFilename endsWith:suff]) ~~ 0 
-        ifTrue:[
-             HTMLDocumentView openFullOnText:(HTMLDocGenerator manPageForFile:fullPath).
-            ^ true
-        ]
+	(#('.man' '.1' '.2' '.3') findFirst:[:suff | aFilename endsWith:suff]) ~~ 0 
+	ifTrue:[
+	     HTMLDocumentView openFullOnText:(HTMLDocGenerator manPageForFile:fullPath).
+	    ^ true
+	]
     ].
     ^ self imageAction:aFilename
 
@@ -2190,8 +2190,8 @@
 
     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 
+	      yesButton:'change') ifTrue:[
+	self doChangeCurrentDirectoryTo:previousDirectory updateHistory:false 
     ]
 !
 
@@ -2206,78 +2206,78 @@
     |oldSelection nOld here newState msg newLabel t|
 
     shown ifTrue:[
-        currentDirectory notNil ifTrue:[
-            lockUpdate ifTrue:[
-                Processor removeTimedBlock:checkBlock.
-                Processor addTimedBlock:checkBlock afterSeconds:checkDelta.
-                ^ self
-            ].
-
-            subView modified ifTrue:[
-                newState := ' (modified)'
-            ].
-
-            here := currentDirectory pathName.
-            (here asFilename isReadable) ifTrue:[
-                Processor removeTimedBlock:checkBlock.
-
-                t := currentDirectory timeOfLastChange.
-                (t notNil and:[t > 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 ...
-                "
-                (here asFilename exists) 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.
-            ]
-        ]
+	currentDirectory notNil ifTrue:[
+	    lockUpdate ifTrue:[
+		Processor removeTimedBlock:checkBlock.
+		Processor addTimedBlock:checkBlock afterSeconds:checkDelta.
+		^ self
+	    ].
+
+	    subView modified ifTrue:[
+		newState := ' (modified)'
+	    ].
+
+	    here := currentDirectory pathName.
+	    (here asFilename isReadable) ifTrue:[
+		Processor removeTimedBlock:checkBlock.
+
+		t := currentDirectory timeOfLastChange.
+		(t notNil and:[t > 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 ...
+		"
+		(here asFilename exists) 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.
+	    ]
+	]
     ]
 
     "Modified: 28.4.1997 / 19:40:34 / cg"
@@ -2288,75 +2288,78 @@
     "verify argument is name of a readable & executable directory
      and if so, go there"
 
-    |msg path idx|
+    |msg path idx f|
 
     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
+	path := currentDirectory pathName.
+	(f := fileName asFilename) isAbsolute ifFalse:[
+	    f := currentDirectory asFilename construct:fileName.
+	].
+	(f isDirectory) ifTrue:[
+	    (f isReadable) ifTrue:[
+		(f isExecutable) ifTrue:[
+		    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.
+
+		    "/ fetch the new path.
+		    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
     ]
 
     "Modified: 24.4.1997 / 22:41:46 / cg"
@@ -2369,22 +2372,22 @@
 !
 
 doChangeToParentDirectory
-    "go to home directory"
+    "go to parent directory"
 
     self doChangeCurrentDirectoryTo:'..' updateHistory:true
 !
 
 doCreateDirectory:newName
     (currentDirectory includes:newName) ifTrue:[
-        self warn:'%1 already exists.' with:newName.
-        ^ self
+	self warn:'%1 already exists.' with:newName.
+	^ self
     ].
 
     (currentDirectory createDirectory:newName) ifTrue:[
-        self updateCurrentDirectoryIfChanged
+	self updateCurrentDirectoryIfChanged
     ] ifFalse:[
-        self showAlert:(resources string:'cannot create directory ''%1'' !!' with:newName)
-                  with:(OperatingSystem lastErrorString)
+	self showAlert:(resources string:'cannot create directory ''%1'' !!' with:newName)
+		  with:(OperatingSystem lastErrorString)
     ]
 
     "Modified: 19.4.1997 / 15:30:32 / cg"
@@ -2397,19 +2400,19 @@
 
     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.
-        ]
+	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"
@@ -2418,7 +2421,7 @@
 
 updateCurrentDirectoryIfChanged
     (currentDirectory timeOfLastChange > timeOfLastCheck) ifTrue:[
-        self updateCurrentDirectory
+	self updateCurrentDirectory
     ]
 
     "Modified: 19.4.1997 / 15:30:03 / cg"
@@ -2428,9 +2431,9 @@
 
 guessEncodingFrom:aBuffer
     "look for a string
-        encoding #name
+	encoding #name
      or:
-        encoding: name
+	encoding: name
      within the given buffer 
      (which is usually the first few bytes of a textFile).
      If thats not found, use heuristics (in CharacterArray) to guess."
@@ -2442,55 +2445,55 @@
     n := aBuffer size.
 
     (idx := aBuffer findString:'charset=') ~~ 0 ifTrue:[
-        s := ReadStream on:aBuffer.
-        s position:idx + 8.
-        s skipSeparators.
-        w := s upToSeparator.
-        w notNil ifTrue:[
-            (idx := w indexOf:$") ~~ 0 ifTrue:[
-                w := w copyTo:idx-1
-            ].
-            ^ w asSymbol
-        ].
+	s := ReadStream on:aBuffer.
+	s position:idx + 8.
+	s skipSeparators.
+	w := s upToSeparator.
+	w notNil ifTrue:[
+	    (idx := w indexOf:$") ~~ 0 ifTrue:[
+		w := w copyTo:idx-1
+	    ].
+	    ^ w asSymbol
+	].
     ].
     (idx := aBuffer findString:'encoding') ~~ 0 ifTrue:[
-        s := ReadStream on:aBuffer.
-        s position:idx + 8.
-        s skipSeparators.
-        s peek == $: ifTrue:[
-            s next.
-            s skipSeparators. 
-        ].
-
-        s peek == $# ifTrue:[
-            s next.
-            s skipSeparators. 
-        ].
-        w := s upToSeparator.
-        w notNil ifTrue:[
-            ^ w asSymbol
-        ].
+	s := ReadStream on:aBuffer.
+	s position:idx + 8.
+	s skipSeparators.
+	s peek == $: ifTrue:[
+	    s next.
+	    s skipSeparators. 
+	].
+
+	s peek == $# ifTrue:[
+	    s next.
+	    s skipSeparators. 
+	].
+	w := s upToSeparator.
+	w notNil ifTrue:[
+	    ^ w asSymbol
+	].
     ].
 
     1 to:n do:[:i |
-        (aBuffer at:i) isPrintable ifFalse:[binary := true].
+	(aBuffer at:i) isPrintable ifFalse:[binary := true].
     ].
 
     binary ifTrue:[
-        "/ look for JIS7 / EUC encoding
-
-        enc := CharacterArray guessEncodingFrom:aBuffer.
-        enc notNil ifTrue:[
-            ^ enc
-        ].
-
-        "/ if the encoding has been set to any non iso setting,
-        "/ assume its what we defined ...
-
-        (('iso*' match:fileEncoding) or:['ascii*' match:fileEncoding]) ifTrue:[
-            ^ #binary
-        ].
-        ^ fileEncoding ? #binary
+	"/ look for JIS7 / EUC encoding
+
+	enc := CharacterArray guessEncodingFrom:aBuffer.
+	enc notNil ifTrue:[
+	    ^ enc
+	].
+
+	"/ if the encoding has been set to any non iso setting,
+	"/ assume its what we defined ...
+
+	(('iso*' match:fileEncoding) or:['ascii*' match:fileEncoding]) ifTrue:[
+	    ^ #binary
+	].
+	^ fileEncoding ? #binary
     ].
     ^ #ascii
 
@@ -2523,66 +2526,66 @@
     pref := self preferredFontEncodingFor:newEncoding.
 
     (pref match:fontsEncoding) ifTrue:[
-        ^ self
+	^ self
     ].
     "/ stupid ...
     pref = 'ascii*' ifTrue:[
-        (fontsEncoding match:'iso8859*') ifTrue:[
-            ^ self
-        ]
+	(fontsEncoding match:'iso8859*') ifTrue:[
+	    ^ self
+	]
     ].
 
     filter := [:f | |coding|
-                    (coding := f encoding) notNil 
-                    and:[pref match:coding]].
+		    (coding := f encoding) notNil 
+		    and:[pref match:coding]].
 
     defaultFont := TextView defaultFont onDevice:device.
     (pref match:(defaultFont encoding)) ifFalse:[
-        defaultFont := nil.
+	defaultFont := nil.
     ].
 
     defaultFont isNil ifTrue:[
-        (pref = 'ascii*'
-        or:[pref = 'iso8859*']) ifTrue:[
-            defaultFont := FontDescription family:'courier' face:'medium' style:'roman' size:12
-        ]
+	(pref = 'ascii*'
+	or:[pref = 'iso8859*']) ifTrue:[
+	    defaultFont := FontDescription family:'courier' face:'medium' style:'roman' size:12
+	]
     ].
 
     defaultFont isNil ifTrue:[
-        defaultFont := device 
-                            listOfAvailableFonts 
-                                detect:[:f | filter value:f]
-                                ifNone:nil.
-        defaultFont isNil ifTrue:[
-
-            "/ flush list, and refetch font list
-            "/ (in case someone just changed the font path ...)
-
-            device flushListOfAvailableFonts.
-            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.
-        ]
+	defaultFont := device 
+			    listOfAvailableFonts 
+				detect:[:f | filter value:f]
+				ifNone:nil.
+	defaultFont isNil ifTrue:[
+
+	    "/ flush list, and refetch font list
+	    "/ (in case someone just changed the font path ...)
+
+	    device flushListOfAvailableFonts.
+	    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.
+	]
     ].
 
     msg := 'switch to a %1 encoded font ?'.
     (ask not or:[self confirm:(resources string:msg with:pref) withCRs])
     ifTrue:[
-        self withWaitCursorDo:[
-            f := FontPanel 
-                fontFromUserInitial:defaultFont
-                              title:(resources string:'font selection')
-                             filter:filter.
-            f notNil ifTrue:[
-                subView font:f
-            ]
-        ]
+	self withWaitCursorDo:[
+	    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"
@@ -2597,19 +2600,19 @@
     |aStream|
 
     (currentDirectory includes:newName) ifTrue:[
-        (self
-            ask:(resources string:'%1 already exists\\truncate ?' with:newName)
-            yesButton:'truncate'
-        ) ifFalse:[^ self].
+	(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
+	aStream close.
+	self updateCurrentDirectoryIfChanged
     ] ifFalse:[
-        self showAlert:(resources string:'cannot create file ''%1'' !!' with:newName)
-                  with:(FileStream lastErrorString)
+	self showAlert:(resources string:'cannot create file ''%1'' !!' with:newName)
+		  with:(FileStream lastErrorString)
     ]
 
     "Modified: 23.4.1997 / 13:19:12 / cg"
@@ -2627,40 +2630,40 @@
     |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.
-        ]
+	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"
@@ -2683,60 +2686,60 @@
 
     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 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
+		self show:nil
 "
-                idx := fileList indexOf:fileName.
-                idx ~~ 0 ifTrue:[
-                    toRemove add:idx.
-                ]
-            ]
-        ].
+		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
-        ]
+	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"
@@ -2746,10 +2749,10 @@
     "rename file(s) (or directories)"
 
     (oldName notNil and:[newName notNil]) ifTrue:[
-        (oldName isBlank or:[newName isBlank]) ifFalse:[
-            currentDirectory renameFile:oldName newName:newName.
-            self updateCurrentDirectoryIfChanged.
-        ]
+	(oldName isBlank or:[newName isBlank]) ifFalse:[
+	    currentDirectory renameFile:oldName newName:newName.
+	    self updateCurrentDirectoryIfChanged.
+	]
     ]
 
     "Modified: 23.4.1997 / 13:19:37 / cg"
@@ -2768,18 +2771,18 @@
     (currentFileName = 'Make.proto'
     or:[currentFileName = 'Makefile'
     or:[currentFileName = 'makefile']]) ifTrue:[
-        ^ #('#' (nil nil)).
+	^ #('#' (nil nil)).
     ].
     ((currentFileName endsWith:'.c')
     or:[(currentFileName endsWith:'.C')]) ifTrue:[
-        ^ #(nil ('/*' '*/')).
+	^ #(nil ('/*' '*/')).
     ].
     ((currentFileName endsWith:'.cc')
     or:[(currentFileName endsWith:'.CC')]) ifTrue:[
-        ^ #('//' ('/*' '*/')).
+	^ #('//' ('/*' '*/')).
     ].
     (currentFileName endsWith:'.java') ifTrue:[
-        ^ #('//' (nil nil)).
+	^ #('//' (nil nil)).
     ].
 
     "/ smalltalk comments
@@ -2798,8 +2801,8 @@
 
     commentStrings := self fileCommentStrings.
     commentStrings notNil ifTrue:[
-        subView
-            commentStrings:#('#' (nil nil)).
+	subView
+	    commentStrings:#('#' (nil nil)).
     ].
 
     "Modified: 7.1.1997 / 20:30:54 / cg"
@@ -2819,27 +2822,27 @@
 
 "/    info := currentDirectory infoOf:fileName.
     info isNil ifTrue:[
-        self showAlert:(resources string:'cannot get info of ''%1'' !!' with:fileName)
-                  with:(OperatingSystem lastErrorString).
-        ^ nil
+	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))
+	text add:(resources string:'symbolic link to: %1' with:(f linkInfo path))
     ].
 
     type := info type.
     (longInfo and:[type == #regular]) ifTrue:[
-        fullPath := currentDirectory pathName asFilename constructString:fileName.
-        fileOutput := fullPath asFilename fileType.
+	fullPath := currentDirectory pathName asFilename constructString:fileName.
+	fileOutput := fullPath asFilename fileType.
     ].
 
     s := (resources at:'type:   ').
     fileOutput isNil ifTrue:[
-        s := s ,  type asString
+	s := s ,  type asString
     ] ifFalse:[
-        s := s , 'regular (' , fileOutput , ')'
+	s := s , 'regular (' , fileOutput , ')'
     ].
     text add:s.
     text add:(resources string:'size:   %1' with:(info size) printString).
@@ -2847,27 +2850,27 @@
     modeBits := info mode.
     modeString := self getModeString:modeBits.
     longInfo ifTrue:[
-        text add:(resources string:'access: %1 (%2)'
-                              with:modeString 
-                              with:(modeBits printStringRadix:8))
+	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:'access: %1' with:modeString)
     ].
     text add:(resources string:'owner:  %1'
-                          with:(OperatingSystem getUserNameFromID:(info uid))).
+			  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 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
 
@@ -2896,9 +2899,9 @@
        'info.txt'
        'INFO.TXT'
     ) do:[:f |
-        (currentDirectory isReadable:f) ifTrue:[
-            (currentDirectory isDirectory:f) ifFalse:[^ f].
-        ]
+	(currentDirectory isReadable:f) ifTrue:[
+	    (currentDirectory isDirectory:f) ifFalse:[^ f].
+	]
     ].
     ^ nil
 
@@ -2910,9 +2913,9 @@
      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 )
+		    with:#( 'owner:' $r $w $x 
+			    ' group:' $r $w $x 
+			    ' others:' $r $w $x )
 !
 
 getModeString:modeBits with:texts
@@ -2926,18 +2929,18 @@
 
     #( 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 
-        ]
+	|ch|
+
+	bitMask isNil ifTrue:[
+	    modeString := modeString , (resources string:access)
+	] ifFalse:[
+	    (bits bitAnd:bitMask) == 0 ifTrue:[
+		ch := $-
+	    ] ifFalse:[
+		ch := access
+	    ].
+	    modeString := modeString copyWith:ch 
+	]
     ].
     ^ modeString
 !
@@ -2949,7 +2952,7 @@
 
     info := self getInfoFile.
     info notNil ifTrue:[
-        txt := self readFile:info
+	txt := self readFile:info
     ].
     self show:txt.
 !
@@ -2966,15 +2969,15 @@
 "
     unitString := ''.
     size < (500 * 1024) ifTrue:[
-        size < 1024 ifTrue:[
-            n := size
-        ] ifFalse:[
-            n := (size * 10 // 1024 / 10.0).
-            unitString := ' Kb'
-        ]
+	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 := (size * 10 // 1024 // 1024 / 10.0).
+	unitString := ' Mb'
     ].
     ^ (n printStringLeftPaddedTo:5) , unitString.
 ! !
@@ -2999,18 +3002,18 @@
 
     stream := (currentDirectory asFilename construct:fileName) readStream.
     stream isNil ifTrue:[
-        msg := (resources string:'cannot read file ''%1'' !!' with:fileName).
-        self showAlert:msg with:(FileStream lastErrorString).
-        ^ nil
+	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 fileSize) > 1000000 ifTrue:[
-        Processor activeProcess withPriority:Processor userBackgroundPriority do:[
-            ObjectMemory announceSpaceNeed:(sz + (sz // 5)) "/ add 20% for tab expansion
-        ].
+	Processor activeProcess withPriority:Processor userBackgroundPriority do:[
+	    ObjectMemory announceSpaceNeed:(sz + (sz // 5)) "/ add 20% for tab expansion
+	].
     ].
 
     text := self readStream:stream lineDelimiter:aCharacter encoding:encoding.
@@ -3041,25 +3044,25 @@
 
     enc := encoding.
     enc == #iso8859 ifTrue:[
-        enc := nil
+	enc := nil
     ].
 
     aCharacter == Character cr ifTrue:[
-        [aStream atEnd] whileFalse:[
-            line := aStream nextLine withTabsExpanded.
-            enc notNil ifTrue:[
-                line := line decodeFrom:enc
-            ].
-            text add:line
-        ].
+	[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
-        ].
+	[aStream atEnd] whileFalse:[
+	    line := (aStream upTo:aCharacter) withTabsExpanded.
+	    enc notNil ifTrue:[
+		line := line decodeFrom:enc
+	    ].
+	    text add:line
+	].
     ].
     ^ text
 
@@ -3079,7 +3082,7 @@
     "show/insert contents of fileName in subView"
 
     ^ self 
-        showFile:fileName insert:insert encoding:encoding doubleClick:false
+	showFile:fileName insert:insert encoding:encoding doubleClick:false
 
     "Modified: 19.6.1996 / 09:40:19 / cg"
 !
@@ -3091,14 +3094,14 @@
      fontsEncoding pref failWarning|
 
     ((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
+	"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
     ].
 
     "/
@@ -3106,9 +3109,9 @@
     "/
     s := FileStream readonlyFileNamed:fileName in:currentDirectory.
     s isNil ifTrue:[
-        self showAlert:(resources string:'cannot read file ''%1'' !!' with:fileName)
-                  with:(FileStream lastErrorString).
-        ^ nil
+	self showAlert:(resources string:'cannot read file ''%1'' !!' with:fileName)
+		  with:(FileStream lastErrorString).
+	^ nil
     ].
 
     buffer := String new:4096.
@@ -3120,101 +3123,101 @@
     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]
+	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].
-        ].
-
-        fontsEncoding := subView font encoding.
-        pref := self preferredFontEncodingFor:guess.
-
-        ok := pref match:fontsEncoding.
-        ok ifFalse:[
-            pref = 'iso8859*' ifTrue:[
-                ok := 'ascii*' match:fontsEncoding
-            ]
-        ].
-        ok ifTrue:[
-            fileEncoding := guess.    
-            enc := guess.
-        ] ifFalse:[
-            action := Dialog choose:(resources string:'''%1'' seems to require a %2 font.' with:fileName with:pref)
-                           labels:(resources array:#('cancel' 'show' 'change font'))
-                           values:#(nil #show #encoding)
-                           default:#encoding.
-            action isNil ifTrue:[^ self].
-            action == #encoding ifTrue:[
-                fileEncoding := guess asSymbol.
-                subView externalEncoding:fileEncoding.
-                self validateFontEncodingFor:fileEncoding ask:false.
-            ] ifFalse:[
-                self information:(resources string:'Individual characters may be invisible/wrong in this font.')
-            ].
-            enc := fileEncoding.
-        ].
+	viaDoubleClick ifTrue:[
+	    (self nonBinaryFileAction:fileName) ifTrue:[^ self].
+	].
+
+	fontsEncoding := subView font encoding.
+	pref := self preferredFontEncodingFor:guess.
+
+	ok := pref match:fontsEncoding.
+	ok ifFalse:[
+	    pref = 'iso8859*' ifTrue:[
+		ok := 'ascii*' match:fontsEncoding
+	    ]
+	].
+	ok ifTrue:[
+	    fileEncoding := guess.    
+	    enc := guess.
+	] ifFalse:[
+	    action := Dialog choose:(resources string:'''%1'' seems to require a %2 font.' with:fileName with:pref)
+			   labels:(resources array:#('cancel' 'show' 'change font'))
+			   values:#(nil #show #encoding)
+			   default:#encoding.
+	    action isNil ifTrue:[^ self].
+	    action == #encoding ifTrue:[
+		fileEncoding := guess asSymbol.
+		subView externalEncoding:fileEncoding.
+		self validateFontEncodingFor:fileEncoding ask:false.
+	    ] ifFalse:[
+		self information:(resources string:'Individual characters may be invisible/wrong in this font.')
+	    ].
+	    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).
-            ]
-        ]
+	"/
+	"/ 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.
+	"/ 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
+	eol := Character value:13
     ] ifFalse:[
-        eol := Character cr
+	eol := Character cr
     ].
 
     failWarning := false.
     CharacterArray decodingFailedSignal handle:[:ex |
-        |errStr|
-
-        failWarning ifFalse:[
-            errStr := resources string:ex errorString.
-            (self confirm:(resources 
-                                string:'An error occurred while decoding:\%1\\The file has either a different encoding or is corrupted.\\Continue ?'
-                                with:errStr) withCRs)
-            ifFalse:[
-                ^ self
-            ].
-            failWarning := true.
-        ].
-        ex proceed.
+	|errStr|
+
+	failWarning ifFalse:[
+	    errStr := resources string:ex errorString.
+	    (self confirm:(resources 
+				string:'An error occurred while decoding:\%1\\The file has either a different encoding or is corrupted.\\Continue ?'
+				with:errStr) withCRs)
+	    ifFalse:[
+		^ self
+	    ].
+	    failWarning := true.
+	].
+	ex proceed.
     ] do:[
-        text := self readFile:fileName lineDelimiter:eol encoding:enc.
+	text := self readFile:fileName lineDelimiter:eol encoding:enc.
     ].
 
     insert ifFalse:[
-        self show:text
+	self show:text
     ] ifTrue:[
-        subView insertSelectedStringAtCursor:text asString
+	subView insertSelectedStringAtCursor:text asString
     ].
 
     "Created: 19.6.1996 / 09:39:52 / cg"
@@ -3226,38 +3229,38 @@
 
     stream := FileStream newFileNamed:fileName in:currentDirectory.
     stream isNil ifTrue:[
-        msg := (resources string:'cannot write file ''%1'' !!' with:fileName).
-        self showAlert:msg with:(FileStream lastErrorString)
+	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 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
+	].
+	stream close.
+	subView modified:false
     ]
 
     "Created: 22.2.1996 / 15:03:10 / cg"
@@ -3306,67 +3309,67 @@
 
     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
-            ].
-        ]
+	f isSymbolicLink ifTrue:[
+	    key := #directoryLink
+	] ifFalse:[
+	    key := #directory.
+	    (f isReadable not or:[f isExecutable not]) ifTrue:[
+		key := #directoryLocked
+	    ].
+	]
     ] ifFalse:[
-        f isSymbolicLink ifTrue:[
-            f isReadable not ifTrue:[
-                key := #fileLocked
-            ] ifFalse:[
-                key := #fileLink
-            ]
-        ] ifFalse:[
-            key := key2 := #file.
-            (f isReadable not) ifTrue:[
-                key := #fileLocked
-            ] ifFalse:[
-                suff := f suffix.
-                mime := MIMETypes mimeTypeForSuffix:suff.
-                mime notNil ifTrue:[
-                    (mime startsWith:'image/') ifTrue:[
-                        key := #imageFile
-                    ] ifFalse:[
-                        (mime startsWith:'text/') ifTrue:[
-                            key := #textFile
-                        ]
-                    ]
-                ].
-            ].
-        ].
+	f isSymbolicLink ifTrue:[
+	    f isReadable not ifTrue:[
+		key := #fileLocked
+	    ] ifFalse:[
+		key := #fileLink
+	    ]
+	] ifFalse:[
+	    key := key2 := #file.
+	    (f isReadable not) ifTrue:[
+		key := #fileLocked
+	    ] ifFalse:[
+		suff := f suffix.
+		mime := MIMETypes mimeTypeForSuffix:suff.
+		mime notNil ifTrue:[
+		    (mime startsWith:'image/') ifTrue:[
+			key := #imageFile
+		    ] ifFalse:[
+			(mime startsWith:'text/') ifTrue:[
+			    key := #textFile
+			]
+		    ]
+		].
+	    ].
+	].
     ].
 
     icons isNil ifTrue:[
-        icons := IdentityDictionary new
+	icons := IdentityDictionary new
     ].
 
     icn := icons at:key ifAbsent:nil.
     icn isNil ifTrue:[
-        Icons isNil ifTrue:[
-            self class initializeIcons
-        ].
-        icn := Icons at:key ifAbsent:nil.
-        icn notNil ifTrue:[
-            icn := icn on:device.
-            icons at:key put:icn.
-        ]
+	Icons isNil ifTrue:[
+	    self class initializeIcons
+	].
+	icn := Icons at:key ifAbsent:nil.
+	icn notNil ifTrue:[
+	    icn := icn on:device.
+	    icons at:key put:icn.
+	]
     ].
     icn isNil ifTrue:[
-        key2 notNil ifTrue:[
-            icn := icons at:key2 ifAbsent:nil.
-            icn isNil ifTrue:[
-                icn := Icons at:key2 ifAbsent:nil.
-                icn notNil ifTrue:[
-                    icn := icn on:device.
-                    icons at:key2 put:icn.
-                ]
-            ]
-        ]
+	key2 notNil ifTrue:[
+	    icn := icons at:key2 ifAbsent:nil.
+	    icn isNil ifTrue:[
+		icn := Icons at:key2 ifAbsent:nil.
+		icn notNil ifTrue:[
+		    icn := icn on:device.
+		    icons at:key2 put:icn.
+		]
+	    ]
+	]
     ].
     ^ icn
 
@@ -3376,8 +3379,8 @@
 stopUpdateProcess
     Processor removeTimedBlock:checkBlock.
     listUpdateProcess notNil ifTrue:[
-        listUpdateProcess terminate.
-        listUpdateProcess := nil.
+	listUpdateProcess terminate.
+	listUpdateProcess := nil.
     ].
 
     "Created: 19.4.1997 / 13:51:34 / cg"
@@ -3401,341 +3404,341 @@
     "
 
     self withReadCursorDo:[
-        |files matchPattern list passDone|
-
-        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.
-
-        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.
-
-        "
-         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
-             anyImages lineIndex aFileName
-             entry typ f p typeString done endIndex 
-             state stopAtEnd nextState img prevFirstLine prevLastLine
-             numVisible|
-
-            "/
-            "/ 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 := 'unknown'
-                                ].
-                            ] 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.
+	|files matchPattern list passDone|
+
+	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.
+
+	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.
+
+	"
+	 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
+	     anyImages lineIndex aFileName
+	     entry typ f p typeString done endIndex 
+	     state stopAtEnd nextState img prevFirstLine prevLastLine
+	     numVisible|
+
+	    "/
+	    "/ 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 := 'unknown'
+				].
+			    ] 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 contractTo:10.
-                                    nameString := nameString , (String new:(10 - nameString size))
-                                ].
-                                nameString isNil ifTrue:[nameString := '???'].
-                                entry colAt:4 put:nameString withoutSpaces.
-
-                                ((info gid) ~~ prevGid) ifTrue:[
-                                    prevGid := (info gid).
-                                    groupString := OperatingSystem getGroupNameFromID:prevGid.
+				    nameString := nameString , (String new:(10 - nameString size))
+				].
+				nameString isNil ifTrue:[nameString := '???'].
+				entry colAt:4 put:nameString withoutSpaces.
+
+				((info gid) ~~ prevGid) ifTrue:[
+				    prevGid := (info gid).
+				    groupString := OperatingSystem getGroupNameFromID:prevGid.
 				    groupString := groupString contractTo:10.
-                                    groupString := groupString , (String new:(10 - groupString size))
-                                ].
-                                groupString isNil ifTrue:[groupString := '???'].
-                                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
+				    groupString := groupString , (String new:(10 - groupString size))
+				].
+				groupString isNil ifTrue:[groupString := '???'].
+				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"
@@ -3755,5 +3758,5 @@
 !FileBrowser class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/FileBrowser.st,v 1.188 1997-09-10 21:35:00 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/FileBrowser.st,v 1.189 1997-09-15 21:22:40 cg Exp $'
 ! !