Merged 7dffb3cbf7c4 and f2c1f0fd05fb (branch default - CVS HEAD) jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Tue, 16 Apr 2013 10:22:43 +0200
branchjv
changeset 12680 4e2f5b0d4cb2
parent 12679 7dffb3cbf7c4 (current diff)
parent 12669 f2c1f0fd05fb (diff)
child 12681 adbbcc25326f
Merged 7dffb3cbf7c4 and f2c1f0fd05fb (branch default - CVS HEAD)
ChangeSetBrowser.st
ChangesBrowser.st
DiffCodeView.st
Tools__BrowserListWithFilter.st
Tools__ChangeList.st
Tools__ChangeSetBrowser2.st
Tools__NewSystemBrowser.st
extensions.st
--- a/ChangeSetBrowser.st	Tue Apr 16 09:35:45 2013 +0200
+++ b/ChangeSetBrowser.st	Tue Apr 16 10:22:43 2013 +0200
@@ -47,6 +47,7 @@
 "
 ! !
 
+
 !ChangeSetBrowser class methodsFor:'instance creation'!
 
 open
@@ -86,6 +87,7 @@
     "Modified: / 17-02-2011 / 10:29:50 / cg"
 ! !
 
+
 !ChangeSetBrowser class methodsFor:'defaults'!
 
 defaultLabel
@@ -94,6 +96,7 @@
     "Created: / 6.2.1998 / 13:25:47 / cg"
 ! !
 
+
 !ChangeSetBrowser class methodsFor:'menu specs'!
 
 menuSpec
@@ -545,6 +548,7 @@
       )
 ! !
 
+
 !ChangeSetBrowser methodsFor:'initialization & release'!
 
 askIfChangesAreToBeWrittenBack
@@ -624,6 +628,7 @@
     ^ "false" super showingDiffsDefault 
 ! !
 
+
 !ChangeSetBrowser methodsFor:'menu aspects'!
 
 hasNotUndoableChangeSelected
@@ -667,6 +672,7 @@
     ^ false
 ! !
 
+
 !ChangeSetBrowser methodsFor:'private'!
 
 applyChange:changeNr
@@ -693,8 +699,8 @@
 "/        AbortOperationRequest handle:[:ex |
 "/            ^ false.
 "/        ] do:[
