*** empty log message ***
authorclaus
Thu, 09 Mar 1995 04:31:23 +0100
changeset 79 d78f92a07d5d
parent 78 037323660c45
child 80 78f9581c78c6
*** empty log message ***
BrowserView.st
BrwsrView.st
FBrowser.st
FileBrowser.st
InspView.st
InspectorView.st
MemMonitor.st
MemoryMonitor.st
--- a/BrowserView.st	Mon Mar 06 23:07:15 1995 +0100
+++ b/BrowserView.st	Thu Mar 09 04:31:23 1995 +0100
@@ -29,7 +29,7 @@
 COPYRIGHT (c) 1989 by Claus Gittinger
 	     All Rights Reserved
 
-$Header: /cvs/stx/stx/libtool/BrowserView.st,v 1.1 1995-03-06 19:30:54 claus Exp $
+$Header: /cvs/stx/stx/libtool/BrowserView.st,v 1.2 1995-03-09 03:30:40 claus Exp $
 '!
 
 !BrowserView class methodsFor:'documentation'!
@@ -50,7 +50,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libtool/BrowserView.st,v 1.1 1995-03-06 19:30:54 claus Exp $
+$Header: /cvs/stx/stx/libtool/BrowserView.st,v 1.2 1995-03-09 03:30:40 claus Exp $
 "
 !
 
@@ -991,7 +991,7 @@
 
     |newList|
 
-    newList := OrderedCollection new.
+    newList := Set new.
     aClass methodArray do:[:aMethod |
 	|cat|
 
@@ -999,11 +999,11 @@
 	cat isNil ifTrue:[
 	    cat := '* no category *'
 	].
-	(newList includes:cat) ifFalse:[newList add:cat]
+	newList add:cat
     ].
     (newList size == 0) ifTrue:[^ nil].
     newList add:'* all *'.
-    ^ newList sort
+    ^ newList asOrderedCollection sort
 !
 
 methodCategorySelection:lineNr
@@ -1061,7 +1061,7 @@
 
     |newList|
 
-    newList := OrderedCollection new.
+    newList := Set new.
     self classesInFullProtocolHierarchy:aClass do:[:c |
 	|cat|
 
@@ -1070,12 +1070,12 @@
 	    cat isNil ifTrue:[
 		cat := '* no category *'
 	    ].
-	    (newList includes:cat) ifFalse:[newList add:cat]
+	    newList add:cat
 	]
     ].
     (newList size == 0) ifTrue:[^ nil].
     newList add:'* all *'.
-    ^ newList sort
+    ^ newList asOrderedCollection sort
 !
 
 checkMethodCategorySelected
@@ -1247,7 +1247,11 @@
 			    ^ self
 			].
 			"compare the source codes"
-			self warnLabel:'the code shown may not up to date'.
+			currentMethod notNil ifTrue:[
+			    changedMethod source = codeView contents ifFalse:[
+				self warnLabel:'the code shown may not up to date'.
+			    ]
+			].
 			^ self    
 		    ].
 		    ^ self
@@ -2023,43 +2027,43 @@
 listOfAllClassesInCategory:aCategory
     "return a list of all classes in a given category"
 
