slight cleanup
authorClaus Gittinger <cg@exept.de>
Wed, 21 Feb 1996 01:37:46 +0100
changeset 380 ec0cfd2b3200
parent 379 b7adadee426a
child 381 0b715d777c48
slight cleanup
FBrowser.st
FileBrowser.st
--- a/FBrowser.st	Wed Feb 21 00:07:17 1996 +0100
+++ b/FBrowser.st	Wed Feb 21 01:37:46 1996 +0100
@@ -943,28 +943,31 @@
     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."
+        "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.
+        (subView modified and:[subView contentsWasSaved not]) ifTrue:[
+            self raiseDeiconified.
 
-	    self ask:(resources at:'FileBrowser:\\contents has not been saved.\\Save before exiting ?') withCRs
-		 yesButton:'save'
-		 noButton:'don''t save'
-		 action:[
-			subView acceptAction notNil ifTrue:[
-			    subView accept
-			] ifFalse:[
-			    subView save
-			]
-		    ]
-	].
-	^ self
+            (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 redraw
+        fileListView redraw
     ].
+
+    "Modified: 21.2.1996 / 01:17:53 / cg"
 ! !
 
 !FileBrowser methodsFor:'pathField user interaction'!
@@ -1080,27 +1083,14 @@
 !
 
 ask:question yesButton:yesButtonText noButton:noButtonText
-    "common method to ask a yes/no question; return true or false"
-
-    self 
-	ask:question 
-	yesButton:yesButtonText 
-	noButton:noButtonText 
-	action:[^ true].
-    ^ false
-!
-
-ask:question yesButton:yesButtonText noButton:noButtonText action:aBlock
     "common method to ask a yes/no question"
 
-    |yesNoBox|
+    ^ Dialog 
+        confirm:question withCRs
+        yesLabel:(resources at:yesButtonText)
+        noLabel:(resources at:noButtonText)
 
-    yesNoBox := YesNoBox 
-		    title:question withCRs
-		  yesText:(resources at:yesButtonText)
-		   noText:(resources at:noButtonText).
-    yesNoBox okAction:aBlock.
-    yesNoBox showAtPointer
+    "Modified: 21.2.1996 / 01:19:21 / cg"
 !
 
 askForCommandThenDo:aBlock
@@ -1380,21 +1370,22 @@
     |aStream|
 
     (currentDirectory includes:newName) ifTrue:[
-	(self
-	    ask:(resources string:'%1 already exists\\truncate ?' with:newName)
-	    yesButton:'truncate'
-	    noButton:'cancel'
-	) 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 updateCurrentDirectory
+        aStream close.
+        self updateCurrentDirectory
     ] 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: 21.2.1996 / 01:24:16 / cg"
 !
 
 doExecuteCommand:command replace:replace
@@ -1571,43 +1562,44 @@
 doFileGet
     "get selected file - show contents in subView"
 
-    |fileName|
+    |fileName iconLbl winLbl|
 
     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.
+        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.
+                currentFileName := fileName.
 
-		subView acceptAction:[:theCode |
-		    self withCursor:(Cursor write) do:[
-			self writeFile:fileName text:theCode.
-			timeOfFileRead := currentDirectory timeOfLastChange:fileName.
-			self label:myName , ': ' , currentFileName
-		    ]
-		].
+                subView acceptAction:[:theCode |
+                    self withCursor:(Cursor write) do:[
+                        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
-	    ]
-	]
+                winLbl := myName , ': ' , fileName.
+                (currentDirectory isWritable:fileName) ifFalse:[
+                    winLbl := winLbl , ' (readonly)'
+                ].
+                iconLbl := fileName
+            ].
+            self label:winLbl.
+            self iconLabel:iconLbl.
+        ]
     ]
 
-    "Modified: 17.12.1995 / 15:42:16 / cg"
+    "Modified: 21.2.1996 / 01:28:35 / cg"
 !
 
 doRemove