-            Parser::ParseError handle:[:ex |       
-                ex signal == Parser::UndefinedSuperclassError ifTrue:[
+            ParseError handle:[:ex |       
+                ex signal == UndefinedSuperclassError ifTrue:[
                     codeView error:(ex errorString) position:1 to:nil from:nil 
                 ] ifFalse:[
                     codeView error:(ex description) position:(ex startPosition) to:(ex endPosition) from:(ex parser). 
@@ -979,6 +985,7 @@
     "Modified: / 7.2.1998 / 19:52:44 / cg"
 ! !
 
+
 !ChangeSetBrowser methodsFor:'user actions'!
 
 doInspectChange
@@ -1033,14 +1040,15 @@
     super updateDiffViewFor:changeNr.
 ! !
 
+
 !ChangeSetBrowser class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/ChangeSetBrowser.st,v 1.58 2013-04-02 19:24:48 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/ChangeSetBrowser.st,v 1.59 2013-04-11 08:42:18 stefan Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libtool/ChangeSetBrowser.st,v 1.58 2013-04-02 19:24:48 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/ChangeSetBrowser.st,v 1.59 2013-04-11 08:42:18 stefan Exp $'
 !
 
 version_HG
--- a/ChangesBrowser.st	Tue Apr 16 09:35:45 2013 +0200
+++ b/ChangesBrowser.st	Tue Apr 16 10:22:43 2013 +0200
@@ -992,21 +992,21 @@
 !ChangesBrowser methodsFor:'compiler interface-error handling'!
 
 correctableError:aString position:relPos to:relEndPos from:aCompiler
-    "compiler notifys us of an error - this should really not happen since
+    "compiler notifies us of an error - this should really not happen since
      changes ought to be correct (did someone edit the changes file ??).
      Show the bad change in the codeView and let codeView hilight the error;
      no corrections allowed here therefore return false"
 
     ShowWarningDialogs == true ifTrue:[
-	self error:aString position:relPos to:relEndPos from:aCompiler.
+        self error:aString position:relPos to:relEndPos from:aCompiler.
     ] ifFalse:[
-	Transcript showCR:aString.
+        Transcript showCR:aString.
     ].
     ^ false
 !
 
 correctableSelectorWarning:aString position:relPos to:relEndPos from:aCompiler
-    "compiler notifys us of a warning"
+    "compiler notifies us of a warning"
 
     ^ false
 
@@ -1015,7 +1015,7 @@
 !
 
 correctableWarning:aString position:relPos to:relEndPos from:aCompiler
-    "compiler notifys us of an error - this should really not happen since
+    "compiler notifies us of an error - this should really not happen since
      changes ought to be correct (did someone edit the changes file ??).
      Show the bad change in the codeView and let codeView hilight the error;
      no corrections allowed here therefore return false"
@@ -1026,7 +1026,7 @@
 !
 
 error:aString position:relPos to:relEndPos from:aCompiler
-    "compiler notifys us of an error - this should really not happen since
+    "compiler notifies us of an error - this should really not happen since
      changes ought to be correct (did someone edit the changes file ??).
      Show the bad change in the codeView and let codeView hilight the error"
 
@@ -1085,7 +1085,7 @@
 !
 
 warning:aString position:relPos to:relEndPos from:aCompiler
-    "compiler notifys us of a warning - ignore it"
+    "compiler notifies us of a warning - ignore it"
 
     ^ self
 ! !
@@ -6559,11 +6559,11 @@
 !ChangesBrowser class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/ChangesBrowser.st,v 1.437 2013-04-04 09:37:02 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/ChangesBrowser.st,v 1.438 2013-04-11 09:33:26 stefan Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libtool/ChangesBrowser.st,v 1.437 2013-04-04 09:37:02 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/ChangesBrowser.st,v 1.438 2013-04-11 09:33:26 stefan Exp $'
 !
 
 version_HG
--- a/DiffCodeView.st	Tue Apr 16 09:35:45 2013 +0200
+++ b/DiffCodeView.st	Tue Apr 16 10:22:43 2013 +0200
@@ -47,6 +47,7 @@
 "
 ! !
 
+
 !DiffCodeView class methodsFor:'defaults'!
 
 textViewClass
@@ -56,10 +57,31 @@
     ^ CodeView
 ! !
 
+
+!DiffCodeView methodsFor:'initialization'!
+
+initialize
+    super initialize.
+
+    textViews doWithIndex:[:v :i |
+        v readOnly:true.
+        "/ v acceptAction:[:text | self acceptInView:i ]
+    ].
+!
+
+leftAcceptAction:aOneArgBlock
+    (textViews at:1) acceptAction:aOneArgBlock
+!
+
+rightAcceptAction:aOneArgBlock
+    (textViews at:2) acceptAction:aOneArgBlock
+! !
+
+
 !DiffCodeView class methodsFor:'documentation'!
 
 version
-    ^ '$Id: DiffCodeView.st 7854 2012-01-30 17:49:41Z vranyj1 $'
+    ^ '$Header: /cvs/stx/stx/libtool/DiffCodeView.st,v 1.2 2013-04-14 18:10:35 cg Exp $'
 !
 
 version_HG
--- a/Tools_MethodList.st	Tue Apr 16 09:35:45 2013 +0200
+++ b/Tools_MethodList.st	Tue Apr 16 10:22:43 2013 +0200
@@ -817,7 +817,7 @@
             cls := aParameter at:1.
             sel := aParameter at:2.
             mthd := cls compiledMethodAt:sel.
-            (mthd isWrapped or:[mthd isMethodWithBreakpoints]) ifTrue:[
+            (mthd notNil and:[mthd isWrapped or:[mthd isMethodWithBreakpoints]]) ifTrue:[
                 (methodList includes:mthd originalMethod) ifTrue:[
                     methodList replaceAll:mthd originalMethod with:mthd.
                     lastSelectedMethods replaceAll:mthd originalMethod with:mthd.
@@ -1811,10 +1811,10 @@
 !MethodList class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/Tools_MethodList.st,v 1.83 2013-04-04 11:51:15 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/Tools_MethodList.st,v 1.84 2013-04-10 08:36:58 stefan Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libtool/Tools_MethodList.st,v 1.83 2013-04-04 11:51:15 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/Tools_MethodList.st,v 1.84 2013-04-10 08:36:58 stefan Exp $'
 ! !
 
--- a/Tools__BrowserListWithFilter.st	Tue Apr 16 09:35:45 2013 +0200
+++ b/Tools__BrowserListWithFilter.st	Tue Apr 16 10:22:43 2013 +0200
@@ -229,14 +229,16 @@
     | pattern filteredList |
 
     self showFilter ifFalse:[ ^ list ].
+
     pattern := self filterPattern.
     pattern isNil ifTrue:[ ^ list ].    
     filteredList := list value select:[:each|pattern matchObject: each relax: 1].
     filteredList isEmpty ifTrue:[
-    filteredList := list value select:[:each|pattern matchObject: each relax: 2].
-    filteredList isEmpty ifTrue:[
-    filteredList := list value select:[:each|pattern matchObject: each relax: 3].
-    ]].
+        filteredList := list value select:[:each|pattern matchObject: each relax: 2].
+        filteredList isEmpty ifTrue:[
+            filteredList := list value select:[:each|pattern matchObject: each relax: 3].
+        ]
+    ].
     ^filteredList
 
     "Created: / 29-11-2011 / 15:31:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -262,11 +264,11 @@
 !BrowserListWithFilter class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/Tools__BrowserListWithFilter.st,v 1.5 2013-02-08 14:10:27 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/Tools__BrowserListWithFilter.st,v 1.6 2013-04-14 06:51:14 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libtool/Tools__BrowserListWithFilter.st,v 1.5 2013-02-08 14:10:27 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/Tools__BrowserListWithFilter.st,v 1.6 2013-04-14 06:51:14 cg Exp $'
 !
 
 version_HG
--- a/Tools__ChangeList.st	Tue Apr 16 09:35:45 2013 +0200
+++ b/Tools__ChangeList.st	Tue Apr 16 10:22:43 2013 +0200
@@ -29,7 +29,7 @@
 
 Tools::BrowserListWithFilter subclass:#ChangeList
 	instanceVariableNames:'listHolder showRemovedHolder showSameHolder showTimestampHolder
-		allowRemoveHolder allowAcceptHolder scrollToBottom applyAction'
+                allowRemoveHolder allowAcceptHolder scrollToBottom applyAction showConflictsOnlyHolder'
 	classVariableNames:'LastSelectionConditionString'
 	poolDictionaries:''
 	category:'Interface-Browsers-ChangeSet'
@@ -87,6 +87,10 @@
     "Modified: / 31-08-2011 / 10:54:00 / cg"
 !
 
+iconExcla
+    ^ ToolbarIconLibrary iconExclaRed12x12
+!
+
 iconMinus
     ^ ToolbarIconLibrary iconMinusRed12x12
 
@@ -440,16 +444,17 @@
      (if this app is embedded in a subCanvas)."
 
     ^ #(
-	#allowAcceptHolder
-	#allowRemoveHolder
-	#inGeneratorHolder
-	#menuHolder
-	#outGeneratorHolder
-	#selectionHolder
-	#showFilterHolder
-	#showRemovedHolder
-	#showSameHolder
-	#showTimestampHolder
+        #allowAcceptHolder
+        #allowRemoveHolder
+        #inGeneratorHolder
+        #menuHolder
+        #outGeneratorHolder
+        #selectionHolder
+        #showFilterHolder
+        #showRemovedHolder
+        #showSameHolder
+        #showTimestampHolder
+        #showConflictsOnlyHolder
       ).
 
 ! !
@@ -626,6 +631,35 @@
     ^ listHolder
 !
 
+showConflictsOnlyHolder
+    "return/create the 'showConflictsOnlyHolder' value holder (automatically generated)"
+
+    showConflictsOnlyHolder isNil ifTrue:[
+        showConflictsOnlyHolder := ValueHolder with: true.
+        showConflictsOnlyHolder addDependent: self.
+    ].
+    ^ showConflictsOnlyHolder
+!
+
+showConflictsOnlyHolder:something
+    "set the 'showConflictsOnlyHolder' value holder (automatically generated)"
+
+    |oldValue newValue|
+
+    showConflictsOnlyHolder notNil ifTrue:[
+        oldValue := showConflictsOnlyHolder value.
+        showConflictsOnlyHolder removeDependent:self.
+    ].
+    showConflictsOnlyHolder := something.
+    showConflictsOnlyHolder notNil ifTrue:[
+        showConflictsOnlyHolder addDependent:self.
+    ].
+    newValue := showConflictsOnlyHolder value.
+    oldValue ~~ newValue ifTrue:[
+        self update:#value with:newValue from:showConflictsOnlyHolder.
+    ].
+!
+
 showRemovedHolder
     "return/create the 'showRemovedHolder' value holder (automatically generated)"
 
@@ -718,30 +752,36 @@
 
 !ChangeList methodsFor:'change & update'!
 
+selectionChanged
+   super selectionChanged
+!
+
 update: aspect with: param from: sender
 
     sender == allowRemoveHolder ifTrue:[
-	self listColumn: #removed visible: allowRemoveHolder value.
-	^self.
+        self listColumn: #removed visible: allowRemoveHolder value.
+        ^self.
     ].
 
     sender == showTimestampHolder ifTrue:[
-	self listColumn: #timeStamp visible: showTimestampHolder value.
-	^self.
+        self listColumn: #timeStamp visible: showTimestampHolder value.
+        ^self.
     ].
 
 
     sender == selectionHolder ifTrue:[
-	self selectionChanged.
-	^self
+        self selectionChanged.
+        ^ self
     ].
     sender == showSameHolder ifTrue:[
-	self updateList.
-	^self.
+        self updateList.
+        ^self.
     ].
     sender == showRemovedHolder ifTrue:[
-	self updateList.
-	^self.
+        self updateList
+    ].
+    sender == showConflictsOnlyHolder ifTrue:[
+        self updateList
     ].
 
     ^super update: aspect with: param from: sender
@@ -815,16 +855,16 @@
     "Superclass Tools::BrowserList says that I am responsible to implement this method"
 
     ^Iterator on:
-	[:whatToDo|
-	selectionHolder value do:
-	    [:changeListItem| | change |
-	    changeListItem notNil ifTrue:[
-		change := changeListItem change.
-		change isCompositeChange ifTrue:
-		    [change changes do: whatToDo]]]]
+        [:whatToDo|
+
+        selectionHolder value do:
+            [:changeListItem| | change |
+            change := changeListItem change.
+            change isCompositeChange ifTrue:
+                [change changes do: whatToDo]]].
 
     "Modified: / 24-07-2009 / 23:00:41 / Jan Vrany <vranyj1@fel.cvut.cz>"
-    "Modified: / 25-07-2012 / 15:39:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 24-10-2009 / 20:00:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 
@@ -857,19 +897,20 @@
 !ChangeList methodsFor:'menu actions'!
 
 listMenuApply
-    |sel list idx|
+    |sel list idx selectionHolder|
 
     self acceptEnabled ifFalse:[^self].
+    selectionHolder := self selectionHolder.
 
-    (sel := self selectionHolder value) do:[:e| applyAction value:e change].
+    (sel := selectionHolder value) do:[:e| applyAction value:e change].
     sel size == 1 ifTrue:[
-	list := self listHolder value.
-	idx := list indexOf:(sel first).
-	idx < list size ifTrue:[
-	    self selectionHolder value:(Array with:(list at:idx+1))
-	] ifFalse:[
-	    self selectionHolder value:#()
-	].
+        list := self listHolder value. 
+        idx := list indexOf:(sel first). 
+        idx < list size ifTrue:[
+            selectionHolder value:(Array with:(list at:idx+1))
+        ] ifFalse:[
+            selectionHolder value:#()
+        ].
     ].
 
     "Modified: / 24-10-2009 / 22:02:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -896,31 +937,35 @@
 !
 
 listMenuBrowseChanges: changes
+    | classes methods methodsOnly browserClass|
 
-    | classes methods methodsOnly |
     classes := Set new.
     methods := Set new.
     methodsOnly := true.
-    changes do:
-	[:each|
-	each  isClassChange ifTrue:
-	    [each  changeClass ifNotNil:
-		[classes add: each  changeClass.
-		each isMethodCodeChange
-		    ifTrue:
-			[each changeMethod ifNotNil:
-			    [methods add:each changeMethod]]
-		    ifFalse:
-			[methodsOnly := false]]]].
-    methodsOnly
-	ifTrue:
-	    [methods size = 1
-		ifTrue:[Smalltalk browserClass openInMethod: methods anyOne]
-		ifFalse:[Smalltalk browserClass browseMethods: methods asArray title: 'Selected methods from changeset' sort: true]]
-	ifFalse:
-	    [classes size = 1
-		ifTrue:[Smalltalk browserClass browseClass: classes anyOne]
-		ifFalse:[Smalltalk browserClass browseClasses: classes]]
+    changes do: [:each |
+        each isClassChange ifTrue:[
+            each changeClass ifNotNil:[
+                classes add: each  changeClass.
+                each isMethodCodeChange 
+                    ifTrue:
+                        [each changeMethod ifNotNil:
+                            [methods add:each changeMethod]]
+                    ifFalse:
+                        [methodsOnly := false]
+            ]
+        ]
+    ].
+
+    browserClass := Smalltalk browserClass.
+    methodsOnly 
+        ifTrue:
+            [methods size = 1 
+                ifTrue:[ browserClass openInMethod: methods anyOne]
+                ifFalse:[ browserClass browseMethods: methods asArray title: 'Selected methods from changeset' sort: true]]
+        ifFalse:
+            [classes size = 1
+                ifTrue:[ browserClass browseClass: classes anyOne]
+                ifFalse:[ browserClass browseClasses: classes]]
 
     "Modified: / 24-10-2009 / 22:02:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Created: / 24-01-2012 / 22:00:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -1045,6 +1090,22 @@
     "Modified: / 24-07-2009 / 22:06:53 / Jan Vrany <vranyj1@fel.cvut.cz>"
 !
 
+iconSelectorForChange:change
+    | delta sym selectorOrNil |
+
+    masterApplication notNil ifTrue:[
+        selectorOrNil := masterApplication iconSelectorForChange:change.
+        selectorOrNil notNil ifTrue:[ ^ selectorOrNil ].
+    ].
+    delta := change deltaDetail.
+    sym := delta shortDeltaSymbol.
+    sym = #+ ifTrue:[^#iconPlus].
+    sym = #- ifTrue:[^#iconMinus].
+    sym = #= ifTrue:[^#iconEqual].
+    "/ different.
+    ^ nil.
+!
+
 listColumn: columnId visible: visible
     visible ifTrue:[
         self listColumnShow: columnId
@@ -1126,44 +1187,44 @@
 
 updateList
     |inGenerator changeset firstLineShown oldSel newList newSel |
-
-    inGenerator := self inGeneratorHolder value.
-    listView notNil ifTrue:[
-	((listView isKindOf: ScrollableView) not or:[listView scrolledView notNil]) ifTrue:[
-	    firstLineShown := listView firstLineShown
-	].
-    ].
-    oldSel := self selection.
+    self withWaitCursorDo:[
+        inGenerator := self inGeneratorHolder value.
+        listView notNil ifTrue:[
+            ((listView isKindOf: ScrollableView) not or:[listView scrolledView notNil]) ifTrue:[
+                firstLineShown := listView firstLineShown
+            ].
+        ].
+        oldSel := self selection.
 
-    changeset := inGenerator isNil ifTrue:[ #() ] ifFalse:[ inGenerator ].
-    newList := changeset
-		select:
-		    [:chg |
-		    (self showRemovedHolder value or:[ chg removed not ])
-			and:[self showSameHolder value or:[chg delta ~~ #=]]
-		    ].
-    newList := self filterList: newList.
-    newList := newList collect:[:chg | self listEntryFor:chg ].
-    self listHolder value ~= newList ifTrue:[
-	self listHolder value: newList.
-	((newList size ~~ 0) and:[scrollToBottom]) ifTrue:[
-	    self selection: { newList last }
-	] ifFalse:[
-	    oldSel notEmptyOrNil ifTrue:[
-		newSel := OrderedCollection new: oldSel size.
-		oldSel := oldSel reject:[:e|e isNil].
-		oldSel := oldSel collect:[:e|e change].
-		newList do:[:e|(oldSel includes:e change) ifTrue:[newSel add:e]].
-		self selection: newSel.
-	    ].
-	    (listView notNil and:[firstLineShown notNil]) ifTrue:[
-		listView scrollToLine: (newList size min: firstLineShown).
-	    ].
-	].
-	scrollToBottom := false.
+        changeset := inGenerator isNil ifTrue:[ #() ] ifFalse:[ inGenerator ].
+        newList := changeset
+                    select:
+                        [:chg |
+                        (self showRemovedHolder value or:[ chg removed not ])
+                            and:[self showSameHolder value or:[chg delta ~~ #=]]
+                        ].
+        newList := self filterList: newList.
+        newList := newList collect:[:chg | self listEntryFor:chg ].
+        self listHolder value ~= newList ifTrue:[
+            self listHolder value: newList.
+            ((newList size ~~ 0) and:[scrollToBottom]) ifTrue:[
+                self selection: { newList last }
+            ] ifFalse:[
+                oldSel notEmptyOrNil ifTrue:[
+                    newSel := OrderedCollection new: oldSel size.
+                    oldSel := oldSel reject:[:e|e isNil].
+                    oldSel := oldSel collect:[:e|e change].
+                    newList do:[:e|(oldSel includes:e change) ifTrue:[newSel add:e]].
+                    self selection: newSel.
+                ].
+                (listView notNil and:[firstLineShown notNil]) ifTrue:[
+                    listView scrollToLine: (newList size min: firstLineShown).
+                ].
+            ].
+            scrollToBottom := false.
 
+        ]
     ]
-
     "Modified: / 28-12-2011 / 15:46:15 / cg"
     "Modified: / 01-08-2012 / 18:10:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
@@ -1190,14 +1251,15 @@
 !
 
 hasSingleChangeSelectedAndCanBrowse
-
+    self selectionHolder value ? #() do: [:each |
+        |chg|
 
-    self selectionHolder value ? #() do:
-	[:each|
-	(each change isClassChange and:
-	    [each change isMethodChange not
-		or:[each change isMethodCodeChange]]) ifFalse:[^false]].
-    ^true
+        chg := each change.
+        chg isClassChange ifTrue:[
+            (chg isMethodChange not or:[chg isMethodCodeChange]) ifFalse:[^ false]
+        ].
+    ].
+    ^ true
 !
 
 showColumn: columnSymbol
@@ -1275,18 +1337,31 @@
 children
 
     children isNil ifTrue:[
-	change isCompositeChange ifTrue:[
-	    children := OrderedCollection new: change changes size.
-	    change changes do:[:chg|
-		((self application showRemovedHolder value or:[ chg removed not ])
-		    and:[self application showSameHolder value or:[chg delta ~~ #=]])
-			ifTrue:[
-			    children add: ((self application listEntryFor: chg) parent: self)
-			]
-	    ].
-	] ifFalse:[
-	    children :=  #()
-	]
+        change isCompositeChange ifTrue:[
+            children := OrderedCollection new: change changes size.
+            self application showConflictsOnlyHolder value ifTrue:[
+                change changes do:[:chg|
+                    (chg isConflict) ifTrue:[
+                        children add: ((self application listEntryFor: chg) parent: self)
+                    ]
+                ].
+            ] ifFalse:[
+                |showRemoved showSame|
+
+                showRemoved := self application showRemovedHolder value.
+                showSame := self application showSameHolder value.
+
+                change changes do:[:chg|
+                    ((showRemoved or:[ chg removed not ])
+                        and:[showSame or:[chg delta ~~ #=]]) 
+                            ifTrue:[
+                                children add: ((self application listEntryFor: chg) parent: self)
+                            ]
+                ].
+            ]
+        ] ifFalse:[
+            children :=  #()
+        ]
     ].
     ^children
 
@@ -1313,8 +1388,8 @@
 !
 
 iconDelta
+    | iconSelector |
 
-    | iconSelector |
     iconSelector := self iconSelector.
     iconSelector isNil ifTrue:[^nil].
     self removed ifTrue:[iconSelector := iconSelector , #Grayed].
@@ -1325,10 +1400,12 @@
 !
 
 iconRemoved
+    |appClass|
 
-    ^self removed
-	ifTrue: [self application class uncheckedIcon ]
-	ifFalse:[self application class checkedIcon ]
+    appClass := self application class.
+    ^self removed 
+        ifTrue: [appClass uncheckedIcon ]
+        ifFalse:[appClass checkedIcon ]
 
     "Created: / 05-12-2009 / 14:11:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -1456,16 +1533,7 @@
 !ChangeList::ListEntry methodsFor:'private'!
 
 iconSelector
-    | delta |
-
-    delta := change deltaDetail.
-    delta shortDeltaSymbol = #+ ifTrue:[^#iconPlus].
-    delta shortDeltaSymbol = #- ifTrue:[^#iconMinus].
-    delta shortDeltaSymbol = #= ifTrue:[^#iconEqual].
-
-    ^ nil.
-
-    "Modified: / 31-08-2011 / 10:39:32 / cg"
+    ^ application iconSelectorForChange:change
 ! !
 
 
@@ -1482,11 +1550,11 @@
 !ChangeList class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/Tools__ChangeList.st,v 1.21 2013-03-30 01:59:17 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/Tools__ChangeList.st,v 1.24 2013-04-14 19:55:58 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libtool/Tools__ChangeList.st,v 1.21 2013-03-30 01:59:17 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/Tools__ChangeList.st,v 1.24 2013-04-14 19:55:58 cg Exp $'
 !
 
 version_HG
--- a/Tools__ChangeSetBrowser2.st	Tue Apr 16 09:35:45 2013 +0200
+++ b/Tools__ChangeSetBrowser2.st	Tue Apr 16 10:22:43 2013 +0200
@@ -29,14 +29,14 @@
 
 ToolApplicationModel subclass:#ChangeSetBrowser2
 	instanceVariableNames:'changesetHolder titleHolder allowOpenHolder changesetFile
-		navigatorChangesetHolder navigatorSpecHolder list1 list1Holder
-		selection1Holder list2 list2Holder selection2Holder classHolder
-		languageHolder codeAspectHolder showRemovedAspect showSameAspect
-		showTimestampHolder sourceView changeSourceHolder
-		imageSourceHolder targetPackage targetNamespace allowRemoveHolder
-		allowAcceptHolder infoPanel updateChangeFileHolder
-		showFilterHolder showingRegularChangesetHolder isWorkingHolder
-		isWorkingNotHolder hasSelectionHolder'
+                navigatorChangesetHolder navigatorSpecHolder list1 list1Holder
+                selection1Holder list2 list2Holder selection2Holder classHolder
+                languageHolder codeAspectHolder showRemovedAspect showSameAspect
+                showTimestampHolder sourceView changeSourceHolder
+                imageSourceHolder targetPackage targetNamespace allowRemoveHolder
+                allowAcceptHolder infoPanel updateChangeFileHolder
+                showFilterHolder showingRegularChangesetHolder isWorkingHolder
+                isWorkingNotHolder hasSelectionHolder showConflictsOnlyAspect'
 	classVariableNames:'ShowRemoved LastSelectionConditionString RecentTargetPackages'
 	poolDictionaries:''
 	category:'Interface-Browsers-ChangeSet'
@@ -80,6 +80,7 @@
 "
 ! !
 
+
 !ChangeSetBrowser2 class methodsFor:'instance creation'!
 
 on: aStringOrChangeSet
@@ -127,6 +128,7 @@
     "Created: / 17-05-2012 / 23:36:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !ChangeSetBrowser2 class methodsFor:'accessing'!
 
 showRemoved
@@ -139,6 +141,7 @@
     ShowRemoved := aBoolean
 ! !
 
+
 !ChangeSetBrowser2 class methodsFor:'help specs'!
 
 flyByHelpSpec
@@ -362,6 +365,7 @@
     "Modified: / 01-08-2012 / 18:40:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !ChangeSetBrowser2 class methodsFor:'image specs'!
 
 applyFromLastSnapshotIcon
@@ -632,6 +636,7 @@
 @P@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@') ; colorMapFromArray:#[0 0 0 255 255 255 255 0 0 170 170 170]; mask:((Depth1Image new) width: 22; height: 22; photometric:(#blackIs0); bitsPerSample:(#(1)); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'C??@C??@C??@C??@C??@C??@C??@C??@C??@C??@C??@C??@C??@C??B@@@B@C@B@G B@O0@@_8@@G @@G @@G @') ; yourself); yourself]
 ! !
 
+
 !ChangeSetBrowser2 class methodsFor:'interface opening'!
 
 confirmChanges: aChangeSet
@@ -736,6 +741,7 @@
     "Modified: / 26-07-2012 / 13:19:30 / cg"
 ! !
 
+
 !ChangeSetBrowser2 class methodsFor:'interface specs'!
 
 hierarchicalNavigatorSpec
@@ -754,69 +760,73 @@
 
     ^
      #(FullSpec
-	name: hierarchicalNavigatorSpec
-	window:
+        name: hierarchicalNavigatorSpec
+        window:
        (WindowSpec
-	  label: 'Hierarchical Navigator'
-	  name: 'Hierarchical Navigator'
-	  min: (Point 10 10)
-	  bounds: (Rectangle 0 0 300 300)
-	)
-	component:
+          label: 'Hierarchical Navigator'
+          name: 'Hierarchical Navigator'
+          min: (Point 10 10)
+          bounds: (Rectangle 0 0 300 300)
+        )
+        component:
        (SpecCollection
-	  collection: (
-	   (SubCanvasSpec
-	      name: 'ChangeList'
-	      layout: (LayoutFrame 0 0 0 0 0 1 0 1)
-	      hasHorizontalScrollBar: false
-	      hasVerticalScrollBar: false
-	      majorKey: #'Tools::HierarchicalChangeList'
-	      subAspectHolders:
-	     (Array
-
-	       (SubChannelInfoSpec
-		  subAspect: allowAcceptHolder
-		  aspect: allowAcceptHolder
-		)
-	       (SubChannelInfoSpec
-		  subAspect: allowRemoveHolder
-		  aspect: allowRemoveHolder
-		)
-
-	       (SubChannelInfoSpec
-		  subAspect: inGeneratorHolder
-		  aspect: list1Holder
-		)
-	       (SubChannelInfoSpec
-		  subAspect: menuHolder
-		  aspect: list1MenuHolder
-		)
-
-	       (SubChannelInfoSpec
-		  subAspect: selectionHolder
-		  aspect: selection1Holder
-		)
-	       (SubChannelInfoSpec
-		  subAspect: showFilterHolder
-		  aspect: showFilterHolder
-		)
-
-	       (SubChannelInfoSpec
-		  subAspect: showRemovedHolder
-		  aspect: showRemovedAspect
-		)
-	       (SubChannelInfoSpec
-		  subAspect: showSameHolder
-		  aspect: showSameAspect
-		)
-	      )
-	      createNewApplication: true
-	      createNewBuilder: true
-	      postBuildCallback: list1View:
-	    )
-	   )
-
-	)
+          collection: (
+           (SubCanvasSpec
+              name: 'ChangeList'
+              layout: (LayoutFrame 0 0 0 0 0 1 0 1)
+              hasHorizontalScrollBar: false
+              hasVerticalScrollBar: false
+              majorKey: #'Tools::HierarchicalChangeList'
+              subAspectHolders:
+             (Array
+
+               (SubChannelInfoSpec
+                  subAspect: allowAcceptHolder
+                  aspect: allowAcceptHolder
+                )
+               (SubChannelInfoSpec
+                  subAspect: allowRemoveHolder
+                  aspect: allowRemoveHolder
+                )
+
+               (SubChannelInfoSpec
+                  subAspect: inGeneratorHolder
+                  aspect: list1Holder
+                )
+               (SubChannelInfoSpec
+                  subAspect: menuHolder
+                  aspect: list1MenuHolder
+                )
+
+               (SubChannelInfoSpec
+                  subAspect: selectionHolder
+                  aspect: selection1Holder
+                )
+               (SubChannelInfoSpec
+                  subAspect: showFilterHolder
+                  aspect: showFilterHolder
+                )
+
+               (SubChannelInfoSpec
+                  subAspect: showRemovedHolder
+                  aspect: showRemovedAspect
+                )
+               (SubChannelInfoSpec
+                  subAspect: showSameHolder
+                  aspect: showSameAspect
+                )
+               (SubChannelInfoSpec
+                  subAspect: showConflictsOnlyHolder
+                  aspect: showConflictsOnlyAspect
+                )
+              )
+              createNewApplication: true
+              createNewBuilder: true
+              postBuildCallback: list1View:
+            )
+           )
+
+        )
       )
 !
 
@@ -836,74 +846,78 @@
 
     ^
      #(FullSpec
-	name: oneColumnNavigatorSpec
-	window:
+        name: oneColumnNavigatorSpec
+        window:
        (WindowSpec
-	  label: 'One Column Navigator'
-	  name: 'One Column Navigator'
-	  min: (Point 10 10)
-	  bounds: (Rectangle 0 0 300 300)
-	)
-	component:
+          label: 'One Column Navigator'
+          name: 'One Column Navigator'
+          min: (Point 10 10)
+          bounds: (Rectangle 0 0 300 300)
+        )
+        component:
        (SpecCollection
-	  collection: (
-	   (SubCanvasSpec
-	      name: 'ChangeList'
-	      layout: (LayoutFrame 0 0 0 0 0 1 0 1)
-	      hasHorizontalScrollBar: false
-	      hasVerticalScrollBar: false
-	      majorKey: #'Tools::ChangeList'
-	      subAspectHolders:
-	     (Array
-
-	       (SubChannelInfoSpec
-		  subAspect: allowAcceptHolder
-		  aspect: allowAcceptHolder
-		)
-	       (SubChannelInfoSpec
-		  subAspect: allowRemoveHolder
-		  aspect: allowRemoveHolder
-		)
-
-	       (SubChannelInfoSpec
-		  subAspect: inGeneratorHolder
-		  aspect: list1Holder
-		)
-	       (SubChannelInfoSpec
-		  subAspect: menuHolder
-		  aspect: list1MenuHolder
-		)
-
-	       (SubChannelInfoSpec
-		  subAspect: selectionHolder
-		  aspect: selection1Holder
-		)
-	       (SubChannelInfoSpec
-		  subAspect: showFilterHolder
-		  aspect: showFilterHolder
-		)
-
-	       (SubChannelInfoSpec
-		  subAspect: showRemovedHolder
-		  aspect: showRemovedAspect
-		)
-	       (SubChannelInfoSpec
-		  subAspect: showSameHolder
-		  aspect: showSameAspect
-		)
-
-	       (SubChannelInfoSpec
-		  subAspect: showTimestampHolder
-		  aspect: showTimestampHolder
-		)
-	      )
-	      createNewApplication: true
-	      createNewBuilder: true
-	      postBuildCallback: list1View:
-	    )
-	   )
-
-	)
+          collection: (
+           (SubCanvasSpec
+              name: 'ChangeList'
+              layout: (LayoutFrame 0 0 0 0 0 1 0 1)
+              hasHorizontalScrollBar: false
+              hasVerticalScrollBar: false
+              majorKey: #'Tools::ChangeList'
+              subAspectHolders:
+             (Array
+
+               (SubChannelInfoSpec
+                  subAspect: allowAcceptHolder
+                  aspect: allowAcceptHolder
+                )
+               (SubChannelInfoSpec
+                  subAspect: allowRemoveHolder
+                  aspect: allowRemoveHolder
+                )
+
+               (SubChannelInfoSpec
+                  subAspect: inGeneratorHolder
+                  aspect: list1Holder
+                )
+               (SubChannelInfoSpec
+                  subAspect: menuHolder
+                  aspect: list1MenuHolder
+                )
+
+               (SubChannelInfoSpec
+                  subAspect: selectionHolder
+                  aspect: selection1Holder
+                )
+               (SubChannelInfoSpec
+                  subAspect: showFilterHolder
+                  aspect: showFilterHolder
+                )
+
+               (SubChannelInfoSpec
+                  subAspect: showRemovedHolder
+                  aspect: showRemovedAspect
+                )
+               (SubChannelInfoSpec
+                  subAspect: showSameHolder
+                  aspect: showSameAspect
+                )
+
+               (SubChannelInfoSpec
+                  subAspect: showTimestampHolder
+                  aspect: showTimestampHolder
+               (SubChannelInfoSpec
+                  subAspect: showConflictsOnlyHolder
+                  aspect: showConflictsOnlyAspect
+                )
+                )
+              )
+              createNewApplication: true
+              createNewBuilder: true
+              postBuildCallback: list1View:
+            )
+           )
+
+        )
       )
 !
 
@@ -923,141 +937,149 @@
 
     ^
      #(FullSpec
-	name: twoColumnNavigatorSpec
-	window:
+        name: twoColumnNavigatorSpec
+        window:
        (WindowSpec
-	  label: 'Two Column Navigator'
-	  name: 'Two Column Navigator'
-	  min: (Point 10 10)
-	  bounds: (Rectangle 0 0 300 300)
-	)
-	component:
+          label: 'Two Column Navigator'
+          name: 'Two Column Navigator'
+          min: (Point 10 10)
+          bounds: (Rectangle 0 0 300 300)
+        )
+        component:
        (SpecCollection
-	  collection: (
-	   (VariableHorizontalPanelSpec
-	      name: 'Columns'
-	      layout: (LayoutFrame 0 0 0 0 0 1 0 1)
-	      component:
-	     (SpecCollection
-		collection: (
-		 (SubCanvasSpec
-		    name: 'FirstColumn'
-		    hasHorizontalScrollBar: false
-		    hasVerticalScrollBar: false
-		    majorKey: #'Tools::ChangeList'
-		    subAspectHolders:
-		   (Array
-
-		     (SubChannelInfoSpec
-			subAspect: allowAcceptHolder
-			aspect: allowAcceptHolder
-		      )
-		     (SubChannelInfoSpec
-			subAspect: allowRemoveHolder
-			aspect: allowRemoveHolder
-		      )
-
-		     (SubChannelInfoSpec
-			subAspect: inGeneratorHolder
-			aspect: list1Holder
-		      )
-		     (SubChannelInfoSpec
-			subAspect: menuHolder
-			aspect: list1MenuHolder
-		      )
-
-		     (SubChannelInfoSpec
-			subAspect: outGeneratorHolder
-			aspect: list2Holder
-		      )
-		     (SubChannelInfoSpec
-			subAspect: selectionHolder
-			aspect: selection1Holder
-		      )
-
-		     (SubChannelInfoSpec
-			subAspect: showFilterHolder
-			aspect: showFilterHolder
-		      )
-		     (SubChannelInfoSpec
-			subAspect: showRemovedHolder
-			aspect: showRemovedAspect
-		      )
-
-		     (SubChannelInfoSpec
-			subAspect: showSameHolder
-			aspect: showSameAspect
-		      )
-		     (SubChannelInfoSpec
-			subAspect: showTimestampHolder
-			aspect: showTimestampHolder
-		      )
-		    )
-		    createNewApplication: true
-		    createNewBuilder: true
-		    postBuildCallback: list1View:
-		  )
-		 (SubCanvasSpec
-		    name: 'SecondColumn'
-		    hasHorizontalScrollBar: false
-		    hasVerticalScrollBar: false
-		    majorKey: #'Tools::ChangeList'
-		    subAspectHolders:
-		   (Array
-
-		     (SubChannelInfoSpec
-			subAspect: allowAcceptHolder
-			aspect: allowAcceptHolder
-		      )
-		     (SubChannelInfoSpec
-			subAspect: allowRemoveHolder
-			aspect: allowRemoveHolder
-		      )
-
-		     (SubChannelInfoSpec
-			subAspect: inGeneratorHolder
-			aspect: list2Holder
-		      )
-		     (SubChannelInfoSpec
-			subAspect: menuHolder
-			aspect: list2MenuHolder
-		      )
-
-		     (SubChannelInfoSpec
-			subAspect: selectionHolder
-			aspect: selection2Holder
-		      )
-		     (SubChannelInfoSpec
-			subAspect: showFilterHolder
-			aspect: showFilterHolder
-		      )
-
-		     (SubChannelInfoSpec
-			subAspect: showRemovedHolder
-			aspect: showRemovedAspect
-		      )
-		     (SubChannelInfoSpec
-			subAspect: showSameHolder
-			aspect: showSameAspect
-		      )
-
-		     (SubChannelInfoSpec
-			subAspect: showTimestampHolder
-			aspect: showTimestampHolder
-		      )
-		    )
-		    createNewApplication: true
-		    createNewBuilder: true
-		    postBuildCallback: list2View:
-		  )
-		 )
-
-	      )
-	      handles: (Any 0.5 1.0)
-	    )
-	   )
-
-	)
+          collection: (
+           (VariableHorizontalPanelSpec
+              name: 'Columns'
+              layout: (LayoutFrame 0 0 0 0 0 1 0 1)
+              component:
+             (SpecCollection
+                collection: (
+                 (SubCanvasSpec
+                    name: 'FirstColumn'
+                    hasHorizontalScrollBar: false
+                    hasVerticalScrollBar: false
+                    majorKey: #'Tools::ChangeList'
+                    subAspectHolders:
+                   (Array
+
+                     (SubChannelInfoSpec
+                        subAspect: allowAcceptHolder
+                        aspect: allowAcceptHolder
+                      )
+                     (SubChannelInfoSpec
+                        subAspect: allowRemoveHolder
+                        aspect: allowRemoveHolder
+                      )
+
+                     (SubChannelInfoSpec
+                        subAspect: inGeneratorHolder
+                        aspect: list1Holder
+                      )
+                     (SubChannelInfoSpec
+                        subAspect: menuHolder
+                        aspect: list1MenuHolder
+                      )
+
+                     (SubChannelInfoSpec
+                        subAspect: outGeneratorHolder
+                        aspect: list2Holder
+                      )
+                     (SubChannelInfoSpec
+                        subAspect: selectionHolder
+                        aspect: selection1Holder
+                      )
+
+                     (SubChannelInfoSpec
+                        subAspect: showFilterHolder
+                        aspect: showFilterHolder
+                      )
+                     (SubChannelInfoSpec
+                        subAspect: showRemovedHolder
+                        aspect: showRemovedAspect
+                      )
+
+                     (SubChannelInfoSpec
+                        subAspect: showSameHolder
+                        aspect: showSameAspect
+                      )
+                     (SubChannelInfoSpec
+                        subAspect: showTimestampHolder
+                        aspect: showTimestampHolder
+                      )
+                   (SubChannelInfoSpec
+                      subAspect: showConflictsOnlyHolder
+                      aspect: showConflictsOnlyAspect
+                    )
+                    )
+                    createNewApplication: true
+                    createNewBuilder: true
+                    postBuildCallback: list1View:
+                  )
+                 (SubCanvasSpec
+                    name: 'SecondColumn'
+                    hasHorizontalScrollBar: false
+                    hasVerticalScrollBar: false
+                    majorKey: #'Tools::ChangeList'
+                    subAspectHolders:
+                   (Array
+
+                     (SubChannelInfoSpec
+                        subAspect: allowAcceptHolder
+                        aspect: allowAcceptHolder
+                      )
+                     (SubChannelInfoSpec
+                        subAspect: allowRemoveHolder
+                        aspect: allowRemoveHolder
+                      )
+
+                     (SubChannelInfoSpec
+                        subAspect: inGeneratorHolder
+                        aspect: list2Holder
+                      )
+                     (SubChannelInfoSpec
+                        subAspect: menuHolder
+                        aspect: list2MenuHolder
+                      )
+
+                     (SubChannelInfoSpec
+                        subAspect: selectionHolder
+                        aspect: selection2Holder
+                      )
+                     (SubChannelInfoSpec
+                        subAspect: showFilterHolder
+                        aspect: showFilterHolder
+                      )
+
+                     (SubChannelInfoSpec
+                        subAspect: showRemovedHolder
+                        aspect: showRemovedAspect
+                      )
+                     (SubChannelInfoSpec
+                        subAspect: showSameHolder
+                        aspect: showSameAspect
+                      )
+
+                     (SubChannelInfoSpec
+                        subAspect: showTimestampHolder
+                        aspect: showTimestampHolder
+               (SubChannelInfoSpec
+                  subAspect: showConflictsOnlyHolder
+                  aspect: showConflictsOnlyAspect
+                )
+                      )
+                    )
+                    createNewApplication: true
+                    createNewBuilder: true
+                    postBuildCallback: list2View:
+                  )
+                 )
+
+              )
+              handles: (Any 0.5 1.0)
+            )
+           )
+
+        )
       )
 !
 
@@ -1221,6 +1243,7 @@
     "Modified: / 16-03-2012 / 13:09:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !ChangeSetBrowser2 class methodsFor:'menu specs'!
 
 changeMenu
@@ -1240,141 +1263,147 @@
 
     ^
      #(Menu
-	(
-	 (MenuItem
-	    enabled: hasChangeSelectedAndNotRemoved:
-	    label: 'Apply'
-	    itemValue: changeMenuApplySelection:
-	    translateLabel: true
-	    isVisible: allowAcceptHolder
-	    shortcutKey: Accept
-	    auxValue: 100
-	  )
-	 (MenuItem
-	    label: 'Apply all'
-	    itemValue: changeMenuApply:
-	    translateLabel: true
-	    isVisible: allowAcceptHolder
-	  )
-	 (MenuItem
-	    label: '-'
-	    isVisible: allowAcceptHolder
-	  )
-	 (MenuItem
-	    label: 'Delete (selected)'
-	    itemValue: changeMenuDeleteSelection:
-	    nameKey: Delete
-	    translateLabel: true
-	    isVisible: allowRemoveHolder
-	    shortcutKey: Delete
-	  )
-	 (MenuItem
-	    label: 'Delete (unselected)'
-	    itemValue: changeMenuDeleteSelectionInverted:
-	    nameKey: Delete
-	    translateLabel: true
-	    isVisible: allowRemoveHolder
-	  )
-	 (MenuItem
-	    label: 'Undelete'
-	    itemValue: changeMenuUndeleteSelection:
-	    nameKey: Undelete
-	    translateLabel: true
-	    isVisible: allowRemoveHolder
-	  )
-	 (MenuItem
-	    label: '-'
-	    isVisible: allowRemoveHolder
-	  )
-	 (MenuItem
-	    label: 'Select...'
-	    translateLabel: true
-	    submenu:
-	   (Menu
-	      (
-	       (MenuItem
-		  label: 'Select same'
-		  itemValue: changeMenuSelectSame:
-		  translateLabel: true
-		)
-	       (MenuItem
-		  label: 'Select additions (new classes/methods)'
-		  itemValue: changeMenuSelectAdditions:
-		  translateLabel: true
-		)
-	       (MenuItem
-		  label: 'Select removals'
-		  itemValue: changeMenuSelectRemovals:
-		  translateLabel: true
-		)
-	       (MenuItem
-		  label: 'Select differences'
-		  itemValue: changeMenuSelectDifferences:
-		  translateLabel: true
-		)
-	       (MenuItem
-		  label: '-'
-		)
-	       (MenuItem
-		  label: 'Select all'
-		  itemValue: changeMenuSelectAll:
-		  translateLabel: true
-		  shortcutKey: SelectAll
-		)
-	       (MenuItem
-		  label: 'Select none'
-		  itemValue: changeMenuSelectNone:
-		  translateLabel: true
-		)
-	       (MenuItem
-		  label: 'Invert Selection'
-		  itemValue: changeMenuSelectInversion:
-		  translateLabel: true
-		)
-	       (MenuItem
-		  label: '-'
-		)
-	       (MenuItem
-		  label: 'Select Using Block...'
-		  itemValue: changeMenuSelectUsingBlock:
-		  translateLabel: true
-		)
-	       )
-	      nil
-	      nil
-	    )
-	  )
-	 (MenuItem
-	    label: '-'
-	  )
-	 (MenuItem
-	    label: 'Show Deleted'
-	    translateLabel: true
-	    isVisible: allowRemoveHolder
-	    indication: showRemovedAspect
-	  )
-	 (MenuItem
-	    label: 'Show Same'
-	    translateLabel: true
-	    indication: showSameAspect
-	  )
-	 (MenuItem
-	    label: '-'
-	  )
-	 (MenuItem
-	    label: 'Inspect change'
-	    itemValue: changeMenuInspect:
-	    translateLabel: true
-	  )
-	 (MenuItem
-	    enabled: hasSingleChangeSelectedAndCanBrowse:
-	    label: 'Browse Method(s)'
-	    itemValue: changeMenuBrowse:
-	    translateLabel: true
-	  )
-	 )
-	nil
-	nil
+        (
+         (MenuItem
+            enabled: hasChangeSelectedAndNotRemoved:
+            label: 'Apply'
+            itemValue: changeMenuApplySelection:
+            translateLabel: true
+            isVisible: allowAcceptHolder
+            shortcutKey: Accept
+            auxValue: 100
+          )
+         (MenuItem
+            label: 'Apply all'
+            itemValue: changeMenuApply:
+            translateLabel: true
+            isVisible: allowAcceptHolder
+          )
+         (MenuItem
+            label: '-'
+            isVisible: allowAcceptHolder
+          )
+         (MenuItem
+            label: 'Delete (selected)'
+            itemValue: changeMenuDeleteSelection:
+            nameKey: Delete
+            translateLabel: true
+            isVisible: allowRemoveHolder
+            shortcutKey: Delete
+          )
+         (MenuItem
+            label: 'Delete (unselected)'
+            itemValue: changeMenuDeleteSelectionInverted:
+            nameKey: Delete
+            translateLabel: true
+            isVisible: allowRemoveHolder
+          )
+         (MenuItem
+            label: 'Undelete'
+            itemValue: changeMenuUndeleteSelection:
+            nameKey: Undelete
+            translateLabel: true
+            isVisible: allowRemoveHolder
+          )
+         (MenuItem
+            label: '-'
+            isVisible: allowRemoveHolder
+          )
+         (MenuItem
+            label: 'Select...'
+            translateLabel: true
+            submenu:
+           (Menu
+              (
+               (MenuItem
+                  label: 'Select same'
+                  itemValue: changeMenuSelectSame:
+                  translateLabel: true
+                )
+               (MenuItem
+                  label: 'Select additions (new classes/methods)'
+                  itemValue: changeMenuSelectAdditions:
+                  translateLabel: true
+                )
+               (MenuItem
+                  label: 'Select removals'
+                  itemValue: changeMenuSelectRemovals:
+                  translateLabel: true
+                )
+               (MenuItem
+                  label: 'Select differences'
+                  itemValue: changeMenuSelectDifferences:
+                  translateLabel: true
+                )
+               (MenuItem
+                  label: '-'
+                )
+               (MenuItem
+                  label: 'Select all'
+                  itemValue: changeMenuSelectAll:
+                  translateLabel: true
+                  shortcutKey: SelectAll
+                )
+               (MenuItem
+                  label: 'Select none'
+                  itemValue: changeMenuSelectNone:
+                  translateLabel: true
+                )
+               (MenuItem
+                  label: 'Invert Selection'
+                  itemValue: changeMenuSelectInversion:
+                  translateLabel: true
+                )
+               (MenuItem
+                  label: '-'
+                )
+               (MenuItem
+                  label: 'Select Using Block...'
+                  itemValue: changeMenuSelectUsingBlock:
+                  translateLabel: true
+                )
+               )
+              nil
+              nil
+            )
+          )
+         (MenuItem
+            label: '-'
+          )
+         (MenuItem
+            enabled: notShowConflictsOnlyAspect
+            label: 'Show Deleted'
+            translateLabel: true
+            isVisible: allowRemoveHolder
+            indication: showRemovedAspect
+          )
+         (MenuItem
+            enabled: notShowConflictsOnlyAspect
+            label: 'Show Same'
+            translateLabel: true
+            indication: showSameAspect
+          )
+         (MenuItem
+            label: 'Show Conflicts Only'
+            indication: showConflictsOnlyAspect
+          )
+         (MenuItem
+            label: '-'
+          )
+         (MenuItem
+            label: 'Inspect change'
+            itemValue: changeMenuInspect:
+            translateLabel: true
+          )
+         (MenuItem
+            enabled: hasSingleChangeSelectedAndCanBrowse:
+            label: 'Browse Method(s)'
+            itemValue: changeMenuBrowse:
+            translateLabel: true
+          )
+         )
+        nil
+        nil
       )
 !
 
@@ -1543,10 +1572,12 @@
                   label: '-'
                 )
                (MenuItem
+                  enabled: notShowConflictsOnlyAspect
                   label: 'Show Deleted'
                   indication: showRemovedAspect
                 )
                (MenuItem
+                  enabled: notShowConflictsOnlyAspect
                   label: 'Show Same'
                   indication: showSameAspect
                 )
@@ -1568,6 +1599,10 @@
                   label: 'Show Timestamp'
                   indication: showTimestampHolder
                 )
+                 (MenuItem
+                  label: 'Update'
+                  itemValue: menuUpdate
+                )
                )
               nil
               nil
@@ -1598,6 +1633,29 @@
               nil
             )
           )
+         (MenuItem
+            label: 'MENU_Help'
+            startGroup: conditionalRight
+            submenu: 
+           (Menu
+              (
+               (MenuItem
+                  label: 'ChangesBrowser Documentation'
+                  itemValue: openHTMLDocument:
+                  argument: 'tools/cbrowser/TOP.html'
+                )
+               (MenuItem
+                  label: '-'
+                )
+               (MenuItem
+                  label: 'About ChangesBrowser...'
+                  itemValue: openAboutThisApplication
+                )
+               )
+              nil
+              nil
+            )
+          )
          )
         nil
         nil
@@ -1735,6 +1793,7 @@
       )
 ! !
 
+
 !ChangeSetBrowser2 class methodsFor:'plugIn spec'!
 
 aspectSelectors
@@ -1754,6 +1813,7 @@
 
 ! !
 
+
 !ChangeSetBrowser2 methodsFor:'accessing'!
 
 allowAccept: aBoolean
@@ -1821,6 +1881,16 @@
     "Modified: / 26-07-2012 / 14:31:50 / cg"
 !
 
+selectedChanges
+    | sel |
+
+    sel := selection2Holder value.
+    sel isEmptyOrNil ifTrue:[
+        sel := selection1Holder value.
+    ].
+    ^ sel select:[:each | each notNil].
+!
+
 showFilter: aBoolean
     self showFilterHolder value: aBoolean
 
@@ -1836,20 +1906,19 @@
 !
 
 theSingleSelectedChange
-
     | change sel |
     change := nil.
     sel := selection2Holder value.
     sel isNil ifTrue:[
-	sel := selection1Holder value.
+        sel := selection1Holder value.
     ].
     sel isNil ifTrue:[
-	^nil
+        ^nil
     ].
     sel do:
-	[:each|
-	change notNil ifTrue:[nil].
-	change isNil ifTrue:[change := each]].
+        [:each|
+        change notNil ifTrue:[nil].
+        change isNil ifTrue:[change := each]].
     ^change
 
     "Modified: / 26-07-2012 / 19:33:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -1862,6 +1931,7 @@
     "Created: / 26-10-2010 / 23:01:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !ChangeSetBrowser2 methodsFor:'accessing - defaults'!
 
 defaultTitle
@@ -1870,6 +1940,7 @@
     "Modified: / 08-04-2011 / 10:10:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !ChangeSetBrowser2 methodsFor:'accessing - menus'!
 
 list1MenuHolder
@@ -1898,6 +1969,7 @@
     "Modified (format): / 05-09-2011 / 16:07:34 / cg"
 ! !
 
+
 !ChangeSetBrowser2 methodsFor:'actions'!
 
 accept: source
@@ -1919,6 +1991,7 @@
     "Modified: / 19-07-2011 / 19:08:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !ChangeSetBrowser2 methodsFor:'aspects'!
 
 allowAcceptHolder
@@ -2177,6 +2250,10 @@
     "Modified: / 04-02-2012 / 21:25:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+notShowConflictsOnlyAspect
+    ^ BlockValue forLogicalNot:(self showConflictsOnlyAspect)
+!
+
 selection1Holder
     "return/create the 'selection1Holder' value holder (automatically generated)"
 
@@ -2235,6 +2312,19 @@
     ].
 !
 
+showConflictsOnlyAspect
+    "return/create the 'showConflictsOnlyAspect' value holder (automatically generated)"
+
+    showConflictsOnlyAspect isNil ifTrue:[
+        showConflictsOnlyAspect := ValueHolder with: false.
+    ].
+    ^ showConflictsOnlyAspect
+!
+
+showConflictsOnlyAspect:aValueHolder
+    showConflictsOnlyAspect := aValueHolder.
+!
+
 showFilterHolder
     "return/create the 'showFilterHolder' value holder (automatically generated)"
 
@@ -2349,7 +2439,10 @@
 
     "Created: / 07-09-2011 / 15:54:03 / cg"
     "Created: / 11-02-2012 / 22:40:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
+!
+
+ !
+
 
 !ChangeSetBrowser2 methodsFor:'aspects-queries'!
 
@@ -2389,6 +2482,7 @@
     "Created: / 17-05-2012 / 20:45:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !ChangeSetBrowser2 methodsFor:'change & update'!
 
 changesetChanged
@@ -2488,6 +2582,7 @@
     "Created: / 24-10-2009 / 19:29:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !ChangeSetBrowser2 methodsFor:'initialization'!
 
 list1View: aSubApplicationView
@@ -2506,6 +2601,7 @@
     "Modified: / 10-09-2012 / 14:22:50 / cg"
 ! !
 
+
 !ChangeSetBrowser2 methodsFor:'menu actions'!
 
 doApply
@@ -2524,6 +2620,11 @@
     "Modified: / 30-03-2012 / 12:19:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+doApplySelectedChanges
+    self selectedChanges.
+self halt.
+!
+
 doApplyToEnd
 
     self changeMenuApplyToEnd: self list.
@@ -2876,6 +2977,7 @@
     "Created: / 07-09-2011 / 12:47:15 / cg"
 ! !
 
+
 !ChangeSetBrowser2 methodsFor:'menu actions - changes'!
 
 changeMenuApply: changeList
@@ -3290,6 +3392,7 @@
     "Created: / 23-07-2012 / 13:13:11 / cg"
 ! !
 
+
 !ChangeSetBrowser2 methodsFor:'menu actions - changes - helpers'!
 
 changeMenuApplyChange: aChange
@@ -3377,6 +3480,7 @@
     "Modified: / 21-01-2013 / 17:12:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !ChangeSetBrowser2 methodsFor:'private'!
 
 changesDo:aBlock
@@ -3402,6 +3506,21 @@
     "Modified: / 27-07-2012 / 17:02:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+iconSelectorForChange:aChange
+    |currentMethod|
+
+    targetPackage notNil ifTrue:[
+        aChange isMethodChange ifTrue:[
+            (currentMethod := aChange changeMethod) notNil ifTrue:[
+                currentMethod package ~= targetPackage ifTrue:[
+                    ^ #iconExcla
+                ]
+            ]
+        ].
+    ].
+    ^ nil.
+!
+
 list
     "Returns list to operate on"
 
@@ -3485,6 +3604,7 @@
     "Created: / 07-09-2011 / 20:12:04 / cg"
 ! !
 
+
 !ChangeSetBrowser2 methodsFor:'queries'!
 
 canApplyChanges
@@ -3523,6 +3643,7 @@
     "Created: / 04-08-2011 / 18:25:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !ChangeSetBrowser2 methodsFor:'testing'!
 
 isHierarchical
@@ -3549,6 +3670,7 @@
     "Created: / 30-03-2012 / 11:59:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !ChangeSetBrowser2::ChangeEditor class methodsFor:'documentation'!
 
 documentation
@@ -3585,6 +3707,7 @@
 "
 ! !
 
+
 !ChangeSetBrowser2::ChangeEditor class methodsFor:'interface specs'!
 
 windowSpec
@@ -3668,6 +3791,7 @@
     "Modified: / 16-03-2012 / 13:08:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !ChangeSetBrowser2::ChangeEditor methodsFor:'accessing'!
 
 sourceChangeHolder
@@ -3686,6 +3810,7 @@
     sourceImageHolder := something.
 ! !
 
+
 !ChangeSetBrowser2::ChangeEditor methodsFor:'aspects'!
 
 changeHolder
@@ -3796,6 +3921,7 @@
     showdiffHolder := something.
 ! !
 
+
 !ChangeSetBrowser2::ChangeEditor methodsFor:'change & update'!
 
 changeChanged
@@ -3825,14 +3951,15 @@
     "Modified: / 29-11-2011 / 11:15:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !ChangeSetBrowser2 class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/Tools__ChangeSetBrowser2.st,v 1.46 2013-03-30 19:11:41 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/Tools__ChangeSetBrowser2.st,v 1.51 2013-04-15 06:54:37 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libtool/Tools__ChangeSetBrowser2.st,v 1.46 2013-03-30 19:11:41 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/Tools__ChangeSetBrowser2.st,v 1.51 2013-04-15 06:54:37 cg Exp $'
 !
 
 version_HG
--- a/Tools__NewSystemBrowser.st	Tue Apr 16 09:35:45 2013 +0200
+++ b/Tools__NewSystemBrowser.st	Tue Apr 16 10:22:43 2013 +0200
@@ -107,6 +107,7 @@
 "
 ! !
 
+
 !NewSystemBrowser class methodsFor:'initialization'!
 
 initialize
@@ -236,6 +237,7 @@
     ].
 ! !
 