-    |newList classList searchCategory string|
-
-    newList := OrderedCollection new.
+    |newList classes searchCategory nm|
+
+    (aCategory = '* hierarchy *') ifTrue:[
+	newList := OrderedCollection new.
+	classes := Set new.
+	self classHierarchyDo:[:aClass :lvl|
+	    nm := aClass name.
+	    (classes includes:nm) ifFalse:[
+		classes add:nm.
+		newList add:(String new:lvl) , nm
+	    ]
+	].
+	^ newList
+    ].
+
+    newList := Set new.
+
     (aCategory = '* all *') ifTrue:[
 	Smalltalk allBehaviorsDo:[:aClass |
-	    string := aClass name.
-	    newList indexOf:string ifAbsent:[newList add:string]
+	    newList add:aClass name
 	]
     ] ifFalse:[
-	(aCategory = '* hierarchy *') ifTrue:[
-	    classList := OrderedCollection new.
-	    self classHierarchyDo:[:aClass :lvl|
-		string := aClass name.
-		classList indexOf:string ifAbsent:[
-		    classList add:string.
-		    newList add:(String new:lvl) , string
-		]
-	    ].
-	    ^ newList
+	(aCategory = '* no category *') ifTrue:[
+	    searchCategory := nil
 	] ifFalse:[
-	    (aCategory = '* no category *') ifTrue:[
-		searchCategory := nil
-	    ] ifFalse:[
-		searchCategory := aCategory
-	    ].
-	    Smalltalk allBehaviorsDo:[:aClass |
-		aClass isMeta ifFalse:[
-		    (aClass category = searchCategory) ifTrue:[
-			string := aClass name.
-			newList indexOf:string ifAbsent:[newList add:string]
-		    ]
+	    searchCategory := aCategory
+	].
+	Smalltalk allBehaviorsDo:[:aClass |
+	    aClass isMeta ifFalse:[
+		(aClass category = searchCategory) ifTrue:[
+		    newList add:aClass name
 		]
 	    ]
 	]
     ].
     (newList size == 0) ifTrue:[^ nil].
-    ^ newList sort
+    ^ newList asOrderedCollection sort
 !
 
 classSelection:lineNr
@@ -2872,7 +2876,7 @@
     ].
     cat := currentClassCategory.
     cat isNil ifTrue:[
-	cat := 'no category'
+	cat := '* no category *'
     ].
     self classClassDefinitionTemplateFor:nm in:cat.
     aspect := nil.
@@ -2918,17 +2922,23 @@
 classLoad
     "load an autoloaded class"
 
+    |nm|
+
     self checkClassSelected ifFalse:[^ self].
-    currentClass unload.
-    self switchToClassNamed:currentClass name
+    nm := currentClass name.
+    currentClass autoload.
+    self switchToClassNamed:nm
 !
 
 classUnload
-    "load an autoloaded class"
+    "unload an autoloaded class"
+
+    |nm|
 
     self checkClassSelected ifFalse:[^ self].
+    nm := currentClass name.
     currentClass unload.
-    self switchToClassNamed:currentClass name
+    self switchToClassNamed:nm
 !
 
 classProtocols
@@ -3140,19 +3150,19 @@
 
     |newList cat|
 
-    newList := OrderedCollection new.
+    newList := Set new.
     self classesInHierarchy:aClass do:[:c |
 	c methodArray do:[:aMethod |
 	    cat := aMethod category.
 	    cat isNil ifTrue:[
 		cat := '* no category *'
 	    ].
-	    (newList includes:cat) ifFalse:[newList add:cat]
+	    newList add:cat
 	]
     ].
     (newList size == 0) ifTrue:[^ nil].
     newList add:'* all *'.
-    ^ newList sort
+    ^ newList asOrderedCollection sort
 
 ! !
 
@@ -3163,15 +3173,15 @@
 
     |newList cat|
 
-    newList := OrderedCollection with:'* all *' with:'* hierarchy *'.
+    newList := Set with:'* all *' with:'* hierarchy *'.
     Smalltalk allBehaviorsDo:[:aClass |
 	cat := aClass category.
 	cat isNil ifTrue:[
 	    cat := '* no category *'
 	].
-	newList indexOf:cat ifAbsent:[newList add:cat]
+	newList add:cat
     ].
-    ^ newList asArray sort.
+    ^ newList asOrderedCollection sort.
 !
 
 classCategorySelectionChanged
@@ -3598,14 +3608,13 @@
 	|categories|
 
 	currentClass notNil ifTrue:[
-	    categories := OrderedCollection new.
+	    categories := Set new.
 	    currentClass withAllSuperclasses do:[:aClass |
 		aClass methodArray do:[:aMethod |
-		    (categories includes:aMethod category) ifFalse:[
-			categories add:aMethod category
-		    ]
+		    categories add:aMethod category
 		]
 	    ].
+	    categories := categories asOrderedCollection
 	].
 	categories isNil ifTrue:[
 	    categories := classCategoryListView list.
--- a/BrwsrView.st	Mon Mar 06 23:07:15 1995 +0100
+++ b/BrwsrView.st	Thu Mar 09 04:31:23 1995 +0100
@@ -29,7 +29,7 @@
 COPYRIGHT (c) 1989 by Claus Gittinger
 	     All Rights Reserved
 
-$Header: /cvs/stx/stx/libtool/Attic/BrwsrView.st,v 1.1 1995-03-06 19:30:54 claus Exp $
+$Header: /cvs/stx/stx/libtool/Attic/BrwsrView.st,v 1.2 1995-03-09 03:30:40 claus Exp $
 '!
 
 !BrowserView class methodsFor:'documentation'!
@@ -50,7 +50,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libtool/Attic/BrwsrView.st,v 1.1 1995-03-06 19:30:54 claus Exp $
+$Header: /cvs/stx/stx/libtool/Attic/BrwsrView.st,v 1.2 1995-03-09 03:30:40 claus Exp $
 "
 !
 
@@ -991,7 +991,7 @@
 
     |newList|
 
-    newList := OrderedCollection new.
+    newList := Set new.
     aClass methodArray do:[:aMethod |
 	|cat|
 
@@ -999,11 +999,11 @@
 	cat isNil ifTrue:[
 	    cat := '* no category *'
 	].
-	(newList includes:cat) ifFalse:[newList add:cat]
+	newList add:cat
     ].
     (newList size == 0) ifTrue:[^ nil].
     newList add:'* all *'.
-    ^ newList sort
+    ^ newList asOrderedCollection sort
 !
 
 methodCategorySelection:lineNr
@@ -1061,7 +1061,7 @@
 
     |newList|
 
-    newList := OrderedCollection new.
+    newList := Set new.
     self classesInFullProtocolHierarchy:aClass do:[:c |
 	|cat|
 
@@ -1070,12 +1070,12 @@
 	    cat isNil ifTrue:[
 		cat := '* no category *'
 	    ].
-	    (newList includes:cat) ifFalse:[newList add:cat]
+	    newList add:cat
 	]
     ].
     (newList size == 0) ifTrue:[^ nil].
     newList add:'* all *'.
-    ^ newList sort
+    ^ newList asOrderedCollection sort
 !
 
 checkMethodCategorySelected
@@ -1247,7 +1247,11 @@
 			    ^ self
 			].
 			"compare the source codes"
-			self warnLabel:'the code shown may not up to date'.
+			currentMethod notNil ifTrue:[
+			    changedMethod source = codeView contents ifFalse:[
+				self warnLabel:'the code shown may not up to date'.
+			    ]
+			].
 			^ self    
 		    ].
 		    ^ self
@@ -2023,43 +2027,43 @@
 listOfAllClassesInCategory:aCategory
     "return a list of all classes in a given category"
 
