FileBrowser.st
changeset 294 a693bd6d7ae6
parent 288 99703e03b072
child 303 1d94813f1977
--- a/FileBrowser.st	Thu Dec 14 18:03:10 1995 +0100
+++ b/FileBrowser.st	Thu Dec 14 21:13:04 1995 +0100
@@ -408,28 +408,30 @@
 filePrint
     |fileName inStream printStream line|
 
-    self withCursor:(Cursor execute) do:[
-	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 nextPutAll:line.
-			    printStream cr
-			].
-			printStream close
-		    ].
-		    inStream close
-		]
-	    ]
-	].
-	0 "compiler hint"
+    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 nextPutAll:line.
+                            printStream cr
+                        ].
+                        printStream close
+                    ].
+                    inStream close
+                ]
+            ]
+        ].
+        0 "compiler hint"
     ]
+
+    "Modified: 14.12.1995 / 20:59:24 / cg"
 !
 
 fileRemove
@@ -1553,37 +1555,39 @@
 
     |fileName|
 
-    self withCursor:(Cursor read) do:[
-	fileName := self getSelectedFileName.
-	fileName notNil ifTrue:[
-	    (currentDirectory isDirectory:fileName) ifTrue:[
-		self doChangeCurrentDirectoryTo:fileName updateHistory:true.
-		self label:myName.
-		self iconLabel: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.
-		currentFileName := fileName.
+    self withReadCursorDo:[
+        fileName := self getSelectedFileName.
+        fileName notNil ifTrue:[
+            (currentDirectory isDirectory:fileName) ifTrue:[
+                self doChangeCurrentDirectoryTo:fileName updateHistory:true.
+                self label:myName.
+                self iconLabel: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.
+                currentFileName := fileName.
 
-		subView acceptAction:[:theCode |
-		    self writeFile:fileName text:theCode.
-		    timeOfFileRead := currentDirectory timeOfLastChange:fileName.
-		    self label:myName , ': ' , currentFileName
-		].
+                subView acceptAction:[:theCode |
+                    self writeFile:fileName text:theCode.
+                    timeOfFileRead := currentDirectory timeOfLastChange:fileName.
+                    self label:myName , ': ' , currentFileName
+                ].
 
-		(currentDirectory isWritable:fileName) ifFalse:[
-		    self label:(myName , ': ' , fileName , ' (readonly)')
-		] ifTrue:[
-		    self label:(myName , ': ' , fileName)
-		].
-		self iconLabel:fileName
-	    ]
-	]
+                (currentDirectory isWritable:fileName) ifFalse:[
+                    self label:(myName , ': ' , fileName , ' (readonly)')
+                ] ifTrue:[
+                    self label:(myName , ': ' , fileName)
+                ].
+                self iconLabel:fileName
+            ]
+        ]
     ]
+
+    "Modified: 14.12.1995 / 20:57:53 / cg"
 !
 
 doRemove
@@ -2136,161 +2140,162 @@
      ST/X users love this behavior ;-)
     "
 