+
 !NewSystemBrowser class methodsFor:'accessing-history'!
 
 addToBookMarks:aClass selector:aSelectorOrNil
@@ -317,6 +319,7 @@
     "Modified: / 13-09-2012 / 18:14:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !NewSystemBrowser class methodsFor:'defaults'!
 
 synchronousUpdate
@@ -330,6 +333,7 @@
     "Modified (comment): / 24-08-2011 / 15:33:27 / cg"
 ! !
 
+
 !NewSystemBrowser class methodsFor:'help specs'!
 
 flyByHelpSpec
@@ -498,6 +502,7 @@
 )
 ! !
 
+
 !NewSystemBrowser class methodsFor:'image specs'!
 
 defaultIcon
@@ -740,6 +745,7 @@
     ^ ToolbarIconLibrary startNewSystemBrowserIcon
 ! !
 
+
 !NewSystemBrowser class methodsFor:'interface specs'!
 
 browserPageSpec
@@ -5453,6 +5459,7 @@
     "Modified: / 07-06-2011 / 14:39:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !NewSystemBrowser class methodsFor:'interface specs-dialogs'!
 
 repositoryConsistencyDialogSpec
@@ -5710,6 +5717,7 @@
       )
 ! !
 
+
 !NewSystemBrowser class methodsFor:'interface specs-message pane'!
 
 messageInfoSpec