@@ -1617,36 +1609,38 @@
 
     lockUpdate := true.
     [
-	self selectedFilesDo:[:fileName |
-	    ok := false.
-	    (currentDirectory isDirectory:fileName) ifTrue:[
-		dir := FileDirectory directoryNamed:fileName in:currentDirectory.
-		dir isEmpty ifFalse:[
-		    (self ask:(resources string:'directory ''%1'' is not empty\remove anyway ?' with:fileName)
-			  yesButton:'remove') ifTrue:[
-			 ok := currentDirectory removeDirectory:fileName
-		    ]
-		] ifTrue:[
-		    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 
+                or:[
+                    (self 
+                        ask:(resources string:'directory ''%1'' is not empty\remove anyway ?' with:fileName)
+                        yesButton:'remove')])
+                ifTrue:[
+                    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
 "
-	    ]
-	].
+            ]
+        ].
     ] valueNowOrOnUnwindDo:[
-	lockUpdate := false.
-	fileListView deselect.
-	self updateCurrentDirectory.
-    ]                
+        lockUpdate := false.
+        fileListView deselect.
+        self updateCurrentDirectory.
+    ]
+
+    "Modified: 21.2.1996 / 01:21:35 / cg"
 !
 
 doRename:oldName to:newName
@@ -2326,15 +2320,22 @@
 
     newCollection := aCollection species new.
     aCollection do:[:fname |
-	((fname startsWith:'.') and:[(fname = '..') not]) ifTrue:[
-	    showDotFiles ifTrue:[
-		newCollection add:fname
-	    ]
-	] ifFalse:[
-	    newCollection add:fname
-	]
+        |ignore|
+
+        ignore := false.
+
+        ((fname startsWith:'.') and:[fname ~= '..']) ifTrue:[
+            showDotFiles ifFalse:[
+                ignore := true
+            ]
+        ].
+        ignore ifFalse:[
+            newCollection add:fname
+        ]
     ].
     ^ newCollection
+
+    "Modified: 21.2.1996 / 01:33:18 / cg"
 !
 
 writeFile:fileName text:someText 
@@ -2388,4 +2389,4 @@
 !FileBrowser class methodsFor:'documentation'!
 
 version
-^ '$Header: /cvs/stx/stx/libtool/Attic/FBrowser.st,v 1.70 1996-02-08 23:26:59 cg Exp $'! !
+^ '$Header: /cvs/stx/stx/libtool/Attic/FBrowser.st,v 1.71 1996-02-21 00:37:46 cg Exp $'! !
--- a/FileBrowser.st	Wed Feb 21 00:07:17 1996 +0100
+++ b/FileBrowser.st	Wed Feb 21 01:37:46 1996 +0100
@@ -943,28 +943,31 @@
     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."
+        "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.
+        (subView modified and:[subView contentsWasSaved not]) ifTrue:[
+            self raiseDeiconified.
 
-	    self ask:(resources at:'FileBrowser:\\contents has not been saved.\\Save before exiting ?') withCRs
-		 yesButton:'save'
-		 noButton:'don''t save'
-		 action:[
-			subView acceptAction notNil ifTrue:[
-			    subView accept
-			] ifFalse:[
-			    subView save
-			]
-		    ]
-	].
-	^ self
+            (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 redraw
+        fileListView redraw
     ].
+
+    "Modified: 21.2.1996 / 01:17:53 / cg"
 ! !
 
 !FileBrowser methodsFor:'pathField user interaction'!
@@ -1080,27 +1083,14 @@
 !
 
 ask:question yesButton:yesButtonText noButton:noButtonText
-    "common method to ask a yes/no question; return true or false"
-
-    self 
-	ask:question 
-	yesButton:yesButtonText 
-	noButton:noButtonText 
-	action:[^ true].
-    ^ false
-!
-
-ask:question yesButton:yesButtonText noButton:noButtonText action:aBlock
     "common method to ask a yes/no question"
 
-    |yesNoBox|
+    ^ Dialog 
+        confirm:question withCRs
+        yesLabel:(resources at:yesButtonText)
+        noLabel:(resources at:noButtonText)
 
-    yesNoBox := YesNoBox 
-		    title:question withCRs
-		  yesText:(resources at:yesButtonText)
-		   noText:(resources at:noButtonText).
-    yesNoBox okAction:aBlock.
-    yesNoBox showAtPointer
+    "Modified: 21.2.1996 / 01:19:21 / cg"
 !
 
 askForCommandThenDo:aBlock