-    |newList classList searchCategory string|
-
-    newList := OrderedCollection new.
+    |newList classes searchCategory nm|
+
+    (aCategory = '* hierarchy *') ifTrue:[
+	newList := OrderedCollection new.
+	classes := Set new.
+	self classHierarchyDo:[:aClass :lvl|
+	    nm := aClass name.
+	    (classes includes:nm) ifFalse:[
+		classes add:nm.
+		newList add:(String new:lvl) , nm
+	    ]
+	].
+	^ newList
+    ].
+
+    newList := Set new.
+
     (aCategory = '* all *') ifTrue:[
 	Smalltalk allBehaviorsDo:[:aClass |
-	    string := aClass name.
-	    newList indexOf:string ifAbsent:[newList add:string]
+	    newList add:aClass name
 	]
     ] ifFalse:[
-	(aCategory = '* hierarchy *') ifTrue:[
-	    classList := OrderedCollection new.
-	    self classHierarchyDo:[:aClass :lvl|
-		string := aClass name.
-		classList indexOf:string ifAbsent:[
-		    classList add:string.
-		    newList add:(String new:lvl) , string
-		]
-	    ].
-	    ^ newList
+	(aCategory = '* no category *') ifTrue:[
+	    searchCategory := nil
 	] ifFalse:[
-	    (aCategory = '* no category *') ifTrue:[
-		searchCategory := nil
-	    ] ifFalse:[
-		searchCategory := aCategory
-	    ].
-	    Smalltalk allBehaviorsDo:[:aClass |
-		aClass isMeta ifFalse:[
-		    (aClass category = searchCategory) ifTrue:[
-			string := aClass name.
-			newList indexOf:string ifAbsent:[newList add:string]
-		    ]
+	    searchCategory := aCategory
+	].
+	Smalltalk allBehaviorsDo:[:aClass |
+	    aClass isMeta ifFalse:[
+		(aClass category = searchCategory) ifTrue:[
+		    newList add:aClass name
 		]
 	    ]
 	]
     ].
     (newList size == 0) ifTrue:[^ nil].
-    ^ newList sort
+    ^ newList asOrderedCollection sort
 !
 
 classSelection:lineNr
@@ -2872,7 +2876,7 @@
     ].
     cat := currentClassCategory.
     cat isNil ifTrue:[
-	cat := 'no category'
+	cat := '* no category *'
     ].
     self classClassDefinitionTemplateFor:nm in:cat.
     aspect := nil.
@@ -2918,17 +2922,23 @@
 classLoad
     "load an autoloaded class"
 
+    |nm|
+
     self checkClassSelected ifFalse:[^ self].
-    currentClass unload.
-    self switchToClassNamed:currentClass name
+    nm := currentClass name.
+    currentClass autoload.
+    self switchToClassNamed:nm
 !
 
 classUnload
-    "load an autoloaded class"
+    "unload an autoloaded class"
+
+    |nm|
 
     self checkClassSelected ifFalse:[^ self].
+    nm := currentClass name.
     currentClass unload.
-    self switchToClassNamed:currentClass name
+    self switchToClassNamed:nm
 !
 
 classProtocols
@@ -3140,19 +3150,19 @@
 
     |newList cat|
 
-    newList := OrderedCollection new.
+    newList := Set new.
     self classesInHierarchy:aClass do:[:c |
 	c methodArray do:[:aMethod |
 	    cat := aMethod category.
 	    cat isNil ifTrue:[
 		cat := '* no category *'
 	    ].
-	    (newList includes:cat) ifFalse:[newList add:cat]
+	    newList add:cat
 	]
     ].
     (newList size == 0) ifTrue:[^ nil].
     newList add:'* all *'.
-    ^ newList sort
+    ^ newList asOrderedCollection sort
 
 ! !
 
@@ -3163,15 +3173,15 @@
 
     |newList cat|
 
-    newList := OrderedCollection with:'* all *' with:'* hierarchy *'.
+    newList := Set with:'* all *' with:'* hierarchy *'.
     Smalltalk allBehaviorsDo:[:aClass |
 	cat := aClass category.
 	cat isNil ifTrue:[
 	    cat := '* no category *'
 	].
-	newList indexOf:cat ifAbsent:[newList add:cat]
+	newList add:cat
     ].
-    ^ newList asArray sort.
+    ^ newList asOrderedCollection sort.
 !
 
 classCategorySelectionChanged
@@ -3598,14 +3608,13 @@
 	|categories|
 
 	currentClass notNil ifTrue:[
-	    categories := OrderedCollection new.
+	    categories := Set new.
 	    currentClass withAllSuperclasses do:[:aClass |
 		aClass methodArray do:[:aMethod |
-		    (categories includes:aMethod category) ifFalse:[
-			categories add:aMethod category
-		    ]
+		    categories add:aMethod category
 		]
 	    ].
+	    categories := categories asOrderedCollection
 	].
 	categories isNil ifTrue:[
 	    categories := classCategoryListView list.
--- a/FBrowser.st	Mon Mar 06 23:07:15 1995 +0100
+++ b/FBrowser.st	Thu Mar 09 04:31:23 1995 +0100
@@ -29,7 +29,7 @@
 COPYRIGHT (c) 1991 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libtool/Attic/FBrowser.st,v 1.32 1995-03-06 19:31:30 claus Exp $
+$Header: /cvs/stx/stx/libtool/Attic/FBrowser.st,v 1.33 1995-03-09 03:31:04 claus Exp $
 '!
 
 !FileBrowser class methodsFor:'documentation'!
@@ -50,7 +50,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libtool/Attic/FBrowser.st,v 1.32 1995-03-06 19:31:30 claus Exp $
+$Header: /cvs/stx/stx/libtool/Attic/FBrowser.st,v 1.33 1995-03-09 03:31:04 claus Exp $
 "
 !
 
@@ -116,7 +116,7 @@
 !FileBrowser methodsFor:'initialization'!
 
 initialize
-    |frame spacing halfSpacing v cutOff topFrame labelFrame|
+    |frame spacing halfSpacing v topFrame labelFrame|
 
     super initialize.
 
@@ -163,12 +163,6 @@
     spacing := ViewSpacing.
     halfSpacing := spacing // 2.
 
-    StyleSheet is3D ifFalse:[
-	cutOff := halfSpacing
-    ] ifTrue:[
-	cutOff := 0
-    ].
-
     checkBlock := [self checkIfDirectoryHasChanged].
     checkDelta := resources at:'CHECK_DELTA' default:10.
 
@@ -297,12 +291,6 @@
     ]
 !
 
-ask:question yesButton:yesButtonText action:aBlock
-    "common method to ask a yes/no question"
-
-    self ask:question yesButton:yesButtonText noButton:'cancel' action:aBlock
-!
-
 ask:question yesButton:yesButtonText noButton:noButtonText action:aBlock
     "common method to ask a yes/no question"
 
@@ -316,16 +304,27 @@
     yesNoBox showAtPointer
 !
 
-askIfModified:question yesButton:yesButtonText action:aBlock
+ask:question yesButton:yesButtonText
+    "common method to ask a yes/no question; return true or false"
+
+    self ask:question 
+	 yesButton:yesButtonText 
+	 noButton:'cancel' 
+	 action:[^ true].
+    ^ false
+!
+
+askIfModified:question yesButton:yesButtonText
     "tell user, that code has been modified - let her confirm"
 
     (subView modified not or:[subView contentsWasSaved]) ifTrue:[
-	aBlock value.
-	^ self
+	^ true
     ].
     self ask:(resources string:question) withCRs
-	 yesButton:yesButtonText 
-	 action:aBlock
+	 yesButton:yesButtonText
+	 noButton:'cancel' 
+	 action:[^ true].
+    ^ false
 !
 
 withoutHiddenFiles:aCollection
@@ -868,12 +867,10 @@
      otherwise change immediately to previous directory."
 
     previousDirectory isNil ifTrue:[^ self].
-    self askIfModified:('contents has not been saved.\\Modifications will be lost when directory is changed.')
-	 yesButton:'change'
-	 action:[
-		    self doChangeCurrentDirectoryTo:previousDirectory  
-				      updateHistory:false 
-		]
+    (self askIfModified:'contents has not been saved.\\Modifications will be lost when directory is changed.'
+	      yesButton:'change') ifTrue:[
+	self doChangeCurrentDirectoryTo:previousDirectory updateHistory:false 
+    ]
 !
 
 setCurrentDirectory:aPathName
@@ -1400,8 +1397,11 @@
 
     |fileName sel box|
 
-    box := FilenameEnterBox new.
-    box initialText:''.
+    box := FilenameEnterBox 
+		title:(resources at:'execute unix command:')
+	       okText:(resources at:'execute')
+	       action:aBlock.
+"/    box initialText:''.
 
     sel := fileListView selection.
     sel isCollection ifFalse:[
@@ -1412,9 +1412,6 @@
     fileName notNil ifTrue:[
 	self initialCommandFor:fileName into:box.
     ].
-    box title:(resources at:'execute unix command:').
-    box okText:(resources at:'execute').
-    box action:aBlock.
     box showAtPointer
 !
 
@@ -1460,9 +1457,10 @@
 	    (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'
-			 action:[currentDirectory removeDirectory:fileName]
+		    (self ask:(resources string:'directory ''%1'' is not empty\remove anyway ?' with:fileName)
+			  yesButton:'remove') ifTrue:[
+			 currentDirectory removeDirectory:fileName
+		    ]
 		] ifTrue:[
 		    currentDirectory removeDirectory:fileName
 		].
@@ -1498,9 +1496,8 @@
 terminate
     "exit FileBrowser"
 
-    self askIfModified:'contents has not been saved.\\Modifications will be lost when FileBrowser is closed.'
-	 yesButton:'close'
-	 action:[self destroy]
+    (self askIfModified:'contents has not been saved.\\Modifications will be lost when FileBrowser is closed.'
+	      yesButton:'close') ifTrue:[self destroy]
 !
 
 destroy
@@ -1614,27 +1611,30 @@
     "if text was modified show a queryBox, 
      otherwise change immediately to directory"
 
-    self askIfModified:'contents has not been saved.\\Modifications will be lost when directory is changed.'
-	 yesButton:'change'
-	 action:[self queryForDirectoryToChange]
+    (self askIfModified:'contents has not been saved.\\Modifications will be lost when directory is changed.'
+	      yesButton:'change') ifTrue:[
+	self queryForDirectoryToChange
+    ]
 !
 
 changeToParentDirectory
     "if text was modified show a queryBox, 
      otherwise change immediately to directory"
 
-    self askIfModified:'contents has not been saved.\\Modifications will be lost when directory is changed.'
-	 yesButton:'change'
-	 action:[self doChangeToParentDirectory]
+    (self askIfModified:'contents has not been saved.\\Modifications will be lost when directory is changed.'
+	      yesButton:'change') ifTrue:[
+	 self doChangeToParentDirectory
+    ]
 !
 
 changeToHomeDirectory
     "if text was modified show a queryBox, 
      otherwise change immediately to directory"
 
-    self askIfModified:'contents has not been saved.\\Modifications will be lost when directory is changed.'
-	 yesButton:'change'
-	 action:[self doChangeToHomeDirectory]
+    (self askIfModified:'contents has not been saved.\\Modifications will be lost when directory is changed.'
+	      yesButton:'change') ifTrue:[
+	 self doChangeToHomeDirectory
+    ]
 !
 
 queryForDirectoryToChange
@@ -1642,10 +1642,11 @@
 
     |queryBox|
 
-    queryBox := FilenameEnterBox title:(resources at:'change directory to:') withCRs.
-    queryBox initialText:''.
-    queryBox okText:(resources at:'change').
-    queryBox action:[:newName | self doChangeCurrentDirectoryTo:newName updateHistory:true].
+    queryBox := FilenameEnterBox 
+		    title:(resources at:'change directory to:') withCRs
+		    okText:(resources at:'change')
+		    action:[:newName | self doChangeCurrentDirectoryTo:newName updateHistory:true].
+"/    queryBox initialText:''.
     queryBox showAtPointer
 ! !
 
@@ -1756,22 +1757,20 @@
 
     |action|
 
-    true ifTrue:[
-	"
-	 this replaces everything by the commands output ...
-	"
-	action := [:command| self doExecuteCommand:command replace:true].
+    "
+     this replaces everything by the commands output ...
+    "
+    action := [:command| self doExecuteCommand:command replace:true].
 
-	self askIfModified:'contents has not been saved.\\Modifications will be lost when command is executed.'
-		 yesButton:'execute'
-		 action:[self askForCommandThenDo:action]
-    ] ifFalse:[
-	"
-	 this inserts the commands output ...
-	"
-	action := [:command| self doExecuteCommand:command replace:false].
-	self askForCommandThenDo:action
-    ]
+    (self askIfModified:'contents has not been saved.\\Modifications will be lost when command is executed.'
+	      yesButton:'execute') ifFalse:[^ self].
+
+"/    "
+"/     this inserts the commands output ...
+"/    "
+"/    action := [:command| self doExecuteCommand:command replace:false].
+"/
+    self askForCommandThenDo:action
 !
 
 openTool:aToolClass
@@ -1821,13 +1820,15 @@
     fileName := self getSelectedFileName.
     fileName notNil ifTrue:[
 	(currentDirectory isDirectory:fileName) ifTrue:[
-	    msg := (resources at:'contents has not been saved.\\Modifications will be lost when directory is changed.').
+	    msg := 'contents has not been saved.\\Modifications will be lost when directory is changed.'.
 	    label := 'change'.
 	] ifFalse:[
-	    msg := (resources at:'contents has not been saved.\\Modifications will be lost when new file is read.').
+	    msg := 'contents has not been saved.\\Modifications will be lost when new file is read.'.
 	    label := 'get'.
 	].
-	self ask:msg yesButton:label action:[self doFileGet]
+	(self ask:(resources at:msg) yesButton:label) ifTrue:[
+	    self doFileGet
+	]
     ]
 !
 
@@ -1906,7 +1907,7 @@
 	] ifFalse:[
 	    q := resources string:'remove ''%1'' ?' with:(fileList at:sel)
 	].
-	self ask:q yesButton:'remove' action:[self doRemove]
+	(self ask:q yesButton:'remove') ifTrue:[self doRemove]
     ]
 !
 
@@ -1915,10 +1916,11 @@
 
     |queryBox|
 
-    queryBox := FilenameEnterBox title:(resources at:'create new directory:') withCRs.
-    queryBox initialText:''.
-    queryBox okText:(resources at:'create').
-    queryBox action:[:newName | self doCreateDirectory:newName].
+    queryBox := FilenameEnterBox 
+		    title:(resources at:'create new directory:') withCRs
+		    okText:(resources at:'create')
+		    action:[:newName | self doCreateDirectory:newName].
+"/    queryBox initialText:''.
     queryBox showAtPointer
 !
 
@@ -1927,15 +1929,16 @@
 
     |sel queryBox|
 
-    queryBox := FilenameEnterBox title:(resources at:'create new file:') withCRs.
+    queryBox := FilenameEnterBox 
+		    title:(resources at:'create new file:') withCRs
+		    okText:(resources at:'create')
+		    action:[:newName | self doCreateFile:newName].
     sel := subView selection.
     sel notNil ifTrue:[
 	queryBox initialText:(sel asString)
     ] ifFalse:[
-	queryBox initialText:''
+"/        queryBox initialText:''
     ].
-    queryBox okText:(resources at:'create').
-    queryBox action:[:newName | self doCreateFile:newName].
     queryBox showAtPointer
 !
 
--- a/FileBrowser.st	Mon Mar 06 23:07:15 1995 +0100
+++ b/FileBrowser.st	Thu Mar 09 04:31:23 1995 +0100
@@ -29,7 +29,7 @@
 COPYRIGHT (c) 1991 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libtool/FileBrowser.st,v 1.32 1995-03-06 19:31:30 claus Exp $
+$Header: /cvs/stx/stx/libtool/FileBrowser.st,v 1.33 1995-03-09 03:31:04 claus Exp $
 '!
 
 !FileBrowser class methodsFor:'documentation'!
@@ -50,7 +50,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libtool/FileBrowser.st,v 1.32 1995-03-06 19:31:30 claus Exp $
+$Header: /cvs/stx/stx/libtool/FileBrowser.st,v 1.33 1995-03-09 03:31:04 claus Exp $
 "
 !
 
@@ -116,7 +116,7 @@
 !FileBrowser methodsFor:'initialization'!
 
 initialize
-    |frame spacing halfSpacing v cutOff topFrame labelFrame|
+    |frame spacing halfSpacing v topFrame labelFrame|
 
     super initialize.
 
@@ -163,12 +163,6 @@
     spacing := ViewSpacing.
     halfSpacing := spacing // 2.
 
-    StyleSheet is3D ifFalse:[
-	cutOff := halfSpacing
-    ] ifTrue:[
-	cutOff := 0
-    ].
-
     checkBlock := [self checkIfDirectoryHasChanged].
     checkDelta := resources at:'CHECK_DELTA' default:10.
 
@@ -297,12 +291,6 @@
     ]
 !
 