@@ -5822,6 +5830,7 @@
       )
 ! !
 
+
 !NewSystemBrowser class methodsFor:'menu specs'!
 
 browseMenu
@@ -5891,8 +5900,12 @@
                 )
                (MenuItem
                   label: 'With Extensions'
-                  itemValue: browseMenuClassesWithExtensions
-                  isVisible: false
+                  itemValue: browseMenuClassExtensionsBuffer
+                  showBusyCursorWhilePerforming: true
+                )
+               (MenuItem
+                  label: 'With Shadowed Methods (Package Conflicts)'
+                  itemValue: browseMenuClassesWithShadowedMethods
                   showBusyCursorWhilePerforming: true
                 )
                (MenuItem
@@ -6065,15 +6078,15 @@
                   showBusyCursorWhilePerforming: true
                 )
                (MenuItem
-                  label: 'Overwritten Methods'
-                  itemValue: browseMenuOverwrittenMethods:
-                  argument: newBrowser
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
                   label: 'Unassigned Extensions'
                   itemValue: browseMenuUnassignedMethods:
-                  argument: newBrowser
+                  argument: newBuffer
+                  showBusyCursorWhilePerforming: true
+                )
+               (MenuItem
+                  label: 'Overwritten Methods (Package Conflicts)'
+                  itemValue: browseMenuOverwrittenMethods:
+                  argument: newBuffer
                   showBusyCursorWhilePerforming: true
                 )
                (MenuItem
@@ -11012,216 +11025,221 @@
 
     ^
      #(Menu
-	(
-	 (MenuItem
-	    enabled: hasMethodSelectedHolder
-	    label: 'Compare'
-	    submenu:
-	   (Menu
-	      (
-	       (MenuItem
-		  enabled: methodRedefinesSuperclassVersionHolder
-		  label: 'With Inherited Method'
-		  itemValue: selectorMenuCompareWithInherited
-		)
-	       (MenuItem
-		  enabled: methodHasPreviousVersionHolder
-		  label: 'With Previous Version'
-		  itemValue: selectorMenuCompareWithPreviousVersion
-		)
-	       (MenuItem
-		  enabled: hasSingleMethodSelectedAndCodeModifiedHolder
-		  label: 'With Methods Actual Source'
-		  itemValue: selectorMenuCompareWithMethod
-		)
-	       (MenuItem
-		  enabled: hasExactlyTwoMethodsSelectedHolder
-		  label: 'With Each Other'
-		  itemValue: selectorMenuCompareTwoSelectedMethods
-		)
-	       (MenuItem
-		  label: '-'
-		)
-	       (MenuItem
-		  enabled: hasMethodSelectedAndSourceCodeManagerHolder
-		  label: 'With Newest in CVS Repository...'
-		  itemValue: selectorMenuCompareAgainstNewestInRepository
-		)
-	       (MenuItem
-		  enabled: smallTeamAvailable
-		  label: 'With SmallTeam Version on Host'
-		  submenuChannel: compareMethodWithSmallTeamVersionMenu
-		)
-	       )
-	      nil
-	      nil
-	    )
-	  )
-	 (MenuItem
-	    label: 'Refactor'
-	    submenuChannel: methodRefactorMenu
-	  )
-	 (MenuItem
-	    label: 'Generate'
-	    submenu:
-	   (Menu
-	      (
-	       (MenuItem
-		  enabled: methodNotImplementedInSuperclass
-		  label: 'SubclassResponsibility in SuperClass'
-		  itemValue: selectorMenuGenerateSubclassResponsibilityInSuperclass
-		)
-	       (MenuItem
-		  enabled: methodNotImplementedInClass
-		  label: 'SubclassResponsibility here'
-		  itemValue: selectorMenuGenerateSubclassResponsibilityHere
-		)
-	       (MenuItem
-		  enabled: methodIsTestAndNotImplementedInSuperclass
-		  label: 'False-returning isXXX-Test in SuperClass'
-		  itemValue: selectorMenuGenerateFalseReturnInSuperclass
-		)
-	       (MenuItem
-		  label: 'Templates in Subclasses'
-		  itemValue: selectorMenuGenerateTemplateInSubclasses
-		)
-	       (MenuItem
-		  label: 'Templates in all Subclasses'
-		  itemValue: selectorMenuGenerateTemplateInAllSubclasses
-		)
-	       (MenuItem
-		  label: '-'
-		)
-	       (MenuItem
-		  enabled: hasInstanceMethodsSelectedHolder
-		  label: 'Corresponding Instance Creation in Class'
-		  itemValue: selectorMenuGenerateCorrespondingInstanceCreationInClass
-		)
-	       (MenuItem
-		  enabled: hasClassMethodsSelectedHolder
-		  label: 'Forwarding Method in Instance Protocol'
-		  itemValue: selectorMenuGenerateForwardingMethodForInstances
-		)
-	       )
-	      nil
-	      nil
-	    )
-	  )
-	 (MenuItem
-	    label: 'Static Analysis (Lint)'
-	    submenuChannel: selectorCheckMenu
-	    labelImage: (ResourceRetriever ToolbarIconLibrary lint16x16Icon 'Static Analysis (Lint)')
-	  )
-	 (MenuItem
-	    label: 'Debug'
-	    submenuChannel: methodDebugMenu
-	    shortcutKey: Ctrl
-	  )
-	 (MenuItem
-	    label: 'Special'
-	    submenu:
-	   (Menu
-	      (
-	       (MenuItem
-		  enabled: hasMethodSelectedHolder
-		  label: 'Remove from ChangeSet'
-		  itemValue: selectorMenuCleanUpChangeSet
-		)
-	       (MenuItem
-		  label: '-'
-		)
-	       (MenuItem
-		  label: 'Select'
-		  isVisible: false
-		  submenu:
-		 (Menu
-		    (
-		     (MenuItem
-			label: 'Methods with String...'
-			itemValue: selectorMenuSelectMethodsWithString
-		      )
-		     (MenuItem
-			label: 'Methods Sending...'
-			itemValue: selectorMenuSelectMethodsSending
-		      )
-		     (MenuItem
-			label: 'Methods Refering to Global...'
-			itemValue: selectorMenuSelectMethodsReferingToGlobal
-		      )
-		     )
-		    nil
-		    nil
-		  )
-		)
-	       (MenuItem
-		  label: '-'
-		  isVisible: false
-		)
-	       (MenuItem
-		  enabled: methodHasPreviousVersionHolder
-		  label: 'Back to Previous Version'
-		  itemValue: selectorMenuBackToPrevious
-		)
-	       (MenuItem
-		  enabled: methodHasPreviousVersionHolder
-		  label: 'Previous Versions'
-		  itemValue: selectorMenuBrowsePreviousVersions
-		)
-	       (MenuItem
-		  label: '-'
-		)
-	       (MenuItem
-		  enabled: hasSingleMethodSelectedHolder
-		  label: 'Inspect Method'
-		  itemValue: selectorMenuInspect
-		)
-	       (MenuItem
-		  enabled: hasSingleResourceMethodSelectedHolder
-		  label: 'Edit Resource'
-		  itemValue: selectorMenuEdit
-		)
-	       (MenuItem
-		  label: '-'
-		)
-	       (MenuItem
-		  enabled: hasMethodSelectedHolder
-		  label: 'Compile with stc'
-		  itemValue: selectorMenuCompileWithSTC
-		)
-	       (MenuItem
-		  enabled: hasSingleMethodWithBytecodeSelectedHolder
-		  label: 'Decompile'
-		  itemValue: selectorMenuDecompile
-		)
-	       (MenuItem
-		  label: '-'
-		)
-	       (MenuItem
-		  enabled: hasMethodSelectedHolder
-		  label: 'Process...'
-		  itemValue: selectorMenuProcess
-		)
-	       (MenuItem
-		  label: '-'
-		)
-	       (MenuItem
-		  enabled: hasMethodsInList
-		  label: 'Copy List to Clipboard'
-		  itemValue: methodListMenuCopyList
-		)
-	       (MenuItem
-		  enabled: hasMethodsInList
-		  label: 'Copy List of Classes to Clipboard'
-		  itemValue: methodListMenuCopyListOfClasses
-		)
-	       )
-	      nil
-	      nil
-	    )
-	  )
-	 )
-	nil
-	nil
+        (
+         (MenuItem
+            enabled: hasMethodSelectedHolder
+            label: 'Compare'
+            submenu:
+           (Menu
+              (
+               (MenuItem
+                  enabled: methodRedefinesSuperclassVersionHolder
+                  label: 'With Inherited Method'
+                  itemValue: selectorMenuCompareWithInherited
+                )
+               (MenuItem
+                  enabled: methodHasPreviousVersionHolder
+                  label: 'With Previous Version'
+                  itemValue: selectorMenuCompareWithPreviousVersion
+                )
+               (MenuItem
+                  enabled: methodIsShadowedHolder
+                  label: 'With Shadowed Method'
+                  itemValue: selectorMenuCompareWithShadowedMethod
+                )
+               (MenuItem
+                  enabled: hasSingleMethodSelectedAndCodeModifiedHolder
+                  label: 'With Methods Actual Source'
+                  itemValue: selectorMenuCompareWithMethod
+                )
+               (MenuItem
+                  enabled: hasExactlyTwoMethodsSelectedHolder
+                  label: 'With Each Other'
+                  itemValue: selectorMenuCompareTwoSelectedMethods
+                )
+               (MenuItem
+                  label: '-'
+                )
+               (MenuItem
+                  enabled: hasMethodSelectedAndSourceCodeManagerHolder
+                  label: 'With Newest in CVS Repository...'
+                  itemValue: selectorMenuCompareAgainstNewestInRepository
+                )
+               (MenuItem
+                  enabled: smallTeamAvailable
+                  label: 'With SmallTeam Version on Host'
+                  submenuChannel: compareMethodWithSmallTeamVersionMenu
+                )
+               )
+              nil
+              nil
+            )
+          )
+         (MenuItem
+            label: 'Refactor'
+            submenuChannel: methodRefactorMenu
+          )
+         (MenuItem
+            label: 'Generate'
+            submenu:
+           (Menu
+              (
+               (MenuItem
+                  enabled: methodNotImplementedInSuperclass
+                  label: 'SubclassResponsibility in SuperClass'
+                  itemValue: selectorMenuGenerateSubclassResponsibilityInSuperclass
+                )
+               (MenuItem
+                  enabled: methodNotImplementedInClass
+                  label: 'SubclassResponsibility here'
+                  itemValue: selectorMenuGenerateSubclassResponsibilityHere
+                )
+               (MenuItem
+                  enabled: methodIsTestAndNotImplementedInSuperclass
+                  label: 'False-returning isXXX-Test in SuperClass'
+                  itemValue: selectorMenuGenerateFalseReturnInSuperclass
+                )
+               (MenuItem
+                  label: 'Templates in Subclasses'
+                  itemValue: selectorMenuGenerateTemplateInSubclasses
+                )
+               (MenuItem
+                  label: 'Templates in all Subclasses'
+                  itemValue: selectorMenuGenerateTemplateInAllSubclasses
+                )
+               (MenuItem
+                  label: '-'
+                )
+               (MenuItem
+                  enabled: hasInstanceMethodsSelectedHolder
+                  label: 'Corresponding Instance Creation in Class'
+                  itemValue: selectorMenuGenerateCorrespondingInstanceCreationInClass
+                )
+               (MenuItem
+                  enabled: hasClassMethodsSelectedHolder
+                  label: 'Forwarding Method in Instance Protocol'
+                  itemValue: selectorMenuGenerateForwardingMethodForInstances
+                )
+               )
+              nil
+              nil
+            )
+          )
+         (MenuItem
+            label: 'Static Analysis (Lint)'
+            submenuChannel: selectorCheckMenu
+            labelImage: (ResourceRetriever ToolbarIconLibrary lint16x16Icon 'Static Analysis (Lint)')
+          )
+         (MenuItem
+            label: 'Debug'
+            submenuChannel: methodDebugMenu
+            shortcutKey: Ctrl
+          )
+         (MenuItem
+            label: 'Special'
+            submenu:
+           (Menu
+              (
+               (MenuItem
+                  enabled: hasMethodSelectedHolder
+                  label: 'Remove from ChangeSet'
+                  itemValue: selectorMenuCleanUpChangeSet
+                )
+               (MenuItem
+                  label: '-'
+                )
+               (MenuItem
+                  label: 'Select'
+                  isVisible: false
+                  submenu:
+                 (Menu
+                    (
+                     (MenuItem
+                        label: 'Methods with String...'
+                        itemValue: selectorMenuSelectMethodsWithString
+                      )
+                     (MenuItem
+                        label: 'Methods Sending...'
+                        itemValue: selectorMenuSelectMethodsSending
+                      )
+                     (MenuItem
+                        label: 'Methods Refering to Global...'
+                        itemValue: selectorMenuSelectMethodsReferingToGlobal
+                      )
+                     )
+                    nil
+                    nil
+                  )
+                )
+               (MenuItem
+                  label: '-'
+                  isVisible: false
+                )
+               (MenuItem
+                  enabled: methodHasPreviousVersionHolder
+                  label: 'Back to Previous Version'
+                  itemValue: selectorMenuBackToPrevious
+                )
+               (MenuItem
+                  enabled: methodHasPreviousVersionHolder
+                  label: 'Previous Versions'
+                  itemValue: selectorMenuBrowsePreviousVersions
+                )
+               (MenuItem
+                  label: '-'
+                )
+               (MenuItem
+                  enabled: hasSingleMethodSelectedHolder
+                  label: 'Inspect Method'
+                  itemValue: selectorMenuInspect
+                )
+               (MenuItem
+                  enabled: hasSingleResourceMethodSelectedHolder
+                  label: 'Edit Resource'
+                  itemValue: selectorMenuEdit
+                )
+               (MenuItem
+                  label: '-'
+                )
+               (MenuItem
+                  enabled: hasMethodSelectedHolder
+                  label: 'Compile with stc'
+                  itemValue: selectorMenuCompileWithSTC
+                )
+               (MenuItem
+                  enabled: hasSingleMethodWithBytecodeSelectedHolder
+                  label: 'Decompile'
+                  itemValue: selectorMenuDecompile
+                )
+               (MenuItem
+                  label: '-'
+                )
+               (MenuItem
+                  enabled: hasMethodSelectedHolder
+                  label: 'Process...'
+                  itemValue: selectorMenuProcess
+                )
+               (MenuItem
+                  label: '-'
+                )
+               (MenuItem
+                  enabled: hasMethodsInList
+                  label: 'Copy List to Clipboard'
+                  itemValue: methodListMenuCopyList
+                )
+               (MenuItem
+                  enabled: hasMethodsInList
+                  label: 'Copy List of Classes to Clipboard'
+                  itemValue: methodListMenuCopyListOfClasses
+                )
+               )
+              nil
+              nil
+            )
+          )
+         )
+        nil
+        nil
       )
 !
 
@@ -12967,6 +12985,7 @@
       )
 ! !
 
+
 !NewSystemBrowser class methodsFor:'menu specs-SCM-category'!
 
 categoryMenuSCMCommon
@@ -13351,6 +13370,7 @@
       )
 ! !
 
+
 !NewSystemBrowser class methodsFor:'menu specs-SCM-class'!
 
 classCVSMenu
