*** empty log message ***
authorClaus Gittinger <cg@exept.de>
Wed, 13 Jul 2005 17:54:29 +0200
changeset 6357 95e37428f3aa
parent 6356 cff12ff7dc25
child 6358 582d839d5b93
*** empty log message ***
BrowserView.st
ChangesBrowser.st
FileBrowser.st
--- a/BrowserView.st	Wed Jul 13 17:50:42 2005 +0200
+++ b/BrowserView.st	Wed Jul 13 17:54:29 2005 +0200
@@ -2451,7 +2451,7 @@
         okText2 := 'Open new'.
     ].
     box := self 
-                enterBoxForCodeSelectionTitle:title withCRs
+                enterBoxForCodeSelectionTitle:(resources stringWithCRs:title)
                 withList:(self class classHistory collect: [:histEntry| histEntry className ])
                 okText:okText.
     box label:(resources string:'Browse or search class').
@@ -5332,7 +5332,7 @@
                 ^ self
             ].
             aStream class readErrorSignal handle:[:ex |
-                self warn:('Read error while reading extracted source\\' , ex description) withCRs.
+                self warn:(resources stringWithCRs:'Read error while reading extracted source\\') , ex description.
                 aStream close.
                 ^ self
             ] do:[
@@ -5431,7 +5431,7 @@
     box := DialogBox new.
     box label:'container fileIn'.
 
-    component := box addTextLabel:(resources string:'container to fileIn') withCRs.
+    component := box addTextLabel:(resources stringWithCRs:'container to fileIn') .
     component adjust:#left; borderWidth:0.
     box addVerticalSpace.
     box addVerticalSpace.
@@ -12267,7 +12267,7 @@
     ].
 
     action := OptionBox 
-                  request:(resources at:'Text has not been accepted.\\Your modifications will be lost when continuing.') withCRs
+                  request:(resources stringWithCRs:'Text has not been accepted.\\Your modifications will be lost when continuing.')
                   label:(resources string:'Attention')
                   image:(WarningBox iconBitmap)
                   buttonLabels:(resources array:labels)
@@ -14626,7 +14626,7 @@
 !BrowserView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/BrowserView.st,v 1.785 2005-04-20 09:23:00 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/BrowserView.st,v 1.786 2005-07-13 15:54:29 cg Exp $'
 ! !
 
 BrowserView initialize!
--- a/ChangesBrowser.st	Wed Jul 13 17:50:42 2005 +0200
+++ b/ChangesBrowser.st	Wed Jul 13 17:54:29 2005 +0200
@@ -1228,11 +1228,11 @@
     autoloadAsRequired := false asValue.
     applyInOriginalNameSpace := true asValue.
     applyInOriginalNameSpace
-	onChangeEvaluate:[
-	    autoCompare value ifTrue:[
-		self doUpdate
-	    ].
-	].
+        onChangeEvaluate:[
+            autoCompare value ifTrue:[
+                self doUpdate
+            ].
+        ].
     updateChangeSet := true "false" asValue.
 
     "