-ask:question yesButton:yesButtonText action:aBlock
-    "common method to ask a yes/no question"
-
-    self ask:question yesButton:yesButtonText noButton:'cancel' action:aBlock
-!
-
 ask:question yesButton:yesButtonText noButton:noButtonText action:aBlock
     "common method to ask a yes/no question"
 
@@ -316,16 +304,27 @@
     yesNoBox showAtPointer
 !
 
-askIfModified:question yesButton:yesButtonText action:aBlock
+ask:question yesButton:yesButtonText
+    "common method to ask a yes/no question; return true or false"
+
+    self ask:question 
+	 yesButton:yesButtonText 
+	 noButton:'cancel' 
+	 action:[^ true].
+    ^ false
+!
+
+askIfModified:question yesButton:yesButtonText
     "tell user, that code has been modified - let her confirm"
 
     (subView modified not or:[subView contentsWasSaved]) ifTrue:[
-	aBlock value.
-	^ self
+	^ true
     ].
     self ask:(resources string:question) withCRs
-	 yesButton:yesButtonText 
-	 action:aBlock
+	 yesButton:yesButtonText
+	 noButton:'cancel' 
+	 action:[^ true].
+    ^ false
 !
 
 withoutHiddenFiles:aCollection
@@ -868,12 +867,10 @@
      otherwise change immediately to previous directory."
 
     previousDirectory isNil ifTrue:[^ self].