@@ -15272,6 +15292,7 @@
     "Modified: / 28-10-2012 / 11:54:14 / cg"
 ! !
 
+
 !NewSystemBrowser class methodsFor:'menu specs-SCM-project'!
 
 projectCVSMenu
@@ -16217,6 +16238,7 @@
     "Modified: / 24-07-2012 / 17:40:34 / cg"
 ! !
 
+
 !NewSystemBrowser class methodsFor:'menu specs-SCM-selector'!
 
 selectorMenuCVS
@@ -16428,22 +16450,22 @@
           )
          (MenuItem
             enabled: hasMethodSelectedAndSourceCodeManagerHolder
-	    label: 'Mercurial+'
-	    isVisible: hgRepositoryMenusAreShown
-	    submenuChannel: selectorMenuSCMFor:
-	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryP4Icon 'Mercurial+')
-	    argument: HGSourceCodeManager
-	  )
-	 (MenuItem
-	    enabled: hasMethodSelectedAndSourceCodeManagerHolder
-	    label: 'Git+'
-	    isVisible: perforceRepositoryMenusAreShown
-	    submenuChannel: selectorMenuSCMFor:
-	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryP4Icon 'Git+')
-	    argument: HGSourceCodeManager2
-	  )
-	 (MenuItem
-	    enabled: hasMethodSelectedAndSourceCodeManagerHolder
+            label: 'Mercurial+'
+            isVisible: hgRepositoryMenusAreShown
+            submenuChannel: selectorMenuSCMFor:
+            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryP4Icon 'Mercurial+')
+            argument: HGSourceCodeManager
+          )
+         (MenuItem
+            enabled: hasMethodSelectedAndSourceCodeManagerHolder
+            label: 'Git+'
+            isVisible: perforceRepositoryMenusAreShown
+            submenuChannel: selectorMenuSCMFor:
+            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryP4Icon 'Git+')
+            argument: HGSourceCodeManager2
+          )
+         (MenuItem
+            enabled: hasMethodSelectedAndSourceCodeManagerHolder
             label: 'Perforce'
             translateLabel: true
             isVisible: hasPerforceSupport
@@ -16585,6 +16607,7 @@
       )
 ! !
 
+
 !NewSystemBrowser class methodsFor:'menu specs-dialogs'!
 
 classesWhichHaveBeenModifiedPopupMenu
@@ -16777,6 +16800,7 @@
     "Modified: / 29-09-2006 / 16:11:08 / cg"
 ! !
 
+
 !NewSystemBrowser class methodsFor:'menu specs-monticello'!
 
 projectMonticelloMenu
@@ -16814,6 +16838,7 @@
       )
 ! !
 
+
 !NewSystemBrowser class methodsFor:'menu specs-popup'!
 
 categoryPopUpMenu
@@ -16959,6 +16984,7 @@
     "Created: / 18.2.2000 / 11:58:25 / cg"
 ! !
 
+
 !NewSystemBrowser class methodsFor:'menu specs-subversion'!
 
 classSubversionMenu
@@ -17222,6 +17248,7 @@
       )
 ! !
 
+
 !NewSystemBrowser class methodsFor:'menu specs-toolbar'!
 
 toolBarMenu
@@ -17540,6 +17567,7 @@
       )
 ! !
 
+
 !NewSystemBrowser class methodsFor:'queries'!
 
 hasSubversionSupport
@@ -17549,6 +17577,7 @@
     "Modified: / 19-01-2012 / 10:46:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !NewSystemBrowser class methodsFor:'startup'!
 
 browseClass:aClass
@@ -17768,6 +17797,7 @@
     "Created: / 06-07-2011 / 18:27:53 / cg"
 ! !
 
+
 !NewSystemBrowser class methodsFor:'utilities'!
 
 enterBoxTitle:title okText:okText label:label
@@ -17786,6 +17816,7 @@
     "Created: / 6.2.2000 / 01:07:11 / cg"
 ! !
 
+
 !NewSystemBrowser methodsFor:'accessing'!
 
 isEmbeddedBrowser
@@ -17800,6 +17831,7 @@
     isEmbedded := aBoolean.
 ! !
 
+
 !NewSystemBrowser methodsFor:'aspects'!
 
 bookmarkHolder
@@ -18105,6 +18137,7 @@
     builder aspectAt:#suppressChangeSetUpdate put:aBoolean
 ! !
 
+
 !NewSystemBrowser methodsFor:'aspects-environment'!
 
 selectedCategoriesAsEnvironment
@@ -18232,6 +18265,7 @@
     "Modified: / 28-02-2012 / 16:28:38 / cg"
 ! !
 
+
 !NewSystemBrowser methodsFor:'aspects-kludges'!
 
 metaToggle
@@ -18245,6 +18279,7 @@
 
 ! !
 
+
 !NewSystemBrowser methodsFor:'aspects-menus'!
 
 categoryMenu
@@ -18442,6 +18477,7 @@
     ^ self class visitedClassNamesHistory
 ! !
 
+
 !NewSystemBrowser methodsFor:'aspects-navigation'!
 
 categoryList
@@ -18663,7 +18699,6 @@
 ! !
 
 
-
 !NewSystemBrowser methodsFor:'aspects-organization'!
 
 categoryMenuVisible
@@ -19137,6 +19172,7 @@
     "Modified: / 18.8.2000 / 19:03:48 / cg"
 ! !
 
+
 !NewSystemBrowser methodsFor:'aspects-presentation'!
 
 bookmarkBarVisibleHolder
@@ -19594,6 +19630,7 @@
     "Created: / 02-07-2011 / 18:27:29 / cg"
 ! !
 
+
 !NewSystemBrowser methodsFor:'aspects-queries'!
 
 anyBreakOrTracePointsAreSet
@@ -22211,6 +22248,14 @@
     ^ [ self methodHasPreviousVersion ]
 !
 
+methodIsShadowed
+    ^ self methodsShadowedMethod notNil
+!
+
+methodIsShadowedHolder
+    ^ [ self methodIsShadowed ]
+!
+
 methodIsSubclassResponsibility
     self selectedMethodsDo:[:eachMethod |
 	(eachMethod sends:#subclassResponsibility) ifTrue:[^ true].
@@ -23455,6 +23500,7 @@
     self navigationState versionDiffApplication:diffApp.
 ! !
 
+
 !NewSystemBrowser methodsFor:'help specs'!
 
 flyByHelpSpec
@@ -23482,6 +23528,7 @@
     ^ super flyByHelpTextFor:aComponent
 ! !
 
+
 !NewSystemBrowser methodsFor:'history'!
 
 addToHistory: class
@@ -23500,8 +23547,11 @@
     "Modified: / 02-07-2011 / 18:33:22 / cg"
 ! !
 
+
 !NewSystemBrowser methodsFor:'menu actions-browse'!
 
+
+
 browseImplementorsOf
     "launch an enterBox for selector to search for"
 
@@ -23659,25 +23709,15 @@
     |searchBlock|
 
     searchBlock := [
-			|classes|
-
-			classes := IdentitySet new.
-
-			Smalltalk allClassesDo:[:eachClass |
-			    |cls|
-
-			    eachClass wasAutoloaded ifTrue:[
-				classes add:eachClass.
-			    ].
-			].
-			classes asOrderedCollection
-		  ].
-
-    self
-	spawnClassBrowserForSearch:searchBlock
-	sortBy:nil
-	in:#newBuffer
-	label:'Classes which were autoloaded'
+                        (Smalltalk allClassesForWhich:[:someClass | someClass wasAutoloaded])
+                            asOrderedCollection
+                   ].
+
+    self
+        spawnClassBrowserForSearch:searchBlock
+        sortBy:nil
+        in:#newBuffer
+        label:'Classes which were autoloaded'
 !
 
 browseMenuClassExtensions
@@ -23699,30 +23739,30 @@
      (i.e. methods where the packageID is different from their classes packageID)"
 
     self withSearchCursorDo:[
-	    |newBrowser|
-
-	    newBrowser := self
-			spawnClassExtensionBrowserForSearch:[
-			    |classes include|
-
-			    classes := IdentitySet new.
-			    aCollectionOfClasses do:[:aClass |
-				aCollectionOfPackagesOrNil isNil ifTrue:[
-				    include := aClass hasExtensions.
-				] ifFalse:[
-				    include := aCollectionOfPackagesOrNil contains:[:eachPackage | aClass hasExtensionsFrom:eachPackage]
-				].
-				include ifTrue:[
-				    classes add:aClass
-				]
-			    ].
-			    classes asOrderedCollection sort:[:a :b | a name < b name]
-			]
-			label:labelOrNil
-			in:openHow.
-
-	    newBrowser navigationState selectedProjects value:aCollectionOfPackagesOrNil.
-	]
+            |newBrowser|
+
+            newBrowser := self
+                        spawnClassExtensionBrowserForSearch:[
+                            |classes|
+
+                            classes := (aCollectionOfClasses 
+                                        select:[:aClass |
+                                            |include|
+
+                                            aCollectionOfPackagesOrNil isNil ifTrue:[
+                                                include := aClass hasExtensions.
+                                            ] ifFalse:[
+                                                include := aCollectionOfPackagesOrNil contains:[:eachPackage | aClass hasExtensionsFrom:eachPackage]
+                                            ].
+                                            include
+                                        ]) asOrderedCollection.
+                            classes sort:[:a :b | a name < b name]
+                        ]
+                        label:labelOrNil
+                        in:openHow.
+
+            newBrowser navigationState selectedProjects value:aCollectionOfPackagesOrNil.
+        ]
 !
 
 browseMenuClassExtensionsOpenAs:openHow
@@ -24104,6 +24144,42 @@
     self searchMenuFindClass:#newBuffer single:false.
 !
 
+browseMenuClassesWithShadowedMethods
+    "open a new browser on all package conflicts (methods shadowing existing one's from
+     another package)"
+
+    self browseMenuClassesWithShadowedMethodsOpenAs:#newBuffer
+!
+
+browseMenuClassesWithShadowedMethodsOpenAs:openHow
+    "open a browser / add a new buffer on all methods which shadow an
+     existing method from another package"
+
+    self withSearchCursorDo:[
+        |newBrowser|
+
+        newBrowser := self
+                    spawnClassExtensionBrowserForSearch:[
+                        |classes|
+
+                        classes := Smalltalk allClassesForWhich:[:someClass |
+                            |include|
+
+                            include := false.
+                            someClass hasExtensions ifTrue:[
+                                someClass instAndClassMethodsDo:[:m | m isShadowingExtension ifTrue:[include := true]].
+                            ].
+                            include 
+                        ].
+                        classes asOrderedCollection sort:[:a :b | a name < b name]
+                    ]
+                    label:'Classes with Overwritten Methods (Package Conflicts)'
+                    in:openHow.
+
+        "/ newBrowser navigationState selectedProjects value:nil.
+    ]
+!
+
 browseMenuClassesWithStringInCommentOrDocumentation
     "open a dialog asking for a string; search for classes having
      such a string fragment in their comment/documentation."
@@ -25052,7 +25128,7 @@
             and:[ (def savedOverwrittenMethodForClass:cls selector:mthd selector) notNil ]]]
         ]
         in:openHow
-        label:'Overwritten Methods'
+        label:'Overwritten Methods (Package Conflicts)'
 !
 
 browseMenuRecentChanges
@@ -25587,6 +25663,10 @@
     "Modified: / 28-02-2012 / 16:15:36 / cg"
 !
 
+
+
+
+
 defaultSearchArea
     "return a useful default seach area"
 
@@ -25774,6 +25854,7 @@
 viewMenuSelectAllClasses
 ! !
 
+
 !NewSystemBrowser methodsFor:'menu actions-buffers'!
 
 bufferMenuCreateBuffer
@@ -25938,6 +26019,7 @@
     "Modified: / 28-02-2012 / 10:22:24 / cg"
 ! !
 
+
 !NewSystemBrowser methodsFor:'menu actions-category'!
 
 categoryMenuCheckInEach
@@ -26749,6 +26831,7 @@
     self spawnCategoryBrowserFor:(self selectedCategoriesValue) in:where
 ! !
 
+
 !NewSystemBrowser methodsFor:'menu actions-checks-lint'!
 
 foo
@@ -27155,6 +27238,7 @@
     "Modified: / 01-03-2012 / 19:52:57 / cg"
 ! !
 
+
 !NewSystemBrowser methodsFor:'menu actions-checks-old'!
 
 classMenuCheck
@@ -27316,6 +27400,7 @@
     "Modified (comment): / 01-03-2012 / 14:10:43 / cg"
 ! !
 
+
 !NewSystemBrowser methodsFor:'menu actions-class'!
 
 addClassesToRemoveForClass:aClass to:classesToRemove removingSubclasses:removingSubclasses withCancel:withCancel
@@ -32017,6 +32102,7 @@
     self classMenuGenerateMultiSetterMethod
 ! !
 
+
 !NewSystemBrowser methodsFor:'menu actions-class hierarchy'!
 
 classHierarchyMenuSelectWithAllSubclasses
@@ -32069,6 +32155,7 @@
     ^ self selectedClasses
 ! !
 
+
 !NewSystemBrowser methodsFor:'menu actions-class packaging'!
 
 excludeClasses: toExclude fromProject:aDefinitionClass using:generator
@@ -32100,6 +32187,7 @@
     aDefinitionClass makeClassesAutoloaded:toMakeAutoloaded usingCompiler:generator
 ! !
 
+
 !NewSystemBrowser methodsFor:'menu actions-class repository'!
 
 allKnownTagsInClasses:aCollectionOfClasses
@@ -34730,6 +34818,7 @@
     "Created: / 21-12-2011 / 20:11:25 / cg"
 ! !
 
+
 !NewSystemBrowser methodsFor:'menu actions-code'!
 
 codeMenuAddClassVariable:newName inClass:aClass asValueHolder:asValueHolder
@@ -36613,6 +36702,7 @@
     aTwoArgBlock value:cls value:selector.
 ! !
 
+
 !NewSystemBrowser methodsFor:'menu actions-debug'!
 
 classMenuClearCoverageInfo
@@ -37246,6 +37336,7 @@
     "Modified: / 28-02-2012 / 16:52:45 / cg"
 ! !
 
+
 !NewSystemBrowser methodsFor:'menu actions-help'!
 
 openClassDocumentation
@@ -37279,6 +37370,7 @@
     self updateSpecialCodeEditorVisibility
 ! !
 
+
 !NewSystemBrowser methodsFor:'menu actions-methodList'!
 
 methodListMenuCheckInClass
@@ -37507,6 +37599,7 @@
     "Modified: / 28-02-2012 / 16:27:44 / cg"
 ! !
 
+
 !NewSystemBrowser methodsFor:'menu actions-namespace'!
 
 nameSpaceMenuCheckOut
@@ -37632,6 +37725,7 @@
     "Modified: / 28-02-2012 / 16:53:04 / cg"
 ! !
 
+
 !NewSystemBrowser methodsFor:'menu actions-other'!
 
 editModeInsert
@@ -37697,6 +37791,7 @@
     "Created: / 15-10-2011 / 12:02:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !NewSystemBrowser methodsFor:'menu actions-project'!
 
 classMenuCheckInBuildSupportFiles
@@ -41139,6 +41234,7 @@
     SourceCodeManagerUtilities basicNew validateConsistencyOfPackage:defClass package
 ! !
 
+
 !NewSystemBrowser methodsFor:'menu actions-project-monticello'!
 
 projectMenuMonticelloBrowseRepositories
@@ -41147,6 +41243,7 @@
     "Created: / 01-12-2011 / 21:47:24 / cg"
 ! !
 
+
 !NewSystemBrowser methodsFor:'menu actions-protocol'!
 
 doMoveSelectedProtocolsToProject:newProject
@@ -41881,6 +41978,7 @@
     "Modified: / 28-02-2012 / 16:34:54 / cg"
 ! !
 
+
 !NewSystemBrowser methodsFor:'menu actions-searching'!
 
 askForClassToSearch:doWhatByDefault single:singleClass msgTail:msgTail resources:resourcesOrNil thenDo:aBlock
@@ -42537,6 +42635,7 @@
     self findResponseTo:selector in:nil
 ! !
 
+
 !NewSystemBrowser methodsFor:'menu actions-selector'!
 
 askForClassToMoveOrCopy:doWhat
@@ -43050,7 +43149,7 @@
 !
 
 methodsPreviousVersionCode
-    "return the methods previous versions code"
+    "return the method's previous version's code"
 
     |m|
 
@@ -43071,6 +43170,25 @@
     ^ m previousVersions.
 !
 
+methodsShadowedMethod
+    "return the method's shadowed method, or nil.
+     The shadowed method is the original method from its original package,
+     which was overloaded by another package"
+
+    |m mClass mProjectDefinition|
+
+    m := self theSingleSelectedMethod.
+    m isNil ifTrue:[^ nil].
+
+    mClass := m mclass theNonMetaclass.
+    (mClass notNil
+      and:[ m package ~= mClass package
+      and:[ (mProjectDefinition := mClass projectDefinitionClass) notNil]]) ifTrue:[
+        ^ mProjectDefinition savedOverwrittenMethodForClass:m mclass selector:m selector
+    ].
+    ^ nil
+!
+
 moveMethods:methods toClass:newClass
     "move some methods to some other class - typically a sister class"
 