@@ -1243,34 +1243,34 @@
     checkBlock := [self pushEvent:#checkIfFileHasChanged].
 
     oldStyle ifFalse:[
-	menuPanel := MenuPanel in:self.
-	"/ menuPanel level:1.
-	menuPanel verticalLayout:false.
-	menuPanel receiver:self.
-	menuPanel menu:(self pullDownMenu).
-
-	mH := menuPanel preferredExtent y.
-	menuPanel origin:(0.0 @ 0.0) corner:(1.0 @ (mH)).
-	mH := mH + 1.
+        menuPanel := MenuPanel in:self.
+        "/ menuPanel level:1.
+        menuPanel verticalLayout:false.
+        menuPanel receiver:self.
+        menuPanel menu:(self pullDownMenu).
+
+        mH := menuPanel preferredExtent y.
+        menuPanel origin:(0.0 @ 0.0) corner:(1.0 @ (mH)).
+        mH := mH + 1.
     ] ifTrue:[
-	mH := 0.0
+        mH := 0.0
     ].
 
     panel := VariableVerticalPanel origin:(0.0 @ mH)
-				   corner:(1.0 @ 1.0)
-			      borderWidth:0
-				       in:self.
+                                   corner:(1.0 @ 1.0)
+                              borderWidth:0
+                                       in:self.
 
     upperFrame := panel.
     oldStyle ifTrue:[
-	upperFrame := VariableHorizontalPanel origin:(0.0 @ 0.0) corner:(1.0 @ 0.3) in:panel.
+        upperFrame := VariableHorizontalPanel origin:(0.0 @ 0.0) corner:(1.0 @ 0.3) in:panel.
     ].
 
     v := HVScrollableView for:SelectionInListView miniScrollerH:true in:upperFrame.
     oldStyle ifTrue:[
-	v origin:(0.0 @ 0.0) corner:(0.75 @ 1.0).
+        v origin:(0.0 @ 0.0) corner:(0.75 @ 1.0).
     ] ifFalse:[
-	v origin:(0.0 @ 0.0) corner:(1.0 @ 0.3).
+        v origin:(0.0 @ 0.0) corner:(1.0 @ 0.3).
     ].
 
     changeListView := v scrolledView.
@@ -1278,28 +1278,28 @@
     changeListView menuHolder:self; menuPerformer:self; menuMessage:#changeListMenu.
     changeListView doubleClickAction:[:line | self doubleClickOnChange:line].
     oldStyle ifFalse:[
-	changeListView multipleSelectOk:true.
+        changeListView multipleSelectOk:true.
     ].
 
     oldStyle ifTrue:[
-	buttonPanel := VerticalPanelView in:upperFrame.
-	buttonPanel origin:(0.75 @ 0.0) corner:(1.0 @ 1.0).
-	buttonPanel verticalLayout:#topSpace; horizontalLayout:#leftSpace.
-
-	checkBox := CheckBox new model:autoCompare.
-	checkBox label:(resources string:'Auto Compare').
-	checkBox action:[:val | autoCompare value:val].
-	buttonPanel addSubView:checkBox.
-
-	checkBox := CheckBox new model:autoUpdate.
-	checkBox label:(resources string:'Auto Update').
-	checkBox action:[:val | autoUpdate value:val].
-	buttonPanel addSubView:checkBox.
-
-	checkBox := CheckBox new.
-	checkBox label:(resources string:'Apply in original NameSpace' withCRs).
-	checkBox model:applyInOriginalNameSpace.
-	buttonPanel addSubView:checkBox.
+        buttonPanel := VerticalPanelView in:upperFrame.
+        buttonPanel origin:(0.75 @ 0.0) corner:(1.0 @ 1.0).
+        buttonPanel verticalLayout:#topSpace; horizontalLayout:#leftSpace.
+
+        checkBox := CheckBox new model:autoCompare.
+        checkBox label:(resources string:'Auto Compare').
+        checkBox action:[:val | autoCompare value:val].
+        buttonPanel addSubView:checkBox.
+
+        checkBox := CheckBox new model:autoUpdate.
+        checkBox label:(resources string:'Auto Update').
+        checkBox action:[:val | autoUpdate value:val].
+        buttonPanel addSubView:checkBox.
+
+        checkBox := CheckBox new.
+        checkBox label:(resources stringWithCRs:'Apply in original NameSpace').
+        checkBox model:applyInOriginalNameSpace.
+        buttonPanel addSubView:checkBox.
     ].
 
 "/    protectExistingMethods := CheckBox new.
@@ -1320,16 +1320,16 @@
 
     lbl := Label label:'Current' in:diffViewBox.
     lbl layout:(LayoutFrame
-			leftFraction:0.0 offset:0
-			rightFraction:0.5 offset:0
-			topFraction:0.0 offset:0
-			bottomFraction:0.0 offset:20).
+                        leftFraction:0.0 offset:0
+                        rightFraction:0.5 offset:0
+                        topFraction:0.0 offset:0
+                        bottomFraction:0.0 offset:20).
     lbl := Label label:'Change' in:diffViewBox.
     lbl layout:(LayoutFrame
-			leftFraction:0.5 offset:0
-			rightFraction:1.0 offset:0
-			topFraction:0.0 offset:0
-			bottomFraction:0.0 offset:20).
+                        leftFraction:0.5 offset:0
+                        rightFraction:1.0 offset:0
+                        topFraction:0.0 offset:0
+                        bottomFraction:0.0 offset:20).
 
 "/    diffView := DiffTextView in:diffViewBox.
 "/    diffView layout:(LayoutFrame
@@ -1340,14 +1340,14 @@
 
     v := HVScrollableView for:DiffTextView miniScrollerH:true miniScrollerV:false in:diffViewBox.
     v layout:(LayoutFrame
-			leftFraction:0.0 offset:0
-			rightFraction:1.0 offset:0
-			topFraction:0.0 offset:20
-			bottomFraction:1.0 offset:0).
+                        leftFraction:0.0 offset:0
+                        rightFraction:1.0 offset:0
+                        topFraction:0.0 offset:20
+                        bottomFraction:1.0 offset:0).
     diffView := v scrolledView.
 
     self showingDiffs value ifFalse:[
-	self makeDiffViewInvisible
+        self makeDiffViewInvisible
     ].
 
     anyChanges := false.
@@ -1513,30 +1513,30 @@
 
     cls := aClass theNonMetaclass.
     cls isLoaded ifTrue:[
-	^ true.
+        ^ true.
     ].
 
     autoloadAsRequired value == true ifTrue:[
-	answer := true
+        answer := true
     ] ifFalse:[
-	answer := (self confirmWithCancel:(resources
-		    string:'%1 is an autoloaded class.\I can only compare the methods source if its loaded first.\\Shall the class be loaded now ?'
-		    with:cls name allBold) withCRs).
+        answer := (self confirmWithCancel:(resources
+                    stringWithCRs:'%1 is an autoloaded class.\I can only compare the methods source if its loaded first.\\Shall the class be loaded now ?'
+                    with:cls name allBold)).
     ].
 
     answer == true ifTrue:[
-	Autoload autoloadFailedSignal handle:[:ex |
-	    AbortOperationRequest raise.
-	    ^ false
-	] do:[
-	    ^ cls autoload isLoaded
-	]
+        Autoload autoloadFailedSignal handle:[:ex |
+            AbortOperationRequest raise.
+            ^ false
+        ] do:[
+            ^ cls autoload isLoaded
+        ]
     ].
 
     answer isNil ifTrue:[
-	"cancel the operation"
-	AbortAllOperationRequest raiseRequest.
-	^ false.
+        "cancel the operation"
+        AbortAllOperationRequest raiseRequest.
+        ^ false.
     ].
 
     "cancel operation for this change, (but possibly continue with others)"