-    self askIfModified:('contents has not been saved.\\Modifications will be lost when directory is changed.')
-	 yesButton:'change'
-	 action:[
-		    self doChangeCurrentDirectoryTo:previousDirectory  
-				      updateHistory:false 
-		]
+    (self askIfModified:'contents has not been saved.\\Modifications will be lost when directory is changed.'
+	      yesButton:'change') ifTrue:[
+	self doChangeCurrentDirectoryTo:previousDirectory updateHistory:false 
+    ]
 !
 
 setCurrentDirectory:aPathName
@@ -1400,8 +1397,11 @@
 
     |fileName sel box|
 
-    box := FilenameEnterBox new.
-    box initialText:''.
+    box := FilenameEnterBox 
+		title:(resources at:'execute unix command:')
+	       okText:(resources at:'execute')
+	       action:aBlock.
+"/    box initialText:''.
 
     sel := fileListView selection.
     sel isCollection ifFalse:[
@@ -1412,9 +1412,6 @@
     fileName notNil ifTrue:[
 	self initialCommandFor:fileName into:box.
     ].
-    box title:(resources at:'execute unix command:').
-    box okText:(resources at:'execute').
-    box action:aBlock.
     box showAtPointer
 !
 
@@ -1460,9 +1457,10 @@
 	    (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'
-			 action:[currentDirectory removeDirectory:fileName]
+		    (self ask:(resources string:'directory ''%1'' is not empty\remove anyway ?' with:fileName)
+			  yesButton:'remove') ifTrue:[
+			 currentDirectory removeDirectory:fileName
+		    ]
 		] ifTrue:[
 		    currentDirectory removeDirectory:fileName
 		].
@@ -1498,9 +1496,8 @@
 terminate
     "exit FileBrowser"
 
-    self askIfModified:'contents has not been saved.\\Modifications will be lost when FileBrowser is closed.'
-	 yesButton:'close'
-	 action:[self destroy]
+    (self askIfModified:'contents has not been saved.\\Modifications will be lost when FileBrowser is closed.'
+	      yesButton:'close') ifTrue:[self destroy]
 !
 
 destroy
@@ -1614,27 +1611,30 @@
     "if text was modified show a queryBox, 
      otherwise change immediately to directory"
 
-    self askIfModified:'contents has not been saved.\\Modifications will be lost when directory is changed.'
-	 yesButton:'change'
-	 action:[self queryForDirectoryToChange]
+    (self askIfModified:'contents has not been saved.\\Modifications will be lost when directory is changed.'
+	      yesButton:'change') ifTrue:[
+	self queryForDirectoryToChange
+    ]
 !
 
 changeToParentDirectory
     "if text was modified show a queryBox, 
      otherwise change immediately to directory"
 
-    self askIfModified:'contents has not been saved.\\Modifications will be lost when directory is changed.'
-	 yesButton:'change'
-	 action:[self doChangeToParentDirectory]
+    (self askIfModified:'contents has not been saved.\\Modifications will be lost when directory is changed.'
+	      yesButton:'change') ifTrue:[
+	 self doChangeToParentDirectory
+    ]
 !
 
 changeToHomeDirectory
     "if text was modified show a queryBox, 
      otherwise change immediately to directory"
 
-    self askIfModified:'contents has not been saved.\\Modifications will be lost when directory is changed.'
-	 yesButton:'change'
-	 action:[self doChangeToHomeDirectory]
+    (self askIfModified:'contents has not been saved.\\Modifications will be lost when directory is changed.'
+	      yesButton:'change') ifTrue:[
+	 self doChangeToHomeDirectory
+    ]
 !
 
 queryForDirectoryToChange
@@ -1642,10 +1642,11 @@
 
     |queryBox|
 
-    queryBox := FilenameEnterBox title:(resources at:'change directory to:') withCRs.
-    queryBox initialText:''.
-    queryBox okText:(resources at:'change').
-    queryBox action:[:newName | self doChangeCurrentDirectoryTo:newName updateHistory:true].
+    queryBox := FilenameEnterBox 
+		    title:(resources at:'change directory to:') withCRs
+		    okText:(resources at:'change')
+		    action:[:newName | self doChangeCurrentDirectoryTo:newName updateHistory:true].
+"/    queryBox initialText:''.
     queryBox showAtPointer
 ! !
 
@@ -1756,22 +1757,20 @@
 
     |action|
 
-    true ifTrue:[
-	"
-	 this replaces everything by the commands output ...
-	"
-	action := [:command| self doExecuteCommand:command replace:true].
+    "
+     this replaces everything by the commands output ...
+    "
+    action := [:command| self doExecuteCommand:command replace:true].
 
-	self askIfModified:'contents has not been saved.\\Modifications will be lost when command is executed.'
-		 yesButton:'execute'
-		 action:[self askForCommandThenDo:action]
-    ] ifFalse:[
-	"
-	 this inserts the commands output ...
-	"
-	action := [:command| self doExecuteCommand:command replace:false].
-	self askForCommandThenDo:action
-    ]
+    (self askIfModified:'contents has not been saved.\\Modifications will be lost when command is executed.'
+	      yesButton:'execute') ifFalse:[^ self].
+
+"/    "
+"/     this inserts the commands output ...
+"/    "
+"/    action := [:command| self doExecuteCommand:command replace:false].
+"/
+    self askForCommandThenDo:action
 !
 
 openTool:aToolClass
@@ -1821,13 +1820,15 @@
     fileName := self getSelectedFileName.
     fileName notNil ifTrue:[
 	(currentDirectory isDirectory:fileName) ifTrue:[
-	    msg := (resources at:'contents has not been saved.\\Modifications will be lost when directory is changed.').
+	    msg := 'contents has not been saved.\\Modifications will be lost when directory is changed.'.
 	    label := 'change'.
 	] ifFalse:[
-	    msg := (resources at:'contents has not been saved.\\Modifications will be lost when new file is read.').
+	    msg := 'contents has not been saved.\\Modifications will be lost when new file is read.'.
 	    label := 'get'.
 	].
-	self ask:msg yesButton:label action:[self doFileGet]
+	(self ask:(resources at:msg) yesButton:label) ifTrue:[
+	    self doFileGet
+	]
     ]
 !
 
@@ -1906,7 +1907,7 @@
 	] ifFalse:[
 	    q := resources string:'remove ''%1'' ?' with:(fileList at:sel)
 	].