@@ -44100,17 +44218,42 @@
     m := self theSingleSelectedMethod.
     previousCode := self methodsPreviousVersionCode.
     previousCode isNil ifTrue:[
-	self information:'Oops - no previous code found'.
-	^ self
+        self information:'Oops - no previous code found'.
+        ^ self
     ].
     self withWaitCursorDo:[
-	v := DiffCodeView
-		openOn:previousCode
-		label:'previous version'
-		and:m source
-		label:'current version'.
-	v label:(resources string:'comparing method').
-	v waitUntilVisible.
+        v := DiffCodeView
+                openOn:previousCode
+                label:'previous version'
+                and:m source
+                label:'current version'.
+        v topView label:(resources string:'comparing method').
+        v waitUntilVisible.
+    ].
+    ^ self
+!
+
+selectorMenuCompareWithShadowedMethod
+    "compare the codeView's contents against the method's shadowed version
+     (that is the original, overloaded method from the method's original package)"
+
+    |m originalMethod v|
+
+    m := self theSingleSelectedMethod.
+    originalMethod := self methodsShadowedMethod.
+    originalMethod isNil ifTrue:[
+        self information:'Oops - no shadowed (original method) found'.
+        ^ self
+    ].
+    self withWaitCursorDo:[
+        v := DiffCodeView
+                openOn:originalMethod source
+                label:(resources string:'shadowed (original) in %1' with:originalMethod package allBold)
+                and:m source
+                label:(resources string:'current in %1' with:m package allBold).
+        v topView label:(resources string:'shadowed method %1' with:m whoString).
+        v leftAcceptAction:[:text | m mclass addSelector:m selector withMethod:originalMethod ].
+        v waitUntilVisible.      
     ].
     ^ self
 !
@@ -44119,22 +44262,22 @@
     "compare the codeViews contents against a SmallTeam version"
 
     self selectedMethodsValue do:[:eachMethod |
-	|v changeList change|
-
-	changeList := SmallTeam changesOnHost:hostName.
-	change := changeList
-		    detectLast:[:change |
-			change changeClass == eachMethod mclass
-			and:[ change selector == eachMethod selector ] ]
-		    ifNone:nil.
-	change notNil ifTrue:[
-	    v := DiffCodeView
-		    openOn:(change source)
-		    label:'Version on ',hostName
-		    and:eachMethod source
-		    label:'Your Version'.
-	    v label:(resources string:'Comparing method').
-	].
+        |v changeList change|
+
+        changeList := SmallTeam changesOnHost:hostName.
+        change := changeList
+                    detectLast:[:change |
+                        change changeClass == eachMethod mclass
+                        and:[ change selector == eachMethod selector ] ]
+                    ifNone:nil.
+        change notNil ifTrue:[
+            v := DiffCodeView
+                    openOn:(change source)
+                    label:'Version on ',hostName
+                    and:eachMethod source
+                    label:'Your Version'.
+            v topView label:(resources string:'Comparing method').
+        ].
     ].
 
     "Created: / 11-11-2006 / 15:15:26 / cg"
@@ -46479,6 +46622,7 @@
     "Modified: / 28-02-2012 / 16:36:22 / cg"
 ! !
 
+
 !NewSystemBrowser methodsFor:'menu actions-subversion'!
 
 commonMenuSubversionOpenSettings
@@ -46488,6 +46632,7 @@
     "Modified: / 26-03-2010 / 20:01:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !NewSystemBrowser methodsFor:'menu actions-subversion-class'!
 
 classMenuSubversionShowRevisionLog
@@ -47879,6 +48024,7 @@
     aBlock value:selectedVariable value:isClassVar
 ! !
 
+
 !NewSystemBrowser methodsFor:'menu-actions-other'!
 
 goBack
@@ -47905,6 +48051,7 @@
     "Modified: / 22-02-2008 / 17:18:56 / janfrog"
 ! !
 
+
 !NewSystemBrowser methodsFor:'menus-dynamic'!
 
 boockmarksMenu
@@ -49172,6 +49319,7 @@
     "Modified: / 09-09-2012 / 13:24:04 / cg"
 ! !
 
+
 !NewSystemBrowser methodsFor:'menus-dynamic-SCM'!
 
 categoryMenuSCMFor: sourceCodeManagerClassName
@@ -49653,6 +49801,7 @@
     "Created: / 12-10-2011 / 20:28:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !NewSystemBrowser methodsFor:'menus-dynamic-subversion'!
 
 commonSubversionBranchMenu
@@ -49685,6 +49834,7 @@
     "Modified (format): / 01-12-2011 / 21:06:52 / cg"
 ! !
 
+
 !NewSystemBrowser methodsFor:'navigation'!
 
 askForClassNameMatching:matchStringArg
@@ -50504,6 +50654,7 @@
     "Modified: / 5.2.2000 / 23:07:10 / cg"
 ! !
 
+
 !NewSystemBrowser methodsFor:'private-buffers'!
 
 removeBuffer:nr
@@ -50555,6 +50706,7 @@
     self removeBuffer:(selectedBuffer value)
 ! !
 
+
 !NewSystemBrowser methodsFor:'private-checks'!
 
 anySpecialEditorModified
@@ -50692,6 +50844,7 @@
     ^ true
 ! !
 
+
 !NewSystemBrowser methodsFor:'private-code update'!
 
 autoSearch:aString
@@ -51740,6 +51893,7 @@
     "Modified: / 01-12-2011 / 14:26:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !NewSystemBrowser methodsFor:'private-dialogs'!
 
 askForDirectoryToFileOut:title default:defaultDirOrNil
@@ -52822,6 +52976,7 @@
 	    cancel: [nil]
 ! !
 
+
 !NewSystemBrowser methodsFor:'private-helpers'!
 
 anySelectedClass
@@ -53949,6 +54104,7 @@
       and:[ (view isSameOrComponentOf:appView) ]
 ! !
 
+
 !NewSystemBrowser methodsFor:'private-helpers-subApps'!
 
 categoryListApp
@@ -54030,6 +54186,7 @@
     "Modified: / 14-02-2012 / 14:00:36 / cg"
 ! !
 
+
 !NewSystemBrowser methodsFor:'private-presentation'!
 
 asyncShowMethodInfo
@@ -54673,6 +54830,7 @@
     ]
 ! !
 
+
 !NewSystemBrowser methodsFor:'private-searching'!
 
 searchCompletionBlock
@@ -54805,6 +54963,7 @@
     "Created: / 06-04-2012 / 12:56:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !NewSystemBrowser methodsFor:'private-semantic checks'!
 
 checkAcceptedMethod:aMethod inClass:aClass
@@ -55135,6 +55294,7 @@
     ^ nil.
 ! !
 
+
 !NewSystemBrowser methodsFor:'private-smalllint'!
 
 smalllintRulesAll
@@ -55169,6 +55329,7 @@
     "Created: / 06-09-2012 / 14:49:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !NewSystemBrowser methodsFor:'private-syntax coloring'!
 
 startSyntaxHighlightProcess
@@ -55461,6 +55622,7 @@
     "Modified: / 08-08-2011 / 15:09:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !NewSystemBrowser methodsFor:'setup'!
 
 browserCanvas
@@ -55768,6 +55930,7 @@
     self normalLabel.
 ! !
 
+
 !NewSystemBrowser methodsFor:'special editors'!
 
 specialEditorCanvasForMethod:aMethod
@@ -56014,6 +56177,7 @@
     "Modified: / 28-02-2012 / 17:02:07 / cg"
 ! !
 
+
 !NewSystemBrowser methodsFor:'startup & release'!
 
 closeRequest
@@ -56077,6 +56241,7 @@
     "Modified: / 20-11-2006 / 12:16:37 / cg"
 ! !
 
+
 !NewSystemBrowser methodsFor:'string search tool'!
 
 hideSearchBar
@@ -56155,6 +56320,7 @@
     ].
 ! !
 
+
 !NewSystemBrowser methodsFor:'user actions'!
 
 backToLastClass
@@ -56953,6 +57119,7 @@
     "Modified: / 28-02-2012 / 16:51:54 / cg"
 ! !
 
+
 !NewSystemBrowser methodsFor:'user actions-accepting'!
 
 acceptMethod:codeArg inClass:cls language: languageOrNil check:doCheck
@@ -58065,6 +58232,7 @@
     self setAcceptAction:[:code | self codeView flash].
 ! !
 
+
 !NewSystemBrowser methodsFor:'user actions-class'!
 
 classLoad
@@ -58212,6 +58380,7 @@
     "Modified: / 12-09-2006 / 13:48:12 / cg"
 ! !
 
+
 !NewSystemBrowser methodsFor:'user actions-comparing'!
 
 doCompareIn:aNavigationState
@@ -58282,6 +58451,7 @@
     "Modified: / 27-07-2012 / 22:25:17 / cg"
 ! !
 
+
 !NewSystemBrowser methodsFor:'user actions-events'!
 
 keyInCategoryListView:key rawKey:rawKey
@@ -58659,6 +58829,7 @@
     "Modified: / 17-08-2011 / 13:29:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !NewSystemBrowser methodsFor:'user actions-helpers'!
 
 hideMessagePane
@@ -58825,6 +58996,7 @@
     "Modified: / 15-05-2012 / 10:46:06 / cg"
 ! !
 
+
 !NewSystemBrowser methodsFor:'user actions-profiler'!
 
 spawnProfilerStatistics:statistics in: where
@@ -58841,6 +59013,7 @@
     "Modified (format): / 29-11-2011 / 14:49:08 / cg"
 ! !
 
+
 !NewSystemBrowser::ClassCompletionEntry methodsFor:'accessing'!
 
 klass
@@ -58859,6 +59032,7 @@
     showPrefix := something.
 ! !
 
+
 !NewSystemBrowser::ClassCompletionEntry methodsFor:'converting'!
 
 asString
@@ -58871,6 +59045,7 @@
     "Created: / 04-04-2012 / 13:00:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !NewSystemBrowser::ClassCompletionEntry methodsFor:'displaying'!
 
 displayOn:aGC x:x y:y opaque:opaque
@@ -58921,6 +59096,7 @@
     "Created: / 20-04-2012 / 18:19:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !NewSystemBrowser::ClassCompletionEntry methodsFor:'printing & storing'!
 
 printOn:aStream
@@ -58934,14 +59110,15 @@
     "Modified: / 06-04-2012 / 13:30:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !NewSystemBrowser class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/Tools__NewSystemBrowser.st,v 1.1863 2013-04-04 06:30:54 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/Tools__NewSystemBrowser.st,v 1.1866 2013-04-14 18:13:55 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libtool/Tools__NewSystemBrowser.st,v 1.1863 2013-04-04 06:30:54 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/Tools__NewSystemBrowser.st,v 1.1866 2013-04-14 18:13:55 cg Exp $'
 !
 
 version_HG
--- a/extensions.st	Tue Apr 16 09:35:45 2013 +0200
+++ b/extensions.st	Tue Apr 16 10:22:43 2013 +0200
@@ -9,7 +9,6 @@
     "Created: / 25-07-2010 / 08:57:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified (format): / 04-10-2011 / 19:47:20 / cg"
 ! !
-
 !AbstractSyntaxHighlighter class methodsFor:'api highlighting'!
 
 formatMethod:aString in:aClass using:preferencesOrNil elementsInto: elements
@@ -18,7 +17,6 @@
 
     "Created: / 25-07-2010 / 08:58:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !ArrayedCollection methodsFor:'inspecting'!
 
 inspector2TabForHexDump
@@ -86,7 +84,6 @@
 
     "Created: / 13-02-2012 / 15:08:42 / cg"
 ! !
-
 !Behavior methodsFor:'inspecting'!
 
 inspectorExtraAttributes
@@ -99,7 +96,6 @@
                 ifTrue:[ '-nonMeta' -> [ self theNonMetaclass ] ]);
         yourself
 ! !
-
 !Behavior methodsFor:'inspecting'!
 
 inspectorValueStringInListFor:anInspector
@@ -112,7 +108,6 @@
     ].
     ^ super inspectorValueStringInListFor:anInspector
 ! !
-
 !Block methodsFor:'inspecting'!
 
 inspectorExtraAttributes
@@ -134,7 +129,6 @@
 
     "Created: / 15-11-2011 / 14:24:10 / cg"
 ! !
-
 !Breakpoint methodsFor:'accessing'!
 
 icon
@@ -143,7 +137,6 @@
 
     "Created: / 11-07-2011 / 18:21:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !BreakpointDescription methodsFor:'accessing'!
 
 icon
@@ -167,7 +160,6 @@
     "Created: / 28-06-2011 / 08:29:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 27-01-2012 / 13:46:23 / cg"
 ! !
-
 !ByteArray methodsFor:'inspecting'!
 
 inspectorExtraAttributes
@@ -196,13 +188,11 @@
     "Created: / 18-09-2006 / 21:29:59 / cg"
     "Modified: / 06-10-2006 / 13:57:20 / cg"
 ! !
-
 !Change methodsFor:'private'!
 
 flattenOnto: aCollection 
 	aCollection add: self
 ! !
-
 !Change methodsFor:'private'!
 
 flattenedChanges
@@ -211,7 +201,6 @@
 	self flattenOnto: changes.
 	^changes
 ! !
-
 !Change methodsFor:'accessing'!
 
 removed
@@ -220,7 +209,6 @@
 
     "Created: / 24-10-2009 / 21:10:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !Change methodsFor:'accessing'!
 
 removed: aBoolean
@@ -229,7 +217,6 @@
 
     "Created: / 24-10-2009 / 21:11:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !ChangeSet methodsFor:'utilities'!
 
 condenseChangesForRemoved
@@ -251,14 +238,12 @@
     "Created: / 05-11-2001 / 14:21:17 / cg"
     "Modified: / 12-10-2006 / 16:51:27 / cg"
 ! !
-
 !ChangeSet methodsFor:'private'!
 
 flattenOnto: aCollection 
 
     self do:[:change|change flattenOnto: aCollection]
 ! !
-
 !ChangeSet methodsFor:'private'!
 
 flattenedChanges
@@ -267,7 +252,6 @@
 	self flattenOnto: changes.
 	^changes
 ! !
-
 !ChangeSet methodsFor:'inspecting'!
 
 inspector2TabBrowser
@@ -284,7 +268,6 @@
     "Modified: / 06-08-2011 / 21:22:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 13-09-2011 / 11:55:53 / cg"
 ! !
-
 !ChangeSet methodsFor:'inspecting'!
 
 inspector2Tabs
@@ -292,7 +275,6 @@
 
     "Created: / 05-07-2011 / 13:40:19 / cg"
 ! !
-
 !Character methodsFor:'inspecting'!
 
 inspectorExtraAttributes
@@ -312,7 +294,6 @@
 
     "Created: / 22-10-2006 / 03:52:20 / cg"
 ! !
-
 !Character methodsFor:'inspecting'!
 
 inspectorValueStringInListFor:anInspector
@@ -323,7 +304,6 @@
     ].
     ^ self storeString,(' "%1"' bindWith:asciivalue)
 ! !
-
 !CharacterArray methodsFor:'inspecting'!
 
 inspector2TabBytes
@@ -338,7 +318,6 @@
     "Created: / 20-07-2011 / 16:36:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 21-08-2011 / 07:32:57 / cg"
 ! !
-
 !CharacterArray methodsFor:'inspecting'!
 
 inspector2TabHTML
@@ -351,7 +330,6 @@
     "Created: / 17-02-2008 / 10:10:50 / janfrog"
     "Created: / 07-11-2011 / 12:35:15 / cg"
 ! !
-
 !CharacterArray methodsFor:'inspecting'!
 
 inspector2TabText
@@ -364,7 +342,6 @@
     "Created: / 17-02-2008 / 10:10:50 / janfrog"
     "Modified: / 21-08-2011 / 08:02:57 / cg"
 ! !
-
 !CharacterArray methodsFor:'inspecting'!
 
 inspector2Tabs
@@ -377,7 +354,6 @@
 
     "Created: / 05-07-2011 / 13:40:27 / cg"
 ! !
-
 !CharacterArray methodsFor:'inspecting'!
 
 inspectorExtraAttributes
@@ -402,7 +378,6 @@
 
     "Created: / 22-10-2006 / 03:52:20 / cg"
 ! !
-
 !CharacterArray methodsFor:'inspecting'!
 
 inspectorValueStringInListFor:anInspector
@@ -410,7 +385,6 @@
 
     ^ self basicStoreString contractTo:30.
 ! !
-
 !Class methodsFor:'misc'!
 
 inspectorClass
@@ -422,7 +396,6 @@
     ].
     ^ super inspectorClass
 ! !
-
 !Collection methodsFor:'inspecting'!
 
 inspectorValueStringInListFor:anInspector
@@ -435,7 +408,6 @@
     ].
     ^ (super inspectorValueStringInListFor:anInspector),' size=',sz printString
 ! !
-
 !Color methodsFor:'inspecting'!
 
 inspectorClass
@@ -446,7 +418,6 @@
 
     "Modified: 23.4.1996 / 13:39:50 / cg"
 ! !
-
 !Color methodsFor:'inspecting'!
 
 inspectorExtraAttributes
@@ -462,7 +433,6 @@
      Color red inspect
     "
 ! !
-
 !Color methodsFor:'inspecting'!
 
 inspectorValueStringInListFor:anInspector
@@ -470,35 +440,30 @@
 
     ^ self htmlPrintString
 ! !
-
 !CompositeChange methodsFor:'utilities'!
 
 condenseChangesForRemoved
 
     self changes condenseChangesForRemoved
 ! !
-
 !CompositeChange methodsFor:'private'!
 
 flattenOnto: aCollection
 
     changes do:[:change|change flattenOnto: aCollection]
 ! !
-
 !CompositeChange methodsFor:'accessing'!
 
 removed
 
     ^changes allSatisfy: [:e|e removed]
 ! !
-
 !CompositeChange methodsFor:'accessing'!
 
 removed: aBoolean
 
     changes do:[:e|e removed: aBoolean]
 ! !
-
 !Date methodsFor:'inspecting'!
 
 inspectorExtraAttributes
@@ -519,7 +484,6 @@
 
     "Created: / 20-01-2011 / 12:19:05 / cg"
 ! !
-
 !Dictionary methodsFor:'inspecting'!
 
 inspector2TabLabel
@@ -527,7 +491,6 @@
 
     "Created: / 14-07-2011 / 11:57:18 / cg"
 ! !
-
 !Dictionary methodsFor:'inspecting'!
 
 inspectorClass
@@ -536,7 +499,6 @@
 
     ^ DictionaryInspectorView
 ! !
-
 !EditTextView methodsFor:'accessing-dimensions'!
 
 absoluteXOfPosition:positionInText 
@@ -554,7 +516,6 @@
 
     "Created: / 16-02-2010 / 10:05:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !EditTextView methodsFor:'accessing-dimensions'!
 
 absoluteYOfCursor
@@ -573,7 +534,6 @@
     "Created: / 27-05-2005 / 07:45:53 / janfrog"
     "Modified: / 27-05-2005 / 23:03:40 / janfrog"
 ! !
-
 !EditTextView methodsFor:'accessing-dimensions'!
 
 xOfPosition: positionInText
@@ -587,7 +547,6 @@
 
     "Created: / 16-02-2010 / 10:04:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !EditTextView methodsFor:'accessing-dimensions'!
 
 yOfCursor
@@ -596,7 +555,6 @@
 
     "Created: / 27-05-2005 / 07:43:41 / janfrog"
 ! !
-
 !EditTextView methodsFor:'accessing-dimensions'!
 
 yOfPosition: positionInText
@@ -607,7 +565,6 @@
 
     "Created: / 16-02-2010 / 10:08:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !ExecutableFunction methodsFor:'printing & storing'!
 
 printStringForBrowserWithSelector:selector
@@ -615,7 +572,6 @@
 
     ^ self printStringForBrowserWithSelector:selector inClass:nil
 ! !
-
 !Form methodsFor:'inspecting'!
 
 inspectorClass
@@ -624,7 +580,6 @@
 
     ^ ImageInspectorView
 ! !
-
 !GenericToolbarIconLibrary class methodsFor:'image specs-22x22'!
 
 bookmarks22x22
@@ -654,7 +609,6 @@
 
     "Modified: / 05-05-2011 / 12:45:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !GenericToolbarIconLibrary class methodsFor:'image specs-16x16'!
 
 bug16x16Icon