-    self withCursor:(Cursor read) do:[
-	Processor removeTimedBlock:checkBlock.
+    self withReadCursorDo:[
+        Processor removeTimedBlock:checkBlock.
 
-	timeOfLastCheck := AbsoluteTime now.
+        timeOfLastCheck := AbsoluteTime now.
 
-	files := currentDirectory asOrderedCollection.
+        files := currentDirectory asOrderedCollection.
 
-	matchPattern := filterField contents.
-	(matchPattern notNil and:[
-	 matchPattern isEmpty not and:[
-	 matchPattern ~= '*']]) ifTrue:[
-	    files := files select:[:aName | 
-			 ((currentDirectory typeOf:aName) == #directory)
-			 or:[matchPattern match:aName]
-		     ].
-	].
-	files sort.
+        matchPattern := filterField contents.
+        (matchPattern notNil and:[
+         matchPattern isEmpty not and:[
+         matchPattern ~= '*']]) ifTrue:[
+            files := files select:[:aName | 
+                         ((currentDirectory typeOf:aName) == #directory)
+                         or:[matchPattern match:aName]
+                     ].
+        ].
+        files sort.
 
-	files size == 0 ifTrue:[
-	    self information:('directory ', currentDirectory pathName, ' vanished').
-	    ^ self
-	].
-	files := self withoutHiddenFiles:files.
-	fileList := files copy.
+        files size == 0 ifTrue:[
+            self information:('directory ', currentDirectory pathName, ' vanished').
+            ^ self
+        ].
+        files := self withoutHiddenFiles:files.
+        fileList := files copy.
 
-	"
-	 this is a time consuming operation (especially, if reading an
-	 NFS-mounted directory); therefore lower my priority while getting
-	 the files info ...
-	"
-	Processor activeProcess withLowerPriorityDo:[
+        "
+         this is a time consuming operation (especially, if reading an
+         NFS-mounted directory); therefore lower my priority while getting
+         the files info ...
+        "
+        Processor activeProcess withLowerPriorityDo:[
 
-	    "
-	     first show the names only - this is relatively fast
-	    "
-	    fileListView setList:files expandTabs:false.
+            "
+             first show the names only - this is relatively fast
+            "
+            fileListView setList:files expandTabs:false.
 
-	    "
-	     then walk over the files, adding more info
-	     (since we have to stat each file, this may take a while longer
-	    "
-	    showLongList ifTrue:[
-		tabSpec isNil ifTrue:[self defineTabulatorsForLongList].
+            "
+             then walk over the files, adding more info
+             (since we have to stat each file, this may take a while longer
+            "
+            showLongList ifTrue:[
+                tabSpec isNil ifTrue:[self defineTabulatorsForLongList].
 
-		text := OrderedCollection new.
-		files keysAndValuesDo:[:lineIndex :aFileName |
-		    |entry col typ f p typeString|
+                text := OrderedCollection new.
+                files keysAndValuesDo:[:lineIndex :aFileName |
+                    |entry col typ f p typeString|
 
-		    entry := MultiColListEntry new.
-		    entry tabulatorSpecification:tabSpec.
+                    entry := MultiColListEntry new.
+                    entry tabulatorSpecification:tabSpec.
 
-		    "
-		     if multiple FileBrowsers are reading, let others
-		     make some progress too
-		    "
-		    windowGroup notNil ifTrue:[windowGroup processExposeEvents].
-		    Processor yield.
-		    "
-		     could be destroyed in the meanwhile ...
-		    "
-		    realized ifFalse:[^ self].
+                    "
+                     if multiple FileBrowsers are reading, let others
+                     make some progress too
+                    "
+                    windowGroup notNil ifTrue:[windowGroup processExposeEvents].
+                    Processor yield.
+                    "
+                     could be destroyed in the meanwhile ...
+                    "
+                    realized ifFalse:[^ self].
 
-		    len := aFileName size.
-		    (len < 20) ifTrue:[
-			line := aFileName , (String new:(22 - len))
-		    ] ifFalse:[
-			"can happen on BSD only"
-			line := (aFileName copyTo:20) , '  '
-		    ].
-		    entry colAt:1 put:line.
+                    len := aFileName size.
+                    (len < 20) ifTrue:[
+                        line := aFileName , (String new:(22 - len))
+                    ] ifFalse:[
+                        "can happen on BSD only"
+                        line := (aFileName copyTo:20) , '  '
+                    ].
+                    entry colAt:1 put:line.
 
-		    info := currentDirectory infoOf:aFileName.
-		    info isNil ifTrue:[
-			"not accessable - usually a symlink,
-			 to a nonexisting/nonreadable file
-			"
-			entry colAt:2 put:'?'.
-			entry colAt:3 put:'(bad symbolic link ?)'.
-		    ] ifFalse:[
-			typ := (info at:#type).
-			(typ == #regular) ifFalse:[
-			    entry colAt:2 put:(typ at:1) asString.
-			] ifTrue:[
-			    entry colAt:2 put:' '.
-			].
+                    info := currentDirectory infoOf:aFileName.
+                    info isNil ifTrue:[
+                        "not accessable - usually a symlink,
+                         to a nonexisting/nonreadable file
+                        "
+                        entry colAt:2 put:'?'.
+                        entry colAt:3 put:'(bad symbolic link ?)'.
+                    ] ifFalse:[
+                        typ := (info at:#type).
+                        (typ == #regular) ifFalse:[
+                            entry colAt:2 put:(typ at:1) asString.
+                        ] ifTrue:[
+                            entry colAt:2 put:' '.
+                        ].
 
-			modeString := self getModeString:(info at:#mode)
-						    with:#( '' $r $w $x 
-							    '  ' $r $w $x 
-							    '  ' $r $w $x ).
-			entry colAt:3 put:modeString.
+                        modeString := self getModeString:(info at:#mode)
+                                                    with:#( '' $r $w $x 
+                                                            '  ' $r $w $x 
+                                                            '  ' $r $w $x ).
+                        entry colAt:3 put:modeString.
 
-			((info at:#uid) ~~ prevUid) ifTrue:[
-			    prevUid := (info at:#uid).
-			    nameString := OperatingSystem getUserNameFromID:prevUid.
-			    nameString := nameString , (String new:(10 - nameString size))
-			].
-			entry colAt:4 put:nameString withoutSpaces.
-			((info at:#gid) ~~ prevGid) ifTrue:[
-			    prevGid := (info at:#gid).
-			    groupString := OperatingSystem getGroupNameFromID:prevGid.
-			    groupString := groupString , (String new:(10 - groupString size))
-			].
-			entry colAt:5 put:groupString withoutSpaces.
+                        ((info at:#uid) ~~ prevUid) ifTrue:[
+                            prevUid := (info at:#uid).
+                            nameString := OperatingSystem getUserNameFromID:prevUid.
+                            nameString := nameString , (String new:(10 - nameString size))
+                        ].
+                        entry colAt:4 put:nameString withoutSpaces.
+                        ((info at:#gid) ~~ prevGid) ifTrue:[
+                            prevGid := (info at:#gid).
+                            groupString := OperatingSystem getGroupNameFromID:prevGid.
+                            groupString := groupString , (String new:(10 - groupString size))
+                        ].
+                        entry colAt:5 put:groupString withoutSpaces.
 
-			(typ == #regular) ifTrue:[
-			    entry colAt:6 put:(self sizePrintString:(info at:#size)).
-			].
+                        (typ == #regular) ifTrue:[
+                            entry colAt:6 put:(self sizePrintString:(info at:#size)).
+                        ].
 
-			f := currentDirectory asFilename:aFileName.
-			f isSymbolicLink ifTrue:[
-			    p := f linkInfo at:#path.    
-			    typeString := 'symbolic link to ' , p
-			] ifFalse:[        
-			    (showVeryLongList not or:[typ == #directory]) ifTrue:[
-				typeString := typ asString
-			    ] ifFalse:[
-				typeString := f fileType.
-			    ].
-			].
-			entry colAt:7 put:typeString.
-			text add:entry
-		    ].
-		    fileListView at:lineIndex put:entry
-		].
-	    ] ifFalse:[
-		files keysAndValuesDo:[:lineIndex :aName |
-		    |entry|
+                        f := currentDirectory asFilename:aFileName.
+                        f isSymbolicLink ifTrue:[
+                            p := f linkInfo at:#path.    
+                            typeString := 'symbolic link to ' , p
+                        ] ifFalse:[        
+                            (showVeryLongList not or:[typ == #directory]) ifTrue:[
+                                typeString := typ asString
+                            ] ifFalse:[
+                                typeString := f fileType.
+                            ].
+                        ].
+                        entry colAt:7 put:typeString.
+                        text add:entry
+                    ].
+                    fileListView at:lineIndex put:entry
+                ].
+            ] ifFalse:[
+                files keysAndValuesDo:[:lineIndex :aName |
+                    |entry|
 
-		    "
-		     if multiple FileBrowsers are reading, let others
-		     make some progress too
-		    "
-		    windowGroup notNil ifTrue:[windowGroup processExposeEvents].
-		    Processor yield.
-		    realized ifFalse:[^ self].
+                    "
+                     if multiple FileBrowsers are reading, let others
+                     make some progress too
+                    "
+                    windowGroup notNil ifTrue:[windowGroup processExposeEvents].
+                    Processor yield.
+                    realized ifFalse:[^ self].
 
-		    ((currentDirectory isDirectory:aName) and:[
-		    (aName ~= '..') and:[aName ~= '.']]) ifTrue:[
-			entry := aName , ' ...'
-		    ] ifFalse:[
-			entry := aName
-		    ].
-		    fileListView at:lineIndex put:entry
-		].
-	    ].
-	].
+                    ((currentDirectory isDirectory:aName) and:[
+                    (aName ~= '..') and:[aName ~= '.']]) ifTrue:[
+                        entry := aName , ' ...'
+                    ] ifFalse:[
+                        entry := aName
+                    ].
+                    fileListView at:lineIndex put:entry
+                ].
+            ].
+        ].
 
-	"
-	 install a new check after some time
-	"
-	Processor addTimedBlock:checkBlock afterSeconds:checkDelta
+        "
+         install a new check after some time
+        "
+        Processor addTimedBlock:checkBlock afterSeconds:checkDelta
     ]
 
     "Modified: 21.9.1995 / 11:40:23 / claus"
+    "Modified: 14.12.1995 / 20:59:09 / cg"
 !
 
 withoutHiddenFiles:aCollection
@@ -2363,4 +2368,4 @@
 !FileBrowser class methodsFor:'documentation'!
 
 version
-^ '$Header: /cvs/stx/stx/libtool/FileBrowser.st,v 1.62 1995-12-13 16:26:41 cg Exp $'! !
+^ '$Header: /cvs/stx/stx/libtool/FileBrowser.st,v 1.63 1995-12-14 20:12:07 cg Exp $'! !