-	self ask:q yesButton:'remove' action:[self doRemove]
+	(self ask:q yesButton:'remove') ifTrue:[self doRemove]
     ]
 !
 
@@ -1915,10 +1916,11 @@
 
     |queryBox|
 
-    queryBox := FilenameEnterBox title:(resources at:'create new directory:') withCRs.
-    queryBox initialText:''.
-    queryBox okText:(resources at:'create').
-    queryBox action:[:newName | self doCreateDirectory:newName].
+    queryBox := FilenameEnterBox 
+		    title:(resources at:'create new directory:') withCRs
+		    okText:(resources at:'create')
+		    action:[:newName | self doCreateDirectory:newName].
+"/    queryBox initialText:''.
     queryBox showAtPointer
 !
 
@@ -1927,15 +1929,16 @@
 
     |sel queryBox|
 
-    queryBox := FilenameEnterBox title:(resources at:'create new file:') withCRs.
+    queryBox := FilenameEnterBox 
+		    title:(resources at:'create new file:') withCRs
+		    okText:(resources at:'create')
+		    action:[:newName | self doCreateFile:newName].
     sel := subView selection.
     sel notNil ifTrue:[
 	queryBox initialText:(sel asString)
     ] ifFalse:[
-	queryBox initialText:''
+"/        queryBox initialText:''
     ].