@@ -679,7 +633,6 @@
 ?_????????????7=W5=_W5?=O/7???????>L?PLC@0LC?_????????7=/4S[7S 8TY/=?VC?????L#L.>JI3I+A%H#[?????GA3_]U*/M3_;BPRLD_????7=
 ?_B@M>DE-04>?U/??????2_=HEXYQ7:R<Q_???????4>G2$%Q9QEL?5_??????????<=?\;M??????????????????=-H????????0@a') ; colorMapFromArray:#[205 205 205 227 35 35 106 106 106 98 98 98 135 135 135 163 34 34 101 5 5 124 124 124 48 2 2 227 11 11 173 173 173 218 54 54 241 241 241 235 19 19 225 225 225 219 18 18 245 58 58 214 214 214 249 46 46 90 90 90 254 61 61 36 36 36 176 176 176 233 233 233 114 114 114 255 78 78 212 33 33 230 57 57 61 61 61 94 94 94 76 76 76 19 19 19 255 57 57 161 161 161 83 83 83 217 217 217 249 249 249 255 65 65 139 2 2 27 27 27 169 169 169 253 53 53 210 28 28 251 251 251 154 154 154 117 117 117 195 1 1 245 245 245 145 145 145 218 5 5 230 230 230 69 2 2 181 181 181 11 11 11 141 141 141 249 61 61 205 21 21 165 165 165 157 157 157 241 28 28 223 223 223 109 109 109 2 2 2 245 45 45 146 0 0 69 69 69 137 137 137 140 40 40 188 1 1 206 24 24 219 33 33 255 76 76 249 49 49 249 56 56 236 236 236 121 121 121 248 53 53 171 1 1 111 40 40 237 41 41 178 21 21 205 16 16 129 129 129 163 1 1 155 18 18 85 4 4 243 68 68 73 73 73 45 45 45 202 51 51 241 40 40 86 86 86 114 1 1 210 4 4 246 41 41 148 148 148 189 189 189 209 209 209 210 17 17 158 28 28 213 5 5 205 1 1 53 53 53 217 9 9 69 40 40 187 10 10 255 74 74 218 28 28 146 11 11 65 65 65 232 37 37 101 101 101 196 26 26 245 53 53 188 26 26 213 10 10 184 184 184 206 5 5 249 65 65 172 21 21 206 34 34 195 195 195 237 32 32 131 12 12 233 29 29 179 36 36 241 37 37 139 13 13 245 49 49 180 1 1 168 37 37 198 198 198 202 202 202 228 21 21 206 10 10 206 29 29 229 30 30 255 80 80 188 20 20 245 37 37 57 57 57 252 50 50 87 42 42 172 10 10 209 13 13 155 4 4 164 11 11 242 44 44 255 70 70 225 25 25 222 14 14 237 24 24 240 49 49 205 13 13 202 44 44 201 0 0 225 17 17 186 42 42 255 72 72 122 1 1 40 40 40 157 10 10 209 8 8 222 8 8 195 41 41 223 21 21 180 11 11 255 68 68 162 28 28 194 11 11 232 25 25 131 1 1 241 32 32 246 246 246 49 49 49 224 44 44 208 2 2 227 227 227 239 239 239 239 46 46 162 20 20 245 33 33 219 219 219 238 29 29 237 37 37 171 29 29 36 46 46 250 68 68 147 16 16 182 26 26 187 187 187 24 1 1 185 32 32 229 24 24 232 33 33 150 150 150 122 12 12 229 17 17 204 27 27 242 52 52 213 2 2 200 15 15 191 191 191 217 43 43 217 12 12 115 10 10 140 16 16 200 28 28 202 6 6 215 13 13 182 41 41 57 46 46 40 46 46 233 40 40 252 70 70 173 40 40 226 28 28 46 54 54 202 22 22 203 18 18 245 72 72 191 17 17 200 37 37 10 0 0 50 52 52 252 74 74 252 72 72 247 38 38 160 40 40 231 14 14 252 68 68 200 10 10 15 15 15 211 47 47 254 254 254 253 76 76 23 23 23 237 69 69 7 7 7 144 7 7 196 8 7 32 32 32 59 59 59 90 93 93 67 67 67 70 28 28 50 56 56 232 15 16 208 4 4 237 35 35 220 12 11 232 20 20 223 62 62 0 0 0 255 255 255 255 255 255]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@L@@0@C8AO C?0O<C?>G?0??#?>C?0_?@O@@L@b') ; yourself); yourself]
 ! !
-
 !GenericToolbarIconLibrary class methodsFor:'image specs-24x24'!
 
 bug24x24Icon
@@ -708,7 +661,6 @@
 <Q_???????????4XO!!?DJRU*Q9P%QSL5?U<-?????????3T5???=F$  EB@?L37?G3;=????????????????O_7D3,7=??????????????????????????<(
 [RO?????????????????????????????????????????????') ; colorMapFromArray:#[205 205 205 227 35 35 106 106 106 98 98 98 135 135 135 163 34 34 101 5 5 124 124 124 48 2 2 227 11 11 173 173 173 218 54 54 241 241 241 235 19 19 225 225 225 219 18 18 245 58 58 214 214 214 249 46 46 90 90 90 254 61 61 36 36 36 176 176 176 233 233 233 114 114 114 255 78 78 212 33 33 230 57 57 61 61 61 94 94 94 76 76 76 19 19 19 255 57 57 161 161 161 83 83 83 217 217 217 249 249 249 255 65 65 139 2 2 27 27 27 169 169 169 253 53 53 210 28 28 251 251 251 154 154 154 117 117 117 195 1 1 245 245 245 145 145 145 218 5 5 230 230 230 69 2 2 181 181 181 11 11 11 141 141 141 249 61 61 205 21 21 165 165 165 157 157 157 241 28 28 223 223 223 109 109 109 2 2 2 245 45 45 146 0 0 69 69 69 137 137 137 140 40 40 188 1 1 206 24 24 219 33 33 255 76 76 249 49 49 249 56 56 236 236 236 121 121 121 248 53 53 171 1 1 111 40 40 237 41 41 178 21 21 205 16 16 129 129 129 163 1 1 155 18 18 85 4 4 243 68 68 73 73 73 45 45 45 202 51 51 241 40 40 86 86 86 114 1 1 210 4 4 246 41 41 148 148 148 189 189 189 209 209 209 210 17 17 158 28 28 213 5 5 205 1 1 53 53 53 217 9 9 69 40 40 187 10 10 255 74 74 218 28 28 146 11 11 65 65 65 232 37 37 101 101 101 196 26 26 245 53 53 188 26 26 213 10 10 184 184 184 206 5 5 249 65 65 172 21 21 206 34 34 195 195 195 237 32 32 131 12 12 233 29 29 179 36 36 241 37 37 139 13 13 245 49 49 180 1 1 168 37 37 198 198 198 202 202 202 228 21 21 206 10 10 206 29 29 229 30 30 255 80 80 188 20 20 245 37 37 57 57 57 252 50 50 87 42 42 172 10 10 209 13 13 155 4 4 164 11 11 242 44 44 255 70 70 225 25 25 222 14 14 237 24 24 240 49 49 205 13 13 202 44 44 201 0 0 225 17 17 186 42 42 255 72 72 122 1 1 40 40 40 157 10 10 209 8 8 222 8 8 195 41 41 223 21 21 180 11 11 255 68 68 162 28 28 194 11 11 232 25 25 131 1 1 241 32 32 246 246 246 49 49 49 224 44 44 208 2 2 227 227 227 239 239 239 239 46 46 162 20 20 245 33 33 219 219 219 238 29 29 237 37 37 171 29 29 36 46 46 250 68 68 147 16 16 182 26 26 187 187 187 24 1 1 185 32 32 229 24 24 232 33 33 150 150 150 122 12 12 229 17 17 204 27 27 242 52 52 213 2 2 200 15 15 191 191 191 217 43 43 217 12 12 115 10 10 140 16 16 200 28 28 202 6 6 215 13 13 182 41 41 57 46 46 40 46 46 233 40 40 252 70 70 173 40 40 226 28 28 46 54 54 202 22 22 203 18 18 245 72 72 191 17 17 200 37 37 10 0 0 50 52 52 252 74 74 252 72 72 247 38 38 160 40 40 231 14 14 252 68 68 200 10 10 15 15 15 211 47 47 254 254 254 253 76 76 23 23 23 237 69 69 7 7 7 144 7 7 196 8 7 32 32 32 59 59 59 90 93 93 67 67 67 70 28 28 50 56 56 232 15 16 208 4 4 237 35 35 220 12 11 232 20 20 223 62 62 0 0 0 255 255 255 255 255 255]; mask:((ImageMask new) width: 24; height: 24; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@H@@HH@@FH@@FH@@CX@@G<@BO<HGO>8A??0@??@@??@G??<C??8@??@G??<G??<G??XA??0C??8CO>8@G8@@A0@@@@@') ; yourself); yourself]
 ! !
-
 !GenericToolbarIconLibrary class methodsFor:'image specs-32x32'!
 
 bug32x32Icon
@@ -760,7 +712,6 @@
                 yourself
         ]
 ! !
-
 !GenericToolbarIconLibrary class methodsFor:'image specs-16x16'!
 
 lint16x16Icon
@@ -785,7 +736,6 @@
 @XS??????????3<)-;^76.Z5A0O???????<P@W!!8>-3J<0+??????0\JI1,;7^?57-[;''T????<JS0P"PN3'':-V>8L??????V5@''G57.1,!!#X-''R_O???1(R
 @RMW:Y*KY6+7*RW??????3P*ZU[;.:#!!/:7???????<A@6AV2?S:9+>5??????????< BC &?????;?Z??????????<XU_?????X<P@a') ; colorMapFromArray:#[0 1 0 0 2 0 1 4 0 3 6 2 30 1 0 6 9 5 34 2 2 10 12 8 43 4 2 13 15 12 15 17 13 77 0 0 16 18 15 35 14 12 17 19 16 67 6 1 19 20 18 75 7 10 21 23 20 86 9 4 25 27 24 111 4 7 103 7 10 96 10 12 32 29 28 29 30 28 31 33 30 153 2 0 33 35 33 35 36 34 110 16 16 173 0 1 36 38 35 41 37 36 165 4 0 155 7 7 128 15 14 39 41 39 157 12 16 51 42 42 207 0 4 43 45 42 58 41 39 141 19 15 199 4 0 210 3 0 221 1 4 48 49 47 231 0 12 211 7 8 172 19 10 172 19 18 52 54 51 53 55 53 234 5 23 59 54 53 176 24 21 56 57 55 57 59 56 204 19 22 195 22 24 103 47 48 227 16 9 60 61 59 198 25 19 216 20 21 61 63 60 119 48 45 228 20 20 63 65 62 211 30 27 68 69 67 69 71 68 212 32 34 242 25 29 72 74 71 74 76 74 191 45 50 245 31 38 76 78 75 77 79 76 79 80 78 138 66 66 248 36 40 240 41 43 83 85 82 216 50 52 241 43 50 195 58 61 86 88 85 244 46 46 87 89 86 89 91 88 214 58 58 193 65 67 92 93 91 248 51 49 109 90 87 185 68 87 194 67 80 87 95 125 250 54 57 173 74 96 202 67 84 159 78 103 253 56 52 188 72 90 87 99 135 129 89 121 99 101 98 73 104 148 255 59 60 159 83 106 175 81 94 94 102 132 187 78 98 215 71 85 255 61 67 169 84 104 251 66 66 104 106 103 90 106 147 151 92 119 200 81 93 107 108 106 140 99 131 162 94 119 255 72 76 144 100 128 96 112 153 228 80 83 159 97 120 111 113 110 191 90 111 206 87 104 113 115 112 87 118 163 115 117 114 83 122 166 179 100 117 118 120 117 199 99 101 231 91 88 138 113 147 120 122 119 196 101 119 123 125 122 115 123 167 213 100 113 119 123 162 180 109 128 127 129 126 208 108 109 115 131 173 185 115 140 158 122 154 173 119 144 131 133 130 130 130 163 178 122 124 181 119 147 106 139 178 136 138 135 120 139 175 126 138 175 204 121 132 132 139 172 113 146 186 136 143 176 144 146 143 121 149 184 153 142 173 135 150 181 148 150 147 125 153 188 130 153 182 179 140 167 150 152 149 205 136 148 181 145 146 136 159 189 155 157 154 140 163 193 159 161 158 161 163 160 143 166 196 162 164 161 148 167 192 164 166 163 165 165 187 197 159 173 167 169 166 152 171 196 191 163 180 157 172 191 169 171 168 216 159 166 171 173 170 208 163 179 187 169 190 217 162 175 174 176 173 159 178 203 186 173 174 207 167 175 163 178 198 213 166 176 179 181 178 198 176 192 169 185 204 183 185 182 216 175 184 209 177 189 212 180 192 204 183 198 208 183 193 188 190 187 180 192 206 194 196 193 215 191 201 187 199 213 204 198 197 211 196 210 199 201 198 190 202 216 191 203 217 201 202 212 202 204 201 208 203 201 219 201 210 205 207 203 217 203 217 206 208 205 213 207 206 223 205 214 203 211 220 211 213 210 211 212 222 214 216 213 221 215 227 217 219 216 219 221 218 228 218 224 217 222 225 221 223 220 231 221 227 216 225 233 220 226 228 224 226 223 221 229 238 231 233 230 228 234 236 233 235 232 235 238 234 249 251 248 255 255 255]; mask:((ImageMask new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@L@@0@C8AO0C?0O>C?>O?0??#?>C?0O?@OC@LLb') ; yourself); yourself]
 ! !
-
 !GenericToolbarIconLibrary class methodsFor:'image specs-24x24'!
 
 lint24x24Icon
@@ -814,7 +764,6 @@
 /:6D??????????<)@PLSXEY?2?S<>.Y-/;V-?????????1$A??<GRU)/]8JMT"_?/;>5#O??????????????H@ +NBXQ??????>:/=*L??????????????<9
 FEU_????????6OF5????????????????????????????-]K?') ; colorMapFromArray:#[0 1 0 0 2 0 1 4 0 3 6 2 30 1 0 6 9 5 34 2 2 10 12 8 43 4 2 13 15 12 15 17 13 77 0 0 16 18 15 35 14 12 17 19 16 67 6 1 19 20 18 75 7 10 21 23 20 86 9 4 25 27 24 111 4 7 103 7 10 96 10 12 32 29 28 29 30 28 31 33 30 153 2 0 33 35 33 35 36 34 110 16 16 173 0 1 36 38 35 41 37 36 165 4 0 155 7 7 128 15 14 39 41 39 157 12 16 51 42 42 207 0 4 43 45 42 58 41 39 141 19 15 199 4 0 210 3 0 221 1 4 48 49 47 231 0 12 211 7 8 172 19 10 172 19 18 52 54 51 53 55 53 234 5 23 59 54 53 176 24 21 56 57 55 57 59 56 204 19 22 195 22 24 103 47 48 227 16 9 60 61 59 198 25 19 216 20 21 61 63 60 119 48 45 228 20 20 63 65 62 211 30 27 68 69 67 69 71 68 212 32 34 242 25 29 72 74 71 74 76 74 191 45 50 245 31 38 76 78 75 77 79 76 79 80 78 138 66 66 248 36 40 240 41 43 83 85 82 216 50 52 241 43 50 195 58 61 86 88 85 244 46 46 87 89 86 89 91 88 214 58 58 193 65 67 92 93 91 248 51 49 109 90 87 185 68 87 194 67 80 87 95 125 250 54 57 173 74 96 202 67 84 159 78 103 253 56 52 188 72 90 87 99 135 129 89 121 99 101 98 73 104 148 255 59 60 159 83 106 175 81 94 94 102 132 187 78 98 215 71 85 255 61 67 169 84 104 251 66 66 104 106 103 90 106 147 151 92 119 200 81 93 107 108 106 140 99 131 162 94 119 255 72 76 144 100 128 96 112 153 228 80 83 159 97 120 111 113 110 191 90 111 206 87 104 113 115 112 87 118 163 115 117 114 83 122 166 179 100 117 118 120 117 199 99 101 231 91 88 138 113 147 120 122 119 196 101 119 123 125 122 115 123 167 213 100 113 119 123 162 180 109 128 127 129 126 208 108 109 115 131 173 185 115 140 158 122 154 173 119 144 131 133 130 130 130 163 178 122 124 181 119 147 106 139 178 136 138 135 120 139 175 126 138 175 204 121 132 132 139 172 113 146 186 136 143 176 144 146 143 121 149 184 153 142 173 135 150 181 148 150 147 125 153 188 130 153 182 179 140 167 150 152 149 205 136 148 181 145 146 136 159 189 155 157 154 140 163 193 159 161 158 161 163 160 143 166 196 162 164 161 148 167 192 164 166 163 165 165 187 197 159 173 167 169 166 152 171 196 191 163 180 157 172 191 169 171 168 216 159 166 171 173 170 208 163 179 187 169 190 217 162 175 174 176 173 159 178 203 186 173 174 207 167 175 163 178 198 213 166 176 179 181 178 198 176 192 169 185 204 183 185 182 216 175 184 209 177 189 212 180 192 204 183 198 208 183 193 188 190 187 180 192 206 194 196 193 215 191 201 187 199 213 204 198 197 211 196 210 199 201 198 190 202 216 191 203 217 201 202 212 202 204 201 208 203 201 219 201 210 205 207 203 217 203 217 206 208 205 213 207 206 223 205 214 203 211 220 211 213 210 211 212 222 214 216 213 221 215 227 217 219 216 219 221 218 228 218 224 217 222 225 221 223 220 231 221 227 216 225 233 220 226 228 224 226 223 221 229 238 231 233 230 228 234 236 233 235 232 235 238 234 249 251 248 255 255 255]; mask:((ImageMask new) width: 24; height: 24; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@LL@@FH@@FH@@CX@@G<@BG>HGO>XA??8@?? @?? G??<G??8@??0G??<G??<G??<@??8A??8CO><@G8O@A8G@@@F') ; yourself); yourself]
 ! !
-
 !GenericToolbarIconLibrary class methodsFor:'image specs-32x32'!
 
 lint32x32Icon
@@ -851,7 +800,6 @@
 @@@@@@@@D@@@NC @@A 8@@@\L@@@CC@@@@Y0@@@G8@@@C? @AA?<H@8??G@G???0@???8@G??8@@??>@C???>A???? O???0@O??0@C??<@O???8G???>@??
 ?? @???@@_??8@O???@GO?38@!!?8_@@O<C8@@>@^@@@@C@@@@@@b') ; yourself); yourself]
 ! !
-
 !GenericToolbarIconLibrary class methodsFor:'image specs-16x16'!
 
 smalllintWarning16x16