@@ -1380,21 +1370,22 @@
     |aStream|
 
     (currentDirectory includes:newName) ifTrue:[
-	(self
-	    ask:(resources string:'%1 already exists\\truncate ?' with:newName)
-	    yesButton:'truncate'
-	    noButton:'cancel'
-	) 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 updateCurrentDirectory
+        aStream close.
+        self updateCurrentDirectory
     ] 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: 21.2.1996 / 01:24:16 / cg"
 !
 
 doExecuteCommand:command replace:replace
@@ -1571,43 +1562,44 @@
 doFileGet
     "get selected file - show contents in subView"
 
-    |fileName|
+    |fileName iconLbl winLbl|
 
     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.
+        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.
+                currentFileName := fileName.
 
-		subView acceptAction:[:theCode |
-		    self withCursor:(Cursor write) do:[
-			self writeFile:fileName text:theCode.
-			timeOfFileRead := currentDirectory timeOfLastChange:fileName.
-			self label:myName , ': ' , currentFileName
-		    ]
-		].
+                subView acceptAction:[:theCode |
+                    self withCursor:(Cursor write) do:[
+                        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
-	    ]
-	]
+                winLbl := myName , ': ' , fileName.
+                (currentDirectory isWritable:fileName) ifFalse:[
+                    winLbl := winLbl , ' (readonly)'
+                ].
+                iconLbl := fileName
+            ].
+            self label:winLbl.
+            self iconLabel:iconLbl.
+        ]
     ]
 
-    "Modified: 17.12.1995 / 15:42:16 / cg"
+    "Modified: 21.2.1996 / 01:28:35 / cg"
 !
 
 doRemove
@@ -1617,36 +1609,38 @@
 
     lockUpdate := true.
     [
-	self selectedFilesDo:[:fileName |
-	    ok := false.
-	    (currentDirectory isDirectory:fileName) ifTrue:[
-		dir := FileDirectory directoryNamed:fileName in:currentDirectory.
-		dir isEmpty ifFalse:[
-		    (self ask:(resources string:'directory ''%1'' is not empty\remove anyway ?' with:fileName)
-			  yesButton:'remove') ifTrue:[
-			 ok := currentDirectory removeDirectory:fileName
-		    ]
-		] ifTrue:[
-		    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 
+                or:[
+                    (self 
+                        ask:(resources string:'directory ''%1'' is not empty\remove anyway ?' with:fileName)
+                        yesButton:'remove')])
+                ifTrue:[
+                    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
 "
-	    ]
-	].
+            ]
+        ].
     ] valueNowOrOnUnwindDo:[
-	lockUpdate := false.
-	fileListView deselect.
-	self updateCurrentDirectory.
-    ]                
+        lockUpdate := false.
+        fileListView deselect.
+        self updateCurrentDirectory.
+    ]
+
+    "Modified: 21.2.1996 / 01:21:35 / cg"
 !
 
 doRename:oldName to:newName
@@ -2326,15 +2320,22 @@
 
     newCollection := aCollection species new.
     aCollection do:[:fname |
-	((fname startsWith:'.') and:[(fname = '..') not]) ifTrue:[
-	    showDotFiles ifTrue:[
-		newCollection add:fname
-	    ]
-	] ifFalse:[
-	    newCollection add:fname
-	]
+        |ignore|
+
+        ignore := false.
+
+        ((fname startsWith:'.') and:[fname ~= '..']) ifTrue:[
+            showDotFiles ifFalse:[
+                ignore := true
+            ]
+        ].
+        ignore ifFalse:[
+            newCollection add:fname
+        ]
     ].
     ^ newCollection
+
+    "Modified: 21.2.1996 / 01:33:18 / cg"
 !
 
 writeFile:fileName text:someText 
@@ -2388,4 +2389,4 @@
 !FileBrowser class methodsFor:'documentation'!
 
 version
-^ '$Header: /cvs/stx/stx/libtool/FileBrowser.st,v 1.70 1996-02-08 23:26:59 cg Exp $'! !
+^ '$Header: /cvs/stx/stx/libtool/FileBrowser.st,v 1.71 1996-02-21 00:37:46 cg Exp $'! !