-    queryBox okText:(resources at:'create').
-    queryBox action:[:newName | self doCreateFile:newName].
     queryBox showAtPointer
 !
 
--- a/InspView.st	Mon Mar 06 23:07:15 1995 +0100
+++ b/InspView.st	Thu Mar 09 04:31:23 1995 +0100
@@ -23,7 +23,7 @@
 COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libtool/Attic/InspView.st,v 1.17 1995-02-28 21:55:41 claus Exp $
+$Header: /cvs/stx/stx/libtool/Attic/InspView.st,v 1.18 1995-03-09 03:31:14 claus Exp $
 '!
 
 !InspectorView class methodsFor:'documentation'!
@@ -44,7 +44,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libtool/Attic/InspView.st,v 1.17 1995-02-28 21:55:41 claus Exp $
+$Header: /cvs/stx/stx/libtool/Attic/InspView.st,v 1.18 1995-03-09 03:31:14 claus Exp $
 "
 !
 
@@ -198,7 +198,7 @@
     "return a list of names to show in the selectionList.
      Leave hasMore as true, if a '...' entry should be added."
 
-    |aList n cls|
+    |aList n cls s|
 
     aList := OrderedCollection new.
     aList add:'self'.
@@ -218,8 +218,15 @@
 	    n := nShown.
 	    hasMore := true.
 	].