@@ -882,7 +830,6 @@
 @@@@@@@@????????????9\^ 1(T.1(T.1(T.1(T.1(T.9\^ @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@????????????????????????????@@@@@@@@
 @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@') ; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@_@C>@_<A?0G?0_? ?>C?<G?0_?!!?>G?8O?@G<@@@b') ; yourself); yourself]
 ! !
-
 !GenericToolbarIconLibrary class methodsFor:'image specs-versions'!
 
 versionMerged24x24
@@ -911,7 +858,6 @@
 UEQNS30GLFI,\V11\W!!,X&I"Y&I!!W%9^T5MSWS0HLH]:^&93[798[G9/\V1,X&I!!WFA\Y30EMIF,%9RK_G%9\&=/[6=1[&91[GV@]DHDJ9>6+)2P"8"A!!7=?
 _7=?_7=?\7Q.^4@CA"X-I2\''I2</JR$)JR (JB (K"4,J"T@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[28 1 19 26 0 23 36 0 35 57 0 48 55 1 50 58 0 51 61 0 54 57 3 52 56 0 54 63 0 57 64 0 58 63 0 62 67 3 66 66 0 68 69 5 67 70 6 68 70 0 72 71 0 73 57 15 60 65 17 63 72 9 70 79 0 77 70 0 74 72 0 75 61 25 59 81 2 79 74 13 71 74 1 77 76 4 79 70 15 72 66 23 68 78 7 81 75 19 76 81 12 83 61 25 67 75 21 77 78 23 79 91 5 94 114 6 111 122 0 119 124 0 121 130 0 123 118 0 120 110 25 104 119 0 122 119 17 114 120 0 123 125 20 115 129 2 127 135 0 131 137 0 134 139 0 136 125 26 118 138 1 141 137 22 130 142 9 143 138 16 142 139 31 136 142 22 145 145 26 147 147 16 155 154 0 166 159 22 161 128 73 126 148 48 147 186 0 187 155 40 156 187 0 189 196 0 193 188 0 190 188 0 191 156 31 162 189 0 192 180 0 187 157 32 163 198 0 197 164 20 172 191 4 193 200 0 200 182 3 189 156 57 155 193 9 194 202 0 202 203 0 204 196 13 195 152 66 152 194 0 199 205 0 206 164 41 168 206 0 207 197 17 195 195 0 201 207 0 208 188 16 192 196 0 202 198 20 195 207 0 209 196 0 203 197 0 204 167 45 171 199 23 196 198 0 205 208 0 211 192 23 194 200 26 196 189 0 201 199 2 206 201 29 196 203 7 208 202 31 197 192 5 203 200 0 210 173 52 176 206 13 209 201 0 211 195 11 204 199 33 198 214 18 211 204 36 198 201 0 212 208 17 210 202 0 213 197 15 205 190 33 195 203 0 214 184 47 187 210 21 211 202 39 200 208 41 201 211 24 212 200 22 207 202 25 208 214 28 214 204 28 209 198 1 216 207 47 203 207 31 211 200 45 202 185 65 187 208 33 212 198 32 208 209 35 213 210 38 214 212 40 215 213 42 216 207 55 208 202 40 211 193 73 194 214 44 217 205 42 213 216 46 218 213 28 223 206 44 214 208 47 215 220 49 221 214 62 214 221 51 222 192 87 193 210 50 217 206 83 201 215 64 215 211 51 218 224 55 224 213 53 219 217 67 217 227 58 226 218 68 218 215 56 221 218 58 223 213 80 212 220 71 220 219 60 224 229 62 229 220 61 225 231 64 230 223 74 222 201 96 202 222 63 226 224 75 223 225 76 224 218 85 217 224 65 228 226 78 224 224 67 229 218 77 222 228 80 226 229 82 227 226 70 231 230 83 228 223 81 226 211 105 211 225 92 223 233 85 230 226 93 224 224 84 228 231 75 235 227 95 225 234 87 232 219 94 223 230 98 228 228 89 232 217 106 222 234 102 232 225 100 229 226 101 230 228 104 232 213 116 219 229 105 233 231 107 235 224 114 229 199 149 203 242 102 244 216 137 220 205 135 215 237 113 241 234 128 234 238 114 242 223 126 229 226 134 228 236 130 236 225 128 231 229 131 234 240 134 239 233 117 242 230 133 236 239 128 243 236 143 238 238 145 239 238 123 247 243 133 247 238 146 240 215 161 223 241 148 243 250 144 249 235 156 239 225 155 235 237 158 241 229 163 235 249 142 255 242 161 245 247 149 252 238 154 246 246 170 245 249 151 254 249 153 255 238 170 243 230 176 238 245 161 253 247 163 255 236 181 244 245 166 255 243 172 253 245 190 253 243 184 254 246 193 255 238 193 253]; yourself]
 ! !
-
 !Image methodsFor:'inspecting'!
 
 inspector2TabImage
@@ -923,7 +869,6 @@
 
     "Created: / 11-10-2011 / 17:12:01 / cg"
 ! !
-
 !Image methodsFor:'inspecting'!
 
 inspector2Tabs
@@ -931,7 +876,6 @@
 
     "Created: / 11-10-2011 / 17:11:21 / cg"
 ! !
-
 !Image methodsFor:'inspecting'!
 
 inspectorClass
@@ -945,7 +889,6 @@
 
     "Modified: 10.6.1996 / 18:23:55 / cg"
 ! !
-
 !Integer methodsFor:'inspecting'!
 
 inspectorExtraAttributes
@@ -965,7 +908,6 @@
     "Created: / 18-09-2006 / 21:22:46 / cg"
     "Modified: / 06-10-2006 / 13:57:28 / cg"
 ! !
-
 !Iterator methodsFor:'inspecting'!
 
 inspectorValueStringInListFor:anInspector
@@ -974,7 +916,6 @@
 
     ^ self classNameWithArticle
 ! !
-
 !LimitedPrecisionReal methodsFor:'inspecting'!
 
 inspectorExtraAttributes
@@ -996,7 +937,6 @@
 
     "Created: / 20-03-2012 / 22:34:46 / cg"
 ! !
-
 !MenuView methodsFor:'accessing-behavior'!
 
 shortKeys
@@ -1004,7 +944,6 @@
 
     "Created: / 18-10-2008 / 19:16:59 / Jan Vrany <vranyj1@fel.cvut.cz>"
 ! !
-
 !Method methodsFor:'inspecting'!
 
 inspectorExtraAttributes
@@ -1023,7 +962,6 @@
     "Created: / 18-09-2006 / 21:34:01 / cg"
     "Modified: / 06-10-2006 / 13:57:33 / cg"
 ! !
-
 !Method methodsFor:'printing & storing'!
 
 printStringForBrowserWithSelector:selector inClass:aClass
@@ -1129,10 +1067,8 @@
             "/ suppressPackage := true
         ].
         suppressPackage ifFalse:[
-            shadowsOrNot := (cls notNil 
-                             and:[ cls theNonMetaclass projectDefinitionClass notNil
-                             and:[ (cls theNonMetaclass projectDefinitionClass savedOverwrittenMethodForClass:cls selector:selector) notNil ]])
-                                ifTrue:[' shadow' ]
+            shadowsOrNot := (self isShadowingExtension)
+                                ifTrue:[' shadowed' ]
                                 ifFalse:[ '' ].
             p := ' [' , ((mthdPackage ? '?'), shadowsOrNot allBold) allItalic , '] '.
             p := p asText emphasisAllAdd:(userPreferences emphasisForDifferentPackage).
@@ -1154,13 +1090,11 @@
     "Modified: / 05-03-2007 / 16:18:53 / cg"
     "Modified: / 20-07-2010 / 15:39:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !Method methodsFor:'printing & storing'!
 
 selectorPrintStringInBrowserFor:selector
     ^ selector
 ! !
-
 !Method methodsFor:'printing & storing'!
 
 selectorPrintStringInBrowserFor:selector class:aClass
@@ -1178,7 +1112,6 @@
 
     "Modified: / 20-07-2010 / 10:33:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !MethodDictionary methodsFor:'inspecting'!
 
 inspectorClass
@@ -1189,7 +1122,6 @@
 
     "Created: 12.6.1996 / 12:29:13 / stefan"
 ! !
-
 !NameSpace class methodsFor:'inspecting'!
 
 inspectorClass
@@ -1202,7 +1134,6 @@
 
 
 ! !
-
 !Object methodsFor:'debugging'!
 
 inspect
@@ -1231,7 +1162,6 @@
      (Image fromFile:'bitmaps/garfield.gif') inspect
     "
 ! !
-
 !Object methodsFor:'inspecting'!
 
 inspector2TabCommon
@@ -1242,7 +1172,6 @@
     "Created: / 24-05-2011 / 14:56:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 05-07-2011 / 14:06:28 / cg"
 ! !
-
 !Object methodsFor:'inspecting'!
 
 inspector2TabForBasicInspect
@@ -1256,7 +1185,6 @@
 
     "Created: / 05-07-2011 / 13:59:59 / cg"
 ! !
-
 !Object methodsFor:'inspecting'!
 
 inspector2TabForInspectorClass
@@ -1270,7 +1198,6 @@
 
     "Created: / 05-07-2011 / 14:06:16 / cg"
 ! !
-
 !Object methodsFor:'inspecting'!
 
 inspector2TabLabel
@@ -1280,7 +1207,6 @@
 
     "Created: / 14-07-2011 / 11:56:23 / cg"
 ! !
-
 !Object methodsFor:'inspecting'!
 
 inspector2Tabs
@@ -1292,7 +1218,6 @@
 
     "Created: / 05-07-2011 / 13:39:24 / cg"
 ! !
-
 !Object methodsFor:'debugging'!
 
 inspectorExtraAttributes
@@ -1313,7 +1238,6 @@
     "Modified: / 02-09-2005 / 19:00:01 / janfrog"
     "Modified: / 04-10-2006 / 14:33:34 / cg"
 ! !
-
 !Object methodsFor:'inspecting'!
 
 inspectorValueStringInListFor:anInspector
@@ -1323,7 +1247,6 @@
 
     "Created: / 13-06-2012 / 12:50:26 / cg"
 ! !
-
 !Object methodsFor:'testing'!
 
 isTestCaseLike
@@ -1332,7 +1255,6 @@
 
     "Created: / 28-02-2011 / 21:30:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !Object methodsFor:'debugging'!
 
 newInspector2Tab
@@ -1343,7 +1265,6 @@
         ifNil:[self error:'Inspector2 not available!! Something is rotten...']
         ifNotNil:[(Smalltalk at: #'Tools::Inspector2Tab') new]
 ! !
-
 !OrderedCollection methodsFor:'inspecting'!
 
 inspectorClass
@@ -1358,7 +1279,6 @@
      #(0 8 15 3 99 2) asSortedCollection inspect
     "
 ! !
-
 !PopUpMenu methodsFor:'converting'!
 
 asMenu
@@ -1385,7 +1305,6 @@
     "Created: / 18-10-2008 / 19:01:32 / Jan Vrany <vranyj1@fel.cvut.cz>"
     "Modified: / 09-09-2012 / 13:10:25 / cg"
 ! !
-
 !ProfileTree methodsFor:'accessing'!
 
 method
@@ -1396,7 +1315,6 @@
     "Created: / 01-12-2007 / 22:50:16 / janfrog"
     "Modified: / 07-11-2008 / 08:40:35 / Jan Vrany <vranyj1@fel.cvut.cz>"
 ! !
-
 !ProfileTree methodsFor:'accessing'!
 
 package
@@ -1407,7 +1325,6 @@
     "Created: / 01-12-2007 / 22:50:28 / janfrog"
     "Modified: / 07-11-2008 / 08:40:35 / Jan Vrany <vranyj1@fel.cvut.cz>"
 ! !
-
 !RunArray methodsFor:'user interface'!
 
 inspectorClass
@@ -1418,19 +1335,16 @@
 
     "Modified: / 30.10.1997 / 14:28:20 / cg"
 ! !
-
 !SelectionInListModelView methodsFor:'accessing'!
 
 textStartLeft
     ^ textStartLeft
 ! !
-
 !SelectionInListModelView methodsFor:'accessing'!
 
 textStartLeft:something
     textStartLeft := something.
 ! !
-
 !Set methodsFor:'inspecting'!
 
 inspectorClass
@@ -1439,7 +1353,6 @@
 
     ^ SetInspectorView
 ! !
-
 !SimpleView methodsFor:'testing'!
 
 isCodeView2
@@ -1448,7 +1361,6 @@
 
     "Created: / 20-07-2010 / 15:42:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !Smalltalk class methodsFor:'queries'!
 
 inspectorClass
@@ -1457,7 +1369,6 @@
 
     ^ DictionaryInspectorView
 ! !
-
 !StringCollection methodsFor:'inspecting'!
 
 inspector2TabText
@@ -1469,7 +1380,6 @@
 
     "Created: / 17-02-2008 / 10:13:07 / janfrog"
 ! !
-
 !StringCollection methodsFor:'inspecting'!
 
 inspector2Tabs
@@ -1477,7 +1387,6 @@
 
     "Created: / 05-07-2011 / 13:40:43 / cg"
 ! !
-
 !Symbol methodsFor:'accessing'!
 
 formattedCode
@@ -1488,7 +1397,6 @@
 
     "Created: / 07-07-2009 / 20:03:21 / Jan Vrany <vranyj1@fel.cvut.cz>"
 ! !
-
 !Symbol methodsFor:'inspecting'!
 
 inspectorValueStringInListFor:anInspector
@@ -1496,7 +1404,6 @@
 
     ^ self storeString
 ! !
-
 !Text methodsFor:'inspecting'!
 
 inspector2TabText
@@ -1510,7 +1417,6 @@
     "Modified: / 17-02-2008 / 10:28:33 / janfrog"
     "Modified: / 21-08-2011 / 08:02:46 / cg"
 ! !
-
 !Text methodsFor:'inspecting'!
 
 inspectorExtraAttributes
@@ -1528,7 +1434,6 @@
     "Created: / 18-09-2006 / 21:25:52 / cg"
     "Modified: / 06-10-2006 / 13:57:38 / cg"
 ! !
-
 !Timestamp methodsFor:'inspecting'!
 
 inspectorExtraAttributes
@@ -1549,7 +1454,6 @@
 
     "Created: / 20-01-2011 / 12:19:05 / cg"
 ! !
-
 !UndefinedObject methodsFor:'inspecting'!
 
 inspectorValueStringInListFor:anInspector
@@ -1557,7 +1461,6 @@
 
     ^ 'nil'
 ! !
-
 !UninterpretedBytes methodsFor:'inspecting'!
 
 inspector2Tabs
@@ -1565,7 +1468,6 @@
 
     "Created: / 27-02-2012 / 21:51:36 / cg"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-browser'!
 
 alwaysOpenNewTabWhenCtrlClick
@@ -1580,7 +1482,6 @@
     "Created: / 19-10-2008 / 08:00:53 / Jan Vrany <vranyj1@fel.cvut.cz>"
     "Modified: / 14-02-2010 / 19:37:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-browser'!
 
 alwaysOpenNewTabWhenCtrlClick: aBoolean
@@ -1589,7 +1490,6 @@
 
     "Created: / 19-10-2008 / 08:01:45 / Jan Vrany <vranyj1@fel.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-pref''d tools'!
 
 changesBrowserClassName
@@ -1600,7 +1500,6 @@
 
     "Created: / 03-04-2012 / 11:02:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-code view'!
 
 codeView2AutoIndent
@@ -1615,7 +1514,6 @@
     "Modified: / 15-02-2010 / 09:26:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Created: / 07-08-2011 / 12:46:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-code view'!
 
 codeView2AutoIndent: aBoolean
@@ -1630,7 +1528,6 @@
     "Modified: / 15-02-2010 / 09:26:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Created: / 07-08-2011 / 12:47:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-code view'!
 
 codeView2ShowAcceptCancel
@@ -1644,7 +1541,6 @@
     "Modified: / 15-02-2010 / 09:26:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Created: / 10-10-2011 / 16:41:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-code view'!
 
 codeView2ShowAcceptCancel: aBoolean
@@ -1658,7 +1554,6 @@
     "Modified: / 15-02-2010 / 09:26:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Created: / 10-10-2011 / 16:40:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-browser'!
 
 confirmRefactorings
@@ -1679,7 +1574,6 @@
 
     "Created: / 04-04-2012 / 14:02:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-browser'!
 
 confirmRefactorings:aBoolean
@@ -1700,7 +1594,6 @@
 
     "Created: / 04-04-2012 / 14:02:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-pref''d tools'!
 
 fileBrowserClass
@@ -1720,7 +1613,6 @@
 
     "Modified: / 03-04-2012 / 10:59:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-pref''d tools'!
 
 fileBrowserClass: aClass
@@ -1735,7 +1627,6 @@
 
     "Created: / 03-04-2012 / 10:57:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-pref''d tools'!
 
 fileBrowserClassName
@@ -1746,7 +1637,6 @@
 
     "Created: / 03-04-2012 / 11:01:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-browser'!
 
 showBookmarkBar
@@ -1763,7 +1653,6 @@
     "Created: / 18-05-2011 / 16:48:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 03-06-2011 / 11:01:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-browser'!
 
 showBookmarkBar: aBoolean
@@ -1779,7 +1668,6 @@
 
     "Created: / 18-05-2011 / 17:28:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-browser'!
 
 showEmbeddedTestRunnerInBrowser
@@ -1795,7 +1683,6 @@
 
     "Created: / 11-03-2010 / 10:11:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-browser'!
 
 showEmbeddedTestRunnerInBrowser:aBoolean
@@ -1810,7 +1697,6 @@
 
     "Created: / 11-03-2010 / 10:11:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-browser'!
 
 showGlobalHistory
@@ -1827,7 +1713,6 @@
     "Created: / 07-07-2011 / 00:03:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified (comment): / 26-07-2012 / 16:35:54 / cg"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-browser'!
 
 showGlobalHistory: aBoolean
@@ -1844,7 +1729,6 @@
     "Created: / 07-07-2011 / 00:02:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified (comment): / 26-07-2012 / 16:35:57 / cg"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-browser'!
 
 showLocalHistory
@@ -1861,7 +1745,6 @@
     "Created: / 07-07-2011 / 00:02:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified (comment): / 26-07-2012 / 16:35:31 / cg"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-browser'!
 
 showLocalHistory: aBoolean
@@ -1878,7 +1761,6 @@
     "Created: / 07-07-2011 / 00:02:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified (comment): / 26-07-2012 / 16:35:41 / cg"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-browser'!
 
 showMethodTemplate
@@ -1894,7 +1776,6 @@
 
     "Created: / 12-02-2010 / 12:06:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-browser'!
 
 showMethodTemplate:aBoolean
@@ -1909,7 +1790,6 @@
 
     "Created: / 12-02-2010 / 12:05:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-browser'!
 
 sortAndIndentClassesByInheritance
@@ -1924,7 +1804,6 @@
 
     "Created: / 06-07-2011 / 19:09:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-browser'!
 
 sortAndIndentClassesByInheritance: aBoolean
@@ -1939,7 +1818,6 @@
 
     "Created: / 06-07-2011 / 19:09:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-browser'!
 
 sourceCodeManagementMenuLayout
@@ -1962,7 +1840,6 @@
 
     "Created: / 06-10-2011 / 18:42:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-browser'!
 
 sourceCodeManagementMenuLayout: aSymbol
@@ -1986,7 +1863,6 @@
 
     "Created: / 06-10-2011 / 18:44:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-code view'!
 
 useCodeView2In: appSymbol
@@ -2008,7 +1884,6 @@
     "Modified: / 15-02-2010 / 09:26:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Created: / 26-07-2011 / 10:26:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-code view'!
 
 useCodeView2InBrowser
@@ -2026,7 +1901,6 @@
     "Modified: / 15-02-2010 / 09:26:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Created: / 26-07-2011 / 10:22:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-code view'!
 
 useCodeView2InBrowser: aBoolean
@@ -2044,7 +1918,6 @@
     "Modified: / 15-02-2010 / 09:26:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Created: / 26-07-2011 / 10:21:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-code view'!
 
 useCodeView2InDebugger
@@ -2062,7 +1935,6 @@
 
     "Created: / 26-07-2011 / 10:22:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-code view'!
 
 useCodeView2InDebugger: aBoolean
@@ -2080,7 +1952,6 @@
     "Modified: / 15-02-2010 / 09:26:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Created: / 26-07-2011 / 10:22:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-code view'!
 
 useCodeView2InTools
@@ -2094,7 +1965,6 @@
     "Created: / 12-02-2010 / 12:13:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 15-02-2010 / 09:26:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-code view'!
 
 useCodeView2InTools:aBoolean 
@@ -2105,7 +1975,6 @@
      UserPreferences current useCodeView2InBrowser:false"
     "Created: / 12-02-2010 / 12:14:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-code view'!
 
 useCodeView2InWorkspace
@@ -2123,7 +1992,6 @@
 
     "Created: / 26-07-2011 / 10:23:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-code view'!
 
 useCodeView2InWorkspace: aBoolean
@@ -2141,7 +2009,6 @@
 
     "Created: / 26-07-2011 / 10:22:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-browser'!
 
 useInPlaceSearchInBrowserLists
@@ -2156,7 +2023,6 @@
 
     "Created: / 28-07-2011 / 09:34:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-browser'!
 
 useInPlaceSearchInBrowserLists: aBoolean
@@ -2171,7 +2037,6 @@
 
     "Created: / 28-07-2011 / 09:35:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-browser'!
 
 webBrowserLikeLayout
@@ -2187,7 +2052,6 @@
 
     "Created: / 07-06-2011 / 14:33:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
-
 !UserPreferences methodsFor:'accessing-prefs-browser'!
 
 webBrowserLikeLayout: aBoolean
@@ -2203,7 +2067,11 @@
 
     "Created: / 07-06-2011 / 14:31:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
+!stx_libtool class methodsFor:'documentation'!
 
+extensionsVersion_CVS
+    ^ '$Header: /cvs/stx/stx/libtool/extensions.st,v 1.105 2013-04-14 12:40:00 cg Exp $'
+! !
 !stx_libtool class methodsFor:'documentation'!
 
 extensionsVersion_HG