@@ -3307,155 +3307,155 @@
     showDiff := false.
 
     (self changeIsFollowupMethodChange:changeNr) ifFalse:[
-	sawExcla := aStream peekFor:(aStream class chunkSeparator).
-	chunk := aStream nextChunk.
+        sawExcla := aStream peekFor:(aStream class chunkSeparator).
+        chunk := aStream nextChunk.
     ] ifTrue:[
-	chunk := (changeChunks at:changeNr).
-	sawExcla := true.
+        chunk := (changeChunks at:changeNr).
+        sawExcla := true.
     ].
 
     isSame := nil.
 
     beep := false.
     sawExcla ifFalse:[
-	outcome := 'cannot compare this change\\(i.e. this is not a method change).'.
-
-	Class nameSpaceQuerySignal answer:(self nameSpaceForApply)
-	do:[
-	    parseTree := Parser parseExpression:chunk.
-	].
-	(parseTree notNil and:[parseTree ~~ #Error and:[ parseTree isMessage ]]) ifTrue:[
-	    selector := parseTree selector.
-
-	    selector == #'removeSelector:' ifTrue:[
-		thisClass := (parseTree receiver evaluate).
-		thisClass isBehavior ifTrue:[
-		    (self checkClassIsLoaded:thisClass) ifTrue:[
-			selector := (parseTree arg1 evaluate).
-			(thisClass includesSelector:selector) ifTrue:[
-			    outcome := 'Change removes the #' , selector , ' method from ' , thisClass name.
-			    isSame := false.
-			] ifFalse:[
-			    outcome := 'Change has no effect\\(there is no method for #' , selector , ' in ' , thisClass name , ')'.
-			    isSame := true.
-			]
-		    ] ifFalse:[
-			beep := true.
-			outcome := 'Cannot compare this change (compare requires class to be loaded).'.
-			isSame := nil.
-		    ]
-		] ifFalse:[
-		    outcome := 'Cannot compare this change (class not present)'.
-		    isSame := nil.
-		].
-	    ].
-	    selector == #'category:' ifTrue:[
-		parseTree receiver isMessage ifTrue:[
-		    parseTree receiver selector == #compiledMethodAt: ifTrue:[
-			|receiver|
-			receiver := parseTree receiver.
-			(receiver receiver evaluate isBehavior
-			 and:[(method := receiver evaluate) isMethod]) ifTrue:[
-			    method category = parseTree arg1 evaluate ifTrue:[
-				outcome := 'Change has no effect\\(same category)'.
-				isSame := true.
-			    ] ifFalse:[
-				outcome := 'Category is different (''' , method category , ''' vs. ''' , parseTree arg1 evaluate , ''')'.
-				isSame := false.
-			    ]
-			] ifFalse:[
-			    beep := true.
-			    outcome := 'There is no such method'.
-			    isSame := nil.
-			]
-		    ]
-		]
-	    ].
-	    selector == #'comment:' ifTrue:[
-		thisClass := (parseTree receiver evaluate).
-		thisClass isBehavior ifTrue:[
-		    (self checkClassIsLoaded:thisClass) ifTrue:[
-			(thisClass comment = parseTree arg1 evaluate) ifTrue:[
-			    outcome := 'Change has no effect\\(same comment)'.
-			    isSame := true.
-			] ifFalse:[
-			    outcome := 'Comment is different'.
-			    isSame := false.
-			]
-		    ] ifFalse:[
-			beep := true.
-			outcome := 'Cannot compare this change (compare requires class to be loaded).'.
-			isSame := nil.
-		    ]
-		] ifFalse:[
-		    outcome := 'Cannot compare this change (class not present)'.
-		    isSame := nil.
-		].
-	    ].
-
-	    selector == #'instanceVariableNames:' ifTrue:[
-		parseTree receiver isMessage ifTrue:[
-		    parseTree receiver selector == #class ifTrue:[
-			thisClass := (parseTree receiver evaluate).
-			varsHere := thisClass instanceVariableString asCollectionOfWords.
-			varsInChange := (parseTree arguments at:1) evaluate asCollectionOfWords.
-			varsHere = varsInChange ifTrue:[
-			    outcome := 'Change has no effect\\(same definition)'.
-			    isSame := true.
-			] ifFalse:[
-			    outcome := 'Class-instanceVariable definition is different'.
-			    isSame := false.
-			].
-		    ].
-		]
-	    ].
-
-	    (Class definitionSelectors includes:selector)
-	    "/ selector == #'subclass:instanceVariableNames:classVariableNames:poolDictionaries:category:'
-	    ifTrue:[
-		superClass := (parseTree receiver evaluate).
-		superClass isBehavior ifFalse:[
-		    outcome := 'Cannot compare this change\\(superclass not loaded).'.
-		    isSame := nil.
-		] ifTrue:[
-		    (self checkClassIsLoaded:superClass) ifTrue:[
-			thisClassSym := (parseTree arguments at:1) evaluate.
-
-			(selector endsWith:':privateIn:') ifTrue:[
-			    ownerClass := (parseTree arguments at:5) evaluate.
-			    ownerClass isBehavior ifTrue:[
-				thisClass := ownerClass privateClassesAt:thisClassSym.
-			    ].
-			] ifFalse:[
-			    thisClass := (self nameSpaceForApply) at:thisClassSym ifAbsent:nil.
-			].
-			thisClass isNil ifTrue:[
-			    outcome := 'Change defines the class: ' , thisClassSym allBold.
-			    isSame := false.
-			] ifFalse:[
-			    (isLoaded := self checkClassIsLoaded:thisClass) ifFalse:[
-				outcome := 'Cannot compare this change\\(compare requires class to be loaded).'.
-				isSame := nil.
-			    ] ifTrue:[
-				superClassHere := thisClass superclass name.
-				superClassInChange := parseTree receiver name.
-				superClassHere ~~ superClassInChange ifTrue:[
-				    outcome := 'Superclass is different.'.
-				    isSame := false.
-				] ifFalse:[
-				    varsHere := thisClass instanceVariableString asCollectionOfWords.
-				    varsInChange := (parseTree arguments at:2) evaluate asCollectionOfWords.
-				    varsHere = varsInChange ifTrue:[
-					thisClass classVariableString asCollectionOfWords = (parseTree arguments at:3) evaluate asCollectionOfWords ifTrue:[
-					    ((thisClass sharedPools size == 0) and:[(parseTree arguments at:4) evaluate = '']) ifTrue:[
-						((selector endsWith:':category:')
-						and:[thisClass category ~= (parseTree arguments at:5) evaluate]) ifTrue:[
-						    outcome := 'Category is different'.
-						    isSame := false.
-						] ifFalse:[
-						    outcome := 'Change has no effect\\(same definition)'.
-						    isSame := true.
-						]
+        outcome := 'cannot compare this change\\(i.e. this is not a method change).'.
+
+        Class nameSpaceQuerySignal answer:(self nameSpaceForApply)
+        do:[
+            parseTree := Parser parseExpression:chunk.
+        ].
+        (parseTree notNil and:[parseTree ~~ #Error and:[ parseTree isMessage ]]) ifTrue:[
+            selector := parseTree selector.
+
+            selector == #'removeSelector:' ifTrue:[
+                thisClass := (parseTree receiver evaluate).
+                thisClass isBehavior ifTrue:[
+                    (self checkClassIsLoaded:thisClass) ifTrue:[
+                        selector := (parseTree arg1 evaluate).
+                        (thisClass includesSelector:selector) ifTrue:[
+                            outcome := 'Change removes the #' , selector , ' method from ' , thisClass name.
+                            isSame := false.
+                        ] ifFalse:[
+                            outcome := 'Change has no effect\\(there is no method for #' , selector , ' in ' , thisClass name , ')'.
+                            isSame := true.
+                        ]
+                    ] ifFalse:[
+                        beep := true.
+                        outcome := 'Cannot compare this change (compare requires class to be loaded).'.
+                        isSame := nil.
+                    ]
+                ] ifFalse:[
+                    outcome := 'Cannot compare this change (class not present)'.
+                    isSame := nil.
+                ].
+            ].
+            selector == #'category:' ifTrue:[
+                parseTree receiver isMessage ifTrue:[
+                    parseTree receiver selector == #compiledMethodAt: ifTrue:[
+                        |receiver|
+                        receiver := parseTree receiver.
+                        (receiver receiver evaluate isBehavior
+                         and:[(method := receiver evaluate) isMethod]) ifTrue:[
+                            method category = parseTree arg1 evaluate ifTrue:[
+                                outcome := 'Change has no effect\\(same category)'.
+                                isSame := true.
+                            ] ifFalse:[
+                                outcome := 'Category is different (''' , method category , ''' vs. ''' , parseTree arg1 evaluate , ''')'.
+                                isSame := false.
+                            ]
+                        ] ifFalse:[
+                            beep := true.
+                            outcome := 'There is no such method'.
+                            isSame := nil.
+                        ]
+                    ]
+                ]
+            ].
+            selector == #'comment:' ifTrue:[
+                thisClass := (parseTree receiver evaluate).
+                thisClass isBehavior ifTrue:[
+                    (self checkClassIsLoaded:thisClass) ifTrue:[
+                        (thisClass comment = parseTree arg1 evaluate) ifTrue:[
+                            outcome := 'Change has no effect\\(same comment)'.
+                            isSame := true.
+                        ] ifFalse:[
+                            outcome := 'Comment is different'.
+                            isSame := false.
+                        ]
+                    ] ifFalse:[
+                        beep := true.
+                        outcome := 'Cannot compare this change (compare requires class to be loaded).'.
+                        isSame := nil.
+                    ]
+                ] ifFalse:[
+                    outcome := 'Cannot compare this change (class not present)'.
+                    isSame := nil.
+                ].
+            ].
+
+            selector == #'instanceVariableNames:' ifTrue:[
+                parseTree receiver isMessage ifTrue:[
+                    parseTree receiver selector == #class ifTrue:[
+                        thisClass := (parseTree receiver evaluate).
+                        varsHere := thisClass instanceVariableString asCollectionOfWords.
+                        varsInChange := (parseTree arguments at:1) evaluate asCollectionOfWords.
+                        varsHere = varsInChange ifTrue:[
+                            outcome := 'Change has no effect\\(same definition)'.
+                            isSame := true.
+                        ] ifFalse:[
+                            outcome := 'Class-instanceVariable definition is different'.
+                            isSame := false.
+                        ].
+                    ].
+                ]
+            ].
+
+            (Class definitionSelectors includes:selector)
+            "/ selector == #'subclass:instanceVariableNames:classVariableNames:poolDictionaries:category:'
+            ifTrue:[
+                superClass := (parseTree receiver evaluate).
+                superClass isBehavior ifFalse:[
+                    outcome := 'Cannot compare this change\\(superclass not loaded).'.
+                    isSame := nil.
+                ] ifTrue:[
+                    (self checkClassIsLoaded:superClass) ifTrue:[
+                        thisClassSym := (parseTree arguments at:1) evaluate.
+
+                        (selector endsWith:':privateIn:') ifTrue:[
+                            ownerClass := (parseTree arguments at:5) evaluate.
+                            ownerClass isBehavior ifTrue:[
+                                thisClass := ownerClass privateClassesAt:thisClassSym.
+                            ].
+                        ] ifFalse:[
+                            thisClass := (self nameSpaceForApply) at:thisClassSym ifAbsent:nil.
+                        ].
+                        thisClass isNil ifTrue:[
+                            outcome := 'Change defines the class: ' , thisClassSym allBold.
+                            isSame := false.
+                        ] ifFalse:[
+                            (isLoaded := self checkClassIsLoaded:thisClass) ifFalse:[
+                                outcome := 'Cannot compare this change\\(compare requires class to be loaded).'.
+                                isSame := nil.
+                            ] ifTrue:[
+                                superClassHere := thisClass superclass name.
+                                superClassInChange := parseTree receiver name.
+                                superClassHere ~~ superClassInChange ifTrue:[
+                                    outcome := 'Superclass is different.'.
+                                    isSame := false.
+                                ] ifFalse:[
+                                    varsHere := thisClass instanceVariableString asCollectionOfWords.
+                                    varsInChange := (parseTree arguments at:2) evaluate asCollectionOfWords.
+                                    varsHere = varsInChange ifTrue:[
+                                        thisClass classVariableString asCollectionOfWords = (parseTree arguments at:3) evaluate asCollectionOfWords ifTrue:[
+                                            ((thisClass sharedPools size == 0) and:[(parseTree arguments at:4) evaluate = '']) ifTrue:[
+                                                ((selector endsWith:':category:')
+                                                and:[thisClass category ~= (parseTree arguments at:5) evaluate]) ifTrue:[
+                                                    outcome := 'Category is different'.
+                                                    isSame := false.
+                                                ] ifFalse:[
+                                                    outcome := 'Change has no effect\\(same definition)'.
+                                                    isSame := true.
+                                                ]
     "/                                            thisClass category = (parseTree arguments at:5) evaluate ifTrue:[
     "/                                                outcome := 'Change has no effect\\(same definition)'.
     "/                                                isSame := true.
@@ -3463,195 +3463,195 @@
     "/                                                outcome := 'Category is different'.
     "/                                                isSame := false.
     "/                                            ]
-					    ] ifFalse:[
-						outcome := 'SharedPool definition is different'.
-						isSame := false.
-					    ].
-					] ifFalse:[
-					    outcome := 'ClassVariable definition is different'.
-					    isSame := false.
-					]
-				    ] ifFalse:[
-					outcome := 'InstanceVariable definition is different'.
-					isSame := false.
-					addedVars := varsInChange select:[:eachVar | (varsHere includes:eachVar) not].
-					removedVars := varsHere select:[:eachVar | (varsInChange includes:eachVar) not].
-					addedVars isEmpty ifTrue:[
-					    removedVars isEmpty ifTrue:[
-						outcome := 'Change reorders instanceVariable(s)'.
-					    ] ifFalse:[
-						removedVars := removedVars collect:[:eachVar | '''' , eachVar , ''''].
-						outcome := 'Change removes instanceVariable(s): ' , (removedVars asStringWith:Character space) allBold.
-					    ]
-					] ifFalse:[
-					    removedVars isEmpty ifTrue:[
-						addedVars := addedVars collect:[:eachVar | '''' , eachVar , ''''].
-						outcome := 'Change adds instanceVariable(s): ' , (addedVars asStringWith:Character space) allBold.
-					    ].
-					].
-				    ]
-				]
-			    ]
-			]
-		    ]
-		]
-	    ]
-	]
+                                            ] ifFalse:[
+                                                outcome := 'SharedPool definition is different'.
+                                                isSame := false.
+                                            ].
+                                        ] ifFalse:[
+                                            outcome := 'ClassVariable definition is different'.
+                                            isSame := false.
+                                        ]
+                                    ] ifFalse:[
+                                        outcome := 'InstanceVariable definition is different'.
+                                        isSame := false.
+                                        addedVars := varsInChange select:[:eachVar | (varsHere includes:eachVar) not].
+                                        removedVars := varsHere select:[:eachVar | (varsInChange includes:eachVar) not].
+                                        addedVars isEmpty ifTrue:[
+                                            removedVars isEmpty ifTrue:[
+                                                outcome := 'Change reorders instanceVariable(s)'.
+                                            ] ifFalse:[
+                                                removedVars := removedVars collect:[:eachVar | '''' , eachVar , ''''].
+                                                outcome := 'Change removes instanceVariable(s): ' , (removedVars asStringWith:Character space) allBold.
+                                            ]
+                                        ] ifFalse:[
+                                            removedVars isEmpty ifTrue:[
+                                                addedVars := addedVars collect:[:eachVar | '''' , eachVar , ''''].
+                                                outcome := 'Change adds instanceVariable(s): ' , (addedVars asStringWith:Character space) allBold.
+                                            ].
+                                        ].
+                                    ]
+                                ]
+                            ]
+                        ]
+                    ]
+                ]
+            ]
+        ]
     ] ifTrue:[
-	Class nameSpaceQuerySignal answer:(self nameSpaceForApply)
-	do:[
-	    parseTree := Parser parseExpression:chunk.
-	].
-	(parseTree notNil
-	 and:[parseTree ~~ #Error
-	 and:[parseTree isMessage]]) ifTrue:[
-	    "/ Squeak support (#methodsFor:***)
-	    (#(
-	       #methodsFor:
-	       #privateMethodsFor:
-	       #publicMethodsFor:
-	       #ignoredMethodsFor:
-	       #protectedMethodsFor:
-
-	       #methodsFor:stamp:             "/ Squeak support
-	       #methodsFor                    "/ Dolphin support
-	       #methods                       "/ STV support
-	      )
-	    includes:parseTree selector) ifTrue:[
-		thisClass := (parseTree receiver evaluate).
-		(thisClass notNil and:[thisClass isKindOf:UndefinedVariable]) ifTrue:[
-		    |thisName path|
-
-		    thisName := thisClass name.
-		    path := thisName asCollectionOfSubstringsSeparatedByAll:'::'.
-		    1 to:path size do:[:length |
-			|ownerName owner|
-
-			ownerName := (path copyTo:length) asStringCollection asStringWith:'::'.
-			owner := Smalltalk classNamed:ownerName.
-			(owner notNil and:[owner isBehavior and:[owner isLoaded not]]) ifTrue:[
-			    self checkClassIsLoaded:owner.
-			].
-		    ].
-		    thisClass := (parseTree receiver evaluate).
-		].
-
-		thisClass isBehavior ifTrue:[
-		    (isLoaded := self checkClassIsLoaded:thisClass) ifFalse:[
-			outcome := 'Cannot compare this change\\(compare requires class to be loaded).'.
-			isSame := nil.
-		    ].
-
-		    parseTree selector == #methodsFor ifTrue:[
-			cat := 'Dolphin methods'.
-		    ] ifFalse:[
-			parseTree selector == #methods ifTrue:[
-			    cat := 'STV methods'.
-			] ifFalse:[
-			    cat := parseTree arg1 evaluate.
-			].
-		    ].
-		    newSource := aStream nextChunk.
-
-		    Class nameSpaceQuerySignal answer:(self nameSpaceForApply)
-		    do:[
-			parser := Parser parseMethod:newSource in:thisClass.
-		    ].
-		    (parser notNil and:[parser ~~ #Error]) ifTrue:[
-			sel := parser selector.
-			oldMethod := thisClass compiledMethodAt:sel.
-			oldMethod notNil ifTrue:[
-			    (oldMethod category = cat) ifFalse:[
-				Transcript showCR:'category changed.'.
-			    ].
-			    oldSource := oldMethod source.
-			    (oldSource = newSource) ifTrue:[
-				outcome := 'Same source'.
-				isSame := true.
-			    ] ifFalse:[
-				oldSource isNil ifTrue:[
-				    beep := true.
-				    outcome := 'No source for compare.'.
-				    isSame := true.
-				] ifFalse:[
-				    "/
-				    "/ compare for tabulator <-> space changes
-				    "/ before showing diff ...
-				    "/
-				    t1 := oldSource asCollectionOfLines collect:[:s | s withTabsExpanded].
-				    t2 := newSource asCollectionOfLines collect:[:s | s withTabsExpanded].
-				    t1 = t2 ifTrue:[
-					outcome := 'Same source'.
-					isSame := true.
-				    ] ifFalse:[
-					outcome := 'Source changed.'.
-					showDiff := true.
-					isSame := false.
-
-					"/
-					"/ check if only historyLine diffs
-					"/
-					(HistoryManager notNil
-					and:[HistoryManager isActive]) ifTrue:[
-					    (HistoryManager withoutHistoryLines:newSource)
-					    =
-					    (HistoryManager withoutHistoryLines:oldSource)
-					    ifTrue:[
-						outcome := 'Same source (history only)'.
-						isSame := true.
-						showDiff := false.
-					    ]
-					].
-				    ]
-				]
-			    ]
-			] ifFalse:[
-			    isLoaded ifTrue:[
-				beep := true.
-				outcome := 'Method does not exist.'.
-				isSame := nil.
-			    ]
-			]
-		    ] ifFalse:[
-			outcome := 'Change is unparsable (parse error).'.
-			isSame := nil.
-		    ].
-		    doShowResult ifTrue:[
-			(showDiff and:[oldSource notNil and:[newSource notNil]]) ifTrue:[
-			    d := DiffTextView
-				    openOn:oldSource label:(resources string:'current version (in image)')
-				    and:newSource label:(resources string:'change version').
-			    d label:'method differences'.
-			]
-		    ]
-		] ifFalse:[
-		    beep := true.
-		    outcome := 'Class does not exist.'.
-		    isSame := nil.
-		]
-	    ] ifFalse:[
-		beep := true.
-		outcome := 'Not comparable.'.
-		isSame := nil.
-	    ]
-	] ifFalse:[
-	    beep := true.
-	    outcome := 'Not comparable.'.
-	    isSame := nil.
-	]
+        Class nameSpaceQuerySignal answer:(self nameSpaceForApply)
+        do:[
+            parseTree := Parser parseExpression:chunk.
+        ].
+        (parseTree notNil
+         and:[parseTree ~~ #Error
+         and:[parseTree isMessage]]) ifTrue:[
+            "/ Squeak support (#methodsFor:***)
+            (#(
+               #methodsFor:
+               #privateMethodsFor:
+               #publicMethodsFor:
+               #ignoredMethodsFor:
+               #protectedMethodsFor:
+
+               #methodsFor:stamp:             "/ Squeak support
+               #methodsFor                    "/ Dolphin support
+               #methods                       "/ STV support
+              )
+            includes:parseTree selector) ifTrue:[
+                thisClass := (parseTree receiver evaluate).
+                (thisClass notNil and:[thisClass isKindOf:UndefinedVariable]) ifTrue:[
+                    |thisName path|
+
+                    thisName := thisClass name.
+                    path := thisName asCollectionOfSubstringsSeparatedByAll:'::'.
+                    1 to:path size do:[:length |
+                        |ownerName owner|
+
+                        ownerName := (path copyTo:length) asStringCollection asStringWith:'::'.
+                        owner := Smalltalk classNamed:ownerName.
+                        (owner notNil and:[owner isBehavior and:[owner isLoaded not]]) ifTrue:[
+                            self checkClassIsLoaded:owner.
+                        ].
+                    ].
+                    thisClass := (parseTree receiver evaluate).
+                ].
+
+                thisClass isBehavior ifTrue:[
+                    (isLoaded := self checkClassIsLoaded:thisClass) ifFalse:[
+                        outcome := 'Cannot compare this change\\(compare requires class to be loaded).'.
+                        isSame := nil.
+                    ].
+
+                    parseTree selector == #methodsFor ifTrue:[
+                        cat := 'Dolphin methods'.
+                    ] ifFalse:[
+                        parseTree selector == #methods ifTrue:[
+                            cat := 'STV methods'.
+                        ] ifFalse:[
+                            cat := parseTree arg1 evaluate.
+                        ].
+                    ].
+                    newSource := aStream nextChunk.
+
+                    Class nameSpaceQuerySignal answer:(self nameSpaceForApply)
+                    do:[
+                        parser := Parser parseMethod:newSource in:thisClass.
+                    ].
+                    (parser notNil and:[parser ~~ #Error]) ifTrue:[
+                        sel := parser selector.
+                        oldMethod := thisClass compiledMethodAt:sel.
+                        oldMethod notNil ifTrue:[
+                            (oldMethod category = cat) ifFalse:[
+                                Transcript showCR:'category changed.'.
+                            ].
+                            oldSource := oldMethod source.
+                            (oldSource = newSource) ifTrue:[
+                                outcome := 'Same source'.
+                                isSame := true.
+                            ] ifFalse:[
+                                oldSource isNil ifTrue:[
+                                    beep := true.
+                                    outcome := 'No source for compare.'.
+                                    isSame := true.
+                                ] ifFalse:[
+                                    "/
+                                    "/ compare for tabulator <-> space changes
+                                    "/ before showing diff ...
+                                    "/
+                                    t1 := oldSource asCollectionOfLines collect:[:s | s withTabsExpanded].
+                                    t2 := newSource asCollectionOfLines collect:[:s | s withTabsExpanded].
+                                    t1 = t2 ifTrue:[
+                                        outcome := 'Same source'.
+                                        isSame := true.
+                                    ] ifFalse:[
+                                        outcome := 'Source changed.'.
+                                        showDiff := true.
+                                        isSame := false.
+
+                                        "/
+                                        "/ check if only historyLine diffs
+                                        "/
+                                        (HistoryManager notNil
+                                        and:[HistoryManager isActive]) ifTrue:[
+                                            (HistoryManager withoutHistoryLines:newSource)
+                                            =
+                                            (HistoryManager withoutHistoryLines:oldSource)
+                                            ifTrue:[
+                                                outcome := 'Same source (history only)'.
+                                                isSame := true.
+                                                showDiff := false.
+                                            ]
+                                        ].
+                                    ]
+                                ]
+                            ]
+                        ] ifFalse:[
+                            isLoaded ifTrue:[
+                                beep := true.
+                                outcome := 'Method does not exist.'.
+                                isSame := nil.
+                            ]
+                        ]
+                    ] ifFalse:[
+                        outcome := 'Change is unparsable (parse error).'.
+                        isSame := nil.
+                    ].
+                    doShowResult ifTrue:[
+                        (showDiff and:[oldSource notNil and:[newSource notNil]]) ifTrue:[
+                            d := DiffTextView
+                                    openOn:oldSource label:(resources string:'current version (in image)')
+                                    and:newSource label:(resources string:'change version').
+                            d label:'method differences'.
+                        ]
+                    ]
+                ] ifFalse:[
+                    beep := true.
+                    outcome := 'Class does not exist.'.
+                    isSame := nil.
+                ]
+            ] ifFalse:[
+                beep := true.
+                outcome := 'Not comparable.'.
+                isSame := nil.
+            ]
+        ] ifFalse:[
+            beep := true.
+            outcome := 'Not comparable.'.
+            isSame := nil.
+        ]
     ].
     aStream close.
 
     doShowResult ifTrue:[
-	showDiff ifFalse:[
-	    outcome := (resources string:outcome) withCRs.
-	    beep ifTrue:[
-		self warn:outcome.
-	    ] ifFalse:[
-		self information:outcome.
-	    ]
+        showDiff ifFalse:[
+            outcome := (resources stringWithCRs:outcome).
+            beep ifTrue:[
+                self warn:outcome.
+            ] ifFalse:[
+                self information:outcome.
+            ]
 "/        Transcript showCR:outcome.
-	].
+        ].
     ].
     ^ isSame.
 
@@ -4150,20 +4150,20 @@
 
     again := true.
     [again] whileTrue:[
-	action := OptionBox
-			  request:(resources at:'The modified changelist has not been written back to the change file.\\Write change file before closing ?') withCRs
-			  label:'ChangesBrowser'
-			  image:(WarningBox iconBitmap)
-			  buttonLabels:(resources array:#('Cancel' 'Don''t Write' 'Write'))
-			  values:#(#abort #ignore #save)
-			  default:#save
-			  onCancel:#abort.
-
-	again := false.
-	action == #abort ifTrue:[AbortSignal raise. ^ self].
-	action  == #save ifTrue:[
-	    again := self writeBackChanges not
-	].
+        action := OptionBox
+                          request:(resources stringWithCRs:'The modified changelist has not been written back to the change file.\\Write change file before closing ?')
+                          label:'ChangesBrowser'
+                          image:(WarningBox iconBitmap)
+                          buttonLabels:(resources array:#('Cancel' 'Don''t Write' 'Write'))
+                          values:#(#abort #ignore #save)
+                          default:#save
+                          onCancel:#abort.
+
+        again := false.
+        action == #abort ifTrue:[AbortSignal raise. ^ self].
+        action  == #save ifTrue:[
+            again := self writeBackChanges not
+        ].
     ].
 !
 
@@ -5666,5 +5666,5 @@
 !ChangesBrowser class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/ChangesBrowser.st,v 1.332 2005-06-07 16:28:48 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/ChangesBrowser.st,v 1.333 2005-07-13 15:53:58 cg Exp $'
 ! !
--- a/FileBrowser.st	Wed Jul 13 17:50:42 2005 +0200
+++ b/FileBrowser.st	Wed Jul 13 17:54:29 2005 +0200
@@ -2201,7 +2201,7 @@
 
     dialog := Dialog new.
 
-    dialog addTextLabel:(resources string:'ENCODING_MSG') withCRs.
+    dialog addTextLabel:(resources stringWithCRs:'ENCODING_MSG') .
     dialog addVerticalSpace.
     dialog addListBoxOn:list withNumberOfLines:5.
 
@@ -3282,7 +3282,7 @@
     |queryBox|
 
     queryBox := FilenameEnterBox 
-                    title:(resources at:'Create new directory:') withCRs
+                    title:(resources stringWithCRs:'Create new directory:') 
                     okText:(resources at:'Create')
                     action:[:newName | self doCreateDirectory:newName].
     queryBox show.
@@ -3297,7 +3297,7 @@
     |sel queryBox|
 
     queryBox := FilenameEnterBox 
-                    title:(resources at:'Create new file:') withCRs
+                    title:(resources stringWithCRs:'Create new file:')
                     okText:(resources at:'Create')
                     action:[:newName | newName isEmpty ifFalse:[
                                            self doCreateFile:newName.
@@ -5162,7 +5162,7 @@
     |queryBox dirName|
 
     queryBox := FilenameEnterBox 
-                    title:(resources at:'Change directory to:') withCRs
+                    title:(resources stringWithCRs:'Change directory to:')
                     okText:(resources at:'Change')
                     action:[:newName | dirName := newName].
 "/    queryBox initialText:''.
@@ -5839,8 +5839,8 @@
                     msg := 'FileBrowser:\\directory %1 is no longer readable ?!!?'
                 ].
                 "/ sigh - avoid translating backslashes in WIN-filenames
-                msg := (resources string:msg) withCRs.
-                Dialog warn:(msg bindWith:currentDirectory pathName allBold).
+                msg := resources stringWithCRs:msg with:currentDirectory pathName allBold.
+                Dialog warn:msg.
 
                 fileListView contents:nil.
                 newLabel := myName , ': directory is gone !!'.
@@ -5924,8 +5924,8 @@
                 msg := '''%1'' is not a directory !!'
             ]
         ].
-        msg := (resources string:msg) withCRs.
-        Dialog warn:(msg bindWith:fileName allBold).
+        msg := resources stringWithCRs:msg with:fileName allBold.
+        Dialog warn:msg.
     ]
 
     "Modified: / 18.9.1997 / 18:22:30 / stefan"
@@ -6149,8 +6149,8 @@
         ] ifTrue:[
             msg := '''%1'' is not a regular file !!'.
         ].
-        msg := (resources string:msg) withCRs.
-        Dialog warn:(msg bindWith:fileNameString allBold).
+        msg := resources stringWithCRs:msg with:fileNameString allBold.
+        Dialog warn:msg.
         ^ self
     ].
 
@@ -6502,7 +6502,7 @@
             iconLbl := myName
         ] ifFalse:[
             f exists ifFalse:[
-                Dialog warn:(resources string:'oops, ''%1'' is gone or unreadable.' withCRs with:f pathName allBold).
+                Dialog warn:(resources stringWithCRs:'oops, ''%1'' is gone or unreadable.' with:f pathName allBold).
                 ^ self
             ].
             timeOfFileRead := f modificationTime.
@@ -6580,13 +6580,13 @@
                             yesToAll ifFalse:[
                                 idx == filesToRemove size ifTrue:[
                                     answer := Dialog
-                                                confirmWithCancel:(resources string:'Directory ''%1'' is not empty\remove anyway ?' with:fileName allBold) withCRs
+                                                confirmWithCancel:(resources stringWithCRs:'Directory ''%1'' is not empty\remove anyway ?' with:fileName allBold) 
                                                 labels:(resources array:#('Cancel' 'Remove'))
                                                 values:#(false true) 
                                                 default:2.
                                 ] ifFalse:[
                                     answer := Dialog
-                                                confirmWithCancel:(resources string:'Directory ''%1'' is not empty\remove anyway ?' with:fileName allBold) withCRs
+                                                confirmWithCancel:(resources stringWithCRs:'Directory ''%1'' is not empty\remove anyway ?' with:fileName allBold)
                                                 labels:(resources array:#('Cancel' 'Remove All' 'Remove'))
                                                 values:#(false #removeAll true) 
                                                 default:3.
@@ -7032,9 +7032,7 @@
         ].
 
         files size == 0 ifTrue:[
-            Dialog warn:((resources string:'Directory ''%1'' is gone.') 
-                        withCRs 
-                            bindWith:currentDirectory pathName allBold).
+            Dialog warn:(resources stringWithCRs:'Directory ''%1'' is gone.' with:currentDirectory pathName allBold).
             ^ self
         ].
         (sortByWhat value == #name) ifTrue:[
@@ -7516,5 +7514,5 @@
 !FileBrowser class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/FileBrowser.st,v 1.603 2005-05-06 09:21:27 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/FileBrowser.st,v 1.604 2005-07-13 15:53:02 cg Exp $'
 ! !