Merged with /trunk jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Tue, 05 Jun 2012 15:49:00 +0100
branchjv
changeset 12254 b1237f76f501
parent 12253 6d3eedcdb4c1
child 12255 f3aabcc20321
Merged with /trunk
AbstractFileBrowser.st
AbstractSettingsApplication.st
ChangesBrowser.st
ContextInspectorView.st
DictionaryInspectorView.st
Diff3TextView.st
InspectorView.st
NewLauncher.st
PerforceSourceCodeManagementSettingsAppl.st
PerforceSourceCodeManagerUtilities.st
ProcessMonitorV2.st
SmalltalkCodeGeneratorTool.st
SystemBrowser.st
Tools__BrowserList.st
Tools__ClassCategoryList.st
Tools__ClassChecker.st
Tools__ClassGeneratorList.st
Tools__ClassList.st
Tools__CodeHighlightingService.st
Tools__CodeView2.st
Tools__FullMethodCategoryList.st
Tools__HierarchicalClassCategoryList.st
Tools__HierarchicalClassList.st
Tools__HierarchicalProjectList.st
Tools__ImplementingClassList.st
Tools__ImplementingMethodList.st
Tools__InheritanceClassList.st
Tools__InlineMessageDialog.st
Tools__MethodCategoryList.st
Tools__MethodList.st
Tools__NamespaceList.st
Tools__NavigationState.st
Tools__NavigatorCanvas.st
Tools__NavigatorModel.st
Tools__NewSystemBrowser.st
Tools__OrganizerCanvas.st
Tools__ProjectList.st
Tools__SearchDialog.st
Tools__SpecialCodeView.st
Tools__TagList.st
Tools__TagsBrowser.st
Tools__TestRunner2.st
Tools__TestRunnerEmbedded.st
Tools__VariableList.st
VersionDiffBrowser.st
WorkspaceApplication.st
stx_libtool.st
--- a/AbstractFileBrowser.st	Wed May 30 21:46:55 2012 +0100
+++ b/AbstractFileBrowser.st	Tue Jun 05 15:49:00 2012 +0100
@@ -516,14 +516,14 @@
 userPreferencesAspectList
     " list of all aspects that will be saved with save settings
       that aspects will be image consistent if the settings are saved in Launcher
-      dont forget to add a access methos in UserPreferences if you add a aspect here
+      don't forget to add a access methods in UserPreferences if you add a aspect here
     "
 
     ^ Dictionary 
         withKeysAndValues:#(
            viewDirsInContentsBrowser   true
            showDirectoryTree           true
-           showHiddenFiles             false
+           showHiddenFiles             true
            viewDescription             false
            viewDetails                 true
            viewDirectoryDescription    false
@@ -546,7 +546,7 @@
            useCodeView2InTools         true
       )
 
-    "Modified: / 06-10-2011 / 11:30:09 / cg"
+    "Modified: / 11-05-2012 / 09:22:04 / cg"
 ! !
 
 !AbstractFileBrowser class methodsFor:'help specs'!
@@ -9194,13 +9194,13 @@
 !AbstractFileBrowser class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/AbstractFileBrowser.st,v 1.493 2012/05/03 06:04:27 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/AbstractFileBrowser.st,v 1.494 2012/05/11 07:32:00 cg Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libtool/AbstractFileBrowser.st,v 1.493 2012/05/03 06:04:27 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libtool/AbstractFileBrowser.st,v 1.494 2012/05/11 07:32:00 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: AbstractFileBrowser.st 7990 2012-05-05 22:06:53Z vranyj1 $'
+    ^ '$Id: AbstractFileBrowser.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/AbstractSettingsApplication.st	Wed May 30 21:46:55 2012 +0100
+++ b/AbstractSettingsApplication.st	Tue Jun 05 15:49:00 2012 +0100
@@ -5553,14 +5553,25 @@
 !
 
 informationLabel
-    ^ resources 
+    |info|
+
+    info := resources 
         string:'HTTPSTARTINFO'
         default:
 'This dialog enables you to create (possibly multiple) HTTP Server processes. 
 (i.e. it is possible to serve multiple ports)
 
 Once created, select the individual server in the left tree, 
-configure its services, and finally start it up.'
+configure its services, and finally start it up.'.
+
+    self hasHTTPServerClass ifFalse:[
+        info := info , 
+                '\\' withCRs, 
+                (resources string:'ATTENTION: Disabled because HTTPServer class is missing.') allBold
+    ].
+    ^ info
+
+    "Modified: / 14-05-2012 / 12:35:46 / cg"
 !
 
 portNumberChannel
@@ -17734,13 +17745,13 @@
 !AbstractSettingsApplication class methodsFor:'documentation'!
 
 version
-    ^ '$Id: AbstractSettingsApplication.st 7969 2012-04-04 16:35:25Z vranyj1 $'
+    ^ '$Header: /cvs/stx/stx/libtool/AbstractSettingsApplication.st,v 1.438 2012/05/14 10:40:01 cg Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libtool/AbstractSettingsApplication.st,v 1.437 2012/03/20 20:54:16 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libtool/AbstractSettingsApplication.st,v 1.438 2012/05/14 10:40:01 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: AbstractSettingsApplication.st 7969 2012-04-04 16:35:25Z vranyj1 $'
-! !
+    ^ '$Id: AbstractSettingsApplication.st 8007 2012-06-05 14:49:00Z vranyj1 $'
+! !
--- a/ChangesBrowser.st	Wed May 30 21:46:55 2012 +0100
+++ b/ChangesBrowser.st	Tue Jun 05 15:49:00 2012 +0100
@@ -1615,6 +1615,1285 @@
 
 !ChangesBrowser methodsFor:'menu actions'!
 
+doApply
+    "user wants a change to be applied"
+
+    self withSelectedChangesDo:[:changeNr |
+        (self applyChange:changeNr) ifFalse:[
+            ^ self "/ cancel
+        ].
+        self autoSelect:(changeNr + 1)
+    ]
+!
+
+doApplyAll
+    "user wants all changes to be applied"
+
+    self withExecuteCursorDo:[
+        |lastNr "{ Class: SmallInteger }" |
+
+        self clearCodeView.
+        lastNr := self numberOfChanges.
+
+        "if we apply multiple changes, and an error occurs,
+         ask the user if all operations should be aborted..."
+        multipleApply := lastNr > 1.
+
+        1 to:lastNr do:[:changeNr |
+            changeListView setSelection:changeNr.
+            self applyChange:changeNr
+        ].
+        self autoSelectLast
+    ]
+
+    "Modified: 21.1.1997 / 22:26:30 / cg"
+!
+
+doApplyClassFromBeginning
+    "user wants all changes for this class from 1 to changeNr to be applied"
+
+    self withSingleSelectedChangeDo:[:changeNr |
+        |thisClassName classNameToApply lastChange
+         lastNr "{ Class: SmallInteger }" |
+
+        classNameToApply := self classNameOfChange:changeNr.
+        classNameToApply notNil ifTrue:[
+            self clearCodeView.
+
+            "if we apply multiple changes, and an error occurs,
+             ask the user if all operations should be aborted..."
+            multipleApply := changeNr ~= 1.
+
+            1 to:changeNr do:[:changeNr |
+                thisClassName := self classNameOfChange:changeNr.
+                thisClassName = classNameToApply ifTrue:[
+                    changeListView setSelection:changeNr.
+                    self applyChange:changeNr.
+                    lastChange := changeNr
+                ].
+            ].
+            self autoSelect:changeNr+1.
+        ]
+    ]
+
+    "Modified: 21.1.1997 / 22:26:04 / cg"
+!
+
+doApplyClassRest
+    "user wants all changes for this class from changeNr to be applied"
+
+    self withSingleSelectedChangeDo:[:changeNr |
+        |thisClassName classNameToApply lastChange
+         lastNr "{ Class: SmallInteger }" |
+
+        classNameToApply := self classNameOfChange:changeNr.
+        classNameToApply notNil ifTrue:[
+            self clearCodeView.
+
+            lastNr := self numberOfChanges.
+
+            "if we apply multiple changes, and an error occurs,
+             ask the user if all operations should be aborted..."
+            multipleApply := (lastNr - changeNr) > 1.
+
+            changeNr to:lastNr do:[:changeNr |
+                thisClassName := self classNameOfChange:changeNr.
+                thisClassName = classNameToApply ifTrue:[
+                    changeListView setSelection:changeNr.
+                    self applyChange:changeNr.
+                    lastChange := changeNr
+                ].
+            ].
+            self autoSelect:lastChange.
+        ]
+    ]
+
+    "Modified: 21.1.1997 / 22:26:04 / cg"
+!
+
+doApplyFromBeginning
+    "user wants all changes from 1 to changeNr to be applied"
+
+    self withSingleSelectedChangeDo:[:changeNr |
+        |lastNr "{ Class: SmallInteger }" |
+
+        self clearCodeView.
+
+        "if we apply multiple changes, and an error occurs,
+         ask the user if all operations should be aborted..."
+        multipleApply := changeNr ~= 1.
+
+        1 to:changeNr do:[:changeNr |
+            changeListView setSelection:changeNr.
+            self applyChange:changeNr
+        ].
+        self autoSelect:changeNr+1.
+    ]
+!
+
+doApplyRest
+    "apply all changes from changeNr to the end"
+
+    self withSingleSelectedChangeDo:[:changeNr |
+        |lastNr "{ Class: SmallInteger }" |
+
+        self clearCodeView.
+
+        lastNr := self numberOfChanges.
+
+        "if we apply multiple changes, and an error occurs,
+         ask the user if all operations should be aborted..."
+        multipleApply := (lastNr - changeNr) > 1.
+
+        changeNr to:lastNr do:[:changeNr |
+            changeListView setSelection:changeNr.
+            self applyChange:changeNr
+        ].
+        self autoSelect:self numberOfChanges.
+    ]
+
+    "Modified: 21.1.1997 / 22:25:29 / cg"
+!
+
+doApplyToConflictOrEnd
+    "apply all changes from changeNr to either a conflict (i.e. method exists)
+     or the end."
+
+    self withSingleSelectedChangeDo:[:changeNr |
+        |lastNr "{ Class: SmallInteger }"|
+
+        self clearCodeView.
+
+        lastNr := self numberOfChanges.
+
+        "if we apply multiple changes, and an error occurs,
+         ask the user if all operations should be aborted..."
+        multipleApply := (lastNr - changeNr) > 1.
+
+        changeNr to:lastNr do:[:changeNr |
+            | cls sel |
+            changeListView setSelection:changeNr.
+
+            ((cls := self classOfChange:changeNr ifAbsent:[:className| nil]) notNil
+            and:[(sel := self selectorOfMethodChange:changeNr) notNil])
+            ifTrue:[
+                (cls includesSelector:sel) ifTrue:[
+                    self autoSelect:changeNr.
+                    ^ self
+                ].
+            ].
+            self applyChange:changeNr
+        ].
+        self autoSelect:self numberOfChanges.
+    ]
+!
+
+doBrowse
+    "user wants a browser on the class of a change"
+
+    self withSingleSelectedChangeDo:[:changeNr |
+	|cls|
+
+	cls := self classOfChange:changeNr.
+	cls notNil ifTrue:[
+	    UserPreferences systemBrowserClass
+		openInClass:cls
+		selector:(self selectorOfMethodChange:changeNr)
+	]
+    ]
+!
+
+doBrowseImplementors
+    "open an implementors-browser"
+
+    |changeNr initial selector|
+
+    (changeNr := self theSingleSelection) notNil ifTrue:[
+	initial := self selectorOfMethodChange:changeNr.
+    ].
+
+    selector := Dialog
+		    request:'Selector to browse implementors of:'
+		    initialAnswer:(initial ? '').
+    selector size ~~ 0 ifTrue:[
+	UserPreferences systemBrowserClass
+	    browseImplementorsMatching:selector.
+    ]
+!
+
+doBrowseSenders
+    "user wants a browser on the class of a change"
+
+    |changeNr initial selector|
+
+    (changeNr := self theSingleSelection) notNil ifTrue:[
+	initial := self selectorOfMethodChange:changeNr.
+    ].
+
+    selector := Dialog
+		    request:'Selector to browse senders of:'
+		    initialAnswer:(initial ? '').
+    selector size ~~ 0 ifTrue:[
+	UserPreferences systemBrowserClass
+	    browseAllCallsOn:selector asSymbol.
+    ]
+!
+
+doCheckinAndDeleteClassAll
+    "first checkin the selected changes class then delete all changes
+     for it."
+
+    |classes answer logTitle checkinInfo|
+
+"/    self theSingleSelection isNil ifTrue:[
+"/        ^ self information:'Only possible if a single change is selected.'.
+"/    ].
+
+    self withExecuteCursorDo:[
+        classes := IdentitySet new.
+
+        self withSelectedChangesDo:[:changeNr |
+            | className class |
+
+            className := self classNameOfChange:changeNr.
+            className notNil ifTrue:[
+                class := Smalltalk classNamed:className.
+                class isNil ifTrue:[
+                    self error:'oops - no class: ', className mayProceed:true.
+                ].
+                class notNil ifTrue:[
+                    class := class theNonMetaclass.
+                    (classes includes:class) ifFalse:[
+                        class isPrivate ifTrue:[
+                            (classes includes:class owningClass) ifFalse:[
+                                answer := self confirmWithCancel:('This is a private class.\\CheckIn the owner ''%1'' and all of its private classes ?'
+                                                                    bindWith:class owningClass name allBold) withCRs.
+                                answer isNil ifTrue:[^ self].
+                                answer ifTrue:[
+                                    classes add:class owningClass
+                                ]
+                            ]
+                        ] ifFalse:[
+                            classes add:class
+                        ].
+                    ]
+                ]
+            ]
+        ].
+
+        classes size == 1 ifTrue:[
+            logTitle := classes first name.
+        ] ifFalse:[
+            logTitle := '%1 classes' bindWith:classes size.
+        ].
+        checkinInfo := SourceCodeManagerUtilities default
+                        getCheckinInfoFor:logTitle
+                        initialAnswer:nil.
+        checkinInfo isNil ifTrue:[^ self ].
+
+        changeListView setSelection:nil.
+        classes do:[:eachClass |
+            (SourceCodeManagerUtilities default checkinClass:eachClass withInfo:checkinInfo)
+                ifTrue:[
+                    self silentDeleteChangesForClassAndPrivateClasses:eachClass name
+                           from:1 to:(self numberOfChanges).
+                ]
+        ].
+        self setChangeList.
+    ]
+
+    "Modified: / 6.9.1995 / 17:11:16 / claus"
+    "Modified: / 17.11.2001 / 14:21:13 / cg"
+!
+
+doCompare
+    "compare change with current system version"
+
+    classesNotToBeAutoloaded removeAll.
+
+    self withSingleSelectedChangeDo:[:changeNr |
+        self withExecuteCursorDo:[
+            self compareChange:changeNr
+        ].
+        self newLabel:''
+    ].
+
+    "Modified: 24.2.1996 / 19:37:19 / cg"
+!
+
+doCompareAndCompress
+    "remove all changes, which are equivalent to the current image version"
+
+    |toDelete|
+
+    classesNotToBeAutoloaded removeAll.
+    toDelete := OrderedCollection new.
+    self withExecuteCursorDo:[
+        1 to:self numberOfChanges do:[:changeNr |
+            (self compareChange:changeNr showResult:false) == true ifTrue:[
+                toDelete add:changeNr
+            ]
+        ].
+    ].
+
+    toDelete reverseDo:[:changeNr |
+        self silentDeleteChange:changeNr.
+    ].
+    self setChangeList.
+    "
+     scroll back a bit, if we are left way behind the list
+    "
+    changeListView firstLineShown > self numberOfChanges ifTrue:[
+        changeListView makeLineVisible:self numberOfChanges
+    ].
+    self clearCodeView.
+
+    self newLabel:''.
+    classesNotToBeAutoloaded removeAll.
+!
+
+doCompress
+    "compress the change-set; this replaces multiple method-changes by the last
+     (i.e. the most recent) change"
+
+    self compressForClass:nil
+
+    "Modified: / 29.10.1997 / 01:03:26 / cg"
+!
+
+doCompressClass
+    "compress changes for the selected class.
+     this replaces multiple method-changes by the last (i.e. the most recent) change."
+
+    self theSingleSelection isNil ifTrue:[
+	^ self information:'Only possible if a single change is selected.'.
+    ].
+
+    self selectedClassNames do:[:classNameToCompress |
+	self compressForClass:classNameToCompress.
+    ]
+
+    "Created: / 29.10.1997 / 01:05:16 / cg"
+    "Modified: / 19.11.2001 / 21:55:17 / cg"
+!
+
+doCompressSelector
+    "compress changes for the selected class & selector.
+     this replaces multiple method-changes by the last (i.e. the most recent) change."
+
+    |classSelectorPairs|
+
+    self theSingleSelection isNil ifTrue:[
+	^ self information:'Only possible if a single change is selected.'.
+    ].
+
+    classSelectorPairs := Set new.
+    self withSelectedChangesDo:[:changeNr |
+	| classNameToCompress selector |
+
+	classNameToCompress := self classNameOfChange:changeNr.
+	classNameToCompress notNil ifTrue:[
+	    selector := self selectorOfMethodChange:changeNr.
+	    selector notNil ifTrue:[
+		classSelectorPairs add:(classNameToCompress -> selector).
+	    ]
+	]
+    ].
+
+    classSelectorPairs do:[:pair |
+	self compressForClass:pair key selector:pair value.
+    ]
+
+    "Created: / 19.11.2001 / 21:50:59 / cg"
+    "Modified: / 19.11.2001 / 22:10:08 / cg"
+!
+
+doDelete
+    "delete currently selected change(s)"
+
+    |rangeEnd rangeStart firstDeleted|
+
+    changeListView selection size <= 5 ifTrue:[
+	self withSelectedChangesReverseDo:[:changeNr |
+	    self deleteChange:changeNr.
+	    self autoSelectOrEnd:changeNr
+	].
+	^ self
+    ].
+
+    self withSelectedChangesReverseDo:[:changeNr |
+	rangeEnd isNil ifTrue:[
+	    rangeEnd := rangeStart := changeNr
+	] ifFalse:[
+	    (changeNr = (rangeEnd + 1)) ifTrue:[
+		rangeEnd := changeNr
+	    ] ifFalse:[
+		(changeNr = (rangeStart - 1)) ifTrue:[
+		    rangeStart := changeNr
+		] ifFalse:[
+		    self deleteChangesFrom:rangeStart to:rangeEnd.
+		    firstDeleted := (firstDeleted ? rangeStart) min:rangeStart.
+		    rangeStart := rangeEnd := nil.
+		].
+	    ].
+	].
+    ].
+    rangeStart notNil ifTrue:[
+	self deleteChangesFrom:rangeStart to:rangeEnd.
+	firstDeleted := (firstDeleted ? rangeStart) min:rangeStart.
+    ].
+    self autoSelectOrEnd:firstDeleted
+!
+
+doDeleteAndSelectPrevious
+    "delete currently selected change(s)"
+
+    self withSelectedChangesReverseDo:[:changeNr |
+	self deleteChange:changeNr.
+	self autoSelectOrEnd:changeNr-1
+    ]
+!
+
+doDeleteClassAll
+    "delete all changes with same class as currently selected change"
+
+    |classNamesToDelete lastChangeNr overAllNumDeletedBefore|
+
+    lastChangeNr := -1.
+    classNamesToDelete := Set new.
+    self withSelectedChangesDo:[:changeNr |
+	|classNameToDelete|
+
+	classNameToDelete := self classNameOfChange:changeNr.
+	classNameToDelete notNil ifTrue:[
+	    classNamesToDelete add:classNameToDelete.
+	].
+	lastChangeNr := lastChangeNr max:changeNr.
+    ].
+
+    overAllNumDeletedBefore := 0.
+    changeListView setSelection:nil.
+
+    self withExecuteCursorDo:[
+	classNamesToDelete do:[:classNameToDelete |
+	    |numDeletedBefore|
+
+	    self silentDeleteChangesFor:classNameToDelete
+				   from:lastChangeNr
+				     to:(self numberOfChanges).
+	    numDeletedBefore := self
+				   silentDeleteChangesFor:classNameToDelete
+				   from:1
+				   to:(lastChangeNr-1).
+	    lastChangeNr := lastChangeNr - numDeletedBefore.
+	    overAllNumDeletedBefore := overAllNumDeletedBefore + numDeletedBefore.
+	].
+    ].
+
+    self setChangeList.
+    self autoSelectOrEnd:lastChangeNr
+
+    "Created: / 13.12.1995 / 16:07:14 / cg"
+    "Modified: / 28.1.1998 / 20:42:14 / cg"
+!
+
+doDeleteClassAndPrivateClassesAll
+    "delete all changes with same class and private classes
+     as currently selected change"
+
+    |lastChangeNr classNamesToDelete overAllNumDeletedBefore|
+
+    lastChangeNr := -1.
+    classNamesToDelete := Set new.
+    self withSelectedChangesDo:[:changeNr |
+	|classNameToDelete|
+
+	classNameToDelete := self ownerClassNameOfChange:changeNr.
+	classNameToDelete notNil ifTrue:[
+	    classNamesToDelete add:classNameToDelete.
+	].
+	lastChangeNr := lastChangeNr max:changeNr.
+    ].
+
+    overAllNumDeletedBefore := 0.
+    changeListView setSelection:nil.
+
+    self withExecuteCursorDo:[
+	classNamesToDelete do:[:classNameToDelete |
+	    | changeNr numDeletedBefore|
+
+	    classNameToDelete notNil ifTrue:[
+		changeListView setSelection:nil.
+		self silentDeleteChangesForClassAndPrivateClasses:classNameToDelete
+				       from:lastChangeNr
+					 to:(self numberOfChanges).
+		numDeletedBefore := self
+				       silentDeleteChangesForClassAndPrivateClasses:classNameToDelete
+				       from:1
+				       to:(lastChangeNr-1).
+		lastChangeNr := lastChangeNr - numDeletedBefore.
+		overAllNumDeletedBefore := overAllNumDeletedBefore + numDeletedBefore.
+	    ]
+	]
+    ].
+    self setChangeList.
+    self autoSelectOrEnd:lastChangeNr
+
+    "Created: / 13.12.1995 / 16:07:14 / cg"
+    "Modified: / 28.1.1998 / 20:42:14 / cg"
+!
+
+doDeleteClassFromBeginning
+    "delete changes with same class as currently selected change from the beginning
+     up to the selected change.
+     Useful to get rid of obsolete changes before a fileout or checkin entry."
+
+    self withSingleSelectedChangeDo:[:changeNr |
+	|classNameToDelete prevSelection numDeleted|
+
+	classNameToDelete := self classNameOfChange:changeNr.
+	classNameToDelete notNil ifTrue:[
+	    prevSelection := changeNr.
+	    changeListView setSelection:nil.
+	    numDeleted := self
+				silentDeleteChangesFor:classNameToDelete
+				from:1
+				to:changeNr.
+	    self setChangeList.
+	    self autoSelectOrEnd:(changeNr + 1 - numDeleted)
+	]
+    ].
+
+    "Created: 13.12.1995 / 15:41:58 / cg"
+    "Modified: 25.5.1996 / 12:26:34 / cg"
+!
+
+doDeleteClassRest
+    "delete rest of changes with same class as currently selected change"
+
+    self withSingleSelectedChangeDo:[:changeNr |
+	| classNameToDelete |
+
+	classNameToDelete := self classNameOfChange:changeNr.
+	classNameToDelete notNil ifTrue:[
+	    changeListView setSelection:nil.
+	    self silentDeleteChangesFor:classNameToDelete
+				   from:changeNr
+				     to:(self numberOfChanges).
+	    self setChangeList.
+	    self autoSelectOrEnd:changeNr
+	]
+    ]
+
+    "Modified: / 18.5.1998 / 14:25:07 / cg"
+!
+
+doDeleteClassSelectorAll
+    "delete all changes with same class and selector as currently selected change"
+
+    |classNameSelectorPairsToDelete lastChangeNr overAllNumDeletedBefore|
+
+    lastChangeNr := -1.
+    classNameSelectorPairsToDelete := Set new.
+    self withSelectedChangesDo:[:changeNr |
+	|className selector|
+
+	className := self classNameOfChange:changeNr.
+	selector := self selectorOfMethodChange:changeNr.
+	selector notNil ifTrue:[
+	    (className notNil and:[selector notNil]) ifTrue:[
+		classNameSelectorPairsToDelete add:(className -> selector).
+	    ]
+	].
+	lastChangeNr := lastChangeNr max:changeNr.
+    ].
+
+    overAllNumDeletedBefore := 0.
+    changeListView setSelection:nil.
+
+    self withExecuteCursorDo:[
+	classNameSelectorPairsToDelete do:[:pair |
+	    |numDeletedBefore className selector|
+
+	    className := pair key.
+	    selector  := pair value.
+	    self silentDeleteChangesFor:className selector:selector
+				   from:lastChangeNr
+				     to:(self numberOfChanges).
+	    numDeletedBefore := self
+				   silentDeleteChangesFor:className selector:selector
+				   from:1
+				   to:(lastChangeNr-1).
+	    lastChangeNr := lastChangeNr - numDeletedBefore.
+	    overAllNumDeletedBefore := overAllNumDeletedBefore + numDeletedBefore.
+	].
+    ].
+
+    self setChangeList.
+    self autoSelectOrEnd:lastChangeNr
+
+    "Created: / 13.12.1995 / 16:07:14 / cg"
+    "Modified: / 28.1.1998 / 20:42:14 / cg"
+!
+
+doDeleteFromBeginning
+    "delete all changes from 1 to the current"
+
+    self withSingleSelectedChangeDo:[:changeNr |
+	self deleteChangesFrom:1 to:changeNr.
+	self clearCodeView.
+	self autoSelectOrEnd:changeNr
+    ]
+!
+
+doDeleteRest
+    "delete all changes from current to the end"
+
+    self withSingleSelectedChangeDo:[:changeNr |
+	self deleteChangesFrom:changeNr to:(self numberOfChanges).
+	self clearCodeView.
+	self autoSelectOrEnd:changeNr-1
+    ]
+!
+
+doFileoutAndDeleteClassAll
+    "first fileOut the selected changes class then delete all changes
+     for it."
+
+    self withSingleSelectedChangeDo:[:changeNr |
+	| className class |
+
+	className := self classNameOfChange:changeNr.
+	className notNil ifTrue:[
+	    class := Smalltalk classNamed:className.
+	    class notNil ifTrue:[
+		Class fileOutErrorSignal handle:[:ex |
+		    self warn:('fileout failed: ' , ex description).
+		] do:[
+		    class fileOut.
+		    self doDeleteClassAll
+		].
+	    ].
+
+	].
+    ]
+
+    "Modified: 6.9.1995 / 17:11:16 / claus"
+!
+
+doMakePatch
+    "user wants a change to be made a patch
+     - copy it over to the patches file"
+
+    self withSelectedChangesDo:[:changeNr |
+	self makeChangeAPatch:changeNr.
+	self autoSelect:(changeNr + 1)
+    ]
+!
+
+doMakePermanent
+    "user wants a change to be made permanent
+     - rewrite the source file where this change has to go"
+
+    |yesNoBox|
+
+    (self theSingleSelection) isNil ifTrue:[
+        ^ self information:'Only possible if a single change is selected.'.
+    ].
+
+    yesNoBox := YesNoBox new.
+    yesNoBox title:(resources string:'Warning: this operation cannot be undone').
+    yesNoBox okText:(resources string:'continue') noText:(resources string:'abort').
+    yesNoBox okAction:[   |changeNr|
+
+                          changeNr := self theSingleSelection.
+                          changeNr notNil ifTrue:[
+                              self makeChangePermanent:changeNr.
+                              self autoSelect:(changeNr + 1)
+                          ]
+                      ].
+    yesNoBox showAtPointer.
+    yesNoBox destroy
+
+    "Modified: 7.1.1997 / 23:03:33 / cg"
+!
+
+doSave
+    "user wants a change to be appended to a file"
+
+    |fileName|
+
+    self withSelectedChangesDo:[:changeNr |
+        fileName := Dialog
+                        requestFileNameForSave:(resources string:'Append change to:')
+                        default:(lastSaveFileName ? '')
+                        ok:(resources string:'Append')
+                        abort:(resources string:'Abort')
+                        pattern:'*.chg'.
+
+        fileName notNil ifTrue:[
+            lastSaveFileName := fileName.
+            self withCursor:(Cursor write) do:[
+                self appendChange:changeNr toFile:fileName.
+            ].
+            self autoSelect:(changeNr + 1)
+        ].
+    ]
+
+    "Modified: / 27-10-2010 / 11:30:07 / cg"
+!
+
+doSaveClass
+    "user wants changes for some class from current to end to be appended to a file"
+
+    (self theSingleSelection) isNil ifTrue:[
+	^ self information:'Only possible if a single change is selected.'.
+    ].
+    self doSaveClassFrom:1
+!
+
+doSaveClassAll
+    "user wants changes for some class from current to end to be appended to a file"
+
+    (self theSingleSelection) isNil ifTrue:[
+	^ self information:'Only possible if a single change is selected.'.
+    ].
+    self doSaveClassFrom:1
+!
+
+doSaveClassFrom:startNr
+    "user wants changes from current to end to be appended to a file"
+
+    |changeNr classNameToSave|
+
+    (changeNr := self theSingleSelection) isNil ifTrue:[
+	^ self information:'Only possible if a single change is selected.'.
+    ].
+    classNameToSave := self classNameOfChange:changeNr.
+    classNameToSave notNil ifTrue:[
+	self saveClass:classNameToSave from:startNr
+    ]
+!
+
+doSaveClassRest
+    "user wants changes for some class from current to end to be appended to a file"
+
+    |changeNr|
+
+    (changeNr := self theSingleSelection) isNil ifTrue:[
+        ^ self information:'Only possible if a single change is selected.'.
+    ].
+    self doSaveClassFrom:changeNr.
+
+    changeListView setSelection:changeNr.
+    "/ self changeSelection:changeNr.
+!
+
+doSaveRest
+    "user wants changes from current to end to be appended to a file"
+
+    |changeNr fileName|
+
+    (changeNr := self theSingleSelection) isNil ifTrue:[
+        ^ self information:(resources string:'Only possible if a single change is selected.').
+    ].
+
+    fileName := Dialog
+                    requestFileNameForSave:(resources string:'Append changes to:')
+                    default:(lastSaveFileName ? '')
+                    ok:(resources string:'Append')
+                    abort:(resources string:'Abort')
+                    pattern:'*.chg'.
+
+    fileName notNil ifTrue:[
+        lastSaveFileName := fileName.
+        self withCursor:(Cursor write) do:[
+            changeNr to:(self numberOfChanges) do:[:changeNr |
+                changeListView setSelection:changeNr.
+                (self appendChange:changeNr toFile:fileName) ifFalse:[
+                    ^ self
+                ]
+            ]
+        ]
+    ]
+
+    "Modified: / 27-10-2010 / 11:30:37 / cg"
+!
+
+doUpdate
+    "reread the changes-file"
+
+    self readChangesFileInBackground:true.
+    self newLabel:''.
+    realized ifTrue:[
+	self setChangeList.
+    ]
+!
+
+doWriteBack
+    "write back the list onto the changes file"
+
+    anyChanges ifTrue:[
+        (self writeBackChanges) ifTrue:[
+            realized ifTrue:[
+                self readChangesFile.
+                realized ifTrue:[
+                    self setChangeList
+                ]
+            ]
+        ]
+    ]
+
+    "Modified: 5.9.1996 / 17:19:46 / cg"
+!
+
+findClass
+    "findClass menu action: let user enter a classes name, and select the next change for that class"
+
+    |current|
+
+    changeNrShown notNil ifTrue:[
+        current := self classNameOfChange:changeNrShown.
+    ].
+
+    self
+        askForSearch:'Class to search for:'
+        initialAnswer:current
+        thenSearchUsing:[:searchString :changeNr |
+                            |thisClassName|
+
+                            thisClassName := self classNameOfChange:changeNr.
+                            thisClassName notNil
+                            and:[
+                                (thisClassName sameAs: searchString)
+                                or:[searchString includesMatchCharacters and:[searchString match:thisClassName ignoreCase:true]]]
+                        ]
+        onCancel:[^ self].
+
+    lastSearchType := #class.
+    changeNrShown == 0 ifTrue:[changeNrShown := nil].
+!
+
+findFirstForClass
+    "findNextForClass menu action: select the next change for the selected changes class"
+
+    self findNextForClassStartingAt:1
+
+    "Created: / 20-11-2006 / 16:37:56 / cg"
+!
+
+findLastForClass
+    "findPreviousForClass menu action: select the previous change for the selected changes class"
+
+    self findPreviousForClassStartingAt:(self numberOfChanges)
+
+    "Created: / 20-11-2006 / 16:39:15 / cg"
+!
+
+findLastSnapshot
+    "findLastSnapshot menu action: select the last change which is for a snapShot-image save action"
+
+    "/ lastSearchType := #snapshot.
+
+    self 
+        findPreviousForWhich: [:changeNr | self changeIsSnapShotInfo:changeNr ]
+        startingAt:(self numberOfChanges)
+
+    "Created: / 06-10-2006 / 11:03:39 / cg"
+!
+
+findNext
+    "findNext menu action: select the next change.
+     Searches for what the last search was for; i.e. either same class or same selector"
+
+    lastSearchType == #selector ifTrue:[
+	^ self findNextForSelector
+    ].
+    lastSearchType == #snapshot ifTrue:[
+	^ self findNextSnapshot
+    ].
+    lastSearchType == #string ifTrue:[
+	^ self findNextForString
+    ].
+    lastSearchType == #difference ifTrue:[
+	^ self findNextDifference
+    ].
+
+    ^ self findNextForClass
+
+    "Created: / 18.6.1998 / 22:15:00 / cg"
+    "Modified: / 18.6.1998 / 22:15:25 / cg"
+!
+
+findNextDifference
+    lastSearchType := #difference.
+    changeNrShown isNil ifTrue:[^ self].
+
+    self findNextForWhich:[:changeNr |
+	    (self compareChange:changeNr showResult:false) == true ifTrue:[
+		"/ same
+		false
+	    ] ifFalse:[
+		"/ different
+		true
+	    ]
+	]
+!
+
+findNextForClass
+    "findNextForClass menu action: select the next change for the selected changes class"
+
+    self findNextForClassStartingAt: changeNrShown + 1
+
+    "Modified: / 20-11-2006 / 16:37:49 / cg"
+!
+
+findNextForClassStartingAt:startNr
+    "findNextForClass menu action: select the next change for the selected changes class"
+
+    |cls|
+
+    lastSearchType := #class.
+    changeNrShown isNil ifTrue:[^ self].
+
+    cls := self classNameOfChange:changeNrShown.
+    cls isNil ifTrue:[^ self].
+
+    self 
+        findNextForWhich:[:changeNr |
+                |thisClass|
+
+                thisClass := self classNameOfChange:changeNr.
+                (thisClass = cls
+                or:[cls includesMatchCharacters and:[cls match:thisClass]])]
+        startingAt:startNr
+
+    "Created: / 20-11-2006 / 16:37:37 / cg"
+!
+
+findNextForSelector
+    "findNextForSelector menu action: select the next change for the selected changes selector"
+
+    |sel|
+
+    lastSearchType := #selector.
+    changeNrShown isNil ifTrue:[^ self].
+
+    sel := self selectorOfMethodChange:changeNrShown.
+    sel isNil ifTrue:[^ self].
+
+    self findNextForWhich: [:changeNr |
+		|thisSelector|
+
+		thisSelector := self selectorOfMethodChange:changeNr.
+		(thisSelector = sel or:[sel includesMatchCharacters and:[sel match:thisSelector]])
+	]
+
+!
+
+findNextForString
+    lastSearchString isNil ifTrue:[
+	^ self findString
+    ].
+    self findNextWithString:lastSearchString
+!
+
+findNextForWhich:aBlock
+    "helper: select the next change for which aBlock evaluates to true"
+
+    ^ self findNextForWhich:aBlock startingAt:changeNrShown + 1
+
+    "Modified: / 20-11-2006 / 16:34:23 / cg"
+!
+
+findNextForWhich:aBlock startingAt:changeNrToStartSearch
+    "helper: select the next change for which aBlock evaluates to true"
+
+    ^ self     
+        findNextOrPrevious:#next 
+        forWhich:aBlock startingAt:changeNrToStartSearch
+
+    "Created: / 20-11-2006 / 16:34:06 / cg"
+!
+
+findNextOrPrevious:direction forWhich:aBlock startingAt:changeNrToStartSearch
+    "helper: find and select the next or previous change for which aBlock evaluates to true"
+
+    self withCursor:Cursor questionMark do:[
+        Object userInterruptSignal handle:[:ex |
+            self beep.
+            ^ 0
+        ] do:[
+            |increment nr lastNr|
+
+            increment := (direction == #previous) ifTrue:[-1] ifFalse:[1].
+            lastNr := self numberOfChanges.
+            nr := changeNrToStartSearch.
+            [ (direction == #previous and:[nr >= 1])
+              or:[ direction == #next and:[ nr <= lastNr]] 
+            ] whileTrue:[
+                (aBlock value:nr) ifTrue:[
+                    changeListView setSelection:nr.
+                    self changeSelection:nr.
+                    ^ nr
+                ].
+                nr := nr + increment.
+            ].
+        ]
+    ].
+    self showNotFound.
+    self windowGroup sensor flushKeyboard. "/ avoid multiple beeps, in case of type ahead
+    ^ 0
+
+    "Created: / 08-03-2012 / 11:57:26 / cg"
+!
+
+findNextSnapshot
+    "findNextSnapshot menu action: select the next change which is for a snapShot-image save action"
+
+    lastSearchType := #snapshot.
+    changeNrShown isNil ifTrue:[^ self].
+
+    self findNextForWhich: [:changeNr | self changeIsSnapShotInfo:changeNr ]
+!
+
+findNextWithString:searchString
+    lastSearchType := #string.
+
+    lastSearchString := searchString.
+
+    changeNrShown isNil ifTrue:[
+	changeNrShown := 0.
+    ].
+
+    self findNextForWhich:
+	[:changeNr |
+	    |s|
+
+	    s := self sourceOfMethodChange:changeNr.
+	    s notNil and:[
+		(searchString includesMatchCharacters not
+			    and:[(s findString:searchString) ~~ 0])
+		or:[ searchString includesMatchCharacters
+			    and:[('*' , searchString , '*') match:s ]]]
+	].
+
+    changeNrShown == 0 ifTrue:[changeNrShown := nil].
+
+    codeView setSearchPattern:searchString.
+    codeView
+	searchFwd:searchString
+	ignoreCase:false
+	startingAtLine:1 col:0
+	ifAbsent:nil.
+
+!
+
+findPrevious
+    "findPrevious menu action: select the previous change.
+     Searches for what the last search was for; i.e. either same class or same selector"
+
+    lastSearchType == #selector ifTrue:[
+	^ self findPreviousForSelector
+    ].
+    lastSearchType == #snapshot ifTrue:[
+	^ self findPreviousSnapshot
+    ].
+    lastSearchType == #string ifTrue:[
+	^ self findPreviousForString
+    ].
+    lastSearchType == #difference ifTrue:[
+	^ self findPreviousDifference
+    ].
+
+    ^ self findPreviousForClass
+
+    "Created: / 18.6.1998 / 22:15:15 / cg"
+!
+
+findPreviousDifference
+    lastSearchType := #difference.
+    changeNrShown isNil ifTrue:[^ self].
+
+    self findPreviousForWhich:[:changeNr |
+	    (self compareChange:changeNr showResult:false) == true ifTrue:[
+		"/ same
+		false
+	    ] ifFalse:[
+		"/ different
+		true
+	    ]
+	]
+!
+
+findPreviousForClass
+    "findPreviousForClass menu action: select the previous change for the selected changes class"
+
+    self findPreviousForClassStartingAt:(changeNrShown - 1)
+
+    "Modified: / 20-11-2006 / 16:39:04 / cg"
+!
+
+findPreviousForClassStartingAt:startNr
+    "findPreviousForClass menu action: select the previous change for the selected changes class"
+
+    |cls|
+
+    lastSearchType := #class.
+    changeNrShown isNil ifTrue:[^ self].
+
+    cls := self classNameOfChange:changeNrShown.
+    cls isNil ifTrue:[^ self].
+
+    self 
+        findPreviousForWhich:
+            [:changeNr |
+                    |thisClass|
+
+                    thisClass := self classNameOfChange:changeNr.
+                    (thisClass = cls
+                    or:[cls includesMatchCharacters and:[cls match:thisClass]])]
+        startingAt:startNr
+
+    "Created: / 20-11-2006 / 16:38:37 / cg"
+!
+
+findPreviousForSelector
+    "findPreviousForSelector menu action: select the previous change for the selected changes selector"
+
+    |sel|
+
+    lastSearchType := #selector.
+    changeNrShown isNil ifTrue:[^ self].
+
+    sel := self selectorOfMethodChange:changeNrShown.
+    sel isNil ifTrue:[^ self].
+
+    self findPreviousForWhich:
+	[:changeNr |
+		|thisSelector|
+
+		thisSelector := self selectorOfMethodChange:changeNr.
+		(thisSelector = sel
+		or:[sel includesMatchCharacters and:[sel match:thisSelector]])
+	]
+
+!
+
+findPreviousForString
+    lastSearchString isNil ifTrue:[
+	^ self findString
+    ].
+    self findPreviousWithString:lastSearchString
+!
+
+findPreviousForWhich:aBlock
+    "helper: select the previous change for which aBlock evaluates to true"
+
+    ^ self findPreviousForWhich:aBlock startingAt:(changeNrShown - 1)
+
+    "Modified: / 06-10-2006 / 11:01:38 / cg"
+!
+
+findPreviousForWhich:aBlock startingAt:changeNrToStartSearch
+    "helper: select the previous change for which aBlock evaluates to true"
+
+    ^ self     
+        findNextOrPrevious:#previous 
+        forWhich:aBlock startingAt:changeNrToStartSearch
+
+    "Created: / 06-10-2006 / 11:01:09 / cg"
+!
+
+findPreviousSnapshot
+    "findPreviousSnapshot menu action: select the previous change which is for a snapShot-image save action"
+
+    lastSearchType := #snapshot.
+    changeNrShown isNil ifTrue:[^ self].
+
+    self findPreviousForWhich: [:changeNr | self changeIsSnapShotInfo:changeNr ]
+!
+
+findPreviousWithString:searchString
+    lastSearchType := #string.
+
+    lastSearchString := searchString.
+
+    changeNrShown isNil ifTrue:[
+	changeNrShown := 0.
+    ].
+
+    self findPreviousForWhich:
+	[:changeNr |
+	    |s includesMatchCharacters|
+
+	    includesMatchCharacters := searchString includesMatchCharacters.
+	    s := self sourceOfMethodChange:changeNr.
+	    s notNil and:[
+		(includesMatchCharacters not and:[(s findString:searchString) ~~ 0])
+		or:[includesMatchCharacters and:[('*' , searchString , '*') match:s ]]]
+	].
+
+    changeNrShown == 0 ifTrue:[changeNrShown := nil].
+
+    codeView setSearchPattern:searchString.
+    codeView
+	searchFwd:searchString
+	ignoreCase:false
+	startingAtLine:1 col:0
+	ifAbsent:nil.
+
+!
+
+findSelector
+    "findSelector menu action: let user enter a selector, and select the next change for that selector"
+
+    |current|
+
+    changeNrShown notNil ifTrue:[
+	current := self selectorOfMethodChange:changeNrShown.
+    ].
+
+    self
+	askForSearch:'Selector to search for:'
+	initialAnswer:current
+	thenSearchUsing:[:searchString :changeNr |
+			    |thisSelector|
+
+			    thisSelector := self selectorOfMethodChange:changeNr.
+			    (thisSelector = searchString
+			    or:[searchString includesMatchCharacters and:[searchString match:thisSelector]])
+			]
+	onCancel:[^ self].
+
+    lastSearchType := #selector.
+    changeNrShown == 0 ifTrue:[changeNrShown := nil].
+!
+
+findString
+    |searchString directionHolder|
+
+    lastSearchType := #string.
+
+    searchString := codeView selection.
+    searchString size == 0 ifTrue:[searchString := lastSearchString].
+
+    searchString := self
+	askForSearchString:'String to search for:'
+	initialAnswer:(searchString ? '')
+	directionInto:(directionHolder := ValueHolder new).
+
+    searchString size == 0 ifTrue:[
+	^ self
+    ].
+
+    directionHolder value == #backward ifTrue:[
+	self findPreviousWithString:searchString.
+    ] ifFalse:[
+	self findNextWithString:searchString.
+    ]
+!
+
 ignorePublicPrivateCategories:aBoolean
     UserPreferences current ignorePublicPrivateCategories:aBoolean
 
@@ -1659,6 +2938,75 @@
     settingsApp openWindow.
 !
 
+setEnforcedNameSpace
+    |nsName listOfKnownNameSpaces keepAsDefaultHolder|
+
+    listOfKnownNameSpaces := Set new.
+    NameSpace
+        allNameSpaces
+            do:[:eachNameSpace |
+                listOfKnownNameSpaces add:eachNameSpace name
+            ].
+    listOfKnownNameSpaces := listOfKnownNameSpaces asOrderedCollection sort.
+
+    Dialog aboutToOpenBoxNotificationSignal handle:[:ex |
+        |box|
+
+        keepAsDefaultHolder := true asValue.
+        box := ex parameter.
+        box verticalPanel
+            add:((CheckBox 
+                    label:(resources string:'Use this as default in the future')) 
+                    model:keepAsDefaultHolder).
+        ex proceed.
+    ] do:[
+        nsName := Dialog
+                request:'When applying, new classes are created in nameSpace:'
+                initialAnswer:(enforcedNameSpace ? LastEnforcedNameSpace ? Class nameSpaceQuerySignal query name)
+                list:listOfKnownNameSpaces.
+    ].
+    nsName isNil ifTrue:[^ self].
+
+    (nsName isEmpty or:[nsName = 'Smalltalk']) ifTrue:[
+        applyInOriginalNameSpace value:true.
+        LastEnforcedNameSpace := enforcedNameSpace := nil.
+    ] ifFalse:[
+        applyInOriginalNameSpace value:false.
+        LastEnforcedNameSpace := enforcedNameSpace := NameSpace name:nsName.
+        autoCompare value ifTrue:[
+            self doUpdate
+        ].
+    ].
+    KeepEnforcedNameSpace := keepAsDefaultHolder value.
+    codeView namespaceForDoits:enforcedNameSpace.
+    diffView textViews do:[:each | each namespaceForDoits:enforcedNameSpace].
+
+    "Modified: / 08-05-2012 / 14:04:19 / cg"
+!
+
+setEnforcedPackage
+    |pkg listOfKnownPackages|
+
+    listOfKnownPackages := Set new.
+    Smalltalk allClassesDo:[:eachClass |
+				|package|
+
+				package := eachClass package.
+				package size > 0 ifTrue:[
+				    listOfKnownPackages add:package
+				]
+			   ].
+    listOfKnownPackages := listOfKnownPackages asOrderedCollection sort.
+
+    pkg := Dialog
+		request:'When applying, changes go into package:'
+		initialAnswer:(enforcedPackage ? Class packageQuerySignal query)
+		list:listOfKnownPackages.
+    pkg size ~~ 0 ifTrue:[
+	enforcedPackage := pkg
+    ]
+!
+
 showAboutSTX
     ToolApplicationModel openAboutSTX
 ! !
@@ -4377,838 +5725,6 @@
     ^ cls
 !
 
-doApply
-    "user wants a change to be applied"
-
-    self withSelectedChangesDo:[:changeNr |
-        (self applyChange:changeNr) ifFalse:[
-            ^ self "/ cancel
-        ].
-        self autoSelect:(changeNr + 1)
-    ]
-!
-
-doApplyAll
-    "user wants all changes to be applied"
-
-    self withExecuteCursorDo:[
-        |lastNr "{ Class: SmallInteger }" |
-
-        self clearCodeView.
-        lastNr := self numberOfChanges.
-
-        "if we apply multiple changes, and an error occurs,
-         ask the user if all operations should be aborted..."
-        multipleApply := lastNr > 1.
-
-        1 to:lastNr do:[:changeNr |
-            changeListView setSelection:changeNr.
-            self applyChange:changeNr
-        ].
-        self autoSelectLast
-    ]
-
-    "Modified: 21.1.1997 / 22:26:30 / cg"
-!
-
-doApplyClassFromBeginning
-    "user wants all changes for this class from 1 to changeNr to be applied"
-
-    self withSingleSelectedChangeDo:[:changeNr |
-        |thisClassName classNameToApply lastChange
-         lastNr "{ Class: SmallInteger }" |
-
-        classNameToApply := self classNameOfChange:changeNr.
-        classNameToApply notNil ifTrue:[
-            self clearCodeView.
-
-            "if we apply multiple changes, and an error occurs,
-             ask the user if all operations should be aborted..."
-            multipleApply := changeNr ~= 1.
-
-            1 to:changeNr do:[:changeNr |
-                thisClassName := self classNameOfChange:changeNr.
-                thisClassName = classNameToApply ifTrue:[
-                    changeListView setSelection:changeNr.
-                    self applyChange:changeNr.
-                    lastChange := changeNr
-                ].
-            ].
-            self autoSelect:changeNr+1.
-        ]
-    ]
-
-    "Modified: 21.1.1997 / 22:26:04 / cg"
-!
-
-doApplyClassRest
-    "user wants all changes for this class from changeNr to be applied"
-
-    self withSingleSelectedChangeDo:[:changeNr |
-        |thisClassName classNameToApply lastChange
-         lastNr "{ Class: SmallInteger }" |
-
-        classNameToApply := self classNameOfChange:changeNr.
-        classNameToApply notNil ifTrue:[
-            self clearCodeView.
-
-            lastNr := self numberOfChanges.
-
-            "if we apply multiple changes, and an error occurs,
-             ask the user if all operations should be aborted..."
-            multipleApply := (lastNr - changeNr) > 1.
-
-            changeNr to:lastNr do:[:changeNr |
-                thisClassName := self classNameOfChange:changeNr.
-                thisClassName = classNameToApply ifTrue:[
-                    changeListView setSelection:changeNr.
-                    self applyChange:changeNr.
-                    lastChange := changeNr
-                ].
-            ].
-            self autoSelect:lastChange.
-        ]
-    ]
-
-    "Modified: 21.1.1997 / 22:26:04 / cg"
-!
-
-doApplyFromBeginning
-    "user wants all changes from 1 to changeNr to be applied"
-
-    self withSingleSelectedChangeDo:[:changeNr |
-        |lastNr "{ Class: SmallInteger }" |
-
-        self clearCodeView.
-
-        "if we apply multiple changes, and an error occurs,
-         ask the user if all operations should be aborted..."
-        multipleApply := changeNr ~= 1.
-
-        1 to:changeNr do:[:changeNr |
-            changeListView setSelection:changeNr.
-            self applyChange:changeNr
-        ].
-        self autoSelect:changeNr+1.
-    ]
-!
-
-doApplyRest
-    "apply all changes from changeNr to the end"
-
-    self withSingleSelectedChangeDo:[:changeNr |
-        |lastNr "{ Class: SmallInteger }" |
-
-        self clearCodeView.
-
-        lastNr := self numberOfChanges.
-
-        "if we apply multiple changes, and an error occurs,
-         ask the user if all operations should be aborted..."
-        multipleApply := (lastNr - changeNr) > 1.
-
-        changeNr to:lastNr do:[:changeNr |
-            changeListView setSelection:changeNr.
-            self applyChange:changeNr
-        ].
-        self autoSelect:self numberOfChanges.
-    ]
-
-    "Modified: 21.1.1997 / 22:25:29 / cg"
-!
-
-doApplyToConflictOrEnd
-    "apply all changes from changeNr to either a conflict (i.e. method exists)
-     or the end."
-
-    self withSingleSelectedChangeDo:[:changeNr |
-        |lastNr "{ Class: SmallInteger }"|
-
-        self clearCodeView.
-
-        lastNr := self numberOfChanges.
-
-        "if we apply multiple changes, and an error occurs,
-         ask the user if all operations should be aborted..."
-        multipleApply := (lastNr - changeNr) > 1.
-
-        changeNr to:lastNr do:[:changeNr |
-            | cls sel |
-            changeListView setSelection:changeNr.
-
-            ((cls := self classOfChange:changeNr ifAbsent:[:className| nil]) notNil
-            and:[(sel := self selectorOfMethodChange:changeNr) notNil])
-            ifTrue:[
-                (cls includesSelector:sel) ifTrue:[
-                    self autoSelect:changeNr.
-                    ^ self
-                ].
-            ].
-            self applyChange:changeNr
-        ].
-        self autoSelect:self numberOfChanges.
-    ]
-!
-
-doBrowse
-    "user wants a browser on the class of a change"
-
-    self withSingleSelectedChangeDo:[:changeNr |
-	|cls|
-
-	cls := self classOfChange:changeNr.
-	cls notNil ifTrue:[
-	    UserPreferences systemBrowserClass
-		openInClass:cls
-		selector:(self selectorOfMethodChange:changeNr)
-	]
-    ]
-!
-
-doBrowseImplementors
-    "open an implementors-browser"
-
-    |changeNr initial selector|
-
-    (changeNr := self theSingleSelection) notNil ifTrue:[
-	initial := self selectorOfMethodChange:changeNr.
-    ].
-
-    selector := Dialog
-		    request:'Selector to browse implementors of:'
-		    initialAnswer:(initial ? '').
-    selector size ~~ 0 ifTrue:[
-	UserPreferences systemBrowserClass
-	    browseImplementorsMatching:selector.
-    ]
-!
-
-doBrowseSenders
-    "user wants a browser on the class of a change"
-
-    |changeNr initial selector|
-
-    (changeNr := self theSingleSelection) notNil ifTrue:[
-	initial := self selectorOfMethodChange:changeNr.
-    ].
-
-    selector := Dialog
-		    request:'Selector to browse senders of:'
-		    initialAnswer:(initial ? '').
-    selector size ~~ 0 ifTrue:[
-	UserPreferences systemBrowserClass
-	    browseAllCallsOn:selector asSymbol.
-    ]
-!
-
-doCheckinAndDeleteClassAll
-    "first checkin the selected changes class then delete all changes
-     for it."
-
-    |classes answer logTitle checkinInfo|
-
-"/    self theSingleSelection isNil ifTrue:[
-"/        ^ self information:'Only possible if a single change is selected.'.
-"/    ].
-
-    self withExecuteCursorDo:[
-        classes := IdentitySet new.
-
-        self withSelectedChangesDo:[:changeNr |
-            | className class |
-
-            className := self classNameOfChange:changeNr.
-            className notNil ifTrue:[
-                class := Smalltalk classNamed:className.
-                class isNil ifTrue:[
-                    self error:'oops - no class: ', className mayProceed:true.
-                ].
-                class notNil ifTrue:[
-                    class := class theNonMetaclass.
-                    (classes includes:class) ifFalse:[
-                        class isPrivate ifTrue:[
-                            (classes includes:class owningClass) ifFalse:[
-                                answer := self confirmWithCancel:('This is a private class.\\CheckIn the owner ''%1'' and all of its private classes ?'
-                                                                    bindWith:class owningClass name allBold) withCRs.
-                                answer isNil ifTrue:[^ self].
-                                answer ifTrue:[
-                                    classes add:class owningClass
-                                ]
-                            ]
-                        ] ifFalse:[
-                            classes add:class
-                        ].
-                    ]
-                ]
-            ]
-        ].
-
-        classes size == 1 ifTrue:[
-            logTitle := classes first name.
-        ] ifFalse:[
-            logTitle := '%1 classes' bindWith:classes size.
-        ].
-        checkinInfo := SourceCodeManagerUtilities default
-                        getCheckinInfoFor:logTitle
-                        initialAnswer:nil.
-        checkinInfo isNil ifTrue:[^ self ].
-
-        changeListView setSelection:nil.
-        classes do:[:eachClass |
-            (SourceCodeManagerUtilities default checkinClass:eachClass withInfo:checkinInfo)
-                ifTrue:[
-                    self silentDeleteChangesForClassAndPrivateClasses:eachClass name
-                           from:1 to:(self numberOfChanges).
-                ]
-        ].
-        self setChangeList.
-    ]
-
-    "Modified: / 6.9.1995 / 17:11:16 / claus"
-    "Modified: / 17.11.2001 / 14:21:13 / cg"
-!
-
-doCompare
-    "compare change with current system version"
-
-    classesNotToBeAutoloaded removeAll.
-
-    self withSingleSelectedChangeDo:[:changeNr |
-        self withExecuteCursorDo:[
-            self compareChange:changeNr
-        ].
-        self newLabel:''
-    ].
-
-    "Modified: 24.2.1996 / 19:37:19 / cg"
-!
-
-doCompareAndCompress
-    "remove all changes, which are equivalent to the current image version"
-
-    |toDelete|
-
-    classesNotToBeAutoloaded removeAll.
-    toDelete := OrderedCollection new.
-    self withExecuteCursorDo:[
-        1 to:self numberOfChanges do:[:changeNr |
-            (self compareChange:changeNr showResult:false) == true ifTrue:[
-                toDelete add:changeNr
-            ]
-        ].
-    ].
-
-    toDelete reverseDo:[:changeNr |
-        self silentDeleteChange:changeNr.
-    ].
-    self setChangeList.
-    "
-     scroll back a bit, if we are left way behind the list
-    "
-    changeListView firstLineShown > self numberOfChanges ifTrue:[
-        changeListView makeLineVisible:self numberOfChanges
-    ].
-    self clearCodeView.
-
-    self newLabel:''.
-    classesNotToBeAutoloaded removeAll.
-!
-
-doCompress
-    "compress the change-set; this replaces multiple method-changes by the last
-     (i.e. the most recent) change"
-
-    self compressForClass:nil
-
-    "Modified: / 29.10.1997 / 01:03:26 / cg"
-!
-
-doCompressClass
-    "compress changes for the selected class.
-     this replaces multiple method-changes by the last (i.e. the most recent) change."
-
-    self theSingleSelection isNil ifTrue:[
-	^ self information:'Only possible if a single change is selected.'.
-    ].
-
-    self selectedClassNames do:[:classNameToCompress |
-	self compressForClass:classNameToCompress.
-    ]
-
-    "Created: / 29.10.1997 / 01:05:16 / cg"
-    "Modified: / 19.11.2001 / 21:55:17 / cg"
-!
-
-doCompressSelector
-    "compress changes for the selected class & selector.
-     this replaces multiple method-changes by the last (i.e. the most recent) change."
-
-    |classSelectorPairs|
-
-    self theSingleSelection isNil ifTrue:[
-	^ self information:'Only possible if a single change is selected.'.
-    ].
-
-    classSelectorPairs := Set new.
-    self withSelectedChangesDo:[:changeNr |
-	| classNameToCompress selector |
-
-	classNameToCompress := self classNameOfChange:changeNr.
-	classNameToCompress notNil ifTrue:[
-	    selector := self selectorOfMethodChange:changeNr.
-	    selector notNil ifTrue:[
-		classSelectorPairs add:(classNameToCompress -> selector).
-	    ]
-	]
-    ].
-
-    classSelectorPairs do:[:pair |
-	self compressForClass:pair key selector:pair value.
-    ]
-
-    "Created: / 19.11.2001 / 21:50:59 / cg"
-    "Modified: / 19.11.2001 / 22:10:08 / cg"
-!
-
-doDelete
-    "delete currently selected change(s)"
-
-    |rangeEnd rangeStart firstDeleted|
-
-    changeListView selection size <= 5 ifTrue:[
-	self withSelectedChangesReverseDo:[:changeNr |
-	    self deleteChange:changeNr.
-	    self autoSelectOrEnd:changeNr
-	].
-	^ self
-    ].
-
-    self withSelectedChangesReverseDo:[:changeNr |
-	rangeEnd isNil ifTrue:[
-	    rangeEnd := rangeStart := changeNr
-	] ifFalse:[
-	    (changeNr = (rangeEnd + 1)) ifTrue:[
-		rangeEnd := changeNr
-	    ] ifFalse:[
-		(changeNr = (rangeStart - 1)) ifTrue:[
-		    rangeStart := changeNr
-		] ifFalse:[
-		    self deleteChangesFrom:rangeStart to:rangeEnd.
-		    firstDeleted := (firstDeleted ? rangeStart) min:rangeStart.
-		    rangeStart := rangeEnd := nil.
-		].
-	    ].
-	].
-    ].
-    rangeStart notNil ifTrue:[
-	self deleteChangesFrom:rangeStart to:rangeEnd.
-	firstDeleted := (firstDeleted ? rangeStart) min:rangeStart.
-    ].
-    self autoSelectOrEnd:firstDeleted
-!
-
-doDeleteAndSelectPrevious
-    "delete currently selected change(s)"
-
-    self withSelectedChangesReverseDo:[:changeNr |
-	self deleteChange:changeNr.
-	self autoSelectOrEnd:changeNr-1
-    ]
-!
-
-doDeleteClassAll
-    "delete all changes with same class as currently selected change"
-
-    |classNamesToDelete lastChangeNr overAllNumDeletedBefore|
-
-    lastChangeNr := -1.
-    classNamesToDelete := Set new.
-    self withSelectedChangesDo:[:changeNr |
-	|classNameToDelete|
-
-	classNameToDelete := self classNameOfChange:changeNr.
-	classNameToDelete notNil ifTrue:[
-	    classNamesToDelete add:classNameToDelete.
-	].
-	lastChangeNr := lastChangeNr max:changeNr.
-    ].
-
-    overAllNumDeletedBefore := 0.
-    changeListView setSelection:nil.
-
-    self withExecuteCursorDo:[
-	classNamesToDelete do:[:classNameToDelete |
-	    |numDeletedBefore|
-
-	    self silentDeleteChangesFor:classNameToDelete
-				   from:lastChangeNr
-				     to:(self numberOfChanges).
-	    numDeletedBefore := self
-				   silentDeleteChangesFor:classNameToDelete
-				   from:1
-				   to:(lastChangeNr-1).
-	    lastChangeNr := lastChangeNr - numDeletedBefore.
-	    overAllNumDeletedBefore := overAllNumDeletedBefore + numDeletedBefore.
-	].
-    ].
-
-    self setChangeList.
-    self autoSelectOrEnd:lastChangeNr
-
-    "Created: / 13.12.1995 / 16:07:14 / cg"
-    "Modified: / 28.1.1998 / 20:42:14 / cg"
-!
-
-doDeleteClassAndPrivateClassesAll
-    "delete all changes with same class and private classes
-     as currently selected change"
-
-    |lastChangeNr classNamesToDelete overAllNumDeletedBefore|
-
-    lastChangeNr := -1.
-    classNamesToDelete := Set new.
-    self withSelectedChangesDo:[:changeNr |
-	|classNameToDelete|
-
-	classNameToDelete := self ownerClassNameOfChange:changeNr.
-	classNameToDelete notNil ifTrue:[
-	    classNamesToDelete add:classNameToDelete.
-	].
-	lastChangeNr := lastChangeNr max:changeNr.
-    ].
-
-    overAllNumDeletedBefore := 0.
-    changeListView setSelection:nil.
-
-    self withExecuteCursorDo:[
-	classNamesToDelete do:[:classNameToDelete |
-	    | changeNr numDeletedBefore|
-
-	    classNameToDelete notNil ifTrue:[
-		changeListView setSelection:nil.
-		self silentDeleteChangesForClassAndPrivateClasses:classNameToDelete
-				       from:lastChangeNr
-					 to:(self numberOfChanges).
-		numDeletedBefore := self
-				       silentDeleteChangesForClassAndPrivateClasses:classNameToDelete
-				       from:1
-				       to:(lastChangeNr-1).
-		lastChangeNr := lastChangeNr - numDeletedBefore.
-		overAllNumDeletedBefore := overAllNumDeletedBefore + numDeletedBefore.
-	    ]
-	]
-    ].
-    self setChangeList.
-    self autoSelectOrEnd:lastChangeNr
-
-    "Created: / 13.12.1995 / 16:07:14 / cg"
-    "Modified: / 28.1.1998 / 20:42:14 / cg"
-!
-
-doDeleteClassFromBeginning
-    "delete changes with same class as currently selected change from the beginning
-     up to the selected change.
-     Useful to get rid of obsolete changes before a fileout or checkin entry."
-
-    self withSingleSelectedChangeDo:[:changeNr |
-	|classNameToDelete prevSelection numDeleted|
-
-	classNameToDelete := self classNameOfChange:changeNr.
-	classNameToDelete notNil ifTrue:[
-	    prevSelection := changeNr.
-	    changeListView setSelection:nil.
-	    numDeleted := self
-				silentDeleteChangesFor:classNameToDelete
-				from:1
-				to:changeNr.
-	    self setChangeList.
-	    self autoSelectOrEnd:(changeNr + 1 - numDeleted)
-	]
-    ].
-
-    "Created: 13.12.1995 / 15:41:58 / cg"
-    "Modified: 25.5.1996 / 12:26:34 / cg"
-!
-
-doDeleteClassRest
-    "delete rest of changes with same class as currently selected change"
-
-    self withSingleSelectedChangeDo:[:changeNr |
-	| classNameToDelete |
-
-	classNameToDelete := self classNameOfChange:changeNr.
-	classNameToDelete notNil ifTrue:[
-	    changeListView setSelection:nil.
-	    self silentDeleteChangesFor:classNameToDelete
-				   from:changeNr
-				     to:(self numberOfChanges).
-	    self setChangeList.
-	    self autoSelectOrEnd:changeNr
-	]
-    ]
-
-    "Modified: / 18.5.1998 / 14:25:07 / cg"
-!
-
-doDeleteClassSelectorAll
-    "delete all changes with same class and selector as currently selected change"
-
-    |classNameSelectorPairsToDelete lastChangeNr overAllNumDeletedBefore|
-
-    lastChangeNr := -1.
-    classNameSelectorPairsToDelete := Set new.
-    self withSelectedChangesDo:[:changeNr |
-	|className selector|
-
-	className := self classNameOfChange:changeNr.
-	selector := self selectorOfMethodChange:changeNr.
-	selector notNil ifTrue:[
-	    (className notNil and:[selector notNil]) ifTrue:[
-		classNameSelectorPairsToDelete add:(className -> selector).
-	    ]
-	].
-	lastChangeNr := lastChangeNr max:changeNr.
-    ].
-
-    overAllNumDeletedBefore := 0.
-    changeListView setSelection:nil.
-
-    self withExecuteCursorDo:[
-	classNameSelectorPairsToDelete do:[:pair |
-	    |numDeletedBefore className selector|
-
-	    className := pair key.
-	    selector  := pair value.
-	    self silentDeleteChangesFor:className selector:selector
-				   from:lastChangeNr
-				     to:(self numberOfChanges).
-	    numDeletedBefore := self
-				   silentDeleteChangesFor:className selector:selector
-				   from:1
-				   to:(lastChangeNr-1).
-	    lastChangeNr := lastChangeNr - numDeletedBefore.
-	    overAllNumDeletedBefore := overAllNumDeletedBefore + numDeletedBefore.
-	].
-    ].
-
-    self setChangeList.
-    self autoSelectOrEnd:lastChangeNr
-
-    "Created: / 13.12.1995 / 16:07:14 / cg"
-    "Modified: / 28.1.1998 / 20:42:14 / cg"
-!
-
-doDeleteFromBeginning
-    "delete all changes from 1 to the current"
-
-    self withSingleSelectedChangeDo:[:changeNr |
-	self deleteChangesFrom:1 to:changeNr.
-	self clearCodeView.
-	self autoSelectOrEnd:changeNr
-    ]
-!
-
-doDeleteRest
-    "delete all changes from current to the end"
-
-    self withSingleSelectedChangeDo:[:changeNr |
-	self deleteChangesFrom:changeNr to:(self numberOfChanges).
-	self clearCodeView.
-	self autoSelectOrEnd:changeNr-1
-    ]
-!
-
-doFileoutAndDeleteClassAll
-    "first fileOut the selected changes class then delete all changes
-     for it."
-
-    self withSingleSelectedChangeDo:[:changeNr |
-	| className class |
-
-	className := self classNameOfChange:changeNr.
-	className notNil ifTrue:[
-	    class := Smalltalk classNamed:className.
-	    class notNil ifTrue:[
-		Class fileOutErrorSignal handle:[:ex |
-		    self warn:('fileout failed: ' , ex description).
-		] do:[
-		    class fileOut.
-		    self doDeleteClassAll
-		].
-	    ].
-
-	].
-    ]
-
-    "Modified: 6.9.1995 / 17:11:16 / claus"
-!
-
-doMakePatch
-    "user wants a change to be made a patch
-     - copy it over to the patches file"
-
-    self withSelectedChangesDo:[:changeNr |
-	self makeChangeAPatch:changeNr.
-	self autoSelect:(changeNr + 1)
-    ]
-!
-
-doMakePermanent
-    "user wants a change to be made permanent
-     - rewrite the source file where this change has to go"
-
-    |yesNoBox|
-
-    (self theSingleSelection) isNil ifTrue:[
-        ^ self information:'Only possible if a single change is selected.'.
-    ].
-
-    yesNoBox := YesNoBox new.
-    yesNoBox title:(resources string:'Warning: this operation cannot be undone').
-    yesNoBox okText:(resources string:'continue') noText:(resources string:'abort').
-    yesNoBox okAction:[   |changeNr|
-
-                          changeNr := self theSingleSelection.
-                          changeNr notNil ifTrue:[
-                              self makeChangePermanent:changeNr.
-                              self autoSelect:(changeNr + 1)
-                          ]
-                      ].
-    yesNoBox showAtPointer.
-    yesNoBox destroy
-
-    "Modified: 7.1.1997 / 23:03:33 / cg"
-!
-
-doSave
-    "user wants a change to be appended to a file"
-
-    |fileName|
-
-    self withSelectedChangesDo:[:changeNr |
-        fileName := Dialog
-                        requestFileNameForSave:(resources string:'Append change to:')
-                        default:(lastSaveFileName ? '')
-                        ok:(resources string:'Append')
-                        abort:(resources string:'Abort')
-                        pattern:'*.chg'.
-
-        fileName notNil ifTrue:[
-            lastSaveFileName := fileName.
-            self withCursor:(Cursor write) do:[
-                self appendChange:changeNr toFile:fileName.
-            ].
-            self autoSelect:(changeNr + 1)
-        ].
-    ]
-
-    "Modified: / 27-10-2010 / 11:30:07 / cg"
-!
-
-doSaveClass
-    "user wants changes for some class from current to end to be appended to a file"
-
-    (self theSingleSelection) isNil ifTrue:[
-	^ self information:'Only possible if a single change is selected.'.
-    ].
-    self doSaveClassFrom:1
-!
-
-doSaveClassAll
-    "user wants changes for some class from current to end to be appended to a file"
-
-    (self theSingleSelection) isNil ifTrue:[
-	^ self information:'Only possible if a single change is selected.'.
-    ].
-    self doSaveClassFrom:1
-!
-
-doSaveClassFrom:startNr
-    "user wants changes from current to end to be appended to a file"
-
-    |changeNr classNameToSave|
-
-    (changeNr := self theSingleSelection) isNil ifTrue:[
-	^ self information:'Only possible if a single change is selected.'.
-    ].
-    classNameToSave := self classNameOfChange:changeNr.
-    classNameToSave notNil ifTrue:[
-	self saveClass:classNameToSave from:startNr
-    ]
-!
-
-doSaveClassRest
-    "user wants changes for some class from current to end to be appended to a file"
-
-    |changeNr|
-
-    (changeNr := self theSingleSelection) isNil ifTrue:[
-        ^ self information:'Only possible if a single change is selected.'.
-    ].
-    self doSaveClassFrom:changeNr.
-
-    changeListView setSelection:changeNr.
-    "/ self changeSelection:changeNr.
-!
-
-doSaveRest
-    "user wants changes from current to end to be appended to a file"
-
-    |changeNr fileName|
-
-    (changeNr := self theSingleSelection) isNil ifTrue:[
-        ^ self information:(resources string:'Only possible if a single change is selected.').
-    ].
-
-    fileName := Dialog
-                    requestFileNameForSave:(resources string:'Append changes to:')
-                    default:(lastSaveFileName ? '')
-                    ok:(resources string:'Append')
-                    abort:(resources string:'Abort')
-                    pattern:'*.chg'.
-
-    fileName notNil ifTrue:[
-        lastSaveFileName := fileName.
-        self withCursor:(Cursor write) do:[
-            changeNr to:(self numberOfChanges) do:[:changeNr |
-                changeListView setSelection:changeNr.
-                (self appendChange:changeNr toFile:fileName) ifFalse:[
-                    ^ self
-                ]
-            ]
-        ]
-    ]
-
-    "Modified: / 27-10-2010 / 11:30:37 / cg"
-!
-
-doUpdate
-    "reread the changes-file"
-
-    self readChangesFileInBackground:true.
-    self newLabel:''.
-    realized ifTrue:[
-	self setChangeList.
-    ]
-!
-
-doWriteBack
-    "write back the list onto the changes file"
-
-    anyChanges ifTrue:[
-        (self writeBackChanges) ifTrue:[
-            realized ifTrue:[
-                self readChangesFile.
-                realized ifTrue:[
-                    self setChangeList
-                ]
-            ]
-        ]
-    ]
-
-    "Modified: 5.9.1996 / 17:19:46 / cg"
-!
-
 doubleClickOnChange:lineNr
     "action performed when a change-list entry is doubleClicked"
 
@@ -5217,453 +5733,6 @@
     "Created: / 6.2.1998 / 13:08:49 / cg"
 !
 
-findClass
-    "findClass menu action: let user enter a classes name, and select the next change for that class"
-
-    |current|
-
-    changeNrShown notNil ifTrue:[
-        current := self classNameOfChange:changeNrShown.
-    ].
-
-    self
-        askForSearch:'Class to search for:'
-        initialAnswer:current
-        thenSearchUsing:[:searchString :changeNr |
-                            |thisClassName|
-
-                            thisClassName := self classNameOfChange:changeNr.
-                            thisClassName notNil
-                            and:[
-                                (thisClassName sameAs: searchString)
-                                or:[searchString includesMatchCharacters and:[searchString match:thisClassName ignoreCase:true]]]
-                        ]
-        onCancel:[^ self].
-
-    lastSearchType := #class.
-    changeNrShown == 0 ifTrue:[changeNrShown := nil].
-!
-
-findFirstForClass
-    "findNextForClass menu action: select the next change for the selected changes class"
-
-    self findNextForClassStartingAt:1
-
-    "Created: / 20-11-2006 / 16:37:56 / cg"
-!
-
-findLastForClass
-    "findPreviousForClass menu action: select the previous change for the selected changes class"
-
-    self findPreviousForClassStartingAt:(self numberOfChanges)
-
-    "Created: / 20-11-2006 / 16:39:15 / cg"
-!
-
-findLastSnapshot
-    "findLastSnapshot menu action: select the last change which is for a snapShot-image save action"
-
-    "/ lastSearchType := #snapshot.
-
-    self 
-        findPreviousForWhich: [:changeNr | self changeIsSnapShotInfo:changeNr ]
-        startingAt:(self numberOfChanges)
-
-    "Created: / 06-10-2006 / 11:03:39 / cg"
-!
-
-findNext
-    "findNext menu action: select the next change.
-     Searches for what the last search was for; i.e. either same class or same selector"
-
-    lastSearchType == #selector ifTrue:[
-	^ self findNextForSelector
-    ].
-    lastSearchType == #snapshot ifTrue:[
-	^ self findNextSnapshot
-    ].
-    lastSearchType == #string ifTrue:[
-	^ self findNextForString
-    ].
-    lastSearchType == #difference ifTrue:[
-	^ self findNextDifference
-    ].
-
-    ^ self findNextForClass
-
-    "Created: / 18.6.1998 / 22:15:00 / cg"
-    "Modified: / 18.6.1998 / 22:15:25 / cg"
-!
-
-findNextDifference
-    lastSearchType := #difference.
-    changeNrShown isNil ifTrue:[^ self].
-
-    self findNextForWhich:[:changeNr |
-	    (self compareChange:changeNr showResult:false) == true ifTrue:[
-		"/ same
-		false
-	    ] ifFalse:[
-		"/ different
-		true
-	    ]
-	]
-!
-
-findNextForClass
-    "findNextForClass menu action: select the next change for the selected changes class"
-
-    self findNextForClassStartingAt: changeNrShown + 1
-
-    "Modified: / 20-11-2006 / 16:37:49 / cg"
-!
-
-findNextForClassStartingAt:startNr
-    "findNextForClass menu action: select the next change for the selected changes class"
-
-    |cls|
-
-    lastSearchType := #class.
-    changeNrShown isNil ifTrue:[^ self].
-
-    cls := self classNameOfChange:changeNrShown.
-    cls isNil ifTrue:[^ self].
-
-    self 
-        findNextForWhich:[:changeNr |
-                |thisClass|
-
-                thisClass := self classNameOfChange:changeNr.
-                (thisClass = cls
-                or:[cls includesMatchCharacters and:[cls match:thisClass]])]
-        startingAt:startNr
-
-    "Created: / 20-11-2006 / 16:37:37 / cg"
-!
-
-findNextForSelector
-    "findNextForSelector menu action: select the next change for the selected changes selector"
-
-    |sel|
-
-    lastSearchType := #selector.
-    changeNrShown isNil ifTrue:[^ self].
-
-    sel := self selectorOfMethodChange:changeNrShown.
-    sel isNil ifTrue:[^ self].
-
-    self findNextForWhich: [:changeNr |
-		|thisSelector|
-
-		thisSelector := self selectorOfMethodChange:changeNr.
-		(thisSelector = sel or:[sel includesMatchCharacters and:[sel match:thisSelector]])
-	]
-
-!
-
-findNextForString
-    lastSearchString isNil ifTrue:[
-	^ self findString
-    ].
-    self findNextWithString:lastSearchString
-!
-
-findNextForWhich:aBlock
-    "helper: select the next change for which aBlock evaluates to true"
-
-    ^ self findNextForWhich:aBlock startingAt:changeNrShown + 1
-
-    "Modified: / 20-11-2006 / 16:34:23 / cg"
-!
-
-findNextForWhich:aBlock startingAt:changeNrToStartSearch
-    "helper: select the next change for which aBlock evaluates to true"
-
-    ^ self     
-        findNextOrPrevious:#next 
-        forWhich:aBlock startingAt:changeNrToStartSearch
-
-    "Created: / 20-11-2006 / 16:34:06 / cg"
-!
-
-findNextOrPrevious:direction forWhich:aBlock startingAt:changeNrToStartSearch
-    "helper: find and select the next or previous change for which aBlock evaluates to true"
-
-    self withCursor:Cursor questionMark do:[
-        Object userInterruptSignal handle:[:ex |
-            self beep.
-            ^ 0
-        ] do:[
-            |increment nr lastNr|
-
-            increment := (direction == #previous) ifTrue:[-1] ifFalse:[1].
-            lastNr := self numberOfChanges.
-            nr := changeNrToStartSearch.
-            [ (direction == #previous and:[nr >= 1])
-              or:[ direction == #next and:[ nr <= lastNr]] 
-            ] whileTrue:[
-                (aBlock value:nr) ifTrue:[
-                    changeListView setSelection:nr.
-                    self changeSelection:nr.
-                    ^ nr
-                ].
-                nr := nr + increment.
-            ].
-        ]
-    ].
-    self showNotFound.
-    self windowGroup sensor flushKeyboard. "/ avoid multiple beeps, in case of type ahead
-    ^ 0
-
-    "Created: / 08-03-2012 / 11:57:26 / cg"
-!
-
-findNextSnapshot
-    "findNextSnapshot menu action: select the next change which is for a snapShot-image save action"
-
-    lastSearchType := #snapshot.
-    changeNrShown isNil ifTrue:[^ self].
-
-    self findNextForWhich: [:changeNr | self changeIsSnapShotInfo:changeNr ]
-!
-
-findNextWithString:searchString
-    lastSearchType := #string.
-
-    lastSearchString := searchString.
-
-    changeNrShown isNil ifTrue:[
-	changeNrShown := 0.
-    ].
-
-    self findNextForWhich:
-	[:changeNr |
-	    |s|
-
-	    s := self sourceOfMethodChange:changeNr.
-	    s notNil and:[
-		(searchString includesMatchCharacters not
-			    and:[(s findString:searchString) ~~ 0])
-		or:[ searchString includesMatchCharacters
-			    and:[('*' , searchString , '*') match:s ]]]
-	].
-
-    changeNrShown == 0 ifTrue:[changeNrShown := nil].
-
-    codeView setSearchPattern:searchString.
-    codeView
-	searchFwd:searchString
-	ignoreCase:false
-	startingAtLine:1 col:0
-	ifAbsent:nil.
-
-!
-
-findPrevious
-    "findPrevious menu action: select the previous change.
-     Searches for what the last search was for; i.e. either same class or same selector"
-
-    lastSearchType == #selector ifTrue:[
-	^ self findPreviousForSelector
-    ].
-    lastSearchType == #snapshot ifTrue:[
-	^ self findPreviousSnapshot
-    ].
-    lastSearchType == #string ifTrue:[
-	^ self findPreviousForString
-    ].
-    lastSearchType == #difference ifTrue:[
-	^ self findPreviousDifference
-    ].
-
-    ^ self findPreviousForClass
-
-    "Created: / 18.6.1998 / 22:15:15 / cg"
-!
-
-findPreviousDifference
-    lastSearchType := #difference.
-    changeNrShown isNil ifTrue:[^ self].
-
-    self findPreviousForWhich:[:changeNr |
-	    (self compareChange:changeNr showResult:false) == true ifTrue:[
-		"/ same
-		false
-	    ] ifFalse:[
-		"/ different
-		true
-	    ]
-	]
-!
-
-findPreviousForClass
-    "findPreviousForClass menu action: select the previous change for the selected changes class"
-
-    self findPreviousForClassStartingAt:(changeNrShown - 1)
-
-    "Modified: / 20-11-2006 / 16:39:04 / cg"
-!
-
-findPreviousForClassStartingAt:startNr
-    "findPreviousForClass menu action: select the previous change for the selected changes class"
-
-    |cls|
-
-    lastSearchType := #class.
-    changeNrShown isNil ifTrue:[^ self].
-
-    cls := self classNameOfChange:changeNrShown.
-    cls isNil ifTrue:[^ self].
-
-    self 
-        findPreviousForWhich:
-            [:changeNr |
-                    |thisClass|
-
-                    thisClass := self classNameOfChange:changeNr.
-                    (thisClass = cls
-                    or:[cls includesMatchCharacters and:[cls match:thisClass]])]
-        startingAt:startNr
-
-    "Created: / 20-11-2006 / 16:38:37 / cg"
-!
-
-findPreviousForSelector
-    "findPreviousForSelector menu action: select the previous change for the selected changes selector"
-
-    |sel|
-
-    lastSearchType := #selector.
-    changeNrShown isNil ifTrue:[^ self].
-
-    sel := self selectorOfMethodChange:changeNrShown.
-    sel isNil ifTrue:[^ self].
-
-    self findPreviousForWhich:
-	[:changeNr |
-		|thisSelector|
-
-		thisSelector := self selectorOfMethodChange:changeNr.
-		(thisSelector = sel
-		or:[sel includesMatchCharacters and:[sel match:thisSelector]])
-	]
-
-!
-
-findPreviousForString
-    lastSearchString isNil ifTrue:[
-	^ self findString
-    ].
-    self findPreviousWithString:lastSearchString
-!
-
-findPreviousForWhich:aBlock
-    "helper: select the previous change for which aBlock evaluates to true"
-
-    ^ self findPreviousForWhich:aBlock startingAt:(changeNrShown - 1)
-
-    "Modified: / 06-10-2006 / 11:01:38 / cg"
-!
-
-findPreviousForWhich:aBlock startingAt:changeNrToStartSearch
-    "helper: select the previous change for which aBlock evaluates to true"
-
-    ^ self     
-        findNextOrPrevious:#previous 
-        forWhich:aBlock startingAt:changeNrToStartSearch
-
-    "Created: / 06-10-2006 / 11:01:09 / cg"
-!
-
-findPreviousSnapshot
-    "findPreviousSnapshot menu action: select the previous change which is for a snapShot-image save action"
-
-    lastSearchType := #snapshot.
-    changeNrShown isNil ifTrue:[^ self].
-
-    self findPreviousForWhich: [:changeNr | self changeIsSnapShotInfo:changeNr ]
-!
-
-findPreviousWithString:searchString
-    lastSearchType := #string.
-
-    lastSearchString := searchString.
-
-    changeNrShown isNil ifTrue:[
-	changeNrShown := 0.
-    ].
-
-    self findPreviousForWhich:
-	[:changeNr |
-	    |s includesMatchCharacters|
-
-	    includesMatchCharacters := searchString includesMatchCharacters.
-	    s := self sourceOfMethodChange:changeNr.
-	    s notNil and:[
-		(includesMatchCharacters not and:[(s findString:searchString) ~~ 0])
-		or:[includesMatchCharacters and:[('*' , searchString , '*') match:s ]]]
-	].
-
-    changeNrShown == 0 ifTrue:[changeNrShown := nil].
-
-    codeView setSearchPattern:searchString.
-    codeView
-	searchFwd:searchString
-	ignoreCase:false
-	startingAtLine:1 col:0
-	ifAbsent:nil.
-
-!
-
-findSelector
-    "findSelector menu action: let user enter a selector, and select the next change for that selector"
-
-    |current|
-
-    changeNrShown notNil ifTrue:[
-	current := self selectorOfMethodChange:changeNrShown.
-    ].
-
-    self
-	askForSearch:'Selector to search for:'
-	initialAnswer:current
-	thenSearchUsing:[:searchString :changeNr |
-			    |thisSelector|
-
-			    thisSelector := self selectorOfMethodChange:changeNr.
-			    (thisSelector = searchString
-			    or:[searchString includesMatchCharacters and:[searchString match:thisSelector]])
-			]
-	onCancel:[^ self].
-
-    lastSearchType := #selector.
-    changeNrShown == 0 ifTrue:[changeNrShown := nil].
-!
-
-findString
-    |searchString directionHolder|
-
-    lastSearchType := #string.
-
-    searchString := codeView selection.
-    searchString size == 0 ifTrue:[searchString := lastSearchString].
-
-    searchString := self
-	askForSearchString:'String to search for:'
-	initialAnswer:(searchString ? '')
-	directionInto:(directionHolder := ValueHolder new).
-
-    searchString size == 0 ifTrue:[
-	^ self
-    ].
-
-    directionHolder value == #backward ifTrue:[
-	self findPreviousWithString:searchString.
-    ] ifFalse:[
-	self findNextWithString:searchString.
-    ]
-!
-
 noChangesAllowed
     "show a warning that changes cannot be changed"
 
@@ -5709,73 +5778,6 @@
 self halt
 
     "Created: / 03-01-2012 / 15:26:36 / cg"
-!
-
-setEnforcedNameSpace
-    |nsName listOfKnownNameSpaces keepAsDefaultHolder|
-
-    listOfKnownNameSpaces := Set new.
-    NameSpace
-        allNameSpaces
-            do:[:eachNameSpace |
-                listOfKnownNameSpaces add:eachNameSpace name
-            ].
-    listOfKnownNameSpaces := listOfKnownNameSpaces asOrderedCollection sort.
-
-    Dialog aboutToOpenBoxNotificationSignal handle:[:ex |
-        |box|
-
-        keepAsDefaultHolder := true asValue.
-        box := ex parameter.
-        box verticalPanel
-            add:((CheckBox 
-                    label:(resources string:'Use this as default in the future')) 
-                    model:keepAsDefaultHolder).
-        ex proceed.
-    ] do:[
-        nsName := Dialog
-                request:'When applying, new classes are created in nameSpace:'
-                initialAnswer:(enforcedNameSpace ? LastEnforcedNameSpace ? Class nameSpaceQuerySignal query name)
-                list:listOfKnownNameSpaces.
-    ].
-    nsName isNil ifTrue:[^ self].
-
-    (nsName isEmpty or:[nsName = 'Smalltalk']) ifTrue:[
-        applyInOriginalNameSpace value:true.
-        LastEnforcedNameSpace := enforcedNameSpace := nil.
-    ] ifFalse:[
-        applyInOriginalNameSpace value:false.
-        LastEnforcedNameSpace := enforcedNameSpace := NameSpace name:nsName.
-        autoCompare value ifTrue:[
-            self doUpdate
-        ].
-    ].
-    KeepEnforcedNameSpace := keepAsDefaultHolder value
-
-    "Modified: / 07-09-2006 / 15:10:25 / cg"
-!
-
-setEnforcedPackage
-    |pkg listOfKnownPackages|
-
-    listOfKnownPackages := Set new.
-    Smalltalk allClassesDo:[:eachClass |
-				|package|
-
-				package := eachClass package.
-				package size > 0 ifTrue:[
-				    listOfKnownPackages add:package
-				]
-			   ].
-    listOfKnownPackages := listOfKnownPackages asOrderedCollection sort.
-
-    pkg := Dialog
-		request:'When applying, changes go into package:'
-		initialAnswer:(enforcedPackage ? Class packageQuerySignal query)
-		list:listOfKnownPackages.
-    pkg size ~~ 0 ifTrue:[
-	enforcedPackage := pkg
-    ]
 ! !
 
 !ChangesBrowser::ChangeFileReader methodsFor:'accessing'!
@@ -6450,13 +6452,13 @@
 !ChangesBrowser class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/ChangesBrowser.st,v 1.428 2012/04/05 11:12:53 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/ChangesBrowser.st,v 1.429 2012/05/08 12:07:14 cg Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libtool/ChangesBrowser.st,v 1.428 2012/04/05 11:12:53 stefan Exp §'
+    ^ '§Header: /cvs/stx/stx/libtool/ChangesBrowser.st,v 1.429 2012/05/08 12:07:14 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: ChangesBrowser.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: ChangesBrowser.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/ContextInspectorView.st	Wed May 30 21:46:55 2012 +0100
+++ b/ContextInspectorView.st	Tue Jun 05 15:49:00 2012 +0100
@@ -60,19 +60,31 @@
      m argsOnly blockNode 
      numVarsInSource numVarsInContext isDoIt
      numArgs numVars n tempNames realTempNames 
-     oldSelection oldSelectedName hCon listSelection|
+     oldSelection oldSelectedName hCon keepList newList|
 
     oldSelection := selectionIndex.
-    oldSelection notNil ifTrue:[oldSelectedName := listView at:oldSelection].
+    oldSelection notNil ifTrue:[
+        oldSelectedName := (self listEntryAt:oldSelection).
+        oldSelectedName notNil ifTrue:[
+            oldSelectedName := oldSelectedName string
+        ]
+    ].
 
-    ((aContext == inspectedContext)
-        "/ care for contexts which change size
-        "/ (after the locals & stack-setup)
-    and:[    contextSize == inspectedContext size ])
-    ifTrue:[
-        "/ do nothing
+    keepList := ((aContext == inspectedContext)
+                "/ care for contexts which change size
+                "/ (after the locals & stack-setup)
+                and:[ contextSize == inspectedContext size ]).
+
+    keepList ifTrue:[
+        "/ assume that the list remains unchanged;
+        "/ this is no longer true, if some inst-slot has changed (bullet colors)
+        UserPreferences current showTypeIndicatorInInspector ifTrue:[
+            newList := self fieldList.
+            newList ~= listView list ifTrue:[
+                listView list:newList. 
+            ]    
+        ].
     ] ifFalse:[
-
         hasMore := argsOnly := false.
         inspectedObject := object := nil.
         inspectedContext := aContext.
@@ -84,10 +96,7 @@
             ^ self
         ].
 
-"/    realized ifFalse:[^ self].
-
-    methodHomeContext := aContext methodHome.
-
+        methodHomeContext := aContext methodHome.
         methodHomeContext isNil ifTrue:[
             "its a cheap blocks context"
             rec := aContext receiver.
@@ -100,7 +109,6 @@
 
             "/ #doIt needs special handling below
             isDoIt := (sel == #doIt) or:[sel == #doIt:].
-
             method := methodHomeContext method.
 
 "/        implementorClass := methodHomeContext methodClass.
@@ -299,14 +307,14 @@
     oldSelectedName notNil ifTrue:[
         |idx|
 
-        idx := listView list indexOf:oldSelectedName.
+        idx := listView list findFirst:[:entry | (entry ? '') string = oldSelectedName].
         idx ~~ 0 "(names includes:oldSelectedName)" ifTrue:[
             listView selectElement:oldSelectedName.
             self showSelection:idx.
         ]
     ].
 
-    "Modified: / 22-10-2010 / 11:47:48 / cg"
+    "Modified: / 03-06-2012 / 11:56:59 / cg"
 !
 
 namesOfBlockContext:aContext
@@ -465,17 +473,23 @@
 
     |sel|
 
-    sel := listView at:selectionIndex.
+    sel := self listEntryAt:selectionIndex.
     (sel startsWith:'-all local vars') ifTrue:[
         ^ self stringWithAllLocalValues
     ].
 
     ^ super displayStringForValue:someValue
+
+    "Modified: / 16-05-2012 / 17:55:33 / cg"
 !
 
 fieldList
     names size == 0 ifTrue:[^ names].
-    ^ (Array with:('-', 'all local vars' allItalic)) , names
+    ^ (Array with:('-', 'all local vars' allItalic)) 
+        , (names keysAndValuesCollect:[:idx :nm |
+                self listEntryForName:nm value:(self valueAtIndex:idx) ])
+
+    "Modified: / 16-05-2012 / 18:54:59 / cg"
 !
 
 hasSelfEntry
@@ -588,15 +602,17 @@
     inspectedContext isNil ifTrue:[^ nil].
 
     varIdx := lineNr.
-    l := listView at:lineNr.
+    l := self listEntryAt:lineNr.
     l isNil ifTrue:[ ^nil].
 
     (l startsWith:$-) ifTrue:[
         (l ~= '-') ifTrue:[
-            ^ self valueForSpecialLine:(listView at:lineNr)
+            ^ self valueForSpecialLine:(self listEntryAt:lineNr)
         ].
     ].
     ^ self valueAtIndex:(varIdx - 1). "/ for the special var
+
+    "Modified: / 16-05-2012 / 17:55:57 / cg"
 !
 
 valueForSpecialLine:line
@@ -655,13 +671,13 @@
 !ContextInspectorView class methodsFor:'documentation'!
 
 version
-    ^ '$Id: ContextInspectorView.st 7854 2012-01-30 17:49:41Z vranyj1 $'
+    ^ '$Header: /cvs/stx/stx/libtool/ContextInspectorView.st,v 1.78 2012/06/03 13:32:46 cg Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libtool/ContextInspectorView.st,v 1.75 2011/08/03 13:08:24 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libtool/ContextInspectorView.st,v 1.78 2012/06/03 13:32:46 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: ContextInspectorView.st 7854 2012-01-30 17:49:41Z vranyj1 $'
+    ^ '$Id: ContextInspectorView.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/DictionaryInspectorView.st	Wed May 30 21:46:55 2012 +0100
+++ b/DictionaryInspectorView.st	Tue Jun 05 15:49:00 2012 +0100
@@ -518,16 +518,23 @@
     "return a list of indexed-variable names to show in the selectionList.
      Set hasMore to true, if a '...' entry should be added."
 
-    |keys|
+    |indexList keyList|
 
-    keys := self indexList.
-    ^ keys 
+    indexList := self indexList.
+    keyList := indexList 
         collect:[:k | 
             k isSymbol 
-                ifTrue:[
-                    k printString] 
-                ifFalse:[
-                    k displayString]].
+                ifTrue:[ k printString] 
+                ifFalse:[ k displayString]
+        ].
+
+    ^ keyList
+        keysAndValuesCollect:[:idx :nm |
+            self listEntryForName:nm value:(object at:(indexList at:idx))
+        ].
+    ^ keyList
+
+    "Modified: / 16-05-2012 / 19:07:57 / cg"
 !
 
 instVarIndexForLine:lineNr
@@ -552,7 +559,7 @@
         ].
         firstRealIndex := 1.
         idx := lineNr.
-        [line := listView at:firstRealIndex. 
+        [line := self listEntryAt:firstRealIndex. 
          (line startsWith:'-') and:[line size < 2 or:[line second isDigit not]]] whileTrue:[
             firstRealIndex := firstRealIndex + 1.
             idx := idx - 1.
@@ -561,6 +568,8 @@
         ^ idx   
     ].
     ^ super keyIndexForLine:lineNr
+
+    "Modified: / 16-05-2012 / 17:56:01 / cg"
 !
 
 namedFieldList 
@@ -648,13 +657,13 @@
 !DictionaryInspectorView class methodsFor:'documentation'!
 
 version
-    ^ '$Id: DictionaryInspectorView.st 7854 2012-01-30 17:49:41Z vranyj1 $'
+    ^ '$Header: /cvs/stx/stx/libtool/DictionaryInspectorView.st,v 1.76 2012/05/16 17:08:54 cg Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libtool/DictionaryInspectorView.st,v 1.74 2011/05/10 06:15:04 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libtool/DictionaryInspectorView.st,v 1.76 2012/05/16 17:08:54 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: DictionaryInspectorView.st 7854 2012-01-30 17:49:41Z vranyj1 $'
+    ^ '$Id: DictionaryInspectorView.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/Diff3TextView.st	Wed May 30 21:46:55 2012 +0100
+++ b/Diff3TextView.st	Tue Jun 05 15:49:00 2012 +0100
@@ -232,6 +232,53 @@
 
     "Created: 9.9.1996 / 19:54:00 / cg"
     "Modified: 9.9.1996 / 20:41:40 / cg"
+!
+
+emphasizeMergedDiff3TextFromPerforce:mergedText origEmphasis:origEmphasize otherEmphasis:otherEmphasize yourEmphasis:yourEmphasize separatorEmphasis:separatorEmphasize
+    "given the merge()/rcsmerge() merged output (as created by 'cvs update'),
+     create & return a text object which contains the conflicts 
+     highlighted.
+     CAVEAT: this is a highly specialized method - probably not the right place
+     for it here ..."
+
+    |list origSeparator otherSeparator yourSeparator endSeparator line currentEmphasis nextEmphasis|
+
+    list := StringCollection new.
+
+    origSeparator := '>>>> ORIGINAL //'.
+    otherSeparator := '==== THEIRS //'.
+    yourSeparator := '==== YOURS //'.
+    endSeparator := '<<<<'.
+    mergedText do:[:aLine|
+        line := aLine withoutTrailingSeparators.
+        (aLine startsWith:origSeparator) ifTrue:[
+            currentEmphasis := separatorEmphasize.
+            nextEmphasis := origEmphasize.
+        ] ifFalse:[
+            (aLine startsWith:otherSeparator) ifTrue:[
+                currentEmphasis := separatorEmphasize.
+                nextEmphasis := otherEmphasize.
+            ] ifFalse:[
+                (aLine startsWith:yourSeparator) ifTrue:[
+                    currentEmphasis := separatorEmphasize.
+                    nextEmphasis := yourEmphasize.
+                ] ifFalse:[
+                    (aLine startsWith:endSeparator) ifTrue:[
+                        currentEmphasis := separatorEmphasize.
+                        nextEmphasis := nil.
+                    ] ifFalse:[
+                        nextEmphasis := currentEmphasis.        
+                    ].
+                ].
+            ].
+        ].
+        list add:(currentEmphasis isNil ifTrue:[aLine] ifFalse:[Text string:aLine emphasis:currentEmphasis]).
+
+        currentEmphasis := nextEmphasis.        
+    ].
+    ^ list
+
+    "Created: / 01-06-2012 / 10:44:31 / cg"
 ! !
 
 !Diff3TextView methodsFor:'initialization'!
@@ -390,9 +437,9 @@
 !Diff3TextView class methodsFor:'documentation'!
 
 version
-    ^ '$Id: Diff3TextView.st 7925 2012-03-16 17:08:17Z vranyj1 $'
+    ^ '$Header: /cvs/stx/stx/libtool/Diff3TextView.st,v 1.9 2012/06/01 10:44:15 cg Exp $'
 !
 
 version_SVN
-    ^ '$Id: Diff3TextView.st 7925 2012-03-16 17:08:17Z vranyj1 $'
+    ^ '$Id: Diff3TextView.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/InspectorView.st	Wed May 30 21:46:55 2012 +0100
+++ b/InspectorView.st	Tue Jun 05 15:49:00 2012 +0100
@@ -344,6 +344,353 @@
     "Created: / 23-10-2007 / 19:10:02 / cg"
 ! !
 
+!InspectorView class methodsFor:'image specs'!
+
+imageFor_arrays
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self imageFor_arrays inspect
+     ImageEditor openOnClass:self andSelector:#imageFor_arrays
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+        constantNamed:'InspectorView class imageFor_arrays'
+        ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#[8]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@A@T5EQT4@@@@@@@@@@@@AOTUAPBU@IS0@@@@@@@@AOTP%PBUAQ
+T %O@@@@@@@@T0$IBP$ITUHIO0@@@@@@@EEPBU@ITUIRBSD@@@@@@@AQBP$IBP%RO0$1@@@@@@@@T5HIT %RO3DIO0@@@@@@@D=RT%HILSEJBR<@@@@@@@@@
+S3D1LP%JBR<@@@@@@@@@@@AOO3D1O2<@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[226 226 226 176 176 176 155 155 155 169 169 169 152 152 152 164 164 164 149 149 149 192 192 192 240 240 240 255 255 255 202 202 202 201 201 201 151 151 151 162 162 162 148 148 148 158 158 158 173 173 173 154 154 154 167 167 167 150 150 150 160 160 160 180 180 180 156 156 156 170 170 170 153 153 153 165 165 165 183 183 183 0 0 0 227 231 0 132 132 0 151 156 0 142 131 128 255 252 49 175 181 0 255 234 140 218 222 0 251 255 33 74 74 0 94 99 0 107 107 0 143 148 0 189 189 0 87 90 0 251 255 8 247 255 16 167 173 0 206 99 132 156 74 99 206 66 107 115 16 49 255 16 90 189 0 57 132 16 49 206 0 57 198 123 140 255 49 123 255 33 99 222 0 66 99 0 24 239 0 66 255 0 74 255 140 214 148 0 41 140 49 74 198 123 148 255 0 82 90 0 24 132 0 41 206 99 123 156 0 41 198 0 57 74 0 24 255 16 82 214 0 66 90 0 33 189 0 49 107 0 33 206 16 74 214 8 66 218 112 214 255 0 255 208 32 144 199 21 133 186 85 211]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@A>@O<A?8G? _>A?8G? _>@?0A>@@@@@@@@@b') ; yourself); yourself]
+!
+
+imageFor_characters
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self imageFor_characters inspect
+     ImageEditor openOnClass:self andSelector:#imageFor_characters
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+        constantNamed:'InspectorView class imageFor_characters'
+        ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#[8]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@6LD5MLCX@@@@@@@@@@@ADRTDIOC-FQ@@@@@@@@@A@MP$IBP$I
+Q$U@@@@@@@@@L@%SOP%HRP$>M@@@@@@@@D4<BP$IS#MEP4H@@@@@@@AMNUP9BP$IP3)B@@@@@@@@L@$3R0%EP0%GLP@@@@@@@D@>BP$IBP%RQ2<@@@@@@@@@
+K$1LBT]GQ3<@@@@@@@@@@@A@LTIBLR<@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[226 226 226 176 176 176 155 155 155 169 169 169 152 152 152 164 164 164 149 149 149 192 192 192 240 240 240 255 255 255 202 202 202 201 201 201 151 151 151 162 162 162 148 148 148 158 158 158 173 173 173 154 154 154 167 167 167 150 150 150 160 160 160 180 180 180 156 156 156 170 170 170 153 153 153 165 165 165 183 183 183 0 0 0 227 231 0 132 132 0 151 156 0 142 131 128 255 252 49 175 181 0 255 234 140 218 222 0 251 255 33 74 74 0 94 99 0 107 107 0 143 148 0 189 189 0 87 90 0 251 255 8 247 255 16 167 173 0 206 99 132 156 74 99 206 66 107 115 16 49 255 16 90 189 0 57 132 16 49 206 0 57 198 123 140 255 49 123 255 33 99 222 0 66 99 0 24 239 0 66 255 0 74 255 140 214 148 0 41 140 49 74 198 123 148 255 0 82 90 0 24 132 0 41 206 99 123 156 0 41 198 0 57 74 0 24 255 16 82 214 0 66 90 0 33 189 0 49 107 0 33 206 16 74 214 8 66 173 0 49 115 0 33 181 0 49 74 0 16 255 8 82 231 0 66]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@A>@O<A?8G? _>A?8G? _>@?0A>@@@@@@@@@b') ; yourself); yourself]
+!
+
+imageFor_classes
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self imageFor_classes inspect
+     ImageEditor openOnClass:self andSelector:#imageFor_classes
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+        constantNamed:'InspectorView class imageFor_classes'
+        ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#[8]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@6LD5MLCX@@@@@@@@@@@ADRTEAOC-FQ@@@@@@@@@A@MT 2M3\;
+Q$U@@@@@@@@@LD!!HRD!!HRTX>M@@@@@@@@D4<RC\8S$%FP4H@@@@@@@AMNS$9MST3P3)B@@@@@@@@LCL3R4,3P4)GLP@@@@@@@D@>O#8>R$)JQ2<@@@@@@@@@
+K$1LP$]GQ3<@@@@@@@@@@@A@LTIBLR<@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[226 226 226 176 176 176 155 155 155 169 169 169 152 152 152 164 164 164 149 149 149 192 192 192 240 240 240 255 255 255 202 202 202 201 201 201 151 151 151 162 162 162 148 148 148 158 158 158 173 173 173 154 154 154 167 167 167 150 150 150 160 160 160 180 180 180 156 156 156 170 170 170 153 153 153 165 165 165 183 183 183 0 0 0 0 215 231 0 125 132 0 143 156 128 142 132 49 248 255 0 166 181 140 255 240 0 207 222 33 240 255 0 70 74 0 89 99 0 102 107 0 136 148 0 180 189 0 82 90 8 239 255 16 235 255 0 158 173 127 206 99 95 156 74 100 206 66 44 115 16 78 255 16 48 189 0 43 132 16 47 206 0 136 198 123 113 255 49 88 255 33 55 222 0 19 99 0 54 239 0 61 255 0 208 255 140 34 148 0 69 140 49 144 198 123 69 255 0 19 90 0 34 132 0 118 206 99 33 156 0 47 198 0 20 74 0 70 255 16 55 214 0 28 90 0 40 189 0 28 107 0 64 206 16 56 214 8]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@A>@O<A?8G? _>A?8G? _>@?0A>@@@@@@@@@b') ; yourself); yourself]
+!
+
+imageFor_collections
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self imageFor_collections inspect
+     ImageEditor openOnClass:self andSelector:#imageFor_collections
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+        constantNamed:'InspectorView class imageFor_collections'
+        ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#[8]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@A@T5EQT4@@@@@@@@@@@@AOBUAPTE@IS0@@@@@@@@AOBUAPTEAQ
+T %O@@@@@@@@T0%PTEAPTUHIO0@@@@@@@EDITEAPTUIRBSD@@@@@@@AQBU@IT%DIO0$1@@@@@@@@T0%RT%IRO3DIO0@@@@@@@D<IT%IRLSEJBR<@@@@@@@@@
+S0$1LSEJBR<@@@@@@@@@@@AOO3D1O2<@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[226 226 226 176 176 176 155 155 155 169 169 169 152 152 152 164 164 164 149 149 149 192 192 192 240 240 240 255 255 255 202 202 202 201 201 201 151 151 151 162 162 162 148 148 148 158 158 158 173 173 173 154 154 154 167 167 167 150 150 150 160 160 160 180 180 180 156 156 156 170 170 170 153 153 153 165 165 165 183 183 183 0 0 0 227 231 0 132 132 0 151 156 0 142 131 128 255 252 49 175 181 0 255 234 140 218 222 0 251 255 33 74 74 0 94 99 0 107 107 0 143 148 0 189 189 0 87 90 0 251 255 8 247 255 16 167 173 0 206 99 132 156 74 99 206 66 107 115 16 49 255 16 90 189 0 57 132 16 49 206 0 57 198 123 140 255 49 123 255 33 99 222 0 66 99 0 24 239 0 66 255 0 74 255 140 214 148 0 41 140 49 74 198 123 148 255 0 82 90 0 24 132 0 41 206 99 123 156 0 41 198 0 57 74 0 24 255 16 82 214 0 66 90 0 33 189 0 49 107 0 33 206 16 74 214 8 66 218 112 214 255 0 255 208 32 144 199 21 133 186 85 211]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@A>@O<A?8G? _>A?8G? _>@?0A>@@@@@@@@@b') ; yourself); yourself]
+!
+
+imageFor_dictionaries
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self imageFor_dictionaries inspect
+     ImageEditor openOnClass:self andSelector:#imageFor_dictionaries
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+        constantNamed:'InspectorView class imageFor_dictionaries'
+        ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#[8]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@A@T5EQT4@@@@@@@@@@@@AOTUAPTEARS0@@@@@@@@AOTU@HTE@I
+BEIO@@@@@@@@T5APBP!!PTUIRO0@@@@@@@EDIBP$I@P$HO3D@@@@@@@AQTUDIBEIRO3D1@@@@@@@@T5IRBEIRBP!!JO0@@@@@@@D=RT%H?LSEJR"<@@@@@@@@@
+S3D1LT(IBB<@@@@@@@@@@@AOO3D1O2<@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[226 226 226 176 176 176 155 155 155 169 169 169 152 152 152 164 164 164 149 149 149 192 192 192 240 240 240 255 255 255 202 202 202 201 201 201 151 151 151 162 162 162 148 148 148 158 158 158 173 173 173 154 154 154 167 167 167 150 150 150 160 160 160 180 180 180 156 156 156 170 170 170 153 153 153 165 165 165 183 183 183 0 0 0 227 231 0 132 132 0 151 156 0 142 131 128 255 252 49 175 181 0 255 234 140 218 222 0 251 255 33 74 74 0 94 99 0 107 107 0 143 148 0 189 189 0 87 90 0 251 255 8 247 255 16 167 173 0 206 99 132 156 74 99 206 66 107 115 16 49 255 16 90 189 0 57 132 16 49 206 0 57 198 123 140 255 49 123 255 33 99 222 0 66 99 0 24 239 0 66 255 0 74 255 140 214 148 0 41 140 49 74 198 123 148 255 0 82 90 0 24 132 0 41 206 99 123 156 0 41 198 0 57 74 0 24 255 16 82 214 0 66 90 0 33 189 0 49 107 0 33 206 16 74 214 8 66 218 112 214 255 0 255 208 32 144 199 21 133 186 85 211]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@A>@O<A?8G? _>A?8G? _>@?0A>@@@@@@@@@b') ; yourself); yourself]
+!
+
+imageFor_false
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self imageFor_false inspect
+     ImageEditor openOnClass:self andSelector:#imageFor_false
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+        constantNamed:'InspectorView imageFor_false'
+        ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#[8]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@A@ LC@ D@@@@@@@@@@@@DAPXFA0 IA@@@@@@@@@@JB0XLC@0L
+CP8J@@@@@@@@@ XOCA@PDA@QD @@@@@@@@LGC00PD1PNEQX@@@@@@@@CE1 LC@0MEQ$V@@@@@@@@@!!PTCA@PDAXZF0@@@@@@@@(QC 0PGA$]F!!8@@@@@@@@@
+G10LDA(ZF"@@@@@@@@@@@@@JF1XVF18@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 200 120 145 208 64 109 208 16 96 208 96 128 208 0 87 248 0 103 248 0 88 240 0 85 200 0 68 200 120 146 208 0 72 250 255 248 184 192 189 160 0 52 248 8 100 135 144 128 144 0 60 128 16 63 208 8 83 184 0 77 128 0 53 88 0 37 216 0 75 224 0 78 96 0 25 64 0 27 120 16 59 120 0 50 64 0 12 160 72 102 208 96 143 136 32 60]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@A>@O<A?8G? _>A?8G? _>@?0A>@@@@@@@@@b') ; yourself); yourself]
+!
+
+imageFor_floats
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self imageFor_floats inspect
+     ImageEditor openOnClass:self andSelector:#imageFor_floats
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+        constantNamed:'InspectorView class imageFor_floats'
+        ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#[8]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@6LD5MLCX@@@@@@@@@@@ADRTEAOC-FQ@@@@@@@@@A@MT 2BS\;
+Q$U@@@@@@@@@LD!!HBP%HRTX>M@@@@@@@@D4<RC\IS#MFP4H@@@@@@@AMNS$9BSUCP3)B@@@@@@@@LCL3R0%EP4)GLP@@@@@@@D@>O $IBS8IQ2<@@@@@@@@@
+K$1LP$]GQ3<@@@@@@@@@@@A@LTIBLR<@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[226 226 226 176 176 176 155 155 155 169 169 169 152 152 152 164 164 164 149 149 149 192 192 192 240 240 240 255 255 255 202 202 202 201 201 201 151 151 151 162 162 162 148 148 148 158 158 158 173 173 173 154 154 154 167 167 167 150 150 150 160 160 160 180 180 180 156 156 156 170 170 170 153 153 153 165 165 165 183 183 183 0 0 0 0 231 4 0 132 0 0 156 5 139 142 128 52 255 49 0 181 6 161 255 140 0 222 4 33 255 37 0 74 0 0 99 5 0 107 0 0 148 5 0 189 0 0 90 3 8 255 12 16 255 24 0 173 6 206 173 99 156 131 74 206 165 66 115 82 16 255 181 16 189 132 0 132 99 16 206 149 0 198 181 123 255 181 49 255 189 33 222 156 0 99 75 0 239 173 0 255 181 0 255 181 140 148 107 0 140 115 49 198 173 123 255 173 0 90 66 0 132 91 0 206 182 99 156 115 0 198 141 0 74 50 0 255 189 16 214 148 0 90 57 0 189 140 0 107 74 0 206 148 16 214 156 8]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@A>@O<A?8G? _>A?8G? _>@?0A>@@@@@@@@@b') ; yourself); yourself]
+!
+
+imageFor_fractions
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self imageFor_fractions inspect
+     ImageEditor openOnClass:self andSelector:#imageFor_fractions
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+        constantNamed:'InspectorView class imageFor_fractions'
+        ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#[8]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@6LD5MLCX@@@@@@@@@@@ADRTEABS-FQ@@@@@@@@@A@MSH2BP$7
+LTY@@@@@@@@@LCH2L#HIS#D1M@@@@@@@@D4<OC0<BSL1LTH@@@@@@@AML3L3BP$ILSEB@@@@@@@@LCL3L0$3BT\1LP@@@@@@@D@>L3L3BT]GQ2<@@@@@@@@@
+K$03BP$IQ3<@@@@@@@@@@@A@LTIBLR<@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[226 226 226 176 176 176 155 155 155 169 169 169 152 152 152 164 164 164 149 149 149 192 192 192 240 240 240 255 255 255 202 202 202 201 201 201 151 151 151 162 162 162 148 148 148 158 158 158 173 173 173 154 154 154 167 167 167 150 150 150 160 160 160 180 180 180 156 156 156 170 170 170 153 153 153 165 165 165 183 183 183 0 0 0 0 231 4 0 132 0 0 156 5 139 142 128 52 255 49 0 181 6 161 255 140 0 222 4 33 255 37 0 74 0 0 99 5 0 107 0 0 148 5 0 189 0 0 90 3 8 255 12 16 255 24 0 173 6 206 173 99 156 131 74 206 165 66 115 82 16 255 181 16 189 132 0 132 99 16 206 149 0 198 181 123 255 181 49 255 189 33 222 156 0 99 75 0 239 173 0 255 181 0 255 181 140 148 107 0 140 115 49 198 173 123 255 173 0 90 66 0 132 91 0 206 182 99 156 115 0 198 141 0 74 50 0 255 189 16 214 148 0 90 57 0 189 140 0 107 74 0 206 148 16 214 156 8]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@A>@O<A?8G? _>A?8G? _>@?0A>@@@@@@@@@b') ; yourself); yourself]
+!
+
+imageFor_integers
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self imageFor_integers inspect
+     ImageEditor openOnClass:self andSelector:#imageFor_integers
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+        constantNamed:'InspectorView class imageFor_integers'
+        ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#[8]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@6LD5MLCX@@@@@@@@@@@ADRTEAOC-FQ@@@@@@@@@A@MT 2BS\;
+Q$U@@@@@@@@@LD!!HBP%HRTX>M@@@@@@@@D4<RC\IS#MFP4H@@@@@@@AMNS$9BSUCP3)B@@@@@@@@LCL3R0%EP4)GLP@@@@@@@D@>O $IBS9JQ2<@@@@@@@@@
+K$1LP$]GQ3<@@@@@@@@@@@A@LTIBLR<@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[226 226 226 176 176 176 155 155 155 169 169 169 152 152 152 164 164 164 149 149 149 192 192 192 240 240 240 255 255 255 202 202 202 201 201 201 151 151 151 162 162 162 148 148 148 158 158 158 173 173 173 154 154 154 167 167 167 150 150 150 160 160 160 180 180 180 156 156 156 170 170 170 153 153 153 165 165 165 183 183 183 0 0 0 0 231 4 0 132 0 0 156 5 139 142 128 52 255 49 0 181 6 161 255 140 0 222 4 33 255 37 0 74 0 0 99 5 0 107 0 0 148 5 0 189 0 0 90 3 8 255 12 16 255 24 0 173 6 206 173 99 156 131 74 206 165 66 115 82 16 255 181 16 189 132 0 132 99 16 206 149 0 198 181 123 255 181 49 255 189 33 222 156 0 99 75 0 239 173 0 255 181 0 255 181 140 148 107 0 140 115 49 198 173 123 255 173 0 90 66 0 132 91 0 206 182 99 156 115 0 198 141 0 74 50 0 255 189 16 214 148 0 90 57 0 189 140 0 107 74 0 206 148 16 214 156 8]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@A>@O<A?8G? _>A?8G? _>@?0A>@@@@@@@@@b') ; yourself); yourself]
+!
+
+imageFor_nil
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self imageFor_nil inspect
+     ImageEditor openOnClass:self andSelector:#imageFor_nil
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+        constantNamed:'InspectorView class imageFor_nil'
+        ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#[8]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@KEP4MEP,@@@@@@@@@@@@GEA$YAP4OA0@@@@@@@@@JEA$WF!!HM
+C1 J@@@@@@@@EQ$R@@ CEAXDDP@@@@@@@@4ED!!(ACQXXC@X@@@@@@@@ME@4TEAXXCALF@@@@@@@@EQXVE HXC@XNF@@@@@@@@@(DF@PLCALNC!!@@@@@@@@@@
+A1LSA 8NC 4@@@@@@@@@@@@JF@XFFA@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[226 226 226 176 176 176 155 155 155 169 169 169 152 152 152 164 164 164 149 149 149 192 192 192 240 240 240 255 255 255 202 202 202 201 201 201 151 151 151 162 162 162 148 148 148 158 158 158 173 173 173 154 154 154 167 167 167 150 150 150 160 160 160 180 180 180 156 156 156 170 170 170 153 153 153 165 165 165 183 183 183]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@A>@O<A?8G? _>A?8G? _>@?0A>@@@@@@@@@b') ; yourself); yourself]
+!
+
+imageFor_others
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self imageFor_others inspect
+     ImageEditor openOnClass:self andSelector:#imageFor_others
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+        constantNamed:'InspectorView class imageFor_others'
+        ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#[8]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@_G1<_G1<@@@@@@@@@@@@_BP$IBP HF0@@@@@@@@@_BP$HH@ \
+BA8[@@@@@@@@G0$HH  ,BB$(F0@@@@@@@A<IJ0 $BB$HGQ,@@@@@@@@_BP #BBDHJRX[@@@@@@@@G0 )BB4HHQ<%F0@@@@@@@A<HBB4HKQ<''IQ,@@@@@@@@@
+F2\''J"T%IQ,@@@@@@@@@@@@[F1,[F1,@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[226 226 226 176 176 176 155 155 155 169 169 169 152 152 152 164 164 164 149 149 149 192 192 192 240 240 240 255 255 255 202 202 202 201 201 201 151 151 151 162 162 162 148 148 148 158 158 158 173 173 173 154 154 154 167 167 167 150 150 150 160 160 160 180 180 180 156 156 156 170 170 170 153 153 153 165 165 165 183 183 183 0 0 0 227 231 0 132 132 0 151 156 0 142 131 128 255 252 49 175 181 0 255 234 140 218 222 0 251 255 33 74 74 0 94 99 0 107 107 0 143 148 0 189 189 0 87 90 0 251 255 8 247 255 16 167 173 0]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@A>@O<A?8G? _>A?8G? _>@?0A>@@@@@@@@@b') ; yourself); yourself]
+!
+
+imageFor_sequenceableCollections
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self imageFor_sequenceableCollections inspect
+     ImageEditor openOnClass:self andSelector:#imageFor_sequenceableCollections
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+        constantNamed:'InspectorView class imageFor_sequenceableCollections'
+        ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#[8]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@A@T5EQT4@@@@@@@@@@@@AOTUAPTEARS0@@@@@@@@AOTUAPTE@I
+BEIO@@@@@@@@T5APTEAPTUIRO0@@@@@@@EEPTEAPT $HO3D@@@@@@@AQTUERT%IRO3D1@@@@@@@@T5IRT%IRBP!!JO0@@@@@@@D=RT%H?LSEJR"<@@@@@@@@@
+S3D1LT(IBB<@@@@@@@@@@@AOO3D1O2<@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[226 226 226 176 176 176 155 155 155 169 169 169 152 152 152 164 164 164 149 149 149 192 192 192 240 240 240 255 255 255 202 202 202 201 201 201 151 151 151 162 162 162 148 148 148 158 158 158 173 173 173 154 154 154 167 167 167 150 150 150 160 160 160 180 180 180 156 156 156 170 170 170 153 153 153 165 165 165 183 183 183 0 0 0 227 231 0 132 132 0 151 156 0 142 131 128 255 252 49 175 181 0 255 234 140 218 222 0 251 255 33 74 74 0 94 99 0 107 107 0 143 148 0 189 189 0 87 90 0 251 255 8 247 255 16 167 173 0 206 99 132 156 74 99 206 66 107 115 16 49 255 16 90 189 0 57 132 16 49 206 0 57 198 123 140 255 49 123 255 33 99 222 0 66 99 0 24 239 0 66 255 0 74 255 140 214 148 0 41 140 49 74 198 123 148 255 0 82 90 0 24 132 0 41 206 99 123 156 0 41 198 0 57 74 0 24 255 16 82 214 0 66 90 0 33 189 0 49 107 0 33 206 16 74 214 8 66 218 112 214 255 0 255 208 32 144 199 21 133 186 85 211]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@A>@O<A?8G? _>A?8G? _>@?0A>@@@@@@@@@b') ; yourself); yourself]
+!
+
+imageFor_strings
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self imageFor_strings inspect
+     ImageEditor openOnClass:self andSelector:#imageFor_strings
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+        constantNamed:'InspectorView class imageFor_strings'
+        ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#[8]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@6LD5MLCX@@@@@@@@@@@ADRTEAOC-FQ@@@@@@@@@A@MTDIM5LI
+BTU@@@@@@@@@LDDIM3]HBP$>M@@@@@@@@D4<BP$8S#LIP4H@@@@@@@AMNP$IMUDIP3)B@@@@@@@@LCL3R4=EP4)GLP@@@@@@@D@>QS9CTC)RQ2<@@@@@@@@@
+K$1LP$]GQ3<@@@@@@@@@@@A@LTIBLR<@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[226 226 226 176 176 176 155 155 155 169 169 169 152 152 152 164 164 164 149 149 149 192 192 192 240 240 240 255 255 255 202 202 202 201 201 201 151 151 151 162 162 162 148 148 148 158 158 158 173 173 173 154 154 154 167 167 167 150 150 150 160 160 160 180 180 180 156 156 156 170 170 170 153 153 153 165 165 165 183 183 183 0 0 0 227 231 0 132 132 0 151 156 0 142 131 128 255 252 49 175 181 0 255 234 140 218 222 0 251 255 33 74 74 0 94 99 0 107 107 0 143 148 0 189 189 0 87 90 0 251 255 8 247 255 16 167 173 0 206 99 132 156 74 99 206 66 107 115 16 49 255 16 90 189 0 57 132 16 49 206 0 57 198 123 140 255 49 123 255 33 99 222 0 66 99 0 24 239 0 66 255 0 74 255 140 214 148 0 41 140 49 74 198 123 148 255 0 82 90 0 24 132 0 41 206 99 123 156 0 41 198 0 57 74 0 24 255 16 82 214 0 66 90 0 33 189 0 49 107 0 33 206 16 74 214 8 66 173 0 49 115 0 33 181 0 49 74 0 16 255 8 82]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@A>@O<A?8G? _>A?8G? _>@?0A>@@@@@@@@@b') ; yourself); yourself]
+!
+
+imageFor_symbols
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self imageFor_symbols inspect
+     ImageEditor openOnClass:self andSelector:#imageFor_symbols
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+        constantNamed:'InspectorView class imageFor_symbols'
+        ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#[8]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@6LD5MLCX@@@@@@@@@@@ADRTEAOC-FQ@@@@@@@@@A@MTDIM5LI
+Q$U@@@@@@@@@LDDIBP$IBP$>M@@@@@@@@D4<NP$8S $>P4H@@@@@@@AMNS$IMUDIP3)B@@@@@@@@LCLIBP$IBP%GLP@@@@@@@D@>QP%CT@%RQ2<@@@@@@@@@
+K$1LP$]GQ3<@@@@@@@@@@@A@LTIBLR<@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[226 226 226 176 176 176 155 155 155 169 169 169 152 152 152 164 164 164 149 149 149 192 192 192 240 240 240 255 255 255 202 202 202 201 201 201 151 151 151 162 162 162 148 148 148 158 158 158 173 173 173 154 154 154 167 167 167 150 150 150 160 160 160 180 180 180 156 156 156 170 170 170 153 153 153 165 165 165 183 183 183 0 0 0 227 231 0 132 132 0 151 156 0 142 131 128 255 252 49 175 181 0 255 234 140 218 222 0 251 255 33 74 74 0 94 99 0 107 107 0 143 148 0 189 189 0 87 90 0 251 255 8 247 255 16 167 173 0 206 99 132 156 74 99 206 66 107 115 16 49 255 16 90 189 0 57 132 16 49 206 0 57 198 123 140 255 49 123 255 33 99 222 0 66 99 0 24 239 0 66 255 0 74 255 140 214 148 0 41 140 49 74 198 123 148 255 0 82 90 0 24 132 0 41 206 99 123 156 0 41 198 0 57 74 0 24 255 16 82 214 0 66 90 0 33 189 0 49 107 0 33 206 16 74 214 8 66 173 0 49 115 0 33 181 0 49 74 0 16 255 8 82]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@A>@O<A?8G? _>A?8G? _>@?0A>@@@@@@@@@b') ; yourself); yourself]
+!
+
+imageFor_true
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self imageFor_true inspect
+     ImageEditor openOnClass:self andSelector:#imageFor_true
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+        constantNamed:'InspectorView imageFor_true'
+        ifAbsentPut:[(Depth8Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#[8]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@(MB@ MB @@@@@@@@@@@@:K#@0F2(\N @@@@@@@@@-H0$IBP$I
+A18-@@@@@@@@MC@GI@$$IBP9HP@@@@@@@B@[J3DIIB0^K3 @@@@@@@@ MRT5BRP^K1<8@@@@@@@@MB0,I $$K2\"JP@@@@@@@B49G#$IIA<]H#H@@@@@@@@@
+M#L3NBH"H#\@@@@@@@@@@@@-JS 8JSH@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[226 226 226 176 176 176 155 155 155 169 169 169 152 152 152 164 164 164 149 149 149 192 192 192 240 240 240 255 255 255 202 202 202 201 201 201 151 151 151 162 162 162 148 148 148 158 158 158 173 173 173 154 154 154 167 167 167 150 150 150 160 160 160 180 180 180 156 156 156 170 170 170 153 153 153 165 165 165 183 183 183 98 255 0 75 198 0 25 74 0 57 156 0 34 99 0 92 206 16 60 132 16 31 74 0 79 206 0 128 131 142 88 231 0 70 189 0 38 90 0 148 198 123 57 115 16 92 239 0 103 255 8 76 189 0 154 198 123 85 214 0 53 132 0 106 255 0 138 255 49 107 156 74 44 115 0 119 206 66 85 222 0 142 206 99 68 139 33 33 90 0 57 148 0 135 206 99]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@A>@O<A?8G? _>A?8G? _>@?0A>@@@@@@@@@b') ; yourself); yourself]
+! !
+
 !InspectorView class methodsFor:'queries-plugin'!
 
 aspectSelectors
@@ -403,7 +750,7 @@
 inspect:anObject
     "set/update the object to be inspected"
 
-    |aList sameObject sameClass oldSelectedField idx|
+    |keepList fieldNameList sameObject sameClass oldSelectedField idx|
 
     "/ (anObject isNil and:[object isNil]) ifTrue:[^ self].
 
@@ -419,15 +766,19 @@
     ].
     inspectedObject := object := anObject.
 
-    ((sameObject | sameClass) and:[listView list notEmptyOrNil]) ifTrue:[
-"/        listView setContents:aList.
-    ] ifFalse:[
+    keepList := ((sameObject | sameClass) and:[listView list notEmptyOrNil]).
+    "/ assume that the list remains unchanged;
+    "/ this is no longer true, if some inst-slot has changed (bullet colors)
+    UserPreferences current showTypeIndicatorInInspector ifTrue:[
+        keepList := false.
+    ].
+    keepList ifFalse:[
         hasMore := false.
-        aList := self fieldList.                               
+        fieldNameList := self fieldList.                               
         hasMore ifTrue:[
-            aList add:' ... '
+            fieldNameList add:' ... '
         ].
-        listView contents:aList.
+        listView contents:fieldNameList.
         workspace contents:nil.
         self setDoItAction.
     ].
@@ -451,8 +802,8 @@
     ].
     self showSelection:((selectedLine ? 1) min: listView list size)
 
-    "Modified: / 15-07-2011 / 16:20:32 / cg"
     "Modified (comment): / 06-08-2011 / 13:41:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 02-06-2012 / 13:06:59 / cg"
 !
 
 isStandaloneInspector:aBoolean
@@ -490,11 +841,10 @@
     ].
 
     listView contents:aList.
-
-"/    workspace contents:nil.
     self setDoItAction.
-
     selectionIndex := selectedLine := nil
+
+    "Modified (comment): / 02-06-2012 / 13:08:15 / cg"
 !
 
 suppressHeadline:aBoolean
@@ -1602,7 +1952,7 @@
 
     idx := self theSingleSelectionIndex.
     idx notNil ifTrue:[
-        sel := listView at:idx.
+        sel := self listEntryAt:idx.
 
         extraAttributes := object inspectorExtraAttributes.
         (extraAttributes notNil and:[extraAttributes includesKey:sel]) ifTrue:[
@@ -1627,7 +1977,100 @@
     ].
     ^ self basicDisplayStringForValue:someValue
 
-    "Modified: / 17-11-2010 / 19:20:47 / cg"
+    "Modified: / 16-05-2012 / 17:55:05 / cg"
+!
+
+iconForValue: anObject
+    anObject isNil ifTrue:[
+        ^ self class imageFor_nil
+    ].
+    anObject isNumber ifTrue:[
+        anObject isInteger ifTrue:[
+            ^ self class imageFor_integers
+        ].
+        anObject isFloat ifTrue:[
+            ^ self class imageFor_floats
+        ].
+        anObject isFraction ifTrue:[
+            ^ self class imageFor_fractions
+        ].
+    ].
+    anObject isCollection ifTrue:[
+        anObject isString ifTrue:[
+            anObject isSymbol ifTrue:[
+                ^ self class imageFor_symbols
+            ].
+            ^ self class imageFor_strings
+        ].
+        (anObject isKindOf:Dictionary) ifTrue:[
+            ^ self class imageFor_dictionaries
+        ].
+        (anObject isArray) ifTrue:[
+            ^ self class imageFor_arrays
+        ].
+        (anObject isSequenceable) ifTrue:[
+            ^ self class imageFor_sequenceableCollections
+        ].
+        ^ self class imageFor_collections
+    ].
+    anObject == true ifTrue:[
+        ^ self class imageFor_true
+    ].
+    anObject == false ifTrue:[
+        ^ self class imageFor_false
+    ].
+    anObject isCharacter ifTrue:[
+        ^ self class imageFor_characters
+    ].
+    anObject isBehavior ifTrue:[
+        ^ self class imageFor_classes
+    ].
+    ^ self class imageFor_others
+
+    "Created: / 16-05-2012 / 17:58:20 / cg"
+!
+
+listEntryForName:nameString value:value
+    |valString plainString|
+
+    UserPreferences current showTypeIndicatorInInspector ifFalse:[
+        ^ nameString
+    ].
+
+    value isNumber ifTrue:[
+        valString := value printString
+    ] ifFalse:[
+        (value isSymbol or:[value isCharacter]) ifTrue:[
+            valString := value storeString
+        ] ifFalse:[
+            value isString ifTrue:[
+                valString := value contractTo:30.
+            ] ifFalse:[
+                value isColor ifTrue:[
+                    valString := value htmlPrintString
+                ].
+            ].
+        ]
+    ].
+
+    valString notNil ifTrue:[
+        plainString := (nameString allBold,' <',valString,'>').
+    ] ifFalse:[
+        plainString := nameString allBold
+    ].
+
+    value isColor ifTrue:[
+        plainString := plainString
+                     , '  ' , ('   '
+                        colorizeAllWith:((value brightness < 0.5)
+                                ifTrue:[ Color white ]
+                                ifFalse:[ Color black ])
+                        on:value).
+    ].
+
+    ^ LabelAndIcon string:plainString image:(self iconForValue:value)
+
+    "Created: / 16-05-2012 / 18:42:28 / cg"
 !
 
 stringWithAllIndexedVarValues
@@ -1839,7 +2282,7 @@
         firstRealIndex := 2.
     ].
 
-    [line := listView at:firstRealIndex. 
+    [line := self listEntryAt:firstRealIndex. 
      (line startsWith:'-') and:[line size < 2 or:[line second isDigit not]]] whileTrue:[
         firstRealIndex := firstRealIndex + 1.
         idx := idx - 1.
@@ -1868,7 +2311,7 @@
     ^ nil "/ indexed instvar or other selected
 
     "Created: / 03-08-2006 / 13:45:14 / cg"
-    "Modified: / 04-08-2006 / 11:45:29 / cg"
+    "Modified: / 16-05-2012 / 17:54:52 / cg"
 !
 
 fieldList 
@@ -1919,7 +2362,7 @@
     "return a list of indexes usable to access the object's indexed slots.
      Set hasMore to true, if a '...' entry should be added."
 
-    |objSz n cls sz|
+    |objSz n cls list|
 
     cls := object class.
 
@@ -1930,9 +2373,13 @@
         n := nShown.
         hasMore := true.
     ].
-    ^ (1 to:n)
-
-    "Modified: / 24-08-2010 / 17:56:23 / cg"
+    list := (1 to:n).
+    ^ list 
+"/        keysAndValuesCollect:[:idx :nm |
+"/            LabelAndIcon string:nm image:(self iconForValue:(object basicAt:idx))
+"/        ].
+
+    "Modified: / 16-05-2012 / 18:34:35 / cg"
 !
 
 indexOfFirstNamedInstvarInList
@@ -1949,19 +2396,21 @@
     [
         |line|
 
-        line := listView at:firstRealIndex. 
+        line := self listEntryAt:firstRealIndex. 
         (line startsWith:'-') and:[line size < 2 or:[line second isDigit not]]
     ] whileTrue:[
         firstRealIndex := firstRealIndex + 1.
     ].
     ^ firstRealIndex
+
+    "Modified: / 16-05-2012 / 17:54:46 / cg"
 !
 
 indexedFieldList 
     "return a list of indexed-variable names to show in the selectionList.
      Set hasMore to true, if a '...' entry should be added."
 
-    |l maxIndex sz|
+    |l maxIndex sz list|
 
     l := self indexList.
     l isEmptyOrNil ifTrue:[^ nil ].
@@ -1973,18 +2422,26 @@
         ] ifFalse:[
             sz := 0
         ].
-        ^ l collect:[:i | 
-            i isInteger ifTrue:[
-                (i printStringRadix:integerDisplayRadix size:sz fill:$0) 
-            ] ifFalse:[
-                i printString
-            ]
+        list := l collect:
+            [:i | 
+                i isInteger ifTrue:[
+                    (i printStringRadix:integerDisplayRadix size:sz fill:$0) 
+                ] ifFalse:[
+                    i printString
+                ]
             ]
     ] ifFalse:[
-        ^ l collect:[:i | i printString].
+        list := l collect:[:i | i printString].
     ].
 
-    "Modified: / 14-11-2011 / 12:56:12 / cg"
+    ^ list
+        keysAndValuesCollect:[:idx :nm |
+            self listEntryForName:nm value:(object at:idx)
+        ].
+
+    ^ list.
+
+    "Modified: / 16-05-2012 / 18:43:10 / cg"
 !
 
 indexedValueAtIndex:idx
@@ -2021,7 +2478,7 @@
         firstRealIndex := 2.
     ].
 
-    [line := listView at:firstRealIndex. 
+    [line :=self listEntryAt:firstRealIndex. 
      (line startsWith:'-') and:[line size < 2 or:[line second isDigit not]]] whileTrue:[
         firstRealIndex := firstRealIndex + 1.
         idx := idx - 1.
@@ -2042,7 +2499,7 @@
     ].
     ^ nil "/ indexed instvar or other selected
 
-    "Modified: / 31.10.2001 / 09:20:20 / cg"
+    "Modified: / 16-05-2012 / 17:54:41 / cg"
 !
 
 keyIndexForLine:lineNr
@@ -2063,7 +2520,7 @@
         firstRealIndex := firstRealIndex + 1.
     ].
 
-    [line := listView at:firstRealIndex. 
+    [line := self listEntryAt:firstRealIndex. 
      line notNil
      and:[(line startsWith:'-') and:[line size < 2 or:[line second isDigit not]]]
     ] whileTrue:[
@@ -2087,7 +2544,17 @@
     ].
     ^ idx - (nNamedInstvarsShown+nExtraNamedInstvarsShown).
 
-    "Modified: / 04-08-2006 / 11:45:42 / cg"
+    "Modified: / 16-05-2012 / 17:54:34 / cg"
+!
+
+listEntryAt:lineNr
+    |entry|
+
+    entry := listView at:lineNr.
+    entry isNil ifTrue:[^ entry].
+    ^ entry string
+
+    "Created: / 16-05-2012 / 17:53:39 / cg"
 !
 
 namedFieldAt:idx
@@ -2113,10 +2580,14 @@
         "/ hide some stuff
         aList := aList copyFrom:(self baseInspectedObjectClass instSize + 1).
     ].
+    ^ aList 
+        keysAndValuesCollect:[:idx :nm |
+            self listEntryForName:nm value:(object instVarAt:idx)
+        ].
 
     ^ aList
 
-    "Modified: / 18-09-2006 / 21:35:30 / cg"
+    "Modified: / 16-05-2012 / 18:43:23 / cg"
 !
 
 pseudoFieldNames
@@ -2193,7 +2664,7 @@
     ifTrue:[
         acceptAction := nil.
     ] ifFalse:[
-        sel := listView at:idx.
+        sel := self listEntryAt:idx.
 
         (sel startsWith:'-all') ifTrue:[
             acceptAction := nil.
@@ -2213,6 +2684,8 @@
     ].
 
     workspace acceptAction:acceptAction.
+
+    "Modified: / 16-05-2012 / 17:54:16 / cg"
 !
 
 setDoItAction
@@ -2288,9 +2761,9 @@
         ^ object
     ].
 
-    ((l := listView at:lineNr) startsWith:$-) ifTrue:[
+    ((l := self listEntryAt:lineNr) startsWith:$-) ifTrue:[
         (l ~= '-' and:[(l at:2) isDigit not "negative number"]) ifTrue:[
-            ^ self valueForSpecialLine:(listView at:lineNr)
+            ^ self valueForSpecialLine:l
         ].
     ].
 
@@ -2323,7 +2796,7 @@
     "/ nope
     ^ nil
 
-    "Modified: / 03-08-2006 / 14:05:30 / cg"
+    "Modified: / 16-05-2012 / 17:54:06 / cg"
 !
 
 valueAtLine:lineNr put:newValue
@@ -2534,9 +3007,9 @@
 !InspectorView methodsFor:'user interaction'!
 
 doAccept:theText
-    |sel newValue|
-
-    sel := listView at:(self theSingleSelectionIndex).
+    |sel newValue fieldNameList|
+
+    sel := self listEntryAt:(self theSingleSelectionIndex).
     (sel startsWith:'-all') ifTrue:[
         workspace flash.
         ^ self.
@@ -2554,8 +3027,16 @@
             (self valueAtLine:selectionIndex) value:newValue
         ] ifFalse:[
             self valueAtLine:selectionIndex put:newValue.
-        ]
+        ].
+        "/ update the fieldList...
+        fieldNameList := self fieldList.                               
+        hasMore ifTrue:[
+            fieldNameList add:' ... '
+        ].
+        listView contents:fieldNameList.
     ]
+
+    "Modified: / 04-06-2012 / 18:16:29 / cg"
 !
 
 doCopyKey
@@ -2713,13 +3194,13 @@
 !InspectorView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/InspectorView.st,v 1.249 2012/03/13 07:26:31 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/InspectorView.st,v 1.257 2012/06/04 16:17:33 cg Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libtool/InspectorView.st,v 1.249 2012/03/13 07:26:31 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libtool/InspectorView.st,v 1.257 2012/06/04 16:17:33 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: InspectorView.st 7952 2012-03-21 17:50:14Z vranyj1 $'
+    ^ '$Id: InspectorView.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/NewLauncher.st	Wed May 30 21:46:55 2012 +0100
+++ b/NewLauncher.st	Tue Jun 05 15:49:00 2012 +0100
@@ -2775,47 +2775,13 @@
          (MenuItem
             label: '-'
           )
-         (MenuItem
-            label: 'GUI'
-            translateLabel: true
-            "JV@2012-05-05: If not kept, installed menu items are not shown!!!!!!
-             Either keep it or patch it whenever popped up."
-            keepLinkedMenu: true
-            submenu:
-           (Menu
-              (
-               (MenuItem
-                  activeHelpKey: toolsGUIPainter
-                  label: 'GUI Painter'
-                  itemValue: openApplication:
-                  nameKey: guiPainter
-                  translateLabel: true
-                  labelImage: (ResourceRetriever ToolbarIconLibrary startUIPainterIcon 'GUI Painter')
-                  argument: 'UIPainter'
-                )
-               (MenuItem
-                  activeHelpKey: toolsMenuEditor
-                  label: 'Menu Editor'
-                  itemValue: openApplication:
-                  nameKey: menuEditor
-                  translateLabel: true
-                  labelImage: (ResourceRetriever ToolbarIconLibrary startMenuEditorIcon 'Menu Editor')
-                  argument: 'MenuEditor'
-                )
-               (MenuItem
-                  activeHelpKey: toolsImageEditor
-                  label: 'Image Editor'
-                  itemValue: openApplication:
-                  nameKey: imageEditor
-                  translateLabel: true
-                  labelImage: (ResourceRetriever ToolbarIconLibrary startImageEditorIcon 'Image Editor')
-                  argument: 'ImageEditor'
-                )
-               )
-              nil
-              nil
-            )
-          )
+       (MenuItem
+          enabled: monticelloRepositoryAvailable
+          label: 'Monticello Repository Browser'
+          itemValue: startMonticelloRepositoryBrowser
+          translateLabel: true
+          showBusyCursorWhilePerforming: true
+        )
          (MenuItem
             label: 'Programming'
             nameKey: programming
@@ -2878,6 +2844,44 @@
             )
           )
          (MenuItem
+            label: 'GUI'
+            translateLabel: true
+            submenu: 
+           (Menu
+              (
+               (MenuItem
+                  activeHelpKey: toolsGUIPainter
+                  label: 'GUI Painter'
+                  itemValue: openApplication:
+                  nameKey: guiPainter
+                  translateLabel: true
+                  labelImage: (ResourceRetriever ToolbarIconLibrary startUIPainterIcon 'GUI Painter')
+                  argument: 'UIPainter'
+                )
+               (MenuItem
+                  activeHelpKey: toolsMenuEditor
+                  label: 'Menu Editor'
+                  itemValue: openApplication:
+                  nameKey: menuEditor
+                  translateLabel: true
+                  labelImage: (ResourceRetriever ToolbarIconLibrary startMenuEditorIcon 'Menu Editor')
+                  argument: 'MenuEditor'
+                )
+               (MenuItem
+                  activeHelpKey: toolsImageEditor
+                  label: 'Image Editor'
+                  itemValue: openApplication:
+                  nameKey: imageEditor
+                  translateLabel: true
+                  labelImage: (ResourceRetriever ToolbarIconLibrary startImageEditorIcon 'Image Editor')
+                  argument: 'ImageEditor'
+                )
+               )
+              nil
+              nil
+            )
+          )
+         (MenuItem
             label: '-'
           )
          (MenuItem
@@ -3031,7 +3035,7 @@
         nil
       )
 
-    "Modified: / 05-05-2012 / 19:17:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified (format): / 27-04-2012 / 14:08:02 / cg"
 !
 
 windowsMenu
@@ -3523,13 +3527,7 @@
       and:[Demos::ChickenFun isRunning]]]
 !
 
-chickenFunRunning
-    "return a 'valueHolder', which returns true if the chickenFun demo is running."
-
-    ^ [Demos::ChickenFun notNil
-      and:[Demos::ChickenFun isLoaded
-      and:[Demos::ChickenFun isRunning]]]
-!
+
 
 debuggerHasIgnoredHalts
     ^ DebugView notNil and:[ DebugView hasIgnoredHalts ]
@@ -3871,7 +3869,7 @@
 
         freeMenuIndex == 0 ifTrue:[
             "item to insert relative to not found, insert at the begin or end"
-            freeMenuIndex := before ifTrue:1 ifFalse:[menuPanel numberOfItems + 1].
+            freeMenuIndex := before ifTrue:[1] ifFalse:[menuPanel numberOfItems + 1].
         ] ifFalse:[
             before ifFalse:[freeMenuIndex := freeMenuIndex +1].
         ].
@@ -3977,7 +3975,7 @@
             ]
         ].
         freeMenuIndex == 0 ifTrue:[
-            freeMenuIndex := before ifTrue:1 ifFalse:[menuPanel numberOfItems + 1].
+            freeMenuIndex := before ifTrue:[1] ifFalse:[menuPanel numberOfItems + 1].
         ] ifFalse:[
             before ifFalse:[freeMenuIndex := freeMenuIndex +1].
         ].
@@ -4535,25 +4533,25 @@
 !
 
 postOpenWith:aBuilder
-    |toolInfo addMenuForToolInfo window|
+    |toolInfo addMenuForToolInfo|
 
     "/ increase my priority"
 "/    self windowGroup process priority:(Processor userSchedulingPriority + 1).
     Processor activeProcess priority:(Processor userSchedulingPriority + 1).
 
     addMenuForToolInfo := 
-        [:toolInfo|
+        [:eachToolInfo|
             |menuItem originalLabel|
 
-            menuItem := toolInfo item.
-            originalLabel := toolInfo originalLabel.
+            menuItem := eachToolInfo item.
+            originalLabel := eachToolInfo originalLabel.
             originalLabel notNil ifTrue:[ menuItem label:originalLabel ].
             self 
                 addMenuItem:menuItem
-                from:(toolInfo resourceProvider)
-                in:toolInfo where
-                position:toolInfo positionSpec
-                space:toolInfo space
+                from:(eachToolInfo resourceProvider)
+                in:eachToolInfo where
+                position:eachToolInfo positionSpec
+                space:eachToolInfo space
         ].
 
     "/ add user tools
@@ -4975,13 +4973,13 @@
 !NewLauncher class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/NewLauncher.st,v 1.433 2012/05/02 12:29:02 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/NewLauncher.st,v 1.436 2012/06/01 11:23:14 cg Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libtool/NewLauncher.st,v 1.433 2012/05/02 12:29:02 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libtool/NewLauncher.st,v 1.436 2012/06/01 11:23:14 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: NewLauncher.st 7990 2012-05-05 22:06:53Z vranyj1 $'
+    ^ '$Id: NewLauncher.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/PerforceSourceCodeManagementSettingsAppl.st	Wed May 30 21:46:55 2012 +0100
+++ b/PerforceSourceCodeManagementSettingsAppl.st	Tue Jun 05 15:49:00 2012 +0100
@@ -14,7 +14,7 @@
 AbstractSourceCodeManagementSettingsAppl subclass:#PerforceSourceCodeManagementSettingsAppl
 	instanceVariableNames:'selectedPerModuleRoot perforceExecutableHolder
 		listOfPerforceModules defaultSettingsHolder tableColumns
-		defaultSettingsPrototypeList'
+		defaultSettingsPrototypeList checkLabel'
 	classVariableNames:'RecentlyUsedCVSRoots RecentlyUsedStoreHosts
 		RecentlyUsedSmallTeamHosts LastStoreHost LastStoreUser
 		LastStorePassword'
@@ -32,7 +32,7 @@
 !
 
 Object subclass:#ModuleManager
-	instanceVariableNames:'manager module settings app'
+	instanceVariableNames:'manager module settings app check checkIcon'
 	classVariableNames:''
 	poolDictionaries:''
 	privateIn:PerforceSourceCodeManagementSettingsAppl
@@ -190,7 +190,7 @@
           label: 'Source Code Manager Settings'
           name: 'Source Code Manager Settings'
           min: (Point 10 10)
-          bounds: (Rectangle 0 0 740 642)
+          bounds: (Rectangle 0 0 767 642)
         )
         component: 
        (SpecCollection
@@ -216,11 +216,19 @@
                        (CheckBoxSpec
                           label: 'Show in Browser Menus'
                           name: 'CheckBox1'
-                          layout: (LayoutFrame 0 0 5 0 0 1 27 0)
+                          layout: (LayoutFrame 0 0 5 0 -150 1 27 0)
+                          activeHelpKey: shownInBrowserMenus
                           model: shownInBrowserMenusHolder
-                                activeHelpKey: shownInBrowserMenus
                           translateLabel: true
                         )
+                       (ActionButtonSpec
+                          label: 'Check'
+                          name: 'Button6'
+                          layout: (LayoutFrame -150 1 5 0 -5 1 27 0)
+                          translateLabel: true
+                          labelChannel: checkLabel
+                          model: checkPerforceSettings
+                        )
                        (ViewSpec
                           name: 'Box3'
                           layout: (LayoutFrame 0 0 36 0 0 1 0 1)
@@ -284,7 +292,7 @@
                        )
                      
                     )
-                    extent: (Point 740 138)
+                    extent: (Point 767 138)
                   )
                  (ViewSpec
                     name: 'ManagerSetupBoxx'
@@ -327,7 +335,7 @@
                                       translateLabel: true
                                       tabable: true
                                       model: addPerModuleRoot
-                                      extent: (Point 345 22)
+                                      extent: (Point 361 22)
                                     )
                                    (ActionButtonSpec
                                       label: 'Remove'
@@ -336,7 +344,7 @@
                                       tabable: true
                                       model: removePerModuleRoot
                                       enableChannel: removeEnabled
-                                      extent: (Point 346 22)
+                                      extent: (Point 361 22)
                                     )
                                    )
                                  
@@ -349,7 +357,7 @@
                        )
                      
                     )
-                    extent: (Point 740 250)
+                    extent: (Point 767 250)
                   )
                  (FramedBoxSpec
                     label: 'Source Cache'
@@ -403,7 +411,7 @@
                                 translateLabel: true
                                 tabable: true
                                 model: flushSourceCache
-                                extent: (Point 238 22)
+                                extent: (Point 250 22)
                               )
                              (ActionButtonSpec
                                 label: 'Condense Cache now'
@@ -411,7 +419,7 @@
                                 translateLabel: true
                                 tabable: true
                                 model: condenseSourceCache
-                                extent: (Point 239 22)
+                                extent: (Point 250 22)
                               )
                              )
                            
@@ -420,7 +428,7 @@
                        )
                      
                     )
-                    extent: (Point 740 95)
+                    extent: (Point 767 95)
                   )
                  (ViewSpec
                     name: 'VerboseBox'
@@ -437,7 +445,7 @@
                        )
                      
                     )
-                    extent: (Point 740 25)
+                    extent: (Point 767 25)
                   )
                  )
                
@@ -447,8 +455,37 @@
          
         )
       )
+! !
 
-    "Modified: / 11-01-2012 / 15:39:42 / cg"
+!PerforceSourceCodeManagementSettingsAppl class methodsFor:'menu specs'!
+
+menuPerModule
+    "This resource specification was automatically generated
+     by the MenuEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the MenuEditor may not be able to read the specification."
+
+
+    "
+     MenuEditor new openOnClass:PerforceSourceCodeManagementSettingsAppl andSelector:#menuPerModule
+     (Menu new fromLiteralArrayEncoding:(PerforceSourceCodeManagementSettingsAppl menuPerModule)) startUp
+    "
+
+    <resource: #menu>
+
+    ^ 
+     #(Menu
+        (
+         (MenuItem
+            label: 'Check'
+            itemValue: checkPerforceSettings
+            translateLabel: true
+          )
+         )
+        nil
+        nil
+      )
 ! !
 
 !PerforceSourceCodeManagementSettingsAppl class methodsFor:'queries'!
@@ -471,7 +508,7 @@
      the DataSetBuilder may not be able to read the specification."
 
     "
-     DataSetBuilder new openOnClass:P4SourceCodeManagementSettingsAppl andSelector:#tableColumns
+     DataSetBuilder new openOnClass:PerforceSourceCodeManagementSettingsAppl andSelector:#tableColumns
     "
 
     <resource: #tableColumns>
@@ -481,17 +518,29 @@
          label: 'Module'
          labelButtonType: Button
          usePreferredWidth: true
+         width: 100
+         minWidth: 100
          model: module
+         menuFromApplication: false
        )
       (DataSetColumnSpec
          label: 'Settings'
          labelButtonType: Button
          editorType: InputField
          model: settings
+         menuFromApplication: false
+         isResizeable: false
+       )
+      (DataSetColumnSpec
+         label: 'Check'
+         labelButtonType: Button
+         model: check
+         menuFromApplication: false
+         doubleClickedSelector: doubleClick
          isResizeable: false
        )
       )
-
+    
 ! !
 
 !PerforceSourceCodeManagementSettingsAppl methodsFor:'actions'!
@@ -535,7 +584,6 @@
         ].
         moduleManager module:app moduleHolder value.
         moduleManager settings:app settingsHolder value.
-        moduleManager settings:app settingsHolder value.
         self listOfModules add:moduleManager.
         self updateModifiedChannel.
     ].
@@ -574,7 +622,7 @@
 !
 
 basicSaveSettings
-    |client settings repositoryInfoPerModule|
+    |client repositoryInfoPerModule|
 
     self hasManager ifTrue:[
         | nm fn|
@@ -605,13 +653,7 @@
         PerforceSourceCodeManager repositoryInfoPerModule:repositoryInfoPerModule.
         PerforceSourceCodeManager perforceExecutable:((self perforceExecutableHolder value ? '') withoutSeparators).
         client := self defaultSettingsHolder value.
-        client notNil ifTrue:[
-            settings := PerforceSourceCodeManager getPerforceSettingsFromString:client.
-            PerforceSourceCodeManager perforceClient:(settings at:#client ifAbsent:nil).
-            PerforceSourceCodeManager perforceUser:(settings at:#user ifAbsent:nil).
-            PerforceSourceCodeManager perforcePort:(settings at:#port ifAbsent:nil).
-            PerforceSourceCodeManager perforcePassword:(settings at:#password ifAbsent:nil).
-        ].
+        PerforceSourceCodeManager setDefaultPerforceSettingsFromString:client.
         PerforceSourceCodeManager verboseSourceCodeAccess:self verboseSourceCodeAccess value.
         PerforceSourceCodeManager shownInBrowserMenus:self shownInBrowserMenusHolder value. 
     ].
@@ -621,6 +663,38 @@
     "Modified: / 10-01-2012 / 00:21:59 / cg"
 !
 
+checkPerforceSettings
+
+    |result icon|
+
+    PerforceSourceCodeManager perforceError handle:[:ex|
+        self warn:ex description.
+        ^false
+    ] do:[
+        result := PerforceSourceCodeManager checkPerforceSettings:(self defaultSettingsHolder value) forPackage:nil.
+        result ifTrue:[
+            icon := GenericToolbarIconLibrary ledGreen14x14.
+        ] ifFalse:[
+            icon := GenericToolbarIconLibrary ledRed14x14.
+        ].
+        self checkLabel value:(LabelAndIcon label:'Check' icon:icon).
+    ].
+    ^false
+!
+
+condenseSourceCache
+    self withWaitCursorDo:[ AbstractSourceCodeManager condenseSourceCache ].
+    Method flushSourceStreamCache.
+
+    "Modified: / 28-11-2006 / 12:21:33 / cg"
+!
+
+flushSourceCache
+    self withWaitCursorDo:[ AbstractSourceCodeManager flushSourceCache ].
+
+    "Modified: / 30-09-2011 / 13:33:51 / cg"
+!
+
 removePerModuleRoot
 
     |module|
@@ -633,6 +707,25 @@
 
 !PerforceSourceCodeManagementSettingsAppl methodsFor:'aspects'!
 
+checkLabel
+    <resource: #uiAspect>
+
+    "automatically generated by UIPainter ..."
+
+    "*** the code below creates a default model when invoked."
+    "*** (which may not be the one you wanted)"
+    "*** Please change as required and accept it in the browser."
+    "*** (and replace this comment by something more useful ;-)"
+
+    checkLabel isNil ifTrue:[
+        checkLabel := 'Check' asValue.
+"/ if your app needs to be notified of changes, uncomment one of the lines below:
+"/       checkLabel addDependent:self.
+"/       checkLabel onChangeSend:#checkLabelChanged to:self.
+    ].
+    ^ checkLabel.
+!
+
 defaultSettingsHolder
 
     defaultSettingsHolder isNil ifTrue:[
@@ -705,6 +798,14 @@
 "/       tableColumns onChangeSend:#tableColumnsChanged to:self.
     ].
     ^ tableColumns.
+!
+
+verboseSourceCodeAccess
+    verboseSourceCodeAccess isNil ifTrue:[
+        verboseSourceCodeAccess := false asValue.
+        verboseSourceCodeAccess onChangeSend:#updateModifiedChannel to:self
+    ].
+    ^ verboseSourceCodeAccess.
 ! !
 
 !PerforceSourceCodeManagementSettingsAppl methodsFor:'change & update'!
@@ -754,13 +855,18 @@
         ^ self
     ].
 
+    changedObject == self listOfModules ifTrue:[
+        self updateModifiedChannel.
+    ].
+
     changedObject == defaultSettingsHolder ifTrue:[
         self updateModifiedChannel.
     ].
 
+
     super update:something with:aParameter from:changedObject
 
-    "Modified (format): / 02-03-2012 / 14:42:15 / cg"
+    "Modified: / 09-11-2006 / 14:41:10 / cg"
 ! !
 
 !PerforceSourceCodeManagementSettingsAppl methodsFor:'help'!
@@ -873,9 +979,9 @@
      the UIPainter may not be able to read the specification."
 
     "
-     UIPainter new openOnClass:P4SourceCodeManagementSettingsAppl::ManagerPerModuleApp andSelector:#windowSpec
-     P4SourceCodeManagementSettingsAppl::ManagerPerModuleApp new openInterface:#windowSpec
-     P4SourceCodeManagementSettingsAppl::ManagerPerModuleApp open
+     UIPainter new openOnClass:PerforceSourceCodeManagementSettingsAppl::ManagerPerModuleApp andSelector:#windowSpec
+     PerforceSourceCodeManagementSettingsAppl::ManagerPerModuleApp new openInterface:#windowSpec
+     PerforceSourceCodeManagementSettingsAppl::ManagerPerModuleApp open
     "
 
     <resource: #canvas>
@@ -971,6 +1077,8 @@
                        (ComboBoxSpec
                           name: 'ComboBox1'
                           model: settingsHolder
+                          immediateAccept: false
+                          acceptOnLostFocus: true
                           acceptOnPointerLeave: false
                           comboList: defaultSettingsPrototypeList
                           extent: (Point 465 20)
@@ -1169,6 +1277,34 @@
     app := something.
 !
 
+check
+
+    |icon|
+
+    check isNil ifTrue:[
+        ^'unchecked'
+    ].
+    check ifTrue:[
+        icon := GenericToolbarIconLibrary ledGreen14x14.
+    ] ifFalse:[
+        icon := GenericToolbarIconLibrary ledRed14x14.
+    ].
+
+    ^icon
+!
+
+check:something
+    check := something.
+!
+
+checkIcon
+    ^ checkIcon
+!
+
+checkIcon:something
+    checkIcon := something.
+!
+
 manager
     ^ manager
 !
@@ -1196,6 +1332,19 @@
     ].
 ! !
 
+!PerforceSourceCodeManagementSettingsAppl::ModuleManager methodsFor:'actions'!
+
+doubleClick
+
+    PerforceSourceCodeManager perforceError handle:[:ex|
+        self warn:ex description.
+        check := false.
+    ] do:[
+        check := PerforceSourceCodeManager checkPerforceSettings:settings forPackage:module.
+    ].
+    self changed.
+! !
+
 !PerforceSourceCodeManagementSettingsAppl::ModuleManager methodsFor:'comparing'!
 
 < aModuleManager
@@ -1217,13 +1366,13 @@
 !PerforceSourceCodeManagementSettingsAppl class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/PerforceSourceCodeManagementSettingsAppl.st,v 1.21 2012/03/02 13:51:07 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/PerforceSourceCodeManagementSettingsAppl.st,v 1.24 2012/06/01 22:21:24 cg Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libtool/PerforceSourceCodeManagementSettingsAppl.st,v 1.21 2012/03/02 13:51:07 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libtool/PerforceSourceCodeManagementSettingsAppl.st,v 1.24 2012/06/01 22:21:24 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: PerforceSourceCodeManagementSettingsAppl.st 7952 2012-03-21 17:50:14Z vranyj1 $'
+    ^ '$Id: PerforceSourceCodeManagementSettingsAppl.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/PerforceSourceCodeManagerUtilities.st	Tue Jun 05 15:49:00 2012 +0100
@@ -0,0 +1,3547 @@
+"{ Package: 'stx:libtool' }"
+
+SourceCodeManagerUtilities subclass:#PerforceSourceCodeManagerUtilities
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'System-SourceCodeManagement'
+!
+
+SimpleDialog subclass:#P4CheckinInfoDialog
+	instanceVariableNames:'descriptionHolder logMessageHolder isStableHolder tagHolder
+		quickCheckInHolder quickCheckInVisibleHolder allowEmptyLogMessage
+		warningMessageHolder logHistory logHistoryHeadLineSelectionHolder
+		submitHolder'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:PerforceSourceCodeManagerUtilities
+!
+
+SimpleDialog subclass:#SubmitInfoDialog
+	instanceVariableNames:'descriptionHolder logMessageHolder isStableHolder tagHolder
+		quickCheckInHolder quickCheckInVisibleHolder allowEmptyLogMessage
+		warningMessageHolder filesHolder tagItInHolder'
+	classVariableNames:'LastSourceLogMessage'
+	poolDictionaries:''
+	privateIn:PerforceSourceCodeManagerUtilities
+!
+
+Object subclass:#WorkSpace
+	instanceVariableNames:'client host owner root views perforceSettings temporaryWorkSpace
+		tempDirectory'
+	classVariableNames:'PerforceCommandSemaphore'
+	poolDictionaries:''
+	privateIn:PerforceSourceCodeManagerUtilities
+!
+
+Object subclass:#View
+	instanceVariableNames:'depot local workspace type'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:PerforceSourceCodeManagerUtilities::WorkSpace
+!
+
+
+!PerforceSourceCodeManagerUtilities class methodsFor:'class access'!
+
+submitInfoDialogClass
+
+    ^ SubmitInfoDialog
+
+    "Created: / 01-06-2012 / 11:09:15 / cg"
+!
+
+workSpaceClass
+    ^ WorkSpace
+
+    "Created: / 01-06-2012 / 11:13:49 / cg"
+! !
+
+!PerforceSourceCodeManagerUtilities methodsFor:'utilities-cvs'!
+
+checkinClass:aClass withInfo:aLogInfoOrNil withCheck:doCheckClass usingManager:managerOrNil
+    "check a class into the source repository.
+     If the argument, aLogInfoOrNil isNil, ask interactively for log-message.
+     If doCheckClass is true, the class is checked for send of halts etc."
+
+    |logMessage checkinInfo mgr pri doSubmit|
+
+    resources := self classResources.
+    doSubmit := false.
+
+    aClass isLoaded ifFalse:[
+        self information:(resources string:'Cannot checkin unloaded classes (%1)' with:aClass name).
+        ^ false.
+    ].
+
+    mgr := managerOrNil.
+    mgr isNil ifTrue:[
+        mgr := self sourceCodeManagerFor:aClass.
+        mgr isNil ifTrue:[
+            ^ false
+        ]
+    ].
+
+    self ensureCorrectVersionMethodsInClass:aClass usingManager:mgr.
+    mgr supportsCheckinLogMessages ifTrue:[
+        (self 
+            getLogMessageForClassCheckinTakingDefaultsFromPreviousLogInfo:aLogInfoOrNil 
+            forClass:aClass
+            valuesInto:[:logMessageRet :checkinInfoRet |
+                logMessage := logMessageRet.
+                checkinInfo := checkinInfoRet.
+                checkinInfo notNil ifTrue:[
+                    doSubmit := checkinInfo submitHolder value.
+                ].
+            ]
+        ) ifFalse:[^ false].
+    ].
+
+    (self classIsNotYetInRepository:aClass withManager:mgr) ifTrue:[
+        (self createSourceContainerForClass:aClass usingManager:mgr) ifFalse:[
+"/            self warn:'did not create a container for ''' , aClass name , ''''.
+            ^ false
+        ].
+        ^ true.
+    ].
+
+    self activityNotification:(resources string:'checking in %1' with:aClass name).
+    pri := Processor activePriority.
+    Processor activeProcess withPriority:pri-1 to:pri
+    do:[
+        |revision aborted|
+
+
+
+        aborted := false.
+        AbortOperationRequest handle:[:ex |
+            aborted := true.
+            ex return.
+        ] do:[
+            |checkinState cause|
+            checkinState := false.
+            cause := ''.
+            [
+                checkinState := mgr checkinClass:aClass logMessage:logMessage submit:doSubmit
+            ] on:SourceCodeManagerError do:[:ex| 
+self halt.
+                cause := ex description.
+                ex proceed.
+            ].
+
+            checkinState ifFalse:[
+                Transcript showCR:'checkin of ''' , aClass name , ''' failed - ', cause.
+                self warn:(resources stringWithCRs:'Checkin of "%1" failed\\' with:aClass name allBold),cause.
+                ^ false.
+            ].
+            checkinInfo notNil ifTrue:[
+                checkinInfo isStable ifTrue:[
+                    "set stable tag for class that has been checked in"
+                    self tagClass:aClass as:#stable.
+                ].
+                checkinInfo tagIt ifTrue:[
+                    "set an additional tag for class that has been checked in"
+                    self tagClass:aClass as:(checkinInfo tag).
+                ].
+            ].
+        ].
+        aborted ifTrue:[  |con|
+            Transcript showCR:'Checkin of ''' , aClass name , ''' aborted'.
+
+            AbortAllOperationWantedQuery query ifTrue:[
+                (Dialog 
+                    confirm:(resources stringWithCRs:'Checkin of "%1" aborted.\\Cancel all ?' with:aClass name)
+                    default:false)
+                ifTrue:[
+                    AbortAllOperationRequest raise.
+                ]
+            ].
+            ^ false.
+        ].
+    ].
+    ^ true
+
+    "Created: / 21-12-2011 / 18:19:14 / cg"
+! !
+
+!PerforceSourceCodeManagerUtilities methodsFor:'utilities-p4'!
+
+submit
+    self defaultManager submit
+! !
+
+!PerforceSourceCodeManagerUtilities methodsFor:'utilities-p4-interaction'!
+
+getCheckinInfoFor:aClassNameOrPackageNameString initialAnswer:initialAnswerOrNil withQuickOption:withQuickOption
+    "ask for a log message for checking in a class (plus checkinQuick state info),
+     and other info (mark as stable, for example).
+     Return the info-object (actually: the dialog) or nil if aborted."
+
+    |logMsg infoDialog|
+
+    infoDialog := self defaultManager checkInInfoDialogClass 
+                getCheckinInfoFor:aClassNameOrPackageNameString 
+                initialAnswer:(initialAnswerOrNil ? LastSourceLogMessage)
+                withQuickOption:withQuickOption.
+    infoDialog notNil ifTrue:[
+        logMsg := infoDialog logMessage.
+        logMsg notEmptyOrNil ifTrue:[
+            LastSourceLogMessage := logMsg
+        ].
+    ].
+    ^ infoDialog
+
+    "
+     SourceCodeManagerUtilities getCheckinInfoFor:'hello' initialAnswer:'bla'
+    "
+
+    "Modified: / 06-07-2010 / 11:21:28 / cg"
+! !
+
+!PerforceSourceCodeManagerUtilities::P4CheckinInfoDialog class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2005 eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
+documentation
+"
+    checkin-dialog.
+    used to be private in SourceCodeManagerUtilites.
+    moved to libtool because libbasic3 should not contain code inheriting from GUI classes.
+
+    [author:]
+
+    [see also:]
+
+    [instance variables:]
+
+    [class variables:]
+"
+! !
+
+!PerforceSourceCodeManagerUtilities::P4CheckinInfoDialog class methodsFor:'interface specs'!
+
+windowSpec
+    "This resource specification was automatically generated
+     by the UIPainter of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the UIPainter may not be able to read the specification."
+
+    "
+     UIPainter new openOnClass:PerforceSourceCodeManager::P4CheckinInfoDialog andSelector:#windowSpec
+     PerforceSourceCodeManager::P4CheckinInfoDialog new openInterface:#windowSpec
+     PerforceSourceCodeManager::P4CheckinInfoDialog open
+    "
+
+    <resource: #canvas>
+
+    ^ 
+     #(FullSpec
+        name: windowSpec
+        window: 
+       (WindowSpec
+          label: 'Enter Log Message'
+          name: 'Enter Log Message'
+          min: (Point 10 10)
+          bounds: (Rectangle 0 0 800 327)
+        )
+        component: 
+       (SpecCollection
+          collection: (
+           (HorizontalPanelViewSpec
+              name: 'HorizontalPanel2'
+              layout: (LayoutFrame 0 0.0 0 0 0 1.0 32 0)
+              horizontalLayout: left
+              verticalLayout: center
+              horizontalSpace: 0
+              verticalSpace: 3
+              component: 
+             (SpecCollection
+                collection: (
+                 (LabelSpec
+                    label: 'Enter checkIn log-message for:'
+                    name: 'Label1'
+                    translateLabel: true
+                    resizeForLabel: true
+                    useDefaultExtent: true
+                  )
+                 (LabelSpec
+                    name: 'Label2'
+                    translateLabel: true
+                    labelChannel: descriptionHolder
+                    useDefaultExtent: true
+                  )
+                 )
+               
+              )
+            )
+           (TextEditorSpec
+              name: 'TextEditor1'
+              layout: (LayoutFrame 2 0.0 38 0 -2 1 -125 1)
+              model: logMessageHolder
+              hasHorizontalScrollBar: true
+              hasVerticalScrollBar: true
+              hasKeyboardFocusInitially: false
+            )
+           (LabelSpec
+              name: 'Label4'
+              layout: (LayoutFrame 0 0.0 -119 1 0 1.0 -97 1)
+              translateLabel: true
+              labelChannel: warningMessageHolder
+            )
+           (CheckBoxSpec
+              label: 'Quick Checkin (Only Classes in ChangeSet)'
+              name: 'CheckInChangedOnlyCheckbox'
+              layout: (LayoutFrame 3 0 -95 1 -3 0.5 -73 1)
+              visibilityChannel: quickCheckInVisibleHolder
+              model: quickCheckInHolder
+              translateLabel: true
+            )
+           (CheckBoxSpec
+              label: 'Mark as Stable'
+              name: 'MarkStableCheckBox'
+              layout: (LayoutFrame 3 0 -68 1 -3 1 -46 1)
+              model: isStableHolder
+              translateLabel: true
+            )
+           (LabelSpec
+              label: 'Tag:'
+              name: 'Label3'
+              layout: (LayoutFrame -40 0.5 -67 1 0 0.5 -45 1)
+              translateLabel: true
+              adjust: right
+            )
+           (InputFieldSpec
+              name: 'TagEntryField'
+              layout: (LayoutFrame 0 0.5 -68 1 -3 1 -46 1)
+              enableChannel: tagItInHolder
+              model: tagHolder
+              acceptOnReturn: true
+              acceptOnTab: true
+              acceptOnLostFocus: true
+              acceptOnPointerLeave: false
+            )
+           (HorizontalPanelViewSpec
+              name: 'ButtonPanel1'
+              layout: (LayoutFrame 0 0.0 -40 1 0 1.0 0 1.0)
+              horizontalLayout: fitSpace
+              verticalLayout: center
+              horizontalSpace: 3
+              verticalSpace: 2
+              reverseOrderIfOKAtLeft: true
+              component: 
+             (SpecCollection
+                collection: (
+                 (ActionButtonSpec
+                    label: 'Cancel'
+                    name: 'Button2'
+                    translateLabel: true
+                    model: doCancel
+                    extent: (Point 395 22)
+                  )
+                 (ActionButtonSpec
+                    label: 'OK'
+                    name: 'Button1'
+                    translateLabel: true
+                    model: doAccept
+                    extent: (Point 396 22)
+                  )
+                 )
+               
+              )
+            )
+           (CheckBoxSpec
+              label: 'Immediate Submit'
+              name: 'CheckBox1'
+              layout: (LayoutFrame 3 0.5 -95 1 -3 1 -73 1)
+              model: submitHolder
+              translateLabel: true
+            )
+           )
+         
+        )
+      )
+! !
+
+!PerforceSourceCodeManagerUtilities::P4CheckinInfoDialog class methodsFor:'opening'!
+
+getCheckinInfoFor:aString initialAnswer:initialAnswer
+    ^ self 
+        getCheckinInfoFor:aString 
+        initialAnswer:initialAnswer 
+        withQuickOption:false
+
+    "
+      self getCheckinInfoFor:'hello' initialAnswer:'bla'
+    "
+
+    "Modified (format): / 12-03-2012 / 12:38:48 / cg"
+!
+
+getCheckinInfoFor:aClassNameOrPackageNameString initialAnswer:initialAnswer withQuickOption:withQuickOption
+    ^ self
+        getCheckinInfoFor:aClassNameOrPackageNameString 
+        initialAnswer:initialAnswer 
+        withQuickOption:withQuickOption
+        logHistory:#()
+
+    "
+     self getCheckinInfoFor:'hello' initialAnswer:'bla'
+    "
+
+    "Modified: / 12-03-2012 / 12:39:00 / cg"
+!
+
+getCheckinInfoFor:aClassNameOrPackageNameString initialAnswer:initialAnswer withQuickOption:withQuickOption logHistory:logHistoryArg
+    |dialog warnMessage|
+
+    warnMessage := nil.
+
+    [
+        dialog := self new.
+        dialog 
+            description:aClassNameOrPackageNameString; 
+            logMessage:initialAnswer;
+            withQuickOption:withQuickOption;
+            logHistory:logHistoryArg.
+
+        dialog warningMessageHolder value:warnMessage.
+        dialog open.
+        dialog accepted ifFalse:[ ^ nil ].
+    ] doUntil:[
+        |stopAsking|
+
+        stopAsking := dialog allowEmptyLogMessage 
+                      or:[ dialog logMessage withoutSeparators notEmptyOrNil ].
+        stopAsking ifFalse:[
+            warnMessage := (self resources string:'Please enter a description of your changes!!') 
+                                asText 
+                                    colorizeAllWith:Color red.
+        ].
+        stopAsking
+    ].
+    ^ dialog    
+
+
+    "
+     self getCheckinInfoFor:'hello' initialAnswer:'bla'
+    "
+
+    "Created: / 12-03-2012 / 12:36:26 / cg"
+! !
+
+!PerforceSourceCodeManagerUtilities::P4CheckinInfoDialog methodsFor:'accessing'!
+
+allowEmptyLogMessage
+    ^ allowEmptyLogMessage ? false
+
+    "Created: / 06-07-2010 / 11:23:18 / cg"
+!
+
+allowEmptyLogMessage:aBoolean 
+    allowEmptyLogMessage := aBoolean
+
+    "Created: / 06-07-2010 / 11:23:31 / cg"
+!
+
+description
+    ^ self descriptionHolder value
+!
+
+description:aString
+    self descriptionHolder value:aString allBold
+!
+
+isStable
+    ^ self isStableHolder value
+!
+
+isStable:aBoolean
+    self isStableHolder value:aBoolean
+!
+
+logHistory:something
+    logHistory := something.
+!
+
+logMessage
+    ^ self logMessageHolder value
+!
+
+logMessage:aString
+    self logMessageHolder value:aString
+!
+
+quickCheckIn
+    ^ self quickCheckInHolder value
+!
+
+quickCheckIn:aBoolean
+    self quickCheckInHolder value:aBoolean
+!
+
+tag
+    ^ self tagHolder value withoutSeparators
+!
+
+tag:aStringOrNil
+    self tagHolder value:aStringOrNil
+
+    "Modified: / 12-09-2006 / 12:03:50 / cg"
+!
+
+tagIt
+    ^ self tag notEmptyOrNil
+
+    "Created: / 12-09-2006 / 13:06:49 / cg"
+!
+
+withQuickOption:aBoolean
+    ^ self quickCheckInVisibleHolder value:aBoolean
+! !
+
+!PerforceSourceCodeManagerUtilities::P4CheckinInfoDialog methodsFor:'aspects'!
+
+descriptionHolder
+    descriptionHolder isNil ifTrue:[
+        descriptionHolder := ValueHolder new.
+    ].
+    ^ descriptionHolder
+!
+
+isStableHolder
+    isStableHolder isNil ifTrue:[
+        isStableHolder := false asValue.
+    ].
+    ^ isStableHolder.
+
+    "Modified: / 16-01-2007 / 16:00:26 / cg"
+!
+
+logHistoryHeadLineSelectionHolder
+    logHistoryHeadLineSelectionHolder isNil ifTrue:[
+        logHistoryHeadLineSelectionHolder := nil asValue.
+        logHistoryHeadLineSelectionHolder 
+            onChangeEvaluate:
+                [
+                    self logMessageHolder value:(logHistory at:logHistoryHeadLineSelectionHolder value)
+                ].
+    ].
+    ^ logHistoryHeadLineSelectionHolder
+
+    "Created: / 12-03-2012 / 12:40:36 / cg"
+!
+
+logHistoryHeadLines
+    ^ (logHistory ? #())
+        collect:[:msg |
+            msg withoutLeadingSeparators asCollectionOfLines first , '...'
+        ]
+
+    "Created: / 12-03-2012 / 12:39:35 / cg"
+!
+
+logMessageHolder
+    logMessageHolder isNil ifTrue:[
+        logMessageHolder := '' asValue.
+    ].
+    ^ logMessageHolder.
+
+    "Modified: / 12-03-2012 / 12:34:13 / cg"
+!
+
+quickCheckInHolder
+    quickCheckInHolder isNil ifTrue:[
+        quickCheckInHolder := true asValue.
+    ].
+    ^ quickCheckInHolder
+!
+
+quickCheckInVisibleHolder
+    quickCheckInVisibleHolder isNil ifTrue:[
+        quickCheckInVisibleHolder := false asValue.
+    ].
+    ^ quickCheckInVisibleHolder
+!
+
+submitHolder
+    submitHolder isNil ifTrue:[
+        submitHolder := false asValue.
+    ].
+    ^ submitHolder
+!
+
+tagHolder
+    tagHolder isNil ifTrue:[
+        tagHolder := '' asValue.
+    ].
+    ^ tagHolder
+!
+
+warningMessageHolder
+    warningMessageHolder isNil ifTrue:[
+        warningMessageHolder := nil asValue.
+    ].
+    ^ warningMessageHolder.
+
+    "Created: / 06-07-2010 / 11:30:29 / cg"
+! !
+
+!PerforceSourceCodeManagerUtilities::SubmitInfoDialog class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2005 eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
+documentation
+"
+    checkin-dialog.
+    used to be private in SourceCodeManagerUtilites.
+    moved to libtool because libbasic3 should not contain code inheriting from GUI classes.
+
+    [author:]
+
+    [see also:]
+
+    [instance variables:]
+
+    [class variables:]
+"
+! !
+
+!PerforceSourceCodeManagerUtilities::SubmitInfoDialog class methodsFor:'interface specs'!
+
+windowSpec
+    "This resource specification was automatically generated
+     by the UIPainter of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the UIPainter may not be able to read the specification."
+
+    "
+     UIPainter new openOnClass:PerforceSourceCodeManager::SubmitInfoDialog andSelector:#windowSpec
+     PerforceSourceCodeManager::SubmitInfoDialog new openInterface:#windowSpec
+     PerforceSourceCodeManager::SubmitInfoDialog open
+    "
+
+    <resource: #canvas>
+
+    ^ 
+     #(FullSpec
+        name: windowSpec
+        window: 
+       (WindowSpec
+          label: 'Enter Log Message'
+          name: 'Enter Log Message'
+          min: (Point 10 10)
+          bounds: (Rectangle 0 0 563 561)
+        )
+        component: 
+       (SpecCollection
+          collection: (
+           (HorizontalPanelViewSpec
+              name: 'HorizontalPanel2'
+              layout: (LayoutFrame 0 0.0 0 0 0 1.0 32 0)
+              horizontalLayout: left
+              verticalLayout: center
+              horizontalSpace: 0
+              verticalSpace: 3
+              component: 
+             (SpecCollection
+                collection: (
+                 (LabelSpec
+                    label: 'Enter checkIn log-message for:'
+                    name: 'Label1'
+                    translateLabel: true
+                    resizeForLabel: true
+                    useDefaultExtent: true
+                  )
+                 (LabelSpec
+                    name: 'Label2'
+                    translateLabel: true
+                    labelChannel: descriptionHolder
+                    useDefaultExtent: true
+                  )
+                 )
+               
+              )
+            )
+           (VerticalPanelViewSpec
+              name: 'VerticalPanel1'
+              layout: (LayoutFrame 0 0.0 38 0 0 1.0 -80 1)
+              horizontalLayout: fit
+              verticalLayout: topFit
+              horizontalSpace: 3
+              verticalSpace: 3
+              component: 
+             (SpecCollection
+                collection: (
+                 (LabelSpec
+                    label: 'Files:'
+                    name: 'Label4'
+                    translateLabel: true
+                    adjust: left
+                    extent: (Point 563 23)
+                  )
+                 (TextEditorSpec
+                    name: 'TextEditor1'
+                    enableChannel: false
+                    model: filesHolder
+                    hasHorizontalScrollBar: true
+                    hasVerticalScrollBar: true
+                    hasKeyboardFocusInitially: false
+                    extent: (Point 563 146)
+                  )
+                 (LabelSpec
+                    label: 'Log Message:'
+                    name: 'Label5'
+                    translateLabel: true
+                    adjust: left
+                    extent: (Point 563 23)
+                  )
+                 (TextEditorSpec
+                    name: 'TextEditor2'
+                    model: logMessageHolder
+                    hasHorizontalScrollBar: true
+                    hasVerticalScrollBar: true
+                    hasKeyboardFocusInitially: false
+                    extent: (Point 563 242)
+                  )
+                 )
+               
+              )
+            )
+           (CheckBoxSpec
+              label: 'Mark as Stable'
+              name: 'MarkStableCheckBox'
+              layout: (LayoutFrame 3 0 -68 1 -3 1 -46 1)
+              model: isStableHolder
+              translateLabel: true
+            )
+           (LabelSpec
+              label: 'Tag:'
+              name: 'Label3'
+              layout: (LayoutFrame -40 0.5 -67 1 0 0.5 -45 1)
+              translateLabel: true
+              adjust: right
+            )
+           (InputFieldSpec
+              name: 'TagEntryField'
+              layout: (LayoutFrame 0 0.5 -68 1 -3 1 -46 1)
+              enableChannel: tagItInHolder
+              model: tagHolder
+              acceptOnReturn: true
+              acceptOnTab: true
+              acceptOnLostFocus: true
+              acceptOnPointerLeave: false
+            )
+           (HorizontalPanelViewSpec
+              name: 'ButtonPanel1'
+              layout: (LayoutFrame 0 0.0 -40 1 0 1.0 0 1.0)
+              horizontalLayout: fitSpace
+              verticalLayout: center
+              horizontalSpace: 3
+              verticalSpace: 2
+              reverseOrderIfOKAtLeft: true
+              component: 
+             (SpecCollection
+                collection: (
+                 (ActionButtonSpec
+                    label: 'Cancel'
+                    name: 'Button2'
+                    translateLabel: true
+                    model: doCancel
+                    extent: (Point 277 22)
+                  )
+                 (ActionButtonSpec
+                    label: 'OK'
+                    name: 'Button1'
+                    translateLabel: true
+                    model: doAccept
+                    extent: (Point 277 22)
+                  )
+                 )
+               
+              )
+            )
+           )
+         
+        )
+      )
+! !
+
+!PerforceSourceCodeManagerUtilities::SubmitInfoDialog class methodsFor:'opening'!
+
+getCheckinInfoFor:aClassNameOrPackageNameString initialAnswer:initialAnswer withFileList:fileList
+    |dialog warnMessage|
+
+    warnMessage := nil.
+
+    [
+        dialog := self new.
+        dialog 
+            description:aClassNameOrPackageNameString; 
+            logMessage:initialAnswer;
+            files:fileList.
+
+        dialog warningMessageHolder value:warnMessage.
+        dialog open.
+        dialog accepted ifFalse:[ ^ nil ].
+    ] doUntil:[
+        |stopAsking|
+
+        stopAsking := dialog allowEmptyLogMessage 
+                      or:[ dialog logMessage withoutSeparators notEmptyOrNil ].
+        stopAsking ifFalse:[
+            warnMessage := (self resources string:'Please enter a description of your changes!!') 
+                                asText 
+                                    colorizeAllWith:Color red.
+        ].
+        stopAsking
+    ].
+    ^ dialog    
+
+
+    "
+     self getCheckinInfoFor:'hello' initialAnswer:'bla'
+    "
+
+    "Modified: / 06-07-2010 / 11:40:00 / cg"
+!
+
+getCheckinInfoFor:aClassNameOrPackageNameString initialAnswer:initialAnswer withQuickOption:withQuickOption
+    |dialog warnMessage|
+
+    warnMessage := nil.
+
+    [
+        dialog := self new.
+        dialog 
+            description:aClassNameOrPackageNameString; 
+            logMessage:initialAnswer;
+            withQuickOption:withQuickOption.
+
+        dialog warningMessageHolder value:warnMessage.
+        dialog open.
+        dialog accepted ifFalse:[ ^ nil ].
+    ] doUntil:[
+        |stopAsking|
+
+        stopAsking := dialog allowEmptyLogMessage 
+                      or:[ dialog logMessage withoutSeparators notEmptyOrNil ].
+        stopAsking ifFalse:[
+            warnMessage := (self resources string:'Please enter a description of your changes!!') 
+                                asText 
+                                    colorizeAllWith:Color red.
+        ].
+        stopAsking
+    ].
+    ^ dialog    
+
+
+    "
+     self getCheckinInfoFor:'hello' initialAnswer:'bla'
+    "
+
+    "Modified: / 06-07-2010 / 11:40:00 / cg"
+! !
+
+!PerforceSourceCodeManagerUtilities::SubmitInfoDialog methodsFor:'accessing'!
+
+allowEmptyLogMessage
+    ^ allowEmptyLogMessage ? false
+
+    "Created: / 06-07-2010 / 11:23:18 / cg"
+!
+
+allowEmptyLogMessage:aBoolean 
+    allowEmptyLogMessage := aBoolean
+
+    "Created: / 06-07-2010 / 11:23:31 / cg"
+!
+
+description
+    ^ self descriptionHolder value
+!
+
+description:aString
+    self descriptionHolder value:aString allBold
+!
+
+files
+    ^ self filesHolder value
+!
+
+files:aString
+    self filesHolder value:aString
+!
+
+isStable
+    ^ self isStableHolder value
+!
+
+isStable:aBoolean
+    self isStableHolder value:aBoolean
+!
+
+logMessage
+    ^ self logMessageHolder value
+!
+
+logMessage:aString
+    self logMessageHolder value:aString
+!
+
+quickCheckIn
+    ^ self quickCheckInHolder value
+!
+
+quickCheckIn:aBoolean
+    self quickCheckInHolder value:aBoolean
+!
+
+tag
+    ^ self tagHolder value withoutSeparators
+!
+
+tag:aStringOrNil
+    self tagHolder value:aStringOrNil
+
+    "Modified: / 12-09-2006 / 12:03:50 / cg"
+!
+
+tagIt
+    ^ self tag notEmptyOrNil
+
+    "Created: / 12-09-2006 / 13:06:49 / cg"
+!
+
+withQuickOption:aBoolean
+    ^ self quickCheckInVisibleHolder value:aBoolean
+! !
+
+!PerforceSourceCodeManagerUtilities::SubmitInfoDialog methodsFor:'aspects'!
+
+descriptionHolder
+    descriptionHolder isNil ifTrue:[
+        descriptionHolder := ValueHolder new.
+    ].
+    ^ descriptionHolder
+!
+
+filesHolder
+    <resource: #uiAspect>
+
+    "automatically generated by UIPainter ..."
+
+    "*** the code below creates a default model when invoked."
+    "*** (which may not be the one you wanted)"
+    "*** Please change as required and accept it in the browser."
+    "*** (and replace this comment by something more useful ;-)"
+
+    filesHolder isNil ifTrue:[
+        filesHolder := '' asValue.
+"/ if your app needs to be notified of changes, uncomment one of the lines below:
+"/       filesHolder addDependent:self.
+"/       filesHolder onChangeSend:#filesHolderChanged to:self.
+    ].
+    ^ filesHolder.
+!
+
+isStableHolder
+    isStableHolder isNil ifTrue:[
+        isStableHolder := false asValue.
+    ].
+    ^ isStableHolder.
+
+    "Modified: / 16-01-2007 / 16:00:26 / cg"
+!
+
+logMessageHolder
+    logMessageHolder isNil ifTrue:[
+        logMessageHolder := LastSourceLogMessage asValue.
+    ].
+    ^ logMessageHolder.
+!
+
+quickCheckInHolder
+    quickCheckInHolder isNil ifTrue:[
+        quickCheckInHolder := true asValue.
+    ].
+    ^ quickCheckInHolder
+!
+
+quickCheckInVisibleHolder
+    quickCheckInVisibleHolder isNil ifTrue:[
+        quickCheckInVisibleHolder := false asValue.
+    ].
+    ^ quickCheckInVisibleHolder
+!
+
+tagHolder
+    tagHolder isNil ifTrue:[
+        tagHolder := '' asValue.
+    ].
+    ^ tagHolder
+!
+
+tagItInHolder
+    <resource: #uiAspect>
+
+    "automatically generated by UIPainter ..."
+
+    "*** the code below creates a default model when invoked."
+    "*** (which may not be the one you wanted)"
+    "*** Please change as required and accept it in the browser."
+    "*** (and replace this comment by something more useful ;-)"
+
+    tagItInHolder isNil ifTrue:[
+        tagItInHolder := true asValue.
+"/ if your app needs to be notified of changes, uncomment one of the lines below:
+"/       tagItInHolder addDependent:self.
+"/       tagItInHolder onChangeSend:#tagItInHolderChanged to:self.
+    ].
+    ^ tagItInHolder.
+!
+
+warningMessageHolder
+    warningMessageHolder isNil ifTrue:[
+        warningMessageHolder := nil asValue.
+    ].
+    ^ warningMessageHolder.
+
+    "Created: / 06-07-2010 / 11:30:29 / cg"
+! !
+
+!PerforceSourceCodeManagerUtilities::WorkSpace class methodsFor:'instance creation'!
+
+newWorkSpaceFor:aSettingsString  
+    "
+        get the workspace definition from perforce client command output
+    "
+    
+    |workSpace|
+
+    aSettingsString isEmptyOrNil ifTrue:[ ^nil].
+    workSpace := self new initialize.
+    ^ workSpace newWorkSpaceFor:aSettingsString
+!
+
+newWorkSpaceForSettings:settingsDict
+    "
+        get the workspace definition from perforce client command output"
+    
+    |workSpace|
+
+    workSpace := self new initialize.
+    ^ workSpace newWorkSpaceForSettings:settingsDict
+! !
+
+!PerforceSourceCodeManagerUtilities::WorkSpace methodsFor:'accessing'!
+
+client
+    ^ client
+!
+
+client:something
+    client := something.
+!
+
+host
+    ^ host
+!
+
+host:something
+    host := something.
+!
+
+owner
+    ^ owner
+!
+
+owner:something
+    owner := something.
+!
+
+perforceSettings
+
+    perforceSettings isNil ifTrue:[
+        perforceSettings := Dictionary new.
+    ].
+    ^ perforceSettings
+!
+
+perforceSettings:something
+    perforceSettings := something.
+    self owner:(perforceSettings at:#user ifAbsent:nil).
+    self client:(perforceSettings at:#client ifAbsent:nil).
+!
+
+root
+    ^ root
+!
+
+root:something
+    root := something.
+!
+
+tempDirectory
+
+    tempDirectory isNil ifTrue:[
+        tempDirectory := PerforceSourceCodeManager createTempDirectory:nil forModule:nil.
+    ].
+    ^ tempDirectory
+!
+
+temporaryWorkSpace
+    ^ temporaryWorkSpace
+!
+
+views
+    views isNil ifTrue:[
+        views := OrderedCollection new.
+    ].
+    ^ views
+! !
+
+!PerforceSourceCodeManagerUtilities::WorkSpace methodsFor:'actions'!
+
+addCheckIn:checkInDefinition submit:doSubmit
+
+    | packagePath fullFilename s perforceCommand outputStream errorStream result tmpFilename binRevision newRevisionString number|
+
+    " create container for class initial check in"
+    checkInDefinition isClassCheckin ifTrue:[
+        binRevision := checkInDefinition getBinaryRevisionNumber.
+        (binRevision notNil and:[binRevision ~= 0]) ifTrue:[
+            (Dialog confirm:('Someone seems to have removed the source container for ',checkInDefinition definitionObjectString,'\\Force new checkin ?') withCRs) ifTrue:[
+                checkInDefinition definitionClass setBinaryRevision:nil.
+            ] ifFalse:[
+                ^false
+            ].
+        ].
+    ].
+    "initial checkin here"
+    self activityNotification:'adding ' , checkInDefinition definitionObjectString , ' to perforce repository...'.
+    self getTemporaryWorkspaceFor:checkInDefinition.
+    self temporaryWorkSpace isNil ifTrue:[
+        self perforceError raiseErrorString:('Error getting temporary workspace when adding ', checkInDefinition definitionObjectString, '.').
+        ^false
+    ].
+    number := self getChangeListNumber.
+    number isNil ifTrue:[
+        self perforceError raiseErrorString:('Error when getting a change list for ', checkInDefinition definitionObjectString, '.').
+        ^false
+    ].
+    packagePath := Smalltalk packageDirectoryForPackageId:checkInDefinition package.
+    fullFilename := (packagePath construct:checkInDefinition packageDir) construct:checkInDefinition fileName.
+    tmpFilename := self getTemporaryFilenameFor:fullFilename pathName.
+    tmpFilename directory recursiveMakeDirectory.
+    s := tmpFilename writeStream.
+    checkInDefinition isClassCheckin ifTrue:[
+        newRevisionString := self initialRevisionStringFor:checkInDefinition.
+        PerforceSourceCodeManager updateVersionMethod:(PerforceSourceCodeManager nameOfVersionMethodInClasses) 
+            of:checkInDefinition definitionClass 
+            for:newRevisionString.
+    ].
+    checkInDefinition isClassCheckin ifTrue:[
+        PerforceSourceCodeManager fileOutSourceCodeOf:checkInDefinition definitionClass on:s.
+    ] ifFalse:[
+        s nextPutAll:checkInDefinition fileContents.
+    ].
+    s close.
+    perforceCommand := ('add  -t +ko -c ' , number printString, ' "', tmpFilename pathName, '"').
+    outputStream := ReadWriteStream on:''.
+    errorStream := ReadWriteStream on:''.
+    result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root 
+        inputFrom:nil outputTo:outputStream 
+        errorTo:errorStream
+        logHeader:('adding ', checkInDefinition definitionObjectString, '.').
+    result ifFalse:[
+        checkInDefinition isClassCheckin ifTrue:[
+            Class withoutUpdatingChangesDo:[
+                checkInDefinition definitionClass class removeSelector:PerforceSourceCodeManager nameOfVersionMethodInClasses    
+            ].
+        ].
+        ^ false
+    ].
+    result := self changeChangeDescriptionTo:checkInDefinition logMessage asStringCollection changeNumber:number printString.
+    doSubmit ifTrue:[
+        result := self submitChangeNumber:number printString.
+        checkInDefinition isClassCheckin ifFalse:[
+            " checkout in real workspace "
+            perforceCommand := ('sync ' , number printString, ' "', fullFilename pathName, '"').
+            outputStream := ReadWriteStream on:''.
+            errorStream := ReadWriteStream on:''.
+            result := self executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root 
+                inputFrom:nil outputTo:outputStream 
+                errorTo:errorStream
+                logHeader:('sync in my workspace ', checkInDefinition definitionObjectString, '.').
+            result ifFalse:[
+                ^ false
+            ].        
+        ].
+    ].
+
+    self activityNotification:''.
+    ^result
+!
+
+askForMergedSource:mergedSource 
+    localSource:mySource 
+    changesDict:changesDict 
+    haveRevision:haveRevision 
+    changesAsLogged:changesAsLogged 
+    pathName:pathName
+    definitionClass:definitionClass
+
+    |msg answer checkInRepaired emphasizedText emSep diffTextComment didAccept editor repairedText resultSource|
+
+    (changesDict notNil and:[(changesDict at:#conflicting) > 0]) ifTrue:[
+        "ooops must resolve conflicts"
+        msg := self messageForConflictsInClass:definitionClass revision:haveRevision.
+        answer := self checkinTroubleDialog:'Version conflict'
+             message:msg
+             log:changesAsLogged
+             abortable:false
+             option:'show conflicts'
+             option2:'resolve conflicts'.
+
+        answer == #option ifTrue:[
+            "/
+            "/ show conflicts in a 3-way DiffTextView ...
+            "/
+            Diff3TextView
+                openOnMergedText:mergedSource
+                label:'your version (checkin attempt)'
+                label:'original (base version)'
+                label:'newest repository version'.
+        ].
+
+        checkInRepaired := false.
+        answer == #option2 ifTrue:[
+            "/
+            "/ allow checkin of repair version
+            "/ this is error prone ...
+            "/
+            "/
+            "/ show merged version in an editor ...
+            "/ ... accept will check it in.
+            "/
+            emphasizedText := mergedSource asStringCollection.
+            emSep := (Array with:(#color->Color black) with:(#backgroundColor->Color green)).
+            emphasizedText := Diff3TextView
+                        emphasizeMergedDiff3TextFromPerforce:emphasizedText
+                        origEmphasis:(Array with:(#color->Color black) with:(#backgroundColor->Color yellow))
+                        otherEmphasis:(Array with:(#color->Color white) with:(#backgroundColor->Color red))
+                        yourEmphasis:(Array with:(#color->Color white) with:(#backgroundColor->Color red))
+                        separatorEmphasis:emSep.
+
+            diffTextComment := self diffTextComment.
+            diffTextComment := (Text string:diffTextComment emphasis:emSep) asStringCollection.
+            emphasizedText := diffTextComment , emphasizedText.
+
+            didAccept := false. checkInRepaired := true.
+            [didAccept not and:[checkInRepaired]] whileTrue:[
+                editor := RCSConflictEditTextView
+                            setupWith:emphasizedText
+                            title:'Resolve conflicts in ' , pathName asFilename baseName , ', then accept & close to checkin'.
+
+                editor acceptAction:[:dummy |
+                    repairedText := editor list.
+                    didAccept := true.
+                ].
+                didAccept := false.
+                editor topView openModal.
+
+                didAccept ifFalse:[
+                    (Dialog confirm:'You did not accept the new text. Edit again ?')
+                    ifFalse:[
+                        checkInRepaired := false.
+                    ]
+                ] ifTrue:[
+                    "/ check if all green-stuff (separators) have been removed
+                    (repairedText findFirst:[:line | line notNil and:[line notEmpty and:[(line emphasisAt:1) = emSep]]]) ~~ 0 ifTrue:[
+                        self warn:'You have to look at ALL conflicts, and remove ALL green lines as a confirmation !!'.
+                        didAccept := false.
+                    ]
+                ].
+            ].
+            resultSource := repairedText asString string.
+        ].
+
+        checkInRepaired ifTrue:[
+            Transcript showCR:'checking in ' , pathName asFilename baseName , ' (manually repaired version) ...'
+        ] ifFalse:[
+            'PerforceSourceCodeManager [warning]: cannot (for now) checkin; conflicts found' infoPrintCR.
+            Transcript showCR:'checkin of ' , pathName asFilename baseName , ' aborted (conflicting changes; repository unchanged)'.
+            ^ nil.
+        ]
+    ] ifFalse:[
+        mySource = mergedSource ifTrue:[
+            msg := self messageForNoChangesInClass:definitionClass.
+            self checkinTroubleDialog:'Merging versions'
+                           message:msg
+                           log:changesAsLogged
+                           abortable:false
+                           option:nil.
+        ] ifFalse:[
+            msg := self messageForChangesInClass:definitionClass revision:haveRevision.
+            answer := self checkinTroubleDialog:'Merging versions'
+                           message:msg
+                           log:changesAsLogged
+                           abortable:true
+                           option:'Stop - see first'.
+            answer ~~ true ifTrue:[
+                answer == #option ifTrue:[
+                    DiffCodeView
+                        openOn:mySource
+                        label:'current version'
+                        and:mergedSource
+                        label:'merged version'.
+
+                ].
+                Transcript showCR:'checkin aborted - (no merge; repository unchanged)'.
+                ^ nil.
+            ].
+            resultSource := mergedSource.
+        ].
+    ].
+    ^ resultSource
+
+    "Modified (format): / 01-06-2012 / 10:45:09 / cg"
+!
+
+changeChangeDescriptionTo:logLines changeNumber:changeNumber
+
+    |perforceCommand outputStream errorStream changeListFile result changeFileContents changeListFileStream firstIndex oldLogFileLines writeNextLine newLogFileLines currentTokenLineParts currentToken|
+
+    perforceCommand := 'change -o ', (changeNumber ? '').
+    outputStream := ReadWriteStream on:''.                                       
+    errorStream := ReadWriteStream on:''.
+    result := self temporaryWorkSpace executePerforceCommand:perforceCommand
+                        inDirectory:self tempDirectory
+                        inputFrom:nil
+                        outputTo:outputStream
+                        errorTo:errorStream
+                        logHeader:('get change desription for change ', changeNumber printString, '.').
+    result ifFalse:[
+        ^ false
+    ].
+    changeFileContents := outputStream contents.
+    changeFileContents isEmptyOrNil ifTrue:[
+        ^false
+    ].
+    changeListFile := self tempDirectory construct:'change'.
+    changeListFileStream := changeListFile writeStream.
+    changeFileContents := changeFileContents asStringCollection.
+    firstIndex := changeFileContents indexOfLineStartingWith:'Description:'.
+    firstIndex == 0 ifTrue:[
+        ^false
+    ].
+    oldLogFileLines := StringCollection new.
+    changeFileContents from:firstIndex do:[:aLine|
+        ((aLine size > 1) and:[aLine first ~= $# and:[aLine first isSeparator not]]) ifTrue:[
+            currentTokenLineParts := aLine asCollectionOfSubstringsSeparatedBy:$:.
+            currentTokenLineParts size > 1 ifTrue:[
+                currentToken := currentTokenLineParts first.
+            ].
+        ].
+        ((aLine size > 1) and:[aLine first isSeparator and:[currentToken = 'Description']]) ifTrue:[
+            oldLogFileLines add:(aLine copyFrom:2).
+        ].
+    ].
+    newLogFileLines := StringCollection new.
+    changeNumber isNil ifTrue:[
+        newLogFileLines := logLines.
+    ] ifFalse:[
+        (oldLogFileLines asString includesString:logLines asString) ifTrue:[
+            newLogFileLines := oldLogFileLines.
+        ] ifFalse:[
+            newLogFileLines := oldLogFileLines.
+            newLogFileLines addAll:logLines
+        ].
+    ].
+    writeNextLine := true.
+    changeFileContents do:[:aLine|
+        writeNextLine ifFalse:[
+            (aLine notEmpty and:[aLine first isSeparator not]) ifTrue:[
+                writeNextLine := true.
+            ].
+        ].
+        writeNextLine ifTrue:[
+            (aLine startsWith:'Description:') ifTrue:[
+                changeListFileStream nextPutLine:aLine.
+                newLogFileLines do:[:logLine|
+                    changeListFileStream nextPut:Character tab.
+                    changeListFileStream nextPutLine:logLine.
+                ].
+                writeNextLine := false.
+            ] ifFalse:[
+                changeListFileStream nextPutLine:aLine
+            ].
+        ].
+    ].
+    changeListFileStream close.
+    perforceCommand := ('change -i < "', changeListFile pathName, '"').
+    outputStream := ReadWriteStream on:''.
+    errorStream := ReadWriteStream on:''.
+    result := self temporaryWorkSpace executePerforceCommand:perforceCommand
+                        inDirectory:self tempDirectory
+                        inputFrom:nil
+                        outputTo:outputStream
+                        errorTo:errorStream
+                        logHeader:('write change desription for change ', changeNumber printString, '.').
+    result ifFalse:[
+        ^false
+    ].
+    ^ true
+!
+
+checkForExistingContainer:checkInDefinition
+
+
+    |perforceCommand outputStream errorStream result packagePath fullFilename depotPath|
+
+    packagePath := Smalltalk packageDirectoryForPackageId:checkInDefinition package.
+    fullFilename := packagePath construct:checkInDefinition packageDir.
+    depotPath := self getDepotPathForLocalPath:fullFilename pathName.
+    perforceCommand := ('dirs "' ,depotPath , '"').
+    outputStream := ReadWriteStream on:''.
+    errorStream := ReadWriteStream on:''.
+    result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root 
+        inputFrom:nil outputTo:outputStream 
+        errorTo:errorStream
+        logHeader:('dirs in checkForExistingContainer for ', depotPath, '.').
+    result ifFalse:[
+        ^ false
+    ].
+    errorStream contents notEmpty ifTrue:[
+        ^false
+    ].
+    ^ true
+!
+
+checkIn:checkInDefinition submit:doSubmit
+
+    | packagePath fullFilename s perforceCommand outputStream errorStream result tmpFilename fileNameAndRev tmpFilenameAndRev 
+      haveChange nextVersionMethod diffOutput number baseRevision cls newestInRepository newVersionString openChangeNumber|
+
+    self activityNotification:'checkin ' , checkInDefinition definitionObjectString , ' to perforce repository...'.
+    [                                 
+        cls := checkInDefinition definitionClass.
+        self getTemporaryWorkspaceFor:checkInDefinition.
+        self temporaryWorkSpace isNil ifTrue:[
+            self perforceError raiseErrorString:('Error getting temporary workspace when check in ', checkInDefinition definitionObjectString, '.').
+            ^false.
+        ].
+        baseRevision := checkInDefinition getLocalRevisionNumber.
+        newestInRepository := checkInDefinition getReposRevisionNumberBeforeCheckin.
+        baseRevision isNil ifTrue:[
+            self perforceError raiseErrorString:('No local revision for ', checkInDefinition definitionObjectString,' - should not happen here.').
+            ^false
+        ].
+        packagePath := Smalltalk packageDirectoryForPackageId:checkInDefinition package.
+        fullFilename := (packagePath construct:checkInDefinition packageDir) construct:checkInDefinition fileName.
+        tmpFilename := self getTemporaryFilenameFor:fullFilename pathName.
+        tmpFilename directory recursiveMakeDirectory.
+        checkInDefinition isClassCheckin ifTrue:[
+            baseRevision > newestInRepository ifTrue:[
+                openChangeNumber := self getOpenChangeFor:checkInDefinition.
+                openChangeNumber isNil ifTrue:[
+                    (Dialog confirm:('The version-info of ',checkInDefinition definitionObjectString allBold,' is wrong \(The class version (',baseRevision printString allBold,') is newer than the newest version in the repository (',newestInRepository printString allBold,').\\Patch the version and checkin ?') withCRs)
+                    ifTrue:[
+                        newVersionString := self updatedRevisionStringOf:cls 
+                                                    forRevision:newestInRepository printString with:(cls revisionStringOfManager:self).
+                        PerforceSourceCodeManager updateVersionMethod:(PerforceSourceCodeManager nameOfVersionMethodInClasses) 
+                            of:cls 
+                            for:newVersionString.
+
+                        cls updateVersionMethodFor:newVersionString.
+                    ].
+                ].
+            ].
+        ].
+        fileNameAndRev := checkInDefinition fileName, '#', baseRevision printString.
+        tmpFilenameAndRev := tmpFilename directory construct:fileNameAndRev.
+
+        openChangeNumber notNil ifTrue:[
+            s := tmpFilename writeStream.
+            checkInDefinition isClassCheckin ifTrue:[
+                PerforceSourceCodeManager fileOutSourceCodeOf:cls on:s.
+            ] ifFalse:[
+                self halt.
+                s nextPutAll:''.
+            ].
+            s close.
+            self changeChangeDescriptionTo:checkInDefinition logMessage asStringCollection changeNumber:openChangeNumber printString.
+            doSubmit ifTrue:[
+                self submitChangeNumber:openChangeNumber printString
+            ].
+            ^true
+        ].
+
+        perforceCommand := ('sync "' , tmpFilenameAndRev pathName, '"').
+        outputStream := ReadWriteStream on:''.
+        errorStream := ReadWriteStream on:''.
+        result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root 
+            inputFrom:nil outputTo:outputStream 
+            errorTo:errorStream
+            logHeader:('sync ', checkInDefinition definitionObjectString, ' to revision ', baseRevision printString, '.').
+        result ifFalse:[
+            ^ false
+        ].
+
+        number := self getChangeListNumber.
+        number isNil ifTrue:[
+            self perforceError raiseErrorString:('Error when getting a change list for ', checkInDefinition definitionObjectString, '.').
+            ^false
+        ].
+        perforceCommand := ('edit -c ' ,number printString, ' "', tmpFilename pathName, '"').
+        outputStream := ReadWriteStream on:''.
+        errorStream := ReadWriteStream on:''.
+        result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root 
+            inputFrom:nil outputTo:outputStream 
+            errorTo:errorStream
+            logHeader:('edit ', checkInDefinition definitionObjectString, '.').
+        result ifFalse:[
+            ^ false
+        ].
+        s := tmpFilename writeStream.
+        checkInDefinition isClassCheckin ifTrue:[
+            PerforceSourceCodeManager fileOutSourceCodeOf:cls on:s.
+        ] ifFalse:[
+            self halt.
+            s nextPutAll:''.
+        ].
+        s close.
+        perforceCommand := ('diff -db -dw -dl "' , tmpFilename pathName, '"').
+        outputStream := ReadWriteStream on:''.
+        errorStream := ReadWriteStream on:''.
+        result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root 
+            inputFrom:nil outputTo:outputStream 
+            errorTo:errorStream
+            logHeader:('diff ', checkInDefinition definitionObjectString, '.').
+        diffOutput := outputStream contents asStringCollection.
+        haveChange := diffOutput isEmptyOrNil or:[diffOutput notEmptyOrNil and:[diffOutput size > 1]].
+        haveChange ifFalse:[
+            self information:checkInDefinition definitionObjectString, ' not changed for revision ', baseRevision printString.
+            perforceCommand := ('revert "' , tmpFilename pathName, '"').
+            outputStream := ReadWriteStream on:''.
+            errorStream := ReadWriteStream on:''.
+            result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root 
+                inputFrom:nil outputTo:outputStream 
+                errorTo:errorStream
+                logHeader:('revert ', checkInDefinition definitionObjectString, '.').
+            ^true
+        ].
+        checkInDefinition isClassCheckin ifTrue:[
+            nextVersionMethod := self nextRevisionStringFor:checkInDefinition.
+            nextVersionMethod isNil ifTrue:[
+                self perforceError raiseErrorString:('Cant get next version method string for ', checkInDefinition definitionObjectString, ' revision ', baseRevision printString, '.').
+                ^false
+            ].
+            PerforceSourceCodeManager updateVersionMethod:(PerforceSourceCodeManager nameOfVersionMethodInClasses) 
+                    of:cls 
+                    for:nextVersionMethod.
+        ].
+        result := self changeChangeDescriptionTo:checkInDefinition logMessage asStringCollection changeNumber:number printString.
+        doSubmit ifTrue:[
+            result := self submitChangeNumber:number printString
+        ].
+    ] ensure:[
+        self activityNotification:''.
+    ].
+    ^result
+!
+
+createChange
+
+    ^self changeChangeDescriptionTo:('' asStringCollection) changeNumber:nil
+!
+
+createWorkSpaceClientSpecFor:checkInDefinition
+
+    |ws myView|
+
+    ws := WriteStream on:''.
+    ws nextPutAll:'Client: '.
+    ws nextPutAll:(self client).
+    ws cr.
+    ws nextPutAll:'Owner: '.
+    ws nextPutAll:(self owner).
+    ws cr.
+    ws nextPutAll:'Host: '.
+    ws nextPutAll:(self host).
+    ws cr.
+    ws nextPutAll:'Description: '.
+    ws nextPutAll:'Used temporary for Smalltalk/X'.
+    ws cr.
+    ws nextPutAll:'Root: '.
+    ws nextPutAll:(self root asFilename pathName).
+    ws cr.
+    ws nextPutAll:'Options: '.
+    ws nextPutAll:'allwrite noclobber nocompress unlocked nomodtime normdir'.
+    ws cr.
+    ws nextPutAll:'SubmitOptions: '.
+    ws nextPutAll:'submitunchanged'.
+    ws cr.
+    ws nextPutAll:'LineEnd: '.
+    ws nextPutAll:'local'.
+    ws cr.
+    ws nextPutAll:'View: '.
+    myView := checkInDefinition workSpace getViewForPackage:checkInDefinition package.
+    ws nextPutAll:myView depot.
+    ws space.
+    ws nextPutAll:'//', self client, '/...'.
+    ws cr.
+    ws close.
+    ^ws contents
+!
+
+delete:checkInDefinition submit:doSubmit
+
+    | packagePath fullFilename perforceCommand outputStream errorStream result tmpFilename number newestInRepository|
+
+    self activityNotification:'delete ' , checkInDefinition definitionObjectString , ' from perforce repository...'.
+    [
+        newestInRepository := checkInDefinition getReposRevisionNumberBeforeCheckin.
+        newestInRepository isNil ifTrue:[
+            self information:(checkInDefinition definitionObjectString, ' not exists in repository.').
+            ^true
+        ].
+        self getTemporaryWorkspaceFor:checkInDefinition.
+        self temporaryWorkSpace isNil ifTrue:[
+            self perforceError raiseErrorString:('Error getting temporary workspace when check in ', checkInDefinition definitionObjectString, '.').
+            ^false.
+        ].
+        packagePath := Smalltalk packageDirectoryForPackageId:checkInDefinition package.
+        fullFilename := (packagePath construct:checkInDefinition packageDir) construct:checkInDefinition fileName.
+        tmpFilename := self getTemporaryFilenameFor:fullFilename pathName.
+        tmpFilename directory recursiveMakeDirectory.
+
+        number := self getChangeListNumber.
+        number isNil ifTrue:[
+            self perforceError raiseErrorString:('Error when getting a change list for ', checkInDefinition definitionObjectString, '.').
+            ^false
+        ].
+        perforceCommand := ('delete -c ' ,number printString, ' "', tmpFilename pathName, '"').
+        outputStream := ReadWriteStream on:''.
+        errorStream := ReadWriteStream on:''.
+        result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root 
+            inputFrom:nil outputTo:outputStream 
+            errorTo:errorStream
+            logHeader:('Error delete ', checkInDefinition definitionObjectString, '.').
+        result ifFalse:[
+            ^ false
+        ].
+        result := self changeChangeDescriptionTo:checkInDefinition logMessage asStringCollection changeNumber:number printString.
+        doSubmit ifTrue:[
+            result := self submitChangeNumber:number printString
+        ].
+    ] ensure:[
+        self activityNotification:''.
+    ].
+    ^result
+!
+
+deleteWorkSpaceFromServer
+
+    |perforceCommand outputStream errorStream result|
+
+    perforceCommand := ('client -df ', client).
+    outputStream := ReadWriteStream on:''.
+    errorStream := ReadWriteStream on:''.
+    result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root 
+        inputFrom:nil outputTo:outputStream 
+        errorTo:errorStream
+        logHeader:('delete client ', client).
+    result ifFalse:[
+        ^ false
+    ].
+    ^true
+!
+
+getChangeDespriptionInfoFor:changeNumber
+
+    |valuePairs startLineIndex keyEndIndex changeContents cmd outputStream errorStream result keyValues beginLine endLine keyName keyValue|
+
+    valuePairs := OrderedCollection new.
+    cmd := 'change -o ', (changeNumber ? '').
+    outputStream := ReadWriteStream on:''.                                       
+    errorStream := ReadWriteStream on:''.
+    result := self temporaryWorkSpace executePerforceCommand:cmd
+                        inDirectory:self tempDirectory
+                        inputFrom:nil
+                        outputTo:outputStream
+                        errorTo:errorStream
+                        logHeader:('getting change description ', (changeNumber ? ''), '.').
+    result ifFalse:[
+        ^ nil
+    ].
+    changeContents := outputStream contents asStringCollection.
+    changeContents doWithIndex:[:aLine :index|
+        startLineIndex isNil ifTrue:[
+            (aLine isEmpty or:[(aLine startsWith:$#) or:[aLine first isSeparator]]) ifFalse:[
+                keyEndIndex := aLine indexOf:$:.
+                keyEndIndex ~= 0 ifTrue:[
+                    startLineIndex := index.
+                    valuePairs add:(Array with:index with:nil with:(aLine copyTo:keyEndIndex - 1)).
+                ].
+            ].
+        ] ifFalse:[
+            (aLine isEmpty or:[aLine startsWith:$#]) ifTrue:[
+                valuePairs last at:2 put:index.
+                startLineIndex := nil.
+            ].
+        ].
+    ].
+    keyValues := Dictionary new.
+    valuePairs do:[:each|
+        beginLine := each first.
+        endLine := each second.
+        keyName := each last.
+        (beginLine == (endLine - 1)) ifTrue:[
+            keyValue := (changeContents at:beginLine) copyFrom:(keyName size + 2).
+            keyValue := (keyValue withoutLeadingSeparators withoutTrailingSeparators) asStringCollection.
+        ] ifFalse:[
+            keyValue := changeContents copyFrom:(beginLine + 1) to:(endLine - 1).
+            keyValue := keyValue collect:[:each | each withoutLeadingSeparators withoutTrailingSeparators].
+        ].
+        keyValues at:keyName put:keyValue.
+    ].
+    ^ keyValues.
+!
+
+getChangeListNumber
+
+    |numbers|
+
+    numbers := self getCurrentChangeListNumbers.
+    numbers notEmptyOrNil ifTrue:[
+        ^numbers first.
+    ].
+    self createChange ifTrue:[
+        numbers := self getCurrentChangeListNumbers.
+        numbers notEmptyOrNil ifTrue:[
+            ^numbers first.
+        ].
+        
+    ].
+    ^nil
+!
+
+getCurrentChangeListNumbers
+
+    |perforceCommand outputStream errorStream result pendingChangesOutput words numbers number|
+
+    perforceCommand := 'changes -s pending -u ', owner.
+    outputStream := ReadWriteStream on:''.                                       
+    errorStream := ReadWriteStream on:''.
+    result := self temporaryWorkSpace executePerforceCommand:perforceCommand
+                        inDirectory:self tempDirectory
+                        inputFrom:nil
+                        outputTo:outputStream
+                        errorTo:errorStream
+                        doLog:false.
+    result ifFalse:[
+        ^ nil
+    ].
+    numbers := OrderedCollection new.
+    pendingChangesOutput := outputStream contents asStringCollection.
+    pendingChangesOutput do:[:eachLine|
+        words := eachLine asCollectionOfWords.
+        words size > 1 ifTrue:[
+            number := Number readFrom:(ReadStream on:(words at:2)) onError:nil.
+            numbers add:number.                              
+        ].
+    ].
+    ^numbers
+!
+
+getFileStatForPathname:aPathname
+
+
+    |perforceCommand outputStream errorStream result fileStatDict endOfKeywordIndex keyWord keyValue|
+
+    perforceCommand := ('fstat  "' , aPathname, '"').
+    outputStream := ReadWriteStream on:''.
+    errorStream := ReadWriteStream on:''.
+    result := self executePerforceCommand:perforceCommand inDirectory:self root 
+        inputFrom:nil outputTo:outputStream 
+        errorTo:errorStream
+        logHeader:('getting file status from ', aPathname, '.').
+    result ifFalse:[
+        ^ nil
+    ].
+    fileStatDict := Dictionary new.
+    outputStream contents asStringCollection do:[:aLine|
+        endOfKeywordIndex := aLine indexOfSeparatorStartingAt:5.
+        keyWord := aLine copyFrom:5 to:(endOfKeywordIndex - 1).
+        keyValue := aLine copyFrom:endOfKeywordIndex + 1.
+        fileStatDict at:keyWord put:keyValue.
+    ].
+    ^ fileStatDict
+
+"
+     | workSpace tempWorkSpace dict|
+    workSpace := PerforceSourceCodeManager getWorkSpaceForPackage:'applistx'.
+    tempWorkSpace := workSpace temporaryWorkSpace.
+    dict := tempWorkSpace getFileStatForPathname:'C:\Dokumente und Einstellungen\gds2180\Lokale Einstellungen\Temp\stx_tmp\st6120368\applistx\util\libDataType\ActionLQualifier.st'.
+    dict includesKey:'unresolved'
+"
+!
+
+getOpenChangeFor:checkInDefinition
+
+    |numbers changeDescr files versionInfo|
+
+    numbers := self getCurrentChangeListNumbers.
+    numbers notEmptyOrNil ifTrue:[
+        numbers do:[:changeNumber|
+            changeDescr := self getChangeDespriptionInfoFor:changeNumber printString.
+            files := changeDescr at:#Files ifAbsent:[nil].
+            files notNil ifTrue:[
+                versionInfo := PerforceSourceCodeManager versionInfoClass fromRCSString:checkInDefinition getLocalRevisionString.
+                files do:[:aFileAndAction|
+                    (aFileAndAction startsWith:versionInfo repositoryPathName) ifTrue:[
+                        ^changeNumber
+                    ].
+                ].
+            ].
+        ].
+    ].
+    ^nil
+!
+
+getTemporaryWorkspaceFor:checkInDefinition
+    "
+        create an temporary workspace for handle checkin
+    "
+
+    |workSpaceName workSpaceDefinitionFilename ws perforceCommand result readStream  directory 
+     settingsTemporary myView outputStream errorStream lineStream clientSpec index words|
+
+    directory := self tempDirectory.
+    workSpaceName := self temporaryClientName.
+    perforceCommand := 'clients -u ' , (self perforceSettings at:#user).
+    outputStream := ReadWriteStream on:''.
+    errorStream := ReadWriteStream on:''.
+    result := self executePerforceCommand:perforceCommand
+                        inDirectory:directory pathName
+                        inputFrom:nil
+                        outputTo:outputStream
+                        errorTo:errorStream
+                        doLog:false
+                        logHeader:('check for existing workspace client.').
+    result ifFalse:[
+        temporaryWorkSpace := nil.
+    ]. 
+    index := outputStream contents asStringCollection findFirst:[:aLine|
+        words := aLine asCollectionOfWords.
+        words size > 1 and:[words second = workSpaceName]
+    ].
+    index = 0 ifTrue:[
+        temporaryWorkSpace := nil.   
+    ].
+    temporaryWorkSpace isNil ifTrue:[
+        directory exists ifFalse:[
+            self perforceError raiseErrorString:('Perforce temporary workspace directory ', directory pathName, ' not exists.').
+            ^nil
+        ].
+        settingsTemporary := self perforceSettings copy.
+        settingsTemporary at:#client put:workSpaceName.
+        temporaryWorkSpace := self class newWorkSpaceForSettings:settingsTemporary.
+        temporaryWorkSpace root:directory asFilename pathName.
+        temporaryWorkSpace host:self host.
+        myView := self getViewForPackage:checkInDefinition package.
+        lineStream := WriteStream on:''.
+        lineStream nextPutAll:myView depot.
+        lineStream space.
+        lineStream nextPutAll:'//', workSpaceName, '/...'.
+        temporaryWorkSpace views add:(View newFromLine:lineStream contents workspace:temporaryWorkSpace).
+        workSpaceDefinitionFilename := directory asFilename construct:workSpaceName.
+        clientSpec := temporaryWorkSpace createWorkSpaceClientSpecFor:checkInDefinition.
+        ws := workSpaceDefinitionFilename writeStream.
+        ws nextPutAll:clientSpec.
+        ws close.
+
+        readStream := ReadStream on:clientSpec.
+        perforceCommand := 'client -i < "', workSpaceDefinitionFilename pathName, '"'.
+        outputStream := ReadWriteStream on:''.
+        errorStream := ReadWriteStream on:''.
+        result := temporaryWorkSpace executePerforceCommand:perforceCommand
+                            inDirectory:directory pathName
+                            inputFrom:nil
+                            outputTo:outputStream 
+                            errorTo:errorStream
+                            doLog:false
+                            logHeader:('writing temporary workspace definition.').
+        result ifFalse:[
+            temporaryWorkSpace := nil.
+        ]. 
+    ].
+    ^temporaryWorkSpace
+!
+
+mergeOrResolveConflictsForChangeNumber:aNumber
+
+    | tmpFilename perforceCommand outputStream errorStream result s 
+      changesAsLogged inStream line changesDict chunksPart words mergedSource mySource 
+      localRevision resultSource definitionClass descriptionInfo resolveFiles depotPath localPath checkInDefinition fileStatDict|
+
+    self temporaryWorkSpace isNil ifTrue:[
+        ^false
+    ].
+    descriptionInfo := (self getChangeDespriptionInfoFor:aNumber printString).
+    descriptionInfo isNil ifTrue:[
+        ^false.
+    ].
+    resolveFiles := descriptionInfo at:#Files ifAbsent:nil.
+    resolveFiles isNil ifTrue:[
+        ^false.
+    ].
+    resolveFiles do:[:aFileLine|
+        depotPath := (aFileLine copyTo:((aFileLine lastIndexOf:$#) - 1 )) withoutTrailingSeparators.
+        localPath := self temporaryWorkSpace getLocalPathForDepotPath:depotPath.
+        fileStatDict := self temporaryWorkSpace getFileStatForPathname:localPath.
+        (fileStatDict includesKey:'unresolved') ifTrue:[
+            definitionClass := Smalltalk at:(localPath asFilename withoutSuffix baseName asSymbol) ifAbsent:nil.
+            checkInDefinition := PerforceSourceCodeManager getCheckInDefinitionForClass:definitionClass.
+            localRevision := checkInDefinition getLocalRevisionNumber.
+            tmpFilename := localPath asFilename.
+            perforceCommand := ('resolve -af  "' , tmpFilename pathName, '"').
+            outputStream := ReadWriteStream on:''.
+            errorStream := ReadWriteStream on:''.
+            result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root 
+                inputFrom:nil outputTo:outputStream 
+                errorTo:errorStream
+                logHeader:('resolving ', tmpFilename pathName, '.').
+            result ifFalse:[
+                ^ false
+            ].
+            "check for conflicts"
+            changesAsLogged := StringCollection new.
+            inStream := ReadStream on:(outputStream contents).
+
+            [inStream atEnd not] whileTrue:[
+                line:= inStream nextLine.
+                line notNil ifTrue:[
+                    (line startsWith:'Diff chunks:') ifTrue:[
+                        changesAsLogged add:line.
+                        changesDict := Dictionary new.
+                        chunksPart := line copyFrom:('Diff chunks:' size + 1).
+                        (chunksPart asCollectionOfSubstringsSeparatedBy:$+) do:[:eachElement|
+                            words := eachElement asCollectionOfWords.
+                            changesDict at:words second asSymbol put:words first asNumber.
+                        ].
+                    ].
+                ].
+            ].
+            s := WriteStream on:String new.
+            PerforceSourceCodeManager fileOutSourceCodeOf:definitionClass on:s.
+            mergedSource := tmpFilename readStream contents asString.
+            mySource := s contents asString.
+            resultSource := self askForMergedSource:mergedSource 
+                    localSource:mySource 
+                    changesDict:changesDict 
+                    haveRevision:(fileStatDict at:'haveRev' ifAbsent:nil) 
+                    changesAsLogged:changesAsLogged 
+                    pathName:tmpFilename pathName
+                    definitionClass:definitionClass.
+            resultSource isNil ifTrue:[
+                ^false.
+            ].
+            "now we have a merge - lets get latest revision and write on it "
+            perforceCommand := ('revert "' , tmpFilename pathName, '"').
+            outputStream := ReadWriteStream on:''.
+            errorStream := ReadWriteStream on:''.
+            result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root 
+                inputFrom:nil outputTo:outputStream 
+                errorTo:errorStream
+                logHeader:('revert after resolving ', tmpFilename pathName, '.').
+            result ifFalse:[
+                ^ false
+            ].
+
+            tmpFilename remove.
+
+            perforceCommand := ('sync -f "' , tmpFilename pathName, '"').
+            outputStream := ReadWriteStream on:''.
+            errorStream := ReadWriteStream on:''.
+            result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root 
+                inputFrom:nil outputTo:outputStream 
+                errorTo:errorStream
+                logHeader:('sync after resolving ', tmpFilename pathName, '.').
+            result ifFalse:[
+                ^ false
+            ].
+
+            perforceCommand := ('edit -c ', aNumber printString, ' "' , tmpFilename pathName, '"').
+            outputStream := ReadWriteStream on:''.
+            errorStream := ReadWriteStream on:''.
+            result := self temporaryWorkSpace executePerforceCommand:perforceCommand inDirectory:self temporaryWorkSpace root 
+                inputFrom:nil outputTo:outputStream 
+                errorTo:errorStream
+                logHeader:('edit after resolving ', tmpFilename pathName, '.').
+            result ifFalse:[
+                ^ false
+            ].
+
+            "write my result"
+            resultSource notNil ifTrue:[
+                s := tmpFilename writeStream.
+                s nextPutAll:resultSource.
+                s close.
+            ].
+        ].
+    ].
+    ^true
+!
+
+releaseWorkSpace
+
+    temporaryWorkSpace notNil ifTrue:[
+        temporaryWorkSpace deleteWorkSpaceFromServer.   
+    ].
+    tempDirectory notNil ifTrue:[
+        tempDirectory recursiveRemove.
+    ].
+!
+
+revisionLogOf:clsOrNil 
+fromRevision:firstRev 
+toRevision:lastRef 
+numberOfRevisions:numRevisions 
+fileName:classFileName 
+directory:packageDir 
+module:aPackage
+
+    |atEnd line inHeaderInfo info record revisionRecords headerOnly msg revArg infoAndLogString elements 
+     foundView outputStream errorStream inStream packagePath fullFilename depotPath perforceCommand result labelLineElements tags label revision|
+
+    [
+        revArg := ''.
+        headerOnly := false.
+        (firstRev notNil or:[lastRef notNil]) ifTrue:[
+            (firstRev == 0 and:[lastRef == 0]) ifTrue:[
+                headerOnly := true.
+            ]
+        ].
+        foundView := self getViewForPackage:aPackage.
+        headerOnly ifTrue:[
+            msg := 'fetching revision info '
+        ] ifFalse:[
+            msg := 'reading revision log '
+        ].
+        clsOrNil isNil ifTrue:[
+            foundView notNil ifTrue:[            
+                msg := msg , 'in ', foundView local.
+            ].
+        ] ifFalse:[
+            msg := msg , 'of ', clsOrNil name.
+        ].
+        self activityNotification:msg,'...'.
+        packagePath := Smalltalk packageDirectoryForPackageId:aPackage.
+        fullFilename := (packagePath construct:packageDir) construct:classFileName.
+        depotPath := foundView getDepotPathForLocalPath:fullFilename pathName.
+        perforceCommand := ('filelog "' , depotPath, '"').
+        outputStream := ReadWriteStream on:''.
+        errorStream := ReadWriteStream on:''.
+        result := self executePerforceCommand:perforceCommand inDirectory:self root 
+            inputFrom:nil outputTo:outputStream 
+            errorTo:errorStream
+            logHeader:('getting filelog ', depotPath, '.').
+        result ifFalse:[
+            ^ nil
+        ].
+
+        "/
+        "/ read the commands pipe output and extract the container info
+        "/
+        info := IdentityDictionary new.
+        inHeaderInfo := true.
+        revisionRecords := OrderedCollection new.
+        info at:#revisions put:revisionRecords.
+        inStream := ReadStream on:(outputStream contents).
+        [inHeaderInfo and:[inStream atEnd not]] whileTrue:[
+            line:= inStream nextLine.
+            line notNil ifTrue:[
+                |gotIt|
+
+                gotIt := false.
+                infoAndLogString := line asCollectionOfSubstringsSeparatedBy:$'.
+                elements := infoAndLogString size.
+                elements > 1 ifTrue:[
+                    record := self readRevisionLogEntryFromString:line.
+                    ((record at:#state ifAbsent:'') = 'delete') ifTrue:[
+                        info at:#newestRevision put:#deleted.
+                    ] ifFalse:[
+                        info at:#newestRevision put:(record at:#revision).
+                    ].
+                    info at:#numberOfRevisions put:((record at:#revision) asNumber).
+                    revisionRecords add:record.
+                    inHeaderInfo := false
+                ].
+            ]
+        ].
+
+        info isEmpty ifTrue:[
+            ('PerforceSourceCodeManager [warning]: no log for ', depotPath) errorPrintCR.
+            ^ nil
+        ].
+
+        "/ strip selected revisions from the total-revisions entry
+        headerOnly ifFalse:[
+            "/
+            "/ continue to read the commands pipe output
+            "/ and extract revision info records
+            "/
+            atEnd := false.
+            [atEnd or:[inStream atEnd]] whileFalse:[
+                record := self readRevisionLogEntryFromStream:inStream.
+                record isNil ifTrue:[
+                    atEnd := true.
+                ] ifFalse:[
+                    revisionRecords add:record.
+                ].
+                (numRevisions notNil and:[revisionRecords size >= numRevisions]) ifTrue:[
+                    atEnd := true
+                ]
+            ].
+        ].
+    ] ensure:[
+        outputStream notNil ifTrue:[outputStream close].
+        self activityNotification:nil.
+    ].
+    perforceCommand := ('labels "' , depotPath, '"').
+    outputStream := ReadWriteStream on:''.
+    errorStream := ReadWriteStream on:''.
+    result := self executePerforceCommand:perforceCommand inDirectory:self root 
+        inputFrom:nil outputTo:outputStream 
+        errorTo:errorStream
+        logHeader:('getting labels ', depotPath, '.').
+    result ifFalse:[
+        ^ nil
+    ].
+    inStream := ReadStream on:(outputStream contents).
+    tags := Dictionary new.
+    [inStream atEnd not] whileTrue:[
+        line:= inStream nextLine.
+        line notEmptyOrNil ifTrue:[
+            labelLineElements := line asCollectionOfWords.
+            elements := labelLineElements size.
+            elements > 1 ifTrue:[
+                label := labelLineElements second withoutSeparators.
+                revision := self getRevisionForLabel:label depotPath:depotPath.
+                tags at:(labelLineElements second withoutSeparators) put:revision.
+            ].
+        ]
+    ].
+    info at:#symbolicNames put:tags.
+
+    ^ info
+!
+
+setSymbolicName:symbolicNameArg revision:rev overWrite:overWriteBool pathes:pathesInRepository
+    "set a symbolicName for revision rev.
+     If rev is nil, set it for the head (most recent) revision.
+     If rev is 0, delete the symbolic name.
+     If overWriteBool is true, the symbolicName will be changed, even if it has already been set.
+     If overWriteBool is false, an error will be raised if symbolicName has already been set.
+
+     If filename is nil, the symbolicName for a whole package is set.
+     If multiple pathes are given, the revision MUST be nil."
+
+    |argumentString result errorStream moduleDirs symbolicName perforceCommand outputStream|
+
+    symbolicName := (symbolicNameArg includes:Character space) 
+                        ifTrue:[ '"',symbolicNameArg,'"' ]
+                        ifFalse:[ symbolicNameArg ].
+
+    pathesInRepository size > 1 ifTrue:[
+        self assert:(rev isNil or:[rev == 0]) "revision must be nil (for head) or 0 (for delete) with multiple pathes"
+    ].
+
+    moduleDirs := pathesInRepository 
+                    collect:[:pathInRepository |
+                        (pathInRepository asCollectionOfSubstringsSeparatedByAny:'/\') first.
+                    ].
+    moduleDirs do:[:moduleDir |
+        |pathesInModule pathesInModuleAsArgument|
+
+        pathesInModule := pathesInRepository
+                    select:[:pathInRepository |
+                        |moduleOfThisPath|
+
+                        moduleOfThisPath := (pathInRepository asCollectionOfSubstringsSeparatedByAny:'/\') first.
+                        moduleOfThisPath = moduleDir
+                    ].
+
+        rev = 0 ifTrue:[
+            argumentString := ' -d '.
+        ] ifFalse:[
+            argumentString := ' -r ', (rev ? 'HEAD').
+            overWriteBool ifTrue:[
+                argumentString := argumentString, ' -F'
+            ].
+        ].
+
+        pathesInModuleAsArgument := pathesInModule 
+                                        collect:[:eachPath |
+                                            (eachPath includes:Character space) ifTrue:[
+                                                '"',eachPath,'"'
+                                            ] ifFalse:[
+                                                eachPath
+                                            ].
+                                        ].
+        pathesInModuleAsArgument := pathesInModuleAsArgument asStringCollection asStringWith:Character space.
+
+        self activityNotification:'setting symbolic name for: ', pathesInModuleAsArgument.
+
+        self information:'Implementation not finished yet'.
+        ^self.
+
+        perforceCommand := ('label "' , pathesInRepository, '"').
+        outputStream := ReadWriteStream on:''.
+        errorStream := ReadWriteStream on:''.
+        result := self executePerforceCommand:perforceCommand inDirectory:self root 
+            inputFrom:nil outputTo:outputStream 
+            errorTo:errorStream
+            logHeader:('set label ', pathesInRepository, '.').
+        result ifFalse:[
+            ^ nil
+        ].
+    ].
+
+    "
+     self setSymbolicName:'stable' revision:nil overWrite:false path:'stx/libbasic/Array.st'
+     self setSymbolicName:'stable' revision:nil overWrite:true path:'stx/libbasic/Array.st'
+
+     self 
+        setSymbolicName:'test1' 
+        revision:nil 
+        overWrite:true 
+        path:'bosch/dapasx/datenbasis/DAPASX__HierarchicalList.st'
+
+     self 
+        setSymbolicName:'test2' 
+        revision:nil 
+        overWrite:true 
+        pathes:#( 'bosch/dapasx/datenbasis/DAPASX__HierarchicalList.st' 
+                  'bosch/dapasx/datenbasis/DAPASX__ProjectSearch.st' )
+
+     self 
+        setSymbolicName:'test2' 
+        revision:0 
+        overWrite:true 
+        pathes:#( 'bosch/dapasx/datenbasis/DAPASX__HierarchicalList.st' 
+                  'bosch/dapasx/datenbasis/DAPASX__ProjectSearch.st' )
+    "
+
+    "Created: / 12-09-2006 / 12:36:44 / cg"
+!
+
+streamFor:checkInDefinition revision:revision cache:doCache
+    "extract a classes source code and return an open readStream on it.
+     A revision of nil selects the current (in image) revision.
+     The classes source code is extracted using the revision and the sourceCodeInfo,
+     which itself is extracted from the classes packageString."
+
+    |cacheIt cacheDir classFileName fullName cachedSourceFilename cacheSubDir cachedFile tempdir checkoutName
+     checkoutNameLocal revMsg fullTempName fullCachedName stream tempFile outStream
+     line modulDir lineNr result outputStream errorStream inStream cls module packageDir packagePath fullFilename perforceCommand|
+
+    cacheIt := doCache.
+    (cacheIt and:[revision ~~ #newest and:[revision notNil]]) ifTrue:[
+        (cacheDir := PerforceSourceCodeManager sourceCacheDirectory) isNil ifTrue:[
+            'PerforceSourceCodeManager [warning]: no source cache directory' errorPrintCR.
+        ]
+    ].
+    self getTemporaryWorkspaceFor:checkInDefinition.
+    cls := checkInDefinition definitionClass.
+    classFileName := checkInDefinition fileName.
+    classFileName isNil ifTrue:[classFileName := cls classBaseFilename].
+
+    (classFileName endsWith:',v') ifTrue:[
+        classFileName := classFileName copyWithoutLast:2.
+    ].
+    (classFileName endsWith:'.st') ifTrue:[
+        cls notNil ifTrue:[
+            classFileName := classFileName copyWithoutLast:3.
+        ]
+    ].
+    module :=  checkInDefinition package.
+    packageDir := checkInDefinition packageDir.
+    fullName := module , '/' , packageDir , '/' , classFileName.
+    cls notNil ifTrue:[
+        fullName := fullName , '.st'.
+    ].
+
+    (revision isNil or:[revision == #newest]) ifTrue:[
+        cachedSourceFilename := classFileName, '_p4'.
+        revMsg := ''.
+    ] ifFalse:[
+        cachedSourceFilename := classFileName , '_p4_' , revision.
+        revMsg := ' (' , revision , ')'.
+    ].                                               
+
+    cacheDir notNil ifTrue:[
+        cacheSubDir := cacheDir construct:module.
+        cacheSubDir := cacheSubDir construct:packageDir.
+        cachedFile := cacheSubDir construct:cachedSourceFilename.
+        cachedFile exists ifTrue:[
+            ^ cachedFile readStream
+        ].
+    ].
+
+    "/
+    "/ first, create a temporary work tree
+    "/ Do not make module and package directories, their existence cause cvs checkout to fail in server mode
+    "/
+    tempdir := self tempDirectory.
+
+
+    "/
+    "/ check it out there
+    "/
+    checkoutName :=  fullName.
+
+    modulDir := module asFilename construct:packageDir.
+    checkoutNameLocal := modulDir constructString:(fullName asFilename baseName).
+
+    self activityNotification:'checking out source ' , checkoutName , revMsg.
+
+    packagePath := Smalltalk packageDirectoryForPackageId:checkInDefinition package.
+    fullFilename := (packagePath construct:checkInDefinition packageDir) construct:checkInDefinition fileName.
+    fullTempName := self getTemporaryFilenameFor:fullFilename pathName.
+
+    perforceCommand := ('print "' , fullFilename pathName, '#', revision, '"').
+    outputStream := ReadWriteStream on:''.
+    errorStream := ReadWriteStream on:''.
+    result := self executePerforceCommand:perforceCommand inDirectory:self root 
+        inputFrom:nil outputTo:outputStream 
+        errorTo:errorStream
+        logHeader:('get contents of ', fullFilename pathName, ' for revision ', revision, '.').
+    result ifFalse:[
+        ^ nil
+    ].
+    errorStream contents notEmpty ifTrue:[
+        ^nil
+    ].
+    FileStream openErrorSignal handle:[:ex|
+        ('PerforceSourceCodeManager [error]: can not create ', fullTempName pathName) errorPrintCR.
+        ^ nil.
+    ] do:[
+        fullTempName directory recursiveMakeDirectory.
+        outStream := fullTempName writeStream.
+    ].
+    lineNr := 1.
+    inStream := ReadStream on:(outputStream contents).
+    [inStream atEnd not] whileTrue:[
+        line:= inStream nextLine.
+        line notNil ifTrue:[
+            lineNr = 1 ifTrue:[
+            ] ifFalse:[
+                outStream nextPutLine:line.
+            ].
+        ].
+        lineNr := lineNr + 1.
+    ].
+    outStream close.
+
+    (cacheSubDir isNil) ifTrue:[
+        cacheIt := false
+    ] ifFalse:[
+        cacheSubDir recursiveMakeDirectory.
+        fullCachedName := cacheSubDir constructString:cachedSourceFilename.
+    ].
+    (cacheIt
+    and:[cachedFile notNil
+    and:[fullTempName exists]])
+    ifTrue:[
+        (OperatingSystem errorSignal catch:[
+            fullTempName moveTo:fullCachedName
+        ]) ifTrue:[
+            ('PerforceSourceCodeManager [error]: failed to rename ', fullTempName pathName, ' to ', cachedSourceFilename) errorPrintCR.
+            ^ nil
+        ].
+        fullCachedName asFilename exists ifTrue:[
+            stream := fullCachedName asFilename readStream.
+        ].
+    ] ifFalse:[
+        checkInDefinition fileName = 'extensions.st' ifTrue:[
+            self activityNotification:'Not cached - please check your settings and/or the version method in the projectDefinition.'.
+        ] ifFalse:[
+            self activityNotification:'Not cached - please check your settings.'.
+        ].
+        OperatingSystem isUNIXlike ifFalse:[
+            "/ cannot remove files which are still open ...
+            "/ sigh - need a delete-on-close flag in FileStream.
+            "/
+            tempFile := Filename newTemporary.
+            fullTempName copyTo:tempFile.
+            stream := tempFile readStream.
+            stream notNil ifTrue:[
+                stream removeOnClose:true.
+            ].
+        ] ifTrue:[
+            stream := fullTempName readStream.
+        ]
+    ].
+
+    ^ stream
+!
+
+submit
+
+    |numbers|
+
+    numbers := self getCurrentChangeListNumbers.
+    numbers isEmptyOrNil ifTrue:[
+        ^false
+    ].
+    numbers do:[:aNumber|
+        (self submitChangeNumber:aNumber) ifFalse:[
+            ^false
+        ].
+    ].
+    ^true
+!
+
+submitChangeNumber:changeNumber
+
+    |cmd outputStream errorStream result changeListDescription infoDialog logMsg|
+
+    changeListDescription := self getChangeDespriptionInfoFor:changeNumber printString.
+    infoDialog := PerforceSourceCodeManager submitInfoDialogClass 
+            getCheckinInfoFor:'Perforce submit message check'                
+            initialAnswer:((changeListDescription at:#Description ifAbsent:'') copy)
+            withFileList:(changeListDescription at:#Files ifAbsent:'').
+    infoDialog notNil ifTrue:[
+        logMsg := infoDialog logMessage.
+        (changeListDescription at:#Description ifAbsent:'') ~= logMsg asStringCollection ifTrue:[
+            self changeChangeDescriptionTo:logMsg asStringCollection changeNumber:changeNumber printString
+        ].
+    ].
+    cmd := ('submit -c ', changeNumber printString).
+    outputStream := ReadWriteStream on:''.
+    errorStream := ReadWriteStream on:''.
+    result := self temporaryWorkSpace executePerforceCommand:cmd
+                        inDirectory:self tempDirectory
+                        inputFrom:nil
+                        outputTo:outputStream
+                        errorTo:errorStream
+                        doLog:false.                     
+    result ifFalse:[   
+        result := self mergeOrResolveConflictsForChangeNumber:changeNumber.
+        result ifTrue:[
+            cmd := ('submit -c ', changeNumber printString).
+            outputStream := ReadWriteStream on:''.
+            errorStream := ReadWriteStream on:''.
+            result := self temporaryWorkSpace executePerforceCommand:cmd
+                                inDirectory:self tempDirectory
+                                inputFrom:nil
+                                outputTo:outputStream
+                                errorTo:errorStream
+                                logHeader:('submit change ', changeNumber printString, ' after resolve.').
+            result ifFalse:[
+                ^ false
+            ].
+        ].
+    ].
+    ^true
+! !
+
+!PerforceSourceCodeManagerUtilities::WorkSpace methodsFor:'basic administration'!
+
+initialRevisionInfo:checkInDefinition
+    "return a string usable as initial revision string"
+
+    |version workSpace foundView packagePath fullFilename depotPath|
+
+    checkInDefinition definitionClass isPrivate ifTrue:[
+        PerforceSourceCodeManager reportError:'refuse to get revision for private classes.'.
+        ^ nil.
+    ].
+
+    "/
+    "/ first, create a temporary work tree
+    "/
+"/    tempdir := checkInDefinition tempDirectory.
+
+
+    workSpace := PerforceSourceCodeManager getWorkSpaceForPackage:(checkInDefinition packageString).
+    workSpace isNil ifTrue:[
+        ('PerforceSourceCodeManager [error]: failed to create workspace for', checkInDefinition definitionObjectString)  errorPrintCR.
+        ^ nil
+    ].
+    checkInDefinition workSpace:workSpace.
+    version := PerforceSourceCodeManager versionInfoClass new.
+    foundView := workSpace getViewForPackage:checkInDefinition package.
+    packagePath := Smalltalk packageDirectoryForPackageId:checkInDefinition package.
+    fullFilename := (packagePath construct:checkInDefinition packageDir) construct:checkInDefinition fileName.
+    depotPath := foundView getDepotPathForLocalPath:fullFilename pathName.
+
+    version repositoryPathName:depotPath.
+    version user:workSpace owner.
+"
+    s := CharacterWriteStream on:(String basicNew:40).    
+    Date today printOn:s format:'%d-%m-%y' language:nil.
+    version date:s contents.
+    s := CharacterWriteStream on:(String basicNew:40).    
+    Timestamp now printOn:s format:'%h-%m-%s.%i'.
+    version time:s contents.
+"
+    version revision:'1'.
+    ^ version.
+
+"
+self initialRevisionStringFor:RTDBInspectorStartup inModule:'applistx' directory:'util/rtdb' container:'RTDBInterfaceInspector.st'
+"
+!
+
+initialRevisionStringFor:checkInDefinition
+    "return a string usable as initial revision string"
+
+    |info|
+
+    info := self initialRevisionInfo:checkInDefinition.
+    info notNil ifTrue:[
+        ^info getVersionString
+    ].
+    ^nil
+"
+self initialRevisionStringFor:RTDBInspectorStartup inModule:'applistx' directory:'util/rtdb' container:'RTDBInterfaceInspector.st'
+"
+!
+
+nextRevisionStringFor:checkInDefinition
+
+    |versionInfo s newestRevisionNumber versionMethod versionString|
+
+    versionMethod := checkInDefinition definitionClass findVersionMethodOfManager:PerforceSourceCodeManager.
+    versionMethod notNil ifTrue:[
+        versionString := (versionMethod valueWithReceiver:(checkInDefinition definitionClass theNonMetaclass) arguments:#()).
+        versionString notNil ifTrue:[
+            versionInfo := PerforceSourceCodeManager versionInfoClass fromRCSString:versionString.
+        ].
+    ].
+    versionInfo isNil ifTrue:[
+        versionInfo := self initialRevisionInfo:checkInDefinition.
+    ] ifFalse:[
+        versionInfo user:checkInDefinition workSpace owner.
+        s := CharacterWriteStream on:(String basicNew:40).    
+        Date today printOn:s format:'%d-%m-%y' language:nil.
+        versionInfo date:s contents.
+        s := CharacterWriteStream on:(String basicNew:40).    
+        Timestamp now printOn:s format:'%h-%m-%s.%i'.
+        versionInfo time:s contents.
+    ].
+    versionInfo isNil ifTrue:[
+        ^nil.
+    ].
+    newestRevisionNumber := checkInDefinition getReposRevisionNumberBeforeCheckin.
+    newestRevisionNumber isNil ifTrue:[
+        ^nil.
+    ].
+    versionInfo revision:((newestRevisionNumber + 1) printString).
+    ^versionInfo getVersionString
+! !
+
+!PerforceSourceCodeManagerUtilities::WorkSpace methodsFor:'command execution'!
+
+executePerforceCommand:perforceCommand inDirectory:dirArg 
+        inputFrom:inputStream outputTo:outputStream 
+        errorTo:errorStream 
+    "execute command and prepend perforce command name and global options.
+     execute command in the dirArg directory.
+     The doLog argument, if false supresses a logEntry to be added
+     in the cvs log file (used when reading / extracting history)"
+
+    ^self executePerforceCommand:perforceCommand inDirectory:dirArg 
+        inputFrom:inputStream outputTo:outputStream 
+        errorTo:errorStream
+        doLog:true
+!
+
+executePerforceCommand:perforceCommand inDirectory:dirArg 
+        inputFrom:inputStream outputTo:outputStream 
+        errorTo:errorStream
+        doLog:doLog
+    "execute command and prepend perforce command name and global options.
+     execute command in the dirArg directory.
+     The doLog argument, if false supresses a logEntry to be added
+     in the cvs log file (used when reading / extracting history)"
+
+    ^self executePerforceCommand:perforceCommand inDirectory:dirArg 
+            inputFrom:inputStream outputTo:outputStream 
+            errorTo:errorStream
+            doLog:doLog
+            logHeader:nil
+!
+
+executePerforceCommand:perforceCommand inDirectory:dirArg 
+        inputFrom:inputStream outputTo:outputStream 
+        errorTo:errorStream
+        doLog:doLog
+        logHeader:logHeader
+    "execute command and prepend perforce command name and global options.
+     execute command in the dirArg directory.
+     The doLog argument, if false supresses a logEntry to be added
+     in the cvs log file (used when reading / extracting history)"
+
+    |command rslt pathOfDir errorString  timeout errorMsgStream executeStream|
+
+    dirArg notNil ifTrue:[
+        pathOfDir := dirArg asFilename pathName.
+    ].
+
+    command := self getCommandOptionsForCommand:perforceCommand.
+    Processor isDispatching ifFalse:[
+        rslt := OperatingSystem executeCommand:command
+                        inputFrom:inputStream
+                        outputTo:outputStream
+                        errorTo:errorStream
+                        auxFrom:nil
+                        inDirectory:pathOfDir
+                        lineWise:true
+                        onError:[:status| false].
+    ] ifTrue:[
+        PerforceCommandSemaphore critical:[
+            |p |
+
+            p := [
+                rslt := OperatingSystem executeCommand:command
+                                inputFrom:inputStream
+                                outputTo:outputStream
+                                errorTo:errorStream
+                                auxFrom:nil
+                                inDirectory:pathOfDir
+                                lineWise:true
+                                onError:[:status| false].
+            ] fork.
+
+            timeout := (p waitUntilTerminatedWithTimeout:300). 
+            timeout ifTrue:[
+                ('PerforceSourceCodeManager [info]: command timeout: ' , command) errorPrintCR.
+                rslt := false.
+                errorString := 'Perforce command timeout'.
+            ] ifFalse:[
+                rslt ifFalse:[
+                    errorString := ('PerforceSourceCodeManager [info]: command failed: ' , command).
+                ].
+            ].
+        ].
+    ].
+
+    PerforceSourceCodeManager verboseSourceCodeAccess == true ifTrue:[
+        executeStream := WriteStream on:''.
+        executeStream nextPutAll:AbsoluteTime now printString.
+        executeStream cr.
+        executeStream nextPutAll:('Command <', command, '>').
+        executeStream cr.
+        executeStream nextPutAll:('StdErr Output: <', errorStream contents, '>').
+        executeStream cr.
+        executeStream nextPutAll:('StdOut Output: <', outputStream contents, '>').
+        executeStream cr.
+        executeStream nextPutAll:('##############################').
+        Transcript showCR:executeStream contents.
+    ].
+    rslt ifFalse:[
+        doLog ifTrue:[
+            errorMsgStream := WriteStream on:''.
+            logHeader notNil ifTrue:[
+                errorMsgStream nextPutAll:'Error '.
+                errorMsgStream nextPutAll:logHeader.
+                errorMsgStream cr.
+            ].
+            timeout ifTrue:[
+                errorMsgStream nextPutAll:('Timeout command <', command, '>').
+                errorMsgStream cr.
+            ] ifFalse:[
+                errorMsgStream nextPutAll:('Command <', command, '>').
+                errorMsgStream cr.
+                errorMsgStream nextPutAll:('Error output: ', errorStream contents).
+                outputStream contents notEmpty ifTrue:[
+                    errorMsgStream nextPutAll:('Output: ', outputStream contents).
+                ].
+            ].
+            self perforceError raiseErrorString:errorMsgStream contents.
+            SourceCodeManagerError isHandled ifTrue:[
+                SourceCodeManagerError raiseErrorString:errorMsgStream contents.
+            ].
+        ].
+    ].
+    ^ rslt.
+!
+
+executePerforceCommand:perforceCommand inDirectory:dirArg 
+        inputFrom:inputStream outputTo:outputStream 
+        errorTo:errorStream 
+        logHeader:logHeader
+    "execute command and prepend perforce command name and global options.
+     execute command in the dirArg directory.
+     The doLog argument, if false supresses a logEntry to be added
+     in the cvs log file (used when reading / extracting history)"
+
+    ^self executePerforceCommand:perforceCommand inDirectory:dirArg 
+        inputFrom:inputStream outputTo:outputStream 
+        errorTo:errorStream
+        doLog:true
+        logHeader:logHeader.
+!
+
+getCommandOptionsForCommand:perforceCommand
+
+    |commandStream executable port user password clientString|
+
+    commandStream := WriteStream on:''.
+    executable := PerforceSourceCodeManager perforceExecutable.
+    (executable includes:Character space) ifTrue:[
+        commandStream nextPut:$".
+        commandStream nextPutAll:executable.
+        commandStream nextPut:$".
+    ] ifFalse:[
+        commandStream nextPutAll:executable.
+    ].
+    commandStream space.
+    port := self perforceSettings at:#port ifAbsent:nil.
+    port notNil ifTrue:[
+        commandStream space.
+        commandStream nextPutAll:'-p '.
+        commandStream nextPutAll:port.
+        commandStream space.
+    ].
+    clientString := self perforceSettings at:#client ifAbsent:nil.
+    clientString notNil ifTrue:[
+        commandStream space.
+        commandStream nextPutAll:'-c '.
+        commandStream nextPutAll:clientString.
+        commandStream space.
+    ].
+    user := self perforceSettings at:#user ifAbsent:nil.
+    user notNil ifTrue:[
+        commandStream space.
+        commandStream nextPutAll:'-u '.
+        commandStream nextPutAll:user.
+        commandStream space.
+    ].
+    password := self perforceSettings at:#password ifAbsent:nil.
+    password notNil ifTrue:[
+        commandStream space.
+        commandStream nextPutAll:'-P '.
+        commandStream nextPutAll:password.
+        commandStream space.
+    ].
+    commandStream nextPutAll:perforceCommand.
+
+    ^ commandStream contents.
+! !
+
+!PerforceSourceCodeManagerUtilities::WorkSpace methodsFor:'dialogs & helpers'!
+
+checkinTroubleDialog:title message:message log:log abortable:abortable option:optionTitle
+    "trouble checking in - open a dialog"
+
+    ^ self
+        checkinTroubleDialog:title
+        message:message
+        log:log
+        abortable:abortable
+        option:optionTitle
+        option2:nil
+
+    "Created: 10.12.1995 / 17:34:33 / cg"
+    "Modified: 12.9.1996 / 02:39:06 / cg"
+!
+
+checkinTroubleDialog:title message:message log:log abortable:abortable option:optionTitle option2:optionTitle2
+    ^self
+        checkinTroubleDialog:title
+        message:message
+        log:log
+        abortable:abortable
+        option:optionTitle
+        option2:optionTitle2
+        option3:nil
+!
+
+checkinTroubleDialog:title message:message log:log abortable:abortable option:optionTitle option2:optionTitle2 option3:optionTitle3
+    "trouble checking in - open a dialog"
+
+    |l box list listView optionPressed option2Pressed option3Pressed|
+
+    l := log collect:[:line | line withTabsExpanded].
+    list := SelectionInList with:l.
+
+    box := Dialog new.
+    box label:(title).
+
+    (box addTextLabel:message) borderWidth:0.
+
+    l asString notEmptyOrNil ifTrue:[
+        listView := SelectionInListView on:list.
+        listView disable.
+        listView height:(listView heightOfContents max:250).
+        box addComponent:(HVScrollableView forView:listView miniScrollerH:true) tabable:false.
+        box addVerticalSpace.
+    ].
+
+    abortable ifTrue:[
+        box addAbortButton
+    ].
+    optionTitle notNil ifTrue:[
+        box addOkButton:(Button label:optionTitle action:[optionPressed := true. box hide]).
+    ].
+    optionTitle2 notNil ifTrue:[
+        box addOkButton:(Button label:optionTitle2 action:[option2Pressed := true. box hide]).
+    ].
+    optionTitle3 notNil ifTrue:[
+        box addOkButton:(Button label:optionTitle3 action:[option3Pressed := true. box hide]).
+    ].
+    box addOkButton.
+
+    box extent:(box preferredExtent).
+    box minExtent:box extent.
+    box maxExtent:box extent.
+
+    box open.
+    box destroy.
+    optionPressed == true ifTrue:[^ #option].
+    option2Pressed == true ifTrue:[^ #option2].
+    option3Pressed == true ifTrue:[^ #option3].
+    ^ box accepted
+
+"
+| changesAsLogged |
+changesAsLogged := OrderedCollection new.
+1 to:10 do:[:each|
+    changesAsLogged add:('Hallo', each printString).
+].
+changesAsLogged := OrderedCollection new.
+self checkinTroubleDialog:'Version conflict'
+             message:'Message Message Message Message Message Message Message Message Message Message Message Message Message Message'
+             log:changesAsLogged
+             abortable:false
+             option:'show conflicts'
+             option2:'resolve conflicts'
+"
+!
+
+diffTextComment
+
+    |ws|
+
+    ws := WriteStream on:''.
+    ws nextPutLine:'"/ ***************************************************************'.
+    ws nextPutLine:'"/ This text contains your current versions code (blue)'.
+    ws nextPutLine:'"/ merged with the conflicting code as found in the repository (red) which resulted'.
+    ws nextPutLine:'"/ from some other checkin.'.
+    ws nextPutLine:'"/ Each such conflict is surrounded by green text (like this paragraph).'.
+    ws nextPutLine:'"/ '.
+    ws nextPutLine:'"/ Please have a look at ALL the conflicts and fix things as appropriate.'.
+    ws nextPutLine:'"/ Delete the green lines as a confirmation - I will not checkin the changed text,'.
+    ws nextPutLine:'"/ unless no more green parts are present. This includes this comment at the top.'.
+    ws nextPutLine:'"/ ***************************************************************'.
+    ^ ws contents
+!
+
+getRevisionForLabel:label depotPath:depotPath
+
+
+    |perforceCommand outputStream errorStream result inStream line depotAndRevision|
+
+    perforceCommand := ('files "@' , label, '"').
+    outputStream := ReadWriteStream on:''.
+    errorStream := ReadWriteStream on:''.
+    result := self executePerforceCommand:perforceCommand inDirectory:self root 
+        inputFrom:nil outputTo:outputStream 
+        errorTo:errorStream
+        logHeader:('getting revision for label ', label, '.').
+    result ifFalse:[
+        ^ nil
+    ].
+    inStream := ReadStream on:(outputStream contents).
+    [inStream atEnd not] whileTrue:[
+        line:= inStream nextLine.
+        line notEmptyOrNil ifTrue:[
+            (line startsWith:depotPath) ifTrue:[
+                depotAndRevision := line asCollectionOfWords first.
+                depotAndRevision := depotAndRevision asCollectionOfSubstringsSeparatedBy:$#.
+                ^ depotAndRevision second
+            ].
+        ].
+    ].
+    ^nil
+!
+
+messageForChangesInClass:class revision:revisionNumber
+
+    |msgStream|
+
+    msgStream := WriteStream on:''.
+    msgStream nextPutAll:'The source of '; nextPutAll:class className; nextPutAll:'has been changed in the meanwhile as listed below.'.
+    msgStream cr.
+    msgStream nextPutAll:'If you continue, your new changes (based upon rev. '; nextPutAll:revisionNumber printString; nextPutAll:') will be MERGED'.
+    msgStream nextPutAll:'into the newest revision. This will combine the other version with your changes'.
+    msgStream nextPutAll:'into a new common revision which may be different from both.'.
+    msgStream nextPutAll:'Although this is a nice feature, it may fail to create the expected result in certain situations.'.
+    msgStream cr.
+    msgStream nextPutAll:'You should carefully check the result - by comparing the current version with the'.
+    msgStream nextPutAll:'most recent version in the repository. If that does not contain an acceptable version,'.
+    msgStream nextPutAll:'change methods as required and check in again.'.
+    msgStream nextPutAll:'Be aware, that after that, the actual repository version is different from your current classes,'.
+    msgStream nextPutAll:'and you should update your class from the repository.'.
+    msgStream cr.
+    msgStream nextPutAll:'Continue ?'.
+    ^ msgStream contents
+!
+
+messageForConflictsInClass:definitionClass revision:revisionNumber
+
+    |msgStream|
+
+    msgStream := WriteStream on:''.
+    msgStream nextPutAll:'The source of '; nextPutAll:definitionClass className; nextPutAll:' has been changed in the meanwhile as listed below.'.
+    msgStream cr.
+    msgStream nextPutAll:'Your new changes (based upon rev. '; nextPutAll:revisionNumber printString; nextPutAll:') CONFLICT with those changes'.
+    msgStream cr.
+    msgStream nextPutAll:'You should fix things by comparing your class with the most recent repository version'.
+    msgStream nextPutAll:'and change your methods avoiding conflicts. The checkin again.'.
+    msgStream cr.
+    ^ msgStream contents
+!
+
+messageForNoChangesInClass:class
+
+    |msgStream|
+
+    msgStream := WriteStream on:''.
+    msgStream nextPutAll:'The source of '; nextPutAll:class className; nextPutAll:'has been changed in the meanwhile as listed below.'.
+    msgStream cr.
+    msgStream nextPutAll:'I have merged your version with the newest repository version,'.
+    msgStream nextPutAll:'and found no differences between the result and your current version'.
+    msgStream nextPutAll:'(i.e. your version seemed up-to-date).'.
+    ^ msgStream contents
+!
+
+updatedRevisionStringOf:aClass forRevision:newRevision with:originalVersionString
+    "update a revision string"
+
+    |versionInfo packageID module foundView packagePath fullFilename depotPath sourceInfo classFileName|
+
+    originalVersionString isEmptyOrNil ifTrue:[
+        packageID := PackageId from:aClass package.
+        module := packageID module.
+        foundView := self getViewForPackage:module.
+        packagePath := Smalltalk packageDirectoryForPackageId:module.
+        sourceInfo := PerforceSourceCodeManager sourceInfoOfClass:aClass.
+        sourceInfo isNil ifTrue:[
+            PerforceSourceCodeManager reportError:('no sourceInfo for class: ' , aClass name).
+            ^ nil
+        ].
+        classFileName := PerforceSourceCodeManager containerFromSourceInfo:sourceInfo.
+        fullFilename := (packagePath construct:packageID directory) construct:classFileName.
+        depotPath := foundView getDepotPathForLocalPath:fullFilename pathName.
+
+        versionInfo := PerforceSourceCodeManager versionInfoClass fromRepositoryPathName:depotPath.        
+    ] ifFalse:[
+        versionInfo := PerforceSourceCodeManager versionInfoClass fromRCSString:originalVersionString.
+    ].
+    versionInfo revision:newRevision printString.
+    ^ versionInfo getVersionString.
+
+
+
+"
+    self updatedRevisionStringOf:nil
+            forRevision:'6'
+            with:'$','Header','$'
+"
+! !
+
+!PerforceSourceCodeManagerUtilities::WorkSpace methodsFor:'initialization'!
+
+initialize
+
+    PerforceCommandSemaphore := Semaphore new:10.
+! !
+
+!PerforceSourceCodeManagerUtilities::WorkSpace methodsFor:'queries'!
+
+getDepotPathForLocalPath:aFilename
+    |view|
+
+    view := self getViewForPath:aFilename.
+    view isNil ifTrue:[
+        ^nil
+    ].             
+    ^view getDepotPathForLocalPath:aFilename
+!
+
+getLocalPathForDepotPath:depotPath
+
+    |view|
+
+    view := self getViewForDepotPath:depotPath.
+    view notNil ifTrue:[
+        ^view getLocalPathForDepotPath:depotPath.
+    ].
+    ^nil
+"
+     | workSpace tempWorkSpace |
+    workSpace := PerforceSourceCodeManager getWorkSpaceForPackage:'applistx'.
+    tempWorkSpace := workSpace temporaryWorkSpace.
+    tempWorkSpace getLocalPathForDepotPath:'//depot/applistx/util/libDataType/ActionLQualifier.st'
+"
+!
+
+getTemporaryFilenameFor:aFilename
+
+    |myView checkInPart fullTempFilename|
+
+    myView := self getViewForPath:aFilename.
+    self temporaryWorkSpace isNil ifTrue:[
+        ^nil
+    ].
+    self temporaryWorkSpace views do:[:aView|
+        myView depot = aView depot ifTrue:[
+            checkInPart := PerforceSourceCodeManager getTrailungPathNameFrom:aFilename with:myView localPathName.
+            fullTempFilename := aView localPathName asFilename construct:checkInPart.
+            ^fullTempFilename
+        ].
+    ].
+    ^nil
+!
+
+getTemporaryViewForPackage:aPackage
+
+    |myView|
+
+    myView := self getViewForPackage:aPackage.
+    self temporaryWorkSpace isNil ifTrue:[
+        ^nil
+    ].
+    self temporaryWorkSpace views do:[:aView|
+        myView depot = aView depot ifTrue:[
+            ^ aView
+        ].
+    ].
+!
+
+getViewForDepotPath:depotPath
+
+    |myHostName|
+
+    myHostName := OperatingSystem getHostName.
+    (myHostName endsWith:OperatingSystem getDomainName) ifTrue:[
+        myHostName := myHostName copyTo:(myHostName size - (OperatingSystem getDomainName size + 1)).
+    ].
+
+    (myHostName asLowercase startsWith:(self host asLowercase)) ifFalse:[
+        self perforceError raiseErrorString:('Client ', (perforceSettings at:#client), ' is made for host ', self host, ' and not for ', myHostName).
+        ^ nil
+    ].
+    self views do:[:aView |
+        (aView hasViewForDepotPath:depotPath) ifTrue:[
+            ^aView
+        ].
+    ].
+    self perforceError raiseErrorString:('Client ', (perforceSettings at:#client), ' have no View for depot path ', depotPath).
+    ^ nil
+!
+
+getViewForPackage:aPackage 
+
+    |locPackage packagePath|
+
+    aPackage isNil ifTrue:[                              
+        locPackage := Smalltalk package.
+    ] ifFalse:[
+        locPackage := aPackage.
+    ].
+    packagePath := self packageDirectoryForPackageId:locPackage.
+    packagePath notNil ifTrue:[
+        packagePath := packagePath pathName.
+    ] ifFalse:[
+        self perforceError raiseErrorString:('no package path for ', aPackage printString).
+        ^nil
+    ].
+    ^self getViewForPath:packagePath
+
+"
+    PerforceSourceCodeManager perforceWorkspaces first value getViewForPackage:'applistx:application/rtdbInspector/builder'
+"
+!
+
+getViewForPath:aPathName
+
+    |myHostName|
+
+    myHostName := OperatingSystem getHostName.
+    (myHostName endsWith:OperatingSystem getDomainName) ifTrue:[
+        myHostName := myHostName copyTo:(myHostName size - (OperatingSystem getDomainName size + 1)).
+    ].
+
+    (myHostName asLowercase startsWith:(self host asLowercase)) ifFalse:[
+        self perforceError raiseErrorString:('Client ', (perforceSettings at:#client), ' is made for host ', self host, ' and not for ', myHostName).
+        ^ nil
+    ].
+    self views do:[:aView |
+        (aView hasViewForPath:aPathName) ifTrue:[
+            ^aView
+        ].
+    ].
+    self perforceError raiseErrorString:('Client ', (perforceSettings at:#client), ' have no View for path ', aPathName).
+    ^ nil
+!
+
+hasViewForPackage:aPackage 
+
+    ^(self getViewForPackage:aPackage) notNil
+!
+
+hasViewForPath:aPathName
+
+    ^(self getViewForPath:aPathName) notNil
+!
+
+packageDirectoryForPackageId:package
+
+    ^self packageDirectoryForPackageId:package checkParents:true
+
+"
+    PerforceSourceCodeManager perforceWorkspaces first value getViewForPackage:'applisddtx:application/rtdbInspector/builder'
+"
+!
+
+packageDirectoryForPackageId:package checkParents:checkParents
+
+    |locPackage packagePath|
+
+    locPackage := package copyReplaceAll:$: with:$/.
+    [ packagePath isNil ] whileTrue:[
+        packagePath := Smalltalk packageDirectoryForPackageId:locPackage.
+        packagePath notNil ifTrue:[
+            ^packagePath
+        ].
+        locPackage := locPackage asFilename directoryName.
+    ].
+    ^nil
+
+"
+    PerforceSourceCodeManager perforceWorkspaces first value getViewForPackage:'applisddtx:application/rtdbInspector/builder'
+"
+!
+
+perforceError
+
+    ^ PerforceSourceCodeManager perforceError
+!
+
+perforceSettingsString
+
+    ^ PerforceSourceCodeManager getStringFromPerforceSettings:self perforceSettings
+!
+
+readRevisionLogEntryFromStream:inStream
+    "read and parse a single revision info-entry from the cvs log output.
+     Return nil on end.
+
+     The returned information is a structure (IdentityDictionary)
+     filled with:
+              #revision              -> the revision string
+              #author                -> who checked that revision into the repository
+              #date                  -> when was it checked in
+              #state                 -> the RCS state
+              #numberOfChangedLines  -> the number of changed line w.r.t the previous
+              #logMessage            -> the checkIn log message
+    "
+
+    |revLine1 atEnd|
+
+    atEnd := false.
+
+    revLine1 := inStream nextLine.
+    ^ self readRevisionLogEntryFromString:revLine1.
+!
+
+readRevisionLogEntryFromString:revLine1
+    "read and parse a single revision info-entry from the cvs log output.
+     Return nil on end.
+
+     The returned information is a structure (IdentityDictionary)
+     filled with:
+              #revision              -> the revision string
+              #author                -> who checked that revision into the repository
+              #date                  -> when was it checked in
+              #state                 -> the RCS state
+              #numberOfChangedLines  -> the number of changed line w.r.t the previous
+              #logMessage            -> the checkIn log message
+    "
+
+    | record revisionLineElements noOfRevisionLineElements posText|
+
+    (revLine1 notNil) ifTrue:[
+        record := IdentityDictionary new.
+        revisionLineElements := revLine1 asCollectionOfWords.
+        noOfRevisionLineElements := revisionLineElements size.
+        noOfRevisionLineElements > 1 ifTrue:[
+            record at:#revision put:((revisionLineElements at:2) copyFrom:2).
+        ].
+        noOfRevisionLineElements > 8 ifTrue:[
+            record at:#author put:(revisionLineElements at:9).
+        ].
+        noOfRevisionLineElements > 6 ifTrue:[
+            record at:#date put:(revisionLineElements at:7).
+        ].
+        noOfRevisionLineElements > 4 ifTrue:[
+            record at:#state put:(revisionLineElements at:5).
+        ].
+        noOfRevisionLineElements > 10 ifTrue:[
+            posText := 0.
+            1 to:9 do:[:ele| posText := posText + (revisionLineElements at:ele) size + 1].
+            record at:#logMessage put:(revLine1 copyFrom:posText).
+        ].
+    ].
+    ^record.
+!
+
+temporaryClientName
+
+    ^ 'stxCheckinWorkSpace_', self owner, self host.
+! !
+
+!PerforceSourceCodeManagerUtilities::WorkSpace methodsFor:'read'!
+
+getDefinitionFromServer
+    |cmd myBaseDirectory outputStream errorStream rslt clients inStream line words|
+
+    cmd := 'clients -u ' , (self perforceSettings at:#user).
+    myBaseDirectory := (Filename currentDirectory asAbsoluteFilename) pathName.
+    outputStream := WriteStream on:''.
+    errorStream := WriteStream on:''.
+    rslt := self  
+                executePerforceCommand:cmd
+                inDirectory:myBaseDirectory
+                inputFrom:nil
+                outputTo:outputStream
+                errorTo:errorStream
+                logHeader:('getting workspaces ').
+    rslt ifFalse:[
+        self perforceError raiseErrorString:(outputStream contents, errorStream contents).
+        ^false
+    ].
+    clients := OrderedCollection new.
+    inStream := ReadStream on:(outputStream contents).
+    [ inStream atEnd not ] whileTrue:[
+        line := inStream nextLine.
+        line notEmptyOrNil ifTrue:[
+            words := line asCollectionOfWords.
+            words size > 1 ifTrue:[
+                clients add:(words at:2).
+            ].
+        ].
+    ].
+    (clients includes:(self perforceSettings at:#client ifAbsent:nil)) ifFalse:[
+        self perforceError raiseErrorString:('No workspace ', (self perforceSettings at:#client ifAbsent:'?'), ' for user ', (self perforceSettings at:#user ifAbsent:'?'), ' on ', (self perforceSettings at:#port ifAbsent:'?'), ' available.').
+    ].
+
+    cmd := 'client -o'.
+    myBaseDirectory := (Filename currentDirectory asAbsoluteFilename) pathName.
+    outputStream reset.
+    errorStream reset.
+    rslt := self 
+                executePerforceCommand:cmd
+                inDirectory:myBaseDirectory
+                inputFrom:nil
+                outputTo:outputStream
+                errorTo:errorStream
+                logHeader:('getting empty workspace definition ').
+    rslt ifFalse:[
+        self perforceError raiseErrorString:(outputStream contents, errorStream contents).
+        ^false
+    ].
+    inStream := ReadStream on:(outputStream contents).
+    self getWorkSpaceFromClientSpecFrom:inStream.
+    ^true
+
+"
+(PerforceSourceCodeManager getWorkSpaceForPackage:'applistx') getDefinitionFromServer
+"
+!
+
+getWorkSpaceFromClientSpecFrom:inStream
+    "
+        get the workspace definition from perforce client command output
+    "
+
+    |line nextKey |
+
+    [inStream atEnd not] whileTrue:[
+        line:= inStream nextLine.
+        line notEmptyOrNil ifTrue:[
+                line first = $# ifFalse:[
+                (line startsWith:'Owner:') ifTrue:[
+                    self owner:line asCollectionOfWords second.
+                ].
+                (line startsWith:'Host:') ifTrue:[
+                    self host:line asCollectionOfWords second.
+                ].
+                (line startsWith:'Client:') ifTrue:[
+                    self client:(line asCollectionOfWords second).
+                ].
+                (line startsWith:'Root:') ifTrue:[
+                    self root:((line copyFrom:('Root:' size + 1)) withoutLeadingSeparators).
+                ].
+                (line startsWith:'View:') ifTrue:[
+                    nextKey := false.
+                    [nextKey not and:[inStream atEnd not]] whileTrue:[
+                        line:= inStream nextLine.
+                        line notEmptyOrNil ifTrue:[
+                            line first isSeparator ifTrue:[
+                                self views add:(View newFromLine:line workspace:self).
+                            ] ifFalse:[
+                                nextKey := true.
+                            ].
+                        ].
+                    ].
+                ].
+            ].
+        ].
+    ].
+!
+
+newWorkSpaceFor:settingsString 
+    settingsString isNil ifTrue:[
+        ^ nil
+    ].
+    self perforceSettings:(PerforceSourceCodeManager 
+                getPerforceSettingsFromString:settingsString).
+    self getDefinitionFromServer ifTrue:[
+        ^self
+    ].
+    ^nil
+!
+
+newWorkSpaceForSettings:settingsDict 
+
+    settingsDict isNil ifTrue:[
+        self perforceError raiseErrorString:('nil settings when creating workspace').
+        ^ self
+    ].
+    self perforceSettings:settingsDict.
+! !
+
+!PerforceSourceCodeManagerUtilities::WorkSpace::View class methodsFor:'instance creation'!
+
+newFromLine:aLine workspace:aWorkspaceDefinition
+
+    |instance|
+
+    instance := self new.
+    instance newFromLine:aLine.
+    instance workspace:aWorkspaceDefinition.
+    ^instance
+! !
+
+!PerforceSourceCodeManagerUtilities::WorkSpace::View methodsFor:'accessing'!
+
+depot
+    ^ depot
+!
+
+depot:something
+    depot := something.
+!
+
+local
+    ^ local
+!
+
+local:something
+    local := something.
+!
+
+type
+
+    " there special types for views 
+      + for added to the same directory
+      - exclude this view
+        and standard view
+    "
+
+    ^ type
+!
+
+type:something
+    type := something.
+!
+
+workspace
+    ^ workspace
+!
+
+workspace:something
+    workspace := something.
+! !
+
+!PerforceSourceCodeManagerUtilities::WorkSpace::View methodsFor:'queries'!
+
+getDepotPathForLocalPath:aFilename
+    |depotPath restPath unixRestPath|
+
+    (self hasViewForPath:aFilename) ifFalse:[
+        ^nil
+    ].                     
+    depotPath := depot.
+    (depot endsWith:'...') ifTrue:[
+        depotPath := depot copyTo:(depot size - 3).
+    ] ifFalse:[
+        depotPath := depot.
+    ].
+    restPath := PerforceSourceCodeManager getTrailungPathNameFrom:aFilename with:self localPathName.
+    unixRestPath := (UnixFilename fromComponents:(restPath asFilename components)) pathName.
+    depotPath := depotPath, unixRestPath.
+    ^depotPath.
+!
+
+getLocalPathForDepotPath:depotPath
+    |viewDepotPath restPath|
+
+    (self hasViewForDepotPath:depotPath) ifFalse:[
+        ^nil
+    ].                     
+    viewDepotPath := depot.
+    (depot endsWith:'...') ifTrue:[
+        viewDepotPath := depot copyTo:(depot size - 3).
+    ] ifFalse:[
+        viewDepotPath := depot.
+    ].
+    restPath := PerforceSourceCodeManager getTrailungPathNameFrom:depotPath with:viewDepotPath.
+    ^ (self localPathName asFilename construct:restPath) pathName.
+!
+
+hasViewForDepotPath:depotPath
+
+    |viewDepotPath|
+
+    depotPath isEmptyOrNil ifTrue:[
+        ^ false.
+    ].
+    viewDepotPath := depot.
+    (depot endsWith:'...') ifTrue:[
+        viewDepotPath := depot copyTo:(depot size - 3).
+    ] ifFalse:[
+        viewDepotPath := depot.
+    ].
+    (PerforceSourceCodeManager path:depotPath hasSamePrefixLikePath:viewDepotPath) ifFalse:[
+        ^false
+    ].
+    ^true
+!
+
+hasViewForPath:aPathname
+
+    aPathname isEmptyOrNil ifTrue:[
+        ^ false.
+    ].
+    (PerforceSourceCodeManager path:aPathname hasSamePrefixLikePath:self localPathName) ifFalse:[
+        ^false
+    ].
+    ^true
+!
+
+localPathName
+
+    |indexOfClientString localPathName|
+
+    (local endsWith:'...') ifTrue:[
+        localPathName := local copyTo:(local size -3).
+    ] ifFalse:[
+        localPathName := local.
+    ].
+    indexOfClientString := local findString:workspace client.
+    indexOfClientString == 0 ifTrue:[
+        ^workspace root.
+    ].
+    localPathName := workspace root asFilename construct:(localPathName copyFrom:(indexOfClientString + workspace client size)).
+    ^localPathName pathName 
+! !
+
+!PerforceSourceCodeManagerUtilities::WorkSpace::View methodsFor:'reading'!
+
+newFromLine:aLine
+
+    |words firstIndex secondIndex theLine|
+
+    theLine := aLine withoutLeadingSeparators.
+    theLine := theLine withoutTrailingSeparators.
+    theLine isEmpty ifTrue:[
+        ^self
+    ].
+    theLine first == $+ ifTrue:[
+        type := #+.
+        theLine := theLine copyFrom:2.
+    ].
+    theLine first == $- ifTrue:[
+        type := #-.
+        theLine := theLine copyFrom:2.
+    ].
+    (theLine includes:$") ifTrue:[
+        "oops we have space directories search for quotes"
+
+        firstIndex := theLine indexOf:$" startingAt:1.
+        firstIndex == 1 ifTrue:[
+            secondIndex := theLine indexOf:$" startingAt:firstIndex + 1.
+            depot := theLine copyFrom:firstIndex + 1 to:secondIndex - 1.
+            firstIndex := theLine indexOf:$" startingAt:secondIndex + 1.
+            secondIndex := theLine indexOf:$" startingAt:firstIndex + 1.
+            local := theLine copyFrom:firstIndex + 1  to:secondIndex - 1.
+        ] ifFalse:[
+            depot := (theLine copyTo:firstIndex - 1) withoutTrailingSeparators.            
+            local := theLine copyFrom:firstIndex + 1 to:(theLine size - 1).
+        ].
+    ] ifFalse:[
+        words := theLine asCollectionOfWords.
+        depot := words first.
+        local := words second.
+    ].
+
+"
+    View newFromLine:ws contents.
+"
+! !
+
+!PerforceSourceCodeManagerUtilities class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libtool/PerforceSourceCodeManagerUtilities.st,v 1.1 2012/06/01 09:16:03 cg Exp $'
+!
+
+version_CVS
+    ^ '§Header: /cvs/stx/stx/libtool/PerforceSourceCodeManagerUtilities.st,v 1.1 2012/06/01 09:16:03 cg Exp §'
+! !
\ No newline at end of file
--- a/ProcessMonitorV2.st	Wed May 30 21:46:55 2012 +0100
+++ b/ProcessMonitorV2.st	Tue Jun 05 15:49:00 2012 +0100
@@ -3290,7 +3290,7 @@
                     myDelay wait.
                     self updateList.
                 ]
-            ] valueOnUnwindDo:[
+            ] ifCurtailed:[
                 updateProcess := nil
             ]
         ]  forkAt:(Processor userSchedulingPriority + 1).
@@ -3784,13 +3784,13 @@
 !ProcessMonitorV2 class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/ProcessMonitorV2.st,v 1.58 2012/02/28 10:51:06 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/ProcessMonitorV2.st,v 1.59 2012/05/21 08:11:18 stefan Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libtool/ProcessMonitorV2.st,v 1.58 2012/02/28 10:51:06 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libtool/ProcessMonitorV2.st,v 1.59 2012/05/21 08:11:18 stefan Exp §'
 !
 
 version_SVN
-    ^ '$Id: ProcessMonitorV2.st 7952 2012-03-21 17:50:14Z vranyj1 $'
+    ^ '$Id: ProcessMonitorV2.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/SmalltalkCodeGeneratorTool.st	Wed May 30 21:46:55 2012 +0100
+++ b/SmalltalkCodeGeneratorTool.st	Tue Jun 05 15:49:00 2012 +0100
@@ -212,7 +212,7 @@
     alreadyInSuperclass ifTrue:[
         code := code, (('\    super %1\' bindWith:method) withCRs).
     ].
-    self compile:code forClass:aClass inCategory:(aCategory ? 'actions').
+    self compile:code forClass:aClass inCategory:(aCategory ? #actions).
     ^ code
 !
 
@@ -250,7 +250,7 @@
         text := '    ^ builder valueAspectFor:#''%1'' initialValue:true\' bindWith:aSelector.
     ].
     code := code, (text withCRs).
-    self compile:code forClass:aClass inCategory:(aCategory ? 'actions').
+    self compile:code forClass:aClass inCategory:(aCategory ? #actions).
     ^ code
 ! !
 
@@ -316,7 +316,7 @@
         self 
             compile:code
             forClass:metaClass 
-            inCategory:'initialization'.
+            inCategory:#initialization.
     ].
 
     self executeCollectedChangesNamed:('Add Class Initializer to ' , className).
@@ -339,14 +339,14 @@
             self 
                 compile:code
                 forClass:aClass 
-                inCategory:'testing'.
+                inCategory:#testing.
         ].
         (eachSubClass includesSelector:selector) ifFalse:[
             code := (selector , '\    ^ true') withCRs.
             self 
                 compile:code
                 forClass:eachSubClass 
-                inCategory:'testing'.
+                inCategory:#testing.
         ].
     ].
 
@@ -418,7 +418,7 @@
     self
         compile:(initCode contents)
         forClass:metaClass 
-        inCategory:'class initialization'.
+        inCategory:#'class initialization'.
 
 
     code := 'allStateNames\    ^ #( ' ,
@@ -429,7 +429,7 @@
     self
         compile:code withCRs
         forClass:metaClass 
-        inCategory:'queries'.
+        inCategory:#queries.
 
     self executeCollectedChangesNamed:('Generate EnumType Code for ' , className).
 
@@ -479,7 +479,7 @@
         self 
             compile:code
             forClass:metaClass 
-            inCategory:'documentation'.
+            inCategory:#documentation.
     ].
 
     self executeCollectedChangesNamed:('Add Example to ' , className).
@@ -496,7 +496,7 @@
 
     self startCollectChanges.
 
-    (nonMetaClass includesSelector:#'initialize') ifFalse:[
+    (nonMetaClass includesSelector:#initialize) ifFalse:[
         code :=
 'initialize
     "Invoked when a new instance is created."
@@ -525,7 +525,7 @@
         self 
             compile:code
             forClass:nonMetaClass 
-            inCategory:'initialization'.
+            inCategory:#initialization.
     ].
 
     self executeCollectedChangesNamed:('Add Initialized Instance Creation to ' , className).
@@ -544,7 +544,7 @@
 
     self createInitializationMethodIn:aClass.
 
-    (metaClass includesSelector:#'new') ifFalse:[
+    (metaClass includesSelector:#new) ifFalse:[
         m := metaClass responseTo:#new.
         (m isNil 
         or:[ (m sends:#initialize) not 
@@ -563,7 +563,7 @@
             self 
                 compile:code
                 forClass:metaClass 
-                inCategory:'instance creation'.
+                inCategory:#'instance creation'.
         ].
     ].
 
@@ -615,7 +615,7 @@
         self 
             compile:code
             forClass:nonMetaClass 
-            inCategory:'initialization'.
+            inCategory:#initialization.
     ].
 
     (metaClass includesSelector:selector) ifFalse:[
@@ -632,7 +632,7 @@
             self 
                 compile:code
                 forClass:metaClass 
-                inCategory:'instance creation'.
+                inCategory:#'instance creation'.
         ].
     ].
 
@@ -640,7 +640,7 @@
 !
 
 createPoolInitializationCodeFor:aClass
-    |nonMetaClass metaClass className poolVars code initCode runValue maxValue|
+    |nonMetaClass metaClass className poolVars initCode|
 
     self startCollectChanges.
 
@@ -677,7 +677,7 @@
     self
         compile:(initCode contents)
         forClass:metaClass 
-        inCategory:'class initialization'.
+        inCategory:#'class initialization'.
 
     self executeCollectedChangesNamed:('Generate Pool Initialization Code for ' , className).
 
@@ -705,7 +705,7 @@
         self 
             compile:code
             forClass:metaClass 
-            inCategory:'redefined instance creation'.
+            inCategory:#'redefined instance creation'.
     ].
     (metaClass includesSelector:#'new:') ifFalse:[
         code :=
@@ -715,7 +715,7 @@
         self 
             compile:code
             forClass:metaClass 
-            inCategory:'redefined instance creation'.
+            inCategory:#'redefined instance creation'.
     ].
 
     self executeCollectedChangesNamed:('Redefined Instance Creation to ' , className).
@@ -733,7 +733,7 @@
 
     self startCollectChanges.
 
-    (metaClass includesSelector:#'theOneAndOnlyInstance') ifFalse:[
+    (metaClass includesSelector:#theOneAndOnlyInstance) ifFalse:[
         code :=
 'theOneAndOnlyInstance
     "returns a singleton"
@@ -746,10 +746,10 @@
         self 
             compile:(code bindWith:varName)
             forClass:metaClass 
-            inCategory:'instance creation'.
+            inCategory:#'instance creation'.
     ].
 
-    (metaClass includesSelector:#'new') ifFalse:[
+    (metaClass includesSelector:#new) ifFalse:[
         code :=
 'new
     "returns a singleton"
@@ -759,10 +759,10 @@
         self 
             compile:(code bindWith:varName)
             forClass:metaClass 
-            inCategory:'instance creation'.
+            inCategory:#'instance creation'.
     ].
 
-   (metaClass includesSelector:#'flushSingleton') ifFalse:[
+   (metaClass includesSelector:#flushSingleton) ifFalse:[
         code :=
 'flushSingleton
     "flushes the cached singleton"
@@ -776,7 +776,7 @@
         self 
             compile:(code bindWith:varName)
             forClass:metaClass 
-            inCategory:'instance creation'.
+            inCategory:#'instance creation'.
     ].
 
     self executeCollectedChangesNamed:('Singleton Pattern for ' , className).
@@ -793,7 +793,7 @@
 
     self startCollectChanges.
 
-    (nonMetaClass includesSelector:#'printOn:') ifFalse:[
+    (nonMetaClass includesSelector:#printOn:) ifFalse:[
         code :=
 'printOn:aStream
     "append a printed representation if the receiver to the argument, aStream"
@@ -814,7 +814,7 @@
         self 
             compile:code
             forClass:nonMetaClass 
-            inCategory:'printing & storing'.
+            inCategory:#'printing & storing'.
     ].
 
 
@@ -861,7 +861,7 @@
         self
             compile:(source bindWith:anApplicationClassNameOrStartupClassName)
             forClass:metaClass 
-            inCategory:'startup'.
+            inCategory:#startup.
     ].
     self executeCollectedChangesNamed:('Add Startup Code to ' , className).
 !
@@ -897,7 +897,7 @@
     "
 '
             forClass:nonMetaClass 
-            inCategory:'tests'.
+            inCategory:#tests.
     ].
 
     ( nonMetaClass includesSelector:#test2 ) ifFalse:[
@@ -920,7 +920,7 @@
     "
 '
             forClass:nonMetaClass 
-            inCategory:'tests'.
+            inCategory:#tests.
     ].
 
     ( nonMetaClass includesSelector:#test3 ) ifFalse:[
@@ -943,7 +943,7 @@
     "
 '
             forClass:nonMetaClass 
-            inCategory:'tests'.
+            inCategory:#tests.
     ].
 
     ( nonMetaClass includesSelector:#setUp ) ifFalse:[
@@ -955,7 +955,7 @@
     super setUp
 '
             forClass:nonMetaClass 
-            inCategory:'initialize / release'.
+            inCategory:#'initialize / release'.
     ].
 
     ( nonMetaClass includesSelector:#tearDown ) ifFalse:[
@@ -967,7 +967,7 @@
     super tearDown
 '
             forClass:nonMetaClass 
-            inCategory:'initialize / release'.
+            inCategory:#'initialize / release'.
     ]
 !
 
@@ -995,10 +995,10 @@
     ^ self visitObject:anObject
 ') bindWith:sel with:visitedClass nameWithoutPrefix asLowercaseFirst)
             forClass:visitorClass 
-            inCategory:'visiting'.
+            inCategory:#visiting.
     ].
 
-    (visitorClass includesSelector:#'visitObject:') ifFalse:[
+    (visitorClass includesSelector:#visitObject:) ifFalse:[
         self 
             compile:
 ('visitObject:anObject 
@@ -1009,10 +1009,10 @@
     self halt:''not yet implemented''
 ')
             forClass:visitorClass 
-            inCategory:'visiting'.
+            inCategory:#visiting.
     ].
 
-    (visitorClass includesSelector:#'visit:') ifFalse:[
+    (visitorClass includesSelector:#visit:) ifFalse:[
         self 
             compile:
 ('visit:anObject 
@@ -1022,7 +1022,7 @@
     ^ anObject acceptVisitor:self
 ')
             forClass:visitorClass 
-            inCategory:'visiting'.
+            inCategory:#visiting.
     ].
 
     self executeCollectedChangesNamed:('Add Visitor Pattern').
@@ -1044,7 +1044,7 @@
         self
             compile:(txt bindWith:className)
             forClass:metaClass 
-            inCategory:'page specs'.
+            inCategory:#'page specs'.
     ].
 
     self executeCollectedChangesNamed:('Add WebApplication Code for ' , className).
@@ -1085,7 +1085,7 @@
         self
             compile:txt
             forClass:nonMetaClass 
-            inCategory:'response generation - pages'.
+            inCategory:#'response generation - pages'.
     ].
 
     (nonMetaClass includesSelector:#page2:) ifFalse:[
@@ -1119,7 +1119,7 @@
         self
             compile:txt
             forClass:nonMetaClass 
-            inCategory:'response generation - pages'.
+            inCategory:#'response generation - pages'.
     ].
 
     (nonMetaClass includesSelector:#page3:) ifFalse:[
@@ -1135,7 +1135,7 @@
         self
             compile:txt
             forClass:nonMetaClass 
-            inCategory:'response generation - pages'.
+            inCategory:#'response generation - pages'.
     ].
 
     (nonMetaClass includesSelector:#process:) ifFalse:[
@@ -1171,7 +1171,7 @@
         self
             compile:txt
             forClass:nonMetaClass 
-            inCategory:'response generation'.
+            inCategory:#'response generation'.
     ].
 
     (metaClass includesSelector:#linkName) ifFalse:[
@@ -1184,7 +1184,7 @@
         self
             compile:txt
             forClass:metaClass 
-            inCategory:'defaults'.
+            inCategory:#defaults.
     ].
 
     (metaClass includesSelector:#settingsApplicationClass) ifFalse:[
@@ -1197,7 +1197,7 @@
         self
             compile:txt
             forClass:metaClass 
-            inCategory:'defaults'.
+            inCategory:#defaults.
     ].
 
 
@@ -1231,12 +1231,12 @@
         ].
 
     #(
-        #'initialize'               #code_forWidget_initialize  'initialization & release'
-        #'update:with:from:'        #code_forWidget_update      'change & update'
-        #'redrawX:y:width:height:'  #code_forWidget_redraw      'drawing'
-        #'buttonPress:x:y:'         #code_forWidget_buttonPress 'event handling'
-        #'keyPress:x:y:'            #code_forWidget_keyPress    'event handling'
-        #'sizeChanged:'             #code_forWidget_sizeChanged 'event handling'
+        initialize               code_forWidget_initialize  #'initialization & release'
+        update:with:from:        code_forWidget_update      #'change & update'
+        redrawX:y:width:height:  code_forWidget_redraw      #'drawing'
+        buttonPress:x:y:         code_forWidget_buttonPress #'event handling'
+        keyPress:x:y:            code_forWidget_keyPress    #'event handling'
+        sizeChanged:             code_forWidget_sizeChanged #'event handling'
     ) inGroupsOf:3 do:compileTemplateAction.
 
     self executeCollectedChangesNamed:('Add Widget Code for ' , className).
@@ -1321,7 +1321,7 @@
                     ].
                 ].
                 source := (source bindWith:varType with:name with:defaultMethodName) withCRs.
-                self compile:source forClass:aClass inCategory:(asValueHolder ifTrue:['aspects'] ifFalse:['accessing']).
+                self compile:source forClass:aClass inCategory:(asValueHolder ifTrue:[#aspects] ifFalse:[#accessing]).
             ] ifTrue:[
                 Transcript showCR:'method ''', methodName , ''' already present'
             ].
@@ -1337,7 +1337,7 @@
                                , '    self shouldImplement.\'
                                , '    ^ nil.'.
                     source := (source bindWith:varType with:name) withCRs.
-                    self compile:source forClass:aClass theMetaclass inCategory:'defaults'.
+                    self compile:source forClass:aClass theMetaclass inCategory:#defaults.
                 ].
             ].
         ].
@@ -1398,7 +1398,7 @@
                 self 
                     compile:source 
                     forClass:aClass 
-                    inCategory:(asValueHolder ifTrue:['aspects'] ifFalse:['accessing']).
+                    inCategory:(asValueHolder ifTrue:[#aspects] ifFalse:[#accessing]).
             ] ifTrue:[
                 Transcript showCR:'method ''', methodName , ':'' already present'
             ].
@@ -1444,7 +1444,7 @@
                        , '    ].\'
                        , '    %2 add: a%1'.
             source := (source bindWith:methodNameBase with:name) withCRs.
-            self compile:source forClass:aClass inCategory:'accessing'.
+            self compile:source forClass:aClass inCategory:#accessing.
         ] ifTrue:[
             Transcript showCR:'method ''', methodName , ''' already present'
         ].
@@ -1460,7 +1460,7 @@
             source := source
                        , '    %2 remove: a%1'.
             source := (source bindWith:methodNameBase with:name) withCRs.
-            self compile:source forClass:aClass inCategory:'accessing'.
+            self compile:source forClass:aClass inCategory:#accessing.
         ] ifTrue:[
             Transcript showCR:'method ''', methodName , ''' already present'
         ].
@@ -1517,7 +1517,7 @@
                 ].
                 source := source , '    ^ self %2 value'.
                 source := (source bindWith:methodName with:holderMethodName) withCRs.
-                self compile:source forClass:nonMetaClass inCategory:('accessing').
+                self compile:source forClass:nonMetaClass inCategory:#accessing.
             ] ifTrue:[
                 Transcript showCR:'method ''', methodName , ''' already present'
             ].
@@ -1529,7 +1529,7 @@
                 ].
                 source := source , '    self %2 value: newValue'.
                 source := (source bindWith:methodName with:holderMethodName) withCRs.
-                self compile:source forClass:nonMetaClass inCategory:('accessing').
+                self compile:source forClass:nonMetaClass inCategory:#accessing.
             ] ifTrue:[
                 Transcript showCR:'method ''', methodName , ':'' already present'
             ].
@@ -1544,7 +1544,7 @@
             source := source , '    ].\'.
             source := source , '    ^ %1\'.
             source := (source bindWith:holderMethodName) withCRs.
-            self compile:source forClass:nonMetaClass inCategory:('accessing').
+            self compile:source forClass:nonMetaClass inCategory:#accessing.
         ] ifTrue:[
             Transcript showCR:'method ''', methodName , ''' already present'
         ].
@@ -1573,7 +1573,7 @@
     ^ aVisitor %1self
 ') bindWith:selector)
             forClass:aClass 
-            inCategory:'visiting'.
+            inCategory:#visiting.
     ]
 !
 
@@ -1601,7 +1601,7 @@
 ' , txt , '
 "
 '             forClass:aClass 
-              inCategory:'documentation'.
+              inCategory:#documentation.
         ]
     ].
 !
@@ -1680,7 +1680,7 @@
         self 
             compile:code
             forClass:metaClass 
-            inCategory:'documentation'.
+            inCategory:#documentation.
     ].
 
     "Modified: / 24-11-2006 / 15:54:27 / cg"
@@ -1729,7 +1729,7 @@
 "
 '                   
             forClass:aClass 
-            inCategory:'documentation'.
+            inCategory:#documentation.
     ].
 !
 
@@ -1739,12 +1739,12 @@
     anImage storeOn: (imageStoreStream := WriteStream on: '').
 
     "/ if that method already exists, do not overwrite the category
-    category := 'image specs'.
+    category := #'image specs'.
     (mthd := aClass compiledMethodAt:sel) notNil ifTrue:[
         category := mthd category.
     ].
 
-    imageKey :=  (aClass name, ' ', sel) asSymbol.
+    imageKey :=  aClass theNonMetaclass name, ' ', sel.
     Icon constantNamed: imageKey put:nil.
     self
         compile: ((sel,
@@ -1779,7 +1779,7 @@
             self
                 compile:code
                 forClass:aClass 
-                inCategory:'documentation'.
+                inCategory:#documentation.
         ].
     ].
 !
@@ -1825,7 +1825,7 @@
     aCollectionOfVarNames do:[:eachVar |
         source := source , ('    ' , eachVar , ' := ' , eachVar , 'Arg.' , Character cr).
     ].
-    self compile:source forClass:aClass inCategory:'accessing'.
+    self compile:source forClass:aClass inCategory:#accessing.
 !
 
 createSubclassResponsibilityMethodFor:aSelector category:cat in:aClass
@@ -1852,7 +1852,7 @@
 
     |code|
 
-    (aClass includesSelector:#'update:with:from:') ifFalse:[
+    (aClass includesSelector:#update:with:from:) ifFalse:[
         generateComments ifFalse:[
             code :=
 'update:something with:aParameter from:changedObject
@@ -1876,7 +1876,7 @@
         self 
             compile:code
             forClass:aClass 
-            inCategory:'change & update'.
+            inCategory:#'change & update'.
     ]
 !
 
@@ -1900,7 +1900,7 @@
             self 
                 compile:code
                 forClass:aClass 
-                inCategory:'documentation'.
+                inCategory:#documentation.
         ]
     ].
 ! !
@@ -2493,13 +2493,13 @@
 !SmalltalkCodeGeneratorTool class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/SmalltalkCodeGeneratorTool.st,v 1.12 2012/01/27 13:55:22 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/SmalltalkCodeGeneratorTool.st,v 1.13 2012/05/22 16:33:26 stefan Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libtool/SmalltalkCodeGeneratorTool.st,v 1.12 2012/01/27 13:55:22 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libtool/SmalltalkCodeGeneratorTool.st,v 1.13 2012/05/22 16:33:26 stefan Exp §'
 !
 
 version_SVN
-    ^ '$Id: SmalltalkCodeGeneratorTool.st 7854 2012-01-30 17:49:41Z vranyj1 $'
+    ^ '$Id: SmalltalkCodeGeneratorTool.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/SystemBrowser.st	Wed May 30 21:46:55 2012 +0100
+++ b/SystemBrowser.st	Tue Jun 05 15:49:00 2012 +0100
@@ -5393,7 +5393,7 @@
     "return all instance- (if wantInst is true) and/or classmethods (if wantClass is true) 
      from classes in aCollectionOfClasses, where aBlock evaluates to true."
 
-    |list checkedClasses checkBlock|
+    |list checkedClasses checkBlock nClasses nClassesDone|
 
     checkedClasses := IdentitySet new.
     list := OrderedCollection new.
@@ -5413,6 +5413,9 @@
         ]
     ].
 
+    nClasses := aCollectionOfClasses size.
+    nClassesDone := 0.
+
     aCollectionOfClasses do:[:aClass |
         (aClass notNil and:[aClass isObsolete not]) ifTrue:[
             "
@@ -5427,10 +5430,16 @@
 "/                Transcript show:'searching '; show:aClass class name; showCR:' ...'; endEntry.
                 checkBlock value:(aClass class)
             ].
-            Processor yield
-        ]
+            nClassesDone > 5 ifTrue:[
+                "/ Processor yield
+                ProgressNotification progressPercentage:(nClassesDone / nClasses)*100.
+            ].
+        ].
+        nClassesDone := nClassesDone + 1.
     ].
     ^ list
+
+    "Modified: / 15-05-2012 / 10:36:44 / cg"
 !
 
 findMethodsIn:aCollectionOfClasses where:aBlock
@@ -5836,11 +5845,11 @@
 !SystemBrowser class methodsFor:'documentation'!
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libtool/SystemBrowser.st,v 1.300 2012/03/22 06:34:51 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libtool/SystemBrowser.st,v 1.301 2012/05/15 09:29:00 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: SystemBrowser.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: SystemBrowser.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
 
 SystemBrowser initialize!
--- a/Tools__BrowserList.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__BrowserList.st	Tue Jun 05 15:49:00 2012 +0100
@@ -13,16 +13,16 @@
 
 "{ NameSpace: Tools }"
 
-NavigatorModel subclass:#BrowserList
+Tools::NavigatorModel subclass:#BrowserList
 	instanceVariableNames:'menuHolder inGeneratorHolder outGeneratorHolder
-		selectionChangeCondition immediateUpdate doubleClickChannel
-		filter updateTrigger forceGeneratorTrigger hideUnloadedClasses
-		showClassPackages selectionHolder packageFilter nameSpaceFilter
-		organizerMode slaveMode listValid pseudoListLabelHolder icons
-		sortBy autoSelect showAllClassesInNameSpaceOrganisation
-		nameFilter showCoverageInformation searchHandler
-		lastUpdateFromSmalltalkTimestamp
-		numUpdatesFromSmalltalkInLast200Msecs'
+                selectionChangeCondition immediateUpdate doubleClickChannel
+                filter updateTrigger forceGeneratorTrigger hideUnloadedClasses
+                showClassPackages selectionHolder packageFilter nameSpaceFilter
+                organizerMode slaveMode listValid pseudoListLabelHolder icons
+                sortBy autoSelect showAllClassesInNameSpaceOrganisation
+                nameFilter showCoverageInformation searchHandler
+                lastUpdateFromSmalltalkTimestamp
+                numUpdatesFromSmalltalkInLast200Msecs autoUpdateOnChange'
 	classVariableNames:'SynchronousUpdate Icons'
 	poolDictionaries:''
 	category:'Interface-Browsers-New'
@@ -192,6 +192,30 @@
 
 !BrowserList methodsFor:'aspects'!
 
+autoUpdateOnChange
+    "automatic update of the list, when the system changes.
+     For some (slow) search lists (such as string-search), autoupdate is
+     disabled as it would otherwise make the browser unusable.
+     Those lists need an explicit menu-update action."
+
+    ^ autoUpdateOnChange ? true.
+
+    "Modified: / 24-02-2000 / 23:57:13 / cg"
+    "Created: / 15-05-2012 / 11:16:07 / cg"
+!
+
+autoUpdateOnChange: aBoolean
+    "automatic update of the list, when the system changes.
+     For some (slow) search lists (such as string-search), autoupdate is
+     disabled as it would otherwise make the browser unusable.
+     Those lists need an explicit menu-update action."
+
+    autoUpdateOnChange := aBoolean
+
+    "Modified: / 24-02-2000 / 23:57:13 / cg"
+    "Created: / 15-05-2012 / 11:17:18 / cg"
+!
+
 defaultSlaveModeValue
     ^ nil.
 
@@ -1784,9 +1808,9 @@
 !BrowserList class methodsFor:'documentation'!
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libtool/Tools_BrowserList.st,v 1.40 2012/02/13 13:45:31 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libtool/Tools_BrowserList.st,v 1.41 2012/05/15 09:32:01 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: Tools__BrowserList.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__BrowserList.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/Tools__ClassCategoryList.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__ClassCategoryList.st	Tue Jun 05 15:49:00 2012 +0100
@@ -915,7 +915,7 @@
 !ClassCategoryList class methodsFor:'documentation'!
 
 version
-    ^ '$Id: Tools__ClassCategoryList.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__ClassCategoryList.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 !
 
 version_CVS
@@ -923,6 +923,6 @@
 !
 
 version_SVN
-    ^ '$Id: Tools__ClassCategoryList.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__ClassCategoryList.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
 
--- a/Tools__ClassChecker.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__ClassChecker.st	Tue Jun 05 15:49:00 2012 +0100
@@ -916,7 +916,7 @@
 !ClassChecker class methodsFor:'documentation'!
 
 version
-    ^ '$Id: Tools__ClassChecker.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__ClassChecker.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 !
 
 version_CVS
@@ -924,5 +924,5 @@
 !
 
 version_SVN
-    ^ '$Id: Tools__ClassChecker.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__ClassChecker.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/Tools__ClassGeneratorList.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__ClassGeneratorList.st	Tue Jun 05 15:49:00 2012 +0100
@@ -513,7 +513,7 @@
 !ClassGeneratorList class methodsFor:'documentation'!
 
 version
-    ^ '$Id: Tools__ClassGeneratorList.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__ClassGeneratorList.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 !
 
 version_CVS
@@ -521,5 +521,5 @@
 !
 
 version_SVN
-    ^ '$Id: Tools__ClassGeneratorList.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__ClassGeneratorList.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/Tools__ClassList.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__ClassList.st	Tue Jun 05 15:49:00 2012 +0100
@@ -2042,5 +2042,5 @@
 !
 
 version_SVN
-    ^ '$Id: Tools__ClassList.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__ClassList.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/Tools__CodeHighlightingService.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__CodeHighlightingService.st	Tue Jun 05 15:49:00 2012 +0100
@@ -101,9 +101,9 @@
     ].
     "App did not provide any highlighter..."
     highlighter isNil ifTrue:[        
-        highlighter := (lang := codeView language)
-                ifNil:[nil]
-                ifNotNil:[lang syntaxHighlighterClass].
+        highlighter := (lang := codeView language) isNil
+                        ifTrue:[nil]
+                        ifFalse:[lang syntaxHighlighterClass].
     ].
     "HACK!!!!!!"
     highlighter == SyntaxHighlighter ifTrue:[
@@ -112,8 +112,8 @@
     ^ highlighter
 
     "Created: / 05-08-2011 / 10:48:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 26-09-2011 / 15:50:10 / cg"
     "Modified: / 28-09-2011 / 00:23:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 01-06-2012 / 21:17:50 / cg"
 !
 
 syntaxHighlighters
@@ -357,13 +357,13 @@
 !CodeHighlightingService class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/Tools__CodeHighlightingService.st,v 1.31 2012/03/07 17:21:49 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/Tools__CodeHighlightingService.st,v 1.32 2012/06/01 22:05:31 cg Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libtool/Tools__CodeHighlightingService.st,v 1.31 2012/03/07 17:21:49 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libtool/Tools__CodeHighlightingService.st,v 1.32 2012/06/01 22:05:31 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: Tools__CodeHighlightingService.st 7952 2012-03-21 17:50:14Z vranyj1 $'
+    ^ '$Id: Tools__CodeHighlightingService.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/Tools__CodeView2.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__CodeView2.st	Tue Jun 05 15:49:00 2012 +0100
@@ -1385,7 +1385,11 @@
 
     "Created: / 06-07-2011 / 17:12:58 / jv"
     "Modified: / 06-10-2011 / 14:13:44 / cg"
-! !
+!
+
+
+
+ !
 
 !CodeView2 methodsFor:'diff mode'!
 
@@ -2195,8 +2199,8 @@
 !CodeView2::GutterView methodsFor:'event handling'!
 
 buttonPress: btn x: x y: y
-
-    "Do not allow clicking on line numbers..."
+    |extraSafeArea|
+
     (x <= (self paddingLeft + widthAcceptCancel)) ifTrue:[
         (y < self acceptButtonBottom) ifTrue:[
             self accept.
@@ -2210,17 +2214,22 @@
         ^self.
     ].
 
+    "Do not allow clicking on line numbers..."
+    extraSafeArea := "('999' widthOn:self)" 10.
+    x < (self width - self paddingRight - widthDiffInfo - extraSafeArea) ifFalse:[^ self].
 
     ((x > (self paddingLeft + widthAcceptCancel)) or:
-        [x < (self width - self paddingRight - widthDiffInfo)])
-        ifTrue:[
-            (codeView buttonPress: btn x:x y:y in: self)
-                ifFalse:[super buttonPress: btn x: x y: y]
-        ] ifFalse:[
+        [x < (self width - self paddingRight - widthDiffInfo)]
+    ) ifTrue:[
+        (codeView buttonPress: btn x:x y:y in: self) ifFalse:[
             super buttonPress: btn x: x y: y
         ]
+    ] ifFalse:[
+        super buttonPress: btn x: x y: y
+    ]
 
     "Created: / 17-06-2011 / 13:02:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified (comment): / 18-05-2012 / 10:56:54 / cg"
 ! !
 
 !CodeView2::GutterView methodsFor:'help'!
@@ -2787,6 +2796,8 @@
     "Modified: / 17-03-2012 / 10:04:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+
+
 redrawLines
     |i pom|
 
@@ -3377,6 +3388,8 @@
 
 !CodeView2::TextView methodsFor:'scrolling'!
 
+
+
 basicScrollTo:anOrigin redraw:doRedraw
     super scrollTo:anOrigin redraw:doRedraw
 
@@ -3385,6 +3398,8 @@
     "Created: / 19-03-2012 / 17:01:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+
+
 originChanged:delta
 
     super originChanged:delta.
@@ -3394,6 +3409,8 @@
     "Created: / 07-12-2009 / 21:50:49 / Jindra <a>"
 !
 
+
+
 scrollTo:anOrigin redraw:doRedraw
 
     codeView scrollTo:anOrigin redraw:doRedraw in: self.
@@ -3402,7 +3419,9 @@
     "Modified: / 06-04-2010 / 14:04:28 / Jakub <zelenja7@fel.cvut.cz>"
     "Modified: / 17-03-2012 / 10:06:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Created: / 19-03-2012 / 17:05:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-! !
+!
+
+ !
 
 !CodeView2::TextView methodsFor:'undo & again'!
 
@@ -3425,15 +3444,15 @@
 !CodeView2 class methodsFor:'documentation'!
 
 version
-    ^ '$Id: Tools__CodeView2.st 8003 2012-05-19 13:13:43Z vranyj1 $'
+    ^ '$Header: /cvs/stx/stx/libtool/Tools__CodeView2.st,v 1.59 2012/05/18 08:59:17 cg Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libtool/Tools__CodeView2.st,v 1.58 2012/03/26 09:21:20 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libtool/Tools__CodeView2.st,v 1.59 2012/05/18 08:59:17 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: Tools__CodeView2.st 8003 2012-05-19 13:13:43Z vranyj1 $'
+    ^ '$Id: Tools__CodeView2.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
 
 CodeView2 initialize!
--- a/Tools__FullMethodCategoryList.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__FullMethodCategoryList.st	Tue Jun 05 15:49:00 2012 +0100
@@ -123,9 +123,9 @@
 !FullMethodCategoryList class methodsFor:'documentation'!
 
 version
-    ^ '$Id: Tools__FullMethodCategoryList.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__FullMethodCategoryList.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 !
 
 version_SVN
-    ^ '$Id: Tools__FullMethodCategoryList.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__FullMethodCategoryList.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/Tools__HierarchicalClassCategoryList.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__HierarchicalClassCategoryList.st	Tue Jun 05 15:49:00 2012 +0100
@@ -402,7 +402,7 @@
 !HierarchicalClassCategoryList class methodsFor:'documentation'!
 
 version
-    ^ '$Id: Tools__HierarchicalClassCategoryList.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__HierarchicalClassCategoryList.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 !
 
 version_CVS
@@ -410,5 +410,5 @@
 !
 
 version_SVN
-    ^ '$Id: Tools__HierarchicalClassCategoryList.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__HierarchicalClassCategoryList.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/Tools__HierarchicalClassList.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__HierarchicalClassList.st	Tue Jun 05 15:49:00 2012 +0100
@@ -308,11 +308,11 @@
 !HierarchicalClassList class methodsFor:'documentation'!
 
 version
-    ^ '$Id: Tools__HierarchicalClassList.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__HierarchicalClassList.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 !
 
 version_SVN
-    ^ '$Id: Tools__HierarchicalClassList.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__HierarchicalClassList.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
 
 HierarchicalClassList initialize!
--- a/Tools__HierarchicalProjectList.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__HierarchicalProjectList.st	Tue Jun 05 15:49:00 2012 +0100
@@ -518,7 +518,7 @@
 !HierarchicalProjectList class methodsFor:'documentation'!
 
 version
-    ^ '$Id: Tools__HierarchicalProjectList.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__HierarchicalProjectList.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 !
 
 version_CVS
@@ -526,5 +526,5 @@
 !
 
 version_SVN
-    ^ '$Id: Tools__HierarchicalProjectList.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__HierarchicalProjectList.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/Tools__ImplementingClassList.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__ImplementingClassList.st	Tue Jun 05 15:49:00 2012 +0100
@@ -117,9 +117,9 @@
 !ImplementingClassList class methodsFor:'documentation'!
 
 version
-    ^ '$Id: Tools__ImplementingClassList.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__ImplementingClassList.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 !
 
 version_SVN
-    ^ '$Id: Tools__ImplementingClassList.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__ImplementingClassList.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/Tools__ImplementingMethodList.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__ImplementingMethodList.st	Tue Jun 05 15:49:00 2012 +0100
@@ -287,9 +287,9 @@
 !ImplementingMethodList class methodsFor:'documentation'!
 
 version
-    ^ '$Id: Tools__ImplementingMethodList.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__ImplementingMethodList.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 !
 
 version_SVN
-    ^ '$Id: Tools__ImplementingMethodList.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__ImplementingMethodList.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/Tools__InheritanceClassList.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__InheritanceClassList.st	Tue Jun 05 15:49:00 2012 +0100
@@ -187,9 +187,9 @@
 !InheritanceClassList class methodsFor:'documentation'!
 
 version
-    ^ '$Id: Tools__InheritanceClassList.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__InheritanceClassList.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 !
 
 version_SVN
-    ^ '$Id: Tools__InheritanceClassList.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__InheritanceClassList.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/Tools__InlineMessageDialog.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__InlineMessageDialog.st	Tue Jun 05 15:49:00 2012 +0100
@@ -315,6 +315,12 @@
       )
 ! !
 
+!InlineMessageDialog class methodsFor:'others'!
+
+version_CVS
+    ^ '§Header: /cvs/stx/stx/libtool/Tools__InlineMessageDialog.st,v 1.7 2012/05/17 15:31:22 vrany Exp §'
+! !
+
 !InlineMessageDialog methodsFor:'accessing'!
 
 backgroundColor: aColor
@@ -920,13 +926,9 @@
 !InlineMessageDialog class methodsFor:'documentation'!
 
 version
-    ^ '$Id: Tools__InlineMessageDialog.st 7998 2012-05-17 15:29:24Z vranyj1 $'
-!
-
-version_CVS
-    ^ '§Header: /cvs/stx/stx/libtool/Tools__InlineMessageDialog.st,v 1.7 2012-05-17 16:31:22 +0100 vrany Exp §'
+    ^ '$Header: /cvs/stx/stx/libtool/Tools__InlineMessageDialog.st,v 1.7 2012/05/17 15:31:22 vrany Exp $'
 !
 
 version_SVN
-    ^ '$Id: Tools__InlineMessageDialog.st 7998 2012-05-17 15:29:24Z vranyj1 $'
+    ^ '$Id: Tools__InlineMessageDialog.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/Tools__MethodCategoryList.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__MethodCategoryList.st	Tue Jun 05 15:49:00 2012 +0100
@@ -2000,7 +2000,7 @@
 !
 
 version_SVN
-    ^ '$Id: Tools__MethodCategoryList.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__MethodCategoryList.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
 
 MethodCategoryList::CachedMethodInfo initialize!
--- a/Tools__MethodList.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__MethodList.st	Tue Jun 05 15:49:00 2012 +0100
@@ -438,9 +438,8 @@
 "/                        or:[oldMethod package ~= newMethod package
 "/                        or:[oldMethod resources ~= newMethod resources
 "/                        or:[showMethodComplexity value == true]]])
-                        true
-                        ifTrue:[
-                            "/ only update that methods entry
+                        self autoUpdateOnChange ifTrue:[
+                            "/ only update that method's entry
                             self updateListEntryFor:newMethod.    
                             "/ sigh - must invalidate
                             "/ self invalidateList.
@@ -474,17 +473,19 @@
             ].
 
             (something == #methodTrap 
-            or:[ something == #privacyOfMethod ]) ifTrue:[
+            or:[ something == #lastTestRunResult 
+            or:[ something == #privacyOfMethod ]]) ifTrue:[
                 cls := aParameter at:1.
                 sel := aParameter at:2.
                 (classes includesIdentical:cls) ifFalse:[ ^ self].
+
                 newMethod := cls compiledMethodAt:sel.
                 newMethod isNil ifTrue:[
                     self invalidateList.
                     ^ self
                 ].
 
-                (something == #privacyOfMethod) ifTrue:[
+                ((something == #privacyOfMethod) or:[something == #lastTestRunResult]) ifTrue:[
                     self updateListEntryFor:newMethod.    
                 ].
 
@@ -699,8 +700,8 @@
     super delayedUpdate:something with:aParameter from:changedObject
 
     "Created: / 05-02-2000 / 13:42:14 / cg"
-    "Modified: / 20-07-2011 / 18:56:23 / cg"
     "Modified: / 13-04-2012 / 16:04:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 04-06-2012 / 16:59:43 / cg"
 !
 
 selectedMethodsChanged
@@ -835,18 +836,19 @@
         (something == #methodTrap 
         or:[ something == #methodPrivacy
         or:[ something == #lastTestRunResult] ]) ifTrue:[
+            cls := aParameter at:1.
+            (classes includesIdentical:cls) ifFalse:[
+                ^ self   "/ I dont care for that class
+            ].
             self window shown ifFalse:[
                 "JV@2011-11-17: Do not break the dependency here,
                  because then the window won't get updates once
                  deiconified -> leads to confusing behavior (browser
                  shows obsolete info)"
                 "/changedObject removeDependent:self. "/ ?????
+                self invalidateList.
                 ^ self
             ].
-            cls := aParameter at:1.
-            (classes includesIdentical:cls) ifFalse:[
-                ^ self   "/ I dont care for that class
-            ].
         ].
 
         "/ as the organisation changes, flush my remembered redefinition-cache-info
@@ -901,8 +903,8 @@
 
     super update:something with:aParameter from:changedObject
 
-    "Modified: / 20-07-2011 / 18:54:04 / cg"
     "Modified: / 18-02-2012 / 21:58:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 04-06-2012 / 17:05:25 / cg"
 ! !
 
 !MethodList methodsFor:'drag & drop'!
@@ -1792,13 +1794,13 @@
 !MethodList class methodsFor:'documentation'!
 
 version
-    ^ '$Id: Tools__MethodList.st 7980 2012-04-18 07:18:46Z vranyj1 $'
+    ^ '$Header: /cvs/stx/stx/libtool/Tools_MethodList.st,v 1.64 2012/06/04 15:45:36 cg Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libtool/Tools_MethodList.st,v 1.62 2012/03/07 18:06:39 cg Exp §'
+    ^ 'Header: /cvs/stx/stx/libtool/Tools_MethodList.st,v 1.64 2012/06/04 15:45:36 cg Exp '
 !
 
 version_SVN
-    ^ '$Id: Tools__MethodList.st 7980 2012-04-18 07:18:46Z vranyj1 $'
+    ^ '$Id: Tools__MethodList.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/Tools__NamespaceList.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__NamespaceList.st	Tue Jun 05 15:49:00 2012 +0100
@@ -559,5 +559,5 @@
 !
 
 version_SVN
-    ^ '$Id: Tools__NamespaceList.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__NamespaceList.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/Tools__NavigationState.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__NavigationState.st	Tue Jun 05 15:49:00 2012 +0100
@@ -1673,5 +1673,5 @@
 !
 
 version_SVN
-    ^ '$Id: Tools__NavigationState.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__NavigationState.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/Tools__NavigatorCanvas.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__NavigatorCanvas.st	Tue Jun 05 15:49:00 2012 +0100
@@ -6933,5 +6933,5 @@
 !
 
 version_SVN
-    ^ '$Id: Tools__NavigatorCanvas.st 7979 2012-04-13 18:16:04Z vranyj1 $'
+    ^ '$Id: Tools__NavigatorCanvas.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/Tools__NavigatorModel.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__NavigatorModel.st	Tue Jun 05 15:49:00 2012 +0100
@@ -351,7 +351,7 @@
 !
 
 version_SVN
-    ^ '$Id: Tools__NavigatorModel.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__NavigatorModel.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
 
 NavigatorModel initialize!
--- a/Tools__NewSystemBrowser.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__NewSystemBrowser.st	Tue Jun 05 15:49:00 2012 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 2000 by eXept Software AG
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -65,7 +65,7 @@
 copyright
 "
  COPYRIGHT (c) 2000 by eXept Software AG
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -80,21 +80,21 @@
 "
     A new, much improved, system browser,
     providing:
-        multiple buffers
-        multi-select in most selectionLists
-        view-selection (by namespace, by project, by category ...)
-        embedded repository diff
-        more search operations
-        code checker (not yet complete)
-        some refactoryBrowser functionality
-        completely built using GUI painter and reusable components.
+	multiple buffers
+	multi-select in most selectionLists
+	view-selection (by namespace, by project, by category ...)
+	embedded repository diff
+	more search operations
+	code checker (not yet complete)
+	some refactoryBrowser functionality
+	completely built using GUI painter and reusable components.
 
     [author:]
-        cg@exept.de
+	cg@exept.de
 
     [see also:]
-        SystemBrowser BrowserView
-        VersionDiffBrowser
+	SystemBrowser BrowserView
+	VersionDiffBrowser
 "
 !
 
@@ -128,41 +128,41 @@
     icon := [self startNewSystemBrowserIcon].
 
     menuItem := MenuItem new
-                    value: action;
-                    isButton: false;
-                    translateLabel: true;
-                    label:'New System Browser' icon:icon;
-                    nameKey: #newSystemBrowser;
-                    activeHelpKey: #newSystemBrowser;
-                    submenuChannel: #menuClassHistoryNew;
-                    showBusyCursorWhilePerforming:true.
+		    value: action;
+		    isButton: false;
+		    translateLabel: true;
+		    label:'New System Browser' icon:icon;
+		    nameKey: #newSystemBrowser;
+		    activeHelpKey: #newSystemBrowser;
+		    submenuChannel: #menuClassHistoryNew;
+		    showBusyCursorWhilePerforming:true.
 
     NewLauncher
-        addMenuItem:menuItem
-        from:self
-        in:'menu.classes'
-        position:#(before systemBrowser)
-        space:true.
+	addMenuItem:menuItem
+	from:self
+	in:'menu.classes'
+	position:#(before systemBrowser)
+	space:true.
 
     menuItem := MenuItem new
-                    value: action;
-                    isButton: true;
-                    translateLabel: true;
-                    icon:icon;
-                    nameKey: #newSystemBrowser;
-                    activeHelpKey: #newSystemBrowser;
-                    submenuChannel: #menuClassHistoryNew;
-                    showBusyCursorWhilePerforming:true.
+		    value: action;
+		    isButton: true;
+		    translateLabel: true;
+		    icon:icon;
+		    nameKey: #newSystemBrowser;
+		    activeHelpKey: #newSystemBrowser;
+		    submenuChannel: #menuClassHistoryNew;
+		    showBusyCursorWhilePerforming:true.
 
     NewLauncher
-        addMenuItem:menuItem
-        from:self
-        in:'toolbar'
-        position:#(before systemBrowser)
-        space:false.
+	addMenuItem:menuItem
+	from:self
+	in:'toolbar'
+	position:#(before systemBrowser)
+	space:false.
     currentLauncher := NewLauncher current.
     currentLauncher notNil ifTrue:[
-        currentLauncher systemBrowserItemVisible value:false.
+	currentLauncher systemBrowserItemVisible value:false.
     ]
 
     "
@@ -180,7 +180,7 @@
 
     "/ could be autoloaded
     RefactoryChangeManager notNil ifTrue:[
-        RefactoryChangeManager autoload.
+	RefactoryChangeManager autoload.
     ]
 !
 
@@ -209,7 +209,7 @@
     NewLauncher removeUserTool:#newSystemBrowser.
     currentLauncher := NewLauncher current.
     currentLauncher notNil ifTrue:[
-        currentLauncher systemBrowserItemVisible value:true
+	currentLauncher systemBrowserItemVisible value:true
     ]
 
     "
@@ -226,23 +226,23 @@
 
 update:something with:aParameter from:changedObject
     something == #initialized ifTrue:[
-        changedObject == ObjectMemory ifTrue:[
-            self installInLauncher.
-            ObjectMemory removeDependent:self.
-        ]
+	changedObject == ObjectMemory ifTrue:[
+	    self installInLauncher.
+	    ObjectMemory removeDependent:self.
+	]
     ].
 ! !
 
 !NewSystemBrowser class methodsFor:'accessing-history'!
 
-addToBookMarks:aClass selector:aSelectorOrNil 
+addToBookMarks:aClass selector:aSelectorOrNil
     |newEntry|
 
-    (newEntry := self bookmarkForClass:aClass selector:aSelectorOrNil) isNil 
-        ifTrue:[ ^ self ].
-    (self bookmarks contains:[:entry | entry = newEntry ]) 
-        ifFalse:
-            [self bookmarks add:newEntry]
+    (newEntry := self bookmarkForClass:aClass selector:aSelectorOrNil) isNil
+	ifTrue:[ ^ self ].
+    (self bookmarks contains:[:entry | entry = newEntry ])
+	ifFalse:
+	    [self bookmarks add:newEntry]
 
     "Modified: / 02-06-2011 / 12:01:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -254,16 +254,16 @@
     newEntry isNil ifTrue:[^ self].
 
     FindHistory isNil ifTrue:[
-        FindHistory := OrderedCollection new.
+	FindHistory := OrderedCollection new.
     ].
 
     FindHistory := FindHistory select:[:entry | entry className ~= newEntry className
-                                                or:[entry selector ~= newEntry selector
-                                                or:[entry meta ~= newEntry meta]]].
+						or:[entry selector ~= newEntry selector
+						or:[entry meta ~= newEntry meta]]].
 
     FindHistory addFirst:newEntry.
     FindHistory size > 30 ifTrue:[
-        FindHistory removeLast.
+	FindHistory removeLast.
     ].
 
     "Created: / 02-07-2011 / 18:12:31 / cg"
@@ -272,8 +272,8 @@
 bookmarkForClass:aClass selector:aSelectorOrNil
 
     ^aSelectorOrNil
-        ifNil:[Bookmark forClass: aClass ]
-        ifNotNil:[Bookmark forClass: aClass selector: aSelectorOrNil ]
+	ifNil:[Bookmark forClass: aClass ]
+	ifNotNil:[Bookmark forClass: aClass selector: aSelectorOrNil ]
 
     "Created: / 05-05-2011 / 23:36:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 02-06-2011 / 23:21:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -289,8 +289,8 @@
 
 classHistory
     NewNavigationHistory isNil ifTrue:[
-        NewNavigationHistory := NavigationHistory new.
-        NewNavigationHistory beGlobalHistory.
+	NewNavigationHistory := NavigationHistory new.
+	NewNavigationHistory beGlobalHistory.
     ].
     ^ NewNavigationHistory
 
@@ -319,6 +319,9 @@
 
     spec := super flyByHelpSpec addPairsFrom:#(
 
+#runLintOnClasses
+'Run static code analyzis (lint) on the selected classes.'
+
 #bookmarks
 'Manage bookmarks'
 
@@ -344,67 +347,70 @@
 'The text-cursor''s column number'
 
 #lineLabel
-'The text-cursor''s line number. Double-Click to change'
+'The text-cursor''s line number. Double-click to change'
 
 #modeLabel
-'The editing mode (Insert vs. Overwrite). Right-Click to change'
+'The editing mode ("Insert" vs. "Overwrite"). Right-click to change'
 
 #packageInfoLabel
 'Package and revision info (for class or method)'
 
 #addBreakPoint
-'Add Breakpoint on Method'
+'Add breakpoint on method'
 
 #createBuffer
-'Add Buffer'
+'Add buffer'
 
 #removeBreakPoint
-'Remove Breakpoint'
+'Remove breakpoint'
 
 #recentlyChangedMethods
-'Recently Changed Methods'
+'Recently changed methods'
 
 #recentlyChangedClasses
-'Recently Changed Classes'
+'Recently changed classes'
 
 #recentChanges
-'Recently Changed Methods'
+'Recently changed methods'
 
 #recentVisits
-'Recently Visited'
+'Recently visited'
 
 #recentlyVisitedMethods
-'Recently Visited Methods'
+'Recently visited methods'
 
 #recentlyVisitedMethods
-'Visited Methods'
+'Visited methods'
 
 #executeSelectedClassMethod
-'Execute the Selected Class Method. Show Execution Time and Answer on the Transcript'
+'Execute the selected class method. Show execution time and answer on the Transcript'
+
+#initializeSharedPool
+'Initialize the selected SharedPool (by calling its "initialize"-method.'
 
 #launchSelectedApplication
-'Launch the Selected Application'
+'Launch the selected application'
 
 #runTestCases
-'Run Selected TestCase(s)'
+'Run selected testCase(s)'
 
 #runTestCasesWithDebug
-'Run Selected TestCase(s) with Debugger enabled'
+'Run selected testCase(s) with debugging enabled'
 
 #showCategories
 'Show Class Categories'
 
 #showClassHierarchy
-'Show Class Inheritance'
+'Show class inheritance'
 
 #showInheritedMethods
-'Show Inherited Methods (except Object''s)'
+'Show inherited methods (except Object''s)'
 
 #doNotShowInheritedMethods
-'Do not Show Inherited Methods'
+'Do not show inherited methods'
 
 #searchClass
-'Search Class'
+'Search class'
 
 #gotoClassEntryField
 'Goto class (uppercase) or method which implements this selector (lowercase)'
@@ -413,36 +419,36 @@
 "/'Goto Class'
 
 #formatCode
-'Format Code (PrettyPrint)'
+'Format code (PrettyPrint)'
 
 #hideToolBar
-'Hide Toolbar. Show again via the "View"-Menu'
+'Hide toolbar. Show again via the "View"-Menu'
 
 #hideBookmarkBar
-'Hide Bookmarkbar. Show again via the "View"-Menu'
+'Hide bookmarkbar. Show again via the "View"-Menu'
 
 #redoOperation
-'Redo undone Operation'
+'Redo undone operation'
 
 #undoOperation
-'Undo Operation'
+'Undo operation'
 
 ).
 
     (RefactoryChangeManager notNil and:[ RefactoryChangeManager isLoaded ]) ifTrue:[
-        manager := RefactoryChangeManager instance.
-        manager hasUndoableOperations
-        ifTrue:[
-            spec at:#undoOperation put:(self resources string:'Undo (%1)' with:manager undoChange name).
-        ].
-        manager hasRedoableOperations
-        ifTrue:[
-            spec at:#redoOperation put:(self resources string:'Redo (%1)' with:manager redoChange name).
-        ].
+	manager := RefactoryChangeManager instance.
+	manager hasUndoableOperations
+	ifTrue:[
+	    spec at:#undoOperation put:(self resources string:'Undo (%1)' with:manager undoChange name).
+	].
+	manager hasRedoableOperations
+	ifTrue:[
+	    spec at:#redoOperation put:(self resources string:'Redo (%1)' with:manager redoChange name).
+	].
     ].
     ^ spec.
 
-    "Modified: / 07-03-2012 / 11:57:59 / cg"
+    "Modified: / 28-05-2012 / 09:44:35 / cg"
 ! !
 
 !NewSystemBrowser class methodsFor:'image specs'!
@@ -471,8 +477,8 @@
     <resource: #image>
 
     ^Icon
-        constantNamed:#'Tools::NewSystemBrowser class defaultIcon1'
-        ifAbsentPut:[(Depth4Image new) width: 28; height: 28; photometric:(#palette); bitsPerSample:(#(4)); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+	constantNamed:#'Tools::NewSystemBrowser class defaultIcon1'
+	ifAbsentPut:[(Depth4Image new) width: 28; height: 28; photometric:(#palette); bitsPerSample:(#(4)); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
 @@@@@@@@@@@@@@@@@@@FY&Y&Y&X0@@@@@FY @@YDQDQDQB@@@@@FXFX@A$QDQDQDH@@@@FY Y&@CH"H"H"H @@@@X@@@X@@@@@@@@@@@@@A&XFY @@@@H@@@
 @@@@@@Y Y @@@@@ @@@@@@@@@FY @@@@@B@@@@@@@@@@@@@@@@@@H@@@@@@@@@@@@@@@@@@@@@@@A&Y&Y&Y#@@@@@F@"H"HFDQDQDQH@@@@@@@@@@@L"H"H"
 H @@@@@ @@@@@@@@@@@@@@@@@B@@@@@@@@@@@@@@@@@@H@@@@@@@@@@@@@@@@@@@@@@@A&Y&Y&Y#@@@@@F@"H"HFUUUUUUH@@@@@@@@@@@L"H"H"H @@@@@@
@@ -498,8 +504,8 @@
     <resource: #image>
 
     ^Icon
-        constantNamed:#'Tools::NewSystemBrowser class doNotShowInheritedMethodsIcon'
-        ifAbsentPut:[(Depth2Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'UUUUUUUUUUU@@@@EUDP@AT@@@@AT@@@EP@Q@AUUUUTU@@@@APUQDDTP@@@E@@@@EUUU@AUUUUPUT@@@UU@@EUP@a') ; colorMapFromArray:#[0 0 0 255 255 255 255 255 127 127 127 127]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+	constantNamed:#'Tools::NewSystemBrowser class doNotShowInheritedMethodsIcon'
+	ifAbsentPut:[(Depth2Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'UUUUUUUUUUU@@@@EUDP@AT@@@@AT@@@EP@Q@AUUUUTU@@@@APUQDDTP@@@E@@@@EUUU@AUUUUPUT@@@UU@@EUP@a') ; colorMapFromArray:#[0 0 0 255 255 255 255 255 127 127 127 127]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
 @@@@@@@@G0@@@@@@A<@@@@@@@_@@@@@@@G0@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
 @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
 @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; yourself); yourself]
@@ -514,6 +520,104 @@
     "Modified: / 18-02-2007 / 14:52:45 / cg"
 !
 
+initializeClass20x20Icon
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self initializeClass20x20Icon inspect
+     ImageEditor openOnClass:self andSelector:#initializeClass20x20Icon
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:'Tools::NewSystemBrowser class initializeClass20x20Icon'
+	ifAbsentPut:[(Depth8Image new) width: 20; height: 20; photometric:(#palette); bitsPerSample:(#[8]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@BP$@@@@@@@@@@@@@@@@@@@@@@@$HB@$@@@@@@@@@@@@@@@@@@@@@BP HBP@@@@@@@@@@@@@@@@@@
+@@$HB@ HBP@@@@@@@@@@@@@@@@@@BP HB@ I@@@@@@@DA@PDA@PDA@PIB@ HB@$C@@@@@@PA@PDA@PDA@P$HB@ HBPD@@@@@A@DA@PDA@PDABP HB@ I@P@@
+@@@D@PDA@PDA@PDABP HBPDA@@@@@@PA@PDA@PDA@PDABP$A@PD@@@@@A@DA@PDA@PDA@P$HB@$A@P@@@@@D@PDA@PDA@PDABP HBPDA@@@@@@LB@ HB@ HB
+@ HBBP$B@ H@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 32 223 32 127 127 127 170 170 170 255 255 255 0 0 0 248 252 128 208 220 0 255 251 176 226 167 74]; mask:((Depth1Image new) width: 20; height: 20; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@@@@@X@@@<@@@<@@A>@_?? _?? _?? _?? _?? _?? _?? _?? _?? _?? @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; yourself); yourself]
+!
+
+initializeSharedPool20x20Icon
+    ^ self initializeSharedPool20x20Icon2
+
+    "Modified: / 01-06-2012 / 15:53:25 / cg"
+!
+
+initializeSharedPool20x20Icon1
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self initializeSharedPool20x20Icon inspect
+     ImageEditor openOnClass:self andSelector:#initializeSharedPool20x20Icon
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:'Tools::NewSystemBrowser class initializeSharedPool20x20Icon'
+	ifAbsentPut:[(Depth8Image new) width: 20; height: 20; photometric:(#palette); bitsPerSample:(#[8]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@BP$@@@@@@@@@@@@@@@@@@@@@@@$HB@$@@@@@@@@@@@@@@@@@@@@@BP HBP@@@@@@@@@@@@@@@@@@
+@@$HB@ HBP@@@@@@@@@@@@@@@@@@BP HB@ I@@@@@@@DA@PDA@PDA@PIB@ HB@$C@@@@@@PA@PDA@PDA@P$HB@ HBPD@@@@@A@DA@PDA@PDABP HB@ I@P@@
+@@@D@PDA@PDA@PDABP HBPDA@@@@@@PA@PDA@PDA@PDABP$A@PD@@@@@A@DA@PDA@PDA@P$HB@$A@P@@@@@D@PDA@PDA@PDABP HBPDA@@@@@@LB@ HB@ HB
+@ HBBP$B@ H@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 0 127 255 127 127 127 170 170 170 255 255 255 0 0 0 248 252 128 208 220 0 255 251 176 226 167 74]; mask:((Depth1Image new) width: 20; height: 20; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@@@@@X@@@<@@@<@@A>@_?? _?? _?? _?? _?? _?? _?? _?? _?? _?? @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; yourself); yourself]
+
+    "Created: / 01-06-2012 / 15:53:14 / cg"
+!
+
+initializeSharedPool20x20Icon2
+    "This resource specification was automatically generated
+     by the ImageEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the ImageEditor may not be able to read the specification."
+
+    "
+     self initializeSharedPool20x20Icon2 inspect
+     ImageEditor openOnClass:self andSelector:#initializeSharedPool20x20Icon2
+     Icon flushCachedIcons
+    "
+
+    <resource: #image>
+
+    ^Icon
+	constantNamed:'Tools::NewSystemBrowser initializeSharedPool20x20Icon2'
+	ifAbsentPut:[(Depth8Image new) width: 20; height: 20; photometric:(#palette); bitsPerSample:(#[8]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@@@@@@@@@@@@@@@@@@M@@@@@@@@@@@@@@@@@@@@@@@@CP8M@@@@@@@@@@@@@@@@@@@MCP@MC04@CP4@@@@@@@@@@@@@CQ@QCQDRDP4QD@4@@@@@@@@@@@@@
+CQLTEQXUEALM@@@@@@@@@@@@@@@@CQDVB1XQCP@@@@@DA@PDA@PDA@PMDQXKE!!DM@@@@@@PA@PDA@PDACQLTEQXUEALM@@@@A@DA@PDA@P4PDP4QD!!DMDQ@M
+@@@D@PDA@PDA@P4M@P4OCPDMCP@@@@PA@PDA@PDA@PDACP8M@PD@@@@@A@DA@PDA@PDA@PDACPDA@P@@@@@D@PDA@PDA@PDA@PDA@PDA@@@@@@LB@ HB@ HB
+@ HB@ HB@ H@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; colorMapFromArray:#[0 0 0 0 127 255 127 127 127 170 170 170 255 255 255 0 0 0 248 252 128 208 220 0 255 251 176 226 167 74 87 87 87 255 248 248 240 240 240 240 144 24 255 248 48 255 248 96 255 248 24 240 208 24 255 248 152 255 248 88 255 248 136 255 248 176 255 248 200]; mask:((Depth1Image new) width: 20; height: 20; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+@@H@@@\@@C] @G?0@C? _?? _?? _?? _??0_?? _?? _?? _?? _?? _?? @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
+@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; yourself); yourself]
+!
+
 showCategoriesIcon
     "This resource specification was automatically generated
      by the ImageEditor of ST/X."
@@ -530,8 +634,8 @@
     <resource: #image>
 
     ^Icon
-        constantNamed:#'Tools::NewSystemBrowser class showCategoriesIcon'
-        ifAbsentPut:[(Depth1Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'?????8@C??.@@N@C @O?>8@A''?6 @X@C??/?<>@G8C<b') ; colorMapFromArray:#[0 0 0 255 255 255]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+	constantNamed:#'Tools::NewSystemBrowser class showCategoriesIcon'
+	ifAbsentPut:[(Depth1Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'?????8@C??.@@N@C @O?>8@A''?6 @X@C??/?<>@G8C<b') ; colorMapFromArray:#[0 0 0 255 255 255]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
 @@@@@A?8@@@@@A?8@@@@@A?8@@@@@A?8@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
 @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
 @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; yourself); yourself]
@@ -553,8 +657,8 @@
     <resource: #image>
 
     ^Icon
-        constantNamed:#'Tools::NewSystemBrowser class showClassHierarchyIcon'
-        ifAbsentPut:[(Depth1Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'?????8@C O.@@N@C @O?>8@A&@6 @X@C? O?<>@G8C<b') ; colorMapFromArray:#[0 0 0 255 255 255]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+	constantNamed:#'Tools::NewSystemBrowser class showClassHierarchyIcon'
+	ifAbsentPut:[(Depth1Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'?????8@C O.@@N@C @O?>8@A&@6 @X@C? O?<>@G8C<b') ; colorMapFromArray:#[0 0 0 255 255 255]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
 @@@@@@@@O0@@@@@@C<@@@@@@@?@@@@@@@O0@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
 @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
 @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; yourself); yourself]
@@ -576,8 +680,8 @@
     <resource: #image>
 
     ^Icon
-        constantNamed:#'Tools::NewSystemBrowser class showInheritedMethodsIcon'
-        ifAbsentPut:[(Depth2Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'UUUQUUUUTWU@@@CMT@A@HT@@@2MT@@B(P@@@@EUUUTU@@@@APU@@@TP@@@E@@@@EUUP@AUUUUPUT@@@UU@@EUP@a') ; colorMapFromArray:#[0 0 0 255 255 255 255 255 127 127 127 127]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
+	constantNamed:#'Tools::NewSystemBrowser class showInheritedMethodsIcon'
+	ifAbsentPut:[(Depth2Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(2 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'UUUQUUUUTWU@@@CMT@A@HT@@@2MT@@B(P@@@@EUUUTU@@@@APU@@@TP@@@E@@@@EUUP@AUUUUPUT@@@UU@@EUP@a') ; colorMapFromArray:#[0 0 0 255 255 255 255 255 127 127 127 127]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'
 @@@@A@@NO08@G0@_C9<@@@@@@>@@@@@@@O @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
 @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@
 @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@a') ; yourself); yourself]
@@ -605,112 +709,112 @@
 
     <resource: #canvas>
 
-    ^ 
+    ^
      #(FullSpec
-        name: browserPageSpec
-        window: 
+	name: browserPageSpec
+	window:
        (WindowSpec
-          label: 'NewSystemBrowser'
-          name: 'NewSystemBrowser'
-          min: (Point 0 0)
-          bounds: (Rectangle 0 0 800 700)
-          menu: mainMenu
-          icon: defaultIcon
-        )
-        component: 
+	  label: 'NewSystemBrowser'
+	  name: 'NewSystemBrowser'
+	  min: (Point 0 0)
+	  bounds: (Rectangle 0 0 800 700)
+	  menu: mainMenu
+	  icon: defaultIcon
+	)
+	component:
        (SpecCollection
-          collection: (
-           (NoteBookViewSpec
-              name: 'BrowserPageContents'
-              layout: (LayoutFrame 0 0 0 0 0 1 0 1)
-              canvas: browserCanvas
-              keepCanvasAlive: true
-            )
-           (ViewSpec
-              name: 'ToolBar'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              level: 0
-              visibilityChannel: toolBarVisibleHolder
-              component: 
-             (SpecCollection
-                collection: (
-                 (ActionButtonSpec
-                    label: 'hideToolBarIcon'
-                    name: 'HideToolBarButton'
-                    layout: (LayoutFrame 0 0 0 0 13 0 0 1)
-                    activeHelpKey: hideToolBar
-                    level: 0
-                    hasCharacterOrientedLabel: false
-                    translateLabel: true
-                    model: hideToolbar
-                    postBuildCallback: hideToolBarButtonCreated:
-                  )
-                 (MenuPanelSpec
-                    name: 'ToolBarMenu'
-                    layout: (LayoutFrame 13 0.0 0 0.0 -250 1.0 0 1.0)
-                    level: 0
-                    visibilityChannel: toolBarVisibleHolder
-                    menu: toolBarMenu
-                    textDefault: true
-                  )
-                 (UISubSpecification
-                    name: 'SubSpecification1'
-                    layout: (LayoutFrame -250 1 0 0 0 1 0 1)
-                    level: 0
-                    minorKey: #'searchSpec_live_level0'
-                  )
-                 )
-               
-              )
-            )
-           (ViewSpec
-              name: 'BookmarkBar'
-              layout: (LayoutFrame 0 0 40 0 0 1 67 0)
-              visibilityChannel: bookmarkBarVisibleHolder
-              component: 
-             (SpecCollection
-                collection: (
-                 (ActionButtonSpec
-                    label: 'hideToolBarIcon'
-                    name: 'Button1'
-                    layout: (LayoutFrame 0 0 0 0 13 0 0 1)
-                    activeHelpKey: hideToolBar
-                    level: 0
-                    hasCharacterOrientedLabel: false
-                    translateLabel: true
-                    model: hideBookmarkBar
-                    postBuildCallback: hideToolBarButtonCreated:
-                  )
-                 (SubCanvasSpec
-                    name: 'Bookmarks'
-                    layout: (LayoutFrame 13 0 2 0 0 1 -1 1)
-                    level: 0
-                    hasHorizontalScrollBar: false
-                    hasVerticalScrollBar: false
-                    miniScrollerHorizontal: false
-                    majorKey: BookmarkBar
-                    subAspectHolders: 
-                   (Array
-                      
-                     (SubChannelInfoSpec
-                        subAspect: bookmarkHolder
-                        aspect: bookmarkHolder
-                      ) 
-                     (SubChannelInfoSpec
-                        subAspect: bookmarksHolder
-                        aspect: bookmarkListHolder
-                      )
-                    )
-                    createNewApplication: true
-                    createNewBuilder: true
-                  )
-                 )
-               
-              )
-            )
-           )
-         
-        )
+	  collection: (
+	   (NoteBookViewSpec
+	      name: 'BrowserPageContents'
+	      layout: (LayoutFrame 0 0 0 0 0 1 0 1)
+	      canvas: browserCanvas
+	      keepCanvasAlive: true
+	    )
+	   (ViewSpec
+	      name: 'ToolBar'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      level: 0
+	      visibilityChannel: toolBarVisibleHolder
+	      component:
+	     (SpecCollection
+		collection: (
+		 (ActionButtonSpec
+		    label: 'hideToolBarIcon'
+		    name: 'HideToolBarButton'
+		    layout: (LayoutFrame 0 0 0 0 13 0 0 1)
+		    activeHelpKey: hideToolBar
+		    level: 0
+		    hasCharacterOrientedLabel: false
+		    translateLabel: true
+		    model: hideToolbar
+		    postBuildCallback: hideToolBarButtonCreated:
+		  )
+		 (MenuPanelSpec
+		    name: 'ToolBarMenu'
+		    layout: (LayoutFrame 13 0.0 0 0.0 -250 1.0 0 1.0)
+		    level: 0
+		    visibilityChannel: toolBarVisibleHolder
+		    menu: toolBarMenu
+		    textDefault: true
+		  )
+		 (UISubSpecification
+		    name: 'SubSpecification1'
+		    layout: (LayoutFrame -250 1 0 0 0 1 0 1)
+		    level: 0
+		    minorKey: #'searchSpec_live_level0'
+		  )
+		 )
+
+	      )
+	    )
+	   (ViewSpec
+	      name: 'BookmarkBar'
+	      layout: (LayoutFrame 0 0 40 0 0 1 67 0)
+	      visibilityChannel: bookmarkBarVisibleHolder
+	      component:
+	     (SpecCollection
+		collection: (
+		 (ActionButtonSpec
+		    label: 'hideToolBarIcon'
+		    name: 'Button1'
+		    layout: (LayoutFrame 0 0 0 0 13 0 0 1)
+		    activeHelpKey: hideToolBar
+		    level: 0
+		    hasCharacterOrientedLabel: false
+		    translateLabel: true
+		    model: hideBookmarkBar
+		    postBuildCallback: hideToolBarButtonCreated:
+		  )
+		 (SubCanvasSpec
+		    name: 'Bookmarks'
+		    layout: (LayoutFrame 13 0 2 0 0 1 -1 1)
+		    level: 0
+		    hasHorizontalScrollBar: false
+		    hasVerticalScrollBar: false
+		    miniScrollerHorizontal: false
+		    majorKey: BookmarkBar
+		    subAspectHolders:
+		   (Array
+
+		     (SubChannelInfoSpec
+			subAspect: bookmarkHolder
+			aspect: bookmarkHolder
+		      )
+		     (SubChannelInfoSpec
+			subAspect: bookmarksHolder
+			aspect: bookmarkListHolder
+		      )
+		    )
+		    createNewApplication: true
+		    createNewBuilder: true
+		  )
+		 )
+
+	      )
+	    )
+	   )
+
+	)
       )
 !
 
@@ -730,302 +834,302 @@
 
     ^
      #(#FullSpec
-        #name: #chainBrowserSpec
-        #window:
+	#name: #chainBrowserSpec
+	#window:
        #(#WindowSpec
-          #label: 'MethodBrowser'
-          #name: 'MethodBrowser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 185 379 647 679)
-        )
-        #component:
+	  #label: 'MethodBrowser'
+	  #name: 'MethodBrowser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 185 379 647 679)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #showHandle: false
-              #snapMode: #both
-              #handlePosition: #left
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#VariableHorizontalPanelSpec
-                    #name: 'VariableHorizontalPanel1'
-                    #showHandle: false
-                    #barWidth: 2
-                    #component:
-                   #(#SpecCollection
-                      #collection: #(
-                       #(#SubCanvasSpec
-                          #name: 'MethodList1'
-                          #majorKey: #'MethodList'
-                          #subAspectHolders:
-                         #(#Array
-
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showCoverageInformation
-                        #aspect: #showCoverageInformation
-                      ) 
-                           #(#SubChannelInfoSpec
-                              #subAspect: #doubleClickChannel
-                              #callBack: #methodDoubleClicked1
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #immediateUpdate
-                              #aspect: #immediateUpdate
-                            )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #inGeneratorHolder
-                              #aspect: #selectorListGenerator1
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #menuHolder
-                              #aspect: #selectorPopUpMenu
-                            )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #packageFilter
-                              #aspect: #packageFilter
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #selectedMethods
-                              #aspect: #selectedMethods1
-                              #callBack: #methodsSelectionChanged1
-                            )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #selectionChangeCondition
-                              #aspect: #selectionChangeConditionHolder
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #sortBy
-                              #aspect: #sortBy
-                            )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodInheritance
-                        #aspect: #showMethodInheritance
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodComplexity
-                        #aspect: #showMethodComplexity
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodTypeIcon
-                        #aspect: #showMethodTypeIcon
-                      )
-                          )
-                          #createNewApplication: true
-                          #createNewBuilder: true
-                        )
-                       #(#SubCanvasSpec
-                          #name: 'MethodList2'
-                          #majorKey: #'MethodList'
-                          #subAspectHolders:
-                         #(#Array
-
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showCoverageInformation
-                        #aspect: #showCoverageInformation
-                      ) 
-                           #(#SubChannelInfoSpec
-                              #subAspect: #doubleClickChannel
-                              #callBack: #methodDoubleClicked2
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #immediateUpdate
-                              #aspect: #immediateUpdate
-                            )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #inGeneratorHolder
-                              #aspect: #selectorListGenerator2
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #menuHolder
-                              #aspect: #selectorPopUpMenu
-                            )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #packageFilter
-                              #aspect: #packageFilter
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #selectedMethods
-                              #aspect: #selectedMethods2
-                              #callBack: #methodsSelectionChanged2
-                            )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #selectionChangeCondition
-                              #aspect: #selectionChangeConditionHolder
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #sortBy
-                              #aspect: #sortBy
-                            )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodInheritance
-                        #aspect: #showMethodInheritance
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodComplexity
-                        #aspect: #showMethodComplexity
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodTypeIcon
-                        #aspect: #showMethodTypeIcon
-                      )
-                          )
-                          #createNewApplication: true
-                          #createNewBuilder: true
-                        )
-                       #(#SubCanvasSpec
-                          #name: 'MethodList3'
-                          #majorKey: #'MethodList'
-                          #subAspectHolders:
-                         #(#Array
-
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showCoverageInformation
-                        #aspect: #showCoverageInformation
-                      ) 
-                           #(#SubChannelInfoSpec
-                              #subAspect: #doubleClickChannel
-                              #callBack: #methodDoubleClicked3
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #immediateUpdate
-                              #aspect: #immediateUpdate
-                            )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #inGeneratorHolder
-                              #aspect: #selectorListGenerator3
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #menuHolder
-                              #aspect: #selectorPopUpMenu
-                            )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #packageFilter
-                              #aspect: #packageFilter
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #selectedMethods
-                              #aspect: #selectedMethods3
-                              #callBack: #methodsSelectionChanged3
-                            )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #selectionChangeCondition
-                              #aspect: #selectionChangeConditionHolder
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #sortBy
-                              #aspect: #sortBy
-                            )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodInheritance
-                        #aspect: #showMethodInheritance
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodComplexity
-                        #aspect: #showMethodComplexity
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodTypeIcon
-                        #aspect: #showMethodTypeIcon
-                      )
-                          )
-                          #createNewApplication: true
-                          #createNewBuilder: true
-                        )
-                       #(#SubCanvasSpec
-                          #name: 'MethodList4'
-                          #majorKey: #'MethodList'
-                          #subAspectHolders:
-                         #(#Array
-
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showCoverageInformation
-                        #aspect: #showCoverageInformation
-                      ) 
-                           #(#SubChannelInfoSpec
-                              #subAspect: #doubleClickChannel
-                              #callBack: #methodDoubleClicked4
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #immediateUpdate
-                              #aspect: #immediateUpdate
-                            )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #inGeneratorHolder
-                              #aspect: #selectorListGenerator4
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #menuHolder
-                              #aspect: #selectorPopUpMenu
-                            )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #packageFilter
-                              #aspect: #packageFilter
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #selectedMethods
-                              #aspect: #selectedMethods4
-                              #callBack: #methodsSelectionChanged4
-                            )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #selectionChangeCondition
-                              #aspect: #selectionChangeConditionHolder
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #sortBy
-                              #aspect: #sortBy
-                            )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodInheritance
-                        #aspect: #showMethodInheritance
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodComplexity
-                        #aspect: #showMethodComplexity
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodTypeIcon
-                        #aspect: #showMethodTypeIcon
-                      )
-                          )
-                          #createNewApplication: true
-                          #createNewBuilder: true
-                        )
-                       )
-
-                    )
-                    #handles: #(#Any 0.25 0.5 0.75 1.0)
-                  )
-                 #(#SubCanvasSpec
-                    #name: 'CodePane'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NewSystemBrowser'
-                    #minorKey: #codePaneSpec
-                  )
+	  #collection: #(
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #showHandle: false
+	      #snapMode: #both
+	      #handlePosition: #left
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#VariableHorizontalPanelSpec
+		    #name: 'VariableHorizontalPanel1'
+		    #showHandle: false
+		    #barWidth: 2
+		    #component:
+		   #(#SpecCollection
+		      #collection: #(
+		       #(#SubCanvasSpec
+			  #name: 'MethodList1'
+			  #majorKey: #'MethodList'
+			  #subAspectHolders:
+			 #(#Array
+
+		     #(#SubChannelInfoSpec
+			#subAspect: #showCoverageInformation
+			#aspect: #showCoverageInformation
+		      )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #doubleClickChannel
+			      #callBack: #methodDoubleClicked1
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #immediateUpdate
+			      #aspect: #immediateUpdate
+			    )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #inGeneratorHolder
+			      #aspect: #selectorListGenerator1
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #menuHolder
+			      #aspect: #selectorPopUpMenu
+			    )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #packageFilter
+			      #aspect: #packageFilter
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #selectedMethods
+			      #aspect: #selectedMethods1
+			      #callBack: #methodsSelectionChanged1
+			    )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #selectionChangeCondition
+			      #aspect: #selectionChangeConditionHolder
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #sortBy
+			      #aspect: #sortBy
+			    )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodInheritance
+			#aspect: #showMethodInheritance
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodComplexity
+			#aspect: #showMethodComplexity
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodTypeIcon
+			#aspect: #showMethodTypeIcon
+		      )
+			  )
+			  #createNewApplication: true
+			  #createNewBuilder: true
+			)
+		       #(#SubCanvasSpec
+			  #name: 'MethodList2'
+			  #majorKey: #'MethodList'
+			  #subAspectHolders:
+			 #(#Array
+
+		     #(#SubChannelInfoSpec
+			#subAspect: #showCoverageInformation
+			#aspect: #showCoverageInformation
+		      )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #doubleClickChannel
+			      #callBack: #methodDoubleClicked2
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #immediateUpdate
+			      #aspect: #immediateUpdate
+			    )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #inGeneratorHolder
+			      #aspect: #selectorListGenerator2
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #menuHolder
+			      #aspect: #selectorPopUpMenu
+			    )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #packageFilter
+			      #aspect: #packageFilter
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #selectedMethods
+			      #aspect: #selectedMethods2
+			      #callBack: #methodsSelectionChanged2
+			    )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #selectionChangeCondition
+			      #aspect: #selectionChangeConditionHolder
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #sortBy
+			      #aspect: #sortBy
+			    )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodInheritance
+			#aspect: #showMethodInheritance
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodComplexity
+			#aspect: #showMethodComplexity
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodTypeIcon
+			#aspect: #showMethodTypeIcon
+		      )
+			  )
+			  #createNewApplication: true
+			  #createNewBuilder: true
+			)
+		       #(#SubCanvasSpec
+			  #name: 'MethodList3'
+			  #majorKey: #'MethodList'
+			  #subAspectHolders:
+			 #(#Array
+
+		     #(#SubChannelInfoSpec
+			#subAspect: #showCoverageInformation
+			#aspect: #showCoverageInformation
+		      )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #doubleClickChannel
+			      #callBack: #methodDoubleClicked3
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #immediateUpdate
+			      #aspect: #immediateUpdate
+			    )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #inGeneratorHolder
+			      #aspect: #selectorListGenerator3
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #menuHolder
+			      #aspect: #selectorPopUpMenu
+			    )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #packageFilter
+			      #aspect: #packageFilter
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #selectedMethods
+			      #aspect: #selectedMethods3
+			      #callBack: #methodsSelectionChanged3
+			    )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #selectionChangeCondition
+			      #aspect: #selectionChangeConditionHolder
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #sortBy
+			      #aspect: #sortBy
+			    )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodInheritance
+			#aspect: #showMethodInheritance
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodComplexity
+			#aspect: #showMethodComplexity
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodTypeIcon
+			#aspect: #showMethodTypeIcon
+		      )
+			  )
+			  #createNewApplication: true
+			  #createNewBuilder: true
+			)
+		       #(#SubCanvasSpec
+			  #name: 'MethodList4'
+			  #majorKey: #'MethodList'
+			  #subAspectHolders:
+			 #(#Array
+
+		     #(#SubChannelInfoSpec
+			#subAspect: #showCoverageInformation
+			#aspect: #showCoverageInformation
+		      )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #doubleClickChannel
+			      #callBack: #methodDoubleClicked4
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #immediateUpdate
+			      #aspect: #immediateUpdate
+			    )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #inGeneratorHolder
+			      #aspect: #selectorListGenerator4
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #menuHolder
+			      #aspect: #selectorPopUpMenu
+			    )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #packageFilter
+			      #aspect: #packageFilter
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #selectedMethods
+			      #aspect: #selectedMethods4
+			      #callBack: #methodsSelectionChanged4
+			    )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #selectionChangeCondition
+			      #aspect: #selectionChangeConditionHolder
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #sortBy
+			      #aspect: #sortBy
+			    )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodInheritance
+			#aspect: #showMethodInheritance
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodComplexity
+			#aspect: #showMethodComplexity
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodTypeIcon
+			#aspect: #showMethodTypeIcon
+		      )
+			  )
+			  #createNewApplication: true
+			  #createNewBuilder: true
+			)
+		       )
+
+		    )
+		    #handles: #(#Any 0.25 0.5 0.75 1.0)
+		  )
+		 #(#SubCanvasSpec
+		    #name: 'CodePane'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NewSystemBrowser'
+		    #minorKey: #codePaneSpec
+		  )
 "/                 #(#CodeViewSpec
 "/                    #name: 'CodeView'
 "/                    #model: #codeHolder
@@ -1035,16 +1139,16 @@
 "/              #postBuildCallback: #postBuildCodeView:
 "/              #modifiedChannel: #codeModifiedHolder
 "/                  )
-                 )
-
-              )
-              #handles: #(#Any 0.5 1.0)
-              postBuildCallback: postBuildTabContentView:
-
-            )
-           )
-
-        )
+		 )
+
+	      )
+	      #handles: #(#Any 0.5 1.0)
+	      postBuildCallback: postBuildTabContentView:
+
+	    )
+	   )
+
+	)
       )
 
     "Modified: / 27-04-2010 / 16:29:54 / cg"
@@ -1067,45 +1171,45 @@
 
     ^
      #(#FullSpec
-        #name: #classDocumentationBrowserSpec
-        #window:
+	#name: #classDocumentationBrowserSpec
+	#window:
        #(#WindowSpec
-          #label: 'Full Class Browser'
-          #name: 'Full Class Browser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 12 22 474 322)
-        )
-        #component:
+	  #label: 'Full Class Browser'
+	  #name: 'Full Class Browser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 12 22 474 322)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #showHandle: false
-              #snapMode: #both
-              #handlePosition: #left
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#SubCanvasSpec
-                    #name: 'Navigator'
-                    #majorKey: #'NavigatorCanvas'
-                    #minorKey: #categoryAndSingleClassOnlySpec
-                  )
-                 #(#HTMLViewSpec
-                    #name: 'HTMLBrowser1'
-                    #htmlText: #classDocumentationHolder
-                    #hasHorizontalScrollBar: true
-                    #hasVerticalScrollBar: true
-                  )
-                 )
-
-              )
-              #handles: #(#Any 0.5 1.0)
-            )
-           )
-
-        )
+	  #collection: #(
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #showHandle: false
+	      #snapMode: #both
+	      #handlePosition: #left
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#SubCanvasSpec
+		    #name: 'Navigator'
+		    #majorKey: #'NavigatorCanvas'
+		    #minorKey: #categoryAndSingleClassOnlySpec
+		  )
+		 #(#HTMLViewSpec
+		    #name: 'HTMLBrowser1'
+		    #htmlText: #classDocumentationHolder
+		    #hasHorizontalScrollBar: true
+		    #hasVerticalScrollBar: true
+		  )
+		 )
+
+	      )
+	      #handles: #(#Any 0.5 1.0)
+	    )
+	   )
+
+	)
       )
 !
 
@@ -1123,163 +1227,163 @@
 
     <resource: #canvas>
 
-    ^ 
+    ^
      #(FullSpec
-        name: codePaneSpec
-        window: 
+	name: codePaneSpec
+	window:
        (WindowSpec
-          label: 'SystemBrowser'
-          name: 'SystemBrowser'
-          min: (Point 0 0)
-          bounds: (Rectangle 0 0 998 535)
-          icon: defaultIcon
-        )
-        component: 
+	  label: 'SystemBrowser'
+	  name: 'SystemBrowser'
+	  min: (Point 0 0)
+	  bounds: (Rectangle 0 0 998 535)
+	  icon: defaultIcon
+	)
+	component:
        (SpecCollection
-          collection: (
-           (VariableHorizontalPanelSpec
-              name: 'EditorAndBrowsletBox'
-              layout: (LayoutFrame 0 0 0 0 0 1 0 1)
-              component: 
-             (SpecCollection
-                collection: (
-                 (ViewSpec
-                    name: 'EditorBox'
-                    component: 
-                   (SpecCollection
-                      collection: (
-                       (NoteBookViewSpec
-                          name: 'EditorNoteBook'
-                          layout: (LayoutFrame 0 0 0 0 0 1 -26 1)
-                          level: 0
-                          model: selectedEditorNoteBookTabIndexHolder
-                          menu: editorNoteBookListHolder
-                          useIndex: true
-                          canvas: editorNoteBookCanvasHolder
-                          keepCanvasAlive: true
-                          postBuildCallback: postBuildEditorNoteBook:
-                        )
-                       (SubCanvasSpec
-                          name: 'StringSearchToolCanvas'
-                          layout: (LayoutFrame 0 0 -24 1 0 1 0 1)
-                          visibilityChannel: stringSearchToolVisibleHolder
-                          hasHorizontalScrollBar: false
-                          hasVerticalScrollBar: false
-                          majorKey: StringSearchToolForTextView
-                          createNewApplication: true
-                          createNewBuilder: false
-                          postBuildCallback: postBuildStringSearchTool:
-                        )
-                       )
-                     
-                    )
-                  )
-                 )
-               
-              )
-              handles: (Any 1.0)
-              postBuildCallback: postBuildCodePaneAndPluginView:
-            )
-           (ViewSpec
-              name: 'InfoBox'
-              layout: (LayoutFrame 0 0 -24 1 0 1 0 1)
-              visibilityChannel: codeInfoVisible
-              component: 
-             (SpecCollection
-                collection: (
-                 (VariableHorizontalPanelSpec
-                    name: 'InfoBoxPanel'
-                    layout: (LayoutFrame 0 0.0 0 0.0 -60 1.0 0 1.0)
-                    showHandle: false
-                    component: 
-                   (SpecCollection
-                      collection: (
-                       (LabelSpec
-                          label: 'Info'
-                          name: 'InfoLabel'
-                          level: -1
-                          translateLabel: true
-                          labelChannel: infoLabelHolder
-                          adjust: left
-                        )
-                       (HorizontalPanelViewSpec
-                          name: 'PackageInfoPanel'
-                          level: -1
-                          horizontalLayout: rightSpaceFit
-                          verticalLayout: fitSpace
-                          horizontalSpace: 0
-                          verticalSpace: 0
-                          elementsChangeSize: true
-                          component: 
-                         (SpecCollection
-                            collection: (
-                             (LabelSpec
-                                label: 'Package'
-                                name: 'PackageLabel'
-                                activeHelpKey: packageInfoLabel
-                                level: 0
-                                borderWidth: -1
-                                backgroundChannel: packageInfoBackgroundColorHolder
-                                translateLabel: true
-                                labelChannel: packageLabelHolder
-                                adjust: left
-                                useDefaultExtent: true
-                              )
-                             (ActionButtonSpec
-                                label: 'Info'
-                                name: 'PackageInfoButton'
-                                level: 0
-                                initiallyInvisible: true
-                                backgroundChannel: packageInfoBackgroundColorHolder
-                                foregroundColor: (Color 0.0 0.0 100.0)
-                                translateLabel: true
-                                resizeForLabel: true
-                                extent: (Point 36 23)
-                                postBuildCallback: postBuildPackageInfoButton:
-                              )
-                             )
-                           
-                          )
-                        )
-                       )
-                     
-                    )
-                    handles: (Any 0.66 1.0)
-                  )
-                 (LabelSpec
-                    name: 'ModeLabel'
-                    layout: (LayoutFrame -60 1 0 0.0 -50 1 0 1.0)
-                    activeHelpKey: modeLabel
-                    level: -1
-                    translateLabel: true
-                    labelChannel: modeLabelHolder
-                    postBuildCallback: postBuildEditModeInfoLabel:
-                  )
-                 (LabelSpec
-                    name: 'CursorLineLabel'
-                    layout: (LayoutFrame -50 1 0 0.0 -20 1 0 1.0)
-                    activeHelpKey: lineLabel
-                    level: -1
-                    translateLabel: true
-                    labelChannel: cursorLineLabelHolder
-                    adjust: right
-                  )
-                 (LabelSpec
-                    name: 'CursorColLabel'
-                    layout: (LayoutFrame -20 1 0 0.0 0 1.0 0 1.0)
-                    activeHelpKey: columnLabel
-                    level: -1
-                    translateLabel: true
-                    labelChannel: cursorColLabelHolder
-                    adjust: right
-                  )
-                 )
-               
-              )
-            )
-           )
-         
-        )
+	  collection: (
+	   (VariableHorizontalPanelSpec
+	      name: 'EditorAndBrowsletBox'
+	      layout: (LayoutFrame 0 0 0 0 0 1 0 1)
+	      component:
+	     (SpecCollection
+		collection: (
+		 (ViewSpec
+		    name: 'EditorBox'
+		    component:
+		   (SpecCollection
+		      collection: (
+		       (NoteBookViewSpec
+			  name: 'EditorNoteBook'
+			  layout: (LayoutFrame 0 0 0 0 0 1 -26 1)
+			  level: 0
+			  model: selectedEditorNoteBookTabIndexHolder
+			  menu: editorNoteBookListHolder
+			  useIndex: true
+			  canvas: editorNoteBookCanvasHolder
+			  keepCanvasAlive: true
+			  postBuildCallback: postBuildEditorNoteBook:
+			)
+		       (SubCanvasSpec
+			  name: 'StringSearchToolCanvas'
+			  layout: (LayoutFrame 0 0 -24 1 0 1 0 1)
+			  visibilityChannel: stringSearchToolVisibleHolder
+			  hasHorizontalScrollBar: false
+			  hasVerticalScrollBar: false
+			  majorKey: StringSearchToolForTextView
+			  createNewApplication: true
+			  createNewBuilder: false
+			  postBuildCallback: postBuildStringSearchTool:
+			)
+		       )
+
+		    )
+		  )
+		 )
+
+	      )
+	      handles: (Any 1.0)
+	      postBuildCallback: postBuildCodePaneAndPluginView:
+	    )
+	   (ViewSpec
+	      name: 'InfoBox'
+	      layout: (LayoutFrame 0 0 -24 1 0 1 0 1)
+	      visibilityChannel: codeInfoVisible
+	      component:
+	     (SpecCollection
+		collection: (
+		 (VariableHorizontalPanelSpec
+		    name: 'InfoBoxPanel'
+		    layout: (LayoutFrame 0 0.0 0 0.0 -60 1.0 0 1.0)
+		    showHandle: false
+		    component:
+		   (SpecCollection
+		      collection: (
+		       (LabelSpec
+			  label: 'Info'
+			  name: 'InfoLabel'
+			  level: -1
+			  translateLabel: true
+			  labelChannel: infoLabelHolder
+			  adjust: left
+			)
+		       (HorizontalPanelViewSpec
+			  name: 'PackageInfoPanel'
+			  level: -1
+			  horizontalLayout: rightSpaceFit
+			  verticalLayout: fitSpace
+			  horizontalSpace: 0
+			  verticalSpace: 0
+			  elementsChangeSize: true
+			  component:
+			 (SpecCollection
+			    collection: (
+			     (LabelSpec
+				label: 'Package'
+				name: 'PackageLabel'
+				activeHelpKey: packageInfoLabel
+				level: 0
+				borderWidth: -1
+				backgroundChannel: packageInfoBackgroundColorHolder
+				translateLabel: true
+				labelChannel: packageLabelHolder
+				adjust: left
+				useDefaultExtent: true
+			      )
+			     (ActionButtonSpec
+				label: 'Info'
+				name: 'PackageInfoButton'
+				level: 0
+				initiallyInvisible: true
+				backgroundChannel: packageInfoBackgroundColorHolder
+				foregroundColor: (Color 0.0 0.0 100.0)
+				translateLabel: true
+				resizeForLabel: true
+				extent: (Point 36 23)
+				postBuildCallback: postBuildPackageInfoButton:
+			      )
+			     )
+
+			  )
+			)
+		       )
+
+		    )
+		    handles: (Any 0.66 1.0)
+		  )
+		 (LabelSpec
+		    name: 'ModeLabel'
+		    layout: (LayoutFrame -60 1 0 0.0 -50 1 0 1.0)
+		    activeHelpKey: modeLabel
+		    level: -1
+		    translateLabel: true
+		    labelChannel: modeLabelHolder
+		    postBuildCallback: postBuildEditModeInfoLabel:
+		  )
+		 (LabelSpec
+		    name: 'CursorLineLabel'
+		    layout: (LayoutFrame -50 1 0 0.0 -20 1 0 1.0)
+		    activeHelpKey: lineLabel
+		    level: -1
+		    translateLabel: true
+		    labelChannel: cursorLineLabelHolder
+		    adjust: right
+		  )
+		 (LabelSpec
+		    name: 'CursorColLabel'
+		    layout: (LayoutFrame -20 1 0 0.0 0 1.0 0 1.0)
+		    activeHelpKey: columnLabel
+		    level: -1
+		    translateLabel: true
+		    labelChannel: cursorColLabelHolder
+		    adjust: right
+		  )
+		 )
+
+	      )
+	    )
+	   )
+
+	)
       )
 !
 
@@ -1297,63 +1401,63 @@
 
     <resource: #canvas>
 
-    ^ 
+    ^
      #(FullSpec
-        name: fullBrowserSpec
-        window: 
+	name: fullBrowserSpec
+	window:
        (WindowSpec
-          label: 'SystemBrowser'
-          name: 'SystemBrowser'
-          min: (Point 0 0)
-          bounds: (Rectangle 0 0 462 300)
-          icon: defaultIcon
-        )
-        component: 
+	  label: 'SystemBrowser'
+	  name: 'SystemBrowser'
+	  min: (Point 0 0)
+	  bounds: (Rectangle 0 0 462 300)
+	  icon: defaultIcon
+	)
+	component:
        (SpecCollection
-          collection: (
-           (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )
-           (VariableVerticalPanelSpec
-              name: 'VariableVerticalPanel1'
-              layout: (LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              barWidth: 2
-              showHandle: false
-              snapMode: both
-              handlePosition: left
-              component: 
-             (SpecCollection
-                collection: (
-                 (SubCanvasSpec
-                    name: 'Navigator'
-                    autoHideScrollBars: false
-                    majorKey: NavigatorCanvas
-                    minorKey: windowSpec
-                    createNewBuilder: false
-                  )
-                 (SubCanvasSpec
-                    name: 'CodePane'
-                    autoHideScrollBars: false
-                    majorKey: NewSystemBrowser
-                    minorKey: codePaneSpec
-                    createNewBuilder: false
-                  )
-                 )
-               
-              )
-              handles: (Any 0.5 1.0)
-              postBuildCallback: postBuildTabContentView:
-            )
-           )
-         
-        )
+	  collection: (
+	   (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+	   (VariableVerticalPanelSpec
+	      name: 'VariableVerticalPanel1'
+	      layout: (LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      barWidth: 2
+	      showHandle: false
+	      snapMode: both
+	      handlePosition: left
+	      component:
+	     (SpecCollection
+		collection: (
+		 (SubCanvasSpec
+		    name: 'Navigator'
+		    autoHideScrollBars: false
+		    majorKey: NavigatorCanvas
+		    minorKey: windowSpec
+		    createNewBuilder: false
+		  )
+		 (SubCanvasSpec
+		    name: 'CodePane'
+		    autoHideScrollBars: false
+		    majorKey: NewSystemBrowser
+		    minorKey: codePaneSpec
+		    createNewBuilder: false
+		  )
+		 )
+
+	      )
+	      handles: (Any 0.5 1.0)
+	      postBuildCallback: postBuildTabContentView:
+	    )
+	   )
+
+	)
       )
 !
 
@@ -1373,49 +1477,49 @@
 
     ^
      #(#FullSpec
-        #name: #fullClassSourceBrowserSpec
-        #window:
+	#name: #fullClassSourceBrowserSpec
+	#window:
        #(#WindowSpec
-          #label: 'Full Class Browser'
-          #name: 'NewBrowser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 13 23 475 323)
-        )
-        #component:
+	  #label: 'Full Class Browser'
+	  #name: 'NewBrowser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 13 23 475 323)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #barWidth: 2
-              #showHandle: false
-              #handlePosition: #left
-              #snapMode: #both
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#SubCanvasSpec
-                    #name: 'Navigator'
-                    #majorKey: #'NavigatorCanvas'
-                    #minorKey: #categoryAndSingleClassOnlySpec
-                  )
-                 #(#SubCanvasSpec
-                    #name: 'CodePane'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NewSystemBrowser'
-                    #minorKey: #codePaneSpec
-                  )
+	  #collection: #(
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #barWidth: 2
+	      #showHandle: false
+	      #handlePosition: #left
+	      #snapMode: #both
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#SubCanvasSpec
+		    #name: 'Navigator'
+		    #majorKey: #'NavigatorCanvas'
+		    #minorKey: #categoryAndSingleClassOnlySpec
+		  )
+		 #(#SubCanvasSpec
+		    #name: 'CodePane'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NewSystemBrowser'
+		    #minorKey: #codePaneSpec
+		  )
 "/                 #(#CodeViewSpec
 "/                    #name: 'CodeView'
 "/                    #model: #codeHolder
@@ -1425,16 +1529,16 @@
 "/              #postBuildCallback: #postBuildCodeView:
 "/              #modifiedChannel: #codeModifiedHolder
 "/                  )
-                 )
-
-              )
-              #handles: #(#Any 0.3 1.0)
-              postBuildCallback: postBuildTabContentView:
-
-            )
-           )
-
-        )
+		 )
+
+	      )
+	      #handles: #(#Any 0.3 1.0)
+	      postBuildCallback: postBuildTabContentView:
+
+	    )
+	   )
+
+	)
       )
 
     "Modified: / 24-02-2000 / 23:35:03 / cg"
@@ -1457,104 +1561,104 @@
 
     ^
      #(#FullSpec
-        #name: #methodListBrowserSpec
-        #window:
+	#name: #methodListBrowserSpec
+	#window:
        #(#WindowSpec
-          #label: 'MethodListBrowser'
-          #name: 'NewBrowser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 13 23 475 323)
-        )
-        #component:
+	  #label: 'MethodListBrowser'
+	  #name: 'NewBrowser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 13 23 475 323)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #snapMode: #both
-              #handlePosition: #left
-              #showHandle: false
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#SubCanvasSpec
-                          #name: 'MethodList'
-                          #majorKey: #'MethodList'
-                          #subAspectHolders:
-                         #(#Array
-
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showCoverageInformation
-                        #aspect: #showCoverageInformation
-                      ) 
-                           #(#SubChannelInfoSpec
-                              #subAspect: #doubleClickChannel
-                              #callBack: #methodDoubleClicked
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #immediateUpdate
-                              #aspect: #immediateUpdate
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #inGeneratorHolder
-                              #aspect: #selectorListGenerator
-                            )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #menuHolder
-                              #aspect: #methodListPopUpMenu
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #packageFilter
-                              #aspect: #packageFilter
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #sortBy
-                              #aspect: #sortBy
-                            )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodInheritance
-                        #aspect: #showMethodInheritance
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodComplexity
-                        #aspect: #showMethodComplexity
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodTypeIcon
-                        #aspect: #showMethodTypeIcon
-                      )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #selectedMethods
-                              #aspect: #selectedMethods
-                              #callBack: #methodsSelectionChanged
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #selectionChangeCondition
-                              #aspect: #selectionChangeConditionHolder
-                            )
-                          )
-                          #createNewApplication: true
-                          #createNewBuilder: true
-                        )
-                 #(#SubCanvasSpec
-                    #name: 'CodePane'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NewSystemBrowser'
-                    #minorKey: #codePaneSpec
-                  )
+	  #collection: #(
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #snapMode: #both
+	      #handlePosition: #left
+	      #showHandle: false
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#SubCanvasSpec
+			  #name: 'MethodList'
+			  #majorKey: #'MethodList'
+			  #subAspectHolders:
+			 #(#Array
+
+		     #(#SubChannelInfoSpec
+			#subAspect: #showCoverageInformation
+			#aspect: #showCoverageInformation
+		      )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #doubleClickChannel
+			      #callBack: #methodDoubleClicked
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #immediateUpdate
+			      #aspect: #immediateUpdate
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #inGeneratorHolder
+			      #aspect: #selectorListGenerator
+			    )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #menuHolder
+			      #aspect: #methodListPopUpMenu
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #packageFilter
+			      #aspect: #packageFilter
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #sortBy
+			      #aspect: #sortBy
+			    )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodInheritance
+			#aspect: #showMethodInheritance
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodComplexity
+			#aspect: #showMethodComplexity
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodTypeIcon
+			#aspect: #showMethodTypeIcon
+		      )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #selectedMethods
+			      #aspect: #selectedMethods
+			      #callBack: #methodsSelectionChanged
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #selectionChangeCondition
+			      #aspect: #selectionChangeConditionHolder
+			    )
+			  )
+			  #createNewApplication: true
+			  #createNewBuilder: true
+			)
+		 #(#SubCanvasSpec
+		    #name: 'CodePane'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NewSystemBrowser'
+		    #minorKey: #codePaneSpec
+		  )
 "/                 #(#CodeViewSpec
 "/                    #name: 'CodeView'
 "/                    #model: #codeHolder
@@ -1562,16 +1666,16 @@
 "/                    #hasVerticalScrollBar: true
 "/                    #miniScrollerHorizontal: true
 "/                  )
-                 )
-
-              )
-              #handles: #(#Any 0.3 1.0)
-              postBuildCallback: postBuildTabContentView:
-
-            )
-           )
-
-        )
+		 )
+
+	      )
+	      #handles: #(#Any 0.3 1.0)
+	      postBuildCallback: postBuildTabContentView:
+
+	    )
+	   )
+
+	)
       )
 
     "Modified: / 27-04-2010 / 16:30:00 / cg"
@@ -1594,49 +1698,49 @@
 
     ^
      #(#FullSpec
-        #name: #multipleCategoryBrowserSpec
-        #window:
+	#name: #multipleCategoryBrowserSpec
+	#window:
        #(#WindowSpec
-          #label: 'CategoryBrowser'
-          #name: 'NewBrowser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 12 22 474 322)
-        )
-        #component:
+	  #label: 'CategoryBrowser'
+	  #name: 'NewBrowser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 12 22 474 322)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #showHandle: false
-              #snapMode: #both
-              #handlePosition: #left
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#SubCanvasSpec
-                    #name: 'Navigator'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NavigatorCanvas'
-                    #minorKey: #'multipleCategoryBrowserSpec'
-                  )
-                 #(#SubCanvasSpec
-                    #name: 'CodePane'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NewSystemBrowser'
-                    #minorKey: #codePaneSpec
-                  )
+	  #collection: #(
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #showHandle: false
+	      #snapMode: #both
+	      #handlePosition: #left
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#SubCanvasSpec
+		    #name: 'Navigator'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NavigatorCanvas'
+		    #minorKey: #'multipleCategoryBrowserSpec'
+		  )
+		 #(#SubCanvasSpec
+		    #name: 'CodePane'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NewSystemBrowser'
+		    #minorKey: #codePaneSpec
+		  )
 "/                 #(#CodeViewSpec
 "/                    #name: 'CodeView'
 "/                    #model: #codeHolder
@@ -1646,16 +1750,16 @@
 "/              #postBuildCallback: #postBuildCodeView:
 "/              #modifiedChannel: #codeModifiedHolder
 "/                  )
-                 )
-
-              )
-              #handles: #(#Any 0.3 1.0)
-              postBuildCallback: postBuildTabContentView:
-
-            )
-           )
-
-        )
+		 )
+
+	      )
+	      #handles: #(#Any 0.3 1.0)
+	      postBuildCallback: postBuildTabContentView:
+
+	    )
+	   )
+
+	)
       )
 
     "Modified: / 28-08-2010 / 12:00:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -1677,49 +1781,49 @@
 
     ^
      #(#FullSpec
-        #name: #multipleClassBrowserSpec
-        #window:
+	#name: #multipleClassBrowserSpec
+	#window:
        #(#WindowSpec
-          #label: 'ClassBrowser'
-          #name: 'NewBrowser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 13 23 475 323)
-        )
-        #component:
+	  #label: 'ClassBrowser'
+	  #name: 'NewBrowser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 13 23 475 323)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #showHandle: false
-              #snapMode: #both
-              #handlePosition: #left
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#SubCanvasSpec
-                    #name: 'Navigator'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NavigatorCanvas'
-                    #minorKey: #'multipleClassBrowserSpec'
-                  )
-                 #(#SubCanvasSpec
-                    #name: 'CodePane'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NewSystemBrowser'
-                    #minorKey: #codePaneSpec
-                  )
+	  #collection: #(
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #showHandle: false
+	      #snapMode: #both
+	      #handlePosition: #left
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#SubCanvasSpec
+		    #name: 'Navigator'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NavigatorCanvas'
+		    #minorKey: #'multipleClassBrowserSpec'
+		  )
+		 #(#SubCanvasSpec
+		    #name: 'CodePane'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NewSystemBrowser'
+		    #minorKey: #codePaneSpec
+		  )
 "/                 #(#CodeViewSpec
 "/                    #name: 'CodeView'
 "/                    #model: #codeHolder
@@ -1729,16 +1833,16 @@
 "/              #postBuildCallback: #postBuildCodeView:
 "/              #modifiedChannel: #codeModifiedHolder
 "/                  )
-                 )
-
-              )
-              #handles: #(#Any 0.5 1.0)
-              postBuildCallback: postBuildTabContentView:
-
-            )
-           )
-
-        )
+		 )
+
+	      )
+	      #handles: #(#Any 0.5 1.0)
+	      postBuildCallback: postBuildTabContentView:
+
+	    )
+	   )
+
+	)
       )
 
     "Modified: / 25-02-2000 / 02:08:21 / cg"
@@ -1761,49 +1865,49 @@
 
     ^
      #(#FullSpec
-        #name: #multipleClassExtensionBrowserSpec
-        #window:
+	#name: #multipleClassExtensionBrowserSpec
+	#window:
        #(#WindowSpec
-          #label: 'ClassExtensionBrowser'
-          #name: 'NewBrowser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 13 23 475 323)
-        )
-        #component:
+	  #label: 'ClassExtensionBrowser'
+	  #name: 'NewBrowser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 13 23 475 323)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #showHandle: false
-              #snapMode: #both
-              #handlePosition: #left
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#SubCanvasSpec
-                    #name: 'Navigator'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NavigatorCanvas'
-                    #minorKey: #'multipleClassExtensionBrowserSpec'
-                  )
-                 #(#SubCanvasSpec
-                    #name: 'CodePane'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NewSystemBrowser'
-                    #minorKey: #codePaneSpec
-                  )
+	  #collection: #(
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #showHandle: false
+	      #snapMode: #both
+	      #handlePosition: #left
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#SubCanvasSpec
+		    #name: 'Navigator'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NavigatorCanvas'
+		    #minorKey: #'multipleClassExtensionBrowserSpec'
+		  )
+		 #(#SubCanvasSpec
+		    #name: 'CodePane'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NewSystemBrowser'
+		    #minorKey: #codePaneSpec
+		  )
 "/                 #(#CodeViewSpec
 "/                    #name: 'CodeView'
 "/                    #model: #codeHolder
@@ -1813,16 +1917,16 @@
 "/              #postBuildCallback: #postBuildCodeView:
 "/              #modifiedChannel: #codeModifiedHolder
 "/                  )
-                 )
-
-              )
-              #handles: #(#Any 0.3 1.0)
-              postBuildCallback: postBuildTabContentView:
-
-            )
-           )
-
-        )
+		 )
+
+	      )
+	      #handles: #(#Any 0.3 1.0)
+	      postBuildCallback: postBuildTabContentView:
+
+	    )
+	   )
+
+	)
       )
 
     "Modified: / 25-02-2000 / 02:08:21 / cg"
@@ -1845,50 +1949,50 @@
 
     ^
      #(#FullSpec
-        #name: #multipleClassRepositoryDiffBrowserSpec
-        #window:
+	#name: #multipleClassRepositoryDiffBrowserSpec
+	#window:
        #(#WindowSpec
-          #label: 'ClassBrowser'
-          #name: 'ClassBrowser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 661 213 1123 513)
-        )
-        #component:
+	  #label: 'ClassBrowser'
+	  #name: 'ClassBrowser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 661 213 1123 513)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #showHandle: false
-              #snapMode: #both
-              #handlePosition: #left
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#SubCanvasSpec
-                    #name: 'Navigator'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NavigatorCanvas'
-                    #minorKey: #multipleClassDiffBrowserSpec
-                  )
-                 #(#SubCanvasSpec
-                    #name: 'DiffView'
-                    #hasHorizontalScrollBar: false
-                    #hasVerticalScrollBar: false
-                    #majorKey: #VersionDiffBrowser
-                    #minorKey: #windowSpec
-                    #createNewApplication: true
-                    #createNewBuilder: true
-                    #postBuildCallback: #versionDiffViewerCreated:
-                  )
-                 )
-
-              )
-              #handles: #(#Any 0.3 1.0)
-            )
-           )
-
-        )
+	  #collection: #(
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #showHandle: false
+	      #snapMode: #both
+	      #handlePosition: #left
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#SubCanvasSpec
+		    #name: 'Navigator'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NavigatorCanvas'
+		    #minorKey: #multipleClassDiffBrowserSpec
+		  )
+		 #(#SubCanvasSpec
+		    #name: 'DiffView'
+		    #hasHorizontalScrollBar: false
+		    #hasVerticalScrollBar: false
+		    #majorKey: #VersionDiffBrowser
+		    #minorKey: #windowSpec
+		    #createNewApplication: true
+		    #createNewBuilder: true
+		    #postBuildCallback: #versionDiffViewerCreated:
+		  )
+		 )
+
+	      )
+	      #handles: #(#Any 0.3 1.0)
+	    )
+	   )
+
+	)
       )
 !
 
@@ -1908,153 +2012,153 @@
 
     ^
      #(#FullSpec
-        #name: #multipleClassWithInfoAndMethodWithInfoBrowserSpec
-        #window:
+	#name: #multipleClassWithInfoAndMethodWithInfoBrowserSpec
+	#window:
        #(#WindowSpec
-          #label: 'MethodBrowser'
-          #name: 'MethodBrowser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 18 51 480 351)
-        )
-        #component:
+	  #label: 'MethodBrowser'
+	  #name: 'MethodBrowser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 18 51 480 351)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #showHandle: false
-              #snapMode: #both
-              #handlePosition: #left
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#SubCanvasSpec
-                    #attributes:
-                   #(#vpext
-                      #(#Point 1.0 0.243333)
-                    )
-                    #name: 'ClassList'
-                    #majorKey: #'ClassList'
-                    #subAspectHolders:
-                   #(#Array
-
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showCoverageInformation
-                        #aspect: #showCoverageInformation
-                      ) 
-                     #(#SubChannelInfoSpec
-                        #subAspect: #doubleClickChannel
-                        #callBack: #classDoubleClicked
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #immediateUpdate
-                        #aspect: #immediateUpdate
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #meta
-                        #aspect: #meta
-                      )
-
-                     #(#SubChannelInfoSpec
-                        #subAspect: #inGeneratorHolder
-                        #aspect: #classListGenerator
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #menuHolder
-                        #aspect: #classMenu
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #selectedClasses
-                        #aspect: #selectedClasses
-                        #callBack: #classSelectionChanged
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #selectionChangeCondition
-                        #aspect: #selectionChangeConditionHolder
-                      )
-                    )
-                    #createNewApplication: true
-                    #createNewBuilder: true
-                  )
-                 #(#SubCanvasSpec
-                    #attributes:
-                   #(#vpext
-                      #(#Point 1.0 0.243333)
-                    )
-                    #name: 'MethodList'
-                    #majorKey: #'MethodList'
-                    #subAspectHolders:
-                   #(#Array
-
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showCoverageInformation
-                        #aspect: #showCoverageInformation
-                      ) 
-                     #(#SubChannelInfoSpec
-                        #subAspect: #doubleClickChannel
-                        #callBack: #methodDoubleClicked
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #immediateUpdate
-                        #aspect: #immediateUpdate
-                      )
-
-                     #(#SubChannelInfoSpec
-                        #subAspect: #inGeneratorHolder
-                        #aspect: #selectorListGenerator
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #menuHolder
-                        #aspect: #methodListPopUpMenu
-                      )
-
-                     #(#SubChannelInfoSpec
-                        #subAspect: #packageFilter
-                        #aspect: #packageFilter
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #selectedMethods
-                        #aspect: #selectedMethods
-                        #callBack: #methodsSelectionChanged
-                      )
-
-                     #(#SubChannelInfoSpec
-                        #subAspect: #selectionChangeCondition
-                        #aspect: #selectionChangeConditionHolder
-                      )
-                    )
-                    #createNewApplication: true
-                    #createNewBuilder: true
-                  )
-                 #(#TextEditorSpec
-                    #attributes:
-                   #(#vpext
-                      #(#Point 1.0 0.53)
-                    )
-                    #name: 'MethodInfoView'
-                    #model: #methodInfo
-                    #hasHorizontalScrollBar: true
-                    #hasVerticalScrollBar: true
-                    #autoHideScrollBars: true
-                    #isReadOnly: true
-                  )
-                 #(#SubCanvasSpec
-                    #name: 'CodePane'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NewSystemBrowser'
-                    #minorKey: #codePaneSpec
-                  )
+	  #collection: #(
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #showHandle: false
+	      #snapMode: #both
+	      #handlePosition: #left
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#SubCanvasSpec
+		    #attributes:
+		   #(#vpext
+		      #(#Point 1.0 0.243333)
+		    )
+		    #name: 'ClassList'
+		    #majorKey: #'ClassList'
+		    #subAspectHolders:
+		   #(#Array
+
+		     #(#SubChannelInfoSpec
+			#subAspect: #showCoverageInformation
+			#aspect: #showCoverageInformation
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #doubleClickChannel
+			#callBack: #classDoubleClicked
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #immediateUpdate
+			#aspect: #immediateUpdate
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #meta
+			#aspect: #meta
+		      )
+
+		     #(#SubChannelInfoSpec
+			#subAspect: #inGeneratorHolder
+			#aspect: #classListGenerator
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #menuHolder
+			#aspect: #classMenu
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #selectedClasses
+			#aspect: #selectedClasses
+			#callBack: #classSelectionChanged
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #selectionChangeCondition
+			#aspect: #selectionChangeConditionHolder
+		      )
+		    )
+		    #createNewApplication: true
+		    #createNewBuilder: true
+		  )
+		 #(#SubCanvasSpec
+		    #attributes:
+		   #(#vpext
+		      #(#Point 1.0 0.243333)
+		    )
+		    #name: 'MethodList'
+		    #majorKey: #'MethodList'
+		    #subAspectHolders:
+		   #(#Array
+
+		     #(#SubChannelInfoSpec
+			#subAspect: #showCoverageInformation
+			#aspect: #showCoverageInformation
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #doubleClickChannel
+			#callBack: #methodDoubleClicked
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #immediateUpdate
+			#aspect: #immediateUpdate
+		      )
+
+		     #(#SubChannelInfoSpec
+			#subAspect: #inGeneratorHolder
+			#aspect: #selectorListGenerator
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #menuHolder
+			#aspect: #methodListPopUpMenu
+		      )
+
+		     #(#SubChannelInfoSpec
+			#subAspect: #packageFilter
+			#aspect: #packageFilter
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #selectedMethods
+			#aspect: #selectedMethods
+			#callBack: #methodsSelectionChanged
+		      )
+
+		     #(#SubChannelInfoSpec
+			#subAspect: #selectionChangeCondition
+			#aspect: #selectionChangeConditionHolder
+		      )
+		    )
+		    #createNewApplication: true
+		    #createNewBuilder: true
+		  )
+		 #(#TextEditorSpec
+		    #attributes:
+		   #(#vpext
+		      #(#Point 1.0 0.53)
+		    )
+		    #name: 'MethodInfoView'
+		    #model: #methodInfo
+		    #hasHorizontalScrollBar: true
+		    #hasVerticalScrollBar: true
+		    #autoHideScrollBars: true
+		    #isReadOnly: true
+		  )
+		 #(#SubCanvasSpec
+		    #name: 'CodePane'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NewSystemBrowser'
+		    #minorKey: #codePaneSpec
+		  )
 "/                 #(#CodeViewSpec
 "/                    #name: 'CodeView'
 "/                    #model: #codeHolder
@@ -2064,16 +2168,16 @@
 "/              #postBuildCallback: #postBuildCodeView:
 "/              #modifiedChannel: #codeModifiedHolder
 "/                  )
-                 )
-
-              )
-              #handles: #(#Any 0.1 0.25 0.5 1.0)
-              postBuildCallback: postBuildTabContentView:
-
-            )
-           )
-
-        )
+		 )
+
+	      )
+	      #handles: #(#Any 0.1 0.25 0.5 1.0)
+	      postBuildCallback: postBuildTabContentView:
+
+	    )
+	   )
+
+	)
       )
 
     "Modified: / 27-04-2010 / 16:30:07 / cg"
@@ -2096,99 +2200,99 @@
 
     ^
      #(#FullSpec
-        #name: #multipleClassWithInfoSpec
-        #window:
+	#name: #multipleClassWithInfoSpec
+	#window:
        #(#WindowSpec
-          #label: 'MethodBrowser'
-          #name: 'MethodBrowser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 18 51 480 351)
-        )
-        #component:
+	  #label: 'MethodBrowser'
+	  #name: 'MethodBrowser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 18 51 480 351)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #showHandle: false
-              #snapMode: #both
-              #handlePosition: #left
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#SubCanvasSpec
-                    #attributes:
-                   #(#vpext
-                      #(#Point 1.0 0.243333)
-                    )
-                    #name: 'ClassList'
-                    #majorKey: #'ClassList'
-                    #subAspectHolders:
-                   #(#Array
-
-                     #(#SubChannelInfoSpec
-                        #subAspect: #doubleClickChannel
-                        #callBack: #classDoubleClicked
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #immediateUpdate
-                        #aspect: #immediateUpdate
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #meta
-                        #aspect: #meta
-                      )
-
-                     #(#SubChannelInfoSpec
-                        #subAspect: #inGeneratorHolder
-                        #aspect: #classListGenerator
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #menuHolder
-                        #aspect: #classMenu
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #selectedClasses
-                        #aspect: #selectedClasses
-                        #callBack: #classSelectionChanged
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #selectionChangeCondition
-                        #aspect: #selectionChangeConditionHolder
-                      )
-                    )
-                    #createNewApplication: true
-                    #createNewBuilder: true
-                  )
-                 #(#TextEditorSpec
-                    #attributes:
-                   #(#vpext
-                      #(#Point 1.0 0.53)
-                    )
-                    #name: 'MethodInfoView'
-                    #model: #methodInfo
-                    #hasHorizontalScrollBar: true
-                    #hasVerticalScrollBar: true
-                    #autoHideScrollBars: true
-                    #isReadOnly: true
-                  )
-                 #(#SubCanvasSpec
-                    #name: 'CodePane'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NewSystemBrowser'
-                    #minorKey: #codePaneSpec
-                  )
+	  #collection: #(
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #showHandle: false
+	      #snapMode: #both
+	      #handlePosition: #left
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#SubCanvasSpec
+		    #attributes:
+		   #(#vpext
+		      #(#Point 1.0 0.243333)
+		    )
+		    #name: 'ClassList'
+		    #majorKey: #'ClassList'
+		    #subAspectHolders:
+		   #(#Array
+
+		     #(#SubChannelInfoSpec
+			#subAspect: #doubleClickChannel
+			#callBack: #classDoubleClicked
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #immediateUpdate
+			#aspect: #immediateUpdate
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #meta
+			#aspect: #meta
+		      )
+
+		     #(#SubChannelInfoSpec
+			#subAspect: #inGeneratorHolder
+			#aspect: #classListGenerator
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #menuHolder
+			#aspect: #classMenu
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #selectedClasses
+			#aspect: #selectedClasses
+			#callBack: #classSelectionChanged
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #selectionChangeCondition
+			#aspect: #selectionChangeConditionHolder
+		      )
+		    )
+		    #createNewApplication: true
+		    #createNewBuilder: true
+		  )
+		 #(#TextEditorSpec
+		    #attributes:
+		   #(#vpext
+		      #(#Point 1.0 0.53)
+		    )
+		    #name: 'MethodInfoView'
+		    #model: #methodInfo
+		    #hasHorizontalScrollBar: true
+		    #hasVerticalScrollBar: true
+		    #autoHideScrollBars: true
+		    #isReadOnly: true
+		  )
+		 #(#SubCanvasSpec
+		    #name: 'CodePane'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NewSystemBrowser'
+		    #minorKey: #codePaneSpec
+		  )
 "/                 #(#CodeViewSpec
 "/                    #name: 'CodeView'
 "/                    #model: #codeHolder
@@ -2198,16 +2302,16 @@
 "/              #postBuildCallback: #postBuildCodeView:
 "/              #modifiedChannel: #codeModifiedHolder
 "/                  )
-                 )
-
-              )
-              #handles: #(#Any 0.25 0.5 1.0)
-              postBuildCallback: postBuildTabContentView:
-
-            )
-           )
-
-        )
+		 )
+
+	      )
+	      #handles: #(#Any 0.25 0.5 1.0)
+	      postBuildCallback: postBuildTabContentView:
+
+	    )
+	   )
+
+	)
       )
 
     "Modified: / 28-08-2010 / 12:00:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -2229,49 +2333,49 @@
 
     ^
      #(#FullSpec
-        #name: #multipleFullProtocolBrowserSpec
-        #window:
+	#name: #multipleFullProtocolBrowserSpec
+	#window:
        #(#WindowSpec
-          #label: 'ProtocolBrowser'
-          #name: 'NewBrowser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 12 22 474 322)
-        )
-        #component:
+	  #label: 'ProtocolBrowser'
+	  #name: 'NewBrowser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 12 22 474 322)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #showHandle: false
-              #snapMode: #both
-              #handlePosition: #left
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#SubCanvasSpec
-                    #name: 'Navigator'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NavigatorCanvas'
-                    #minorKey: #'multipleFullProtocolBrowserSpec'
-                  )
-                 #(#SubCanvasSpec
-                    #name: 'CodePane'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NewSystemBrowser'
-                    #minorKey: #codePaneSpec
-                  )
+	  #collection: #(
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #showHandle: false
+	      #snapMode: #both
+	      #handlePosition: #left
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#SubCanvasSpec
+		    #name: 'Navigator'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NavigatorCanvas'
+		    #minorKey: #'multipleFullProtocolBrowserSpec'
+		  )
+		 #(#SubCanvasSpec
+		    #name: 'CodePane'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NewSystemBrowser'
+		    #minorKey: #codePaneSpec
+		  )
 "/                 #(#CodeViewSpec
 "/                    #name: 'CodeView'
 "/                    #model: #codeHolder
@@ -2281,16 +2385,16 @@
 "/              #postBuildCallback: #postBuildCodeView:
 "/              #modifiedChannel: #codeModifiedHolder
 "/                  )
-                 )
-
-              )
-              #handles: #(#Any 0.3 1.0)
-              postBuildCallback: postBuildTabContentView:
-
-            )
-           )
-
-        )
+		 )
+
+	      )
+	      #handles: #(#Any 0.3 1.0)
+	      postBuildCallback: postBuildTabContentView:
+
+	    )
+	   )
+
+	)
       )
 
     "Modified: / 01-03-2000 / 20:45:30 / cg"
@@ -2313,109 +2417,109 @@
 
     ^
      #(#FullSpec
-        #name: #multipleMethodBrowserSpec
-        #window:
+	#name: #multipleMethodBrowserSpec
+	#window:
        #(#WindowSpec
-          #label: 'MethodBrowser'
-          #name: 'NewBrowser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 13 23 475 323)
-        )
-        #component:
+	  #label: 'MethodBrowser'
+	  #name: 'NewBrowser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 13 23 475 323)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #showHandle: false
-              #snapMode: #both
-              #handlePosition: #left
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#SubCanvasSpec
-                          #name: 'MethodList'
-                          #majorKey: #'MethodList'
-                          #subAspectHolders:
-                         #(#Array
-
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showCoverageInformation
-                        #aspect: #showCoverageInformation
-                      ) 
-                           #(#SubChannelInfoSpec
-                              #subAspect: #doubleClickChannel
-                              #callBack: #methodDoubleClicked
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #immediateUpdate
-                              #aspect: #immediateUpdate
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #inGeneratorHolder
-                              #aspect: #selectorListGenerator
-                            )
-
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodInheritance
-                        #aspect: #showMethodInheritance
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodComplexity
-                        #aspect: #showMethodComplexity
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodTypeIcon
-                        #aspect: #showMethodTypeIcon
-                      )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #menuHolder
-                              #aspect: #selectorPopUpMenu
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #packageFilter
-                              #aspect: #packageFilter
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #variableFilter
-                              #aspect: #variableFilter
-                            )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #selectedMethods
-                              #aspect: #selectedMethods
-                              #callBack: #methodsSelectionChanged
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #sortBy
-                              #aspect: #sortBy
-                            )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #selectionChangeCondition
-                              #aspect: #selectionChangeConditionHolder
-                            )
-                          )
-                          #createNewApplication: true
-                          #createNewBuilder: true
-                        )
-                 #(#SubCanvasSpec
-                    #name: 'CodePane'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NewSystemBrowser'
-                    #minorKey: #codePaneSpec
-                  )
+	  #collection: #(
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #showHandle: false
+	      #snapMode: #both
+	      #handlePosition: #left
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#SubCanvasSpec
+			  #name: 'MethodList'
+			  #majorKey: #'MethodList'
+			  #subAspectHolders:
+			 #(#Array
+
+		     #(#SubChannelInfoSpec
+			#subAspect: #showCoverageInformation
+			#aspect: #showCoverageInformation
+		      )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #doubleClickChannel
+			      #callBack: #methodDoubleClicked
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #immediateUpdate
+			      #aspect: #immediateUpdate
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #inGeneratorHolder
+			      #aspect: #selectorListGenerator
+			    )
+
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodInheritance
+			#aspect: #showMethodInheritance
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodComplexity
+			#aspect: #showMethodComplexity
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodTypeIcon
+			#aspect: #showMethodTypeIcon
+		      )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #menuHolder
+			      #aspect: #selectorPopUpMenu
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #packageFilter
+			      #aspect: #packageFilter
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #variableFilter
+			      #aspect: #variableFilter
+			    )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #selectedMethods
+			      #aspect: #selectedMethods
+			      #callBack: #methodsSelectionChanged
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #sortBy
+			      #aspect: #sortBy
+			    )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #selectionChangeCondition
+			      #aspect: #selectionChangeConditionHolder
+			    )
+			  )
+			  #createNewApplication: true
+			  #createNewBuilder: true
+			)
+		 #(#SubCanvasSpec
+		    #name: 'CodePane'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NewSystemBrowser'
+		    #minorKey: #codePaneSpec
+		  )
 "/                 #(#CodeViewSpec
 "/                    #name: 'CodeView'
 "/                    #model: #codeHolder
@@ -2425,16 +2529,16 @@
 "/              #postBuildCallback: #postBuildCodeView:
 "/              #modifiedChannel: #codeModifiedHolder
 "/                  )
-                 )
-
-              )
-              #handles: #(#Any 0.3 1.0)
-              postBuildCallback: postBuildTabContentView:
-
-            )
-           )
-
-        )
+		 )
+
+	      )
+	      #handles: #(#Any 0.3 1.0)
+	      postBuildCallback: postBuildTabContentView:
+
+	    )
+	   )
+
+	)
       )
 
     "Modified: / 27-04-2010 / 16:30:12 / cg"
@@ -2457,117 +2561,117 @@
 
     ^
      #(#FullSpec
-        #name: #multipleMethodWithInfoBrowserSpec
-        #window:
+	#name: #multipleMethodWithInfoBrowserSpec
+	#window:
        #(#WindowSpec
-          #label: 'MethodBrowser'
-          #name: 'MethodBrowser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 18 51 480 351)
-        )
-        #component:
+	  #label: 'MethodBrowser'
+	  #name: 'MethodBrowser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 18 51 480 351)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #showHandle: false
-              #snapMode: #both
-              #handlePosition: #left
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#SubCanvasSpec
-                    #attributes:
-                   #(#vpext
-                      #(#Point 1.0 0.243333)
-                    )
-                    #name: 'MethodList'
-                    #majorKey: #'MethodList'
-                    #subAspectHolders:
-                   #(#Array
-
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showCoverageInformation
-                        #aspect: #showCoverageInformation
-                      ) 
-                     #(#SubChannelInfoSpec
-                        #subAspect: #doubleClickChannel
-                        #callBack: #methodDoubleClicked
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #immediateUpdate
-                        #aspect: #immediateUpdate
-                      )
-
-                     #(#SubChannelInfoSpec
-                        #subAspect: #inGeneratorHolder
-                        #aspect: #selectorListGenerator
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #menuHolder
-                        #aspect: #methodListPopUpMenu
-                      )
-
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodInheritance
-                        #aspect: #showMethodInheritance
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodComplexity
-                        #aspect: #showMethodComplexity
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodTypeIcon
-                        #aspect: #showMethodTypeIcon
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #packageFilter
-                        #aspect: #packageFilter
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #selectedMethods
-                        #aspect: #selectedMethods
-                        #callBack: #methodsSelectionChanged
-                      )
-
-                     #(#SubChannelInfoSpec
-                        #subAspect: #selectionChangeCondition
-                        #aspect: #selectionChangeConditionHolder
-                      )
-                    )
-                    #createNewApplication: true
-                    #createNewBuilder: true
-                  )
-                 #(#TextEditorSpec
-                    #attributes:
-                   #(#vpext
-                      #(#Point 1.0 0.53)
-                    )
-                    #name: 'MethodInfoView'
-                    #model: #methodInfo
-                    #hasHorizontalScrollBar: true
-                    #hasVerticalScrollBar: true
-                    #autoHideScrollBars: true
-                    #isReadOnly: true
-                  )
-                 #(#SubCanvasSpec
-                    #name: 'CodePane'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NewSystemBrowser'
-                    #minorKey: #codePaneSpec
-                  )
+	  #collection: #(
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #showHandle: false
+	      #snapMode: #both
+	      #handlePosition: #left
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#SubCanvasSpec
+		    #attributes:
+		   #(#vpext
+		      #(#Point 1.0 0.243333)
+		    )
+		    #name: 'MethodList'
+		    #majorKey: #'MethodList'
+		    #subAspectHolders:
+		   #(#Array
+
+		     #(#SubChannelInfoSpec
+			#subAspect: #showCoverageInformation
+			#aspect: #showCoverageInformation
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #doubleClickChannel
+			#callBack: #methodDoubleClicked
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #immediateUpdate
+			#aspect: #immediateUpdate
+		      )
+
+		     #(#SubChannelInfoSpec
+			#subAspect: #inGeneratorHolder
+			#aspect: #selectorListGenerator
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #menuHolder
+			#aspect: #methodListPopUpMenu
+		      )
+
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodInheritance
+			#aspect: #showMethodInheritance
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodComplexity
+			#aspect: #showMethodComplexity
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodTypeIcon
+			#aspect: #showMethodTypeIcon
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #packageFilter
+			#aspect: #packageFilter
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #selectedMethods
+			#aspect: #selectedMethods
+			#callBack: #methodsSelectionChanged
+		      )
+
+		     #(#SubChannelInfoSpec
+			#subAspect: #selectionChangeCondition
+			#aspect: #selectionChangeConditionHolder
+		      )
+		    )
+		    #createNewApplication: true
+		    #createNewBuilder: true
+		  )
+		 #(#TextEditorSpec
+		    #attributes:
+		   #(#vpext
+		      #(#Point 1.0 0.53)
+		    )
+		    #name: 'MethodInfoView'
+		    #model: #methodInfo
+		    #hasHorizontalScrollBar: true
+		    #hasVerticalScrollBar: true
+		    #autoHideScrollBars: true
+		    #isReadOnly: true
+		  )
+		 #(#SubCanvasSpec
+		    #name: 'CodePane'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NewSystemBrowser'
+		    #minorKey: #codePaneSpec
+		  )
 "/                 #(#CodeViewSpec
 "/                    #name: 'CodeView'
 "/                    #model: #codeHolder
@@ -2577,16 +2681,16 @@
 "/              #postBuildCallback: #postBuildCodeView:
 "/              #modifiedChannel: #codeModifiedHolder
 "/                  )
-                 )
-
-              )
-              #handles: #(#Any 0.25 0.5 1.0)
-              postBuildCallback: postBuildTabContentView:
-
-            )
-           )
-
-        )
+		 )
+
+	      )
+	      #handles: #(#Any 0.25 0.5 1.0)
+	      postBuildCallback: postBuildTabContentView:
+
+	    )
+	   )
+
+	)
       )
 
     "Modified: / 27-04-2010 / 16:30:16 / cg"
@@ -2609,49 +2713,49 @@
 
     ^
      #(#FullSpec
-        #name: #multipleNameSpaceBrowserSpec
-        #window:
+	#name: #multipleNameSpaceBrowserSpec
+	#window:
        #(#WindowSpec
-          #label: 'NameSpaceBrowser'
-          #name: 'NewBrowser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 12 22 474 322)
-        )
-        #component:
+	  #label: 'NameSpaceBrowser'
+	  #name: 'NewBrowser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 12 22 474 322)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #showHandle: false
-              #snapMode: #both
-              #handlePosition: #left
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#SubCanvasSpec
-                    #name: 'Navigator'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NavigatorCanvas'
-                    #minorKey: #'multipleNameSpaceBrowserSpec'
-                  )
-                 #(#SubCanvasSpec
-                    #name: 'CodePane'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NewSystemBrowser'
-                    #minorKey: #codePaneSpec
-                  )
+	  #collection: #(
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #showHandle: false
+	      #snapMode: #both
+	      #handlePosition: #left
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#SubCanvasSpec
+		    #name: 'Navigator'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NavigatorCanvas'
+		    #minorKey: #'multipleNameSpaceBrowserSpec'
+		  )
+		 #(#SubCanvasSpec
+		    #name: 'CodePane'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NewSystemBrowser'
+		    #minorKey: #codePaneSpec
+		  )
 "/                 #(#CodeViewSpec
 "/                    #name: 'CodeView'
 "/                    #model: #codeHolder
@@ -2661,16 +2765,16 @@
 "/              #postBuildCallback: #postBuildCodeView:
 "/              #modifiedChannel: #codeModifiedHolder
 "/                  )
-                 )
-
-              )
-              #handles: #(#Any 0.3 1.0)
-              postBuildCallback: postBuildTabContentView:
-
-            )
-           )
-
-        )
+		 )
+
+	      )
+	      #handles: #(#Any 0.3 1.0)
+	      postBuildCallback: postBuildTabContentView:
+
+	    )
+	   )
+
+	)
       )
 
     "Modified: / 18-08-2000 / 15:01:15 / cg"
@@ -2693,49 +2797,49 @@
 
     ^
      #(#FullSpec
-        #name: #multipleNameSpaceBrowserSpec
-        #window:
+	#name: #multipleNameSpaceBrowserSpec
+	#window:
        #(#WindowSpec
-          #label: 'NameSpaceBrowser'
-          #name: 'NewBrowser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 12 22 474 322)
-        )
-        #component:
+	  #label: 'NameSpaceBrowser'
+	  #name: 'NewBrowser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 12 22 474 322)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #showHandle: false
-              #snapMode: #both
-              #handlePosition: #left
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#SubCanvasSpec
-                    #name: 'Navigator'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NavigatorCanvas'
-                    #minorKey: #'multipleNameSpaceFullBrowserSpec'
-                  )
-                 #(#SubCanvasSpec
-                    #name: 'CodePane'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NewSystemBrowser'
-                    #minorKey: #codePaneSpec
-                  )
+	  #collection: #(
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #showHandle: false
+	      #snapMode: #both
+	      #handlePosition: #left
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#SubCanvasSpec
+		    #name: 'Navigator'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NavigatorCanvas'
+		    #minorKey: #'multipleNameSpaceFullBrowserSpec'
+		  )
+		 #(#SubCanvasSpec
+		    #name: 'CodePane'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NewSystemBrowser'
+		    #minorKey: #codePaneSpec
+		  )
 "/                 #(#CodeViewSpec
 "/                    #name: 'CodeView'
 "/                    #model: #codeHolder
@@ -2745,16 +2849,16 @@
 "/              #postBuildCallback: #postBuildCodeView:
 "/              #modifiedChannel: #codeModifiedHolder
 "/                  )
-                 )
-
-              )
-              #handles: #(#Any 0.3 1.0)
-              postBuildCallback: postBuildTabContentView:
-
-            )
-           )
-
-        )
+		 )
+
+	      )
+	      #handles: #(#Any 0.3 1.0)
+	      postBuildCallback: postBuildTabContentView:
+
+	    )
+	   )
+
+	)
       )
 
     "Created: / 18-08-2000 / 15:01:00 / cg"
@@ -2777,49 +2881,49 @@
 
     ^
      #(#FullSpec
-        #name: #multipleProjectBrowserSpec
-        #window:
+	#name: #multipleProjectBrowserSpec
+	#window:
        #(#WindowSpec
-          #label: 'ProjectBrowser'
-          #name: 'NewBrowser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 12 22 474 322)
-        )
-        #component:
+	  #label: 'ProjectBrowser'
+	  #name: 'NewBrowser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 12 22 474 322)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #showHandle: false
-              #snapMode: #both
-              #handlePosition: #left
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#SubCanvasSpec
-                    #name: 'Navigator'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NavigatorCanvas'
-                    #minorKey: #'multipleProjectBrowserSpec'
-                  )
-                 #(#SubCanvasSpec
-                    #name: 'CodePane'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NewSystemBrowser'
-                    #minorKey: #codePaneSpec
-                  )
+	  #collection: #(
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #showHandle: false
+	      #snapMode: #both
+	      #handlePosition: #left
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#SubCanvasSpec
+		    #name: 'Navigator'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NavigatorCanvas'
+		    #minorKey: #'multipleProjectBrowserSpec'
+		  )
+		 #(#SubCanvasSpec
+		    #name: 'CodePane'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NewSystemBrowser'
+		    #minorKey: #codePaneSpec
+		  )
 "/                 #(#CodeViewSpec
 "/                    #name: 'CodeView'
 "/                    #model: #codeHolder
@@ -2829,16 +2933,16 @@
 "/              #postBuildCallback: #postBuildCodeView:
 "/              #modifiedChannel: #codeModifiedHolder
 "/                  )
-                 )
-
-              )
-              #handles: #(#Any 0.3 1.0)
-              postBuildCallback: postBuildTabContentView:
-
-            )
-           )
-
-        )
+		 )
+
+	      )
+	      #handles: #(#Any 0.3 1.0)
+	      postBuildCallback: postBuildTabContentView:
+
+	    )
+	   )
+
+	)
       )
 
     "Modified: / 28-08-2010 / 12:01:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -2860,49 +2964,49 @@
 
     ^
      #(#FullSpec
-        #name: #multipleProjectFullBrowserSpec
-        #window:
+	#name: #multipleProjectFullBrowserSpec
+	#window:
        #(#WindowSpec
-          #label: 'ProjectBrowser'
-          #name: 'NewBrowser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 12 22 474 322)
-        )
-        #component:
+	  #label: 'ProjectBrowser'
+	  #name: 'NewBrowser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 12 22 474 322)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #showHandle: false
-              #snapMode: #both
-              #handlePosition: #left
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#SubCanvasSpec
-                    #name: 'Navigator'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NavigatorCanvas'
-                    #minorKey: #'multipleProjectFullBrowserSpec'
-                  )
-                 #(#SubCanvasSpec
-                    #name: 'CodePane'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NewSystemBrowser'
-                    #minorKey: #codePaneSpec
-                  )
+	  #collection: #(
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #showHandle: false
+	      #snapMode: #both
+	      #handlePosition: #left
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#SubCanvasSpec
+		    #name: 'Navigator'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NavigatorCanvas'
+		    #minorKey: #'multipleProjectFullBrowserSpec'
+		  )
+		 #(#SubCanvasSpec
+		    #name: 'CodePane'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NewSystemBrowser'
+		    #minorKey: #codePaneSpec
+		  )
 "/                 #(#CodeViewSpec
 "/                    #name: 'CodeView'
 "/                    #model: #codeHolder
@@ -2912,16 +3016,16 @@
 "/              #postBuildCallback: #postBuildCodeView:
 "/              #modifiedChannel: #codeModifiedHolder
 "/                  )
-                 )
-
-              )
-              #handles: #(#Any 0.3 1.0)
-              postBuildCallback: postBuildTabContentView:
-
-            )
-           )
-
-        )
+		 )
+
+	      )
+	      #handles: #(#Any 0.3 1.0)
+	      postBuildCallback: postBuildTabContentView:
+
+	    )
+	   )
+
+	)
       )
 
     "Created: / 18-08-2000 / 18:42:38 / cg"
@@ -2944,49 +3048,49 @@
 
     ^
      #(#FullSpec
-        #name: #multipleProtocolBrowserSpec
-        #window:
+	#name: #multipleProtocolBrowserSpec
+	#window:
        #(#WindowSpec
-          #label: 'ProtocolBrowser'
-          #name: 'NewBrowser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 12 22 474 322)
-        )
-        #component:
+	  #label: 'ProtocolBrowser'
+	  #name: 'NewBrowser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 12 22 474 322)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #showHandle: false
-              #snapMode: #both
-              #handlePosition: #left
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#SubCanvasSpec
-                    #name: 'Navigator'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NavigatorCanvas'
-                    #minorKey: #'multipleProtocolBrowserSpec'
-                  )
-                 #(#SubCanvasSpec
-                    #name: 'CodePane'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NewSystemBrowser'
-                    #minorKey: #codePaneSpec
-                  )
+	  #collection: #(
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #showHandle: false
+	      #snapMode: #both
+	      #handlePosition: #left
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#SubCanvasSpec
+		    #name: 'Navigator'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NavigatorCanvas'
+		    #minorKey: #'multipleProtocolBrowserSpec'
+		  )
+		 #(#SubCanvasSpec
+		    #name: 'CodePane'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NewSystemBrowser'
+		    #minorKey: #codePaneSpec
+		  )
 "/                 #(#CodeViewSpec
 "/                    #name: 'CodeView'
 "/                    #model: #codeHolder
@@ -2996,16 +3100,16 @@
 "/              #postBuildCallback: #postBuildCodeView:
 "/              #modifiedChannel: #codeModifiedHolder
 "/                  )
-                 )
-
-              )
-              #handles: #(#Any 0.3 1.0)
-              postBuildCallback: postBuildTabContentView:
-
-            )
-           )
-
-        )
+		 )
+
+	      )
+	      #handles: #(#Any 0.3 1.0)
+	      postBuildCallback: postBuildTabContentView:
+
+	    )
+	   )
+
+	)
       )
 
     "Modified: / 01-03-2000 / 20:45:30 / cg"
@@ -3026,118 +3130,118 @@
 
     <resource: #canvas>
 
-    ^ 
+    ^
      #(FullSpec
-        name: noteBookWindowSpec
-        window: 
+	name: noteBookWindowSpec
+	window:
        (WindowSpec
-          label: 'NewSystemBrowser'
-          name: 'NewSystemBrowser'
-          min: (Point 0 0)
-          bounds: (Rectangle 0 0 800 700)
-          menu: mainMenu
-          icon: defaultIcon
-        )
-        component: 
+	  label: 'NewSystemBrowser'
+	  name: 'NewSystemBrowser'
+	  min: (Point 0 0)
+	  bounds: (Rectangle 0 0 800 700)
+	  menu: mainMenu
+	  icon: defaultIcon
+	)
+	component:
        (SpecCollection
-          collection: (
-           (NoteBookViewSpec
-              name: 'NoteBook'
-              layout: (LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              level: 0
-              model: selectedBuffer
-              menu: bufferNameList
-              useIndex: true
-              valueChangeSelector: bufferSelectionChanged
-              accessTabMenuAction: tabMenu:
-              hasScrollButtons: true
-              destroyTabAction: destroyTab:
-              canvas: browserCanvas
-              canvasInset: 0
-              keepCanvasAlive: true
-              tabLevel: 1
-            )
-           (ViewSpec
-              name: 'ToolBar'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              visibilityChannel: toolBarVisibleHolder
-              component: 
-             (SpecCollection
-                collection: (
-                 (ActionButtonSpec
-                    label: 'hideToolBarIcon'
-                    name: 'HideToolBarButton'
-                    layout: (LayoutFrame 0 0 0 0 13 0 0 1)
-                    activeHelpKey: hideToolBar
-                    hasCharacterOrientedLabel: false
-                    translateLabel: true
-                    model: hideToolbar
-                    postBuildCallback: hideToolBarButtonCreated:
-                  )
-                 (MenuPanelSpec
-                    name: 'ToolBarMenu'
-                    layout: (LayoutFrame 13 0.0 0 0.0 -250 1.0 0 1.0)
-                    visibilityChannel: toolBarVisibleHolder
-                    menu: toolBarMenu
-                    textDefault: true
-                  )
-                 (UISubSpecification
-                    name: 'SubSpecification1'
-                    layout: (LayoutFrame -250 1 0 0 0 1 0 1)
-                    minorKey: searchSpec
-                  )
-                 )
-               
-              )
-            )
-           (ViewSpec
-              name: 'BookmarkBar'
-              layout: (LayoutFrame 0 0 40 0 0 1 67 0)
-              level: 1
-              visibilityChannel: bookmarkBarVisibleHolder
-              component: 
-             (SpecCollection
-                collection: (
-                 (ActionButtonSpec
-                    label: 'hideToolBarIcon'
-                    name: 'Button1'
-                    layout: (LayoutFrame 0 0 0 0 12 0 0 1)
-                    activeHelpKey: hideToolBar
-                    hasCharacterOrientedLabel: false
-                    translateLabel: true
-                    model: hideBookmarkBar
-                    postBuildCallback: hideToolBarButtonCreated:
-                  )
-                 (SubCanvasSpec
-                    name: 'Bookmarks'
-                    layout: (LayoutFrame 13 0 2 0 0 1 -1 1)
-                    level: 0
-                    hasHorizontalScrollBar: false
-                    hasVerticalScrollBar: false
-                    miniScrollerHorizontal: false
-                    majorKey: BookmarkBar
-                    subAspectHolders: 
-                   (Array
-                      
-                     (SubChannelInfoSpec
-                        subAspect: bookmarkHolder
-                        aspect: bookmarkHolder
-                      ) 
-                     (SubChannelInfoSpec
-                        subAspect: bookmarksHolder
-                        aspect: bookmarkListHolder
-                      )
-                    )
-                    createNewApplication: true
-                    createNewBuilder: true
-                  )
-                 )
-               
-              )
-            )
-           )
-         
-        )
+	  collection: (
+	   (NoteBookViewSpec
+	      name: 'NoteBook'
+	      layout: (LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      level: 0
+	      model: selectedBuffer
+	      menu: bufferNameList
+	      useIndex: true
+	      valueChangeSelector: bufferSelectionChanged
+	      accessTabMenuAction: tabMenu:
+	      hasScrollButtons: true
+	      destroyTabAction: destroyTab:
+	      canvas: browserCanvas
+	      canvasInset: 0
+	      keepCanvasAlive: true
+	      tabLevel: 1
+	    )
+	   (ViewSpec
+	      name: 'ToolBar'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      visibilityChannel: toolBarVisibleHolder
+	      component:
+	     (SpecCollection
+		collection: (
+		 (ActionButtonSpec
+		    label: 'hideToolBarIcon'
+		    name: 'HideToolBarButton'
+		    layout: (LayoutFrame 0 0 0 0 13 0 0 1)
+		    activeHelpKey: hideToolBar
+		    hasCharacterOrientedLabel: false
+		    translateLabel: true
+		    model: hideToolbar
+		    postBuildCallback: hideToolBarButtonCreated:
+		  )
+		 (MenuPanelSpec
+		    name: 'ToolBarMenu'
+		    layout: (LayoutFrame 13 0.0 0 0.0 -250 1.0 0 1.0)
+		    visibilityChannel: toolBarVisibleHolder
+		    menu: toolBarMenu
+		    textDefault: true
+		  )
+		 (UISubSpecification
+		    name: 'SubSpecification1'
+		    layout: (LayoutFrame -250 1 0 0 0 1 0 1)
+		    minorKey: searchSpec
+		  )
+		 )
+
+	      )
+	    )
+	   (ViewSpec
+	      name: 'BookmarkBar'
+	      layout: (LayoutFrame 0 0 40 0 0 1 67 0)
+	      level: 1
+	      visibilityChannel: bookmarkBarVisibleHolder
+	      component:
+	     (SpecCollection
+		collection: (
+		 (ActionButtonSpec
+		    label: 'hideToolBarIcon'
+		    name: 'Button1'
+		    layout: (LayoutFrame 0 0 0 0 12 0 0 1)
+		    activeHelpKey: hideToolBar
+		    hasCharacterOrientedLabel: false
+		    translateLabel: true
+		    model: hideBookmarkBar
+		    postBuildCallback: hideToolBarButtonCreated:
+		  )
+		 (SubCanvasSpec
+		    name: 'Bookmarks'
+		    layout: (LayoutFrame 13 0 2 0 0 1 -1 1)
+		    level: 0
+		    hasHorizontalScrollBar: false
+		    hasVerticalScrollBar: false
+		    miniScrollerHorizontal: false
+		    majorKey: BookmarkBar
+		    subAspectHolders:
+		   (Array
+
+		     (SubChannelInfoSpec
+			subAspect: bookmarkHolder
+			aspect: bookmarkHolder
+		      )
+		     (SubChannelInfoSpec
+			subAspect: bookmarksHolder
+			aspect: bookmarkListHolder
+		      )
+		    )
+		    createNewApplication: true
+		    createNewBuilder: true
+		  )
+		 )
+
+	      )
+	    )
+	   )
+
+	)
       )
 !
 
@@ -3150,7 +3254,7 @@
     "
      UIPainter new openOnClass:Tools::NewSystemBrowser andSelector:#webBrowserLayoutWindowSpec
      Tools::NewSystemBrowser new openInterface:#webBrowserLayoutWindowSpec"
-    
+
     ^ #( #FullSpec
   #name: #pagedWindowSpec
   #window:
@@ -3173,183 +3277,183 @@
 
     <resource: #canvas>
 
-    ^ 
+    ^
      #(FullSpec
-        name: #'protocolAndMethodListSpec_Both'
-        window: 
+	name: #'protocolAndMethodListSpec_Both'
+	window:
        (WindowSpec
-          label: 'Protocol and Method List'
-          name: 'Protocol and Method List'
-          min: (Point 0 0)
-          bounds: (Rectangle 0 0 498 456)
-          icon: defaultIcon
-        )
-        component: 
+	  label: 'Protocol and Method List'
+	  name: 'Protocol and Method List'
+	  min: (Point 0 0)
+	  bounds: (Rectangle 0 0 498 456)
+	  icon: defaultIcon
+	)
+	component:
        (SpecCollection
-          collection: (
-           (VariableHorizontalPanelSpec
-              name: 'Lists'
-              layout: (LayoutFrame 0 0 0 0 0 1 0 1)
-              barWidth: 2
-              showHandle: false
-              component: 
-             (SpecCollection
-                collection: (
-                 (SubCanvasSpec
-                    name: 'MethodCategoryList'
-                    majorKey: MethodCategoryList
-                    subAspectHolders: 
-                   (Array
-                      
-                     (SubChannelInfoSpec
-                        subAspect: showCoverageInformation
-                        aspect: showCoverageInformation
-                      ) 
-                     (SubChannelInfoSpec
-                        subAspect: showPseudoProtocols
-                        aspect: showPseudoProtocols
-                      )
-                      
-                     (SubChannelInfoSpec
-                        subAspect: immediateUpdate
-                        aspect: immediateUpdate
-                      ) 
-                     (SubChannelInfoSpec
-                        subAspect: inGeneratorHolder
-                        aspect: protocolListGenerator
-                      )
-                      
-                     (SubChannelInfoSpec
-                        subAspect: doubleClickChannel
-                        callBack: protocolDoubleClicked
-                      ) 
-                     (SubChannelInfoSpec
-                        subAspect: menuHolder
-                        aspect: protocolMenu
-                      )
-                      
-                     (SubChannelInfoSpec
-                        subAspect: outGeneratorHolder
-                        aspect: selectorListGenerator
-                      ) 
-                     (SubChannelInfoSpec
-                        subAspect: packageFilter
-                        aspect: packageFilter
-                      )
-                      
-                     (SubChannelInfoSpec
-                        subAspect: selectedProtocols
-                        aspect: selectedProtocols
-                        callBack: protocolSelectionChanged
-                      ) 
-                     (SubChannelInfoSpec
-                        subAspect: selectionChangeCondition
-                        aspect: selectionChangeConditionHolder
-                      )
-                      
-                     (SubChannelInfoSpec
-                        subAspect: variableFilter
-                        aspect: variableFilter
-                        callBack: variableSelectionChanged
-                      ) 
-                     (SubChannelInfoSpec
-                        subAspect: filterClassVars
-                        aspect: filterClassVars
-                      )
-                      
-                     (SubChannelInfoSpec
-                        subAspect: methodVisibilityHolder
-                        aspect: methodVisibilityHolder
-                      )
-                    )
-                    createNewApplication: true
-                    createNewBuilder: true
-                    postBuildCallback: methodCategoryList:
-                  )
-                 (SubCanvasSpec
-                    name: 'MethodList'
-                    majorKey: MethodList
-                    subAspectHolders: 
-                   (Array
-                      
-                     (SubChannelInfoSpec
-                        subAspect: showCoverageInformation
-                        aspect: showCoverageInformation
-                      ) 
-                     (SubChannelInfoSpec
-                        subAspect: doubleClickChannel
-                        callBack: methodDoubleClicked
-                      )
-                      
-                     (SubChannelInfoSpec
-                        subAspect: immediateUpdate
-                        aspect: immediateUpdate
-                      ) 
-                     (SubChannelInfoSpec
-                        subAspect: inGeneratorHolder
-                        aspect: selectorListGenerator
-                      )
-                      
-                     (SubChannelInfoSpec
-                        subAspect: menuHolder
-                        aspect: selectorPopUpMenu
-                      ) 
-                     (SubChannelInfoSpec
-                        subAspect: packageFilter
-                        aspect: packageFilter
-                      )
-                      
-                     (SubChannelInfoSpec
-                        subAspect: selectedMethods
-                        aspect: selectedMethods
-                        callBack: methodsSelectionChanged
-                      ) 
-                     (SubChannelInfoSpec
-                        subAspect: selectionChangeCondition
-                        aspect: selectionChangeConditionHolder
-                      )
-                      
-                     (SubChannelInfoSpec
-                        subAspect: variableFilter
-                        aspect: variableFilter
-                        callBack: variableSelectionChanged
-                      ) 
-                     (SubChannelInfoSpec
-                        subAspect: showMethodInheritance
-                        aspect: showMethodInheritance
-                      )
-                      
-                     (SubChannelInfoSpec
-                        subAspect: showMethodComplexity
-                        aspect: showMethodComplexity
-                      ) 
-                     (SubChannelInfoSpec
-                        subAspect: showMethodTypeIcon
-                        aspect: showMethodTypeIcon
-                      )
-                     (SubChannelInfoSpec
-                        subAspect: showSyntheticMethods
-                        aspect: showSyntheticMethods
-                      )
-
-
-                     (SubChannelInfoSpec
-                        subAspect: filterClassVars
-                        aspect: filterClassVars
-                      )
-                    )
-                    createNewApplication: true
-                    createNewBuilder: true
-                    postBuildCallback: methodList:
-                  )
-                 )
-               
-              )
-              handles: (Any 0.5 1.0)
-            )
-           )
-         
-        )
+	  collection: (
+	   (VariableHorizontalPanelSpec
+	      name: 'Lists'
+	      layout: (LayoutFrame 0 0 0 0 0 1 0 1)
+	      barWidth: 2
+	      showHandle: false
+	      component:
+	     (SpecCollection
+		collection: (
+		 (SubCanvasSpec
+		    name: 'MethodCategoryList'
+		    majorKey: MethodCategoryList
+		    subAspectHolders:
+		   (Array
+
+		     (SubChannelInfoSpec
+			subAspect: showCoverageInformation
+			aspect: showCoverageInformation
+		      )
+		     (SubChannelInfoSpec
+			subAspect: showPseudoProtocols
+			aspect: showPseudoProtocols
+		      )
+
+		     (SubChannelInfoSpec
+			subAspect: immediateUpdate
+			aspect: immediateUpdate
+		      )
+		     (SubChannelInfoSpec
+			subAspect: inGeneratorHolder
+			aspect: protocolListGenerator
+		      )
+
+		     (SubChannelInfoSpec
+			subAspect: doubleClickChannel
+			callBack: protocolDoubleClicked
+		      )
+		     (SubChannelInfoSpec
+			subAspect: menuHolder
+			aspect: protocolMenu
+		      )
+
+		     (SubChannelInfoSpec
+			subAspect: outGeneratorHolder
+			aspect: selectorListGenerator
+		      )
+		     (SubChannelInfoSpec
+			subAspect: packageFilter
+			aspect: packageFilter
+		      )
+
+		     (SubChannelInfoSpec
+			subAspect: selectedProtocols
+			aspect: selectedProtocols
+			callBack: protocolSelectionChanged
+		      )
+		     (SubChannelInfoSpec
+			subAspect: selectionChangeCondition
+			aspect: selectionChangeConditionHolder
+		      )
+
+		     (SubChannelInfoSpec
+			subAspect: variableFilter
+			aspect: variableFilter
+			callBack: variableSelectionChanged
+		      )
+		     (SubChannelInfoSpec
+			subAspect: filterClassVars
+			aspect: filterClassVars
+		      )
+
+		     (SubChannelInfoSpec
+			subAspect: methodVisibilityHolder
+			aspect: methodVisibilityHolder
+		      )
+		    )
+		    createNewApplication: true
+		    createNewBuilder: true
+		    postBuildCallback: methodCategoryList:
+		  )
+		 (SubCanvasSpec
+		    name: 'MethodList'
+		    majorKey: MethodList
+		    subAspectHolders:
+		   (Array
+
+		     (SubChannelInfoSpec
+			subAspect: showCoverageInformation
+			aspect: showCoverageInformation
+		      )
+		     (SubChannelInfoSpec
+			subAspect: doubleClickChannel
+			callBack: methodDoubleClicked
+		      )
+
+		     (SubChannelInfoSpec
+			subAspect: immediateUpdate
+			aspect: immediateUpdate
+		      )
+		     (SubChannelInfoSpec
+			subAspect: inGeneratorHolder
+			aspect: selectorListGenerator
+		      )
+
+		     (SubChannelInfoSpec
+			subAspect: menuHolder
+			aspect: selectorPopUpMenu
+		      )
+		     (SubChannelInfoSpec
+			subAspect: packageFilter
+			aspect: packageFilter
+		      )
+
+		     (SubChannelInfoSpec
+			subAspect: selectedMethods
+			aspect: selectedMethods
+			callBack: methodsSelectionChanged
+		      )
+		     (SubChannelInfoSpec
+			subAspect: selectionChangeCondition
+			aspect: selectionChangeConditionHolder
+		      )
+
+		     (SubChannelInfoSpec
+			subAspect: variableFilter
+			aspect: variableFilter
+			callBack: variableSelectionChanged
+		      )
+		     (SubChannelInfoSpec
+			subAspect: showMethodInheritance
+			aspect: showMethodInheritance
+		      )
+
+		     (SubChannelInfoSpec
+			subAspect: showMethodComplexity
+			aspect: showMethodComplexity
+		      )
+		     (SubChannelInfoSpec
+			subAspect: showMethodTypeIcon
+			aspect: showMethodTypeIcon
+		      )
+		     (SubChannelInfoSpec
+			subAspect: showSyntheticMethods
+			aspect: showSyntheticMethods
+		      )
+
+
+		     (SubChannelInfoSpec
+			subAspect: filterClassVars
+			aspect: filterClassVars
+		      )
+		    )
+		    createNewApplication: true
+		    createNewBuilder: true
+		    postBuildCallback: methodList:
+		  )
+		 )
+
+	      )
+	      handles: (Any 0.5 1.0)
+	    )
+	   )
+
+	)
       )
 
     "Modified: / 17-08-2011 / 13:57:39 / cg"
@@ -3370,99 +3474,99 @@
 
     <resource: #canvas>
 
-    ^ 
+    ^
      #(FullSpec
-        name: #'protocolAndMethodListSpec_JustMethodList'
-        window: 
+	name: #'protocolAndMethodListSpec_JustMethodList'
+	window:
        (WindowSpec
-          label: 'Protocol and Method List'
-          name: 'Protocol and Method List'
-          min: (Point 0 0)
-          bounds: (Rectangle 0 0 498 456)
-          icon: defaultIcon
-        )
-        component: 
+	  label: 'Protocol and Method List'
+	  name: 'Protocol and Method List'
+	  min: (Point 0 0)
+	  bounds: (Rectangle 0 0 498 456)
+	  icon: defaultIcon
+	)
+	component:
        (SpecCollection
-          collection: (
-           (SubCanvasSpec
-              name: 'MethodList'
-              layout: (LayoutFrame 0 0 0 0 0 1 0 1)
-              majorKey: MethodList
-              subAspectHolders: 
-             (Array
-                
-               (SubChannelInfoSpec
-                  subAspect: showCoverageInformation
-                  aspect: showCoverageInformation
-                ) 
-               (SubChannelInfoSpec
-                  subAspect: doubleClickChannel
-                  callBack: methodDoubleClicked
-                )
-                
-               (SubChannelInfoSpec
-                  subAspect: immediateUpdate
-                  aspect: immediateUpdate
-                ) 
-               (SubChannelInfoSpec
-                  subAspect: inGeneratorHolder
-                  aspect: selectorListGenerator5
-                )
-                
-               (SubChannelInfoSpec
-                  subAspect: menuHolder
-                  aspect: selectorPopUpMenu
-                ) 
-               (SubChannelInfoSpec
-                  subAspect: packageFilter
-                  aspect: packageFilter
-                )
-                
-               (SubChannelInfoSpec
-                  subAspect: selectedMethods
-                  aspect: selectedMethods
-                  callBack: methodsSelectionChanged
-                ) 
-               (SubChannelInfoSpec
-                  subAspect: selectionChangeCondition
-                  aspect: selectionChangeConditionHolder
-                )
-                
-               (SubChannelInfoSpec
-                  subAspect: variableFilter
-                  aspect: variableFilter
-                  callBack: variableSelectionChanged
-                ) 
-               (SubChannelInfoSpec
-                  subAspect: showMethodInheritance
-                  aspect: showMethodInheritance
-                )
-                
-               (SubChannelInfoSpec
-                  subAspect: showMethodComplexity
-                  aspect: showMethodComplexity
-                ) 
-                (SubChannelInfoSpec
-                    subAspect: showSyntheticMethods
-                    aspect: showSyntheticMethods
-                  )
-               (SubChannelInfoSpec
-                  subAspect: showMethodTypeIcon
-                  aspect: showMethodTypeIcon
-                )
-                
-               (SubChannelInfoSpec
-                  subAspect: filterClassVars
-                  aspect: filterClassVars
-                )
-              )
-              createNewApplication: true
-              createNewBuilder: true
-              postBuildCallback: methodList:
-            )
-           )
-         
-        )
+	  collection: (
+	   (SubCanvasSpec
+	      name: 'MethodList'
+	      layout: (LayoutFrame 0 0 0 0 0 1 0 1)
+	      majorKey: MethodList
+	      subAspectHolders:
+	     (Array
+
+	       (SubChannelInfoSpec
+		  subAspect: showCoverageInformation
+		  aspect: showCoverageInformation
+		)
+	       (SubChannelInfoSpec
+		  subAspect: doubleClickChannel
+		  callBack: methodDoubleClicked
+		)
+
+	       (SubChannelInfoSpec
+		  subAspect: immediateUpdate
+		  aspect: immediateUpdate
+		)
+	       (SubChannelInfoSpec
+		  subAspect: inGeneratorHolder
+		  aspect: selectorListGenerator5
+		)
+
+	       (SubChannelInfoSpec
+		  subAspect: menuHolder
+		  aspect: selectorPopUpMenu
+		)
+	       (SubChannelInfoSpec
+		  subAspect: packageFilter
+		  aspect: packageFilter
+		)
+
+	       (SubChannelInfoSpec
+		  subAspect: selectedMethods
+		  aspect: selectedMethods
+		  callBack: methodsSelectionChanged
+		)
+	       (SubChannelInfoSpec
+		  subAspect: selectionChangeCondition
+		  aspect: selectionChangeConditionHolder
+		)
+
+	       (SubChannelInfoSpec
+		  subAspect: variableFilter
+		  aspect: variableFilter
+		  callBack: variableSelectionChanged
+		)
+	       (SubChannelInfoSpec
+		  subAspect: showMethodInheritance
+		  aspect: showMethodInheritance
+		)
+
+	       (SubChannelInfoSpec
+		  subAspect: showMethodComplexity
+		  aspect: showMethodComplexity
+		)
+		(SubChannelInfoSpec
+		    subAspect: showSyntheticMethods
+		    aspect: showSyntheticMethods
+		  )
+	       (SubChannelInfoSpec
+		  subAspect: showMethodTypeIcon
+		  aspect: showMethodTypeIcon
+		)
+
+	       (SubChannelInfoSpec
+		  subAspect: filterClassVars
+		  aspect: filterClassVars
+		)
+	      )
+	      createNewApplication: true
+	      createNewBuilder: true
+	      postBuildCallback: methodList:
+	    )
+	   )
+
+	)
       )
 
     "Modified: / 17-08-2011 / 13:57:59 / cg"
@@ -3490,50 +3594,50 @@
 
     <resource: #canvas>
 
-    ^ 
+    ^
      #(FullSpec
-        name: #'searchSpec_classic'
-        window: 
+	name: #'searchSpec_classic'
+	window:
        (WindowSpec
-          label: 'Search Spec (classic)'
-          name: 'Search Spec (classic)'
-          min: (Point 10 10)
-          bounds: (Rectangle 0 0 300 40)
-        )
-        component: 
+	  label: 'Search Spec (classic)'
+	  name: 'Search Spec (classic)'
+	  min: (Point 10 10)
+	  bounds: (Rectangle 0 0 300 40)
+	)
+	component:
        (SpecCollection
-          collection: (
-           (HorizontalPanelViewSpec
-              name: 'HorizontalPanel1'
-              layout: (LayoutFrame 0 0 0 0 0 1 0 1)
-              level: 1
-              horizontalLayout: fitSpace
-              verticalLayout: center
-              horizontalSpace: 2
-              verticalSpace: 2
-              component: 
-             (SpecCollection
-                collection: (
-                 (ComboBoxSpec
-                    name: 'SearchedClassNameComboBox'
-                    activeHelpKey: gotoClassEntryField
-                    model: searchedClassNameOrSelectorHolder
-                    acceptOnLeave: false
-                    acceptOnReturn: true
-                    acceptOnPointerLeave: false
-                    acceptIfUnchanged: true
-                    comboList: visitedClassesHistory
-                    extent: (Point 294 24)
-                    postBuildCallback: searchFieldCreated:
-                  )
-                 )
-               
-              )
-              postBuildCallback: searchFieldPanelCreated:
-            )
-           )
-         
-        )
+	  collection: (
+	   (HorizontalPanelViewSpec
+	      name: 'HorizontalPanel1'
+	      layout: (LayoutFrame 0 0 0 0 0 1 0 1)
+	      level: 1
+	      horizontalLayout: fitSpace
+	      verticalLayout: center
+	      horizontalSpace: 2
+	      verticalSpace: 2
+	      component:
+	     (SpecCollection
+		collection: (
+		 (ComboBoxSpec
+		    name: 'SearchedClassNameComboBox'
+		    activeHelpKey: gotoClassEntryField
+		    model: searchedClassNameOrSelectorHolder
+		    acceptOnLeave: false
+		    acceptOnReturn: true
+		    acceptOnPointerLeave: false
+		    acceptIfUnchanged: true
+		    comboList: visitedClassesHistory
+		    extent: (Point 294 24)
+		    postBuildCallback: searchFieldCreated:
+		  )
+		 )
+
+	      )
+	      postBuildCallback: searchFieldPanelCreated:
+	    )
+	   )
+
+	)
       )
 !
 
@@ -3551,50 +3655,50 @@
 
     <resource: #canvas>
 
-    ^ 
+    ^
      #(FullSpec
-        name: #'searchSpec_live'
-        window: 
+	name: #'searchSpec_live'
+	window:
        (WindowSpec
-          label: 'Search Spec (live)'
-          name: 'Search Spec (live)'
-          min: (Point 10 10)
-          bounds: (Rectangle 0 0 300 40)
-        )
-        component: 
+	  label: 'Search Spec (live)'
+	  name: 'Search Spec (live)'
+	  min: (Point 10 10)
+	  bounds: (Rectangle 0 0 300 40)
+	)
+	component:
        (SpecCollection
-          collection: (
-           (HorizontalPanelViewSpec
-              name: 'HorizontalPanel1'
-              layout: (LayoutFrame 0 0 0 0 0 1 0 1)
-              level: 1
-              horizontalLayout: fitSpace
-              verticalLayout: center
-              horizontalSpace: 2
-              verticalSpace: 2
-              component: 
-             (SpecCollection
-                collection: (
-                 (EditFieldWithCompletionSpec
-                    name: 'SearchedClassNameComboBox'
-                    activeHelpKey: gotoClassEntryField
-                    model: searchedClassNameOrSelectorHolder
-                    acceptOnLeave: false
-                    acceptOnReturn: true
-                    acceptOnPointerLeave: false
-                    acceptIfUnchanged: true
-                    entryCompletionBlock: searchCompletionBlock
-                    extent: (Point 294 24)
-                    postBuildCallback: searchFieldCreated:
-                  )
-                 )
-               
-              )
-              postBuildCallback: searchFieldPanelCreated:
-            )
-           )
-         
-        )
+	  collection: (
+	   (HorizontalPanelViewSpec
+	      name: 'HorizontalPanel1'
+	      layout: (LayoutFrame 0 0 0 0 0 1 0 1)
+	      level: 1
+	      horizontalLayout: fitSpace
+	      verticalLayout: center
+	      horizontalSpace: 2
+	      verticalSpace: 2
+	      component:
+	     (SpecCollection
+		collection: (
+		 (EditFieldWithCompletionSpec
+		    name: 'SearchedClassNameComboBox'
+		    activeHelpKey: gotoClassEntryField
+		    model: searchedClassNameOrSelectorHolder
+		    acceptOnLeave: false
+		    acceptOnReturn: true
+		    acceptOnPointerLeave: false
+		    acceptIfUnchanged: true
+		    entryCompletionBlock: searchCompletionBlock
+		    extent: (Point 294 24)
+		    postBuildCallback: searchFieldCreated:
+		  )
+		 )
+
+	      )
+	      postBuildCallback: searchFieldPanelCreated:
+	    )
+	   )
+
+	)
       )
 !
 
@@ -3612,51 +3716,51 @@
 
     <resource: #canvas>
 
-    ^ 
+    ^
      #(FullSpec
-        name: #'searchSpec_live_level0'
-        window: 
+	name: #'searchSpec_live_level0'
+	window:
        (WindowSpec
-          label: 'Search Spec (live)'
-          name: 'Search Spec (live)'
-          min: (Point 10 10)
-          bounds: (Rectangle 0 0 300 40)
-        )
-        component: 
+	  label: 'Search Spec (live)'
+	  name: 'Search Spec (live)'
+	  min: (Point 10 10)
+	  bounds: (Rectangle 0 0 300 40)
+	)
+	component:
        (SpecCollection
-          collection: (
-           (HorizontalPanelViewSpec
-              name: 'HorizontalPanel1'
-              layout: (LayoutFrame 0 0 0 0 0 1 0 1)
-              level: 0
-              horizontalLayout: fitSpace
-              verticalLayout: center
-              horizontalSpace: 2
-              verticalSpace: 2
-              component: 
-             (SpecCollection
-                collection: (
-                 (EditFieldWithCompletionSpec
-                    name: 'SearchedClassNameComboBox'
-                    activeHelpKey: gotoClassEntryField
-                    level: -1
-                    model: searchedClassNameOrSelectorHolder
-                    acceptOnLeave: false
-                    acceptOnReturn: true
-                    acceptOnPointerLeave: false
-                    acceptIfUnchanged: true
-                    entryCompletionBlock: searchCompletionBlock
-                    extent: (Point 296 24)
-                    postBuildCallback: searchFieldCreated:
-                  )
-                 )
-               
-              )
-              postBuildCallback: searchFieldPanelCreated:
-            )
-           )
-         
-        )
+	  collection: (
+	   (HorizontalPanelViewSpec
+	      name: 'HorizontalPanel1'
+	      layout: (LayoutFrame 0 0 0 0 0 1 0 1)
+	      level: 0
+	      horizontalLayout: fitSpace
+	      verticalLayout: center
+	      horizontalSpace: 2
+	      verticalSpace: 2
+	      component:
+	     (SpecCollection
+		collection: (
+		 (EditFieldWithCompletionSpec
+		    name: 'SearchedClassNameComboBox'
+		    activeHelpKey: gotoClassEntryField
+		    level: -1
+		    model: searchedClassNameOrSelectorHolder
+		    acceptOnLeave: false
+		    acceptOnReturn: true
+		    acceptOnPointerLeave: false
+		    acceptIfUnchanged: true
+		    entryCompletionBlock: searchCompletionBlock
+		    extent: (Point 296 24)
+		    postBuildCallback: searchFieldCreated:
+		  )
+		 )
+
+	      )
+	      postBuildCallback: searchFieldPanelCreated:
+	    )
+	   )
+
+	)
       )
 !
 
@@ -3676,49 +3780,49 @@
 
     ^
      #(#FullSpec
-        #name: #selectorBrowserSpec
-        #window:
+	#name: #selectorBrowserSpec
+	#window:
        #(#WindowSpec
-          #label: 'SelectorBrowser'
-          #name: 'NewBrowser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 18 51 480 351)
-        )
-        #component:
+	  #label: 'SelectorBrowser'
+	  #name: 'NewBrowser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 18 51 480 351)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #showHandle: false
-              #snapMode: #both
-              #handlePosition: #left
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#SubCanvasSpec
-                    #name: 'Navigator'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NavigatorCanvas'
-                    #minorKey: #'selectorBrowserSpec'
-                  )
-                 #(#SubCanvasSpec
-                    #name: 'CodePane'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NewSystemBrowser'
-                    #minorKey: #codePaneSpec
-                  )
+	  #collection: #(
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #showHandle: false
+	      #snapMode: #both
+	      #handlePosition: #left
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#SubCanvasSpec
+		    #name: 'Navigator'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NavigatorCanvas'
+		    #minorKey: #'selectorBrowserSpec'
+		  )
+		 #(#SubCanvasSpec
+		    #name: 'CodePane'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NewSystemBrowser'
+		    #minorKey: #codePaneSpec
+		  )
 "/                 #(#CodeViewSpec
 "/                    #name: 'CodeView'
 "/                    #model: #codeHolder
@@ -3729,16 +3833,16 @@
 "/              #postBuildCallback: #postBuildCodeView:
 "/              #modifiedChannel: #codeModifiedHolder
 "/                  )
-                 )
-
-              )
-              #handles: #(#Any 0.3 1.0)
-              postBuildCallback: postBuildTabContentView:
-
-            )
-           )
-
-        )
+		 )
+
+	      )
+	      #handles: #(#Any 0.3 1.0)
+	      postBuildCallback: postBuildTabContentView:
+
+	    )
+	   )
+
+	)
       )
 
     "Modified: / 28-08-2010 / 12:01:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -3760,287 +3864,287 @@
 
     ^
      #(#FullSpec
-        #name: #senderChainBrowserSpec
-        #window:
+	#name: #senderChainBrowserSpec
+	#window:
        #(#WindowSpec
-          #label: 'MethodBrowser'
-          #name: 'MethodBrowser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 185 379 647 679)
-        )
-        #component:
+	  #label: 'MethodBrowser'
+	  #name: 'MethodBrowser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 185 379 647 679)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #showHandle: false
-              #snapMode: #both
-              #handlePosition: #left
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#VariableHorizontalPanelSpec
-                    #name: 'VariableHorizontalPanel1'
-                    #showHandle: false
-                    #barWidth: 2
-                    #component:
-                   #(#SpecCollection
-                      #collection: #(
-                       #(#SubCanvasSpec
-                          #name: 'MethodList1'
-                          #majorKey: #'MethodList'
-                          #subAspectHolders:
-                         #(#Array
-
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showCoverageInformation
-                        #aspect: #showCoverageInformation
-                      ) 
-                           #(#SubChannelInfoSpec
-                              #subAspect: #doubleClickChannel
-                              #callBack: #methodDoubleClicked1
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #immediateUpdate
-                              #aspect: #immediateUpdate
-                            )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #inGeneratorHolder
-                              #aspect: #selectorListGenerator1
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #menuHolder
-                              #aspect: #selectorPopUpMenu
-                            )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodInheritance
-                        #aspect: #showMethodInheritance
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodComplexity
-                        #aspect: #showMethodComplexity
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodTypeIcon
-                        #aspect: #showMethodTypeIcon
-                      )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #packageFilter
-                              #aspect: #packageFilter
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #selectedMethods
-                              #aspect: #selectedMethods1
-                              #callBack: #methodsSelectionChanged1
-                            )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #selectionChangeCondition
-                              #aspect: #selectionChangeConditionHolder
-                            )
-                          )
-                          #createNewApplication: true
-                          #createNewBuilder: true
-                        )
-                       #(#SubCanvasSpec
-                          #name: 'MethodList2'
-                          #majorKey: #'MethodList'
-                          #subAspectHolders:
-                         #(#Array
-
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showCoverageInformation
-                        #aspect: #showCoverageInformation
-                      ) 
-                           #(#SubChannelInfoSpec
-                              #subAspect: #doubleClickChannel
-                              #callBack: #methodDoubleClicked2
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #immediateUpdate
-                              #aspect: #immediateUpdate
-                            )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodInheritance
-                        #aspect: #showMethodInheritance
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodComplexity
-                        #aspect: #showMethodComplexity
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodTypeIcon
-                        #aspect: #showMethodTypeIcon
-                      )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #inGeneratorHolder
-                              #aspect: #selectorListGenerator2
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #menuHolder
-                              #aspect: #selectorPopUpMenu
-                            )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #packageFilter
-                              #aspect: #packageFilter
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #selectedMethods
-                              #aspect: #selectedMethods2
-                              #callBack: #methodsSelectionChanged2
-                            )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #selectionChangeCondition
-                              #aspect: #selectionChangeConditionHolder
-                            )
-                          )
-                          #createNewApplication: true
-                          #createNewBuilder: true
-                        )
-                       #(#SubCanvasSpec
-                          #name: 'MethodList3'
-                          #majorKey: #'MethodList'
-                          #subAspectHolders:
-                         #(#Array
-
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showCoverageInformation
-                        #aspect: #showCoverageInformation
-                      ) 
-                           #(#SubChannelInfoSpec
-                              #subAspect: #doubleClickChannel
-                              #callBack: #methodDoubleClicked3
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #immediateUpdate
-                              #aspect: #immediateUpdate
-                            )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodInheritance
-                        #aspect: #showMethodInheritance
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodComplexity
-                        #aspect: #showMethodComplexity
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodTypeIcon
-                        #aspect: #showMethodTypeIcon
-                      )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #inGeneratorHolder
-                              #aspect: #selectorListGenerator3
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #menuHolder
-                              #aspect: #selectorPopUpMenu
-                            )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #packageFilter
-                              #aspect: #packageFilter
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #selectedMethods
-                              #aspect: #selectedMethods3
-                              #callBack: #methodsSelectionChanged3
-                            )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #selectionChangeCondition
-                              #aspect: #selectionChangeConditionHolder
-                            )
-                          )
-                          #createNewApplication: true
-                          #createNewBuilder: true
-                        )
-                       #(#SubCanvasSpec
-                          #name: 'MethodList4'
-                          #majorKey: #'MethodList'
-                          #subAspectHolders:
-                         #(#Array
-
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showCoverageInformation
-                        #aspect: #showCoverageInformation
-                      ) 
-                           #(#SubChannelInfoSpec
-                              #subAspect: #doubleClickChannel
-                              #callBack: #methodDoubleClicked4
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #immediateUpdate
-                              #aspect: #immediateUpdate
-                            )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodInheritance
-                        #aspect: #showMethodInheritance
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodComplexity
-                        #aspect: #showMethodComplexity
-                      )
-                     #(#SubChannelInfoSpec
-                        #subAspect: #showMethodTypeIcon
-                        #aspect: #showMethodTypeIcon
-                      )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #inGeneratorHolder
-                              #aspect: #selectorListGenerator4
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #menuHolder
-                              #aspect: #selectorPopUpMenu
-                            )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #packageFilter
-                              #aspect: #packageFilter
-                            )
-                           #(#SubChannelInfoSpec
-                              #subAspect: #selectedMethods
-                              #aspect: #selectedMethods4
-                              #callBack: #methodsSelectionChanged4
-                            )
-
-                           #(#SubChannelInfoSpec
-                              #subAspect: #selectionChangeCondition
-                              #aspect: #selectionChangeConditionHolder
-                            )
-                          )
-                          #createNewApplication: true
-                          #createNewBuilder: true
-                        )
-                       )
-
-                    )
-                    #handles: #(#Any 0.25 0.5 0.75 1.0)
-                  )
-                 #(#SubCanvasSpec
-                    #name: 'CodePane'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NewSystemBrowser'
-                    #minorKey: #codePaneSpec
-                  )
+	  #collection: #(
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #showHandle: false
+	      #snapMode: #both
+	      #handlePosition: #left
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#VariableHorizontalPanelSpec
+		    #name: 'VariableHorizontalPanel1'
+		    #showHandle: false
+		    #barWidth: 2
+		    #component:
+		   #(#SpecCollection
+		      #collection: #(
+		       #(#SubCanvasSpec
+			  #name: 'MethodList1'
+			  #majorKey: #'MethodList'
+			  #subAspectHolders:
+			 #(#Array
+
+		     #(#SubChannelInfoSpec
+			#subAspect: #showCoverageInformation
+			#aspect: #showCoverageInformation
+		      )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #doubleClickChannel
+			      #callBack: #methodDoubleClicked1
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #immediateUpdate
+			      #aspect: #immediateUpdate
+			    )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #inGeneratorHolder
+			      #aspect: #selectorListGenerator1
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #menuHolder
+			      #aspect: #selectorPopUpMenu
+			    )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodInheritance
+			#aspect: #showMethodInheritance
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodComplexity
+			#aspect: #showMethodComplexity
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodTypeIcon
+			#aspect: #showMethodTypeIcon
+		      )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #packageFilter
+			      #aspect: #packageFilter
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #selectedMethods
+			      #aspect: #selectedMethods1
+			      #callBack: #methodsSelectionChanged1
+			    )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #selectionChangeCondition
+			      #aspect: #selectionChangeConditionHolder
+			    )
+			  )
+			  #createNewApplication: true
+			  #createNewBuilder: true
+			)
+		       #(#SubCanvasSpec
+			  #name: 'MethodList2'
+			  #majorKey: #'MethodList'
+			  #subAspectHolders:
+			 #(#Array
+
+		     #(#SubChannelInfoSpec
+			#subAspect: #showCoverageInformation
+			#aspect: #showCoverageInformation
+		      )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #doubleClickChannel
+			      #callBack: #methodDoubleClicked2
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #immediateUpdate
+			      #aspect: #immediateUpdate
+			    )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodInheritance
+			#aspect: #showMethodInheritance
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodComplexity
+			#aspect: #showMethodComplexity
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodTypeIcon
+			#aspect: #showMethodTypeIcon
+		      )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #inGeneratorHolder
+			      #aspect: #selectorListGenerator2
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #menuHolder
+			      #aspect: #selectorPopUpMenu
+			    )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #packageFilter
+			      #aspect: #packageFilter
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #selectedMethods
+			      #aspect: #selectedMethods2
+			      #callBack: #methodsSelectionChanged2
+			    )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #selectionChangeCondition
+			      #aspect: #selectionChangeConditionHolder
+			    )
+			  )
+			  #createNewApplication: true
+			  #createNewBuilder: true
+			)
+		       #(#SubCanvasSpec
+			  #name: 'MethodList3'
+			  #majorKey: #'MethodList'
+			  #subAspectHolders:
+			 #(#Array
+
+		     #(#SubChannelInfoSpec
+			#subAspect: #showCoverageInformation
+			#aspect: #showCoverageInformation
+		      )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #doubleClickChannel
+			      #callBack: #methodDoubleClicked3
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #immediateUpdate
+			      #aspect: #immediateUpdate
+			    )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodInheritance
+			#aspect: #showMethodInheritance
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodComplexity
+			#aspect: #showMethodComplexity
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodTypeIcon
+			#aspect: #showMethodTypeIcon
+		      )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #inGeneratorHolder
+			      #aspect: #selectorListGenerator3
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #menuHolder
+			      #aspect: #selectorPopUpMenu
+			    )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #packageFilter
+			      #aspect: #packageFilter
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #selectedMethods
+			      #aspect: #selectedMethods3
+			      #callBack: #methodsSelectionChanged3
+			    )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #selectionChangeCondition
+			      #aspect: #selectionChangeConditionHolder
+			    )
+			  )
+			  #createNewApplication: true
+			  #createNewBuilder: true
+			)
+		       #(#SubCanvasSpec
+			  #name: 'MethodList4'
+			  #majorKey: #'MethodList'
+			  #subAspectHolders:
+			 #(#Array
+
+		     #(#SubChannelInfoSpec
+			#subAspect: #showCoverageInformation
+			#aspect: #showCoverageInformation
+		      )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #doubleClickChannel
+			      #callBack: #methodDoubleClicked4
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #immediateUpdate
+			      #aspect: #immediateUpdate
+			    )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodInheritance
+			#aspect: #showMethodInheritance
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodComplexity
+			#aspect: #showMethodComplexity
+		      )
+		     #(#SubChannelInfoSpec
+			#subAspect: #showMethodTypeIcon
+			#aspect: #showMethodTypeIcon
+		      )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #inGeneratorHolder
+			      #aspect: #selectorListGenerator4
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #menuHolder
+			      #aspect: #selectorPopUpMenu
+			    )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #packageFilter
+			      #aspect: #packageFilter
+			    )
+			   #(#SubChannelInfoSpec
+			      #subAspect: #selectedMethods
+			      #aspect: #selectedMethods4
+			      #callBack: #methodsSelectionChanged4
+			    )
+
+			   #(#SubChannelInfoSpec
+			      #subAspect: #selectionChangeCondition
+			      #aspect: #selectionChangeConditionHolder
+			    )
+			  )
+			  #createNewApplication: true
+			  #createNewBuilder: true
+			)
+		       )
+
+		    )
+		    #handles: #(#Any 0.25 0.5 0.75 1.0)
+		  )
+		 #(#SubCanvasSpec
+		    #name: 'CodePane'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NewSystemBrowser'
+		    #minorKey: #codePaneSpec
+		  )
 "/                 #(#CodeViewSpec
 "/                    #name: 'CodeView'
 "/                    #model: #codeHolder
@@ -4050,16 +4154,16 @@
 "/              #postBuildCallback: #postBuildCodeView:
 "/              #modifiedChannel: #codeModifiedHolder
 "/                  )
-                 )
-
-              )
-              #handles: #(#Any 0.5 1.0)
-              postBuildCallback: postBuildTabContentView:
-
-            )
-           )
-
-        )
+		 )
+
+	      )
+	      #handles: #(#Any 0.5 1.0)
+	      postBuildCallback: postBuildTabContentView:
+
+	    )
+	   )
+
+	)
       )
 
     "Modified: / 27-04-2010 / 16:30:26 / cg"
@@ -4082,49 +4186,49 @@
 
     ^
      #(#FullSpec
-        #name: #singleCategoryBrowserSpec
-        #window:
+	#name: #singleCategoryBrowserSpec
+	#window:
        #(#WindowSpec
-          #label: 'CategoryBrowser'
-          #name: 'SingleCategoryBrowser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 12 22 474 322)
-        )
-        #component:
+	  #label: 'CategoryBrowser'
+	  #name: 'SingleCategoryBrowser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 12 22 474 322)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #showHandle: false
-              #snapMode: #both
-              #handlePosition: #left
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#SubCanvasSpec
-                    #name: 'Navigator'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NavigatorCanvas'
-                    #minorKey: #'singleCategoryBrowserSpec'
-                  )
-                 #(#SubCanvasSpec
-                    #name: 'CodePane'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NewSystemBrowser'
-                    #minorKey: #codePaneSpec
-                  )
+	  #collection: #(
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #showHandle: false
+	      #snapMode: #both
+	      #handlePosition: #left
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#SubCanvasSpec
+		    #name: 'Navigator'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NavigatorCanvas'
+		    #minorKey: #'singleCategoryBrowserSpec'
+		  )
+		 #(#SubCanvasSpec
+		    #name: 'CodePane'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NewSystemBrowser'
+		    #minorKey: #codePaneSpec
+		  )
 "/                 #(#CodeViewSpec
 "/                    #name: 'CodeView'
 "/                    #model: #codeHolder
@@ -4134,16 +4238,16 @@
 "/              #postBuildCallback: #postBuildCodeView:
 "/              #modifiedChannel: #codeModifiedHolder
 "/                  )
-                 )
-
-              )
-              #handles: #(#Any 0.3 1.0)
-              postBuildCallback: postBuildTabContentView:
-
-            )
-           )
-
-        )
+		 )
+
+	      )
+	      #handles: #(#Any 0.3 1.0)
+	      postBuildCallback: postBuildTabContentView:
+
+	    )
+	   )
+
+	)
       )
 
     "Modified: / 28-08-2010 / 12:01:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -4165,49 +4269,49 @@
 
     ^
      #(#FullSpec
-        #name: #singleClassBrowserSpec
-        #window:
+	#name: #singleClassBrowserSpec
+	#window:
        #(#WindowSpec
-          #label: 'ClassBrowser'
-          #name: 'NewBrowser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 12 22 474 322)
-        )
-        #component:
+	  #label: 'ClassBrowser'
+	  #name: 'NewBrowser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 12 22 474 322)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #showHandle: false
-              #snapMode: #both
-              #handlePosition: #left
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#SubCanvasSpec
-                    #name: 'Navigator'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NavigatorCanvas'
-                    #minorKey: #'singleClassBrowserSpec'
-                  )
-                 #(#SubCanvasSpec
-                    #name: 'CodePane'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NewSystemBrowser'
-                    #minorKey: #codePaneSpec
-                  )
+	  #collection: #(
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #showHandle: false
+	      #snapMode: #both
+	      #handlePosition: #left
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#SubCanvasSpec
+		    #name: 'Navigator'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NavigatorCanvas'
+		    #minorKey: #'singleClassBrowserSpec'
+		  )
+		 #(#SubCanvasSpec
+		    #name: 'CodePane'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NewSystemBrowser'
+		    #minorKey: #codePaneSpec
+		  )
 "/                 #(#CodeViewSpec
 "/                    #name: 'CodeView'
 "/                    #model: #codeHolder
@@ -4217,16 +4321,16 @@
 "/              #postBuildCallback: #postBuildCodeView:
 "/              #modifiedChannel: #codeModifiedHolder
 "/                  )
-                 )
-
-              )
-              #handles: #(#Any 0.4 1.0)
-              postBuildCallback: postBuildTabContentView:
-
-            )
-           )
-
-        )
+		 )
+
+	      )
+	      #handles: #(#Any 0.4 1.0)
+	      postBuildCallback: postBuildTabContentView:
+
+	    )
+	   )
+
+	)
       )
 
     "Modified: / 28-08-2010 / 12:01:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -4248,49 +4352,49 @@
 
     ^
      #(#FullSpec
-        #name: #singleFullProtocolBrowserSpec
-        #window:
+	#name: #singleFullProtocolBrowserSpec
+	#window:
        #(#WindowSpec
-          #label: 'ProtocolBrowser'
-          #name: 'NewBrowser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 13 23 475 323)
-        )
-        #component:
+	  #label: 'ProtocolBrowser'
+	  #name: 'NewBrowser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 13 23 475 323)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #showHandle: false
-              #snapMode: #both
-              #handlePosition: #left
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#SubCanvasSpec
-                    #name: 'Navigator'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NavigatorCanvas'
-                    #minorKey: #'singleFullProtocolBrowserSpec'
-                  )
-                 #(#SubCanvasSpec
-                    #name: 'CodePane'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NewSystemBrowser'
-                    #minorKey: #codePaneSpec
-                  )
+	  #collection: #(
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #showHandle: false
+	      #snapMode: #both
+	      #handlePosition: #left
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#SubCanvasSpec
+		    #name: 'Navigator'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NavigatorCanvas'
+		    #minorKey: #'singleFullProtocolBrowserSpec'
+		  )
+		 #(#SubCanvasSpec
+		    #name: 'CodePane'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NewSystemBrowser'
+		    #minorKey: #codePaneSpec
+		  )
 "/                 #(#CodeViewSpec
 "/                    #name: 'CodeView'
 "/                    #model: #codeHolder
@@ -4300,16 +4404,16 @@
 "/              #postBuildCallback: #postBuildCodeView:
 "/              #modifiedChannel: #codeModifiedHolder
 "/                  )
-                 )
-
-              )
-              #handles: #(#Any 0.3 1.0)
-              postBuildCallback: postBuildTabContentView:
-
-            )
-           )
-
-        )
+		 )
+
+	      )
+	      #handles: #(#Any 0.3 1.0)
+	      postBuildCallback: postBuildTabContentView:
+
+	    )
+	   )
+
+	)
       )
 
     "Modified: / 01-03-2000 / 11:59:28 / cg"
@@ -4330,86 +4434,86 @@
 
     <resource: #canvas>
 
-    ^ 
+    ^
      #(FullSpec
-        name: singleMethodBrowserSpec
-        window: 
+	name: singleMethodBrowserSpec
+	window:
        (WindowSpec
-          label: 'MethodBrowser'
-          name: 'MethodBrowser'
-          min: (Point 0 0)
-          bounds: (Rectangle 0 0 462 300)
-        )
-        component: 
+	  label: 'MethodBrowser'
+	  name: 'MethodBrowser'
+	  min: (Point 0 0)
+	  bounds: (Rectangle 0 0 462 300)
+	)
+	component:
        (SpecCollection
-          collection: (
-           (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )
-           (TransparentBoxSpec
-              name: 'Box1'
-              layout: (LayoutFrame 0 0 0 0 0 1 0 1)
-              postBuildCallback: postBuildTabContentView:
-
-              component: 
-             (SpecCollection
-                collection: (
-                 (SubCanvasSpec
-                    name: 'PseudoMethodList'
-                    layout: (LayoutFrame 0 0.0 0 0 0 1.0 25 0)
-                    majorKey: MethodList
-                    minorKey: singleMethodWindowSpec
-                    subAspectHolders: 
-                   (Array
-                      
-                     (SubChannelInfoSpec
-                        subAspect: immediateUpdate
-                        aspect: immediateUpdate
-                      ) 
-                     (SubChannelInfoSpec
-                        subAspect: inGeneratorHolder
-                        aspect: selectorListGenerator
-                      )
-                      
-                     (SubChannelInfoSpec
-                        subAspect: packageFilter
-                        aspect: packageFilter
-                      ) 
-                     (SubChannelInfoSpec
-                        subAspect: selectedMethods
-                        aspect: selectedProtocolMethods
-                      )
-                      
-                     (SubChannelInfoSpec
-                        subAspect: menuHolder
-                        aspect: selectorPopUpMenu
-                      )
-                    )
-                    createNewApplication: true
-                    createNewBuilder: true
-                  )
-                 (SubCanvasSpec
-                    name: 'CodePane'
-                    layout: (LayoutFrame 0 0.0 25 0.0 0 1.0 0 1.0)
-                    autoHideScrollBars: false
-                    majorKey: NewSystemBrowser
-                    minorKey: codePaneSpec
-                    createNewBuilder: false
-                  )
-                 )
-               
-              )
-            )
-           )
-         
-        )
+	  collection: (
+	   (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+	   (TransparentBoxSpec
+	      name: 'Box1'
+	      layout: (LayoutFrame 0 0 0 0 0 1 0 1)
+	      postBuildCallback: postBuildTabContentView:
+
+	      component:
+	     (SpecCollection
+		collection: (
+		 (SubCanvasSpec
+		    name: 'PseudoMethodList'
+		    layout: (LayoutFrame 0 0.0 0 0 0 1.0 25 0)
+		    majorKey: MethodList
+		    minorKey: singleMethodWindowSpec
+		    subAspectHolders:
+		   (Array
+
+		     (SubChannelInfoSpec
+			subAspect: immediateUpdate
+			aspect: immediateUpdate
+		      )
+		     (SubChannelInfoSpec
+			subAspect: inGeneratorHolder
+			aspect: selectorListGenerator
+		      )
+
+		     (SubChannelInfoSpec
+			subAspect: packageFilter
+			aspect: packageFilter
+		      )
+		     (SubChannelInfoSpec
+			subAspect: selectedMethods
+			aspect: selectedProtocolMethods
+		      )
+
+		     (SubChannelInfoSpec
+			subAspect: menuHolder
+			aspect: selectorPopUpMenu
+		      )
+		    )
+		    createNewApplication: true
+		    createNewBuilder: true
+		  )
+		 (SubCanvasSpec
+		    name: 'CodePane'
+		    layout: (LayoutFrame 0 0.0 25 0.0 0 1.0 0 1.0)
+		    autoHideScrollBars: false
+		    majorKey: NewSystemBrowser
+		    minorKey: codePaneSpec
+		    createNewBuilder: false
+		  )
+		 )
+
+	      )
+	    )
+	   )
+
+	)
       )
 
     "Modified: / 28-08-2010 / 12:01:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -4429,109 +4533,109 @@
 
     <resource: #canvas>
 
-    ^ 
+    ^
      #(FullSpec
-        name: singleMethodWithInfoBrowserSpec
-        window: 
+	name: singleMethodWithInfoBrowserSpec
+	window:
        (WindowSpec
-          label: 'MethodBrowser'
-          name: 'MethodBrowser'
-          min: (Point 0 0)
-          bounds: (Rectangle 0 0 462 300)
-        )
-        component: 
+	  label: 'MethodBrowser'
+	  name: 'MethodBrowser'
+	  min: (Point 0 0)
+	  bounds: (Rectangle 0 0 462 300)
+	)
+	component:
        (SpecCollection
-          collection: (
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-
-           (TransparentBoxSpec
-              name: 'Box'
-              layout: (LayoutFrame 0 0 0 0 0 1 0 1)
-              postBuildCallback: postBuildTabContentView:
-
-              component: 
-             (SpecCollection
-                collection: (
-                 (SubCanvasSpec
-                    name: 'SubCanvas1'
-                    layout: (LayoutFrame 0 0.0 0 0 0 1.0 25 0)
-                    majorKey: MethodList
-                    minorKey: singleMethodWindowSpec
-                    subAspectHolders: 
-                   (Array
-                      
-                     (SubChannelInfoSpec
-                        subAspect: immediateUpdate
-                        aspect: immediateUpdate
-                      ) 
-                     (SubChannelInfoSpec
-                        subAspect: inGeneratorHolder
-                        aspect: selectorListGenerator
-                      )
-                      
-                     (SubChannelInfoSpec
-                        subAspect: packageFilter
-                        aspect: packageFilter
-                      ) 
-                     (SubChannelInfoSpec
-                        subAspect: selectedMethods
-                        aspect: selectedProtocolMethods
-                      )
-                      
-                     (SubChannelInfoSpec
-                        subAspect: menuHolder
-                        aspect: methodListPopUpMenu
-                      )
-                    )
-                    createNewApplication: true
-                    createNewBuilder: true
-                  )
-                 (VariableVerticalPanelSpec
-                    name: 'VariableVerticalPanel2'
-                    layout: (LayoutFrame 0 0.0 25 0 0 1.0 0 1.0)
-                    showHandle: false
-                    snapMode: both
-                    handlePosition: left
-                    component: 
-                   (SpecCollection
-                      collection: (
-                       (TextEditorSpec
-                          name: 'TextEditor1'
-                          model: methodInfo
-                          hasHorizontalScrollBar: true
-                          hasVerticalScrollBar: true
-                          autoHideScrollBars: true
-                          isReadOnly: true
-                          hasKeyboardFocusInitially: false
-                        )
-                       (SubCanvasSpec
-                          name: 'SubCanvas2'
-                          autoHideScrollBars: false
-                          majorKey: NewSystemBrowser
-                          minorKey: codePaneSpec
-                          createNewBuilder: false
-                        )
-                       )
-                     
-                    )
-                    handles: (Any 0.5 1.0)
-                  )
-                 )
-               
-              )
-            )
-           )
-         
-        )
+	  collection: (
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+
+	   (TransparentBoxSpec
+	      name: 'Box'
+	      layout: (LayoutFrame 0 0 0 0 0 1 0 1)
+	      postBuildCallback: postBuildTabContentView:
+
+	      component:
+	     (SpecCollection
+		collection: (
+		 (SubCanvasSpec
+		    name: 'SubCanvas1'
+		    layout: (LayoutFrame 0 0.0 0 0 0 1.0 25 0)
+		    majorKey: MethodList
+		    minorKey: singleMethodWindowSpec
+		    subAspectHolders:
+		   (Array
+
+		     (SubChannelInfoSpec
+			subAspect: immediateUpdate
+			aspect: immediateUpdate
+		      )
+		     (SubChannelInfoSpec
+			subAspect: inGeneratorHolder
+			aspect: selectorListGenerator
+		      )
+
+		     (SubChannelInfoSpec
+			subAspect: packageFilter
+			aspect: packageFilter
+		      )
+		     (SubChannelInfoSpec
+			subAspect: selectedMethods
+			aspect: selectedProtocolMethods
+		      )
+
+		     (SubChannelInfoSpec
+			subAspect: menuHolder
+			aspect: methodListPopUpMenu
+		      )
+		    )
+		    createNewApplication: true
+		    createNewBuilder: true
+		  )
+		 (VariableVerticalPanelSpec
+		    name: 'VariableVerticalPanel2'
+		    layout: (LayoutFrame 0 0.0 25 0 0 1.0 0 1.0)
+		    showHandle: false
+		    snapMode: both
+		    handlePosition: left
+		    component:
+		   (SpecCollection
+		      collection: (
+		       (TextEditorSpec
+			  name: 'TextEditor1'
+			  model: methodInfo
+			  hasHorizontalScrollBar: true
+			  hasVerticalScrollBar: true
+			  autoHideScrollBars: true
+			  isReadOnly: true
+			  hasKeyboardFocusInitially: false
+			)
+		       (SubCanvasSpec
+			  name: 'SubCanvas2'
+			  autoHideScrollBars: false
+			  majorKey: NewSystemBrowser
+			  minorKey: codePaneSpec
+			  createNewBuilder: false
+			)
+		       )
+
+		    )
+		    handles: (Any 0.5 1.0)
+		  )
+		 )
+
+	      )
+	    )
+	   )
+
+	)
       )
 
     "Modified: / 28-08-2010 / 12:02:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -4553,49 +4657,49 @@
 
     ^
      #(#FullSpec
-        #name: #singleNameSpaceBrowserSpec
-        #window:
+	#name: #singleNameSpaceBrowserSpec
+	#window:
        #(#WindowSpec
-          #label: 'NameSpaceBrowser'
-          #name: 'NameSpaceBrowser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 518 71 1205 712)
-        )
-        #component:
+	  #label: 'NameSpaceBrowser'
+	  #name: 'NameSpaceBrowser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 518 71 1205 712)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #showHandle: false
-              #snapMode: #both
-              #handlePosition: #left
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#SubCanvasSpec
-                    #name: 'Navigator'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NavigatorCanvas'
-                    #minorKey: #singleNameSpaceBrowserSpec
-                  )
-                 #(#SubCanvasSpec
-                    #name: 'CodePane'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NewSystemBrowser'
-                    #minorKey: #codePaneSpec
-                  )
+	  #collection: #(
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #showHandle: false
+	      #snapMode: #both
+	      #handlePosition: #left
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#SubCanvasSpec
+		    #name: 'Navigator'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NavigatorCanvas'
+		    #minorKey: #singleNameSpaceBrowserSpec
+		  )
+		 #(#SubCanvasSpec
+		    #name: 'CodePane'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NewSystemBrowser'
+		    #minorKey: #codePaneSpec
+		  )
 "/                 #(#CodeViewSpec
 "/                    #name: 'CodeView'
 "/                    #model: #codeHolder
@@ -4605,16 +4709,16 @@
 "/              #postBuildCallback: #postBuildCodeView:
 "/              #modifiedChannel: #codeModifiedHolder
 "/                  )
-                 )
-
-              )
-              #handles: #(#Any 0.3 1.0)
-              postBuildCallback: postBuildTabContentView:
-
-            )
-           )
-
-        )
+		 )
+
+	      )
+	      #handles: #(#Any 0.3 1.0)
+	      postBuildCallback: postBuildTabContentView:
+
+	    )
+	   )
+
+	)
       )
 
     "Modified: / 18-08-2000 / 15:01:10 / cg"
@@ -4637,49 +4741,49 @@
 
     ^
      #(#FullSpec
-        #name: #singleNameSpaceBrowserSpec
-        #window:
+	#name: #singleNameSpaceBrowserSpec
+	#window:
        #(#WindowSpec
-          #label: 'NameSpaceBrowser'
-          #name: 'NameSpaceBrowser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 518 71 1205 712)
-        )
-        #component:
+	  #label: 'NameSpaceBrowser'
+	  #name: 'NameSpaceBrowser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 518 71 1205 712)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #showHandle: false
-              #snapMode: #both
-              #handlePosition: #left
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#SubCanvasSpec
-                    #name: 'Navigator'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NavigatorCanvas'
-                    #minorKey: #singleNameSpaceFullBrowserSpec
-                  )
-                 #(#SubCanvasSpec
-                    #name: 'CodePane'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NewSystemBrowser'
-                    #minorKey: #codePaneSpec
-                  )
+	  #collection: #(
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #showHandle: false
+	      #snapMode: #both
+	      #handlePosition: #left
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#SubCanvasSpec
+		    #name: 'Navigator'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NavigatorCanvas'
+		    #minorKey: #singleNameSpaceFullBrowserSpec
+		  )
+		 #(#SubCanvasSpec
+		    #name: 'CodePane'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NewSystemBrowser'
+		    #minorKey: #codePaneSpec
+		  )
 "/                 #(#CodeViewSpec
 "/                    #name: 'CodeView'
 "/                    #model: #codeHolder
@@ -4689,16 +4793,16 @@
 "/              #postBuildCallback: #postBuildCodeView:
 "/              #modifiedChannel: #codeModifiedHolder
 "/                  )
-                 )
-
-              )
-              #handles: #(#Any 0.3 1.0)
-              postBuildCallback: postBuildTabContentView:
-
-            )
-           )
-
-        )
+		 )
+
+	      )
+	      #handles: #(#Any 0.3 1.0)
+	      postBuildCallback: postBuildTabContentView:
+
+	    )
+	   )
+
+	)
       )
 
     "Created: / 18-08-2000 / 15:01:07 / cg"
@@ -4721,49 +4825,49 @@
 
     ^
      #(#FullSpec
-        #name: #singleProjectBrowserSpec
-        #window:
+	#name: #singleProjectBrowserSpec
+	#window:
        #(#WindowSpec
-          #label: 'ProjectBrowser'
-          #name: 'NewBrowser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 13 23 475 323)
-        )
-        #component:
+	  #label: 'ProjectBrowser'
+	  #name: 'NewBrowser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 13 23 475 323)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #showHandle: false
-              #snapMode: #both
-              #handlePosition: #left
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#SubCanvasSpec
-                    #name: 'Navigator'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NavigatorCanvas'
-                    #minorKey: #'singleProjectBrowserSpec'
-                  )
-                 #(#SubCanvasSpec
-                    #name: 'CodePane'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NewSystemBrowser'
-                    #minorKey: #codePaneSpec
-                  )
+	  #collection: #(
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #showHandle: false
+	      #snapMode: #both
+	      #handlePosition: #left
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#SubCanvasSpec
+		    #name: 'Navigator'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NavigatorCanvas'
+		    #minorKey: #'singleProjectBrowserSpec'
+		  )
+		 #(#SubCanvasSpec
+		    #name: 'CodePane'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NewSystemBrowser'
+		    #minorKey: #codePaneSpec
+		  )
 "/                 #(#CodeViewSpec
 "/                    #name: 'CodeView'
 "/                    #model: #codeHolder
@@ -4773,16 +4877,16 @@
 "/              #postBuildCallback: #postBuildCodeView:
 "/              #modifiedChannel: #codeModifiedHolder
 "/                  )
-                 )
-
-              )
-              #handles: #(#Any 0.3 1.0)
-              postBuildCallback: postBuildTabContentView:
-
-            )
-           )
-
-        )
+		 )
+
+	      )
+	      #handles: #(#Any 0.3 1.0)
+	      postBuildCallback: postBuildTabContentView:
+
+	    )
+	   )
+
+	)
       )
 
     "Created: / 25-02-2000 / 02:33:53 / cg"
@@ -4805,49 +4909,49 @@
 
     ^
      #(#FullSpec
-        #name: #singleProjectFullBrowserSpec
-        #window:
+	#name: #singleProjectFullBrowserSpec
+	#window:
        #(#WindowSpec
-          #label: 'ProjectBrowser'
-          #name: 'NewBrowser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 13 23 475 323)
-        )
-        #component:
+	  #label: 'ProjectBrowser'
+	  #name: 'NewBrowser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 13 23 475 323)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #showHandle: false
-              #snapMode: #both
-              #handlePosition: #left
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#SubCanvasSpec
-                    #name: 'Navigator'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NavigatorCanvas'
-                    #minorKey: #'singleProjectFullBrowserSpec'
-                  )
-                 #(#SubCanvasSpec
-                    #name: 'CodePane'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NewSystemBrowser'
-                    #minorKey: #codePaneSpec
-                  )
+	  #collection: #(
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #showHandle: false
+	      #snapMode: #both
+	      #handlePosition: #left
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#SubCanvasSpec
+		    #name: 'Navigator'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NavigatorCanvas'
+		    #minorKey: #'singleProjectFullBrowserSpec'
+		  )
+		 #(#SubCanvasSpec
+		    #name: 'CodePane'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NewSystemBrowser'
+		    #minorKey: #codePaneSpec
+		  )
 "/                 #(#CodeViewSpec
 "/                    #name: 'CodeView'
 "/                    #model: #codeHolder
@@ -4857,16 +4961,16 @@
 "/              #postBuildCallback: #postBuildCodeView:
 "/              #modifiedChannel: #codeModifiedHolder
 "/                  )
-                 )
-
-              )
-              #handles: #(#Any 0.3 1.0)
-              postBuildCallback: postBuildTabContentView:
-
-            )
-           )
-
-        )
+		 )
+
+	      )
+	      #handles: #(#Any 0.3 1.0)
+	      postBuildCallback: postBuildTabContentView:
+
+	    )
+	   )
+
+	)
       )
 
     "Created: / 18-08-2000 / 18:42:51 / cg"
@@ -4889,49 +4993,49 @@
 
     ^
      #(#FullSpec
-        #name: #singleProtocolBrowserSpec
-        #window:
+	#name: #singleProtocolBrowserSpec
+	#window:
        #(#WindowSpec
-          #label: 'ProtocolBrowser'
-          #name: 'NewBrowser'
-          #min: #(#Point 0 0)
-          #bounds: #(#Rectangle 13 23 475 323)
-        )
-        #component:
+	  #label: 'ProtocolBrowser'
+	  #name: 'NewBrowser'
+	  #min: #(#Point 0 0)
+	  #bounds: #(#Rectangle 13 23 475 323)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-
-           #(#VariableVerticalPanelSpec
-              #name: 'VariableVerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              #showHandle: false
-              #snapMode: #both
-              #handlePosition: #left
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#SubCanvasSpec
-                    #name: 'Navigator'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NavigatorCanvas'
-                    #minorKey: #'singleProtocolBrowserSpec'
-                  )
-                 #(#SubCanvasSpec
-                    #name: 'CodePane'
-                    #autoHideScrollBars: false
-                    #majorKey: #'NewSystemBrowser'
-                    #minorKey: #codePaneSpec
-                  )
+	  #collection: #(
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+
+	   #(#VariableVerticalPanelSpec
+	      #name: 'VariableVerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      #showHandle: false
+	      #snapMode: #both
+	      #handlePosition: #left
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#SubCanvasSpec
+		    #name: 'Navigator'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NavigatorCanvas'
+		    #minorKey: #'singleProtocolBrowserSpec'
+		  )
+		 #(#SubCanvasSpec
+		    #name: 'CodePane'
+		    #autoHideScrollBars: false
+		    #majorKey: #'NewSystemBrowser'
+		    #minorKey: #codePaneSpec
+		  )
 "/                 #(#CodeViewSpec
 "/                    #name: 'CodeView'
 "/                    #model: #codeHolder
@@ -4941,16 +5045,16 @@
 "/              #postBuildCallback: #postBuildCodeView:
 "/              #modifiedChannel: #codeModifiedHolder
 "/                  )
-                 )
-
-              )
-              #handles: #(#Any 0.3 1.0)
-              postBuildCallback: postBuildTabContentView:
-
-            )
-           )
-
-        )
+		 )
+
+	      )
+	      #handles: #(#Any 0.3 1.0)
+	      postBuildCallback: postBuildTabContentView:
+
+	    )
+	   )
+
+	)
       )
 
     "Modified: / 01-03-2000 / 11:59:28 / cg"
@@ -4971,226 +5075,226 @@
 
     <resource: #canvas>
 
-    ^ 
+    ^
      #(FullSpec
-        name: smallLintByRuleResultBrowserSpec
-        window: 
+	name: smallLintByRuleResultBrowserSpec
+	window:
        (WindowSpec
-          label: 'SmallLintByClassResultBrowser'
-          name: 'SmallLintByClassResultBrowser'
-          min: (Point 0 0)
-          bounds: (Rectangle 0 0 775 579)
-        )
-        component: 
+	  label: 'SmallLintByClassResultBrowser'
+	  name: 'SmallLintByClassResultBrowser'
+	  min: (Point 0 0)
+	  bounds: (Rectangle 0 0 775 579)
+	)
+	component:
        (SpecCollection
-          collection: (
-           (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )
-           (VariableVerticalPanelSpec
-              name: 'NavigatorAndCodePane'
-              layout: (LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              showHandle: false
-              snapMode: both
-              handlePosition: left
-              component: 
-             (SpecCollection
-                collection: (
-                 (ViewSpec
-                    name: 'NavigatorAndDetail'
-                    component: 
-                   (SpecCollection
-                      collection: (
-                       (VariableHorizontalPanelSpec
-                          name: 'Lists'
-                          layout: (LayoutFrame 0 0 0 0 0 1 0 1)
-                          component: 
-                         (SpecCollection
-                            collection: (
-                             (VariableVerticalPanelSpec
-                                name: 'RuleListPanel'
-                                component: 
-                               (SpecCollection
-                                  collection: (
-                                   (SubCanvasSpec
-                                      name: 'RuleList'
-                                      majorKey: #'Tools::LintRuleList'
-                                      subAspectHolders: 
-                                     (Array
-                                        
-                                       (SubChannelInfoSpec
-                                          subAspect: inGeneratorHolder
-                                          aspect: lintRuleListGenerator
-                                        ) 
-                                       (SubChannelInfoSpec
-                                          subAspect: outGeneratorHolder
-                                          aspect: classListGenerator
-                                        )
-                                        
-                                       (SubChannelInfoSpec
-                                          subAspect: selectionHolder
-                                          aspect: selectedLintRules
-                                        )
-                                      )
-                                      createNewApplication: true
-                                      createNewBuilder: true
-                                    )
-                                   )
-                                 
-                                )
-                                handles: (Any 1.0)
-                              )
-                             (TransparentBoxSpec
-                                name: 'ClassListBox'
-                                component: 
-                               (SpecCollection
-                                  collection: (
-                                   (SubCanvasSpec
-                                      name: 'ClassList'
-                                      layout: (LayoutFrame 0 0 0 0 0 1 -25 1)
-                                      majorKey: ClassList
-                                      subAspectHolders: 
-                                     (Array
-                                        
-                                       (SubChannelInfoSpec
-                                          subAspect: doubleClickChannel
-                                          callBack: classDoubleClicked
-                                        ) 
-                                       (SubChannelInfoSpec
-                                          subAspect: immediateUpdate
-                                          aspect: immediateUpdate
-                                        )
-                                        
-                                       (SubChannelInfoSpec
-                                          subAspect: meta
-                                          aspect: meta
-                                        ) 
-                                       (SubChannelInfoSpec
-                                          subAspect: inGeneratorHolder
-                                          aspect: classListGenerator
-                                        )
-                                        
-                                       (SubChannelInfoSpec
-                                          subAspect: menuHolder
-                                          aspect: classMenu
-                                        ) 
-                                       (SubChannelInfoSpec
-                                          subAspect: selectedClasses
-                                          aspect: selectedClasses
-                                          callBack: classSelectionChanged
-                                        )
-                                        
-                                       (SubChannelInfoSpec
-                                          subAspect: selectionChangeCondition
-                                          aspect: selectionChangeConditionHolder
-                                        )
-                                      )
-                                      createNewApplication: true
-                                      createNewBuilder: true
-                                    )
-                                   (SubCanvasSpec
-                                      name: 'MetaToggles'
-                                      layout: (LayoutFrame 5 0 -25 1 -5 1 0 1)
-                                      hasHorizontalScrollBar: false
-                                      hasVerticalScrollBar: false
-                                      majorKey: #'Tools::ClassList'
-                                      minorKey: metaSpec
-                                      createNewBuilder: false
-                                    )
-                                   )
-                                 
-                                )
-                              )
-                             (SubCanvasSpec
-                                name: 'MethodList'
-                                majorKey: MethodList
-                                subAspectHolders: 
-                               (Array
-                                  
-                                 (SubChannelInfoSpec
-                                    subAspect: doubleClickChannel
-                                    callBack: methodDoubleClicked
-                                  ) 
-                                 (SubChannelInfoSpec
-                                    subAspect: immediateUpdate
-                                    aspect: immediateUpdate
-                                  )
-                                  
-                                 (SubChannelInfoSpec
-                                    subAspect: inGeneratorHolder
-                                    aspect: selectorListGenerator
-                                  ) 
-                                 (SubChannelInfoSpec
-                                    subAspect: menuHolder
-                                    aspect: methodListPopUpMenu
-                                  )
-                                  
-                                 (SubChannelInfoSpec
-                                    subAspect: packageFilter
-                                    aspect: packageFilter
-                                  ) 
-                                 (SubChannelInfoSpec
-                                    subAspect: selectedMethods
-                                    aspect: selectedMethods
-                                    callBack: methodsSelectionChanged
-                                  )
-                                  
-                                 (SubChannelInfoSpec
-                                    subAspect: selectionChangeCondition
-                                    aspect: selectionChangeConditionHolder
-                                  )
-                                )
-                                createNewApplication: true
-                                createNewBuilder: true
-                              )
-                             )
-                           
-                          )
-                          handles: (Any 0.33 0.67 1.0)
-                        )
-                       )
-                     
-                    )
-                  )
-                 (SubCanvasSpec
-                    name: 'RuleDesc'
-                    hasHorizontalScrollBar: false
-                    hasVerticalScrollBar: false
-                    majorKey: #'Tools::LintRuleDetail'
-                    subAspectHolders: 
-                   (Array
-                      
-                     (SubChannelInfoSpec
-                        subAspect: ruleHolder
-                        aspect: theSingleSelectedLintRuleHolder
-                      )
-                    )
-                    createNewApplication: true
-                    createNewBuilder: true
-                  )
-                 (SubCanvasSpec
-                    name: 'CodePane'
-                    autoHideScrollBars: false
-                    majorKey: NewSystemBrowser
-                    minorKey: codePaneSpec
-                    createNewBuilder: false
-                  )
-                 )
-               
-              )
-              handles: (Any 0.333333333333333 0.455958549222798 1.0)
-              postBuildCallback: postBuildTabContentView:
-            )
-           )
-         
-        )
+	  collection: (
+	   (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+	   (VariableVerticalPanelSpec
+	      name: 'NavigatorAndCodePane'
+	      layout: (LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      showHandle: false
+	      snapMode: both
+	      handlePosition: left
+	      component:
+	     (SpecCollection
+		collection: (
+		 (ViewSpec
+		    name: 'NavigatorAndDetail'
+		    component:
+		   (SpecCollection
+		      collection: (
+		       (VariableHorizontalPanelSpec
+			  name: 'Lists'
+			  layout: (LayoutFrame 0 0 0 0 0 1 0 1)
+			  component:
+			 (SpecCollection
+			    collection: (
+			     (VariableVerticalPanelSpec
+				name: 'RuleListPanel'
+				component:
+			       (SpecCollection
+				  collection: (
+				   (SubCanvasSpec
+				      name: 'RuleList'
+				      majorKey: #'Tools::LintRuleList'
+				      subAspectHolders:
+				     (Array
+
+				       (SubChannelInfoSpec
+					  subAspect: inGeneratorHolder
+					  aspect: lintRuleListGenerator
+					)
+				       (SubChannelInfoSpec
+					  subAspect: outGeneratorHolder
+					  aspect: classListGenerator
+					)
+
+				       (SubChannelInfoSpec
+					  subAspect: selectionHolder
+					  aspect: selectedLintRules
+					)
+				      )
+				      createNewApplication: true
+				      createNewBuilder: true
+				    )
+				   )
+
+				)
+				handles: (Any 1.0)
+			      )
+			     (TransparentBoxSpec
+				name: 'ClassListBox'
+				component:
+			       (SpecCollection
+				  collection: (
+				   (SubCanvasSpec
+				      name: 'ClassList'
+				      layout: (LayoutFrame 0 0 0 0 0 1 -25 1)
+				      majorKey: ClassList
+				      subAspectHolders:
+				     (Array
+
+				       (SubChannelInfoSpec
+					  subAspect: doubleClickChannel
+					  callBack: classDoubleClicked
+					)
+				       (SubChannelInfoSpec
+					  subAspect: immediateUpdate
+					  aspect: immediateUpdate
+					)
+
+				       (SubChannelInfoSpec
+					  subAspect: meta
+					  aspect: meta
+					)
+				       (SubChannelInfoSpec
+					  subAspect: inGeneratorHolder
+					  aspect: classListGenerator
+					)
+
+				       (SubChannelInfoSpec
+					  subAspect: menuHolder
+					  aspect: classMenu
+					)
+				       (SubChannelInfoSpec
+					  subAspect: selectedClasses
+					  aspect: selectedClasses
+					  callBack: classSelectionChanged
+					)
+
+				       (SubChannelInfoSpec
+					  subAspect: selectionChangeCondition
+					  aspect: selectionChangeConditionHolder
+					)
+				      )
+				      createNewApplication: true
+				      createNewBuilder: true
+				    )
+				   (SubCanvasSpec
+				      name: 'MetaToggles'
+				      layout: (LayoutFrame 5 0 -25 1 -5 1 0 1)
+				      hasHorizontalScrollBar: false
+				      hasVerticalScrollBar: false
+				      majorKey: #'Tools::ClassList'
+				      minorKey: metaSpec
+				      createNewBuilder: false
+				    )
+				   )
+
+				)
+			      )
+			     (SubCanvasSpec
+				name: 'MethodList'
+				majorKey: MethodList
+				subAspectHolders:
+			       (Array
+
+				 (SubChannelInfoSpec
+				    subAspect: doubleClickChannel
+				    callBack: methodDoubleClicked
+				  )
+				 (SubChannelInfoSpec
+				    subAspect: immediateUpdate
+				    aspect: immediateUpdate
+				  )
+
+				 (SubChannelInfoSpec
+				    subAspect: inGeneratorHolder
+				    aspect: selectorListGenerator
+				  )
+				 (SubChannelInfoSpec
+				    subAspect: menuHolder
+				    aspect: methodListPopUpMenu
+				  )
+
+				 (SubChannelInfoSpec
+				    subAspect: packageFilter
+				    aspect: packageFilter
+				  )
+				 (SubChannelInfoSpec
+				    subAspect: selectedMethods
+				    aspect: selectedMethods
+				    callBack: methodsSelectionChanged
+				  )
+
+				 (SubChannelInfoSpec
+				    subAspect: selectionChangeCondition
+				    aspect: selectionChangeConditionHolder
+				  )
+				)
+				createNewApplication: true
+				createNewBuilder: true
+			      )
+			     )
+
+			  )
+			  handles: (Any 0.33 0.67 1.0)
+			)
+		       )
+
+		    )
+		  )
+		 (SubCanvasSpec
+		    name: 'RuleDesc'
+		    hasHorizontalScrollBar: false
+		    hasVerticalScrollBar: false
+		    majorKey: #'Tools::LintRuleDetail'
+		    subAspectHolders:
+		   (Array
+
+		     (SubChannelInfoSpec
+			subAspect: ruleHolder
+			aspect: theSingleSelectedLintRuleHolder
+		      )
+		    )
+		    createNewApplication: true
+		    createNewBuilder: true
+		  )
+		 (SubCanvasSpec
+		    name: 'CodePane'
+		    autoHideScrollBars: false
+		    majorKey: NewSystemBrowser
+		    minorKey: codePaneSpec
+		    createNewBuilder: false
+		  )
+		 )
+
+	      )
+	      handles: (Any 0.333333333333333 0.455958549222798 1.0)
+	      postBuildCallback: postBuildTabContentView:
+	    )
+	   )
+
+	)
       )
 !
 
@@ -5208,82 +5312,82 @@
 
     <resource: #canvas>
 
-    ^ 
+    ^
      #(FullSpec
-        name: visualProfilerSpec
-        window: 
+	name: visualProfilerSpec
+	window:
        (WindowSpec
-          label: 'SystemBrowser'
-          name: 'SystemBrowser'
-          min: (Point 0 0)
-          bounds: (Rectangle 0 0 462 300)
-          icon: defaultIcon
-        )
-        component: 
+	  label: 'SystemBrowser'
+	  name: 'SystemBrowser'
+	  min: (Point 0 0)
+	  bounds: (Rectangle 0 0 462 300)
+	  icon: defaultIcon
+	)
+	component:
        (SpecCollection
-          collection: (
-            (SubCanvasSpec
-              name: 'MessagePane'
-              layout: (LayoutFrame 0 0 0 0 0 1 40 0)
-              initiallyInvisible: true
-              hasHorizontalScrollBar: false
-              hasVerticalScrollBar: false
-              specHolder: messageSpecHolder
-              createNewBuilder: false
-              postBuildCallback: postBuildMessagePane:
-            )            
-
-           (VariableVerticalPanelSpec
-              name: 'VariableVerticalPanel1'
-              layout: (LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
-              barWidth: 2
-              showHandle: false
-              snapMode: both
-              handlePosition: left
-              component: 
-             (SpecCollection
-                collection: (
-                 (SubCanvasSpec
-                    name: 'VisualProfiler'
-                    autoHideScrollBars: false
-                    majorKey: #'Tools::VisualProfilerCanvas'
-                    minorKey: windowSpec
-                    subAspectHolders: 
-                   (Array
-                      
-                     (SubChannelInfoSpec
-                        subAspect: packageFilter
-                        aspect: packageFilter
-                      ) 
-                     (SubChannelInfoSpec
-                        subAspect: profilerStatistics
-                        aspect: profilerStatistics
-                      )
-                      
-                     (SubChannelInfoSpec
-                        subAspect: selectedMethods
-                        aspect: selectedMethods
-                      )
-                    )
-                    createNewApplication: true
-                    createNewBuilder: true
-                  )
-                 (SubCanvasSpec
-                    name: 'CodePane'
-                    autoHideScrollBars: false
-                    majorKey: NewSystemBrowser
-                    minorKey: codePaneSpec
-                  )
-                 )
-               
-              )
-              handles: (Any 0.5 1.0)
-              postBuildCallback: postBuildTabContentView:
-
-            )
-           )
-         
-        )
+	  collection: (
+	    (SubCanvasSpec
+	      name: 'MessagePane'
+	      layout: (LayoutFrame 0 0 0 0 0 1 40 0)
+	      initiallyInvisible: true
+	      hasHorizontalScrollBar: false
+	      hasVerticalScrollBar: false
+	      specHolder: messageSpecHolder
+	      createNewBuilder: false
+	      postBuildCallback: postBuildMessagePane:
+	    )
+
+	   (VariableVerticalPanelSpec
+	      name: 'VariableVerticalPanel1'
+	      layout: (LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
+	      barWidth: 2
+	      showHandle: false
+	      snapMode: both
+	      handlePosition: left
+	      component:
+	     (SpecCollection
+		collection: (
+		 (SubCanvasSpec
+		    name: 'VisualProfiler'
+		    autoHideScrollBars: false
+		    majorKey: #'Tools::VisualProfilerCanvas'
+		    minorKey: windowSpec
+		    subAspectHolders:
+		   (Array
+
+		     (SubChannelInfoSpec
+			subAspect: packageFilter
+			aspect: packageFilter
+		      )
+		     (SubChannelInfoSpec
+			subAspect: profilerStatistics
+			aspect: profilerStatistics
+		      )
+
+		     (SubChannelInfoSpec
+			subAspect: selectedMethods
+			aspect: selectedMethods
+		      )
+		    )
+		    createNewApplication: true
+		    createNewBuilder: true
+		  )
+		 (SubCanvasSpec
+		    name: 'CodePane'
+		    autoHideScrollBars: false
+		    majorKey: NewSystemBrowser
+		    minorKey: codePaneSpec
+		  )
+		 )
+
+	      )
+	      handles: (Any 0.5 1.0)
+	      postBuildCallback: postBuildTabContentView:
+
+	    )
+	   )
+
+	)
       )
 
     "Modified: / 09-10-2007 / 21:54:57 / janfrog"
@@ -5292,10 +5396,10 @@
 
 windowSpec
     "/    ^ self browserWindowSpec
-    
-    ^ UserPreferences current webBrowserLikeLayout 
-        ifTrue:[ self pagedWindowSpec ]
-        ifFalse:[ self noteBookWindowSpec ]
+
+    ^ UserPreferences current webBrowserLikeLayout
+	ifTrue:[ self pagedWindowSpec ]
+	ifFalse:[ self noteBookWindowSpec ]
 
     "Modified: / 05-02-2000 / 12:23:55 / cg"
     "Modified: / 07-06-2011 / 14:39:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -5319,242 +5423,242 @@
 
     ^
      #(#FullSpec
-        #name: #repositoryConsistencyDialogSpec
-        #window:
+	#name: #repositoryConsistencyDialogSpec
+	#window:
        #(#WindowSpec
-          #label: 'Repository Consistency Check'
-          #name: 'Repository Consistency Check'
-          #min: #(#Point 10 10)
-          #max: #(#Point 1280 1024)
-          #bounds: #(#Rectangle 16 46 316 492)
-        )
-        #component:
+	  #label: 'Repository Consistency Check'
+	  #name: 'Repository Consistency Check'
+	  #min: #(#Point 10 10)
+	  #max: #(#Point 1280 1024)
+	  #bounds: #(#Rectangle 16 46 316 492)
+	)
+	#component:
        #(#SpecCollection
-          #collection: #(
-           #(#LabelSpec
-              #label: 'Repository Consistency Check Report:'
-              #name: 'Label1'
-              #layout: #(#LayoutFrame 0 0 0 0 0 1 33 0)
-              #translateLabel: true
-            )
-           #(#VerticalPanelViewSpec
-              #name: 'VerticalPanel1'
-              #layout: #(#LayoutFrame 0 0.0 34 0.0 0 1.0 -31 1.0)
-              #horizontalLayout: #fit
-              #verticalLayout: #fit
-              #horizontalSpace: 3
-              #verticalSpace: 3
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#ViewSpec
-                    #name: 'Box1'
-                    #visibilityChannel: #classesWithoutContainerBoxVisible
-                    #component:
-                   #(#SpecCollection
-                      #collection: #(
-                       #(#DividerSpec
-                          #name: 'Separator1'
-                          #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 4 0)
-                        )
-                       #(#LabelSpec
-                          #label: 'Classes without Repository Container:'
-                          #name: 'Label2'
-                          #layout: #(#LayoutFrame 0 0.0 5 0 0 1.0 27 0)
-                          #translateLabel: true
-                          #adjust: #left
-                          #menu: #classesWithMissingContainerPopupMenu
-                          #performer: #dialogMenuPerformer
-                        )
-                       #(#SequenceViewSpec
-                          #name: 'List1'
-                          #layout: #(#LayoutFrame 0 0.0 28 0 0 1.0 0 1)
-                          #model: #selectedClassesWithMissingContainer
-                          #menu: #classesWithMissingContainerPopupMenu
-                          #performer: #dialogMenuPerformer
-                          #hasHorizontalScrollBar: true
-                          #hasVerticalScrollBar: true
-                          #isMultiSelect: true
-                          #useIndex: true
-                          #sequenceList: #listOfClassesWithMissingContainer
-                        )
-                       )
-
-                    )
-                    #extent: #(#Point 300 74)
-                  )
-                 #(#ViewSpec
-                    #name: 'Box2'
-                    #visibilityChannel: #classesWithInvalidInfoBoxVisible
-                    #component:
-                   #(#SpecCollection
-                      #collection: #(
-                       #(#DividerSpec
-                          #name: 'Separator2'
-                          #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 4 0)
-                        )
-                       #(#LabelSpec
-                          #label: 'Classes with Invalid Repository Info:'
-                          #name: 'Label3'
-                          #layout: #(#LayoutFrame 0 0.0 5 0 0 1.0 27 0)
-                          #translateLabel: true
-                          #adjust: #left
-                          #menu: #classesWithInvalidInfoPopupMenu
-                          #performer: #dialogMenuPerformer
-                        )
-                       #(#SequenceViewSpec
-                          #name: 'List2'
-                          #layout: #(#LayoutFrame 0 0.0 28 0 0 1.0 0 1)
-                          #model: #selectedClassesWithRepositoryMismatches
-                          #menu: #classesWithInvalidInfoPopupMenu
-                          #performer: #dialogMenuPerformer
-                          #hasHorizontalScrollBar: true
-                          #hasVerticalScrollBar: true
-                          #isMultiSelect: true
-                          #useIndex: true
-                          #sequenceList: #listOfClassesWithRepositoryMismatches
-                        )
-                       )
-
-                    )
-                    #extent: #(#Point 300 74)
-                  )
-                 #(#ViewSpec
-                    #name: 'Box3'
-                    #visibilityChannel: #obsoleteContainersBoxVisible
-                    #component:
-                   #(#SpecCollection
-                      #collection: #(
-                       #(#DividerSpec
-                          #name: 'Separator3'
-                          #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 4 0)
-                        )
-                       #(#LabelSpec
-                          #label: 'Containers without class: (need checkOut ?)'
-                          #name: 'Label4'
-                          #layout: #(#LayoutFrame 0 0.0 5 0 0 1.0 27 0)
-                          #translateLabel: true
-                          #adjust: #left
-                          #menu: #obsoleteContainersPopupMenu
-                          #performer: #dialogMenuPerformer
-                        )
-                       #(#SequenceViewSpec
-                          #name: 'List3'
-                          #layout: #(#LayoutFrame 0 0.0 28 0 0 1.0 0 1)
-                          #model: #selectedObsoleteContainers
-                          #menu: #obsoleteContainersPopupMenu
-                          #performer: #dialogMenuPerformer
-                          #hasHorizontalScrollBar: true
-                          #hasVerticalScrollBar: true
-                          #isMultiSelect: true
-                          #useIndex: true
-                          #sequenceList: #listOfObsoleteContainers
-                        )
-                       )
-
-                    )
-                    #extent: #(#Point 300 73)
-                  )
-                 #(#ViewSpec
-                    #name: 'Box4'
-                    #visibilityChannel: #classesWhichHaveBeenModifiedBoxVisible
-                    #component:
-                   #(#SpecCollection
-                      #collection: #(
-                       #(#DividerSpec
-                          #name: 'Separator4'
-                          #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 4 0)
-                        )
-                       #(#LabelSpec
-                          #label: 'Modified Classes (need checkIn ?):'
-                          #name: 'Label5'
-                          #layout: #(#LayoutFrame 0 0.0 5 0 0 1.0 27 0)
-                          #translateLabel: true
-                          #adjust: #left
-                          #menu: #classesWhichHaveBeenModifiedPopupMenu
-                          #performer: #dialogMenuPerformer
-                        )
-                       #(#SequenceViewSpec
-                          #name: 'List4'
-                          #layout: #(#LayoutFrame 0 0.0 28 0 0 1.0 0 1)
-                          #model: #selectedClassesWhichHaveBeenModified
-                          #menu: #classesWhichHaveBeenModifiedPopupMenu
-                          #performer: #dialogMenuPerformer
-                          #hasHorizontalScrollBar: true
-                          #hasVerticalScrollBar: true
-                          #isMultiSelect: true
-                          #useIndex: true
-                          #sequenceList: #listOfClassesWhichHaveBeenModified
-                        )
-                       )
-
-                    )
-                    #extent: #(#Point 300 74)
-                  )
-                 #(#ViewSpec
-                    #name: 'Box5'
-                    #visibilityChannel: #classesWithNewerVersionInRepositoryBoxVisible
-                    #component:
-                   #(#SpecCollection
-                      #collection: #(
-                       #(#DividerSpec
-                          #name: 'Separator5'
-                          #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 4 0)
-                        )
-                       #(#LabelSpec
-                          #label: 'New Version in Repository (need checkOut ?):'
-                          #name: 'Label6'
-                          #layout: #(#LayoutFrame 0 0.0 5 0 0 1.0 27 0)
-                          #translateLabel: true
-                          #adjust: #left
-                          #menu: #classesWithNewerVersionInRepositoryPopupMenu
-                          #performer: #dialogMenuPerformer
-                        )
-                       #(#SequenceViewSpec
-                          #name: 'List5'
-                          #layout: #(#LayoutFrame 0 0.0 28 0 0 1.0 0 1)
-                          #model: #selectedClassesWithNewerVersionInRepository
-                          #menu: #classesWithNewerVersionInRepositoryPopupMenu
-                          #performer: #dialogMenuPerformer
-                          #hasHorizontalScrollBar: true
-                          #hasVerticalScrollBar: true
-                          #isMultiSelect: true
-                          #useIndex: true
-                          #sequenceList: #listOfClassesWithNewerVersionInRepository
-                        )
-                       )
-
-                    )
-                    #extent: #(#Point 300 74)
-                  )
-                 )
-
-              )
-            )
-           #(#HorizontalPanelViewSpec
-              #name: 'HorizontalPanel1'
-              #layout: #(#LayoutFrame 0 0 -30 1 0 1 0 1)
-              #horizontalLayout: #center
-              #verticalLayout: #center
-              #horizontalSpace: 3
-              #verticalSpace: 3
-              #component:
-             #(#SpecCollection
-                #collection: #(
-                 #(#ActionButtonSpec
-                    #label: 'Close'
-                    #name: 'Button1'
-                    #translateLabel: true
-                    #model: #closeRequest
-                    #extent: #(#Point 125 22)
-                  )
-                 )
-
-              )
-            )
-           )
-
-        )
+	  #collection: #(
+	   #(#LabelSpec
+	      #label: 'Repository Consistency Check Report:'
+	      #name: 'Label1'
+	      #layout: #(#LayoutFrame 0 0 0 0 0 1 33 0)
+	      #translateLabel: true
+	    )
+	   #(#VerticalPanelViewSpec
+	      #name: 'VerticalPanel1'
+	      #layout: #(#LayoutFrame 0 0.0 34 0.0 0 1.0 -31 1.0)
+	      #horizontalLayout: #fit
+	      #verticalLayout: #fit
+	      #horizontalSpace: 3
+	      #verticalSpace: 3
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#ViewSpec
+		    #name: 'Box1'
+		    #visibilityChannel: #classesWithoutContainerBoxVisible
+		    #component:
+		   #(#SpecCollection
+		      #collection: #(
+		       #(#DividerSpec
+			  #name: 'Separator1'
+			  #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 4 0)
+			)
+		       #(#LabelSpec
+			  #label: 'Classes without Repository Container:'
+			  #name: 'Label2'
+			  #layout: #(#LayoutFrame 0 0.0 5 0 0 1.0 27 0)
+			  #translateLabel: true
+			  #adjust: #left
+			  #menu: #classesWithMissingContainerPopupMenu
+			  #performer: #dialogMenuPerformer
+			)
+		       #(#SequenceViewSpec
+			  #name: 'List1'
+			  #layout: #(#LayoutFrame 0 0.0 28 0 0 1.0 0 1)
+			  #model: #selectedClassesWithMissingContainer
+			  #menu: #classesWithMissingContainerPopupMenu
+			  #performer: #dialogMenuPerformer
+			  #hasHorizontalScrollBar: true
+			  #hasVerticalScrollBar: true
+			  #isMultiSelect: true
+			  #useIndex: true
+			  #sequenceList: #listOfClassesWithMissingContainer
+			)
+		       )
+
+		    )
+		    #extent: #(#Point 300 74)
+		  )
+		 #(#ViewSpec
+		    #name: 'Box2'
+		    #visibilityChannel: #classesWithInvalidInfoBoxVisible
+		    #component:
+		   #(#SpecCollection
+		      #collection: #(
+		       #(#DividerSpec
+			  #name: 'Separator2'
+			  #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 4 0)
+			)
+		       #(#LabelSpec
+			  #label: 'Classes with Invalid Repository Info:'
+			  #name: 'Label3'
+			  #layout: #(#LayoutFrame 0 0.0 5 0 0 1.0 27 0)
+			  #translateLabel: true
+			  #adjust: #left
+			  #menu: #classesWithInvalidInfoPopupMenu
+			  #performer: #dialogMenuPerformer
+			)
+		       #(#SequenceViewSpec
+			  #name: 'List2'
+			  #layout: #(#LayoutFrame 0 0.0 28 0 0 1.0 0 1)
+			  #model: #selectedClassesWithRepositoryMismatches
+			  #menu: #classesWithInvalidInfoPopupMenu
+			  #performer: #dialogMenuPerformer
+			  #hasHorizontalScrollBar: true
+			  #hasVerticalScrollBar: true
+			  #isMultiSelect: true
+			  #useIndex: true
+			  #sequenceList: #listOfClassesWithRepositoryMismatches
+			)
+		       )
+
+		    )
+		    #extent: #(#Point 300 74)
+		  )
+		 #(#ViewSpec
+		    #name: 'Box3'
+		    #visibilityChannel: #obsoleteContainersBoxVisible
+		    #component:
+		   #(#SpecCollection
+		      #collection: #(
+		       #(#DividerSpec
+			  #name: 'Separator3'
+			  #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 4 0)
+			)
+		       #(#LabelSpec
+			  #label: 'Containers without class: (need checkOut ?)'
+			  #name: 'Label4'
+			  #layout: #(#LayoutFrame 0 0.0 5 0 0 1.0 27 0)
+			  #translateLabel: true
+			  #adjust: #left
+			  #menu: #obsoleteContainersPopupMenu
+			  #performer: #dialogMenuPerformer
+			)
+		       #(#SequenceViewSpec
+			  #name: 'List3'
+			  #layout: #(#LayoutFrame 0 0.0 28 0 0 1.0 0 1)
+			  #model: #selectedObsoleteContainers
+			  #menu: #obsoleteContainersPopupMenu
+			  #performer: #dialogMenuPerformer
+			  #hasHorizontalScrollBar: true
+			  #hasVerticalScrollBar: true
+			  #isMultiSelect: true
+			  #useIndex: true
+			  #sequenceList: #listOfObsoleteContainers
+			)
+		       )
+
+		    )
+		    #extent: #(#Point 300 73)
+		  )
+		 #(#ViewSpec
+		    #name: 'Box4'
+		    #visibilityChannel: #classesWhichHaveBeenModifiedBoxVisible
+		    #component:
+		   #(#SpecCollection
+		      #collection: #(
+		       #(#DividerSpec
+			  #name: 'Separator4'
+			  #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 4 0)
+			)
+		       #(#LabelSpec
+			  #label: 'Modified Classes (need checkIn ?):'
+			  #name: 'Label5'
+			  #layout: #(#LayoutFrame 0 0.0 5 0 0 1.0 27 0)
+			  #translateLabel: true
+			  #adjust: #left
+			  #menu: #classesWhichHaveBeenModifiedPopupMenu
+			  #performer: #dialogMenuPerformer
+			)
+		       #(#SequenceViewSpec
+			  #name: 'List4'
+			  #layout: #(#LayoutFrame 0 0.0 28 0 0 1.0 0 1)
+			  #model: #selectedClassesWhichHaveBeenModified
+			  #menu: #classesWhichHaveBeenModifiedPopupMenu
+			  #performer: #dialogMenuPerformer
+			  #hasHorizontalScrollBar: true
+			  #hasVerticalScrollBar: true
+			  #isMultiSelect: true
+			  #useIndex: true
+			  #sequenceList: #listOfClassesWhichHaveBeenModified
+			)
+		       )
+
+		    )
+		    #extent: #(#Point 300 74)
+		  )
+		 #(#ViewSpec
+		    #name: 'Box5'
+		    #visibilityChannel: #classesWithNewerVersionInRepositoryBoxVisible
+		    #component:
+		   #(#SpecCollection
+		      #collection: #(
+		       #(#DividerSpec
+			  #name: 'Separator5'
+			  #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 4 0)
+			)
+		       #(#LabelSpec
+			  #label: 'New Version in Repository (need checkOut ?):'
+			  #name: 'Label6'
+			  #layout: #(#LayoutFrame 0 0.0 5 0 0 1.0 27 0)
+			  #translateLabel: true
+			  #adjust: #left
+			  #menu: #classesWithNewerVersionInRepositoryPopupMenu
+			  #performer: #dialogMenuPerformer
+			)
+		       #(#SequenceViewSpec
+			  #name: 'List5'
+			  #layout: #(#LayoutFrame 0 0.0 28 0 0 1.0 0 1)
+			  #model: #selectedClassesWithNewerVersionInRepository
+			  #menu: #classesWithNewerVersionInRepositoryPopupMenu
+			  #performer: #dialogMenuPerformer
+			  #hasHorizontalScrollBar: true
+			  #hasVerticalScrollBar: true
+			  #isMultiSelect: true
+			  #useIndex: true
+			  #sequenceList: #listOfClassesWithNewerVersionInRepository
+			)
+		       )
+
+		    )
+		    #extent: #(#Point 300 74)
+		  )
+		 )
+
+	      )
+	    )
+	   #(#HorizontalPanelViewSpec
+	      #name: 'HorizontalPanel1'
+	      #layout: #(#LayoutFrame 0 0 -30 1 0 1 0 1)
+	      #horizontalLayout: #center
+	      #verticalLayout: #center
+	      #horizontalSpace: 3
+	      #verticalSpace: 3
+	      #component:
+	     #(#SpecCollection
+		#collection: #(
+		 #(#ActionButtonSpec
+		    #label: 'Close'
+		    #name: 'Button1'
+		    #translateLabel: true
+		    #model: #closeRequest
+		    #extent: #(#Point 125 22)
+		  )
+		 )
+
+	      )
+	    )
+	   )
+
+	)
       )
 ! !
 
@@ -5574,40 +5678,40 @@
 
     <resource: #canvas>
 
-    ^ 
+    ^
      #(FullSpec
-        name: messageInfoSpec
-        window: 
+	name: messageInfoSpec
+	window:
        (WindowSpec
-          label: 'MessageInfo'
-          name: 'MessageInfo'
-          min: (Point 10 10)
-          bounds: (Rectangle 0 0 800 40)
-          backgroundColor: (Color 100.0 78.0392156862745 22.7450980392157)
-          forceRecursiveBackgroundOfDefaultBackground: true
-        )
-        component: 
+	  label: 'MessageInfo'
+	  name: 'MessageInfo'
+	  min: (Point 10 10)
+	  bounds: (Rectangle 0 0 800 40)
+	  backgroundColor: (Color 100.0 78.0392156862745 22.7450980392157)
+	  forceRecursiveBackgroundOfDefaultBackground: true
+	)
+	component:
        (SpecCollection
-          collection: (
-           (LabelSpec
-              label: 'Label'
-              name: 'Message'
-              layout: (LayoutFrame 10 0 -10 0.5 -90 1 10 0.5)
-              backgroundColor: (Color 100.0 78.0392156862745 22.7450980392157)
-              translateLabel: true
-              labelChannel: messageHolder
-              adjust: left
-            )
-           (ActionButtonSpec
-              label: 'OK'
-              name: 'OK'
-              layout: (LayoutFrame -80 1 -12 0.5 -12 1 12 0.5)
-              translateLabel: true
-              model: hideMessagePane
-            )
-           )
-         
-        )
+	  collection: (
+	   (LabelSpec
+	      label: 'Label'
+	      name: 'Message'
+	      layout: (LayoutFrame 10 0 -10 0.5 -90 1 10 0.5)
+	      backgroundColor: (Color 100.0 78.0392156862745 22.7450980392157)
+	      translateLabel: true
+	      labelChannel: messageHolder
+	      adjust: left
+	    )
+	   (ActionButtonSpec
+	      label: 'OK'
+	      name: 'OK'
+	      layout: (LayoutFrame -80 1 -12 0.5 -12 1 12 0.5)
+	      translateLabel: true
+	      model: hideMessagePane
+	    )
+	   )
+
+	)
       )
 !
 
@@ -5625,48 +5729,48 @@
 
     <resource: #canvas>
 
-    ^ 
+    ^
      #(FullSpec
-        name: progressInfoSpec
-        window: 
+	name: progressInfoSpec
+	window:
        (WindowSpec
-          label: 'ProgressInfo'
-          name: 'ProgressInfo'
-          min: (Point 10 10)
-          bounds: (Rectangle 0 0 800 40)
-          backgroundColor: (Color 100.0 78.0392156862745 22.7450980392157)
-          forceRecursiveBackgroundOfDefaultBackground: true
-        )
-        component: 
+	  label: 'ProgressInfo'
+	  name: 'ProgressInfo'
+	  min: (Point 10 10)
+	  bounds: (Rectangle 0 0 800 40)
+	  backgroundColor: (Color 100.0 78.0392156862745 22.7450980392157)
+	  forceRecursiveBackgroundOfDefaultBackground: true
+	)
+	component:
        (SpecCollection
-          collection: (
-           (LabelSpec
-              label: 'Label'
-              name: 'Message'
-              layout: (LayoutFrame 10 0 0 0 -90 1 20 0)
-              backgroundColor: (Color 100.0 78.0392156862745 22.7450980392157)
-              translateLabel: true
-              labelChannel: messageHolder
-              adjust: left
-            )
-           (ProgressIndicatorSpec
-              name: 'ProgressIndicator'
-              layout: (LayoutFrame 10 0 -20 1 -133 1 -3 1)
-              model: progressHolder
-              foregroundColor: (Color 52.156862745098 37.2549019607843 0.0)
-              backgroundColor: (Color 100.0 91.3725490196078 70.1960784313726)
-            )
-           (ActionButtonSpec
-              label: 'Abort'
-              name: 'Abort'
-              layout: (AlignmentOrigin -12 1 0 0.5 1 0.5)
-              translateLabel: true
-              resizeForLabel: true
-              model: hideMessagePaneAndAbort
-            )
-           )
-         
-        )
+	  collection: (
+	   (LabelSpec
+	      label: 'Label'
+	      name: 'Message'
+	      layout: (LayoutFrame 10 0 0 0 -90 1 20 0)
+	      backgroundColor: (Color 100.0 78.0392156862745 22.7450980392157)
+	      translateLabel: true
+	      labelChannel: messageHolder
+	      adjust: left
+	    )
+	   (ProgressIndicatorSpec
+	      name: 'ProgressIndicator'
+	      layout: (LayoutFrame 10 0 -20 1 -133 1 -3 1)
+	      model: progressHolder
+	      foregroundColor: (Color 52.156862745098 37.2549019607843 0.0)
+	      backgroundColor: (Color 100.0 91.3725490196078 70.1960784313726)
+	    )
+	   (ActionButtonSpec
+	      label: 'Abort'
+	      name: 'Abort'
+	      layout: (AlignmentOrigin -12 1 0 0.5 1 0.5)
+	      translateLabel: true
+	      resizeForLabel: true
+	      model: hideMessagePaneAndAbort
+	    )
+	   )
+
+	)
       )
 ! !
 
@@ -5687,416 +5791,416 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'Clone'
-            itemValue: browseMenuClone
-            translateLabel: true
-            isVisible: shiftNotPressedHolder
-            shortcutKey: Ctrln
-          )
-         (MenuItem
-            label: 'Old SystemBrowser on Class'
-            itemValue: browseMenuClone
-            translateLabel: true
-            isVisible: shiftPressedHolder
-          )
-         (MenuItem
-            label: '-'
-            isVisible: false
-          )
-         (MenuItem
-            label: 'Class...'
-            itemValue: browseMenuOpenInClass
-            translateLabel: true
-          )
-         (MenuItem
-            label: 'Classes'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  label: 'With Name Matching...'
-                  itemValue: browseMenuClassesWithNameMatching
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'In Current ChangeSet'
-                  itemValue: browseMenuClassesInCurrentChangeSet
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'In All ChangeSets'
-                  itemValue: browseMenuClassesInAllChangeSets
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'Which were Autoloaded'
-                  itemValue: browseMenuAutoloadedClasses
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'With Extensions'
-                  itemValue: browseMenuClassesWithExtensions
-                  translateLabel: true
-                  isVisible: false
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'Recently Opened Applications'
-                  itemValue: browseMenuClassesOfRecentlyOpenedApplications
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'All Subclasses of...'
-                  itemValue: browseMenuAllSubclassesOf
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'All Applications'
-                  itemValue: browseMenuApplicationClasses
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'All Web Services'
-                  itemValue: browseMenuHTTPServiceClasses
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'All TestCases'
-                  itemValue: browseMenuTestCaseClasses
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'All Shared Pools'
-                  itemValue: browseMenuSharedPoolClasses
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'Without Documentation'
-                  itemValue: browseMenuClassesWithoutDocumentation
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'Without Copyright'
-                  itemValue: browseMenuClassesWithoutCopyright
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'Without Examples'
-                  itemValue: browseMenuClassesWithoutExamples
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'Without CVS Repository Container'
-                  itemValue: browseMenuClassesWithoutCVSRepositoryContainer
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'Without SVN Repository Container'
-                  itemValue: browseMenuClassesWithoutSVNRepositoryContainer
-                  translateLabel: true
-                  isVisible: hasSubversionSupport
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'Defining Variable...'
-                  itemValue: browseMenuClassesDefiningVariable
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'With String in Comment/Documentation...'
-                  itemValue: browseMenuClassesWithStringInCommentOrDocumentation
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'With External Function Calls (FFI)'
-                  itemValue: browseMenuClassesWithExternalFunctionCalls
-                  translateLabel: true
-                  isVisible: false
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'With Primitive Code'
-                  itemValue: browseMenuClassesWithPrimitiveCode
-                  translateLabel: true
-                  isVisible: false
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'For which...'
-                  itemValue: browseMenuClassesWithUserFilter
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'Special'
-                  translateLabel: true
-                  submenuChannel: specialBrowseMenu
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Implementors of...'
-            itemValue: browseMenuImplementorsOf
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: 'Senders of...'
-            itemValue: browseSendersOf
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'References to Class or Global...'
-            itemValue: browseMenuReferencesToGlobal
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: 'References to Symbol...'
-            itemValue: browseMenuReferencesToSymbol
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: 'Writes to Global...'
-            itemValue: browseMenuWritesToGlobal
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Recently Changed Methods'
-            itemValue: browseMenuRecentChanges
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: 'Class Extensions'
-            itemValue: browseMenuClassExtensionsBuffer
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: 'Methods'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  label: 'Changed Methods'
-                  itemValue: browseMenuMethodsInCurrentChangeSet
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'Overwritten Methods'
-                  itemValue: browseMenuOverwrittenMethods:
-                  translateLabel: true
-                  isVisible: false
-                  argument: newBrowser
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'Unassigned Extensions'
-                  itemValue: browseMenuUnassignedMethods:
-                  translateLabel: true
-                  argument: newBrowser
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'With Break- or Tracepoint'
-                  itemValue: browseMenuMethodsWithWrap
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'With String...'
-                  itemValue: browseMenuMethodsWithString
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'With String in Help Spec...'
-                  itemValue: browseMenuMethodsWithStringInHelpSpec
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'With String in Menu Spec...'
-                  itemValue: browseMenuMethodsWithStringInMenuSpec
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'With String-Literal Matching...'
-                  itemValue: browseMenuMethodsWithStringLiteral
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'With Window Spec...'
-                  itemValue: browseMenuMethodsWithWindowSpec
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'With Menu Spec...'
-                  itemValue: browseMenuMethodsWithMenuSpec
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'With Image Spec...'
-                  itemValue: browseMenuMethodsWithImageSpec
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'With Table Spec...'
-                  itemValue: browseMenuMethodsWithTableSpec
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'With Help Spec...'
-                  itemValue: browseMenuMethodsWithHelpSpec
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'With any Resource...'
-                  itemValue: browseMenuMethodsWithResource
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'Without Comment...'
-                  itemValue: browseMenuMethodsWithoutComment
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'With Ugly Coding Style...'
-                  itemValue: browseMenuMethodsWithUglyCodingStyle
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'With Possible Leftover Debug Code...'
-                  itemValue: browseMenuMethodsWithLeftoverDebugCode
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'Deprecated'
-                  itemValue: browseMenuDeprecatedMethods
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'With Exception Handlers'
-                  itemValue: browseMenuMethodsWithExceptionHandlers
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'With Exception Raisers'
-                  itemValue: browseMenuMethodsWithExceptionRaisers
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'With Primitive Code'
-                  itemValue: browseMenuMethodsWithPrimitiveCode
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'With External Function Calls (FFI)'
-                  itemValue: browseMenuMethodsWithExternalFunctionCalls
-                  translateLabel: true
-                  isVisible: false
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'For which...'
-                  itemValue: browseMenuMethodsWithUserFilter
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'Clone'
+	    itemValue: browseMenuClone
+	    translateLabel: true
+	    isVisible: shiftNotPressedHolder
+	    shortcutKey: Ctrln
+	  )
+	 (MenuItem
+	    label: 'Old SystemBrowser on Class'
+	    itemValue: browseMenuClone
+	    translateLabel: true
+	    isVisible: shiftPressedHolder
+	  )
+	 (MenuItem
+	    label: '-'
+	    isVisible: false
+	  )
+	 (MenuItem
+	    label: 'Class...'
+	    itemValue: browseMenuOpenInClass
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: 'Classes'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  label: 'With Name Matching...'
+		  itemValue: browseMenuClassesWithNameMatching
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'In Current ChangeSet'
+		  itemValue: browseMenuClassesInCurrentChangeSet
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'In All ChangeSets'
+		  itemValue: browseMenuClassesInAllChangeSets
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'Which were Autoloaded'
+		  itemValue: browseMenuAutoloadedClasses
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'With Extensions'
+		  itemValue: browseMenuClassesWithExtensions
+		  translateLabel: true
+		  isVisible: false
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'Recently Opened Applications'
+		  itemValue: browseMenuClassesOfRecentlyOpenedApplications
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'All Subclasses of...'
+		  itemValue: browseMenuAllSubclassesOf
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'All Applications'
+		  itemValue: browseMenuApplicationClasses
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'All Web Services'
+		  itemValue: browseMenuHTTPServiceClasses
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'All TestCases'
+		  itemValue: browseMenuTestCaseClasses
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'All Shared Pools'
+		  itemValue: browseMenuSharedPoolClasses
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'Without Documentation'
+		  itemValue: browseMenuClassesWithoutDocumentation
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'Without Copyright'
+		  itemValue: browseMenuClassesWithoutCopyright
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'Without Examples'
+		  itemValue: browseMenuClassesWithoutExamples
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'Without CVS Repository Container'
+		  itemValue: browseMenuClassesWithoutCVSRepositoryContainer
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'Without SVN Repository Container'
+		  itemValue: browseMenuClassesWithoutSVNRepositoryContainer
+		  translateLabel: true
+		  isVisible: hasSubversionSupport
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'Defining Variable...'
+		  itemValue: browseMenuClassesDefiningVariable
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'With String in Comment/Documentation...'
+		  itemValue: browseMenuClassesWithStringInCommentOrDocumentation
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'With External Function Calls (FFI)'
+		  itemValue: browseMenuClassesWithExternalFunctionCalls
+		  translateLabel: true
+		  isVisible: false
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'With Primitive Code'
+		  itemValue: browseMenuClassesWithPrimitiveCode
+		  translateLabel: true
+		  isVisible: false
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'For which...'
+		  itemValue: browseMenuClassesWithUserFilter
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'Special'
+		  translateLabel: true
+		  submenuChannel: specialBrowseMenu
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Implementors of...'
+	    itemValue: browseMenuImplementorsOf
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: 'Senders of...'
+	    itemValue: browseSendersOf
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'References to Class or Global...'
+	    itemValue: browseMenuReferencesToGlobal
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: 'References to Symbol...'
+	    itemValue: browseMenuReferencesToSymbol
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: 'Writes to Global...'
+	    itemValue: browseMenuWritesToGlobal
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Recently Changed Methods'
+	    itemValue: browseMenuRecentChanges
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: 'Class Extensions'
+	    itemValue: browseMenuClassExtensionsBuffer
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: 'Methods'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  label: 'Changed Methods'
+		  itemValue: browseMenuMethodsInCurrentChangeSet
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'Overwritten Methods'
+		  itemValue: browseMenuOverwrittenMethods:
+		  translateLabel: true
+		  isVisible: false
+		  argument: newBrowser
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'Unassigned Extensions'
+		  itemValue: browseMenuUnassignedMethods:
+		  translateLabel: true
+		  argument: newBrowser
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'With Break- or Tracepoint'
+		  itemValue: browseMenuMethodsWithWrap
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'With String...'
+		  itemValue: browseMenuMethodsWithString
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'With String in Help Spec...'
+		  itemValue: browseMenuMethodsWithStringInHelpSpec
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'With String in Menu Spec...'
+		  itemValue: browseMenuMethodsWithStringInMenuSpec
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'With String-Literal Matching...'
+		  itemValue: browseMenuMethodsWithStringLiteral
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'With Window Spec...'
+		  itemValue: browseMenuMethodsWithWindowSpec
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'With Menu Spec...'
+		  itemValue: browseMenuMethodsWithMenuSpec
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'With Image Spec...'
+		  itemValue: browseMenuMethodsWithImageSpec
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'With Table Spec...'
+		  itemValue: browseMenuMethodsWithTableSpec
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'With Help Spec...'
+		  itemValue: browseMenuMethodsWithHelpSpec
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'With any Resource...'
+		  itemValue: browseMenuMethodsWithResource
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'Without Comment...'
+		  itemValue: browseMenuMethodsWithoutComment
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'With Ugly Coding Style...'
+		  itemValue: browseMenuMethodsWithUglyCodingStyle
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'With Possible Leftover Debug Code...'
+		  itemValue: browseMenuMethodsWithLeftoverDebugCode
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'Deprecated'
+		  itemValue: browseMenuDeprecatedMethods
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'With Exception Handlers'
+		  itemValue: browseMenuMethodsWithExceptionHandlers
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'With Exception Raisers'
+		  itemValue: browseMenuMethodsWithExceptionRaisers
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'With Primitive Code'
+		  itemValue: browseMenuMethodsWithPrimitiveCode
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'With External Function Calls (FFI)'
+		  itemValue: browseMenuMethodsWithExternalFunctionCalls
+		  translateLabel: true
+		  isVisible: false
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'For which...'
+		  itemValue: browseMenuMethodsWithUserFilter
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -6116,23 +6220,23 @@
 
     ^
      #(Menu
-        (
-         (MenuItem
-            label: 'Add Page'
-            itemValue: bufferMenuCreateBuffer
-            nameKey: CreateBuffer
-            translateLabel: true
-            shortcutKey: Ctrlt
-          )
-         (MenuItem
-            label: 'Remove Page'
-            itemValue: bufferMenuRemoveCurrentBuffer
-            nameKey: RemoveBuffer
-            translateLabel: true
-          )
-         )
-        nil
-        nil
+	(
+	 (MenuItem
+	    label: 'Add Page'
+	    itemValue: bufferMenuCreateBuffer
+	    nameKey: CreateBuffer
+	    translateLabel: true
+	    shortcutKey: Ctrlt
+	  )
+	 (MenuItem
+	    label: 'Remove Page'
+	    itemValue: bufferMenuRemoveCurrentBuffer
+	    nameKey: RemoveBuffer
+	    translateLabel: true
+	  )
+	 )
+	nil
+	nil
       )
 
     "Modified: / 03-08-2004 / 14:28:02 / stefan"
@@ -6152,113 +6256,41 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'Check'
-            itemValue: categoryCheckMenuSmalllintCheck:
-            translateLabel: true
-            argument: smalllintRules
-          )
-         (MenuItem
-            label: 'Check (all checks)'
-            itemValue: categoryCheckMenuSmalllintCheck:
-            translateLabel: true
-            argument: smalllintRulesAll
-          )
-         (MenuItem
-            label: 'Check (selected checks)'
-            itemValue: categoryCheckMenuSmalllintCheck:
-            translateLabel: true
-            argument: smalllintRulesFromUser
-          )
-
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'Check'
+	    itemValue: categoryMenuSmalllintCheck:
+	    translateLabel: true
+	    argument: smalllintRules
+	  )
+	 (MenuItem
+	    label: 'Check (all checks)'
+	    itemValue: categoryMenuSmalllintCheck:
+	    translateLabel: true
+	    argument: smalllintRulesAll
+	  )
+	 (MenuItem
+	    label: 'Check (selected checks)'
+	    itemValue: categoryMenuSmalllintCheck:
+	    translateLabel: true
+	    argument: smalllintRulesFromUser
+	  )
+
+	 )
+	nil
+	nil
       )
 
     "Modified: / 17-04-2010 / 11:14:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 05-05-2012 / 10:18:13 / cg"
 !
 
 categoryMenu
-    "This resource specification was automatically generated
-     by the MenuEditor of ST/X."
-
-    "Do not manually edit this!! If it is corrupted,
-     the MenuEditor may not be able to read the specification."
-
-    "
-     MenuEditor new openOnClass:Tools::NewSystemBrowser andSelector:#categoryMenu
-     (Menu new fromLiteralArrayEncoding:(Tools::NewSystemBrowser categoryMenu)) startUp
-    "
-
-    <resource: #menu>
-
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'FileOutAndRepositorySlice'
-            translateLabel: true
-            submenuChannel: categoryMenuFileOutAndRepositorySlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'DocumentationSlice'
-            translateLabel: true
-            submenuChannel: categoryMenuDocumentationSlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'SpawnSlice'
-            translateLabel: true
-            submenuChannel: categoryMenuSpawnSlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'NewAndRenameSlice'
-            nameKey: NewAndRenameSlice
-            translateLabel: true
-            submenuChannel: categoryMenuNewAndRenameSlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Static Analysis (Lint)'
-            translateLabel: true
-            submenuChannel: categoryCheckMenu
-            labelImage: (ResourceRetriever ToolbarIconLibrary lint16x16Icon 'Static Analysis (Lint)')
-          )
-         (MenuItem
-            label: 'Special'
-            translateLabel: true
-            submenuChannel: categorySpecialMenu
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Update'
-            itemValue: categoryMenuUpdate
-            translateLabel: true
-          )
-         )
-        nil
-        nil
-      )
+    ^ self categoryMenuWithoutFind
+
+    "Modified: / 31-05-2012 / 09:19:08 / cg"
 !
 
 categoryMenuDocumentationSlice
@@ -6277,46 +6309,46 @@
 
     ^
      #(Menu
-        (
-         (MenuItem
-            enabled: hasCategorySelectedHolder
-            label: 'Documentation'
-            translateLabel: true
-            submenu:
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasCategorySelectedHolder
-                  label: 'PrintOut'
-                  itemValue: categoryMenuPrintOut
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasCategorySelectedHolder
-                  label: 'PrintOut Protocol'
-                  itemValue: categoryMenuPrintOutProtocol
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasCategorySelectedHolder
-                  label: 'Save HTML Documentation In...'
-                  itemValue: categoryMenuSaveDocumentationIn
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         )
-        nil
-        nil
+	(
+	 (MenuItem
+	    enabled: hasCategorySelectedHolder
+	    label: 'Documentation'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasCategorySelectedHolder
+		  label: 'PrintOut'
+		  itemValue: categoryMenuPrintOut
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasCategorySelectedHolder
+		  label: 'PrintOut Protocol'
+		  itemValue: categoryMenuPrintOutProtocol
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasCategorySelectedHolder
+		  label: 'Save HTML Documentation In...'
+		  itemValue: categoryMenuSaveDocumentationIn
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -6335,82 +6367,82 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasCategorySelectedHolder
-            label: 'FileOut'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasCategorySelectedHolder
-                  label: 'as...'
-                  itemValue: categoryMenuFileOutAs
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasCategorySelectedAndCanFileOutXMLHolder
-                  label: 'XML as...'
-                  itemValue: categoryMenuFileOutXMLAs
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasCategorySelectedAndCanFileOutSIFHolder
-                  label: 'SIF as...'
-                  itemValue: categoryMenuFileOutSIFAs
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasCategorySelectedHolder
-                  label: 'Each in...'
-                  itemValue: categoryMenuFileOutEachIn
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasCategorySelectedAndCanFileOutXMLHolder
-                  label: 'Each XML in...'
-                  itemValue: categoryMenuFileOutEachXMLIn
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasCategorySelectedAndCanFileOutSIFHolder
-                  label: 'Each SIF in...'
-                  itemValue: categoryMenuFileOutEachSIFIn
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasCategorySelectedHolder
-                  label: 'Each Binary in...'
-                  itemValue: categoryMenuFileOutEachBinaryIn
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            label: 'Repository'
-            translateLabel: true
-            submenuChannel: categoryMenuSCMSlice
-            isMenuSlice: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasCategorySelectedHolder
+	    label: 'FileOut'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasCategorySelectedHolder
+		  label: 'as...'
+		  itemValue: categoryMenuFileOutAs
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasCategorySelectedAndCanFileOutXMLHolder
+		  label: 'XML as...'
+		  itemValue: categoryMenuFileOutXMLAs
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasCategorySelectedAndCanFileOutSIFHolder
+		  label: 'SIF as...'
+		  itemValue: categoryMenuFileOutSIFAs
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasCategorySelectedHolder
+		  label: 'Each in...'
+		  itemValue: categoryMenuFileOutEachIn
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasCategorySelectedAndCanFileOutXMLHolder
+		  label: 'Each XML in...'
+		  itemValue: categoryMenuFileOutEachXMLIn
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasCategorySelectedAndCanFileOutSIFHolder
+		  label: 'Each SIF in...'
+		  itemValue: categoryMenuFileOutEachSIFIn
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasCategorySelectedHolder
+		  label: 'Each Binary in...'
+		  itemValue: categoryMenuFileOutEachBinaryIn
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: 'Repository'
+	    translateLabel: true
+	    submenuChannel: categoryMenuSCMSlice
+	    isMenuSlice: true
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -6428,32 +6460,32 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'New...'
-            itemValue: categoryMenuNewCategory
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasCategorySelectedHolder
-            label: 'Rename...'
-            itemValue: categoryMenuRename
-            translateLabel: true
-            shortcutKey: Rename
-            ignoreShortcutKeys: true
-          )
-         (MenuItem
-            enabled: hasCategorySelectedHolder
-            label: 'Remove...'
-            itemValue: categoryMenuRemove
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary erase16x16Icon 'Remove...')
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'New...'
+	    itemValue: categoryMenuNewCategory
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: hasCategorySelectedHolder
+	    label: 'Rename...'
+	    itemValue: categoryMenuRename
+	    translateLabel: true
+	    shortcutKey: Rename
+	    ignoreShortcutKeys: true
+	  )
+	 (MenuItem
+	    enabled: hasCategorySelectedHolder
+	    label: 'Remove...'
+	    itemValue: categoryMenuRemove
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary erase16x16Icon 'Remove...')
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -6473,47 +6505,47 @@
 
     ^
      #(Menu
-        (
-         (MenuItem
-            enabled: hasCategorySelectedHolder
-            label: 'Spawn'
-            translateLabel: true
-            submenu:
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasCategorySelectedHolder
-                  label: 'Buffer'
-                  itemValue: categoryMenuSpawnBuffer
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: 'Buffer with Categories Matching...'
-                  itemValue: categoryMenuSpawnMatchingCategoriesBuffer
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasCategorySelectedHolder
-                  label: 'Browser'
-                  itemValue: categoryMenuSpawnBrowser
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: 'Browser on Categories Matching...'
-                  itemValue: categoryMenuSpawnMatchingCategoriesBrowser
-                  translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         )
-        nil
-        nil
+	(
+	 (MenuItem
+	    enabled: hasCategorySelectedHolder
+	    label: 'Spawn'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasCategorySelectedHolder
+		  label: 'Buffer'
+		  itemValue: categoryMenuSpawnBuffer
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: 'Buffer with Categories Matching...'
+		  itemValue: categoryMenuSpawnMatchingCategoriesBuffer
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasCategorySelectedHolder
+		  label: 'Browser'
+		  itemValue: categoryMenuSpawnBrowser
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: 'Browser on Categories Matching...'
+		  itemValue: categoryMenuSpawnMatchingCategoriesBrowser
+		  translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -6531,72 +6563,199 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'FileOutAndRepositorySlice'
-            translateLabel: true
-            submenuChannel: categoryMenuFileOutAndRepositorySlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'DocumentationSlice'
-            translateLabel: true
-            submenuChannel: categoryMenuDocumentationSlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'SpawnSlice'
-            translateLabel: true
-            submenuChannel: categoryMenuSpawnSlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            label: 'Find'
-            translateLabel: true
-            submenuChannel: searchMenu
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'NewAndRenameSlice'
-            translateLabel: true
-            submenuChannel: categoryMenuNewAndRenameSlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Static Analysis (Lint)'
-            translateLabel: true
-            submenuChannel: categoryCheckMenu
-          )
-         (MenuItem
-            label: 'Special'
-            translateLabel: true
-            submenuChannel: categorySpecialMenu
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Update'
-            itemValue: categoryMenuUpdate
-            translateLabel: true
-          )
-         )
-        nil
-        nil
-      )
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'FileOutAndRepositorySlice'
+	    translateLabel: true
+	    submenuChannel: categoryMenuFileOutAndRepositorySlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'DocumentationSlice'
+	    translateLabel: true
+	    submenuChannel: categoryMenuDocumentationSlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'SpawnSlice'
+	    translateLabel: true
+	    submenuChannel: categoryMenuSpawnSlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: 'Find'
+	    translateLabel: true
+	    submenuChannel: searchMenu
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'NewAndRenameSlice'
+	    translateLabel: true
+	    submenuChannel: categoryMenuNewAndRenameSlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Static Analysis (Lint)'
+	    translateLabel: true
+	    submenuChannel: categoryCheckMenu
+	  )
+	(MenuItem
+	    label: 'Debug'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	 (MenuItem
+	    enabled: hasCategorySelectedHolder
+	    label: 'Recompile all Classes'
+	    itemValue: categoryMenuRecompile
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasCategorySelectedAndInstrumentingCompilerExistsHolder
+	    label: 'Recompile all Classes with Instrumentation'
+	    itemValue: categoryMenuRecompileInstrumented
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: 'Special'
+	    translateLabel: true
+	    submenuChannel: categorySpecialMenu
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Update'
+	    itemValue: categoryMenuUpdate
+	    translateLabel: true
+	  )
+	 )
+	nil
+	nil
+      )
+
+    "Modified: / 31-05-2012 / 12:00:17 / cg"
+!
+
+categoryMenuWithoutFind
+    "This resource specification was automatically generated
+     by the MenuEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the MenuEditor may not be able to read the specification."
+
+
+    "
+     MenuEditor new openOnClass:Tools::NewSystemBrowser andSelector:#categoryMenu
+     (Menu new fromLiteralArrayEncoding:(Tools::NewSystemBrowser categoryMenu)) startUp
+    "
+
+    <resource: #menu>
+
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'FileOutAndRepositorySlice'
+	    translateLabel: true
+	    submenuChannel: categoryMenuFileOutAndRepositorySlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'DocumentationSlice'
+	    translateLabel: true
+	    submenuChannel: categoryMenuDocumentationSlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'SpawnSlice'
+	    translateLabel: true
+	    submenuChannel: categoryMenuSpawnSlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'NewAndRenameSlice'
+	    nameKey: NewAndRenameSlice
+	    translateLabel: true
+	    submenuChannel: categoryMenuNewAndRenameSlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Static Analysis (Lint)'
+	    translateLabel: true
+	    submenuChannel: categoryCheckMenu
+	    labelImage: (ResourceRetriever ToolbarIconLibrary lint16x16Icon 'Static Analysis (Lint)')
+	  )
+	 (MenuItem
+	    label: 'Debug'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	 (MenuItem
+	    enabled: hasCategorySelectedAndInstrumentingCompilerExistsHolder
+	    label: 'Recompile all Classes with Instrumentation'
+	    itemValue: categoryMenuRecompileInstrumented
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: 'Special'
+	    translateLabel: true
+	    submenuChannel: categorySpecialMenu
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Update'
+	    itemValue: categoryMenuUpdate
+	    translateLabel: true
+	  )
+	 )
+	nil
+	nil
+      )
+
+    "Created: / 31-05-2012 / 09:18:50 / cg"
 !
 
 categorySpecialMenu
@@ -6615,33 +6774,33 @@
 
     ^
      #(Menu
-        (
-         (MenuItem
-            enabled: hasAnyCategoryWithAnyUnLoadedClassSelectedHolder
-            label: 'Load'
-            itemValue: categoryMenuLoad
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasAnyCategoryWithAnyAutoLoadedClassSelectedHolder
-            label: 'Unload'
-            itemValue: categoryMenuUnload
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasCategorySelectedHolder
-            label: 'Remove all from ChangeSet'
-            itemValue: categoryMenuCleanUpChangeSet
-            translateLabel: true
-          )
-         )
-        nil
-        nil
+	(
+	 (MenuItem
+	    enabled: hasAnyCategoryWithAnyUnLoadedClassSelectedHolder
+	    label: 'Load'
+	    itemValue: categoryMenuLoad
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasAnyCategoryWithAnyAutoLoadedClassSelectedHolder
+	    label: 'Unload'
+	    itemValue: categoryMenuUnload
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasCategorySelectedHolder
+	    label: 'Remove all from ChangeSet'
+	    itemValue: categoryMenuCleanUpChangeSet
+	    translateLabel: true
+	  )
+	 )
+	nil
+	nil
       )
 
     "Modified: / 31-01-2011 / 11:11:18 / cg"
@@ -6661,28 +6820,28 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'Lint'
-            translateLabel: true
-            submenuChannel: lintMenu
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasClassSelectedAndInstrumentingCompilerExistsHolder
-            label: 'Recompile all Methods with Instrumentation'
-            itemValue: classMenuRecompileInstrumented
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'Lint'
+	    translateLabel: true
+	    submenuChannel: lintMenu
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedAndInstrumentingCompilerExistsHolder
+	    label: 'Recompile all Methods with Instrumentation'
+	    itemValue: classMenuRecompileInstrumented
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -6700,46 +6859,46 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'Check'
-            itemValue: classCheckMenuSmalllintCheck:
-            translateLabel: true
-            argument: smalllintRules
-          )
-         (MenuItem
-            label: 'Check (all checks)'
-            itemValue: classCheckMenuSmalllintCheck:
-            translateLabel: true
-            argument: smalllintRulesAll
-          )
-         (MenuItem
-            label: 'Check (selected checks)'
-            itemValue: classCheckMenuSmalllintCheck:
-            translateLabel: true
-            argument: smalllintRulesFromUser
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Smalltalk/X Checks'
-            translateLabel: true
-            submenuChannel: lintMenu
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            enabled: hasClassSelectedAndInstrumentingCompilerExistsHolder
-            label: 'Recompile all Methods with Instrumentation'
-            itemValue: classMenuRecompileInstrumented
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'Check'
+	    itemValue: classCheckMenuSmalllintCheck:
+	    translateLabel: true
+	    argument: smalllintRules
+	  )
+	 (MenuItem
+	    label: 'Check (all checks)'
+	    itemValue: classCheckMenuSmalllintCheck:
+	    translateLabel: true
+	    argument: smalllintRulesAll
+	  )
+	 (MenuItem
+	    label: 'Check (selected checks)'
+	    itemValue: classCheckMenuSmalllintCheck:
+	    translateLabel: true
+	    argument: smalllintRulesFromUser
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Smalltalk/X Checks'
+	    translateLabel: true
+	    submenuChannel: lintMenu
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedAndInstrumentingCompilerExistsHolder
+	    label: 'Recompile all Methods with Instrumentation'
+	    itemValue: classMenuRecompileInstrumented
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 )
+	nil
+	nil
       )
 
     "Modified: / 17-04-2010 / 11:17:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -6761,86 +6920,86 @@
 
     ^
      #(#Menu
-        #(
-         #(#MenuItem
-            #label: 'References...'
-            #translateLabel: true
-            #value: #variablesMenuBrowseAllClassVarRefs
-            #enabled: #hasClassSelectedHolder
-            #showBusyCursorWhilePerforming: true
-          )
-         #(#MenuItem
-            #label: 'Readers...'
-            #translateLabel: true
-            #value: #variablesMenuBrowseAllClassVarReads
-            #enabled: #hasClassSelectedHolder
-            #showBusyCursorWhilePerforming: true
-          )
-         #(#MenuItem
-            #label: 'Writers...'
-            #translateLabel: true
-            #value: #variablesMenuBrowseAllClassVarMods
-            #enabled: #hasClassSelectedHolder
-            #showBusyCursorWhilePerforming: true
-          )
-         #(#MenuItem
-            #label: '-'
-          )
-         #(#MenuItem
-            #label: 'Add...'
-            #translateLabel: true
-            #value: #variablesMenuAddClassVariable
-            #enabled: #hasSingleClassSelectedAndCanUseRefactoringSupportHolder
-            #showBusyCursorWhilePerforming: true
-          )
-         #(#MenuItem
-            #label: 'Rename...'
-            #translateLabel: true
-            #value: #variablesMenuRenameClassVariable
-            #enabled: #hasSingleClassAndClassVariableSelectedAndCanUseRefactoringSupportHolder
-            #showBusyCursorWhilePerforming: true
-          )
-         #(#MenuItem
-            #label: 'Remove'
-            #translateLabel: true
-            #value: #variablesMenuRemoveClassVariable
-            #enabled: #hasSingleClassAndClassVariableSelectedAndCanUseRefactoringSupportHolder
-            #showBusyCursorWhilePerforming: true
-          )
-         #(#MenuItem
-            #label: '-'
-          )
-         #(#MenuItem
-            #label: 'Pull Up'
-            #translateLabel: true
-            #value: #codeMenuPullUpClassVariable
-            #enabled: #hasClassVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
-            #showBusyCursorWhilePerforming: true
-          )
-         #(#MenuItem
-            #label: 'Push Down'
-            #translateLabel: true
-            #value: #codeMenuPushDownClassVariable
-            #enabled: #hasClassVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
-            #showBusyCursorWhilePerforming: true
-          )
-         #(#MenuItem
-            #label: '-'
-          )
-         #(#MenuItem
-            #label: 'Make Abstract (Access only via Getters/Setters)'
-            #translateLabel: true
-            #value: #codeMenuMakeAbstractVariable
-            #enabled: #hasClassVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
-            #showBusyCursorWhilePerforming: true
-          )
-         #(#MenuItem
-            #label: 'Make Concrete (Protect from Access via Getters/Setters)'
-            #translateLabel: true
-            #value: #codeMenuProtectInstanceVariable
-            #enabled: #hasClassVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
-            #showBusyCursorWhilePerforming: true
-          )
+	#(
+	 #(#MenuItem
+	    #label: 'References...'
+	    #translateLabel: true
+	    #value: #variablesMenuBrowseAllClassVarRefs
+	    #enabled: #hasClassSelectedHolder
+	    #showBusyCursorWhilePerforming: true
+	  )
+	 #(#MenuItem
+	    #label: 'Readers...'
+	    #translateLabel: true
+	    #value: #variablesMenuBrowseAllClassVarReads
+	    #enabled: #hasClassSelectedHolder
+	    #showBusyCursorWhilePerforming: true
+	  )
+	 #(#MenuItem
+	    #label: 'Writers...'
+	    #translateLabel: true
+	    #value: #variablesMenuBrowseAllClassVarMods
+	    #enabled: #hasClassSelectedHolder
+	    #showBusyCursorWhilePerforming: true
+	  )
+	 #(#MenuItem
+	    #label: '-'
+	  )
+	 #(#MenuItem
+	    #label: 'Add...'
+	    #translateLabel: true
+	    #value: #variablesMenuAddClassVariable
+	    #enabled: #hasSingleClassSelectedAndCanUseRefactoringSupportHolder
+	    #showBusyCursorWhilePerforming: true
+	  )
+	 #(#MenuItem
+	    #label: 'Rename...'
+	    #translateLabel: true
+	    #value: #variablesMenuRenameClassVariable
+	    #enabled: #hasSingleClassAndClassVariableSelectedAndCanUseRefactoringSupportHolder
+	    #showBusyCursorWhilePerforming: true
+	  )
+	 #(#MenuItem
+	    #label: 'Remove'
+	    #translateLabel: true
+	    #value: #variablesMenuRemoveClassVariable
+	    #enabled: #hasSingleClassAndClassVariableSelectedAndCanUseRefactoringSupportHolder
+	    #showBusyCursorWhilePerforming: true
+	  )
+	 #(#MenuItem
+	    #label: '-'
+	  )
+	 #(#MenuItem
+	    #label: 'Pull Up'
+	    #translateLabel: true
+	    #value: #codeMenuPullUpClassVariable
+	    #enabled: #hasClassVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
+	    #showBusyCursorWhilePerforming: true
+	  )
+	 #(#MenuItem
+	    #label: 'Push Down'
+	    #translateLabel: true
+	    #value: #codeMenuPushDownClassVariable
+	    #enabled: #hasClassVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
+	    #showBusyCursorWhilePerforming: true
+	  )
+	 #(#MenuItem
+	    #label: '-'
+	  )
+	 #(#MenuItem
+	    #label: 'Make Abstract (Access only via Getters/Setters)'
+	    #translateLabel: true
+	    #value: #codeMenuMakeAbstractVariable
+	    #enabled: #hasClassVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
+	    #showBusyCursorWhilePerforming: true
+	  )
+	 #(#MenuItem
+	    #label: 'Make Concrete (Protect from Access via Getters/Setters)'
+	    #translateLabel: true
+	    #value: #codeMenuProtectInstanceVariable
+	    #enabled: #hasClassVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
+	    #showBusyCursorWhilePerforming: true
+	  )
 "/         #(#MenuItem
 "/            #label: 'Type info...'
 "/            #translateLabel: true
@@ -6848,9 +7007,9 @@
 "/            #enabled: #hasSingleVariableSelectedHolder
 "/            #showBusyCursorWhilePerforming: true
 "/          )
-         )
-        nil
-        nil
+	 )
+	nil
+	nil
       )
 !
 
@@ -6869,92 +7028,92 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Inspect Class'
-            itemValue: classMenuInspectClass
-            translateLabel: true
-            isVisible: hasNotMultipleClassesSelectedHolder
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Inspect Classes'
-            itemValue: classMenuInspectClass
-            translateLabel: true
-            isVisible: hasMultipleClassesSelectedHolder
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Inspect Subclasses'
-            itemValue: classMenuInspectSubclasses
-            translateLabel: true
-            isVisible: hasNotMultipleClassesSelectedHolder
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Inspect Instances'
-            itemValue: classMenuInspectInstances
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Inspect Derived Instances'
-            itemValue: classMenuInspectDerivedInstances
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Inspect References to Instances'
-            itemValue: classMenuInspectReferencesToInstances
-            translateLabel: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Lint'
-            translateLabel: true
-            isVisible: false
-            submenuChannel: lintMenu
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Recompile all Methods'
-            itemValue: classMenuRecompile
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Recompile all Methods here and in Subclasses'
-            itemValue: classMenuRecompileAll
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasClassSelectedAndInstrumentingCompilerExistsHolder
-            label: 'Recompile all Methods with Instrumentation'
-            itemValue: classMenuRecompileInstrumented
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasClassSelectedAndInstrumentingCompilerExistsAndOOMPackageLoadedHolder
-            label: 'Call Graph'
-            itemValue: debugMenuOpenCallGraphForClasses
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Inspect Class'
+	    itemValue: classMenuInspectClass
+	    translateLabel: true
+	    isVisible: hasNotMultipleClassesSelectedHolder
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Inspect Classes'
+	    itemValue: classMenuInspectClass
+	    translateLabel: true
+	    isVisible: hasMultipleClassesSelectedHolder
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Inspect Subclasses'
+	    itemValue: classMenuInspectSubclasses
+	    translateLabel: true
+	    isVisible: hasNotMultipleClassesSelectedHolder
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Inspect Instances'
+	    itemValue: classMenuInspectInstances
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Inspect Derived Instances'
+	    itemValue: classMenuInspectDerivedInstances
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Inspect References to Instances'
+	    itemValue: classMenuInspectReferencesToInstances
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Lint'
+	    translateLabel: true
+	    isVisible: false
+	    submenuChannel: lintMenu
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Recompile all Methods'
+	    itemValue: classMenuRecompile
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Recompile all Methods here and in Subclasses'
+	    itemValue: classMenuRecompileAll
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedAndInstrumentingCompilerExistsHolder
+	    label: 'Recompile all Methods with Instrumentation'
+	    itemValue: classMenuRecompileInstrumented
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedAndInstrumentingCompilerExistsAndOOMPackageLoadedHolder
+	    label: 'Call Graph'
+	    itemValue: debugMenuOpenCallGraphForClasses
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -6972,131 +7131,131 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'AccessMethodsSlice'
-            translateLabel: true
-            submenuChannel: classGenerateMenuAccessMethodsSlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            label: 'CommonInstMethodsSlice'
-            translateLabel: true
-            submenuChannel: classGenerateMenuCommonInstMethodsSlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            enabled: hasLoadedClassSelectedHolder
-            label: 'Documentation Stubs'
-            itemValue: classMenuGenerateDocumentationStubs
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasSingleLoadedClassWithCommentSelectedHolder
-            label: 'Documentation Method from Comment'
-            itemValue: classMenuGenerateDocumentationMethodFromComment
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasLoadedClassSelectedHolder
-            label: 'Copyright Method'
-            itemValue: classMenuGenerateCopyrightMethod
-            translateLabel: true
-          )
-         (MenuItem
-            label: '-'
-            isVisible: hasClassSelectedHolder
-          )
-         (MenuItem
-            label: 'Project Definitions'
-            itemValue: classMenuGenerateProjectDefinitions
-            translateLabel: true
-            isVisible: hasProjectDefinitionSelectedHolder
-          )
-         (MenuItem
-            label: 'Update Project Contents Definitions'
-            itemValue: classMenuUpdateProjectContentsDefinitions
-            translateLabel: true
-            isVisible: hasProjectDefinitionSelectedHolder
-          )
-         (MenuItem
-            label: 'Regenerate Project Contents Definitions'
-            itemValue: classMenuRegenerateProjectContentsDefinitions
-            translateLabel: true
-            isVisible: hasProjectDefinitionSelectedHolder
-          )
-         (MenuItem
-            enabled: hasSingleLoadedClassSelectedHolder
-            label: 'Initialized Instance Creation'
-            itemValue: classMenuGenerateInitializedInstanceCreationMethods
-            translateLabel: true
-            isVisible: hasNonProjectDefinitionSelectedHolder
-          )
-         (MenuItem
-            enabled: hasSingleLoadedClassSelectedHolder
-            label: 'Parametrized Instance Creation'
-            itemValue: classMenuGenerateParametrizedInstanceCreationMethods
-            translateLabel: true
-            isVisible: hasNonProjectDefinitionSelectedHolder
-          )
-         (MenuItem
-            enabled: hasSingleLoadedClassSelectedHolder
-            label: 'Redefined Instance Creation'
-            itemValue: classMenuGenerateRedefinedInstanceCreationMethods
-            translateLabel: true
-            isVisible: hasNonProjectDefinitionSelectedHolder
-          )
-         (MenuItem
-            enabled: hasLoadedClassSelectedHolder
-            label: 'Singleton Pattern'
-            itemValue: classMenuGenerateSingletonPatternInstanceCreationMethods
-            translateLabel: true
-            isVisible: hasNonProjectDefinitionSelectedHolder
-          )
-         (MenuItem
-            enabled: hasEnumTypeClassSelectedHolder
-            label: 'EnumType Code'
-            itemValue: classMenuGenerateEnumTypeCode
-            translateLabel: true
-            isVisible: hasNonProjectDefinitionSelectedHolder
-          )
-         (MenuItem
-            enabled: hasSharedPoolClassSelectedHolder
-            label: 'SharedPool Initialization Code'
-            itemValue: classMenuGeneratePoolInitializationCode
-            translateLabel: true
-            isVisible: hasNonProjectDefinitionSelectedHolder
-          )
-         (MenuItem
-            label: '-'
-            isVisible: hasNonProjectDefinitionSelectedHolder
-          )
-         (MenuItem
-            enabled: hasApplicationOrHTTPServiceClassSelectedHolder
-            label: 'Application Code'
-            itemValue: classMenuGenerateApplicationCode
-            translateLabel: true
-            isVisible: hasNonProjectDefinitionSelectedHolder
-          )
-         (MenuItem
-            enabled: hasLoadedClassSelectedHolder
-            label: 'Class Initialization Code'
-            itemValue: classMenuGenerateClassInitializationCode
-            translateLabel: true
-            isVisible: hasNonProjectDefinitionSelectedHolder
-          )
-         (MenuItem
-            enabled: hasLoadedClassSelectedHolder
-            label: 'Required Protocol'
-            itemValue: classMenuGenerateRequiredProtocol
-            translateLabel: true
-            isVisible: hasNonProjectDefinitionSelectedHolder
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'AccessMethodsSlice'
+	    translateLabel: true
+	    submenuChannel: classGenerateMenuAccessMethodsSlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: 'CommonInstMethodsSlice'
+	    translateLabel: true
+	    submenuChannel: classGenerateMenuCommonInstMethodsSlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    enabled: hasLoadedClassSelectedHolder
+	    label: 'Documentation Stubs'
+	    itemValue: classMenuGenerateDocumentationStubs
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleLoadedClassWithCommentSelectedHolder
+	    label: 'Documentation Method from Comment'
+	    itemValue: classMenuGenerateDocumentationMethodFromComment
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: hasLoadedClassSelectedHolder
+	    label: 'Copyright Method'
+	    itemValue: classMenuGenerateCopyrightMethod
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: '-'
+	    isVisible: hasClassSelectedHolder
+	  )
+	 (MenuItem
+	    label: 'Project Definitions'
+	    itemValue: classMenuGenerateProjectDefinitions
+	    translateLabel: true
+	    isVisible: hasProjectDefinitionSelectedHolder
+	  )
+	 (MenuItem
+	    label: 'Update Project Contents Definitions'
+	    itemValue: classMenuUpdateProjectContentsDefinitions
+	    translateLabel: true
+	    isVisible: hasProjectDefinitionSelectedHolder
+	  )
+	 (MenuItem
+	    label: 'Regenerate Project Contents Definitions'
+	    itemValue: classMenuRegenerateProjectContentsDefinitions
+	    translateLabel: true
+	    isVisible: hasProjectDefinitionSelectedHolder
+	  )
+	 (MenuItem
+	    enabled: hasSingleLoadedClassSelectedHolder
+	    label: 'Initialized Instance Creation'
+	    itemValue: classMenuGenerateInitializedInstanceCreationMethods
+	    translateLabel: true
+	    isVisible: hasNonProjectDefinitionSelectedHolder
+	  )
+	 (MenuItem
+	    enabled: hasSingleLoadedClassSelectedHolder
+	    label: 'Parametrized Instance Creation'
+	    itemValue: classMenuGenerateParametrizedInstanceCreationMethods
+	    translateLabel: true
+	    isVisible: hasNonProjectDefinitionSelectedHolder
+	  )
+	 (MenuItem
+	    enabled: hasSingleLoadedClassSelectedHolder
+	    label: 'Redefined Instance Creation'
+	    itemValue: classMenuGenerateRedefinedInstanceCreationMethods
+	    translateLabel: true
+	    isVisible: hasNonProjectDefinitionSelectedHolder
+	  )
+	 (MenuItem
+	    enabled: hasLoadedClassSelectedHolder
+	    label: 'Singleton Pattern'
+	    itemValue: classMenuGenerateSingletonPatternInstanceCreationMethods
+	    translateLabel: true
+	    isVisible: hasNonProjectDefinitionSelectedHolder
+	  )
+	 (MenuItem
+	    enabled: hasEnumTypeClassSelectedHolder
+	    label: 'EnumType Code'
+	    itemValue: classMenuGenerateEnumTypeCode
+	    translateLabel: true
+	    isVisible: hasNonProjectDefinitionSelectedHolder
+	  )
+	 (MenuItem
+	    enabled: hasSharedPoolClassSelectedHolder
+	    label: 'SharedPool Initialization Code'
+	    itemValue: classMenuGeneratePoolInitializationCode
+	    translateLabel: true
+	    isVisible: hasNonProjectDefinitionSelectedHolder
+	  )
+	 (MenuItem
+	    label: '-'
+	    isVisible: hasNonProjectDefinitionSelectedHolder
+	  )
+	 (MenuItem
+	    enabled: hasApplicationOrHTTPServiceClassSelectedHolder
+	    label: 'Application Code'
+	    itemValue: classMenuGenerateApplicationCode
+	    translateLabel: true
+	    isVisible: hasNonProjectDefinitionSelectedHolder
+	  )
+	 (MenuItem
+	    enabled: hasLoadedClassSelectedHolder
+	    label: 'Class Initialization Code'
+	    itemValue: classMenuGenerateClassInitializationCode
+	    translateLabel: true
+	    isVisible: hasNonProjectDefinitionSelectedHolder
+	  )
+	 (MenuItem
+	    enabled: hasLoadedClassSelectedHolder
+	    label: 'Required Protocol'
+	    itemValue: classMenuGenerateRequiredProtocol
+	    translateLabel: true
+	    isVisible: hasNonProjectDefinitionSelectedHolder
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -7116,69 +7275,69 @@
 
     ^
      #(Menu
-        (
-         (MenuItem
-            enabled: hasSingleLoadedClassSelectedHolder
-            label: 'Access Methods'
-            itemValue: classMenuGenerateAccessMethods
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasSingleLoadedClassSelectedHolder
-            label: 'Getter Method(s)'
-            itemValue: classMenuGenerateGetterMethods
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasSingleLoadedClassSelectedHolder
-            label: 'Setter Method(s)'
-            itemValue: classMenuGenerateSetterMethods
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasSingleLoadedClassSelectedAndMultipleVariablesSelectedHolder
-            label: 'Multi-Setter Method'
-            itemValue: classMenuGenerateMultiSetterMethod
-            translateLabel: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasSingleLoadedClassSelectedHolder
-            label: 'Access Methods with Lazy Initialization in Getter'
-            itemValue: classMenuGenerateAccessMethodsWithLazyInitialization
-            translateLabel: true
-            isVisible: hasNonMetaSelectedHolder
-          )
-         (MenuItem
-            enabled: hasSingleLoadedClassSelectedHolder
-            label: 'Access Methods with Change Notification'
-            itemValue: classMenuGenerateAccessMethodsWithChange
-            translateLabel: true
-            isVisible: hasNonMetaSelectedHolder
-          )
-         (MenuItem
-            enabled: hasSingleLoadedClassSelectedHolder
-            label: 'Access Methods for ValueHolder'
-            itemValue: classMenuGenerateAccessMethodsForValueHolder
-            translateLabel: true
-            isVisible: hasNonMetaSelectedHolder
-          )
-         (MenuItem
-            enabled: hasSingleLoadedClassSelectedHolder
-            label: 'Access Methods for ValueHolder with Change Notification'
-            itemValue: classMenuGenerateAccessMethodsForValueHolderWithChange
-            translateLabel: true
-            isVisible: hasNonMetaSelectedHolder
-          )
-         (MenuItem
-            label: '-'
-            isVisible: hasNonMetaSelectedHolder
-          )
-         )
-        nil
-        nil
+	(
+	 (MenuItem
+	    enabled: hasSingleLoadedClassSelectedHolder
+	    label: 'Access Methods'
+	    itemValue: classMenuGenerateAccessMethods
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleLoadedClassSelectedHolder
+	    label: 'Getter Method(s)'
+	    itemValue: classMenuGenerateGetterMethods
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleLoadedClassSelectedHolder
+	    label: 'Setter Method(s)'
+	    itemValue: classMenuGenerateSetterMethods
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleLoadedClassSelectedAndMultipleVariablesSelectedHolder
+	    label: 'Multi-Setter Method'
+	    itemValue: classMenuGenerateMultiSetterMethod
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasSingleLoadedClassSelectedHolder
+	    label: 'Access Methods with Lazy Initialization in Getter'
+	    itemValue: classMenuGenerateAccessMethodsWithLazyInitialization
+	    translateLabel: true
+	    isVisible: hasNonMetaSelectedHolder
+	  )
+	 (MenuItem
+	    enabled: hasSingleLoadedClassSelectedHolder
+	    label: 'Access Methods with Change Notification'
+	    itemValue: classMenuGenerateAccessMethodsWithChange
+	    translateLabel: true
+	    isVisible: hasNonMetaSelectedHolder
+	  )
+	 (MenuItem
+	    enabled: hasSingleLoadedClassSelectedHolder
+	    label: 'Access Methods for ValueHolder'
+	    itemValue: classMenuGenerateAccessMethodsForValueHolder
+	    translateLabel: true
+	    isVisible: hasNonMetaSelectedHolder
+	  )
+	 (MenuItem
+	    enabled: hasSingleLoadedClassSelectedHolder
+	    label: 'Access Methods for ValueHolder with Change Notification'
+	    itemValue: classMenuGenerateAccessMethodsForValueHolderWithChange
+	    translateLabel: true
+	    isVisible: hasNonMetaSelectedHolder
+	  )
+	 (MenuItem
+	    label: '-'
+	    isVisible: hasNonMetaSelectedHolder
+	  )
+	 )
+	nil
+	nil
       )
 
     "Created: / 10-08-2006 / 16:11:12 / cg"
@@ -7198,74 +7357,74 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: '"initialize"-Method'
-            itemValue: classMenuGenerateInitializationMethod
-            translateLabel: true
-            isVisible: hasNonMetaSelectedHolder
-            sendToOriginator: true
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: '"printOn:"-Method'
-            itemValue: classMenuGenerateStandardPrintOnMethod
-            translateLabel: true
-            isVisible: hasNonMetaSelectedHolder
-            sendToOriginator: true
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Update Method Template'
-            itemValue: classMenuGenerateUpdateMethod
-            translateLabel: true
-            isVisible: hasNonMetaSelectedHolder
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Visitor Method'
-            itemValue: classMenuGenerateAcceptVisitor
-            translateLabel: true
-            isVisible: hasNonMetaSelectedHolder
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Visitor and Visited Methods'
-            itemValue: classMenuGenerateVisitorMethods
-            translateLabel: true
-            isVisible: hasNonMetaSelectedHolder
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Visitor and Visited Methods (with visitSuper:)'
-            itemValue: classMenuGenerateVisitorMethods2
-            translateLabel: true
-            isVisible: hasNonMetaSelectedHolder
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Classtype Test Methods for this Class (isXXX)'
-            itemValue: classMenuGenerateClassTypeTestMethodsForThisClass
-            translateLabel: true
-            isVisible: hasNonMetaSelectedHolder
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Classtype Test Methods for all Subclass(es) (isXXX)'
-            itemValue: classMenuGenerateClassTypeTestMethods
-            translateLabel: true
-            isVisible: hasNonMetaSelectedHolder
-          )
-         (MenuItem
-            label: '-'
-            isVisible: hasNonMetaSelectedHolder
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: '"initialize"-Method'
+	    itemValue: classMenuGenerateInitializationMethod
+	    translateLabel: true
+	    isVisible: hasNonMetaSelectedHolder
+	    sendToOriginator: true
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: '"printOn:"-Method'
+	    itemValue: classMenuGenerateStandardPrintOnMethod
+	    translateLabel: true
+	    isVisible: hasNonMetaSelectedHolder
+	    sendToOriginator: true
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Update Method Template'
+	    itemValue: classMenuGenerateUpdateMethod
+	    translateLabel: true
+	    isVisible: hasNonMetaSelectedHolder
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Visitor Method'
+	    itemValue: classMenuGenerateAcceptVisitor
+	    translateLabel: true
+	    isVisible: hasNonMetaSelectedHolder
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Visitor and Visited Methods'
+	    itemValue: classMenuGenerateVisitorMethods
+	    translateLabel: true
+	    isVisible: hasNonMetaSelectedHolder
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Visitor and Visited Methods (with visitSuper:)'
+	    itemValue: classMenuGenerateVisitorMethods2
+	    translateLabel: true
+	    isVisible: hasNonMetaSelectedHolder
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Classtype Test Methods for this Class (isXXX)'
+	    itemValue: classMenuGenerateClassTypeTestMethodsForThisClass
+	    translateLabel: true
+	    isVisible: hasNonMetaSelectedHolder
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Classtype Test Methods for all Subclass(es) (isXXX)'
+	    itemValue: classMenuGenerateClassTypeTestMethods
+	    translateLabel: true
+	    isVisible: hasNonMetaSelectedHolder
+	  )
+	 (MenuItem
+	    label: '-'
+	    isVisible: hasNonMetaSelectedHolder
+	  )
+	 )
+	nil
+	nil
       )
 
     "Modified: / 23-03-2012 / 11:58:16 / cg"
@@ -7287,37 +7446,37 @@
 
     ^
      #(#Menu
-        #(
-         #(#MenuItem
-            #label: 'Select Class with Superclasses'
-            #translateLabel: true
-            #value: #classHierarchyMenuSelectWithSuperclasses
-            #enabled: #hasAtMostOneClassesSelectedHolder
-          )
-         #(#MenuItem
-            #label: 'Select Class with Subclasses'
-            #translateLabel: true
-            #value: #classHierarchyMenuSelectWithSubclasses
-            #enabled: #hasAtMostOneClassesSelectedHolder
-          )
-         #(#MenuItem
-            #label: 'Select Class with All Subclasses'
-            #translateLabel: true
-            #value: #classHierarchyMenuSelectWithAllSubclasses
-            #enabled: #hasAtMostOneClassesSelectedHolder
-          )
-         #(#MenuItem
-            #label: '-'
-          )
-         #(#MenuItem
-            #label: 'Update'
-            #translateLabel: true
-            #value: #classHierarchyMenuUpdate
-            #enabled: #hasSingleClassSelected
-          )
-         )
-        nil
-        nil
+	#(
+	 #(#MenuItem
+	    #label: 'Select Class with Superclasses'
+	    #translateLabel: true
+	    #value: #classHierarchyMenuSelectWithSuperclasses
+	    #enabled: #hasAtMostOneClassesSelectedHolder
+	  )
+	 #(#MenuItem
+	    #label: 'Select Class with Subclasses'
+	    #translateLabel: true
+	    #value: #classHierarchyMenuSelectWithSubclasses
+	    #enabled: #hasAtMostOneClassesSelectedHolder
+	  )
+	 #(#MenuItem
+	    #label: 'Select Class with All Subclasses'
+	    #translateLabel: true
+	    #value: #classHierarchyMenuSelectWithAllSubclasses
+	    #enabled: #hasAtMostOneClassesSelectedHolder
+	  )
+	 #(#MenuItem
+	    #label: '-'
+	  )
+	 #(#MenuItem
+	    #label: 'Update'
+	    #translateLabel: true
+	    #value: #classHierarchyMenuUpdate
+	    #enabled: #hasSingleClassSelected
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -7337,93 +7496,93 @@
 
     ^
      #(#Menu
-        #(
-         #(#MenuItem
-            #label: 'References...'
-            #translateLabel: true
-            #value: #variablesMenuBrowseAllInstVarOrClassInstVarRefs
-            #enabled: #hasClassSelectedHolder
-            #showBusyCursorWhilePerforming: true
-          )
-         #(#MenuItem
-            #label: 'Readers...'
-            #translateLabel: true
-            #value: #variablesMenuBrowseAllInstVarOrClassInstVarReads
-            #enabled: #hasClassSelectedHolder
-            #showBusyCursorWhilePerforming: true
-          )
-         #(#MenuItem
-            #label: 'Writers...'
-            #translateLabel: true
-            #value: #variablesMenuBrowseAllInstVarOrClassInstVarMods
-            #enabled: #hasClassSelectedHolder
-            #showBusyCursorWhilePerforming: true
-          )
-         #(#MenuItem
-            #label: '-'
-          )
-         #(#MenuItem
-            #label: 'Add...'
-            #translateLabel: true
-            #value: #variablesMenuAddInstanceVariable
-            #enabled: #hasSingleClassSelectedAndCanUseRefactoringSupportHolder
-            #showBusyCursorWhilePerforming: true
-          )
-         #(#MenuItem
-            #label: 'Rename...'
-            #translateLabel: true
-            #value: #variablesMenuRenameInstanceVariable
-            #enabled: #hasSingleClassAndSingleVariableSelectedAndCanUseRefactoringSupportHolder
-            #showBusyCursorWhilePerforming: true
-          )
-         #(#MenuItem
-            #label: 'Remove'
-            #translateLabel: true
-            #value: #variablesMenuRemoveInstanceVariable
-            #enabled: #hasSingleClassAndSingleVariableSelectedAndCanUseRefactoringSupportHolder
-            #showBusyCursorWhilePerforming: true
-          )
-         #(#MenuItem
-            #label: '-'
-          )
-         #(#MenuItem
-            #label: 'Pull Up'
-            #translateLabel: true
-            #value: #codeMenuPullUpInstanceVariable
-            #enabled: #hasInstanceVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
-            #showBusyCursorWhilePerforming: true
-          )
-         #(#MenuItem
-            #label: 'Push Down'
-            #translateLabel: true
-            #value: #codeMenuPushDownInstanceVariable
-            #enabled: #hasInstanceVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
-            #showBusyCursorWhilePerforming: true
-          )
-         #(#MenuItem
-            #label: '-'
-          )
-         #(#MenuItem
-            #label: 'Convert to ValueHolder'
-            #translateLabel: true
-            #value: #codeMenuConvertToValueHolder
-            #enabled: #hasInstanceVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
-            #showBusyCursorWhilePerforming: true
-          )
-         #(#MenuItem
-            #label: 'Make Abstract (Access only via Getters/Setters)'
-            #translateLabel: true
-            #value: #codeMenuMakeAbstractVariable
-            #enabled: #hasSingleVariableSelectedInCodeViewOrVariableListHolder
-            #showBusyCursorWhilePerforming: true
-          )
-         #(#MenuItem
-            #label: 'Make Concrete (Protect from Access via Getters/Setters)'
-            #translateLabel: true
-            #value: #codeMenuProtectInstanceVariable
-            #enabled: #hasSingleVariableSelectedInCodeViewOrVariableListHolder
-            #showBusyCursorWhilePerforming: true
-          )
+	#(
+	 #(#MenuItem
+	    #label: 'References...'
+	    #translateLabel: true
+	    #value: #variablesMenuBrowseAllInstVarOrClassInstVarRefs
+	    #enabled: #hasClassSelectedHolder
+	    #showBusyCursorWhilePerforming: true
+	  )
+	 #(#MenuItem
+	    #label: 'Readers...'
+	    #translateLabel: true
+	    #value: #variablesMenuBrowseAllInstVarOrClassInstVarReads
+	    #enabled: #hasClassSelectedHolder
+	    #showBusyCursorWhilePerforming: true
+	  )
+	 #(#MenuItem
+	    #label: 'Writers...'
+	    #translateLabel: true
+	    #value: #variablesMenuBrowseAllInstVarOrClassInstVarMods
+	    #enabled: #hasClassSelectedHolder
+	    #showBusyCursorWhilePerforming: true
+	  )
+	 #(#MenuItem
+	    #label: '-'
+	  )
+	 #(#MenuItem
+	    #label: 'Add...'
+	    #translateLabel: true
+	    #value: #variablesMenuAddInstanceVariable
+	    #enabled: #hasSingleClassSelectedAndCanUseRefactoringSupportHolder
+	    #showBusyCursorWhilePerforming: true
+	  )
+	 #(#MenuItem
+	    #label: 'Rename...'
+	    #translateLabel: true
+	    #value: #variablesMenuRenameInstanceVariable
+	    #enabled: #hasSingleClassAndSingleVariableSelectedAndCanUseRefactoringSupportHolder
+	    #showBusyCursorWhilePerforming: true
+	  )
+	 #(#MenuItem
+	    #label: 'Remove'
+	    #translateLabel: true
+	    #value: #variablesMenuRemoveInstanceVariable
+	    #enabled: #hasSingleClassAndSingleVariableSelectedAndCanUseRefactoringSupportHolder
+	    #showBusyCursorWhilePerforming: true
+	  )
+	 #(#MenuItem
+	    #label: '-'
+	  )
+	 #(#MenuItem
+	    #label: 'Pull Up'
+	    #translateLabel: true
+	    #value: #codeMenuPullUpInstanceVariable
+	    #enabled: #hasInstanceVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
+	    #showBusyCursorWhilePerforming: true
+	  )
+	 #(#MenuItem
+	    #label: 'Push Down'
+	    #translateLabel: true
+	    #value: #codeMenuPushDownInstanceVariable
+	    #enabled: #hasInstanceVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
+	    #showBusyCursorWhilePerforming: true
+	  )
+	 #(#MenuItem
+	    #label: '-'
+	  )
+	 #(#MenuItem
+	    #label: 'Convert to ValueHolder'
+	    #translateLabel: true
+	    #value: #codeMenuConvertToValueHolder
+	    #enabled: #hasInstanceVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
+	    #showBusyCursorWhilePerforming: true
+	  )
+	 #(#MenuItem
+	    #label: 'Make Abstract (Access only via Getters/Setters)'
+	    #translateLabel: true
+	    #value: #codeMenuMakeAbstractVariable
+	    #enabled: #hasSingleVariableSelectedInCodeViewOrVariableListHolder
+	    #showBusyCursorWhilePerforming: true
+	  )
+	 #(#MenuItem
+	    #label: 'Make Concrete (Protect from Access via Getters/Setters)'
+	    #translateLabel: true
+	    #value: #codeMenuProtectInstanceVariable
+	    #enabled: #hasSingleVariableSelectedInCodeViewOrVariableListHolder
+	    #showBusyCursorWhilePerforming: true
+	  )
 "/         #(#MenuItem
 "/            #label: 'Type info...'
 "/            #translateLabel: true
@@ -7431,9 +7590,9 @@
 "/            #enabled: #hasSingleVariableSelectedHolder
 "/            #showBusyCursorWhilePerforming: true
 "/          )
-         )
-        nil
-        nil
+	 )
+	nil
+	nil
       )
 !
 
@@ -7452,569 +7611,569 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'FileOut'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'as...'
-                  itemValue: classMenuFileOutAs
-                  translateLabel: true
-                  isVisible: hasSingleClassSelectedHolder
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedAndCanFileOutXMLHolder
-                  label: 'XML as...'
-                  itemValue: classMenuFileOutXMLAs
-                  translateLabel: true
-                  isVisible: hasSingleClassSelectedHolder
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedAndCanFileOutSIFHolder
-                  label: 'SIF as...'
-                  itemValue: classMenuFileOutSIFAs
-                  translateLabel: true
-                  isVisible: hasSingleClassSelectedHolder
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedAndCanFileOutBinaryHolder
-                  label: 'Binary as...'
-                  itemValue: classMenuFileOutBinaryAs
-                  translateLabel: true
-                  isVisible: hasSingleClassSelectedHolder
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Each in...'
-                  itemValue: classMenuFileOutEachIn
-                  translateLabel: true
-                  isVisible: hasMultipleClassesSelectedHolder
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasProjectDefinitionSelectedHolder
-                  label: 'Build Support Files in...'
-                  itemValue: classMenuFileOutBuildSupportFiles
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedAndCanFileOutXMLHolder
-                  label: 'Each XML in...'
-                  itemValue: classMenuFileOutEachXMLIn
-                  translateLabel: true
-                  isVisible: hasMultipleClassesSelectedHolder
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedAndCanFileOutSIFHolder
-                  label: 'Each SIF in...'
-                  itemValue: classMenuFileOutEachSIFIn
-                  translateLabel: true
-                  isVisible: hasMultipleClassesSelectedHolder
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Each Binary in...'
-                  itemValue: classMenuFileOutEachBinaryIn
-                  translateLabel: true
-                  isVisible: hasMultipleClassesSelectedHolder
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasClassSelectedAndCanSendMailHolder
-                  label: 'Mail To...'
-                  itemValue: classMenuMailTo
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Copy Source to Clipboard'
-                  itemValue: classMenuCopySourceToClipboard
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            label: 'Repository Slice'
-            translateLabel: true
-            submenuChannel: classMenuSCMSlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Documentation'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'PrintOut'
-                  itemValue: classMenuPrintOut
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'PrintOut Protocol'
-                  itemValue: classMenuPrintOutProtocol
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'HTML Documentation'
-                  itemValue: classMenuDocumentation
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Save HTML Documentation As...'
-                  itemValue: classMenuSaveDocumentationAs
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'Show Comment'
-                  itemValue: classMenuComment
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: 'Show Hierarchy'
-                  itemValue: classMenuHierarchy
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: 'Show Definition'
-                  itemValue: classMenuDefinition
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasOOMPackageLoadedHolder
-                  label: 'Metrics Report'
-                  itemValue: classMenuMetrics
-                  translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Spawn'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Buffer with References to Class'
-                  itemValue: classMenuSpawnBufferWithClassReferences
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Buffer with References to Class or Subclass'
-                  itemValue: classMenuSpawnBufferWithClassOrSubclassReferences
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Buffer with Subclasses'
-                  itemValue: classMenuSpawnBufferWithAllSubclasses
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Buffer with Superclasses'
-                  itemValue: classMenuSpawnBufferWithAllSuperclasses
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasMultipleClassesSelectedHolder
-                  label: 'Buffer with Common Superclass'
-                  itemValue: classMenuSpawnBufferWithCommonSuperclass
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Buffer with Projects'
-                  itemValue: classMenuSpawnBufferWithClassProjects
-                  translateLabel: true
-                  isVisible: false
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Buffer'
-                  itemValue: classMenuSpawnClassBuffer
-                  translateLabel: true
-                  isVisible: false
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Browser on References to Class'
-                  itemValue: classMenuSpawnClassReferences
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Browser on References to Class or Subclass'
-                  itemValue: classMenuSpawnClassOrSubclassReferences
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Browser on Subclasses'
-                  itemValue: classMenuSpawnWithAllSubclasses
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Browser on Superclasses'
-                  itemValue: classMenuSpawnWithAllSuperclasses
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasMultipleClassesSelectedHolder
-                  label: 'Browser on Common Superclass'
-                  itemValue: classMenuSpawnWithCommonSuperclass
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Browser on Projects'
-                  itemValue: classMenuSpawnClassProjects
-                  translateLabel: true
-                  isVisible: false
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Browser'
-                  itemValue: classMenuSpawnClass
-                  translateLabel: true
-                  isVisible: false
-                )
-
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Find'
-            translateLabel: true
-            isVisible: false
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'String...'
-                  itemValue: classMenuFindString
-                  translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Instance Variables'
-            translateLabel: true
-            isVisible: hasNonMetaSelectedHolder
-            submenuChannel: classInstanceVariablesMenu
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Class Instance Variables'
-            translateLabel: true
-            isVisible: hasMetaSelectedHolder
-            submenuChannel: classInstanceVariablesMenu
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Class Variables'
-            translateLabel: true
-            submenuChannel: classClassVariablesMenu
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'New'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  label: 'classNewSlice'
-                  translateLabel: true
-                  submenuChannel: classNewSlice
-                  isMenuSlice: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedHolder
-            label: 'Copy...'
-            itemValue: classMenuCopyAs
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Move'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasNonPrivateClassSelected
-                  label: 'To Category...'
-                  itemValue: classMenuMoveToCategory
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasNonPrivateClassSelected
-                  label: 'To Namespace...'
-                  itemValue: classMenuMoveToNamespace
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasNonPrivateClassSelected
-                  label: 'To Package...'
-                  itemValue: classMenuMoveToProject
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Make Private in...'
-                  itemValue: classMenuMakePrivateIn
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: canMakePublicClass
-                  label: 'Make Public'
-                  itemValue: classMenuMakePublic
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: canMakePublicClass
-                  label: 'Make Public in...'
-                  itemValue: classMenuMakePublicIn
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: canConvertToSiblingsHolder
-                  label: 'New Common Superclass with Children (Convert to Siblings)...'
-                  itemValue: classMenuChildrenToSiblings
-                  nameKey: convertToSibling
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: canInsertSuperclassHolder
-                  label: 'New Common Superclass (Insert Superclass)...'
-                  itemValue: classMenuInsertNewSuperclass
-                  nameKey: insertSuperclass
-                  translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedHolder
-            label: 'Rename...'
-            itemValue: classMenuRename
-            translateLabel: true
-            shortcutKey: Rename
-            ignoreShortcutKeys: true
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Safe Remove...'
-            itemValue: classMenuSaveRemove
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Remove...'
-            itemValue: classMenuRemove
-            translateLabel: true
-            shortcutKey: Delete
-            labelImage: (ResourceRetriever ToolbarIconLibrary erase16x16Icon 'Remove...')
-            ignoreShortcutKeys: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Compare'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasClassSelectedAndSourceCodeManagerHolder
-                  label: 'With Newest in Repository...'
-                  itemValue: classMenuCompareAgainstNewestInRepository
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-                  label: 'With Original in Repository...'
-                  itemValue: classMenuCompareAgainstOriginalInRepository
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-                  label: 'With Repository...'
-                  itemValue: classMenuCompareWithRepository
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasSingleClassSelected
-                  label: 'With File...'
-                  itemValue: classMenuCompareWithFile
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                  isVisible: smallTeamAvailable
-                )
-               (MenuItem
-                  label: 'With SmallTeam Version on Host'
-                  translateLabel: true
-                  isVisible: smallTeamAvailable
-                  submenuChannel: compareClassWithSmallTeamVersionMenu
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasSingleClassSelectedHolder
-                  label: 'With Class...'
-                  itemValue: classMenuCompareWithClass
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasExactlyTwoClassesSelectedHolder
-                  label: 'With each other'
-                  itemValue: classMenuCompareTwoSelectedClasses
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            label: 'Generate'
-            translateLabel: true
-            submenuChannel: classGenerateMenu
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            label: 'Static Analysis (Lint)'
-            translateLabel: true
-            submenuChannel: classCheckMenu
-            labelImage: (ResourceRetriever ToolbarIconLibrary lint16x16Icon 'Static Analysis (Lint)')
-          )
-         (MenuItem
-            label: 'Debug'
-            translateLabel: true
-            submenuChannel: classDebugMenu
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            label: 'Special'
-            translateLabel: true
-            submenuChannel: classSpecialMenu
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Search && Rewrite...'
-            itemValue: classMenuRewrite
-            translateLabel: true
-          )
-         (MenuItem
-            label: '-'
-            isVisible: false
-          )
-         (MenuItem
-            label: 'Update'
-            itemValue: classMenuUpdate
-            translateLabel: true
-            isVisible: false
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'FileOut'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'as...'
+		  itemValue: classMenuFileOutAs
+		  translateLabel: true
+		  isVisible: hasSingleClassSelectedHolder
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedAndCanFileOutXMLHolder
+		  label: 'XML as...'
+		  itemValue: classMenuFileOutXMLAs
+		  translateLabel: true
+		  isVisible: hasSingleClassSelectedHolder
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedAndCanFileOutSIFHolder
+		  label: 'SIF as...'
+		  itemValue: classMenuFileOutSIFAs
+		  translateLabel: true
+		  isVisible: hasSingleClassSelectedHolder
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedAndCanFileOutBinaryHolder
+		  label: 'Binary as...'
+		  itemValue: classMenuFileOutBinaryAs
+		  translateLabel: true
+		  isVisible: hasSingleClassSelectedHolder
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Each in...'
+		  itemValue: classMenuFileOutEachIn
+		  translateLabel: true
+		  isVisible: hasMultipleClassesSelectedHolder
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasProjectDefinitionSelectedHolder
+		  label: 'Build Support Files in...'
+		  itemValue: classMenuFileOutBuildSupportFiles
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedAndCanFileOutXMLHolder
+		  label: 'Each XML in...'
+		  itemValue: classMenuFileOutEachXMLIn
+		  translateLabel: true
+		  isVisible: hasMultipleClassesSelectedHolder
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedAndCanFileOutSIFHolder
+		  label: 'Each SIF in...'
+		  itemValue: classMenuFileOutEachSIFIn
+		  translateLabel: true
+		  isVisible: hasMultipleClassesSelectedHolder
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Each Binary in...'
+		  itemValue: classMenuFileOutEachBinaryIn
+		  translateLabel: true
+		  isVisible: hasMultipleClassesSelectedHolder
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedAndCanSendMailHolder
+		  label: 'Mail To...'
+		  itemValue: classMenuMailTo
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Copy Source to Clipboard'
+		  itemValue: classMenuCopySourceToClipboard
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: 'Repository Slice'
+	    translateLabel: true
+	    submenuChannel: classMenuSCMSlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Documentation'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'PrintOut'
+		  itemValue: classMenuPrintOut
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'PrintOut Protocol'
+		  itemValue: classMenuPrintOutProtocol
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'HTML Documentation'
+		  itemValue: classMenuDocumentation
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Save HTML Documentation As...'
+		  itemValue: classMenuSaveDocumentationAs
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'Show Comment'
+		  itemValue: classMenuComment
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: 'Show Hierarchy'
+		  itemValue: classMenuHierarchy
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: 'Show Definition'
+		  itemValue: classMenuDefinition
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasOOMPackageLoadedHolder
+		  label: 'Metrics Report'
+		  itemValue: classMenuMetrics
+		  translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Spawn'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Buffer with References to Class'
+		  itemValue: classMenuSpawnBufferWithClassReferences
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Buffer with References to Class or Subclass'
+		  itemValue: classMenuSpawnBufferWithClassOrSubclassReferences
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Buffer with Subclasses'
+		  itemValue: classMenuSpawnBufferWithAllSubclasses
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Buffer with Superclasses'
+		  itemValue: classMenuSpawnBufferWithAllSuperclasses
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasMultipleClassesSelectedHolder
+		  label: 'Buffer with Common Superclass'
+		  itemValue: classMenuSpawnBufferWithCommonSuperclass
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Buffer with Projects'
+		  itemValue: classMenuSpawnBufferWithClassProjects
+		  translateLabel: true
+		  isVisible: false
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Buffer'
+		  itemValue: classMenuSpawnClassBuffer
+		  translateLabel: true
+		  isVisible: false
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Browser on References to Class'
+		  itemValue: classMenuSpawnClassReferences
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Browser on References to Class or Subclass'
+		  itemValue: classMenuSpawnClassOrSubclassReferences
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Browser on Subclasses'
+		  itemValue: classMenuSpawnWithAllSubclasses
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Browser on Superclasses'
+		  itemValue: classMenuSpawnWithAllSuperclasses
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasMultipleClassesSelectedHolder
+		  label: 'Browser on Common Superclass'
+		  itemValue: classMenuSpawnWithCommonSuperclass
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Browser on Projects'
+		  itemValue: classMenuSpawnClassProjects
+		  translateLabel: true
+		  isVisible: false
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Browser'
+		  itemValue: classMenuSpawnClass
+		  translateLabel: true
+		  isVisible: false
+		)
+
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Find'
+	    translateLabel: true
+	    isVisible: false
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'String...'
+		  itemValue: classMenuFindString
+		  translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Instance Variables'
+	    translateLabel: true
+	    isVisible: hasNonMetaSelectedHolder
+	    submenuChannel: classInstanceVariablesMenu
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Class Instance Variables'
+	    translateLabel: true
+	    isVisible: hasMetaSelectedHolder
+	    submenuChannel: classInstanceVariablesMenu
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Class Variables'
+	    translateLabel: true
+	    submenuChannel: classClassVariablesMenu
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'New'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  label: 'classNewSlice'
+		  translateLabel: true
+		  submenuChannel: classNewSlice
+		  isMenuSlice: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedHolder
+	    label: 'Copy...'
+	    itemValue: classMenuCopyAs
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Move'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasNonPrivateClassSelected
+		  label: 'To Category...'
+		  itemValue: classMenuMoveToCategory
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasNonPrivateClassSelected
+		  label: 'To Namespace...'
+		  itemValue: classMenuMoveToNamespace
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasNonPrivateClassSelected
+		  label: 'To Package...'
+		  itemValue: classMenuMoveToProject
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Make Private in...'
+		  itemValue: classMenuMakePrivateIn
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: canMakePublicClass
+		  label: 'Make Public'
+		  itemValue: classMenuMakePublic
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: canMakePublicClass
+		  label: 'Make Public in...'
+		  itemValue: classMenuMakePublicIn
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: canConvertToSiblingsHolder
+		  label: 'New Common Superclass with Children (Convert to Siblings)...'
+		  itemValue: classMenuChildrenToSiblings
+		  nameKey: convertToSibling
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: canInsertSuperclassHolder
+		  label: 'New Common Superclass (Insert Superclass)...'
+		  itemValue: classMenuInsertNewSuperclass
+		  nameKey: insertSuperclass
+		  translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedHolder
+	    label: 'Rename...'
+	    itemValue: classMenuRename
+	    translateLabel: true
+	    shortcutKey: Rename
+	    ignoreShortcutKeys: true
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Safe Remove...'
+	    itemValue: classMenuSaveRemove
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Remove...'
+	    itemValue: classMenuRemove
+	    translateLabel: true
+	    shortcutKey: Delete
+	    labelImage: (ResourceRetriever ToolbarIconLibrary erase16x16Icon 'Remove...')
+	    ignoreShortcutKeys: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Compare'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasClassSelectedAndSourceCodeManagerHolder
+		  label: 'With Newest in Repository...'
+		  itemValue: classMenuCompareAgainstNewestInRepository
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+		  label: 'With Original in Repository...'
+		  itemValue: classMenuCompareAgainstOriginalInRepository
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+		  label: 'With Repository...'
+		  itemValue: classMenuCompareWithRepository
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasSingleClassSelected
+		  label: 'With File...'
+		  itemValue: classMenuCompareWithFile
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		  isVisible: smallTeamAvailable
+		)
+	       (MenuItem
+		  label: 'With SmallTeam Version on Host'
+		  translateLabel: true
+		  isVisible: smallTeamAvailable
+		  submenuChannel: compareClassWithSmallTeamVersionMenu
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasSingleClassSelectedHolder
+		  label: 'With Class...'
+		  itemValue: classMenuCompareWithClass
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasExactlyTwoClassesSelectedHolder
+		  label: 'With each other'
+		  itemValue: classMenuCompareTwoSelectedClasses
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: 'Generate'
+	    translateLabel: true
+	    submenuChannel: classGenerateMenu
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    label: 'Static Analysis (Lint)'
+	    translateLabel: true
+	    submenuChannel: classCheckMenu
+	    labelImage: (ResourceRetriever ToolbarIconLibrary lint16x16Icon 'Static Analysis (Lint)')
+	  )
+	 (MenuItem
+	    label: 'Debug'
+	    translateLabel: true
+	    submenuChannel: classDebugMenu
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    label: 'Special'
+	    translateLabel: true
+	    submenuChannel: classSpecialMenu
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Search && Rewrite...'
+	    itemValue: classMenuRewrite
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: '-'
+	    isVisible: false
+	  )
+	 (MenuItem
+	    label: 'Update'
+	    itemValue: classMenuUpdate
+	    translateLabel: true
+	    isVisible: false
+	  )
+	 )
+	nil
+	nil
       )
 
     "Modified: / 28-02-2012 / 08:57:35 / cg"
@@ -8035,22 +8194,22 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: '-'
-            isVisible: hasGroovySupport
-          )
-         (MenuItem
-            label: 'Groovy Class'
-            itemValue: classMenuNewGroovyClass
-            translateLabel: true
-            isVisible: hasGroovySupport
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: '-'
+	    isVisible: hasGroovySupport
+	  )
+	 (MenuItem
+	    label: 'Groovy Class'
+	    itemValue: classMenuNewGroovyClass
+	    translateLabel: true
+	    isVisible: hasGroovySupport
+	  )
+	 )
+	nil
+	nil
       )
 
     "Created: / 18-02-2012 / 17:01:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -8070,23 +8229,23 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: '-'
-            isVisible: isHaskellModulePresent
-          )
-         (MenuItem
-            enabled: isHaskellModulePresent
-            label: 'Haskell Module'
-            itemValue: classMenuNewHaskellModule
-            translateLabel: true
-            isVisible: isHaskellModulePresent
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: '-'
+	    isVisible: isHaskellModulePresent
+	  )
+	 (MenuItem
+	    enabled: isHaskellModulePresent
+	    label: 'Haskell Module'
+	    itemValue: classMenuNewHaskellModule
+	    translateLabel: true
+	    isVisible: isHaskellModulePresent
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -8104,23 +8263,64 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: '-'
-            isVisible: isJavaScriptMetaclassPresent
-          )
-         (MenuItem
-            enabled: isJavaScriptMetaclassPresent
-            label: 'JavaScript Class'
-            itemValue: classMenuNewJavaScriptClass
-            translateLabel: true
-          )
-         )
-        nil
-        nil
-      )
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: '-'
+	    isVisible: isJavaScriptMetaclassPresent
+	  )
+	 (MenuItem
+	    enabled: isJavaScriptMetaclassPresent
+	    label: 'JavaScript Class'
+	    itemValue: classMenuNewJavaScriptClass
+	    translateLabel: true
+	  )
+	 )
+	nil
+	nil
+      )
+!
+
+classNewLispClassSlice
+    "This resource specification was automatically generated
+     by the MenuEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the MenuEditor may not be able to read the specification."
+
+    "
+     MenuEditor new openOnClass:Tools::NewSystemBrowser andSelector:#classNewLispClassSlice
+     (Menu new fromLiteralArrayEncoding:(Tools::NewSystemBrowser classNewLispClassSlice)) startUp
+    "
+
+    <resource: #menu>
+
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: '-'
+	    isVisible: isLispMetaclassPresent
+	  )
+	 (MenuItem
+	    label: 'Scheme Namespace'
+	    itemValue: classMenuNewLispNamespace
+	    isVisible: isLispMetaclassPresent
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: 'Scheme Class'
+	    itemValue: classMenuNewLispClass
+	    isVisible: isLispMetaclassPresent
+	    translateLabel: true
+	  )
+	 )
+	nil
+	nil
+      )
+
+    "Created: / 13-05-2012 / 12:51:10 / cg"
 !
 
 classNewPLSQLClassSlice
@@ -8137,18 +8337,18 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'PLSQL ObjectType'
-            itemValue: classMenuNewPLSQLObjectType
-            translateLabel: true
-            isVisible: isPlsqlMetaclassPresent                           
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'PLSQL ObjectType'
+	    itemValue: classMenuNewPLSQLObjectType
+	    translateLabel: true
+	    isVisible: isPlsqlMetaclassPresent
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -8166,41 +8366,41 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: '-'
-            isVisible: isRubyMetaclassPresent
-          )
-         (MenuItem
-            label: 'Ruby class'
-            itemValue: classMenuNewRubyClass
-            translateLabel: true
-            isVisible: isRubyMetaclassPresent
-            labelImage: (ResourceRetriever ToolbarIconLibrary rubyClassBrowserIcon 'Ruby class')
-          )
-         (MenuItem
-            label: 'Ruby...'
-            translateLabel: true
-            isVisible: isRubyMetaclassPresent
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  label: 'Module'
-                  itemValue: classMenuNewRubyModule
-                  translateLabel: true
-                  isVisible: isRubyMetaclassPresent
-                )
-               )
-              nil
-              nil
-            )
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: '-'
+	    isVisible: isRubyMetaclassPresent
+	  )
+	 (MenuItem
+	    label: 'Ruby class'
+	    itemValue: classMenuNewRubyClass
+	    translateLabel: true
+	    isVisible: isRubyMetaclassPresent
+	    labelImage: (ResourceRetriever ToolbarIconLibrary rubyClassBrowserIcon 'Ruby class')
+	  )
+	 (MenuItem
+	    label: 'Ruby...'
+	    translateLabel: true
+	    isVisible: isRubyMetaclassPresent
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  label: 'Module'
+		  itemValue: classMenuNewRubyModule
+		  translateLabel: true
+		  isVisible: isRubyMetaclassPresent
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -8219,77 +8419,84 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'Class'
-            itemValue: classMenuNewClass
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedHolder
-            label: 'Subclass'
-            itemValue: classMenuNewSubclass
-            translateLabel: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Smalltalk Class Slice'
-            nameKey: classNewSmalltalkSlice
-            translateLabel: true
-            submenuChannel: classNewSmalltalkSlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            label: 'Ruby Class Slice'
-            nameKey: classNewRubyClassSlice
-            translateLabel: true
-            submenuChannel: classNewRubyClassSlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            label: 'JavaScript Class Slice'
-            nameKey: classNewJavaScriptClassSlice
-            translateLabel: true
-            submenuChannel: classNewJavaScriptClassSlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            label: 'Groovy Class Slice'
-            nameKey: classNewGroovyClassSlice
-            translateLabel: true
-            submenuChannel: classNewGroovyClassSlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            label: 'Haskell Class Slice'
-            nameKey: classNewHaskellClassSlice
-            translateLabel: true
-            submenuChannel: classNewHaskellClassSlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            label: 'PLSQL Class Slice'
-            nameKey: classNewPLSQLClassSlice
-            translateLabel: true
-            submenuChannel: classNewPLSQLClassSlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Class Wizard'
-            itemValue: classMenuOpenClassCreationWizard
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary newClassWizardIcon 'Class Wizard')
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'Class'
+	    itemValue: classMenuNewClass
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedHolder
+	    label: 'Subclass'
+	    itemValue: classMenuNewSubclass
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Smalltalk Class Slice'
+	    nameKey: classNewSmalltalkSlice
+	    translateLabel: true
+	    submenuChannel: classNewSmalltalkSlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: 'Ruby Class Slice'
+	    nameKey: classNewRubyClassSlice
+	    translateLabel: true
+	    submenuChannel: classNewRubyClassSlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: 'JavaScript Class Slice'
+	    nameKey: classNewJavaScriptClassSlice
+	    translateLabel: true
+	    submenuChannel: classNewJavaScriptClassSlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: 'Groovy Class Slice'
+	    nameKey: classNewGroovyClassSlice
+	    translateLabel: true
+	    submenuChannel: classNewGroovyClassSlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: 'Lisp Class Slice'
+	    nameKey: classNewLispClassSlice
+	    translateLabel: true
+	    submenuChannel: classNewLispClassSlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: 'Haskell Class Slice'
+	    nameKey: classNewHaskellClassSlice
+	    translateLabel: true
+	    submenuChannel: classNewHaskellClassSlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: 'PLSQL Class Slice'
+	    nameKey: classNewPLSQLClassSlice
+	    translateLabel: true
+	    submenuChannel: classNewPLSQLClassSlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Class Wizard'
+	    itemValue: classMenuOpenClassCreationWizard
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary newClassWizardIcon 'Class Wizard')
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -8307,91 +8514,91 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'Smalltalk Class'
-            itemValue: classMenuNewSmalltalkClass
-            translateLabel: true
-          )
-         (MenuItem
-            label: 'Smalltalk...'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasSingleLoadedNonJavascriptClassSelectedHolder
-                  label: 'Private Class'
-                  itemValue: classMenuNewPrivateClass
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'Application'
-                  itemValue: classMenuNewApplication
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: 'Dialog'
-                  itemValue: classMenuNewDialog
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: 'WebService'
-                  itemValue: classMenuNewWebService
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: 'WebApplication'
-                  itemValue: classMenuNewWebApplication
-                  translateLabel: true
-                  isVisible: false
-                )
-               (MenuItem
-                  label: 'Widget (View)'
-                  itemValue: classMenuNewWidgetClass
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: 'Standalone Startup'
-                  itemValue: classMenuNewStandaloneStartupClass
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'Error'
-                  itemValue: classMenuNewError
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: 'Notification'
-                  itemValue: classMenuNewNotification
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: 'Shared Pool'
-                  itemValue: classMenuNewSharedPool
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: 'TestCase'
-                  itemValue: classMenuNewTestCase
-                  translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'Smalltalk Class'
+	    itemValue: classMenuNewSmalltalkClass
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: 'Smalltalk...'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasSingleLoadedNonJavascriptClassSelectedHolder
+		  label: 'Private Class'
+		  itemValue: classMenuNewPrivateClass
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'Application'
+		  itemValue: classMenuNewApplication
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: 'Dialog'
+		  itemValue: classMenuNewDialog
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: 'WebService'
+		  itemValue: classMenuNewWebService
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: 'WebApplication'
+		  itemValue: classMenuNewWebApplication
+		  translateLabel: true
+		  isVisible: false
+		)
+	       (MenuItem
+		  label: 'Widget (View)'
+		  itemValue: classMenuNewWidgetClass
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: 'Standalone Startup'
+		  itemValue: classMenuNewStandaloneStartupClass
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'Error'
+		  itemValue: classMenuNewError
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: 'Notification'
+		  itemValue: classMenuNewNotification
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: 'Shared Pool'
+		  itemValue: classMenuNewSharedPool
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: 'TestCase'
+		  itemValue: classMenuNewTestCase
+		  translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 )
+	nil
+	nil
       )
 
     "Modified: / 17-02-2012 / 22:03:09 / cg"
@@ -8413,16 +8620,16 @@
 
     ^
      #(Menu
-        (
-         (MenuItem
-            label: 'Compare with Version On Host'
-            translateLabel: true
-            submenuChannel: compareClassWithSmallTeamVersionMenu
-            keepLinkedMenu: true
-          )
-         )
-        nil
-        nil
+	(
+	 (MenuItem
+	    label: 'Compare with Version On Host'
+	    translateLabel: true
+	    submenuChannel: compareClassWithSmallTeamVersionMenu
+	    keepLinkedMenu: true
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -8440,118 +8647,118 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasAnyUnloadedClassSelectedHolder
-            label: 'Load'
-            itemValue: classMenuLoad
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectDefinitionWithAnyUnloadedClassSelectedHolder
-            label: 'Load Project'
-            itemValue: classMenuLoadProject
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Unload'
-            itemValue: classMenuUnload
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Initialize Class(es)'
-            itemValue: classMenuInitialize
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Compile Lazy Methods'
-            itemValue: classMenuCompileLazyMethods
-            translateLabel: true
-            isVisible: false
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Reload'
-            itemValue: classMenuReload
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasClassSelectedWhichCanBeIncludedInProjectHolder
-            label: 'Include in Project as Compiled Class'
-            itemValue: classMenuIncludeInProject
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasClassSelectedWhichCanBeMadeAutoloadedInProject
-            label: 'Include in Project as Autoloaded Class'
-            itemValue: classMenuMakeAutoloadedInProject
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasClassSelectedWhichCanBeExcludedFromProject
-            label: 'Exclude from Project'
-            itemValue: classMenuExcludeFromProject
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasSingleLoadedClassSelectedHolder
-            label: 'Primitive Definitions'
-            itemValue: classMenuPrimitiveDefinitions
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleLoadedClassSelectedHolder
-            label: 'Primitive Functions'
-            itemValue: classMenuPrimitiveFunctions
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleLoadedClassSelectedHolder
-            label: 'Primitive Variables'
-            itemValue: classMenuPrimitiveVariables
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Remove from ChangeSet'
-            itemValue: classMenuCleanUpChangeSet
-            translateLabel: true
-          )
-         (MenuItem
-            label: 'Special ClassOPS'
-            translateLabel: true
-            submenuChannel: classOperationsMenu
-            isMenuSlice: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasAnyUnloadedClassSelectedHolder
+	    label: 'Load'
+	    itemValue: classMenuLoad
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectDefinitionWithAnyUnloadedClassSelectedHolder
+	    label: 'Load Project'
+	    itemValue: classMenuLoadProject
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Unload'
+	    itemValue: classMenuUnload
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Initialize Class(es)'
+	    itemValue: classMenuInitialize
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Compile Lazy Methods'
+	    itemValue: classMenuCompileLazyMethods
+	    translateLabel: true
+	    isVisible: false
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Reload'
+	    itemValue: classMenuReload
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedWhichCanBeIncludedInProjectHolder
+	    label: 'Include in Project as Compiled Class'
+	    itemValue: classMenuIncludeInProject
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedWhichCanBeMadeAutoloadedInProject
+	    label: 'Include in Project as Autoloaded Class'
+	    itemValue: classMenuMakeAutoloadedInProject
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedWhichCanBeExcludedFromProject
+	    label: 'Exclude from Project'
+	    itemValue: classMenuExcludeFromProject
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasSingleLoadedClassSelectedHolder
+	    label: 'Primitive Definitions'
+	    itemValue: classMenuPrimitiveDefinitions
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleLoadedClassSelectedHolder
+	    label: 'Primitive Functions'
+	    itemValue: classMenuPrimitiveFunctions
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleLoadedClassSelectedHolder
+	    label: 'Primitive Variables'
+	    itemValue: classMenuPrimitiveVariables
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Remove from ChangeSet'
+	    itemValue: classMenuCleanUpChangeSet
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: 'Special ClassOPS'
+	    translateLabel: true
+	    submenuChannel: classOperationsMenu
+	    isMenuSlice: true
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -8569,145 +8776,145 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: canUseRefactoringSupport
-            label: 'Variables'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasTemporaryVariableSelectedInCodeViewHolder
-                  label: 'Rename Local Variable...'
-                  itemValue: codeMenuRenameTemporary
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasTemporaryVariableSelectedInCodeViewHolder
-                  label: 'Move to Inner Scope...'
-                  itemValue: codeMenuMoveVariableToInnerScope
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasTemporaryVariableSelectedInCodeViewHolder
-                  label: 'Make Instance Variable'
-                  itemValue: codeMenuMakeInstanceVariable
-                  translateLabel: true
-                  isVisible: hasNotMultipleTemporaryVariablesSelectedInCodeViewHolder
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasMultipleTemporaryVariablesSelectedInCodeViewHolder
-                  label: 'Make Instance Variables'
-                  itemValue: codeMenuMakeInstanceVariable
-                  translateLabel: true
-                  isVisible: hasMultipleTemporaryVariablesSelectedInCodeViewHolder
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasUndefinedUppercaseIdentifierSelectedInCodeViewHolder
-                  label: 'Declare as Class Variable'
-                  itemValue: codeMenuDeclareSelectionAsClassVariable
-                  translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasSingleMethodSelectedAndSelectionInCodeViewAndCanUseRefactoringSupportHolder
-            label: 'Inline Message'
-            itemValue: codeMenuInlineMessage
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleMethodSelectedAndSelectionInCodeViewAndCanUseRefactoringSupportHolder
-            label: 'Extract Selection to Temporary...'
-            itemValue: codeMenuExtractSelectionToTemporary
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleMethodSelectedAndSelectionInCodeViewAndCanUseRefactoringSupportHolder
-            label: 'Extract Method...'
-            itemValue: codeMenuExtractMethod
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleMethodSelectedAndSelectionInCodeViewAndCanUseRefactoringSupportHolder
-            label: 'Extract Method to Component...'
-            itemValue: codeMenuExtractMethodToComponent
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasSingleMethodSelectedAndCanUseRefactoringSupportHolder
-            label: 'Add Parameter to Method...'
-            itemValue: codeMenuAddParameter
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleMethodSelectedAndSelectionInCodeViewAndSingleSelectedMethodHasParameterAndCanUseRefactoringSupportHolder
-            label: 'Inline Parameter of Method'
-            itemValue: codeMenuInlineParameter
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleMethodSelectedAndSelectionInCodeViewAndSingleSelectedMethodHasParameterAndCanUseRefactoringSupportHolder
-            label: 'Remove Parameter from Method'
-            itemValue: codeMenuRemoveParameter
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasSingleMethodSelectedAndCanUseRefactoringSupportHolder
-            label: 'Format'
-            itemValue: codeMenuFormat
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-            isVisible: canLoadRefactoringSupport
-          )
-         (MenuItem
-            label: 'Load Refactoring and Undo Features'
-            itemValue: doLoadRefactoringSupport
-            translateLabel: true
-            isVisible: canLoadRefactoringSupport
-            showBusyCursorWhilePerforming: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: canUseRefactoringSupport
+	    label: 'Variables'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasTemporaryVariableSelectedInCodeViewHolder
+		  label: 'Rename Local Variable...'
+		  itemValue: codeMenuRenameTemporary
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasTemporaryVariableSelectedInCodeViewHolder
+		  label: 'Move to Inner Scope...'
+		  itemValue: codeMenuMoveVariableToInnerScope
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasTemporaryVariableSelectedInCodeViewHolder
+		  label: 'Make Instance Variable'
+		  itemValue: codeMenuMakeInstanceVariable
+		  translateLabel: true
+		  isVisible: hasNotMultipleTemporaryVariablesSelectedInCodeViewHolder
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasMultipleTemporaryVariablesSelectedInCodeViewHolder
+		  label: 'Make Instance Variables'
+		  itemValue: codeMenuMakeInstanceVariable
+		  translateLabel: true
+		  isVisible: hasMultipleTemporaryVariablesSelectedInCodeViewHolder
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasUndefinedUppercaseIdentifierSelectedInCodeViewHolder
+		  label: 'Declare as Class Variable'
+		  itemValue: codeMenuDeclareSelectionAsClassVariable
+		  translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasSingleMethodSelectedAndSelectionInCodeViewAndCanUseRefactoringSupportHolder
+	    label: 'Inline Message'
+	    itemValue: codeMenuInlineMessage
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleMethodSelectedAndSelectionInCodeViewAndCanUseRefactoringSupportHolder
+	    label: 'Extract Selection to Temporary...'
+	    itemValue: codeMenuExtractSelectionToTemporary
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleMethodSelectedAndSelectionInCodeViewAndCanUseRefactoringSupportHolder
+	    label: 'Extract Method...'
+	    itemValue: codeMenuExtractMethod
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleMethodSelectedAndSelectionInCodeViewAndCanUseRefactoringSupportHolder
+	    label: 'Extract Method to Component...'
+	    itemValue: codeMenuExtractMethodToComponent
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasSingleMethodSelectedAndCanUseRefactoringSupportHolder
+	    label: 'Add Parameter to Method...'
+	    itemValue: codeMenuAddParameter
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleMethodSelectedAndSelectionInCodeViewAndSingleSelectedMethodHasParameterAndCanUseRefactoringSupportHolder
+	    label: 'Inline Parameter of Method'
+	    itemValue: codeMenuInlineParameter
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleMethodSelectedAndSelectionInCodeViewAndSingleSelectedMethodHasParameterAndCanUseRefactoringSupportHolder
+	    label: 'Remove Parameter from Method'
+	    itemValue: codeMenuRemoveParameter
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasSingleMethodSelectedAndCanUseRefactoringSupportHolder
+	    label: 'Format'
+	    itemValue: codeMenuFormat
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	    isVisible: canLoadRefactoringSupport
+	  )
+	 (MenuItem
+	    label: 'Load Refactoring and Undo Features'
+	    itemValue: doLoadRefactoringSupport
+	    translateLabel: true
+	    isVisible: canLoadRefactoringSupport
+	    showBusyCursorWhilePerforming: true
+	  )
+	 )
+	nil
+	nil
       )
 
     "Modified: / 04-07-2011 / 17:51:17 / cg"
@@ -8727,92 +8934,92 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasSingleProjectOrProjectDefinitionSelected
-            label: 'Make.spec'
-            itemValue: projectMenuShowGeneratedBuildFile:
-            translateLabel: true
-            argument: 'Make.spec'
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleProjectOrProjectDefinitionSelected
-            label: 'Make.proto'
-            itemValue: projectMenuShowGeneratedBuildFile:
-            translateLabel: true
-            argument: 'Make.proto'
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleProjectOrProjectDefinitionSelected
-            label: 'bc.mak'
-            itemValue: projectMenuShowGeneratedBuildFile:
-            translateLabel: true
-            argument: 'bc.mak'
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleProjectOrProjectDefinitionSelected
-            label: 'libInit.cc'
-            itemValue: projectMenuShowGeneratedBuildFile:
-            translateLabel: true
-            argument: 'libInit.cc'
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleProjectOrProjectDefinitionSelected
-            label: 'modules.stx'
-            itemValue: projectMenuShowGeneratedBuildFile:
-            translateLabel: true
-            argument: 'modules.stx'
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleProjectOrProjectDefinitionSelected
-            label: 'lib.rc / app.rc'
-            itemValue: projectMenuShowGeneratedBuildFile:
-            translateLabel: true
-            argument: 'lib.rc'
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleProjectOrProjectDefinitionSelected
-            label: 'app.nsi'
-            itemValue: projectMenuShowGeneratedBuildFile:
-            translateLabel: true
-            argument: 'app.nsi'
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleProjectOrProjectDefinitionSelected
-            label: 'abbrev.stc'
-            itemValue: projectMenuShowGeneratedBuildFile:
-            translateLabel: true
-            argument: 'abbrev.stc'
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleProjectOrProjectDefinitionSelected
-            label: 'loadAll'
-            itemValue: projectMenuShowGeneratedBuildFile:
-            translateLabel: true
-            argument: 'loadAll'
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleProjectOrProjectDefinitionSelected
-            label: 'bmake.bat'
-            itemValue: projectMenuShowGeneratedBuildFile:
-            translateLabel: true
-            argument: 'bmake.bat'
-            showBusyCursorWhilePerforming: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasSingleProjectOrProjectDefinitionSelected
+	    label: 'Make.spec'
+	    itemValue: projectMenuShowGeneratedBuildFile:
+	    translateLabel: true
+	    argument: 'Make.spec'
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleProjectOrProjectDefinitionSelected
+	    label: 'Make.proto'
+	    itemValue: projectMenuShowGeneratedBuildFile:
+	    translateLabel: true
+	    argument: 'Make.proto'
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleProjectOrProjectDefinitionSelected
+	    label: 'bc.mak'
+	    itemValue: projectMenuShowGeneratedBuildFile:
+	    translateLabel: true
+	    argument: 'bc.mak'
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleProjectOrProjectDefinitionSelected
+	    label: 'libInit.cc'
+	    itemValue: projectMenuShowGeneratedBuildFile:
+	    translateLabel: true
+	    argument: 'libInit.cc'
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleProjectOrProjectDefinitionSelected
+	    label: 'modules.stx'
+	    itemValue: projectMenuShowGeneratedBuildFile:
+	    translateLabel: true
+	    argument: 'modules.stx'
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleProjectOrProjectDefinitionSelected
+	    label: 'lib.rc / app.rc'
+	    itemValue: projectMenuShowGeneratedBuildFile:
+	    translateLabel: true
+	    argument: 'lib.rc'
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleProjectOrProjectDefinitionSelected
+	    label: 'app.nsi'
+	    itemValue: projectMenuShowGeneratedBuildFile:
+	    translateLabel: true
+	    argument: 'app.nsi'
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleProjectOrProjectDefinitionSelected
+	    label: 'abbrev.stc'
+	    itemValue: projectMenuShowGeneratedBuildFile:
+	    translateLabel: true
+	    argument: 'abbrev.stc'
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleProjectOrProjectDefinitionSelected
+	    label: 'loadAll'
+	    itemValue: projectMenuShowGeneratedBuildFile:
+	    translateLabel: true
+	    argument: 'loadAll'
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleProjectOrProjectDefinitionSelected
+	    label: 'bmake.bat'
+	    itemValue: projectMenuShowGeneratedBuildFile:
+	    translateLabel: true
+	    argument: 'bmake.bat'
+	    showBusyCursorWhilePerforming: true
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -8832,25 +9039,25 @@
 
     ^
      #(Menu
-        (
-         (MenuItem
-            label: 'Insert'
-            itemValue: editModeInsert
-            translateLabel: true
-          )
-         (MenuItem
-            label: 'Overwrite'
-            itemValue: editModeOverwrite
-            translateLabel: true
-          )
-         (MenuItem
-            label: 'Insert Selecting'
-            itemValue: editModeInsertAndSelect
-            translateLabel: true
-          )
-         )
-        nil
-        nil
+	(
+	 (MenuItem
+	    label: 'Insert'
+	    itemValue: editModeInsert
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: 'Overwrite'
+	    itemValue: editModeOverwrite
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: 'Insert Selecting'
+	    itemValue: editModeInsertAndSelect
+	    translateLabel: true
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -8868,25 +9075,25 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'Navigate to Selected Class'
-            itemValue: inheritanceMenuNavigateToClass
-            translateLabel: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Update'
-            itemValue: inheritanceMenuUpdate
-            translateLabel: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'Navigate to Selected Class'
+	    itemValue: inheritanceMenuNavigateToClass
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Update'
+	    itemValue: inheritanceMenuUpdate
+	    translateLabel: true
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -8904,53 +9111,53 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'All'
-            itemValue: classMenuCheckAll
-            translateLabel: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Errors'
-            itemValue: classMenuCheckErrors
-            translateLabel: true
-          )
-         (MenuItem
-            label: 'Possible Errors'
-            itemValue: classMenuCheckWarnings
-            translateLabel: true
-          )
-         (MenuItem
-            label: 'Style'
-            itemValue: classMenuCheckStyle
-            translateLabel: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Individual Checks...'
-            itemValue: classMenuCheckIndividual
-            translateLabel: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Check Compilability'
-            itemValue: classMenuCheckCompilability
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'All'
+	    itemValue: classMenuCheckAll
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Errors'
+	    itemValue: classMenuCheckErrors
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: 'Possible Errors'
+	    itemValue: classMenuCheckWarnings
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: 'Style'
+	    itemValue: classMenuCheckStyle
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Individual Checks...'
+	    itemValue: classMenuCheckIndividual
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Check Compilability'
+	    itemValue: classMenuCheckCompilability
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -8969,167 +9176,167 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'B&uffers'
-            translateLabel: true
-            submenuChannel: bufferMenu
-          )
-         (MenuItem
-            label: 'Browse'
-            translateLabel: true
-            submenuChannel: browseMenu
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            label: 'Find'
-            translateLabel: true
-            isVisible: searchMenuVisible
-            submenuChannel: searchMenu
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            label: 'Find'
-            translateLabel: true
-            isVisible: searchMenuInMethodListVisible
-            submenuChannel: searchMenuInMethodList
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            label: 'View'
-            translateLabel: true
-            isVisible: viewMenuVisible
-            submenuChannel: viewMenu
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            label: 'View'
-            translateLabel: true
-            isVisible: viewMenuForMethodListVisible
-            submenuChannel: viewMenuForMethodList
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            label: 'Package'
-            translateLabel: true
-            isVisible: projectMenuVisible
-            submenuChannel: projectMenu
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            label: 'Namespace'
-            translateLabel: true
-            isVisible: nameSpaceMenuVisible
-            submenuChannel: nameSpaceMenu
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            label: 'Category'
-            translateLabel: true
-            isVisible: categoryMenuVisible
-            submenuChannel: categoryMenu
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            label: 'Hierarchy'
-            translateLabel: true
-            isVisible: classHierarchyMenuVisible
-            submenuChannel: classHierarchyMenu
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            label: 'Class'
-            translateLabel: true
-            isVisible: classMenuVisible
-            submenuChannel: classMenu
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            label: 'Protocol'
-            translateLabel: true
-            isVisible: protocolMenuVisible
-            submenuChannel: protocolMenu
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            label: 'Selector'
-            translateLabel: true
-            isVisible: selectorMenuVisible
-            submenuChannel: selectorMenu
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            label: 'Code'
-            translateLabel: true
-            isVisible: codeMenuVisible
-            submenuChannel: codeMenu
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            label: 'Debug'
-            translateLabel: true
-            isVisible: selectorMenuVisible
-            submenuChannel: methodDebugMenu
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            label: 'Operations'
-            translateLabel: true
-            submenuChannel: operationsMenu
-          )
-         (MenuItem
-            label: 'MENU_Help'
-            translateLabel: true
-            startGroup: conditionalRight
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  label: 'Browser Documentation'
-                  itemValue: openDocumentation
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: 'Refactorings'
-                  itemValue: openRefactoringDocumentation
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'Class Documentation'
-                  itemValue: openClassDocumentation
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: 'ST/X Documentation'
-                  itemValue: openSTXDocumentation
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: 'Keyword Index'
-                  itemValue: openKeywordIndexDocumentation
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'About SystemBrowser...'
-                  itemValue: openAboutThisApplication
-                  translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'B&uffers'
+	    translateLabel: true
+	    submenuChannel: bufferMenu
+	  )
+	 (MenuItem
+	    label: 'Browse'
+	    translateLabel: true
+	    submenuChannel: browseMenu
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    label: 'Find'
+	    translateLabel: true
+	    isVisible: searchMenuVisible
+	    submenuChannel: searchMenu
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    label: 'Find'
+	    translateLabel: true
+	    isVisible: searchMenuInMethodListVisible
+	    submenuChannel: searchMenuInMethodList
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    label: 'View'
+	    translateLabel: true
+	    isVisible: viewMenuVisible
+	    submenuChannel: viewMenu
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    label: 'View'
+	    translateLabel: true
+	    isVisible: viewMenuForMethodListVisible
+	    submenuChannel: viewMenuForMethodList
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    label: 'Package'
+	    translateLabel: true
+	    isVisible: projectMenuVisible
+	    submenuChannel: projectMenu
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    label: 'Namespace'
+	    translateLabel: true
+	    isVisible: nameSpaceMenuVisible
+	    submenuChannel: nameSpaceMenu
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    label: 'Category'
+	    translateLabel: true
+	    isVisible: categoryMenuVisible
+	    submenuChannel: categoryMenu
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    label: 'Hierarchy'
+	    translateLabel: true
+	    isVisible: classHierarchyMenuVisible
+	    submenuChannel: classHierarchyMenu
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    label: 'Class'
+	    translateLabel: true
+	    isVisible: classMenuVisible
+	    submenuChannel: classMenu
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    label: 'Protocol'
+	    translateLabel: true
+	    isVisible: protocolMenuVisible
+	    submenuChannel: protocolMenu
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    label: 'Selector'
+	    translateLabel: true
+	    isVisible: selectorMenuVisible
+	    submenuChannel: selectorMenu
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    label: 'Code'
+	    translateLabel: true
+	    isVisible: codeMenuVisible
+	    submenuChannel: codeMenu
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    label: 'Debug'
+	    translateLabel: true
+	    isVisible: selectorMenuVisible
+	    submenuChannel: methodDebugMenu
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    label: 'Operations'
+	    translateLabel: true
+	    submenuChannel: operationsMenu
+	  )
+	 (MenuItem
+	    label: 'MENU_Help'
+	    translateLabel: true
+	    startGroup: conditionalRight
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  label: 'Browser Documentation'
+		  itemValue: openDocumentation
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: 'Refactorings'
+		  itemValue: openRefactoringDocumentation
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'Class Documentation'
+		  itemValue: openClassDocumentation
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: 'ST/X Documentation'
+		  itemValue: openSTXDocumentation
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: 'Keyword Index'
+		  itemValue: openKeywordIndexDocumentation
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'About SystemBrowser...'
+		  itemValue: openAboutThisApplication
+		  translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -9148,206 +9355,206 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasMethodWithWrapSelectedHolder
-            label: 'Remove Break/Trace'
-            itemValue: debugMenuRemoveBreakOrTrace
-            translateLabel: true
-            isVisible: hasNoMethodOrMixedWrapsSelectedHolder
-          )
-         (MenuItem
-            enabled: hasMethodWithBreakPointSelectedHolder
-            label: 'Remove Break'
-            itemValue: debugMenuRemoveBreakOrTrace
-            translateLabel: true
-            isVisible: hasOnlyMethodsWithBreakPointSelected
-          )
-         (MenuItem
-            enabled: hasMethodWithTracePointSelectedHolder
-            label: 'Remove Trace'
-            itemValue: debugMenuRemoveBreakOrTrace
-            translateLabel: true
-            isVisible: hasOnlyMethodsWithTracePointSelected
-          )
-         (MenuItem
-            enabled: anyBreakOrTracePointsAreSetHolder
-            label: 'Remove all Break- && Tracepoints'
-            itemValue: debugMenuRemoveAllBreakpoints
-            translateLabel: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasMethodSelectedHolder
-            label: 'Breakpoint'
-            itemValue: debugMenuBreakPoint
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasMethodSelectedHolder
-            label: 'Breakpoint in Process...'
-            itemValue: debugMenuBreakPointIn
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasMethodSelectedHolder
-            label: 'Breakpoint for Instances Of...'
-            itemValue: debugMenuBreakPointFor
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasMethodSelectedHolder
-            label: 'Breakpoint After...'
-            itemValue: debugMenuBreakPointAfter
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasMethodSelectedHolder
-            label: 'Breakpoint If...'
-            itemValue: debugMenuBreakPointIf
-            translateLabel: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasMethodSelectedHolder
-            label: 'Trace'
-            itemValue: debugMenuTrace
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasMethodSelectedHolder
-            label: 'Trace Sender'
-            itemValue: debugMenuTraceSender
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasMethodSelectedHolder
-            label: 'Trace Full Walkback'
-            itemValue: debugMenuTraceFullWalkback
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasUpdateMethodSelectedHolder
-            label: 'Trace Change->Update Reason'
-            itemValue: debugMenuTraceChangeUpdate
-            translateLabel: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasMethodSelectedHolder
-            label: 'Start Message Tally'
-            itemValue: debugMenuStartMessageTally
-            translateLabel: true
-            isVisible: false
-          )
-         (MenuItem
-            label: '-'
-            isVisible: false
-          )
-         (MenuItem
-            enabled: hasMethodSelectedHolder
-            label: 'Start Timing'
-            itemValue: debugMenuStartTiming
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasMethodSelectedHolder
-            label: 'Start Counting'
-            itemValue: debugMenuStartCounting
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasMethodSelectedHolder
-            label: 'Start Memory Usage'
-            itemValue: debugMenuStartMemoryUsage
-            translateLabel: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasAnyTestCaseSelectedHolder
-            label: 'Run Tests'
-            itemValue: runTestCases
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasAnyTestCaseSelectedHolder
-            label: 'Debug Tests'
-            itemValue: runTestCasesWithDebug
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasAnyTestCaseSelectedHolder
-            label: 'Run Tests for Coverage'
-            itemValue: runTestCasesForCoverage
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasMethodSelectedAndInstrumentingCompilerExistsHolder
-            label: 'Recompile Method(s) with Instrumentation'
-            itemValue: debugMenuRecompileMethodsInstrumented
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasClassSelectedAndInstrumentingCompilerExistsHolder
-            label: 'Recompile Class(es) with Instrumentation'
-            itemValue: classMenuRecompileInstrumented
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectSelectedAndInstrumentingCompilerExistsHolder
-            label: 'Recompile Project(s) with Instrumentation'
-            itemValue: projectMenuRecompileInstrumented
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasMethodSelectedAndInstrumentingCompilerExistsAndOOMPackageLoadedHolder
-            label: 'Call Graph'
-            itemValue: debugMenuOpenCallGraphForMethods
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: 'Clear all Coverage Info (Systemwide)'
-            itemValue: debugMenuClearCoverageInfo
-            translateLabel: true
-          )
-         (MenuItem
-            label: 'Enable Coverage Recording in all Processes'
-            itemValue: debugMenuEnableGlobalCoverageRecording
-            translateLabel: true
-            isVisible: globalCoverageRecordingIsDisabled
-          )
-         (MenuItem
-            label: 'Disable Coverage Recording in all Processes'
-            itemValue: debugMenuDisableGlobalCoverageRecording
-            translateLabel: true
-            isVisible: globalCoverageRecordingIsEnabled
-          )
-         )
-        nil
-        nil
-      )
-
-    "Modified: / 28-02-2012 / 11:31:30 / cg"
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasMethodWithWrapSelectedHolder
+	    label: 'Remove Break/Trace'
+	    itemValue: debugMenuRemoveBreakOrTrace
+	    translateLabel: true
+	    isVisible: hasNoMethodOrMixedWrapsSelectedHolder
+	  )
+	 (MenuItem
+	    enabled: hasMethodWithBreakPointSelectedHolder
+	    label: 'Remove Break'
+	    itemValue: debugMenuRemoveBreakOrTrace
+	    translateLabel: true
+	    isVisible: hasOnlyMethodsWithBreakPointSelected
+	  )
+	 (MenuItem
+	    enabled: hasMethodWithTracePointSelectedHolder
+	    label: 'Remove Trace'
+	    itemValue: debugMenuRemoveBreakOrTrace
+	    translateLabel: true
+	    isVisible: hasOnlyMethodsWithTracePointSelected
+	  )
+	 (MenuItem
+	    enabled: anyBreakOrTracePointsAreSetHolder
+	    label: 'Remove all Break- && Tracepoints'
+	    itemValue: debugMenuRemoveAllBreakpoints
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasMethodSelectedHolder
+	    label: 'Breakpoint'
+	    itemValue: debugMenuBreakPoint
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: hasMethodSelectedHolder
+	    label: 'Breakpoint in Process...'
+	    itemValue: debugMenuBreakPointIn
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: hasMethodSelectedHolder
+	    label: 'Breakpoint for Instances Of...'
+	    itemValue: debugMenuBreakPointFor
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: hasMethodSelectedHolder
+	    label: 'Breakpoint After...'
+	    itemValue: debugMenuBreakPointAfter
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: hasMethodSelectedHolder
+	    label: 'Breakpoint If...'
+	    itemValue: debugMenuBreakPointIf
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasMethodSelectedHolder
+	    label: 'Trace'
+	    itemValue: debugMenuTrace
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: hasMethodSelectedHolder
+	    label: 'Trace Sender'
+	    itemValue: debugMenuTraceSender
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: hasMethodSelectedHolder
+	    label: 'Trace Full Walkback'
+	    itemValue: debugMenuTraceFullWalkback
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: hasUpdateMethodSelectedHolder
+	    label: 'Trace Change->Update Reason'
+	    itemValue: debugMenuTraceChangeUpdate
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasMethodSelectedHolder
+	    label: 'Start Message Tally'
+	    itemValue: debugMenuStartMessageTally
+	    translateLabel: true
+	    isVisible: false
+	  )
+	 (MenuItem
+	    label: '-'
+	    isVisible: false
+	  )
+	 (MenuItem
+	    enabled: hasMethodSelectedHolder
+	    label: 'Start Timing'
+	    itemValue: debugMenuStartTiming
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: hasMethodSelectedHolder
+	    label: 'Start Counting'
+	    itemValue: debugMenuStartCounting
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: hasMethodSelectedHolder
+	    label: 'Start Memory Usage'
+	    itemValue: debugMenuStartMemoryUsage
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasAnyTestCaseSelectedHolder
+	    label: 'Run Tests'
+	    itemValue: runTestCases
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasAnyTestCaseSelectedHolder
+	    label: 'Debug Tests'
+	    itemValue: runTestCasesWithDebug
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasAnyTestCaseSelectedHolder
+	    label: 'Run Tests for Coverage'
+	    itemValue: runTestCasesForCoverage
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasMethodSelectedAndInstrumentingCompilerExistsHolder
+	    label: 'Recompile Method(s) with Instrumentation'
+	    itemValue: debugMenuRecompileMethodsInstrumented
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedAndInstrumentingCompilerExistsHolder
+	    label: 'Recompile Class(es) with Instrumentation'
+	    itemValue: classMenuRecompileInstrumented
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedAndInstrumentingCompilerExistsHolder
+	    label: 'Recompile Project(s) with Instrumentation'
+	    itemValue: projectMenuRecompileInstrumented
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasMethodSelectedAndInstrumentingCompilerExistsAndOOMPackageLoadedHolder
+	    label: 'Call Graph'
+	    itemValue: debugMenuOpenCallGraphForMethods
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: 'Clear all Coverage Info (Systemwide)'
+	    itemValue: debugMenuClearCoverageInfo
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: 'Enable Global Coverage Recording (in all Processes)'
+	    itemValue: debugMenuEnableGlobalCoverageRecording
+	    translateLabel: true
+	    isVisible: globalCoverageRecordingIsDisabled
+	  )
+	 (MenuItem
+	    label: 'Disable Global Coverage Recording (in all Processes)'
+	    itemValue: debugMenuDisableGlobalCoverageRecording
+	    translateLabel: true
+	    isVisible: globalCoverageRecordingIsEnabled
+	  )
+	 )
+	nil
+	nil
+      )
+
+    "Modified: / 31-05-2012 / 10:25:37 / cg"
 !
 
 methodListMenu
@@ -9366,60 +9573,60 @@
 
     ^
      #(Menu
-        (
-         (MenuItem
-            label: 'FileOutPrintOutSlice'
-            translateLabel: true
-            submenuChannel: selectorMenuFileOutPrintOutSlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'SpawnSlice'
-            translateLabel: true
-            submenuChannel: selectorMenuSpawnSlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'SearchSlice'
-            translateLabel: true
-            submenuChannel: selectorMenuSearchSlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'CopyMoveRemoveSlice'
-            translateLabel: true
-            submenuChannel: selectorMenuCopyMoveRemoveSlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'CompareGenerateDebugSlice'
-            translateLabel: true
-            submenuChannel: selectorMenuCompareGenerateDebugSlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Update'
-            itemValue: methodListMenuUpdate
-            translateLabel: true
-          )
-         )
-        nil
-        nil
+	(
+	 (MenuItem
+	    label: 'FileOutPrintOutSlice'
+	    translateLabel: true
+	    submenuChannel: selectorMenuFileOutPrintOutSlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'SpawnSlice'
+	    translateLabel: true
+	    submenuChannel: selectorMenuSpawnSlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'SearchSlice'
+	    translateLabel: true
+	    submenuChannel: selectorMenuSearchSlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'CopyMoveRemoveSlice'
+	    translateLabel: true
+	    submenuChannel: selectorMenuCopyMoveRemoveSlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'CompareGenerateDebugSlice'
+	    translateLabel: true
+	    submenuChannel: selectorMenuCompareGenerateDebugSlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Update'
+	    itemValue: methodListMenuUpdate
+	    translateLabel: true
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -9439,48 +9646,48 @@
 
     ^
      #(#Menu
-        #(
-         #(#MenuItem
-            #label: 'Add Parameter'
-            #enabled: #hasSingleMethodSelectedAndCanUseRefactoringSupportHolder
-            #translateLabel: true
-            #value: #selectorMenuAddParameter
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: 'Inline Parameter'
-            enabled: hasSingleMethodSelectedAndSingleSelectedMethodHasParameterAndCanUseRefactoringSupportHolder
-            itemValue: selectorMenuInlineParameter
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         #(#MenuItem
-            label: 'Remove Parameter'
-            enabled: hasSingleMethodSelectedAndSingleSelectedMethodHasParameterAndCanUseRefactoringSupportHolder
-            translateLabel: true
-            value: #selectorMenuRemoveParameter
-            showBusyCursorWhilePerforming: true
-          )
-               #(#MenuItem
-                  #label: '-'
-                )
-         #(#MenuItem
-            #label: 'Inline all self-Sends'
-            #translateLabel: true
-            #value: #selectorMenuInlineSelfSends
-            #enabled: #hasSingleMethodSelectedAndCanUseRefactoringSupportHolder
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Search && Rewrite'
-            itemValue: selectorMenuRewrite
-            translateLabel: true
-          )
-         )
-        nil
-        nil
+	#(
+	 #(#MenuItem
+	    #label: 'Add Parameter'
+	    #enabled: #hasSingleMethodSelectedAndCanUseRefactoringSupportHolder
+	    #translateLabel: true
+	    #value: #selectorMenuAddParameter
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: 'Inline Parameter'
+	    enabled: hasSingleMethodSelectedAndSingleSelectedMethodHasParameterAndCanUseRefactoringSupportHolder
+	    itemValue: selectorMenuInlineParameter
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 #(#MenuItem
+	    label: 'Remove Parameter'
+	    enabled: hasSingleMethodSelectedAndSingleSelectedMethodHasParameterAndCanUseRefactoringSupportHolder
+	    translateLabel: true
+	    value: #selectorMenuRemoveParameter
+	    showBusyCursorWhilePerforming: true
+	  )
+	       #(#MenuItem
+		  #label: '-'
+		)
+	 #(#MenuItem
+	    #label: 'Inline all self-Sends'
+	    #translateLabel: true
+	    #value: #selectorMenuInlineSelfSends
+	    #enabled: #hasSingleMethodSelectedAndCanUseRefactoringSupportHolder
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Search && Rewrite'
+	    itemValue: selectorMenuRewrite
+	    translateLabel: true
+	  )
+	 )
+	nil
+	nil
       )
 
     "Created: / 11-09-2007 / 11:43:37 / cg"
@@ -9500,119 +9707,164 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasNameSpaceSelectedAndSourceCodeManagerHolder
-            label: 'CVS'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasNameSpaceSelectedAndSourceCodeManagerHolder
-                  label: 'CheckIn All...'
-                  itemValue: nameSpaceMenuCheckInAll
-                  translateLabel: true
-                  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn All...')
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasNameSpaceSelectedAndSourceCodeManagerHolder
-                  label: 'CheckOut Newest All'
-                  itemValue: nameSpaceMenuCheckOutNewest
-                  translateLabel: true
-                  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckOut 'CheckOut Newest All')
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasNameSpaceSelectedAndSourceCodeManagerHolder
-                  label: 'CheckOut Previous Version All...'
-                  itemValue: nameSpaceMenuCheckOut
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasNameSpaceSelectedHolder
-            label: 'Spawn'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasNameSpaceSelectedHolder
-                  label: 'Buffer'
-                  itemValue: nameSpaceMenuSpawnBuffer
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasNameSpaceSelectedHolder
-                  label: 'Browser'
-                  itemValue: nameSpaceMenuSpawn
-                  translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            label: 'Find'
-            translateLabel: true
-            submenuChannel: searchMenu
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'New...'
-            itemValue: nameSpaceMenuNew
-            translateLabel: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: canRenameNameSpaceHolder
-            label: 'Rename'
-            itemValue: nameSpaceMenuRename
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: canRemoveNameSpaceHolder
-            label: 'Remove'
-            itemValue: nameSpaceMenuRemove
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Update'
-            itemValue: nameSpaceMenuUpdate
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         )
-        nil
-        nil
-      )
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasNameSpaceSelectedAndSourceCodeManagerHolder
+	    label: 'CVS'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasNameSpaceSelectedAndSourceCodeManagerHolder
+		  label: 'CheckIn All...'
+		  itemValue: nameSpaceMenuCheckInAll
+		  translateLabel: true
+		  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn All...')
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasNameSpaceSelectedAndSourceCodeManagerHolder
+		  label: 'CheckOut Newest All'
+		  itemValue: nameSpaceMenuCheckOutNewest
+		  translateLabel: true
+		  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckOut 'CheckOut Newest All')
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasNameSpaceSelectedAndSourceCodeManagerHolder
+		  label: 'CheckOut Previous Version All...'
+		  itemValue: nameSpaceMenuCheckOut
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasNameSpaceSelectedHolder
+	    label: 'Spawn'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasNameSpaceSelectedHolder
+		  label: 'Buffer'
+		  itemValue: nameSpaceMenuSpawnBuffer
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasNameSpaceSelectedHolder
+		  label: 'Browser'
+		  itemValue: nameSpaceMenuSpawn
+		  translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: 'Find'
+	    translateLabel: true
+	    submenuChannel: searchMenu
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'New...'
+	    itemValue: nameSpaceMenuNew
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: canRenameNameSpaceHolder
+	    label: 'Rename'
+	    itemValue: nameSpaceMenuRename
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: canRemoveNameSpaceHolder
+	    label: 'Remove'
+	    itemValue: nameSpaceMenuRemove
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Update'
+	    itemValue: nameSpaceMenuUpdate
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 )
+	nil
+	nil
+      )
+!
+
+projectCheckMenu
+    "This resource specification was automatically generated
+     by the MenuEditor of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the MenuEditor may not be able to read the specification."
+
+    "
+     MenuEditor new openOnClass:Tools::NewSystemBrowser andSelector:#categoryCheckMenu
+     (Menu new fromLiteralArrayEncoding:(Tools::NewSystemBrowser categoryCheckMenu)) startUp
+    "
+
+    <resource: #menu>
+
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'Check'
+	    itemValue: projectMenuSmalllintCheck:
+	    translateLabel: true
+	    argument: smalllintRules
+	  )
+	 (MenuItem
+	    label: 'Check (all checks)'
+	    itemValue: projectMenuSmalllintCheck:
+	    translateLabel: true
+	    argument: smalllintRulesAll
+	  )
+	 (MenuItem
+	    label: 'Check (selected checks)'
+	    itemValue: projectMenuSmalllintCheck:
+	    translateLabel: true
+	    argument: smalllintRulesFromUser
+	  )
+
+	 )
+	nil
+	nil
+      )
+
+    "Modified: / 17-04-2010 / 11:14:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 05-05-2012 / 10:22:19 / cg"
 !
 
 projectDebugMenu
@@ -9629,30 +9881,37 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasProjectSelectedAndInstrumentingCompilerExistsHolder
-            label: 'Recompile all Methods with Instrumentation'
-            itemValue: projectMenuRecompileInstrumented
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectSelectedAndInstrumentingCompilerExistsAndOOMPackageLoadedHolder
-            label: 'Call Graph'
-            itemValue: debugMenuOpenCallGraphForProjects
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasProjectSelectedHolder
+	    label: 'Recompile all Classes'
+	    itemValue: projectMenuRecompile
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedAndInstrumentingCompilerExistsHolder
+	    label: 'Recompile all Classes with Instrumentation'
+	    itemValue: projectMenuRecompileInstrumented
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedAndInstrumentingCompilerExistsAndOOMPackageLoadedHolder
+	    label: 'Call Graph'
+	    itemValue: debugMenuOpenCallGraphForProjects
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 )
+	nil
+	nil
       )
 
     "Created: / 27-04-2010 / 12:41:02 / cg"
-    "Modified: / 27-04-2010 / 14:06:33 / cg"
+    "Modified: / 31-05-2012 / 11:59:26 / cg"
 !
 
 projectMenu
@@ -9670,339 +9929,348 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasProjectSelectedHolder
-            label: 'File out'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasProjectSelectedHolder
-                  label: 'as...'
-                  itemValue: projectMenuFileOutAs
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedAndCanFileOutXMLHolder
-                  label: 'XML as...'
-                  itemValue: projectMenuFileOutXMLAs
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedAndCanFileOutSIFHolder
-                  label: 'SIF as...'
-                  itemValue: projectMenuFileOutSIFAs
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedHolder
-                  label: 'Each in...'
-                  itemValue: projectMenuFileOutEachIn
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedHolder
-                  label: 'Build Support File in...'
-                  itemValue: projectMenuFileOutBuildSupportFiles
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedAndCanFileOutXMLHolder
-                  label: 'Each XML in...'
-                  itemValue: projectMenuFileOutEachXMLIn
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedAndCanFileOutSIFHolder
-                  label: 'Each SIF in...'
-                  itemValue: projectMenuFileOutEachSIFIn
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedHolder
-                  label: 'Each Binary in...'
-                  itemValue: projectMenuFileOutEachBinaryIn
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedHolder
-                  label: 'Mail To...'
-                  itemValue: projectMenuMailTo
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            label: 'Repositoru'
-            translateLabel: true
-            submenuChannel: projectMenuSCMSlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Documentation'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasSingleRealProjectSelectedHolder
-                  label: 'Generate Project Documentation'
-                  itemValue: projectMenuDocumentation
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasOOMPackageLoadedAndSingleRealProjectSelectedHolder
-                  label: 'Metrics Summary Report'
-                  itemValue: projectMenuMetricsSummary
-                  translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasProjectSelectedHolder
-            label: 'Spawn'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasProjectSelectedHolder
-                  label: 'Buffer'
-                  itemValue: projectMenuSpawnBuffer
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedHolder
-                  label: 'Buffer with Extensions'
-                  itemValue: projectMenuSpawnExtensionsBuffer
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedHolder
-                  label: 'Buffer with Projects Requiring this Project'
-                  itemValue: projectMenuSpawnPreRequirerBuffer
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedHolder
-                  label: 'Browser'
-                  itemValue: projectMenuSpawn
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedHolder
-                  label: 'Browser on Extensions'
-                  itemValue: projectMenuSpawnExtensionsBrowser
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedHolder
-                  label: 'Browser on Projects Requiring this Project'
-                  itemValue: projectMenuSpawnPreRequirerBrowser
-                  translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            enabled: hasProjectSelectedHolder
-            label: 'Find'
-            translateLabel: true
-            submenuChannel: searchMenu
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'New...'
-            itemValue: projectMenuNew
-            translateLabel: true
-          )
-         (MenuItem
-            label: 'Load...'
-            itemValue: projectMenuLoad
-            translateLabel: true
-            isVisible: hasNoProjectSelectedHolder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: 'Load'
-            itemValue: projectMenuLoad
-            translateLabel: true
-            isVisible: hasProjectSelectedHolder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectSelectedHolder
-            label: 'Rename...'
-            itemValue: projectMenuRename
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasProjectSelectedHolder
-            label: 'Remove...'
-            itemValue: projectMenuRemove
-            translateLabel: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasSingleRealProjectSelectedHolder
-            label: 'Properties...'
-            itemValue: projectMenuProperties
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasProjectSelectedHolder
-            label: 'Generate'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasSingleRealProjectSelectedHolder
-                  label: 'Generate Project Definition Methods'
-                  itemValue: projectMenuGenerateProjectDefinitions
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasSingleRealProjectSelectedHolder
-                  label: 'Update Project Contents Definition Methods'
-                  itemValue: projectMenuUpdateProjectContentsDefinitions
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasSingleRealProjectSelectedHolder
-                  label: 'Regenerate Project Contents Definition Methods'
-                  itemValue: projectMenuRegenerateProjectContentsDefinitions
-                  translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            label: 'Build'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasSingleRealProjectSelectedHolder
-                  label: 'Build Package for Deployment'
-                  itemValue: projectMenuBuild
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasSingleRealProjectSelectedHolder
-                  label: 'Build Binaries for Execution'
-                  itemValue: projectMenuBuildExeOnly
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedHolder
-                  label: 'Patch-Set...'
-                  itemValue: projectMenuGeneratePatchSet
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            label: 'Debug'
-            translateLabel: true
-            submenuChannel: projectDebugMenu
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            label: 'Special'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasSingleRealProjectSelectedHolder
-                  label: 'Remove from ChangeSet'
-                  itemValue: projectMenuCleanUpChangeSet
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                  isVisible: false
-                )
-               (MenuItem
-                  enabled: hasSingleRealProjectSelectedHolder
-                  label: 'Make Current Project'
-                  itemValue: projectMenuMakeCurrentProject
-                  translateLabel: true
-                  isVisible: false
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Update'
-            itemValue: projectMenuUpdate
-            translateLabel: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasProjectSelectedHolder
+	    label: 'File out'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasProjectSelectedHolder
+		  label: 'as...'
+		  itemValue: projectMenuFileOutAs
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedAndCanFileOutXMLHolder
+		  label: 'XML as...'
+		  itemValue: projectMenuFileOutXMLAs
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedAndCanFileOutSIFHolder
+		  label: 'SIF as...'
+		  itemValue: projectMenuFileOutSIFAs
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedHolder
+		  label: 'Each in...'
+		  itemValue: projectMenuFileOutEachIn
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedHolder
+		  label: 'Build Support File in...'
+		  itemValue: projectMenuFileOutBuildSupportFiles
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedAndCanFileOutXMLHolder
+		  label: 'Each XML in...'
+		  itemValue: projectMenuFileOutEachXMLIn
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedAndCanFileOutSIFHolder
+		  label: 'Each SIF in...'
+		  itemValue: projectMenuFileOutEachSIFIn
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedHolder
+		  label: 'Each Binary in...'
+		  itemValue: projectMenuFileOutEachBinaryIn
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedHolder
+		  label: 'Mail To...'
+		  itemValue: projectMenuMailTo
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: 'Repositoru'
+	    translateLabel: true
+	    submenuChannel: projectMenuSCMSlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Documentation'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasSingleRealProjectSelectedHolder
+		  label: 'Generate Project Documentation'
+		  itemValue: projectMenuDocumentation
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasOOMPackageLoadedAndSingleRealProjectSelectedHolder
+		  label: 'Metrics Summary Report'
+		  itemValue: projectMenuMetricsSummary
+		  translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedHolder
+	    label: 'Spawn'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasProjectSelectedHolder
+		  label: 'Buffer'
+		  itemValue: projectMenuSpawnBuffer
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedHolder
+		  label: 'Buffer with Extensions'
+		  itemValue: projectMenuSpawnExtensionsBuffer
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedHolder
+		  label: 'Buffer with Projects Requiring this Project'
+		  itemValue: projectMenuSpawnPreRequirerBuffer
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedHolder
+		  label: 'Browser'
+		  itemValue: projectMenuSpawn
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedHolder
+		  label: 'Browser on Extensions'
+		  itemValue: projectMenuSpawnExtensionsBrowser
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedHolder
+		  label: 'Browser on Projects Requiring this Project'
+		  itemValue: projectMenuSpawnPreRequirerBrowser
+		  translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedHolder
+	    label: 'Find'
+	    translateLabel: true
+	    submenuChannel: searchMenu
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'New...'
+	    itemValue: projectMenuNew
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: 'Load...'
+	    itemValue: projectMenuLoad
+	    translateLabel: true
+	    isVisible: hasNoProjectSelectedHolder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: 'Load'
+	    itemValue: projectMenuLoad
+	    translateLabel: true
+	    isVisible: hasProjectSelectedHolder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedHolder
+	    label: 'Rename...'
+	    itemValue: projectMenuRename
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedHolder
+	    label: 'Remove...'
+	    itemValue: projectMenuRemove
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Build'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasSingleRealProjectSelectedHolder
+		  label: 'Build Package for Deployment'
+		  itemValue: projectMenuBuild
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasSingleRealProjectSelectedHolder
+		  label: 'Build Binaries for Execution'
+		  itemValue: projectMenuBuildExeOnly
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedHolder
+		  label: 'Patch-Set...'
+		  itemValue: projectMenuGeneratePatchSet
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedHolder
+	    label: 'Generate'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasSingleRealProjectSelectedHolder
+		  label: 'Generate Project Definition Methods'
+		  itemValue: projectMenuGenerateProjectDefinitions
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasSingleRealProjectSelectedHolder
+		  label: 'Update Project Contents Definition Methods'
+		  itemValue: projectMenuUpdateProjectContentsDefinitions
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasSingleRealProjectSelectedHolder
+		  label: 'Regenerate Project Contents Definition Methods'
+		  itemValue: projectMenuRegenerateProjectContentsDefinitions
+		  translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: 'Static Analysis (Lint)'
+	    translateLabel: true
+	    submenuChannel: projectCheckMenu
+	    labelImage: (ResourceRetriever ToolbarIconLibrary lint16x16Icon 'Static Analysis (Lint)')
+	  )
+	 (MenuItem
+	    label: 'Debug'
+	    translateLabel: true
+	    submenuChannel: projectDebugMenu
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    label: 'Special'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasSingleRealProjectSelectedHolder
+		  label: 'Remove from ChangeSet'
+		  itemValue: projectMenuCleanUpChangeSet
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		  isVisible: false
+		)
+	       (MenuItem
+		  enabled: hasSingleRealProjectSelectedHolder
+		  label: 'Make Current Project'
+		  itemValue: projectMenuMakeCurrentProject
+		  translateLabel: true
+		  isVisible: false
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasSingleRealProjectSelectedHolder
+	    label: 'Properties...'
+	    itemValue: projectMenuProperties
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Update'
+	    itemValue: projectMenuUpdate
+	    translateLabel: true
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -10020,30 +10288,30 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'Check'
-            itemValue: protocolCheckMenuSmalllintCheck:
-            translateLabel: true
-            argument: smalllintRules
-          )
-         (MenuItem
-            label: 'Check (all checks)'
-            itemValue: protocolCheckMenuSmalllintCheck:
-            translateLabel: true
-            argument: smalllintRulesAll
-          )
-         (MenuItem
-            label: 'Check (selected checks)'
-            itemValue: protocolCheckMenuSmalllintCheck:
-            translateLabel: true
-            argument: smalllintRulesFromUser
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'Check'
+	    itemValue: protocolCheckMenuSmalllintCheck:
+	    translateLabel: true
+	    argument: smalllintRules
+	  )
+	 (MenuItem
+	    label: 'Check (all checks)'
+	    itemValue: protocolCheckMenuSmalllintCheck:
+	    translateLabel: true
+	    argument: smalllintRulesAll
+	  )
+	 (MenuItem
+	    label: 'Check (selected checks)'
+	    itemValue: protocolCheckMenuSmalllintCheck:
+	    translateLabel: true
+	    argument: smalllintRulesFromUser
+	  )
+	 )
+	nil
+	nil
       )
 
     "Modified: / 17-04-2010 / 11:13:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -10063,240 +10331,240 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasProtocolSelectedHolder
-            label: 'FileOut'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasProtocolSelectedHolder
-                  label: 'as...'
-                  itemValue: protocolMenuFileOutAs
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasProtocolSelectedAndCanFileOutXMLHolder
-                  label: 'XML as...'
-                  itemValue: protocolMenuFileOutXMLAs
-                  translateLabel: true
-                  isVisible: false
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasProtocolSelectedAndCanFileOutSIFHolder
-                  label: 'SIF as...'
-                  itemValue: protocolMenuFileOutSIFAs
-                  translateLabel: true
-                  isVisible: false
-                  showBusyCursorWhilePerforming: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasProtocolSelectedHolder
-            label: 'Documentation'
-            translateLabel: true
-            isVisible: false
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasProtocolSelectedHolder
-                  label: 'PrintOut'
-                  itemValue: protocolMenuPrintOut
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasProtocolSelectedHolder
-                  label: 'PrintOut Protocol'
-                  itemValue: protocolMenuPrintOutProtocol
-                  translateLabel: true
-                  isVisible: false
-                  showBusyCursorWhilePerforming: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            enabled: hasProtocolSelectedHolder
-            label: 'PrintOut'
-            itemValue: protocolMenuPrintOut
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Spawn'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasProtocolSelectedHolder
-                  label: 'Buffer'
-                  itemValue: protocolMenuSpawnBuffer
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasProtocolSelectedHolder
-                  label: 'Buffer with Full Protocol'
-                  itemValue: protocolMenuSpawnFullCategoryBuffer
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: 'Buffer with Full Protocols Matching...'
-                  itemValue: protocolMenuSpawnMatchingFullCategoryBuffer
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasProtocolSelectedHolder
-                  label: 'Browser'
-                  itemValue: protocolMenuSpawn
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasProtocolSelectedHolder
-                  label: 'Browser on Full Protocol'
-                  itemValue: protocolMenuSpawnFullCategory
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: 'Browser on Full Protocols Matching...'
-                  itemValue: protocolMenuSpawnMatchingFullCategoryBrowser
-                  translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            enabled: hasProtocolSelectedHolder
-            label: 'Find'
-            translateLabel: true
-            isVisible: false
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasProtocolSelectedHolder
-                  label: 'String...'
-                  itemValue: protocolMenuFindString
-                  translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'New...'
-            itemValue: protocolMenuNew
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasProtocolSelectedHolder
-            label: 'Copy...'
-            itemValue: protocolMenuCopyToClass
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasProtocolSelectedHolder
-            label: 'Move'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasProtocolSelectedHolder
-                  label: 'To Class...'
-                  itemValue: protocolMenuMoveToClass
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasProtocolSelectedHolder
-                  label: 'To Project...'
-                  itemValue: protocolMenuMoveToProject
-                  translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            enabled: hasSingleRealProtocolSelectedHolder
-            label: 'Rename...'
-            itemValue: protocolMenuRename
-            translateLabel: true
-            shortcutKey: Rename
-            ignoreShortcutKeys: true
-          )
-         (MenuItem
-            enabled: hasProtocolSelectedHolder
-            label: 'Remove...'
-            itemValue: protocolMenuRemove
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary erase16x16Icon 'Remove...')
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Static Anlysis (Lint)'
-            translateLabel: true
-            submenuChannel: protocolCheckMenu
-            labelImage: (ResourceRetriever ToolbarIconLibrary lint16x16Icon 'Static Anlysis (Lint)')
-          )
-         (MenuItem
-            label: 'Generate'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  label: 'Common Categories'
-                  itemValue: protocolMenuGenerateCommonProtocols
-                  translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            label: 'Update'
-            itemValue: protocolMenuUpdate
-            translateLabel: true
-            isVisible: false
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasProtocolSelectedHolder
+	    label: 'FileOut'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasProtocolSelectedHolder
+		  label: 'as...'
+		  itemValue: protocolMenuFileOutAs
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasProtocolSelectedAndCanFileOutXMLHolder
+		  label: 'XML as...'
+		  itemValue: protocolMenuFileOutXMLAs
+		  translateLabel: true
+		  isVisible: false
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasProtocolSelectedAndCanFileOutSIFHolder
+		  label: 'SIF as...'
+		  itemValue: protocolMenuFileOutSIFAs
+		  translateLabel: true
+		  isVisible: false
+		  showBusyCursorWhilePerforming: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasProtocolSelectedHolder
+	    label: 'Documentation'
+	    translateLabel: true
+	    isVisible: false
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasProtocolSelectedHolder
+		  label: 'PrintOut'
+		  itemValue: protocolMenuPrintOut
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasProtocolSelectedHolder
+		  label: 'PrintOut Protocol'
+		  itemValue: protocolMenuPrintOutProtocol
+		  translateLabel: true
+		  isVisible: false
+		  showBusyCursorWhilePerforming: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    enabled: hasProtocolSelectedHolder
+	    label: 'PrintOut'
+	    itemValue: protocolMenuPrintOut
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Spawn'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasProtocolSelectedHolder
+		  label: 'Buffer'
+		  itemValue: protocolMenuSpawnBuffer
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasProtocolSelectedHolder
+		  label: 'Buffer with Full Protocol'
+		  itemValue: protocolMenuSpawnFullCategoryBuffer
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: 'Buffer with Full Protocols Matching...'
+		  itemValue: protocolMenuSpawnMatchingFullCategoryBuffer
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasProtocolSelectedHolder
+		  label: 'Browser'
+		  itemValue: protocolMenuSpawn
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasProtocolSelectedHolder
+		  label: 'Browser on Full Protocol'
+		  itemValue: protocolMenuSpawnFullCategory
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: 'Browser on Full Protocols Matching...'
+		  itemValue: protocolMenuSpawnMatchingFullCategoryBrowser
+		  translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    enabled: hasProtocolSelectedHolder
+	    label: 'Find'
+	    translateLabel: true
+	    isVisible: false
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasProtocolSelectedHolder
+		  label: 'String...'
+		  itemValue: protocolMenuFindString
+		  translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'New...'
+	    itemValue: protocolMenuNew
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: hasProtocolSelectedHolder
+	    label: 'Copy...'
+	    itemValue: protocolMenuCopyToClass
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: hasProtocolSelectedHolder
+	    label: 'Move'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasProtocolSelectedHolder
+		  label: 'To Class...'
+		  itemValue: protocolMenuMoveToClass
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasProtocolSelectedHolder
+		  label: 'To Project...'
+		  itemValue: protocolMenuMoveToProject
+		  translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    enabled: hasSingleRealProtocolSelectedHolder
+	    label: 'Rename...'
+	    itemValue: protocolMenuRename
+	    translateLabel: true
+	    shortcutKey: Rename
+	    ignoreShortcutKeys: true
+	  )
+	 (MenuItem
+	    enabled: hasProtocolSelectedHolder
+	    label: 'Remove...'
+	    itemValue: protocolMenuRemove
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary erase16x16Icon 'Remove...')
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Static Anlysis (Lint)'
+	    translateLabel: true
+	    submenuChannel: protocolCheckMenu
+	    labelImage: (ResourceRetriever ToolbarIconLibrary lint16x16Icon 'Static Anlysis (Lint)')
+	  )
+	 (MenuItem
+	    label: 'Generate'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  label: 'Common Categories'
+		  itemValue: protocolMenuGenerateCommonProtocols
+		  translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: 'Update'
+	    itemValue: protocolMenuUpdate
+	    translateLabel: true
+	    isVisible: false
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -10310,115 +10578,115 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasClassNameSelectedInCodeView
-            label: 'Goto Class'
-            itemValue: codeMenuGotoClass
-            translateLabel: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasTemporaryVariableSelectedInCodeViewHolder
-            label: 'Rename Local Variable...'
-            itemValue: codeMenuRenameTemporary
-            translateLabel: true
-            shortcutKey: Rename
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasTemporaryVariableSelectedInCodeViewHolder
-            label: 'Make Instance Variable'
-            itemValue: codeMenuMakeInstanceVariable
-            translateLabel: true
-            isVisible: hasNotMultipleTemporaryVariablesSelectedInCodeViewHolder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasMultipleTemporaryVariablesSelectedInCodeViewHolder
-            label: 'Make Instance Variables'
-            itemValue: codeMenuMakeInstanceVariable
-            translateLabel: true
-            isVisible: hasMultipleTemporaryVariablesSelectedInCodeViewHolder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasUndefinedUppercaseIdentifierSelectedInCodeViewHolder
-            label: 'Define as Class Variable'
-            itemValue: codeMenuDeclareSelectionAsClassVariable
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasClassVariableSelectedInCodeViewOrVariableList
-            label: 'Make Pool Variable...'
-            itemValue: codeMenuDeclareSelectionAsPoolVariable
-            translateLabel: true
-            isVisible: false
-          )
-         (MenuItem
-            enabled: hasLiteralConstantSelectedInCodeViewHolder
-            label: 'Eliminate Constant...'
-            itemValue: codeMenuEliminateConstant
-            translateLabel: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasSingleMethodSelectedAndSelectionInCodeViewAndCanUseRefactoringSupportHolder
-            label: 'Inline Message'
-            itemValue: codeMenuInlineMessage
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleMethodSelectedAndSelectionInCodeViewAndCanUseRefactoringSupportHolder
-            label: 'Extract Selection to Temporary...'
-            itemValue: codeMenuExtractSelectionToTemporary
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleMethodSelectedAndSelectionInCodeViewAndCanUseRefactoringSupportHolder
-            label: 'Extract Method...'
-            itemValue: codeMenuExtractMethod
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasSingleMethodSelectedAndSelectionInCodeViewAndSingleSelectedMethodHasParameterAndCanUseRefactoringSupportHolder
-            label: 'Inline Parameter of Method'
-            itemValue: codeMenuInlineParameter
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleMethodSelectedAndSelectionInCodeViewAndSingleSelectedMethodHasParameterAndCanUseRefactoringSupportHolder
-            label: 'Remove Parameter from Method'
-            itemValue: codeMenuRemoveParameter
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasSingleMethodSelectedAndCanUseRefactoringSupportHolder
-            label: 'Format'
-            itemValue: codeMenuFormat
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasClassNameSelectedInCodeView
+	    label: 'Goto Class'
+	    itemValue: codeMenuGotoClass
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasTemporaryVariableSelectedInCodeViewHolder
+	    label: 'Rename Local Variable...'
+	    itemValue: codeMenuRenameTemporary
+	    translateLabel: true
+	    shortcutKey: Rename
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasTemporaryVariableSelectedInCodeViewHolder
+	    label: 'Make Instance Variable'
+	    itemValue: codeMenuMakeInstanceVariable
+	    translateLabel: true
+	    isVisible: hasNotMultipleTemporaryVariablesSelectedInCodeViewHolder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasMultipleTemporaryVariablesSelectedInCodeViewHolder
+	    label: 'Make Instance Variables'
+	    itemValue: codeMenuMakeInstanceVariable
+	    translateLabel: true
+	    isVisible: hasMultipleTemporaryVariablesSelectedInCodeViewHolder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasUndefinedUppercaseIdentifierSelectedInCodeViewHolder
+	    label: 'Define as Class Variable'
+	    itemValue: codeMenuDeclareSelectionAsClassVariable
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: hasClassVariableSelectedInCodeViewOrVariableList
+	    label: 'Make Pool Variable...'
+	    itemValue: codeMenuDeclareSelectionAsPoolVariable
+	    translateLabel: true
+	    isVisible: false
+	  )
+	 (MenuItem
+	    enabled: hasLiteralConstantSelectedInCodeViewHolder
+	    label: 'Eliminate Constant...'
+	    itemValue: codeMenuEliminateConstant
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasSingleMethodSelectedAndSelectionInCodeViewAndCanUseRefactoringSupportHolder
+	    label: 'Inline Message'
+	    itemValue: codeMenuInlineMessage
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleMethodSelectedAndSelectionInCodeViewAndCanUseRefactoringSupportHolder
+	    label: 'Extract Selection to Temporary...'
+	    itemValue: codeMenuExtractSelectionToTemporary
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleMethodSelectedAndSelectionInCodeViewAndCanUseRefactoringSupportHolder
+	    label: 'Extract Method...'
+	    itemValue: codeMenuExtractMethod
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasSingleMethodSelectedAndSelectionInCodeViewAndSingleSelectedMethodHasParameterAndCanUseRefactoringSupportHolder
+	    label: 'Inline Parameter of Method'
+	    itemValue: codeMenuInlineParameter
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleMethodSelectedAndSelectionInCodeViewAndSingleSelectedMethodHasParameterAndCanUseRefactoringSupportHolder
+	    label: 'Remove Parameter from Method'
+	    itemValue: codeMenuRemoveParameter
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasSingleMethodSelectedAndCanUseRefactoringSupportHolder
+	    label: 'Format'
+	    itemValue: codeMenuFormat
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 )
+	nil
+	nil
       )
 
     "Modified: / 24-07-2011 / 12:34:17 / cg"
@@ -10439,78 +10707,78 @@
     <resource: #menu>
     ^
      #(#Menu
-        #(
-         #(#MenuItem
-            #label: 'Class...'
-            #translateLabel: true
-            #value: #searchMenuFindClass
-            shortcutKey: #'Cmds'
+	#(
+	 #(#MenuItem
+	    #label: 'Class...'
+	    #translateLabel: true
+	    #value: #searchMenuFindClass
+	    shortcutKey: #'Cmds'
 ignoreShortcutKeys: true
-          )
-         #(#MenuItem
-            #label: 'Class Hierarchy'
-            #translateLabel: true
-            #enabled: #hasSelectedClassWithSuperclassHolder
-            #submenuChannel: #selectedClassesHierarchyMenu
-          )
-         #(#MenuItem
-            #label: 'Changed Classes'
-            #translateLabel: true
-            #enabled: #hasChangedClassesHolder
-            #submenuChannel: #changedClassesMenu
-          )
-         #(#MenuItem
-            #label: 'Visited Classes'
-            #translateLabel: true
-            #enabled: #hasVisitedClassesHolder
-            #submenuChannel: #visitedClassesMenu
-          )
-         #(#MenuItem
-            #label: '-'
-          )
-         #(#MenuItem
-            #label: 'Method...'
-            #translateLabel: true
-            #value: #searchMenuFindMethod
-          )
-         #(#MenuItem
-            #label: 'Changed Methods'
-            #translateLabel: true
-            #enabled: #hasChangedMethodsHolder
-            #submenuChannel: #changedMethodsMenu
-          )
-         #(#MenuItem
-            #label: 'Visited Methods'
-            #translateLabel: true
-            #enabled: #hasFindHistoryClassesHolder
-            #submenuChannel: #findHistoryMenu
-          )
-         #(#MenuItem
-            #label: '-'
-          )
-         #(#MenuItem
-            #label: 'Response to...'
-            #translateLabel: true
-            #value: #searchMenuFindResponseTo
-            #enabled: #hasSingleClassOrMethodSelectedHolder
-          )
-         #(#MenuItem
-            #label: 'Response to'
-            #translateLabel: true
-            #submenuChannel: #sentMessagesResponseMenu
-            #isVisible: #hasSingleMethodSelectedHolder
-          )
-         #(#MenuItem
-            #label: '-'
-          )
-         #(#MenuItem
-            #label: 'Bookmarks'
-            #translateLabel: true
-            #submenuChannel: #boockmarksMenu
-          )
-         )
-        nil
-        nil
+	  )
+	 #(#MenuItem
+	    #label: 'Class Hierarchy'
+	    #translateLabel: true
+	    #enabled: #hasSelectedClassWithSuperclassHolder
+	    #submenuChannel: #selectedClassesHierarchyMenu
+	  )
+	 #(#MenuItem
+	    #label: 'Changed Classes'
+	    #translateLabel: true
+	    #enabled: #hasChangedClassesHolder
+	    #submenuChannel: #changedClassesMenu
+	  )
+	 #(#MenuItem
+	    #label: 'Visited Classes'
+	    #translateLabel: true
+	    #enabled: #hasVisitedClassesHolder
+	    #submenuChannel: #visitedClassesMenu
+	  )
+	 #(#MenuItem
+	    #label: '-'
+	  )
+	 #(#MenuItem
+	    #label: 'Method...'
+	    #translateLabel: true
+	    #value: #searchMenuFindMethod
+	  )
+	 #(#MenuItem
+	    #label: 'Changed Methods'
+	    #translateLabel: true
+	    #enabled: #hasChangedMethodsHolder
+	    #submenuChannel: #changedMethodsMenu
+	  )
+	 #(#MenuItem
+	    #label: 'Visited Methods'
+	    #translateLabel: true
+	    #enabled: #hasFindHistoryClassesHolder
+	    #submenuChannel: #findHistoryMenu
+	  )
+	 #(#MenuItem
+	    #label: '-'
+	  )
+	 #(#MenuItem
+	    #label: 'Response to...'
+	    #translateLabel: true
+	    #value: #searchMenuFindResponseTo
+	    #enabled: #hasSingleClassOrMethodSelectedHolder
+	  )
+	 #(#MenuItem
+	    #label: 'Response to'
+	    #translateLabel: true
+	    #submenuChannel: #sentMessagesResponseMenu
+	    #isVisible: #hasSingleMethodSelectedHolder
+	  )
+	 #(#MenuItem
+	    #label: '-'
+	  )
+	 #(#MenuItem
+	    #label: 'Bookmarks'
+	    #translateLabel: true
+	    #submenuChannel: #boockmarksMenu
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -10530,31 +10798,31 @@
 
     ^
      #(#Menu
-        #(
-         #(#MenuItem
-            #label: 'Response to...'
-            #translateLabel: true
-            #value: #searchMenuFindResponseTo
-            #enabled: #hasSingleClassOrMethodSelectedHolder
-          )
-         #(#MenuItem
-            #label: '-'
-          )
-         #(#MenuItem
-            #label: 'Back'
-            #translateLabel: true
-            #enabled: #hasFindHistoryClassesHolder
-            #submenuChannel: #findHistoryMenu
-          )
-         #(#MenuItem
-            #label: 'Changed Methods'
-            #translateLabel: true
-            #enabled: #hasChangedMethodsHolder
-            #submenuChannel: #changedMethodsMenu
-          )
-         )
-        nil
-        nil
+	#(
+	 #(#MenuItem
+	    #label: 'Response to...'
+	    #translateLabel: true
+	    #value: #searchMenuFindResponseTo
+	    #enabled: #hasSingleClassOrMethodSelectedHolder
+	  )
+	 #(#MenuItem
+	    #label: '-'
+	  )
+	 #(#MenuItem
+	    #label: 'Back'
+	    #translateLabel: true
+	    #enabled: #hasFindHistoryClassesHolder
+	    #submenuChannel: #findHistoryMenu
+	  )
+	 #(#MenuItem
+	    #label: 'Changed Methods'
+	    #translateLabel: true
+	    #enabled: #hasChangedMethodsHolder
+	    #submenuChannel: #changedMethodsMenu
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -10572,31 +10840,31 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'Check'
-            itemValue: selectorCheckMenuSmalllintCheck:
-            translateLabel: true
-            argument: smalllintRules
-          )
-         (MenuItem
-            label: 'Check (all checks)'
-            itemValue: selectorCheckMenuSmalllintCheck:
-            translateLabel: true
-            argument: smalllintRulesAll
-          )
-         (MenuItem
-            label: 'Check (selected checks)'
-            itemValue: selectorCheckMenuSmalllintCheck:
-            translateLabel: true
-            argument: smalllintRulesFromUser
-          )
-
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'Check'
+	    itemValue: selectorCheckMenuSmalllintCheck:
+	    translateLabel: true
+	    argument: smalllintRules
+	  )
+	 (MenuItem
+	    label: 'Check (all checks)'
+	    itemValue: selectorCheckMenuSmalllintCheck:
+	    translateLabel: true
+	    argument: smalllintRulesAll
+	  )
+	 (MenuItem
+	    label: 'Check (selected checks)'
+	    itemValue: selectorCheckMenuSmalllintCheck:
+	    translateLabel: true
+	    argument: smalllintRulesFromUser
+	  )
+
+	 )
+	nil
+	nil
       )
 
     "Created: / 17-04-2010 / 10:48:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -10616,108 +10884,108 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'FileOutPrintOutSlice'
-            translateLabel: true
-            submenuChannel: selectorMenuFileOutPrintOutSlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'SpawnSlice'
-            translateLabel: true
-            submenuChannel: selectorMenuSpawnSlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'SearchSlice'
-            translateLabel: true
-            submenuChannel: selectorMenuSearchSlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'New'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Method'
-                  itemValue: selectorMenuNewMethod
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'Smalltak/Ruby/... Method'
-                  translateLabel: true
-                  submenuChannel: selectorMenuNewSlice
-                  isMenuSlice: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Window Spec'
-                  itemValue: selectorMenuNewWindowSpec
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Menu Spec'
-                  itemValue: selectorMenuNewMenuSpec
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Image Spec'
-                  itemValue: selectorMenuNewImageSpec
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Table-Column Spec'
-                  itemValue: selectorMenuNewTableColumnSpec
-                  translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            label: 'CopyMoveRemoveSlice'
-            translateLabel: true
-            submenuChannel: selectorMenuCopyMoveRemoveSlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'CompareGenerateDebugSlice'
-            translateLabel: true
-            submenuChannel: selectorMenuCompareGenerateDebugSlice
-            isMenuSlice: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'FileOutPrintOutSlice'
+	    translateLabel: true
+	    submenuChannel: selectorMenuFileOutPrintOutSlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'SpawnSlice'
+	    translateLabel: true
+	    submenuChannel: selectorMenuSpawnSlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'SearchSlice'
+	    translateLabel: true
+	    submenuChannel: selectorMenuSearchSlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'New'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Method'
+		  itemValue: selectorMenuNewMethod
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'Smalltak/Ruby/... Method'
+		  translateLabel: true
+		  submenuChannel: selectorMenuNewSlice
+		  isMenuSlice: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Window Spec'
+		  itemValue: selectorMenuNewWindowSpec
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Menu Spec'
+		  itemValue: selectorMenuNewMenuSpec
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Image Spec'
+		  itemValue: selectorMenuNewImageSpec
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Table-Column Spec'
+		  itemValue: selectorMenuNewTableColumnSpec
+		  translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: 'CopyMoveRemoveSlice'
+	    translateLabel: true
+	    submenuChannel: selectorMenuCopyMoveRemoveSlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'CompareGenerateDebugSlice'
+	    translateLabel: true
+	    submenuChannel: selectorMenuCompareGenerateDebugSlice
+	    isMenuSlice: true
+	  )
+	 )
+	nil
+	nil
       )
 
     "Modified: / 05-07-2011 / 14:46:40 / cg"
@@ -10737,252 +11005,252 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasMethodSelectedHolder
-            label: 'Compare'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: methodRedefinesSuperclassVersionHolder
-                  label: 'With Inherited Method'
-                  itemValue: selectorMenuCompareWithInherited
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: methodHasPreviousVersionHolder
-                  label: 'With Previous Version'
-                  itemValue: selectorMenuCompareWithPreviousVersion
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasSingleMethodSelectedAndCodeModifiedHolder
-                  label: 'With Methods Actual Source'
-                  itemValue: selectorMenuCompareWithMethod
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasExactlyTwoMethodsSelectedHolder
-                  label: 'With Each Other'
-                  itemValue: selectorMenuCompareTwoSelectedMethods
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasMethodSelectedAndSourceCodeManagerHolder
-                  label: 'With Newest in CVS Repository...'
-                  itemValue: selectorMenuCompareAgainstNewestInRepository
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: smallTeamAvailable
-                  label: 'With SmallTeam Version on Host'
-                  translateLabel: true
-                  submenuChannel: compareMethodWithSmallTeamVersionMenu
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            label: 'Refactor'
-            translateLabel: true
-            submenuChannel: methodRefactorMenu
-          )
-         (MenuItem
-            label: 'Static Anlysis (Lint)'
-            translateLabel: true
-            submenuChannel: selectorCheckMenu
-            labelImage: (ResourceRetriever ToolbarIconLibrary lint16x16Icon 'Static Anlysis (Lint)')
-          )
-         (MenuItem
-            label: 'Generate'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: methodNotImplementedInSuperclass
-                  label: 'SubclassResponsibility in SuperClass'
-                  itemValue: selectorMenuGenerateSubclassResponsibilityInSuperclass
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: methodNotImplementedInClass
-                  label: 'SubclassResponsibility here'
-                  itemValue: selectorMenuGenerateSubclassResponsibilityHere
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: 'Templates in Subclasses'
-                  itemValue: selectorMenuGenerateTemplateInSubclasses
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: 'Templates in all Subclasses'
-                  itemValue: selectorMenuGenerateTemplateInAllSubclasses
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasInstanceMethodsSelectedHolder
-                  label: 'Corresponding Instance Creation in Class'
-                  itemValue: selectorMenuGenerateCorrespondingInstanceCreationInClass
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasClassMethodsSelectedHolder
-                  label: 'Forwarding Method in Instance Protocol'
-                  itemValue: selectorMenuGenerateForwardingMethodForInstances
-                  translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            label: 'Debug'
-            translateLabel: true
-            submenuChannel: methodDebugMenu
-            shortcutKey: Ctrl
-          )
-         (MenuItem
-            label: 'Special'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  label: 'Select'
-                  translateLabel: true
-                  isVisible: false
-                  submenu: 
-                 (Menu
-                    (
-                     (MenuItem
-                        label: 'Methods with String...'
-                        itemValue: selectorMenuSelectMethodsWithString
-                        translateLabel: true
-                      )
-                     (MenuItem
-                        label: 'Methods Sending...'
-                        itemValue: selectorMenuSelectMethodsSending
-                        translateLabel: true
-                      )
-                     (MenuItem
-                        label: 'Methods Refering to Global...'
-                        itemValue: selectorMenuSelectMethodsReferingToGlobal
-                        translateLabel: true
-                      )
-                     )
-                    nil
-                    nil
-                  )
-                )
-               (MenuItem
-                  label: '-'
-                  isVisible: false
-                )
-               (MenuItem
-                  enabled: methodHasPreviousVersionHolder
-                  label: 'Back to Previous Version'
-                  itemValue: selectorMenuBackToPrevious
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: methodHasPreviousVersionHolder
-                  label: 'Previous Versions'
-                  itemValue: selectorMenuBrowsePreviousVersions
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasSingleMethodSelectedHolder
-                  label: 'Inspect Method'
-                  itemValue: selectorMenuInspect
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasSingleResourceMethodSelectedHolder
-                  label: 'Edit Resource'
-                  itemValue: selectorMenuEdit
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasMethodSelectedHolder
-                  label: 'Recompile'
-                  itemValue: selectorMenuRecompile
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasMethodSelectedHolder
-                  label: 'Compile with stc'
-                  itemValue: selectorMenuCompileWithSTC
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasSingleMethodWithBytecodeSelectedHolder
-                  label: 'Decompile'
-                  itemValue: selectorMenuDecompile
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasMethodSelectedHolder
-                  label: 'Process...'
-                  itemValue: selectorMenuProcess
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasMethodsInList
-                  label: 'Copy List to Clipboard'
-                  itemValue: methodListMenuCopyList
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasMethodsInList
-                  label: 'Copy List of Classes to Clipboard'
-                  itemValue: methodListMenuCopyListOfClasses
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasMethodSelectedHolder
-                  label: 'Remove from ChangeSet'
-                  itemValue: selectorMenuCleanUpChangeSet
-                  translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasMethodSelectedHolder
+	    label: 'Compare'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: methodRedefinesSuperclassVersionHolder
+		  label: 'With Inherited Method'
+		  itemValue: selectorMenuCompareWithInherited
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: methodHasPreviousVersionHolder
+		  label: 'With Previous Version'
+		  itemValue: selectorMenuCompareWithPreviousVersion
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasSingleMethodSelectedAndCodeModifiedHolder
+		  label: 'With Methods Actual Source'
+		  itemValue: selectorMenuCompareWithMethod
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasExactlyTwoMethodsSelectedHolder
+		  label: 'With Each Other'
+		  itemValue: selectorMenuCompareTwoSelectedMethods
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasMethodSelectedAndSourceCodeManagerHolder
+		  label: 'With Newest in CVS Repository...'
+		  itemValue: selectorMenuCompareAgainstNewestInRepository
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: smallTeamAvailable
+		  label: 'With SmallTeam Version on Host'
+		  translateLabel: true
+		  submenuChannel: compareMethodWithSmallTeamVersionMenu
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: 'Refactor'
+	    translateLabel: true
+	    submenuChannel: methodRefactorMenu
+	  )
+	 (MenuItem
+	    label: 'Static Anlysis (Lint)'
+	    translateLabel: true
+	    submenuChannel: selectorCheckMenu
+	    labelImage: (ResourceRetriever ToolbarIconLibrary lint16x16Icon 'Static Anlysis (Lint)')
+	  )
+	 (MenuItem
+	    label: 'Generate'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: methodNotImplementedInSuperclass
+		  label: 'SubclassResponsibility in SuperClass'
+		  itemValue: selectorMenuGenerateSubclassResponsibilityInSuperclass
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: methodNotImplementedInClass
+		  label: 'SubclassResponsibility here'
+		  itemValue: selectorMenuGenerateSubclassResponsibilityHere
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: 'Templates in Subclasses'
+		  itemValue: selectorMenuGenerateTemplateInSubclasses
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: 'Templates in all Subclasses'
+		  itemValue: selectorMenuGenerateTemplateInAllSubclasses
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasInstanceMethodsSelectedHolder
+		  label: 'Corresponding Instance Creation in Class'
+		  itemValue: selectorMenuGenerateCorrespondingInstanceCreationInClass
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasClassMethodsSelectedHolder
+		  label: 'Forwarding Method in Instance Protocol'
+		  itemValue: selectorMenuGenerateForwardingMethodForInstances
+		  translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: 'Debug'
+	    translateLabel: true
+	    submenuChannel: methodDebugMenu
+	    shortcutKey: Ctrl
+	  )
+	 (MenuItem
+	    label: 'Special'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  label: 'Select'
+		  translateLabel: true
+		  isVisible: false
+		  submenu:
+		 (Menu
+		    (
+		     (MenuItem
+			label: 'Methods with String...'
+			itemValue: selectorMenuSelectMethodsWithString
+			translateLabel: true
+		      )
+		     (MenuItem
+			label: 'Methods Sending...'
+			itemValue: selectorMenuSelectMethodsSending
+			translateLabel: true
+		      )
+		     (MenuItem
+			label: 'Methods Refering to Global...'
+			itemValue: selectorMenuSelectMethodsReferingToGlobal
+			translateLabel: true
+		      )
+		     )
+		    nil
+		    nil
+		  )
+		)
+	       (MenuItem
+		  label: '-'
+		  isVisible: false
+		)
+	       (MenuItem
+		  enabled: methodHasPreviousVersionHolder
+		  label: 'Back to Previous Version'
+		  itemValue: selectorMenuBackToPrevious
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: methodHasPreviousVersionHolder
+		  label: 'Previous Versions'
+		  itemValue: selectorMenuBrowsePreviousVersions
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasSingleMethodSelectedHolder
+		  label: 'Inspect Method'
+		  itemValue: selectorMenuInspect
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasSingleResourceMethodSelectedHolder
+		  label: 'Edit Resource'
+		  itemValue: selectorMenuEdit
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasMethodSelectedHolder
+		  label: 'Recompile'
+		  itemValue: selectorMenuRecompile
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasMethodSelectedHolder
+		  label: 'Compile with stc'
+		  itemValue: selectorMenuCompileWithSTC
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasSingleMethodWithBytecodeSelectedHolder
+		  label: 'Decompile'
+		  itemValue: selectorMenuDecompile
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasMethodSelectedHolder
+		  label: 'Process...'
+		  itemValue: selectorMenuProcess
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasMethodsInList
+		  label: 'Copy List to Clipboard'
+		  itemValue: methodListMenuCopyList
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasMethodsInList
+		  label: 'Copy List of Classes to Clipboard'
+		  itemValue: methodListMenuCopyListOfClasses
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasMethodSelectedHolder
+		  label: 'Remove from ChangeSet'
+		  itemValue: selectorMenuCleanUpChangeSet
+		  translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 )
+	nil
+	nil
       )
 
     "Modified: / 17-02-2012 / 22:20:52 / cg"
@@ -11003,165 +11271,165 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasMethodSelectedHolder
-            label: 'Copy...'
-            itemValue: selectorMenuCopy
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasMethodSelectedHolder
-            label: 'Move'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasMethodSelectedHolder
-                  label: 'To Protocol...'
-                  itemValue: selectorMenuMoveToProtocol
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasMethodSelectedHolder
-                  label: 'To Class...'
-                  itemValue: selectorMenuMoveToClass
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasClassMethodsSelectedHolder
-                  label: 'To Class with Forwarding...'
-                  itemValue: selectorMenuMoveToClassWithForwarding
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasMethodSelectedHolder
-                  label: 'To Package...'
-                  itemValue: selectorMenuMoveToProject
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasExtensionMethodSelectedHolder
-                  label: 'To Classes Package'
-                  itemValue: selectorMenuMoveToClassProject
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasInstanceMethodsSelectedHolder
-                  label: 'To Class Protocol (Make Class Method)'
-                  itemValue: selectorMenuMakeClassMethod
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasInstanceMethodsSelectedHolder
-                  label: 'To Class Protocol (Make Class Method) with Forwarding'
-                  itemValue: selectorMenuMakeClassMethodWithForwarding
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasClassMethodsSelectedHolder
-                  label: 'To Instance Protocol (Make Instance Method)'
-                  itemValue: selectorMenuMakeInstanceMethod
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasMethodSelectedAndCanUseRefactoringSupportHolder
-                  label: 'Push Up'
-                  itemValue: selectorMenuPushUpMethod
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasMethodSelectedAndCanUseRefactoringSupportHolder
-                  label: 'Push Down'
-                  itemValue: selectorMenuPushDownMethod
-                  translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            enabled: hasMethodSelectedHolder
-            label: 'Visibility'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasAnyNonPublicMethodSelectedHolder
-                  label: 'Public'
-                  itemValue: selectorMenuMakePublic
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasAnyNonProtectedMethodSelectedHolder
-                  label: 'Protected'
-                  itemValue: selectorMenuMakeProtected
-                  translateLabel: true
-                  labelImage: (ResourceRetriever SystemBrowser protectedMethodIcon 'Protected')
-                )
-               (MenuItem
-                  enabled: hasAnyNonPrivateMethodSelectedHolder
-                  label: 'Private'
-                  itemValue: selectorMenuMakePrivate
-                  translateLabel: true
-                  labelImage: (ResourceRetriever SystemBrowser privateMethodIcon 'Private')
-                )
-               (MenuItem
-                  enabled: hasAnyNonIgnoredMethodSelectedHolder
-                  label: 'Ignored'
-                  itemValue: selectorMenuMakeIgnored
-                  translateLabel: true
-                  labelImage: (ResourceRetriever SystemBrowser ignoredMethodIcon 'Ignored')
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasMethodSelectedHolder
-                  label: 'Mark as Obsolete'
-                  itemValue: selectorMenuMarkAsObsolete
-                  translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            enabled: hasMethodSelectedAndCanUseRefactoringSupportHolder
-            label: 'Rename...'
-            itemValue: selectorMenuRename
-            translateLabel: true
-            shortcutKey: Rename
-            ignoreShortcutKeys: true
-          )
-         (MenuItem
-            enabled: hasMethodSelectedAndCanUseRefactoringSupportHolder
-            label: 'Safe Remove...'
-            itemValue: selectorMenuSaveRemove
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasMethodSelectedHolder
-            label: 'Remove...'
-            itemValue: selectorMenuRemove
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary erase16x16Icon 'Remove...')
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasMethodSelectedHolder
+	    label: 'Copy...'
+	    itemValue: selectorMenuCopy
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: hasMethodSelectedHolder
+	    label: 'Move'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasMethodSelectedHolder
+		  label: 'To Protocol...'
+		  itemValue: selectorMenuMoveToProtocol
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasMethodSelectedHolder
+		  label: 'To Class...'
+		  itemValue: selectorMenuMoveToClass
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasClassMethodsSelectedHolder
+		  label: 'To Class with Forwarding...'
+		  itemValue: selectorMenuMoveToClassWithForwarding
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasMethodSelectedHolder
+		  label: 'To Package...'
+		  itemValue: selectorMenuMoveToProject
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasExtensionMethodSelectedHolder
+		  label: 'To Classes Package'
+		  itemValue: selectorMenuMoveToClassProject
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasInstanceMethodsSelectedHolder
+		  label: 'To Class Protocol (Make Class Method)'
+		  itemValue: selectorMenuMakeClassMethod
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasInstanceMethodsSelectedHolder
+		  label: 'To Class Protocol (Make Class Method) with Forwarding'
+		  itemValue: selectorMenuMakeClassMethodWithForwarding
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasClassMethodsSelectedHolder
+		  label: 'To Instance Protocol (Make Instance Method)'
+		  itemValue: selectorMenuMakeInstanceMethod
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasMethodSelectedAndCanUseRefactoringSupportHolder
+		  label: 'Push Up'
+		  itemValue: selectorMenuPushUpMethod
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasMethodSelectedAndCanUseRefactoringSupportHolder
+		  label: 'Push Down'
+		  itemValue: selectorMenuPushDownMethod
+		  translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    enabled: hasMethodSelectedHolder
+	    label: 'Visibility'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasAnyNonPublicMethodSelectedHolder
+		  label: 'Public'
+		  itemValue: selectorMenuMakePublic
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasAnyNonProtectedMethodSelectedHolder
+		  label: 'Protected'
+		  itemValue: selectorMenuMakeProtected
+		  translateLabel: true
+		  labelImage: (ResourceRetriever SystemBrowser protectedMethodIcon 'Protected')
+		)
+	       (MenuItem
+		  enabled: hasAnyNonPrivateMethodSelectedHolder
+		  label: 'Private'
+		  itemValue: selectorMenuMakePrivate
+		  translateLabel: true
+		  labelImage: (ResourceRetriever SystemBrowser privateMethodIcon 'Private')
+		)
+	       (MenuItem
+		  enabled: hasAnyNonIgnoredMethodSelectedHolder
+		  label: 'Ignored'
+		  itemValue: selectorMenuMakeIgnored
+		  translateLabel: true
+		  labelImage: (ResourceRetriever SystemBrowser ignoredMethodIcon 'Ignored')
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasMethodSelectedHolder
+		  label: 'Mark as Obsolete'
+		  itemValue: selectorMenuMarkAsObsolete
+		  translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    enabled: hasMethodSelectedAndCanUseRefactoringSupportHolder
+	    label: 'Rename...'
+	    itemValue: selectorMenuRename
+	    translateLabel: true
+	    shortcutKey: Rename
+	    ignoreShortcutKeys: true
+	  )
+	 (MenuItem
+	    enabled: hasMethodSelectedAndCanUseRefactoringSupportHolder
+	    label: 'Safe Remove...'
+	    itemValue: selectorMenuSaveRemove
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: hasMethodSelectedHolder
+	    label: 'Remove...'
+	    itemValue: selectorMenuRemove
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary erase16x16Icon 'Remove...')
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -11180,68 +11448,68 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasMethodSelectedHolder
-            label: 'FileOut'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasMethodSelectedHolder
-                  label: 'as...'
-                  itemValue: selectorMenuFileOutAs
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasMethodSelectedAndCanFileOutXMLHolder
-                  label: 'XML as...'
-                  itemValue: selectorMenuFileOutXMLAs
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasMethodSelectedAndCanFileOutSIFHolder
-                  label: 'SIF as...'
-                  itemValue: selectorMenuFileOutSIFAs
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            label: 'Repository'
-            translateLabel: true
-            submenuChannel: selectorMenuSCMSlice
-            isMenuSlice: true
-          )
-         (MenuItem
-            label: 'SmallTeam'
-            translateLabel: true
-            isVisible: smallTeamAvailable
-            submenuChannel: selectorSmallTeamMenu
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasMethodSelectedHolder
-            label: 'PrintOut'
-            itemValue: selectorMenuPrintOut
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasMethodSelectedHolder
+	    label: 'FileOut'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasMethodSelectedHolder
+		  label: 'as...'
+		  itemValue: selectorMenuFileOutAs
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasMethodSelectedAndCanFileOutXMLHolder
+		  label: 'XML as...'
+		  itemValue: selectorMenuFileOutXMLAs
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasMethodSelectedAndCanFileOutSIFHolder
+		  label: 'SIF as...'
+		  itemValue: selectorMenuFileOutSIFAs
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: 'Repository'
+	    translateLabel: true
+	    submenuChannel: selectorMenuSCMSlice
+	    isMenuSlice: true
+	  )
+	 (MenuItem
+	    label: 'SmallTeam'
+	    translateLabel: true
+	    isVisible: smallTeamAvailable
+	    submenuChannel: selectorSmallTeamMenu
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasMethodSelectedHolder
+	    label: 'PrintOut'
+	    itemValue: selectorMenuPrintOut
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -11261,64 +11529,64 @@
 
     ^
      #(Menu
-        (
-         (MenuItem
-            label: 'Senders...'
-            itemValue: browseSendersOf
-            translateLabel: true
-          )
-         (MenuItem
-            label: 'Senders of Any...'
-            itemValue: browseSendersOfAny
-            translateLabel: true
-            isVisible: hasMultipleMethodsSelectedHolder
-          )
-         (MenuItem
-            label: 'Senders'
-            translateLabel: true
-            isVisible: hasSingleMethodSelectedHolder
-            submenuChannel: sentMessagesMenu
-          )
-         (MenuItem
-            label: 'Implementors...'
-            itemValue: browseMenuImplementorsOf
-            translateLabel: true
-            shortcutKey: #'Cmdi'
+	(
+	 (MenuItem
+	    label: 'Senders...'
+	    itemValue: browseSendersOf
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: 'Senders of Any...'
+	    itemValue: browseSendersOfAny
+	    translateLabel: true
+	    isVisible: hasMultipleMethodsSelectedHolder
+	  )
+	 (MenuItem
+	    label: 'Senders'
+	    translateLabel: true
+	    isVisible: hasSingleMethodSelectedHolder
+	    submenuChannel: sentMessagesMenu
+	  )
+	 (MenuItem
+	    label: 'Implementors...'
+	    itemValue: browseMenuImplementorsOf
+	    translateLabel: true
+	    shortcutKey: #'Cmdi'
 ignoreShortcutKeys: true
-          )
-         (MenuItem
-            label: 'Implementors of Any...'
-            itemValue: browseMenuImplementorsOfAny
-            translateLabel: true
-            isVisible: hasMultipleMethodsSelectedHolder
-          )
-         (MenuItem
-            label: 'Implementors'
-            translateLabel: true
-            "/ isVisible: hasSingleMethodSelectedHolder
-            submenuChannel: implementedMessagesMenu
-          )
-         (MenuItem
-            label: 'Globals'
-            translateLabel: true
-            "/ isVisible: hasSingleMethodSelectedHolder
-            submenuChannel: globalReferencesMenu
-          )
-         (MenuItem
-            label: 'String Search...'
-            itemValue: browseMenuMethodsWithString
-            translateLabel: true
-            shortcutKey: #'Cmdt'
+	  )
+	 (MenuItem
+	    label: 'Implementors of Any...'
+	    itemValue: browseMenuImplementorsOfAny
+	    translateLabel: true
+	    isVisible: hasMultipleMethodsSelectedHolder
+	  )
+	 (MenuItem
+	    label: 'Implementors'
+	    translateLabel: true
+	    "/ isVisible: hasSingleMethodSelectedHolder
+	    submenuChannel: implementedMessagesMenu
+	  )
+	 (MenuItem
+	    label: 'Globals'
+	    translateLabel: true
+	    "/ isVisible: hasSingleMethodSelectedHolder
+	    submenuChannel: globalReferencesMenu
+	  )
+	 (MenuItem
+	    label: 'String Search...'
+	    itemValue: browseMenuMethodsWithString
+	    translateLabel: true
+	    shortcutKey: #'Cmdt'
 ignoreShortcutKeys: true
-          )
-         (MenuItem
-            label: 'Code Search...'
-            itemValue: browseMenuMethodsWithCode
-            translateLabel: true
-          )
-         )
-        nil
-        nil
+	  )
+	 (MenuItem
+	    label: 'Code Search...'
+	    itemValue: browseMenuMethodsWithCode
+	    translateLabel: true
+	  )
+	 )
+	nil
+	nil
       )
 
     "Modified: / 26-10-2011 / 18:08:38 / cg"
@@ -11340,177 +11608,177 @@
 
     ^
      #(Menu
-        (
-         (MenuItem
-            enabled: hasMethodSelectedHolder
-            label: 'Spawn'
-            translateLabel: true
-            submenu:
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasMethodSelectedHolder
-                  label: 'Buffer with Full Class(es)'
-                  itemValue: methodListMenuSpawnFullBrowserBuffer
-                  translateLabel: true
-                  isVisible: isMethodListBrowserOrHasMultipleClassesSelectedHolder
-                )
-               (MenuItem
-                  enabled: hasMethodSelectedHolder
-                  label: 'Buffer with Class(es)'
-                  itemValue: methodListMenuSpawnClassesBuffer
-                  translateLabel: true
-                  isVisible: isMethodListBrowserOrHasMultipleClassesSelectedHolder
-                )
-               (MenuItem
-                  enabled: hasMethodSelectedHolder
-                  label: 'Buffer with References to Class'
-                  itemValue: methodListMenuSpawnBufferWithClassReferences
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasMethodSelectedHolder
-                  label: 'Buffer with References to Class or Subclass'
-                  itemValue: methodListMenuSpawnBufferWithClassOrSubclassReferences
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasMultipleMethodsSelectedHolder
-                  label: 'Buffer with Common Superclass'
-                  itemValue: methodListMenuSpawnBufferWithCommonSuperclass
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasMethodSelectedHolder
-                  label: 'Buffer'
-                  itemValue: selectorMenuSpawnMethodBuffer
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasMethodSelectedHolder
-                  label: 'Buffer with Implementors'
-                  itemValue: selectorMenuSpawnImplementorsBuffer
-                  translateLabel: true
-                  isVisible: false
-                )
-               (MenuItem
-                  enabled: hasMethodSelectedHolder
-                  label: 'Buffer with Senders'
-                  itemValue: selectorMenuSpawnSendersBuffer
-                  translateLabel: true
-                  isVisible: false
-                )
-               (MenuItem
-                  enabled: hasRealExtensionMethodSelectedHolder
-                  label: 'Buffer with Extensions for Project'
-                  itemValue: selectorMenuSpawnProjectExtensionsBuffer
-                  translateLabel: true
-                  isVisible: hasExtensionMethodSelectedHolder
-                )
-               (MenuItem
-                  enabled: hasRealExtensionMethodSelectedHolder
-                  label: 'Buffer with Extension''s Project'
-                  itemValue: selectorMenuSpawnExtensionsProjectBuffer
-                  translateLabel: true
-                  isVisible: hasExtensionMethodSelectedHolder
-                )
-               (MenuItem
-                  enabled: hasUnassignedExtensionMethodSelectedHolder
-                  label: 'Buffer with Unassigned Extensions'
-                  itemValue: selectorMenuSpawnProjectExtensionsBuffer
-                  translateLabel: true
-                  isVisible: hasExtensionMethodSelectedHolder
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasMethodSelectedHolder
-                  label: 'Browser on Full Class(es)'
-                  itemValue: methodListMenuSpawnFullBrowser
-                  translateLabel: true
-                  isVisible: isMethodListBrowserOrHasMultipleClassesSelectedHolder
-                )
-               (MenuItem
-                  enabled: hasMethodSelectedHolder
-                  label: 'Browser on Class(es)'
-                  itemValue: methodListMenuSpawnClasses
-                  translateLabel: true
-                  isVisible: isMethodListBrowserOrHasMultipleClassesSelectedHolder
-                )
-               (MenuItem
-                  enabled: hasMethodSelectedHolder
-                  label: 'Browser on References to Class'
-                  itemValue: methodListMenuSpawnClassReferences
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasMethodSelectedHolder
-                  label: 'Browser on References to Class or Subclass'
-                  itemValue: methodListMenuSpawnClassOrSubclassReferences
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasMultipleMethodsSelectedHolder
-                  label: 'Browser on Common Superclass'
-                  itemValue: methodListMenuSpawnCommonSuperclass
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasMethodSelectedHolder
-                  label: 'Browser'
-                  itemValue: selectorMenuSpawnMethod
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasMethodSelectedHolder
-                  label: 'Browser on Implementors'
-                  itemValue: selectorMenuSpawnImplementors
-                  translateLabel: true
-                  isVisible: false
-                )
-               (MenuItem
-                  enabled: hasMethodSelectedHolder
-                  label: 'Browser on Senders'
-                  itemValue: selectorMenuSpawnSenders
-                  translateLabel: true
-                  isVisible: false
-                )
-               (MenuItem
-                  enabled: hasRealExtensionMethodSelectedHolder
-                  label: 'Browser on Extensions for Project'
-                  itemValue: selectorMenuSpawnProjectExtensions 
-                  translateLabel: true
-                  isVisible: hasExtensionMethodSelectedHolder
-                )
-               (MenuItem
-                  enabled: hasRealExtensionMethodSelectedHolder
-                  label: 'Browser on Extension''s Project'
-                  itemValue: selectorMenuSpawnExtensionsProject
-                  translateLabel: true
-                  isVisible: hasExtensionMethodSelectedHolder
-                )
-               (MenuItem
-                  enabled: hasUnassignedExtensionMethodSelectedHolder
-                  label: 'Browser on Unassigned Extensions'
-                  itemValue: selectorMenuSpawnProjectExtensions
-                  translateLabel: true
-                  isVisible: hasExtensionMethodSelectedHolder
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            enabled: hasMethodSelectedHolder
-            label: 'Inheritance'
-            itemValue: selectorMenuSpawnInheritanceBuffer
-            translateLabel: true
-          )
-         )
-        nil
-        nil
+	(
+	 (MenuItem
+	    enabled: hasMethodSelectedHolder
+	    label: 'Spawn'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasMethodSelectedHolder
+		  label: 'Buffer with Full Class(es)'
+		  itemValue: methodListMenuSpawnFullBrowserBuffer
+		  translateLabel: true
+		  isVisible: isMethodListBrowserOrHasMultipleClassesSelectedHolder
+		)
+	       (MenuItem
+		  enabled: hasMethodSelectedHolder
+		  label: 'Buffer with Class(es)'
+		  itemValue: methodListMenuSpawnClassesBuffer
+		  translateLabel: true
+		  isVisible: isMethodListBrowserOrHasMultipleClassesSelectedHolder
+		)
+	       (MenuItem
+		  enabled: hasMethodSelectedHolder
+		  label: 'Buffer with References to Class'
+		  itemValue: methodListMenuSpawnBufferWithClassReferences
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasMethodSelectedHolder
+		  label: 'Buffer with References to Class or Subclass'
+		  itemValue: methodListMenuSpawnBufferWithClassOrSubclassReferences
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasMultipleMethodsSelectedHolder
+		  label: 'Buffer with Common Superclass'
+		  itemValue: methodListMenuSpawnBufferWithCommonSuperclass
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasMethodSelectedHolder
+		  label: 'Buffer'
+		  itemValue: selectorMenuSpawnMethodBuffer
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasMethodSelectedHolder
+		  label: 'Buffer with Implementors'
+		  itemValue: selectorMenuSpawnImplementorsBuffer
+		  translateLabel: true
+		  isVisible: false
+		)
+	       (MenuItem
+		  enabled: hasMethodSelectedHolder
+		  label: 'Buffer with Senders'
+		  itemValue: selectorMenuSpawnSendersBuffer
+		  translateLabel: true
+		  isVisible: false
+		)
+	       (MenuItem
+		  enabled: hasRealExtensionMethodSelectedHolder
+		  label: 'Buffer with Extensions for Project'
+		  itemValue: selectorMenuSpawnProjectExtensionsBuffer
+		  translateLabel: true
+		  isVisible: hasExtensionMethodSelectedHolder
+		)
+	       (MenuItem
+		  enabled: hasRealExtensionMethodSelectedHolder
+		  label: 'Buffer with Extension''s Project'
+		  itemValue: selectorMenuSpawnExtensionsProjectBuffer
+		  translateLabel: true
+		  isVisible: hasExtensionMethodSelectedHolder
+		)
+	       (MenuItem
+		  enabled: hasUnassignedExtensionMethodSelectedHolder
+		  label: 'Buffer with Unassigned Extensions'
+		  itemValue: selectorMenuSpawnProjectExtensionsBuffer
+		  translateLabel: true
+		  isVisible: hasExtensionMethodSelectedHolder
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasMethodSelectedHolder
+		  label: 'Browser on Full Class(es)'
+		  itemValue: methodListMenuSpawnFullBrowser
+		  translateLabel: true
+		  isVisible: isMethodListBrowserOrHasMultipleClassesSelectedHolder
+		)
+	       (MenuItem
+		  enabled: hasMethodSelectedHolder
+		  label: 'Browser on Class(es)'
+		  itemValue: methodListMenuSpawnClasses
+		  translateLabel: true
+		  isVisible: isMethodListBrowserOrHasMultipleClassesSelectedHolder
+		)
+	       (MenuItem
+		  enabled: hasMethodSelectedHolder
+		  label: 'Browser on References to Class'
+		  itemValue: methodListMenuSpawnClassReferences
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasMethodSelectedHolder
+		  label: 'Browser on References to Class or Subclass'
+		  itemValue: methodListMenuSpawnClassOrSubclassReferences
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasMultipleMethodsSelectedHolder
+		  label: 'Browser on Common Superclass'
+		  itemValue: methodListMenuSpawnCommonSuperclass
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasMethodSelectedHolder
+		  label: 'Browser'
+		  itemValue: selectorMenuSpawnMethod
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasMethodSelectedHolder
+		  label: 'Browser on Implementors'
+		  itemValue: selectorMenuSpawnImplementors
+		  translateLabel: true
+		  isVisible: false
+		)
+	       (MenuItem
+		  enabled: hasMethodSelectedHolder
+		  label: 'Browser on Senders'
+		  itemValue: selectorMenuSpawnSenders
+		  translateLabel: true
+		  isVisible: false
+		)
+	       (MenuItem
+		  enabled: hasRealExtensionMethodSelectedHolder
+		  label: 'Browser on Extensions for Project'
+		  itemValue: selectorMenuSpawnProjectExtensions
+		  translateLabel: true
+		  isVisible: hasExtensionMethodSelectedHolder
+		)
+	       (MenuItem
+		  enabled: hasRealExtensionMethodSelectedHolder
+		  label: 'Browser on Extension''s Project'
+		  itemValue: selectorMenuSpawnExtensionsProject
+		  translateLabel: true
+		  isVisible: hasExtensionMethodSelectedHolder
+		)
+	       (MenuItem
+		  enabled: hasUnassignedExtensionMethodSelectedHolder
+		  label: 'Browser on Unassigned Extensions'
+		  itemValue: selectorMenuSpawnProjectExtensions
+		  translateLabel: true
+		  isVisible: hasExtensionMethodSelectedHolder
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    enabled: hasMethodSelectedHolder
+	    label: 'Inheritance'
+	    itemValue: selectorMenuSpawnInheritanceBuffer
+	    translateLabel: true
+	  )
+	 )
+	nil
+	nil
       )
 
     "Modified: / 28-02-2012 / 09:06:15 / cg"
@@ -11532,26 +11800,26 @@
 
     ^
      #(Menu
-        (
-         (MenuItem
-            enabled: hasMethodSelected
-            label: 'Load Version from Host'
-            translateLabel: true
-            submenuChannel: loadMethodFromSmallTeamHostMenu
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasMethodSelected
-            label: 'Compare with Version On Host'
-            translateLabel: true
-            submenuChannel: compareMethodWithSmallTeamVersionMenu
-            keepLinkedMenu: true
-          )
-         )
-        nil
-        nil
+	(
+	 (MenuItem
+	    enabled: hasMethodSelected
+	    label: 'Load Version from Host'
+	    translateLabel: true
+	    submenuChannel: loadMethodFromSmallTeamHostMenu
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasMethodSelected
+	    label: 'Compare with Version On Host'
+	    translateLabel: true
+	    submenuChannel: compareMethodWithSmallTeamVersionMenu
+	    keepLinkedMenu: true
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -11571,85 +11839,85 @@
 
     ^
      #(#Menu
-        #(
-         #(#MenuItem
-            #enabled: #hasSourceCodeManagerHolder
-            #label: 'CVS Repository Diffs'
-            #translateLabel: true
-            #submenu:
-           #(#Menu
-              #(
-               #(#MenuItem
-                  #label: 'Buffer'
-                  #itemValue: #browseMenuSpawnRepositoryDiffsInBuffer
-                  #translateLabel: true
-                )
-               #(#MenuItem
-                  #label: '-'
-                )
-               #(#MenuItem
-                  #label: 'Browser'
-                  #itemValue: #browseMenuSpawnRepositoryDiffs
-                  #translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         #(#MenuItem
-            #label: 'Full Class Source'
-            #translateLabel: true
-            #submenu:
-           #(#Menu
-              #(
-               #(#MenuItem
-                  #label: 'Buffer'
-                  #itemValue: #browseMenuSpawnFullClassSourceInBuffer
-                  #translateLabel: true
-                )
-               #(#MenuItem
-                  #label: '-'
-                )
-               #(#MenuItem
-                  #label: 'Browser'
-                  #itemValue: #browseMenuSpawnFullClassSource
-                  #translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         #(#MenuItem
-            #label: 'Class Documentation'
-            #translateLabel: true
-            #submenu:
-           #(#Menu
-              #(
-               #(#MenuItem
-                  #label: 'Buffer'
-                  #itemValue: #spawnClassDocumentationBrowserIn:
-                  #translateLabel: true
-                  #argument: #newBuffer
-                )
-               #(#MenuItem
-                  #label: '-'
-                )
-               #(#MenuItem
-                  #label: 'Browser'
-                  #itemValue: #spawnClassDocumentationBrowserIn:
-                  #translateLabel: true
-                  #argument: #newBrowser
-                )
-               )
-              nil
-              nil
-            )
-          )
-         )
-        nil
-        nil
+	#(
+	 #(#MenuItem
+	    #enabled: #hasSourceCodeManagerHolder
+	    #label: 'CVS Repository Diffs'
+	    #translateLabel: true
+	    #submenu:
+	   #(#Menu
+	      #(
+	       #(#MenuItem
+		  #label: 'Buffer'
+		  #itemValue: #browseMenuSpawnRepositoryDiffsInBuffer
+		  #translateLabel: true
+		)
+	       #(#MenuItem
+		  #label: '-'
+		)
+	       #(#MenuItem
+		  #label: 'Browser'
+		  #itemValue: #browseMenuSpawnRepositoryDiffs
+		  #translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 #(#MenuItem
+	    #label: 'Full Class Source'
+	    #translateLabel: true
+	    #submenu:
+	   #(#Menu
+	      #(
+	       #(#MenuItem
+		  #label: 'Buffer'
+		  #itemValue: #browseMenuSpawnFullClassSourceInBuffer
+		  #translateLabel: true
+		)
+	       #(#MenuItem
+		  #label: '-'
+		)
+	       #(#MenuItem
+		  #label: 'Browser'
+		  #itemValue: #browseMenuSpawnFullClassSource
+		  #translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 #(#MenuItem
+	    #label: 'Class Documentation'
+	    #translateLabel: true
+	    #submenu:
+	   #(#Menu
+	      #(
+	       #(#MenuItem
+		  #label: 'Buffer'
+		  #itemValue: #spawnClassDocumentationBrowserIn:
+		  #translateLabel: true
+		  #argument: #newBuffer
+		)
+	       #(#MenuItem
+		  #label: '-'
+		)
+	       #(#MenuItem
+		  #label: 'Browser'
+		  #itemValue: #spawnClassDocumentationBrowserIn:
+		  #translateLabel: true
+		  #argument: #newBrowser
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -11668,496 +11936,496 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasSingleClassSelectedAndCanUseRefactoringSupportHolder
-            label: 'Add...'
-            itemValue: variablesMenuAdd
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedAndCanUseRefactoringSupportHolder
-            label: 'Add ValueHolder...'
-            itemValue: variablesMenuAddValueHolder
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasNonMetaSelectedAndClassSelectedHolder
-            label: 'Instance Variables'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'All References...'
-                  itemValue: variablesMenuBrowseAllInstVarRefs
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'All Readers...'
-                  itemValue: variablesMenuBrowseAllInstVarReads
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'All Writers...'
-                  itemValue: variablesMenuBrowseAllInstVarMods
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Local References...'
-                  itemValue: variablesMenuBrowseInstVarRefs
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Local Readers...'
-                  itemValue: variablesMenuBrowseInstVarReads
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Local Writers...'
-                  itemValue: variablesMenuBrowseInstVarMods
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasInstanceVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
-                  label: 'Pull Up'
-                  itemValue: variablesMenuPullUp
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasInstanceVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
-                  label: 'Push Down'
-                  itemValue: variablesMenuPushDown
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasInstanceVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
-                  label: 'Convert to ValueHolder'
-                  itemValue: codeMenuConvertToValueHolder
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasSingleVariableSelectedInCodeViewOrVariableListHolder
-                  label: 'Make Abstract (Access only via Getters/Setters)'
-                  itemValue: codeMenuMakeAbstractVariable
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasSingleVariableSelectedInCodeViewOrVariableListHolder
-                  label: 'Make Concrete (Protect from Access via Getters/Setters)'
-                  itemValue: codeMenuProtectInstanceVariable
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            enabled: hasMetaSelectedAndClassSelectedHolder
-            label: 'Class Instance Variables'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'All References...'
-                  itemValue: variablesMenuBrowseAllClassInstVarRefs
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'All Readers...'
-                  itemValue: variablesMenuBrowseAllClassInstVarReads
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'All Writers...'
-                  itemValue: variablesMenuBrowseAllClassInstVarMods
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Local References...'
-                  itemValue: variablesMenuBrowseClassInstVarRefs
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Local Readers...'
-                  itemValue: variablesMenuBrowseClassInstVarReads
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Local Writers...'
-                  itemValue: variablesMenuBrowseClassInstVarMods
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Class Variables'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'All References...'
-                  itemValue: variablesMenuBrowseAllClassVarRefs
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'All Readers...'
-                  itemValue: variablesMenuBrowseAllClassVarReads
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'All Writers...'
-                  itemValue: variablesMenuBrowseAllClassVarMods
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Local References...'
-                  itemValue: variablesMenuBrowseClassVarRefs
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Local Readers...'
-                  itemValue: variablesMenuBrowseClassVarReads
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasClassSelectedHolder
-                  label: 'Writers...'
-                  itemValue: variablesMenuBrowseClassVarMods
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasClassVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
-                  label: 'Pull Up'
-                  itemValue: variablesMenuPullUp
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasClassVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
-                  label: 'Push Down'
-                  itemValue: variablesMenuPushDown
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasClassVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
-                  label: 'Make Abstract (Access only via Getters/Setters)'
-                  itemValue: codeMenuMakeAbstractVariable
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasClassVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
-                  label: 'Make Concrete (Protect from Access via Getters/Setters)'
-                  itemValue: codeMenuProtectClassVariable
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Move'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasSingleClassAndSingleVariableSelectedAndCanUseRefactoringSupportHolder
-                  label: 'Pull Up'
-                  itemValue: variablesMenuPullUp
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasSingleClassAndSingleVariableSelectedAndCanUseRefactoringSupportHolder
-                  label: 'Push Down'
-                  itemValue: variablesMenuPushDown
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            enabled: hasSingleClassAndSingleVariableSelectedAndCanUseRefactoringSupportHolder
-            label: 'Rename...'
-            itemValue: variablesMenuRename
-            translateLabel: true
-            shortcutKey: Rename
-            showBusyCursorWhilePerforming: true
-            ignoreShortcutKeys: true
-          )
-         (MenuItem
-            enabled: hasClassesWithCommonSuperclassAndVariableSelectedAndCanUseRefactoringSupportHolder
-            label: 'Remove'
-            itemValue: variablesMenuRemove
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary erase16x16Icon 'Remove')
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasVariableSelected
-            label: 'Copy Selected Name'
-            itemValue: variablesMenuCopySelectedName
-            translateLabel: true
-          )
-         (MenuItem
-            label: '-'
-            isVisible: false
-          )
-         (MenuItem
-            enabled: hasVariableSelected
-            label: 'Find Variable'
-            itemValue: doFindVariable
-            translateLabel: true
-            isVisible: false
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Show ClassVars (Statics)'
-            translateLabel: true
-            hideMenuOnActivated: false
-            indication: showClassVarsInVariableList
-          )
-         (MenuItem
-            label: 'Sort by Name'
-            translateLabel: true
-            hideMenuOnActivated: false
-            indication: sortVariablesByName
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Generate'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: canGenerateAccessMethodsHolder
-                  label: 'Access Methods'
-                  itemValue: variablesMenuGenerateAccessMethods
-                  translateLabel: true
-                  isVisible: hasVariableSelected
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: canGenerateAccessMethodsForAllHolder
-                  label: 'Access Methods for All'
-                  itemValue: variablesMenuGenerateAccessMethodsForAll
-                  translateLabel: true
-                  isVisible: hasNoVariableSelected
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: canGenerateAccessMethodsHolder
-                  label: 'Getter Method(s)'
-                  itemValue: variablesMenuGenerateGetterMethods
-                  translateLabel: true
-                  isVisible: hasVariableSelected
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: canGenerateAccessMethodsForAllHolder
-                  label: 'Getter Method(s) for All'
-                  itemValue: variablesMenuGenerateGetterMethodsForAll
-                  translateLabel: true
-                  isVisible: hasNoVariableSelected
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: canGenerateAccessMethodsHolder
-                  label: 'Setter Method(s)'
-                  itemValue: variablesMenuGenerateSetterMethods
-                  translateLabel: true
-                  isVisible: hasVariableSelected
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: canGenerateAccessMethodsForAllHolder
-                  label: 'Setter Method(s) for All'
-                  itemValue: variablesMenuGenerateSetterMethodsForAll
-                  translateLabel: true
-                  isVisible: hasNoVariableSelected
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: canGenerateMultiSetterMethodHolder
-                  label: 'Multi-Setter Method'
-                  itemValue: variablesMenuGenerateMultiSetterMethod
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                  isVisible: hasNonMetaSelectedHolder
-                )
-               (MenuItem
-                  enabled: canGenerateAccessMethodsHolder
-                  label: 'Access Methods with Lazy Initialization in Getter'
-                  itemValue: variablesMenuGenerateAccessMethodsWithLazyInitialization
-                  translateLabel: true
-                  isVisible: hasNonMetaSelectedHolder
-                )
-               (MenuItem
-                  enabled: canGenerateAccessMethodsHolder
-                  label: 'Access Methods with Change Notification'
-                  itemValue: variablesMenuGenerateAccessMethodsWithChange
-                  translateLabel: true
-                  isVisible: hasNonMetaSelectedHolder
-                )
-               (MenuItem
-                  enabled: canGenerateAccessMethodsHolder
-                  label: 'Access Methods for ValueHolder'
-                  itemValue: variablesMenuGenerateAccessMethodsForValueHolder
-                  translateLabel: true
-                  isVisible: hasNonMetaSelectedHolder
-                )
-               (MenuItem
-                  enabled: canGenerateAccessMethodsHolder
-                  label: 'Access Methods for ValueHolder with Change Notification'
-                  itemValue: variablesMenuGenerateAccessMethodsForValueHolderWithChange
-                  translateLabel: true
-                  isVisible: hasNonMetaSelectedHolder
-                )
-               (MenuItem
-                  enabled: canGenerateAccessMethodsHolder
-                  label: 'Collection Access Methods'
-                  itemValue: variablesMenuGenerateCollectionAccessMethods
-                  translateLabel: true
-                  isVisible: hasNonMetaSelectedHolder
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            label: 'Debug'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasClassVariableSelectedHolder
-                  label: 'Inspect...'
-                  itemValue: variablesMenuInspect
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasSingleVariableSelectedHolder
-                  label: 'Show Type(s)...'
-                  itemValue: variablesMenuTypeInfo
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasSingleVariableSelectedHolder
-                  label: 'Browse Type(s)'
-                  itemValue: variablesMenuTypeBrowe
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndCanUseRefactoringSupportHolder
+	    label: 'Add...'
+	    itemValue: variablesMenuAdd
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndCanUseRefactoringSupportHolder
+	    label: 'Add ValueHolder...'
+	    itemValue: variablesMenuAddValueHolder
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasNonMetaSelectedAndClassSelectedHolder
+	    label: 'Instance Variables'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'All References...'
+		  itemValue: variablesMenuBrowseAllInstVarRefs
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'All Readers...'
+		  itemValue: variablesMenuBrowseAllInstVarReads
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'All Writers...'
+		  itemValue: variablesMenuBrowseAllInstVarMods
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Local References...'
+		  itemValue: variablesMenuBrowseInstVarRefs
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Local Readers...'
+		  itemValue: variablesMenuBrowseInstVarReads
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Local Writers...'
+		  itemValue: variablesMenuBrowseInstVarMods
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasInstanceVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
+		  label: 'Pull Up'
+		  itemValue: variablesMenuPullUp
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasInstanceVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
+		  label: 'Push Down'
+		  itemValue: variablesMenuPushDown
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasInstanceVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
+		  label: 'Convert to ValueHolder'
+		  itemValue: codeMenuConvertToValueHolder
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasSingleVariableSelectedInCodeViewOrVariableListHolder
+		  label: 'Make Abstract (Access only via Getters/Setters)'
+		  itemValue: codeMenuMakeAbstractVariable
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasSingleVariableSelectedInCodeViewOrVariableListHolder
+		  label: 'Make Concrete (Protect from Access via Getters/Setters)'
+		  itemValue: codeMenuProtectInstanceVariable
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    enabled: hasMetaSelectedAndClassSelectedHolder
+	    label: 'Class Instance Variables'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'All References...'
+		  itemValue: variablesMenuBrowseAllClassInstVarRefs
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'All Readers...'
+		  itemValue: variablesMenuBrowseAllClassInstVarReads
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'All Writers...'
+		  itemValue: variablesMenuBrowseAllClassInstVarMods
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Local References...'
+		  itemValue: variablesMenuBrowseClassInstVarRefs
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Local Readers...'
+		  itemValue: variablesMenuBrowseClassInstVarReads
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Local Writers...'
+		  itemValue: variablesMenuBrowseClassInstVarMods
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Class Variables'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'All References...'
+		  itemValue: variablesMenuBrowseAllClassVarRefs
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'All Readers...'
+		  itemValue: variablesMenuBrowseAllClassVarReads
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'All Writers...'
+		  itemValue: variablesMenuBrowseAllClassVarMods
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Local References...'
+		  itemValue: variablesMenuBrowseClassVarRefs
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Local Readers...'
+		  itemValue: variablesMenuBrowseClassVarReads
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasClassSelectedHolder
+		  label: 'Writers...'
+		  itemValue: variablesMenuBrowseClassVarMods
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasClassVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
+		  label: 'Pull Up'
+		  itemValue: variablesMenuPullUp
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasClassVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
+		  label: 'Push Down'
+		  itemValue: variablesMenuPushDown
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasClassVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
+		  label: 'Make Abstract (Access only via Getters/Setters)'
+		  itemValue: codeMenuMakeAbstractVariable
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasClassVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
+		  label: 'Make Concrete (Protect from Access via Getters/Setters)'
+		  itemValue: codeMenuProtectClassVariable
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Move'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasSingleClassAndSingleVariableSelectedAndCanUseRefactoringSupportHolder
+		  label: 'Pull Up'
+		  itemValue: variablesMenuPullUp
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasSingleClassAndSingleVariableSelectedAndCanUseRefactoringSupportHolder
+		  label: 'Push Down'
+		  itemValue: variablesMenuPushDown
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassAndSingleVariableSelectedAndCanUseRefactoringSupportHolder
+	    label: 'Rename...'
+	    itemValue: variablesMenuRename
+	    translateLabel: true
+	    shortcutKey: Rename
+	    showBusyCursorWhilePerforming: true
+	    ignoreShortcutKeys: true
+	  )
+	 (MenuItem
+	    enabled: hasClassesWithCommonSuperclassAndVariableSelectedAndCanUseRefactoringSupportHolder
+	    label: 'Remove'
+	    itemValue: variablesMenuRemove
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary erase16x16Icon 'Remove')
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasVariableSelected
+	    label: 'Copy Selected Name'
+	    itemValue: variablesMenuCopySelectedName
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: '-'
+	    isVisible: false
+	  )
+	 (MenuItem
+	    enabled: hasVariableSelected
+	    label: 'Find Variable'
+	    itemValue: doFindVariable
+	    translateLabel: true
+	    isVisible: false
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Show ClassVars (Statics)'
+	    translateLabel: true
+	    hideMenuOnActivated: false
+	    indication: showClassVarsInVariableList
+	  )
+	 (MenuItem
+	    label: 'Sort by Name'
+	    translateLabel: true
+	    hideMenuOnActivated: false
+	    indication: sortVariablesByName
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolder
+	    label: 'Generate'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: canGenerateAccessMethodsHolder
+		  label: 'Access Methods'
+		  itemValue: variablesMenuGenerateAccessMethods
+		  translateLabel: true
+		  isVisible: hasVariableSelected
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: canGenerateAccessMethodsForAllHolder
+		  label: 'Access Methods for All'
+		  itemValue: variablesMenuGenerateAccessMethodsForAll
+		  translateLabel: true
+		  isVisible: hasNoVariableSelected
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: canGenerateAccessMethodsHolder
+		  label: 'Getter Method(s)'
+		  itemValue: variablesMenuGenerateGetterMethods
+		  translateLabel: true
+		  isVisible: hasVariableSelected
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: canGenerateAccessMethodsForAllHolder
+		  label: 'Getter Method(s) for All'
+		  itemValue: variablesMenuGenerateGetterMethodsForAll
+		  translateLabel: true
+		  isVisible: hasNoVariableSelected
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: canGenerateAccessMethodsHolder
+		  label: 'Setter Method(s)'
+		  itemValue: variablesMenuGenerateSetterMethods
+		  translateLabel: true
+		  isVisible: hasVariableSelected
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: canGenerateAccessMethodsForAllHolder
+		  label: 'Setter Method(s) for All'
+		  itemValue: variablesMenuGenerateSetterMethodsForAll
+		  translateLabel: true
+		  isVisible: hasNoVariableSelected
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: canGenerateMultiSetterMethodHolder
+		  label: 'Multi-Setter Method'
+		  itemValue: variablesMenuGenerateMultiSetterMethod
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		  isVisible: hasNonMetaSelectedHolder
+		)
+	       (MenuItem
+		  enabled: canGenerateAccessMethodsHolder
+		  label: 'Access Methods with Lazy Initialization in Getter'
+		  itemValue: variablesMenuGenerateAccessMethodsWithLazyInitialization
+		  translateLabel: true
+		  isVisible: hasNonMetaSelectedHolder
+		)
+	       (MenuItem
+		  enabled: canGenerateAccessMethodsHolder
+		  label: 'Access Methods with Change Notification'
+		  itemValue: variablesMenuGenerateAccessMethodsWithChange
+		  translateLabel: true
+		  isVisible: hasNonMetaSelectedHolder
+		)
+	       (MenuItem
+		  enabled: canGenerateAccessMethodsHolder
+		  label: 'Access Methods for ValueHolder'
+		  itemValue: variablesMenuGenerateAccessMethodsForValueHolder
+		  translateLabel: true
+		  isVisible: hasNonMetaSelectedHolder
+		)
+	       (MenuItem
+		  enabled: canGenerateAccessMethodsHolder
+		  label: 'Access Methods for ValueHolder with Change Notification'
+		  itemValue: variablesMenuGenerateAccessMethodsForValueHolderWithChange
+		  translateLabel: true
+		  isVisible: hasNonMetaSelectedHolder
+		)
+	       (MenuItem
+		  enabled: canGenerateAccessMethodsHolder
+		  label: 'Collection Access Methods'
+		  itemValue: variablesMenuGenerateCollectionAccessMethods
+		  translateLabel: true
+		  isVisible: hasNonMetaSelectedHolder
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: 'Debug'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasClassVariableSelectedHolder
+		  label: 'Inspect...'
+		  itemValue: variablesMenuInspect
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasSingleVariableSelectedHolder
+		  label: 'Show Type(s)...'
+		  itemValue: variablesMenuTypeInfo
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasSingleVariableSelectedHolder
+		  label: 'Browse Type(s)'
+		  itemValue: variablesMenuTypeBrowe
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -12176,80 +12444,80 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'Category'
-            translateLabel: true
-            isVisible: viewMenuOrganizerItemsVisible
-            hideMenuOnActivated: false
-            choice: organizerModeForMenu
-            choiceValue: category
-          )
-         (MenuItem
-            enabled: hasSingleClassSelected
-            label: 'Class Hierarchy'
-            translateLabel: true
-            isVisible: viewMenuOrganizerItemsVisible
-            hideMenuOnActivated: false
-            choice: organizerModeForMenu
-            choiceValue: classHierarchy
-          )
-         (MenuItem
-            enabled: hasSingleClassSelected
-            label: 'Class Inheritance'
-            translateLabel: true
-            isVisible: classInheritanceMenuItemVisible
-            hideMenuOnActivated: false
-            choice: organizerModeForMenu
-            choiceValue: classInheritance
-          )
-         (MenuItem
-            label: 'Hierarchy'
-            translateLabel: true
-            isVisible: viewMenuOrganizerItemsVisible
-            hideMenuOnActivated: false
-            choice: organizerModeForMenu
-            choiceValue: hierarchy
-          )
-         (MenuItem
-            label: 'Namespace'
-            translateLabel: true
-            isVisible: viewMenuOrganizerItemsVisible
-            hideMenuOnActivated: false
-            choice: organizerModeForMenu
-            choiceValue: namespace
-          )
-         (MenuItem
-            label: 'Package'
-            translateLabel: true
-            isVisible: viewMenuOrganizerItemsVisible
-            hideMenuOnActivated: false
-            choice: organizerModeForMenu
-            choiceValue: project
-          )
-         (MenuItem
-            label: 'Package Diagram'
-            translateLabel: true
-            isVisible: packageDiagramMenuItemVisible
-            hideMenuOnActivated: false
-            choice: organizerModeForMenu
-            choiceValue: packageDiagram
-          )
-         (MenuItem
-            label: '-'
-            isVisible: viewMenuOrganizerItemsVisible
-          )
-         (MenuItem
-            label: 'viewMenuCommonSlice'
-            translateLabel: true
-            submenuChannel: viewMenuCommonSlice
-            isMenuSlice: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'Category'
+	    translateLabel: true
+	    isVisible: viewMenuOrganizerItemsVisible
+	    hideMenuOnActivated: false
+	    choice: organizerModeForMenu
+	    choiceValue: category
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelected
+	    label: 'Class Hierarchy'
+	    translateLabel: true
+	    isVisible: viewMenuOrganizerItemsVisible
+	    hideMenuOnActivated: false
+	    choice: organizerModeForMenu
+	    choiceValue: classHierarchy
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelected
+	    label: 'Class Inheritance'
+	    translateLabel: true
+	    isVisible: classInheritanceMenuItemVisible
+	    hideMenuOnActivated: false
+	    choice: organizerModeForMenu
+	    choiceValue: classInheritance
+	  )
+	 (MenuItem
+	    label: 'Hierarchy'
+	    translateLabel: true
+	    isVisible: viewMenuOrganizerItemsVisible
+	    hideMenuOnActivated: false
+	    choice: organizerModeForMenu
+	    choiceValue: hierarchy
+	  )
+	 (MenuItem
+	    label: 'Namespace'
+	    translateLabel: true
+	    isVisible: viewMenuOrganizerItemsVisible
+	    hideMenuOnActivated: false
+	    choice: organizerModeForMenu
+	    choiceValue: namespace
+	  )
+	 (MenuItem
+	    label: 'Package'
+	    translateLabel: true
+	    isVisible: viewMenuOrganizerItemsVisible
+	    hideMenuOnActivated: false
+	    choice: organizerModeForMenu
+	    choiceValue: project
+	  )
+	 (MenuItem
+	    label: 'Package Diagram'
+	    translateLabel: true
+	    isVisible: packageDiagramMenuItemVisible
+	    hideMenuOnActivated: false
+	    choice: organizerModeForMenu
+	    choiceValue: packageDiagram
+	  )
+	 (MenuItem
+	    label: '-'
+	    isVisible: viewMenuOrganizerItemsVisible
+	  )
+	 (MenuItem
+	    label: 'viewMenuCommonSlice'
+	    translateLabel: true
+	    submenuChannel: viewMenuCommonSlice
+	    isMenuSlice: true
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -12268,258 +12536,258 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'Toolbar'
-            translateLabel: true
-            hideMenuOnActivated: false
-            indication: toolBarVisibleHolder
-          )
-         (MenuItem
-            label: 'Bookmarks'
-            translateLabel: true
-            hideMenuOnActivated: false
-            indication: bookmarkBarVisibleHolder
-          )
-         (MenuItem
-            label: 'Searchbar'
-            translateLabel: true
-            hideMenuOnActivated: false
-            indication: stringSearchToolVisibleHolder
-          )
-         (MenuItem
-            label: 'Info'
-            translateLabel: true
-            hideMenuOnActivated: false
-            indication: codeInfoVisible
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Multitab Mode'
-            translateLabel: true
-            hideMenuOnActivated: false
-            indication: showMultitabMode
-          )
-         (MenuItem
-            label: 'Enable Embedded Resource Editors'
-            translateLabel: true
-            hideMenuOnActivated: false
-            indication: showSpecialResourceEditors
-          )
-         (MenuItem
-            label: 'Coverage Info'
-            translateLabel: true
-            hideMenuOnActivated: false
-            indication: showCoverageInformation
-          )
-         (MenuItem
-            label: 'Browslet'
-            itemValue: showPlugin:
-            translateLabel: true
-            isVisible: false
-            hideMenuOnActivated: false
-            indication: showPlugin
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Class'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  label: 'Hide Unloaded Classes'
-                  translateLabel: true
-                  hideMenuOnActivated: false
-                  indication: hideUnloadedClasses
-                )
-               (MenuItem
-                  label: 'Show All Classes in NameSpace View'
-                  translateLabel: true
-                  hideMenuOnActivated: false
-                  indication: showAllClassesInNameSpaceOrganisation
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: showUnloadedClasses
-                  label: 'Emphasize Unloaded Classes'
-                  translateLabel: true
-                  hideMenuOnActivated: false
-                  indication: emphasizeUnloadedClasses
-                )
-               (MenuItem
-                  label: 'Show Class Type Indicator'
-                  translateLabel: true
-                  hideMenuOnActivated: false
-                  indication: markApplicationsHolder
-                )
-               (MenuItem
-                  label: 'Short Class Names in Tabs'
-                  translateLabel: true
-                  hideMenuOnActivated: false
-                  indication: shortNamesInTabs
-                )
-               (MenuItem
-                  label: 'Show Class-Packages'
-                  translateLabel: true
-                  hideMenuOnActivated: false
-                  indication: showClassPackages
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'Sort and Indent by Inheritance'
-                  translateLabel: true
-                  hideMenuOnActivated: false
-                  indication: sortByNameAndInheritance
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            label: 'Protocol'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  label: 'Show Pseudo Protocols'
-                  translateLabel: true
-                  hideMenuOnActivated: false
-                  indication: showPseudoProtocols
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            label: 'Selector'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  label: 'Show Inherited Methods'
-                  translateLabel: true
-                  hideMenuOnActivated: false
-                  choice: methodVisibilityHolder
-                  choiceValue: all
-                )
-               (MenuItem
-                  label: 'Show Inherited Methods except Object''s'
-                  translateLabel: true
-                  hideMenuOnActivated: false
-                  choice: methodVisibilityHolder
-                  choiceValue: allButObject
-                )
-               (MenuItem
-                  label: 'Do not Show Inherited Methods'
-                  translateLabel: true
-                  hideMenuOnActivated: false
-                  choice: methodVisibilityHolder
-                  choiceValue: class
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'Show Synthetic Methods'
-                  translateLabel: true
-                  hideMenuOnActivated: false
-                  indication: showSyntheticMethods
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'Show Method Inheritance Indicator'
-                  translateLabel: true
-                  hideMenuOnActivated: false
-                  indication: showMethodInheritance
-                )
-               (MenuItem
-                  label: 'Show Method Type Indicator'
-                  translateLabel: true
-                  hideMenuOnActivated: false
-                  indication: showMethodTypeIcon
-                )
-               (MenuItem
-                  enabled: hasOOMPackageLoadedHolder
-                  label: 'Show Method-Complexity'
-                  translateLabel: true
-                  hideMenuOnActivated: false
-                  indication: showMethodComplexity
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            label: 'Code'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  label: 'Syntax Coloring'
-                  translateLabel: true
-                  hideMenuOnActivated: false
-                  indication: doSyntaxColoring
-                )
-               (MenuItem
-                  enabled: doSyntaxColoring
-                  label: 'Immediate Syntax Coloring'
-                  translateLabel: true
-                  hideMenuOnActivated: false
-                  indication: doImmediateSyntaxColoring
-                )
-               (MenuItem
-                  label: 'Immediate Explaining'
-                  translateLabel: true
-                  hideMenuOnActivated: false
-                  indication: doImmediateExplaining
-                )
-               (MenuItem
-                  label: 'Auto-Format Code'
-                  translateLabel: true
-                  hideMenuOnActivated: false
-                  indication: doAutoFormat
-                )
-               (MenuItem
-                  label: 'Show MethodTemplate for New Methods'
-                  translateLabel: true
-                  hideMenuOnActivated: false
-                  indication: showMethodTemplate
-                )
-               )
-              nil
-              nil
-            )
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Settings...'
-            itemValue: openSettingsDialog
-            translateLabel: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'Toolbar'
+	    translateLabel: true
+	    hideMenuOnActivated: false
+	    indication: toolBarVisibleHolder
+	  )
+	 (MenuItem
+	    label: 'Bookmarks'
+	    translateLabel: true
+	    hideMenuOnActivated: false
+	    indication: bookmarkBarVisibleHolder
+	  )
+	 (MenuItem
+	    label: 'Searchbar'
+	    translateLabel: true
+	    hideMenuOnActivated: false
+	    indication: stringSearchToolVisibleHolder
+	  )
+	 (MenuItem
+	    label: 'Info'
+	    translateLabel: true
+	    hideMenuOnActivated: false
+	    indication: codeInfoVisible
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Multitab Mode'
+	    translateLabel: true
+	    hideMenuOnActivated: false
+	    indication: showMultitabMode
+	  )
+	 (MenuItem
+	    label: 'Enable Embedded Resource Editors'
+	    translateLabel: true
+	    hideMenuOnActivated: false
+	    indication: showSpecialResourceEditors
+	  )
+	 (MenuItem
+	    label: 'Coverage Info'
+	    translateLabel: true
+	    hideMenuOnActivated: false
+	    indication: showCoverageInformation
+	  )
+	 (MenuItem
+	    label: 'Browslet'
+	    itemValue: showPlugin:
+	    translateLabel: true
+	    isVisible: false
+	    hideMenuOnActivated: false
+	    indication: showPlugin
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Class'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  label: 'Hide Unloaded Classes'
+		  translateLabel: true
+		  hideMenuOnActivated: false
+		  indication: hideUnloadedClasses
+		)
+	       (MenuItem
+		  label: 'Show All Classes in NameSpace View'
+		  translateLabel: true
+		  hideMenuOnActivated: false
+		  indication: showAllClassesInNameSpaceOrganisation
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: showUnloadedClasses
+		  label: 'Emphasize Unloaded Classes'
+		  translateLabel: true
+		  hideMenuOnActivated: false
+		  indication: emphasizeUnloadedClasses
+		)
+	       (MenuItem
+		  label: 'Show Class Type Indicator'
+		  translateLabel: true
+		  hideMenuOnActivated: false
+		  indication: markApplicationsHolder
+		)
+	       (MenuItem
+		  label: 'Short Class Names in Tabs'
+		  translateLabel: true
+		  hideMenuOnActivated: false
+		  indication: shortNamesInTabs
+		)
+	       (MenuItem
+		  label: 'Show Class-Packages'
+		  translateLabel: true
+		  hideMenuOnActivated: false
+		  indication: showClassPackages
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'Sort and Indent by Inheritance'
+		  translateLabel: true
+		  hideMenuOnActivated: false
+		  indication: sortByNameAndInheritance
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: 'Protocol'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  label: 'Show Pseudo Protocols'
+		  translateLabel: true
+		  hideMenuOnActivated: false
+		  indication: showPseudoProtocols
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: 'Selector'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  label: 'Show Inherited Methods'
+		  translateLabel: true
+		  hideMenuOnActivated: false
+		  choice: methodVisibilityHolder
+		  choiceValue: all
+		)
+	       (MenuItem
+		  label: 'Show Inherited Methods except Object''s'
+		  translateLabel: true
+		  hideMenuOnActivated: false
+		  choice: methodVisibilityHolder
+		  choiceValue: allButObject
+		)
+	       (MenuItem
+		  label: 'Do not Show Inherited Methods'
+		  translateLabel: true
+		  hideMenuOnActivated: false
+		  choice: methodVisibilityHolder
+		  choiceValue: class
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'Show Synthetic Methods'
+		  translateLabel: true
+		  hideMenuOnActivated: false
+		  indication: showSyntheticMethods
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'Show Method Inheritance Indicator'
+		  translateLabel: true
+		  hideMenuOnActivated: false
+		  indication: showMethodInheritance
+		)
+	       (MenuItem
+		  label: 'Show Method Type Indicator'
+		  translateLabel: true
+		  hideMenuOnActivated: false
+		  indication: showMethodTypeIcon
+		)
+	       (MenuItem
+		  enabled: hasOOMPackageLoadedHolder
+		  label: 'Show Method-Complexity'
+		  translateLabel: true
+		  hideMenuOnActivated: false
+		  indication: showMethodComplexity
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: 'Code'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  label: 'Syntax Coloring'
+		  translateLabel: true
+		  hideMenuOnActivated: false
+		  indication: doSyntaxColoring
+		)
+	       (MenuItem
+		  enabled: doSyntaxColoring
+		  label: 'Immediate Syntax Coloring'
+		  translateLabel: true
+		  hideMenuOnActivated: false
+		  indication: doImmediateSyntaxColoring
+		)
+	       (MenuItem
+		  label: 'Immediate Explaining'
+		  translateLabel: true
+		  hideMenuOnActivated: false
+		  indication: doImmediateExplaining
+		)
+	       (MenuItem
+		  label: 'Auto-Format Code'
+		  translateLabel: true
+		  hideMenuOnActivated: false
+		  indication: doAutoFormat
+		)
+	       (MenuItem
+		  label: 'Show MethodTemplate for New Methods'
+		  translateLabel: true
+		  hideMenuOnActivated: false
+		  indication: showMethodTemplate
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Settings...'
+	    itemValue: openSettingsDialog
+	    translateLabel: true
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -12537,39 +12805,39 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'Original Order'
-            translateLabel: true
-            hideMenuOnActivated: false
-            choice: sortBy
-            choiceValue: false
-          )
-         (MenuItem
-            label: 'Sort by Class'
-            translateLabel: true
-            hideMenuOnActivated: false
-            choice: sortBy
-            choiceValue: class
-          )
-         (MenuItem
-            label: 'Sort by Selector'
-            translateLabel: true
-            hideMenuOnActivated: false
-            choice: sortBy
-            choiceValue: selector
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Menu Slice'
-            translateLabel: true
-            submenuChannel: viewMenuCommonSlice
-            isMenuSlice: true
-          )
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'Original Order'
+	    translateLabel: true
+	    hideMenuOnActivated: false
+	    choice: sortBy
+	    choiceValue: false
+	  )
+	 (MenuItem
+	    label: 'Sort by Class'
+	    translateLabel: true
+	    hideMenuOnActivated: false
+	    choice: sortBy
+	    choiceValue: class
+	  )
+	 (MenuItem
+	    label: 'Sort by Selector'
+	    translateLabel: true
+	    hideMenuOnActivated: false
+	    choice: sortBy
+	    choiceValue: selector
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Menu Slice'
+	    translateLabel: true
+	    submenuChannel: viewMenuCommonSlice
+	    isMenuSlice: true
+	  )
 "/         (MenuItem
 "/            label: '-'
 "/          )
@@ -12602,7 +12870,7 @@
 "/         (MenuItem
 "/            label: 'Indicators'
 "/            translateLabel: true
-"/            submenu: 
+"/            submenu:
 "/           (Menu
 "/              (
 "/               (MenuItem
@@ -12635,9 +12903,9 @@
 "/              nil
 "/            )
 "/          )
-         )
-        nil
-        nil
+	 )
+	nil
+	nil
       )
 !
 
@@ -12655,46 +12923,46 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'Original Order'
-            translateLabel: true
-            hideMenuOnActivated: false
-            choice: sortBy
-            choiceValue: false
-          )
-         (MenuItem
-            label: 'Sort by Class'
-            translateLabel: true
-            hideMenuOnActivated: false
-            choice: sortBy
-            choiceValue: class
-          )
-         (MenuItem
-            label: 'Sort by Selector'
-            translateLabel: true
-            hideMenuOnActivated: false
-            choice: sortBy
-            choiceValue: selector
-          )
-         (MenuItem
-            label: 'Sort by Category'
-            translateLabel: true
-            hideMenuOnActivated: false
-            choice: sortBy
-            choiceValue: category
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Menu Slice'
-            translateLabel: true
-            submenuChannel: viewMenuCommonSlice
-            isMenuSlice: true
-          )
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'Original Order'
+	    translateLabel: true
+	    hideMenuOnActivated: false
+	    choice: sortBy
+	    choiceValue: false
+	  )
+	 (MenuItem
+	    label: 'Sort by Class'
+	    translateLabel: true
+	    hideMenuOnActivated: false
+	    choice: sortBy
+	    choiceValue: class
+	  )
+	 (MenuItem
+	    label: 'Sort by Selector'
+	    translateLabel: true
+	    hideMenuOnActivated: false
+	    choice: sortBy
+	    choiceValue: selector
+	  )
+	 (MenuItem
+	    label: 'Sort by Category'
+	    translateLabel: true
+	    hideMenuOnActivated: false
+	    choice: sortBy
+	    choiceValue: category
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Menu Slice'
+	    translateLabel: true
+	    submenuChannel: viewMenuCommonSlice
+	    isMenuSlice: true
+	  )
 "/         (MenuItem
 "/            label: 'Toolbar'
 "/            translateLabel: true
@@ -12745,7 +13013,7 @@
 "/         (MenuItem
 "/            label: 'Indicators'
 "/            translateLabel: true
-"/            submenu: 
+"/            submenu:
 "/           (Menu
 "/              (
 "/               (MenuItem
@@ -12778,9 +13046,9 @@
 "/              nil
 "/            )
 "/          )
-         )
-        nil
-        nil
+	 )
+	nil
+	nil
       )
 ! !
 
@@ -12801,54 +13069,54 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-              (
-               (MenuItem
-                  enabled: hasCategorySelectedAndSourceCodeManagerHolder
-                  label: 'CheckIn all...'
-                  itemValue: categoryMenuCheckInEachUsing:
-                  translateLabel: true
-                  argument: SourceCodeManagerPlaceholder
-                  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn all...')
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasCategorySelectedAndSourceCodeManagerHolder
-                  label: 'CheckOut Newest All'
-                  itemValue: categoryMenuCheckOutNewestUsing:
-                  translateLabel: true
-                  argument: SourceCodeManagerPlaceholder
-                  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckOut 'CheckOut Newest All')
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasCategorySelectedAndSourceCodeManagerHolder
-                  label: 'CheckOut Previous Versions All...'
-                  itemValue: categoryMenuCheckOutUsing:
-                  translateLabel: true
-                  argument: SourceCodeManagerPlaceholder
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasSourceCodeManagerHolder
-                  label: 'Repository History...'
-                  itemValue: categoryMenuRepositoryHistoryUsing:
-                  translateLabel: true
-                  argument: SourceCodeManagerPlaceholder
-                  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryLog 'Repository History...')
-                  showBusyCursorWhilePerforming: true
-                )
-               )
-              nil
-              nil
-            )
+    ^
+     #(Menu
+	      (
+	       (MenuItem
+		  enabled: hasCategorySelectedAndSourceCodeManagerHolder
+		  label: 'CheckIn all...'
+		  itemValue: categoryMenuCheckInEachUsing:
+		  translateLabel: true
+		  argument: SourceCodeManagerPlaceholder
+		  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn all...')
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasCategorySelectedAndSourceCodeManagerHolder
+		  label: 'CheckOut Newest All'
+		  itemValue: categoryMenuCheckOutNewestUsing:
+		  translateLabel: true
+		  argument: SourceCodeManagerPlaceholder
+		  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckOut 'CheckOut Newest All')
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasCategorySelectedAndSourceCodeManagerHolder
+		  label: 'CheckOut Previous Versions All...'
+		  itemValue: categoryMenuCheckOutUsing:
+		  translateLabel: true
+		  argument: SourceCodeManagerPlaceholder
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasSourceCodeManagerHolder
+		  label: 'Repository History...'
+		  itemValue: categoryMenuRepositoryHistoryUsing:
+		  translateLabel: true
+		  argument: SourceCodeManagerPlaceholder
+		  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryLog 'Repository History...')
+		  showBusyCursorWhilePerforming: true
+		)
+	       )
+	      nil
+	      nil
+	    )
 
     "Created: / 15-10-2011 / 12:22:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -12868,61 +13136,61 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'CVS'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasCategorySelectedAndSourceCodeManagerHolder
-                  label: 'CheckIn all...'
-                  itemValue: categoryMenuCheckInEach
-                  translateLabel: true
-                  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn all...')
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasCategorySelectedAndSourceCodeManagerHolder
-                  label: 'CheckOut Newest All'
-                  itemValue: categoryMenuCheckOutNewest
-                  translateLabel: true
-                  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckOut 'CheckOut Newest All')
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasCategorySelectedAndSourceCodeManagerHolder
-                  label: 'CheckOut Previous Versions All...'
-                  itemValue: categoryMenuCheckOut
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasSourceCodeManagerHolder
-                  label: 'Repository History...'
-                  itemValue: categoryMenuRepositoryHistory
-                  translateLabel: true
-                  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryLog 'Repository History...')
-                  showBusyCursorWhilePerforming: true
-                )
-               )
-              nil
-              nil
-            )
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCVSIcon 'CVS')
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'CVS'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasCategorySelectedAndSourceCodeManagerHolder
+		  label: 'CheckIn all...'
+		  itemValue: categoryMenuCheckInEach
+		  translateLabel: true
+		  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn all...')
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasCategorySelectedAndSourceCodeManagerHolder
+		  label: 'CheckOut Newest All'
+		  itemValue: categoryMenuCheckOutNewest
+		  translateLabel: true
+		  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckOut 'CheckOut Newest All')
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasCategorySelectedAndSourceCodeManagerHolder
+		  label: 'CheckOut Previous Versions All...'
+		  itemValue: categoryMenuCheckOut
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasSourceCodeManagerHolder
+		  label: 'Repository History...'
+		  itemValue: categoryMenuRepositoryHistory
+		  translateLabel: true
+		  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryLog 'Repository History...')
+		  showBusyCursorWhilePerforming: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCVSIcon 'CVS')
+	  )
+	 )
+	nil
+	nil
       )
 
     "Modified: / 01-12-2011 / 21:16:05 / cg"
@@ -12943,39 +13211,39 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasClassSelectedAndSourceCodeManagerHolder
-            label: 'CVS'
-            translateLabel: true
-            submenuChannel: categoryMenuSCMFor:
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCVSIcon 'CVS')
-            argument: CVSSourceCodeManager
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            enabled: hasClassesSelectedAndSubversionRepositoryExistsHolder
-            label: 'SubVersion'
-            translateLabel: true
-            isVisible: hasSubversionSupport
-            submenuChannel: categoryMenuSCMFor:
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositorySVNIcon 'SubVersion')
-            argument: SVNSourceCodeManager
-          )
-         (MenuItem
-            enabled: hasClassSelectedAndSourceCodeManagerHolder
-            label: 'Perforce'
-            translateLabel: true
-            isVisible: hasPerforceSupport
-            submenuChannel: categoryMenuSCMFor:
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositorySVNIcon 'Perforce')
-            argument: PerforceSourceCodeManager
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasClassSelectedAndSourceCodeManagerHolder
+	    label: 'CVS'
+	    translateLabel: true
+	    submenuChannel: categoryMenuSCMFor:
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCVSIcon 'CVS')
+	    argument: CVSSourceCodeManager
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    enabled: hasClassesSelectedAndSubversionRepositoryExistsHolder
+	    label: 'SubVersion'
+	    translateLabel: true
+	    isVisible: hasSubversionSupport
+	    submenuChannel: categoryMenuSCMFor:
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositorySVNIcon 'SubVersion')
+	    argument: SVNSourceCodeManager
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedAndSourceCodeManagerHolder
+	    label: 'Perforce'
+	    translateLabel: true
+	    isVisible: hasPerforceSupport
+	    submenuChannel: categoryMenuSCMFor:
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositorySVNIcon 'Perforce')
+	    argument: PerforceSourceCodeManager
+	  )
+	 )
+	nil
+	nil
       )
 
     "Created: / 15-10-2011 / 12:22:41 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -12996,49 +13264,49 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'Repository'
-            nameKey: SCM
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  label: 'Common Slice'
-                  nameKey: CommonSlice
-                  translateLabel: true
-                  submenuChannel: categoryMenuSCMFor:
-                  argument: SourceCodeManagerPlaceholder
-                  isMenuSlice: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'All Slice'
-                  translateLabel: true
-                  submenuChannel: categoryMenuSCMSliceAll
-                  isMenuSlice: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'Repository Settings'
-                  itemValue: openSettingsDialogAndSelectSourceCodeManagement
-                  translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'Repository'
+	    nameKey: SCM
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  label: 'Common Slice'
+		  nameKey: CommonSlice
+		  translateLabel: true
+		  submenuChannel: categoryMenuSCMFor:
+		  argument: SourceCodeManagerPlaceholder
+		  isMenuSlice: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'All Slice'
+		  translateLabel: true
+		  submenuChannel: categoryMenuSCMSliceAll
+		  isMenuSlice: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'Repository Settings'
+		  itemValue: openSettingsDialogAndSelectSourceCodeManagement
+		  translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 )
+	nil
+	nil
       )
 
     "Created: / 15-10-2011 / 12:21:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -13059,21 +13327,21 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'All Slice'
-            translateLabel: true
-            submenuChannel: categoryMenuSCMSliceAll
-            isMenuSlice: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'All Slice'
+	    translateLabel: true
+	    submenuChannel: categoryMenuSCMSliceAll
+	    isMenuSlice: true
+	  )
+	 )
+	nil
+	nil
       )
 
     "Created: / 15-10-2011 / 12:21:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -13094,61 +13362,61 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'CVS'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasCategorySelectedAndSourceCodeManagerHolder
-                  label: 'CheckIn all...'
-                  itemValue: categoryMenuCheckInEach
-                  translateLabel: true
-                  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn all...')
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasCategorySelectedAndSourceCodeManagerHolder
-                  label: 'CheckOut Newest All'
-                  itemValue: categoryMenuCheckOutNewest
-                  translateLabel: true
-                  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckOut 'CheckOut Newest All')
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasCategorySelectedAndSourceCodeManagerHolder
-                  label: 'CheckOut Previous Versions All...'
-                  itemValue: categoryMenuCheckOut
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasSourceCodeManagerHolder
-                  label: 'Repository History...'
-                  itemValue: categoryMenuRepositoryHistory
-                  translateLabel: true
-                  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryLog 'Repository History...')
-                  showBusyCursorWhilePerforming: true
-                )
-               )
-              nil
-              nil
-            )
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCVSIcon 'CVS')
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'CVS'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasCategorySelectedAndSourceCodeManagerHolder
+		  label: 'CheckIn all...'
+		  itemValue: categoryMenuCheckInEach
+		  translateLabel: true
+		  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn all...')
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasCategorySelectedAndSourceCodeManagerHolder
+		  label: 'CheckOut Newest All'
+		  itemValue: categoryMenuCheckOutNewest
+		  translateLabel: true
+		  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckOut 'CheckOut Newest All')
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasCategorySelectedAndSourceCodeManagerHolder
+		  label: 'CheckOut Previous Versions All...'
+		  itemValue: categoryMenuCheckOut
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasSourceCodeManagerHolder
+		  label: 'Repository History...'
+		  itemValue: categoryMenuRepositoryHistory
+		  translateLabel: true
+		  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryLog 'Repository History...')
+		  showBusyCursorWhilePerforming: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCVSIcon 'CVS')
+	  )
+	 )
+	nil
+	nil
       )
 ! !
 
@@ -13169,159 +13437,159 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: '** No SourceCodeManager - See Settings in the Launcher **'
-            translateLabel: true
-            isVisible: hasNoSourceCodeManagerHolder
-          )
-         (MenuItem
-            label: '-'
-            isVisible: hasNoSourceCodeManagerHolder
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolderAndSourceCodeManagerHolder
-            label: 'CheckIn...'
-            itemValue: classMenuCheckIn
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn...')
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasClassWithExtensionsSelectedHolder
-            label: 'CheckIn Extensions For'
-            translateLabel: true
-            submenuChannel: browseClassExtensionsMenu
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: changeSetContainsChangedClassesAndSourceCodeManagerHolder
-            label: 'CheckIn All Changed Classes'
-            itemValue: classMenuCheckInAllChangedClasses
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: 'Quick CheckIn...'
-            itemValue: classMenuQuickCheckIn
-            translateLabel: true
-            isVisible: hasClassSelectedAndControlKeyDownHolder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
-            label: 'CheckIn Build Support Files...'
-            itemValue: classMenuCheckInBuildSupportFiles
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'CheckOut Newest'
-            itemValue: classMenuCheckOutNewest
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckOut 'CheckOut Newest')
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'CheckOut Previous Version...'
-            itemValue: classMenuCheckOut
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-            label: 'Edit Version in Repository...'
-            itemValue: classMenuEditVersionInRepository
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare with Newest in Repository...'
-            itemValue: classMenuCompareAgainstNewestInRepository
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryVersions 'Compare with Newest in Repository...')
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare with Original in Repository...'
-            itemValue: classMenuCompareAgainstOriginalInRepository
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare with Repository...'
-            itemValue: classMenuCompareWithRepository
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare two Repository Versions...'
-            itemValue: classMenuCompareTwoRepositoryVersions
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectDefinitionOrClassWithExtensionsSelectedAndSourceCodeManagerHolder
-            label: 'Compare Extensions with Repository...'
-            itemValue: classMenuCompareExtensionsWithRepository
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
-            label: 'Compare Build Support File'
-            translateLabel: true
-            submenuChannel: compareBuildSupportFileMenu
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'Set Tag...'
-            itemValue: classMenuSetTag
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryTag 'Set Tag...')
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'Revision Log (Recent Changes)'
-            itemValue: classMenuShortRevisionLog
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryLog 'Revision Log (Recent Changes)')
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'Revision Log (Full)'
-            itemValue: classMenuRevisionLog
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: '** No SourceCodeManager - See Settings in the Launcher **'
+	    translateLabel: true
+	    isVisible: hasNoSourceCodeManagerHolder
+	  )
+	 (MenuItem
+	    label: '-'
+	    isVisible: hasNoSourceCodeManagerHolder
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolderAndSourceCodeManagerHolder
+	    label: 'CheckIn...'
+	    itemValue: classMenuCheckIn
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn...')
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasClassWithExtensionsSelectedHolder
+	    label: 'CheckIn Extensions For'
+	    translateLabel: true
+	    submenuChannel: browseClassExtensionsMenu
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: changeSetContainsChangedClassesAndSourceCodeManagerHolder
+	    label: 'CheckIn All Changed Classes'
+	    itemValue: classMenuCheckInAllChangedClasses
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: 'Quick CheckIn...'
+	    itemValue: classMenuQuickCheckIn
+	    translateLabel: true
+	    isVisible: hasClassSelectedAndControlKeyDownHolder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
+	    label: 'CheckIn Build Support Files...'
+	    itemValue: classMenuCheckInBuildSupportFiles
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'CheckOut Newest'
+	    itemValue: classMenuCheckOutNewest
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckOut 'CheckOut Newest')
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'CheckOut Previous Version...'
+	    itemValue: classMenuCheckOut
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+	    label: 'Edit Version in Repository...'
+	    itemValue: classMenuEditVersionInRepository
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare with Newest in Repository...'
+	    itemValue: classMenuCompareAgainstNewestInRepository
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryVersions 'Compare with Newest in Repository...')
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare with Original in Repository...'
+	    itemValue: classMenuCompareAgainstOriginalInRepository
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare with Repository...'
+	    itemValue: classMenuCompareWithRepository
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare two Repository Versions...'
+	    itemValue: classMenuCompareTwoRepositoryVersions
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectDefinitionOrClassWithExtensionsSelectedAndSourceCodeManagerHolder
+	    label: 'Compare Extensions with Repository...'
+	    itemValue: classMenuCompareExtensionsWithRepository
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
+	    label: 'Compare Build Support File'
+	    translateLabel: true
+	    submenuChannel: compareBuildSupportFileMenu
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'Set Tag...'
+	    itemValue: classMenuSetTag
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryTag 'Set Tag...')
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'Revision Log (Recent Changes)'
+	    itemValue: classMenuShortRevisionLog
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryLog 'Revision Log (Recent Changes)')
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'Revision Log (Full)'
+	    itemValue: classMenuRevisionLog
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -13340,136 +13608,136 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasClassSelectedHolderAndSourceCodeManagerHolder
-            label: 'CheckIn...'
-            itemValue: classMenuCheckInUsingManagerNamed:
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn...')
-            argument: DataBaseSourceCodeManager
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasClassWithExtensionsSelectedHolder
-            label: 'CheckIn Extensions For'
-            translateLabel: true
-            submenuChannel: browseClassExtensionsMenuUsingManagerNamed:
-            argument: DataBaseSourceCodeManager
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: changeSetContainsChangedClassesAndSourceCodeManagerHolder
-            label: 'CheckIn All Changed Classes'
-            itemValue: classMenuCheckInAllChangedClassesUsingManagerNamed:
-            translateLabel: true
-            argument: DataBaseSourceCodeManager
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
-            label: 'CheckIn Build Support Files...'
-            itemValue: classMenuCheckInBuildSupportFilesUsingManagerNamed:
-            translateLabel: true
-            argument: DataBaseSourceCodeManager
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'CheckOut Newest'
-            itemValue: classMenuCheckOutNewestUsingManagerNamed:
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckOut 'CheckOut Newest')
-            argument: DataBaseSourceCodeManager
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'CheckOut Previous Version...'
-            itemValue: classMenuCheckOutUsingManagerNamed:
-            translateLabel: true
-            argument: DataBaseSourceCodeManager
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare with Newest in Repository...'
-            itemValue: classMenuCompareAgainstNewestInRepositoryUsingManagerNamed:
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryVersions 'Compare with Newest in Repository...')
-            argument: DataBaseSourceCodeManager
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare with Original in Repository...'
-            itemValue: classMenuCompareAgainstOriginalInRepositoryUsingManagerNamed:
-            translateLabel: true
-            argument: DataBaseSourceCodeManager
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare with Repository...'
-            itemValue: classMenuCompareWithRepositoryUsingManagerNamed:
-            translateLabel: true
-            argument: DataBaseSourceCodeManager
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare two Repository Versions...'
-            itemValue: classMenuCompareTwoRepositoryVersionsUsingManagerNamed:
-            translateLabel: true
-            argument: DataBaseSourceCodeManager
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectDefinitionOrClassWithExtensionsSelectedAndSourceCodeManagerHolder
-            label: 'Compare Extensions with Repository...'
-            itemValue: classMenuCompareExtensionsWithRepositoryUsingManagerNamed:
-            translateLabel: true
-            argument: DataBaseSourceCodeManager
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
-            label: 'Compare Build Support File'
-            translateLabel: true
-            submenuChannel: compareBuildSupportFileMenuUsingManagerNamed:
-            argument: DataBaseSourceCodeManager
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'Revision Log (Recent Changes)'
-            itemValue: classMenuShortRevisionLogUsingManagerNamed:
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryLog 'Revision Log (Recent Changes)')
-            argument: DataBaseSourceCodeManager
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'Revision Log (Full)'
-            itemValue: classMenuRevisionLogUsingManagerNamed:
-            translateLabel: true
-            argument: DataBaseSourceCodeManager
-            showBusyCursorWhilePerforming: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasClassSelectedHolderAndSourceCodeManagerHolder
+	    label: 'CheckIn...'
+	    itemValue: classMenuCheckInUsingManagerNamed:
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn...')
+	    argument: DataBaseSourceCodeManager
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasClassWithExtensionsSelectedHolder
+	    label: 'CheckIn Extensions For'
+	    translateLabel: true
+	    submenuChannel: browseClassExtensionsMenuUsingManagerNamed:
+	    argument: DataBaseSourceCodeManager
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: changeSetContainsChangedClassesAndSourceCodeManagerHolder
+	    label: 'CheckIn All Changed Classes'
+	    itemValue: classMenuCheckInAllChangedClassesUsingManagerNamed:
+	    translateLabel: true
+	    argument: DataBaseSourceCodeManager
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
+	    label: 'CheckIn Build Support Files...'
+	    itemValue: classMenuCheckInBuildSupportFilesUsingManagerNamed:
+	    translateLabel: true
+	    argument: DataBaseSourceCodeManager
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'CheckOut Newest'
+	    itemValue: classMenuCheckOutNewestUsingManagerNamed:
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckOut 'CheckOut Newest')
+	    argument: DataBaseSourceCodeManager
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'CheckOut Previous Version...'
+	    itemValue: classMenuCheckOutUsingManagerNamed:
+	    translateLabel: true
+	    argument: DataBaseSourceCodeManager
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare with Newest in Repository...'
+	    itemValue: classMenuCompareAgainstNewestInRepositoryUsingManagerNamed:
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryVersions 'Compare with Newest in Repository...')
+	    argument: DataBaseSourceCodeManager
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare with Original in Repository...'
+	    itemValue: classMenuCompareAgainstOriginalInRepositoryUsingManagerNamed:
+	    translateLabel: true
+	    argument: DataBaseSourceCodeManager
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare with Repository...'
+	    itemValue: classMenuCompareWithRepositoryUsingManagerNamed:
+	    translateLabel: true
+	    argument: DataBaseSourceCodeManager
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare two Repository Versions...'
+	    itemValue: classMenuCompareTwoRepositoryVersionsUsingManagerNamed:
+	    translateLabel: true
+	    argument: DataBaseSourceCodeManager
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectDefinitionOrClassWithExtensionsSelectedAndSourceCodeManagerHolder
+	    label: 'Compare Extensions with Repository...'
+	    itemValue: classMenuCompareExtensionsWithRepositoryUsingManagerNamed:
+	    translateLabel: true
+	    argument: DataBaseSourceCodeManager
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
+	    label: 'Compare Build Support File'
+	    translateLabel: true
+	    submenuChannel: compareBuildSupportFileMenuUsingManagerNamed:
+	    argument: DataBaseSourceCodeManager
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'Revision Log (Recent Changes)'
+	    itemValue: classMenuShortRevisionLogUsingManagerNamed:
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryLog 'Revision Log (Recent Changes)')
+	    argument: DataBaseSourceCodeManager
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'Revision Log (Full)'
+	    itemValue: classMenuRevisionLogUsingManagerNamed:
+	    translateLabel: true
+	    argument: DataBaseSourceCodeManager
+	    showBusyCursorWhilePerforming: true
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -13488,136 +13756,136 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasClassSelectedHolderAndSourceCodeManagerHolder
-            label: 'CheckIn...'
-            itemValue: classMenuCheckInUsingManagerNamed:
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn...')
-            argument: FileBasedSourceCodeManager
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasClassWithExtensionsSelectedHolder
-            label: 'CheckIn Extensions For'
-            translateLabel: true
-            submenuChannel: browseClassExtensionsMenuUsingManagerNamed:
-            argument: FileBasedSourceCodeManager
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: changeSetContainsChangedClassesAndSourceCodeManagerHolder
-            label: 'CheckIn All Changed Classes'
-            itemValue: classMenuCheckInAllChangedClassesUsingManagerNamed:
-            translateLabel: true
-            argument: FileBasedSourceCodeManager
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
-            label: 'CheckIn Build Support Files...'
-            itemValue: classMenuCheckInBuildSupportFilesUsingManagerNamed:
-            translateLabel: true
-            argument: FileBasedSourceCodeManager
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'CheckOut Newest'
-            itemValue: classMenuCheckOutNewestUsingManagerNamed:
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckOut 'CheckOut Newest')
-            argument: FileBasedSourceCodeManager
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'CheckOut Previous Version...'
-            itemValue: classMenuCheckOutUsingManagerNamed:
-            translateLabel: true
-            argument: FileBasedSourceCodeManager
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare with Newest in Repository...'
-            itemValue: classMenuCompareAgainstNewestInRepositoryUsingManagerNamed:
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryVersions 'Compare with Newest in Repository...')
-            argument: FileBasedSourceCodeManager
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare with Original in Repository...'
-            itemValue: classMenuCompareAgainstOriginalInRepositoryUsingManagerNamed:
-            translateLabel: true
-            argument: FileBasedSourceCodeManager
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare with Repository...'
-            itemValue: classMenuCompareWithRepositoryUsingManagerNamed:
-            translateLabel: true
-            argument: FileBasedSourceCodeManager
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare two Repository Versions...'
-            itemValue: classMenuCompareTwoRepositoryVersionsUsingManagerNamed:
-            translateLabel: true
-            argument: FileBasedSourceCodeManager
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectDefinitionOrClassWithExtensionsSelectedAndSourceCodeManagerHolder
-            label: 'Compare Extensions with Repository...'
-            itemValue: classMenuCompareExtensionsWithRepositoryUsingManagerNamed:
-            translateLabel: true
-            argument: FileBasedSourceCodeManager
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
-            label: 'Compare Build Support File'
-            translateLabel: true
-            submenuChannel: compareBuildSupportFileMenuUsingManagerNamed:
-            argument: FileBasedSourceCodeManager
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'Revision Log (Recent Changes)'
-            itemValue: classMenuShortRevisionLogUsingManagerNamed:
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryLog 'Revision Log (Recent Changes)')
-            argument: FileBasedSourceCodeManager
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'Revision Log (Full)'
-            itemValue: classMenuRevisionLogUsingManagerNamed:
-            translateLabel: true
-            argument: FileBasedSourceCodeManager
-            showBusyCursorWhilePerforming: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasClassSelectedHolderAndSourceCodeManagerHolder
+	    label: 'CheckIn...'
+	    itemValue: classMenuCheckInUsingManagerNamed:
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn...')
+	    argument: FileBasedSourceCodeManager
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasClassWithExtensionsSelectedHolder
+	    label: 'CheckIn Extensions For'
+	    translateLabel: true
+	    submenuChannel: browseClassExtensionsMenuUsingManagerNamed:
+	    argument: FileBasedSourceCodeManager
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: changeSetContainsChangedClassesAndSourceCodeManagerHolder
+	    label: 'CheckIn All Changed Classes'
+	    itemValue: classMenuCheckInAllChangedClassesUsingManagerNamed:
+	    translateLabel: true
+	    argument: FileBasedSourceCodeManager
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
+	    label: 'CheckIn Build Support Files...'
+	    itemValue: classMenuCheckInBuildSupportFilesUsingManagerNamed:
+	    translateLabel: true
+	    argument: FileBasedSourceCodeManager
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'CheckOut Newest'
+	    itemValue: classMenuCheckOutNewestUsingManagerNamed:
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckOut 'CheckOut Newest')
+	    argument: FileBasedSourceCodeManager
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'CheckOut Previous Version...'
+	    itemValue: classMenuCheckOutUsingManagerNamed:
+	    translateLabel: true
+	    argument: FileBasedSourceCodeManager
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare with Newest in Repository...'
+	    itemValue: classMenuCompareAgainstNewestInRepositoryUsingManagerNamed:
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryVersions 'Compare with Newest in Repository...')
+	    argument: FileBasedSourceCodeManager
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare with Original in Repository...'
+	    itemValue: classMenuCompareAgainstOriginalInRepositoryUsingManagerNamed:
+	    translateLabel: true
+	    argument: FileBasedSourceCodeManager
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare with Repository...'
+	    itemValue: classMenuCompareWithRepositoryUsingManagerNamed:
+	    translateLabel: true
+	    argument: FileBasedSourceCodeManager
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare two Repository Versions...'
+	    itemValue: classMenuCompareTwoRepositoryVersionsUsingManagerNamed:
+	    translateLabel: true
+	    argument: FileBasedSourceCodeManager
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectDefinitionOrClassWithExtensionsSelectedAndSourceCodeManagerHolder
+	    label: 'Compare Extensions with Repository...'
+	    itemValue: classMenuCompareExtensionsWithRepositoryUsingManagerNamed:
+	    translateLabel: true
+	    argument: FileBasedSourceCodeManager
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
+	    label: 'Compare Build Support File'
+	    translateLabel: true
+	    submenuChannel: compareBuildSupportFileMenuUsingManagerNamed:
+	    argument: FileBasedSourceCodeManager
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'Revision Log (Recent Changes)'
+	    itemValue: classMenuShortRevisionLogUsingManagerNamed:
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryLog 'Revision Log (Recent Changes)')
+	    argument: FileBasedSourceCodeManager
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'Revision Log (Full)'
+	    itemValue: classMenuRevisionLogUsingManagerNamed:
+	    translateLabel: true
+	    argument: FileBasedSourceCodeManager
+	    showBusyCursorWhilePerforming: true
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -13636,152 +13904,152 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasClassSelectedHolderAndSourceCodeManagerHolder
-            label: 'CheckIn...'
-            itemValue: classMenuCheckInUsingManagerNamed:
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn...')
-            argument: SourceCodeManagerPlaceholder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: 'CheckIn (Quick)...'
-            itemValue: classMenuQuickCheckInUsingManagerNamed:
-            translateLabel: true
-            isVisible: hasClassSelectedAndControlKeyDownHolder
-            argument: SourceCodeManagerPlaceholder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasClassWithExtensionsSelectedHolder
-            label: 'CheckIn Extensions For'
-            translateLabel: true
-            argument: SourceCodeManagerPlaceholder
-            submenuChannel: browseClassExtensionsMenuUsingManagerNamed:
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: changeSetContainsChangedClassesAndSourceCodeManagerHolder
-            label: 'CheckIn All Changed Classes'
-            itemValue: classMenuCheckInAllChangedClassesUsingManagerNamed:
-            translateLabel: true
-            argument: SourceCodeManagerPlaceholder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
-            label: 'CheckIn Build Support Files...'
-            itemValue: classMenuCheckInBuildSupportFilesUsingManagerNamed:
-            translateLabel: true
-            argument: SourceCodeManagerPlaceholder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'CheckOut Newest'
-            itemValue: classMenuCheckOutNewestUsingManagerNamed:
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckOut 'CheckOut Newest')
-            argument: SourceCodeManagerPlaceholder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'CheckOut Previous Version...'
-            itemValue: classMenuCheckOutUsingManagerNamed:
-            translateLabel: true
-            argument: SourceCodeManagerPlaceholder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'Revision Log (Recent Changes)'
-            itemValue: classMenuShortRevisionLogUsingManagerNamed:
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryLog 'Revision Log (Recent Changes)')
-            argument: SourceCodeManagerPlaceholder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'Revision Log (Full)'
-            itemValue: classMenuRevisionLogUsingManagerNamed:
-            translateLabel: true
-            argument: SourceCodeManagerPlaceholder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare with Newest in Repository...'
-            itemValue: classMenuCompareAgainstNewestInRepositoryUsingManagerNamed:
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryVersions 'Compare with Newest in Repository...')
-            argument: SourceCodeManagerPlaceholder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare with Original in Repository...'
-            itemValue: classMenuCompareAgainstOriginalInRepositoryUsingManagerNamed:
-            translateLabel: true
-            argument: SourceCodeManagerPlaceholder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare with Repository...'
-            itemValue: classMenuCompareWithRepositoryUsingManagerNamed:
-            translateLabel: true
-            argument: SourceCodeManagerPlaceholder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare two Repository Versions...'
-            itemValue: classMenuCompareTwoRepositoryVersionsUsingManagerNamed:
-            translateLabel: true
-            argument: SourceCodeManagerPlaceholder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectDefinitionOrClassWithExtensionsSelectedAndSourceCodeManagerHolder
-            label: 'Compare Extensions with Repository...'
-            itemValue: classMenuCompareExtensionsWithRepositoryUsingManagerNamed:
-            translateLabel: true
-            argument: SourceCodeManagerPlaceholder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
-            label: 'Compare Build Support File'
-            translateLabel: true
-            argument: SourceCodeManagerPlaceholder
-            submenuChannel: projectMenuSCMCompareBuildSupportFileForManagerNamed:
-            argument: Default
-          )
-         (MenuItem
-            label: 'Extras'
-            translateLabel: true
-            submenuChannel: classMenuSCMExtraForManagerNamed:
-            argument: SourceCodeManagerPlaceholder
-            isMenuSlice: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasClassSelectedHolderAndSourceCodeManagerHolder
+	    label: 'CheckIn...'
+	    itemValue: classMenuCheckInUsingManagerNamed:
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn...')
+	    argument: SourceCodeManagerPlaceholder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: 'CheckIn (Quick)...'
+	    itemValue: classMenuQuickCheckInUsingManagerNamed:
+	    translateLabel: true
+	    isVisible: hasClassSelectedAndControlKeyDownHolder
+	    argument: SourceCodeManagerPlaceholder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasClassWithExtensionsSelectedHolder
+	    label: 'CheckIn Extensions For'
+	    translateLabel: true
+	    argument: SourceCodeManagerPlaceholder
+	    submenuChannel: browseClassExtensionsMenuUsingManagerNamed:
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: changeSetContainsChangedClassesAndSourceCodeManagerHolder
+	    label: 'CheckIn All Changed Classes'
+	    itemValue: classMenuCheckInAllChangedClassesUsingManagerNamed:
+	    translateLabel: true
+	    argument: SourceCodeManagerPlaceholder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
+	    label: 'CheckIn Build Support Files...'
+	    itemValue: classMenuCheckInBuildSupportFilesUsingManagerNamed:
+	    translateLabel: true
+	    argument: SourceCodeManagerPlaceholder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'CheckOut Newest'
+	    itemValue: classMenuCheckOutNewestUsingManagerNamed:
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckOut 'CheckOut Newest')
+	    argument: SourceCodeManagerPlaceholder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'CheckOut Previous Version...'
+	    itemValue: classMenuCheckOutUsingManagerNamed:
+	    translateLabel: true
+	    argument: SourceCodeManagerPlaceholder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'Revision Log (Recent Changes)'
+	    itemValue: classMenuShortRevisionLogUsingManagerNamed:
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryLog 'Revision Log (Recent Changes)')
+	    argument: SourceCodeManagerPlaceholder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'Revision Log (Full)'
+	    itemValue: classMenuRevisionLogUsingManagerNamed:
+	    translateLabel: true
+	    argument: SourceCodeManagerPlaceholder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare with Newest in Repository...'
+	    itemValue: classMenuCompareAgainstNewestInRepositoryUsingManagerNamed:
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryVersions 'Compare with Newest in Repository...')
+	    argument: SourceCodeManagerPlaceholder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare with Original in Repository...'
+	    itemValue: classMenuCompareAgainstOriginalInRepositoryUsingManagerNamed:
+	    translateLabel: true
+	    argument: SourceCodeManagerPlaceholder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare with Repository...'
+	    itemValue: classMenuCompareWithRepositoryUsingManagerNamed:
+	    translateLabel: true
+	    argument: SourceCodeManagerPlaceholder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare two Repository Versions...'
+	    itemValue: classMenuCompareTwoRepositoryVersionsUsingManagerNamed:
+	    translateLabel: true
+	    argument: SourceCodeManagerPlaceholder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectDefinitionOrClassWithExtensionsSelectedAndSourceCodeManagerHolder
+	    label: 'Compare Extensions with Repository...'
+	    itemValue: classMenuCompareExtensionsWithRepositoryUsingManagerNamed:
+	    translateLabel: true
+	    argument: SourceCodeManagerPlaceholder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
+	    label: 'Compare Build Support File'
+	    translateLabel: true
+	    argument: SourceCodeManagerPlaceholder
+	    submenuChannel: projectMenuSCMCompareBuildSupportFileForManagerNamed:
+	    argument: Default
+	  )
+	 (MenuItem
+	    label: 'Extras'
+	    translateLabel: true
+	    submenuChannel: classMenuSCMExtraForManagerNamed:
+	    argument: SourceCodeManagerPlaceholder
+	    isMenuSlice: true
+	  )
+	 )
+	nil
+	nil
       )
 
     "Modified: / 12-10-2011 / 20:24:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -13803,27 +14071,27 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'Set Tag...'
-            itemValue: classMenuSetTag
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryTag 'Set Tag...')
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-            label: 'Edit Version in Repository...'
-            itemValue: classMenuEditVersionInRepository
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'Set Tag...'
+	    itemValue: classMenuSetTag
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryTag 'Set Tag...')
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+	    label: 'Edit Version in Repository...'
+	    itemValue: classMenuEditVersionInRepository
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -13842,62 +14110,62 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasClassesSelectedAndSubversionRepositoryExistsAndBranchSelectedHolder
-            label: 'Changeset'
-            translateLabel: true
-            submenuChannel: classSubversionChangesetMenu
-          )
-         (MenuItem
-            label: 'Branch'
-            translateLabel: true
-            submenuChannel: commonSubversionBranchMenu
-          )
-         (MenuItem
-            label: 'Browse working copy'
-            itemValue: commonMenuSubversionBrowseWorkingCopy
-            translateLabel: true
-          )
-         (MenuItem
-            label: 'More'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  label: 'Common Slice'
-                  translateLabel: true
-                  submenuChannel: commonSubversionMenuSlice
-                  isMenuSlice: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasClassesSelectedAndSubversionRepositoryExistsAndBranchSelectedHolder
-                  label: 'Compare'
-                  translateLabel: true
-                  submenuChannel: classSubversionCompareMenu
-                  labelImage: (ResourceRetriever #'SVN::IconLibrary' compare 'Compare')
-                )
-               (MenuItem
-                  enabled: hasClassesSelectedAndSubversionRepositoryExistsAndBranchSelectedHolder
-                  label: 'Browse Revision log'
-                  itemValue: classMenuSubversionShowRevisionLog
-                  translateLabel: true
-                  labelImage: (ResourceRetriever #'SVN::IconLibrary' log 'Browse Revision log')
-                )
-               )
-              nil
-              nil
-            )
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasClassesSelectedAndSubversionRepositoryExistsAndBranchSelectedHolder
+	    label: 'Changeset'
+	    translateLabel: true
+	    submenuChannel: classSubversionChangesetMenu
+	  )
+	 (MenuItem
+	    label: 'Branch'
+	    translateLabel: true
+	    submenuChannel: commonSubversionBranchMenu
+	  )
+	 (MenuItem
+	    label: 'Browse working copy'
+	    itemValue: commonMenuSubversionBrowseWorkingCopy
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: 'More'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  label: 'Common Slice'
+		  translateLabel: true
+		  submenuChannel: commonSubversionMenuSlice
+		  isMenuSlice: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasClassesSelectedAndSubversionRepositoryExistsAndBranchSelectedHolder
+		  label: 'Compare'
+		  translateLabel: true
+		  submenuChannel: classSubversionCompareMenu
+		  labelImage: (ResourceRetriever #'SVN::IconLibrary' compare 'Compare')
+		)
+	       (MenuItem
+		  enabled: hasClassesSelectedAndSubversionRepositoryExistsAndBranchSelectedHolder
+		  label: 'Browse Revision log'
+		  itemValue: classMenuSubversionShowRevisionLog
+		  translateLabel: true
+		  labelImage: (ResourceRetriever #'SVN::IconLibrary' log 'Browse Revision log')
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 )
+	nil
+	nil
       )
 
     "Created: / 15-01-2012 / 14:35:48 / cg"
@@ -13918,62 +14186,62 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasClassesSelectedAndSubversionRepositoryExistsAndBranchSelectedHolder
-            label: 'Changeset'
-            translateLabel: true
-            submenuChannel: classSubversionChangesetMenu
-          )
-         (MenuItem
-            label: 'Branch'
-            translateLabel: true
-            submenuChannel: commonSubversionBranchMenu
-          )
-         (MenuItem
-            label: 'Browse working copy'
-            itemValue: commonMenuSubversionBrowseWorkingCopy
-            translateLabel: true
-          )
-         (MenuItem
-            label: 'More'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  label: 'Common Slice'
-                  translateLabel: true
-                  submenuChannel: commonSubversionMenuSlice
-                  isMenuSlice: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasClassesSelectedAndSubversionRepositoryExistsAndBranchSelectedHolder
-                  label: 'Compare'
-                  translateLabel: true
-                  submenuChannel: classSubversionCompareMenu
-                  labelImage: (ResourceRetriever #'SVN::IconLibrary' compare 'Compare')
-                )
-               (MenuItem
-                  enabled: hasClassesSelectedAndSubversionRepositoryExistsAndBranchSelectedHolder
-                  label: 'Browse Revision log'
-                  itemValue: classMenuSubversionShowRevisionLog
-                  translateLabel: true
-                  labelImage: (ResourceRetriever #'SVN::IconLibrary' log 'Browse Revision log')
-                )
-               )
-              nil
-              nil
-            )
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasClassesSelectedAndSubversionRepositoryExistsAndBranchSelectedHolder
+	    label: 'Changeset'
+	    translateLabel: true
+	    submenuChannel: classSubversionChangesetMenu
+	  )
+	 (MenuItem
+	    label: 'Branch'
+	    translateLabel: true
+	    submenuChannel: commonSubversionBranchMenu
+	  )
+	 (MenuItem
+	    label: 'Browse working copy'
+	    itemValue: commonMenuSubversionBrowseWorkingCopy
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: 'More'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  label: 'Common Slice'
+		  translateLabel: true
+		  submenuChannel: commonSubversionMenuSlice
+		  isMenuSlice: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasClassesSelectedAndSubversionRepositoryExistsAndBranchSelectedHolder
+		  label: 'Compare'
+		  translateLabel: true
+		  submenuChannel: classSubversionCompareMenu
+		  labelImage: (ResourceRetriever #'SVN::IconLibrary' compare 'Compare')
+		)
+	       (MenuItem
+		  enabled: hasClassesSelectedAndSubversionRepositoryExistsAndBranchSelectedHolder
+		  label: 'Browse Revision log'
+		  itemValue: classMenuSubversionShowRevisionLog
+		  translateLabel: true
+		  labelImage: (ResourceRetriever #'SVN::IconLibrary' log 'Browse Revision log')
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -13992,54 +14260,54 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasClassSelectedAndSourceCodeManagerHolder
-            isVisible: cvsRepositoryMenusAreShown
-            label: 'CVS'
-            translateLabel: true
-            submenuChannel: classCVSMenu
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCVSIcon 'CVS')
-            argument: 'CVS'
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            enabled: hasClassesSelectedAndSubversionRepositoryExistsHolder
-            isVisible: svnRepositoryMenusAreShown
-            label: 'SubVersion'
-            translateLabel: true
-            submenuChannel: classSubversionMenu
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositorySVNIcon 'SubVersion')
-          )
-         (MenuItem
-            enabled: hasClassesSelectedAndFileBasedRepositoryExistsHolder
-            isVisible: fileBasedRepositoryMenusAreShown
-            label: 'File Repository'
-            translateLabel: true
-            submenuChannel: classFileBasedRepositoryMenu
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryIcon 'File Repository')
-          )
-         (MenuItem
-            enabled: hasClassesSelectedAndDataBaseRepositoryExistsHolder
-            isVisible: dataBaseRepositoryMenusAreShown
-            label: 'Database Repository'
-            translateLabel: true
-            submenuChannel: classDataBaseRepositoryMenu
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryIcon 'Database Repository')
-          )
-         (MenuItem
-            enabled: hasClassesSelectedAndMercurialRepositoryExistsHolder
-            isVisible: mercurialRepositoryMenusAreShown
-            label: 'Mercurial'
-            translateLabel: true
-            submenuChannel: classMercurialMenu
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryHGIcon 'Mercurial')
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasClassSelectedAndSourceCodeManagerHolder
+	    isVisible: cvsRepositoryMenusAreShown
+	    label: 'CVS'
+	    translateLabel: true
+	    submenuChannel: classCVSMenu
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCVSIcon 'CVS')
+	    argument: 'CVS'
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    enabled: hasClassesSelectedAndSubversionRepositoryExistsHolder
+	    isVisible: svnRepositoryMenusAreShown
+	    label: 'SubVersion'
+	    translateLabel: true
+	    submenuChannel: classSubversionMenu
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositorySVNIcon 'SubVersion')
+	  )
+	 (MenuItem
+	    enabled: hasClassesSelectedAndFileBasedRepositoryExistsHolder
+	    isVisible: fileBasedRepositoryMenusAreShown
+	    label: 'File Repository'
+	    translateLabel: true
+	    submenuChannel: classFileBasedRepositoryMenu
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryIcon 'File Repository')
+	  )
+	 (MenuItem
+	    enabled: hasClassesSelectedAndDataBaseRepositoryExistsHolder
+	    isVisible: dataBaseRepositoryMenusAreShown
+	    label: 'Database Repository'
+	    translateLabel: true
+	    submenuChannel: classDataBaseRepositoryMenu
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryIcon 'Database Repository')
+	  )
+	 (MenuItem
+	    enabled: hasClassesSelectedAndMercurialRepositoryExistsHolder
+	    isVisible: mercurialRepositoryMenusAreShown
+	    label: 'Mercurial'
+	    translateLabel: true
+	    submenuChannel: classMercurialMenu
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryHGIcon 'Mercurial')
+	  )
+	 )
+	nil
+	nil
       )
 
     "Modified: / 15-01-2012 / 14:50:31 / cg"
@@ -14060,49 +14328,49 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasClassSelectedAndSourceCodeManagerHolder
-            isVisible: cvsRepositoryMenusAreShown
-            label: 'CVS'
-            translateLabel: true
-            submenuChannel: classMenuSCMFor:
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCVSIcon 'CVS')
-            argument: CVSSourceCodeManager
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            enabled: hasClassesSelectedAndSubversionRepositoryExistsHolder
-            isVisible: svnRepositoryMenusAreShown
-            label: 'SubVersion'
-            translateLabel: true
-            submenuChannel: classMenuSCMFor:
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositorySVNIcon 'SubVersion')
-            argument: SVNSourceCodeManager
-          )
-         (MenuItem
-            enabled: hasClassSelectedAndSourceCodeManagerHolder
-            isVisible: mercurialRepositoryMenusAreShown
-            label: 'Mercurial'
-            translateLabel: true
-            submenuChannel: classMenuSCMFor:
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryHGIcon 'Mercurial')
-            argument: MercurialSourceCodeManager
-          )
-         (MenuItem
-            enabled: hasClassSelectedAndSourceCodeManagerHolder
-            isVisible: perforceRepositoryMenusAreShown
-            label: 'Perforce'
-            translateLabel: true
-            submenuChannel: classMenuSCMFor:
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositorySVNIcon 'Perforce')
-            argument: PerforceSourceCodeManager
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasClassSelectedAndSourceCodeManagerHolder
+	    isVisible: cvsRepositoryMenusAreShown
+	    label: 'CVS'
+	    translateLabel: true
+	    submenuChannel: classMenuSCMFor:
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCVSIcon 'CVS')
+	    argument: CVSSourceCodeManager
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    enabled: hasClassesSelectedAndSubversionRepositoryExistsHolder
+	    isVisible: svnRepositoryMenusAreShown
+	    label: 'SubVersion'
+	    translateLabel: true
+	    submenuChannel: classMenuSCMFor:
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositorySVNIcon 'SubVersion')
+	    argument: SVNSourceCodeManager
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedAndSourceCodeManagerHolder
+	    isVisible: mercurialRepositoryMenusAreShown
+	    label: 'Mercurial'
+	    translateLabel: true
+	    submenuChannel: classMenuSCMFor:
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryHGIcon 'Mercurial')
+	    argument: MercurialSourceCodeManager
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedAndSourceCodeManagerHolder
+	    isVisible: perforceRepositoryMenusAreShown
+	    label: 'Perforce'
+	    translateLabel: true
+	    submenuChannel: classMenuSCMFor:
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositorySVNIcon 'Perforce')
+	    argument: PerforceSourceCodeManager
+	  )
+	 )
+	nil
+	nil
       )
 
     "Modified: / 15-01-2012 / 14:50:44 / cg"
@@ -14123,49 +14391,49 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'Repository'
-            nameKey: SCM
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  label: 'Common Slice'
-                  nameKey: CommonSlice
-                  translateLabel: true
-                  submenuChannel: classMenuSCMFor:
-                  argument: SourceCodeManagerPlaceholder
-                  isMenuSlice: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'All Slice'
-                  translateLabel: true
-                  submenuChannel: classMenuSCMSliceAll
-                  isMenuSlice: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'Repository Settings'
-                  itemValue: openSettingsDialogAndSelectSourceCodeManagement
-                  translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'Repository'
+	    nameKey: SCM
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  label: 'Common Slice'
+		  nameKey: CommonSlice
+		  translateLabel: true
+		  submenuChannel: classMenuSCMFor:
+		  argument: SourceCodeManagerPlaceholder
+		  isMenuSlice: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'All Slice'
+		  translateLabel: true
+		  submenuChannel: classMenuSCMSliceAll
+		  isMenuSlice: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'Repository Settings'
+		  itemValue: openSettingsDialogAndSelectSourceCodeManagement
+		  translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 )
+	nil
+	nil
       )
 
     "Modified: / 15-10-2011 / 12:04:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -14186,21 +14454,21 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'All Slice'
-            translateLabel: true
-            submenuChannel: classMenuSCMSliceAll
-            isMenuSlice: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'All Slice'
+	    translateLabel: true
+	    submenuChannel: classMenuSCMSliceAll
+	    isMenuSlice: true
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -14219,62 +14487,62 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasClassSelectedAndSourceCodeManagerHolder
-            label: 'CVS'
-            isVisible: cvsRepositoryMenusAreShown
-            translateLabel: true
-            submenuChannel: classCVSMenu
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCVSIcon 'CVS')
-            argument: 'CVS'
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            enabled: hasClassesSelectedAndSubversionRepositoryExistsHolder
-            isVisible: svnRepositoryMenusAreShown
-            label: 'SubVersion'
-            translateLabel: true
-            submenuChannel: classSubversionMenu
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositorySVNIcon 'SubVersion')
-          )
-         (MenuItem
-            enabled: hasClassesSelectedAndMercurialRepositoryExistsHolder
-            isVisible: mercurialRepositoryMenusAreShown
-            label: 'Mercurial'
-            translateLabel: true
-            submenuChannel: classMercurialMenu
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryHGIcon 'Mercurial')
-          )
-         (MenuItem
-            enabled: hasClassesSelectedAndPerforceRepositoryExistsHolder
-            isVisible: perforceRepositoryMenusAreShown
-            label: 'Perforce'
-            translateLabel: true
-            submenuChannel: classPerforceMenu
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositorySVNIcon 'Perforce')
-          )
-         (MenuItem
-            enabled: hasClassesSelectedAndFileBasedRepositoryExistsHolder
-            label: 'File Repository'
-            isVisible: fileBasedRepositoryMenusAreShown
-            translateLabel: true
-            submenuChannel: classFileBasedRepositoryMenu
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryIcon 'File Repository')
-          )
-         (MenuItem
-            enabled: hasClassesSelectedAndDataBaseRepositoryExistsHolder
-            isVisible: dataBaseRepositoryMenusAreShown
-            label: 'Database Repository'
-            translateLabel: true
-            submenuChannel: classDataBaseRepositoryMenu
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryIcon 'Database Repository')
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasClassSelectedAndSourceCodeManagerHolder
+	    label: 'CVS'
+	    isVisible: cvsRepositoryMenusAreShown
+	    translateLabel: true
+	    submenuChannel: classCVSMenu
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCVSIcon 'CVS')
+	    argument: 'CVS'
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    enabled: hasClassesSelectedAndSubversionRepositoryExistsHolder
+	    isVisible: svnRepositoryMenusAreShown
+	    label: 'SubVersion'
+	    translateLabel: true
+	    submenuChannel: classSubversionMenu
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositorySVNIcon 'SubVersion')
+	  )
+	 (MenuItem
+	    enabled: hasClassesSelectedAndMercurialRepositoryExistsHolder
+	    isVisible: mercurialRepositoryMenusAreShown
+	    label: 'Mercurial'
+	    translateLabel: true
+	    submenuChannel: classMercurialMenu
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryHGIcon 'Mercurial')
+	  )
+	 (MenuItem
+	    enabled: hasClassesSelectedAndPerforceRepositoryExistsHolder
+	    isVisible: perforceRepositoryMenusAreShown
+	    label: 'Perforce'
+	    translateLabel: true
+	    submenuChannel: classPerforceMenu
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryP4Icon 'Perforce')
+	  )
+	 (MenuItem
+	    enabled: hasClassesSelectedAndFileBasedRepositoryExistsHolder
+	    label: 'File Repository'
+	    isVisible: fileBasedRepositoryMenusAreShown
+	    translateLabel: true
+	    submenuChannel: classFileBasedRepositoryMenu
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryIcon 'File Repository')
+	  )
+	 (MenuItem
+	    enabled: hasClassesSelectedAndDataBaseRepositoryExistsHolder
+	    isVisible: dataBaseRepositoryMenusAreShown
+	    label: 'Database Repository'
+	    translateLabel: true
+	    submenuChannel: classDataBaseRepositoryMenu
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryIcon 'Database Repository')
+	  )
+	 )
+	nil
+	nil
       )
 
     "Modified: / 15-01-2012 / 14:49:41 / cg"
@@ -14295,159 +14563,159 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: '** No SourceCodeManager - See Settings in the Launcher **'
-            translateLabel: true
-            isVisible: hasNoSourceCodeManagerHolder
-          )
-         (MenuItem
-            label: '-'
-            isVisible: hasNoSourceCodeManagerHolder
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolderAndSourceCodeManagerHolder
-            label: 'CheckIn...'
-            itemValue: classMenuCheckIn
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn...')
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasClassWithExtensionsSelectedHolder
-            label: 'CheckIn Extensions For'
-            translateLabel: true
-            submenuChannel: browseClassExtensionsMenu
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: changeSetContainsChangedClassesAndSourceCodeManagerHolder
-            label: 'CheckIn All Changed Classes'
-            itemValue: classMenuCheckInAllChangedClasses
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: 'Quick CheckIn...'
-            itemValue: classMenuQuickCheckIn
-            translateLabel: true
-            isVisible: hasClassSelectedAndControlKeyDownHolder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
-            label: 'CheckIn Build Support Files...'
-            itemValue: classMenuCheckInBuildSupportFiles
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'CheckOut Newest'
-            itemValue: classMenuCheckOutNewest
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckOut 'CheckOut Newest')
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'CheckOut Previous Version...'
-            itemValue: classMenuCheckOut
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-            label: 'Edit Version in Repository...'
-            itemValue: classMenuEditVersionInRepository
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare with Newest in Repository...'
-            itemValue: classMenuCompareAgainstNewestInRepository
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryVersions 'Compare with Newest in Repository...')
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare with Original in Repository...'
-            itemValue: classMenuCompareAgainstOriginalInRepository
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare with Repository...'
-            itemValue: classMenuCompareWithRepository
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare two Repository Versions...'
-            itemValue: classMenuCompareTwoRepositoryVersions
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectDefinitionOrClassWithExtensionsSelectedAndSourceCodeManagerHolder
-            label: 'Compare Extensions with Repository...'
-            itemValue: classMenuCompareExtensionsWithRepository
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
-            label: 'Compare Build Support File'
-            translateLabel: true
-            submenuChannel: compareBuildSupportFileMenu
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'Set Tag...'
-            itemValue: classMenuSetTag
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryTag 'Set Tag...')
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'Revision Log (Recent Changes)'
-            itemValue: classMenuShortRevisionLog
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryLog 'Revision Log (Recent Changes)')
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'Revision Log (Full)'
-            itemValue: classMenuRevisionLog
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: '** No SourceCodeManager - See Settings in the Launcher **'
+	    translateLabel: true
+	    isVisible: hasNoSourceCodeManagerHolder
+	  )
+	 (MenuItem
+	    label: '-'
+	    isVisible: hasNoSourceCodeManagerHolder
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolderAndSourceCodeManagerHolder
+	    label: 'CheckIn...'
+	    itemValue: classMenuCheckIn
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn...')
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasClassWithExtensionsSelectedHolder
+	    label: 'CheckIn Extensions For'
+	    translateLabel: true
+	    submenuChannel: browseClassExtensionsMenu
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: changeSetContainsChangedClassesAndSourceCodeManagerHolder
+	    label: 'CheckIn All Changed Classes'
+	    itemValue: classMenuCheckInAllChangedClasses
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: 'Quick CheckIn...'
+	    itemValue: classMenuQuickCheckIn
+	    translateLabel: true
+	    isVisible: hasClassSelectedAndControlKeyDownHolder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
+	    label: 'CheckIn Build Support Files...'
+	    itemValue: classMenuCheckInBuildSupportFiles
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'CheckOut Newest'
+	    itemValue: classMenuCheckOutNewest
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckOut 'CheckOut Newest')
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'CheckOut Previous Version...'
+	    itemValue: classMenuCheckOut
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+	    label: 'Edit Version in Repository...'
+	    itemValue: classMenuEditVersionInRepository
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare with Newest in Repository...'
+	    itemValue: classMenuCompareAgainstNewestInRepository
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryVersions 'Compare with Newest in Repository...')
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare with Original in Repository...'
+	    itemValue: classMenuCompareAgainstOriginalInRepository
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare with Repository...'
+	    itemValue: classMenuCompareWithRepository
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare two Repository Versions...'
+	    itemValue: classMenuCompareTwoRepositoryVersions
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectDefinitionOrClassWithExtensionsSelectedAndSourceCodeManagerHolder
+	    label: 'Compare Extensions with Repository...'
+	    itemValue: classMenuCompareExtensionsWithRepository
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
+	    label: 'Compare Build Support File'
+	    translateLabel: true
+	    submenuChannel: compareBuildSupportFileMenu
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'Set Tag...'
+	    itemValue: classMenuSetTag
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryTag 'Set Tag...')
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'Revision Log (Recent Changes)'
+	    itemValue: classMenuShortRevisionLog
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryLog 'Revision Log (Recent Changes)')
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'Revision Log (Full)'
+	    itemValue: classMenuRevisionLog
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -14466,159 +14734,166 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: '** No SourceCodeManager - See Settings in the Launcher **'
-            translateLabel: true
-            isVisible: hasNoSourceCodeManagerHolder
-          )
-         (MenuItem
-            label: '-'
-            isVisible: hasNoSourceCodeManagerHolder
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolderAndSourceCodeManagerHolder
-            label: 'CheckIn...'
-            itemValue: classMenuCheckIn
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn...')
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasClassWithExtensionsSelectedHolder
-            label: 'CheckIn Extensions For'
-            translateLabel: true
-            submenuChannel: browseClassExtensionsMenu
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: changeSetContainsChangedClassesAndSourceCodeManagerHolder
-            label: 'CheckIn All Changed Classes'
-            itemValue: classMenuCheckInAllChangedClasses
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: 'Quick CheckIn...'
-            itemValue: classMenuQuickCheckIn
-            translateLabel: true
-            isVisible: hasClassSelectedAndControlKeyDownHolder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
-            label: 'CheckIn Build Support Files...'
-            itemValue: classMenuCheckInBuildSupportFiles
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'CheckOut Newest'
-            itemValue: classMenuCheckOutNewest
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckOut 'CheckOut Newest')
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'CheckOut Previous Version...'
-            itemValue: classMenuCheckOut
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-            label: 'Edit Version in Repository...'
-            itemValue: classMenuEditVersionInRepository
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare with Newest in Repository...'
-            itemValue: classMenuCompareAgainstNewestInRepository
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryVersions 'Compare with Newest in Repository...')
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare with Original in Repository...'
-            itemValue: classMenuCompareAgainstOriginalInRepository
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare with Repository...'
-            itemValue: classMenuCompareWithRepository
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare two Repository Versions...'
-            itemValue: classMenuCompareTwoRepositoryVersions
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectDefinitionOrClassWithExtensionsSelectedAndSourceCodeManagerHolder
-            label: 'Compare Extensions with Repository...'
-            itemValue: classMenuCompareExtensionsWithRepository
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
-            label: 'Compare Build Support File'
-            translateLabel: true
-            submenuChannel: compareBuildSupportFileMenu
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'Set Tag...'
-            itemValue: classMenuSetTag
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryTag 'Set Tag...')
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'Revision Log (Recent Changes)'
-            itemValue: classMenuShortRevisionLog
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryLog 'Revision Log (Recent Changes)')
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'Revision Log (Full)'
-            itemValue: classMenuRevisionLog
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: '** No SourceCodeManager - See Settings in the Launcher **'
+	    translateLabel: true
+	    isVisible: hasNoSourceCodeManagerHolder
+	  )
+	 (MenuItem
+	    label: '-'
+	    isVisible: hasNoSourceCodeManagerHolder
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolderAndSourceCodeManagerHolder
+	    label: 'CheckIn...'
+	    itemValue: classMenuCheckInP4
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn...')
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasClassWithExtensionsSelectedHolder
+	    label: 'CheckIn Extensions For'
+	    translateLabel: true
+	    submenuChannel: browseClassExtensionsMenu
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: changeSetContainsChangedClassesAndSourceCodeManagerHolder
+	    label: 'CheckIn All Changed Classes'
+	    itemValue: classMenuCheckInAllChangedClasses
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: 'Quick CheckIn...'
+	    itemValue: classMenuQuickCheckIn
+	    translateLabel: true
+	    isVisible: hasClassSelectedAndControlKeyDownHolder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
+	    label: 'CheckIn Build Support Files...'
+	    itemValue: classMenuCheckInBuildSupportFiles
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolderAndSourceCodeManagerHolder
+	    label: 'Submit...'
+	    itemValue: classMenuPerforceSubmit
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'CheckOut Newest'
+	    itemValue: classMenuCheckOutNewest
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckOut 'CheckOut Newest')
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'CheckOut Previous Version...'
+	    itemValue: classMenuCheckOut
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+	    label: 'Edit Version in Repository...'
+	    itemValue: classMenuEditVersionInRepository
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare with Newest in Repository...'
+	    itemValue: classMenuCompareAgainstNewestInRepository
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryVersions 'Compare with Newest in Repository...')
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare with Original in Repository...'
+	    itemValue: classMenuCompareAgainstOriginalInRepository
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare with Repository...'
+	    itemValue: classMenuCompareWithRepository
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare two Repository Versions...'
+	    itemValue: classMenuCompareTwoRepositoryVersions
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectDefinitionOrClassWithExtensionsSelectedAndSourceCodeManagerHolder
+	    label: 'Compare Extensions with Repository...'
+	    itemValue: classMenuCompareExtensionsWithRepository
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
+	    label: 'Compare Build Support File'
+	    translateLabel: true
+	    submenuChannel: compareBuildSupportFileMenu
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'Set Tag...'
+	    itemValue: classMenuSetTag
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryTag 'Set Tag...')
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'Revision Log (Recent Changes)'
+	    itemValue: classMenuShortRevisionLog
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryLog 'Revision Log (Recent Changes)')
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'Revision Log (Full)'
+	    itemValue: classMenuRevisionLog
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -14636,159 +14911,159 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: '** No SourceCodeManager - See Settings in the Launcher **'
-            translateLabel: true
-            isVisible: hasNoSourceCodeManagerHolder
-          )
-         (MenuItem
-            label: '-'
-            isVisible: hasNoSourceCodeManagerHolder
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolderAndSourceCodeManagerHolder
-            label: 'CheckIn...'
-            itemValue: classMenuCheckIn
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn...')
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasClassWithExtensionsSelectedHolder
-            label: 'CheckIn Extensions For'
-            translateLabel: true
-            submenuChannel: browseClassExtensionsMenu
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: changeSetContainsChangedClassesAndSourceCodeManagerHolder
-            label: 'CheckIn All Changed Classes'
-            itemValue: classMenuCheckInAllChangedClasses
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: 'Quick CheckIn...'
-            itemValue: classMenuQuickCheckIn
-            translateLabel: true
-            isVisible: hasClassSelectedAndControlKeyDownHolder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
-            label: 'CheckIn Build Support Files...'
-            itemValue: classMenuCheckInBuildSupportFiles
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'Set Tag...'
-            itemValue: classMenuSetTag
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryTag 'Set Tag...')
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'CheckOut Newest'
-            itemValue: classMenuCheckOutNewest
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckOut 'CheckOut Newest')
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'CheckOut Previous Version...'
-            itemValue: classMenuCheckOut
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'Revision Log (Recent Changes)'
-            itemValue: classMenuShortRevisionLog
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryLog 'Revision Log (Recent Changes)')
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
-            label: 'Revision Log (Full)'
-            itemValue: classMenuRevisionLog
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare with Newest in Repository...'
-            itemValue: classMenuCompareAgainstNewestInRepository
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryVersions 'Compare with Newest in Repository...')
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare with Original in Repository...'
-            itemValue: classMenuCompareAgainstOriginalInRepository
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare with Repository...'
-            itemValue: classMenuCompareWithRepository
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-            label: 'Compare two Repository Versions...'
-            itemValue: classMenuCompareTwoRepositoryVersions
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
-            label: 'Compare Extensions with Repository...'
-            itemValue: classMenuCompareExtensionsWithRepository
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
-            label: 'Compare Build Support File'
-            translateLabel: true
-            submenuChannel: compareBuildSupportFileMenu
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
-            label: 'Edit Version in Repository...'
-            itemValue: classMenuEditVersionInRepository
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: '** No SourceCodeManager - See Settings in the Launcher **'
+	    translateLabel: true
+	    isVisible: hasNoSourceCodeManagerHolder
+	  )
+	 (MenuItem
+	    label: '-'
+	    isVisible: hasNoSourceCodeManagerHolder
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedHolderAndSourceCodeManagerHolder
+	    label: 'CheckIn...'
+	    itemValue: classMenuCheckIn
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn...')
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasClassWithExtensionsSelectedHolder
+	    label: 'CheckIn Extensions For'
+	    translateLabel: true
+	    submenuChannel: browseClassExtensionsMenu
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: changeSetContainsChangedClassesAndSourceCodeManagerHolder
+	    label: 'CheckIn All Changed Classes'
+	    itemValue: classMenuCheckInAllChangedClasses
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: 'Quick CheckIn...'
+	    itemValue: classMenuQuickCheckIn
+	    translateLabel: true
+	    isVisible: hasClassSelectedAndControlKeyDownHolder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
+	    label: 'CheckIn Build Support Files...'
+	    itemValue: classMenuCheckInBuildSupportFiles
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'Set Tag...'
+	    itemValue: classMenuSetTag
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryTag 'Set Tag...')
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'CheckOut Newest'
+	    itemValue: classMenuCheckOutNewest
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckOut 'CheckOut Newest')
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'CheckOut Previous Version...'
+	    itemValue: classMenuCheckOut
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'Revision Log (Recent Changes)'
+	    itemValue: classMenuShortRevisionLog
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryLog 'Revision Log (Recent Changes)')
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasNonPrivateClassSelectedAndSourceCodeManagerHolder
+	    label: 'Revision Log (Full)'
+	    itemValue: classMenuRevisionLog
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare with Newest in Repository...'
+	    itemValue: classMenuCompareAgainstNewestInRepository
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryVersions 'Compare with Newest in Repository...')
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare with Original in Repository...'
+	    itemValue: classMenuCompareAgainstOriginalInRepository
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare with Repository...'
+	    itemValue: classMenuCompareWithRepository
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+	    label: 'Compare two Repository Versions...'
+	    itemValue: classMenuCompareTwoRepositoryVersions
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
+	    label: 'Compare Extensions with Repository...'
+	    itemValue: classMenuCompareExtensionsWithRepository
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectDefinitionSelectedAndSourceCodeManagerHolder
+	    label: 'Compare Build Support File'
+	    translateLabel: true
+	    submenuChannel: compareBuildSupportFileMenu
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasSingleClassSelectedAndSourceCodeManagerHolder
+	    label: 'Edit Version in Repository...'
+	    itemValue: classMenuEditVersionInRepository
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 )
+	nil
+	nil
       )
 ! !
 
@@ -14808,146 +15083,146 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-              (
-               (MenuItem
-                  enabled: hasProjectSelectedAndSourceCodeManagerHolder
-                  label: 'CheckIn...'
-                  itemValue: projectMenuCheckInAll
-                  translateLabel: true
-                  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn...')
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedAndSourceCodeManagerHolder
-                  label: 'CheckIn Classes Only...'
-                  itemValue: projectMenuCheckInClasses
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedAndSourceCodeManagerHolder
-                  label: 'CheckIn Extensions Only...'
-                  itemValue: projectMenuCheckInExtensions
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedAndSourceCodeManagerHolder
-                  label: 'CheckIn Build Support Files Only...'
-                  itemValue: projectMenuCheckInBuildSupportFiles
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedAndSourceCodeManagerHolder
-                  label: 'Set Tag (Release As)...'
-                  itemValue: projectMenuSetTag
-                  translateLabel: true
-                  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryTag 'Set Tag (Release As)...')
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedAndSourceCodeManagerHolder
-                  label: 'CheckOut Newest'
-                  itemValue: projectMenuCheckOutNewest
-                  translateLabel: true
-                  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckOut 'CheckOut Newest')
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedAndSourceCodeManagerHolder
-                  label: 'CheckOut Previous Version...'
-                  itemValue: projectMenuCheckOut
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedAndSourceCodeManagerHolder
-                  label: 'CheckOut Extensions Only...'
-                  itemValue: projectMenuCheckOutExtensions
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'Import Structure...'
-                  itemValue: projectMenuImport
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: 'Import...'
-                  itemValue: projectMenuImportAndLoadClasses
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedAndSourceCodeManagerHolder
-                  label: 'Repository History...'
-                  itemValue: projectMenuRepositoryHistory
-                  translateLabel: true
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedAndSourceCodeManagerHolder
-                  label: 'Compare with Newest in Repository...'
-                  itemValue: projectMenuCompareAgainstNewestInRepository
-                  translateLabel: true
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedAndSourceCodeManagerHolder
-                  label: 'Compare with Repository at Date...'
-                  itemValue: projectMenuCompareAgainstRepository
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: 'Compare Build Support File'
-                  translateLabel: true
-                  submenuChannel: compareBuildSupportFileMenu
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedAndSourceCodeManagerHolder
-                  label: 'Consistency Check...'
-                  itemValue: projectMenuCheckRepositoryConsistency
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                  isVisible: false
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedHolder
-                  label: 'Resource Files...'
-                  itemValue: projectMenuResources
-                  translateLabel: true
-                  isVisible: false
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedHolder
-                  label: 'Bitmap Files...'
-                  itemValue: projectMenuBitmapFiles
-                  translateLabel: true
-                  isVisible: false
-                )
-               )
-              nil
-              nil
-            )
+    ^
+     #(Menu
+	      (
+	       (MenuItem
+		  enabled: hasProjectSelectedAndSourceCodeManagerHolder
+		  label: 'CheckIn...'
+		  itemValue: projectMenuCheckInAll
+		  translateLabel: true
+		  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn...')
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedAndSourceCodeManagerHolder
+		  label: 'CheckIn Classes Only...'
+		  itemValue: projectMenuCheckInClasses
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedAndSourceCodeManagerHolder
+		  label: 'CheckIn Extensions Only...'
+		  itemValue: projectMenuCheckInExtensions
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedAndSourceCodeManagerHolder
+		  label: 'CheckIn Build Support Files Only...'
+		  itemValue: projectMenuCheckInBuildSupportFiles
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedAndSourceCodeManagerHolder
+		  label: 'Set Tag (Release As)...'
+		  itemValue: projectMenuSetTag
+		  translateLabel: true
+		  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryTag 'Set Tag (Release As)...')
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedAndSourceCodeManagerHolder
+		  label: 'CheckOut Newest'
+		  itemValue: projectMenuCheckOutNewest
+		  translateLabel: true
+		  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckOut 'CheckOut Newest')
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedAndSourceCodeManagerHolder
+		  label: 'CheckOut Previous Version...'
+		  itemValue: projectMenuCheckOut
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedAndSourceCodeManagerHolder
+		  label: 'CheckOut Extensions Only...'
+		  itemValue: projectMenuCheckOutExtensions
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'Import Structure...'
+		  itemValue: projectMenuImport
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: 'Import...'
+		  itemValue: projectMenuImportAndLoadClasses
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedAndSourceCodeManagerHolder
+		  label: 'Repository History...'
+		  itemValue: projectMenuRepositoryHistory
+		  translateLabel: true
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedAndSourceCodeManagerHolder
+		  label: 'Compare with Newest in Repository...'
+		  itemValue: projectMenuCompareAgainstNewestInRepository
+		  translateLabel: true
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedAndSourceCodeManagerHolder
+		  label: 'Compare with Repository at Date...'
+		  itemValue: projectMenuCompareAgainstRepository
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: 'Compare Build Support File'
+		  translateLabel: true
+		  submenuChannel: compareBuildSupportFileMenu
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedAndSourceCodeManagerHolder
+		  label: 'Consistency Check...'
+		  itemValue: projectMenuCheckRepositoryConsistency
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		  isVisible: false
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedHolder
+		  label: 'Resource Files...'
+		  itemValue: projectMenuResources
+		  translateLabel: true
+		  isVisible: false
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedHolder
+		  label: 'Bitmap Files...'
+		  itemValue: projectMenuBitmapFiles
+		  translateLabel: true
+		  isVisible: false
+		)
+	       )
+	      nil
+	      nil
+	    )
 !
 
 projectMenuSCMCommon
@@ -14965,153 +15240,153 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasProjectSelectedAndSourceCodeManagerHolder
-            label: 'CheckIn...'
-            itemValue: projectMenuCheckInAllUsingManagerNamed:
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn...')
-            argument: SourceCodeManagerPlaceholder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectSelectedAndSourceCodeManagerHolder
-            label: 'CheckIn Classes Only...'
-            itemValue: projectMenuCheckInClassesUsingManagerNamed:
-            translateLabel: true
-            argument: SourceCodeManagerPlaceholder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectSelectedAndSourceCodeManagerHolder
-            label: 'CheckIn Extensions Only...'
-            itemValue: projectMenuCheckInExtensionsUsingManagerNamed:
-            translateLabel: true
-            argument: SourceCodeManagerPlaceholder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectSelectedAndSourceCodeManagerHolder
-            label: 'CheckIn Build Support Files Only...'
-            itemValue: projectMenuCheckInBuildSupportFilesUsingManagerNamed:
-            translateLabel: true
-            argument: SourceCodeManagerPlaceholder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasProjectSelectedAndSourceCodeManagerHolder
-            label: 'CheckOut Newest'
-            itemValue: projectMenuCheckOutNewestUsingManagerNamed:
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckOut 'CheckOut Newest')
-            argument: SourceCodeManagerPlaceholder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectSelectedAndSourceCodeManagerHolder
-            label: 'CheckOut Previous Version...'
-            itemValue: projectMenuCheckOutUsingManagerNamed:
-            translateLabel: true
-            argument: SourceCodeManagerPlaceholder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectSelectedAndSourceCodeManagerHolder
-            label: 'CheckOut Extensions Only...'
-            itemValue: projectMenuCheckOutExtensionsUsingManagerNamed:
-            translateLabel: true
-            argument: SourceCodeManagerPlaceholder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Import Structure...'
-            itemValue: projectMenuImportUsing:
-            translateLabel: true
-            argument: SourceCodeManagerPlaceholder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: 'Import...'
-            itemValue: projectMenuImportAndLoadClassesUsingManagerNamed:
-            translateLabel: true
-            argument: SourceCodeManagerPlaceholder
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasProjectSelectedAndSourceCodeManagerHolder
-            label: 'Compare with Newest in Repository...'
-            itemValue: projectMenuCompareAgainstNewestInRepositoryUsingManagerNamed:
-            translateLabel: true
-            argument: SourceCodeManagerPlaceholder
-          )
-         (MenuItem
-            enabled: hasProjectSelectedAndSourceCodeManagerHolder
-            label: 'Compare with Repository at Date...'
-            itemValue: projectMenuCompareAgainstRepositoryUsingManagerNamed:
-            translateLabel: true
-            argument: SourceCodeManagerPlaceholder
-          )
-         (MenuItem
-            label: 'Compare Build Support File'
-            translateLabel: true
-            submenuChannel: projectMenuSCMCompareBuildSupportFileForManagerNamed:
-            argument: SourceCodeManagerPlaceholder
-          )
-         (MenuItem
-            enabled: hasProjectSelectedAndSourceCodeManagerHolder
-            label: 'Consistency Check...'
-            itemValue: projectMenuCheckRepositoryConsistencyUsingManagerNamed:
-            translateLabel: true
-            argument: SourceCodeManagerPlaceholder
-          )
-         (MenuItem
-            enabled: hasProjectSelectedAndSourceCodeManagerHolder
-            label: 'Integrity Check...'
-            itemValue: projectMenuCheckPackageIntegrity
-            translateLabel: true
-          )
-         (MenuItem
-            label: '-'
-            isVisible: false
-          )
-         (MenuItem
-            enabled: hasProjectSelectedHolder
-            label: 'Resource Files...'
-            itemValue: projectMenuResourcesUsingManagerNamed:
-            translateLabel: true
-            isVisible: false
-            argument: SourceCodeManagerPlaceholder
-          )
-         (MenuItem
-            enabled: hasProjectSelectedHolder
-            label: 'Bitmap Files...'
-            itemValue: projectMenuBitmapFilesUsingManagerNamed:
-            translateLabel: true
-            isVisible: false
-            argument: SourceCodeManagerPlaceholder
-          )
-         (MenuItem
-            label: 'Extras'
-            translateLabel: true
-            submenuChannel: projectMenuSCMExtraFor:
-            argument: SourceCodeManagerPlaceholder
-            isMenuSlice: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasProjectSelectedAndSourceCodeManagerHolder
+	    label: 'CheckIn...'
+	    itemValue: projectMenuCheckInAllUsingManagerNamed:
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn...')
+	    argument: SourceCodeManagerPlaceholder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedAndSourceCodeManagerHolder
+	    label: 'CheckIn Classes Only...'
+	    itemValue: projectMenuCheckInClassesUsingManagerNamed:
+	    translateLabel: true
+	    argument: SourceCodeManagerPlaceholder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedAndSourceCodeManagerHolder
+	    label: 'CheckIn Extensions Only...'
+	    itemValue: projectMenuCheckInExtensionsUsingManagerNamed:
+	    translateLabel: true
+	    argument: SourceCodeManagerPlaceholder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedAndSourceCodeManagerHolder
+	    label: 'CheckIn Build Support Files Only...'
+	    itemValue: projectMenuCheckInBuildSupportFilesUsingManagerNamed:
+	    translateLabel: true
+	    argument: SourceCodeManagerPlaceholder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedAndSourceCodeManagerHolder
+	    label: 'CheckOut Newest'
+	    itemValue: projectMenuCheckOutNewestUsingManagerNamed:
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckOut 'CheckOut Newest')
+	    argument: SourceCodeManagerPlaceholder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedAndSourceCodeManagerHolder
+	    label: 'CheckOut Previous Version...'
+	    itemValue: projectMenuCheckOutUsingManagerNamed:
+	    translateLabel: true
+	    argument: SourceCodeManagerPlaceholder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedAndSourceCodeManagerHolder
+	    label: 'CheckOut Extensions Only...'
+	    itemValue: projectMenuCheckOutExtensionsUsingManagerNamed:
+	    translateLabel: true
+	    argument: SourceCodeManagerPlaceholder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Import Structure...'
+	    itemValue: projectMenuImportUsing:
+	    translateLabel: true
+	    argument: SourceCodeManagerPlaceholder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: 'Import...'
+	    itemValue: projectMenuImportAndLoadClassesUsingManagerNamed:
+	    translateLabel: true
+	    argument: SourceCodeManagerPlaceholder
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedAndSourceCodeManagerHolder
+	    label: 'Compare with Newest in Repository...'
+	    itemValue: projectMenuCompareAgainstNewestInRepositoryUsingManagerNamed:
+	    translateLabel: true
+	    argument: SourceCodeManagerPlaceholder
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedAndSourceCodeManagerHolder
+	    label: 'Compare with Repository at Date...'
+	    itemValue: projectMenuCompareAgainstRepositoryUsingManagerNamed:
+	    translateLabel: true
+	    argument: SourceCodeManagerPlaceholder
+	  )
+	 (MenuItem
+	    label: 'Compare Build Support File'
+	    translateLabel: true
+	    submenuChannel: projectMenuSCMCompareBuildSupportFileForManagerNamed:
+	    argument: SourceCodeManagerPlaceholder
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedAndSourceCodeManagerHolder
+	    label: 'Consistency Check...'
+	    itemValue: projectMenuCheckRepositoryConsistencyUsingManagerNamed:
+	    translateLabel: true
+	    argument: SourceCodeManagerPlaceholder
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedAndSourceCodeManagerHolder
+	    label: 'Integrity Check...'
+	    itemValue: projectMenuCheckPackageIntegrity
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: '-'
+	    isVisible: false
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedHolder
+	    label: 'Resource Files...'
+	    itemValue: projectMenuResourcesUsingManagerNamed:
+	    translateLabel: true
+	    isVisible: false
+	    argument: SourceCodeManagerPlaceholder
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedHolder
+	    label: 'Bitmap Files...'
+	    itemValue: projectMenuBitmapFilesUsingManagerNamed:
+	    translateLabel: true
+	    isVisible: false
+	    argument: SourceCodeManagerPlaceholder
+	  )
+	 (MenuItem
+	    label: 'Extras'
+	    translateLabel: true
+	    submenuChannel: projectMenuSCMExtraFor:
+	    argument: SourceCodeManagerPlaceholder
+	    isMenuSlice: true
+	  )
+	 )
+	nil
+	nil
       )
 
     "Modified: / 23-02-2012 / 14:30:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -15131,92 +15406,92 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasSingleProjectOrProjectDefinitionSelected
-            label: 'Make.spec'
-            itemValue: projectMenuShowGeneratedBuildFile:usingManager:
-            translateLabel: true
-            argument: 'Make.spec'
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleProjectOrProjectDefinitionSelected
-            label: 'Make.proto'
-            itemValue: projectMenuShowGeneratedBuildFile:usingManager:
-            translateLabel: true
-            argument: 'Make.proto'
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleProjectOrProjectDefinitionSelected
-            label: 'bc.mak'
-            itemValue: projectMenuShowGeneratedBuildFile:usingManager:
-            translateLabel: true
-            argument: 'bc.mak'
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleProjectOrProjectDefinitionSelected
-            label: 'libInit.cc'
-            itemValue: projectMenuShowGeneratedBuildFile:usingManager:
-            translateLabel: true
-            argument: 'libInit.cc'
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleProjectOrProjectDefinitionSelected
-            label: 'modules.stx'
-            itemValue: projectMenuShowGeneratedBuildFile:usingManager:
-            translateLabel: true
-            argument: 'modules.stx'
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleProjectOrProjectDefinitionSelected
-            label: 'lib.rc / app.rc'
-            itemValue: projectMenuShowGeneratedBuildFile:usingManager:
-            translateLabel: true
-            argument: 'lib.rc'
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleProjectOrProjectDefinitionSelected
-            label: 'app.nsi'
-            itemValue: projectMenuShowGeneratedBuildFile:usingManager:
-            translateLabel: true
-            argument: 'app.nsi'
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleProjectOrProjectDefinitionSelected
-            label: 'abbrev.stc'
-            itemValue: projectMenuShowGeneratedBuildFile:usingManager:
-            translateLabel: true
-            argument: 'abbrev.stc'
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleProjectOrProjectDefinitionSelected
-            label: 'loadAll'
-            itemValue: projectMenuShowGeneratedBuildFile:usingManager:
-            translateLabel: true
-            argument: 'loadAll'
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasSingleProjectOrProjectDefinitionSelected
-            label: 'bmake.bat'
-            itemValue: projectMenuShowGeneratedBuildFile:usingManager:
-            translateLabel: true
-            argument: 'bmake.bat'
-            showBusyCursorWhilePerforming: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasSingleProjectOrProjectDefinitionSelected
+	    label: 'Make.spec'
+	    itemValue: projectMenuShowGeneratedBuildFile:usingManager:
+	    translateLabel: true
+	    argument: 'Make.spec'
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleProjectOrProjectDefinitionSelected
+	    label: 'Make.proto'
+	    itemValue: projectMenuShowGeneratedBuildFile:usingManager:
+	    translateLabel: true
+	    argument: 'Make.proto'
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleProjectOrProjectDefinitionSelected
+	    label: 'bc.mak'
+	    itemValue: projectMenuShowGeneratedBuildFile:usingManager:
+	    translateLabel: true
+	    argument: 'bc.mak'
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleProjectOrProjectDefinitionSelected
+	    label: 'libInit.cc'
+	    itemValue: projectMenuShowGeneratedBuildFile:usingManager:
+	    translateLabel: true
+	    argument: 'libInit.cc'
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleProjectOrProjectDefinitionSelected
+	    label: 'modules.stx'
+	    itemValue: projectMenuShowGeneratedBuildFile:usingManager:
+	    translateLabel: true
+	    argument: 'modules.stx'
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleProjectOrProjectDefinitionSelected
+	    label: 'lib.rc / app.rc'
+	    itemValue: projectMenuShowGeneratedBuildFile:usingManager:
+	    translateLabel: true
+	    argument: 'lib.rc'
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleProjectOrProjectDefinitionSelected
+	    label: 'app.nsi'
+	    itemValue: projectMenuShowGeneratedBuildFile:usingManager:
+	    translateLabel: true
+	    argument: 'app.nsi'
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleProjectOrProjectDefinitionSelected
+	    label: 'abbrev.stc'
+	    itemValue: projectMenuShowGeneratedBuildFile:usingManager:
+	    translateLabel: true
+	    argument: 'abbrev.stc'
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleProjectOrProjectDefinitionSelected
+	    label: 'loadAll'
+	    itemValue: projectMenuShowGeneratedBuildFile:usingManager:
+	    translateLabel: true
+	    argument: 'loadAll'
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasSingleProjectOrProjectDefinitionSelected
+	    label: 'bmake.bat'
+	    itemValue: projectMenuShowGeneratedBuildFile:usingManager:
+	    translateLabel: true
+	    argument: 'bmake.bat'
+	    showBusyCursorWhilePerforming: true
+	  )
+	 )
+	nil
+	nil
       )
 
     "Created: / 12-10-2011 / 18:56:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -15238,27 +15513,27 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasProjectSelectedAndSourceCodeManagerHolder
-            label: 'Repository History...'
-            itemValue: projectMenuRepositoryHistory
-            translateLabel: true
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasProjectSelectedAndSourceCodeManagerHolder
-            label: 'Set Tag (Release As)...'
-            itemValue: projectMenuSetTagUsing:
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryTag 'Set Tag (Release As)...')
-            argument: SourceCodeManagerPlaceholder
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasProjectSelectedAndSourceCodeManagerHolder
+	    label: 'Repository History...'
+	    itemValue: projectMenuRepositoryHistory
+	    translateLabel: true
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedAndSourceCodeManagerHolder
+	    label: 'Set Tag (Release As)...'
+	    itemValue: projectMenuSetTagUsing:
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryTag 'Set Tag (Release As)...')
+	    argument: SourceCodeManagerPlaceholder
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -15277,78 +15552,78 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasProjectSelectedSubversionRepositoryExistsAndBranchSelectedHolder
-            label: 'Changeset'
-            translateLabel: true
-            submenuChannel: projectSubversionChangesetMenu
-          )
-         (MenuItem
-            label: 'Branch'
-            translateLabel: true
-            submenuChannel: commonSubversionBranchMenu
-          )
-         (MenuItem
-            label: 'Browse working copy'
-            itemValue: commonMenuSubversionBrowseWorkingCopy
-            translateLabel: true
-          )
-         (MenuItem
-            enabled: hasProjectSelectedAndSourceCodeManagerHolder
-            label: 'Set Tag (Release As)...'
-            itemValue: projectMenuSetTagUsing:
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryTag 'Set Tag (Release As)...')
-            argument: SourceCodeManagerPlaceholder
-          )
-         (MenuItem
-            label: 'More'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  label: 'Remove working copy'
-                  itemValue: projectMenuSubversionRemoveWorkingCopy
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedSubversionRepositoryExistsAndBranchSelectedHolder
-                  label: 'Fast commit'
-                  translateLabel: true
-                  choice: projectMenuSubversionCommitMode
-                  choiceValue: fast
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedSubversionRepositoryExistsAndBranchSelectedHolder
-                  label: 'Full commit'
-                  translateLabel: true
-                  choice: projectMenuSubversionCommitMode
-                  choiceValue: full
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'Common Slice'
-                  translateLabel: true
-                  submenuChannel: commonSubversionMenuSlice
-                  isMenuSlice: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasProjectSelectedSubversionRepositoryExistsAndBranchSelectedHolder
+	    label: 'Changeset'
+	    translateLabel: true
+	    submenuChannel: projectSubversionChangesetMenu
+	  )
+	 (MenuItem
+	    label: 'Branch'
+	    translateLabel: true
+	    submenuChannel: commonSubversionBranchMenu
+	  )
+	 (MenuItem
+	    label: 'Browse working copy'
+	    itemValue: commonMenuSubversionBrowseWorkingCopy
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedAndSourceCodeManagerHolder
+	    label: 'Set Tag (Release As)...'
+	    itemValue: projectMenuSetTagUsing:
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryTag 'Set Tag (Release As)...')
+	    argument: SourceCodeManagerPlaceholder
+	  )
+	 (MenuItem
+	    label: 'More'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  label: 'Remove working copy'
+		  itemValue: projectMenuSubversionRemoveWorkingCopy
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedSubversionRepositoryExistsAndBranchSelectedHolder
+		  label: 'Fast commit'
+		  translateLabel: true
+		  choice: projectMenuSubversionCommitMode
+		  choiceValue: fast
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedSubversionRepositoryExistsAndBranchSelectedHolder
+		  label: 'Full commit'
+		  translateLabel: true
+		  choice: projectMenuSubversionCommitMode
+		  choiceValue: full
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'Common Slice'
+		  translateLabel: true
+		  submenuChannel: commonSubversionMenuSlice
+		  isMenuSlice: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -15356,9 +15631,9 @@
 
     <resource: #menu>
 
-    ^self 
-        perform: ('projectMenuSCMSlice_' , UserPreferences current sourceCodeManagementMenuLayout) asSymbol
-        ifNotUnderstood: [self projectMenuSCMSlice_old].
+    ^self
+	perform: ('projectMenuSCMSlice_' , UserPreferences current sourceCodeManagementMenuLayout) asSymbol
+	ifNotUnderstood: [self projectMenuSCMSlice_old].
 
     "Created: / 07-10-2011 / 14:50:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -15378,48 +15653,48 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasProjectSelectedAndSourceCodeManagerHolder
-            label: 'CVS'
-            translateLabel: true
-            submenuChannel: projectMenuSCMFor:
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCVSIcon 'CVS')
-            argument: CVSSourceCodeManager
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            enabled: hasProjectSelectedAndSourceCodeManagerHolder
-            label: 'SubVersion'
-            translateLabel: true
-            isVisible: hasSubversionSupport
-            submenuChannel: projectMenuSCMFor:
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositorySVNIcon 'SubVersion')
-            argument: SVNSourceCodeManager
-          )
-         (MenuItem
-            enabled: hasProjectSelectedAndSourceCodeManagerHolder
-            label: 'Perforce'
-            translateLabel: true
-            isVisible: hasPerforceSupport
-            submenuChannel: projectMenuSCMFor:
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryP4Icon 'Perforce')
-            argument: PerforceSourceCodeManager
-          )
-         (MenuItem
-            enabled: hasProjectSelectedAndSourceCodeManagerHolder
-            label: 'Monticello'
-            translateLabel: true
-            isVisible: hasMonticelloSupport
-            submenuChannel: projectMenuSCMFor:
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryMCIcon 'Monticello')
-            argument: MCSourceCodeManager
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasProjectSelectedAndSourceCodeManagerHolder
+	    label: 'CVS'
+	    translateLabel: true
+	    submenuChannel: projectMenuSCMFor:
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCVSIcon 'CVS')
+	    argument: CVSSourceCodeManager
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedAndSourceCodeManagerHolder
+	    label: 'SubVersion'
+	    translateLabel: true
+	    isVisible: hasSubversionSupport
+	    submenuChannel: projectMenuSCMFor:
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositorySVNIcon 'SubVersion')
+	    argument: SVNSourceCodeManager
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedAndSourceCodeManagerHolder
+	    label: 'Perforce'
+	    translateLabel: true
+	    isVisible: hasPerforceSupport
+	    submenuChannel: projectMenuSCMFor:
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryP4Icon 'Perforce')
+	    argument: PerforceSourceCodeManager
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedAndSourceCodeManagerHolder
+	    label: 'Monticello'
+	    translateLabel: true
+	    isVisible: hasMonticelloSupport
+	    submenuChannel: projectMenuSCMFor:
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryMCIcon 'Monticello')
+	    argument: MCSourceCodeManager
+	  )
+	 )
+	nil
+	nil
       )
 
     "Created: / 12-10-2011 / 20:38:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -15441,49 +15716,49 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'Repository'
-            nameKey: SCM
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  label: 'Common Slice'
-                  nameKey: CommonSlice
-                  translateLabel: true
-                  submenuChannel: projectMenuSCMFor:
-                  argument: SourceCodeManagerPlaceholder
-                  isMenuSlice: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'All Slice'
-                  translateLabel: true
-                  submenuChannel: projectMenuSCMSliceAll
-                  isMenuSlice: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'Repository Settings'
-                  itemValue: openSettingsDialogAndSelectSourceCodeManagement
-                  translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'Repository'
+	    nameKey: SCM
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  label: 'Common Slice'
+		  nameKey: CommonSlice
+		  translateLabel: true
+		  submenuChannel: projectMenuSCMFor:
+		  argument: SourceCodeManagerPlaceholder
+		  isMenuSlice: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'All Slice'
+		  translateLabel: true
+		  submenuChannel: projectMenuSCMSliceAll
+		  isMenuSlice: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'Repository Settings'
+		  itemValue: openSettingsDialogAndSelectSourceCodeManagement
+		  translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 )
+	nil
+	nil
       )
 
     "Created: / 12-10-2011 / 20:36:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -15504,21 +15779,21 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'All Slice'
-            translateLabel: true
-            submenuChannel: projectMenuSCMSliceAll
-            isMenuSlice: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'All Slice'
+	    translateLabel: true
+	    submenuChannel: projectMenuSCMSliceAll
+	    isMenuSlice: true
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -15537,34 +15812,34 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'CVS'
-            translateLabel: true
-            submenuChannel: projectMenuCVS
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCVSIcon 'CVS')
-          )
-         (MenuItem
-            enabled: hasProjectSelectedSubversionRepositoryExistsHolder
-            label: 'SubVersion'
-            translateLabel: true
-            isVisible: hasSubversionSupport
-            submenuChannel: projectSubversionMenu
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositorySVNIcon 'SubVersion')
-          )
-         (MenuItem
-            enabled: hasProjectSelectedMonticelloRepositoryExistsHolder
-            label: 'Monticello'
-            translateLabel: true
-            isVisible: hasMonticelloSupport
-            submenuChannel: projectMonticelloMenu
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryMCIcon 'Monticello')
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'CVS'
+	    translateLabel: true
+	    submenuChannel: projectMenuCVS
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCVSIcon 'CVS')
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedSubversionRepositoryExistsHolder
+	    label: 'SubVersion'
+	    translateLabel: true
+	    isVisible: hasSubversionSupport
+	    submenuChannel: projectSubversionMenu
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositorySVNIcon 'SubVersion')
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedMonticelloRepositoryExistsHolder
+	    label: 'Monticello'
+	    translateLabel: true
+	    isVisible: hasMonticelloSupport
+	    submenuChannel: projectMonticelloMenu
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryMCIcon 'Monticello')
+	  )
+	 )
+	nil
+	nil
       )
 ! !
 
@@ -15584,53 +15859,53 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-              (
-               (MenuItem
-                  enabled: hasMethodSelected
-                  label: 'CheckIn Class(es)...'
-                  itemValue: methodListMenuCheckInClass
-                  translateLabel: true
-                  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn Class(es)...')
-                  showBusyCursorWhilePerforming: true
-                )
-               (MenuItem
-                  enabled: hasRealExtensionMethodSelectedHolder
-                  label: 'CheckIn Extensions for Project...'
-                  itemValue: selectorMenuCheckInProjectExtensions
-                  translateLabel: true
-                  isVisible: hasExtensionMethodSelectedHolder
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasMethodSelectedAndSourceCodeManagerHolder
-                  label: 'Compare with Newest in Repository...'
-                  itemValue: selectorMenuCompareAgainstNewestInRepository
-                  translateLabel: true
-                  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryVersions 'Compare with Newest in Repository...')
-                )
-               (MenuItem
-                  enabled: hasMethodSelectedAndSourceCodeManagerHolder
-                  label: 'Compare Class with Newest in Repository...'
-                  itemValue: selectorMenuCompareClassAgainstNewestInRepository
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasSingleMethodSelected
-                  label: 'Browse Repository Versions...'
-                  itemValue: selectorMenuBrowseRepositoryVersions
-                  translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
+    ^
+     #(Menu
+	      (
+	       (MenuItem
+		  enabled: hasMethodSelected
+		  label: 'CheckIn Class(es)...'
+		  itemValue: methodListMenuCheckInClass
+		  translateLabel: true
+		  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn Class(es)...')
+		  showBusyCursorWhilePerforming: true
+		)
+	       (MenuItem
+		  enabled: hasRealExtensionMethodSelectedHolder
+		  label: 'CheckIn Extensions for Project...'
+		  itemValue: selectorMenuCheckInProjectExtensions
+		  translateLabel: true
+		  isVisible: hasExtensionMethodSelectedHolder
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasMethodSelectedAndSourceCodeManagerHolder
+		  label: 'Compare with Newest in Repository...'
+		  itemValue: selectorMenuCompareAgainstNewestInRepository
+		  translateLabel: true
+		  labelImage: (ResourceRetriever ToolbarIconLibrary repositoryVersions 'Compare with Newest in Repository...')
+		)
+	       (MenuItem
+		  enabled: hasMethodSelectedAndSourceCodeManagerHolder
+		  label: 'Compare Class with Newest in Repository...'
+		  itemValue: selectorMenuCompareClassAgainstNewestInRepository
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasSingleMethodSelected
+		  label: 'Browse Repository Versions...'
+		  itemValue: selectorMenuBrowseRepositoryVersions
+		  translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
 !
 
 selectorMenuSCMCommon
@@ -15648,57 +15923,57 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasMethodSelected
-            label: 'CheckIn Class(es)...'
-            itemValue: methodListMenuCheckInClassUsingManagerNamed:
-            argument: SourceCodeManagerPlaceholder
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn Class(es)...')
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            enabled: hasRealExtensionMethodSelectedHolder
-            label: 'CheckIn Extensions for Project...'
-            itemValue: selectorMenuCheckInProjectExtensionsUsingManagerNamed:
-            argument: SourceCodeManagerPlaceholder
-            translateLabel: true
-            isVisible: hasExtensionMethodSelectedHolder
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasMethodSelectedAndSourceCodeManagerHolder
-            label: 'Compare with Newest in Repository...'
-            itemValue: selectorMenuCompareAgainstNewestInRepositoryUsingManagerNamed:
-            argument: SourceCodeManagerPlaceholder
-            translateLabel: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryVersions 'Compare with Newest in Repository...')
-          )
-         (MenuItem
-            enabled: hasMethodSelectedAndSourceCodeManagerHolder
-            label: 'Compare Class with Newest in Repository...'
-            itemValue: selectorMenuCompareClassAgainstNewestInRepositoryUsingManagerNamed:
-            argument: SourceCodeManagerPlaceholder
-            translateLabel: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasSingleMethodSelected
-            label: 'Browse Repository Versions...'
-            itemValue: selectorMenuBrowseRepositoryVersionsUsingManagerNamed:
-            argument: SourceCodeManagerPlaceholder
-            translateLabel: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasMethodSelected
+	    label: 'CheckIn Class(es)...'
+	    itemValue: methodListMenuCheckInClassUsingManagerNamed:
+	    argument: SourceCodeManagerPlaceholder
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCheckIn 'CheckIn Class(es)...')
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    enabled: hasRealExtensionMethodSelectedHolder
+	    label: 'CheckIn Extensions for Project...'
+	    itemValue: selectorMenuCheckInProjectExtensionsUsingManagerNamed:
+	    argument: SourceCodeManagerPlaceholder
+	    translateLabel: true
+	    isVisible: hasExtensionMethodSelectedHolder
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasMethodSelectedAndSourceCodeManagerHolder
+	    label: 'Compare with Newest in Repository...'
+	    itemValue: selectorMenuCompareAgainstNewestInRepositoryUsingManagerNamed:
+	    argument: SourceCodeManagerPlaceholder
+	    translateLabel: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryVersions 'Compare with Newest in Repository...')
+	  )
+	 (MenuItem
+	    enabled: hasMethodSelectedAndSourceCodeManagerHolder
+	    label: 'Compare Class with Newest in Repository...'
+	    itemValue: selectorMenuCompareClassAgainstNewestInRepositoryUsingManagerNamed:
+	    argument: SourceCodeManagerPlaceholder
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasSingleMethodSelected
+	    label: 'Browse Repository Versions...'
+	    itemValue: selectorMenuBrowseRepositoryVersionsUsingManagerNamed:
+	    argument: SourceCodeManagerPlaceholder
+	    translateLabel: true
+	  )
+	 )
+	nil
+	nil
       )
 
     "Modified: / 11-01-2012 / 14:05:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -15719,21 +15994,21 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'All Slice'
-            translateLabel: true
-            submenuChannel: selectorMenuSCMSliceAll
-            isMenuSlice: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'All Slice'
+	    translateLabel: true
+	    submenuChannel: selectorMenuSCMSliceAll
+	    isMenuSlice: true
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -15752,39 +16027,39 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasMethodSelectedAndSourceCodeManagerHolder
-            label: 'CVS'
-            translateLabel: true
-            submenuChannel: selectorMenuSCMFor:
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCVSIcon 'CVS')
-            argument: CVSSourceCodeManager
-            keepLinkedMenu: true
-          )
-         (MenuItem
-            enabled: hasMethodSelectedAndSourceCodeManagerHolder
-            label: 'SubVersion'
-            translateLabel: true
-            isVisible: hasSubversionSupport
-            submenuChannel: selectorMenuSCMFor:
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositorySVNIcon 'SubVersion')
-            argument: SVNSourceCodeManager
-          )
-         (MenuItem
-            enabled: hasMethodSelectedAndSourceCodeManagerHolder
-            label: 'Perforce'
-            translateLabel: true
-            isVisible: hasPerforceSupport
-            submenuChannel: selectorMenuSCMFor:
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryP4Icon 'Perforce')
-            argument: PerforceSourceCodeManager
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasMethodSelectedAndSourceCodeManagerHolder
+	    label: 'CVS'
+	    translateLabel: true
+	    submenuChannel: selectorMenuSCMFor:
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCVSIcon 'CVS')
+	    argument: CVSSourceCodeManager
+	    keepLinkedMenu: true
+	  )
+	 (MenuItem
+	    enabled: hasMethodSelectedAndSourceCodeManagerHolder
+	    label: 'SubVersion'
+	    translateLabel: true
+	    isVisible: hasSubversionSupport
+	    submenuChannel: selectorMenuSCMFor:
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositorySVNIcon 'SubVersion')
+	    argument: SVNSourceCodeManager
+	  )
+	 (MenuItem
+	    enabled: hasMethodSelectedAndSourceCodeManagerHolder
+	    label: 'Perforce'
+	    translateLabel: true
+	    isVisible: hasPerforceSupport
+	    submenuChannel: selectorMenuSCMFor:
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryP4Icon 'Perforce')
+	    argument: PerforceSourceCodeManager
+	  )
+	 )
+	nil
+	nil
       )
 
     "Created: / 12-10-2011 / 20:47:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -15806,49 +16081,49 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'Repository'
-            nameKey: SCM
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  label: 'Common Slice'
-                  nameKey: CommonSlice
-                  translateLabel: true
-                  submenuChannel: selectorMenuSCMFor:
-                  argument: SourceCodeManagerPlaceholder
-                  isMenuSlice: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'All Slice'
-                  translateLabel: true
-                  submenuChannel: selectorMenuSCMSliceAll
-                  isMenuSlice: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'Repository Settings'
-                  itemValue: openSettingsDialogAndSelectSourceCodeManagement
-                  translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'Repository'
+	    nameKey: SCM
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  label: 'Common Slice'
+		  nameKey: CommonSlice
+		  translateLabel: true
+		  submenuChannel: selectorMenuSCMFor:
+		  argument: SourceCodeManagerPlaceholder
+		  isMenuSlice: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'All Slice'
+		  translateLabel: true
+		  submenuChannel: selectorMenuSCMSliceAll
+		  isMenuSlice: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'Repository Settings'
+		  itemValue: openSettingsDialogAndSelectSourceCodeManagement
+		  translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 )
+	nil
+	nil
       )
 
     "Created: / 12-10-2011 / 20:45:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -15869,21 +16144,21 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'All Slice'
-            translateLabel: true
-            submenuChannel: selectorMenuSCMSliceAll
-            isMenuSlice: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'All Slice'
+	    translateLabel: true
+	    submenuChannel: selectorMenuSCMSliceAll
+	    isMenuSlice: true
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -15902,19 +16177,19 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasMethodSelected
-            label: 'CVS'
-            translateLabel: true
-            submenuChannel: selectorMenuCVS
-            labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCVSIcon 'CVS')
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasMethodSelected
+	    label: 'CVS'
+	    translateLabel: true
+	    submenuChannel: selectorMenuCVS
+	    labelImage: (ResourceRetriever ToolbarIconLibrary repositoryCVSIcon 'CVS')
+	  )
+	 )
+	nil
+	nil
       )
 ! !
 
@@ -15936,39 +16211,39 @@
 
     ^
      #(#Menu
-        #(
-         #(#MenuItem
-            #label: 'File out as...'
-            #translateLabel: true
-            #value: #classMenu3FileOutAs
-            #showBusyCursorWhilePerforming: true
-          )
-         #(#MenuItem
-            #label: 'Check Into Repository...'
-            #translateLabel: true
-            #value: #classMenu3CheckIn
-            #showBusyCursorWhilePerforming: true
-          )
-         #(#MenuItem
-            #label: '-'
-          )
-         #(#MenuItem
-            #label: 'Spawn'
-            #translateLabel: true
-            #value: #classMenu3SpawnClass
-          )
-         #(#MenuItem
-            #label: '-'
-          )
-         #(#MenuItem
-            #label: 'Compare With Newest in Repository...'
-            #translateLabel: true
-            #value: #classMenu3CompareAgainstNewestInRepository
-            #showBusyCursorWhilePerforming: true
-          )
-         )
-        nil
-        nil
+	#(
+	 #(#MenuItem
+	    #label: 'File out as...'
+	    #translateLabel: true
+	    #value: #classMenu3FileOutAs
+	    #showBusyCursorWhilePerforming: true
+	  )
+	 #(#MenuItem
+	    #label: 'Check Into Repository...'
+	    #translateLabel: true
+	    #value: #classMenu3CheckIn
+	    #showBusyCursorWhilePerforming: true
+	  )
+	 #(#MenuItem
+	    #label: '-'
+	  )
+	 #(#MenuItem
+	    #label: 'Spawn'
+	    #translateLabel: true
+	    #value: #classMenu3SpawnClass
+	  )
+	 #(#MenuItem
+	    #label: '-'
+	  )
+	 #(#MenuItem
+	    #label: 'Compare With Newest in Repository...'
+	    #translateLabel: true
+	    #value: #classMenu3CompareAgainstNewestInRepository
+	    #showBusyCursorWhilePerforming: true
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -15988,38 +16263,38 @@
 
     ^
      #(#Menu
-        #(
-         #(#MenuItem
-            #label: 'File out as...'
-            #translateLabel: true
-            #value: #classMenuFileOutAs
-            #showBusyCursorWhilePerforming: true
-          )
-         #(#MenuItem
-            #label: 'Check Into Repository...'
-            #translateLabel: true
-            #value: #classMenuCheckIn
-            #showBusyCursorWhilePerforming: true
-          )
-         #(#MenuItem
-            #label: '-'
-          )
-         #(#MenuItem
-            #label: 'Spawn'
-            #translateLabel: true
-            #value: #classMenuSpawnClass
-          )
-         #(#MenuItem
-            #label: '-'
-          )
-         #(#MenuItem
-            #label: 'Remove...'
-            #translateLabel: true
-            #value: #classMenuRemove
-          )
-         )
-        nil
-        nil
+	#(
+	 #(#MenuItem
+	    #label: 'File out as...'
+	    #translateLabel: true
+	    #value: #classMenuFileOutAs
+	    #showBusyCursorWhilePerforming: true
+	  )
+	 #(#MenuItem
+	    #label: 'Check Into Repository...'
+	    #translateLabel: true
+	    #value: #classMenuCheckIn
+	    #showBusyCursorWhilePerforming: true
+	  )
+	 #(#MenuItem
+	    #label: '-'
+	  )
+	 #(#MenuItem
+	    #label: 'Spawn'
+	    #translateLabel: true
+	    #value: #classMenuSpawnClass
+	  )
+	 #(#MenuItem
+	    #label: '-'
+	  )
+	 #(#MenuItem
+	    #label: 'Remove...'
+	    #translateLabel: true
+	    #value: #classMenuRemove
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -16039,33 +16314,33 @@
 
     ^
      #(#Menu
-        #(
-         #(#MenuItem
-            #label: 'CheckOut Newest...'
-            #translateLabel: true
-            #value: #classMenu2CheckOutNewest
-            #showBusyCursorWhilePerforming: true
-          )
-         #(#MenuItem
-            #label: '-'
-          )
-         #(#MenuItem
-            #label: 'Spawn'
-            #translateLabel: true
-            #value: #classMenu2SpawnClass
-          )
-         #(#MenuItem
-            #label: '-'
-          )
-         #(#MenuItem
-            #label: 'Compare With Newest in Repository...'
-            #translateLabel: true
-            #value: #classMenu2CompareAgainstNewestInRepository
-            #showBusyCursorWhilePerforming: true
-          )
-         )
-        nil
-        nil
+	#(
+	 #(#MenuItem
+	    #label: 'CheckOut Newest...'
+	    #translateLabel: true
+	    #value: #classMenu2CheckOutNewest
+	    #showBusyCursorWhilePerforming: true
+	  )
+	 #(#MenuItem
+	    #label: '-'
+	  )
+	 #(#MenuItem
+	    #label: 'Spawn'
+	    #translateLabel: true
+	    #value: #classMenu2SpawnClass
+	  )
+	 #(#MenuItem
+	    #label: '-'
+	  )
+	 #(#MenuItem
+	    #label: 'Compare With Newest in Repository...'
+	    #translateLabel: true
+	    #value: #classMenu2CompareAgainstNewestInRepository
+	    #showBusyCursorWhilePerforming: true
+	  )
+	 )
+	nil
+	nil
       )
 
     "Modified: / 29-09-2006 / 16:10:31 / cg"
@@ -16087,30 +16362,29 @@
 
     ^
      #(#Menu
-        #(
-         #(#MenuItem
-            #label: 'CheckOut...'
-            #translateLabel: true
-            #value: #classMenu4CheckOut
-            #showBusyCursorWhilePerforming: true
-          )
-         #(#MenuItem
-            #label: '-'
-          )
-         #(#MenuItem
-            #label: 'Remove Container'
-            #translateLabel: true
-            #value: #classMenu4RemoveContainer
-          )
-         )
-        nil
-        nil
+	#(
+	 #(#MenuItem
+	    #label: 'CheckOut...'
+	    #translateLabel: true
+	    #value: #classMenu4CheckOut
+	    #showBusyCursorWhilePerforming: true
+	  )
+	 #(#MenuItem
+	    #label: '-'
+	  )
+	 #(#MenuItem
+	    #label: 'Remove Container'
+	    #translateLabel: true
+	    #value: #classMenu4RemoveContainer
+	  )
+	 )
+	nil
+	nil
       )
 
     "Modified: / 29-09-2006 / 16:11:08 / cg"
 ! !
 
-
 !NewSystemBrowser class methodsFor:'menu specs-popup'!
 
 categoryPopUpMenu
@@ -16187,33 +16461,33 @@
 
     ^
      #(Menu
-        (
-         (MenuItem
-            label: 'Add Page'
-            itemValue: bufferMenuCreateBuffer
-            nameKey: CreateBuffer
-            translateLabel: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Remove Page'
-            itemValue: bufferMenuRemoveBuffer:
-            nameKey: RemoveBuffer
-            translateLabel: true
-            argument: 0
-          )
-         (MenuItem
-            label: 'Remove all other Pages'
-            itemValue: bufferMenuRemoveAllButBuffer:
-            nameKey: RemoveAllButBuffer
-            translateLabel: true
-            argument: 0
-          )
-         )
-        nil
-        nil
+	(
+	 (MenuItem
+	    label: 'Add Page'
+	    itemValue: bufferMenuCreateBuffer
+	    nameKey: CreateBuffer
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Remove Page'
+	    itemValue: bufferMenuRemoveBuffer:
+	    nameKey: RemoveBuffer
+	    translateLabel: true
+	    argument: 0
+	  )
+	 (MenuItem
+	    label: 'Remove all other Pages'
+	    itemValue: bufferMenuRemoveAllButBuffer:
+	    nameKey: RemoveAllButBuffer
+	    translateLabel: true
+	    argument: 0
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -16233,16 +16507,16 @@
 
     ^
      #(#Menu
-        #(
-         #(#MenuItem
-            #label: 'Add Tab'
-            #translateLabel: true
-            #nameKey: #CreateBuffer
-            #value: #bufferMenuCreateBuffer
-          )
-         )
-        nil
-        nil
+	#(
+	 #(#MenuItem
+	    #label: 'Add Tab'
+	    #translateLabel: true
+	    #nameKey: #CreateBuffer
+	    #value: #bufferMenuCreateBuffer
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -16272,86 +16546,86 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasClassesSelectedAndSubversionRepositoryExistsAndBranchSelectedHolder
-            label: 'Commit'
-            itemValue: classMenuSubversionCommit
-            translateLabel: true
-            labelImage: (ResourceRetriever #'SVN::IconLibrary' commit 'Commit')
-          )
-         (MenuItem
-            enabled: hasClassesSelectedAndSubversionRepositoryExistsAndBranchSelectedHolder
-            label: 'Update'
-            itemValue: classMenuSubversionUpdate
-            translateLabel: true
-            labelImage: (ResourceRetriever #'SVN::IconLibrary' update 'Update')
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasClassesSelectedAndSubversionRepositoryExistsAndBranchSelectedHolder
-            label: 'Compare'
-            translateLabel: true
-            submenuChannel: classSubversionCompareMenu
-            labelImage: (ResourceRetriever #'SVN::IconLibrary' compare 'Compare')
-          )
-         (MenuItem
-            enabled: false
-            label: 'Merge'
-            translateLabel: true
-            submenuChannel: classSubversionMergeMenu
-            labelImage: (ResourceRetriever #'SVN::IconLibrary' merge 'Merge')
-          )
-         (MenuItem
-            enabled: hasClassesSelectedAndSubversionRepositoryExistsAndBranchSelectedHolder
-            label: 'Changeset'
-            translateLabel: true
-            submenuChannel: classSubversionChangesetMenu
-          )
-         (MenuItem
-            enabled: hasClassesSelectedAndSubversionRepositoryExistsAndBranchSelectedHolder
-            label: 'Revision log'
-            itemValue: classMenuSubversionShowRevisionLog
-            translateLabel: true
-            labelImage: (ResourceRetriever #'SVN::IconLibrary' log 'Revision log')
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Branch'
-            translateLabel: true
-            submenuChannel: commonSubversionBranchMenu
-          )
-         (MenuItem
-            label: 'Browse working copy'
-            itemValue: commonMenuSubversionBrowseWorkingCopy
-            translateLabel: true
-          )
-         (MenuItem
-            label: 'More'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  label: 'Common Slice'
-                  translateLabel: true
-                  submenuChannel: commonSubversionMenuSlice
-                  isMenuSlice: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasClassesSelectedAndSubversionRepositoryExistsAndBranchSelectedHolder
+	    label: 'Commit'
+	    itemValue: classMenuSubversionCommit
+	    translateLabel: true
+	    labelImage: (ResourceRetriever #'SVN::IconLibrary' commit 'Commit')
+	  )
+	 (MenuItem
+	    enabled: hasClassesSelectedAndSubversionRepositoryExistsAndBranchSelectedHolder
+	    label: 'Update'
+	    itemValue: classMenuSubversionUpdate
+	    translateLabel: true
+	    labelImage: (ResourceRetriever #'SVN::IconLibrary' update 'Update')
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasClassesSelectedAndSubversionRepositoryExistsAndBranchSelectedHolder
+	    label: 'Compare'
+	    translateLabel: true
+	    submenuChannel: classSubversionCompareMenu
+	    labelImage: (ResourceRetriever #'SVN::IconLibrary' compare 'Compare')
+	  )
+	 (MenuItem
+	    enabled: false
+	    label: 'Merge'
+	    translateLabel: true
+	    submenuChannel: classSubversionMergeMenu
+	    labelImage: (ResourceRetriever #'SVN::IconLibrary' merge 'Merge')
+	  )
+	 (MenuItem
+	    enabled: hasClassesSelectedAndSubversionRepositoryExistsAndBranchSelectedHolder
+	    label: 'Changeset'
+	    translateLabel: true
+	    submenuChannel: classSubversionChangesetMenu
+	  )
+	 (MenuItem
+	    enabled: hasClassesSelectedAndSubversionRepositoryExistsAndBranchSelectedHolder
+	    label: 'Revision log'
+	    itemValue: classMenuSubversionShowRevisionLog
+	    translateLabel: true
+	    labelImage: (ResourceRetriever #'SVN::IconLibrary' log 'Revision log')
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Branch'
+	    translateLabel: true
+	    submenuChannel: commonSubversionBranchMenu
+	  )
+	 (MenuItem
+	    label: 'Browse working copy'
+	    itemValue: commonMenuSubversionBrowseWorkingCopy
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: 'More'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  label: 'Common Slice'
+		  translateLabel: true
+		  submenuChannel: commonSubversionMenuSlice
+		  isMenuSlice: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -16369,22 +16643,22 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            label: 'Settings'
-            itemValue: commonMenuSubversionOpenSettings
-            translateLabel: true
-          )
-         (MenuItem
-            label: 'Flush caches'
-            itemValue: commonMenuSubversionFlushCaches
-            translateLabel: true
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    label: 'Settings'
+	    itemValue: commonMenuSubversionOpenSettings
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: 'Flush caches'
+	    itemValue: commonMenuSubversionFlushCaches
+	    translateLabel: true
+	  )
+	 )
+	nil
+	nil
       )
 !
 
@@ -16402,120 +16676,120 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            enabled: hasProjectSelectedSubversionRepositoryExistsAndBranchSelectedHolder
-            label: 'Commit'
-            itemValue: projectMenuSubversionCommit
-            translateLabel: true
-            labelImage: (ResourceRetriever #'SVN::IconLibrary' commit 'Commit')
-          )
-         (MenuItem
-            enabled: hasProjectSelectedSubversionRepositoryExistsAndBranchSelectedHolder
-            label: 'Update'
-            itemValue: projectMenuSubversionUpdate
-            translateLabel: true
-            labelImage: (ResourceRetriever #'SVN::IconLibrary' update 'Update')
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasProjectSelectedSubversionRepositoryExistsAndBranchSelectedHolder
-            label: 'Compare'
-            translateLabel: true
-            submenuChannel: projectSubversionCompareMenu
-            labelImage: (ResourceRetriever #'SVN::IconLibrary' compare 'Compare')
-          )
-         (MenuItem
-            enabled: hasProjectSelectedSubversionRepositoryExistsAndBranchSelectedHolder
-            label: 'Merge'
-            translateLabel: true
-            submenuChannel: projectSubversionMergeMenu
-            labelImage: (ResourceRetriever #'SVN::IconLibrary' merge 'Merge')
-          )
-         (MenuItem
-            enabled: hasProjectSelectedSubversionRepositoryExistsAndBranchSelectedHolder
-            label: 'Changeset'
-            translateLabel: true
-            submenuChannel: projectSubversionChangesetMenu
-          )
-         (MenuItem
-            enabled: hasProjectSelectedSubversionRepositoryExistsAndBranchSelectedHolder
-            label: 'Revision log'
-            itemValue: projectMenuSubversionShowRevisionLog
-            translateLabel: true
-            labelImage: (ResourceRetriever #'SVN::IconLibrary' log 'Revision log')
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            label: 'Branch'
-            translateLabel: true
-            submenuChannel: commonSubversionBranchMenu
-          )
-         (MenuItem
-            label: 'Browse working copy'
-            itemValue: commonMenuSubversionBrowseWorkingCopy
-            translateLabel: true
-          )
-         (MenuItem
-            label: 'More'
-            translateLabel: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  enabled: hasProjectSelectedSubversionRepositoryExistsAndBranchSelectedHolder
-                  label: 'Load revision...'
-                  itemValue: projectMenuSubversionLoadRevision
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'Remove working copy'
-                  itemValue: projectMenuSubversionRemoveWorkingCopy
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedSubversionRepositoryExistsAndBranchSelectedHolder
-                  label: 'Fast commit'
-                  translateLabel: true
-                  choice: projectMenuSubversionCommitMode
-                  choiceValue: fast
-                )
-               (MenuItem
-                  enabled: hasProjectSelectedSubversionRepositoryExistsAndBranchSelectedHolder
-                  label: 'Full commit'
-                  translateLabel: true
-                  choice: projectMenuSubversionCommitMode
-                  choiceValue: full
-                )
-               (MenuItem
-                  label: '-'
-                )
-               (MenuItem
-                  label: 'Common Slice'
-                  translateLabel: true
-                  submenuChannel: commonSubversionMenuSlice
-                  isMenuSlice: true
-                )
-               )
-              nil
-              nil
-            )
-          )
-         )
-        nil
-        nil
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    enabled: hasProjectSelectedSubversionRepositoryExistsAndBranchSelectedHolder
+	    label: 'Commit'
+	    itemValue: projectMenuSubversionCommit
+	    translateLabel: true
+	    labelImage: (ResourceRetriever #'SVN::IconLibrary' commit 'Commit')
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedSubversionRepositoryExistsAndBranchSelectedHolder
+	    label: 'Update'
+	    itemValue: projectMenuSubversionUpdate
+	    translateLabel: true
+	    labelImage: (ResourceRetriever #'SVN::IconLibrary' update 'Update')
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedSubversionRepositoryExistsAndBranchSelectedHolder
+	    label: 'Compare'
+	    translateLabel: true
+	    submenuChannel: projectSubversionCompareMenu
+	    labelImage: (ResourceRetriever #'SVN::IconLibrary' compare 'Compare')
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedSubversionRepositoryExistsAndBranchSelectedHolder
+	    label: 'Merge'
+	    translateLabel: true
+	    submenuChannel: projectSubversionMergeMenu
+	    labelImage: (ResourceRetriever #'SVN::IconLibrary' merge 'Merge')
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedSubversionRepositoryExistsAndBranchSelectedHolder
+	    label: 'Changeset'
+	    translateLabel: true
+	    submenuChannel: projectSubversionChangesetMenu
+	  )
+	 (MenuItem
+	    enabled: hasProjectSelectedSubversionRepositoryExistsAndBranchSelectedHolder
+	    label: 'Revision log'
+	    itemValue: projectMenuSubversionShowRevisionLog
+	    translateLabel: true
+	    labelImage: (ResourceRetriever #'SVN::IconLibrary' log 'Revision log')
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    label: 'Branch'
+	    translateLabel: true
+	    submenuChannel: commonSubversionBranchMenu
+	  )
+	 (MenuItem
+	    label: 'Browse working copy'
+	    itemValue: commonMenuSubversionBrowseWorkingCopy
+	    translateLabel: true
+	  )
+	 (MenuItem
+	    label: 'More'
+	    translateLabel: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  enabled: hasProjectSelectedSubversionRepositoryExistsAndBranchSelectedHolder
+		  label: 'Load revision...'
+		  itemValue: projectMenuSubversionLoadRevision
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'Remove working copy'
+		  itemValue: projectMenuSubversionRemoveWorkingCopy
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedSubversionRepositoryExistsAndBranchSelectedHolder
+		  label: 'Fast commit'
+		  translateLabel: true
+		  choice: projectMenuSubversionCommitMode
+		  choiceValue: fast
+		)
+	       (MenuItem
+		  enabled: hasProjectSelectedSubversionRepositoryExistsAndBranchSelectedHolder
+		  label: 'Full commit'
+		  translateLabel: true
+		  choice: projectMenuSubversionCommitMode
+		  choiceValue: full
+		)
+	       (MenuItem
+		  label: '-'
+		)
+	       (MenuItem
+		  label: 'Common Slice'
+		  translateLabel: true
+		  submenuChannel: commonSubversionMenuSlice
+		  isMenuSlice: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	  )
+	 )
+	nil
+	nil
       )
 ! !
 
@@ -16536,292 +16810,317 @@
 
     <resource: #menu>
 
-    ^ 
-     #(Menu
-        (
-         (MenuItem
-            activeHelpKey: goBackInGlobalHistory
-            enabled: canGoBackInGlobalHistoryAspect
-            label: 'Back (Global History)'
-            itemValue: goBackInGlobalHistory
-            translateLabel: true
-            isButton: true
-            isVisible: showGlobalHistory
-            labelImage: (ResourceRetriever ToolbarIconLibrary historyBackInGlobalListIcon)
-          )
-         (MenuItem
-            activeHelpKey: goBack
-            enabled: canGoBackAspect
-            label: 'Back'
-            itemValue: goBack
-            translateLabel: true
-            isButton: true
-            isVisible: showLocalHistory
-            labelImage: (ResourceRetriever ToolbarIconLibrary historyBackIcon)
-          )
-         (MenuItem
-            activeHelpKey: goForward
-            enabled: canGoForwardAspect
-            label: 'Forward'
-            itemValue: goForward
-            translateLabel: true
-            isButton: true
-            isVisible: showLocalHistory
-            labelImage: (ResourceRetriever ToolbarIconLibrary historyForwardIcon)
-          )
-         (MenuItem
-            label: ''
-          )
-         (MenuItem
-            activeHelpKey: createBuffer
-            label: 'CreateBuffer'
-            itemValue: createBufferForCurrentClassOrSelectionInCodeView
-            translateLabel: true
-            isButton: true
-            labelImage: (ResourceRetriever ToolbarIconLibrary addBufferIcon)
-          )
-         (MenuItem
-            label: '-'
-            isVisible: organizerIsShowingClasses
-          )
-         (MenuItem
-            activeHelpKey: showCategories
-            label: 'ShowCategory'
-            itemValue: switchToCategoryView
-            translateLabel: true
-            isButton: true
-            isVisible: organizerIsShowingClassesAndIsNotShowingCategories
-            labelImage: (ResourceRetriever NewSystemBrowser showCategoriesIcon)
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            activeHelpKey: showClassHierarchy
-            label: 'ShowClassHierarchy'
-            itemValue: switchToClassHierarchyView
-            translateLabel: true
-            isButton: true
-            isVisible: organizerIsShowingClassesAndIsShowingCategories
-            labelImage: (ResourceRetriever NewSystemBrowser showClassHierarchyIcon)
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            activeHelpKey: recentChanges
-            label: 'Recently Changed'
-            translateLabel: true
-            isButton: true
-            submenuChannel: changedMenu
-            labelImage: (ResourceRetriever ToolbarIconLibrary changesBrowserIcon)
-            showBusyCursorWhilePerforming: true
-            ignoreMnemonicKeys: true
-            ignoreShortcutKeys: true
-          )
-         (MenuItem
-            activeHelpKey: recentClassChanges
-            label: 'Recently Changed Classes'
-            translateLabel: true
-            isButton: true
-            isVisible: false
-            submenuChannel: changedClassesMenu
-            labelImage: (ResourceRetriever ToolbarIconLibrary empty1x20Icon)
-            showBusyCursorWhilePerforming: true
-            ignoreMnemonicKeys: true
-            ignoreShortcutKeys: true
-          )
-         (MenuItem
-            activeHelpKey: bookmarks
-            label: 'Bookmarks'
-            translateLabel: true
-            isVisible: false
-            submenuChannel: boockmarksMenu
-            labelImage: (ResourceRetriever ToolbarIconLibrary bookmarks14x14)
-            ignoreMnemonicKeys: true
-            ignoreShortcutKeys: true
-          )
-         (MenuItem
-            label: ''
-            isVisible: false
-          )
-         (MenuItem
-            activeHelpKey: undoOperation
-            enabled: hasUndoableOperations
-            label: 'Undo'
-            itemValue: operationsMenuUndo
-            translateLabel: true
-            isButton: true
-            isVisible: false
-            labelImage: (ResourceRetriever ToolbarIconLibrary undoIcon)
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            activeHelpKey: redoOperation
-            enabled: hasUndoableOperations
-            label: 'Redo'
-            itemValue: operationsMenuRedo
-            translateLabel: true
-            isButton: true
-            isVisible: false
-            labelImage: (ResourceRetriever ToolbarIconLibrary redoIcon)
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: '-'
-            isVisible: classWizardVisibleHolder
-          )
-         (MenuItem
-            label: 'Class Wizard'
-            itemValue: classMenuOpenClassCreationWizard
-            translateLabel: true
-            isButton: true
-            isVisible: classWizardVisibleHolder
-            labelImage: (ResourceRetriever ToolbarIconLibrary newClassWizardIcon)
-          )
-         (MenuItem
-            label: '-'
-          )
-         (MenuItem
-            enabled: hasClassSelectedHolder
-            label: 'Run Static Analysis (Lint)'
-            itemValue: runLint
-            nameKey: RunLint
-            translateLabel: true
-            isButton: true
-            submenu: 
-           (Menu
-              (
-               (MenuItem
-                  label: 'Repeat Previously Selected Checks'
-                  itemValue: runLintOnPreviousRules
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: 'Run all Checks'
-                  itemValue: runLintOnAllRules
-                  translateLabel: true
-                )
-               (MenuItem
-                  label: 'Select Checks...'
-                  itemValue: runLintOnSelectedRules
-                  translateLabel: true
-                )
-               )
-              nil
-              nil
-            )
-            labelImage: (ResourceRetriever ToolbarIconLibrary lint24x24Icon)
-          )
-         (MenuItem
-            label: '-'
-            isVisible: hasAnyTestCaseOrExecutableClassMethodOrStartableApplicationSelectedHolder
-          )
-         (MenuItem
-            activeHelpKey: launchSelectedApplication
-            label: 'Launch Selected Application'
-            itemValue: launchSelectedApplication
-            translateLabel: true
-            isButton: true
-            isVisible: hasStartableApplicationSelectedHolder
-            labelImage: (ResourceRetriever ToolbarIconLibrary start22x22Icon)
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            activeHelpKey: executeSelectedClassMethod
-            label: 'Execute Selected Class Method'
-            itemValue: executeSelectedClassMethod
-            translateLabel: true
-            isButton: true
-            isVisible: hasAnyExecutableClassMethodSelectedHolder
-            labelImage: (ResourceRetriever ToolbarIconLibrary executeMethod20x20Icon)
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            activeHelpKey: runTestCases
-            label: 'Run Tests'
-            itemValue: runTestCases
-            translateLabel: true
-            isButton: true
-            isVisible: hasAnyTestCaseSelectedHolder
-            labelImage: (ResourceRetriever ToolbarIconLibrary sUnit24x24Icon)
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            activeHelpKey: runTestCasesWithDebug
-            label: 'Debug Tests'
-            itemValue: runTestCasesWithDebug
-            translateLabel: true
-            isButton: true
-            isVisible: hasAnyTestCaseSelectedHolder
-            labelImage: (ResourceRetriever ToolbarIconLibrary sUnit24x24DebugIcon)
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            label: ''
-          )
-         (MenuItem
-            label: '-'
-            startGroup: right
-          )
-         (MenuItem
-            activeHelpKey: showInheritedMethods
-            label: 'ShowInheritedMethods'
-            itemValue: showInheritedMethods
-            translateLabel: true
-            isButton: true
-            startGroup: right
-            isVisible: notShowingInheritedMethods
-            labelImage: (ResourceRetriever NewSystemBrowser showInheritedMethodsIcon)
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            activeHelpKey: doNotShowInheritedMethods
-            label: 'DoNotShowInheritedMethods'
-            itemValue: doNotShowInheritedMethods
-            translateLabel: true
-            isButton: true
-            startGroup: right
-            isVisible: showingInheritedMethods
-            labelImage: (ResourceRetriever NewSystemBrowser doNotShowInheritedMethodsIcon)
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            activeHelpKey: formatCode
-            enabled: hasMethodSelectedHolder
-            label: 'Format'
-            itemValue: codeMenuFormat
-            translateLabel: true
-            isButton: true
-            startGroup: right
-            labelImage: (ResourceRetriever ToolbarIconLibrary formatCode16x16Icon)
-            showBusyCursorWhilePerforming: true
-          )
-         (MenuItem
-            activeHelpKey: addBreakPoint
-            enabled: hasMethodWithoutBreakPointSelectedHolder
-            label: 'Add BreakPoint'
-            itemValue: debugMenuBreakPoint
-            translateLabel: true
-            isButton: true
-            startGroup: right
-            labelImage: (ResourceRetriever nil addBreakPointIcon2)
-          )
-         (MenuItem
-            label: ''
-          )
-         (MenuItem
-            activeHelpKey: removeBreakPoint
-            enabled: hasMethodWithBreakPointSelectedHolder
-            label: 'Remove BreakPoint'
-            itemValue: debugMenuRemoveBreakOrTrace
-            translateLabel: true
-            isButton: true
-            labelImage: (ResourceRetriever nil removeBreakPointIcon2)
-          )
-         )
-        nil
-        nil
-      )
+    ^
+     #(Menu
+	(
+	 (MenuItem
+	    activeHelpKey: goBackInGlobalHistory
+	    enabled: canGoBackInGlobalHistoryAspect
+	    label: 'Back (Global History)'
+	    itemValue: goBackInGlobalHistory
+	    translateLabel: true
+	    isButton: true
+	    isVisible: showGlobalHistory
+	    labelImage: (ResourceRetriever ToolbarIconLibrary historyBackInGlobalListIcon)
+	  )
+	 (MenuItem
+	    activeHelpKey: goBack
+	    enabled: canGoBackAspect
+	    label: 'Back'
+	    itemValue: goBack
+	    translateLabel: true
+	    isButton: true
+	    isVisible: showLocalHistory
+	    labelImage: (ResourceRetriever ToolbarIconLibrary historyBackIcon)
+	  )
+	 (MenuItem
+	    activeHelpKey: goForward
+	    enabled: canGoForwardAspect
+	    label: 'Forward'
+	    itemValue: goForward
+	    translateLabel: true
+	    isButton: true
+	    isVisible: showLocalHistory
+	    labelImage: (ResourceRetriever ToolbarIconLibrary historyForwardIcon)
+	  )
+	 (MenuItem
+	    label: ''
+	  )
+	 (MenuItem
+	    activeHelpKey: createBuffer
+	    label: 'CreateBuffer'
+	    itemValue: createBufferForCurrentClassOrSelectionInCodeView
+	    translateLabel: true
+	    isButton: true
+	    labelImage: (ResourceRetriever ToolbarIconLibrary addBufferIcon)
+	  )
+	 (MenuItem
+	    label: '-'
+	    isVisible: organizerIsShowingClasses
+	  )
+	 (MenuItem
+	    activeHelpKey: showCategories
+	    label: 'ShowCategory'
+	    itemValue: switchToCategoryView
+	    translateLabel: true
+	    isButton: true
+	    isVisible: organizerIsShowingClassesAndIsNotShowingCategories
+	    labelImage: (ResourceRetriever NewSystemBrowser showCategoriesIcon)
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    activeHelpKey: showClassHierarchy
+	    label: 'ShowClassHierarchy'
+	    itemValue: switchToClassHierarchyView
+	    translateLabel: true
+	    isButton: true
+	    isVisible: organizerIsShowingClassesAndIsShowingCategories
+	    labelImage: (ResourceRetriever NewSystemBrowser showClassHierarchyIcon)
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    activeHelpKey: recentChanges
+	    label: 'Recently Changed'
+	    translateLabel: true
+	    isButton: true
+	    submenuChannel: changedMenu
+	    labelImage: (ResourceRetriever ToolbarIconLibrary changesBrowserIcon)
+	    showBusyCursorWhilePerforming: true
+	    ignoreMnemonicKeys: true
+	    ignoreShortcutKeys: true
+	  )
+	 (MenuItem
+	    activeHelpKey: recentClassChanges
+	    label: 'Recently Changed Classes'
+	    translateLabel: true
+	    isButton: true
+	    isVisible: false
+	    submenuChannel: changedClassesMenu
+	    labelImage: (ResourceRetriever ToolbarIconLibrary empty1x20Icon)
+	    showBusyCursorWhilePerforming: true
+	    ignoreMnemonicKeys: true
+	    ignoreShortcutKeys: true
+	  )
+	 (MenuItem
+	    activeHelpKey: bookmarks
+	    label: 'Bookmarks'
+	    translateLabel: true
+	    isVisible: false
+	    submenuChannel: boockmarksMenu
+	    labelImage: (ResourceRetriever ToolbarIconLibrary bookmarks14x14)
+	    ignoreMnemonicKeys: true
+	    ignoreShortcutKeys: true
+	  )
+	 (MenuItem
+	    label: ''
+	    isVisible: false
+	  )
+	 (MenuItem
+	    activeHelpKey: undoOperation
+	    enabled: hasUndoableOperations
+	    label: 'Undo'
+	    itemValue: operationsMenuUndo
+	    translateLabel: true
+	    isButton: true
+	    isVisible: false
+	    labelImage: (ResourceRetriever ToolbarIconLibrary undoIcon)
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    activeHelpKey: redoOperation
+	    enabled: hasUndoableOperations
+	    label: 'Redo'
+	    itemValue: operationsMenuRedo
+	    translateLabel: true
+	    isButton: true
+	    isVisible: false
+	    labelImage: (ResourceRetriever ToolbarIconLibrary redoIcon)
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	    isVisible: classWizardVisibleHolder
+	  )
+	 (MenuItem
+	    label: 'Class Wizard'
+	    itemValue: classMenuOpenClassCreationWizard
+	    translateLabel: true
+	    isButton: true
+	    isVisible: classWizardVisibleHolder
+	    labelImage: (ResourceRetriever ToolbarIconLibrary newClassWizardIcon)
+	  )
+	 (MenuItem
+	    label: '-'
+	  )
+	 (MenuItem
+	    activeHelpKey: runLintOnClasses
+	    enabled: hasClassSelectedHolder
+	    label: 'Run Static Analysis (Lint)'
+	    itemValue: runLint
+	    nameKey: RunLint
+	    translateLabel: true
+	    isButton: true
+	    submenu:
+	   (Menu
+	      (
+	       (MenuItem
+		  label: 'Repeat Previously Selected Checks'
+		  itemValue: runLintOnPreviousRules
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: 'Run all Checks'
+		  itemValue: runLintOnAllRules
+		  translateLabel: true
+		)
+	       (MenuItem
+		  label: 'Select Checks...'
+		  itemValue: runLintOnSelectedRules
+		  translateLabel: true
+		)
+	       )
+	      nil
+	      nil
+	    )
+	    labelImage: (ResourceRetriever ToolbarIconLibrary lint24x24Icon)
+	  )
+	 (MenuItem
+	    label: '-'
+	    isVisible: hasClassSelectedHolder
+	  )
+	 (MenuItem
+	    activeHelpKey: launchSelectedApplication
+	    label: 'Launch Selected Application'
+	    itemValue: launchSelectedApplication
+	    translateLabel: true
+	    isButton: true
+	    isVisible: hasStartableApplicationSelectedHolder
+	    labelImage: (ResourceRetriever ToolbarIconLibrary start22x22Icon)
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	    isVisible: hasStartableApplicationSelectedHolder
+	  )
+	 (MenuItem
+	    activeHelpKey: executeSelectedClassMethod
+	    label: 'Execute Selected Class Method'
+	    itemValue: executeSelectedClassMethod
+	    translateLabel: true
+	    isButton: true
+	    isVisible: hasAnyExecutableClassMethodSelectedHolder
+	    labelImage: (ResourceRetriever ToolbarIconLibrary executeMethod20x20Icon)
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	    isVisible: hasAnyExecutableClassMethodSelectedHolder
+	  )
+	 (MenuItem
+	    activeHelpKey: initializeSharedPool
+	    label: 'Initialize Selected Pool'
+	    itemValue: initializeSelectedPool
+	    translateLabel: true
+	    isButton: true
+	    isVisible: hasSharedPoolClassSelectedHolder
+	    labelImage: (ResourceRetriever #'Tools::NewSystemBrowser' initializeSharedPool20x20Icon)
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: '-'
+	    isVisible: hasSharedPoolClassSelectedHolder
+	  )
+	 (MenuItem
+	    activeHelpKey: runTestCases
+	    label: 'Run Tests'
+	    itemValue: runTestCases
+	    translateLabel: true
+	    isButton: true
+	    isVisible: hasAnyTestCaseSelectedHolder
+	    labelImage: (ResourceRetriever ToolbarIconLibrary sUnit24x24Icon)
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    activeHelpKey: runTestCasesWithDebug
+	    label: 'Debug Tests'
+	    itemValue: runTestCasesWithDebug
+	    translateLabel: true
+	    isButton: true
+	    isVisible: hasAnyTestCaseSelectedHolder
+	    labelImage: (ResourceRetriever ToolbarIconLibrary sUnit24x24DebugIcon)
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    label: ''
+	  )
+	 (MenuItem
+	    label: '-'
+	    startGroup: right
+	  )
+	 (MenuItem
+	    activeHelpKey: showInheritedMethods
+	    label: 'ShowInheritedMethods'
+	    itemValue: showInheritedMethods
+	    translateLabel: true
+	    isButton: true
+	    startGroup: right
+	    isVisible: notShowingInheritedMethods
+	    labelImage: (ResourceRetriever NewSystemBrowser showInheritedMethodsIcon)
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    activeHelpKey: doNotShowInheritedMethods
+	    label: 'DoNotShowInheritedMethods'
+	    itemValue: doNotShowInheritedMethods
+	    translateLabel: true
+	    isButton: true
+	    startGroup: right
+	    isVisible: showingInheritedMethods
+	    labelImage: (ResourceRetriever NewSystemBrowser doNotShowInheritedMethodsIcon)
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    activeHelpKey: formatCode
+	    enabled: hasMethodSelectedHolder
+	    label: 'Format'
+	    itemValue: codeMenuFormat
+	    translateLabel: true
+	    isButton: true
+	    startGroup: right
+	    labelImage: (ResourceRetriever ToolbarIconLibrary formatCode16x16Icon)
+	    showBusyCursorWhilePerforming: true
+	  )
+	 (MenuItem
+	    activeHelpKey: addBreakPoint
+	    enabled: hasMethodWithoutBreakPointSelectedHolder
+	    label: 'Add BreakPoint'
+	    itemValue: debugMenuBreakPoint
+	    translateLabel: true
+	    isButton: true
+	    startGroup: right
+	    labelImage: (ResourceRetriever nil addBreakPointIcon2)
+	  )
+	 (MenuItem
+	    label: ''
+	  )
+	 (MenuItem
+	    activeHelpKey: removeBreakPoint
+	    enabled: hasMethodWithBreakPointSelectedHolder
+	    label: 'Remove BreakPoint'
+	    itemValue: debugMenuRemoveBreakOrTrace
+	    translateLabel: true
+	    isButton: true
+	    labelImage: (ResourceRetriever nil removeBreakPointIcon2)
+	  )
+	 )
+	nil
+	nil
+      )
+
+    "Modified: / 28-05-2012 / 09:50:34 / cg"
 ! !
 
 !NewSystemBrowser class methodsFor:'queries'!
@@ -16842,7 +17141,7 @@
 
     browser := self basicNew spawnClassBrowserFor:(Array with:aClass theNonMetaclass) in:#newBrowser.
     aClass isMeta ifTrue:[
-        browser switchToClass:aClass.
+	browser switchToClass:aClass.
     ].
     ^ browser.
 
@@ -16867,9 +17166,9 @@
     "launch a multi class browser."
 
     ^ self openWithSelectedClasses:aCollectionOfClasses label:titleOrNil
-"/    ^ self basicNew 
-"/        spawnClassBrowserFor:aCollectionOfClasses 
-"/        label:titleOrNil 
+"/    ^ self basicNew
+"/        spawnClassBrowserFor:aCollectionOfClasses
+"/        label:titleOrNil
 "/        in:#newBrowser.
 
     "
@@ -16883,32 +17182,32 @@
     "launch a multi-method browser."
 
     ^ self basicNew
-        spawnMethodBrowserFor:aListOfMethods
-        in:#newBrowser
-        label:title
-        perMethodInfo:nil
-        sortBy:(doSort ifTrue:[#class] ifFalse:[nil])
+	spawnMethodBrowserFor:aListOfMethods
+	in:#newBrowser
+	label:title
+	perMethodInfo:nil
+	sortBy:(doSort ifTrue:[#class] ifFalse:[nil])
 
     "
      self
-        browseMethods:(Array with:(OrderedCollection compiledMethodAt:#at:)
-                             with:(Array compiledMethodAt:#at:)
-                             )
-        title:'some methods'
-        sort:true
+	browseMethods:(Array with:(OrderedCollection compiledMethodAt:#at:)
+			     with:(Array compiledMethodAt:#at:)
+			     )
+	title:'some methods'
+	sort:true
 
      self
-        browseMethods:(Array with:(OrderedCollection compiledMethodAt:#at:)
-                             with:(Array compiledMethodAt:#at:)
-                             )
-        title:'some methods'
-        sort:false
+	browseMethods:(Array with:(OrderedCollection compiledMethodAt:#at:)
+			     with:(Array compiledMethodAt:#at:)
+			     )
+	title:'some methods'
+	sort:false
 
      self
-        browseMethods:(Array with:(Array compiledMethodAt:#at:)
-                             with:(Array compiledMethodAt:#at:put:))
-        title:'some methods'
-        sort:false
+	browseMethods:(Array with:(Array compiledMethodAt:#at:)
+			     with:(Array compiledMethodAt:#at:put:))
+	title:'some methods'
+	sort:false
     "
 !
 
@@ -16918,7 +17217,7 @@
     ^ self basicNew spawnProfilerStatistics: statistics in:#newBrowser.
 
     "
-     self browseClass:Array 
+     self browseClass:Array
     "
 
     "Created: / 09-10-2007 / 22:03:05 / janfrog"
@@ -16931,7 +17230,7 @@
 
     browser := self basicNew spawnSingleClassBrowserFor:aClass theNonMetaclass in:#newBrowser.
     aClass isMeta ifTrue:[
-        browser switchToClass:aClass.
+	browser switchToClass:aClass.
     ].
     ^ browser.
 
@@ -16948,10 +17247,10 @@
 
     classHistory := self classHistory.
     classHistory size > 0 ifTrue:[
-        lastClass := Smalltalk classNamed:(classHistory first className).
-        lastClass notNil ifTrue:[
-            ^ self openInClass:lastClass selector:nil
-        ]
+	lastClass := Smalltalk classNamed:(classHistory first className).
+	lastClass notNil ifTrue:[
+	    ^ self openInClass:lastClass selector:nil
+	]
     ].
     ^ super open
 
@@ -16999,7 +17298,7 @@
     "open a browser, showing all classes in the changeSet."
 
     ^ self basicNew
-        browseMenuClassesInCurrentChangeSetOpenAs:#newBrowser
+	browseMenuClassesInCurrentChangeSetOpenAs:#newBrowser
 
     "
      self openOnClassesInChangeSet
@@ -17010,7 +17309,7 @@
     "open a browser, showing all methods in the changeSet."
 
     ^ self basicNew basicInitialize
-        browseMenuMethodsInCurrentChangeSetIn:#newBrowser
+	browseMenuMethodsInCurrentChangeSetIn:#newBrowser
 
     "
      self openOnMethodsInChangeSet
@@ -17021,7 +17320,7 @@
     "open a browser, showing all classes in the given package."
 
     ^ self basicNew
-        spawnProjectBrowserFor:(Array with:aPackage) in:#newBrowser
+	spawnProjectBrowserFor:(Array with:aPackage) in:#newBrowser
 
     "
      self openOnPackage:'stx:libbasic'
@@ -17040,9 +17339,9 @@
     browser openWindow.
     ^ browser
 
-"/    ^ self basicNew 
-"/        spawnClassBrowserFor:aCollectionOfClasses 
-"/        label:titleOrNil 
+"/    ^ self basicNew
+"/        spawnClassBrowserFor:aCollectionOfClasses
+"/        label:titleOrNil
 "/        in:#newBrowser.
 "/
     "
@@ -17069,8 +17368,8 @@
     box := EnterBox new.
     box label:(rresources string:label).
     box
-        title:(rresources string:title)
-        okText:(rresources string:okText).
+	title:(rresources string:title)
+	okText:(rresources string:okText).
     ^ box
 
     "Created: / 6.2.2000 / 01:07:11 / cg"
@@ -17096,7 +17395,7 @@
     "the list of buffer-name-labels (model of the notebook)"
 
     bufferNameList isNil ifTrue:[
-        bufferNameList := List new.
+	bufferNameList := List new.
     ].
     ^ bufferNameList
 
@@ -17117,7 +17416,7 @@
     |holder|
 
     (holder := builder bindingAt:#classesProjectInfoHolder) isNil ifTrue:[
-        builder aspectAt:#classesProjectInfoHolder put:(holder := '' asValue).
+	builder aspectAt:#classesProjectInfoHolder put:(holder := '' asValue).
     ].
     ^ holder.
 !
@@ -17167,9 +17466,9 @@
 !
 
 doEnableRefactoringSupport
-    ^ builder 
-        valueAspectFor:#doEnableRefactoringSupport
-        computeInitialValueWith:[ self canUseRefactoringSupport ]
+    ^ builder
+	valueAspectFor:#doEnableRefactoringSupport
+	computeInitialValueWith:[ self canUseRefactoringSupport ]
 !
 
 doLoadRefactoringSupport
@@ -17190,7 +17489,7 @@
 
 immediateUpdate
     immediateUpdate isNil ifTrue:[
-        immediateUpdate := false asValue.
+	immediateUpdate := false asValue.
     ].
     ^ immediateUpdate
 
@@ -17241,15 +17540,15 @@
     |theCanvas theCanvasType|
 
     navigationState isNil ifTrue:[
-        navigationState := NavigationState new.
-        "/ the kludge below is required to allow
-        "/ subSpecs to be opened in full-window (without a noteBook) as well 
-        "/ (without that, we get trouble accessing the codeView later ...)
-        browserCanvas isNil ifTrue:[
-            "/ opened spec as top-spec (there is no canvas)
-
-            ^ navigationState.
-"/            theCanvas := self. 
+	navigationState := NavigationState new.
+	"/ the kludge below is required to allow
+	"/ subSpecs to be opened in full-window (without a noteBook) as well
+	"/ (without that, we get trouble accessing the codeView later ...)
+	browserCanvas isNil ifTrue:[
+	    "/ opened spec as top-spec (there is no canvas)
+
+	    ^ navigationState.
+"/            theCanvas := self.
 "/            bldr := self builder.
 "/
 "/            bldr notNil ifTrue:[
@@ -17257,19 +17556,19 @@
 "/            ] ifFalse:[
 "/                theCanvasType := self browserCanvasType.
 "/            ]
-        ] ifFalse:[
-            "/ opened spec in canvas
-            theCanvas := self browserCanvas value.
-            theCanvasType := self browserCanvasType.
-        ].
-        self assert:theCanvas notNil.
-        navigationState canvas:theCanvas.
-        theCanvasType isNil ifTrue:[
-            theCanvasType := theCanvas spec.
-        ].
-        navigationState canvasType:theCanvasType.
-        self updateNavigationHistory.
-        self updateBookmarkHolder.
+	] ifFalse:[
+	    "/ opened spec in canvas
+	    theCanvas := self browserCanvas value.
+	    theCanvasType := self browserCanvasType.
+	].
+	self assert:theCanvas notNil.
+	navigationState canvas:theCanvas.
+	theCanvasType isNil ifTrue:[
+	    theCanvasType := theCanvas spec.
+	].
+	navigationState canvasType:theCanvasType.
+	self updateNavigationHistory.
+	self updateBookmarkHolder.
     ].
     ^ navigationState
 
@@ -17285,7 +17584,7 @@
 
 packageInfoBackgroundColorHolder
 
-    "Current background color of package info bar"        
+    "Current background color of package info bar"
 
     ^ self navigationState packageInfoBackgroundColorHolder
 
@@ -17310,10 +17609,10 @@
     |holder|
 
     (holder := builder bindingAt:#searchedClassNameHolder) isNil ifTrue:[
-        holder := '' asValue.
-        builder aspectAt:#searchedClassNameHolder put:holder.
-        holder onChangeEvaluate:[
-            self switchToClassNameMatching: holder value].
+	holder := '' asValue.
+	builder aspectAt:#searchedClassNameHolder put:holder.
+	holder onChangeEvaluate:[
+	    self switchToClassNameMatching: holder value].
     ].
     ^ holder
 !
@@ -17322,9 +17621,9 @@
     |holder|
 
     (holder := builder bindingAt:#searchedClassNameOrSelectorHolder) isNil ifTrue:[
-        holder := '' asValue.
-        builder aspectAt:#searchedClassNameOrSelectorHolder put:holder.
-        holder onChangeEvaluate:[ self switchToSearchItemMatching: holder value].
+	holder := '' asValue.
+	builder aspectAt:#searchedClassNameOrSelectorHolder put:holder.
+	holder onChangeEvaluate:[ self switchToSearchItemMatching: holder value].
     ].
     ^ holder
 
@@ -17333,8 +17632,8 @@
 
 selectedBuffer
     selectedBuffer isNil ifTrue:[
-        selectedBuffer := nil asValue.
-        selectedBuffer addDependent:self.
+	selectedBuffer := nil asValue.
+	selectedBuffer addDependent:self.
     ].
     ^ selectedBuffer
 
@@ -17348,15 +17647,15 @@
 
     answer := self askIfModified:'Modifications have not been saved.\\Change selection anyway ?'.
     answer ifTrue:[
-        navigationState modified:false.
-        navigationState realModifiedState:false.
-
-        (self codeAspect == #classDefinition
-        and:[aSubApplication ~~ self classListApp]) ifTrue:[
-            self classListApp forceReselect
-        ] ifFalse:[
-            aSubApplication forceSelectionClear.
-        ]
+	navigationState modified:false.
+	navigationState realModifiedState:false.
+
+	(self codeAspect == #classDefinition
+	and:[aSubApplication ~~ self classListApp]) ifTrue:[
+	    self classListApp forceReselect
+	] ifFalse:[
+	    aSubApplication forceSelectionClear.
+	]
     ].
     ^ answer
 
@@ -17390,11 +17689,11 @@
 
     subjects := self selectedCategoriesValue.
     ^ (CategoryEnvironment new)
-        categories:subjects;
-        label:(subjects size = 1 
-                    ifTrue:[ 'class category' , subjects anyOne ]
-                    ifFalse:[ subjects size printString , ' class categories' ]);
-        yourself
+	categories:subjects;
+	label:(subjects size = 1
+		    ifTrue:[ 'class category' , subjects anyOne ]
+		    ifFalse:[ subjects size printString , ' class categories' ]);
+	yourself
 
     "Created: / 17-04-2010 / 10:29:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 06-03-2012 / 18:54:41 / cg"
@@ -17405,11 +17704,11 @@
 
     subjects := self selectedClassesValue.
     ^ (ClassEnvironment new)
-        classes:subjects;
-        label:(subjects size = 1 
-                    ifTrue:[ 'class ' , subjects anyOne fullName ]
-                    ifFalse:[ subjects size printString , ' classes' ]);
-        yourself
+	classes:subjects;
+	label:(subjects size = 1
+		    ifTrue:[ 'class ' , subjects anyOne fullName ]
+		    ifFalse:[ subjects size printString , ' classes' ]);
+	yourself
 
     "Created: / 24-02-2009 / 11:08:35 / Jan Vrany <vranyj1@fel.cvut.cz>"
     "Modified: / 06-03-2012 / 18:54:49 / cg"
@@ -17425,13 +17724,13 @@
     classes := ClassEnvironment new.
     methods := SelectorEnvironment new.
     components do:
-        [:each|
-        each isMethod ifTrue:[methods addClass: each mclass selector: each selector].
-        each isBehavior ifTrue:[classes addClass: each theNonMetaclass; addClass: each theMetaclass]].
+	[:each|
+	each isMethod ifTrue:[methods addClass: each mclass selector: each selector].
+	each isBehavior ifTrue:[classes addClass: each theNonMetaclass; addClass: each theMetaclass]].
     "Kludge"
     ^methods isEmpty
-        ifFalse:[methods]
-        ifTrue:[classes].
+	ifFalse:[methods]
+	ifTrue:[classes].
 
     "Created: / 17-04-2010 / 10:09:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 03-08-2011 / 22:48:50 / cg"
@@ -17447,17 +17746,33 @@
     classes := ClassEnvironment new.
     methods := SelectorEnvironment new.
     components do:
-        [:each|
-        each isMethod ifTrue:[methods addClass: each mclass selector: each selector].
-        each isBehavior ifTrue:[classes addClass: each theNonMetaclass; addClass: each theMetaclass]].
+	[:each|
+	each isMethod ifTrue:[methods addClass: each mclass selector: each selector].
+	each isBehavior ifTrue:[classes addClass: each theNonMetaclass; addClass: each theMetaclass]].
     "Kludge"
     ^methods isEmpty
-        ifFalse:[methods]
-        ifTrue:[classes].
+	ifFalse:[methods]
+	ifTrue:[classes].
 
     "Modified: / 03-08-2011 / 22:49:37 / cg"
 !
 
+selectedPackagesAsEnvironment
+    |subjects|
+
+    PackageEnvironment isNil ifTrue:[ Smalltalk loadPackage:'stx:goodies/refactoryBrowser/browser'].
+
+    subjects := self selectedProjectsValue.
+    ^ (PackageEnvironment new)
+	packageNames:subjects;
+	label:(subjects size = 1
+		    ifTrue:[ 'package' , subjects anyOne ]
+		    ifFalse:[ subjects size printString , ' packages' ]);
+	yourself
+
+    "Created: / 05-05-2012 / 10:21:37 / cg"
+!
+
 selectedProtocolsAsEnvironment
     |classes protocols|
 
@@ -17466,12 +17781,12 @@
     protocols := self selectedProtocolsValue.
 
     ^ ProtocolEnvironment new
-        class: classes anyOne
-        protocols: protocols;
-        label:(protocols size = 1 
-                    ifTrue:[ 'protocol' , protocols anyOne , ' in ' , classes anyOne name ]
-                    ifFalse:[ protocols size printString , ' protocols in ' , classes anyOne name ]);
-        yourself
+	class: classes anyOne
+	protocols: protocols;
+	label:(protocols size = 1
+		    ifTrue:[ 'protocol' , protocols anyOne , ' in ' , classes anyOne name ]
+		    ifFalse:[ protocols size printString , ' protocols in ' , classes anyOne name ]);
+	yourself
 
     "Created: / 17-04-2010 / 10:57:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 06-03-2012 / 18:55:00 / cg"
@@ -17549,15 +17864,15 @@
     <resource: #programMenu>
 
     ^ [
-        |m|
-
-        self window sensor ctrlDown ifTrue:[
-            m := self class methodDebugMenu
-        ] ifFalse:[
-            m := self class methodListMenu
-        ].
-        m := m decodeAsLiteralArray.
-        m findGuiResourcesIn:self.
+	|m|
+
+	self window sensor ctrlDown ifTrue:[
+	    m := self class methodDebugMenu
+	] ifFalse:[
+	    m := self class methodListMenu
+	].
+	m := m decodeAsLiteralArray.
+	m findGuiResourcesIn:self.
       ]
 
     "Modified: / 11-09-2007 / 11:44:04 / cg"
@@ -17600,15 +17915,15 @@
     <resource: #programMenu>
 
     ^ [
-        |m|
-
-        self window sensor ctrlDown ifTrue:[
-            m := self class methodDebugMenu
-        ] ifFalse:[
-            m := self class selectorMenu
-        ].
-        m := m decodeAsLiteralArray.
-        m findGuiResourcesIn:self.
+	|m|
+
+	self window sensor ctrlDown ifTrue:[
+	    m := self class methodDebugMenu
+	] ifFalse:[
+	    m := self class selectorMenu
+	].
+	m := m decodeAsLiteralArray.
+	m findGuiResourcesIn:self.
       ]
 
     "Modified: / 11-09-2007 / 11:44:09 / cg"
@@ -17630,21 +17945,21 @@
     m := m decodeAsLiteralArray.
     i := m detectItem:[:item | item nameKey == #RemoveBuffer] ifNone:nil.
     i notNil ifTrue:[
-        i label:(resources string:i label with:index printString).
-        i argument:index.
-        index ~~ self selectedBuffer value ifTrue:[
-            "/ for now: if that buffer is modified,
-            "/ do not allow removing.
-            "/ (must be brought to front, in order for check-for-modification to work)
-            (buffers at:index) modified ifTrue:[
-                i disable
-            ].
-        ].
+	i label:(resources string:i label with:index printString).
+	i argument:index.
+	index ~~ self selectedBuffer value ifTrue:[
+	    "/ for now: if that buffer is modified,
+	    "/ do not allow removing.
+	    "/ (must be brought to front, in order for check-for-modification to work)
+	    (buffers at:index) modified ifTrue:[
+		i disable
+	    ].
+	].
     ].
     i := m detectItem:[:item | item nameKey == #RemoveAllButBuffer] ifNone:nil.
     i notNil ifTrue:[
-        i label:(resources string:i label with:index printString).
-        i argument:index.
+	i label:(resources string:i label with:index printString).
+	i argument:index.
     ].
     m findGuiResourcesIn:self.
     ^ m
@@ -17659,9 +17974,9 @@
     |holder|
 
     (holder := builder bindingAt:#visitedClassesHistory) isNil ifTrue:[
-        builder aspectAt:#visitedClassesHistory put:(holder := List new).
-        holder addAll:(self class visitedClassNamesHistory).
-        SystemBrowser addDependent:self.
+	builder aspectAt:#visitedClassesHistory put:(holder := List new).
+	holder addAll:(self class visitedClassNamesHistory).
+	SystemBrowser addDependent:self.
     ].
     ^ holder
 
@@ -17891,28 +18206,27 @@
     "Created: / 24.2.2000 / 23:28:06 / cg"
 ! !
 
-
 !NewSystemBrowser methodsFor:'aspects-organization'!
 
 categoryMenuVisible
     |holder|
 
     (holder := builder bindingAt:#categoryMenuVisible) isNil ifTrue:[
-        holder := BlockValue
-                        with:[:v1 :v2 | |n|
-                                n := self navigationState.
-                                n isClassBrowser not
-                                and:[n isProtocolOrFullProtocolBrowser not
-                                and:[n isMethodBrowser not
-                                and:[n isClassExtensionBrowser not
-                                and:[n isChainBrowser not
-                                and:[(n isNameSpaceFullBrowser or:[n isNameSpaceBrowser not])
-                                and:[n isVersionDiffBrowser not
-                                and:[(n isNameSpaceFullBrowser or:[v1 == OrganizerCanvas organizerModeCategory])]]]]]]]
-                             ]
-                        argument:(self organizerModeForMenu)
-                        argument:(self browserCanvas).
-        builder aspectAt:#categoryMenuVisible put: holder
+	holder := BlockValue
+			with:[:v1 :v2 | |n|
+				n := self navigationState.
+				n isClassBrowser not
+				and:[n isProtocolOrFullProtocolBrowser not
+				and:[n isMethodBrowser not
+				and:[n isClassExtensionBrowser not
+				and:[n isChainBrowser not
+				and:[(n isNameSpaceFullBrowser or:[n isNameSpaceBrowser not])
+				and:[n isVersionDiffBrowser not
+				and:[(n isNameSpaceFullBrowser or:[v1 == OrganizerCanvas organizerModeCategory])]]]]]]]
+			     ]
+			argument:(self organizerModeForMenu)
+			argument:(self browserCanvas).
+	builder aspectAt:#categoryMenuVisible put: holder
     ].
     ^ holder
 
@@ -17923,14 +18237,14 @@
     |holder|
 
     (holder := builder bindingAt:#classHierarchyMenuVisible) isNil ifTrue:[
-        holder := BlockValue
-                        with:[:orgMode :v2 | 
-                                (orgMode == OrganizerCanvas organizerModeClassHierarchy)
-                                or:[orgMode == OrganizerCanvas organizerModeHierarchy]
-                             ]
-                        argument:(self organizerModeForMenu)
-                        argument:(self browserCanvas).
-        builder aspectAt:#classHierarchyMenuVisible put: holder
+	holder := BlockValue
+			with:[:orgMode :v2 |
+				(orgMode == OrganizerCanvas organizerModeClassHierarchy)
+				or:[orgMode == OrganizerCanvas organizerModeHierarchy]
+			     ]
+			argument:(self organizerModeForMenu)
+			argument:(self browserCanvas).
+	builder aspectAt:#classHierarchyMenuVisible put: holder
     ].
     ^ holder
 
@@ -17946,15 +18260,15 @@
     |holder|
 
     (holder := builder bindingAt:#classMenuVisible) isNil ifTrue:[
-        holder := BlockValue
-                        with:[:v | |n|
-                                n := self navigationState.
-                                n isProtocolOrFullProtocolBrowser not
-                                and:[n isMethodBrowser not
-                                and:[n isChainBrowser not]]
-                             ]
-                        argument:(self browserCanvas).
-        builder aspectAt:#classMenuVisible put: holder
+	holder := BlockValue
+			with:[:v | |n|
+				n := self navigationState.
+				n isProtocolOrFullProtocolBrowser not
+				and:[n isMethodBrowser not
+				and:[n isChainBrowser not]]
+			     ]
+			argument:(self browserCanvas).
+	builder aspectAt:#classMenuVisible put: holder
     ].
     ^ holder
 !
@@ -17963,15 +18277,15 @@
     |holder|
 
     (holder := builder bindingAt:#codeMenuVisible) isNil ifTrue:[
-        holder := BlockValue
-                        with:[:v | |n|
-                                n := self navigationState.
-                                n isClassDocumentationBrowser not
-                                and:[n isVersionDiffBrowser not
-                                and:[n isFullClassSourceBrowser not]]
-                             ]
-                        argument:(self browserCanvas).
-        builder aspectAt:#codeMenuVisible put: holder
+	holder := BlockValue
+			with:[:v | |n|
+				n := self navigationState.
+				n isClassDocumentationBrowser not
+				and:[n isVersionDiffBrowser not
+				and:[n isFullClassSourceBrowser not]]
+			     ]
+			argument:(self browserCanvas).
+	builder aspectAt:#codeMenuVisible put: holder
     ].
     ^ holder
 
@@ -17982,13 +18296,13 @@
     |holder|
 
     (holder := builder bindingAt:#isNotFullProtocolBrowser) isNil ifTrue:[
-        holder := BlockValue
-                        with:[:v | |n|
-                                n := self navigationState.
-                                n isFullProtocolBrowser not
-                             ]
-                        argument:(self browserCanvas).
-        builder aspectAt:#isNotFullProtocolBrowser put: holder
+	holder := BlockValue
+			with:[:v | |n|
+				n := self navigationState.
+				n isFullProtocolBrowser not
+			     ]
+			argument:(self browserCanvas).
+	builder aspectAt:#isNotFullProtocolBrowser put: holder
     ].
     ^ holder
 
@@ -17999,13 +18313,13 @@
     |holder|
 
     (holder := builder bindingAt:#methodListMenuVisible) isNil ifTrue:[
-        holder := BlockValue
-                        with:[:v | |n|
-                                n := self navigationState.
-                                n isMethodListBrowser
-                             ]
-                        argument:(self browserCanvas).
-        builder aspectAt:#methodListMenuVisible put: holder
+	holder := BlockValue
+			with:[:v | |n|
+				n := self navigationState.
+				n isMethodListBrowser
+			     ]
+			argument:(self browserCanvas).
+	builder aspectAt:#methodListMenuVisible put: holder
     ].
     ^ holder
 !
@@ -18014,14 +18328,14 @@
     |holder|
 
     (holder := builder bindingAt:#nameSpaceMenuVisible) isNil ifTrue:[
-        holder := BlockValue
-                        with:[:orgMode :v2 | 
-                                orgMode == OrganizerCanvas organizerModeNamespace
-                                or:[self navigationState isNameSpaceFullBrowser]
-                             ]
-                        argument:(self organizerModeForMenu)
-                        argument:(self browserCanvas).
-        builder aspectAt:#nameSpaceMenuVisible put: holder
+	holder := BlockValue
+			with:[:orgMode :v2 |
+				orgMode == OrganizerCanvas organizerModeNamespace
+				or:[self navigationState isNameSpaceFullBrowser]
+			     ]
+			argument:(self organizerModeForMenu)
+			argument:(self browserCanvas).
+	builder aspectAt:#nameSpaceMenuVisible put: holder
     ].
     ^ holder
 
@@ -18033,11 +18347,11 @@
     |holder|
 
     (holder := builder bindingAt:#notShowingInheritedMethods) isNil ifTrue:[
-        holder := BlockValue
-                with:[:h :o | self isMethodListBrowser not and:[h == #class] ]
-                argument:(self methodVisibilityHolder)
-                argument:(self organizerModeForMenu).
-        builder aspectAt:#notShowingInheritedMethods put: holder
+	holder := BlockValue
+		with:[:h :o | self isMethodListBrowser not and:[h == #class] ]
+		argument:(self methodVisibilityHolder)
+		argument:(self organizerModeForMenu).
+	builder aspectAt:#notShowingInheritedMethods put: holder
     ].
     ^ holder
 
@@ -18046,13 +18360,13 @@
 
 operationsMenuEnabled
     ^ [
-        (self canUseRefactoringSupport)
+	(self canUseRefactoringSupport)
       ]
 !
 
 operationsMenuVisible
     ^ [
-        (self canUseRefactoringSupport)
+	(self canUseRefactoringSupport)
       ]
 !
 
@@ -18060,9 +18374,9 @@
     |holder|
 
     (holder := builder bindingAt:#organizerIsNotShowingCategories) isNil ifTrue:[
-        holder := BlockValue
-            with:[:h | h ~~ OrganizerCanvas organizerModeCategory]
-            argument:(self organizerModeForMenu)
+	holder := BlockValue
+	    with:[:h | h ~~ OrganizerCanvas organizerModeCategory]
+	    argument:(self organizerModeForMenu)
     ].
     ^ holder
 
@@ -18073,9 +18387,9 @@
     |holder|
 
     (holder := builder bindingAt:#organizerIsShowingCategories) isNil ifTrue:[
-        holder := BlockValue
-            with:[:h | h == OrganizerCanvas organizerModeCategory]
-            argument:(self organizerModeForMenu)
+	holder := BlockValue
+	    with:[:h | h == OrganizerCanvas organizerModeCategory]
+	    argument:(self organizerModeForMenu)
     ].
     ^ holder
 
@@ -18086,9 +18400,9 @@
     |holder|
 
     (holder := builder bindingAt:#organizerIsShowingClasses) isNil ifTrue:[
-        holder := BlockValue
-            with:[:h :b | navigationState isMethodListBrowser not]
-            arguments:(Array with:self organizerModeForMenu with:self selectedBuffer)
+	holder := BlockValue
+	    with:[:h :b | navigationState isMethodListBrowser not]
+	    arguments:(Array with:self organizerModeForMenu with:self selectedBuffer)
     ].
     ^ holder
 !
@@ -18097,9 +18411,9 @@
     |holder|
 
     (holder := builder bindingAt:#organizerIsShowingClassesAndIsNotShowingCategories) isNil ifTrue:[
-        holder := BlockValue
-            with:[:h | navigationState isMethodListBrowser not and:[h ~~ OrganizerCanvas organizerModeCategory]]
-            argument:(self organizerModeForMenu)
+	holder := BlockValue
+	    with:[:h | navigationState isMethodListBrowser not and:[h ~~ OrganizerCanvas organizerModeCategory]]
+	    argument:(self organizerModeForMenu)
     ].
     ^ holder
 
@@ -18110,9 +18424,9 @@
     |holder|
 
     (holder := builder bindingAt:#organizerIsShowingClassesAndIsShowingCategories) isNil ifTrue:[
-        holder := BlockValue
-            with:[:h | navigationState isMethodListBrowser not and:[h == OrganizerCanvas organizerModeCategory]]
-            argument:(self organizerModeForMenu)
+	holder := BlockValue
+	    with:[:h | navigationState isMethodListBrowser not and:[h == OrganizerCanvas organizerModeCategory]]
+	    argument:(self organizerModeForMenu)
     ].
     ^ holder
 
@@ -18133,12 +18447,12 @@
     |holder|
 
     (holder := builder bindingAt:#organizerModeForMenu) isNil ifTrue:[
-        holder := (PluggableAdaptor new)
-                getBlock:[:m | self organizerMode value ]
-                putBlock:[:m :newValue | self organizerMode value:newValue.]
-                updateBlock:[:m :aspect :param | ].
-        builder aspectAt:#organizerModeForMenu put:holder.
-        holder addDependent:self.
+	holder := (PluggableAdaptor new)
+		getBlock:[:m | self organizerMode value ]
+		putBlock:[:m :newValue | self organizerMode value:newValue.]
+		updateBlock:[:m :aspect :param | ].
+	builder aspectAt:#organizerModeForMenu put:holder.
+	holder addDependent:self.
     ].
     ^ holder
 
@@ -18149,41 +18463,41 @@
     |holder|
 
     (holder := builder bindingAt:#organizerProtocolAndMethodListSpecHolder) isNil ifTrue:[
-        holder := BlockValue
-            with:[:classes :old | 
-                | spec |
-                spec := old at:1.
-                classes notEmptyOrNil ifTrue:[
-                    (classes anySatisfy:[:cls|cls theNonMetaclass supportsMethodCategories]) ifTrue:[
-                        spec := #protocolAndMethodListSpec_Both.
-                    ] ifFalse:[
-                        spec := #protocolAndMethodListSpec_JustMethodList
-                    ].
-                    old at:1 put: spec.
-                ].
-                spec.
-            ]
-            argument:(self selectedClasses)
-            argument:(ValueHolder with: (Array with:#protocolAndMethodListSpec_Both))
+	holder := BlockValue
+	    with:[:classes :old |
+		| spec |
+		spec := old at:1.
+		classes notEmptyOrNil ifTrue:[
+		    (classes anySatisfy:[:cls|cls supportsMethodCategories]) ifTrue:[
+			spec := #protocolAndMethodListSpec_Both.
+		    ] ifFalse:[
+			spec := #protocolAndMethodListSpec_JustMethodList
+		    ].
+		    old at:1 put: spec.
+		].
+		spec.
+	    ]
+	    argument:(self selectedClasses)
+	    argument:(ValueHolder with: (Array with:#protocolAndMethodListSpec_Both))
     ].
     ^ holder
 
-    "Modified: / 08-03-2007 / 23:01:20 / cg"
     "Created: / 07-08-2011 / 16:40:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 01-06-2012 / 20:36:55 / cg"
 !
 
 projectMenuVisible
     |holder|
 
     (holder := builder bindingAt:#projectMenuVisible) isNil ifTrue:[
-        holder := BlockValue
-                        with:[:orgMode :v2 |
-                                orgMode == OrganizerCanvas organizerModeProject
-                                or:[self navigationState isClassExtensionBrowser]
-                              ]
-                        argument:(self organizerModeForMenu)
-                        argument:(self browserCanvas).
-        builder aspectAt:#projectMenuVisible put: holder
+	holder := BlockValue
+			with:[:orgMode :v2 |
+				orgMode == OrganizerCanvas organizerModeProject
+				or:[self navigationState isClassExtensionBrowser]
+			      ]
+			argument:(self organizerModeForMenu)
+			argument:(self browserCanvas).
+	builder aspectAt:#projectMenuVisible put: holder
     ].
     ^ holder
 
@@ -18195,17 +18509,17 @@
     |holder|
 
     (holder := builder bindingAt:#protocolMenuVisible) isNil ifTrue:[
-        holder := BlockValue
-                        with:[:v | |n|
-                                n := self navigationState.
-                                n isFullClassSourceBrowser not
-                                and:[n isClassDocumentationBrowser not
-                                and:[n isVersionDiffBrowser not
-                                and:[n isMethodBrowser not
-                                and:[n isChainBrowser not]]]]
-                             ]
-                        argument:(self browserCanvas).
-        builder aspectAt:#protocolMenuVisible put: holder
+	holder := BlockValue
+			with:[:v | |n|
+				n := self navigationState.
+				n isFullClassSourceBrowser not
+				and:[n isClassDocumentationBrowser not
+				and:[n isVersionDiffBrowser not
+				and:[n isMethodBrowser not
+				and:[n isChainBrowser not]]]]
+			     ]
+			argument:(self browserCanvas).
+	builder aspectAt:#protocolMenuVisible put: holder
     ].
     ^ holder
 
@@ -18216,14 +18530,14 @@
     |holder|
 
     (holder := builder bindingAt:#searchMenuInMethodListVisible) isNil ifTrue:[
-        holder := BlockValue
-                        with:[:v | |n|
-                                n := self navigationState.
-                                self searchMenuVisible value not
-                                and:[n isMethodBrowser]
-                             ]
-                        argument:(self browserCanvas).
-        builder aspectAt:#searchMenuInMethodListVisible put: holder
+	holder := BlockValue
+			with:[:v | |n|
+				n := self navigationState.
+				self searchMenuVisible value not
+				and:[n isMethodBrowser]
+			     ]
+			argument:(self browserCanvas).
+	builder aspectAt:#searchMenuInMethodListVisible put: holder
     ].
     ^ holder
 !
@@ -18232,16 +18546,16 @@
     |holder|
 
     (holder := builder bindingAt:#searchMenuVisible) isNil ifTrue:[
-        holder := BlockValue
-                        with:[:v | |n|
-                                n := self navigationState.
-                                n isProtocolOrFullProtocolBrowser not
-                                and:[n isChainBrowser not
-                                and:[n isVersionDiffBrowser not
-                                and:[n isCategoryBrowser not]]]
-                             ]
-                        argument:(self browserCanvas).
-        builder aspectAt:#searchMenuVisible put: holder
+	holder := BlockValue
+			with:[:v | |n|
+				n := self navigationState.
+				n isProtocolOrFullProtocolBrowser not
+				and:[n isChainBrowser not
+				and:[n isVersionDiffBrowser not
+				and:[n isCategoryBrowser not]]]
+			     ]
+			argument:(self browserCanvas).
+	builder aspectAt:#searchMenuVisible put: holder
     ].
     ^ holder
 !
@@ -18250,15 +18564,15 @@
     |holder|
 
     (holder := builder bindingAt:#selectorMenuVisible) isNil ifTrue:[
-        holder := BlockValue
-                        with:[:v | |n|
-                                n := self navigationState.
-                                n isClassDocumentationBrowser not
-                                and:[n isVersionDiffBrowser not
-                                and:[n isFullClassSourceBrowser not]]
-                             ]
-                        argument:(self browserCanvas).
-        builder aspectAt:#selectorMenuVisible put: holder
+	holder := BlockValue
+			with:[:v | |n|
+				n := self navigationState.
+				n isClassDocumentationBrowser not
+				and:[n isVersionDiffBrowser not
+				and:[n isFullClassSourceBrowser not]]
+			     ]
+			argument:(self browserCanvas).
+	builder aspectAt:#selectorMenuVisible put: holder
     ].
     ^ holder
 
@@ -18269,11 +18583,11 @@
     |holder|
 
     (holder := builder bindingAt:#showingInheritedMethods) isNil ifTrue:[
-        holder := BlockValue
-                with:[:h :o | self isMethodListBrowser not and:[h ~~ #class] ]
-                argument:(self methodVisibilityHolder)
-                argument:(self organizerModeForMenu).
-        builder aspectAt:#showingInheritedMethods put: holder
+	holder := BlockValue
+		with:[:h :o | self isMethodListBrowser not and:[h ~~ #class] ]
+		argument:(self methodVisibilityHolder)
+		argument:(self organizerModeForMenu).
+	builder aspectAt:#showingInheritedMethods put: holder
     ].
     ^ holder
 
@@ -18284,13 +18598,13 @@
     |holder|
 
     (holder := builder bindingAt:#viewMenuForMethodListVisible) isNil ifTrue:[
-        holder := BlockValue
-                        with:[:v | |n|
-                                n := self navigationState.
-                                n isMethodListBrowser or:[n isChainBrowser]
-                             ]
-                        argument:(self browserCanvas).
-        builder aspectAt:#viewMenuForMethodListVisible put: holder
+	holder := BlockValue
+			with:[:v | |n|
+				n := self navigationState.
+				n isMethodListBrowser or:[n isChainBrowser]
+			     ]
+			argument:(self browserCanvas).
+	builder aspectAt:#viewMenuForMethodListVisible put: holder
     ].
     ^ holder
 !
@@ -18299,22 +18613,22 @@
     |holder|
 
     (holder := builder bindingAt:#viewMenuOrganizerItemsVisible) isNil ifTrue:[
-        holder := BlockValue
-                        with:[:v | |n|
-                                n := self navigationState.
-                                n isClassBrowser not
-                                and:[n isProtocolOrFullProtocolBrowser not
-                                and:[n isProjectFullBrowser not
-                                and:[n isMethodBrowser not
-                                and:[n isChainBrowser not
-                                and:[n isCategoryBrowser not
-                                and:[n isNameSpaceBrowser not
-                                and:[n isNameSpaceFullBrowser not
-                                and:[n isVersionDiffBrowser not
-                                and:[n isProjectBrowser not]]]]]]]]]
-                             ]
-                        argument:(self browserCanvas).
-        builder aspectAt:#viewMenuOrganizerItemsVisible put: holder
+	holder := BlockValue
+			with:[:v | |n|
+				n := self navigationState.
+				n isClassBrowser not
+				and:[n isProtocolOrFullProtocolBrowser not
+				and:[n isProjectFullBrowser not
+				and:[n isMethodBrowser not
+				and:[n isChainBrowser not
+				and:[n isCategoryBrowser not
+				and:[n isNameSpaceBrowser not
+				and:[n isNameSpaceFullBrowser not
+				and:[n isVersionDiffBrowser not
+				and:[n isProjectBrowser not]]]]]]]]]
+			     ]
+			argument:(self browserCanvas).
+	builder aspectAt:#viewMenuOrganizerItemsVisible put: holder
     ].
     ^ holder
 
@@ -18325,23 +18639,23 @@
     |holder|
 
     (holder := builder bindingAt:#viewMenuVisible) isNil ifTrue:[
-        holder := BlockValue
-                        with:[:v | |n| 
-                                n := self navigationState.
-                                true "n isClassBrowser not"
-                                and:[true "n isProtocolOrFullProtocolBrowser not"
-                                and:[true "n isProjectFullBrowser not"
-                                and:[n isMethodBrowser not
-                                and:[n isMethodListBrowser not
-                                and:[n isChainBrowser not
-                                and:[n isCategoryBrowser not
-                                and:[n isNameSpaceBrowser not
-                                and:[n isNameSpaceFullBrowser not
-                                and:[n isVersionDiffBrowser not
-                                and:[n isProjectBrowser not]]]]]]]]]]
-                             ]
-                        argument:(self browserCanvas).
-        builder aspectAt:#viewMenuVisible put: holder
+	holder := BlockValue
+			with:[:v | |n|
+				n := self navigationState.
+				true "n isClassBrowser not"
+				and:[true "n isProtocolOrFullProtocolBrowser not"
+				and:[true "n isProjectFullBrowser not"
+				and:[n isMethodBrowser not
+				and:[n isMethodListBrowser not
+				and:[n isChainBrowser not
+				and:[n isCategoryBrowser not
+				and:[n isNameSpaceBrowser not
+				and:[n isNameSpaceFullBrowser not
+				and:[n isVersionDiffBrowser not
+				and:[n isProjectBrowser not]]]]]]]]]]
+			     ]
+			argument:(self browserCanvas).
+	builder aspectAt:#viewMenuVisible put: holder
     ].
     ^ holder
 
@@ -18354,9 +18668,9 @@
     |holder|
 
     (holder := builder bindingAt:#bookmarkBarVisibleHolder) isNil ifTrue:[
-        holder := UserPreferences current showBookmarkBar asValue.
-        builder aspectAt:#bookmarkBarVisibleHolder put: holder.
-        holder addDependent:self.
+	holder := UserPreferences current showBookmarkBar asValue.
+	builder aspectAt:#bookmarkBarVisibleHolder put: holder.
+	holder addDependent:self.
     ].
     ^ holder
 
@@ -18368,7 +18682,7 @@
     <resource: #uiAspect>
 
     browsletShowHideLabelHolder isNil ifTrue:[
-        browsletShowHideLabelHolder := self class showBrowsletIcon asValue
+	browsletShowHideLabelHolder := self class showBrowsletIcon asValue
     ].
     ^ browsletShowHideLabelHolder.
 
@@ -18379,9 +18693,9 @@
     |holder|
 
     (holder := builder bindingAt:#codeInfoVisible) isNil ifTrue:[
-        holder := (DefaultCodeInfoVisible ? true "false")  asValue.
-        builder aspectAt:#codeInfoVisible put: holder.
-        holder addDependent:self.
+	holder := (DefaultCodeInfoVisible ? true "false")  asValue.
+	builder aspectAt:#codeInfoVisible put: holder.
+	holder addDependent:self.
     ].
     ^ holder
 
@@ -18393,10 +18707,10 @@
     |holder|
 
     (holder := builder bindingAt:#doAutoFormat) isNil ifTrue:[
-        holder := (DefaultAutoFormat ? UserPreferences current autoFormatting) asValue.
-        builder aspectAt:#doAutoFormat put:holder.
-        holder onChangeEvaluate:[ DefaultAutoFormat := holder value.
-                                  self enqueueDelayedUpdateCodeWithoutAutoSearch].
+	holder := (DefaultAutoFormat ? UserPreferences current autoFormatting) asValue.
+	builder aspectAt:#doAutoFormat put:holder.
+	holder onChangeEvaluate:[ DefaultAutoFormat := holder value.
+				  self enqueueDelayedUpdateCodeWithoutAutoSearch].
     ].
     ^ holder.
 !
@@ -18405,10 +18719,10 @@
     |holder|
 
     (holder := builder bindingAt:#doImmediateExplaining) isNil ifTrue:[
-        holder := (DefaultImmediateExplaining ? true) asValue.
-        builder aspectAt:#doImmediateExplaining put:holder.
-        holder onChangeEvaluate:[ DefaultImmediateExplaining := holder value.
-                                ].
+	holder := (DefaultImmediateExplaining ? true) asValue.
+	builder aspectAt:#doImmediateExplaining put:holder.
+	holder onChangeEvaluate:[ DefaultImmediateExplaining := holder value.
+				].
     ].
 
     ^ holder
@@ -18418,11 +18732,11 @@
     |holder|
 
     (holder := builder bindingAt:#doImmediateSyntaxColoring) isNil ifTrue:[
-        holder := (DefaultImmediateSyntaxColoring ? true) asValue.
-        builder aspectAt:#doImmediateSyntaxColoring put:holder.
-        holder onChangeEvaluate:[ DefaultImmediateSyntaxColoring := holder value.
-                                  self startSyntaxHighlightProcess
-                                ].
+	holder := (DefaultImmediateSyntaxColoring ? true) asValue.
+	builder aspectAt:#doImmediateSyntaxColoring put:holder.
+	holder onChangeEvaluate:[ DefaultImmediateSyntaxColoring := holder value.
+				  self startSyntaxHighlightProcess
+				].
     ].
     ^ holder
 !
@@ -18431,10 +18745,10 @@
     |holder|
 
     (holder := builder bindingAt:#doSyntaxColoring) isNil ifTrue:[
-        holder := (DefaultSyntaxColoring ? UserPreferences current syntaxColoring) asValue.
-        builder aspectAt:#doSyntaxColoring put:holder.
-        holder onChangeEvaluate:[ DefaultSyntaxColoring := holder value.
-                                  self enqueueDelayedUpdateCodeWithoutAutoSearch].
+	holder := (DefaultSyntaxColoring ? UserPreferences current syntaxColoring) asValue.
+	builder aspectAt:#doSyntaxColoring put:holder.
+	holder onChangeEvaluate:[ DefaultSyntaxColoring := holder value.
+				  self enqueueDelayedUpdateCodeWithoutAutoSearch].
     ].
     ^ holder.
 !
@@ -18451,9 +18765,9 @@
     |holder|
 
     (holder := builder bindingAt:#emphasizeUnloadedClasses) isNil ifTrue:[
-        holder := (DefaultEmphasizeUnloadedClasses ? false) asValue.
-        builder aspectAt:#emphasizeUnloadedClasses put: holder.
-        holder onChangeSend:#emphasizeUnloadedClassesChanged to:self.
+	holder := (DefaultEmphasizeUnloadedClasses ? false) asValue.
+	builder aspectAt:#emphasizeUnloadedClasses put: holder.
+	holder onChangeSend:#emphasizeUnloadedClassesChanged to:self.
     ].
     ^ holder
 
@@ -18467,10 +18781,10 @@
     classListApp := self classListApp.
     DefaultEmphasizeUnloadedClasses := e := self emphasizeUnloadedClasses value.
     e ifTrue:[
-        clr := Color red:(classListApp window font boldness < 0.6 
-                                ifTrue:[20] ifFalse:[10]).
-    ] ifFalse:[
-        clr := nil
+	clr := Color red:(classListApp window font boldness < 0.6
+				ifTrue:[20] ifFalse:[10]).
+    ] ifFalse:[
+	clr := nil
     ].
     classListApp unloadedClassesColor:clr.
     "/ classListApp updateList.
@@ -18489,9 +18803,9 @@
     |holder|
 
     (holder := builder bindingAt:#hideUnloadedClasses) isNil ifTrue:[
-        holder := (DefaultHideUnloadedClasses ? false) asValue.
-        builder aspectAt:#hideUnloadedClasses put: holder.
-        holder onChangeEvaluate:[ DefaultHideUnloadedClasses := holder value ].
+	holder := (DefaultHideUnloadedClasses ? false) asValue.
+	builder aspectAt:#hideUnloadedClasses put: holder.
+	holder onChangeEvaluate:[ DefaultHideUnloadedClasses := holder value ].
     ].
     ^ holder
 
@@ -18503,9 +18817,9 @@
     |holder|
 
     (holder := builder bindingAt:#markApplicationsHolder) isNil ifTrue:[
-        holder := (DefaultMarkApplications ? true) asValue.
-        builder aspectAt:#markApplicationsHolder put: holder.
-        holder onChangeEvaluate:[ DefaultMarkApplications := holder value ].
+	holder := (DefaultMarkApplications ? true) asValue.
+	builder aspectAt:#markApplicationsHolder put: holder.
+	holder onChangeEvaluate:[ DefaultMarkApplications := holder value ].
     ].
     ^ holder
 
@@ -18535,9 +18849,9 @@
     |holder|
 
     (holder := builder bindingAt:#shortNamesInTabs) isNil ifTrue:[
-        holder := (DefaultShortNameInTabs ? true) asValue.
-        builder aspectAt:#shortNamesInTabs put: holder.
-        holder onChangeEvaluate:[ DefaultShortNameInTabs := holder value ].
+	holder := (DefaultShortNameInTabs ? true) asValue.
+	builder aspectAt:#shortNamesInTabs put: holder.
+	holder onChangeEvaluate:[ DefaultShortNameInTabs := holder value ].
     ].
     ^ holder
 !
@@ -18546,9 +18860,9 @@
     |holder|
 
     (holder := builder bindingAt:#showAllClassesInNameSpaceOrganisation) isNil ifTrue:[
-        holder := (DefaultShortAllClassesInNameSpaceOrganisation ? false) asValue.
-        builder aspectAt:#showAllClassesInNameSpaceOrganisation put: holder.
-        holder onChangeEvaluate:[ DefaultShortAllClassesInNameSpaceOrganisation := holder value ].
+	holder := (DefaultShortAllClassesInNameSpaceOrganisation ? false) asValue.
+	builder aspectAt:#showAllClassesInNameSpaceOrganisation put: holder.
+	holder onChangeEvaluate:[ DefaultShortAllClassesInNameSpaceOrganisation := holder value ].
     ].
     ^ holder
 
@@ -18558,7 +18872,7 @@
 
 showClassPackages
     showClassPackages isNil ifTrue:[
-        showClassPackages := false asValue.
+	showClassPackages := false asValue.
     ].
     ^ showClassPackages.
 
@@ -18575,8 +18889,8 @@
     |holder|
 
     (holder := builder bindingAt:#showCoverageInformation) isNil ifTrue:[
-        holder := false asValue.
-        builder aspectAt:#showCoverageInformation put: holder.
+	holder := false asValue.
+	builder aspectAt:#showCoverageInformation put: holder.
     ].
     ^ holder
 
@@ -18587,9 +18901,9 @@
     |holder|
 
     (holder := builder bindingAt:#showGlobalHistory) isNil ifTrue:[
-        holder := (AspectAdaptor forAspect: #showGlobalHistory)
-                    subject: UserPreferences current.
-        builder aspectAt:#showGlobalHistory put: holder.
+	holder := (AspectAdaptor forAspect: #showGlobalHistory)
+		    subject: UserPreferences current.
+	builder aspectAt:#showGlobalHistory put: holder.
     ].
     ^ holder
 
@@ -18602,9 +18916,9 @@
     |holder|
 
     (holder := builder bindingAt:#showLocalHistory) isNil ifTrue:[
-        holder := (AspectAdaptor forAspect: #showLocalHistory)
-                    subject: UserPreferences current.
-        builder aspectAt:#showLocalHistory put: holder.
+	holder := (AspectAdaptor forAspect: #showLocalHistory)
+		    subject: UserPreferences current.
+	builder aspectAt:#showLocalHistory put: holder.
     ].
     ^ holder
 
@@ -18615,9 +18929,9 @@
     |holder|
 
     (holder := builder bindingAt:#showMethodComplexity) isNil ifTrue:[
-        holder := (DefaultShowMethodComplexity ? false) asValue.
-        builder aspectAt:#showMethodComplexity put: holder.
-        holder onChangeEvaluate:[ DefaultShowMethodComplexity := holder value ].
+	holder := (DefaultShowMethodComplexity ? false) asValue.
+	builder aspectAt:#showMethodComplexity put: holder.
+	holder onChangeEvaluate:[ DefaultShowMethodComplexity := holder value ].
     ].
     ^ holder
 !
@@ -18626,9 +18940,9 @@
     |holder|
 
     (holder := builder bindingAt:#showMethodInheritance) isNil ifTrue:[
-        holder := (DefaultShowMethodInheritance ? true) asValue.
-        builder aspectAt:#showMethodInheritance put: holder.
-        holder onChangeEvaluate:[ DefaultShowMethodInheritance := holder value ].
+	holder := (DefaultShowMethodInheritance ? true) asValue.
+	builder aspectAt:#showMethodInheritance put: holder.
+	holder onChangeEvaluate:[ DefaultShowMethodInheritance := holder value ].
     ].
     ^ holder
 
@@ -18640,9 +18954,9 @@
     |holder|
 
     (holder := builder bindingAt:#showMethodTemplate) isNil ifTrue:[
-        holder := (AspectAdaptor forAspect: #showMethodTemplate)
-                    subject: UserPreferences current.
-        builder aspectAt:#showMethodTemplate put: holder.
+	holder := (AspectAdaptor forAspect: #showMethodTemplate)
+		    subject: UserPreferences current.
+	builder aspectAt:#showMethodTemplate put: holder.
     ].
     ^ holder
 
@@ -18654,9 +18968,9 @@
     |holder|
 
     (holder := builder bindingAt:#showMethodTypeIcon) isNil ifTrue:[
-        holder := (DefaultShowMethodTypeIcon ? true) asValue.
-        builder aspectAt:#showMethodTypeIcon put: holder.
-        holder onChangeEvaluate:[ DefaultShowMethodTypeIcon := holder value ].
+	holder := (DefaultShowMethodTypeIcon ? true) asValue.
+	builder aspectAt:#showMethodTypeIcon put: holder.
+	holder onChangeEvaluate:[ DefaultShowMethodTypeIcon := holder value ].
     ].
     ^ holder
 !
@@ -18665,12 +18979,12 @@
     |holder|
 
     (holder := builder bindingAt:#showMultitabMode) isNil ifTrue:[
-        holder := (DefaultShowMultitabMode ? false) asValue.
-        builder aspectAt:#showMultitabMode put: holder.
-        holder onChangeEvaluate:[
-            self updateSpecialCodeEditorVisibility.
-            DefaultShowMultitabMode := holder value.
-        ].
+	holder := (DefaultShowMultitabMode ? false) asValue.
+	builder aspectAt:#showMultitabMode put: holder.
+	holder onChangeEvaluate:[
+	    self updateSpecialCodeEditorVisibility.
+	    DefaultShowMultitabMode := holder value.
+	].
     ].
     ^ holder
 !
@@ -18683,8 +18997,8 @@
     |holder|
 
     (holder := builder bindingAt:#showPlugin) isNil ifTrue:[
-        holder := false asValue.
-        builder aspectAt:#showPlugin put: holder.
+	holder := false asValue.
+	builder aspectAt:#showPlugin put: holder.
     ].
     ^ holder
     "
@@ -18704,9 +19018,9 @@
     |holder|
 
     (holder := builder bindingAt:#showPseudoProtocols) isNil ifTrue:[
-        holder := (DefaultShowPseudoProtocols ? true) asValue.
-        builder aspectAt:#showPseudoProtocols put: holder.
-        holder onChangeEvaluate:[ DefaultShowPseudoProtocols := holder value ].
+	holder := (DefaultShowPseudoProtocols ? true) asValue.
+	builder aspectAt:#showPseudoProtocols put: holder.
+	holder onChangeEvaluate:[ DefaultShowPseudoProtocols := holder value ].
     ].
     ^ holder
 !
@@ -18715,12 +19029,12 @@
     |holder|
 
     (holder := builder bindingAt:#showSpecialResourceEditors) isNil ifTrue:[
-        holder := (DefaultShowSpecialResourceEditors ? false) asValue.
-        builder aspectAt:#showSpecialResourceEditors put: holder.
-        holder onChangeEvaluate:[ 
-            self updateSpecialCodeEditorVisibility.
-            DefaultShowSpecialResourceEditors := holder value 
-        ].
+	holder := (DefaultShowSpecialResourceEditors ? false) asValue.
+	builder aspectAt:#showSpecialResourceEditors put: holder.
+	holder onChangeEvaluate:[
+	    self updateSpecialCodeEditorVisibility.
+	    DefaultShowSpecialResourceEditors := holder value
+	].
     ].
     ^ holder
 !
@@ -18729,11 +19043,11 @@
     |holder|
 
     (holder := builder bindingAt:#showSyntheticMethods) isNil ifTrue:[
-        holder := (DefaultShowSyntheticMethods ? false) asValue.
-        builder aspectAt:#showSyntheticMethods put: holder.
-        holder onChangeEvaluate:[ 
-            DefaultShowSyntheticMethods := holder value 
-        ].
+	holder := (DefaultShowSyntheticMethods ? false) asValue.
+	builder aspectAt:#showSyntheticMethods put: holder.
+	holder onChangeEvaluate:[
+	    DefaultShowSyntheticMethods := holder value
+	].
     ].
     ^ holder
 
@@ -18744,9 +19058,9 @@
     |holder|
 
     (holder := builder bindingAt:#showUnloadedClasses) isNil ifTrue:[
-        holder := BlockValue forLogicalNot:(self hideUnloadedClasses).
-        builder aspectAt:#showUnloadedClasses put: holder.
-        holder onChangeEvaluate:[self classListApp invalidateList].
+	holder := BlockValue forLogicalNot:(self hideUnloadedClasses).
+	builder aspectAt:#showUnloadedClasses put: holder.
+	holder onChangeEvaluate:[self classListApp invalidateList].
     ].
     ^ holder
 
@@ -18758,9 +19072,9 @@
     |holder|
 
     (holder := builder bindingAt:#sortByNameAndInheritance) isNil ifTrue:[
-        "now: I do not want that to be automatically forwarded to the prefs"
-        holder := (UserPreferences current sortAndIndentClassesByInheritance) asValue.
-        builder aspectAt:#sortByNameAndInheritance put: holder.
+	"now: I do not want that to be automatically forwarded to the prefs"
+	holder := (UserPreferences current sortAndIndentClassesByInheritance) asValue.
+	builder aspectAt:#sortByNameAndInheritance put: holder.
     ].
     ^ holder
 
@@ -18778,9 +19092,9 @@
     |holder|
 
     (holder := builder bindingAt:#stringSearchToolVisibleHolder) isNil ifTrue:[
-        holder := false asValue.
-        builder aspectAt:#stringSearchToolVisibleHolder put: holder.
-        holder addDependent:self.
+	holder := false asValue.
+	builder aspectAt:#stringSearchToolVisibleHolder put: holder.
+	holder addDependent:self.
     ].
     ^ holder
 !
@@ -18789,9 +19103,9 @@
     |holder|
 
     (holder := builder bindingAt:#toolBarVisibleHolder) isNil ifTrue:[
-        holder := (DefaultToolBarVisible ? true "false") asValue.
-        builder aspectAt:#toolBarVisibleHolder put: holder.
-        holder addDependent:self.
+	holder := (DefaultToolBarVisible ? true "false") asValue.
+	builder aspectAt:#toolBarVisibleHolder put: holder.
+	holder addDependent:self.
     ].
     ^ holder
 
@@ -18856,10 +19170,10 @@
     |holder|
 
     (holder := builder bindingAt:#canGoBackAspect) isNil ifTrue:[
-        holder := (AspectAdaptor forAspect:#canGoBack)                
-                        subjectChannel: self navigationHistory;
-                        yourself.
-        builder aspectAt:#canGoBackAspect put:holder.
+	holder := (AspectAdaptor forAspect:#canGoBack)
+			subjectChannel: self navigationHistory;
+			yourself.
+	builder aspectAt:#canGoBackAspect put:holder.
     ].
     ^ holder.
 
@@ -18867,7 +19181,7 @@
 "/    aspect := self objectAttributeAt: #canGoBackAspect.
 "/    aspect ifNil:
 "/        [aspect :=
-"/            (AspectAdaptor forAspect:#canGoBack)                
+"/            (AspectAdaptor forAspect:#canGoBack)
 "/                subjectChannel: self navigationHistory;
 "/                yourself.
 "/        self objectAttributeAt: #canGoBackAspect put: aspect].
@@ -18881,10 +19195,10 @@
     |holder|
 
     (holder := builder bindingAt:#canGoBackInGlobalHistoryAspect) isNil ifTrue:[
-        holder := (AspectAdaptor forAspect:#canGoBack)                
-                        subjectChannel: self class classHistory;
-                        yourself.
-        builder aspectAt:#canGoBackInGlobalHistoryAspect put:holder.
+	holder := (AspectAdaptor forAspect:#canGoBack)
+			subjectChannel: self class classHistory;
+			yourself.
+	builder aspectAt:#canGoBackInGlobalHistoryAspect put:holder.
     ].
     ^ holder.
 
@@ -18892,7 +19206,7 @@
 "/    aspect := self objectAttributeAt: #canGoBackAspect.
 "/    aspect ifNil:
 "/        [aspect :=
-"/            (AspectAdaptor forAspect:#canGoBack)                
+"/            (AspectAdaptor forAspect:#canGoBack)
 "/                subjectChannel: self navigationHistory;
 "/                yourself.
 "/        self objectAttributeAt: #canGoBackAspect put: aspect].
@@ -18906,10 +19220,10 @@
     |holder|
 
     (holder := builder bindingAt:#canGoForwardAspect) isNil ifTrue:[
-        holder := (AspectAdaptor forAspect:#canGoForward)                
-                        subjectChannel: self navigationHistory;
-                        yourself.
-        builder aspectAt:#canGoForwardAspect put:holder.
+	holder := (AspectAdaptor forAspect:#canGoForward)
+			subjectChannel: self navigationHistory;
+			yourself.
+	builder aspectAt:#canGoForwardAspect put:holder.
     ].
     ^ holder.
 
@@ -18917,7 +19231,7 @@
 "/    aspect := self objectAttributeAt: #canGoForwardAspect.
 "/    aspect ifNil:
 "/        [aspect :=
-"/            (AspectAdaptor forAspect:#canGoForward)                
+"/            (AspectAdaptor forAspect:#canGoForward)
 "/                subjectChannel: self navigationHistory;
 "/                yourself.
 "/        self objectAttributeAt: #canGoForwardAspect put: aspect].
@@ -18952,12 +19266,12 @@
     | mthd mclass|
 
     (mthd := self theSingleSelectedMethod) notNil ifTrue:[
-        mclass := mthd mclass.
+	mclass := mthd mclass.
     ] ifFalse:[
 "/        self codeAspect value ~= #classDefinition ifTrue:[
 "/            ^ nil
 "/        ].
-        mclass := self theSingleSelectedClass.
+	mclass := self theSingleSelectedClass.
     ].
     ^ mclass
 !
@@ -18978,12 +19292,12 @@
     |nsSymbol cls|
 
     (nsSymbol := self theSingleSelectedNamespace) notNil ifTrue:[
-        nsSymbol ~= BrowserList nameListEntryForALL ifTrue:[
-            ^ NameSpace name:nsSymbol
-        ]
+	nsSymbol ~= BrowserList nameListEntryForALL ifTrue:[
+	    ^ NameSpace name:nsSymbol
+	]
     ].
     (cls := self theSingleSelectedClass) notNil ifTrue:[
-        ^ cls topNameSpace
+	^ cls topNameSpace
     ].
     ^ Class nameSpaceQuerySignal query ? Smalltalk
 !
@@ -18992,17 +19306,17 @@
     |prj projects|
 
     (prj := self theSingleSelectedProject) notNil ifTrue:[
-        prj ~= BrowserList nameListEntryForALL ifTrue:[
-            ^ prj
-        ]
+	prj ~= BrowserList nameListEntryForALL ifTrue:[
+	    ^ prj
+	]
     ].
     projects := ((self selectedClassesValue) collect:[:cls | cls package]) asSet.
     projects size == 1 ifTrue:[
-        ^ projects first
+	^ projects first
     ].
     projects := (self selectedMethodsValue collect:[:m | m package]) asSet.
     projects size == 1 ifTrue:[
-        ^ projects first
+	^ projects first
     ].
     ^ nil
 
@@ -19071,12 +19385,12 @@
 
     selected := self selectedClassesValue.
     selected isEmptyOrNil ifTrue:[
-        selected := self selectedCategoryClasses
+	selected := self selectedCategoryClasses
     ].
     selected size > 0 ifTrue:[
-        selected do:[ :cls | 
-            cls instAndClassMethodsDo:[:m | m isInstrumented ifTrue:[^ true]].
-        ].
+	selected do:[ :cls |
+	    cls instAndClassMethodsDo:[:m | m isInstrumented ifTrue:[^ true]].
+	].
     ].
     ^ false.
 
@@ -19154,15 +19468,15 @@
 
 hasAnyTestCaseOrExecutableClassMethodOrStartableApplicationSelectedHolder
     ^ BlockValue
-        forLogical:(self hasAnyExecutableClassMethodSelectedHolder)
-        or:(self hasAnyTestCaseSelectedHolder)
-        or:(self hasStartableApplicationSelectedHolder)
+	forLogical:(self hasAnyExecutableClassMethodSelectedHolder)
+	or:(self hasAnyTestCaseSelectedHolder)
+	or:(self hasStartableApplicationSelectedHolder)
 !
 
 hasAnyTestCaseOrExecutableClassMethodSelectedHolder
     ^ BlockValue
-        forLogical:(self hasAnyExecutableClassMethodSelectedHolder)
-        or:(self hasAnyTestCaseSelectedHolder)
+	forLogical:(self hasAnyExecutableClassMethodSelectedHolder)
+	or:(self hasAnyTestCaseSelectedHolder)
 !
 
 hasAnyTestCaseSelected
@@ -19170,14 +19484,14 @@
 
     selected := self selectedClassesValue.
     selected isEmptyOrNil ifTrue:[
-        selected := self selectedCategoryClasses
+	selected := self selectedCategoryClasses
     ].
     selected size > 0 ifTrue:[
-        ^ selected 
-            contains:[ :cls | 
-                            cls theNonMetaclass isTestCaseLike
-                            and:[ cls theNonMetaclass isAbstract not ]
-            ].
+	^ selected
+	    contains:[ :cls |
+			    cls theNonMetaclass isTestCaseLike
+			    and:[ cls theNonMetaclass isAbstract not ]
+	    ].
     ].
     ^ false.
 
@@ -19188,8 +19502,8 @@
     |holder|
 
     (holder := builder bindingAt:#hasAnyTestCaseSelectedHolder) isNil ifTrue:[
-        holder := ValueHolder with:false.
-        builder aspectAt:#hasAnyTestCaseSelectedHolder put: holder.
+	holder := ValueHolder with:false.
+	builder aspectAt:#hasAnyTestCaseSelectedHolder put: holder.
     ].
     ^ holder
 
@@ -19223,8 +19537,8 @@
 
 hasApplicationOrHTTPServiceClassSelectedHolder
     ^ [ self hasApplicationClassSelected
-        | self hasWebApplicationClassSelected
-        | self hasStandaloneStartupClassSelected ]
+	| self hasWebApplicationClassSelected
+	| self hasStandaloneStartupClassSelected ]
 
     "Created: / 04-02-2000 / 22:02:53 / cg"
 !
@@ -19245,12 +19559,12 @@
     foundBreak := false.
     foundTrace := false.
     self
-        selectedMethodsDo:[ :aMethod |
-            aMethod isWrapped ifTrue:[
-                foundBreak := foundBreak or:[ aMethod isBreakpointed ].
-                foundTrace := foundTrace or:[ aMethod isBreakpointed not ]
-            ]
-        ].
+	selectedMethodsDo:[ :aMethod |
+	    aMethod isWrapped ifTrue:[
+		foundBreak := foundBreak or:[ aMethod isBreakpointed ].
+		foundTrace := foundTrace or:[ aMethod isBreakpointed not ]
+	    ]
+	].
     ^ foundBreak and:[ foundTrace ]
 !
 
@@ -19268,6 +19582,12 @@
     ^ [ self hasCategorySelected and:[self canFileOutXML] ]
 !
 
+hasCategorySelectedAndInstrumentingCompilerExistsHolder
+    ^ [ self hasCategorySelected and:[ self instrumentingCompilerExists] ]
+
+    "Created: / 31-05-2012 / 09:20:44 / cg"
+!
+
 hasCategorySelectedAndSourceCodeManager
     ^ self hasCategorySelected and:[self hasSourceCodeManager]
 
@@ -19392,8 +19712,8 @@
 !
 
 hasClassSelectedAndInstrumentingCompilerExistsAndOOMPackageLoadedHolder
-    ^ [ self hasClassSelectedAndInstrumentingCompilerExistsHolder value 
-        and:[ OOM::MetricVisualizer notNil ] 
+    ^ [ self hasClassSelectedAndInstrumentingCompilerExistsHolder value
+	and:[ OOM::MetricVisualizer notNil ]
       ]
 
     "Created: / 27-04-2010 / 12:33:41 / cg"
@@ -19425,16 +19745,16 @@
 
 hasClassSelectedWhichCanBeExcludedFromProject
     ^ self hasAnyClassSelectedForWhich:
-        [:cls |
-            |def|
-
-            def := ProjectDefinition definitionClassForPackage:cls package.
-
-            def notNil
-            and:[ def isLoaded
-            and:[ (def allClassNames includes:cls name)
-            and:[ cls isProjectDefinition not ]]]
-        ]
+	[:cls |
+	    |def|
+
+	    def := ProjectDefinition definitionClassForPackage:cls package.
+
+	    def notNil
+	    and:[ def isLoaded
+	    and:[ (def allClassNames includes:cls name)
+	    and:[ cls isProjectDefinition not ]]]
+	]
 
     "Created: / 22-02-2007 / 13:55:03 / cg"
     "Modified: / 28-02-2012 / 16:51:10 / cg"
@@ -19448,16 +19768,16 @@
 
 hasClassSelectedWhichCanBeIncludedInProject
     ^ self hasAnyClassSelectedForWhich:
-        [:cls |
-            |def|
-
-            def := ProjectDefinition definitionClassForPackage:cls package.
-
-            def notNil
-            and:[ def isLoaded
-            and:[ (def compiled_classNames includes:cls name) not
-            and:[ cls isProjectDefinition not ]]]
-        ]
+	[:cls |
+	    |def|
+
+	    def := ProjectDefinition definitionClassForPackage:cls package.
+
+	    def notNil
+	    and:[ def isLoaded
+	    and:[ (def compiled_classNames includes:cls name) not
+	    and:[ cls isProjectDefinition not ]]]
+	]
 
     "Created: / 22-02-2007 / 13:54:16 / cg"
     "Modified: / 28-02-2012 / 16:50:59 / cg"
@@ -19471,16 +19791,16 @@
 
 hasClassSelectedWhichCanBeMadeAutoloadedInProject
     ^ self hasAnyClassSelectedForWhich:
-        [:cls |
-            |def|
-
-            def := ProjectDefinition definitionClassForPackage:cls package.
-
-            def notNil
-            and:[ def isLoaded
-            and:[ (def autoloaded_classNames includes:cls name) not
-            and:[ cls isProjectDefinition not ]]]
-        ]
+	[:cls |
+	    |def|
+
+	    def := ProjectDefinition definitionClassForPackage:cls package.
+
+	    def notNil
+	    and:[ def isLoaded
+	    and:[ (def autoloaded_classNames includes:cls name) not
+	    and:[ cls isProjectDefinition not ]]]
+	]
 
     "Created: / 30-08-2007 / 18:48:59 / cg"
 !
@@ -19509,11 +19829,11 @@
     selection := self selectionInCodeView.
 
     (mthd := self theSingleSelectedMethod) notNil ifTrue:[
-        mclass := mthd mclass.
+	mclass := mthd mclass.
     ].
     mclass isNil ifTrue:[
-        mclass := self theSingleSelectedClass.
-        mclass isNil ifTrue:[^ false].
+	mclass := self theSingleSelectedClass.
+	mclass isNil ifTrue:[^ false].
     ].
     ^ (mclass theNonMetaclass whichClassDefinesClassVar:selection) notNil.
 
@@ -19538,7 +19858,7 @@
 
 hasClassVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
     ^ [ self canUseRefactoringSupport
-        and:[self hasClassVariableSelectedInCodeViewOrVariableList] ]
+	and:[self hasClassVariableSelectedInCodeViewOrVariableList] ]
 !
 
 hasClassVariableSelectedInCodeViewOrVariableListHolder
@@ -19570,14 +19890,14 @@
 
 hasClassesSelectedAndDataBaseRepositoryExistsHolder
     ^ [
-        | classes |
-
-        classes := self selectedClassesValue.
-        classes isEmptyOrNil ifTrue:[
-            false
-        ] ifFalse:[
-            ConfigurableFeatures includesFeature: #DataBaseSourceCodeManagerSupport
-        ]
+	| classes |
+
+	classes := self selectedClassesValue.
+	classes isEmptyOrNil ifTrue:[
+	    false
+	] ifFalse:[
+	    ConfigurableFeatures includesFeature: #DataBaseSourceCodeManagerSupport
+	]
     ]
 
     "Created: / 03-01-2012 / 15:48:46 / cg"
@@ -19587,14 +19907,14 @@
 
 hasClassesSelectedAndFileBasedRepositoryExistsHolder
     ^ [
-        | classes |
-
-        classes := self selectedClassesValue.
-        classes isEmptyOrNil ifTrue:[
-            false
-        ] ifFalse:[
-            ConfigurableFeatures includesFeature: #FileBasedSourceCodeManagerSupport
-        ]
+	| classes |
+
+	classes := self selectedClassesValue.
+	classes isEmptyOrNil ifTrue:[
+	    false
+	] ifFalse:[
+	    ConfigurableFeatures includesFeature: #FileBasedSourceCodeManagerSupport
+	]
     ]
 
     "Created: / 21-12-2011 / 17:05:28 / cg"
@@ -19604,16 +19924,16 @@
 
 hasClassesSelectedAndMercurialRepositoryExistsHolder
     ^ [
-        | classes |
-
-        classes := self selectedClassesValue.
-        classes isEmptyOrNil ifTrue:[
-            false
-        ] ifFalse:[
-            classes 
-                allSatisfy:
-                    [:cls | self hasMercurialRepositoryFor: cls theNonMetaclass package]
-        ]
+	| classes |
+
+	classes := self selectedClassesValue.
+	classes isEmptyOrNil ifTrue:[
+	    false
+	] ifFalse:[
+	    classes
+		allSatisfy:
+		    [:cls | self hasMercurialRepositoryFor: cls theNonMetaclass package]
+	]
     ]
 
     "Created: / 19-01-2012 / 16:14:57 / cg"
@@ -19621,16 +19941,16 @@
 
 hasClassesSelectedAndPerforceRepositoryExistsHolder
     ^ [
-        | classes |
-
-        classes := self selectedClassesValue.
-        classes isEmptyOrNil ifTrue:[
-            false
-        ] ifFalse:[
-            classes 
-                allSatisfy:
-                    [:cls | self hasPerforceRepositoryFor: cls theNonMetaclass package]
-        ]
+	| classes |
+
+	classes := self selectedClassesValue.
+	classes isEmptyOrNil ifTrue:[
+	    false
+	] ifFalse:[
+	    classes
+		allSatisfy:
+		    [:cls | self hasPerforceRepositoryFor: cls theNonMetaclass package]
+	]
     ]
 
     "Created: / 19-04-2011 / 14:13:52 / cg"
@@ -19642,24 +19962,24 @@
     classes := self selectedClassesValue.
     classes size = 0 ifTrue:[^false].
     ^ classes
-        allSatisfy:
-            [:cls | self hasSubversionRepositoryFor: cls theNonMetaclass package]
+	allSatisfy:
+	    [:cls | self hasSubversionRepositoryFor: cls theNonMetaclass package]
 
     "Modified: / 28-02-2012 / 16:55:03 / cg"
 !
 
 hasClassesSelectedAndSubversionRepositoryExistsHolder
     ^ [
-        | classes |
-
-        classes := self selectedClassesValue.
-        classes isEmptyOrNil ifTrue:[
-            false
-        ] ifFalse:[
-            classes 
-                allSatisfy:
-                    [:cls | self hasSubversionRepositoryFor: cls theNonMetaclass package]
-        ]
+	| classes |
+
+	classes := self selectedClassesValue.
+	classes isEmptyOrNil ifTrue:[
+	    false
+	] ifFalse:[
+	    classes
+		allSatisfy:
+		    [:cls | self hasSubversionRepositoryFor: cls theNonMetaclass package]
+	]
     ]
 
     "Modified: / 28-02-2012 / 16:55:12 / cg"
@@ -19678,8 +19998,8 @@
 
 hasClassesWithCommonSuperclassAndVariableSelectedAndCanUseRefactoringSupportHolder
     ^ [ self canUseRefactoringSupport
-        and:[self hasClassesWithCommonSuperclassSelected
-        and:[self hasVariableSelectedInCodeViewOrVariableList]] ]
+	and:[self hasClassesWithCommonSuperclassSelected
+	and:[self hasVariableSelectedInCodeViewOrVariableList]] ]
 
     "Created: / 4.2.2000 / 22:02:53 / cg"
 !
@@ -19721,13 +20041,13 @@
     selectedNamespaces := self selectedNamespaces value.
     selectedNamespaces size == 0 ifTrue:[^ false].
     ^ (selectedNamespaces
-        contains:[:nm |
-            |ns|
-
-            ns := Smalltalk at:nm asSymbol ifAbsent:nil.
-            ns notNil
-            and:[ns allClasses size ~~ 0]
-        ]
+	contains:[:nm |
+	    |ns|
+
+	    ns := Smalltalk at:nm asSymbol ifAbsent:nil.
+	    ns notNil
+	    and:[ns allClasses size ~~ 0]
+	]
       ) not
 !
 
@@ -19739,10 +20059,10 @@
 
 hasEnumTypeClassSelected
     ^ self hasAnyClassSelectedForWhich:[:cls |
-                        cls isLoaded
-                        and:[(cls theNonMetaclass askFor:#isAbstract) not
-                        and:[ cls withAllSuperclasses contains:[:aSuperClass |
-                                 aSuperClass theNonMetaclass name includesString:'Enum']]] ]
+			cls isLoaded
+			and:[(cls theNonMetaclass askFor:#isAbstract) not
+			and:[ cls withAllSuperclasses contains:[:aSuperClass |
+				 aSuperClass theNonMetaclass name includesString:'Enum']]] ]
 
     "Modified: / 28-02-2012 / 16:56:28 / cg"
 !
@@ -19778,18 +20098,18 @@
 !
 
 hasExtensionMethodSelected
-    ^ self hasAnyMethodSelectedForWhich:[:m | 
-                                            m containingClass isNil
-                                            or:[ m package ~= m containingClass package ]
-                                        ]
+    ^ self hasAnyMethodSelectedForWhich:[:m |
+					    m containingClass isNil
+					    or:[ m package ~= m containingClass package ]
+					]
 
     "Modified: / 28-02-2012 / 16:21:22 / cg"
 !
 
 hasExtensionMethodSelectedHolder
     ^ BlockValue
-        with:[:m | m and:[self hasExtensionMethodSelected]]
-        argument:(self hasMethodSelectedHolder)
+	with:[:m | m and:[self hasExtensionMethodSelected]]
+	argument:(self hasMethodSelectedHolder)
 
     "Modified: / 08-03-2007 / 23:00:43 / cg"
 !
@@ -19848,14 +20168,14 @@
     selection := self selectionInCodeView.
 
     (mthd := self theSingleSelectedMethod) notNil ifTrue:[
-        mclass := mthd mclass.
+	mclass := mthd mclass.
     ].
     mclass isNil ifTrue:[
-        self codeAspect value ~= #classDefinition ifTrue:[
-            ^ false
-        ].
-        mclass := self theSingleSelectedClass.
-        (mclass isNil or:[mclass isMeta]) ifTrue:[ ^ false].
+	self codeAspect value ~= #classDefinition ifTrue:[
+	    ^ false
+	].
+	mclass := self theSingleSelectedClass.
+	(mclass isNil or:[mclass isMeta]) ifTrue:[ ^ false].
     ].
     ^ (mclass whichClassDefinesInstVar:selection) notNil.
 
@@ -19885,7 +20205,7 @@
 
 hasInstanceVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
     ^ [ self canUseRefactoringSupport
-        and:[self hasInstanceVariableSelectedInCodeViewOrVariableList]]
+	and:[self hasInstanceVariableSelectedInCodeViewOrVariableList]]
 !
 
 hasInstanceVariableSelectedInCodeViewOrVariableListHolder
@@ -19931,7 +20251,7 @@
     sel isNil ifTrue:[^ false].
 
     (self hasAnyClassSelectedForWhich:[:cls |
-        (cls canUnderstand:sel)]) ifTrue:[^ true].
+	(cls canUnderstand:sel)]) ifTrue:[^ true].
 
     ^ false "true".
 
@@ -19980,7 +20300,7 @@
 
 hasMetaMethodSelectedHolder
     ^ [ (self hasMethodSelected and:[self hasMetaSelected])
-        or:[self hasClassMethodsSelected ]]
+	or:[self hasClassMethodsSelected ]]
 !
 
 hasMetaSelected
@@ -20016,14 +20336,14 @@
 
 hasMethodSelectedAndCanUseRefactoringSupportHolder
     ^ [ self canUseRefactoringSupport
-        and:[self hasMethodSelected] ]
+	and:[self hasMethodSelected] ]
 
     "Created: / 4.2.2000 / 22:23:39 / cg"
 !
 
 hasMethodSelectedAndInstrumentingCompilerExistsAndOOMPackageLoadedHolder
-    ^ [ self hasMethodSelectedAndInstrumentingCompilerExistsHolder value 
-        and:[ OOM::MetricVisualizer notNil ] 
+    ^ [ self hasMethodSelectedAndInstrumentingCompilerExistsHolder value
+	and:[ OOM::MetricVisualizer notNil ]
       ]
 
     "Created: / 10-08-2010 / 14:42:18 / cg"
@@ -20206,8 +20526,8 @@
 
 hasNoMethodOrMixedWrapsSelectedHolder
     ^ [ self hasMethodSelected not
-        or:[ self hasBothMethodsWithBreakAndTraceSelected
-        or:[ self hasMethodWithWrapSelected not] ]]
+	or:[ self hasBothMethodsWithBreakAndTraceSelected
+	or:[ self hasMethodWithWrapSelected not] ]]
 !
 
 hasNoProjectSelectedHolder
@@ -20262,7 +20582,7 @@
 
 hasNonProjectDefinitionSelected
     ^ self selectedClassesValue
-        contains:[:cls | cls theNonMetaclass isProjectDefinition not]
+	contains:[:cls | cls theNonMetaclass isProjectDefinition not]
 
     "Created: / 10-08-2006 / 16:26:02 / cg"
     "Modified: / 13-10-2006 / 11:54:45 / cg"
@@ -20294,8 +20614,8 @@
     |holder|
 
     (holder := builder bindingAt:#hasNonTestCaseClassMethodWithoutArgsSelectedHolder) isNil ifTrue:[
-        holder := ValueHolder with:false.
-        builder aspectAt:#hasNonTestCaseClassMethodWithoutArgsSelectedHolder put: holder.
+	holder := ValueHolder with:false.
+	builder aspectAt:#hasNonTestCaseClassMethodWithoutArgsSelectedHolder put: holder.
     ].
     ^ holder
 
@@ -20336,37 +20656,37 @@
 !
 
 hasOnlyMethodsWithBreakPointSelected
-        |anyBreak anyWrap|
-
-        anyBreak := anyWrap := false.
-        self
-                selectedMethodsDo:[:aMethod |
-                        aMethod isBreakpointed ifTrue:[
-                                anyBreak := true
-                        ] ifFalse:[
-                                aMethod isWrapped ifTrue:[
-                                        anyWrap := true
-                                ]
-                        ]
-                ].
-        ^ anyBreak and:[anyWrap not]
+	|anyBreak anyWrap|
+
+	anyBreak := anyWrap := false.
+	self
+		selectedMethodsDo:[:aMethod |
+			aMethod isBreakpointed ifTrue:[
+				anyBreak := true
+			] ifFalse:[
+				aMethod isWrapped ifTrue:[
+					anyWrap := true
+				]
+			]
+		].
+	^ anyBreak and:[anyWrap not]
 !
 
 hasOnlyMethodsWithTracePointSelected
-        |anyBreak anyWrap|
-
-        anyBreak := anyWrap := false.
-        self
-                selectedMethodsDo:[:aMethod |
-                        aMethod isBreakpointed ifTrue:[
-                                anyBreak := true
-                        ] ifFalse:[
-                                aMethod isWrapped ifTrue:[
-                                        anyWrap := true
-                                ]
-                        ]
-                ].
-        ^ anyWrap and:[anyBreak not]
+	|anyBreak anyWrap|
+
+	anyBreak := anyWrap := false.
+	self
+		selectedMethodsDo:[:aMethod |
+			aMethod isBreakpointed ifTrue:[
+				anyBreak := true
+			] ifFalse:[
+				aMethod isWrapped ifTrue:[
+					anyWrap := true
+				]
+			]
+		].
+	^ anyWrap and:[anyBreak not]
 !
 
 hasPerforceRepositoryFor: package
@@ -20390,7 +20710,7 @@
 
 hasProjectDefinitionOrClassWithExtensionsSelectedAndSourceCodeManagerHolder
     ^ [ self hasSourceCodeManager
-        and:[ self hasProjectDefinitionSelected or:[self hasClassWithExtensionsSelected]]]
+	and:[ self hasProjectDefinitionSelected or:[self hasClassWithExtensionsSelected]]]
 
     "Created: / 12-09-2011 / 11:12:12 / cg"
 !
@@ -20415,11 +20735,11 @@
 
 hasProjectDefinitionWithAnyUnloadedClassSelected
     (self selectedClassesValue) do:[:cls |
-        cls isLoaded ifFalse:[^ true].
-        cls isProjectDefinition ifTrue:[
-            cls hasAllExtensionsLoaded ifFalse:[^ true].
-            cls hasAllClassesLoaded ifFalse:[^ true].
-        ].
+	cls isLoaded ifFalse:[^ true].
+	cls isProjectDefinition ifTrue:[
+	    cls hasAllExtensionsLoaded ifFalse:[^ true].
+	    cls hasAllClassesLoaded ifFalse:[^ true].
+	].
     ].
     ^ true
 
@@ -20471,16 +20791,16 @@
 hasProjectSelectedMonticelloRepositoryExistsHolder
 
     ^[self hasProjectSelected and:
-        [(Smalltalk at: #MCRepositoryGroup) notNil and:
-            [(Smalltalk at: #MCRepositoryGroup) default repositories size > 0]]]
+	[(Smalltalk at: #MCRepositoryGroup) notNil and:
+	    [(Smalltalk at: #MCRepositoryGroup) default repositories size > 0]]]
 
     "Created: / 14-09-2010 / 22:37:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 hasProjectSelectedSubversionRepositoryExistsHolder
     ^ [ self hasProjectSelected
-            and:[self selectedProjects value size = 1
-                and:[self hasSubversionRepositoryFor: self selectedProjects value anyOne]]]
+	    and:[self selectedProjects value size = 1
+		and:[self hasSubversionRepositoryFor: self selectedProjects value anyOne]]]
 
     "Created: / 31-03-2008 / 15:07:52 / janfrog"
 !
@@ -20511,22 +20831,22 @@
 !
 
 hasRealExtensionMethodSelected
-    ^ self hasAnyMethodSelectedForWhich:[:aMethod | 
-                    |mPackage|
-
-                    mPackage := aMethod package.
-                    aMethod containingClass notNil
-                    and:[mPackage ~= aMethod containingClass package
-                    and:[mPackage ~= PackageId noProjectID]] 
-                ]
+    ^ self hasAnyMethodSelectedForWhich:[:aMethod |
+		    |mPackage|
+
+		    mPackage := aMethod package.
+		    aMethod containingClass notNil
+		    and:[mPackage ~= aMethod containingClass package
+		    and:[mPackage ~= PackageId noProjectID]]
+		]
 
     "Modified: / 28-02-2012 / 16:24:22 / cg"
 !
 
 hasRealExtensionMethodSelectedHolder
     ^ BlockValue
-        with:[:m | m and:[self hasRealExtensionMethodSelected]]
-        argument:(self hasMethodSelectedHolder)
+	with:[:m | m and:[self hasRealExtensionMethodSelected]]
+	argument:(self hasMethodSelectedHolder)
 
     "Modified: / 08-03-2007 / 23:00:45 / cg"
 !
@@ -20562,7 +20882,7 @@
 
     "/ use Smalltalk-at to trick the dependency/prerequisite generator
     manager := Smalltalk at:aManagerClassName.
-    ^ manager notNil 
+    ^ manager notNil
     and:[ manager isLoaded
     and:[ manager shownInBrowserMenus ]]
 
@@ -20571,7 +20891,7 @@
 
 hasSelectedClassWithSuperclassHolder
     ^ [ self theSingleSelectedClass notNil
-        and:[self theSingleSelectedClass superclass notNil ]]
+	and:[self theSingleSelectedClass superclass notNil ]]
 
 !
 
@@ -20583,7 +20903,7 @@
 
 hasSelectionInCodeViewAndCanUseRefactoringSupportHolder
     ^ [ self canUseRefactoringSupport
-        and:[self hasSelectionInCodeView]
+	and:[self hasSelectionInCodeView]
       ]
 !
 
@@ -20599,18 +20919,12 @@
     ^ true.
 !
 
-hasSharedPoolClassSelected
-    ^ self hasAnyClassSelectedForWhich:[:cls |    
-                        cls isLoaded  
-                        and:[(cls theNonMetaclass askFor:#isAbstract) not
-                        and:[ cls inheritsFrom:SharedPool ]]]
-
-    "Created: / 25-10-2006 / 09:23:07 / cg"
-    "Modified: / 28-02-2012 / 16:59:17 / cg"
-!
+
 
 hasSharedPoolClassSelectedHolder
-    ^ [ self hasSharedPoolClassSelected ]
+    ^ builder booleanValueAspectFor:#hasSharedPoolClassSelectedHolder.
+
+    "Modified: / 29-05-2012 / 10:20:15 / cg"
 !
 
 hasSingleCategorySelected
@@ -20632,7 +20946,7 @@
 
 hasSingleClassAndClassVariableSelectedAndCanUseRefactoringSupportHolder
     ^ [ self canUseRefactoringSupport
-        and:[self hasSingleClassAndClassVariableSelected] ]
+	and:[self hasSingleClassAndClassVariableSelected] ]
 
     "Created: / 4.2.2000 / 22:02:53 / cg"
 !
@@ -20649,7 +20963,7 @@
 
 hasSingleClassAndSingleVariableSelectedAndCanUseRefactoringSupportHolder
     ^ [ self canUseRefactoringSupport
-        and:[self hasSingleClassAndSingleVariableSelected] ]
+	and:[self hasSingleClassAndSingleVariableSelected] ]
 
     "Created: / 4.2.2000 / 22:02:53 / cg"
 !
@@ -20667,8 +20981,8 @@
 
 hasSingleClassAndVariableSelectedAndCanUseRefactoringSupportHolder
     ^ [ self canUseRefactoringSupport
-        and:[self hasSingleClassSelected
-        and:[self hasVariableSelectedInCodeViewOrVariableList]] ]
+	and:[self hasSingleClassSelected
+	and:[self hasVariableSelectedInCodeViewOrVariableList]] ]
 
     "Created: / 4.2.2000 / 22:02:53 / cg"
 !
@@ -20698,7 +21012,7 @@
 
 hasSingleClassSelectedAndCanUseRefactoringSupportHolder
     ^ [ self canUseRefactoringSupport
-        and:[self hasSingleClassSelected] ]
+	and:[self hasSingleClassSelected] ]
 
     "Created: / 4.2.2000 / 22:03:08 / cg"
 !
@@ -20790,7 +21104,7 @@
 
 hasSingleMethodSelectedAndCanUseRefactoringSupportHolder
     ^ [ self canUseRefactoringSupport
-        and:[self hasSingleMethodSelected]
+	and:[self hasSingleMethodSelected]
       ]
 
     "Created: / 4.2.2000 / 22:11:34 / cg"
@@ -20798,8 +21112,8 @@
 
 hasSingleMethodSelectedAndCodeModifiedHolder
     ^ [
-        self codeReallyModified
-        and:[self hasSingleMethodSelected]
+	self codeReallyModified
+	and:[self hasSingleMethodSelected]
       ]
 
     "Created: / 4.2.2000 / 22:11:34 / cg"
@@ -20812,7 +21126,7 @@
 
 hasSingleMethodSelectedAndSelectionInCodeViewAndCanUseRefactoringSupportHolder
     ^ [ self canUseRefactoringSupport
-        and:[self hasSingleMethodSelectedAndSelectionInCodeView ]
+	and:[self hasSingleMethodSelectedAndSelectionInCodeView ]
       ]
 !
 
@@ -20823,7 +21137,7 @@
 
 hasSingleMethodSelectedAndSelectionInCodeViewAndSingleSelectedMethodHasParameterAndCanUseRefactoringSupportHolder
     ^ [ self canUseRefactoringSupport
-        and:[self hasSingleMethodSelectedAndSelectionInCodeViewAndSingleSelectedMethodHasParameter]
+	and:[self hasSingleMethodSelectedAndSelectionInCodeViewAndSingleSelectedMethodHasParameter]
       ]
 !
 
@@ -20842,7 +21156,7 @@
 
 hasSingleMethodSelectedAndSingleSelectedMethodHasParameterAndCanUseRefactoringSupportHolder
     ^ [ self canUseRefactoringSupport
-        and:[self hasSingleMethodSelectedAndSingleSelectedMethodHasParameter]
+	and:[self hasSingleMethodSelectedAndSingleSelectedMethodHasParameter]
       ]
 !
 
@@ -20933,9 +21247,9 @@
 !
 
 hasSingleRealProjectSelectedHolder
-    ^ [ self hasSingleProjectSelected 
-        and:[ self theSingleSelectedProject notNil
-        and:[ self theSingleSelectedProject string asPackageId isModuleId not ]]]
+    ^ [ self hasSingleProjectSelected
+	and:[ self theSingleSelectedProject notNil
+	and:[ self theSingleSelectedProject string asPackageId isModuleId not ]]]
 !
 
 hasSingleRealProtocolSelected
@@ -20965,9 +21279,9 @@
 !
 
 hasSingleResourceMethodSelectedHolder
-    ^ builder 
-        valueAspectFor:#hasSingleResourceMethodSelectedHolder
-        computeInitialValueWith:[ self hasSingleResourceMethodSelected ]
+    ^ builder
+	valueAspectFor:#hasSingleResourceMethodSelectedHolder
+	computeInitialValueWith:[ self hasSingleResourceMethodSelected ]
 !
 
 hasSingleVariableSelected
@@ -21035,8 +21349,8 @@
     |holder|
 
     (holder := builder bindingAt:#hasStartableApplicationSelectedHolder) isNil ifTrue:[
-        holder := ValueHolder with:false.
-        builder aspectAt:#hasStartableApplicationSelectedHolder put: holder.
+	holder := ValueHolder with:false.
+	builder aspectAt:#hasStartableApplicationSelectedHolder put: holder.
     ].
     ^ holder
 !
@@ -21080,22 +21394,22 @@
 
 hasUnassignedExtensionMethodSelected
     ^ self hasAnyMethodSelectedForWhich:[:aMethod |
-                    |mPackage mClass|
-
-                    mPackage := aMethod package.
-                    mClass := aMethod containingClass.
-                    mClass isNil or:[
-                        mPackage ~= aMethod containingClass package
-                        and:[mPackage = PackageId noProjectID]]
-        ]
+		    |mPackage mClass|
+
+		    mPackage := aMethod package.
+		    mClass := aMethod containingClass.
+		    mClass isNil or:[
+			mPackage ~= aMethod containingClass package
+			and:[mPackage = PackageId noProjectID]]
+	]
 
     "Modified: / 28-02-2012 / 16:24:32 / cg"
 !
 
 hasUnassignedExtensionMethodSelectedHolder
     ^ BlockValue
-        with:[:m | m and:[self hasUnassignedExtensionMethodSelected]]
-        argument:(self hasMethodSelectedHolder)
+	with:[:m | m and:[self hasUnassignedExtensionMethodSelected]]
+	argument:(self hasMethodSelectedHolder)
 
     "Modified: / 08-03-2007 / 23:00:47 / cg"
 !
@@ -21104,8 +21418,8 @@
     |codeView s selClass|
 
     ^ (codeView := self codeView) hasSelection
-    and:[ (s := codeView selectionAsString) isValidSmalltalkIdentifier 
-    and:[ s isUppercaseFirst 
+    and:[ (s := codeView selectionAsString) isValidSmalltalkIdentifier
+    and:[ s isUppercaseFirst
     and:[ (Smalltalk includesKey:s) not
     and:[ (selClass := self theSingleSelectedClass) notNil
     and:[ (selClass theNonMetaclass classVarNames includes:s) not ]]]]]
@@ -21120,7 +21434,7 @@
 hasUndoableOperations
     |manager|
 
-    RefactoryChangeManager isNil ifTrue:[^ false].    "/   returns false if the class is not present  
+    RefactoryChangeManager isNil ifTrue:[^ false].    "/   returns false if the class is not present
     manager := RefactoryChangeManager instance.
     manager isNil ifTrue:[^ false].
     ^ manager hasUndoableOperations
@@ -21129,10 +21443,10 @@
 hasUpdateMethodSelected
     ^ self hasMethodSelected
       and:[self hasOnlyMethodsSelectedForWhich:[:eachMethod | #(
-                                            #'update:'
-                                            #'update:with:'
-                                            #'update:with:from:'
-                                       ) includes:eachMethod selector ]]
+					    #'update:'
+					    #'update:with:'
+					    #'update:with:from:'
+				       ) includes:eachMethod selector ]]
 
     "Modified: / 28-02-2012 / 16:27:19 / cg"
 !
@@ -21168,7 +21482,7 @@
 
 hasVariableSelectedInCodeViewOrVariableListAndCanUseRefactoringSupportHolder
     ^ [ self canUseRefactoringSupport
-        and:[self hasVariableSelectedInCodeViewOrVariableList] ]
+	and:[self hasVariableSelectedInCodeViewOrVariableList] ]
 !
 
 hasVariableSelectedInCodeViewOrVariableListHolder
@@ -21191,7 +21505,7 @@
 !
 
 instrumentingCompilerExists
-    "true, if instrumenting is possible 
+    "true, if instrumenting is possible
      (now, always true, because InstrumentingCompiler is now in the libcomp package)"
 
     ^ InstrumentingCompiler notNil
@@ -21202,7 +21516,7 @@
 isAnyOtherMetaclassPresent
     ^ self isJavaScriptMetaclassPresent
     or:[ self isPlsqlMetaclassPresent
-        or:[ self isHaskellModulePresent ]]
+	or:[ self isHaskellModulePresent ]]
 !
 
 isHaskellModulePresent
@@ -21217,6 +21531,12 @@
     ^ LispEnvironment notNil
 !
 
+isLispMetaclassPresent
+    ^ LispMetaclass notNil and:[LispMetaclass notNil]
+
+    "Created: / 13-05-2012 / 12:52:16 / cg"
+!
+
 isMethodListBrowser
     ^ navigationState isMethodListBrowser
 !
@@ -21229,7 +21549,7 @@
 
 isMethodListBrowserOrHasMultipleClassesSelectedHolder
     ^ [navigationState isMethodListBrowser
-        or:[self selectedClassesValue size > 1] ]
+	or:[self selectedClassesValue size > 1] ]
 
     "Created: / 04-02-2000 / 22:23:39 / cg"
 !
@@ -21245,10 +21565,10 @@
     rubyMetaclass   := Smalltalk classNamed:#'Ruby::Metaclass'.
     rubyParser      := Smalltalk classNamed:#'Ruby::Parser'.
 
-    ^ (rubyMetaclass notNil 
-        and:[rubyMetaclass isLoaded]) 
-            and:[rubyParser notNil
-                and:[rubyParser isLoaded]]
+    ^ (rubyMetaclass notNil
+	and:[rubyMetaclass isLoaded])
+	    and:[rubyParser notNil
+		and:[rubyParser isLoaded]]
 
     "Created: / 11-08-2009 / 16:06:11 / Jan Vrany <vranyj1@fel.cvut.cz>"
 !
@@ -21267,7 +21587,7 @@
 
 methodIsSubclassResponsibility
     self selectedMethodsDo:[:eachMethod |
-        (eachMethod sends:#subclassResponsibility) ifTrue:[^ true].
+	(eachMethod sends:#subclassResponsibility) ifTrue:[^ true].
     ].
     ^ false.
 !
@@ -21281,7 +21601,7 @@
     selector := selector asSymbol.
 
     self selectedClassesDo:[:eachClass |
-        (eachClass includesSelector:selector) ifTrue:[^ false].
+	(eachClass includesSelector:selector) ifTrue:[^ false].
     ].
     ^ true.
 !
@@ -21289,16 +21609,16 @@
 methodNotImplementedInSuperclass
 
     self selectedMethodsDo:[:eachMethod |
-        |selector category mclass|
-
-        selector := eachMethod selector.
-        category := eachMethod category.
-        mclass := eachMethod mclass.
-        mclass notNil ifTrue:[
-            mclass superclass notNil ifTrue:[
-                (mclass superclass includesSelector:selector) ifFalse:[^ true].
-            ]
-        ].
+	|selector category mclass|
+
+	selector := eachMethod selector.
+	category := eachMethod category.
+	mclass := eachMethod mclass.
+	mclass notNil ifTrue:[
+	    mclass superclass notNil ifTrue:[
+		(mclass superclass includesSelector:selector) ifFalse:[^ true].
+	    ]
+	].
     ].
     ^ false.
 !
@@ -21365,7 +21685,6 @@
     ^ UserPreferences current useSearchBarInBrowser or:[self codeView searchBarActionBlock notNil]
 ! !
 
-
 !NewSystemBrowser methodsFor:'change & update'!
 
 categorySelectionChanged
@@ -21395,12 +21714,12 @@
     "/ self classWizardVisibleHolder value:(selectedClasses size == 0).
 
     (navigationState isClassDocumentationBrowser) ifTrue:[
-        "/ kludge - docBrowser can only show one single class
-        selectedClasses size > 1 ifTrue:[
-            selectedClassesHolder value:(Array with:selectedClasses first).
-            self enqueueDelayedUpdateBufferLabel.
-            ^ self.
-        ]
+	"/ kludge - docBrowser can only show one single class
+	selectedClasses size > 1 ifTrue:[
+	    selectedClassesHolder value:(Array with:selectedClasses first).
+	    self enqueueDelayedUpdateBufferLabel.
+	    ^ self.
+	]
     ].
 
 "/    selectedClasses size == 1 ifTrue:[
@@ -21408,7 +21727,7 @@
 "/    ].
 
     navigationState isVersionDiffBrowser ifFalse:[
-        self class addToHistory:(self theSingleSelectedClass) selector:nil.
+	self class addToHistory:(self theSingleSelectedClass) selector:nil.
     ].
     self enqueueDelayedClassSelectionChange.
 
@@ -21422,7 +21741,7 @@
     "/ when the next class is selected
 
     (mc := self methodCategoryListApp) notNil ifTrue:[
-        mc clearLastSelectedProtocol
+	mc clearLastSelectedProtocol
     ]
 !
 
@@ -21439,23 +21758,25 @@
     self updateInfoForChangedClassSelection.
     self updateTestRunnerVisibility.
     self updateExecuteMethodVisibility.
+    self updateInitSharedPoolVisibility.
     self updateLaunchApplicationVisibility.
-
-    "Modified: / 05-08-2006 / 13:21:10 / cg"
+    self updateTextEditorBehavior.
+
+    "Modified: / 01-06-2012 / 23:01:52 / cg"
 !
 
 delayedExplainSelection
     |codeView|
 
     self synchronousUpdate == true ifFalse:[
-        self windowGroup sensor hasUserEvents ifTrue:[
-            "/ re-enqueue at the end to delay until all user input has been handled
-            self
-                enqueueMessage:#delayedExplainSelection
-                for:self
-                arguments:#().
-            ^ self
-        ].
+	self windowGroup sensor hasUserEvents ifTrue:[
+	    "/ re-enqueue at the end to delay until all user input has been handled
+	    self
+		enqueueMessage:#delayedExplainSelection
+		for:self
+		arguments:#().
+	    ^ self
+	].
     ].
 
     self clearInfo.
@@ -21481,9 +21802,9 @@
     "/ dont update codeView, as long as no protocol is selected
     ((codeAspect := self codeAspect) == #repositoryLog
     or:[codeAspect == #repositoryHistory]) ifTrue:[
-        self selectedMethodsValue size == 0 ifTrue:[
-            ^ self
-        ]
+	self selectedMethodsValue size == 0 ifTrue:[
+	    ^ self
+	]
     ].
 
     self enqueueDelayedUpdateCodeWithAutoSearch.
@@ -21495,8 +21816,8 @@
 
     process := methodInfoProcess.
     process notNil ifTrue:[
-        process terminate.
-        process := nil.
+	process terminate.
+	process := nil.
     ].
     methodInfoProcess := [ self asyncShowMethodInfo. methodInfoProcess := nil. ] fork.
 
@@ -21508,7 +21829,7 @@
     or:[ self codeAspect ~~ #classDefinition
     or:[ navigationState methodList size == 0 ]])
     ifTrue:[
-        self enqueueDelayedUpdateCode
+	self enqueueDelayedUpdateCode
     ]
 !
 
@@ -21529,100 +21850,100 @@
     self enqueueDelayedUpdateBufferLabel.
 
     navigationState isClassDocumentationBrowser ifTrue:[
-        "/ show classes documentation
-        self showClassDocumentation.
-        ^ self.
+	"/ show classes documentation
+	self showClassDocumentation.
+	^ self.
     ].
     navigationState isVersionDiffBrowser ifTrue:[
-        "/ show version differences
-        self showVersionDiff.
-        ^ self.
+	"/ show version differences
+	self showVersionDiff.
+	^ self.
     ].
 
     codeView := self codeView.
 
     checkModified ifTrue:[
-        ((codeView notNil and:[codeView modified])
-        or:[navigationState modified])
-        ifTrue:[
-            "/ recheck against the code (could have been unedited)
-            (self reallyModified:navigationState) ifTrue:[
-                "/ do not overwrite the users modifications;
-                "/ instead, flash and show the code all-red
-                "/ (to tell user, that she is editing obolete code)
-                self codeHolder
-                    value:(codeView contentsAsString asText
-                                            emphasizeAllWith:(UserPreferences current emphasisForObsoleteCode)).
-                self codeHolder changed:#value.
-                codeView flash.
-                ^ self.
-            ]
-        ].
+	((codeView notNil and:[codeView modified])
+	or:[navigationState modified])
+	ifTrue:[
+	    "/ recheck against the code (could have been unedited)
+	    (self reallyModified:navigationState) ifTrue:[
+		"/ do not overwrite the users modifications;
+		"/ instead, flash and show the code all-red
+		"/ (to tell user, that she is editing obolete code)
+		self codeHolder
+		    value:(codeView contentsAsString asText
+					    emphasizeAllWith:(UserPreferences current emphasisForObsoleteCode)).
+		self codeHolder changed:#value.
+		codeView flash.
+		^ self.
+	    ]
+	].
     ].
 
     navigationState isFullClassSourceBrowser ifTrue:[
-        "/ show full classes source - set accept action for fileIn
-        self showFullClassSource.
-        ^ self.
+	"/ show full classes source - set accept action for fileIn
+	self showFullClassSource.
+	^ self.
     ].
 
     "/ show method, or class definition
 
     methods := self selectedMethodsValue.
     methods size == 1 ifTrue:[
-        mthd := methods first.
+	mthd := methods first.
     ].
 
     mthd notNil ifTrue:[
-        "/ show methods source - set accept action to compile that single method
-        self setAcceptActionForMethod.
-        self showMethodsCode:mthd scrollToTop:false.
-
-        "/ if there is a variable filter,
-        "/ set the autoSearch for it
-        (navigationState isMethodListBrowser
-        or:[navigationState isFullProtocolBrowser
-        or:[navigationState isMethodBrowser]]) ifFalse:[
-            filteredVariables := self variableFilter value.
-            filteredVariables size > 0 ifTrue:[
-                self searchVariables:filteredVariables readers:true writers:true asAutoSearch:false.
-                "/ codeView notNil ifTrue:[codeView searchFwd]
-            ] ifFalse:[
-                self autoSearchPattern:nil
-            ].
-        ].
-    ] ifFalse:[
-        self updatePackageInfoForMethod:nil.
-
-        protocol := self theSingleSelectedProtocol.
-        (protocol isNil or:[protocol = BrowserList nameListEntryForALL]) ifTrue:[
-            doShowMethodTemplate := false
-        ] ifFalse:[
-            navigationState showMethodTemplate ifTrue:[
-                doShowMethodTemplate := self showMethodTemplate value
+	"/ show methods source - set accept action to compile that single method
+	self setAcceptActionForMethod.
+	self showMethodsCode:mthd scrollToTop:false.
+
+	"/ if there is a variable filter,
+	"/ set the autoSearch for it
+	(navigationState isMethodListBrowser
+	or:[navigationState isFullProtocolBrowser
+	or:[navigationState isMethodBrowser]]) ifFalse:[
+	    filteredVariables := self variableFilter value.
+	    filteredVariables size > 0 ifTrue:[
+		self searchVariables:filteredVariables readers:true writers:true asAutoSearch:false.
+		"/ codeView notNil ifTrue:[codeView searchFwd]
+	    ] ifFalse:[
+		self autoSearchPattern:nil
+	    ].
+	].
+    ] ifFalse:[
+	self updatePackageInfoForMethod:nil.
+
+	protocol := self theSingleSelectedProtocol.
+	(protocol isNil or:[protocol = BrowserList nameListEntryForALL]) ifTrue:[
+	    doShowMethodTemplate := false
+	] ifFalse:[
+	    navigationState showMethodTemplate ifTrue:[
+		doShowMethodTemplate := self showMethodTemplate value
 "/                                    and:[ShowMethodTemplateWhenProtocolIsSelected == true
 "/                                         or:[ navigationState methodList size == 0 ]].
-            ]
-        ].
-        doShowMethodTemplate ifTrue:[
-            methods size > 1 ifTrue:[
-                code := nil.
-            ] ifFalse:[
-                code := self methodTemplate.
-            ].
-            self setAcceptActionForMethod.
-            self codeAspect:#method.
-            self showCode:code.
-        ] ifFalse:[
-            self hasProtocolSelected ifTrue:[
-                self showCode:''.
-                self setAcceptActionForMethod.
-                self codeAspect:#method.
-            ] ifFalse:[
-                selectedClass := self theSingleSelectedClass.
-                selectedClass notNil ifTrue:[
-                    self showClassAspect:(self codeAspect) forClass:selectedClass.
-                ] ifFalse:[
+	    ]
+	].
+	doShowMethodTemplate ifTrue:[
+	    methods size > 1 ifTrue:[
+		code := nil.
+	    ] ifFalse:[
+		code := self methodTemplate.
+	    ].
+	    self setAcceptActionForMethod.
+	    self codeAspect:#method.
+	    self showCode:code.
+	] ifFalse:[
+	    self hasProtocolSelected ifTrue:[
+		self showCode:''.
+		self setAcceptActionForMethod.
+		self codeAspect:#method.
+	    ] ifFalse:[
+		selectedClass := self theSingleSelectedClass.
+		selectedClass notNil ifTrue:[
+		    self showClassAspect:(self codeAspect) forClass:selectedClass.
+		] ifFalse:[
 "/                    self organizerMode value == OrganizerCanvas organizerModeProject ifTrue:[
 "/                        package := self theSingleSelectedProject.
 "/                        package notNil ifTrue:[
@@ -21634,54 +21955,54 @@
 "/                        self showCode:code ? ''.
 "/                        self setAcceptActionForProjectComment.
 "/                    ] ifFalse:[
-                        self showCode:code ? ''.
-                        self setAcceptActionForClass.
+			self showCode:code ? ''.
+			self setAcceptActionForClass.
 "/                    ]
-                ]
-            ]
-        ]
+		]
+	    ]
+	]
     ].
     self updateSpecialCodeEditorVisibility.
 
     codeView notNil ifTrue:[
-        "/ perform an auto-search, unless the user did some other search
-        "/ in the meanwhile (i.e. the codeViews searchPattern is different from the autoSearchPattern)
-        withAutoSearch ifTrue:[
-            codeView numberOfLines > 0 ifTrue:[
-                searchAction := navigationState autoSearchAction.
-                searchAction notNil ifTrue:[
-                    true "codeView searchAction isNil" ifTrue:[
-                        true "codeView searchPattern isNil" ifTrue:[
-                            codeView
-                                cursorHome;
-                                searchAction:searchAction;
-                                searchUsingSearchAction:#forward ifAbsent:nil.
-
-                          "/ The searchAction is mantained until a cut/replace or a search with a user selection is done
+	"/ perform an auto-search, unless the user did some other search
+	"/ in the meanwhile (i.e. the codeViews searchPattern is different from the autoSearchPattern)
+	withAutoSearch ifTrue:[
+	    codeView numberOfLines > 0 ifTrue:[
+		searchAction := navigationState autoSearchAction.
+		searchAction notNil ifTrue:[
+		    true "codeView searchAction isNil" ifTrue:[
+			true "codeView searchPattern isNil" ifTrue:[
+			    codeView
+				cursorHome;
+				searchAction:searchAction;
+				searchUsingSearchAction:#forward ifAbsent:nil.
+
+			  "/ The searchAction is mantained until a cut/replace or a search with a user selection is done
 "/                          codeView clearSearchAction.
-                        ]
+			]
 "/                    ] ifFalse:[
-"/                        codeView 
+"/                        codeView
 "/                            cursorHome;
 "/                            searchUsingSearchAction:#forward ifAbsent:nil
-                    ].
-                ] ifFalse:[
-                    searchPattern := navigationState autoSearchPattern.
-                    searchPattern notNil ifTrue:[
-                        searchPattern = codeView searchPattern ifTrue:[
-                            codeView 
-                                cursorHome; 
-                                cursorRight; "/ to avoid finding the selector
-                                searchFwd:searchPattern 
-                                    ignoreCase:(navigationState autoSearchIgnoreCase)
-                                    ifAbsent:[codeView cursorHome].
-                        ].
-                    ].
-                ].
-            ].
-        ] ifFalse:[
-            codeView clearSearchAction.
-        ].
+		    ].
+		] ifFalse:[
+		    searchPattern := navigationState autoSearchPattern.
+		    searchPattern notNil ifTrue:[
+			searchPattern = codeView searchPattern ifTrue:[
+			    codeView
+				cursorHome;
+				cursorRight; "/ to avoid finding the selector
+				searchFwd:searchPattern
+				    ignoreCase:(navigationState autoSearchIgnoreCase)
+				    ifAbsent:[codeView cursorHome].
+			].
+		    ].
+		].
+	    ].
+	] ifFalse:[
+	    codeView clearSearchAction.
+	].
     ].
 
     navigationState modified:false.
@@ -21697,19 +22018,19 @@
 
     var := self theSingleSelectedVariable.
     var isNil ifTrue:[
-        navigationState autoSearchAction:nil.
-        ^ self
+	navigationState autoSearchAction:nil.
+	^ self
     ].
 
     self selectedNonMetaclassesDo:[:eachClass |
-        |cls|
-
-        cls := eachClass whichClassDefinesClassVar:var.
-        cls notNil ifTrue:[
-            val := cls classVarAt:var asSymbol.
-            self showClassVarInfoFor:var in:cls value:val.
-            ^ self
-        ].
+	|cls|
+
+	cls := eachClass whichClassDefinesClassVar:var.
+	cls notNil ifTrue:[
+	    val := cls classVarAt:var asSymbol.
+	    self showClassVarInfoFor:var in:cls value:val.
+	    ^ self
+	].
     ].
 
     mclass := self classOfSelectedMethodOrSelectedClass.
@@ -21717,8 +22038,8 @@
 
     cls := mclass theNonMetaclass whichClassDefinesClassVar:var.
     cls notNil ifTrue:[
-        val := cls classVarAt:var asSymbol.
-        self showClassVarInfoFor:var in:cls value:val.
+	val := cls classVarAt:var asSymbol.
+	self showClassVarInfoFor:var in:cls value:val.
     ]
 
     "Modified: / 12-09-2006 / 13:56:20 / cg"
@@ -21726,66 +22047,66 @@
 
 enqueueDelayedCheckReallyModified
     ^ self
-        enqueueMessage:#delayedCheckReallyModified
-        for:self
-        arguments:#()
+	enqueueMessage:#delayedCheckReallyModified
+	for:self
+	arguments:#()
 
     "Modified: / 26.2.2000 / 18:01:49 / cg"
 !
 
 enqueueDelayedClassSelectionChange
     ^ self
-        enqueueMessage:#delayedClassSelectionChange
-        for:self
-        arguments:#()
+	enqueueMessage:#delayedClassSelectionChange
+	for:self
+	arguments:#()
 
     "Modified: / 26.2.2000 / 18:01:49 / cg"
 !
 
 enqueueDelayedLabelUpdate
     ^ self
-        enqueueMessage:#delayedLabelUpdate
-        for:self
-        arguments:#()
+	enqueueMessage:#delayedLabelUpdate
+	for:self
+	arguments:#()
 
     "Modified: / 26.2.2000 / 18:01:49 / cg"
 !
 
 enqueueDelayedMethodsSelectionChanged
     ^ self
-        enqueueMessage:#delayedMethodsSelectionChanged
-        for:self
-        arguments:#()
+	enqueueMessage:#delayedMethodsSelectionChanged
+	for:self
+	arguments:#()
 !
 
 enqueueDelayedProtocolSelectionChanged
     ^ self
-        enqueueMessage:#delayedProtocolSelectionChanged
-        for:self
-        arguments:#()
+	enqueueMessage:#delayedProtocolSelectionChanged
+	for:self
+	arguments:#()
 !
 
 enqueueDelayedStartSyntaxHighlightProcess
     ^ self
-        enqueueMessage:#startSyntaxHighlightProcess
-        for:self
-        arguments:#()
+	enqueueMessage:#startSyntaxHighlightProcess
+	for:self
+	arguments:#()
 !
 
 enqueueDelayedUpdateBufferLabel
     ^ self
-        enqueueMessage:#delayedUpdateBufferLabel
-        for:self
-        arguments:#()
+	enqueueMessage:#delayedUpdateBufferLabel
+	for:self
+	arguments:#()
 
     "Modified: / 26.2.2000 / 18:01:49 / cg"
 !
 
 enqueueDelayedUpdateBufferLabelWithCheckIfModified
     ^ self
-        enqueueMessage:#delayedUpdateBufferLabelWithCheckIfModified
-        for:self
-        arguments:#()
+	enqueueMessage:#delayedUpdateBufferLabelWithCheckIfModified
+	for:self
+	arguments:#()
 
     "Modified: / 26.2.2000 / 18:01:49 / cg"
 !
@@ -21793,9 +22114,9 @@
 enqueueDelayedUpdateCode
 ^ self delayedUpdateCode.
     ^ self
-        enqueueMessage:#delayedUpdateCode
-        for:self
-        arguments:#()
+	enqueueMessage:#delayedUpdateCode
+	for:self
+	arguments:#()
 
     "Modified: / 06-09-2006 / 19:07:15 / cg"
 !
@@ -21803,9 +22124,9 @@
 enqueueDelayedUpdateCodeWithAutoSearch
 "/ ^ self delayedUpdateCodeWithAutoSearch:true.
     ^ self
-        enqueueMessage:#delayedUpdateCodeWithAutoSearch:
-        for:self
-        arguments:#( true )
+	enqueueMessage:#delayedUpdateCodeWithAutoSearch:
+	for:self
+	arguments:#( true )
 
     "Modified: / 06-09-2006 / 19:07:10 / cg"
 !
@@ -21814,50 +22135,60 @@
 ^ self delayedUpdateCodeWithAutoSearch:false.
 
     ^ self
-        enqueueMessage:#delayedUpdateCodeWithAutoSearch:
-        for:self
-        arguments:#( false )
+	enqueueMessage:#delayedUpdateCodeWithAutoSearch:
+	for:self
+	arguments:#( false )
 
     "Modified: / 06-09-2006 / 19:07:00 / cg"
 !
 
 enqueueDelayedUpdateExecuteMethodVisibility
     ^ self
-        enqueueMessage:#updateExecuteMethodVisibility
-        for:self
-        arguments:#()
+	enqueueMessage:#updateExecuteMethodVisibility
+	for:self
+	arguments:#()
 
     "Modified: / 26.2.2000 / 18:01:49 / cg"
 !
 
+enqueueDelayedUpdateInitSharedPoolVisibility
+    ^ self
+	enqueueMessage:#updateInitSharedPoolVisibility
+	for:self
+	arguments:#()
+
+    "Modified: / 26-02-2000 / 18:01:49 / cg"
+    "Created: / 29-05-2012 / 10:26:41 / cg"
+!
+
 enqueueDelayedUpdateTestRunnerVisibility
     ^ self
-        enqueueMessage:#updateTestRunnerVisibility
-        for:self
-        arguments:#()
+	enqueueMessage:#updateTestRunnerVisibility
+	for:self
+	arguments:#()
 
     "Modified: / 26.2.2000 / 18:01:49 / cg"
 !
 
 enqueueDelayedVariableSelectionChanged
     ^ self
-        enqueueMessage:#delayedVariableSelectionChanged
-        for:self
-        arguments:#()
+	enqueueMessage:#delayedVariableSelectionChanged
+	for:self
+	arguments:#()
 !
 
 enqueueMessage:selector for:someone arguments:argList
 "/ Transcript show:'enqueue '; showCR:selector.
     self synchronousUpdate == true ifTrue:[
-        someone perform:selector withArguments:argList.
-        ^ self
+	someone perform:selector withArguments:argList.
+	^ self
     ].
     ^ super enqueueMessage:selector for:someone arguments:argList
 !
 
 methodsSelectionChanged
     (self theSingleSelectedMethod) notNil ifTrue:[
-        self rememberLocationInHistory
+	self rememberLocationInHistory
     ].
     self enqueueDelayedMethodsSelectionChanged.
 !
@@ -21889,41 +22220,41 @@
     selectedMethods := selectedMethods select:[:m | m selector notNil].
 
     selectedMethods isEmpty ifTrue:[
-        generator := #().
-        selectedMethods := #().
-    ] ifFalse:[
-        "/ fetch the searchBlock - what a tricky kludge (no, really this should be done different)
-        myGenerator := (navigationState selectorListGeneratorArrayAt:index) value.
-        myGeneratorsHome := myGenerator block methodHome.
-        mySearchBlock := myGeneratorsHome at:(myGeneratorsHome numArgs + 1).
-        mySearchBlock isBlock ifFalse:[
-            mySearchBlock := myGeneratorsHome at:(myGeneratorsHome numArgs + 2)
-        ].
-
-        generator := Iterator on:[:whatToDo |
-                                    |theMethodList|
-
-                                    theMethodList := IdentitySet new.
-                                    self withWaitCursorDo:[
-                                        selectedMethods do:[:selectedMethod |
-                                            theMethodList addAll:(mySearchBlock value:selectedMethod).
-                                        ]
-                                    ].
-                                    theMethodList do:[:aMethod |
-                                        whatToDo
-                                            value:aMethod mclass
-                                            value:aMethod category
-                                            value:aMethod selector
-                                            value:aMethod.
-                                    ].
-                                    "/ theMethodList size == 1 ifTrue:[
-                                        whatToDo
-                                            value:nil
-                                            value:nil
-                                            value:nil
-                                            value:nil.
-                                    "/ ].
-                              ].
+	generator := #().
+	selectedMethods := #().
+    ] ifFalse:[
+	"/ fetch the searchBlock - what a tricky kludge (no, really this should be done different)
+	myGenerator := (navigationState selectorListGeneratorArrayAt:index) value.
+	myGeneratorsHome := myGenerator block methodHome.
+	mySearchBlock := myGeneratorsHome at:(myGeneratorsHome numArgs + 1).
+	mySearchBlock isBlock ifFalse:[
+	    mySearchBlock := myGeneratorsHome at:(myGeneratorsHome numArgs + 2)
+	].
+
+	generator := Iterator on:[:whatToDo |
+				    |theMethodList|
+
+				    theMethodList := IdentitySet new.
+				    self withWaitCursorDo:[
+					selectedMethods do:[:selectedMethod |
+					    theMethodList addAll:(mySearchBlock value:selectedMethod).
+					]
+				    ].
+				    theMethodList do:[:aMethod |
+					whatToDo
+					    value:aMethod mclass
+					    value:aMethod category
+					    value:aMethod selector
+					    value:aMethod.
+				    ].
+				    "/ theMethodList size == 1 ifTrue:[
+					whatToDo
+					    value:nil
+					    value:nil
+					    value:nil
+					    value:nil.
+				    "/ ].
+			      ].
     ].
 
     "/ the selection used in the other code...
@@ -21931,7 +22262,7 @@
     self methodsSelectionChanged.
 
     index+1 to:4 do:[:i |
-        (navigationState selectorListGeneratorArrayAt:i) value:#().
+	(navigationState selectorListGeneratorArrayAt:i) value:#().
     ].
     (navigationState selectorListGeneratorArrayAt:(index+1)) value:generator.
 !
@@ -21985,9 +22316,9 @@
     "/ dont update codeView, as long as no protocol is selected
     ((codeAspect := self codeAspect) == #repositoryLog
     or:[codeAspect == #repositoryHistory]) ifTrue:[
-        self hasProtocolSelected ifFalse:[
-            ^ self
-        ]
+	self hasProtocolSelected ifFalse:[
+	    ^ self
+	]
     ].
     self enqueueDelayedProtocolSelectionChanged
 !
@@ -21997,14 +22328,14 @@
 
     ((m := self theSingleSelectedMethod) notNil
     and:[m mclass isNil]) ifTrue:[
-        "/ kludge: still showing old code, but a change should be on its
-        "/ way, coming from the MethodList.
-        "/ push back the event, to allow for the change event to be handled first.
-        self
-            enqueueMessage:#selectedEditorNoteBookTabIndexChanged2
-            for:self
-            arguments:#().
-        ^ self.
+	"/ kludge: still showing old code, but a change should be on its
+	"/ way, coming from the MethodList.
+	"/ push back the event, to allow for the change event to be handled first.
+	self
+	    enqueueMessage:#selectedEditorNoteBookTabIndexChanged2
+	    for:self
+	    arguments:#().
+	^ self.
     ].
     self selectedEditorNoteBookTabIndexChanged2.
 !
@@ -22026,99 +22357,100 @@
 "/    ].
 
     changedObject == self selectedClasses ifTrue:[
-        self assert:(changedObject value includes:nil) not.
+	self assert:(changedObject value includes:nil) not.
     ].
 
     changedObject == self codeInfoVisible ifTrue:[
-        self codeInfoVisibilityChanged.
-        ^ self
+	self codeInfoVisibilityChanged.
+	^ self
     ].
     changedObject == self toolBarVisibleHolder ifTrue:[
-        self toolBarVisibilityChanged.
-        ^ self
+	self toolBarVisibilityChanged.
+	^ self
     ].
 
     changedObject == self bookmarkBarVisibleHolder ifTrue:[
-        self bookmarkBarVisibilityChanged.
-        ^ self
+	self bookmarkBarVisibilityChanged.
+	^ self
     ].
 
     changedObject == self stringSearchToolVisibleHolder ifTrue:[
-        self stringSearchToolVisibilityChanged.
-        ^ self
+	self stringSearchToolVisibilityChanged.
+	^ self
     ].
     ((codeView := self codeView) notNil
      and:[changedObject == codeView modifiedChannel]) ifTrue:[
-        self codeModified.
-        ^ self.
+	self codeModified.
+	^ self.
     ].
     changedObject == self selectedEditorNoteBookTabIndexHolder ifTrue:[
-        self selectedEditorNoteBookTabIndexChanged.
-        ^ self
+	self selectedEditorNoteBookTabIndexChanged.
+	^ self
     ].
 
     changedObject == selectedBuffer ifTrue:[
-        self enqueueDelayedLabelUpdate.
-        self organizerModeForMenu changed.
-        self enqueueDelayedUpdateTestRunnerVisibility.
-        self enqueueDelayedUpdateExecuteMethodVisibility.
-        self updateCodeInfoAndStringSearchToolVisibility.
-        ^ self.
+	self enqueueDelayedLabelUpdate.
+	self organizerModeForMenu changed.
+	self enqueueDelayedUpdateTestRunnerVisibility.
+	self enqueueDelayedUpdateExecuteMethodVisibility.
+	self updateCodeInfoAndStringSearchToolVisibility.
+	self enqueueDelayedUpdateInitSharedPoolVisibility.
+	^ self.
     ].
     changedObject == self organizerModeForMenu ifTrue:[
-        self enqueueDelayedUpdateBufferLabel.
-        ^ self.
+	self enqueueDelayedUpdateBufferLabel.
+	^ self.
     ].
 
     something == #visitedClassHistory ifTrue:[
-        self visitedClassesHistory contents:(self class visitedClassNamesHistory).
-        ^ self.
+	self visitedClassesHistory contents:(self class visitedClassNamesHistory).
+	^ self.
     ].
 
     changedObject == Smalltalk ifTrue:[
-        codeAspect := self codeAspect.
-
-        isForAspect := (codeAspect == something)
-                       and:[ something == #classDefinition
-                             or:[ something == #classComment
-                             or:[ something == #classHierarchy
-                             or:[ something == #primitiveDefinitions
-                             or:[ something == #primitiveFunctions
-                             or:[ something == #primitiveVariables ]]]]]].
-
-        isForAspect ifTrue:[
-            ((self selectedClassesValue) contains:[:cls | cls name = aParameter name]) ifTrue:[
-                self enqueueDelayedUpdateCode.
-            ]
-        ].
-        something == #methodInClass ifTrue:[
-            self codeAspect == #method ifTrue:[
-                mthd := self theSingleSelectedMethod.
-               (mthd notNil and:[aParameter third == mthd])
-                ifTrue:[
-                    mthd mclass notNil ifTrue:[
-                        "/ mhmh - Smalltalk tells me that a method has changed,
-                        "/ but my selectedMethod has not yet been updated
-                        "/ (the methodList seems to be behind me in the dependency chain).
-                        "/ simply ignore this update here (assuming that the methodList will trigger
-                        "/ another change soon).
-                        self enqueueDelayedUpdateCodeWithoutAutoSearch.
-                    ].
-                ].
-            ]
-        ].
-
-        something == #methodTrap ifTrue:[
-            self hasMethodWithoutBreakPointSelectedHolder value:(self hasMethodWithoutBreakPointSelected).
-            self hasMethodWithBreakPointSelectedHolder value:(self hasMethodWithBreakPointSelected).
-        ].
-        ^ self
+	codeAspect := self codeAspect.
+
+	isForAspect := (codeAspect == something)
+		       and:[ something == #classDefinition
+			     or:[ something == #classComment
+			     or:[ something == #classHierarchy
+			     or:[ something == #primitiveDefinitions
+			     or:[ something == #primitiveFunctions
+			     or:[ something == #primitiveVariables ]]]]]].
+
+	isForAspect ifTrue:[
+	    ((self selectedClassesValue) contains:[:cls | cls name = aParameter name]) ifTrue:[
+		self enqueueDelayedUpdateCode.
+	    ]
+	].
+	something == #methodInClass ifTrue:[
+	    self codeAspect == #method ifTrue:[
+		mthd := self theSingleSelectedMethod.
+	       (mthd notNil and:[aParameter third == mthd])
+		ifTrue:[
+		    mthd mclass notNil ifTrue:[
+			"/ mhmh - Smalltalk tells me that a method has changed,
+			"/ but my selectedMethod has not yet been updated
+			"/ (the methodList seems to be behind me in the dependency chain).
+			"/ simply ignore this update here (assuming that the methodList will trigger
+			"/ another change soon).
+			self enqueueDelayedUpdateCodeWithoutAutoSearch.
+		    ].
+		].
+	    ]
+	].
+
+	something == #methodTrap ifTrue:[
+	    self hasMethodWithoutBreakPointSelectedHolder value:(self hasMethodWithoutBreakPointSelected).
+	    self hasMethodWithBreakPointSelectedHolder value:(self hasMethodWithBreakPointSelected).
+	].
+	^ self
     ].
 
     super update:something with:aParameter from:changedObject
 
     "Modified: / 15-11-2011 / 23:10:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 28-02-2012 / 16:51:27 / cg"
+    "Modified: / 29-05-2012 / 10:26:51 / cg"
 !
 
 updateBookmarkHolder
@@ -22142,56 +22474,67 @@
     cFrame isNil ifTrue:[^ self].
 
     cFrame notNil ifTrue:[
-        (stringSearchToolVisible not and:[codeInfoVisible not]) ifTrue:[
-            cBottomOffset := 0. 
-            sTopOffset := 0.
-            sBottomOffset := 0.
-        ].
-        (stringSearchToolVisible not and:[codeInfoVisible]) ifTrue:[
-            cBottomOffset := -25.    
-            sTopOffset := 0.
-            sBottomOffset := 0.
-        ].
-        (stringSearchToolVisible and:[codeInfoVisible not]) ifTrue:[
-            cBottomOffset := -25.    
-            sTopOffset := -24.
-            sBottomOffset := 0.
-        ].
-        (stringSearchToolVisible and:[codeInfoVisible]) ifTrue:[
-            cBottomOffset := -50.  
-            sTopOffset := -49.
-            sBottomOffset := -25.
-        ].
-        cFrame layout notNil ifTrue:[
-            cFrame layout bottomOffset:cBottomOffset.
-        ].
-        cFrame container notNil ifTrue:[
-            cFrame containerChangedSize.
-        ].
-        sFrame := self stringSearchToolView.
-
-        sFrame notNil ifTrue:[
-            sFrame layout notNil ifTrue:[
-                sTopOffset notNil ifTrue:[sFrame layout topOffset:sTopOffset].
-                sBottomOffset notNil ifTrue:[sFrame layout bottomOffset:sBottomOffset].
-                sFrame container notNil ifTrue:[
-                    sFrame containerChangedSize.
-                ].
-            ].
-        ].
+	(stringSearchToolVisible not and:[codeInfoVisible not]) ifTrue:[
+	    cBottomOffset := 0.
+	    sTopOffset := 0.
+	    sBottomOffset := 0.
+	].
+	(stringSearchToolVisible not and:[codeInfoVisible]) ifTrue:[
+	    cBottomOffset := -25.
+	    sTopOffset := 0.
+	    sBottomOffset := 0.
+	].
+	(stringSearchToolVisible and:[codeInfoVisible not]) ifTrue:[
+	    cBottomOffset := -25.
+	    sTopOffset := -24.
+	    sBottomOffset := 0.
+	].
+	(stringSearchToolVisible and:[codeInfoVisible]) ifTrue:[
+	    cBottomOffset := -50.
+	    sTopOffset := -49.
+	    sBottomOffset := -25.
+	].
+	cFrame layout notNil ifTrue:[
+	    cFrame layout bottomOffset:cBottomOffset.
+	].
+	cFrame container notNil ifTrue:[
+	    cFrame containerChangedSize.
+	].
+	sFrame := self stringSearchToolView.
+
+	sFrame notNil ifTrue:[
+	    sFrame layout notNil ifTrue:[
+		sTopOffset notNil ifTrue:[sFrame layout topOffset:sTopOffset].
+		sBottomOffset notNil ifTrue:[sFrame layout bottomOffset:sBottomOffset].
+		sFrame container notNil ifTrue:[
+		    sFrame containerChangedSize.
+		].
+	    ].
+	].
     ].
 !
 
 updateExecuteMethodVisibility
-    self hasNonTestCaseClassMethodWithoutArgsSelectedHolder 
-            value:(self hasNonTestCaseClassMethodWithoutArgsSelected)
+    self hasNonTestCaseClassMethodWithoutArgsSelectedHolder
+	    value:(self hasNonTestCaseClassMethodWithoutArgsSelected)
 
     "Modified: / 05-08-2006 / 13:22:53 / cg"
 !
 
+updateInitSharedPoolVisibility
+    self hasSharedPoolClassSelectedHolder
+	    value:(
+		(self selectedClasses value ? #()) contains:[:cls |
+			cls isLoaded
+			and:[(cls theNonMetaclass askFor:#isAbstract) not
+			and:[ cls theNonMetaclass inheritsFrom:SharedPool ]]])
+
+    "Created: / 29-05-2012 / 10:19:08 / cg"
+!
+
 updateLaunchApplicationVisibility
-    self hasStartableApplicationSelectedHolder 
-            value:(self hasStartableApplicationSelected)
+    self hasStartableApplicationSelectedHolder
+	    value:(self hasStartableApplicationSelected)
 !
 
 updateMetaToggleForClassSelection
@@ -22199,17 +22542,17 @@
 
     selectedClasses := self selectedNonMetaclasses.
     (selectedClasses contains:[:eachClass | eachClass isJavaClass]) ifTrue:[
-        "/ selection contains at least on java class
-        (selectedClasses conform:[:eachClass | eachClass isJavaClass]) ifTrue:[
-            "/ only java classes selected
-            newMetaToggleLabel := 'Static'.
-        ] ifFalse:[
-            "/ mixed ..
-            newMetaToggleLabel := 'Class / Static'.
-        ]
-    ] ifFalse:[
-        "/ only smalltalk classes selected
-        newMetaToggleLabel := 'Class'.
+	"/ selection contains at least on java class
+	(selectedClasses conform:[:eachClass | eachClass isJavaClass]) ifTrue:[
+	    "/ only java classes selected
+	    newMetaToggleLabel := 'Static'.
+	] ifFalse:[
+	    "/ mixed ..
+	    newMetaToggleLabel := 'Class / Static'.
+	]
+    ] ifFalse:[
+	"/ only smalltalk classes selected
+	newMetaToggleLabel := 'Class'.
     ].
     self navigationState metaToggleLabelHolder value:(resources string:newMetaToggleLabel)
 
@@ -22232,18 +22575,18 @@
     frame := self navigationState codePaneAndPluginView.
     frame ifNil:[^self].
     self showPlugin value ifTrue: [
-        pluginApp := BrowsletCanvas new.
-        pluginApp masterApplication: self.
-        pluginView := ApplicationSubView new client: pluginApp.
-        frame addSubView: pluginView.
-        frame relativeCorners: self navigationState codePaneAndPluginViewRelativeCorners.
+	pluginApp := BrowsletCanvas new.
+	pluginApp masterApplication: self.
+	pluginView := ApplicationSubView new client: pluginApp.
+	frame addSubView: pluginView.
+	frame relativeCorners: self navigationState codePaneAndPluginViewRelativeCorners.
     ] ifFalse: [
-        self navigationState codePaneAndPluginViewRelativeCorners: frame relativeCorners.
-        pluginView := frame subViews second.
-        pluginView destroy.
+	self navigationState codePaneAndPluginViewRelativeCorners: frame relativeCorners.
+	pluginView := frame subViews second.
+	pluginView destroy.
     ].
     frame resizeSubviews
-    
+
 
 
     "
@@ -22255,43 +22598,43 @@
     cFrame isNil ifTrue:[^ self].
 
     cFrame notNil ifTrue:[
-        (stringSearchToolVisible not and:[codeInfoVisible not]) ifTrue:[
-            cBottomOffset := 0. 
-            sTopOffset := 0.
-            sBottomOffset := 0.
-        ].
-        (stringSearchToolVisible not and:[codeInfoVisible]) ifTrue:[
-            cBottomOffset := -25.    
-            sTopOffset := 0.
-            sBottomOffset := 0.
-        ].
-        (stringSearchToolVisible and:[codeInfoVisible not]) ifTrue:[
-            cBottomOffset := -25.    
-            sTopOffset := -24.
-            sBottomOffset := 0.
-        ].
-        (stringSearchToolVisible and:[codeInfoVisible]) ifTrue:[
-            cBottomOffset := -50.  
-            sTopOffset := -49.
-            sBottomOffset := -25.
-        ].
-        cFrame layout notNil ifTrue:[
-            cFrame layout bottomOffset:cBottomOffset.
-        ].
-        cFrame container notNil ifTrue:[
-            cFrame containerChangedSize.
-        ].
-        sFrame := self stringSearchToolView.
-
-        sFrame notNil ifTrue:[
-            sFrame layout notNil ifTrue:[
-                sTopOffset notNil ifTrue:[sFrame layout topOffset:sTopOffset].
-                sBottomOffset notNil ifTrue:[sFrame layout bottomOffset:sBottomOffset].
-                sFrame container notNil ifTrue:[
-                    sFrame containerChangedSize.
-                ].
-            ].
-        ].
+	(stringSearchToolVisible not and:[codeInfoVisible not]) ifTrue:[
+	    cBottomOffset := 0.
+	    sTopOffset := 0.
+	    sBottomOffset := 0.
+	].
+	(stringSearchToolVisible not and:[codeInfoVisible]) ifTrue:[
+	    cBottomOffset := -25.
+	    sTopOffset := 0.
+	    sBottomOffset := 0.
+	].
+	(stringSearchToolVisible and:[codeInfoVisible not]) ifTrue:[
+	    cBottomOffset := -25.
+	    sTopOffset := -24.
+	    sBottomOffset := 0.
+	].
+	(stringSearchToolVisible and:[codeInfoVisible]) ifTrue:[
+	    cBottomOffset := -50.
+	    sTopOffset := -49.
+	    sBottomOffset := -25.
+	].
+	cFrame layout notNil ifTrue:[
+	    cFrame layout bottomOffset:cBottomOffset.
+	].
+	cFrame container notNil ifTrue:[
+	    cFrame containerChangedSize.
+	].
+	sFrame := self stringSearchToolView.
+
+	sFrame notNil ifTrue:[
+	    sFrame layout notNil ifTrue:[
+		sTopOffset notNil ifTrue:[sFrame layout topOffset:sTopOffset].
+		sBottomOffset notNil ifTrue:[sFrame layout bottomOffset:sBottomOffset].
+		sFrame container notNil ifTrue:[
+		    sFrame containerChangedSize.
+		].
+	    ].
+	].
     ].
     "
 
@@ -22305,6 +22648,27 @@
     "Modified: / 05-08-2006 / 13:22:53 / cg"
 !
 
+updateTextEditorBehavior
+    |languages spec|
+
+    spec := TextView defaultParenthesisSpecification.
+
+    languages := Set new.
+    (self selectedMethodsValue ? #()) do:[:each |
+	languages add:(each programmingLanguage).
+    ].
+    (self selectedClassesValue ? #()) do:[:each |
+	languages add:(each programmingLanguage).
+    ].
+
+    languages size == 1 ifTrue:[
+	spec := languages first parenthesisSpecificationForEditor.
+    ].
+    self codeView parenthesisSpecification:spec
+
+    "Created: / 01-06-2012 / 23:01:35 / cg"
+!
+
 variableSelectionChanged
     "variable selection changed by user interaction"
 
@@ -22329,12 +22693,12 @@
     spec := super flyByHelpSpec.
     changeSet := ChangeSet current.
     (changeSet findLast:[:chg | chg isMethodChange and:[chg changeClass notNil]]) ~~ 0 ifTrue:[
-        spec at:#recentChanges put:(spec at:#recentlyChangedMethods).
+	spec at:#recentChanges put:(spec at:#recentlyChangedMethods).
     ] ifFalse:[
 "/        (changeSet contains:[:chg | chg isClassChange and:[chg changeClass notNil]]) ifTrue:[
 "/            spec at:#recentChanges put:(spec at:#recentlyChangedClasses).
 "/        ] ifFalse:[
-            spec at:#recentChanges put:'Recently Changed'.
+	    spec at:#recentChanges put:'Recently Changed'.
 "/        ]
     ].
     ^ spec.
@@ -22372,16 +22736,16 @@
     "launch an enterBox for selector to search for"
 
     ^ self
-        askForMethodAndSpawnSearchTitle:'Selector to browse implementors of:\(TAB for completion; matchPattern allowed)'
-        browserLabel:'Implementors of %1'
-        searchWith:#( #'findImplementors:in:ignoreCase:match:' #'findImplementors:inMethods:ignoreCase:match:' )
-        searchWhat:#selector
-        searchArea:#everywhere
-        withCaseIgnore:true
-        withTextEntry:true
-        withMatch:true
-        withMethodList:true
-        setSearchPattern:nil
+	askForMethodAndSpawnSearchTitle:'Selector to browse implementors of:\(TAB for completion; matchPattern allowed)'
+	browserLabel:'Implementors of %1'
+	searchWith:#( #'findImplementors:in:ignoreCase:match:' #'findImplementors:inMethods:ignoreCase:match:' )
+	searchWhat:#selector
+	searchArea:#everywhere
+	withCaseIgnore:true
+	withTextEntry:true
+	withMatch:true
+	withMethodList:true
+	setSearchPattern:nil
 
     "Modified: / 17.11.2001 / 09:50:36 / cg"
 !
@@ -22392,25 +22756,25 @@
     selectors := self selectedMethodsValue collect:[:each | each selector].
 
     ^ self
-        askForMethodAndSpawnSearchTitle:'Browse Implementors of (any in selected):'
-        browserLabel:('Implementors (any of %1 selectors)' bindWith:selectors size)
-        searchWith:[:ignoredString :classes :ignoredCase :match|
-                        match ifTrue:[
-                            self class
-                                findImplementorsMatchingAny:selectors
-                                in:classes ignoreCase:false
-                        ] ifFalse:[
-                            self class
-                                findImplementorsOfAny:selectors
-                                in:classes ignoreCase:false
-                        ].
-                   ]
-        searchWhat:#selector
-        searchArea:#everywhere
-        withCaseIgnore:false
-        withTextEntry:false
-        withMethodList:false
-        setSearchPattern:nil
+	askForMethodAndSpawnSearchTitle:'Browse Implementors of (any in selected):'
+	browserLabel:('Implementors (any of %1 selectors)' bindWith:selectors size)
+	searchWith:[:ignoredString :classes :ignoredCase :match|
+			match ifTrue:[
+			    self class
+				findImplementorsMatchingAny:selectors
+				in:classes ignoreCase:false
+			] ifFalse:[
+			    self class
+				findImplementorsOfAny:selectors
+				in:classes ignoreCase:false
+			].
+		   ]
+	searchWhat:#selector
+	searchArea:#everywhere
+	withCaseIgnore:false
+	withTextEntry:false
+	withMethodList:false
+	setSearchPattern:nil
 
     "Modified: / 28-02-2012 / 16:14:55 / cg"
 !
@@ -22422,10 +22786,10 @@
 
     sel := self selectorToSearchFor.
     sel isEmptyOrNil ifTrue:[
-        "/ use last searchString
-        LastSearchPatterns size > 0 ifTrue:[
-            sel := LastSearchPatterns first.
-        ].
+	"/ use last searchString
+	LastSearchPatterns size > 0 ifTrue:[
+	    sel := LastSearchPatterns first.
+	].
     ].
     selectorHolder := sel asValue.
 
@@ -22436,38 +22800,38 @@
 
     inputField selectAllInitially.
     inputField entryCompletionBlock:[:contents |
-        |s what|
-
-        s := contents withoutSpaces.
-        box topView withWaitCursorDo:[
-            what := Smalltalk selectorCompletion:s.
-            inputField contents:what first.
-            (what at:2) size ~~ 1 ifTrue:[
-                self window beep
-            ]
-        ]
+	|s what|
+
+	s := contents withoutSpaces.
+	box topView withWaitCursorDo:[
+	    what := Smalltalk selectorCompletion:s.
+	    inputField contents:what first.
+	    (what at:2) size ~~ 1 ifTrue:[
+		self window beep
+	    ]
+	]
     ].
 
     true "withCaseIgnore" ifTrue:[
-        box addCheckBox:(resources string:'Ignore case') on:(caseHolder := false asValue).
+	box addCheckBox:(resources string:'Ignore case') on:(caseHolder := false asValue).
     ].
 
     true "allowBuffer" ifTrue:[
-        box addButton:(b := Button label:(resources string:'Add Buffer')).
-        b action:[
-           openHow := #newBuffer.
-           box doAccept.
-           box okPressed.
-        ].
+	box addButton:(b := Button label:(resources string:'Add Buffer')).
+	b action:[
+	   openHow := #newBuffer.
+	   box doAccept.
+	   box okPressed.
+	].
     ].
 
     true "allowBrowser" ifTrue:[
-        b := box addOkButtonLabelled:(resources string:'Browse').
-        b action:[
-           openHow := #newBrowser.
-           box doAccept.
-           box okPressed.
-        ].
+	b := box addOkButtonLabelled:(resources string:'Browse').
+	b action:[
+	   openHow := #newBrowser.
+	   box doAccept.
+	   box okPressed.
+	].
     ].
 
     box addAbortButton.
@@ -22476,13 +22840,13 @@
     box open.
 
     box accepted ifTrue:[
-        sel := selectorHolder value.
-
-        sel isEmpty ifTrue:[
-            self warn:'No selector entered for search'.
-            ^ self.
-        ].
-        self rememberSearchPattern:sel.
+	sel := selectorHolder value.
+
+	sel isEmpty ifTrue:[
+	    self warn:'No selector entered for search'.
+	    ^ self.
+	].
+	self rememberSearchPattern:sel.
     ].
 !
 
@@ -22490,38 +22854,38 @@
     "add a new buffer on all subclasses of an entered class"
 
     self
-        askForClassToSearch:nil
-        single:true
-        msgTail:' subclass of'
-        thenDo:[:classNameArg :single :doWhat |
-            |className class searchBlock|
-
-            className := classNameArg.
-            className = 'nil' ifTrue:[
-                searchBlock := [ Behavior allSubInstances select:[:cls | cls superclass isNil] ].
-            ] ifFalse:[
-                className includesMatchCharacters ifTrue:[
-                    className := self askForClassNameMatching:className.
-                ].
-                class := (Smalltalk classNamed:className) theNonMetaclass.
-                searchBlock := [ class allSubclasses ]
-            ].
-
-            self
-                spawnClassBrowserForSearch:searchBlock
-                spec:#multipleClassBrowserSpec
-                sortBy:nil in:#newBuffer label:('All Subclasses of ' , className)
-                autoSelectIfOne:true
-                callBack:[:brwsr |  ].
-        ]
+	askForClassToSearch:nil
+	single:true
+	msgTail:' subclass of'
+	thenDo:[:classNameArg :single :doWhat |
+	    |className class searchBlock|
+
+	    className := classNameArg.
+	    className = 'nil' ifTrue:[
+		searchBlock := [ Behavior allSubInstances select:[:cls | cls superclass isNil] ].
+	    ] ifFalse:[
+		className includesMatchCharacters ifTrue:[
+		    className := self askForClassNameMatching:className.
+		].
+		class := (Smalltalk classNamed:className) theNonMetaclass.
+		searchBlock := [ class allSubclasses ]
+	    ].
+
+	    self
+		spawnClassBrowserForSearch:searchBlock
+		spec:#multipleClassBrowserSpec
+		sortBy:nil in:#newBuffer label:('All Subclasses of ' , className)
+		autoSelectIfOne:true
+		callBack:[:brwsr |  ].
+	]
 !
 
 browseMenuApplicationClasses
     "add a new buffer on all application classes"
 
-    self 
-        browseMenuClassesForWhich:[:cls | cls isBrowserStartable] 
-        label: 'Applications'
+    self
+	browseMenuClassesForWhich:[:cls | cls isBrowserStartable]
+	label: 'Applications'
 
     "Modified: / 18-04-2012 / 16:20:54 / cg"
 !
@@ -22532,25 +22896,25 @@
     |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'
+			|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'
 !
 
 browseMenuClassExtensions
@@ -22572,30 +22936,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 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.
+	]
 !
 
 browseMenuClassExtensionsOpenAs:openHow
@@ -22603,10 +22967,10 @@
      (i.e. methods where the packageID is different from their classes packageID)"
 
     ^ self
-        browseMenuClassExtensionsFor:nil
-        in:Smalltalk allClasses
-        label:'All Class Extensions'
-        openAs:openHow
+	browseMenuClassExtensionsFor:nil
+	in:Smalltalk allClasses
+	label:'All Class Extensions'
+	openAs:openHow
 !
 
 browseMenuClassesDefiningVariable
@@ -22621,18 +22985,18 @@
     okText2 := 'Open'.      doWhat2 := #newBrowser.
     okText := 'Add Buffer'. doWhat := #newBuffer.
     navigationState isFullBrowser ifTrue:[
-        okText3 := 'Find'.       doWhat3 := nil.
+	okText3 := 'Find'.       doWhat3 := nil.
     ].
 
     allInstVariables := Set new.
     allClassVariables := Set new.
     allClassInstVariables := Set new.
     Smalltalk allClassesDo:[:cls |
-        cls isMeta ifFalse:[
-            allInstVariables addAll:(cls instVarNames).
-            allClassVariables addAll:(cls classVarNames).
-            allClassInstVariables addAll:(cls class instVarNames).
-        ].
+	cls isMeta ifFalse:[
+	    allInstVariables addAll:(cls instVarNames).
+	    allClassVariables addAll:(cls classVarNames).
+	    allClassInstVariables addAll:(cls class instVarNames).
+	].
     ].
     list := OrderedCollection new.
     list add:'---- Instance Variables ----'.
@@ -22651,14 +23015,14 @@
     box label:(resources string:'Browse or Search Variable').
     button2 := Button label:(resources string:okText2).
     okText3 notNil ifTrue:[
-        button3 := Button label:(resources string:okText3).
+	button3 := Button label:(resources string:okText3).
     ].
     (DialogBox defaultOKButtonAtLeft) ifFalse:[
-        box addButton:button2 before:(box okButton).
-        button3 notNil ifTrue:[box addButton:button3 before:button2].
+	box addButton:button2 before:(box okButton).
+	button3 notNil ifTrue:[box addButton:button3 before:button2].
     ] ifTrue:[
-        box addButton:button2 after:(box okButton).
-        button3 notNil ifTrue:[box addButton:button3 after:button2].
+	box addButton:button2 after:(box okButton).
+	button3 notNil ifTrue:[box addButton:button3 after:button2].
     ].
 
     button2 action:[
@@ -22667,61 +23031,61 @@
        box okPressed.
     ].
     button3 notNil ifTrue:[
-        button3 action:[
-                            doWhat := doWhat3.
-                            box doAccept.
-                            box okPressed.
-                        ].
+	button3 action:[
+			    doWhat := doWhat3.
+			    box doAccept.
+			    box okPressed.
+			].
     ].
 
     box entryCompletionBlock:[:contents |
-        |s what m|
-
-        s := contents withoutSpaces.
-        what := Smalltalk classnameCompletion:s.
-        box contents:what first.
-        (what at:2) size ~~ 1 ifTrue:[
-            self builder window beep
-        ].
-        box listView list:(list select:[:entry | s match:entry]).
+	|s what m|
+
+	s := contents withoutSpaces.
+	what := Smalltalk classnameCompletion:s.
+	box contents:what first.
+	(what at:2) size ~~ 1 ifTrue:[
+	    self builder window beep
+	].
+	box listView list:(list select:[:entry | s match:entry]).
     ].
 
     box action:[:aString | varNameString := aString].
     box showAtPointer.
 
     varNameString isEmptyOrNil ifTrue:[
-        ^ self   
-    ].
-
-    varNamesToSearch := varNameString asCollectionOfSubstringsSeparatedBy:$; .    
+	^ self
+    ].
+
+    varNamesToSearch := varNameString asCollectionOfSubstringsSeparatedBy:$; .
     (varNamesToSearch contains:[:varNameToSearch | varNameToSearch includesMatchCharacters]) ifTrue:[
-        checkFilterBlock := [:v | varNamesToSearch contains:[:varNameToSearch | varNameToSearch match:v]]
-    ] ifFalse:[
-        varNamesToSearch := varNamesToSearch asSet.
-        checkFilterBlock := [:v | varNamesToSearch includes:v]
+	checkFilterBlock := [:v | varNamesToSearch contains:[:varNameToSearch | varNameToSearch match:v]]
+    ] ifFalse:[
+	varNamesToSearch := varNamesToSearch asSet.
+	checkFilterBlock := [:v | varNamesToSearch includes:v]
     ].
 
     classes := Smalltalk allClasses select:[:cls |
-                    cls isMeta not
-                    and:[(cls instVarNames contains:checkFilterBlock)
-                         or:[(cls classVarNames contains:checkFilterBlock)
-                             or:[cls class instVarNames contains:checkFilterBlock]]]
-               ].
+		    cls isMeta not
+		    and:[(cls instVarNames contains:checkFilterBlock)
+			 or:[(cls classVarNames contains:checkFilterBlock)
+			     or:[cls class instVarNames contains:checkFilterBlock]]]
+	       ].
 
     classes size == 0 ifTrue:[
-        self information:'None found.'.
-        ^ self
+	self information:'None found.'.
+	^ self
     ].
     classes := classes asOrderedCollection sort:[:a :b | a name < b name].
 
     (doWhat == #newBrowser or:[ doWhat == #newBuffer ]) ifTrue:[
-        self spawnClassBrowserFor:classes in:doWhat.
-        ^ self
+	self spawnClassBrowserFor:classes in:doWhat.
+	^ self
     ].
 
     brwsr := self.
     doWhat == #newBuffer ifTrue:[
-        brwsr createBuffer.
+	brwsr createBuffer.
     ].
     brwsr selectClasses:classes.
 
@@ -22735,24 +23099,24 @@
     |searchBlock|
 
     searchBlock := [
-                        |classes|
-
-                        classes := OrderedCollection new.
-
-                        Smalltalk allClassesDo:[:eachClass |
-                            (aFilter value: eachClass) ifTrue:[
-                                classes add:eachClass
-                            ]
-                        ].
-                        classes
-                  ].
-
-    self
-        spawnClassBrowserForSearch:searchBlock
-        spec:#multipleClassBrowserSpec
-        sortBy:nil in:#newBuffer label:label
-        autoSelectIfOne:true
-        callBack:[:brwsr | brwsr classListApp markApplications:true ].
+			|classes|
+
+			classes := OrderedCollection new.
+
+			Smalltalk allClassesDo:[:eachClass |
+			    (aFilter value: eachClass) ifTrue:[
+				classes add:eachClass
+			    ]
+			].
+			classes
+		  ].
+
+    self
+	spawnClassBrowserForSearch:searchBlock
+	spec:#multipleClassBrowserSpec
+	sortBy:nil in:#newBuffer label:label
+	autoSelectIfOne:true
+	callBack:[:brwsr | brwsr classListApp markApplications:true ].
 
     "Modified: / 06-07-2011 / 14:05:37 / cg"
     "Created: / 18-04-2012 / 16:15:09 / cg"
@@ -22770,8 +23134,8 @@
      (i.e. that have been changed, but not yet checked into the source repository)"
 
     ^ self
-        browseMenuClassesInChangeSets:(ChangeSet allInstances)
-        label:'Changed classes in any changeSet' openAs:openHow
+	browseMenuClassesInChangeSets:(ChangeSet allInstances)
+	label:'Changed classes in any changeSet' openAs:openHow
 !
 
 browseMenuClassesInChangeSets:aSetOfChangeSets label:title openAs:openHow
@@ -22781,30 +23145,30 @@
     |searchBlock|
 
     searchBlock :=
-        [
-            |classes|
-
-            classes := IdentitySet new.
-
-            aSetOfChangeSets do:[:eachChangeSet |
-                eachChangeSet do:[:aChange |
-                    |cls|
-
-                    (aChange isMethodChange or:[aChange isClassChange]) ifTrue:[
-                        (cls := aChange changeClass) notNil ifTrue:[
-                            cls isRealNameSpace ifFalse:[
-                                cls := cls theNonMetaclass.
-                                classes add:cls.
-                                cls isPrivate ifTrue:[
-                                    classes add:cls owningClass
-                                ].
-                            ].
-                        ]
-                    ].
-                ].
-            ].
-            classes asOrderedCollection
-        ].
+	[
+	    |classes|
+
+	    classes := IdentitySet new.
+
+	    aSetOfChangeSets do:[:eachChangeSet |
+		eachChangeSet do:[:aChange |
+		    |cls|
+
+		    (aChange isMethodChange or:[aChange isClassChange]) ifTrue:[
+			(cls := aChange changeClass) notNil ifTrue:[
+			    cls isRealNameSpace ifFalse:[
+				cls := cls theNonMetaclass.
+				classes add:cls.
+				cls isPrivate ifTrue:[
+				    classes add:cls owningClass
+				].
+			    ].
+			]
+		    ].
+		].
+	    ].
+	    classes asOrderedCollection
+	].
 
     ^ self spawnClassBrowserForSearch:searchBlock sortBy:nil in:openHow label:title
 
@@ -22823,8 +23187,8 @@
      (i.e. that have been changed, but not yet checked into the source repository)"
 
     ^ self
-        browseMenuClassesInChangeSets:(Array with:ChangeSet current)
-        label:'Changed classes in current changeSet' openAs:openHow
+	browseMenuClassesInChangeSets:(Array with:ChangeSet current)
+	label:'Changed classes in current changeSet' openAs:openHow
 !
 
 browseMenuClassesOfRecentlyOpenedApplications
@@ -22841,14 +23205,14 @@
     |searchBlock|
 
     searchBlock :=
-        [
-            |appHistory|
-
-            appHistory := ApplicationModel recentlyOpenedApplications.
-            appHistory 
-                collect:[:nm | Smalltalk classNamed:nm]
-                as:OrderedCollection
-        ].
+	[
+	    |appHistory|
+
+	    appHistory := ApplicationModel recentlyOpenedApplications.
+	    appHistory
+		collect:[:nm | Smalltalk classNamed:nm]
+		as:OrderedCollection
+	].
 
     ^ self spawnClassBrowserForSearch:searchBlock sortBy:nil in:openHow label:'Recently opened applications'
 
@@ -22861,10 +23225,10 @@
     searchBlock := [ Smalltalk allClasses select:aFilterBlock ].
 
     ^ self
-        spawnClassBrowserForSearch:searchBlock
-        sortBy:nil
-        in:#newBuffer
-        label:aLabelString
+	spawnClassBrowserForSearch:searchBlock
+	sortBy:nil
+	in:#newBuffer
+	label:aLabelString
 !
 
 browseMenuClassesWithNameMatching
@@ -22885,8 +23249,8 @@
     okText2 := 'Open'.        doWhat2 := #newBrowser.
     okText := 'Add Buffer'. doWhat := #newBuffer.
     navigationState isFullBrowser ifTrue:[
-        title := 'Browse/search classes with string in comment/documentation (matchPattern allowed):'.
-        okText3 := 'Find'.       doWhat3 := nil.
+	title := 'Browse/search classes with string in comment/documentation (matchPattern allowed):'.
+	okText3 := 'Find'.       doWhat3 := nil.
     ].
 
     box := EnterBox new.
@@ -22896,14 +23260,14 @@
     box label:(resources string:'Search for documentation string').
     button2 := Button label:(resources string:okText2).
     okText3 notNil ifTrue:[
-        button3 := Button label:(resources string:okText3).
+	button3 := Button label:(resources string:okText3).
     ].
     (DialogBox defaultOKButtonAtLeft) ifFalse:[
-        box addButton:button2 before:(box okButton).
-        button3 notNil ifTrue:[box addButton:button3 before:button2].
+	box addButton:button2 before:(box okButton).
+	button3 notNil ifTrue:[box addButton:button3 before:button2].
     ] ifTrue:[
-        box addButton:button2 after:(box okButton).
-        button3 notNil ifTrue:[box addButton:button3 after:button2].
+	box addButton:button2 after:(box okButton).
+	button3 notNil ifTrue:[box addButton:button3 after:button2].
     ].
 
     button2 action:[
@@ -22912,72 +23276,72 @@
        box okPressed.
     ].
     button3 notNil ifTrue:[
-        button3 action:[
-                            doWhat := doWhat3.
-                            box doAccept.
-                            box okPressed.
-                        ].
+	button3 action:[
+			    doWhat := doWhat3.
+			    box doAccept.
+			    box okPressed.
+			].
     ].
 
     box action:[:aString | stringToSearch := aString].
     box showAtPointer.
 
     stringToSearch isNil ifTrue:[
-        ^ self
+	^ self
     ].
 
     withMatch := stringToSearch includesMatchCharacters.
     withMatch ifTrue:[
-        stringToSearch := '*' , stringToSearch , '*'
+	stringToSearch := '*' , stringToSearch , '*'
     ].
 
     self withWaitCursorDo:[
-        classes := Smalltalk allClasses select:[:cls |
-                        |s m found|
-
-                        (cls isLoaded and:[cls isMeta not]) ifTrue:[
-                            self activityNotification:('searching %1 ...' bindWith:cls name).
-                            found := false.
-                            (s := cls comment) notNil ifTrue:[
-                                withMatch ifTrue:[
-                                    found := stringToSearch match:s
-                                ] ifFalse:[
-                                    found := s includesString:stringToSearch
-                                ]
-                            ].
-                            (m := cls theMetaclass compiledMethodAt:#documentation) notNil
-                            ifTrue:[
-                                s := m source ? ''.
-                                withMatch ifTrue:[
-                                    found := stringToSearch match:s
-                                ] ifFalse:[
-                                    found := s includesString:stringToSearch
-                                ]
-
-                            ]
-                       ].
-                    ].
-        classes := classes asOrderedCollection.
+	classes := Smalltalk allClasses select:[:cls |
+			|s m found|
+
+			(cls isLoaded and:[cls isMeta not]) ifTrue:[
+			    self activityNotification:('searching %1 ...' bindWith:cls name).
+			    found := false.
+			    (s := cls comment) notNil ifTrue:[
+				withMatch ifTrue:[
+				    found := stringToSearch match:s
+				] ifFalse:[
+				    found := s includesString:stringToSearch
+				]
+			    ].
+			    (m := cls theMetaclass compiledMethodAt:#documentation) notNil
+			    ifTrue:[
+				s := m source ? ''.
+				withMatch ifTrue:[
+				    found := stringToSearch match:s
+				] ifFalse:[
+				    found := s includesString:stringToSearch
+				]
+
+			    ]
+		       ].
+		    ].
+	classes := classes asOrderedCollection.
     ].
     self activityNotification:nil.
 
     classes size == 0 ifTrue:[
-        self information:'None found.'.
-        ^ self
+	self information:'None found.'.
+	^ self
     ].
 
     doWhat == #newBrowser ifTrue:[
-        ^ self spawnClassBrowserFor:classes in:#newBrowser
+	^ self spawnClassBrowserFor:classes in:#newBrowser
 "/        brwsr := self class new.
 "/        brwsr open.
     ] ifFalse:[
-        doWhat == #newBuffer ifTrue:[
-            ^ self spawnClassBrowserFor:classes in:#newBuffer
-        ].
-        brwsr := self.
-        doWhat == #newBuffer ifTrue:[
-            brwsr createBuffer.
-        ]
+	doWhat == #newBuffer ifTrue:[
+	    ^ self spawnClassBrowserFor:classes in:#newBuffer
+	].
+	brwsr := self.
+	doWhat == #newBuffer ifTrue:[
+	    brwsr createBuffer.
+	]
     ].
     brwsr selectClasses:classes.
 
@@ -23025,16 +23389,16 @@
 '.
 
     LastClassFilterBlockString isNil ifTrue:[
-        LastClassFilterBlockString := template.
+	LastClassFilterBlockString := template.
     ].
 
     textHolder := ValueHolder new.
     dialog := Dialog
-                 forRequestText:(resources string:'Enter filterBlock')
-                 lines:25
-                 columns:70
-                 initialAnswer:LastClassFilterBlockString
-                 model:textHolder.
+		 forRequestText:(resources string:'Enter filterBlock')
+		 lines:25
+		 columns:70
+		 initialAnswer:LastClassFilterBlockString
+		 model:textHolder.
     dialog addButton:(Button label:'Template' action:[textHolder value:template. textHolder changed:#value.]).
     dialog open.
     dialog accepted ifFalse:[^ self].
@@ -23055,8 +23419,8 @@
 
     sourceCodeManager := Smalltalk at: #CVSSourceCodeManager.
     sourceCodeManager isNil ifTrue: [
-        Dialog warn: 'CVS Source Code Manager is not available'.
-        ^ self.
+	Dialog warn: 'CVS Source Code Manager is not available'.
+	^ self.
     ].
     ^ self browseMenuClassesWithoutRepositoryContainerFor:sourceCodeManager
 
@@ -23067,16 +23431,16 @@
     |searchBlock|
 
     searchBlock :=
-            [|classes|
-
-            classes := self findClassesWithoutClassMethod:#copyright.
-            classes := classes reject:[:each | each isPrivate].
-            classes].
-    self
-        spawnClassBrowserForSearch:searchBlock
-        sortBy:nil
-        in:#newBuffer
-        label:'Classes without copyright'
+	    [|classes|
+
+	    classes := self findClassesWithoutClassMethod:#copyright.
+	    classes := classes reject:[:each | each isPrivate].
+	    classes].
+    self
+	spawnClassBrowserForSearch:searchBlock
+	sortBy:nil
+	in:#newBuffer
+	label:'Classes without copyright'
 
     "Modified: / 11-07-2010 / 16:42:04 / cg"
 !
@@ -23085,8 +23449,8 @@
     |searchBlock|
 
     searchBlock := [
-                        self findClassesWithoutClassMethod:#documentation
-                   ].
+			self findClassesWithoutClassMethod:#documentation
+		   ].
 
     self spawnClassBrowserForSearch:searchBlock sortBy:nil in:#newBuffer label:'Classes without documentation'
 !
@@ -23096,14 +23460,14 @@
 
     searchBlock := [    |classes|
 
-                        classes := self findClassesWithoutClassMethod:#examples.
-                        classes 
-                            select:[:each | 
-                                        (each isPrivate not
-                                            or:[classes includes:each owningClass])
-                                        and:[ (each isSubclassOf:Exception) not ]
-                            ].
-                   ].
+			classes := self findClassesWithoutClassMethod:#examples.
+			classes
+			    select:[:each |
+					(each isPrivate not
+					    or:[classes includes:each owningClass])
+					and:[ (each isSubclassOf:Exception) not ]
+			    ].
+		   ].
 
     self spawnClassBrowserForSearch:searchBlock sortBy:nil in:#newBuffer label:'Classes without examples'
 
@@ -23116,20 +23480,20 @@
     nameOfVersionMethodInClasses := aSourceCodeManager nameOfVersionMethodInClasses.
 
     searchBlock := [
-                        |classesWithVersion classesWithVersionSVN classesWithoutBoth|
-
-                        classesWithVersion := self findClassesWithoutClassMethod:#version.
-                        classesWithVersion := classesWithVersion reject:[:each | each isPrivate].
-                        classesWithVersionSVN := self findClassesWithoutClassMethod: nameOfVersionMethodInClasses.
-                        classesWithVersionSVN := classesWithVersionSVN select:[:each | each isPrivate not].
-                        classesWithoutBoth := classesWithVersion asSet intersect: classesWithVersionSVN.
-                   ].
-
-    ^ self 
-        spawnClassBrowserForSearch:searchBlock 
-        sortBy:nil 
-        in:#newBuffer 
-        label:(resources string:'Classes without %1 repository container' with:aSourceCodeManager managerTypeName)
+			|classesWithVersion classesWithVersionSVN classesWithoutBoth|
+
+			classesWithVersion := self findClassesWithoutClassMethod:#version.
+			classesWithVersion := classesWithVersion reject:[:each | each isPrivate].
+			classesWithVersionSVN := self findClassesWithoutClassMethod: nameOfVersionMethodInClasses.
+			classesWithVersionSVN := classesWithVersionSVN select:[:each | each isPrivate not].
+			classesWithoutBoth := classesWithVersion asSet intersect: classesWithVersionSVN.
+		   ].
+
+    ^ self
+	spawnClassBrowserForSearch:searchBlock
+	sortBy:nil
+	in:#newBuffer
+	label:(resources string:'Classes without %1 repository container' with:aSourceCodeManager managerTypeName)
 
     "Created: / 19-04-2011 / 11:51:38 / cg"
 !
@@ -23139,8 +23503,8 @@
 
     sourceCodeManager := Smalltalk at: #SVNSourceCodeManager.
     sourceCodeManager isNil ifTrue: [
-        Dialog warn: 'SVN Source Code Manager is not available'.
-        ^ self.
+	Dialog warn: 'SVN Source Code Manager is not available'.
+	^ self.
     ].
     ^ self browseMenuClassesWithoutRepositoryContainerFor:sourceCodeManager
 
@@ -23151,9 +23515,9 @@
     |browser categoryListApp|
 
     self window sensor shiftDown ifTrue:[
-        "/ temporary: allow old browser to be used
-        SystemBrowser openInClass:(self theSingleSelectedClass) selector:(self theSingleSelectedSelector).
-        ^ self
+	"/ temporary: allow old browser to be used
+	SystemBrowser openInClass:(self theSingleSelectedClass) selector:(self theSingleSelectedSelector).
+	^ self
     ].
 
     "/ do not use self class new here - to avoid using obsolete classes instances
@@ -23164,9 +23528,9 @@
     browser window extent:(self window extent).
 
     self currentNamespace ~~ Smalltalk ifTrue:[
-        (categoryListApp := browser categoryListApp) notNil ifTrue:[
-            categoryListApp nameSpaceFilter value:(self navigationState selectedNamespaces value copy)
-        ].
+	(categoryListApp := browser categoryListApp) notNil ifTrue:[
+	    categoryListApp nameSpaceFilter value:(self navigationState selectedNamespaces value copy)
+	].
     ].
 
     browser openWindow.
@@ -23178,19 +23542,19 @@
 
 browseMenuDeprecatedMethods
     ^ self
-        askForMethodAndSpawnSearchTitle:'Search for Deprecated Methods in:'
-        browserLabel:(LabelAndIcon icon:(self class menuIcon) string:'Deprecated Methods')
-        searchWith:[:classes | self class findMethodsIn:classes where:[:c :m :sel | m isObsolete]]
-        searchArea:(self defaultSearchArea)
+	askForMethodAndSpawnSearchTitle:'Search for Deprecated Methods in:'
+	browserLabel:(LabelAndIcon icon:(self class menuIcon) string:'Deprecated Methods')
+	searchWith:[:classes | self class findMethodsIn:classes where:[:c :m :sel | m isObsolete]]
+	searchArea:(self defaultSearchArea)
 !
 
 browseMenuHTTPServiceClasses
     "add a new buffer on all web service classes"
 
-    self 
-        browseMenuClassesForWhich:[:cls | cls isBrowserStartable
-                                          and:[cls inheritsFrom:HTTPService]] 
-        label: 'Web Services'
+    self
+	browseMenuClassesForWhich:[:cls | cls isBrowserStartable
+					  and:[cls inheritsFrom:HTTPService]]
+	label: 'Web Services'
 
     "Created: / 20-07-2007 / 10:02:14 / cg"
 !
@@ -23216,36 +23580,36 @@
     |searchBlock|
 
     searchBlock := [
-                        |methods methodsInOrder|
-
-                        aSetOfChangeSets do:[:eachChangeSet |
-                            methods := IdentitySet new.
-                            methodsInOrder := OrderedCollection new.
-
-                            eachChangeSet reverseDo:[:aChange |
-                                |cls selector method|
-
-                                (aChange isMethodChange) ifTrue:[
-                                    (cls := aChange changeClass) notNil ifTrue:[
-                                        method := cls compiledMethodAt:aChange selector.
-                                        method notNil ifTrue:[
-                                            (methods includes:method) ifFalse:[
-                                                methods add:method.
-                                                methodsInOrder add:method.
-                                            ]
-                                        ]
-                                    ]
-                                ].
-                            ].
-                        ].
-                        methodsInOrder
-                  ].
-
-    ^ self
-        spawnMethodBrowserForSearch:searchBlock
-        sortBy:false "#class"
-        in:openHow
-        label:'Changed methods'
+			|methods methodsInOrder|
+
+			aSetOfChangeSets do:[:eachChangeSet |
+			    methods := IdentitySet new.
+			    methodsInOrder := OrderedCollection new.
+
+			    eachChangeSet reverseDo:[:aChange |
+				|cls selector method|
+
+				(aChange isMethodChange) ifTrue:[
+				    (cls := aChange changeClass) notNil ifTrue:[
+					method := cls compiledMethodAt:aChange selector.
+					method notNil ifTrue:[
+					    (methods includes:method) ifFalse:[
+						methods add:method.
+						methodsInOrder add:method.
+					    ]
+					]
+				    ]
+				].
+			    ].
+			].
+			methodsInOrder
+		  ].
+
+    ^ self
+	spawnMethodBrowserForSearch:searchBlock
+	sortBy:false "#class"
+	in:openHow
+	label:'Changed methods'
 !
 
 browseMenuMethodsInCurrentChangeSet
@@ -23277,19 +23641,19 @@
 "/    ].
 
     self
-        askForMethodAndSpawnSearchTitle:'Code to Search:'
-        browserLabel:'Methods containing code'
-        searchWith:#( #'findCode:in:isMethod:' #'findCode:inMethods:isMethod:' )
-        searchWhat:#code
-        searchArea:whereDefault
-        withCaseIgnore:false
-        withTextEntry:true
-        withMethodList:true
-        setSearchPattern:[:brwsr :codePattern :isMethodSearch :doMatch|
-                            isMethodSearch ifFalse:[
-                                brwsr autoSearchCodePattern:codePattern
-                            ]
-                         ]
+	askForMethodAndSpawnSearchTitle:'Code to Search:'
+	browserLabel:'Methods containing code'
+	searchWith:#( #'findCode:in:isMethod:' #'findCode:inMethods:isMethod:' )
+	searchWhat:#code
+	searchArea:whereDefault
+	withCaseIgnore:false
+	withTextEntry:true
+	withMethodList:true
+	setSearchPattern:[:brwsr :codePattern :isMethodSearch :doMatch|
+			    isMethodSearch ifFalse:[
+				brwsr autoSearchCodePattern:codePattern
+			    ]
+			 ]
 !
 
 browseMenuMethodsWithExceptionHandlers
@@ -23300,15 +23664,15 @@
     whereDefault := SearchDialog lastCodeSearchArea ? #everywhere.
 
     self
-        askForMethodAndSpawnSearchTitle:'Search Exception Raisers:'
-        browserLabel:'Methods containing Exception Raisers'
-        searchWith:#( #'findExceptionHandlersIn:' #'findExceptionHandlersInMethods:' )
-        searchWhat:nil
-        searchArea:whereDefault
-        withCaseIgnore:false
-        withTextEntry:false
-        withMethodList:true
-        setSearchPattern:[:brwsr :codePattern :isMethodSearch :doMatch | ]
+	askForMethodAndSpawnSearchTitle:'Search Exception Raisers:'
+	browserLabel:'Methods containing Exception Raisers'
+	searchWith:#( #'findExceptionHandlersIn:' #'findExceptionHandlersInMethods:' )
+	searchWhat:nil
+	searchArea:whereDefault
+	withCaseIgnore:false
+	withTextEntry:false
+	withMethodList:true
+	setSearchPattern:[:brwsr :codePattern :isMethodSearch :doMatch | ]
 
     "Created: / 11-05-2010 / 14:19:27 / cg"
 !
@@ -23321,15 +23685,15 @@
     whereDefault := SearchDialog lastCodeSearchArea ? #everywhere.
 
     self
-        askForMethodAndSpawnSearchTitle:'Search Exception Raisers:'
-        browserLabel:'Methods containing Exception Raisers'
-        searchWith:#( #'findExceptionRaisersIn:' #'findExceptionRaisersInMethods:' )
-        searchWhat:nil
-        searchArea:whereDefault
-        withCaseIgnore:false
-        withTextEntry:false
-        withMethodList:true
-        setSearchPattern:[:brwsr :codePattern :isMethodSearch :doMatch | ]
+	askForMethodAndSpawnSearchTitle:'Search Exception Raisers:'
+	browserLabel:'Methods containing Exception Raisers'
+	searchWith:#( #'findExceptionRaisersIn:' #'findExceptionRaisersInMethods:' )
+	searchWhat:nil
+	searchArea:whereDefault
+	withCaseIgnore:false
+	withTextEntry:false
+	withMethodList:true
+	setSearchPattern:[:brwsr :codePattern :isMethodSearch :doMatch | ]
 
     "Created: / 11-05-2010 / 14:19:14 / cg"
 !
@@ -23339,81 +23703,81 @@
 
     whereDefault := self defaultSearchArea.
     ^ self
-        askForMethodAndSpawnSearchTitle:'Search for Methods with Library Calls (FFI):'
-        browserLabel:'Library Calls (FFI)'
-        searchWith:[:classes |
-                       self class
-                            findMethodsIn:classes
-                            where:[:cls :mthd :sel |
-                                        mthd isExternalLibraryFunctionCall
-                                  ]
-                   ]
-        searchArea:whereDefault
+	askForMethodAndSpawnSearchTitle:'Search for Methods with Library Calls (FFI):'
+	browserLabel:'Library Calls (FFI)'
+	searchWith:[:classes |
+		       self class
+			    findMethodsIn:classes
+			    where:[:cls :mthd :sel |
+					mthd isExternalLibraryFunctionCall
+				  ]
+		   ]
+	searchArea:whereDefault
 !
 
 browseMenuMethodsWithHelpSpec
     "launch an enterBox for area to search in"
 
     ^ self
-        askForMethodAndSpawnSearchTitle:'Search for help texts (helpSpec methods) in:'
-        browserLabel:(LabelAndIcon icon:(self class menuIcon) string:'Help')
-        searchWith:[:classes | self class findResource:#(help) in:classes]
-        searchArea:(self defaultSearchArea)
+	askForMethodAndSpawnSearchTitle:'Search for help texts (helpSpec methods) in:'
+	browserLabel:(LabelAndIcon icon:(self class menuIcon) string:'Help')
+	searchWith:[:classes | self class findResource:#(help) in:classes]
+	searchArea:(self defaultSearchArea)
 !
 
 browseMenuMethodsWithImageSpec
     "launch an enterBox for area to search in"
 
     ^ self
-        askForMethodAndSpawnSearchTitle:'Search for images (imageSpec methods) in:'
-        browserLabel:(LabelAndIcon icon:(self class imageIcon) string:'Images')  " 'Images' "
-        searchWith:[:classes | self class findResource:#(image fileImage) in:classes]
-        searchArea:(self defaultSearchArea)
+	askForMethodAndSpawnSearchTitle:'Search for images (imageSpec methods) in:'
+	browserLabel:(LabelAndIcon icon:(self class imageIcon) string:'Images')  " 'Images' "
+	searchWith:[:classes | self class findResource:#(image fileImage) in:classes]
+	searchArea:(self defaultSearchArea)
 !
 
 browseMenuMethodsWithLeftoverDebugCode
     |whereDefault codeStrings matcher|
 
     codeStrings  :=
-        #(
-                'Transcript `@msg: `@args'
-                '`@any halt'
-                'true ifTrue: `@stuff'
-                'true ifFalse: `@stuff'
-                'false ifTrue: `@stuff'
-                'false ifFalse: `@stuff'
-                '`@any handle:[] do:`@anyBlock'
-                '`@any handle:[:ex | ] do:`@anyBlock'
-                '`@any needsWork'
-                '#needsWork'
-                '#todo'
-        ).
+	#(
+		'Transcript `@msg: `@args'
+		'`@any halt'
+		'true ifTrue: `@stuff'
+		'true ifFalse: `@stuff'
+		'false ifTrue: `@stuff'
+		'false ifFalse: `@stuff'
+		'`@any handle:[] do:`@anyBlock'
+		'`@any handle:[:ex | ] do:`@anyBlock'
+		'`@any needsWork'
+		'#needsWork'
+		'#todo'
+	).
 
     matcher := ParseTreeSearcher new.
     matcher matchesAnyOf: codeStrings do: [:aNode :answer | aNode].
 
     whereDefault := self defaultSearchArea.
     ^ self
-        askForMethodAndSpawnSearchTitle:'Search for methods with possible leftOver debug code in:'
-        browserLabel:'Methods with leftOver debug code'
-        searchWith:[:classes |
-                       self class
-                            findMethodsIn:classes
-                            where:[:cls :mthd :sel |
-                                        self method:mthd selector:sel inClass:cls matchesParseTreeMatcher:matcher
-                                  ]
-                   ]
-        searchArea:whereDefault
+	askForMethodAndSpawnSearchTitle:'Search for methods with possible leftOver debug code in:'
+	browserLabel:'Methods with leftOver debug code'
+	searchWith:[:classes |
+		       self class
+			    findMethodsIn:classes
+			    where:[:cls :mthd :sel |
+					self method:mthd selector:sel inClass:cls matchesParseTreeMatcher:matcher
+				  ]
+		   ]
+	searchArea:whereDefault
 !
 
 browseMenuMethodsWithMenuSpec
     "launch an enterBox for area to search in"
 
     ^ self
-        askForMethodAndSpawnSearchTitle:'Search for menus (menuSpec methods) in:'
-        browserLabel:(LabelAndIcon icon:(self class menuIcon) string:'Menus') "'Menus'"
-        searchWith:[:classes | self class findResource:#(menu programMenu) in:classes]
-        searchArea:(self defaultSearchArea)
+	askForMethodAndSpawnSearchTitle:'Search for menus (menuSpec methods) in:'
+	browserLabel:(LabelAndIcon icon:(self class menuIcon) string:'Menus') "'Menus'"
+	searchWith:[:classes | self class findResource:#(menu programMenu) in:classes]
+	searchArea:(self defaultSearchArea)
 !
 
 browseMenuMethodsWithPrimitiveCode
@@ -23421,34 +23785,34 @@
 
     whereDefault := self defaultSearchArea.
     ^ self
-        askForMethodAndSpawnSearchTitle:'Search for Methods with Primitive Code:'
-        browserLabel:'Primitive Code'
-        searchWith:[:classes |
-                       self class
-                            findMethodsIn:classes
-                            where:[:cls :mthd :sel |
-                                        mthd hasPrimitiveCode
-                                  ]
-                   ]
-        searchArea:whereDefault
+	askForMethodAndSpawnSearchTitle:'Search for Methods with Primitive Code:'
+	browserLabel:'Primitive Code'
+	searchWith:[:classes |
+		       self class
+			    findMethodsIn:classes
+			    where:[:cls :mthd :sel |
+					mthd hasPrimitiveCode
+				  ]
+		   ]
+	searchArea:whereDefault
 !
 
 browseMenuMethodsWithResource
     "launch an enterBox for area to search in"
 
     ^ self
-        askForMethodAndSpawnSearchTitle:'Search for Resource Methods:\\Resource (empty for any; matchpattern allowed)'
-        browserLabel:'Resources'
-        searchWith:[:resourceOrEmpty :classes :ignoreCase :doMatch |
-            self class findResource:resourceOrEmpty match:doMatch ignoreCase:ignoreCase in:classes
-        ]
-        searchWhat:#resource
-        searchArea:(self defaultSearchArea)
-        withCaseIgnore:true
-        withTextEntry:true
-        withMatch:true
-        withMethodList:false
-        setSearchPattern:nil
+	askForMethodAndSpawnSearchTitle:'Search for Resource Methods:\\Resource (empty for any; matchpattern allowed)'
+	browserLabel:'Resources'
+	searchWith:[:resourceOrEmpty :classes :ignoreCase :doMatch |
+	    self class findResource:resourceOrEmpty match:doMatch ignoreCase:ignoreCase in:classes
+	]
+	searchWhat:#resource
+	searchArea:(self defaultSearchArea)
+	withCaseIgnore:true
+	withTextEntry:true
+	withMatch:true
+	withMethodList:false
+	setSearchPattern:nil
 
 "/    ^ self
 "/        askForMethodAndSpawnSearchTitle:'Search for resource methods in:'
@@ -23465,30 +23829,30 @@
     |whereDefault|
 
     self isMethodListBrowser ifTrue:[
-        whereDefault := SearchDialog constantForListOfMethodsArea.
-    ] ifFalse:[
-        whereDefault := SearchDialog lastStringSearchArea ? self defaultSearchArea.
-
-        whereDefault == #classes ifTrue:[
-            (self hasAnyMethodSelectedForWhich:[:m | m mclass notNil and:[m mclass isPrivate]])
-            ifTrue:[
-                whereDefault := #ownersWithPrivateClasses
-            ]
-        ].
-    ].
-
-    self
-        askForMethodAndSpawnSearchTitle:'String to Search for in Sources:'
-        browserLabel:'Methods containing "%1"'
-        searchWith:#( #'findString:in:ignoreCase:match:' #'findString:inMethods:ignoreCase:match:' )
-        searchWhat:#string
-        searchArea:whereDefault
-        withCaseIgnore:true
-        withTextEntry:true
-        withMethodList:true
-        setSearchPattern:[:brwsr :string :ignoreCase :doMatch|
-                            brwsr autoSearchPattern:string ignoreCase:ignoreCase.
-                         ]
+	whereDefault := SearchDialog constantForListOfMethodsArea.
+    ] ifFalse:[
+	whereDefault := SearchDialog lastStringSearchArea ? self defaultSearchArea.
+
+	whereDefault == #classes ifTrue:[
+	    (self hasAnyMethodSelectedForWhich:[:m | m mclass notNil and:[m mclass isPrivate]])
+	    ifTrue:[
+		whereDefault := #ownersWithPrivateClasses
+	    ]
+	].
+    ].
+
+    self
+	askForMethodAndSpawnSearchTitle:'String to Search for in Sources:'
+	browserLabel:'Methods containing "%1"'
+	searchWith:#( #'findString:in:ignoreCase:match:' #'findString:inMethods:ignoreCase:match:' )
+	searchWhat:#string
+	searchArea:whereDefault
+	withCaseIgnore:true
+	withTextEntry:true
+	withMethodList:true
+	setSearchPattern:[:brwsr :string :ignoreCase :doMatch|
+			    brwsr autoSearchPattern:string ignoreCase:ignoreCase.
+			 ]
 
     "Modified: / 28-02-2012 / 16:40:11 / cg"
 !
@@ -23500,20 +23864,20 @@
 
     whereDefault := self defaultSearchArea.
     whereDefault == #classes ifTrue:[
-        (self hasAnyMethodSelectedForWhich:[:m | m mclass isPrivate]) ifTrue:[
-            whereDefault := #ownersWithPrivateClasses
-        ]
-    ].
-    self
-        askForMethodAndSpawnSearchTitle:'String to search for in help spec methods:'
-        browserLabel:'HelpSpec Methods containing "%1"'
-        searchWith:#findHelpSpecMethodsWithString:in:ignoreCase:match:
-        searchWhat:#string
-        searchArea:whereDefault
-        withCaseIgnore:true
-        setSearchPattern:[:brwsr :string :ignoreCase :doMatch|
-                            brwsr autoSearchPattern:string ignoreCase:ignoreCase.
-                         ]
+	(self hasAnyMethodSelectedForWhich:[:m | m mclass isPrivate]) ifTrue:[
+	    whereDefault := #ownersWithPrivateClasses
+	]
+    ].
+    self
+	askForMethodAndSpawnSearchTitle:'String to search for in help spec methods:'
+	browserLabel:'HelpSpec Methods containing "%1"'
+	searchWith:#findHelpSpecMethodsWithString:in:ignoreCase:match:
+	searchWhat:#string
+	searchArea:whereDefault
+	withCaseIgnore:true
+	setSearchPattern:[:brwsr :string :ignoreCase :doMatch|
+			    brwsr autoSearchPattern:string ignoreCase:ignoreCase.
+			 ]
 
     "Modified: / 28-02-2012 / 16:40:37 / cg"
 !
@@ -23525,20 +23889,20 @@
 
     whereDefault := self defaultSearchArea.
     whereDefault == #classes ifTrue:[
-        (self hasAnyMethodSelectedForWhich:[:m | m mclass isPrivate]) ifTrue:[
-            whereDefault := #ownersWithPrivateClasses
-        ]
-    ].
-    self
-        askForMethodAndSpawnSearchTitle:'String to search for in menu spec methods:'
-        browserLabel:'MenuSpec Methods containing "%1"'
-        searchWith:#'findMenuSpecMethodsWithString:in:ignoreCase:match:'
-        searchWhat:#string
-        searchArea:whereDefault
-        withCaseIgnore:true
-        setSearchPattern:[:brwsr :string :ignoreCase :doMatch|
-                            brwsr autoSearchPattern:string ignoreCase:ignoreCase.
-                         ]
+	(self hasAnyMethodSelectedForWhich:[:m | m mclass isPrivate]) ifTrue:[
+	    whereDefault := #ownersWithPrivateClasses
+	]
+    ].
+    self
+	askForMethodAndSpawnSearchTitle:'String to search for in menu spec methods:'
+	browserLabel:'MenuSpec Methods containing "%1"'
+	searchWith:#'findMenuSpecMethodsWithString:in:ignoreCase:match:'
+	searchWhat:#string
+	searchArea:whereDefault
+	withCaseIgnore:true
+	setSearchPattern:[:brwsr :string :ignoreCase :doMatch|
+			    brwsr autoSearchPattern:string ignoreCase:ignoreCase.
+			 ]
 
     "Modified: / 28-02-2012 / 16:40:54 / cg"
 !
@@ -23558,27 +23922,27 @@
 "/    ].
 
     self
-        askForMethodAndSpawnSearchTitle:'Search Matchstring in Literal-Strings:'
-        browserLabel:'Methods with Literal-String Matching'
-        searchWith:#( #'findStringLiteral:in:ignoreCase:match:' #'findStringLiteral:inMethods:ignoreCase:match:' )
-        searchWhat:#string
-        searchArea:whereDefault
-        withCaseIgnore:true
-        withTextEntry:true
-        withMethodList:true
-        setSearchPattern:[:brwsr :string :ignoreCase :doMatch|
-                            brwsr autoSearchPattern:string ignoreCase:ignoreCase.
-                         ]
+	askForMethodAndSpawnSearchTitle:'Search Matchstring in Literal-Strings:'
+	browserLabel:'Methods with Literal-String Matching'
+	searchWith:#( #'findStringLiteral:in:ignoreCase:match:' #'findStringLiteral:inMethods:ignoreCase:match:' )
+	searchWhat:#string
+	searchArea:whereDefault
+	withCaseIgnore:true
+	withTextEntry:true
+	withMethodList:true
+	setSearchPattern:[:brwsr :string :ignoreCase :doMatch|
+			    brwsr autoSearchPattern:string ignoreCase:ignoreCase.
+			 ]
 !
 
 browseMenuMethodsWithTableSpec
     "launch an enterBox for area to search in"
 
     ^ self
-        askForMethodAndSpawnSearchTitle:'Search for tableSpec methods in:'
-        browserLabel:(LabelAndIcon icon:(self class menuIcon) string:'TableSpecs')
-        searchWith:[:classes | self class findResource:#(tableColumns) in:classes]
-        searchArea:(self defaultSearchArea)
+	askForMethodAndSpawnSearchTitle:'Search for tableSpec methods in:'
+	browserLabel:(LabelAndIcon icon:(self class menuIcon) string:'TableSpecs')
+	searchWith:[:classes | self class findResource:#(tableColumns) in:classes]
+	searchArea:(self defaultSearchArea)
 !
 
 browseMenuMethodsWithUglyCodingStyle
@@ -23586,19 +23950,19 @@
 
     whereDefault := self defaultSearchArea.
     ^ self
-        askForMethodAndSpawnSearchTitle:'Search for methods with ugly coding style in:'
-        browserLabel:'Methods with ugly coding style'
-        searchWith:[:classes |
-                       self class
-                            findMethodsIn:classes
-                            where:[:cls :mthd :sel |
-                                        |note|
-
-                                        note := self methodHasUglyCodingStyle:mthd selector:sel inClass:cls.
-                                        note notNil
-                                  ]
-                   ]
-        searchArea:whereDefault
+	askForMethodAndSpawnSearchTitle:'Search for methods with ugly coding style in:'
+	browserLabel:'Methods with ugly coding style'
+	searchWith:[:classes |
+		       self class
+			    findMethodsIn:classes
+			    where:[:cls :mthd :sel |
+					|note|
+
+					note := self methodHasUglyCodingStyle:mthd selector:sel inClass:cls.
+					note notNil
+				  ]
+		   ]
+	searchArea:whereDefault
 !
 
 browseMenuMethodsWithUserFilter
@@ -23672,17 +24036,17 @@
 '.
 
     LastMethodFilterBlockString isNil ifTrue:[
-        LastMethodFilterBlockString := template.
+	LastMethodFilterBlockString := template.
     ].
 
     textHolder := ValueHolder new.
     dialog := Dialog
-                 forRequestText:(resources string:'Enter filterBlock')
-                 editViewClass:CodeView
-                 lines:25
-                 columns:70
-                 initialAnswer:LastMethodFilterBlockString
-                 model:textHolder.
+		 forRequestText:(resources string:'Enter filterBlock')
+		 editViewClass:CodeView
+		 lines:25
+		 columns:70
+		 initialAnswer:LastMethodFilterBlockString
+		 model:textHolder.
     dialog addButton:(Button label:'Template' action:[textHolder value:template. textHolder changed:#value.]).
     dialog open.
     dialog accepted ifFalse:[^ self].
@@ -23691,11 +24055,11 @@
     LastMethodFilterBlockString := filterBlockString.
 
     dummyMethod := Compiler
-                         compile:('dummy ^' , filterBlockString)
-                         forClass:UndefinedObject
-                         inCategory:nil
-                         notifying:nil
-                         install:false.
+			 compile:('dummy ^' , filterBlockString)
+			 forClass:UndefinedObject
+			 inCategory:nil
+			 notifying:nil
+			 install:false.
 
 "/    filterBlock := Parser evaluate:filterBlockString.
 "/    filterBlock isBlock ifFalse:[
@@ -23703,20 +24067,20 @@
     (dummyMethod isMethod not
     or:[(filterBlock := dummyMethod valueWithReceiver:nil arguments:nil) isBlock not])
     ifTrue:[
-        self error:'bad input'.
-        ^ self
+	self error:'bad input'.
+	^ self
     ].
 
     whereDefault := self defaultSearchArea.
     self
-        askForMethodAndSpawnSearchTitle:'Search for methods in:'
-        browserLabel:'Method-Search'
-        searchWith:[:classes |
-                       self class
-                            findMethodsIn:classes
-                            where:[:cls :mthd :sel | filterBlock value:cls value:mthd value:sel ]
-                   ]
-        searchArea:whereDefault.
+	askForMethodAndSpawnSearchTitle:'Search for methods in:'
+	browserLabel:'Method-Search'
+	searchWith:[:classes |
+		       self class
+			    findMethodsIn:classes
+			    where:[:cls :mthd :sel | filterBlock value:cls value:mthd value:sel ]
+		   ]
+	searchArea:whereDefault.
 
     "Created: / 18.8.2000 / 21:26:37 / cg"
     "Modified: / 18.8.2000 / 21:58:31 / cg"
@@ -23729,10 +24093,10 @@
 
     whereDefault := self defaultSearchArea.
     ^ self
-        askForMethodAndSpawnSearchTitle:'Search for GUI specs (windowSpec methods) in:'
-        browserLabel:(LabelAndIcon icon:(self class canvasIcon) string:'UISpecs') "'UISpecs'"
-        searchWith:[:classes | self class findResource:#canvas in:classes]
-        searchArea:whereDefault
+	askForMethodAndSpawnSearchTitle:'Search for GUI specs (windowSpec methods) in:'
+	browserLabel:(LabelAndIcon icon:(self class canvasIcon) string:'UISpecs') "'UISpecs'"
+	searchWith:[:classes | self class findResource:#canvas in:classes]
+	searchArea:whereDefault
 !
 
 browseMenuMethodsWithWrap
@@ -23740,8 +24104,8 @@
      (i.e. that have a break, trace or watchPoint)"
 
     self
-        spawnMethodBrowserForSearch:[ MessageTracer allWrappedMethods ]
-        sortBy:#class in:#newBuffer label:'Wrapped methods'
+	spawnMethodBrowserForSearch:[ MessageTracer allWrappedMethods ]
+	sortBy:#class in:#newBuffer label:'Wrapped methods'
 !
 
 browseMenuMethodsWithoutComment
@@ -23751,17 +24115,17 @@
 
     whereDefault := self defaultSearchArea.
     ^ self
-        askForMethodAndSpawnSearchTitle:'Search for methods without comment in:'
-        browserLabel:'Methods without comment'
-        searchWith:[:classes |
-                       self class
-                            findMethodsIn:classes
-                            where:[:cls :mthd :sel |
-                                        (cls isMeta not or:[(AbstractSourceCodeManager isVersionMethodSelector:sel) not])
-                                        and:[ mthd comment size == 0 ]
-                                  ]
-                   ]
-        searchArea:whereDefault
+	askForMethodAndSpawnSearchTitle:'Search for methods without comment in:'
+	browserLabel:'Methods without comment'
+	searchWith:[:classes |
+		       self class
+			    findMethodsIn:classes
+			    where:[:cls :mthd :sel |
+					(cls isMeta not or:[(AbstractSourceCodeManager isVersionMethodSelector:sel) not])
+					and:[ mthd comment size == 0 ]
+				  ]
+		   ]
+	searchArea:whereDefault
 !
 
 browseMenuOpenInClass
@@ -23772,23 +24136,23 @@
     |searchBlock|
 
     searchBlock := [
-                        |defaultId methods methodsInOrder|
-
-                        methods := OrderedCollection new.
-
-                        Smalltalk allMethodsDo:[:mthd |
-                            mthd previousVersion notNil ifTrue:[
-                                methods add:mthd.
-                            ].
-                        ].
-                        methods
-                  ].
-
-    ^ self
-        spawnMethodBrowserForSearch:searchBlock
-        sortBy:#class
-        in:openHow
-        label:'Changed Methods'
+			|defaultId methods methodsInOrder|
+
+			methods := OrderedCollection new.
+
+			Smalltalk allMethodsDo:[:mthd |
+			    mthd previousVersion notNil ifTrue:[
+				methods add:mthd.
+			    ].
+			].
+			methods
+		  ].
+
+    ^ self
+	spawnMethodBrowserForSearch:searchBlock
+	sortBy:#class
+	in:openHow
+	label:'Changed Methods'
 !
 
 browseMenuRecentChanges
@@ -23807,135 +24171,135 @@
 
     labelHolder := 'Methods referring to global ''%1''' asValue.
     self
-        askForMethodAndSpawnSearchTitle:'Global to search:\(TAB for completion; matchPattern allowed)'
-        browserLabel:labelHolder
-        searchWith:[:string :classes :dummyIgnoreCase :dummyMatch|
-                        |globlNames globlNamesAndSymbols globlName sym baseName matchBlock realClasses val
-                         keysReferringToValue otherKeysReferringToValue msg searchAll|
-
-                        globlNames := string withoutSeparators asCollectionOfSubstringsSeparatedByAny:',;| '.
-                        globlNames size > 1 ifTrue:[
-                            globlNames := globlNames collect:[:nm | nm asSymbol].
-                            matchBlock := [:cls :mthd :sel |
-                                            |mSource usedGlobals|
-
-                                            mthd isLazyMethod ifTrue:[
-                                                mSource := mthd source.
-
-                                                (mSource notNil
-                                                and:[(globlNames contains:[:nm |
-                                                        (mSource includesString:nm)
-                                                        and:[
-                                                           usedGlobals isNil ifTrue:[ usedGlobals := mthd usedGlobals].
-                                                           usedGlobals includes:nm
-                                                        ]])]).
-                                            ] ifFalse:[
-                                                globlNames contains:[:nm |
-                                                        (mthd referencesLiteral:nm)
-                                                        and:[
-                                                           usedGlobals isNil ifTrue:[ usedGlobals := mthd usedGlobals].
-                                                           usedGlobals includes:nm
-                                                        ]].
-                                            ]
-                                          ]
-                        ] ifFalse:[
-                            globlName := globlNames first.
-                            globlName knownAsSymbol ifFalse:[
-                                globlName includesMatchCharacters ifFalse:[
-                                    ^ self warn:'No such global (''' , globlName , ''')'.
-                                ].
-                                matchBlock := [:cls :mthd :sel |
-                                                (mthd literals contains:[:lit | globlName match:lit])
-                                                 and:[mthd usedGlobals contains:[:lit | globlName match:lit] ]
-                                              ]
-                            ] ifTrue:[
-                                searchAll := false.
-                                sym := globlName asSymbol.
-
-                                val := globlName lastIndexOf:$:.
-                                val ~~ 0 ifTrue:[
-                                    baseName := (globlName copyFrom:val+1) asSymbol.
-                                ] ifFalse:[
-                                    baseName := sym.
-                                ].
-                                (val := Smalltalk at:sym) isBehavior ifTrue:[
-                                    otherKeysReferringToValue := OrderedCollection new.
-                                    Smalltalk keysAndValuesDo:[:k :v | v == val ifTrue:[
-                                                                           k ~~ sym ifTrue:[
-                                                                               otherKeysReferringToValue add:k
-                                                                           ]
-                                                                       ]
-                                                              ].
-                                    otherKeysReferringToValue size > 0 ifTrue:[
-                                        keysReferringToValue := otherKeysReferringToValue copyWith:sym.
-                                        otherKeysReferringToValue size == 1 ifTrue:[
-                                            msg := '''%1'' also refers to that value. Search these references too ?'.
-                                            searchAllLabel := 'Methods referring to ''%1'' or ''%2''' bindWithArguments:keysReferringToValue.
-                                        ] ifFalse:[
-                                            searchAllLabel := 'Methods referring to the value of ''%1'''.
-                                            otherKeysReferringToValue size <= 3 ifTrue:[
-                                                msg := (otherKeysReferringToValue copyWithoutLast:1) asStringWith:', '.
-                                                msg := msg , ' and ' , otherKeysReferringToValue last.
-                                                msg := msg , ' also refer to that value. Search those references too ?'.
-                                            ] ifFalse:[
-                                                msg := 'There are %2 other globals referring to that value. Search those references too ?'.
-                                            ]
-                                        ].
-                                        alreadyAsked isNil ifTrue:[
-                                            searchAll := Dialog
-                                                            confirmWithCancel:(msg bindWith:otherKeysReferringToValue first with:otherKeysReferringToValue size)
-                                                            default:true.
-                                            searchAll isNil ifTrue:[^ self].
-                                            alreadyAsked := searchAll.
-                                        ] ifFalse:[
-                                            searchAll := alreadyAsked.
-                                        ].
-                                    ]
-                                ].
-                                searchAll ifTrue:[
-                                    labelHolder value:searchAllLabel.
-                                    matchBlock := [:cls :mthd :sel |
-                                                    "/ kludge: Lazy methods do not include symbols in the literal array - sigh
-                                                    mthd isLazyMethod ifTrue:[
-                                                        (mthd usedGlobals includesAny:keysReferringToValue)
-                                                    ] ifFalse:[
-                                                        (keysReferringToValue contains:[:globl | mthd refersToLiteral:globl])
-                                                        and:[mthd usedGlobals includesAny:keysReferringToValue]
-                                                    ]
-                                                  ]
-                                ] ifFalse:[
-                                    matchBlock := [:cls :mthd :sel | |mSource|
-                                                    "/ kludge: Lazy methods do not include symbols in the literal array - sigh
-                                                    mthd isLazyMethod ifTrue:[
-                                                        mSource := mthd source.
-                                                        (mSource notNil
-                                                        and:[(mSource includesString:baseName)
-                                                        and:[mthd usedGlobals includes:sym]])
-                                                    ] ifFalse:[
-                                                        (((mthd referencesLiteral:baseName) or:[baseName ~~ sym and:[mthd referencesLiteral:sym]])
-                                                         and:[mthd usedGlobals includes:sym])
-                                                    ]
-                                                  ]
-                                ]
-                           ].
-                       ].
-                       "/ recollect realClasses from names (in case of class-changes)
-                       realClasses := classes collect:[:eachClass | Smalltalk at:eachClass name].
-                       self class
-                               findMethodsIn:realClasses
-                               where:matchBlock
-                   ]
-        searchWhat:#globalName
-        searchArea:#everywhere
-        withCaseIgnore:false
-        setSearchPattern:[:brwsr :string :ignoreCase :doMatch|
-                            |globlNames|
-
-                            globlNames := string withoutSeparators asCollectionOfSubstringsSeparatedByAny:',;| '.
-                            brwsr autoSearchVariables:globlNames.
-
-                            "/ brwsr autoSearchPattern:string ignoreCase:ignoreCase.
-                         ]
+	askForMethodAndSpawnSearchTitle:'Global to search:\(TAB for completion; matchPattern allowed)'
+	browserLabel:labelHolder
+	searchWith:[:string :classes :dummyIgnoreCase :dummyMatch|
+			|globlNames globlNamesAndSymbols globlName sym baseName matchBlock realClasses val
+			 keysReferringToValue otherKeysReferringToValue msg searchAll|
+
+			globlNames := string withoutSeparators asCollectionOfSubstringsSeparatedByAny:',;| '.
+			globlNames size > 1 ifTrue:[
+			    globlNames := globlNames collect:[:nm | nm asSymbol].
+			    matchBlock := [:cls :mthd :sel |
+					    |mSource usedGlobals|
+
+					    mthd isLazyMethod ifTrue:[
+						mSource := mthd source.
+
+						(mSource notNil
+						and:[(globlNames contains:[:nm |
+							(mSource includesString:nm)
+							and:[
+							   usedGlobals isNil ifTrue:[ usedGlobals := mthd usedGlobals].
+							   usedGlobals includes:nm
+							]])]).
+					    ] ifFalse:[
+						globlNames contains:[:nm |
+							(mthd referencesLiteral:nm)
+							and:[
+							   usedGlobals isNil ifTrue:[ usedGlobals := mthd usedGlobals].
+							   usedGlobals includes:nm
+							]].
+					    ]
+					  ]
+			] ifFalse:[
+			    globlName := globlNames first.
+			    globlName knownAsSymbol ifFalse:[
+				globlName includesMatchCharacters ifFalse:[
+				    ^ self warn:'No such global (''' , globlName , ''')'.
+				].
+				matchBlock := [:cls :mthd :sel |
+						(mthd literals contains:[:lit | globlName match:lit])
+						 and:[mthd usedGlobals contains:[:lit | globlName match:lit] ]
+					      ]
+			    ] ifTrue:[
+				searchAll := false.
+				sym := globlName asSymbol.
+
+				val := globlName lastIndexOf:$:.
+				val ~~ 0 ifTrue:[
+				    baseName := (globlName copyFrom:val+1) asSymbol.
+				] ifFalse:[
+				    baseName := sym.
+				].
+				(val := Smalltalk at:sym) isBehavior ifTrue:[
+				    otherKeysReferringToValue := OrderedCollection new.
+				    Smalltalk keysAndValuesDo:[:k :v | v == val ifTrue:[
+									   k ~~ sym ifTrue:[
+									       otherKeysReferringToValue add:k
+									   ]
+								       ]
+							      ].
+				    otherKeysReferringToValue size > 0 ifTrue:[
+					keysReferringToValue := otherKeysReferringToValue copyWith:sym.
+					otherKeysReferringToValue size == 1 ifTrue:[
+					    msg := '''%1'' also refers to that value. Search these references too ?'.
+					    searchAllLabel := 'Methods referring to ''%1'' or ''%2''' bindWithArguments:keysReferringToValue.
+					] ifFalse:[
+					    searchAllLabel := 'Methods referring to the value of ''%1'''.
+					    otherKeysReferringToValue size <= 3 ifTrue:[
+						msg := (otherKeysReferringToValue copyWithoutLast:1) asStringWith:', '.
+						msg := msg , ' and ' , otherKeysReferringToValue last.
+						msg := msg , ' also refer to that value. Search those references too ?'.
+					    ] ifFalse:[
+						msg := 'There are %2 other globals referring to that value. Search those references too ?'.
+					    ]
+					].
+					alreadyAsked isNil ifTrue:[
+					    searchAll := Dialog
+							    confirmWithCancel:(msg bindWith:otherKeysReferringToValue first with:otherKeysReferringToValue size)
+							    default:true.
+					    searchAll isNil ifTrue:[^ self].
+					    alreadyAsked := searchAll.
+					] ifFalse:[
+					    searchAll := alreadyAsked.
+					].
+				    ]
+				].
+				searchAll ifTrue:[
+				    labelHolder value:searchAllLabel.
+				    matchBlock := [:cls :mthd :sel |
+						    "/ kludge: Lazy methods do not include symbols in the literal array - sigh
+						    mthd isLazyMethod ifTrue:[
+							(mthd usedGlobals includesAny:keysReferringToValue)
+						    ] ifFalse:[
+							(keysReferringToValue contains:[:globl | mthd refersToLiteral:globl])
+							and:[mthd usedGlobals includesAny:keysReferringToValue]
+						    ]
+						  ]
+				] ifFalse:[
+				    matchBlock := [:cls :mthd :sel | |mSource|
+						    "/ kludge: Lazy methods do not include symbols in the literal array - sigh
+						    mthd isLazyMethod ifTrue:[
+							mSource := mthd source.
+							(mSource notNil
+							and:[(mSource includesString:baseName)
+							and:[mthd usedGlobals includes:sym]])
+						    ] ifFalse:[
+							(((mthd referencesLiteral:baseName) or:[baseName ~~ sym and:[mthd referencesLiteral:sym]])
+							 and:[mthd usedGlobals includes:sym])
+						    ]
+						  ]
+				]
+			   ].
+		       ].
+		       "/ recollect realClasses from names (in case of class-changes)
+		       realClasses := classes collect:[:eachClass | Smalltalk at:eachClass name].
+		       self class
+			       findMethodsIn:realClasses
+			       where:matchBlock
+		   ]
+	searchWhat:#globalName
+	searchArea:#everywhere
+	withCaseIgnore:false
+	setSearchPattern:[:brwsr :string :ignoreCase :doMatch|
+			    |globlNames|
+
+			    globlNames := string withoutSeparators asCollectionOfSubstringsSeparatedByAny:',;| '.
+			    brwsr autoSearchVariables:globlNames.
+
+			    "/ brwsr autoSearchPattern:string ignoreCase:ignoreCase.
+			 ]
 
     "Modified: / 5.11.2001 / 14:19:22 / cg"
 !
@@ -23944,58 +24308,58 @@
     "launch an enterBox for symbol to search for"
 
     self
-        askForMethodAndSpawnSearchTitle:'Symbol to search:'
-        browserLabel:'Methods referring to #''%1'''
-        searchWith:[:string :classes :dummyIgnoreCase :dummyMatch|
-                        |sym stringToSearch searchBlock|
-
-                        stringToSearch := string.
-                        (string startsWith:'#') ifTrue:[
-                            stringToSearch := Symbol readFrom:string.
-                            Dialog information:'Searching for ',stringToSearch
-                        ].
-
-                        (sym := stringToSearch asSymbolIfInterned) notNil ifTrue:[
-                            searchBlock := [:cls :mthd :sel | |mSource|
-                                                "/ kludge: stc does not include symbols in the literal array - sigh
-                                                "/ (also: Lazy methods)
-                                                mthd byteCode isNil ifTrue:[
-                                                    mSource := mthd source.
-                                                    (mSource notNil
-                                                    and:[(mSource includesString:(sym upTo:$:))
-                                                    and:[mthd usedSymbols includes:sym]])
-                                                ] ifFalse:[
-                                                    ((mthd refersToLiteral:sym)
-                                                     and:[mthd usedSymbols includes:sym])
-                                                ]
-                                          ].
-                        ] ifFalse:[
-                            stringToSearch includesMatchCharacters ifFalse:[
-                                ^ self warn:'No such symbol'.
-                            ].
-                            searchBlock := [:cls :mthd :sel | |mSource|
-                                                "/ kludge: stc does not include symbols in the literal array - sigh
-                                                "/ (also: Lazy methods)
-                                                mthd byteCode isNil ifTrue:[
-                                                    mSource := mthd source.
-                                                    (mSource notNil
-                                                    and:[mthd usedSymbols contains:[:sym | stringToSearch match:sym]])
-                                                ] ifFalse:[
-                                                    mthd usedSymbols contains:[:sym | stringToSearch match:sym]
-                                                ]
-                                          ].
-                        ].
-                        self class
-                                findMethodsIn:classes
-                                where:searchBlock
-
-                   ]
-        searchWhat:#selector
-        searchArea:(self defaultSearchArea)
-        withCaseIgnore:false
-        setSearchPattern:[:brwsr :string :ignoreCase :doMatch|
-                            brwsr autoSearchPattern:string ignoreCase:ignoreCase.
-                         ]
+	askForMethodAndSpawnSearchTitle:'Symbol to search:'
+	browserLabel:'Methods referring to #''%1'''
+	searchWith:[:string :classes :dummyIgnoreCase :dummyMatch|
+			|sym stringToSearch searchBlock|
+
+			stringToSearch := string.
+			(string startsWith:'#') ifTrue:[
+			    stringToSearch := Symbol readFrom:string.
+			    Dialog information:'Searching for ',stringToSearch
+			].
+
+			(sym := stringToSearch asSymbolIfInterned) notNil ifTrue:[
+			    searchBlock := [:cls :mthd :sel | |mSource|
+						"/ kludge: stc does not include symbols in the literal array - sigh
+						"/ (also: Lazy methods)
+						mthd byteCode isNil ifTrue:[
+						    mSource := mthd source.
+						    (mSource notNil
+						    and:[(mSource includesString:(sym upTo:$:))
+						    and:[mthd usedSymbols includes:sym]])
+						] ifFalse:[
+						    ((mthd refersToLiteral:sym)
+						     and:[mthd usedSymbols includes:sym])
+						]
+					  ].
+			] ifFalse:[
+			    stringToSearch includesMatchCharacters ifFalse:[
+				^ self warn:'No such symbol'.
+			    ].
+			    searchBlock := [:cls :mthd :sel | |mSource|
+						"/ kludge: stc does not include symbols in the literal array - sigh
+						"/ (also: Lazy methods)
+						mthd byteCode isNil ifTrue:[
+						    mSource := mthd source.
+						    (mSource notNil
+						    and:[mthd usedSymbols contains:[:sym | stringToSearch match:sym]])
+						] ifFalse:[
+						    mthd usedSymbols contains:[:sym | stringToSearch match:sym]
+						]
+					  ].
+			].
+			self class
+				findMethodsIn:classes
+				where:searchBlock
+
+		   ]
+	searchWhat:#selector
+	searchArea:(self defaultSearchArea)
+	withCaseIgnore:false
+	setSearchPattern:[:brwsr :string :ignoreCase :doMatch|
+			    brwsr autoSearchPattern:string ignoreCase:ignoreCase.
+			 ]
 
     "Modified: / 25-11-2010 / 11:41:10 / cg"
 !
@@ -24032,29 +24396,29 @@
     |searchBlock|
 
     searchBlock := [
-                        |changes classes|
-
-                        changes := ChangeSet current.
-                        classes := IdentitySet new.
-
-                        changes do:[:aChange |
-                            |cls|
-
-                            (aChange isMethodChange or:[aChange isClassChange]) ifTrue:[
-                                (cls := aChange changeClass) notNil ifTrue:[
-                                    cls := cls theNonMetaclass.
-                                    (classes includes:cls) ifFalse:[
-                                        classes add:cls.
-                                    ]
-                                ]
-                            ].
-                        ].
-                        classes asOrderedCollection
-                  ].
-
-    ^ self
-        spawnClassBrowserForSearch:searchBlock spec:#multipleClassRepositoryDiffBrowserSpec
-        sortBy:nil in:where label:'Repository Diffs' autoSelectIfOne:false
+			|changes classes|
+
+			changes := ChangeSet current.
+			classes := IdentitySet new.
+
+			changes do:[:aChange |
+			    |cls|
+
+			    (aChange isMethodChange or:[aChange isClassChange]) ifTrue:[
+				(cls := aChange changeClass) notNil ifTrue:[
+				    cls := cls theNonMetaclass.
+				    (classes includes:cls) ifFalse:[
+					classes add:cls.
+				    ]
+				]
+			    ].
+			].
+			classes asOrderedCollection
+		  ].
+
+    ^ self
+	spawnClassBrowserForSearch:searchBlock spec:#multipleClassRepositoryDiffBrowserSpec
+	sortBy:nil in:where label:'Repository Diffs' autoSelectIfOne:false
 !
 
 browseMenuSpawnRepositoryDiffsInBuffer
@@ -24073,24 +24437,24 @@
     |searchBlock|
 
     searchBlock := [
-                        |defaultId methods methodsInOrder|
-
-                        methods := OrderedCollection new.
-                        defaultId := PackageId noProjectID.
-
-                        Smalltalk allMethodsDo:[:mthd |
-                            mthd package = defaultId ifTrue:[
-                                methods add:mthd.
-                            ].
-                        ].
-                        methods
-                  ].
-
-    ^ self
-        spawnMethodBrowserForSearch:searchBlock
-        sortBy:#class
-        in:openHow
-        label:'Loose methods'
+			|defaultId methods methodsInOrder|
+
+			methods := OrderedCollection new.
+			defaultId := PackageId noProjectID.
+
+			Smalltalk allMethodsDo:[:mthd |
+			    mthd package = defaultId ifTrue:[
+				methods add:mthd.
+			    ].
+			].
+			methods
+		  ].
+
+    ^ self
+	spawnMethodBrowserForSearch:searchBlock
+	sortBy:#class
+	in:openHow
+	label:'Loose methods'
 
     "Modified: / 12-10-2006 / 20:51:48 / cg"
 !
@@ -24102,13 +24466,13 @@
 
     labelHolder := 'Methods writing to global ''%1''' asValue.
     self
-        askForMethodAndSpawnSearchTitle:'Global to search:\(TAB for completion; matchPattern allowed)'
-        browserLabel:labelHolder
-        searchWith:[:string :classes :dummyIgnoreCase :dummyMatch|
-                        |globlNames globlNamesAndSymbols globlName sym baseName matchBlock realClasses val
-                         keysReferringToValue otherKeysReferringToValue msg searchAll|
-
-                        globlNames := string withoutSeparators asCollectionOfSubstringsSeparatedByAny:',;| '.
+	askForMethodAndSpawnSearchTitle:'Global to search:\(TAB for completion; matchPattern allowed)'
+	browserLabel:labelHolder
+	searchWith:[:string :classes :dummyIgnoreCase :dummyMatch|
+			|globlNames globlNamesAndSymbols globlName sym baseName matchBlock realClasses val
+			 keysReferringToValue otherKeysReferringToValue msg searchAll|
+
+			globlNames := string withoutSeparators asCollectionOfSubstringsSeparatedByAny:',;| '.
 "/                        globlNames size > 1 ifTrue:[
 "/                            globlNames := globlNames collect:[:nm | nm asSymbol].
 "/                            matchBlock := [:cls :mthd :sel |
@@ -24218,30 +24582,30 @@
 "/                           ].
 "/                       ].
 
-                        matchBlock := self class
-                            filterToSearchRefsTo:string 
-                            instVars:false 
-                            classVars:false 
-                            globals:true 
-                            access:#write.
-
-                       "/ recollect realClasses from names (in case of class-changes)
-                       realClasses := classes collect:[:eachClass | Smalltalk at:eachClass name].
-                       self class
-                           findMethodsIn:realClasses
-                           where:matchBlock
-                   ]
-        searchWhat:#globalName
-        searchArea:#everywhere
-        withCaseIgnore:false
-        setSearchPattern:[:brwsr :string :ignoreCase :doMatch|
-                            |globlNames|
-
-                            globlNames := string withoutSeparators asCollectionOfSubstringsSeparatedByAny:',;| '.
-                            brwsr autoSearchVariables:globlNames.
-
-                            "/ brwsr autoSearchPattern:string ignoreCase:ignoreCase.
-                         ]
+			matchBlock := self class
+			    filterToSearchRefsTo:string
+			    instVars:false
+			    classVars:false
+			    globals:true
+			    access:#write.
+
+		       "/ recollect realClasses from names (in case of class-changes)
+		       realClasses := classes collect:[:eachClass | Smalltalk at:eachClass name].
+		       self class
+			   findMethodsIn:realClasses
+			   where:matchBlock
+		   ]
+	searchWhat:#globalName
+	searchArea:#everywhere
+	withCaseIgnore:false
+	setSearchPattern:[:brwsr :string :ignoreCase :doMatch|
+			    |globlNames|
+
+			    globlNames := string withoutSeparators asCollectionOfSubstringsSeparatedByAny:',;| '.
+			    brwsr autoSearchVariables:globlNames.
+
+			    "/ brwsr autoSearchPattern:string ignoreCase:ignoreCase.
+			 ]
 
     "Created: / 29-09-2011 / 10:40:16 / cg"
 !
@@ -24259,17 +24623,17 @@
     "launch an enterBox for selector to search for"
 
     ^ self
-        askForMethodAndSpawnSearchTitle:'Selector to browse senders of:\(TAB for completion; matchPattern allowed)'
-        browserLabel:'Senders of %1'
-        searchWith:#( #'findSendersOf:in:ignoreCase:match:' #'findSendersOf:inMethods:ignoreCase:match:' )
-        searchWhat:#selector
-        searchArea:#everywhere
-        withCaseIgnore:true
-        withTextEntry:true
-        withMethodList:true
-        setSearchPattern:[:brwsr :selector :ignoreCase :doMatch|
-                            brwsr autoSearchSelector:selector ignoreCase:ignoreCase doMatch:doMatch.
-                         ]
+	askForMethodAndSpawnSearchTitle:'Selector to browse senders of:\(TAB for completion; matchPattern allowed)'
+	browserLabel:'Senders of %1'
+	searchWith:#( #'findSendersOf:in:ignoreCase:match:' #'findSendersOf:inMethods:ignoreCase:match:' )
+	searchWhat:#selector
+	searchArea:#everywhere
+	withCaseIgnore:true
+	withTextEntry:true
+	withMethodList:true
+	setSearchPattern:[:brwsr :selector :ignoreCase :doMatch|
+			    brwsr autoSearchSelector:selector ignoreCase:ignoreCase doMatch:doMatch.
+			 ]
 
     "Modified: / 17.11.2001 / 09:51:00 / cg"
 !
@@ -24283,22 +24647,22 @@
 self autoSearchSelector:selectors ignoreCase:false doMatch:true.
 ].
     ^ self
-        askForMethodAndSpawnSearchTitle:'Browse Senders of (any in selected):'
-        browserLabel:('Senders (any of %1 selectors)' bindWith:selectors size)
-        searchWith:[:ignoredString :classes :ignoredCase :match|
-                            self class
-                                findSendersOfAny:selectors
-                                in:classes
-                                ignoreCase:false
-                   ]
-        searchWhat:#selector
-        searchArea:#everywhere
-        withCaseIgnore:false
-        withTextEntry:false
-        withMethodList:false
-        setSearchPattern:[:brwsr :string :ignoreCase :doMatch|
-                            brwsr autoSearchSelector:selectors ignoreCase:ignoreCase doMatch:doMatch.
-                         ]
+	askForMethodAndSpawnSearchTitle:'Browse Senders of (any in selected):'
+	browserLabel:('Senders (any of %1 selectors)' bindWith:selectors size)
+	searchWith:[:ignoredString :classes :ignoredCase :match|
+			    self class
+				findSendersOfAny:selectors
+				in:classes
+				ignoreCase:false
+		   ]
+	searchWhat:#selector
+	searchArea:#everywhere
+	withCaseIgnore:false
+	withTextEntry:false
+	withMethodList:false
+	setSearchPattern:[:brwsr :string :ignoreCase :doMatch|
+			    brwsr autoSearchSelector:selectors ignoreCase:ignoreCase doMatch:doMatch.
+			 ]
 
     "Modified: / 28-02-2012 / 16:15:36 / cg"
 !
@@ -24307,13 +24671,13 @@
     "return a useful default seach area"
 
     self hasClassSelected ifTrue:[
-        ^ #classes.
+	^ #classes.
     ].
     self hasCategorySelected ifTrue:[
-        ^ #classCategories.
+	^ #classCategories.
     ].
     self hasNameSpaceSelected ifTrue:[
-        ^ #currentNameSpace.
+	^ #currentNameSpace.
     ].
     ^ nil
 !
@@ -24323,42 +24687,42 @@
 
     classes := IdentitySet new.
     Smalltalk allClassesDo:[:eachClass |
-        (eachClass isMeta not
-        and:[eachClass isLoaded
-        and:[eachClass isNameSpace not
-        and:[(eachClass class includesSelector:selector) not]]])
-        ifTrue:[
-             classes add:eachClass
-        ].
+	(eachClass isMeta not
+	and:[eachClass isLoaded
+	and:[eachClass isNameSpace not
+	and:[(eachClass class includesSelector:selector) not]]])
+	ifTrue:[
+	     classes add:eachClass
+	].
     ].
     ^ classes asOrderedCollection
 !
 
 spawnClassDocumentationBrowserIn:where
     "browse documentation;
-        where is: #newBrowser - open a new browser
-        where is: #newBuffer  - add a new buffer"
+	where is: #newBrowser - open a new browser
+	where is: #newBuffer  - add a new buffer"
 
     |selectedClasses selectedCategories|
 
     selectedClasses := self selectedNonMetaclasses.
     selectedCategories := self selectedCategoriesValue copy.
     ^ self
-        newBrowserOrBufferDependingOn:where
-        label:nil
-        forSpec:#classDocumentationBrowserSpec
-        setupWith:[:brwsr |
-                        brwsr selectCategories:selectedCategories.
-                        brwsr selectClasses:selectedClasses.
-                  ]
+	newBrowserOrBufferDependingOn:where
+	label:nil
+	forSpec:#classDocumentationBrowserSpec
+	setupWith:[:brwsr |
+			brwsr selectCategories:selectedCategories.
+			brwsr selectClasses:selectedClasses.
+		  ]
 
     "Modified: / 12-09-2006 / 13:44:08 / cg"
 !
 
 spawnClassExtensionBrowserFor:classes in:where
     "browse extensions on selected classes;
-        where is: #newBrowser - open a new browser showing the projects
-        where is: #newBuffer  - add a new buffer showing the projects"
+	where is: #newBrowser - open a new browser showing the projects
+	where is: #newBuffer  - add a new buffer showing the projects"
 
     |spec classList "singleSelection"|
 
@@ -24373,95 +24737,95 @@
     classList := classes copy.
 
     ^ self
-        newBrowserOrBufferDependingOn:where
-        label: 'Class Extensions'
-        forSpec:spec
-        setupWith:[:brwsr |
-            |packageListGeneratorBlock|
-
-            "/ setup for a constant list ...
-            "/ brwsr organizerMode value:#project.
-            brwsr showClassPackages value:true.
-            brwsr classListGenerator value:classList.
-
-            packageListGeneratorBlock := [
-                                |packages|
-
-                                packages := Set new.
-                                (brwsr selectedClasses value ? #()) do:[:eachClass |
-                                    packages add:eachClass package.
-                                    eachClass instAndClassSelectorsAndMethodsDo:[:sel :mthd |
-                                        packages add:mthd package
-                                    ].
-                                ].
-                                packages asOrderedCollection sort.
-                          ].
-
-            brwsr projectListGenerator value:(packageListGeneratorBlock value).
-            brwsr selectedClasses onChangeEvaluate:[brwsr projectListGenerator value:(packageListGeneratorBlock value).].
-            brwsr packageFilter value:#().
-            "/ singleSelection ifTrue:[
-            "/     brwsr selectProjects:projectList.
-            "/ ].
-            "/ brwsr packageFilter value:projectList.
-        ]
+	newBrowserOrBufferDependingOn:where
+	label: 'Class Extensions'
+	forSpec:spec
+	setupWith:[:brwsr |
+	    |packageListGeneratorBlock|
+
+	    "/ setup for a constant list ...
+	    "/ brwsr organizerMode value:#project.
+	    brwsr showClassPackages value:true.
+	    brwsr classListGenerator value:classList.
+
+	    packageListGeneratorBlock := [
+				|packages|
+
+				packages := Set new.
+				(brwsr selectedClasses value ? #()) do:[:eachClass |
+				    packages add:eachClass package.
+				    eachClass instAndClassSelectorsAndMethodsDo:[:sel :mthd |
+					packages add:mthd package
+				    ].
+				].
+				packages asOrderedCollection sort.
+			  ].
+
+	    brwsr projectListGenerator value:(packageListGeneratorBlock value).
+	    brwsr selectedClasses onChangeEvaluate:[brwsr projectListGenerator value:(packageListGeneratorBlock value).].
+	    brwsr packageFilter value:#().
+	    "/ singleSelection ifTrue:[
+	    "/     brwsr selectProjects:projectList.
+	    "/ ].
+	    "/ brwsr packageFilter value:projectList.
+	]
 
     "Modified: / 18.8.2000 / 18:48:40 / cg"
 !
 
 spawnClassExtensionBrowserForSearch:searchBlock label:labelOrNil in:where
     "browse extensions on a searchBlock;
-        where is: #newBrowser - open a new browser showing the projects
-        where is: #newBuffer  - add a new buffer showing the projects"
-
-    ^ self
-        newBrowserOrBufferDependingOn:where
-        label:(labelOrNil ? 'Class Extensions')
-        forSpec:#multipleClassExtensionBrowserSpec
-        setupWith:[:brwsr |
-            |classListGenerator packageListGeneratorBlock theClassList|
-
-            classListGenerator := Iterator on:[:whatToDo |
-                                            theClassList isNil ifTrue:[
-                                                theClassList := searchBlock value.
-                                            ].
-                                            theClassList notNil ifTrue:[
-                                                theClassList do:[:aClass |
-                                                    whatToDo value:aClass
-                                                ].
-                                                theClassList := nil.
-                                            ].
-                                      ].
-
-            "/ brwsr organizerMode value:#project.
-            brwsr showClassPackages value:true.
-            brwsr classListGenerator value:classListGenerator.
-
-            packageListGeneratorBlock := [
-                                |packages|
-
-                                packages := Set new.
-                                (brwsr selectedClasses value ? #()) do:[:eachClass |
-                                    packages add:eachClass package.
-                                    eachClass instAndClassSelectorsAndMethodsDo:[:sel :mthd |
-                                        packages add:mthd package
-                                    ].
-                                ].
-                                packages asOrderedCollection sort.
-                          ].
-
-            brwsr projectListGenerator value:(packageListGeneratorBlock value).
-            brwsr selectedClasses onChangeEvaluate:[brwsr projectListGenerator value:(packageListGeneratorBlock value).].
-            brwsr packageFilter value:#().
-        ]
+	where is: #newBrowser - open a new browser showing the projects
+	where is: #newBuffer  - add a new buffer showing the projects"
+
+    ^ self
+	newBrowserOrBufferDependingOn:where
+	label:(labelOrNil ? 'Class Extensions')
+	forSpec:#multipleClassExtensionBrowserSpec
+	setupWith:[:brwsr |
+	    |classListGenerator packageListGeneratorBlock theClassList|
+
+	    classListGenerator := Iterator on:[:whatToDo |
+					    theClassList isNil ifTrue:[
+						theClassList := searchBlock value.
+					    ].
+					    theClassList notNil ifTrue:[
+						theClassList do:[:aClass |
+						    whatToDo value:aClass
+						].
+						theClassList := nil.
+					    ].
+				      ].
+
+	    "/ brwsr organizerMode value:#project.
+	    brwsr showClassPackages value:true.
+	    brwsr classListGenerator value:classListGenerator.
+
+	    packageListGeneratorBlock := [
+				|packages|
+
+				packages := Set new.
+				(brwsr selectedClasses value ? #()) do:[:eachClass |
+				    packages add:eachClass package.
+				    eachClass instAndClassSelectorsAndMethodsDo:[:sel :mthd |
+					packages add:mthd package
+				    ].
+				].
+				packages asOrderedCollection sort.
+			  ].
+
+	    brwsr projectListGenerator value:(packageListGeneratorBlock value).
+	    brwsr selectedClasses onChangeEvaluate:[brwsr projectListGenerator value:(packageListGeneratorBlock value).].
+	    brwsr packageFilter value:#().
+	]
 
     "Modified: / 18.8.2000 / 18:48:40 / cg"
 !
 
 spawnFullClassSourceBrowserIn:where
     "browse full classes (file-like);
-        where is: #newBrowser - open a new browser
-        where is: #newBuffer  - add a new buffer"
+	where is: #newBrowser - open a new browser
+	where is: #newBuffer  - add a new buffer"
 
     |selectedClasses selectedCategories|
 
@@ -24469,14 +24833,14 @@
     selectedCategories := self selectedCategoriesValue copy.
 
     ^ self
-        newBrowserOrBufferDependingOn:where
-        label:nil
-        forSpec:#fullClassSourceBrowserSpec
-        setupWith:[:brwsr |
-                        brwsr meta value:false.
-                        brwsr selectCategories:selectedCategories.
-                        brwsr selectClasses:selectedClasses.
-                  ]
+	newBrowserOrBufferDependingOn:where
+	label:nil
+	forSpec:#fullClassSourceBrowserSpec
+	setupWith:[:brwsr |
+			brwsr meta value:false.
+			brwsr selectCategories:selectedCategories.
+			brwsr selectClasses:selectedClasses.
+		  ]
 
     "Modified: / 12-09-2006 / 13:43:48 / cg"
 !
@@ -24496,14 +24860,14 @@
     "remove all other than the numbered buffer"
 
     buffers size to:1 by:-1 do:[:bNrToClose |
-        bNrToClose ~~ bNrToLeaveOpen ifTrue:[
-            (self
-                askIfModified:'Code was modified.\\Remove buffer anyway ?'
-                in:(buffers at:bNrToClose))
-            ifTrue:[
-                self removeBuffer:bNrToClose.
-            ].
-        ].
+	bNrToClose ~~ bNrToLeaveOpen ifTrue:[
+	    (self
+		askIfModified:'Code was modified.\\Remove buffer anyway ?'
+		in:(buffers at:bNrToClose))
+	    ifTrue:[
+		self removeBuffer:bNrToClose.
+	    ].
+	].
     ].
 
     "Modified: / 11.2.2000 / 10:55:02 / cg"
@@ -24513,13 +24877,13 @@
     "remove the numbered buffer"
 
     buffers size > 0 ifTrue:[
-        (self
-            askIfModified:'Code was modified.\\Remove buffer anyway ?'
-            in:(buffers at:nr)
-        )
-        ifTrue:[
-            self removeBuffer:nr.
-        ].
+	(self
+	    askIfModified:'Code was modified.\\Remove buffer anyway ?'
+	    in:(buffers at:nr)
+	)
+	ifTrue:[
+	    self removeBuffer:nr.
+	].
     ]
 
     "Modified: / 11.2.2000 / 10:55:02 / cg"
@@ -24538,10 +24902,10 @@
 
     nr := selectedBuffer value.
     (nr notNil and:[nr between:1 and:buffers size]) ifTrue:[
-        navigationState := buffers at:selectedBuffer value.
-        self browserCanvas value:(navigationState canvas).
-        self updateNavigationHistory.
-        self updateBookmarkHolder.
+	navigationState := buffers at:selectedBuffer value.
+	self browserCanvas value:(navigationState canvas).
+	self updateNavigationHistory.
+	self updateBookmarkHolder.
     ].
 
     "/ force update of the menus orgMode aspect
@@ -24569,7 +24933,7 @@
     cls := self selectedClassNameInCodeViewOrNil.
     navigationState := self createBuffer.
     cls notNil ifTrue:[
-        self switchToClass:cls
+	self switchToClass:cls
     ]
 !
 
@@ -24587,18 +24951,18 @@
     bNameList := self bufferNameList.  "/ for lazy setup
 
     buffers size == 0 ifTrue:[
-        "the original (initial) buffer is created here (lazy)"
-
-        buffers := OrderedCollection new.
-        bufferUsageOrder := OrderedCollection new.
-
-        navigationState canvasType isNil ifTrue:[
-            navigationState canvas:self browserCanvas value.
-            navigationState canvasType:(self browserCanvasType ? navigationState canvasType).
-        ].
-        buffers add:navigationState.
-        bNameList add:(self currentBufferLabel).
-        bufferUsageOrder add:navigationState.
+	"the original (initial) buffer is created here (lazy)"
+
+	buffers := OrderedCollection new.
+	bufferUsageOrder := OrderedCollection new.
+
+	navigationState canvasType isNil ifTrue:[
+	    navigationState canvas:self browserCanvas value.
+	    navigationState canvasType:(self browserCanvasType ? navigationState canvasType).
+	].
+	buffers add:navigationState.
+	bNameList add:(self currentBufferLabel).
+	bufferUsageOrder add:navigationState.
     ].
 
     oldNavigationState := navigationState.
@@ -24634,13 +24998,13 @@
     |brwsr|
 
     openHow == #newBrowser ifTrue:[
-        brwsr := self class openInClass:aClass selector:selector
-    ] ifFalse:[
-        brwsr := self.
-        "/ brwsr createBuffer.
-        brwsr createBufferWithSpec:#fullBrowserSpec setupFromCurrentState:false.
-        brwsr selectedCategories value:nil. "/ kludge workaround; classList needs a change to update.
-        brwsr switchToClass:aClass selector:selector.
+	brwsr := self class openInClass:aClass selector:selector
+    ] ifFalse:[
+	brwsr := self.
+	"/ brwsr createBuffer.
+	brwsr createBufferWithSpec:#fullBrowserSpec setupFromCurrentState:false.
+	brwsr selectedCategories value:nil. "/ kludge workaround; classList needs a change to update.
+	brwsr switchToClass:aClass selector:selector.
     ].
     ^ brwsr
 
@@ -24649,17 +25013,7 @@
 
 !NewSystemBrowser methodsFor:'menu actions-category'!
 
-categoryCheckMenuSmalllintCheck: what
-    "perform all checks on the selected class(es)."
-    
-    self 
-        smalllintCheck:self selectedCategoriesAsEnvironment
-        against: what
-
-    "Modified: / 28-12-2008 / 14:42:01 / bazantj <enter your email here>"
-    "Modified: / 13-01-2009 / 13:20:48 / Jiri Bazant <bazanj2@fel.cvut.cz>"
-    "Created: / 17-04-2010 / 10:32:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-!
+
 
 categoryMenuCheckInEach
     "check a class into the source repository"
@@ -24672,8 +25026,8 @@
     classes := IdentitySet new.
     self selectedCategoryClassesDo:[:aClass | classes add:aClass].
     classes isEmpty ifTrue:[
-        self warn:'No classes matched (all private classes)'.
-        ^ self.
+	self warn:'No classes matched (all private classes)'.
+	^ self.
     ].
     classes := classes asSortedCollection:[:a :b | a name < b name].
 
@@ -24711,12 +25065,12 @@
     "remove all changes for the selected category-class(es) from the changeSet"
 
     (self confirm:'This will remove all changes for all classes from the selected categories from the internal changeSet.\(They will still be in the change-file, in case of emergency.)\\Really cleanup ?' withCRs)
-        ifFalse:[ ^ self].
+	ifFalse:[ ^ self].
 
     self withWaitCursorDo:[
-        self selectedCategoryClassesDo:[:eachClass |
-            ChangeSet current condenseChangesForClass:eachClass
-        ].
+	self selectedCategoryClassesDo:[:eachClass |
+	    ChangeSet current condenseChangesForClass:eachClass
+	].
     ]
 
     "Created: / 31-01-2011 / 11:10:13 / cg"
@@ -24730,51 +25084,51 @@
 
 categoryMenuFileOutAsWithFormat:aFormatSymbolOrNil
     "fileOut selected categories -  file format as specified by the argument:
-        nil     - standard format
-        #xml    - XML standard format
-        #sif    - SIF (smalltalk interchange file) standard format
-        #binary - ST/X binary format
+	nil     - standard format
+	#xml    - XML standard format
+	#sif    - SIF (smalltalk interchange file) standard format
+	#binary - ST/X binary format
     "
 
     |currentClassCategory fileName suffix saveName aStream classesToInitialize classesToFileout mgr|
 
     currentClassCategory := self theSingleSelectedCategory.
     currentClassCategory notNil ifTrue:[
-        fileName := currentClassCategory asString.
-        fileName replaceAll:Character space with:$_.
-    ] ifFalse:[
-        fileName := 'someCategories'
+	fileName := currentClassCategory asString.
+	fileName replaceAll:Character space with:$_.
+    ] ifFalse:[
+	fileName := 'someCategories'
     ].
     aFormatSymbolOrNil == #xml ifTrue:[
-        suffix := '.xml'
-    ] ifFalse:[
-        aFormatSymbolOrNil == #sif ifTrue:[
-            suffix := '.sif'
-        ] ifFalse:[
-            aFormatSymbolOrNil == #binary ifTrue:[
-                suffix := '.cls'
-            ] ifFalse:[
-                suffix := '.st'
-            ]
-        ]
+	suffix := '.xml'
+    ] ifFalse:[
+	aFormatSymbolOrNil == #sif ifTrue:[
+	    suffix := '.sif'
+	] ifFalse:[
+	    aFormatSymbolOrNil == #binary ifTrue:[
+		suffix := '.cls'
+	    ] ifFalse:[
+		suffix := '.st'
+	    ]
+	]
     ].
     fileName := fileName , suffix.
 
     aFormatSymbolOrNil == #binary ifTrue:[
-        self error:'binary must go into separate files'.
-        ^ self
+	self error:'binary must go into separate files'.
+	^ self
     ].
 
     saveName := self
-                    fileNameDialogForFileOut:(resources string:'FileOut %1 as:' with:(currentClassCategory ? 'selected categories'))
-                    default:fileName.
+		    fileNameDialogForFileOut:(resources string:'FileOut %1 as:' with:(currentClassCategory ? 'selected categories'))
+		    default:fileName.
 
     saveName isNil ifTrue:[
-        ^ self
+	^ self
     ].
     saveName isEmpty ifTrue:[
-        self warn:'Bad name given'.
-        ^ self
+	self warn:'Bad name given'.
+	^ self
     ].
     FileSelectionBox lastFileSelectionDirectory:(saveName asFilename directoryName).
     fileName := saveName.
@@ -24783,67 +25137,67 @@
     classesToFileout := OrderedCollection new.
 
     self selectedCategoryClassesDo:[:eachClassInCategory |
-        |eachClass|
-
-        eachClass := eachClassInCategory theNonMetaclass.
-        eachClass isPrivate ifFalse:[
-            eachClass isLoaded ifFalse:[
-                self warn:'Cannot fileOut unloaded class: %1\\skipped.' with:eachClass name allBold.
-            ] ifTrue:[
-                classesToFileout add:eachClass.
-                (eachClass class includesSelector:#initialize) ifTrue:[
-                    classesToInitialize add:eachClass
-                ].
-            ]
-        ]
+	|eachClass|
+
+	eachClass := eachClassInCategory theNonMetaclass.
+	eachClass isPrivate ifFalse:[
+	    eachClass isLoaded ifFalse:[
+		self warn:'Cannot fileOut unloaded class: %1\\skipped.' with:eachClass name allBold.
+	    ] ifTrue:[
+		classesToFileout add:eachClass.
+		(eachClass class includesSelector:#initialize) ifTrue:[
+		    classesToInitialize add:eachClass
+		].
+	    ]
+	]
     ].
 
     "
      if file exists, save original in a .sav file
     "
     fileName asFilename exists ifTrue:[
-        self busyLabel:'saving existing %1' with:fileName.
-        fileName asFilename copyTo:(fileName , '.sav')
+	self busyLabel:'saving existing %1' with:fileName.
+	fileName asFilename copyTo:(fileName , '.sav')
     ].
 
     classesToFileout topologicalSort:[:a :b | b isSubclassOf:a].
 
     aFormatSymbolOrNil == #xml ifTrue:[
-        self warn:'Not yet implemented: XML saving'.
-        ^ self
+	self warn:'Not yet implemented: XML saving'.
+	^ self
     ].
 
     aFormatSymbolOrNil == #sif ifTrue:[
-        mgr := SmalltalkInterchangeFileManager newForFileOut.
-        mgr fileName: fileName.
-        classesToFileout do:[:eachClass |
-            mgr addClass: eachClass.
-        ].
-        self busyLabel:'writing...'.
-        mgr fileOut.
-    ] ifFalse:[
-        [
-            aStream := fileName asFilename newReadWriteStream.
-            classesToFileout do:[:eachClass |
-                self busyLabel:'writing: %1' with:eachClass name.
-                eachClass fileOutOn:aStream withTimeStamp:true withInitialize:false.
-                aStream cr.
-            ].
-
-            "/ all class-inits at the end
-            "/ (this makes certain, that all classes have been loaded
-            "/  before possibly used/needed in an initializer
-
-            classesToInitialize do:[:aClass |
-                aClass printClassNameOn:aStream. aStream nextPutAll:' initialize'.
-                aStream nextPutChunkSeparator.
-                aStream cr
-            ].
-
-            aStream close.
-        ] on:FileStream openErrorSignal do:[
-            self warn:'Cannot create: %1' with:fileName allBold
-        ].
+	mgr := SmalltalkInterchangeFileManager newForFileOut.
+	mgr fileName: fileName.
+	classesToFileout do:[:eachClass |
+	    mgr addClass: eachClass.
+	].
+	self busyLabel:'writing...'.
+	mgr fileOut.
+    ] ifFalse:[
+	[
+	    aStream := fileName asFilename newReadWriteStream.
+	    classesToFileout do:[:eachClass |
+		self busyLabel:'writing: %1' with:eachClass name.
+		eachClass fileOutOn:aStream withTimeStamp:true withInitialize:false.
+		aStream cr.
+	    ].
+
+	    "/ all class-inits at the end
+	    "/ (this makes certain, that all classes have been loaded
+	    "/  before possibly used/needed in an initializer
+
+	    classesToInitialize do:[:aClass |
+		aClass printClassNameOn:aStream. aStream nextPutAll:' initialize'.
+		aStream nextPutChunkSeparator.
+		aStream cr
+	    ].
+
+	    aStream close.
+	] on:FileStream openErrorSignal do:[
+	    self warn:'Cannot create: %1' with:fileName allBold
+	].
     ].
     self normalLabel.
 !
@@ -24868,14 +25222,14 @@
     currentCategory := self theSingleSelectedCategory ? 'selected categories'.
 
     dirName := self
-                askForDirectoryToFileOut:(resources string:'FileOut %1 in:' with:currentCategory)
-                default:nil.
+		askForDirectoryToFileOut:(resources string:'FileOut %1 in:' with:currentCategory)
+		default:nil.
     dirName isEmptyOrNil ifTrue:[^ self].
 
     self
-        fileOutEachClassIn:(self selectedCategoryClasses)
-        in:dirName
-        withFormat:aFormatSymbolOrNil.
+	fileOutEachClassIn:(self selectedCategoryClasses)
+	in:dirName
+	withFormat:aFormatSymbolOrNil.
 
     "Modified: / 23-08-2006 / 12:31:28 / cg"
 !
@@ -24922,45 +25276,61 @@
     allClassCategories := Smalltalk allClassCategories.
 
     box := self
-                enterBoxTitle:'Name of new class category:'
-                okText:'Create'
-                label:'Create Category'.
+		enterBoxTitle:'Name of new class category:'
+		okText:'Create'
+		label:'Create Category'.
 
     (allClassCategories includes:'* as yet unspecified *')
     ifFalse:[
-        box initialAnswer:'* as yet unspecified *'.
+	box initialAnswer:'* as yet unspecified *'.
     ].
 
     box entryCompletionBlock:[:contents |
-        |s what cat|
-
-        s := contents withoutSpaces.
-        what := self navigationState environment classCategoryCompletion:s.
-        cat := what first.
-        (allClassCategories includes:cat) ifTrue:[
-            cat := cat , '-'.
-        ].
-        box contents:cat.
-        (what at:2) size ~~ 1 ifTrue:[
-            self builder window beep
-        ]
+	|s what cat|
+
+	s := contents withoutSpaces.
+	what := self navigationState environment classCategoryCompletion:s.
+	cat := what first.
+	(allClassCategories includes:cat) ifTrue:[
+	    cat := cat , '-'.
+	].
+	box contents:cat.
+	(what at:2) size ~~ 1 ifTrue:[
+	    self builder window beep
+	]
     ].
     box action:[:aString | newCategory := aString].
     box open.
 
     newCategory notNil ifTrue:[
-        "/ self immediateUpdate value:true.
-        self categoryListApp addAdditionalCategory:newCategory.
-        "/ self immediateUpdate value:false.
-
-        self codeReallyModified ifFalse:[
-            self selectCategory:newCategory.
-        ]
+	"/ self immediateUpdate value:true.
+	self categoryListApp addAdditionalCategory:newCategory.
+	"/ self immediateUpdate value:false.
+
+	self codeReallyModified ifFalse:[
+	    self selectCategory:newCategory.
+	]
     ].
 
     "Modified: / 25.2.2000 / 00:50:48 / cg"
 !
 
+categoryMenuRecompile
+    self selectedCategoryClassesDo:[:eachClass |
+	self recompileClass:eachClass
+    ].
+
+    "Created: / 31-05-2012 / 12:03:11 / cg"
+!
+
+categoryMenuRecompileInstrumented
+    self selectedCategoryClassesDo:[:eachClass |
+	self recompileClassWithInstrumentation:eachClass
+    ].
+
+    "Created: / 31-05-2012 / 09:15:44 / cg"
+!
+
 categoryMenuRemove
     |box txt answer selectedCategories classes count categories includesBuiltIn
      affectedSubClasses classesToReallyRemove|
@@ -24971,112 +25341,112 @@
     categories := Set new.
     includesBuiltIn := false.
     self selectedCategoryClassesDo:[:aClass |
-        classes add:aClass.
-        categories add:aClass category.
-        aClass isBuiltInClass ifTrue:[includesBuiltIn := true].
+	classes add:aClass.
+	categories add:aClass category.
+	aClass isBuiltInClass ifTrue:[includesBuiltIn := true].
     ].
 
     classes size == 0 ifTrue:[
-        "/ removing an empty category
-        self selectedCategories value:#().
-        self categoryListApp removeAdditionalCategories:selectedCategories.
-        ^ self
+	"/ removing an empty category
+	self selectedCategories value:#().
+	self categoryListApp removeAdditionalCategories:selectedCategories.
+	^ self
     ].
 
     "/ count affected sub-classes
     affectedSubClasses := IdentitySet new.
     classes do:[:aClassToRemove |
-        affectedSubClasses addAll:(aClassToRemove allSubclasses).
+	affectedSubClasses addAll:(aClassToRemove allSubclasses).
     ].
     affectedSubClasses := affectedSubClasses reject:[:eachClass | classes includes:eachClass ].
     count := affectedSubClasses size.
 
     classes size == 1 ifTrue:[
-        txt := 'Really remove %1'.
-    ] ifFalse:[
-        txt := 'Really remove %2 classes'.
+	txt := 'Really remove %1'.
+    ] ifFalse:[
+	txt := 'Really remove %2 classes'.
     ].
     count ~~ 0 ifTrue:[
        txt := txt , '\(with %3 subclass'.
        count ~~ 1 ifTrue:[
-           txt := txt , 'es in other categories)'
+	   txt := txt , 'es in other categories)'
        ] ifFalse:[
-           txt := txt , ' - ', affectedSubClasses first name , ' - in category ''' , affectedSubClasses first category, ''')'
+	   txt := txt , ' - ', affectedSubClasses first name , ' - in category ''' , affectedSubClasses first category, ''')'
        ]
     ].
     categories size > 1 ifTrue:[
-        txt := txt , ' in %4 categories'.
-    ] ifFalse:[
-        txt := txt , ' in %5'.
+	txt := txt , ' in %4 categories'.
+    ] ifFalse:[
+	txt := txt , ' in %5'.
     ].
     txt := txt , ' ?'.
     txt := (resources
-                string:txt
-                with:classes first name allBold
-                with:classes size printString
-                with:count
-                with:categories size printString
-                with:categories first) withCRs.
+		string:txt
+		with:classes first name allBold
+		with:classes size printString
+		with:count
+		with:categories size printString
+		with:categories first) withCRs.
 
     box := YesNoBox
-               title:txt
-               yesText:(resources string:'Remove')
-               noText:(resources string:'Cancel').
+	       title:txt
+	       yesText:(resources string:'Remove')
+	       noText:(resources string:'Cancel').
     box label:(resources string:'Remove Class(es)').
     answer := box confirm.
     box destroy.
 
     (answer and:[includesBuiltIn]) ifTrue:[
-        "/ ask again - severe damage is to be expected ...
-        answer := Dialog confirm:('The set of classes to remove includes at least one systemClass,\without which ST/X will fail to work.\Be prepared for a crash, if you proceed.\\Really remove ?' withCRs)
+	"/ ask again - severe damage is to be expected ...
+	answer := Dialog confirm:('The set of classes to remove includes at least one systemClass,\without which ST/X will fail to work.\Be prepared for a crash, if you proceed.\\Really remove ?' withCRs)
     ].
 
     answer ifTrue:[
-        self withWaitCursorDo:[
-            classesToReallyRemove := OrderedCollection new.
-
-            "after querying user - do really remove the classes
-             and all subclasses
-            "
-            classes do:[:aClassToRemove |
-                |doRemove didRemove|
-
-                didRemove := false.
-                doRemove := true.
-                aClassToRemove withAllSubclasses do:[:eachClass |
-                    eachClass hasExtensions ifTrue:[
-                        doRemove := self confirm:(resources string:'''%1'' has extensions (methods in other packages) - remove anyway ?' with:eachClass name).
-                    ]
-                ].
-                doRemove ifTrue:[
-                    "
-                     query ?
-                    "
-                    aClassToRemove allSubclassesDo:[:aSubClass |
-                        (CheckForInstancesWhenRemovingClasses == false
-                        or:[aSubClass hasInstances not
-                        or:[self confirm:(resources string:'''%1'' has instances - remove anyway ?' with:aSubClass name)]])
-                            ifTrue:[
-                                classesToReallyRemove add:aSubClass
-                        ]
-                    ].
-                    (CheckForInstancesWhenRemovingClasses == false
-                    or:[aClassToRemove hasInstances not
-                    or:[self confirm:(resources string:'''%1'' has instances - remove anyway ?' with:aClassToRemove name)]])
-                        ifTrue:[
-                            didRemove := true.
-                            classesToReallyRemove add:aClassToRemove
-                    ].
-                ].
-            ].
+	self withWaitCursorDo:[
+	    classesToReallyRemove := OrderedCollection new.
+
+	    "after querying user - do really remove the classes
+	     and all subclasses
+	    "
+	    classes do:[:aClassToRemove |
+		|doRemove didRemove|
+
+		didRemove := false.
+		doRemove := true.
+		aClassToRemove withAllSubclasses do:[:eachClass |
+		    eachClass hasExtensions ifTrue:[
+			doRemove := self confirm:(resources string:'''%1'' has extensions (methods in other packages) - remove anyway ?' with:eachClass name).
+		    ]
+		].
+		doRemove ifTrue:[
+		    "
+		     query ?
+		    "
+		    aClassToRemove allSubclassesDo:[:aSubClass |
+			(CheckForInstancesWhenRemovingClasses == false
+			or:[aSubClass hasInstances not
+			or:[self confirm:(resources string:'''%1'' has instances - remove anyway ?' with:aSubClass name)]])
+			    ifTrue:[
+				classesToReallyRemove add:aSubClass
+			]
+		    ].
+		    (CheckForInstancesWhenRemovingClasses == false
+		    or:[aClassToRemove hasInstances not
+		    or:[self confirm:(resources string:'''%1'' has instances - remove anyway ?' with:aClassToRemove name)]])
+			ifTrue:[
+			    didRemove := true.
+			    classesToReallyRemove add:aClassToRemove
+		    ].
+		].
+	    ].
 
 "/            classesToReallyRemove do:[:each |
 "/                each removeFromSystem.
 "/            ].
-            classesToReallyRemove notEmpty ifTrue:[
-                self removeClasses:classesToReallyRemove pullUpSubclasses:false
-            ]
-        ].
+	    classesToReallyRemove notEmpty ifTrue:[
+		self removeClasses:classesToReallyRemove pullUpSubclasses:false
+	    ]
+	].
     ]
 
     "Modified: / 11-07-2010 / 16:44:24 / cg"
@@ -25087,94 +25457,94 @@
      cancelAll guess combosList change numClasses|
 
     self canUseRefactoringSupport ifTrue:[
-        change := CompositeRefactoryChange named:'Rename categories'.
+	change := CompositeRefactoryChange named:'Rename categories'.
     ].
 
     numClasses := 0.
 
     self withWaitCursorDo:[
-        categoriesToRename := self selectedCategoriesValue copy.
-        categoriesToRename do:[:eachCategory |
-            guess := DoWhatIMeanSupport
-                        goodRenameDefaultFor:eachCategory
-                        lastOld:LastCategoryRenameOld
-                        lastNew:LastCategoryRenameNew.
-
-            guess isNil ifTrue:[
-                guess := eachCategory string.
-            ].
-
-            allCategories := Smalltalk allClassCategories asArray sort.
-            combosList := LastCategoryRenames.
-            (combosList size > 0 and:[combosList includes:eachCategory]) ifFalse:[
-                combosList size == 0 ifTrue:[
-                    combosList := List with:eachCategory
-                ] ifFalse:[
-                    combosList := (List with:eachCategory with:'-') , combosList
-                ]
-            ].
-
-            box := ListSelectionBox new.
-            box title:(resources string:'Rename category ''%1'' to:' with:eachCategory allBold).
-            box useComboBoxWithList:combosList.
-            box list:allCategories.
-            box okAction:[:sel | newCategory := sel].
-            box initialText:guess.
-
-            cancelAll := false.
-            categoriesToRename size > 1 ifTrue:[
-                |cancelAllButton|
-
-                cancelAllButton := Button label:(resources string:'Cancel All').
-                box addButton:cancelAllButton before:box cancelButton.
-                cancelAllButton action:[
-                                            cancelAll := true.
-                                            box doAccept.
-                                            box okPressed.
-                                       ].
-            ].
-            box label:(resources string:'Rename ClassCategory').
-            box showAtPointer.
-            cancelAll ifTrue:[^ self].
-
-            newCategory notNil ifTrue:[
-                newCategory := newCategory withoutSeparators asSymbol.
-                LastCategoryRenames isNil ifTrue:[
-                    LastCategoryRenames := OrderedCollection new
-                ].
-                LastCategoryRenames addFirst:newCategory.
-                LastCategoryRenames size > 20 ifTrue:[
-                    LastCategoryRenames removeLast
-                ].
-
-                LastCategoryRenameOld := eachCategory.
-                LastCategoryRenameNew := newCategory.
-
-                (self selectedClassesInCategories:(Array with:eachCategory)) do:[:aClass |
-                    "/ must be loaded ...
-                    aClass autoload
-                ].
-                (self selectedClassesInCategories:(Array with:eachCategory)) do:[:aClass |
-                    aClass category ~= newCategory ifTrue:[
-                        numClasses := numClasses + 1.
-                        change notNil ifTrue:[
-                            change changeClassCategoryOf:aClass to:newCategory
-                        ] ifFalse:[
-                            aClass category:newCategory.
-                        ].
-                    ]
-                ].
-
-                self selectedCategories value:(Array with:newCategory).
-            ].
-        ].
+	categoriesToRename := self selectedCategoriesValue copy.
+	categoriesToRename do:[:eachCategory |
+	    guess := DoWhatIMeanSupport
+			goodRenameDefaultFor:eachCategory
+			lastOld:LastCategoryRenameOld
+			lastNew:LastCategoryRenameNew.
+
+	    guess isNil ifTrue:[
+		guess := eachCategory string.
+	    ].
+
+	    allCategories := Smalltalk allClassCategories asArray sort.
+	    combosList := LastCategoryRenames.
+	    (combosList size > 0 and:[combosList includes:eachCategory]) ifFalse:[
+		combosList size == 0 ifTrue:[
+		    combosList := List with:eachCategory
+		] ifFalse:[
+		    combosList := (List with:eachCategory with:'-') , combosList
+		]
+	    ].
+
+	    box := ListSelectionBox new.
+	    box title:(resources string:'Rename category ''%1'' to:' with:eachCategory allBold).
+	    box useComboBoxWithList:combosList.
+	    box list:allCategories.
+	    box okAction:[:sel | newCategory := sel].
+	    box initialText:guess.
+
+	    cancelAll := false.
+	    categoriesToRename size > 1 ifTrue:[
+		|cancelAllButton|
+
+		cancelAllButton := Button label:(resources string:'Cancel All').
+		box addButton:cancelAllButton before:box cancelButton.
+		cancelAllButton action:[
+					    cancelAll := true.
+					    box doAccept.
+					    box okPressed.
+				       ].
+	    ].
+	    box label:(resources string:'Rename ClassCategory').
+	    box showAtPointer.
+	    cancelAll ifTrue:[^ self].
+
+	    newCategory notNil ifTrue:[
+		newCategory := newCategory withoutSeparators asSymbol.
+		LastCategoryRenames isNil ifTrue:[
+		    LastCategoryRenames := OrderedCollection new
+		].
+		LastCategoryRenames addFirst:newCategory.
+		LastCategoryRenames size > 20 ifTrue:[
+		    LastCategoryRenames removeLast
+		].
+
+		LastCategoryRenameOld := eachCategory.
+		LastCategoryRenameNew := newCategory.
+
+		(self selectedClassesInCategories:(Array with:eachCategory)) do:[:aClass |
+		    "/ must be loaded ...
+		    aClass autoload
+		].
+		(self selectedClassesInCategories:(Array with:eachCategory)) do:[:aClass |
+		    aClass category ~= newCategory ifTrue:[
+			numClasses := numClasses + 1.
+			change notNil ifTrue:[
+			    change changeClassCategoryOf:aClass to:newCategory
+			] ifFalse:[
+			    aClass category:newCategory.
+			].
+		    ]
+		].
+
+		self selectedCategories value:(Array with:newCategory).
+	    ].
+	].
     ].
 
     change notNil ifTrue:[
-        numClasses > 0 ifTrue:[
-            change name:('Rename category of %1 classes' bindWith:numClasses).
-            RefactoryChangeManager performChange:change
-        ]
+	numClasses > 0 ifTrue:[
+	    change name:('Rename category of %1 classes' bindWith:numClasses).
+	    RefactoryChangeManager performChange:change
+	]
     ].
 
     "Modified: / 06-02-2007 / 10:31:45 / cg"
@@ -25191,13 +25561,26 @@
 
     classes := self selectedClassesInCategories: self selectedCategoriesValue.
     MethodRewriter new
-        classes: classes;
-        open
+	classes: classes;
+	open
 
     "Created: / 21-07-2007 / 07:06:53 / janfrog"
     "Modified: / 28-02-2012 / 17:01:34 / cg"
 !
 
+categoryMenuSmalllintCheck: what
+    "perform all checks on the selected class(es)."
+
+    self
+	smalllintCheck:self selectedCategoriesAsEnvironment
+	against: what
+
+    "Modified: / 28-12-2008 / 14:42:01 / bazantj <enter your email here>"
+    "Modified: / 13-01-2009 / 13:20:48 / Jiri Bazant <bazanj2@fel.cvut.cz>"
+    "Created: / 17-04-2010 / 10:32:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 05-05-2012 / 10:17:41 / cg"
+!
+
 categoryMenuSpawnBrowser
     "open a browser showing the selected categories only"
 
@@ -25235,12 +25618,12 @@
 
     matchingCategories := Set new.
     Smalltalk allClassesAndMetaclassesDo:[:eachClass |
-        |cat|
-
-        cat := eachClass category.
-        (pattern match:cat) ifTrue:[
-            matchingCategories add:cat.
-        ]
+	|cat|
+
+	cat := eachClass category.
+	(pattern match:cat) ifTrue:[
+	    matchingCategories add:cat.
+	]
     ].
     ^ self spawnCategoryBrowserFor:matchingCategories in:openHow
 !
@@ -25271,52 +25654,52 @@
 
     defaultDir := FileSelectionBox lastFileSelectionDirectory.
     defaultDir isNil ifTrue:[
-        "
-         this test allows a smalltalk to be built without Projects/ChangeSets
-        "
-        Project notNil ifTrue:[
-            defaultDir := Project currentProjectDirectory asFilename
-        ].
-        defaultDir isNil ifTrue:[
-            defaultDir := Filename currentDirectory
-        ]
+	"
+	 this test allows a smalltalk to be built without Projects/ChangeSets
+	"
+	Project notNil ifTrue:[
+	    defaultDir := Project currentProjectDirectory asFilename
+	].
+	defaultDir isNil ifTrue:[
+	    defaultDir := Filename currentDirectory
+	]
     ].
     currentClassCategory := self theSingleSelectedCategory.
 
     UserPreferences current useNewFileDialog ifTrue:[
-        saveName := Dialog
-                        requestFileName:(resources string:'FileOut %1 as:' with:(currentClassCategory ? 'selected categories'))
-                        default:defaultFileName
-                        ok:(resources string:'FileOut')
-                        abort:(resources string:'Cancel')
-                        pattern:nil
-                        fromDirectory:defaultDir.
-        saveName isEmptyOrNil ifTrue:[
-            saveName := nil
-        ].
-    ] ifFalse:[
-        fileBox := FileSelectionBox
-                        title:(resources string:'FileOut %1 as:' with:(currentClassCategory ? 'selected categories'))
-                        okText:(resources string:'FileOut')
-                        abortText:(resources string:'Cancel')
-                        action:[:fileName | saveName := fileName.].
-
-        fileBox initialText:defaultFileName.
-        fileBox directory:defaultDir.
-
-        cancelAllActionOrNil notNil ifTrue:[
-            cancelAllButton := Button label:(resources string:'Cancel All').
-            fileBox addButton:cancelAllButton before:fileBox cancelButton.
-            cancelAllButton action:[
-                cancelAllActionOrNil value.
-                fileBox doAccept.
-                fileBox okPressed.
-            ].
-        ].
-
-        fileBox showAtPointer.
-        fileBox destroy.
-        fileBox := nil.
+	saveName := Dialog
+			requestFileName:(resources string:'FileOut %1 as:' with:(currentClassCategory ? 'selected categories'))
+			default:defaultFileName
+			ok:(resources string:'FileOut')
+			abort:(resources string:'Cancel')
+			pattern:nil
+			fromDirectory:defaultDir.
+	saveName isEmptyOrNil ifTrue:[
+	    saveName := nil
+	].
+    ] ifFalse:[
+	fileBox := FileSelectionBox
+			title:(resources string:'FileOut %1 as:' with:(currentClassCategory ? 'selected categories'))
+			okText:(resources string:'FileOut')
+			abortText:(resources string:'Cancel')
+			action:[:fileName | saveName := fileName.].
+
+	fileBox initialText:defaultFileName.
+	fileBox directory:defaultDir.
+
+	cancelAllActionOrNil notNil ifTrue:[
+	    cancelAllButton := Button label:(resources string:'Cancel All').
+	    fileBox addButton:cancelAllButton before:fileBox cancelButton.
+	    cancelAllButton action:[
+		cancelAllActionOrNil value.
+		fileBox doAccept.
+		fileBox okPressed.
+	    ].
+	].
+
+	fileBox showAtPointer.
+	fileBox destroy.
+	fileBox := nil.
     ].
 
     ^ saveName
@@ -25333,34 +25716,34 @@
     unsavedOwners := owningClasses copy.
     unsavedOwners removeAllFoundIn:savedClasses.
     unsavedOwners notEmpty ifTrue:[
-        answer := self confirmWithCancel:'Private classes are saved with their owningClasses;\\Save owners as well ?' withCRs.
-        answer isNil ifTrue:[^ self].
-        answer == true ifTrue:[
-            savedClasses addAll:unsavedOwners
-        ]
+	answer := self confirmWithCancel:'Private classes are saved with their owningClasses;\\Save owners as well ?' withCRs.
+	answer isNil ifTrue:[^ self].
+	answer == true ifTrue:[
+	    savedClasses addAll:unsavedOwners
+	]
     ].
 
     savedClasses do:[:eachClass |
-        |fn answer|
-
-        eachClass isPrivate ifFalse:[
-            self busyLabel:'saving: %1' with:eachClass name.
-            Class fileOutErrorSignal handle:[:ex |
-                answer := DialogBox
-                                confirm:(resources stringWithCRs:'Cannot fileOut: %1\(%2)\\skipped.'
-                                                     with:(eachClass name allBold)
-                                                     with:ex description)
-                                yesLabel:'ok' noLabel:'cancel'.
-                answer == false ifTrue:[
-                    ^ self
-                ].
-                self normalLabel.
-                ex return.
-            ] do:[
-                fn := (Smalltalk fileNameForClass:eachClass) , '.st'.
-                eachClass fileOutAs:(aDirectory asFilename constructString:fn).
-            ]
-        ]
+	|fn answer|
+
+	eachClass isPrivate ifFalse:[
+	    self busyLabel:'saving: %1' with:eachClass name.
+	    Class fileOutErrorSignal handle:[:ex |
+		answer := DialogBox
+				confirm:(resources stringWithCRs:'Cannot fileOut: %1\(%2)\\skipped.'
+						     with:(eachClass name allBold)
+						     with:ex description)
+				yesLabel:'ok' noLabel:'cancel'.
+		answer == false ifTrue:[
+		    ^ self
+		].
+		self normalLabel.
+		ex return.
+	    ] do:[
+		fn := (Smalltalk fileNameForClass:eachClass) , '.st'.
+		eachClass fileOutAs:(aDirectory asFilename constructString:fn).
+	    ]
+	]
     ].
     self normalLabel.
 
@@ -25369,16 +25752,16 @@
 
 spawnCategoryBrowserFor:categories in:where
     "browse selected category(ies);
-        where is: #newBrowser - open a new browser showing the categories
-        where is: #newBuffer  - add a new buffer showing the categories"
+	where is: #newBrowser - open a new browser showing the categories
+	where is: #newBuffer  - add a new buffer showing the categories"
 
     |spec categoryList selectedClasses selectedProtocols selectedMethods
      singleSelection|
 
     (singleSelection := categories size == 1) ifTrue:[
-        spec := #singleCategoryBrowserSpec.
-    ] ifFalse:[
-        spec := #multipleCategoryBrowserSpec.
+	spec := #singleCategoryBrowserSpec.
+    ] ifFalse:[
+	spec := #multipleCategoryBrowserSpec.
     ].
 
     categoryList := categories copy.
@@ -25387,37 +25770,37 @@
     selectedMethods := self selectedMethodsValue copy.
 
     self
-        newBrowserOrBufferDependingOn:where
-        label:nil
-        forSpec:spec
-        setupWith:[:brwsr |
-            |allMeta|
-
-            "/ setup for a constant list ...
-            brwsr immediateUpdate value:true.
-            brwsr categoryListGenerator value:categoryList.
-            brwsr selectCategories:categoryList.
-
-            selectedClasses notNil ifTrue:[
-                allMeta := selectedClasses conform:[:aClass | aClass isMeta].
-                allMeta ifTrue:[
-                    brwsr meta value:true.
-                ]
-            ].
-            selectedClasses size > 0 ifTrue:[brwsr selectClasses:selectedClasses].
-            selectedProtocols size > 0 ifTrue:[brwsr selectProtocols:selectedProtocols].
-            selectedMethods size > 0 ifTrue:[brwsr selectMethods:selectedMethods].
-
-            brwsr immediateUpdate value:false.
-        ]
+	newBrowserOrBufferDependingOn:where
+	label:nil
+	forSpec:spec
+	setupWith:[:brwsr |
+	    |allMeta|
+
+	    "/ setup for a constant list ...
+	    brwsr immediateUpdate value:true.
+	    brwsr categoryListGenerator value:categoryList.
+	    brwsr selectCategories:categoryList.
+
+	    selectedClasses notNil ifTrue:[
+		allMeta := selectedClasses conform:[:aClass | aClass isMeta].
+		allMeta ifTrue:[
+		    brwsr meta value:true.
+		]
+	    ].
+	    selectedClasses size > 0 ifTrue:[brwsr selectClasses:selectedClasses].
+	    selectedProtocols size > 0 ifTrue:[brwsr selectProtocols:selectedProtocols].
+	    selectedMethods size > 0 ifTrue:[brwsr selectMethods:selectedMethods].
+
+	    brwsr immediateUpdate value:false.
+	]
 
     "Modified: / 28-02-2012 / 16:52:32 / cg"
 !
 
 spawnCategoryBrowserIn:where
     "browse selected category(ies);
-        where is: #newBrowser - open a new browser showing the categories
-        where is: #newBuffer  - add a new buffer showing the categories"
+	where is: #newBrowser - open a new browser showing the categories
+	where is: #newBuffer  - add a new buffer showing the categories"
 
     self spawnCategoryBrowserFor:(self selectedCategoriesValue) in:where
 ! !
@@ -25466,61 +25849,61 @@
     classes isEmptyOrNil ifTrue:[^ self].
 
     (theSingleClass := self theSingleSelectedClass) notNil ifTrue:[
-        lbl := 'Check results of ' , theSingleClass name
-    ] ifFalse:[
-        lbl := 'Checker result'
+	lbl := 'Check results of ' , theSingleClass name
+    ] ifFalse:[
+	lbl := 'Checker result'
     ].
     badMethodInfoHolder := ValueHolder new.
     badClassInfoHolder := ValueHolder new.
 
     badMethodsGenerator := [
-        |checker badMethodInfo badClassInfo badMethods|
-
-        checker := ClassChecker new.
-
-        self withWaitCursorDo:[
-            classes do:[:eachClass |
-                |cls|
-
-                cls := eachClass theNonMetaclass.
-                cls isLoaded ifTrue:[
-                    self activityNotification:('checking ' , cls name , '...').
-                    checker checkedClass:cls.
-                    aCollectionOfCheckSymbols do:[:eachCheck |
-                        checker doCheck:eachCheck
-                    ]
-                ]
-            ].
-        ].
-
-        badClassInfo := checker badClassInfo.
-        badMethodInfo := checker badMethodInfo.
-        (badMethodInfo isEmptyOrNil and:[ badClassInfo isEmptyOrNil ]) ifTrue:[
-            "/ self information:'Nothing special found'.
-            badClassInfoHolder value:nil.
-            badMethodInfoHolder value:nil.
-            #().
-        ] ifFalse:[
-            badClassInfoHolder value:badClassInfo.
-            badMethodInfoHolder value:badMethodInfo.
-
-            badMethodInfo size > 0 ifTrue:[
-                badMethods := badMethodInfo keys.
-            ] ifFalse:[
-                badMethods := #()
-            ].
-
-            badMethods
-        ].
-    ].
-
-    self
-        spawnMethodBrowserFor:badMethodsGenerator
-        in:#newBuffer
-        label:lbl
-        perClassInfo:badClassInfoHolder
-        perMethodInfo:badMethodInfoHolder
-        sortBy:#class
+	|checker badMethodInfo badClassInfo badMethods|
+
+	checker := ClassChecker new.
+
+	self withWaitCursorDo:[
+	    classes do:[:eachClass |
+		|cls|
+
+		cls := eachClass theNonMetaclass.
+		cls isLoaded ifTrue:[
+		    self activityNotification:('checking ' , cls name , '...').
+		    checker checkedClass:cls.
+		    aCollectionOfCheckSymbols do:[:eachCheck |
+			checker doCheck:eachCheck
+		    ]
+		]
+	    ].
+	].
+
+	badClassInfo := checker badClassInfo.
+	badMethodInfo := checker badMethodInfo.
+	(badMethodInfo isEmptyOrNil and:[ badClassInfo isEmptyOrNil ]) ifTrue:[
+	    "/ self information:'Nothing special found'.
+	    badClassInfoHolder value:nil.
+	    badMethodInfoHolder value:nil.
+	    #().
+	] ifFalse:[
+	    badClassInfoHolder value:badClassInfo.
+	    badMethodInfoHolder value:badMethodInfo.
+
+	    badMethodInfo size > 0 ifTrue:[
+		badMethods := badMethodInfo keys.
+	    ] ifFalse:[
+		badMethods := #()
+	    ].
+
+	    badMethods
+	].
+    ].
+
+    self
+	spawnMethodBrowserFor:badMethodsGenerator
+	in:#newBuffer
+	label:lbl
+	perClassInfo:badClassInfoHolder
+	perMethodInfo:badMethodInfoHolder
+	sortBy:#class
 
     "Created: / 18-08-2000 / 22:43:56 / cg"
     "Modified: / 28-02-2012 / 16:45:37 / cg"
@@ -25547,14 +25930,14 @@
     allChecks := ClassChecker individualChecks.
     selectedChecks := List new.
     LastIndividualChecks notNil ifTrue:[
-        selectedChecks addAll:LastIndividualChecks
+	selectedChecks addAll:LastIndividualChecks
     ].
 
     selectedChecks := Dialog
-        chooseMultiple:'Select check(s) to perform on selected classes\(toggle items using CTRL-click)\' withCRs
-        fromList:allChecks values:allChecks
-        initialSelection:selectedChecks
-        lines:10.
+	chooseMultiple:'Select check(s) to perform on selected classes\(toggle items using CTRL-click)\' withCRs
+	fromList:allChecks values:allChecks
+	initialSelection:selectedChecks
+	lines:10.
     selectedChecks isNil ifTrue:[^ self].
     LastIndividualChecks := selectedChecks.
     self classMenuCheckEach:selectedChecks.
@@ -25588,9 +25971,9 @@
 runLintOnAllRules
     "run the new smallLint checker tool on all rules"
 
-    self 
-        smalllintCheck: self selectedCodeComponentsAsEnvironment 
-        against: #smalllintRulesAll
+    self
+	smalllintCheck: self selectedCodeComponentsAsEnvironment
+	against: #smalllintRulesAll
 
     "Created: / 07-03-2012 / 17:40:07 / cg"
 !
@@ -25598,9 +25981,9 @@
 runLintOnPreviousRules
     "run the new smallLint checker tool"
 
-    self 
-        smalllintCheck: self selectedCodeComponentsAsEnvironment 
-        against: #smalllintRules
+    self
+	smalllintCheck: self selectedCodeComponentsAsEnvironment
+	against: #smalllintRules
 
     "Modified: / 17-04-2010 / 10:44:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified (comment): / 01-03-2012 / 14:10:47 / cg"
@@ -25610,22 +25993,22 @@
 runLintOnSelectedRules
     "run the new smallLint checker tool on selected rules"
 
-    self 
-        smalllintCheck: self selectedCodeComponentsAsEnvironment 
-        against: #smalllintRulesFromUser
+    self
+	smalllintCheck: self selectedCodeComponentsAsEnvironment
+	against: #smalllintRulesFromUser
 
     "Created: / 07-03-2012 / 17:40:23 / cg"
 !
 
 smalllintRules
 
-   ^LastLintRules 
-        ifNil:[self smalllintRulesFromUser]
-        ifNotNil:[LastLintRules]
-
-
-    "
-        Tools::NewSystemBrowser basicNew smalllintRules
+   ^LastLintRules
+	ifNil:[self smalllintRulesFromUser]
+	ifNotNil:[LastLintRules]
+
+
+    "
+	Tools::NewSystemBrowser basicNew smalllintRules
     "
 
     "Modified: / 17-04-2010 / 09:42:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -25645,11 +26028,11 @@
 
 addClassesToRemoveForClass:aClass to:classesToRemove removingSubclasses:removingSubclasses withCancel:withCancel
     self
-        addClassesToRemoveForClass:aClass
-        to:classesToRemove
-        removingSubclasses:removingSubclasses
-        withCancel:withCancel
-        withConfirm:true
+	addClassesToRemoveForClass:aClass
+	to:classesToRemove
+	removingSubclasses:removingSubclasses
+	withCancel:withCancel
+	withConfirm:true
 !
 
 addClassesToRemoveForClass:aClass to:classesToRemove removingSubclasses:removingSubclasses withCancel:withCancel withConfirm:withConfirm
@@ -25657,225 +26040,225 @@
      answer toRemove stillSearchingForMore more|
 
     (classesToRemove includes:aClass) ifTrue:[
-        "/ already in list
-        ^ self
+	"/ already in list
+	^ self
     ].
 
     aClass wasAutoloaded ifTrue:[
-        answer := self
-                    confirmWithCancel:(resources
-                            string:'%1 was autoloaded.\\Reinstall as autoloaded ?'
-                            with:aClass name allBold) withCRs.
-        answer isNil ifTrue:[
-            ^ self
-        ].
-        answer == true ifTrue:[
-            self withWaitCursorDo:[
-                    aClass unload.
-                    Smalltalk changed:#classDefinition with:aClass
-                ].
-            ^ self
-        ]
+	answer := self
+		    confirmWithCancel:(resources
+			    string:'%1 was autoloaded.\\Reinstall as autoloaded ?'
+			    with:aClass name allBold) withCRs.
+	answer isNil ifTrue:[
+	    ^ self
+	].
+	answer == true ifTrue:[
+	    self withWaitCursorDo:[
+		    aClass unload.
+		    Smalltalk changed:#classDefinition with:aClass
+		].
+	    ^ self
+	]
     ].
 
     countSubClasses := aClass allSubclasses size.
     t := 'Remove Class ''%1'''.
     countSubClasses ~~ 0 ifTrue:[
-        removingSubclasses ifTrue:[
-            t := t , '\(with %2 subclass'.
-        ] ifFalse:[
-            t := t , '\(and pull up %2 subclass'.
-        ].
-        countSubClasses ~~ 1 ifTrue:[
-            t := t , 'es'
-        ]
+	removingSubclasses ifTrue:[
+	    t := t , '\(with %2 subclass'.
+	] ifFalse:[
+	    t := t , '\(and pull up %2 subclass'.
+	].
+	countSubClasses ~~ 1 ifTrue:[
+	    t := t , 'es'
+	]
     ].
 
     countPrivateClasses := aClass allPrivateClasses size.
     countPrivateClasses ~~ 0 ifTrue:[
-        removingSubclasses ifFalse:[
-            self warn:('%1 has private classes - please make them public; then try again' bindWith:aClass name allBold).
-            ^ self
-        ].
-
-        countSubClasses ~~ 0 ifTrue:[
-            t := t , ' and'
-        ] ifFalse:[
-            t := t , '\(with'
-        ].
-        t := t , ' %3 private class'.
-        countPrivateClasses ~~ 1 ifTrue:[
-            t := t , 'es'
-        ]
+	removingSubclasses ifFalse:[
+	    self warn:('%1 has private classes - please make them public; then try again' bindWith:aClass name allBold).
+	    ^ self
+	].
+
+	countSubClasses ~~ 0 ifTrue:[
+	    t := t , ' and'
+	] ifFalse:[
+	    t := t , '\(with'
+	].
+	t := t , ' %3 private class'.
+	countPrivateClasses ~~ 1 ifTrue:[
+	    t := t , 'es'
+	]
     ].
 
     (countSubClasses ~~ 0 or:[countPrivateClasses ~~ 0]) ifTrue:[
-        t := t , ')'
+	t := t , ')'
     ].
     t := t , ' ?'.
     t := (resources
-                string:t
-                with:aClass name allBold
-                with:countSubClasses
-                with:countPrivateClasses) withCRs.
+		string:t
+		with:aClass name allBold
+		with:countSubClasses
+		with:countPrivateClasses) withCRs.
 
     YesToAllConfirmation query ifTrue:[
     ] ifFalse:[
-        (countSubClasses ~~ 0 or:[countPrivateClasses ~~ 0 or:[withConfirm]]) ifTrue:[
-            withCancel ifTrue:[
-                confirmed := OptionBox
-                              request:t
-                              label:(resources string:'Remove Class')
-                              image:(YesNoBox iconBitmap)
-                              buttonLabels:(resources array:#('Cancel' 'No' 'Yes' 'Yes to All'))
-                              values:#(nil false true #yesToAll)
-                              default:false
-                              onCancel:false.
-                "/ confirmed := Dialog confirmWithCancel:t default:false
-            ] ifFalse:[
-                confirmed := Dialog confirm:t
-            ].
-            confirmed isNil ifTrue:[
-                "/ cancelled
-                AbortOperationRequest raise
-            ].
-            confirmed == #yesToAll ifTrue:[
-                YesToAllConfirmation notify.
-                confirmed := true.
-            ].
-
-            confirmed ifFalse:[
-                ^ self
-            ]
-        ].
+	(countSubClasses ~~ 0 or:[countPrivateClasses ~~ 0 or:[withConfirm]]) ifTrue:[
+	    withCancel ifTrue:[
+		confirmed := OptionBox
+			      request:t
+			      label:(resources string:'Remove Class')
+			      image:(YesNoBox iconBitmap)
+			      buttonLabels:(resources array:#('Cancel' 'No' 'Yes' 'Yes to All'))
+			      values:#(nil false true #yesToAll)
+			      default:false
+			      onCancel:false.
+		"/ confirmed := Dialog confirmWithCancel:t default:false
+	    ] ifFalse:[
+		confirmed := Dialog confirm:t
+	    ].
+	    confirmed isNil ifTrue:[
+		"/ cancelled
+		AbortOperationRequest raise
+	    ].
+	    confirmed == #yesToAll ifTrue:[
+		YesToAllConfirmation notify.
+		confirmed := true.
+	    ].
+
+	    confirmed ifFalse:[
+		^ self
+	    ]
+	].
     ].
 
     didRemove := false.
     includesBuiltIn := aClass isBuiltInClass.
     aClass allSubclassesDo:[:aSubClass |
-            includesBuiltIn := includesBuiltIn or:[aSubClass isBuiltInClass]
-        ].
+	    includesBuiltIn := includesBuiltIn or:[aSubClass isBuiltInClass]
+	].
     includesBuiltIn ifTrue:[
-        "/ ask again - severe damage is to be expected ...
-
-        confirmed := Dialog
-                    confirmWithCancel:'The set of classes to remove includes at least one systemClass,\without which ST/X will fail to work.\Be prepared for a crash, if you proceed.\\Really remove ?'
-                            withCRs
-                    default:false.
-        confirmed isNil ifTrue:[
-            "/ cancelled
-
-            AbortSignal raise
-        ].
-        confirmed ifFalse:[
-            ^ self
-        ]
+	"/ ask again - severe damage is to be expected ...
+
+	confirmed := Dialog
+		    confirmWithCancel:'The set of classes to remove includes at least one systemClass,\without which ST/X will fail to work.\Be prepared for a crash, if you proceed.\\Really remove ?'
+			    withCRs
+		    default:false.
+	confirmed isNil ifTrue:[
+	    "/ cancelled
+
+	    AbortSignal raise
+	].
+	confirmed ifFalse:[
+	    ^ self
+	]
     ].
 
     "/ check if any of the classes to remove has a repository container - warn about this if so
     aClass withAllSubclassesDo:[:eachClassToRemove |
-        eachClassToRemove isPrivate ifFalse:[
-            eachClassToRemove revision notNil ifTrue:[
-                (removingSubclasses or:[eachClassToRemove == aClass])
-                ifTrue:[
-                    "JV@2012-02-09: Only ask if configured source code manager is CVS,
-                     as other managers handles removals nicely (they version whole tree).
-                     Such a query is not only annoying but also  confusing to newcomers
-                    "
-                    eachClassToRemove sourceCodeManager isCVS ifTrue:[
-                        confirmed := Dialog
-                                    confirmWithCancel:(resources
-                                            string:'Remove the source container for ''%1'' in the repository ?\\Warning: can only be undone by manually fixing the CVS repository !!'
-                                            with:eachClassToRemove name allBold) withCRs
-                                    default:false.
-                    ] ifFalse:[
-                        "JV@2012-02-09: Mhh, mhh, what to return here?"
-                        confirmed := false. "/false avoids timely listing of huge expecco's repository,
-                                            "/Obviously, this should be fixed in libsvn.
-                    ].
-                    confirmed isNil ifTrue:[
-                        "/ cancelled
-
-                        AbortSignal raise
-                    ].
-                    confirmed ifTrue:[
-                        "JV@2012-02-09: Use class's sourcecode manager's utilities, 
-                         not default one"
-                        eachClassToRemove sourceCodeManager utilities
-                            removeSourceContainerForClass:eachClassToRemove
-                            confirm:true
-                            warn:true
-                    ]
-                ]
-            ].
-        ]
+	eachClassToRemove isPrivate ifFalse:[
+	    eachClassToRemove revision notNil ifTrue:[
+		(removingSubclasses or:[eachClassToRemove == aClass])
+		ifTrue:[
+		    "JV@2012-02-09: Only ask if configured source code manager is CVS,
+		     as other managers handles removals nicely (they version whole tree).
+		     Such a query is not only annoying but also  confusing to newcomers
+		    "
+		    eachClassToRemove sourceCodeManager isCVS ifTrue:[
+			confirmed := Dialog
+				    confirmWithCancel:(resources
+					    string:'Remove the source container for ''%1'' in the repository ?\\Warning: can only be undone by manually fixing the CVS repository !!'
+					    with:eachClassToRemove name allBold) withCRs
+				    default:false.
+		    ] ifFalse:[
+			"JV@2012-02-09: Mhh, mhh, what to return here?"
+			confirmed := false. "/false avoids timely listing of huge expecco's repository,
+					    "/Obviously, this should be fixed in libsvn.
+		    ].
+		    confirmed isNil ifTrue:[
+			"/ cancelled
+
+			AbortSignal raise
+		    ].
+		    confirmed ifTrue:[
+			"JV@2012-02-09: Use class's sourcecode manager's utilities,
+			 not default one"
+			eachClassToRemove sourceCodeManager utilities
+			    removeSourceContainerForClass:eachClassToRemove
+			    confirm:true
+			    warn:true
+		    ]
+		]
+	    ].
+	]
     ].
 
     "/ check if any of the classes to be removed from the ProjectDefinition
     aClass withAllSubclassesDo:[:eachClassToRemove |
-        eachClassToRemove isPrivate ifFalse:[
-            |def|
-
-            def := eachClassToRemove projectDefinitionClass.
-            def notNil and:[
-                (eachClassToRemove ~~ def
-                and:[ def allClassNames includes:eachClassToRemove name ]) ifTrue:[
-                    (Dialog confirm:(resources string:'Remove %1 from its Package definition ?'
-                                                 with:eachClassToRemove name))
-                    ifTrue:[
-                        self excludeClasses: (Array with: eachClassToRemove) fromProject:def using:Compiler.
-                    ].
-                ]
-            ]
-        ]
+	eachClassToRemove isPrivate ifFalse:[
+	    |def|
+
+	    def := eachClassToRemove projectDefinitionClass.
+	    def notNil and:[
+		(eachClassToRemove ~~ def
+		and:[ def allClassNames includes:eachClassToRemove name ]) ifTrue:[
+		    (Dialog confirm:(resources string:'Remove %1 from its Package definition ?'
+						 with:eachClassToRemove name))
+		    ifTrue:[
+			self excludeClasses: (Array with: eachClassToRemove) fromProject:def using:Compiler.
+		    ].
+		]
+	    ]
+	]
     ].
 
     toRemove := IdentitySet new.
     toRemove addAll:classesToRemove.
 
     removingSubclasses ifTrue:[
-        aClass allSubclassesDo:[:aSubClass |
-            (CheckForInstancesWhenRemovingClasses == false or:[
-                    aSubClass hasInstances not or:[
-                            self confirm:(resources string:'''%1'' has instances - remove anyway ?'
-                                                    with:aSubClass name allBold)
-                        ]
-                ]) ifTrue:[
-                classesToRemove add:aSubClass.
-                toRemove add:aSubClass
-            ]
-        ].
+	aClass allSubclassesDo:[:aSubClass |
+	    (CheckForInstancesWhenRemovingClasses == false or:[
+		    aSubClass hasInstances not or:[
+			    self confirm:(resources string:'''%1'' has instances - remove anyway ?'
+						    with:aSubClass name allBold)
+			]
+		]) ifTrue:[
+		classesToRemove add:aSubClass.
+		toRemove add:aSubClass
+	    ]
+	].
     ].
     (CheckForInstancesWhenRemovingClasses == false or:[
-            aClass hasInstances not or:[
-                    self confirm:(resources string:'''%1'' has instances - remove anyway ?'
-                                with:aClass name allBold)
-                ]
+	    aClass hasInstances not or:[
+		    self confirm:(resources string:'''%1'' has instances - remove anyway ?'
+				with:aClass name allBold)
+		]
      ]) ifTrue:[
-        didRemove := true.
-        aClass allPrivateClassesDo:[:eachPrivate |
-                classesToRemove addFirst:eachPrivate.
-                toRemove add:eachPrivate
-            ].
-        classesToRemove add:aClass.
-        toRemove add:aClass
+	didRemove := true.
+	aClass allPrivateClassesDo:[:eachPrivate |
+		classesToRemove addFirst:eachPrivate.
+		toRemove add:eachPrivate
+	    ].
+	classesToRemove add:aClass.
+	toRemove add:aClass
     ].
 
     stillSearchingForMore := true.
     [
-        stillSearchingForMore
+	stillSearchingForMore
     ] whileTrue:[
-        stillSearchingForMore := false.
-        more := IdentitySet new.
-        classesToRemove do:[:eachClass |
-            eachClass allPrivateClasses do:[:eachPrivate |
-                classesToRemove addFirst:eachPrivate.
-                (toRemove includes:eachPrivate) ifFalse:[
-                    toRemove add:eachPrivate.
-                    more := true
-                ]
-            ]
-        ]
+	stillSearchingForMore := false.
+	more := IdentitySet new.
+	classesToRemove do:[:eachClass |
+	    eachClass allPrivateClasses do:[:eachPrivate |
+		classesToRemove addFirst:eachPrivate.
+		(toRemove includes:eachPrivate) ifFalse:[
+		    toRemove add:eachPrivate.
+		    more := true
+		]
+	    ]
+	]
     ]
 
     "Modified: / 21-12-2011 / 20:22:34 / cg"
@@ -25889,67 +26272,67 @@
     "/ provide a reasonable default in the pull-down-list
     currentClass := self anySelectedClass.
     currentClass isNil ifTrue:[
-        m := self anySelectedMethod.
-        currentClass := m mclass.
+	m := self anySelectedMethod.
+	currentClass := m mclass.
     ].
 
     LastMethodMoveOrCopyTargetClass notNil ifTrue:[
-        initial := Smalltalk classNamed:LastMethodMoveOrCopyTargetClass.
-        initial notNil ifTrue:[
-            (currentClass notNil and:[currentClass theNonMetaclass name = initial name]) ifTrue:[
-                initial := nil
-            ]
-        ].
-        initial notNil ifTrue:[
-            currentClass isMeta ifTrue:[
-                initial := initial theMetaclass
-            ] ifFalse:[
-                initial := initial theNonMetaclass
-            ].
-            initial := initial name.
-        ].
+	initial := Smalltalk classNamed:LastMethodMoveOrCopyTargetClass.
+	initial notNil ifTrue:[
+	    (currentClass notNil and:[currentClass theNonMetaclass name = initial name]) ifTrue:[
+		initial := nil
+	    ]
+	].
+	initial notNil ifTrue:[
+	    currentClass isMeta ifTrue:[
+		initial := initial theMetaclass
+	    ] ifFalse:[
+		initial := initial theNonMetaclass
+	    ].
+	    initial := initial name.
+	].
     ].
 
     initial isNil ifTrue:[
-        (sup := currentClass superclass) notNil ifTrue:[
-            initial := sup name
-        ] ifFalse:[
-            initial := nil.
-        ].
+	(sup := currentClass superclass) notNil ifTrue:[
+	    initial := sup name
+	] ifFalse:[
+	    initial := nil.
+	].
     ].
 
     supers := currentClass allSuperclasses reverse.
     currentClass isMeta ifTrue:[
-        supers := supers select:[:each | each isSubclassOf:Class].
+	supers := supers select:[:each | each isSubclassOf:Class].
     ].
     supers := supers collect:[:cls | cls name].
 
     list := supers.
 
     self selectedClassesValue size > 1 ifTrue:[
-        reqString := 'Generate isXXX methods in which superclass ?'.
-        title := 'Generate isXXX methods'.
-    ] ifFalse:[
-        reqString := 'Generate %1 method in which superclass ?'.
-        title := 'Generate %1 method'.
+	reqString := 'Generate isXXX methods in which superclass ?'.
+	title := 'Generate isXXX methods'.
+    ] ifFalse:[
+	reqString := 'Generate %1 method in which superclass ?'.
+	title := 'Generate %1 method'.
     ].
     okLabel := 'Generate'.
 
     newClassName := Dialog
-                    request:(resources stringWithCRs:reqString with:selector)
-                    initialAnswer:(initial ? '')
-                    okLabel:(resources string:okLabel)
-                    title:(resources string:title with:selector)
-                    onCancel:nil
-                    list:list
-                    entryCompletionBlock:(DoWhatIMeanSupport classNameEntryCompletionBlock).
+		    request:(resources stringWithCRs:reqString with:selector)
+		    initialAnswer:(initial ? '')
+		    okLabel:(resources string:okLabel)
+		    title:(resources string:title with:selector)
+		    onCancel:nil
+		    list:list
+		    entryCompletionBlock:(DoWhatIMeanSupport classNameEntryCompletionBlock).
 
     newClassName isNil ifTrue:[^ nil].
     (newClassName startsWith:'---- ') ifTrue:[^ nil].
 
     newClass := self classIfValidNonMetaClassName:newClassName.
     newClass isNil ifTrue:[
-        ^ nil
+	^ nil
     ].
 
     LastMethodMoveOrCopyTargetClass := newClass theNonMetaclass name.
@@ -25969,26 +26352,26 @@
     warningCollector errorsOnly:errorsOnly.
 
     aClass theNonMetaclass withAllPrivateClassesDo:[:eachClass |
-        eachClass instAndClassSelectorsAndMethodsDo:[:aSelector :aMethod | 
-            Parser warningSignal 
-                handle:[:ex | self halt ]
-                do:[
-                    aMethod source isEmpty ifTrue:[
-                        outStream nextPutAll:'No source for method: ',aMethod whoString
-                    ] ifFalse:[
-                        eachClass compilerClass new
-                            compile:aMethod source
-                            forClass:aMethod mclass
-                            inCategory:'others'
-                            notifying:warningCollector
-                            install:false
-                            skipIfSame:false
-                            silent:false
-                            foldConstants:true
-                            ifFail:[ outStream nextPutAll:'not compilable: ',aMethod whoString ]
-                    ]
-                ]
-        ].
+	eachClass instAndClassSelectorsAndMethodsDo:[:aSelector :aMethod |
+	    Parser warningSignal
+		handle:[:ex | self halt ]
+		do:[
+		    aMethod source isEmpty ifTrue:[
+			outStream nextPutAll:'No source for method: ',aMethod whoString
+		    ] ifFalse:[
+			eachClass compilerClass new
+			    compile:aMethod source
+			    forClass:aMethod mclass
+			    inCategory:'others'
+			    notifying:warningCollector
+			    install:false
+			    skipIfSame:false
+			    silent:false
+			    foldConstants:true
+			    ifFail:[ outStream nextPutAll:'not compilable: ',aMethod whoString ]
+		    ]
+		]
+	].
     ].
 
     "Created: / 02-11-2010 / 13:11:17 / cg"
@@ -26013,7 +26396,7 @@
      (meant for a human to read)"
 
     aCollectionOfClasses do:[:eachClass |
-        self checkCompilabilityOf:eachClass errorsOnly:errorsOnly outputTo:outStream.
+	self checkCompilabilityOf:eachClass errorsOnly:errorsOnly outputTo:outStream.
     ].
 
     "Created: / 02-11-2010 / 13:11:47 / cg"
@@ -26023,12 +26406,12 @@
     "perform all checks on the selected class(es)."
 
     ClassEnvironment isNil ifTrue:[
-        Dialog warn:'Missing refactoryBrowser/browser package'.
-        ^ self.
-    ].
-    self 
-        smalllintCheck:self selectedClassesAsEnvironment
-        against: what
+	Dialog warn:'Missing refactoryBrowser/browser package'.
+	^ self.
+    ].
+    self
+	smalllintCheck:self selectedClassesAsEnvironment
+	against: what
 
     "Modified: / 28-12-2008 / 14:42:01 / bazantj <enter your email here>"
     "Modified: / 13-01-2009 / 13:20:48 / Jiri Bazant <bazanj2@fel.cvut.cz>"
@@ -26042,8 +26425,8 @@
      Also, set acceptaction to install the class."
 
     ^ self
-        classClassDefinitionTemplateFor:aClass in:cat
-        asNamespace:isNameSpace private:isPrivate metaClassUsed:nil
+	classClassDefinitionTemplateFor:aClass in:cat
+	asNamespace:isNameSpace private:isPrivate metaClassUsed:nil
 !
 
 classClassDefinitionTemplateFor:aClass in:cat asNamespace:isNameSpace private:isPrivate metaClassUsed:metaClassUsedOrNil
@@ -26055,23 +26438,23 @@
 
     (aClass == Autoload
     or:[aClass isNil or:[aClass isLoaded not]]) ifTrue:[
-        self javaMode ifTrue:[
-            theSuperClass := Java at:'java.lang.Object'
-        ] ifFalse:[
-            theSuperClass := Object
-        ]
-    ] ifFalse:[
-        theSuperClass := aClass
+	self javaMode ifTrue:[
+	    theSuperClass := Java at:'java.lang.Object'
+	] ifFalse:[
+	    theSuperClass := Object
+	]
+    ] ifFalse:[
+	theSuperClass := aClass
     ].
 
 "/    self switchToClass:nil.
 
     self showCode:(self
-                        classTemplateFor:theSuperClass
-                        in:cat
-                        asNamespace:isNameSpace
-                        private:isPrivate
-                        metaClassUsed:metaClassUsedOrNil).
+			classTemplateFor:theSuperClass
+			in:cat
+			asNamespace:isNameSpace
+			private:isPrivate
+			metaClassUsed:metaClassUsedOrNil).
 
     self setAcceptActionForMetaClassUsed:metaClassUsedOrNil.
     self codeAspect:#newClassDefinition.
@@ -26091,7 +26474,7 @@
     className isNil ifTrue:[^ self].
     class := Smalltalk at:className asSymbol ifAbsent:nil.
     class isNil ifTrue:[
-        ^ self warn:'No such class'
+	^ self warn:'No such class'
     ].
     classList add:class.
     classList sort:[:a :b | a name < b name].
@@ -26109,7 +26492,7 @@
 
     classesToHide := self selectedClassesValue copy.
     classesToHide do:[:classToHide |
-        classList removeIdentical:classToHide
+	classList removeIdentical:classToHide
     ].
     classList sort:[:a :b | a name < b name].
 
@@ -26133,20 +26516,20 @@
 
     cls := self theSingleSelectedClass.
     cls notNil ifTrue:[
-        cls := cls theNonMetaclass
+	cls := cls theNonMetaclass
     ].
 
     aspect == #classComment ifTrue:[
-        self showClassComment:cls.
-        ^ self
+	self showClassComment:cls.
+	^ self
     ].
     aspect == #classHierarchy ifTrue:[
-        self showClassHierarchy:cls.
-        ^ self
+	self showClassHierarchy:cls.
+	^ self
     ].
     aspect == #classDefinition ifTrue:[
-        self showClassDefinition:cls.
-        ^ self
+	self showClassDefinition:cls.
+	^ self
     ].
 
     self error:'unknown aspect: ', aspect printString.
@@ -26162,7 +26545,7 @@
 
     allMessages := self checkCompilabilityOfAll:(self selectedClassesValue) errorsOnly:false.
     allMessages notEmpty ifTrue:[
-        Dialog warn:allMessages
+	Dialog warn:allMessages
     ].
 
     "Created: / 16-11-2006 / 14:53:21 / cg"
@@ -26175,22 +26558,22 @@
 
     currentClass := self theSingleSelectedLoadedNonMetaclassOrNil.
     currentClass isNil ifTrue:[
-        self warn:'Cannot copy unloaded classes.'.
-        ^ self
+	self warn:'Cannot copy unloaded classes.'.
+	^ self
     ].
 
     name := Dialog request:(resources
-                                string:'Enter name for new parent class of "%1" and its subclasses:'
-                                with:currentClass name allBold).
+				string:'Enter name for new parent class of "%1" and its subclasses:'
+				with:currentClass name allBold).
     name isEmpty ifTrue: [^self].
 
     subclasses := self selectSubclassesOf:currentClass.
     subclasses isNil ifTrue: [^self].
 
     self performRefactoring:
-            (ChildrenToSiblingsRefactoring name: name
-                    class: currentClass
-                    subclasses: subclasses).
+	    (ChildrenToSiblingsRefactoring name: name
+		    class: currentClass
+		    subclasses: subclasses).
 
     self switchToClassNamed:name.
 "/            meta: self isMeta
@@ -26203,12 +26586,12 @@
     "remove all changes for the selected class(es) from the changeSet"
 
     (self confirm:'This will remove all changes for the selected class(es) from the changeSet.\\Really cleanup ?' withCRs)
-        ifFalse:[ ^ self].
+	ifFalse:[ ^ self].
 
     self withWaitCursorDo:[
-        self selectedClassesDo:[:eachClass |
-            ChangeSet current condenseChangesForClass:eachClass
-        ].
+	self selectedClassesDo:[:eachClass |
+	    ChangeSet current condenseChangesForClass:eachClass
+	].
     ]
 !
 
@@ -26228,9 +26611,9 @@
 
     sel := self selectedNonMetaclasses value.
     sel size == 2 ifTrue:[
-        class1 := sel first.
-        class2 := sel second.
-        self doCompareClass:class1 withClass:class2
+	class1 := sel first.
+	class2 := sel second.
+	self doCompareClass:class1 withClass:class2
     ]
 
     "Modified: / 12-09-2006 / 13:52:57 / cg"
@@ -26244,32 +26627,32 @@
 
     currentClass := self theSingleSelectedLoadedNonMetaclassOrNil.
     currentClass isNil ifTrue:[
-        self warn:'Cannot compare unloaded classes.'.
-        ^ self.
+	self warn:'Cannot compare unloaded classes.'.
+	^ self.
     ].
 
     supers := (currentClass allSuperclasses reverse collect:[:cls | cls name]).
     subs := (currentClass allSubclasses collect:[:cls | cls name]).
     list := supers.
     (supers notEmpty and:[subs notEmpty]) ifTrue:[
-        list := list , (Array with:'---- ' , currentClass name , ' ----')
+	list := list , (Array with:'---- ' , currentClass name , ' ----')
     ].
     list := list , subs.
 
     otherClassName := Dialog
-                    request:(resources string:'Compare this class against which class:')
-                    initialAnswer:''
-                    okLabel:(resources string:'Compare')
-                    title:(resources string:'Compare class')
-                    onCancel:nil
-                    list:list.
+		    request:(resources string:'Compare this class against which class:')
+		    initialAnswer:''
+		    okLabel:(resources string:'Compare')
+		    title:(resources string:'Compare class')
+		    onCancel:nil
+		    list:list.
     otherClassName isNil ifTrue:[^ self].
     (otherClassName startsWith:'---- ') ifTrue:[^ self].
 
     otherClass := Smalltalk classNamed:otherClassName.
     otherClass isNil ifTrue:[
-        self warn:'no such class: ', otherClassName.
-        ^ self
+	self warn:'no such class: ', otherClassName.
+	^ self
     ].
 
     otherClass := otherClass theNonMetaclass.
@@ -26282,11 +26665,11 @@
     "compile selected classes' lazy methods (kludge - for me)"
 
     self selectedClassesDo:[:eachClass |
-        eachClass instAndClassSelectorsAndMethodsDo:[:sel :mthd |
-            mthd isLazyMethod ifTrue:[
-                mthd makeRealMethod
-            ]
-        ]
+	eachClass instAndClassSelectorsAndMethodsDo:[:sel :mthd |
+	    mthd isLazyMethod ifTrue:[
+		mthd makeRealMethod
+	    ]
+	]
     ].
 !
 
@@ -26298,8 +26681,8 @@
 
     currentClass := self theSingleSelectedLoadedNonMetaclassOrNil.
     currentClass isNil ifTrue:[
-        self warn:'Cannot copy unloaded classes.'.
-        ^ self
+	self warn:'Cannot copy unloaded classes.'.
+	^ self
     ].
 
     currentClassName := currentClass name.
@@ -26311,62 +26694,63 @@
 "/    ].
 
     newClassName := Dialog
-                        request:(resources string:'Copy class %1 as:' with:currentClassName allBold)
-                        initialAnswer:newClassName.
+			request:(resources string:'Copy class %1 as:' with:currentClassName allBold)
+			initialAnswer:newClassName.
     (newClassName isEmptyOrNil or:[newClassName withoutSeparators = currentClassName]) ifTrue:[
-        ^ self
+	^ self
     ].
     (Smalltalk classNamed:newClassName) notNil ifTrue:[
-        (self confirm:(resources string:'A class named: ''%1'' already exists.\\Overwrite ?' with:newClassName) withCRs)
-            ifFalse:[^ self]
+	(self confirm:(resources string:'A class named: ''%1'' already exists.\\Overwrite ?' with:newClassName) withCRs)
+	    ifFalse:[^ self]
     ].
     (owningClass := currentClass owningClass) notNil ifTrue:[
-        (newClassName startsWith:(owningClass name , '::')) ifTrue:[
-            newClassName := newClassName copyFrom:(owningClass name , '::') size + 1.
-            newOwnerClass := owningClass.
-        ] ifFalse:[
-            (newClassName includes:$:) ifTrue:[
-                idx := newClassName lastIndexOf:$:.
-                ownerName := newClassName copyTo:idx.
-                [ownerName endsWith:$:] whileTrue:[ownerName := ownerName copyWithoutLast:1].
-                newClassName := newClassName copyFrom:idx+1.
-            ] ifFalse:[
-                (self confirm:(resources string:'Copy as public class ''%1'' ?' with:newClassName) withCRs)
-                    ifFalse:[^ self].
-            ]
-        ].
-    ] ifFalse:[
-        idx := newClassName lastIndexOf:$:.
-        idx ~~ 0 ifTrue:[
-            ownerName := newClassName copyTo:idx-2.
-            newClassName := newClassName copyFrom:idx+1.
-        ].
+	(newClassName startsWith:(owningClass name , '::')) ifTrue:[
+	    newClassName := newClassName copyFrom:(owningClass name , '::') size + 1.
+	    newOwnerClass := owningClass.
+	] ifFalse:[
+	    (newClassName includes:$:) ifTrue:[
+		idx := newClassName lastIndexOf:$:.
+		ownerName := newClassName copyTo:idx.
+		[ownerName endsWith:$:] whileTrue:[ownerName := ownerName copyWithoutLast:1].
+		newClassName := newClassName copyFrom:idx+1.
+	    ] ifFalse:[
+		(self confirm:(resources string:'Copy as public class ''%1'' ?' with:newClassName) withCRs)
+		    ifFalse:[^ self].
+	    ]
+	].
+    ] ifFalse:[
+	idx := newClassName lastIndexOf:$:.
+	idx ~~ 0 ifTrue:[
+	    ownerName := newClassName copyTo:idx-2.
+	    newClassName := newClassName copyFrom:idx+1.
+	].
     ].
 
     ownerName notNil ifTrue:[
-        (Smalltalk classNamed:ownerName) isNil ifTrue:[
-            (Dialog confirm:(resources 
-                                stringWithCRs:'No class or nameSpace named: "%1"\\Create as Namespace ?' with:ownerName))
-            ifFalse:[
-                ^ self
-            ].
-            newOwnerClass := NameSpace fullName:ownerName. 
-        ].
-        newOwnerClass := Smalltalk at:ownerName asSymbol.
-        (newOwnerClass == Smalltalk or:[newOwnerClass isNameSpace]) ifTrue:[
-            newOwnerClass == Smalltalk ifFalse:[
-                newClassName := ownerName , '::' , newClassName.
-            ].
-            newOwnerClass := nil.
-        ].
+	(Smalltalk classNamed:ownerName) isNil ifTrue:[
+	    (Dialog confirm:(resources
+				stringWithCRs:'No class or nameSpace named: "%1"\\Create as Namespace ?' with:ownerName))
+	    ifFalse:[
+		^ self
+	    ].
+	    newOwnerClass := NameSpace fullName:ownerName.
+	].
+	newOwnerClass := Smalltalk at:ownerName asSymbol.
+	(newOwnerClass == Smalltalk or:[newOwnerClass isNameSpace]) ifTrue:[
+	    newOwnerClass == Smalltalk ifFalse:[
+		newClassName := ownerName , '::' , newClassName.
+	    ].
+	    newOwnerClass := nil.
+	].
     ].
 
     self busyLabel:'copying class ...' with:nil.
     self withWaitCursorDo:[
-        newClass := self doCopyClass:currentClass as:newClassName privateIn:newOwnerClass.
-    ].
-
-    "Modified: / 01-03-2007 / 20:50:33 / cg"
+	newClass := self doCopyClass:currentClass as:newClassName privateIn:newOwnerClass.
+    ].
+    self selectClass:newClass.
+
+    "Modified: / 24-05-2012 / 15:49:14 / cg"
 !
 
 classMenuDefinition
@@ -26382,17 +26766,17 @@
     "show classes documentation (i.e. open doc-View on it)"
 
     self
-        selectedClassesNonMetaDo:
-            [:cls |
-                self openClassDocumentationFor:cls
-            ]
-        ifUnloaded:
-            [:cls |
-                true
-            ]
-        ifPrivate:
-            [:cls |
-            ]
+	selectedClassesNonMetaDo:
+	    [:cls |
+		self openClassDocumentationFor:cls
+	    ]
+	ifUnloaded:
+	    [:cls |
+		true
+	    ]
+	ifPrivate:
+	    [:cls |
+	    ]
 !
 
 classMenuExcludeFromProject
@@ -26401,16 +26785,16 @@
     projectDefinitionClasses := (self selectedClassesValue collect:[:cls | cls projectDefinitionClass]) asSet.
 
     projectDefinitionClasses do:[:eachDefinitionClass |
-        |toExcludeForThis|
-
-        toExcludeForThis := self selectedClassesValue select:[:cls | cls projectDefinitionClass == eachDefinitionClass].
-
-        self
-            generateUndoableChange:(resources string:'Exclude %1 class(es) from Project %2' with:toExcludeForThis size with:eachDefinitionClass name)
-            overClasses:(Array with: eachDefinitionClass)
-            via:[:generator :projectDefinition |
-                self excludeClasses:toExcludeForThis fromProject:projectDefinition using:generator
-            ].
+	|toExcludeForThis|
+
+	toExcludeForThis := self selectedClassesValue select:[:cls | cls projectDefinitionClass == eachDefinitionClass].
+
+	self
+	    generateUndoableChange:(resources string:'Exclude %1 class(es) from Project %2' with:toExcludeForThis size with:eachDefinitionClass name)
+	    overClasses:(Array with: eachDefinitionClass)
+	    via:[:generator :projectDefinition |
+		self excludeClasses:toExcludeForThis fromProject:projectDefinition using:generator
+	    ].
     ].
 
     "Created: / 19-02-2007 / 17:29:12 / cg"
@@ -26425,47 +26809,47 @@
 
 classMenuFileOutAsWithFormat:aFormatSymbolOrNil
     "fileOut selected classes -  file format as specified by the argument:
-        nil     - standard format
-        #xml    - XML standard format
-        #sif    - SIF (smalltalk interchange file) standard format
-        #binary - ST/X binary format
+	nil     - standard format
+	#xml    - XML standard format
+	#sif    - SIF (smalltalk interchange file) standard format
+	#binary - ST/X binary format
     "
 
     |mode|
 
     aFormatSymbolOrNil == #binary ifTrue:[
-        mode := Dialog choose:(resources string:'Save including sources ?')
-                       labels:(resources array:#('Cancel' 'Discard' 'By file reference' 'Include source'))
-                       values:#(nil #discard #reference #keep)
-                       default:#keep.
-
-        mode isNil ifTrue:[^ self].   "/ cancelled
-    ].
-
-    self
-        selectedClassesNonMetaDo:
-            [:cls |
-               self
-                   fileOutClass:cls
-                   askForFile:true
-                   withCancelAll:(self selectedClassesValue size > 1)
-                   format:aFormatSymbolOrNil
-                   sourceMode:mode.
-            ]
-        ifUnloaded:
-            [:cls |
-                self warn:'Cannot fileOut unloaded class: %1' with:cls name allBold.
-                false.
-            ]
-        ifPrivate:
-            [:cls | |owner|
-                owner := cls owningClass.
-                (self selectedClassesValue includes:owner) ifFalse:[
-                    self warn:'Cannot fileOut private class: %1\\Please fileOut the owning class (%2).'
-                        with:cls nameWithoutPrefix allBold
-                        with:owner name.
-                ]
-            ]
+	mode := Dialog choose:(resources string:'Save including sources ?')
+		       labels:(resources array:#('Cancel' 'Discard' 'By file reference' 'Include source'))
+		       values:#(nil #discard #reference #keep)
+		       default:#keep.
+
+	mode isNil ifTrue:[^ self].   "/ cancelled
+    ].
+
+    self
+	selectedClassesNonMetaDo:
+	    [:cls |
+	       self
+		   fileOutClass:cls
+		   askForFile:true
+		   withCancelAll:(self selectedClassesValue size > 1)
+		   format:aFormatSymbolOrNil
+		   sourceMode:mode.
+	    ]
+	ifUnloaded:
+	    [:cls |
+		self warn:'Cannot fileOut unloaded class: %1' with:cls name allBold.
+		false.
+	    ]
+	ifPrivate:
+	    [:cls | |owner|
+		owner := cls owningClass.
+		(self selectedClassesValue includes:owner) ifFalse:[
+		    self warn:'Cannot fileOut private class: %1\\Please fileOut the owning class (%2).'
+			with:cls nameWithoutPrefix allBold
+			with:owner name.
+		]
+	    ]
 
     "Modified: / 28-02-2012 / 16:46:20 / cg"
 !
@@ -26496,18 +26880,18 @@
     classes := self selectedNonMetaclasses.
     classes := classes reject:[:eachClass | eachClass isPrivate].
     classes size == 0 ifTrue:[
-        ^ self warn:'Only private classes selected'.
+	^ self warn:'Only private classes selected'.
     ].
 
     dirName := self
-                askForDirectoryToFileOut:(resources string:'FileOut %1 classes in:' with:classes size)
-                default:nil.
+		askForDirectoryToFileOut:(resources string:'FileOut %1 classes in:' with:classes size)
+		default:nil.
     dirName isNil ifTrue:[^ self].
 
     self
-        fileOutEachClassIn:classes
-        in:dirName
-        withFormat:aFormatSymbolOrNil.
+	fileOutEachClassIn:classes
+	in:dirName
+	withFormat:aFormatSymbolOrNil.
 
     "Modified: / 11-07-2010 / 16:44:33 / cg"
 !
@@ -26532,10 +26916,10 @@
 
 classMenuFileOutInWithFormat:aFormatSymbolOrNil
     "fileOut selected classes -  file format as specified by the argument:
-        nil     - standard format
-        #xml    - XML standard format
-        #sif    - SIF (smalltalk interchange file) standard format
-        #binary - ST/X binary format
+	nil     - standard format
+	#xml    - XML standard format
+	#sif    - SIF (smalltalk interchange file) standard format
+	#binary - ST/X binary format
     "
 
     self fileOutClasses:(self selectedNonMetaclasses) withFormat:aFormatSymbolOrNil
@@ -26559,10 +26943,10 @@
     "create a visitor acceptor method"
 
     self
-        generateUndoableChange:'Generate Accept-Visitor Method for %(singleClassNameOrNumberOfClasses)'
-        overSelectedClassesVia:[:generator :eachClass |
-            generator createAcceptVisitorMethodIn:eachClass theNonMetaclass
-        ].
+	generateUndoableChange:'Generate Accept-Visitor Method for %(singleClassNameOrNumberOfClasses)'
+	overSelectedClassesVia:[:generator :eachClass |
+	    generator createAcceptVisitorMethodIn:eachClass theNonMetaclass
+	].
 
     "Modified: / 21-01-2012 / 10:22:31 / cg"
 !
@@ -26573,11 +26957,11 @@
      otherwise for that selected instvar."
 
     self
-        classMenuGenerateAccessMethodsWithChange:false
-        asValueHolder:false
-        readersOnly:false
-        writersOnly:false
-        lazyInitialization:false
+	classMenuGenerateAccessMethodsWithChange:false
+	asValueHolder:false
+	readersOnly:false
+	writersOnly:false
+	lazyInitialization:false
 !
 
 classMenuGenerateAccessMethodsForValueHolder
@@ -26586,11 +26970,11 @@
      otherwise for that selected instvar."
 
     self
-        classMenuGenerateAccessMethodsWithChange:false
-        asValueHolder:true
-        readersOnly:false
-        writersOnly:false
-        lazyInitialization:false
+	classMenuGenerateAccessMethodsWithChange:false
+	asValueHolder:true
+	readersOnly:false
+	writersOnly:false
+	lazyInitialization:false
 !
 
 classMenuGenerateAccessMethodsForValueHolderWithChange
@@ -26599,11 +26983,11 @@
      otherwise for that selected instvar."
 
     self
-        classMenuGenerateAccessMethodsWithChange:true
-        asValueHolder:true
-        readersOnly:false
-        writersOnly:false
-        lazyInitialization:false
+	classMenuGenerateAccessMethodsWithChange:true
+	asValueHolder:true
+	readersOnly:false
+	writersOnly:false
+	lazyInitialization:false
 !
 
 classMenuGenerateAccessMethodsWithChange
@@ -26612,11 +26996,11 @@
      otherwise for that selected instvar."
 
     self
-        classMenuGenerateAccessMethodsWithChange:true
-        asValueHolder:false
-        readersOnly:false
-        writersOnly:false
-        lazyInitialization:false
+	classMenuGenerateAccessMethodsWithChange:true
+	asValueHolder:false
+	readersOnly:false
+	writersOnly:false
+	lazyInitialization:false
 !
 
 classMenuGenerateAccessMethodsWithChange:aBoolean asValueHolder:asValueHolder readersOnly:readersOnly writersOnly:writersOnly
@@ -26625,11 +27009,11 @@
      otherwise for that selected instvar."
 
     self
-        classMenuGenerateAccessMethodsWithChange:aBoolean
-        asValueHolder:asValueHolder
-        readersOnly:readersOnly
-        writersOnly:writersOnly
-        lazyInitialization:false
+	classMenuGenerateAccessMethodsWithChange:aBoolean
+	asValueHolder:asValueHolder
+	readersOnly:readersOnly
+	writersOnly:writersOnly
+	lazyInitialization:false
 !
 
 classMenuGenerateAccessMethodsWithChange:aBoolean asValueHolder:asValueHolder readersOnly:readersOnly writersOnly:writersOnly lazyInitialization:lazyInitialization
@@ -26639,23 +27023,23 @@
      otherwise for that selected instvar."
 
     self
-        generateUndoableChange:'Generate Access Methods in %(singleClassNameOrNumberOfClasses)'
-        overSelectedClassesVia:[:generator :eachClass |
-            |names|
-
-            names := self variableFilter value.
-            names size == 0 ifTrue:[
-                names := eachClass instVarNames
-            ].
-            generator
-                createAccessMethodsFor:names
-                in:eachClass
-                withChange:aBoolean
-                asValueHolder:asValueHolder
-                readersOnly:readersOnly
-                writersOnly:writersOnly
-                lazyInitialization:lazyInitialization
-        ]
+	generateUndoableChange:'Generate Access Methods in %(singleClassNameOrNumberOfClasses)'
+	overSelectedClassesVia:[:generator :eachClass |
+	    |names|
+
+	    names := self variableFilter value.
+	    names size == 0 ifTrue:[
+		names := eachClass instVarNames
+	    ].
+	    generator
+		createAccessMethodsFor:names
+		in:eachClass
+		withChange:aBoolean
+		asValueHolder:asValueHolder
+		readersOnly:readersOnly
+		writersOnly:writersOnly
+		lazyInitialization:lazyInitialization
+	]
 
     "Created: / 07-08-1998 / 18:17:18 / cg"
 !
@@ -26666,11 +27050,11 @@
      otherwise for that selected instvar."
 
     self
-        classMenuGenerateAccessMethodsWithChange:true
-        asValueHolder:false
-        readersOnly:false
-        writersOnly:false
-        lazyInitialization:true
+	classMenuGenerateAccessMethodsWithChange:true
+	asValueHolder:false
+	readersOnly:false
+	writersOnly:false
+	lazyInitialization:true
 !
 
 classMenuGenerateApplicationCode
@@ -26685,20 +27069,20 @@
     "create application code methods"
 
     (cls isSubclassOf:WebApplicationModel) ifTrue:[
-        generator createWebApplicationCodeFor:cls.
-        ^ self.
+	generator createWebApplicationCodeFor:cls.
+	^ self.
     ].
     (cls isSubclassOf:HTTPService) ifTrue:[
-        generator createWebServiceCodeFor:cls.
-        ^ self.
+	generator createWebServiceCodeFor:cls.
+	^ self.
     ].
     (cls isSubclassOf:ApplicationModel) ifTrue:[
-        generator createApplicationCodeFor:cls.
-        ^ self.
+	generator createApplicationCodeFor:cls.
+	^ self.
     ].
     (cls isSubclassOf:StandaloneStartup) ifTrue:[
-        generator createStandaloneStartupCodeFor:cls.
-        ^ self.
+	generator createStandaloneStartupCodeFor:cls.
+	^ self.
     ].
 
     "Modified: / 19-08-2011 / 01:58:40 / cg"
@@ -26708,12 +27092,12 @@
     "create application code methods"
 
     self
-        generateUndoableChange:'Generate ApplicationCode in %(singleClassNameOrNumberOfClasses)'
-        overClasses:classes
-        via:[:generator :eachClass |
-            generator confirmChanges:false.
-            self classMenuGenerateApplicationCodeFor:(eachClass theNonMetaclass) using:generator
-        ]
+	generateUndoableChange:'Generate ApplicationCode in %(singleClassNameOrNumberOfClasses)'
+	overClasses:classes
+	via:[:generator :eachClass |
+	    generator confirmChanges:false.
+	    self classMenuGenerateApplicationCodeFor:(eachClass theNonMetaclass) using:generator
+	]
 
     "Created: / 21-01-2012 / 11:09:47 / cg"
 !
@@ -26722,10 +27106,10 @@
     "create #initialize method on the class side"
 
     self
-        generateUndoableChange:'Generate Class Initializer in %(singleClassNameOrNumberOfClasses)'
-        overSelectedClassesVia:[:generator :eachClass |
-            generator createClassInitializeMethodIn:eachClass theMetaclass.
-        ]
+	generateUndoableChange:'Generate Class Initializer in %(singleClassNameOrNumberOfClasses)'
+	overSelectedClassesVia:[:generator :eachClass |
+	    generator createClassInitializeMethodIn:eachClass theMetaclass.
+	]
 
     "Modified: / 21-01-2012 / 10:22:58 / cg"
 !
@@ -26736,21 +27120,21 @@
     |cls subclasses|
 
     (cls := self theSingleSelectedLoadedNonMetaclassOrNil) isNil ifTrue:[
-        self information:'You must select a single (abstract) superclass'.
-        ^ self.
+	self information:'You must select a single (abstract) superclass'.
+	^ self.
     ].
 
     subclasses := cls subclasses.
     subclasses isEmpty ifTrue:[
-        self information:'(Abstract) superclass ' , cls name , ' has no subclasses.'.
-        ^ self.
-    ].
-
-    self
-        generateUndoableChange:'Generate ClassType Testers'
-        overSelectedClassesVia:[:generator :eachClass |
-            generator createClassTypeTestMethodsIn:cls theNonMetaclass forClasses:subclasses
-        ].
+	self information:'(Abstract) superclass ' , cls name , ' has no subclasses.'.
+	^ self.
+    ].
+
+    self
+	generateUndoableChange:'Generate ClassType Testers'
+	overSelectedClassesVia:[:generator :eachClass |
+	    generator createClassTypeTestMethodsIn:cls theNonMetaclass forClasses:subclasses
+	].
 
     "Modified: / 21-01-2012 / 10:23:07 / cg"
 !
@@ -26761,19 +27145,19 @@
     |cls sel superclass|
 
     (cls := self theSingleSelectedClass) notNil ifTrue:[
-        sel := 'is' , cls nameWithoutPrefix.
-    ] ifFalse:[
-        sel := 'isXXX'.
+	sel := 'is' , cls nameWithoutPrefix.
+    ] ifFalse:[
+	sel := 'isXXX'.
     ].
 
     superclass := self askForSuperclassToGenerateTestMethod:sel.
     superclass isNil ifTrue:[^ self].
 
     self
-        generateUndoableChange:'Generate ClassType Testers'
-        overSelectedClassesVia:[:generator :eachClass |
-            generator createClassTypeTestMethodsIn:(superclass theNonMetaclass) forClasses:(Array with:eachClass)
-        ].
+	generateUndoableChange:'Generate ClassType Testers'
+	overSelectedClassesVia:[:generator :eachClass |
+	    generator createClassTypeTestMethodsIn:(superclass theNonMetaclass) forClasses:(Array with:eachClass)
+	].
 
     "Modified: / 21-01-2012 / 10:23:15 / cg"
 !
@@ -26783,22 +27167,22 @@
 
     |copyRightText|
 
-    copyRightText := Dialog 
-                        requestText:'Copyright-Text:' 
-                        lines:20 columns:80 
-                        initialAnswer:(SmalltalkCodeGeneratorTool copyrightTemplate).
+    copyRightText := Dialog
+			requestText:'Copyright-Text:'
+			lines:20 columns:80
+			initialAnswer:(SmalltalkCodeGeneratorTool copyrightTemplate).
 
     copyRightText isEmptyOrNil ifTrue:[^ self].
     SmalltalkCodeGeneratorTool copyrightTemplate:copyRightText.
 
     self
-        generateUndoableChange:'Generate Copyright Method in %(singleClassNameOrNumberOfClasses)'
-        overSelectedClassesVia:[:generator :eachClass |
-            |metaClass |
-
-            metaClass := eachClass theMetaclass.
-            generator createCopyrightMethodFor:copyRightText for:metaClass.
-        ]
+	generateUndoableChange:'Generate Copyright Method in %(singleClassNameOrNumberOfClasses)'
+	overSelectedClassesVia:[:generator :eachClass |
+	    |metaClass |
+
+	    metaClass := eachClass theMetaclass.
+	    generator createCopyrightMethodFor:copyRightText for:metaClass.
+	]
 
     "Modified: / 21-01-2012 / 10:23:22 / cg"
 !
@@ -26807,18 +27191,18 @@
     "create documentation method from comment"
 
     self
-        generateUndoableChange:'Generate Documentation method in %(singleClassNameOrNumberOfClasses)'
-        overSelectedClassesVia:[:generator :eachClass |
-            |cls|
-
-            cls := eachClass theMetaclass.
-            (cls includesSelector:#documentation) ifFalse:[
-                generator createDocumentationMethodFor:cls.
-                (cls includesSelector:#documentation) ifTrue:[
-                    cls theNonMetaclass comment:nil
-                ].
-            ].
-        ]
+	generateUndoableChange:'Generate Documentation method in %(singleClassNameOrNumberOfClasses)'
+	overSelectedClassesVia:[:generator :eachClass |
+	    |cls|
+
+	    cls := eachClass theMetaclass.
+	    (cls includesSelector:#documentation) ifFalse:[
+		generator createDocumentationMethodFor:cls.
+		(cls includesSelector:#documentation) ifTrue:[
+		    cls theNonMetaclass comment:nil
+		].
+	    ].
+	]
 
     "Modified: / 21-01-2012 / 10:23:31 / cg"
 !
@@ -26827,18 +27211,18 @@
     "create documentation methods"
 
     self
-        generateUndoableChange:'Generate Documentation in %(singleClassNameOrNumberOfClasses)'
-        overSelectedClassesVia:[:generator :eachClass |
-            |metaClass |
-
-            metaClass := eachClass theMetaclass.
-
-            generator createDocumentationMethodsFor:metaClass.
-
-            "/ add examples method containing examples template
-            "/ but only if not already present.
-            generator createExamplesMethodFor:metaClass.
-        ]
+	generateUndoableChange:'Generate Documentation in %(singleClassNameOrNumberOfClasses)'
+	overSelectedClassesVia:[:generator :eachClass |
+	    |metaClass |
+
+	    metaClass := eachClass theMetaclass.
+
+	    generator createDocumentationMethodsFor:metaClass.
+
+	    "/ add examples method containing examples template
+	    "/ but only if not already present.
+	    generator createExamplesMethodFor:metaClass.
+	]
 
     "Modified: / 21-01-2012 / 10:23:38 / cg"
 !
@@ -26847,13 +27231,13 @@
     "create an enumeration type"
 
     self
-        generateUndoableChange:'Generate EnumTypeCode in %(singleClassNameOrNumberOfClasses)'
-        overSelectedClassesVia:[:generator :eachClass |
-            |cls|
-
-            cls := eachClass theNonMetaclass.
-            generator createEnumTypeCodeFor:cls
-        ]
+	generateUndoableChange:'Generate EnumTypeCode in %(singleClassNameOrNumberOfClasses)'
+	overSelectedClassesVia:[:generator :eachClass |
+	    |cls|
+
+	    cls := eachClass theNonMetaclass.
+	    generator createEnumTypeCodeFor:cls
+	]
 
     "Modified: / 21-01-2012 / 10:23:45 / cg"
 !
@@ -26864,21 +27248,21 @@
      otherwise for that selected instvar."
 
     self
-        classMenuGenerateAccessMethodsWithChange:false
-        asValueHolder:false
-        readersOnly:true
-        writersOnly:false
-        lazyInitialization:false
+	classMenuGenerateAccessMethodsWithChange:false
+	asValueHolder:false
+	readersOnly:true
+	writersOnly:false
+	lazyInitialization:false
 !
 
 classMenuGenerateInitializationMethod
     "create initialize method"
 
     self
-        generateUndoableChange:'Initialization Code for %(singleClassNameOrNumberOfClasses)'
-        overSelectedClassesVia:[:generator :eachClass |
-            generator createInitializationMethodIn:eachClass theNonMetaclass
-        ].
+	generateUndoableChange:'Initialization Code for %(singleClassNameOrNumberOfClasses)'
+	overSelectedClassesVia:[:generator :eachClass |
+	    generator createInitializationMethodIn:eachClass theNonMetaclass
+	].
 
     "Modified: / 21-01-2012 / 10:23:53 / cg"
 !
@@ -26887,10 +27271,10 @@
     "create the initialize method"
 
     self
-        generateUndoableChange:'Initializer for %(singleClassNameOrNumberOfClasses)'
-        overSelectedClassesVia:[:generator :eachClass |
-            generator createInitializationMethodIn:eachClass theNonMetaclass
-        ].
+	generateUndoableChange:'Initializer for %(singleClassNameOrNumberOfClasses)'
+	overSelectedClassesVia:[:generator :eachClass |
+	    generator createInitializationMethodIn:eachClass theNonMetaclass
+	].
 
     "Modified: / 21-01-2012 / 10:24:01 / cg"
 !
@@ -26899,10 +27283,10 @@
     "create new and initialize methods"
 
     self
-        generateUndoableChange:'Initialized Instance Creation Code for %(singleClassNameOrNumberOfClasses)'
-        overSelectedClassesVia:[:generator :eachClass |
-            generator createInitializedInstanceCreationMethodsIn:eachClass theNonMetaclass
-        ].
+	generateUndoableChange:'Initialized Instance Creation Code for %(singleClassNameOrNumberOfClasses)'
+	overSelectedClassesVia:[:generator :eachClass |
+	    generator createInitializedInstanceCreationMethodsIn:eachClass theNonMetaclass
+	].
 
     "Modified: / 21-01-2012 / 10:24:07 / cg"
 !
@@ -26914,14 +27298,14 @@
 
     cls := self theSingleSelectedClass.
     vars := cls allInstVarNames
-            select:[:var | self selectedVariables value includes:var].
-
-    self
-        generateUndoableChange:'Generate multi-setter'
-        overClasses:(Array with:cls)
-        via:[:generator :eachClass |
-            generator createMultiSetterMethodFor:vars in:cls
-        ].
+	    select:[:var | self selectedVariables value includes:var].
+
+    self
+	generateUndoableChange:'Generate multi-setter'
+	overClasses:(Array with:cls)
+	via:[:generator :eachClass |
+	    generator createMultiSetterMethodFor:vars in:cls
+	].
 !
 
 classMenuGenerateParametrizedInstanceCreationMethods
@@ -26930,16 +27314,16 @@
     |selector|
 
     selector := Dialog
-                    requestSelector:'Name of Instance Creation Method:'
-                    initialAnswer:'for:'.
+		    requestSelector:'Name of Instance Creation Method:'
+		    initialAnswer:'for:'.
     selector isEmptyOrNil ifTrue:[^ self].
     selector := selector asSymbol.
 
     self
-        generateUndoableChange:'Parametrized Instance Creation Code for %(singleClassNameOrNumberOfClasses)'
-        overSelectedClassesVia:[:generator :eachClass |
-            generator createParametrizedInstanceCreationMethodsNamed:selector in:eachClass theNonMetaclass
-        ].
+	generateUndoableChange:'Parametrized Instance Creation Code for %(singleClassNameOrNumberOfClasses)'
+	overSelectedClassesVia:[:generator :eachClass |
+	    generator createParametrizedInstanceCreationMethodsNamed:selector in:eachClass theNonMetaclass
+	].
 
     "Modified: / 21-01-2012 / 10:24:15 / cg"
 !
@@ -26948,13 +27332,13 @@
     "create a Pool initialization template method"
 
     self
-        generateUndoableChange:'Generate Pool Initialization in %(singleClassNameOrNumberOfClasses)'
-        overSelectedClassesVia:[:generator :eachClass |
-            |cls|
-
-            cls := eachClass theNonMetaclass.
-            generator createPoolInitializationCodeFor:cls
-        ]
+	generateUndoableChange:'Generate Pool Initialization in %(singleClassNameOrNumberOfClasses)'
+	overSelectedClassesVia:[:generator :eachClass |
+	    |cls|
+
+	    cls := eachClass theNonMetaclass.
+	    generator createPoolInitializationCodeFor:cls
+	]
 
     "Created: / 25-10-2006 / 09:24:48 / cg"
 !
@@ -26969,10 +27353,10 @@
     "create redefined new methods"
 
     self
-        generateUndoableChange:'Redefined Instance Creation for %(singleClassNameOrNumberOfClasses)'
-        overSelectedClassesVia:[:generator :eachClass |
-            generator createRedefinedInstanceCreationMethodsIn:eachClass theNonMetaclass
-        ].
+	generateUndoableChange:'Redefined Instance Creation for %(singleClassNameOrNumberOfClasses)'
+	overSelectedClassesVia:[:generator :eachClass |
+	    generator createRedefinedInstanceCreationMethodsIn:eachClass theNonMetaclass
+	].
 
     "Modified: / 21-01-2012 / 10:24:28 / cg"
 !
@@ -26981,10 +27365,10 @@
     "create required protocol (all inherited subclassResponsibility methods)"
 
     self
-        generateUndoableChange:'Generate Required Protocol in %(singleClassNameOrNumberOfClasses)'
-        overSelectedClassesVia:[:generator :eachClass |
-            generator createClassResponsibleProtocolFor:eachClass
-        ]
+	generateUndoableChange:'Generate Required Protocol in %(singleClassNameOrNumberOfClasses)'
+	overSelectedClassesVia:[:generator :eachClass |
+	    generator createClassResponsibleProtocolFor:eachClass
+	]
 
     "Modified: / 21-01-2012 / 10:24:37 / cg"
 !
@@ -26995,11 +27379,11 @@
      otherwise for that selected instvar."
 
     self
-        classMenuGenerateAccessMethodsWithChange:false
-        asValueHolder:false
-        readersOnly:false
-        writersOnly:true
-        lazyInitialization:false
+	classMenuGenerateAccessMethodsWithChange:false
+	asValueHolder:false
+	readersOnly:false
+	writersOnly:true
+	lazyInitialization:false
 !
 
 classMenuGenerateSingletonPatternInstanceCreationMethods
@@ -27008,48 +27392,48 @@
     |singletonVarName|
 
     self
-        generateUndoableChange:'Singleton Pattern for %(singleClassNameOrNumberOfClasses)'
-        overSelectedClassesVia:[:generator :eachClass |
-            |theClass vars defaultNameForSingleton singletonVar|
-
-            "/ if any of the selected classes is a subclass of one of the previously processed,
-            "/ and we have added a class-instvar in the previous loop cycle,
-            "/ we have top refetch, because the class is now obsolete (stupid consequence of not having a
-            "/ good become).
-            "/ refetch to get the present class (sigh)
-            theClass := Smalltalk at:(eachClass theNonMetaclass name).
-
-            vars := theClass theMetaclass allInstanceVariableNames asSet.
-            vars removeAll:(Class allInstanceVariableNames).
-
-            (singletonVarName notNil and:[vars includes:singletonVarName]) ifTrue:[
-                defaultNameForSingleton := singletonVarName
-            ] ifFalse:[
-                defaultNameForSingleton := 'theOneAndOnlyInstance'.
-                "/ vars add:'theOneAndOnlyInstance'.
-            ].
-            singletonVar := Dialog  
-                request:'Class-Instvar to keep Singleton in?'
-                initialAnswer:defaultNameForSingleton
-                list:(vars asSortedCollection).
-            singletonVar isEmptyOrNil ifTrue:[^ self].
-
-            (theClass theMetaclass allInstanceVariableNames asSet includes:singletonVar) ifFalse:[
-                theClass theMetaclass addInstVarName:singletonVar.
-                theClass := Smalltalk at:(eachClass theNonMetaclass name).
-            ].
-            generator createSingletonPatternInstanceCreationMethodsIn:theClass usingVariable:singletonVar
-        ].
+	generateUndoableChange:'Singleton Pattern for %(singleClassNameOrNumberOfClasses)'
+	overSelectedClassesVia:[:generator :eachClass |
+	    |theClass vars defaultNameForSingleton singletonVar|
+
+	    "/ if any of the selected classes is a subclass of one of the previously processed,
+	    "/ and we have added a class-instvar in the previous loop cycle,
+	    "/ we have top refetch, because the class is now obsolete (stupid consequence of not having a
+	    "/ good become).
+	    "/ refetch to get the present class (sigh)
+	    theClass := Smalltalk at:(eachClass theNonMetaclass name).
+
+	    vars := theClass theMetaclass allInstanceVariableNames asSet.
+	    vars removeAll:(Class allInstanceVariableNames).
+
+	    (singletonVarName notNil and:[vars includes:singletonVarName]) ifTrue:[
+		defaultNameForSingleton := singletonVarName
+	    ] ifFalse:[
+		defaultNameForSingleton := 'theOneAndOnlyInstance'.
+		"/ vars add:'theOneAndOnlyInstance'.
+	    ].
+	    singletonVar := Dialog
+		request:'Class-Instvar to keep Singleton in?'
+		initialAnswer:defaultNameForSingleton
+		list:(vars asSortedCollection).
+	    singletonVar isEmptyOrNil ifTrue:[^ self].
+
+	    (theClass theMetaclass allInstanceVariableNames asSet includes:singletonVar) ifFalse:[
+		theClass theMetaclass addInstVarName:singletonVar.
+		theClass := Smalltalk at:(eachClass theNonMetaclass name).
+	    ].
+	    generator createSingletonPatternInstanceCreationMethodsIn:theClass usingVariable:singletonVar
+	].
 
     "Created: / 10-02-2011 / 16:28:36 / cg"
 !
 
 classMenuGenerateStandardPrintOnMethod
     self
-        generateUndoableChange:'Generate PrintOn Method for %(singleClassNameOrNumberOfClasses)'
-        overSelectedClassesVia:[:generator :eachClass |
-            generator createStandardPrintOnMethodIn:eachClass theNonMetaclass
-        ].
+	generateUndoableChange:'Generate PrintOn Method for %(singleClassNameOrNumberOfClasses)'
+	overSelectedClassesVia:[:generator :eachClass |
+	    generator createStandardPrintOnMethodIn:eachClass theNonMetaclass
+	].
 
     "Modified: / 21-01-2012 / 10:24:51 / cg"
 !
@@ -27058,10 +27442,10 @@
     "create a standard update method template"
 
     self
-        generateUndoableChange:'Generate%(numClassesOrEmpty)Update Method%(sForPlural)%(forSingleClassOrEmpty)'
-        overSelectedClassesVia:[:generator :eachClass |
-            generator createUpdateMethodIn:eachClass theNonMetaclass
-        ].
+	generateUndoableChange:'Generate%(numClassesOrEmpty)Update Method%(sForPlural)%(forSingleClassOrEmpty)'
+	overSelectedClassesVia:[:generator :eachClass |
+	    generator createUpdateMethodIn:eachClass theNonMetaclass
+	].
 
     "Modified: / 21-01-2012 / 10:24:58 / cg"
 !
@@ -27072,13 +27456,13 @@
     |visitorClassName visitorClass|
 
     visitorClassName := Dialog
-                    request:'Name of Visitor class'
-                    initialAnswer:(LastVisitorClassName ? '')
-                    okLabel:(resources string:'Create')
-                    title:'Visitor class'
-                    onCancel:nil
-                    list:#()
-                    entryCompletionBlock:(DoWhatIMeanSupport classNameEntryCompletionBlock).
+		    request:'Name of Visitor class'
+		    initialAnswer:(LastVisitorClassName ? '')
+		    okLabel:(resources string:'Create')
+		    title:'Visitor class'
+		    onCancel:nil
+		    list:#()
+		    entryCompletionBlock:(DoWhatIMeanSupport classNameEntryCompletionBlock).
 
     visitorClass := self classIfValidNonMetaClassName:visitorClassName.
     visitorClass isNil ifTrue:[^ nil].
@@ -27086,10 +27470,10 @@
     LastVisitorClassName := visitorClassName.
 
     self
-        generateUndoableChange:'Generate Visitor Pattern'
-        overSelectedClassesVia:[:generator :eachClass |
-            generator createVisitorMethodsIn:eachClass theNonMetaclass andVisitorClass:visitorClass
-        ].
+	generateUndoableChange:'Generate Visitor Pattern'
+	overSelectedClassesVia:[:generator :eachClass |
+	    generator createVisitorMethodsIn:eachClass theNonMetaclass andVisitorClass:visitorClass
+	].
 
     "Created: / 11-10-2001 / 22:26:08 / cg"
 !
@@ -27100,13 +27484,13 @@
     |visitorClassName visitorClass|
 
     visitorClassName := Dialog
-                    request:'Name of Visitor class'
-                    initialAnswer:(LastVisitorClassName ? '')
-                    okLabel:(resources string:'Create')
-                    title:'Visitor class'
-                    onCancel:nil
-                    list:#()
-                    entryCompletionBlock:(DoWhatIMeanSupport classNameEntryCompletionBlock).
+		    request:'Name of Visitor class'
+		    initialAnswer:(LastVisitorClassName ? '')
+		    okLabel:(resources string:'Create')
+		    title:'Visitor class'
+		    onCancel:nil
+		    list:#()
+		    entryCompletionBlock:(DoWhatIMeanSupport classNameEntryCompletionBlock).
 
     visitorClass := self classIfValidNonMetaClassName:visitorClassName.
     visitorClass isNil ifTrue:[^ nil].
@@ -27114,10 +27498,10 @@
     LastVisitorClassName := visitorClassName.
 
     self
-        generateUndoableChange:'Generate Visitor Pattern'
-        overSelectedClassesVia:[:generator :eachClass |
-            generator createVisitorMethodsIn:eachClass theNonMetaclass andVisitorClass2:visitorClass
-        ].
+	generateUndoableChange:'Generate Visitor Pattern'
+	overSelectedClassesVia:[:generator :eachClass |
+	    generator createVisitorMethodsIn:eachClass theNonMetaclass andVisitorClass2:visitorClass
+	].
 
     "Created: / 07-07-2009 / 20:41:47 / Jan Vrany <vranyj1@fel.cvut.cz>"
     "Modified: / 21-01-2012 / 10:25:37 / cg"
@@ -27137,16 +27521,16 @@
     projectDefinitionClasses := (self selectedClassesValue collect:[:cls | cls projectDefinitionClass]) asSet.
 
     projectDefinitionClasses do:[:eachDefinitionClass |
-        |toIncludeForThis|
-
-        toIncludeForThis := self selectedClassesValue select:[:cls | cls projectDefinitionClass == eachDefinitionClass].
-
-        self
-            generateUndoableChange:(resources string:'Include %1 class(es) in Project %2 (Make Compiled Class)' with:toIncludeForThis size with:eachDefinitionClass name)
-            overClasses:(Array with: eachDefinitionClass)
-            via:[:generator :projectDefinition |
-                self includeClasses:toIncludeForThis inProject:projectDefinition using:generator
-            ].
+	|toIncludeForThis|
+
+	toIncludeForThis := self selectedClassesValue select:[:cls | cls projectDefinitionClass == eachDefinitionClass].
+
+	self
+	    generateUndoableChange:(resources string:'Include %1 class(es) in Project %2 (Make Compiled Class)' with:toIncludeForThis size with:eachDefinitionClass name)
+	    overClasses:(Array with: eachDefinitionClass)
+	    via:[:generator :projectDefinition |
+		self includeClasses:toIncludeForThis inProject:projectDefinition using:generator
+	    ].
     ].
 
     "Created: / 19-02-2007 / 16:46:16 / cg"
@@ -27157,9 +27541,9 @@
     "reinit selected classes (kludge - for me)"
 
     self selectedNonMetaclassesDo:[:eachClass |
-        (eachClass class includesSelector:#initialize) ifTrue:[
-            eachClass initialize.
-        ]
+	(eachClass class includesSelector:#initialize) ifTrue:[
+	    eachClass initialize.
+	]
     ].
 
     "Modified: / 12-09-2006 / 13:51:50 / cg"
@@ -27175,30 +27559,30 @@
 
     superClasses := selectedClasses collect:[:c | c superclass].
     superClasses asSet size > 1 ifTrue:[
-        Dialog warn:'Classes must have a common superclass'.
-        ^ self
+	Dialog warn:'Classes must have a common superclass'.
+	^ self
     ].
     superClass := superClasses anElement.
 
     name := Dialog request:(resources
-                                string:'Enter name for new parent class of the selected class(es):').
+				string:'Enter name for new parent class of the selected class(es):').
     name isEmpty ifTrue: [^self].
 
     existingClass := Smalltalk classNamed:name.
     existingClass notNil ifTrue:[
-        (Dialog confirm:(resources
-                                string:'A Class named "%1" already exists - make the selected class(es) a subclass of it ?'))
-        ifFalse:[
-            ^ self
-        ].
+	(Dialog confirm:(resources
+				string:'A Class named "%1" already exists - make the selected class(es) a subclass of it ?'))
+	ifFalse:[
+	    ^ self
+	].
     ].
 
     self performRefactoring:
-            (AddClassRefactoring
-                addClass:name
-                superclass:superClass
-                subclasses:selectedClasses
-                category:(selectedClasses first category) "dialog categoryName").
+	    (AddClassRefactoring
+		addClass:name
+		superclass:superClass
+		subclasses:selectedClasses
+		category:(selectedClasses first category) "dialog categoryName").
 
     self switchToClassNamed:name.
 "/            meta: self isMeta
@@ -27213,12 +27597,12 @@
     |classes toInspect|
 
     (classes := self selectedNonMetaclasses) size > 0 ifTrue:[
-        classes size == 1 ifTrue:[
-            toInspect := classes first.
-        ] ifFalse:[
-            toInspect := classes
-        ].
-        toInspect inspect
+	classes size == 1 ifTrue:[
+	    toInspect := classes first.
+	] ifFalse:[
+	    toInspect := classes
+	].
+	toInspect inspect
     ].
 
     "Modified: / 12-09-2006 / 13:51:26 / cg"
@@ -27233,17 +27617,17 @@
 
     insts := OrderedCollection new.
     classes do:[:eachClass |
-        insts addAll:(eachClass allSubInstances).
+	insts addAll:(eachClass allSubInstances).
     ].
 
     insts size == 0 ifTrue:[
-        self information:'No instances or subInstances.'
-    ] ifFalse:[
-        insts size == 1 ifTrue:[
-            insts first inspect.
-        ] ifFalse:[
-            insts inspect
-        ]
+	self information:'No instances or subInstances.'
+    ] ifFalse:[
+	insts size == 1 ifTrue:[
+	    insts first inspect.
+	] ifFalse:[
+	    insts inspect
+	]
     ]
 
     "Modified: / 12-09-2006 / 13:51:09 / cg"
@@ -27258,17 +27642,17 @@
 
     insts := OrderedCollection new.
     classes do:[:eachClass |
-        insts addAll:(eachClass allInstances).
+	insts addAll:(eachClass allInstances).
     ].
 
     insts size == 0 ifTrue:[
-        self information:'No instances.'
-    ] ifFalse:[
-        insts size == 1 ifTrue:[
-            insts first inspect.
-        ] ifFalse:[
-            insts inspect
-        ]
+	self information:'No instances.'
+    ] ifFalse:[
+	insts size == 1 ifTrue:[
+	    insts first inspect.
+	] ifFalse:[
+	    insts inspect
+	]
     ]
 
     "Modified: / 12-09-2006 / 13:51:02 / cg"
@@ -27285,21 +27669,21 @@
     insts := OrderedCollection new.
     ObjectMemory garbageCollect.
     ObjectMemory allObjectsDo:[:obj |
-        (classes contains:[:cls | (obj referencesInstanceOf:cls)])
-        ifTrue:[
-            insts add:obj
-        ].
+	(classes contains:[:cls | (obj referencesInstanceOf:cls)])
+	ifTrue:[
+	    insts add:obj
+	].
     ].
     insts remove:(insts instVarAt:1) ifAbsent:nil.
 
     insts size == 0 ifTrue:[
-        self information:'Noone references any instance of the selected class(es).'
-    ] ifFalse:[
-        insts size == 1 ifTrue:[
-            insts first inspect.
-        ] ifFalse:[
-            insts inspect
-        ]
+	self information:'Noone references any instance of the selected class(es).'
+    ] ifFalse:[
+	insts size == 1 ifTrue:[
+	    insts first inspect.
+	] ifFalse:[
+	    insts inspect
+	]
     ]
 
     "Modified: / 12-09-2006 / 13:50:54 / cg"
@@ -27311,8 +27695,8 @@
     |classes toInspect|
 
     (classes := self selectedNonMetaclasses) size > 0 ifTrue:[
-        toInspect := classes collectAll:[:cls | cls allSubclasses].
-        toInspect inspect
+	toInspect := classes collectAll:[:cls | cls allSubclasses].
+	toInspect inspect
     ].
 !
 
@@ -27327,11 +27711,11 @@
     "load all classes from the selected project definitions"
 
     (self selectedNonMetaclasses copy) do:[:cls |
-        cls autoload.
-        cls isProjectDefinition ifTrue:[
-            self activityNotification:('Loading ', cls description , '..').
-            cls load
-        ].
+	cls autoload.
+	cls isProjectDefinition ifTrue:[
+	    self activityNotification:('Loading ', cls description , '..').
+	    cls load
+	].
     ].
 
     "Modified: / 12-09-2006 / 13:50:41 / cg"
@@ -27341,8 +27725,8 @@
     "fileOut selected classes (chunk format) and eMail to someone"
 
     self
-        mailClasses:self selectedClassesValue
-        subject:'Class Source from Browser'
+	mailClasses:self selectedClassesValue
+	subject:'Class Source from Browser'
 
     "Modified: / 28-02-2012 / 16:47:18 / cg"
 !
@@ -27353,15 +27737,15 @@
     projectDefinitionClasses := (self selectedClassesValue collect:[:cls | cls theNonMetaclass projectDefinitionClass]) asSet.
 
     projectDefinitionClasses do:[:eachDefinitionClass |
-        |toMakeAutoloadedForThis|
-
-        toMakeAutoloadedForThis := self selectedClassesValue select:[:cls | cls theNonMetaclass projectDefinitionClass == eachDefinitionClass].
-        self
-            generateUndoableChange:(resources string:'Make %1 class(es) autoloaded in %2' with:toMakeAutoloadedForThis size with:eachDefinitionClass name)
-            overClasses:(Array with: eachDefinitionClass)
-            via:[:generator :projectDefinition |
-                self makeClassesAutoloaded:toMakeAutoloadedForThis inProject:projectDefinition using:generator
-            ].
+	|toMakeAutoloadedForThis|
+
+	toMakeAutoloadedForThis := self selectedClassesValue select:[:cls | cls theNonMetaclass projectDefinitionClass == eachDefinitionClass].
+	self
+	    generateUndoableChange:(resources string:'Make %1 class(es) autoloaded in %2' with:toMakeAutoloadedForThis size with:eachDefinitionClass name)
+	    overClasses:(Array with: eachDefinitionClass)
+	    via:[:generator :projectDefinition |
+		self makeClassesAutoloaded:toMakeAutoloadedForThis inProject:projectDefinition using:generator
+	    ].
     ].
 
     "Created: / 30-08-2007 / 18:51:35 / cg"
@@ -27374,62 +27758,62 @@
 
     currentClass := self theSingleSelectedClass.
     currentClass isNil ifTrue:[
-        currentClass := self selectedClassesValue first
+	currentClass := self selectedClassesValue first
     ].
     currentClass := currentClass theNonMetaclass.
     supers := (currentClass allSuperclasses reverse collect:[:cls | cls name]).
     subs := (currentClass allSubclasses collect:[:cls | cls name]).
     list := supers.
     (supers notEmpty and:[subs notEmpty]) ifTrue:[
-        list := list , (Array with:'---- ' , currentClass name , ' ----')
+	list := list , (Array with:'---- ' , currentClass name , ' ----')
     ].
     list := list , subs.
 
     newOwnerName := Dialog
-                    request:(resources string:'Make private in which class:')
-                    initialAnswer:''
-                    okLabel:(resources string:'OK')
-                    title:(resources string:'Make class private')
-                    onCancel:nil
-                    list:list
-                    entryCompletionBlock:(DoWhatIMeanSupport classNameEntryCompletionBlock).
+		    request:(resources string:'Make private in which class:')
+		    initialAnswer:''
+		    okLabel:(resources string:'OK')
+		    title:(resources string:'Make class private')
+		    onCancel:nil
+		    list:list
+		    entryCompletionBlock:(DoWhatIMeanSupport classNameEntryCompletionBlock).
     newOwnerName isNil ifTrue:[^ self].
     (newOwnerName startsWith:'---- ') ifTrue:[^ self].
 
     newOwner := Smalltalk classNamed:newOwnerName.
     newOwner isNil ifTrue:[
-        (currentClass nameSpace notNil and:[currentClass nameSpace ~~ Smalltalk]) ifTrue:[
-            newOwner := currentClass nameSpace classNamed:newOwnerName
-        ].
+	(currentClass nameSpace notNil and:[currentClass nameSpace ~~ Smalltalk]) ifTrue:[
+	    newOwner := currentClass nameSpace classNamed:newOwnerName
+	].
     ].
     newOwner isNil ifTrue:[
-        self warn:'No such class: ', newOwnerName.
-        ^ self
+	self warn:'No such class: ', newOwnerName.
+	^ self
     ].
 
     classes := self selectedNonMetaclasses.
     classes do:[:eachClass |
-        eachClass autoload.
-        newName := newOwner name , '::' , eachClass nameWithoutPrefix.
-        (Smalltalk classNamed:newName) notNil ifTrue:[
-            (Smalltalk classNamed:newName) ~~ eachClass ifTrue:[
-                self warn:'A class named ' , newName , ' already exists.'.
-                ^ self
-            ].
-        ].
-        (newOwner == eachClass) ifTrue:[
-            self warn:'A class cannot be its own owner.'.
-            ^ self
-        ].
-        (newOwner topOwningClass == eachClass) ifTrue:[
-            self warn:'Cannot create mutual (cyclic) ownership.'.
-            ^ self
-        ].
+	eachClass autoload.
+	newName := newOwner name , '::' , eachClass nameWithoutPrefix.
+	(Smalltalk classNamed:newName) notNil ifTrue:[
+	    (Smalltalk classNamed:newName) ~~ eachClass ifTrue:[
+		self warn:'A class named ' , newName , ' already exists.'.
+		^ self
+	    ].
+	].
+	(newOwner == eachClass) ifTrue:[
+	    self warn:'A class cannot be its own owner.'.
+	    ^ self
+	].
+	(newOwner topOwningClass == eachClass) ifTrue:[
+	    self warn:'Cannot create mutual (cyclic) ownership.'.
+	    ^ self
+	].
     ].
     classes do:[:eachClass |
-        newName := newOwner name , '::' , eachClass nameWithoutPrefix.
-        Smalltalk renameClass:eachClass theNonMetaclass to:newName.
-        eachClass theMetaclass setOwningClass:newOwner.
+	newName := newOwner name , '::' , eachClass nameWithoutPrefix.
+	Smalltalk renameClass:eachClass theNonMetaclass to:newName.
+	eachClass theMetaclass setOwningClass:newOwner.
     ].
 
     "Modified: / 28-02-2012 / 16:47:28 / cg"
@@ -27443,27 +27827,27 @@
     |nsName ns baseName|
 
     self selectedNonMetaclassesDo:[:eachClass |
-        baseName := eachClass nameWithoutPrefix.
-        (ns := eachClass topOwningClass nameSpace) ~~ Smalltalk ifTrue:[
-            nsName := Dialog confirmWithCancel:(resources string:'Make public in ''Smalltalk'' or in its nameSpace ''%1'' ?' with:ns name)
-                    labels:(Array with:'Cancel' with:'In Smalltalk' with:'In ' , ns name)
-                    values:(Array with:nil with:Smalltalk with:ns)
-                    default:3.
-            nsName isEmptyOrNil ifTrue:[^ self].
-            nsName isNameSpace ifTrue:[
-                ns := nsName
-            ] ifFalse:[
-                ns := Smalltalk at:nsName.
-            ].
-        ].
-
-        (ns classNamed:baseName) notNil ifTrue:[
-            self warn:(resources
-                            string:'A public class named ''%1'' already exists in %2.\\Please remove/rename that one first,\or rename the private class ''%1'' here\and try again.'
-                            with:baseName with:ns name) withCRs.
-        ] ifFalse:[
-            eachClass makePublicIn:ns
-        ]
+	baseName := eachClass nameWithoutPrefix.
+	(ns := eachClass topOwningClass nameSpace) ~~ Smalltalk ifTrue:[
+	    nsName := Dialog confirmWithCancel:(resources string:'Make public in ''Smalltalk'' or in its nameSpace ''%1'' ?' with:ns name)
+		    labels:(Array with:'Cancel' with:'In Smalltalk' with:'In ' , ns name)
+		    values:(Array with:nil with:Smalltalk with:ns)
+		    default:3.
+	    nsName isEmptyOrNil ifTrue:[^ self].
+	    nsName isNameSpace ifTrue:[
+		ns := nsName
+	    ] ifFalse:[
+		ns := Smalltalk at:nsName.
+	    ].
+	].
+
+	(ns classNamed:baseName) notNil ifTrue:[
+	    self warn:(resources
+			    string:'A public class named ''%1'' already exists in %2.\\Please remove/rename that one first,\or rename the private class ''%1'' here\and try again.'
+			    with:baseName with:ns name) withCRs.
+	] ifFalse:[
+	    eachClass makePublicIn:ns
+	]
     ]
 
     "Modified: / 04-07-2006 / 18:48:23 / fm"
@@ -27477,23 +27861,23 @@
     |nsName ns baseName|
 
     nsName := self
-            askForNameSpace:(resources string:'Make classes public in which Namespace ?')
-            title:(resources string:'Move to Namespace')
-            initialText:(LastNameSpaceMove ? '').
+	    askForNameSpace:(resources string:'Make classes public in which Namespace ?')
+	    title:(resources string:'Move to Namespace')
+	    initialText:(LastNameSpaceMove ? '').
     nsName isEmptyOrNil ifTrue:[^ self].
     ns := Smalltalk at:nsName asSymbol.
     LastNameSpaceMove := nsName.
 
     self selectedNonMetaclassesDo:[:eachClass |
-        baseName := eachClass nameWithoutPrefix.
-
-        (ns classNamed:baseName) notNil ifTrue:[
-            self warn:(resources
-                            string:'A public class named ''%1'' already exists in %2.\\Please remove/rename that one first,\or rename the private class ''%1'' here\and try again.'
-                            with:baseName with:ns name) withCRs.
-        ] ifFalse:[
-            eachClass makePublicIn:ns
-        ]
+	baseName := eachClass nameWithoutPrefix.
+
+	(ns classNamed:baseName) notNil ifTrue:[
+	    self warn:(resources
+			    string:'A public class named ''%1'' already exists in %2.\\Please remove/rename that one first,\or rename the private class ''%1'' here\and try again.'
+			    with:baseName with:ns name) withCRs.
+	] ifFalse:[
+	    eachClass makePublicIn:ns
+	]
     ]
 
     "Created: / 04-07-2006 / 18:48:23 / fm"
@@ -27509,20 +27893,20 @@
     box title:(resources string:'Move class(es) to which category:').
     box list:allCategories.
     box okAction:[:sel |
-        self withWaitCursorDo:[
-            self moveSelectedClassesToCategory:sel
-        ]
+	self withWaitCursorDo:[
+	    self moveSelectedClassesToCategory:sel
+	]
     ].
     box initialText:(LastCategoryRenames ? #('')) first.
     box entryCompletionBlock:[:contents |
-        |s what|
-
-        s := contents withoutLeadingSeparators.
-        what := Smalltalk classCategoryCompletion:s.
-        box contents:what first.
-        (what at:2) size ~~ 1 ifTrue:[
-            self builder window beep
-        ]
+	|s what|
+
+	s := contents withoutLeadingSeparators.
+	what := Smalltalk classCategoryCompletion:s.
+	box contents:what first.
+	(what at:2) size ~~ 1 ifTrue:[
+	    self builder window beep
+	]
     ].
     box label:(resources string:'Change Class-Category').
     box showAtPointer
@@ -27537,73 +27921,73 @@
     |newNameSpace ns|
 
     newNameSpace := self
-                        askForNameSpace:'Move class(es) to which nameSpace:'
-                        title:(resources string:'Move to Namespace')
-                        initialText:(LastNameSpaceMove ? '').
+			askForNameSpace:'Move class(es) to which nameSpace:'
+			title:(resources string:'Move to Namespace')
+			initialText:(LastNameSpaceMove ? '').
     newNameSpace size == 0 ifTrue:[^ self].
 
     ns := Smalltalk at:newNameSpace asSymbol.
     ns isNil ifTrue:[
-        (self confirm:(resources string:'No such nameSpace exists.\\Create "%1" ?' with:newNameSpace) withCRs) ifFalse:[
-            ^ self
-        ].
-        ns := NameSpace name:newNameSpace asSymbol
-    ] ifFalse:[
-        ns isNameSpace ifFalse:[
-            self warn:(resources string:'Not a NameSpace: %1' with:newNameSpace).
-            ^ self
-        ]
+	(self confirm:(resources string:'No such nameSpace exists.\\Create "%1" ?' with:newNameSpace) withCRs) ifFalse:[
+	    ^ self
+	].
+	ns := NameSpace name:newNameSpace asSymbol
+    ] ifFalse:[
+	ns isNameSpace ifFalse:[
+	    self warn:(resources string:'Not a NameSpace: %1' with:newNameSpace).
+	    ^ self
+	]
     ].
 
     LastNameSpaceMove := newNameSpace.
 
     self withWaitCursorDo:[
-        self selectedNonMetaclassesDo:[:classToMove |
-            |className doMove oldSym oldBaseSym|
-
-            classToMove isPrivate ifTrue:[
-                self warn:'Cannot move a private class - please move the owner.'.
-            ] ifFalse:[
-                classToMove nameSpace ~~ ns ifTrue:[
-                    className := classToMove nameWithoutPrefix.
-
-                    "/ check if the target already exists - confirm if so.
-                    doMove := true.
-                    (ns at:className asSymbol) notNil ifTrue:[
-                        doMove := self confirmWithCancel:(resources string:'Attention: a class named ''%1'' already present (in ''%2'' category).\\Move over it ?'
-                                                 with:className allBold
-                                                 with:ns name allBold) withCRs.
-                        doMove isNil ifTrue:[
-                            ^ self
-                        ]
-                    ].
-                    doMove ifTrue:[
-                        oldSym := classToMove name asSymbol.
-                        oldBaseSym := classToMove nameWithoutPrefix asSymbol.
-
-                        "/
-                        "/ renaming is actually more complicated as one might
-                        "/ think (care for classVariables, privateClasses etc.)
-                        "/ Smalltalk knows all about that ...
-
-                        ns == Smalltalk ifTrue:[
-                            Smalltalk renameClass:classToMove to:className asSymbol.
-                        ] ifFalse:[
-                            Smalltalk renameClass:classToMove to:(ns name , '::' , className) asSymbol.
-                            ns changed.
-                        ].
-                        Smalltalk changed.
-
-                        Transcript showCR:('searching for users of ' , oldSym); endEntry.
-                        SystemBrowser browseReferendsOf:oldSym warnIfNone:false.
-                        oldBaseSym ~= oldSym ifTrue:[
-                            Transcript showCR:('searching for users of ' , oldBaseSym); endEntry.
-                            SystemBrowser browseReferendsOf:oldBaseSym warnIfNone:false
-                        ]
-                    ]
-                ]
-            ]
-        ]
+	self selectedNonMetaclassesDo:[:classToMove |
+	    |className doMove oldSym oldBaseSym|
+
+	    classToMove isPrivate ifTrue:[
+		self warn:'Cannot move a private class - please move the owner.'.
+	    ] ifFalse:[
+		classToMove nameSpace ~~ ns ifTrue:[
+		    className := classToMove nameWithoutPrefix.
+
+		    "/ check if the target already exists - confirm if so.
+		    doMove := true.
+		    (ns at:className asSymbol) notNil ifTrue:[
+			doMove := self confirmWithCancel:(resources string:'Attention: a class named ''%1'' already present (in ''%2'' category).\\Move over it ?'
+						 with:className allBold
+						 with:ns name allBold) withCRs.
+			doMove isNil ifTrue:[
+			    ^ self
+			]
+		    ].
+		    doMove ifTrue:[
+			oldSym := classToMove name asSymbol.
+			oldBaseSym := classToMove nameWithoutPrefix asSymbol.
+
+			"/
+			"/ renaming is actually more complicated as one might
+			"/ think (care for classVariables, privateClasses etc.)
+			"/ Smalltalk knows all about that ...
+
+			ns == Smalltalk ifTrue:[
+			    Smalltalk renameClass:classToMove to:className asSymbol.
+			] ifFalse:[
+			    Smalltalk renameClass:classToMove to:(ns name , '::' , className) asSymbol.
+			    ns changed.
+			].
+			Smalltalk changed.
+
+			Transcript showCR:('searching for users of ' , oldSym); endEntry.
+			SystemBrowser browseReferendsOf:oldSym warnIfNone:false.
+			oldBaseSym ~= oldSym ifTrue:[
+			    Transcript showCR:('searching for users of ' , oldBaseSym); endEntry.
+			    SystemBrowser browseReferendsOf:oldBaseSym warnIfNone:false
+			]
+		    ]
+		]
+	    ]
+	]
     ]
 
     "Modified: / 12-09-2006 / 13:49:01 / cg"
@@ -27617,16 +28001,16 @@
 
     packages := self selectedClassesValue collect:[:each | each package].
     packages size == 1 ifTrue:[
-        msg := resources string:'Move class(es) from ''%1'' to which project:'
-                           with:packages first allBold.
-    ] ifFalse:[
-        msg := resources string:'Move class(es) to which project:'
+	msg := resources string:'Move class(es) from ''%1'' to which project:'
+			   with:packages first allBold.
+    ] ifFalse:[
+	msg := resources string:'Move class(es) to which project:'
     ].
     newProject := self askForProject:msg.
     newProject notNil ifTrue:[
-        self withWaitCursorDo:[
-            self moveSelectedClassesToProject:newProject.
-        ]
+	self withWaitCursorDo:[
+	    self moveSelectedClassesToProject:newProject.
+	]
     ].
 
     "Created: / 17-02-2000 / 22:50:07 / cg"
@@ -27637,10 +28021,10 @@
     "create a class-definition prototype for an application"
 
     self
-        classClassDefinitionTemplateFor:ApplicationModel
-        in:(self theSingleSelectedCategory ? 'Applications')
-        asNamespace:false
-        private:false.
+	classClassDefinitionTemplateFor:ApplicationModel
+	in:(self theSingleSelectedCategory ? 'Applications')
+	asNamespace:false
+	private:false.
 
     self codeAspect:#newApplication.
 !
@@ -27657,29 +28041,29 @@
     |theClass superClass cat|
 
     (theClass := self theSingleSelectedClass) notNil ifTrue:[
-        (superClass := theClass theNonMetaclass superclass) notNil ifTrue:[
-            theClass := superClass
-        ]
-    ] ifFalse:[
-        self javaMode ifTrue:[
-            theClass := Java at:'java.lang.Object'
-        ] ifFalse:[
-            theClass := Object.
-        ].
+	(superClass := theClass theNonMetaclass superclass) notNil ifTrue:[
+	    theClass := superClass
+	]
+    ] ifFalse:[
+	self javaMode ifTrue:[
+	    theClass := Java at:'java.lang.Object'
+	] ifFalse:[
+	    theClass := Object.
+	].
     ].
 
     self hasCategorySelected ifTrue:[
-        cat := self selectedCategoriesValue first
-    ] ifFalse:[
-        cat := Compiler defaultMethodCategory "/ '* As yet uncategorized *'
-    ].
-
-    self
-        classClassDefinitionTemplateFor:theClass
-        in:cat
-        asNamespace:false
-        private:false
-        metaClassUsed:metaClassUsedOrNil
+	cat := self selectedCategoriesValue first
+    ] ifFalse:[
+	cat := Compiler defaultMethodCategory "/ '* As yet uncategorized *'
+    ].
+
+    self
+	classClassDefinitionTemplateFor:theClass
+	in:cat
+	asNamespace:false
+	private:false
+	metaClassUsed:metaClassUsedOrNil
 
     "Modified: / 15.11.2001 / 18:01:04 / cg"
 !
@@ -27688,10 +28072,10 @@
     "create a class-definition prototype for a dialog"
 
     self
-        classClassDefinitionTemplateFor:SimpleDialog
-        in:(self theSingleSelectedCategory ? 'Applications - Dialogs')
-        asNamespace:false
-        private:false.
+	classClassDefinitionTemplateFor:SimpleDialog
+	in:(self theSingleSelectedCategory ? 'Applications - Dialogs')
+	asNamespace:false
+	private:false.
 
     self codeAspect:#newDialog.
 !
@@ -27700,10 +28084,10 @@
     "create a class-definition prototype for an error class"
 
     self
-        classClassDefinitionTemplateFor:Error
-        in:(self theSingleSelectedCategory ? 'Errors')
-        asNamespace:false
-        private:false.
+	classClassDefinitionTemplateFor:Error
+	in:(self theSingleSelectedCategory ? 'Errors')
+	asNamespace:false
+	private:false.
 
     self codeAspect:#newError.
 !
@@ -27718,14 +28102,30 @@
     self classMenuNewClass:JavaScriptMetaclass
 !
 
+classMenuNewLispClass
+    "create a class-definition template in codeview"
+
+    self classMenuNewClass:LispMetaclass
+
+    "Created: / 13-05-2012 / 12:53:17 / cg"
+!
+
+classMenuNewLispNamespace
+    "create a class-definition template in codeview"
+
+    self classMenuNewClass:LispNameSpace
+
+    "Created: / 01-06-2012 / 14:36:28 / cg"
+!
+
 classMenuNewNotification
     "create a class-definition prototype for an exception class"
 
     self
-        classClassDefinitionTemplateFor:Notification
-        in:(self theSingleSelectedCategory ? 'Exceptions')
-        asNamespace:false
-        private:false.
+	classClassDefinitionTemplateFor:Notification
+	in:(self theSingleSelectedCategory ? 'Exceptions')
+	asNamespace:false
+	private:false.
 
     self codeAspect:#newNotification.
 !
@@ -27738,10 +28138,10 @@
     "create a class-definition prototype for a dialog"
 
     self
-        classClassDefinitionTemplateFor:Object
-        in:nil
-        asNamespace:false
-        private:true.
+	classClassDefinitionTemplateFor:Object
+	in:nil
+	asNamespace:false
+	private:true.
 
 
 
@@ -27753,10 +28153,10 @@
     "create a class-definition prototype for a shared pool"
 
     self
-        classClassDefinitionTemplateFor:SharedPool
-        in:(self theSingleSelectedCategory ? 'Pools')
-        asNamespace:false
-        private:false.
+	classClassDefinitionTemplateFor:SharedPool
+	in:(self theSingleSelectedCategory ? 'Pools')
+	asNamespace:false
+	private:false.
 
 "/    self codeAspect:#newSharedPool.
 !
@@ -27773,10 +28173,10 @@
     "create a class-definition prototype for a standalone startup class"
 
     self
-        classClassDefinitionTemplateFor:StandaloneStartup
-        in:(self theSingleSelectedCategory ? 'startup')
-        asNamespace:false
-        private:false.
+	classClassDefinitionTemplateFor:StandaloneStartup
+	in:(self theSingleSelectedCategory ? 'startup')
+	asNamespace:false
+	private:false.
 
     "Created: / 08-08-2011 / 07:46:47 / cg"
 !
@@ -27787,29 +28187,29 @@
     |theClass cat metaClassUsedOrNil|
 
     (theClass := self theSingleSelectedClass) isNil ifTrue:[
-        self javaMode ifTrue:[
-            theClass := Java at:'java.lang.Object'
-        ].
-        theClass isNil ifTrue:[
-            theClass := Object.
-        ].
-    ] ifFalse:[
-        theClass := theClass theNonMetaclass.
-        metaClassUsedOrNil := theClass theMetaclass class.
+	self javaMode ifTrue:[
+	    theClass := Java at:'java.lang.Object'
+	].
+	theClass isNil ifTrue:[
+	    theClass := Object.
+	].
+    ] ifFalse:[
+	theClass := theClass theNonMetaclass.
+	metaClassUsedOrNil := theClass theMetaclass class.
     ].
 
     self hasCategorySelected ifTrue:[
-        cat := self selectedCategoriesValue first
-    ] ifFalse:[
-        cat := theClass category.
-    ].
-
-    self
-        classClassDefinitionTemplateFor:theClass
-        in:cat
-        asNamespace:false
-        private:false
-        metaClassUsed:metaClassUsedOrNil
+	cat := self selectedCategoriesValue first
+    ] ifFalse:[
+	cat := theClass category.
+    ].
+
+    self
+	classClassDefinitionTemplateFor:theClass
+	in:cat
+	asNamespace:false
+	private:false
+	metaClassUsed:metaClassUsedOrNil
 
     "Created: / 17.2.2000 / 23:25:33 / cg"
 !
@@ -27820,10 +28220,10 @@
     TestCase isNil ifTrue:[ Smalltalk loadPackage:'stx:goodies/sunit' ].
     TestCase autoload.
     self
-        classClassDefinitionTemplateFor:TestCase
-        in:(self theSingleSelectedCategory ? 'TestCases')
-        asNamespace:false
-        private:false.
+	classClassDefinitionTemplateFor:TestCase
+	in:(self theSingleSelectedCategory ? 'TestCases')
+	asNamespace:false
+	private:false.
 
     self codeAspect:#newTestCase.
 
@@ -27834,10 +28234,10 @@
     "create a class-definition prototype for a web page"
 
     self
-        classClassDefinitionTemplateFor:WebApplicationModel
-        in:(self theSingleSelectedCategory ? 'WebServices')
-        asNamespace:false
-        private:false.
+	classClassDefinitionTemplateFor:WebApplicationModel
+	in:(self theSingleSelectedCategory ? 'WebServices')
+	asNamespace:false
+	private:false.
 
     self codeAspect:#newWebApplication.
 !
@@ -27849,10 +28249,10 @@
     HTTPService autoload.
 
     self
-        classClassDefinitionTemplateFor:HTTPService
-        in:(self theSingleSelectedCategory ? 'WebServices')
-        asNamespace:false
-        private:false.
+	classClassDefinitionTemplateFor:HTTPService
+	in:(self theSingleSelectedCategory ? 'WebServices')
+	asNamespace:false
+	private:false.
 
     self codeAspect:#newWebService.
 
@@ -27863,16 +28263,16 @@
     "create a class-definition prototype for a widget"
 
     self
-        classClassDefinitionTemplateFor:View
-        in:(self theSingleSelectedCategory ? 'Views-Misc')
-        asNamespace:false
-        private:false.
+	classClassDefinitionTemplateFor:View
+	in:(self theSingleSelectedCategory ? 'Views-Misc')
+	asNamespace:false
+	private:false.
 
     self codeAspect:#newWidget.
 !
 
 classMenuOpenClassCreationWizard
-    |dialog newClassName superclassName superclass package namespace namespaceName 
+    |dialog newClassName superclassName superclass package namespace namespaceName
      namespacePrefix createdClass category language|
 
     dialog := NewClassWizardDialog new.
@@ -27893,21 +28293,21 @@
     category := (dialog categoryHolder value ? '* as yet unspecified *') withoutSeparators.
 
     (namespaceName = 'Smalltalk') ifTrue:[
-        namespacePrefix := ''
-    ] ifFalse:[
-        namespacePrefix := namespaceName , '::'
+	namespacePrefix := ''
+    ] ifFalse:[
+	namespacePrefix := namespaceName , '::'
     ].
     namespace := NameSpace name:namespaceName.
 
     Class packageQuerySignal answer:package
     do:[
-        |builder|
-
-"/        createdClass := 
+	|builder|
+
+"/        createdClass :=
 "/            superclass
-"/                subclass: (namespacePrefix,newClassName) asSymbol 
-"/                instanceVariableNames: dialog instVarNamesHolder value 
-"/                classVariableNames: dialog classVarNamesHolder value 
+"/                subclass: (namespacePrefix,newClassName) asSymbol
+"/                instanceVariableNames: dialog instVarNamesHolder value
+"/                classVariableNames: dialog classVarNamesHolder value
 "/                poolDictionaries: ' '
 "/                category: category.
 "/
@@ -27915,23 +28315,23 @@
 "/            createdClass class instanceVariableNames: dialog classInstVarNamesHolder value
 "/        ].
 
-        builder := ClassBuilder new.
-        builder metaclass:(language metaClass).
-        builder 
-            name:(namespacePrefix,newClassName) asSymbol 
-            inEnvironment:namespace 
-            subclassOf:superclass 
-            instanceVariableNames:(dialog instVarNamesHolder value) 
-            variable:false 
-            words:false 
-            pointers:false 
-            classVariableNames:(dialog classVarNamesHolder value) 
-            poolDictionaries:'' 
-            category:category 
-            comment:nil 
-            changed:true 
-            classInstanceVariableNames:(dialog classInstVarNamesHolder value).
-        createdClass := builder buildClass.
+	builder := ClassBuilder new.
+	builder metaclass:(language metaClass).
+	builder
+	    name:(namespacePrefix,newClassName) asSymbol
+	    inEnvironment:namespace
+	    subclassOf:superclass
+	    instanceVariableNames:(dialog instVarNamesHolder value)
+	    variable:false
+	    words:false
+	    pointers:false
+	    classVariableNames:(dialog classVarNamesHolder value)
+	    poolDictionaries:''
+	    category:category
+	    comment:nil
+	    changed:true
+	    classInstanceVariableNames:(dialog classInstVarNamesHolder value).
+	createdClass := builder buildClass.
     ].
 
     createdClass isNil ifTrue:[^ self ].
@@ -27939,44 +28339,44 @@
 
     Class packageQuerySignal answer:package
     do:[
-        self
-            generateUndoableChange:'Generate Code for %(singleClassNameOrNumberOfClasses)'
-            overClasses:(Array with:createdClass)
-            via:[:generator :cls |
-                |theNonMetaclass theMetaclass inheritedInitializeMethod|
-
-                theNonMetaclass := cls theNonMetaclass.
-                theMetaclass := cls theMetaclass.
-
-                dialog createAccessors ifTrue:[
-                    generator
-                        createAccessMethodsFor:(cls instVarNames)
-                        in:cls
-                        withChange:false
-                        asValueHolder:false
-                        readersOnly:false
-                        writersOnly:false
-                        lazyInitialization:false.
-                ].
-                dialog createInitializer ifTrue:[
-                    inheritedInitializeMethod := cls theMetaclass responseTo:#new.
-                    (inheritedInitializeMethod isNil or:[ (inheritedInitializeMethod sends:#initialize) not ]) ifTrue:[ 
-                        generator createInitializedInstanceCreationMethodsIn:theNonMetaclass
-                    ] ifFalse:[
-                        generator createInitializationMethodIn:theNonMetaclass
-                    ].
-                    generator createClassInitializeMethodIn:theMetaclass.
-                ].
-                dialog createUpdateMethod ifTrue:[
-                    generator createUpdateMethodIn:theNonMetaclass
-                ].
-                dialog createRequiredMethods ifTrue:[
-                    generator createClassResponsibleProtocolFor:theNonMetaclass
-                ].
-                dialog createInitialGUICode ifTrue:[
-                    self classMenuGenerateApplicationCodeFor:theNonMetaclass using:generator
-                ].
-            ].
+	self
+	    generateUndoableChange:'Generate Code for %(singleClassNameOrNumberOfClasses)'
+	    overClasses:(Array with:createdClass)
+	    via:[:generator :cls |
+		|theNonMetaclass theMetaclass inheritedInitializeMethod|
+
+		theNonMetaclass := cls theNonMetaclass.
+		theMetaclass := cls theMetaclass.
+
+		dialog createAccessors ifTrue:[
+		    generator
+			createAccessMethodsFor:(cls instVarNames)
+			in:cls
+			withChange:false
+			asValueHolder:false
+			readersOnly:false
+			writersOnly:false
+			lazyInitialization:false.
+		].
+		dialog createInitializer ifTrue:[
+		    inheritedInitializeMethod := cls theMetaclass responseTo:#new.
+		    (inheritedInitializeMethod isNil or:[ (inheritedInitializeMethod sends:#initialize) not ]) ifTrue:[
+			generator createInitializedInstanceCreationMethodsIn:theNonMetaclass
+		    ] ifFalse:[
+			generator createInitializationMethodIn:theNonMetaclass
+		    ].
+		    generator createClassInitializeMethodIn:theMetaclass.
+		].
+		dialog createUpdateMethod ifTrue:[
+		    generator createUpdateMethodIn:theNonMetaclass
+		].
+		dialog createRequiredMethods ifTrue:[
+		    generator createClassResponsibleProtocolFor:theNonMetaclass
+		].
+		dialog createInitialGUICode ifTrue:[
+		    self classMenuGenerateApplicationCodeFor:theNonMetaclass using:generator
+		].
+	    ].
     ].
 
     "Modified: / 29-12-2011 / 13:48:54 / cg"
@@ -27992,8 +28392,8 @@
     self selectedMethods value:nil.
     self selectProtocols:nil.
     self
-        showClassPrimitive:aspect
-        class:(self theSingleSelectedClass theNonMetaclass)
+	showClassPrimitive:aspect
+	class:(self theSingleSelectedClass theNonMetaclass)
 !
 
 classMenuPrimitiveDefinitions
@@ -28030,28 +28430,28 @@
 !
 
 classMenuRecompile
-    "recompile selected classes (kludge - for me)"
+    "recompile selected classes (to turn off instrumentation, for example)"
 
     self selectedClassesDo:[:eachClass |
-        eachClass theNonMetaclass recompile.
-        eachClass theMetaclass recompile.
-    ].
+	self recompileClass:eachClass
+    ].
+
+    "Modified: / 31-05-2012 / 12:01:57 / cg"
 !
 
 classMenuRecompileAll
-    "recompile selected classes incl all subclasses (kludge - for me)"
+    "recompile selected classes incl. all subclasses (to turn off instrumentation, for example)"
 
     |already|
 
     already := Set new.
     self selectedClassesDo:[:each |
-        each withAllSubclassesDo:[:eachClass |
-            (already includes:eachClass theNonMetaclass) ifFalse:[
-                already add:eachClass theNonMetaclass.
-                eachClass theNonMetaclass recompile.
-                eachClass theMetaclass recompile.
-            ]
-        ].
+	each withAllSubclassesDo:[:eachClass |
+	    (already includes:eachClass theNonMetaclass) ifFalse:[
+		already add:eachClass theNonMetaclass.
+		self recompileClass:eachClass
+	    ]
+	].
     ].
 
     "Created: / 07-09-2011 / 21:23:01 / cg"
@@ -28059,7 +28459,7 @@
 
 classMenuRecompileInstrumented
     self selectedClassesDo:[:eachClass |
-        self recompileClassWithInstrumentation:eachClass
+	self recompileClassWithInstrumentation:eachClass
     ].
 
     "Modified: / 10-08-2010 / 14:36:42 / cg"
@@ -28083,7 +28483,7 @@
     "remove the selected classes (and all of its subclasses)"
 
     self withWaitCursorDo:[
-        self classMenuRemoveAndPullUpSubclasses:false
+	self classMenuRemoveAndPullUpSubclasses:false
     ]
 
     "Modified: / 27-07-2006 / 09:33:35 / cg"
@@ -28101,78 +28501,78 @@
     offerYesToAll := self selectedClassesValue size > 1.
 
     YesToAllConfirmation handleConfirmationIn:[
-        self
-            selectedClassesNonMetaDo:[:cls |
-                self
-                    addClassesToRemoveForClass:cls
-                    to:classesToRemove
-                    removingSubclasses:pullUpSubclasses not
-                    withCancel:offerCancel
-            ]
-            ifUnloaded:[:cls |
-                |answer|
-
-                YesToAllConfirmation query ifTrue:[
-                    answer :=  true
-                ] ifFalse:[
-                    offerYesToAll ifTrue:[
-                        answer := OptionBox
-                                      request:(resources
-                                                string:'Class ''%1'' is autoloaded - remove anyway ?'
-                                                with:cls name allBold)
-                                      label:(resources string:'Confirm')
-                                      image:(YesNoBox iconBitmap)
-                                      buttonLabels:(resources array:#('Cancel' 'No' 'Yes' 'Yes to All'))
-                                      values:#(nil false true #yesToAll)
-                                      default:false
-                                      onCancel:false.
-                        answer == #yesToAll ifTrue:[
-                            YesToAllConfirmation notify.
-                            answer := true
-                        ].
-                    ] ifFalse:[
-                        answer := Dialog
-                                        confirmWithCancel:
-                                            (resources
-                                                string:'Class ''%1'' is autoloaded - remove anyway ?'
-                                                with:cls name allBold)
-                                        default:
-                                            false.
-                    ].
-                    answer == nil ifTrue:[
-                        ^ self    "/ cancelled
-                    ].
-                ].
-                answer == true ifTrue:[
-                    self
-                        addClassesToRemoveForClass:cls
-                        to:classesToRemove
-                        removingSubclasses:pullUpSubclasses not
-                        withCancel:offerCancel
-                        withConfirm:false
-                ].
-                false
-            ]
-            ifPrivate:[:cls |
-                self
-                    addClassesToRemoveForClass:cls
-                    to:classesToRemove
-                    removingSubclasses:pullUpSubclasses not
-                    withCancel:offerCancel
-            ].
+	self
+	    selectedClassesNonMetaDo:[:cls |
+		self
+		    addClassesToRemoveForClass:cls
+		    to:classesToRemove
+		    removingSubclasses:pullUpSubclasses not
+		    withCancel:offerCancel
+	    ]
+	    ifUnloaded:[:cls |
+		|answer|
+
+		YesToAllConfirmation query ifTrue:[
+		    answer :=  true
+		] ifFalse:[
+		    offerYesToAll ifTrue:[
+			answer := OptionBox
+				      request:(resources
+						string:'Class ''%1'' is autoloaded - remove anyway ?'
+						with:cls name allBold)
+				      label:(resources string:'Confirm')
+				      image:(YesNoBox iconBitmap)
+				      buttonLabels:(resources array:#('Cancel' 'No' 'Yes' 'Yes to All'))
+				      values:#(nil false true #yesToAll)
+				      default:false
+				      onCancel:false.
+			answer == #yesToAll ifTrue:[
+			    YesToAllConfirmation notify.
+			    answer := true
+			].
+		    ] ifFalse:[
+			answer := Dialog
+					confirmWithCancel:
+					    (resources
+						string:'Class ''%1'' is autoloaded - remove anyway ?'
+						with:cls name allBold)
+					default:
+					    false.
+		    ].
+		    answer == nil ifTrue:[
+			^ self    "/ cancelled
+		    ].
+		].
+		answer == true ifTrue:[
+		    self
+			addClassesToRemoveForClass:cls
+			to:classesToRemove
+			removingSubclasses:pullUpSubclasses not
+			withCancel:offerCancel
+			withConfirm:false
+		].
+		false
+	    ]
+	    ifPrivate:[:cls |
+		self
+		    addClassesToRemoveForClass:cls
+		    to:classesToRemove
+		    removingSubclasses:pullUpSubclasses not
+		    withCancel:offerCancel
+	    ].
     ].
 
     classesToRemove notEmpty ifTrue:[
-        self removeClasses:classesToRemove pullUpSubclasses:pullUpSubclasses.
-        (Dialog
-              confirm:(resources
-                        stringWithCRs:'Cleanup the ChangeSet ?\\i.e. remove entries for removed class(es)')
-              yesLabel:(resources string:'Cleanup'))
-        ifTrue:[
-            classesToRemove do:[:eachClass |
-                ChangeSet current condenseChangesForClass:eachClass
-            ].
-        ].
+	self removeClasses:classesToRemove pullUpSubclasses:pullUpSubclasses.
+	(Dialog
+	      confirm:(resources
+			stringWithCRs:'Cleanup the ChangeSet ?\\i.e. remove entries for removed class(es)')
+	      yesLabel:(resources string:'Cleanup'))
+	ifTrue:[
+	    classesToRemove do:[:eachClass |
+		ChangeSet current condenseChangesForClass:eachClass
+	    ].
+	].
     ]
 
     "Modified: / 28-02-2012 / 16:47:47 / cg"
@@ -28191,11 +28591,11 @@
     currentClass := currentClass theNonMetaclass.
 
     box := self
-                enterBoxTitle:(resources
-                                string:'Rename ''%1'' to:'
-                                with:currentClass name allBold)
-                okText:'Rename'
-                label:'Rename Class'.
+		enterBoxTitle:(resources
+				string:'Rename ''%1'' to:'
+				with:currentClass name allBold)
+		okText:'Rename'
+		label:'Rename Class'.
 
     box initialText:(currentClass name).
     box action:[:aString | newNameString := aString].
@@ -28210,60 +28610,60 @@
     nsOrOwner := Smalltalk.
     s := newNameString readStream.
     [s atEnd] whileFalse:[
-        nextWord := s nextAlphaNumericWord.
-        [s peek == $_] whileTrue:[
-            nextWord := nextWord , '_' , s nextAlphaNumericWord.
-        ].
-        s skipSeparators.
-        s atEnd ifFalse:[
-            nsOrOwner isNameSpace ifTrue:[
-                t := nsOrOwner at:nextWord asSymbol
-            ] ifFalse:[
-                t := nsOrOwner privateClassesAt:nextWord asSymbol
-            ].
-            t isNil ifTrue:[
-                self warn:('Name: ''' , newNameString , ''' specifies a non-existing NameSpace or Ownerclass.\\(no ''' , nextWord , ''' in ''' , nsOrOwner name , ')') withCRs.
-                ^ self
-            ].
-            nsOrOwner := t.
-            s peek == $. ifTrue:[
-                s next.
-            ] ifFalse:[
-                s peek == $: ifTrue:[
-                    s next.
-                    s next ~= $: ifTrue:[
-                        self warn:'Bad name: ''' , newNameString , ''' (either use ''.'' or ''::'' as nameSpace separator)'.
-                        ^ self
-                    ]
-                ]
-            ]
-        ]
+	nextWord := s nextAlphaNumericWord.
+	[s peek == $_] whileTrue:[
+	    nextWord := nextWord , '_' , s nextAlphaNumericWord.
+	].
+	s skipSeparators.
+	s atEnd ifFalse:[
+	    nsOrOwner isNameSpace ifTrue:[
+		t := nsOrOwner at:nextWord asSymbol
+	    ] ifFalse:[
+		t := nsOrOwner privateClassesAt:nextWord asSymbol
+	    ].
+	    t isNil ifTrue:[
+		self warn:('Name: ''' , newNameString , ''' specifies a non-existing NameSpace or Ownerclass.\\(no ''' , nextWord , ''' in ''' , nsOrOwner name , ')') withCRs.
+		^ self
+	    ].
+	    nsOrOwner := t.
+	    s peek == $. ifTrue:[
+		s next.
+	    ] ifFalse:[
+		s peek == $: ifTrue:[
+		    s next.
+		    s next ~= $: ifTrue:[
+			self warn:'Bad name: ''' , newNameString , ''' (either use ''.'' or ''::'' as nameSpace separator)'.
+			^ self
+		    ]
+		]
+	    ]
+	]
     ].
     nsOrOwner isNil ifTrue:[
-        self warn:'Name ''' , newNameString , ''' specifies a non-existing NameSpace or Ownerclass'.
-        ^ self
+	self warn:'Name ''' , newNameString , ''' specifies a non-existing NameSpace or Ownerclass'.
+	^ self
     ].
 
     hardRename := false.
     currentClass isPrivate ifTrue:[
-        "/ check if the new name implies an owner-change
-        hardRename := (nsOrOwner ~~ currentClass owningClass)
-    ] ifFalse:[
-        hardRename := (nsOrOwner ~~ currentClass nameSpace)
+	"/ check if the new name implies an owner-change
+	hardRename := (nsOrOwner ~~ currentClass owningClass)
+    ] ifFalse:[
+	hardRename := (nsOrOwner ~~ currentClass nameSpace)
     ].
     hardRename ifTrue:[
-        (self confirm:'New name implies a NameSpace or OwningClass change - is this what you want ?') ifFalse:[
-            ^ self
-        ]
+	(self confirm:'New name implies a NameSpace or OwningClass change - is this what you want ?') ifFalse:[
+	    ^ self
+	]
     ].
 
     "/ check if the target already exists - confirm if so.
 
     (cls := Smalltalk classNamed:newNameString) notNil ifTrue:[
-        (self confirm:(resources string:'Attention: a class named ''%1'' already present (in the ''%2'' category).\\Rename over it ?'
-                                 with:newNameString allBold
-                                 with:cls category allBold) withCRs)
-            ifFalse:[^ self]
+	(self confirm:(resources string:'Attention: a class named ''%1'' already present (in the ''%2'' category).\\Rename over it ?'
+				 with:newNameString allBold
+				 with:cls category allBold) withCRs)
+	    ifFalse:[^ self]
     ].
 
     oldSym := currentClass name asSymbol.
@@ -28276,103 +28676,103 @@
     askForNewContainer := false.
     "/ check if the class has a repository container - warn about this if so
     currentClass isPrivate ifFalse:[
-        currentClass revision notNil ifTrue:[
-            "JV@2012-02-18: Ask only if manager is CVS (assuming that
-             other SCMs handle class renames nicely"
-            currentClass sourceCodeManager isCVS ifTrue:[
-                (self confirm:(resources string:'Remove the (old) source container for ''%1'' in the repository ?' with:oldSym allBold))
-                ifTrue:[
-                    SourceCodeManagerUtilities
-                            removeSourceContainerForClass:currentClass
-                            confirm:false
-                            warn:true.
-                    askForNewContainer := true.
-                ].
-            ] ifFalse:[
-                askForNewContainer := true.
-            ]
-        ]
+	currentClass revision notNil ifTrue:[
+	    "JV@2012-02-18: Ask only if manager is CVS (assuming that
+	     other SCMs handle class renames nicely"
+	    currentClass sourceCodeManager isCVS ifTrue:[
+		(self confirm:(resources string:'Remove the (old) source container for ''%1'' in the repository ?' with:oldSym allBold))
+		ifTrue:[
+		    SourceCodeManagerUtilities
+			    removeSourceContainerForClass:currentClass
+			    confirm:false
+			    warn:true.
+		    askForNewContainer := true.
+		].
+	    ] ifFalse:[
+		askForNewContainer := true.
+	    ]
+	]
     ].
 
     self busyLabel:('Searching for references to ' , oldSym).
-    referingMethods := SystemBrowser 
-                            allMethodsIn:(Smalltalk allClasses) 
-                            where:(SystemBrowser searchBlockForReferendsOf:oldSym).
+    referingMethods := SystemBrowser
+			    allMethodsIn:(Smalltalk allClasses)
+			    where:(SystemBrowser searchBlockForReferendsOf:oldSym).
     self normalLabel.
     referingMethods isEmpty ifTrue:[
-        Smalltalk renameClass:currentClass to:newNameString.
-    ] ifFalse:[
-        RenameClassRefactoring isNil ifTrue:[
-            Smalltalk renameClass:currentClass to:newNameString.
-            answer := OptionBox
-                          request:(resources 
-                                        stringWithCRs:'Browse %1 references to "%2" ?'
-                                        with:referingMethods size
-                                        with:oldSym allBold
-                                        with:newNameString allBold)
-                          label:(resources string:'Renaming class "%1" to "%2"' with:oldSym with:newNameString)
-                          buttonLabels:(resources array:#('Cancel' 'Browse' 'Rename'))
-                          values:#(false #browse #rename)
-                          default:#rename
-                          onCancel:false.
-        ] ifFalse:[
-            referingMethods size == 1 ifTrue:[
-                question := 'There is 1 reference to "%2"\from %4.\\Rename only or Rename and Rewrite to "%3" ?'
-            ] ifFalse:[
-                question := 'There are %1 references to "%2".\\Rename only or Rename and Rewrite to "%3" ?'
-            ].
-
-            answer := OptionBox
-                          request:(resources 
-                                        stringWithCRs:question
-                                        with:referingMethods size
-                                        with:oldSym allBold
-                                        with:newNameString allBold
-                                        with:(referingMethods first whoString))
-                          label:(resources string:'Renaming class "%1" to "%2"' with:oldSym with:newNameString)
-                          buttonLabels:(resources array:#('Cancel' 'Browse' 'Rename && Browse' 'Rename' 'Rename && Rewrite'  ))
-                          values:#(false #browse #renameAndBrowse #rename #renameAndRewrite )
-                          default:#renameAndRewrite
-                          onCancel:false.
-        ].
-
-        (answer == #browse or:[answer == #renameAndBrowse]) ifTrue:[
-            browser := self 
-                            spawnMethodBrowserFor:referingMethods 
-                            in:#newBuffer 
-                            label:(resources string:'Methods referring to %1' with:oldSym)
-        ].
-        (answer == #rename or:[answer == #renameAndBrowse]) ifTrue:[
-            Smalltalk renameClass:currentClass to:newNameString.
-            browser := self 
-                            spawnMethodBrowserFor:referingMethods 
-                            in:#newBuffer 
-                            label:(resources string:'Methods referring to %1 which was renamed to %2' with:oldSym with:newNameString)
-        ].
-        answer == #renameAndRewrite ifTrue:[
-            refactoring := RenameClassRefactoring renameClassNamed:oldSym to:newNameString.
-            self performRefactoring:refactoring.
-            referingMethods := SystemBrowser 
-                            allMethodsIn:(Smalltalk allClasses) 
-                            where:(SystemBrowser searchBlockForReferendsOf:newNameString).
-            UserInformation ignoreIn:[
-                browser := self 
-                            spawnMethodBrowserFor:referingMethods 
-                            in:#newBuffer 
-                            label:(resources string:'Rewritten Methods now referring to %1' with:newNameString).
-            ].
-        ].
-        browser notNil ifTrue:[
-            browser autoSearchVariable:oldBaseSym.
-        ].
+	Smalltalk renameClass:currentClass to:newNameString.
+    ] ifFalse:[
+	RenameClassRefactoring isNil ifTrue:[
+	    Smalltalk renameClass:currentClass to:newNameString.
+	    answer := OptionBox
+			  request:(resources
+					stringWithCRs:'Browse %1 references to "%2" ?'
+					with:referingMethods size
+					with:oldSym allBold
+					with:newNameString allBold)
+			  label:(resources string:'Renaming class "%1" to "%2"' with:oldSym with:newNameString)
+			  buttonLabels:(resources array:#('Cancel' 'Browse' 'Rename'))
+			  values:#(false #browse #rename)
+			  default:#rename
+			  onCancel:false.
+	] ifFalse:[
+	    referingMethods size == 1 ifTrue:[
+		question := 'There is 1 reference to "%2"\from %4.\\Rename only or Rename and Rewrite to "%3" ?'
+	    ] ifFalse:[
+		question := 'There are %1 references to "%2".\\Rename only or Rename and Rewrite to "%3" ?'
+	    ].
+
+	    answer := OptionBox
+			  request:(resources
+					stringWithCRs:question
+					with:referingMethods size
+					with:oldSym allBold
+					with:newNameString allBold
+					with:(referingMethods first whoString))
+			  label:(resources string:'Renaming class "%1" to "%2"' with:oldSym with:newNameString)
+			  buttonLabels:(resources array:#('Cancel' 'Browse' 'Rename && Browse' 'Rename' 'Rename && Rewrite'  ))
+			  values:#(false #browse #renameAndBrowse #rename #renameAndRewrite )
+			  default:#renameAndRewrite
+			  onCancel:false.
+	].
+
+	(answer == #browse or:[answer == #renameAndBrowse]) ifTrue:[
+	    browser := self
+			    spawnMethodBrowserFor:referingMethods
+			    in:#newBuffer
+			    label:(resources string:'Methods referring to %1' with:oldSym)
+	].
+	(answer == #rename or:[answer == #renameAndBrowse]) ifTrue:[
+	    Smalltalk renameClass:currentClass to:newNameString.
+	    browser := self
+			    spawnMethodBrowserFor:referingMethods
+			    in:#newBuffer
+			    label:(resources string:'Methods referring to %1 which was renamed to %2' with:oldSym with:newNameString)
+	].
+	answer == #renameAndRewrite ifTrue:[
+	    refactoring := RenameClassRefactoring renameClassNamed:oldSym to:newNameString.
+	    self performRefactoring:refactoring.
+	    referingMethods := SystemBrowser
+			    allMethodsIn:(Smalltalk allClasses)
+			    where:(SystemBrowser searchBlockForReferendsOf:newNameString).
+	    UserInformation ignoreIn:[
+		browser := self
+			    spawnMethodBrowserFor:referingMethods
+			    in:#newBuffer
+			    label:(resources string:'Rewritten Methods now referring to %1' with:newNameString).
+	    ].
+	].
+	browser notNil ifTrue:[
+	    browser autoSearchVariable:oldBaseSym.
+	].
     ].
 
     askForNewContainer ifTrue:[
-        (self confirm:(resources string:'Create a new source container for ''%1'' ?' with:newNameString allBold))
-        ifTrue:[
-            currentClass setClassFilename:nil.
-            SourceCodeManagerUtilities createSourceContainerForClass:(Smalltalk at:newNameString asSymbol)
-        ]
+	(self confirm:(resources string:'Create a new source container for ''%1'' ?' with:newNameString allBold))
+	ifTrue:[
+	    currentClass setClassFilename:nil.
+	    SourceCodeManagerUtilities createSourceContainerForClass:(Smalltalk at:newNameString asSymbol)
+	]
     ].
 
     "Modified: / 15-08-2010 / 11:54:23 / cg"
@@ -28381,8 +28781,8 @@
 
 classMenuRewrite
     MethodRewriter new
-        classes: self selectedClassesValue;
-        open
+	classes: self selectedClassesValue;
+	open
 
     "Created: / 05-07-2011 / 14:48:32 / cg"
 !
@@ -28391,24 +28791,24 @@
     "write classes documentation to a file"
 
     self
-        selectedClassesNonMetaDo:
-            [:cls |
-                self saveClassDocumentationFor:cls
-            ]
-        ifUnloaded:
-            [:cls |
-                true
-            ]
-        ifPrivate:
-            [:cls |
-            ]
+	selectedClassesNonMetaDo:
+	    [:cls |
+		self saveClassDocumentationFor:cls
+	    ]
+	ifUnloaded:
+	    [:cls |
+		true
+	    ]
+	ifPrivate:
+	    [:cls |
+	    ]
 !
 
 classMenuSaveRemove
     "remove the selected classes and pull up their subclasses"
 
     (self canUseRefactoringSupport) ifFalse:[
-        ^ self warn:'Sorry - need refactoring support for this function'.
+	^ self warn:'Sorry - need refactoring support for this function'.
     ].
     ^ self classMenuRemoveAndPullUpSubclasses:true
 
@@ -28543,159 +28943,159 @@
 
     isPrivate := isPrivateWanted.
     isPrivate ifTrue:[
-        ownerClass := currentClass.
-        ownerClass notNil ifTrue:[
-            ownerClass := ownerClass theNonMetaclass.
-        ].
+	ownerClass := currentClass.
+	ownerClass notNil ifTrue:[
+	    ownerClass := ownerClass theNonMetaclass.
+	].
     ].
     aSuperClass isPrivate ifTrue:[
-        isPrivate := true.
-        ownerClass := aSuperClass theNonMetaclass owningClass
+	isPrivate := true.
+	ownerClass := aSuperClass theNonMetaclass owningClass
     ].
 
     isPrivate ifTrue:[
-        metaClassUsedOrNil isNil ifTrue:[
-            metaClassUsedOrNil := ownerClass theMetaclass class
-        ] ifFalse:[
-        ]
+	metaClassUsedOrNil isNil ifTrue:[
+	    metaClassUsedOrNil := ownerClass theMetaclass class
+	] ifFalse:[
+	]
     ].
 
     (metaClassUsedOrNil notNil
     and:[(metaClassUsedOrNil ~~ Metaclass)
-         and:[metaClassUsedOrNil ~~ PrivateMetaclass]
+	 and:[metaClassUsedOrNil ~~ PrivateMetaclass]
     " and:[(metaClassUsedOrNil isSubclassOf:Metaclass) not] " ]) ifTrue:[
-        ^ metaClassUsedOrNil
-                classTemplateFor:aSuperClass
-                in:categoryString
-                asNamespace:asNameSpace
-                private:isPrivate
+	^ metaClassUsedOrNil
+		classTemplateFor:aSuperClass
+		in:categoryString
+		asNamespace:asNameSpace
+		private:isPrivate
     ].
 
     (self javaMode
     or:[aSuperClass notNil and:[aSuperClass isJavaClass]])
     ifTrue:[
-        ^ self javaClassTemplateFor:aSuperClass in:categoryString private:isPrivate
+	^ self javaClassTemplateFor:aSuperClass in:categoryString private:isPrivate
     ].
 
     nsTemplate := ''.
 
     self organizerMode value ~~ OrganizerCanvas organizerModeNamespace ifTrue:[
-        (aSuperClass notNil
-        and:[(superclassesNamespace := aSuperClass nameSpace) ~~ Smalltalk]) ifTrue:[
-            (superclassesNamespace isNameSpace
-            or:[superclassesNamespace ~~ ownerClass]) ifTrue:[
-                nsTemplate := superclassesNamespace name , '::'.
-            ].
-        ]
-    ] ifFalse:[
-        (selectedNamespaces := self selectedNamespaces value) size > 0 ifTrue:[
-            selectedNamespaces size == 1 ifTrue:[
-                selectedNamespaces first ~= BrowserList nameListEntryForALL ifTrue:[
-                    currentNamespace := Smalltalk at:selectedNamespaces first asSymbol.
-                ]
-            ]
-        ]
+	(aSuperClass notNil
+	and:[(superclassesNamespace := aSuperClass nameSpace) ~~ Smalltalk]) ifTrue:[
+	    (superclassesNamespace isNameSpace
+	    or:[superclassesNamespace ~~ ownerClass]) ifTrue:[
+		nsTemplate := superclassesNamespace name , '::'.
+	    ].
+	]
+    ] ifFalse:[
+	(selectedNamespaces := self selectedNamespaces value) size > 0 ifTrue:[
+	    selectedNamespaces size == 1 ifTrue:[
+		selectedNamespaces first ~= BrowserList nameListEntryForALL ifTrue:[
+		    currentNamespace := Smalltalk at:selectedNamespaces first asSymbol.
+		]
+	    ]
+	]
     ].
 
     s := TextStream on:''.
 
     asNameSpace ifTrue:[
-        s nextPutLine:'NameSpace name:''' , nsTemplate , 'NewNameSpace'''.
-        s cr.
-        s emphasis:(UserPreferences current commentEmphasisAndColor).
-        s nextPutAll:'"
+	s nextPutLine:'NameSpace name:''' , nsTemplate , 'NewNameSpace'''.
+	s cr.
+	s emphasis:(UserPreferences current commentEmphasisAndColor).
+	s nextPutAll:'"
  Replace ''NewNameSpace'' by the desired name.
 
  Create the namespace by ''accepting'',
  either via the menu or the keyboard (usually CMD-A).
 "
 '.
-        ^ s contents.
+	^ s contents.
     ].
 
     currentNamespace isNil ifTrue:[
-        currentNamespace := self currentNamespace.
+	currentNamespace := self currentNamespace.
     ].
     currentClass notNil ifTrue:[
-        currentClass := currentClass theNonMetaclass.
+	currentClass := currentClass theNonMetaclass.
     ].
 
     withNameSpaceDirective :=
-        currentNamespace notNil
-        and:[currentNamespace ~= (BrowserList nameListEntryForALL)
-        and:[currentNamespace ~= Smalltalk]].
+	currentNamespace notNil
+	and:[currentNamespace ~= (BrowserList nameListEntryForALL)
+	and:[currentNamespace ~= Smalltalk]].
 
     withNameSpaceDirective ifTrue:[
-        s nextPutAll:('"{ NameSpace: ''' , currentNamespace name , ''' }"').
-        s cr; cr.
-        aSuperClass nameSpace = currentNamespace ifTrue:[
-            className := aSuperClass nameWithoutNameSpacePrefix.
-        ] ifFalse:[
-            className := aSuperClass name.
-        ].
-    ] ifFalse:[
-        className := aSuperClass name.
+	s nextPutAll:('"{ NameSpace: ''' , currentNamespace name , ''' }"').
+	s cr; cr.
+	aSuperClass nameSpace = currentNamespace ifTrue:[
+	    className := aSuperClass nameWithoutNameSpacePrefix.
+	] ifFalse:[
+	    className := aSuperClass name.
+	].
+    ] ifFalse:[
+	className := aSuperClass name.
     ].
 
     nsTemplate := ''.
     withNameSpaceDirective ifFalse:[
-        self organizerMode value ~~ OrganizerCanvas organizerModeNamespace ifTrue:[
-            (aSuperClass notNil
-            and:[(superclassesNamespace := aSuperClass nameSpace) ~~ Smalltalk]) ifTrue:[
-                (superclassesNamespace isNameSpace
-                or:[superclassesNamespace ~~ ownerClass]) ifTrue:[
-                    nsTemplate := superclassesNamespace name , '::'.
-                ].
-            ]
-        ].
+	self organizerMode value ~~ OrganizerCanvas organizerModeNamespace ifTrue:[
+	    (aSuperClass notNil
+	    and:[(superclassesNamespace := aSuperClass nameSpace) ~~ Smalltalk]) ifTrue:[
+		(superclassesNamespace isNameSpace
+		or:[superclassesNamespace ~~ ownerClass]) ifTrue:[
+		    nsTemplate := superclassesNamespace name , '::'.
+		].
+	    ]
+	].
     ].
 
     cat := categoryString.
     (cat isNil or:[cat startsWith:$*]) ifTrue:[
-        cat := Compiler defaultMethodCategory "/ '** As yet uncategorized **'
+	cat := Compiler defaultMethodCategory "/ '** As yet uncategorized **'
     ].
 
     ((aSuperClass == SimpleDialog) or:[aSuperClass isSubclassOf:SimpleDialog]) ifTrue:[
-        nameProto := 'NewDialog'.
-    ] ifFalse:[
-        ((aSuperClass == ApplicationModel) or:[aSuperClass isSubclassOf:ApplicationModel]) ifTrue:[
-            nameProto := 'NewApplication'.
-        ] ifFalse:[
-            aSuperClass == TestCase ifTrue:[
-                nameProto := 'NewTestCase'.
-            ] ifFalse:[ aSuperClass == Error ifTrue:[
-                nameProto := 'NewError'.
-            ] ifFalse:[ aSuperClass == Exception ifTrue:[
-                nameProto := 'NewException'.
-            ] ifFalse:[ aSuperClass == SharedPool ifTrue:[
-                nameProto := 'NewSharedPool'.
-            ] ifFalse:[
-                nameProto := 'NewClass'.
-            ]]]]
-        ]
+	nameProto := 'NewDialog'.
+    ] ifFalse:[
+	((aSuperClass == ApplicationModel) or:[aSuperClass isSubclassOf:ApplicationModel]) ifTrue:[
+	    nameProto := 'NewApplication'.
+	] ifFalse:[
+	    aSuperClass == TestCase ifTrue:[
+		nameProto := 'NewTestCase'.
+	    ] ifFalse:[ aSuperClass == Error ifTrue:[
+		nameProto := 'NewError'.
+	    ] ifFalse:[ aSuperClass == Exception ifTrue:[
+		nameProto := 'NewException'.
+	    ] ifFalse:[ aSuperClass == SharedPool ifTrue:[
+		nameProto := 'NewSharedPool'.
+	    ] ifFalse:[
+		nameProto := 'NewClass'.
+	    ]]]]
+	]
     ].
 
     i := 1.
 
     isPrivate ifTrue:[
-        namePrefix := ownerClass name , '::'.
-        existingNames := ownerClass privateClasses.
-        existingNames size > 0 ifTrue:[
-            existingNames := existingNames collect:[:cls | cls name].
-        ]
-    ] ifFalse:[
-        namePrefix := ''.
-        existingNames := Smalltalk keys
+	namePrefix := ownerClass name , '::'.
+	existingNames := ownerClass privateClasses.
+	existingNames size > 0 ifTrue:[
+	    existingNames := existingNames collect:[:cls | cls name].
+	]
+    ] ifFalse:[
+	namePrefix := ''.
+	existingNames := Smalltalk keys
     ].
 
     name := nsTemplate , nameProto , i printString.
     existingNames notNil ifTrue:[
-        nameUsed := namePrefix , name.
-        [nameUsed knownAsSymbol and:[existingNames includes:nameUsed asSymbol]] whileTrue:[
-            i := i + 1.
-            name := nsTemplate , nameProto , i printString.
-            nameUsed := namePrefix , name
-        ].
+	nameUsed := namePrefix , name.
+	[nameUsed knownAsSymbol and:[existingNames includes:nameUsed asSymbol]] whileTrue:[
+	    i := i + 1.
+	    name := nsTemplate , nameProto , i printString.
+	    nameUsed := namePrefix , name
+	].
     ].
 
     s emphasis:#bold.
@@ -28710,24 +29110,24 @@
 
     s nextPutLine:'    instanceVariableNames: '''''.
     aSuperClass == SharedPool ifTrue:[
-        s nextPutLine:'    classVariableNames: ''PoolVar1 PoolVar2...'''.
-    ] ifFalse:[
-        s nextPutLine:'    classVariableNames: '''''.
+	s nextPutLine:'    classVariableNames: ''PoolVar1 PoolVar2...'''.
+    ] ifFalse:[
+	s nextPutLine:'    classVariableNames: '''''.
     ].
     s nextPutLine:'    poolDictionaries: '''''.
     isPrivate ifTrue:[
-        withNameSpaceDirective ifTrue:[
-            ownerName := ownerClass nameWithoutNameSpacePrefix
-        ] ifFalse:[
-            ownerName := ownerClass name
-        ].
-        s nextPutAll:'    privateIn: ' , ownerName
-    ] ifFalse:[
-        s nextPutAll:'    category: '''.
-        cat notNil ifTrue:[
-            cat printWithQuotesDoubledOn:s
-        ].
-        s nextPutAll: ''''
+	withNameSpaceDirective ifTrue:[
+	    ownerName := ownerClass nameWithoutNameSpacePrefix
+	] ifFalse:[
+	    ownerName := ownerClass name
+	].
+	s nextPutAll:'    privateIn: ' , ownerName
+    ] ifFalse:[
+	s nextPutAll:'    category: '''.
+	cat notNil ifTrue:[
+	    cat printWithQuotesDoubledOn:s
+	].
+	s nextPutAll: ''''
     ].
 
     s cr; cr.
@@ -28763,7 +29163,7 @@
 
 debugMenuRecompileMethodsInstrumented
     self selectedMethodsDo:[:eachMethod |
-        self recompileMethodWithInstrumentation:eachMethod
+	self recompileMethodWithInstrumentation:eachMethod
     ].
 
     "Created: / 10-08-2010 / 14:36:33 / cg"
@@ -28775,8 +29175,8 @@
     |lbl1 lbl2|
 
     (class1 isLoaded not or:[class2 isLoaded not]) ifTrue:[
-        self warn:'Cannot compare unloaded classes.'.
-        ^ self.
+	self warn:'Cannot compare unloaded classes.'.
+	^ self.
     ].
 
     self busyLabel:'comparing  ...' with:nil.
@@ -28785,22 +29185,24 @@
     lbl2 := class2 name.
 
     (UserPreferences versionDiffViewerClass)
-          openOnClass:class1
-          labelA:lbl1
-          andClass:class2
-          labelB:lbl2
-          title:('comparing ' , lbl1 , ' against ' , lbl2)
-          ifSame:[ self information:'sources are identical' ].
+	  openOnClass:class1
+	  labelA:lbl1
+	  andClass:class2
+	  labelB:lbl2
+	  title:('comparing ' , lbl1 , ' against ' , lbl2)
+	  ifSame:[ self information:'sources are identical' ].
 
     self normalLabel.
 !
 
 doCopyClass:aClass as:newClassName privateIn:ownerOrNil
-    self
-        doCopyClass:aClass
-        as:newClassName
-        privateIn:ownerOrNil
-        ignore:(IdentitySet new)
+    ^ self
+	doCopyClass:aClass
+	as:newClassName
+	privateIn:ownerOrNil
+	ignore:(IdentitySet new)
+
+    "Modified: / 24-05-2012 / 15:49:49 / cg"
 !
 
 doCopyClass:aClass as:newClassName privateIn:ownerOrNil ignore:setOfClassesToIgnore
@@ -28809,24 +29211,24 @@
     privateClassesBefore := aClass privateClasses.
 
     ownerOrNil isNil ifTrue:[
-        sel := aClass definitionSelector.
-        realNewClassName := newClassName asSymbol.
-    ] ifFalse:[
-        sel := aClass definitionSelectorPrivate.
-        realNewClassName := (ownerOrNil name , '::' , newClassName) asSymbol.
+	sel := aClass definitionSelector.
+	realNewClassName := newClassName asSymbol.
+    ] ifFalse:[
+	sel := aClass definitionSelectorPrivate.
+	realNewClassName := (ownerOrNil name , '::' , newClassName) asSymbol.
     ].
 
     newClass := aClass superclass
-                perform:sel
-                with:newClassName asSymbol
-                with:aClass instanceVariableString              
-                with:aClass classVariableString                 
-                with:aClass poolDictionaries                    
-                with:(ownerOrNil ifNil:[aClass category] ifNotNil:[ownerOrNil]).  "/ category: or privateIn:
+		perform:sel
+		with:newClassName asSymbol
+		with:aClass instanceVariableString
+		with:aClass classVariableString
+		with:aClass poolDictionaries
+		with:(ownerOrNil ifNil:[aClass category] ifNotNil:[ownerOrNil]).  "/ category: or privateIn:
 
     newClass isNil ifTrue:[
-        self error:'Internal class-definition error (should not happen)' mayProceed:true.
-        ^ self.
+	self error:'Internal class-definition error (should not happen)' mayProceed:true.
+	^ nil.
     ].
 
     newMetaclass := newClass class.
@@ -28837,35 +29239,35 @@
     newMetaclass := newClass class.
 
     aClass methodDictionary
-        keysAndValuesDo:[:sel :mthd |
-            newClass compile:(mthd source) classified:(mthd category)
+	keysAndValuesDo:[:sel :mthd |
+	    newClass compile:(mthd source) classified:(mthd category)
     ].
     aClass class methodDictionary
-        keysAndValuesDo:[:sel :mthd |
-            "/ skip the version method (to avoid confusing the repository)
-            (AbstractSourceCodeManager isVersionMethodSelector:sel) ifFalse:[
-                newMetaclass compile:(mthd source) classified:(mthd category)
-            ]
+	keysAndValuesDo:[:sel :mthd |
+	    "/ skip the version method (to avoid confusing the repository)
+	    (AbstractSourceCodeManager isVersionMethodSelector:sel) ifFalse:[
+		newMetaclass compile:(mthd source) classified:(mthd category)
+	    ]
     ].
     setOfClassesToIgnore add:newClass.
 
     privateClassesBefore do:[:eachPrivateClass |
-        (setOfClassesToIgnore includes:eachPrivateClass) ifFalse:[
-            self
-                doCopyClass:eachPrivateClass
-                as:(eachPrivateClass nameWithoutPrefix)
-                privateIn:newClass
-                ignore:setOfClassesToIgnore.
-        ].
+	(setOfClassesToIgnore includes:eachPrivateClass) ifFalse:[
+	    self
+		doCopyClass:eachPrivateClass
+		as:(eachPrivateClass nameWithoutPrefix)
+		privateIn:newClass
+		ignore:setOfClassesToIgnore.
+	].
     ].
 
     (newMetaclass includesSelector:#initialize) ifTrue:[
-        newClass initialize.
+	newClass initialize.
     ].
     newClass package:(Class packageQuerySignal query).
     ^ newClass
 
-    "Modified: / 22-12-2010 / 18:44:04 / cg"
+    "Modified: / 24-05-2012 / 15:49:59 / cg"
 !
 
 doMoveMethodsOfClass:aClass fromProject:oldProject toProject:newProject
@@ -28875,33 +29277,33 @@
     movedClassMethods := OrderedCollection new.
 
     aClass theNonMetaclass methodDictionary keysAndValuesDo:[:sel :mthd |
-        mthd package = oldProject ifTrue:[
-            "/ JV@2012-02-11
-            "/ this is required, because otherwise I would no longer be able to
-            "/ reconstruct my sourcecode (as the connection to the source-file is lost).
-            mthd makeLocalStringSource.
-            mthd setPackage:newProject.
-            movedInstMethods add:mthd.
-        ].
+	mthd package = oldProject ifTrue:[
+	    "/ JV@2012-02-11
+	    "/ this is required, because otherwise I would no longer be able to
+	    "/ reconstruct my sourcecode (as the connection to the source-file is lost).
+	    mthd makeLocalStringSource.
+	    mthd setPackage:newProject.
+	    movedInstMethods add:mthd.
+	].
     ].
     aClass theMetaclass methodDictionary keysAndValuesDo:[:sel :mthd |
-        mthd package = oldProject ifTrue:[
-            "/ JV@2012-02-11
-            "/ this is required, because otherwise I would no longer be able to
-            "/ reconstruct my sourcecode (as the connection to the source-file is lost).
-            mthd makeLocalStringSource.
-            mthd setPackage:newProject.
-            movedClassMethods add:mthd.
-        ].
+	mthd package = oldProject ifTrue:[
+	    "/ JV@2012-02-11
+	    "/ this is required, because otherwise I would no longer be able to
+	    "/ reconstruct my sourcecode (as the connection to the source-file is lost).
+	    mthd makeLocalStringSource.
+	    mthd setPackage:newProject.
+	    movedClassMethods add:mthd.
+	].
     ].
 
     movedInstMethods notEmpty ifTrue:[
-        aClass theNonMetaclass changed:#projectOrganization.
-        Smalltalk changed:#projectOrganization with:(Array with:aClass theNonMetaclass with:movedInstMethods).
+	aClass theNonMetaclass changed:#projectOrganization.
+	Smalltalk changed:#projectOrganization with:(Array with:aClass theNonMetaclass with:movedInstMethods).
     ].
     movedClassMethods notEmpty ifTrue:[
-        aClass theMetaclass changed:#projectOrganization.
-        Smalltalk changed:#projectOrganization with:(Array with:aClass theMetaclass with:movedClassMethods).
+	aClass theMetaclass changed:#projectOrganization.
+	Smalltalk changed:#projectOrganization with:(Array with:aClass theMetaclass with:movedClassMethods).
     ]
 
     "Modified: / 09-03-2012 / 23:41:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -28915,20 +29317,20 @@
     "run the selected method"
 
     self withWaitCursorDo:[
-        |m t retVal retvalString|
-
-        m := self theSingleSelectedMethod.
-        t := Time millisecondsToRun:[
-            retVal := m mclass theNonMetaclass perform:(m selector).
-        ].
-        (retVal isString 
-        or:[ retVal isLiteral ]) ifTrue:[
-            retvalString := retVal storeString.
-        ]  ifFalse:[
-            retvalString := retVal printString.
-        ].
-        Transcript showCR:'Exec. Time: %1' with:t milliseconds.
-        Transcript showCR:'Answer: %1' with:retvalString.
+	|m t retVal retvalString|
+
+	m := self theSingleSelectedMethod.
+	t := Time millisecondsToRun:[
+	    retVal := m mclass theNonMetaclass perform:(m selector).
+	].
+	(retVal isString
+	or:[ retVal isLiteral ]) ifTrue:[
+	    retvalString := retVal storeString.
+	]  ifFalse:[
+	    retvalString := retVal printString.
+	].
+	Transcript showCR:'Exec. Time: %1' with:t milliseconds.
+	Transcript showCR:'Answer: %1' with:retvalString.
     ]
 
     "Modified: / 19-11-2010 / 12:07:05 / cg"
@@ -28938,11 +29340,11 @@
     "fileOut a class."
 
     ^ self
-        fileOutClass:aClass
-        askForFile:doAsk
-        withCancelAll:withCancelAll
-        format:nil
-        sourceMode:nil
+	fileOutClass:aClass
+	askForFile:doAsk
+	withCancelAll:withCancelAll
+	format:nil
+	sourceMode:nil
 !
 
 fileOutClass:aClass askForFile:doAsk withCancelAll:withCancelAll format:formatSymbolOrNil sourceMode:sourceMode
@@ -28952,72 +29354,72 @@
 
     suffix := self fileSuffixForClass:aClass format:formatSymbolOrNil.
     formatSymbolOrNil notNil ifTrue:[
-        saveName := aClass theNonMetaclass name , '.' , suffix.
+	saveName := aClass theNonMetaclass name , '.' , suffix.
     ].
 
     stillAsking := doAsk.
 
     [stillAsking] whileTrue:[
-        saveName := self
-                        fileNameDialogForFileOut:(resources string:'FileOut ''%1'' as:' with:aClass name allBold)
-                        default:((Smalltalk fileNameForClass:aClass) , '.' , suffix)
-                        withCancelAll:(withCancelAll
-                                        ifTrue:[
-                                                  cancelAll := true.
-                                               ]
-                                        ifFalse:nil).
-
-        cancelAll == true ifTrue:[
-            AbortOperationRequest raise
-        ].
-
-        saveName isNil ifTrue:[
-            ^ self
-        ].
-
-        saveName isEmpty ifTrue:[       "/ can no longer happen ...
-            (self confirm:'Bad name given - try again ?') ifFalse:[
-                ^ self.
-            ].
-            stillAsking := true.
-        ] ifFalse:[
-            FileSelectionBox lastFileSelectionDirectory:(saveName asFilename directoryName).
-            stillAsking := false.
-        ].
+	saveName := self
+			fileNameDialogForFileOut:(resources string:'FileOut ''%1'' as:' with:aClass name allBold)
+			default:((Smalltalk fileNameForClass:aClass) , '.' , suffix)
+			withCancelAll:(withCancelAll
+					ifTrue:[
+						  cancelAll := true.
+					       ]
+					ifFalse:nil).
+
+	cancelAll == true ifTrue:[
+	    AbortOperationRequest raise
+	].
+
+	saveName isNil ifTrue:[
+	    ^ self
+	].
+
+	saveName isEmpty ifTrue:[       "/ can no longer happen ...
+	    (self confirm:'Bad name given - try again ?') ifFalse:[
+		^ self.
+	    ].
+	    stillAsking := true.
+	] ifFalse:[
+	    FileSelectionBox lastFileSelectionDirectory:(saveName asFilename directoryName).
+	    stillAsking := false.
+	].
     ].
 
     self busyLabel:'saving %1' with:aClass name.
     self withCursor:Cursor write do:[
-        Class fileOutErrorSignal handle:[:ex |
-            self warn:'Cannot fileOut: %1\(%2)' with:aClass name with:ex description.
-            self normalLabel.
-            ex return.
-        ] do:[
-            formatSymbolOrNil == #sif ifTrue:[
-                SmalltalkInterchangeFileManager newForFileOut
-                        fileName: saveName;
-                        addClass: aClass;
-                        fileOut
-            ] ifFalse:[
-                formatSymbolOrNil == #xml ifTrue:[
-                    saveName notNil ifTrue:[
-                        aClass fileOutXMLAs:saveName.
-                    ] ifFalse:[
-                        aClass fileOutXML.
-                    ]
-                ] ifFalse:[
-                    formatSymbolOrNil == #binary ifTrue:[
-                        aClass binaryFileOutOn:(saveName asFilename writeStream binary) sourceMode:sourceMode
-                    ] ifFalse:[
-                        saveName notNil ifTrue:[
-                            aClass fileOutAs:saveName.
-                        ] ifFalse:[
-                            aClass fileOut.
-                        ]
-                    ]
-                ]
-            ]
-        ].
+	Class fileOutErrorSignal handle:[:ex |
+	    self warn:'Cannot fileOut: %1\(%2)' with:aClass name with:ex description.
+	    self normalLabel.
+	    ex return.
+	] do:[
+	    formatSymbolOrNil == #sif ifTrue:[
+		SmalltalkInterchangeFileManager newForFileOut
+			fileName: saveName;
+			addClass: aClass;
+			fileOut
+	    ] ifFalse:[
+		formatSymbolOrNil == #xml ifTrue:[
+		    saveName notNil ifTrue:[
+			aClass fileOutXMLAs:saveName.
+		    ] ifFalse:[
+			aClass fileOutXML.
+		    ]
+		] ifFalse:[
+		    formatSymbolOrNil == #binary ifTrue:[
+			aClass binaryFileOutOn:(saveName asFilename writeStream binary) sourceMode:sourceMode
+		    ] ifFalse:[
+			saveName notNil ifTrue:[
+			    aClass fileOutAs:saveName.
+			] ifFalse:[
+			    aClass fileOut.
+			]
+		    ]
+		]
+	    ]
+	].
     ].
     self normalLabel.
 
@@ -29030,16 +29432,16 @@
     |dirName|
 
     dirName := self
-                askForDirectoryToFileOut:(resources string:'FileOut %1 class(es) in:'
-                                                    with:aBunchOfClasses size)
-                default:nil.
+		askForDirectoryToFileOut:(resources string:'FileOut %1 class(es) in:'
+						    with:aBunchOfClasses size)
+		default:nil.
     dirName isNil ifTrue:[
-        ^ self
-    ].
-    self
-        fileOutEachClass:aBunchOfClasses
-        in:dirName
-        withFormat:aFormatSymbolOrNil
+	^ self
+    ].
+    self
+	fileOutEachClass:aBunchOfClasses
+	in:dirName
+	withFormat:aFormatSymbolOrNil
 !
 
 fileOutEachClass:aCollectionOfClasses in:aDirectory withFormat:aFormatSymbolOrNil
@@ -29048,43 +29450,43 @@
     |savedClasses privateClasses owningClasses unsavedOwners answer|
 
     privateClasses := aCollectionOfClasses
-                select:[:eachClass | eachClass isPrivate].
+		select:[:eachClass | eachClass isPrivate].
     savedClasses := (aCollectionOfClasses
-                select:[:eachClass | eachClass isPrivate not]) asIdentitySet.
+		select:[:eachClass | eachClass isPrivate not]) asIdentitySet.
     owningClasses := (privateClasses
-                collect:[:eachPrivateClass | eachPrivateClass topOwningClass])
-                    asIdentitySet.
+		collect:[:eachPrivateClass | eachPrivateClass topOwningClass])
+		    asIdentitySet.
     unsavedOwners := owningClasses copy.
     unsavedOwners removeAllFoundIn:savedClasses.
     unsavedOwners notEmpty ifTrue:[
-        answer := self
-                    confirmWithCancel:'Private classes are saved with their owningClasses;\\Save owners as well ?'
-                            withCRs.
-        answer isNil ifTrue:[
-            ^ self
-        ].
-        answer == true ifTrue:[
-            savedClasses addAll:unsavedOwners
-        ]
+	answer := self
+		    confirmWithCancel:'Private classes are saved with their owningClasses;\\Save owners as well ?'
+			    withCRs.
+	answer isNil ifTrue:[
+	    ^ self
+	].
+	answer == true ifTrue:[
+	    savedClasses addAll:unsavedOwners
+	]
     ].
     savedClasses do:[:eachClass |
-        |fn|
-
-        eachClass isPrivate ifFalse:[
-            self busyLabel:'saving: %1' with:eachClass name.
-            Class fileOutErrorSignal handle:[:ex |
-                    self
-                        warn:'cannot fileOut: %1\(%2)\\skipped.'
-                        with:eachClass name allBold
-                        with:ex description.
-                    self normalLabel.
-                    ex return
-                ]
-                do:[
-                    fn := (Smalltalk fileNameForClass:eachClass) , '.st'.
-                    eachClass fileOutAs:(aDirectory asFilename constructString:fn)
-                ]
-        ]
+	|fn|
+
+	eachClass isPrivate ifFalse:[
+	    self busyLabel:'saving: %1' with:eachClass name.
+	    Class fileOutErrorSignal handle:[:ex |
+		    self
+			warn:'cannot fileOut: %1\(%2)\\skipped.'
+			with:eachClass name allBold
+			with:ex description.
+		    self normalLabel.
+		    ex return
+		]
+		do:[
+		    fn := (Smalltalk fileNameForClass:eachClass) , '.st'.
+		    eachClass fileOutAs:(aDirectory asFilename constructString:fn)
+		]
+	]
     ].
     self normalLabel
 !
@@ -29097,28 +29499,28 @@
     |programmingLanguage generator count dict className codeGeneratorClass|
 
     classes notNil ifTrue:[
-        "/ remove this a.s.a.p
-        "/ check if all classes are either smalltalk or java-script
-        (classes 
-            conform:[:cls | 
-                |lang| 
-
-                lang := cls programmingLanguage. 
-                lang isSmalltalk or:[lang isSTXJavaScript]]
-        ) ifFalse:[
-            Dialog warn:('Sorry.\\For now, this works only for Smalltalk classes.' withCRs).
-            ^ self.
-        ].
+	"/ remove this a.s.a.p
+	"/ check if all classes are either smalltalk or java-script
+	(classes
+	    conform:[:cls |
+		|lang|
+
+		lang := cls programmingLanguage.
+		lang isSmalltalk or:[lang isSTXJavaScript]]
+	) ifFalse:[
+	    Dialog warn:('Sorry.\\For now, this works only for Smalltalk classes.' withCRs).
+	    ^ self.
+	].
     ].
 
     programmingLanguage := (classes isEmptyOrNil)
-                    ifTrue:[ SmalltalkLanguage instance ]
-                    ifFalse:[ classes first programmingLanguage ].
-    
+		    ifTrue:[ SmalltalkLanguage instance ]
+		    ifFalse:[ classes first programmingLanguage ].
+
     codeGeneratorClass := programmingLanguage codeGeneratorClass.
     codeGeneratorClass isNil ifTrue:[
-        Dialog warn:('Sorry.\\For now, there seems to be no codeGeneratorClass defined for this language.' withCRs).
-        ^ self.
+	Dialog warn:('Sorry.\\For now, there seems to be no codeGeneratorClass defined for this language.' withCRs).
+	^ self.
     ].
 
     generator := codeGeneratorClass new.
@@ -29126,42 +29528,42 @@
 
     count := 0.
     self withWaitCursorDo:[
-        classes isNil ifTrue:[
-            aBlock value:generator value:nil.
-        ] ifFalse:[
-            classes do:[:eachClass |
-                eachClass isLoaded ifFalse:[
-                    Transcript showCR:'skipping unloaded class: ' , eachClass name.
-                ] ifTrue:[
-                    aBlock value:generator value:eachClass.
-                    count := count + 1.
-                ]
-            ].
-        ].
-
-        dict := Dictionary new.
-        dict at:1 put:count.
-        dict at:#numClasses put:count.
-        count ~~ 1 ifTrue:[
-            dict at:#numClassesOrEmpty put:( ' ' , count printString, ' ').
-            dict at:#inSingleClassOrEmpty put:''.
-            dict at:#forSingleClassOrEmpty put:''.
-            dict at:#sForPlural put:'s'.
-            dict at:#singleClassNameOrNumberOfClasses put:(count printString , ' classes').
-        ] ifFalse:[
-            className := classes first theNonMetaclass name.
-            dict at:#numClassesOrEmpty put:' '.
-            dict at:#inSingleClassOrEmpty put:' in ' , className.
-            dict at:#forSingleClassOrEmpty put:' for ' , className.
-            dict at:#sForPlural put:''.
-            dict at:#singleClassNameOrNumberOfClasses put:className.
-        ].
-
-        UserInformation handle:[:ex |
-            self showInfo:(ex messageText).
-        ] do:[
-            generator executeCollectedChangesNamed:(nameOfOperation expandPlaceholdersWith:dict)
-        ]
+	classes isNil ifTrue:[
+	    aBlock value:generator value:nil.
+	] ifFalse:[
+	    classes do:[:eachClass |
+		eachClass isLoaded ifFalse:[
+		    Transcript showCR:'skipping unloaded class: ' , eachClass name.
+		] ifTrue:[
+		    aBlock value:generator value:eachClass.
+		    count := count + 1.
+		]
+	    ].
+	].
+
+	dict := Dictionary new.
+	dict at:1 put:count.
+	dict at:#numClasses put:count.
+	count ~~ 1 ifTrue:[
+	    dict at:#numClassesOrEmpty put:( ' ' , count printString, ' ').
+	    dict at:#inSingleClassOrEmpty put:''.
+	    dict at:#forSingleClassOrEmpty put:''.
+	    dict at:#sForPlural put:'s'.
+	    dict at:#singleClassNameOrNumberOfClasses put:(count printString , ' classes').
+	] ifFalse:[
+	    className := classes first theNonMetaclass name.
+	    dict at:#numClassesOrEmpty put:' '.
+	    dict at:#inSingleClassOrEmpty put:' in ' , className.
+	    dict at:#forSingleClassOrEmpty put:' for ' , className.
+	    dict at:#sForPlural put:''.
+	    dict at:#singleClassNameOrNumberOfClasses put:className.
+	].
+
+	UserInformation handle:[:ex |
+	    self showInfo:(ex messageText).
+	] do:[
+	    generator executeCollectedChangesNamed:(nameOfOperation expandPlaceholdersWith:dict)
+	]
     ]
 
     "Modified: / 21-01-2012 / 11:11:24 / cg"
@@ -29171,9 +29573,9 @@
     "helper for code generators"
 
     self
-        generateUndoableChange:nameOfOperation
-        overClasses:(self selectedClassesValue)
-        via:aBlock
+	generateUndoableChange:nameOfOperation
+	overClasses:(self selectedClassesValue)
+	via:aBlock
 
     "Created: / 21-01-2012 / 10:22:19 / cg"
 !
@@ -29182,9 +29584,9 @@
     "helper for code generators"
 
     self
-        generateUndoableChange:nameOfOperation
-        overClasses:(self selectedClassesValue)
-        via:aBlock
+	generateUndoableChange:nameOfOperation
+	overClasses:(self selectedClassesValue)
+	via:aBlock
 
     "Modified: / 28-02-2012 / 16:49:22 / cg"
 !
@@ -29198,8 +29600,8 @@
 
     languageOfFirstMethod := selMethods first mclass programmingLanguage.
     (selMethods conform:[:mthd | (mthd mclass programmingLanguage) = languageOfFirstMethod]) ifFalse:[
-        Dialog warn:'All methods must be defined in the same programming language'.
-        ^ self
+	Dialog warn:'All methods must be defined in the same programming language'.
+	^ self
     ].
 
     generator := languageOfFirstMethod codeGeneratorClass new.
@@ -29207,27 +29609,27 @@
 
     count := 0.
     self selectedMethodsDo:[:eachClass |
-        aBlock value:generator value:eachClass.
-        count := count + 1.
+	aBlock value:generator value:eachClass.
+	count := count + 1.
     ].
 
     dict := Dictionary new.
     dict at:1 put:count.
     dict at:#numMethods put:count.
     count ~~ 1 ifTrue:[
-        dict at:#numMethodsOrEmpty put:( ' ' , count printString allBold, ' ').
-        dict at:#inSingleMethodOrEmpty put:''.
-        dict at:#forSingleMethodOrEmpty put:''.
-        dict at:#sForPlural put:'s'.
-        dict at:#singleMethodNameOrNumberOfMethods put:(count printString allBold , ' methods').
-    ] ifFalse:[
-        method := self selectedMethodsValue first.
-        methodName := method mclass nameWithoutPrefix , '>>' , method selector allBold.
-        dict at:#numMethodsOrEmpty put:' '.
-        dict at:#inSingleMethodOrEmpty put:' in ' , methodName.
-        dict at:#forSingleMethodOrEmpty put:' for ' , methodName.
-        dict at:#sForPlural put:''.
-        dict at:#singleMethodNameOrNumberOfMethods put:methodName.
+	dict at:#numMethodsOrEmpty put:( ' ' , count printString allBold, ' ').
+	dict at:#inSingleMethodOrEmpty put:''.
+	dict at:#forSingleMethodOrEmpty put:''.
+	dict at:#sForPlural put:'s'.
+	dict at:#singleMethodNameOrNumberOfMethods put:(count printString allBold , ' methods').
+    ] ifFalse:[
+	method := self selectedMethodsValue first.
+	methodName := method mclass nameWithoutPrefix , '>>' , method selector allBold.
+	dict at:#numMethodsOrEmpty put:' '.
+	dict at:#inSingleMethodOrEmpty put:' in ' , methodName.
+	dict at:#forSingleMethodOrEmpty put:' for ' , methodName.
+	dict at:#sForPlural put:''.
+	dict at:#singleMethodNameOrNumberOfMethods put:methodName.
     ].
 
     generator executeCollectedChangesNamed:(nameOfOperation expandPlaceholdersWith:dict)
@@ -29236,6 +29638,14 @@
     "Modified: / 28-02-2012 / 16:16:27 / cg"
 !
 
+initializeSelectedPool
+    self selectedClassesValue do:[:cls |
+	cls theNonMetaclass initialize
+    ]
+
+    "Created: / 28-05-2012 / 09:49:28 / cg"
+!
+
 launchSelectedApplication
     self startApplication:(self theSingleSelectedClass).
 !
@@ -29244,25 +29654,25 @@
     "change the class-category of the given classes"
 
     classes do:[:aClass |
-        "/ must be loaded ...
-        aClass theNonMetaclass autoload
+	"/ must be loaded ...
+	aClass theNonMetaclass autoload
     ].
     classes do:[:eachClass |
-        |cls|
-
-        cls := eachClass theNonMetaclass.
-        cls isPrivate ifFalse:[
-            Smalltalk changeCategoryOf:cls to:newCategory.
-        ]
+	|cls|
+
+	cls := eachClass theNonMetaclass.
+	cls isPrivate ifFalse:[
+	    Smalltalk changeCategoryOf:cls to:newCategory.
+	]
     ].
 
     LastCategoryRenames isNil ifTrue:[
-        LastCategoryRenames := OrderedCollection new.
+	LastCategoryRenames := OrderedCollection new.
     ].
     LastCategoryRenames remove:newCategory ifAbsent:nil.
     LastCategoryRenames addFirst:newCategory.
     LastCategoryRenames size > 10 ifTrue:[
-        LastCategoryRenames removeLast.
+	LastCategoryRenames removeLast.
     ].
 !
 
@@ -29275,36 +29685,36 @@
     anyClassMoved := false.
     anyMethodMoved := false.
     classes do:[:eachClass |
-        |oldProject theClass|
-
-        theClass := eachClass theNonMetaclass.
-        (oldProject := theClass package) ~= newProject ifTrue:[
-            theClass package:newProject.
-            self doMoveMethodsOfClass:theClass fromProject:oldProject toProject:newProject.
-            theClass allPrivateClassesDo:[:eachPrivateClass |
-                self doMoveMethodsOfClass:eachPrivateClass fromProject:oldProject toProject:newProject.
-            ].
-            anyClassMoved := true.
-        ].
-        theClass hasExtensions ifTrue:[
-            (self confirm:(resources string:'%1 has extensions in other packages - move those methods as well ?' with:theClass name))
-            ifTrue:[
-                theClass instAndClassSelectorsAndMethodsDo:[:sel :eachMethod |
-                    eachMethod package ~= newProject ifTrue:[
-                        eachMethod package:newProject.
-                        anyMethodMoved := true.
-                    ]
-                ].
-                anyMethodMoved ifTrue:[
-                    theClass changed:#projectOrganization.
-                    theClass theMetaclass changed:#projectOrganization.
-                    Smalltalk changed:#projectOrganization with:(Array with:theClass with:oldProject).
-                ].
-            ].
-        ].
+	|oldProject theClass|
+
+	theClass := eachClass theNonMetaclass.
+	(oldProject := theClass package) ~= newProject ifTrue:[
+	    theClass package:newProject.
+	    self doMoveMethodsOfClass:theClass fromProject:oldProject toProject:newProject.
+	    theClass allPrivateClassesDo:[:eachPrivateClass |
+		self doMoveMethodsOfClass:eachPrivateClass fromProject:oldProject toProject:newProject.
+	    ].
+	    anyClassMoved := true.
+	].
+	theClass hasExtensions ifTrue:[
+	    (self confirm:(resources string:'%1 has extensions in other packages - move those methods as well ?' with:theClass name))
+	    ifTrue:[
+		theClass instAndClassSelectorsAndMethodsDo:[:sel :eachMethod |
+		    eachMethod package ~= newProject ifTrue:[
+			eachMethod package:newProject.
+			anyMethodMoved := true.
+		    ]
+		].
+		anyMethodMoved ifTrue:[
+		    theClass changed:#projectOrganization.
+		    theClass theMetaclass changed:#projectOrganization.
+		    Smalltalk changed:#projectOrganization with:(Array with:theClass with:oldProject).
+		].
+	    ].
+	].
     ].
     anyClassMoved ifTrue:[
-        Smalltalk changed:#projectOrganization.
+	Smalltalk changed:#projectOrganization.
     ].
     self rememberLastProjectMoveTo:newProject
 
@@ -29332,21 +29742,21 @@
     "show a classes documentation (i.e. open doc-View on it)"
 
     Autoload autoloadFailedSignal handle:[:ex |
-        self warn:'autoload failed.
+	self warn:'autoload failed.
 
 Check your source directory and/or
 the abbreviation file for the classes (correct) shortened name.'.
-        ex return.
+	ex return.
     ] do:[
-        |text v|
-
-        text := HTMLDocGenerator htmlDocOf:aClass.
-        text notNil ifTrue:[
-            v := HTMLDocumentView
-                    openFullOnText:text
-                    inDirectory:(Smalltalk getSystemFileName:'doc/online/english/classDoc').
-            v nameSpaceForExecution:(aClass nameSpace).
-        ]
+	|text v|
+
+	text := HTMLDocGenerator htmlDocOf:aClass.
+	text notNil ifTrue:[
+	    v := HTMLDocumentView
+		    openFullOnText:text
+		    inDirectory:(Smalltalk getSystemFileName:'doc/online/english/classDoc').
+	    v nameSpaceForExecution:(aClass nameSpace).
+	]
     ]
 !
 
@@ -29360,8 +29770,17 @@
 
 printOutClassesWithSelector:aSelector
     self selectedClassesWithWaitCursorDo:[:eachClass |
-        self printOutClass:eachClass withSelector:aSelector
-    ]
+	self printOutClass:eachClass withSelector:aSelector
+    ]
+!
+
+recompileClass:aClass
+    "recompile a class (to turn off instrumentation, for example)"
+
+    aClass theNonMetaclass recompile.
+    aClass theMetaclass recompile.
+
+    "Created: / 31-05-2012 / 12:01:28 / cg"
 !
 
 recompileClassWithInstrumentation:aClass
@@ -29374,45 +29793,51 @@
 "/    aClass theNonMetaclass recompileUsingCompilerClass:InstrumentingCompiler.
 "/    aClass theMetaclass recompileUsingCompilerClass:InstrumentingCompiler.
 
-    compile := 
-        [:cls :sel :mthd |
-            ((mthd sends:#subclassResponsibility)
-            or:[ (mthd sends:#subclassResponsibility:) ]) ifFalse:[
-                mthd hasPrimitiveCode ifFalse:[
-                    cls recompile:sel usingCompiler:InstrumentingCompiler new
-                ]
-            ]
-        ].
+    compile :=
+	[:cls :sel :mthd |
+	    ((mthd sends:#subclassResponsibility)
+	    or:[ (mthd sends:#subclassResponsibility:) ]) ifFalse:[
+		mthd hasPrimitiveCode ifFalse:[
+		    cls recompile:sel usingCompiler:InstrumentingCompiler new
+		]
+	    ]
+	].
 
     (cls := aClass theNonMetaclass)
-        selectorsAndMethodsDo:[:aSelector :aMethod |
-            compile value:cls value:aSelector value:aMethod.
-        ].
-
-    (cls := aClass theMetaclass) 
-        selectorsAndMethodsDo:[:aSelector :aMethod |
-            aMethod category ~= 'documentation' ifTrue:[
-                compile value:cls value:aSelector value:aMethod.
-            ]
-        ].
+	selectorsAndMethodsDo:[:aSelector :aMethod |
+	    compile value:cls value:aSelector value:aMethod.
+	].
+
+    (cls := aClass theMetaclass)
+	selectorsAndMethodsDo:[:aSelector :aMethod |
+	    aMethod category ~= 'documentation' ifTrue:[
+		compile value:cls value:aSelector value:aMethod.
+	    ]
+	].
 
     self showCoverageInformation value ifFalse:[
-        (Dialog confirm:'Turn on coverage display now ?') ifTrue:[
-            self showCoverageInformation value:true
-        ].
+	true "(Dialog confirm:(resources string:'Turn on coverage display now ?'))" ifTrue:[
+	    self showCoverageInformation value:true
+	].
+    ].
+    self globalCoverageRecordingIsEnabled value ifFalse:[
+	(Dialog confirm:(resources stringWithCRs:'Coverage recording can be done either during a single test-run, or globally for every process.\Currently, global recording is disabled, which means that recording will only be done during a special recording test-run (in the Testrunner tool).\\Do you want to enable global coverage recording now?'))
+	ifTrue:[
+	    self debugMenuEnableGlobalCoverageRecording
+	].
     ].
 
     "Created: / 10-08-2010 / 14:36:45 / cg"
-    "Modified: / 30-09-2011 / 12:46:34 / cg"
+    "Modified: / 31-05-2012 / 10:36:42 / cg"
 !
 
 recompileMethodWithInstrumentation:aMethod
     (aMethod sends:#subclassResponsibility) ifFalse:[
-        aMethod hasPrimitiveCode ifFalse:[
-            aMethod mclass 
-                recompile:aMethod selector
-                usingCompiler:InstrumentingCompiler new
-        ]
+	aMethod hasPrimitiveCode ifFalse:[
+	    aMethod mclass
+		recompile:aMethod selector
+		usingCompiler:InstrumentingCompiler new
+	]
     ]
 
     "Created: / 10-08-2010 / 14:41:17 / cg"
@@ -29425,34 +29850,34 @@
 
     classesToRemove size == 0 ifTrue:[^ self].
     self withWaitCursorDo:[
-        self canUseRefactoringSupport ifFalse:[
-            classesToRemove do:[:each |
-                each removeFromSystem.
-            ].
-            ^ self.
-        ].
-
-        pullUpSubclasses ifTrue:[
-            classesToRemove do:[:eachClass |
-                self performRefactoring:(RemoveClassRefactoring className:eachClass name).
-            ]
-        ] ifFalse:[
-            numClasses := classesToRemove size.
-            numClasses > 1 ifTrue:[
-                numClasses == 2 ifTrue:[
-                    nm := 'Remove ', classesToRemove first theNonMetaclass name , ' and ' , classesToRemove second theNonMetaclass name
-                ] ifFalse:[
-                    nm := 'Remove ', numClasses printString , ' classes'
-                ]
-            ] ifFalse:[
-                nm := 'Remove ', classesToRemove first theNonMetaclass name
-            ].
-            change := CompositeRefactoryChange named:nm.
-            classesToRemove do:[:eachClass |
-                change removeClass:eachClass
-            ].
-            RefactoryChangeManager performChange:change
-        ]
+	self canUseRefactoringSupport ifFalse:[
+	    classesToRemove do:[:each |
+		each removeFromSystem.
+	    ].
+	    ^ self.
+	].
+
+	pullUpSubclasses ifTrue:[
+	    classesToRemove do:[:eachClass |
+		self performRefactoring:(RemoveClassRefactoring className:eachClass name).
+	    ]
+	] ifFalse:[
+	    numClasses := classesToRemove size.
+	    numClasses > 1 ifTrue:[
+		numClasses == 2 ifTrue:[
+		    nm := 'Remove ', classesToRemove first theNonMetaclass name , ' and ' , classesToRemove second theNonMetaclass name
+		] ifFalse:[
+		    nm := 'Remove ', numClasses printString , ' classes'
+		]
+	    ] ifFalse:[
+		nm := 'Remove ', classesToRemove first theNonMetaclass name
+	    ].
+	    change := CompositeRefactoryChange named:nm.
+	    classesToRemove do:[:eachClass |
+		change removeClass:eachClass
+	    ].
+	    RefactoryChangeManager performChange:change
+	]
     ]
 !
 
@@ -29460,36 +29885,36 @@
     "save a classes documentation to a file"
 
     Autoload autoloadFailedSignal handle:[:ex |
-        self warn:'autoload failed.
+	self warn:'autoload failed.
 
 Check your source directory and/or
 the abbreviation file for the classes (correct) shortened name.'.
-        ex return.
+	ex return.
     ] do:[
-        |fileBox dir saveName|
-
-        fileBox := FileSelectionBox
-                        title:(resources string:'save HTML doc of ''%1'' as:' with:aClass name)
-                        okText:(resources string:'save')
-                        abortText:(resources string:'cancel')
-                        action:[:fileName | saveName := fileName].
-        fileBox initialText:((Smalltalk fileNameForClass:aClass) , '.html').
-        dir := FileSelectionBox lastFileSelectionDirectory.
-        dir notNil ifTrue:[
-            fileBox directory:dir.
-        ].
-        fileBox showAtPointer.
-        fileBox destroy.
-        saveName isNil ifTrue:[
-            ^ self
-        ].
-        saveName isEmpty ifTrue:[
-            self warn:'bad name given'.
-            ^ self
-        ].
-        FileSelectionBox lastFileSelectionDirectory:(saveName asFilename directoryName).
-
-        self saveClassDocumentationFor:aClass as:saveName
+	|fileBox dir saveName|
+
+	fileBox := FileSelectionBox
+			title:(resources string:'save HTML doc of ''%1'' as:' with:aClass name)
+			okText:(resources string:'save')
+			abortText:(resources string:'cancel')
+			action:[:fileName | saveName := fileName].
+	fileBox initialText:((Smalltalk fileNameForClass:aClass) , '.html').
+	dir := FileSelectionBox lastFileSelectionDirectory.
+	dir notNil ifTrue:[
+	    fileBox directory:dir.
+	].
+	fileBox showAtPointer.
+	fileBox destroy.
+	saveName isNil ifTrue:[
+	    ^ self
+	].
+	saveName isEmpty ifTrue:[
+	    self warn:'bad name given'.
+	    ^ self
+	].
+	FileSelectionBox lastFileSelectionDirectory:(saveName asFilename directoryName).
+
+	self saveClassDocumentationFor:aClass as:saveName
     ]
 !
 
@@ -29500,9 +29925,9 @@
 
     text := HTMLDocGenerator htmlDocOf:aClass.
     text notNil ifTrue:[
-        f := aFileName asFilename writeStream.
-        f nextPutAll:text asString.
-        f close.
+	f := aFileName asFilename writeStream.
+	f nextPutAll:text asString.
+	f close.
     ]
 !
 
@@ -29514,32 +29939,32 @@
 
 spawnClassBrowserFor:classes in:where
     "browse selected class(es);
-        where is: #newBrowser - open a new browser showing the classes
-        where is: #newBuffer  - add a new buffer showing the classes"
+	where is: #newBrowser - open a new browser showing the classes
+	where is: #newBuffer  - add a new buffer showing the classes"
 
     ^ self spawnClassBrowserFor:classes label:nil in:where
 !
 
 spawnClassBrowserFor:classes in:where select:doSelect
     "browse selected class(es);
-        where is: #newBrowser - open a new browser showing the classes
-        where is: #newBuffer  - add a new buffer showing the classes"
+	where is: #newBrowser - open a new browser showing the classes
+	where is: #newBuffer  - add a new buffer showing the classes"
 
     ^ self spawnClassBrowserFor:classes label:nil in:where select:doSelect
 !
 
 spawnClassBrowserFor:classes label:titleOrNil in:where
     "browse selected class(es);
-        where is: #newBrowser - open a new browser showing the classes
-        where is: #newBuffer  - add a new buffer showing the classes"
+	where is: #newBrowser - open a new browser showing the classes
+	where is: #newBuffer  - add a new buffer showing the classes"
 
     |allClasses|
 
     allClasses := OrderedCollection new.
     classes do:[:eachClass |
-        eachClass theNonMetaclass withAllPrivateClassesDo:[:everyClass |
-            allClasses add:everyClass
-        ].
+	eachClass theNonMetaclass withAllPrivateClassesDo:[:everyClass |
+	    allClasses add:everyClass
+	].
     ].
     ^ self spawnClassBrowserFor:allClasses label:titleOrNil in:where select:true
 
@@ -29548,171 +29973,171 @@
 
 spawnClassBrowserFor:classes label:labelOrNil in:where select:doSelectIn
     "browse selected class(es);
-        where is: #newBrowser - open a new browser showing the classes
-        where is: #newBuffer  - add a new buffer showing the classes"
+	where is: #newBrowser - open a new browser showing the classes
+	where is: #newBuffer  - add a new buffer showing the classes"
 
     |spec meta allClasses selectedClasses selectedProtocols selectedMethods
      singleSelection singleClass doSelect|
 
     doSelect := doSelectIn.
     false "(singleSelection := (classes size == 1))" ifTrue:[
-        spec := #singleClassBrowserSpec.
-        singleClass := classes first.
-        meta := singleClass isMeta.
-        doSelect := true.
-    ] ifFalse:[
-        spec := #fullBrowserSpec. "/#multipleClassBrowserSpec.
-        meta := self meta value ? false.
+	spec := #singleClassBrowserSpec.
+	singleClass := classes first.
+	meta := singleClass isMeta.
+	doSelect := true.
+    ] ifFalse:[
+	spec := #fullBrowserSpec. "/#multipleClassBrowserSpec.
+	meta := self meta value ? false.
     ].
 
     allClasses := classes collect:[:cls | cls theNonMetaclass].
     doSelect ifTrue:[
-        selectedClasses := classes copy.
-        navigationState notNil ifTrue:[
-            selectedProtocols := self selectedProtocols value copy.
-            selectedMethods := self selectedMethodsValue copy.
-            (selectedMethods size > 0
-            and:[ selectedProtocols size == 0 ]) ifTrue:[
-                selectedProtocols := (selectedMethods collect:[:each | each category]) asSet asOrderedCollection
-            ].
-        ]
-    ].
-
-    ^ self
-        newBrowserOrBufferDependingOn:where
-        label:labelOrNil
-        forSpec:spec
-        setupWith:[:brwsr |
-            brwsr immediateUpdate value:true.
-            brwsr classListGenerator value:allClasses.
-            brwsr meta value:meta.
-            doSelect ifTrue:[
-                brwsr selectClasses:selectedClasses.
-                selectedProtocols size > 0 ifTrue:[
-                    brwsr selectProtocols:selectedProtocols.
-                ].
-                brwsr selectMethods:selectedMethods.
-            ].
-            brwsr immediateUpdate value:false.
-
-            "/ kludge - enforce generator update when meta changes
-            brwsr meta onChangeEvaluate:[ brwsr classListGenerator changed ].
-        ]
+	selectedClasses := classes copy.
+	navigationState notNil ifTrue:[
+	    selectedProtocols := self selectedProtocols value copy.
+	    selectedMethods := self selectedMethodsValue copy.
+	    (selectedMethods size > 0
+	    and:[ selectedProtocols size == 0 ]) ifTrue:[
+		selectedProtocols := (selectedMethods collect:[:each | each category]) asSet asOrderedCollection
+	    ].
+	]
+    ].
+
+    ^ self
+	newBrowserOrBufferDependingOn:where
+	label:labelOrNil
+	forSpec:spec
+	setupWith:[:brwsr |
+	    brwsr immediateUpdate value:true.
+	    brwsr classListGenerator value:allClasses.
+	    brwsr meta value:meta.
+	    doSelect ifTrue:[
+		brwsr selectClasses:selectedClasses.
+		selectedProtocols size > 0 ifTrue:[
+		    brwsr selectProtocols:selectedProtocols.
+		].
+		brwsr selectMethods:selectedMethods.
+	    ].
+	    brwsr immediateUpdate value:false.
+
+	    "/ kludge - enforce generator update when meta changes
+	    brwsr meta onChangeEvaluate:[ brwsr classListGenerator changed ].
+	]
 
     "Modified: / 28-02-2012 / 16:30:36 / cg"
 !
 
 spawnClassBrowserForSearch:searchBlock sortBy:sortByWhat in:openHow label:lbl
     "browse some class(es);
-        openHow is: #newBrowser - open a new browser showing the method(s)
-        openHow is: #newBuffer  - add a new buffer showing the method(s)
-
-        and sortByWhat is:
-            nil
-        or  #class
-    "
-
-    ^ self
-        spawnClassBrowserForSearch:searchBlock
-        spec:#multipleClassBrowserSpec
-        sortBy:sortByWhat in:openHow label:lbl
+	openHow is: #newBrowser - open a new browser showing the method(s)
+	openHow is: #newBuffer  - add a new buffer showing the method(s)
+
+	and sortByWhat is:
+	    nil
+	or  #class
+    "
+
+    ^ self
+	spawnClassBrowserForSearch:searchBlock
+	spec:#multipleClassBrowserSpec
+	sortBy:sortByWhat in:openHow label:lbl
 
     "Modified: / 2.11.2001 / 09:57:35 / cg"
 !
 
 spawnClassBrowserForSearch:searchBlock spec:spec sortBy:sortByWhat in:openHow label:lbl
     "browse some class(es);
-        openHow is: #newBrowser - open a new browser showing the method(s)
-        openHow is: #newBuffer  - add a new buffer showing the method(s)
-
-        and sortByWhat is:
-            nil
-        or  #class
-    "
-
-    ^ self
-        spawnClassBrowserForSearch:searchBlock
-        spec:spec
-        sortBy:sortByWhat in:openHow label:lbl
-        autoSelectIfOne:true
+	openHow is: #newBrowser - open a new browser showing the method(s)
+	openHow is: #newBuffer  - add a new buffer showing the method(s)
+
+	and sortByWhat is:
+	    nil
+	or  #class
+    "
+
+    ^ self
+	spawnClassBrowserForSearch:searchBlock
+	spec:spec
+	sortBy:sortByWhat in:openHow label:lbl
+	autoSelectIfOne:true
 
     "Modified: / 2.11.2001 / 09:58:01 / cg"
 !
 
 spawnClassBrowserForSearch:searchBlock spec:spec sortBy:sortByWhat in:openHow label:lbl autoSelectIfOne:doAutoSelectIfOne
     "browse some class(es);
-        openHow is: #newBrowser - open a new browser showing the method(s)
-        openHow is: #newBuffer  - add a new buffer showing the method(s)
-
-        and sortByWhat is:
-            nil
-        or  #class
-    "
-
-    ^ self
-        spawnClassBrowserForSearch:searchBlock
-        spec:spec
-        sortBy:sortByWhat in:openHow label:lbl
-        autoSelectIfOne:doAutoSelectIfOne callBack:nil
+	openHow is: #newBrowser - open a new browser showing the method(s)
+	openHow is: #newBuffer  - add a new buffer showing the method(s)
+
+	and sortByWhat is:
+	    nil
+	or  #class
+    "
+
+    ^ self
+	spawnClassBrowserForSearch:searchBlock
+	spec:spec
+	sortBy:sortByWhat in:openHow label:lbl
+	autoSelectIfOne:doAutoSelectIfOne callBack:nil
 
     "Modified: / 5.11.2001 / 09:36:13 / cg"
 !
 
 spawnClassBrowserForSearch:searchBlock spec:spec sortBy:sortByWhat in:openHow label:lbl autoSelectIfOne:doAutoSelectIfOne callBack:callBack
     "browse some class(es);
-        openHow is: #newBrowser - open a new browser showing the method(s)
-        openHow is: #newBuffer  - add a new buffer showing the method(s)
-
-        and sortByWhat is:
-            nil
-        or  #class
+	openHow is: #newBrowser - open a new browser showing the method(s)
+	openHow is: #newBuffer  - add a new buffer showing the method(s)
+
+	and sortByWhat is:
+	    nil
+	or  #class
     "
 
     |initialList|
 
     initialList := searchBlock value.
     initialList size == 0 ifTrue:[
-        self warn:(lbl , ' - none found.').
-        ^ nil
-    ].
-
-    ^ self
-        newBrowserOrBufferDependingOn:openHow
-        label:lbl
-        forSpec:spec
-        setupWith:[:brwsr |
-            |generator theClassList|
-
-            generator := Iterator on:[:whatToDo |
-                                            initialList size > 0 ifTrue:[
-                                                theClassList := initialList.
-                                                initialList := nil
-                                            ] ifFalse:[
-                                                theClassList isNil ifTrue:[
-                                                    theClassList := searchBlock value.
-                                                ].
-                                            ].
-                                            theClassList do:[:aClass |
-                                                whatToDo value:aClass
-                                            ].
-                                            theClassList := nil.
-                                      ].
-
-            sortByWhat notNil ifTrue:[brwsr sortBy value:sortByWhat].
-            brwsr classListGenerator value:generator.
-            "/ auto-select the first class, if there is only one
-
-            callBack notNil ifTrue:[callBack value:brwsr].
-            initialList isNil ifTrue:[
-                "/ newBuffer will evaluate the generator later;
-                "/ newBrowser might have it already evaluated ... (sigh)
-                initialList := theClassList := searchBlock value
-            ].
-            (doAutoSelectIfOne and:[initialList size == 1]) ifTrue:[
-                brwsr selectClasses:initialList.
-                brwsr classSelectionChanged.
-            ].
-        ]
+	self warn:(lbl , ' - none found.').
+	^ nil
+    ].
+
+    ^ self
+	newBrowserOrBufferDependingOn:openHow
+	label:lbl
+	forSpec:spec
+	setupWith:[:brwsr |
+	    |generator theClassList|
+
+	    generator := Iterator on:[:whatToDo |
+					    initialList size > 0 ifTrue:[
+						theClassList := initialList.
+						initialList := nil
+					    ] ifFalse:[
+						theClassList isNil ifTrue:[
+						    theClassList := searchBlock value.
+						].
+					    ].
+					    theClassList do:[:aClass |
+						whatToDo value:aClass
+					    ].
+					    theClassList := nil.
+				      ].
+
+	    sortByWhat notNil ifTrue:[brwsr sortBy value:sortByWhat].
+	    brwsr classListGenerator value:generator.
+	    "/ auto-select the first class, if there is only one
+
+	    callBack notNil ifTrue:[callBack value:brwsr].
+	    initialList isNil ifTrue:[
+		"/ newBuffer will evaluate the generator later;
+		"/ newBrowser might have it already evaluated ... (sigh)
+		initialList := theClassList := searchBlock value
+	    ].
+	    (doAutoSelectIfOne and:[initialList size == 1]) ifTrue:[
+		brwsr selectClasses:initialList.
+		brwsr classSelectionChanged.
+	    ].
+	]
 
     "Modified: / 3.11.2001 / 14:11:05 / cg"
     "Created: / 5.11.2001 / 09:35:52 / cg"
@@ -29724,58 +30149,58 @@
     |lbl searchBlock cachedList brwsr singleClassName|
 
     aCollectionOfClasses size == 1 ifTrue:[
-        singleClassName := aCollectionOfClasses first theNonMetaclass name.
-        lbl := 'References to ' , singleClassName , ' and its subclasses'
-    ] ifFalse:[
-        lbl := 'References to classes and their subclasses'
+	singleClassName := aCollectionOfClasses first theNonMetaclass name.
+	lbl := 'References to ' , singleClassName , ' and its subclasses'
+    ] ifFalse:[
+	lbl := 'References to classes and their subclasses'
     ].
 
     searchBlock := [
-        |allRefs|
-
-        cachedList notNil ifTrue:[
-            allRefs := cachedList.
-            cachedList := nil.
-        ] ifFalse:[
-            allRefs := IdentitySet new.
-            aCollectionOfClasses do:[:eachClassInQuestion |
-                |syms refsHere|
-
-                syms := eachClassInQuestion theNonMetaclass withAllSubclasses collect:[:cls | cls name].
-                refsHere := self class
-                        findMethodsIn:(Smalltalk allClasses)
-                        where:[:cls :mthd :sel |   |mSource|
-                                    "/ kludge: Lazy methods do not include symbols in the literal array - sigh
-                                    mthd isLazyMethod ifTrue:[
-                                        mSource := mthd source.
-                                        (mSource notNil
-                                        and:[(syms contains:[:sym | (mSource includesString:sym)])
-                                        and:[|usedGlobals|
-                                             usedGlobals := mthd usedGlobals.
-                                             syms contains:[:sym | usedGlobals includes:sym]]])
-                                    ] ifFalse:[
-                                        ((syms contains:[:sym | mthd referencesLiteral:sym])
-                                         and:[|usedGlobals|
-                                             usedGlobals := mthd usedGlobals.
-                                             syms contains:[:sym | usedGlobals includes:sym]])
-                                    ]
-                              ].
-                allRefs addAll:refsHere.
-            ].
-        ].
-        allRefs
+	|allRefs|
+
+	cachedList notNil ifTrue:[
+	    allRefs := cachedList.
+	    cachedList := nil.
+	] ifFalse:[
+	    allRefs := IdentitySet new.
+	    aCollectionOfClasses do:[:eachClassInQuestion |
+		|syms refsHere|
+
+		syms := eachClassInQuestion theNonMetaclass withAllSubclasses collect:[:cls | cls name].
+		refsHere := self class
+			findMethodsIn:(Smalltalk allClasses)
+			where:[:cls :mthd :sel |   |mSource|
+				    "/ kludge: Lazy methods do not include symbols in the literal array - sigh
+				    mthd isLazyMethod ifTrue:[
+					mSource := mthd source.
+					(mSource notNil
+					and:[(syms contains:[:sym | (mSource includesString:sym)])
+					and:[|usedGlobals|
+					     usedGlobals := mthd usedGlobals.
+					     syms contains:[:sym | usedGlobals includes:sym]]])
+				    ] ifFalse:[
+					((syms contains:[:sym | mthd referencesLiteral:sym])
+					 and:[|usedGlobals|
+					     usedGlobals := mthd usedGlobals.
+					     syms contains:[:sym | usedGlobals includes:sym]])
+				    ]
+			      ].
+		allRefs addAll:refsHere.
+	    ].
+	].
+	allRefs
     ].
 
     (cachedList := searchBlock value) isEmpty ifTrue:[
-        self information:(lbl , ' - none found').
-        ^ self
+	self information:(lbl , ' - none found').
+	^ self
     ].
 
     brwsr := self spawnMethodBrowserForSearch:searchBlock sortBy:#class in:openHow label:lbl.
     brwsr notNil ifTrue:[
-        singleClassName notNil ifTrue:[
-            brwsr autoSearchPattern:singleClassName ignoreCase:false.
-        ]
+	singleClassName notNil ifTrue:[
+	    brwsr autoSearchPattern:singleClassName ignoreCase:false.
+	]
     ].
 !
 
@@ -29786,8 +30211,8 @@
 
     projects := Set new.
     aCollectionOfClasses do:[:eachClass |
-        projects add:eachClass package.
-        eachClass instAndClassSelectorsAndMethodsDo:[:sel :mthd | projects add:(mthd package)].
+	projects add:eachClass package.
+	eachClass instAndClassSelectorsAndMethodsDo:[:sel :mthd | projects add:(mthd package)].
     ].
     self spawnProjectBrowserFor:projects in:openHow
 
@@ -29800,99 +30225,99 @@
     |lbl searchBlock cachedList brwsr singleClassName|
 
     aCollectionOfClasses size == 1 ifTrue:[
-        singleClassName := aCollectionOfClasses first theNonMetaclass name.
-        lbl := 'References to ' , singleClassName
-    ] ifFalse:[
-        lbl := 'References to classes'
+	singleClassName := aCollectionOfClasses first theNonMetaclass name.
+	lbl := 'References to ' , singleClassName
+    ] ifFalse:[
+	lbl := 'References to classes'
     ].
 
     searchBlock := [
-        |allRefs|
-
-        cachedList notNil ifTrue:[
-            allRefs := cachedList.
-            cachedList := nil.
-        ] ifFalse:[
-            allRefs := IdentitySet new.
-            aCollectionOfClasses do:[:eachClassInQuestion |
-                |findRefs sym sym2 classesNameSpace symInsideNamespace symInsideOwner refsHere|
-
-                sym := eachClassInQuestion theNonMetaclass name.
-                sym2 := eachClassInQuestion theNonMetaclass nameWithoutPrefix asSymbol.
-
-                classesNameSpace := eachClassInQuestion theNonMetaclass nameSpace.
-
-                findRefs := 
-                    [:setOfClasses | 
-                        self class
-                            findMethodsIn:setOfClasses
-                            where:[:cls :mthdIn :sel |   
-                                |mthd mSource isCandidate isReference usedGlobals|
-
-                                mthd := mthdIn.
-                                mthd isWrapped ifTrue:[ mthd := mthd originalMethod ].
-
-                                "/ kludge: Lazy methods do not include symbols in the literal array - sigh
-                                mthd isLazyMethod ifTrue:[
-                                    mSource := mthd source.
-                                    isCandidate := mSource notNil 
-                                                        and:[ (mSource includesString:sym) or: [mSource includesString:sym2]].
-                                ] ifFalse:[
-                                    isCandidate := (mthd referencesLiteral:sym) or:[mthd referencesLiteral:sym2]
-                                ].
-                                isReference := false.
-                                isCandidate ifTrue:[
-                                    usedGlobals := mthd usedGlobals.
-                                    isReference := (usedGlobals includes:sym).
-                                    isReference ifFalse:[
-                                        (mthd referencesLiteral:classesNameSpace name) ifTrue:[
-                                            isReference := mthd sendsAny:#(#'at:' #'at:ifAbsent:' #'classNamed:')
-                                        ].
-                                        isReference ifFalse:[
-                                            classesNameSpace ~= Smalltalk ifTrue:[
-                                                (mthd referencesLiteral:#Smalltalk) ifTrue:[
-                                                    isReference := mthd sendsAny:#(#'at:' #'at:ifAbsent:' #'classNamed:')
-                                                ].
-                                            ]
-                                        ]
-                                    ]
-                                ].
-                                isReference
-                            ].
-                    ].
-
-                refsHere := findRefs value:(Smalltalk allClasses).
-                allRefs addAll:refsHere.
-
-                (eachClassInQuestion nameSpace notNil
-                and:[ eachClassInQuestion nameSpace ~~ Smalltalk ]) ifTrue:[
-                    symInsideNamespace := eachClassInQuestion theNonMetaclass nameWithoutNameSpacePrefix asSymbol.
-                    refsHere := findRefs value:(eachClassInQuestion topNameSpace allClassesWithAllPrivateClasses).
-                    allRefs addAll:refsHere.
-                ].
-                (eachClassInQuestion owningClass notNil) ifTrue:[
-                    symInsideOwner := eachClassInQuestion theNonMetaclass nameWithoutPrefix asSymbol.
-                    refsHere := findRefs value:(Array with:eachClassInQuestion owningClass).
-                    allRefs addAll:refsHere.
-                ].
-            ].
-        ].
-        allRefs
+	|allRefs|
+
+	cachedList notNil ifTrue:[
+	    allRefs := cachedList.
+	    cachedList := nil.
+	] ifFalse:[
+	    allRefs := IdentitySet new.
+	    aCollectionOfClasses do:[:eachClassInQuestion |
+		|findRefs sym sym2 classesNameSpace symInsideNamespace symInsideOwner refsHere|
+
+		sym := eachClassInQuestion theNonMetaclass name.
+		sym2 := eachClassInQuestion theNonMetaclass nameWithoutPrefix asSymbol.
+
+		classesNameSpace := eachClassInQuestion theNonMetaclass nameSpace.
+
+		findRefs :=
+		    [:setOfClasses |
+			self class
+			    findMethodsIn:setOfClasses
+			    where:[:cls :mthdIn :sel |
+				|mthd mSource isCandidate isReference usedGlobals|
+
+				mthd := mthdIn.
+				mthd isWrapped ifTrue:[ mthd := mthd originalMethod ].
+
+				"/ kludge: Lazy methods do not include symbols in the literal array - sigh
+				mthd isLazyMethod ifTrue:[
+				    mSource := mthd source.
+				    isCandidate := mSource notNil
+							and:[ (mSource includesString:sym) or: [mSource includesString:sym2]].
+				] ifFalse:[
+				    isCandidate := (mthd referencesLiteral:sym) or:[mthd referencesLiteral:sym2]
+				].
+				isReference := false.
+				isCandidate ifTrue:[
+				    usedGlobals := mthd usedGlobals.
+				    isReference := (usedGlobals includes:sym).
+				    isReference ifFalse:[
+					(mthd referencesLiteral:classesNameSpace name) ifTrue:[
+					    isReference := mthd sendsAny:#(#'at:' #'at:ifAbsent:' #'classNamed:')
+					].
+					isReference ifFalse:[
+					    classesNameSpace ~= Smalltalk ifTrue:[
+						(mthd referencesLiteral:#Smalltalk) ifTrue:[
+						    isReference := mthd sendsAny:#(#'at:' #'at:ifAbsent:' #'classNamed:')
+						].
+					    ]
+					]
+				    ]
+				].
+				isReference
+			    ].
+		    ].
+
+		refsHere := findRefs value:(Smalltalk allClasses).
+		allRefs addAll:refsHere.
+
+		(eachClassInQuestion nameSpace notNil
+		and:[ eachClassInQuestion nameSpace ~~ Smalltalk ]) ifTrue:[
+		    symInsideNamespace := eachClassInQuestion theNonMetaclass nameWithoutNameSpacePrefix asSymbol.
+		    refsHere := findRefs value:(eachClassInQuestion topNameSpace allClassesWithAllPrivateClasses).
+		    allRefs addAll:refsHere.
+		].
+		(eachClassInQuestion owningClass notNil) ifTrue:[
+		    symInsideOwner := eachClassInQuestion theNonMetaclass nameWithoutPrefix asSymbol.
+		    refsHere := findRefs value:(Array with:eachClassInQuestion owningClass).
+		    allRefs addAll:refsHere.
+		].
+	    ].
+	].
+	allRefs
     ].
 
     self withSearchCursorDo:[
-        cachedList := searchBlock value.
+	cachedList := searchBlock value.
     ].
     cachedList isEmpty ifTrue:[
-        self information:(lbl , ' - none found').
-        ^ self
+	self information:(lbl , ' - none found').
+	^ self
     ].
 
     brwsr := self spawnMethodBrowserForSearch:searchBlock sortBy:#class in:openHow label:lbl.
     brwsr notNil ifTrue:[
-        singleClassName notNil ifTrue:[
-            brwsr autoSearchPattern:singleClassName ignoreCase:false.
-        ]
+	singleClassName notNil ifTrue:[
+	    brwsr autoSearchPattern:singleClassName ignoreCase:false.
+	]
     ].
 
     "Modified (format): / 25-11-2011 / 14:02:17 / cg"
@@ -29901,8 +30326,8 @@
 
 spawnMultipleClassBrowserFor:classes sortBy:sortHow in:where
     "browse selected class(es);
-        where is: #newBrowser - open a new browser showing the classes
-        where is: #newBuffer  - add a new buffer showing the classes"
+	where is: #newBrowser - open a new browser showing the classes
+	where is: #newBuffer  - add a new buffer showing the classes"
 
     |allClasses
      "/ selectedClasses selectedProtocols selectedMethods
@@ -29914,31 +30339,31 @@
 "/    selectedMethods := self selectedMethods value copy.
 
     ^ self
-        newBrowserOrBufferDependingOn:where
-        label:nil
-        forSpec:#multipleClassBrowserSpec
-        setupWith:[:brwsr |
-            brwsr sortBy value:sortHow.
-            brwsr immediateUpdate value:true.
-            brwsr classListGenerator value:allClasses.
-
-            brwsr meta value:(self meta value).
+	newBrowserOrBufferDependingOn:where
+	label:nil
+	forSpec:#multipleClassBrowserSpec
+	setupWith:[:brwsr |
+	    brwsr sortBy value:sortHow.
+	    brwsr immediateUpdate value:true.
+	    brwsr classListGenerator value:allClasses.
+
+	    brwsr meta value:(self meta value).
 "/            brwsr selectClasses:selectedClasses.
 "/            brwsr selectProtocols:selectedProtocols.
 "/            brwsr selectMethods:selectedMethods.
 
-            "/ kludge - enforce generator update when meta changes
-            brwsr immediateUpdate value:false.
-            brwsr meta onChangeEvaluate:[ brwsr classListGenerator changed ].
-        ]
+	    "/ kludge - enforce generator update when meta changes
+	    brwsr immediateUpdate value:false.
+	    brwsr meta onChangeEvaluate:[ brwsr classListGenerator changed ].
+	]
 
     "Modified: / 1.3.2000 / 11:54:08 / cg"
 !
 
 spawnSingleClassBrowserFor:classes in:where
     "browse selected class(es) in a single class (classlist) browser
-        where is: #newBrowser - open a new browser showing the classes
-        where is: #newBuffer  - add a new buffer showing the classes"
+	where is: #newBrowser - open a new browser showing the classes
+	where is: #newBuffer  - add a new buffer showing the classes"
 
     ^ self spawnSingleClassBrowserFor:classes label:nil in:where
 
@@ -29948,8 +30373,8 @@
 
 spawnSingleClassBrowserFor:class label:titleOrNil in:where
     "browse selected class(es) in a single class (classlist) browser
-        where is: #newBrowser - open a new browser showing the classes
-        where is: #newBuffer  - add a new buffer showing the classes"
+	where is: #newBrowser - open a new browser showing the classes
+	where is: #newBuffer  - add a new buffer showing the classes"
 
     ^ self spawnSingleClassBrowserFor:class label:titleOrNil in:where select:true
 
@@ -29959,8 +30384,8 @@
 
 spawnSingleClassBrowserFor:class label:labelOrNil in:where select:doSelectIn
     "browse selected class(es);
-        where is: #newBrowser - open a new browser showing the class
-        where is: #newBuffer  - add a new buffer showing the class"
+	where is: #newBrowser - open a new browser showing the class
+	where is: #newBuffer  - add a new buffer showing the class"
 
     |spec meta allClasses selectedClasses selectedProtocols selectedMethods singleClass doSelect|
 
@@ -29974,37 +30399,37 @@
 
     allClasses := Array with: singleClass theNonMetaclass.
     doSelect ifTrue:[
-        selectedClasses := Array with: singleClass.
-        navigationState notNil ifTrue:[
-            selectedProtocols := self selectedProtocols value copy.
-            selectedMethods := self selectedMethodsValue copy.
-            (selectedMethods size > 0
-            and:[ selectedProtocols size == 0 ]) ifTrue:[
-                selectedProtocols := (selectedMethods collect:[:each | each category]) asSet asOrderedCollection
-            ].
-        ]
-    ].
-
-    ^ self
-        newBrowserOrBufferDependingOn:where
-        label:labelOrNil
-        forSpec:spec
-        setupWith:[:brwsr |
-            brwsr immediateUpdate value:true.
-            brwsr classListGenerator value:allClasses.
-            brwsr meta value:meta.
-            doSelect ifTrue:[
-                brwsr selectClasses:selectedClasses.
-                selectedProtocols size > 0 ifTrue:[
-                    brwsr selectProtocols:selectedProtocols.
-                ].
-                brwsr selectMethods:selectedMethods.
-            ].
-            brwsr immediateUpdate value:false.
-
-            "/ kludge - enforce generator update when meta changes
-            brwsr meta onChangeEvaluate:[ brwsr classListGenerator changed ].
-        ]
+	selectedClasses := Array with: singleClass.
+	navigationState notNil ifTrue:[
+	    selectedProtocols := self selectedProtocols value copy.
+	    selectedMethods := self selectedMethodsValue copy.
+	    (selectedMethods size > 0
+	    and:[ selectedProtocols size == 0 ]) ifTrue:[
+		selectedProtocols := (selectedMethods collect:[:each | each category]) asSet asOrderedCollection
+	    ].
+	]
+    ].
+
+    ^ self
+	newBrowserOrBufferDependingOn:where
+	label:labelOrNil
+	forSpec:spec
+	setupWith:[:brwsr |
+	    brwsr immediateUpdate value:true.
+	    brwsr classListGenerator value:allClasses.
+	    brwsr meta value:meta.
+	    doSelect ifTrue:[
+		brwsr selectClasses:selectedClasses.
+		selectedProtocols size > 0 ifTrue:[
+		    brwsr selectProtocols:selectedProtocols.
+		].
+		brwsr selectMethods:selectedMethods.
+	    ].
+	    brwsr immediateUpdate value:false.
+
+	    "/ kludge - enforce generator update when meta changes
+	    brwsr meta onChangeEvaluate:[ brwsr classListGenerator changed ].
+	]
 
     "Created: / 22-07-2011 / 18:37:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 28-02-2012 / 16:36:30 / cg"
@@ -30018,17 +30443,17 @@
     all := IdentitySet new.
     allOrdered := OrderedCollection new.
     self selectedNonMetaclassesDo:[:each |
-        each withAllSubclasses do:[:eachClass |
-            (all includesIdentical:eachClass) ifFalse:[
-                all add:eachClass.
-                allOrdered add:eachClass
-            ]
-        ]
+	each withAllSubclasses do:[:eachClass |
+	    (all includesIdentical:eachClass) ifFalse:[
+		all add:eachClass.
+		allOrdered add:eachClass
+	    ]
+	]
     ].
 
     (all removeAllFoundIn:self selectedClassesValue; yourself) isEmpty ifTrue:[
-        self information:'No additional subclasses (same as selected).'.
-        ^ self
+	self information:'No additional subclasses (same as selected).'.
+	^ self
     ].
     brwsr := self spawnMultipleClassBrowserFor:allOrdered sortBy:#doNotSort in:how.
 
@@ -30043,16 +30468,16 @@
     all := IdentitySet new.
     allOrdered := OrderedCollection new.
     self selectedNonMetaclassesDo:[:each |
-        each withAllSuperclasses reverse do:[:eachClass |
-            (all includesIdentical:eachClass) ifFalse:[
-                all add:eachClass.
-                allOrdered add:eachClass
-            ]
-        ]
+	each withAllSuperclasses reverse do:[:eachClass |
+	    (all includesIdentical:eachClass) ifFalse:[
+		all add:eachClass.
+		allOrdered add:eachClass
+	    ]
+	]
     ].
     (all removeAllFoundIn:(self selectedClassesValue); yourself) isEmpty ifTrue:[
-        self information:'No additional superclasses (same as selected).'.
-        ^ self
+	self information:'No additional superclasses (same as selected).'.
+	^ self
     ].
     brwsr := self spawnMultipleClassBrowserFor:allOrdered sortBy:#doNotSort in:how.
 
@@ -30122,17 +30547,17 @@
 
     class := self theSingleSelectedClass.
     class isNil ifTrue:[
-        class := self classHierarchyTopClass value.
-        class notNil ifTrue:[
-            self meta value ifTrue:[
-                class := class theMetaclass.
-            ] ifFalse:[
-                class := class theNonMetaclass.
-            ]
-        ].
+	class := self classHierarchyTopClass value.
+	class notNil ifTrue:[
+	    self meta value ifTrue:[
+		class := class theMetaclass.
+	    ] ifFalse:[
+		class := class theNonMetaclass.
+	    ]
+	].
     ].
     class notNil ifTrue:[
-        ^ Array with:class
+	^ Array with:class
     ].
     ^ self selectedClasses
 ! !
@@ -30140,30 +30565,30 @@
 !NewSystemBrowser methodsFor:'menu actions-class packaging'!
 
 excludeClasses: toExclude fromProject:aDefinitionClass using:generator
-    "exclude (remove from classList) a number of classes." 
+    "exclude (remove from classList) a number of classes."
 
     aDefinitionClass excludeClasses:toExclude usingCompiler:generator.
 !
 
 includeClassInProject:aClass usingManager:compiler
-    "include (add to classList) a class." 
-
-    self 
-        includeClasses:(Array with: aClass) 
-        inProject:aClass projectDefinitionClass 
-        usingManager:compiler
+    "include (add to classList) a class."
+
+    self
+	includeClasses:(Array with: aClass)
+	inProject:aClass projectDefinitionClass
+	usingManager:compiler
 
     "Created: / 21-12-2011 / 20:17:48 / cg"
 !
 
 includeClasses: toInclude inProject:aDefinitionClass using:compiler
-    "include (add to classList) a number of classes." 
+    "include (add to classList) a number of classes."
 
     aDefinitionClass includeClasses:toInclude usingCompiler:compiler.
 !
 
 makeClassesAutoloaded:toMakeAutoloaded inProject:aDefinitionClass using:generator
-    "include as autoloaded (add to classList) a number of classes." 
+    "include as autoloaded (add to classList) a number of classes."
 
     aDefinitionClass makeClassesAutoloaded:toMakeAutoloaded usingCompiler:generator
 ! !
@@ -30175,8 +30600,8 @@
 
     knownTags := Set new.
     aCollectionOfClasses do:[:eachClass |
-        thisClassesTags := eachClass sourceCodeManager knownTagsFor:eachClass.
-        knownTags addAll:thisClassesTags.
+	thisClassesTags := eachClass sourceCodeManager knownTagsFor:eachClass.
+	knownTags addAll:thisClassesTags.
     ].
     ^ knownTags asSortedCollection.
 
@@ -30197,125 +30622,125 @@
     nm := aClass name.
     mgr := SourceCodeManagerUtilities default sourceCodeManagerFor:aClass.
     mgr isNil ifTrue:[
-        ^ false
+	^ false
     ].
     rev := aClass binaryRevision.
     rev2 := aClass revision.
     rev isNil ifTrue:[
-        rev := rev2
+	rev := rev2
     ].
     rev isNil ifTrue:[
-        "/
-        "/ class not in repository - allow compare against any other containers newest contents
-        "/
-        self normalLabel.
-
-        pkg := aClass package.
-        (pkg notNil and:[pkg ~= PackageId noProjectID]) ifTrue:[
-            containerModule := pkg upTo:$:.
-            containerPackage := pkg copyFrom:(containerModule size + 2).
-        ].
-        containerModule size == 0 ifTrue:[
-            containerModule := (SourceCodeManagerUtilities lastModule) ? Project current repositoryModule.
-        ].
-        containerPackage size == 0 ifTrue:[
-            containerPackage := (SourceCodeManagerUtilities lastPackage) ? Project current package.
-        ].
-        rslt := SourceCodeManagerUtilities default
-            askForContainer:(resources string:'The class seems to have no repository information.\\Do you want to compare it against an existing containers contents ?')
-            title:'Container to compare' note:nil
-            initialModule:containerModule
-            initialPackage:containerPackage
-            initialFileName:(aClass nameWithoutPrefix , '.st')
-            forNewContainer:false.
-        rslt isNil ifTrue:[
-            "/ canel
-            ^ false
-        ].
-        containerModule := rslt at:#module.
-        containerPackage := rslt at:#package.
-        containerFile := rslt at:#fileName.
-        SourceCodeManagerUtilities lastModule:containerModule.
-        SourceCodeManagerUtilities lastPackage:containerPackage.
-    ] ifFalse:[
-        "/
-        "/ class in repository - ask for revision
-        "/
-        newestRev := mgr newestRevisionOf:aClass.
-
-        msg := resources string:'Compare to revision: (empty for newest)'.
-        rev notNil ifTrue:[
-            msg := msg , '\\' , (resources string:'Current %1 is based upon rev %2.'
-                                           with:nm allBold with:rev).
-            (rev2 notNil and:[rev2 ~= rev]) ifTrue:[
-                msg := msg , '\' , (resources string:'And has been checked into the repository as %1.' with:rev2)
-            ]
-        ].
-        newestRev notNil ifTrue:[
-            msg := msg , '\' , (resources string:'Newest in reporitory is %1.' with:newestRev)
-        ].
-
-        self normalLabel.
-        rev := SourceCodeManagerUtilities default
-                    askForExistingRevision:msg
-                    title:'Compare with repository'
-                    class:aClass
+	"/
+	"/ class not in repository - allow compare against any other containers newest contents
+	"/
+	self normalLabel.
+
+	pkg := aClass package.
+	(pkg notNil and:[pkg ~= PackageId noProjectID]) ifTrue:[
+	    containerModule := pkg upTo:$:.
+	    containerPackage := pkg copyFrom:(containerModule size + 2).
+	].
+	containerModule size == 0 ifTrue:[
+	    containerModule := (SourceCodeManagerUtilities lastModule) ? Project current repositoryModule.
+	].
+	containerPackage size == 0 ifTrue:[
+	    containerPackage := (SourceCodeManagerUtilities lastPackage) ? Project current package.
+	].
+	rslt := SourceCodeManagerUtilities default
+	    askForContainer:(resources string:'The class seems to have no repository information.\\Do you want to compare it against an existing containers contents ?')
+	    title:'Container to compare' note:nil
+	    initialModule:containerModule
+	    initialPackage:containerPackage
+	    initialFileName:(aClass nameWithoutPrefix , '.st')
+	    forNewContainer:false.
+	rslt isNil ifTrue:[
+	    "/ canel
+	    ^ false
+	].
+	containerModule := rslt at:#module.
+	containerPackage := rslt at:#package.
+	containerFile := rslt at:#fileName.
+	SourceCodeManagerUtilities lastModule:containerModule.
+	SourceCodeManagerUtilities lastPackage:containerPackage.
+    ] ifFalse:[
+	"/
+	"/ class in repository - ask for revision
+	"/
+	newestRev := mgr newestRevisionOf:aClass.
+
+	msg := resources string:'Compare to revision: (empty for newest)'.
+	rev notNil ifTrue:[
+	    msg := msg , '\\' , (resources string:'Current %1 is based upon rev %2.'
+					   with:nm allBold with:rev).
+	    (rev2 notNil and:[rev2 ~= rev]) ifTrue:[
+		msg := msg , '\' , (resources string:'And has been checked into the repository as %1.' with:rev2)
+	    ]
+	].
+	newestRev notNil ifTrue:[
+	    msg := msg , '\' , (resources string:'Newest in reporitory is %1.' with:newestRev)
+	].
+
+	self normalLabel.
+	rev := SourceCodeManagerUtilities default
+		    askForExistingRevision:msg
+		    title:'Compare with repository'
+		    class:aClass
     ].
 
     versionsAreTheSame := false.
     (rev notNil or:[containerFile notNil]) ifFalse:[
-        self normalLabel.
-        ^ false
+	self normalLabel.
+	^ false
     ].
 
     rev notNil ifTrue:[
-        rev withoutSpaces isEmpty ifTrue:[
-            msg := 'extracting newest %1 (' , (newestRev ? '???') , ')'.
-            "/ aStream := mgr getMostRecentSourceStreamForClassNamed:nm.
-            rev := newestRev.
-            revInfoString := 'newest'.
-        ] ifFalse:[
-            msg := 'extracting previous %1'.
-            revInfoString := rev
-        ].
-        aStream := mgr getSourceStreamFor:aClass revision:rev.
-    ] ifFalse:[
-        msg := 'extracting newest version from ' , containerModule , '/' , containerPackage, '/' , containerFile.
-        aStream := mgr streamForClass:nil fileName:containerFile revision:#newest directory:containerPackage module:containerModule cache:false.
-        revInfoString := '???'
+	rev withoutSpaces isEmpty ifTrue:[
+	    msg := 'extracting newest %1 (' , (newestRev ? '???') , ')'.
+	    "/ aStream := mgr getMostRecentSourceStreamForClassNamed:nm.
+	    rev := newestRev.
+	    revInfoString := 'newest'.
+	] ifFalse:[
+	    msg := 'extracting previous %1'.
+	    revInfoString := rev
+	].
+	aStream := mgr getSourceStreamFor:aClass revision:rev.
+    ] ifFalse:[
+	msg := 'extracting newest version from ' , containerModule , '/' , containerPackage, '/' , containerFile.
+	aStream := mgr streamForClass:nil fileName:containerFile revision:#newest directory:containerPackage module:containerModule cache:false.
+	revInfoString := '???'
     ].
     self busyLabel:msg with:nm.
 
     aStream isNil ifTrue:[
-        info := mgr sourceInfoOfClass:aClass.
-        info notNil ifTrue:[
-            mod := info at:#module ifAbsent:'??'.
-            dir := info at:#directory ifAbsent:'??'.
-        ].
-
-        self warn:(resources
-                     string:'Could not extract source from repository (for module: ''%1'' , directory: ''%2'' , revision: ''%3'')'
-                     with:mod with:dir with:revInfoString).
-        self normalLabel.
-        ^ false
+	info := mgr sourceInfoOfClass:aClass.
+	info notNil ifTrue:[
+	    mod := info at:#module ifAbsent:'??'.
+	    dir := info at:#directory ifAbsent:'??'.
+	].
+
+	self warn:(resources
+		     string:'Could not extract source from repository (for module: ''%1'' , directory: ''%2'' , revision: ''%3'')'
+		     with:mod with:dir with:revInfoString).
+	self normalLabel.
+	^ false
     ].
 
     aStream class readErrorSignal handle:[:ex |
-        self warn:('read error while reading extracted source\\' , ex description) withCRs.
-        aStream close.
-        self normalLabel.
-        ^ false
+	self warn:('read error while reading extracted source\\' , ex description) withCRs.
+	aStream close.
+	self normalLabel.
+	^ false
     ] do:[
-        comparedSource := aStream contents asString.
+	comparedSource := aStream contents asString.
     ].
     aStream close.
 
     revInfoString = '(newest)' ifTrue:[
-        |rev|
-
-        (rev := mgr newestRevisionOf:aClass) notNil ifTrue:[
-            revInfoString := '(newest is ' , rev , ')'
-        ]
+	|rev|
+
+	(rev := mgr newestRevisionOf:aClass) notNil ifTrue:[
+	    revInfoString := '(newest is ' , rev , ')'
+	]
     ].
 
     aTwoArgBlock value:comparedSource value:revInfoString.
@@ -30341,70 +30766,70 @@
 
     |classesNotInPackage utilities msg answer errors|
 
-    "JV@2012-04-11: Kludge for SVNSourceCodeManager that does the check itself using 
+    "JV@2012-04-11: Kludge for SVNSourceCodeManager that does the check itself using
      new ProjectChecker and I don't want same message to appear twice. Anyway, there
      is another check for bad selectors in SCM, sigh"
 
     (aManagerOrNil isNil or:[aManagerOrNil performsCompilabilityChecks not]) ifTrue:[
-        errors := self checkCompilabilityOfAll:aCollectionOfClasses errorsOnly:true.
-        errors notEmptyOrNil ifTrue:[
-            (TextBox openOn:errors title:'Attention: about to check in class with errors' readOnly:true) isNil
-            ifTrue:[
-                AbortSignal raise
-            ].
-        ].
+	errors := self checkCompilabilityOfAll:aCollectionOfClasses errorsOnly:true.
+	errors notEmptyOrNil ifTrue:[
+	    (TextBox openOn:errors title:'Attention: about to check in class with errors' readOnly:true) isNil
+	    ifTrue:[
+		AbortSignal raise
+	    ].
+	].
     ].
 
     utilities := aManagerOrNil isNil
-                    ifTrue:[ SourceCodeManagerUtilities default ]
-                    ifFalse:[ aManagerOrNil utilities ].
+		    ifTrue:[ SourceCodeManagerUtilities default ]
+		    ifFalse:[ aManagerOrNil utilities ].
 
     self withActivityNotificationsRedirectedToInfoLabelDo:[
-        utilities
-            checkinClasses:aCollectionOfClasses
-            withInfo:logInfoOrNil
-            withCheck:doCheck
-            usingManager:aManagerOrNil.
+	utilities
+	    checkinClasses:aCollectionOfClasses
+	    withInfo:logInfoOrNil
+	    withCheck:doCheck
+	    usingManager:aManagerOrNil.
     ].
 
     classesNotInPackage := aCollectionOfClasses select:[:cls |
-                                |pkg def|
-
-                                pkg := cls package.
-                                pkg notNil ifTrue:[
-                                    def := ProjectDefinition definitionClassForPackage:pkg.
-                                ].
-                                def notNil and:[
-                                    (def allClassNames includes:cls name) not]
-                           ].
+				|pkg def|
+
+				pkg := cls package.
+				pkg notNil ifTrue:[
+				    def := ProjectDefinition definitionClassForPackage:pkg.
+				].
+				def notNil and:[
+				    (def allClassNames includes:cls name) not]
+			   ].
     classesNotInPackage := classesNotInPackage collect:[:cls | cls theNonMetaclass].
 
     classesNotInPackage notEmpty ifTrue:[
-        classesNotInPackage size > 1 ifTrue:[
-            msg := 'Add %2 classes to their Package definition (Make compiled or autoloaded) ?'
-        ] ifFalse:[
-            msg := 'Add %1 to its Package definition (Make compiled or autoloaded) ?'
-        ].
-        answer := Dialog 
-                    confirmWithCancel:((resources string:msg
-                                        with:classesNotInPackage first name
-                                        with:classesNotInPackage size)
-                                      , (resources 
-                                            stringWithCRs:'\\(Notice: You have to "checkIn build support files" for the package\for the compilation to become effective)')
-                                      )
-                    labels:(resources array:#('Cancel' 'Autoloaded' 'Compiled')).
-        answer == nil ifTrue:[^ self ].
-
-        classesNotInPackage do:[:eachClass |
-            |defClass|
-
-            defClass := eachClass projectDefinitionClass.
-            answer == true ifTrue:[
-                defClass includeClasses:{ eachClass } usingCompiler:nil
-            ] ifFalse:[
-                defClass makeClassesAutoloaded:{ eachClass } usingCompiler:nil
-            ].
-        ].
+	classesNotInPackage size > 1 ifTrue:[
+	    msg := 'Add %2 classes to their Package definition (Make compiled or autoloaded) ?'
+	] ifFalse:[
+	    msg := 'Add %1 to its Package definition (Make compiled or autoloaded) ?'
+	].
+	answer := Dialog
+		    confirmWithCancel:((resources string:msg
+					with:classesNotInPackage first name
+					with:classesNotInPackage size)
+				      , (resources
+					    stringWithCRs:'\\(Notice: You have to "checkIn build support files" for the package\for the compilation to become effective)')
+				      )
+		    labels:(resources array:#('Cancel' 'Autoloaded' 'Compiled')).
+	answer == nil ifTrue:[^ self ].
+
+	classesNotInPackage do:[:eachClass |
+	    |defClass|
+
+	    defClass := eachClass projectDefinitionClass.
+	    answer == true ifTrue:[
+		defClass includeClasses:{ eachClass } usingCompiler:nil
+	    ] ifFalse:[
+		defClass makeClassesAutoloaded:{ eachClass } usingCompiler:nil
+	    ].
+	].
     ].
 
     "Created: / 21-12-2011 / 18:22:58 / cg"
@@ -30418,8 +30843,8 @@
      otherwise ask for the revision."
 
     self withActivityNotificationsRedirectedToInfoLabelDo:[
-        SourceCodeManagerUtilities
-            checkoutClass:aClass askForRevision:askForRevision askForMerge:true.
+	SourceCodeManagerUtilities
+	    checkoutClass:aClass askForRevision:askForRevision askForMerge:true.
     ]
 
     "Modified: / 01-03-2007 / 17:47:32 / cg"
@@ -30432,8 +30857,8 @@
      otherwise ask for the revision."
 
     self withActivityNotificationsRedirectedToInfoLabelDo:[
-        manager utilities
-            checkoutClass:aClass askForRevision:askForRevision askForMerge:true.
+	manager utilities
+	    checkoutClass:aClass askForRevision:askForRevision askForMerge:true.
     ]
 
     "Modified: / 01-03-2007 / 17:47:32 / cg"
@@ -30466,68 +30891,68 @@
     ifFalse:[^ self].
 
     classes isEmpty ifTrue:[
-        Dialog warn:'No classes to checkout'.
+	Dialog warn:'No classes to checkout'.
 "/        SourceCodeManagerUtilities
 "/            checkoutClass:nil
 "/            askForRevision:true
 "/            askForMerge:false.
-        ^ self
+	^ self
     ].
 
     alreadyCheckedOut := IdentitySet new.
 
     "abortAll is handled, and also asked for here!!"
     AbortAllOperationRequest handleAndAnswerQueryIn:[
-        self
-            classes:classes
-            nonMetaDo:
-                [:cls |
-
-                  UserInformation handle:[:ex |
-                       classes size > 1 ifTrue:[
-                           Transcript showCR:ex description.
-                       ] ifFalse:[
-                            (Dialog confirm:ex description noLabel:'Cancel') ifFalse:[
-                                AbortSignal raise
-                            ].
-                       ].
-                       ex proceed.
-                  ] do:[
-                       self withActivityNotificationsRedirectedToInfoLabelDo:[
-                            |utilities|
-
-                            utilities := aManagerOrNil notNil
-                                            ifTrue:[ aManagerOrNil utilities ]
-                                            ifFalse:[ SourceCodeManagerUtilities default ].
-                            utilities
-                                checkoutClass:cls askForRevision:askForRevision askForMerge:true askForConfirmation:false.
-                       ].
-                       alreadyCheckedOut add:cls.
-                  ]
-                ]
-            ifUnloaded:
-                [:cls | true]
-            ifPrivate:
-                [:cls | |owner answer|
-
-                    owner := cls topOwningClass.
-                    (alreadyCheckedOut includes:owner) ifFalse:[
-                        ((self selectedClassesValue ? #()) includes:owner) ifFalse:[
-                            answer := Dialog
-                                        confirmWithCancel:(resources string:'Cannot checkOut private class: %1\\Shall the owner ''%2'' be checked out ?'
-                                                                          with:cls nameWithoutPrefix allBold
-                                                                          with:owner name) withCRs
-                                        default:true.
-                            answer == nil ifTrue:[
-                                AbortAllOperationRequest raise    "/ cancel
-                            ].
-                            answer == true ifTrue:[
-                                self checkOutClass:owner askForRevision:askForRevision usingManager:aManagerOrNil.
-                                alreadyCheckedOut add:owner.
-                            ].
-                        ]
-                    ]
-                ].
+	self
+	    classes:classes
+	    nonMetaDo:
+		[:cls |
+
+		  UserInformation handle:[:ex |
+		       classes size > 1 ifTrue:[
+			   Transcript showCR:ex description.
+		       ] ifFalse:[
+			    (Dialog confirm:ex description noLabel:'Cancel') ifFalse:[
+				AbortSignal raise
+			    ].
+		       ].
+		       ex proceed.
+		  ] do:[
+		       self withActivityNotificationsRedirectedToInfoLabelDo:[
+			    |utilities|
+
+			    utilities := aManagerOrNil notNil
+					    ifTrue:[ aManagerOrNil utilities ]
+					    ifFalse:[ SourceCodeManagerUtilities default ].
+			    utilities
+				checkoutClass:cls askForRevision:askForRevision askForMerge:true askForConfirmation:false.
+		       ].
+		       alreadyCheckedOut add:cls.
+		  ]
+		]
+	    ifUnloaded:
+		[:cls | true]
+	    ifPrivate:
+		[:cls | |owner answer|
+
+		    owner := cls topOwningClass.
+		    (alreadyCheckedOut includes:owner) ifFalse:[
+			((self selectedClassesValue ? #()) includes:owner) ifFalse:[
+			    answer := Dialog
+					confirmWithCancel:(resources string:'Cannot checkOut private class: %1\\Shall the owner ''%2'' be checked out ?'
+									  with:cls nameWithoutPrefix allBold
+									  with:owner name) withCRs
+					default:true.
+			    answer == nil ifTrue:[
+				AbortAllOperationRequest raise    "/ cancel
+			    ].
+			    answer == true ifTrue:[
+				self checkOutClass:owner askForRevision:askForRevision usingManager:aManagerOrNil.
+				alreadyCheckedOut add:owner.
+			    ].
+			]
+		    ]
+		].
     ].
     self normalLabel.
 
@@ -30582,45 +31007,45 @@
     classesToCheckIn := IdentitySet new.
 
     self
-        classes:classesSelected
-        nonMetaDo:
-            [:cls |
-              InformationSignal handle:[:ex |
-                   Transcript showCR:ex description.
-                   ex proceed.
-              ] do:[
-                   classesToCheckIn add:cls.
-              ]
-            ]
-        ifUnloaded:
-            [:cls |
-                (Dialog confirm:('Cannot checkin unloaded class: %1.' bindWith:cls name allBold)
-                      title:'Cannot Checkin' yesLabel:'OK' noLabel:'Cancel' ) ifFalse:[^ self].
-                false.
-            ]
-        ifPrivate:
-            [:cls | |owner answer|
-
-                owner := cls topOwningClass.
-                (classesToCheckIn includes:owner) ifFalse:[
-                    (classesSelected "self selectedClasses value" includes:owner) ifFalse:[
-                        answer := Dialog
-                                    confirmWithCancel:(resources string:'Cannot checkin private class: %1\\Shall the owner ''%2'' be checked in ?'
-                                                                      with:cls nameWithoutPrefix allBold
-                                                                      with:owner name allBold) withCRs
-                                    default:true.
-                        answer == nil ifTrue:[
-                            ^ self
-                        ].
-                        answer == true ifTrue:[
-                            classesToCheckIn add:owner.
-                        ].
-                    ]
-                ]
-            ].
+	classes:classesSelected
+	nonMetaDo:
+	    [:cls |
+	      InformationSignal handle:[:ex |
+		   Transcript showCR:ex description.
+		   ex proceed.
+	      ] do:[
+		   classesToCheckIn add:cls.
+	      ]
+	    ]
+	ifUnloaded:
+	    [:cls |
+		(Dialog confirm:('Cannot checkin unloaded class: %1.' bindWith:cls name allBold)
+		      title:'Cannot Checkin' yesLabel:'OK' noLabel:'Cancel' ) ifFalse:[^ self].
+		false.
+	    ]
+	ifPrivate:
+	    [:cls | |owner answer|
+
+		owner := cls topOwningClass.
+		(classesToCheckIn includes:owner) ifFalse:[
+		    (classesSelected "self selectedClasses value" includes:owner) ifFalse:[
+			answer := Dialog
+				    confirmWithCancel:(resources string:'Cannot checkin private class: %1\\Shall the owner ''%2'' be checked in ?'
+								      with:cls nameWithoutPrefix allBold
+								      with:owner name allBold) withCRs
+				    default:true.
+			answer == nil ifTrue:[
+			    ^ self
+			].
+			answer == true ifTrue:[
+			    classesToCheckIn add:owner.
+			].
+		    ]
+		]
+	    ].
 
     classesToCheckIn notEmpty ifTrue:[
-        self checkInClasses:classesToCheckIn withInfo:nil withCheck:doCheck usingManager:aManagerOrNil.
+	self checkInClasses:classesToCheckIn withInfo:nil withCheck:doCheck usingManager:aManagerOrNil.
     ].
     self normalLabel.
 
@@ -30635,9 +31060,9 @@
      "
 
     ^ self
-        classMenuCheckIn:doCheck
-        classes:(self selectedClassesValue)
-        usingManager:aManagerOrNil
+	classMenuCheckIn:doCheck
+	classes:(self selectedClassesValue)
+	usingManager:aManagerOrNil
 
     "Created: / 21-12-2011 / 18:21:30 / cg"
 !
@@ -30670,9 +31095,9 @@
     "
 
     ^ self
-        classMenuCheckIn:doCheck
-        classes:(ChangeSet current changedClasses)
-        usingManager:aManagerOrNil
+	classMenuCheckIn:doCheck
+	classes:(ChangeSet current changedClasses)
+	usingManager:aManagerOrNil
 
     "Created: / 21-12-2011 / 19:52:50 / cg"
 !
@@ -30719,15 +31144,15 @@
 
     projects := Set new.
     self selectedClassesDo:[:eachClass |
-        eachClass instAndClassSelectorsAndMethodsDo:[:sel :mthd | projects add:mthd package].
+	eachClass instAndClassSelectorsAndMethodsDo:[:sel :mthd | projects add:mthd package].
     ].
     projects do:[:eachProject |
-        self
-            projectMenuCheckInProject:eachProject
-            classes:false
-            extensions:true
-            buildSupport:false
-            askForMethodsInOtherPackages:false
+	self
+	    projectMenuCheckInProject:eachProject
+	    classes:false
+	    extensions:true
+	    buildSupport:false
+	    askForMethodsInOtherPackages:false
     ].
 !
 
@@ -30737,17 +31162,27 @@
     (self askIfModified:'Code was modified.\\CheckIn (without that modification) anyway ?')
     ifFalse:[^ self].
     self withWaitCursorDo:[
-        self
-            projectMenuCheckInProject:aProjectID
-            classes:false
-            extensions:true
-            buildSupport:false
-            askForMethodsInOtherPackages:false
+	self
+	    projectMenuCheckInProject:aProjectID
+	    classes:false
+	    extensions:true
+	    buildSupport:false
+	    askForMethodsInOtherPackages:false
     ]
 
     "Modified: / 08-09-2011 / 04:07:58 / cg"
 !
 
+classMenuCheckInP4
+    "check a class into the source repository (with checks)"
+
+    PerforceSourceCodeManager notNil ifTrue:[
+	self classMenuCheckInUsingManager:PerforceSourceCodeManager
+    ].
+
+    "Modified: / 21-12-2011 / 18:20:40 / cg"
+!
+
 classMenuCheckInUsingManager:aManagerOrNil
     "check a class into the source repository (with checks)"
 
@@ -30757,7 +31192,7 @@
     doChecks := doChecks asValue.
     self classMenuCheckIn:doChecks usingManager:aManagerOrNil.
     doChecks value ~~ (UserPreferences current at:#checkClassesWhenCheckingIn ifAbsent:true) ifTrue:[
-        UserPreferences current at:#checkClassesWhenCheckingIn put:doChecks value
+	UserPreferences current at:#checkClassesWhenCheckingIn put:doChecks value
     ].
 
     "Created: / 21-12-2011 / 18:20:19 / cg"
@@ -30869,8 +31304,8 @@
 
     currentClass := self theSingleSelectedLoadedNonMetaclassOrNil.
     currentClass isNil ifTrue:[
-        self warn:'Cannot compare unloaded classes.'.
-        ^ self.
+	self warn:'Cannot compare unloaded classes.'.
+	^ self.
     ].
     mgr := SourceCodeManagerUtilities default sourceCodeManagerFor:currentClass.
     self classMenuCompareAgainstOriginalInRepositoryUsingManager:mgr.
@@ -30889,24 +31324,24 @@
 
     currentClass := self theSingleSelectedLoadedNonMetaclassOrNil.
     currentClass isNil ifTrue:[
-        self warn:'Cannot compare unloaded classes.'.
-        ^ self.
+	self warn:'Cannot compare unloaded classes.'.
+	^ self.
     ].
 
     nm := currentClass name.
     mgr := manager.
     mgr isNil ifTrue:[
-        ^ self
+	^ self
     ].
     revInfo := currentClass revisionInfoOfManager: manager.
     revInfo ifNil:[
-        self warn:('The class seems to have no repository information for %1.' bindWith: mgr managerTypeName).
-        ^ self
+	self warn:('The class seems to have no repository information for %1.' bindWith: mgr managerTypeName).
+	^ self
     ].
     rev := revInfo revision.
     rev isNil ifTrue:[
-        self warn:'The class seems to have no repository information.'.
-        ^ self
+	self warn:'The class seems to have no repository information.'.
+	^ self
     ].
     "/
     "/ class in repository - ask for revision
@@ -30914,19 +31349,19 @@
     msg := 'extracting revision %1'.
     self busyLabel:msg with:rev.
     self withActivityNotificationsRedirectedToInfoLabelDo:[
-        aStream := mgr getSourceStreamFor:currentClass revision:rev.
+	aStream := mgr getSourceStreamFor:currentClass revision:rev.
     ].
 
     aStream isNil ifTrue:[
-        self warn:'Could not extract source from repository.'.
-        ^ self
+	self warn:'Could not extract source from repository.'.
+	^ self
     ].
     aStream class readErrorSignal handle:[:ex |
-        self warn:('Read error while reading extracted source:\\' , ex description) withCRs.
-        aStream close.
-        ^ self
+	self warn:('Read error while reading extracted source:\\' , ex description) withCRs.
+	aStream close.
+	^ self
     ] do:[
-        comparedSource := aStream contents asString.
+	comparedSource := aStream contents asString.
     ].
     aStream close.
 
@@ -30941,14 +31376,14 @@
     self busyLabel:'comparing  ...' with:nil.
 
     comparedSource = currentSource ifTrue:[
-        self information:'Versions are identical.'.
-    ] ifFalse:[
-        thisRevString := currentClass revision.
-        thisRevString isNil ifTrue:[
-            thisRevString := 'no revision'
-        ].
-
-        revString := rev.
+	self information:'Versions are identical.'.
+    ] ifFalse:[
+	thisRevString := currentClass revision.
+	thisRevString isNil ifTrue:[
+	    thisRevString := 'no revision'
+	].
+
+	revString := rev.
 "/        "/ this takes some time ... is it worth ?
 "/        (newestRev := mgr newestRevisionOf:currentClass) notNil ifTrue:[
 "/            newestRev ~= rev ifTrue:[
@@ -30956,21 +31391,21 @@
 "/            ]
 "/        ].
 
-        self busyLabel:'comparing  ...' with:nil.
-
-        brwsr := (UserPreferences versionDiffViewerClass)
-              openOnClass:currentClass
-              labelA:('repository: ' , revString)
-              sourceA:comparedSource
-              labelB:('current: (based on: ' , rev , ')')
-              sourceB:currentSource
-              title:('comparing ' , currentClass name)
-              ifSame:[self normalLabel. self information:'Versions are identical.'. ^ self].
-
-        brwsr classChangeSet
-            classBeingCompared:currentClass;
-            versionA:rev;
-            versionB:rev , 'mod'.
+	self busyLabel:'comparing  ...' with:nil.
+
+	brwsr := (UserPreferences versionDiffViewerClass)
+	      openOnClass:currentClass
+	      labelA:('repository: ' , revString)
+	      sourceA:comparedSource
+	      labelB:('current: (based on: ' , rev , ')')
+	      sourceB:currentSource
+	      title:('comparing ' , currentClass name)
+	      ifSame:[self normalLabel. self information:'Versions are identical.'. ^ self].
+
+	brwsr classChangeSet
+	    classBeingCompared:currentClass;
+	    versionA:rev;
+	    versionB:rev , 'mod'.
     ].
     self normalLabel.
 
@@ -30992,7 +31427,7 @@
     "open a diff-textView comparing the current (in-image) extensions of the selected class
      with the some extensions version found in the repository."
 
-    |currentClass extensionMethods extensionMethodChangesInImage extensionProjectDefinitions 
+    |currentClass extensionMethods extensionMethodChangesInImage extensionProjectDefinitions
      extensionMethodChangesInRepository diffSet versionsAreTheSame|
 
     currentClass := self theSingleSelectedLoadedNonMetaclassOrNil.
@@ -31002,64 +31437,64 @@
 
     extensionProjectDefinitions := Set new.
     ProjectDefinition allSubclasses do:[:eachProjectDefinition |
-        (eachProjectDefinition extensionClasses includes:currentClass) ifTrue:[
-            extensionProjectDefinitions add:eachProjectDefinition.
-        ].
+	(eachProjectDefinition extensionClasses includes:currentClass) ifTrue:[
+	    extensionProjectDefinitions add:eachProjectDefinition.
+	].
     ].
 
     extensionMethodChangesInImage := ChangeSet forExistingClass:currentClass withExtensions:true extensionsOnly:true.
     extensionMethodChangesInRepository := ChangeSet new.
 
     extensionProjectDefinitions do:[:eachProjectDefinition |
-        |mgr revString info rev package changesHere changesHereForMe|
-
-        package := eachProjectDefinition package.
-        mgr := SourceCodeManagerUtilities default sourceCodeManagerFor:eachProjectDefinition.
-        mgr isNil ifTrue:[
-            Dialog warn:(resources string:'No sourceCodeManager known for %1.' with:eachProjectDefinition package).
-        ] ifFalse:[
-            rev := mgr
-                    newestRevisionInFile:'extensions.st' 
-                    directory:(eachProjectDefinition directory) 
-                    module:(eachProjectDefinition module).
-            "/ revString := eachProjectDefinition perform:(mgr nameOfVersionMethodForExtensions) ifNotUnderstood:nil.
-            "/ revString isNil ifTrue:[
-            "/    Dialog warn:(resources string:'%1 seems to not have any extensions (loaded)' with:package).
-            "/] ifFalse:[
-            "/    info := mgr revisionInfoFromString:revString.
-            "/    rev := info revision.
-                "/
-                "/ ask for revision
-                "/
-"/                newestRev := mgr 
-"/                                newestRevisionInFile:'extensions.st' 
-"/                                directory:(eachProjectDefinition directory) 
+	|mgr revString info rev package changesHere changesHereForMe|
+
+	package := eachProjectDefinition package.
+	mgr := SourceCodeManagerUtilities default sourceCodeManagerFor:eachProjectDefinition.
+	mgr isNil ifTrue:[
+	    Dialog warn:(resources string:'No sourceCodeManager known for %1.' with:eachProjectDefinition package).
+	] ifFalse:[
+	    rev := mgr
+		    newestRevisionInFile:'extensions.st'
+		    directory:(eachProjectDefinition directory)
+		    module:(eachProjectDefinition module).
+	    "/ revString := eachProjectDefinition perform:(mgr nameOfVersionMethodForExtensions) ifNotUnderstood:nil.
+	    "/ revString isNil ifTrue:[
+	    "/    Dialog warn:(resources string:'%1 seems to not have any extensions (loaded)' with:package).
+	    "/] ifFalse:[
+	    "/    info := mgr revisionInfoFromString:revString.
+	    "/    rev := info revision.
+		"/
+		"/ ask for revision
+		"/
+"/                newestRev := mgr
+"/                                newestRevisionInFile:'extensions.st'
+"/                                directory:(eachProjectDefinition directory)
 "/                                module:(eachProjectDefinition module).
 
-                changesHere := SourceCodeManagerUtilities default
-                    changeSetForExtensionMethodsForPackage:package 
-                    revision:rev orAskForRevision:false 
-                    usingManager:mgr.
-                changesHereForMe := changesHere select:[:chg | chg isMethodChange
-                                                               and:[chg changeClass == currentClass]].
-                extensionMethodChangesInRepository addAll:changesHereForMe.
-            "/ ].
-        ].
+		changesHere := SourceCodeManagerUtilities default
+		    changeSetForExtensionMethodsForPackage:package
+		    revision:rev orAskForRevision:false
+		    usingManager:mgr.
+		changesHereForMe := changesHere select:[:chg | chg isMethodChange
+							       and:[chg changeClass == currentClass]].
+		extensionMethodChangesInRepository addAll:changesHereForMe.
+	    "/ ].
+	].
     ].
 
     versionsAreTheSame := false.
-    diffSet := extensionMethodChangesInImage diffSetsAgainst:extensionMethodChangesInRepository. 
+    diffSet := extensionMethodChangesInImage diffSetsAgainst:extensionMethodChangesInRepository.
     diffSet isEmpty ifTrue:[
-        self information:'Versions are identical.'.
-        ^ self
+	self information:'Versions are identical.'.
+	^ self
     ].
 
     (UserPreferences versionDiffViewerClass)
-        openOnDiffSet:diffSet 
-        labelA:'Current (In Image)'
-        labelB:('Repository (%1 extension package(s))' bindWith:extensionProjectDefinitions size) 
-        title:'Diffs'
-        ignoreExtensions:false.
+	openOnDiffSet:diffSet
+	labelA:'Current (In Image)'
+	labelB:('Repository (%1 extension package(s))' bindWith:extensionProjectDefinitions size)
+	title:'Diffs'
+	ignoreExtensions:false.
 
     self normalLabel.
 
@@ -31076,19 +31511,19 @@
     currentClass isNil ifTrue:[^ self].
 
     (projectDefinition := currentClass theNonMetaclass) isProjectDefinition ifFalse:[
-        self classMenuCompareClassExtensionsWithRepository.
-        ^ self.
+	self classMenuCompareClassExtensionsWithRepository.
+	^ self.
     ].
 
     mgr := SourceCodeManagerUtilities default sourceCodeManagerFor:projectDefinition.
     mgr isNil ifTrue:[
-        ^ self
+	^ self
     ].
 
     revString := projectDefinition perform:(mgr nameOfVersionMethodForExtensions) ifNotUnderstood:nil.
     revString isNil ifTrue:[
-        self warn:('%1 seems to not have any extensions (loaded)' bindWith:projectDefinition package).
-        ^ self.
+	self warn:('%1 seems to not have any extensions (loaded)' bindWith:projectDefinition package).
+	^ self.
     ].
     info := mgr revisionInfoFromString:revString.
     rev := info revision.
@@ -31096,64 +31531,64 @@
     "/
     "/ ask for revision
     "/
-    newestRev := mgr 
-                    newestRevisionInFile:'extensions.st' 
-                    directory:(projectDefinition directory) 
-                    module:(projectDefinition module).
+    newestRev := mgr
+		    newestRevisionInFile:'extensions.st'
+		    directory:(projectDefinition directory)
+		    module:(projectDefinition module).
 
     msg := resources string:'Compare to revision: (empty for newest)'.
     rev notNil ifTrue:[
-        msg := msg , '\\' , (resources string:'Current extensions.st is based upon rev %1.'
-                                       with:rev).
+	msg := msg , '\\' , (resources string:'Current extensions.st is based upon rev %1.'
+				       with:rev).
     ].
     newestRev notNil ifTrue:[
-        msg := msg , '\' , (resources string:'Newest in reporitory is %1.'
-                                       with:newestRev)
+	msg := msg , '\' , (resources string:'Newest in reporitory is %1.'
+				       with:newestRev)
     ].
 
     self normalLabel.
     rev := SourceCodeManagerUtilities default
-                askForExistingRevision:msg 
-                title:'Compare Extensions against Revision' 
-                class:nil 
-                manager:mgr 
-                module:projectDefinition module package:projectDefinition directory 
-                fileName:'extensions.st'.
+		askForExistingRevision:msg
+		title:'Compare Extensions against Revision'
+		class:nil
+		manager:mgr
+		module:projectDefinition module package:projectDefinition directory
+		fileName:'extensions.st'.
 
     versionsAreTheSame := false.
     rev isNil ifTrue:[
-        self normalLabel.
-        ^ self.
+	self normalLabel.
+	^ self.
     ].
 
     rev withoutSpaces isEmpty ifTrue:[
-        msg := 'extracting newest %1 (' , (newestRev ? '???') , ')'.
-        rev := newestRev.
-        revString := 'newest'.
-    ] ifFalse:[
-        msg := 'extracting previous %1'.
-        revString := rev
+	msg := 'extracting newest %1 (' , (newestRev ? '???') , ')'.
+	rev := newestRev.
+	revString := 'newest'.
+    ] ifFalse:[
+	msg := 'extracting previous %1'.
+	revString := rev
     ].
     changeSetForMethodsInRepository :=
-        SourceCodeManagerUtilities default
-            changeSetForExtensionMethodsForPackage:projectDefinition package 
-            revision:revString orAskForRevision:false 
-            usingManager:mgr.
+	SourceCodeManagerUtilities default
+	    changeSetForExtensionMethodsForPackage:projectDefinition package
+	    revision:revString orAskForRevision:false
+	    usingManager:mgr.
 
     changeSetForMethodsInImage := ChangeSet forExistingMethods:(
-                                    Method allInstances 
-                                        select:[:m | m package = projectDefinition package
-                                                     and:[ m mclass isNil 
-                                                           or:[m package ~= m mclass package]]]).
-
-    diffSet := changeSetForMethodsInImage diffSetsAgainst:changeSetForMethodsInRepository. 
+				    Method allInstances
+					select:[:m | m package = projectDefinition package
+						     and:[ m mclass isNil
+							   or:[m package ~= m mclass package]]]).
+
+    diffSet := changeSetForMethodsInImage diffSetsAgainst:changeSetForMethodsInRepository.
 
     (UserPreferences versionDiffViewerClass)
-        openOnDiffSet:diffSet 
-        labelA:'Current (In Image)'
-        labelB:'Repository (',rev,')' 
-        title:'Diffs'
-        ignoreExtensions:false.
+	openOnDiffSet:diffSet
+	labelA:'Current (In Image)'
+	labelB:'Repository (',rev,')'
+	title:'Diffs'
+	ignoreExtensions:false.
 
     self normalLabel.
 
@@ -31175,27 +31610,27 @@
 
     currentClass := self theSingleSelectedLoadedNonMetaclassOrNil.
     currentClass isNil ifTrue:[
-        self warn:'Cannot compare unloaded classes.'.
-        ^ self.
+	self warn:'Cannot compare unloaded classes.'.
+	^ self.
     ].
 
     nm := currentClass name.
     mgr := SourceCodeManagerUtilities default sourceCodeManagerFor:currentClass.
     mgr isNil ifTrue:[
-        ^ self
+	^ self
     ].
 
     self normalLabel.
     rev1 := SourceCodeManagerUtilities default
-                askForExistingRevision:(resources string:'Compare which revision:')
-                title:(resources string:'Compare which repository version')
-                class:currentClass.
+		askForExistingRevision:(resources string:'Compare which revision:')
+		title:(resources string:'Compare which repository version')
+		class:currentClass.
     rev1 isNil ifTrue:[^ self].
 
     rev2 := SourceCodeManagerUtilities default
-                askForExistingRevision:(resources string:'Against which revision:')
-                title:(resources string:'Against which repository version')
-                class:currentClass.
+		askForExistingRevision:(resources string:'Against which revision:')
+		title:(resources string:'Against which repository version')
+		class:currentClass.
     rev2 isNil ifTrue:[^ self].
 
     source1 := self getClassSourceFor:currentClass revision:rev1.
@@ -31204,19 +31639,19 @@
     self busyLabel:'comparing  ...' with:nil.
     versionsAreTheSame := (source1 = source2).
     versionsAreTheSame ifFalse:[
-        self busyLabel:'comparing  ...' with:nil.
-        (UserPreferences versionDiffViewerClass)
-                  openOnClass:currentClass
-                  labelA:(rev1)
-                  sourceA:source1
-                  labelB:(rev2)
-                  sourceB:source2
-                  title:('comparing ' , currentClass name)
-                  ifSame:[versionsAreTheSame := true].
-
-        versionsAreTheSame ifTrue:[
-            self information:'Versions are identical.'.
-        ].
+	self busyLabel:'comparing  ...' with:nil.
+	(UserPreferences versionDiffViewerClass)
+		  openOnClass:currentClass
+		  labelA:(rev1)
+		  sourceA:source1
+		  labelB:(rev2)
+		  sourceB:source2
+		  title:('comparing ' , currentClass name)
+		  ifSame:[versionsAreTheSame := true].
+
+	versionsAreTheSame ifTrue:[
+	    self information:'Versions are identical.'.
+	].
     ].
     self normalLabel.
 
@@ -31231,27 +31666,27 @@
 
     currentClass := self theSingleSelectedLoadedNonMetaclassOrNil.
     currentClass isNil ifTrue:[
-        self warn:'Cannot compare unloaded classes.'.
-        ^ self.
+	self warn:'Cannot compare unloaded classes.'.
+	^ self.
     ].
 
     nm := currentClass name.
     mgr := manager.
     mgr isNil ifTrue:[
-        ^ self
+	^ self
     ].
 
     self normalLabel.
     rev1 := manager utilities
-                askForExistingRevision:(resources string:'Compare which revision:')
-                title:(resources string:'Compare which repository version')
-                class:currentClass.
+		askForExistingRevision:(resources string:'Compare which revision:')
+		title:(resources string:'Compare which repository version')
+		class:currentClass.
     rev1 isNil ifTrue:[^ self].
 
     rev2 := manager utilities
-                askForExistingRevision:(resources string:'Against which revision:')
-                title:(resources string:'Against which repository version')
-                class:currentClass.
+		askForExistingRevision:(resources string:'Against which revision:')
+		title:(resources string:'Against which repository version')
+		class:currentClass.
     rev2 isNil ifTrue:[^ self].
 
     source1 := self getClassSourceFor:currentClass revision:rev1 usingManager: manager.
@@ -31260,19 +31695,19 @@
     self busyLabel:'comparing  ...' with:nil.
     versionsAreTheSame := (source1 = source2).
     versionsAreTheSame ifFalse:[
-        self busyLabel:'comparing  ...' with:nil.
-        (UserPreferences versionDiffViewerClass)
-                  openOnClass:currentClass
-                  labelA:(rev1)
-                  sourceA:source1
-                  labelB:(rev2)
-                  sourceB:source2
-                  title:('comparing ' , currentClass name)
-                  ifSame:[versionsAreTheSame := true].
-
-        versionsAreTheSame ifTrue:[
-            self information:'Versions are identical.'.
-        ].
+	self busyLabel:'comparing  ...' with:nil.
+	(UserPreferences versionDiffViewerClass)
+		  openOnClass:currentClass
+		  labelA:(rev1)
+		  sourceA:source1
+		  labelB:(rev2)
+		  sourceB:source2
+		  title:('comparing ' , currentClass name)
+		  ifSame:[versionsAreTheSame := true].
+
+	versionsAreTheSame ifTrue:[
+	    self information:'Versions are identical.'.
+	].
     ].
     self normalLabel.
 
@@ -31296,45 +31731,45 @@
     collectionOfClasses := self selectedClassesValue.
 
     collectionOfClasses do:[:eachClass |
-        |className metaclassName|
-
-        className := eachClass theNonMetaclass name.
-        metaclassName := eachClass theMetaclass name.
-        eachClass isLoaded ifFalse:[
-            Transcript showCR:('Cannot compare unloaded class: ' , eachClass name).
-        ] ifTrue:[
-            fileName := Dialog requestFileName:'Compare against:'.
-            fileName isEmptyOrNil ifTrue:[^ self].
-
-            self busyLabel:'comparing  ...' with:nil.
-
-            current    := ChangeSet forExistingClass:eachClass theNonMetaclass.
-            fileVersion := ChangeSet fromFile:fileName.
-
-            diffs := fileVersion diffSetsAgainst:current.
-            allDiffs isNil ifTrue:[
-                allDiffs := diffs.
-            ] ifFalse:[
-                allDiffs changed addAll:(diffs changed).
-                allDiffs onlyInArg addAll:(diffs onlyInArg).
-                allDiffs onlyInReceiver addAll:(diffs onlyInReceiver).
-            ].
-        ].
+	|className metaclassName|
+
+	className := eachClass theNonMetaclass name.
+	metaclassName := eachClass theMetaclass name.
+	eachClass isLoaded ifFalse:[
+	    Transcript showCR:('Cannot compare unloaded class: ' , eachClass name).
+	] ifTrue:[
+	    fileName := Dialog requestFileName:'Compare against:'.
+	    fileName isEmptyOrNil ifTrue:[^ self].
+
+	    self busyLabel:'comparing  ...' with:nil.
+
+	    current    := ChangeSet forExistingClass:eachClass theNonMetaclass.
+	    fileVersion := ChangeSet fromFile:fileName.
+
+	    diffs := fileVersion diffSetsAgainst:current.
+	    allDiffs isNil ifTrue:[
+		allDiffs := diffs.
+	    ] ifFalse:[
+		allDiffs changed addAll:(diffs changed).
+		allDiffs onlyInArg addAll:(diffs onlyInArg).
+		allDiffs onlyInReceiver addAll:(diffs onlyInReceiver).
+	    ].
+	].
     ].
 
     allDiffs isEmpty ifTrue:[
-        self information:'The Versions are Equal.'.
-    ] ifFalse:[
-        title := collectionOfClasses size == 1
-                    ifTrue:['Differences of %1' bindWith:collectionOfClasses first name]
-                    ifFalse:['Differences of %1 classes' bindWith:collectionOfClasses size].
-
-        VersionDiffBrowser
-            openOnDiffSet:allDiffs
-            labelA:'Version in File ',fileName
-            labelB:'Image'
-            title:title
-            ignoreExtensions:true.
+	self information:'The Versions are Equal.'.
+    ] ifFalse:[
+	title := collectionOfClasses size == 1
+		    ifTrue:['Differences of %1' bindWith:collectionOfClasses first name]
+		    ifFalse:['Differences of %1 classes' bindWith:collectionOfClasses size].
+
+	VersionDiffBrowser
+	    openOnDiffSet:allDiffs
+	    labelA:'Version in File ',fileName
+	    labelB:'Image'
+	    title:title
+	    ignoreExtensions:true.
     ].
 
     self normalLabel.
@@ -31351,54 +31786,54 @@
 
     currentClass := self theSingleSelectedLoadedNonMetaclassOrNil.
     currentClass isNil ifTrue:[
-        self warn:'Cannot compare unloaded classes.'.
-        ^ self.
-    ].
-
-    self 
-        askForRepositoryVersionOf:currentClass 
-        withSourceDo:[:comparedSource :revString |
-
-            self busyLabel:'generating current source ...' with:nil.
-
-            aStream := '' writeStream.
-            Method flushSourceStreamCache.
-            "/ currentClass fileOutOn:aStream withTimeStamp:false.
-            "/ currentSource := aStream contents asString.
-
-            Class fileOutErrorSignal handle:[:ex |
-                ex proceed
-            ] do:[
-                currentSource := currentClass source asString.
-            ].
-            
-            self busyLabel:'comparing  ...' with:nil.
-            versionsAreTheSame := (comparedSource = currentSource).
-            versionsAreTheSame ifFalse:[
-                thisRevString := currentClass revision.
-                thisRevString isNil ifTrue:[
-                    thisRevString := 'no revision'
-                ].
-
-                self busyLabel:'comparing  ...' with:nil.
-                (UserPreferences versionDiffViewerClass)
-                      openOnClass:currentClass
-                      labelA:('repository: ' , revString) sourceA:comparedSource
-                      labelB:('current: (based on: ' , thisRevString , ')') sourceB:currentSource
-                      title:('comparing ' , currentClass name)
-                      ifSame:[versionsAreTheSame := true].
-            ].
-            versionsAreTheSame ifTrue:[
-                ((currentClass revision = newestRev)
-                and:[currentClass hasUnsavedChanges]) ifTrue:[
-                    (self confirm:'Versions are identical.\\Remove entries from changeSet ?' withCRs) ifTrue:[
-                        ChangeSet current condenseChangesForClass:currentClass.
-                    ].
-                ] ifFalse:[
-                    self information:'Versions are identical.'.
-                ]
-            ].
-        ].
+	self warn:'Cannot compare unloaded classes.'.
+	^ self.
+    ].
+
+    self
+	askForRepositoryVersionOf:currentClass
+	withSourceDo:[:comparedSource :revString |
+
+	    self busyLabel:'generating current source ...' with:nil.
+
+	    aStream := '' writeStream.
+	    Method flushSourceStreamCache.
+	    "/ currentClass fileOutOn:aStream withTimeStamp:false.
+	    "/ currentSource := aStream contents asString.
+
+	    Class fileOutErrorSignal handle:[:ex |
+		ex proceed
+	    ] do:[
+		currentSource := currentClass source asString.
+	    ].
+
+	    self busyLabel:'comparing  ...' with:nil.
+	    versionsAreTheSame := (comparedSource = currentSource).
+	    versionsAreTheSame ifFalse:[
+		thisRevString := currentClass revision.
+		thisRevString isNil ifTrue:[
+		    thisRevString := 'no revision'
+		].
+
+		self busyLabel:'comparing  ...' with:nil.
+		(UserPreferences versionDiffViewerClass)
+		      openOnClass:currentClass
+		      labelA:('repository: ' , revString) sourceA:comparedSource
+		      labelB:('current: (based on: ' , thisRevString , ')') sourceB:currentSource
+		      title:('comparing ' , currentClass name)
+		      ifSame:[versionsAreTheSame := true].
+	    ].
+	    versionsAreTheSame ifTrue:[
+		((currentClass revision = newestRev)
+		and:[currentClass hasUnsavedChanges]) ifTrue:[
+		    (self confirm:'Versions are identical.\\Remove entries from changeSet ?' withCRs) ifTrue:[
+			ChangeSet current condenseChangesForClass:currentClass.
+		    ].
+		] ifFalse:[
+		    self information:'Versions are identical.'.
+		]
+	    ].
+	].
 
     self normalLabel.
 
@@ -31418,170 +31853,170 @@
 
     currentClass := self theSingleSelectedLoadedNonMetaclassOrNil.
     currentClass isNil ifTrue:[
-        self warn:'Cannot compare unloaded classes.'.
-        ^ self.
+	self warn:'Cannot compare unloaded classes.'.
+	^ self.
     ].
 
     nm := currentClass name.
     mgr := manager.
     mgr isNil ifTrue:[
-        ^ self
+	^ self
     ].
     "Use revision of manager"
     rev := currentClass binaryRevision.
     revInfo := mgr revisionInfoOfManager: mgr.
     revInfo notNil ifTrue:[
-        rev2 := revInfo revision.
+	rev2 := revInfo revision.
     ].
     rev2 notNil ifTrue:[
-        rev := rev2
+	rev := rev2
     ].
     rev isNil ifTrue:[
-        "/
-        "/ class not in repository - allow compare against any other containers newest contents
-        "/
-        self normalLabel.
-
-        pkg := currentClass package.
-        (pkg notNil and:[pkg ~= PackageId noProjectID]) ifTrue:[
-            containerModule := pkg upTo:$:.
-            containerPackage := pkg copyFrom:(containerModule size + 2).
-        ].
-        containerModule size == 0 ifTrue:[
-            containerModule := (SourceCodeManagerUtilities lastModule) ? Project current repositoryModule.
-        ].
-        containerPackage size == 0 ifTrue:[
-            containerPackage := (SourceCodeManagerUtilities lastPackage) ? Project current package.
-        ].
-        rslt := manager utilities
-            askForContainer:(resources string:'The class seems to have no repository information.\\Do you want to compare it against an existing containers contents ?')
-            title:'Container to compare' note:nil
-            initialModule:containerModule
-            initialPackage:containerPackage
-            initialFileName:(currentClass nameWithoutPrefix , '.st')
-            forNewContainer:false.
-        rslt isNil ifTrue:[
-            "/ canel
-            ^ self
-        ].
-        containerModule := rslt at:#module.
-        containerPackage := rslt at:#package.
-        containerFile := rslt at:#fileName.
-        SourceCodeManagerUtilities lastModule:containerModule.
-        SourceCodeManagerUtilities lastPackage:containerPackage.
-    ] ifFalse:[
-        "/
-        "/ class in repository - ask for revision
-        "/
-        newestRev := mgr newestRevisionOf:currentClass.
-
-        msg := resources string:'Compare to revision: (empty for newest)'.
-        rev notNil ifTrue:[
-            msg := msg , '\\' , (resources string:'Current %1 is based upon rev %2.'
-                                           with:nm allBold with:rev).
-            (rev2 notNil and:[rev2 ~= rev]) ifTrue:[
-                msg := msg , '\' , (resources string:'And has been checked into the repository as %1.' with:rev2)
-            ]
-        ].
-        newestRev notNil ifTrue:[
-            msg := msg , '\' , (resources string:'Newest in reporitory is %1.' with:newestRev)
-        ].
-
-        self normalLabel.
-        rev := manager utilities
-                    askForExistingRevision:msg
-                    title:'Compare with repository'
-                    class:currentClass
+	"/
+	"/ class not in repository - allow compare against any other containers newest contents
+	"/
+	self normalLabel.
+
+	pkg := currentClass package.
+	(pkg notNil and:[pkg ~= PackageId noProjectID]) ifTrue:[
+	    containerModule := pkg upTo:$:.
+	    containerPackage := pkg copyFrom:(containerModule size + 2).
+	].
+	containerModule size == 0 ifTrue:[
+	    containerModule := (SourceCodeManagerUtilities lastModule) ? Project current repositoryModule.
+	].
+	containerPackage size == 0 ifTrue:[
+	    containerPackage := (SourceCodeManagerUtilities lastPackage) ? Project current package.
+	].
+	rslt := manager utilities
+	    askForContainer:(resources string:'The class seems to have no repository information.\\Do you want to compare it against an existing containers contents ?')
+	    title:'Container to compare' note:nil
+	    initialModule:containerModule
+	    initialPackage:containerPackage
+	    initialFileName:(currentClass nameWithoutPrefix , '.st')
+	    forNewContainer:false.
+	rslt isNil ifTrue:[
+	    "/ canel
+	    ^ self
+	].
+	containerModule := rslt at:#module.
+	containerPackage := rslt at:#package.
+	containerFile := rslt at:#fileName.
+	SourceCodeManagerUtilities lastModule:containerModule.
+	SourceCodeManagerUtilities lastPackage:containerPackage.
+    ] ifFalse:[
+	"/
+	"/ class in repository - ask for revision
+	"/
+	newestRev := mgr newestRevisionOf:currentClass.
+
+	msg := resources string:'Compare to revision: (empty for newest)'.
+	rev notNil ifTrue:[
+	    msg := msg , '\\' , (resources string:'Current %1 is based upon rev %2.'
+					   with:nm allBold with:rev).
+	    (rev2 notNil and:[rev2 ~= rev]) ifTrue:[
+		msg := msg , '\' , (resources string:'And has been checked into the repository as %1.' with:rev2)
+	    ]
+	].
+	newestRev notNil ifTrue:[
+	    msg := msg , '\' , (resources string:'Newest in reporitory is %1.' with:newestRev)
+	].
+
+	self normalLabel.
+	rev := manager utilities
+		    askForExistingRevision:msg
+		    title:'Compare with repository'
+		    class:currentClass
     ].
 
     versionsAreTheSame := false.
     (rev notNil or:[containerFile notNil]) ifTrue:[
-        rev notNil ifTrue:[
-            rev withoutSpaces isEmpty ifTrue:[
-                msg := 'extracting newest %1 (' , (newestRev ? '???') , ')'.
-                "/ aStream := mgr getMostRecentSourceStreamForClassNamed:nm.
-                rev := newestRev.
-                revString := 'newest'.
-            ] ifFalse:[
-                msg := 'extracting previous %1'.
-                revString := rev
-            ].
-            aStream := mgr getSourceStreamFor:currentClass revision:rev.
-        ] ifFalse:[
-            msg := 'extracting newest version from ' , containerModule , '/' , containerPackage, '/' , containerFile.
-            aStream := mgr streamForClass:nil fileName:containerFile revision:#newest directory:containerPackage module:containerModule cache:false.
-            revString := '???'
-        ].
-        self busyLabel:msg with:nm.
-
-        aStream isNil ifTrue:[
-            info := mgr sourceInfoOfClass:currentClass.
-            info notNil ifTrue:[
-                mod := info at:#module ifAbsent:'??'.
-                dir := info at:#directory ifAbsent:'??'.
-            ].
-
-            self warn:(resources
-                         string:'Could not extract source from repository (for module: ''%1'' , directory: ''%2'' , revision: ''%3'')'
-                         with:mod with:dir with:revString).
-            ^ self
-        ].
-        aStream class readErrorSignal handle:[:ex |
-            self warn:('read error while reading extracted source\\' , ex description) withCRs.
-            aStream close.
-            ^ self
-        ] do:[
-            comparedSource := aStream contents asString.
-        ].
-        aStream close.
-
-        self busyLabel:'generating current source ...' with:nil.
-
-        aStream := '' writeStream.
-        Method flushSourceStreamCache.
-        "/ currentClass fileOutOn:aStream withTimeStamp:false.
-        "/ currentSource := aStream contents asString.
-
-        Class fileOutErrorSignal handle:[:ex |
-            ex proceed
-        ] do:[
-            currentSource := currentClass source asString.
-        ].
-
-        self busyLabel:'comparing  ...' with:nil.
-        versionsAreTheSame := (comparedSource = currentSource).
-        versionsAreTheSame ifFalse:[
-            thisRevString := currentClass revision.
-            thisRevString isNil ifTrue:[
-                thisRevString := 'no revision'
-            ].
-
-            revString = '(newest)' ifTrue:[
-                (rev := mgr newestRevisionOf:currentClass) notNil ifTrue:[
-                    revString := '(newest is ' , rev , ')'
-                ]
-            ].
-
-            self busyLabel:'comparing  ...' with:nil.
-            (UserPreferences versionDiffViewerClass)
-                  openOnClass:currentClass
-                  labelA:('repository: ' , revString)
-                  sourceA:comparedSource
-                  labelB:('current: (based on: ' , thisRevString , ')')
-                  sourceB:currentSource
-                  title:('comparing ' , currentClass name)
-                  ifSame:[versionsAreTheSame := true].
-        ].
-        versionsAreTheSame ifTrue:[
-            ((currentClass revision = newestRev)
-            and:[currentClass hasUnsavedChanges]) ifTrue:[
-                (self confirm:'Versions are identical.\\Remove entries from changeSet ?' withCRs) ifTrue:[
-                    ChangeSet current condenseChangesForClass:currentClass.
-                ].
-            ] ifFalse:[
-                self information:'Versions are identical.'.
-            ]
-        ].
+	rev notNil ifTrue:[
+	    rev withoutSpaces isEmpty ifTrue:[
+		msg := 'extracting newest %1 (' , (newestRev ? '???') , ')'.
+		"/ aStream := mgr getMostRecentSourceStreamForClassNamed:nm.
+		rev := newestRev.
+		revString := 'newest'.
+	    ] ifFalse:[
+		msg := 'extracting previous %1'.
+		revString := rev
+	    ].
+	    aStream := mgr getSourceStreamFor:currentClass revision:rev.
+	] ifFalse:[
+	    msg := 'extracting newest version from ' , containerModule , '/' , containerPackage, '/' , containerFile.
+	    aStream := mgr streamForClass:nil fileName:containerFile revision:#newest directory:containerPackage module:containerModule cache:false.
+	    revString := '???'
+	].
+	self busyLabel:msg with:nm.
+
+	aStream isNil ifTrue:[
+	    info := mgr sourceInfoOfClass:currentClass.
+	    info notNil ifTrue:[
+		mod := info at:#module ifAbsent:'??'.
+		dir := info at:#directory ifAbsent:'??'.
+	    ].
+
+	    self warn:(resources
+			 string:'Could not extract source from repository (for module: ''%1'' , directory: ''%2'' , revision: ''%3'')'
+			 with:mod with:dir with:revString).
+	    ^ self
+	].
+	aStream class readErrorSignal handle:[:ex |
+	    self warn:('read error while reading extracted source\\' , ex description) withCRs.
+	    aStream close.
+	    ^ self
+	] do:[
+	    comparedSource := aStream contents asString.
+	].
+	aStream close.
+
+	self busyLabel:'generating current source ...' with:nil.
+
+	aStream := '' writeStream.
+	Method flushSourceStreamCache.
+	"/ currentClass fileOutOn:aStream withTimeStamp:false.
+	"/ currentSource := aStream contents asString.
+
+	Class fileOutErrorSignal handle:[:ex |
+	    ex proceed
+	] do:[
+	    currentSource := currentClass source asString.
+	].
+
+	self busyLabel:'comparing  ...' with:nil.
+	versionsAreTheSame := (comparedSource = currentSource).
+	versionsAreTheSame ifFalse:[
+	    thisRevString := currentClass revision.
+	    thisRevString isNil ifTrue:[
+		thisRevString := 'no revision'
+	    ].
+
+	    revString = '(newest)' ifTrue:[
+		(rev := mgr newestRevisionOf:currentClass) notNil ifTrue:[
+		    revString := '(newest is ' , rev , ')'
+		]
+	    ].
+
+	    self busyLabel:'comparing  ...' with:nil.
+	    (UserPreferences versionDiffViewerClass)
+		  openOnClass:currentClass
+		  labelA:('repository: ' , revString)
+		  sourceA:comparedSource
+		  labelB:('current: (based on: ' , thisRevString , ')')
+		  sourceB:currentSource
+		  title:('comparing ' , currentClass name)
+		  ifSame:[versionsAreTheSame := true].
+	].
+	versionsAreTheSame ifTrue:[
+	    ((currentClass revision = newestRev)
+	    and:[currentClass hasUnsavedChanges]) ifTrue:[
+		(self confirm:'Versions are identical.\\Remove entries from changeSet ?' withCRs) ifTrue:[
+		    ChangeSet current condenseChangesForClass:currentClass.
+		].
+	    ] ifFalse:[
+		self information:'Versions are identical.'.
+	    ]
+	].
     ].
     self normalLabel.
 
@@ -31608,58 +32043,58 @@
 
     classesToUnload := IdentitySet new.
     classes :=
-        collectionOfClasses
-            collect:[:eachClass |
-                |loadedClass|
-
-                eachClass isLoaded ifFalse:[
-                    loadedClass := eachClass autoload.
-                    loadedClass notNil ifTrue:[classesToUnload add:loadedClass].
-                ] ifTrue:[
-                    loadedClass := eachClass
-                ].
-                loadedClass isNil
-                    ifTrue:nil
-                    ifFalse:[loadedClass theNonMetaclass]]
-            thenSelect:[:cls | cls notNil].
+	collectionOfClasses
+	    collect:[:eachClass |
+		|loadedClass|
+
+		eachClass isLoaded ifFalse:[
+		    loadedClass := eachClass autoload.
+		    loadedClass notNil ifTrue:[classesToUnload add:loadedClass].
+		] ifTrue:[
+		    loadedClass := eachClass
+		].
+		loadedClass isNil
+		    ifTrue:nil
+		    ifFalse:[loadedClass theNonMetaclass]]
+	    thenSelect:[:cls | cls notNil].
 
     classes do:[:eachClass |
-        |className metaclassName|
-
-        className := eachClass theNonMetaclass name.
-        metaclassName := eachClass theMetaclass name.
-        eachClass isLoaded ifFalse:[
-            Transcript showCR:('Cannot compare unloaded class: ' , eachClass name).
-        ] ifTrue:[
-            self busyLabel:'comparing  ...' with:nil.
-
-            current    := ChangeSet forExistingClass:eachClass theNonMetaclass.
-            remote := (SmallTeam changesOnHost:hostName) select:[:ch | (ch className = className) or:[(ch className = metaclassName)] ].
-
-            diffs := remote diffSetsAgainst:current.
-            allDiffs isNil ifTrue:[
-                allDiffs := diffs.
-            ] ifFalse:[
-                allDiffs changed addAll:(diffs changed).
-                allDiffs onlyInArg addAll:(diffs onlyInArg).
-                allDiffs onlyInReceiver addAll:(diffs onlyInReceiver).
-            ].
-        ].
+	|className metaclassName|
+
+	className := eachClass theNonMetaclass name.
+	metaclassName := eachClass theMetaclass name.
+	eachClass isLoaded ifFalse:[
+	    Transcript showCR:('Cannot compare unloaded class: ' , eachClass name).
+	] ifTrue:[
+	    self busyLabel:'comparing  ...' with:nil.
+
+	    current    := ChangeSet forExistingClass:eachClass theNonMetaclass.
+	    remote := (SmallTeam changesOnHost:hostName) select:[:ch | (ch className = className) or:[(ch className = metaclassName)] ].
+
+	    diffs := remote diffSetsAgainst:current.
+	    allDiffs isNil ifTrue:[
+		allDiffs := diffs.
+	    ] ifFalse:[
+		allDiffs changed addAll:(diffs changed).
+		allDiffs onlyInArg addAll:(diffs onlyInArg).
+		allDiffs onlyInReceiver addAll:(diffs onlyInReceiver).
+	    ].
+	].
     ].
 
     allDiffs isEmpty ifTrue:[
-        self information:'The Versions are Equal.'.
-    ] ifFalse:[
-        title := collectionOfClasses size == 1
-                    ifTrue:['Differences of %1' bindWith:collectionOfClasses first name]
-                    ifFalse:['Differences of %1 classes' bindWith:collectionOfClasses size].
-
-        VersionDiffBrowser
-            openOnDiffSet:allDiffs
-            labelA:'Version on Host ',hostName
-            labelB:'Image'
-            title:title
-            ignoreExtensions:false.
+	self information:'The Versions are Equal.'.
+    ] ifFalse:[
+	title := collectionOfClasses size == 1
+		    ifTrue:['Differences of %1' bindWith:collectionOfClasses first name]
+		    ifFalse:['Differences of %1 classes' bindWith:collectionOfClasses size].
+
+	VersionDiffBrowser
+	    openOnDiffSet:allDiffs
+	    labelA:'Version on Host ',hostName
+	    labelB:'Image'
+	    title:title
+	    ignoreExtensions:false.
     ].
 
     self normalLabel.
@@ -31679,21 +32114,21 @@
 
     currentClass := self theSingleSelectedLoadedNonMetaclassOrNil.
     currentClass isNil ifTrue:[
-        self warn:'Cannot load unloaded classes.'.
-        ^ self.
+	self warn:'Cannot load unloaded classes.'.
+	^ self.
     ].
 
     nm := currentClass name.
     mgr := SourceCodeManagerUtilities default sourceCodeManagerFor:currentClass.
     mgr isNil ifTrue:[
-        ^ self
+	^ self
     ].
 
     self normalLabel.
     rev := SourceCodeManagerUtilities default
-                askForExistingRevision:(resources string:'Edit which revision:')
-                title:(resources string:'Edit which repository version')
-                class:currentClass.
+		askForExistingRevision:(resources string:'Edit which revision:')
+		title:(resources string:'Edit which repository version')
+		class:currentClass.
     rev isNil ifTrue:[^ self].
 
     source := self getClassSourceFor:currentClass revision:rev.
@@ -31745,35 +32180,35 @@
     navigationState realModifiedState:false.
 
     self
-        selectedClassesNonMetaDo:
-            [:cls |
-               self 
-                showRepositoryLogOf:cls short:shortOrNot
-                beforeLogDo:[:s |
-                    self selectedClassesValue size > 1 ifTrue:[
-                        s nextPutLine:'-----------------------------------------------------------'. 
-                        s nextPutLine:('%1 log for %2:' 
-                                            bindWith:(shortOrNot ifTrue:['Short'] ifFalse:['Full']) 
-                                            with:cls name).
-                        s nextPutLine:'-----------------------------------------------------------'. 
-                        s cr. 
-                    ]
-                ]
-            ]
-        ifUnloaded:
-            [:cls |
-                true.
-            ]
-        ifPrivate:
-            [:cls | 
-                |owner|
-                owner := cls owningClass.
-                (self selectedClassesValue includes:owner) ifFalse:[
-                    self warn:'cannot show log of private class: %1\\Please see the log of the owning class (%2).'
-                        with:cls nameWithoutPrefix allBold
-                        with:owner name.
-                ]
-            ].
+	selectedClassesNonMetaDo:
+	    [:cls |
+	       self
+		showRepositoryLogOf:cls short:shortOrNot
+		beforeLogDo:[:s |
+		    self selectedClassesValue size > 1 ifTrue:[
+			s nextPutLine:'-----------------------------------------------------------'.
+			s nextPutLine:('%1 log for %2:'
+					    bindWith:(shortOrNot ifTrue:['Short'] ifFalse:['Full'])
+					    with:cls name).
+			s nextPutLine:'-----------------------------------------------------------'.
+			s cr.
+		    ]
+		]
+	    ]
+	ifUnloaded:
+	    [:cls |
+		true.
+	    ]
+	ifPrivate:
+	    [:cls |
+		|owner|
+		owner := cls owningClass.
+		(self selectedClassesValue includes:owner) ifFalse:[
+		    self warn:'cannot show log of private class: %1\\Please see the log of the owning class (%2).'
+			with:cls nameWithoutPrefix allBold
+			with:owner name.
+		]
+	    ].
     self normalLabel.
 
     "Modified: / 28-02-2012 / 16:47:53 / cg"
@@ -31797,35 +32232,35 @@
     navigationState realModifiedState:false.
 
     self
-        selectedClassesNonMetaDo:
-            [:cls |
-               self 
-                showRepositoryLogOf:cls short:shortOrNot usingManager: manager
-                beforeLogDo:[:s |
-                    self selectedClassesValue size > 1 ifTrue:[
-                        s nextPutLine:'-----------------------------------------------------------'. 
-                        s nextPutLine:('%1 log for %2:' 
-                                            bindWith:(shortOrNot ifTrue:['Short'] ifFalse:['Full']) 
-                                            with:cls name).
-                        s nextPutLine:'-----------------------------------------------------------'. 
-                        s cr. 
-                    ]
-                ]
-            ]
-        ifUnloaded:
-            [:cls |
-                true.
-            ]
-        ifPrivate:
-            [:cls | 
-                |owner|
-                owner := cls owningClass.
-                (self selectedClassesValue includes:owner) ifFalse:[
-                    self warn:'cannot show log of private class: %1\\Please see the log of the owning class (%2).'
-                        with:cls nameWithoutPrefix allBold
-                        with:owner name.
-                ]
-            ].
+	selectedClassesNonMetaDo:
+	    [:cls |
+	       self
+		showRepositoryLogOf:cls short:shortOrNot usingManager: manager
+		beforeLogDo:[:s |
+		    self selectedClassesValue size > 1 ifTrue:[
+			s nextPutLine:'-----------------------------------------------------------'.
+			s nextPutLine:('%1 log for %2:'
+					    bindWith:(shortOrNot ifTrue:['Short'] ifFalse:['Full'])
+					    with:cls name).
+			s nextPutLine:'-----------------------------------------------------------'.
+			s cr.
+		    ]
+		]
+	    ]
+	ifUnloaded:
+	    [:cls |
+		true.
+	    ]
+	ifPrivate:
+	    [:cls |
+		|owner|
+		owner := cls owningClass.
+		(self selectedClassesValue includes:owner) ifFalse:[
+		    self warn:'cannot show log of private class: %1\\Please see the log of the owning class (%2).'
+			with:cls nameWithoutPrefix allBold
+			with:owner name.
+		]
+	    ].
     self normalLabel.
 
     "Created: / 11-10-2011 / 20:32:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -31855,31 +32290,31 @@
 
     classes := self selectedNonMetaclasses.
 
-    ((classes size <= 10) 
-        or:[ |answer|
-             answer := Dialog 
-                        confirmWithCancel:'Fetch known tags to choose from all classes?\(this may take some time)' withCRs
-                        default:false.
-             answer isNil ifTrue:[^ self].
-             answer == true
-           ]
+    ((classes size <= 10)
+	or:[ |answer|
+	     answer := Dialog
+			confirmWithCancel:'Fetch known tags to choose from all classes?\(this may take some time)' withCRs
+			default:false.
+	     answer isNil ifTrue:[^ self].
+	     answer == true
+	   ]
     ) ifTrue:[
-        "/ fetch from all classes
-        knownTags := self allKnownTagsInClasses:classes.
-    ] ifFalse:[
-        "/ only fetch from ProjectDefinitionClasses
-        knownTags := self allKnownTagsInClasses:(classes select:[:cls | cls isProjectDefinition]).
-    ].
-
-    tag := Dialog 
-                request:(resources string:'Tag:')
-                initialAnswer:LastTag  
-                list:knownTags.  
+	"/ fetch from all classes
+	knownTags := self allKnownTagsInClasses:classes.
+    ] ifFalse:[
+	"/ only fetch from ProjectDefinitionClasses
+	knownTags := self allKnownTagsInClasses:(classes select:[:cls | cls isProjectDefinition]).
+    ].
+
+    tag := Dialog
+		request:(resources string:'Tag:')
+		initialAnswer:LastTag
+		list:knownTags.
     tag isEmptyOrNil ifTrue:[^ self ].
 
     LastTag := tag.
     self withWaitCursorDo:[
-        SourceCodeManagerUtilities tagClasses:classes as:tag.
+	SourceCodeManagerUtilities tagClasses:classes as:tag.
     ]
 
     "Created: / 12-09-2006 / 13:36:59 / cg"
@@ -31933,8 +32368,8 @@
     |utilities|
 
     utilities := aManagerOrNil isNil
-                    ifTrue:[SourceCodeManagerUtilities default]
-                    ifFalse:[aManagerOrNil utilities].
+		    ifTrue:[SourceCodeManagerUtilities default]
+		    ifFalse:[aManagerOrNil utilities].
 
     utilities compareClassWithRepository:aClass askForRevision:false.
     self normalLabel.
@@ -31958,112 +32393,112 @@
      title|
 
     collectionOfClasses size == 1 ifTrue:[
-        self compareAgainstNewestInRepository:(collectionOfClasses first theNonMetaclass) usingManager:aManagerOrNil.
-        ^ self.
+	self compareAgainstNewestInRepository:(collectionOfClasses first theNonMetaclass) usingManager:aManagerOrNil.
+	^ self.
     ].
 
     classesToUnload := IdentitySet new.
     classes :=
-        collectionOfClasses
-            collect:[:eachClass |
-                |loadedClass|
-
-                eachClass isLoaded ifFalse:[
-                    loadedClass := eachClass autoload.
-                    loadedClass notNil ifTrue:[classesToUnload add:loadedClass].
-                ] ifTrue:[
-                    loadedClass := eachClass
-                ].
-                loadedClass isNil
-                    ifTrue:nil
-                    ifFalse:[loadedClass theNonMetaclass]]
-            thenSelect:[:cls | cls notNil].
+	collectionOfClasses
+	    collect:[:eachClass |
+		|loadedClass|
+
+		eachClass isLoaded ifFalse:[
+		    loadedClass := eachClass autoload.
+		    loadedClass notNil ifTrue:[classesToUnload add:loadedClass].
+		] ifTrue:[
+		    loadedClass := eachClass
+		].
+		loadedClass isNil
+		    ifTrue:nil
+		    ifFalse:[loadedClass theNonMetaclass]]
+	    thenSelect:[:cls | cls notNil].
 
     classes do:[:eachClass |
-        eachClass isLoaded ifFalse:[
-            Transcript showCR:('Cannot compare unloaded class: ' , eachClass name).
-        ] ifTrue:[
-            aStream := self sourceStreamForRepositorySourceOfClass:eachClass usingManager:aManagerOrNil.
-            aStream notNil ifTrue:[
-                aStream class readErrorSignal handle:[:ex |
-                    self warn:('read error while reading extracted source\\' , ex description) withCRs.
-                    aStream close.
-                    ^ self
-                ] do:[
-                    comparedSource := aStream contents asString.
-                ].
-                aStream close.
-
-                self busyLabel:'generating current source ...' with:nil.
-
-                aStream := '' writeStream.
-                Method flushSourceStreamCache.
-                "/ eachClass fileOutOn:aStream withTimeStamp:false.
-                "/ currentSource := aStream contents asString.
-                currentSource := eachClass source asString.
-                aStream close.
-
-                self busyLabel:'comparing  ...' with:nil.
-
-                comparedSource = currentSource ifTrue:[
-                    ((eachClass revision = ((aManagerOrNil ? eachClass sourceCodeManager) newestRevisionOf:eachClass))
-                    and:[eachClass hasUnsavedChanges]) ifTrue:[
-                        (self confirm:'Versions are identical.\\Remove entries from changeSet ?' withCRs) ifTrue:[
-                            ChangeSet current condenseChangesForClass:eachClass.
-                        ].
-                    ] ifFalse:[
-                        self information:'Versions are identical.'.
-                    ]
-                ] ifFalse:[
-                    thisRevString := eachClass revision.
-                    thisRevString isNil ifTrue:[
-                        thisRevString := 'no revision'
-                    ].
-
-                    self busyLabel:'comparing  ...' with:nil.
-
-                    current    := ChangeSet fromStream:(s := currentSource readStream). s close.
-                    repository := ChangeSet fromStream:(s := comparedSource readStream). s close.
-
-                    diffs := repository diffSetsAgainst:current.
-                    allDiffs isNil ifTrue:[
-                        allDiffs := diffs.
-                    ] ifFalse:[
-                        allDiffs changed addAll:(diffs changed).
-                        allDiffs onlyInArg addAll:(diffs onlyInArg).
-                        allDiffs onlyInReceiver addAll:(diffs onlyInReceiver).
-                    ].
-                ].
-            ].
-        ].
+	eachClass isLoaded ifFalse:[
+	    Transcript showCR:('Cannot compare unloaded class: ' , eachClass name).
+	] ifTrue:[
+	    aStream := self sourceStreamForRepositorySourceOfClass:eachClass usingManager:aManagerOrNil.
+	    aStream notNil ifTrue:[
+		aStream class readErrorSignal handle:[:ex |
+		    self warn:('read error while reading extracted source\\' , ex description) withCRs.
+		    aStream close.
+		    ^ self
+		] do:[
+		    comparedSource := aStream contents asString.
+		].
+		aStream close.
+
+		self busyLabel:'generating current source ...' with:nil.
+
+		aStream := '' writeStream.
+		Method flushSourceStreamCache.
+		"/ eachClass fileOutOn:aStream withTimeStamp:false.
+		"/ currentSource := aStream contents asString.
+		currentSource := eachClass source asString.
+		aStream close.
+
+		self busyLabel:'comparing  ...' with:nil.
+
+		comparedSource = currentSource ifTrue:[
+		    ((eachClass revision = ((aManagerOrNil ? eachClass sourceCodeManager) newestRevisionOf:eachClass))
+		    and:[eachClass hasUnsavedChanges]) ifTrue:[
+			(self confirm:'Versions are identical.\\Remove entries from changeSet ?' withCRs) ifTrue:[
+			    ChangeSet current condenseChangesForClass:eachClass.
+			].
+		    ] ifFalse:[
+			self information:'Versions are identical.'.
+		    ]
+		] ifFalse:[
+		    thisRevString := eachClass revision.
+		    thisRevString isNil ifTrue:[
+			thisRevString := 'no revision'
+		    ].
+
+		    self busyLabel:'comparing  ...' with:nil.
+
+		    current    := ChangeSet fromStream:(s := currentSource readStream). s close.
+		    repository := ChangeSet fromStream:(s := comparedSource readStream). s close.
+
+		    diffs := repository diffSetsAgainst:current.
+		    allDiffs isNil ifTrue:[
+			allDiffs := diffs.
+		    ] ifFalse:[
+			allDiffs changed addAll:(diffs changed).
+			allDiffs onlyInArg addAll:(diffs onlyInArg).
+			allDiffs onlyInReceiver addAll:(diffs onlyInReceiver).
+		    ].
+		].
+	    ].
+	].
     ].
 
     allDiffs isEmpty ifTrue:[
-        (classes contains:[:someClass |
-            (someClass hasUnsavedChanges)])
-        ifTrue:[
-            (self confirm:(resources
-                            stringWithCRs:'The classes are up-to-date.\\Remove entries from changeSet ?'))
-            ifTrue:[
-                classes do:[:eachClass |
-                    ChangeSet current condenseChangesForClass:eachClass.
-                ]
-            ].
-        ] ifFalse:[
-            self information:'The classes are up-to-date.'.
-            ChangeSet current unrememberChangedClasses.
-        ].
-    ] ifFalse:[
-        title := collectionOfClasses size == 1
-                    ifTrue:['Differences of %1' bindWith:collectionOfClasses first name]
-                    ifFalse:['Differences of %1 classes' bindWith:collectionOfClasses size].
-
-        VersionDiffBrowser
-            openOnDiffSet:allDiffs
-            labelA:'Repository'
-            labelB:'Image'
-            title:title
-            ignoreExtensions:true.
+	(classes contains:[:someClass |
+	    (someClass hasUnsavedChanges)])
+	ifTrue:[
+	    (self confirm:(resources
+			    stringWithCRs:'The classes are up-to-date.\\Remove entries from changeSet ?'))
+	    ifTrue:[
+		classes do:[:eachClass |
+		    ChangeSet current condenseChangesForClass:eachClass.
+		]
+	    ].
+	] ifFalse:[
+	    self information:'The classes are up-to-date.'.
+	    ChangeSet current unrememberChangedClasses.
+	].
+    ] ifFalse:[
+	title := collectionOfClasses size == 1
+		    ifTrue:['Differences of %1' bindWith:collectionOfClasses first name]
+		    ifFalse:['Differences of %1 classes' bindWith:collectionOfClasses size].
+
+	VersionDiffBrowser
+	    openOnDiffSet:allDiffs
+	    labelA:'Repository'
+	    labelB:'Image'
+	    title:title
+	    ignoreExtensions:true.
     ].
 
     self normalLabel.
@@ -32084,171 +32519,171 @@
 
     classesToUnload := IdentitySet new.
     classes := collectionOfClasses collect:[:eachClass |
-        |loadedClass|
-
-        eachClass isLoaded ifFalse:[
-            loadedClass := eachClass autoload.
-            classesToUnload add:loadedClass.
-        ] ifTrue:[
-            loadedClass := eachClass
-        ].
-        loadedClass theNonMetaclass
+	|loadedClass|
+
+	eachClass isLoaded ifFalse:[
+	    loadedClass := eachClass autoload.
+	    classesToUnload add:loadedClass.
+	] ifTrue:[
+	    loadedClass := eachClass
+	].
+	loadedClass theNonMetaclass
 
     ].
 
     classes do:[:currentClass |
-        nm := currentClass name.
-        mgr := SourceCodeManagerUtilities default sourceCodeManagerFor:currentClass.
-        mgr isNil ifTrue:[
-            (Dialog
-                confirm:('No sourceCode manager defined for %1 - check settings.\\Skip this class ?' bindWith:currentClass name) withCRs)
-            ifFalse:[
-                ^ self
-            ].
-        ].
-        rev := currentClass binaryRevision.
-        rev isNil ifTrue:[
-            rev := currentClass revision
-        ].
-        rev isNil ifTrue:[
-            "/
-            "/ class not in repository - allow compare against any other containers newest contents
-            "/
-            self normalLabel.
-
-            pkg := currentClass package.
-            (pkg notNil and:[pkg ~= PackageId noProjectID]) ifTrue:[
-                containerModule := pkg upTo:$:.
-                containerPackage := pkg copyFrom:(containerModule size + 2).
-            ].
-            containerModule size == 0 ifTrue:[
-                containerModule := (SourceCodeManagerUtilities lastModule) ? Project current repositoryModule.
-            ].
-            containerPackage size == 0 ifTrue:[
-                containerPackage := (SourceCodeManagerUtilities lastPackage) ? Project current package.
-            ].
-            rslt := SourceCodeManagerUtilities default
-                askForContainer:(resources string:'The class seems to have no repository information.\\Do you want to compare it against an existing containers contents ?')
-                title:'Container to compare' note:nil
-                initialModule:containerModule
-                initialPackage:containerPackage
-                initialFileName:(currentClass name , '.st')
-                forNewContainer:false.
-            rslt isNil ifTrue:[
-                "/ canel
-                ^ self
-            ].
-            containerModule := rslt at:#module.
-            containerPackage := rslt at:#package.
-            containerFile := rslt at:#fileName.
-            SourceCodeManagerUtilities lastModule:containerModule.
-            SourceCodeManagerUtilities lastPackage:containerPackage.
-        ] ifFalse:[
-            "/
-            "/ class in repository - ask for revision
-            "/
-            newestRev := mgr newestRevisionOf:currentClass.
-            rev := newestRev.
-        ].
-
-        (rev notNil or:[containerFile notNil]) ifTrue:[
-            rev notNil ifTrue:[
-                rev withoutSpaces isEmpty ifTrue:[
-                    msg := 'extracting newest %1 (' , (newestRev ? '???') , ')'.
-                    "/ aStream := mgr getMostRecentSourceStreamForClassNamed:nm.
-                    aStream := mgr getSourceStreamFor:currentClass revision:newestRev.
-                    revString := 'newest'.
-                ] ifFalse:[
-                    msg := 'extracting previous %1'.
-                    aStream := mgr getSourceStreamFor:currentClass revision:rev.
-                    revString := rev
-                ].
-            ] ifFalse:[
-                msg := 'extracting newest version from ' , containerModule , '/' , containerPackage, '/' , containerFile.
-                aStream := mgr streamForClass:nil fileName:containerFile revision:#newest directory:containerPackage module:containerModule cache:false.
-                revString := '???'
-            ].
-            self busyLabel:msg with:nm.
-
-            aStream isNil ifTrue:[
-                info := mgr sourceInfoOfClass:currentClass.
-                info notNil ifTrue:[
-                    mod := info at:#module ifAbsent:'??'.
-                    dir := info at:#directory ifAbsent:'??'.
-                ].
-
-                self warn:(resources
-                             string:'Could not extract source from repository (for module: ''%1'' , directory: ''%2'' , revision: ''%3'')'
-                             with:mod with:dir with:revString).
-                ^ self
-            ].
-            aStream class readErrorSignal handle:[:ex |
-                self warn:('read error while reading extracted source\\' , ex description) withCRs.
-                aStream close.
-                ^ self
-            ] do:[
-                comparedSource := aStream contents asString.
-            ].
-            aStream close.
-
-            self busyLabel:'generating current source ...' with:nil.
-
-            aStream := '' writeStream.
-            Method flushSourceStreamCache.
-            "/ currentClass fileOutOn:aStream withTimeStamp:false.
-            "/ currentSource := aStream contents asString.
-            currentSource := currentClass source asString.
-            aStream close.
-
-            self busyLabel:'comparing  ...' with:nil.
-
-            comparedSource = currentSource ifTrue:[
-                ((currentClass revision = newestRev)
-                and:[currentClass hasUnsavedChanges]) ifTrue:[
-                    (self confirm:'Versions are identical.\\Remove entries from changeSet ?' withCRs) ifTrue:[
-                        ChangeSet current condenseChangesForClass:currentClass.
-                    ].
-                ] ifFalse:[
-                    self information:'Versions are identical.'.
-                ]
-            ] ifFalse:[
-                thisRevString := currentClass revision.
-                thisRevString isNil ifTrue:[
-                    thisRevString := 'no revision'
-                ].
-
-                revString = '(newest)' ifTrue:[
-                    (rev := mgr newestRevisionOf:currentClass) notNil ifTrue:[
-                        revString := '(newest is ' , rev , ')'
-                    ]
-                ].
-
-                self busyLabel:'comparing  ...' with:nil.
-
-                current    := ChangeSet fromStream:(s := currentSource readStream). s close.
-                repository := ChangeSet fromStream:(s := comparedSource readStream). s close.
-                diffs := repository diffSetsAgainst:current.
-                allDiffs isNil ifTrue:[
-                    allDiffs := diffs.
-                ] ifFalse:[
-                    allDiffs changed addAll:(diffs changed).
-                    allDiffs onlyInArg addAll:(diffs onlyInArg).
-                    allDiffs onlyInReceiver addAll:(diffs onlyInReceiver).
-                ].
-            ].
-        ].
+	nm := currentClass name.
+	mgr := SourceCodeManagerUtilities default sourceCodeManagerFor:currentClass.
+	mgr isNil ifTrue:[
+	    (Dialog
+		confirm:('No sourceCode manager defined for %1 - check settings.\\Skip this class ?' bindWith:currentClass name) withCRs)
+	    ifFalse:[
+		^ self
+	    ].
+	].
+	rev := currentClass binaryRevision.
+	rev isNil ifTrue:[
+	    rev := currentClass revision
+	].
+	rev isNil ifTrue:[
+	    "/
+	    "/ class not in repository - allow compare against any other containers newest contents
+	    "/
+	    self normalLabel.
+
+	    pkg := currentClass package.
+	    (pkg notNil and:[pkg ~= PackageId noProjectID]) ifTrue:[
+		containerModule := pkg upTo:$:.
+		containerPackage := pkg copyFrom:(containerModule size + 2).
+	    ].
+	    containerModule size == 0 ifTrue:[
+		containerModule := (SourceCodeManagerUtilities lastModule) ? Project current repositoryModule.
+	    ].
+	    containerPackage size == 0 ifTrue:[
+		containerPackage := (SourceCodeManagerUtilities lastPackage) ? Project current package.
+	    ].
+	    rslt := SourceCodeManagerUtilities default
+		askForContainer:(resources string:'The class seems to have no repository information.\\Do you want to compare it against an existing containers contents ?')
+		title:'Container to compare' note:nil
+		initialModule:containerModule
+		initialPackage:containerPackage
+		initialFileName:(currentClass name , '.st')
+		forNewContainer:false.
+	    rslt isNil ifTrue:[
+		"/ canel
+		^ self
+	    ].
+	    containerModule := rslt at:#module.
+	    containerPackage := rslt at:#package.
+	    containerFile := rslt at:#fileName.
+	    SourceCodeManagerUtilities lastModule:containerModule.
+	    SourceCodeManagerUtilities lastPackage:containerPackage.
+	] ifFalse:[
+	    "/
+	    "/ class in repository - ask for revision
+	    "/
+	    newestRev := mgr newestRevisionOf:currentClass.
+	    rev := newestRev.
+	].
+
+	(rev notNil or:[containerFile notNil]) ifTrue:[
+	    rev notNil ifTrue:[
+		rev withoutSpaces isEmpty ifTrue:[
+		    msg := 'extracting newest %1 (' , (newestRev ? '???') , ')'.
+		    "/ aStream := mgr getMostRecentSourceStreamForClassNamed:nm.
+		    aStream := mgr getSourceStreamFor:currentClass revision:newestRev.
+		    revString := 'newest'.
+		] ifFalse:[
+		    msg := 'extracting previous %1'.
+		    aStream := mgr getSourceStreamFor:currentClass revision:rev.
+		    revString := rev
+		].
+	    ] ifFalse:[
+		msg := 'extracting newest version from ' , containerModule , '/' , containerPackage, '/' , containerFile.
+		aStream := mgr streamForClass:nil fileName:containerFile revision:#newest directory:containerPackage module:containerModule cache:false.
+		revString := '???'
+	    ].
+	    self busyLabel:msg with:nm.
+
+	    aStream isNil ifTrue:[
+		info := mgr sourceInfoOfClass:currentClass.
+		info notNil ifTrue:[
+		    mod := info at:#module ifAbsent:'??'.
+		    dir := info at:#directory ifAbsent:'??'.
+		].
+
+		self warn:(resources
+			     string:'Could not extract source from repository (for module: ''%1'' , directory: ''%2'' , revision: ''%3'')'
+			     with:mod with:dir with:revString).
+		^ self
+	    ].
+	    aStream class readErrorSignal handle:[:ex |
+		self warn:('read error while reading extracted source\\' , ex description) withCRs.
+		aStream close.
+		^ self
+	    ] do:[
+		comparedSource := aStream contents asString.
+	    ].
+	    aStream close.
+
+	    self busyLabel:'generating current source ...' with:nil.
+
+	    aStream := '' writeStream.
+	    Method flushSourceStreamCache.
+	    "/ currentClass fileOutOn:aStream withTimeStamp:false.
+	    "/ currentSource := aStream contents asString.
+	    currentSource := currentClass source asString.
+	    aStream close.
+
+	    self busyLabel:'comparing  ...' with:nil.
+
+	    comparedSource = currentSource ifTrue:[
+		((currentClass revision = newestRev)
+		and:[currentClass hasUnsavedChanges]) ifTrue:[
+		    (self confirm:'Versions are identical.\\Remove entries from changeSet ?' withCRs) ifTrue:[
+			ChangeSet current condenseChangesForClass:currentClass.
+		    ].
+		] ifFalse:[
+		    self information:'Versions are identical.'.
+		]
+	    ] ifFalse:[
+		thisRevString := currentClass revision.
+		thisRevString isNil ifTrue:[
+		    thisRevString := 'no revision'
+		].
+
+		revString = '(newest)' ifTrue:[
+		    (rev := mgr newestRevisionOf:currentClass) notNil ifTrue:[
+			revString := '(newest is ' , rev , ')'
+		    ]
+		].
+
+		self busyLabel:'comparing  ...' with:nil.
+
+		current    := ChangeSet fromStream:(s := currentSource readStream). s close.
+		repository := ChangeSet fromStream:(s := comparedSource readStream). s close.
+		diffs := repository diffSetsAgainst:current.
+		allDiffs isNil ifTrue:[
+		    allDiffs := diffs.
+		] ifFalse:[
+		    allDiffs changed addAll:(diffs changed).
+		    allDiffs onlyInArg addAll:(diffs onlyInArg).
+		    allDiffs onlyInReceiver addAll:(diffs onlyInReceiver).
+		].
+	    ].
+	].
     ].
 
     title := collectionOfClasses size == 1
-                ifTrue:['Differences of %1' bindWith:collectionOfClasses first name]
-                ifFalse:['Differences of %1 classes' bindWith:collectionOfClasses size].
+		ifTrue:['Differences of %1' bindWith:collectionOfClasses first name]
+		ifFalse:['Differences of %1 classes' bindWith:collectionOfClasses size].
 
     VersionDiffBrowser
-        openOnDiffSet:allDiffs
-        labelA:'Repository'
-        labelB:'Image'
-        title:title
-        ignoreExtensions:true.
+	openOnDiffSet:allDiffs
+	labelA:'Repository'
+	labelB:'Image'
+	title:title
+	ignoreExtensions:true.
 
     self normalLabel.
 
@@ -32266,17 +32701,17 @@
 
     stream := aClass sourceCodeManager getSourceStreamFor:aClass revision:revision.
     stream isNil ifTrue:[
-        self warn:(resources
-                     string:'Could not extract source of rev %1 from repository'
-                    with:revision).
-        ^ nil
+	self warn:(resources
+		     string:'Could not extract source of rev %1 from repository'
+		    with:revision).
+	^ nil
     ].
     stream class readErrorSignal handle:[:ex |
-        self warn:('read error while reading extracted source\\' , ex description) withCRs.
-        stream close.
-        ^ nil
+	self warn:('read error while reading extracted source\\' , ex description) withCRs.
+	stream close.
+	^ nil
     ] do:[
-        source := stream contents asString.
+	source := stream contents asString.
     ].
     stream close.
     ^ source
@@ -32294,17 +32729,17 @@
 
     stream := manager getSourceStreamFor:aClass revision:revision.
     stream isNil ifTrue:[
-        self warn:(resources
-                     string:'Could not extract source of rev %1 from repository'
-                    with:revision).
-        ^ nil
+	self warn:(resources
+		     string:'Could not extract source of rev %1 from repository'
+		    with:revision).
+	^ nil
     ].
     stream class readErrorSignal handle:[:ex |
-        self warn:('read error while reading extracted source\\' , ex description) withCRs.
-        stream close.
-        ^ nil
+	self warn:('read error while reading extracted source\\' , ex description) withCRs.
+	stream close.
+	^ nil
     ] do:[
-        source := stream contents asString.
+	source := stream contents asString.
     ].
     stream close.
     ^ source
@@ -32318,138 +32753,138 @@
      ifFalse:[^ self].
 
     self withWaitCursorDo:[
-        |timeGoal moduleFilter moduleFilterHolder repositoryFilter userFilter aStream box y component
-         timeGoalListPop moduleFilterPop userFilterPop dateList userList|
-
-        timeGoal := 'yesterday' asValue.
-        moduleFilterHolder := nil asValue.
-        userFilter := nil asValue.
-
-        box := Dialog new.
-        (box addTextLabel:(resources string:'Repository change report')) adjust:#left.
-        box addVerticalSpace:20.
-
-        y := box yPosition.
-        component := box addTextLabel:(resources string:'List changes since (yyyy-mm-dd):').
-        component width:0.5; adjust:#right; borderWidth:0.
-        box yPosition:y.
-        timeGoalListPop := box addComboBoxOn:timeGoal tabable:true.
-        timeGoalListPop width:0.5; left:0.5; immediateAccept:true; acceptOnLeave:false; cursorMovementWhenUpdating:#beginOfLine.
-
-        dateList := OrderedCollection new.
-        dateList add:(Timestamp now printStringFormat:'%(year)-%(month)-%(day)').
-        dateList add:((Timestamp now subtractHours:1) printStringFormat:'%(year)-%(month)-%(day) %h:%m').
-        dateList addAll:#('yesterday'
-                          '1 hour ago'
-                          '1 week ago'
-                          '1 month ago'
-                          '1 year ago'
-                          'all'
-                         ).
-
-        timeGoalListPop list:dateList.
-
-        projectListOrNil notNil ifTrue:[
-            moduleFilter := (projectListOrNil collect:[:prj | prj asPackageId module]) asSet.
-            moduleFilterHolder := nil.
-        ] ifFalse:[
-            y := box yPosition.
-            component := box addTextLabel:(resources string:'For CVS repository (empty for all):').
-            component width:0.5; adjust:#right; borderWidth:0.
-            box yPosition:y.
-            moduleFilterPop := box addComboBoxOn:moduleFilterHolder tabable:true.
-            moduleFilterPop width:0.5; left:0.5; immediateAccept:true; acceptOnLeave:false; cursorMovementWhenUpdating:#beginOfLine.
-            moduleFilterPop list:(SourceCodeManager knownModules asOrderedCollection sort addFirst:'stx'; yourself).
-        ].
-
-        y := box yPosition.
-        component := box addTextLabel:(resources string:'For user (empty for all):').
-        component width:0.5; adjust:#right; borderWidth:0.
-        box yPosition:y.
-        userFilterPop := box addComboBoxOn:userFilter tabable:true.
-        userFilterPop width:0.5; left:0.5; immediateAccept:true; acceptOnLeave:false; cursorMovementWhenUpdating:#beginOfLine.
-
-        "Fetch the list of konwn user names (which are possibly used when cheking in):
-            - Try the repository names (smething like ':method:user@host:....')
-            - If nothing found, use the login name"
-
-        userList := Set new.
-        SourceCodeManager knownRepositories do:[:eachRepository|
-            |user idx|
-
-            (eachRepository includes:$@) ifTrue:[
-                user := eachRepository copyUpTo:$@.
-                idx := user lastIndexOf:$:.
-                idx ~~ 0 ifTrue:[
-                    user := user copyFrom:idx+1.
-                ].
-                userList add:user.
-            ].
-        ].
-        userList isEmpty ifTrue:[
-            userList add:OperatingSystem getLoginName.
-        ].
-
-        userFilterPop list:userList asArray sort.
-
-        box addAbortAndOkButtons.
-        box open.
-
-        box accepted ifTrue:[
-            moduleFilterHolder notNil ifTrue:[
-                moduleFilter := moduleFilterHolder value.
-                moduleFilter size == 0
-                    ifTrue:[moduleFilter := nil]
-                    ifFalse:[moduleFilter := Set with:moduleFilter].
-            ].
-
-            moduleFilter notNil ifTrue:[
-                repositoryFilter := moduleFilter
-                                        collect:[:eachModule|
-                                            SourceCodeManager getCVSROOTForModule:eachModule.
-                                        ].
-            ].
-
-            userFilter := userFilter value.
-            userFilter size == 0
-                ifTrue:[userFilter := nil]
-                ifFalse:[userFilter := Array with:userFilter].
-
-            timeGoal := timeGoal value.
-
-            self busyLabel:'extracting history ...' with:nil.
-
-            aStream := WriteStream on:(String new:200).
-            Processor activeProcess
-                withPriority:Processor activePriority-1 to:Processor activePriority
-            do:[
-                SourceCodeManager notNil ifTrue:[
-                    SourceCodeManager
-                        writeHistoryLogSince:timeGoal
-                        filterSTSources:true
-                        filterUser:userFilter
-                        filterRepository:repositoryFilter
-                        filterModules:moduleFilter
-                        filterProjects:projectListOrNil
-                        to:aStream.
-                ] ifFalse:[
-                    aStream nextPutLine:'no history available (no SourceCodeManagement installed)'
-                ].
-            ].
-            self codeView
-                contents:(aStream contents);
-                modified:false.
-            navigationState realModifiedState:false.
-
-            self codeAspect:#repositoryHistory.
-            self selectedMethods value:nil.
-            self selectProtocols:nil.
+	|timeGoal moduleFilter moduleFilterHolder repositoryFilter userFilter aStream box y component
+	 timeGoalListPop moduleFilterPop userFilterPop dateList userList|
+
+	timeGoal := 'yesterday' asValue.
+	moduleFilterHolder := nil asValue.
+	userFilter := nil asValue.
+
+	box := Dialog new.
+	(box addTextLabel:(resources string:'Repository change report')) adjust:#left.
+	box addVerticalSpace:20.
+
+	y := box yPosition.
+	component := box addTextLabel:(resources string:'List changes since (yyyy-mm-dd):').
+	component width:0.5; adjust:#right; borderWidth:0.
+	box yPosition:y.
+	timeGoalListPop := box addComboBoxOn:timeGoal tabable:true.
+	timeGoalListPop width:0.5; left:0.5; immediateAccept:true; acceptOnLeave:false; cursorMovementWhenUpdating:#beginOfLine.
+
+	dateList := OrderedCollection new.
+	dateList add:(Timestamp now printStringFormat:'%(year)-%(month)-%(day)').
+	dateList add:((Timestamp now subtractHours:1) printStringFormat:'%(year)-%(month)-%(day) %h:%m').
+	dateList addAll:#('yesterday'
+			  '1 hour ago'
+			  '1 week ago'
+			  '1 month ago'
+			  '1 year ago'
+			  'all'
+			 ).
+
+	timeGoalListPop list:dateList.
+
+	projectListOrNil notNil ifTrue:[
+	    moduleFilter := (projectListOrNil collect:[:prj | prj asPackageId module]) asSet.
+	    moduleFilterHolder := nil.
+	] ifFalse:[
+	    y := box yPosition.
+	    component := box addTextLabel:(resources string:'For CVS repository (empty for all):').
+	    component width:0.5; adjust:#right; borderWidth:0.
+	    box yPosition:y.
+	    moduleFilterPop := box addComboBoxOn:moduleFilterHolder tabable:true.
+	    moduleFilterPop width:0.5; left:0.5; immediateAccept:true; acceptOnLeave:false; cursorMovementWhenUpdating:#beginOfLine.
+	    moduleFilterPop list:(SourceCodeManager knownModules asOrderedCollection sort addFirst:'stx'; yourself).
+	].
+
+	y := box yPosition.
+	component := box addTextLabel:(resources string:'For user (empty for all):').
+	component width:0.5; adjust:#right; borderWidth:0.
+	box yPosition:y.
+	userFilterPop := box addComboBoxOn:userFilter tabable:true.
+	userFilterPop width:0.5; left:0.5; immediateAccept:true; acceptOnLeave:false; cursorMovementWhenUpdating:#beginOfLine.
+
+	"Fetch the list of konwn user names (which are possibly used when cheking in):
+	    - Try the repository names (smething like ':method:user@host:....')
+	    - If nothing found, use the login name"
+
+	userList := Set new.
+	SourceCodeManager knownRepositories do:[:eachRepository|
+	    |user idx|
+
+	    (eachRepository includes:$@) ifTrue:[
+		user := eachRepository copyUpTo:$@.
+		idx := user lastIndexOf:$:.
+		idx ~~ 0 ifTrue:[
+		    user := user copyFrom:idx+1.
+		].
+		userList add:user.
+	    ].
+	].
+	userList isEmpty ifTrue:[
+	    userList add:OperatingSystem getLoginName.
+	].
+
+	userFilterPop list:userList asArray sort.
+
+	box addAbortAndOkButtons.
+	box open.
+
+	box accepted ifTrue:[
+	    moduleFilterHolder notNil ifTrue:[
+		moduleFilter := moduleFilterHolder value.
+		moduleFilter size == 0
+		    ifTrue:[moduleFilter := nil]
+		    ifFalse:[moduleFilter := Set with:moduleFilter].
+	    ].
+
+	    moduleFilter notNil ifTrue:[
+		repositoryFilter := moduleFilter
+					collect:[:eachModule|
+					    SourceCodeManager getCVSROOTForModule:eachModule.
+					].
+	    ].
+
+	    userFilter := userFilter value.
+	    userFilter size == 0
+		ifTrue:[userFilter := nil]
+		ifFalse:[userFilter := Array with:userFilter].
+
+	    timeGoal := timeGoal value.
+
+	    self busyLabel:'extracting history ...' with:nil.
+
+	    aStream := WriteStream on:(String new:200).
+	    Processor activeProcess
+		withPriority:Processor activePriority-1 to:Processor activePriority
+	    do:[
+		SourceCodeManager notNil ifTrue:[
+		    SourceCodeManager
+			writeHistoryLogSince:timeGoal
+			filterSTSources:true
+			filterUser:userFilter
+			filterRepository:repositoryFilter
+			filterModules:moduleFilter
+			filterProjects:projectListOrNil
+			to:aStream.
+		] ifFalse:[
+		    aStream nextPutLine:'no history available (no SourceCodeManagement installed)'
+		].
+	    ].
+	    self codeView
+		contents:(aStream contents);
+		modified:false.
+	    navigationState realModifiedState:false.
+
+	    self codeAspect:#repositoryHistory.
+	    self selectedMethods value:nil.
+	    self selectProtocols:nil.
 
 "/            self clearAcceptAction.
 "/            self clearExplainAction.
 
-            self normalLabel
-        ].
+	    self normalLabel
+	].
     ]
 
     "Created: / 12-09-2006 / 15:03:24 / cg"
@@ -32458,7 +32893,7 @@
 showRepositoryLogOf:aClass
     "show a classes repository log - append to codeView.
      CAVEAT: that is almost the same code as found in SystemBrowser;
-             move to SourceCodeManagerUtilities"
+	     move to SourceCodeManagerUtilities"
 
     self showRepositoryLogOf:aClass short:false
 !
@@ -32472,18 +32907,18 @@
 showRepositoryLogOf:aClass short:shortOrNot beforeLogDo:aBlock
     "show a classes repository log - append to codeView.
      CAVEAT: that is almost the same code as found in SystemBrowser;
-             move to SourceCodeManagerUtilities."
+	     move to SourceCodeManagerUtilities."
 
     |codeView aStream|
 
     aStream := WriteStream on:(String new:200).
 
     Processor activeProcess
-        withPriority:Processor activePriority-1 to:Processor activePriority
+	withPriority:Processor activePriority-1 to:Processor activePriority
     do:[
-        self busyLabel:'Extracting log of %1' with:aClass name.
-        aBlock value:aStream.
-        SourceCodeManagerUtilities default repositoryLogOf:aClass short:shortOrNot onto:aStream
+	self busyLabel:'Extracting log of %1' with:aClass name.
+	aBlock value:aStream.
+	SourceCodeManagerUtilities default repositoryLogOf:aClass short:shortOrNot onto:aStream
     ].
 
     self codeAspect:#repositoryLog.
@@ -32492,9 +32927,9 @@
 
     codeView := self codeView.
     codeView contents:(codeView contents ,
-                       Character cr asString ,
-                       Character cr asString ,
-                       aStream contents).
+		       Character cr asString ,
+		       Character cr asString ,
+		       aStream contents).
 
     codeView modified:false.
     navigationState realModifiedState:false.
@@ -32508,18 +32943,18 @@
 showRepositoryLogOf:aClass short:shortOrNot usingManager: manager beforeLogDo:aBlock
     "show a classes repository log - append to codeView.
      CAVEAT: that is almost the same code as found in SystemBrowser;
-             move to SourceCodeManagerUtilities."
+	     move to SourceCodeManagerUtilities."
 
     |codeView aStream|
 
     aStream := WriteStream on:(String new:200).
 
     Processor activeProcess
-        withPriority:Processor activePriority-1 to:Processor activePriority
+	withPriority:Processor activePriority-1 to:Processor activePriority
     do:[
-        self busyLabel:'Extracting log of %1' with:aClass name.
-        aBlock value:aStream.
-        manager utilities repositoryLogOf:aClass short:shortOrNot onto:aStream
+	self busyLabel:'Extracting log of %1' with:aClass name.
+	aBlock value:aStream.
+	manager utilities repositoryLogOf:aClass short:shortOrNot onto:aStream
     ].
 
     self codeAspect:#repositoryLog.
@@ -32528,9 +32963,9 @@
 
     codeView := self codeView.
     codeView contents:(codeView contents ,
-                       Character cr asString ,
-                       Character cr asString ,
-                       aStream contents).
+		       Character cr asString ,
+		       Character cr asString ,
+		       aStream contents).
 
     codeView modified:false.
     navigationState realModifiedState:false.
@@ -32561,82 +32996,82 @@
     mgr := aManagerOrNil ? aClass sourceCodeManager.
     rev := aClass binaryRevision.
     rev isNil ifTrue:[
-        rev := aClass revision
+	rev := aClass revision
     ].
     rev isNil ifTrue:[
-        "/
-        "/ class not in repository - allow compare against any other containers newest contents
-        "/
-        self normalLabel.
-
-        pkg := aClass package.
-        (pkg notNil and:[pkg ~= PackageId noProjectID]) ifTrue:[
-            containerModule := pkg upTo:$:.
-            containerPackage := pkg copyFrom:(containerModule size + 2).
-        ].
-        containerModule size == 0 ifTrue:[
-            containerModule := (SourceCodeManagerUtilities lastModule) ? Project current repositoryModule.
-        ].
-        containerPackage size == 0 ifTrue:[
-            containerPackage := (SourceCodeManagerUtilities lastPackage) ? Project current package.
-        ].
-        rslt := mgr utilities
-            askForContainer:(resources
-                    stringWithCRs:'The "%1"-class seems to have no repository information.\\Do you want to compare it against an existing containers contents ?'
-                    with:aClass name)
-            title:'Container to compare' note:nil
-            initialModule:containerModule
-            initialPackage:containerPackage
-            initialFileName:(aClass name , '.st')
-            forNewContainer:false.
-        rslt isNil ifTrue:[
-            "/ cancel
-            ^ nil
-        ].
-        containerModule := rslt at:#module.
-        containerPackage := rslt at:#package.
-        containerFile := rslt at:#fileName.
-        SourceCodeManagerUtilities lastModule:containerModule.
-        SourceCodeManagerUtilities lastPackage:containerPackage.
-    ] ifFalse:[
-        "/
-        "/ class in repository - ask for revision
-        "/
-        newestRev := mgr newestRevisionOf:aClass.
-        rev := newestRev.
+	"/
+	"/ class not in repository - allow compare against any other containers newest contents
+	"/
+	self normalLabel.
+
+	pkg := aClass package.
+	(pkg notNil and:[pkg ~= PackageId noProjectID]) ifTrue:[
+	    containerModule := pkg upTo:$:.
+	    containerPackage := pkg copyFrom:(containerModule size + 2).
+	].
+	containerModule size == 0 ifTrue:[
+	    containerModule := (SourceCodeManagerUtilities lastModule) ? Project current repositoryModule.
+	].
+	containerPackage size == 0 ifTrue:[
+	    containerPackage := (SourceCodeManagerUtilities lastPackage) ? Project current package.
+	].
+	rslt := mgr utilities
+	    askForContainer:(resources
+		    stringWithCRs:'The "%1"-class seems to have no repository information.\\Do you want to compare it against an existing containers contents ?'
+		    with:aClass name)
+	    title:'Container to compare' note:nil
+	    initialModule:containerModule
+	    initialPackage:containerPackage
+	    initialFileName:(aClass name , '.st')
+	    forNewContainer:false.
+	rslt isNil ifTrue:[
+	    "/ cancel
+	    ^ nil
+	].
+	containerModule := rslt at:#module.
+	containerPackage := rslt at:#package.
+	containerFile := rslt at:#fileName.
+	SourceCodeManagerUtilities lastModule:containerModule.
+	SourceCodeManagerUtilities lastPackage:containerPackage.
+    ] ifFalse:[
+	"/
+	"/ class in repository - ask for revision
+	"/
+	newestRev := mgr newestRevisionOf:aClass.
+	rev := newestRev.
     ].
 
     (rev notNil or:[containerFile notNil]) ifTrue:[
-        rev notNil ifTrue:[
-            rev withoutSpaces isEmpty ifTrue:[
-                msg := 'extracting newest %1 (' , (newestRev ? '???') , ')'.
-                sourceStream := mgr getSourceStreamFor:aClass revision:newestRev.
-                revString := 'newest'.
-            ] ifFalse:[
-                msg := 'extracting previous %1'.
-                sourceStream := mgr getSourceStreamFor:aClass revision:rev.
-                revString := rev
-            ].
-        ] ifFalse:[
-            msg := 'extracting newest version from ' , containerModule , '/' , containerPackage, '/' , containerFile.
-            sourceStream := mgr streamForClass:nil fileName:containerFile revision:#newest directory:containerPackage module:containerModule cache:false.
-            revString := '???'
-        ].
-        self busyLabel:msg with:(aClass name).
-
-        sourceStream isNil ifTrue:[
-            info := mgr sourceInfoOfClass:aClass.
-            info notNil ifTrue:[
-                mod := info at:#module ifAbsent:'??'.
-                dir := info at:#directory ifAbsent:'??'.
-            ].
-
-            self warn:(resources
-                         string:'Could not extract source from repository (for module: ''%1'' , directory: ''%2'' , revision: ''%3'')'
-                         with:mod with:dir with:revString).
-            ^ nil
-        ].
-        ^ sourceStream
+	rev notNil ifTrue:[
+	    rev withoutSpaces isEmpty ifTrue:[
+		msg := 'extracting newest %1 (' , (newestRev ? '???') , ')'.
+		sourceStream := mgr getSourceStreamFor:aClass revision:newestRev.
+		revString := 'newest'.
+	    ] ifFalse:[
+		msg := 'extracting previous %1'.
+		sourceStream := mgr getSourceStreamFor:aClass revision:rev.
+		revString := rev
+	    ].
+	] ifFalse:[
+	    msg := 'extracting newest version from ' , containerModule , '/' , containerPackage, '/' , containerFile.
+	    sourceStream := mgr streamForClass:nil fileName:containerFile revision:#newest directory:containerPackage module:containerModule cache:false.
+	    revString := '???'
+	].
+	self busyLabel:msg with:(aClass name).
+
+	sourceStream isNil ifTrue:[
+	    info := mgr sourceInfoOfClass:aClass.
+	    info notNil ifTrue:[
+		mod := info at:#module ifAbsent:'??'.
+		dir := info at:#directory ifAbsent:'??'.
+	    ].
+
+	    self warn:(resources
+			 string:'Could not extract source from repository (for module: ''%1'' , directory: ''%2'' , revision: ''%3'')'
+			 with:mod with:dir with:revString).
+	    ^ nil
+	].
+	^ sourceStream
     ].
     ^ nil
 
@@ -32654,18 +33089,18 @@
 
     nonMeta := aClass theNonMetaclass.
     (cls := nonMeta whichClassDefinesClassVar:newName) notNil ifTrue:[
-        cls == aClass ifTrue:[
-            Dialog information:(resources string:'A variable named ''%1'' is already defined in ''%2''.'
-                                    with:newName allBold
-                                    with:cls name allBold).
-            ^ self
-        ].
-        (Dialog confirm:(resources stringWithCRs:'Attention: a variable named ''%1'' is already defined in ''%2''.\\Proceed ?'
-                                with:newName allBold
-                                with:cls name allBold))
-        ifFalse:[
-            ^ self
-        ].
+	cls == aClass ifTrue:[
+	    Dialog information:(resources string:'A variable named ''%1'' is already defined in ''%2''.'
+				    with:newName allBold
+				    with:cls name allBold).
+	    ^ self
+	].
+	(Dialog confirm:(resources stringWithCRs:'Attention: a variable named ''%1'' is already defined in ''%2''.\\Proceed ?'
+				with:newName allBold
+				with:cls name allBold))
+	ifFalse:[
+	    ^ self
+	].
     ].
 
     refactoring := AddClassVariableChange add:newName to:nonMeta.
@@ -32687,51 +33122,51 @@
     |refactoring cls generator varName pseudoVarName|
 
     asValueHolder ifTrue:[
-        varName := newName.
-        varName isUppercaseFirst ifTrue:[
-            varName := varName asLowercaseFirst.
-        ].
-        (varName endsWith:'Holder') ifTrue:[
-            pseudoVarName := varName copyWithoutLast:6.
-        ] ifFalse:[
-            pseudoVarName := varName.
-            varName := pseudoVarName , 'Holder'.
-        ].
-    ] ifFalse:[
-        varName := newName
+	varName := newName.
+	varName isUppercaseFirst ifTrue:[
+	    varName := varName asLowercaseFirst.
+	].
+	(varName endsWith:'Holder') ifTrue:[
+	    pseudoVarName := varName copyWithoutLast:6.
+	] ifFalse:[
+	    pseudoVarName := varName.
+	    varName := pseudoVarName , 'Holder'.
+	].
+    ] ifFalse:[
+	varName := newName
     ].
 
     (cls := aClass whichClassDefinesInstVar:varName) notNil ifTrue:[
-        Dialog warn:(resources string:'An instance variable named ''%1'' is already defined in ''%2''.'
-                                with:varName allBold
-                                with:cls name allBold).
-        ^ self
+	Dialog warn:(resources string:'An instance variable named ''%1'' is already defined in ''%2''.'
+				with:varName allBold
+				with:cls name allBold).
+	^ self
     ].
 
 "/    refactoring := AddInstanceVariableRefactoring variable:newName class:aClass.
 "/    refactoring model name:('Add instvar %1 to %2' bindWith:newName with:aClass name).
 
     asValueHolder ifTrue:[
-        generator := SmalltalkCodeGeneratorTool new.
-        generator startCollectChanges.
-
-        generator addChange:(AddInstanceVariableChange add:varName to:aClass).
-        generator createValueHoldersFor:(Array with:varName) in:aClass lazyInitialization:false.
-        generator executeCollectedChangesNamed:'Add ValueHolder'
-    ] ifFalse:[
-        refactoring := AddInstanceVariableChange add:varName to:aClass.
-        self performRefactoring:refactoring.
+	generator := SmalltalkCodeGeneratorTool new.
+	generator startCollectChanges.
+
+	generator addChange:(AddInstanceVariableChange add:varName to:aClass).
+	generator createValueHoldersFor:(Array with:varName) in:aClass lazyInitialization:false.
+	generator executeCollectedChangesNamed:'Add ValueHolder'
+    ] ifFalse:[
+	refactoring := AddInstanceVariableChange add:varName to:aClass.
+	self performRefactoring:refactoring.
     ].
 
     "Modified: / 31-01-2011 / 18:29:55 / cg"
 !
 
 codeMenuAddParameter
-    |currentMethod cls selector refactoring initializer newSelector l initialAnswer 
+    |currentMethod cls selector refactoring initializer newSelector l initialAnswer
      senders nSenders tree args dialog|
 
     (self askIfModified) ifFalse:[
-        ^ self
+	^ self
     ].
 
     currentMethod := self theSingleSelectedMethod.
@@ -32744,23 +33179,23 @@
 
     tree := cls parseTreeFor:selector.
     tree isNil ifTrue:[
-        self warn: 'Could not parse the method'.
-        ^ self
+	self warn: 'Could not parse the method'.
+	^ self
     ].
     args := tree argumentNames.
     args := args copyWith:('arg%1' bindWith:args size + 1).
 
     selector numArgs == 0 ifTrue:[
-        initialAnswer := selector , ':'.
-        l := 'Enter new selector:'.
-    ] ifFalse:[
-        initialAnswer := selector , 'xxxx:'.
-        l := 'Enter new selector (replace xxxx as desired):'.
+	initialAnswer := selector , ':'.
+	l := 'Enter new selector:'.
+    ] ifFalse:[
+	initialAnswer := selector , 'xxxx:'.
+	l := 'Enter new selector (replace xxxx as desired):'.
     ].
 
     dialog := MethodNameDialogForAddParameter methodNameFor: args initial:initialAnswer.
     nSenders == 0 ifTrue:[
-        dialog askForDefaultValue:false.
+	dialog askForDefaultValue:false.
     ].
     dialog cancelAllVisible value:(AbortAllOperationWantedQuery query).
     dialog renameOnlyVisible value:true.
@@ -32776,7 +33211,7 @@
 
 "/     newSelector := Dialog request:(resources string:l) initialAnswer:initialAnswer.
     newSelector isEmptyOrNil ifTrue:[
-        ^ nil "/ cancelled
+	^ nil "/ cancelled
     ].
 
 "/    nSenders > 0 ifTrue:[
@@ -32790,14 +33225,14 @@
 
     newSelector := newSelector asSymbol.
     refactoring := AddParameterRefactoring
-                        addParameterToMethod:selector
-                        in:cls
-                        newSelector:newSelector
-                        initializer:initializer.
+			addParameterToMethod:selector
+			in:cls
+			newSelector:newSelector
+			initializer:initializer.
 
     (self findSendersOf:selector in:(Smalltalk allClasses) andConfirmRefactoring:refactoring) ifTrue:[
-        self performRefactoring:refactoring.
-        self switchToSelector:newSelector
+	self performRefactoring:refactoring.
+	self switchToSelector:newSelector
     ]
 
     "Modified: / 09-02-2011 / 13:54:16 / cg"
@@ -32811,7 +33246,7 @@
 
     varName := self selectedInstanceVariableOrNil.
     varName notNil ifTrue:[
-        self codeMenuConvertToValueHolder:varName
+	self codeMenuConvertToValueHolder:varName
     ]
 !
 
@@ -32822,13 +33257,13 @@
     |refactoring|
 
     (self askIfModified) ifFalse:[
-        ^ self
+	^ self
     ].
 
     (self confirm:'About to rewrite methods...') ifFalse:[^ self].
     refactoring := (ValueHolderRefactoring
-                                variable: aString
-                                class: (self theSingleSelectedClass whichClassDefinesInstVar: aString)).
+				variable: aString
+				class: (self theSingleSelectedClass whichClassDefinesInstVar: aString)).
     self performRefactoring:refactoring.
 !
 
@@ -32838,13 +33273,13 @@
     |varName cls refactoring|
 
     varName := self codeView selectionAsString.
-    (varName isValidSmalltalkIdentifier 
-    and:[ varName isUppercaseFirst 
+    (varName isValidSmalltalkIdentifier
+    and:[ varName isUppercaseFirst
     and:[ (Smalltalk includesKey:varName) not
     and:[ (cls := self theSingleSelectedClass) notNil
-    and:[ (cls theNonMetaclass classVarNames includes:varName) not 
+    and:[ (cls theNonMetaclass classVarNames includes:varName) not
     ]]]]) ifFalse:[
-        ^ self.
+	^ self.
     ].
 
     refactoring := AddClassVariableChange add:varName to:cls theNonMetaclass.
@@ -32854,7 +33289,7 @@
 codeMenuEliminateConstant
     "a new refactoring:
      given a literal constant as current text selection,
-     ask for either a class or inst variable name, 
+     ask for either a class or inst variable name,
      or the name of a class or instance getter-method
      define it, assign it a value (in the initialize method)
      and change the code to refer to that variable/getter instead.
@@ -32863,8 +33298,8 @@
      Most of the code below should go into the RB-package as a new refactoring class, once
      it is debugged and stable."
 
-    |literalString literalValue name selectedClass refactoring matchingMethods mthd 
-     initialNewName radioModel box rb nameHolder changeHow targetClass 
+    |literalString literalValue name selectedClass refactoring matchingMethods mthd
+     initialNewName radioModel box rb nameHolder changeHow targetClass
      numMethodsAdded numMethodsRewritten confirmationQuestion informationMessage|
 
     literalString := self codeView selectionAsString withoutSeparators.
@@ -32873,25 +33308,25 @@
 
     selectedClass := self theSingleSelectedClass.
     selectedClass isNil ifTrue:[
-        mthd := self theSingleSelectedMethod.
-        mthd isNil ifTrue:[
-            Dialog information:'Please select a class or method'.
-            ^ self
-        ].
-        selectedClass := mthd mclass
+	mthd := self theSingleSelectedMethod.
+	mthd isNil ifTrue:[
+	    Dialog information:'Please select a class or method'.
+	    ^ self
+	].
+	selectedClass := mthd mclass
     ].
 
     selectedClass isMeta ifTrue:[
-        LastLiteralReplacementType == #instanceMethod ifTrue:[ LastLiteralReplacementType := #classMethod ].      
-        LastLiteralReplacementType == #instanceVariable ifTrue:[ LastLiteralReplacementType := #classVariable ].      
+	LastLiteralReplacementType == #instanceMethod ifTrue:[ LastLiteralReplacementType := #classMethod ].
+	LastLiteralReplacementType == #instanceVariable ifTrue:[ LastLiteralReplacementType := #classVariable ].
     ].
     radioModel := RadioButtonGroup new value:(LastLiteralReplacementType ? #classMethod).
 
-    initialNewName := 
-        DoWhatIMeanSupport 
-            goodRenameDefaultFor:literalString 
-            lastOld:LastLiteralReplacementOldLiteral 
-            lastNew:LastLiteralReplacementNewName.
+    initialNewName :=
+	DoWhatIMeanSupport
+	    goodRenameDefaultFor:literalString
+	    lastOld:LastLiteralReplacementOldLiteral
+	    lastNew:LastLiteralReplacementNewName.
     initialNewName isEmptyOrNil ifTrue:[ initialNewName := literalString "(LastLiteralReplacementNewName ? '')" ].
     nameHolder := initialNewName asValue.
 
@@ -32925,131 +33360,131 @@
     numMethodsAdded := numMethodsRewritten := 0.
 
     (changeHow == #instanceMethod or:[changeHow == #instanceVariable]) ifTrue:[
-        targetClass := selectedClass theNonMetaclass
-    ] ifFalse:[
-        targetClass := selectedClass theMetaclass
+	targetClass := selectedClass theNonMetaclass
+    ] ifFalse:[
+	targetClass := selectedClass theMetaclass
     ].
 
     (changeHow == #instanceMethod or:[changeHow == #classMethod]) ifTrue:[
-        (targetClass includesSelector:name asSymbol) ifFalse:[
-            refactoring compile:('%1\    ^ %2' withCRs bindWith:name with:literalString) in:targetClass classified:'constants'.
-            numMethodsAdded := numMethodsAdded + 1.
-        ] ifTrue:[
-            "/ if the getter already exists, it must return the same literal
-            mthd := targetClass compiledMethodAt:name asSymbol.
-            ((ParseTreeSearcher isJustReturningLiteralString:literalString)
-                executeTree:(mthd parseTree) initialAnswer:false) 
-            ifFalse:[
-                Dialog information:(resources 
-                                        stringWithCRs:'A method named "%1" already exists\with different semantics (does not return "%2")'
-                                        with:name
-                                        with:literalString).
-                ^ self.
-            ].
-        ].
-    ] ifFalse:[
-        changeHow == #instanceVariable ifTrue:[
-            (targetClass theNonMetaclass allInstVarNames includes:name) ifTrue:[
-                "/ already present
-                Dialog information:(resources 
-                                        stringWithCRs:'An instance variable named "%1" already exists'
-                                        with:name).
-                ^ self.
-            ].
-            refactoring addInstanceVariable:name to:targetClass theNonMetaclass.
-        ] ifFalse:[
-            "/ class variable
-            (targetClass theNonMetaclass allClassVarNames includes:name) ifTrue:[
-                "/ already present
-                Dialog information:(resources 
-                                        stringWithCRs:'A class variable named "%1" already exists'
-                                        with:name).
-                ^ self.
-            ].
-            refactoring addClassVariable:name to:targetClass theNonMetaclass.
-        ].
-
-        (targetClass includesSelector:#initialize) ifFalse:[
-            refactoring compile:('initialize\    %1 := %2.' withCRs bindWith:name with:literalString) in:targetClass classified:'initialization'.
-            numMethodsAdded := numMethodsAdded + 1.
-        ] ifTrue:[
-            |setToThis setToOther rewriter newSource change|
-
-            setToThis := setToOther := false.
-            
-            mthd := targetClass compiledMethodAt:#initialize.
-
-            "/ already a setting for that variable ?
-            "/ cannot happen now, as we only allow not-already-existing vars in the above code.
-            "/ if we ever support this, must check if the existing init-code is already correct for the new value
-            (ParseTreeSearcher new 
-                        answer:false;
-                        matches:('%1 := ``@expr' bindWith:name) do:[:aNode :ans | self halt. false];
-                        yourself)
-                executeTree:(mthd parseTree) initialAnswer:false.
-
-            setToOther ifTrue:[
-                Dialog information:(resources 
-                                        stringWithCRs:'Variable named "%1" is already initialized to a different value'
-                                        with:name).
-                ^ self.
-            ].
-            setToThis ifFalse:[
-                "/ sigh - the source rewriter is very limited; it cannot append code yet...
-                rewriter := "ParseTreeSourceRewriter "ParseTreeRewriter new
-                                replace: '| `@temps | ``@.stats. '  
-                                with:('| `@temps | ``@.stats.\    %1 := %2.' withCRs bindWith:name with:literalString).
-
-                rewriter executeTree: mthd parseTree.
-                newSource := rewriter tree formattedCode.
+	(targetClass includesSelector:name asSymbol) ifFalse:[
+	    refactoring compile:('%1\    ^ %2' withCRs bindWith:name with:literalString) in:targetClass classified:'constants'.
+	    numMethodsAdded := numMethodsAdded + 1.
+	] ifTrue:[
+	    "/ if the getter already exists, it must return the same literal
+	    mthd := targetClass compiledMethodAt:name asSymbol.
+	    ((ParseTreeSearcher isJustReturningLiteralString:literalString)
+		executeTree:(mthd parseTree) initialAnswer:false)
+	    ifFalse:[
+		Dialog information:(resources
+					stringWithCRs:'A method named "%1" already exists\with different semantics (does not return "%2")'
+					with:name
+					with:literalString).
+		^ self.
+	    ].
+	].
+    ] ifFalse:[
+	changeHow == #instanceVariable ifTrue:[
+	    (targetClass theNonMetaclass allInstVarNames includes:name) ifTrue:[
+		"/ already present
+		Dialog information:(resources
+					stringWithCRs:'An instance variable named "%1" already exists'
+					with:name).
+		^ self.
+	    ].
+	    refactoring addInstanceVariable:name to:targetClass theNonMetaclass.
+	] ifFalse:[
+	    "/ class variable
+	    (targetClass theNonMetaclass allClassVarNames includes:name) ifTrue:[
+		"/ already present
+		Dialog information:(resources
+					stringWithCRs:'A class variable named "%1" already exists'
+					with:name).
+		^ self.
+	    ].
+	    refactoring addClassVariable:name to:targetClass theNonMetaclass.
+	].
+
+	(targetClass includesSelector:#initialize) ifFalse:[
+	    refactoring compile:('initialize\    %1 := %2.' withCRs bindWith:name with:literalString) in:targetClass classified:'initialization'.
+	    numMethodsAdded := numMethodsAdded + 1.
+	] ifTrue:[
+	    |setToThis setToOther rewriter newSource change|
+
+	    setToThis := setToOther := false.
+
+	    mthd := targetClass compiledMethodAt:#initialize.
+
+	    "/ already a setting for that variable ?
+	    "/ cannot happen now, as we only allow not-already-existing vars in the above code.
+	    "/ if we ever support this, must check if the existing init-code is already correct for the new value
+	    (ParseTreeSearcher new
+			answer:false;
+			matches:('%1 := ``@expr' bindWith:name) do:[:aNode :ans | self halt. false];
+			yourself)
+		executeTree:(mthd parseTree) initialAnswer:false.
+
+	    setToOther ifTrue:[
+		Dialog information:(resources
+					stringWithCRs:'Variable named "%1" is already initialized to a different value'
+					with:name).
+		^ self.
+	    ].
+	    setToThis ifFalse:[
+		"/ sigh - the source rewriter is very limited; it cannot append code yet...
+		rewriter := "ParseTreeSourceRewriter "ParseTreeRewriter new
+				replace: '| `@temps | ``@.stats. '
+				with:('| `@temps | ``@.stats.\    %1 := %2.' withCRs bindWith:name with:literalString).
+
+		rewriter executeTree: mthd parseTree.
+		newSource := rewriter tree formattedCode.
 
 "/                newSource := rewriter executeReplacementsInSource:mthd source.
 "/                rewriter forgetReplacements.
 
-                change := InteractiveAddMethodChange compile:newSource in:mthd mclass classified:mthd category.
-                refactoring addChange:change.
-                numMethodsRewritten := numMethodsRewritten + 1.
-            ].
-        ]
+		change := InteractiveAddMethodChange compile:newSource in:mthd mclass classified:mthd category.
+		refactoring addChange:change.
+		numMethodsRewritten := numMethodsRewritten + 1.
+	    ].
+	]
     ].
 
     matchingMethods := OrderedCollection new.
-    targetClass theNonMetaclass methodDictionary keysAndValuesDo:[:selector :mth | 
-        selector ~= name ifTrue:[
-            (ParseTreeSearcher new)
-                matches:literalString do:[:aNode :answer | matchingMethods add:mth ];
-                executeTree:mth parseTree.
-        ].
+    targetClass theNonMetaclass methodDictionary keysAndValuesDo:[:selector :mth |
+	selector ~= name ifTrue:[
+	    (ParseTreeSearcher new)
+		matches:literalString do:[:aNode :answer | matchingMethods add:mth ];
+		executeTree:mth parseTree.
+	].
     ].
     (changeHow == #classVariable or:[changeHow == #classMethod]) ifTrue:[
-        targetClass theMetaclass methodDictionary keysAndValuesDo:[:selector :mth | 
-            selector ~= name ifTrue:[
-                (ParseTreeSearcher new)
-                    matches:literalString do:[:aNode :answer | matchingMethods add:mth ];
-                    executeTree:mth parseTree.
-            ].
-        ].
+	targetClass theMetaclass methodDictionary keysAndValuesDo:[:selector :mth |
+	    selector ~= name ifTrue:[
+		(ParseTreeSearcher new)
+		    matches:literalString do:[:aNode :answer | matchingMethods add:mth ];
+		    executeTree:mth parseTree.
+	    ].
+	].
     ].
 
     matchingMethods do:[:mth |
-        |change replacementSource rewriter newSource|
-
-        (changeHow == #instanceVariable or:[changeHow == #classVariable]) ifTrue:[
-            replacementSource := name.
-        ] ifFalse:[
-            (changeHow == #instanceMethod) ifTrue:[
-                replacementSource := ('self ',name).
-            ] ifFalse:[
-                mth mclass isMeta ifTrue:[
-                    replacementSource := ('self ',name).
-                ] ifFalse:[
-                    replacementSource := ('self class ',name).
-                ].
-            ].
-        ].
-        rewriter := ParseTreeSourceRewriter "ParseTreeRewriter" new
-                        replace: literalString 
-                        with: replacementSource.
+	|change replacementSource rewriter newSource|
+
+	(changeHow == #instanceVariable or:[changeHow == #classVariable]) ifTrue:[
+	    replacementSource := name.
+	] ifFalse:[
+	    (changeHow == #instanceMethod) ifTrue:[
+		replacementSource := ('self ',name).
+	    ] ifFalse:[
+		mth mclass isMeta ifTrue:[
+		    replacementSource := ('self ',name).
+		] ifFalse:[
+		    replacementSource := ('self class ',name).
+		].
+	    ].
+	].
+	rewriter := ParseTreeSourceRewriter "ParseTreeRewriter" new
+			replace: literalString
+			with: replacementSource.
 
 "/        "/ with the original ParseTreeRewriter, you would
 "/        "/ get a new tree, loose all formatting and some comments...
@@ -33058,32 +33493,32 @@
 "/                    tree.
 "/        newSource := newTree formattedCode.
 
-        "/ so we use the new in-place ParseTreeSourceRewriter 
-        rewriter executeTree: mth parseTree.
-        newSource := rewriter executeReplacementsInSource:mth source.
-        rewriter forgetReplacements.
-
-        change := InteractiveAddMethodChange compile:newSource in:mth mclass classified:mth category.
-        refactoring addChange:change.
-        numMethodsRewritten := numMethodsRewritten + 1.
+	"/ so we use the new in-place ParseTreeSourceRewriter
+	rewriter executeTree: mth parseTree.
+	newSource := rewriter executeReplacementsInSource:mth source.
+	rewriter forgetReplacements.
+
+	change := InteractiveAddMethodChange compile:newSource in:mth mclass classified:mth category.
+	refactoring addChange:change.
+	numMethodsRewritten := numMethodsRewritten + 1.
     ].
 
     (numMethodsRewritten+numMethodsAdded) > 1 ifTrue:[
-        informationMessage := 
-            numMethodsRewritten > 0
-                ifTrue:[
-                    numMethodsAdded > 0 
-                        ifTrue:[ 'rewrite %1 and add %2 methods' ]
-                        ifFalse:[ 'rewrite %1 methods' ] ]
-                ifFalse:[ 'add %2 methods' ].
-        confirmationQuestion := 'OK to ',informationMessage.
-        "/ (Dialog confirm:(resources string:confirmationQuestion with:numMethodsRewritten with:numMethodsAdded)) ifFalse:[^ self].
+	informationMessage :=
+	    numMethodsRewritten > 0
+		ifTrue:[
+		    numMethodsAdded > 0
+			ifTrue:[ 'rewrite %1 and add %2 methods' ]
+			ifFalse:[ 'rewrite %1 methods' ] ]
+		ifFalse:[ 'add %2 methods' ].
+	confirmationQuestion := 'OK to ',informationMessage.
+	"/ (Dialog confirm:(resources string:confirmationQuestion with:numMethodsRewritten with:numMethodsAdded)) ifFalse:[^ self].
     ].
     self performRefactoring:refactoring.
 
     "/ set the class variable
     (changeHow == #classVariable) ifTrue:[
-        targetClass classVarAt:name asSymbol put:literalValue
+	targetClass classVarAt:name asSymbol put:literalValue
     ].
 
     self showInfo:(resources string:informationMessage with:numMethodsRewritten with:numMethodsAdded).
@@ -33093,29 +33528,29 @@
 
 codeMenuExtractMethod
     self withCurrentMethodsClassAndSelectorDo:[:mClass :mSelector |
-        | refactoring |
-
-        refactoring := (ExtractMethodRefactoring
-                            extract: (self selectedInterval)
-                            from: mSelector
-                            in: mClass).
-
-        refactoring source:self codeView contentsAsString.
-        self performRefactoring:refactoring.
+	| refactoring |
+
+	refactoring := (ExtractMethodRefactoring
+			    extract: (self selectedInterval)
+			    from: mSelector
+			    in: mClass).
+
+	refactoring source:self codeView contentsAsString.
+	self performRefactoring:refactoring.
     ]
 !
 
 codeMenuExtractMethodToComponent
     self withCurrentMethodsClassAndSelectorDo:[:mClass :mSelector |
-        | refactoring |
-
-        refactoring := (ExtractMethodToComponentRefactoring
-                            extract: (self selectedInterval)
-                            from: mSelector
-                            in: mClass).
-
-        refactoring source:self codeView contentsAsString.
-        self performRefactoring:refactoring.
+	| refactoring |
+
+	refactoring := (ExtractMethodToComponentRefactoring
+			    extract: (self selectedInterval)
+			    from: mSelector
+			    in: mClass).
+
+	refactoring source:self codeView contentsAsString.
+	self performRefactoring:refactoring.
     ]
 !
 
@@ -33126,27 +33561,27 @@
 
     (self askIfModified:'Text was modified - please accept first' default:false) ~~ true
     ifTrue:[
-        ^ self
+	^ self
     ].
 
     node := self findNode.
     (node notNil and: [node isValue]) ifFalse: [
-        ^ self warn: 'Could not find the node (please select the message expression to extract)'
+	^ self warn: 'Could not find the node (please select the message expression to extract)'
     ].
 
     (node isMessage and:[node isUnary]) ifTrue:[
-        varName := node selector
-    ] ifFalse:[
-        varName := LastTemporaryVariableName ? 't'.
+	varName := node selector
+    ] ifFalse:[
+	varName := LastTemporaryVariableName ? 't'.
     ].
 
     source := self codeView contentsAsString string.
     codeTree := RBParser
-                parseMethod:source
-                onError: [:str :err ":nodesSoFar" | nil].
+		parseMethod:source
+		onError: [:str :err ":nodesSoFar" | nil].
 
     codeTree notNil ifTrue:[
-        (codeTree body temporaries contains:[:nd | nd name = varName]) ifTrue:[varName := nil].
+	(codeTree body temporaries contains:[:nd | nd name = varName]) ifTrue:[varName := nil].
     ].
 
     newName := Dialog request: 'Enter name for Temporary:' initialAnswer:varName.
@@ -33157,37 +33592,37 @@
     cls := currentMethod mclass.
     selector := currentMethod selector.
     (cls isNil or:[selector isNil]) ifTrue:[
-        self information:'Oops - no class/selector. Please reselect.'.
-        ^ self.
+	self information:'Oops - no class/selector. Please reselect.'.
+	^ self.
     ].
 
     refactoring := (ExtractToTemporaryRefactoring
-                                extract: (node sourceInterval)
-                                to: newName
-                                from: selector
-                                in: cls).
+				extract: (node sourceInterval)
+				to: newName
+				from: selector
+				in: cls).
     refactoring source:self codeView contentsAsString.
     self performRefactoring:refactoring.
 !
 
 codeMenuFormat
     "format (prettyPrint) the selected method(s)"
-    
+
     |modifiedBefore|
 
     self hasSingleMethodSelected ifTrue:[
-        modifiedBefore := navigationState modified.
-
-        self formatCode.
-        ("autoAcceptFormattedCode" false or:[modifiedBefore not]) ifTrue:[
-            self codeView accept
-        ].
-    ] ifFalse:[
-        self information:'Bulk formatting is currently disabled, because the formatter
+	modifiedBefore := navigationState modified.
+
+	self formatCode.
+	("autoAcceptFormattedCode" false or:[modifiedBefore not]) ifTrue:[
+	    self codeView accept
+	].
+    ] ifFalse:[
+	self information:'Bulk formatting is currently disabled, because the formatter
 has still problems to layout comments in an acceptable way (although its much better
 than it used to be...) Therefore, please have an eye on each formatted method.'.
-        ^ self.
-"/        self selectedMethodsDo:[:each | 
+	^ self.
+"/        self selectedMethodsDo:[:each |
 "/            self formatMethod:each
 "/        ].
     ].
@@ -33201,20 +33636,20 @@
     |currentMethod selector refactoring|
 
     (self askIfModified) ifFalse:[
-        ^ self
+	^ self
     ].
 
     currentMethod := self theSingleSelectedMethod.
     selector := currentMethod selector.
 
-    refactoring := InlineAllSelfSendersRefactoring 
-                            sendersOf: selector
-                            in: currentMethod mclass.
+    refactoring := InlineAllSelfSendersRefactoring
+			    sendersOf: selector
+			    in: currentMethod mclass.
     refactoring setOption: #inlineExpression toUse: [:ref :string | true].
     self performRefactoring: refactoring.
 
     (self findSendersOf:selector andConfirmRefactoring:refactoring) ifTrue:[
-        self performRefactoring:refactoring.
+	self performRefactoring:refactoring.
     ]
 !
 
@@ -33222,7 +33657,7 @@
     |currentMethod node cls selector refactoring receiverNode inlinedSelector senders rslt|
 
     (self askIfModified) ifFalse:[
-        ^ self
+	^ self
     ].
 
     currentMethod := self theSingleSelectedMethod.
@@ -33231,7 +33666,7 @@
 
     node := self findNode.
     (node isNil or: [node isMessage not]) ifTrue: [
-        ^ self warn: 'Could not find message send (please select the messageSelector or part of it)'
+	^ self warn: 'Could not find message send (please select the messageSelector or part of it)'
     ].
     receiverNode := node receiver.
     inlinedSelector := node selector.
@@ -33239,15 +33674,15 @@
     (receiverNode isVariable
     and: [#('self' 'super') includes: receiverNode name])
     ifTrue:[
-        refactoring := (InlineMethodRefactoring
-                                    inline: node sourceInterval
-                                    inMethod: selector
-                                    forClass: cls)
-    ] ifFalse:[
-        refactoring := (InlineMethodFromComponentRefactoring
-                                    inline: node sourceInterval
-                                    inMethod: selector
-                                    forClass: cls)
+	refactoring := (InlineMethodRefactoring
+				    inline: node sourceInterval
+				    inMethod: selector
+				    forClass: cls)
+    ] ifFalse:[
+	refactoring := (InlineMethodFromComponentRefactoring
+				    inline: node sourceInterval
+				    inMethod: selector
+				    forClass: cls)
     ].
 
 "/    refactoring model name:('inline %1 into %2' bindWith:inlinedSelector with:selector).
@@ -33255,14 +33690,14 @@
     rslt isNil ifTrue:[^ self ].
 
     senders := self class findSendersOf:inlinedSelector
-                    in:Smalltalk allClasses
-                    ignoreCase:false
-                    match:false.
+		    in:Smalltalk allClasses
+		    ignoreCase:false
+		    match:false.
 
     senders isEmpty ifTrue:[
-        (self confirm:('There seem to be no more senders of ', inlinedSelector , '.\\Remove the implementation in ' , cls name , ' ?') withCRs)
-        ifFalse:[^ self].
-        self doRemoveMethodsUnconfirmed:(Array with:(refactoring inlineClass realClass compiledMethodAt:inlinedSelector)).
+	(self confirm:('There seem to be no more senders of ', inlinedSelector , '.\\Remove the implementation in ' , cls name , ' ?') withCRs)
+	ifFalse:[^ self].
+	self doRemoveMethodsUnconfirmed:(Array with:(refactoring inlineClass realClass compiledMethodAt:inlinedSelector)).
     ].
 
     "Modified: / 17-11-2006 / 13:51:06 / cg"
@@ -33280,7 +33715,7 @@
     |currentMethod cls selector refactoring|
 
     (self askIfModified) ifFalse:[
-        ^ self
+	^ self
     ].
 
     currentMethod := self theSingleSelectedMethod.
@@ -33291,8 +33726,8 @@
     refactoring := InlineParameterRefactoring inlineParameter:parameterName in:cls selector:selector.
 
     (self findSendersOf:selector andConfirmRefactoring:refactoring) ifTrue:[
-        self performRefactoring:refactoring.
-        self switchToSelector:refactoring newSelector.
+	self performRefactoring:refactoring.
+	self switchToSelector:refactoring newSelector.
     ]
 !
 
@@ -33303,26 +33738,26 @@
     |selectedClass definingClass cls|
 
     (self askIfModified) ifFalse:[
-        ^ self
+	^ self
     ].
 
     selectedClass := self theSingleSelectedClass theNonMetaclass.
     cls := definingClass := selectedClass whichClassDefinesClassVar:aString.
 
     definingClass ~~ selectedClass ifTrue:[
-        cls := OptionBox
-                      request:(resources string:'Rewrite methods below %1 (defining) or %2 (selected) ?'
-                                         with:definingClass name allBold
-                                         with:selectedClass name allBold)
-                      label:'Rewrite which classes'
-                      buttonLabels:(Array with:'cancel' with:definingClass name with:selectedClass name)
-                      values:(Array with:nil with:definingClass with:selectedClass).
-        cls isNil ifTrue:[^ self].
+	cls := OptionBox
+		      request:(resources string:'Rewrite methods below %1 (defining) or %2 (selected) ?'
+					 with:definingClass name allBold
+					 with:selectedClass name allBold)
+		      label:'Rewrite which classes'
+		      buttonLabels:(Array with:'cancel' with:definingClass name with:selectedClass name)
+		      values:(Array with:nil with:definingClass with:selectedClass).
+	cls isNil ifTrue:[^ self].
     ].
 
     (self confirm:(resources string:'About to rewrite references to ''%1'' (in and below %2).'
-                             with:aString allBold
-                             with:cls name)) ifFalse:[^ self].
+			     with:aString allBold
+			     with:cls name)) ifFalse:[^ self].
 
     self performRefactoring:(AbstractClassVariableRefactoring variable:aString class:cls).
 !
@@ -33334,26 +33769,26 @@
     |selectedClass definingClass cls|
 
     (self askIfModified) ifFalse:[
-        ^ self
+	^ self
     ].
 
     selectedClass := self theSingleSelectedClass.
     cls := definingClass := selectedClass whichClassDefinesInstVar:aString.
 
     definingClass ~~ selectedClass ifTrue:[
-        cls := OptionBox
-                      request:(resources string:'Rewrite methods below %1 (defining) or %2 (selected) ?'
-                                         with:definingClass name allBold
-                                         with:selectedClass name allBold)
-                      label:'Rewrite which classes'
-                      buttonLabels:(Array with:'cancel' with:definingClass name with:selectedClass name)
-                      values:(Array with:nil with:definingClass with:selectedClass).
-        cls isNil ifTrue:[^ self].
+	cls := OptionBox
+		      request:(resources string:'Rewrite methods below %1 (defining) or %2 (selected) ?'
+					 with:definingClass name allBold
+					 with:selectedClass name allBold)
+		      label:'Rewrite which classes'
+		      buttonLabels:(Array with:'cancel' with:definingClass name with:selectedClass name)
+		      values:(Array with:nil with:definingClass with:selectedClass).
+	cls isNil ifTrue:[^ self].
     ].
 
     (self confirm:(resources string:'About to rewrite references to ''%1'' (in and below %2).'
-                             with:aString allBold
-                             with:cls name)) ifFalse:[^ self].
+			     with:aString allBold
+			     with:cls name)) ifFalse:[^ self].
 
     self performRefactoring:(AbstractInstanceVariableRefactoring variable:aString class:cls).
 !
@@ -33366,12 +33801,12 @@
 
     varName := self selectedInstanceVariableOrNil.
     varName notNil ifTrue:[
-        ^ self codeMenuMakeAbstractInstanceVariable:varName.
+	^ self codeMenuMakeAbstractInstanceVariable:varName.
     ].
 
     varName := self selectedClassVariableOrNil.
     varName notNil ifTrue:[
-        ^ self codeMenuMakeAbstractClassVariable:varName
+	^ self codeMenuMakeAbstractClassVariable:varName
     ].
 
     self warn:'Please select either an instance or a class variable (in the codeView or the variableList).'
@@ -33384,12 +33819,12 @@
 
     varNames := self selectedTemporaryVariablesInCodeViewOrNil.
     varNames isEmptyOrNil ifTrue:[
-        self warn:'Please select at least one temporary variable in the code.'.
-        ^ self.
+	self warn:'Please select at least one temporary variable in the code.'.
+	^ self.
     ].
 
     varNames do:[:varName |
-        self codeMenuMakeInstanceVariable:varName.
+	self codeMenuMakeInstanceVariable:varName.
     ].
 !
 
@@ -33397,32 +33832,32 @@
     "make selected local an instvar."
 
     self withCurrentMethodsClassAndSelectorDo:[:mClass :mSelector |
-        |refactoring newClass newMethod|
-
-        refactoring := (TemporaryToInstanceVariableRefactoring
-                                class: mClass
-                                selector: mSelector
-                                variable: aString).
-
-        (self confirm:'About to rewrite methods for ',aString,'...') ifFalse:[^ self].
-
-        "/ cannot delay the update class/method
-        "/ (otherwise, selectedMethod will be wrong for the second variable)
-        immediateUpdate value:true.
-
-        self performRefactoring:refactoring.
-
-        immediateUpdate value:false.
-
-        "/ must reselect manually here
-        newClass := Smalltalk classNamed:(mClass name).
-        newMethod := newClass compiledMethodAt:mSelector.
-        newClass ~~ self theSingleSelectedClass ifTrue:[
-            self selectClass:newClass.
-        ].
-        newMethod ~~ self theSingleSelectedMethod ifTrue:[
-            self selectMethod:newMethod.
-        ].
+	|refactoring newClass newMethod|
+
+	refactoring := (TemporaryToInstanceVariableRefactoring
+				class: mClass
+				selector: mSelector
+				variable: aString).
+
+	(self confirm:'About to rewrite methods for ',aString,'...') ifFalse:[^ self].
+
+	"/ cannot delay the update class/method
+	"/ (otherwise, selectedMethod will be wrong for the second variable)
+	immediateUpdate value:true.
+
+	self performRefactoring:refactoring.
+
+	immediateUpdate value:false.
+
+	"/ must reselect manually here
+	newClass := Smalltalk classNamed:(mClass name).
+	newMethod := newClass compiledMethodAt:mSelector.
+	newClass ~~ self theSingleSelectedClass ifTrue:[
+	    self selectClass:newClass.
+	].
+	newMethod ~~ self theSingleSelectedMethod ifTrue:[
+	    self selectMethod:newMethod.
+	].
     ].
 !
 
@@ -33433,25 +33868,25 @@
 
     node := self findNode.
     (node isNil or:[node isVariable not]) ifTrue:[
-        ^ self warn:'Please select a temporary variable in the code.'
+	^ self warn:'Please select a temporary variable in the code.'
     ].
 
     varName := node name.
     definingNode := node whoDefines:varName.
     definingNode isNil ifTrue: [
-        self warn:varName , ' is not a temporary variable in the method'. 
-        ^ self
+	self warn:varName , ' is not a temporary variable in the method'.
+	^ self
     ].
 
     self withCurrentMethodsClassAndSelectorDo:[:mClass :mSelector |
-        |refactoring|
-
-        refactoring := MoveVariableDefinitionRefactoring
-                            bindTight: (node sourceInterval)
-                            in: mClass
-                            selector: mSelector.
-
-        self performRefactoring: refactoring.
+	|refactoring|
+
+	refactoring := MoveVariableDefinitionRefactoring
+			    bindTight: (node sourceInterval)
+			    in: mClass
+			    selector: mSelector.
+
+	self performRefactoring: refactoring.
     ].
     self switchToMethod:(self theSingleSelectedMethod).
 !
@@ -33464,12 +33899,12 @@
 
     varName := self selectedInstanceVariableOrNil.
     varName notNil ifTrue:[
-        ^ self codeMenuProtectInstanceVariable:varName.
+	^ self codeMenuProtectInstanceVariable:varName.
     ].
 
     varName := self selectedClassVariableOrNil.
     varName notNil ifTrue:[
-        ^ self warn:'Sorry: This Refactoring is (currently) only supported for instance variables.'.
+	^ self warn:'Sorry: This Refactoring is (currently) only supported for instance variables.'.
     ].
 
     self warn:'Please select an instance variable (in the codeView or the variableList).'
@@ -33482,24 +33917,24 @@
     |selectedClass definingClass cls|
 
     (self askIfModified) ifFalse:[
-        ^ self
+	^ self
     ].
 
     selectedClass := self theSingleSelectedClass.
     cls := definingClass := selectedClass whichClassDefinesInstVar:aString.
     definingClass ~~ selectedClass ifTrue:[
-        cls := OptionBox
-                      request:(resources string:'Rewrite methods below %1 (defining) or %2 (selected) ?'
-                                         with:definingClass name allBold
-                                         with:selectedClass name allBold)
-                      label:'Rewrite which classes'
-                      buttonLabels:(Array with:'cancel' with:definingClass name with:selectedClass name)
-                      values:(Array with:nil with:definingClass with:selectedClass).
-        cls isNil ifTrue:[^ self].
+	cls := OptionBox
+		      request:(resources string:'Rewrite methods below %1 (defining) or %2 (selected) ?'
+					 with:definingClass name allBold
+					 with:selectedClass name allBold)
+		      label:'Rewrite which classes'
+		      buttonLabels:(Array with:'cancel' with:definingClass name with:selectedClass name)
+		      values:(Array with:nil with:definingClass with:selectedClass).
+	cls isNil ifTrue:[^ self].
     ].
     (self confirm:(resources string:'About to rewrite references to ''%1'' (in and below %2).'
-                             with:aString allBold
-                             with:cls name)) ifFalse:[^ self].
+			     with:aString allBold
+			     with:cls name)) ifFalse:[^ self].
 
     self performRefactoring:(ProtectInstanceVariableRefactoring variable:aString class:cls).
 !
@@ -33508,43 +33943,43 @@
     "pull a class variable up to its superclasses"
 
     self withCurrentClassDo:[:cls |
-        |oldName node mthd nonMeta definingClass|
-
-        nonMeta := cls theNonMetaclass.
-
-        node := self findNode.
-        node isNil ifTrue:[
-            (self hasClassVariableSelectedInCodeView) ifFalse:[
-                oldName := self theSingleSelectedVariable.
-                oldName isNil ifTrue:[
-                    ^ self warn:'Please select a variable'
-                ]
-            ] ifTrue:[
-                oldName := self selectionInCodeView.
-            ]
-        ] ifFalse:[
-            node isVariable ifFalse:[
-                ^ self warn:'Please select a variable'
-            ].
-            oldName := node name.
-        ].
-
-        definingClass := nonMeta whichClassDefinesClassVar:oldName.
-        definingClass isNil ifTrue:[
-            self warn:'Oops - could not find the defining class'.
-            ^ self
-        ].
-        definingClass ~~ nonMeta ifTrue:[
-            (self confirm:'Will pull in ' , definingClass name , ' - OK ?')
-            ifFalse:[
-                ^ self
-            ].
-        ].
-        self codeMenuPullUpClassVariable:oldName inClass:definingClass.
-        mthd notNil ifTrue:[
-            "/ self switchToSelector:mthd selector.
-            self switchToMethod:mthd.
-        ].
+	|oldName node mthd nonMeta definingClass|
+
+	nonMeta := cls theNonMetaclass.
+
+	node := self findNode.
+	node isNil ifTrue:[
+	    (self hasClassVariableSelectedInCodeView) ifFalse:[
+		oldName := self theSingleSelectedVariable.
+		oldName isNil ifTrue:[
+		    ^ self warn:'Please select a variable'
+		]
+	    ] ifTrue:[
+		oldName := self selectionInCodeView.
+	    ]
+	] ifFalse:[
+	    node isVariable ifFalse:[
+		^ self warn:'Please select a variable'
+	    ].
+	    oldName := node name.
+	].
+
+	definingClass := nonMeta whichClassDefinesClassVar:oldName.
+	definingClass isNil ifTrue:[
+	    self warn:'Oops - could not find the defining class'.
+	    ^ self
+	].
+	definingClass ~~ nonMeta ifTrue:[
+	    (self confirm:'Will pull in ' , definingClass name , ' - OK ?')
+	    ifFalse:[
+		^ self
+	    ].
+	].
+	self codeMenuPullUpClassVariable:oldName inClass:definingClass.
+	mthd notNil ifTrue:[
+	    "/ self switchToSelector:mthd selector.
+	    self switchToMethod:mthd.
+	].
     ].
 !
 
@@ -33554,16 +33989,16 @@
     |refactoring|
 
     (self askIfModified) ifFalse:[
-        ^ self
+	^ self
     ].
 
     (Dialog
-        confirm:'About to rewrite methods...'
-        title:'About to rewrite methods...'
-        yesLabel:'proceed'
-        noLabel:'cancel')
+	confirm:'About to rewrite methods...'
+	title:'About to rewrite methods...'
+	yesLabel:'proceed'
+	noLabel:'cancel')
     ifFalse:[
-        ^ self
+	^ self
     ].
 
     refactoring := PullUpClassVariableRefactoring variable:oldName class:aClass superclass.
@@ -33574,44 +34009,44 @@
     "pull an instance variable up to its superclasses"
 
     self withCurrentClassDo:[:cls |
-        |oldName node mthd definingClass|
-
-        cls isMeta ifTrue:[
-            ^ self warn:'Please switch to the non-meta side.'
-        ].
-
-        node := self findNode.
-        node isNil ifTrue:[
-            (self hasInstanceVariableSelectedInCodeView) ifFalse:[
-                oldName := self theSingleSelectedVariable.
-                oldName isNil ifTrue:[
-                    ^ self warn:'Please select a variable'
-                ]
-            ] ifTrue:[
-                oldName := self selectionInCodeView.
-            ]
-        ] ifFalse:[
-            node isVariable ifFalse:[
-                ^ self warn:'Please select a variable'
-            ].
-            oldName := node name.
-        ].
-        definingClass := cls whichClassDefinesInstVar:oldName.
-        definingClass isNil ifTrue:[
-            self warn:'Oops - could not find the defining class'.
-            ^ self
-        ].
-        definingClass ~~ cls ifTrue:[
-            (self confirm:'Will pull in ' , definingClass name , ' - OK ?')
-            ifFalse:[
-                ^ self
-            ].
-        ].
-        self codeMenuPullUpInstanceVariable:oldName inClass:definingClass.
-        mthd notNil ifTrue:[
-            "/ self switchToSelector:mthd selector.
-            self switchToMethod:mthd.
-        ].
+	|oldName node mthd definingClass|
+
+	cls isMeta ifTrue:[
+	    ^ self warn:'Please switch to the non-meta side.'
+	].
+
+	node := self findNode.
+	node isNil ifTrue:[
+	    (self hasInstanceVariableSelectedInCodeView) ifFalse:[
+		oldName := self theSingleSelectedVariable.
+		oldName isNil ifTrue:[
+		    ^ self warn:'Please select a variable'
+		]
+	    ] ifTrue:[
+		oldName := self selectionInCodeView.
+	    ]
+	] ifFalse:[
+	    node isVariable ifFalse:[
+		^ self warn:'Please select a variable'
+	    ].
+	    oldName := node name.
+	].
+	definingClass := cls whichClassDefinesInstVar:oldName.
+	definingClass isNil ifTrue:[
+	    self warn:'Oops - could not find the defining class'.
+	    ^ self
+	].
+	definingClass ~~ cls ifTrue:[
+	    (self confirm:'Will pull in ' , definingClass name , ' - OK ?')
+	    ifFalse:[
+		^ self
+	    ].
+	].
+	self codeMenuPullUpInstanceVariable:oldName inClass:definingClass.
+	mthd notNil ifTrue:[
+	    "/ self switchToSelector:mthd selector.
+	    self switchToMethod:mthd.
+	].
     ].
 !
 
@@ -33621,24 +34056,24 @@
     |superClass refactoring|
 
     (self askIfModified) ifFalse:[
-        ^ self
+	^ self
     ].
 
     superClass := aClass superclass.
     superClass isNil ifTrue:[
-        ^ self warn:'No superClass to pull variables into.'.
+	^ self warn:'No superClass to pull variables into.'.
     ].
     superClass == Object ifTrue:[
-        ^ self warn:'Cannot pull variables into Object (may not have instVars).'.
+	^ self warn:'Cannot pull variables into Object (may not have instVars).'.
     ].
 
     (Dialog
-        confirm:('About to pull ''%1'' up into %2...'bindWith:varName allBold with:superClass name)
-        title:('About to pullUp ''%1''...' bindWith:varName)
-        yesLabel:'Proceed'
-        noLabel:'Cancel')
+	confirm:('About to pull ''%1'' up into %2...'bindWith:varName allBold with:superClass name)
+	title:('About to pullUp ''%1''...' bindWith:varName)
+	yesLabel:'Proceed'
+	noLabel:'Cancel')
     ifFalse:[
-        ^ self
+	^ self
     ].
 
     refactoring := PullUpInstanceVariableRefactoring variable:varName class:superClass.
@@ -33652,11 +34087,11 @@
 
     varName := self selectedInstanceVariableOrNil.
     varName notNil ifTrue:[
-        ^ self codeMenuPullUpInstanceVariable
+	^ self codeMenuPullUpInstanceVariable
     ].
     varName := self selectedClassVariableOrNil.
     varName notNil ifTrue:[
-        ^ self codeMenuPullUpClassVariable
+	^ self codeMenuPullUpClassVariable
     ].
 
     ^ self warn:'Please select a variable and try again.'
@@ -33666,42 +34101,42 @@
     "push a class variable down to its subclasses"
 
     self withCurrentClassDo:[:cls |
-        |oldName node mthd nonMeta definingClass|
-
-        nonMeta := cls theNonMetaclass.
-
-        node := self findNode.
-        node isNil ifTrue:[
-            (self hasClassVariableSelectedInCodeView) ifFalse:[
-                oldName := self theSingleSelectedVariable.
-                oldName isNil ifTrue:[
-                    ^ self warn:'Please select a variable'
-                ]
-            ] ifTrue:[
-                oldName := self selectionInCodeView.
-            ]
-        ] ifFalse:[
-            node isVariable ifFalse:[
-                ^ self warn:'Please select a variable'
-            ].
-            oldName := node name.
-        ].
-        definingClass := nonMeta whichClassDefinesClassVar:oldName.
-        definingClass isNil ifTrue:[
-            self warn:'Oops - could not find the defining class'.
-            ^ self
-        ].
-        definingClass ~~ nonMeta ifTrue:[
-            (self confirm:'Will push in ' , definingClass name , ' - OK ?')
-            ifFalse:[
-                ^ self
-            ].
-        ].
-        self codeMenuPushDownClassVariable:oldName inClass:definingClass.
-        mthd notNil ifTrue:[
-            "/ self switchToSelector:mthd selector.
-            self switchToMethod:mthd.
-        ].
+	|oldName node mthd nonMeta definingClass|
+
+	nonMeta := cls theNonMetaclass.
+
+	node := self findNode.
+	node isNil ifTrue:[
+	    (self hasClassVariableSelectedInCodeView) ifFalse:[
+		oldName := self theSingleSelectedVariable.
+		oldName isNil ifTrue:[
+		    ^ self warn:'Please select a variable'
+		]
+	    ] ifTrue:[
+		oldName := self selectionInCodeView.
+	    ]
+	] ifFalse:[
+	    node isVariable ifFalse:[
+		^ self warn:'Please select a variable'
+	    ].
+	    oldName := node name.
+	].
+	definingClass := nonMeta whichClassDefinesClassVar:oldName.
+	definingClass isNil ifTrue:[
+	    self warn:'Oops - could not find the defining class'.
+	    ^ self
+	].
+	definingClass ~~ nonMeta ifTrue:[
+	    (self confirm:'Will push in ' , definingClass name , ' - OK ?')
+	    ifFalse:[
+		^ self
+	    ].
+	].
+	self codeMenuPushDownClassVariable:oldName inClass:definingClass.
+	mthd notNil ifTrue:[
+	    "/ self switchToSelector:mthd selector.
+	    self switchToMethod:mthd.
+	].
     ].
 !
 
@@ -33711,16 +34146,16 @@
     |cls refactoring|
 
     (self askIfModified) ifFalse:[
-        ^ self
+	^ self
     ].
 
     (Dialog
-        confirm:'About to rewrite methods...'
-        title:'About to rewrite methods...'
-        yesLabel:'proceed'
-        noLabel:'cancel')
+	confirm:'About to rewrite methods...'
+	title:'About to rewrite methods...'
+	yesLabel:'proceed'
+	noLabel:'cancel')
     ifFalse:[
-        ^ self
+	^ self
     ].
 
     cls := aClass whichClassDefinesClassVar:oldName.
@@ -33732,44 +34167,44 @@
     "push an instance variable down to its subclasses"
 
     self withCurrentClassDo:[:cls |
-        |oldName node mthd definingClass|
-
-        cls isMeta ifTrue:[
-            ^ self warn:'Please switch to the non-meta side.'
-        ].
-
-        node := self findNode.
-        node isNil ifTrue:[
-            (self hasInstanceVariableSelectedInCodeView) ifFalse:[
-                oldName := self theSingleSelectedVariable.
-                oldName isNil ifTrue:[
-                    ^ self warn:'Please select a variable'
-                ]
-            ] ifTrue:[
-                oldName := self selectionInCodeView.
-            ]
-        ] ifFalse:[
-            node isVariable ifFalse:[
-                ^ self warn:'Please select a variable'
-            ].
-            oldName := node name.
-        ].
-        definingClass := cls whichClassDefinesInstVar:oldName.
-        definingClass isNil ifTrue:[
-            self warn:'Oops - could not find the defining class'.
-            ^ self
-        ].
-        definingClass ~~ cls ifTrue:[
-            (self confirm:'Will pull ''' , oldName , ''' from ' , definingClass name , ' - OK ?')
-            ifFalse:[
-                ^ self
-            ].
-        ].
-        self codeMenuPushDownInstanceVariable:oldName inClass:definingClass.
-        mthd notNil ifTrue:[
-            "/ self switchToSelector:mthd selector.
-            self switchToMethod:mthd.
-        ].
+	|oldName node mthd definingClass|
+
+	cls isMeta ifTrue:[
+	    ^ self warn:'Please switch to the non-meta side.'
+	].
+
+	node := self findNode.
+	node isNil ifTrue:[
+	    (self hasInstanceVariableSelectedInCodeView) ifFalse:[
+		oldName := self theSingleSelectedVariable.
+		oldName isNil ifTrue:[
+		    ^ self warn:'Please select a variable'
+		]
+	    ] ifTrue:[
+		oldName := self selectionInCodeView.
+	    ]
+	] ifFalse:[
+	    node isVariable ifFalse:[
+		^ self warn:'Please select a variable'
+	    ].
+	    oldName := node name.
+	].
+	definingClass := cls whichClassDefinesInstVar:oldName.
+	definingClass isNil ifTrue:[
+	    self warn:'Oops - could not find the defining class'.
+	    ^ self
+	].
+	definingClass ~~ cls ifTrue:[
+	    (self confirm:'Will pull ''' , oldName , ''' from ' , definingClass name , ' - OK ?')
+	    ifFalse:[
+		^ self
+	    ].
+	].
+	self codeMenuPushDownInstanceVariable:oldName inClass:definingClass.
+	mthd notNil ifTrue:[
+	    "/ self switchToSelector:mthd selector.
+	    self switchToMethod:mthd.
+	].
     ].
 !
 
@@ -33779,16 +34214,16 @@
     |cls refactoring|
 
     (self askIfModified) ifFalse:[
-        ^ self
+	^ self
     ].
 
     (Dialog
-        confirm:('About to push instance variable ''%1'' down to subclasses which use it...' bindWith:varName allBold)
-        title:('About to pushDown ''%1''...' bindWith:varName)
-        yesLabel:'Proceed'
-        noLabel:'Cancel')
+	confirm:('About to push instance variable ''%1'' down to subclasses which use it...' bindWith:varName allBold)
+	title:('About to pushDown ''%1''...' bindWith:varName)
+	yesLabel:'Proceed'
+	noLabel:'Cancel')
     ifFalse:[
-        ^ self
+	^ self
     ].
     cls := aClass whichClassDefinesInstVar:varName.
     refactoring := PushDownInstanceVariableRefactoring variable:varName class:cls.
@@ -33802,11 +34237,11 @@
 
     varName := self selectedInstanceVariableOrNil.
     varName notNil ifTrue:[
-        ^ self codeMenuPushDownInstanceVariable
+	^ self codeMenuPushDownInstanceVariable
     ].
     varName := self selectedClassVariableOrNil.
     varName notNil ifTrue:[
-        ^ self codeMenuPushDownClassVariable
+	^ self codeMenuPushDownClassVariable
     ].
 
     ^ self warn:'Please select a variable and try again.'
@@ -33818,22 +34253,22 @@
     |cls change methods|
 
     (self askIfModified) ifFalse:[
-        ^ self
+	^ self
     ].
 
     cls := aClass theNonMetaclass whichClassDefinesClassVar:oldName.
 
-    methods := self class 
-                    findClassRefsTo:oldName 
-                    under:cls access:#readOrWrite.
-"/    methods addAll:(self class 
-"/                    findClassRefsTo:oldName 
+    methods := self class
+		    findClassRefsTo:oldName
+		    under:cls access:#readOrWrite.
+"/    methods addAll:(self class
+"/                    findClassRefsTo:oldName
 "/                    under:cls theMetaclass access:#readOrWrite).
     methods notEmpty ifTrue:[
-        (Dialog confirm:(resources 
-                            stringWithCRs:'"%1" is still referenced by %2 method(s).\\Remove anyway ?'
-                            with:oldName
-                            with:methods size)) ifFalse:[^ self].
+	(Dialog confirm:(resources
+			    stringWithCRs:'"%1" is still referenced by %2 method(s).\\Remove anyway ?'
+			    with:oldName
+			    with:methods size)) ifFalse:[^ self].
     ].
 
     change := RemoveClassVariableChange remove:oldName from:cls.
@@ -33849,47 +34284,47 @@
 
     cls := aClass whichClassDefinesInstVar:oldName.
     cls isNil ifTrue:[
-        self error:'no class'
-    ].
-
-    methods := self class 
-                    findInstRefsTo:oldName 
-                    under:cls access:#readOrWrite.
+	self error:'no class'
+    ].
+
+    methods := self class
+		    findInstRefsTo:oldName
+		    under:cls access:#readOrWrite.
     methods notEmpty ifTrue:[
-        whatTypeOfMethods := 'method'.
-        (methods conform:[:m |
-                    |tree searcher|
-
-                    tree := RBParser 
-                                parseSearchMethod:m source 
-                                onError: [:str :pos | nil].
-
-                    searcher := ParseTreeSearcher isGetterOrSetterMethod:oldName.
-                    searcher executeTree:tree initialAnswer:false.    
-                ]) ifTrue:[ whatTypeOfMethods := 'accessor' ].
-
-        answer := OptionBox 
-                    request:(resources 
-                            stringWithCRs:'"%1" is still referenced by %2 %3(s).\\Remove these methods ?'
-                            with:oldName
-                            with:methods size
-                            with:whatTypeOfMethods)
-                    label:'Confirm Removal'
-                    image:(WarningBox iconBitmap)
-                    buttonLabels:(resources array:#('Cancel' 'Browse' 'No' 'Remove Methods'))
-                    values:#(#abort #browse false true)
-                    default:#abort
-                    onCancel:#abort.
-        answer == #abort ifTrue:[^ self].
-        answer == #browse ifTrue:[
-            self class 
-                browseMethods:methods 
-                title:(resources string:'Methods referring to %1' with:oldName).
-            ^ self.
-        ].
-        answer == true ifTrue:[
-            self doRemoveMethodsUnconfirmed:methods
-        ].
+	whatTypeOfMethods := 'method'.
+	(methods conform:[:m |
+		    |tree searcher|
+
+		    tree := RBParser
+				parseSearchMethod:m source
+				onError: [:str :pos | nil].
+
+		    searcher := ParseTreeSearcher isGetterOrSetterMethod:oldName.
+		    searcher executeTree:tree initialAnswer:false.
+		]) ifTrue:[ whatTypeOfMethods := 'accessor' ].
+
+	answer := OptionBox
+		    request:(resources
+			    stringWithCRs:'"%1" is still referenced by %2 %3(s).\\Remove these methods ?'
+			    with:oldName
+			    with:methods size
+			    with:whatTypeOfMethods)
+		    label:'Confirm Removal'
+		    image:(WarningBox iconBitmap)
+		    buttonLabels:(resources array:#('Cancel' 'Browse' 'No' 'Remove Methods'))
+		    values:#(#abort #browse false true)
+		    default:#abort
+		    onCancel:#abort.
+	answer == #abort ifTrue:[^ self].
+	answer == #browse ifTrue:[
+	    self class
+		browseMethods:methods
+		title:(resources string:'Methods referring to %1' with:oldName).
+	    ^ self.
+	].
+	answer == true ifTrue:[
+	    self doRemoveMethodsUnconfirmed:methods
+	].
     ].
 
     refactoring := RemoveInstanceVariableChange remove:oldName from:cls.
@@ -33910,7 +34345,7 @@
     | cls selector refactoring|
 
     (self askIfModified) ifFalse:[
-        ^ self
+	^ self
     ].
 
     cls := self theSingleSelectedMethod mclass.
@@ -33920,8 +34355,8 @@
     refactoring := RemoveParameterRefactoring removeParameter:parameterName in:cls selector:selector.
 
     (self findSendersOf:selector andConfirmRefactoring:refactoring) ifTrue:[
-        self performRefactoring:refactoring.
-        self switchToSelector:refactoring newSelector.
+	self performRefactoring:refactoring.
+	self switchToSelector:refactoring newSelector.
     ]
 !
 
@@ -33929,36 +34364,36 @@
     "rename a class variable"
 
     self withCurrentClassDo:[:cls |
-        |oldName node mthd cls definingClass|
-
-        node := self findNode.
-        node isNil ifTrue:[
-            (self hasClassVariableSelectedInCodeView) ifFalse:[
-                oldName := self theSingleSelectedVariable.
-                oldName isNil ifTrue:[
-                    ^ self warn:'Please select a variable'
-                ]
-            ] ifTrue:[
-                oldName := self selectionInCodeView.
-            ]
-        ] ifFalse:[
-            node isVariable ifFalse:[
-                ^ self warn:'Please select a variable'
-            ].
-            oldName := node name.
-        ].
-        definingClass := cls whichClassDefinesClassVar:oldName.
-        definingClass isNil ifTrue:[
-            self warn:'Oops - could not find the defining class'.
-            ^ self
-        ].
-        definingClass ~~ cls ifTrue:[
-            (self confirm:'Will rename in ' , definingClass name , ' - OK ?')
-            ifFalse:[
-                ^ self
-            ].
-        ].
-        self codeMenuRenameClassVariable:oldName inClass:definingClass.
+	|oldName node mthd cls definingClass|
+
+	node := self findNode.
+	node isNil ifTrue:[
+	    (self hasClassVariableSelectedInCodeView) ifFalse:[
+		oldName := self theSingleSelectedVariable.
+		oldName isNil ifTrue:[
+		    ^ self warn:'Please select a variable'
+		]
+	    ] ifTrue:[
+		oldName := self selectionInCodeView.
+	    ]
+	] ifFalse:[
+	    node isVariable ifFalse:[
+		^ self warn:'Please select a variable'
+	    ].
+	    oldName := node name.
+	].
+	definingClass := cls whichClassDefinesClassVar:oldName.
+	definingClass isNil ifTrue:[
+	    self warn:'Oops - could not find the defining class'.
+	    ^ self
+	].
+	definingClass ~~ cls ifTrue:[
+	    (self confirm:'Will rename in ' , definingClass name , ' - OK ?')
+	    ifFalse:[
+		^ self
+	    ].
+	].
+	self codeMenuRenameClassVariable:oldName inClass:definingClass.
     ].
 !
 
@@ -33968,20 +34403,20 @@
     |newName refactoring cls|
 
     (self askIfModified) ifFalse:[
-        ^ self
+	^ self
     ].
 
     newName := Dialog request:('Enter the new name for classVariable ''%1'':' bindWith:oldName) initialAnswer:oldName.
     newName isEmpty ifTrue:[
-        ^ self
+	^ self
     ].
     (cls := aClass whichClassDefinesClassVar:newName) notNil ifTrue:[
-        (Dialog confirm:(resources string:'Attention: a variable named ''%1'' is already defined in ''%2''.\\Proceed ?'
-                                with:newName allBold
-                                with:cls name allBold))
-        ifFalse:[
-            ^ self
-        ].
+	(Dialog confirm:(resources string:'Attention: a variable named ''%1'' is already defined in ''%2''.\\Proceed ?'
+				with:newName allBold
+				with:cls name allBold))
+	ifFalse:[
+	    ^ self
+	].
     ].
 
     (self confirm:'About to rewrite methods...') ifFalse:[^ self].
@@ -33996,44 +34431,44 @@
     "rename an instance variable"
 
     self withCurrentClassDo:[:cls |
-        |oldName node mthd definingClass|
-
-        cls isMeta ifTrue:[
-            ^ self warn:'Please switch to the non-meta side.'
-        ].
-
-        node := self findNode.
-        node isNil ifTrue:[
-            (self hasInstanceVariableSelectedInCodeView) ifFalse:[
-                oldName := self theSingleSelectedVariable.
-                oldName isNil ifTrue:[
-                    ^ self warn:'Please select a variable'
-                ]
-            ] ifTrue:[
-                oldName := self selectionInCodeView.
-            ]
-        ] ifFalse:[
-            node isVariable ifFalse:[
-                ^ self warn:'Please select a variable'
-            ].
-            oldName := node name.
-        ].
-        definingClass := cls whichClassDefinesInstVar:oldName.
-        definingClass isNil ifTrue:[
-            self warn:'Oops - could not find the defining class'.
-            ^ self
-        ].
-        definingClass ~~ cls ifTrue:[
-            (self confirm:'Will rename in ' , definingClass name , ' - OK ?')
-            ifFalse:[
-                ^ self
-            ].
-        ].
-        self codeMenuRenameInstanceVariable:oldName inClass:definingClass.
-        mthd notNil ifTrue:[
-            "/ self switchToSelector:mthd selector.
-            self switchToMethod:mthd.
-        ].
+	|oldName node mthd definingClass|
+
+	cls isMeta ifTrue:[
+	    ^ self warn:'Please switch to the non-meta side.'
+	].
+
+	node := self findNode.
+	node isNil ifTrue:[
+	    (self hasInstanceVariableSelectedInCodeView) ifFalse:[
+		oldName := self theSingleSelectedVariable.
+		oldName isNil ifTrue:[
+		    ^ self warn:'Please select a variable'
+		]
+	    ] ifTrue:[
+		oldName := self selectionInCodeView.
+	    ]
+	] ifFalse:[
+	    node isVariable ifFalse:[
+		^ self warn:'Please select a variable'
+	    ].
+	    oldName := node name.
+	].
+	definingClass := cls whichClassDefinesInstVar:oldName.
+	definingClass isNil ifTrue:[
+	    self warn:'Oops - could not find the defining class'.
+	    ^ self
+	].
+	definingClass ~~ cls ifTrue:[
+	    (self confirm:'Will rename in ' , definingClass name , ' - OK ?')
+	    ifFalse:[
+		^ self
+	    ].
+	].
+	self codeMenuRenameInstanceVariable:oldName inClass:definingClass.
+	mthd notNil ifTrue:[
+	    "/ self switchToSelector:mthd selector.
+	    self switchToMethod:mthd.
+	].
     ].
 !
 
@@ -34045,29 +34480,29 @@
     (self askIfModified) ifFalse:[ ^ self ].
 
     newName := Dialog
-                    request:(resources
-                                string:'Enter new name for %2 variable ''%1'':'
-                                with:oldName allBold
-                                with:(self meta value ifTrue:['classInstance'] ifFalse:['instance']))
-                    title:(resources string:'Rename Variable')
-                    initialAnswer:oldName.
+		    request:(resources
+				string:'Enter new name for %2 variable ''%1'':'
+				with:oldName allBold
+				with:(self meta value ifTrue:['classInstance'] ifFalse:['instance']))
+		    title:(resources string:'Rename Variable')
+		    initialAnswer:oldName.
     newName isEmpty ifTrue:[
-        ^ self
+	^ self
     ].
     (cls := aClass whichClassDefinesInstVar:newName) notNil ifTrue:[
-        Dialog warn:(resources string:'Sorry: a variable named ''%1'' is already defined in ''%2''.\\Proceed ?'
-                                with:newName allBold
-                                with:cls name allBold).
-        ^ self
+	Dialog warn:(resources string:'Sorry: a variable named ''%1'' is already defined in ''%2''.\\Proceed ?'
+				with:newName allBold
+				with:cls name allBold).
+	^ self
     ].
 
     (Dialog
-        confirm:(resources string:'About to rewrite methods...')
-        title:(resources string:'About to rewrite methods...')
-        yesLabel:(resources string:'Proceed')
-        noLabel:(resources string:'Cancel'))
+	confirm:(resources string:'About to rewrite methods...')
+	title:(resources string:'About to rewrite methods...')
+	yesLabel:(resources string:'Proceed')
+	noLabel:(resources string:'Cancel'))
     ifFalse:[
-        ^ self
+	^ self
     ].
     cls := aClass whichClassDefinesInstVar:oldName.
 
@@ -34081,12 +34516,12 @@
     |oldName newName node definingNode refactoring mthd initial|
 
     (self askIfModified) ifFalse:[
-        ^ self
+	^ self
     ].
 
     node := self findNode.
     (node isNil or:[node isVariable not]) ifTrue:[
-        ^ self warn:'Please select a temporary variable in the code.'
+	^ self warn:'Please select a temporary variable in the code.'
     ].
 
     oldName := node name.
@@ -34094,23 +34529,23 @@
     definingNode isNil ifTrue: [self warn: oldName , ' is not a temporary variable in the method'. ^ self].
 
     LastVariableRenames isNil ifTrue:[
-        LastVariableRenames := CacheDictionary new:30.
+	LastVariableRenames := CacheDictionary new:30.
     ].
     initial := LastVariableRenames at:oldName ifAbsent:oldName.
 
     newName := Dialog request:('Enter new name for ''%1'':' bindWith:oldName allBold) initialAnswer:initial.
     newName size == 0 ifTrue:[
-        ^ self   "/ cancel
+	^ self   "/ cancel
     ].
     newName = oldName ifTrue: [self warn: 'Same name given.'. ^ self].
 
     LastVariableRenames at:oldName put:newName.
 
     refactoring := RenameTemporaryRefactoring
-                        renameTemporaryFrom:node sourceInterval
-                        to:newName
-                        in:(mthd := self theSingleSelectedMethod) mclass
-                        selector:mthd selector.
+			renameTemporaryFrom:node sourceInterval
+			to:newName
+			in:(mthd := self theSingleSelectedMethod) mclass
+			selector:mthd selector.
     refactoring source:(self codeView contentsAsString).
     refactoring okToRenameAsKnownVariable:true.
 
@@ -34127,16 +34562,16 @@
 !
 
 findNodeForInterval:interval
-    ^ DoWhatIMeanSupport 
-        findNodeForInterval:interval 
-        in:(self codeView contentsAsString string).
+    ^ DoWhatIMeanSupport
+	findNodeForInterval:interval
+	in:(self codeView contentsAsString string).
 !
 
 findNodeForInterval:interval allowErrors:allowErrors
-    ^ DoWhatIMeanSupport 
-        findNodeForInterval:interval 
-        in:(self codeView contentsAsString string) 
-        allowErrors:allowErrors.
+    ^ DoWhatIMeanSupport
+	findNodeForInterval:interval
+	in:(self codeView contentsAsString string)
+	allowErrors:allowErrors.
 !
 
 findNodeIn:tree forInterval:interval
@@ -34146,19 +34581,19 @@
 self obsoleteMethodWarning.
     node := nil.
     tree nodesDo:[:each |
-        (each intersectsInterval:interval) ifTrue:[
-            (node isNil or:[node == each parent]) ifTrue:[
-                node := each
-            ] ifFalse:[
-                (node parent notNil
-                    and:[node parent isCascade and:[each parent isCascade]]) ifFalse:[^ nil]
-            ]
-        ] ifFalse:[
-            node notNil ifTrue:[
-                "/ already found one - beyond that one; leave
-                wouldReturn notNil ifTrue:[wouldReturn := node].
-            ]
-        ].
+	(each intersectsInterval:interval) ifTrue:[
+	    (node isNil or:[node == each parent]) ifTrue:[
+		node := each
+	    ] ifFalse:[
+		(node parent notNil
+		    and:[node parent isCascade and:[each parent isCascade]]) ifFalse:[^ nil]
+	    ]
+	] ifFalse:[
+	    node notNil ifTrue:[
+		"/ already found one - beyond that one; leave
+		wouldReturn notNil ifTrue:[wouldReturn := node].
+	    ]
+	].
     ].
 "/ (wouldReturn notNil and:[wouldReturn ~~ node]) ifTrue:[self halt].
     ^ node
@@ -34184,55 +34619,55 @@
     nClasses := classes size.
 
     nClasses > 0 ifTrue:[
-        firstClassName := classes first name allBold.
-        nClasses > 1 ifTrue:[
-            secondClassName := classes second name allBold.
-        ].
+	firstClassName := classes first name allBold.
+	nClasses > 1 ifTrue:[
+	    secondClassName := classes second name allBold.
+	].
     ].
 
     nClasses == 1 ifTrue:[
-        nSenders == 1 ifTrue:[
-            infoMsg := 'Proceed to rewrite sending method %5'
-        ] ifFalse:[
-            infoMsg := 'Proceed to rewrite %1 sending method(s) in %3'
-        ]
-    ] ifFalse:[
-        nClasses == 2 ifTrue:[
-            infoMsg := 'Proceed to rewrite %1 sending method(s) in %3 and %4'
-        ] ifFalse:[
-            infoMsg := 'Proceed to rewrite %1 sending method(s) in %2 class(es)'
-        ]
+	nSenders == 1 ifTrue:[
+	    infoMsg := 'Proceed to rewrite sending method %5'
+	] ifFalse:[
+	    infoMsg := 'Proceed to rewrite %1 sending method(s) in %3'
+	]
+    ] ifFalse:[
+	nClasses == 2 ifTrue:[
+	    infoMsg := 'Proceed to rewrite %1 sending method(s) in %3 and %4'
+	] ifFalse:[
+	    infoMsg := 'Proceed to rewrite %1 sending method(s) in %2 class(es)'
+	]
     ].
 
     infoMsg := resources
-                  string:infoMsg
-                  with:nSenders printString
-                  with:nClasses printString
-                  with:firstClassName
-                  with:secondClassName
-                  with:senders first whoString allBold.
-
-    infoMsg := infoMsg , (resources stringWithCRs:'\for "%1" ?' with:refactoring changeString).         
+		  string:infoMsg
+		  with:nSenders printString
+		  with:nClasses printString
+		  with:firstClassName
+		  with:secondClassName
+		  with:senders first whoString allBold.
+
+    infoMsg := infoMsg , (resources stringWithCRs:'\for "%1" ?' with:refactoring changeString).
 
     answer := Dialog
-                confirmWithCancel:infoMsg
-                labels:#('Cancel' 'Browse' 'Rewrite' )
-                values:#(nil #browse #rewrite)
-                default:3.
+		confirmWithCancel:infoMsg
+		labels:#('Cancel' 'Browse' 'Rewrite' )
+		values:#(nil #browse #rewrite)
+		default:3.
 
     answer == nil ifTrue:[
-        "/ cancel
-        ^ false
+	"/ cancel
+	^ false
     ].
 
     answer == #browse ifTrue:[
-        brwsr := self
-                    spawnMethodBrowserFor:senders in:#newBuffer
-                    label:'Senders of ' , selector
-                    perMethodInfo:nil
-                    sortBy:#class.
-        brwsr autoSearchPattern:selector.
-        ^ false
+	brwsr := self
+		    spawnMethodBrowserFor:senders in:#newBuffer
+		    label:'Senders of ' , selector
+		    perMethodInfo:nil
+		    sortBy:#class.
+	brwsr autoSearchPattern:selector.
+	^ false
     ].
     ^ true
 
@@ -34250,22 +34685,22 @@
     mthd := self theSingleSelectedMethod.
 
     tree := RBParser
-                    parseMethod:(codeView contentsAsString)
-                    onError: [:aString :position |
-                                codeView selectFromCharacterPosition:1 to:position.
-                                self showInfo:aString.
-                                ^ nil "ignore any error"
-                             ].
+		    parseMethod:(codeView contentsAsString)
+		    onError: [:aString :position |
+				codeView selectFromCharacterPosition:1 to:position.
+				self showInfo:aString.
+				^ nil "ignore any error"
+			     ].
     tree isNil ifTrue:[^ nil].
 
     newText := tree printString.
 
     self doSyntaxColoring value ~~ false ifTrue:[
-        newText := self syntaxHighlightedCodeFor:newText method:mthd.
+	newText := self syntaxHighlightedCodeFor:newText method:mthd.
     ].
     codeView
-        undoableDo:[ codeView replaceContentsWith:newText ]
-        info:'Format'.
+	undoableDo:[ codeView replaceContentsWith:newText ]
+	info:'Format'.
     codeView modified:true.
     navigationState realModifiedState:true.
     ^ newText.
@@ -34273,82 +34708,82 @@
 
 handlingRefactoringErrorDo:aBlock
     ^ Refactoring preconditionSignal
-        handle:[:ex |
-            |param answer errMsg dialogMsg|
-
-            errMsg := ex description.
-            param := ex parameter.
-            ex willProceed ifTrue:[
-                dialogMsg := (errMsg last == $?)
-                                    ifTrue:[errMsg]
-                                    ifFalse:[errMsg , '\\Do you want to proceed?' withCRs].
-
-                param notNil ifTrue:[
-                    answer := Dialog
-                                choose:dialogMsg
-                                labels:#('No' 'No, Browse' 'Yes')
-                                values:#(false #browse true)
-                                default:true
-                ] ifFalse:[
-                    answer := Dialog confirm:dialogMsg
-                ].
-
-                answer == #browse ifTrue:[
-                    "/ param is either a collection of classes, or methods;
-
-                    param := param collect:[:each | (each isKindOf:RBAbstractClass) ifTrue:[
-                                                        each realClass
-                                                    ] ifFalse:[
+	handle:[:ex |
+	    |param answer errMsg dialogMsg|
+
+	    errMsg := ex description.
+	    param := ex parameter.
+	    ex willProceed ifTrue:[
+		dialogMsg := (errMsg last == $?)
+				    ifTrue:[errMsg]
+				    ifFalse:[errMsg , '\\Do you want to proceed?' withCRs].
+
+		param notNil ifTrue:[
+		    answer := Dialog
+				choose:dialogMsg
+				labels:#('No' 'No, Browse' 'Yes')
+				values:#(false #browse true)
+				default:true
+		] ifFalse:[
+		    answer := Dialog confirm:dialogMsg
+		].
+
+		answer == #browse ifTrue:[
+		    "/ param is either a collection of classes, or methods;
+
+		    param := param collect:[:each | (each isKindOf:RBAbstractClass) ifTrue:[
+							each realClass
+						    ] ifFalse:[
 self error:'should not happen' mayProceed:true.
-                                                        (each isKindOf:RBMethod) ifTrue:[
-                                                        ] ifFalse:[
-                                                        ].
-                                                        each
-                                                    ]
-                                           ].
-
-                    param first isBehavior ifTrue:[
-                        self
-                            spawnClassBrowserFor:param
-                            label:'Classes affected by change'
-                            in:#newBrowser
-                            select:false
-                    ] ifFalse:[
-                        self
-                            spawnMethodBrowserFor:param
-                            in:#newBrowser
-                            label:'Methods affected by change'
-                    ].
-                    answer := false
-                    "/                    answer := Dialog confirm: (ex description last == $?
-                    "/                                            ifTrue: [ex description]
-                    "/                                            ifFalse: [ex description , '\Do you want to proceed?' withCRs]).
-                ].
-                answer ifTrue:[
-                    ex proceed
-                ]
-            ] ifFalse:[
-                param notNil ifTrue:[
-                    (Dialog confirm:errMsg) ifTrue:[
-                        ex parameter value
-                    ]
-                ] ifFalse:[
-                    ex mayProceed ifTrue:[
-                        (Dialog
-                            confirm:('Missing Precondition for refactoring:\\' withCRs , errMsg)
-                            yesLabel:'Proceed Anyway'
-                            noLabel:'Cancel')
-                        ifTrue:[
-                            ex proceed.
-                        ].
-                    ] ifFalse:[
-                        Dialog warn:('Refactoring failed:\\' withCRs , errMsg)
-                    ].
-                ]
-            ].
-            ex return
-        ]
-        do:[self topApplication withWaitCursorDo:aBlock]
+							(each isKindOf:RBMethod) ifTrue:[
+							] ifFalse:[
+							].
+							each
+						    ]
+					   ].
+
+		    param first isBehavior ifTrue:[
+			self
+			    spawnClassBrowserFor:param
+			    label:'Classes affected by change'
+			    in:#newBrowser
+			    select:false
+		    ] ifFalse:[
+			self
+			    spawnMethodBrowserFor:param
+			    in:#newBrowser
+			    label:'Methods affected by change'
+		    ].
+		    answer := false
+		    "/                    answer := Dialog confirm: (ex description last == $?
+		    "/                                            ifTrue: [ex description]
+		    "/                                            ifFalse: [ex description , '\Do you want to proceed?' withCRs]).
+		].
+		answer ifTrue:[
+		    ex proceed
+		]
+	    ] ifFalse:[
+		param notNil ifTrue:[
+		    (Dialog confirm:errMsg) ifTrue:[
+			ex parameter value
+		    ]
+		] ifFalse:[
+		    ex mayProceed ifTrue:[
+			(Dialog
+			    confirm:('Missing Precondition for refactoring:\\' withCRs , errMsg)
+			    yesLabel:'Proceed Anyway'
+			    noLabel:'Cancel')
+			ifTrue:[
+			    ex proceed.
+			].
+		    ] ifFalse:[
+			Dialog warn:('Refactoring failed:\\' withCRs , errMsg)
+		    ].
+		]
+	    ].
+	    ex return
+	]
+	do:[self topApplication withWaitCursorDo:aBlock]
 !
 
 operationsMenuRedo
@@ -34356,7 +34791,7 @@
 
     manager := RefactoryChangeManager instance.
     self changeRequest ifTrue:[
-        manager redoOperation.
+	manager redoOperation.
     ]
 !
 
@@ -34365,7 +34800,7 @@
 
     manager := RefactoryChangeManager instance.
     self changeRequest ifTrue:[
-        manager undoOperation.
+	manager undoOperation.
     ]
 !
 
@@ -34377,34 +34812,34 @@
     |rslt|
 
     aRefactoring isNil ifTrue:[
-        ^ self
+	^ self
     ].
 
     rslt := self
-                handlingRefactoringErrorDo:
-                    [
-                        | changes |
-                        aRefactoring isRefactoryChange ifTrue:[
-                            changes := aRefactoring.
-                            (UserPreferences current confirmRefactorings and:[changes shouldBeConfirmed]) ifTrue:[
-                                changes := ChangeSetBrowser2 confirmChanges: changes.
-                            ].
-                            RefactoryChangeManager performChange:changes.
-                        ] ifFalse:[
-                            UserPreferences current confirmRefactorings ifTrue:[
-                                aRefactoring primitiveExecute.
-                                changes := aRefactoring changes.
-                                changes changes size > 1 ifTrue:[
-                                    changes := ChangeSetBrowser2 confirmChanges: changes.
-                                    changes := (CompositeRefactoryChange named: (aRefactoring printString)) changes: changes.
-                                ].
-                                RefactoryChangeManager performChange:changes.
-                                RefactoringManager instance addRefactoring: aRefactoring performChanges: false.
-                            ] ifFalse:[
-                                aRefactoring execute
-                            ]
-                        ].
-                    ].
+		handlingRefactoringErrorDo:
+		    [
+			| changes |
+			aRefactoring isRefactoryChange ifTrue:[
+			    changes := aRefactoring.
+			    (UserPreferences current confirmRefactorings and:[changes shouldBeConfirmed]) ifTrue:[
+				changes := ChangeSetBrowser2 confirmChanges: changes.
+			    ].
+			    RefactoryChangeManager performChange:changes.
+			] ifFalse:[
+			    UserPreferences current confirmRefactorings ifTrue:[
+				aRefactoring primitiveExecute.
+				changes := aRefactoring changes.
+				changes changes size > 1 ifTrue:[
+				    changes := ChangeSetBrowser2 confirmChanges: changes.
+				    changes := (CompositeRefactoryChange named: (aRefactoring printString)) changes: changes.
+				].
+				RefactoryChangeManager performChange:changes.
+				RefactoringManager instance addRefactoring: aRefactoring performChanges: false.
+			    ] ifFalse:[
+				aRefactoring execute
+			    ]
+			].
+		    ].
 
     self enqueueDelayedUpdateCodeWithoutAutoSearch.
     ^ rslt
@@ -34422,15 +34857,15 @@
 
     varName := self selectedClassVariableInCodeViewOrNil.
     varName notNil ifTrue:[
-        cls := self theSingleSelectedClass theNonMetaclass whichClassDefinesClassVar:varName.
-        cls notNil ifTrue:[
-            ^ varName
-        ].
+	cls := self theSingleSelectedClass theNonMetaclass whichClassDefinesClassVar:varName.
+	cls notNil ifTrue:[
+	    ^ varName
+	].
     ].
 
     self showingClassVarsInVariableList ifTrue:[
-        varName := self theSingleSelectedVariable.
-        ^ varName.
+	varName := self theSingleSelectedVariable.
+	^ varName.
     ].
 
     ^ nil.
@@ -34445,15 +34880,15 @@
 
     varName := self selectedInstanceVariableInCodeViewOrNil.
     varName notNil ifTrue:[
-        cls := self theSingleSelectedClass whichClassDefinesInstVar:varName.
-        cls notNil ifTrue:[
-            ^ varName.
-        ].
+	cls := self theSingleSelectedClass whichClassDefinesInstVar:varName.
+	cls notNil ifTrue:[
+	    ^ varName.
+	].
     ].
 
     self showingClassVarsInVariableList ifFalse:[
-        varName := self theSingleSelectedVariable.
-        ^ varName.
+	varName := self theSingleSelectedVariable.
+	^ varName.
     ].
 
     ^ nil.
@@ -34474,7 +34909,7 @@
     (self canUseRefactoringSupport) ifFalse:[^ self].
 
     undoString := Dialog request: 'Enter undo stack size:\(i.e.: Number of remembered operations)' withCRs
-                         initialAnswer:(RefactoryChangeManager undoSize printString).
+			 initialAnswer:(RefactoryChangeManager undoSize printString).
 
     undoSize := Integer readFrom:undoString onError:nil.
     undoSize isNil ifTrue: [^self].
@@ -34493,15 +34928,15 @@
 self obsoleteMethodWarning.
     source := self codeView contentsAsString string.
     tree := RBParser
-                parseMethod:source
-                onError: [:str :err :nodesSoFar :parser|
-                        allowErrors ifTrue:[
-                            ^ parser currentMethodNode
-                        ].
-                        ^ nil
-                    ]
-                proceedAfterError:false
-                rememberNodes:true.
+		parseMethod:source
+		onError: [:str :err :nodesSoFar :parser|
+			allowErrors ifTrue:[
+			    ^ parser currentMethodNode
+			].
+			^ nil
+		    ]
+		proceedAfterError:false
+		rememberNodes:true.
 
     ^ tree
 
@@ -34512,16 +34947,16 @@
     |mthd cls|
 
     (self askIfModified) ifFalse:[
-        ^ self
+	^ self
     ].
 
     (mthd := self theSingleSelectedMethod) notNil ifTrue:[
-        cls := mthd mclass.
-    ] ifFalse:[
-        self codeAspect value ~= #classDefinition ifTrue:[
-            ^ self warn:'Select either a single class or a single method.'
-        ].
-        cls := self theSingleSelectedClass.
+	cls := mthd mclass.
+    ] ifFalse:[
+	self codeAspect value ~= #classDefinition ifTrue:[
+	    ^ self warn:'Select either a single class or a single method.'
+	].
+	cls := self theSingleSelectedClass.
     ].
     aOneArgBlock value:cls.
 
@@ -34532,7 +34967,7 @@
     |currentMethod cls selector|
 
     (self askIfModified) ifFalse:[
-        ^ self
+	^ self
     ].
 
     currentMethod := self theSingleSelectedMethod.
@@ -34550,39 +34985,39 @@
     "install a break/trace or countPoint for the current method(s)"
 
     self selectedMethodsDo:[:mthdArg |
-        |mthd originalMethod cls sel|
-
-        mthd := mthdArg.
-        cls := mthd mclass.
-        cls notNil ifTrue:[
-            sel := mthd selector.
-
-            doClear ifTrue:[
-                mthd isWrapped ifTrue:[
-                    originalMethod := mthd originalMethod.
-                    mthd clearBreakPoint.
-                    mthd := originalMethod.
-                    sel isNil ifTrue:[sel := mthd selector].
-                ].
-            ].
-
-            aSelector == #changeUpdateTrace ifTrue:[
-                MessageTracer traceUpdateMethod:mthd on:Transcript
-            ] ifFalse:[
-                aSelector numArgs == 0 ifTrue:[
-                    mthd perform:aSelector.
-                ] ifFalse:[
-                    mthd perform:aSelector with:argumentOrNil.
-                ]
-            ].
-
-            sel isNil ifTrue:[sel := mthd selector].
-            (sel isNil
-            and:[mthd isWrapped
-            and:[(originalMethod := mthd originalMethod) notNil]]) ifTrue:[
-                sel := originalMethod selector
-            ].
-        ]
+	|mthd originalMethod cls sel|
+
+	mthd := mthdArg.
+	cls := mthd mclass.
+	cls notNil ifTrue:[
+	    sel := mthd selector.
+
+	    doClear ifTrue:[
+		mthd isWrapped ifTrue:[
+		    originalMethod := mthd originalMethod.
+		    mthd clearBreakPoint.
+		    mthd := originalMethod.
+		    sel isNil ifTrue:[sel := mthd selector].
+		].
+	    ].
+
+	    aSelector == #changeUpdateTrace ifTrue:[
+		MessageTracer traceUpdateMethod:mthd on:Transcript
+	    ] ifFalse:[
+		aSelector numArgs == 0 ifTrue:[
+		    mthd perform:aSelector.
+		] ifFalse:[
+		    mthd perform:aSelector with:argumentOrNil.
+		]
+	    ].
+
+	    sel isNil ifTrue:[sel := mthd selector].
+	    (sel isNil
+	    and:[mthd isWrapped
+	    and:[(originalMethod := mthd originalMethod) notNil]]) ifTrue:[
+		sel := originalMethod selector
+	    ].
+	]
     ].
 !
 
@@ -34624,17 +35059,17 @@
     "/ resources := ResourcePack for:self class.
 
     Dialog aboutToOpenBoxNotificationSignal
-        handle:[:ex |
-            ex parameter window minExtent:300@300.
-            ex proceed.
-        ] do:[
-            class := Dialog
-                         choose:(resources string:'Break for (Sub-)Instances of')
-                         fromList:classList
-                         lines:20
-                         initialSelection:initialSelection  
-                         title:(resources string:'Break for some Instances only').
-        ].
+	handle:[:ex |
+	    ex parameter window minExtent:300@300.
+	    ex proceed.
+	] do:[
+	    class := Dialog
+			 choose:(resources string:'Break for (Sub-)Instances of')
+			 fromList:classList
+			 lines:20
+			 initialSelection:initialSelection
+			 title:(resources string:'Break for some Instances only').
+	].
 
     class isNil ifTrue:[^ self].
 "/    LastBreakPointClassName := class name.
@@ -34683,10 +35118,10 @@
      "/ stop if the receiver is a NewSystemBrowser
      "/     (context receiver isMemberOf:NewSystemBrowser)
 
-     "/ stop if some argument has a particular value 
-     "/     (context argAt:1) = ''hello'' 
-     "/     (context argAt:1) = 1234 
-     "/     (context argAt:1) = (context argAt:2) 
+     "/ stop if some argument has a particular value
+     "/     (context argAt:1) = ''hello''
+     "/     (context argAt:1) = 1234
+     "/     (context argAt:1) = (context argAt:2)
 
      "/ stop if the sender is a Workspace
      "/     (context sender receiver isMemberOf:Workspace)
@@ -34706,18 +35141,18 @@
 '.
 
     LastBreakPointConditionString isNil ifTrue:[
-        LastBreakPointConditionString := template.
+	LastBreakPointConditionString := template.
     ].
 
     "/ resources := ResourcePack for:self class.
 
     textHolder := ValueHolder new.
     dialog := Dialog
-                 forRequestText:(resources string:'Enter condition for breakpoint')
-                 lines:20
-                 columns:70
-                 initialAnswer:LastBreakPointConditionString
-                 model:textHolder.
+		 forRequestText:(resources string:'Enter condition for breakpoint')
+		 lines:20
+		 columns:70
+		 initialAnswer:LastBreakPointConditionString
+		 model:textHolder.
     dialog addButton:(Button label:'Template' action:[textHolder value:template. textHolder changed:#value.]).
     dialog open.
     dialog accepted ifFalse:[^ self].
@@ -34727,8 +35162,8 @@
 
     conditionBlock := Parser evaluate:conditionBlockString.
     conditionBlock isBlock ifFalse:[
-        self error:'bad input'.
-        ^ self
+	self error:'bad input'.
+	^ self
     ].
 
     self commonTraceHelperWith:#breakPointIf: with:conditionBlock clear:true
@@ -34746,33 +35181,33 @@
 
     processes := ProcessorScheduler knownProcesses asOrderedCollection.
     processes := processes select:[:aProcess |
-                        aProcess notNil
-                        and:[aProcess id notNil]
-                 ].
+			aProcess notNil
+			and:[aProcess id notNil]
+		 ].
     processes := processes sort:[:a :b | a id < b id].
     processNames := processes collect:[:aProcess |
-                        |pName theGroup top topLabel winLabel|
-
-                        pName := aProcess nameOrId.
-
-                        "/ if its a windowGroup process,
-                        "/ fetch its first topViews name and add.
-                        "/ (allows selecting among multiple browsers ...)
-                        winLabel := ''.
-
-                        theGroup := windowGroups detect:[:g | g process == aProcess] ifNone:nil.
-                        theGroup notNil ifTrue:[
-                            top := theGroup topViews.
-                            top size > 0 ifTrue:[
-                                top := top first.
-                                topLabel := top label.
-                                (topLabel notNil and:[topLabel ~= pName]) ifTrue:[
-                                     winLabel := '  ("' , topLabel , '")'.
-                                ]
-                            ].
-                        ].
-                        aProcess id printString , ' [' , pName , ']' , winLabel
-                    ].
+			|pName theGroup top topLabel winLabel|
+
+			pName := aProcess nameOrId.
+
+			"/ if its a windowGroup process,
+			"/ fetch its first topViews name and add.
+			"/ (allows selecting among multiple browsers ...)
+			winLabel := ''.
+
+			theGroup := windowGroups detect:[:g | g process == aProcess] ifNone:nil.
+			theGroup notNil ifTrue:[
+			    top := theGroup topViews.
+			    top size > 0 ifTrue:[
+				top := top first.
+				topLabel := top label.
+				(topLabel notNil and:[topLabel ~= pName]) ifTrue:[
+				     winLabel := '  ("' , topLabel , '")'.
+				]
+			    ].
+			].
+			aProcess id printString , ' [' , pName , ']' , winLabel
+		    ].
 
     "/ let user specify which one ...
 
@@ -34781,9 +35216,9 @@
     box list:processNames.
     box label:(resources string:'process selection').
     box title:(resources
-                string:'Stop if method is executed by process:\\(current process is %1)'
-                with:(Processor activeProcess id)
-                with:(Processor activeProcess nameOrId)) withCRs.
+		string:'Stop if method is executed by process:\\(current process is %1)'
+		with:(Processor activeProcess id)
+		with:(Processor activeProcess nameOrId)) withCRs.
     box action:[:selection | selectedProcessIndex := box selectionIndex].
     box initialSelection:(processes identityIndexOf:Processor activeProcess).
     box extent:(450 @ 350).
@@ -34791,10 +35226,10 @@
     box destroy.
 
     selectedProcessIndex notNil ifTrue:[
-        self
-            commonTraceHelperWith:#breakPointInProcess:
-            with:(processes at:selectedProcessIndex)
-            clear:true
+	self
+	    commonTraceHelperWith:#breakPointInProcess:
+	    with:(processes at:selectedProcessIndex)
+	    clear:true
     ].
 
     "Created: / 14-10-1996 / 15:40:53 / cg"
@@ -34806,9 +35241,10 @@
     "clear all coverage information"
 
     self withWaitCursorDo:[
-        InstrumentedMethod cleanAllInfoWithChange:false
-    ].
-    Smalltalk changed.
+	InstrumentedMethod cleanAllInfoWithChange:false
+    ].
+    Smalltalk changed:#coverageInfo.
+    self showCoverageInformation changed.   "/ to force update
 
     "Created: / 27-04-2010 / 19:00:32 / cg"
 !
@@ -34820,7 +35256,9 @@
 !
 
 debugMenuEnableGlobalCoverageRecording
-    InstrumentationContext new beActiveEverywhere
+    InstrumentationContext new
+	coverageOnly:true;
+	beActiveEverywhere
 
     "Created: / 21-09-2011 / 19:17:42 / cg"
 !
@@ -34850,40 +35288,40 @@
     |callingMethods allMethods|
 
     OOM::MetricVisualizer isNil ifTrue:[
-        Dialog information:'Missing class: OOM::MetricVisualizer'.
-        ^ self.
+	Dialog information:'Missing class: OOM::MetricVisualizer'.
+	^ self.
     ].
 
     callingMethods := Set new.
-    methods 
-        do:[:eachMethod |
-            |info|
-
-            InstrumentingCompiler callersOf:eachMethod do:[:callingMethod |
-                callingMethod == eachMethod ifFalse:[
-                    callingMethods add:callingMethod
-                ]
-            ]
-        ].
+    methods
+	do:[:eachMethod |
+	    |info|
+
+	    InstrumentingCompiler callersOf:eachMethod do:[:callingMethod |
+		callingMethod == eachMethod ifFalse:[
+		    callingMethods add:callingMethod
+		]
+	    ]
+	].
 
     callingMethods removeAllFoundIn:methods.
     callingMethods do:[:caller |
-        "/ dont do primitives...
-        caller hasPrimitiveCode ifFalse:[
-            caller mclass notNil ifTrue:[
-                caller isInstrumented ifFalse:[
-                    InstrumentingCompiler compileMethod:caller
-                ].                                              
-            ]
-        ].                                              
+	"/ dont do primitives...
+	caller hasPrimitiveCode ifFalse:[
+	    caller mclass notNil ifTrue:[
+		caller isInstrumented ifFalse:[
+		    InstrumentingCompiler compileMethod:caller
+		].
+	    ]
+	].
     ].
 
     allMethods := Set withAll:methods.
     allMethods addAll:callingMethods.
 
-    OOM::MetricVisualizer 
-        openViewerOnDiagramForMethods:allMethods 
-        setupWith:[:viewer | viewer set_DynamicMethodInvocationDiagram]
+    OOM::MetricVisualizer
+	openViewerOnDiagramForMethods:allMethods
+	setupWith:[:viewer | viewer set_DynamicMethodInvocationDiagram]
 
     "Created: / 27-04-2010 / 14:07:07 / cg"
 !
@@ -34900,9 +35338,9 @@
     "remove all breakpoints in the system"
 
     (MessageTracer notNil and:[MessageTracer isLoaded]) ifTrue:[
-        self withExecuteCursorDo:[
-            MessageTracer unwrapAllMethods
-        ]
+	self withExecuteCursorDo:[
+	    MessageTracer unwrapAllMethods
+	]
     ]
 !
 
@@ -34990,12 +35428,12 @@
 
     testedClassNames := Set new.
     self selectedNonAbstractTestCaseClassesDo:[:eachClass |
-        testedClassNames addAll:(eachClass testedClasses).
+	testedClassNames addAll:(eachClass testedClasses).
     ].
     testedClasses := testedClassNames collect:[:eachClassName | Smalltalk at:eachClassName].
 
-    testedClasses do:[:eachClass | 
-        self recompileClassWithInstrumentation:eachClass
+    testedClasses do:[:eachClass |
+	self recompileClassWithInstrumentation:eachClass
     ].
 
     self runTestCasesWithDebug:false protocols:nil.
@@ -35021,77 +35459,77 @@
     ^ self runTestCasesWithDebug:withDebug protocols:self selectedProtocolsValue.
 !
 
-runTestCasesWithDebug:withDebug protocols:protocolsOrNil 
+runTestCasesWithDebug:withDebug protocols:protocolsOrNil
     "run selected testcases"
-    
+
     |t embeddedTestRunner|
 
     embeddedTestRunner := self navigationState applicationOfComponent:#TestRunnerEmbedded.
     embeddedTestRunner notNil ifTrue:[
-        withDebug ifTrue:[
-            embeddedTestRunner runWithDebug
-            "/ embeddedTestRunner debug
-        ] ifFalse:[
-            embeddedTestRunner run
-        ].
-        ^ self
+	withDebug ifTrue:[
+	    embeddedTestRunner runWithDebug
+	    "/ embeddedTestRunner debug
+	] ifFalse:[
+	    embeddedTestRunner run
+	].
+	^ self
     ].
 
     "/ original code
     [
-        t := Time millisecondsToRun:
-                [
-                    self 
-                        selectedNonAbstractTestCaseClassesDo:[:cls | 
-                            |isCompleteSuite suite selectors toRun result|
-
-                            (protocolsOrNil isEmptyOrNil 
-                                or:[ protocolsOrNil includes:BrowserList nameListEntryForALL ]) 
-                                    ifTrue:[
-                                        isCompleteSuite := true.
-                                        suite := cls buildSuite.
-                                    ]
-                                    ifFalse:[
-                                        isCompleteSuite := false.
-                                        (selectors := self selectedSelectors) isEmptyOrNil ifTrue:[
-                                            selectors := OrderedCollection new.
-                                            self 
-                                                selectedProtocolMethodsDo:[:cls :category :sel :mthd | 
-                                                    (cls isTestCaseLike and:[ cls isAbstract not ]) ifTrue:[
-                                                        (cls isTestSelector:sel) ifTrue:[
-                                                            selectors add:sel
-                                                        ].
-                                                    ].
-                                                ].
-                                        ].
-                                        suite := cls buildSuiteFromMethods:selectors.
-                                    ].
-                            self busyLabel:'running test %1 ...' with:cls name.
-                            toRun := suite tests size.
-                            withDebug ifTrue:[
-                                result := TestResultForRunWithDebug new.
-                            ] ifFalse:[
-                                result := TestResult new.
-                            ].
-                            suite 
-                                run:result
-                                beforeEachDo:[:case :result | 
-                                    self showInfo:('To Run: %1 ; executing %2...' bindWith:toRun
-                                                with:case printString).
-                                ]
-                                afterEachDo:[:case :result | toRun := toRun - 1. ].
-
-                            result hasPassed ifTrue:[
-                                result passedCount > 0 ifTrue:[
-                                    self showInfo:(result printString asText colorizeAllWith:Color black
-                                                on:Color green).
-                                ].
-                            ] ifFalse:[
-                                self showInfo:(result printString asText colorizeAllWith:Color black
-                                            on:Color red).
-                            ].
-                        ].
-                ].
+	t := Time millisecondsToRun:
+		[
+		    self
+			selectedNonAbstractTestCaseClassesDo:[:cls |
+			    |isCompleteSuite suite selectors toRun result|
+
+			    (protocolsOrNil isEmptyOrNil
+				or:[ protocolsOrNil includes:BrowserList nameListEntryForALL ])
+				    ifTrue:[
+					isCompleteSuite := true.
+					suite := cls buildSuite.
+				    ]
+				    ifFalse:[
+					isCompleteSuite := false.
+					(selectors := self selectedSelectors) isEmptyOrNil ifTrue:[
+					    selectors := OrderedCollection new.
+					    self
+						selectedProtocolMethodsDo:[:cls :category :sel :mthd |
+						    (cls isTestCaseLike and:[ cls isAbstract not ]) ifTrue:[
+							(cls isTestSelector:sel) ifTrue:[
+							    selectors add:sel
+							].
+						    ].
+						].
+					].
+					suite := cls buildSuiteFromMethods:selectors.
+				    ].
+			    self busyLabel:'running test %1 ...' with:cls name.
+			    toRun := suite tests size.
+			    withDebug ifTrue:[
+				result := TestResultForRunWithDebug new.
+			    ] ifFalse:[
+				result := TestResult new.
+			    ].
+			    suite
+				run:result
+				beforeEachDo:[:case :result |
+				    self showInfo:('To Run: %1 ; executing %2...' bindWith:toRun
+						with:case printString).
+				]
+				afterEachDo:[:case :result | toRun := toRun - 1. ].
+
+			    result hasPassed ifTrue:[
+				result passedCount > 0 ifTrue:[
+				    self showInfo:(result printString asText colorizeAllWith:Color black
+						on:Color green).
+				].
+			    ] ifFalse:[
+				self showInfo:(result printString asText colorizeAllWith:Color black
+					    on:Color red).
+			    ].
+			].
+		].
     ] ensure:[ self normalLabel. ].
     Transcript showCR:(TimeDuration new setMilliseconds:t).
 
@@ -35109,20 +35547,20 @@
 
     selectedClasses := self selectedClassesValue.
     selectedClasses isEmptyOrNil ifTrue:[
-        selectedClasses := self selectedCategoryClasses
+	selectedClasses := self selectedCategoryClasses
     ].
 
     selectedClasses do:[:eachClass |
-        |cls|
-
-        cls := eachClass.
-        cls isLoaded ifFalse:[
-            cls := eachClass autoload.
-        ].
-        cls := cls theNonMetaclass.
-        (cls isTestCaseLike and:[cls isAbstract not]) ifTrue:[
-            aBlock value:cls
-        ]
+	|cls|
+
+	cls := eachClass.
+	cls isLoaded ifFalse:[
+	    cls := eachClass autoload.
+	].
+	cls := cls theNonMetaclass.
+	(cls isTestCaseLike and:[cls isAbstract not]) ifTrue:[
+	    aBlock value:cls
+	]
     ].
 
     "Modified: / 28-02-2012 / 16:52:45 / cg"
@@ -35183,8 +35621,8 @@
     classes := self selectedMethodsClasses asOrderedCollection.
 
     ^ self
-        classMenuCheckIn:true
-        classes:classes
+	classMenuCheckIn:true
+	classes:classes
 
     "Modified: / 18-11-2011 / 18:49:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 28-02-2012 / 09:12:37 / cg"
@@ -35198,9 +35636,9 @@
     classes := self selectedMethodsClasses asOrderedCollection.
 
     ^ self
-        classMenuCheckIn:true
-        classes:classes
-        usingManager: manager.
+	classMenuCheckIn:true
+	classes:classes
+	usingManager: manager.
 
     "Created: / 18-11-2011 / 18:49:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Created: / 21-12-2011 / 20:18:09 / cg"
@@ -35236,10 +35674,10 @@
 
 methodListMenuFileOutAllAsWithFormat:aFormatSymbolOrNil
     "fileOut all methods from the list -  file format as specified by the argument:
-        nil     - standard format
-        #xml    - XML standard format
-        #sif    - SIF (smalltalk interchange file) standard format
-        #binary - ST/X binary format
+	nil     - standard format
+	#xml    - XML standard format
+	#sif    - SIF (smalltalk interchange file) standard format
+	#binary - ST/X binary format
     "
 
     |methods|
@@ -35248,10 +35686,10 @@
     methods size == 0 ifTrue:[ ^ self ].
 
     self
-        fileOutMethods:methods
-        format:aFormatSymbolOrNil
-        fileNameTemplate:'someMethods'
-        boxTitle:'FileOut all listed methods as:'
+	fileOutMethods:methods
+	format:aFormatSymbolOrNil
+	fileNameTemplate:'someMethods'
+	boxTitle:'FileOut all listed methods as:'
 
     "Created: / 15.11.2001 / 17:53:22 / cg"
     "Modified: / 15.11.2001 / 18:00:20 / cg"
@@ -35366,30 +35804,29 @@
     brwsr := self spawnFullBrowserInClass:nil selector:nil in:where.
 
     classes size > 0 ifTrue:[
-        brwsr immediateUpdate value:true.
-        brwsr selectedCategories value:(classes collect:[:each | each theNonMetaclass category]) asSet asOrderedCollection.
-        anyNonMeta := classes contains:[:any | any isMeta not].
-        anyMeta := classes contains:[:any | any isMeta].
-        anyMeta ifFalse:[
-            brwsr selectedClasses value:classes
-        ] ifTrue:[
-            anyNonMeta ifFalse:[
-                brwsr meta value:true.
-                brwsr selectedClasses value:classes.
-            ]
-        ].
-        methods size == 1 ifTrue:[
-            brwsr selectProtocols:(methods collect:[:each | each category]) asSet asOrderedCollection.
-            brwsr selectedMethods value:methods
-        ].
-        brwsr immediateUpdate value:false.
+	brwsr immediateUpdate value:true.
+	brwsr selectedCategories value:(classes collect:[:each | each theNonMetaclass category]) asSet asOrderedCollection.
+	anyNonMeta := classes contains:[:any | any isMeta not].
+	anyMeta := classes contains:[:any | any isMeta].
+	anyMeta ifFalse:[
+	    brwsr selectedClasses value:classes
+	] ifTrue:[
+	    anyNonMeta ifFalse:[
+		brwsr meta value:true.
+		brwsr selectedClasses value:classes.
+	    ]
+	].
+	methods size == 1 ifTrue:[
+	    brwsr selectProtocols:(methods collect:[:each | each category]) asSet asOrderedCollection.
+	    brwsr selectedMethods value:methods
+	].
+	brwsr immediateUpdate value:false.
     ].
     ^ brwsr
 
     "Modified: / 28-02-2012 / 16:27:44 / cg"
 ! !
 
-
 !NewSystemBrowser methodsFor:'menu actions-namespace'!
 
 nameSpaceMenuCheckOut
@@ -35403,9 +35840,9 @@
 
     selectedNameSpaces := self selectedNamespaces value.
     selectedNameSpaceClasses := Smalltalk allClasses select:[:eachClass |
-                                                                  eachClass isPrivate not
-                                                                  and:[selectedNameSpaces includes:eachClass nameSpace name]
-                                                             ] .
+								  eachClass isPrivate not
+								  and:[selectedNameSpaces includes:eachClass nameSpace name]
+							     ] .
 
     self checkOutClasses:selectedNameSpaceClasses askForRevision:true
 !
@@ -35417,27 +35854,27 @@
 
     nm := Dialog request:(resources string:'Name of new NameSpace:').
     (nm isNil or:[(nm := nm withoutSeparators) size == 0]) ifTrue:[
-        ^ self
+	^ self
     ].
     existing := Smalltalk at:nm asSymbol ifAbsent:nil.
     existing notNil ifTrue:[
-        existing isNameSpace ifTrue:[
-            self warn:'A NameSpace named ''%1'' alread exists.' with:nm.
-            ^ self
-        ].
-        existing isBehavior ifFalse:[
-            self warn:'A class named ''%1'' alread exists.' with:nm.
-            ^ self
-        ].
-        self warn:'A global named ''%1'' alread exists.\(Currently bound to %2)' with:nm with:existing classNameWithArticle.
-        ^ self
+	existing isNameSpace ifTrue:[
+	    self warn:'A NameSpace named ''%1'' alread exists.' with:nm.
+	    ^ self
+	].
+	existing isBehavior ifFalse:[
+	    self warn:'A class named ''%1'' alread exists.' with:nm.
+	    ^ self
+	].
+	self warn:'A global named ''%1'' alread exists.\(Currently bound to %2)' with:nm with:existing classNameWithArticle.
+	^ self
     ].
     Class nameSpaceQuerySignal answer:Smalltalk do:[
-        ns := NameSpace fullName:nm.
+	ns := NameSpace fullName:nm.
     ].
     ns isNil ifTrue:[
-        self warn:'Could not create new NameSpace ''%1''.' with:nm.
-        ^ self
+	self warn:'Could not create new NameSpace ''%1''.' with:nm.
+	^ self
     ].
     self selectedNamespaces value:(Array with:nm)
 !
@@ -35446,12 +35883,12 @@
     "remove the selected namespace(s)"
 
     self selectedNamespacesValue do:[:nm |
-        |ns|
-
-        nm ~= BrowserList nameListEntryForALL ifTrue:[
-            ns := Smalltalk at:nm asSymbol.
-            Smalltalk removeClass:ns.
-        ]
+	|ns|
+
+	nm ~= BrowserList nameListEntryForALL ifTrue:[
+	    ns := Smalltalk at:nm asSymbol.
+	    Smalltalk removeClass:ns.
+	]
     ].
 !
 
@@ -35482,35 +35919,35 @@
 
 spawnNamespaceBrowserFor:namespaces in:where
     "browse selected namespace(s);
-        where is: #newBrowser - open a new browser showing the namespaces
-        where is: #newBuffer  - add a new buffer showing the namespaces"
+	where is: #newBrowser - open a new browser showing the namespaces
+	where is: #newBuffer  - add a new buffer showing the namespaces"
 
     |spec namespaceList singleSelection selectedClasses|
 
     (singleSelection := namespaces size == 1) ifTrue:[
-        spec := #singleNameSpaceBrowserSpec.
-        spec := #singleNameSpaceFullBrowserSpec.
-    ] ifFalse:[
-        spec := #multipleNameSpaceBrowserSpec.
-        spec := #multipleNameSpaceFullBrowserSpec.
+	spec := #singleNameSpaceBrowserSpec.
+	spec := #singleNameSpaceFullBrowserSpec.
+    ] ifFalse:[
+	spec := #multipleNameSpaceBrowserSpec.
+	spec := #multipleNameSpaceFullBrowserSpec.
     ].
 
     namespaceList := namespaces copy.
     selectedClasses := self selectedClassesValue.
 
     self
-        newBrowserOrBufferDependingOn:where
-        label:nil
-        forSpec:spec
-        setupWith:[:brwsr |
-            "/ setup for a constant list ...
-
-            "/ brwsr immediateUpdate value:true.
-            brwsr organizerMode value:(OrganizerCanvas organizerModeNamespace).
-            brwsr nameSpaceListGenerator value:namespaceList.
-            brwsr selectNamespaces:(singleSelection ifTrue:[namespaceList] ifFalse:[#()]).
-            "/ brwsr immediateUpdate value:false.
-        ]
+	newBrowserOrBufferDependingOn:where
+	label:nil
+	forSpec:spec
+	setupWith:[:brwsr |
+	    "/ setup for a constant list ...
+
+	    "/ brwsr immediateUpdate value:true.
+	    brwsr organizerMode value:(OrganizerCanvas organizerModeNamespace).
+	    brwsr nameSpaceListGenerator value:namespaceList.
+	    brwsr selectNamespaces:(singleSelection ifTrue:[namespaceList] ifFalse:[#()]).
+	    "/ brwsr immediateUpdate value:false.
+	]
 
     "Modified: / 28-02-2012 / 16:53:04 / cg"
 ! !
@@ -35540,22 +35977,22 @@
 openSettingsDialogAndSelect: settingsClassToSelectOrNil
     |settingsList settingsApp|
 
-    settingsList := 
-        #(
-            #('Editor'                  #'AbstractSettingsApplication::EditSettingsAppl'                )
-            #('Code Editor 2'           #'Tools::CodeView2SettingsAppl'                                 )
-            #('Syntax Color'            #'AbstractSettingsApplication::SyntaxColorSettingsAppl'         )
-            #('Code Format'             #'AbstractSettingsApplication::SourceCodeFormatSettingsAppl'    )
-            #('System Browser'          #'AbstractSettingsApplication::SystemBrowserSettingsAppl'       )
-            #('Compiler'                #'AbstractSettingsApplication::GeneralCompilerSettingsAppl'     )
-            #('Compiler/ByteCode'       #'AbstractSettingsApplication::ByteCodeCompilerSettingsAppl'    )
-            #('Source Code Management'  #'AbstractSettingsApplication::SourceCodeManagementSettingsAppl')
-            "/ see initializeSettingsList for how the following is expanded...
-            #('Source Code Management/[% managerTypeName]'     
-                                                '[ AbstractSourceCodeManager availableManagers 
-                                                     collect:[:each | each settingsApplicationClass] ]'    
-                                                                                                            '[% defaultIcon]' )
-        ).
+    settingsList :=
+	#(
+	    #('Editor'                  #'AbstractSettingsApplication::EditSettingsAppl'                )
+	    #('Code Editor 2'           #'Tools::CodeView2SettingsAppl'                                 )
+	    #('Syntax Color'            #'AbstractSettingsApplication::SyntaxColorSettingsAppl'         )
+	    #('Code Format'             #'AbstractSettingsApplication::SourceCodeFormatSettingsAppl'    )
+	    #('System Browser'          #'AbstractSettingsApplication::SystemBrowserSettingsAppl'       )
+	    #('Compiler'                #'AbstractSettingsApplication::GeneralCompilerSettingsAppl'     )
+	    #('Compiler/ByteCode'       #'AbstractSettingsApplication::ByteCodeCompilerSettingsAppl'    )
+	    #('Source Code Management'  #'AbstractSettingsApplication::SourceCodeManagementSettingsAppl')
+	    "/ see initializeSettingsList for how the following is expanded...
+	    #('Source Code Management/[% managerTypeName]'
+						'[ AbstractSourceCodeManager availableManagers
+						     collect:[:each | each settingsApplicationClass] ]'
+													    '[% defaultIcon]' )
+	).
 
     settingsApp := SettingsDialog new.
     "/ settingsApp requestor:self.
@@ -35563,7 +36000,7 @@
     settingsApp allButOpen.
     settingsApp showRoot: false.
     settingsClassToSelectOrNil notNil ifTrue:[
-        settingsApp selectItemWithClass: settingsClassToSelectOrNil.
+	settingsApp selectItemWithClass: settingsClassToSelectOrNil.
     ].
     settingsApp window label:('System Browser Settings').
     settingsApp openWindow.
@@ -35584,9 +36021,9 @@
 
 classMenuCheckInBuildSupportFiles
     self selectedNonMetaclassesDo:[:eachClass |
-        eachClass isProjectDefinition ifTrue:[
-            self projectMenuCheckInBuildSupportFilesForProject:eachClass package
-        ]
+	eachClass isProjectDefinition ifTrue:[
+	    self projectMenuCheckInBuildSupportFilesForProject:eachClass package
+	]
     ]
 
     "Created: / 09-08-2006 / 19:04:52 / fm"
@@ -35595,9 +36032,9 @@
 
 classMenuCheckInBuildSupportFilesUsingManager:aManagerOrNil
     self selectedNonMetaclassesDo:[:eachClass |
-        eachClass isProjectDefinition ifTrue:[
-            self projectMenuCheckInBuildSupportFilesForProject:eachClass package definition:eachClass usingManager:aManagerOrNil
-        ]
+	eachClass isProjectDefinition ifTrue:[
+	    self projectMenuCheckInBuildSupportFilesForProject:eachClass package definition:eachClass usingManager:aManagerOrNil
+	]
     ]
 
     "Modified: / 11-10-2011 / 23:16:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -35615,7 +36052,7 @@
 
     stream := '' writeStream.
     self selectedClassesValue do:[:cls |
-        cls theNonMetaclass fileOutOn:stream.
+	cls theNonMetaclass fileOutOn:stream.
     ].
 
     self window setClipboardText:stream contents
@@ -35625,10 +36062,25 @@
 
 classMenuFileOutBuildSupportFiles
     self selectedNonMetaclassesDo:[:eachClass |
-        eachClass isProjectDefinition ifTrue:[
-            self projectMenuFileOutBuildSupportFilesForProject:eachClass package
-        ]
-    ]
+	eachClass isProjectDefinition ifTrue:[
+	    self projectMenuFileOutBuildSupportFilesForProject:eachClass package
+	]
+    ]
+!
+
+classMenuPerforceSubmit
+
+    |utilities|
+
+    PerforceSourceCodeManager notNil ifTrue:[
+	utilities := PerforceSourceCodeManager utilities.
+
+	self withActivityNotificationsRedirectedToInfoLabelDo:[
+	    utilities submit.
+	].
+    ]
+    "Created: / 09-08-2006 / 19:04:52 / fm"
+    "Modified: / 12-09-2006 / 13:53:28 / cg"
 !
 
 generatePatchSetForClasses:classes
@@ -35637,20 +36089,20 @@
 
     |baseVersionTag patchVersionTag knownTags|
 
-    ((classes size <= 10) 
-        or:[ |answer|
-             answer := Dialog 
-                        confirmWithCancel:'Fetch known tags to choose from all classes?\(this may take some time)' withCRs
-                        default:false.
-             answer isNil ifTrue:[^ self].
-             answer == true
-           ]
+    ((classes size <= 10)
+	or:[ |answer|
+	     answer := Dialog
+			confirmWithCancel:'Fetch known tags to choose from all classes?\(this may take some time)' withCRs
+			default:false.
+	     answer isNil ifTrue:[^ self].
+	     answer == true
+	   ]
     ) ifTrue:[
-        "/ fetch from all classes
-        knownTags := self allKnownTagsInClasses:classes.
-    ] ifFalse:[
-        "/ only fetch from ProjectDefinitionClasses
-        knownTags := self allKnownTagsInClasses:(classes select:[:cls | cls isProjectDefinition]).
+	"/ fetch from all classes
+	knownTags := self allKnownTagsInClasses:classes.
+    ] ifFalse:[
+	"/ only fetch from ProjectDefinitionClasses
+	knownTags := self allKnownTagsInClasses:(classes select:[:cls | cls isProjectDefinition]).
     ].
 
     baseVersionTag := Dialog request:'Tag of Base Version:' initialAnswer:LastBaseVersionTag list:knownTags.
@@ -35674,71 +36126,71 @@
     fullPatchSet := ChangeSet new.
 
     classes do:[:eachClass |
-        |tagRevisionMapping baseVersion patchVersion baseVersionSource patchVersionSource 
-         baseChangeSet patchChangeSet diffSet thisPatchSet|
-
-        tagRevisionMapping := eachClass sourceCodeManager knownTagsAndRevisionsFor:eachClass.
-        (tagRevisionMapping includesKey:patchVersionTag) ifTrue:[
-            (tagRevisionMapping includesKey:baseVersionTag) ifTrue:[
-                "/ versions?
-                baseVersion := tagRevisionMapping at:baseVersionTag.
-                patchVersion := tagRevisionMapping at:patchVersionTag.
-
-                baseVersion ~= patchVersion ifTrue:[
-                    "/ change-sets...
-                    baseVersionSource := self getClassSourceFor:eachClass revision:baseVersionTag.
-                    patchVersionSource := self getClassSourceFor:eachClass revision:patchVersionTag.
-
-                    (baseVersionSource notNil and:[patchVersionSource notNil]) ifTrue:[
-                        baseChangeSet := ChangeSet fromStream:baseVersionSource readStream.
-                        patchChangeSet := ChangeSet fromStream:patchVersionSource readStream.
-                    ].
-
-                    diffSet := baseChangeSet diffSetsAgainst:patchChangeSet.
-                    thisPatchSet := ChangeSet fromDiffSet:diffSet.
-
-                    fullPatchSet addAll:thisPatchSet.
-                ].
-            ]
-        ]
+	|tagRevisionMapping baseVersion patchVersion baseVersionSource patchVersionSource
+	 baseChangeSet patchChangeSet diffSet thisPatchSet|
+
+	tagRevisionMapping := eachClass sourceCodeManager knownTagsAndRevisionsFor:eachClass.
+	(tagRevisionMapping includesKey:patchVersionTag) ifTrue:[
+	    (tagRevisionMapping includesKey:baseVersionTag) ifTrue:[
+		"/ versions?
+		baseVersion := tagRevisionMapping at:baseVersionTag.
+		patchVersion := tagRevisionMapping at:patchVersionTag.
+
+		baseVersion ~= patchVersion ifTrue:[
+		    "/ change-sets...
+		    baseVersionSource := self getClassSourceFor:eachClass revision:baseVersionTag.
+		    patchVersionSource := self getClassSourceFor:eachClass revision:patchVersionTag.
+
+		    (baseVersionSource notNil and:[patchVersionSource notNil]) ifTrue:[
+			baseChangeSet := ChangeSet fromStream:baseVersionSource readStream.
+			patchChangeSet := ChangeSet fromStream:patchVersionSource readStream.
+		    ].
+
+		    diffSet := baseChangeSet diffSetsAgainst:patchChangeSet.
+		    thisPatchSet := ChangeSet fromDiffSet:diffSet.
+
+		    fullPatchSet addAll:thisPatchSet.
+		].
+	    ]
+	]
     ].
     fullPatchSet size == 0 ifTrue:[
-        Dialog information:'Patch-Set is empty; nothing to generate.'.
-        ^ self.
+	Dialog information:'Patch-Set is empty; nothing to generate.'.
+	^ self.
     ].
 
     Expecco::KeyFileGenerator isNil ifTrue:[
-        buttonLabels := #('Cancel' 'Browse' 'Save as Patch...' ).
-        buttonValues := #(nil browse saveAsPatchFile ).   
-    ] ifFalse:[
-        buttonLabels := #('Cancel' 'Browse' 'Save as Signed Patch...' 'Save as Patch...' ).
-        buttonValues := #(nil browse saveAsSignedPatchFile saveAsPatchFile ).   
+	buttonLabels := #('Cancel' 'Browse' 'Save as Patch...' ).
+	buttonValues := #(nil browse saveAsPatchFile ).
+    ] ifFalse:[
+	buttonLabels := #('Cancel' 'Browse' 'Save as Signed Patch...' 'Save as Patch...' ).
+	buttonValues := #(nil browse saveAsSignedPatchFile saveAsPatchFile ).
     ].
 
     answer := OptionBox
-        request:('PatchSet contains %1 individual changes.\\Proceed how?' bindWith:fullPatchSet size) withCRs
-        label:'Patch-Set Generated'
-        buttonLabels:(resources array:buttonLabels)
-        values:buttonValues
-        default:#saveAsPatchFile.   
+	request:('PatchSet contains %1 individual changes.\\Proceed how?' bindWith:fullPatchSet size) withCRs
+	label:'Patch-Set Generated'
+	buttonLabels:(resources array:buttonLabels)
+	values:buttonValues
+	default:#saveAsPatchFile.
 
     (answer isNil) ifTrue:[ ^ self ].
 
     answer == #browse ifTrue:[
-        (UserPreferences current changeSetBrowserClass) openOn:fullPatchSet.
-        ^ self.
-    ].
-
-    fileName := Dialog 
-                    requestFileNameForSave:'Name of PatchFile' 
-                    default:('%1_to_%2.patch' bindWith:baseVersionTag with:patchVersionTag).
+	(UserPreferences current changeSetBrowserClass) openOn:fullPatchSet.
+	^ self.
+    ].
+
+    fileName := Dialog
+		    requestFileNameForSave:'Name of PatchFile'
+		    default:('%1_to_%2.patch' bindWith:baseVersionTag with:patchVersionTag).
     answer == #saveAsPatchFile ifTrue:[
-        fullPatchSet saveToFile:fileName.
-        ^ self.
+	fullPatchSet saveToFile:fileName.
+	^ self.
     ].
     answer == #saveAsSignedPatchFile ifTrue:[
-        fullPatchSet saveSignedToFile:fileName.
-        ^ self.
+	fullPatchSet saveSignedToFile:fileName.
+	^ self.
     ].
 
     "Created: / 08-02-2011 / 09:44:36 / cg"
@@ -35747,23 +36199,23 @@
 
 generateProjectDefinitionsIn:classes
     self
-        generateUndoableChange:'Generate Project Definitions'
-        overClasses:classes
-        via:[:generator :eachClass |
-            Class packageQuerySignal
-                answer:eachClass package
-                do:[
-                    eachClass theNonMetaclass
-                        forEachMethodsCodeToCompileDo:
-                            [:code :category |
-                                generator
-                                    compile:code
-                                    forClass:eachClass theMetaclass
-                                    inCategory:category.
-                            ]
-                        ignoreOldDefinition:false
-                ].
-        ].
+	generateUndoableChange:'Generate Project Definitions'
+	overClasses:classes
+	via:[:generator :eachClass |
+	    Class packageQuerySignal
+		answer:eachClass package
+		do:[
+		    eachClass theNonMetaclass
+			forEachMethodsCodeToCompileDo:
+			    [:code :category |
+				generator
+				    compile:code
+				    forClass:eachClass theMetaclass
+				    inCategory:category.
+			    ]
+			ignoreOldDefinition:false
+		].
+	].
 
     "Created: / 10-08-2006 / 16:33:07 / cg"
     "Modified: / 14-09-2006 / 10:53:13 / cg"
@@ -35775,19 +36227,19 @@
     |tempFile stream|
 
     [
-        tempFile := Filename newTemporary.
-        [
-            stream := tempFile writeStream.
-
-            classes do:[:cls |
-                cls theNonMetaclass fileOutOn:stream.
-            ].
-        ] ensure:[
-            stream close.
-        ].
-        self sendFileViaEmail:tempFile subject:subject.
+	tempFile := Filename newTemporary.
+	[
+	    stream := tempFile writeStream.
+
+	    classes do:[:cls |
+		cls theNonMetaclass fileOutOn:stream.
+	    ].
+	] ensure:[
+	    stream close.
+	].
+	self sendFileViaEmail:tempFile subject:subject.
     ] ensure:[
-        tempFile delete
+	tempFile delete
     ].
 
     "Created: / 20-09-2007 / 15:01:42 / cg"
@@ -35797,204 +36249,204 @@
     |bindings listOfObsoleteContainers listOfObsoleteContainerAssocs menuPerformer|
 
     needExtensionsContainer ~~ hasExtensionContainer ifTrue:[
-        self halt
+	self halt
     ].
     listOfObsoleteContainers := OrderedCollection new.
     listOfObsoleteContainerAssocs := OrderedCollection new.
     obsoleteContainers do:[:eachAssoc |
-        eachAssoc value do:[:eachObsolete |
-            listOfObsoleteContainerAssocs add:eachAssoc key -> eachObsolete.
-            listOfObsoleteContainers add:eachObsolete , ' (in ' , eachAssoc key , ')'
-        ]
+	eachAssoc value do:[:eachObsolete |
+	    listOfObsoleteContainerAssocs add:eachAssoc key -> eachObsolete.
+	    listOfObsoleteContainers add:eachObsolete , ' (in ' , eachAssoc key , ')'
+	]
     ].
     bindings := IdentityDictionary new.
     bindings at:#listOfObsoleteContainers put:listOfObsoleteContainers.
     bindings at:#listOfClassesWithRepositoryMismatches
-        put:classesWithRepositoryMismatches.
+	put:classesWithRepositoryMismatches.
     bindings at:#listOfClassesWithMissingContainer
-        put:classesWithMissingContainer.
+	put:classesWithMissingContainer.
     bindings at:#listOfClassesWhichHaveBeenModified
-        put:classesWhichHaveBeenModified.
+	put:classesWhichHaveBeenModified.
     bindings at:#listOfClassesWithNewerVersionInRepository
-        put:classesWithNewerVersionInRepository.
+	put:classesWithNewerVersionInRepository.
     bindings at:#obsoleteContainersBoxVisible
-        put:listOfObsoleteContainers size > 0.
+	put:listOfObsoleteContainers size > 0.
     bindings at:#classesWithInvalidInfoBoxVisible
-        put:classesWithRepositoryMismatches size > 0.
+	put:classesWithRepositoryMismatches size > 0.
     bindings at:#classesWithoutContainerBoxVisible
-        put:classesWithMissingContainer size > 0.
+	put:classesWithMissingContainer size > 0.
     bindings at:#classesWhichHaveBeenModifiedBoxVisible
-        put:classesWhichHaveBeenModified size > 0.
+	put:classesWhichHaveBeenModified size > 0.
     bindings at:#classesWithNewerVersionInRepositoryBoxVisible
-        put:classesWithNewerVersionInRepository size > 0.
+	put:classesWithNewerVersionInRepository size > 0.
     bindings at:#selectedClassesWithMissingContainer put:ValueHolder new.
     bindings at:#selectedClassesWithRepositoryMismatches put:ValueHolder new.
     bindings at:#selectedObsoleteContainers put:ValueHolder new.
     bindings at:#selectedClassesWhichHaveBeenModified put:ValueHolder new.
     bindings at:#selectedClassesWithNewerVersionInRepository
-        put:ValueHolder new.
+	put:ValueHolder new.
     menuPerformer := Plug new.
     menuPerformer respondTo:#classMenuFileOutAs
-        with:[
-            |classes|
-
-            classes := (bindings at:#selectedClassesWithMissingContainer) value
-                        collect:[:idx | classesWithMissingContainer at:idx].
-            classes do:[:cls |
-                self
-                    fileOutClass:cls
-                    askForFile:true
-                    withCancelAll:false
-                    format:nil
-                    sourceMode:nil
-            ]
-        ].
+	with:[
+	    |classes|
+
+	    classes := (bindings at:#selectedClassesWithMissingContainer) value
+			collect:[:idx | classesWithMissingContainer at:idx].
+	    classes do:[:cls |
+		self
+		    fileOutClass:cls
+		    askForFile:true
+		    withCancelAll:false
+		    format:nil
+		    sourceMode:nil
+	    ]
+	].
     menuPerformer respondTo:#classMenuCheckIn
-        with:[
-            |classes|
-
-            classes := (bindings at:#selectedClassesWithMissingContainer) value
-                        collect:[:idx | classesWithMissingContainer at:idx].
-            SourceCodeManagerUtilities default
-                checkinClasses:classes
-                withInfo:nil
-                withCheck:true
-        ].
+	with:[
+	    |classes|
+
+	    classes := (bindings at:#selectedClassesWithMissingContainer) value
+			collect:[:idx | classesWithMissingContainer at:idx].
+	    SourceCodeManagerUtilities default
+		checkinClasses:classes
+		withInfo:nil
+		withCheck:true
+	].
     menuPerformer respondTo:#classMenuSpawnClass
-        with:[
-            |classes|
-
-            classes := (bindings at:#selectedClassesWithMissingContainer) value
-                        collect:[:idx | classesWithMissingContainer at:idx].
-            self spawnClassBrowserFor:classes in:#newBrowser
-        ].
+	with:[
+	    |classes|
+
+	    classes := (bindings at:#selectedClassesWithMissingContainer) value
+			collect:[:idx | classesWithMissingContainer at:idx].
+	    self spawnClassBrowserFor:classes in:#newBrowser
+	].
     menuPerformer respondTo:#classMenuRemove
-        with:[
-            |classes classesToRemove|
-
-            classes := (bindings at:#selectedClassesWithMissingContainer) value
-                        collect:[:idx | classesWithMissingContainer at:idx].
-            classes do:[:cls |
-                classesToRemove := OrderedCollection new.
-                self
-                    addClassesToRemoveForClass:cls
-                    to:classesToRemove
-                    removingSubclasses:true
-                    withCancel:nil.
-                self removeClasses:classesToRemove pullUpSubclasses:false
-            ]
-        ].
+	with:[
+	    |classes classesToRemove|
+
+	    classes := (bindings at:#selectedClassesWithMissingContainer) value
+			collect:[:idx | classesWithMissingContainer at:idx].
+	    classes do:[:cls |
+		classesToRemove := OrderedCollection new.
+		self
+		    addClassesToRemoveForClass:cls
+		    to:classesToRemove
+		    removingSubclasses:true
+		    withCancel:nil.
+		self removeClasses:classesToRemove pullUpSubclasses:false
+	    ]
+	].
     menuPerformer respondTo:#classMenu2SpawnClass
-        with:[
-            |classes|
-
-            classes := (bindings at:#selectedClassesWithNewerVersionInRepository)
-                        value collect:[:idx | classesWithNewerVersionInRepository at:idx].
-            self spawnClassBrowserFor:classes in:#newBrowser
-        ].
+	with:[
+	    |classes|
+
+	    classes := (bindings at:#selectedClassesWithNewerVersionInRepository)
+			value collect:[:idx | classesWithNewerVersionInRepository at:idx].
+	    self spawnClassBrowserFor:classes in:#newBrowser
+	].
     menuPerformer respondTo:#classMenu2CheckOutNewest
-        with:[
-            |classes|
-
-            classes := (bindings at:#selectedClassesWithNewerVersionInRepository)
-                        value collect:[:idx | classesWithNewerVersionInRepository at:idx].
-            self checkOutClasses:classes askForRevision:false
-        ].
+	with:[
+	    |classes|
+
+	    classes := (bindings at:#selectedClassesWithNewerVersionInRepository)
+			value collect:[:idx | classesWithNewerVersionInRepository at:idx].
+	    self checkOutClasses:classes askForRevision:false
+	].
     menuPerformer respondTo:#classMenu2CompareAgainstNewestInRepository
-        with:[
-            |classes|
-
-            classes := (bindings at:#selectedClassesWithNewerVersionInRepository)
-                        value collect:[:idx | classesWithNewerVersionInRepository at:idx].
-            classes do:[:cls |
-                self compareAgainstNewestInRepository:cls
-            ]
-        ].
+	with:[
+	    |classes|
+
+	    classes := (bindings at:#selectedClassesWithNewerVersionInRepository)
+			value collect:[:idx | classesWithNewerVersionInRepository at:idx].
+	    classes do:[:cls |
+		self compareAgainstNewestInRepository:cls
+	    ]
+	].
     menuPerformer respondTo:#classMenu3FileOutAs
-        with:[
-            |classes|
-
-            classes := (bindings at:#selectedClassesWhichHaveBeenModified) value
-                        collect:[:idx | classesWhichHaveBeenModified at:idx].
-            classes do:[:cls |
-                self
-                    fileOutClass:cls
-                    askForFile:true
-                    withCancelAll:false
-                    format:nil
-                    sourceMode:nil
-            ]
-        ].
+	with:[
+	    |classes|
+
+	    classes := (bindings at:#selectedClassesWhichHaveBeenModified) value
+			collect:[:idx | classesWhichHaveBeenModified at:idx].
+	    classes do:[:cls |
+		self
+		    fileOutClass:cls
+		    askForFile:true
+		    withCancelAll:false
+		    format:nil
+		    sourceMode:nil
+	    ]
+	].
     menuPerformer respondTo:#classMenu3CheckIn
-        with:[
-            |classes|
-
-            classes := (bindings at:#selectedClassesWhichHaveBeenModified) value
-                        collect:[:idx | classesWhichHaveBeenModified at:idx].
-
-            SourceCodeManagerUtilities default
-                checkinClasses:classes
-                withInfo:nil
-                withCheck:true
-        ].
+	with:[
+	    |classes|
+
+	    classes := (bindings at:#selectedClassesWhichHaveBeenModified) value
+			collect:[:idx | classesWhichHaveBeenModified at:idx].
+
+	    SourceCodeManagerUtilities default
+		checkinClasses:classes
+		withInfo:nil
+		withCheck:true
+	].
     menuPerformer respondTo:#classMenu3SpawnClass
-        with:[
-            |classes|
-
-            classes := (bindings at:#selectedClassesWhichHaveBeenModified) value
-                        collect:[:idx | classesWhichHaveBeenModified at:idx].
-            self spawnClassBrowserFor:classes in:#newBrowser
-        ].
+	with:[
+	    |classes|
+
+	    classes := (bindings at:#selectedClassesWhichHaveBeenModified) value
+			collect:[:idx | classesWhichHaveBeenModified at:idx].
+	    self spawnClassBrowserFor:classes in:#newBrowser
+	].
     menuPerformer respondTo:#classMenu3CompareAgainstNewestInRepository
-        with:[
-            |classes|
-
-            classes := (bindings at:#selectedClassesWhichHaveBeenModified) value
-                        collect:[:idx | classesWhichHaveBeenModified at:idx].
-            classes do:[:cls |
-                self compareAgainstNewestInRepository:cls
-            ]
-        ].
+	with:[
+	    |classes|
+
+	    classes := (bindings at:#selectedClassesWhichHaveBeenModified) value
+			collect:[:idx | classesWhichHaveBeenModified at:idx].
+	    classes do:[:cls |
+		self compareAgainstNewestInRepository:cls
+	    ]
+	].
     menuPerformer respondTo:#classMenu4CheckOut
-        with:[
-            |containers|
-
-            containers := (bindings at:#selectedObsoleteContainers) value.
-            containers do:[:container |
-                |def packageID moduleDir packageDir fileName|
-
-                def := listOfObsoleteContainerAssocs at:container.
-                packageID := def key.
-                moduleDir := packageID upTo:$:.
-                packageDir := packageID copyFrom:moduleDir size + 2.
-                fileName := def value.
-
-                "/ check out that module ...
-                SourceCodeManager
-                    checkoutModule:moduleDir
-                    directory:packageDir
-                    andDo:[:tempDir |
-                        "/                                       (Dialog confirm:'FileIn ' , fileName , ' ?') ifTrue:[
-
-
-                        Smalltalk fileIn:(tempDir asFilename construct:fileName)
-                        "/                                       ]
-                    ]
-            ]
-        ].
+	with:[
+	    |containers|
+
+	    containers := (bindings at:#selectedObsoleteContainers) value.
+	    containers do:[:container |
+		|def packageID moduleDir packageDir fileName|
+
+		def := listOfObsoleteContainerAssocs at:container.
+		packageID := def key.
+		moduleDir := packageID upTo:$:.
+		packageDir := packageID copyFrom:moduleDir size + 2.
+		fileName := def value.
+
+		"/ check out that module ...
+		SourceCodeManager
+		    checkoutModule:moduleDir
+		    directory:packageDir
+		    andDo:[:tempDir |
+			"/                                       (Dialog confirm:'FileIn ' , fileName , ' ?') ifTrue:[
+
+
+			Smalltalk fileIn:(tempDir asFilename construct:fileName)
+			"/                                       ]
+		    ]
+	    ]
+	].
     bindings at:#classesWithMissingContainerPopupMenu
-        put:self class classesWithMissingContainerPopupMenu.
+	put:self class classesWithMissingContainerPopupMenu.
     bindings at:#classesWithNewerVersionInRepositoryPopupMenu
-        put:self class classesWithNewerVersionInRepositoryPopupMenu.
+	put:self class classesWithNewerVersionInRepositoryPopupMenu.
     bindings at:#classesWhichHaveBeenModifiedPopupMenu
-        put:self class classesWhichHaveBeenModifiedPopupMenu.
+	put:self class classesWhichHaveBeenModifiedPopupMenu.
     bindings at:#obsoleteContainersPopupMenu
-        put:self class obsoleteContainersPopupMenu.
+	put:self class obsoleteContainersPopupMenu.
     bindings at:#dialogMenuPerformer put:menuPerformer.
 
-    SimpleDialog new 
-        openSpec:(self class repositoryConsistencyDialogSpec)
-        withBindings:bindings
+    SimpleDialog new
+	openSpec:(self class repositoryConsistencyDialogSpec)
+	withBindings:bindings
 
     "Modified: / 23-08-2006 / 14:08:28 / cg"
     "Modified (format): / 01-07-2011 / 17:16:31 / cg"
@@ -36005,24 +36457,24 @@
 
     projectClasses := OrderedCollection new.
     self selectedProjectsDo:[:packageID |
-        |defClass answer|
-
-        defClass := ProjectDefinition definitionClassForPackage:packageID createIfAbsent:false.
-        defClass isNil ifTrue:[
-            answer := Dialog
-                        confirm:(resources
-                                stringWithCRs:'Missing ProjectDefinition for %1\\Create ?'
-                                with:packageID allBold)
-                        withCancel:(self selectedProjects value size > 1)
-                        default: true.
-            answer isNil ifTrue:[^ self ].
-            answer == true ifTrue:[
-                defClass := self projectDefinitionDialogFor:packageID.
-            ].
-        ].
-        defClass notNil ifTrue:[
-            projectClasses add:defClass.
-        ]
+	|defClass answer|
+
+	defClass := ProjectDefinition definitionClassForPackage:packageID createIfAbsent:false.
+	defClass isNil ifTrue:[
+	    answer := Dialog
+			confirm:(resources
+				stringWithCRs:'Missing ProjectDefinition for %1\\Create ?'
+				with:packageID allBold)
+			withCancel:(self selectedProjects value size > 1)
+			default: true.
+	    answer isNil ifTrue:[^ self ].
+	    answer == true ifTrue:[
+		defClass := self projectDefinitionDialogFor:packageID.
+	    ].
+	].
+	defClass notNil ifTrue:[
+	    projectClasses add:defClass.
+	]
     ].
 
     ^ projectClasses
@@ -36036,47 +36488,47 @@
      projectDefinitionClass y defaultProjectType setupDefaultType|
 
     setupDefaultType :=
-        [:package |
-            |classesInPackage|
-
-            classesInPackage := Smalltalk allClassesInPackage:package.
-            classesInPackage isEmpty ifTrue:[
-                defaultProjectType := LastNewProjectType ? ProjectDefinition guiApplicationType
-            ] ifFalse:[
-                (classesInPackage contains:[:cls | cls isBrowserStartable]) ifTrue:[
-                    (classesInPackage contains:[:cls | cls isVisualStartable])
-                        ifTrue:[ defaultProjectType := ProjectDefinition guiApplicationType]
-                        ifFalse:[ defaultProjectType := ProjectDefinition nonGuiApplicationType]
-                ] ifFalse:[
-                    defaultProjectType := ProjectDefinition libraryType
-                ].
-            ]
-        ].
+	[:package |
+	    |classesInPackage|
+
+	    classesInPackage := Smalltalk allClassesInPackage:package.
+	    classesInPackage isEmpty ifTrue:[
+		defaultProjectType := LastNewProjectType ? ProjectDefinition guiApplicationType
+	    ] ifFalse:[
+		(classesInPackage contains:[:cls | cls isBrowserStartable]) ifTrue:[
+		    (classesInPackage contains:[:cls | cls isVisualStartable])
+			ifTrue:[ defaultProjectType := ProjectDefinition guiApplicationType]
+			ifFalse:[ defaultProjectType := ProjectDefinition nonGuiApplicationType]
+		] ifFalse:[
+		    defaultProjectType := ProjectDefinition libraryType
+		].
+	    ]
+	].
 
     aProjectIDOrNil notNil ifTrue:[
-        initial := aProjectIDOrNil.
-        boxLabel := 'Create ProjectDefinition Class'.
-
-        setupDefaultType value:aProjectIDOrNil.
-    ] ifFalse:[
-        initial := 'module:directory'.
-        currentProject := self theSingleSelectedProject.
-        currentProject notNil ifTrue:[
-            initial := currentProject.
-            (initial includes:$:) ifTrue:[
-                (ProjectDefinition definitionClassForPackage:initial) notNil ifTrue:[
-                    initial := initial , '/newProject'.
-                ].
-            ] ifFalse:[
-                initial := initial , ':newProject'.
-            ].
-        ] ifFalse:[
-            initial := OperatingSystem getLoginName , ':newProject'.
-        ].
-
-        defaultProjectType := ProjectDefinition defaultProjectType.
-        setupDefaultType value:initial.
-        boxLabel := 'Create New Project'.
+	initial := aProjectIDOrNil.
+	boxLabel := 'Create ProjectDefinition Class'.
+
+	setupDefaultType value:aProjectIDOrNil.
+    ] ifFalse:[
+	initial := 'module:directory'.
+	currentProject := self theSingleSelectedProject.
+	currentProject notNil ifTrue:[
+	    initial := currentProject.
+	    (initial includes:$:) ifTrue:[
+		(ProjectDefinition definitionClassForPackage:initial) notNil ifTrue:[
+		    initial := initial , '/newProject'.
+		].
+	    ] ifFalse:[
+		initial := initial , ':newProject'.
+	    ].
+	] ifFalse:[
+	    initial := OperatingSystem getLoginName , ':newProject'.
+	].
+
+	defaultProjectType := ProjectDefinition defaultProjectType.
+	setupDefaultType value:initial.
+	boxLabel := 'Create New Project'.
     ].
 
     packageIDHolder := ValueHolder with:initial.
@@ -36095,11 +36547,11 @@
     field := box addInputFieldOn:packageIDHolder tabable:true.
     field width:0.7; left:0.3; rightInset:3.
     aProjectIDOrNil notNil ifTrue:[
-        field readOnly:true.
-    ] ifFalse:[
-        field acceptOnLeave:true.
-        field immediateAccept:true.
-        field entryCompletionBlock:(DoWhatIMeanSupport packageNameEntryCompletionBlock).
+	field readOnly:true.
+    ] ifFalse:[
+	field acceptOnLeave:true.
+	field immediateAccept:true.
+	field entryCompletionBlock:(DoWhatIMeanSupport packageNameEntryCompletionBlock).
     ].
 
     y := box yPosition.
@@ -36119,28 +36571,28 @@
     box open.
 
     box accepted ifFalse:[
-        ^ nil
+	^ nil
     ].
 
     LastNewProjectType := projectTypeHolder value.
 
     self withWaitCursorDo:[
-        aProjectIDOrNil notNil ifTrue:[
-            newProjectID := aProjectIDOrNil.
-        ] ifFalse:[
-            newProjectID := packageIDHolder value.
-            newProjectID notEmptyOrNil ifTrue:[
-                "/ self immediateUpdate value:true.
-                self projectListApp addAdditionalProject:newProjectID.
-                "/ self immediateUpdate value:false.
-                self selectProject:newProjectID.
-                self selectedClasses value:#().
-            ].
-        ].
-        projectDefinitionClass := ProjectDefinition
-                                    definitionClassForPackage:newProjectID
-                                    projectType: (projectTypeHolder value)
-                                    createIfAbsent:true.
+	aProjectIDOrNil notNil ifTrue:[
+	    newProjectID := aProjectIDOrNil.
+	] ifFalse:[
+	    newProjectID := packageIDHolder value.
+	    newProjectID notEmptyOrNil ifTrue:[
+		"/ self immediateUpdate value:true.
+		self projectListApp addAdditionalProject:newProjectID.
+		"/ self immediateUpdate value:false.
+		self selectProject:newProjectID.
+		self selectedClasses value:#().
+	    ].
+	].
+	projectDefinitionClass := ProjectDefinition
+				    definitionClassForPackage:newProjectID
+				    projectType: (projectTypeHolder value)
+				    createIfAbsent:true.
     ].
     ^ projectDefinitionClass
 
@@ -36171,22 +36623,22 @@
 
     projectDefinition := projectDefinitionClasses firstIfEmpty:nil.
     projectDefinition isNil ifTrue:[
-        ^ self
+	^ self
     ].
 
     Tools::ProjectBuilderAssistantApplication new
-        projectType:projectDefinition projectType.    
+	projectType:projectDefinition projectType.
 
     Transcript isView ifTrue:[
-        Transcript topView raise.
+	Transcript topView raise.
     ].
 
     projectBuilder := Tools::ProjectBuilder new.
-    projectBuilder 
-        makeExeOnly:exeOnly;
-        package:projectToBuild;
-        "/ build
-        buildWithColorizedOutputTo:Transcript.
+    projectBuilder
+	makeExeOnly:exeOnly;
+	package:projectToBuild;
+	"/ build
+	buildWithColorizedOutputTo:Transcript.
 
     FileBrowserV2 openOnDirectory:(projectBuilder buildDirectory)
 
@@ -36196,13 +36648,13 @@
 projectMenuCheckInAll
 
     <resource: #obsolete> "use ...Using:manager variant"
-    
+
     self selectedProjectsDo:[:packageToCheckIn |
-        self
-            projectMenuCheckInProject:packageToCheckIn
-            classes:true
-            extensions:true
-            buildSupport:true.
+	self
+	    projectMenuCheckInProject:packageToCheckIn
+	    classes:true
+	    extensions:true
+	    buildSupport:true.
     ]
 
     "Modified: / 09-08-2006 / 18:57:28 / fm"
@@ -36212,12 +36664,12 @@
 
 projectMenuCheckInAllUsingManager: manager
     self selectedProjectsDo:[:packageToCheckIn |
-        self
-            projectMenuCheckInProject:packageToCheckIn
-            classes:true
-            extensions:true
-            buildSupport:true
-            usingManager: manager
+	self
+	    projectMenuCheckInProject:packageToCheckIn
+	    classes:true
+	    extensions:true
+	    buildSupport:true
+	    usingManager: manager
     ]
 
     "Modified: / 09-08-2006 / 18:57:28 / fm"
@@ -36237,7 +36689,7 @@
     <resource: #obsolete> "use ...Using:manager variant"
 
     self selectedProjectsDo:[:packageToCheckIn |
-        self projectMenuCheckInBuildSupportFilesForProject:packageToCheckIn
+	self projectMenuCheckInBuildSupportFilesForProject:packageToCheckIn
     ]
 
     "Created: / 09-08-2006 / 19:04:52 / fm"
@@ -36252,15 +36704,15 @@
 
     defClass := ProjectDefinition definitionClassForPackage:packageID createIfAbsent:false.
     defClass isNil ifTrue:[
-        defClass := self projectDefinitionDialogFor:packageID.
-        defClass isNil ifTrue:[ ^ self ].
-        defClass compileDescriptionMethods.
+	defClass := self projectDefinitionDialogFor:packageID.
+	defClass isNil ifTrue:[ ^ self ].
+	defClass compileDescriptionMethods.
     ].
 
     mgr := SourceCodeManagerUtilities default sourceCodeManagerFor:defClass.
     mgr isNil ifTrue:[
-        self warn:'No sourceCode manager - cannot checkin.'.
-        ^ self.
+	self warn:'No sourceCode manager - cannot checkin.'.
+	^ self.
     ].
     self projectMenuCheckInBuildSupportFilesForProject:packageID definition:defClass usingManager:mgr
 
@@ -36282,80 +36734,80 @@
 
     self activityNotification:(resources string:'checking in build-support files...').
     (mgr checkForExistingModule:module directory:directory) ifFalse:[
-        mgr createModule:module directory:directory
+	mgr createModule:module directory:directory
     ].
     self withActivityNotificationsRedirectedToInfoLabelDo:[
-        defClass forEachFileNameAndGeneratedContentsDo:[:fileName :fileContents |
-            |realFileName realDirectory|
-
-            "/ care for subdirectories
-            (fileName includes:$/) ifTrue:[
-                realDirectory := (directory asFilename construct:(fileName asFilename directoryName)) name.
-                realFileName := fileName asFilename baseName.
-            ] ifFalse:[
-                realDirectory := directory.
-                realFileName := fileName.
-            ].
-            realDirectory := realDirectory replaceAll:$\ with:$/.
-
-            self showInfo:(resources string:'checking in %1...' with:realFileName).
-
-            UserInformation
-                handle:[:ex | Transcript showCR:ex description ]
-                do:[
-                    (mgr
-                        checkForExistingContainer:realFileName inModule:module directory:realDirectory)
-                    ifFalse:[
-                        realDirectory ~= directory ifTrue:[
-                            (mgr checkForExistingModule:module directory:realDirectory) ifFalse:[
-                                mgr createModule:module directory:realDirectory
-                            ].
-                        ].
-                        (mgr
-                            createContainerForText:fileContents
-                            inModule:module
-                            package:realDirectory
-                            container:realFileName)
-                                ifFalse:[
-                                    self warn:(resources
-                                                stringWithCRs:'Cannot create new container: ''%3'' (in %1:%2)'
-                                                with:module
-                                                with:realDirectory
-                                                with:realFileName)
-                                         translate:false.
-                                ].
-                    ] ifTrue:[
-                        (mgr
-                            checkin:realFileName
-                            text:fileContents
-                            directory:realDirectory
-                            module:module
-                            logMessage:'automatically generated by browser'
-                            force:false)
-                                ifFalse:[
-                                    Transcript showCR:'checkin of ' , realFileName , ' failed'.
-                                    anyFailure := true.
-                                ].
-                    ].
-                ].
-        ].
-
-        defClass instAndClassMethodsDo:[:m | m package:defClass package].
-
-        self
-            checkInClasses:(Array with:defClass)
-            withInfo:'automatic checkIn'
-            withCheck:false
-            usingManager: mgr
+	defClass forEachFileNameAndGeneratedContentsDo:[:fileName :fileContents |
+	    |realFileName realDirectory|
+
+	    "/ care for subdirectories
+	    (fileName includes:$/) ifTrue:[
+		realDirectory := (directory asFilename construct:(fileName asFilename directoryName)) name.
+		realFileName := fileName asFilename baseName.
+	    ] ifFalse:[
+		realDirectory := directory.
+		realFileName := fileName.
+	    ].
+	    realDirectory := realDirectory replaceAll:$\ with:$/.
+
+	    self showInfo:(resources string:'checking in %1...' with:realFileName).
+
+	    UserInformation
+		handle:[:ex | Transcript showCR:ex description ]
+		do:[
+		    (mgr
+			checkForExistingContainer:realFileName inModule:module directory:realDirectory)
+		    ifFalse:[
+			realDirectory ~= directory ifTrue:[
+			    (mgr checkForExistingModule:module directory:realDirectory) ifFalse:[
+				mgr createModule:module directory:realDirectory
+			    ].
+			].
+			(mgr
+			    createContainerForText:fileContents
+			    inModule:module
+			    package:realDirectory
+			    container:realFileName)
+				ifFalse:[
+				    self warn:(resources
+						stringWithCRs:'Cannot create new container: ''%3'' (in %1:%2)'
+						with:module
+						with:realDirectory
+						with:realFileName)
+					 translate:false.
+				].
+		    ] ifTrue:[
+			(mgr
+			    checkin:realFileName
+			    text:fileContents
+			    directory:realDirectory
+			    module:module
+			    logMessage:'automatically generated by browser'
+			    force:false)
+				ifFalse:[
+				    Transcript showCR:'checkin of ' , realFileName , ' failed'.
+				    anyFailure := true.
+				].
+		    ].
+		].
+	].
+
+	defClass instAndClassMethodsDo:[:m | m package:defClass package].
+
+	self
+	    checkInClasses:(Array with:defClass)
+	    withInfo:'automatic checkIn'
+	    withCheck:false
+	    usingManager: mgr
     ].
 
     self activityNotification:nil.
 
     anyFailure ifTrue:[
-        self warn:'Checkin failed - see Transcript.'.
-        self showInfo:'Checkin of build-support files failed - see Transcript.'.
-    ] ifFalse:[
-        self showInfo:'Build-support files checked into the repository.'.
+	self warn:'Checkin failed - see Transcript.'.
+	self showInfo:'Checkin of build-support files failed - see Transcript.'.
+    ] ifFalse:[
+	self showInfo:'Build-support files checked into the repository.'.
     ].
 
     "Created: / 09-08-2006 / 18:59:42 / fm"
@@ -36369,15 +36821,15 @@
 
     defClass := ProjectDefinition definitionClassForPackage:packageID createIfAbsent:false.
     defClass isNil ifTrue:[
-        defClass := self projectDefinitionDialogFor:packageID.
-        defClass isNil ifTrue:[ ^ self ].
-        defClass compileDescriptionMethods.
+	defClass := self projectDefinitionDialogFor:packageID.
+	defClass isNil ifTrue:[ ^ self ].
+	defClass compileDescriptionMethods.
     ].
 
     mgr := manager.
     mgr isNil ifTrue:[
-        self warn:'No sourceCode manager - cannot checkin.'.
-        ^ self.
+	self warn:'No sourceCode manager - cannot checkin.'.
+	^ self.
     ].
     self projectMenuCheckInBuildSupportFilesForProject:packageID definition:defClass usingManager:mgr
 
@@ -36391,7 +36843,7 @@
 
 projectMenuCheckInBuildSupportFilesUsingManager: manager
     self selectedProjectsDo:[:packageToCheckIn |
-        self projectMenuCheckInBuildSupportFilesForProject:packageToCheckIn usingManager: manager
+	self projectMenuCheckInBuildSupportFilesForProject:packageToCheckIn usingManager: manager
     ]
 
     "Created: / 09-08-2006 / 19:04:52 / fm"
@@ -36412,11 +36864,11 @@
     <resource: #obsolete> "use ...Using:manager variant"
 
     self selectedProjectsDo:[:packageToCheckIn |
-        self
-            projectMenuCheckInProject:packageToCheckIn
-            classes:true
-            extensions:false
-            buildSupport:false
+	self
+	    projectMenuCheckInProject:packageToCheckIn
+	    classes:true
+	    extensions:false
+	    buildSupport:false
     ]
 
     "Modified: / 15-10-2011 / 20:22:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -36424,12 +36876,12 @@
 
 projectMenuCheckInClassesUsingManager: manager
     self selectedProjectsDo:[:packageToCheckIn |
-        self
-            projectMenuCheckInProject:packageToCheckIn
-            classes:true
-            extensions:false
-            buildSupport:false
-            usingManager: manager
+	self
+	    projectMenuCheckInProject:packageToCheckIn
+	    classes:true
+	    extensions:false
+	    buildSupport:false
+	    usingManager: manager
     ]
 
     "Created: / 15-10-2011 / 20:21:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -36448,11 +36900,11 @@
     <resource: #obsolete> "use ...Using:manager variant"
 
     self selectedProjectsDo:[:packageToCheckIn |
-        self
-            projectMenuCheckInProject:packageToCheckIn
-            classes:false
-            extensions:true
-            buildSupport:false
+	self
+	    projectMenuCheckInProject:packageToCheckIn
+	    classes:false
+	    extensions:true
+	    buildSupport:false
     ]
 
     "Modified: / 15-10-2011 / 20:22:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -36461,12 +36913,12 @@
 projectMenuCheckInExtensionsUsingManager: manager
 
     self selectedProjectsDo:[:packageToCheckIn |
-        self
-            projectMenuCheckInProject:packageToCheckIn
-            classes:false
-            extensions:true
-            buildSupport:false
-            usingManager: manager
+	self
+	    projectMenuCheckInProject:packageToCheckIn
+	    classes:false
+	    extensions:true
+	    buildSupport:false
+	    usingManager: manager
     ]
 
     "Created: / 15-10-2011 / 20:06:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -36485,11 +36937,11 @@
     <resource: #obsolete>
 
     ^ self
-        projectMenuCheckInProject:packageToCheckIn
-        classes:doClasses
-        extensions:doExtensions
-        buildSupport:doBuild
-        askForMethodsInOtherPackages:true
+	projectMenuCheckInProject:packageToCheckIn
+	classes:doClasses
+	extensions:doExtensions
+	buildSupport:doBuild
+	askForMethodsInOtherPackages:true
 
     "Modified: / 21-08-2006 / 19:43:22 / cg"
     "Modified: / 13-10-2011 / 11:07:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -36511,203 +36963,203 @@
 
     "/ classes ...
     classes do:[:aClass | |owner classPackage|
-        (owner := aClass owningClass) notNil ifTrue:[
-            classPackage := aClass topOwningClass package
-        ] ifFalse:[
-            classPackage := aClass package
-        ].
-        (classPackage = packageToCheckIn) ifTrue:[
-            classesToCheckIn add:aClass.
-        ].
+	(owner := aClass owningClass) notNil ifTrue:[
+	    classPackage := aClass topOwningClass package
+	] ifFalse:[
+	    classPackage := aClass package
+	].
+	(classPackage = packageToCheckIn) ifTrue:[
+	    classesToCheckIn add:aClass.
+	].
     ].
 
     "/ cg: O(n^2) algorithm
     "/  classesInChangeSet := classesToCheckIn select:[:cls | cls hasUnsavedChanges].
     "/ replaced by: O(n) algorithm
-    classesInChangeSet := ChangeSet current selectForWhichIncludesChangeForClassOrMetaclassOrPrivateClassFrom:classesToCheckIn. 
+    classesInChangeSet := ChangeSet current selectForWhichIncludesChangeForClassOrMetaclassOrPrivateClassFrom:classesToCheckIn.
 
     "/ individual methods ...
     classes do:[:aClass |
-        aClass isMeta ifFalse:[
-            "/ ... whose class is not in the chechIn-set
-            (classesToCheckIn includes:aClass) ifFalse:[
-                aClass instAndClassSelectorsAndMethodsDo:[:sel :mthd |
-                    "/ methods in this project ...
-                    (mthd package = packageToCheckIn) ifTrue:[
-                        methodsToCheckIn add:mthd
-                    ]
-                ]
-            ].
-        ].
+	aClass isMeta ifFalse:[
+	    "/ ... whose class is not in the chechIn-set
+	    (classesToCheckIn includes:aClass) ifFalse:[
+		aClass instAndClassSelectorsAndMethodsDo:[:sel :mthd |
+		    "/ methods in this project ...
+		    (mthd package = packageToCheckIn) ifTrue:[
+			methodsToCheckIn add:mthd
+		    ]
+		]
+	    ].
+	].
     ].
 
     doExtensions ifTrue:[
-        methodsToCheckIn notEmpty ifTrue:[
-            doClasses ifTrue:[
-                msg := '%1 classes (%4 changed) '.
-            ] ifFalse:[
-                msg := ''.
-            ].
-            doExtensions ifTrue:[
-                doClasses ifTrue:[
-                    msg := msg , 'and '.
-                ].
-                msg := msg , '%2 extensions '.
-            ].
-            msg := msg , 'of project "%3"'.
-
-            checkinInfo := SourceCodeManagerUtilities default
-                        getCheckinInfoFor:(msg
-                                                    bindWith:classesToCheckIn size
-                                                    with:methodsToCheckIn size
-                                                    with:packageToCheckIn allBold
-                                                    with:classesInChangeSet size)
-                        initialAnswer:nil
-                        withQuickOption:(classesToCheckIn size > 0).
-            checkinInfo isNil ifTrue:[
-                ^ self.
-            ].
-            (SourceCodeManagerUtilities default
-                checkinExtensionMethods:methodsToCheckIn
-                forPackage:packageToCheckIn
-                withInfo:checkinInfo)
-            ifFalse:[
-                self warn:'Could not check in extensions for project %1' with:packageToCheckIn.
-                ^ self.
-            ]
-        ] ifFalse:[
-            "/ there may have been extension-methods previously - if so, remove them
-            (SourceCodeManager
-                checkForExistingContainer:'extensions.st' inPackage:packageToCheckIn)
-            ifTrue:[
+	methodsToCheckIn notEmpty ifTrue:[
+	    doClasses ifTrue:[
+		msg := '%1 classes (%4 changed) '.
+	    ] ifFalse:[
+		msg := ''.
+	    ].
+	    doExtensions ifTrue:[
+		doClasses ifTrue:[
+		    msg := msg , 'and '.
+		].
+		msg := msg , '%2 extensions '.
+	    ].
+	    msg := msg , 'of project "%3"'.
+
+	    checkinInfo := SourceCodeManagerUtilities default
+			getCheckinInfoFor:(msg
+						    bindWith:classesToCheckIn size
+						    with:methodsToCheckIn size
+						    with:packageToCheckIn allBold
+						    with:classesInChangeSet size)
+			initialAnswer:nil
+			withQuickOption:(classesToCheckIn size > 0).
+	    checkinInfo isNil ifTrue:[
+		^ self.
+	    ].
+	    (SourceCodeManagerUtilities default
+		checkinExtensionMethods:methodsToCheckIn
+		forPackage:packageToCheckIn
+		withInfo:checkinInfo)
+	    ifFalse:[
+		self warn:'Could not check in extensions for project %1' with:packageToCheckIn.
+		^ self.
+	    ]
+	] ifFalse:[
+	    "/ there may have been extension-methods previously - if so, remove them
+	    (SourceCodeManager
+		checkForExistingContainer:'extensions.st' inPackage:packageToCheckIn)
+	    ifTrue:[
 "/ self halt.
-                (SourceCodeManagerUtilities default
-                    checkinExtensionMethods:#()
-                    forPackage:packageToCheckIn
-                    withInfo:'No extensions any more')
-                ifFalse:[
-                    self warn:'Could not check in extensions for project %1' with:packageToCheckIn.
-                    ^ self.
-                ]
-            ]
-        ].
+		(SourceCodeManagerUtilities default
+		    checkinExtensionMethods:#()
+		    forPackage:packageToCheckIn
+		    withInfo:'No extensions any more')
+		ifFalse:[
+		    self warn:'Could not check in extensions for project %1' with:packageToCheckIn.
+		    ^ self.
+		]
+	    ]
+	].
     ].
 
     checkinInfo isNil ifTrue:[
-        checkinInfo := SourceCodeManagerUtilities default
-                    getCheckinInfoFor:('%1 classes (%4 changed) and %2 extensions for project "%3"'
-                                                        bindWith:classesToCheckIn size
-                                                        with:methodsToCheckIn size
-                                                        with:packageToCheckIn allBold
-                                                        with:classesInChangeSet size)
-                    initialAnswer:nil
-                    withQuickOption:(classesToCheckIn size > 0).
-        checkinInfo isNil ifTrue:[
-            ^ self.
-        ].
+	checkinInfo := SourceCodeManagerUtilities default
+		    getCheckinInfoFor:('%1 classes (%4 changed) and %2 extensions for project "%3"'
+							bindWith:classesToCheckIn size
+							with:methodsToCheckIn size
+							with:packageToCheckIn allBold
+							with:classesInChangeSet size)
+		    initialAnswer:nil
+		    withQuickOption:(classesToCheckIn size > 0).
+	checkinInfo isNil ifTrue:[
+	    ^ self.
+	].
     ].
 
     checkinInfo quickCheckIn ifTrue:[
-        (checkinInfo isStable or:[checkinInfo tagIt]) ifTrue:[
-            classesToTag := classesToCheckIn.
-            originalCheckinInfo := checkinInfo.
-            checkinInfo := checkinInfo copy.
-            checkinInfo isStable:false.
-            checkinInfo tag:nil.
-        ].
-        classesToCheckIn := classesInChangeSet.
+	(checkinInfo isStable or:[checkinInfo tagIt]) ifTrue:[
+	    classesToTag := classesToCheckIn.
+	    originalCheckinInfo := checkinInfo.
+	    checkinInfo := checkinInfo copy.
+	    checkinInfo isStable:false.
+	    checkinInfo tag:nil.
+	].
+	classesToCheckIn := classesInChangeSet.
     ].
 
     "/ check if any of the classes contains methods for other packages ...
     classesToCheckIn do:[:eachClass |
-        eachClass instAndClassMethodsDo:[:eachMethod |
-            |mPgk|
-
-            mPgk := eachMethod package.
-            (mPgk = packageToCheckIn) ifFalse:[
-                mPgk == PackageId noProjectID ifTrue:[
-                    looseMethods add:eachMethod
-                ] ifFalse:[
-                    methodsInOtherPackages add:eachMethod
-                ]
-            ]
-        ].
+	eachClass instAndClassMethodsDo:[:eachMethod |
+	    |mPgk|
+
+	    mPgk := eachMethod package.
+	    (mPgk = packageToCheckIn) ifFalse:[
+		mPgk == PackageId noProjectID ifTrue:[
+		    looseMethods add:eachMethod
+		] ifFalse:[
+		    methodsInOtherPackages add:eachMethod
+		]
+	    ]
+	].
     ].
 
     askForMethodsInOtherPackages ifTrue:[
-        methodsInOtherPackages notEmpty ifTrue:[
-            otherPackages := Set new.
-            methodsInOtherPackages do:[:eachMethod | otherPackages add:eachMethod package].
-
-            methodsInOtherPackages size == 1 ifTrue:[
-                msg := 'The ''%4'' method in ''%5'' is contained in the ''%2'' package.'.
-                msg := msg , '\\This method will remain in its package.'.
-            ] ifFalse:[
-                otherPackages size == 1 ifTrue:[
-                    msg := 'The %1 methods from the %2 package will remain in its package.'
-                ] ifFalse:[
-                    msg := 'The %1 methods from %3 other packages will remain in their packages.'
-                ].
-                msg := msg , '\\Hint: if these are meant to belong to this package,'.
-                msg := msg , '\move them first, then repeat the checkin operation.'.
-            ].
-            msg := msg withCRs.
-            msg := msg bindWith:methodsInOtherPackages size
-                           with:otherPackages first allBold
-                           with:otherPackages size
-                           with:methodsInOtherPackages first selector allBold
-                           with:methodsInOtherPackages first mclass name allBold.
-            (Dialog confirm:msg noLabel:(resources string:'Cancel')) ifFalse:[^ self].
-        ].
+	methodsInOtherPackages notEmpty ifTrue:[
+	    otherPackages := Set new.
+	    methodsInOtherPackages do:[:eachMethod | otherPackages add:eachMethod package].
+
+	    methodsInOtherPackages size == 1 ifTrue:[
+		msg := 'The ''%4'' method in ''%5'' is contained in the ''%2'' package.'.
+		msg := msg , '\\This method will remain in its package.'.
+	    ] ifFalse:[
+		otherPackages size == 1 ifTrue:[
+		    msg := 'The %1 methods from the %2 package will remain in its package.'
+		] ifFalse:[
+		    msg := 'The %1 methods from %3 other packages will remain in their packages.'
+		].
+		msg := msg , '\\Hint: if these are meant to belong to this package,'.
+		msg := msg , '\move them first, then repeat the checkin operation.'.
+	    ].
+	    msg := msg withCRs.
+	    msg := msg bindWith:methodsInOtherPackages size
+			   with:otherPackages first allBold
+			   with:otherPackages size
+			   with:methodsInOtherPackages first selector allBold
+			   with:methodsInOtherPackages first mclass name allBold.
+	    (Dialog confirm:msg noLabel:(resources string:'Cancel')) ifFalse:[^ self].
+	].
     ].
 
     doClasses ifTrue:[
-        classesToCheckIn notEmpty ifTrue:[
-            looseMethods notEmpty ifTrue:[
-                looseMethods size == 1 ifTrue:[
-                    msg := 'The ''%2'' method in ''%3'' is unassigned (loose).'.
-                    msg := msg , '\\If you proceed, this method will be moved to the ''%4'' package'.
-                    msg := msg , '\\Hint: if this is meant to be an extension of another package,'.
-                    msg := msg , '\cancel and move it to the appropriate package first.'.
-                ] ifFalse:[
-                    msg := 'There are %1 unassigned (loose) methods in classes from this project.'.
-                    msg := msg , '\\If you proceed, those will be moved to the ''%4'' package ?'.
-                    msg := msg , '\\Hint: if these are meant to be extensions of another package,'.
-                    msg := msg , '\cancel and move them to the appropriate package first.'.
-                ].
-                doClasses ifTrue:[
-                    msg := msg , '\\If you answer with "No" here, you will be asked for each class individually.'.
-                ].
-                msg := msg withCRs.
-                msg := msg bindWith:looseMethods size
-                               with:(looseMethods isEmpty ifTrue:[''] ifFalse:[looseMethods first selector allBold])
-                               with:(looseMethods isEmpty ifTrue:[''] ifFalse:[looseMethods first mclass name allBold])
-                               with:packageToCheckIn allBold.
-                (Dialog confirm:msg noLabel:(resources string:'Cancel')) ifFalse:[^ self].
-
-                looseMethods do:[:mthd |
-                    mthd package:packageToCheckIn
-                ].
-            ].
-            SourceCodeManagerUtilities default checkinClasses:classesToCheckIn withInfo:checkinInfo.
-        ].
-
-        originalCheckinInfo notNil ifTrue:[
-            originalCheckinInfo isStable ifTrue:[
-                classesToTag do:[:eachClass |
-                    SourceCodeManagerUtilities default tagClass:eachClass as:#stable
-                ].
-            ].
-            originalCheckinInfo tagIt ifTrue:[
-                classesToTag do:[:eachClass |
-                    SourceCodeManagerUtilities default tagClass:eachClass as:(originalCheckinInfo tag)
-                ].
-            ].
-        ].
+	classesToCheckIn notEmpty ifTrue:[
+	    looseMethods notEmpty ifTrue:[
+		looseMethods size == 1 ifTrue:[
+		    msg := 'The ''%2'' method in ''%3'' is unassigned (loose).'.
+		    msg := msg , '\\If you proceed, this method will be moved to the ''%4'' package'.
+		    msg := msg , '\\Hint: if this is meant to be an extension of another package,'.
+		    msg := msg , '\cancel and move it to the appropriate package first.'.
+		] ifFalse:[
+		    msg := 'There are %1 unassigned (loose) methods in classes from this project.'.
+		    msg := msg , '\\If you proceed, those will be moved to the ''%4'' package ?'.
+		    msg := msg , '\\Hint: if these are meant to be extensions of another package,'.
+		    msg := msg , '\cancel and move them to the appropriate package first.'.
+		].
+		doClasses ifTrue:[
+		    msg := msg , '\\If you answer with "No" here, you will be asked for each class individually.'.
+		].
+		msg := msg withCRs.
+		msg := msg bindWith:looseMethods size
+			       with:(looseMethods isEmpty ifTrue:[''] ifFalse:[looseMethods first selector allBold])
+			       with:(looseMethods isEmpty ifTrue:[''] ifFalse:[looseMethods first mclass name allBold])
+			       with:packageToCheckIn allBold.
+		(Dialog confirm:msg noLabel:(resources string:'Cancel')) ifFalse:[^ self].
+
+		looseMethods do:[:mthd |
+		    mthd package:packageToCheckIn
+		].
+	    ].
+	    SourceCodeManagerUtilities default checkinClasses:classesToCheckIn withInfo:checkinInfo.
+	].
+
+	originalCheckinInfo notNil ifTrue:[
+	    originalCheckinInfo isStable ifTrue:[
+		classesToTag do:[:eachClass |
+		    SourceCodeManagerUtilities default tagClass:eachClass as:#stable
+		].
+	    ].
+	    originalCheckinInfo tagIt ifTrue:[
+		classesToTag do:[:eachClass |
+		    SourceCodeManagerUtilities default tagClass:eachClass as:(originalCheckinInfo tag)
+		].
+	    ].
+	].
     ].
 
     doBuild ifTrue:[
-        self projectMenuCheckInBuildSupportFilesForProject:packageToCheckIn
+	self projectMenuCheckInBuildSupportFilesForProject:packageToCheckIn
     ].
 
     self normalLabel.
@@ -36719,12 +37171,12 @@
 projectMenuCheckInProject:packageToCheckIn classes:doClasses extensions:doExtensions buildSupport:doBuild askForMethodsInOtherPackages:askForMethodsInOtherPackages usingManager: manager
 
     self withActivityNotificationsRedirectedToInfoLabelDo:[
-        manager utilities
-            checkinPackage:packageToCheckIn 
-            classes:doClasses 
-            extensions:doExtensions 
-            buildSupport:doBuild 
-            askForMethodsInOtherPackages:askForMethodsInOtherPackages
+	manager utilities
+	    checkinPackage:packageToCheckIn
+	    classes:doClasses
+	    extensions:doExtensions
+	    buildSupport:doBuild
+	    askForMethodsInOtherPackages:askForMethodsInOtherPackages
     ]
 
     "Modified: / 08-09-2011 / 04:42:38 / cg"
@@ -36734,12 +37186,12 @@
 
 projectMenuCheckInProject:packageToCheckIn classes:doClasses extensions:doExtensions buildSupport:doBuild usingManager: manager
     ^ self
-        projectMenuCheckInProject:packageToCheckIn
-        classes:doClasses
-        extensions:doExtensions
-        buildSupport:doBuild
-        askForMethodsInOtherPackages:true
-        usingManager: manager
+	projectMenuCheckInProject:packageToCheckIn
+	classes:doClasses
+	extensions:doExtensions
+	buildSupport:doBuild
+	askForMethodsInOtherPackages:true
+	usingManager: manager
 
     "Modified: / 21-08-2006 / 19:43:22 / cg"
     "Created: / 13-10-2011 / 10:37:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -36758,11 +37210,11 @@
 
 projectMenuCheckOutExtensions
     self selectedProjectsDo:[:packageToCheckOut |
-        SourceCodeManagerUtilities
-            checkoutExtensionMethodsForPackage:packageToCheckOut
-            askForRevision:true
-            askForMerge:true
-            usingManager:(SourceCodeManager defaultManager)
+	SourceCodeManagerUtilities
+	    checkoutExtensionMethodsForPackage:packageToCheckOut
+	    askForRevision:true
+	    askForMerge:true
+	    usingManager:(SourceCodeManager defaultManager)
     ]
 
     "Created: / 10-08-2006 / 18:16:51 / cg"
@@ -36778,195 +37230,195 @@
     |classesInImage filesInImage|
 
     (Dialog confirm:('This functionality is not yet completely implemented.'
-                , String lf
-                ,'For now, only existing classes are updated - no new classes are added or old ones removed.'
-                , String lf
-                , 'Please use the import-structure function to get new definitions.')) ifFalse:[^ self].
+		, String lf
+		,'For now, only existing classes are updated - no new classes are added or old ones removed.'
+		, String lf
+		, 'Please use the import-structure function to get new definitions.')) ifFalse:[^ self].
     self checkOutClasses:(self selectedProjectClasses) askForRevision:false.
 ^ self.
 
     #TODO.
 
     self selectedProjects value do:[:eachProject |
-        |module directory perProjectInfo
-         classesNotInRepository filesNotInImage classesDeletedInRepository
-         classesModifiedInImage classesModifiedInRepository
-         classesDeletedInImage classesAddedInImage
-         anyDifference box doRemove classDefs changeSets filePerClassDefintion
-         classesToCheckIn|
-
-        module := eachProject asPackageId module.
-        directory := eachProject asPackageId directory.
-        perProjectInfo := SourceCodeManager newestRevisionsInModule:module directory:directory.
-        perProjectInfo := perProjectInfo ? #().
-        perProjectInfo := perProjectInfo select:[:info | info key asFilename hasSuffix:'st'].
-        perProjectInfo := Dictionary withAssociations:perProjectInfo.
-
-        classesInImage := Smalltalk allClassesInPackage:eachProject.
-        filesInImage := (classesInImage collect:[:cls | cls classBaseFilename]) asSet.
-        "/ any differences ?
-        classesNotInRepository := classesInImage reject:[:cls | (perProjectInfo includesKey:cls classBaseFilename)].
-        classesDeletedInRepository := classesInImage select:[:cls | (perProjectInfo at:cls classBaseFilename ifAbsent:nil) == #deleted].
-        perProjectInfo := perProjectInfo reject:[:v | v == #deleted].
-        filesNotInImage := perProjectInfo keys reject:[:file | (filesInImage includes:file)].
-
-        classesModifiedInImage := classesInImage select:[:cls | ChangeSet current includesChangeForClassOrMetaclass:cls].
-        classesModifiedInRepository := classesInImage select:[:cls | |v|
-                                                        v := (perProjectInfo at:cls classBaseFilename ifAbsent:nil).
-                                                        v notNil and:[ v > cls revision]].
-
-        anyDifference := false.
-        filesNotInImage notEmpty ifTrue:[
-            filePerClassDefintion := Dictionary new.
-            classDefs := ChangeSet new.
-            changeSets := OrderedCollection new.
-            filesNotInImage do:[:eachSTFile |
-                |s chgSet classDefinitions|
-
-                s := SourceCodeManager
-                    streamForClass:nil fileName:eachSTFile revision:#newest directory:directory module:module cache:true.
-                chgSet := ChangeSet fromStream:s.
-                s close.
-                changeSets add:chgSet.
-                classDefinitions := chgSet select:[:change | change isClassDefinitionChange and:[change isPrivateClassDefinitionChange not]].
-                classDefinitions do:[:def | filePerClassDefintion at:def put:eachSTFile].
-                classDefs addAll:classDefinitions.
-            ].
-            "/ now, install ...
-            classDefs do:[:eachClassDefinition |
-                |cls oldPackage|
-
-                eachClassDefinition package:eachProject.
-                eachClassDefinition installAsAutoloadedClassIfPublicWithFilename:(filePerClassDefintion at:eachClassDefinition).
-                (cls := eachClassDefinition changeClass) notNil ifTrue:[
-                    (oldPackage := cls package) ~= eachProject ifTrue:[
-                        (Dialog confirm:('Move the %1-class from %2 to %3 ?' bindWith:cls name allBold with:oldPackage allBold with:eachProject allBold)) ifTrue:[
-                            cls package:eachProject.
-                            cls instAndClassMethodsDo:[:m | m package = oldPackage ifTrue:[ m package:eachProject]].
-                        ]
-                    ].
-                ].
-            ].
-            changeSets do:[:chgSet |
-                chgSet apply
-            ].
-        ].
-        classesModifiedInImage notEmpty ifTrue:[
-            classesToCheckIn := OrderedCollection new.
-            classesModifiedInImage do:[:eachChangedClass |
-                |currentVersion repositoryVersion s stFile diffs|
-
-                stFile := eachChangedClass classBaseFilename.
-                s := SourceCodeManager
-                    streamForClass:nil fileName:stFile revision:#newest directory:directory module:module cache:true.
-                repositoryVersion := ChangeSet fromStream:s.
-                s close.
-
-                currentVersion := ChangeSet forExistingClass:eachChangedClass.
-                diffs := currentVersion diffSetsAgainst:repositoryVersion.
-                diffs isEmpty ifTrue:[
-                    ChangeSet current condenseChangesForClass:eachChangedClass
-                ] ifFalse:[
+	|module directory perProjectInfo
+	 classesNotInRepository filesNotInImage classesDeletedInRepository
+	 classesModifiedInImage classesModifiedInRepository
+	 classesDeletedInImage classesAddedInImage
+	 anyDifference box doRemove classDefs changeSets filePerClassDefintion
+	 classesToCheckIn|
+
+	module := eachProject asPackageId module.
+	directory := eachProject asPackageId directory.
+	perProjectInfo := SourceCodeManager newestRevisionsInModule:module directory:directory.
+	perProjectInfo := perProjectInfo ? #().
+	perProjectInfo := perProjectInfo select:[:info | info key asFilename hasSuffix:'st'].
+	perProjectInfo := Dictionary withAssociations:perProjectInfo.
+
+	classesInImage := Smalltalk allClassesInPackage:eachProject.
+	filesInImage := (classesInImage collect:[:cls | cls classBaseFilename]) asSet.
+	"/ any differences ?
+	classesNotInRepository := classesInImage reject:[:cls | (perProjectInfo includesKey:cls classBaseFilename)].
+	classesDeletedInRepository := classesInImage select:[:cls | (perProjectInfo at:cls classBaseFilename ifAbsent:nil) == #deleted].
+	perProjectInfo := perProjectInfo reject:[:v | v == #deleted].
+	filesNotInImage := perProjectInfo keys reject:[:file | (filesInImage includes:file)].
+
+	classesModifiedInImage := classesInImage select:[:cls | ChangeSet current includesChangeForClassOrMetaclass:cls].
+	classesModifiedInRepository := classesInImage select:[:cls | |v|
+							v := (perProjectInfo at:cls classBaseFilename ifAbsent:nil).
+							v notNil and:[ v > cls revision]].
+
+	anyDifference := false.
+	filesNotInImage notEmpty ifTrue:[
+	    filePerClassDefintion := Dictionary new.
+	    classDefs := ChangeSet new.
+	    changeSets := OrderedCollection new.
+	    filesNotInImage do:[:eachSTFile |
+		|s chgSet classDefinitions|
+
+		s := SourceCodeManager
+		    streamForClass:nil fileName:eachSTFile revision:#newest directory:directory module:module cache:true.
+		chgSet := ChangeSet fromStream:s.
+		s close.
+		changeSets add:chgSet.
+		classDefinitions := chgSet select:[:change | change isClassDefinitionChange and:[change isPrivateClassDefinitionChange not]].
+		classDefinitions do:[:def | filePerClassDefintion at:def put:eachSTFile].
+		classDefs addAll:classDefinitions.
+	    ].
+	    "/ now, install ...
+	    classDefs do:[:eachClassDefinition |
+		|cls oldPackage|
+
+		eachClassDefinition package:eachProject.
+		eachClassDefinition installAsAutoloadedClassIfPublicWithFilename:(filePerClassDefintion at:eachClassDefinition).
+		(cls := eachClassDefinition changeClass) notNil ifTrue:[
+		    (oldPackage := cls package) ~= eachProject ifTrue:[
+			(Dialog confirm:('Move the %1-class from %2 to %3 ?' bindWith:cls name allBold with:oldPackage allBold with:eachProject allBold)) ifTrue:[
+			    cls package:eachProject.
+			    cls instAndClassMethodsDo:[:m | m package = oldPackage ifTrue:[ m package:eachProject]].
+			]
+		    ].
+		].
+	    ].
+	    changeSets do:[:chgSet |
+		chgSet apply
+	    ].
+	].
+	classesModifiedInImage notEmpty ifTrue:[
+	    classesToCheckIn := OrderedCollection new.
+	    classesModifiedInImage do:[:eachChangedClass |
+		|currentVersion repositoryVersion s stFile diffs|
+
+		stFile := eachChangedClass classBaseFilename.
+		s := SourceCodeManager
+		    streamForClass:nil fileName:stFile revision:#newest directory:directory module:module cache:true.
+		repositoryVersion := ChangeSet fromStream:s.
+		s close.
+
+		currentVersion := ChangeSet forExistingClass:eachChangedClass.
+		diffs := currentVersion diffSetsAgainst:repositoryVersion.
+		diffs isEmpty ifTrue:[
+		    ChangeSet current condenseChangesForClass:eachChangedClass
+		] ifFalse:[
 self halt.
-                    classesToCheckIn add:eachChangedClass.
-                ].
-            ].
-            classesToCheckIn notEmpty ifTrue:[
+		    classesToCheckIn add:eachChangedClass.
+		].
+	    ].
+	    classesToCheckIn notEmpty ifTrue:[
 self halt.
-            ].
-        ].
-        classesModifiedInRepository notEmpty ifTrue:[
-            box := Dialog
-                forRequestText:(resources stringWithCRs:'The following classes need to be updated from the repository.')
-                editViewClass:ListView
-                lines:10 columns:20
-                initialAnswer:nil model:nil
-                setupWith:
-                   [:v :d |
-                            |removeButton|
-
-                            v list:classesModifiedInRepository.
-                            d okButton label:(resources string:'Update').
-                            d okButton isReturnButton:true.
-                   ].
-            box open.
-            box accepted ifFalse:[
-                ^ self
-            ].
-            classesModifiedInRepository do:[:eachClass|
-                |s chgSet|
-
-                s := SourceCodeManager
-                    streamForClass:eachClass fileName:nil revision:#newest directory:directory module:module cache:true.
-                chgSet := ChangeSet fromStream:s.
-                s close.
-                chgSet apply.
-            ].
-        ].
-        classesDeletedInRepository notEmpty ifTrue:[
+	    ].
+	].
+	classesModifiedInRepository notEmpty ifTrue:[
+	    box := Dialog
+		forRequestText:(resources stringWithCRs:'The following classes need to be updated from the repository.')
+		editViewClass:ListView
+		lines:10 columns:20
+		initialAnswer:nil model:nil
+		setupWith:
+		   [:v :d |
+			    |removeButton|
+
+			    v list:classesModifiedInRepository.
+			    d okButton label:(resources string:'Update').
+			    d okButton isReturnButton:true.
+		   ].
+	    box open.
+	    box accepted ifFalse:[
+		^ self
+	    ].
+	    classesModifiedInRepository do:[:eachClass|
+		|s chgSet|
+
+		s := SourceCodeManager
+		    streamForClass:eachClass fileName:nil revision:#newest directory:directory module:module cache:true.
+		chgSet := ChangeSet fromStream:s.
+		s close.
+		chgSet apply.
+	    ].
+	].
+	classesDeletedInRepository notEmpty ifTrue:[
 self halt.
-        ].
-        classesNotInRepository notEmpty ifTrue:[
-            "/ if there are no changeSet entries for those classes, they seem to be
-            "/ no longer in the repository (possibly moved ?)
-            "/ If there are entries, these might have been added in the image and need a check-in
-            classesAddedInImage := classesNotInRepository select:[:cls | ChangeSet current includesChangeForClassOrMetaclass:cls].
-            classesAddedInImage isEmpty ifTrue:[
-                doRemove := false.
-                box := Dialog
-                    forRequestText:(resources stringWithCRs:'The following classes are no longer in the repository (or moved to another package).\\Remove classes from the image ?')
-                    editViewClass:ListView
-                    lines:10 columns:20
-                    initialAnswer:nil model:nil
-                    setupWith:
-                       [:v :d |
-                                |removeButton|
-
-                                removeButton := Button label:(resources string:'Remove').
-                                removeButton action:[ doRemove := true. box okPressed. ].
-                                v list:classesNotInRepository.
-                                d addButton:removeButton after:(d okButton).
-                                d okButton label:(resources string:'Continue').
-                                d okButton isReturnButton:true.
-                       ].
-                box open.
-                box accepted ifFalse:[
-                    ^ self
-                ].
-                doRemove ifTrue:[
+	].
+	classesNotInRepository notEmpty ifTrue:[
+	    "/ if there are no changeSet entries for those classes, they seem to be
+	    "/ no longer in the repository (possibly moved ?)
+	    "/ If there are entries, these might have been added in the image and need a check-in
+	    classesAddedInImage := classesNotInRepository select:[:cls | ChangeSet current includesChangeForClassOrMetaclass:cls].
+	    classesAddedInImage isEmpty ifTrue:[
+		doRemove := false.
+		box := Dialog
+		    forRequestText:(resources stringWithCRs:'The following classes are no longer in the repository (or moved to another package).\\Remove classes from the image ?')
+		    editViewClass:ListView
+		    lines:10 columns:20
+		    initialAnswer:nil model:nil
+		    setupWith:
+		       [:v :d |
+				|removeButton|
+
+				removeButton := Button label:(resources string:'Remove').
+				removeButton action:[ doRemove := true. box okPressed. ].
+				v list:classesNotInRepository.
+				d addButton:removeButton after:(d okButton).
+				d okButton label:(resources string:'Continue').
+				d okButton isReturnButton:true.
+		       ].
+		box open.
+		box accepted ifFalse:[
+		    ^ self
+		].
+		doRemove ifTrue:[
 self halt.
-                    classesNotInRepository do:[:eachClassToRemove |
-                        |subClasses|
-
-                        subClasses := eachClassToRemove allSubclasses.
-                        (subClasses conform:
-                            [:subClass |
-                                |ownerOrClassItself|
-
-                                ownerOrClassItself := subClass topOwningClass ? subClass.
-                                (classesNotInRepository includes:ownerOrClassItself)
-                            ])
-                        ifTrue:[
-                            Smalltalk removeClass:eachClassToRemove.
-                            ChangeSet current condenseChangesForClass:eachClassToRemove.
-                        ] ifFalse:[
-                            Dialog warn:'Cannit simply remove the class - more repair needed due to subclass(es)'.
-                        ].
-                    ].
-                ].
-            ] ifFalse:[
+		    classesNotInRepository do:[:eachClassToRemove |
+			|subClasses|
+
+			subClasses := eachClassToRemove allSubclasses.
+			(subClasses conform:
+			    [:subClass |
+				|ownerOrClassItself|
+
+				ownerOrClassItself := subClass topOwningClass ? subClass.
+				(classesNotInRepository includes:ownerOrClassItself)
+			    ])
+			ifTrue:[
+			    Smalltalk removeClass:eachClassToRemove.
+			    ChangeSet current condenseChangesForClass:eachClassToRemove.
+			] ifFalse:[
+			    Dialog warn:'Cannit simply remove the class - more repair needed due to subclass(es)'.
+			].
+		    ].
+		].
+	    ] ifFalse:[
 self halt.
-            ].
-        ].
-
-        anyDifference ifFalse:[
-            "/ Dialog information:(resources string:'%1 is up-to-date.' with:eachProject allBold).
-            Transcript showCR:('%1 is up-to-date.' bindWith:eachProject allBold).
-            ChangeSet current condenseChangesForPackage:eachProject.
-        ] ifTrue:[
+	    ].
+	].
+
+	anyDifference ifFalse:[
+	    "/ Dialog information:(resources string:'%1 is up-to-date.' with:eachProject allBold).
+	    Transcript showCR:('%1 is up-to-date.' bindWith:eachProject allBold).
+	    ChangeSet current condenseChangesForPackage:eachProject.
+	] ifTrue:[
 self halt.
-            self checkOutClasses:(self selectedProjectClasses) askForRevision:false
-        ].
+	    self checkOutClasses:(self selectedProjectClasses) askForRevision:false
+	].
     ].
 
     "Modified: / 13-10-2006 / 01:31:43 / cg"
@@ -36979,16 +37431,16 @@
     problems := OrderedCollection new.
 
     self selectedProjectsDo:[:package |
-        checker := ProjectChecker check: package.
-        problems addAll: checker problems
+	checker := ProjectChecker check: package.
+	problems addAll: checker problems
     ].
 
     problems isEmpty ifTrue:[
-        Dialog information: 'Excellent!! No problems found!!'.
-    ] ifFalse:[
-        Tools::ProjectCheckerBrowser new
-            problemList: problems;
-            open
+	Dialog information: 'Excellent!! No problems found!!'.
+    ] ifFalse:[
+	Tools::ProjectCheckerBrowser new
+	    problemList: problems;
+	    open
     ]
 
     "Created: / 23-02-2012 / 14:08:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -37004,175 +37456,175 @@
     SourceCodeManager isNil ifTrue:[^ self warn:'No SourceCodeManagement is configured.'].
 
     self withWaitCursorDo:[
-        |classesToLoad classesToUnload classesWithMissingContainer classesWithRepositoryMismatches
-         obsoleteContainers allChangeSets answer needExtensionsContainer hasExtensionContainer
-         classesWithNewerVersionInRepository classesWhichHaveBeenModified|
-
-        classesWithRepositoryMismatches := OrderedCollection new.
-        classesWithMissingContainer := OrderedCollection new.
-        obsoleteContainers := OrderedCollection new.
-        classesWithNewerVersionInRepository := OrderedCollection new.
-        classesWhichHaveBeenModified := OrderedCollection new.
-
-        self selectedProjectsDo:[:packageToCheck |
-            |containerModule containerPackage containers allContainers
-             hasLoadAll hasMakeProto hasMakeSpec hasBcMakefile hasNtMakefile hasAbbrev
-             otherFiles classesInProject |
-
-            containerModule := packageToCheck upTo:$:.
-            containerPackage := packageToCheck copyFrom:(containerModule size + 2).
-
-            self busyLabel:'Checking ' , packageToCheck , '...'.
-
-            allContainers := SourceCodeManager getExistingContainersInModule:containerModule directory:containerPackage.
-            allContainers := allContainers select:[:each | (each startsWith:'.') not].
-
-            hasLoadAll := allContainers includes:'loadAll'.
-            hasMakeProto := allContainers includes:'Make.proto'.
-            hasMakeSpec := allContainers includes:'Make.spec'.
-            hasBcMakefile := allContainers includes:'bc.mak'.
-            hasNtMakefile := allContainers includes:'nt.mak'.
-            hasAbbrev := allContainers includes:'abbrev.stc'.
-            hasExtensionContainer := allContainers includes:'extensions.st'.
-
-            containers := allContainers copyAsOrderedCollection.
-            containers removeAllFoundIn:#('loadAll' 'Make.proto' 'Make.spec' 'nt.mak' 'bc.mak' 'abbrev.stc' 'extensions.st').
-            otherFiles := containers select:[:each | (each asFilename hasSuffix:'st') not].
-            containers removeAllFoundIn:otherFiles.
-
-            classesInProject := IdentitySet new.
-            needExtensionsContainer := false.
-            Smalltalk allClassesDo:[:aClass |
-                (packageToCheck = aClass package) ifTrue:[
-                    aClass isPrivate ifFalse:[
-                        classesInProject add:aClass .
-                    ]
-                ] ifFalse:[
-                    needExtensionsContainer := needExtensionsContainer or:[aClass hasExtensionsFrom:packageToCheck].
-                ]
-            ].
-
-            "/ load unloaded classes...
-            classesToLoad := OrderedCollection new.
-            classesInProject do:[:eachClassInProject |
-                eachClassInProject isLoaded ifFalse:[
-                    classesToLoad add:eachClassInProject
-                ].
-            ].
-            classesToLoad size > 0 ifTrue:[
-                answer := Dialog confirmWithCancel:(resources string:'%1 class(es) are not loaded.\(Unloaded classes will be skipped when checking)\\Load them first ?'
-                                                              with:classesToLoad size) withCRs
-                                 default:false.
-                answer isNil ifTrue:[^ self].
-
-                answer ifTrue:[
-                    classesToUnload := OrderedCollection new.
-                    classesInProject do:[:eachClassInProject |
-                        eachClassInProject isLoaded ifFalse:[
-                            eachClassInProject autoload.
-                            classesToUnload add:eachClassInProject
-                        ].
-                    ].
-                ].
-            ].
-
-            "/ any class without container ?
-            classesInProject do:[:eachClassInProject |
-                |mgr info classesModule classesPackageDir classesContainerFileName|
-
-                eachClassInProject isPrivate ifFalse:[
-                  "/ eachClassInProject isLoaded ifTrue:[
-                    self busyLabel:'Checking ' , packageToCheck , ' - ' , eachClassInProject name.
-
-                    mgr := SourceCodeManagerUtilities default sourceCodeManagerFor:eachClassInProject.
-                    info := mgr sourceInfoOfClass:eachClassInProject.
-                    info isNil ifTrue:[
-                        "/ no container for that class
-                    ] ifFalse:[
-                        (info includesKey:#module) ifTrue:[
-                            classesModule := (info at:#module).
-                        ].
-                        (info includesKey:#directory) ifTrue:[
-                            classesPackageDir := (info at:#directory).
-                        ].
-                        classesContainerFileName := mgr containerFromSourceInfo:info.
-
-                        "/ module & packageDir must match
-                        ((classesModule ~= containerModule)
-                        or:[classesPackageDir ~= containerPackage]) ifTrue:[
-                            classesWithRepositoryMismatches add:eachClassInProject
-                        ].
-                        (containers includes:classesContainerFileName) ifFalse:[
-                            classesWithMissingContainer add:eachClassInProject.
-                        ] ifTrue:[
-                            eachClassInProject isLoaded ifTrue:[
-                                eachClassInProject revision ~= (mgr newestRevisionOf:eachClassInProject)
-                                ifTrue:[
-                                    classesWithNewerVersionInRepository add:eachClassInProject.
-                                ].
-                            ].
-                        ].
-                        containers remove:classesContainerFileName ifAbsent:nil.
-                    ].
-                ].
-            ].
-
-            "/ any container left ?
-            containers notEmpty ifTrue:[
-                obsoleteContainers add:(packageToCheck -> containers).
-            ].
-
-            "/ any version mismatches ?
-            classesInProject do:[:eachClassInProject |
-              eachClassInProject isLoaded ifTrue:[
-                (classesWithMissingContainer includes:eachClassInProject) ifFalse:[
-                    (classesWithRepositoryMismatches includes:eachClassInProject) ifFalse:[
-                        "/ class modified ?
-                        allChangeSets isNil ifTrue:[
-                            allChangeSets := ChangeSet allInstances.
-                        ].
-                        (allChangeSets contains:[:aChangeSet |
-                            (eachClassInProject hasUnsavedChanges)
-                            or:[eachClassInProject allPrivateClasses contains:[:aPrivateClass |
-                                    aPrivateClass hasUnsavedChanges]]
-                        ])
-                        ifTrue:[
-                            classesWhichHaveBeenModified add:eachClassInProject
-                        ]
-                    ]
-                ]
-              ]
-            ].
-
-            classesToUnload size >0 ifTrue:[
-                answer := Dialog confirm:(resources string:'%1 class(es) were loaded - unload them now ?'
-                                          with:classesToLoad size)
-                                 default:false.
-                answer ifTrue:[
-                    "/ unload classes which have been loaded temporarily
-                    classesToUnload do:[:eachClassToUnload |
-                        eachClassToUnload unload
-                    ].
-                ]
-            ]
-        ].
-
-        (obsoleteContainers notEmpty
-        or:[ classesWithRepositoryMismatches notEmpty
-        or:[ classesWithMissingContainer notEmpty
-        or:[ classesWhichHaveBeenModified notEmpty
-        or:[ classesWithNewerVersionInRepository notEmpty
-        or:[ needExtensionsContainer ~~ hasExtensionContainer ]]]]])
-        ifTrue:[
-            self
-                openRepositoryConsistencyDialogForObsoleteContainers:obsoleteContainers
-                classesWithRepositoryMismatches:classesWithRepositoryMismatches
-                classesWithMissingContainer:classesWithMissingContainer
-                classesWhichHaveBeenModified:classesWhichHaveBeenModified
-                classesWithNewerVersionInRepository:classesWithNewerVersionInRepository
-                needExtensionsContainer:needExtensionsContainer
-                hasExtensionContainer:hasExtensionContainer
-        ]
+	|classesToLoad classesToUnload classesWithMissingContainer classesWithRepositoryMismatches
+	 obsoleteContainers allChangeSets answer needExtensionsContainer hasExtensionContainer
+	 classesWithNewerVersionInRepository classesWhichHaveBeenModified|
+
+	classesWithRepositoryMismatches := OrderedCollection new.
+	classesWithMissingContainer := OrderedCollection new.
+	obsoleteContainers := OrderedCollection new.
+	classesWithNewerVersionInRepository := OrderedCollection new.
+	classesWhichHaveBeenModified := OrderedCollection new.
+
+	self selectedProjectsDo:[:packageToCheck |
+	    |containerModule containerPackage containers allContainers
+	     hasLoadAll hasMakeProto hasMakeSpec hasBcMakefile hasNtMakefile hasAbbrev
+	     otherFiles classesInProject |
+
+	    containerModule := packageToCheck upTo:$:.
+	    containerPackage := packageToCheck copyFrom:(containerModule size + 2).
+
+	    self busyLabel:'Checking ' , packageToCheck , '...'.
+
+	    allContainers := SourceCodeManager getExistingContainersInModule:containerModule directory:containerPackage.
+	    allContainers := allContainers select:[:each | (each startsWith:'.') not].
+
+	    hasLoadAll := allContainers includes:'loadAll'.
+	    hasMakeProto := allContainers includes:'Make.proto'.
+	    hasMakeSpec := allContainers includes:'Make.spec'.
+	    hasBcMakefile := allContainers includes:'bc.mak'.
+	    hasNtMakefile := allContainers includes:'nt.mak'.
+	    hasAbbrev := allContainers includes:'abbrev.stc'.
+	    hasExtensionContainer := allContainers includes:'extensions.st'.
+
+	    containers := allContainers copyAsOrderedCollection.
+	    containers removeAllFoundIn:#('loadAll' 'Make.proto' 'Make.spec' 'nt.mak' 'bc.mak' 'abbrev.stc' 'extensions.st').
+	    otherFiles := containers select:[:each | (each asFilename hasSuffix:'st') not].
+	    containers removeAllFoundIn:otherFiles.
+
+	    classesInProject := IdentitySet new.
+	    needExtensionsContainer := false.
+	    Smalltalk allClassesDo:[:aClass |
+		(packageToCheck = aClass package) ifTrue:[
+		    aClass isPrivate ifFalse:[
+			classesInProject add:aClass .
+		    ]
+		] ifFalse:[
+		    needExtensionsContainer := needExtensionsContainer or:[aClass hasExtensionsFrom:packageToCheck].
+		]
+	    ].
+
+	    "/ load unloaded classes...
+	    classesToLoad := OrderedCollection new.
+	    classesInProject do:[:eachClassInProject |
+		eachClassInProject isLoaded ifFalse:[
+		    classesToLoad add:eachClassInProject
+		].
+	    ].
+	    classesToLoad size > 0 ifTrue:[
+		answer := Dialog confirmWithCancel:(resources string:'%1 class(es) are not loaded.\(Unloaded classes will be skipped when checking)\\Load them first ?'
+							      with:classesToLoad size) withCRs
+				 default:false.
+		answer isNil ifTrue:[^ self].
+
+		answer ifTrue:[
+		    classesToUnload := OrderedCollection new.
+		    classesInProject do:[:eachClassInProject |
+			eachClassInProject isLoaded ifFalse:[
+			    eachClassInProject autoload.
+			    classesToUnload add:eachClassInProject
+			].
+		    ].
+		].
+	    ].
+
+	    "/ any class without container ?
+	    classesInProject do:[:eachClassInProject |
+		|mgr info classesModule classesPackageDir classesContainerFileName|
+
+		eachClassInProject isPrivate ifFalse:[
+		  "/ eachClassInProject isLoaded ifTrue:[
+		    self busyLabel:'Checking ' , packageToCheck , ' - ' , eachClassInProject name.
+
+		    mgr := SourceCodeManagerUtilities default sourceCodeManagerFor:eachClassInProject.
+		    info := mgr sourceInfoOfClass:eachClassInProject.
+		    info isNil ifTrue:[
+			"/ no container for that class
+		    ] ifFalse:[
+			(info includesKey:#module) ifTrue:[
+			    classesModule := (info at:#module).
+			].
+			(info includesKey:#directory) ifTrue:[
+			    classesPackageDir := (info at:#directory).
+			].
+			classesContainerFileName := mgr containerFromSourceInfo:info.
+
+			"/ module & packageDir must match
+			((classesModule ~= containerModule)
+			or:[classesPackageDir ~= containerPackage]) ifTrue:[
+			    classesWithRepositoryMismatches add:eachClassInProject
+			].
+			(containers includes:classesContainerFileName) ifFalse:[
+			    classesWithMissingContainer add:eachClassInProject.
+			] ifTrue:[
+			    eachClassInProject isLoaded ifTrue:[
+				eachClassInProject revision ~= (mgr newestRevisionOf:eachClassInProject)
+				ifTrue:[
+				    classesWithNewerVersionInRepository add:eachClassInProject.
+				].
+			    ].
+			].
+			containers remove:classesContainerFileName ifAbsent:nil.
+		    ].
+		].
+	    ].
+
+	    "/ any container left ?
+	    containers notEmpty ifTrue:[
+		obsoleteContainers add:(packageToCheck -> containers).
+	    ].
+
+	    "/ any version mismatches ?
+	    classesInProject do:[:eachClassInProject |
+	      eachClassInProject isLoaded ifTrue:[
+		(classesWithMissingContainer includes:eachClassInProject) ifFalse:[
+		    (classesWithRepositoryMismatches includes:eachClassInProject) ifFalse:[
+			"/ class modified ?
+			allChangeSets isNil ifTrue:[
+			    allChangeSets := ChangeSet allInstances.
+			].
+			(allChangeSets contains:[:aChangeSet |
+			    (eachClassInProject hasUnsavedChanges)
+			    or:[eachClassInProject allPrivateClasses contains:[:aPrivateClass |
+				    aPrivateClass hasUnsavedChanges]]
+			])
+			ifTrue:[
+			    classesWhichHaveBeenModified add:eachClassInProject
+			]
+		    ]
+		]
+	      ]
+	    ].
+
+	    classesToUnload size >0 ifTrue:[
+		answer := Dialog confirm:(resources string:'%1 class(es) were loaded - unload them now ?'
+					  with:classesToLoad size)
+				 default:false.
+		answer ifTrue:[
+		    "/ unload classes which have been loaded temporarily
+		    classesToUnload do:[:eachClassToUnload |
+			eachClassToUnload unload
+		    ].
+		]
+	    ]
+	].
+
+	(obsoleteContainers notEmpty
+	or:[ classesWithRepositoryMismatches notEmpty
+	or:[ classesWithMissingContainer notEmpty
+	or:[ classesWhichHaveBeenModified notEmpty
+	or:[ classesWithNewerVersionInRepository notEmpty
+	or:[ needExtensionsContainer ~~ hasExtensionContainer ]]]]])
+	ifTrue:[
+	    self
+		openRepositoryConsistencyDialogForObsoleteContainers:obsoleteContainers
+		classesWithRepositoryMismatches:classesWithRepositoryMismatches
+		classesWithMissingContainer:classesWithMissingContainer
+		classesWhichHaveBeenModified:classesWhichHaveBeenModified
+		classesWithNewerVersionInRepository:classesWithNewerVersionInRepository
+		needExtensionsContainer:needExtensionsContainer
+		hasExtensionContainer:hasExtensionContainer
+	]
     ].
     self normalLabel
 
@@ -37183,12 +37635,12 @@
     "remove all changes for the selected project(s) from the changeSet"
 
     (self confirm:'This will remove all changes for the selected project(s) from the changeSet.\\Really cleanup ?' withCRs)
-        ifFalse:[ ^ self].
+	ifFalse:[ ^ self].
 
     self withWaitCursorDo:[
-        self selectedProjectsDo:[:eachProject |
-            ChangeSet current condenseChangesForPackage:eachProject
-        ].
+	self selectedProjectsDo:[:eachProject |
+	    ChangeSet current condenseChangesForPackage:eachProject
+	].
     ]
 
     "Created: / 26-10-2006 / 19:41:27 / cg"
@@ -37201,9 +37653,9 @@
     <resource: #obsolete> "use ...Using:manager variant"
 
     self withWaitCursorDo:[
-        self selectedProjects value do:[:eachProject |
-            SourceCodeManagerUtilities compareProjectWithRepository:eachProject
-        ].
+	self selectedProjects value do:[:eachProject |
+	    SourceCodeManagerUtilities compareProjectWithRepository:eachProject
+	].
     ].
 
     "Created: / 12-10-2006 / 17:41:55 / cg"
@@ -37216,9 +37668,9 @@
      against the the newest version found in the repository."
 
     self withWaitCursorDo:[
-        self selectedProjects value do:[:eachProject |
-            manager utilities compareProjectWithRepository:eachProject
-        ].
+	self selectedProjects value do:[:eachProject |
+	    manager utilities compareProjectWithRepository:eachProject
+	].
     ].
 
     "Modified: / 12-10-2006 / 21:46:14 / cg"
@@ -37242,19 +37694,19 @@
 
     |string date|
 
-    string := Dialog 
-                request:(resources 
-                        string:'Compare with version from date: (%1)' 
-                        with:(UserPreferences current dateInputFormat))
-                initialAnswer:(Date today printStringFormat:(UserPreferences current dateInputFormat)).
+    string := Dialog
+		request:(resources
+			string:'Compare with version from date: (%1)'
+			with:(UserPreferences current dateInputFormat))
+		initialAnswer:(Date today printStringFormat:(UserPreferences current dateInputFormat)).
 
     string isEmptyOrNil ifTrue:[^ self].
     date := Date readFrom:string printFormat:(UserPreferences current dateInputFormat).
 
     self withWaitCursorDo:[
-        self selectedProjects value do:[:eachProject |
-            SourceCodeManagerUtilities compareProject:eachProject withRepositoryVersionFrom:date
-        ].
+	self selectedProjects value do:[:eachProject |
+	    SourceCodeManagerUtilities compareProject:eachProject withRepositoryVersionFrom:date
+	].
     ].
 
     "Created: / 12-10-2006 / 17:41:55 / cg"
@@ -37278,35 +37730,35 @@
     selectedProjects := self selectedProjectsValue.
     currentProject := self theSingleSelectedProject.
     currentProject notNil ifTrue:[
-        fileName := currentProject asString copy replaceAny:' :/' with:$_.
-    ] ifFalse:[
-        fileName := 'someProjects'
+	fileName := currentProject asString copy replaceAny:' :/' with:$_.
+    ] ifFalse:[
+	fileName := 'someProjects'
     ].
     aFormatSymbolOrNil == #xml ifTrue:[
-        suffix := '.xml'
-    ] ifFalse:[
-        aFormatSymbolOrNil == #sif ifTrue:[
-            suffix := '.sif'
-        ] ifFalse:[
-            aFormatSymbolOrNil == #binary ifTrue:[
-                suffix := '.cls'
-            ] ifFalse:[
-                suffix := '.st'
-            ]
-        ]
+	suffix := '.xml'
+    ] ifFalse:[
+	aFormatSymbolOrNil == #sif ifTrue:[
+	    suffix := '.sif'
+	] ifFalse:[
+	    aFormatSymbolOrNil == #binary ifTrue:[
+		suffix := '.cls'
+	    ] ifFalse:[
+		suffix := '.st'
+	    ]
+	]
     ].
     fileName := fileName , suffix.
 
     aFormatSymbolOrNil == #binary ifTrue:[
-        self error:'binary must go into separate files' mayProceed:true.
-        ^ self
-    ].
-
-    saveName := Dialog 
-        requestFileNameForSave:(resources string:'FileOut %1 as:' with:(currentProject ? 'selected projects'))
-        default:fileName
-        fromDirectory:(FileSelectionBox lastFileSelectionDirectory).
-    
+	self error:'binary must go into separate files' mayProceed:true.
+	^ self
+    ].
+
+    saveName := Dialog
+	requestFileNameForSave:(resources string:'FileOut %1 as:' with:(currentProject ? 'selected projects'))
+	default:fileName
+	fromDirectory:(FileSelectionBox lastFileSelectionDirectory).
+
 "/    fileBox := FileSelectionBox
 "/                    title:(resources string:'FileOut %1 as:' with:(currentProject ? 'selected projects'))
 "/                    okText:(resources string:'FileOut')
@@ -37324,63 +37776,63 @@
 "/    fileBox := nil.
 
     saveName isEmptyOrNil ifTrue:[
-        ^ self
+	^ self
     ].
     FileSelectionBox lastFileSelectionDirectory:(saveName asFilename directoryName).
     fileName := saveName.
 
     aFormatSymbolOrNil == #sif ifTrue:[
-        SmalltalkInterchangeSTXFileOutManager initialize.
-        mgr := SmalltalkInterchangeFileManager newForFileOut.
-        mgr fileName: fileName.
-        self selectedProjectClasses do:[:eachClass |
-            mgr addClass:eachClass.
-        ].
-        Smalltalk allClassesDo:[:eachClass |
-            eachClass instAndClassSelectorsAndMethodsDo:[:sel :mthd |
-                |mPckg|
-
-                mPckg := mthd package.
-                mPckg ~= eachClass package ifTrue:[
-                    (selectedProjects includes:mPckg) ifTrue:[
-                        mgr addMethodNamed:mthd selector ofClass:mthd mclass
-                    ]
-                ]
-            ]
-        ].
-        self busyLabel:'writing...'.
-        mgr fileOut.
-        self normalLabel.
-        ^ self
+	SmalltalkInterchangeSTXFileOutManager initialize.
+	mgr := SmalltalkInterchangeFileManager newForFileOut.
+	mgr fileName: fileName.
+	self selectedProjectClasses do:[:eachClass |
+	    mgr addClass:eachClass.
+	].
+	Smalltalk allClassesDo:[:eachClass |
+	    eachClass instAndClassSelectorsAndMethodsDo:[:sel :mthd |
+		|mPckg|
+
+		mPckg := mthd package.
+		mPckg ~= eachClass package ifTrue:[
+		    (selectedProjects includes:mPckg) ifTrue:[
+			mgr addMethodNamed:mthd selector ofClass:mthd mclass
+		    ]
+		]
+	    ]
+	].
+	self busyLabel:'writing...'.
+	mgr fileOut.
+	self normalLabel.
+	^ self
     ].
 
     aFormatSymbolOrNil isNil ifTrue:[
-        self busyLabel:'writing...'.
-        s := fileName asFilename writeStream.
-        classesToFileout := OrderedCollection withAll:(self selectedProjectClasses).
-        classesToFileout topologicalSort:[:a :b | b isSubclassOf:a].
-
-        classesToFileout do:[:eachClass |
-            eachClass fileOutOn:s.
-        ].
-
-        Smalltalk allClassesDo:[:eachClass |
-            eachClass instAndClassSelectorsAndMethodsDo:[:sel :mthd |
-                |mPckg|
-
-                mPckg := mthd package.
-                (mPckg = currentProject and:[mPckg ~= eachClass package]) ifTrue:[
-                    eachClass 
-                        fileOutCategory:mthd category 
-                        methodFilter:[:m | m == mthd] 
-                        on:s.
-                    s cr.
-                ]
-            ]
-        ].
-        s close.
-        self normalLabel.
-        ^ self.
+	self busyLabel:'writing...'.
+	s := fileName asFilename writeStream.
+	classesToFileout := OrderedCollection withAll:(self selectedProjectClasses).
+	classesToFileout topologicalSort:[:a :b | b isSubclassOf:a].
+
+	classesToFileout do:[:eachClass |
+	    eachClass fileOutOn:s.
+	].
+
+	Smalltalk allClassesDo:[:eachClass |
+	    eachClass instAndClassSelectorsAndMethodsDo:[:sel :mthd |
+		|mPckg|
+
+		mPckg := mthd package.
+		(mPckg = currentProject and:[mPckg ~= eachClass package]) ifTrue:[
+		    eachClass
+			fileOutCategory:mthd category
+			methodFilter:[:m | m == mthd]
+			on:s.
+		    s cr.
+		]
+	    ]
+	].
+	s close.
+	self normalLabel.
+	^ self.
     ].
 
     self shouldImplement.
@@ -37390,67 +37842,67 @@
 
 projectMenuFileOutBuildSupportFiles
     self selectedProjectsDo:[:packageToCheckIn |
-        self projectMenuFileOutBuildSupportFilesForProject:packageToCheckIn
-    ]
-!
-
-projectMenuFileOutBuildSupportFilesForProject:packageIDSymbol 
+	self projectMenuFileOutBuildSupportFilesForProject:packageToCheckIn
+    ]
+!
+
+projectMenuFileOutBuildSupportFilesForProject:packageIDSymbol
     |directory defClass foundPackageDir packageID fullPathName|
 
     defClass := ProjectDefinition definitionClassForPackage:packageIDSymbol
-                createIfAbsent:false.
+		createIfAbsent:false.
     defClass isNil ifTrue:[
-        defClass := self projectDefinitionDialogFor:packageID.
-        defClass isNil ifTrue:[
-            ^ self
-        ].
-        defClass compileDescriptionMethods.
+	defClass := self projectDefinitionDialogFor:packageID.
+	defClass isNil ifTrue:[
+	    ^ self
+	].
+	defClass compileDescriptionMethods.
     ].
     defClass validateDescription.
     defClass hasAllCompiledClassesFullyLoaded ifFalse:[
-        (Dialog 
-            confirm:('%1: the dependency information as generated will be incomplete,%<cr>because some compiled class(es) are not loaded (see Transcript).%<cr>%<cr>%2%<cr>Continue anyway ?' 
-                    bindWith:defClass name
-                    with:('Warning: these classes will be excluded from the list of compiled classes.' 
-                            allBold))) 
-                ifFalse:[ ^ self. ]
+	(Dialog
+	    confirm:('%1: the dependency information as generated will be incomplete,%<cr>because some compiled class(es) are not loaded (see Transcript).%<cr>%<cr>%2%<cr>Continue anyway ?'
+		    bindWith:defClass name
+		    with:('Warning: these classes will be excluded from the list of compiled classes.'
+			    allBold)))
+		ifFalse:[ ^ self. ]
     ].
     packageID := packageIDSymbol asPackageId.
     directory := packageID directory.
-    Smalltalk packagePath 
-        detect:[:eachDir | 
-            |thisPackageDir|
-
-            thisPackageDir := packageID pathRelativeToTopDirectory:eachDir.
-            thisPackageDir exists ifTrue:[
-                foundPackageDir := thisPackageDir.
-                true.
-            ] ifFalse:[ false ].
-        ].
-    directory := Dialog 
-                requestDirectoryName:'Directory Where to Generate Build Support Files?'
-                default:foundPackageDir.
+    Smalltalk packagePath
+	detect:[:eachDir |
+	    |thisPackageDir|
+
+	    thisPackageDir := packageID pathRelativeToTopDirectory:eachDir.
+	    thisPackageDir exists ifTrue:[
+		foundPackageDir := thisPackageDir.
+		true.
+	    ] ifFalse:[ false ].
+	].
+    directory := Dialog
+		requestDirectoryName:'Directory Where to Generate Build Support Files?'
+		default:foundPackageDir.
     directory isNil ifTrue:[
-        ^ self.
+	^ self.
     ].
     directory := directory asFilename.
     directory exists ifFalse:[
-        Dialog warn:'Directory does not exists!!'.
-        ^ self.
-    ].
-    self activityNotification:(resources 
-                string:'generating build-support files...').
+	Dialog warn:'Directory does not exists!!'.
+	^ self.
+    ].
+    self activityNotification:(resources
+		string:'generating build-support files...').
 
     self withActivityNotificationsRedirectedToInfoLabelDo:[
-        defClass forEachFileNameAndGeneratedContentsDo:[:fileName :fileContents |
-            self showInfo:(resources string:'filing out %1...' with:fileName).
-            fullPathName := directory construct:fileName.
-            fullPathName directory exists ifFalse:[
-                "take care for files like 'autopackage/default.apspec'"
-                fullPathName directory makeDirectory.
-            ].
-            fullPathName contents:fileContents.
-        ].
+	defClass forEachFileNameAndGeneratedContentsDo:[:fileName :fileContents |
+	    self showInfo:(resources string:'filing out %1...' with:fileName).
+	    fullPathName := directory construct:fileName.
+	    fullPathName directory exists ifFalse:[
+		"take care for files like 'autopackage/default.apspec'"
+		fullPathName directory makeDirectory.
+	    ].
+	    fullPathName contents:fileContents.
+	].
     ].
     self activityNotification:nil.
 
@@ -37476,38 +37928,38 @@
 
     currentProject := self theSingleSelectedProject ? 'selected projects'.
     dirName := self
-                askForDirectoryToFileOut:(resources string:'FileOut %1 in:'
-                                                    with:currentProject)
-                default:nil.
+		askForDirectoryToFileOut:(resources string:'FileOut %1 in:'
+						    with:currentProject)
+		default:nil.
     dirName isNil ifTrue:[
-        ^ self
+	^ self
     ].
     dirName asFilename exists ifFalse:[
-        dirName asFilename recursiveMakeDirectory    
-    ].
-
-    self
-        fileOutEachClassIn:self selectedProjectClasses
-        in:dirName
-        withFormat:aFormatSymbolOrNil.
+	dirName asFilename recursiveMakeDirectory
+    ].
+
+    self
+	fileOutEachClassIn:self selectedProjectClasses
+	in:dirName
+	withFormat:aFormatSymbolOrNil.
     methodsToFileOut := OrderedCollection new.
     Smalltalk allClassesDo:[:eachClass |
-        eachClass instAndClassSelectorsAndMethodsDo:[:sel :mthd |
-            |mPckg|
-
-            mPckg := mthd package.
-            (mPckg = currentProject and:[mPckg ~= eachClass package]) ifTrue:[
-                methodsToFileOut add:mthd
-            ]
-        ]
+	eachClass instAndClassSelectorsAndMethodsDo:[:sel :mthd |
+	    |mPckg|
+
+	    mPckg := mthd package.
+	    (mPckg = currentProject and:[mPckg ~= eachClass package]) ifTrue:[
+		methodsToFileOut add:mthd
+	    ]
+	]
     ].
     dirName := dirName asFilename.
     fileNameForExtensions := (dirName construct:'extensions') withSuffix:(self fileSuffixForFormat:aFormatSymbolOrNil).
     self
-        fileOutMethods:methodsToFileOut
-        format:aFormatSymbolOrNil
-        toFile:fileNameForExtensions
-        withPackage:true
+	fileOutMethods:methodsToFileOut
+	format:aFormatSymbolOrNil
+	toFile:fileNameForExtensions
+	withPackage:true
 
     "Modified: / 05-09-2011 / 22:02:48 / cg"
 !
@@ -37570,249 +38022,249 @@
 
     default := LastImportedPackage.
     default isNil ifTrue:[
-        currentProject := self theSingleSelectedProject.
-        currentProject isNil ifTrue:[
-            default := 'module:package'.
-        ] ifFalse:[
-            module := currentProject upTo:$:.
-            module size + 2 > currentProject size ifTrue:[
-                default := currentProject , ':*'
-            ] ifFalse:[
-                default := currentProject , '/*'
-            ].
-        ].
+	currentProject := self theSingleSelectedProject.
+	currentProject isNil ifTrue:[
+	    default := 'module:package'.
+	] ifFalse:[
+	    module := currentProject upTo:$:.
+	    module size + 2 > currentProject size ifTrue:[
+		default := currentProject , ':*'
+	    ] ifFalse:[
+		default := currentProject , '/*'
+	    ].
+	].
     ].
 
     SourceCodeManager notNil ifTrue:[
-        fromWhere := 'repository'
-    ] ifFalse:[
-        fromWhere := 'file system'
+	fromWhere := 'repository'
+    ] ifFalse:[
+	fromWhere := 'file system'
     ].
 
     msg := 'Name of package to import '.
     doLoadClasses ifFalse:[
-        msg := msg , '(i.e. install as autoloaded) '.
+	msg := msg , '(i.e. install as autoloaded) '.
     ].
     msg := msg , 'from ' , fromWhere , ':\'.
     msg := msg , '   use ''module:*'' to import a complete module;\'.
     msg := msg , '   use ''module:package'' to import a package with all of its subpackages;\'.
     msg := msg , '   use ''module:package/*'' to import subpackages only.'.
     pkg := Dialog
-                request:msg withCRs
-                initialAnswer:default.
+		request:msg withCRs
+		initialAnswer:default.
     pkg size == 0 ifTrue:[^ self].
     LastImportedPackage := pkg.
 
     "/ see if such a module/package exists in the repository
     module := pkg asPackageId module.
     module size + 2 > pkg size ifTrue:[
-        package := checkedOutPackageDir := nil.  "/ i.e. all
-    ] ifFalse:[
-        package := checkedOutPackageDir := pkg asPackageId directory.
-        (package includesMatchCharacters) ifTrue:[
-            "if the match-char is not at the end..."
-            ((package endsWith:'/*') and:[ (package copyWithoutLast:2) includesMatchCharacters not ])
-            ifTrue:[
-                checkedOutPackageDir := package copyWithoutLast:2
-            ] ifFalse:[
-                checkedOutPackageDir := nil.      "/ must check out everything and filter
-            ]
-        ].
+	package := checkedOutPackageDir := nil.  "/ i.e. all
+    ] ifFalse:[
+	package := checkedOutPackageDir := pkg asPackageId directory.
+	(package includesMatchCharacters) ifTrue:[
+	    "if the match-char is not at the end..."
+	    ((package endsWith:'/*') and:[ (package copyWithoutLast:2) includesMatchCharacters not ])
+	    ifTrue:[
+		checkedOutPackageDir := package copyWithoutLast:2
+	    ] ifFalse:[
+		checkedOutPackageDir := nil.      "/ must check out everything and filter
+	    ]
+	].
     ].
 
     sourceCodeManager := (AbstractSourceCodeManager managerForModule:module) ? AbstractSourceCodeManager defaultManager.
 
     UnimplementedFunctionalityError,SourceCodeManagerError handle:[:ex |
-        |msg1 msg2|
-
-        (UnimplementedFunctionalityError accepts:ex signal) ifTrue:[
-            msg1 := 'Cannot access module "%1".\\'.
-            msg2 := 'Missing functionality in the "%2"-source code manager.'.
-        ] ifFalse:[
-            msg1 := 'Cannot access module "%1".\\'.
-            msg2 := ex errorString ? ('No module "%1" in the repository (%2).').
-        ].
-
-        (Dialog confirm:
-                    (resources stringWithCRs:msg1 with:module)
-                    ,(resources string:msg2 with:module with:sourceCodeManager managerTypeName)
-                    ,(resources stringWithCRs:('\\Import from the filesystem ?')))
-        ifFalse:[
-            ^ self.
-        ].
-        importFromFilesystem := true.
-
-        checkedOutPackageDir isNil ifTrue:[
-            default := Smalltalk projectDirectoryForPackage:module.
-        ] ifFalse:[
-            default := Smalltalk projectDirectoryForPackage:pkg.
-        ].
-        (default notNil
-            and:[ (default := default asFilename) exists
-            and:[ default isDirectory ]])
-        ifFalse:[
-            default := nil.
-        ].
-
-        importDirectory := Dialog
-                            requestDirectoryName:(resources
-                                                    string:'Import "%1" from Directory:'
-                                                    with:pkg)
-                            default:default.
-        importDirectory isEmptyOrNil ifTrue:[
-            ^ self
-        ].
-        importDirectory := importDirectory asFilename pathName asFilename.
+	|msg1 msg2|
+
+	(UnimplementedFunctionalityError accepts:ex signal) ifTrue:[
+	    msg1 := 'Cannot access module "%1".\\'.
+	    msg2 := 'Missing functionality in the "%2"-source code manager.'.
+	] ifFalse:[
+	    msg1 := 'Cannot access module "%1".\\'.
+	    msg2 := ex errorString ? ('No module "%1" in the repository (%2).').
+	].
+
+	(Dialog confirm:
+		    (resources stringWithCRs:msg1 with:module)
+		    ,(resources string:msg2 with:module with:sourceCodeManager managerTypeName)
+		    ,(resources stringWithCRs:('\\Import from the filesystem ?')))
+	ifFalse:[
+	    ^ self.
+	].
+	importFromFilesystem := true.
+
+	checkedOutPackageDir isNil ifTrue:[
+	    default := Smalltalk projectDirectoryForPackage:module.
+	] ifFalse:[
+	    default := Smalltalk projectDirectoryForPackage:pkg.
+	].
+	(default notNil
+	    and:[ (default := default asFilename) exists
+	    and:[ default isDirectory ]])
+	ifFalse:[
+	    default := nil.
+	].
+
+	importDirectory := Dialog
+			    requestDirectoryName:(resources
+						    string:'Import "%1" from Directory:'
+						    with:pkg)
+			    default:default.
+	importDirectory isEmptyOrNil ifTrue:[
+	    ^ self
+	].
+	importDirectory := importDirectory asFilename pathName asFilename.
     ] do:[
-        sourceCodeManager isNil ifTrue:[ SourceCodeManagerError raise ].
-        (sourceCodeManager checkForExistingModule:module) ifFalse:[
-            self warn:(resources string:'No module "%1" in the repository.' with:module).
-            ^ self.
-        ].
-        checkedOutPackageDir notNil ifTrue:[
-            (sourceCodeManager checkForExistingModule:module directory:checkedOutPackageDir) ifFalse:[
-                self warn:(resources string:'No package "%1" in the repository (but the module "%2" exists).' with:checkedOutPackageDir with:module).
-                ^ self
-            ]
-        ].
+	sourceCodeManager isNil ifTrue:[ SourceCodeManagerError raise ].
+	(sourceCodeManager checkForExistingModule:module) ifFalse:[
+	    self warn:(resources string:'No module "%1" in the repository.' with:module).
+	    ^ self.
+	].
+	checkedOutPackageDir notNil ifTrue:[
+	    (sourceCodeManager checkForExistingModule:module directory:checkedOutPackageDir) ifFalse:[
+		self warn:(resources string:'No package "%1" in the repository (but the module "%2" exists).' with:checkedOutPackageDir with:module).
+		^ self
+	    ]
+	].
     ].
 
     "/ check out that module ...
     importFromDirectoryAction :=
-        [:tempDir |
-            |filesThere skip|
-
-            numImported := numSkipped := 0.
-            tempDir asFilename withAllDirectoriesDo:[:eachDir |
-                |relDir theProject anyFound anyUnsavedClass|
-
-                ( #( 'CVS' 'bitmaps' 'resources' ) includes:eachDir baseName)
-                ifFalse:[
-                    relDir := eachDir name.
-                    (relDir startsWith:tempDir name) ifTrue:[
-                        relDir := relDir copyFrom:tempDir name size + 2.
-                    ] ifFalse:[
-                        self halt:'mhmh - can this happen ?'.
-                    ].
-                    checkedOutPackageDir notNil ifTrue:[
-                        relDir size > 0 ifTrue:[
-                            relDir := checkedOutPackageDir asFilename constructString:relDir
-                        ] ifFalse:[
-                            relDir := checkedOutPackageDir
-                        ]
-                    ].
-                    relDir := relDir copy replaceAll:$\ with:$/.
-                    relDir size > 0 ifTrue:[
-                        theProject := module , ':' , relDir
-                    ] ifFalse:[
-                        theProject := module
-                    ].
-
-                    skip := false.
-
-                    (checkedOutPackageDir isNil and:[package notNil]) ifTrue:[
-                        skip := (package ~= (relDir , '/*') ) and:[ (package match:relDir) not ].
-                    ].
-                    anyFound := false.
-                    skip ifTrue:[
-                        numSkipped := numSkipped + 1.
-                    ] ifFalse:[
-                        Transcript showCR:('processing ' , relDir , '...').
-
-                        filesThere := eachDir directoryContents select:[:eachFile | eachFile asFilename hasSuffix:'st'].
-                        filesThere isEmpty ifTrue:[
-                            Transcript showCR:(eachDir pathName , ': no smalltalk files in package.').
-                        ] ifFalse:[
-                            anyFound := true.
-                            "/ cannot simply fileIn that stuff (because of load order)
-                            "/ instead, create a change set containing all class definitions,
-                            "/ and define them first ...
-                            filePerClassDefintion := Dictionary new.
-                            classDefs := ChangeSet new.
-                            filesThere do:[:eachSTFile |
-                                |s classDefinitions chgSet|
-
-                                s := (eachDir asFilename construct:eachSTFile) readStream.
-                                chgSet := ChangeSet fromStream:s.
-                                s close.
-                                classDefinitions := chgSet select:[:change | change isClassDefinitionChange and:[change isPrivateClassDefinitionChange not]].
-                                classDefinitions do:[:def | filePerClassDefintion at:def put:eachSTFile].
-                                classDefs addAll:classDefinitions.
-                            ].
-
-                            "/ now, install ...
-                            classDefs do:[:eachClassDefinition |
-                                |cls oldPackage|
-
-                                eachClassDefinition package:theProject.
-                                eachClassDefinition installAsAutoloadedClassIfPublicWithFilename:(filePerClassDefintion at:eachClassDefinition).
-                                (cls := eachClassDefinition changeClass) notNil ifTrue:[
-                                    (oldPackage := cls package) ~= theProject ifTrue:[
-                                        (Dialog confirm:('Move the %1-class from the %2-package ?' bindWith:cls name with:oldPackage)) ifTrue:[
-                                            cls package:theProject.
-                                            cls instAndClassMethodsDo:[:m | m package = oldPackage ifTrue:[ m package:theProject]].
-                                        ]
-                                    ].
-                                ].
-                            ].
-
-                            doLoadClasses ifTrue:[
-
-                                anyUnsavedClass := classDefs
-                                                    contains:[:someClassDefinition |
-                                                        |cls|
-
-                                                        ((cls := someClassDefinition changeClass) notNil
-                                                        and:[cls isLoaded
-                                                        and:[ChangeSet current includesChangeForClassOrMetaclass:cls]])
-                                                    ].
-                                anyUnsavedClass ifTrue:[
-                                    (Dialog
-                                        confirm:'There is at least one unsaved class (changed but not yet checked in) in the project.\\Load (i.e. overwrite) ?' withCRs)
-                                    ifFalse:[ AbortSignal raise ].
-                                ].
-
-                                filesThere do:[:eachSTFile |
-                                    Transcript showCR:('  loading ' , (eachDir asFilename constructString:eachSTFile) , '...').
-                                    self activityNotification:('loading ',eachSTFile,'...').
-                                    Class packageQuerySignal answer:theProject do:[
-                                        Smalltalk fileIn:(eachDir asFilename construct:eachSTFile).
-                                    ]
-                                ].
-                                numImported := numImported + 1.
-                            ].
-                        ].
-                    ].
-                    (anyFound and:[theProject notNil]) ifTrue:[
-                        self projectListApp addAdditionalProject:theProject.
-                    ]
-                ]
-            ]
-        ].
+	[:tempDir |
+	    |filesThere skip|
+
+	    numImported := numSkipped := 0.
+	    tempDir asFilename withAllDirectoriesDo:[:eachDir |
+		|relDir theProject anyFound anyUnsavedClass|
+
+		( #( 'CVS' 'bitmaps' 'resources' ) includes:eachDir baseName)
+		ifFalse:[
+		    relDir := eachDir name.
+		    (relDir startsWith:tempDir name) ifTrue:[
+			relDir := relDir copyFrom:tempDir name size + 2.
+		    ] ifFalse:[
+			self halt:'mhmh - can this happen ?'.
+		    ].
+		    checkedOutPackageDir notNil ifTrue:[
+			relDir size > 0 ifTrue:[
+			    relDir := checkedOutPackageDir asFilename constructString:relDir
+			] ifFalse:[
+			    relDir := checkedOutPackageDir
+			]
+		    ].
+		    relDir := relDir copy replaceAll:$\ with:$/.
+		    relDir size > 0 ifTrue:[
+			theProject := module , ':' , relDir
+		    ] ifFalse:[
+			theProject := module
+		    ].
+
+		    skip := false.
+
+		    (checkedOutPackageDir isNil and:[package notNil]) ifTrue:[
+			skip := (package ~= (relDir , '/*') ) and:[ (package match:relDir) not ].
+		    ].
+		    anyFound := false.
+		    skip ifTrue:[
+			numSkipped := numSkipped + 1.
+		    ] ifFalse:[
+			Transcript showCR:('processing ' , relDir , '...').
+
+			filesThere := eachDir directoryContents select:[:eachFile | eachFile asFilename hasSuffix:'st'].
+			filesThere isEmpty ifTrue:[
+			    Transcript showCR:(eachDir pathName , ': no smalltalk files in package.').
+			] ifFalse:[
+			    anyFound := true.
+			    "/ cannot simply fileIn that stuff (because of load order)
+			    "/ instead, create a change set containing all class definitions,
+			    "/ and define them first ...
+			    filePerClassDefintion := Dictionary new.
+			    classDefs := ChangeSet new.
+			    filesThere do:[:eachSTFile |
+				|s classDefinitions chgSet|
+
+				s := (eachDir asFilename construct:eachSTFile) readStream.
+				chgSet := ChangeSet fromStream:s.
+				s close.
+				classDefinitions := chgSet select:[:change | change isClassDefinitionChange and:[change isPrivateClassDefinitionChange not]].
+				classDefinitions do:[:def | filePerClassDefintion at:def put:eachSTFile].
+				classDefs addAll:classDefinitions.
+			    ].
+
+			    "/ now, install ...
+			    classDefs do:[:eachClassDefinition |
+				|cls oldPackage|
+
+				eachClassDefinition package:theProject.
+				eachClassDefinition installAsAutoloadedClassIfPublicWithFilename:(filePerClassDefintion at:eachClassDefinition).
+				(cls := eachClassDefinition changeClass) notNil ifTrue:[
+				    (oldPackage := cls package) ~= theProject ifTrue:[
+					(Dialog confirm:('Move the %1-class from the %2-package ?' bindWith:cls name with:oldPackage)) ifTrue:[
+					    cls package:theProject.
+					    cls instAndClassMethodsDo:[:m | m package = oldPackage ifTrue:[ m package:theProject]].
+					]
+				    ].
+				].
+			    ].
+
+			    doLoadClasses ifTrue:[
+
+				anyUnsavedClass := classDefs
+						    contains:[:someClassDefinition |
+							|cls|
+
+							((cls := someClassDefinition changeClass) notNil
+							and:[cls isLoaded
+							and:[ChangeSet current includesChangeForClassOrMetaclass:cls]])
+						    ].
+				anyUnsavedClass ifTrue:[
+				    (Dialog
+					confirm:'There is at least one unsaved class (changed but not yet checked in) in the project.\\Load (i.e. overwrite) ?' withCRs)
+				    ifFalse:[ AbortSignal raise ].
+				].
+
+				filesThere do:[:eachSTFile |
+				    Transcript showCR:('  loading ' , (eachDir asFilename constructString:eachSTFile) , '...').
+				    self activityNotification:('loading ',eachSTFile,'...').
+				    Class packageQuerySignal answer:theProject do:[
+					Smalltalk fileIn:(eachDir asFilename construct:eachSTFile).
+				    ]
+				].
+				numImported := numImported + 1.
+			    ].
+			].
+		    ].
+		    (anyFound and:[theProject notNil]) ifTrue:[
+			self projectListApp addAdditionalProject:theProject.
+		    ]
+		]
+	    ]
+	].
 
     importFromFilesystem ifTrue:[
-        importFromDirectoryAction value:importDirectory
-    ] ifFalse:[
-        "/ check out that module ...
-        SourceCodeManagerError handle:[:ex |
-            Dialog warn:ex description
-        ] do:[
-            sourceCodeManager
-                checkoutModule:module
-                directory:checkedOutPackageDir
-                andDo:importFromDirectoryAction.
-        ].
+	importFromDirectoryAction value:importDirectory
+    ] ifFalse:[
+	"/ check out that module ...
+	SourceCodeManagerError handle:[:ex |
+	    Dialog warn:ex description
+	] do:[
+	    sourceCodeManager
+		checkoutModule:module
+		directory:checkedOutPackageDir
+		andDo:importFromDirectoryAction.
+	].
     ].
 
     numImported == 0 ifTrue:[
-        numSkipped ~~ 0 ifTrue:[
-            (package endsWith:'*') ifTrue:[
-                self information:('Nothing imported. Notice:\You may want to try ''' ,
-                                 (package copyWithoutLast:2) , ''' (i.e. not the matching sub-packages).') withCRs
-            ] ifFalse:[
-                self information:'Nothing imported.'
-            ]
-        ].
+	numSkipped ~~ 0 ifTrue:[
+	    (package endsWith:'*') ifTrue:[
+		self information:('Nothing imported. Notice:\You may want to try ''' ,
+				 (package copyWithoutLast:2) , ''' (i.e. not the matching sub-packages).') withCRs
+	    ] ifFalse:[
+		self information:'Nothing imported.'
+	    ]
+	].
     ].
     LastImportedPackage := nil.
 
@@ -37829,25 +38281,25 @@
     |projects projectsString|
 
     LastLoadedPackages isNil ifTrue:[
-        LastLoadedPackages := OrderedCollection new.
+	LastLoadedPackages := OrderedCollection new.
     ].
 
     projects := self selectedProjects value.
     projects isEmptyOrNil ifTrue:[
-        projectsString := Dialog
-                            request:'Load which package(s):'
-                            initialAnswer:projectsString
-                            list:LastLoadedPackages.
-        projectsString size == 0 ifTrue:[^  self].
-        projects := projectsString asCollectionOfWords.
+	projectsString := Dialog
+			    request:'Load which package(s):'
+			    initialAnswer:projectsString
+			    list:LastLoadedPackages.
+	projectsString size == 0 ifTrue:[^  self].
+	projects := projectsString asCollectionOfWords.
     ].
 
     projects do:[:packageToLoad |
-        LastLoadedPackages add:packageToLoad.
-        LastLoadedPackages size > 20 ifTrue:[
-            LastLoadedPackages removeFirst.
-        ].
-        Smalltalk loadPackage:packageToLoad
+	LastLoadedPackages add:packageToLoad.
+	LastLoadedPackages size > 20 ifTrue:[
+	    LastLoadedPackages removeFirst.
+	].
+	Smalltalk loadPackage:packageToLoad
     ].
 
     "Modified: / 14-09-2006 / 17:38:00 / cg"
@@ -37857,8 +38309,8 @@
     "fileOut selected classes (chunk format) and eMail to someone"
 
     self
-        mailClasses:self selectedProjectClasses 
-        subject:'Project Source from Browser'
+	mailClasses:self selectedProjectClasses
+	subject:'Project Source from Browser'
 
     "Modified: / 20-09-2007 / 15:03:00 / cg"
 !
@@ -37870,10 +38322,10 @@
 
     theProject := Project projectWithId:id.
     theProject isNil ifTrue:[
-        "/ create it
-        theProject := Project new.
-        theProject name:id.
-        theProject package:id.
+	"/ create it
+	theProject := Project new.
+	theProject name:id.
+	theProject package:id.
     ].
 
     Project current:theProject.
@@ -37900,27 +38352,27 @@
     resultStream := WriteStream on:String new.
 
     self
-        projectMenuWithAllClassesLoadedDo:[:module :package :classesInProject |
-            |moduleAndPackage text metrics allClasses|
-
-            moduleAndPackage := module , ':' , package.
-            self busyLabel:'Computing metrics for ' , moduleAndPackage , '...'.
-            Transcript showCR:'Computing metrics for ' , moduleAndPackage , '...'.
-
-            allClasses := OrderedCollection new.
-            allClasses addAll:classesInProject.
-            classesInProject do:[:eachClass |
-                allClasses addAll:(eachClass allPrivateClasses).
-            ].
-
-            metrics := OOM::MetricsSummaryGenerator new.
-            metrics computeMetricsForClasses:allClasses.
-            text := metrics generateSummaryReport.
-
-            resultStream nextPutLine:'Package: ', moduleAndPackage.
-            resultStream cr.
-            resultStream nextPutLine:text.
-        ].
+	projectMenuWithAllClassesLoadedDo:[:module :package :classesInProject |
+	    |moduleAndPackage text metrics allClasses|
+
+	    moduleAndPackage := module , ':' , package.
+	    self busyLabel:'Computing metrics for ' , moduleAndPackage , '...'.
+	    Transcript showCR:'Computing metrics for ' , moduleAndPackage , '...'.
+
+	    allClasses := OrderedCollection new.
+	    allClasses addAll:classesInProject.
+	    classesInProject do:[:eachClass |
+		allClasses addAll:(eachClass allPrivateClasses).
+	    ].
+
+	    metrics := OOM::MetricsSummaryGenerator new.
+	    metrics computeMetricsForClasses:allClasses.
+	    text := metrics generateSummaryReport.
+
+	    resultStream nextPutLine:'Package: ', moduleAndPackage.
+	    resultStream cr.
+	    resultStream nextPutLine:text.
+	].
 
     codeView contents:(resultStream contents).
 
@@ -37929,96 +38381,96 @@
 !
 
 projectMenuNew
-    |projectDefinitionClass appClassName theCode appClass package  
+    |projectDefinitionClass appClassName theCode appClass package
      defaultStartupClassName startupClassName startupClass change|
 
     projectDefinitionClass := self projectDefinitionDialogFor:nil.
     projectDefinitionClass isNil ifTrue:[
-        ^ self
+	^ self
     ].
 
     package := projectDefinitionClass package.
     Class packageQuerySignal answer:package
     do:[
-        projectDefinitionClass compileDescriptionMethods.
-        self selectClass:projectDefinitionClass.
-
-        projectDefinitionClass isApplicationDefinition ifTrue:[
-            appClassName := Dialog 
-                                request:(resources 
-                                    stringWithCRs:'Create initial application class?\(Enter name or cancel)').
-            appClassName notNil ifTrue:[
-                theCode := '
+	projectDefinitionClass compileDescriptionMethods.
+	self selectClass:projectDefinitionClass.
+
+	projectDefinitionClass isApplicationDefinition ifTrue:[
+	    appClassName := Dialog
+				request:(resources
+				    stringWithCRs:'Create initial application class?\(Enter name or cancel)').
+	    appClassName notNil ifTrue:[
+		theCode := '
 ApplicationModel subclass: #''%1''
     instanceVariableNames:'' ''
     classVariableNames:'' ''
     poolDictionaries:'' ''
-    category:''%1'' 
+    category:''%1''
 '               bindWith:appClassName.
 
 
-                self canUseRefactoringSupport ifTrue:[
-                    change := AddClassChange definition: theCode.
-                    change name:('Create application class %1' bindWith:appClassName).
-                    RefactoryChangeManager performChange:change
-                ] ifFalse:[
-                    self 
-                        doAcceptClassDefinition:theCode 
-                        usingCompiler:Compiler.
-                ].
-
-                appClass := Smalltalk classNamed:appClassName.
-                appClass package:package.
-
-                self classMenuGenerateApplicationCodeForClasses:{ appClass }.
-                appClass instAndClassMethodsDo:[:m | m package:package].
-
-                defaultStartupClassName := appClassName,'Start'.
-                (Smalltalk classNamed:defaultStartupClassName) notNil ifTrue:[
-                    defaultStartupClassName := nil
-                ].
-                startupClassName := Dialog 
-                                request:(resources 
-                                    stringWithCRs:'Create startup class (e.g. main)?\(Enter name or cancel)')
-                                initialAnswer:defaultStartupClassName.
-                startupClassName notNil ifTrue:[
-                    theCode := '
+		self canUseRefactoringSupport ifTrue:[
+		    change := AddClassChange definition: theCode.
+		    change name:('Create application class %1' bindWith:appClassName).
+		    RefactoryChangeManager performChange:change
+		] ifFalse:[
+		    self
+			doAcceptClassDefinition:theCode
+			usingCompiler:Compiler.
+		].
+
+		appClass := Smalltalk classNamed:appClassName.
+		appClass package:package.
+
+		self classMenuGenerateApplicationCodeForClasses:{ appClass }.
+		appClass instAndClassMethodsDo:[:m | m package:package].
+
+		defaultStartupClassName := appClassName,'Start'.
+		(Smalltalk classNamed:defaultStartupClassName) notNil ifTrue:[
+		    defaultStartupClassName := nil
+		].
+		startupClassName := Dialog
+				request:(resources
+				    stringWithCRs:'Create startup class (e.g. main)?\(Enter name or cancel)')
+				initialAnswer:defaultStartupClassName.
+		startupClassName notNil ifTrue:[
+		    theCode := '
 StandaloneStartup subclass: #''%1''
     instanceVariableNames:'' ''
     classVariableNames:'' ''
     poolDictionaries:'' ''
-    category:''%1'' 
+    category:''%1''
 '               bindWith:startupClassName.
 
-                    self canUseRefactoringSupport ifTrue:[
-                        change := AddClassChange definition: theCode.
-                        change name:('Create startup class %1' bindWith:startupClassName).
-                        RefactoryChangeManager performChange:change
-                    ] ifFalse:[
-                        self 
-                            doAcceptClassDefinition:theCode 
-                            usingCompiler:Compiler.
-                    ].
-
-                    startupClass := Smalltalk classNamed:startupClassName.
-                    startupClass package:package.
-
-                    "/ update the classList, again
-                    projectDefinitionClass compileDescriptionMethods.
-                    "/ generate startupClass code
+		    self canUseRefactoringSupport ifTrue:[
+			change := AddClassChange definition: theCode.
+			change name:('Create startup class %1' bindWith:startupClassName).
+			RefactoryChangeManager performChange:change
+		    ] ifFalse:[
+			self
+			    doAcceptClassDefinition:theCode
+			    usingCompiler:Compiler.
+		    ].
+
+		    startupClass := Smalltalk classNamed:startupClassName.
+		    startupClass package:package.
+
+		    "/ update the classList, again
+		    projectDefinitionClass compileDescriptionMethods.
+		    "/ generate startupClass code
     self halt.
-                    SmalltalkCodeGeneratorTool
-                        compile:(projectDefinitionClass startupClassName_codeFor:(startupClass name))
-                        forClass:projectDefinitionClass theMetaclass
-                        inCategory:'description - startup'.
-
-                    self classMenuGenerateApplicationCodeForClasses:{ startupClass }.
-                    startupClass instAndClassMethodsDo:[:m | m package:package].
-                ].
-
-                self selectClass:appClass.
-            ]
-        ]
+		    SmalltalkCodeGeneratorTool
+			compile:(projectDefinitionClass startupClassName_codeFor:(startupClass name))
+			forClass:projectDefinitionClass theMetaclass
+			inCategory:'description - startup'.
+
+		    self classMenuGenerateApplicationCodeForClasses:{ startupClass }.
+		    startupClass instAndClassMethodsDo:[:m | m package:package].
+		].
+
+		self selectClass:appClass.
+	    ]
+	]
     ].
 
     "Modified: / 21-01-2012 / 13:38:43 / cg"
@@ -38031,29 +38483,38 @@
     project isNil ifTrue:[^ self ].
 
     project asPackageId directory isEmptyOrNil ifTrue:[
-        Dialog warn:(resources
-                            stringWithCRs:'"%1" is a topLevel module identifier.\\Real packages are required to consist of module:directory (i.e. %1:xxx).\Please create a package below this module first'
-                            with:(ProjectDefinition initialClassNameForDefinitionOf:project)).
+	Dialog warn:(resources
+			    stringWithCRs:'"%1" is a topLevel module identifier.\\Real packages are required to consist of module:directory (i.e. %1:xxx).\Please create a package below this module first'
+			    with:(ProjectDefinition initialClassNameForDefinitionOf:project)).
     ].
 
     defClass := ProjectDefinition definitionClassForPackage:project.
     defClass isNil ifTrue:[
-        Dialog warn:(resources
-                            string:'Missing ProjectDefinition class: %1'
-                            with:(ProjectDefinition initialClassNameForDefinitionOf:project)).
-        ^ self
+	Dialog warn:(resources
+			    string:'Missing ProjectDefinition class: %1'
+			    with:(ProjectDefinition initialClassNameForDefinitionOf:project)).
+	^ self
     ].
 
     Tools::ProjectDefinitionEditor new
-        definitionClass:defClass;
-        open
+	definitionClass:defClass;
+	open
 
     "Modified: / 20-01-2012 / 16:36:32 / cg"
 !
 
+projectMenuRecompile
+    self selectedProjectClasses do:[:eachClass |
+	self recompileClass:eachClass
+    ].
+
+    "Modified: / 30-09-2011 / 12:39:19 / cg"
+    "Created: / 31-05-2012 / 12:03:19 / cg"
+!
+
 projectMenuRecompileInstrumented
     self selectedProjectClasses do:[:eachClass |
-        self recompileClassWithInstrumentation:eachClass
+	self recompileClassWithInstrumentation:eachClass
     ].
 
     "Created: / 27-04-2010 / 12:39:43 / cg"
@@ -38071,14 +38532,14 @@
 
 projectMenuRemove
     (self selectedProjects value includes:(BrowserList nameListEntryForALL)) ifTrue:[
-        self warn:'I won''t do that !!'.
-        ^ self
+	self warn:'I won''t do that !!'.
+	^ self
     ].
 
     self withWaitCursorDo:[
-        self selectedProjectsDo:[:packageToRemove |
-            self projectMenuRemoveProject:packageToRemove
-        ]
+	self selectedProjectsDo:[:packageToRemove |
+	    self projectMenuRemoveProject:packageToRemove
+	]
     ]
 !
 
@@ -38093,60 +38554,60 @@
     "/ classes ...
     "/ ... and individual methods (extensions)
     Smalltalk allClassesDo:[:aClass |
-        (aClass package = projectToRemove) ifTrue:[
-            classesToRemove add:aClass.
-        ] ifFalse:[
-            aClass instAndClassSelectorsAndMethodsDo:[:sel :mthd |
-                (mthd package = projectToRemove) ifTrue:[
-                    methodsToRemove add:mthd
-                ]
-            ].
-        ]
+	(aClass package = projectToRemove) ifTrue:[
+	    classesToRemove add:aClass.
+	] ifFalse:[
+	    aClass instAndClassSelectorsAndMethodsDo:[:sel :mthd |
+		(mthd package = projectToRemove) ifTrue:[
+		    methodsToRemove add:mthd
+		]
+	    ].
+	]
     ].
 
     msg := 'Remove project ''%1'' with\'.
     classesToRemove size > 0 ifTrue:[
-        classesToRemove size == 1 ifTrue:[
-            msg := msg , '1 class'.
-        ] ifFalse:[
-            msg := msg , '%2 classes'.
-        ].
-        methodsToRemove size > 0 ifTrue:[
-            msg := msg , ' and '
-        ]
+	classesToRemove size == 1 ifTrue:[
+	    msg := msg , '1 class'.
+	] ifFalse:[
+	    msg := msg , '%2 classes'.
+	].
+	methodsToRemove size > 0 ifTrue:[
+	    msg := msg , ' and '
+	]
     ].
     methodsToRemove size > 0 ifTrue:[
-        methodsToRemove size == 1 ifTrue:[
-            msg := msg , '1 method extension in another class'.
-        ] ifFalse:[
-            msg := msg , '%3 method extensions in other classes'.
-        ]
+	methodsToRemove size == 1 ifTrue:[
+	    msg := msg , '1 method extension in another class'.
+	] ifFalse:[
+	    msg := msg , '%3 method extensions in other classes'.
+	]
     ].
     msg := msg , '.'.
 
     (classesToRemove contains:[:someClass | someClass wasAutoloaded]) ifTrue:[
-        msg := msg , '\\Notice: this is a real remove (no autoload stubs will remain)'.
+	msg := msg , '\\Notice: this is a real remove (no autoload stubs will remain)'.
     ].
 
     msg := msg
-            bindWith:projectToRemove string allBold
-            with:classesToRemove size
-            with:methodsToRemove size.
+	    bindWith:projectToRemove string allBold
+	    with:classesToRemove size
+	    with:methodsToRemove size.
     msg := msg withCRs.
 
     (classesToRemove size > 0
     or:[methodsToRemove size > 0]) ifTrue:[
-        (Dialog confirm:msg) ifFalse:[^ self].
+	(Dialog confirm:msg) ifFalse:[^ self].
     ].
 
     self withWaitCursorDo:[
-        methodsToRemove do:[:eachMethod |
-            eachMethod mclass removeSelector:eachMethod selector.
-        ].
-        classesToRemove do:[:eachClass |
-            eachClass removeFromSystem.
-        ].
-        self projectListApp removeAdditionalProjects:(Array with:projectToRemove).
+	methodsToRemove do:[:eachMethod |
+	    eachMethod mclass removeSelector:eachMethod selector.
+	].
+	classesToRemove do:[:eachClass |
+	    eachClass removeFromSystem.
+	].
+	self projectListApp removeAdditionalProjects:(Array with:projectToRemove).
     ].
     self normalLabel.
 !
@@ -38198,12 +38659,12 @@
     tag isEmptyOrNil ifTrue:[^ self ].
 
     self withWaitCursorDo: [
-        self selectedProjectsDo:[:packageToTag |
-            |classes|
-
-            classes := Smalltalk allClassesInPackage:packageToTag.
-            SourceCodeManagerUtilities tagClasses:classes as:tag.
-        ]
+	self selectedProjectsDo:[:packageToTag |
+	    |classes|
+
+	    classes := Smalltalk allClassesInPackage:packageToTag.
+	    SourceCodeManagerUtilities tagClasses:classes as:tag.
+	]
     ]
 
     "Created: / 12-09-2006 / 13:25:09 / cg"
@@ -38216,88 +38677,88 @@
     |package defClass newFile oldFile editor differ theFile missingName|
 
     self hasProjectDefinitionSelected ifTrue:[
-        self hasSingleClassSelected ifTrue:[
-            defClass := self theSingleSelectedClass
-        ].
-        defClass isNil ifTrue:[
-            self warn:(resources string:'Please select a single project definition class').
-            ^ self.
-        ].
-        defClass := defClass theNonMetaclass.
-        package := defClass package.
-    ] ifFalse:[
-        self hasSingleProjectSelected ifTrue:[
-            package := self theSingleSelectedProject.
-            defClass := ProjectDefinition definitionClassForPackage:package.
-            defClass isNil ifTrue:[
-                self warn:(resources string:'Missing project definition class (%1)\for package: %2.'
-                        with:(ProjectDefinition initialClassNameForDefinitionOf:package)
-                        with:package allBold).
-                ^ self.
-            ].
-        ]
+	self hasSingleClassSelected ifTrue:[
+	    defClass := self theSingleSelectedClass
+	].
+	defClass isNil ifTrue:[
+	    self warn:(resources string:'Please select a single project definition class').
+	    ^ self.
+	].
+	defClass := defClass theNonMetaclass.
+	package := defClass package.
+    ] ifFalse:[
+	self hasSingleProjectSelected ifTrue:[
+	    package := self theSingleSelectedProject.
+	    defClass := ProjectDefinition definitionClassForPackage:package.
+	    defClass isNil ifTrue:[
+		self warn:(resources string:'Missing project definition class (%1)\for package: %2.'
+			with:(ProjectDefinition initialClassNameForDefinitionOf:package)
+			with:package allBold).
+		^ self.
+	    ].
+	]
     ].
 
     theFile := whichFile.
     theFile = 'lib.rc' ifTrue:[
-        theFile := defClass rcFilename.
+	theFile := defClass rcFilename.
     ].
     theFile = 'app.nsi' ifTrue:[
-        theFile := defClass nsiFilename.
+	theFile := defClass nsiFilename.
     ].
 
     (missingName := defClass allClassNames "compiled_classNames"
-        detect:[:aName |
-            |cls|
-
-            cls := Smalltalk at:aName asSymbol.
-            cls isNil
-        ]
-        ifNone:nil)
+	detect:[:aName |
+	    |cls|
+
+	    cls := Smalltalk at:aName asSymbol.
+	    cls isNil
+	]
+	ifNone:nil)
     notNil ifTrue:[
-        (Dialog confirm:(resources stringWithCRs:'Some class (%1) from the list of compiled classes is missing in the image!!\\Continue anyway ?'
-                                    with:missingName))
-        ifFalse:[^ self ].
+	(Dialog confirm:(resources stringWithCRs:'Some class (%1) from the list of compiled classes is missing in the image!!\\Continue anyway ?'
+				    with:missingName))
+	ifFalse:[^ self ].
     ].
 
     whichFile = 'abbrev.stc' ifTrue:[
-        (defClass compiled_classNames
-            contains:[:aName |
-                |cls|
-
-                cls := Smalltalk at:aName asSymbol.
-                cls notNil and:[cls isLoaded not]
-            ])
-        ifTrue:[
-            (Dialog confirm:'Autoload missing class(es) ?\\Notice: generated abbrev.stc file is wrong if autoloaded classes are unloaded' withCRs) ifTrue:[
-                defClass compiled_classNames do:[:aName |
-                    (Smalltalk at:aName asSymbol) autoload
-                ].
-            ].
-        ].
+	(defClass compiled_classNames
+	    contains:[:aName |
+		|cls|
+
+		cls := Smalltalk at:aName asSymbol.
+		cls notNil and:[cls isLoaded not]
+	    ])
+	ifTrue:[
+	    (Dialog confirm:'Autoload missing class(es) ?\\Notice: generated abbrev.stc file is wrong if autoloaded classes are unloaded' withCRs) ifTrue:[
+		defClass compiled_classNames do:[:aName |
+		    (Smalltalk at:aName asSymbol) autoload
+		].
+	    ].
+	].
     ].
 
     [
-        newFile := defClass generateFile:theFile.
+	newFile := defClass generateFile:theFile.
     ] on:Error do:[:ex|
-        self errorNotify:ex description.
-        ^ self.
+	self errorNotify:ex description.
+	^ self.
     ].
 
     SourceCodeManager notNil ifTrue:[
-        oldFile := SourceCodeManager
-                        getFile:theFile
-                        revision:#newest
-                        directory:(package asPackageId directory)
-                        module:(package asPackageId module).
+	oldFile := SourceCodeManager
+			getFile:theFile
+			revision:#newest
+			directory:(package asPackageId directory)
+			module:(package asPackageId module).
     ].
     oldFile isNil ifTrue:[
-        editor := EditTextView openOnModel:newFile.
-        editor topView label:(resources string:'Generated %1' with:theFile).
-    ] ifFalse:[
-        differ := DiffCodeView
-                openOn:oldFile label:(resources string:'Newest %1 in Repository' with:theFile)
-                and:newFile label:(resources string:'Generated %1' with:theFile).
+	editor := EditTextView openOnModel:newFile.
+	editor topView label:(resources string:'Generated %1' with:theFile).
+    ] ifFalse:[
+	differ := DiffCodeView
+		openOn:oldFile label:(resources string:'Newest %1 in Repository' with:theFile)
+		and:newFile label:(resources string:'Generated %1' with:theFile).
     ].
 
     "Created: / 29-08-2006 / 15:35:44 / cg"
@@ -38310,88 +38771,88 @@
     |package defClass newFile oldFile editor differ theFile missingName|
 
     self hasProjectDefinitionSelected ifTrue:[
-        self hasSingleClassSelected ifTrue:[
-            defClass := self theSingleSelectedClass
-        ].
-        defClass isNil ifTrue:[
-            self warn:(resources string:'Please select a single project definition class').
-            ^ self.
-        ].
-        defClass := defClass theNonMetaclass.
-        package := defClass package.
-    ] ifFalse:[
-        self hasSingleProjectSelected ifTrue:[
-            package := self theSingleSelectedProject.
-            defClass := ProjectDefinition definitionClassForPackage:package.
-            defClass isNil ifTrue:[
-                self warn:(resources string:'Missing project definition class (%1)\for package: %2.'
-                        with:(ProjectDefinition initialClassNameForDefinitionOf:package)
-                        with:package allBold).
-                ^ self.
-            ].
-        ]
+	self hasSingleClassSelected ifTrue:[
+	    defClass := self theSingleSelectedClass
+	].
+	defClass isNil ifTrue:[
+	    self warn:(resources string:'Please select a single project definition class').
+	    ^ self.
+	].
+	defClass := defClass theNonMetaclass.
+	package := defClass package.
+    ] ifFalse:[
+	self hasSingleProjectSelected ifTrue:[
+	    package := self theSingleSelectedProject.
+	    defClass := ProjectDefinition definitionClassForPackage:package.
+	    defClass isNil ifTrue:[
+		self warn:(resources string:'Missing project definition class (%1)\for package: %2.'
+			with:(ProjectDefinition initialClassNameForDefinitionOf:package)
+			with:package allBold).
+		^ self.
+	    ].
+	]
     ].
 
     theFile := whichFile.
     theFile = 'lib.rc' ifTrue:[
-        theFile := defClass rcFilename.
+	theFile := defClass rcFilename.
     ].
     theFile = 'app.nsi' ifTrue:[
-        theFile := defClass nsiFilename.
+	theFile := defClass nsiFilename.
     ].
 
     (missingName := defClass allClassNames "compiled_classNames"
-        detect:[:aName |
-            |cls|
-
-            cls := Smalltalk at:aName asSymbol.
-            cls isNil
-        ]
-        ifNone:nil)
+	detect:[:aName |
+	    |cls|
+
+	    cls := Smalltalk at:aName asSymbol.
+	    cls isNil
+	]
+	ifNone:nil)
     notNil ifTrue:[
-        (Dialog confirm:(resources stringWithCRs:'Some class (%1) from the list of compiled classes is missing in the image!!\\Continue anyway ?'
-                                    with:missingName))
-        ifFalse:[^ self ].
+	(Dialog confirm:(resources stringWithCRs:'Some class (%1) from the list of compiled classes is missing in the image!!\\Continue anyway ?'
+				    with:missingName))
+	ifFalse:[^ self ].
     ].
 
     whichFile = 'abbrev.stc' ifTrue:[
-        (defClass compiled_classNames
-            contains:[:aName |
-                |cls|
-
-                cls := Smalltalk at:aName asSymbol.
-                cls notNil and:[cls isLoaded not]
-            ])
-        ifTrue:[
-            (Dialog confirm:'Autoload missing class(es) ?\\Notice: generated abbrev.stc file is wrong if autoloaded classes are unloaded' withCRs) ifTrue:[
-                defClass compiled_classNames do:[:aName |
-                    (Smalltalk at:aName asSymbol) autoload
-                ].
-            ].
-        ].
+	(defClass compiled_classNames
+	    contains:[:aName |
+		|cls|
+
+		cls := Smalltalk at:aName asSymbol.
+		cls notNil and:[cls isLoaded not]
+	    ])
+	ifTrue:[
+	    (Dialog confirm:'Autoload missing class(es) ?\\Notice: generated abbrev.stc file is wrong if autoloaded classes are unloaded' withCRs) ifTrue:[
+		defClass compiled_classNames do:[:aName |
+		    (Smalltalk at:aName asSymbol) autoload
+		].
+	    ].
+	].
     ].
 
     [
-        newFile := defClass generateFile:theFile.
+	newFile := defClass generateFile:theFile.
     ] on:Error do:[:ex|
-        self errorNotify:ex description.
-        ^ self.
+	self errorNotify:ex description.
+	^ self.
     ].
 
     manager notNil ifTrue:[
-        oldFile := manager
-                        getFile:theFile
-                        revision:#newest
-                        directory:(package asPackageId directory)
-                        module:(package asPackageId module).
+	oldFile := manager
+			getFile:theFile
+			revision:#newest
+			directory:(package asPackageId directory)
+			module:(package asPackageId module).
     ].
     oldFile isNil ifTrue:[
-        editor := EditTextView openOnModel:newFile.
-        editor topView label:(resources string:'Generated %1' with:theFile).
-    ] ifFalse:[
-        differ := DiffCodeView
-                openOn:oldFile label:(resources string:'Newest %1 in Repository' with:theFile)
-                and:newFile label:(resources string:'Generated %1' with:theFile).
+	editor := EditTextView openOnModel:newFile.
+	editor topView label:(resources string:'Generated %1' with:theFile).
+    ] ifFalse:[
+	differ := DiffCodeView
+		openOn:oldFile label:(resources string:'Newest %1 in Repository' with:theFile)
+		and:newFile label:(resources string:'Generated %1' with:theFile).
     ].
 
     "Modified: / 12-09-2011 / 16:03:28 / cg"
@@ -38399,6 +38860,16 @@
     "Created: / 21-12-2011 / 20:24:42 / cg"
 !
 
+projectMenuSmalllintCheck: what
+    "perform all checks on the selected project's class(es)."
+
+    self
+	smalllintCheck:self selectedPackagesAsEnvironment
+	against: what
+
+    "Created: / 05-05-2012 / 10:19:44 / cg"
+!
+
 projectMenuSpawn
     "open a browser showing the selected projects only"
 
@@ -38464,96 +38935,96 @@
     SourceCodeManager isNil ifTrue:[^ self warn:'No SourceCodeManagement is configured.'].
 
     self withWaitCursorDo:[
-        |classesToLoad classesToUnload answer outStream classesSorted|
-
-        self selectedProjectsDo:[:packageToCheck |
-            |module package containers classesInProject classesWithoutContainer|
-
-            module := packageToCheck asPackageId module.
-            package := packageToCheck asPackageId directory.
+	|classesToLoad classesToUnload answer outStream classesSorted|
+
+	self selectedProjectsDo:[:packageToCheck |
+	    |module package containers classesInProject classesWithoutContainer|
+
+	    module := packageToCheck asPackageId module.
+	    package := packageToCheck asPackageId directory.
 
 "/            containers := SourceCodeManager getExistingContainersInModule:module package:package.
 "/            containers := containers select:[:each | (each startsWith:'.') not].
 
-            classesInProject := IdentitySet new.
-            Smalltalk allClassesDo:[:aClass |
-                (packageToCheck = aClass package) ifTrue:[
-                    aClass isPrivate ifFalse:[
-                        aClass isObsolete ifTrue:[
-                            Transcript showCR:'skipping obsolete class: ' , aClass name.
-                        ] ifFalse:[
-                            classesInProject add:aClass .
-                        ]
-                    ]
-                ]
-            ].
-
-            "/ load unloaded classes...
-            classesToLoad := OrderedCollection new.
-            classesInProject do:[:eachClassInProject |
-                eachClassInProject isLoaded ifFalse:[
-                    classesToLoad add:eachClassInProject
-                ].
-            ].
-            classesToLoad size > 0 ifTrue:[
-                answer := Dialog confirmWithCancel:(resources string:'%1 class(es) are not loaded.\In order to proceed, these must be loaded first.\\Load them now ?'
-                                                              with:classesToLoad size) withCRs
-                                 default:false.
-                answer isNil ifTrue:[^ self].
-
-                answer ifTrue:[
-                    self busyLabel:'Autoloading all classes in ' , packageToCheck , '...'.
-
-                    classesToUnload := OrderedCollection new.
-                    classesInProject do:[:eachClassInProject |
-                        eachClassInProject isLoaded ifFalse:[
-                            eachClassInProject autoload.
-                            classesToUnload add:eachClassInProject
-                        ].
-                    ].
-                ].
-            ].
-
-            self busyLabel:'Checking for classes without container in ' , packageToCheck , '...'.
-
-            "/ any class without container ?
-            classesWithoutContainer := IdentitySet new.
-
-            classesInProject do:[:eachClassInProject |
-                |mgr info classesModule classesPackageDir classesContainerFileName|
-
-                eachClassInProject isPrivate ifFalse:[
-                    mgr := SourceCodeManagerUtilities default sourceCodeManagerFor:eachClassInProject.
-                    info := mgr sourceInfoOfClass:eachClassInProject.
-                    info isNil ifTrue:[
-                        "/ no container for that class
-                        classesWithoutContainer add:eachClassInProject
-                    ].
-                ].
-            ].
-
-            "/ any container left ?
-            classesWithoutContainer notEmpty ifTrue:[
-                answer := Dialog warn:(resources string:'%1 class(es) have no container in the repository.\\Please do not forget to check them in.'
-                                                              with:classesToLoad size) withCRs.
-            ].
-
-            aBlock value:module value:package value:classesInProject.
-
-            classesToUnload size >0 ifTrue:[
-                answer := Dialog confirm:(resources string:'%1 class(es) were loaded - unload them now ?'
-                                          with:classesToLoad size)
-                                 default:false.
-                answer ifTrue:[
-                    self busyLabel:'Unloading autoloaded classes in ' , packageToCheck , '...'.
-
-                    "/ unload classes which have been loaded temporarily
-                    classesToUnload do:[:eachClassToUnload |
-                        eachClassToUnload unload
-                    ].
-                ]
-            ]
-        ].
+	    classesInProject := IdentitySet new.
+	    Smalltalk allClassesDo:[:aClass |
+		(packageToCheck = aClass package) ifTrue:[
+		    aClass isPrivate ifFalse:[
+			aClass isObsolete ifTrue:[
+			    Transcript showCR:'skipping obsolete class: ' , aClass name.
+			] ifFalse:[
+			    classesInProject add:aClass .
+			]
+		    ]
+		]
+	    ].
+
+	    "/ load unloaded classes...
+	    classesToLoad := OrderedCollection new.
+	    classesInProject do:[:eachClassInProject |
+		eachClassInProject isLoaded ifFalse:[
+		    classesToLoad add:eachClassInProject
+		].
+	    ].
+	    classesToLoad size > 0 ifTrue:[
+		answer := Dialog confirmWithCancel:(resources string:'%1 class(es) are not loaded.\In order to proceed, these must be loaded first.\\Load them now ?'
+							      with:classesToLoad size) withCRs
+				 default:false.
+		answer isNil ifTrue:[^ self].
+
+		answer ifTrue:[
+		    self busyLabel:'Autoloading all classes in ' , packageToCheck , '...'.
+
+		    classesToUnload := OrderedCollection new.
+		    classesInProject do:[:eachClassInProject |
+			eachClassInProject isLoaded ifFalse:[
+			    eachClassInProject autoload.
+			    classesToUnload add:eachClassInProject
+			].
+		    ].
+		].
+	    ].
+
+	    self busyLabel:'Checking for classes without container in ' , packageToCheck , '...'.
+
+	    "/ any class without container ?
+	    classesWithoutContainer := IdentitySet new.
+
+	    classesInProject do:[:eachClassInProject |
+		|mgr info classesModule classesPackageDir classesContainerFileName|
+
+		eachClassInProject isPrivate ifFalse:[
+		    mgr := SourceCodeManagerUtilities default sourceCodeManagerFor:eachClassInProject.
+		    info := mgr sourceInfoOfClass:eachClassInProject.
+		    info isNil ifTrue:[
+			"/ no container for that class
+			classesWithoutContainer add:eachClassInProject
+		    ].
+		].
+	    ].
+
+	    "/ any container left ?
+	    classesWithoutContainer notEmpty ifTrue:[
+		answer := Dialog warn:(resources string:'%1 class(es) have no container in the repository.\\Please do not forget to check them in.'
+							      with:classesToLoad size) withCRs.
+	    ].
+
+	    aBlock value:module value:package value:classesInProject.
+
+	    classesToUnload size >0 ifTrue:[
+		answer := Dialog confirm:(resources string:'%1 class(es) were loaded - unload them now ?'
+					  with:classesToLoad size)
+				 default:false.
+		answer ifTrue:[
+		    self busyLabel:'Unloading autoloaded classes in ' , packageToCheck , '...'.
+
+		    "/ unload classes which have been loaded temporarily
+		    classesToUnload do:[:eachClassToUnload |
+			eachClassToUnload unload
+		    ].
+		]
+	    ]
+	].
     ].
     self normalLabel
 
@@ -38565,8 +39036,8 @@
 
     selectedProjects := self selectedProjects value.
     (selectedProjects includes:(BrowserList nameListEntryForALL)) ifTrue:[
-        allProjects := (Smalltalk allClasses collect:[:eachClass | eachClass package]) asSet.
-        selectedProjects := allProjects.
+	allProjects := (Smalltalk allClasses collect:[:eachClass | eachClass package]) asSet.
+	selectedProjects := allProjects.
     ].
     selectedProjects := selectedProjects asOrderedCollection.
     selectedProjects sort do:aBlock
@@ -38574,61 +39045,61 @@
 
 spawnProjectBrowserFor:projects in:where
     "browse selected project(s);
-        where is: #newBrowser - open a new browser showing the projects
-        where is: #newBuffer  - add a new buffer showing the projects"
+	where is: #newBrowser - open a new browser showing the projects
+	where is: #newBuffer  - add a new buffer showing the projects"
 
     |spec projectList singleSelection|
 
     (singleSelection := projects size == 1) ifTrue:[
-        "/ spec := #singleProjectBrowserSpec.
-        spec := #singleProjectFullBrowserSpec.
-    ] ifFalse:[
-        "/ spec := #multipleProjectBrowserSpec.
-        spec := #multipleProjectFullBrowserSpec.
+	"/ spec := #singleProjectBrowserSpec.
+	spec := #singleProjectFullBrowserSpec.
+    ] ifFalse:[
+	"/ spec := #multipleProjectBrowserSpec.
+	spec := #multipleProjectFullBrowserSpec.
     ].
 
     projectList := projects copy.
 
     self
-        newBrowserOrBufferDependingOn:where
-        label:nil
-        forSpec:spec
-        setupWith:[:brwsr |
-            "/ setup for a constant list ...
-
-            brwsr immediateUpdate value:true.
-            brwsr projectListApp slaveMode:false.
-            brwsr organizerMode value:#project.
-            brwsr projectListGenerator value:projectList.
-            brwsr packageFilter value:projectList.
-            brwsr selectProjects:(singleSelection ifTrue:[projectList] ifFalse:[#()]).
-            brwsr immediateUpdate value:false.
-        ]
+	newBrowserOrBufferDependingOn:where
+	label:nil
+	forSpec:spec
+	setupWith:[:brwsr |
+	    "/ setup for a constant list ...
+
+	    brwsr immediateUpdate value:true.
+	    brwsr projectListApp slaveMode:false.
+	    brwsr organizerMode value:#project.
+	    brwsr projectListGenerator value:projectList.
+	    brwsr packageFilter value:projectList.
+	    brwsr selectProjects:(singleSelection ifTrue:[projectList] ifFalse:[#()]).
+	    brwsr immediateUpdate value:false.
+	]
 
     "Modified: / 23-01-2007 / 19:42:18 / cg"
 !
 
 spawnProjectExtensionBrowserFor:projects in:where
     "browse selected project(s) extensions;
-        where is: #newBrowser - open a new browser showing the projects
-        where is: #newBuffer  - add a new buffer showing the projects"
+	where is: #newBrowser - open a new browser showing the projects
+	where is: #newBuffer  - add a new buffer showing the projects"
 
     |classes title|
 
     classes := Smalltalk allClasses
-                select:[:each | (projects includes:each package) not].
+		select:[:each | (projects includes:each package) not].
 
     projects size == 1 ifTrue:[
-        title := 'Extensions for Project ''' , projects first , ''''
-    ] ifFalse:[
-        title := 'Extensions for Projects'
-    ].
-
-    ^ self
-        browseMenuClassExtensionsFor:projects
-        in:classes
-        label:title
-        openAs:where
+	title := 'Extensions for Project ''' , projects first , ''''
+    ] ifFalse:[
+	title := 'Extensions for Projects'
+    ].
+
+    ^ self
+	browseMenuClassExtensionsFor:projects
+	in:classes
+	label:title
+	openAs:where
 !
 
 spawnProjectPreRequirerBrowserFor:someProjects in:how
@@ -38638,13 +39109,13 @@
 
     requirer := Set new.
     ProjectDefinition allSubclassesDo:[:eachProjectDefinition |
-        (eachProjectDefinition preRequisites includesAny:someProjects) ifTrue:[
-            requirer add:(eachProjectDefinition package).
-        ]
+	(eachProjectDefinition preRequisites includesAny:someProjects) ifTrue:[
+	    requirer add:(eachProjectDefinition package).
+	]
     ].
     requirer isEmpty ifTrue:[
-        Dialog warn:'Noone seems to require this package (not found in any prerequisites).'.
-        ^ self.
+	Dialog warn:'Noone seems to require this package (not found in any prerequisites).'.
+	^ self.
     ].
     self spawnProjectBrowserFor:(requirer asOrderedCollection sort) in:how
 
@@ -38653,23 +39124,23 @@
 
 updateProjectContentsDefinitionsIn:classes regenerate:doRegenerate
     self
-        generateUndoableChange:(doRegenerate ifTrue:'Generate Project Definitions' ifFalse:'Update Project Definitions')
-        overClasses:classes
-        via:[:generator :eachClass |
-            Class packageQuerySignal
-                answer:eachClass package
-                do:[
-                    eachClass theNonMetaclass
-                        forEachContentsMethodsCodeToCompileDo:
-                            [:code :category |
-                                generator
-                                    compile:code
-                                    forClass:eachClass theMetaclass
-                                    inCategory:category.
-                            ]
-                        ignoreOldDefinition:doRegenerate
-                ].
-        ].
+	generateUndoableChange:(doRegenerate ifTrue:'Generate Project Definitions' ifFalse:'Update Project Definitions')
+	overClasses:classes
+	via:[:generator :eachClass |
+	    Class packageQuerySignal
+		answer:eachClass package
+		do:[
+		    eachClass theNonMetaclass
+			forEachContentsMethodsCodeToCompileDo:
+			    [:code :category |
+				generator
+				    compile:code
+				    forClass:eachClass theMetaclass
+				    inCategory:category.
+			    ]
+			ignoreOldDefinition:doRegenerate
+		].
+	].
 
     "Created: / 10-10-2006 / 21:05:14 / cg"
     "Modified: / 23-10-2006 / 11:01:42 / cg"
@@ -38690,10 +39161,10 @@
      Will eventually update the Project-object"
 
     self withWaitCursorDo:[
-        self selectedProtocolMethodsDo:[:cls :protocol :sel :eachMethod |
-            eachMethod package:newProject.
-        ].
-        self rememberLastProjectMoveTo:newProject
+	self selectedProtocolMethodsDo:[:cls :protocol :sel :eachMethod |
+	    eachMethod package:newProject.
+	].
+	self rememberLastProjectMoveTo:newProject
     ].
 
     "Modified: / 08-09-2011 / 04:17:32 / cg"
@@ -38709,12 +39180,12 @@
     printStream := Printer new.
 
     (self selectedClassesValue) do:[:eachClass |
-        (self selectedProtocols value sort) do:[:eachProtocol |
-            (eachClass methodDictionary contains:[:m | m category = eachProtocol])
-            ifTrue:[
-                eachClass perform:aSelector with:eachProtocol with:printStream.
-            ].
-        ].
+	(self selectedProtocols value sort) do:[:eachProtocol |
+	    (eachClass methodDictionary contains:[:m | m category = eachProtocol])
+	    ifTrue:[
+		eachClass perform:aSelector with:eachProtocol with:printStream.
+	    ].
+	].
     ].
 
     printStream close
@@ -38724,10 +39195,10 @@
 
 protocolCheckMenuSmalllintCheck: what
     "perform all checks on the selected class(es)."
-    
-    self 
-        smalllintCheck:self selectedProtocolsAsEnvironment
-        against: what
+
+    self
+	smalllintCheck:self selectedProtocolsAsEnvironment
+	against: what
 
     "Modified: / 28-12-2008 / 14:42:01 / bazantj <enter your email here>"
     "Modified: / 13-01-2009 / 13:20:48 / Jiri Bazant <bazanj2@fel.cvut.cz>"
@@ -38752,10 +39223,10 @@
     methods := methods select:[:eachMethod| protocols includes:eachMethod category].
 
     self
-        fileOutMethods:methods
-        format:nil
-        fileNameTemplate:self currentClass name , '-' , protocols first
-        boxTitle:'FileOut protocol as:'
+	fileOutMethods:methods
+	format:nil
+	fileNameTemplate:self currentClass name , '-' , protocols first
+	boxTitle:'FileOut protocol as:'
 !
 
 protocolMenuGenerateCommonProtocols
@@ -38764,18 +39235,18 @@
     |protocols|
 
     self hasMetaSelected ifTrue:[
-        protocols := #('instance creation' 'documentation' 'defaults')
-    ] ifFalse:[
-        protocols := #('accessing' 'adding & removing' 'testing' 'initialization' 'queries' 'private'
-                       'printing & storing' 'change & update')
+	protocols := #('instance creation' 'documentation' 'defaults')
+    ] ifFalse:[
+	protocols := #('accessing' 'adding & removing' 'testing' 'initialization' 'queries' 'private'
+		       'printing & storing' 'change & update')
     ].
 
     protocols do:[:newProtocol |
 "/        self immediateUpdate value:true.
-        self selectedClassesDo:[:cls |
-            self methodCategoryListApp addAdditionalProtocol:newProtocol forClass:cls.
-        ].
-        self clearAutoSelectOfLastSelectedProtocol.
+	self selectedClassesDo:[:cls |
+	    self methodCategoryListApp addAdditionalProtocol:newProtocol forClass:cls.
+	].
+	self clearAutoSelectOfLastSelectedProtocol.
 "/        self immediateUpdate value:false.
     ].
 !
@@ -38789,27 +39260,27 @@
     "/ provide a reasonable default in the pull-down-list
     currentClass := self anySelectedClass.
     currentClass isNil ifTrue:[
-        m := self anySelectedMethod.
-        currentClass := m mclass.
+	m := self anySelectedMethod.
+	currentClass := m mclass.
     ].
 
     LastMethodMoveOrCopyTargetClass notNil ifTrue:[
-        initial := LastMethodMoveOrCopyTargetClass.
+	initial := LastMethodMoveOrCopyTargetClass.
     ].
 
     initial isNil ifTrue:[
-        (sup := currentClass superclass) notNil ifTrue:[
-            initial := sup name
-        ] ifFalse:[
-            initial := nil.
-        ].
+	(sup := currentClass superclass) notNil ifTrue:[
+	    initial := sup name
+	] ifFalse:[
+	    initial := nil.
+	].
     ].
 
     supers := (currentClass allSuperclasses reverse collect:[:cls | cls name]).
     subs := (currentClass allSubclasses collect:[:cls | cls name]).
     list := supers.
     (supers notEmpty and:[subs notEmpty]) ifTrue:[
-        list := list , (Array with:'---- ' , currentClass name , ' ----')
+	list := list , (Array with:'---- ' , currentClass name , ' ----')
     ].
     list := list , subs.
 
@@ -38828,97 +39299,97 @@
 "/    newClassName := (holders at:#className) value.
 
     doWhat == #copy ifTrue:[
-        reqString := 'Copy selected protocols method(s) to which class:'.
-        okLabel := 'Copy'.
-        title := 'Copy protocol'.
-    ] ifFalse:[
-        reqString := 'Move selected protocols method(s) to which class:'.
-        okLabel := 'Move'.
-        title := 'Move protocol'.
+	reqString := 'Copy selected protocols method(s) to which class:'.
+	okLabel := 'Copy'.
+	title := 'Copy protocol'.
+    ] ifFalse:[
+	reqString := 'Move selected protocols method(s) to which class:'.
+	okLabel := 'Move'.
+	title := 'Move protocol'.
     ].
 
     newClassName := Dialog
-                    request:(resources string:reqString)
-                    initialAnswer:initial
-                    okLabel:(resources string:okLabel)
-                    title:(resources string:title)
-                    onCancel:nil
-                    list:list
-                    entryCompletionBlock:(DoWhatIMeanSupport classNameEntryCompletionBlock).
+		    request:(resources string:reqString)
+		    initialAnswer:initial
+		    okLabel:(resources string:okLabel)
+		    title:(resources string:title)
+		    onCancel:nil
+		    list:list
+		    entryCompletionBlock:(DoWhatIMeanSupport classNameEntryCompletionBlock).
     newClassName isNil ifTrue:[^ self].
     (newClassName startsWith:'---- ') ifTrue:[^ self].
 
     newClass := Smalltalk classNamed:newClassName.
     newClass isNil ifTrue:[
-        self warn:'no such class: ', newClassName.
-        ^ self
+	self warn:'no such class: ', newClassName.
+	^ self
     ].
 
     LastMethodMoveOrCopyTargetClass := newClassName.
 
     self meta value ifTrue:[
-        newClass := newClass theMetaclass
-    ] ifFalse:[
-        newClass := newClass theNonMetaclass
+	newClass := newClass theMetaclass
+    ] ifFalse:[
+	newClass := newClass theNonMetaclass
     ].
 
     (self canUseRefactoringSupport) ifTrue:[
-        changes := CompositeRefactoryChange named:((doWhat == #copy) ifTrue:['Copy protocol(s)'] ifFalse:['Move protocol(s)']).
+	changes := CompositeRefactoryChange named:((doWhat == #copy) ifTrue:['Copy protocol(s)'] ifFalse:['Move protocol(s)']).
     ].
 
     self selectedProtocolMethodsDo:[:cls :protocol :sel :methodToCopyOrMove |
-        |question msg selectorToCopyOrMove dontDoIt newMethod|
-
-        "/ skip the version method (to avoid confusing the repository)
-        ((AbstractSourceCodeManager isVersionMethodSelector:sel) and:[newClass isMeta]) ifFalse:[
-            dontDoIt := false.
-            selectorToCopyOrMove := methodToCopyOrMove selector.
-            (newClass includesSelector:selectorToCopyOrMove) ifTrue:[
-                question := (doWhat == #copy)
-                        ifTrue:['%1 already implements #%2\\Copy anyway ?']
-                        ifFalse:['%1 already implements #%2\\Move anyway ?'].
-
-                (self confirm:(resources string:question
-                                          with:newClass name allBold
-                                          with:selectorToCopyOrMove) withCRs) ifFalse:[
-                    dontDoIt := true
-                ]
-            ].
-            dontDoIt ifFalse:[
-                lastMethodMoveClass := newClassName.
-
-                changes notNil ifTrue:[
-                    changes
-                            compile: (methodToCopyOrMove source)
-                            in: newClass
-                            classified: (methodToCopyOrMove category).
-                    newMethod := #dummy. "/ to make following if happy
-                ] ifFalse:[
-                    newMethod := newClass
-                                        compile:(methodToCopyOrMove source)
-                                        classified:(methodToCopyOrMove category).
-                ].
-
-                (newMethod isNil or:[newMethod == #Error]) ifTrue:[
-                    msg := (doWhat == #copy)
-                               ifTrue:['#%1 not copied - compilation failed due to an error']
-                               ifFalse:['#%1 not moved - compilation failed due to an error'].
-                    self warn:(resources string:msg with:selectorToCopyOrMove)
-                ] ifFalse:[
-                    (doWhat == #move) ifTrue:[
-                        changes notNil ifTrue:[
-                            changes removeMethod: selectorToCopyOrMove from: (methodToCopyOrMove mclass)
-                        ] ifFalse:[
-                            (methodToCopyOrMove mclass) removeSelector:selectorToCopyOrMove.
-                        ]
-                    ]
-                ]
-            ]
-        ]
+	|question msg selectorToCopyOrMove dontDoIt newMethod|
+
+	"/ skip the version method (to avoid confusing the repository)
+	((AbstractSourceCodeManager isVersionMethodSelector:sel) and:[newClass isMeta]) ifFalse:[
+	    dontDoIt := false.
+	    selectorToCopyOrMove := methodToCopyOrMove selector.
+	    (newClass includesSelector:selectorToCopyOrMove) ifTrue:[
+		question := (doWhat == #copy)
+			ifTrue:['%1 already implements #%2\\Copy anyway ?']
+			ifFalse:['%1 already implements #%2\\Move anyway ?'].
+
+		(self confirm:(resources string:question
+					  with:newClass name allBold
+					  with:selectorToCopyOrMove) withCRs) ifFalse:[
+		    dontDoIt := true
+		]
+	    ].
+	    dontDoIt ifFalse:[
+		lastMethodMoveClass := newClassName.
+
+		changes notNil ifTrue:[
+		    changes
+			    compile: (methodToCopyOrMove source)
+			    in: newClass
+			    classified: (methodToCopyOrMove category).
+		    newMethod := #dummy. "/ to make following if happy
+		] ifFalse:[
+		    newMethod := newClass
+					compile:(methodToCopyOrMove source)
+					classified:(methodToCopyOrMove category).
+		].
+
+		(newMethod isNil or:[newMethod == #Error]) ifTrue:[
+		    msg := (doWhat == #copy)
+			       ifTrue:['#%1 not copied - compilation failed due to an error']
+			       ifFalse:['#%1 not moved - compilation failed due to an error'].
+		    self warn:(resources string:msg with:selectorToCopyOrMove)
+		] ifFalse:[
+		    (doWhat == #move) ifTrue:[
+			changes notNil ifTrue:[
+			    changes removeMethod: selectorToCopyOrMove from: (methodToCopyOrMove mclass)
+			] ifFalse:[
+			    (methodToCopyOrMove mclass) removeSelector:selectorToCopyOrMove.
+			]
+		    ]
+		]
+	    ]
+	]
     ].
 
     changes notNil ifTrue:[
-        RefactoryChangeManager performChange: changes
+	RefactoryChangeManager performChange: changes
     ].
 !
 
@@ -38936,7 +39407,7 @@
 
     newProject := self askForProject:'Move all methods in protocol(s) to which project:'.
     newProject notNil ifTrue:[
-        self doMoveSelectedProtocolsToProject:newProject.
+	self doMoveSelectedProtocolsToProject:newProject.
     ].
 !
 
@@ -38946,7 +39417,7 @@
      cls suggestion|
 
     LastNewProtocols notEmptyOrNil ifTrue:[
-        suggestion := LastNewProtocols first.
+	suggestion := LastNewProtocols first.
     ].
 
 "/    allMethodCategories := Set new.
@@ -38955,61 +39426,61 @@
 "/    ].
 "/
     SharedMethodCategoryCache isNil ifTrue:[
-        SharedMethodCategoryCache := MethodCategoryCache new
+	SharedMethodCategoryCache := MethodCategoryCache new
     ].
     allMethodCategories := SharedMethodCategoryCache allMethodCategories.
 
     "/ remove existing ones ...
     (cls := self theSingleSelectedClass) notNil ifTrue:[
-        classesMethodCategories := cls categories asSet.
-        someMethodCategories := allMethodCategories select:[:cat | (classesMethodCategories includes:cat) not].
+	classesMethodCategories := cls categories asSet.
+	someMethodCategories := allMethodCategories select:[:cat | (classesMethodCategories includes:cat) not].
 "/        someMethodCategories removeAllFoundIn:classesMethodCategories.
-        (classesMethodCategories includes:suggestion) ifTrue:[
-            suggestion := nil.
-        ].
+	(classesMethodCategories includes:suggestion) ifTrue:[
+	    suggestion := nil.
+	].
     ].
 
     someMethodCategories := (someMethodCategories ? allMethodCategories) asOrderedCollection sort.
 
     someRecentlyVisitedMethodCategories := self methodCategoryListApp lastSelectedProtocols.
     someRecentlyVisitedMethodCategories notEmptyOrNil ifTrue:[
-        someRecentlyVisitedMethodCategories := someRecentlyVisitedMethodCategories asOrderedCollection sort.
-        someMethodCategories addFirst:''.
-        someMethodCategories addAllFirst:someRecentlyVisitedMethodCategories.
-        suggestion isNil ifTrue:[
-            suggestion := someRecentlyVisitedMethodCategories first
-        ].
+	someRecentlyVisitedMethodCategories := someRecentlyVisitedMethodCategories asOrderedCollection sort.
+	someMethodCategories addFirst:''.
+	someMethodCategories addAllFirst:someRecentlyVisitedMethodCategories.
+	suggestion isNil ifTrue:[
+	    suggestion := someRecentlyVisitedMethodCategories first
+	].
     ].
 
     newProtocol := self
-                        askForMethodCategory:'Name of new protocol:\(Tab for completion)' withCRs
-                        title:'New MethodCategory'
-                        okLabel:'Create'
-                        list:someMethodCategories
-                        recentList:LastNewProtocols
-                        initialAnswer:suggestion.
+			askForMethodCategory:'Name of new protocol:\(Tab for completion)' withCRs
+			title:'New MethodCategory'
+			okLabel:'Create'
+			list:someMethodCategories
+			recentList:LastNewProtocols
+			initialAnswer:suggestion.
 
     newProtocol isNil ifTrue:[^ self].
     newProtocol bitsPerCharacter > 8 ifTrue:[
-        Dialog warn:'Sorry - for now, non-ascii categories are not allowed (no 2-byte symbols).'.
-        ^ self.
+	Dialog warn:'Sorry - for now, non-ascii categories are not allowed (no 2-byte symbols).'.
+	^ self.
     ].
 
     self immediateUpdate value:true.
     self selectedClassesDo:[:cls |
-        self methodCategoryListApp addAdditionalProtocol:newProtocol forClass:cls.
+	self methodCategoryListApp addAdditionalProtocol:newProtocol forClass:cls.
     ].
     self selectProtocol:newProtocol.
     self clearAutoSelectOfLastSelectedProtocol.
     self immediateUpdate value:false.
 
     LastNewProtocols isNil ifTrue:[
-        LastNewProtocols := OrderedCollection new
+	LastNewProtocols := OrderedCollection new
     ].
     LastNewProtocols remove:newProtocol ifAbsent:[].
     LastNewProtocols addFirst:newProtocol.
     LastNewProtocols size > 10 ifTrue:[
-        LastNewProtocols removeLast
+	LastNewProtocols removeLast
     ].
 
     "Modified: / 25.2.2000 / 00:56:04 / cg"
@@ -39030,42 +39501,42 @@
     protocols := Set new.
     methods := IdentitySet new.
     self selectedProtocolMethodsDo:[:cls :protocol :sel :eachMethod |
-        classes add:cls.
-        protocols add:protocol.
-        methods add:eachMethod.
+	classes add:cls.
+	protocols add:protocol.
+	methods add:eachMethod.
     ].
     numClasses := classes size.
     numProtocols := protocols size.
     numMethods := methods size.
 
     numMethods ~~ 0 ifTrue:[
-        numMethods == 1 ifTrue:[
-            msg := resources
-                        string:'Really remove %1 from ''%2'''
-                        with:(methods first selector allBold)
-                        with:classes first name allBold.
-        ] ifFalse:[
-            msg := 'Really remove %1 methods'.
-            numProtocols > 1 ifTrue:[
-                msg := msg , ' (in %3 categories)'
-            ] ifFalse:[
-                msg := msg , ' categorized as ''%4'''
-            ].
-            numClasses > 1 ifTrue:[
-                msg := msg , ' from %2 classes'
-            ] ifFalse:[
-                msg := msg , ' from ''%5'''
-            ].
-            msg := msg , ' ?'.
-            msg := resources
-                        string:msg
-                        with:numMethods printString
-                        with:numClasses printString
-                        with:numProtocols printString
-                        with:protocols first allBold
-                        with:classes first name allBold.
-        ].
-        (self confirm:msg) ifFalse:[^ self].
+	numMethods == 1 ifTrue:[
+	    msg := resources
+			string:'Really remove %1 from ''%2'''
+			with:(methods first selector allBold)
+			with:classes first name allBold.
+	] ifFalse:[
+	    msg := 'Really remove %1 methods'.
+	    numProtocols > 1 ifTrue:[
+		msg := msg , ' (in %3 categories)'
+	    ] ifFalse:[
+		msg := msg , ' categorized as ''%4'''
+	    ].
+	    numClasses > 1 ifTrue:[
+		msg := msg , ' from %2 classes'
+	    ] ifFalse:[
+		msg := msg , ' from ''%5'''
+	    ].
+	    msg := msg , ' ?'.
+	    msg := resources
+			string:msg
+			with:numMethods printString
+			with:numClasses printString
+			with:numProtocols printString
+			with:protocols first allBold
+			with:classes first name allBold.
+	].
+	(self confirm:msg) ifFalse:[^ self].
     ].
     classes := protocols := nil.
 
@@ -39076,12 +39547,12 @@
     "/ kludge: remove the simulated entries ...
     methodCategoryListApp := self methodCategoryListApp.
     methodCategoryListApp notNil ifTrue:[
-        self selectedClassesDo:[:cls |
-            methodCategoryListApp
-                    removeAdditionalProtocol:self selectedProtocols value
-                    forClass:cls.
-        ].
-        methodCategoryListApp updateList.
+	self selectedClassesDo:[:cls |
+	    methodCategoryListApp
+		    removeAdditionalProtocol:self selectedProtocols value
+		    forClass:cls.
+	].
+	methodCategoryListApp updateList.
     ]
 !
 
@@ -39094,30 +39565,30 @@
     self hasProtocolSelected ifFalse:[^ self].
 
     LastProtocolRenames isNil ifTrue:[
-        LastProtocolRenames := OrderedCollection new.
+	LastProtocolRenames := OrderedCollection new.
     ].
     currentMethodCategory := self theSingleSelectedProtocol.
     currentMethodCategory isNil ifTrue:[
-        LastProtocolRenames size > 0 ifTrue:[
-            last := LastProtocolRenames last
-        ].
-    ] ifFalse:[
-        currentMethodCategory := currentMethodCategory string.
-
-        last := LastProtocolRenames detect:[:ren | ren key = currentMethodCategory] ifNone:nil.
-        last notNil ifTrue:[
-            suggestion := last value
-        ]
+	LastProtocolRenames size > 0 ifTrue:[
+	    last := LastProtocolRenames last
+	].
+    ] ifFalse:[
+	currentMethodCategory := currentMethodCategory string.
+
+	last := LastProtocolRenames detect:[:ren | ren key = currentMethodCategory] ifNone:nil.
+	last notNil ifTrue:[
+	    suggestion := last value
+	]
     ].
     last isNil ifTrue:[
-        suggestion := currentMethodCategory
+	suggestion := currentMethodCategory
     ].
 
     currentMethodCategory isNil ifTrue:[
-        msg := resources string:'Rename selected categories to:'
-    ] ifFalse:[
-        msg := resources string:'Rename method category ''%1'' to:'
-                         with:currentMethodCategory allBold
+	msg := resources string:'Rename selected categories to:'
+    ] ifFalse:[
+	msg := resources string:'Rename method category ''%1'' to:'
+			 with:currentMethodCategory allBold
     ].
 "/    box := self class
 "/                enterBoxTitle:msg
@@ -39133,31 +39604,31 @@
 
     "/ offer the current classes's protocols in the dialog
     (selClasses := self selectedClassesValue) notEmptyOrNil ifTrue:[
-        selClasses do:[:eachClass |
-            someCategories addAll:(eachClass categories).
-        ]
-    ] ifFalse:[
-        "/ offer the current method-classes' protocols in the dialog
-        (selMethods := self selectedMethodsValue) notNil ifTrue:[
-            selMethods do:[:eachMethod | |cls|
-                (cls := eachMethod mclass) notNil ifTrue:[
-                    someCategories addAll:cls categories
-                ]
-            ]
-        ]
+	selClasses do:[:eachClass |
+	    someCategories addAll:(eachClass categories).
+	]
+    ] ifFalse:[
+	"/ offer the current method-classes' protocols in the dialog
+	(selMethods := self selectedMethodsValue) notNil ifTrue:[
+	    selMethods do:[:eachMethod | |cls|
+		(cls := eachMethod mclass) notNil ifTrue:[
+		    someCategories addAll:cls categories
+		]
+	    ]
+	]
     ].
     someCategories := someCategories asOrderedCollection sort.
     someCategories notEmpty ifTrue:[
-        someCategories add:''.
+	someCategories add:''.
     ].
     someCategories addAll:(Smalltalk allMethodCategories select:[:cat | (someCategories includes:cat) not]) asOrderedCollection sort.
 
     newCategory := self
-                        askForMethodCategory:msg
-                        title:'Rename MethodCategory'
-                        okLabel:'Rename'
-                        list:someCategories
-                        initialAnswer:suggestion.
+			askForMethodCategory:msg
+			title:'Rename MethodCategory'
+			okLabel:'Rename'
+			list:someCategories
+			initialAnswer:suggestion.
 
     newCategory isNil ifTrue:[^ self].
     newCategory := newCategory withoutSeparators.
@@ -39166,42 +39637,42 @@
     newCategory = currentMethodCategory ifTrue:[^ self].
 
     newCategory bitsPerCharacter > 8 ifTrue:[
-        Dialog warn:'Sorry - for now, non-ascii categories are not allowed (no 2-byte symbols).'.
-        ^ self.
+	Dialog warn:'Sorry - for now, non-ascii categories are not allowed (no 2-byte symbols).'.
+	^ self.
     ].
 
     self withWaitCursorDo:[
-        LastProtocolRenames := LastProtocolRenames select:[:ren | ren key ~= currentMethodCategory].
-        LastProtocolRenames addLast:(currentMethodCategory -> newCategory).
-        LastProtocolRenames size > 20 ifTrue:[LastProtocolRenames removeFirst].
-
-        methodCategoryListApp := self methodCategoryListApp.
-
-        newCategory := newCategory asSymbol.
-        self selectedProtocolsDo:[:cls :protocol |
-            |methods|
-
-            methods := cls methodDictionary values select:[:m | m category = protocol].
-            self moveMethods:methods toProtocol:newCategory.
+	LastProtocolRenames := LastProtocolRenames select:[:ren | ren key ~= currentMethodCategory].
+	LastProtocolRenames addLast:(currentMethodCategory -> newCategory).
+	LastProtocolRenames size > 20 ifTrue:[LastProtocolRenames removeFirst].
+
+	methodCategoryListApp := self methodCategoryListApp.
+
+	newCategory := newCategory asSymbol.
+	self selectedProtocolsDo:[:cls :protocol |
+	    |methods|
+
+	    methods := cls methodDictionary values select:[:m | m category = protocol].
+	    self moveMethods:methods toProtocol:newCategory.
 
 "/            cls renameCategory:protocol to:newCategory.
-            "/ kludge - must also rename in addedProtocols
-            methodCategoryListApp notNil ifTrue:[
-                methodCategoryListApp renameAdditionalProtocol:protocol to:newCategory forClass:cls.
-            ]
-        ].
-        methodCategoryListApp notNil ifTrue:[
-            (self selectedClassesValue) do:[:cls |
-                "/ kludge - must also rename in addedProtocols
-                methodCategoryListApp renameAdditionalProtocol:currentMethodCategory to:newCategory forClass:cls.
-            ].
-
-            methodCategoryListApp updateList.
-        ].
-
-        self immediateUpdate value:true.
-        self selectProtocol:newCategory.
-        self immediateUpdate value:false.
+	    "/ kludge - must also rename in addedProtocols
+	    methodCategoryListApp notNil ifTrue:[
+		methodCategoryListApp renameAdditionalProtocol:protocol to:newCategory forClass:cls.
+	    ]
+	].
+	methodCategoryListApp notNil ifTrue:[
+	    (self selectedClassesValue) do:[:cls |
+		"/ kludge - must also rename in addedProtocols
+		methodCategoryListApp renameAdditionalProtocol:currentMethodCategory to:newCategory forClass:cls.
+	    ].
+
+	    methodCategoryListApp updateList.
+	].
+
+	self immediateUpdate value:true.
+	self selectProtocol:newCategory.
+	self immediateUpdate value:false.
     ]
 
     "Modified: / 28-02-2012 / 17:00:47 / cg"
@@ -39211,9 +39682,9 @@
     "open a new browser showing the selected category only"
 
     ^ self
-        spawnProtocolBrowserFor:(self selectedClassesValue)
-        and:(self selectedProtocols value)
-        in:#newBrowser
+	spawnProtocolBrowserFor:(self selectedClassesValue)
+	and:(self selectedProtocols value)
+	in:#newBrowser
 
     "Modified: / 28-02-2012 / 17:00:28 / cg"
 !
@@ -39222,9 +39693,9 @@
     "add a new buffer showing the selected category only"
 
     ^ self
-        spawnProtocolBrowserFor:(self selectedClassesValue)
-        and:(self selectedProtocols value)
-        in:#newBuffer
+	spawnProtocolBrowserFor:(self selectedClassesValue)
+	and:(self selectedProtocols value)
+	in:#newBuffer
 
     "Modified: / 28-02-2012 / 16:54:00 / cg"
 !
@@ -39233,16 +39704,16 @@
     "open a new browser showing all methods (from all classes) in that category"
 
     ^ self
-        spawnFullProtocolBrowserFor:(self selectedProtocols value)
-        in:#newBrowser
+	spawnFullProtocolBrowserFor:(self selectedProtocols value)
+	in:#newBrowser
 !
 
 protocolMenuSpawnFullCategoryBuffer
     "add a new buffer showing all methods (from all classes) in that category"
 
     ^ self
-        spawnFullProtocolBrowserFor:(self selectedProtocols value)
-        in:#newBuffer
+	spawnFullProtocolBrowserFor:(self selectedProtocols value)
+	in:#newBuffer
 !
 
 protocolMenuSpawnMatchingFullCategoryBrowser
@@ -39268,13 +39739,13 @@
 
     matchingProtocols := Set new.
     Smalltalk allClassesAndMetaclassesDo:[:eachClass |
-        eachClass isLoaded ifTrue:[
-            eachClass categories do:[:cat |
-                (pattern match:cat) ifTrue:[
-                    matchingProtocols add:cat.
-                ]
-            ]
-        ]
+	eachClass isLoaded ifTrue:[
+	    eachClass categories do:[:cat |
+		(pattern match:cat) ifTrue:[
+		    matchingProtocols add:cat.
+		]
+	    ]
+	]
     ].
     ^ self spawnFullProtocolBrowserFor:matchingProtocols in:openHow
 !
@@ -39283,10 +39754,10 @@
     |methodCategoryListApp|
 
     (methodCategoryListApp := self methodCategoryListApp) notNil ifTrue:[
-        (self selectedClassesValue) do:[:aClass |
-            methodCategoryListApp removeAllAdditionalProtocolForClass:aClass
-        ].
-        methodCategoryListApp forceUpdateList
+	(self selectedClassesValue) do:[:aClass |
+	    methodCategoryListApp removeAllAdditionalProtocolForClass:aClass
+	].
+	methodCategoryListApp forceUpdateList
     ]
 
     "Modified: / 28-02-2012 / 16:53:56 / cg"
@@ -39294,125 +39765,125 @@
 
 spawnFullProtocolBrowserFor:protocols in:where
     "browse selected protocols;
-        where is: #newBrowser - open a new browser showing the classes
-        where is: #newBuffer  - add a new buffer showing the classes"
+	where is: #newBrowser - open a new browser showing the classes
+	where is: #newBuffer  - add a new buffer showing the classes"
 
     |spec lbl|
 
     protocols size == 1 ifTrue:[
-        spec := #singleFullProtocolBrowserSpec.
-        lbl := protocols first , ' [full Protocol]'
-    ] ifFalse:[
-        spec := #multipleFullProtocolBrowserSpec.
-        lbl := '[full Protocols]'
+	spec := #singleFullProtocolBrowserSpec.
+	lbl := protocols first , ' [full Protocol]'
+    ] ifFalse:[
+	spec := #multipleFullProtocolBrowserSpec.
+	lbl := '[full Protocols]'
     ].
     "/ selectedMethods := self selectedMethods value copy.
 
     ^ self
-        newBrowserOrBufferDependingOn:where
-        label:lbl
-        forSpec:spec
-        setupWith:[:brwsr |
-            |generator protocolList|
-
-            protocolList := protocols collect:[:each | each string].
-
-            "/ setup a special generator ...
-
-            generator :=
-                Iterator on:[:whatToDo |
-                                |all protocols|
-
-                                protocols := protocolList.
-                                "/ protocols := (brwsr selectedProtocols value) ? protocolList.
-
-                                all := protocols includes:(BrowserList nameListEntryForALL).
-                                self withWaitCursorDo:[
-                                    Smalltalk allClassesAndMetaclassesDo:[:eachClass |
-                                        eachClass categories do:[:cat |
-                                            (all or:[protocols includes:cat]) ifTrue:[
-                                                whatToDo value:eachClass value:cat.
-                                            ]
-                                        ]
-                                    ]
-                                ].  
-                          ].
-
-            brwsr noAllItem value:true.
-            brwsr sortBy value:#class.
+	newBrowserOrBufferDependingOn:where
+	label:lbl
+	forSpec:spec
+	setupWith:[:brwsr |
+	    |generator protocolList|
+
+	    protocolList := protocols collect:[:each | each string].
+
+	    "/ setup a special generator ...
+
+	    generator :=
+		Iterator on:[:whatToDo |
+				|all protocols|
+
+				protocols := protocolList.
+				"/ protocols := (brwsr selectedProtocols value) ? protocolList.
+
+				all := protocols includes:(BrowserList nameListEntryForALL).
+				self withWaitCursorDo:[
+				    Smalltalk allClassesAndMetaclassesDo:[:eachClass |
+					eachClass categories do:[:cat |
+					    (all or:[protocols includes:cat]) ifTrue:[
+						whatToDo value:eachClass value:cat.
+					    ]
+					]
+				    ]
+				].
+			  ].
+
+	    brwsr noAllItem value:true.
+	    brwsr sortBy value:#class.
 "/            brwsr immediateUpdate value:true.
-            "/ kludge - need a dummy organizer (with constant classList/protocolList)
-            brwsr withWaitCursorDo:[
-                brwsr protocolListGenerator value:generator.
-                protocolList size == 1 ifTrue:[brwsr selectProtocols:protocolList copy].
-            ].
-            "/ brwsr selectMethods:selectedMethods.
+	    "/ kludge - need a dummy organizer (with constant classList/protocolList)
+	    brwsr withWaitCursorDo:[
+		brwsr protocolListGenerator value:generator.
+		protocolList size == 1 ifTrue:[brwsr selectProtocols:protocolList copy].
+	    ].
+	    "/ brwsr selectMethods:selectedMethods.
 "/            brwsr immediateUpdate value:false.
-        ]
+	]
 !
 
 spawnProtocolBrowserFor:classes and:protocols in:where
     "browse selected protocols;
-        where is: #newBrowser - open a new browser showing the classes
-        where is: #newBuffer  - add a new buffer showing the classes"
+	where is: #newBrowser - open a new browser showing the classes
+	where is: #newBuffer  - add a new buffer showing the classes"
 
     |spec selectedMethods singleSelection|
 
     (singleSelection := protocols size) == 1 ifTrue:[
-        spec := #singleProtocolBrowserSpec.
-    ] ifFalse:[
-        spec := #multipleProtocolBrowserSpec.
+	spec := #singleProtocolBrowserSpec.
+    ] ifFalse:[
+	spec := #multipleProtocolBrowserSpec.
     ].
     selectedMethods := self selectedMethodsValue copy.
 
     ^ self
-        newBrowserOrBufferDependingOn:where
-        label:nil
-        forSpec:spec
-        setupWith:[:brwsr |
-            |generator classList protocolList|
-
-            classList := classes copy.
-            protocolList := protocols collect:[:each | each string].
-
-            brwsr selectClasses:classList.
-            "/ setup a special generator ...
-
-            generator :=
-                Iterator on:[:whatToDo |
-                                |all remainingClasses remainingCategories|
-
-                                remainingClasses := classList copy asIdentitySet.
-                                remainingCategories := protocolList copy asSet.
-
-                                all := protocolList includes:(BrowserList nameListEntryForALL).
-
-                                classList do:[:aClass |
-                                    aClass methodDictionary keysAndValuesDo:[:sel :mthd |
-                                        |cat|
-
-                                        cat := mthd category.
-                                        (all
-                                        or:[protocolList includes:cat]) ifTrue:[
-                                            whatToDo value:aClass value:cat.
-                                            remainingClasses remove:aClass ifAbsent:nil.
-                                            remainingCategories remove:cat ifAbsent:nil.
-                                        ]
-                                    ]
-                                ].
-                                remainingClasses do:[:aClass |
-                                    whatToDo value:aClass value:nil.
-                                ].
-                          ].
-
-            "/ kludge - need a dummy organizer (with constant classList/protocolList)
-            brwsr immediateUpdate value:true.
-            brwsr protocolListGenerator value:generator.
-            brwsr selectProtocols:protocolList copy.
-            brwsr selectMethods:selectedMethods.
-
-            brwsr immediateUpdate value:false.
-        ]
+	newBrowserOrBufferDependingOn:where
+	label:nil
+	forSpec:spec
+	setupWith:[:brwsr |
+	    |generator classList protocolList|
+
+	    classList := classes copy.
+	    protocolList := protocols collect:[:each | each string].
+
+	    brwsr selectClasses:classList.
+	    "/ setup a special generator ...
+
+	    generator :=
+		Iterator on:[:whatToDo |
+				|all remainingClasses remainingCategories|
+
+				remainingClasses := classList copy asIdentitySet.
+				remainingCategories := protocolList copy asSet.
+
+				all := protocolList includes:(BrowserList nameListEntryForALL).
+
+				classList do:[:aClass |
+				    aClass methodDictionary keysAndValuesDo:[:sel :mthd |
+					|cat|
+
+					cat := mthd category.
+					(all
+					or:[protocolList includes:cat]) ifTrue:[
+					    whatToDo value:aClass value:cat.
+					    remainingClasses remove:aClass ifAbsent:nil.
+					    remainingCategories remove:cat ifAbsent:nil.
+					]
+				    ]
+				].
+				remainingClasses do:[:aClass |
+				    whatToDo value:aClass value:nil.
+				].
+			  ].
+
+	    "/ kludge - need a dummy organizer (with constant classList/protocolList)
+	    brwsr immediateUpdate value:true.
+	    brwsr protocolListGenerator value:generator.
+	    brwsr selectProtocols:protocolList copy.
+	    brwsr selectMethods:selectedMethods.
+
+	    brwsr immediateUpdate value:false.
+	]
 
     "Modified: / 28-02-2012 / 16:34:54 / cg"
 ! !
@@ -39427,9 +39898,9 @@
      otherwise, a match pattern is allowed and a multi-class browser is opened."
 
     |box boxLabel title okText okText2 okText3 className canFind
-     button2 button3 doWhat doWhat2 doWhat3 classNameHolder updateList 
-     allClasses 
-     allNames allFullNames initialShortNames initialFullNames 
+     button2 button3 doWhat doWhat2 doWhat3 classNameHolder updateList
+     allClasses
+     allNames allFullNames initialShortNames initialFullNames
      resources check showingWhatLabel showFullNameHolder genShortNameListEntry|
 
     resources := resourcesOrNil ? self class classResources.
@@ -39439,48 +39910,48 @@
     canFind := navigationState notNil and:[ navigationState isFullBrowser ].
 
     doWhat isNil ifTrue:[
-        title := ''.
-        boxLabel := (resources string:'Select a class').
-        okText := 'OK'.
-        okText2 := nil. doWhat2 := nil.
-        okText3 := nil. doWhat3 := nil.
-    ] ifFalse:[
-        title := (singleClass ifTrue:[ 'Class to browse' ] ifFalse:[ 'Class(es) to browse' ]).
-        boxLabel := (resources string:'Browse or Search').
-
-        (doWhat isNil and:[canFind not]) ifTrue:[
-            doWhat := #newBuffer.
-        ].
-
-        doWhat == #newBrowser ifTrue:[
-            okText := 'Open'.
-            okText2 := 'Add Buffer'. doWhat2 := #newBuffer.
-            okText3 := 'Find'.       doWhat3 := nil.
-        ] ifFalse:[ doWhat == #newBuffer ifTrue:[
-            okText := 'Add Buffer'.
-            okText2 := 'Open New'.   doWhat2 := #newBrowser.
-            okText3 := 'Find'.       doWhat3 := nil.
-        ] ifFalse:[
-            title := (singleClass ifTrue:[ 'Class to find' ] ifFalse:[ 'Class(es) to find' ]).
-            okText := 'Find'.
-            okText2 := 'Open New'.   doWhat2 := #newBrowser.
-            okText3 := 'Add Buffer'. doWhat3 := #newBuffer.
-        ]].
-    ].
-
-    genShortNameListEntry := 
-        [:cls | 
-            |ns|
-            cls isNil ifTrue:[
-                nil
-            ] ifFalse:[
-                ns := cls topNameSpace name.
-                ns = 'Smalltalk' 
-                    ifTrue:[ ns := '' ]
-                    ifFalse:[ns := ' (in ',ns,')'].
-                cls nameWithoutNameSpacePrefix,ns
-            ].
-        ].
+	title := ''.
+	boxLabel := (resources string:'Select a class').
+	okText := 'OK'.
+	okText2 := nil. doWhat2 := nil.
+	okText3 := nil. doWhat3 := nil.
+    ] ifFalse:[
+	title := (singleClass ifTrue:[ 'Class to browse' ] ifFalse:[ 'Class(es) to browse' ]).
+	boxLabel := (resources string:'Browse or Search').
+
+	(doWhat isNil and:[canFind not]) ifTrue:[
+	    doWhat := #newBuffer.
+	].
+
+	doWhat == #newBrowser ifTrue:[
+	    okText := 'Open'.
+	    okText2 := 'Add Buffer'. doWhat2 := #newBuffer.
+	    okText3 := 'Find'.       doWhat3 := nil.
+	] ifFalse:[ doWhat == #newBuffer ifTrue:[
+	    okText := 'Add Buffer'.
+	    okText2 := 'Open New'.   doWhat2 := #newBrowser.
+	    okText3 := 'Find'.       doWhat3 := nil.
+	] ifFalse:[
+	    title := (singleClass ifTrue:[ 'Class to find' ] ifFalse:[ 'Class(es) to find' ]).
+	    okText := 'Find'.
+	    okText2 := 'Open New'.   doWhat2 := #newBrowser.
+	    okText3 := 'Add Buffer'. doWhat3 := #newBuffer.
+	]].
+    ].
+
+    genShortNameListEntry :=
+	[:cls |
+	    |ns|
+	    cls isNil ifTrue:[
+		nil
+	    ] ifFalse:[
+		ns := cls topNameSpace name.
+		ns = 'Smalltalk'
+		    ifTrue:[ ns := '' ]
+		    ifFalse:[ns := ' (in ',ns,')'].
+		cls nameWithoutNameSpacePrefix,ns
+	    ].
+	].
 
     initialFullNames := self class visitedClassNamesHistory.
     initialShortNames := initialFullNames collect:[:nm | genShortNameListEntry value:(Smalltalk at:nm)] thenSelect:[:nm | nm notNil].
@@ -39488,112 +39959,112 @@
     title := (resources string:title) , msgTail , '.\' , (resources string:'(TAB to complete; matchPattern allowed):').
 
     box := self
-                enterBoxForClassWithCodeSelectionTitle:title withCRs
-                withList:(showFullNameHolder value ifTrue:[initialFullNames] ifFalse:[initialShortNames])
-                okText:okText.
+		enterBoxForClassWithCodeSelectionTitle:title withCRs
+		withList:(showFullNameHolder value ifTrue:[initialFullNames] ifFalse:[initialShortNames])
+		okText:okText.
 
     box label:boxLabel.
 
     doWhat notNil ifTrue:[
-        button2 := Button label:(resources string:okText2).
-        navigationState isFullBrowser "singleClass" ifTrue:[
-            button3 := Button label:(resources string:okText3)
-        ].
-        (DialogBox defaultOKButtonAtLeft) ifFalse:[
-            box addButton:button2 before:(box okButton).
-            button3 notNil ifTrue:[box addButton:button3 before:button2].
-        ] ifTrue:[
-            box addButton:button2 after:(box okButton).
-            button3 notNil ifTrue:[box addButton:button3 after:button2].
-        ].
-
-        button2 action:[
-           doWhat := doWhat2.
-           box doAccept.
-           box okPressed.
-        ].
-        button3 notNil ifTrue:[
-            button3 action:[
-               doWhat := doWhat3.
-               box doAccept.
-               box okPressed.
-            ].
-        ].
+	button2 := Button label:(resources string:okText2).
+	navigationState isFullBrowser "singleClass" ifTrue:[
+	    button3 := Button label:(resources string:okText3)
+	].
+	(DialogBox defaultOKButtonAtLeft) ifFalse:[
+	    box addButton:button2 before:(box okButton).
+	    button3 notNil ifTrue:[box addButton:button3 before:button2].
+	] ifTrue:[
+	    box addButton:button2 after:(box okButton).
+	    button3 notNil ifTrue:[box addButton:button3 after:button2].
+	].
+
+	button2 action:[
+	   doWhat := doWhat2.
+	   box doAccept.
+	   box okPressed.
+	].
+	button3 notNil ifTrue:[
+	    button3 action:[
+	       doWhat := doWhat3.
+	       box doAccept.
+	       box okPressed.
+	    ].
+	].
     ].
 
     allClasses := Smalltalk allClasses asOrderedCollection.
 
     allNames := (allClasses
-                    collect:[:cls | 
-                        |ns|
-                        ns := cls topNameSpace name.
-                        ns = 'Smalltalk' 
-                            ifTrue:[ ns := '' ]
-                            ifFalse:[ns := ' (in ',ns,')'].
-                        cls nameWithoutNameSpacePrefix,ns
-                    ]) sortWith:allClasses; yourself.
+		    collect:[:cls |
+			|ns|
+			ns := cls topNameSpace name.
+			ns = 'Smalltalk'
+			    ifTrue:[ ns := '' ]
+			    ifFalse:[ns := ' (in ',ns,')'].
+			cls nameWithoutNameSpacePrefix,ns
+		    ]) sortWith:allClasses; yourself.
     allFullNames := (allClasses collect:[:cls | cls name]) sortWith:allClasses; yourself.
 
     updateList := [
-            |nameToSearch list namesStarting namesIncluding lcName nameList|
-
-            (nameToSearch := classNameHolder value withoutSeparators) isEmpty ifTrue:[
-                showingWhatLabel label:(resources string:'Recently visited:'). 
-                list := (showFullNameHolder value ifTrue:[initialFullNames] ifFalse:[initialShortNames]).
-            ] ifFalse:[
-                showingWhatLabel label:(resources string:'Matching classes:'). 
-                nameList := showFullNameHolder value
-                                ifTrue:[ allFullNames ]
-                                ifFalse:[ allNames ].
-
-                lcName := nameToSearch asLowercase.
-                (lcName includesString:'::') ifTrue:[
-                    list := OrderedCollection new.
-                    allClasses doWithIndex:[:cls :idx |
-                        |isIncluded|
-
-                        (nameToSearch includesMatchCharacters) ifTrue:[
-                            isIncluded := (lcName match:cls name asLowercase) 
-                        ] ifFalse:[
-                            isIncluded := (cls name includesString:lcName caseSensitive:false) 
-                        ].
-                        isIncluded ifTrue:[
-                            list add:(nameList at:idx)
-                        ].
-                    ].
-                ] ifFalse:[
-                    (nameToSearch includesMatchCharacters) ifTrue:[
-                        list := nameList select:[:nm | lcName match:nm asLowercase]
-                    ] ifFalse:[
-                        namesIncluding := nameList 
-                                            select:[:nm | 
-                                                "/ nm asLowercase startsWith:lcName 
-                                                nm asLowercase includesString:lcName caseSensitive:false
-                                            ].
-                        namesStarting := namesIncluding select:[:nm | nm asLowercase startsWith:lcName].
-                        list := namesStarting , {nil} , (namesIncluding \ namesStarting).
-                    ]
-                ]
-            ].
-            box listView list:list.
-            box listView scrollToLine:((list findFirst:[:line | (line ? '') startsWith:lcName]) max:1)
-        ].
+	    |nameToSearch list namesStarting namesIncluding lcName nameList|
+
+	    (nameToSearch := classNameHolder value withoutSeparators) isEmpty ifTrue:[
+		showingWhatLabel label:(resources string:'Recently visited:').
+		list := (showFullNameHolder value ifTrue:[initialFullNames] ifFalse:[initialShortNames]).
+	    ] ifFalse:[
+		showingWhatLabel label:(resources string:'Matching classes:').
+		nameList := showFullNameHolder value
+				ifTrue:[ allFullNames ]
+				ifFalse:[ allNames ].
+
+		lcName := nameToSearch asLowercase.
+		(lcName includesString:'::') ifTrue:[
+		    list := OrderedCollection new.
+		    allClasses doWithIndex:[:cls :idx |
+			|isIncluded|
+
+			(nameToSearch includesMatchCharacters) ifTrue:[
+			    isIncluded := (lcName match:cls name asLowercase)
+			] ifFalse:[
+			    isIncluded := (cls name includesString:lcName caseSensitive:false)
+			].
+			isIncluded ifTrue:[
+			    list add:(nameList at:idx)
+			].
+		    ].
+		] ifFalse:[
+		    (nameToSearch includesMatchCharacters) ifTrue:[
+			list := nameList select:[:nm | lcName match:nm asLowercase]
+		    ] ifFalse:[
+			namesIncluding := nameList
+					    select:[:nm |
+						"/ nm asLowercase startsWith:lcName
+						nm asLowercase includesString:lcName caseSensitive:false
+					    ].
+			namesStarting := namesIncluding select:[:nm | nm asLowercase startsWith:lcName].
+			list := namesStarting , {nil} , (namesIncluding \ namesStarting).
+		    ]
+		]
+	    ].
+	    box listView list:list.
+	    box listView scrollToLine:((list findFirst:[:line | (line ? '') startsWith:lcName]) max:1)
+	].
 
     classNameHolder := '' asValue.
-    box enterField 
-        model:classNameHolder;
-        immediateAccept:true.
+    box enterField
+	model:classNameHolder;
+	immediateAccept:true.
     classNameHolder onChangeEvaluate:updateList.
 
     box entryCompletionBlock:(DoWhatIMeanSupport classNameEntryCompletionBlock).
     box action:[:aString | className := aString].
 
-    box panelView 
-        addSubView:(showingWhatLabel := (Label label:(resources string:'Recently visited:')) adjust:#left) 
-        before:nil.
-    box panelView 
-        addSubView:(check := CheckBox label:'Show Full Name (do not strip off Namespace)' model:showFullNameHolder) 
-        before:nil.
+    box panelView
+	addSubView:(showingWhatLabel := (Label label:(resources string:'Recently visited:')) adjust:#left)
+	before:nil.
+    box panelView
+	addSubView:(check := CheckBox label:'Show Full Name (do not strip off Namespace)' model:showFullNameHolder)
+	before:nil.
     showFullNameHolder onChangeEvaluate:updateList.
     box enterField origin:(0 @ check corner y).
     box listView origin:(0 @ check corner y).
@@ -39604,18 +40075,18 @@
     className isNil ifTrue:[^ nil "cancel"].
 
     (className endsWith:$) ) ifTrue:[
-        className := ((className copyFrom:(className indexOfSubCollection:'(in ')+4)
-                        copyWithoutLast:1)
-                     , '::' , className asCollectionOfWords first 
+	className := ((className copyFrom:(className indexOfSubCollection:'(in ')+4)
+			copyWithoutLast:1)
+		     , '::' , className asCollectionOfWords first
     ].
 
     doWhat isNil ifTrue:[
-        aBlock notNil ifTrue:[aBlock value:className optionalArgument:singleClass and:doWhat].
-        ^ className
+	aBlock notNil ifTrue:[aBlock value:className optionalArgument:singleClass and:doWhat].
+	^ className
     ].
 
     self withSearchCursorDo:[
-        aBlock value:className value:singleClass value:doWhat.
+	aBlock value:className value:singleClass value:doWhat.
     ].
     ^ className
 
@@ -39630,11 +40101,11 @@
      otherwise, a match pattern is allowed and a multi-class browser is opened."
 
     ^ self
-        askForClassToSearch:doWhatByDefault 
-        single:singleClass 
-        msgTail:msgTail 
-        resources:resources 
-        thenDo:aBlock
+	askForClassToSearch:doWhatByDefault
+	single:singleClass
+	msgTail:msgTail
+	resources:resources
+	thenDo:aBlock
 !
 
 findClass:classNameArg single:singleClass in:doWhat
@@ -39643,119 +40114,119 @@
     className := classNameArg.
 
     singleClass ifTrue:[
-        className includesMatchCharacters ifFalse:[
-            currentNamespace := self currentNamespace.
-
-            aliases := Smalltalk
-                        keysAndValuesSelect:[:nm :val | (nm sameAs:classNameArg) ]
-                        thenCollect:[:nm :val | val isBehavior ifTrue:[val] ifFalse:[val class]].
-
-            classes := (self class classesWithNameSimilarTo:className from:currentNamespace) asOrderedCollection.
-            classes := classes select:[:each | each isRealNameSpace not].
-
-            aliases := aliases select:[:eachAlias | (classes includesIdentical:eachAlias) not].
-            classes addAll:aliases.
-
-            class := classes firstIfEmpty:nil.
-            class isNil ifTrue:[
-                className := self askForClassNameMatching:className.
-                "/ ^ self warn:('No such class: ' , className).
-            ] ifFalse:[
-                classes size == 1 ifTrue:[
-                    className := class name
-                ] ifFalse:[
-                    classNames := classes collect:[:each| (each name?'') , ' (',(each package?'?'),')'].
-                    classNameArg includesMatchCharacters ifFalse:[
-                        classNames := classNames
-                                        collect:[:nm |
-                                            |idx|
-                                            idx := nm asLowercase indexOfSubCollection:classNameArg asLowercase.
-                                            idx == 0 ifTrue:[
-                                                nm
-                                            ] ifFalse:[
-                                                nm asText emphasizeFrom:idx to:idx+classNameArg size-1 with:#bold
-                                            ]
-                                        ]
-                    ].
-
-                    box := self listBoxTitle:('Multiple class with name similar to/containing ''',classNameArg allBold,'''\\Select class to switch to:') withCRs
-                                      okText:'OK'
-                                        list:classNames "asSortedCollection".
-                    box initialText:(classes first name).
-                    box entryCompletionBlock:(DoWhatIMeanSupport classNameEntryCompletionBlock).
-                    box action:[:aString | className := aString string].
-
-                    browseButton := Button label:(resources string:'Browse All').
-                    browseButton action:[
-                                    self
-                                        spawnClassBrowserFor:classes 
-                                        label:('Classes named like "%1"' bindWith:classNameArg) 
-                                        in:#newBrowser 
-                                        select:false.
-                                    box hide
-                                 ].
-                    box addButton:browseButton before:box okButton.
-                    box extent:(400 @ 300).
-                    box open.
-
-                    className isNil ifTrue:[ "/ cancel
-                        ^ nil
-                    ].
-                    className := (className upTo:$( ) withoutTrailingSeparators.
-                ].
-            ].
-        ] ifTrue:[
-            className := self askForClassNameMatching:className.
-        ].
-
-        className notNil ifTrue:[
-            doWhat == #newBrowser ifTrue:[
-                brwsr := self class new.
-                brwsr allButOpen.
-                brwsr switchToClassNamed:className.
-                brwsr openWindow.
-            ] ifFalse:[
-                brwsr := self.
-                doWhat == #newBuffer ifTrue:[
-                    brwsr createBuffer.
-                ] ifFalse:[
-                    "/ self rememberLocationInHistory
-                ].
-                brwsr switchToClassNamed:className.
-            ].
-        ].
-        ^ self.
+	className includesMatchCharacters ifFalse:[
+	    currentNamespace := self currentNamespace.
+
+	    aliases := Smalltalk
+			keysAndValuesSelect:[:nm :val | (nm sameAs:classNameArg) ]
+			thenCollect:[:nm :val | val isBehavior ifTrue:[val] ifFalse:[val class]].
+
+	    classes := (self class classesWithNameSimilarTo:className from:currentNamespace) asOrderedCollection.
+	    classes := classes select:[:each | each isRealNameSpace not].
+
+	    aliases := aliases select:[:eachAlias | (classes includesIdentical:eachAlias) not].
+	    classes addAll:aliases.
+
+	    class := classes firstIfEmpty:nil.
+	    class isNil ifTrue:[
+		className := self askForClassNameMatching:className.
+		"/ ^ self warn:('No such class: ' , className).
+	    ] ifFalse:[
+		classes size == 1 ifTrue:[
+		    className := class name
+		] ifFalse:[
+		    classNames := classes collect:[:each| (each name?'') , ' (',(each package?'?'),')'].
+		    classNameArg includesMatchCharacters ifFalse:[
+			classNames := classNames
+					collect:[:nm |
+					    |idx|
+					    idx := nm asLowercase indexOfSubCollection:classNameArg asLowercase.
+					    idx == 0 ifTrue:[
+						nm
+					    ] ifFalse:[
+						nm asText emphasizeFrom:idx to:idx+classNameArg size-1 with:#bold
+					    ]
+					]
+		    ].
+
+		    box := self listBoxTitle:('Multiple class with name similar to/containing ''',classNameArg allBold,'''\\Select class to switch to:') withCRs
+				      okText:'OK'
+					list:classNames "asSortedCollection".
+		    box initialText:(classes first name).
+		    box entryCompletionBlock:(DoWhatIMeanSupport classNameEntryCompletionBlock).
+		    box action:[:aString | className := aString string].
+
+		    browseButton := Button label:(resources string:'Browse All').
+		    browseButton action:[
+				    self
+					spawnClassBrowserFor:classes
+					label:('Classes named like "%1"' bindWith:classNameArg)
+					in:#newBrowser
+					select:false.
+				    box hide
+				 ].
+		    box addButton:browseButton before:box okButton.
+		    box extent:(400 @ 300).
+		    box open.
+
+		    className isNil ifTrue:[ "/ cancel
+			^ nil
+		    ].
+		    className := (className upTo:$( ) withoutTrailingSeparators.
+		].
+	    ].
+	] ifTrue:[
+	    className := self askForClassNameMatching:className.
+	].
+
+	className notNil ifTrue:[
+	    doWhat == #newBrowser ifTrue:[
+		brwsr := self class new.
+		brwsr allButOpen.
+		brwsr switchToClassNamed:className.
+		brwsr openWindow.
+	    ] ifFalse:[
+		brwsr := self.
+		doWhat == #newBuffer ifTrue:[
+		    brwsr createBuffer.
+		] ifFalse:[
+		    "/ self rememberLocationInHistory
+		].
+		brwsr switchToClassNamed:className.
+	    ].
+	].
+	^ self.
     ].
 
     className includesMatchCharacters ifFalse:[
-        class := Smalltalk at:className asSymbol.
-        class isBehavior ifTrue:[
-            classes := Array with:class
-        ]
+	class := Smalltalk at:className asSymbol.
+	class isBehavior ifTrue:[
+	    classes := Array with:class
+	]
     ] ifTrue:[
-        classes := Smalltalk allClasses select:[:each | className match:each name].
-        classes := classes asOrderedCollection.
+	classes := Smalltalk allClasses select:[:each | className match:each name].
+	classes := classes asOrderedCollection.
     ].
     classes size == 0 ifTrue:[
-        ^ self warn:'No className matches'.
+	^ self warn:'No className matches'.
     ].
     classes := classes asSet.
     classes copy do:[:eachClass |
-        |owner|
-
-        owner := eachClass owningClass.
-        [owner notNil] whileTrue:[classes add:owner. owner := owner owningClass].
+	|owner|
+
+	owner := eachClass owningClass.
+	[owner notNil] whileTrue:[classes add:owner. owner := owner owningClass].
     ].
     classes := classes asOrderedCollection.
 
     doWhat isNil ifTrue:[
-        "/ select them ...
-        self immediateUpdate value:true.
-        self selectedCategories value: (classes collect:[:each | each category]) asSet asOrderedCollection.
-        self selectedClasses value:classes.
-        self immediateUpdate value:false.
-    ] ifFalse:[
-        self spawnClassBrowserFor:classes label:('classes matching ''',className,'''') in:doWhat select:false
+	"/ select them ...
+	self immediateUpdate value:true.
+	self selectedCategories value: (classes collect:[:each | each category]) asSet asOrderedCollection.
+	self selectedClasses value:classes.
+	self immediateUpdate value:false.
+    ] ifFalse:[
+	self spawnClassBrowserFor:classes label:('classes matching ''',className,'''') in:doWhat select:false
     ]
 
     "Created: / 13-02-2000 / 20:35:30 / cg"
@@ -39774,51 +40245,51 @@
     currentMethod := self theSingleSelectedMethod.
     searchClass := self theSingleSelectedClass.
     searchClass isNil ifTrue:[
-        searchClass := self classHierarchyTopClass value.
-        searchClass isNil ifTrue:[
-            currentMethod notNil ifTrue:[
-                searchClass := currentMethod mclass
-            ].
-        ].
-        searchClass isNil ifTrue:[
-            self information:'No class or method selected (cannot search).'.
-            ^ self
-        ]
+	searchClass := self classHierarchyTopClass value.
+	searchClass isNil ifTrue:[
+	    currentMethod notNil ifTrue:[
+		searchClass := currentMethod mclass
+	    ].
+	].
+	searchClass isNil ifTrue:[
+	    self information:'No class or method selected (cannot search).'.
+	    ^ self
+	]
     ].
 
     (currentMethod notNil
     and:[currentMethod selector == selector]) ifTrue:[
-        searchClass := searchClass superclass.
+	searchClass := searchClass superclass.
     ].
 
     "/ search for the implementaion
     class := searchClass whichClassIncludesSelector:selector.
     class isNil ifTrue:[
-        searchClass isMeta ifTrue:[
-            class := searchClass theNonMetaclass whichClassIncludesSelector:selector.
-        ] ifFalse:[
-            class := searchClass theMetaclass whichClassIncludesSelector:selector.
-        ]
+	searchClass isMeta ifTrue:[
+	    class := searchClass theNonMetaclass whichClassIncludesSelector:selector.
+	] ifFalse:[
+	    class := searchClass theMetaclass whichClassIncludesSelector:selector.
+	]
     ].
 
     "/ cannot switch method in a singleMethod browser ...
     (where isNil and:[navigationState isSingleMethodBrowser])
     ifTrue:[
-        where := #newBuffer.
+	where := #newBuffer.
     ].
 
     class isNil ifTrue:[
-        self information:'None found'.
-    ] ifFalse:[
-        mthd := class compiledMethodAt:selector.
-
-        where isNil ifTrue:[
-            self rememberLocationInHistory.
-            self switchToClass:class selector:selector.
-        ] ifFalse:[
-            self spawnMethodBrowserFor:(Array with:mthd) in:where
-                 label:(resources string:'Response to %1' with:selector)
-        ]
+	self information:'None found'.
+    ] ifFalse:[
+	mthd := class compiledMethodAt:selector.
+
+	where isNil ifTrue:[
+	    self rememberLocationInHistory.
+	    self switchToClass:class selector:selector.
+	] ifFalse:[
+	    self spawnMethodBrowserFor:(Array with:mthd) in:where
+		 label:(resources string:'Response to %1' with:selector)
+	]
     ].
 !
 
@@ -39830,13 +40301,13 @@
     cls := self anySelectedClass.
     mthd := self anySelectedMethod.
     (mthd notNil and:[cls isNil]) ifTrue:[
-        cls := mthd mclass
+	cls := mthd mclass
     ].
     mthd notNil ifTrue:[
-        sel := mthd selector.
-        self class addToBookMarks:cls selector:sel
-    ] ifFalse:[
-        self class addToBookMarks:cls selector:nil
+	sel := mthd selector.
+	self class addToBookMarks:cls selector:sel
+    ] ifFalse:[
+	self class addToBookMarks:cls selector:nil
     ]
 
     "Modified: / 05-05-2011 / 12:20:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -39863,12 +40334,12 @@
      otherwise, a match pattern is allowed and a multi-class browser is opened."
 
     self
-        askForClassToSearch:doWhatByDefault
-        single:singleClass
-        msgTail:''
-        thenDo:[:className :single :doWhat |
-            self findClass:className single:singleClass in:doWhat.
-        ]
+	askForClassToSearch:doWhatByDefault
+	single:singleClass
+	msgTail:''
+	thenDo:[:className :single :doWhat |
+	    self findClass:className single:singleClass in:doWhat.
+	]
 !
 
 searchMenuFindImplementationOf
@@ -39921,50 +40392,50 @@
     title := 'selector to find:\(TAB for completion; matchPattern allowed)'.
 
     box := self
-                listBoxForCodeSelectionTitle:title withCRs
-                isSelector:true
-                okText:'Find'.
+		listBoxForCodeSelectionTitle:title withCRs
+		isSelector:true
+		okText:'Find'.
     box label:(resources string:'find method').
 
-    matchBlock := 
-        [     
-            |searchPattern matchingSelectors|
-
-            searchPattern := box contents.
-            searchPattern includesMatchCharacters ifTrue:[
-                matchingSelectors := Set new.
-                Smalltalk allMethodsWithSelectorDo:[:eachMethod :eachSelector |
-                    (searchPattern match:eachSelector) ifTrue:[
-                        matchingSelectors add:eachSelector.
-                    ].
-                ].
-                box list:(matchingSelectors asOrderedCollection sort).
-                false.
-            ] ifFalse:[
-                true
-            ]
+    matchBlock :=
+	[
+	    |searchPattern matchingSelectors|
+
+	    searchPattern := box contents.
+	    searchPattern includesMatchCharacters ifTrue:[
+		matchingSelectors := Set new.
+		Smalltalk allMethodsWithSelectorDo:[:eachMethod :eachSelector |
+		    (searchPattern match:eachSelector) ifTrue:[
+			matchingSelectors add:eachSelector.
+		    ].
+		].
+		box list:(matchingSelectors asOrderedCollection sort).
+		false.
+	    ] ifFalse:[
+		true
+	    ]
        ].
 
-    entryCompletionBlock := 
-        [:contents |
-            |s what longest matching|
-
-            box topView withWaitCursorDo:[
-                s := contents withoutSpaces.
-                s includesMatchCharacters ifTrue:[
-                    matchBlock value
-                ] ifFalse:[
-                    what := Smalltalk selectorCompletion:s.
-                    longest := what first.
-                    matching := what last.
-                    box list:matching.
-                    box contents:longest.
-                    matching size ~~ 1 ifTrue:[
-                        self window beep
-                    ]
-                ]
-            ]
-        ].
+    entryCompletionBlock :=
+	[:contents |
+	    |s what longest matching|
+
+	    box topView withWaitCursorDo:[
+		s := contents withoutSpaces.
+		s includesMatchCharacters ifTrue:[
+		    matchBlock value
+		] ifFalse:[
+		    what := Smalltalk selectorCompletion:s.
+		    longest := what first.
+		    matching := what last.
+		    box list:matching.
+		    box contents:longest.
+		    matching size ~~ 1 ifTrue:[
+			self window beep
+		    ]
+		]
+	    ]
+	].
     box entryCompletionBlock:entryCompletionBlock.
     box acceptCheck:matchBlock.
     box extent:(300@300).
@@ -39984,49 +40455,49 @@
     ].
 
     [:restart |
-        box 
-            action:[:aString |
-                |browser|
-
-                aString includesMatchCharacters ifFalse:[
-                    openHow == #newBuffer ifTrue:[
-                        browser := self.
-                        browser createBuffer
-                    ] ifFalse:[
-                        openHow == #newBrowser ifTrue:[
-                            browser := self browseMenuClone.
-                        ] ifFalse:[
-                            (self
-                              askIfModified:'Code was modified.\\Switch to that method anyway ?'
-                              default:false
-                              withAccept:false
-                              withCompare:true) ifTrue:[
-                                browser := self.
-                            ].
-                        ]
-                    ].
-                    browser notNil ifTrue:[
-                        browser switchToAnyMethod:aString string.
-                    ]
-                ] ifTrue:[
-                    restart value
-                ]
-            ].
-        box contents size > 0 ifTrue:[
-            entryCompletionBlock value:(box contents).
-        ].
-        box showAtPointer.
+	box
+	    action:[:aString |
+		|browser|
+
+		aString includesMatchCharacters ifFalse:[
+		    openHow == #newBuffer ifTrue:[
+			browser := self.
+			browser createBuffer
+		    ] ifFalse:[
+			openHow == #newBrowser ifTrue:[
+			    browser := self browseMenuClone.
+			] ifFalse:[
+			    (self
+			      askIfModified:'Code was modified.\\Switch to that method anyway ?'
+			      default:false
+			      withAccept:false
+			      withCompare:true) ifTrue:[
+				browser := self.
+			    ].
+			]
+		    ].
+		    browser notNil ifTrue:[
+			browser switchToAnyMethod:aString string.
+		    ]
+		] ifTrue:[
+		    restart value
+		]
+	    ].
+	box contents size > 0 ifTrue:[
+	    entryCompletionBlock value:(box contents).
+	].
+	box showAtPointer.
     ] valueWithRestart
 !
 
 searchMenuFindResponseTo
     self
-        askForSelector:'Search for implementation of (if sent to selected class):'
-        allowBuffer:true
-        allowBrowser:true
-        thenDo:[:selector :whereWanted |
-            self findResponseTo:selector in:whereWanted
-        ]
+	askForSelector:'Search for implementation of (if sent to selected class):'
+	allowBuffer:true
+	allowBrowser:true
+	thenDo:[:selector :whereWanted |
+	    self findResponseTo:selector in:whereWanted
+	]
 !
 
 searchMenuRemoveFromBookmarks
@@ -40039,20 +40510,20 @@
     cls := self anySelectedClass.
     mthd := self anySelectedMethod.
     (mthd notNil and:[cls isNil]) ifTrue:[
-        cls := mthd mclass
+	cls := mthd mclass
     ].
     mthd notNil ifTrue:[
-        sel := mthd selector.
-        meta := cls isMetaclass.
-        cls := cls theNonMetaclass.
-        bookmarks := bookmarks
-                        select:[:each |
-                                    meta ~~ each meta
-                                    or:[each className ~= cls name
-                                    or:[each selector ~= sel]]
-                               ].
-    ] ifFalse:[
-        self warn:'no method selected'
+	sel := mthd selector.
+	meta := cls isMetaclass.
+	cls := cls theNonMetaclass.
+	bookmarks := bookmarks
+			select:[:each |
+				    meta ~~ each meta
+				    or:[each className ~= cls name
+				    or:[each selector ~= sel]]
+			       ].
+    ] ifFalse:[
+	self warn:'no method selected'
     ]
 
     "Modified: / 02-06-2011 / 11:35:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -40067,81 +40538,81 @@
     "/ provide a reasonable default in the pull-down-list
     currentClass := self anySelectedClass.
     currentClass isNil ifTrue:[
-        m := self anySelectedMethod.
-        currentClass := m mclass.
+	m := self anySelectedMethod.
+	currentClass := m mclass.
     ].
 
     LastMethodMoveOrCopyTargetClass notNil ifTrue:[
-        initial := Smalltalk classNamed:LastMethodMoveOrCopyTargetClass.
-        initial notNil ifTrue:[
-            (currentClass notNil and:[currentClass theNonMetaclass name = initial name]) ifTrue:[
-                initial := nil
-            ]
-        ].
-        initial notNil ifTrue:[
-            currentClass isMeta ifTrue:[
-                initial := initial theMetaclass
-            ] ifFalse:[
-                initial := initial theNonMetaclass
-            ].
-            initial := initial name.
-        ].
+	initial := Smalltalk classNamed:LastMethodMoveOrCopyTargetClass.
+	initial notNil ifTrue:[
+	    (currentClass notNil and:[currentClass theNonMetaclass name = initial name]) ifTrue:[
+		initial := nil
+	    ]
+	].
+	initial notNil ifTrue:[
+	    currentClass isMeta ifTrue:[
+		initial := initial theMetaclass
+	    ] ifFalse:[
+		initial := initial theNonMetaclass
+	    ].
+	    initial := initial name.
+	].
     ].
 
     initial isNil ifTrue:[
-        (sup := currentClass superclass) notNil ifTrue:[
-            initial := sup name
-        ] ifFalse:[
-            initial := nil.
-        ].
+	(sup := currentClass superclass) notNil ifTrue:[
+	    initial := sup name
+	] ifFalse:[
+	    initial := nil.
+	].
     ].
 
     supers := currentClass allSuperclasses reverse.
     currentClass isMeta ifTrue:[
-        supers := supers select:[:each | each isSubclassOf:Class].
+	supers := supers select:[:each | each isSubclassOf:Class].
     ].
     supers := supers collect:[:cls | cls name].
 
     subs := (currentClass allSubclasses collect:[:cls | cls name]).
     list := OrderedCollection withAll:supers.
     (supers notEmpty and:[subs notEmpty]) ifTrue:[
-        list add:'---- '; add:currentClass name; add:' ----'
+	list add:'---- '; add:currentClass name; add:' ----'
     ].
     list addAll:(subs sort).
 
     doWhat == #copy ifTrue:[
-        reqString := 'Copy selected method(s) to which class ?\(enter ''Foo class'' to copy to Metaclass)'.
-        okLabel := 'Copy'.
-        title := 'Copy method(s)'.
-    ] ifFalse:[
-        okLabel := 'Move'.
-        title := 'Move method(s)'.
-        doWhat == #move ifTrue:[
-            reqString := 'Move selected method(s) to which class ?\(enter ''Foo class'' to move to Metaclass)'.
-        ] ifFalse:[
-            doWhat == #moveAndForward ifTrue:[
-                reqString := 'Move selected method(s) to which class ?'.
-            ] ifFalse:[
-                self error:'unknown aspect: ', doWhat printString.
-            ].
-        ].
+	reqString := 'Copy selected method(s) to which class ?\(enter ''Foo class'' to copy to Metaclass)'.
+	okLabel := 'Copy'.
+	title := 'Copy method(s)'.
+    ] ifFalse:[
+	okLabel := 'Move'.
+	title := 'Move method(s)'.
+	doWhat == #move ifTrue:[
+	    reqString := 'Move selected method(s) to which class ?\(enter ''Foo class'' to move to Metaclass)'.
+	] ifFalse:[
+	    doWhat == #moveAndForward ifTrue:[
+		reqString := 'Move selected method(s) to which class ?'.
+	    ] ifFalse:[
+		self error:'unknown aspect: ', doWhat printString.
+	    ].
+	].
     ].
 
     newClassName := Dialog
-                    request:(resources string:reqString) withCRs
-                    initialAnswer:(initial ? '')
-                    okLabel:(resources string:okLabel)
-                    title:(resources string:title)
-                    onCancel:nil
-                    list:list               
-                    entryCompletionBlock:(DoWhatIMeanSupport classNameEntryCompletionBlock).
+		    request:(resources string:reqString) withCRs
+		    initialAnswer:(initial ? '')
+		    okLabel:(resources string:okLabel)
+		    title:(resources string:title)
+		    onCancel:nil
+		    list:list
+		    entryCompletionBlock:(DoWhatIMeanSupport classNameEntryCompletionBlock).
 
     newClassName isNil ifTrue:[^ nil].
     (newClassName startsWith:'---- ') ifTrue:[^ nil].
 
     newClass := self classIfValidNonMetaClassName:newClassName.
     newClass isNil ifTrue:[
-        ^ nil
+	^ nil
     ].
 
     LastMethodMoveOrCopyTargetClass := newClass theNonMetaclass name.
@@ -40163,23 +40634,23 @@
 
     source1 := m1 source string.
     source1 isNil ifTrue:[
-        self warn:'Oops - methods source is gone. Cannot compare source.'.
-        ^ self
+	self warn:'Oops - methods source is gone. Cannot compare source.'.
+	^ self
     ].
     source2 := m2 source string.
     source2 isNil ifTrue:[
-        self warn:'Oops - methods source is gone. Cannot compare source.'.
-        ^ self
+	self warn:'Oops - methods source is gone. Cannot compare source.'.
+	^ self
     ].
 
     m1Class := m1 mclass.
     m2Class := m2 mclass.
 
     v := DiffCodeView
-            openOn:source1
-            label:(m1Class name , ' ' , (m1 printStringForBrowserWithSelector:m1 selector inClass:m1Class))
-            and:source2
-            label:(m2Class name , ' ' , (m2 printStringForBrowserWithSelector:m2 selector inClass:m2Class)).
+	    openOn:source1
+	    label:(m1Class name , ' ' , (m1 printStringForBrowserWithSelector:m1 selector inClass:m1Class))
+	    and:source2
+	    label:(m2Class name , ' ' , (m2 printStringForBrowserWithSelector:m2 selector inClass:m2Class)).
     v label:label.
     v waitUntilVisible.
     ^ self
@@ -40198,125 +40669,125 @@
      isExtension title labelA labelB|
 
     self withWaitCursorDo:[
-        Method flushSourceStreamCache.
-
-        methods do:[:eachMethod |
-            |classPackage methodPackage|
-
-            mclass := eachMethod mclass.
-            mclass isNil ifTrue:[
-                self warn:('Cannot find methods class (obsolete).').
-            ] ifFalse:[
-                classPackage := mclass package.
-                methodPackage := eachMethod package.
-                (classPackage == methodPackage or:[ methodPackage == PackageId noProjectID ]) ifTrue:[
-                    theNonMetaclass := mclass theNonMetaclass.
-                    isExtension := false.
-                ] ifFalse:[
-                    isExtension := true.
-                ].
-
-                mselector := eachMethod selector.
-
-                currentSource := eachMethod source asString.
-                current := ChangeSet new.
-                current addMethodChange:eachMethod in:mclass.
-
-                self busyLabel:'getting repository source...' with:nil.
-
-                isExtension ifTrue:[
-                    repositoryChangeSet := SourceCodeManagerUtilities
-                                                 changeSetForExtensionMethodsForPackage:methodPackage
-                                                 askForRevision:false
-                                                 usingManager:SourceCodeManager.
-                    repositoryChangeSet := repositoryChangeSet
-                                    select:[:eachChange | eachChange isMethodChange
-                                                          and:[eachChange selector = mselector
-                                                          and:[eachChange className = mclass name]]].
-                    lastClass := nil.
-                ] ifFalse:[
-                    (lastClass ~~ theNonMetaclass) ifTrue:[
-                        aStream := self sourceStreamForRepositorySourceOfClass:theNonMetaclass.
-                        aStream notNil ifTrue:[
-                            aStream class readErrorSignal handle:[:ex |
-                                self warn:('read error while reading extracted source\\' , ex description) withCRs.
-                                aStream close.
-                                comparedSource := nil.
-                            ] do:[
-                                comparedSource := aStream contents asString.
-                            ].
-                            aStream close.
-
-                            thisRevString := theNonMetaclass revision.
-                            thisRevString isNil ifTrue:[
-                                thisRevString := 'no revision'
-                            ].
-
-                            lastRepositoryChangeSet := ChangeSet fromStream:(s := comparedSource readStream). s close.
-                            lastClass := theNonMetaclass.
-
-                            self busyLabel:'comparing...' with:nil.
-                        ].
-                    ].
-                    repositoryChangeSet := (lastRepositoryChangeSet ? #())
-                                    select:[:eachChange | eachChange isMethodChange
-                                                          and:[eachChange selector = mselector
-                                                          and:[eachChange className = mclass name]]].
-                ].
-                repositoryChangeSet notEmptyOrNil ifTrue:[
-                    diffs := repositoryChangeSet diffSetsAgainst:current.
-                ].
-                allDiffs isNil ifTrue:[
-                    allDiffs := diffs.
-                ] ifFalse:[
-                    allDiffs changed addAll:(diffs changed).
-                    allDiffs onlyInArg addAll:(diffs onlyInArg).
-                    allDiffs onlyInReceiver addAll:(diffs onlyInReceiver).
-                ].
-            ].
-        ].
+	Method flushSourceStreamCache.
+
+	methods do:[:eachMethod |
+	    |classPackage methodPackage|
+
+	    mclass := eachMethod mclass.
+	    mclass isNil ifTrue:[
+		self warn:('Cannot find methods class (obsolete).').
+	    ] ifFalse:[
+		classPackage := mclass package.
+		methodPackage := eachMethod package.
+		(classPackage == methodPackage or:[ methodPackage == PackageId noProjectID ]) ifTrue:[
+		    theNonMetaclass := mclass theNonMetaclass.
+		    isExtension := false.
+		] ifFalse:[
+		    isExtension := true.
+		].
+
+		mselector := eachMethod selector.
+
+		currentSource := eachMethod source asString.
+		current := ChangeSet new.
+		current addMethodChange:eachMethod in:mclass.
+
+		self busyLabel:'getting repository source...' with:nil.
+
+		isExtension ifTrue:[
+		    repositoryChangeSet := SourceCodeManagerUtilities
+						 changeSetForExtensionMethodsForPackage:methodPackage
+						 askForRevision:false
+						 usingManager:SourceCodeManager.
+		    repositoryChangeSet := repositoryChangeSet
+				    select:[:eachChange | eachChange isMethodChange
+							  and:[eachChange selector = mselector
+							  and:[eachChange className = mclass name]]].
+		    lastClass := nil.
+		] ifFalse:[
+		    (lastClass ~~ theNonMetaclass) ifTrue:[
+			aStream := self sourceStreamForRepositorySourceOfClass:theNonMetaclass.
+			aStream notNil ifTrue:[
+			    aStream class readErrorSignal handle:[:ex |
+				self warn:('read error while reading extracted source\\' , ex description) withCRs.
+				aStream close.
+				comparedSource := nil.
+			    ] do:[
+				comparedSource := aStream contents asString.
+			    ].
+			    aStream close.
+
+			    thisRevString := theNonMetaclass revision.
+			    thisRevString isNil ifTrue:[
+				thisRevString := 'no revision'
+			    ].
+
+			    lastRepositoryChangeSet := ChangeSet fromStream:(s := comparedSource readStream). s close.
+			    lastClass := theNonMetaclass.
+
+			    self busyLabel:'comparing...' with:nil.
+			].
+		    ].
+		    repositoryChangeSet := (lastRepositoryChangeSet ? #())
+				    select:[:eachChange | eachChange isMethodChange
+							  and:[eachChange selector = mselector
+							  and:[eachChange className = mclass name]]].
+		].
+		repositoryChangeSet notEmptyOrNil ifTrue:[
+		    diffs := repositoryChangeSet diffSetsAgainst:current.
+		].
+		allDiffs isNil ifTrue:[
+		    allDiffs := diffs.
+		] ifFalse:[
+		    allDiffs changed addAll:(diffs changed).
+		    allDiffs onlyInArg addAll:(diffs onlyInArg).
+		    allDiffs onlyInReceiver addAll:(diffs onlyInReceiver).
+		].
+	    ].
+	].
     ].
 
     (allDiffs isNil or:[allDiffs isEmpty]) ifTrue:[
-        (methods
-            contains:[:m |
-                ChangeSet current includesChangeForClass:m mclass selector:m selector
-            ]
-        ) ifTrue:[
-            (self confirm:'Versions are identical.\\Remove entries from changeSet ?' withCRs)
-            ifTrue:[
-                methods do:[:m |
-                    ChangeSet current condenseChangesForClass:m mclass selector:m selector.
-                ].
-            ].
-        ] ifFalse:[
-            self information:'Versions are identical.'.
-        ].
-        ^ self.
+	(methods
+	    contains:[:m |
+		ChangeSet current includesChangeForClass:m mclass selector:m selector
+	    ]
+	) ifTrue:[
+	    (self confirm:'Versions are identical.\\Remove entries from changeSet ?' withCRs)
+	    ifTrue:[
+		methods do:[:m |
+		    ChangeSet current condenseChangesForClass:m mclass selector:m selector.
+		].
+	    ].
+	] ifFalse:[
+	    self information:'Versions are identical.'.
+	].
+	^ self.
     ].
 
     title := methods size == 1
-                ifTrue:['Difference of %1' bindWith:methods first whoString]
-                ifFalse:['Differences of %1 classes' bindWith:methods size].
+		ifTrue:['Difference of %1' bindWith:methods first whoString]
+		ifFalse:['Differences of %1 classes' bindWith:methods size].
 
     labelA := 'Repository'.
     labelB := 'Image'.
 
     (methods collect:[:m | m mclass theNonMetaclass]) asSet size == 1 ifTrue:[
-        "/ all methods of the same class
-        (methods collect:[:m | m package]) asSet size == 1 ifTrue:[
-            "/ all methods from the same package (source container)
-            labelA := 'Repository (%1)' bindWith:(thisRevString ? '?').
-            labelB := 'Image (based on %1)' bindWith:(methods first mclass theNonMetaclass revision).
-        ].
+	"/ all methods of the same class
+	(methods collect:[:m | m package]) asSet size == 1 ifTrue:[
+	    "/ all methods from the same package (source container)
+	    labelA := 'Repository (%1)' bindWith:(thisRevString ? '?').
+	    labelB := 'Image (based on %1)' bindWith:(methods first mclass theNonMetaclass revision).
+	].
     ].
 
     VersionDiffBrowser
-        openOnDiffSet:allDiffs
-        labelA:labelA
-        labelB:labelB
-        title:title
-        ignoreExtensions:false.
+	openOnDiffSet:allDiffs
+	labelA:labelA
+	labelB:labelB
+	title:title
+	ignoreExtensions:false.
 
     self normalLabel.
 
@@ -40337,125 +40808,125 @@
      isExtension title labelA labelB|
 
     self withWaitCursorDo:[
-        Method flushSourceStreamCache.
-
-        methods do:[:eachMethod |
-            |classPackage methodPackage|
-
-            mclass := eachMethod mclass.
-            mclass isNil ifTrue:[
-                self warn:('Cannot find methods class (obsolete).').
-            ] ifFalse:[
-                classPackage := mclass package.
-                methodPackage := eachMethod package.
-                (classPackage == methodPackage or:[ methodPackage == PackageId noProjectID ]) ifTrue:[
-                    theNonMetaclass := mclass theNonMetaclass.
-                    isExtension := false.
-                ] ifFalse:[
-                    isExtension := true.
-                ].
-
-                mselector := eachMethod selector.
-
-                currentSource := eachMethod source asString.
-                current := ChangeSet new.
-                current addMethodChange:eachMethod in:mclass.
-
-                self busyLabel:'getting repository source...' with:nil.
-
-                isExtension ifTrue:[
-                    repositoryChangeSet := manager utilities
-                                                 changeSetForExtensionMethodsForPackage:methodPackage
-                                                 askForRevision:false
-                                                 usingManager:manager.
-                    repositoryChangeSet := repositoryChangeSet
-                                    select:[:eachChange | eachChange isMethodChange
-                                                          and:[eachChange selector = mselector
-                                                          and:[eachChange className = mclass name]]].
-                    lastClass := nil.
-                ] ifFalse:[
-                    (lastClass ~~ theNonMetaclass) ifTrue:[
-                        aStream := self sourceStreamForRepositorySourceOfClass:theNonMetaclass.
-                        aStream notNil ifTrue:[
-                            aStream class readErrorSignal handle:[:ex |
-                                self warn:('read error while reading extracted source\\' , ex description) withCRs.
-                                aStream close.
-                                comparedSource := nil.
-                            ] do:[
-                                comparedSource := aStream contents asString.
-                            ].
-                            aStream close.
-
-                            thisRevString := theNonMetaclass revision.
-                            thisRevString isNil ifTrue:[
-                                thisRevString := 'no revision'
-                            ].
-
-                            lastRepositoryChangeSet := ChangeSet fromStream:(s := comparedSource readStream). s close.
-                            lastClass := theNonMetaclass.
-
-                            self busyLabel:'comparing...' with:nil.
-                        ].
-                    ].
-                    repositoryChangeSet := (lastRepositoryChangeSet ? #())
-                                    select:[:eachChange | eachChange isMethodChange
-                                                          and:[eachChange selector = mselector
-                                                          and:[eachChange className = mclass name]]].
-                ].
-                repositoryChangeSet notEmptyOrNil ifTrue:[
-                    diffs := repositoryChangeSet diffSetsAgainst:current.
-                ].
-                allDiffs isNil ifTrue:[
-                    allDiffs := diffs.
-                ] ifFalse:[
-                    allDiffs changed addAll:(diffs changed).
-                    allDiffs onlyInArg addAll:(diffs onlyInArg).
-                    allDiffs onlyInReceiver addAll:(diffs onlyInReceiver).
-                ].
-            ].
-        ].
+	Method flushSourceStreamCache.
+
+	methods do:[:eachMethod |
+	    |classPackage methodPackage|
+
+	    mclass := eachMethod mclass.
+	    mclass isNil ifTrue:[
+		self warn:('Cannot find methods class (obsolete).').
+	    ] ifFalse:[
+		classPackage := mclass package.
+		methodPackage := eachMethod package.
+		(classPackage == methodPackage or:[ methodPackage == PackageId noProjectID ]) ifTrue:[
+		    theNonMetaclass := mclass theNonMetaclass.
+		    isExtension := false.
+		] ifFalse:[
+		    isExtension := true.
+		].
+
+		mselector := eachMethod selector.
+
+		currentSource := eachMethod source asString.
+		current := ChangeSet new.
+		current addMethodChange:eachMethod in:mclass.
+
+		self busyLabel:'getting repository source...' with:nil.
+
+		isExtension ifTrue:[
+		    repositoryChangeSet := manager utilities
+						 changeSetForExtensionMethodsForPackage:methodPackage
+						 askForRevision:false
+						 usingManager:manager.
+		    repositoryChangeSet := repositoryChangeSet
+				    select:[:eachChange | eachChange isMethodChange
+							  and:[eachChange selector = mselector
+							  and:[eachChange className = mclass name]]].
+		    lastClass := nil.
+		] ifFalse:[
+		    (lastClass ~~ theNonMetaclass) ifTrue:[
+			aStream := self sourceStreamForRepositorySourceOfClass:theNonMetaclass.
+			aStream notNil ifTrue:[
+			    aStream class readErrorSignal handle:[:ex |
+				self warn:('read error while reading extracted source\\' , ex description) withCRs.
+				aStream close.
+				comparedSource := nil.
+			    ] do:[
+				comparedSource := aStream contents asString.
+			    ].
+			    aStream close.
+
+			    thisRevString := theNonMetaclass revision.
+			    thisRevString isNil ifTrue:[
+				thisRevString := 'no revision'
+			    ].
+
+			    lastRepositoryChangeSet := ChangeSet fromStream:(s := comparedSource readStream). s close.
+			    lastClass := theNonMetaclass.
+
+			    self busyLabel:'comparing...' with:nil.
+			].
+		    ].
+		    repositoryChangeSet := (lastRepositoryChangeSet ? #())
+				    select:[:eachChange | eachChange isMethodChange
+							  and:[eachChange selector = mselector
+							  and:[eachChange className = mclass name]]].
+		].
+		repositoryChangeSet notEmptyOrNil ifTrue:[
+		    diffs := repositoryChangeSet diffSetsAgainst:current.
+		].
+		allDiffs isNil ifTrue:[
+		    allDiffs := diffs.
+		] ifFalse:[
+		    allDiffs changed addAll:(diffs changed).
+		    allDiffs onlyInArg addAll:(diffs onlyInArg).
+		    allDiffs onlyInReceiver addAll:(diffs onlyInReceiver).
+		].
+	    ].
+	].
     ].
 
     (allDiffs isNil or:[allDiffs isEmpty]) ifTrue:[
-        (methods
-            contains:[:m |
-                ChangeSet current includesChangeForClass:m mclass selector:m selector
-            ]
-        ) ifTrue:[
-            (self confirm:'Versions are identical.\\Remove entries from changeSet ?' withCRs)
-            ifTrue:[
-                methods do:[:m |
-                    ChangeSet current condenseChangesForClass:m mclass selector:m selector.
-                ].
-            ].
-        ] ifFalse:[
-            self information:'Versions are identical.'.
-        ].
-        ^ self.
+	(methods
+	    contains:[:m |
+		ChangeSet current includesChangeForClass:m mclass selector:m selector
+	    ]
+	) ifTrue:[
+	    (self confirm:'Versions are identical.\\Remove entries from changeSet ?' withCRs)
+	    ifTrue:[
+		methods do:[:m |
+		    ChangeSet current condenseChangesForClass:m mclass selector:m selector.
+		].
+	    ].
+	] ifFalse:[
+	    self information:'Versions are identical.'.
+	].
+	^ self.
     ].
 
     title := methods size == 1
-                ifTrue:['Difference of %1' bindWith:methods first whoString]
-                ifFalse:['Differences of %1 classes' bindWith:methods size].
+		ifTrue:['Difference of %1' bindWith:methods first whoString]
+		ifFalse:['Differences of %1 classes' bindWith:methods size].
 
     labelA := 'Repository'.
     labelB := 'Image'.
 
     (methods collect:[:m | m mclass theNonMetaclass]) asSet size == 1 ifTrue:[
-        "/ all methods of the same class
-        (methods collect:[:m | m package]) asSet size == 1 ifTrue:[
-            "/ all methods from the same package (source container)
-            labelA := 'Repository (%1)' bindWith:(thisRevString ? '?').
-            labelB := 'Image (based on %1)' bindWith:(methods first mclass theNonMetaclass revision).
-        ].
+	"/ all methods of the same class
+	(methods collect:[:m | m package]) asSet size == 1 ifTrue:[
+	    "/ all methods from the same package (source container)
+	    labelA := 'Repository (%1)' bindWith:(thisRevString ? '?').
+	    labelB := 'Image (based on %1)' bindWith:(methods first mclass theNonMetaclass revision).
+	].
     ].
 
     VersionDiffBrowser
-        openOnDiffSet:allDiffs
-        labelA:labelA
-        labelB:labelB
-        title:title
-        ignoreExtensions:false.
+	openOnDiffSet:allDiffs
+	labelA:labelA
+	labelB:labelB
+	title:title
+	ignoreExtensions:false.
 
     self normalLabel.
 
@@ -40481,13 +40952,13 @@
     methods := IdentitySet new.
     numVersionMethods := 0.
     methodsToRemove do:[:eachMethod |
-        classes add:(eachMethod mclass).
-        methods add:eachMethod.
-        (AbstractSourceCodeManager isVersionMethodSelector:eachMethod selector) ifTrue:[
-            eachMethod mclass isMeta ifTrue:[
-                numVersionMethods := numVersionMethods + 1
-            ]
-        ]
+	classes add:(eachMethod mclass).
+	methods add:eachMethod.
+	(AbstractSourceCodeManager isVersionMethodSelector:eachMethod selector) ifTrue:[
+	    eachMethod mclass isMeta ifTrue:[
+		numVersionMethods := numVersionMethods + 1
+	    ]
+	]
     ].
     numClasses := classes size.
     numMethods := methodsToRemove value size.
@@ -40495,55 +40966,55 @@
     numMethods == 0 ifTrue:[^ self].
 
     numMethods == 1 ifTrue:[
-        msg := 'Really remove ''%3'' from ''%4'' ?'.
-    ] ifFalse:[
-        (methods collect:[:m | m selector]) size == 1 ifTrue:[
-            msg := 'Really remove ''%3'''.
-        ] ifFalse:[
-            msg := 'Really remove %1 methods'.
-        ].
-        numClasses > 1 ifTrue:[
-            msg := msg , ' from %2 classes'
-        ] ifFalse:[
-            msg := msg , ' from ''%4'''
-        ].
-        msg := msg , ' ?'
+	msg := 'Really remove ''%3'' from ''%4'' ?'.
+    ] ifFalse:[
+	(methods collect:[:m | m selector]) size == 1 ifTrue:[
+	    msg := 'Really remove ''%3'''.
+	] ifFalse:[
+	    msg := 'Really remove %1 methods'.
+	].
+	numClasses > 1 ifTrue:[
+	    msg := msg , ' from %2 classes'
+	] ifFalse:[
+	    msg := msg , ' from ''%4'''
+	].
+	msg := msg , ' ?'
     ].
     classes notEmpty ifTrue:[
-        firstClassName := classes first name
-    ] ifFalse:[
-        firstClassName := '???'
+	firstClassName := classes first name
+    ] ifFalse:[
+	firstClassName := '???'
     ].
     msg := resources
-                string:msg
-                with:numMethods printString
-                with:numClasses printString
-                with:(methods first selector ? '?') allBold
-                with:firstClassName allBold.
+		string:msg
+		with:numMethods printString
+		with:numClasses printString
+		with:(methods first selector ? '?') allBold
+		with:firstClassName allBold.
 
     numVersionMethods > 0 ifTrue:[
-        msg := msg , '\\' ,
-               (resources
-                string:'ATTENTION: Removing a classes version method might make the versionManagers life hard.' allBold).
-
-        (OptionBox
-                      request:msg withCRs
-                      label:(resources string:'Attention')
-                      image:(WarningBox iconBitmap)
-                      buttonLabels:(resources array:#('Cancel' 'Remove'))
-                      values:#(false true)
-                      default:false
-                      onCancel:false) ifFalse:[^ self].
-
-    ] ifFalse:[
-        (self confirm:msg withCRs) ifFalse:[^ self].
+	msg := msg , '\\' ,
+	       (resources
+		string:'ATTENTION: Removing a classes version method might make the versionManagers life hard.' allBold).
+
+	(OptionBox
+		      request:msg withCRs
+		      label:(resources string:'Attention')
+		      image:(WarningBox iconBitmap)
+		      buttonLabels:(resources array:#('Cancel' 'Remove'))
+		      values:#(false true)
+		      default:false
+		      onCancel:false) ifFalse:[^ self].
+
+    ] ifFalse:[
+	(self confirm:msg withCRs) ifFalse:[^ self].
     ].
 
     classes := methods := nil.
 
     "/ then, remove them
     self withWaitCursorDo:[
-        self doRemoveSelectedMethodsUnconfirmed.
+	self doRemoveSelectedMethodsUnconfirmed.
     ]
 !
 
@@ -40556,21 +41027,21 @@
     numMethods == 0 ifTrue:[^ self].
 
     (self canUseRefactoringSupport) ifTrue:[
-        numMethods > 1 ifTrue:[
-            change := CompositeRefactoryChange named:('Remove ', numMethods printString , ' methods').
-            methods do:[:eachMethod |
-                change removeMethod:(eachMethod selector) from:(eachMethod mclass)
-            ].
-        ] ifFalse:[
-            mthd := methods first.
-            change := RemoveMethodChange remove:(mthd selector) from:(mthd mclass)
-        ].
-
-        RefactoryChangeManager performChange: change
-    ] ifFalse:[
-        methods do:[:eachMethod |
-            (eachMethod mclass) removeSelector:(eachMethod selector).
-        ].
+	numMethods > 1 ifTrue:[
+	    change := CompositeRefactoryChange named:('Remove ', numMethods printString , ' methods').
+	    methods do:[:eachMethod |
+		change removeMethod:(eachMethod selector) from:(eachMethod mclass)
+	    ].
+	] ifFalse:[
+	    mthd := methods first.
+	    change := RemoveMethodChange remove:(mthd selector) from:(mthd mclass)
+	].
+
+	RefactoryChangeManager performChange: change
+    ] ifFalse:[
+	methods do:[:eachMethod |
+	    (eachMethod mclass) removeSelector:(eachMethod selector).
+	].
     ]
 !
 
@@ -40594,23 +41065,23 @@
     stillAsking := true.
 
     [stillAsking] whileTrue:[
-        saveName := self
-                        fileNameDialogForFileOut:(resources string:(boxTitleOrNil ? 'FileOut methods as:'))
-                        default:defaultName.
-
-        saveName isNil ifTrue:[
-            ^ self
-        ].
-
-        saveName isEmpty ifTrue:[       "/ can no longer happen ...
-            (self confirm:'Bad name given - try again ?') ifFalse:[
-                ^ self.
-            ].
-            stillAsking := true.
-        ] ifFalse:[
-            FileSelectionBox lastFileSelectionDirectory:(saveName asFilename directoryName).
-            stillAsking := false.
-        ].
+	saveName := self
+			fileNameDialogForFileOut:(resources string:(boxTitleOrNil ? 'FileOut methods as:'))
+			default:defaultName.
+
+	saveName isNil ifTrue:[
+	    ^ self
+	].
+
+	saveName isEmpty ifTrue:[       "/ can no longer happen ...
+	    (self confirm:'Bad name given - try again ?') ifFalse:[
+		^ self.
+	    ].
+	    stillAsking := true.
+	] ifFalse:[
+	    FileSelectionBox lastFileSelectionDirectory:(saveName asFilename directoryName).
+	    stillAsking := false.
+	].
     ].
 
     self busyLabel:'saving...'.
@@ -40626,59 +41097,59 @@
 
     self busyLabel:'saving...'.
     Class fileOutErrorSignal
-        handle:[:ex |
-            self warn:'Cannot fileOut\(%2)' with:ex description.
-            self normalLabel.
-            ex return.
-        ] do:[
-            formatSymbolOrNil == #sif ifTrue:[
-                (SmalltalkInterchangeFileManager newForFileOut)
-                    fileName:aFilename;
-                    addMethods:aCollectionOfMethods;
-                    fileOut
-            ] ifFalse:[
-                fileName := aFilename asFilename.
-
-                "
-                 if file exists, save original in a .sav file
-                "
-                fileName exists ifTrue:[
-                    fileName copyTo:(fileName withSuffix:'sav')
-                ].
-                [
-                    aStream := fileName newReadWriteStream.
-                ] on:FileStream openErrorSignal do:[:ex|
-                    ^ self warn:('Cannot create file:', fileName name)
-                ].
-
-                (formatSymbolOrNil ~~ #xml
-                and:[formatSymbolOrNil ~~ #binary]) ifTrue:[
-                    aStream := EncodedStream stream:aStream encoder:(CharacterEncoder encoderForUTF8).
-                    aStream nextPutLine:'"{ Encoding: utf8 }" !!'.
-                ].
-
-                aCollectionOfMethods do:[:aMethod |
-                    formatSymbolOrNil == #xml ifTrue:[
-                        aMethod mclass fileOutXMLMethod:aMethod on:aStream
-                    ] ifFalse:[
-                        formatSymbolOrNil == #binary ifTrue:[
-                            self shouldImplement. "unimplemented: binary fileout"
-                            "/ aClass binaryFileOutOn:(saveName asFilename writeStream binary)
-                        ] ifFalse:[
-                            withPackage ifTrue:[
-                                lastPackage ~= aMethod package ifTrue:[
-                                    lastPackage := aMethod package.
-                                    aStream nextPutAll:('"{ Package: ''%1'' }" !!\\' bindWith:(lastPackage)) withCRs.
-                                ].
-                            ].
-                            aMethod mclass fileOutMethod:aMethod on:aStream.
-                            aStream cr.
-                        ]
-                    ]
-                ].
-                aStream close
-            ]
-        ].
+	handle:[:ex |
+	    self warn:'Cannot fileOut\(%2)' with:ex description.
+	    self normalLabel.
+	    ex return.
+	] do:[
+	    formatSymbolOrNil == #sif ifTrue:[
+		(SmalltalkInterchangeFileManager newForFileOut)
+		    fileName:aFilename;
+		    addMethods:aCollectionOfMethods;
+		    fileOut
+	    ] ifFalse:[
+		fileName := aFilename asFilename.
+
+		"
+		 if file exists, save original in a .sav file
+		"
+		fileName exists ifTrue:[
+		    fileName copyTo:(fileName withSuffix:'sav')
+		].
+		[
+		    aStream := fileName newReadWriteStream.
+		] on:FileStream openErrorSignal do:[:ex|
+		    ^ self warn:('Cannot create file:', fileName name)
+		].
+
+		(formatSymbolOrNil ~~ #xml
+		and:[formatSymbolOrNil ~~ #binary]) ifTrue:[
+		    aStream := EncodedStream stream:aStream encoder:(CharacterEncoder encoderForUTF8).
+		    aStream nextPutLine:'"{ Encoding: utf8 }" !!'.
+		].
+
+		aCollectionOfMethods do:[:aMethod |
+		    formatSymbolOrNil == #xml ifTrue:[
+			aMethod mclass fileOutXMLMethod:aMethod on:aStream
+		    ] ifFalse:[
+			formatSymbolOrNil == #binary ifTrue:[
+			    self shouldImplement. "unimplemented: binary fileout"
+			    "/ aClass binaryFileOutOn:(saveName asFilename writeStream binary)
+			] ifFalse:[
+			    withPackage ifTrue:[
+				lastPackage ~= aMethod package ifTrue:[
+				    lastPackage := aMethod package.
+				    aStream nextPutAll:('"{ Package: ''%1'' }" !!\\' bindWith:(lastPackage)) withCRs.
+				].
+			    ].
+			    aMethod mclass fileOutMethod:aMethod on:aStream.
+			    aStream cr.
+			]
+		    ]
+		].
+		aStream close
+	    ]
+	].
     self normalLabel
 !
 
@@ -40689,13 +41160,13 @@
 
     cls := self theSingleSelectedClass.
     cls isNil ifTrue:[
-        classes := self selectedClassesValue.
-        classes notEmptyOrNil ifTrue:[
-            cls := classes first.
-        ]
+	classes := self selectedClassesValue.
+	classes notEmptyOrNil ifTrue:[
+	    cls := classes first.
+	]
     ].
     cls notNil ifTrue:[
-        ^ cls programmingLanguage methodTemplate
+	^ cls programmingLanguage methodTemplate
     ].
     ^ SystemBrowser methodTemplate
 
@@ -40737,38 +41208,38 @@
     numMethods := methods size.
 
     (self canUseRefactoringSupport and:[numMethods > 1]) ifTrue:[
-        change := CompositeRefactoryChange named:('Move ', numMethods printString , ' methods to project ' , newProject).
-        methods do:[:eachMethod |
-            |mClass|
-            mClass := eachMethod mclass.
-            change
-                changeProjectOf:(eachMethod selector)
-                in:mClass
-                to:newProject.
-        ].
-        RefactoryChangeManager performChange: change.
-    ] ifFalse:[
-        methods do:[:eachMethod |
-            |mClass|
-            mClass := eachMethod mclass.
-            self canUseRefactoringSupport ifTrue:[
-                change := RefactoryMethodProjectChange
-                    changeProjectOf:(eachMethod selector)
-                    in:mClass
-                    to:newProject.
-                RefactoryChangeManager performChange: change.
-            ] ifFalse:[
-                eachMethod package:newProject.
-            ].
-            classesChanged add:eachMethod mclass.
-        ].
+	change := CompositeRefactoryChange named:('Move ', numMethods printString , ' methods to project ' , newProject).
+	methods do:[:eachMethod |
+	    |mClass|
+	    mClass := eachMethod mclass.
+	    change
+		changeProjectOf:(eachMethod selector)
+		in:mClass
+		to:newProject.
+	].
+	RefactoryChangeManager performChange: change.
+    ] ifFalse:[
+	methods do:[:eachMethod |
+	    |mClass|
+	    mClass := eachMethod mclass.
+	    self canUseRefactoringSupport ifTrue:[
+		change := RefactoryMethodProjectChange
+		    changeProjectOf:(eachMethod selector)
+		    in:mClass
+		    to:newProject.
+		RefactoryChangeManager performChange: change.
+	    ] ifFalse:[
+		eachMethod package:newProject.
+	    ].
+	    classesChanged add:eachMethod mclass.
+	].
     ].
 
     self rememberLastProjectMoveTo:newProject.
 
     classesChanged do:[:eachClass |
-        eachClass changed:#projectOrganization.
-        Smalltalk changed:#projectOrganization with:(Array with:eachClass theNonMetaclass with:(methods select:[:m | m mclass == eachClass])).
+	eachClass changed:#projectOrganization.
+	Smalltalk changed:#projectOrganization with:(Array with:eachClass theNonMetaclass with:(methods select:[:m | m mclass == eachClass])).
     ].
 
     "Created: / 17-02-2000 / 23:04:45 / cg"
@@ -40786,32 +41257,32 @@
     numMethods := methods size.
 
     (self canUseRefactoringSupport and:[numMethods > 1]) ifTrue:[
-        change := CompositeRefactoryChange named:('Change category of ', numMethods printString , ' methods').
-        methods do:[:eachMethod |
-            |mClass|
-            mClass := eachMethod mclass.
-
-            change
-                changeCategoryOf:(eachMethod selector)
-                in:mClass
-                to:newCategory.
-        ].
-        RefactoryChangeManager performChange: change.
-    ] ifFalse:[
-        methods do:[:mthd |
-            |mClass|
-            mClass := mthd mclass.
-
-            (self canUseRefactoringSupport) ifTrue:[
-                change := RefactoryMethodCategoryChange
-                    changeCategoryOf:(mthd selector)
-                    in:mClass
-                    to:newCategory.
-                RefactoryChangeManager performChange: change.
-            ] ifFalse:[
-                mthd category:newCategory.
-            ].
-        ].
+	change := CompositeRefactoryChange named:('Change category of ', numMethods printString , ' methods').
+	methods do:[:eachMethod |
+	    |mClass|
+	    mClass := eachMethod mclass.
+
+	    change
+		changeCategoryOf:(eachMethod selector)
+		in:mClass
+		to:newCategory.
+	].
+	RefactoryChangeManager performChange: change.
+    ] ifFalse:[
+	methods do:[:mthd |
+	    |mClass|
+	    mClass := mthd mclass.
+
+	    (self canUseRefactoringSupport) ifTrue:[
+		change := RefactoryMethodCategoryChange
+		    changeCategoryOf:(mthd selector)
+		    in:mClass
+		    to:newCategory.
+		RefactoryChangeManager performChange: change.
+	    ] ifFalse:[
+		mthd category:newCategory.
+	    ].
+	].
     ].
 
     "Modified: / 23-11-2006 / 17:00:01 / cg"
@@ -40830,131 +41301,131 @@
 
     canUseRefactoringSupport := self canUseRefactoringSupport.
     canUseRefactoringSupport ifTrue:[
-        nm := (doWhat == #copy)
-                ifTrue:['Copy %1 to %2']
-                ifFalse:[
-                    (doWhat == #moveAndForward)
-                        ifTrue:['Move with Forwarding %1 to %2']
-                        ifFalse:['Move %1 to %2']].
-        nm := nm bindWith:(methods size == 1 ifTrue:[methods first whoString] ifFalse:[methods size printString , ' methods'])
-                 with:newClass name.
-        changes := CompositeRefactoryChange named:nm.
+	nm := (doWhat == #copy)
+		ifTrue:['Copy %1 to %2']
+		ifFalse:[
+		    (doWhat == #moveAndForward)
+			ifTrue:['Move with Forwarding %1 to %2']
+			ifFalse:['Move %1 to %2']].
+	nm := nm bindWith:(methods size == 1 ifTrue:[methods first whoString] ifFalse:[methods size printString , ' methods'])
+		 with:newClass name.
+	changes := CompositeRefactoryChange named:nm.
     ].
 
     methods copy do:[:methodToCopyOrMove |
-        |question msg selectorToCopyOrMove
-         category source dontDoIt newMethod oldClass
-         template|
-
-        dontDoIt := false.
-        selectorToCopyOrMove := methodToCopyOrMove selector.
-        (newClass includesSelector:selectorToCopyOrMove) ifTrue:[
-            question := (doWhat == #copy)
-                    ifTrue:['%1 already implements #%2\\Copy anyway ?']
-                    ifFalse:['%1 already implements #%2\\Move anyway ?'].
-
-            (self confirm:(resources string:question
-                                      with:newClass name allBold
-                                      with:selectorToCopyOrMove) withCRs) ifFalse:[
-                dontDoIt := true
-            ]
-        ] ifFalse:[
-            "/ confirm copy/move of the version method (to avoid confusing the repository)
-            ((AbstractSourceCodeManager isVersionMethodSelector:selectorToCopyOrMove) and:[newClass isMeta]) ifTrue:[
-                question := (doWhat == #copy)
-                        ifTrue:['Copying the version method might confuse the repository.\\Copy anyway ?']
-                        ifFalse:['Moving the version method might confuse the repository.\\Move anyway ?'].
-                (self confirm:(resources string:question) withCRs) ifFalse:[
-                    dontDoIt := true
-                ]
-            ].
-        ].
-        dontDoIt ifFalse:[
-            source := methodToCopyOrMove source.
-            category := methodToCopyOrMove category.
-
-            lastMethodMoveClass := newClass name.
-
-            canUseRefactoringSupport ifTrue:[
-                changes
-                        compile:source
-                        in:newClass
-                        classified:category.
-                newMethod := #dummy. "/ to make following if happy
-            ] ifFalse:[
-                newMethod := newClass
-                                    compile:source
-                                    classified:category.
-            ].
-
-            (newMethod isNil or:[newMethod == #Error]) ifTrue:[
-                msg := (doWhat == #copy)
-                           ifTrue:['#%1 not copied - compilation failed due to an error']
-                           ifFalse:['#%1 not moved - compilation failed due to an error'].
-                self warn:(resources string:msg with:selectorToCopyOrMove)
-            ] ifFalse:[
-                oldClass := methodToCopyOrMove mclass.
-                (doWhat == #copy) ifFalse:[
-                    canUseRefactoringSupport ifTrue:[
-                        changes removeMethod: selectorToCopyOrMove from:oldClass
-                    ] ifFalse:[
-                        oldClass removeSelector:selectorToCopyOrMove.
-                    ].
-                    (doWhat == #moveAndForward) ifTrue:[
-                        template := Parser methodSpecificationForSelector:selectorToCopyOrMove.
-                        newClass == oldClass class ifTrue:[
-                            newClassName := 'self class'.
-                        ] ifFalse:[
-                            newClass nameSpace = oldClass nameSpace ifTrue:[
-                                newClassName := newClass theNonMetaclass nameWithoutNameSpacePrefix.
-                            ] ifFalse:[
-                                newClassName := newClass theNonMetaclass name
-                            ].
-                        ].
-                        source := template , '
+	|question msg selectorToCopyOrMove
+	 category source dontDoIt newMethod oldClass
+	 template|
+
+	dontDoIt := false.
+	selectorToCopyOrMove := methodToCopyOrMove selector.
+	(newClass includesSelector:selectorToCopyOrMove) ifTrue:[
+	    question := (doWhat == #copy)
+		    ifTrue:['%1 already implements #%2\\Copy anyway ?']
+		    ifFalse:['%1 already implements #%2\\Move anyway ?'].
+
+	    (self confirm:(resources string:question
+				      with:newClass name allBold
+				      with:selectorToCopyOrMove) withCRs) ifFalse:[
+		dontDoIt := true
+	    ]
+	] ifFalse:[
+	    "/ confirm copy/move of the version method (to avoid confusing the repository)
+	    ((AbstractSourceCodeManager isVersionMethodSelector:selectorToCopyOrMove) and:[newClass isMeta]) ifTrue:[
+		question := (doWhat == #copy)
+			ifTrue:['Copying the version method might confuse the repository.\\Copy anyway ?']
+			ifFalse:['Moving the version method might confuse the repository.\\Move anyway ?'].
+		(self confirm:(resources string:question) withCRs) ifFalse:[
+		    dontDoIt := true
+		]
+	    ].
+	].
+	dontDoIt ifFalse:[
+	    source := methodToCopyOrMove source.
+	    category := methodToCopyOrMove category.
+
+	    lastMethodMoveClass := newClass name.
+
+	    canUseRefactoringSupport ifTrue:[
+		changes
+			compile:source
+			in:newClass
+			classified:category.
+		newMethod := #dummy. "/ to make following if happy
+	    ] ifFalse:[
+		newMethod := newClass
+				    compile:source
+				    classified:category.
+	    ].
+
+	    (newMethod isNil or:[newMethod == #Error]) ifTrue:[
+		msg := (doWhat == #copy)
+			   ifTrue:['#%1 not copied - compilation failed due to an error']
+			   ifFalse:['#%1 not moved - compilation failed due to an error'].
+		self warn:(resources string:msg with:selectorToCopyOrMove)
+	    ] ifFalse:[
+		oldClass := methodToCopyOrMove mclass.
+		(doWhat == #copy) ifFalse:[
+		    canUseRefactoringSupport ifTrue:[
+			changes removeMethod: selectorToCopyOrMove from:oldClass
+		    ] ifFalse:[
+			oldClass removeSelector:selectorToCopyOrMove.
+		    ].
+		    (doWhat == #moveAndForward) ifTrue:[
+			template := Parser methodSpecificationForSelector:selectorToCopyOrMove.
+			newClass == oldClass class ifTrue:[
+			    newClassName := 'self class'.
+			] ifFalse:[
+			    newClass nameSpace = oldClass nameSpace ifTrue:[
+				newClassName := newClass theNonMetaclass nameWithoutNameSpacePrefix.
+			    ] ifFalse:[
+				newClassName := newClass theNonMetaclass name
+			    ].
+			].
+			source := template , '
     ^ ' , newClassName , ' ' , template , '
 '.
-                        canUseRefactoringSupport ifTrue:[
-                            changes
-                                    compile:source
-                                    in:oldClass
-                                    classified:category.
-                        ] ifFalse:[
-                            oldClass
-                                    compile:source
-                                    classified:category.
-                        ].
-                    ]
-                ]
-            ]
-        ]
+			canUseRefactoringSupport ifTrue:[
+			    changes
+				    compile:source
+				    in:oldClass
+				    classified:category.
+			] ifFalse:[
+			    oldClass
+				    compile:source
+				    classified:category.
+			].
+		    ]
+		]
+	    ]
+	]
     ].
 
     canUseRefactoringSupport ifTrue:[
-        RefactoryChangeManager performChange: changes
+	RefactoryChangeManager performChange: changes
     ].
 !
 
 renameMethod:oldSelector in:aClass
-    |newSelector tree dialog args newArgs map refactoring rslt 
-     renameSelectedMethodsOnly renameOnly rewriteLocalSendersOnly 
+    |newSelector tree dialog args newArgs map refactoring rslt
+     renameSelectedMethodsOnly renameOnly rewriteLocalSendersOnly
      affectedClasses classesOfSelectedMethods suggestion|
 
     RBParser isNil ifTrue:[
-        Dialog warn:'Missing class: RBParser'.
-        ^ self
+	Dialog warn:'Missing class: RBParser'.
+	^ self
     ].
     RBParser autoload.
     MethodNameDialog isNil ifTrue:[
-        Dialog warn:'Missing class: MethodNameDialog'.
-        ^ self
+	Dialog warn:'Missing class: MethodNameDialog'.
+	^ self
     ].
     MethodNameDialog autoload.
 
     tree := aClass parseTreeFor:oldSelector.
     tree isNil ifTrue:[
-        self warn: 'Could not parse the method'.
-        ^ self
+	self warn: 'Could not parse the method'.
+	^ self
     ].
     args := tree argumentNames.
 
@@ -40977,10 +41448,10 @@
 
     newSelector := dialog methodName.
     newSelector = oldSelector ifTrue:[
-        newArgs = args ifTrue:[
-            Dialog information:'no change'.
-            ^ self.
-        ].
+	newArgs = args ifTrue:[
+	    Dialog information:'no change'.
+	    ^ self.
+	].
     ].
 
     LastRenamedOld := oldSelector.
@@ -40991,61 +41462,61 @@
     rewriteLocalSendersOnly := dialog isRewritingLocalSendersOnly.
 
     refactoring := RenameMethodRefactoring
-                                renameMethod: oldSelector
-                                in: aClass
-                                to: newSelector
-                                permuation: map.
+				renameMethod: oldSelector
+				in: aClass
+				to: newSelector
+				permuation: map.
     refactoring suppressRewriteOfSenders:renameOnly.
 
     renameOnly ifFalse:[
-        affectedClasses := rewriteLocalSendersOnly 
-                                ifTrue:[ Smalltalk allClasses ] 
-                                ifFalse:[ aClass withAllSubclasses ].
-        "/ ask if so many methods should be rewritten; give chance to cancel
-        "/ JV: but not if refactorings are confimed anyway in performRefactoring:...
-        UserPreferences current confirmRefactorings ifFalse:[
-            (self findSendersOf:oldSelector in:affectedClasses andConfirmRefactoring:refactoring) ifFalse:[ ^ self ].
-        ].
+	affectedClasses := rewriteLocalSendersOnly
+				ifTrue:[ Smalltalk allClasses ]
+				ifFalse:[ aClass withAllSubclasses ].
+	"/ ask if so many methods should be rewritten; give chance to cancel
+	"/ JV: but not if refactorings are confimed anyway in performRefactoring:...
+	UserPreferences current confirmRefactorings ifFalse:[
+	    (self findSendersOf:oldSelector in:affectedClasses andConfirmRefactoring:refactoring) ifFalse:[ ^ self ].
+	].
     ].
 
     renameSelectedMethodsOnly ifTrue:[
-        (self selectedMethodsValue collect:[:m | m selector]) asSet size == 1 ifFalse:[
-            Dialog warn:'Multiple different selectors selected'.
-            ^ self.
-        ].
-
-        classesOfSelectedMethods := self selectedMethodsValue collect:[:m|m mclass].
-"/        classesOfSelectedMethods := classesOfSelectedMethods 
-"/                collect:[:cls | 
+	(self selectedMethodsValue collect:[:m | m selector]) asSet size == 1 ifFalse:[
+	    Dialog warn:'Multiple different selectors selected'.
+	    ^ self.
+	].
+
+	classesOfSelectedMethods := self selectedMethodsValue collect:[:m|m mclass].
+"/        classesOfSelectedMethods := classesOfSelectedMethods
+"/                collect:[:cls |
 "/                    |className rbClass|
 "/
-"/                    className := cls theNonMetaclass name. 
-"/                    cls isMeta 
+"/                    className := cls theNonMetaclass name.
+"/                    cls isMeta
 "/                        ifTrue:[rbClass := RBMetaclass existingNamed: className]
 "/                        ifFalse:[rbClass := RBClass existingNamed: className].
 "/                    rbClass model:(RBNamespace new).
 "/                    rbClass
 "/                ].
-        refactoring onlyRenameTheseImplementors:classesOfSelectedMethods.
+	refactoring onlyRenameTheseImplementors:classesOfSelectedMethods.
     ].
 
     self withWaitCursorDo:[
-        |classesOfSelectedMethods affectedImplementors|
+	|classesOfSelectedMethods affectedImplementors|
 
 "/        refactoring model name:('rename %1 to %2' bindWith:oldSelector storeString with:newSelector storeString).
 
-        rslt := self performRefactoring:refactoring.
-        self switchToSelector:newSelector asSymbol.
+	rslt := self performRefactoring:refactoring.
+	self switchToSelector:newSelector asSymbol.
     ].
 
     dialog browseOldSendersHolder value ifTrue:[
-        self spawnMethodSendersBrowserFor:(Array with:oldSelector) in:#newBrowser
+	self spawnMethodSendersBrowserFor:(Array with:oldSelector) in:#newBrowser
     ].
     dialog browseNewSendersHolder value ifTrue:[
-        self spawnMethodSendersBrowserFor:(Array with:newSelector) in:#newBrowser
+	self spawnMethodSendersBrowserFor:(Array with:newSelector) in:#newBrowser
     ].
     dialog browseChangedMethodsHolder value ifTrue:[
-        self spawnMethodImplementorsBrowserFor:(Array with:newSelector) match:false in:#newBrowser
+	self spawnMethodImplementorsBrowserFor:(Array with:newSelector) match:false in:#newBrowser
     ].
 
     "Modified: / 28-02-2012 / 16:28:12 / cg"
@@ -41085,10 +41556,10 @@
 
 selectorCheckMenuSmalllintCheck: what
     "perform all checks on the selected class(es)."
-    
-    self 
-        smalllintCheck:self selectedSelectorsAsEnvironment
-        against: what
+
+    self
+	smalllintCheck:self selectedSelectorsAsEnvironment
+	against: what
 
     "Modified: / 28-12-2008 / 14:42:01 / bazantj <enter your email here>"
     "Modified: / 13-01-2009 / 13:20:48 / Jiri Bazant <bazanj2@fel.cvut.cz>"
@@ -41107,8 +41578,8 @@
     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 showCode:previousCode scrollToTop:false.
@@ -41125,8 +41596,8 @@
     m := self theSingleSelectedMethod.
     previousMethods := self methodsPreviousVersions.
     previousMethods isEmpty ifTrue:[
-        self information:'Oops - no previous versions found'.
-        ^ self
+	self information:'Oops - no previous versions found'.
+	^ self
     ].
 
     dummyChangeSet := ChangeSet new addAll:previousMethods; yourself.
@@ -41153,193 +41624,193 @@
     mselector := method selector.
     className := mclass name.
     [
-        |set|
-
-        set := ChangeSet forExistingMethods:(Array with:method).
-        set := set select:[:c | c isMethodChange].
-        lastChange := set first.
+	|set|
+
+	set := ChangeSet forExistingMethods:(Array with:method).
+	set := set select:[:c | c isMethodChange].
+	lastChange := set first.
     ] value.
 
     thisIsAnExtensionMethod := (method package ~= mclass package).
     thisIsAnExtensionMethod ifTrue:[
-        packageId := method package asPackageId.
-        mgr := packageId projectDefinitionClass sourceCodeManager.
-    ] ifFalse:[
-        packageId := mclass package asPackageId.
-        "/ mgr := packageId projectDefinitionClass sourceCodeManager.
-        mgr := SourceCodeManagerUtilities default sourceCodeManagerFor:mclass.
-        self assert:(mgr = packageId projectDefinitionClass sourceCodeManager).
+	packageId := method package asPackageId.
+	mgr := packageId projectDefinitionClass sourceCodeManager.
+    ] ifFalse:[
+	packageId := mclass package asPackageId.
+	"/ mgr := packageId projectDefinitionClass sourceCodeManager.
+	mgr := SourceCodeManagerUtilities default sourceCodeManagerFor:mclass.
+	self assert:(mgr = packageId projectDefinitionClass sourceCodeManager).
     ].
     directory := packageId directory.
     module := packageId module.
 
     self withWaitCursorDo:[
-        |revisionLog start stop answer t tS list msg first|
-
-        thisIsAnExtensionMethod ifTrue:[
-            revisionLog := mgr 
-                revisionLogOf:nil
-                fromRevision:nil 
-                toRevision:nil
-                numberOfRevisions:nil
-                fileName:'extensions.st'
-                directory:directory 
-                module:module.
-        ] ifFalse:[
-            revisionLog := mgr revisionLogOf:mclass.
-        ].
-        revisions := revisionLog at:#revisions.
-
-        start := 1.
-        stop := revisions size.
-        stop > 20 ifTrue:[
-            thisIsAnExtensionMethod ifTrue:[
-                t := 500.   "/ fake time
-            ] ifFalse:[
-                "/ measure the time it takes to checkout a version...
-                t := Time millisecondsToRun:[
-                    |revSourceStream|
-
-                    revSourceStream := mgr getSourceStreamFor:mclass revision:((revisions at:10) at:#revision).
-                    ChangeSet fromStream:revSourceStream.
-                    revSourceStream close.
-                ].
-            ].
-
-            list := revisions collect:[:entry |
-                                        |rev author dateString date msg|
-
-                                        rev := entry at:#revision.
-                                        author := entry at:#author.
-                                        dateString := entry at:#date.
-                                        date := Timestamp readGeneralizedFrom:dateString.
-                                        dateString := date printStringFormat:'%(year)-%(mon)-%(day) %h:%m:%s'.
-                                        entry at:#date put:dateString.
-                                        msg := (entry at:#logMessage) asStringCollection first asString.
-                                        rev,' ',author,' ',dateString,' ',msg
-                                      ].
-            msg := 'There are %1 revisions to extract from the repository'.
-            t := (t * revisions size / 1000) rounded.
-            t < 10 ifTrue:[
-                msg := msg,'\(this will take a few seconds).'.
-                tS := t.
-            ] ifFalse:[
-                t := t * revisions size // 1000 // 10 * 10.
-                tS := (TimeDuration fromSeconds:t) printStringForApproximation.
-                msg := msg,'\(this will take roughly %2).'
-            ].
-            msg := msg,'\\Do you want to see all or only some of the revisions ?'.
-
-            answer := Dialog
-                choose:(resources stringWithCRs:msg
-                                    with:revisions size
-                                    with:tS)
-                fromList:list values:revisions initialSelection:nil
-                buttons:nil
-                values:nil
-                default:nil
-                lines:20
-                cancel:[^ self]
-                multiple:false
-                title:(resources string:'Confirmation')
-                postBuildBlock:[:dialog |
-                            |b|
-
-                            b := Button label:(resources string:'Browse Newer than Selected').
-                            b action:[ stop := (dialog componentAt:#ListView) selection. dialog okPressed].
-                            b := dialog addButton:b before:dialog okButton.
-
-                            dialog okButton label:(resources string:'Browse All').
-                            dialog okButton action:[ stop := revisions size. dialog okPressed].
-                        ].
-
-            stop isNil ifTrue:[^ self ].
-        ].
+	|revisionLog start stop answer t tS list msg first|
+
+	thisIsAnExtensionMethod ifTrue:[
+	    revisionLog := mgr
+		revisionLogOf:nil
+		fromRevision:nil
+		toRevision:nil
+		numberOfRevisions:nil
+		fileName:'extensions.st'
+		directory:directory
+		module:module.
+	] ifFalse:[
+	    revisionLog := mgr revisionLogOf:mclass.
+	].
+	revisions := revisionLog at:#revisions.
+
+	start := 1.
+	stop := revisions size.
+	stop > 20 ifTrue:[
+	    thisIsAnExtensionMethod ifTrue:[
+		t := 500.   "/ fake time
+	    ] ifFalse:[
+		"/ measure the time it takes to checkout a version...
+		t := Time millisecondsToRun:[
+		    |revSourceStream|
+
+		    revSourceStream := mgr getSourceStreamFor:mclass revision:((revisions at:10) at:#revision).
+		    ChangeSet fromStream:revSourceStream.
+		    revSourceStream close.
+		].
+	    ].
+
+	    list := revisions collect:[:entry |
+					|rev author dateString date msg|
+
+					rev := entry at:#revision.
+					author := entry at:#author.
+					dateString := entry at:#date.
+					date := Timestamp readGeneralizedFrom:dateString.
+					dateString := date printStringFormat:'%(year)-%(mon)-%(day) %h:%m:%s'.
+					entry at:#date put:dateString.
+					msg := (entry at:#logMessage) asStringCollection first asString.
+					rev,' ',author,' ',dateString,' ',msg
+				      ].
+	    msg := 'There are %1 revisions to extract from the repository'.
+	    t := (t * revisions size / 1000) rounded.
+	    t < 10 ifTrue:[
+		msg := msg,'\(this will take a few seconds).'.
+		tS := t.
+	    ] ifFalse:[
+		t := t * revisions size // 1000 // 10 * 10.
+		tS := (TimeDuration fromSeconds:t) printStringForApproximation.
+		msg := msg,'\(this will take roughly %2).'
+	    ].
+	    msg := msg,'\\Do you want to see all or only some of the revisions ?'.
+
+	    answer := Dialog
+		choose:(resources stringWithCRs:msg
+				    with:revisions size
+				    with:tS)
+		fromList:list values:revisions initialSelection:nil
+		buttons:nil
+		values:nil
+		default:nil
+		lines:20
+		cancel:[^ self]
+		multiple:false
+		title:(resources string:'Confirmation')
+		postBuildBlock:[:dialog |
+			    |b|
+
+			    b := Button label:(resources string:'Browse Newer than Selected').
+			    b action:[ stop := (dialog componentAt:#ListView) selection. dialog okPressed].
+			    b := dialog addButton:b before:dialog okButton.
+
+			    dialog okButton label:(resources string:'Browse All').
+			    dialog okButton action:[ stop := revisions size. dialog okPressed].
+			].
+
+	    stop isNil ifTrue:[^ self ].
+	].
 
 t := Time millisecondsToRun:[
 
-        previousMethods := ChangeSet new.
-        lastSource := currentSource := method source.
-        lastRevision := lastDate := nil.
-        first := true.
-
-        revisions from:start to:stop do:[:eachLogEntry |
-            |revision date revSourceStream|
-
-            revision := eachLogEntry at:#revision.
-            date := eachLogEntry at:#date.
-
-            [
-                |chg nChg classChangeSet changeSource changeName|
-
-                self activityNotification:('Fetching revision ',revision,'...').
-                thisIsAnExtensionMethod ifTrue:[
-                    revSourceStream := mgr 
-                                            streamForClass:nil
-                                            fileName:'extensions.st' 
-                                            revision:revision 
-                                            directory:directory 
-                                            module:module
-                                            cache:true.
-                ] ifFalse:[
-                    revSourceStream := mgr getSourceStreamFor:mclass revision:revision.
-                ].
-                classChangeSet := ChangeSet fromStream:revSourceStream.
-
-                chg := classChangeSet
-                            detect:[:chg | chg isMethodChange
-                                           and:[chg selector = mselector
-                                           and:[chg className = className]]]
-                            ifNone:nil.
-
-                chg isNil ifTrue:[
-                    "the method was created in the next version (previous one processed)"
-                ] ifFalse:[
-                    changeSource := chg source.
-                ].
-                ((changeSource isNil and:[lastSource isNil]) 
-                or:[ changeSource asString = lastSource asString ]) ifTrue:[
-                ] ifFalse:[
-                    lastChange isNil ifTrue:[ 
-                        "/ mhm - was not in the previous version
-                    ] ifFalse:[
-                        nChg := lastChange asNamedMethodChange 
-                    ].
-                    lastRevision isNil ifTrue:[
-                        (stop = revisions size) ifTrue:[
-                            changeName := 'current (not in the repository)'.
-                        ] ifFalse:[
-                            "/ not showing all - dont really know
-                            changeName := 'current'.
-                        ].
-                    ] ifFalse:[
-                        changeName := lastRevision,' [',lastDate,']'.
-                        first ifTrue:[
-                            changeName := changeName,' (= current)'.
-                        ]
-                    ].
-                    nChg notNil ifTrue:[
-                        nChg changeName:changeName.
-                        previousMethods add:nChg.
-                    ].
-                    lastSource := changeSource.
-                    lastChange := chg.
-
-                    first := false.
-                ].
-                lastRevision := revision.
-                lastDate := date.
-            ] ensure:[
-                revSourceStream notNil ifTrue:[revSourceStream close].
-            ].
-        ].
+	previousMethods := ChangeSet new.
+	lastSource := currentSource := method source.
+	lastRevision := lastDate := nil.
+	first := true.
+
+	revisions from:start to:stop do:[:eachLogEntry |
+	    |revision date revSourceStream|
+
+	    revision := eachLogEntry at:#revision.
+	    date := eachLogEntry at:#date.
+
+	    [
+		|chg nChg classChangeSet changeSource changeName|
+
+		self activityNotification:('Fetching revision ',revision,'...').
+		thisIsAnExtensionMethod ifTrue:[
+		    revSourceStream := mgr
+					    streamForClass:nil
+					    fileName:'extensions.st'
+					    revision:revision
+					    directory:directory
+					    module:module
+					    cache:true.
+		] ifFalse:[
+		    revSourceStream := mgr getSourceStreamFor:mclass revision:revision.
+		].
+		classChangeSet := ChangeSet fromStream:revSourceStream.
+
+		chg := classChangeSet
+			    detect:[:chg | chg isMethodChange
+					   and:[chg selector = mselector
+					   and:[chg className = className]]]
+			    ifNone:nil.
+
+		chg isNil ifTrue:[
+		    "the method was created in the next version (previous one processed)"
+		] ifFalse:[
+		    changeSource := chg source.
+		].
+		((changeSource isNil and:[lastSource isNil])
+		or:[ changeSource asString = lastSource asString ]) ifTrue:[
+		] ifFalse:[
+		    lastChange isNil ifTrue:[
+			"/ mhm - was not in the previous version
+		    ] ifFalse:[
+			nChg := lastChange asNamedMethodChange
+		    ].
+		    lastRevision isNil ifTrue:[
+			(stop = revisions size) ifTrue:[
+			    changeName := 'current (not in the repository)'.
+			] ifFalse:[
+			    "/ not showing all - dont really know
+			    changeName := 'current'.
+			].
+		    ] ifFalse:[
+			changeName := lastRevision,' [',lastDate,']'.
+			first ifTrue:[
+			    changeName := changeName,' (= current)'.
+			]
+		    ].
+		    nChg notNil ifTrue:[
+			nChg changeName:changeName.
+			previousMethods add:nChg.
+		    ].
+		    lastSource := changeSource.
+		    lastChange := chg.
+
+		    first := false.
+		].
+		lastRevision := revision.
+		lastDate := date.
+	    ] ensure:[
+		revSourceStream notNil ifTrue:[revSourceStream close].
+	    ].
+	].
 ].
 "/ Transcript showCR:('it took %1 seconds' bindWith:(t /1000)printString).
 
-        self activityNotification:nil.
-        browser := (UserPreferences current changeSetBrowserClass) openOn:previousMethods.
-        browser window label:('Revisions of ' , mclass name , ' ' , mselector).
-        browser readOnly:true.
+	self activityNotification:nil.
+	browser := (UserPreferences current changeSetBrowserClass) openOn:previousMethods.
+	browser window label:('Revisions of ' , mclass name , ' ' , mselector).
+	browser readOnly:true.
     ].
 
     "Modified: / 01-07-2011 / 16:34:29 / cg"
@@ -41359,193 +41830,193 @@
     mselector := method selector.
     className := mclass name.
     [
-        |set|
-
-        set := ChangeSet forExistingMethods:(Array with:method).
-        set := set select:[:c | c isMethodChange].
-        lastChange := set first.
+	|set|
+
+	set := ChangeSet forExistingMethods:(Array with:method).
+	set := set select:[:c | c isMethodChange].
+	lastChange := set first.
     ] value.
 
     thisIsAnExtensionMethod := (method package ~= mclass package).
     thisIsAnExtensionMethod ifTrue:[
-        packageId := method package asPackageId.
-        mgr := manager
-    ] ifFalse:[
-        packageId := mclass package asPackageId.
-        "/ mgr := packageId projectDefinitionClass sourceCodeManager.
-        mgr := manager.
-        "/self assert:(mgr = packageId projectDefinitionClass sourceCodeManager).
+	packageId := method package asPackageId.
+	mgr := manager
+    ] ifFalse:[
+	packageId := mclass package asPackageId.
+	"/ mgr := packageId projectDefinitionClass sourceCodeManager.
+	mgr := manager.
+	"/self assert:(mgr = packageId projectDefinitionClass sourceCodeManager).
     ].
     directory := packageId directory.
     module := packageId module.
 
     self withWaitCursorDo:[
-        |revisionLog start stop answer t tS list msg first|
-
-        thisIsAnExtensionMethod ifTrue:[
-            revisionLog := mgr 
-                revisionLogOf:nil
-                fromRevision:nil 
-                toRevision:nil
-                numberOfRevisions:nil
-                fileName:'extensions.st'
-                directory:directory 
-                module:module.
-        ] ifFalse:[
-            revisionLog := mgr revisionLogOf:mclass.
-        ].
-        revisions := revisionLog at:#revisions.
-
-        start := 1.
-        stop := revisions size.
-        stop > 20 ifTrue:[
-            thisIsAnExtensionMethod ifTrue:[
-                t := 500.   "/ fake time
-            ] ifFalse:[
-                "/ measure the time it takes to checkout a version...
-                t := Time millisecondsToRun:[
-                    |revSourceStream|
-
-                    revSourceStream := mgr getSourceStreamFor:mclass revision:((revisions at:10) at:#revision).
-                    ChangeSet fromStream:revSourceStream.
-                    revSourceStream close.
-                ].
-            ].
-
-            list := revisions collect:[:entry |
-                                        |rev author dateString date msg|
-
-                                        rev := entry at:#revision.
-                                        author := entry at:#author.
-                                        dateString := entry at:#date.
-                                        date := Timestamp readGeneralizedFrom:dateString.
-                                        dateString := date printStringFormat:'%(year)-%(mon)-%(day) %h:%m:%s'.
-                                        entry at:#date put:dateString.
-                                        msg := (entry at:#logMessage) asStringCollection first asString.
-                                        rev,' ',author,' ',dateString,' ',msg
-                                      ].
-            msg := 'There are %1 revisions to extract from the repository'.
-            t := (t * revisions size / 1000) rounded.
-            t < 10 ifTrue:[
-                msg := msg,'\(this will take a few seconds).'.
-                tS := t.
-            ] ifFalse:[
-                t := t * revisions size // 1000 // 10 * 10.
-                tS := (TimeDuration fromSeconds:t) printStringForApproximation.
-                msg := msg,'\(this will take roughly %2).'
-            ].
-            msg := msg,'\\Do you want to see all or only some of the revisions ?'.
-
-            answer := Dialog
-                choose:(resources stringWithCRs:msg
-                                    with:revisions size
-                                    with:tS)
-                fromList:list values:revisions initialSelection:nil
-                buttons:nil
-                values:nil
-                default:nil
-                lines:20
-                cancel:[^ self]
-                multiple:false
-                title:(resources string:'Confirmation')
-                postBuildBlock:[:dialog |
-                            |b|
-
-                            b := Button label:(resources string:'Browse Newer than Selected').
-                            b action:[ stop := (dialog componentAt:#ListView) selection. dialog okPressed].
-                            b := dialog addButton:b before:dialog okButton.
-
-                            dialog okButton label:(resources string:'Browse All').
-                            dialog okButton action:[ stop := revisions size. dialog okPressed].
-                        ].
-
-            stop isNil ifTrue:[^ self ].
-        ].
+	|revisionLog start stop answer t tS list msg first|
+
+	thisIsAnExtensionMethod ifTrue:[
+	    revisionLog := mgr
+		revisionLogOf:nil
+		fromRevision:nil
+		toRevision:nil
+		numberOfRevisions:nil
+		fileName:'extensions.st'
+		directory:directory
+		module:module.
+	] ifFalse:[
+	    revisionLog := mgr revisionLogOf:mclass.
+	].
+	revisions := revisionLog at:#revisions.
+
+	start := 1.
+	stop := revisions size.
+	stop > 20 ifTrue:[
+	    thisIsAnExtensionMethod ifTrue:[
+		t := 500.   "/ fake time
+	    ] ifFalse:[
+		"/ measure the time it takes to checkout a version...
+		t := Time millisecondsToRun:[
+		    |revSourceStream|
+
+		    revSourceStream := mgr getSourceStreamFor:mclass revision:((revisions at:10) at:#revision).
+		    ChangeSet fromStream:revSourceStream.
+		    revSourceStream close.
+		].
+	    ].
+
+	    list := revisions collect:[:entry |
+					|rev author dateString date msg|
+
+					rev := entry at:#revision.
+					author := entry at:#author.
+					dateString := entry at:#date.
+					date := Timestamp readGeneralizedFrom:dateString.
+					dateString := date printStringFormat:'%(year)-%(mon)-%(day) %h:%m:%s'.
+					entry at:#date put:dateString.
+					msg := (entry at:#logMessage) asStringCollection first asString.
+					rev,' ',author,' ',dateString,' ',msg
+				      ].
+	    msg := 'There are %1 revisions to extract from the repository'.
+	    t := (t * revisions size / 1000) rounded.
+	    t < 10 ifTrue:[
+		msg := msg,'\(this will take a few seconds).'.
+		tS := t.
+	    ] ifFalse:[
+		t := t * revisions size // 1000 // 10 * 10.
+		tS := (TimeDuration fromSeconds:t) printStringForApproximation.
+		msg := msg,'\(this will take roughly %2).'
+	    ].
+	    msg := msg,'\\Do you want to see all or only some of the revisions ?'.
+
+	    answer := Dialog
+		choose:(resources stringWithCRs:msg
+				    with:revisions size
+				    with:tS)
+		fromList:list values:revisions initialSelection:nil
+		buttons:nil
+		values:nil
+		default:nil
+		lines:20
+		cancel:[^ self]
+		multiple:false
+		title:(resources string:'Confirmation')
+		postBuildBlock:[:dialog |
+			    |b|
+
+			    b := Button label:(resources string:'Browse Newer than Selected').
+			    b action:[ stop := (dialog componentAt:#ListView) selection. dialog okPressed].
+			    b := dialog addButton:b before:dialog okButton.
+
+			    dialog okButton label:(resources string:'Browse All').
+			    dialog okButton action:[ stop := revisions size. dialog okPressed].
+			].
+
+	    stop isNil ifTrue:[^ self ].
+	].
 
 t := Time millisecondsToRun:[
 
-        previousMethods := ChangeSet new.
-        lastSource := currentSource := method source.
-        lastRevision := lastDate := nil.
-        first := true.
-
-        revisions from:start to:stop do:[:eachLogEntry |
-            |revision date revSourceStream|
-
-            revision := eachLogEntry at:#revision.
-            date := eachLogEntry at:#date.
-
-            [
-                |chg nChg classChangeSet changeSource changeName|
-
-                self activityNotification:('Fetching revision ',revision,'...').
-                thisIsAnExtensionMethod ifTrue:[
-                    revSourceStream := mgr 
-                                            streamForClass:nil
-                                            fileName:'extensions.st' 
-                                            revision:revision 
-                                            directory:directory 
-                                            module:module
-                                            cache:true.
-                ] ifFalse:[
-                    revSourceStream := mgr getSourceStreamFor:mclass revision:revision.
-                ].
-                classChangeSet := ChangeSet fromStream:revSourceStream.
-
-                chg := classChangeSet
-                            detect:[:chg | chg isMethodChange
-                                           and:[chg selector = mselector
-                                           and:[chg className = className]]]
-                            ifNone:nil.
-
-                chg isNil ifTrue:[
-                    "the method was created in the next version (previous one processed)"
-                ] ifFalse:[
-                    changeSource := chg source.
-                ].
-                ((changeSource isNil and:[lastSource isNil]) 
-                or:[ changeSource asString = lastSource asString ]) ifTrue:[
-                ] ifFalse:[
-                    lastChange isNil ifTrue:[ 
-                        "/ mhm - was not in the previous version
-                    ] ifFalse:[
-                        nChg := lastChange asNamedMethodChange 
-                    ].
-                    lastRevision isNil ifTrue:[
-                        (stop = revisions size) ifTrue:[
-                            changeName := 'current (not in the repository)'.
-                        ] ifFalse:[
-                            "/ not showing all - dont really know
-                            changeName := 'current'.
-                        ].
-                    ] ifFalse:[
-                        changeName := lastRevision,' [',lastDate,']'.
-                        first ifTrue:[
-                            changeName := changeName,' (= current)'.
-                        ]
-                    ].
-                    nChg notNil ifTrue:[
-                        nChg changeName:changeName.
-                        previousMethods add:nChg.
-                    ].
-                    lastSource := changeSource.
-                    lastChange := chg.
-
-                    first := false.
-                ].
-                lastRevision := revision.
-                lastDate := date.
-            ] ensure:[
-                revSourceStream notNil ifTrue:[revSourceStream close].
-            ].
-        ].
+	previousMethods := ChangeSet new.
+	lastSource := currentSource := method source.
+	lastRevision := lastDate := nil.
+	first := true.
+
+	revisions from:start to:stop do:[:eachLogEntry |
+	    |revision date revSourceStream|
+
+	    revision := eachLogEntry at:#revision.
+	    date := eachLogEntry at:#date.
+
+	    [
+		|chg nChg classChangeSet changeSource changeName|
+
+		self activityNotification:('Fetching revision ',revision,'...').
+		thisIsAnExtensionMethod ifTrue:[
+		    revSourceStream := mgr
+					    streamForClass:nil
+					    fileName:'extensions.st'
+					    revision:revision
+					    directory:directory
+					    module:module
+					    cache:true.
+		] ifFalse:[
+		    revSourceStream := mgr getSourceStreamFor:mclass revision:revision.
+		].
+		classChangeSet := ChangeSet fromStream:revSourceStream.
+
+		chg := classChangeSet
+			    detect:[:chg | chg isMethodChange
+					   and:[chg selector = mselector
+					   and:[chg className = className]]]
+			    ifNone:nil.
+
+		chg isNil ifTrue:[
+		    "the method was created in the next version (previous one processed)"
+		] ifFalse:[
+		    changeSource := chg source.
+		].
+		((changeSource isNil and:[lastSource isNil])
+		or:[ changeSource asString = lastSource asString ]) ifTrue:[
+		] ifFalse:[
+		    lastChange isNil ifTrue:[
+			"/ mhm - was not in the previous version
+		    ] ifFalse:[
+			nChg := lastChange asNamedMethodChange
+		    ].
+		    lastRevision isNil ifTrue:[
+			(stop = revisions size) ifTrue:[
+			    changeName := 'current (not in the repository)'.
+			] ifFalse:[
+			    "/ not showing all - dont really know
+			    changeName := 'current'.
+			].
+		    ] ifFalse:[
+			changeName := lastRevision,' [',lastDate,']'.
+			first ifTrue:[
+			    changeName := changeName,' (= current)'.
+			]
+		    ].
+		    nChg notNil ifTrue:[
+			nChg changeName:changeName.
+			previousMethods add:nChg.
+		    ].
+		    lastSource := changeSource.
+		    lastChange := chg.
+
+		    first := false.
+		].
+		lastRevision := revision.
+		lastDate := date.
+	    ] ensure:[
+		revSourceStream notNil ifTrue:[revSourceStream close].
+	    ].
+	].
 ].
 "/ Transcript showCR:('it took %1 seconds' bindWith:(t /1000)printString).
 
-        self activityNotification:nil.
-        browser := (UserPreferences current changeSetBrowserClass) openOn:previousMethods.
-        browser window label:('Revisions of ' , mclass name , ' ' , mselector).
-        browser readOnly:true.
+	self activityNotification:nil.
+	browser := (UserPreferences current changeSetBrowserClass) openOn:previousMethods.
+	browser window label:('Revisions of ' , mclass name , ' ' , mselector).
+	browser readOnly:true.
     ].
 
     "Modified: / 01-07-2011 / 16:34:29 / cg"
@@ -41562,9 +42033,9 @@
 
 selectorMenuChangePrivacyTo:privacySymbol
     self selectedMethodsDo:[:eachMethod |
-        (eachMethod privacy ~~ privacySymbol) ifTrue:[
-            eachMethod privacy:privacySymbol.
-        ]
+	(eachMethod privacy ~~ privacySymbol) ifTrue:[
+	    eachMethod privacy:privacySymbol.
+	]
     ].
 
     "Modified: / 23-11-2006 / 17:03:39 / cg"
@@ -41575,11 +42046,11 @@
 
     projects := ((self selectedMethodsValue) collect:[:each | each package]) asSet.
     projects do:[:packageToCheckIn |
-        self
-            projectMenuCheckInProject:packageToCheckIn
-            classes:false
-            extensions:true
-            buildSupport:false
+	self
+	    projectMenuCheckInProject:packageToCheckIn
+	    classes:false
+	    extensions:true
+	    buildSupport:false
     ].
 
     "Modified: / 28-02-2012 / 16:28:43 / cg"
@@ -41589,12 +42060,12 @@
     "remove all changes for the selected method(s) from the changeSet"
 
     (self confirm:'This will remove all changes for the selected method(s) from the changeSet.\\Really cleanup ?' withCRs)
-        ifFalse:[ ^ self].
+	ifFalse:[ ^ self].
 
     self withWaitCursorDo:[
-        self selectedMethodsValue do:[:eachMethod |
-            ChangeSet current condenseChangesForClass:eachMethod mclass selector:eachMethod selector
-        ]
+	self selectedMethodsValue do:[:eachMethod |
+	    ChangeSet current condenseChangesForClass:eachMethod mclass selector:eachMethod selector
+	]
     ]
 
     "Created: / 06-10-2006 / 16:36:44 / cg"
@@ -41681,9 +42152,9 @@
     selectedMethods := self selectedMethodsValue.
 
     self
-        doCompareMethod:(selectedMethods first)
-        against:(selectedMethods second)
-        label:(resources string:'Comparing methods')
+	doCompareMethod:(selectedMethods first)
+	against:(selectedMethods second)
+	label:(resources string:'Comparing methods')
 
     "Modified: / 28-02-2012 / 16:29:05 / cg"
 !
@@ -41696,9 +42167,9 @@
     m1 := self selectedMethodsValue first.
     m2 := m1 mclass superclass lookupMethodFor:(m1 selector).
     self
-        doCompareMethod:m1
-        against:m2
-        label:(resources string:'Comparing against inherited')
+	doCompareMethod:m1
+	against:m2
+	label:(resources string:'Comparing against inherited')
 
     "Modified: / 28-02-2012 / 16:29:11 / cg"
 !
@@ -41717,17 +42188,17 @@
     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 label:(resources string:'comparing method').
+	v waitUntilVisible.
     ].
     ^ self
 !
@@ -41736,22 +42207,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 label:(resources string:'Comparing method').
+	].
     ].
 
     "Created: / 11-11-2006 / 15:15:26 / cg"
@@ -41765,10 +42236,10 @@
     self theSingleSelectedMethod isNil ifTrue:[^ self].
 
     ParserFlags
-        withSTCCompilation:#always
-        do:[
-            self codeView accept.
-        ].
+	withSTCCompilation:#always
+	do:[
+	    self codeView accept.
+	].
 !
 
 selectorMenuCopy
@@ -41783,21 +42254,21 @@
     |currentMethod s codeView|
 
     (currentMethod := self theSingleSelectedMethod) notNil ifTrue:[
-        (self askIfModified:'Code was modified.\\Decompile anyway ?')
-        ifFalse:[^ self].
-
-        s := '' writeStream.
-        (currentMethod decompileTo:s) ifFalse:[
-            self warn:'No decompiler available'.
-        ].
-        codeView := self codeView.
-
-        codeView contents:s contents.
-        codeView modified:false.
-        navigationState modified:false.
-        navigationState realModifiedState:false.
-
-        codeView acceptAction:nil.
+	(self askIfModified:'Code was modified.\\Decompile anyway ?')
+	ifFalse:[^ self].
+
+	s := '' writeStream.
+	(currentMethod decompileTo:s) ifFalse:[
+	    self warn:'No decompiler available'.
+	].
+	codeView := self codeView.
+
+	codeView contents:s contents.
+	codeView modified:false.
+	navigationState modified:false.
+	navigationState realModifiedState:false.
+
+	codeView acceptAction:nil.
     ]
 !
 
@@ -41812,16 +42283,16 @@
     (currentMethod notNil
     and:[(methodsResources := currentMethod resources) notNil]
     ) ifTrue:[
-        "/
-        "/ kludge - this info should come from somewhere else ...
-        "/
-        editorClass := self class resourceEditorClassForResources:methodsResources.
-        editorClass notNil ifTrue: [
-            editorClass
-                openOnClass:currentMethod mclass theNonMetaclass
-                andSelector:currentMethod selector.
-            ^ self.
-        ]
+	"/
+	"/ kludge - this info should come from somewhere else ...
+	"/
+	editorClass := self class resourceEditorClassForResources:methodsResources.
+	editorClass notNil ifTrue: [
+	    editorClass
+		openOnClass:currentMethod mclass theNonMetaclass
+		andSelector:currentMethod selector.
+	    ^ self.
+	]
     ].
 !
 
@@ -41833,26 +42304,26 @@
 
 selectorMenuFileOutAsWithFormat:aFormatSymbolOrNil
     "fileOut selected methods from the list -  file format as specified by the argument:
-        nil     - standard format
-        #xml    - XML standard format
-        #sif    - SIF (smalltalk interchange file) standard format
-        #binary - ST/X binary format
+	nil     - standard format
+	#xml    - XML standard format
+	#sif    - SIF (smalltalk interchange file) standard format
+	#binary - ST/X binary format
     "
 
     |methods fileNameTemplate m|
 
     methods := self selectedMethodsValue.
     methods size > 1 ifTrue:[
-        fileNameTemplate := 'someMethods'.
-    ] ifFalse:[
-        m := methods first.
-        fileNameTemplate := m mclass nameWithoutPrefix , '-' , m selector.
-    ].
-    self
-        fileOutMethods:methods
-        format:aFormatSymbolOrNil
-        fileNameTemplate:fileNameTemplate
-        boxTitle:'FileOut selected method(s) as:'
+	fileNameTemplate := 'someMethods'.
+    ] ifFalse:[
+	m := methods first.
+	fileNameTemplate := m mclass nameWithoutPrefix , '-' , m selector.
+    ].
+    self
+	fileOutMethods:methods
+	format:aFormatSymbolOrNil
+	fileNameTemplate:fileNameTemplate
+	boxTitle:'FileOut selected method(s) as:'
 
     "Modified: / 28-02-2012 / 16:29:16 / cg"
 !
@@ -41867,8 +42338,8 @@
     "fileOut selected methods from the list - xml format"
 
     XMLCoder isNil ifTrue:[
-        self warn:'Sorry - missing class: XMLCoder.\\Cannot generate XML file.' withCRs.
-        ^ self
+	self warn:'Sorry - missing class: XMLCoder.\\Cannot generate XML file.' withCRs.
+	^ self
     ].
     ^ self selectorMenuFileOutAsWithFormat:#xml
 !
@@ -41877,43 +42348,43 @@
     "generate a subclassResponsibility method in the methods superclass"
 
     self
-        generateUndoableChangeOverSelectedMethods:'Generate Instance creation for %(singleMethodNameOrNumberOfMethods)'
-        via:[:generator :eachMethod |
-            |selector mclass|
-
-            selector := eachMethod selector.
-            mclass := eachMethod mclass.
-
-            generator
-                createInstanceCreationMethodWithSetupFor:selector category:'instance creation' in:mclass theMetaclass.
-        ]
+	generateUndoableChangeOverSelectedMethods:'Generate Instance creation for %(singleMethodNameOrNumberOfMethods)'
+	via:[:generator :eachMethod |
+	    |selector mclass|
+
+	    selector := eachMethod selector.
+	    mclass := eachMethod mclass.
+
+	    generator
+		createInstanceCreationMethodWithSetupFor:selector category:'instance creation' in:mclass theMetaclass.
+	]
 !
 
 selectorMenuGenerateForwardingMethodForInstances
     "generate a forwarding method on the instance side"
 
     self
-        generateUndoableChangeOverSelectedMethods:'Generate Forwarder for %(singleMethodNameOrNumberOfMethods)'
-        via:[:generator :eachMethod |
-            |selector category mclass implClass defineIt parser spec code|
-
-            selector := eachMethod selector.
-            category := eachMethod category.
-            mclass := eachMethod mclass.
-            mclass isMeta ifTrue:[
-                parser := Parser for:eachMethod source.
-                parser parseMethod.
-                spec := Parser methodSpecificationForSelector:selector argNames:parser methodArgs.
-
-                (mclass theNonMetaclass includesSelector:selector) ifFalse:[
-                    code := (spec , '\    ^ self class ' , spec , '.') withCRs.
-                    generator
-                        compile:code
-                        forClass:mclass theNonMetaclass
-                        inCategory:category
-                ].
-            ].
-        ]
+	generateUndoableChangeOverSelectedMethods:'Generate Forwarder for %(singleMethodNameOrNumberOfMethods)'
+	via:[:generator :eachMethod |
+	    |selector category mclass implClass defineIt parser spec code|
+
+	    selector := eachMethod selector.
+	    category := eachMethod category.
+	    mclass := eachMethod mclass.
+	    mclass isMeta ifTrue:[
+		parser := Parser for:eachMethod source.
+		parser parseMethod.
+		spec := Parser methodSpecificationForSelector:selector argNames:parser methodArgs.
+
+		(mclass theNonMetaclass includesSelector:selector) ifFalse:[
+		    code := (spec , '\    ^ self class ' , spec , '.') withCRs.
+		    generator
+			compile:code
+			forClass:mclass theNonMetaclass
+			inCategory:category
+		].
+	    ].
+	]
 !
 
 selectorMenuGenerateSubclassResponsibilityHere
@@ -41927,11 +42398,11 @@
     selector := selector asSymbol.
 
     self selectedClassesDo:[:eachClass |
-        |category|
-
-        category := '* as yet unspecified *'.
-        SmalltalkCodeGeneratorTool
-            createSubclassResponsibilityMethodFor:selector category:category in:eachClass.
+	|category|
+
+	category := '* as yet unspecified *'.
+	SmalltalkCodeGeneratorTool
+	    createSubclassResponsibilityMethodFor:selector category:category in:eachClass.
     ]
 
     "Modified: / 31-01-2011 / 18:29:52 / cg"
@@ -41941,38 +42412,38 @@
     "generate a subclassResponsibility method in the methods superclass"
 
     self
-        generateUndoableChangeOverSelectedMethods:'Generate Responsibility in superclass for %(singleMethodNameOrNumberOfMethods)'
-        via:[:generator :eachMethod |
-
-            |selector category mclass implClass defineIt answer|
-
-            selector := eachMethod selector.
-            category := eachMethod category.
-            mclass := eachMethod mclass.
-
-            mclass superclass notNil ifTrue:[
-                (mclass superclass includesSelector:selector) ifFalse:[
-                    defineIt := true.
-
-                    implClass := mclass superclass whichClassIncludesSelector:selector.
-                    implClass notNil ifTrue:[
-                        answer := Dialog
-                                    confirmWithCancel:(resources
-                                                            string:'%1 is inherited from %2.\\Define as subclassResponsibility in %3 anyway ?'
-                                                            with:selector allBold
-                                                            with:implClass name allBold
-                                                            with:mclass superclass name allBold
-                                                      ) withCRs.
-                        answer isNil ifTrue:[^ self].
-                        defineIt := answer.
-                    ].
-                    defineIt ifTrue:[
-                        generator
-                            createSubclassResponsibilityMethodFor:selector category:category in:mclass superclass.
-                    ]
-                ].
-            ].
-        ]
+	generateUndoableChangeOverSelectedMethods:'Generate Responsibility in superclass for %(singleMethodNameOrNumberOfMethods)'
+	via:[:generator :eachMethod |
+
+	    |selector category mclass implClass defineIt answer|
+
+	    selector := eachMethod selector.
+	    category := eachMethod category.
+	    mclass := eachMethod mclass.
+
+	    mclass superclass notNil ifTrue:[
+		(mclass superclass includesSelector:selector) ifFalse:[
+		    defineIt := true.
+
+		    implClass := mclass superclass whichClassIncludesSelector:selector.
+		    implClass notNil ifTrue:[
+			answer := Dialog
+				    confirmWithCancel:(resources
+							    string:'%1 is inherited from %2.\\Define as subclassResponsibility in %3 anyway ?'
+							    with:selector allBold
+							    with:implClass name allBold
+							    with:mclass superclass name allBold
+						      ) withCRs.
+			answer isNil ifTrue:[^ self].
+			defineIt := answer.
+		    ].
+		    defineIt ifTrue:[
+			generator
+			    createSubclassResponsibilityMethodFor:selector category:category in:mclass superclass.
+		    ]
+		].
+	    ].
+	]
 !
 
 selectorMenuGenerateTemplateInAllSubclasses
@@ -41985,30 +42456,30 @@
     "generate a template in some subclass for each subclassResponsibility method"
 
     self
-        generateUndoableChangeOverSelectedMethods:'Generate Responsibility for %(singleMethodNameOrNumberOfMethods)'
-        via:[:generator :eachMethod |
-            |selector category mclass implClass defineIt parser spec |
-
-            selector := eachMethod selector.
-            category := eachMethod category.
-            mclass := eachMethod mclass.
-
-            parser := Parser for:eachMethod source.
-            parser parseMethod.
-            spec := Parser methodSpecificationForSelector:selector argNames:parser methodArgs.
-
-            (mclass perform:aSubclassEnumeratingSelector) do:[:eachSubClass |
-                |code|
-
-                (eachSubClass includesSelector:selector) ifFalse:[
-                    code := spec , '\    self halt.\    ^ self' withCRs.
-                    generator
-                        compile:code
-                        forClass:eachSubClass
-                        inCategory:category
-                ].
-            ].
-        ]
+	generateUndoableChangeOverSelectedMethods:'Generate Responsibility for %(singleMethodNameOrNumberOfMethods)'
+	via:[:generator :eachMethod |
+	    |selector category mclass implClass defineIt parser spec |
+
+	    selector := eachMethod selector.
+	    category := eachMethod category.
+	    mclass := eachMethod mclass.
+
+	    parser := Parser for:eachMethod source.
+	    parser parseMethod.
+	    spec := Parser methodSpecificationForSelector:selector argNames:parser methodArgs.
+
+	    (mclass perform:aSubclassEnumeratingSelector) do:[:eachSubClass |
+		|code|
+
+		(eachSubClass includesSelector:selector) ifFalse:[
+		    code := spec , '\    self halt.\    ^ self' withCRs.
+		    generator
+			compile:code
+			forClass:eachSubClass
+			inCategory:category
+		].
+	    ].
+	]
 !
 
 selectorMenuGenerateTemplateInSubclasses
@@ -42021,7 +42492,7 @@
     |currentMethod cls selector tree args whichParameter|
 
     (self askIfModified) ifFalse:[
-        ^ self
+	^ self
     ].
 
     currentMethod := self theSingleSelectedMethod.
@@ -42031,18 +42502,18 @@
 
     tree := cls parseTreeFor:selector.
     tree isNil ifTrue:[
-        self warn: 'Could not parse the method'.
-        ^ self
+	self warn: 'Could not parse the method'.
+	^ self
     ].
     args := tree argumentNames.
     args size > 1 ifTrue:[
-        whichParameter := self selectionInCodeView.
-        (whichParameter notEmptyOrNil and:[ args includes:whichParameter]) ifFalse:[
-            whichParameter := Dialog choose:'Inline which Parameter ?' fromList:args lines:5 title:'Inline Parameter'.
-            whichParameter isEmptyOrNil ifTrue:[^ self].
-        ].
-    ] ifFalse:[
-        whichParameter := args first.
+	whichParameter := self selectionInCodeView.
+	(whichParameter notEmptyOrNil and:[ args includes:whichParameter]) ifFalse:[
+	    whichParameter := Dialog choose:'Inline which Parameter ?' fromList:args lines:5 title:'Inline Parameter'.
+	    whichParameter isEmptyOrNil ifTrue:[^ self].
+	].
+    ] ifFalse:[
+	whichParameter := args first.
     ].
 
     self codeMenuInlineParameter:whichParameter
@@ -42059,7 +42530,7 @@
 
     mthd := self theSingleSelectedMethod.
     mthd notNil ifTrue:[
-        mthd inspect
+	mthd inspect
     ].
 
     "Created: / 6.2.2000 / 01:53:56 / cg"
@@ -42069,17 +42540,17 @@
     "load a smallTeam version"
 
     self selectedMethodsValue do:[:eachMethod |
-        |changeList change|
-
-        changeList := SmallTeam changesOnHost:hostName.
-        change := changeList
-                    detectLast:[:change |
-                        change changeClass == eachMethod mclass
-                        and:[ change selector == eachMethod selector ] ]
-                    ifNone:nil.
-        change notNil ifTrue:[
-            change apply
-        ].
+	|changeList change|
+
+	changeList := SmallTeam changesOnHost:hostName.
+	change := changeList
+		    detectLast:[:change |
+			change changeClass == eachMethod mclass
+			and:[ change selector == eachMethod selector ] ]
+		    ifNone:nil.
+	change notNil ifTrue:[
+	    change apply
+	].
     ].
 
     "Created: / 12-11-2006 / 15:48:43 / cg"
@@ -42111,19 +42582,19 @@
     "move the selected methods from inst to their class side or vice versa"
 
     self selectedMethodsValue copy do:[:methodToMove |
-        |mclass question msg selectorToMove dontDoIt newMethod dstClass|
-
-        mclass := methodToMove mclass.
-        mclass isMeta ifTrue:[
-            dstClass := mclass theNonMetaclass.
-        ] ifFalse:[
-            dstClass := mclass theMetaclass.
-        ].
-
-        self
-            moveOrCopyMethods:(Array with:methodToMove)
-            toClass:dstClass
-            moveOrCopy:(withForwarder ifTrue:#moveAndForward ifFalse:#move).
+	|mclass question msg selectorToMove dontDoIt newMethod dstClass|
+
+	mclass := methodToMove mclass.
+	mclass isMeta ifTrue:[
+	    dstClass := mclass theNonMetaclass.
+	] ifFalse:[
+	    dstClass := mclass theMetaclass.
+	].
+
+	self
+	    moveOrCopyMethods:(Array with:methodToMove)
+	    toClass:dstClass
+	    moveOrCopy:(withForwarder ifTrue:#moveAndForward ifFalse:#move).
 
 
 "/        dontDoIt := false.
@@ -42194,76 +42665,76 @@
 
     useRefactoringSupport := self canUseRefactoringSupport.
     useRefactoringSupport ifTrue:[
-        changes := CompositeRefactoryChange named:'Mark Method(s) as Obsolete'.
+	changes := CompositeRefactoryChange named:'Mark Method(s) as Obsolete'.
     ].
 
     methodsToChangePackage := OrderedCollection new.
 
     self selectedMethodsDo:[:eachMethod |
-        |rs mClass selector source parser definitionPart bodyPart newSource newMethod result
-         s p1 indent category bodyStartsWithNewLine|
-
-        eachMethod isObsolete ifFalse:[
-            rs := eachMethod resources.
-            false "rs notEmptyOrNil" ifTrue:[
-                self halt.
-            ] ifFalse:[
-                mClass := eachMethod mclass.
-                selector := eachMethod selector.
-                source := eachMethod source.
-                category := eachMethod category.
-
-                parser := Parser for:source in:nil.
-                parser ignoreErrors:true; ignoreWarnings:true; saveComments:true.
-                parser parseMethodSpec.
-
-                "/ insert an obsolete-resource into the first line after the selector-spec
-                definitionPart := source copyTo:parser endOfSelectorPosition.
-                bodyPart := source copyFrom:parser endOfSelectorPosition+1.
-
-                bodyStartsWithNewLine := false.
-
-                s := bodyPart readStream.
-                [ s peek == Character cr or:[ s peek == Character nl ] ] whileTrue:[ bodyStartsWithNewLine := true. s next ].
-
-                p1 := s position.
-                [ s peek == Character space ] whileTrue:[ s next ].
-                indent := s position - p1.
-                indent := indent max:4.
-
-                newSource := definitionPart
-                             , '\' withCRs, (String new:indent), '<resource: #obsolete>'.
-                bodyStartsWithNewLine ifFalse:[
-                    newSource := newSource , '\' withCRs.
-                ].
-                newSource := newSource , bodyPart.
-
-                result := Compiler compile:newSource forClass:mClass install:false.
-                (result isNil or:[result == #Error]) ifTrue:[
-                    Dialog warn:(resources string:'Failed to compile new version of %1' with:eachMethod whoString allBold).
-                ] ifFalse:[
-                    useRefactoringSupport ifTrue:[
-                        changes
-                            compile:newSource
-                            in:mClass
-                            classified:category.
-                    ] ifFalse:[
-                        newMethod := mClass
-                                        compile:newSource
-                                        classified:category.
-                    ].
-                    methodsToChangePackage add:(Array with:mClass
-                                                      with:selector
-                                                      with:eachMethod package).
-                ].
-            ].
-        ].
+	|rs mClass selector source parser definitionPart bodyPart newSource newMethod result
+	 s p1 indent category bodyStartsWithNewLine|
+
+	eachMethod isObsolete ifFalse:[
+	    rs := eachMethod resources.
+	    false "rs notEmptyOrNil" ifTrue:[
+		self halt.
+	    ] ifFalse:[
+		mClass := eachMethod mclass.
+		selector := eachMethod selector.
+		source := eachMethod source.
+		category := eachMethod category.
+
+		parser := Parser for:source in:nil.
+		parser ignoreErrors:true; ignoreWarnings:true; saveComments:true.
+		parser parseMethodSpec.
+
+		"/ insert an obsolete-resource into the first line after the selector-spec
+		definitionPart := source copyTo:parser endOfSelectorPosition.
+		bodyPart := source copyFrom:parser endOfSelectorPosition+1.
+
+		bodyStartsWithNewLine := false.
+
+		s := bodyPart readStream.
+		[ s peek == Character cr or:[ s peek == Character nl ] ] whileTrue:[ bodyStartsWithNewLine := true. s next ].
+
+		p1 := s position.
+		[ s peek == Character space ] whileTrue:[ s next ].
+		indent := s position - p1.
+		indent := indent max:4.
+
+		newSource := definitionPart
+			     , '\' withCRs, (String new:indent), '<resource: #obsolete>'.
+		bodyStartsWithNewLine ifFalse:[
+		    newSource := newSource , '\' withCRs.
+		].
+		newSource := newSource , bodyPart.
+
+		result := Compiler compile:newSource forClass:mClass install:false.
+		(result isNil or:[result == #Error]) ifTrue:[
+		    Dialog warn:(resources string:'Failed to compile new version of %1' with:eachMethod whoString allBold).
+		] ifFalse:[
+		    useRefactoringSupport ifTrue:[
+			changes
+			    compile:newSource
+			    in:mClass
+			    classified:category.
+		    ] ifFalse:[
+			newMethod := mClass
+					compile:newSource
+					classified:category.
+		    ].
+		    methodsToChangePackage add:(Array with:mClass
+						      with:selector
+						      with:eachMethod package).
+		].
+	    ].
+	].
     ].
     useRefactoringSupport ifTrue:[
-        RefactoryChangeManager performChange: changes.
+	RefactoryChangeManager performChange: changes.
     ].
     methodsToChangePackage triplesDo:[:cls :sel :pkg|
-        (cls compiledMethodAt:sel) setPackage:pkg.
+	(cls compiledMethodAt:sel) setPackage:pkg.
     ].
 
     "Created: / 23-11-2006 / 16:52:27 / cg"
@@ -42279,17 +42750,17 @@
     newClass isNil ifTrue:[^ self].
 
     doWhat == #moveAndForward ifTrue:[
-        newClass isMeta ifFalse:[
-            (Dialog
-                confirm:(resources
-                            stringWithCRs:'Destination must be a Metaclass.\\Moving to %1.'
-                            with:newClass theMetaclass name)
-                noLabel:(resources string:'Cancel')
-            ) ifFalse:[
-                ^  self
-            ].
-            newClass := newClass theMetaclass.
-        ].
+	newClass isMeta ifFalse:[
+	    (Dialog
+		confirm:(resources
+			    stringWithCRs:'Destination must be a Metaclass.\\Moving to %1.'
+			    with:newClass theMetaclass name)
+		noLabel:(resources string:'Cancel')
+	    ) ifFalse:[
+		^  self
+	    ].
+	    newClass := newClass theMetaclass.
+	].
     ].
 
     methods := self selectedMethodsValue.
@@ -42312,17 +42783,17 @@
 
     perPackageMethods := Dictionary new.
     self selectedMethodsValue do:[:eachMethod |
-        |methodsPackage classPackage set|
-
-        methodsPackage := eachMethod package.
-        classPackage := eachMethod mclass package.
-        methodsPackage ~= classPackage ifTrue:[
-            set := perPackageMethods at:classPackage ifAbsentPut:[Set new].
-            set add:eachMethod.
-        ].
+	|methodsPackage classPackage set|
+
+	methodsPackage := eachMethod package.
+	classPackage := eachMethod mclass package.
+	methodsPackage ~= classPackage ifTrue:[
+	    set := perPackageMethods at:classPackage ifAbsentPut:[Set new].
+	    set add:eachMethod.
+	].
     ].
     perPackageMethods keysAndValuesDo:[:pkg :setOfMethods |
-        self moveMethods:setOfMethods toProject:pkg
+	self moveMethods:setOfMethods toProject:pkg
     ].
 
     "Created: / 22-11-2006 / 13:17:00 / cg"
@@ -42344,29 +42815,29 @@
     classProjects := (affectedMethods collect:[:eachMethod | eachMethod mclass package]) asSet.
 
     LastProjectMoves size > 0 ifTrue:[
-        offered := LastProjectMoves first
-    ] ifFalse:[
-        classProjects size == 1 ifTrue:[
-            offered := classProjects first
-        ] ifFalse:[
-            offered := "classesProject ? "Project current package
-        ].
+	offered := LastProjectMoves first
+    ] ifFalse:[
+	classProjects size == 1 ifTrue:[
+	    offered := classProjects first
+	] ifFalse:[
+	    offered := "classesProject ? "Project current package
+	].
     ].
     classProjects remove:offered ifAbsent:[].
     classProjects := classProjects asOrderedCollection.
 
     classProjects size == 1 ifTrue:[
-        msg := resources stringWithCRs:'Move method(s) to which project:\(Hint: The class is in ''%1'')\'
-                 with:(classProjects first allBold).
-    ] ifFalse:[
-        msg := resources stringWithCRs:'Move method(s) to which project:\'.
+	msg := resources stringWithCRs:'Move method(s) to which project:\(Hint: The class is in ''%1'')\'
+		 with:(classProjects first allBold).
+    ] ifFalse:[
+	msg := resources stringWithCRs:'Move method(s) to which project:\'.
     ].
     newProject := self
-                    askForProject:msg
-                    initialText:offered
-                    moreSuggestions:classProjects.
+		    askForProject:msg
+		    initialText:offered
+		    moreSuggestions:classProjects.
     newProject notNil ifTrue:[
-        self doMoveSelectedMethodsToProject:newProject.
+	self doMoveSelectedMethodsToProject:newProject.
     ].
 
     "Created: / 17-02-2000 / 23:02:49 / cg"
@@ -42386,140 +42857,140 @@
 
     "/ offer the current classes's protocols in the dialog
     (selClasses := self selectedClassesValue) notNil ifTrue:[
-        selClasses do:[:eachClass |
-            someCategories addAll:(eachClass categories).
-        ]
-    ] ifFalse:[
-        "/ offer the current method-classes' protocols in the dialog
-        methodSelection do:[:eachMethod | |cls|
-            (cls := eachMethod mclass) notNil ifTrue:[
-                someCategories addAll:cls categories
-            ]
-        ]
+	selClasses do:[:eachClass |
+	    someCategories addAll:(eachClass categories).
+	]
+    ] ifFalse:[
+	"/ offer the current method-classes' protocols in the dialog
+	methodSelection do:[:eachMethod | |cls|
+	    (cls := eachMethod mclass) notNil ifTrue:[
+		someCategories addAll:cls categories
+	    ]
+	]
     ].
 
     selectors := methodSelection collect:[:each | each selector].
 
     "/ if all selectors are getters/setters, add 'accessing'
     RBParser notNil ifTrue:[
-        |searcher allGettersOrSetters allReturnTrueOrFalse|
-
-        searcher := ParseTreeSearcher isGetterOrSetterMethod.
-        allGettersOrSetters := 
-            methodSelection 
-                conform:[:eachMethod |
-                    |tree|
-
-                    tree := RBParser 
-                             parseSearchMethod:(eachMethod source) 
-                             onError: [:str :pos | nil].
-
-                    tree notNil and:[ searcher executeTree:tree initialAnswer:false ].   
-                ].
-        allGettersOrSetters ifTrue:[
-            someCategories add:'accessing'.
-            goodCandidates add:'accessing'.
-            initialAnswer := 'accessing'.
-        ].
-
-        searcher := ParseTreeSearcher isJustReturningTrueOrFalse.
-        allReturnTrueOrFalse := 
-            methodSelection 
-                conform:[:eachMethod |
-                    |tree|
-                    tree := RBParser 
-                             parseSearchMethod:(eachMethod source) 
-                             onError: [:str :pos | nil].
-
-                    tree notNil and:[ searcher executeTree:tree initialAnswer:false ].   
-                ].
-        allReturnTrueOrFalse ifTrue:[
-            someCategories add:'testing'.
-            goodCandidates add:'testing'.
-            initialAnswer := 'testing'.
-        ].
+	|searcher allGettersOrSetters allReturnTrueOrFalse|
+
+	searcher := ParseTreeSearcher isGetterOrSetterMethod.
+	allGettersOrSetters :=
+	    methodSelection
+		conform:[:eachMethod |
+		    |tree|
+
+		    tree := RBParser
+			     parseSearchMethod:(eachMethod source)
+			     onError: [:str :pos | nil].
+
+		    tree notNil and:[ searcher executeTree:tree initialAnswer:false ].
+		].
+	allGettersOrSetters ifTrue:[
+	    someCategories add:'accessing'.
+	    goodCandidates add:'accessing'.
+	    initialAnswer := 'accessing'.
+	].
+
+	searcher := ParseTreeSearcher isJustReturningTrueOrFalse.
+	allReturnTrueOrFalse :=
+	    methodSelection
+		conform:[:eachMethod |
+		    |tree|
+		    tree := RBParser
+			     parseSearchMethod:(eachMethod source)
+			     onError: [:str :pos | nil].
+
+		    tree notNil and:[ searcher executeTree:tree initialAnswer:false ].
+		].
+	allReturnTrueOrFalse ifTrue:[
+	    someCategories add:'testing'.
+	    goodCandidates add:'testing'.
+	    initialAnswer := 'testing'.
+	].
     ].
 
     "/ add actual categories of selected methods
     (SystemBrowser findImplementorsOfAny:selectors in:(Smalltalk allClasses) ignoreCase:false)
     do:[:otherMethod |
-        |cat|
-
-        (methodSelection includesIdentical:otherMethod) ifFalse:[
-            cat := otherMethod category.
-            someCategories add:cat.
-            goodCandidates add:cat.
-        ]
+	|cat|
+
+	(methodSelection includesIdentical:otherMethod) ifFalse:[
+	    cat := otherMethod category.
+	    someCategories add:cat.
+	    goodCandidates add:cat.
+	]
     ].
 
     "/ for isXXX methods, add 'testing'
     (methodSelection contains:[:method | method selector = ('is',method mclass name) ]) ifTrue:[
-        someCategories add:'testing'.
-        goodCandidates add:'testing'.
+	someCategories add:'testing'.
+	goodCandidates add:'testing'.
     ].
     "/ for hasXXX, canXXX methods, add 'queries'
     (methodSelection contains:[:method | |sel|
-                                sel := method selector.
-                                ((sel startsWith:'has') and:[sel size > 3 and:[ (sel at:4) isUppercase ]])
-                                or:[ ((sel startsWith:'can') and:[sel size > 3 and:[ (sel at:4) isUppercase ]]) ]]) ifTrue:[
-        someCategories add:'queries'.
-        goodCandidates add:'queries'.
+				sel := method selector.
+				((sel startsWith:'has') and:[sel size > 3 and:[ (sel at:4) isUppercase ]])
+				or:[ ((sel startsWith:'can') and:[sel size > 3 and:[ (sel at:4) isUppercase ]]) ]]) ifTrue:[
+	someCategories add:'queries'.
+	goodCandidates add:'queries'.
     ].
     (methodSelection contains:[:method | method selector asLowercase endsWith:'do:']) ifTrue:[
-        someCategories add:'enumeration'.
-        goodCandidates add:'enumeration'.
+	someCategories add:'enumeration'.
+	goodCandidates add:'enumeration'.
     ].
 
     goodCandidates size == 1 ifTrue:[
-        initialAnswer := goodCandidates anElement
-    ] ifFalse:[
-        (mthd := self theSingleSelectedMethod) notNil ifTrue:[
-            gotInherited := false.
-
-            "look for protocol of inherited"
-            superClass := mthd mclass superclass.
-            superClass notNil ifTrue:[
-                superClass := superClass whichClassIncludesSelector:mthd selector.
-                superClass notNil ifTrue:[
-                    inherited := superClass compiledMethodAt:mthd selector.
-                    inherited notNil ifTrue:[
-                        initialAnswer := inherited category.
-                        gotInherited := true.
-                    ]
-                ] ifFalse:[
-                    superClass := mthd mclass superclass.
-                ].
-            ].
-            "look for majority protocol in subclasses"
-            subclassCategories := Bag new.
-            mthd mclass allSubclassesDo:[:cls |
-                |redefined|
-
-                redefined := superClass compiledMethodAt:mthd selector.
-                redefined notNil ifTrue:[
-                    subclassCategories add:(redefined category).
-                ]
-            ].
-            subclassCategories notEmpty ifTrue:[
-                subclassCategories := (subclassCategories valuesAndCounts 
-                                            sort:[:a :b | a value > b value])
-                                                collect:[:each | each key].
-                someCategories addAll:(subclassCategories first:(3 min:subclassCategories size)).
-                gotInherited ifFalse:[
-                    initialAnswer := subclassCategories first.
-                ]
-            ].
-        ]
+	initialAnswer := goodCandidates anElement
+    ] ifFalse:[
+	(mthd := self theSingleSelectedMethod) notNil ifTrue:[
+	    gotInherited := false.
+
+	    "look for protocol of inherited"
+	    superClass := mthd mclass superclass.
+	    superClass notNil ifTrue:[
+		superClass := superClass whichClassIncludesSelector:mthd selector.
+		superClass notNil ifTrue:[
+		    inherited := superClass compiledMethodAt:mthd selector.
+		    inherited notNil ifTrue:[
+			initialAnswer := inherited category.
+			gotInherited := true.
+		    ]
+		] ifFalse:[
+		    superClass := mthd mclass superclass.
+		].
+	    ].
+	    "look for majority protocol in subclasses"
+	    subclassCategories := Bag new.
+	    mthd mclass allSubclassesDo:[:cls |
+		|redefined|
+
+		redefined := superClass compiledMethodAt:mthd selector.
+		redefined notNil ifTrue:[
+		    subclassCategories add:(redefined category).
+		]
+	    ].
+	    subclassCategories notEmpty ifTrue:[
+		subclassCategories := (subclassCategories valuesAndCounts
+					    sort:[:a :b | a value > b value])
+						collect:[:each | each key].
+		someCategories addAll:(subclassCategories first:(3 min:subclassCategories size)).
+		gotInherited ifFalse:[
+		    initialAnswer := subclassCategories first.
+		]
+	    ].
+	]
     ].
 
     someCategories := someCategories asOrderedCollection sort.
 
     newCategory := self
-                        askForMethodCategory:'Move to which protocol ?'
-                        title:'Change MethodCategory'
-                        okLabel:'Move'
-                        list:someCategories
-                        initialAnswer:(initialAnswer ? (lastMethodCategory ? self theSingleSelectedProtocol)).
+			askForMethodCategory:'Move to which protocol ?'
+			title:'Change MethodCategory'
+			okLabel:'Move'
+			list:someCategories
+			initialAnswer:(initialAnswer ? (lastMethodCategory ? self theSingleSelectedProtocol)).
 
     self moveMethods:methodSelection toProtocol:newCategory
 
@@ -42568,15 +43039,15 @@
     |editorClass currentClass|
 
     (currentClass := self theSingleSelectedClass) notNil ifTrue:[
-        "/
-        "/ kludge - this info should come from somewhere else ...
-        "/
-        editorClass := self class resourceEditorClassFor:specTypeSymbol.
-        editorClass notNil ifTrue: [
-            editorClass
-                openOnClass:currentClass theNonMetaclass
-                andSelector:nil
-        ]
+	"/
+	"/ kludge - this info should come from somewhere else ...
+	"/
+	editorClass := self class resourceEditorClassFor:specTypeSymbol.
+	editorClass notNil ifTrue: [
+	    editorClass
+		openOnClass:currentClass theNonMetaclass
+		andSelector:nil
+	]
     ]
 
     "Created: / 01-03-2007 / 20:55:46 / cg"
@@ -42604,7 +43075,7 @@
     printStream := Printer new.
 
     self selectedMethodsDo:[:eachMethod |
-        eachMethod mclass printOutSource:(eachMethod source) on:printStream.
+	eachMethod mclass printOutSource:(eachMethod source) on:printStream.
     ].
     printStream close
 !
@@ -42634,26 +43105,26 @@
 
      "/ example (rename all foo* methods)
      (selector startsWith:''foo'') ifTrue:[
-        newSource := ''bar'' , (method source copyFrom:3+1).
-        class
-            compile:newSource
-            classified:(method category).
-        class removeSelector:selector.
+	newSource := ''bar'' , (method source copyFrom:3+1).
+	class
+	    compile:newSource
+	    classified:(method category).
+	class removeSelector:selector.
      ].
 ].
 '.
 
     LastMethodProcessingBlockString isNil ifTrue:[
-        LastMethodProcessingBlockString := template.
+	LastMethodProcessingBlockString := template.
     ].
 
     textHolder := ValueHolder new.
     dialog := Dialog
-                 forRequestText:(resources string:'Enter method processing block')
-                 lines:25
-                 columns:70
-                 initialAnswer:LastMethodProcessingBlockString
-                 model:textHolder.
+		 forRequestText:(resources string:'Enter method processing block')
+		 lines:25
+		 columns:70
+		 initialAnswer:LastMethodProcessingBlockString
+		 model:textHolder.
     dialog addButton:(Button label:'Template' action:[textHolder value:template. textHolder changed:#value.]).
     dialog open.
     dialog accepted ifFalse:[^ self].
@@ -42663,17 +43134,17 @@
 
     processingBlock := Parser evaluate:processingBlockString.
     processingBlock isBlock ifFalse:[
-        self error:'bad input'.
-        ^ self
-    ].
-
-    self
-        selectedMethodsDo:[:eachMethod |
-            processingBlock
-                value:(eachMethod mclass)
-                value:(eachMethod selector)
-                value:eachMethod
-        ]
+	self error:'bad input'.
+	^ self
+    ].
+
+    self
+	selectedMethodsDo:[:eachMethod |
+	    processingBlock
+		value:(eachMethod mclass)
+		value:(eachMethod selector)
+		value:eachMethod
+	]
 !
 
 selectorMenuPushDownMethod
@@ -42693,26 +43164,26 @@
     selectedMethods := self selectedMethodsValue.
 
     (selectedMethods collect:[:m | m mclass]) asIdentitySet do:[:eachClass |
-        |methods selectors nm|
-
-        methods := selectedMethods select:[:m | m mclass == eachClass].
-        selectedMethods := selectedMethods select:[:m | m mclass ~~ eachClass].
-        selectors := methods collect:[:each | each  selector].
-        upOrDown == #down ifTrue:[
-            refactoring := PushDownMethodRefactoring pushDown:selectors from:eachClass.
-            nm := 'Push down '.
-        ] ifFalse:[
-            refactoring := PushUpMethodRefactoring pushUp:selectors from:eachClass.
-            nm := 'Push up '.
-        ].
-        selectors size == 1 ifTrue:[
-            nm := nm , selectors first.
-        ] ifFalse:[
-            nm := nm , selectors size printString , ' methods'.
-        ].
-        nm := nm , ' from ' , eachClass name.
-        refactoring model name:nm.
-        self performRefactoring:refactoring.
+	|methods selectors nm|
+
+	methods := selectedMethods select:[:m | m mclass == eachClass].
+	selectedMethods := selectedMethods select:[:m | m mclass ~~ eachClass].
+	selectors := methods collect:[:each | each  selector].
+	upOrDown == #down ifTrue:[
+	    refactoring := PushDownMethodRefactoring pushDown:selectors from:eachClass.
+	    nm := 'Push down '.
+	] ifFalse:[
+	    refactoring := PushUpMethodRefactoring pushUp:selectors from:eachClass.
+	    nm := 'Push up '.
+	].
+	selectors size == 1 ifTrue:[
+	    nm := nm , selectors first.
+	] ifFalse:[
+	    nm := nm , selectors size printString , ' methods'.
+	].
+	nm := nm , ' from ' , eachClass name.
+	refactoring model name:nm.
+	self performRefactoring:refactoring.
     ].
 
     "Modified: / 28-02-2012 / 16:29:38 / cg"
@@ -42728,7 +43199,7 @@
     "recompile the selected methods (for Debug only)"
 
     self selectedMethodsValue do:[:eachMethod |
-        eachMethod mclass recompile:eachMethod selector
+	eachMethod mclass recompile:eachMethod selector
     ]
 
     "Modified: / 28-02-2012 / 16:29:42 / cg"
@@ -42747,7 +43218,7 @@
     |currentMethod cls selector tree args whichParameter|
 
     (self askIfModified) ifFalse:[
-        ^ self
+	^ self
     ].
 
     currentMethod := self theSingleSelectedMethod.
@@ -42757,18 +43228,18 @@
 
     tree := cls parseTreeFor:selector.
     tree isNil ifTrue:[
-        self warn: 'Could not parse the method'.
-        ^ self
+	self warn: 'Could not parse the method'.
+	^ self
     ].
     args := tree argumentNames.
     args size > 1 ifTrue:[
-        whichParameter := self selectionInCodeView.
-        (whichParameter notEmptyOrNil and:[ args includes:whichParameter]) ifFalse:[
-            whichParameter := Dialog choose:'Remove which Parameter ?' fromList:args lines:5 title:'Remove Parameter'.
-            whichParameter isEmptyOrNil ifTrue:[^ self].
-        ].
-    ] ifFalse:[
-        whichParameter := args first.
+	whichParameter := self selectionInCodeView.
+	(whichParameter notEmptyOrNil and:[ args includes:whichParameter]) ifFalse:[
+	    whichParameter := Dialog choose:'Remove which Parameter ?' fromList:args lines:5 title:'Remove Parameter'.
+	    whichParameter isEmptyOrNil ifTrue:[^ self].
+	].
+    ] ifFalse:[
+	whichParameter := args first.
     ].
 
     self codeMenuRemoveParameter:whichParameter
@@ -42781,26 +43252,26 @@
 
     mthd := self theSingleSelectedMethod.
     mthd isNil ifTrue:[
-        methods := self selectedMethodsValue.
-        (methods asSet collect:[:eachMethod | eachMethod selector]) size == 1 ifTrue:[
-            mthd := methods first.
-        ]
+	methods := self selectedMethodsValue.
+	(methods asSet collect:[:eachMethod | eachMethod selector]) size == 1 ifTrue:[
+	    mthd := methods first.
+	]
     ].
     mthd isNil ifTrue:[
-        AbortAllSignal catch:[
-            selectorsDone := Set new.
-            methods do:[:eachMethod |
-                |eachSelector|
-
-                eachSelector := eachMethod selector.
-                (selectorsDone includes:eachSelector) ifFalse:[
-                    self renameMethod:eachSelector in:eachMethod mclass.
-                    selectorsDone add:eachSelector.
-                ]
-            ]
-        ]
-    ] ifFalse:[
-        self renameMethod:(mthd selector) in:(mthd mclass).
+	AbortAllSignal catch:[
+	    selectorsDone := Set new.
+	    methods do:[:eachMethod |
+		|eachSelector|
+
+		eachSelector := eachMethod selector.
+		(selectorsDone includes:eachSelector) ifFalse:[
+		    self renameMethod:eachSelector in:eachMethod mclass.
+		    selectorsDone add:eachSelector.
+		]
+	    ]
+	]
+    ] ifFalse:[
+	self renameMethod:(mthd selector) in:(mthd mclass).
     ]
 "/    |mthd|
 "/
@@ -42812,8 +43283,8 @@
 
 selectorMenuRewrite
     MethodRewriter new
-        methods: self selectedMethodsValue;
-        open
+	methods: self selectedMethodsValue;
+	open
 
     "Created: / 05-07-2011 / 14:49:06 / cg"
 !
@@ -42828,12 +43299,12 @@
     selectorsToRemove := IdentitySet new.
     numVersionMethods := 0.
     self selectedMethodsDo:[:eachMethod |
-        selectorsToRemove add:(eachMethod selector).
-        (AbstractSourceCodeManager isVersionMethodSelector:eachMethod selector) ifTrue:[
-            eachMethod mclass isMeta ifTrue:[
-                numVersionMethods := numVersionMethods + 1
-            ]
-        ]
+	selectorsToRemove add:(eachMethod selector).
+	(AbstractSourceCodeManager isVersionMethodSelector:eachMethod selector) ifTrue:[
+	    eachMethod mclass isMeta ifTrue:[
+		numVersionMethods := numVersionMethods + 1
+	    ]
+	]
     ].
 
     selectorsToCheckForInvokation := IdentitySet new addAll:selectorsToRemove; yourself.
@@ -42845,109 +43316,109 @@
     methodsToRemove := self selectedMethodsValue copy.
 
     self withSearchCursorDo:[
-        "/ search through all of the system
-        Smalltalk allMethodsDo:[:mthd |
-            |sent resources newFound any|
-
-            any := false.
-            mthd literalsDo:[:eachLiteral |
-                 (selectorsToRemove includes:eachLiteral) ifTrue:[any := true].
-                 "/ could be an array (as in a spec)
-                 eachLiteral isArray ifTrue:[
-                    selectorsToRemove contains:[:selToRemove |
-                        (eachLiteral refersToLiteral:selToRemove) ifTrue:[
-                            possiblyUsedAsSelector add:mthd.
-                        ]
-                    ]
-                ]
-            ].
-            any ifTrue:[
-                selectorsToRemove do:[:eachSelectorToRemove |
-                    sent := mthd messagesSent.
-                   (sent includes:eachSelectorToRemove) ifTrue:[
-                       (methodsToRemove includesIdentical:mthd) ifFalse:[
-                           possiblyInvoked add:mthd.
-                       ]
-                   ]
-               ]
-            ].
-            mthd hasResource ifTrue:[
-                newFound := IdentitySet new.
-                selectorsToRemove do:[:eachSelectorToRemove |
-                    (mthd refersToLiteral:eachSelectorToRemove) ifTrue:[
-                        (methodsToRemove includesIdentical:mthd) ifFalse:[
-                            possiblyUsedAsSelector add:mthd.
-                        ]
-                    ].
-                ].
-            ].
-        ].
+	"/ search through all of the system
+	Smalltalk allMethodsDo:[:mthd |
+	    |sent resources newFound any|
+
+	    any := false.
+	    mthd literalsDo:[:eachLiteral |
+		 (selectorsToRemove includes:eachLiteral) ifTrue:[any := true].
+		 "/ could be an array (as in a spec)
+		 eachLiteral isArray ifTrue:[
+		    selectorsToRemove contains:[:selToRemove |
+			(eachLiteral refersToLiteral:selToRemove) ifTrue:[
+			    possiblyUsedAsSelector add:mthd.
+			]
+		    ]
+		]
+	    ].
+	    any ifTrue:[
+		selectorsToRemove do:[:eachSelectorToRemove |
+		    sent := mthd messagesSent.
+		   (sent includes:eachSelectorToRemove) ifTrue:[
+		       (methodsToRemove includesIdentical:mthd) ifFalse:[
+			   possiblyInvoked add:mthd.
+		       ]
+		   ]
+	       ]
+	    ].
+	    mthd hasResource ifTrue:[
+		newFound := IdentitySet new.
+		selectorsToRemove do:[:eachSelectorToRemove |
+		    (mthd refersToLiteral:eachSelectorToRemove) ifTrue:[
+			(methodsToRemove includesIdentical:mthd) ifFalse:[
+			    possiblyUsedAsSelector add:mthd.
+			]
+		    ].
+		].
+	    ].
+	].
     ].
     self normalLabel.
 
     possiblyInvoked isEmpty ifTrue:[
-        possiblyUsedAsSelector isEmpty ifTrue:[
-            self selectorMenuRemove.
-            ^ self.
-        ]
+	possiblyUsedAsSelector isEmpty ifTrue:[
+	    self selectorMenuRemove.
+	    ^ self.
+	]
     ].
 
     selectorsToRemove size == 1 ifTrue:[
-        selInfo := selectorsToRemove first allBold.
-        isAre := 'is'
-    ] ifFalse:[
-        selInfo := 'selectors to remove'.
-        isAre := 'are'
+	selInfo := selectorsToRemove first allBold.
+	isAre := 'is'
+    ] ifFalse:[
+	selInfo := 'selectors to remove'.
+	isAre := 'are'
     ].
     msg := selInfo , ' '.
 
     possiblyInvoked notEmpty ifTrue:[
-        msg := msg , isAre , ' possibly sent by %1 methods '
+	msg := msg , isAre , ' possibly sent by %1 methods '
     ].
     possiblyUsedAsSelector notEmpty ifTrue:[
-        possiblyInvoked notEmpty ifTrue:[
-            msg := msg , 'and '
-        ].
-        msg := msg , 'possibly used as selector by %2 methods'
+	possiblyInvoked notEmpty ifTrue:[
+	    msg := msg , 'and '
+	].
+	msg := msg , 'possibly used as selector by %2 methods'
     ].
 
     numVersionMethods > 0 ifTrue:[
-        msg := msg , '\\' ,
-               (resources
-                string:'ATTENTION: Removing a classes version method might make the versionManagers life hard.' allBold).
+	msg := msg , '\\' ,
+	       (resources
+		string:'ATTENTION: Removing a classes version method might make the versionManagers life hard.' allBold).
     ].
 
     answer := OptionBox
-                  request:((resources string:msg 
-                                        with:possiblyInvoked size 
-                                        with:possiblyUsedAsSelector size)
-                           , '\\Really remove ?') withCRs
-                  label:(resources string:'Attention')
-                  image:(WarningBox iconBitmap)
-                  buttonLabels:(resources array:#( 'Cancel' 'Remove' 'Remove then Browse Senders' 'Browse Senders'))
-                  values:#(false true #removeAndBrowse #browse )
-                  default:#browse
-                  onCancel:false.
+		  request:((resources string:msg
+					with:possiblyInvoked size
+					with:possiblyUsedAsSelector size)
+			   , '\\Really remove ?') withCRs
+		  label:(resources string:'Attention')
+		  image:(WarningBox iconBitmap)
+		  buttonLabels:(resources array:#( 'Cancel' 'Remove' 'Remove then Browse Senders' 'Browse Senders'))
+		  values:#(false true #removeAndBrowse #browse )
+		  default:#removeAndBrowse
+		  onCancel:false.
 
      answer == false ifTrue:[^ self].
      (answer == #browse or:[answer == #removeAndBrowse]) ifTrue:[
-        methods := IdentitySet new.
-        methods addAll:possiblyInvoked.
-        methods addAll:possiblyUsedAsSelector.
-        brwsr := self
-                    spawnMethodBrowserFor:methods in:#newBuffer
-                    label:'methods referring to ' , selInfo
-                    perMethodInfo:nil
-                    sortBy:#class.
-        selectorsToRemove size == 1 ifTrue:[
-            brwsr autoSearchPattern:selInfo
-        ].
-        answer == #browse ifTrue:[ ^ self ].
-        "/ fall into remove
+	methods := IdentitySet new.
+	methods addAll:possiblyInvoked.
+	methods addAll:possiblyUsedAsSelector.
+	brwsr := self
+		    spawnMethodBrowserFor:methods in:#newBuffer
+		    label:'methods referring to ' , selInfo
+		    perMethodInfo:nil
+		    sortBy:#class.
+	selectorsToRemove size == 1 ifTrue:[
+	    brwsr autoSearchPattern:selInfo
+	].
+	answer == #browse ifTrue:[ ^ self ].
+	"/ fall into remove
      ].
      self doRemoveMethodsUnconfirmed:methodsToRemove
 
-    "Modified: / 28-04-2012 / 11:12:03 / cg"
+    "Modified: / 11-05-2012 / 10:00:46 / cg"
 !
 
 selectorMenuSelectMethodsWithString
@@ -42965,8 +43436,8 @@
 
     projects := (self selectedMethodsValue collect:[:m | m package]) asSet asSortedCollection.
     ^ self
-        spawnProjectBrowserFor:projects
-        in:#newBrowser
+	spawnProjectBrowserFor:projects
+	in:#newBrowser
 
     "Modified: / 28-02-2012 / 16:30:06 / cg"
 !
@@ -42978,8 +43449,8 @@
 
     projects := (self selectedMethodsValue collect:[:m | m package]) asSet asSortedCollection.
     ^ self
-        spawnProjectBrowserFor:projects
-        in:#newBuffer
+	spawnProjectBrowserFor:projects
+	in:#newBuffer
 
     "Modified: / 28-02-2012 / 16:30:08 / cg"
 !
@@ -42988,8 +43459,8 @@
     "open a new browser showing implementations of the selected method"
 
     ^ self
-        spawnMethodImplementorsBrowserFor:(self selectedSelectors)
-        in:#newBrowser
+	spawnMethodImplementorsBrowserFor:(self selectedSelectors)
+	in:#newBrowser
 
 
 !
@@ -42998,8 +43469,8 @@
     "add a new buffer showing implementations of the selected method"
 
     ^ self
-        spawnMethodImplementorsBrowserFor:(self selectedSelectors)
-        in:#newBuffer
+	spawnMethodImplementorsBrowserFor:(self selectedSelectors)
+	in:#newBuffer
 
 
 !
@@ -43008,8 +43479,8 @@
     "open a new browser showing inheritance of the selected method(s)"
 
     ^ self
-        spawnMethodInheritanceBrowserFor:(self selectedSelectors)
-        in:#newBrowser
+	spawnMethodInheritanceBrowserFor:(self selectedSelectors)
+	in:#newBrowser
 
 
 !
@@ -43018,8 +43489,8 @@
     "add a buffer showing inheritance of the selected method(s)"
 
     ^ self
-        spawnMethodInheritanceBrowserFor:(self selectedSelectors)
-        in:#newBuffer
+	spawnMethodInheritanceBrowserFor:(self selectedSelectors)
+	in:#newBuffer
 
 
 !
@@ -43028,9 +43499,9 @@
     "open a new browser showing the selected methods only"
 
     ^ self
-        spawnMethodBrowserFor:(self selectedMethodsValue)
-        in:#newBrowser
-        label:nil
+	spawnMethodBrowserFor:(self selectedMethodsValue)
+	in:#newBrowser
+	label:nil
 
     "Modified: / 28-02-2012 / 16:30:11 / cg"
 !
@@ -43039,9 +43510,9 @@
     "add a new buffer showing the selected methods only"
 
     ^ self
-        spawnMethodBrowserFor:(self selectedMethodsValue)
-        in:#newBuffer
-        label:nil
+	spawnMethodBrowserFor:(self selectedMethodsValue)
+	in:#newBuffer
+	label:nil
 
     "Modified: / 28-02-2012 / 16:30:14 / cg"
 !
@@ -43051,8 +43522,8 @@
      selected methods project(s)"
 
     ^ self
-        spawnProjectExtensionsBrowserFor:(self selectedMethodsValue)
-        in:#newBrowser
+	spawnProjectExtensionsBrowserFor:(self selectedMethodsValue)
+	in:#newBrowser
 
     "Modified: / 28-02-2012 / 16:30:16 / cg"
 !
@@ -43062,8 +43533,8 @@
      selected methods project(s)"
 
     ^ self
-        spawnProjectExtensionsBrowserFor:(self selectedMethodsValue)
-        in:#newBuffer
+	spawnProjectExtensionsBrowserFor:(self selectedMethodsValue)
+	in:#newBuffer
 
     "Modified: / 28-02-2012 / 16:30:19 / cg"
 !
@@ -43072,8 +43543,8 @@
     "open a new browser showing senders of the selected method"
 
     ^ self
-        spawnMethodSendersBrowserFor:(self selectedSelectors)
-        in:#newBrowser
+	spawnMethodSendersBrowserFor:(self selectedSelectors)
+	in:#newBrowser
 
 
 !
@@ -43082,8 +43553,8 @@
     "add a new buffer showing senders of the selected methods selector"
 
     ^ self
-        spawnMethodSendersBrowserFor:(self selectedSelectors)
-        in:#newBuffer
+	spawnMethodSendersBrowserFor:(self selectedSelectors)
+	in:#newBuffer
 
 
 !
@@ -43108,48 +43579,48 @@
     "Created: / 27-04-2010 / 15:09:20 / cg"
 !
 
-spawnCallersBrowserFor:aMethodCollection in:openHow 
+spawnCallersBrowserFor:aMethodCollection in:openHow
     "open a new browser or add a buffer showing the selected method's callers"
 
     |label|
 
     self withSearchCursorDo:[
-        |cachedList newBrowser searchBlock|
-
-        aMethodCollection size == 1 ifTrue:[
-            label := resources string:('Callers of %1') with:aMethodCollection first whoString allBold.
-        ] ifFalse:[
-            label := resources string:'Callers of Any'.
-        ].
-
-        searchBlock := [
-                            |l|
-
-                            cachedList notNil ifTrue:[
-                                l := cachedList.
-                                cachedList := nil
-                            ] ifFalse:[
-                                l := IdentitySet new.
-                                aMethodCollection do:[:eachCalledMethod |
-                                    |info|
-
-                                    info := eachCalledMethod methodInvocationInfo.
-                                    info notNil ifTrue:[
-                                        info callingMethodsDo:[:caller |
-                                            l add:caller
-                                        ]
-                                    ]
-                                ].
-                                l := l asOrderedCollection
-                            ].
-                            l
-                       ].
-
-        newBrowser := self
-                        spawnMethodBrowserForSearch:searchBlock
-                        sortBy:#class
-                        in:openHow
-                        label:label.
+	|cachedList newBrowser searchBlock|
+
+	aMethodCollection size == 1 ifTrue:[
+	    label := resources string:('Callers of %1') with:aMethodCollection first whoString allBold.
+	] ifFalse:[
+	    label := resources string:'Callers of Any'.
+	].
+
+	searchBlock := [
+			    |l|
+
+			    cachedList notNil ifTrue:[
+				l := cachedList.
+				cachedList := nil
+			    ] ifFalse:[
+				l := IdentitySet new.
+				aMethodCollection do:[:eachCalledMethod |
+				    |info|
+
+				    info := eachCalledMethod methodInvocationInfo.
+				    info notNil ifTrue:[
+					info callingMethodsDo:[:caller |
+					    l add:caller
+					]
+				    ]
+				].
+				l := l asOrderedCollection
+			    ].
+			    l
+		       ].
+
+	newBrowser := self
+			spawnMethodBrowserForSearch:searchBlock
+			sortBy:#class
+			in:openHow
+			label:label.
     ]
 
     "Created: / 27-04-2010 / 15:16:40 / cg"
@@ -43163,7 +43634,7 @@
     "Created: / 27-04-2010 / 15:09:02 / cg"
 !
 
-spawnCallersIn:openHow 
+spawnCallersIn:openHow
     "open a new browser or add a buffer showing the selected method's callers"
 
     self spawnCallersBrowserFor:(self selectedMethodsValue) in:openHow
@@ -43185,8 +43656,8 @@
 
 spawnImplementorChainIn:openHow
     "browse implementation chain;
-        openHow is: #newBrowser - open a new browser showing the method(s)
-        openHow is: #newBuffer  - add a new buffer showing the method(s)
+	openHow is: #newBrowser - open a new browser showing the method(s)
+	openHow is: #newBuffer  - add a new buffer showing the method(s)
     "
 
     |searchBlock "must be first local in block (see #methodsSelectionChangedAt:index, which fetches this value)"
@@ -43194,70 +43665,70 @@
 
     multipleMethods := self selectedMethodsValue size > 1.
     multipleMethods ifTrue:[
-        methods := self selectedMethodsValue copy.
-        lbl := resources string:'implementor chains'.
-    ] ifFalse:[
-        aMethod := self theSingleSelectedMethod.
-        lbl := resources string:'implementor chain of %1' with:aMethod selector.
+	methods := self selectedMethodsValue copy.
+	lbl := resources string:'implementor chains'.
+    ] ifFalse:[
+	aMethod := self theSingleSelectedMethod.
+	lbl := resources string:'implementor chain of %1' with:aMethod selector.
     ].
     spec := #chainBrowserSpec.
 
     ^ self
-        newBrowserOrBufferDependingOn:openHow
-        label:lbl
-        forSpec:spec
-        setupWith:[:brwsr |
-            |methodListGenerator generator theMethodList|
-
-            searchBlock := [:whichMethod |
-                                | sentMessages |
-                                sentMessages := whichMethod messagesSent.
-                                self class findImplementorsOfAny:sentMessages in:(Smalltalk allClasses) ignoreCase:false.
-                           ].
-
-            generator := Iterator on:[:whatToDo |
-                                            theMethodList isNil ifTrue:[
-                                                theMethodList := searchBlock value:aMethod.
-                                            ].
-                                            theMethodList do:[:aMethod |
-                                                whatToDo
-                                                    value:aMethod mclass
-                                                    value:aMethod category
-                                                    value:aMethod selector
-                                                    value:aMethod.
-                                            ].
-                                            "enforce display of class in methodList"
-                                            whatToDo
-                                                value:nil
-                                                value:nil
-                                                value:nil
-                                                value:nil.
-
-                                            multipleMethods ifFalse:[
-                                                theMethodList := nil.
-                                            ]
-                                      ].
-
-            multipleMethods ifTrue:[
-                theMethodList := methods.
-            ].
-
-            brwsr selectorListGenerator1 value:generator.
-            "/ auto-select the first methods, if there is only one
-
-            multipleMethods ifFalse:[
-                theMethodList isNil ifTrue:[
-                    "/ newBuffer will evaluate the generator later;
-                    "/ newBrowser might have it already evaluated ... (sigh)
-                    theMethodList := searchBlock value:aMethod.
-                ].
-
-                theMethodList size == 1 ifTrue:[
-                    brwsr selectedMethods1 value:theMethodList.
-                    brwsr methodsSelectionChanged.
-                ].
-            ].
-        ]
+	newBrowserOrBufferDependingOn:openHow
+	label:lbl
+	forSpec:spec
+	setupWith:[:brwsr |
+	    |methodListGenerator generator theMethodList|
+
+	    searchBlock := [:whichMethod |
+				| sentMessages |
+				sentMessages := whichMethod messagesSent.
+				self class findImplementorsOfAny:sentMessages in:(Smalltalk allClasses) ignoreCase:false.
+			   ].
+
+	    generator := Iterator on:[:whatToDo |
+					    theMethodList isNil ifTrue:[
+						theMethodList := searchBlock value:aMethod.
+					    ].
+					    theMethodList do:[:aMethod |
+						whatToDo
+						    value:aMethod mclass
+						    value:aMethod category
+						    value:aMethod selector
+						    value:aMethod.
+					    ].
+					    "enforce display of class in methodList"
+					    whatToDo
+						value:nil
+						value:nil
+						value:nil
+						value:nil.
+
+					    multipleMethods ifFalse:[
+						theMethodList := nil.
+					    ]
+				      ].
+
+	    multipleMethods ifTrue:[
+		theMethodList := methods.
+	    ].
+
+	    brwsr selectorListGenerator1 value:generator.
+	    "/ auto-select the first methods, if there is only one
+
+	    multipleMethods ifFalse:[
+		theMethodList isNil ifTrue:[
+		    "/ newBuffer will evaluate the generator later;
+		    "/ newBrowser might have it already evaluated ... (sigh)
+		    theMethodList := searchBlock value:aMethod.
+		].
+
+		theMethodList size == 1 ifTrue:[
+		    brwsr selectedMethods1 value:theMethodList.
+		    brwsr methodsSelectionChanged.
+		].
+	    ].
+	]
 
     "Modified: / 28-02-2012 / 16:37:04 / cg"
 !
@@ -43266,8 +43737,8 @@
     "add a new buffer showing implementations of the selected method"
 
     ^ self
-        spawnMethodLocalImplementorsBrowserFor:(self selectedSelectors)
-        in:#newBuffer
+	spawnMethodLocalImplementorsBrowserFor:(self selectedSelectors)
+	in:#newBuffer
 
     "Created: / 05-09-2006 / 10:51:47 / cg"
 !
@@ -43276,205 +43747,205 @@
     "add a new buffer showing local senders of the selected methods selector"
 
     ^ self
-        spawnMethodLocalSendersBrowserFor:(self selectedSelectors)
-        in:#newBuffer
+	spawnMethodLocalSendersBrowserFor:(self selectedSelectors)
+	in:#newBuffer
 
     "Created: / 05-09-2006 / 10:44:28 / cg"
 !
 
 spawnMethodBrowserFor:methods in:where label:labelOrNil
     "browse selected method(s);
-        where is: #newBrowser - open a new browser showing the method(s)
-        where is: #newBuffer  - add a new buffer showing the method(s)"
-
-    ^ self
-        spawnMethodBrowserFor:methods
-        in:where
-        label:labelOrNil
-        perMethodInfo:nil
-        sortBy:nil
+	where is: #newBrowser - open a new browser showing the method(s)
+	where is: #newBuffer  - add a new buffer showing the method(s)"
+
+    ^ self
+	spawnMethodBrowserFor:methods
+	in:where
+	label:labelOrNil
+	perMethodInfo:nil
+	sortBy:nil
 !
 
 spawnMethodBrowserFor:methods in:where label:labelOrNil perClassInfo:perClassInfoOrNil perMethodInfo:perMethodInfoOrNil sortBy:sortHow
     "browse selected method(s);
-        where is: #newBrowser - open a new browser showing the method(s)
-        where is: #newBuffer  - add a new buffer showing the method(s)"
-
-    ^ self
-        spawnMethodBrowserFor:methods
-        in:where
-        label:labelOrNil
-        perClassInfo:perClassInfoOrNil
-        perMethodInfo:perMethodInfoOrNil
-        sortBy:sortHow
-        select:true
+	where is: #newBrowser - open a new browser showing the method(s)
+	where is: #newBuffer  - add a new buffer showing the method(s)"
+
+    ^ self
+	spawnMethodBrowserFor:methods
+	in:where
+	label:labelOrNil
+	perClassInfo:perClassInfoOrNil
+	perMethodInfo:perMethodInfoOrNil
+	sortBy:sortHow
+	select:true
 !
 
 spawnMethodBrowserFor:methodsOrMethodGeneratorBlock in:where label:labelOrNil perClassInfo:perClassInfoHolder perMethodInfo:perMethodInfoHolder sortBy:sortHow select:doSelect
     "browse selected method(s);
-        where is: #newBrowser - open a new browser showing the method(s)
-        where is: #newBuffer  - add a new buffer showing the method(s)"
+	where is: #newBrowser - open a new browser showing the method(s)
+	where is: #newBuffer  - add a new buffer showing the method(s)"
 
     |theMethodList spec "singleSelection"|
 
     methodsOrMethodGeneratorBlock isBlock ifTrue:[
-        theMethodList := methodsOrMethodGeneratorBlock value.
-    ] ifFalse:[
-        theMethodList := methodsOrMethodGeneratorBlock copy.
+	theMethodList := methodsOrMethodGeneratorBlock value.
+    ] ifFalse:[
+	theMethodList := methodsOrMethodGeneratorBlock copy.
     ].
 
     (theMethodList isEmptyOrNil and:[perClassInfoHolder value isEmptyOrNil]) ifTrue:[
-        self information:'Nothing special found'.
-        ^ self.
+	self information:'Nothing special found'.
+	^ self.
     ].
 
     (perMethodInfoHolder value notEmptyOrNil) ifTrue:[
-        (perClassInfoHolder value notEmptyOrNil) ifTrue:[
-            "/ both present
-            spec := #multipleClassWithInfoAndMethodWithInfoBrowserSpec.
-        ] ifFalse:[
-            "/ methodInfo present
-            spec := #multipleMethodWithInfoBrowserSpec.
-        ].
-    ] ifFalse:[
-        (perClassInfoHolder value notEmptyOrNil) ifTrue:[
-            "/ classInfo present
-            spec := #multipleClassWithInfoBrowserSpec.
-        ] ifFalse:[
-            "/ none present
-            spec := #multipleMethodBrowserSpec.
-        ].
-    ].
-
-    ^ self
-        newBrowserOrBufferDependingOn:where
-        label:labelOrNil
-        forSpec:spec
-        setupWith:[:brwsr |
-            |methodGenerator classGenerator perClassInfo perMethodInfo
-             theMethodNameList|
-
-            theMethodList isNil ifTrue:[
-                methodsOrMethodGeneratorBlock isBlock ifTrue:[
-                    theMethodList := methodsOrMethodGeneratorBlock value.
-                ] ifFalse:[
-                    theMethodList := methodsOrMethodGeneratorBlock copy.
-                ].
-            ].
-            perClassInfo := perClassInfoHolder value.
-            perMethodInfo := perMethodInfoHolder value.
-
-            methodGenerator := Iterator on:[:whatToDo |
-                                            theMethodList isNil ifTrue:[
-                                                methodsOrMethodGeneratorBlock isBlock ifTrue:[
-                                                    theMethodList := methodsOrMethodGeneratorBlock value.
-                                                ] ifFalse:[
-                                                    theMethodList := methodsOrMethodGeneratorBlock copy.
-                                                ].
-                                            ].
-                                            perClassInfo := perClassInfoHolder value.
-                                            perMethodInfo := perMethodInfoHolder value.
-
-                                            theMethodNameList := theMethodList collect:[:eachMethod | eachMethod mclass -> eachMethod selector].
-                                            theMethodNameList do:[:mAssoc |
-                                                |methodClass methodSelector method|
-
-                                                methodClass := mAssoc key.
-                                                methodSelector := mAssoc value.
-                                                methodClass notNil ifTrue:[
-                                                    method := methodClass compiledMethodAt:methodSelector.
-                                                    method notNil ifTrue:[
-                                                        whatToDo
-                                                            value:methodClass
-                                                            value:method category
-                                                            value:methodSelector
-                                                            value:method.
-                                                    ].
-                                                ].
-                                            ].
-                                            methodsOrMethodGeneratorBlock isBlock ifTrue:[
-                                                theMethodList := nil.
-                                            ].
-                                            "enforce display of class in methodList"
-                                            whatToDo
-                                                value:nil
-                                                value:nil
-                                                value:nil
-                                                value:nil.
-                                      ].
-
-            sortHow notNil ifTrue:[brwsr sortBy value:sortHow].
-
-            brwsr selectorListGenerator value:methodGenerator.
-            perClassInfo notNil ifTrue:[
-                classGenerator := perClassInfo keys.
-                brwsr classListGenerator value:classGenerator.
-                brwsr meta value:false.
-            ].
-
-            perClassInfo notNil ifTrue:[
-                brwsr selectedClasses
-                    onChangeEvaluate:[
-                        |class infoText|
-
-                        brwsr selectedMethods value:nil.
-                        class := brwsr theSingleSelectedClass.
-                        class notNil ifTrue:[
-                            brwsr meta value:false.
-                            infoText := perClassInfoHolder value at:class theNonMetaclass ifAbsent:nil.
-                            infoText isNil ifTrue:[
-                                infoText := perClassInfo at:class theMetaclass ifAbsent:nil
-                            ]
-                        ].
-                        brwsr methodInfo value:infoText.
-                    ]
-            ].
-
-            perMethodInfo notNil ifTrue:[
-                brwsr selectedMethods
-                    onChangeEvaluate:[
-                        |mthd infoText|
-
-                        brwsr selectedClasses value:nil.
-                        mthd := brwsr theSingleSelectedMethod.
-                        mthd notNil ifTrue:[
-                            infoText := perMethodInfo at:mthd ifAbsent:nil
-                        ].
-                        brwsr methodInfo value:infoText.
-                    ]
-            ] ifFalse:[
-                (doSelect and:[theMethodList size == 1]) ifTrue:[
-                    brwsr selectMethods:(Array with:theMethodList first).
-                    brwsr methodsSelectionChanged.
-                ]
-            ].
-
-            methodsOrMethodGeneratorBlock isBlock ifTrue:[
-                theMethodList := nil "/ force re-evaluation
-            ]
-        ]
+	(perClassInfoHolder value notEmptyOrNil) ifTrue:[
+	    "/ both present
+	    spec := #multipleClassWithInfoAndMethodWithInfoBrowserSpec.
+	] ifFalse:[
+	    "/ methodInfo present
+	    spec := #multipleMethodWithInfoBrowserSpec.
+	].
+    ] ifFalse:[
+	(perClassInfoHolder value notEmptyOrNil) ifTrue:[
+	    "/ classInfo present
+	    spec := #multipleClassWithInfoBrowserSpec.
+	] ifFalse:[
+	    "/ none present
+	    spec := #multipleMethodBrowserSpec.
+	].
+    ].
+
+    ^ self
+	newBrowserOrBufferDependingOn:where
+	label:labelOrNil
+	forSpec:spec
+	setupWith:[:brwsr |
+	    |methodGenerator classGenerator perClassInfo perMethodInfo
+	     theMethodNameList|
+
+	    theMethodList isNil ifTrue:[
+		methodsOrMethodGeneratorBlock isBlock ifTrue:[
+		    theMethodList := methodsOrMethodGeneratorBlock value.
+		] ifFalse:[
+		    theMethodList := methodsOrMethodGeneratorBlock copy.
+		].
+	    ].
+	    perClassInfo := perClassInfoHolder value.
+	    perMethodInfo := perMethodInfoHolder value.
+
+	    methodGenerator := Iterator on:[:whatToDo |
+					    theMethodList isNil ifTrue:[
+						methodsOrMethodGeneratorBlock isBlock ifTrue:[
+						    theMethodList := methodsOrMethodGeneratorBlock value.
+						] ifFalse:[
+						    theMethodList := methodsOrMethodGeneratorBlock copy.
+						].
+					    ].
+					    perClassInfo := perClassInfoHolder value.
+					    perMethodInfo := perMethodInfoHolder value.
+
+					    theMethodNameList := theMethodList collect:[:eachMethod | eachMethod mclass -> eachMethod selector].
+					    theMethodNameList do:[:mAssoc |
+						|methodClass methodSelector method|
+
+						methodClass := mAssoc key.
+						methodSelector := mAssoc value.
+						methodClass notNil ifTrue:[
+						    method := methodClass compiledMethodAt:methodSelector.
+						    method notNil ifTrue:[
+							whatToDo
+							    value:methodClass
+							    value:method category
+							    value:methodSelector
+							    value:method.
+						    ].
+						].
+					    ].
+					    methodsOrMethodGeneratorBlock isBlock ifTrue:[
+						theMethodList := nil.
+					    ].
+					    "enforce display of class in methodList"
+					    whatToDo
+						value:nil
+						value:nil
+						value:nil
+						value:nil.
+				      ].
+
+	    sortHow notNil ifTrue:[brwsr sortBy value:sortHow].
+
+	    brwsr selectorListGenerator value:methodGenerator.
+	    perClassInfo notNil ifTrue:[
+		classGenerator := perClassInfo keys.
+		brwsr classListGenerator value:classGenerator.
+		brwsr meta value:false.
+	    ].
+
+	    perClassInfo notNil ifTrue:[
+		brwsr selectedClasses
+		    onChangeEvaluate:[
+			|class infoText|
+
+			brwsr selectedMethods value:nil.
+			class := brwsr theSingleSelectedClass.
+			class notNil ifTrue:[
+			    brwsr meta value:false.
+			    infoText := perClassInfoHolder value at:class theNonMetaclass ifAbsent:nil.
+			    infoText isNil ifTrue:[
+				infoText := perClassInfo at:class theMetaclass ifAbsent:nil
+			    ]
+			].
+			brwsr methodInfo value:infoText.
+		    ]
+	    ].
+
+	    perMethodInfo notNil ifTrue:[
+		brwsr selectedMethods
+		    onChangeEvaluate:[
+			|mthd infoText|
+
+			brwsr selectedClasses value:nil.
+			mthd := brwsr theSingleSelectedMethod.
+			mthd notNil ifTrue:[
+			    infoText := perMethodInfo at:mthd ifAbsent:nil
+			].
+			brwsr methodInfo value:infoText.
+		    ]
+	    ] ifFalse:[
+		(doSelect and:[theMethodList size == 1]) ifTrue:[
+		    brwsr selectMethods:(Array with:theMethodList first).
+		    brwsr methodsSelectionChanged.
+		]
+	    ].
+
+	    methodsOrMethodGeneratorBlock isBlock ifTrue:[
+		theMethodList := nil "/ force re-evaluation
+	    ]
+	]
 
     "Modified: / 18-05-2010 / 15:15:27 / cg"
 !
 
 spawnMethodBrowserFor:methods in:where label:labelOrNil perMethodInfo:infoDictionaryOrNil sortBy:sortHow
     "browse selected method(s);
-        where is: #newBrowser - open a new browser showing the method(s)
-        where is: #newBuffer  - add a new buffer showing the method(s)"
-
-    ^ self
-        spawnMethodBrowserFor:methods
-        in:where
-        label:labelOrNil
-        perMethodInfo:infoDictionaryOrNil
-        sortBy:sortHow
-        select:true
+	where is: #newBrowser - open a new browser showing the method(s)
+	where is: #newBuffer  - add a new buffer showing the method(s)"
+
+    ^ self
+	spawnMethodBrowserFor:methods
+	in:where
+	label:labelOrNil
+	perMethodInfo:infoDictionaryOrNil
+	sortBy:sortHow
+	select:true
 !
 
 spawnMethodBrowserFor:methods in:where label:labelOrNil perMethodInfo:infoDictionaryOrNil sortBy:sortHow select:doSelect
     "browse selected method(s);
-        where is: #newBrowser - open a new browser showing the method(s)
-        where is: #newBuffer  - add a new buffer showing the method(s)"
+	where is: #newBrowser - open a new browser showing the method(s)
+	where is: #newBuffer  - add a new buffer showing the method(s)"
 
     ^ self
        spawnMethodBrowserFor:methods in:where label:labelOrNil
@@ -43540,59 +44011,59 @@
 
 spawnMethodBrowserForSearch:searchBlock sortBy:sortByWhat in:openHow label:lbl
     "browse selected method(s);
-        openHow is: #newBrowser - open a new browser showing the method(s)
-        openHow is: #newBuffer  - add a new buffer showing the method(s)
-
-        and sortByWhat is:
-            #selector
-        or  #class
+	openHow is: #newBrowser - open a new browser showing the method(s)
+	openHow is: #newBuffer  - add a new buffer showing the method(s)
+
+	and sortByWhat is:
+	    #selector
+	or  #class
     "
 
     |spec theMethodList|
 
     theMethodList := searchBlock value.
     theMethodList size == 0 ifTrue:[
-        self information:(lbl , ' - none found').
-        ^ self.
+	self information:(lbl , ' - none found').
+	^ self.
     ].
 
     spec := #methodListBrowserSpec.
 
     ^ self
-        newBrowserOrBufferDependingOn:openHow
-        label:lbl
-        forSpec:spec
-        setupWith:[:brwsr |
-            |generator|
-
-            generator := Iterator on:[:whatToDo |
-                                            brwsr window withWaitCursorDo:[
-                                                theMethodList isNil ifTrue:[
-                                                    theMethodList := searchBlock value.
-                                                ].
-                                                theMethodList notNil ifTrue:[
-                                                    theMethodList do:[:aMethod |
-                                                        whatToDo
-                                                            value:aMethod mclass
-                                                            value:aMethod category
-                                                            value:aMethod selector
-                                                            value:aMethod.
-                                                    ].
-                                                ].
-                                                "enforce display of class in methodList"
-                                                whatToDo
-                                                    value:nil
-                                                    value:nil
-                                                    value:nil
-                                                    value:nil.
-                                            ].
-                                            theMethodList := nil.
-                                      ].
-
-            sortByWhat notNil ifTrue:[brwsr sortBy value:sortByWhat].
-            "/ sortByWhat notNil ifTrue:[brwsr sortBy:sortByWhat].
-            brwsr selectorListGenerator value:generator.
-            "/ auto-select the first methods, if there is only one
+	newBrowserOrBufferDependingOn:openHow
+	label:lbl
+	forSpec:spec
+	setupWith:[:brwsr |
+	    |generator|
+
+	    generator := Iterator on:[:whatToDo |
+					    brwsr window withWaitCursorDo:[
+						theMethodList isNil ifTrue:[
+						    theMethodList := searchBlock value.
+						].
+						theMethodList notNil ifTrue:[
+						    theMethodList do:[:aMethod |
+							whatToDo
+							    value:aMethod mclass
+							    value:aMethod category
+							    value:aMethod selector
+							    value:aMethod.
+						    ].
+						].
+						"enforce display of class in methodList"
+						whatToDo
+						    value:nil
+						    value:nil
+						    value:nil
+						    value:nil.
+					    ].
+					    theMethodList := nil.
+				      ].
+
+	    sortByWhat notNil ifTrue:[brwsr sortBy value:sortByWhat].
+	    "/ sortByWhat notNil ifTrue:[brwsr sortBy:sortByWhat].
+	    brwsr selectorListGenerator value:generator.
+	    "/ auto-select the first methods, if there is only one
 
 "/            theMethodList isNil ifTrue:[
 "/                "/ newBuffer will evaluate the generator later;
@@ -43602,11 +44073,11 @@
 "/                ]
 "/            ].
 
-            theMethodList size == 1 ifTrue:[
-                brwsr selectMethods:theMethodList.
-                brwsr methodsSelectionChanged.
-            ].
-        ]
+	    theMethodList size == 1 ifTrue:[
+		brwsr selectMethods:theMethodList.
+		brwsr methodsSelectionChanged.
+	    ].
+	]
 
     "Modified: / 1.3.2000 / 21:03:34 / cg"
 !
@@ -43615,9 +44086,9 @@
     "open a new browser or add a buffer showing the selected methods only"
 
     ^ self
-        spawnMethodImplementorsBrowserFor:aSelectorCollection
-        match:true
-        in:openHow
+	spawnMethodImplementorsBrowserFor:aSelectorCollection
+	match:true
+	in:openHow
 
     "Modified: / 05-09-2006 / 10:49:28 / cg"
 !
@@ -43626,11 +44097,11 @@
     "open a new browser or add a buffer showing the selected methods"
 
     self
-        spawnMethodImplementorsBrowserFor:aSelectorCollection
-        match:doMatch
-        in:openHow
-        classes:Smalltalk allClasses
-        label:'Implementors'
+	spawnMethodImplementorsBrowserFor:aSelectorCollection
+	match:doMatch
+	in:openHow
+	classes:Smalltalk allClasses
+	label:'Implementors'
 
     "Modified: / 05-09-2006 / 11:07:20 / cg"
 !
@@ -43639,59 +44110,59 @@
     "open a new browser or add a buffer showing the selected methods only"
 
     self withSearchCursorDo:[
-        |newBrowser label impls searchBlock cachedList theSingleSelector|
-
-        aSelectorCollection size == 1 ifTrue:[
-            theSingleSelector := aSelectorCollection first.
-            label := resources string:(labelPrefix,' of %1') with:(theSingleSelector allBold)
-        ] ifFalse:[
-            label := resources string:labelPrefix.
-        ].
-
-        searchBlock := [
-                        |list|
-
-                        (list := cachedList) notNil ifTrue:[
-                            cachedList := nil
-                        ] ifFalse:[
-                            list := IdentitySet new.
-                            aSelectorCollection do:[:aSelector |
-                                doMatch ifTrue:[
-                                    list addAll:(self class
-                                                    findImplementorsMatching:aSelector
-                                                    in:classes
-                                                    ignoreCase:false
-                                                )
-                                ] ifFalse:[
-                                    list addAll:(self class
-                                                    findImplementorsOf:aSelector
-                                                    in:Smalltalk allClasses
-                                                    ignoreCase:false
-                                                )
-                                ].
-                            ].
-                            list := list asOrderedCollection
-                        ].
-                        list
-                       ].
-
-        cachedList := searchBlock value.
-        (cachedList size == 1 and:[cachedList first == self theSingleSelectedMethod]) ifTrue:[
-            (Dialog confirm:label,' - ',(resources stringWithCRs:'only the selected method found.\\Browse anyway ?'))
-            ifFalse:[
-                ^ self
-            ]
-        ].
-
-        newBrowser := self
-                        spawnMethodBrowserForSearch:searchBlock
-                        sortBy:nil
-                        in:openHow
-                        label:label.
-        aSelectorCollection size == 1 ifTrue:[
-            newBrowser sortBy value:#classes
-        ].
-        newBrowser
+	|newBrowser label impls searchBlock cachedList theSingleSelector|
+
+	aSelectorCollection size == 1 ifTrue:[
+	    theSingleSelector := aSelectorCollection first.
+	    label := resources string:(labelPrefix,' of %1') with:(theSingleSelector allBold)
+	] ifFalse:[
+	    label := resources string:labelPrefix.
+	].
+
+	searchBlock := [
+			|list|
+
+			(list := cachedList) notNil ifTrue:[
+			    cachedList := nil
+			] ifFalse:[
+			    list := IdentitySet new.
+			    aSelectorCollection do:[:aSelector |
+				doMatch ifTrue:[
+				    list addAll:(self class
+						    findImplementorsMatching:aSelector
+						    in:classes
+						    ignoreCase:false
+						)
+				] ifFalse:[
+				    list addAll:(self class
+						    findImplementorsOf:aSelector
+						    in:Smalltalk allClasses
+						    ignoreCase:false
+						)
+				].
+			    ].
+			    list := list asOrderedCollection
+			].
+			list
+		       ].
+
+	cachedList := searchBlock value.
+	(cachedList size == 1 and:[cachedList first == self theSingleSelectedMethod]) ifTrue:[
+	    (Dialog confirm:label,' - ',(resources stringWithCRs:'only the selected method found.\\Browse anyway ?'))
+	    ifFalse:[
+		^ self
+	    ]
+	].
+
+	newBrowser := self
+			spawnMethodBrowserForSearch:searchBlock
+			sortBy:nil
+			in:openHow
+			label:label.
+	aSelectorCollection size == 1 ifTrue:[
+	    newBrowser sortBy value:#classes
+	].
+	newBrowser
     ]
 
     "Created: / 05-09-2006 / 11:07:05 / cg"
@@ -43702,77 +44173,77 @@
     "open a new browser or add a buffer showing the selected methods inheritance only"
 
     self withSearchCursorDo:[
-        |selectedMethods classes list newBrowser label searchBlock
-         initialList anyRedefined|
-
-        (selectedMethods := self selectedMethodsValue) size == 0 ifTrue:[
-            self warn:'No method selected.'.
-            ^ self
-        ].
-
-        "/ classes := self selectedClasses value.
-        classes isNil ifTrue:[
-            classes := selectedMethods
-                        collect:[:eachMethod | eachMethod mclass]
-                        thenSelect:[:eachClass | eachClass notNil].
-        ].
-
-        searchBlock := [
-                |list subList already|
-
-                (list := initialList) size > 0 ifTrue:[
-                    initialList := nil
-                ] ifFalse:[
-                    already := IdentitySet new.
-                    list := OrderedCollection new.
-                    aSelectorCollection do:[:eachSelector |
-                        classes do:[:eachClass |
-                            (eachClass withAllSuperclasses copy reverse , eachClass allSubclasses)
-                            do:[:eachSuperAndSubclass |
-                                |mthd|
-
-                                (eachSuperAndSubclass includesSelector:eachSelector) ifTrue:[
-                                    mthd := eachSuperAndSubclass compiledMethodAt:eachSelector.
-                                    (already includes:mthd) ifFalse:[
-                                        eachSuperAndSubclass ~~ eachClass ifTrue:[anyRedefined := true].
-                                        list add:mthd.
-                                        already add:mthd.
-                                    ]
-                                ]
-                            ]
-                        ].
-                    ].
-                ].
-                list
-            ].
-
-        anyRedefined := false.
-        initialList := searchBlock value.
-        anyRedefined ifFalse:[
-            |msg|
-
-            selectedMethods size == 1 ifTrue:[
-                msg := 'The method does not redefine any superclass method and is not redefined in any subclass.'.
-            ] ifFalse:[
-                msg := 'None of the methods redefines any superclass method or is redefined in any subclass.'.
-            ].
-            self warn:msg.
-            ^ self
-        ].
-
-        aSelectorCollection size == 1 ifTrue:[
-            label := 'Inheritance of %1' bindWith:(aSelectorCollection first)
-        ] ifFalse:[
-            label := 'Inheritance'.
-        ].
-
-        newBrowser := self
-                        spawnMethodBrowserForSearch:searchBlock
-                        sortBy:nil
-                        in:openHow
-                        label:label.
-        newBrowser selectMethods:(selectedMethods copy).
-        newBrowser sortBy value:false.
+	|selectedMethods classes list newBrowser label searchBlock
+	 initialList anyRedefined|
+
+	(selectedMethods := self selectedMethodsValue) size == 0 ifTrue:[
+	    self warn:'No method selected.'.
+	    ^ self
+	].
+
+	"/ classes := self selectedClasses value.
+	classes isNil ifTrue:[
+	    classes := selectedMethods
+			collect:[:eachMethod | eachMethod mclass]
+			thenSelect:[:eachClass | eachClass notNil].
+	].
+
+	searchBlock := [
+		|list subList already|
+
+		(list := initialList) size > 0 ifTrue:[
+		    initialList := nil
+		] ifFalse:[
+		    already := IdentitySet new.
+		    list := OrderedCollection new.
+		    aSelectorCollection do:[:eachSelector |
+			classes do:[:eachClass |
+			    (eachClass withAllSuperclasses copy reverse , eachClass allSubclasses)
+			    do:[:eachSuperAndSubclass |
+				|mthd|
+
+				(eachSuperAndSubclass includesSelector:eachSelector) ifTrue:[
+				    mthd := eachSuperAndSubclass compiledMethodAt:eachSelector.
+				    (already includes:mthd) ifFalse:[
+					eachSuperAndSubclass ~~ eachClass ifTrue:[anyRedefined := true].
+					list add:mthd.
+					already add:mthd.
+				    ]
+				]
+			    ]
+			].
+		    ].
+		].
+		list
+	    ].
+
+	anyRedefined := false.
+	initialList := searchBlock value.
+	anyRedefined ifFalse:[
+	    |msg|
+
+	    selectedMethods size == 1 ifTrue:[
+		msg := 'The method does not redefine any superclass method and is not redefined in any subclass.'.
+	    ] ifFalse:[
+		msg := 'None of the methods redefines any superclass method or is redefined in any subclass.'.
+	    ].
+	    self warn:msg.
+	    ^ self
+	].
+
+	aSelectorCollection size == 1 ifTrue:[
+	    label := 'Inheritance of %1' bindWith:(aSelectorCollection first)
+	] ifFalse:[
+	    label := 'Inheritance'.
+	].
+
+	newBrowser := self
+			spawnMethodBrowserForSearch:searchBlock
+			sortBy:nil
+			in:openHow
+			label:label.
+	newBrowser selectMethods:(selectedMethods copy).
+	newBrowser sortBy value:false.
     ]
 
     "Modified: / 28-02-2012 / 16:30:45 / cg"
@@ -43782,11 +44253,11 @@
     "open a new browser or add a buffer showing the selected methods only"
 
     ^ self
-        spawnMethodImplementorsBrowserFor:aSelectorCollection
-        match:true
-        in:openHow
-        classes:(self selectedLocalMethodClasses)
-        label:'Local Implementors'
+	spawnMethodImplementorsBrowserFor:aSelectorCollection
+	match:true
+	in:openHow
+	classes:(self selectedLocalMethodClasses)
+	label:'Local Implementors'
 
     "Created: / 05-09-2006 / 10:49:50 / cg"
 !
@@ -43795,10 +44266,10 @@
     "open a new browser or add a buffer showing the selected methods local senders"
 
     self
-        spawnMethodSendersBrowserFor:aSelectorCollection
-        in:openHow
-        classes:(self selectedLocalMethodClasses)
-        label:'Local Senders'
+	spawnMethodSendersBrowserFor:aSelectorCollection
+	in:openHow
+	classes:(self selectedLocalMethodClasses)
+	label:'Local Senders'
 
     "Created: / 05-09-2006 / 10:46:35 / cg"
 !
@@ -43807,10 +44278,10 @@
     "open a new browser or add a buffer showing the selected methods senders only"
 
     self
-        spawnMethodSendersBrowserFor:aSelectorCollection
-        in:openHow
-        classes:Smalltalk allClasses
-        label:'Senders'
+	spawnMethodSendersBrowserFor:aSelectorCollection
+	in:openHow
+	classes:Smalltalk allClasses
+	label:'Senders'
 
     "Modified: / 05-09-2006 / 10:42:46 / cg"
 !
@@ -43821,65 +44292,65 @@
     |label|
 
     self withSearchCursorDo:[
-        |cachedList newBrowser theSingleSelector searchBlock|
-
-        aSelectorCollection size == 1 ifTrue:[
-            theSingleSelector := aSelectorCollection first.
-            label := resources string:(labelPrefix,' of %1') with:theSingleSelector allBold.
-        ] ifFalse:[
-            label := resources string:labelPrefix.
-        ].
-
-        searchBlock := [
-                            |l|
-
-                            cachedList notNil ifTrue:[
-                                l := cachedList.
-                                cachedList := nil
-                            ] ifFalse:[
-                                l := IdentitySet new.
-                                aSelectorCollection do:[:aSelector |
-                                    l addAll:(self class
-                                                    findSendersOf:aSelector
-                                                    in:setOfClasses
-                                                    ignoreCase:false
-                                                    match:false
-                                                )
-                                ].
-                                l := l asOrderedCollection
-                            ].
-                            l
-                       ].
-
-        theSingleSelector notNil ifTrue:[
-            cachedList := searchBlock value.
-            cachedList size == 0 ifTrue:[
-                (Dialog 
-                    confirm:(label , (resources string:' - none found'))
-                    yesLabel:(resources string:'Show Implementors') noLabel:'OK'
-                    initialAnswer:false
-                ) ifTrue:[
-                    self spawnMethodImplementorsBrowserFor:aSelectorCollection in:openHow
-                ].
-                ^ self
-            ].
-            (cachedList size == 1 and:[cachedList first == self theSingleSelectedMethod]) ifTrue:[
-                (Dialog confirm:(label,' - ',(resources stringWithCRs:'only the selected method found.\\Browse anyway ?')))
-                ifFalse:[
-                    ^ self
-                ]
-            ].
-        ].
-
-        newBrowser := self
-                        spawnMethodBrowserForSearch:searchBlock
-                        sortBy:#class
-                        in:openHow
-                        label:label.
-
-        theSingleSelector notNil ifTrue:[
-            newBrowser autoSearchSelector:theSingleSelector ignoreCase:false doMatch:false.
-        ].
+	|cachedList newBrowser theSingleSelector searchBlock|
+
+	aSelectorCollection size == 1 ifTrue:[
+	    theSingleSelector := aSelectorCollection first.
+	    label := resources string:(labelPrefix,' of %1') with:theSingleSelector allBold.
+	] ifFalse:[
+	    label := resources string:labelPrefix.
+	].
+
+	searchBlock := [
+			    |l|
+
+			    cachedList notNil ifTrue:[
+				l := cachedList.
+				cachedList := nil
+			    ] ifFalse:[
+				l := IdentitySet new.
+				aSelectorCollection do:[:aSelector |
+				    l addAll:(self class
+						    findSendersOf:aSelector
+						    in:setOfClasses
+						    ignoreCase:false
+						    match:false
+						)
+				].
+				l := l asOrderedCollection
+			    ].
+			    l
+		       ].
+
+	theSingleSelector notNil ifTrue:[
+	    cachedList := searchBlock value.
+	    cachedList size == 0 ifTrue:[
+		(Dialog
+		    confirm:(label , (resources string:' - none found'))
+		    yesLabel:(resources string:'Show Implementors') noLabel:'OK'
+		    initialAnswer:false
+		) ifTrue:[
+		    self spawnMethodImplementorsBrowserFor:aSelectorCollection in:openHow
+		].
+		^ self
+	    ].
+	    (cachedList size == 1 and:[cachedList first == self theSingleSelectedMethod]) ifTrue:[
+		(Dialog confirm:(label,' - ',(resources stringWithCRs:'only the selected method found.\\Browse anyway ?')))
+		ifFalse:[
+		    ^ self
+		]
+	    ].
+	].
+
+	newBrowser := self
+			spawnMethodBrowserForSearch:searchBlock
+			sortBy:#class
+			in:openHow
+			label:label.
+
+	theSingleSelector notNil ifTrue:[
+	    newBrowser autoSearchSelector:theSingleSelector ignoreCase:false doMatch:false.
+	].
     ]
 
     "Created: / 05-09-2006 / 10:43:21 / cg"
@@ -43891,53 +44362,53 @@
     |label|
 
     self withSearchCursorDo:[
-        |packages cachedList newBrowser theSinglePackage searchBlock|
-
-        packages := (aMethodCollection collect:[:each | each package]) asSet.
-        packages size == 1 ifTrue:[
-            theSinglePackage := packages first.
-            label := 'Extensions for %1' bindWith:theSinglePackage.
-        ] ifFalse:[
-            label := 'Extensions'.
-        ].
-
-        searchBlock := [
-                            |l|
-
-                            cachedList notNil ifTrue:[
-                                l := cachedList.
-                                cachedList := nil
-                            ] ifFalse:[
-                                l := OrderedCollection new.
-                                Smalltalk allClasses
-                                    do:[:eachClass |
-                                        l addAll:(eachClass extensions
-                                                    select:[:extensionMethod |
-                                                        (packages includes:extensionMethod package)])
-                                    ].
-                            ].
-                            l
-                       ].
-
-        theSinglePackage notNil ifTrue:[
-            cachedList := searchBlock value.
-            cachedList size == 0 ifTrue:[
-                self information:(label , ' - none found').
-                ^ self
-            ].
-            (cachedList size == 1 and:[cachedList first == self theSingleSelectedMethod]) ifTrue:[
-                (self confirm:((label bindWith:label) , ' - only the selected method found.\\Browse anyway ?' withCRs))
-                ifFalse:[
-                    ^ self
-                ]
-            ].
-        ].
-
-        newBrowser := self
-                        spawnMethodBrowserForSearch:searchBlock
-                        sortBy:#class
-                        in:openHow
-                        label:label.
+	|packages cachedList newBrowser theSinglePackage searchBlock|
+
+	packages := (aMethodCollection collect:[:each | each package]) asSet.
+	packages size == 1 ifTrue:[
+	    theSinglePackage := packages first.
+	    label := 'Extensions for %1' bindWith:theSinglePackage.
+	] ifFalse:[
+	    label := 'Extensions'.
+	].
+
+	searchBlock := [
+			    |l|
+
+			    cachedList notNil ifTrue:[
+				l := cachedList.
+				cachedList := nil
+			    ] ifFalse:[
+				l := OrderedCollection new.
+				Smalltalk allClasses
+				    do:[:eachClass |
+					l addAll:(eachClass extensions
+						    select:[:extensionMethod |
+							(packages includes:extensionMethod package)])
+				    ].
+			    ].
+			    l
+		       ].
+
+	theSinglePackage notNil ifTrue:[
+	    cachedList := searchBlock value.
+	    cachedList size == 0 ifTrue:[
+		self information:(label , ' - none found').
+		^ self
+	    ].
+	    (cachedList size == 1 and:[cachedList first == self theSingleSelectedMethod]) ifTrue:[
+		(self confirm:((label bindWith:label) , ' - only the selected method found.\\Browse anyway ?' withCRs))
+		ifFalse:[
+		    ^ self
+		]
+	    ].
+	].
+
+	newBrowser := self
+			spawnMethodBrowserForSearch:searchBlock
+			sortBy:#class
+			in:openHow
+			label:label.
     ]
 
     "Modified: / 12-10-2006 / 20:59:02 / cg"
@@ -43957,8 +44428,8 @@
 
 spawnSenderChainIn:openHow
     "browse selected methods sender chain;
-        openHow is: #newBrowser - open a new browser showing the method(s)
-        openHow is: #newBuffer  - add a new buffer showing the method(s)
+	openHow is: #newBrowser - open a new browser showing the method(s)
+	openHow is: #newBuffer  - add a new buffer showing the method(s)
     "
 
     |searchBlock "must be first local in block (see #methodsSelectionChangedAt:index, which fetches this value)"
@@ -43966,72 +44437,72 @@
 
     multipleMethods := self selectedMethodsValue size > 1.
     multipleMethods ifTrue:[
-        methods := self selectedMethodsValue copy.
-        lbl := resources string:'Sender chains'.
-    ] ifFalse:[
-        aMethod := self theSingleSelectedMethod.
-        lbl := resources string:'Sender chain of %1' with:aMethod selector.
+	methods := self selectedMethodsValue copy.
+	lbl := resources string:'Sender chains'.
+    ] ifFalse:[
+	aMethod := self theSingleSelectedMethod.
+	lbl := resources string:'Sender chain of %1' with:aMethod selector.
     ].
     spec := #chainBrowserSpec.
 
     ^ self
-        newBrowserOrBufferDependingOn:openHow
-        label:lbl
-        forSpec:spec
-        setupWith:[:brwsr |
-            |generator theMethodList|
-
-            searchBlock := [:whichMethod | |selector|
-                                selector := whichMethod selector.
-                                selector isNil ifTrue:[
-                                    #()
-                                ] ifFalse:[
-                                    self class allCallsOn:selector in:(Smalltalk allClasses) ignoreCase:false match:false.
-                                ].
-                           ].
-
-            generator := Iterator on:[:whatToDo |
-                                            theMethodList isNil ifTrue:[
-                                                theMethodList := searchBlock value:aMethod.
-                                            ].
-                                            theMethodList do:[:aMethod |
-                                                whatToDo
-                                                    value:aMethod mclass
-                                                    value:aMethod category
-                                                    value:aMethod selector
-                                                    value:aMethod.
-                                            ].
-                                            "enforce display of class in methodList"
-                                            whatToDo
-                                                value:nil
-                                                value:nil
-                                                value:nil
-                                                value:nil.
-                                            multipleMethods ifFalse:[
-                                                theMethodList := nil.
-                                            ]
-                                      ].
-
-            multipleMethods ifTrue:[
-                theMethodList := methods.
-            ].
-
-            brwsr selectorListGenerator1 value:generator.
-            "/ auto-select the first methods, if there is only one
-
-            multipleMethods ifFalse:[
-                theMethodList isNil ifTrue:[
-                    "/ newBuffer will evaluate the generator later;
-                    "/ newBrowser might have it already evaluated ... (sigh)
-                    theMethodList := searchBlock value:aMethod.
-                ].
-
-                theMethodList size == 1 ifTrue:[
-                    brwsr selectedMethods1 value:theMethodList.
-                    brwsr methodsSelectionChanged.
-                ].
-            ].
-        ]
+	newBrowserOrBufferDependingOn:openHow
+	label:lbl
+	forSpec:spec
+	setupWith:[:brwsr |
+	    |generator theMethodList|
+
+	    searchBlock := [:whichMethod | |selector|
+				selector := whichMethod selector.
+				selector isNil ifTrue:[
+				    #()
+				] ifFalse:[
+				    self class allCallsOn:selector in:(Smalltalk allClasses) ignoreCase:false match:false.
+				].
+			   ].
+
+	    generator := Iterator on:[:whatToDo |
+					    theMethodList isNil ifTrue:[
+						theMethodList := searchBlock value:aMethod.
+					    ].
+					    theMethodList do:[:aMethod |
+						whatToDo
+						    value:aMethod mclass
+						    value:aMethod category
+						    value:aMethod selector
+						    value:aMethod.
+					    ].
+					    "enforce display of class in methodList"
+					    whatToDo
+						value:nil
+						value:nil
+						value:nil
+						value:nil.
+					    multipleMethods ifFalse:[
+						theMethodList := nil.
+					    ]
+				      ].
+
+	    multipleMethods ifTrue:[
+		theMethodList := methods.
+	    ].
+
+	    brwsr selectorListGenerator1 value:generator.
+	    "/ auto-select the first methods, if there is only one
+
+	    multipleMethods ifFalse:[
+		theMethodList isNil ifTrue:[
+		    "/ newBuffer will evaluate the generator later;
+		    "/ newBrowser might have it already evaluated ... (sigh)
+		    theMethodList := searchBlock value:aMethod.
+		].
+
+		theMethodList size == 1 ifTrue:[
+		    brwsr selectedMethods1 value:theMethodList.
+		    brwsr methodsSelectionChanged.
+		].
+	    ].
+	]
 
     "Modified: / 28-02-2012 / 16:36:22 / cg"
 ! !
@@ -44052,38 +44523,52 @@
 
     classes := self selectedClassesValue.
     pkg := self theSingleSelectedProjectFromClasses.
-    path := classes size == 1 
-                ifTrue: [SVN::Repository containerNameForClass: classes anyOne]
-                ifFalse:[''].
+    path := classes size == 1
+		ifTrue: [SVN::Repository containerNameForClass: classes anyOne]
+		ifFalse:[''].
     branch := (self svnRepositoryFor: pkg) branch.
     SVN::RevisionLogBrowser new
-        branch: branch;
-        path: path;
-        open
+	branch: branch;
+	path: path;
+	open
 
     "Modified: / 25-06-2010 / 10:08:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 28-02-2012 / 16:48:38 / cg"
 ! !
 
-
 !NewSystemBrowser methodsFor:'menu actions-variables'!
 
 browseVarRefsOrModsWithTitle:browserTitle boxTitle:boxTitle variables:varType access:accessType all:browseAll
     "show an enterbox for instVar/classVar to search for.
      Then open a new browser or add a buffer showing methods referring/modifying to that var"
 
-    |box b varNames varNameList openHow classes|
+    |box b allNames varNames varNameList openHow classes copyOfClasses |
 
     openHow := #newBuffer.
 
-    box := self enterBoxForVariableSearch:boxTitle.
+    allNames := Set new.
+    self selectedClasses value do:[:eachClass |
+	(varType == #classVarNames or:[ varType == #poolVarNames ]) ifTrue:[
+	    allNames addAll:(eachClass allClassVarNames).
+	] ifFalse:[
+	    (varType == #instVarNames) ifTrue:[
+		allNames addAll:(eachClass allInstVarNames).
+	    ] ifFalse:[
+		self halt
+	    ]
+	].
+    ].
+    allNames := allNames asOrderedCollection sort.
+    allNames isEmpty ifTrue:[ allNames := nil ].
+
+    box := self enterBoxForVariableSearch:boxTitle list:allNames.
     box action:[:enteredString | varNames := enteredString].
 
     b := Button label:(resources string:'Browser').
     (DialogBox defaultOKButtonAtLeft) ifFalse:[
-        box addButton:b before:box okButton.
+	box addButton:b before:box okButton.
     ] ifTrue:[
-        box addButton:b after:box okButton.
+	box addButton:b after:box okButton.
     ].
     b action:[
        openHow := #newBrowser.
@@ -44099,11 +44584,24 @@
 
     classes := self classesToSearchForVariable.
 
-    self
-        browseVarRefsToAny:varNameList
-        classes:classes
-        variables:varType access:accessType all:browseAll
-        title:browserTitle in:openHow
+    varType == #poolVarNames ifTrue:[
+	"/ also check classes which refer to that pool
+	copyOfClasses := IdentitySet withAll:classes.
+	Smalltalk allClassesDo:[:someOtherClass |
+	    (someOtherClass sharedPools includesAny:copyOfClasses) ifTrue:[
+self halt.
+		classes add:someOtherClass.
+	    ]
+	].
+    ].
+
+    self
+	browseVarRefsToAny:varNameList
+	classes:classes
+	variables:varType access:accessType all:browseAll
+	title:browserTitle in:openHow
+
+    "Modified: / 29-05-2012 / 12:18:40 / cg"
 !
 
 browseVarRefsToAny:varNameList classes:classesIn variables:varType access:accessType all:browseAll title:browserTitle in:openHow
@@ -44119,66 +44617,66 @@
     classes := classesIn collect:[:each | each theNonMetaclass].
 
     searchBlock := [
-                    |allMethods|
-
-                    methods notNil ifTrue:[
-                        allMethods := methods.
-                        methods := nil.
-                    ] ifFalse:[
-                        allMethods := IdentitySet new.
-                        varNameList do:[:aVariableName |
-                            |homeClasses methods1 methods2|
-
-                            browseAll ifTrue:[
-                                homeClasses := self findClassesOfVariable:aVariableName accessWith:varType in:classes.
-                                homeClasses do:[:homeClass |
-                                    varType == #classVarNames ifTrue:[
-                                        methods1 := self class findClassRefsTo:aVariableName under:homeClass theNonMetaclass access:accessType.
-                                        methods2 := self class findClassRefsTo:aVariableName under:homeClass theMetaclass access:accessType.
-                                    ] ifFalse:[
-                                        varType == #classInstVarNames ifTrue:[
-                                            methods1 := self class findInstRefsTo:aVariableName under:homeClass theMetaclass access:accessType
-                                        ] ifFalse:[
-                                            methods1 := self class findInstRefsTo:aVariableName under:homeClass theNonMetaclass access:accessType
-                                        ]
-                                    ].
-                                    allMethods addAll:methods1.
-                                    methods2 notNil ifTrue:[allMethods addAll:methods2].
-                                ].
-                            ] ifFalse:[
-                                classes do:[:eachClass |
-                                    varType == #classVarNames ifTrue:[
-                                        methods1 := self class findClassRefsTo:aVariableName inClass:eachClass theNonMetaclass access:accessType.
-                                        methods2 := self class findClassRefsTo:aVariableName inClass:eachClass theMetaclass access:accessType.
-                                    ] ifFalse:[
-                                        varType == #classInstVarNames ifTrue:[
-                                            methods1 := self class findInstRefsTo:aVariableName inClass:eachClass theMetaclass access:accessType
-                                        ] ifFalse:[
-                                            methods1 := self class findInstRefsTo:aVariableName inClass:eachClass theNonMetaclass access:accessType
-                                        ]
-                                    ].
-                                    allMethods addAll:methods1.
-                                    methods2 notNil ifTrue:[allMethods addAll:methods2].
-                                ].
-                            ].
-                        ].
-                        allMethods := allMethods asOrderedCollection
-                    ].
-                    allMethods
-                ].
+		    |allMethods|
+
+		    methods notNil ifTrue:[
+			allMethods := methods.
+			methods := nil.
+		    ] ifFalse:[
+			allMethods := IdentitySet new.
+			varNameList do:[:aVariableName |
+			    |homeClasses methods1 methods2|
+
+			    browseAll ifTrue:[
+				homeClasses := self findClassesOfVariable:aVariableName accessWith:varType in:classes.
+				homeClasses do:[:homeClass |
+				    varType == #classVarNames ifTrue:[
+					methods1 := self class findClassRefsTo:aVariableName under:homeClass theNonMetaclass access:accessType.
+					methods2 := self class findClassRefsTo:aVariableName under:homeClass theMetaclass access:accessType.
+				    ] ifFalse:[
+					varType == #classInstVarNames ifTrue:[
+					    methods1 := self class findInstRefsTo:aVariableName under:homeClass theMetaclass access:accessType
+					] ifFalse:[
+					    methods1 := self class findInstRefsTo:aVariableName under:homeClass theNonMetaclass access:accessType
+					]
+				    ].
+				    allMethods addAll:methods1.
+				    methods2 notNil ifTrue:[allMethods addAll:methods2].
+				].
+			    ] ifFalse:[
+				classes do:[:eachClass |
+				    varType == #classVarNames ifTrue:[
+					methods1 := self class findClassRefsTo:aVariableName inClass:eachClass theNonMetaclass access:accessType.
+					methods2 := self class findClassRefsTo:aVariableName inClass:eachClass theMetaclass access:accessType.
+				    ] ifFalse:[
+					varType == #classInstVarNames ifTrue:[
+					    methods1 := self class findInstRefsTo:aVariableName inClass:eachClass theMetaclass access:accessType
+					] ifFalse:[
+					    methods1 := self class findInstRefsTo:aVariableName inClass:eachClass theNonMetaclass access:accessType
+					]
+				    ].
+				    allMethods addAll:methods1.
+				    methods2 notNil ifTrue:[allMethods addAll:methods2].
+				].
+			    ].
+			].
+			allMethods := allMethods asOrderedCollection
+		    ].
+		    allMethods
+		].
 
     self busyLabel:'searching...'.
     methods := searchBlock value.
     self normalLabel.
     methods size == 0 ifTrue:[
-        self information:((browserTitle bindWith:varNames allBold) , ' - none found').
-        ^ self
+	self information:((browserTitle bindWith:varNames allBold) , ' - none found').
+	^ self
     ].
 
     brwsr := self spawnMethodBrowserForSearch:searchBlock
-                sortBy:#class
-                in:openHow
-                label:(browserTitle bindWith:varNames).
+		sortBy:#class
+		in:openHow
+		label:(browserTitle bindWith:varNames).
 
     brwsr variableFilter value:varNameList.
 
@@ -44193,32 +44691,32 @@
 
     homeClasses := IdentitySet new.
     collectionOfClasses do:[:currentClass |
-        cls := currentClass.
-        [cls notNil] whileTrue:[
-            "
-             first, find the class, where the variable is declared
-            "
-            aSelector == #classInstVarNames ifTrue:[
-                list := cls class instVarNames
-            ] ifFalse:[
-                list := cls perform:aSelector
-            ].
-            (list includes:aVariableName) ifTrue:[
-                homeClass := cls.
-                cls := nil.
-            ] ifFalse:[
-                cls := cls superclass
-            ]
-        ].
-        homeClass isNil ifTrue:[
-            "nope, must be one below ... (could optimize a bit, by searching down
-             for the declaring class ...
-            "
-            homeClass := currentClass
-        ] ifFalse:[
-            "/ Transcript showCR:'starting search in ' , homeClass name.
-        ].
-        homeClasses add:homeClass.
+	cls := currentClass.
+	[cls notNil] whileTrue:[
+	    "
+	     first, find the class, where the variable is declared
+	    "
+	    aSelector == #classInstVarNames ifTrue:[
+		list := cls class instVarNames
+	    ] ifFalse:[
+		list := cls perform:aSelector
+	    ].
+	    (list includes:aVariableName) ifTrue:[
+		homeClass := cls.
+		cls := nil.
+	    ] ifFalse:[
+		cls := cls superclass
+	    ]
+	].
+	homeClass isNil ifTrue:[
+	    "nope, must be one below ... (could optimize a bit, by searching down
+	     for the declaring class ...
+	    "
+	    homeClass := currentClass
+	] ifFalse:[
+	    "/ Transcript showCR:'starting search in ' , homeClass name.
+	].
+	homeClasses add:homeClass.
     ].
 
     ^ homeClasses
@@ -44262,46 +44760,46 @@
     initial := ''.
     words := (self selectionInCodeView ? '') asCollectionOfWords.
     words size == 1 ifTrue:[
-        initial := words first.
+	initial := words first.
     ].
     boxTitle := 'Add Variable'.
     asValueHolder ifTrue:[
-        (initial isEmpty or:[initial endsWith:'Holder']) ifFalse:[
-            initial := initial , 'Holder'
-        ].
-        boxTitle := 'Add ValueHolder'.
+	(initial isEmpty or:[initial endsWith:'Holder']) ifFalse:[
+	    initial := initial , 'Holder'
+	].
+	boxTitle := 'Add ValueHolder'.
     ].
     msg := 'Name of new %1 %2'.
     msg := msg
-            bindWith:
-                (asClassVariableBoolean
-                    ifTrue:['Class']
-                    ifFalse:[
-                        self meta value
-                            ifTrue:['Class Instance']
-                            ifFalse:['Instance']
-                    ])
-            with:
-                (asValueHolder
-                    ifTrue:['ValueHolder(s)']
-                    ifFalse:['Variable(s)']).
+	    bindWith:
+		(asClassVariableBoolean
+		    ifTrue:['Class']
+		    ifFalse:[
+			self meta value
+			    ifTrue:['Class Instance']
+			    ifFalse:['Instance']
+		    ])
+	    with:
+		(asValueHolder
+		    ifTrue:['ValueHolder(s)']
+		    ifFalse:['Variable(s)']).
 
     generateAccessorsHolder := true asValue.
     Dialog aboutToOpenBoxNotificationSignal handle:[:ex |
-        |box|
-
-        box := ex parameter.
-        box verticalPanel 
-            add:((CheckBox 
-                    label:(resources string:'Generate Getters and Setters')) 
-                    model:generateAccessorsHolder).
-        ex proceed
+	|box|
+
+	box := ex parameter.
+	box verticalPanel
+	    add:((CheckBox
+		    label:(resources string:'Generate Getters and Setters'))
+		    model:generateAccessorsHolder).
+	ex proceed
     ] do:[
-        variablesToAdd :=
-            Dialog
-                request:(resources string:msg)
-                title:(resources string:boxTitle)
-                initialAnswer:initial.
+	variablesToAdd :=
+	    Dialog
+		request:(resources string:msg)
+		title:(resources string:boxTitle)
+		initialAnswer:initial.
     ].
 
     variablesToAdd size == 0 ifTrue:[^ self].
@@ -44310,21 +44808,21 @@
 
     variablesToAdd := variablesToAdd asCollectionOfWords.
     variablesToAdd do:[:variableToAdd |
-        asClassVariableBoolean ifTrue:[
-            self codeMenuAddClassVariable:variableToAdd inClass:selectedClass asValueHolder:asValueHolder
-        ] ifFalse:[
-            self codeMenuAddInstanceVariable:variableToAdd inClass:selectedClass asValueHolder:asValueHolder
-        ]
+	asClassVariableBoolean ifTrue:[
+	    self codeMenuAddClassVariable:variableToAdd inClass:selectedClass asValueHolder:asValueHolder
+	] ifFalse:[
+	    self codeMenuAddInstanceVariable:variableToAdd inClass:selectedClass asValueHolder:asValueHolder
+	]
     ].
 
     generateAccessorsHolder value ifTrue:[
-        self 
-            variablesMenuGenerateAccessMethodsFor:variablesToAdd 
-            withChange:false 
-            asValueHolder:false
-            readersOnly:false 
-            writersOnly:false 
-            lazyInitialization:false.
+	self
+	    variablesMenuGenerateAccessMethodsFor:variablesToAdd
+	    withChange:false
+	    asValueHolder:false
+	    readersOnly:false
+	    writersOnly:false
+	    lazyInitialization:false.
     ].
 !
 
@@ -44351,9 +44849,9 @@
      Then open a new browser or add a buffer showing all methods modifying to that var"
 
     self
-        browseVarRefsOrModsWithTitle:'all writers of class-instance variable %1'
-        boxTitle:'class-instance variable to browse writers:'
-        variables:#classInstVarNames access:#write all:true
+	browseVarRefsOrModsWithTitle:'all writers of class-instance variable %1'
+	boxTitle:'class-instance variable to browse writers:'
+	variables:#classInstVarNames access:#write all:true
 !
 
 variablesMenuBrowseAllClassInstVarReads
@@ -44361,9 +44859,9 @@
      Then open a new browser or add a buffer showing all methods reading to that var"
 
     self
-        browseVarRefsOrModsWithTitle:'all readers of class-instance variable %1'
-        boxTitle:'class-instance variable to browse readers:'
-        variables:#classInstVarNames access:#read all:true
+	browseVarRefsOrModsWithTitle:'all readers of class-instance variable %1'
+	boxTitle:'class-instance variable to browse readers:'
+	variables:#classInstVarNames access:#read all:true
 !
 
 variablesMenuBrowseAllClassInstVarRefs
@@ -44371,19 +44869,21 @@
      Then open a new browser or add a buffer showing all methods referring to that var"
 
     self
-        browseVarRefsOrModsWithTitle:'All references to class-instance variable %1'
-        boxTitle:'Class-instance variable to browse all references to:'
-        variables:#classInstVarNames access:#readOrWrite all:true
+	browseVarRefsOrModsWithTitle:'All references to class-instance variable %1'
+	boxTitle:'Class-instance variable to browse all references to:'
+	variables:#classInstVarNames access:#readOrWrite all:true
 !
 
 variablesMenuBrowseAllClassVarMods
     "show an enterbox for classVar to search for.
-     Then open a new browser or add a buffer showing all methods modifying to that var"
-
-    self
-        browseVarRefsOrModsWithTitle:'All writers of class variable %1'
-        boxTitle:'Class variable to browse all writers:'
-        variables:#classVarNames access:#write all:true
+     Then open a new browser or add a buffer showing all methods modifying that var"
+
+    self
+	browseVarRefsOrModsWithTitle:'All writers of class variable %1'
+	boxTitle:'Class variable to browse all writers:'
+	variables:#classVarNames access:#write all:true
+
+    "Modified (comment): / 29-05-2012 / 12:13:48 / cg"
 !
 
 variablesMenuBrowseAllClassVarReads
@@ -44391,9 +44891,9 @@
      Then open a new browser or add a buffer showing all methods reading to that var"
 
     self
-        browseVarRefsOrModsWithTitle:'all readers of class variable %1'
-        boxTitle:'class variable to browse readers:'
-        variables:#classVarNames access:#read all:true
+	browseVarRefsOrModsWithTitle:'all readers of class variable %1'
+	boxTitle:'class variable to browse readers:'
+	variables:#classVarNames access:#read all:true
 !
 
 variablesMenuBrowseAllClassVarRefs
@@ -44401,19 +44901,21 @@
      Then open a new browser or add a buffer showing all methods referring to that var"
 
     self
-        browseVarRefsOrModsWithTitle:'All references to class variable %1'
-        boxTitle:'Class variable to browse all references to:'
-        variables:#classVarNames access:#readOrWrite all:true
+	browseVarRefsOrModsWithTitle:'All references to class variable %1'
+	boxTitle:'Class variable to browse all references to:'
+	variables:#classVarNames access:#readOrWrite all:true
 !
 
 variablesMenuBrowseAllInstVarMods
     "show an enterbox for instVar to search for.
-     Then open a new browser or add a buffer showing all methods modifying to that var"
-
-    self
-        browseVarRefsOrModsWithTitle:'All writers of instance variable %1'
-        boxTitle:'Instance variable to browse all writers:'
-        variables:#instVarNames access:#write all:true
+     Then open a new browser or add a buffer showing all methods modifying that var"
+
+    self
+	browseVarRefsOrModsWithTitle:'All writers of instance variable %1'
+	boxTitle:'Instance variable to browse all writers:'
+	variables:#instVarNames access:#write all:true
+
+    "Modified (comment): / 29-05-2012 / 12:13:52 / cg"
 !
 
 variablesMenuBrowseAllInstVarOrClassInstVarMods
@@ -44421,9 +44923,9 @@
      Then open a new browser or add a buffer showing all methods writing that var"
 
     self meta value ifTrue:[
-        self variablesMenuBrowseAllClassInstVarMods.
-    ] ifFalse:[
-        self variablesMenuBrowseAllInstVarMods.
+	self variablesMenuBrowseAllClassInstVarMods.
+    ] ifFalse:[
+	self variablesMenuBrowseAllInstVarMods.
     ].
 !
 
@@ -44432,9 +44934,9 @@
      Then open a new browser or add a buffer showing all methods reading that var"
 
     self meta value ifTrue:[
-        self variablesMenuBrowseAllClassInstVarReads.
-    ] ifFalse:[
-        self variablesMenuBrowseAllInstVarReads.
+	self variablesMenuBrowseAllClassInstVarReads.
+    ] ifFalse:[
+	self variablesMenuBrowseAllInstVarReads.
     ].
 !
 
@@ -44443,9 +44945,9 @@
      Then open a new browser or add a buffer showing all methods referring to that var"
 
     self meta value ifTrue:[
-        self variablesMenuBrowseAllClassInstVarRefs.
-    ] ifFalse:[
-        self variablesMenuBrowseAllInstVarRefs.
+	self variablesMenuBrowseAllClassInstVarRefs.
+    ] ifFalse:[
+	self variablesMenuBrowseAllInstVarRefs.
     ].
 !
 
@@ -44454,9 +44956,9 @@
      Then open a new browser or add a buffer showing all methods reading that var"
 
     self
-        browseVarRefsOrModsWithTitle:'All readers of instance variable %1'
-        boxTitle:'Instance variable to browse all readers:'
-        variables:#instVarNames access:#read all:true
+	browseVarRefsOrModsWithTitle:'All readers of instance variable %1'
+	boxTitle:'Instance variable to browse all readers:'
+	variables:#instVarNames access:#read all:true
 !
 
 variablesMenuBrowseAllInstVarRefs
@@ -44464,19 +44966,21 @@
      Then open a new browser or add a buffer showing all methods referring to that var"
 
     self
-        browseVarRefsOrModsWithTitle:'All references to instance variable %1'
-        boxTitle:'Instance variable to browse all references to:'
-        variables:#instVarNames access:#readOrWrite all:true
+	browseVarRefsOrModsWithTitle:'All references to instance variable %1'
+	boxTitle:'Instance variable to browse all references to:'
+	variables:#instVarNames access:#readOrWrite all:true
 !
 
 variablesMenuBrowseClassInstVarMods
     "show an enterbox for classInstVar to search for.
-     Then open a new browser or add a buffer showing methods modifying to that var"
-
-    self
-        browseVarRefsOrModsWithTitle:'writers of class-instance variable %1'
-        boxTitle:'class-instance variable to browse writers:'
-        variables:#classInstVarNames access:#write all:false
+     Then open a new browser or add a buffer showing methods modifying that var"
+
+    self
+	browseVarRefsOrModsWithTitle:'writers of class-instance variable %1'
+	boxTitle:'class-instance variable to browse writers:'
+	variables:#classInstVarNames access:#write all:false
+
+    "Modified (comment): / 29-05-2012 / 12:13:56 / cg"
 !
 
 variablesMenuBrowseClassInstVarReads
@@ -44484,9 +44988,9 @@
      Then open a new browser or add a buffer showing methods reading that var"
 
     self
-        browseVarRefsOrModsWithTitle:'readers of class-instance variable %1'
-        boxTitle:'class-instance variable to browse readers:'
-        variables:#classInstVarNames access:#read all:false
+	browseVarRefsOrModsWithTitle:'readers of class-instance variable %1'
+	boxTitle:'class-instance variable to browse readers:'
+	variables:#classInstVarNames access:#read all:false
 !
 
 variablesMenuBrowseClassInstVarRefs
@@ -44494,19 +44998,21 @@
      Then open a new browser or add a buffer showing methods referring to that var"
 
     self
-        browseVarRefsOrModsWithTitle:'references to class-instance variable %1'
-        boxTitle:'class-instance variable to browse references to:'
-        variables:#classInstVarNames access:#readOrWrite all:false
+	browseVarRefsOrModsWithTitle:'references to class-instance variable %1'
+	boxTitle:'class-instance variable to browse references to:'
+	variables:#classInstVarNames access:#readOrWrite all:false
 !
 
 variablesMenuBrowseClassVarMods
     "show an enterbox for classVar to search for.
-     Then open a new browser or add a buffer showing methods modifying to that var"
-
-    self
-        browseVarRefsOrModsWithTitle:'writers of class variable %1'
-        boxTitle:'class variable to browse writers:'
-        variables:#classVarNames access:#write all:false
+     Then open a new browser or add a buffer showing methods modifying that var"
+
+    self
+	browseVarRefsOrModsWithTitle:'writers of class variable %1'
+	boxTitle:'class variable to browse writers:'
+	variables:#classVarNames access:#write all:false
+
+    "Modified (comment): / 29-05-2012 / 12:14:01 / cg"
 !
 
 variablesMenuBrowseClassVarReads
@@ -44514,9 +45020,9 @@
      Then open a new browser or add a buffer showing methods reading that var"
 
     self
-        browseVarRefsOrModsWithTitle:'readers of class variable %1'
-        boxTitle:'class variable to browse readers:'
-        variables:#classVarNames access:#read all:false
+	browseVarRefsOrModsWithTitle:'readers of class variable %1'
+	boxTitle:'class variable to browse readers:'
+	variables:#classVarNames access:#read all:false
 !
 
 variablesMenuBrowseClassVarRefs
@@ -44524,19 +45030,21 @@
      Then open a new browser or add a buffer showing methods referring to that var"
 
     self
-        browseVarRefsOrModsWithTitle:'references to class variable %1'
-        boxTitle:'class variable to browse references to:'
-        variables:#classVarNames access:#readOrWrite all:false
+	browseVarRefsOrModsWithTitle:'references to class variable %1'
+	boxTitle:'class variable to browse references to:'
+	variables:#classVarNames access:#readOrWrite all:false
 !
 
 variablesMenuBrowseInstVarMods
     "show an enterbox for instVar to search for.
-     Then open a new browser or add a buffer showing methods modifying to that var"
-
-    self
-        browseVarRefsOrModsWithTitle:'writers of instance variable %1'
-        boxTitle:'instance variable to browse writers:'
-        variables:#instVarNames access:#write all:false
+     Then open a new browser or add a buffer showing methods modifying that var"
+
+    self
+	browseVarRefsOrModsWithTitle:'writers of instance variable %1'
+	boxTitle:'instance variable to browse writers:'
+	variables:#instVarNames access:#write all:false
+
+    "Modified (comment): / 29-05-2012 / 12:14:05 / cg"
 !
 
 variablesMenuBrowseInstVarReads
@@ -44544,9 +45052,9 @@
      Then open a new browser or add a buffer showing methods modifying to that var"
 
     self
-        browseVarRefsOrModsWithTitle:'readers of instance variable %1'
-        boxTitle:'instance variable to browse readers:'
-        variables:#instVarNames access:#read all:false
+	browseVarRefsOrModsWithTitle:'readers of instance variable %1'
+	boxTitle:'instance variable to browse readers:'
+	variables:#instVarNames access:#read all:false
 !
 
 variablesMenuBrowseInstVarRefs
@@ -44554,9 +45062,45 @@
      Then open a new browser or add a buffer showing methods referring to that var"
 
     self
-        browseVarRefsOrModsWithTitle:'references to instance variable %1'
-        boxTitle:'instance variable to browse references to:'
-        variables:#instVarNames access:#readOrWrite all:false
+	browseVarRefsOrModsWithTitle:'references to instance variable %1'
+	boxTitle:'instance variable to browse references to:'
+	variables:#instVarNames access:#readOrWrite all:false
+!
+
+variablesMenuBrowsePoolVarMods
+    "show an enterbox for poolVar to search for.
+     Then open a new browser or add a buffer showing methods modifying that var"
+
+    self
+	browseVarRefsOrModsWithTitle:'writers of pool variable %1'
+	boxTitle:'pool variable to browse writers:'
+	variables:#poolVarNames access:#write all:false
+
+    "Created: / 29-05-2012 / 12:13:06 / cg"
+!
+
+variablesMenuBrowsePoolVarReads
+    "show an enterbox for poolVar to search for.
+     Then open a new browser or add a buffer showing methods reading that var"
+
+    self
+	browseVarRefsOrModsWithTitle:'readers of pool variable %1'
+	boxTitle:'pool variable to browse readers:'
+	variables:#poolVarNames access:#read all:false
+
+    "Created: / 29-05-2012 / 12:13:34 / cg"
+!
+
+variablesMenuBrowsePoolVarRefs
+    "show an enterbox for poolVar to search for.
+     Then open a new browser or add a buffer showing methods referring to that var"
+
+    self
+	browseVarRefsOrModsWithTitle:'references to pool variable %1'
+	boxTitle:'pool variable to browse references to:'
+	variables:#poolVarNames access:#readOrWrite all:false
+
+    "Created: / 29-05-2012 / 12:14:39 / cg"
 !
 
 variablesMenuCopySelectedName
@@ -44566,16 +45110,16 @@
 
     first := true.
     names :=
-        String streamContents:[:s |
-            self selectedVariables value do:[:variableName |
-                first ifTrue:[
-                    first := false
-                ] ifFalse:[
-                    s space.
-                ].
-                s nextPutAll:variableName.
-            ]
-        ].
+	String streamContents:[:s |
+	    self selectedVariables value do:[:variableName |
+		first ifTrue:[
+		    first := false
+		] ifFalse:[
+		    s space.
+		].
+		s nextPutAll:variableName.
+	    ]
+	].
 
     self window setClipboardText:names
 !
@@ -44588,11 +45132,11 @@
     "create access methods for selected instvars."
 
     self
-        variablesMenuGenerateAccessMethodsWithChange:false
-        asValueHolder:false
-        readersOnly:false
-        writersOnly:false
-        lazyInitialization:false
+	variablesMenuGenerateAccessMethodsWithChange:false
+	asValueHolder:false
+	readersOnly:false
+	writersOnly:false
+	lazyInitialization:false
 !
 
 variablesMenuGenerateAccessMethodsFor:names withChange:withChange asValueHolder:asValueHolder readersOnly:readersOnly writersOnly:writersOnly lazyInitialization:lazyInitialization
@@ -44603,40 +45147,40 @@
     names isEmptyOrNil ifTrue:[^ self].
 
     what := readersOnly
-                ifTrue:['Getters']
-                ifFalse:[
-                    writersOnly
-                        ifTrue:['Setters']
-                        ifFalse:['Accessors']].
-
-    self
-        generateUndoableChange:'Generate ',what,' in %(singleClassNameOrNumberOfClasses)'
-        overSelectedClassesVia:[:generator :eachClass |
-            |classVars instVars|
-
-            classVars := names select:[:var | eachClass classVarNames includes:var].      
-            classVars notEmpty ifTrue:[
-                generator
-                    createAccessMethodsFor:classVars
-                    in:eachClass theMetaclass
-                    withChange:withChange
-                    asValueHolder:asValueHolder
-                    readersOnly:readersOnly
-                    writersOnly:writersOnly
-                    lazyInitialization:lazyInitialization
-            ].
-            instVars := names reject:[:var | classVars includes:var].
-            instVars notEmpty ifTrue:[
-                generator
-                    createAccessMethodsFor:instVars
-                    in:eachClass
-                    withChange:withChange
-                    asValueHolder:asValueHolder
-                    readersOnly:readersOnly
-                    writersOnly:writersOnly
-                    lazyInitialization:lazyInitialization
-            ]
-        ]
+		ifTrue:['Getters']
+		ifFalse:[
+		    writersOnly
+			ifTrue:['Setters']
+			ifFalse:['Accessors']].
+
+    self
+	generateUndoableChange:'Generate ',what,' in %(singleClassNameOrNumberOfClasses)'
+	overSelectedClassesVia:[:generator :eachClass |
+	    |classVars instVars|
+
+	    classVars := names select:[:var | eachClass classVarNames includes:var].
+	    classVars notEmpty ifTrue:[
+		generator
+		    createAccessMethodsFor:classVars
+		    in:eachClass theMetaclass
+		    withChange:withChange
+		    asValueHolder:asValueHolder
+		    readersOnly:readersOnly
+		    writersOnly:writersOnly
+		    lazyInitialization:lazyInitialization
+	    ].
+	    instVars := names reject:[:var | classVars includes:var].
+	    instVars notEmpty ifTrue:[
+		generator
+		    createAccessMethodsFor:instVars
+		    in:eachClass
+		    withChange:withChange
+		    asValueHolder:asValueHolder
+		    readersOnly:readersOnly
+		    writersOnly:writersOnly
+		    lazyInitialization:lazyInitialization
+	    ]
+	]
 
     "Modified: / 21-01-2012 / 10:25:52 / cg"
 !
@@ -44646,56 +45190,56 @@
 
     names := self instVarNamesOfAllSelectedClasses.
     self
-        variablesMenuGenerateAccessMethodsFor:names
-        withChange:false
-        asValueHolder:false
-        readersOnly:false
-        writersOnly:false
-        lazyInitialization:false
+	variablesMenuGenerateAccessMethodsFor:names
+	withChange:false
+	asValueHolder:false
+	readersOnly:false
+	writersOnly:false
+	lazyInitialization:false
 !
 
 variablesMenuGenerateAccessMethodsForValueHolder
     "create access methods for selected instvars as valueHolders."
 
     self
-        variablesMenuGenerateAccessMethodsWithChange:false
-        asValueHolder:true
-        readersOnly:false
-        writersOnly:false
-        lazyInitialization:false
+	variablesMenuGenerateAccessMethodsWithChange:false
+	asValueHolder:true
+	readersOnly:false
+	writersOnly:false
+	lazyInitialization:false
 !
 
 variablesMenuGenerateAccessMethodsForValueHolderWithChange
     "create access methods for selected instvars as valueHolders with change notification."
 
     self
-        variablesMenuGenerateAccessMethodsWithChange:true
-        asValueHolder:true
-        readersOnly:false
-        writersOnly:false
-        lazyInitialization:false
+	variablesMenuGenerateAccessMethodsWithChange:true
+	asValueHolder:true
+	readersOnly:false
+	writersOnly:false
+	lazyInitialization:false
 !
 
 variablesMenuGenerateAccessMethodsWithChange
     "create access methods with change notification for selected instvars."
 
     self
-        variablesMenuGenerateAccessMethodsWithChange:true
-        asValueHolder:false
-        readersOnly:false
-        writersOnly:false
-        lazyInitialization:false
+	variablesMenuGenerateAccessMethodsWithChange:true
+	asValueHolder:false
+	readersOnly:false
+	writersOnly:false
+	lazyInitialization:false
 !
 
 variablesMenuGenerateAccessMethodsWithChange:withChange asValueHolder:asValueHolder readersOnly:readersOnly writersOnly:writersOnly
     "common helper to create access methods."
 
     ^ self
-        variablesMenuGenerateAccessMethodsWithChange:withChange
-        asValueHolder:asValueHolder
-        readersOnly:readersOnly
-        writersOnly:writersOnly
-        lazyInitialization:false
+	variablesMenuGenerateAccessMethodsWithChange:withChange
+	asValueHolder:asValueHolder
+	readersOnly:readersOnly
+	writersOnly:writersOnly
+	lazyInitialization:false
 !
 
 variablesMenuGenerateAccessMethodsWithChange:withChange asValueHolder:asValueHolder readersOnly:readersOnly writersOnly:writersOnly lazyInitialization:lazyInitialization
@@ -44705,19 +45249,19 @@
 
     names := self variableFilter value.
     self
-        variablesMenuGenerateAccessMethodsFor:names
-        withChange:withChange asValueHolder:asValueHolder readersOnly:readersOnly writersOnly:writersOnly lazyInitialization:lazyInitialization
+	variablesMenuGenerateAccessMethodsFor:names
+	withChange:withChange asValueHolder:asValueHolder readersOnly:readersOnly writersOnly:writersOnly lazyInitialization:lazyInitialization
 !
 
 variablesMenuGenerateAccessMethodsWithLazyInitialization
     "create access methods for selected instvars with lazy ini."
 
     self
-        variablesMenuGenerateAccessMethodsWithChange:false
-        asValueHolder:false
-        readersOnly:false
-        writersOnly:false
-        lazyInitialization:true
+	variablesMenuGenerateAccessMethodsWithChange:false
+	asValueHolder:false
+	readersOnly:false
+	writersOnly:false
+	lazyInitialization:true
 !
 
 variablesMenuGenerateCollectionAccessMethods
@@ -44725,7 +45269,7 @@
 
     names := self instVarNamesOfAllSelectedClasses.
     self
-        variablesMenuGenerateCollectionAccessMethodsFor:names withChange:false
+	variablesMenuGenerateCollectionAccessMethodsFor:names withChange:false
 
     "Created: / 04-02-2007 / 15:56:24 / cg"
 !
@@ -44734,15 +45278,15 @@
     "common helper to create access methods."
 
     self
-        generateUndoableChange:'Generate collection access in %(singleClassNameOrNumberOfClasses)'
-        overSelectedClassesVia:[:generator :eachClass |
-            names size > 0 ifTrue:[
-                generator
-                    createCollectionAccessMethodsFor:names
-                    in:eachClass
-                    withChange:withChange
-            ]
-        ]
+	generateUndoableChange:'Generate collection access in %(singleClassNameOrNumberOfClasses)'
+	overSelectedClassesVia:[:generator :eachClass |
+	    names size > 0 ifTrue:[
+		generator
+		    createCollectionAccessMethodsFor:names
+		    in:eachClass
+		    withChange:withChange
+	    ]
+	]
 
     "Created: / 04-02-2007 / 15:57:22 / cg"
 !
@@ -44751,11 +45295,11 @@
     "create access methods for selected instvars."
 
     self
-        variablesMenuGenerateAccessMethodsWithChange:false
-        asValueHolder:false
-        readersOnly:true
-        writersOnly:false
-        lazyInitialization:false
+	variablesMenuGenerateAccessMethodsWithChange:false
+	asValueHolder:false
+	readersOnly:true
+	writersOnly:false
+	lazyInitialization:false
 !
 
 variablesMenuGenerateGetterMethodsForAll
@@ -44763,23 +45307,23 @@
 
     names := self instVarNamesOfAllSelectedClasses.
     self
-        variablesMenuGenerateAccessMethodsFor:names
-        withChange:false
-        asValueHolder:false
-        readersOnly:true
-        writersOnly:false
-        lazyInitialization:false
+	variablesMenuGenerateAccessMethodsFor:names
+	withChange:false
+	asValueHolder:false
+	readersOnly:true
+	writersOnly:false
+	lazyInitialization:false
 !
 
 variablesMenuGenerateSetterMethods
     "create setter methods for selected instvars."
 
     self
-        variablesMenuGenerateAccessMethodsWithChange:false
-        asValueHolder:false
-        readersOnly:false
-        writersOnly:true
-        lazyInitialization:false
+	variablesMenuGenerateAccessMethodsWithChange:false
+	asValueHolder:false
+	readersOnly:false
+	writersOnly:true
+	lazyInitialization:false
 !
 
 variablesMenuGenerateSetterMethodsForAll
@@ -44787,12 +45331,12 @@
 
     names := self instVarNamesOfAllSelectedClasses.
     self
-        variablesMenuGenerateAccessMethodsFor:names
-        withChange:false
-        asValueHolder:false
-        readersOnly:false
-        writersOnly:true
-        lazyInitialization:false
+	variablesMenuGenerateAccessMethodsFor:names
+	withChange:false
+	asValueHolder:false
+	readersOnly:false
+	writersOnly:true
+	lazyInitialization:false
 !
 
 variablesMenuInspect
@@ -44802,20 +45346,20 @@
 
     cls := self theSingleSelectedClass.
     cls isNil ifTrue:[
-        Dialog warn:'Please select a single class.'.
-        ^ self.
+	Dialog warn:'Please select a single class.'.
+	^ self.
     ].
     cls := cls theNonMetaclass.
 
     self withSelectedVariableDo:[:variableToInspect :isClassVar |
-        |value|
-
-        isClassVar ifTrue:[
-            value := cls classVarAt:variableToInspect 
-        ] ifFalse:[
-            value := cls instVarNamed:variableToInspect
-        ].
-        value inspect
+	|value|
+
+	isClassVar ifTrue:[
+	    value := cls classVarAt:variableToInspect
+	] ifFalse:[
+	    value := cls instVarNamed:variableToInspect
+	].
+	value inspect
     ]
 !
 
@@ -44823,14 +45367,14 @@
     "pull selected variable into superclass."
 
     self withSelectedVariableDo:[:variableToPull :isClassVar |
-        |cls|
-
-        cls := self theSingleSelectedClass.
-        isClassVar ifTrue:[
-            self codeMenuPullUpClassVariable:variableToPull inClass:(cls theNonMetaclass)
-        ] ifFalse:[
-            self codeMenuPullUpInstanceVariable:variableToPull inClass:cls
-        ]
+	|cls|
+
+	cls := self theSingleSelectedClass.
+	isClassVar ifTrue:[
+	    self codeMenuPullUpClassVariable:variableToPull inClass:(cls theNonMetaclass)
+	] ifFalse:[
+	    self codeMenuPullUpInstanceVariable:variableToPull inClass:cls
+	]
     ]
 !
 
@@ -44838,14 +45382,14 @@
     "push selected variable into subclass."
 
     self withSelectedVariableDo:[:variableToPush :isClassVar |
-        |cls|
-
-        cls := self theSingleSelectedClass.
-        isClassVar ifTrue:[
-            self codeMenuPushDownClassVariable:variableToPush inClass:(cls theNonMetaclass)
-        ] ifFalse:[
-            self codeMenuPushDownInstanceVariable:variableToPush inClass:cls
-        ]
+	|cls|
+
+	cls := self theSingleSelectedClass.
+	isClassVar ifTrue:[
+	    self codeMenuPushDownClassVariable:variableToPush inClass:(cls theNonMetaclass)
+	] ifFalse:[
+	    self codeMenuPushDownInstanceVariable:variableToPush inClass:cls
+	]
     ]
 !
 
@@ -44855,20 +45399,20 @@
     |variablesToRemove classVar cls|
 
     (variablesToRemove := self selectedVariables value) size > 0 ifTrue:[
-        classVar := self showingClassVarsInVariableList.
-    ] ifFalse:[
-        variablesToRemove := Array with:(self selectionInCodeView).
-        classVar := self hasClassVariableSelectedInCodeView.
+	classVar := self showingClassVarsInVariableList.
+    ] ifFalse:[
+	variablesToRemove := Array with:(self selectionInCodeView).
+	classVar := self hasClassVariableSelectedInCodeView.
     ].
 
 "/    cls := self theSingleSelectedClass.
     cls := Behavior commonSuperclassOf:(self selectedClassesValue).
     variablesToRemove do:[:variableToRemove |
-        classVar ifTrue:[
-            self codeMenuRemoveClassVariable:variableToRemove inClass:(cls theNonMetaclass)
-        ] ifFalse:[
-            self codeMenuRemoveInstanceVariable:variableToRemove inClass:cls
-        ]
+	classVar ifTrue:[
+	    self codeMenuRemoveClassVariable:variableToRemove inClass:(cls theNonMetaclass)
+	] ifFalse:[
+	    self codeMenuRemoveInstanceVariable:variableToRemove inClass:cls
+	]
     ].
 
     "Modified: / 28-02-2012 / 16:51:57 / cg"
@@ -44880,12 +45424,12 @@
     |variableToRemove cls|
 
     self showingClassVarsInVariableList ifTrue:[
-        variableToRemove := self theSingleSelectedVariable.
+	variableToRemove := self theSingleSelectedVariable.
     ].
     variableToRemove isNil ifTrue:[
-        self hasClassVariableSelectedInCodeView ifTrue:[
-            variableToRemove := self selectionInCodeView.
-        ]
+	self hasClassVariableSelectedInCodeView ifTrue:[
+	    variableToRemove := self selectionInCodeView.
+	]
     ].
 
     cls := self theSingleSelectedClass.
@@ -44898,12 +45442,12 @@
     |variableToRemove cls|
 
     self showingClassVarsInVariableList ifFalse:[
-        variableToRemove := self theSingleSelectedVariable.
+	variableToRemove := self theSingleSelectedVariable.
     ].
     variableToRemove isNil ifTrue:[
-        self hasInstanceVariableSelectedInCodeView ifTrue:[
-            variableToRemove := self selectionInCodeView.
-        ]
+	self hasInstanceVariableSelectedInCodeView ifTrue:[
+	    variableToRemove := self selectionInCodeView.
+	]
     ].
 
     cls := self theSingleSelectedClass.
@@ -44914,15 +45458,15 @@
     "rename selected variable."
 
     self withSelectedVariableDo:[:variableToRename :isClassVar |
-        |cls|
-
-        cls := self theSingleSelectedClass.
-
-        isClassVar ifTrue:[
-            self codeMenuRenameClassVariable:variableToRename inClass:(cls theNonMetaclass)
-        ] ifFalse:[
-            self codeMenuRenameInstanceVariable:variableToRename inClass:cls
-        ]
+	|cls|
+
+	cls := self theSingleSelectedClass.
+
+	isClassVar ifTrue:[
+	    self codeMenuRenameClassVariable:variableToRename inClass:(cls theNonMetaclass)
+	] ifFalse:[
+	    self codeMenuRenameInstanceVariable:variableToRename inClass:cls
+	]
     ]
 !
 
@@ -44932,17 +45476,17 @@
     |variableToRename|
 
     self showingClassVarsInVariableList ifTrue:[
-        variableToRename := self theSingleSelectedVariable.
+	variableToRename := self theSingleSelectedVariable.
     ].
     variableToRename isNil ifTrue:[
-        self hasClassVariableSelectedInCodeView ifTrue:[
-            variableToRename := self selectionInCodeView.
-        ]
-    ].
-
-    self
-        codeMenuRenameClassVariable:variableToRename
-        inClass:(self theSingleSelectedClass theNonMetaclass)
+	self hasClassVariableSelectedInCodeView ifTrue:[
+	    variableToRename := self selectionInCodeView.
+	]
+    ].
+
+    self
+	codeMenuRenameClassVariable:variableToRename
+	inClass:(self theSingleSelectedClass theNonMetaclass)
 !
 
 variablesMenuRenameInstanceVariable
@@ -44951,17 +45495,17 @@
     |variableToRename|
 
     self showingClassVarsInVariableList ifFalse:[
-        variableToRename := self theSingleSelectedVariable.
+	variableToRename := self theSingleSelectedVariable.
     ].
     variableToRename isNil ifTrue:[
-        self hasInstanceVariableSelectedInCodeView ifTrue:[
-            variableToRename := self selectionInCodeView.
-        ]
-    ].
-
-    self
-        codeMenuRenameInstanceVariable:variableToRename
-        inClass:(self theSingleSelectedClass theNonMetaclass)
+	self hasInstanceVariableSelectedInCodeView ifTrue:[
+	    variableToRename := self selectionInCodeView.
+	]
+    ].
+
+    self
+	codeMenuRenameInstanceVariable:variableToRename
+	inClass:(self theSingleSelectedClass theNonMetaclass)
 !
 
 variablesMenuTypeBrowe
@@ -44993,178 +45537,178 @@
 
     showingClassVars := self showingClassVarsInVariableList.
     showingClassVars ifFalse:[
-        showingInstVars := self meta value not
+	showingInstVars := self meta value not
     ].
 
     currentClass := self theSingleSelectedClass.
 
     showingClassVars ifTrue:[
-        currentClass isNil ifTrue:[
-            self selectedNonMetaclassesDo:[:cls | 
-                    |sCls|
-                    sCls := (cls whichClassDefinesClassVar:name).
-                    sCls notNil ifTrue:[ searchClass := sCls ]
-            ].
-        ] ifFalse:[
-            searchClass := currentClass theNonMetaclass whichClassDefinesClassVar:name.
-        ].
-        value := searchClass classVarAt:(name asSymbol).
-        values := Array with:value.
-        s := value displayString.
-        s size > 60 ifTrue:[
-            s := (s copyTo:60) , ' ...'
-        ].
-        msg := name , ' is (currently):\\' , s.
-        s ~= value classNameWithArticle ifTrue:[
-            msg := msg , '\\(' , value class name , ')'
-        ].
-        canInspect := true.
-    ] ifFalse:[
-        searchClass := currentClass whichClassDefinesInstVar:name.
-
-        idx := searchClass instVarOffsetOf:name.
-        idx isNil ifTrue:[^ nil].
-
-        classes := IdentitySet new.
-        values := IdentitySet new.
-        instCount := 0.
-        subInstCount := 0.
-        searchClass allSubInstancesDo:[:i |
-            |val|
-
-            val := i instVarAt:idx.
-            val notNil ifTrue:[values add:val].
-            classes add:val class name.
-            (i isMemberOf:searchClass) ifTrue:[
-                instCount := instCount + 1.
-            ] ifFalse:[
-                subInstCount := subInstCount + 1
-            ]
-        ].
-        classes := classes collect:[:eachName | Smalltalk classNamed:eachName].
-
-        (instCount == 0 and:[subInstCount == 0]) ifTrue:[
-            self warn:(resources
-                        string:'There are currently no instances or subInstances of %1.'
-                        with:currentClass name allBold).
-            ^ nil
-        ].
-
-        instCount ~~ 0 ifTrue:[
-            msg := 'in (currently: ' , instCount printString,') instances '.
-            subInstCount ~~ 0 ifTrue:[
-                msg := msg , 'and '
-            ]
-        ] ifFalse:[
-            msg := 'in '.
-        ].
-        subInstCount ~~ 0 ifTrue:[
-            msg := msg , '(currently: ' , subInstCount printString, ') derived instances '
-        ].
-        msg := msg, 'of ' , searchClass name , ',\'.
-        msg := msg , name allBold , ' '.
-
-        canInspectMultiple := values size > 0.
-
-        ((values size == 1)
-        or:[classes size == 1 and:[classes first == UndefinedObject]]) ifTrue:[
-            values size == 1 ifTrue:[
-                value := values first.
-            ].
-            (value isNil or:[value == true or:[value == false]]) ifTrue:[
-                (instCount+subInstCount) == 1 ifTrue:[
-                    msg := msg , 'is'
-                ] ifFalse:[
-                    msg := msg , 'is always'.
-                    classes size > 1 ifTrue:[
-                        "/ must be nil
-                        msg := msg , ' nil or'
-                    ].
-                ].
-                msg := msg , ':\\    ' , value printString.
-            ] ifFalse:[
-                (instCount+subInstCount) == 1 ifTrue:[
-                    msg := msg , 'is'
-                ] ifFalse:[
-                    classes size > 1 ifTrue:[
-                        "/ must be nil
-                        msg := msg , 'is always nil or the same'
-                    ] ifFalse:[
-                        msg := msg , 'is always the same'
-                    ]
-                ].
-                msg := msg , ':\\'.
-                msg := msg , '    ' , value class name.
-                value isLiteral ifTrue:[
-                    msg := msg , ' (' , (value storeString copyToMax:50) , ')'
-                ].
-                canInspect := true.
-            ]
-        ] ifFalse:[
-            classes size == 1 ifTrue:[
-                msg := msg , 'is always:\\' , '    ' , classes first name , '\'.
-            ] ifFalse:[
-                msg := msg , 'is one of:\\'.
-                classes := classes asOrderedCollection.
-                classes size > 20 ifTrue:[
-                    classes := classes copyFrom:1 to:20.
-                    cut := true
-                ] ifFalse:[
-                    cut := false.
-                ].
-                names := classes collect:[:cls |
-                    cls == UndefinedObject ifTrue:[
-                        'nil'
-                    ] ifFalse:[
-                        cls == True ifTrue:[
-                            'true'
-                        ] ifFalse:[
-                            cls == False ifTrue:[
-                                'false'
-                            ] ifFalse:[
-                                cls name
-                            ]
-                        ]
-                    ].
-                ].
-                names sort.
-                names do:[:nm |
-                    msg := msg , '    ' , nm , '\'.
-                ].
-            ]
-        ].
-
-        "/ generate a type-decl string
-        (nilIncluded := (classes includes:UndefinedObject)) ifTrue:[
-            classes remove:UndefinedObject.
-        ].
-        classes size > 0 ifTrue:[
-            commonSuperClass := Behavior commonSuperclassOf:(classes collect:[:each| each name]).
-            ((commonSuperClass == True) or:[commonSuperClass == False]) ifTrue:[
-                commonSuperClass := Boolean
-            ].
-            (commonSuperClass == SmallInteger) ifTrue:[
-                commonSuperClass := Integer
-            ].
-            commonSuperClass == Object class ifTrue:[
-                commonSuperClass := Class
-            ].
-            msg := msg , '\\'.
-            msg := msg , 'suggested type (for documentation):\\'.
-            msg := msg , '    <' , commonSuperClass name.
-            nilIncluded ifTrue:[
-                msg := msg , ' | nil'
-            ].
-            msg := msg , '>'.
-        ]
-    ].
-
-    info := Dictionary new 
-                at:#message put:msg;
-                at:#values put:values;
-                at:#classes put:classes;
-                at:#searchClass put:searchClass;
-                yourself.
+	currentClass isNil ifTrue:[
+	    self selectedNonMetaclassesDo:[:cls |
+		    |sCls|
+		    sCls := (cls whichClassDefinesClassVar:name).
+		    sCls notNil ifTrue:[ searchClass := sCls ]
+	    ].
+	] ifFalse:[
+	    searchClass := currentClass theNonMetaclass whichClassDefinesClassVar:name.
+	].
+	value := searchClass classVarAt:(name asSymbol).
+	values := Array with:value.
+	s := value displayString.
+	s size > 60 ifTrue:[
+	    s := (s copyTo:60) , ' ...'
+	].
+	msg := name , ' is (currently):\\' , s.
+	s ~= value classNameWithArticle ifTrue:[
+	    msg := msg , '\\(' , value class name , ')'
+	].
+	canInspect := true.
+    ] ifFalse:[
+	searchClass := currentClass whichClassDefinesInstVar:name.
+
+	idx := searchClass instVarOffsetOf:name.
+	idx isNil ifTrue:[^ nil].
+
+	classes := IdentitySet new.
+	values := IdentitySet new.
+	instCount := 0.
+	subInstCount := 0.
+	searchClass allSubInstancesDo:[:i |
+	    |val|
+
+	    val := i instVarAt:idx.
+	    val notNil ifTrue:[values add:val].
+	    classes add:val class name.
+	    (i isMemberOf:searchClass) ifTrue:[
+		instCount := instCount + 1.
+	    ] ifFalse:[
+		subInstCount := subInstCount + 1
+	    ]
+	].
+	classes := classes collect:[:eachName | Smalltalk classNamed:eachName].
+
+	(instCount == 0 and:[subInstCount == 0]) ifTrue:[
+	    self warn:(resources
+			string:'There are currently no instances or subInstances of %1.'
+			with:currentClass name allBold).
+	    ^ nil
+	].
+
+	instCount ~~ 0 ifTrue:[
+	    msg := 'in (currently: ' , instCount printString,') instances '.
+	    subInstCount ~~ 0 ifTrue:[
+		msg := msg , 'and '
+	    ]
+	] ifFalse:[
+	    msg := 'in '.
+	].
+	subInstCount ~~ 0 ifTrue:[
+	    msg := msg , '(currently: ' , subInstCount printString, ') derived instances '
+	].
+	msg := msg, 'of ' , searchClass name , ',\'.
+	msg := msg , name allBold , ' '.
+
+	canInspectMultiple := values size > 0.
+
+	((values size == 1)
+	or:[classes size == 1 and:[classes first == UndefinedObject]]) ifTrue:[
+	    values size == 1 ifTrue:[
+		value := values first.
+	    ].
+	    (value isNil or:[value == true or:[value == false]]) ifTrue:[
+		(instCount+subInstCount) == 1 ifTrue:[
+		    msg := msg , 'is'
+		] ifFalse:[
+		    msg := msg , 'is always'.
+		    classes size > 1 ifTrue:[
+			"/ must be nil
+			msg := msg , ' nil or'
+		    ].
+		].
+		msg := msg , ':\\    ' , value printString.
+	    ] ifFalse:[
+		(instCount+subInstCount) == 1 ifTrue:[
+		    msg := msg , 'is'
+		] ifFalse:[
+		    classes size > 1 ifTrue:[
+			"/ must be nil
+			msg := msg , 'is always nil or the same'
+		    ] ifFalse:[
+			msg := msg , 'is always the same'
+		    ]
+		].
+		msg := msg , ':\\'.
+		msg := msg , '    ' , value class name.
+		value isLiteral ifTrue:[
+		    msg := msg , ' (' , (value storeString copyToMax:50) , ')'
+		].
+		canInspect := true.
+	    ]
+	] ifFalse:[
+	    classes size == 1 ifTrue:[
+		msg := msg , 'is always:\\' , '    ' , classes first name , '\'.
+	    ] ifFalse:[
+		msg := msg , 'is one of:\\'.
+		classes := classes asOrderedCollection.
+		classes size > 20 ifTrue:[
+		    classes := classes copyFrom:1 to:20.
+		    cut := true
+		] ifFalse:[
+		    cut := false.
+		].
+		names := classes collect:[:cls |
+		    cls == UndefinedObject ifTrue:[
+			'nil'
+		    ] ifFalse:[
+			cls == True ifTrue:[
+			    'true'
+			] ifFalse:[
+			    cls == False ifTrue:[
+				'false'
+			    ] ifFalse:[
+				cls name
+			    ]
+			]
+		    ].
+		].
+		names sort.
+		names do:[:nm |
+		    msg := msg , '    ' , nm , '\'.
+		].
+	    ]
+	].
+
+	"/ generate a type-decl string
+	(nilIncluded := (classes includes:UndefinedObject)) ifTrue:[
+	    classes remove:UndefinedObject.
+	].
+	classes size > 0 ifTrue:[
+	    commonSuperClass := Behavior commonSuperclassOf:(classes collect:[:each| each name]).
+	    ((commonSuperClass == True) or:[commonSuperClass == False]) ifTrue:[
+		commonSuperClass := Boolean
+	    ].
+	    (commonSuperClass == SmallInteger) ifTrue:[
+		commonSuperClass := Integer
+	    ].
+	    commonSuperClass == Object class ifTrue:[
+		commonSuperClass := Class
+	    ].
+	    msg := msg , '\\'.
+	    msg := msg , 'suggested type (for documentation):\\'.
+	    msg := msg , '    <' , commonSuperClass name.
+	    nilIncluded ifTrue:[
+		msg := msg , ' | nil'
+	    ].
+	    msg := msg , '>'.
+	]
+    ].
+
+    info := Dictionary new
+		at:#message put:msg;
+		at:#values put:values;
+		at:#classes put:classes;
+		at:#searchClass put:searchClass;
+		yourself.
 
     ^ info
 !
@@ -45180,7 +45724,7 @@
 
     showingClassVars := self showingClassVarsInVariableList.
     showingClassVars ifFalse:[
-        showingInstVars := self meta value not
+	showingInstVars := self meta value not
     ].
     currentClass := self theSingleSelectedClass.
 
@@ -45196,78 +45740,78 @@
     canInspectMultiple := values size > 1.
 
     doBrowseTypes ifTrue:[
-        classes size > 0 ifTrue:[
-            self spawnClassBrowserFor:classes in:#newBuffer.
-            ^ self
-        ].
+	classes size > 0 ifTrue:[
+	    self spawnClassBrowserFor:classes in:#newBuffer.
+	    ^ self
+	].
     ].
 
     boxLabels := #('OK').
     boxValues := #(true).
     (canInspect or:[canInspectMultiple]) ifTrue:[
-        canInspectMultiple ifTrue:[
-            boxLabels := boxLabels , #('Inspect all Values').
-            boxValues := boxValues , #(#inspectValues).
-
-            boxLabels := boxLabels , #('Inspect a Value').
-            boxValues := boxValues , #(#inspectAValue).
-        ] ifFalse:[
-            boxLabels := boxLabels , #('Inspect Value').
-            boxValues := boxValues , #(#inspectAValue).
-        ].
-
-        showingClassVars ifFalse:[
-            canInspectMultiple ifTrue:[
-                boxLabels := boxLabels , #('Inspect all Instances').
-                boxValues := boxValues , #(#inspectInstances).
-
-                boxLabels := boxLabels , #('Inspect an Instance').
-                boxValues := boxValues , #(#inspectAnInstance).
-            ] ifFalse:[
-                boxLabels := boxLabels , #('Inspect Instance').
-                boxValues := boxValues , #(#inspectAnInstance).
-            ].
-        ].
+	canInspectMultiple ifTrue:[
+	    boxLabels := boxLabels , #('Inspect all Values').
+	    boxValues := boxValues , #(#inspectValues).
+
+	    boxLabels := boxLabels , #('Inspect a Value').
+	    boxValues := boxValues , #(#inspectAValue).
+	] ifFalse:[
+	    boxLabels := boxLabels , #('Inspect Value').
+	    boxValues := boxValues , #(#inspectAValue).
+	].
+
+	showingClassVars ifFalse:[
+	    canInspectMultiple ifTrue:[
+		boxLabels := boxLabels , #('Inspect all Instances').
+		boxValues := boxValues , #(#inspectInstances).
+
+		boxLabels := boxLabels , #('Inspect an Instance').
+		boxValues := boxValues , #(#inspectAnInstance).
+	    ] ifFalse:[
+		boxLabels := boxLabels , #('Inspect Instance').
+		boxValues := boxValues , #(#inspectAnInstance).
+	    ].
+	].
     ].
 
     Dialog defaultOKButtonAtLeft ifFalse:[
-        boxLabels reverse.
-        boxValues reverse.
+	boxLabels reverse.
+	boxValues reverse.
     ].
 
     answer := OptionBox
-                      request:msg withCRs
-                      label:'Variable Type Information'
-                      image:(InfoBox iconBitmap)
-                      buttonLabels:boxLabels
-                      values:boxValues
-                      default:true
-                      onCancel:nil.
+		      request:msg withCRs
+		      label:'Variable Type Information'
+		      image:(InfoBox iconBitmap)
+		      buttonLabels:boxLabels
+		      values:boxValues
+		      default:true
+		      onCancel:nil.
 
     answer == #inspectAValue ifTrue:[
-        canInspect ifTrue:[
-            value inspect
-        ] ifFalse:[
-            value := values inject:nil into:[:max :this | this size > max size ifTrue:[this] ifFalse:[max]].
-            value notNil ifTrue:[
-                value inspect
-            ] ifFalse:[
-                values first inspect
-            ].
-        ].
-        ^ self
+	canInspect ifTrue:[
+	    value inspect
+	] ifFalse:[
+	    value := values inject:nil into:[:max :this | this size > max size ifTrue:[this] ifFalse:[max]].
+	    value notNil ifTrue:[
+		value inspect
+	    ] ifFalse:[
+		values first inspect
+	    ].
+	].
+	^ self
     ].
     answer == #inspectValues ifTrue:[
-        (canInspect ifTrue:value ifFalse:values) inspect.
-        ^ self
+	(canInspect ifTrue:value ifFalse:values) inspect.
+	^ self
     ].
     answer == #inspectInstances ifTrue:[
-        searchClass allSubInstances inspect.
-        ^ self
+	searchClass allSubInstances inspect.
+	^ self
     ].
     answer == #inspectAnInstance ifTrue:[
-        searchClass allSubInstances first inspect.
-        ^ self
+	searchClass allSubInstances first inspect.
+	^ self
     ].
 
     "Modified: / 12-09-2006 / 13:59:24 / cg"
@@ -45304,13 +45848,13 @@
 
     selectedVariable := self theSingleSelectedVariable.
     selectedVariable notNil ifTrue:[
-        isClassVar := self showingClassVarsInVariableList.
-    ] ifFalse:[
-        selectedVariable := self selectionInCodeView.
-        selectedVariable isNil ifTrue:[
-            ^ self
-        ].
-        isClassVar := self hasClassVariableSelectedInCodeView.
+	isClassVar := self showingClassVarsInVariableList.
+    ] ifFalse:[
+	selectedVariable := self selectionInCodeView.
+	selectedVariable isNil ifTrue:[
+	    ^ self
+	].
+	isClassVar := self hasClassVariableSelectedInCodeView.
     ].
     aBlock value:selectedVariable value:isClassVar
 ! !
@@ -45347,13 +45891,13 @@
     <resource: #programMenu >
 
     ^ [
-        |m item|
-
-        m := Menu new.
-
-        item := MenuItem label:(resources string:'Add Bookmark').
-        m addItem:item.
-        item value:#'searchMenuAddToBookmarks'.
+	|m item|
+
+	m := Menu new.
+
+	item := MenuItem label:(resources string:'Add Bookmark').
+	m addItem:item.
+	item value:#'searchMenuAddToBookmarks'.
 
 "/        BookMarks size > 0 ifTrue:[
 "/            item := MenuItem label:(resources string:'Remove Bookmark').
@@ -45376,8 +45920,8 @@
 "/                item argument:entry.
 "/            ].
 "/        ].
-        m findGuiResourcesIn:self.
-        m
+	m findGuiResourcesIn:self.
+	m
     ].
 
     "Modified: / 02-11-2001 / 09:33:41 / cg"
@@ -45388,34 +45932,34 @@
     <resource: #programMenu >
 
     ^ [
-        |m extensionProjectIDs classPackage item|
-
-        extensionProjectIDs := Set new.
-
-        self selectedClassesDo:[:eachClass |
-            classPackage := eachClass package.
-            eachClass instAndClassSelectorsAndMethodsDo:[:sel :mthd |
-                mthd package ~= classPackage ifTrue:[
-                    extensionProjectIDs add:mthd package.
-                ]
-            ]
-        ].
-        extensionProjectIDs size > 0 ifTrue:[
-            m := Menu new.
-            extensionProjectIDs size > 1 ifTrue:[
-                item := MenuItem label:'All'.
-                item value:#'classMenuCheckInExtensions:'.
-                m addItem:item.
-                m addSeparator.
-            ].
-            extensionProjectIDs asSortedCollection do:[:eachExtensionPackage |
-                item := MenuItem label:eachExtensionPackage.
-                item value:#'classMenuCheckInExtensionsFor:'.
-                item argument:eachExtensionPackage.
-                m addItem:item.
-            ].
-        ].
-        m
+	|m extensionProjectIDs classPackage item|
+
+	extensionProjectIDs := Set new.
+
+	self selectedClassesDo:[:eachClass |
+	    classPackage := eachClass package.
+	    eachClass instAndClassSelectorsAndMethodsDo:[:sel :mthd |
+		mthd package ~= classPackage ifTrue:[
+		    extensionProjectIDs add:mthd package.
+		]
+	    ]
+	].
+	extensionProjectIDs size > 0 ifTrue:[
+	    m := Menu new.
+	    extensionProjectIDs size > 1 ifTrue:[
+		item := MenuItem label:'All'.
+		item value:#'classMenuCheckInExtensions:'.
+		m addItem:item.
+		m addSeparator.
+	    ].
+	    extensionProjectIDs asSortedCollection do:[:eachExtensionPackage |
+		item := MenuItem label:eachExtensionPackage.
+		item value:#'classMenuCheckInExtensionsFor:'.
+		item argument:eachExtensionPackage.
+		m addItem:item.
+	    ].
+	].
+	m
     ].
 !
 
@@ -45423,30 +45967,30 @@
     <resource: #programMenu >
 
     ^ [
-        |m selected|
-
-        m := self class bufferBaseMenu decodeAsLiteralArray.
-        m findGuiResourcesIn:self.
-
-        m addSeparator.
-        bufferNameList size > 0 ifTrue:[
-            selected := selectedBuffer value.
-            bufferNameList keysAndValuesDo:[:idx :nm |
-                |item|
-
-                item := MenuItem label:nm.
-                m addItem:item.
-                item indication:(idx == selected).
-                item value:[:i |
-                                selectedBuffer value:idx.
-                          ]
-            ].
-            m addSeparator.
-        ] ifFalse:[
-            (m atNameKey:#'RemoveBuffer') disable
-        ].
-        m addItem:(MenuItem label:(resources string:'Exit') value:#closeRequest).
-        m
+	|m selected|
+
+	m := self class bufferBaseMenu decodeAsLiteralArray.
+	m findGuiResourcesIn:self.
+
+	m addSeparator.
+	bufferNameList size > 0 ifTrue:[
+	    selected := selectedBuffer value.
+	    bufferNameList keysAndValuesDo:[:idx :nm |
+		|item|
+
+		item := MenuItem label:nm.
+		m addItem:item.
+		item indication:(idx == selected).
+		item value:[:i |
+				selectedBuffer value:idx.
+			  ]
+	    ].
+	    m addSeparator.
+	] ifFalse:[
+	    (m atNameKey:#'RemoveBuffer') disable
+	].
+	m addItem:(MenuItem label:(resources string:'Exit') value:#closeRequest).
+	m
     ].
 !
 
@@ -45472,12 +46016,12 @@
     <resource: #programMenu >
 
     ^ [
-        self
-            changedMenuForFilter:[:chg | (chg isMethodChange or:[chg isClassChange and:[chg changeClass isNameSpace not]])]
-            itemClass:[:chg | chg changeClass theNonMetaclass]
-            itemSelector:[:chg | nil]
-            label:[:chg | chg changeClass theNonMetaclass name allBold]
-            browseActionOfLastItem:[NewSystemBrowser openOnClassesInChangeSet].
+	self
+	    changedMenuForFilter:[:chg | (chg isMethodChange or:[chg isClassChange and:[chg changeClass isNameSpace not]])]
+	    itemClass:[:chg | chg changeClass theNonMetaclass]
+	    itemSelector:[:chg | nil]
+	    label:[:chg | chg changeClass theNonMetaclass name allBold]
+	    browseActionOfLastItem:[NewSystemBrowser openOnClassesInChangeSet].
       ].
 !
 
@@ -45488,13 +46032,13 @@
     <resource: #programMenu >
 
     ^ [
-        |menu|
-
-        menu := self changedMethodsMenu value.
-        menu isNil ifTrue:[
-            menu := self changedClassesMenu value.
-        ].
-        menu
+	|menu|
+
+	menu := self changedMethodsMenu value.
+	menu isNil ifTrue:[
+	    menu := self changedClassesMenu value.
+	].
+	menu
     ].
 !
 
@@ -45518,70 +46062,70 @@
     maxReached := false.
 
     changes reverseDo:[:aChange |
-        |item cls sel lbl histEntry|
-
-        maxReached ifTrue:[
-            (nOverAll = 0) ifTrue:[
-                ^ nil
-            ].
-            ^ menu
-        ].
-
-        nItem > nMaxItem ifTrue:[
-            nLevel < nMaxLevel ifTrue:[
-                nextMenu := Menu new.
-                item := MenuItem label:(resources string:'more').
-                currentMenu addItem:item.
-                item submenu:nextMenu.
-                currentMenu := nextMenu.
-
-                nItem := 0.
-                nLevel := nLevel + 1.
-            ] ifFalse:[
-                maxReached ifFalse:[
-                    maxReached := true.
-
-                    item := MenuItem label:(resources string:'>> more changes ignored <<').
-                    item enabled:false.
-                    currentMenu addItem:item.
-
-                    browseActionOfLastItemOrNil notNil ifTrue:[
-                        item := MenuItem label:(resources string:'Browse all changes').
-                        item value:browseActionOfLastItemOrNil.
-                    ].
-                    currentMenu addItem:item.
-                ]
-            ]
-        ].
-        maxReached ifFalse:[
-            cls := aChange changeClass.
-            cls notNil ifTrue:[
-                (aChangeFilter value:aChange) ifTrue:[
-                    cls := itemClassBlock value:aChange.
-                    sel := itemSelectorBlock value:aChange.
-                    lbl := labelBlock value:aChange.
-                    (already includes:lbl) ifFalse:[
-
-                        histEntry := self class
-                                        historyEntryForClass:cls
-                                        selector:sel.
-
-                        item := MenuItem label:(lbl contractTo:80).
-                        currentMenu addItem:item.
-                        item value:#'switchToHistoryEntry:'.
-                        item argument:histEntry.
-
-                        already add:lbl.
-                        nItem := nItem + 1.
-                        nOverAll := nOverAll + 1.
-                    ]
-                ]
-            ].
-        ]
+	|item cls sel lbl histEntry|
+
+	maxReached ifTrue:[
+	    (nOverAll = 0) ifTrue:[
+		^ nil
+	    ].
+	    ^ menu
+	].
+
+	nItem > nMaxItem ifTrue:[
+	    nLevel < nMaxLevel ifTrue:[
+		nextMenu := Menu new.
+		item := MenuItem label:(resources string:'more').
+		currentMenu addItem:item.
+		item submenu:nextMenu.
+		currentMenu := nextMenu.
+
+		nItem := 0.
+		nLevel := nLevel + 1.
+	    ] ifFalse:[
+		maxReached ifFalse:[
+		    maxReached := true.
+
+		    item := MenuItem label:(resources string:'>> more changes ignored <<').
+		    item enabled:false.
+		    currentMenu addItem:item.
+
+		    browseActionOfLastItemOrNil notNil ifTrue:[
+			item := MenuItem label:(resources string:'Browse all changes').
+			item value:browseActionOfLastItemOrNil.
+		    ].
+		    currentMenu addItem:item.
+		]
+	    ]
+	].
+	maxReached ifFalse:[
+	    cls := aChange changeClass.
+	    cls notNil ifTrue:[
+		(aChangeFilter value:aChange) ifTrue:[
+		    cls := itemClassBlock value:aChange.
+		    sel := itemSelectorBlock value:aChange.
+		    lbl := labelBlock value:aChange.
+		    (already includes:lbl) ifFalse:[
+
+			histEntry := self class
+					historyEntryForClass:cls
+					selector:sel.
+
+			item := MenuItem label:(lbl contractTo:80).
+			currentMenu addItem:item.
+			item value:#'switchToHistoryEntry:'.
+			item argument:histEntry.
+
+			already add:lbl.
+			nItem := nItem + 1.
+			nOverAll := nOverAll + 1.
+		    ]
+		]
+	    ].
+	]
     ].
 
     (nOverAll = 0) ifTrue:[
-        ^ nil
+	^ nil
     ].
     ^ menu
 
@@ -45595,12 +46139,12 @@
     <resource: #programMenu >
 
     ^ [
-        self
-            changedMenuForFilter:[:chg | chg isMethodChange]
-            itemClass:[:chg | chg changeClass]
-            itemSelector:[:chg | chg selector]
-            label:[:chg | (chg className allBold?'???') , ' ' , (chg selector?'???') "chg printString"]
-            browseActionOfLastItem:[NewSystemBrowser openOnMethodsInChangeSet].
+	self
+	    changedMenuForFilter:[:chg | chg isMethodChange]
+	    itemClass:[:chg | chg changeClass]
+	    itemSelector:[:chg | chg selector]
+	    label:[:chg | (chg className allBold?'???') , ' ' , (chg selector?'???') "chg printString"]
+	    browseActionOfLastItem:[NewSystemBrowser openOnMethodsInChangeSet].
       ].
 !
 
@@ -45627,13 +46171,13 @@
     <resource: #programMenu >
 
     ^ [
-        |cls m |
-
-        cls := self theSingleSelectedClass.
-        cls notNil ifTrue:[
-            m := cls theNonMetaclass classOperationsMenu
-        ].
-        m
+	|cls m |
+
+	cls := self theSingleSelectedClass.
+	cls notNil ifTrue:[
+	    m := cls theNonMetaclass classOperationsMenu
+	].
+	m
     ].
 
     "Modified: / 31-01-2011 / 11:09:04 / cg"
@@ -45648,34 +46192,34 @@
     |spec menu first skippedManager|
 
     self theSingleSelectedClass notNil ifTrue:[
-        skippedManager := self theSingleSelectedClass sourceCodeManager.
-    ] ifFalse:[
-        skippedManager := SourceCodeManager ?  AbstractSourceCodeManager defaultManager
+	skippedManager := self theSingleSelectedClass sourceCodeManager.
+    ] ifFalse:[
+	skippedManager := SourceCodeManager ?  AbstractSourceCodeManager defaultManager
     ].
 
     spec := self class classSCMMenu.
     menu := spec decodeAsLiteralArray.
     menu itemsDo:[:eachItem |
-        eachItem argument:skippedManager.
+	eachItem argument:skippedManager.
     ].
 
 false ifTrue:[
     SourceCodeManager availableManagers do:[:eachManager |
-        |newItem subMenu|
-
-        eachManager ~= skippedManager ifTrue:[
-            first ifTrue:[
-                menu addSeparator.
-                first := false.
-            ].
-            subMenu := spec decodeAsLiteralArray.
-            subMenu receiver:self.
-            subMenu findGuiResourcesIn:self.
-
-            newItem := MenuItem label:eachManager managerTypeName.
-            newItem submenu:subMenu.
-            menu addItem:newItem.
-        ].
+	|newItem subMenu|
+
+	eachManager ~= skippedManager ifTrue:[
+	    first ifTrue:[
+		menu addSeparator.
+		first := false.
+	    ].
+	    subMenu := spec decodeAsLiteralArray.
+	    subMenu receiver:self.
+	    subMenu findGuiResourcesIn:self.
+
+	    newItem := MenuItem label:eachManager managerTypeName.
+	    newItem submenu:subMenu.
+	    menu addItem:newItem.
+	].
     ].
 ].
 
@@ -45707,9 +46251,9 @@
     codeView := self codeView.
     sensor := codeView sensor.
     sensor shiftDown ifTrue:[
-        sensor ctrlDown ifFalse:[
-            ^ shiftedMenu
-        ].
+	sensor ctrlDown ifFalse:[
+	    ^ shiftedMenu
+	].
     ].
 
     menu := codeView editMenu.
@@ -45723,24 +46267,24 @@
 "/            menuOthers := menu.
 "/        ]
 "/    ] ifFalse:[
-        (menu isKindOf:Menu) ifTrue:[
-            "/ a newStyle menuPanel
-            "/ (menu atNameKey:'refactor') "atMenuItemLabeled:'Refactor'" putSubmenu:shiftedMenu visible:true.
-            menu atMenuItemLabeled:(resources string:'Refactor') putSubmenu:shiftedMenu visible:true.
-        ] ifFalse:[
-            "/ an oldStyle popUpMenu
-            "/ this is a kludge...
-            shiftedMenu := shiftedMenu asOldStylePopUpMenuFor:self.
-            "/ would like to add the shifted-menu here
-            menu menuView
-                addLabels:(Array with:'-' with:(resources string:'Refactor'))
-                selectors:#( nil refactorings)
-                accelerators:#(nil 'Shift')
-                after:#accept.
-            menu subMenuAt:#refactorings put:shiftedMenu.
-
-            menuOthers := menu subMenuAt:#others.
-        ].
+	(menu isKindOf:Menu) ifTrue:[
+	    "/ a newStyle menuPanel
+	    "/ (menu atNameKey:'refactor') "atMenuItemLabeled:'Refactor'" putSubmenu:shiftedMenu visible:true.
+	    menu atMenuItemLabeled:(resources string:'Refactor') putSubmenu:shiftedMenu visible:true.
+	] ifFalse:[
+	    "/ an oldStyle popUpMenu
+	    "/ this is a kludge...
+	    shiftedMenu := shiftedMenu asOldStylePopUpMenuFor:self.
+	    "/ would like to add the shifted-menu here
+	    menu menuView
+		addLabels:(Array with:'-' with:(resources string:'Refactor'))
+		selectors:#( nil refactorings)
+		accelerators:#(nil 'Shift')
+		after:#accept.
+	    menu subMenuAt:#refactorings put:shiftedMenu.
+
+	    menuOthers := menu subMenuAt:#others.
+	].
 "/    ].
 
 "/    sensor shiftDown ifFalse:[
@@ -45768,25 +46312,25 @@
     <resource: #programMenu >
 
     ^ [
-        |m anyItem hosts|
-
-        m := Menu new.
-        hosts := Set new.
-        self selectedClassesValue do:[:cls |
-            hosts addAll:(SmallTeam hostsWithChangeForClassOrMetaclass:cls theNonMetaclass).
-        ].
-        hosts := hosts asOrderedCollection sort.
-        anyItem := false.
-        hosts do:[:eachHost |
-            |item|
-
-            item := MenuItem label:eachHost.
-            item value:#'classMenuCompareWithSmallTeamVersionOnHost:'.
-            item argument:eachHost.
-            m addItem:item.
-            anyItem := true.
-        ].
-        anyItem ifFalse:[ nil ] ifTrue:[ m ]
+	|m anyItem hosts|
+
+	m := Menu new.
+	hosts := Set new.
+	self selectedClassesValue do:[:cls |
+	    hosts addAll:(SmallTeam hostsWithChangeForClassOrMetaclass:cls theNonMetaclass).
+	].
+	hosts := hosts asOrderedCollection sort.
+	anyItem := false.
+	hosts do:[:eachHost |
+	    |item|
+
+	    item := MenuItem label:eachHost.
+	    item value:#'classMenuCompareWithSmallTeamVersionOnHost:'.
+	    item argument:eachHost.
+	    m addItem:item.
+	    anyItem := true.
+	].
+	anyItem ifFalse:[ nil ] ifTrue:[ m ]
     ].
 
     "Created: / 11-11-2006 / 15:19:53 / cg"
@@ -45796,27 +46340,27 @@
     <resource: #programMenu >
 
     ^ [
-        |m anyItem hosts|
-
-        anyItem := false.
-        SmallTeam notNil ifTrue:[
-            m := Menu new.
-            hosts := Set new.
-            self selectedMethodsValue do:[:m |
-                hosts addAll:(SmallTeam hostsWithChangeForClass:(m mclass) selector:(m selector)).
-            ].
-            hosts := hosts asOrderedCollection sort.
-            hosts do:[:eachHost |
-                |item|
-
-                item := MenuItem label:eachHost.
-                item value:#'selectorMenuCompareWithSmallTeamVersionOnHost:'.
-                item argument:eachHost.
-                m addItem:item.
-                anyItem := true.
-            ].
-        ].
-        anyItem ifFalse:[ nil ] ifTrue:[ m ]
+	|m anyItem hosts|
+
+	anyItem := false.
+	SmallTeam notNil ifTrue:[
+	    m := Menu new.
+	    hosts := Set new.
+	    self selectedMethodsValue do:[:m |
+		hosts addAll:(SmallTeam hostsWithChangeForClass:(m mclass) selector:(m selector)).
+	    ].
+	    hosts := hosts asOrderedCollection sort.
+	    hosts do:[:eachHost |
+		|item|
+
+		item := MenuItem label:eachHost.
+		item value:#'selectorMenuCompareWithSmallTeamVersionOnHost:'.
+		item argument:eachHost.
+		m addItem:item.
+		anyItem := true.
+	    ].
+	].
+	anyItem ifFalse:[ nil ] ifTrue:[ m ]
     ].
 
     "Created: / 11-11-2006 / 15:19:18 / cg"
@@ -45826,25 +46370,25 @@
     <resource: #programMenu >
 
     ^ [
-        |m anyItem hosts|
-
-        m := Menu new.
-        hosts := Set new.
-        self selectedMethodsValue do:[:m |
-            hosts addAll:(SmallTeam hostsWithChangeForClass:(m mclass) selector:(m selector)).
-        ].
-        hosts := hosts asOrderedCollection sort.
-        anyItem := false.
-        hosts do:[:eachHost |
-            |item|
-
-            item := MenuItem label:eachHost.
-            item value:#'selectorMenuCompareWithSmallTeamVersionOnHost:'.
-            item argument:eachHost.
-            m addItem:item.
-            anyItem := true.
-        ].
-        anyItem ifFalse:[ nil ] ifTrue:[ m ]
+	|m anyItem hosts|
+
+	m := Menu new.
+	hosts := Set new.
+	self selectedMethodsValue do:[:m |
+	    hosts addAll:(SmallTeam hostsWithChangeForClass:(m mclass) selector:(m selector)).
+	].
+	hosts := hosts asOrderedCollection sort.
+	anyItem := false.
+	hosts do:[:eachHost |
+	    |item|
+
+	    item := MenuItem label:eachHost.
+	    item value:#'selectorMenuCompareWithSmallTeamVersionOnHost:'.
+	    item argument:eachHost.
+	    m addItem:item.
+	    anyItem := true.
+	].
+	anyItem ifFalse:[ nil ] ifTrue:[ m ]
     ].
 
     "Created: / 11-11-2006 / 15:03:16 / cg"
@@ -45860,33 +46404,33 @@
     <resource: #programMenu >
 
     ^ [
-        |m|
-
-        FindHistory size > 0 ifTrue:[
-            m := Menu new.
-            FindHistory do:[:entry |
-                |item className name sel itemLabel|
-
-                className := entry className ? '?'.
-                entry meta ifTrue:[
-                    className := className , ' class'.
-                ].
-                name := className allBold.
-                (sel := entry selector) notNil ifTrue:[
-                    name := name , ' ' , sel.
-                ].
-                itemLabel := name contractTo:100.
-                item := MenuItem label:itemLabel.
-                m addItem:item.
-                item value:#'switchToFindHistoryEntry:'.
-                item argument:entry.
-                (Smalltalk classNamed:className) isBehavior ifFalse:[
-                    item enabled:false.
-                    item label:(LabelAndIcon icon:(ToolbarIconLibrary erase16x16Icon2) string:itemLabel)
-                ].
-            ].
-        ].
-        m
+	|m|
+
+	FindHistory size > 0 ifTrue:[
+	    m := Menu new.
+	    FindHistory do:[:entry |
+		|item className name sel itemLabel|
+
+		className := entry className ? '?'.
+		entry meta ifTrue:[
+		    className := className , ' class'.
+		].
+		name := className allBold.
+		(sel := entry selector) notNil ifTrue:[
+		    name := name , ' ' , sel.
+		].
+		itemLabel := name contractTo:100.
+		item := MenuItem label:itemLabel.
+		m addItem:item.
+		item value:#'switchToFindHistoryEntry:'.
+		item argument:entry.
+		(Smalltalk classNamed:className) isBehavior ifFalse:[
+		    item enabled:false.
+		    item label:(LabelAndIcon icon:(ToolbarIconLibrary erase16x16Icon2) string:itemLabel)
+		].
+	    ].
+	].
+	m
     ].
 !
 
@@ -45899,39 +46443,39 @@
     classes := Set new.
 
     self selectedMethodsDo:[:m |
-        m literalsDo:[:lit |
-            |cls ns|
-
-            lit isSymbol ifTrue:[
-                (((cls := Smalltalk at:lit) notNil and:[ cls isBehavior ])
-                "JV@2011-11-25: Added check if the nameSpace is really a namespace, it may be
-                 a class if m mclass is a privateClass...
-                 ---------------------------------------------v"
-                or:[ m mclass notNil 
-                     and:[ (ns := m mclass nameSpace) notNil 
-                     and:[ ns isNameSpace 
-                     and:[ ns ~= Smalltalk
-                     and:[ (cls := ns at:lit) notNil  and:[ cls isBehavior ]]]]]])
-                ifTrue:[
-                    classes add:cls
-                ]
-            ]
-        ].
+	m literalsDo:[:lit |
+	    |cls ns|
+
+	    lit isSymbol ifTrue:[
+		(((cls := Smalltalk at:lit) notNil and:[ cls isBehavior ])
+		"JV@2011-11-25: Added check if the nameSpace is really a namespace, it may be
+		 a class if m mclass is a privateClass...
+		 ---------------------------------------------v"
+		or:[ m mclass notNil
+		     and:[ (ns := m mclass nameSpace) notNil
+		     and:[ ns isNameSpace
+		     and:[ ns ~= Smalltalk
+		     and:[ (cls := ns at:lit) notNil  and:[ cls isBehavior ]]]]]])
+		ifTrue:[
+		    classes add:cls
+		]
+	    ]
+	].
     ].
     classes isEmpty ifTrue:[
-        ^ nil
+	^ nil
     ].
 
     classes := classes asOrderedCollection sort:[:a :b | a name < b name].
 
     m := Menu new.
     classes do:[:each |
-        |item|
-
-        item := MenuItem label:each name.   
-        item value:#'spawnBrowserOnClass:'.
-        item argument:each.
-        m addItem:item.
+	|item|
+
+	item := MenuItem label:each name.
+	item value:#'spawnBrowserOnClass:'.
+	item argument:each.
+	m addItem:item.
     ].
     ^ m
 
@@ -45997,13 +46541,13 @@
 
 implementedMessagesMenu
     ^ [
-        self
-            messagesMenuFor:#'spawnBrowserOnAllImplementorsOf:'
-            withSenderChain:false
-            withImplementorChain:true
-            withLocalSenders:false
-            withLocalImplementors:true
-            selfSendsOnly:false
+	self
+	    messagesMenuFor:#'spawnBrowserOnAllImplementorsOf:'
+	    withSenderChain:false
+	    withImplementorChain:true
+	    withLocalSenders:false
+	    withLocalImplementors:true
+	    selfSendsOnly:false
       ]
 
     "Modified: / 05-09-2006 / 10:34:10 / cg"
@@ -46013,25 +46557,25 @@
     <resource: #programMenu >
 
     ^ [
-        |m anyItem hosts|
-
-        m := Menu new.
-        hosts := Set new.
-        self selectedMethodsValue do:[:m |
-            hosts addAll:(SmallTeam hostsWithChangeForClass:(m mclass) selector:(m selector)).
-        ].
-        hosts := hosts asOrderedCollection sort.
-        anyItem := false.
-        hosts do:[:eachHost |
-            |item|
-
-            item := MenuItem label:eachHost.
-            item value:#'selectorMenuLoadSmallTeamVersionFromHost:'.
-            item argument:eachHost.
-            m addItem:item.
-            anyItem := true.
-        ].
-        anyItem ifFalse:[ nil ] ifTrue:[ m ]
+	|m anyItem hosts|
+
+	m := Menu new.
+	hosts := Set new.
+	self selectedMethodsValue do:[:m |
+	    hosts addAll:(SmallTeam hostsWithChangeForClass:(m mclass) selector:(m selector)).
+	].
+	hosts := hosts asOrderedCollection sort.
+	anyItem := false.
+	hosts do:[:eachHost |
+	    |item|
+
+	    item := MenuItem label:eachHost.
+	    item value:#'selectorMenuLoadSmallTeamVersionFromHost:'.
+	    item argument:eachHost.
+	    m addItem:item.
+	    anyItem := true.
+	].
+	anyItem ifFalse:[ nil ] ifTrue:[ m ]
     ].
 
     "Created: / 12-11-2006 / 15:47:43 / cg"
@@ -46046,11 +46590,11 @@
 
     menu := Menu new.
     items do:[:historyEntry|
-        any := true.
-        menu addItem:
-            (MenuItem new
-                label: historyEntry displayString;
-                value:[self switchToHistoryEntry: historyEntry])
+	any := true.
+	menu addItem:
+	    (MenuItem new
+		label: historyEntry displayString;
+		value:[self switchToHistoryEntry: historyEntry])
     ].
     any ifFalse:[^ nil ].
     ^ menu
@@ -46061,45 +46605,45 @@
 
 messagesMenuFor:actionSelector withSenderChain:withSenderChain withImplementorChain:withImplementorChain
     ^ self
-        messagesMenuFor:actionSelector
-        withSenderChain:withSenderChain
-        withImplementorChain:withImplementorChain
-        selfSendsOnly:false
+	messagesMenuFor:actionSelector
+	withSenderChain:withSenderChain
+	withImplementorChain:withImplementorChain
+	selfSendsOnly:false
 
     "Modified: / 05-09-2006 / 10:26:26 / cg"
 !
 
 messagesMenuFor:actionSelector withSenderChain:withSenderChain withImplementorChain:withImplementorChain selfSendsOnly:selfSendsOnly
     ^ [
-        self
-            messagesMenuFor:actionSelector
-            withSenderChain:withSenderChain
-            withImplementorChain:withImplementorChain
-            withLocalSenders:false
-            withLocalImplementors:false
-            selfSendsOnly:selfSendsOnly
+	self
+	    messagesMenuFor:actionSelector
+	    withSenderChain:withSenderChain
+	    withImplementorChain:withImplementorChain
+	    withLocalSenders:false
+	    withLocalImplementors:false
+	    selfSendsOnly:selfSendsOnly
       ]
 
     "Modified: / 05-09-2006 / 10:33:05 / cg"
 !
 
-messagesMenuFor:actionSelector 
-    withSenderChain:withSenderChain withImplementorChain:withImplementorChain 
-    withLocalSenders:withLocalSenders withLocalImplementors:withLocalImplementors 
+messagesMenuFor:actionSelector
+    withSenderChain:withSenderChain withImplementorChain:withImplementorChain
+    withLocalSenders:withLocalSenders withLocalImplementors:withLocalImplementors
     selfSendsOnly:selfSendsOnly
 
     ^ self
-        messagesMenuFor:actionSelector
-        withSenderChain:withSenderChain withImplementorChain:withImplementorChain 
-        withLocalSenders:withLocalSenders withLocalImplementors:withLocalImplementors 
-        withCallersOfThisMethod:true "false" withMethodsCalledByThisMethod:false
-        selfSendsOnly:selfSendsOnly
+	messagesMenuFor:actionSelector
+	withSenderChain:withSenderChain withImplementorChain:withImplementorChain
+	withLocalSenders:withLocalSenders withLocalImplementors:withLocalImplementors
+	withCallersOfThisMethod:true "false" withMethodsCalledByThisMethod:false
+	selfSendsOnly:selfSendsOnly
 
     "Modified: / 27-04-2010 / 15:07:13 / cg"
 !
 
-messagesMenuFor:actionSelector 
-    withSenderChain:withSenderChain withImplementorChain:withImplementorChain 
+messagesMenuFor:actionSelector
+    withSenderChain:withSenderChain withImplementorChain:withImplementorChain
     withLocalSenders:withLocalSenders withLocalImplementors:withLocalImplementors
     withCallersOfThisMethod:withCallersOfThisMethod withMethodsCalledByThisMethod:withMethodsCalledByThisMethod
     selfSendsOnly:selfSendsOnly
@@ -46112,12 +46656,12 @@
 
     mthd := self theSingleSelectedMethod.
     (mthd notNil and:[ (mSel := mthd selector) notNil]) ifTrue:[
-        contractedSelector := mSel contractTo:80.
-
-        item := MenuItem label:(' ' , contractedSelector , ' ').   "/ ' ' is a kludge - to allow '-' selector
-        item value:actionSelector.
-        item argument:mSel.
-        m addItem:item.
+	contractedSelector := mSel contractTo:80.
+
+	item := MenuItem label:(' ' , contractedSelector , ' ').   "/ ' ' is a kludge - to allow '-' selector
+	item value:actionSelector.
+	item argument:mSel.
+	m addItem:item.
 
 "/            true "withInstanceProtocolOnly" ifTrue:[
 "/                item := MenuItem label:(resources string:' %1 - Instance Protocol Only' with:contractedSelector).
@@ -46132,121 +46676,121 @@
 "/                m addItem:item.
 "/            ].
 
-        (withLocalSenders | withSenderChain | withLocalImplementors | withImplementorChain) ifTrue:[
-            m addSeparator.
-        ].
-
-        withLocalSenders ifTrue:[
-            "/ item := MenuItem label:(resources string:' %1 - Local Senders' with:contractedSelector).
-            item := MenuItem label:(resources string:'Local Senders of %1' with:contractedSelector).
-            item value:#spawnLocalSendersBuffer.
-            m addItem:item.
-        ].
-        withSenderChain ifTrue:[
-            "/ item := MenuItem label:(resources string:' %1 - Sender Chain' with:contractedSelector).
-            item := MenuItem label:(resources string:'Sender Chain of %1' with:contractedSelector).
-            item value:#spawnSenderChainBuffer.
-            m addItem:item.
-        ].
-        (withCallersOfThisMethod and:[mthd isInstrumented]) ifTrue:[
-            item := MenuItem label:(resources string:'Callers of this %1' with:contractedSelector).
-            item value:#spawnCallersBuffer.
-            m addItem:item.
-        ].
-
-        withLocalImplementors ifTrue:[
-            item := MenuItem label:(resources string:'Local Implementors of %1' with:contractedSelector).
-            item value:#spawnLocalImplementorsBuffer.
-            m addItem:item.
-        ].
-        withImplementorChain ifTrue:[
-            item := MenuItem label:(resources string:'Implementor Chain of %1' with:contractedSelector).
-            item value:#spawnImplementorChainBuffer.
-            m addItem:item.
-        ].
-        withMethodsCalledByThisMethod ifTrue:[
-            item := MenuItem label:(resources string:'Methods Called by this %1' with:contractedSelector).
-            item value:#spawnMethodsCalledByBuffer.
-            m addItem:item.
-        ].
-
-        selfSendsOnly ifTrue:[
-            l := mthd messagesSentToSelf.
-        ] ifFalse:[
-            l := mthd messagesSent.
-        ].
-        l := l asSortedCollection.
-        l size > 0 ifTrue:[
-            m addSeparator.
+	(withLocalSenders | withSenderChain | withLocalImplementors | withImplementorChain) ifTrue:[
+	    m addSeparator.
+	].
+
+	withLocalSenders ifTrue:[
+	    "/ item := MenuItem label:(resources string:' %1 - Local Senders' with:contractedSelector).
+	    item := MenuItem label:(resources string:'Local Senders of %1' with:contractedSelector).
+	    item value:#spawnLocalSendersBuffer.
+	    m addItem:item.
+	].
+	withSenderChain ifTrue:[
+	    "/ item := MenuItem label:(resources string:' %1 - Sender Chain' with:contractedSelector).
+	    item := MenuItem label:(resources string:'Sender Chain of %1' with:contractedSelector).
+	    item value:#spawnSenderChainBuffer.
+	    m addItem:item.
+	].
+	(withCallersOfThisMethod and:[mthd isInstrumented]) ifTrue:[
+	    item := MenuItem label:(resources string:'Callers of this %1' with:contractedSelector).
+	    item value:#spawnCallersBuffer.
+	    m addItem:item.
+	].
+
+	withLocalImplementors ifTrue:[
+	    item := MenuItem label:(resources string:'Local Implementors of %1' with:contractedSelector).
+	    item value:#spawnLocalImplementorsBuffer.
+	    m addItem:item.
+	].
+	withImplementorChain ifTrue:[
+	    item := MenuItem label:(resources string:'Implementor Chain of %1' with:contractedSelector).
+	    item value:#spawnImplementorChainBuffer.
+	    m addItem:item.
+	].
+	withMethodsCalledByThisMethod ifTrue:[
+	    item := MenuItem label:(resources string:'Methods Called by this %1' with:contractedSelector).
+	    item value:#spawnMethodsCalledByBuffer.
+	    m addItem:item.
+	].
+
+	selfSendsOnly ifTrue:[
+	    l := mthd messagesSentToSelf.
+	] ifFalse:[
+	    l := mthd messagesSent.
+	].
+	l := l asSortedCollection.
+	l size > 0 ifTrue:[
+	    m addSeparator.
 
 "
-                (l size > 30) ifTrue:[
-                    l removeAllFoundIn:#(ifTrue: ifFalse: ifTrue:ifFalse: ifFalse:ifTrue:
-                                         whileTrue: whileFalse:
-                                         isNil notNil
-                                         and: or:
-                                        ).
-                    (l size > 30) ifTrue:[
-                        l removeAllFoundIn:#(#'==' #'~~' class
-                                            ).
-                    ]
-                ].
-                (cut := l size > 30) ifTrue:[
-                    l := l copyTo:30
-                ].
+		(l size > 30) ifTrue:[
+		    l removeAllFoundIn:#(ifTrue: ifFalse: ifTrue:ifFalse: ifFalse:ifTrue:
+					 whileTrue: whileFalse:
+					 isNil notNil
+					 and: or:
+					).
+		    (l size > 30) ifTrue:[
+			l removeAllFoundIn:#(#'==' #'~~' class
+					    ).
+		    ]
+		].
+		(cut := l size > 30) ifTrue:[
+		    l := l copyTo:30
+		].
 "
-            l do:[:eachMessage |
-                item := MenuItem label:(' ' , (eachMessage contractTo:100), ' ').  "/ ' ' is a kludge - to allow '-' selector
-                item value:actionSelector.
-                item argument:eachMessage asSymbol.
-                m addItem:item.
-            ].
+	    l do:[:eachMessage |
+		item := MenuItem label:(' ' , (eachMessage contractTo:100), ' ').  "/ ' ' is a kludge - to allow '-' selector
+		item value:actionSelector.
+		item argument:eachMessage asSymbol.
+		m addItem:item.
+	    ].
 
 "
-                cut ifTrue:[
-                    m addItem:(MenuItem label:'-').
-                    m addItem:(MenuItem label:'<< more items ignored >>').
-                ]
+		cut ifTrue:[
+		    m addItem:(MenuItem label:'-').
+		    m addItem:(MenuItem label:'<< more items ignored >>').
+		]
 "
-        ]
-    ] ifFalse:[
-        allMessagesSent := Set new.
-
-        "/ not exactly one method selected;
-        "/ generate a menu for all selected method's implementors and sent messages.
-        methods := self selectedMethodsValue.
-        methods isEmptyOrNil ifTrue:[
-            methods := OrderedCollection new.
-            self selectedClassesDo:[:cls |
-                cls methodsDo:[:eachMethod | methods add:eachMethod].
-            ].
-        ].
-        methods do:[:eachMethod |
-            mSel := eachMethod selector ? '?'.
-            contractedSelector := mSel contractTo:80.
-
-            item := MenuItem label:(' ' , contractedSelector , ' ').   "/ ' ' is a kludge - to allow '-' selector
-            item value:actionSelector.
-            item argument:mSel.
-            m addItem:item.
-
-            selfSendsOnly ifTrue:[
-                allMessagesSent addAll:(eachMethod messagesSentToSelf).
-            ] ifFalse:[
-                allMessagesSent addAll:(eachMethod messagesSent).
-            ].
-        ].
-
-        allMessagesSent := allMessagesSent asSortedCollection.
-        allMessagesSent size > 0 ifTrue:[
-            m addSeparator.
-            allMessagesSent do:[:eachMessage |
-                item := MenuItem label:(' ' , (eachMessage contractTo:100), ' ').  "/ ' ' is a kludge - to allow '-' selector
-                item value:actionSelector.
-                item argument:eachMessage asSymbol.
-                m addItem:item.
-            ].
-        ].
+	]
+    ] ifFalse:[
+	allMessagesSent := Set new.
+
+	"/ not exactly one method selected;
+	"/ generate a menu for all selected method's implementors and sent messages.
+	methods := self selectedMethodsValue.
+	methods isEmptyOrNil ifTrue:[
+	    methods := OrderedCollection new.
+	    self selectedClassesDo:[:cls |
+		cls methodsDo:[:eachMethod | methods add:eachMethod].
+	    ].
+	].
+	methods do:[:eachMethod |
+	    mSel := eachMethod selector ? '?'.
+	    contractedSelector := mSel contractTo:80.
+
+	    item := MenuItem label:(' ' , contractedSelector , ' ').   "/ ' ' is a kludge - to allow '-' selector
+	    item value:actionSelector.
+	    item argument:mSel.
+	    m addItem:item.
+
+	    selfSendsOnly ifTrue:[
+		allMessagesSent addAll:(eachMethod messagesSentToSelf).
+	    ] ifFalse:[
+		allMessagesSent addAll:(eachMethod messagesSent).
+	    ].
+	].
+
+	allMessagesSent := allMessagesSent asSortedCollection.
+	allMessagesSent size > 0 ifTrue:[
+	    m addSeparator.
+	    allMessagesSent do:[:eachMessage |
+		item := MenuItem label:(' ' , (eachMessage contractTo:100), ' ').  "/ ' ' is a kludge - to allow '-' selector
+		item value:actionSelector.
+		item argument:eachMessage asSymbol.
+		m addItem:item.
+	    ].
+	].
     ].
 
     ^ m
@@ -46258,65 +46802,65 @@
 operationsMenu
     <resource: #programMenu >
 
-        | manager item menu undoCountMenuItem lRedo lUndo
-          undoListMenu|
-
-        (self canUseRefactoringSupport) ifFalse:[
-            ^
-             #(#Menu
-                #(
-                 #(#MenuItem
-                    #label: 'Load Refactoring and Undo Features'
-                    #translateLabel: true
-                    #showBusyCursorWhilePerforming: true
-                    #value: #doLoadRefactoringSupport
-                  )
-                 )
-                nil
-                nil
-              )
-        ].
-
-        manager := RefactoryChangeManager instance.
-        menu := Menu new.
-
-        lUndo := (manager hasUndoableOperations
-                ifTrue: [resources string:'Undo: %1' with:(manager undoChange name contractTo:100)]
-                ifFalse: [resources string:'Undo']).
-
-        item := MenuItem labeled:lUndo.
-        item showBusyCursorWhilePerforming:true.
-        item value:[ self operationsMenuUndo ].
-        manager hasUndoableOperations ifFalse: [item disable].
-        menu addItem:item.
-
-        lRedo := (manager hasRedoableOperations
-                ifTrue: [resources string:'Redo: %1' with:(manager redoChange name contractTo:100)]
-                ifFalse: [resources string:'Redo']).
-
-        item := MenuItem labeled:lRedo.
-        item showBusyCursorWhilePerforming:true.
-        item value:[ self operationsMenuRedo].
-        manager hasRedoableOperations ifFalse: [item disable].
-        menu addItem:item.
-
-        undoListMenu := Menu new.
-        manager undoableOperations reverseDo:[:eachUndoChange |
-            item := MenuItem labeled:(eachUndoChange name contractTo:100).
-            item showBusyCursorWhilePerforming:true.
-            item value:[ self operationsMenuUndo:eachUndoChange ].
-            undoListMenu addItem:item.
-        ].
-        item := MenuItem labeled:(resources string:'Undo Recent').
-        item submenu:undoListMenu.
-        item enabled:manager hasUndoableOperations.
-        menu addItem:item.
-
-        undoCountMenuItem := (MenuItem labeled: (resources string:'Set Undo Count...'))
-                                value: [self setUndoCount];
-                                yourself.
-        menu addItemGroup: (Array with: undoCountMenuItem).
-        ^menu
+	| manager item menu undoCountMenuItem lRedo lUndo
+	  undoListMenu|
+
+	(self canUseRefactoringSupport) ifFalse:[
+	    ^
+	     #(#Menu
+		#(
+		 #(#MenuItem
+		    #label: 'Load Refactoring and Undo Features'
+		    #translateLabel: true
+		    #showBusyCursorWhilePerforming: true
+		    #value: #doLoadRefactoringSupport
+		  )
+		 )
+		nil
+		nil
+	      )
+	].
+
+	manager := RefactoryChangeManager instance.
+	menu := Menu new.
+
+	lUndo := (manager hasUndoableOperations
+		ifTrue: [resources string:'Undo: %1' with:(manager undoChange name contractTo:100)]
+		ifFalse: [resources string:'Undo']).
+
+	item := MenuItem labeled:lUndo.
+	item showBusyCursorWhilePerforming:true.
+	item value:[ self operationsMenuUndo ].
+	manager hasUndoableOperations ifFalse: [item disable].
+	menu addItem:item.
+
+	lRedo := (manager hasRedoableOperations
+		ifTrue: [resources string:'Redo: %1' with:(manager redoChange name contractTo:100)]
+		ifFalse: [resources string:'Redo']).
+
+	item := MenuItem labeled:lRedo.
+	item showBusyCursorWhilePerforming:true.
+	item value:[ self operationsMenuRedo].
+	manager hasRedoableOperations ifFalse: [item disable].
+	menu addItem:item.
+
+	undoListMenu := Menu new.
+	manager undoableOperations reverseDo:[:eachUndoChange |
+	    item := MenuItem labeled:(eachUndoChange name contractTo:100).
+	    item showBusyCursorWhilePerforming:true.
+	    item value:[ self operationsMenuUndo:eachUndoChange ].
+	    undoListMenu addItem:item.
+	].
+	item := MenuItem labeled:(resources string:'Undo Recent').
+	item submenu:undoListMenu.
+	item enabled:manager hasUndoableOperations.
+	menu addItem:item.
+
+	undoCountMenuItem := (MenuItem labeled: (resources string:'Set Undo Count...'))
+				value: [self setUndoCount];
+				yourself.
+	menu addItemGroup: (Array with: undoCountMenuItem).
+	^menu
 !
 
 projectMenu
@@ -46338,24 +46882,24 @@
     <resource: #programMenu >
 
     ^ [
-        |m cls classes|
-
-        cls := self theSingleSelectedClass.
-        (cls notNil and:[cls superclass notNil]) ifTrue:[
-            m := Menu new.
-            cls := cls superclass.
-            [cls notNil] whileTrue:[
-                |item className|
-
-                className := cls name.
-                item := MenuItem label:className.
-                m addItem:item beforeIndex:1.   "/ reverse
-                item value:#'switchToClassNamed:'.
-                item argument:className.
-                cls := cls superclass.
-            ].
-        ].
-        m
+	|m cls classes|
+
+	cls := self theSingleSelectedClass.
+	(cls notNil and:[cls superclass notNil]) ifTrue:[
+	    m := Menu new.
+	    cls := cls superclass.
+	    [cls notNil] whileTrue:[
+		|item className|
+
+		className := cls name.
+		item := MenuItem label:className.
+		m addItem:item beforeIndex:1.   "/ reverse
+		item value:#'switchToClassNamed:'.
+		item argument:className.
+		cls := cls superclass.
+	    ].
+	].
+	m
     ].
 !
 
@@ -46364,37 +46908,37 @@
     |m selectedClasses currentLanguage allLanguages|
 
     (selectedClasses := self selectedClasses value) notEmptyOrNil ifTrue:[
-        selectedClasses size == 1 ifTrue:[
-            "/Single class selected
-            currentLanguage := selectedClasses anElement programmingLanguage.
-        ] ifFalse:[
-            "/Multiple class selected, be strict here
-            currentLanguage := nil."/unknown
-        ].
-    ] ifFalse:[
-        currentLanguage := nil."/unknown
+	selectedClasses size == 1 ifTrue:[
+	    "/Single class selected
+	    currentLanguage := selectedClasses anElement programmingLanguage.
+	] ifFalse:[
+	    "/Multiple class selected, be strict here
+	    currentLanguage := nil."/unknown
+	].
+    ] ifFalse:[
+	currentLanguage := nil."/unknown
     ].
 
     allLanguages := OrderedCollection new.
-    ProgrammingLanguage allDo:[:eachLanguage | 
-        eachLanguage isSmalltalk ifFalse:[
-            allLanguages add:eachLanguage
-        ]
+    ProgrammingLanguage allDo:[:eachLanguage |
+	eachLanguage isSmalltalk ifFalse:[
+	    allLanguages add:eachLanguage
+	]
     ].
     allLanguages sort:[:a :b | a name < b name].
 
     m := Menu new.
-    m addItem:(MenuItem 
-                label:'Smalltalk Method' 
-                value:[self selectorMenuNewMethod: SmalltalkLanguage instance]).
+    m addItem:(MenuItem
+		label:'Smalltalk Method'
+		value:[self selectorMenuNewMethod: SmalltalkLanguage instance]).
 
     allLanguages do:[:eachLanguage |
-        eachLanguage compilerClass notNil ifTrue:[
-            m addItem:((MenuItem 
-                        label:(eachLanguage name) , ' Method'
-                        value:[self selectorMenuNewMethod: eachLanguage])
-                        enabled: (eachLanguage supportsExtensionMethods or:[eachLanguage = currentLanguage]))
-        ]
+	eachLanguage compilerClass notNil ifTrue:[
+	    m addItem:((MenuItem
+			label:(eachLanguage name) , ' Method'
+			value:[self selectorMenuNewMethod: eachLanguage])
+			enabled: (eachLanguage supportsExtensionMethods or:[eachLanguage = currentLanguage]))
+	]
     ].
     ^ m
 
@@ -46405,13 +46949,13 @@
 
 sentMessagesMenu
     ^ [
-        self
-            messagesMenuFor:#'spawnBrowserOnAllSendersOf:'
-            withSenderChain:true "(self window sensor ctrlDown)"
-            withImplementorChain:false
-            withLocalSenders:true
-            withLocalImplementors:false
-            selfSendsOnly:false
+	self
+	    messagesMenuFor:#'spawnBrowserOnAllSendersOf:'
+	    withSenderChain:true "(self window sensor ctrlDown)"
+	    withImplementorChain:false
+	    withLocalSenders:true
+	    withLocalImplementors:false
+	    selfSendsOnly:false
       ]
 
     "Modified: / 05-09-2006 / 10:33:41 / cg"
@@ -46419,10 +46963,10 @@
 
 sentMessagesResponseMenu
     ^ self
-        messagesMenuFor:#'findResponseTo:'
-        withSenderChain:false
-        withImplementorChain:false
-        selfSendsOnly:true
+	messagesMenuFor:#'findResponseTo:'
+	withSenderChain:false
+	withImplementorChain:false
+	selfSendsOnly:true
 
     "Modified: / 05-09-2006 / 10:33:49 / cg"
 !
@@ -46434,11 +46978,11 @@
     | menu |
     menu := Menu decodeFromLiteralArray: self class toolBarMenu.
     (menu menuItemWithValue: #goBack)
-        submenuChannel:[self goBackMenu].
+	submenuChannel:[self goBackMenu].
     (menu menuItemWithValue: #goBackInGlobalHistory)
-        submenuChannel:[self goBackInGlobalHistoryMenu].
+	submenuChannel:[self goBackInGlobalHistoryMenu].
     (menu menuItemWithValue: #goForward)
-        submenuChannel:[self goForwardMenu].
+	submenuChannel:[self goForwardMenu].
 "/ no, I explicitly do not want this
 "/    (menu menuItemWithValue: #goForwardInGlobalHistory)
 "/        submenuChannel:[self goForwardInGlobalHistoryMenu].
@@ -46452,27 +46996,27 @@
     <resource: #programMenu >
 
     ^ [
-        |m classHistory currentClass|
-
-        currentClass := self theSingleSelectedClass.
-        classHistory := self class classHistory.
-        classHistory size > 0 ifTrue:[
-            m := Menu new.
-            classHistory do:[:entry |
-                |item className|
-
-                className := entry className ? ''.
-                (currentClass notNil
-                and:[currentClass name = className])
-                ifFalse:[
-                    item := MenuItem label:(className contractTo:100).
-                    m addItem:item.
-                    item value:#'switchToHistoryEntry:'.
-                    item argument:entry.
-                ].
-            ].
-        ].
-        m
+	|m classHistory currentClass|
+
+	currentClass := self theSingleSelectedClass.
+	classHistory := self class classHistory.
+	classHistory size > 0 ifTrue:[
+	    m := Menu new.
+	    classHistory do:[:entry |
+		|item className|
+
+		className := entry className ? ''.
+		(currentClass notNil
+		and:[currentClass name = className])
+		ifFalse:[
+		    item := MenuItem label:(className contractTo:100).
+		    m addItem:item.
+		    item value:#'switchToHistoryEntry:'.
+		    item argument:entry.
+		].
+	    ].
+	].
+	m
     ].
 
     "Modified: / 20-11-2006 / 12:23:08 / cg"
@@ -46488,18 +47032,18 @@
     |manager menu |
 
     sourceCodeManagerClassName isBehavior ifTrue:[
-        manager := sourceCodeManagerClassName
-    ] ifFalse:[
-        manager := Smalltalk at: sourceCodeManagerClassName.
+	manager := sourceCodeManagerClassName
+    ] ifFalse:[
+	manager := Smalltalk at: sourceCodeManagerClassName.
     ].
     manager isNil ifTrue:[
-        menu := Menu new.
-        menu addItem: 
-            (MenuItem 
-                label: (resources string: 'Unavailable - Configure SCM') 
-                value: [self openSettingsDialogAndSelectSourceCodeManagement])
-    ] ifFalse:[
-        menu := self class categoryMenuSCMCommon decodeAsLiteralArray.
+	menu := Menu new.
+	menu addItem:
+	    (MenuItem
+		label: (resources string: 'Unavailable - Configure SCM')
+		value: [self openSettingsDialogAndSelectSourceCodeManagement])
+    ] ifFalse:[
+	menu := self class categoryMenuSCMCommon decodeAsLiteralArray.
     ].
     self replaceSourceCodeManagerPlaceholderWith: manager in: menu.
 
@@ -46512,16 +47056,16 @@
 
     <resource: #programMenu>
 
-    ^self 
-        commonMenuSCMSliceNamed: #categoryMenuSCMSlice
-        computeManagerWith:
-            [:managers|
-            self selectedCategoryClassesDo: [:cls|
-                | mgr |
-
-                mgr := cls theNonMetaclass sourceCodeManager. 
-                mgr isNil ifFalse:[managers add: mgr]
-            ]].
+    ^self
+	commonMenuSCMSliceNamed: #categoryMenuSCMSlice
+	computeManagerWith:
+	    [:managers|
+	    self selectedCategoryClassesDo: [:cls|
+		| mgr |
+
+		mgr := cls theNonMetaclass sourceCodeManager.
+		mgr isNil ifFalse:[managers add: mgr]
+	    ]].
 
     "Created: / 19-04-2011 / 14:29:47 / cg"
     "Created: / 15-10-2011 / 12:31:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -46534,21 +47078,21 @@
     |manager spec menu |
 
     sourceCodeManagerClassName isBehavior ifTrue:[
-        manager := sourceCodeManagerClassName
-    ] ifFalse:[
-        manager := Smalltalk at: sourceCodeManagerClassName.
-        manager isNil ifTrue:[
-            ^Menu new
-        ].
+	manager := sourceCodeManagerClassName
+    ] ifFalse:[
+	manager := Smalltalk at: sourceCodeManagerClassName.
+	manager isNil ifTrue:[
+	    ^Menu new
+	].
     ].
     spec := self class perform: ('classMenuSCMExtra_' , manager managerTypeNameShort) asSymbol ifNotUnderstood:[nil].
     spec notNil ifTrue:[
-        menu := spec decodeAsLiteralArray.
-        menu receiver:self.
-        menu findGuiResourcesIn:self.
-        menu addItem: (MenuItem separator) beforeIndex: 1
-    ] ifFalse:[
-        menu := Menu new.
+	menu := spec decodeAsLiteralArray.
+	menu receiver:self.
+	menu findGuiResourcesIn:self.
+	menu addItem: (MenuItem separator) beforeIndex: 1
+    ] ifFalse:[
+	menu := Menu new.
     ].
     ^menu
 
@@ -46562,21 +47106,21 @@
     |manager spec menu |
 
     sourceCodeManagerClassName isBehavior ifTrue:[
-        manager := sourceCodeManagerClassName
-    ] ifFalse:[
-        manager := Smalltalk at: sourceCodeManagerClassName.
-        manager isNil ifTrue:[
-            ^Menu new
-        ].
+	manager := sourceCodeManagerClassName
+    ] ifFalse:[
+	manager := Smalltalk at: sourceCodeManagerClassName.
+	manager isNil ifTrue:[
+	    ^Menu new
+	].
     ].
     spec := self class perform: ('classMenuSCMExtra_' , manager managerTypeNameShort) asSymbol ifNotUnderstood:[nil].
     spec notNil ifTrue:[
-        menu := spec decodeAsLiteralArray.
-        menu receiver:self.
-        menu findGuiResourcesIn:self.
-        menu addItem: (MenuItem separator) beforeIndex: 1
-    ] ifFalse:[
-        menu := Menu new.
+	menu := spec decodeAsLiteralArray.
+	menu receiver:self.
+	menu findGuiResourcesIn:self.
+	menu addItem: (MenuItem separator) beforeIndex: 1
+    ] ifFalse:[
+	menu := Menu new.
     ].
     ^menu
 
@@ -46592,18 +47136,18 @@
     |manager menu |
 
     sourceCodeManagerClassName isBehavior ifTrue:[
-        manager := sourceCodeManagerClassName
-    ] ifFalse:[
-        manager := Smalltalk at: sourceCodeManagerClassName.
+	manager := sourceCodeManagerClassName
+    ] ifFalse:[
+	manager := Smalltalk at: sourceCodeManagerClassName.
     ].
     manager isNil ifTrue:[
-        menu := Menu new.
-        menu addItem: 
-            (MenuItem 
-                label: (resources string: 'Unavailable - Configure SCM') 
-                value: [self openSettingsDialogAndSelectSourceCodeManagement])
-    ] ifFalse:[
-        menu := self class classMenuSCMCommon decodeAsLiteralArray.
+	menu := Menu new.
+	menu addItem:
+	    (MenuItem
+		label: (resources string: 'Unavailable - Configure SCM')
+		value: [self openSettingsDialogAndSelectSourceCodeManagement])
+    ] ifFalse:[
+	menu := self class classMenuSCMCommon decodeAsLiteralArray.
     ].
     self replaceSourceCodeManagerPlaceholderWith: manager in: menu.
 
@@ -46616,23 +47160,23 @@
 
     <resource: #programMenu>
 
-    ^self 
-        commonMenuSCMSliceNamed: #classMenuSCMSlice
-        computeManagerWith:[:managers|
-            self selectedClassesDo: [:cls|
-                | mgr |
-
-                mgr := cls theNonMetaclass sourceCodeManager. 
-                mgr notNil ifTrue:[managers add: mgr]
-            ]
-        ].
+    ^self
+	commonMenuSCMSliceNamed: #classMenuSCMSlice
+	computeManagerWith:[:managers|
+	    self selectedClassesDo: [:cls|
+		| mgr |
+
+		mgr := cls theNonMetaclass sourceCodeManager.
+		mgr notNil ifTrue:[managers add: mgr]
+	    ]
+	].
 
     "Created: / 19-04-2011 / 14:29:47 / cg"
     "Created: / 07-10-2011 / 14:53:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 10-01-2012 / 00:26:38 / cg"
 !
 
-commonMenuSCMSliceNamed: sliceName computeManagerWith: managersBlock  
+commonMenuSCMSliceNamed: sliceName computeManagerWith: managersBlock
     "Common helper for SCM menu creation. managersBlock
      is one arg block that should fill a set of managers
      (passes as arg) for currently selected thingies
@@ -46643,39 +47187,39 @@
     | layout menu item managers manager |
 
     layout := UserPreferences current sourceCodeManagementMenuLayout.
-    menu := self class 
-                perform: 
-                    (sliceName,  '_' , layout) asSymbol
-                ifNotUnderstood: [self class perform:(sliceName,  '_old') asSymbol].    
+    menu := self class
+		perform:
+		    (sliceName,  '_' , layout) asSymbol
+		ifNotUnderstood: [self class perform:(sliceName,  '_old') asSymbol].
     menu := menu decodeAsLiteralArray.
-    managers := Set new.        
+    managers := Set new.
     managersBlock value: managers.
     managers size == 1 ifTrue:[
-        manager := managers anyOne.
-    ] ifFalse:[
-        manager := nil
+	manager := managers anyOne.
+    ] ifFalse:[
+	manager := nil
     ].
     item := menu menuItemWithKey:#SCM.
     (item notNil) ifTrue:[
-        manager notNil ifTrue:[
-            manager := managers anyOne.
-            item label:(resources string:'Repository') , '  ' , (manager managerTypeName asText colorizeAllWith:Color gray).
-        ] ifFalse:[
-            item label:(resources string:'Repository').
-            item enabled: false.
-        ].
+	manager notNil ifTrue:[
+	    manager := managers anyOne.
+	    item label:(resources string:'Repository') , '  ' , (manager managerTypeName asText colorizeAllWith:Color gray).
+	] ifFalse:[
+	    item label:(resources string:'Repository').
+	    item enabled: false.
+	].
     ].
     self replaceSourceCodeManagerPlaceholderWith: manager in: menu.
     (layout = 'inline') ifTrue:[
-        menu itemsDo:[:item|
-            manager notNil ifTrue:[
-                item argument == manager name ifTrue:[
-                    item label: (item label , '  ' , ((resources string: '(default)') asText colorizeAllWith: Color gray)).
-                ]
-            ] ifFalse:[
-                item enabled: false                
-            ].
-        ]
+	menu itemsDo:[:item|
+	    manager notNil ifTrue:[
+		item argument == manager name ifTrue:[
+		    item label: (item label , '  ' , ((resources string: '(default)') asText colorizeAllWith: Color gray)).
+		]
+	    ] ifFalse:[
+		item enabled: false
+	    ].
+	]
     ].
     ^ menu
 
@@ -46691,24 +47235,24 @@
     |manager menu |
 
     sourceCodeManagerClassName isBehavior ifTrue:[
-        manager := sourceCodeManagerClassName
-    ] ifFalse:[
-        manager := Smalltalk at: sourceCodeManagerClassName.
+	manager := sourceCodeManagerClassName
+    ] ifFalse:[
+	manager := Smalltalk at: sourceCodeManagerClassName.
     ].
     manager isNil ifTrue:[
-        menu := Menu new.
-        menu addItem: 
-            (MenuItem 
-                label: (resources string: 'Unavailable - Configure SCM') 
-                value: [self openSettingsDialogAndSelectSourceCodeManagement])
-    ] ifFalse:[
-        menu := self class projectMenuSCMCompareBuildSupportFile decodeAsLiteralArray.
-        menu itemsDo:[:item|
-
-            | selector |
-            selector := item value.
-            item value:[self perform: selector with: item argument with: manager]
-        ]
+	menu := Menu new.
+	menu addItem:
+	    (MenuItem
+		label: (resources string: 'Unavailable - Configure SCM')
+		value: [self openSettingsDialogAndSelectSourceCodeManagement])
+    ] ifFalse:[
+	menu := self class projectMenuSCMCompareBuildSupportFile decodeAsLiteralArray.
+	menu itemsDo:[:item|
+
+	    | selector |
+	    selector := item value.
+	    item value:[self perform: selector with: item argument with: manager]
+	]
     ].
     menu receiver:self.
     menu findGuiResourcesIn:self.
@@ -46724,24 +47268,24 @@
     |manager menu |
 
     sourceCodeManagerClassName isBehavior ifTrue:[
-        manager := sourceCodeManagerClassName
-    ] ifFalse:[
-        manager := Smalltalk at: sourceCodeManagerClassName.
+	manager := sourceCodeManagerClassName
+    ] ifFalse:[
+	manager := Smalltalk at: sourceCodeManagerClassName.
     ].
     manager isNil ifTrue:[
-        menu := Menu new.
-        menu addItem: 
-            (MenuItem 
-                label: (resources string: 'Unavailable - Configure SCM') 
-                value: [self openSettingsDialogAndSelectSourceCodeManagement])
-    ] ifFalse:[
-        menu := self class projectMenuSCMCompareBuildSupportFile decodeAsLiteralArray.
-        menu itemsDo:[:item|
-
-            | selector |
-            selector := item value.
-            item value:[self perform: selector with: item argument with: manager]
-        ]
+	menu := Menu new.
+	menu addItem:
+	    (MenuItem
+		label: (resources string: 'Unavailable - Configure SCM')
+		value: [self openSettingsDialogAndSelectSourceCodeManagement])
+    ] ifFalse:[
+	menu := self class projectMenuSCMCompareBuildSupportFile decodeAsLiteralArray.
+	menu itemsDo:[:item|
+
+	    | selector |
+	    selector := item value.
+	    item value:[self perform: selector with: item argument with: manager]
+	]
     ].
     menu receiver:self.
     menu findGuiResourcesIn:self.
@@ -46758,21 +47302,21 @@
     |manager spec menu |
 
     sourceCodeManagerClassName isBehavior ifTrue:[
-        manager := sourceCodeManagerClassName
-    ] ifFalse:[
-        manager := Smalltalk at: sourceCodeManagerClassName.
-        manager isNil ifTrue:[
-            ^Menu new
-        ].
+	manager := sourceCodeManagerClassName
+    ] ifFalse:[
+	manager := Smalltalk at: sourceCodeManagerClassName.
+	manager isNil ifTrue:[
+	    ^Menu new
+	].
     ].
     spec := self class perform: ('projectMenuSCMExtra_' , manager managerTypeNameShort) asSymbol ifNotUnderstood:[nil].
     spec notNil ifTrue:[
-        menu := spec decodeAsLiteralArray.
-        menu receiver:self.
-        menu findGuiResourcesIn:self.
-        menu addItem: (MenuItem separator) beforeIndex: 1
-    ] ifFalse:[
-        menu := Menu new.
+	menu := spec decodeAsLiteralArray.
+	menu receiver:self.
+	menu findGuiResourcesIn:self.
+	menu addItem: (MenuItem separator) beforeIndex: 1
+    ] ifFalse:[
+	menu := Menu new.
     ].
     ^menu
 
@@ -46787,18 +47331,18 @@
     |manager menu |
 
     sourceCodeManagerClassName isBehavior ifTrue:[
-        manager := sourceCodeManagerClassName
-    ] ifFalse:[
-        manager := Smalltalk at: sourceCodeManagerClassName.
+	manager := sourceCodeManagerClassName
+    ] ifFalse:[
+	manager := Smalltalk at: sourceCodeManagerClassName.
     ].
     manager isNil ifTrue:[
-        menu := Menu new.
-        menu addItem: 
-            (MenuItem 
-                label: (resources string: 'Unavailable - Configure SCM') 
-                value: [self openSettingsDialogAndSelectSourceCodeManagement])
-    ] ifFalse:[
-        menu := self class projectMenuSCMCommon decodeAsLiteralArray.
+	menu := Menu new.
+	menu addItem:
+	    (MenuItem
+		label: (resources string: 'Unavailable - Configure SCM')
+		value: [self openSettingsDialogAndSelectSourceCodeManagement])
+    ] ifFalse:[
+	menu := self class projectMenuSCMCommon decodeAsLiteralArray.
     ].
     self replaceSourceCodeManagerPlaceholderWith: manager in: menu.
 
@@ -46811,16 +47355,16 @@
 
     <resource: #programMenu>
 
-    ^self 
-        commonMenuSCMSliceNamed: #projectMenuSCMSlice
-        computeManagerWith:
-            [:managers|
-            self selectedProjectsDo:[:pkg|
-                | mgr |
-
-                mgr := AbstractSourceCodeManager managerForPackage:pkg.
-                mgr isNil ifFalse:[managers add: mgr]
-            ]].
+    ^self
+	commonMenuSCMSliceNamed: #projectMenuSCMSlice
+	computeManagerWith:
+	    [:managers|
+	    self selectedProjectsDo:[:pkg|
+		| mgr |
+
+		mgr := AbstractSourceCodeManager managerForPackage:pkg.
+		mgr isNil ifFalse:[managers add: mgr]
+	    ]].
 
     "Created: / 19-04-2011 / 14:29:47 / cg"
     "Created: / 12-10-2011 / 20:53:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -46833,21 +47377,21 @@
     |manager spec menu |
 
     sourceCodeManagerClassName isBehavior ifTrue:[
-        manager := sourceCodeManagerClassName
-    ] ifFalse:[
-        manager := Smalltalk at: sourceCodeManagerClassName.
-        manager isNil ifTrue:[
-            ^Menu new
-        ].
+	manager := sourceCodeManagerClassName
+    ] ifFalse:[
+	manager := Smalltalk at: sourceCodeManagerClassName.
+	manager isNil ifTrue:[
+	    ^Menu new
+	].
     ].
     spec := self class perform: ('selectorMenuSCMExtra_' , manager managerTypeNameShort) asSymbol ifNotUnderstood:[nil].
     spec notNil ifTrue:[
-        menu := spec decodeAsLiteralArray.
-        menu receiver:self.
-        menu findGuiResourcesIn:self.
-        menu addItem: (MenuItem separator) beforeIndex: 1
-    ] ifFalse:[
-        menu := Menu new.
+	menu := spec decodeAsLiteralArray.
+	menu receiver:self.
+	menu findGuiResourcesIn:self.
+	menu addItem: (MenuItem separator) beforeIndex: 1
+    ] ifFalse:[
+	menu := Menu new.
     ].
     ^menu
 
@@ -46862,18 +47406,18 @@
     |manager menu |
 
     sourceCodeManagerClassName isBehavior ifTrue:[
-        manager := sourceCodeManagerClassName
-    ] ifFalse:[
-        manager := Smalltalk at: sourceCodeManagerClassName.
+	manager := sourceCodeManagerClassName
+    ] ifFalse:[
+	manager := Smalltalk at: sourceCodeManagerClassName.
     ].
     manager isNil ifTrue:[
-        menu := Menu new.
-        menu addItem: 
-            (MenuItem 
-                label: (resources string: 'Unavailable - Configure SCM') 
-                value: [self openSettingsDialogAndSelectSourceCodeManagement])
-    ] ifFalse:[
-        menu := self class selectorMenuSCMCommon decodeAsLiteralArray.
+	menu := Menu new.
+	menu addItem:
+	    (MenuItem
+		label: (resources string: 'Unavailable - Configure SCM')
+		value: [self openSettingsDialogAndSelectSourceCodeManagement])
+    ] ifFalse:[
+	menu := self class selectorMenuSCMCommon decodeAsLiteralArray.
     ].
     self replaceSourceCodeManagerPlaceholderWith: manager in: menu.
 
@@ -46886,16 +47430,16 @@
 
     <resource: #programMenu>
 
-    ^self 
-        commonMenuSCMSliceNamed: #selectorMenuSCMSlice
-        computeManagerWith:
-            [:managers|
-            self selectedMethodsDo:[:mthd|
-                | mgr |
-    
-                mgr := AbstractSourceCodeManager managerForPackage:mthd package.
-                mgr isNil ifFalse:[managers add: mgr].
-            ]].
+    ^self
+	commonMenuSCMSliceNamed: #selectorMenuSCMSlice
+	computeManagerWith:
+	    [:managers|
+	    self selectedMethodsDo:[:mthd|
+		| mgr |
+
+		mgr := AbstractSourceCodeManager managerForPackage:mthd package.
+		mgr isNil ifFalse:[managers add: mgr].
+	    ]].
 
     "Created: / 19-04-2011 / 14:29:47 / cg"
     "Created: / 12-10-2011 / 20:54:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -46956,21 +47500,21 @@
     | menu repository wc branchAspect|
 
     menu := Menu new.
-    repository := self selectedProjectSubversionRepository. 
+    repository := self selectedProjectSubversionRepository.
     repository ifNil:[^nil].
     wc := repository workingCopy.
     branchAspect := (AspectAdaptor accessWith: #branchOrNil assignWith: #branch:)
-                        subject: wc.
+			subject: wc.
     repository branches do:
-        [:branch|
-        menu addItem:
-            (MenuItem new
-                label: branch displayString ;"/icon: branch icon;
-                choiceValue: branch;
-                choice: branchAspect;
-                enabled:(wc hasBranch not or: [(repository workingCopy branch) = branch]);
-                yourself)
-        ].
+	[:branch|
+	menu addItem:
+	    (MenuItem new
+		label: branch displayString ;"/icon: branch icon;
+		choiceValue: branch;
+		choice: branchAspect;
+		enabled:(wc hasBranch not or: [(repository workingCopy branch) = branch]);
+		yourself)
+	].
 
     ^menu
 
@@ -46985,9 +47529,9 @@
     "open a dialog to ask for a class name"
 
     ^ self class
-        askForClassNameMatching:matchStringArg 
-        inEnvironment:self navigationState environment
-        for:self
+	askForClassNameMatching:matchStringArg
+	inEnvironment:self navigationState environment
+	for:self
 !
 
 delayedSwitchToCategory:aCategory
@@ -47016,7 +47560,7 @@
     |canvasType|
 
     (canvasType := browserCanvasType) isNil ifTrue:[
-        canvasType := navigationState canvasType.
+	canvasType := navigationState canvasType.
     ].
 
     canvasType == #singleNameSpaceFullBrowserSpec ifTrue:[^ OrganizerCanvas organizerModeNamespace ].
@@ -47114,7 +47658,7 @@
 
     allProtocols := Set new.
     self selectedClassesDo:[:eachClass |
-        allProtocols addAll:(eachClass categories).
+	allProtocols addAll:(eachClass categories).
     ].
     allProtocols := allProtocols select:[:each | aMatchPattern match:each].
     self selectProtocols:allProtocols asOrderedCollection.
@@ -47132,116 +47676,116 @@
 
     canvasType := navigationState canvasType ? #fullBrowserSpec.
     canvasType == #fullBrowserSpec ifTrue:[
-        isMethodBrowser := anotherNavigationState isMethodListBrowser or:[anotherNavigationState isSingleMethodBrowser].
-        (isMethodBrowser
-        or:[otherOrganizerMode == OrganizerCanvas organizerModeCategory]) ifTrue:[
-            selectedMethods := anotherNavigationState selectedMethods value ? #().
-            isMethodBrowser ifTrue:[
-                selectedClasses := (selectedMethods collect:[:each | each mclass]) asIdentitySet.
-                protocols := (selectedMethods collect:[:each | each category]) asSet.
-                meta := (selectedClasses size == 1) and:[ selectedClasses anElement isMeta ].
-            ] ifFalse:[
-                protocols := anotherNavigationState selectedProtocols value ? #().
-                meta := anotherNavigationState meta value.
-                categories := anotherNavigationState selectedCategories value ? #().
-            ].
-        ] ifFalse:[
-            protocols := anotherNavigationState selectedProtocols value copy.
-            meta := anotherNavigationState meta value.
-
-            navigationState selectedNamespaces value:(anotherNavigationState selectedNamespaces value).
-            navigationState nameSpaceFilter value:(anotherNavigationState selectedNamespaces value).
-        ].
-        categories size == 0 ifTrue:[
-            "/ collect categories from selected classes.
-            categories :=  ((selectedClasses ? #()) collect:[:eachClass | eachClass theNonMetaclass category]) asSet
-        ].
-
-        navigationState selectedCategories value:categories.
-
-        otherOrganizerMode == OrganizerCanvas organizerModeProject ifTrue:[
-            navigationState organizerMode value:otherOrganizerMode.
-            projects := anotherNavigationState selectedProjects value copy.
-            navigationState selectedProjects value:projects.
-        ].
-
-        navigationState meta value:meta.
-
-        "/ self immediateUpdate value:true.
-        "/ selectedClasses := selectedClasses collect:[:each | each theNonMetaclass].
-        navigationState selectedClasses value:selectedClasses.
-        navigationState selectedProtocols value:protocols.
-        "/ self immediateUpdate value:false.
-        navigationState selectedMethods value:(anotherNavigationState selectedMethods value copy).
-
-        ^ self
+	isMethodBrowser := anotherNavigationState isMethodListBrowser or:[anotherNavigationState isSingleMethodBrowser].
+	(isMethodBrowser
+	or:[otherOrganizerMode == OrganizerCanvas organizerModeCategory]) ifTrue:[
+	    selectedMethods := anotherNavigationState selectedMethods value ? #().
+	    isMethodBrowser ifTrue:[
+		selectedClasses := (selectedMethods collect:[:each | each mclass]) asIdentitySet.
+		protocols := (selectedMethods collect:[:each | each category]) asSet.
+		meta := (selectedClasses size == 1) and:[ selectedClasses anElement isMeta ].
+	    ] ifFalse:[
+		protocols := anotherNavigationState selectedProtocols value ? #().
+		meta := anotherNavigationState meta value.
+		categories := anotherNavigationState selectedCategories value ? #().
+	    ].
+	] ifFalse:[
+	    protocols := anotherNavigationState selectedProtocols value copy.
+	    meta := anotherNavigationState meta value.
+
+	    navigationState selectedNamespaces value:(anotherNavigationState selectedNamespaces value).
+	    navigationState nameSpaceFilter value:(anotherNavigationState selectedNamespaces value).
+	].
+	categories size == 0 ifTrue:[
+	    "/ collect categories from selected classes.
+	    categories :=  ((selectedClasses ? #()) collect:[:eachClass | eachClass theNonMetaclass category]) asSet
+	].
+
+	navigationState selectedCategories value:categories.
+
+	otherOrganizerMode == OrganizerCanvas organizerModeProject ifTrue:[
+	    navigationState organizerMode value:otherOrganizerMode.
+	    projects := anotherNavigationState selectedProjects value copy.
+	    navigationState selectedProjects value:projects.
+	].
+
+	navigationState meta value:meta.
+
+	"/ self immediateUpdate value:true.
+	"/ selectedClasses := selectedClasses collect:[:each | each theNonMetaclass].
+	navigationState selectedClasses value:selectedClasses.
+	navigationState selectedProtocols value:protocols.
+	"/ self immediateUpdate value:false.
+	navigationState selectedMethods value:(anotherNavigationState selectedMethods value copy).
+
+	^ self
     ].
 
     navigationState isFullClassSourceBrowser ifTrue:[
-        otherOrganizerMode == OrganizerCanvas organizerModeCategory ifTrue:[
-            categories := anotherNavigationState selectedCategories value copy.
-        ] ifFalse:[
-            "/ collect categories from selected classes.
-            categories :=  ((selectedClasses ? #())
-                           collect:[:eachClass | eachClass category]) asSet
-        ].
-        navigationState selectedCategories value:categories.
-        selectedClasses size > 0 ifTrue:[
-            navigationState selectedClasses value:(selectedClasses collect:[:each | each theNonMetaclass]).
-        ].
-        self enqueueDelayedUpdateCode.
-        ^ self
+	otherOrganizerMode == OrganizerCanvas organizerModeCategory ifTrue:[
+	    categories := anotherNavigationState selectedCategories value copy.
+	] ifFalse:[
+	    "/ collect categories from selected classes.
+	    categories :=  ((selectedClasses ? #())
+			   collect:[:eachClass | eachClass category]) asSet
+	].
+	navigationState selectedCategories value:categories.
+	selectedClasses size > 0 ifTrue:[
+	    navigationState selectedClasses value:(selectedClasses collect:[:each | each theNonMetaclass]).
+	].
+	self enqueueDelayedUpdateCode.
+	^ self
     ].
 
     navigationState isFullClassSourceBrowser ifTrue:[
-        otherOrganizerMode == OrganizerCanvas organizerModeCategory ifTrue:[
-            categories := anotherNavigationState selectedCategories value copy.
-        ] ifFalse:[
-            "/ collect categories from selected classes.
-            categories :=  ((selectedClasses ? #())
-                           collect:[:eachClass | eachClass category]) asSet
-        ].
-        navigationState selectedCategories value:categories.
-        selectedClasses size > 0 ifTrue:[
-            navigationState selectedClasses value:(selectedClasses collect:[:each | each theNonMetaclass]).
-        ].
-        self enqueueDelayedUpdateCode.
-        ^ self
+	otherOrganizerMode == OrganizerCanvas organizerModeCategory ifTrue:[
+	    categories := anotherNavigationState selectedCategories value copy.
+	] ifFalse:[
+	    "/ collect categories from selected classes.
+	    categories :=  ((selectedClasses ? #())
+			   collect:[:eachClass | eachClass category]) asSet
+	].
+	navigationState selectedCategories value:categories.
+	selectedClasses size > 0 ifTrue:[
+	    navigationState selectedClasses value:(selectedClasses collect:[:each | each theNonMetaclass]).
+	].
+	self enqueueDelayedUpdateCode.
+	^ self
     ].
 
     navigationState isNameSpaceBrowser ifTrue:[
-        otherOrganizerMode == OrganizerCanvas organizerModeNamespace ifTrue:[
-            namespaces := anotherNavigationState selectedNamespaces value copy.
-        ] ifFalse:[
-            "/ collect namespaces from selected classes.
-            namespaces :=  ((selectedClasses ? #())
-                           collect:[:eachClass | eachClass nameSpace name]) asSet
-        ].
-        navigationState selectedNamespaces value:namespaces.
-        selectedClasses size > 0 ifTrue:[
-            navigationState selectedClasses value:selectedClasses.
-        ].
-        self enqueueDelayedUpdateCode.
-        ^ self
+	otherOrganizerMode == OrganizerCanvas organizerModeNamespace ifTrue:[
+	    namespaces := anotherNavigationState selectedNamespaces value copy.
+	] ifFalse:[
+	    "/ collect namespaces from selected classes.
+	    namespaces :=  ((selectedClasses ? #())
+			   collect:[:eachClass | eachClass nameSpace name]) asSet
+	].
+	navigationState selectedNamespaces value:namespaces.
+	selectedClasses size > 0 ifTrue:[
+	    navigationState selectedClasses value:selectedClasses.
+	].
+	self enqueueDelayedUpdateCode.
+	^ self
     ].
 
     (navigationState isCategoryBrowser
     or:[navigationState isNameSpaceFullBrowser
     or:[navigationState isProjectFullBrowser]]) ifTrue:[
-        otherOrganizerMode == OrganizerCanvas organizerModeCategory ifTrue:[
-            categories := anotherNavigationState selectedCategories value copy.
-        ] ifFalse:[
-            "/ collect categories from selected classes.
-            categories :=  ((selectedClasses ? #())
-                           collect:[:eachClass | eachClass category]) asSet
-        ].
-        navigationState selectedCategories value:categories.
-        selectedClasses size > 0 ifTrue:[
-            navigationState selectedClasses value:selectedClasses.
-        ].
-
-        self enqueueDelayedUpdateCode.
-        ^ self
+	otherOrganizerMode == OrganizerCanvas organizerModeCategory ifTrue:[
+	    categories := anotherNavigationState selectedCategories value copy.
+	] ifFalse:[
+	    "/ collect categories from selected classes.
+	    categories :=  ((selectedClasses ? #())
+			   collect:[:eachClass | eachClass category]) asSet
+	].
+	navigationState selectedCategories value:categories.
+	selectedClasses size > 0 ifTrue:[
+	    navigationState selectedClasses value:selectedClasses.
+	].
+
+	self enqueueDelayedUpdateCode.
+	^ self
     ].
 
     "Modified: / 29-09-2006 / 22:35:33 / cg"
@@ -47264,56 +47808,56 @@
 
     classes := OrderedCollection new.
     (sel := aSelectorString asSymbolIfInterned) notNil ifTrue:[
-        Smalltalk allClassesDo:[:aClass |
-            (aClass includesSelector:sel) ifTrue:[
-                classes add:aClass.
-            ].
-            (aClass class includesSelector:sel) ifTrue:[
-                classes add:aClass class.
-            ].
-        ]
+	Smalltalk allClassesDo:[:aClass |
+	    (aClass includesSelector:sel) ifTrue:[
+		classes add:aClass.
+	    ].
+	    (aClass class includesSelector:sel) ifTrue:[
+		classes add:aClass class.
+	    ].
+	]
     ].
     classes size == 0 ifTrue:[
-        self class showNoneFound.
-        ^ self
+	self class showNoneFound.
+	^ self
     ].
 
     classes size > 1 ifTrue:[
-        box := ListSelectionBox
-                    title:(resources stringWithCRs:'searching for #%1 method.\\in which class ?\\(Tab for completion or select)' with:aSelectorString).
-        box label:'find method'.
-        box okText:(resources string:'show').
-        box list:(classes collect:[:aClass | aClass name]) asSortedCollection.
-        box action:[:aString | theClassName := aString].
-        box entryCompletionBlock:[:contents |
-            |s l names|
-
-            s := contents withoutSpaces.
-            s size == 0 ifTrue:[
-                l := classes
-            ] ifFalse:[
-                l := classes select:[:cls | cls name startsWith:s].
-            ].
-            l size == 0 ifTrue:[
-                l := classes select:[:cls | cls name asLowercase startsWith:s asLowercase].
-            ].
-            l size > 0 ifTrue:[
-                box list:(names := l collect:[:aClass | aClass name]) asSortedCollection.
-                box contents:(names longestCommonPrefix). "/ l first name.
-                l size ~~ 1 ifTrue:[
-                    self window beep
-                ]
-            ]
-        ].
-        box showAtPointer.
-    ] ifFalse:[
-        theClassName := classes first name
+	box := ListSelectionBox
+		    title:(resources stringWithCRs:'searching for #%1 method.\\in which class ?\\(Tab for completion or select)' with:aSelectorString).
+	box label:'find method'.
+	box okText:(resources string:'show').
+	box list:(classes collect:[:aClass | aClass name]) asSortedCollection.
+	box action:[:aString | theClassName := aString].
+	box entryCompletionBlock:[:contents |
+	    |s l names|
+
+	    s := contents withoutSpaces.
+	    s size == 0 ifTrue:[
+		l := classes
+	    ] ifFalse:[
+		l := classes select:[:cls | cls name startsWith:s].
+	    ].
+	    l size == 0 ifTrue:[
+		l := classes select:[:cls | cls name asLowercase startsWith:s asLowercase].
+	    ].
+	    l size > 0 ifTrue:[
+		box list:(names := l collect:[:aClass | aClass name]) asSortedCollection.
+		box contents:(names longestCommonPrefix). "/ l first name.
+		l size ~~ 1 ifTrue:[
+		    self window beep
+		]
+	    ]
+	].
+	box showAtPointer.
+    ] ifFalse:[
+	theClassName := classes first name
     ].
 
     theClassName notNil ifTrue:[
-        self rememberLocationInHistory.
-        self switchToClassNamed:theClassName.
-        self switchToSelector:aSelectorString.
+	self rememberLocationInHistory.
+	self switchToClassNamed:theClassName.
+	self switchToSelector:aSelectorString.
     ].
 
     "Modified: / 1.9.1995 / 01:39:58 / claus"
@@ -47323,12 +47867,12 @@
 switchToBookmarkEntry:entry
     "invoked when switching to a method from the bookmark history"
 
-    (entry isKindOf: Bookmark) 
-        ifTrue:
-            [entry switchToBookmarkIn: self]
-        ifFalse:
-            [self breakPoint: #jv info:'BrowserHistoryEntries should no longet be used'.
-            self switchToHistoryEntry: entry].
+    (entry isKindOf: Bookmark)
+	ifTrue:
+	    [entry switchToBookmarkIn: self]
+	ifFalse:
+	    [self breakPoint: #jv info:'BrowserHistoryEntries should no longet be used'.
+	    self switchToHistoryEntry: entry].
 
     "Modified: / 05-05-2011 / 23:51:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -47351,67 +47895,67 @@
      ns classes|
 
     aClass isNil ifTrue:[
-        ^ self
+	^ self
     ].
     aSelector notNil ifTrue:[
-        mthd := aClass compiledMethodAt:aSelector.
-    ].
-
-    (navigationState isMethodListBrowser 
+	mthd := aClass compiledMethodAt:aSelector.
+    ].
+
+    (navigationState isMethodListBrowser
     or:[navigationState isMethodBrowser]) ifTrue:[
-        "/ must check if that method is in the list ...
-
-        mthd isNil ifTrue:[
+	"/ must check if that method is in the list ...
+
+	mthd isNil ifTrue:[
 "/            (self confirm:'Add a buffer for the class ?' withCRs) ifFalse:[
 "/                ^ self
 "/            ].
-            self spawnFullBrowserInClass:aClass selector:nil in:#newBuffer.
-            ^ self
-        ].
-
-        navigationState methodListApplication isNil ifTrue:[
-            self spawnFullBrowserInClass:aClass selector:aSelector in:#newBuffer.
-            ^ self
-        ].
-
-        (navigationState methodList includesIdentical:mthd) ifFalse:[
-            answer := OptionBox request:'Method not in list.\\Add a buffer for it ?' withCRs
-                        label:'New Browser ?'
-                        image:(WarningBox iconBitmap)
-                        buttonLabels:(resources array:#('New Browser' 'Add Buffer' 'Cancel'))
-                        values:#(#newBrowser #newBuffer nil)
-                        default:#newBuffer
-                        onCancel:nil.
-            answer notNil ifTrue:[
-                self spawnFullBrowserInClass:aClass selector:aSelector in:answer.
-            ].
-            ^ self
-        ].
-        self selectedMethods value:(OrderedCollection with:mthd).
-        ^ self
+	    self spawnFullBrowserInClass:aClass selector:nil in:#newBuffer.
+	    ^ self
+	].
+
+	navigationState methodListApplication isNil ifTrue:[
+	    self spawnFullBrowserInClass:aClass selector:aSelector in:#newBuffer.
+	    ^ self
+	].
+
+	(navigationState methodList includesIdentical:mthd) ifFalse:[
+	    answer := OptionBox request:'Method not in list.\\Add a buffer for it ?' withCRs
+			label:'New Browser ?'
+			image:(WarningBox iconBitmap)
+			buttonLabels:(resources array:#('New Browser' 'Add Buffer' 'Cancel'))
+			values:#(#newBrowser #newBuffer nil)
+			default:#newBuffer
+			onCancel:nil.
+	    answer notNil ifTrue:[
+		self spawnFullBrowserInClass:aClass selector:aSelector in:answer.
+	    ].
+	    ^ self
+	].
+	self selectedMethods value:(OrderedCollection with:mthd).
+	^ self
     ].
 
     (navigationState isClassBrowser) ifTrue:[
-        "/ must check if that class is in the list ...
-        ((navigationState classList value ? #()) includesIdentical:aClass) ifFalse:[
-            navigationState isSingleClassBrowser ifTrue:[
-                navigationState classList value:(Array with:aClass).
-            ] ifFalse:[
-                (self confirm:'Class not in list.\\Add a buffer for it ?' withCRs) ifTrue:[
-                    self spawnFullBrowserInClass:aClass selector:aSelector in:#newBuffer.
-                ].
-                ^ self
-            ].
-        ].
-        self selectedClasses value:(OrderedCollection with:aClass).
-        ^ self
+	"/ must check if that class is in the list ...
+	((navigationState classList value ? #()) includesIdentical:aClass) ifFalse:[
+	    navigationState isSingleClassBrowser ifTrue:[
+		navigationState classList value:(Array with:aClass).
+	    ] ifFalse:[
+		(self confirm:'Class not in list.\\Add a buffer for it ?' withCRs) ifTrue:[
+		    self spawnFullBrowserInClass:aClass selector:aSelector in:#newBuffer.
+		].
+		^ self
+	    ].
+	].
+	self selectedClasses value:(OrderedCollection with:aClass).
+	^ self
     ].
 
     (navigationState isProtocolBrowser) ifTrue:[
-        (self confirm:'Add a buffer for it ?' withCRs) ifTrue:[
-            self spawnFullBrowserInClass:aClass selector:aSelector in:#newBuffer.
-        ].
-        ^ self
+	(self confirm:'Add a buffer for it ?' withCRs) ifTrue:[
+	    self spawnFullBrowserInClass:aClass selector:aSelector in:#newBuffer.
+	].
+	^ self
     ].
 
     orgMode := self organizerMode value.
@@ -47419,34 +47963,34 @@
     "/ if the class is a namespace, ask if mode should be changed
 
     (aClass isNameSpace and:[aClass ~~ Smalltalk]) ifTrue:[
-        orgMode ~~ OrganizerCanvas organizerModeNamespace ifTrue:[      
-            answer := self 
-                        confirmWithCancel:(resources string:'Browser: %1 is a namespace - switch organizers display mode ?' with:aClass name)
-                        defaultAnswer:false.
-            answer isNil ifTrue:[
-                AbortOperationRequest raise.
-                ^ self
-            ].
-            answer ifTrue:[
-                self organizerMode value:(OrganizerCanvas organizerModeNamespace).
-                orgMode := self organizerMode value.
-            ] ifFalse:[
-                ((self selectedClassesValue) contains:[:cls | cls nameSpace == aClass]) ifTrue:[^ self ].
-
-                "/ select the first class of that namespace
-                classes := aClass allClasses.
-                classes notEmpty ifTrue:[
-                    self switchToClass:(classes first) selector:nil.
-                    ^ self.
-                ]
-            ]
-        ].
+	orgMode ~~ OrganizerCanvas organizerModeNamespace ifTrue:[
+	    answer := self
+			confirmWithCancel:(resources string:'Browser: %1 is a namespace - switch organizers display mode ?' with:aClass name)
+			defaultAnswer:false.
+	    answer isNil ifTrue:[
+		AbortOperationRequest raise.
+		^ self
+	    ].
+	    answer ifTrue:[
+		self organizerMode value:(OrganizerCanvas organizerModeNamespace).
+		orgMode := self organizerMode value.
+	    ] ifFalse:[
+		((self selectedClassesValue) contains:[:cls | cls nameSpace == aClass]) ifTrue:[^ self ].
+
+		"/ select the first class of that namespace
+		classes := aClass allClasses.
+		classes notEmpty ifTrue:[
+		    self switchToClass:(classes first) selector:nil.
+		    ^ self.
+		]
+	    ]
+	].
     ].
 
     "/ if the class is unloaded, turn hideUnloaded off
     (aClass isLoaded not
     and:[self hideUnloadedClasses value == true]) ifTrue:[
-        self hideUnloadedClasses value:false
+	self hideUnloadedClasses value:false
     ].
 
     doSwitchMeta := true.
@@ -47457,9 +48001,9 @@
     ns := aClass topNameSpace.
     ns notNil ifTrue:[nsName := ns name].
     (namespaces includes:nsName) ifFalse:[
-        (namespaces includes:(NavigatorModel nameListEntryForALL)) ifFalse:[
-            self selectedNamespaces value:(OrderedCollection with: NavigatorModel nameListEntryForALL)
-        ]
+	(namespaces includes:(NavigatorModel nameListEntryForALL)) ifFalse:[
+	    self selectedNamespaces value:(OrderedCollection with: NavigatorModel nameListEntryForALL)
+	]
     ].
 "/    namespaces := self nameSpaceFilter value ? #().
 "/    (namespaces includes:aClass nameSpace name) ifFalse:[
@@ -47468,72 +48012,72 @@
 "/        ]
 "/    ].
     orgMode == OrganizerCanvas organizerModeCategory ifTrue:[
-        cat := aClass category ? '* no category *'.
-        (self selectedCategoriesValue includes:cat) ifFalse:[
-            self selectedCategories value:(OrderedCollection with:cat).
-        ]
+	cat := aClass category ? '* no category *'.
+	(self selectedCategoriesValue includes:cat) ifFalse:[
+	    self selectedCategories value:(OrderedCollection with:cat).
+	]
     ] ifFalse:[ orgMode == OrganizerCanvas organizerModeNamespace ifTrue:[
-        aClass isNameSpace ifTrue:[
-            nsName := aClass name.
-        ] ifFalse:[
-            nsName := aClass nameSpace name.
-        ].
-        (self selectedNamespacesValue includes:nsName) ifFalse:[
-            self selectedNamespaces value:(OrderedCollection with:nsName).
-        ]
+	aClass isNameSpace ifTrue:[
+	    nsName := aClass name.
+	] ifFalse:[
+	    nsName := aClass nameSpace name.
+	].
+	(self selectedNamespacesValue includes:nsName) ifFalse:[
+	    self selectedNamespaces value:(OrderedCollection with:nsName).
+	]
     ] ifFalse:[ orgMode == OrganizerCanvas organizerModeProject ifTrue:[
-        pkg := aClass package.
-        holder := self selectedProjects.
-        newValue := holder value ? #().
-        (newValue includes:pkg) ifFalse:[
-            newValue := OrderedCollection with:pkg.
-        ].
-        mthd notNil ifTrue:[
-            "/ careful - the method could be in an extension ...
-            mthd package ~= pkg ifTrue:[
-                (newValue includes:mthd package) ifFalse:[
-                    newValue := newValue asOrderedCollection.
-                    newValue add:mthd package.
-                ].
-            ].
-        ].
-        newValue ~= holder value ifTrue:[
-            holder value:newValue.
-        ].
+	pkg := aClass package.
+	holder := self selectedProjects.
+	newValue := holder value ? #().
+	(newValue includes:pkg) ifFalse:[
+	    newValue := OrderedCollection with:pkg.
+	].
+	mthd notNil ifTrue:[
+	    "/ careful - the method could be in an extension ...
+	    mthd package ~= pkg ifTrue:[
+		(newValue includes:mthd package) ifFalse:[
+		    newValue := newValue asOrderedCollection.
+		    newValue add:mthd package.
+		].
+	    ].
+	].
+	newValue ~= holder value ifTrue:[
+	    holder value:newValue.
+	].
     ] ifFalse:[ (orgMode == OrganizerCanvas organizerModeClassHierarchy
-                 or:[orgMode == OrganizerCanvas organizerModeClassInheritance]) ifTrue:[
-        "/ make sure, that the class is in the hierarchy;
-        "/ if required, update the hierarchy.
-
-        holder := self classHierarchyTopClass.
-        cls := holder value.
-        (cls isNil or:[(cls withAllSuperclasses includesIdentical:aClass) not]) ifTrue:[
-            holder value:aClass.
-        ].
-        doSwitchMeta := false.
+		 or:[orgMode == OrganizerCanvas organizerModeClassInheritance]) ifTrue:[
+	"/ make sure, that the class is in the hierarchy;
+	"/ if required, update the hierarchy.
+
+	holder := self classHierarchyTopClass.
+	cls := holder value.
+	(cls isNil or:[(cls withAllSuperclasses includesIdentical:aClass) not]) ifTrue:[
+	    holder value:aClass.
+	].
+	doSwitchMeta := false.
     ]]]].
 
     doSwitchMeta ifTrue:[
-        self meta value:(aClass isMeta).
+	self meta value:(aClass isMeta).
     ].
 
     (self selectedClassesValue includesIdentical:aClass) ifFalse:[
-        self selectedClasses value:(OrderedCollection with:aClass).
+	self selectedClasses value:(OrderedCollection with:aClass).
     ].
 
     mthd notNil ifTrue:[
-        (self selectedProtocolsValue contains:[:cat | cat string = mthd category]) ifFalse:[
-            self selectProtocols:(OrderedCollection with:mthd category).
-        ].
-        self switchToMethod:mthd.
-    ] ifFalse:[
-        self switchToSelector:aSelector.
+	(self selectedProtocolsValue contains:[:cat | cat string = mthd category]) ifFalse:[
+	    self selectProtocols:(OrderedCollection with:mthd category).
+	].
+	self switchToMethod:mthd.
+    ] ifFalse:[
+	self switchToSelector:aSelector.
     ].
 
     self immediateUpdate value:false.
 
     updateHistory ifTrue:[
-        self addToHistory:aClass selector:aSelector
+	self addToHistory:aClass selector:aSelector
     ].
 
     self normalLabel.
@@ -47550,12 +48094,12 @@
     class := Smalltalk classNamed:aMatchString.
 
     class notNil ifTrue:[
-        self switchToClass:class
-    ] ifFalse:[
-        className := self askForClassNameMatching:aMatchString.
-        className notNil ifTrue:[
-            self switchToClassNamed:className.
-        ]
+	self switchToClass:class
+    ] ifFalse:[
+	className := self askForClassNameMatching:aMatchString.
+	className notNil ifTrue:[
+	    self switchToClassNamed:className.
+	]
     ]
 
     "Modified: / 13.2.2000 / 20:57:42 / cg"
@@ -47565,108 +48109,108 @@
     |className class implementors answer classesMatchingCaseless|
 
     aMatchString isEmptyOrNil ifTrue:[
-        ^ self.
+	^ self.
     ].
 
     aMatchString knownAsSymbol ifTrue:[
-        class := Smalltalk classNamed:aMatchString.
-        class notNil ifTrue:[
-            self switchToClass:class.
-            ^ self.
-        ].
-        classesMatchingCaseless := Smalltalk keys select:[:nm | nm sameAs:aMatchString].
+	class := Smalltalk classNamed:aMatchString.
+	class notNil ifTrue:[
+	    self switchToClass:class.
+	    ^ self.
+	].
+	classesMatchingCaseless := Smalltalk keys select:[:nm | nm sameAs:aMatchString].
 "/        matchStringLowercase := aMatchString asLowercase.
 "/        classesWithPrefixCaseless := Smalltalk keys select:[:nm | nm asLowercase startsWith:aMatchString].
 
 "/        impl := Smalltalk allImplementorsOf:aMatchString asSymbol.
 "/        impl notEmptyOrNil ifTrue:[
 "/        ].
-        (aMatchString first isLetter not
-         or:[ aMatchString first isLowercase]) ifTrue:[
-            implementors := SystemBrowser findImplementorsMatching:aMatchString in:(Smalltalk allClasses) ignoreCase:true.
-            implementors size > 0 ifTrue:[
-                (classesMatchingCaseless isEmpty and:[implementors size == 1]) ifTrue:[
-                    answer := Dialog 
-                        confirm:(resources 
-                                        stringWithCRs:'No class named "%1".\But "%2" implements it. Go there ?' 
-                                        with:aMatchString allBold
-                                        with:implementors first mclass name).
-                    answer ifTrue:[
-                        self switchToClass:implementors first mclass selector:implementors first selector.
-                    ].
-                    ^ self.
-                ].
-                implementors := implementors asOrderedCollection sort:[:a :b | a mclass name < b mclass name].
-                classesMatchingCaseless isEmpty ifTrue:[
-                    answer := Dialog 
-                        choose:(resources 
-                                        stringWithCRs:'No class named "%1.\But there are %2 implementors of it.\\Goto one of them ?' 
-                                        with:aMatchString allBold
-                                        with:implementors size)
-                        fromList:(implementors collect:[:m | m mclass name])
-                        values:implementors 
-                        buttons:#('No, Search for a Class' 'Show all Implementors') values:#(searchClass browseAllImplementors) 
-                        lines:10 cancel:nil
-                        postBuildBlock:[:box | box minExtent:300@250].
-                ] ifFalse:[
-                    answer := Dialog 
-                        choose:(resources 
-                                        stringWithCRs:'No class named "%1".\But there are %2 implementors of it and %3 '
-                                                      , (classesMatchingCaseless size == 1 ifTrue:['class'] ifFalse:['classes'])
-                                                      ,' with a similar name.\\Goto one of them ?' 
-                                        with:aMatchString allBold
-                                        with:implementors size
-                                        with:classesMatchingCaseless size)
-                        fromList:({'Implementors:' colorizeAllWith:Color grey}
-                                  ,(implementors collect:[:m | m mclass name])
-                                  ,{'Classes:' colorizeAllWith:Color grey}
-                                  ,classesMatchingCaseless)
-                        values:(#(nil),implementors,#(nil),classesMatchingCaseless) 
-                        buttons:#('No, Search for a Class' 'Show all Implementors') values:#(searchClass browseAllImplementors) 
-                        lines:10 cancel:nil
-                        postBuildBlock:[:box | box minExtent:300@250].
-                ].
-
-                answer isNil ifTrue:[^ self].
-                answer == #browseAllImplementors ifTrue:[
-                    self
-                        spawnMethodBrowserForSearch:[
-                                SystemBrowser 
-                                    findImplementorsOf:aMatchString 
-                                    in:Smalltalk allClasses 
-                                    ignoreCase:false.
-                            ]
-                        sortBy:#class
-                        in:#newBuffer
-                        label:(resources string:'Implementors of %1' string with:aMatchString).
-                    ^ self                    
-                ].
-                answer ~~ #searchClass ifTrue:[
-                    answer isSymbol ifTrue:[
-                        self switchToClass:(Smalltalk classNamed:answer).
-                    ] ifFalse:[
-                        self switchToClass:(answer mclass) selector:(answer selector).
-                    ].
-                    ^ self.
-                ].
-            ].
-        ].
+	(aMatchString first isLetter not
+	 or:[ aMatchString first isLowercase]) ifTrue:[
+	    implementors := SystemBrowser findImplementorsMatching:aMatchString in:(Smalltalk allClasses) ignoreCase:true.
+	    implementors size > 0 ifTrue:[
+		(classesMatchingCaseless isEmpty and:[implementors size == 1]) ifTrue:[
+		    answer := Dialog
+			confirm:(resources
+					stringWithCRs:'No class named "%1".\But "%2" implements it. Go there ?'
+					with:aMatchString allBold
+					with:implementors first mclass name).
+		    answer ifTrue:[
+			self switchToClass:implementors first mclass selector:implementors first selector.
+		    ].
+		    ^ self.
+		].
+		implementors := implementors asOrderedCollection sort:[:a :b | a mclass name < b mclass name].
+		classesMatchingCaseless isEmpty ifTrue:[
+		    answer := Dialog
+			choose:(resources
+					stringWithCRs:'No class named "%1.\But there are %2 implementors of it.\\Goto one of them ?'
+					with:aMatchString allBold
+					with:implementors size)
+			fromList:(implementors collect:[:m | m mclass name])
+			values:implementors
+			buttons:#('No, Search for a Class' 'Show all Implementors') values:#(searchClass browseAllImplementors)
+			lines:10 cancel:nil
+			postBuildBlock:[:box | box minExtent:300@250].
+		] ifFalse:[
+		    answer := Dialog
+			choose:(resources
+					stringWithCRs:'No class named "%1".\But there are %2 implementors of it and %3 '
+						      , (classesMatchingCaseless size == 1 ifTrue:['class'] ifFalse:['classes'])
+						      ,' with a similar name.\\Goto one of them ?'
+					with:aMatchString allBold
+					with:implementors size
+					with:classesMatchingCaseless size)
+			fromList:({'Implementors:' colorizeAllWith:Color grey}
+				  ,(implementors collect:[:m | m mclass name])
+				  ,{'Classes:' colorizeAllWith:Color grey}
+				  ,classesMatchingCaseless)
+			values:(#(nil),implementors,#(nil),classesMatchingCaseless)
+			buttons:#('No, Search for a Class' 'Show all Implementors') values:#(searchClass browseAllImplementors)
+			lines:10 cancel:nil
+			postBuildBlock:[:box | box minExtent:300@250].
+		].
+
+		answer isNil ifTrue:[^ self].
+		answer == #browseAllImplementors ifTrue:[
+		    self
+			spawnMethodBrowserForSearch:[
+				SystemBrowser
+				    findImplementorsOf:aMatchString
+				    in:Smalltalk allClasses
+				    ignoreCase:false.
+			    ]
+			sortBy:#class
+			in:#newBuffer
+			label:(resources string:'Implementors of %1' string with:aMatchString).
+		    ^ self
+		].
+		answer ~~ #searchClass ifTrue:[
+		    answer isSymbol ifTrue:[
+			self switchToClass:(Smalltalk classNamed:answer).
+		    ] ifFalse:[
+			self switchToClass:(answer mclass) selector:(answer selector).
+		    ].
+		    ^ self.
+		].
+	    ].
+	].
     ].
 
     "Look for Java class..."
     (JAVA notNil and:[aMatchString includes: $.]) ifTrue:[
-        | javaClass |
-
-        javaClass := Java at: aMatchString.
-        javaClass notNil ifTrue:[ 
-            self switchToClass: javaClass.
-            ^self
-        ].
+	| javaClass |
+
+	javaClass := Java at: aMatchString.
+	javaClass notNil ifTrue:[
+	    self switchToClass: javaClass.
+	    ^self
+	].
     ].
 
     className := self askForClassNameMatching:aMatchString.
     className notNil ifTrue:[
-        self switchToClassNamed:className.
+	self switchToClassNamed:className.
     ]
 
     "Modified: / 04-07-2006 / 18:48:25 / fm"
@@ -47679,7 +48223,7 @@
 
     str := aString.
     (aString endsWith:' class') ifTrue:[
-        str := aString copyWithoutLast:6.
+	str := aString copyWithoutLast:6.
     ].
 
     theClass := self findClassNamed:str.
@@ -47688,9 +48232,9 @@
     "/ if currently in meta-mode,
     "/ switch to the metaClass
     self meta value ifTrue:[
-        theClass := theClass theMetaclass
-    ] ifFalse:[
-        theClass := theClass theNonMetaclass
+	theClass := theClass theMetaclass
+    ] ifFalse:[
+	theClass := theClass theNonMetaclass
     ].
     self switchToClass:theClass.
 
@@ -47714,11 +48258,11 @@
 
     cls := Smalltalk at:entry className.
     cls isNil ifTrue:[
-        self warn:'Oops - class is gone'.
-        ^ self
+	self warn:'Oops - class is gone'.
+	^ self
     ].
     entry meta ifTrue:[
-        cls := cls theMetaclass
+	cls := cls theMetaclass
     ].
     self switchToClass:cls selector:entry selector updateHistory: false
 
@@ -47731,21 +48275,21 @@
     "/ care for method being in another package
     orgMode := self organizerMode value.
     orgMode == OrganizerCanvas organizerModeProject ifTrue:[
-        pkg := aMethod package.
-        holder := self selectedProjects.
-        ((holder value ? #()) includes:pkg) ifFalse:[
-            holder value:(Array with:pkg).
-        ]
+	pkg := aMethod package.
+	holder := self selectedProjects.
+	((holder value ? #()) includes:pkg) ifFalse:[
+	    holder value:(Array with:pkg).
+	]
     ].
 
     category := aMethod category.
     (self selectedProtocolsValue contains:[:p | p notNil and:[p string = category]]) ifFalse:[
-        (self selectedProtocolsValue includes:BrowserList nameListEntryForALL) ifFalse:[
-            self selectProtocols:(Array with:category).
-        ]
+	(self selectedProtocolsValue includes:BrowserList nameListEntryForALL) ifFalse:[
+	    self selectProtocols:(Array with:category).
+	]
     ].
     self theSingleSelectedMethod ~~ aMethod ifTrue:[
-        self selectedMethods value:(Array with:aMethod).
+	self selectedMethods value:(Array with:aMethod).
     ]
 
     "Modified: / 30-08-2011 / 16:03:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -47761,30 +48305,30 @@
     |mthd cls orgMode pkg holder|
 
     aSelector notNil ifTrue:[
-        (cls := self theSingleSelectedClass) notNil ifTrue:[
-            mthd := cls compiledMethodAt:aSelector asSymbol.
-            mthd notNil ifTrue:[
-
-                "/ care for method being in another package
-                orgMode := self organizerMode value.
-                orgMode == OrganizerCanvas organizerModeProject ifTrue:[
-                    pkg := mthd package.
-                    holder := self selectedProjects.
-                    ((holder value ? #()) includes:pkg) ifFalse:[
-                        holder value:(Array with:pkg).
-                    ]
-                ].
-
-                (self selectedProtocolsValue contains:[:p | p string = mthd category]) ifFalse:[
-                    (self selectedProtocolsValue includes:BrowserList nameListEntryForALL) ifFalse:[
-                        self selectProtocols:(Array with:mthd category).
-                    ]
-                ].
-                self theSingleSelectedMethod ~~ mthd ifTrue:[
-                    self selectedMethods value:(Array with:mthd).
-                ]
-            ]
-        ]
+	(cls := self theSingleSelectedClass) notNil ifTrue:[
+	    mthd := cls compiledMethodAt:aSelector asSymbol.
+	    mthd notNil ifTrue:[
+
+		"/ care for method being in another package
+		orgMode := self organizerMode value.
+		orgMode == OrganizerCanvas organizerModeProject ifTrue:[
+		    pkg := mthd package.
+		    holder := self selectedProjects.
+		    ((holder value ? #()) includes:pkg) ifFalse:[
+			holder value:(Array with:pkg).
+		    ]
+		].
+
+		(self selectedProtocolsValue contains:[:p | p string = mthd category]) ifFalse:[
+		    (self selectedProtocolsValue includes:BrowserList nameListEntryForALL) ifFalse:[
+			self selectProtocols:(Array with:mthd category).
+		    ]
+		].
+		self theSingleSelectedMethod ~~ mthd ifTrue:[
+		    self selectedMethods value:(Array with:mthd).
+		]
+	    ]
+	]
     ].
 
     "Created: / 4.2.2000 / 23:20:34 / cg"
@@ -47801,7 +48345,7 @@
     "/ the buffer before that one
     prevBuffer := nr - 1.
     prevBuffer == 0 ifTrue:[
-        prevBuffer := nr.
+	prevBuffer := nr.
     ].
 
     bufferUsageOrder removeIdentical:state.
@@ -47822,13 +48366,13 @@
 
     "/ oops
     newIndex > buffers size ifTrue:[
-        selectedBuffer value:buffers size.
+	selectedBuffer value:buffers size.
     ].
 
     buffers size == 1 ifTrue:[
-        selectedBuffer value:nil.
-        buffers := bufferUsageOrder := nil.
-        bufferNameList removeAll.
+	selectedBuffer value:nil.
+	buffers := bufferUsageOrder := nil.
+	bufferNameList removeAll.
     ]
 
     "Modified: / 01-03-2007 / 17:17:11 / cg"
@@ -47842,7 +48386,7 @@
 
 anySpecialEditorModified
     self showSpecialResourceEditors value ifTrue:[
-        ^ navigationState anySpecialEditorModified
+	^ navigationState anySpecialEditorModified
     ].
     ^ false.
 !
@@ -47890,7 +48434,7 @@
 !
 
 canFileOutSIF
-    ^ SmalltalkInterchangeFileManager notNil    
+    ^ SmalltalkInterchangeFileManager notNil
     and:[ self hasOnlySmalltalkClassesSelected ]
 !
 
@@ -47907,7 +48451,7 @@
     "can make public, if selected and any selected class is private"
 
     self selectedClassesDo:[:cls |
-        cls owningClass notNil ifTrue:[^ true].
+	cls owningClass notNil ifTrue:[^ true].
     ].
     ^ false
 
@@ -47947,7 +48491,7 @@
 
     (self theSingleSelectedClass isNil
     or:[ self theSingleSelectedClass programmingLanguage isSmalltalk ]) ifTrue:[
-        ^ SmalltalkCodeGeneratorTool canUseRefactoringSupport
+	^ SmalltalkCodeGeneratorTool canUseRefactoringSupport
     ].
     ^ false
 
@@ -47988,24 +48532,24 @@
     |searchAction codeView|
 
     codePattern notNil ifTrue:[
-        codeView := self codeView.
-
-        searchAction :=
-            [:direction :startLine :startCol :foundBlock :notFoundBlock|
-                self
-                    searchForCodePattern:codePattern direction:direction
-                    startLine:(codeView cursorLine ? startLine) startCol:(codeView cursorCol ? startCol)
-                    ifFound:[:charPos1 :charPos2 |
-                            codeView
-                                cursorToCharacterPosition:charPos1;
-                                selectFromCharacterPosition:charPos1 to:charPos2
-                        ]
-                    ifNotFound:notFoundBlock
-            ].
-
-        navigationState autoSearchAction:searchAction.
-        codeView clearSearchAction. "/ searchAction
-        codeView setSearchPattern:nil.
+	codeView := self codeView.
+
+	searchAction :=
+	    [:direction :startLine :startCol :foundBlock :notFoundBlock|
+		self
+		    searchForCodePattern:codePattern direction:direction
+		    startLine:(codeView cursorLine ? startLine) startCol:(codeView cursorCol ? startCol)
+		    ifFound:[:charPos1 :charPos2 |
+			    codeView
+				cursorToCharacterPosition:charPos1;
+				selectFromCharacterPosition:charPos1 to:charPos2
+			]
+		    ifNotFound:notFoundBlock
+	    ].
+
+	navigationState autoSearchAction:searchAction.
+	codeView clearSearchAction. "/ searchAction
+	codeView setSearchPattern:nil.
     ]
 
     "Modified: / 11-05-2010 / 14:13:34 / cg"
@@ -48022,7 +48566,7 @@
 autoSearchPattern:aString ignoreCase:doIgnoreCase
     navigationState autoSearchPattern:aString; autoSearchIgnoreCase:doIgnoreCase.
     aString notNil ifTrue:[
-        self codeView setSearchPattern:aString ignoreCase:doIgnoreCase.
+	self codeView setSearchPattern:aString ignoreCase:doIgnoreCase.
     ]
 !
 
@@ -48031,35 +48575,35 @@
 
     aSelectorOrCollectionOfSelectors notNil ifTrue:[
 
-        searchAction :=
-            [:direction :startLine :startCol :foundBlock :notFoundBlock|
-                |codeView|
-
-                codeView := self codeView.
-                self
-                    searchForSelector:aSelectorOrCollectionOfSelectors direction:direction
-                    startLine:(startLine ? codeView cursorLine) startCol:(startCol ? codeView cursorCol)
-                    ignoreCase:doIgnoreCase doMatch:doMatch
-                    ifFound:
-                        [:charPos1 :charPos2 |
-                            codeView
-                                cursorToCharacterPosition:charPos1;
-                                selectFromCharacterPosition:charPos1 to:charPos2
-                        ]
-                    ifNotFound:notFoundBlock
-            ].
-
-        navigationState autoSearchAction:searchAction.
-        self codeView clearSearchAction. "/ searchAction
-        self codeView setSearchPattern:nil.
-    ]
-!
-
-autoSearchVariable:aVariable 
+	searchAction :=
+	    [:direction :startLine :startCol :foundBlock :notFoundBlock|
+		|codeView|
+
+		codeView := self codeView.
+		self
+		    searchForSelector:aSelectorOrCollectionOfSelectors direction:direction
+		    startLine:(startLine ? codeView cursorLine) startCol:(startCol ? codeView cursorCol)
+		    ignoreCase:doIgnoreCase doMatch:doMatch
+		    ifFound:
+			[:charPos1 :charPos2 |
+			    codeView
+				cursorToCharacterPosition:charPos1;
+				selectFromCharacterPosition:charPos1 to:charPos2
+			]
+		    ifNotFound:notFoundBlock
+	    ].
+
+	navigationState autoSearchAction:searchAction.
+	self codeView clearSearchAction. "/ searchAction
+	self codeView setSearchPattern:nil.
+    ]
+!
+
+autoSearchVariable:aVariable
     self autoSearchVariables:(Array with:aVariable)
 !
 
-autoSearchVariables:aCollectionOfVariables 
+autoSearchVariables:aCollectionOfVariables
     self autoSearchVariables:aCollectionOfVariables readers:true writers:true
 !
 
@@ -48073,33 +48617,33 @@
     s := '' writeStream.
 
     (aClass isRealNameSpace) ifTrue:[
-        aClass fileOutDefinitionOn:s
-    ] ifFalse:[
-        aClass theNonMetaclass isJavaClass ifTrue:[
-            | src |
-            src := aClass theNonMetaclass source.
-            src notNil ifTrue:[ ^ src ].
-            s nextPutLine: '// *** WARNING ***'.
-            s nextPutLine: '// Following code has been decompiled from loaded class'.
-            s nextPutLine: '// *** WARNING ***'.
-            s cr.
-            aClass fileOutDefinitionOn:s
-        ] ifFalse:[
-            aClass isMeta ifTrue:[
-                aClass
-                    fileOutClassInstVarDefinitionOn:s
-                    withNameSpace:true.
-            ] ifFalse:[
-                "/
-                "/ here, show it with a nameSpace pragma
-                "/ and prefer short names.
-                "/
-                aClass
-                    basicFileOutDefinitionOn:s
-                    withNameSpace:true
-                    withPackage:false
-            ].
-        ].
+	aClass fileOutDefinitionOn:s
+    ] ifFalse:[
+	aClass theNonMetaclass isJavaClass ifTrue:[
+	    | src |
+	    src := aClass theNonMetaclass source.
+	    src notNil ifTrue:[ ^ src ].
+	    s nextPutLine: '// *** WARNING ***'.
+	    s nextPutLine: '// Following code has been decompiled from loaded class'.
+	    s nextPutLine: '// *** WARNING ***'.
+	    s cr.
+	    aClass fileOutDefinitionOn:s
+	] ifFalse:[
+	    aClass isMeta ifTrue:[
+		aClass
+		    fileOutClassInstVarDefinitionOn:s
+		    withNameSpace:true.
+	    ] ifFalse:[
+		"/
+		"/ here, show it with a nameSpace pragma
+		"/ and prefer short names.
+		"/
+		aClass
+		    basicFileOutDefinitionOn:s
+		    withNameSpace:true
+		    withPackage:false
+	    ].
+	].
     ].
 
     ^ s contents withTabsExpanded.
@@ -48122,62 +48666,62 @@
 
     m := aClass theMetaclass compiledMethodAt:#documentation.
     m notNil ifTrue:[
-        s := m comment.
-        isComment := false.
-    ] ifFalse:[
-        "try comment"
-        s := aClass comment.
-        s isString ifTrue:[
-            s isEmpty ifTrue:[
-                s := nil
-            ] ifFalse:[
-                (s includes:$") ifTrue:[
-                    s := s copyReplaceAll:$" with:$'.
-                ].
-                isComment := true.
-                s size > 80 ifTrue:[
-                    s := s asCollectionOfSubstringsSeparatedBy:$..
-                    s := s asStringCollection.
-                    s := s collect:[:each | (each startsWith:Character space) ifTrue:[
-                                                each copyFrom:2
-                                            ] ifFalse:[
-                                                each
-                                            ]
-                                   ].
-                    s := s asStringWith:('.' , Character cr).
-                ].
-            ]
-        ] ifFalse:[
-            "/ class redefines comment ?
-            s := nil
-        ].
+	s := m comment.
+	isComment := false.
+    ] ifFalse:[
+	"try comment"
+	s := aClass comment.
+	s isString ifTrue:[
+	    s isEmpty ifTrue:[
+		s := nil
+	    ] ifFalse:[
+		(s includes:$") ifTrue:[
+		    s := s copyReplaceAll:$" with:$'.
+		].
+		isComment := true.
+		s size > 80 ifTrue:[
+		    s := s asCollectionOfSubstringsSeparatedBy:$..
+		    s := s asStringCollection.
+		    s := s collect:[:each | (each startsWith:Character space) ifTrue:[
+						each copyFrom:2
+					    ] ifFalse:[
+						each
+					    ]
+				   ].
+		    s := s asStringWith:('.' , Character cr).
+		].
+	    ]
+	] ifFalse:[
+	    "/ class redefines comment ?
+	    s := nil
+	].
     ].
     s notNil ifTrue:[
-        s asStringCollection withoutLeadingBlankLines
+	s asStringCollection withoutLeadingBlankLines
     ].
 
     infoStream := TextStream on:''.
     infoStream "cr; cr;" cr.
     s isNil ifTrue:[
-        infoStream nextPutLine:' no comment or documentation method found'.
-    ] ifFalse:[
-        "/ nextPutLine:' Documentation:'.
-        infoStream nextPutLine:s; cr.
-        infoStream nextPutLine:' Notice: '.
-        infoStream nextPutAll:'   the above text has been extracted from the classes '.
-        infoStream nextPutLine:(isComment ifTrue:['comment.'] ifFalse:['documentation method.']).
-        infoStream nextPutLine:'   Any change in it will be lost if you ''accept'' here.'.
-        infoStream nextPutAll:'   To change the '.
-        infoStream nextPutAll:(isComment ifTrue:['comment'] ifFalse:['documentation']).
-        infoStream nextPutAll:', switch to the '.
-        infoStream nextPutAll:(isComment ifTrue:['comment'] ifFalse:['documentation method']).
-        infoStream nextPutLine:' and ''accept'' any changes there.'.
+	infoStream nextPutLine:' no comment or documentation method found'.
+    ] ifFalse:[
+	"/ nextPutLine:' Documentation:'.
+	infoStream nextPutLine:s; cr.
+	infoStream nextPutLine:' Notice: '.
+	infoStream nextPutAll:'   the above text has been extracted from the classes '.
+	infoStream nextPutLine:(isComment ifTrue:['comment.'] ifFalse:['documentation method.']).
+	infoStream nextPutLine:'   Any change in it will be lost if you ''accept'' here.'.
+	infoStream nextPutAll:'   To change the '.
+	infoStream nextPutAll:(isComment ifTrue:['comment'] ifFalse:['documentation']).
+	infoStream nextPutAll:', switch to the '.
+	infoStream nextPutAll:(isComment ifTrue:['comment'] ifFalse:['documentation method']).
+	infoStream nextPutLine:' and ''accept'' any changes there.'.
     ].
     infoStream cr.
 
     info := String streamContents:[:s |
-                aClass programmingLanguage writeComment:(infoStream contents) on:s
-            ].
+		aClass programmingLanguage writeComment:(infoStream contents) on:s
+	    ].
     info := info emphasizeAllWith:UserPreferences current commentEmphasisAndColor.
     ^ info
 
@@ -48185,117 +48729,117 @@
 !
 
 searchForCodePattern:codePattern direction:direction startLine:startLine startCol:startCol
-                            ifFound:foundBlock ifNotFound:notFoundBlock
+			    ifFound:foundBlock ifNotFound:notFoundBlock
     |searcher|
 
     self parseTreeSearcherAvailable ifFalse:[ ^ self ].
 
     searcher := ParseTreeSearcher new.
     searcher
-        matches: codePattern
-        do:[:aNode :answer | answer add:aNode. answer ].
-
-    ^ self
-        searchUsingSearcher:searcher
-        direction:direction
-        startLine:startLine startCol:startCol
-        ifFound:foundBlock ifNotFound:notFoundBlock.
+	matches: codePattern
+	do:[:aNode :answer | answer add:aNode. answer ].
+
+    ^ self
+	searchUsingSearcher:searcher
+	direction:direction
+	startLine:startLine startCol:startCol
+	ifFound:foundBlock ifNotFound:notFoundBlock.
 !
 
 searchForSelector:aSelectorOrCollectionOfSelectors direction:direction
-                            startLine:startLine startCol:startCol
-                            ignoreCase:ignoreCase doMatch:doMatch
-                            ifFound:foundBlock ifNotFound:notFoundBlock
+			    startLine:startLine startCol:startCol
+			    ignoreCase:ignoreCase doMatch:doMatch
+			    ifFound:foundBlock ifNotFound:notFoundBlock
     |searcher|
 
     self parseTreeSearcherAvailable ifFalse:[ ^ self ].
 
     doMatch ifTrue:[
-        (aSelectorOrCollectionOfSelectors isSymbol or:[aSelectorOrCollectionOfSelectors isString]) ifTrue:[
-            searcher := ParseTreeSearcher allMessageSendsMatching:aSelectorOrCollectionOfSelectors ignoreCase:ignoreCase.
-        ] ifFalse:[
-            searcher := ParseTreeSearcher allMessageSendsMatchingAny:aSelectorOrCollectionOfSelectors ignoreCase:ignoreCase.
-        ].
-    ] ifFalse:[
-        (aSelectorOrCollectionOfSelectors isSymbol or:[aSelectorOrCollectionOfSelectors isString]) ifTrue:[
-            searcher := ParseTreeSearcher allMessageSendsTo:aSelectorOrCollectionOfSelectors ignoreCase:ignoreCase.
-        ] ifFalse:[
-            searcher := ParseTreeSearcher allMessageSendsToAny:aSelectorOrCollectionOfSelectors ignoreCase:ignoreCase.
-        ].
-    ].
-    ^ self 
-        searchUsingSearcher:searcher 
-        direction:direction
-        startLine:startLine startCol:startCol
-        ifFound:foundBlock ifNotFound:notFoundBlock.
+	(aSelectorOrCollectionOfSelectors isSymbol or:[aSelectorOrCollectionOfSelectors isString]) ifTrue:[
+	    searcher := ParseTreeSearcher allMessageSendsMatching:aSelectorOrCollectionOfSelectors ignoreCase:ignoreCase.
+	] ifFalse:[
+	    searcher := ParseTreeSearcher allMessageSendsMatchingAny:aSelectorOrCollectionOfSelectors ignoreCase:ignoreCase.
+	].
+    ] ifFalse:[
+	(aSelectorOrCollectionOfSelectors isSymbol or:[aSelectorOrCollectionOfSelectors isString]) ifTrue:[
+	    searcher := ParseTreeSearcher allMessageSendsTo:aSelectorOrCollectionOfSelectors ignoreCase:ignoreCase.
+	] ifFalse:[
+	    searcher := ParseTreeSearcher allMessageSendsToAny:aSelectorOrCollectionOfSelectors ignoreCase:ignoreCase.
+	].
+    ].
+    ^ self
+	searchUsingSearcher:searcher
+	direction:direction
+	startLine:startLine startCol:startCol
+	ifFound:foundBlock ifNotFound:notFoundBlock.
 !
 
 searchForVariable:aVariableNameOrCollectionOfVariableNames direction:direction
-                            startLine:startLine startCol:startCol
-                            readers:searchReaders writers:searchWriters
-                            ifFound:foundBlock ifNotFound:notFoundBlock
+			    startLine:startLine startCol:startCol
+			    readers:searchReaders writers:searchWriters
+			    ifFound:foundBlock ifNotFound:notFoundBlock
     |searcher|
 
     self parseTreeSearcherAvailable ifFalse:[ ^ self ].
 
     searchReaders ifTrue:[
-        searchWriters ifTrue:[
-            searcher := ParseTreeSearcher allReferencesToAnyVariableIn:aVariableNameOrCollectionOfVariableNames.
-        ] ifFalse:[
-            searcher := ParseTreeSearcher allReadsOfAnyVariableIn:aVariableNameOrCollectionOfVariableNames.
-        ].
-    ] ifFalse:[
-        searchWriters ifTrue:[
-            searcher := ParseTreeSearcher allModificationsOfAnyVariableIn:aVariableNameOrCollectionOfVariableNames.
-        ] ifFalse:[
-            self error:'missing search criteria'
-        ].
+	searchWriters ifTrue:[
+	    searcher := ParseTreeSearcher allReferencesToAnyVariableIn:aVariableNameOrCollectionOfVariableNames.
+	] ifFalse:[
+	    searcher := ParseTreeSearcher allReadsOfAnyVariableIn:aVariableNameOrCollectionOfVariableNames.
+	].
+    ] ifFalse:[
+	searchWriters ifTrue:[
+	    searcher := ParseTreeSearcher allModificationsOfAnyVariableIn:aVariableNameOrCollectionOfVariableNames.
+	] ifFalse:[
+	    self error:'missing search criteria'
+	].
     ].
     ^ self searchUsingSearcher:searcher direction:direction
-                    startLine:startLine startCol:startCol
-                    ifFound:foundBlock ifNotFound:notFoundBlock.
+		    startLine:startLine startCol:startCol
+		    ifFound:foundBlock ifNotFound:notFoundBlock.
 !
 
 searchUsingSearcher:searcher direction:direction
-                            startLine:startLine startCol:startCol
-                            ifFound:foundBlock ifNotFound:notFoundBlock
+			    startLine:startLine startCol:startCol
+			    ifFound:foundBlock ifNotFound:notFoundBlock
     |codeTree nodes searchStartPos prevNode|
 
     RBParser isNil ifTrue:[^ self].
     codeTree := RBParser
-                    parseSearchMethod:self codeView contents
-                    onError: [:str :pos | "Transcript showCR:str. Transcript showCR:pos." nil].
+		    parseSearchMethod:self codeView contents
+		    onError: [:str :pos | "Transcript showCR:str. Transcript showCR:pos." nil].
 
     codeTree notNil ifTrue:[
-        searcher executeTree:codeTree initialAnswer:(nodes := OrderedCollection new).
-
-        searchStartPos := self codeView characterPositionOfLine:startLine col:startCol.
-        nodes do:[:aNode |
-            |nodeStartPos nodeEndPos selStartLine selEndLine|
-
-            nodeStartPos := aNode start.
-            nodeEndPos := aNode stop.
+	searcher executeTree:codeTree initialAnswer:(nodes := OrderedCollection new).
+
+	searchStartPos := self codeView characterPositionOfLine:startLine col:startCol.
+	nodes do:[:aNode |
+	    |nodeStartPos nodeEndPos selStartLine selEndLine|
+
+	    nodeStartPos := aNode start.
+	    nodeEndPos := aNode stop.
 
 "/ self codeView selectFromCharacterPosition:nodeStartPos to:nodeEndPos.
 
-            direction == #backward ifTrue:[
-                nodeEndPos >= (searchStartPos-1) ifTrue:[
-                    prevNode isNil ifTrue:[^ self].
-                    foundBlock value:(prevNode start) value:(prevNode stop).
-                    ^ self.
-                ].
-                prevNode := aNode.
-            ] ifFalse:[
-                nodeStartPos >= searchStartPos ifTrue:[
-                    foundBlock value:nodeStartPos value:nodeEndPos.
-                    ^ self.
-                ].
-            ].
-        ].
-        prevNode notNil ifTrue:[
-            foundBlock value:(prevNode start) value:(prevNode stop).
-            ^ self
-        ].
+	    direction == #backward ifTrue:[
+		nodeEndPos >= (searchStartPos-1) ifTrue:[
+		    prevNode isNil ifTrue:[^ self].
+		    foundBlock value:(prevNode start) value:(prevNode stop).
+		    ^ self.
+		].
+		prevNode := aNode.
+	    ] ifFalse:[
+		nodeStartPos >= searchStartPos ifTrue:[
+		    foundBlock value:nodeStartPos value:nodeEndPos.
+		    ^ self.
+		].
+	    ].
+	].
+	prevNode notNil ifTrue:[
+	    foundBlock value:(prevNode start) value:(prevNode stop).
+	    ^ self
+	].
     ].
     notFoundBlock value
 !
@@ -48304,27 +48848,27 @@
     |searchAction|
 
     aCollectionOfVariables size > 0 ifTrue:[
-        searchAction :=
-            [:direction :startLine :startCol :foundBlock :notFoundBlock|
-                |codeView|
-
-                codeView := self codeView.
-                self
-                    searchForVariable:aCollectionOfVariables direction:direction
-                    startLine:(codeView cursorLine ? startLine) startCol:(codeView cursorCol ? startCol)
-                    readers:doReaders writers:doWriters
-                    ifFound:
-                        [:charPos1 :charPos2 |
-
-                            codeView
-                                cursorToCharacterPosition:charPos1;
-                                selectFromCharacterPosition:charPos1 to:charPos2
-                        ]
-                    ifNotFound:(asAutoSearch ifTrue:[notFoundBlock] ifFalse:[nil])
-            ].
-
-        navigationState autoSearchAction:searchAction.
-        self codeView searchAction:searchAction
+	searchAction :=
+	    [:direction :startLine :startCol :foundBlock :notFoundBlock|
+		|codeView|
+
+		codeView := self codeView.
+		self
+		    searchForVariable:aCollectionOfVariables direction:direction
+		    startLine:(codeView cursorLine ? startLine) startCol:(codeView cursorCol ? startCol)
+		    readers:doReaders writers:doWriters
+		    ifFound:
+			[:charPos1 :charPos2 |
+
+			    codeView
+				cursorToCharacterPosition:charPos1;
+				selectFromCharacterPosition:charPos1 to:charPos2
+			]
+		    ifNotFound:(asAutoSearch ifTrue:[notFoundBlock] ifFalse:[nil])
+	    ].
+
+	navigationState autoSearchAction:searchAction.
+	self codeView searchAction:searchAction
     ]
 !
 
@@ -48333,19 +48877,19 @@
 
     theNonMetaclass := aClass theNonMetaclass.
     codeAspect == #classComment ifTrue:[
-        self showClassComment:theNonMetaclass.
-        ^ self.
+	self showClassComment:theNonMetaclass.
+	^ self.
     ].
     codeAspect == #classHierarchy ifTrue:[
-        self showClassHierarchy:theNonMetaclass.
-        ^ self.
+	self showClassHierarchy:theNonMetaclass.
+	^ self.
     ].
 
     ((codeAspect == #primitiveDefinitions)
     or:[ (codeAspect == #primitiveFunctions)
     or:[ (codeAspect == #primitiveVariables) ]]) ifTrue:[
-        self showClassPrimitive:codeAspect class:aClass theNonMetaclass.
-        ^ self.
+	self showClassPrimitive:codeAspect class:aClass theNonMetaclass.
+	^ self.
     ].
     self setAcceptActionForClass.
     self showClassDefinition:aClass.
@@ -48360,16 +48904,16 @@
 "/    self selectedProtocols value:nil.
 
     aClass notNil ifTrue:[
-        aClass isLoaded ifFalse:[
-            code := 'Class is not loaded.'.
-        ] ifTrue:[
-            code := aClass comment.
-        ].
-
-        codeView := self codeView.
-        codeView contents:code.
-        codeView modified:false.
-        navigationState realModifiedState:false.
+	aClass isLoaded ifFalse:[
+	    code := 'Class is not loaded.'.
+	] ifTrue:[
+	    code := aClass comment.
+	].
+
+	codeView := self codeView.
+	codeView contents:code.
+	codeView modified:false.
+	navigationState realModifiedState:false.
     ]
 
     "Modified: / 8.11.2001 / 23:08:31 / cg"
@@ -48387,32 +48931,32 @@
     definition := self classDefinitionStringFor:aClass.
 
     self doSyntaxColoring value ~~ false ifTrue:[
-        highlighter := aClass syntaxHighlighterClass.
-        highlighter notNil ifTrue:[
-            definition := highlighter formatClassDefinition:definition in:nil.
-        ]
+	highlighter := aClass syntaxHighlighterClass.
+	highlighter notNil ifTrue:[
+	    definition := highlighter formatClassDefinition:definition in:nil.
+	]
     ].
 
     self showCode:definition.
     self normalLabel.
 
     aClass isLoaded ifTrue:[
-        "/ continue fetching the documentation,
-        "/ which may take longer, if the source must be fetched
-        "/ from the repository.
-
-        "
-         add documentation as a comment, if there is any
-        "
-        info := self commentOrDocumentationStringFromClass:aClass.
-        text := definition.
-        info notNil ifTrue:[
-            text := text,(Character cr),info. 
-        ].
-        self codeHolder setValue:text.
-        self codeView notNil ifTrue:[
-            self codeView setContents:text
-        ].
+	"/ continue fetching the documentation,
+	"/ which may take longer, if the source must be fetched
+	"/ from the repository.
+
+	"
+	 add documentation as a comment, if there is any
+	"
+	info := self commentOrDocumentationStringFromClass:aClass.
+	text := definition.
+	info notNil ifTrue:[
+	    text := text,(Character cr),info.
+	].
+	self codeHolder setValue:text.
+	self codeView notNil ifTrue:[
+	    self codeView setContents:text
+	].
     ].
     self updatePackageInfoForClass:aClass.
 
@@ -48426,14 +48970,14 @@
     "/ show classes documentation
     cls := self theSingleSelectedClass.
     cls notNil ifTrue:[
-        cls isLoaded ifFalse:[
-            text := 'Class is not loaded.'.
-        ] ifTrue:[
-            text := HTMLDocGenerator htmlDocOf:cls.
-        ].
-        self classDocumentationHolder value:text.
-    ] ifFalse:[
-        self showNothing.
+	cls isLoaded ifFalse:[
+	    text := 'Class is not loaded.'.
+	] ifTrue:[
+	    text := HTMLDocGenerator htmlDocOf:cls.
+	].
+	self classDocumentationHolder value:text.
+    ] ifFalse:[
+	self showNothing.
     ].
 
     "Modified: / 01-03-2007 / 20:58:34 / cg"
@@ -48447,20 +48991,20 @@
     self setAcceptActionForNothing.
 
     aClass notNil ifTrue:[
-        s := '' writeStream.
-        indent := 0.
-        aClass withAllSuperclasses reverse do:[:cls |
-            s spaces:indent * 2.
-            s nextPutAll:cls name.
-            s cr.
-            indent := indent + 1.
-        ].
-        code := s contents.
-
-        codeView := self codeView.
-        codeView contents:code.
-        codeView modified:false.
-        navigationState realModifiedState:false.
+	s := '' writeStream.
+	indent := 0.
+	aClass withAllSuperclasses reverse do:[:cls |
+	    s spaces:indent * 2.
+	    s nextPutAll:cls name.
+	    s cr.
+	    indent := indent + 1.
+	].
+	code := s contents.
+
+	codeView := self codeView.
+	codeView contents:code.
+	codeView modified:false.
+	navigationState realModifiedState:false.
     ]
 
     "Modified: / 8.11.2001 / 23:07:57 / cg"
@@ -48472,23 +49016,23 @@
     self codeAspect:aspect.
 
     aClass isLoaded ifFalse:[
-        primCode := 'Class is not loaded'.
-        self setAcceptActionForNothing.
+	primCode := 'Class is not loaded'.
+	self setAcceptActionForNothing.
     ] ifTrue:[
-        aspect == #primitiveDefinitions ifTrue:[
-            primCode := aClass primitiveDefinitionsStringOrDefault.
-        ] ifFalse:[
-            aspect == #primitiveFunctions ifTrue:[
-                primCode := aClass primitiveFunctionsStringOrDefault.
-            ] ifFalse:[
-                aspect == #primitiveVariables ifTrue:[
-                    primCode := aClass primitiveVariablesStringOrDefault.
-                ] ifFalse:[
-                    self error:'unknown primitive aspect'.
-                ]
-            ]
-        ].
-        self setAcceptAction:[:theCode | self doAcceptClassPrimitive:theCode].
+	aspect == #primitiveDefinitions ifTrue:[
+	    primCode := aClass primitiveDefinitionsStringOrDefault.
+	] ifFalse:[
+	    aspect == #primitiveFunctions ifTrue:[
+		primCode := aClass primitiveFunctionsStringOrDefault.
+	    ] ifFalse:[
+		aspect == #primitiveVariables ifTrue:[
+		    primCode := aClass primitiveVariablesStringOrDefault.
+		] ifFalse:[
+		    self error:'unknown primitive aspect'.
+		]
+	    ]
+	].
+	self setAcceptAction:[:theCode | self doAcceptClassPrimitive:theCode].
     ].
 
     codeView := self codeView.
@@ -48510,47 +49054,47 @@
 
     text := '%1 (%2) : %3'.
     val isNumber ifTrue:[
-        text := '%1 (%2) : %3 (%4)'.
-        valText := val printString.
-    ] ifFalse:[
-        val isLiteral ifTrue:[
-            text := '%1 (%2) : %4'.
-            lines := val storeString asCollectionOfLines.
-            valText := lines first contractTo:30.
-            valText := valText copy.
-            valText replaceAllForWhich:[:ch | ch isControlCharacter] with:$?.
-            lines size > 1 ifTrue:[
-                valText := valText , '...'.
-            ].
-        ] ifFalse:[
-            val isCollection ifTrue:[
-                text := '%1 (%2) : %3 (%4)'.
-                valText := val isEmpty
-                            ifTrue:['empty']
-                            ifFalse:['size: ' , val size printString].
-            ] ifFalse:[
-                val isBehavior ifTrue:[
-                    (val isSubclassOf:Error) ifTrue:[
-                        text := '%1 (%2) : %4 (an Error subclass)'.
-                        valText := val name.
-                    ] ifFalse:[
-                        (val isSubclassOf:Exception) ifTrue:[
-                            text := '%1 (%2) : %4 (an Exception subclass)'.
-                            valText := val name.
-                        ] ifFalse:[
-                            text := '%1 (%2) : %4'.
-                            valText := val name.
-                        ]
-                    ]
-                ]
-            ]
-        ].
+	text := '%1 (%2) : %3 (%4)'.
+	valText := val printString.
+    ] ifFalse:[
+	val isLiteral ifTrue:[
+	    text := '%1 (%2) : %4'.
+	    lines := val storeString asCollectionOfLines.
+	    valText := lines first contractTo:30.
+	    valText := valText copy.
+	    valText replaceAllForWhich:[:ch | ch isControlCharacter] with:$?.
+	    lines size > 1 ifTrue:[
+		valText := valText , '...'.
+	    ].
+	] ifFalse:[
+	    val isCollection ifTrue:[
+		text := '%1 (%2) : %3 (%4)'.
+		valText := val isEmpty
+			    ifTrue:['empty']
+			    ifFalse:['size: ' , val size printString].
+	    ] ifFalse:[
+		val isBehavior ifTrue:[
+		    (val isSubclassOf:Error) ifTrue:[
+			text := '%1 (%2) : %4 (an Error subclass)'.
+			valText := val name.
+		    ] ifFalse:[
+			(val isSubclassOf:Exception) ifTrue:[
+			    text := '%1 (%2) : %4 (an Exception subclass)'.
+			    valText := val name.
+			] ifFalse:[
+			    text := '%1 (%2) : %4'.
+			    valText := val name.
+			]
+		    ]
+		]
+	    ]
+	].
     ].
     text := text
-                bindWith:var allBold
-                with:(aClass name)
-                with:(val class nameWithArticle)
-                with:valText.
+		bindWith:var allBold
+		with:(aClass name)
+		with:(val class nameWithArticle)
+		with:valText.
     self showInfo:text.
 !
 
@@ -48567,43 +49111,43 @@
 
 
     (codeView := self codeView) notNil ifTrue:[
-        codeView numberOfLines < 1000 ifTrue:[
-            shownCode := codeView contents.
-        ].
-        prevCode := (shownCode ? '') asString.
-        (codeView modified
-        or:[
-            (prevCode asText sameStringAndEmphasisAs:(code ? '') asString asText) not
-        ]) ifTrue:[
-            (prevCode isNil
-            or:[code isNil
-            or:[(prevCode withTabsExpanded sameStringAndEmphasisAs: code withTabsExpanded) not]]) ifTrue:[
-                code = self codeHolder value ifTrue:[
-                    "/ a reselect without accepting before ...
-                    "/ sigh - must use setValue, and enforce a change
-                    "/ (workaround for proceed after changed text-warning)
-                    self codeHolder setValue:code.
-                    code = shownCode ifFalse:[
-                        codeView setContents:code.
-                    ]
-                ] ifFalse:[
-                    self codeHolder value:code.
-                ].
-            ].
-            doScrollToTop ifTrue:[
-                codeView cursorHome.
-            ]
-        ]
-    ] ifFalse:[
-        code = self codeHolder value ifTrue:[
-            "/ a reselect without accepting before ...
-            "/ sigh - must use setValue, and enforce a change
-            "/ (workaround for proceed after changed text-warning)
-            self codeHolder setValue:code.
+	codeView numberOfLines < 1000 ifTrue:[
+	    shownCode := codeView contents.
+	].
+	prevCode := (shownCode ? '') asString.
+	(codeView modified
+	or:[
+	    (prevCode asText sameStringAndEmphasisAs:(code ? '') asString asText) not
+	]) ifTrue:[
+	    (prevCode isNil
+	    or:[code isNil
+	    or:[(prevCode withTabsExpanded sameStringAndEmphasisAs: code withTabsExpanded) not]]) ifTrue:[
+		code = self codeHolder value ifTrue:[
+		    "/ a reselect without accepting before ...
+		    "/ sigh - must use setValue, and enforce a change
+		    "/ (workaround for proceed after changed text-warning)
+		    self codeHolder setValue:code.
+		    code = shownCode ifFalse:[
+			codeView setContents:code.
+		    ]
+		] ifFalse:[
+		    self codeHolder value:code.
+		].
+	    ].
+	    doScrollToTop ifTrue:[
+		codeView cursorHome.
+	    ]
+	]
+    ] ifFalse:[
+	code = self codeHolder value ifTrue:[
+	    "/ a reselect without accepting before ...
+	    "/ sigh - must use setValue, and enforce a change
+	    "/ (workaround for proceed after changed text-warning)
+	    self codeHolder setValue:code.
 "/            codeView setContents:aString.
-        ] ifFalse:[
-            self codeHolder value:code.
-        ]
+	] ifFalse:[
+	    self codeHolder value:code.
+	]
     ].
 
     "Created: / 01-03-2000 / 11:38:07 / cg"
@@ -48614,8 +49158,8 @@
     |definition|
 
     aClass isLoaded ifFalse:[
-        self showClassDefinition:aClass.
-        ^ self.
+	self showClassDefinition:aClass.
+	^ self.
     ].
     definition := aClass source.
     self showCode:definition.
@@ -48631,10 +49175,10 @@
     "/ show full classes source - set accept action for fileIn
     cls := self theSingleSelectedClass.
     cls notNil ifTrue:[
-        self setAcceptActionForClass.
-        self showFullClassDefinition:cls.
-    ] ifFalse:[
-        self showNothing.
+	self setAcceptActionForClass.
+	self showFullClassDefinition:cls.
+    ] ifFalse:[
+	self showNothing.
     ].
 
     navigationState modified:false.
@@ -48659,18 +49203,18 @@
 
     code := self sourceOfMethod:mthd.
     code isText ifTrue:[
-        doSyntaxColoring := false.
-    ] ifFalse:[
-        "/Do no coloring here if CodeView2 is used,
-        "/since CodeView2 itself cares about the coloring!!
-        "/Not working correctly -> do the coloring until fixed in CodeView2
-        "JV: Enable is, otherwise I won't notice that it does not work
-         correctly!!"
-        (UserPreferences current useCodeView2In: #Browser) ifTrue:[
-            doSyntaxColoring := code size < 2000
-        ] ifFalse:[
-            doSyntaxColoring := self doSyntaxColoring value == true.
-        ].
+	doSyntaxColoring := false.
+    ] ifFalse:[
+	"/Do no coloring here if CodeView2 is used,
+	"/since CodeView2 itself cares about the coloring!!
+	"/Not working correctly -> do the coloring until fixed in CodeView2
+	"JV: Enable is, otherwise I won't notice that it does not work
+	 correctly!!"
+	(UserPreferences current useCodeView2In: #Browser) ifTrue:[
+	    doSyntaxColoring := code size < 2000
+	] ifFalse:[
+	    doSyntaxColoring := self doSyntaxColoring value == true.
+	].
     ].
 
 
@@ -48678,9 +49222,9 @@
 
 
     doAutoFormat ifTrue:[
-        Error catch:[
-            code := RBFormatter format:code
-        ].
+	Error catch:[
+	    code := RBFormatter format:code
+	].
     ].
 
     "Hack for Java methods: 'As whole class source coce is shown,
@@ -48690,43 +49234,43 @@
     "hmm...hmm...how implement it in a better, more generic way?"
     doUpdateCode := true.
     (mthd isJavaMethod and:[mthd isSynthetic not]) ifTrue:[
-        prevMthd := navigationState lastMethodShownInCodeView.
-        (prevMthd notNil and:[prevMthd isJavaMethod]) ifTrue:[
-            doUpdateCode := prevMthd isSynthetic or:[mthd javaClass ~~ prevMthd javaClass]
-        ].
+	prevMthd := navigationState lastMethodShownInCodeView.
+	(prevMthd notNil and:[prevMthd isJavaMethod]) ifTrue:[
+	    doUpdateCode := prevMthd isSynthetic or:[mthd javaClass ~~ prevMthd javaClass]
+	].
     ].
     doUpdateCode ifTrue:[
-        doSyntaxColoring ifTrue:[
-            "/ immediate coloring, if code is not too large;
-            "/ otherwise, do it in the background.
-            code size < 2000 " 10000 " ifTrue:[
-                Error handle:[:ex |
-                    Transcript showCR:'error in syntaxHighlighter: ',ex description.
-                ] do:[
-                    code := self syntaxHighlightedCodeFor:code method:mthd.
-                ].
-            ] ifFalse:[
-                self enqueueDelayedStartSyntaxHighlightProcess.
-            ].
-
-            [
-                codeView modifiedChannel removeDependent:self.
-                codeView modified:false.
-                self showCode:code scrollToTop:doScrollToTop.
-            ] ensure:[
-                codeView modifiedChannel addDependent:self.
-            ]
-        ] ifFalse:[
-            self showCode:code scrollToTop:doScrollToTop.
-        ].
+	doSyntaxColoring ifTrue:[
+	    "/ immediate coloring, if code is not too large;
+	    "/ otherwise, do it in the background.
+	    code size < 2000 " 10000 " ifTrue:[
+		Error handle:[:ex |
+		    Transcript showCR:'error in syntaxHighlighter: ',ex description.
+		] do:[
+		    code := self syntaxHighlightedCodeFor:code method:mthd.
+		].
+	    ] ifFalse:[
+		self enqueueDelayedStartSyntaxHighlightProcess.
+	    ].
+
+	    [
+		codeView modifiedChannel removeDependent:self.
+		codeView modified:false.
+		self showCode:code scrollToTop:doScrollToTop.
+	    ] ensure:[
+		codeView modifiedChannel addDependent:self.
+	    ]
+	] ifFalse:[
+	    self showCode:code scrollToTop:doScrollToTop.
+	].
     ].
     navigationState lastMethodShownInCodeView: mthd.
 
     "/ scroll, for file-based classes (java, ruby, etc.)
     mthd sourceLineNumber ~~ 1 ifTrue:[
-        doScrollToTop "ifTrue:" ifFalse:[
-            codeView scrollToLine:mthd sourceLineNumber
-        ]
+	doScrollToTop "ifTrue:" ifFalse:[
+	    codeView scrollToLine:mthd sourceLineNumber
+	]
     ].
     self codeAspect:(code ifNil:[nil] ifNotNil:[#method]).
     self normalLabel.
@@ -48754,32 +49298,32 @@
     "/ show version differences against repository
     cls := self theSingleSelectedClass.
     cls notNil ifTrue:[
-        cls := cls theNonMetaclass.
-        (ownerClass := cls topOwningClass) isNil ifTrue:[ownerClass := cls].
-        mgr := SourceCodeManagerUtilities default sourceCodeManagerFor:ownerClass.
-
-        info := 'Package: ' , ownerClass package.
+	cls := cls theNonMetaclass.
+	(ownerClass := cls topOwningClass) isNil ifTrue:[ownerClass := cls].
+	mgr := SourceCodeManagerUtilities default sourceCodeManagerFor:ownerClass.
+
+	info := 'Package: ' , ownerClass package.
 
 "/        (mgr checkForExistingContainerForClass:ownerClass) ifFalse:[
 "/            info := info , ' not in repository (?)'
 "/        ] ifTrue:[
-            info := info , ' Version: ' , (ownerClass revision ? 'no-version').
-            info := info , ' Repository: ' , ((ownerClass sourceCodeManager ? SourceCodeManager) newestRevisionOf:ownerClass).
-
-            info := info , ' Location: '.
-            sourceInfo := mgr sourceInfoOfClass:ownerClass.
-            sourceInfo notNil ifTrue:[
-                moduleDir := mgr moduleFromSourceInfo:sourceInfo.
-                packageDir := mgr directoryFromSourceInfo:sourceInfo.
-                classFileName := mgr containerFromSourceInfo:sourceInfo.
-
-                info := info , ' ' , (moduleDir ? '???').
-                info := info , '/' , (packageDir ? '???').
-                info := info , '/' , (classFileName ? '???').
-            ].
+	    info := info , ' Version: ' , (ownerClass revision ? 'no-version').
+	    info := info , ' Repository: ' , ((ownerClass sourceCodeManager ? SourceCodeManager) newestRevisionOf:ownerClass).
+
+	    info := info , ' Location: '.
+	    sourceInfo := mgr sourceInfoOfClass:ownerClass.
+	    sourceInfo notNil ifTrue:[
+		moduleDir := mgr moduleFromSourceInfo:sourceInfo.
+		packageDir := mgr directoryFromSourceInfo:sourceInfo.
+		classFileName := mgr containerFromSourceInfo:sourceInfo.
+
+		info := info , ' ' , (moduleDir ? '???').
+		info := info , '/' , (packageDir ? '???').
+		info := info , '/' , (classFileName ? '???').
+	    ].
 "/         ].
     ] ifFalse:[
-        info := 'Please select a single class to see the diffs.'
+	info := 'Please select a single class to see the diffs.'
     ].
 
     diffApp setupForClass:cls againstVersion:nil. "/ #newest
@@ -48801,15 +49345,15 @@
     "/ instead of using perform:ifNotUnderstood:
 
     (nonMetaclass respondsTo:#sourceCodeManagerForSourceAccess) ifTrue:[
-        sourceCodeManager := nonMetaclass sourceCodeManagerForSourceAccess. 
-        sourceCodeManager notNil ifTrue:[ ^ sourceCodeManager].
+	sourceCodeManager := nonMetaclass sourceCodeManagerForSourceAccess.
+	sourceCodeManager notNil ifTrue:[ ^ sourceCodeManager].
     ].
     (nonMetaclass respondsTo:#sourceCodeManagerFromBinaryRevision) ifTrue:[
-        sourceCodeManager := nonMetaclass sourceCodeManagerFromBinaryRevision.
-        sourceCodeManager notNil ifTrue:[ ^ sourceCodeManager].
+	sourceCodeManager := nonMetaclass sourceCodeManagerFromBinaryRevision.
+	sourceCodeManager notNil ifTrue:[ ^ sourceCodeManager].
     ].
     (nonMetaclass respondsTo:#sourceCodeManager) ifTrue:[
-        sourceCodeManager := nonMetaclass sourceCodeManager
+	sourceCodeManager := nonMetaclass sourceCodeManager
     ].
     ^ sourceCodeManager
 
@@ -48827,7 +49371,7 @@
 
     (mthd sourcePosition isNil
     or:[mthd getSource isNil]) ifTrue:[
-        ^ '"
+	^ '"
 Sorry, but the methods sourceCode is not available.
 
 Probably, the methods sourceCode-info was stripped from the system.
@@ -48861,16 +49405,16 @@
 !
 
 updatePackageInfoBarIfSourceCodeManagersDoesNotMatchForClass: aClass
-    "Show a warning in package info bar if configured source code manager 
+    "Show a warning in package info bar if configured source code manager
      does not match the source code manager for source access"
 
     | cls cnfManager srcManager color showInfoButton |
 
     navigationState packageInfoButton isNil ifTrue:[
-        "JV@2011-10-03: When a browser is embedded in the inspector,
-         this method is called before the view is set. As a workaround,
-         return here"
-        ^self.
+	"JV@2011-10-03: When a browser is embedded in the inspector,
+	 this method is called before the view is set. As a workaround,
+	 return here"
+	^self.
     ].
 
 
@@ -48878,26 +49422,26 @@
     showInfoButton := false.
 
     (aClass notNil and:[aClass isLoaded]) ifTrue:[
-         cls := aClass.
-        [ cls isPrivate ] whileTrue:[cls := cls owningClass].
-        "For libbasic without #sourceCodeManagerFromBinaryRevision..."
-        (cls respondsTo: #sourceCodeManagerFromBinaryRevision) ifTrue:[
-            cnfManager := cls sourceCodeManager.
-            srcManager := cls sourceCodeManagerFromBinaryRevision.
-
-            cnfManager ~~ srcManager ifTrue:[
-                         "Color yellow lighter"
-                color := (Color red:100.0 green:100.0 blue:54.5464255741207).
-                showInfoButton := true.
-                navigationState packageInfoButton action:
-                    [self 
-                        informUserAboutPackage: cls package 
-                        configuredManager: cnfManager 
-                        sourceManager: srcManager
-                    ]
-                
-            ]
-        ]
+	 cls := aClass.
+	[ cls isPrivate ] whileTrue:[cls := cls owningClass].
+	"For libbasic without #sourceCodeManagerFromBinaryRevision..."
+	(cls respondsTo: #sourceCodeManagerFromBinaryRevision) ifTrue:[
+	    cnfManager := cls sourceCodeManager.
+	    srcManager := cls sourceCodeManagerFromBinaryRevision.
+
+	    cnfManager ~~ srcManager ifTrue:[
+			 "Color yellow lighter"
+		color := (Color red:100.0 green:100.0 blue:54.5464255741207).
+		showInfoButton := true.
+		navigationState packageInfoButton action:
+		    [self
+			informUserAboutPackage: cls package
+			configuredManager: cnfManager
+			sourceManager: srcManager
+		    ]
+
+	    ]
+	]
     ].
 
     navigationState packageInfoButton isVisible: showInfoButton.
@@ -48909,38 +49453,38 @@
 updatePackageInfoForClass:aClass
     |cls packageLabel loadInfo revisionInfo sourceCodeManager sourceCodeManagerInfo revision lastUser|
 
-    (aClass notNil and:[aClass isClass or:[aClass isMetaclass]]) ifTrue:[        
-        "/ packageLabel := 'Base: ' , (aClass package ? '?').
-
-        cls := aClass theNonMetaclass.
-        packageLabel := (aClass package ? '?') allBold.
-
-        aClass isLoaded ifTrue:[
-            sourceCodeManager := self sourceCodeManagerOfClass:aClass.
-
-            sourceCodeManager notNil ifTrue:[
-                sourceCodeManagerInfo := sourceCodeManager managerTypeNameShort , ' '
-            ] ifFalse:[
-                sourceCodeManagerInfo := ''.
-            ].
-
-            revisionInfo := cls revisionInfo.
-            (revisionInfo notNil and:[(revisionInfo at:#revision) notNil]) ifTrue:[
-                revision := revisionInfo at:#revision.
-                lastUser := ' ',((revisionInfo at:#user) ? '').
-            ] ifFalse:[
-                revision := cls revision.
-                lastUser := ''.
-            ].
-            loadInfo := ' [%1%2%3]' bindWith: sourceCodeManagerInfo with:(revision ? 'no revision') with:lastUser.
-            aClass wasAutoloaded ifTrue:[
-                loadInfo := loadInfo , ' {Auto}'.
-            ].
-        ] ifFalse:[
-            loadInfo := ' {Unloaded}'.
-        ].
-        packageLabel := packageLabel , loadInfo.
-        "/ packageLabel := packageLabel,' (Base)'.
+    (aClass notNil and:[aClass isClass or:[aClass isMetaclass]]) ifTrue:[
+	"/ packageLabel := 'Base: ' , (aClass package ? '?').
+
+	cls := aClass theNonMetaclass.
+	packageLabel := (aClass package ? '?') allBold.
+
+	aClass isLoaded ifTrue:[
+	    sourceCodeManager := self sourceCodeManagerOfClass:aClass.
+
+	    sourceCodeManager notNil ifTrue:[
+		sourceCodeManagerInfo := sourceCodeManager managerTypeNameShort , ' '
+	    ] ifFalse:[
+		sourceCodeManagerInfo := ''.
+	    ].
+
+	    revisionInfo := cls revisionInfo.
+	    (revisionInfo notNil and:[(revisionInfo at:#revision) notNil]) ifTrue:[
+		revision := revisionInfo at:#revision.
+		lastUser := ' ',((revisionInfo at:#user) ? '').
+	    ] ifFalse:[
+		revision := cls revision.
+		lastUser := ''.
+	    ].
+	    loadInfo := ' [%1%2%3]' bindWith: sourceCodeManagerInfo with:(revision ? 'no revision') with:lastUser.
+	    aClass wasAutoloaded ifTrue:[
+		loadInfo := loadInfo , ' {Auto}'.
+	    ].
+	] ifFalse:[
+	    loadInfo := ' {Unloaded}'.
+	].
+	packageLabel := packageLabel , loadInfo.
+	"/ packageLabel := packageLabel,' (Base)'.
     ].
 
     self updatePackageInfoBarIfSourceCodeManagersDoesNotMatchForClass: cls.
@@ -48956,54 +49500,54 @@
     |mpkg info info2 mClass revision sourceCodeManager sourceCodeManagerInfo prjDef scmInfo extensionOrNot|
 
     aMethod isNil ifTrue:[
-        ^ self updatePackageInfoForClass:self theSingleSelectedClass.
+	^ self updatePackageInfoForClass:self theSingleSelectedClass.
     ].
 
     mClass := aMethod mclass.
     mClass isNil ifTrue:[
-        info := 'Unassigned'
-    ] ifFalse:[
-        mpkg := aMethod package.
-        info := mpkg allBold.
-        extensionOrNot := ''.
-
-        (mpkg ~= mClass package) ifTrue:[
-            mpkg = PackageId noProjectID ifTrue:[
-                info2 := ' (Unassigned)'
-            ] ifFalse:[
-                extensionOrNot := ' Extension'.
-                prjDef := ProjectDefinition definitionClassForPackage: mpkg.
-                prjDef notNil ifTrue:[    
-                    sourceCodeManager := self sourceCodeManagerOfClass:prjDef.
-                    scmInfo := prjDef extensionsRevisionInfoForManager:nil.
-                    scmInfo notNil ifTrue:[
-                        revision := scmInfo revision.
-                    ]
-                ]
-            ].
-        ] ifFalse:[
-            sourceCodeManager := self sourceCodeManagerOfClass:mClass theNonMetaclass. 
-            revision := mClass theNonMetaclass revision printString.
-        ].
-
-        sourceCodeManager notNil ifTrue:[
-            sourceCodeManagerInfo := sourceCodeManager managerTypeNameShort , ' '
-        ] ifFalse:[
-            sourceCodeManagerInfo := ''.
-        ].
-
-        revision notNil ifTrue:[
-            info2 := ' ['.
-            (ChangeSet current includesChangeForClass:mClass selector:aMethod selector) ifTrue:[
-                info2 := info2,'derived from '
-            ].
-            info2 := info2,sourceCodeManagerInfo,revision,extensionOrNot,']'.
-        ].
-        info2 notNil ifTrue:[info := info,info2].
+	info := 'Unassigned'
+    ] ifFalse:[
+	mpkg := aMethod package.
+	info := mpkg allBold.
+	extensionOrNot := ''.
+
+	(mpkg ~= mClass package) ifTrue:[
+	    mpkg = PackageId noProjectID ifTrue:[
+		info2 := ' (Unassigned)'
+	    ] ifFalse:[
+		extensionOrNot := ' Extension'.
+		prjDef := ProjectDefinition definitionClassForPackage: mpkg.
+		prjDef notNil ifTrue:[
+		    sourceCodeManager := self sourceCodeManagerOfClass:prjDef.
+		    scmInfo := prjDef extensionsRevisionInfoForManager:nil.
+		    scmInfo notNil ifTrue:[
+			revision := scmInfo revision.
+		    ]
+		]
+	    ].
+	] ifFalse:[
+	    sourceCodeManager := self sourceCodeManagerOfClass:mClass theNonMetaclass.
+	    revision := mClass theNonMetaclass revision printString.
+	].
+
+	sourceCodeManager notNil ifTrue:[
+	    sourceCodeManagerInfo := sourceCodeManager managerTypeNameShort , ' '
+	] ifFalse:[
+	    sourceCodeManagerInfo := ''.
+	].
+
+	revision notNil ifTrue:[
+	    info2 := ' ['.
+	    (ChangeSet current includesChangeForClass:mClass selector:aMethod selector) ifTrue:[
+		info2 := info2,'derived from '
+	    ].
+	    info2 := info2,sourceCodeManagerInfo,revision,extensionOrNot,']'.
+	].
+	info2 notNil ifTrue:[info := info,info2].
     ].
 
     mClass notNil ifTrue:[
-        self updatePackageInfoBarIfSourceCodeManagersDoesNotMatchForClass: mClass theNonMetaclass.
+	self updatePackageInfoBarIfSourceCodeManagersDoesNotMatchForClass: mClass theNonMetaclass.
     ].
     navigationState packageLabelHolder value:info
 
@@ -49018,22 +49562,22 @@
 
     dir := defaultDirOrNil.
     dir isNil ifTrue:[
-        dir := FileSelectionBox lastFileSelectionDirectory.
-        dir isNil ifTrue:[
-            "
-             this test allows a smalltalk to be built without Projects/ChangeSets
-            "
-            Project notNil ifTrue:[
-                dir := Project currentProjectDirectory
-            ]
-        ]
+	dir := FileSelectionBox lastFileSelectionDirectory.
+	dir isNil ifTrue:[
+	    "
+	     this test allows a smalltalk to be built without Projects/ChangeSets
+	    "
+	    Project notNil ifTrue:[
+		dir := Project currentProjectDirectory
+	    ]
+	]
     ].
 
     dirName := Dialog
-        requestDirectoryName:title
-        default:dir
-        ok:(resources string:'FileOut')
-        abort:(resources string:'Cancel').
+	requestDirectoryName:title
+	default:dir
+	ok:(resources string:'FileOut')
+	abort:(resources string:'Cancel').
 
     dirName isEmptyOrNil ifTrue:[ ^ nil ].
     FileSelectionBox lastFileSelectionDirectory:dirName.
@@ -49066,92 +49610,92 @@
 askForMethodAndSpawnSearchTitle:title browserLabel:label searchWith:aSelectorOrBlock searchArea:whereDefault
     "convenient helper method: setup an enterBox for method browsing without text-entry.
      SearchArea may be one of
-        #everywhere,
-        #currentNameSpace
-        #currentClassesNameSpace
-        #classCategories
-        #classes
-        #classesWithPrivateClasses
-        #classHierarchies
-        #classHierarchiesWithPrivateClasses"
-
-    ^ self
-        askForMethodAndSpawnSearchTitle:title
-        browserLabel:label
-        searchWith:aSelectorOrBlock
-        searchArea:whereDefault
-        allowFind:false
-        allowBuffer:true
-        allowBrowser:true
+	#everywhere,
+	#currentNameSpace
+	#currentClassesNameSpace
+	#classCategories
+	#classes
+	#classesWithPrivateClasses
+	#classHierarchies
+	#classHierarchiesWithPrivateClasses"
+
+    ^ self
+	askForMethodAndSpawnSearchTitle:title
+	browserLabel:label
+	searchWith:aSelectorOrBlock
+	searchArea:whereDefault
+	allowFind:false
+	allowBuffer:true
+	allowBrowser:true
 !
 
 askForMethodAndSpawnSearchTitle:title browserLabel:label searchWith:aSelectorOrBlock searchArea:whereDefault allowFind:allowFind allowBuffer:allowBuffer allowBrowser:allowBrowser
     "convenient helper method: setup an enterBox for method browsing without text-entry.
      SearchArea may be one of
-        #everywhere,
-        #currentNameSpace
-        #currentClassesNameSpace
-        #classCategories
-        #classes
-        #classesWithPrivateClasses
-        #classHierarchies
-        #classHierarchiesWithPrivateClasses"
-
-    ^ self
-        askForMethodAndSpawnSearchTitle:title
-        browserLabel:label
-        searchWith:[:dummyString :classes :dummyCaseIgnore :dummyMatch |
-            aSelectorOrBlock value:classes
-        ]
-        searchWhat:#special
-        searchArea:whereDefault
-        withCaseIgnore:false
-        withTextEntry:false
-        withMatch:false
-        withMethodList:false
-        setSearchPattern:nil
+	#everywhere,
+	#currentNameSpace
+	#currentClassesNameSpace
+	#classCategories
+	#classes
+	#classesWithPrivateClasses
+	#classHierarchies
+	#classHierarchiesWithPrivateClasses"
+
+    ^ self
+	askForMethodAndSpawnSearchTitle:title
+	browserLabel:label
+	searchWith:[:dummyString :classes :dummyCaseIgnore :dummyMatch |
+	    aSelectorOrBlock value:classes
+	]
+	searchWhat:#special
+	searchArea:whereDefault
+	withCaseIgnore:false
+	withTextEntry:false
+	withMatch:false
+	withMethodList:false
+	setSearchPattern:nil
 !
 
 askForMethodAndSpawnSearchTitle:title browserLabel:labelHolderOrBlock searchWith:aSelectorOrBlock searchWhat:searchWhat searchArea:whereDefault withCaseIgnore:withCaseIgnore setSearchPattern:setSearchPatternAction
     "convenient helper method: setup an enterBox with text from codeView or selected
      method for browsing based on a selector. Set action and launch box.
      SearchArea may be one of
-        #everywhere,
-        #currentNameSpace
-        #currentClassesNameSpace
-        #classCategories
-        #classes
-        #classesWithPrivateClasses
-        #classHierarchies
-        #classHierarchiesWithPrivateClasses"
-
-    ^ self
-        askForMethodAndSpawnSearchTitle:title
-        browserLabel:labelHolderOrBlock
-        searchWith:aSelectorOrBlock
-        searchWhat:searchWhat
-        searchArea:whereDefault
-        withCaseIgnore:withCaseIgnore
-        withTextEntry:true
-        withMethodList:false
-        setSearchPattern:setSearchPatternAction
+	#everywhere,
+	#currentNameSpace
+	#currentClassesNameSpace
+	#classCategories
+	#classes
+	#classesWithPrivateClasses
+	#classHierarchies
+	#classHierarchiesWithPrivateClasses"
+
+    ^ self
+	askForMethodAndSpawnSearchTitle:title
+	browserLabel:labelHolderOrBlock
+	searchWith:aSelectorOrBlock
+	searchWhat:searchWhat
+	searchArea:whereDefault
+	withCaseIgnore:withCaseIgnore
+	withTextEntry:true
+	withMethodList:false
+	setSearchPattern:setSearchPatternAction
 !
 
 askForMethodAndSpawnSearchTitle:title browserLabel:labelHolderOrBlock searchWith:aSelectorOrBlock searchWhat:searchWhat searchArea:whereDefault
     withCaseIgnore:withCaseIgnore withTextEntry:withTextEntry withMatch:withMatch withMethodList:withMethodList setSearchPattern:setSearchPatternAction
 
-    "convenient common helper method for searches: 
+    "convenient common helper method for searches:
      setup an enterBox with text from codeView or selected
      method for browsing based on a selector. Set action and launch box.
      SearchArea may be one of
-        #everywhere,
-        #currentNameSpace
-        #currentClassesNameSpace
-        #classCategories
-        #classes
-        #classesWithPrivateClasses
-        #classHierarchies
-        #classHierarchiesWithPrivateClasses
+	#everywhere,
+	#currentNameSpace
+	#currentClassesNameSpace
+	#classCategories
+	#classes
+	#classesWithPrivateClasses
+	#classHierarchies
+	#classHierarchiesWithPrivateClasses
 
      aSelectorOrBlock is either a search selector (to be sent to SystemBrowser, such as findMethods:...)
      or a block, or a pair containing class- and methodlist search selectors.
@@ -49162,165 +49706,183 @@
     |restart dialog|
 
     dialog := SearchDialog new
-        setupToAskForMethodSearchTitle:title
-        forBrowser:self
-        searchWhat:searchWhat
-        searchArea:whereDefault
-        withCaseIgnore:withCaseIgnore
-        withMatch:withMatch
-        withMethodList:withMethodList
-        allowFind:(self navigationState isMethodBrowser)
-        allowBuffer:true
-        allowBrowser:true
-        withTextEntry:withTextEntry.
+	setupToAskForMethodSearchTitle:title
+	forBrowser:self
+	searchWhat:searchWhat
+	searchArea:whereDefault
+	withCaseIgnore:withCaseIgnore
+	withMatch:withMatch
+	withMethodList:withMethodList
+	allowFind:(self navigationState isMethodBrowser)
+	allowBuffer:true
+	allowBrowser:true
+	withTextEntry:withTextEntry.
 
     restart := Signal new.
     restart
-        handle:[:ex |
-            ex restart
-        ]
-        do:[
-            dialog askThenDo:[
-                |classes string ignoreCase openHow match methods isMethod|
-
-                classes := dialog classesToSearch.
-                string := dialog selectorToSearch.
-                ignoreCase := dialog searchIgnoringCase.
-                openHow := dialog openHow.
-                match := dialog searchWithMatch.
-                methods := dialog methodsToSearch.
-                isMethod := dialog matchMethods.
-
-                self withSearchCursorDo:[
-                    |initialList list newBrowser numFound label selector entities arguments numArgs answer
-                     alternativeSelector question altArguments|
-
-                    aSelectorOrBlock isArray ifTrue:[
-                        classes notNil ifTrue:[
-                            selector := aSelectorOrBlock first.
-                            entities := classes.
-                        ] ifFalse:[
-                            selector := aSelectorOrBlock second.
-                            entities := methods.
-                        ].
-                        numArgs := selector numArgs.
-                    ] ifFalse:[
-                        entities := classes.
-                        aSelectorOrBlock isSymbol ifTrue:[
-                            selector := aSelectorOrBlock.
-                        ] ifFalse:[
-                            selector := nil
-                        ].
-                        numArgs := aSelectorOrBlock numArgs.
-                    ].
-                    (selector notNil 
-                    and:[ (selector numArgs == 1) 
-                    and:[ (selector endsWith:'In:') or:[ selector endsWith:'inMethods:' ]]]) ifTrue:[
-                        arguments := Array with:entities
-                    ] ifFalse:[
-                        arguments := (Array
-                                            with:string
-                                            with:entities
-                                            with:((selector notNil and:[selector endsWith:'isMethod:']) ifTrue:[isMethod] ifFalse:[ignoreCase])
-                                            with:match
-                                      ) copyTo:numArgs.
-                    ].
-
-                    selector notNil ifTrue:[
-                        initialList := self class perform:selector withArguments:arguments.
-                    ] ifFalse:[
-                        initialList := aSelectorOrBlock valueWithArguments:arguments
-                    ].
-
-                    label := labelHolderOrBlock value.
-
-                    numFound := initialList size.
-                    numFound == 0 ifTrue:[
-                        question := resources stringWithCRs:label with:((string ? '') allBold colorizeAllWith:Color red darkened).
-                        question := question , (resources string:' - none found.').
-
-                        ((selector == #findImplementors:in:ignoreCase:match:)
-                        and:[ (arguments first numArgs == 0)
-                        and:[
-                                string := ((arguments at:1),':') asSymbol.
-                                altArguments := arguments copy.
-                                altArguments at:1 put:string.
-                                initialList := self class perform:selector withArguments:altArguments.
-                                numFound := initialList size.
-                                numFound ~~ 0
-                        ]]) ifTrue:[
-                            question := question,(resources stringWithCRs:'\\But there are %1 implementations of %2 (with colon).\Browse those ?' with:numFound with:(altArguments first)).
-                            answer := Dialog
-                                confirmWithCancel:question
-                                labels:(resources array:#('Cancel' 'Search Again' 'Yes'))
-                                default:2.
-
-                            answer isNil ifTrue:[
-                                ^ self
-                            ].
-                            answer ifFalse:[
-                                restart raiseRequest
-                            ].
-                            arguments := altArguments.
-
-                        ] ifFalse:[
-                            answer := Dialog
-                                confirm:question
-                                yesLabel:(resources string:'Search Again')
-                                noLabel:(resources string:'Cancel').
-                            answer ifFalse:[
-                                ^ self
-                            ].
-                            restart raiseRequest
-                        ].
-                    ].
-
-                    (initialList asSet = self selectedMethodsValue asSet)
-                    "/ (numFound == 1 and:[initialList first == self theSingleSelectedMethod])
-                    ifTrue:[
-                        answer := Dialog
-                            confirmWithCancel:((resources stringWithCRs:label with:(string ? 'messages') allBold)
-                                               , '.\\' withCRs
-                                               , (resources stringWithCRs:'Only the selected method(s) found.\Browse anyway ?'))
-                            labels:(resources array:#('Cancel' 'Search Again' 'Yes' ))
-                            values:#(nil #again true)
-                            default:2.
-
-                        answer == nil ifTrue:[
-                            ^ self
-                        ].
-                        answer == #again ifTrue:[
-                            restart raiseRequest
-                        ]
-                    ].
-
-                    newBrowser := self
-                                    spawnMethodBrowserForSearch:[
-                                            initialList notNil ifTrue:[
-                                                list := initialList.
-                                                initialList := nil
-                                            ] ifFalse:[
-                                                selector notNil ifTrue:[
-                                                    list := self class perform:selector withArguments:arguments.
-                                                ] ifFalse:[
-                                                    list := aSelectorOrBlock valueWithArguments:arguments
-                                                ].
-                                            ].
-                                            list
-                                        ]
-                                    sortBy:#class
-                                    in:openHow
-                                    label:(resources string:label string with:string).
-
-                    setSearchPatternAction notNil ifTrue:[
-                        setSearchPatternAction value:newBrowser value:string value:((selector notNil and:[selector endsWith:'isMethod:']) ifTrue:[isMethod] ifFalse:[ignoreCase]) value:match.
-                    ].
-                    ^ newBrowser.
-                ].
-            ].
-        ].
-
-    "Modified: / 28-02-2012 / 16:38:36 / cg"
+	handle:[:ex |
+	    ex restart
+	]
+	do:[
+	    dialog askThenDo:[
+		|classes string ignoreCase openHow match methods isMethod searchAction|
+
+		classes := dialog classesToSearch.
+		string := dialog selectorToSearch.
+		ignoreCase := dialog searchIgnoringCase.
+		openHow := dialog openHow.
+		match := dialog searchWithMatch.
+		methods := dialog methodsToSearch.
+		isMethod := dialog matchMethods.
+
+		self withSearchCursorDo:[
+		    |initialList list newBrowser numFound label selector entities arguments numArgs answer
+		     alternativeSelector question altArguments t|
+
+		    aSelectorOrBlock isArray ifTrue:[
+			classes notNil ifTrue:[
+			    selector := aSelectorOrBlock first.
+			    entities := classes.
+			] ifFalse:[
+			    selector := aSelectorOrBlock second.
+			    entities := methods.
+			].
+			numArgs := selector numArgs.
+		    ] ifFalse:[
+			entities := classes.
+			aSelectorOrBlock isSymbol ifTrue:[
+			    selector := aSelectorOrBlock.
+			] ifFalse:[
+			    selector := nil
+			].
+			numArgs := aSelectorOrBlock numArgs.
+		    ].
+		    (selector notNil
+		    and:[ (selector numArgs == 1)
+		    and:[ (selector endsWith:'In:') or:[ selector endsWith:'inMethods:' ]]]) ifTrue:[
+			arguments := Array with:entities
+		    ] ifFalse:[
+			arguments := (Array
+					    with:string
+					    with:entities
+					    with:((selector notNil and:[selector endsWith:'isMethod:']) ifTrue:[isMethod] ifFalse:[ignoreCase])
+					    with:match
+				      ) copyTo:numArgs.
+		    ].
+
+		    searchAction :=
+			[
+			    |result|
+
+			    selector notNil ifTrue:[
+				result := self class perform:selector withArguments:arguments.
+			    ] ifFalse:[
+				result := aSelectorOrBlock valueWithArguments:arguments
+			    ].
+			    result
+			].
+
+		    t := TimeDuration toRun:
+			[
+			    false "classes size > 1" ifTrue:[
+				self
+				    showMessage:'Searching...'
+				    while:[
+					initialList := searchAction value.
+				    ]
+			    ] ifFalse:[
+				initialList := searchAction value.
+			    ].
+			].
+
+		    label := labelHolderOrBlock value.
+
+		    numFound := initialList size.
+		    numFound == 0 ifTrue:[
+			question := resources stringWithCRs:label with:((string ? '') allBold colorizeAllWith:Color red darkened).
+			question := question , (resources string:' - none found.').
+
+			((selector == #findImplementors:in:ignoreCase:match:)
+			and:[ (arguments first numArgs == 0)
+			and:[
+				string := ((arguments at:1),':') asSymbol.
+				altArguments := arguments copy.
+				altArguments at:1 put:string.
+				initialList := self class perform:selector withArguments:altArguments.
+				numFound := initialList size.
+				numFound ~~ 0
+			]]) ifTrue:[
+			    question := question,(resources stringWithCRs:'\\But there are %1 implementations of %2 (with colon).\Browse those ?' with:numFound with:(altArguments first)).
+			    answer := Dialog
+				confirmWithCancel:question
+				labels:(resources array:#('Cancel' 'Search Again' 'Yes'))
+				default:2.
+
+			    answer isNil ifTrue:[
+				^ self
+			    ].
+			    answer ifFalse:[
+				restart raiseRequest
+			    ].
+			    arguments := altArguments.
+
+			] ifFalse:[
+			    answer := Dialog
+				confirm:question
+				yesLabel:(resources string:'Search Again')
+				noLabel:(resources string:'Cancel').
+			    answer ifFalse:[
+				^ self
+			    ].
+			    restart raiseRequest
+			].
+		    ].
+
+		    (initialList asSet = self selectedMethodsValue asSet)
+		    "/ (numFound == 1 and:[initialList first == self theSingleSelectedMethod])
+		    ifTrue:[
+			answer := Dialog
+			    confirmWithCancel:((resources stringWithCRs:label with:(string ? 'messages') allBold)
+					       , '.\\' withCRs
+					       , (resources stringWithCRs:'Only the selected method(s) found.\Browse anyway ?'))
+			    labels:(resources array:#('Cancel' 'Search Again' 'Yes' ))
+			    values:#(nil #again true)
+			    default:2.
+
+			answer == nil ifTrue:[
+			    ^ self
+			].
+			answer == #again ifTrue:[
+			    restart raiseRequest
+			]
+		    ].
+
+		    newBrowser := self
+				    spawnMethodBrowserForSearch:[
+					    initialList notNil ifTrue:[
+						list := initialList.
+						initialList := nil
+					    ] ifFalse:[
+						list := searchAction value
+					    ].
+					    list
+					]
+				    sortBy:#class
+				    in:openHow
+				    label:(resources string:label string with:string).
+
+		    setSearchPatternAction notNil ifTrue:[
+			setSearchPatternAction value:newBrowser value:string value:((selector notNil and:[selector endsWith:'isMethod:']) ifTrue:[isMethod] ifFalse:[ignoreCase]) value:match.
+		    ].
+		    t > 5 seconds ifTrue:[
+			newBrowser methodListApp autoUpdateOnChange: false.
+		    ].
+		    ^ newBrowser.
+		].
+	    ].
+	].
+
+    "Modified: / 01-06-2012 / 22:47:41 / cg"
 !
 
 askForMethodAndSpawnSearchTitle:title browserLabel:labelHolderOrBlock searchWith:aSelectorOrBlock searchWhat:searchWhat searchArea:whereDefault
@@ -49328,38 +49890,38 @@
     "convenient helper method: setup an enterBox with text from codeView or selected
      method for browsing based on a selector. Set action and launch box.
      SearchArea may be one of
-        #everywhere,
-        #currentNameSpace
-        #currentClassesNameSpace
-        #classCategories
-        #classes
-        #classesWithPrivateClasses
-        #classHierarchies
-        #classHierarchiesWithPrivateClasses"
+	#everywhere,
+	#currentNameSpace
+	#currentClassesNameSpace
+	#classCategories
+	#classes
+	#classesWithPrivateClasses
+	#classHierarchies
+	#classHierarchiesWithPrivateClasses"
 
     ^self
-        askForMethodAndSpawnSearchTitle:title
-        browserLabel:labelHolderOrBlock
-        searchWith:aSelectorOrBlock
-        searchWhat:searchWhat
-        searchArea:whereDefault
-        withCaseIgnore:withCaseIgnore
-        withTextEntry:withTextEntry
-        withMatch:true
-        withMethodList:withMethodList
-        setSearchPattern:setSearchPatternAction
+	askForMethodAndSpawnSearchTitle:title
+	browserLabel:labelHolderOrBlock
+	searchWith:aSelectorOrBlock
+	searchWhat:searchWhat
+	searchArea:whereDefault
+	withCaseIgnore:withCaseIgnore
+	withTextEntry:withTextEntry
+	withMatch:true
+	withMethodList:withMethodList
+	setSearchPattern:setSearchPatternAction
 !
 
 askForMethodCategory:question title:boxTitle okLabel:okLabel list:someCategories initialAnswer:initialText
     "convenient helper method: setup a box asking for a method category"
 
     ^ self
-        askForMethodCategory:question
-        title:boxTitle
-        okLabel:okLabel
-        list:someCategories
-        recentList:nil
-        initialAnswer:initialText
+	askForMethodCategory:question
+	title:boxTitle
+	okLabel:okLabel
+	list:someCategories
+	recentList:nil
+	initialAnswer:initialText
 !
 
 askForMethodCategory:title title:boxTitle okLabel:okLabel list:someCategories recentList:recentListOrNil initialAnswer:initialText
@@ -49368,39 +49930,39 @@
     |box retVal shownCategories allMethodCategories|
 
     box := self
-            listBoxTitle:title
-            okText:okLabel
-            list:someCategories.
+	    listBoxTitle:title
+	    okText:okLabel
+	    list:someCategories.
     box label:boxTitle.
 
     recentListOrNil notNil ifTrue:[
-        box useComboBoxWithList:recentListOrNil.
+	box useComboBoxWithList:recentListOrNil.
     ].
     shownCategories := someCategories.
     box initialText:initialText.
     box action:[:aString | aString notEmpty ifTrue:[retVal := aString] ].
     box entryCompletionBlock:[:contents |
-        |s what best idx|
-
-        s := contents withoutLeadingSeparators.
-        what := self navigationState environment methodProtocolCompletion:s.
-        best := what first.
-        box contents:best.
-        idx := shownCategories findFirst:[:l | l startsWith:best].
-        idx == 0 ifTrue:[
-            allMethodCategories isNil ifTrue:[
-                allMethodCategories := Smalltalk allMethodCategories asArray sort.
-            ].
-            box list:allMethodCategories.
-            shownCategories := allMethodCategories.
-            idx := shownCategories findFirst:[:l | l startsWith:best].
-        ].
-        idx ~~ 0 ifTrue:[
-            box listView scrollToLine:idx.
-        ].
-        (what at:2) size ~~ 1 ifTrue:[
-            self builder window beep
-        ].
+	|s what best idx|
+
+	s := contents withoutLeadingSeparators.
+	what := self navigationState environment methodProtocolCompletion:s.
+	best := what first.
+	box contents:best.
+	idx := shownCategories findFirst:[:l | l startsWith:best].
+	idx == 0 ifTrue:[
+	    allMethodCategories isNil ifTrue:[
+		allMethodCategories := Smalltalk allMethodCategories asArray sort.
+	    ].
+	    box list:allMethodCategories.
+	    shownCategories := allMethodCategories.
+	    idx := shownCategories findFirst:[:l | l startsWith:best].
+	].
+	idx ~~ 0 ifTrue:[
+	    box listView scrollToLine:idx.
+	].
+	(what at:2) size ~~ 1 ifTrue:[
+	    self builder window beep
+	].
     ].
     box open.
     ^ retVal
@@ -49420,39 +49982,39 @@
     meta := cls isMeta.
     "/ do not include above Class if meta.
     cls theNonMetaclass withAllSuperclassesDo:[:eachNonMetaClass |
-        |eachClass|
-
-        eachClass := eachNonMetaClass.
-        meta ifTrue:[eachClass := eachNonMetaClass theMetaclass].
-
-        someCategories addAll:eachClass categories.
-        methodCategoryListApp notNil ifTrue:[
-            someCategories addAll:(methodCategoryListApp additionalProtocolForClass:eachClass).
-        ]
+	|eachClass|
+
+	eachClass := eachNonMetaClass.
+	meta ifTrue:[eachClass := eachNonMetaClass theMetaclass].
+
+	someCategories addAll:eachClass categories.
+	methodCategoryListApp notNil ifTrue:[
+	    someCategories addAll:(methodCategoryListApp additionalProtocolForClass:eachClass).
+	]
     ].
     someCategories := someCategories asOrderedCollection sort.
 
     "/ look for inherited; default to that category
     selectorOrNil notNil ifTrue:[
-        inheritedMethod := cls lookupMethodFor:selectorOrNil.
-        inheritedMethod notNil ifTrue:[
-            initial := inheritedMethod category
-        ]
+	inheritedMethod := cls lookupMethodFor:selectorOrNil.
+	inheritedMethod notNil ifTrue:[
+	    initial := inheritedMethod category
+	]
     ].
     initial isNil ifTrue:[
-        lastMethodCategory isNil ifTrue:[
-            initial := Compiler defaultMethodCategory "/ 'new methods' '* As yet uncategorized *'
-        ] ifFalse:[
-            initial := lastMethodCategory
-        ].
-    ].
-
-    ^ self
-        askForMethodCategory:'Accept in which method category ?'
-        title:'Methods Category'
-        okLabel:'Accept'
-        list:someCategories
-        initialAnswer:initial
+	lastMethodCategory isNil ifTrue:[
+	    initial := Compiler defaultMethodCategory "/ 'new methods' '* As yet uncategorized *'
+	] ifFalse:[
+	    initial := lastMethodCategory
+	].
+    ].
+
+    ^ self
+	askForMethodCategory:'Accept in which method category ?'
+	title:'Methods Category'
+	okLabel:'Accept'
+	list:someCategories
+	initialAnswer:initial
 
     "Created: / 29.2.2000 / 10:50:38 / cg"
     "Modified: / 29.2.2000 / 10:54:26 / cg"
@@ -49461,10 +50023,10 @@
 askForNameSpace:title title:boxTitle initialText:initialTextOrNil
     "Ask for the new namespaces name"
 
-    ^ Dialog 
-        requestNameSpace:title 
-        title:boxTitle 
-        initialAnswer:initialTextOrNil
+    ^ Dialog
+	requestNameSpace:title
+	title:boxTitle
+	initialAnswer:initialTextOrNil
 
     "Modified: / 11-02-2011 / 11:26:25 / cg"
 !
@@ -49496,20 +50058,20 @@
 
     selectedClasses := self selectedClassesValue.
     selectedClasses notNil ifTrue:[
-        classesProjects := selectedClasses
-                            collectAll:[:cls |
-                                (cls methodDictionary values
-                                    collect:[:m | m package ]) asSet ].
-    ] ifFalse:[
-        selectedMethods := self selectedMethodsValue.
-        selectedMethods notEmptyOrNil ifTrue:[
-            classesProjects := selectedMethods
-                                collectAll:[:mthd |
-                                    (mthd mclass methodDictionary values
-                                        collect:[:m | m package ]) asSet ].
-        ] ifFalse:[
-            classesProjects := #()
-        ]
+	classesProjects := selectedClasses
+			    collectAll:[:cls |
+				(cls methodDictionary values
+				    collect:[:m | m package ]) asSet ].
+    ] ifFalse:[
+	selectedMethods := self selectedMethodsValue.
+	selectedMethods notEmptyOrNil ifTrue:[
+	    classesProjects := selectedMethods
+				collectAll:[:mthd |
+				    (mthd mclass methodDictionary values
+					collect:[:m | m package ]) asSet ].
+	] ifFalse:[
+	    classesProjects := #()
+	]
     ].
     classesProjects remove:(PackageId noProjectID) ifAbsent:nil.
     classesProjects removeAllFoundIn:(moreSuggestions ? #()).
@@ -49519,18 +50081,18 @@
     offered := OrderedCollection new.
     already := Set new.
     (moreSuggestions ? #()) do:[:p |
-        (already includes:p) ifFalse:[ offered add:p]
+	(already includes:p) ifFalse:[ offered add:p]
     ].
     (LastProjectMoves ? #()) do:[:p |
-        (already includes:p) ifFalse:[ offered add:p]
+	(already includes:p) ifFalse:[ offered add:p]
     ].
     classesProjects do:[:p |
-        (already includes:p) ifFalse:[ offered add:p]
+	(already includes:p) ifFalse:[ offered add:p]
     ].
     ^ Dialog
-        requestProject:((resources ? self class classResources) string:title)
-        initialAnswer:initialTextOrNil
-        suggestions:offered
+	requestProject:((resources ? self class classResources) string:title)
+	initialAnswer:initialTextOrNil
+	suggestions:offered
 
     "Created: / 11-08-2006 / 13:31:34 / cg"
     "Modified: / 28-02-2012 / 16:45:05 / cg"
@@ -49548,25 +50110,25 @@
     selectors := Set new.
     methods := self selectedMethodsValue.
     methods notEmptyOrNil ifTrue:[
-        firstMethod := methods first.
-        firstSelector := firstMethod selector.
+	firstMethod := methods first.
+	firstSelector := firstMethod selector.
     ].
     searchClass := self theSingleSelectedClass ? self classHierarchyTopClass value.
     searchClass isNil ifTrue:[
-        self theSingleSelectedMethod notNil ifTrue:[
-            searchClass := self theSingleSelectedMethod mclass
-        ]
+	self theSingleSelectedMethod notNil ifTrue:[
+	    searchClass := self theSingleSelectedMethod mclass
+	]
     ].
     searchClass notNil ifTrue:[
-        searchClass withAllSuperclassesDo:[:cls |
-            selectors addAll:(cls methodDictionary keys copy)
-        ]
+	searchClass withAllSuperclassesDo:[:cls |
+	    selectors addAll:(cls methodDictionary keys copy)
+	]
     ].
     selectors := selectors asOrderedCollection sort.
-    listInBox := selectors 
-                    collect:[:eachSel | eachSel , (' [ ' , (searchClass whichClassIncludesSelector:eachSel) name , ' ]')].
+    listInBox := selectors
+		    collect:[:eachSel | eachSel , (' [ ' , (searchClass whichClassIncludesSelector:eachSel) name , ' ]')].
     UserPreferences current avoidSlowDrawingOperationsUnderWindows ifFalse:[
-        listInBox := listInBox collect:[:eachEntry | eachEntry allItalic].
+	listInBox := listInBox collect:[:eachEntry | eachEntry allItalic].
     ].
 
     box := ListSelectionBox new.
@@ -49582,54 +50144,54 @@
 "/    ].
     selector := self selectorToSearchFor.
     selector isNil ifTrue:[
-        selector := firstSelector
+	selector := firstSelector
     ].
     box initialText:selector.
     box entryCompletionBlock:[:contents |
-        |s what longest matching|
-
-        box topView withWaitCursorDo:[
-            s := contents withoutSpaces.
-            what := Smalltalk selectorCompletion:s.
-            longest := what first.
-            matching := what last.
-            box list:matching.
-            box contents:longest.
-            matching size ~~ 1 ifTrue:[
-                self window beep
-            ]
-        ]
+	|s what longest matching|
+
+	box topView withWaitCursorDo:[
+	    s := contents withoutSpaces.
+	    what := Smalltalk selectorCompletion:s.
+	    longest := what first.
+	    matching := what last.
+	    box list:matching.
+	    box contents:longest.
+	    matching size ~~ 1 ifTrue:[
+		self window beep
+	    ]
+	]
     ].
 
     box okText:(resources string:'Find').
     allowBuffer ifTrue:[
-        b := Button label:(resources string:'Add Buffer').
-        (DialogBox defaultOKButtonAtLeft) ifFalse:[
-            box addButton:b before:box okButton.
-        ] ifTrue:[
-            box addButton:b before:nil.
-        ].
-        b action:[
-           openHow := #newBuffer.
-           box doAccept.
-           box okPressed.
-        ].
-        prevButton := b.
+	b := Button label:(resources string:'Add Buffer').
+	(DialogBox defaultOKButtonAtLeft) ifFalse:[
+	    box addButton:b before:box okButton.
+	] ifTrue:[
+	    box addButton:b before:nil.
+	].
+	b action:[
+	   openHow := #newBuffer.
+	   box doAccept.
+	   box okPressed.
+	].
+	prevButton := b.
     ].
 
     allowBrowser ifTrue:[
-        b := Button label:(resources string:'Browse').
-        (DialogBox defaultOKButtonAtLeft) ifFalse:[
-            box addButton:b before:box okButton.
-        ] ifTrue:[
-            box addButton:b before:nil.
-        ].
-        b action:[
-           openHow := #newBrowser.
-           box doAccept.
-           box okPressed.
-        ].
-        prevButton := b.
+	b := Button label:(resources string:'Browse').
+	(DialogBox defaultOKButtonAtLeft) ifFalse:[
+	    box addButton:b before:box okButton.
+	] ifTrue:[
+	    box addButton:b before:nil.
+	].
+	b action:[
+	   openHow := #newBrowser.
+	   box doAccept.
+	   box okPressed.
+	].
+	prevButton := b.
     ].
     "/ prevButton notNil ifTrue:[prevButton isReturnButton:true].
 
@@ -49638,7 +50200,7 @@
     box showAtPointer.
 
     selector notNil ifTrue:[
-        aBlock value:selector asSymbol value:openHow
+	aBlock value:selector asSymbol value:openHow
     ].
     ^ selector
 
@@ -49664,10 +50226,10 @@
      otherwise, return true"
 
     ^ self
-        askIfModified:question
-        default:default
-        withAccept:(self canAcceptCode)
-        withCompare:(self canCompareCode)
+	askIfModified:question
+	default:default
+	withAccept:(self canAcceptCode)
+	withCompare:(self canCompareCode)
 
     "Created: / 11.2.2000 / 10:52:28 / cg"
     "Modified: / 11.2.2000 / 12:37:34 / cg"
@@ -49678,11 +50240,11 @@
      otherwise, return true"
 
     ^ self
-        askIfModified:question
-        default:default
-        withAccept:(self canAcceptCode)
-        withCompare:(self canCompareCode)
-        in:aNavigationState
+	askIfModified:question
+	default:default
+	withAccept:(self canAcceptCode)
+	withCompare:(self canCompareCode)
+	in:aNavigationState
 
     "Created: / 11.2.2000 / 10:52:28 / cg"
     "Modified: / 11.2.2000 / 12:37:34 / cg"
@@ -49691,10 +50253,10 @@
 askIfModified:question default:default withAccept:acceptOffered withCompare:compareOffered
     "if codeView was not modified, return true.
      If it was, return the answer from asking question, which can be
-        true     - go on
-        false    - cancel
-        #compare - open a diff-viewer on the code vs. its original
-        #accept  - accept, then proceed
+	true     - go on
+	false    - cancel
+	#compare - open a diff-viewer on the code vs. its original
+	#accept  - accept, then proceed
      If compareOffered is true, offer the compare option.
      If acceptOffered is true, offer the accept option.
      Used to confirm selectionChange, closing or buffer removal when code
@@ -49702,11 +50264,11 @@
      question is the message to ask, or nil for a standard message."
 
     ^ self
-        askIfModified:question
-        default:default
-        withAccept:acceptOffered
-        withCompare:compareOffered
-        in:navigationState
+	askIfModified:question
+	default:default
+	withAccept:acceptOffered
+	withCompare:compareOffered
+	in:navigationState
 
 
 !
@@ -49714,8 +50276,8 @@
 askIfModified:question default:default withAccept:acceptOffered withCompare:compareOffered in:aNavigationState
     "if codeView was not modified, return true.
      If it was, return the answer from asking question, which can be
-        true     - go on
-        false    - cancel
+	true     - go on
+	false    - cancel
      If compareOffered is true, offer the compare option.
      If acceptOffered is true, offer the accept option.
      Used to confirm selectionChange, closing or buffer removal when code was modified.
@@ -49724,8 +50286,8 @@
     |answer labels values msg textModified specialEditorModified|
 
     self codeView isNil ifTrue:[
-        "/ if in documentation browser ...
-        ^ true
+	"/ if in documentation browser ...
+	^ true
     ].
 
     specialEditorModified := self anySpecialEditorModified.
@@ -49734,52 +50296,52 @@
 
     (specialEditorModified not
     and:[ textModified not ]) ifTrue:[
-        ^ true
+	^ true
     ].
 
     (compareOffered and:[ specialEditorModified not ]) ifTrue:[
-        acceptOffered ifTrue:[
-            labels := #('Cancel' 'Compare' 'Accept' 'Continue').
-            values := #(false #compare #accept true).
-        ] ifFalse:[
-            labels := #('Cancel' 'Compare' 'Continue').
-            values := #(false #compare true).
-        ]
-    ] ifFalse:[
-        acceptOffered ifTrue:[
-            labels := #('Cancel' 'Accept' 'Continue').
-            values := #(false #accept true).
-        ] ifFalse:[
-            labels := #('Cancel' 'Continue').
-            values := #(false true).
-        ].
+	acceptOffered ifTrue:[
+	    labels := #('Cancel' 'Compare' 'Accept' 'Continue').
+	    values := #(false #compare #accept true).
+	] ifFalse:[
+	    labels := #('Cancel' 'Compare' 'Continue').
+	    values := #(false #compare true).
+	]
+    ] ifFalse:[
+	acceptOffered ifTrue:[
+	    labels := #('Cancel' 'Accept' 'Continue').
+	    values := #(false #accept true).
+	] ifFalse:[
+	    labels := #('Cancel' 'Continue').
+	    values := #(false true).
+	].
     ].
 
     msg := question ? 'Modifications have not been saved.\\Your changes will be lost when continuing.'.
     answer := OptionBox
-                  request:(resources string:msg) withCRs
-                  label:(resources string:'Attention')
-                  image:(WarningBox iconBitmap)
-                  buttonLabels:(resources array:labels)
-                  values:values
-                  default:default
-                  onCancel:false.
+		  request:(resources string:msg) withCRs
+		  label:(resources string:'Attention')
+		  image:(WarningBox iconBitmap)
+		  buttonLabels:(resources array:labels)
+		  values:values
+		  default:default
+		  onCancel:false.
 
     answer == #accept ifTrue:[
 "/ self halt.
-        specialEditorModified ifTrue:[
-            self doSaveInSpecialEditors
-        ] ifFalse:[
-            self doAcceptCodeIn:aNavigationState.
-        ].
-        ^ true
+	specialEditorModified ifTrue:[
+	    self doSaveInSpecialEditors
+	] ifFalse:[
+	    self doAcceptCodeIn:aNavigationState.
+	].
+	^ true
     ].
     answer == #compare ifTrue:[
-        self doCompareIn:aNavigationState.
-        ^ false.
+	self doCompareIn:aNavigationState.
+	^ false.
     ].
     answer ifTrue:[
-        navigationState modified:false.
+	navigationState modified:false.
     ].
     ^ answer
 
@@ -49805,88 +50367,88 @@
 
     sel := self selectionInCodeView.
     sel notNil ifTrue:[
-        self selectedNamespacesValue doWithExit:[:eachNs :exit |
-            s := eachNs , '::' , sel asSymbol.
-            (s knownAsSymbol
-            and:[(Smalltalk at:s asSymbol) isBehavior]) ifTrue:[
-                "/ a private class of current ...
-                sel := eachNs , '::' , sel asSymbol.
-                exit value:nil.
-            ].
-        ].
-        (sel knownAsSymbol and:[currentClass notNil
-        and:[(currentClass theNonMetaclass privateClassesAt:sel asSymbol) notNil]]) ifTrue:[
-            "/ a private class of current ...
-            sel := (currentClass theNonMetaclass privateClassesAt:sel asSymbol) name
-        ] ifFalse:[
-            (sel knownAsSymbol and:[(Smalltalk at:sel asSymbol) isBehavior]) ifFalse:[
-                "/ ignore it, if there is no class-name which comes close.
-                anyClose := false.
-                Smalltalk keysAndValuesDo:[:aGlobalName :aGlobal|
-                    aGlobal isBehavior ifTrue:[
-                        aGlobal isMeta ifFalse:[
-                            aGlobal name == aGlobalName ifTrue:[
-                                ((aGlobalName startsWith:sel)
-                                or:[(sel startsWith:aGlobalName)]) ifTrue:[
-                                    closeName isNil ifTrue:[closeName := aGlobalName].
-                                    anyClose := true.
-                                ]
-                            ]
-                        ]
-                    ]
-                ].
-                anyClose ifFalse:[
-                    sel := nil
-                ] ifTrue:[
-                    sel := closeName
-                ]
-            ]
-        ]
+	self selectedNamespacesValue doWithExit:[:eachNs :exit |
+	    s := eachNs , '::' , sel asSymbol.
+	    (s knownAsSymbol
+	    and:[(Smalltalk at:s asSymbol) isBehavior]) ifTrue:[
+		"/ a private class of current ...
+		sel := eachNs , '::' , sel asSymbol.
+		exit value:nil.
+	    ].
+	].
+	(sel knownAsSymbol and:[currentClass notNil
+	and:[(currentClass theNonMetaclass privateClassesAt:sel asSymbol) notNil]]) ifTrue:[
+	    "/ a private class of current ...
+	    sel := (currentClass theNonMetaclass privateClassesAt:sel asSymbol) name
+	] ifFalse:[
+	    (sel knownAsSymbol and:[(Smalltalk at:sel asSymbol) isBehavior]) ifFalse:[
+		"/ ignore it, if there is no class-name which comes close.
+		anyClose := false.
+		Smalltalk keysAndValuesDo:[:aGlobalName :aGlobal|
+		    aGlobal isBehavior ifTrue:[
+			aGlobal isMeta ifFalse:[
+			    aGlobal name == aGlobalName ifTrue:[
+				((aGlobalName startsWith:sel)
+				or:[(sel startsWith:aGlobalName)]) ifTrue:[
+				    closeName isNil ifTrue:[closeName := aGlobalName].
+				    anyClose := true.
+				]
+			    ]
+			]
+		    ]
+		].
+		anyClose ifFalse:[
+		    sel := nil
+		] ifTrue:[
+		    sel := closeName
+		]
+	    ]
+	]
     ].
 
     sel notNil ifTrue:[
-        initialText := sel asString withoutSeparators
-    ] ifFalse:[
-        self codeAspect == #method ifTrue:[
-            methods := self selectedMethodsValue.
-            methods size > 0 ifTrue:[
-                someMethod := methods first.
-                usedGlobals := someMethod usedGlobals collect:[:eachVar | eachVar asSymbol].
-                usedGlobals := usedGlobals select:[:eachVar | (Smalltalk at:eachVar) isBehavior].
-                usedGlobals size > 0 ifTrue:[
-                    list := list reject:[:each | usedGlobals includes:each ].
-                    list := usedGlobals asOrderedCollection sort , list.
-                    offeredClass := Smalltalk at:usedGlobals first
-                ] ifFalse:[
-                    offeredClass := someMethod mclass
-                ]
-            ]
-        ] ifFalse:[
-            (navigationState isVersionDiffBrowser
-            or:[navigationState isClassDocumentationBrowser]) ifTrue:[
-                offeredClass := currentClass.
-                (offeredClass notNil and:[offeredClass isPrivate]) ifTrue:[
-                    offeredClass := offeredClass owningClass
-                ]
-            ] ifFalse:[
-                (currentClass notNil
-                and:[(superclass := currentClass superclass) notNil]) ifTrue:[
-                    offeredClass := superclass
-                ]
-            ]
-        ].
-        offeredClass notNil ifTrue:[
-            initialText := offeredClass theNonMetaclass name
-        ]
+	initialText := sel asString withoutSeparators
+    ] ifFalse:[
+	self codeAspect == #method ifTrue:[
+	    methods := self selectedMethodsValue.
+	    methods size > 0 ifTrue:[
+		someMethod := methods first.
+		usedGlobals := someMethod usedGlobals collect:[:eachVar | eachVar asSymbol].
+		usedGlobals := usedGlobals select:[:eachVar | (Smalltalk at:eachVar) isBehavior].
+		usedGlobals size > 0 ifTrue:[
+		    list := list reject:[:each | usedGlobals includes:each ].
+		    list := usedGlobals asOrderedCollection sort , list.
+		    offeredClass := Smalltalk at:usedGlobals first
+		] ifFalse:[
+		    offeredClass := someMethod mclass
+		]
+	    ]
+	] ifFalse:[
+	    (navigationState isVersionDiffBrowser
+	    or:[navigationState isClassDocumentationBrowser]) ifTrue:[
+		offeredClass := currentClass.
+		(offeredClass notNil and:[offeredClass isPrivate]) ifTrue:[
+		    offeredClass := offeredClass owningClass
+		]
+	    ] ifFalse:[
+		(currentClass notNil
+		and:[(superclass := currentClass superclass) notNil]) ifTrue:[
+		    offeredClass := superclass
+		]
+	    ]
+	].
+	offeredClass notNil ifTrue:[
+	    initialText := offeredClass theNonMetaclass name
+	]
     ].
 
     box := self
-                enterBoxTitle:((resources ? self class classResources) string:title)
-                withList:list
-                okText:((resources ? self class classResources) string:okText).
+		enterBoxTitle:((resources ? self class classResources) string:title)
+		withList:list
+		okText:((resources ? self class classResources) string:okText).
 
     initialText notNil ifTrue:[
-        box initialText:initialText
+	box initialText:initialText
     ].
     ^ box
 
@@ -49898,7 +50460,7 @@
     "convenient method: setup enterBox with text from codeview"
 
     ^ self
-        enterBoxForCodeSelectionTitle:title withList:nil okText:okText
+	enterBoxForCodeSelectionTitle:title withList:nil okText:okText
 !
 
 enterBoxForCodeSelectionTitle:title withList:listOrNil okText:okText
@@ -49907,42 +50469,50 @@
     |sel box initialText|
 
     box := self
-                enterBoxTitle:(resources string:title)
-                withList:listOrNil
-                okText:(resources string:okText).
+		enterBoxTitle:(resources string:title)
+		withList:listOrNil
+		okText:(resources string:okText).
 
     sel := self codeView selection.
     sel notNil ifTrue:[
-        initialText := sel asString string withoutSeparators
+	initialText := sel asString string withoutSeparators
     ].
     initialText notNil ifTrue:[
-        box initialText:initialText
+	box initialText:initialText
     ].
     ^ box
 !
 
 enterBoxForVariableSearch:title
+    ^ self enterBoxForVariableSearch:title list:nil
+
+    "Modified: / 29-05-2012 / 11:59:35 / cg"
+!
+
+enterBoxForVariableSearch:title list:listOrNil
     |box sel selectedVariables|
 
-    box := self enterBoxForCodeSelectionTitle:title okText:'Add Buffer'.
+    box := self enterBoxForCodeSelectionTitle:title withList:listOrNil okText:'Add Buffer'.
 
     self codeView hasSelection ifTrue:[
-        sel := self selectionInCodeView.
-        sel size > 0 ifTrue:[
-            sel := sel withoutSeparators.
-            sel asCollectionOfWords size == 1 ifFalse:[
-                sel := nil
-            ]
-        ]
+	sel := self selectionInCodeView.
+	sel size > 0 ifTrue:[
+	    sel := sel withoutSeparators.
+	    sel asCollectionOfWords size == 1 ifFalse:[
+		sel := nil
+	    ]
+	]
     ].
     sel size == 0 ifTrue:[
-        selectedVariables := self variableFilter value.
-        selectedVariables size > 0 ifTrue:[
-            box initialText:(selectedVariables asStringCollection asStringWith:Character space)
-        ]
+	selectedVariables := self variableFilter value.
+	selectedVariables size > 0 ifTrue:[
+	    box initialText:(selectedVariables asStringCollection asStringWith:Character space)
+	]
     ].
 
     ^ box
+
+    "Created: / 29-05-2012 / 11:59:21 / cg"
 !
 
 enterBoxTitle:title okText:okText label:label
@@ -49953,7 +50523,7 @@
     box := EnterBox new.
     box label:(resources string:label).
     box title:(resources string:title)
-        okText:(resources string:okText).
+	okText:(resources string:okText).
     ^ box
 
 
@@ -49965,11 +50535,11 @@
     |box rsrcs|
 
     aListOrNil notNil ifTrue:[
-        box := ListSelectionBox new.
-        "/ box := EnterBoxWithList new.
-        box list:aListOrNil.
-    ] ifFalse:[
-        box := EnterBox new.
+	box := ListSelectionBox new.
+	"/ box := EnterBoxWithList new.
+	box list:aListOrNil.
+    ] ifFalse:[
+	box := EnterBox new.
     ].
     rsrcs := (resources ? self class classResources).
     box title:(rsrcs string:title) okText:(rsrcs string:okText).
@@ -49987,13 +50557,13 @@
     box := self listBoxTitle:title okText:okText list:nil.
     sel := self codeView selection.
     sel notNil ifTrue:[
-        sel := sel asString string withoutSeparators.
-        isSelector ifTrue:[
-            sel knownAsSymbol ifFalse:[
-                sel := SystemBrowser extractSelectorFrom:sel
-            ].
-        ].
-        box initialText:sel
+	sel := sel asString string withoutSeparators.
+	isSelector ifTrue:[
+	    sel knownAsSymbol ifFalse:[
+		sel := SystemBrowser extractSelectorFrom:sel
+	    ].
+	].
+	box initialText:sel
     ].
     ^ box
 !
@@ -50016,9 +50586,9 @@
     title := 'class to add to list (Tab to complete or use matchPattern):'.
 
     box := self
-                enterBoxForClassWithCodeSelectionTitle:title
-                withList:(self class visitedClassNamesHistory)
-                okText:'add'.
+		enterBoxForClassWithCodeSelectionTitle:title
+		withList:(self class visitedClassNamesHistory)
+		okText:'add'.
 
     box label:(resources string:'add class to list').
     box entryCompletionBlock:(DoWhatIMeanSupport classNameEntryCompletionBlock).
@@ -50037,13 +50607,13 @@
     subclasses isEmpty ifTrue: [^#()].
 
     ^Dialog
-            chooseMultiple: 'Choose Subclasses:'
-            fromList: subclasses
-            values: subclasses
-            buttons: #()
-            values: #()
-            lines: 8
-            cancel: [nil]
+	    chooseMultiple: 'Choose Subclasses:'
+	    fromList: subclasses
+	    values: subclasses
+	    buttons: #()
+	    values: #()
+	    lines: 8
+	    cancel: [nil]
 ! !
 
 !NewSystemBrowser methodsFor:'private-helpers'!
@@ -50078,53 +50648,53 @@
     aClassName isNil ifTrue:[^ nil].
     class := Smalltalk classNamed:aClassName.
     class isNil ifTrue:[
-        selectedClass := self theSingleSelectedClass.
-        selectedClass notNil ifTrue:[
-            selectedClass isPrivate ifTrue:[
-                class := (selectedClass owningClass privateClassesAt:aClassName).
-                class notNil ifTrue:[
-                    (self confirm:(resources
-                                    string:'No class named: %1 exists (in Smalltalk).\\Do you mean the private class %1 in %2 ?'
-                                    with:aClassName allBold with:selectedClass owningClass name allBold) withCRs)
-                    ifTrue:[
-                        ^ class
-                    ].
-                    ^ nil.
-                ].
-            ].
-            (ns := selectedClass nameSpace) isNameSpace ifTrue:[
-                ns ~~ Smalltalk ifTrue:[
-                    class := ns at:aClassName.
-                    class notNil ifTrue:[
-                        (self confirm:(resources
-                                        string:'No class named: %1 exists (in Smalltalk).\\Do you mean the class %1 in namespace %2 ?'
-                                        with:aClassName allBold with:ns name allBold) withCRs)
-                        ifTrue:[
-                            ^ class
-                        ].
-                        ^ nil.
-                    ].
-                ]
-            ].
-        ].
-
-
-        self warn:'No such class: ', aClassName.
-        ^ nil
+	selectedClass := self theSingleSelectedClass.
+	selectedClass notNil ifTrue:[
+	    selectedClass isPrivate ifTrue:[
+		class := (selectedClass owningClass privateClassesAt:aClassName).
+		class notNil ifTrue:[
+		    (self confirm:(resources
+				    string:'No class named: %1 exists (in Smalltalk).\\Do you mean the private class %1 in %2 ?'
+				    with:aClassName allBold with:selectedClass owningClass name allBold) withCRs)
+		    ifTrue:[
+			^ class
+		    ].
+		    ^ nil.
+		].
+	    ].
+	    (ns := selectedClass nameSpace) isNameSpace ifTrue:[
+		ns ~~ Smalltalk ifTrue:[
+		    class := ns at:aClassName.
+		    class notNil ifTrue:[
+			(self confirm:(resources
+					string:'No class named: %1 exists (in Smalltalk).\\Do you mean the class %1 in namespace %2 ?'
+					with:aClassName allBold with:ns name allBold) withCRs)
+			ifTrue:[
+			    ^ class
+			].
+			^ nil.
+		    ].
+		]
+	    ].
+	].
+
+
+	self warn:'No such class: ', aClassName.
+	^ nil
     ].
     class isBehavior ifFalse:[
-        self warn:'Not a class: ', aClassName.
-        ^ nil
+	self warn:'Not a class: ', aClassName.
+	^ nil
     ].
     (class isNameSpace
     and:[class ~~ Smalltalk]) ifTrue:[
-        self warn:'Is a nameSpace: ', aClassName.
-        ^ nil
+	self warn:'Is a nameSpace: ', aClassName.
+	^ nil
     ].
     (class theNonMetaclass isNameSpace
     and:[class theNonMetaclass ~~ Smalltalk]) ifTrue:[
-        self warn:'Is meta of a nameSpace: ', aClassName.
-        ^ nil
+	self warn:'Is meta of a nameSpace: ', aClassName.
+	^ nil
     ].
     ^ class
 !
@@ -50141,24 +50711,24 @@
      pass the non-metaclass as arg"
 
     aCollectionOfClasses do:[:aClass |
-        |cls|
-
-        cls := aClass theNonMetaclass.
-        cls isLoaded ifFalse:[
-            (unloadedBlock value:cls) ifTrue:[
-                cls owningClass notNil ifTrue:[
-                    privateBlock value:cls
-                ] ifFalse:[
-                    aBlock value:cls
-                ]
-            ]
-        ] ifTrue:[
-            cls owningClass notNil ifTrue:[
-                privateBlock value:cls
-            ] ifFalse:[
-                aBlock value:cls
-            ]
-        ]
+	|cls|
+
+	cls := aClass theNonMetaclass.
+	cls isLoaded ifFalse:[
+	    (unloadedBlock value:cls) ifTrue:[
+		cls owningClass notNil ifTrue:[
+		    privateBlock value:cls
+		] ifFalse:[
+		    aBlock value:cls
+		]
+	    ]
+	] ifTrue:[
+	    cls owningClass notNil ifTrue:[
+		privateBlock value:cls
+	    ] ifFalse:[
+		aBlock value:cls
+	    ]
+	]
     ]
 !
 
@@ -50169,10 +50739,10 @@
 
     classes := self selectedClassesValue copy.
     classes size == 0 ifTrue:[
-        self isMethodListBrowser ifTrue:[
-            classes := ((self selectedMethodsClasses)
-                            collect:[:each| each theNonMetaclass]) asIdentitySet.
-        ]
+	self isMethodListBrowser ifTrue:[
+	    classes := ((self selectedMethodsClasses)
+			    collect:[:each| each theNonMetaclass]) asIdentitySet.
+	]
     ].
     ^ classes
 
@@ -50195,16 +50765,16 @@
 
 fileSuffixForClass:aClass format:formatSymbolOrNil
     formatSymbolOrNil == #sif ifTrue:[
-        ^ 'sif'.
+	^ 'sif'.
     ].
     formatSymbolOrNil == #xml ifTrue:[
-        ^ 'xml'.
+	^ 'xml'.
     ].
     formatSymbolOrNil == #binary ifTrue:[
-        ^ 'cls'
+	^ 'cls'
     ].
     aClass notNil ifTrue:[
-        ^ aClass sourceFileSuffix
+	^ aClass sourceFileSuffix
     ].
     ^ 'st'.
 !
@@ -50221,8 +50791,8 @@
     meta := false.
     nm := aClassName.
     (nm endsWith:' class') ifTrue:[
-        meta := true.
-        nm := nm copyWithoutLast:6.
+	meta := true.
+	nm := nm copyWithoutLast:6.
     ].
     nameSym := nm asSymbol.
 
@@ -50230,32 +50800,32 @@
 listOfNamespaces := self selectedNamespaces value.
 
     currentNamespace = (BrowserList nameListEntryForALL) ifTrue:[
-        (cls := Smalltalk at:nameSym) notNil ifTrue:[
-            meta ifTrue:[^ cls class].
-            ^ cls
-        ]
+	(cls := Smalltalk at:nameSym) notNil ifTrue:[
+	    meta ifTrue:[^ cls class].
+	    ^ cls
+	]
     ].
     ("(Array with:Smalltalk) ," (self listOfNamespaces)) do:[:aNamespace |
-        aNamespace = (BrowserList nameListEntryForALL) ifFalse:[
-            (cls := aNamespace at:nameSym) notNil ifTrue:[
-                meta ifTrue:[^ cls class].
-                ^ cls
-            ]
-        ]
+	aNamespace = (BrowserList nameListEntryForALL) ifFalse:[
+	    (cls := aNamespace at:nameSym) notNil ifTrue:[
+		meta ifTrue:[^ cls class].
+		^ cls
+	    ]
+	]
     ].
     currentNamespace ~= (BrowserList nameListEntryForALL) ifTrue:[
-        (cls := Smalltalk at:nameSym) notNil ifTrue:[
-            meta ifTrue:[^ cls class].
-            ^ cls
-        ]
+	(cls := Smalltalk at:nameSym) notNil ifTrue:[
+	    meta ifTrue:[^ cls class].
+	    ^ cls
+	]
     ].
 
     (nm startsWith:'Smalltalk::') ifTrue:[
-        cls := Smalltalk classNamed:(nm copyFrom:'Smalltalk::' size + 1).
-        cls notNil ifTrue:[
-            meta ifTrue:[^ cls class].
-            ^ cls
-        ]
+	cls := Smalltalk classNamed:(nm copyFrom:'Smalltalk::' size + 1).
+	cls notNil ifTrue:[
+	    meta ifTrue:[^ cls class].
+	    ^ cls
+	]
     ].
     ^ nil
 
@@ -50268,13 +50838,13 @@
      Return the class or nil, if not found."
 
     self listOfNamespaces do:[:aNamespace |
-        |cls|
-
-        (cls := aNamespace at:aClassName asSymbol) notNil ifTrue:[
-            (cls topNameSpace == aNamespace) ifTrue:[
-                ^ cls
-            ]
-        ]
+	|cls|
+
+	(cls := aNamespace at:aClassName asSymbol) notNil ifTrue:[
+	    (cls topNameSpace == aNamespace) ifTrue:[
+		^ cls
+	    ]
+	]
     ].
     ^ nil
 !
@@ -50286,35 +50856,35 @@
 
     sel := self selectionInCodeView.
     sel notNil ifTrue:[
-        (sel knownAsSymbol and:[Smalltalk includesKey:sel asSymbol]) ifTrue:[
-            ^ sel
-        ].
-
-        "/ validate
-        nSel := (Parser new findBestVariablesFor:sel) first.
-
-        nSel ~= sel ifTrue:[
-            "/ is it a known classVar or classInstance variable ?
-            classes := self classesToSearchForVariable.
-            classes do:[:eachClass |
-                eachClass withAllSuperclassesDo:[:classToLookFor |
-                    (classToLookFor classVarNames includes:sel) ifTrue:[
-                        self information:('''%1'' is a class variable in %2.'
-                                          bindWith:sel with:classToLookFor name).
-                        ^ self variablesMenuBrowseAllClassVarRefs.
-                    ]
-                ]
-            ].
-        ].
+	(sel knownAsSymbol and:[Smalltalk includesKey:sel asSymbol]) ifTrue:[
+	    ^ sel
+	].
+
+	"/ validate
+	nSel := (Parser new findBestVariablesFor:sel) first.
+
+	nSel ~= sel ifTrue:[
+	    "/ is it a known classVar or classInstance variable ?
+	    classes := self classesToSearchForVariable.
+	    classes do:[:eachClass |
+		eachClass withAllSuperclassesDo:[:classToLookFor |
+		    (classToLookFor classVarNames includes:sel) ifTrue:[
+			self information:('''%1'' is a class variable in %2.'
+					  bindWith:sel with:classToLookFor name).
+			^ self variablesMenuBrowseAllClassVarRefs.
+		    ]
+		]
+	    ].
+	].
     ].
     "/ take selected classes name as default
     (classes := self selectedClassesValue) notEmptyOrNil ifTrue:[
-        sel := (classes collect:[:cls | cls theNonMetaclass name]) asSortedCollection asStringWith:$|
+	sel := (classes collect:[:cls | cls theNonMetaclass name]) asSortedCollection asStringWith:$|
     ].
     sel isNil ifTrue:[
-        (mthd := self theSingleSelectedMethod) notNil ifTrue:[
-            sel := mthd mclass name
-        ].
+	(mthd := self theSingleSelectedMethod) notNil ifTrue:[
+	    sel := mthd mclass name
+	].
     ].
 "/    "/ take last search as default
 "/    sel isNil ifTrue:[
@@ -50332,14 +50902,14 @@
     |allNamespaces|
 
     allNamespaces isNil ifTrue:[
-        allNamespaces := NameSpace allNameSpaces.
-
-        self showAllNamespaces ifFalse:[
-            "/ only topLevel namespaces are shown
-            "/ i.e. ignore subspaces
-
-            allNamespaces := allNamespaces select:[:ns | ns isTopLevelNameSpace].
-        ]
+	allNamespaces := NameSpace allNameSpaces.
+
+	self showAllNamespaces ifFalse:[
+	    "/ only topLevel namespaces are shown
+	    "/ i.e. ignore subspaces
+
+	    allNamespaces := allNamespaces select:[:ns | ns isTopLevelNameSpace].
+	]
     ].
     ^ allNamespaces
 !
@@ -50351,11 +50921,11 @@
 
     currentNamespace := self currentNamespace.
     currentNamespace isNil ifTrue:[
-        ^ Array with:Smalltalk
+	^ Array with:Smalltalk
     ].
 
     currentNamespace = (BrowserList nameListEntryForALL) ifTrue:[
-        ^ self listOfAllNamespaces
+	^ self listOfAllNamespaces
     ].
 
     ^ Array with:currentNamespace
@@ -50367,38 +50937,38 @@
     |brwsr|
 
     openHow == #newBrowser ifTrue:[
-        brwsr := self class new.
-        brwsr browserCanvasType:spec.
-
-        "/ cannot invoke aBlock here
-        "/ (it requires that all components are built,
-        "/  in order to perform selection changes).
-        "/ therefore, ensure that the components are built:
-        brwsr allButOpen.
-        "/ ... do the setup ...
-        aBlock value:brwsr.
-        "/ and finally open it.
-        navigationState notNil ifTrue:[
-            brwsr setupNavigationStateFrom:navigationState.
-        ].
-        brwsr openWindow.
-    ] ifFalse:[
-        openHow == #newBuffer ifTrue:[
-            self createBufferWithSpec:spec.
-        ] ifFalse:[
-            "/ find here
-        ].
-        brwsr := self.
-        aBlock value:brwsr.
+	brwsr := self class new.
+	brwsr browserCanvasType:spec.
+
+	"/ cannot invoke aBlock here
+	"/ (it requires that all components are built,
+	"/  in order to perform selection changes).
+	"/ therefore, ensure that the components are built:
+	brwsr allButOpen.
+	"/ ... do the setup ...
+	aBlock value:brwsr.
+	"/ and finally open it.
+	navigationState notNil ifTrue:[
+	    brwsr setupNavigationStateFrom:navigationState.
+	].
+	brwsr openWindow.
+    ] ifFalse:[
+	openHow == #newBuffer ifTrue:[
+	    self createBufferWithSpec:spec.
+	] ifFalse:[
+	    "/ find here
+	].
+	brwsr := self.
+	aBlock value:brwsr.
     ].
     brwsr enqueueDelayedUpdateBufferLabel.
 
     labelOrNil notNil ifTrue:[
-        openHow == #newBrowser ifTrue:[
-            brwsr windowLabel:labelOrNil.
-        ] ifFalse:[
-            brwsr bufferLabel:labelOrNil
-        ]
+	openHow == #newBrowser ifTrue:[
+	    brwsr windowLabel:labelOrNil.
+	] ifFalse:[
+	    brwsr bufferLabel:labelOrNil
+	]
     ].
     ^ brwsr
 
@@ -50410,7 +50980,7 @@
     "the current buffers noteBookView"
 
     ^ self navigationState noteBookView
-    
+
 "/    ^ self navigationState canvas builder findComponentAt: 'EditorNoteBook'.
 
 "/    | editorNoteBookCanvas|
@@ -50437,69 +51007,69 @@
     aNavigationState modified ifFalse:[^ false].
 
     (codeAspect := aNavigationState codeAspect) isNil ifTrue:[
-        "/ no aspect yet (i.e. there is nothing shown)
-        ^ aNavigationState codeView modified.
+	"/ no aspect yet (i.e. there is nothing shown)
+	^ aNavigationState codeView modified.
     ].
 
     "/ higher prio to prevent it from being changed while we convert it (by editing)
     Processor activeProcess
-        withHigherPriorityDo:[
-            changedSource := aNavigationState codeView contentsAsString asStringCollection.
-        ].
+	withHigherPriorityDo:[
+	    changedSource := aNavigationState codeView contentsAsString asStringCollection.
+	].
     changedSource := changedSource collect:[:line | line string withoutTrailingSeparators withTabsExpanded].
     changedSource := changedSource collect:[:line | line isEmpty ifTrue:[nil] ifFalse:[line]].
     [changedSource size > 0 and:[changedSource last isNil]] whileTrue:[
-        changedSource := changedSource copyWithoutLast:1
+	changedSource := changedSource copyWithoutLast:1
     ].
     changedSource := changedSource asString.
 
     codeAspect == #method ifTrue:[
-        methods := aNavigationState selectedMethods value.
-        methods size > 0 ifTrue:[
-           mthd := methods first.
-        ].
-        mthd isNil ifTrue:[
-            "/ method was either removed by someone else or never accepted;
-            "/ however, the code is modified anyhow.
-            ^ true.
-        ].
-        originalSource := mthd source.
-        originalSource isNil ifTrue:[
-            "/ cannot get methods code ..
-            ^ true
-        ].
-
-        originalSource := originalSource asStringCollection.
-        originalSource := originalSource collect:[:line | line string withoutTrailingSeparators withTabsExpanded].
-        originalSource := originalSource collect:[:line | line isEmpty ifTrue:[nil] ifFalse:[line]].
-        [originalSource size > 0 and:[originalSource last isNil]] whileTrue:[
-            originalSource := originalSource copyWithoutLast:1
-        ].
-
-        s1 := originalSource asString.
-        s2 := changedSource asString.
-        modified := (s1 ~= s2)
-    ] ifFalse:[
-        codeAspect == #classDefinition ifTrue:[
-            classes := aNavigationState selectedClasses value.
-            classes size > 0 ifTrue:[
-                cls := classes first.
-            ].
-            cls isNil ifTrue:[
-                "/ class was either removed by someone else or never accepted;
-                "/ however, the code is modified anyhow.
-                ^ true
-            ].
-            originalSource := self classDefinitionStringFor:cls.
-            modified := (originalSource string withTabsExpanded ~= changedSource string withTabsExpanded)
-        ] ifFalse:[
-            ^ true
-        ]
+	methods := aNavigationState selectedMethods value.
+	methods size > 0 ifTrue:[
+	   mthd := methods first.
+	].
+	mthd isNil ifTrue:[
+	    "/ method was either removed by someone else or never accepted;
+	    "/ however, the code is modified anyhow.
+	    ^ true.
+	].
+	originalSource := mthd source.
+	originalSource isNil ifTrue:[
+	    "/ cannot get methods code ..
+	    ^ true
+	].
+
+	originalSource := originalSource asStringCollection.
+	originalSource := originalSource collect:[:line | line string withoutTrailingSeparators withTabsExpanded].
+	originalSource := originalSource collect:[:line | line isEmpty ifTrue:[nil] ifFalse:[line]].
+	[originalSource size > 0 and:[originalSource last isNil]] whileTrue:[
+	    originalSource := originalSource copyWithoutLast:1
+	].
+
+	s1 := originalSource asString.
+	s2 := changedSource asString.
+	modified := (s1 ~= s2)
+    ] ifFalse:[
+	codeAspect == #classDefinition ifTrue:[
+	    classes := aNavigationState selectedClasses value.
+	    classes size > 0 ifTrue:[
+		cls := classes first.
+	    ].
+	    cls isNil ifTrue:[
+		"/ class was either removed by someone else or never accepted;
+		"/ however, the code is modified anyhow.
+		^ true
+	    ].
+	    originalSource := self classDefinitionStringFor:cls.
+	    modified := (originalSource string withTabsExpanded ~= changedSource string withTabsExpanded)
+	] ifFalse:[
+	    ^ true
+	]
     ].
     modified ifFalse:[
-        aNavigationState codeModifiedHolder value:false.
-        aNavigationState realModifiedState:false.
-        self updateBufferLabel.
+	aNavigationState codeModifiedHolder value:false.
+	aNavigationState realModifiedState:false.
+	self updateBufferLabel.
     ].
     ^ modified
 
@@ -50509,12 +51079,12 @@
 
 rememberLastProjectMoveTo:aProject
     LastProjectMoves isNil ifTrue:[
-        LastProjectMoves := OrderedCollection new.
+	LastProjectMoves := OrderedCollection new.
     ].
     LastProjectMoves remove:aProject ifAbsent:nil.
     LastProjectMoves addFirst:aProject.
     LastProjectMoves size > 10 ifTrue:[
-        LastProjectMoves removeLast.
+	LastProjectMoves removeLast.
     ].
 
     "Created: / 17.2.2000 / 23:03:50 / cg"
@@ -50529,7 +51099,7 @@
     allCategories := selectedCategories includes:BrowserList nameListEntryForALL.
 
     ^ self
-        selectedClassesInCategories:selectedCategories orAll:allCategories
+	selectedClassesInCategories:selectedCategories orAll:allCategories
 !
 
 selectedCategoryClassesDo:aBlock
@@ -50543,7 +51113,7 @@
 
     varName := self selectedClassVariableInCodeViewOrNil.
     varName isNil ifTrue:[
-            self warn:'Please select a variable'.
+	    self warn:'Please select a variable'.
     ].
     ^ varName
 !
@@ -50552,22 +51122,22 @@
     |node mthd cls|
 
     (mthd := self theSingleSelectedMethod) notNil ifTrue:[
-        cls := mthd mclass.
-    ] ifFalse:[
-        self codeAspect value ~= #classDefinition ifTrue:[
-            ^ nil
-        ].
-        cls := self theSingleSelectedClass.
+	cls := mthd mclass.
+    ] ifFalse:[
+	self codeAspect value ~= #classDefinition ifTrue:[
+	    ^ nil
+	].
+	cls := self theSingleSelectedClass.
     ].
     node := self findNode.
     node isNil ifTrue:[
-        (self hasClassVariableSelectedInCodeView) ifFalse:[
-            ^ nil
-        ].
-        ^ self selectionInCodeView.
+	(self hasClassVariableSelectedInCodeView) ifFalse:[
+	    ^ nil
+	].
+	^ self selectionInCodeView.
     ].
     node isVariable ifFalse:[
-        ^ nil
+	^ nil
     ].
     ^ node name.
 !
@@ -50585,7 +51155,7 @@
      caring for nameSpace and packageFilters"
 
     ^ self
-        selectedClassesInCategories:aCollectionOfCategories orAll:false
+	selectedClassesInCategories:aCollectionOfCategories orAll:false
 !
 
 selectedClassesInCategories:aCollectionOfCategories orAll:allCategories
@@ -50596,7 +51166,7 @@
 
     nameSpaceFilter := self selectedNamespaces value.
     nameSpaceFilter isNil ifTrue:[
-        nameSpaceFilter := navigationState nameSpaceFilter value.
+	nameSpaceFilter := navigationState nameSpaceFilter value.
     ].
     (nameSpaceFilter notNil and:[nameSpaceFilter includes:BrowserList nameListEntryForALL])
     ifTrue:[nameSpaceFilter := nil].
@@ -50606,9 +51176,9 @@
     ifTrue:[packageFilter := nil].
 
     ^ Smalltalk allClassesForWhich:[:aClass |
-        (allCategories or:[aCollectionOfCategories includes:aClass category])
-        and:[ (nameSpaceFilter isNil or:[nameSpaceFilter includes:aClass nameSpace name])
-        and:[ (packageFilter isNil or:[packageFilter includes:aClass package]) ]].
+	(allCategories or:[aCollectionOfCategories includes:aClass category])
+	and:[ (nameSpaceFilter isNil or:[nameSpaceFilter includes:aClass nameSpace name])
+	and:[ (packageFilter isNil or:[packageFilter includes:aClass package]) ]].
     ].
 
     "Modified: / 10-08-2006 / 15:58:11 / cg"
@@ -50621,10 +51191,10 @@
      for private classes, evaluate privateBlock."
 
     self
-        classes:(self selectedClassesValue)
-        nonMetaDo:aBlock
-        ifUnloaded:unloadedBlock
-        ifPrivate:privateBlock
+	classes:(self selectedClassesValue)
+	nonMetaDo:aBlock
+	ifUnloaded:unloadedBlock
+	ifPrivate:privateBlock
 
     "Modified: / 28-02-2012 / 16:53:41 / cg"
 !
@@ -50642,17 +51212,17 @@
 
     mode := self navigationState canvasType.
     #(
-        fullBrowserSpec 
-            (selectedMethods selectedProtocolMethods selectedClasses selectedCategoryClasses)
-        smallLintByRuleResultBrowserSpec
-            (selectedMethods selectedClasses selectedLintRuleClasses)
-        methodListBrowserSpec
-            (selectedMethods)
-        "Add more"
+	fullBrowserSpec
+	    (selectedMethods selectedProtocolMethods selectedClasses selectedCategoryClasses)
+	smallLintByRuleResultBrowserSpec
+	    (selectedMethods selectedClasses selectedLintRuleClasses)
+	methodListBrowserSpec
+	    (selectedMethods)
+	"Add more"
 
     ) pairWiseDo:
-        [:key :selectors|mode == key ifTrue:            
-            [^self selectedCodeComponentsUsing:selectors]].
+	[:key :selectors|mode == key ifTrue:
+	    [^self selectedCodeComponentsUsing:selectors]].
 
     self breakPoint: #jv.
     "/Fallback
@@ -50667,9 +51237,9 @@
 
     | result |
     selectors do:
-        [:selector|
-        (result := (self perform: selector) value)
-            isEmptyOrNil ifFalse:[^result]].
+	[:selector|
+	(result := (self perform: selector) value)
+	    isEmptyOrNil ifFalse:[^result]].
     ^#()
 
     "Modified: / 04-08-2011 / 19:05:31 / cg"
@@ -50680,7 +51250,7 @@
 
     varName := self selectedInstanceVariableInCodeViewOrNil.
     varName isNil ifTrue:[
-        self warn:'Please select an instance variable'.
+	self warn:'Please select an instance variable'.
     ].
     ^ varName
 !
@@ -50689,26 +51259,26 @@
     |node mthd cls|
 
     (mthd := self theSingleSelectedMethod) notNil ifTrue:[
-        cls := mthd mclass.
-    ] ifFalse:[
-        self codeAspect value ~= #classDefinition ifTrue:[
-            ^ nil
-        ].
-        cls := self theSingleSelectedClass.
+	cls := mthd mclass.
+    ] ifFalse:[
+	self codeAspect value ~= #classDefinition ifTrue:[
+	    ^ nil
+	].
+	cls := self theSingleSelectedClass.
     ].
     cls isMeta ifTrue:[
-        ^ nil
+	^ nil
     ].
 
     node := self findNode.
     node isNil ifTrue:[
-        (self hasInstanceVariableSelectedInCodeView) ifFalse:[
-            ^ nil
-        ].
-        ^ self selectionInCodeView.
+	(self hasInstanceVariableSelectedInCodeView) ifFalse:[
+	    ^ nil
+	].
+	^ self selectionInCodeView.
     ].
     node isVariable ifFalse:[
-        ^ nil
+	^ nil
     ].
     ^ node name.
 !
@@ -50720,10 +51290,10 @@
 
     classes := Set new.
     self selectedMethodsClasses
-        do:[:cls |
-            classes addAll:(cls withAllSuperclasses).
-            classes addAll:(cls allSubclasses).
-        ].
+	do:[:cls |
+	    classes addAll:(cls withAllSuperclasses).
+	    classes addAll:(cls allSubclasses).
+	].
     ^ classes
 
     "Created: / 05-09-2006 / 10:50:48 / cg"
@@ -50763,9 +51333,9 @@
     setOfClasses := IdentitySet new.
 
     Smalltalk allClassesDo:[:aClass |
-        (selectedProjects includes:aClass package) ifTrue:[
-            setOfClasses add:aClass .
-        ]
+	(selectedProjects includes:aClass package) ifTrue:[
+	    setOfClasses add:aClass .
+	]
     ].
     ^ setOfClasses
 !
@@ -50775,7 +51345,7 @@
     | methods |
     methods := Set new.
     self selectedProtocolMethodsDo:
-        [:ign1 :ign2 :ign3 :mth|methods add: mth].
+	[:ign1 :ign2 :ign3 :mth|methods add: mth].
     ^methods
 !
 
@@ -50790,26 +51360,26 @@
     allIncluded := protocols includes:(BrowserList nameListEntryForALL).
 
     navigationState isFullProtocolBrowser ifTrue:[
-        targets := Smalltalk allClassesAndMetaclasses
-    ] ifFalse:[
-        targets := self selectedClassesValue
+	targets := Smalltalk allClassesAndMetaclasses
+    ] ifFalse:[
+	targets := self selectedClassesValue
     ].
     targets isEmptyOrNil ifTrue:[^self].
-    
+
     targets do:[:cls |
-        allIncluded ifTrue:[
-            cls methodDictionary keysAndValuesDo:[:sel :mthd |
-                aBlock value:cls value:mthd category value:sel value:mthd
-            ]
-        ] ifFalse:[
-            protocols do:[:aCategory |
-                cls methodDictionary keysAndValuesDo:[:sel :mthd |
-                    aCategory = mthd category ifTrue:[
-                        aBlock value:cls value:aCategory value:sel value:mthd
-                    ]
-                ]
-            ]
-        ]
+	allIncluded ifTrue:[
+	    cls methodDictionary keysAndValuesDo:[:sel :mthd |
+		aBlock value:cls value:mthd category value:sel value:mthd
+	    ]
+	] ifFalse:[
+	    protocols do:[:aCategory |
+		cls methodDictionary keysAndValuesDo:[:sel :mthd |
+		    aCategory = mthd category ifTrue:[
+			aBlock value:cls value:aCategory value:sel value:mthd
+		    ]
+		]
+	    ]
+	]
     ].
 
     "Modified: / 01-08-2010 / 14:39:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -50825,27 +51395,27 @@
     protocols := self selectedProtocolsValue.
 
     navigationState isFullProtocolBrowser ifTrue:[
-        targets := Smalltalk allClassesAndMetaclasses
-    ] ifFalse:[
-        targets := self selectedClassesValue
+	targets := Smalltalk allClassesAndMetaclasses
+    ] ifFalse:[
+	targets := self selectedClassesValue
     ].
     allIncluded := protocols includes:(BrowserList nameListEntryForALL).
 
     targets do:[:cls |
-        allIncluded ifTrue:[
-            cls categories do:[:cat |
-                aBlock value:cls value:cat
-            ]
-        ] ifFalse:[
-            protocols do:[:aCategory |
-                |cat|
-
-                cat := aCategory string.
-                (cls methodDictionary contains:[:mthd | cat = mthd category]) ifTrue:[
-                    aBlock value:cls value:cat
-                ]
-            ]
-        ]
+	allIncluded ifTrue:[
+	    cls categories do:[:cat |
+		aBlock value:cls value:cat
+	    ]
+	] ifFalse:[
+	    protocols do:[:aCategory |
+		|cat|
+
+		cat := aCategory string.
+		(cls methodDictionary contains:[:mthd | cat = mthd category]) ifTrue:[
+		    aBlock value:cls value:cat
+		]
+	    ]
+	]
     ].
 
     "Modified: / 28-02-2012 / 16:53:00 / cg"
@@ -50863,14 +51433,14 @@
 
     t := SystemBrowser extractSelectorFrom:sel.
     t notNil ifTrue:[
-        sel := t.
+	sel := t.
     ].
     sel knownAsSymbol ifFalse:[
-        goodSelectors := Parser findBest:5 selectorsFor:sel in:nil forCompletion:false.
-        goodSelectors size == 0 ifTrue:[
-            ^ nil
-        ].
-        sel := goodSelectors first
+	goodSelectors := Parser findBest:5 selectorsFor:sel in:nil forCompletion:false.
+	goodSelectors size == 0 ifTrue:[
+	    ^ nil
+	].
+	sel := goodSelectors first
     ].
     sel isNil ifTrue:[^ nil].
 
@@ -50902,7 +51472,7 @@
 
     namesOrNil := RBParser parseVariableNames:(self selectionInCodeView).
     namesOrNil notNil ifTrue:[
-        names := namesOrNil collect:[:each |each name].
+	names := namesOrNil collect:[:each |each name].
     ].
     ^ names
 !
@@ -50919,7 +51489,7 @@
     |codeView|
 
     (codeView := self codeView) notNil ifTrue:[
-        ^ codeView selectionAsString.
+	^ codeView selectionAsString.
     ].
     ^ nil
 !
@@ -50946,12 +51516,12 @@
 "/            ]
 "/        ]
 "/    ] ifFalse:[
-        sel := self theSingleSelectedSelector.
-        sel notNil ifTrue:[
-            sel := sel withoutSpaces upTo:(Character space)
-        ] ifFalse:[
-            sel := ''
-        ]
+	sel := self theSingleSelectedSelector.
+	sel notNil ifTrue:[
+	    sel := sel withoutSpaces upTo:(Character space)
+	] ifFalse:[
+	    sel := ''
+	]
     ].
     ^ sel string
 
@@ -50960,9 +51530,9 @@
 
 sendFileViaEmail:aFile subject:subject
     SendMailTool
-        openForFile:aFile
-        withSubject:subject
-        recipient:nil
+	openForFile:aFile
+	withSubject:subject
+	recipient:nil
 
     "Created: / 20-09-2007 / 15:02:49 / cg"
 !
@@ -50979,7 +51549,7 @@
     "the current buffers stringSearchToolView"
 
     ^ self navigationState stringSearchToolView
-"/    ^ self navigationState viewOfComponent: 'StringSearchToolCanvas' "'StringSearchTool'". 
+"/    ^ self navigationState viewOfComponent: 'StringSearchToolCanvas' "'StringSearchTool'".
 !
 
 stringToSearchFor
@@ -50989,7 +51559,7 @@
 
     sel := self selectionInCodeView.
     sel notNil ifTrue:[
-        ^ sel string
+	^ sel string
     ].
     ^ sel
 !
@@ -51002,7 +51572,7 @@
 
     categories := self selectedCategoriesValue.
     categories size == 1 ifTrue:[
-        ^ categories first string
+	^ categories first string
     ].
     ^ nil
 
@@ -51019,14 +51589,14 @@
 theSingleSelectedLintRuleHolder
 
     ^BlockValue
-        with:[:generator| 
-            | rule size |
-
-            rule := nil.
-            size := 0.
-            (generator value ? #()) do:[:each|rule := each.size := size + 1].
-            size == 1 ifTrue:[rule] ifFalse:[nil]]
-        argument: self selectedLintRules
+	with:[:generator|
+	    | rule size |
+
+	    rule := nil.
+	    size := 0.
+	    (generator value ? #()) do:[:each|rule := each.size := size + 1].
+	    size == 1 ifTrue:[rule] ifFalse:[nil]]
+	argument: self selectedLintRules
 
     "Created: / 05-02-2010 / 12:56:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 01-03-2012 / 15:31:23 / cg"
@@ -51057,7 +51627,7 @@
 
     mthd := self theSingleSelectedMethod.
     mthd notNil ifTrue:[
-        name := mthd name
+	name := mthd name
     ].
     ^ name
 
@@ -51071,7 +51641,7 @@
 
     namespaces := self selectedNamespaces value.
     namespaces size == 1 ifTrue:[
-        ^ namespaces first
+	^ namespaces first
     ].
     ^ nil
 
@@ -51085,10 +51655,10 @@
 
     projects := self selectedProjects value.
     projects size == 1 ifTrue:[
-        p := projects first.
-        p ~= (BrowserList nameListEntryForALL) ifTrue:[
-            ^ p
-        ]
+	p := projects first.
+	p ~= (BrowserList nameListEntryForALL) ifTrue:[
+	    ^ p
+	]
     ].
     ^ nil
 
@@ -51102,7 +51672,7 @@
     |selectedProtocols|
 
     (selectedProtocols := self selectedProtocols value) size == 1 ifTrue:[
-        ^ selectedProtocols first
+	^ selectedProtocols first
     ].
     ^ nil
 
@@ -51116,12 +51686,12 @@
 
     mthd := self theSingleSelectedMethod.
     mthd notNil ifTrue:[
-        "JV: I changed this to answer the selector (not  name),
-        because for non-smalltalk languages (Ruby for instance) 
-        method selector may differ from method name."
-
-        "/sel := mthd name "/ who methodSelector
-        sel := mthd selector.
+	"JV: I changed this to answer the selector (not  name),
+	because for non-smalltalk languages (Ruby for instance)
+	method selector may differ from method name."
+
+	"/sel := mthd name "/ who methodSelector
+	sel := mthd selector.
     ].
     ^ sel
 
@@ -51136,7 +51706,7 @@
     |selectedVariables|
 
     (selectedVariables := self selectedVariables value) size == 1 ifTrue:[
-        ^ selectedVariables first
+	^ selectedVariables first
     ].
     ^ nil
 !
@@ -51145,7 +51715,7 @@
     |appView|
 
     anAppOrNil isNil ifTrue:[
-        ^ false
+	^ false
     ].
     appView := anAppOrNil window.
     ^ appView notNil
@@ -51200,7 +51770,6 @@
     ^ navigationState projectListApplication
 ! !
 
-
 !NewSystemBrowser methodsFor:'private-history'!
 
 lastSearchPatterns
@@ -51212,13 +51781,13 @@
 
     mthd := self theSingleSelectedMethod.
     mthd isNil ifTrue:[
-        cls := self theSingleSelectedClass.
-    ] ifFalse:[
-        cls := mthd mclass.
-        sel := mthd selector.
+	cls := self theSingleSelectedClass.
+    ] ifFalse:[
+	cls := mthd mclass.
+	sel := mthd selector.
     ].
     cls isNil ifTrue:[
-        ^ self
+	^ self
     ].
     self class addToFindHistory: cls selector: sel.
     self addToHistory: cls selector: sel.
@@ -51237,9 +51806,9 @@
 
 asyncShowMethodInfo
     self
-        enqueueMessage:#showInfo:
-        for:self
-        arguments:(Array with:self getMethodInfo)
+	enqueueMessage:#showInfo:
+	for:self
+	arguments:(Array with:self getMethodInfo)
 !
 
 busyLabel:what
@@ -51248,8 +51817,8 @@
     |window|
 
     (window := builder window) isTopView ifTrue:[
-        window
-            label:('SystemBrowser - ' , (resources string:what))
+	window
+	    label:('SystemBrowser - ' , (resources string:what))
     ]
 !
 
@@ -51259,8 +51828,8 @@
     |window|
 
     (window := builder window) isTopView ifTrue:[
-        window
-            label:('SystemBrowser - ' , (resources string:what with:someArgument))
+	window
+	    label:('SystemBrowser - ' , (resources string:what with:someArgument))
     ]
 !
 
@@ -51276,15 +51845,15 @@
     category := categories anElement.
 
     selectedClasses size == 1 ifTrue:[
-        msg := 'Category of %1: %3'
-    ] ifFalse:[
-        msg := 'Category of %2 classes: %3'
+	msg := 'Category of %1: %3'
+    ] ifFalse:[
+	msg := 'Category of %2 classes: %3'
     ].
 
     ^ resources string:msg
-                with:selectedClasses first name
-                with:selectedClasses size
-                with:category
+		with:selectedClasses first name
+		with:selectedClasses size
+		with:category
 
     "Modified: / 28-02-2012 / 16:45:20 / cg"
 !
@@ -51302,8 +51871,8 @@
     subclasses := singleSelectedClass subclasses.
     msg := self infoStringForClasses:subclasses withPrefix:'sub'.
     ^ resources string:('%1: ' , msg)
-                with:singleSelectedClass theNonMetaclass name
-                with:subclasses size
+		with:singleSelectedClass theNonMetaclass name
+		with:subclasses size
 
     "Modified: / 27-07-2006 / 10:10:38 / cg"
 !
@@ -51316,7 +51885,7 @@
 
 currentBufferLabel
     self shortNamesInTabs value ifTrue:[
-        ^ navigationState shortNameString
+	^ navigationState shortNameString
     ].
     ^ navigationState nameString
 
@@ -51331,27 +51900,27 @@
     "return the defaultLabel"
 
     navigationState isCategoryBrowser ifTrue:[
-        ^ 'Category'
+	^ 'Category'
     ].
     (navigationState isNameSpaceBrowser
     or:[navigationState isNameSpaceFullBrowser]) ifTrue:[
-        ^ 'NameSpace'
+	^ 'NameSpace'
     ].
     (navigationState isProjectBrowser
     or:[navigationState isProjectFullBrowser]) ifTrue:[
-        ^ 'Project'
+	^ 'Project'
     ].
     navigationState isFullClassSourceBrowser ifTrue:[
-        ^ 'FullClass'
+	^ 'FullClass'
     ].
     navigationState isClassDocumentationBrowser ifTrue:[
-        ^ 'Documentation'
+	^ 'Documentation'
     ].
     navigationState isVersionDiffBrowser ifTrue:[
-        ^ 'Revisions'
+	^ 'Revisions'
     ].
     navigationState isClassDocumentationBrowser ifTrue:[
-        ^ 'Documentation'
+	^ 'Documentation'
     ].
     ^ ''
 
@@ -51396,22 +51965,22 @@
     |nm ns currentNamespace|
 
     aClass isJavaClass ifTrue:[
-        ^ aClass nameInBrowser "/ fullName "/ asString replaceAll:$/ with:$.
+	^ aClass nameInBrowser "/ fullName "/ asString replaceAll:$/ with:$.
     ].
 
     ns := aClass topNameSpace.
     ns isNil ifTrue:[          "/ this 'cannot' happen (should always be Smalltalk)
-        ^ aClass name
+	^ aClass name
     ].
 
     currentNamespace := self currentNamespace.
     currentNamespace = (BrowserList nameListEntryForALL) ifTrue:[
-        (ns == Smalltalk) ifTrue:[
-            nm := aClass nameWithoutNameSpacePrefix.
-            ^ nm
-        ].
-        nm := aClass nameWithoutNameSpacePrefix.
-        ^ ns name , '::' , nm   "/ full name
+	(ns == Smalltalk) ifTrue:[
+	    nm := aClass nameWithoutNameSpacePrefix.
+	    ^ nm
+	].
+	nm := aClass nameWithoutNameSpacePrefix.
+	^ ns name , '::' , nm   "/ full name
     ].
 
     nm := aClass nameWithoutNameSpacePrefix.
@@ -51419,10 +51988,10 @@
     "/ is it in one of the selected namespaces ?
 
     (self findClassNamedInNameSpace:nm) isNil ifTrue:[
-        ^ ns name , '::' , nm   "/ full name
+	^ ns name , '::' , nm   "/ full name
     ].
     currentNamespace == ns ifFalse:[
-        ^ ns name , '::' , nm   "/ full name
+	^ ns name , '::' , nm   "/ full name
     ].
     ^ nm.
 
@@ -51443,27 +52012,27 @@
 
     explainTookTooLong := false.
     withTimeout ifTrue:[
-        explanation :=
-            [ self explanationForCode:code short:short ]
-                    valueWithWatchDog:[explainTookTooLong := true]
-                    afterMilliseconds:100.
-    ] ifFalse:[
-        explanation := self explanationForCode:code short:short
+	explanation :=
+	    [ self explanationForCode:code short:short ]
+		    valueWithWatchDog:[explainTookTooLong := true]
+		    afterMilliseconds:100.
+    ] ifFalse:[
+	explanation := self explanationForCode:code short:short
     ].
 
     self activityNotification:nil.
     explainTookTooLong ifTrue:[
-        self showInfo:'Explain took too long - cancelled.'.
-        ^ self.
+	self showInfo:'Explain took too long - cancelled.'.
+	^ self.
     ].
 
     explanation notNil ifTrue:[
-        short ifTrue:[
-            self showInfo:explanation
-        ] ifFalse:[
-            self information:explanation
-        ].
-        builder window flush
+	short ifTrue:[
+	    self showInfo:explanation
+	] ifFalse:[
+	    self information:explanation
+	].
+	builder window flush
     ].
 
     "Created: / 05-09-2006 / 10:37:04 / cg"
@@ -51481,31 +52050,31 @@
 
     interval := self selectedInterval.
     interval isEmpty ifTrue:[
-        crsrPos := codeView characterPositionOfCursor.
-        codeView characterUnderCursor isSeparator ifTrue:[
-            crsrPos := (crsrPos - 1) max:1
-        ].
-        interval := crsrPos to:crsrPos.
+	crsrPos := codeView characterPositionOfCursor.
+	codeView characterUnderCursor isSeparator ifTrue:[
+	    crsrPos := (crsrPos - 1) max:1
+	].
+	interval := crsrPos to:crsrPos.
     ].
 
     node := self findNodeForInterval:interval.
     node notNil ifTrue: [
-        Error
-            handle:[:ex | ]
-            do:[
-                explanation := Explainer explainNode:node in:code forClass:cls short:short interval:interval
-            ]
+	Error
+	    handle:[:ex | ]
+	    do:[
+		explanation := Explainer explainNode:node in:code forClass:cls short:short interval:interval
+	    ]
     ].
     explanation isNil ifTrue:[
-        codeView hasSelection ifTrue:[
-            selection := codeView selection.
-        ] ifFalse:[
-            "/ selection := codeView characterBeforeCursor.
-        ].
-        selection notNil ifTrue:[
-            selection := selection asString string withoutSeparators.
-            explanation := Explainer explain:selection in:code forClass:cls short:short
-        ].
+	codeView hasSelection ifTrue:[
+	    selection := codeView selection.
+	] ifFalse:[
+	    "/ selection := codeView characterBeforeCursor.
+	].
+	selection notNil ifTrue:[
+	    selection := selection asString string withoutSeparators.
+	    explanation := Explainer explain:selection in:code forClass:cls short:short
+	].
     ].
     ^ explanation
 
@@ -51518,7 +52087,7 @@
     organizerMode := self organizerMode value.
     (organizerMode == OrganizerCanvas organizerModeClassHierarchy
     or:[ organizerMode == OrganizerCanvas organizerModeHierarchy] ) ifTrue:[
-        ^ self classCategoryInfo.
+	^ self classCategoryInfo.
     ].
 
     msg := self classInheritanceInfo.
@@ -51544,23 +52113,23 @@
     firstMethod := selectedMethods first.
 
     selectedMethods size == 1 ifTrue:[
-        ^ self getMethodInfoForMethod:firstMethod.
+	^ self getMethodInfoForMethod:firstMethod.
     ].
 
     differentSourceButSameSemantic := false.
 
     source1 := firstMethod source.
     selectedMethods from:2 do:[:eachOtherMethod |
-        eachOtherMethod source ~= source1 ifTrue:[
-            Error
-                handle:[:ex | ^  nil]
-                do:[
-                    firstMethod parseTree ~= eachOtherMethod parseTree ifTrue:[
-                        ^ nil.
-                    ].
-                ].
-            differentSourceButSameSemantic := true.
-        ].
+	eachOtherMethod source ~= source1 ifTrue:[
+	    Error
+		handle:[:ex | ^  nil]
+		do:[
+		    firstMethod parseTree ~= eachOtherMethod parseTree ifTrue:[
+			^ nil.
+		    ].
+		].
+	    differentSourceButSameSemantic := true.
+	].
     ].
 
     prefix := differentSourceButSameSemantic ifTrue:['Same effect'] ifFalse:['Same source'].
@@ -51568,7 +52137,7 @@
     "/ all are the same.
     msg := self getMethodInfoForMethod:firstMethod.
     msg isEmptyOrNil ifTrue:[
-        ^ prefix.
+	^ prefix.
     ].
     ^ prefix,' - ' , msg.
 
@@ -51581,21 +52150,21 @@
     method := aMethod.
     method isNil ifTrue:[ ^ nil ].
     method wrapper notNil ifTrue:[
-        method := method wrapper
+	method := method wrapper
     ].
     method isNil ifTrue:[
-        ^ 'oops - this method is not attached to any class'.
+	^ 'oops - this method is not attached to any class'.
     ].
 
     msg := self methodSpecialInfoFor:method.
     msg isNil ifTrue:[
-        msg := self methodRedefinitionInfoFor:method.
-        msg isNil ifTrue:[
-            msg := self methodInheritanceInfoFor:method.
-            msg isNil ifTrue:[
-                msg := self methodImplementorsInfoFor:method
-            ]
-        ].
+	msg := self methodRedefinitionInfoFor:method.
+	msg isNil ifTrue:[
+	    msg := self methodInheritanceInfoFor:method.
+	    msg isNil ifTrue:[
+		msg := self methodImplementorsInfoFor:method
+	    ]
+	].
     ].
     ^ (msg ? '').
 !
@@ -51604,7 +52173,7 @@
     |nClassNames sortedByName classNames|
 
     aCollectionOfClasses isEmpty ifTrue:[
-        ^ 'No %1classes.' bindWith:prefix.
+	^ 'No %1classes.' bindWith:prefix.
     ].
 
     classNames := aCollectionOfClasses asIdentitySet asOrderedCollection collect:[:each | each theNonMetaclass name].
@@ -51612,19 +52181,19 @@
     nClassNames := classNames size.
 
     nClassNames <= 3 ifTrue:[
-        nClassNames == 1 ifTrue:[
-            ^ '1 %1class: %2' bindWith:prefix with:(classNames first allBold).
-        ].
-        sortedByName := classNames sort.
-        nClassNames == 2 ifTrue:[
-            ^ '2 %1classes: %2 and %3' bindWith:prefix
-                        with:(sortedByName first allBold)
-                        with:(sortedByName second allBold).
-        ].
-        ^ '3 %1classes: %2, %3 and %4' bindWith:prefix
-                    with:(sortedByName first allBold)
-                    with:(sortedByName second allBold)
-                    with:(sortedByName third allBold).
+	nClassNames == 1 ifTrue:[
+	    ^ '1 %1class: %2' bindWith:prefix with:(classNames first allBold).
+	].
+	sortedByName := classNames sort.
+	nClassNames == 2 ifTrue:[
+	    ^ '2 %1classes: %2 and %3' bindWith:prefix
+			with:(sortedByName first allBold)
+			with:(sortedByName second allBold).
+	].
+	^ '3 %1classes: %2, %3 and %4' bindWith:prefix
+		    with:(sortedByName first allBold)
+		    with:(sortedByName second allBold)
+		    with:(sortedByName third allBold).
     ].
     ^ '%1 %2classes' bindWith:nClassNames printString allBold with:prefix
 
@@ -51635,32 +52204,32 @@
     |implementors msg senders msg2|
 
     implementors := SystemBrowser
-        findImplementorsOf:aMethod selector
-        in:(Smalltalk allClasses)
-        ignoreCase:false.
+	findImplementorsOf:aMethod selector
+	in:(Smalltalk allClasses)
+	ignoreCase:false.
 
     implementors notEmpty ifTrue:[
-        msg := 'Only implemented here.'.
-        implementors remove:aMethod ifAbsent:nil.
-        implementors notEmpty ifTrue:[
-            implementors := implementors collect:[:mthd | mthd mclass].
-            implementors notEmpty ifTrue:[
-                msg := 'Also implemented in '.
-                msg := msg , (self infoStringForClasses:implementors withPrefix:'other ').
-                msg := msg , '.'.
-            ]
-        ].
+	msg := 'Only implemented here.'.
+	implementors remove:aMethod ifAbsent:nil.
+	implementors notEmpty ifTrue:[
+	    implementors := implementors collect:[:mthd | mthd mclass].
+	    implementors notEmpty ifTrue:[
+		msg := 'Also implemented in '.
+		msg := msg , (self infoStringForClasses:implementors withPrefix:'other ').
+		msg := msg , '.'.
+	    ]
+	].
     ].
 
 false ifTrue:[  "/ too slow
     senders := SystemBrowser
-        findSendersOf:aMethod selector
-        in:(Smalltalk allClasses)
-        ignoreCase:false.
+	findSendersOf:aMethod selector
+	in:(Smalltalk allClasses)
+	ignoreCase:false.
     senders notEmpty ifTrue:[
-        msg2 := 'Sent from ' , senders size printString, ' methods.'.
-    ] ifFalse:[
-        msg2 := 'No senders.'.
+	msg2 := 'Sent from ' , senders size printString, ' methods.'.
+    ] ifFalse:[
+	msg2 := 'No senders.'.
     ].
     msg := msg , '/' , msg2
 ].
@@ -51680,15 +52249,15 @@
     sel := aMethod selector.
     inheritedClass := superclass whichClassIncludesSelector:sel.
     inheritedClass notNil ifTrue:[
-        mthd := inheritedClass compiledMethodAt:sel.
-        msg := (sel contractTo:30) allBold.
-        (mthd sends:#'subclassResponsibility') ifTrue:[
-            msg := msg , ' overrides subclassResponsibility in '.
-        ] ifFalse:[
-            msg := msg , ' overrides implementation in '.
-        ].
-        msg := msg , inheritedClass name allBold.
-        msg := msg , '.'.
+	mthd := inheritedClass compiledMethodAt:sel.
+	msg := (sel contractTo:30) allBold.
+	(mthd sends:#'subclassResponsibility') ifTrue:[
+	    msg := msg , ' overrides subclassResponsibility in '.
+	] ifFalse:[
+	    msg := msg , ' overrides implementation in '.
+	].
+	msg := msg , inheritedClass name allBold.
+	msg := msg , '.'.
     ].
 
     ^ msg
@@ -51702,9 +52271,9 @@
 
     redefiningClasses := cls allSubclasses select:[:cls | cls includesSelector:aMethod selector. ].
     redefiningClasses size > 0 ifTrue:[
-        msg := 'redefined in '.
-        msg := msg , (self infoStringForClasses:redefiningClasses withPrefix:'sub').
-        msg := msg , '.'.
+	msg := 'redefined in '.
+	msg := msg , (self infoStringForClasses:redefiningClasses withPrefix:'sub').
+	msg := msg , '.'.
     ].
 
     ^ msg
@@ -51721,12 +52290,12 @@
     cls isNil ifTrue:[^ nil].
 
     cls isMeta ifTrue:[
-        (AbstractSourceCodeManager isVersionMethodSelector:sel) ifTrue:[
-            ^ 'The version method is required for the source code repository - do not modify.'.
-        ].
-        sel == #documentation ifTrue:[
-            ^ 'ST/X stores documentation in this method (not in comment slots)'.
-        ].
+	(AbstractSourceCodeManager isVersionMethodSelector:sel) ifTrue:[
+	    ^ 'The version method is required for the source code repository - do not modify.'.
+	].
+	sel == #documentation ifTrue:[
+	    ^ 'ST/X stores documentation in this method (not in comment slots)'.
+	].
     ].
     ^ nil
 !
@@ -51744,8 +52313,8 @@
 
     window := builder window.
     (window notNil and:[window isTopView]) ifFalse:[
-        "/ if I am used as a subApp, do not update the label
-        ^ self
+	"/ if I am used as a subApp, do not update the label
+	^ self
     ].
 
 "/    windowLabel notNil ifTrue:[
@@ -51758,11 +52327,11 @@
 "/    ].
 
     l isNil ifTrue:[
-        l := il := self currentWindowLabel.
+	l := il := self currentWindowLabel.
     ].
     navigationState realModifiedState == true
     ifTrue:[
-        l := l , ' [modified]'
+	l := l , ' [modified]'
     ].
     window label:l; iconLabel:il.
 
@@ -51774,9 +52343,9 @@
     | nm |
 
     manager isNil ifTrue:[
-        nm := nil
-    ] ifFalse:[
-        nm := manager name.
+	nm := nil
+    ] ifFalse:[
+	nm := manager name.
     ].
 
     menu replaceArgument: #SourceCodeManagerPlaceholder with: nm.
@@ -51813,17 +52382,17 @@
     self showInfo:(self getMethodInfo).
 
     self showMethodComplexity value ifTrue:[
-        OOM::MethodMetrics notNil ifTrue:[
-            method := self theSingleSelectedMethod.
-            method notNil ifTrue:[    
-                metrics := OOM::MethodMetrics forMethod:method.
-                complexity := metrics complexity.
-                complexity notNil ifTrue:[
-                    msg := metrics class descriptiveName,': ',complexity printString.
-                ].
-                
-            ]
-        ]
+	OOM::MethodMetrics notNil ifTrue:[
+	    method := self theSingleSelectedMethod.
+	    method notNil ifTrue:[
+		metrics := OOM::MethodMetrics forMethod:method.
+		complexity := metrics complexity.
+		complexity notNil ifTrue:[
+		    msg := metrics class descriptiveName,': ',complexity printString.
+		].
+
+	    ]
+	]
     ].
 !
 
@@ -51833,13 +52402,13 @@
     |nr newLabel|
 
     (nr := selectedBuffer value) notNil ifTrue:[
-        nr ~~ 0 ifTrue:[
-            newLabel := self currentBufferLabel.
-            (newLabel sameStringAndEmphasisAs:(bufferNameList at:nr)) ifTrue:[
-                ^ self.
-            ].
-            bufferNameList at:nr put:newLabel.
-        ]
+	nr ~~ 0 ifTrue:[
+	    newLabel := self currentBufferLabel.
+	    (newLabel sameStringAndEmphasisAs:(bufferNameList at:nr)) ifTrue:[
+		^ self.
+	    ].
+	    bufferNameList at:nr put:newLabel.
+	]
     ].
     self normalLabel
 
@@ -51852,20 +52421,20 @@
 
     classes := self selectedClassesValue.
     classes size > 0 ifTrue:[
-        "/ category-selection feedBack:
-        "/ update the category-selection, if '* all *' is in its selection
-        "/ (add the selected categories to the category-selection)
-        nameListEntryForALL := BrowserList nameListEntryForALL.
-        selectedCategories := self selectedCategoriesValue.
-        (selectedCategories includes:nameListEntryForALL)
-        ifTrue:[
-            oldSelectedCategories := selectedCategories asSet.
-            selectedCategories := Set with:nameListEntryForALL.
-            selectedCategories addAll:(classes collect:[:eachClass | eachClass category]).
-            selectedCategories ~= oldSelectedCategories ifTrue:[
-                self selectedCategories value:selectedCategories.
-            ].
-        ].
+	"/ category-selection feedBack:
+	"/ update the category-selection, if '* all *' is in its selection
+	"/ (add the selected categories to the category-selection)
+	nameListEntryForALL := BrowserList nameListEntryForALL.
+	selectedCategories := self selectedCategoriesValue.
+	(selectedCategories includes:nameListEntryForALL)
+	ifTrue:[
+	    oldSelectedCategories := selectedCategories asSet.
+	    selectedCategories := Set with:nameListEntryForALL.
+	    selectedCategories addAll:(classes collect:[:eachClass | eachClass category]).
+	    selectedCategories ~= oldSelectedCategories ifTrue:[
+		self selectedCategories value:selectedCategories.
+	    ].
+	].
     ].
 
     "Created: / 24-02-2000 / 14:10:09 / cg"
@@ -51876,30 +52445,30 @@
     |selectedClasses singleSelectedClass categories msg|
 
     navigationState organizerMode value == OrganizerCanvas organizerModeCategory ifTrue:[
-        self selectedCategoriesValue size > 1 ifTrue:[
-            singleSelectedClass := self theSingleSelectedClass.
-            singleSelectedClass notNil ifTrue:[
-                msg := (resources string:'Category: %2'
-                                  with:singleSelectedClass name allBold
-                                  with:singleSelectedClass category allBold).
-            ] ifFalse:[
-
-                selectedClasses := self selectedClassesValue.
-                categories := (selectedClasses collect:[:cls | cls category]) asSet.
-                categories size == 1 ifTrue:[
-                    msg := (resources string:'Category: %1'
-                                      with:categories anElement allBold).
-                ].
-            ].
-        ].
+	self selectedCategoriesValue size > 1 ifTrue:[
+	    singleSelectedClass := self theSingleSelectedClass.
+	    singleSelectedClass notNil ifTrue:[
+		msg := (resources string:'Category: %2'
+				  with:singleSelectedClass name allBold
+				  with:singleSelectedClass category allBold).
+	    ] ifFalse:[
+
+		selectedClasses := self selectedClassesValue.
+		categories := (selectedClasses collect:[:cls | cls category]) asSet.
+		categories size == 1 ifTrue:[
+		    msg := (resources string:'Category: %1'
+				      with:categories anElement allBold).
+		].
+	    ].
+	].
     ].
 
     msg isNil ifTrue:[
-        msg := self getClassInfo.
+	msg := self getClassInfo.
     ].
     msg notNil ifTrue:[
-        self showInfo:msg.
-        ^ self.
+	self showInfo:msg.
+	^ self.
     ].
     self clearInfo.
 
@@ -51911,20 +52480,20 @@
 
     methods := self selectedMethodsValue.
     methods size > 0 ifTrue:[
-        "/ protocol-selection feedBack:
-        "/ update the protocol-selection, if '* all *' is in its selection
-        "/ (add the selected methods categories to the protocol-selection)
-        selectedProtocolsHolder := self selectedProtocols.
-        selectedProtocols := selectedProtocolsHolder value.
-        (selectedProtocols size > 0 and:[selectedProtocols includes:(BrowserList nameListEntryForALL)])
-        ifTrue:[
-            oldSelectedProtocols := selectedProtocols asSet.
-            selectedProtocols := Set with:(BrowserList nameListEntryForALL).
-            selectedProtocols addAll:(methods collect:[:eachMethod | eachMethod category]).
-            selectedProtocols ~= oldSelectedProtocols ifTrue:[
-                self selectProtocols:selectedProtocols.
-            ].
-        ].
+	"/ protocol-selection feedBack:
+	"/ update the protocol-selection, if '* all *' is in its selection
+	"/ (add the selected methods categories to the protocol-selection)
+	selectedProtocolsHolder := self selectedProtocols.
+	selectedProtocols := selectedProtocolsHolder value.
+	(selectedProtocols size > 0 and:[selectedProtocols includes:(BrowserList nameListEntryForALL)])
+	ifTrue:[
+	    oldSelectedProtocols := selectedProtocols asSet.
+	    selectedProtocols := Set with:(BrowserList nameListEntryForALL).
+	    selectedProtocols addAll:(methods collect:[:eachMethod | eachMethod category]).
+	    selectedProtocols ~= oldSelectedProtocols ifTrue:[
+		self selectProtocols:selectedProtocols.
+	    ].
+	].
     ].
 
     "Modified: / 28-02-2012 / 16:36:38 / cg"
@@ -51932,8 +52501,8 @@
 
 withActivityNotificationsRedirectedToInfoLabelDo:aBlock
     ActivityNotification handle:[:ex |
-        self showInfo:(ex messageText).
-        ex proceed.
+	self showInfo:(ex messageText).
+	ex proceed.
     ] do:aBlock
 
     "Created: / 01-03-2007 / 17:45:27 / cg"
@@ -51941,10 +52510,10 @@
 
 withSearchCursorDo:aBlock
     [
-        self busyLabel:'searching...'.
-        self withCursor:(Cursor questionMark) do:aBlock
+	self busyLabel:'searching...'.
+	self withCursor:(Cursor questionMark) do:aBlock
     ] ensure:[
-        self normalLabel
+	self normalLabel
     ]
 ! !
 
@@ -51962,11 +52531,11 @@
     | sel |
     sel := UserPreferences current at: #searchCompletionBlock ifAbsent:[nil].
     sel notNil ifTrue:[
-        ^self perform: ('searchCompletionBlock_' , sel) asSymbol ifNotUnderstood:[
-            self searchCompletionBlock_Standard
-        ].        
-    ].
-    ^self searchCompletionBlock_Standard 
+	^self perform: ('searchCompletionBlock_' , sel) asSymbol ifNotUnderstood:[
+	    self searchCompletionBlock_Standard
+	].
+    ].
+    ^self searchCompletionBlock_Standard
 
     "
     UserPreferences current removeKey: #searchCompletionBlock.
@@ -52000,18 +52569,18 @@
 
     ^[:partialName| | env |
     env := self theSingleSelectedNamespace ? #Smalltalk.
-    env = NavigatorModel nameListEntryForALL 
-        ifTrue:[env := #Smalltalk].
+    env = NavigatorModel nameListEntryForALL
+	ifTrue:[env := #Smalltalk].
     env := Smalltalk at: env.
     partialName isEmptyOrNil
-        ifTrue:
-            [#('' #())]
-        ifFalse:
-            [partialName first isUppercase
-                ifTrue:
-                    [DoWhatIMeanSupport classnameCompletion: partialName inEnvironment: env]
-                ifFalse:
-                    [DoWhatIMeanSupport selectorCompletion: partialName inEnvironment: env]]]
+	ifTrue:
+	    [#('' #())]
+	ifFalse:
+	    [partialName first isUppercase
+		ifTrue:
+		    [DoWhatIMeanSupport classnameCompletion: partialName inEnvironment: env]
+		ifFalse:
+		    [DoWhatIMeanSupport selectorCompletion: partialName inEnvironment: env]]]
 
     "Modified: / 10-02-2010 / 08:47:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 04-08-2011 / 19:05:28 / cg"
@@ -52049,32 +52618,32 @@
 
 
     withPrefix ifTrue:[
-        matcher := [:cls|pattern match: cls name]
-    ] ifFalse:[
-        matcher := [:cls|pattern match: cls nameWithoutPrefix]
+	matcher := [:cls|pattern match: cls name]
+    ] ifFalse:[
+	matcher := [:cls|pattern match: cls nameWithoutPrefix]
     ].
 
     relax := 1.
     [ matches isEmptyOrNil and:[relax <= 3] ] whileTrue:[
-        matches := OrderedCollection new.
-        env keysDo:[:nm|
-            | cls |
-
-            cls := env at: nm.
-            (cls notNil and:[cls isBehavior and:[(matches includesIdentical: cls)not]]) ifTrue:[
-                (matcher value: cls) ifTrue:[
-                    matches add: cls
-                ].
-            ].
-        ].
-        relax := relax + 1.
+	matches := OrderedCollection new.
+	env keysDo:[:nm|
+	    | cls |
+
+	    cls := env at: nm.
+	    (cls notNil and:[cls isBehavior and:[(matches includesIdentical: cls)not]]) ifTrue:[
+		(matcher value: cls) ifTrue:[
+		    matches add: cls
+		].
+	    ].
+	].
+	relax := relax + 1.
     ].
 
     matches isEmpty ifTrue:[
-        ^ #(nil #())
-    ] ifFalse:[
-        matches := matches collect:[:cls|self searchCompletionEntryForClass: cls showPrefix: withPrefix].
-        ^ { matches first . matches }
+	^ #(nil #())
+    ] ifFalse:[
+	matches := matches collect:[:cls|self searchCompletionEntryForClass: cls showPrefix: withPrefix].
+	^ { matches first . matches }
     ]
 
     "Created: / 06-04-2012 / 12:56:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -52084,7 +52653,7 @@
 
 checkAcceptedMethod:aMethod inClass:aClass
     "do some semantic checks on the just accepted method:
-        does new method redefine an inherited method, which does the same ?
+	does new method redefine an inherited method, which does the same ?
     "
 
     |msg selector subMethods answer|
@@ -52093,72 +52662,72 @@
 
     "/ skip for some...
     (aClass isMeta) ifTrue:[
-        (AbstractSourceCodeManager isVersionMethodSelector:selector) ifTrue:[
-            ^ self
-        ].
-        ( #(
-            documentation
-            copyright
-            legalCopyright
-        ) includes:selector) ifTrue:[
-            ^ self
-        ].
+	(AbstractSourceCodeManager isVersionMethodSelector:selector) ifTrue:[
+	    ^ self
+	].
+	( #(
+	    documentation
+	    copyright
+	    legalCopyright
+	) includes:selector) ifTrue:[
+	    ^ self
+	].
     ].
 
     (self canUseRefactoringParser) ifTrue:[
-        "/ does new method redefine an inherited method,
-        "/ which does the same ?
-        msg := self checkIfSameSemanticsRedefinedWith:aMethod inClass:aClass.
-        msg notNil ifTrue:[
-            (Dialog
-                confirm:msg withCRs
-                title:'Remove duplicate method'
-                yesLabel:(resources string:'Remove Here')
-                noLabel:(resources string:'Keep')
-                initialAnswer:false)
-            ifTrue:[
-                self doRemoveMethodsUnconfirmed:(Array with:aMethod)
-            ].
-            ^ self
-        ].
-
-        subMethods := OrderedCollection new.
-        aClass allSubclassesDo:[:eachInheritingClass |
-            |redefiningMethod|
-
-            redefiningMethod := eachInheritingClass compiledMethodAt:selector.
-            redefiningMethod notNil ifTrue:[
-                msg := self checkIfSameSemanticsRedefinedWith:redefiningMethod inClass:eachInheritingClass.
-                msg notNil ifTrue:[
-                    (eachInheritingClass superclass whichClassIncludesSelector:selector) == aClass
-                    ifTrue:[
-                        subMethods add:redefiningMethod.
-                    ]
-                ].
-            ]
-        ].
-        subMethods size > 0 ifTrue:[
-            msg := 'The same code is found in the subclass(es):\\'.
-            subMethods do:[:eachMethod | msg := msg , '    ' , eachMethod mclass name , '\'].
-            msg := msg , '\You may want to remove it there.'.
-            answer := Dialog
-                confirmWithCancel:msg withCRs
-                labels:(resources array:#('Keep' 'Remove here' 'Remove in Subclass(es)'))
-                values:#(true #removeHere #removeThere)
-                default:1.
-            answer == #removeHere ifTrue:[
-                self doRemoveMethodsUnconfirmed:(Array with:aMethod)
-            ] ifFalse:[
-                answer == #removeThere ifTrue:[
-                    self doRemoveMethodsUnconfirmed:subMethods
-                ]
-            ]
-        ]
+	"/ does new method redefine an inherited method,
+	"/ which does the same ?
+	msg := self checkIfSameSemanticsRedefinedWith:aMethod inClass:aClass.
+	msg notNil ifTrue:[
+	    (Dialog
+		confirm:msg withCRs
+		title:'Remove duplicate method'
+		yesLabel:(resources string:'Remove Here')
+		noLabel:(resources string:'Keep')
+		initialAnswer:false)
+	    ifTrue:[
+		self doRemoveMethodsUnconfirmed:(Array with:aMethod)
+	    ].
+	    ^ self
+	].
+
+	subMethods := OrderedCollection new.
+	aClass allSubclassesDo:[:eachInheritingClass |
+	    |redefiningMethod|
+
+	    redefiningMethod := eachInheritingClass compiledMethodAt:selector.
+	    redefiningMethod notNil ifTrue:[
+		msg := self checkIfSameSemanticsRedefinedWith:redefiningMethod inClass:eachInheritingClass.
+		msg notNil ifTrue:[
+		    (eachInheritingClass superclass whichClassIncludesSelector:selector) == aClass
+		    ifTrue:[
+			subMethods add:redefiningMethod.
+		    ]
+		].
+	    ]
+	].
+	subMethods size > 0 ifTrue:[
+	    msg := 'The same code is found in the subclass(es):\\'.
+	    subMethods do:[:eachMethod | msg := msg , '    ' , eachMethod mclass name , '\'].
+	    msg := msg , '\You may want to remove it there.'.
+	    answer := Dialog
+		confirmWithCancel:msg withCRs
+		labels:(resources array:#('Keep' 'Remove here' 'Remove in Subclass(es)'))
+		values:#(true #removeHere #removeThere)
+		default:1.
+	    answer == #removeHere ifTrue:[
+		self doRemoveMethodsUnconfirmed:(Array with:aMethod)
+	    ] ifFalse:[
+		answer == #removeThere ifTrue:[
+		    self doRemoveMethodsUnconfirmed:subMethods
+		]
+	    ]
+	]
     ].
 
     ParserFlags warnAboutBadComments ifFalse:[
-        "/ check for empty method comment
-        self checkForEmptyMethodComment:aMethod inClass:aClass.
+	"/ check for empty method comment
+	self checkForEmptyMethodComment:aMethod inClass:aClass.
     ].
 
 "/    "/ super-send probably missing ?
@@ -52183,10 +52752,10 @@
 
     firstComment := comments first.
     firstComment string withoutSeparators isEmpty ifTrue:[
-        firstComment isEndOfLineComment ifFalse:[
-            Dialog warn:'Useless (empty) Method-Comment. Please add flesh or remove it !!'.
-            ^ self
-        ]
+	firstComment isEndOfLineComment ifFalse:[
+	    Dialog warn:'Useless (empty) Method-Comment. Please add flesh or remove it !!'.
+	    ^ self
+	]
     ].
 
     "Modified (format): / 06-03-2012 / 18:38:55 / cg"
@@ -52206,91 +52775,91 @@
 
     "/ these are meant to be empty nad only contain different comments...
     ( #(
-        documentation
-        version
-        examples
-        copyright
-        history
-        initialize      "/ because that is not invoked if only inherited
+	documentation
+	version
+	examples
+	copyright
+	history
+	initialize      "/ because that is not invoked if only inherited
        ) includes:sel) ifTrue:[
-        aClass isMeta ifTrue:[
-            ^ nil
-        ]
+	aClass isMeta ifTrue:[
+	    ^ nil
+	]
     ].
 
     superCls := aClass superclass.
     superCls notNil ifTrue:[
-        implClass := superCls whichClassIncludesSelector:sel.
+	implClass := superCls whichClassIncludesSelector:sel.
     ].
     implClass isNil ifTrue:[^ nil].
 
     "/ ok, it is redefined
     methodThere := implClass compiledMethodAt:sel.
     treeHere := RBParser
-                    parseMethod:methodHere source ? ''
-                    onError: [:aString :position | ^ nil "ignore any error"].
+		    parseMethod:methodHere source ? ''
+		    onError: [:aString :position | ^ nil "ignore any error"].
     treeHere isNil ifTrue:[^ nil].
     treeThere := RBParser
-                    parseMethod:methodThere source ? ''
-                    onError: [:aString :position | ^ nil "ignore any error"].
+		    parseMethod:methodThere source ? ''
+		    onError: [:aString :position | ^ nil "ignore any error"].
     treeThere isNil ifTrue:[^ nil].
 
     dictionary := Dictionary new.
     (treeHere body equalTo: treeThere body withMapping: dictionary) ifTrue:[
-        mClass := methodHere mclass theNonMetaclass.
-        "/ must try again, but remove mappings to classVariables and classInstanceVariables ...
-        mClass allClassVarNames do:[:each |
-            dictionary removeKey:each ifAbsent:nil.
-            dictionary removeValue:each ifAbsent:nil.
-        ].
-
-        mClass allInstVarNames do:[:each |
+	mClass := methodHere mclass theNonMetaclass.
+	"/ must try again, but remove mappings to classVariables and classInstanceVariables ...
+	mClass allClassVarNames do:[:each |
+	    dictionary removeKey:each ifAbsent:nil.
+	    dictionary removeValue:each ifAbsent:nil.
+	].
+
+	mClass allInstVarNames do:[:each |
 "/            dictionary removeKey:each ifAbsent:nil.
 "/            dictionary removeValue:each ifAbsent:nil.
-            dictionary at:each put:each
-        ].
-        mClass allClassVarNames do:[:each |
-            dictionary at:each put:each
-        ].
-
-        (treeHere body equalTo: treeThere body withMapping: dictionary) ifTrue:[
-            "/ super and here mean something different in a subclass; may not ne present.
-            (dictionary keys contains:[:key | (key = 'super') or:[key = 'here']]) ifFalse:[
-                (dictionary values contains:[:value | value = 'super' or:[value = 'here']]) ifFalse:[
-                    "/ look at the mapping dictionary ..
-                    "/ remove equivalently mapped ones ..
-                    dictionary keys
-                        select:[:key | (dictionary at:key) = key]
-                        thenDo:[:key | dictionary removeKey:key].
-
-                    "/ now, no upper-case variables are allowed ...
-                    (dictionary keys contains:[:key | key isUppercaseFirst]) ifFalse:[
-                        "/ ignore (possibly renamed) arguments ...
-                        dictionary keys
-                            select:[:key | treeHere arguments contains:[:argVar | argVar name = key]]
-                            thenDo:[:eachArgHere |
-                                |argIndexHere argThere argIndexThere|
-
-                                argIndexHere := treeHere arguments findFirst:[:argVar | argVar name = eachArgHere].
-                                argThere := dictionary at:eachArgHere.
-                                argIndexThere := treeThere arguments findFirst:[:argVar | argVar name = argThere].
-                                argIndexHere == argIndexThere ifTrue:[
-                                    dictionary removeKey:eachArgHere
-                                ].
-                            ].
-
-                        remainingRenames := dictionary keys.
-                        (remainingRenames contains:[:key | treeHere arguments contains:[:argVar | argVar name = key]])
-                        ifFalse:[
-                            (remainingRenames contains:[:key | treeThere arguments contains:[:argVar | argVar name = key]])
-                            ifFalse:[
-                                ^ 'This method''s functionality is already inherited from ', implClass name , '.\\You may want to remove it here.'.
-                            ]
-                        ]
-                    ].
-                ].
-            ].
-        ].
+	    dictionary at:each put:each
+	].
+	mClass allClassVarNames do:[:each |
+	    dictionary at:each put:each
+	].
+
+	(treeHere body equalTo: treeThere body withMapping: dictionary) ifTrue:[
+	    "/ super and here mean something different in a subclass; may not ne present.
+	    (dictionary keys contains:[:key | (key = 'super') or:[key = 'here']]) ifFalse:[
+		(dictionary values contains:[:value | value = 'super' or:[value = 'here']]) ifFalse:[
+		    "/ look at the mapping dictionary ..
+		    "/ remove equivalently mapped ones ..
+		    dictionary keys
+			select:[:key | (dictionary at:key) = key]
+			thenDo:[:key | dictionary removeKey:key].
+
+		    "/ now, no upper-case variables are allowed ...
+		    (dictionary keys contains:[:key | key isUppercaseFirst]) ifFalse:[
+			"/ ignore (possibly renamed) arguments ...
+			dictionary keys
+			    select:[:key | treeHere arguments contains:[:argVar | argVar name = key]]
+			    thenDo:[:eachArgHere |
+				|argIndexHere argThere argIndexThere|
+
+				argIndexHere := treeHere arguments findFirst:[:argVar | argVar name = eachArgHere].
+				argThere := dictionary at:eachArgHere.
+				argIndexThere := treeThere arguments findFirst:[:argVar | argVar name = argThere].
+				argIndexHere == argIndexThere ifTrue:[
+				    dictionary removeKey:eachArgHere
+				].
+			    ].
+
+			remainingRenames := dictionary keys.
+			(remainingRenames contains:[:key | treeHere arguments contains:[:argVar | argVar name = key]])
+			ifFalse:[
+			    (remainingRenames contains:[:key | treeThere arguments contains:[:argVar | argVar name = key]])
+			    ifFalse:[
+				^ 'This method''s functionality is already inherited from ', implClass name , '.\\You may want to remove it here.'.
+			    ]
+			]
+		    ].
+		].
+	    ].
+	].
     ].
     ^ nil
 
@@ -52307,21 +52876,21 @@
     aClass compilerClass == Compiler ifFalse:[^ false].
 
     methodHere selector == #initialize ifTrue:[
-        aClass isMeta ifTrue:[^ false].
-        aClass == Object ifTrue:[^ false].
-        aClass superclass == Object ifTrue:[^ false].
+	aClass isMeta ifTrue:[^ false].
+	aClass == Object ifTrue:[^ false].
+	aClass superclass == Object ifTrue:[^ false].
     ].
 
     sel := methodHere selector.
 
     "/ see if new method already invokes the redefined super method
     (methodHere referencesLiteral:sel) ifTrue:[
-        (methodHere messagesSentToSuper includes:sel) ifTrue:[ ^ false ]
+	(methodHere messagesSentToSuper includes:sel) ifTrue:[ ^ false ]
     ].
 
     superCls := aClass superclass.
     superCls notNil ifTrue:[
-        implClass := superCls whichClassIncludesSelector:sel.
+	implClass := superCls whichClassIncludesSelector:sel.
     ].
     implClass isNil ifTrue:[^ false].
 
@@ -52329,28 +52898,28 @@
     methodThere := implClass compiledMethodAt:sel.
 
     (methodThere notNil and:[methodThere referencesLiteral:sel]) ifTrue:[
-        (methodThere messagesSentToSuper includes:sel) ifTrue:[
-            self information:(resources
-                                string:'Could it be possible, that you forgot a ''super %1''\(I found a ''super %1'' in the overwritten #%1-method) ?'
-                                with:sel) withCRs.
-            ^ true
-        ]
+	(methodThere messagesSentToSuper includes:sel) ifTrue:[
+	    self information:(resources
+				string:'Could it be possible, that you forgot a ''super %1''\(I found a ''super %1'' in the overwritten #%1-method) ?'
+				with:sel) withCRs.
+	    ^ true
+	]
     ].
 
     "/ see if the redefined method is empty
     methodThere notNil ifTrue:[
-        parser := Parser parseMethod:methodThere source in:methodThere mclass.
-        treeThere := parser tree.
-        treeThere isNil ifTrue:[
-            "/ yes, empty
-            ^ false
-        ].
-        treeThere isReturnNode ifTrue:[
-            treeThere expression isSelf ifTrue:[
-                "/ yes, a simple ^ self
-                ^ false
-            ].
-        ].
+	parser := Parser parseMethod:methodThere source in:methodThere mclass.
+	treeThere := parser tree.
+	treeThere isNil ifTrue:[
+	    "/ yes, empty
+	    ^ false
+	].
+	treeThere isReturnNode ifTrue:[
+	    treeThere expression isSelf ifTrue:[
+		"/ yes, a simple ^ self
+		^ false
+	    ].
+	].
     ].
 
     "/ look if all any subclasses of the superclass do a super-send
@@ -52379,12 +52948,12 @@
     (aMatcher canMatchMethod:mthd) ifFalse: [^ false].
 
     parseTree := RBParser
-            parseMethod:mthd source
-            onError: [:str :pos | Transcript showCR:str. Transcript showCR:pos.
-                                  nil].
+	    parseMethod:mthd source
+	    onError: [:str :pos | Transcript showCR:str. Transcript showCR:pos.
+				  nil].
     parseTree isNil ifTrue:[^ false ].
     (aMatcher executeTree: parseTree initialAnswer: false) ifTrue:[
-        ^ true
+	^ true
     ].
     ^ false
 !
@@ -52397,11 +52966,11 @@
 
     comment := mthd comment.
     cls isMeta ifTrue:[
-        (AbstractSourceCodeManager isVersionMethodSelector:sel) ifTrue:[^ nil].
-        sel == #documentation ifTrue:[
-            comment isBlank ifTrue:[ ^ 'no documentation in documentation method' ].
-            ^ nil    
-        ].
+	(AbstractSourceCodeManager isVersionMethodSelector:sel) ifTrue:[^ nil].
+	sel == #documentation ifTrue:[
+	    comment isBlank ifTrue:[ ^ 'no documentation in documentation method' ].
+	    ^ nil
+	].
     ].
 
     comment size == 0 ifTrue:[^ 'missing comment' ].
@@ -52417,7 +52986,7 @@
 
     pkg := Smalltalk at:#'stx_goodies_refactoryBrowser_lint'.
     (pkg isNil or:[ pkg isFullyLoaded not ]) ifTrue:[
-        Smalltalk loadPackage:#'stx:goodies/refactoryBrowser/lint' asAutoloaded:false
+	Smalltalk loadPackage:#'stx:goodies/refactoryBrowser/lint' asAutoloaded:false
     ].
 
     "
@@ -52443,42 +53012,42 @@
 "/ therefore, isEmpty returns true here, so we will be always asked twice!!
 
     rule isEmptyInTree ifTrue:[
-        ruleSetSymbol ~~ #smalllintRulesFromUser ifTrue:[
-            rule := self smalllintRulesFromUser.
-            rule isNil ifTrue:[ ^ self ].
-        ]
+	ruleSetSymbol ~~ #smalllintRulesFromUser ifTrue:[
+	    rule := self smalllintRulesFromUser.
+	    rule isNil ifTrue:[ ^ self ].
+	]
     ].
 
     self showMessage:'Checking code...'
-        while:[
-            |showResult|
-
-            self smalllintRunRule:rule onEnvironment:anEnvironment.
-            showResult := true.
-            [rule notNil and:[rule isEmpty]] whileTrue:[
-                (Dialog confirm:'Nothing special found.\\Proceed to select more/different lint rules.' withCRs) ifTrue:[
-                    rule := self smalllintRulesFromUser.
-                    rule notNil ifTrue:[
-                        self smalllintRunRule:rule onEnvironment:anEnvironment.
-                    ].
-                ] ifFalse:[
-                    rule := nil
-                ].
-            ].
-            rule notNil ifTrue:[
-                self 
-                    spawnSmalllintBrowserByRuleFor:rule
-                    in:#newBuffer
-                    label:'SmallLint results for ' , anEnvironment label
-            ].
-        ].
+	whileExecutingBackgroundAction:[
+	    |showResult|
+
+	    self smalllintRunRule:rule onEnvironment:anEnvironment.
+	    showResult := true.
+	    [rule notNil and:[rule isEmpty]] whileTrue:[
+		(Dialog confirm:'Nothing special found.\\Proceed to select more/different lint rules.' withCRs) ifTrue:[
+		    rule := self smalllintRulesFromUser.
+		    rule notNil ifTrue:[
+			self smalllintRunRule:rule onEnvironment:anEnvironment.
+		    ].
+		] ifFalse:[
+		    rule := nil
+		].
+	    ].
+	    rule notNil ifTrue:[
+		self
+		    spawnSmalllintBrowserByRuleFor:rule
+		    in:#newBuffer
+		    label:'SmallLint results for ' , anEnvironment label
+	    ].
+	].
 
     "Modified: / 15-12-2008 / 18:51:43 / Josef Grega <gregaj1@fel.cvut.cz>"
     "Modified: / 28-12-2008 / 14:40:01 / bazantj <enter your email here>"
     "Created: / 24-02-2009 / 11:02:57 / Jan Vrany <vranyj1@fel.cvut.cz>"
     "Modified: / 22-07-2009 / 14:38:30 / Jan Vrany <vranyj1@fel.cvut.cz>"
     "Modified: / 28-08-2010 / 20:45:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 07-03-2012 / 20:25:58 / cg"
+    "Modified: / 15-05-2012 / 10:46:02 / cg"
 !
 
 smalllintRulesAll
@@ -52500,13 +53069,13 @@
     self loadSmalllint.
     dlg := Tools::LintRuleSelectionDialog new.
     dlg selection: (LastLintRules ifNil:[nil"self smalllintRulesAll flattened"] ifNotNil:[LastLintRules flattened]).
-    ^ (dlg open; accepted) 
-            ifTrue:[ LastLintRules := dlg selectionAsRule ] 
-            ifFalse:[ nil ].
-
-    "
-        LastLintRules := nil.
-        Tools::NewSystemBrowser basicNew smalllintRulesFromUser
+    ^ (dlg open; accepted)
+	    ifTrue:[ LastLintRules := dlg selectionAsRule ]
+	    ifFalse:[ nil ].
+
+    "
+	LastLintRules := nil.
+	Tools::NewSystemBrowser basicNew smalllintRulesFromUser
     "
 
     "Created: / 17-04-2010 / 09:41:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -52516,11 +53085,11 @@
 
 smalllintRulesOrAll
     "Returns a set of user-selected SmallLint rules or all rules,
-     if no user selection is done"    
-
-   ^LastLintRules notNil 
-        ifTrue:[ LastLintRules ] 
-        ifFalse:[ self smalllintRulesAll ]
+     if no user selection is done"
+
+   ^LastLintRules notNil
+	ifTrue:[ LastLintRules ]
+	ifFalse:[ self smalllintRulesAll ]
 
     "Created: / 23-01-2012 / 10:59:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified (format): / 07-03-2012 / 20:05:40 / cg"
@@ -52533,16 +53102,16 @@
 
     rules := aLintRule flattened.
     rules withIndexDo:[:rule :index|
-        ProgressNotification new
-            messageText: ('Checking: ', rule name);
-            parameter: (rules size / 100) * index;
-            raiseRequest.
+	ProgressNotification new
+	    messageText: ('Checking: ', rule name);
+	    parameter: (rules size / 100) * index;
+	    raiseRequest.
        (SmalllintChecker runRule: rule onEnvironment: anEnvironment)
     ].
     ProgressNotification new
-        messageText: ('Done');
-        parameter: 100;
-        raiseRequest.
+	messageText: ('Done');
+	parameter: 100;
+	raiseRequest.
 
     "Modified: / 15-12-2008 / 18:51:43 / Josef Grega <gregaj1@fel.cvut.cz>"
     "Modified: / 28-12-2008 / 14:40:01 / bazantj <enter your email here>"
@@ -52553,153 +53122,153 @@
 
 spawnSmalllintBrowserByRuleFor: result in:where label:labelOrNil
     ^ self
-        newBrowserOrBufferDependingOn:where
-        label:labelOrNil
-        forSpec: #smallLintByRuleResultBrowserSpec
-        setupWith:[:browser | 
-            |methodGenerator classGenerator ruleGenerator|
-
-            ruleGenerator :=
-                Iterator on:[:whatToDo|
-                    result failedRules do:whatToDo].
-
-            methodGenerator :=
-                Iterator on: [:whatToDo|
-                    | selectedRules selectedClasses failedMethods |
-
-                    selectedClasses := browser selectedClasses value.
-                    selectedRules := browser selectedLintRules value.
-                    failedMethods := OrderedCollection new.
-                    selectedClasses isEmptyOrNil ifFalse:
-                        [selectedRules ? #() do:
-                            [:rule|
-                            failedMethods addAll:
-                                (rule failedMethodsInAnyOf: selectedClasses meta: self hasMetaSelected)].
-                    failedMethods do:
-                        [:mth|
-                        whatToDo
-                            value:mth containingClass
-                            value:mth category
-                            value:mth selector
-                            value:mth]]].
-
-            browser lintRuleListGenerator value:ruleGenerator.
-            browser selectorListGenerator value:methodGenerator.
-
-            browser selectedClasses
-                onChangeSend: #changed to: browser selectorListGenerator.
-            browser selectedLintRules
-                onChangeSend: #changed to: browser selectorListGenerator.
-            browser meta
-                onChangeSend: #changed to: browser selectorListGenerator.
-
-            "/ cg: does not work - why?
-            result failedRules size == 1 ifTrue:[
-                "/ autoselect the first one
-                browser selectedLintRules value:(result failedRules).
-            ].
-
-            "/self halt.
-            "
-            theMethodList isNil ifTrue:[
-                methodsOrMethodGeneratorBlock isBlock ifTrue:[
-                    theMethodList := methodsOrMethodGeneratorBlock value.
-                ] ifFalse:[
-                    theMethodList := methodsOrMethodGeneratorBlock copy.
-                ].
-            ].
-            perClassInfo := perClassInfoHolder value.
-            perMethodInfo := perMethodInfoHolder value.
-
-            methodGenerator := Iterator on:[:whatToDo |
-                                            theMethodList isNil ifTrue:[
-                                                methodsOrMethodGeneratorBlock isBlock ifTrue:[
-                                                    theMethodList := methodsOrMethodGeneratorBlock value.
-                                                ] ifFalse:[
-                                                    theMethodList := methodsOrMethodGeneratorBlock copy.
-                                                ].
-                                            ].
-                                            perClassInfo := perClassInfoHolder value.
-                                            perMethodInfo := perMethodInfoHolder value.
-
-                                            theMethodNameList := theMethodList collect:[:eachMethod | eachMethod mclass -> eachMethod selector].
-                                            theMethodNameList do:[:mAssoc |
-                                                |methodClass methodSelector method|
-
-                                                methodClass := mAssoc key.
-                                                methodSelector := mAssoc value.
-                                                methodClass notNil ifTrue:[
-                                                    method := methodClass compiledMethodAt:methodSelector.
-                                                    method notNil ifTrue:[
-                                                        whatToDo
-                                                            value:methodClass
-                                                            value:method category
-                                                            value:methodSelector
-                                                            value:method.
-                                                    ].
-                                                ].
-                                            ].
-                                            methodsOrMethodGeneratorBlock isBlock ifTrue:[
-                                                theMethodList := nil.
-                                            ].
-                                            whatToDo
-                                                value:nil
-                                                value:nil
-                                                value:nil
-                                                value:nil.
-                                      ].
-
-            sortHow notNil ifTrue:[brwsr sortBy value:sortHow].
-
-            brwsr selectorListGenerator value:methodGenerator.
-            perClassInfo notNil ifTrue:[
-                classGenerator := perClassInfo keys.
-                brwsr classListGenerator value:classGenerator.
-                brwsr meta value:false.
-            ].
-
-            perClassInfo notNil ifTrue:[
-                brwsr selectedClasses
-                    onChangeEvaluate:[
-                        |class infoText|
-
-                        brwsr selectedMethods value:nil.
-                        class := brwsr theSingleSelectedClass.
-                        class notNil ifTrue:[
-                            brwsr meta value:false.
-                            infoText := perClassInfoHolder value at:class theNonMetaclass ifAbsent:nil.
-                            infoText isNil ifTrue:[
-                                infoText := perClassInfo at:class theMetaclass ifAbsent:nil
-                            ]
-                        ].
-                        brwsr methodInfo value:infoText.
-                    ]
-            ].
-
-            perMethodInfo notNil ifTrue:[
-                brwsr selectedMethods
-                    onChangeEvaluate:[
-                        |mthd infoText|
-
-                        brwsr selectedClasses value:nil.
-                        mthd := brwsr theSingleSelectedMethod.
-                        mthd notNil ifTrue:[
-                            infoText := perMethodInfo at:mthd ifAbsent:nil
-                        ].
-                        brwsr methodInfo value:infoText.
-                    ]
-            ] ifFalse:[
-                (doSelect and:[theMethodList size == 1]) ifTrue:[
-                    brwsr selectMethods:(Array with:theMethodList first).
-                    brwsr methodsSelectionChanged.
-                ]
-            ].
-
-            methodsOrMethodGeneratorBlock isBlock ifTrue:[
-                theMethodList := nil 
-            ]
-            "
-        ]
+	newBrowserOrBufferDependingOn:where
+	label:labelOrNil
+	forSpec: #smallLintByRuleResultBrowserSpec
+	setupWith:[:browser |
+	    |methodGenerator classGenerator ruleGenerator|
+
+	    ruleGenerator :=
+		Iterator on:[:whatToDo|
+		    result failedRules do:whatToDo].
+
+	    methodGenerator :=
+		Iterator on: [:whatToDo|
+		    | selectedRules selectedClasses failedMethods |
+
+		    selectedClasses := browser selectedClasses value.
+		    selectedRules := browser selectedLintRules value.
+		    failedMethods := OrderedCollection new.
+		    selectedClasses isEmptyOrNil ifFalse:
+			[selectedRules ? #() do:
+			    [:rule|
+			    failedMethods addAll:
+				(rule failedMethodsInAnyOf: selectedClasses meta: self hasMetaSelected)].
+		    failedMethods do:
+			[:mth|
+			whatToDo
+			    value:mth containingClass
+			    value:mth category
+			    value:mth selector
+			    value:mth]]].
+
+	    browser lintRuleListGenerator value:ruleGenerator.
+	    browser selectorListGenerator value:methodGenerator.
+
+	    browser selectedClasses
+		onChangeSend: #changed to: browser selectorListGenerator.
+	    browser selectedLintRules
+		onChangeSend: #changed to: browser selectorListGenerator.
+	    browser meta
+		onChangeSend: #changed to: browser selectorListGenerator.
+
+	    "/ cg: does not work - why?
+	    result failedRules size == 1 ifTrue:[
+		"/ autoselect the first one
+		browser selectedLintRules value:(result failedRules).
+	    ].
+
+	    "/self halt.
+	    "
+	    theMethodList isNil ifTrue:[
+		methodsOrMethodGeneratorBlock isBlock ifTrue:[
+		    theMethodList := methodsOrMethodGeneratorBlock value.
+		] ifFalse:[
+		    theMethodList := methodsOrMethodGeneratorBlock copy.
+		].
+	    ].
+	    perClassInfo := perClassInfoHolder value.
+	    perMethodInfo := perMethodInfoHolder value.
+
+	    methodGenerator := Iterator on:[:whatToDo |
+					    theMethodList isNil ifTrue:[
+						methodsOrMethodGeneratorBlock isBlock ifTrue:[
+						    theMethodList := methodsOrMethodGeneratorBlock value.
+						] ifFalse:[
+						    theMethodList := methodsOrMethodGeneratorBlock copy.
+						].
+					    ].
+					    perClassInfo := perClassInfoHolder value.
+					    perMethodInfo := perMethodInfoHolder value.
+
+					    theMethodNameList := theMethodList collect:[:eachMethod | eachMethod mclass -> eachMethod selector].
+					    theMethodNameList do:[:mAssoc |
+						|methodClass methodSelector method|
+
+						methodClass := mAssoc key.
+						methodSelector := mAssoc value.
+						methodClass notNil ifTrue:[
+						    method := methodClass compiledMethodAt:methodSelector.
+						    method notNil ifTrue:[
+							whatToDo
+							    value:methodClass
+							    value:method category
+							    value:methodSelector
+							    value:method.
+						    ].
+						].
+					    ].
+					    methodsOrMethodGeneratorBlock isBlock ifTrue:[
+						theMethodList := nil.
+					    ].
+					    whatToDo
+						value:nil
+						value:nil
+						value:nil
+						value:nil.
+				      ].
+
+	    sortHow notNil ifTrue:[brwsr sortBy value:sortHow].
+
+	    brwsr selectorListGenerator value:methodGenerator.
+	    perClassInfo notNil ifTrue:[
+		classGenerator := perClassInfo keys.
+		brwsr classListGenerator value:classGenerator.
+		brwsr meta value:false.
+	    ].
+
+	    perClassInfo notNil ifTrue:[
+		brwsr selectedClasses
+		    onChangeEvaluate:[
+			|class infoText|
+
+			brwsr selectedMethods value:nil.
+			class := brwsr theSingleSelectedClass.
+			class notNil ifTrue:[
+			    brwsr meta value:false.
+			    infoText := perClassInfoHolder value at:class theNonMetaclass ifAbsent:nil.
+			    infoText isNil ifTrue:[
+				infoText := perClassInfo at:class theMetaclass ifAbsent:nil
+			    ]
+			].
+			brwsr methodInfo value:infoText.
+		    ]
+	    ].
+
+	    perMethodInfo notNil ifTrue:[
+		brwsr selectedMethods
+		    onChangeEvaluate:[
+			|mthd infoText|
+
+			brwsr selectedClasses value:nil.
+			mthd := brwsr theSingleSelectedMethod.
+			mthd notNil ifTrue:[
+			    infoText := perMethodInfo at:mthd ifAbsent:nil
+			].
+			brwsr methodInfo value:infoText.
+		    ]
+	    ] ifFalse:[
+		(doSelect and:[theMethodList size == 1]) ifTrue:[
+		    brwsr selectMethods:(Array with:theMethodList first).
+		    brwsr methodsSelectionChanged.
+		]
+	    ].
+
+	    methodsOrMethodGeneratorBlock isBlock ifTrue:[
+		theMethodList := nil
+	    ]
+	    "
+	]
 
     "Modified: / 22-07-2009 / 15:51:56 / Jan Vrany <vranyj1@fel.cvut.cz>"
     "Created: / 02-02-2010 / 20:05:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -52723,21 +53292,21 @@
 
     dontDoIt := (currentMethod := self theSingleSelectedMethod) isNil.
     dontDoIt := dontDoIt
-                or:[self doSyntaxColoring value ~~ true
-                or:[(self doImmediateSyntaxColoring) value ~~ true]].
+		or:[self doSyntaxColoring value ~~ true
+		or:[(self doImmediateSyntaxColoring) value ~~ true]].
 
     dontDoIt ifFalse:[
-        methodsClass := currentMethod mclass.
-        methodsClass isNil ifTrue:[
-            dontDoIt := true
-        ].
-        highlighterClass := self syntaxHighlighterForMethod:currentMethod.
+	methodsClass := currentMethod mclass.
+	methodsClass isNil ifTrue:[
+	    dontDoIt := true
+	].
+	highlighterClass := self syntaxHighlighterForMethod:currentMethod.
     ].
     highlighterClass isNil ifTrue:[
-        syntaxColoringProcess notNil ifTrue:[
-            self stopSyntaxHighlightProcess
-        ].
-        ^ self
+	syntaxColoringProcess notNil ifTrue:[
+	    self stopSyntaxHighlightProcess
+	].
+	^ self
     ].
 
     codeView := self codeView.
@@ -52749,84 +53318,84 @@
 "/    ].
 "/    codeView modifiedChannel setValue:false.
     syntaxColoringProcess notNil ifTrue:[
-        syntaxColoringProcessRunning ~~ true ifTrue:[
-            "/ process already created, but did not get a change to start yet;
-            ^ self
-        ].
-        self stopSyntaxHighlightProcess
+	syntaxColoringProcessRunning ~~ true ifTrue:[
+	    "/ process already created, but did not get a change to start yet;
+	    ^ self
+	].
+	self stopSyntaxHighlightProcess
     ].
     prio := Processor userBackgroundPriority - 1.
     codeView shown ifFalse:[
-        prio := prio - 1 max:1
+	prio := prio - 1 max:1
     ].
     syntaxColoringProcess := [
-                |oldCode newCode cls sensor|
-
-                [
-                    syntaxColoringProcessRunning := true.
-                    cls := methodsClass.
-                    (cls notNil and:[cls isObsolete]) ifTrue:[
-                        cls isMeta ifTrue:[
-                            cls := (Smalltalk at:cls theNonMetaclass name) class
-                        ] ifFalse:[
-                            cls := Smalltalk at:cls name
-                        ].
-                    ].
-                    codeView modified ifFalse:[
-                        oldCodeList := codeView list copy.
-                        codeView modified ifFalse:[
-                            oldCodeList isNil ifFalse:[
-                                oldCode := oldCodeList asStringWithoutEmphasis.
-                                codeView modified ifFalse:[
-                                    Screen currentScreenQuerySignal answer:device
-                                    do:[
-                                        Parser::ParseError handle:[:ex |
-                                            |errMsg|
-
-                                            errMsg := ex description asStringCollection first asString.
-
-                                            "/ Transcript topView raiseDeiconified.
-                                            "/ Transcript showCR:'ParseError: ', ex description.
+		|oldCode newCode cls sensor|
+
+		[
+		    syntaxColoringProcessRunning := true.
+		    cls := methodsClass.
+		    (cls notNil and:[cls isObsolete]) ifTrue:[
+			cls isMeta ifTrue:[
+			    cls := (Smalltalk at:cls theNonMetaclass name) class
+			] ifFalse:[
+			    cls := Smalltalk at:cls name
+			].
+		    ].
+		    codeView modified ifFalse:[
+			oldCodeList := codeView list copy.
+			codeView modified ifFalse:[
+			    oldCodeList isNil ifFalse:[
+				oldCode := oldCodeList asStringWithoutEmphasis.
+				codeView modified ifFalse:[
+				    Screen currentScreenQuerySignal answer:device
+				    do:[
+					Parser::ParseError handle:[:ex |
+					    |errMsg|
+
+					    errMsg := ex description asStringCollection first asString.
+
+					    "/ Transcript topView raiseDeiconified.
+					    "/ Transcript showCR:'ParseError: ', ex description.
 "/ self halt.
-                                            self showInfo:(errMsg colorizeAllWith:Color red).
-                                            newCode := nil.
-                                        ] do:[
-                                            self codeAspect == #method ifTrue:[
-                                                newCode := highlighterClass formatMethod:currentMethod source:oldCode in:cls
-                                            ] ifFalse:[
-                                                self codeAspect == #classDefinition ifTrue:[
-                                                    newCode := highlighterClass formatExpression:oldCode in:cls
-                                                ].
-                                            ].
-                                        ]
-                                    ].
-                                    newCode notNil ifTrue:[
-                                        codeView modified ifFalse:[
-                                            newCode := newCode asStringCollection.
-                                            codeView modified ifFalse:[
-                                                syntaxColoringProcess := nil.
-                                                (codeView := self codeView) notNil ifTrue:[
-                                                    "/ must add this event - and not been interrupted
-                                                    "/ by any arriving key-event.
-                                                    self showInfo:nil.
-                                                    codeView sensor
-                                                        pushUserEvent:#syntaxHighlightedCode:
-                                                        for:self
-                                                        withArguments:(Array with:newCode).
-                                                    self delayedUpdateBufferLabelWithCheckIfModified
-                                                ]
-                                            ]
-                                        ]
-                                    ]
-                                ]
-                            ]
-                        ]
-                    ]
-                ] ensure:[
-                    syntaxColoringProcessRunning := false.
-                    syntaxColoringProcess := nil
-                ]
-            ] forkAt:prio
+					    self showInfo:(errMsg colorizeAllWith:Color red).
+					    newCode := nil.
+					] do:[
+					    self codeAspect == #method ifTrue:[
+						newCode := highlighterClass formatMethod:currentMethod source:oldCode in:cls
+					    ] ifFalse:[
+						self codeAspect == #classDefinition ifTrue:[
+						    newCode := highlighterClass formatExpression:oldCode in:cls
+						].
+					    ].
+					]
+				    ].
+				    newCode notNil ifTrue:[
+					codeView modified ifFalse:[
+					    newCode := newCode asStringCollection.
+					    codeView modified ifFalse:[
+						syntaxColoringProcess := nil.
+						(codeView := self codeView) notNil ifTrue:[
+						    "/ must add this event - and not been interrupted
+						    "/ by any arriving key-event.
+						    self showInfo:nil.
+						    codeView sensor
+							pushUserEvent:#syntaxHighlightedCode:
+							for:self
+							withArguments:(Array with:newCode).
+						    self delayedUpdateBufferLabelWithCheckIfModified
+						]
+					    ]
+					]
+				    ]
+				]
+			    ]
+			]
+		    ]
+		] ensure:[
+		    syntaxColoringProcessRunning := false.
+		    syntaxColoringProcess := nil
+		]
+	    ] forkAt:prio
 
     "Modified: / 26-07-2011 / 10:28:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 17-08-2011 / 14:35:16 / cg"
@@ -52838,10 +53407,10 @@
     |p|
 
     (p := syntaxColoringProcess) notNil ifTrue:[
-        syntaxColoringProcess := nil.
-        p terminate.
-        "/ raise its prio to make it terminate quickly
-        p priority:(Processor userSchedulingPriority + 1)
+	syntaxColoringProcess := nil.
+	p terminate.
+	"/ raise its prio to make it terminate quickly
+	p priority:(Processor userSchedulingPriority + 1)
     ]
 !
 
@@ -52854,70 +53423,70 @@
 
     codeView := self codeView.
     codeView modified ifTrue:[
-        "/ new input arrived in the meantime
-
-        ^ self
+	"/ new input arrived in the meantime
+
+	^ self
     ].
     syntaxColoringProcess notNil ifTrue:[
-        "/ another coloring process has already been started.
-        "/ ignore this (leftover) code.
-
-        ^ self
+	"/ another coloring process has already been started.
+	"/ ignore this (leftover) code.
+
+	^ self
     ].
     self theSingleSelectedMethod isNil ifTrue:[
-        "/ have already switched to some other method,
-        "/ or closed.
-
-        ^ self
+	"/ have already switched to some other method,
+	"/ or closed.
+
+	^ self
     ].
     firstShown := codeView firstLineShown.
     lastShown := codeView lastLineShown.
     replaceAction := [:lNr :line |
-            |oldLine|
-
-            oldLine := list at:lNr ifAbsent:nil.
-            oldLine notNil ifTrue:[
-                line notNil ifTrue:[
-                    "/ this check is needed - there is a race
-                    "/ when the text is converted. This detects the
-                    "/ resulting error.
-                    "/ Certainly a kludge.
-
-                    oldLine string = line string ifTrue:[
-                        oldLine emphasis ~= line emphasis ifTrue:[
-                            codeView modifiedChannel removeDependent:self.
-                            list at:lNr put:line.
-                            codeView modifiedChannel addDependent:self.
-                            (lNr between:firstShown and:lastShown) ifTrue:[
-                                anyChange ifFalse:[
-                                    anyChange := true.
-                                    cursorWasOn := codeView hideCursor
-                                ].
-                                codeView redrawLine:lNr
-                            ]
-                        ]
-                    ]
-                ]
-            ]
-        ].
+	    |oldLine|
+
+	    oldLine := list at:lNr ifAbsent:nil.
+	    oldLine notNil ifTrue:[
+		line notNil ifTrue:[
+		    "/ this check is needed - there is a race
+		    "/ when the text is converted. This detects the
+		    "/ resulting error.
+		    "/ Certainly a kludge.
+
+		    oldLine string = line string ifTrue:[
+			oldLine emphasis ~= line emphasis ifTrue:[
+			    codeView modifiedChannel removeDependent:self.
+			    list at:lNr put:line.
+			    codeView modifiedChannel addDependent:self.
+			    (lNr between:firstShown and:lastShown) ifTrue:[
+				anyChange ifFalse:[
+				    anyChange := true.
+				    cursorWasOn := codeView hideCursor
+				].
+				codeView redrawLine:lNr
+			    ]
+			]
+		    ]
+		]
+	    ]
+	].
     anyChange := false.
     newLines := newCode asStringCollection.
     list := codeView list.
     list isNil ifTrue:[
-        codeView list:newLines.
-    ] ifFalse:[
-        "/ the cursor line first - thats where your eyes are ...
-        (l := codeView cursorLine) notNil ifTrue:[
-            l <= newLines size ifTrue:[
-                replaceAction value:l value:(newLines at:l)
-            ]
-        ].
-        newLines keysAndValuesDo:replaceAction.
-        anyChange ifTrue:[
-            cursorWasOn ifTrue:[
-                codeView showCursor
-            ]
-        ]
+	codeView list:newLines.
+    ] ifFalse:[
+	"/ the cursor line first - thats where your eyes are ...
+	(l := codeView cursorLine) notNil ifTrue:[
+	    l <= newLines size ifTrue:[
+		replaceAction value:l value:(newLines at:l)
+	    ]
+	].
+	newLines keysAndValuesDo:replaceAction.
+	anyChange ifTrue:[
+	    cursorWasOn ifTrue:[
+		codeView showCursor
+	    ]
+	]
     ].
 
     "Modified: / 09-10-2006 / 11:50:17 / cg"
@@ -52943,7 +53512,7 @@
     "HACK!!!!!!"
 
     highlighterClass == SyntaxHighlighter ifTrue:[
-        highlighterClass := SyntaxHighlighter2
+	highlighterClass := SyntaxHighlighter2
     ].
 
     ^ highlighterClass
@@ -52958,19 +53527,19 @@
 
     highlighterClass := mthd syntaxHighlighterClass.
     highlighterClass == #askClass ifTrue:[
-        highlighterClass := cls syntaxHighlighterClass.
+	highlighterClass := cls syntaxHighlighterClass.
     ].
     "HACK!!!!!!"
 
     highlighterClass == SyntaxHighlighter ifTrue:[
-        highlighterClass := SyntaxHighlighter2
+	highlighterClass := SyntaxHighlighter2
     ].
 
     (mthd isInstrumented
     and:[ self showCoverageInformation value ]) ifTrue:[
-        (highlighterClass isKindOf: SyntaxHighlighter class) ifTrue:[
-            highlighterClass := CodeCoverageHighlighter
-        ].
+	(highlighterClass isKindOf: SyntaxHighlighter class) ifTrue:[
+	    highlighterClass := CodeCoverageHighlighter
+	].
     ].
 
     ^ highlighterClass
@@ -52985,8 +53554,8 @@
     "return a holder on the current canvas"
 
     browserCanvas isNil ifTrue:[
-        browserCanvas := ValueHolder new.
-        browserCanvas value:(self newCanvasWithSpec:(self browserCanvasType ? #fullBrowserSpec))
+	browserCanvas := ValueHolder new.
+	browserCanvas value:(self newCanvasWithSpec:(self browserCanvasType ? #fullBrowserSpec))
     ].
     ^ browserCanvas
 
@@ -53020,7 +53589,7 @@
 browserCanvasTypeHolder
 
     ^(AspectAdaptor forAspect: #spec)
-        subjectChannel: self browserCanvas.
+	subjectChannel: self browserCanvas.
 
     "Created: / 07-06-2011 / 21:48:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -53030,12 +53599,12 @@
 
     | canvas |
     browserPageCanvas isNil ifTrue:[
-        browserPageCanvas := ValueHolder new.
-        canvas := SubCanvas new.
-        canvas client:self spec:#browserPageSpec builder: builder.
-        canvas level:0.
-        canvas origin:0.0@0.0 corner:1.0@1.0.
-        browserPageCanvas value: canvas.
+	browserPageCanvas := ValueHolder new.
+	canvas := SubCanvas new.
+	canvas client:self spec:#browserPageSpec builder: builder.
+	canvas level:0.
+	canvas origin:0.0@0.0 corner:1.0@1.0.
+	browserPageCanvas value: canvas.
     ].
     ^ browserPageCanvas
 
@@ -53045,8 +53614,8 @@
 
 bufferLabel:aString
     navigationState notNil ifTrue:[
-        navigationState browserLabel:aString.
-        self enqueueDelayedUpdateBufferLabel.
+	navigationState browserLabel:aString.
+	self enqueueDelayedUpdateBufferLabel.
     ].
 !
 
@@ -53106,7 +53675,7 @@
     codeView formatAction:[:code | self formatCode ].
     codeView menuHolder:self; menuMessage:#codeViewMenu.
     self stringSearchToolVisibleHolder value ifTrue:[
-        self codeView searchBarActionBlock: self searchBarActionBlock.
+	self codeView searchBarActionBlock: self searchBarActionBlock.
     ].
 !
 
@@ -53130,20 +53699,20 @@
     self updateCodeInfoAndStringSearchToolVisibility.
 
     editorNoteBook selectConditionBlock:
-        [:index |
-            |canSelect editorCanvas method|
-
-            canSelect := true.
-            self showSpecialResourceEditors value ifTrue:[
-                (method := self theSingleSelectedMethod) notNil ifTrue:[
-                    "/ toggling away from the special editor - see if it was modified and ask for accept if so
-                    navigationState modified ifTrue:[
-                        canSelect := self askIfModified.
-                    ]
-                ].
-            ].
-            canSelect
-        ].
+	[:index |
+	    |canSelect editorCanvas method|
+
+	    canSelect := true.
+	    self showSpecialResourceEditors value ifTrue:[
+		(method := self theSingleSelectedMethod) notNil ifTrue:[
+		    "/ toggling away from the special editor - see if it was modified and ask for accept if so
+		    navigationState modified ifTrue:[
+			canSelect := self askIfModified.
+		    ]
+		].
+	    ].
+	    canSelect
+	].
 !
 
 postBuildFixup
@@ -53151,44 +53720,44 @@
 
     newNavigationState := self navigationState.
     self assert:newNavigationState canvasType notNil.
-    newNavigationState isFullClassSourceBrowser 
-        ifTrue:[self hidePrivateClasses value:true.].
-    
+    newNavigationState isFullClassSourceBrowser
+	ifTrue:[self hidePrivateClasses value:true.].
+
     "/ newNavigationState setUpScrollableCodeView.
-    
-    self editorNoteBookCanvasHolder 
-        value:(newNavigationState scrollableCodeView).
+
+    self editorNoteBookCanvasHolder
+	value:(newNavigationState scrollableCodeView).
     self codeView formatAction:[:code | self formatCode].
     (self codeView)
-        menuHolder:self;
-        menuMessage:#codeViewMenu.
-
-    (UserPreferences current useCodeView2In: #Browser) 
-        ifTrue:[self codeView browserHolder value:self].
-
-    UserPreferences current useSearchBarInBrowser 
-        ifTrue:
-            ["/        self stringSearchToolVisibleHolder value:true.          "/ Initially hidden. Show search bar after pressing CTRL+f or clicking view menu
-            self codeView searchBarActionBlock:self searchBarActionBlock.].
+	menuHolder:self;
+	menuMessage:#codeViewMenu.
+
+    (UserPreferences current useCodeView2In: #Browser)
+	ifTrue:[self codeView browserHolder value:self].
+
+    UserPreferences current useSearchBarInBrowser
+	ifTrue:
+	    ["/        self stringSearchToolVisibleHolder value:true.          "/ Initially hidden. Show search bar after pressing CTRL+f or clicking view menu
+	    self codeView searchBarActionBlock:self searchBarActionBlock.].
     self normalLabel.
     orgModeHolder := self organizerMode.
-    newNavigationState isNameSpaceBrowser 
-        ifTrue:[orgModeHolder value:(OrganizerCanvas organizerModeNamespace)]
-        ifFalse:
-            [newNavigationState isCategoryBrowser 
-                ifTrue:[orgModeHolder value:(OrganizerCanvas organizerModeCategory)]
-                ifFalse:
-                    [newNavigationState isProjectBrowser 
-                        ifTrue:[orgModeHolder value:(OrganizerCanvas organizerModeProject)].].].
-    self theSingleSelectedMethod notNil 
-        ifTrue:
-            ["/ fetch the initially selected methods code
-            self methodsSelectionChanged.]
-        ifFalse:
-            [self theSingleSelectedClass notNil 
-                ifTrue:
-                    ["/ to show the classes definition initially
-                    self classSelectionChanged.].].
+    newNavigationState isNameSpaceBrowser
+	ifTrue:[orgModeHolder value:(OrganizerCanvas organizerModeNamespace)]
+	ifFalse:
+	    [newNavigationState isCategoryBrowser
+		ifTrue:[orgModeHolder value:(OrganizerCanvas organizerModeCategory)]
+		ifFalse:
+		    [newNavigationState isProjectBrowser
+			ifTrue:[orgModeHolder value:(OrganizerCanvas organizerModeProject)].].].
+    self theSingleSelectedMethod notNil
+	ifTrue:
+	    ["/ fetch the initially selected methods code
+	    self methodsSelectionChanged.]
+	ifFalse:
+	    [self theSingleSelectedClass notNil
+		ifTrue:
+		    ["/ to show the classes definition initially
+		    self classSelectionChanged.].].
     newNavigationState codeModifiedHolder addDependent:self.
 
     "Modified (format): / 05-07-2011 / 10:32:23 / cg"
@@ -53242,8 +53811,8 @@
     Smalltalk addDependent:self.
 
     self codeInfoVisible value ifTrue:[ self codeInfoVisibilityChanged ].
-    (self toolBarVisibleHolder value or:[self bookmarkBarVisibleHolder value])  
-            ifTrue:[ self toolBarOrBookmarkBarVisibilityChanged ].
+    (self toolBarVisibleHolder value or:[self bookmarkBarVisibleHolder value])
+	    ifTrue:[ self toolBarOrBookmarkBarVisibilityChanged ].
 
 
 "/    self editorNoteBookCanvasHolder value:(navigationState scrollableCodeView).
@@ -53267,8 +53836,8 @@
 
 searchFieldCreated:anInputField
     anInputField emptyFieldReplacementText:
-        "/(resources string:'Class Search & History').
-        (resources string:'Search Class/Selector (Ctrl-L)').
+	"/(resources string:'Class Search & History').
+	(resources string:'Search Class/Selector (Ctrl-L)').
 
     "Modified: / 09-02-2010 / 21:56:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 07-03-2012 / 11:59:16 / cg"
@@ -53281,7 +53850,7 @@
 
 windowLabel:aString
     navigationState notNil ifTrue:[
-        navigationState browserLabel:aString
+	navigationState browserLabel:aString
     ].
     self normalLabel.
 ! !
@@ -53292,17 +53861,17 @@
     |methodsResources|
 
     (methodsResources := aMethod resources) notEmptyOrNil ifTrue:[
-        #( #image #fileImage #programImage #menu #canvas #help #tableColumns ) 
-        do:[:triedResourceType |
-            |editorCanvas list|
-
-            (methodsResources includesKey:triedResourceType) ifTrue:[
-                editorCanvas := navigationState specialEditorCanvasForResourceType:triedResourceType.
-                editorCanvas notNil ifTrue:[
-                    ^ editorCanvas
-                ].
-            ].
-        ].
+	#( #image #fileImage #programImage #menu #canvas #help #tableColumns )
+	do:[:triedResourceType |
+	    |editorCanvas list|
+
+	    (methodsResources includesKey:triedResourceType) ifTrue:[
+		editorCanvas := navigationState specialEditorCanvasForResourceType:triedResourceType.
+		editorCanvas notNil ifTrue:[
+		    ^ editorCanvas
+		].
+	    ].
+	].
     ].
     ^ nil
 !
@@ -53316,14 +53885,14 @@
     editorApplication masterApplication:self.
 
     aMethod notNil ifTrue:[
-        editorApplication
-            specClass:(aMethod mclass theNonMetaclass);
-            specSelector:(aMethod selector);
-            loadFromClass:(aMethod mclass theNonMetaclass)
-            andSelector:(aMethod selector).
-    ] ifFalse:[
-        editorApplication
-            specClass:(aClassOrNil theNonMetaclass)
+	editorApplication
+	    specClass:(aMethod mclass theNonMetaclass);
+	    specSelector:(aMethod selector);
+	    loadFromClass:(aMethod mclass theNonMetaclass)
+	    andSelector:(aMethod selector).
+    ] ifFalse:[
+	editorApplication
+	    specClass:(aClassOrNil theNonMetaclass)
     ].
 !
 
@@ -53332,9 +53901,9 @@
 
     view := navigationState documentationView.
     aClass isLoaded ifFalse:[
-        comment := 'Class is not loaded.'.
+	comment := 'Class is not loaded.'.
     ] ifTrue:[
-        comment := aClass comment.
+	comment := aClass comment.
     ].
     view scrolledView contents:comment.
 
@@ -53349,8 +53918,8 @@
 
     text := HTMLDocGenerator htmlDocOf:aClass.
     text notNil ifTrue:[
-        documentView top:(Smalltalk getSystemFileName:'doc/online/english/classDoc').
-        documentView nameSpaceForExecution:(aClass nameSpace).
+	documentView top:(Smalltalk getSystemFileName:'doc/online/english/classDoc').
+	documentView nameSpaceForExecution:(aClass nameSpace).
     ].
     documentView setText:text
 !
@@ -53421,13 +53990,13 @@
     mthd := self theSingleSelectedMethod.
     "/ temporary kludge: check if the selected method is really still in the class
     mthd notNil ifTrue:[
-        mthd mclass isNil ifTrue:[
-            mthd := nil
-        ].
-    ].
-    self
-        updateSpecialCodeEditorVisibilityForClass:cls
-        method:mthd
+	mthd mclass isNil ifTrue:[
+	    mthd := nil
+	].
+    ].
+    self
+	updateSpecialCodeEditorVisibilityForClass:cls
+	method:mthd
 
     "Created: / 17-08-2006 / 16:46:50 / cg"
 !
@@ -53446,28 +54015,28 @@
     actionList := OrderedCollection new.
     self showMultitabMode value ifTrue:[
 "/ self halt.
-        aMethod isNil ifTrue:[
-            "/ no method selected
-            aClassOrNil isNil ifTrue:[
-                (self selectedClassesValue isEmptyOrNil
-                and:[ self selectedCategoriesValue isEmptyOrNil
-                and:[ self selectedProjects value isEmptyOrNil
-                and:[ navigationState isNameSpaceBrowser not
-                      or:[ self selectedNamespaces value isEmptyOrNil ] ]]]) ifTrue:[
-                    "/ no class selected
-                    navigationState isFullBrowser ifTrue:[
-                        tabList add:'Welcome'.         actionList add:[ self updateCodeEditorVisibilityForWelcomePage ].
-                    ]
-                ].
-            ].
-            tabList add:'Definition'.      actionList add:[ self updateCodeEditorVisibilityForSource ].
-            aClassOrNil notNil ifTrue:[
+	aMethod isNil ifTrue:[
+	    "/ no method selected
+	    aClassOrNil isNil ifTrue:[
+		(self selectedClassesValue isEmptyOrNil
+		and:[ self selectedCategoriesValue isEmptyOrNil
+		and:[ self selectedProjects value isEmptyOrNil
+		and:[ navigationState isNameSpaceBrowser not
+		      or:[ self selectedNamespaces value isEmptyOrNil ] ]]]) ifTrue:[
+		    "/ no class selected
+		    navigationState isFullBrowser ifTrue:[
+			tabList add:'Welcome'.         actionList add:[ self updateCodeEditorVisibilityForWelcomePage ].
+		    ]
+		].
+	    ].
+	    tabList add:'Definition'.      actionList add:[ self updateCodeEditorVisibilityForSource ].
+	    aClassOrNil notNil ifTrue:[
 
 "/                tabList add:'Doc-Gen'.         actionList add:[ self updateCodeEditorVisibilityForHTMLDocumentationOf:aClassOrNil ].
 "/                tabList add:'Comment'.         actionList add:[ self updateCodeEditorVisibilityForDocumentationOf:aClassOrNil ].
-                ClassTreeGraphView notNil ifTrue:[
-                    tabList add:'Inheritance'.     actionList add:[ self updateCodeEditorVisibilityForInheritanceOf:aClassOrNil ].
-                ].
+		ClassTreeGraphView notNil ifTrue:[
+		    tabList add:'Inheritance'.     actionList add:[ self updateCodeEditorVisibilityForInheritanceOf:aClassOrNil ].
+		].
 "/                tabList add:'UML'.             actionList add:[ self updateCodeEditorVisibilityForUMLOf:aClassOrNil ].
 "/                tabList add:'Lint'.            actionList add:[ self updateCodeEditorVisibilityForLintOf:aClassOrNil ].
 "/                tabList add:'Rewrite'.         actionList add:[ self updateCodeEditorVisibilityForRewriteOf:aClassOrNil ].
@@ -53475,57 +54044,57 @@
 "/                ((aClassOrNil inheritsFrom:TestCase) and:[aClassOrNil isAbstract not]) ifTrue:[
 "/                    tabList add:'Test'.            actionList add:[ self updateCodeEditorVisibilityForTestRunsOf:aClassOrNil ].
 "/                ].
-            ].
-        ] ifFalse:[
-            tabList add:'Source'.          actionList add:[ self updateCodeEditorVisibilityForSource ].
+	    ].
+	] ifFalse:[
+	    tabList add:'Source'.          actionList add:[ self updateCodeEditorVisibilityForSource ].
 "/            tabList add:'Lint'.            actionList add:[ self updateCodeEditorVisibilityForLintOfMethod:aMethod ].
-        ].
-
-        self selectedMethodsValue size == 2 ifTrue:[
-            tabList add:'Diff'.
-            actionList add:[ self updateDiffViewerVisibilityFor:(self selectedMethodsValue first source)
-                                                            and:(self selectedMethodsValue second source) ].
-        ].
-    ] ifFalse:[
-        tabList add:'Source'.               actionList add:[ self updateCodeEditorVisibilityForSource ].
+	].
+
+	self selectedMethodsValue size == 2 ifTrue:[
+	    tabList add:'Diff'.
+	    actionList add:[ self updateDiffViewerVisibilityFor:(self selectedMethodsValue first source)
+							    and:(self selectedMethodsValue second source) ].
+	].
+    ] ifFalse:[
+	tabList add:'Source'.               actionList add:[ self updateCodeEditorVisibilityForSource ].
     ].
 
     self showSpecialResourceEditors value ifTrue:[
-        aMethod notNil ifTrue:[
-            editorCanvas := self specialEditorCanvasForMethod:aMethod.
-        ] ifFalse:[
-            (aClassOrNil notNil and:[aClassOrNil theNonMetaclass isProjectDefinition]) ifTrue:[
-                editorCanvas := navigationState specialEditorCanvasForResourceType:#projectDefinition.
-            ].
-        ].
+	aMethod notNil ifTrue:[
+	    editorCanvas := self specialEditorCanvasForMethod:aMethod.
+	] ifFalse:[
+	    (aClassOrNil notNil and:[aClassOrNil theNonMetaclass isProjectDefinition]) ifTrue:[
+		editorCanvas := navigationState specialEditorCanvasForResourceType:#projectDefinition.
+	    ].
+	].
     ].
 
     editorCanvas notNil ifTrue:[
-        hideSpecialEditor := false.
-        tabList add:(editorCanvas application class nameWithoutPrefix asUppercaseFirst).
-        actionList add:[ self updateCodeEditorVisibilityForCanvasEditor:editorCanvas class:aClassOrNil method:aMethod ].
+	hideSpecialEditor := false.
+	tabList add:(editorCanvas application class nameWithoutPrefix asUppercaseFirst).
+	actionList add:[ self updateCodeEditorVisibilityForCanvasEditor:editorCanvas class:aClassOrNil method:aMethod ].
     ].
 
     (hideSpecialEditor and:[tabList size = 1]) ifTrue:[
-        "/ sigh - setting an empty list also changes the selection to 0 (side effect in NoteBookView).
-        "/ To avoid flickering change messages, preSet its value to 0.
-        self selectedEditorNoteBookTabIndexHolder setValue:0.
-        self editorNoteBookListHolder value notEmptyOrNil ifTrue:[
-            self editorNoteBookListHolder value:#().
-        ].
-        self updateCodeEditorVisibilityForSource.
-    ] ifFalse:[
-        tabList = self editorNoteBookListHolder value ifFalse:[
-            self editorNoteBookListHolder value:tabList.
-        ].
+	"/ sigh - setting an empty list also changes the selection to 0 (side effect in NoteBookView).
+	"/ To avoid flickering change messages, preSet its value to 0.
+	self selectedEditorNoteBookTabIndexHolder setValue:0.
+	self editorNoteBookListHolder value notEmptyOrNil ifTrue:[
+	    self editorNoteBookListHolder value:#().
+	].
+	self updateCodeEditorVisibilityForSource.
+    ] ifFalse:[
+	tabList = self editorNoteBookListHolder value ifFalse:[
+	    self editorNoteBookListHolder value:tabList.
+	].
 
 "/        self selectedEditorNoteBookTabIndexHolder value:1.
-        "/ make one of the codeViews visible...
-        self selectedEditorNoteBookTabIndexHolder value == 0 ifTrue:[
-            self selectedEditorNoteBookTabIndexHolder value:1.
-            ^ self.
-        ].
-        (actionList at:(self selectedEditorNoteBookTabIndexHolder value)) value.
+	"/ make one of the codeViews visible...
+	self selectedEditorNoteBookTabIndexHolder value == 0 ifTrue:[
+	    self selectedEditorNoteBookTabIndexHolder value:1.
+	    ^ self.
+	].
+	(actionList at:(self selectedEditorNoteBookTabIndexHolder value)) value.
     ].
 
     "Created: / 17-08-2006 / 16:44:51 / cg"
@@ -53540,31 +54109,31 @@
     |nModified modifiedBuffers|
 
     buffers isNil ifTrue:[
-        (self
-            askIfModified:'Modifications have not been saved.\\Exit anyway ?'
-            default:false
-            withAccept:false
-            withCompare:true)
-        ifFalse:[
-            ^ self
-        ].
-    ] ifFalse:[
-        nModified := 0.
-        modifiedBuffers := buffers select:[:aBuffer | aBuffer modified].
-        modifiedBuffers do:[:aBuffer | |bufferIndex|
-            bufferIndex := buffers identityIndexOf:aBuffer.
-            self selectedBuffer value:bufferIndex.
-
-            (self
-                askIfModified:(resources stringWithCRs:'Buffer "%1" was modified.\\Exit anyway ?' with:aBuffer nameString allBold)
-                default:false
-                withAccept:(self canAcceptCodeIn:aBuffer)
-                withCompare:(self canCompareCodeIn:aBuffer)
-                in:aBuffer)
-            ifFalse:[
-                ^ self
-            ]
-        ]
+	(self
+	    askIfModified:'Modifications have not been saved.\\Exit anyway ?'
+	    default:false
+	    withAccept:false
+	    withCompare:true)
+	ifFalse:[
+	    ^ self
+	].
+    ] ifFalse:[
+	nModified := 0.
+	modifiedBuffers := buffers select:[:aBuffer | aBuffer modified].
+	modifiedBuffers do:[:aBuffer | |bufferIndex|
+	    bufferIndex := buffers identityIndexOf:aBuffer.
+	    self selectedBuffer value:bufferIndex.
+
+	    (self
+		askIfModified:(resources stringWithCRs:'Buffer "%1" was modified.\\Exit anyway ?' with:aBuffer nameString allBold)
+		default:false
+		withAccept:(self canAcceptCodeIn:aBuffer)
+		withCompare:(self canCompareCodeIn:aBuffer)
+		in:aBuffer)
+	    ifFalse:[
+		^ self
+	    ]
+	]
     ].
 
     Smalltalk removeDependent:self.
@@ -53584,17 +54153,17 @@
 
 !NewSystemBrowser methodsFor:'string search tool'!
 
-hideSearchBar 
+hideSearchBar
 
     self stringSearchToolVisibleHolder value: false.
 !
 
-searchBackwardWithSearchBar 
+searchBackwardWithSearchBar
 
     self stringSearchToolView application searchPreviousText.
 !
 
-searchBackwardWithSearchBarWith: aString 
+searchBackwardWithSearchBarWith: aString
 
     self setInitialSearchString: aString.
     self searchBackwardWithSearchBar.
@@ -53602,14 +54171,14 @@
 
 searchBarActionBlock
 
-    ^ [:how :view | 
-        how == #search ifTrue:[self showSearchBarWith: view searchPatternForSearchBar ].
-        how == #forward ifTrue:[self searchForwardWithSearchBarWith: view searchPatternForSearchBar ].
-        how == #backward ifTrue:[self searchBackwardWithSearchBarWith: view searchPatternForSearchBar ].
-    ]
-!
-
-searchForwardWithSearchBar 
+    ^ [:how :view |
+	how == #search ifTrue:[self showSearchBarWith: view searchPatternForSearchBar ].
+	how == #forward ifTrue:[self searchForwardWithSearchBarWith: view searchPatternForSearchBar ].
+	how == #backward ifTrue:[self searchBackwardWithSearchBarWith: view searchPatternForSearchBar ].
+    ]
+!
+
+searchForwardWithSearchBar
 
     self stringSearchToolView application searchNextText.
 !
@@ -53621,13 +54190,13 @@
     "Modified (comment): / 17-08-2011 / 15:08:29 / cg"
 !
 
-setFocusToSearchBar 
+setFocusToSearchBar
     |stringSearchTool|
 
-    stringSearchTool := self stringSearchToolView. 
+    stringSearchTool := self stringSearchToolView.
     stringSearchTool notNil ifTrue:[
-        stringSearchTool takeFocus.
-        stringSearchTool client searchBarOpened.
+	stringSearchTool takeFocus.
+	stringSearchTool client searchBarOpened.
     ].
 !
 
@@ -53636,13 +54205,13 @@
 
     stringSearchTool := self stringSearchToolView client.
     stringSearchTool notNil ifTrue:[
-        aString notEmptyOrNil ifTrue:[        
-            stringSearchTool initialSearchString: aString string.
-        ].
-    ].
-!
-
-showSearchBar 
+	aString notEmptyOrNil ifTrue:[
+	    stringSearchTool initialSearchString: aString string.
+	].
+    ].
+!
+
+showSearchBar
     self stringSearchToolVisibleHolder value: true.
 
     self setFocusToSearchBar
@@ -53655,8 +54224,8 @@
     self setInitialSearchString: aString.
     stringSearchTool := self stringSearchToolView client.
     stringSearchTool notNil ifTrue:[
-        stringSearchTool setFocusToSearchTextView.
-        stringSearchTool searchTextStarted.
+	stringSearchTool setFocusToSearchTextView.
+	stringSearchTool searchTextStarted.
     ].
 ! !
 
@@ -53669,30 +54238,30 @@
     allTheBest size == 1 ifTrue:[ ^ allTheBest first ].
 
     allTheBest size < 20 ifTrue:[
-        |menu idx exitKey|
-
-        menu := PopUpMenu labels:allTheBest.
-        menu hideOnKeyFilter:[:key | |hide|
-                hide := ( #( CursorDown CursorUp Escape Return ) includes: key) not.
-                hide ifTrue:[
-                    exitKey := key.
-                ].
-                hide].
-
-        idx := menu startUp.
-        idx == 0 ifTrue:[
-            exitKey notNil ifTrue:[
-                self codeView keyPress:exitKey x:0 y:0.
-            ].
-            ^ nil
-        ].
-        ^ allTheBest at:idx.
-    ] ifFalse:[
-        ^ Dialog
-           choose:(resources string:'Choose ',what)
-           fromList:allTheBest
-           lines:10
-           title:(resources string:'Code completion').
+	|menu idx exitKey|
+
+	menu := PopUpMenu labels:allTheBest.
+	menu hideOnKeyFilter:[:key | |hide|
+		hide := ( #( CursorDown CursorUp Escape Return ) includes: key) not.
+		hide ifTrue:[
+		    exitKey := key.
+		].
+		hide].
+
+	idx := menu startUp.
+	idx == 0 ifTrue:[
+	    exitKey notNil ifTrue:[
+		self codeView keyPress:exitKey x:0 y:0.
+	    ].
+	    ^ nil
+	].
+	^ allTheBest at:idx.
+    ] ifFalse:[
+	^ Dialog
+	   choose:(resources string:'Choose ',what)
+	   fromList:allTheBest
+	   lines:10
+	   title:(resources string:'Code completion').
     ].
 
     "Created: / 10-11-2006 / 14:00:53 / cg"
@@ -53704,15 +54273,15 @@
     "/ try local history
     localHistory := self navigationHistory.
     localHistory canGoBack ifTrue:[
-        self goBack.
-        ^ self
+	self goBack.
+	^ self
     ].
 
     "/ try global history
     globalHistory := self class classHistory.
     globalHistory size > 0 ifTrue:[
-        entry := globalHistory first.
-        self switchToFindHistoryEntry:entry
+	entry := globalHistory first.
+	self switchToFindHistoryEntry:entry
     ]
 
     "Modified: / 01-11-2010 / 18:17:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -53733,8 +54302,8 @@
 
     cat := self theSingleSelectedCategory.
     cat notNil ifTrue:[
-        self spawnCategoryBrowserFor:(self selectedCategoriesValue) in:#newBuffer.
-        ^ self
+	self spawnCategoryBrowserFor:(self selectedCategoriesValue) in:#newBuffer.
+	^ self
     ].
 
     "Created: / 18.8.2000 / 20:03:28 / cg"
@@ -53743,9 +54312,9 @@
 
 classDoubleClicked
     "double click on a class:
-        if unloaded        : load it
-        if browserStartable: start the application
-        if its a testcase  : run it
+	if unloaded        : load it
+	if browserStartable: start the application
+	if its a testcase  : run it
     "
 
     |cls clsName organizerModeHolder organizerMode newMode doSwitchDisplayMode|
@@ -53755,63 +54324,63 @@
 
     (navigationState isVersionDiffBrowser
     or:[navigationState isCheckOutputBrowser]) ifTrue:[
-        self spawnFullBrowserInClass:cls selector:nil in:#newBuffer.
-        ^ self
+	self spawnFullBrowserInClass:cls selector:nil in:#newBuffer.
+	^ self
     ].
 
     self withWaitCursorDo:[
-        cls := cls theNonMetaclass.
-        clsName := cls name.
-
-        self window sensor shiftDown ifTrue:[
-            self spawnClassReferencesBrowserFor:(Array with:cls) in:#newBuffer.
-            ^ self.
-        ].
-
-        doSwitchDisplayMode := true.
-        self window sensor metaDown ifFalse:[
-            (cls isBrowserStartable) ifTrue:[
-                (self startApplication:cls) ifTrue:[
-                    doSwitchDisplayMode := false.
-                ].
-            ] ifFalse:[
-                cls isLoaded ifFalse:[
-                    self busyLabel:'loading %1' with:clsName.
-                    self classLoad.
-                    doSwitchDisplayMode := false.
-                ] ifTrue:[
-                    (cls isTestCaseLike and:[cls isAbstract not]) ifTrue:[
-                        |testRunner|
-
-                        testRunner := UserPreferences current testRunnerClass.
-                        testRunner notNil ifTrue:[
-                            testRunner openOnTestCase:cls.
-                            doSwitchDisplayMode := false.
-                        ]
-                    ].
-                ].
-            ].
-        ].
-
-        doSwitchDisplayMode ifTrue:[
-            organizerModeHolder := navigationState organizerMode.
-            organizerMode := organizerModeHolder value.
-
-            "/ toggle view mode (between category and class hierarchy)
-            organizerMode == OrganizerCanvas organizerModeClassHierarchy ifTrue:[
-                newMode := OrganizerCanvas organizerModeCategory
-            ] ifFalse:[
-                organizerMode == OrganizerCanvas organizerModeCategory ifTrue:[
-                    newMode := OrganizerCanvas organizerModeClassHierarchy
-                ].
-            ].
-            newMode notNil ifTrue:[
-                organizerModeHolder value:newMode.
-                self organizerModeForMenu changed.
-            ]
-        ].
-
-        self normalLabel.
+	cls := cls theNonMetaclass.
+	clsName := cls name.
+
+	self window sensor shiftDown ifTrue:[
+	    self spawnClassReferencesBrowserFor:(Array with:cls) in:#newBuffer.
+	    ^ self.
+	].
+
+	doSwitchDisplayMode := true.
+	self window sensor metaDown ifFalse:[
+	    (cls isBrowserStartable) ifTrue:[
+		(self startApplication:cls) ifTrue:[
+		    doSwitchDisplayMode := false.
+		].
+	    ] ifFalse:[
+		cls isLoaded ifFalse:[
+		    self busyLabel:'loading %1' with:clsName.
+		    self classLoad.
+		    doSwitchDisplayMode := false.
+		] ifTrue:[
+		    (cls isTestCaseLike and:[cls isAbstract not]) ifTrue:[
+			|testRunner|
+
+			testRunner := UserPreferences current testRunnerClass.
+			testRunner notNil ifTrue:[
+			    testRunner openOnTestCase:cls.
+			    doSwitchDisplayMode := false.
+			]
+		    ].
+		].
+	    ].
+	].
+
+	doSwitchDisplayMode ifTrue:[
+	    organizerModeHolder := navigationState organizerMode.
+	    organizerMode := organizerModeHolder value.
+
+	    "/ toggle view mode (between category and class hierarchy)
+	    organizerMode == OrganizerCanvas organizerModeClassHierarchy ifTrue:[
+		newMode := OrganizerCanvas organizerModeCategory
+	    ] ifFalse:[
+		organizerMode == OrganizerCanvas organizerModeCategory ifTrue:[
+		    newMode := OrganizerCanvas organizerModeClassHierarchy
+		].
+	    ].
+	    newMode notNil ifTrue:[
+		organizerModeHolder value:newMode.
+		self organizerModeForMenu changed.
+	    ]
+	].
+
+	self normalLabel.
     ].
     ^ self
 
@@ -53819,7 +54388,7 @@
 !
 
 codeCompletion
-    |cls codeView 
+    |cls codeView
 "/     crsrPos interval node checkedNode
 "/     char start stop selectorSoFar matchingSelectors
     |
@@ -53832,12 +54401,12 @@
 "/    ].
 
     UserInformation handle:[:ex |
-        self showInfo:(ex messageText).
-        ex proceed.
+	self showInfo:(ex messageText).
+	ex proceed.
     ] do:[
-        self withWaitCursorDo:[
-            DoWhatIMeanSupport codeCompletionForClass:cls codeView:codeView.
-        ]
+	self withWaitCursorDo:[
+	    DoWhatIMeanSupport codeCompletionForClass:cls codeView:codeView.
+	]
     ].
     ^ self.
 
@@ -53900,166 +54469,166 @@
     selector := node selector.
     receiver := node receiver.
     receiver isVariable ifTrue:[
-        nm := receiver name.
-        nm = 'self' ifTrue:[
-            srchClass := cls
-        ].
-        nm = 'super' ifTrue:[
-            srchClass := cls superclass
-        ].
-        (Smalltalk includesKey:nm asSymbol) ifTrue:[
-            nodeVal := Smalltalk at:nm asSymbol.
-            nodeVal notNil ifTrue:[
-                srchClass := nodeVal class
-            ]
-        ]
+	nm := receiver name.
+	nm = 'self' ifTrue:[
+	    srchClass := cls
+	].
+	nm = 'super' ifTrue:[
+	    srchClass := cls superclass
+	].
+	(Smalltalk includesKey:nm asSymbol) ifTrue:[
+	    nodeVal := Smalltalk at:nm asSymbol.
+	    nodeVal notNil ifTrue:[
+		srchClass := nodeVal class
+	    ]
+	]
     ].
 
     receiver isLiteral ifTrue:[
-        srchClass := receiver value class
+	srchClass := receiver value class
     ].
     srchClass notNil ifTrue:[
-        bestSelectors := Parser findBest:30 selectorsFor:selector in:srchClass forCompletion:true.
-        (bestSelectors includes:selector) ifTrue:[
-            bestSelectors := bestSelectors select:[:sel | sel size > selector size].
-        ].
-        bestSelectors size > 0 ifTrue:[
-            bestPrefixes := bestSelectors select:[:sel | sel asLowercase startsWith:selector asLowercase].
-            bestPrefixes size > 0 ifTrue:[
-                bestSelectors := bestPrefixes
-            ].
-            best := bestSelectors first.
-            bestSelectors size > 1 ifTrue:[
-                best = selector ifTrue:[
-                    best := bestSelectors second.
-                ].
-                bestSelectors size < 20 ifTrue:[
-                    |idx|
-
-                    idx := (PopUpMenu labels:bestSelectors) startUp.
-                    idx == 0 ifTrue:[ ^ self].
-                    best := bestSelectors at:idx.
-                ] ifFalse:[
-                    best := Dialog request:'Matching selectors:' initialAnswer:best list:bestSelectors.
-                    best size == 0 ifTrue:[^ self].
-                ].
-            ] ifFalse:[
-                best := bestSelectors first.
-            ].
-            implClass := srchClass whichClassIncludesSelector:best.
-        ].
-    ] ifFalse:[
-        "/ class not known
-        self withSearchCursorDo:[
-            bestSelectors := Parser findBest:30 selectorsFor:selector in:nil forCompletion:true.
-        ].
-        (bestSelectors includes:selector) ifTrue:[
-            bestSelectors := bestSelectors select:[:sel | sel size > selector size].
-        ].
-
-        bestSelectors size > 0 ifTrue:[
-            best := bestSelectors first.
-            bestSelectors size > 1 ifTrue:[
-                best = selector ifTrue:[
-                    best := bestSelectors second.
-                ].
-
-                bestSelectors size < 20 ifTrue:[
-                    |idx|
-
-                    idx := (PopUpMenu labels:bestSelectors) startUp.
-                    idx == 0 ifTrue:[ ^ self].
-                    best := bestSelectors at:idx.
-                ] ifFalse:[
-                    best := Dialog request:'Matching selectors:' initialAnswer:best list:bestSelectors.
-                    best size == 0 ifTrue:[^ self].
-                ]
-            ] ifFalse:[
-                best := bestSelectors first.
-            ].
-            implClass := Smalltalk allClasses select:[:cls | (cls includesSelector:best) or:[cls class includesSelector:best]].
-            implClass size == 1 ifTrue:[
-                implClass := implClass first.
-            ] ifFalse:[
-                implClass := nil
-            ]
-        ].
+	bestSelectors := Parser findBest:30 selectorsFor:selector in:srchClass forCompletion:true.
+	(bestSelectors includes:selector) ifTrue:[
+	    bestSelectors := bestSelectors select:[:sel | sel size > selector size].
+	].
+	bestSelectors size > 0 ifTrue:[
+	    bestPrefixes := bestSelectors select:[:sel | sel asLowercase startsWith:selector asLowercase].
+	    bestPrefixes size > 0 ifTrue:[
+		bestSelectors := bestPrefixes
+	    ].
+	    best := bestSelectors first.
+	    bestSelectors size > 1 ifTrue:[
+		best = selector ifTrue:[
+		    best := bestSelectors second.
+		].
+		bestSelectors size < 20 ifTrue:[
+		    |idx|
+
+		    idx := (PopUpMenu labels:bestSelectors) startUp.
+		    idx == 0 ifTrue:[ ^ self].
+		    best := bestSelectors at:idx.
+		] ifFalse:[
+		    best := Dialog request:'Matching selectors:' initialAnswer:best list:bestSelectors.
+		    best size == 0 ifTrue:[^ self].
+		].
+	    ] ifFalse:[
+		best := bestSelectors first.
+	    ].
+	    implClass := srchClass whichClassIncludesSelector:best.
+	].
+    ] ifFalse:[
+	"/ class not known
+	self withSearchCursorDo:[
+	    bestSelectors := Parser findBest:30 selectorsFor:selector in:nil forCompletion:true.
+	].
+	(bestSelectors includes:selector) ifTrue:[
+	    bestSelectors := bestSelectors select:[:sel | sel size > selector size].
+	].
+
+	bestSelectors size > 0 ifTrue:[
+	    best := bestSelectors first.
+	    bestSelectors size > 1 ifTrue:[
+		best = selector ifTrue:[
+		    best := bestSelectors second.
+		].
+
+		bestSelectors size < 20 ifTrue:[
+		    |idx|
+
+		    idx := (PopUpMenu labels:bestSelectors) startUp.
+		    idx == 0 ifTrue:[ ^ self].
+		    best := bestSelectors at:idx.
+		] ifFalse:[
+		    best := Dialog request:'Matching selectors:' initialAnswer:best list:bestSelectors.
+		    best size == 0 ifTrue:[^ self].
+		]
+	    ] ifFalse:[
+		best := bestSelectors first.
+	    ].
+	    implClass := Smalltalk allClasses select:[:cls | (cls includesSelector:best) or:[cls class includesSelector:best]].
+	    implClass size == 1 ifTrue:[
+		implClass := implClass first.
+	    ] ifFalse:[
+		implClass := nil
+	    ]
+	].
     ].
 
     best notNil ifTrue:[
-        info := best storeString.
-        implClass notNil ifTrue:[
-            info := implClass name , ' >> ' , info.
-        ].
-        self showInfo:info.
-
-        best ~= selector ifTrue:[
-            numArgs := best numArgs.
-            selectorParts := node selectorParts.
-            nSelParts := selectorParts size.
-
-            newParts := best asCollectionOfSubstringsSeparatedBy:$:.
-            newParts := newParts select:[:part | part size > 0].
-
-            codeView
-                undoableDo:[
-                    |stop|
-
-                    numArgs > nSelParts ifTrue:[
-                        stop := selectorParts last stop.
-
-                        "/ append the rest ...
-                        numArgs downTo:nSelParts+1 do:[:idx |
-                            |newPart|
-
-                            newPart := newParts at:idx.
-                            (best endsWith:$:) ifTrue:[
-                                newPart := newPart , ':'
-                            ].
-
-                            (codeView characterAtCharacterPosition:stop) == $: ifFalse:[
-                                newPart := ':' , newPart.
-                            ].
-                            newPart := (codeView characterAtCharacterPosition:stop) asString , newPart.
-
-                            codeView replaceFromCharacterPosition:stop to:stop with:newPart
-                        ]
-                    ].
-
-                    nSelParts downTo:1 do:[:idx |
-                        |newPart oldPartialToken start stop|
-
-                        newPart := newParts at:idx.
-                        oldPartialToken := selectorParts at:idx.
-                        start := oldPartialToken start.
-                        stop := oldPartialToken stop.
-                        (best endsWith:$:) ifTrue:[
-                            (codeView characterAtCharacterPosition:stop+1) == $: ifFalse:[
-                                newPart := newPart , ':'
-                            ]
-                        ] ifFalse:[
-                            (codeView characterAtCharacterPosition:stop) == $: ifTrue:[
-                                newPart := newPart , ':'
-                            ] ifFalse:[
-                                (codeView characterAtCharacterPosition:stop+1) isSeparator ifFalse:[
-                                    newPart := newPart , ' '
-                                ]
-                            ]
+	info := best storeString.
+	implClass notNil ifTrue:[
+	    info := implClass name , ' >> ' , info.
+	].
+	self showInfo:info.
+
+	best ~= selector ifTrue:[
+	    numArgs := best numArgs.
+	    selectorParts := node selectorParts.
+	    nSelParts := selectorParts size.
+
+	    newParts := best asCollectionOfSubstringsSeparatedBy:$:.
+	    newParts := newParts select:[:part | part size > 0].
+
+	    codeView
+		undoableDo:[
+		    |stop|
+
+		    numArgs > nSelParts ifTrue:[
+			stop := selectorParts last stop.
+
+			"/ append the rest ...
+			numArgs downTo:nSelParts+1 do:[:idx |
+			    |newPart|
+
+			    newPart := newParts at:idx.
+			    (best endsWith:$:) ifTrue:[
+				newPart := newPart , ':'
+			    ].
+
+			    (codeView characterAtCharacterPosition:stop) == $: ifFalse:[
+				newPart := ':' , newPart.
+			    ].
+			    newPart := (codeView characterAtCharacterPosition:stop) asString , newPart.
+
+			    codeView replaceFromCharacterPosition:stop to:stop with:newPart
+			]
+		    ].
+
+		    nSelParts downTo:1 do:[:idx |
+			|newPart oldPartialToken start stop|
+
+			newPart := newParts at:idx.
+			oldPartialToken := selectorParts at:idx.
+			start := oldPartialToken start.
+			stop := oldPartialToken stop.
+			(best endsWith:$:) ifTrue:[
+			    (codeView characterAtCharacterPosition:stop+1) == $: ifFalse:[
+				newPart := newPart , ':'
+			    ]
+			] ifFalse:[
+			    (codeView characterAtCharacterPosition:stop) == $: ifTrue:[
+				newPart := newPart , ':'
+			    ] ifFalse:[
+				(codeView characterAtCharacterPosition:stop+1) isSeparator ifFalse:[
+				    newPart := newPart , ' '
+				]
+			    ]
 "/                            codeView replaceFromCharacterPosition:start to:stop with:(newPart , ':').
 "/                        ] ifFalse:[
 "/                            codeView replaceFromCharacterPosition:start to:stop with:newPart.
-                        ].
-
-                        codeView replaceFromCharacterPosition:start to:stop with:newPart.
-
-                        oldLen := stop - start + 1.
-                        newLen := newPart size.
-                        codeView selectFromCharacterPosition:start+oldLen to:start+newLen-1.
-                    ].
-                    codeView dontReplaceSelectionOnInput.
-                ]
-            info:'completion'.
-        ].
+			].
+
+			codeView replaceFromCharacterPosition:start to:stop with:newPart.
+
+			oldLen := stop - start + 1.
+			newLen := newPart size.
+			codeView selectFromCharacterPosition:start+oldLen to:start+newLen-1.
+		    ].
+		    codeView dontReplaceSelectionOnInput.
+		]
+	    info:'completion'.
+	].
     ].
 
     "Created: / 10-11-2006 / 13:18:27 / cg"
@@ -54077,45 +54646,45 @@
 
     selectorSoFar := ''.
     node selectorParts do:[:partToken |
-        |part|
-
-        part := partToken value.
-        selectorSoFar := selectorSoFar , part.
-
-        (crsrPos >= partToken start
-        and:[crsrPos <= partToken stop]) ifTrue:[
-            matchingSelectors := Smalltalk allClasses
-                                    inject:(Set new)
-                                    into:[:theSet :eachClass |
-                                        |md|
-
-                                        cls isMeta ifTrue:[
-                                            md := eachClass theMetaclass methodDictionary
-                                        ] ifFalse:[
-                                            md := eachClass theNonMetaclass methodDictionary
-                                        ].
-                                        theSet addAll:(md keys select:[:sel |sel startsWith:selectorSoFar]).
-                                        theSet.
-                                    ].
-            selectors := matchingSelectors asOrderedCollection.
-            distances := selectors collect:[:each | each spellAgainst:selectorSoFar].
-            distances sortWith:selectors.
-            selectors reverse.
-            best := self askUserForCompletion:'selector' from:selectors.
-            best isNil ifTrue:[^ self].
-
-            rest := best copyFrom:selectorSoFar size.
-            codeView
-                undoableDo:[ 
-                    codeView 
-                        replaceFromCharacterPosition:crsrPos 
-                        to:crsrPos 
-                        with:rest 
-                ]
-                info:'completion'.
-            codeView cursorToCharacterPosition:(crsrPos + rest size - 1).    
-            codeView cursorRight.    
-        ].
+	|part|
+
+	part := partToken value.
+	selectorSoFar := selectorSoFar , part.
+
+	(crsrPos >= partToken start
+	and:[crsrPos <= partToken stop]) ifTrue:[
+	    matchingSelectors := Smalltalk allClasses
+				    inject:(Set new)
+				    into:[:theSet :eachClass |
+					|md|
+
+					cls isMeta ifTrue:[
+					    md := eachClass theMetaclass methodDictionary
+					] ifFalse:[
+					    md := eachClass theNonMetaclass methodDictionary
+					].
+					theSet addAll:(md keys select:[:sel |sel startsWith:selectorSoFar]).
+					theSet.
+				    ].
+	    selectors := matchingSelectors asOrderedCollection.
+	    distances := selectors collect:[:each | each spellAgainst:selectorSoFar].
+	    distances sortWith:selectors.
+	    selectors reverse.
+	    best := self askUserForCompletion:'selector' from:selectors.
+	    best isNil ifTrue:[^ self].
+
+	    rest := best copyFrom:selectorSoFar size.
+	    codeView
+		undoableDo:[
+		    codeView
+			replaceFromCharacterPosition:crsrPos
+			to:crsrPos
+			with:rest
+		]
+		info:'completion'.
+	    codeView cursorToCharacterPosition:(crsrPos + rest size - 1).
+	    codeView cursorRight.
+	].
     ].
 
     "Modified: / 04-07-2006 / 18:48:26 / fm"
@@ -54142,84 +54711,84 @@
     crsrPos := codeView characterPositionOfCursor.
     char := codeView characterAtCharacterPosition:crsrPos-1.
     char isSeparator ifTrue:[
-        nodeVal := self currentClass nameSpace at:nm asSymbol ifAbsent:[Smalltalk at:nm asSymbol].
-        nodeVal isBehavior ifTrue:[
-            |methods menu exitKey idx|
-
-            methods := nodeVal class methodDictionary values
-                            select:[:m | |cat|
-                                cat := m category asLowercase.
-                                cat = 'instance creation'
-                            ].
-
-            menu := PopUpMenu labels:(methods collect:[:each | each selector]).
-            menu hideOnKeyFilter:[:key | |hide|
-                    hide := ( #( CursorDown CursorUp Escape Return ) includes: key) not.
-                    hide ifTrue:[
-                        exitKey := key.
-                    ].
-                    hide].
-
-            idx := menu startUp.
-            idx == 0 ifTrue:[
-                exitKey notNil ifTrue:[
-                    codeView keyPress:exitKey x:0 y:0.
-                ].
-                ^ self
-            ].
-            best := (methods at:idx) selector.
-            codeView
-                undoableDo:[
-                    codeView insertString:best atCharacterPosition:crsrPos.
-                    codeView cursorToCharacterPosition:crsrPos+best size.
-                    ]
-                info:'completion'.
-            ^ self.
-        ].
+	nodeVal := self currentClass nameSpace at:nm asSymbol ifAbsent:[Smalltalk at:nm asSymbol].
+	nodeVal isBehavior ifTrue:[
+	    |methods menu exitKey idx|
+
+	    methods := nodeVal class methodDictionary values
+			    select:[:m | |cat|
+				cat := m category asLowercase.
+				cat = 'instance creation'
+			    ].
+
+	    menu := PopUpMenu labels:(methods collect:[:each | each selector]).
+	    menu hideOnKeyFilter:[:key | |hide|
+		    hide := ( #( CursorDown CursorUp Escape Return ) includes: key) not.
+		    hide ifTrue:[
+			exitKey := key.
+		    ].
+		    hide].
+
+	    idx := menu startUp.
+	    idx == 0 ifTrue:[
+		exitKey notNil ifTrue:[
+		    codeView keyPress:exitKey x:0 y:0.
+		].
+		^ self
+	    ].
+	    best := (methods at:idx) selector.
+	    codeView
+		undoableDo:[
+		    codeView insertString:best atCharacterPosition:crsrPos.
+		    codeView cursorToCharacterPosition:crsrPos+best size.
+		    ]
+		info:'completion'.
+	    ^ self.
+	].
     ].
 
     (node parent notNil and:[node parent isMessage]) ifTrue:[
-        node == node parent receiver ifTrue:[
-            selectorOfMessageToNode := node parent selector
-        ]
+	node == node parent receiver ifTrue:[
+	    selectorOfMessageToNode := node parent selector
+	]
     ].
 
     nm isUppercaseFirst ifTrue:[
-        globalFactor := 2.
-        localFactor := 1.
-    ] ifFalse:[
-        globalFactor := 1.
-        localFactor := 2.
+	globalFactor := 2.
+	localFactor := 1.
+    ] ifFalse:[
+	globalFactor := 1.
+	localFactor := 2.
     ].
 
     getDistanceComputeBlockWithWeight :=
-        [:weight |
-            [:each |
-                |dist factor|
-
-                dist := each spellAgainst:nm.
-                factor := 1.
-
-                (each startsWith:nm) ifTrue:[
-                    factor := 4 * nm size.
-                ] ifFalse:[
-                    (each asLowercase startsWith:nm asLowercase) ifTrue:[
-                        factor := 3 * nm size.
-                    ].
-                ].
-                dist := dist + (weight*factor).
-
-                each -> (dist * weight)
-             ]
-        ].
+	[:weight |
+	    [:each |
+		|dist factor|
+
+		dist := each spellAgainst:nm.
+		factor := 1.
+
+		(each startsWith:nm) ifTrue:[
+		    factor := 4 * nm size.
+		] ifFalse:[
+		    (each asLowercase startsWith:nm asLowercase) ifTrue:[
+			factor := 3 * nm size.
+		    ].
+		].
+		dist := dist + (weight*factor).
+
+		each -> (dist * weight)
+	     ]
+	].
 
     addWithFactorBlock :=
-        [:names :factor | |namesToAdd|
-            namesToAdd := names select:[:nameToAdd | nameToAdd ~= nm ].
-            namesToAdd := namesToAdd reject:[:each | allVariables includes:each ].
-            allVariables addAll:namesToAdd.
-            allDistances addAll:(namesToAdd collect:(getDistanceComputeBlockWithWeight value:factor)).
-        ].
+	[:names :factor | |namesToAdd|
+	    namesToAdd := names select:[:nameToAdd | nameToAdd ~= nm ].
+	    namesToAdd := namesToAdd reject:[:each | allVariables includes:each ].
+	    allVariables addAll:namesToAdd.
+	    allDistances addAll:(namesToAdd collect:(getDistanceComputeBlockWithWeight value:factor)).
+	].
 
     allVariables := OrderedCollection new.
     allDistances := OrderedCollection new.
@@ -54229,10 +54798,10 @@
     "/ if there were no variables (due to a parse error)
     "/ do another parse and see what we have
     names isEmpty ifTrue:[
-        tree := self treeForCodeAllowErrors:true.
-        "/ better if we already have a body (include locals then)
-        "/ otherwise, only the arguments are considered
-        names := (tree body ? tree) allVariablesOnScope.
+	tree := self treeForCodeAllowErrors:true.
+	"/ better if we already have a body (include locals then)
+	"/ otherwise, only the arguments are considered
+	names := (tree body ? tree) allVariablesOnScope.
     ].
 
     addWithFactorBlock value:names value:(4 * localFactor).
@@ -54242,64 +54811,64 @@
 
     "/ inherited instance variables
     cls superclass notNil ifTrue:[
-        addWithFactorBlock value:cls superclass allInstVarNames value:(2.5 * localFactor).
+	addWithFactorBlock value:cls superclass allInstVarNames value:(2.5 * localFactor).
     ].
 
     selectorOfMessageToNode notNil ifTrue:[
-        |names responders nonResponders|
-
-        "/ responding to that messsage
-
-        "/ class variables
-        names := nonMetaClass classVarNames.
-        responders := names select:[:classVar | (nonMetaClass classVarAt:classVar) respondsTo:selectorOfMessageToNode].
-        nonResponders := names reject:[:classVar | (nonMetaClass classVarAt:classVar) respondsTo:selectorOfMessageToNode].
-
-        addWithFactorBlock value:responders value:(1.5 * globalFactor).
-        addWithFactorBlock value:nonResponders value:(0.5 * 1.5 * globalFactor).
-
-        nonMetaClass allSuperclassesDo:[:superClass |
-            names := superClass classVarNames.
-            responders := names select:[:classVar | (superClass classVarAt:classVar) respondsTo:selectorOfMessageToNode].
-            nonResponders := names reject:[:classVar | (superClass classVarAt:classVar) respondsTo:selectorOfMessageToNode].
-
-            addWithFactorBlock value:responders value:(1 * globalFactor).
-            addWithFactorBlock value:nonResponders value:(0.5 * 1 * globalFactor).
-        ].
-
-        "/ globals
-        cls nameSpace ~~ Smalltalk ifTrue:[
-            names := cls topNameSpace keys.
-            names := names reject:[:nm | nm includes:$:].
-            names := names select:[:nm | nm isUppercaseFirst ].
-            responders := names select:[:nsVar | |c| c := cls topNameSpace at:nsVar. c isBehavior not or:[c isLoaded and:[c respondsTo:selectorOfMessageToNode]]].
-            nonResponders := names reject:[:nsVar | |c| c := cls topNameSpace at:nsVar. c isBehavior not or:[c isLoaded and:[c respondsTo:selectorOfMessageToNode]]].
-            addWithFactorBlock value:responders value:(1.5 * globalFactor).
-            addWithFactorBlock value:nonResponders value:(0.5 * 1.5 * globalFactor).
-        ].
-        names := Smalltalk keys.
-        names := names reject:[:nm | nm includes:$:].
-        names := names select:[:nm | nm isUppercaseFirst ].
-        responders := names select:[:glblVar | |c| c := Smalltalk at:glblVar. c isBehavior not or:[c isLoaded and:[c respondsTo:selectorOfMessageToNode]]].
-        nonResponders := names reject:[:glblVar | |c| c := Smalltalk at:glblVar. c isBehavior not or:[c isLoaded and:[c respondsTo:selectorOfMessageToNode]]].
-        addWithFactorBlock value:responders value:(1.5 * globalFactor).
-        addWithFactorBlock value:nonResponders value:(0.5 * 1.5 * globalFactor).
-    ] ifFalse:[
-        "/ class variables
-        addWithFactorBlock value:nonMetaClass classVarNames value:(1.5 * globalFactor).
-        cls superclass notNil ifTrue:[
-            addWithFactorBlock value:nonMetaClass superclass allClassVarNames value:(1 * globalFactor).
-        ].
-
-        "/ globals
-        cls nameSpace ~~ Smalltalk ifTrue:[
-            names := cls nameSpace isNameSpace ifTrue:[cls nameSpace keys] ifFalse:[cls nameSpace privateClasses collect:[:c | c nameWithoutPrefix]].
-            names := names select:[:nm | nm isUppercaseFirst ].
-            addWithFactorBlock value:names value:(1.5 * globalFactor).
-        ].
-        names := Smalltalk keys.
-        names := names select:[:nm | nm isUppercaseFirst ].
-        addWithFactorBlock value:names value:(1.5 * globalFactor).
+	|names responders nonResponders|
+
+	"/ responding to that messsage
+
+	"/ class variables
+	names := nonMetaClass classVarNames.
+	responders := names select:[:classVar | (nonMetaClass classVarAt:classVar) respondsTo:selectorOfMessageToNode].
+	nonResponders := names reject:[:classVar | (nonMetaClass classVarAt:classVar) respondsTo:selectorOfMessageToNode].
+
+	addWithFactorBlock value:responders value:(1.5 * globalFactor).
+	addWithFactorBlock value:nonResponders value:(0.5 * 1.5 * globalFactor).
+
+	nonMetaClass allSuperclassesDo:[:superClass |
+	    names := superClass classVarNames.
+	    responders := names select:[:classVar | (superClass classVarAt:classVar) respondsTo:selectorOfMessageToNode].
+	    nonResponders := names reject:[:classVar | (superClass classVarAt:classVar) respondsTo:selectorOfMessageToNode].
+
+	    addWithFactorBlock value:responders value:(1 * globalFactor).
+	    addWithFactorBlock value:nonResponders value:(0.5 * 1 * globalFactor).
+	].
+
+	"/ globals
+	cls nameSpace ~~ Smalltalk ifTrue:[
+	    names := cls topNameSpace keys.
+	    names := names reject:[:nm | nm includes:$:].
+	    names := names select:[:nm | nm isUppercaseFirst ].
+	    responders := names select:[:nsVar | |c| c := cls topNameSpace at:nsVar. c isBehavior not or:[c isLoaded and:[c respondsTo:selectorOfMessageToNode]]].
+	    nonResponders := names reject:[:nsVar | |c| c := cls topNameSpace at:nsVar. c isBehavior not or:[c isLoaded and:[c respondsTo:selectorOfMessageToNode]]].
+	    addWithFactorBlock value:responders value:(1.5 * globalFactor).
+	    addWithFactorBlock value:nonResponders value:(0.5 * 1.5 * globalFactor).
+	].
+	names := Smalltalk keys.
+	names := names reject:[:nm | nm includes:$:].
+	names := names select:[:nm | nm isUppercaseFirst ].
+	responders := names select:[:glblVar | |c| c := Smalltalk at:glblVar. c isBehavior not or:[c isLoaded and:[c respondsTo:selectorOfMessageToNode]]].
+	nonResponders := names reject:[:glblVar | |c| c := Smalltalk at:glblVar. c isBehavior not or:[c isLoaded and:[c respondsTo:selectorOfMessageToNode]]].
+	addWithFactorBlock value:responders value:(1.5 * globalFactor).
+	addWithFactorBlock value:nonResponders value:(0.5 * 1.5 * globalFactor).
+    ] ifFalse:[
+	"/ class variables
+	addWithFactorBlock value:nonMetaClass classVarNames value:(1.5 * globalFactor).
+	cls superclass notNil ifTrue:[
+	    addWithFactorBlock value:nonMetaClass superclass allClassVarNames value:(1 * globalFactor).
+	].
+
+	"/ globals
+	cls nameSpace ~~ Smalltalk ifTrue:[
+	    names := cls nameSpace isNameSpace ifTrue:[cls nameSpace keys] ifFalse:[cls nameSpace privateClasses collect:[:c | c nameWithoutPrefix]].
+	    names := names select:[:nm | nm isUppercaseFirst ].
+	    addWithFactorBlock value:names value:(1.5 * globalFactor).
+	].
+	names := Smalltalk keys.
+	names := names select:[:nm | nm isUppercaseFirst ].
+	addWithFactorBlock value:names value:(1.5 * globalFactor).
     ].
 
     "/ pseudos - assuming that thisContext is seldom used.
@@ -54311,9 +54880,9 @@
 
     bestAssoc := allDistances at:1.
     bestAssoc := allDistances inject:bestAssoc into:[:el :best | el value > best value
-                                                           ifTrue:[el]
-                                                           ifFalse:[best]
-                                                    ].
+							   ifTrue:[el]
+							   ifFalse:[best]
+						    ].
 
     allDistances sort:[:a :b | a value > b value].
     allTheBest := allDistances select:[:entry | entry value >= (bestAssoc value * 0.8)].
@@ -54328,14 +54897,14 @@
     oldVar := (codeView textFromCharacterPosition:start to:stop) asString string withoutSeparators.
 
     codeView
-        undoableDo:[ codeView replaceFromCharacterPosition:start to:stop with:best ]
-        info:'completion'.
+	undoableDo:[ codeView replaceFromCharacterPosition:start to:stop with:best ]
+	info:'completion'.
 
     (best startsWith:oldVar) ifTrue:[
-        oldLen := stop - start + 1.
-        newLen := best size.
-        codeView selectFromCharacterPosition:start+oldLen to:start+newLen-1.
-        codeView dontReplaceSelectionOnInput
+	oldLen := stop - start + 1.
+	newLen := best size.
+	codeView selectFromCharacterPosition:start+oldLen to:start+newLen-1.
+	codeView dontReplaceSelectionOnInput
     ].
 
     "Created: / 10-11-2006 / 13:16:33 / cg"
@@ -54373,13 +54942,13 @@
     navigationState := self navigationState.
 
     self codeView modified ifTrue:[
-        navigationState realModifiedState:true.
-
-        self codeView isCodeView2 ifFalse:[
-            self startSyntaxHighlightProcess.
-        ].
-        self navigationState realModifiedState:true.
-        self codeView modifiedChannel setValue:false.
+	navigationState realModifiedState:true.
+
+	self codeView isCodeView2 ifFalse:[
+	    self startSyntaxHighlightProcess.
+	].
+	self navigationState realModifiedState:true.
+	self codeView modifiedChannel setValue:false.
     ].
     self enqueueDelayedCheckReallyModified.
     self updateBufferLabel.
@@ -54413,26 +54982,26 @@
     | dialog cnfManagerName srcManagerName |
 
     cnfManager notNil ifTrue:[
-        cnfManagerName := cnfManager managerTypeName
-    ] ifFalse:[
-        cnfManagerName := self class resources at: 'Not configured'.
+	cnfManagerName := cnfManager managerTypeName
+    ] ifFalse:[
+	cnfManagerName := self class resources at: 'Not configured'.
     ].
     srcManager notNil ifTrue:[
-        srcManagerName := srcManager managerTypeName
-    ] ifFalse:[
-        srcManagerName := self class resources at: 'Unknown'.
+	srcManagerName := srcManager managerTypeName
+    ] ifFalse:[
+	srcManagerName := self class resources at: 'Unknown'.
     ].
 
     dialog := DialogBox new.
     dialog label: package, ': source code managers does not match'.
-    (dialog addTextLabel: 
-            ('Default configured source manager does match with\' ,
-            'source code manager for the source. This may mean\' ,
-            'that you have compiled the package using sources\',
-            'checked out using different repository and source\',
-            'code management system that the one you have configured\',
-            'for the package') withCRs) 
-            adjust: #left.
+    (dialog addTextLabel:
+	    ('Default configured source manager does match with\' ,
+	    'source code manager for the source. This may mean\' ,
+	    'that you have compiled the package using sources\',
+	    'checked out using different repository and source\',
+	    'code management system that the one you have configured\',
+	    'for the package') withCRs)
+	    adjust: #left.
     (dialog addTextLabel: 'Package: ', package) adjust: #left.
     (dialog addTextLabel: 'Configured SCM: ', cnfManagerName) adjust: #left.
     (dialog addTextLabel: 'Source SCM: ', srcManagerName) adjust: #left.
@@ -54449,7 +55018,7 @@
 
     currentMethod := self theSingleSelectedMethod.
     currentMethod isNil ifTrue:[
-        ^ self
+	^ self
     ].
     self methodDoubleClicked:currentMethod
 !
@@ -54474,32 +55043,32 @@
     |isMethodListLikeBrowser resources editorClass mSelector mClass|
 
     isMethodListLikeBrowser := navigationState isMethodBrowser
-                               or:[navigationState isMethodListBrowser
-                               or:[navigationState isProtocolOrFullProtocolBrowser
-                               or:[navigationState isChainBrowser ]]].
+			       or:[navigationState isMethodListBrowser
+			       or:[navigationState isProtocolOrFullProtocolBrowser
+			       or:[navigationState isChainBrowser ]]].
 
     "/
     "/ double clicking on wrapped method removes the wrap
     "/
     aMethod isWrapped ifTrue:[
-        self debugMenuRemoveBreakOrTrace.
-        ^ self
+	self debugMenuRemoveBreakOrTrace.
+	^ self
     ].
 
     mSelector := aMethod selector.
     mClass := aMethod mclass.
     mClass isNil ifTrue:[
-        Dialog information:'oops - method''s class is gone (try to reselect)'.
-        ^ self.
+	Dialog information:'oops - method''s class is gone (try to reselect)'.
+	^ self.
     ].
 
     isMethodListLikeBrowser ifTrue:[
-        self window sensor shiftDown ifTrue:[
-            self spawnFullBrowserInClass:mClass
-                 selector:mSelector
-                 in:(DoubleClickIsOpenBrowser == true ifTrue:[#newBrowser] ifFalse:[#newBuffer]).
-            ^ self
-        ].
+	self window sensor shiftDown ifTrue:[
+	    self spawnFullBrowserInClass:mClass
+		 selector:mSelector
+		 in:(DoubleClickIsOpenBrowser == true ifTrue:[#newBrowser] ifFalse:[#newBuffer]).
+	    ^ self
+	].
     ].
 
     "/
@@ -54508,30 +55077,30 @@
     "/
     (resources := aMethod resources) notNil
     ifTrue:[
-        "/
-        "/ kludge - this info should come from somewhere else ...
-        "/
-        editorClass := self class resourceEditorClassForResources:resources.
-        editorClass notNil ifTrue: [
-            mClass isMeta ifTrue:[
-                "/ these uzdsakfhiv-stupid editors cannot edit nonMeta-methods - sigh
-
-                self withExecuteCursorDo:[
-                    editorClass
-                        openOnClass:mClass theNonMetaclass
-                        andSelector:mSelector.
-                    ^ self.
-                ]
-            ]
-        ]
+	"/
+	"/ kludge - this info should come from somewhere else ...
+	"/
+	editorClass := self class resourceEditorClassForResources:resources.
+	editorClass notNil ifTrue: [
+	    mClass isMeta ifTrue:[
+		"/ these uzdsakfhiv-stupid editors cannot edit nonMeta-methods - sigh
+
+		self withExecuteCursorDo:[
+		    editorClass
+			openOnClass:mClass theNonMetaclass
+			andSelector:mSelector.
+		    ^ self.
+		]
+	    ]
+	]
     ].
     "/
     "/ double clicking on a normal-method adds a buffer on the class;
     "/ but not if I am already a class browser.
     "/
     isMethodListLikeBrowser ifTrue:[
-        self spawnFullBrowserInClass:mClass selector:mSelector
-             in:(DoubleClickIsOpenBrowser == true ifTrue:[#newBrowser] ifFalse:[#newBuffer]).
+	self spawnFullBrowserInClass:mClass selector:mSelector
+	     in:(DoubleClickIsOpenBrowser == true ifTrue:[#newBrowser] ifFalse:[#newBuffer]).
 "/
 "/            brwsr := self spawnClassBrowserFor:(Array with:mClass) in:#newBuffer.
 "/            "/ brwsr selectClass:mClass.
@@ -54539,7 +55108,7 @@
 "/            brwsr selectProtocol:(aMethod category).
 "/            brwsr selectMethod:(aMethod).
 "/            brwsr immediateUpdate value:false.
-        ^ self
+	^ self
     ].
 
     "/
@@ -54550,8 +55119,8 @@
 "/        in:#newBuffer
 
     self
-        spawnMethodInheritanceBrowserFor:(Array with:mSelector)
-        in:#newBuffer
+	spawnMethodInheritanceBrowserFor:(Array with:mSelector)
+	in:#newBuffer
 
     "Modified: / 14-02-2012 / 11:11:58 / cg"
 !
@@ -54561,42 +55130,42 @@
 
     selectedMethods := (navigationState selectedMethodsArrayAt:index) value.
     selectedMethods size == 1 ifTrue:[
-        selectedMethod := selectedMethods first.
-        self methodDoubleClicked:selectedMethod.
+	selectedMethod := selectedMethods first.
+	self methodDoubleClicked:selectedMethod.
     ]
 !
 
 nameSpaceDoubleClicked
     "double click on a nameSpace:
-        add a buffer browsing that namespace"
+	add a buffer browsing that namespace"
 
     self withWaitCursorDo:[
-        DoubleClickIsOpenBrowser == true ifTrue:[
-            self nameSpaceMenuSpawn
-        ] ifFalse:[
-            self nameSpaceMenuSpawnBuffer
-        ]
+	DoubleClickIsOpenBrowser == true ifTrue:[
+	    self nameSpaceMenuSpawn
+	] ifFalse:[
+	    self nameSpaceMenuSpawnBuffer
+	]
     ].
     self normalLabel.
 !
 
 projectDoubleClicked
     "double click on a project:
-        add a buffer browsing that project"
+	add a buffer browsing that project"
 
     self withWaitCursorDo:[
-        DoubleClickIsOpenBrowser == true ifTrue:[
-            self projectMenuSpawn
-        ] ifFalse:[
-            self projectMenuSpawnBuffer
-        ]
+	DoubleClickIsOpenBrowser == true ifTrue:[
+	    self projectMenuSpawn
+	] ifFalse:[
+	    self projectMenuSpawnBuffer
+	]
     ].
     self normalLabel.
 !
 
 protocolDoubleClicked
     "double click on a protocol:
-        open a full-protocol browser"
+	open a full-protocol browser"
 
 "/    self theSingleSelectedProtocol notNil ifTrue:[
 "/        self protocolMenuSpawnFullCategoryBuffer
@@ -54620,29 +55189,29 @@
     (cls isBrowserStartable) ifFalse:[^ false].
 
     (cls isVisualStartable) ifTrue:[
-        self busyLabel:'starting application %1' with:cls name.
-        MessageNotUnderstood handle:[:ex |
-            ex selector ~~ #windowSpec ifTrue:[
-                ex reject.
-            ]
-        ] do:[
-            cls open.
-        ].
-        ^ true.
+	self busyLabel:'starting application %1' with:cls name.
+	MessageNotUnderstood handle:[:ex |
+	    ex selector ~~ #windowSpec ifTrue:[
+		ex reject.
+	    ]
+	] do:[
+	    cls open.
+	].
+	^ true.
     ].
     (cls isStartableWithMain) ifTrue:[
-        self busyLabel:'invoking main of %1' with:cls name.
-        "/ (self confirm:('Invoke %1''s main ?' bindWith:clsName)) ifTrue:[
-            cls main.
-        "/ ].
-        ^ true.
+	self busyLabel:'invoking main of %1' with:cls name.
+	"/ (self confirm:('Invoke %1''s main ?' bindWith:clsName)) ifTrue:[
+	    cls main.
+	"/ ].
+	^ true.
     ].
     (cls isStartableWithStart) ifTrue:[
-        self busyLabel:'invoking start of %1' with:cls name.
-        "/ (self confirm:('Invoke %1''s start ?' bindWith:clsName)) ifTrue:[
-            cls start.
-        "/ ].
-        ^ true.
+	self busyLabel:'invoking start of %1' with:cls name.
+	"/ (self confirm:('Invoke %1''s start ?' bindWith:clsName)) ifTrue:[
+	    cls start.
+	"/ ].
+	^ true.
     ].
     ^ false.
 !
@@ -54651,9 +55220,9 @@
     |stringSearchToolVisible|
 
     self updateCodeInfoAndStringSearchToolVisibility.
-    stringSearchToolVisible := self stringSearchToolVisibleHolder value.  
+    stringSearchToolVisible := self stringSearchToolVisibleHolder value.
     stringSearchToolVisible ifTrue:[
-        self setFocusToSearchBar.
+	self setFocusToSearchBar.
     ].
 !
 
@@ -54675,36 +55244,36 @@
     topOffset := 0.
 
     toolBar isNil ifFalse:[
-        toolBarVisible := self toolBarVisibleHolder value.
-        DefaultToolBarVisible := toolBarVisible.
-        toolBarVisible ifTrue:[
-            topOffset := topOffset + toolBar height.
-        ]
-    ].
-
-    bookmarkBar isNil ifFalse:[    
-        bookmarkBarVisible := self bookmarkBarVisibleHolder value.     
-        UserPreferences current showBookmarkBar:bookmarkBarVisible.
-        bookmarkBarVisible ifTrue:[
-            h := bookmarkBar height.
-            bookmarkBar layout topOffset:topOffset.
-            bookmarkBar layout bottomOffset:topOffset + h.
-            bookmarkBar container notNil ifTrue:[
-                bookmarkBar containerChangedSize.
-            ].
-            topOffset := topOffset + h. 
-        ]
-    ].
-
-    topOffset := topOffset - 1. 
-    pageContent := (browserPageCanvas notNil or:[builder spec name == #browserPageSpec]) 
-                    ifTrue:[(self componentAt: #BrowserPageContents)]
-                    ifFalse:[(self componentAt:#NoteBook)].
+	toolBarVisible := self toolBarVisibleHolder value.
+	DefaultToolBarVisible := toolBarVisible.
+	toolBarVisible ifTrue:[
+	    topOffset := topOffset + toolBar height.
+	]
+    ].
+
+    bookmarkBar isNil ifFalse:[
+	bookmarkBarVisible := self bookmarkBarVisibleHolder value.
+	UserPreferences current showBookmarkBar:bookmarkBarVisible.
+	bookmarkBarVisible ifTrue:[
+	    h := bookmarkBar height.
+	    bookmarkBar layout topOffset:topOffset.
+	    bookmarkBar layout bottomOffset:topOffset + h.
+	    bookmarkBar container notNil ifTrue:[
+		bookmarkBar containerChangedSize.
+	    ].
+	    topOffset := topOffset + h.
+	]
+    ].
+
+    topOffset := topOffset - 1.
+    pageContent := (browserPageCanvas notNil or:[builder spec name == #browserPageSpec])
+		    ifTrue:[(self componentAt: #BrowserPageContents)]
+		    ifFalse:[(self componentAt:#NoteBook)].
     pageContent notNil ifTrue:[
-        pageContent layout topOffset:topOffset.
-        pageContent container notNil ifTrue:[
-            pageContent containerChangedSize.
-        ].
+	pageContent layout topOffset:topOffset.
+	pageContent container notNil ifTrue:[
+	    pageContent containerChangedSize.
+	].
     ].
 
     "Created: / 18-05-2011 / 17:28:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -54742,7 +55311,7 @@
 
 variableDoubleClicked
     "double click on a variable:
-        add a buffer showing all references to this variable"
+	add a buffer showing all references to this variable"
 
     |names type title|
 
@@ -54750,23 +55319,23 @@
     names size == 0 ifTrue:[^ self].
 
     self showingClassVarsInVariableList ifTrue:[
-        type := #classVarNames.
-        title := 'all references to class variable ''%1'''.
-    ] ifFalse:[
-        self meta value ifTrue:[
-            type := #classInstVarNames.
-            title := 'all references to class-instance variable ''%1'''.
-        ] ifFalse:[
-            type := #instVarNames.
-            title := 'all references to instance variable ''%1'''.
-        ].
-    ].
-
-    self
-        browseVarRefsToAny:names
-        classes:self selectedClassesValue
-        variables:type access:#readOrWrite all:true
-        title:title  in:#newBuffer
+	type := #classVarNames.
+	title := 'all references to class variable ''%1'''.
+    ] ifFalse:[
+	self meta value ifTrue:[
+	    type := #classInstVarNames.
+	    title := 'all references to class-instance variable ''%1'''.
+	] ifFalse:[
+	    type := #instVarNames.
+	    title := 'all references to instance variable ''%1'''.
+	].
+    ].
+
+    self
+	browseVarRefsToAny:names
+	classes:self selectedClassesValue
+	variables:type access:#readOrWrite all:true
+	title:title  in:#newBuffer
 
     "Modified: / 28-02-2012 / 16:51:54 / cg"
 ! !
@@ -54782,11 +55351,11 @@
 
     code := codeArg.
     returnValue := false.
-    language := languageOrNil 
-                    ifNotNil: [languageOrNil]
-                    ifNil: [self hasMethodSelected
-                            ifTrue:[self selectedMethodsValue first programmingLanguage]
-                            ifFalse:[cls programmingLanguage]].
+    language := languageOrNil
+		    ifNotNil: [languageOrNil]
+		    ifNil: [self hasMethodSelected
+			    ifTrue:[self selectedMethodsValue first programmingLanguage]
+			    ifFalse:[cls programmingLanguage]].
 
     "/ a quick parse for the selector ...
     newSelector := self selectorOfMethodFromCode:code in:cls.
@@ -54794,28 +55363,28 @@
     cat := self protocolToAcceptMethod:newSelector class:cls.
 
     AbortOperationRequest catch:[
-        (Class methodRedefinitionNotification) handle:[:ex |
-            |answer|
-
-            answer := SystemBrowser askForPackageChangeFrom:ex oldPackage to:ex newPackage.
-            (answer ~~ #cancel) ifTrue:[
-                ex proceedWith:answer
-            ].
-        ] do:[
-            |codeView package oldMethod oldSelector defPackage answer rslt lang|
-
-            "/ used to be
-            "/    oldSelector := self theSingleSelectedSelector.
-            "/ here; however, with Ruby, a funny selector (fact) instead of fact: is returned...
-
-            oldMethod := self theSingleSelectedMethod.
-            oldMethod notNil ifTrue:[
-                oldSelector := oldMethod selector.
-            ].
-
-            "/ check for overwritten version method
-            (cls isMeta and:[(AbstractSourceCodeManager isVersionMethodSelector:newSelector)]) ifTrue:[
-                (self confirm:'ATTENTION: you are about to accept the classes version method.
+	(Class methodRedefinitionNotification) handle:[:ex |
+	    |answer|
+
+	    answer := SystemBrowser askForPackageChangeFrom:ex oldPackage to:ex newPackage.
+	    (answer ~~ #cancel) ifTrue:[
+		ex proceedWith:answer
+	    ].
+	] do:[
+	    |codeView package oldMethod oldSelector defPackage answer rslt lang|
+
+	    "/ used to be
+	    "/    oldSelector := self theSingleSelectedSelector.
+	    "/ here; however, with Ruby, a funny selector (fact) instead of fact: is returned...
+
+	    oldMethod := self theSingleSelectedMethod.
+	    oldMethod notNil ifTrue:[
+		oldSelector := oldMethod selector.
+	    ].
+
+	    "/ check for overwritten version method
+	    (cls isMeta and:[(AbstractSourceCodeManager isVersionMethodSelector:newSelector)]) ifTrue:[
+		(self confirm:'ATTENTION: you are about to accept the classes version method.
 This method is required by the sourceCodeManager and should correctly return
 the classes version as present in the source repository.
 An incorrect version method may lead to failures when accessing/showing/changing
@@ -54823,215 +55392,215 @@
 You have been warned.
 
 Accept anyway ?')
-                ifFalse:[
-                    ^ false
-                ]
-            ] ifFalse:[
-                "/ check if accepting a different selector than the selected one,
-                "/ and a method for the new selector exists.
-                (existingMethod notNil and:[oldSelector ~= newSelector]) ifTrue:[
-                    answer := OptionBox
-                                  request:('You are about to overwrite an existing method.\\Accept anyway ?' withCRs)
-                                  label:(resources string:'Attention')
-                                  image:(WarningBox iconBitmap)
-                                  buttonLabels:(resources array:#('Cancel' 'Compare' 'Yes'))
-                                  values:#(false #compare true)
-                                  default:false
-                                  onCancel:false.
-
-                    answer == false ifTrue:[ ^ false ].
-                    answer == #compare ifTrue:[
-                        self openDiffViewForText:code againstSourceOfMethod:existingMethod.
-                        ^ false
-                    ].
-                ]
-            ].
-
-            codeView := self codeView.
-            codeView cursorMovementWhenUpdating:nil.
-            codeView scrollWhenUpdating:nil.
-
-            existingMethod notNil ifTrue:[
-                "keep old package if selector does already exist in class"
-                package := existingMethod package.
-            ] ifFalse:[
-                cls theNonMetaclass canHaveExtensions ifFalse:[
-                    defPackage := package := cls package.
-                ] ifTrue:[
-                    defPackage := Class packageQuerySignal query.
-                ].
-
-                "/ if in project-mode,
-                "/ assign the currently selected packageID (or ask, if there is none or multiple)
-                "/ otherwise, use the current project
-
-                (navigationState isProjectBrowser
-                or:[navigationState organizerMode value == OrganizerCanvas organizerModeProject])
-                ifTrue:[
-                    cls theNonMetaclass canHaveExtensions ifTrue:[
-                        package := self theSingleSelectedProject.
-                    ].
-                    package isNil ifTrue:[
-                        package := self
-                                        askForProject:'Method shall be assigned to which project ?'
-                                        initialText:(LastAcceptPackage ? cls package).
-                        package isNil ifTrue:[^ false].
-                        LastAcceptPackage := package.
-                    ] ifFalse:[
-                        package := package asSymbol.
-                        "/ if the current project is different from the selected one
-                        package ~= defPackage ifTrue:[
-                            "/ and the current project is not the default project
-                            (defPackage = PackageId noProjectID) ifFalse:[
-                                "/ ask
-                                package := self
-                                                askForProject:('The browsers selected project is ''%1''\however, your currently active (default) project is ''%2''.\\To which project shall the method be assigned ?'
-                                                               bindWith:package allBold with:defPackage allBold) withCRs
-                                                initialText:package.
-                                package isNil ifTrue:[^ false].
-                                LastAcceptPackage := package.
-                            ]
-                        ]
-                    ].
-                ].
-                package isNil ifTrue:[ package := defPackage ].
-            ].
-
-            lang := oldMethod notNil
-                        ifTrue:[ oldMethod programmingLanguage ]
-                        ifFalse:[ cls programmingLanguage ].
-
-            "/ notice: when compiling, the classes change message will already
-            "/ be noticed by the methodList and lead to an update
-            "/ to be enqueued.
-
-            [
-                |codeCritics|
-
-                code := code asString.
-
-                "/ cg: for now, only smalltalk critics is possible...
-                (self enforceCodeStyle and:[lang isSmalltalk]) ifTrue:[
-                    codeCritics := CodeCritics checkCodeQuality:code.
-                    codeCritics notNil ifTrue:[
-                        codeCritics do:[:eachCritic |
-                            codeView
-                                highlightingErrorLine:(eachCritic key)
-                                do:[
-                                    Dialog 
-                                        warn:(resources 
-                                            stringWithCRs:'Ugly code warning\\    %1\\Please beautify.' 
-                                            with:eachCritic value allBold).
-                                ].
-                        ].
-                    ].
-                ].
-                self enforceComment ifTrue:[
-                    "/ allow simple getters, setters, basicNew etc...
-                    "/ should be coupled with a metric
-                    code asCollectionOfLines size > 3 ifTrue:[
-                        (lang parserClass methodCommentFromSource:code) isEmptyOrNil ifTrue:[
-                            Dialog 
-                                warn:(resources stringWithCRs:'Bad style: please add a method comment.') 
-                        ].
-                    ].
-                ].
-
-                "/ do not react on the methodSelectionChanged notification
-                "/ (which is enforced by the methodList)
-                self selectedMethods retractInterestsFor:self.
-                "/ self immediateUpdate value:true.
-
-                "/ Transcript showCR:'accepting in package: ', (package ? '__NoPackage__').
-                Class packageQuerySignal answer:package do:[ |change|
-                    ClassDescription updateHistoryLineQuerySignal answer:true do:[
-                        (ClassDescription updateChangeFileQuerySignal
-                        , ClassDescription updateChangeListQuerySignal) answer:self suppressChangeSetUpdate not
-                        do:[
-Class nameSpaceQuerySignal 
+		ifFalse:[
+		    ^ false
+		]
+	    ] ifFalse:[
+		"/ check if accepting a different selector than the selected one,
+		"/ and a method for the new selector exists.
+		(existingMethod notNil and:[oldSelector ~= newSelector]) ifTrue:[
+		    answer := OptionBox
+				  request:('You are about to overwrite an existing method.\\Accept anyway ?' withCRs)
+				  label:(resources string:'Attention')
+				  image:(WarningBox iconBitmap)
+				  buttonLabels:(resources array:#('Cancel' 'Compare' 'Yes'))
+				  values:#(false #compare true)
+				  default:false
+				  onCancel:false.
+
+		    answer == false ifTrue:[ ^ false ].
+		    answer == #compare ifTrue:[
+			self openDiffViewForText:code againstSourceOfMethod:existingMethod.
+			^ false
+		    ].
+		]
+	    ].
+
+	    codeView := self codeView.
+	    codeView cursorMovementWhenUpdating:nil.
+	    codeView scrollWhenUpdating:nil.
+
+	    existingMethod notNil ifTrue:[
+		"keep old package if selector does already exist in class"
+		package := existingMethod package.
+	    ] ifFalse:[
+		cls theNonMetaclass canHaveExtensions ifFalse:[
+		    defPackage := package := cls package.
+		] ifTrue:[
+		    defPackage := Class packageQuerySignal query.
+		].
+
+		"/ if in project-mode,
+		"/ assign the currently selected packageID (or ask, if there is none or multiple)
+		"/ otherwise, use the current project
+
+		(navigationState isProjectBrowser
+		or:[navigationState organizerMode value == OrganizerCanvas organizerModeProject])
+		ifTrue:[
+		    cls theNonMetaclass canHaveExtensions ifTrue:[
+			package := self theSingleSelectedProject.
+		    ].
+		    package isNil ifTrue:[
+			package := self
+					askForProject:'Method shall be assigned to which project ?'
+					initialText:(LastAcceptPackage ? cls package).
+			package isNil ifTrue:[^ false].
+			LastAcceptPackage := package.
+		    ] ifFalse:[
+			package := package asSymbol.
+			"/ if the current project is different from the selected one
+			package ~= defPackage ifTrue:[
+			    "/ and the current project is not the default project
+			    (defPackage = PackageId noProjectID) ifFalse:[
+				"/ ask
+				package := self
+						askForProject:('The browsers selected project is ''%1''\however, your currently active (default) project is ''%2''.\\To which project shall the method be assigned ?'
+							       bindWith:package allBold with:defPackage allBold) withCRs
+						initialText:package.
+				package isNil ifTrue:[^ false].
+				LastAcceptPackage := package.
+			    ]
+			]
+		    ].
+		].
+		package isNil ifTrue:[ package := defPackage ].
+	    ].
+
+	    lang := oldMethod notNil
+			ifTrue:[ oldMethod programmingLanguage ]
+			ifFalse:[ cls programmingLanguage ].
+
+	    "/ notice: when compiling, the classes change message will already
+	    "/ be noticed by the methodList and lead to an update
+	    "/ to be enqueued.
+
+	    [
+		|codeCritics|
+
+		code := code asString.
+
+		"/ cg: for now, only smalltalk critics is possible...
+		(self enforceCodeStyle and:[lang isSmalltalk]) ifTrue:[
+		    codeCritics := CodeCritics checkCodeQuality:code.
+		    codeCritics notNil ifTrue:[
+			codeCritics do:[:eachCritic |
+			    codeView
+				highlightingErrorLine:(eachCritic key)
+				do:[
+				    Dialog
+					warn:(resources
+					    stringWithCRs:'Ugly code warning\\    %1\\Please beautify.'
+					    with:eachCritic value allBold).
+				].
+			].
+		    ].
+		].
+		self enforceComment ifTrue:[
+		    "/ allow simple getters, setters, basicNew etc...
+		    "/ should be coupled with a metric
+		    code asCollectionOfLines size > 3 ifTrue:[
+			(lang parserClass methodCommentFromSource:code) isEmptyOrNil ifTrue:[
+			    Dialog
+				warn:(resources stringWithCRs:'Bad style: please add a method comment.')
+			].
+		    ].
+		].
+
+		"/ do not react on the methodSelectionChanged notification
+		"/ (which is enforced by the methodList)
+		self selectedMethods retractInterestsFor:self.
+		"/ self immediateUpdate value:true.
+
+		"/ Transcript showCR:'accepting in package: ', (package ? '__NoPackage__').
+		Class packageQuerySignal answer:package do:[ |change|
+		    ClassDescription updateHistoryLineQuerySignal answer:true do:[
+			(ClassDescription updateChangeFileQuerySignal
+			, ClassDescription updateChangeListQuerySignal) answer:self suppressChangeSetUpdate not
+			do:[
+Class nameSpaceQuerySignal
 answer:(self currentNamespace)
 do:[
-                            ("self canUseRefactoringSupport"
-                             language isSmalltalk 
-                             and:[(Smalltalk at:cls theNonMetaclass name)==cls 
-                             and:[cls programmingLanguage == language
-                             and:[InteractiveAddMethodChange notNil]]]
-                            ) ifTrue:[
-                                "/ cg: Q: is the AddMethodChange prepared for languages ?
-                                change := InteractiveAddMethodChange compile:code in:cls classified:cat.
-                                change controller:codeView.
-                                "/ change named:('Accept method ' , newSelector ? '???').
-
-                                RefactoryChangeManager performChange: change.
-                                rslt := cls compiledMethodAt:newSelector.
-                            ] ifFalse:[
-                                rslt := language compilerClass
-                                "/ cg: I am not sure, if this is correct; shouldn' we ask the old method
-                                "/ for its progLanguage/compilerClass if we accept an old method ???
-                                    compile:code
-                                    forClass:cls
-                                    inCategory:cat
-                                    notifying:codeView
-                                    install:true.
-                            ].
+			    ("self canUseRefactoringSupport"
+			     language isSmalltalk
+			     and:[(Smalltalk at:cls theNonMetaclass name)==cls
+			     and:[cls programmingLanguage == language
+			     and:[InteractiveAddMethodChange notNil]]]
+			    ) ifTrue:[
+				"/ cg: Q: is the AddMethodChange prepared for languages ?
+				change := InteractiveAddMethodChange compile:code in:cls classified:cat.
+				change controller:codeView.
+				"/ change named:('Accept method ' , newSelector ? '???').
+
+				RefactoryChangeManager performChange: change.
+				rslt := cls compiledMethodAt:newSelector.
+			    ] ifFalse:[
+				rslt := language compilerClass
+				"/ cg: I am not sure, if this is correct; shouldn' we ask the old method
+				"/ for its progLanguage/compilerClass if we accept an old method ???
+				    compile:code
+				    forClass:cls
+				    inCategory:cat
+				    notifying:codeView
+				    install:true.
+			    ].
 ].
-                        ].
-                    ].
-                ].
-
-                "/ give subcanvases a chance to synchronize ...
-
-                "/ self immediateUpdate value:true.
-
-                rslt isMethod ifTrue:[
+			].
+		    ].
+		].
+
+		"/ give subcanvases a chance to synchronize ...
+
+		"/ self immediateUpdate value:true.
+
+		rslt isMethod ifTrue:[
 "/                        rslt resourceType == #image ifTrue:[
 "/                            Icon flushCachedIcons
 "/                        ].
 
-                    rslt package.
-                    navigationState realModifiedState:false.
-                    codeView modified:false.
-
-                    "/ immediateUpdate value:true.
-                    "/ self switchToSelector:rslt selector.
-
-                    codeView cursorMovementWhenUpdating:nil.
-                    codeView scrollWhenUpdating:nil.
-                    codeView setSearchPattern:nil.
-                    lastMethodCategory := rslt category.
-
-                    (self selectedProtocolsValue contains:[:p | p string = lastMethodCategory]) ifFalse:[
-                        (self selectedProtocolsValue includes:BrowserList nameListEntryForALL) ifFalse:[
-                            "/ self selectedProtocols setValue:(Array with:rslt category).
-                           self selectProtocols:(Array with:lastMethodCategory).
-                        ]
-                    ].
-
-                    oldSelector ~= rslt selector ifTrue:[
-                        self selectedMethods value:(Array with:rslt).
-                        "/ self switchToSelector:rslt selector
-                    ] ifFalse:[
+		    rslt package.
+		    navigationState realModifiedState:false.
+		    codeView modified:false.
+
+		    "/ immediateUpdate value:true.
+		    "/ self switchToSelector:rslt selector.
+
+		    codeView cursorMovementWhenUpdating:nil.
+		    codeView scrollWhenUpdating:nil.
+		    codeView setSearchPattern:nil.
+		    lastMethodCategory := rslt category.
+
+		    (self selectedProtocolsValue contains:[:p | p string = lastMethodCategory]) ifFalse:[
+			(self selectedProtocolsValue includes:BrowserList nameListEntryForALL) ifFalse:[
+			    "/ self selectedProtocols setValue:(Array with:rslt category).
+			   self selectProtocols:(Array with:lastMethodCategory).
+			]
+		    ].
+
+		    oldSelector ~= rslt selector ifTrue:[
+			self selectedMethods value:(Array with:rslt).
+			"/ self switchToSelector:rslt selector
+		    ] ifFalse:[
 "/                            "/ do not notify myself (to avoid scroll-to-top)
 "/
 "/                            self selectedMethods value:(Array with:rslt).
-                    ].
+		    ].
 "/                        self showMethodsCode:rslt scrollToTop:false.
 "/                        self selectedMethods setValue:(Array with:rslt).
 "/                        self switchToClass:cls selector:rslt selector.
 
-                    "/ immediateUpdate value:false.
-                    doCheck ifTrue:[
-                        self checkAcceptedMethod:rslt inClass:cls.
-                    ].
-                    returnValue := true.
-                    "/ self updateBufferLabel.
-                ].
-            ] ensure:[
-                "/ do again react on the methodSelectionChanged notification
-                self selectedMethods onChangeSend:#methodsSelectionChanged to:self.
-                "/ self immediateUpdate value:false.
-            ].
-        ]
+		    "/ immediateUpdate value:false.
+		    doCheck ifTrue:[
+			self checkAcceptedMethod:rslt inClass:cls.
+		    ].
+		    returnValue := true.
+		    "/ self updateBufferLabel.
+		].
+	    ] ensure:[
+		"/ do again react on the methodSelectionChanged notification
+		self selectedMethods onChangeSend:#methodsSelectionChanged to:self.
+		"/ self immediateUpdate value:false.
+	    ].
+	]
     ].
     ^ returnValue.
 
@@ -55054,30 +55623,30 @@
 
     (msg notNil and:[self confirm:(resources string:msg)])
     ifTrue:[
-        SmalltalkCodeGeneratorTool createDocumentationMethodsFor:mcls.
-
-        (codeAspect == #newWebService) ifTrue:[
-            SmalltalkCodeGeneratorTool createWebServiceCodeFor:cls.
-            ^ self.
-        ].
-        (codeAspect == #newWebPage) ifTrue:[
-            SmalltalkCodeGeneratorTool createWebPageCodeFor:cls.
-            ^ self.
-        ].
-        codeAspect == #newApplication ifTrue:[
-            SmalltalkCodeGeneratorTool createExamplesMethodFor:mcls.
-            SmalltalkCodeGeneratorTool createApplicationCodeFor:cls.
-        ].
-        codeAspect == #newWidget ifTrue:[
-            SmalltalkCodeGeneratorTool createWidgetCodeFor:cls.
-        ].
-        ^ self.
+	SmalltalkCodeGeneratorTool createDocumentationMethodsFor:mcls.
+
+	(codeAspect == #newWebService) ifTrue:[
+	    SmalltalkCodeGeneratorTool createWebServiceCodeFor:cls.
+	    ^ self.
+	].
+	(codeAspect == #newWebPage) ifTrue:[
+	    SmalltalkCodeGeneratorTool createWebPageCodeFor:cls.
+	    ^ self.
+	].
+	codeAspect == #newApplication ifTrue:[
+	    SmalltalkCodeGeneratorTool createExamplesMethodFor:mcls.
+	    SmalltalkCodeGeneratorTool createApplicationCodeFor:cls.
+	].
+	codeAspect == #newWidget ifTrue:[
+	    SmalltalkCodeGeneratorTool createWidgetCodeFor:cls.
+	].
+	^ self.
     ].
 
     (codeAspect == #newTestCase) ifTrue:[
-        SmalltalkCodeGeneratorTool createDocumentationMethodsFor:mcls.
-        SmalltalkCodeGeneratorTool createTestCaseSampleCodeFor:cls.
-        ^ self.
+	SmalltalkCodeGeneratorTool createDocumentationMethodsFor:mcls.
+	SmalltalkCodeGeneratorTool createTestCaseSampleCodeFor:cls.
+	^ self.
     ]
 
     "Modified: / 31-01-2011 / 18:29:32 / cg"
@@ -55085,15 +55654,15 @@
 
 checkCodeQuality:code
     code asCollectionOfLines keysAndValuesDo:[:lineNr :eachLine |
-        |lineString column|
-
-        lineString := eachLine string.
-        (lineString withoutLeadingSeparators startsWith:'^') ifTrue:[
-            column := lineString indexOf:$^.
-            (column-1) \\ 4 ~~ 0 ifTrue:[
-                ^ (lineNr -> 'bad indentation').
-            ].
-        ]
+	|lineString column|
+
+	lineString := eachLine string.
+	(lineString withoutLeadingSeparators startsWith:'^') ifTrue:[
+	    column := lineString indexOf:$^.
+	    (column-1) \\ 4 ~~ 0 ifTrue:[
+		^ (lineNr -> 'bad indentation').
+	    ].
+	]
     ].
     ^ nil
 !
@@ -55103,44 +55672,44 @@
 
     cls := self theSingleSelectedClass.
     cls isNil ifTrue:[
-        mthd := self theSingleSelectedMethod.
-        mthd notNil ifTrue:[
-            cls := mthd mclass
-        ]
+	mthd := self theSingleSelectedMethod.
+	mthd notNil ifTrue:[
+	    cls := mthd mclass
+	]
     ].
     cls isNil ifTrue:[
-        classes := self selectedClassesValue.
-        classes isEmptyOrNil ifTrue:[
-            self warn:'oops class is gone; reselect and try again'.
-            ^ nil
-        ].
-
-        "/ ask for class in which to accept
-        commonSuper := Behavior commonSuperclassOf:classes.
-        (classes includes:commonSuper) ifTrue:[
-            initial := commonSuper name.
-        ].
-        classNameList := classes collect:[:cls|cls name].
-        classNameList size > 0 ifTrue:[
-            classNameList addLast:'-'.
-            classNameList addLast:'*'.
-        ].
-        className := Dialog
-                        request:'Accept code for which class ? ("*" for all)'
-                        initialAnswer:initial
-                        list:classNameList.
-        className size == 0 ifTrue:[
-            ^ nil
-        ].
-        className = '*' ifTrue:[
-            ^ classes asArray.
-        ].
-
-        cls := Smalltalk at:className asSymbol.
-        cls isNil ifTrue:[
-            self warn:'No such class - try again'.
-            ^ nil
-        ].
+	classes := self selectedClassesValue.
+	classes isEmptyOrNil ifTrue:[
+	    self warn:'oops class is gone; reselect and try again'.
+	    ^ nil
+	].
+
+	"/ ask for class in which to accept
+	commonSuper := Behavior commonSuperclassOf:classes.
+	(classes includes:commonSuper) ifTrue:[
+	    initial := commonSuper name.
+	].
+	classNameList := classes collect:[:cls|cls name].
+	classNameList size > 0 ifTrue:[
+	    classNameList addLast:'-'.
+	    classNameList addLast:'*'.
+	].
+	className := Dialog
+			request:'Accept code for which class ? ("*" for all)'
+			initialAnswer:initial
+			list:classNameList.
+	className size == 0 ifTrue:[
+	    ^ nil
+	].
+	className = '*' ifTrue:[
+	    ^ classes asArray.
+	].
+
+	cls := Smalltalk at:className asSymbol.
+	cls isNil ifTrue:[
+	    self warn:'No such class - try again'.
+	    ^ nil
+	].
     ].
     ^ cls
 
@@ -55156,31 +55725,31 @@
 
     currentClass := self theSingleSelectedLoadedNonMetaclassOrNil.
     currentClass isNil ifTrue:[
-        ^ self warn:'oops - no loaded class selected'
+	^ self warn:'oops - no loaded class selected'
     ].
 
     ((currentClass class includesSelector:getSelector)
     or:[ (currentClass class includesSelector:setSelector) ]) ifTrue:[
-        self warn:('The "%1"-class redefines the "%2" and/or the "%3"-message.\\The Accept may fail - please check manually.'
-                    bindWith:currentClass name allBold
-                    with:getSelector allBold
-                    with:setSelector allBold) withCRs.
+	self warn:('The "%1"-class redefines the "%2" and/or the "%3"-message.\\The Accept may fail - please check manually.'
+		    bindWith:currentClass name allBold
+		    with:getSelector allBold
+		    with:setSelector allBold) withCRs.
     ].
 
     [
-        Smalltalk removeDependent:self.   "/ avoid update
-        ClassDescription updateHistoryLineQuerySignal answer:true do:[
-            (ClassDescription updateChangeFileQuerySignal
-            , ClassDescription updateChangeListQuerySignal) answer:self suppressChangeSetUpdate not
-            do:[
-                currentClass perform:setSelector with:theCode asString string.
-            ].
-        ].
-        codeView contents:(currentClass perform:getSelector).
-        codeView modified:false.
-        navigationState realModifiedState:false.
+	Smalltalk removeDependent:self.   "/ avoid update
+	ClassDescription updateHistoryLineQuerySignal answer:true do:[
+	    (ClassDescription updateChangeFileQuerySignal
+	    , ClassDescription updateChangeListQuerySignal) answer:self suppressChangeSetUpdate not
+	    do:[
+		currentClass perform:setSelector with:theCode asString string.
+	    ].
+	].
+	codeView contents:(currentClass perform:getSelector).
+	codeView modified:false.
+	navigationState realModifiedState:false.
     ] ensure:[
-        Smalltalk addDependent:self.
+	Smalltalk addDependent:self.
     ].
 
     self codeAspect:aspect.
@@ -55197,8 +55766,8 @@
 doAcceptClassDefinition:theCode fullClass:thisIsAFullClassesCode usingCompiler:aCompilerClass
     "tell the codeView what to do on accept.
      Return false, if NOT accepted (i.e. compilation canceled).
-     Ouch: this shares a lot of duplicate code with setAcceptActionForClass; 
-           please refacor"
+     Ouch: this shares a lot of duplicate code with setAcceptActionForClass;
+	   please refacor"
 
     |codeView returnValue package|
 
@@ -55209,121 +55778,121 @@
     codeView modified:false.
 
     self withExecuteCursorDo:[
-        |currentCategory currentClass ns|
-
-        currentClass := self theSingleSelectedClass.
-        currentClass notNil ifTrue:[
-            ns := currentClass nameSpace
-        ] ifFalse:[
-            ns := nil
-        ].
-        ns := nil. "/ experimental - needed for JS parsing; is it still needed for ST ?
-
-        currentCategory := self theSingleSelectedCategory.
-        currentCategory isNil ifTrue:[
-            currentClass notNil ifTrue:[
-                currentCategory := currentClass category
-            ]
-        ].
-
-        self organizerMode value == OrganizerCanvas organizerModeProject ifTrue:[
-            currentClass notNil ifTrue:[
-                package := currentClass package.
-            ] ifFalse:[
-                package := self theSingleSelectedProject.
-            ].
-            package isNil ifTrue:[
-                package := Dialog request:'Add to which project ?'.
-                package size == 0 ifTrue:[^ self].
-            ].
-            package := package asSymbol.
-        ] ifFalse:[
-            package := Class packageQuerySignal query.
-        ].
-
-        Class classCategoryQuerySignal answer:(currentCategory ? '* as yet unspecified *')
-        do:[
-          Class packageQuerySignal answer:package
-          do:[
-            Class nameSpaceQuerySignal handle:[:ex |
-                ns isNil ifTrue:[
-                    ex reject
-                ].
-                ex proceedWith:ns
-            ] do:[
-                AbortOperationRequest catch:[
-                  UndefinedObject createMinimumProtocolInNewSubclassQuery
-                    answer:true
-                    do:[
-                        (Class classRedefinitionNotification) handle:[:ex |
-                            |answer|
+	|currentCategory currentClass ns|
+
+	currentClass := self theSingleSelectedClass.
+	currentClass notNil ifTrue:[
+	    ns := currentClass nameSpace
+	] ifFalse:[
+	    ns := nil
+	].
+	ns := nil. "/ experimental - needed for JS parsing; is it still needed for ST ?
+
+	currentCategory := self theSingleSelectedCategory.
+	currentCategory isNil ifTrue:[
+	    currentClass notNil ifTrue:[
+		currentCategory := currentClass category
+	    ]
+	].
+
+	self organizerMode value == OrganizerCanvas organizerModeProject ifTrue:[
+	    currentClass notNil ifTrue:[
+		package := currentClass package.
+	    ] ifFalse:[
+		package := self theSingleSelectedProject.
+	    ].
+	    package isNil ifTrue:[
+		package := Dialog request:'Add to which project ?'.
+		package size == 0 ifTrue:[^ self].
+	    ].
+	    package := package asSymbol.
+	] ifFalse:[
+	    package := Class packageQuerySignal query.
+	].
+
+	Class classCategoryQuerySignal answer:(currentCategory ? '* as yet unspecified *')
+	do:[
+	  Class packageQuerySignal answer:package
+	  do:[
+	    Class nameSpaceQuerySignal handle:[:ex |
+		ns isNil ifTrue:[
+		    ex reject
+		].
+		ex proceedWith:ns
+	    ] do:[
+		AbortOperationRequest catch:[
+		  UndefinedObject createMinimumProtocolInNewSubclassQuery
+		    answer:true
+		    do:[
+			(Class classRedefinitionNotification) handle:[:ex |
+			    |answer|
 
 "/ cg: now always keep the old packageID
-                            Class catchClassRedefinitions ifFalse:[
-                                ex proceedWith:#keep
-                            ].
-                            answer := OptionBox
-                                          request:
+			    Class catchClassRedefinitions ifFalse:[
+				ex proceedWith:#keep
+			    ].
+			    answer := OptionBox
+					  request:
 ('You are about to change the definition of a class from another (system-) package.
 The class is part of the ''%1'' package.
 
 PS: you can disable this check in the launchers settings-compilation dialog.'
-                                                      bindWith:(ex oldPackage allBold))
-
-                                          label:'Class redefinition'
-                                          image:(WarningBox iconBitmap)
-                                          buttonLabels:#('Cancel' 'Continue')
-                                          values:#(#cancel #keep)
-                                          default:#keep
-                                          onCancel:#cancel.
-
-                            (answer ~~ #cancel) ifTrue:[
-                                ex proceedWith:answer
-                            ]
-                        ] do:[
-                            |rslt cls mcls|
-
-                            self immediateUpdate value:true.
-                            navigationState realModifiedState:false.
-                            navigationState modified:false.
-
-                            ClassDescription updateHistoryLineQuerySignal answer:true do:[
-                                (ClassDescription updateChangeFileQuerySignal
-                                , ClassDescription updateChangeListQuerySignal) answer:self suppressChangeSetUpdate not
-                                do:[
-                                    thisIsAFullClassesCode ifTrue:[
-                                        rslt := (ReadStream on:theCode asString) fileIn.
-                                    ] ifFalse:[
-                                        ClassBuildError handle:[:ex |
-                                            self warn:ex description
-                                        ] do:[
-                                            rslt := (aCompilerClass ? Compiler)
-                                                        evaluate:theCode asString string
-                                                        notifying:codeView
-                                                        compile:false.
-
-                                        ].
-                                    ].
-                                ].
-                            ].
-                            self immediateUpdate value:false.
-
-                            rslt isBehavior ifTrue:[
-                                self switchToClass:rslt.
-                                "/ self switchToClassNamed:rslt name.
-                                returnValue := true.
-                            ].
-
-                            returnValue ifTrue:[
-                                cls := rslt theNonMetaclass.
-                                mcls := rslt theMetaclass.
-                                self askForInitialApplicationCodeFor:mcls.
-                            ].
-                        ]
-                    ]
-                ].
-            ].
-        ].
+						      bindWith:(ex oldPackage allBold))
+
+					  label:'Class redefinition'
+					  image:(WarningBox iconBitmap)
+					  buttonLabels:#('Cancel' 'Continue')
+					  values:#(#cancel #keep)
+					  default:#keep
+					  onCancel:#cancel.
+
+			    (answer ~~ #cancel) ifTrue:[
+				ex proceedWith:answer
+			    ]
+			] do:[
+			    |rslt cls mcls|
+
+			    self immediateUpdate value:true.
+			    navigationState realModifiedState:false.
+			    navigationState modified:false.
+
+			    ClassDescription updateHistoryLineQuerySignal answer:true do:[
+				(ClassDescription updateChangeFileQuerySignal
+				, ClassDescription updateChangeListQuerySignal) answer:self suppressChangeSetUpdate not
+				do:[
+				    thisIsAFullClassesCode ifTrue:[
+					rslt := (ReadStream on:theCode asString) fileIn.
+				    ] ifFalse:[
+					ClassBuildError handle:[:ex |
+					    self warn:ex description
+					] do:[
+					    rslt := (aCompilerClass ? Compiler)
+							evaluate:theCode asString string
+							notifying:codeView
+							compile:false.
+
+					].
+				    ].
+				].
+			    ].
+			    self immediateUpdate value:false.
+
+			    rslt isBehavior ifTrue:[
+				self switchToClass:rslt.
+				"/ self switchToClassNamed:rslt name.
+				returnValue := true.
+			    ].
+
+			    returnValue ifTrue:[
+				cls := rslt theNonMetaclass.
+				mcls := rslt theMetaclass.
+				self askForInitialApplicationCodeFor:mcls.
+			    ].
+			]
+		    ]
+		].
+	    ].
+	].
       ]
     ].
 
@@ -55340,9 +55909,9 @@
      Return false, if NOT accepted (i.e. compilation canceled)"
 
     ^ self
-        doAcceptClassDefinition:theCode
-        fullClass:false
-        usingCompiler:aCompilerClass
+	doAcceptClassDefinition:theCode
+	fullClass:false
+	usingCompiler:aCompilerClass
 
     "Modified: / 24.2.2000 / 15:40:11 / cg"
 !
@@ -55354,20 +55923,20 @@
 
     codeAspect := self codeAspect.
     codeAspect == #primitiveDefinitions ifTrue:[
-        getter := #'primitiveDefinitionsString'.
-        setter := #'primitiveDefinitions:'.
-    ] ifFalse:[
-        codeAspect == #primitiveFunctions ifTrue:[
-            getter := #'primitiveFunctionsString'.
-            setter := #'primitiveFunctions:'.
-        ] ifFalse:[
-            codeAspect == #primitiveVariables ifTrue:[
-                getter := #'primitiveVariablesString'.
-                setter := #'primitiveVariables:'.
-            ] ifFalse:[
-                self error:'unknown codeAspect: ', codeAspect printString.
-            ]
-        ]
+	getter := #'primitiveDefinitionsString'.
+	setter := #'primitiveDefinitions:'.
+    ] ifFalse:[
+	codeAspect == #primitiveFunctions ifTrue:[
+	    getter := #'primitiveFunctionsString'.
+	    setter := #'primitiveFunctions:'.
+	] ifFalse:[
+	    codeAspect == #primitiveVariables ifTrue:[
+		getter := #'primitiveVariablesString'.
+		setter := #'primitiveVariables:'.
+	    ] ifFalse:[
+		self error:'unknown codeAspect: ', codeAspect printString.
+	    ]
+	]
     ].
     self doAcceptClassAspect:codeAspect get:getter set:setter code:theCode.
 !
@@ -55383,7 +55952,7 @@
 
     codeAspect := aNavigationState codeAspect.
     (codeAspect == #classDefinition or:[codeAspect == #method]) ifTrue:[
-        acceptAction value:(codeView contentsAsString)
+	acceptAction value:(codeView contentsAsString)
     ].
 
     "Modified: / 24.2.2000 / 15:38:07 / cg"
@@ -55394,9 +55963,9 @@
      Return false, if NOT accepted (i.e. compilation canceled)"
 
     ^ self
-        doAcceptClassDefinition:theCode
-        fullClass:true
-        usingCompiler:aCompilerClass
+	doAcceptClassDefinition:theCode
+	fullClass:true
+	usingCompiler:aCompilerClass
 
     "Created: / 24.2.2000 / 15:40:19 / cg"
 !
@@ -55416,7 +55985,7 @@
     newClass isNil ifTrue:[ ^ self ].
 
     newClass isBehavior ifTrue:[
-        self switchToClass:newClass.
+	self switchToClass:newClass.
     ].
     self codeAspect: #classDefinition
 
@@ -55431,7 +56000,7 @@
      using GroovyCompiler (which effectively turn it into Groovy class)"
 
     JavaLanguage instance compilerClass == GroovyCompiler ifTrue:[
-        ^self doAcceptGroovyClassDefinition:theCode
+	^self doAcceptGroovyClassDefinition:theCode
     ].
 
     self warn:'Accept of Java classes is not yet implemented'.
@@ -55442,41 +56011,41 @@
 
 doAcceptMethod:theCode language: languageOrNil
     "accept a new/modified method using given language"
-    
+
     |codeWithoutEmphasis classOrClassCollection|
 
     theCode isStringCollection ifTrue:[
-        codeWithoutEmphasis := theCode 
-                    collect:[:eachLine | 
-                        eachLine isNil ifTrue:[
-                            nil
-                        ] ifFalse:[
-                            eachLine string
-                        ]
-                    ].
-    ] ifFalse:[
-        codeWithoutEmphasis := theCode
+	codeWithoutEmphasis := theCode
+		    collect:[:eachLine |
+			eachLine isNil ifTrue:[
+			    nil
+			] ifFalse:[
+			    eachLine string
+			]
+		    ].
+    ] ifFalse:[
+	codeWithoutEmphasis := theCode
     ].
     classOrClassCollection := self classToAcceptMethodIn.
     classOrClassCollection notNil ifTrue:[
-        self 
-            withWaitCursorVisibleDo:[
-                classOrClassCollection isArray ifTrue:[
-                    classOrClassCollection do:[:eachClass | 
-                        self 
-                            acceptMethod:codeWithoutEmphasis
-                            inClass:eachClass
-                            language: languageOrNil
-                            check:false.
-                    ].
-                ] ifFalse:[
-                    self 
-                        acceptMethod:codeWithoutEmphasis
-                        inClass:classOrClassCollection
-                        language: languageOrNil
-                        check:true.
-                ].
-            ]
+	self
+	    withWaitCursorVisibleDo:[
+		classOrClassCollection isArray ifTrue:[
+		    classOrClassCollection do:[:eachClass |
+			self
+			    acceptMethod:codeWithoutEmphasis
+			    inClass:eachClass
+			    language: languageOrNil
+			    check:false.
+		    ].
+		] ifFalse:[
+		    self
+			acceptMethod:codeWithoutEmphasis
+			inClass:classOrClassCollection
+			language: languageOrNil
+			check:true.
+		].
+	    ]
     ].
 
     "Created: / 30-12-2009 / 20:02:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -55488,7 +56057,7 @@
     self navigationState doSaveInSpecialEditors.
 !
 
-enforceCodeStyle   
+enforceCodeStyle
     ^ UserPreferences current enforceCodeStyle
 
 !
@@ -55503,11 +56072,11 @@
     |parser|
 
     parser := aClass parserClass
-                parseMethodSpecification:someCode asString
-                in:aClass
-                ignoreErrors:true ignoreWarnings:true.
+		parseMethodSpecification:someCode asString
+		in:aClass
+		ignoreErrors:true ignoreWarnings:true.
     (parser notNil and:[parser ~~ #Error]) ifTrue:[
-        ^ parser name.
+	^ parser name.
     ].
     ^ nil
 
@@ -55521,10 +56090,10 @@
     originalSource := aMethod source.
     changedSource := theCode asString string.
     v := DiffCodeView
-            openOn:changedSource
-            label:(resources string:'Code here (to be accepted ?)')
-            and:originalSource
-            label:(resources string:'Method''s actual code').
+	    openOn:changedSource
+	    label:(resources string:'Code here (to be accepted ?)')
+	    and:originalSource
+	    label:(resources string:'Method''s actual code').
     v topView label:(resources string:'Comparing methods').
     v waitUntilVisible.
 
@@ -55535,23 +56104,23 @@
 
     mthd := self theSingleSelectedMethod.
     mthd notNil ifTrue:[
-        cat := mthd category
-    ] ifFalse:[
-        protocols := (self selectedMethodsValue collect:[:m | m category]) asSet.
-        protocols size == 1 ifTrue:[
-            cat := protocols first
-        ] ifFalse:[
-            cat := self theSingleSelectedProtocol.
-            (cat isNil or:[cat = (BrowserList nameListEntryForALL)]) ifTrue:[
-                "must check from which category this code came from ...
-                 ... thanks to Arno for pointing this out"
-
-                cat := self askForMethodCategoryForAcceptInClass:aClass selector:selector.
-                cat size == 0 ifTrue:[
-                    ^ nil
-                ].
-            ]
-        ]
+	cat := mthd category
+    ] ifFalse:[
+	protocols := (self selectedMethodsValue collect:[:m | m category]) asSet.
+	protocols size == 1 ifTrue:[
+	    cat := protocols first
+	] ifFalse:[
+	    cat := self theSingleSelectedProtocol.
+	    (cat isNil or:[cat = (BrowserList nameListEntryForALL)]) ifTrue:[
+		"must check from which category this code came from ...
+		 ... thanks to Arno for pointing this out"
+
+		cat := self askForMethodCategoryForAcceptInClass:aClass selector:selector.
+		cat size == 0 ifTrue:[
+		    ^ nil
+		].
+	    ]
+	]
     ].
     ^ cat
 
@@ -55562,13 +56131,13 @@
     |parser|
 
     parser := aClass parserClass
-                parseMethodSpecification:someCode asString
-                in:aClass
-                ignoreErrors:true ignoreWarnings:true.
+		parseMethodSpecification:someCode asString
+		in:aClass
+		ignoreErrors:true ignoreWarnings:true.
     (parser notNil and:[parser ~~ #Error]) ifTrue:[
-        ^Array 
-            with: parser selector asSymbol
-            with: parser name
+	^Array
+	    with: parser selector asSymbol
+	    with: parser name
     ].
     ^ nil
 
@@ -55585,15 +56154,15 @@
 
     "/ that's a stupid interface - should ask for a tree and then for a selector...
     parser := aClass parserClass
-                perform:#'parseMethodSpecification:in:ignoreErrors:ignoreWarnings:'
-                    withArguments:(Array with:(someCode asString)
-                                         with:aClass
-                                         with:true 
-                                         with:true)
-                    ifNotUnderstood:[ nil ].
+		perform:#'parseMethodSpecification:in:ignoreErrors:ignoreWarnings:'
+		    withArguments:(Array with:(someCode asString)
+					 with:aClass
+					 with:true
+					 with:true)
+		    ifNotUnderstood:[ nil ].
 
     (parser notNil and:[parser ~~ #Error]) ifTrue:[
-        ^ parser selector asSymbol.
+	^ parser selector asSymbol.
     ].
     ^ nil
 
@@ -55604,11 +56173,11 @@
     |parser|
 
     parser := language parserClass
-                parseMethodSpecification:someCode asString
-                in:aClass
-                ignoreErrors:true ignoreWarnings:true.
+		parseMethodSpecification:someCode asString
+		in:aClass
+		ignoreErrors:true ignoreWarnings:true.
     (parser notNil and:[parser ~~ #Error]) ifTrue:[
-        ^ parser selector asSymbol.
+	^ parser selector asSymbol.
     ].
     ^ nil
 
@@ -55622,7 +56191,7 @@
     |codeView|
 
     (codeView := self codeView) notNil ifTrue:[
-        codeView acceptAction:aBlockOrNil.
+	codeView acceptAction:aBlockOrNil.
     ].
 !
 
@@ -55638,12 +56207,12 @@
     |currentClass|
 
     currentClass := self theSingleSelectedClass.
-    (currentClass isNil 
-        or:[ currentClass programmingLanguage isSmalltalk not
-        or:[ currentClass isRealNameSpace ]])
+    (currentClass isNil
+	or:[ currentClass programmingLanguage isSmalltalk not
+	or:[ currentClass isRealNameSpace ]])
     ifTrue:[
-        self setAcceptActionForNothing.
-        ^ self
+	self setAcceptActionForNothing.
+	^ self
     ].
 
     self setAcceptAction:[:theCode | self doAcceptClassComment:theCode].
@@ -55659,13 +56228,13 @@
     currentClass := self theSingleSelectedClass.
 
     currentClass isGroovyClass ifTrue:[
-        action := [:theCode | self doAcceptGroovyClassDefinition:theCode asString]
-    ] ifFalse:[
-        navigationState isFullClassSourceBrowser ifTrue:[
-            action := [:theCode | self doAcceptFullJavaClassDefinition:theCode asString].
-        ] ifFalse:[
-            action := [:theCode | self doAcceptJavaClassDefinition:theCode asString].
-        ].
+	action := [:theCode | self doAcceptGroovyClassDefinition:theCode asString]
+    ] ifFalse:[
+	navigationState isFullClassSourceBrowser ifTrue:[
+	    action := [:theCode | self doAcceptFullJavaClassDefinition:theCode asString].
+	] ifFalse:[
+	    action := [:theCode | self doAcceptJavaClassDefinition:theCode asString].
+	].
     ].
     self setAcceptAction:action.
 
@@ -55686,32 +56255,32 @@
     currentClass := self theSingleSelectedClass.
 
     metaClassUsedOrNil isNil ifTrue:[
-        currentClass isJavaClass ifTrue:[
-            ^ self setAcceptActionForJavaClass.
-        ].
+	currentClass isJavaClass ifTrue:[
+	    ^ self setAcceptActionForJavaClass.
+	].
     ].
 
     (currentClass isRealNameSpace) ifTrue:[
-        self setAcceptActionForNothing.
-        ^ self
+	self setAcceptActionForNothing.
+	^ self
     ].
 
     metaClassUsedOrNil notNil ifTrue:[
-        compiler := metaClassUsedOrNil basicNew realSubclassDefinerClass
-    ] ifFalse:[
-        compiler := currentClass
-                        ifNil:[Compiler]
-                        ifNotNil:[ (currentClass subclassDefinerClass ? Compiler) ].
+	compiler := metaClassUsedOrNil basicNew realSubclassDefinerClass
+    ] ifFalse:[
+	compiler := currentClass
+			ifNil:[Compiler]
+			ifNotNil:[ (currentClass subclassDefinerClass ? Compiler) ].
     ].
 
     navigationState isFullClassSourceBrowser ifTrue:[
-        action := [:theCode | self doAcceptFullClassDefinition:theCode
-                                   usingCompiler:compiler
-                  ].
-    ] ifFalse:[
-        action := [:theCode | self doAcceptClassDefinition:theCode
-                                   usingCompiler:compiler
-                  ].
+	action := [:theCode | self doAcceptFullClassDefinition:theCode
+				   usingCompiler:compiler
+		  ].
+    ] ifFalse:[
+	action := [:theCode | self doAcceptClassDefinition:theCode
+				   usingCompiler:compiler
+		  ].
     ].
     self setAcceptAction:action.
 
@@ -55734,16 +56303,16 @@
     self setAcceptAction:[:theCode | self doAcceptMethod:theCode language: languageOrNil  ].
 
     (codeView := self codeView) notNil ifTrue:[
-        codeView
-            explainAction:[:theCode :theSelection |
-                self explain:theSelection inCode:theCode
-            ].
-        codeView isCodeView2 ifTrue:[
-            languageOrNil ifNotNil:[
-                codeView languageHolder value: languageOrNil.
-            ]
-            
-        ]
+	codeView
+	    explainAction:[:theCode :theSelection |
+		self explain:theSelection inCode:theCode
+	    ].
+	codeView isCodeView2 ifTrue:[
+	    languageOrNil ifNotNil:[
+		codeView languageHolder value: languageOrNil.
+	    ]
+
+	]
 
     ]
 
@@ -55761,16 +56330,16 @@
     "tell the codeView what to do on accept"
 
     self setAcceptAction:[:code |  |package project|
-                                package := self theSingleSelectedProject.
-                                project := Project projectWithId:package.
-                                project isNil ifTrue:[
-                                    self warn:'No such project.'
-                                ] ifFalse:[
-                                    project comment:(code asString string).
-                                    navigationState modified:false.
-                                    navigationState realModifiedState:false.
-                                ].
-                          ].
+				package := self theSingleSelectedProject.
+				project := Project projectWithId:package.
+				project isNil ifTrue:[
+				    self warn:'No such project.'
+				] ifFalse:[
+				    project comment:(code asString string).
+				    navigationState modified:false.
+				    navigationState realModifiedState:false.
+				].
+			  ].
 !
 
 setDoitActionForClass
@@ -55787,48 +56356,48 @@
     codeView isNil ifTrue:[^ self].
 
     codeView doItAction:[:theCode |
-        |compiler nsName ns currentClass currentNonMetaClass currentMethod result|
-
-        currentClass := self theSingleSelectedClass.
-        currentClass isNil ifTrue:[
-            currentMethod := self theSingleSelectedMethod.
-            currentMethod notNil ifTrue:[
-                currentClass := currentMethod mclass
-            ]
-        ].
-        currentClass notNil ifTrue:[
-            currentNonMetaClass := currentClass theNonMetaclass.
-            ns := currentNonMetaClass nameSpace
-        ] ifFalse:[
-            self organizerMode == OrganizerCanvas organizerModeNamespace ifTrue:[
-                nsName := self theSingleSelectedNamespace.
-                nsName notNil ifTrue:[
-                    ns := NameSpace name:nsName
-                ].
-            ]
-        ].
-
-        Class nameSpaceQuerySignal handle:[:ex |
-            ns isNil ifTrue:[
-                ex reject
-            ].
-            ex proceedWith:ns
-        ] do:[
-            currentClass isNil ifTrue:[
-                compiler := Compiler
-            ] ifFalse:[
-                compiler := currentClass evaluatorClass
-            ].
-
-            result := compiler
-                evaluate:theCode string
-                in:nil
-                receiver:currentNonMetaClass
-                notifying:codeView
-                logged:false
-                ifFail:nil.
-        ].
-        result
+	|compiler nsName ns currentClass currentNonMetaClass currentMethod result|
+
+	currentClass := self theSingleSelectedClass.
+	currentClass isNil ifTrue:[
+	    currentMethod := self theSingleSelectedMethod.
+	    currentMethod notNil ifTrue:[
+		currentClass := currentMethod mclass
+	    ]
+	].
+	currentClass notNil ifTrue:[
+	    currentNonMetaClass := currentClass theNonMetaclass.
+	    ns := currentNonMetaClass nameSpace
+	] ifFalse:[
+	    self organizerMode == OrganizerCanvas organizerModeNamespace ifTrue:[
+		nsName := self theSingleSelectedNamespace.
+		nsName notNil ifTrue:[
+		    ns := NameSpace name:nsName
+		].
+	    ]
+	].
+
+	Class nameSpaceQuerySignal handle:[:ex |
+	    ns isNil ifTrue:[
+		ex reject
+	    ].
+	    ex proceedWith:ns
+	] do:[
+	    currentClass isNil ifTrue:[
+		compiler := Compiler
+	    ] ifFalse:[
+		compiler := currentClass evaluatorClass
+	    ].
+
+	    result := compiler
+		evaluate:theCode string
+		in:nil
+		receiver:currentNonMetaClass
+		notifying:codeView
+		logged:false
+		ifFail:nil.
+	].
+	result
     ].
 
     "Created: / 23.2.2000 / 11:54:24 / cg"
@@ -55889,19 +56458,19 @@
      Invoked on doubleClick on an unloaded class or via the menu"
 
     [
-        |numClasses|
-
-        numClasses := aCollectionOfClasses size.
-        aCollectionOfClasses do:[:eachClass |
-            |cls nm nameShown msg|
-
-            cls := eachClass theNonMetaclass.
-            cls isLoaded ifFalse:[
-                nm := cls name.
-                nameShown := self displayedClassNameOf:cls.
-
-                Autoload autoloadFailedSignal handle:[:ex |
-                    msg := 'Autoload of %1 failed.
+	|numClasses|
+
+	numClasses := aCollectionOfClasses size.
+	aCollectionOfClasses do:[:eachClass |
+	    |cls nm nameShown msg|
+
+	    cls := eachClass theNonMetaclass.
+	    cls isLoaded ifFalse:[
+		nm := cls name.
+		nameShown := self displayedClassNameOf:cls.
+
+		Autoload autoloadFailedSignal handle:[:ex |
+		    msg := 'Autoload of %1 failed.
 
 Check for a file named ''%2.st'' either in the package ''%3''
 along your packagePath, or in the current directory.
@@ -55910,28 +56479,28 @@
 You can also try to load the class(es) from the repository,
 via the ''import and load classes'' menu function of the
 project list.'.
-                    msg := (resources string:msg
-                            with:nameShown
-                            with:(Smalltalk fileNameForClass:cls)
-                            with:cls package
-                            with:(Smalltalk packagePath asStringCollection asStringWith:' , ')).
-
-                    numClasses > 1 ifTrue:[
-                        (Dialog
-                            confirm:msg
-                            yesLabel:'OK' noLabel:'Cancel') ifFalse:[^ self].
-                    ] ifFalse:[
-                        Dialog warn:msg.
-                    ].
-                    ex return.
-                ] do:[
-                    self busyLabel:'loading %1 ...' with:nameShown.
-                    cls autoload.
-                ].
-            ]
-        ].
+		    msg := (resources string:msg
+			    with:nameShown
+			    with:(Smalltalk fileNameForClass:cls)
+			    with:cls package
+			    with:(Smalltalk packagePath asStringCollection asStringWith:' , ')).
+
+		    numClasses > 1 ifTrue:[
+			(Dialog
+			    confirm:msg
+			    yesLabel:'OK' noLabel:'Cancel') ifFalse:[^ self].
+		    ] ifFalse:[
+			Dialog warn:msg.
+		    ].
+		    ex return.
+		] do:[
+		    self busyLabel:'loading %1 ...' with:nameShown.
+		    cls autoload.
+		].
+	    ]
+	].
     ] ensure:[
-        self normalLabel.
+	self normalLabel.
     ].
 !
 
@@ -55941,48 +56510,48 @@
     |notAutoloaded force|
 
     notAutoloaded := OrderedCollection new.
-    aCollectionOfClasses do:[:eachClass | 
-        |eachNonMetaClass|
-        eachNonMetaClass := eachClass theNonMetaclass.
-        
-        (eachNonMetaClass isLoaded and:[eachNonMetaClass wasAutoloaded not]) ifTrue:[
-            notAutoloaded add:eachNonMetaClass.
-        ].
+    aCollectionOfClasses do:[:eachClass |
+	|eachNonMetaClass|
+	eachNonMetaClass := eachClass theNonMetaclass.
+
+	(eachNonMetaClass isLoaded and:[eachNonMetaClass wasAutoloaded not]) ifTrue:[
+	    notAutoloaded add:eachNonMetaClass.
+	].
     ].
 
     notAutoloaded notEmpty ifTrue:[
-        force := Dialog
-                    confirm:(resources
-                                stringWithCRs:(notAutoloaded size == 1
-                                                ifTrue:['%1 was not autoloaded.\\Force unloading it anyway ?']
-                                                ifFalse:['Some (%2) classes were not autoloaded.\\Force unloading them anyway ?'])
-                                with:notAutoloaded first name
-                                with:notAutoloaded size).
-    ] ifFalse:[
-        force := false.
+	force := Dialog
+		    confirm:(resources
+				stringWithCRs:(notAutoloaded size == 1
+						ifTrue:['%1 was not autoloaded.\\Force unloading it anyway ?']
+						ifFalse:['Some (%2) classes were not autoloaded.\\Force unloading them anyway ?'])
+				with:notAutoloaded first name
+				with:notAutoloaded size).
+    ] ifFalse:[
+	force := false.
     ].
 
     aCollectionOfClasses do:[:eachClass |
-        |nm nameShown doIt eachNonMetaClass|
-
-        eachNonMetaClass := eachClass theNonMetaclass.
-        (force or:[(eachNonMetaClass isLoaded and:[eachNonMetaClass wasAutoloaded])]) ifTrue:[
-            nm := eachNonMetaClass name.
-            nameShown := self displayedClassNameOf:eachNonMetaClass.
-
-            doIt := true.
-            eachNonMetaClass hasDerivedInstances ifTrue:[
-                doIt := self confirm:(resources string:'''%1'' has (derived) instances. Unload anyway ?' with:nameShown allBold)
-            ].
-            doIt ifTrue:[
-                self busyLabel:'unloading %1 ...' with:nameShown.
-                [
-                    eachNonMetaClass unload.
-                ] ensure:[
-                    self normalLabel.
-                ].
-            ].
-        ]
+	|nm nameShown doIt eachNonMetaClass|
+
+	eachNonMetaClass := eachClass theNonMetaclass.
+	(force or:[(eachNonMetaClass isLoaded and:[eachNonMetaClass wasAutoloaded])]) ifTrue:[
+	    nm := eachNonMetaClass name.
+	    nameShown := self displayedClassNameOf:eachNonMetaClass.
+
+	    doIt := true.
+	    eachNonMetaClass hasDerivedInstances ifTrue:[
+		doIt := self confirm:(resources string:'''%1'' has (derived) instances. Unload anyway ?' with:nameShown allBold)
+	    ].
+	    doIt ifTrue:[
+		self busyLabel:'unloading %1 ...' with:nameShown.
+		[
+		    eachNonMetaClass unload.
+		] ensure:[
+		    self normalLabel.
+		].
+	    ].
+	]
     ].
 
     "Modified: / 12-09-2006 / 13:48:12 / cg"
@@ -55998,25 +56567,25 @@
     changedSource := aNavigationState codeView contentsAsString string.
 
     aNavigationState codeAspect == #method ifTrue:[
-        selectedMethod := aNavigationState theSingleSelectedMethod.
-        selectedMethod isNil ifTrue:[
-            aNavigationState selectedMethods value size > 0 ifTrue:[
-                self warn:'Oops - multiple methods selected. Cannot compare.'.
-            ] ifFalse:[
-                self warn:'Oops - method is gone. Cannot compare.'.
-            ].
-            ^ self
-        ].
-        originalSource := selectedMethod source string.
-        originalSource isNil ifTrue:[
-            self warn:'Oops - methods source is gone. Cannot compare source.'.
-            ^ self
-        ].
-        originalSource string = changedSource string ifTrue:[
-            self information:'Same text.'.
-            ^ self.
-        ].
-        self openDiffViewForText:changedSource againstSourceOfMethod:selectedMethod.
+	selectedMethod := aNavigationState theSingleSelectedMethod.
+	selectedMethod isNil ifTrue:[
+	    aNavigationState selectedMethods value size > 0 ifTrue:[
+		self warn:'Oops - multiple methods selected. Cannot compare.'.
+	    ] ifFalse:[
+		self warn:'Oops - method is gone. Cannot compare.'.
+	    ].
+	    ^ self
+	].
+	originalSource := selectedMethod source string.
+	originalSource isNil ifTrue:[
+	    self warn:'Oops - methods source is gone. Cannot compare source.'.
+	    ^ self
+	].
+	originalSource string = changedSource string ifTrue:[
+	    self information:'Same text.'.
+	    ^ self.
+	].
+	self openDiffViewForText:changedSource againstSourceOfMethod:selectedMethod.
 "/
 "/        v := DiffTextView
 "/                openOn:changedSource
@@ -56025,32 +56594,32 @@
 "/                label:(resources string:'Method''s actual code').
 "/        v label:(resources string:'Comparing method versions').
 "/        v waitUntilVisible.
-        ^ self
+	^ self
     ].
 
     aNavigationState codeAspect == #classDefinition ifTrue:[
-        selectedClass := aNavigationState theSingleSelectedClass.
-        selectedClass isNil ifTrue:[
-            aNavigationState selectedClasses value size > 0 ifTrue:[
-                self warn:'Oops - multiple classes selected. Cannot compare.'.
-            ] ifFalse:[
-                self warn:'Oops - class is gone. Cannot compare.'.
-            ].
-            ^ self
-        ].
-        originalSource := self classDefinitionStringFor:selectedClass.
-        originalSource isNil ifTrue:[
-            self warn:'Oops - class is gone. Cannot compare source.'.
-            ^ self
-        ].
-        v := DiffCodeView
-                openOn:changedSource
-                label:(resources string:'Changed definition (to be accepted ?)')
-                and:originalSource
-                label:(resources string:'Classes actual definition').
-        v label:(resources string:'Comparing class definitions').
-        v waitUntilVisible.
-        ^ self
+	selectedClass := aNavigationState theSingleSelectedClass.
+	selectedClass isNil ifTrue:[
+	    aNavigationState selectedClasses value size > 0 ifTrue:[
+		self warn:'Oops - multiple classes selected. Cannot compare.'.
+	    ] ifFalse:[
+		self warn:'Oops - class is gone. Cannot compare.'.
+	    ].
+	    ^ self
+	].
+	originalSource := self classDefinitionStringFor:selectedClass.
+	originalSource isNil ifTrue:[
+	    self warn:'Oops - class is gone. Cannot compare source.'.
+	    ^ self
+	].
+	v := DiffCodeView
+		openOn:changedSource
+		label:(resources string:'Changed definition (to be accepted ?)')
+		and:originalSource
+		label:(resources string:'Classes actual definition').
+	v label:(resources string:'Comparing class definitions').
+	v waitUntilVisible.
+	^ self
     ].
 
     ^ self.
@@ -56063,25 +56632,25 @@
      Return true, if I have eaten the event"
 
     ((rawKey == #BackSpace) or:[ key == #CursorLeft ]) ifTrue:[
-        self
-            enqueueMessage:#backToLastClass
-            for:self
-            arguments:#().
-        ^ true
+	self
+	    enqueueMessage:#backToLastClass
+	    for:self
+	    arguments:#().
+	^ true
     ].
     (key == #Rename "rawKey == #Cmdr") ifTrue:[
-        self
-            enqueueMessage:#categoryMenuRename
-            for:self
-            arguments:#().
-        ^ true
+	self
+	    enqueueMessage:#categoryMenuRename
+	    for:self
+	    arguments:#().
+	^ true
     ].
     (key == #Find or:[ key == #FindNext ]) ifTrue:[
-        self
-            enqueueMessage:#searchMenuFindClass
-            for:self
-            arguments:#().
-        ^ true
+	self
+	    enqueueMessage:#searchMenuFindClass
+	    for:self
+	    arguments:#().
+	^ true
     ].
     ^ false
 !
@@ -56091,18 +56660,18 @@
      Return true, if I have eaten the event"
 
     ((rawKey == #BackSpace) or:[ key == #CursorLeft ]) ifTrue:[
-        self
-            enqueueMessage:#backToLastClass
-            for:self
-            arguments:#().
-        ^ true
+	self
+	    enqueueMessage:#backToLastClass
+	    for:self
+	    arguments:#().
+	^ true
     ].
     (key == #Rename "rawKey == #Cmdr") ifTrue:[
-        self
-            enqueueMessage:#classMenuRename
-            for:self
-            arguments:#().
-        ^ true
+	self
+	    enqueueMessage:#classMenuRename
+	    for:self
+	    arguments:#().
+	^ true
     ].
 "/    (rawKey == #Delete) ifTrue:[
 "/        self
@@ -56112,11 +56681,11 @@
 "/        ^ true
 "/    ].
     (key == #Find or:[ key == #FindNext ]) ifTrue:[
-        self
-            enqueueMessage:#searchMenuFindClass
-            for:self
-            arguments:#().
-        ^ true
+	self
+	    enqueueMessage:#searchMenuFindClass
+	    for:self
+	    arguments:#().
+	^ true
     ].
     ^ false
 !
@@ -56126,32 +56695,32 @@
      Return true, if I have eaten the event"
 
     ((rawKey == #BackSpace) or:[ key == #CursorLeft ]) ifTrue:[
-        self
-            enqueueMessage:#backToLastClass
-            for:self
-            arguments:#().
-        ^ true
+	self
+	    enqueueMessage:#backToLastClass
+	    for:self
+	    arguments:#().
+	^ true
     ].
     (key == #Rename "rawKey == #Cmdr") ifTrue:[
-        self
-            enqueueMessage:#classMenuRename
-            for:self
-            arguments:#().
-        ^ true
+	self
+	    enqueueMessage:#classMenuRename
+	    for:self
+	    arguments:#().
+	^ true
     ].
     ((key == #Cut) or:[rawKey == #Delete]) ifTrue:[
-        self
-            enqueueMessage:#classMenuRemove
-            for:self
-            arguments:#().
-        ^ true
+	self
+	    enqueueMessage:#classMenuRemove
+	    for:self
+	    arguments:#().
+	^ true
     ].
     (key == #Find or:[ key == #FindNext ]) ifTrue:[
-        self
-            enqueueMessage:#searchMenuFindClass
-            for:self
-            arguments:#().
-        ^ true
+	self
+	    enqueueMessage:#searchMenuFindClass
+	    for:self
+	    arguments:#().
+	^ true
     ].
     ^ false
 
@@ -56162,25 +56731,25 @@
     "filter keyboard events for Find key (unless typed into the codeView).
      Return true, if I have eaten the event"
 
-    (UserPreferences current useCodeView2In:#Browser) ifFalse:[ 
-        "/ old-style codeView
-        key == #CodeCompletion ifTrue:[
-            "/ complete the word before/under the cursor.
-            self
-                enqueueMessage:#codeCompletion
-                for:self
-                arguments:#().
-            ^ true
-        ].
+    (UserPreferences current useCodeView2In:#Browser) ifFalse:[
+	"/ old-style codeView
+	key == #CodeCompletion ifTrue:[
+	    "/ complete the word before/under the cursor.
+	    self
+		enqueueMessage:#codeCompletion
+		for:self
+		arguments:#().
+	    ^ true
+	].
     ].
     key == #Rename ifTrue:[
-        self hasLocalVariableSelectedInCodeView ifTrue:[
-        self
-            enqueueMessage:#codeMenuRenameTemporary
-            for:self
-            arguments:#().
-        ].
-        ^ true
+	self hasLocalVariableSelectedInCodeView ifTrue:[
+	self
+	    enqueueMessage:#codeMenuRenameTemporary
+	    for:self
+	    arguments:#().
+	].
+	^ true
     ].
     ^ false
 
@@ -56193,11 +56762,11 @@
      Return true, if I have eaten the event"
 
     (key == #Rename "rawKey == #Cmdr") ifTrue:[
-        self
-            enqueueMessage:#protocolMenuRename
-            for:self
-            arguments:#().
-        ^ true
+	self
+	    enqueueMessage:#protocolMenuRename
+	    for:self
+	    arguments:#().
+	^ true
     ].
     "/ cg: no longer; these keys are now ALWAYS forwarded to the codeView
     "/    (key == #Find or:[ key == #FindNext ]) ifTrue:[
@@ -56208,11 +56777,11 @@
     "/        ^ true
     "/    ].
     (rawKey == #Cmdt) ifTrue:[
-        self
-            enqueueMessage:#browseMenuMethodsWithString
-            for:self
-            arguments:#().
-        ^ true
+	self
+	    enqueueMessage:#browseMenuMethodsWithString
+	    for:self
+	    arguments:#().
+	^ true
     ].
     ^ false
 !
@@ -56222,47 +56791,47 @@
      Return true, if I have eaten the event"
 
     (rawKey == #CtrlCursorUp) ifTrue:[
-        self
-            enqueueMessage:#selectorMenuPushUpMethod
-            for:self
-            arguments:#().
-        ^ true
+	self
+	    enqueueMessage:#selectorMenuPushUpMethod
+	    for:self
+	    arguments:#().
+	^ true
     ].
     ((key == #Cut) or:[rawKey == #Delete]) ifTrue:[
-        "JV@2012-05-08: This used to be 'unsafe' remove. When changing
-         such a havily used feature, please at least add an preference to
-         to switch it back to old behavior!!!!!!
-
-         Perhaps, we need a better framework to define shortcuts.
-
-         HACK: changed back
-        "
-        self
-            enqueueMessage:#selectorMenuRemove
-            for:self
-            arguments:#().
-        ^ true
+	"JV@2012-05-08: This used to be 'unsafe' remove. When changing
+	 such a havily used feature, please at least add an preference to
+	 to switch it back to old behavior!!!!!!
+
+	 Perhaps, we need a better framework to define shortcuts.
+
+	 HACK: changed back
+	"
+	self
+	    enqueueMessage:#selectorMenuRemove
+	    for:self
+	    arguments:#().
+	^ true
     ].
     (key == #Rename "rawKey == #Cmdr") ifTrue:[
-        self
-            enqueueMessage:#selectorMenuRename
-            for:self
-            arguments:#().
-        ^ true
+	self
+	    enqueueMessage:#selectorMenuRename
+	    for:self
+	    arguments:#().
+	^ true
     ].
     (rawKey == #Cmdi) ifTrue:[
-        self
-            enqueueMessage:#browseImplementorsOf
-            for:self
-            arguments:#().
-        ^ true
+	self
+	    enqueueMessage:#browseImplementorsOf
+	    for:self
+	    arguments:#().
+	^ true
     ].
     (rawKey == #Cmdt) ifTrue:[
-        self
-            enqueueMessage:#browseMenuMethodsWithString
-            for:self
-            arguments:#().
-        ^ true
+	self
+	    enqueueMessage:#browseMenuMethodsWithString
+	    for:self
+	    arguments:#().
+	^ true
     ].
     "/ cg: no longer; these keys are now ALWAYS forwarded to the codeView
     "/    (key == #Find or:[ key == #FindNext ]) ifTrue:[
@@ -56283,18 +56852,18 @@
      Return true, if I have eaten the event"
 
     ((rawKey == #BackSpace) or:[ key == #CursorLeft ]) ifTrue:[
-        self
-            enqueueMessage:#backToLastClass
-            for:self
-            arguments:#().
-        ^ true
+	self
+	    enqueueMessage:#backToLastClass
+	    for:self
+	    arguments:#().
+	^ true
     ].
     (key == #Find or:[ key == #FindNext ]) ifTrue:[
-        self
-            enqueueMessage:#searchMenuFindClass
-            for:self
-            arguments:#().
-        ^ true
+	self
+	    enqueueMessage:#searchMenuFindClass
+	    for:self
+	    arguments:#().
+	^ true
     ].
     ^ false
 !
@@ -56306,21 +56875,21 @@
     |variablesToRemove|
 
     ((key == #Cut) or:[rawKey == #Delete]) ifTrue:[
-        variablesToRemove := self selectedVariables value.
-        variablesToRemove size > 0 ifTrue:[
-            self
-                enqueueMessage:#variablesRemoveWithConfirmation
-                for:self
-                arguments:#().
-        ].
-        ^ true
+	variablesToRemove := self selectedVariables value.
+	variablesToRemove size > 0 ifTrue:[
+	    self
+		enqueueMessage:#variablesRemoveWithConfirmation
+		for:self
+		arguments:#().
+	].
+	^ true
     ].
     (key == #Rename "rawKey == #Cmdr") ifTrue:[
-        self
-            enqueueMessage:#variablesMenuRename
-            for:self
-            arguments:#().
-        ^ true
+	self
+	    enqueueMessage:#variablesMenuRename
+	    for:self
+	    arguments:#().
+	^ true
     ].
     ^ false
 
@@ -56334,30 +56903,30 @@
     |codeView evView key rawKey sensor|
 
     codeView := self codeView.
-    "/JV@2011-08-17: FIXME: remove the typecheck and add isCodeView2 
+    "/JV@2011-08-17: FIXME: remove the typecheck and add isCodeView2
     "/or something...
     (codeView isKindOf: Tools::CodeView2) ifTrue:[
-        codeView := codeView textView.
+	codeView := codeView textView.
     ].
     evView := anEvent targetView.
     evView notNil ifTrue:[
-        anEvent isKeyPressEvent ifTrue:[
-            key := anEvent key.
-            rawKey := anEvent rawKey.
-
-            rawKey == #Ctrll ifTrue:
-                [(self componentAt: #SearchedClassNameComboBox) takeFocus.
-                ^true].
-
-            (evView isSameOrComponentOf:codeView) ifTrue:[
-                ^ self keyInCodeView:key rawKey:rawKey
-            ].
-
-            "/ cg: these keys are now ALWAYS forwarded to the codeView
-            (false "key == #Find" or:[ key == #FindNext or:[ key == #FindPrev ]]) ifTrue:[
-                anEvent dispatchTo:self codeView.
-                ^ true
-            ].
+	anEvent isKeyPressEvent ifTrue:[
+	    key := anEvent key.
+	    rawKey := anEvent rawKey.
+
+	    rawKey == #Ctrll ifTrue:
+		[(self componentAt: #SearchedClassNameComboBox) takeFocus.
+		^true].
+
+	    (evView isSameOrComponentOf:codeView) ifTrue:[
+		^ self keyInCodeView:key rawKey:rawKey
+	    ].
+
+	    "/ cg: these keys are now ALWAYS forwarded to the codeView
+	    (false "key == #Find" or:[ key == #FindNext or:[ key == #FindPrev ]]) ifTrue:[
+		anEvent dispatchTo:self codeView.
+		^ true
+	    ].
 
 "/            key == #Find ifTrue:[
 "/                self
@@ -56374,56 +56943,56 @@
 "/                ^ true
 "/            ].
 
-            (self view:evView belongsToSubApplication:self categoryListApp) ifTrue:[
-                ^ self keyInCategoryListView:key rawKey:rawKey
-            ].
-            (self view:evView belongsToSubApplication:self projectListApp) ifTrue:[
-                ^ self keyInProjectListView:key rawKey:rawKey
-            ].
-            (self view:evView belongsToSubApplication:self classListApp) ifTrue:[
-                ^ self keyInClassListView:key rawKey:rawKey
-            ].
-            (self view:evView belongsToSubApplication:self classHierarchyListApp) ifTrue:[
-                ^ self keyInClassHierarchyListView:key rawKey:rawKey
-            ].
-            (self view:evView belongsToSubApplication:self methodCategoryListApp) ifTrue:[
-                ^ self keyInMethodCategoryListView:key rawKey:rawKey
-            ].
-            (self view:evView belongsToSubApplication:self methodListApp) ifTrue:[
-                ^ self keyInMethodListView:key rawKey:rawKey
-            ].
-            (self view:evView belongsToSubApplication:navigationState variableListApplication) ifTrue:[
-                ^ self keyInVariableListView:key rawKey:rawKey
-            ].
-        ].
-
-        anEvent isButtonReleaseEvent ifTrue:[
-            anEvent delegatedFrom isNil ifTrue:[
-                
-                evView == codeView ifTrue:[
-                    self codeInfoVisible value ifTrue:[
-                        self doImmediateExplaining value ifTrue:[
-                            anEvent delegatedFrom:self.
-                            sensor := evView sensor.
-                            sensor pushEvent:anEvent.  "/ must be first in queue
-                                                       "/ (for the buttonRelease to be processed)
-                            self
-                                enqueueMessage:#delayedExplainSelection
-                                for:self
-                                arguments:#() .
-
-                            ^ true "/ release event has been added already
-                        ].
-                    ].
-                ]
-            ]
-        ].
+	    (self view:evView belongsToSubApplication:self categoryListApp) ifTrue:[
+		^ self keyInCategoryListView:key rawKey:rawKey
+	    ].
+	    (self view:evView belongsToSubApplication:self projectListApp) ifTrue:[
+		^ self keyInProjectListView:key rawKey:rawKey
+	    ].
+	    (self view:evView belongsToSubApplication:self classListApp) ifTrue:[
+		^ self keyInClassListView:key rawKey:rawKey
+	    ].
+	    (self view:evView belongsToSubApplication:self classHierarchyListApp) ifTrue:[
+		^ self keyInClassHierarchyListView:key rawKey:rawKey
+	    ].
+	    (self view:evView belongsToSubApplication:self methodCategoryListApp) ifTrue:[
+		^ self keyInMethodCategoryListView:key rawKey:rawKey
+	    ].
+	    (self view:evView belongsToSubApplication:self methodListApp) ifTrue:[
+		^ self keyInMethodListView:key rawKey:rawKey
+	    ].
+	    (self view:evView belongsToSubApplication:navigationState variableListApplication) ifTrue:[
+		^ self keyInVariableListView:key rawKey:rawKey
+	    ].
+	].
+
+	anEvent isButtonReleaseEvent ifTrue:[
+	    anEvent delegatedFrom isNil ifTrue:[
+
+		evView == codeView ifTrue:[
+		    self codeInfoVisible value ifTrue:[
+			self doImmediateExplaining value ifTrue:[
+			    anEvent delegatedFrom:self.
+			    sensor := evView sensor.
+			    sensor pushEvent:anEvent.  "/ must be first in queue
+						       "/ (for the buttonRelease to be processed)
+			    self
+				enqueueMessage:#delayedExplainSelection
+				for:self
+				arguments:#() .
+
+			    ^ true "/ release event has been added already
+			].
+		    ].
+		]
+	    ]
+	].
     ].
 
     anEvent isButtonMultiPressEvent ifTrue:[
-        anEvent view name = 'CursorLineLabel' ifTrue:[
-            self codeView gotoLine
-        ].
+	anEvent view name = 'CursorLineLabel' ifTrue:[
+	    self codeView gotoLine
+	].
     ].
 
     ^ false
@@ -56443,17 +57012,26 @@
 
     messagePaneView isVisible ifFalse:[^self]."/already hidden"
     messagePaneView isVisible: false.
-    tabContentView  layout: 
-        (tabContentView layout topOffset: 0; yourself)
+    tabContentView  layout:
+	(tabContentView layout topOffset: 0; yourself)
 
     "Created: / 28-08-2010 / 10:49:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 hideMessagePaneAndAbort
-    self navigationState worker terminate.
-    self navigationState worker:nil.
+    |worker|
+
+    (worker := self navigationState worker) notNil ifTrue:[
+	"asynchronous"
+	self navigationState worker:nil.
+	worker terminate.
+    ] ifFalse:[
+	"synchronous"
+	AbortSignal raise
+    ].
 
     "Created: / 28-08-2010 / 20:50:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 15-05-2012 / 11:03:06 / cg"
 !
 
 hideMessagePaneIn: givenNavigationState
@@ -56464,8 +57042,8 @@
 
     messagePaneView isVisible ifFalse:[^self]."/already hidden"
     messagePaneView isVisible: false.
-    tabContentView  layout: 
-        (tabContentView layout topOffset: 0; yourself)
+    tabContentView  layout:
+	(tabContentView layout topOffset: 0; yourself)
 
     "Created: / 28-08-2010 / 20:39:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -56476,41 +57054,80 @@
     self showMessagePane: #messageInfoSpec.
 
     "
-        WindowGroup activeApplication showMessage: 'Hello'
+	WindowGroup activeApplication showMessage: 'Hello'
     "
 
     "Created: / 28-08-2010 / 11:47:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 showMessage:message while:block
+    "used for long-during operations: show a progressbar and a message in the top pane,
+     while executing block"
+
+    ^ self showMessage:message while:block inBackground: false
+
+    "Created: / 28-08-2010 / 20:10:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 15-05-2012 / 10:47:31 / cg"
+!
+
+showMessage:message while:block inBackground:inBackgroundBoolean
     "used for long-during lint operations: show a progressbar and a message in the top pane,
-     execute block in another (background-) thread"
-
-    |state worker|
+     optionally execute block in another (background-) thread"
+
+    |state actionWithIndicator worker|
 
     state := self navigationState.
-    worker := 
-        [
-            self showMessagePane:#progressInfoSpec in:state.
-            block on:UserNotification
-                do:[:notification | 
-                    self messageHolder value:notification description.
-                    (notification isKindOf:ProgressNotification) ifTrue:[
-                        self progressHolder value:notification progressValue
-                    ].
-                    notification proceed
-                ]
-        ] newProcess. 
-    worker addExitAction:[ self hideMessagePaneIn:state ].
-    worker priorityRange:(4 to:8).
-    state worker:worker.
-    worker resume.
+
+    actionWithIndicator :=
+	    [
+		[
+		    self showMessagePane:#progressInfoSpec in:state.
+		    block
+			on:UserNotification
+			do:[:notification |
+			    (notification isKindOf:ProgressNotification) ifTrue:[
+				self progressHolder value:notification progressValue.
+				inBackgroundBoolean ifFalse:[
+				    "care for redraw and abort-button"
+				    "/ self windowGroup repairDamage.
+				    self windowGroup processEvents.
+				].
+			    ] ifFalse:[
+				self messageHolder value:notification description.
+			    ].
+			    notification proceed
+			]
+		] ensure:[
+		    self hideMessagePaneIn:state.
+		].
+	    ].
+
+    inBackgroundBoolean ifTrue:[
+	worker := actionWithIndicator newProcess.
+	worker priorityRange:(4 to:8).
+	state worker:worker.
+	worker resume.
+	^ worker
+    ].
+
+    actionWithIndicator value.
+    ^ nil
 
     "Created: / 28-08-2010 / 20:10:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 06-03-2012 / 18:37:40 / cg"
-!
-
-showMessagePane: spec 
+    "Created: / 15-05-2012 / 10:46:47 / cg"
+!
+
+showMessage:message whileExecutingBackgroundAction:block
+    "used for long-during lint operations: show a progressbar and a message in the top pane,
+     execute block in another (background-) thread"
+
+    ^ self showMessage:message while:block inBackground: true
+
+    "Created: / 28-08-2010 / 20:10:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 15-05-2012 / 10:45:49 / cg"
+!
+
+showMessagePane: spec
 
     ^self showMessagePane: spec in: self navigationState
 
@@ -56524,8 +57141,8 @@
     tabContentView :=  givenNavigationState tabContentView.
     messagePaneView isVisible ifTrue:[^self]."/already shown"
     messagePaneView isVisible: true.
-    tabContentView  layout: 
-        (tabContentView layout topOffset: 40; yourself).
+    tabContentView  layout:
+	(tabContentView layout topOffset: 40; yourself).
     self messageSpecHolder value: spec.
 
     "Created: / 28-08-2010 / 20:37:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -56533,35 +57150,35 @@
 !
 
 showMessageWhileTest
-    self 
-        showMessage:'Tools::NewSystemBrowser >> testProgressAction'
-        while:[
-            (1 to:100) do:[:i | 
-                (ProgressNotification new)
-                    messageText:('Tools::NewSystemBrowser >> testProgressAction (%1 done)' 
-                                bindWith:i);
-                    parameter:i;
-                    raiseRequest.
-                Delay waitForMilliseconds:30.
-            ].
-            Transcript showCR:'Tools::NewSystemBrowser >> testProgressAction done!!'
-        ]
+    self
+	showMessage:'Tools::NewSystemBrowser >> testProgressAction'
+	whileExecutingBackgroundAction:[
+	    (1 to:100) do:[:i |
+		(ProgressNotification new)
+		    messageText:('Tools::NewSystemBrowser >> testProgressAction (%1 done)'
+				bindWith:i);
+		    parameter:i;
+		    raiseRequest.
+		Delay waitForMilliseconds:30.
+	    ].
+	    Transcript showCR:'Tools::NewSystemBrowser >> testProgressAction done!!'
+	]
 
     "Created: / 28-08-2010 / 10:32:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 29-11-2011 / 15:05:31 / cg"
+    "Modified: / 15-05-2012 / 10:46:06 / cg"
 ! !
 
 !NewSystemBrowser methodsFor:'user actions-profiler'!
 
 spawnProfilerStatistics:statistics in: where
 
-    self 
-        newBrowserOrBufferDependingOn: where 
-        label:'Visual Profiler' 
-        forSpec:#visualProfilerSpec 
-        setupWith: [:browser|
-            browser profilerStatistics value: statistics
-        ]
+    self
+	newBrowserOrBufferDependingOn: where
+	label:'Visual Profiler'
+	forSpec:#visualProfilerSpec
+	setupWith: [:browser|
+	    browser profilerStatistics value: statistics
+	]
 
     "Created: / 09-10-2007 / 22:05:36 / janfrog"
     "Modified (format): / 29-11-2011 / 14:49:08 / cg"
@@ -56589,9 +57206,9 @@
 
 asString
     ^klass isJavaClass ifTrue:[
-        klass javaName
-    ] ifFalse:[
-        klass name
+	klass javaName
+    ] ifFalse:[
+	klass name
     ].
 
     "Created: / 04-04-2012 / 13:00:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -56604,30 +57221,30 @@
     | name namespace lw cnw fg |
 
     showPrefix ifTrue:[
-        name := klass name.
-        namespace := nil
-    ] ifFalse:[
-        name := klass nameWithoutPrefix.
-        klass isJavaClass ifFalse:[
-            namespace := klass  nameSpace name.
-        ] ifTrue:[
-            namespace := klass javaPackage.
-        ]
+	name := klass name.
+	namespace := nil
+    ] ifFalse:[
+	name := klass nameWithoutPrefix.
+	klass isJavaClass ifFalse:[
+	    namespace := klass  nameSpace name.
+	] ifTrue:[
+	    namespace := klass javaPackage.
+	]
     ].
 
     name displayOn:aGC x:x y:y opaque:opaque.
 
     (namespace notNil and:[namespace ~~ #Smalltalk]) ifTrue:[
-        namespace := 'in ', namespace.
-        lw :=  x + 16 + (name widthOn: aGC).
-        cnw := aGC widthOfString: namespace.
-
-        (aGC width > (lw + cnw + 5)) ifTrue:[
-            fg := aGC paint.
-            aGC paint: (Color gray: 40).
-            namespace displayOn:aGC x: aGC width - cnw - 5 y:y opaque:opaque.
-            aGC paint: fg.
-        ]
+	namespace := 'in ', namespace.
+	lw :=  x + 16 + (name widthOn: aGC).
+	cnw := aGC widthOfString: namespace.
+
+	(aGC width > (lw + cnw + 5)) ifTrue:[
+	    fg := aGC paint.
+	    aGC paint: (Color gray: 40).
+	    namespace displayOn:aGC x: aGC width - cnw - 5 y:y opaque:opaque.
+	    aGC paint: fg.
+	]
     ]
 
     "Created: / 04-04-2012 / 13:03:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -56638,9 +57255,9 @@
     | name |
 
     showPrefix ifTrue:[
-        name := klass name.
-    ] ifFalse:[
-        name := klass nameWithoutPrefix.
+	name := klass name.
+    ] ifFalse:[
+	name := klass nameWithoutPrefix.
     ].
     ^name
 
@@ -56663,15 +57280,15 @@
 !NewSystemBrowser class methodsFor:'documentation'!
 
 version
-    ^ '$Id: Tools__NewSystemBrowser.st 7996 2012-05-15 17:04:40Z vranyj1 $'
+    ^ '$Header: /cvs/stx/stx/libtool/Tools__NewSystemBrowser.st,v 1.1750 2012/06/04 20:50:26 cg Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libtool/Tools__NewSystemBrowser.st,v 1.1741 2012/04/28 16:13:27 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libtool/Tools__NewSystemBrowser.st,v 1.1750 2012/06/04 20:50:26 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: Tools__NewSystemBrowser.st 7996 2012-05-15 17:04:40Z vranyj1 $'
+    ^ '$Id: Tools__NewSystemBrowser.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
 
 NewSystemBrowser initialize!
--- a/Tools__OrganizerCanvas.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__OrganizerCanvas.st	Tue Jun 05 15:49:00 2012 +0100
@@ -5037,6 +5037,6 @@
 !
 
 version_SVN
-    ^ '$Id: Tools__OrganizerCanvas.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__OrganizerCanvas.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
 
--- a/Tools__ProjectList.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__ProjectList.st	Tue Jun 05 15:49:00 2012 +0100
@@ -966,5 +966,5 @@
 !
 
 version_SVN
-    ^ '$Id: Tools__ProjectList.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__ProjectList.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/Tools__SearchDialog.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__SearchDialog.st	Tue Jun 05 15:49:00 2012 +0100
@@ -1329,7 +1329,7 @@
 !
 
 version_SVN
-    ^ '$Id: Tools__SearchDialog.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__SearchDialog.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
 
 SearchDialog initialize!
--- a/Tools__SpecialCodeView.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__SpecialCodeView.st	Tue Jun 05 15:49:00 2012 +0100
@@ -73,7 +73,7 @@
 !SpecialCodeView class methodsFor:'documentation'!
 
 version
-    ^ '$Id: Tools__SpecialCodeView.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__SpecialCodeView.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 !
 
 version_CVS
@@ -81,5 +81,5 @@
 !
 
 version_SVN
-    ^ '$Id: Tools__SpecialCodeView.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__SpecialCodeView.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/Tools__TagList.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__TagList.st	Tue Jun 05 15:49:00 2012 +0100
@@ -25,7 +25,7 @@
 		hidePythonFunctions hideOzClasses hideOzMethods hideOzFunctions
 		hideHTMLTextArea hideHTMLInput hideHTMLTable hideHTMLScript
 		hideHTMLForm usingDefaultCTags ctagsCommand ctagsIsExCtags
-		ctagsIsExCtags5x hideDocumentation remoteTarget'
+		ctagsIsExCtags5x hideDocumentation remoteTarget hideLocalLabels3'
 	classVariableNames:'Sorted CachedTagListsPerFile DefaultSortCriteria DefaultShowOnly
 		TagsSuffixes DefaultGroupBy'
 	poolDictionaries:''
@@ -857,6 +857,19 @@
     "Created: / 24-03-2012 / 23:23:20 / cg"
 !
 
+hideLocalLabels3
+    ^ hideLocalLabels3 ? false
+
+    "Created: / 13-05-2012 / 11:12:37 / cg"
+!
+
+hideLocalLabels3:aBoolean
+    hideLocalLabels3 := aBoolean.
+
+    "Modified: / 05-05-2011 / 15:22:54 / cg"
+    "Created: / 13-05-2012 / 11:12:42 / cg"
+!
+
 hideLocalLabels:aBoolean
     hideLocalLabels := aBoolean.
 
@@ -1920,7 +1933,7 @@
 
     [ 
         list := self fromFile:aFile in:aTempDirectory
-    ] valueNowOrOnUnwindDo:[
+    ] ensure:[
         remoteTarget := nil.
     ].
     ^ list
@@ -2255,7 +2268,7 @@
     "
 
     |targets line l lineNr nm s words w directive
-     hideLocals hideLocals2 hideData hideText currentSegment|
+     hideLocals hideLocals2 hideLocals3 hideData hideText currentSegment|
 
     Tag autoload.
 
@@ -2264,6 +2277,7 @@
     s notNil ifTrue:[
         hideLocals := hideLocalLabels ? false.
         hideLocals2 := hideLocalLabels2 ? false.
+        hideLocals3 := hideLocalLabels3 ? false.
         hideData := hideDataLabels ? false.
         hideText := hideTextLabels ? false.
         currentSegment := #text.
@@ -2281,12 +2295,18 @@
                         (hideData and:[currentSegment == #data]) ifFalse:[
                             (hideLocals and:[(w startsWith:$.)]) ifFalse:[
                                 (hideLocals2 and:[(w startsWith:$_) not]) ifFalse:[
-                                    nm := w copyWithoutLast:1.
-                                    targets add:(Tag::TLabel 
-                                                    label:nm 
-                                                    pattern:nil
-                                                    type:nil
-                                                    lineNumber:lineNr).
+                                    (hideLocals3 
+                                        and:[ (w startsWith:$L) 
+                                        and:[ (w size > 1) 
+                                        and:[ ((w copyFrom:2 to:(w size-1)) conform:[:c | c isDigit])
+                                     ]]]) ifFalse:[
+                                        nm := w copyWithoutLast:1.
+                                        targets add:(Tag::TLabel 
+                                                        label:nm 
+                                                        pattern:nil
+                                                        type:nil
+                                                        lineNumber:lineNr).
+                                    ].
                                 ].
                             ].
                         ].
@@ -2316,7 +2336,7 @@
     ].
     ^ targets
 
-    "Modified: / 24-03-2012 / 23:24:22 / cg"
+    "Modified: / 13-05-2012 / 11:25:49 / cg"
 !
 
 getSimpleTagListFromFile:aFileOrString in:aTempDirectory
@@ -3291,13 +3311,13 @@
 !TagList class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/Tools__TagList.st,v 1.10 2012/03/24 22:26:07 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/Tools__TagList.st,v 1.12 2012/05/13 09:28:08 cg Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libtool/Tools__TagList.st,v 1.10 2012/03/24 22:26:07 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libtool/Tools__TagList.st,v 1.12 2012/05/13 09:28:08 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: Tools__TagList.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__TagList.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/Tools__TagsBrowser.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__TagsBrowser.st	Tue Jun 05 15:49:00 2012 +0100
@@ -177,6 +177,14 @@
           )
          (MenuItem
             enabled: tagTypesPresentHolder
+            label: 'Hide local labels3 ("L[0-9]+")'
+            translateLabel: true
+            isVisible: editedFileHasAssemblerSuffix
+            hideMenuOnActivated: false
+            indication: hideLocalLabels3:
+          )
+         (MenuItem
+            enabled: tagTypesPresentHolder
             label: 'Hide data labels'
             translateLabel: true
             isVisible: editedFileHasAssemblerSuffix
@@ -196,7 +204,7 @@
         nil
       )
 
-    "Modified: / 24-03-2012 / 23:22:45 / cg"
+    "Modified: / 13-05-2012 / 11:26:28 / cg"
 !
 
 cMenuSlice
@@ -1310,6 +1318,19 @@
     "Created: / 24-03-2012 / 23:23:26 / cg"
 !
 
+hideLocalLabels3
+    ^ tagList hideLocalLabels3
+
+    "Created: / 13-05-2012 / 11:09:54 / cg"
+!
+
+hideLocalLabels3:aBool
+    tagList hideLocalLabels3:aBool.
+    self updateTagList
+
+    "Created: / 13-05-2012 / 11:10:01 / cg"
+!
+
 hideLocalLabels:aBool
     tagList hideLocalLabels:aBool.
     self updateTagList
@@ -2205,7 +2226,7 @@
                 ].
                 aBlock value.
             ]
-        ] valueNowOrOnUnwindDo:[
+        ] ensure:[
             process := nil.
             self enabled:true.
         ].
@@ -2272,13 +2293,13 @@
 !TagsBrowser class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/Tools__TagsBrowser.st,v 1.24 2012/03/24 22:25:38 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/Tools__TagsBrowser.st,v 1.26 2012/05/13 09:30:16 cg Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libtool/Tools__TagsBrowser.st,v 1.24 2012/03/24 22:25:38 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libtool/Tools__TagsBrowser.st,v 1.26 2012/05/13 09:30:16 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: Tools__TagsBrowser.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__TagsBrowser.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/Tools__TestRunner2.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__TestRunner2.st	Tue Jun 05 15:49:00 2012 +0100
@@ -27,7 +27,7 @@
 
 "{ NameSpace: Tools }"
 
-AbstractTestRunner subclass:#TestRunner2
+Tools::AbstractTestRunner subclass:#TestRunner2
 	instanceVariableNames:'classCategoryOrPackageTabIndexHolder classCategoryList
 		packageList classList classListOutGeneratorHolder
 		classListInGeneratorHolder modeHolder detailsHolder
@@ -39,7 +39,7 @@
 	category:'SUnit-UI'
 !
 
-ClassList subclass:#ClassList
+Tools::ClassList subclass:#ClassList
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -1468,7 +1468,7 @@
 
 resultListMenuBrowse
     UserPreferences current systemBrowserClass 
-        openInClass: (self selectedTestSuite tests first class) selector:(self selectedResultHolder value test selector).
+        openInClass: (self selectedResultHolder value test class) selector:(self selectedResultHolder value test selector).
 
     "Created: / 23-09-2011 / 18:55:50 / cg"
 ! !
@@ -1815,7 +1815,7 @@
 !TestRunner2::ClassList class methodsFor:'documentation'!
 
 version
-    ^'$Id: Tools__TestRunner2.st 7911 2012-02-22 09:55:48Z vranyj1 $'
+    ^'$Header: /cvs/stx/stx/libtool/Tools__TestRunner2.st,v 1.29 2012/05/09 10:25:30 stefan Exp $'
 ! !
 
 !TestRunner2::ClassList methodsFor:'private'!
@@ -2312,16 +2312,16 @@
 !TestRunner2 class methodsFor:'documentation'!
 
 version
-    ^ '$Id: Tools__TestRunner2.st 7911 2012-02-22 09:55:48Z vranyj1 $'
+    ^ '$Header: /cvs/stx/stx/libtool/Tools__TestRunner2.st,v 1.29 2012/05/09 10:25:30 stefan Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libtool/Tools__TestRunner2.st,v 1.28 2011/09/23 17:18:27 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libtool/Tools__TestRunner2.st,v 1.29 2012/05/09 10:25:30 stefan Exp §'
 !
 
 version_SVN
-    ^ '$Id: Tools__TestRunner2.st 7911 2012-02-22 09:55:48Z vranyj1 $'
+    ^ '$Id: Tools__TestRunner2.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
 
 TestRunner2 initialize!
-
+TestRunner2::ResultList::ListEntry initialize!
--- a/Tools__TestRunnerEmbedded.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__TestRunnerEmbedded.st	Tue Jun 05 15:49:00 2012 +0100
@@ -28,11 +28,11 @@
 "{ NameSpace: Tools }"
 
 AbstractTestRunner subclass:#TestRunnerEmbedded
-	instanceVariableNames:'runnerPanel selectedTestCases selectedClassesHolder
-		selectedProtocolsHolder selectedMethodsHolder
-		methodGeneratorHolder resultHolder resultInfoHolder
-		resultBackgroundColorHolder runningHolder progressHolder
-		infoHolder'
+	instanceVariableNames:'runnerPanel selectedClassesHolder selectedProtocolsHolder
+		selectedMethodsHolder methodGeneratorHolder resultHolder
+		resultInfoHolder resultBackgroundColorHolder runningHolder
+		progressHolder progressIndicatorShownHolder infoHolder
+		testProcess allTestCases'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'SUnit-UI'
@@ -81,6 +81,43 @@
 "
 ! !
 
+!TestRunnerEmbedded class methodsFor:'help specs'!
+
+flyByHelpSpec
+    "This resource specification was automatically generated
+     by the UIHelpTool of ST/X."
+
+    "Do not manually edit this!! If it is corrupted,
+     the UIHelpTool may not be able to read the specification."
+
+    "
+     UIHelpTool openOnClass:Tools::TestRunnerEmbedded    
+    "
+
+    <resource: #help>
+
+    ^ super flyByHelpSpec addPairsFrom:#(
+
+#debugSelected
+'Run the selected test(s) with debugging enabled'
+
+#runAll
+'Run all tests'
+
+#runFailed
+'Only rerun failed tests'
+
+#runSelected
+'Run the selected test(s)'
+
+#stopRun
+'Stop the test-run'
+
+)
+
+    "Created: / 04-06-2012 / 19:27:47 / cg"
+! !
+
 !TestRunnerEmbedded class methodsFor:'interface specs'!
 
 windowSpec
@@ -106,120 +143,127 @@
           label: 'Test Runner Embedded'
           name: 'Test Runner Embedded'
           min: (Point 10 10)
-          bounds: (Rectangle 0 0 350 50)
+          bounds: (Rectangle 0 0 595 50)
         )
         component: 
        (SpecCollection
           collection: (
-           (VerticalPanelViewSpec
-              name: 'Runners'
+           (ViewSpec
+              name: 'Runner'
               layout: (LayoutFrame 5 0 0 0 -5 1 0 1)
-              horizontalLayout: fit
-              verticalLayout: topSpaceFit
-              horizontalSpace: 0
-              verticalSpace: 5
-              elementsChangeSize: true
+              backgroundChannel: resultBackgroundColorAspect
               component: 
              (SpecCollection
                 collection: (
-                 (ViewSpec
-                    name: 'Runner'
+                 (HorizontalPanelViewSpec
+                    name: 'RunnerInnerBox'
+                    layout: (LayoutFrame 5 0 0 0 -5 1 0 1)
                     backgroundChannel: resultBackgroundColorAspect
+                    horizontalLayout: rightSpaceFit
+                    verticalLayout: center
+                    horizontalSpace: 0
+                    elementsChangeSize: true
                     component: 
                    (SpecCollection
                       collection: (
-                       (HorizontalPanelViewSpec
-                          name: 'RunnerInnerBox'
-                          layout: (LayoutFrame 5 0 0 0 -5 1 0 1)
-                          horizontalLayout: rightSpaceFit
-                          verticalLayout: center
-                          horizontalSpace: 0
-                          elementsChangeSize: true
+                       (ViewSpec
+                          name: 'RunnerInfoBox'
+                          backgroundChannel: resultBackgroundColorAspect
                           component: 
                          (SpecCollection
                             collection: (
+                             (LabelSpec
+                                label: 'Run tests first!!'
+                                name: 'ResultName'
+                                layout: (LayoutFrame 0 0 0 0 0 1 -10 1)
+                                backgroundChannel: resultBackgroundColorAspect
+                                foregroundColor: (Color 100.0 100.0 100.0)
+                                translateLabel: true
+                                labelChannel: resultNameAspect
+                                adjust: left
+                              )
+                             (LabelSpec
+                                name: 'ResultInfo'
+                                layout: (LayoutFrame 0 0 -10 1 0 1 0 1)
+                                style: (FontDescription helvetica medium roman 8 #'iso10646-1')
+                                backgroundChannel: resultBackgroundColorAspect
+                                foregroundColor: (Color 100.0 100.0 100.0)
+                                translateLabel: true
+                                labelChannel: resultInfoAspect
+                                adjust: left
+                              )
                              (ViewSpec
-                                name: 'RunnerInfoBox'
+                                name: 'ProgressPanel'
+                                layout: (LayoutFrame 0 0 0 0 0 1 0 1)
+                                visibilityChannel: progressIndicatorShownHolder
                                 backgroundChannel: resultBackgroundColorAspect
                                 component: 
                                (SpecCollection
                                   collection: (
-                                   (LabelSpec
-                                      label: 'Run tests first!!'
-                                      name: 'ResultName'
-                                      layout: (LayoutFrame 0 0 0 0 0 1 -10 1)
-                                      backgroundChannel: resultBackgroundColorAspect
-                                      foregroundColor: (Color 100.0 100.0 100.0)
-                                      translateLabel: true
-                                      labelChannel: resultNameAspect
-                                      adjust: left
-                                    )
-                                   (LabelSpec
-                                      name: 'ResultInfo'
-                                      layout: (LayoutFrame 0 0 -10 1 0 1 0 1)
-                                      style: (FontDescription helvetica medium roman 8)
-                                      backgroundChannel: resultBackgroundColorAspect
-                                      foregroundColor: (Color 100.0 100.0 100.0)
-                                      translateLabel: true
-                                      labelChannel: resultInfoAspect
-                                      adjust: left
-                                    )
-                                   (ViewSpec
-                                      name: 'ProgressPanel'
-                                      layout: (LayoutFrame 0 0 0 0 0 1 0 1)
-                                      visibilityChannel: runningHolder
-                                      backgroundChannel: resultBackgroundColorAspect
-                                      component: 
-                                     (SpecCollection
-                                        collection: (
-                                         (ProgressIndicatorSpec
-                                            name: 'RunningProgress'
-                                            layout: (LayoutFrame 5 0 -10 0.5 -5 1 10 0.5)
-                                            model: progressHolder
-                                          )
-                                         )
-                                       
-                                      )
+                                   (ProgressIndicatorSpec
+                                      name: 'RunningProgress'
+                                      layout: (LayoutFrame 5 0 -10 0.5 -5 1 10 0.5)
+                                      model: progressHolder
                                     )
                                    )
                                  
                                 )
-                                extent: (Point 151 30)
-                              )
-                             (ActionButtonSpec
-                                label: 'Debug'
-                                name: 'DebugButton'
-                                initiallyInvisible: true
-                                visibilityChannel: debugVisibleAspect
-                                translateLabel: true
-                                model: debug
-                                extent: (Point 60 25)
-                              )
-                             (ActionButtonSpec
-                                label: 'Run'
-                                name: 'Run'
-                                translateLabel: true
-                                model: run
-                                enableChannel: runEnabledHolder
-                                extent: (Point 60 25)
-                              )
-                             (ActionButtonSpec
-                                label: 'Run all'
-                                name: 'RunAll'
-                                translateLabel: true
-                                model: runAll
-                                enableChannel: runAllEnabledHolder
-                                extent: (Point 60 25)
                               )
                              )
                            
                           )
-                          postBuildCallback: postBuildRunnerPanel:
+                          extent: (Point 276 30)
+                        )
+                       (ActionButtonSpec
+                          label: 'Stop'
+                          name: 'Button2'
+                          activeHelpKey: stopRun
+                          visibilityChannel: runningHolder
+                          translateLabel: true
+                          model: stop
+                          extent: (Point 60 25)
+                        )
+                       (ActionButtonSpec
+                          label: 'Run'
+                          name: 'Run'
+                          activeHelpKey: runSelected
+                          visibilityChannel: notRunningHolder
+                          translateLabel: true
+                          model: run
+                          enableChannel: runEnabledHolder
+                          extent: (Point 60 25)
+                        )
+                       (ActionButtonSpec
+                          label: 'Debug'
+                          name: 'DebugButton'
+                          activeHelpKey: debugSelected
+                          translateLabel: true
+                          model: debug
+                          enableChannel: runEnabledHolder
+                          extent: (Point 60 25)
+                        )
+                       (ActionButtonSpec
+                          label: 'Run Failed'
+                          name: 'Button1'
+                          activeHelpKey: runFailed
+                          translateLabel: true
+                          model: runFailed
+                          enableChannel: runFailedEnabledHolder
+                          extent: (Point 60 25)
+                        )
+                       (ActionButtonSpec
+                          label: 'Run all'
+                          name: 'RunAll'
+                          activeHelpKey: runAll
+                          translateLabel: true
+                          model: runAll
+                          enableChannel: runAllEnabledHolder
+                          extent: (Point 60 25)
                         )
                        )
                      
                     )
-                    extent: (Point 340 40)
+                    postBuildCallback: postBuildRunnerPanel:
                   )
                  )
                
@@ -288,31 +332,36 @@
     generator := self methodGeneratorHolder value.
     selectedClass := self theSingleTestCase.
 
-    generator ifNotNil:
-            [ generator do:
-                    [:cls :cat :sel :mthd | 
-                    (mthd notNil 
-                        and:[ (self isTestCaseLike:(selectedClass ? cls)) and:[ (selectedClass ? cls) isTestSelector:sel ] ]) 
-                            ifTrue:[ methods add:mthd ] ] ]
-        ifNil:
-            [ selectedTestCases do:
-                    [:cls | 
-                    cls methodsDo:
-                            [:mthd | 
-                            ((protocols includes:mthd category) 
-                                and:[ cls isTestSelector:mthd selector ]) ifTrue:[ methods add:mthd ] ] ] ].
+    generator notNil ifTrue:[ 
+        generator do: [:cls :cat :sel :mthd | 
+            (mthd notNil 
+                and:[ (self isTestCaseLike:(selectedClass ? cls)) 
+                and:[ (selectedClass ? cls) isTestSelector:sel ] ]) 
+            ifTrue:[ methods add:mthd ] 
+        ] 
+    ] ifFalse:[
+        allTestCases do: [:cls | 
+            cls methodsDo: [:mthd | 
+                ((protocols includes:mthd category) and:[ cls isTestSelector:mthd selector ]) 
+                ifTrue:[ 
+                    methods add:mthd 
+                ] 
+            ] 
+        ] 
+    ].
     ^ methods
 
     "Created: / 15-03-2010 / 19:50:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 22-07-2011 / 15:53:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified (format): / 04-06-2012 / 19:05:32 / cg"
 !
 
 theSingleTestCase
 
-    selectedTestCases isEmptyOrNil ifTrue:[^nil].
-    selectedTestCases size > 1 ifTrue:[^nil].
+    allTestCases isEmptyOrNil ifTrue:[^nil].
+    allTestCases size > 1 ifTrue:[^nil].
 
-    ^selectedTestCases anyOne.
+    ^allTestCases anyOne.
 
     "Created: / 22-07-2011 / 15:44:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
@@ -324,23 +373,36 @@
 
     suiteAndResult := self resultHolder value.
     suite := suiteAndResult suiteForRun.
-    suite tests size ~= 1 ifTrue:[^self breakPoint: #jv].
-    test := suiteAndResult suite tests anyOne.
-    [
-        test debug.
-        (test class testSelectorPassed:test selector) ifTrue:[
-            result := TestResult new.
-            result passed add: test.
-            suiteAndResult := SuiteAndResult suite: suite result: result.       
-            self resultHolder value:suiteAndResult.    
-        ].            
-    ] fork
+    "/ suite tests size ~= 1 ifTrue:[^self breakPoint: #jv].
+    "/ test := suiteAndResult suite tests anyOne.
+
+    self stop.
+
+    testProcess :=
+        [
+            [
+                self runningHolder value:true.
+
+                suite tests do:[:test |
+                    test debug. 
+                    (test class testSelectorPassed:test selector) ifTrue:[
+                        result := TestResult new.
+                        result passed add: test.
+                        suiteAndResult := SuiteAndResult suite: suite result: result.       
+                        self resultHolder value:suiteAndResult.    
+                    ].
+                ].
+            ] ensure:[
+                self runningHolder value:false.
+            ].
+        ] newProcess.
+    testProcess priority:(Processor userBackgroundPriority).
+    testProcess resume.
 
     "Created: / 15-03-2010 / 15:43:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 05-07-2011 / 19:05:31 / cg"
     "Modified: / 07-07-2011 / 11:33:48 / Jan Vrany <jan.vrant@fit.cvut,cz>"
-    "Modified (format): / 02-08-2011 / 18:18:38 / cg"
     "Modified: / 22-08-2011 / 09:59:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 04-06-2012 / 19:46:38 / cg"
 !
 
 run
@@ -359,19 +421,22 @@
 !
 
 run:suite 
-    |process suiteAndResult numTests|
+    |suiteAndResult numTests|
 
     numTests := suite tests size.
     numTests == 0 ifTrue:[
         ^ self
     ].
 
-    process := [
+    self stop.
+
+    testProcess := [
                 |result incr run|
 
                 [
+                    self runningHolder value:true.
+                    self progressIndicatorShownHolder value:(numTests size > 1).
                     self progressHolder value:0.
-                    self runningHolder value:true.
                     incr := 100 / numTests.
                     run := 0.
                     result := suite 
@@ -391,23 +456,33 @@
                                 ].
                     suiteAndResult := SuiteAndResult suite:suite result:result.
                 ] ensure:[
+                    self progressIndicatorShownHolder value:false.
                     self resultHolder value:suiteAndResult.
                     self runningHolder value:false.
                 ]
             ] newProcess.
-    process resume.
+
+    testProcess priority:(Processor userBackgroundPriority).
+    testProcess resume.
 
     "Created: / 11-03-2010 / 10:22:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 06-09-2010 / 21:48:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 06-07-2011 / 14:28:02 / cg"
+    "Modified: / 04-06-2012 / 19:43:34 / cg"
 !
 
 runAll
 
-    self run: self suiteForRunAll.
+    self run: (self suiteForRunAll).
 
     "Created: / 10-03-2010 / 19:42:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 15-03-2010 / 13:12:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 04-06-2012 / 19:00:14 / cg"
+!
+
+runFailed
+    self run: self suiteForRunFailed.
+
+    "Created: / 04-06-2012 / 18:32:19 / cg"
 !
 
 runWithDebug
@@ -433,6 +508,17 @@
     "Created: / 05-07-2011 / 18:45:43 / cg"
     "Modified: / 22-08-2011 / 09:59:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 09-10-2011 / 10:55:46 / cg"
+!
+
+stop
+    |p|
+
+    (p := testProcess) notNil ifTrue:[
+        testProcess := nil.
+        p terminate
+    ].
+
+    "Created: / 04-06-2012 / 18:34:07 / cg"
 ! !
 
 !TestRunnerEmbedded methodsFor:'aspects'!
@@ -479,6 +565,12 @@
     ].
 !
 
+notRunningHolder
+    ^ BlockValue forLogicalNot:(self runningHolder)
+
+    "Created: / 04-06-2012 / 18:38:48 / cg"
+!
+
 progressHolder
     "return/create the 'progressHolder' value holder (automatically generated)"
 
@@ -488,6 +580,17 @@
     ^ progressHolder
 !
 
+progressIndicatorShownHolder
+    progressIndicatorShownHolder isNil ifTrue:[
+        progressIndicatorShownHolder := ValueHolder with: false.
+    ].
+    ^ progressIndicatorShownHolder
+
+    "Modified: / 15-03-2010 / 20:29:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified (comment): / 04-06-2012 / 18:38:52 / cg"
+    "Created: / 04-06-2012 / 19:42:59 / cg"
+!
+
 resultBackgroundColorAspect
     <resource: #uiAspect>
     resultBackgroundColorHolder isNil ifTrue:[
@@ -497,7 +600,7 @@
                             self class currentlyRunningColor "/ View defaultBackgroundColor
                         ] ifFalse:[
                             result ifNil:[ self class notRunColor ] ifNotNil:[ result color ]
-                        ]
+                        ].
                     ]
                     argument:self resultHolder
                     argument:self runningHolder.
@@ -511,7 +614,7 @@
 
     "Created: / 15-03-2010 / 15:22:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 15-03-2010 / 21:02:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified (comment): / 05-07-2011 / 14:13:30 / cg"
+    "Modified: / 04-06-2012 / 19:40:11 / cg"
 !
 
 resultHolder
@@ -544,31 +647,55 @@
 
 runAllEnabledHolder
 
-    ^true
+    ^ self notRunningHolder
 
     "Created: / 07-09-2010 / 09:15:10 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 04-06-2012 / 18:40:46 / cg"
 !
 
 runEnabledHolder
-
     ^BlockValue
         with:
-            [:resultHolder | | result | 
-            (result := resultHolder value) notNil and:[result testCount > 0 ]]
+            [:result :running | 
+
+            running not
+            and:[ result notNil 
+            and:[ result testCount > 0 ]]
+        ]
         argument: self resultHolder
+        argument: self runningHolder
 
     "Created: / 07-09-2010 / 09:15:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 04-06-2012 / 18:52:41 / cg"
+!
+
+runFailedEnabledHolder
+    ^BlockValue
+        with:
+            [:running | 
+
+            |result|
+
+            result := (self resultForSuite:self suiteForRunAll).
+            running not 
+            and:[ result notNil 
+            and:[ result hasFailuresOrErrors ]]
+        ]
+        "/ argument: self resultHolder
+        argument: self runningHolder
+
+    "Created: / 07-09-2010 / 09:15:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 04-06-2012 / 18:28:12 / cg"
 !
 
 runningHolder
-    "return/create the 'runningHolder' value holder (automatically generated)"
-
     runningHolder isNil ifTrue:[
         runningHolder := ValueHolder with: false.
     ].
     ^ runningHolder
 
     "Modified: / 15-03-2010 / 20:29:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified (comment): / 04-06-2012 / 18:38:52 / cg"
 !
 
 selectedClassesHolder
@@ -656,6 +783,12 @@
     oldValue ~~ newValue ifTrue:[
         self update:#value with:newValue from:selectedProtocolsHolder.
     ].
+!
+
+stopEnabledHolder
+    ^ self runningHolder
+
+    "Created: / 04-06-2012 / 18:29:01 / cg"
 ! !
 
 !TestRunnerEmbedded methodsFor:'change & update'!
@@ -686,7 +819,7 @@
 
     sender == Smalltalk ifTrue:[
         aspect == #lastTestRunResult ifTrue:[
-            (selectedTestCases notNil and:[selectedTestCases includesIdentical: param first]) ifTrue:[
+            (allTestCases includesIdentical: param first) ifTrue:[
                 self updateTestSuiteAndResult.
                 ^self        
             ]
@@ -698,24 +831,24 @@
     super update:aspect with:param from: sender
 
     "Modified: / 20-11-2011 / 12:40:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 04-06-2012 / 19:03:34 / cg"
 !
 
 updateTestCases
-    selectedTestCases := ((self selectedClassesHolder value ? #()) 
+    allTestCases := ((self selectedClassesHolder value ? #()) 
                 select:[:cls | self isTestCaseLike:cls ]).
-    selectedTestCases := selectedTestCases isEmpty 
-                ifTrue:[ nil ]
-                ifFalse:[ selectedTestCases asArray ]
+    allTestCases := allTestCases asArray
 
     "Created: / 11-03-2010 / 10:31:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 24-01-2012 / 22:09:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 04-06-2012 / 19:02:52 / cg"
 !
 
 updateTestSuiteAndResult
 
     | suite suiteAndResult |
     self runningHolder value ifTrue:[^self].
-    selectedTestCases ifNil:[^self].
+    allTestCases isEmptyOrNil ifTrue:[^self].
     suiteAndResult := SuiteAndResult
                         suite:  (suite := self suiteForRun)
                         result: (self resultForSuite: suite).
@@ -723,6 +856,7 @@
 
     "Created: / 15-03-2010 / 19:41:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 15-03-2010 / 20:55:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 04-06-2012 / 19:03:15 / cg"
 !
 
 updateVisibility
@@ -804,7 +938,7 @@
 
 hasTestCaseSelected
 
-    ^selectedTestCases notEmptyOrNil
+    ^allTestCases notEmptyOrNil
 
     "Created: / 11-03-2010 / 09:06:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 15-03-2010 / 20:54:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -874,13 +1008,39 @@
 
 suiteForRunAll
     |suite|
-    suite := TestSuite named:(self suiteNameFromClasses: selectedTestCases).
-    selectedTestCases do:[:testCase | 
+    suite := TestSuite named:(self suiteNameFromClasses: allTestCases).
+    allTestCases isNil ifTrue:[
+        self updateTestCases.
+    ].
+
+    allTestCases do:[:testCase | 
         suite addTests:(self buildSuiteFromClass:testCase) tests
     ].
     ^suite
 
     "Modified: / 04-03-2011 / 06:57:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 04-06-2012 / 19:01:48 / cg"
+!
+
+suiteForRunFailed
+    |suite|
+
+    suite := TestSuite named:(self suiteNameFromClasses: allTestCases).
+    allTestCases do:[:testCase |
+        (self buildSuiteFromClass:testCase) tests do:[:eachTest |
+            | sel cls |
+
+            sel := eachTest selector.
+            cls := eachTest class.
+            (cls testSelectorPassed:sel) ifFalse:[
+                suite addTest:eachTest
+            ]
+        ]
+    ].
+    ^suite
+
+    "Modified: / 04-03-2011 / 06:57:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 04-06-2012 / 18:32:40 / cg"
 ! !
 
 !TestRunnerEmbedded::SuiteAndResult class methodsFor:'instance creation'!
@@ -998,13 +1158,13 @@
 !TestRunnerEmbedded class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/Tools__TestRunnerEmbedded.st,v 1.22 2012/01/24 22:20:06 vrany Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/Tools__TestRunnerEmbedded.st,v 1.24 2012/06/04 18:12:25 cg Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libtool/Tools__TestRunnerEmbedded.st,v 1.22 2012/01/24 22:20:06 vrany Exp §'
+    ^ '§Header: /cvs/stx/stx/libtool/Tools__TestRunnerEmbedded.st,v 1.24 2012/06/04 18:12:25 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: Tools__TestRunnerEmbedded.st 7854 2012-01-30 17:49:41Z vranyj1 $'
+    ^ '$Id: Tools__TestRunnerEmbedded.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/Tools__VariableList.st	Wed May 30 21:46:55 2012 +0100
+++ b/Tools__VariableList.st	Tue Jun 05 15:49:00 2012 +0100
@@ -825,5 +825,5 @@
 !
 
 version_SVN
-    ^ '$Id: Tools__VariableList.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: Tools__VariableList.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/VersionDiffBrowser.st	Wed May 30 21:46:55 2012 +0100
+++ b/VersionDiffBrowser.st	Tue Jun 05 15:49:00 2012 +0100
@@ -1635,58 +1635,59 @@
      singleComparedClass singleComparedClassesName singleComparedMetaclassesName|
 
     (singleComparedClass := self classBeingCompared) notNil ifTrue:[
-	singleComparedClassesName := singleComparedClass name.
-	singleComparedMetaclassesName := singleComparedClass theMetaclass name.
+        singleComparedClassesName := singleComparedClass name.
+        singleComparedMetaclassesName := singleComparedClass theMetaclass name.
     ].
 
     aChange isClassDefinitionChange ifTrue:[
-	^ aChange printStringWithoutClassName
+        ^ aChange printStringWithoutClassName
     ].
     aChange isDoIt ifTrue:[
-	^ aChange source , ' (doIt)'
+        ^ aChange source , ' (doIt)'
     ].
     aChange isNameSpaceCreationChange ifTrue:[
-	^ aChange source
+        ^ aChange source
     ].
 
     changeClassName := aChange className.
     changeClassName isNil ifTrue:[
-	^ aChange source
+        ^ aChange source
     ].
     useChangesString := false.
 
     (changeClassName = singleComparedClassesName) ifTrue:[
-	changeClassName := ''.
-	useChangesString := true.
+        changeClassName := ''.
+        useChangesString := true.
     ] ifFalse:[
-	(changeClassName = singleComparedMetaclassesName) ifTrue:[
-	    changeClassName := 'class '.
-	    useChangesString := true.
-	] ifFalse:[
-	    ((changeClassName includes:$:) and:[ changeClassName startsWith:((singleComparedClassesName ? ''),'::') ]) ifTrue:[
-		changeClassName := changeClassName copyFrom:(singleComparedClassesName,'::') size+1.
-	    ].
-	].
+        (changeClassName = singleComparedMetaclassesName) ifTrue:[
+            changeClassName := 'class '.
+            useChangesString := true.
+        ] ifFalse:[
+            ((changeClassName includes:$:) and:[ changeClassName startsWith:((singleComparedClassesName ? ''),'::') ]) ifTrue:[
+                changeClassName := changeClassName copyFrom:(singleComparedClassesName,'::') size+1.
+            ].
+        ].
     ].
 
     selectorString := ''.
-    (aChange isMethodChange
-    and:[ aChange changeClass notNil ]) ifTrue:[
-	selectorString := aChange selector.
-	m := aChange changeMethod.
-	m notNil ifTrue:[
-	    m := m originalMethodIfWrapped.
-	    selectorString := m printStringForBrowserWithSelector:aChange selector inClass:aChange changeClass.
-	].
-	selectorString := ' ',selectorString
+    (aChange isMethodChange) ifTrue:[
+        selectorString := aChange selector.
+        aChange changeClass notNil ifTrue:[
+            m := aChange changeMethod.
+            m notNil ifTrue:[
+                m := m originalMethodIfWrapped.
+                selectorString := m printStringForBrowserWithSelector:aChange selector inClass:aChange changeClass.
+            ].
+        ].
+        selectorString := ' ',selectorString
     ].
 
     aChange isMethodCategoryChange ifTrue:[
-	^ changeClassName,selectorString, ' (category)'
+        ^ changeClassName,selectorString, ' (category)'
     ].
     ^ changeClassName,selectorString
 
-    "Modified: / 24-11-2011 / 12:11:02 / cg"
+    "Modified: / 01-06-2012 / 11:04:10 / cg"
 !
 
 resetSelectionHolders
@@ -2295,13 +2296,13 @@
 !VersionDiffBrowser class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/VersionDiffBrowser.st,v 1.104 2012/03/22 08:32:02 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/VersionDiffBrowser.st,v 1.105 2012/06/01 10:43:13 cg Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libtool/VersionDiffBrowser.st,v 1.104 2012/03/22 08:32:02 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libtool/VersionDiffBrowser.st,v 1.105 2012/06/01 10:43:13 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: VersionDiffBrowser.st 7978 2012-04-13 13:15:47Z vranyj1 $'
+    ^ '$Id: VersionDiffBrowser.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/WorkspaceApplication.st	Wed May 30 21:46:55 2012 +0100
+++ b/WorkspaceApplication.st	Tue Jun 05 15:49:00 2012 +0100
@@ -2522,6 +2522,31 @@
     Workspace clearDoItHistory
 !
 
+compareTextAgainst
+    |ws otherText thisText|
+
+    ws := self selectedWorkspace scrolledView.
+    ws isTextView ifFalse:[
+        ^ self 
+    ].
+
+    ws hasSelection ifTrue:[
+        thisText := ws selectionAsString.
+    ] ifFalse:[
+        thisText := ws contents asString.
+    ].
+
+    otherText := Dialog requestText:'Paste other text below:'.
+    otherText isEmptyOrNil ifTrue:[^ self ].
+
+    DiffTextView 
+        openOn: thisText label: 'Workspace' 
+        and: otherText label: 'Other Text' 
+        title: 'Comparing Workspace Contents'
+
+    "Created: / 04-05-2012 / 15:35:32 / cg"
+!
+
 doIt
     |ws|
 
@@ -3474,67 +3499,106 @@
 !
 
 filterText
-    |template filterBlock newList oldList answer nDeleted deletedLines|
+    |template filterBlock newList oldList answer nDeleted deletedLines
+     prevLine nextLine line|
 
     template :=
 '"/ general text filter;
 "/ the following block should evaluate to true for all lines
-"/ you want to keep - lines for which the block returns false will be removed.
+"/ you want to KEEP.
+"/ Lines for which the block returns false, will be removed.
 "/ Beginner warning: Smalltalk know-how is useful here.
 
-[:line |
+[:line :lineNr :previousLine :nextLine|
      "/ any condition on line.
      "/ Notice, that line might be a Text object (i.e. non-string),
-     "/ so you may want to use line string.
+     "/ so you may want to use ''line string''.
      "/ 
      "/ Useful queries on the line are:
      "/     - size                   the length of the line
      "/     - hasChangeOfEmphasis    any bold, italic etc.
      "/     - startsWith:someString
      "/     - endsWith:someString
-
-     "/ example filter (removes all empty lines)
+     "/     - includesString:someString
+     "/     - pattern match: 
+
+     "/ example filters
+     "/
+     "/ -------- removes all empty lines ---------------
      "/
      "/ line size > 0
 
-     "/ example filter (removes all lines which do not end with some suffix)
+     "/ -------- removes all lines which do not end with some suffix ----------
      "/
      "/ (line asLowercase endsWith:''foo'') not
 
+     "/ -------- removes duplicates ----------
+     "/
+     "/ (line = nextLine) not
+
      "/ dummy filter (keeps all lines)
      "/
      true
 ]
 '.
 
-    filterBlock := self askForFilterBlock:'Filter block:'
+    filterBlock := self askForFilterBlock:'Filter block (to remove lines):'
                         template:template
                         rememberIn:#LastFilterBlockString.
     filterBlock isNil ifTrue:[^ self].
 
     oldList := self selectedWorkspacesTextView list.
-    oldList := oldList collect:[:lineOrNil | lineOrNil ? ''].
-    newList := oldList select:filterBlock.
-    newList := newList collect:[:line | (line isString and:[line size == 0]) ifTrue:[nil] ifFalse:[line]].
-    nDeleted := oldList size - newList size.
+    newList := StringCollection new.
+    deletedLines := OrderedCollection new.
+
+    oldList notEmptyOrNil ifTrue:[
+        line := nil.
+        nextLine := oldList at: 1.
+        1 to: oldList size do:[:lineNr |
+            prevLine := line.
+            line := nextLine.
+            nextLine := oldList at: lineNr + 1 ifAbsent: nil.
+
+            (filterBlock 
+                value:(line ? '') 
+                value: lineNr 
+                value: (prevLine ? '')  
+                value: (nextLine ? '') 
+            ) ifTrue: [
+                newList add: line
+            ] ifFalse:[
+                deletedLines add: line.
+            ]
+        ].
+
+        newList := newList collect:[:line | (line isString and:[line size == 0]) ifTrue:[nil] ifFalse:[line]].
+    ].
+
+    nDeleted := deletedLines size.
     nDeleted == 0 ifTrue:[
         self information:'No lines were deleted.'.
         ^ self
     ].
 
-    answer := Dialog confirmWithCancel:(resources 
+    answer := OptionBox 
+                request:(resources 
                         string:'%1 lines remain (%2 deleted). Change text ?'
                         with:newList size
                         with:nDeleted)
-                labels:#( 'Cancel' 'No, Show Deleted' 'Yes').
+                buttonLabels:#( 'Cancel' 'No, Show Deleted' 'Yes, but Show Deleted' 'Yes')
+                values:#(nil false yesAndShow true)
+                default:true.
     answer isNil ifTrue:[^ self].
-    answer ifFalse:[
-        deletedLines := oldList reject:filterBlock.
+    (answer ~~ true) ifTrue:[
         TextBox openOn:(deletedLines asStringCollection) title:'Filtered lines'.
-        ^ self.
+        (answer == false) ifTrue:[
+            ^ self.
+        ].
     ].
 
     self selectedWorkspacesTextView list:newList.
+
+    "Modified: / 04-05-2012 / 16:03:32 / cg"
 !
 
 googleSpellingSuggestion
@@ -3968,13 +4032,13 @@
 !WorkspaceApplication class methodsFor:'documentation'!
 
 version
-    ^ '$Id: WorkspaceApplication.st 7995 2012-05-11 16:35:43Z vranyj1 $'
+    ^ '$Header: /cvs/stx/stx/libtool/WorkspaceApplication.st,v 1.220 2012/05/04 14:04:21 cg Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libtool/WorkspaceApplication.st,v 1.219 2012/04/26 12:15:48 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libtool/WorkspaceApplication.st,v 1.220 2012/05/04 14:04:21 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: WorkspaceApplication.st 7995 2012-05-11 16:35:43Z vranyj1 $'
+    ^ '$Id: WorkspaceApplication.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !
--- a/stx_libtool.st	Wed May 30 21:46:55 2012 +0100
+++ b/stx_libtool.st	Tue Jun 05 15:49:00 2012 +0100
@@ -11,7 +11,7 @@
 "
 "{ Package: 'stx:libtool' }"
 
-LibraryDefinition subclass:#stx_libtool
+LibraryDefinition subclass:#'stx_libtool'
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -42,8 +42,10 @@
 !
 
 extensionsVersion_CVS
-    ^ '$Header: /cvs/stx/stx/libtool/stx_libtool.st,v 1.81 2012/03/19 11:31:47 stefan Exp $'
-! !
+    ^ '$Header: /cvs/stx/stx/libtool/stx_libtool.st,v 1.82 2012/06/01 10:44:51 cg Exp $'
+!
+
+ !
 
 !stx_libtool class methodsFor:'description'!
 
@@ -350,7 +352,7 @@
         Diff3ExclusiveVisitor
         #'Tools::TextMergeInfo'
         FileBrowserV3
-        #'Tools::ChangeSetDiffInfo'
+        #'Tools::ChangeSetDiffInfo' PerforceSourceCodeManagerUtilities
     )
 !
 
@@ -542,13 +544,13 @@
 !stx_libtool class methodsFor:'documentation'!
 
 version
-    ^ '$Id: stx_libtool.st 7993 2012-05-10 23:18:29Z vranyj1 $'
+    ^ '$Header: /cvs/stx/stx/libtool/stx_libtool.st,v 1.82 2012/06/01 10:44:51 cg Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libtool/stx_libtool.st,v 1.81 2012/03/19 11:31:47 stefan Exp §'
+    ^ '§Header: /cvs/stx/stx/libtool/stx_libtool.st,v 1.82 2012/06/01 10:44:51 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: stx_libtool.st 7993 2012-05-10 23:18:29Z vranyj1 $'
+    ^ '$Id: stx_libtool.st 8007 2012-06-05 14:49:00Z vranyj1 $'
 ! !