-	1 to:n do:[:index |
-	    aList add:(index printString)
+	(inspectedObject respondsTo:#keys) ifTrue:[
+	    s := ReadStream on:(inspectedObject keys).
+	    1 to:n do:[:index |
+		aList add:(s next printString)
+	    ]
+	] ifFalse:[
+	    1 to:n do:[:index |
+		aList add:(index printString)
+	    ]
 	].
     ].
     ^ aList
--- a/InspectorView.st	Mon Mar 06 23:07:15 1995 +0100
+++ b/InspectorView.st	Thu Mar 09 04:31:23 1995 +0100
@@ -23,7 +23,7 @@
 COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libtool/InspectorView.st,v 1.17 1995-02-28 21:55:41 claus Exp $
+$Header: /cvs/stx/stx/libtool/InspectorView.st,v 1.18 1995-03-09 03:31:14 claus Exp $
 '!
 
 !InspectorView class methodsFor:'documentation'!
@@ -44,7 +44,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libtool/InspectorView.st,v 1.17 1995-02-28 21:55:41 claus Exp $
+$Header: /cvs/stx/stx/libtool/InspectorView.st,v 1.18 1995-03-09 03:31:14 claus Exp $
 "
 !
 
@@ -198,7 +198,7 @@
     "return a list of names to show in the selectionList.
      Leave hasMore as true, if a '...' entry should be added."
 
-    |aList n cls|
+    |aList n cls s|
 
     aList := OrderedCollection new.
     aList add:'self'.
@@ -218,8 +218,15 @@
 	    n := nShown.
 	    hasMore := true.
 	].
-	1 to:n do:[:index |
-	    aList add:(index printString)
+	(inspectedObject respondsTo:#keys) ifTrue:[
+	    s := ReadStream on:(inspectedObject keys).
+	    1 to:n do:[:index |
+		aList add:(s next printString)
+	    ]
+	] ifFalse:[
+	    1 to:n do:[:index |
+		aList add:(index printString)
+	    ]
 	].
     ].
     ^ aList
--- a/MemMonitor.st	Mon Mar 06 23:07:15 1995 +0100
+++ b/MemMonitor.st	Thu Mar 09 04:31:23 1995 +0100
@@ -24,7 +24,7 @@
  COPYRIGHT (c) 1991 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libtool/Attic/MemMonitor.st,v 1.10 1995-03-06 19:31:50 claus Exp $
+$Header: /cvs/stx/stx/libtool/Attic/MemMonitor.st,v 1.11 1995-03-09 03:31:23 claus Exp $
 '!
 
 !MemoryMonitor class methodsFor:'documentation'!
@@ -45,7 +45,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libtool/Attic/MemMonitor.st,v 1.10 1995-03-06 19:31:50 claus Exp $
+$Header: /cvs/stx/stx/libtool/Attic/MemMonitor.st,v 1.11 1995-03-09 03:31:23 claus Exp $
 "
 !
 
@@ -462,7 +462,7 @@
 		(Delay forSeconds:updateInterval) wait.
 		self updateDisplay
 	    ]
-	] forkAt:5.
+	] forkAt:6.
 	myProcess name:'Memory Monitor [' , 
 			Processor activeProcess id printString , '] update'
     ].
@@ -552,11 +552,10 @@
 !
 
 backgroundCollect
-    [ObjectMemory incrementalGC] forkAt:4
+    [ObjectMemory incrementalGC] forkAt:5 
 !
 
 compressSources
     Smalltalk compressSources.
     ObjectMemory markAndSweep
 ! !
-
--- a/MemoryMonitor.st	Mon Mar 06 23:07:15 1995 +0100
+++ b/MemoryMonitor.st	Thu Mar 09 04:31:23 1995 +0100
@@ -24,7 +24,7 @@
  COPYRIGHT (c) 1991 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libtool/MemoryMonitor.st,v 1.10 1995-03-06 19:31:50 claus Exp $
+$Header: /cvs/stx/stx/libtool/MemoryMonitor.st,v 1.11 1995-03-09 03:31:23 claus Exp $
 '!
 
 !MemoryMonitor class methodsFor:'documentation'!
@@ -45,7 +45,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libtool/MemoryMonitor.st,v 1.10 1995-03-06 19:31:50 claus Exp $
+$Header: /cvs/stx/stx/libtool/MemoryMonitor.st,v 1.11 1995-03-09 03:31:23 claus Exp $
 "
 !
 
@@ -462,7 +462,7 @@
 		(Delay forSeconds:updateInterval) wait.
 		self updateDisplay
 	    ]
-	] forkAt:5.
+	] forkAt:6.
 	myProcess name:'Memory Monitor [' , 
 			Processor activeProcess id printString , '] update'
     ].
@@ -552,11 +552,10 @@
 !
 
 backgroundCollect
-    [ObjectMemory incrementalGC] forkAt:4
+    [ObjectMemory incrementalGC] forkAt:5 
 !
 
 compressSources
     Smalltalk compressSources.
     ObjectMemory markAndSweep
 ! !
-