ChangeSet.st
branchjv
changeset 3840 1ef5ad4e7c0b
parent 3838 474d8ec95b33
parent 3839 e16f2217fc74
child 3841 813b462d169a
--- a/ChangeSet.st	Wed Apr 01 10:37:40 2015 +0100
+++ b/ChangeSet.st	Wed Apr 08 12:24:39 2015 +0200
@@ -2,7 +2,7 @@
 
 "
  COPYRIGHT (c) 1993 by Claus Gittinger
-              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
@@ -103,7 +103,7 @@
 copyright
 "
  COPYRIGHT (c) 1993 by Claus Gittinger
-              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
@@ -119,7 +119,7 @@
     used in the changes management to keep track of changes
 
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 "
 ! !
 
@@ -127,7 +127,7 @@
 
 forExistingClass:aClass
     "build a changeSet for some given class, all of its private classes
-     and all extensions if any. 
+     and all extensions if any.
      I.e. a changeSet which represents the existing class in the image.
      That does of course not give deltas, but instead reflects the current
      state of the given class.
@@ -144,19 +144,19 @@
 
     "/ fetch the real package info...
     changeSet do:[:eachChange |
-        eachChange isMethodChange ifTrue:[
-            changeObject := eachChange changeMethod.
-            changeObject notNil ifTrue:[
-                eachChange package:changeObject package
-            ].
-        ] ifFalse:[
-            eachChange isClassChange ifTrue:[
-                changeObject := eachChange changeClass.
-                changeObject notNil ifTrue:[
-                    eachChange package:changeObject package
-                ].
-            ].
-        ].
+	eachChange isMethodChange ifTrue:[
+	    changeObject := eachChange changeMethod.
+	    changeObject notNil ifTrue:[
+		eachChange package:changeObject package
+	    ].
+	] ifFalse:[
+	    eachChange isClassChange ifTrue:[
+		changeObject := eachChange changeClass.
+		changeObject notNil ifTrue:[
+		    eachChange package:changeObject package
+		].
+	    ].
+	].
     ].
 
     ^ changeSet
@@ -178,7 +178,7 @@
 "/
 "/    "/ class methods first ...
 "/    aClass class methodDictionary keysAndValuesDo:[:sel :mthd |
-"/        changeSet addMethodChange:mthd in:aClass class. 
+"/        changeSet addMethodChange:mthd in:aClass class.
 "/    ].
 "/
 "/    "/ instance methods ...
@@ -210,19 +210,19 @@
      for example, when building patchLists, diffSets etc."
 
     ^ self
-        forExistingClass:aClass 
-        withExtensions:withExtensions
-        withLooseMethods:false
-        extensionsOnly:false
+	forExistingClass:aClass
+	withExtensions:withExtensions
+	withLooseMethods:false
+	extensionsOnly:false
 
     "
-     Object hasExtensions   
-     Object extensions size           
+     Object hasExtensions
+     Object extensions size
 
      (ChangeSet forExistingClass:Object) size
-     (ChangeSet forExistingClass:Object withExtensions:false) size  
-
-     (ChangeSet forExistingClass:stx_libbasic3 withExtensions:false)   
+     (ChangeSet forExistingClass:Object withExtensions:false) size
+
+     (ChangeSet forExistingClass:stx_libbasic3 withExtensions:false)
     "
 
     "Created: / 12-10-2006 / 18:13:02 / cg"
@@ -238,10 +238,10 @@
      for example, when building patchLists, diffSets etc."
 
     ^ self
-        forExistingClass:aClass 
-        withExtensions:withExtensions 
-        withLooseMethods:false
-        extensionsOnly:extensionsOnly
+	forExistingClass:aClass
+	withExtensions:withExtensions
+	withLooseMethods:false
+	extensionsOnly:extensionsOnly
 
     "
      ChangeSet forExistingClass:ChangeSet
@@ -266,19 +266,19 @@
      for example, when building patchLists, diffSets etc."
 
     ^ self
-        forExistingClass:aClass 
-        withExtensions:withExtensions 
-        withLooseMethods:withLooseMethods
-        extensionsOnly:false
+	forExistingClass:aClass
+	withExtensions:withExtensions
+	withLooseMethods:withLooseMethods
+	extensionsOnly:false
 
     "
-     Object hasExtensions   
-     Object extensions size           
+     Object hasExtensions
+     Object extensions size
 
      (ChangeSet forExistingClass:Object) size
-     (ChangeSet forExistingClass:Object withExtensions:false) size  
-
-     (ChangeSet forExistingClass:stx_libbasic3 withExtensions:false)   
+     (ChangeSet forExistingClass:Object withExtensions:false) size
+
+     (ChangeSet forExistingClass:stx_libbasic3 withExtensions:false)
     "
 
     "Created: / 12-10-2006 / 18:13:02 / cg"
@@ -299,42 +299,42 @@
     classPackage := aClass package.
 
     notInClassesPackage :=
-                [:change |
-                    change isMethodChange 
-                    and:[ change package ~= classPackage ]
-                ].
+		[:change |
+		    change isMethodChange
+		    and:[ change package ~= classPackage ]
+		].
 
     realExtensions :=
-                [:change |
-                    change isMethodChange 
-                    and:[ change package ~= classPackage 
-                    and:[ change package ~~ PackageId noProjectID ]]
-                ].
+		[:change |
+		    change isMethodChange
+		    and:[ change package ~= classPackage
+		    and:[ change package ~~ PackageId noProjectID ]]
+		].
 
     looseMethods :=
-                [:change |
-                    change isMethodChange 
-                    and:[change package == PackageId noProjectID ]
-                ].
+		[:change |
+		    change isMethodChange
+		    and:[change package == PackageId noProjectID ]
+		].
 
     extensionsOnly ifTrue:[
-        withLooseMethods ifTrue:[
-            ^ changeSet select:notInClassesPackage
-        ].
-
-        ^ changeSet select:realExtensions.
+	withLooseMethods ifTrue:[
+	    ^ changeSet select:notInClassesPackage
+	].
+
+	^ changeSet select:realExtensions.
     ].
 
     withExtensions ifFalse:[
-        withLooseMethods ifFalse:[
-            ^ changeSet reject:notInClassesPackage
-        ].
-
-        ^ changeSet reject:realExtensions.
+	withLooseMethods ifFalse:[
+	    ^ changeSet reject:notInClassesPackage
+	].
+
+	^ changeSet reject:realExtensions.
     ].
 
     withLooseMethods ifFalse:[
-        ^ changeSet reject:looseMethods.
+	^ changeSet reject:looseMethods.
     ].
 
     ^ changeSet
@@ -364,24 +364,24 @@
     |changeSet stream previousPackage|
 
     changeSet := self new.
-    aCollectionOfMethods do:[:eachMethod | 
-        |change source|
-
-        source := eachMethod source.
-        source isNil ifTrue:[
-            Transcript showCR:'oops - no source for ',eachMethod whoString.
-        ].
-        change := MethodDefinitionChange new.
-        eachMethod mclass notNil ifTrue:[ change className:eachMethod mclass name ].
-        source notNil ifTrue:[ change source:source ].
-        change selector:eachMethod selector.
-        change package:(eachMethod package).
-        change category:(eachMethod category).
-        changeSet add:change.
+    aCollectionOfMethods do:[:eachMethod |
+	|change source|
+
+	source := eachMethod source.
+	source isNil ifTrue:[
+	    Transcript showCR:'oops - no source for ',eachMethod whoString.
+	].
+	change := MethodDefinitionChange new.
+	eachMethod mclass notNil ifTrue:[ change className:eachMethod mclass name ].
+	source notNil ifTrue:[ change source:source ].
+	change selector:eachMethod selector.
+	change package:(eachMethod package).
+	change category:(eachMethod category).
+	changeSet add:change.
     ].
 
 "/    stream := ReadWriteStream on:''.
-"/    aCollectionOfMethods do:[:eachMethod | 
+"/    aCollectionOfMethods do:[:eachMethod |
 "/        previousPackage ~= eachMethod package ifTrue:[
 "/            stream nextPutAll:'"{ Package: '''.
 "/            stream nextPutAll:eachMethod package asString.
@@ -398,8 +398,8 @@
 
     "
      ChangeSet forExistingMethods:(Array with:(Array compiledMethodAt:#at:)
-                                         with:(Object compiledMethodAt:#at:)
-                                         with:(Behavior compiledMethodAt:#compiledMethodAt:) )
+					 with:(Object compiledMethodAt:#at:)
+					 with:(Behavior compiledMethodAt:#compiledMethodAt:) )
     "
 
     "Modified: / 17-09-2011 / 10:26:03 / cg"
@@ -424,10 +424,10 @@
     packageExtensions := packageExtensions select:[:each | each programmingLanguage isSmalltalk ].
     changeSet := self forExistingMethods: packageExtensions.
     packageClasses do:[:cls|
-        (ignoreAutoloaded not and:[cls isLoaded not]) ifTrue:[cls autoload].
-        cls isLoaded ifTrue: [
-            changeSet addAll: (self forExistingClass:cls withExtensions:false)
-        ]
+	(ignoreAutoloaded not and:[cls isLoaded not]) ifTrue:[cls autoload].
+	cls isLoaded ifTrue: [
+	    changeSet addAll: (self forExistingClass:cls withExtensions:false)
+	]
     ].
     changeSet name: 'Package ' , pkg.
     ^changeSet
@@ -449,21 +449,21 @@
     "build a changeSet from a Bee Smalltalk .bsc stream, containing chunks
      Pass each change to the conditionBlock and stop whenever that
      returns false. This allows skipping reamaining chunks, and speeding up
-     reading, if only parts need to be extracted 
+     reading, if only parts need to be extracted
      (for example: only documentation methods).
      Return the changeSet."
 
     |changeSet|
 
     changeSet := self new.
-    self 
-        changesFromStream:aStream 
-        for:changeSet 
-        reader:(BeeChangeFileReader new) 
-        do:[:aChange :lineNumberOrNil :posOrNil |
-            changeSet add:aChange.
-            (aConditionBlock value:aChange) ifFalse:[^ changeSet].
-        ].
+    self
+	changesFromStream:aStream
+	for:changeSet
+	reader:(BeeChangeFileReader new)
+	do:[:aChange :lineNumberOrNil :posOrNil |
+	    changeSet add:aChange.
+	    (aConditionBlock value:aChange) ifFalse:[^ changeSet].
+	].
 
     ^ changeSet
 
@@ -487,10 +487,10 @@
     changeSet addAll:((aDiffSet changed collect:[:eachPair | eachPair second]) reject:[:ch | ch isClassDefinitionChange]).
     "/ then, removed methods...
     aDiffSet onlyInReceiver do:[:each |
-        |ch|
-
-        ch := MethodRemoveChange className:(each className) selector:(each selector).
-        changeSet add:ch.
+	|ch|
+
+	ch := MethodRemoveChange className:(each className) selector:(each selector).
+	changeSet add:ch.
     ].
     ^ changeSet
 
@@ -498,7 +498,7 @@
 !
 
 fromDirectory: aStringOfFilename
-      "Read all .st files (non-recursively) from `aStringOrFilename` Return the resuling ChangeSet"        
+      "Read all .st files (non-recursively) from `aStringOrFilename` Return the resuling ChangeSet"
 
     ^ self fromDirectory: aStringOfFilename asSmalltalkXPackage: false.
 
@@ -507,7 +507,7 @@
 !
 
 fromDirectory: aStringOfFilename asSmalltalkXPackage: isSmalltalkXPackage
-    "Read all .st files (non-recursively) from `aStringOrFilename` 
+    "Read all .st files (non-recursively) from `aStringOrFilename`
      Return the resuling ChangeSet.
 
      If `isSmalltalkXPacklage` is true, then treat directory as Smalltalk/X
@@ -518,16 +518,16 @@
 
     directory := aStringOfFilename asFilename.
     (isSmalltalkXPackage and:[(abbrevFile := directory asFilename / 'abbrev.stc') exists]) ifTrue:[
-        | files |
-
-        files := OrderedCollection new.
-        files add:'extensions.st'.
-        (directory asFilename / 'abbrev.stc') readingFileDo:[:s |
-            Smalltalk withAbbreviationsFromStream: s do:[:className :abbrev :pkg  | files add: (abbrev , '.st')]
-        ].
-        filter := [:filename | files includes: filename baseName ]
+	| files |
+
+	files := OrderedCollection new.
+	files add:'extensions.st'.
+	(directory asFilename / 'abbrev.stc') readingFileDo:[:s |
+	    Smalltalk withAbbreviationsFromStream: s do:[:className :abbrev :pkg  | files add: (abbrev , '.st')]
+	].
+	filter := [:filename | files includes: filename baseName ]
     ] ifFalse:[
-        filter := [:filename | filename  suffix = 'st' ]
+	filter := [:filename | filename  suffix = 'st' ]
     ].
     ^ self fromDirectory: aStringOfFilename filter: filter
 
@@ -542,16 +542,16 @@
     | d cs files step |
 
     d := aStringOrFilename asFilename.
-    cs := self new.    
+    cs := self new.
     files := (d directoryContentsAsFilenames) select:filter.
     step :=  100 / files size.
     files withIndexDo: [:each :index |
-        ProgressNotification notify: 'Reading ', each baseName progress: (step * (index - 1)).
-        [
-            cs addAll: (self fromFileOrDirectory: each)
-        ] on: ProgressNotification do:[:ex |
-            ex proceed.
-        ].
+	ProgressNotification notify: 'Reading ', each baseName progress: (step * (index - 1)).
+	[
+	    cs addAll: (self fromFileOrDirectory: each)
+	] on: ProgressNotification do:[:ex |
+	    ex proceed.
+	].
     ].
     ProgressNotification notify: nil progress: 100.
     cs name: aStringOrFilename asFilename asAbsoluteFilename pathName.
@@ -559,7 +559,7 @@
 
 
     "
-        ChangeSet fromDirectory: (Smalltalk getPackageDirectoryForPackage:'stx:libbasic')
+	ChangeSet fromDirectory: (Smalltalk getPackageDirectoryForPackage:'stx:libbasic')
     "
 
     "Created: / 12-11-2013 / 15:24:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -576,20 +576,20 @@
     "build a changeSet from a stream, containing dolphin pac file chunks.
      Pass each change to the conditionBlock and stop whenever that
      returns false. This allows skipping reamaining chunks, and speeding up
-     reading, if only parts need to be extracted 
+     reading, if only parts need to be extracted
      (for example: only documentation methods)."
 
     |changeSet|
 
     changeSet := self new.
-    self 
-        changesFromStream:aStream 
-        for:changeSet 
-        reader:(DolphinPACFileReader new) 
-        do:[:aChange :lineNumberOrNil :posOrNil |
-            changeSet add:aChange.
-            (aConditionBlock value:aChange) ifFalse:[^ changeSet].
-        ].
+    self
+	changesFromStream:aStream
+	for:changeSet
+	reader:(DolphinPACFileReader new)
+	do:[:aChange :lineNumberOrNil :posOrNil |
+	    changeSet add:aChange.
+	    (aConditionBlock value:aChange) ifFalse:[^ changeSet].
+	].
 
     ^ changeSet
 !
@@ -603,43 +603,43 @@
 
     filename := filenameOrString asFilename.
 
-    filename suffix = 'bsc' ifTrue:[ 
-        filename readingFileDo:[:stream |  
-            changeSet := self fromBeeStream:stream.       
-        ].
-        changeSet name: filename baseName.
-        ^ changeSet      
+    filename suffix = 'bsc' ifTrue:[
+	filename readingFileDo:[:stream |
+	    changeSet := self fromBeeStream:stream.
+	].
+	changeSet name: filename baseName.
+	^ changeSet
     ].
 
     mime := MIMETypes mimeTypeForFilename:filename.
     mime isNil ifTrue:[
-        mime := filename mimeTypeOfContents.
-        mime isNil ifTrue:[
-            "/ self error:'unknown MIME type for file' mayProceed:true.
-
-            "/ assume chunk format
-            mime := 'text/plain'.
-        ].
+	mime := filename mimeTypeOfContents.
+	mime isNil ifTrue:[
+	    "/ self error:'unknown MIME type for file' mayProceed:true.
+
+	    "/ assume chunk format
+	    mime := 'text/plain'.
+	].
     ].
 
     [
-        stream := filename readStream.
-        mime = 'text/xml' ifTrue:[
-            changeSet := self fromXMLStream:stream.
-        ] ifFalse:[
-            mime = 'application/x-smalltalk-source-sif' ifTrue:[
-                changeSet := self fromSIFStream:stream.
-            ] ifFalse:[
-                mime = 'application/x-smalltalk-dolphin-package' ifTrue:[
-                    changeSet := self fromDolphinPACStream:stream.
-                ] ifFalse:[            
-                    stream := EncodedStream decodedStreamFor:stream.
-                    changeSet := self fromStream:stream.
-                ]
-            ]
-        ]
+	stream := filename readStream.
+	mime = 'text/xml' ifTrue:[
+	    changeSet := self fromXMLStream:stream.
+	] ifFalse:[
+	    mime = 'application/x-smalltalk-source-sif' ifTrue:[
+		changeSet := self fromSIFStream:stream.
+	    ] ifFalse:[
+		mime = 'application/x-smalltalk-dolphin-package' ifTrue:[
+		    changeSet := self fromDolphinPACStream:stream.
+		] ifFalse:[
+		    stream := EncodedStream decodedStreamFor:stream.
+		    changeSet := self fromStream:stream.
+		]
+	    ]
+	]
     ] ensure:[
-        stream notNil ifTrue:[stream close].
+	stream notNil ifTrue:[stream close].
     ].
     changeSet name: filename baseName.
     ^ changeSet
@@ -658,11 +658,11 @@
     | f |
 
     f := fileOrDirectory asFilename.
-    ^(f isDirectory 
-        ifTrue:[self fromDirectory: f]
-        ifFalse:[self fromFile: f])
-        name: f pathName;
-        yourself.
+    ^(f isDirectory
+	ifTrue:[self fromDirectory: f]
+	ifFalse:[self fromFile: f])
+	name: f pathName;
+	yourself.
 
     "
      ChangeSet fromFileOrDirectory: (Smalltalk getPackageDirectoryForPackage:'stx:libbasic')
@@ -684,21 +684,21 @@
      in smalltalk interchange format.
      Pass each change to the conditionBlock and stop whenever that
      returns false. This allows skipping reamaining chunks, and speeding up
-     reading, if only parts need to be extracted 
+     reading, if only parts need to be extracted
      (for example: only documentation methods).
      Return the changeSet."
 
     |changeSet|
 
     changeSet := self new.
-    self 
-        changesFromStream:aStream 
-        for:changeSet 
-        reader:(SIFChangeFileReader new) 
-        do:[:aChange :lineNumberOrNil :posOrNil |
-            changeSet add:aChange.
-            (aConditionBlock value:aChange) ifFalse:[^ changeSet].
-        ].
+    self
+	changesFromStream:aStream
+	for:changeSet
+	reader:(SIFChangeFileReader new)
+	do:[:aChange :lineNumberOrNil :posOrNil |
+	    changeSet add:aChange.
+	    (aConditionBlock value:aChange) ifFalse:[^ changeSet].
+	].
 
     ^ changeSet
 !
@@ -725,21 +725,21 @@
      (i.e. either a classes sourceFile or a change-file).
      Pass each change to the conditionBlock and stop whenever that
      returns false. This allows skipping reamaining chunks, and speeding up
-     reading, if only parts need to be extracted 
+     reading, if only parts need to be extracted
      (for example: only documentation methods).
      Return the changeSet."
 
     |changeSet|
 
     changeSet := self new.
-    self 
-        changesFromStream:aStream 
-        for:changeSet 
-        reader:(ChangeFileReader new)
-        do:[:aChange :lineNumberOrNil :posOrNil |
-            changeSet add:aChange.
-            (aConditionBlock value:aChange) ifFalse:[^ changeSet].
-        ].
+    self
+	changesFromStream:aStream
+	for:changeSet
+	reader:(ChangeFileReader new)
+	do:[:aChange :lineNumberOrNil :posOrNil |
+	    changeSet add:aChange.
+	    (aConditionBlock value:aChange) ifFalse:[^ changeSet].
+	].
 
     ^ changeSet
 
@@ -772,8 +772,8 @@
 
     "
      ChangeSet fromXMLStream:('../../goodies/xml/vw/xmlFileInTests/XMLParser.xml' asFilename readStream)
-     ChangeSetBrowser 
-        openOn:(ChangeSet fromXMLStream:('../../goodies/xml/vw/xmlFileInTests/XMLParser.xml' asFilename readStream))
+     ChangeSetBrowser
+	openOn:(ChangeSet fromXMLStream:('../../goodies/xml/vw/xmlFileInTests/XMLParser.xml' asFilename readStream))
     "
 ! !
 
@@ -789,16 +789,16 @@
 
 component: component definition: anObject change: changeSymbol
     "Include indication that a class/namespace was added or removed
-     from a CodeComponent." 
-
-    self 
-        changed:#'component:definition:change:'
-        with:
-            ( Array 
-                    with: component
-                    with: anObject
-                    with: changeSymbol
-            )
+     from a CodeComponent."
+
+    self
+	changed:#'component:definition:change:'
+	with:
+	    ( Array
+		    with: component
+		    with: anObject
+		    with: changeSymbol
+	    )
 
 ! !
 
@@ -806,20 +806,20 @@
 
 changesFromStream:aStream do:aBlock
     "enumerate changes from a stream and invoke aBlock on each.
-     The block is invoked with the change, a lineNumberOrNil and streamPosition arguments. 
-     The lineNumber is only valid, if the underlying stream 
+     The block is invoked with the change, a lineNumberOrNil and streamPosition arguments.
+     The lineNumber is only valid, if the underlying stream
      provides line-numbers; otherwise, nil is passed."
 
     ^ self
-        changesFromStream:aStream 
-        for:(self new) 
-        reader:nil
-        do:aBlock
+	changesFromStream:aStream
+	for:(self new)
+	reader:nil
+	do:aBlock
 
     "
-     ChangeSet 
-        changesFromStream:('changes' asFilename readStream) 
-        do:[:chg | Transcript showCR:chg]
+     ChangeSet
+	changesFromStream:('changes' asFilename readStream)
+	do:[:chg | Transcript showCR:chg]
     "
 
     "Created: / 16.2.1998 / 12:19:34 / cg"
@@ -828,8 +828,8 @@
 
 changesFromStream:aStream for:aChangeSet reader:aReader do:aBlock
     "enumerate changes from a stream and invoke aBlock on each.
-     The block is invoked with the change, a lineNumberOrNil and streamPosition arguments. 
-     The lineNumber is only valid, if the underlying stream 
+     The block is invoked with the change, a lineNumberOrNil and streamPosition arguments.
+     The lineNumber is only valid, if the underlying stream
      provides line-numbers; otherwise, nil is passed."
 
     |encodedStream chunk s change currentNameSpace currentPackage
@@ -841,21 +841,23 @@
     currentPackage := Class packageQuerySignal query.
 
     (reader := aReader) isNil ifTrue:[
-        reader := ChangeFileReader new.
+	reader := ChangeFileReader new.
     ].
 
     aStream isEncodedStream ifTrue:[
-        encodedStream := aStream 
-    ] ifFalse:[ 
-        aStream isPositionable ifTrue:[ 
-            encodedStream := EncodedStream decodedStreamFor: aStream
-        ] ifFalse:[ 
-            encodedStream := EncodedStream stream: aStream encoder: CharacterEncoder nullEncoderInstance
-        ].
+	encodedStream := aStream
+    ] ifFalse:[
+	aStream isPositionable ifTrue:[
+	    encodedStream := EncodedStream decodedStreamFor: aStream
+	] ifFalse:[
+	    encodedStream := EncodedStream stream: aStream encoder: CharacterEncoder nullEncoderInstance
+	].
     ].
-    reportProgress := encodedStream stream isPositionable and:[ ProgressNotification isHandled ].
+    reportProgress := encodedStream stream isPositionable
+			and:[ ProgressNotification notNil
+			and:[ ProgressNotification isHandled ]].
     reportProgress ifTrue:[
-        size := encodedStream stream size.
+	size := encodedStream stream size.
     ].
 
     reader changeSet:aChangeSet.
@@ -863,99 +865,99 @@
     reader inputStream:encodedStream.
 
     [encodedStream atEnd] whileFalse:[
-        encodedStream skipSeparators.
-        lineNumber := encodedStream lineNumber.
-
-
-        reportProgress ifTrue:[
-            pos := encodedStream position + 1.
-            ProgressNotification notify: nil progress:(100 / size) * pos.
-        ].
-
-        chunk := encodedStream nextChunk.
-
-        (chunk notEmptyOrNil) ifTrue:[
-            Class nameSpaceQuerySignal handle:[:ex| ex proceedWith:currentNameSpace] do:[
-                Class packageQuerySignal handle:[:ex| ex proceedWith:currentPackage] do:[
-                    |parser tree ns pkg|
-
-                    parser := Parser for:chunk.
-                    "/ parser parseForCode.
-                    Parser parseErrorSignal handle:[:ex |
-                        Transcript showCR:'ChangeSet: error while reading: ',ex description.
-                        tree := #Error.
-                    ] do:[
-                        tree := parser 
-                                parseExpressionWithSelf:nil 
-                                notifying:nil 
-                                ignoreErrors:true 
-                                ignoreWarnings:true 
-                                inNameSpace:currentNameSpace.
-                    ].
-                    tree ~~ #Error ifTrue:[
-                        tree isNil ifTrue:[
-                            "/ Hmm....it could be package-definition chunk in extensions container...
-                            "/ if there is any package directive in there, extract it.
-                            ((pkg := parser currentPackage) notNil 
-                            and:[pkg ~~ currentPackage]) ifTrue:[
-                                currentPackage := pkg
-                            ] ifFalse:[
-                                "/ if there is any nameSpace directive in there, extract it.
-                                ((ns := parser currentNameSpace) notNil 
-                                and:[ns ~~ currentNameSpace]) ifTrue:[
-                                    currentNameSpace := ns
-                                ] ifFalse:[
-                                    change := DoItChange new.
-                                    change source:chunk.
-                                    aBlock valueWithOptionalArgument:change and:lineNumber and:pos.
-                                ].
-                            ].
-                        ] ifFalse:[    
-                            "/ if there is any nameSpace directive in there, extract it.
-                            ((ns := parser currentNameSpace) notNil 
-                            and:[ns ~~ currentNameSpace]) ifTrue:[
-                                currentNameSpace := ns
-                            ].
-                            "/ if there is any package directive in there, extract it.
-                            ((pkg := parser currentPackage) notNil 
-                            and:[pkg ~~ currentPackage]) ifTrue:[
-                                currentPackage := pkg
-                            ].
-                            "/
-                            "/ what type of chunk is this ...
-                            "/
-                            tree isConstant ifTrue:[
-                                (s := tree evaluate) isString ifTrue:[
-                                    (s startsWith:'---- ') ifTrue:[
-                                        reader inputStream: s readStream.
-                                        reader processInfo: s.
-                                        reader inputStream: encodedStream.
-                                    ].
-                                ] ifFalse:[
-                                    self error:'unexpected change-chunk' mayProceed:true
-                                ]
-                            ] ifFalse:[
-                                tree isMessage ifTrue:[
-                                    (reader 
-                                        changesFromParseTree:tree 
-                                        lineNumber:lineNumber
-                                        position:pos
-                                        chunk: chunk
-                                    ) ifFalse:[
-                                        change := DoItChange new.
-                                        change source:chunk.
-                                        aBlock valueWithOptionalArgument:change and:lineNumber and:pos.
-                                    ]
-                                ] ifFalse:[
-                                    InvalidChangeChunkError 
-                                        raiseRequestErrorString:('unexpected change-chunk i nor around line %1' bindWith:lineNumber) 
-                                ]
-                            ]
-                        ]
-                    ]
-                ]
-            ]
-        ]
+	encodedStream skipSeparators.
+	lineNumber := encodedStream lineNumber.
+
+
+	reportProgress ifTrue:[
+	    pos := encodedStream position + 1.
+	    ProgressNotification notify: nil progress:(100 / size) * pos.
+	].
+
+	chunk := encodedStream nextChunk.
+
+	(chunk notEmptyOrNil) ifTrue:[
+	    Class nameSpaceQuerySignal handle:[:ex| ex proceedWith:currentNameSpace] do:[
+		Class packageQuerySignal handle:[:ex| ex proceedWith:currentPackage] do:[
+		    |parser tree ns pkg|
+
+		    parser := Parser for:chunk.
+		    "/ parser parseForCode.
+		    Parser parseErrorSignal handle:[:ex |
+			Transcript showCR:'ChangeSet: error while reading: ',ex description.
+			tree := #Error.
+		    ] do:[
+			tree := parser
+				parseExpressionWithSelf:nil
+				notifying:nil
+				ignoreErrors:true
+				ignoreWarnings:true
+				inNameSpace:currentNameSpace.
+		    ].
+		    tree ~~ #Error ifTrue:[
+			tree isNil ifTrue:[
+			    "/ Hmm....it could be package-definition chunk in extensions container...
+			    "/ if there is any package directive in there, extract it.
+			    ((pkg := parser currentPackage) notNil
+			    and:[pkg ~~ currentPackage]) ifTrue:[
+				currentPackage := pkg
+			    ] ifFalse:[
+				"/ if there is any nameSpace directive in there, extract it.
+				((ns := parser currentNameSpace) notNil
+				and:[ns ~~ currentNameSpace]) ifTrue:[
+				    currentNameSpace := ns
+				] ifFalse:[
+				    change := DoItChange new.
+				    change source:chunk.
+				    aBlock valueWithOptionalArgument:change and:lineNumber and:pos.
+				].
+			    ].
+			] ifFalse:[
+			    "/ if there is any nameSpace directive in there, extract it.
+			    ((ns := parser currentNameSpace) notNil
+			    and:[ns ~~ currentNameSpace]) ifTrue:[
+				currentNameSpace := ns
+			    ].
+			    "/ if there is any package directive in there, extract it.
+			    ((pkg := parser currentPackage) notNil
+			    and:[pkg ~~ currentPackage]) ifTrue:[
+				currentPackage := pkg
+			    ].
+			    "/
+			    "/ what type of chunk is this ...
+			    "/
+			    tree isConstant ifTrue:[
+				(s := tree evaluate) isString ifTrue:[
+				    (s startsWith:'---- ') ifTrue:[
+					reader inputStream: s readStream.
+					reader processInfo: s.
+					reader inputStream: encodedStream.
+				    ].
+				] ifFalse:[
+				    self error:'unexpected change-chunk' mayProceed:true
+				]
+			    ] ifFalse:[
+				tree isMessage ifTrue:[
+				    (reader
+					changesFromParseTree:tree
+					lineNumber:lineNumber
+					position:pos
+					chunk: chunk
+				    ) ifFalse:[
+					change := DoItChange new.
+					change source:chunk.
+					aBlock valueWithOptionalArgument:change and:lineNumber and:pos.
+				    ]
+				] ifFalse:[
+				    InvalidChangeChunkError
+					raiseRequestErrorString:('unexpected change-chunk i nor around line %1' bindWith:lineNumber)
+				]
+			    ]
+			]
+		    ]
+		]
+	    ]
+	]
     ].
 
     "
@@ -977,12 +979,12 @@
     |p|
 
     (Project notNil and:[(p := Project current) notNil]) ifTrue:[
-        ^ p changeSet
+	^ p changeSet
     ].
     ^ #()
 
     "
-     ChangeSet current 
+     ChangeSet current
     "
 ! !
 
@@ -1015,25 +1017,25 @@
     |selectors|
 
     changeSelectors isNil ifTrue:[
-        selectors := IdentitySet new.
-        self do:[:chg |
-            |sel|
-
-            chg notNil ifTrue:[
-                chg isMethodChange ifTrue:[
-                    sel := chg selector.
-                    sel notNil ifTrue:[
-                        selectors add:sel
-                    ]
-                ]
-            ]
-        ].
-        changeSelectors := selectors.
+	selectors := IdentitySet new.
+	self do:[:chg |
+	    |sel|
+
+	    chg notNil ifTrue:[
+		chg isMethodChange ifTrue:[
+		    sel := chg selector.
+		    sel notNil ifTrue:[
+			selectors add:sel
+		    ]
+		]
+	    ]
+	].
+	changeSelectors := selectors.
     ].
     ^ changeSelectors.
 
     "
-     ChangeSet current changeSelectors  
+     ChangeSet current changeSelectors
     "
 
     "Modified: / 30-05-2007 / 12:12:32 / cg"
@@ -1045,25 +1047,25 @@
     |classes|
 
     changedClasses isNil ifTrue:[
-        classes := IdentitySet new.
-        self do:[:chg |
-            |cls|
-
-            chg notNil ifTrue:[
-                cls := chg changeClass.
-                cls notNil ifTrue:[
-                    cls isRealNameSpace ifFalse:[
-                        classes add:cls
-                    ]
-                ]
-            ]
-        ].
-        changedClasses := classes.
+	classes := IdentitySet new.
+	self do:[:chg |
+	    |cls|
+
+	    chg notNil ifTrue:[
+		cls := chg changeClass.
+		cls notNil ifTrue:[
+		    cls isRealNameSpace ifFalse:[
+			classes add:cls
+		    ]
+		]
+	    ]
+	].
+	changedClasses := classes.
     ].
     ^ changedClasses.
 
     "
-     ChangeSet current changedClasses  
+     ChangeSet current changedClasses
      ChangeSet current flushChangedClassesCache
     "
 
@@ -1072,16 +1074,16 @@
 
 component:component definition:anObject change:changeSymbol
     "Include indication that a class/namespace was added or removed
-     from a CodeComponent." 
-
-    self 
-        changed:#'component:definition:change:'
-        with:
-            ( Array 
-                    with: component
-                    with: anObject
-                    with: changeSymbol
-            )
+     from a CodeComponent."
+
+    self
+	changed:#'component:definition:change:'
+	with:
+	    ( Array
+		    with: component
+		    with: anObject
+		    with: changeSymbol
+	    )
 !
 
 reorganizeSystem
@@ -1104,12 +1106,12 @@
 
 !ChangeSet methodsFor:'change & update'!
 
-changed:anAspectSymbol with:aParameter 
-    "Allow objects to depend on the ChangeSet class instead of a particular instance 
+changed:anAspectSymbol with:aParameter
+    "Allow objects to depend on the ChangeSet class instead of a particular instance
      of ChangeSet (which may be switched using projects)."
 
     self == ChangeSet current ifTrue:[
-        ChangeSet changed:anAspectSymbol with:aParameter.
+	ChangeSet changed:anAspectSymbol with:aParameter.
     ].
     super changed:anAspectSymbol with:aParameter
 ! !
@@ -1146,7 +1148,7 @@
     "Modified: / 12-10-2006 / 18:17:02 / cg"
 !
 
-addClassRemoveChange:oldClass 
+addClassRemoveChange:oldClass
     "add a classRemove change to the receiver"
 
     |newChange|
@@ -1154,13 +1156,13 @@
     newChange := ClassRemoveChange new className:oldClass name.
     self rememberChangedClass:oldClass.
     oldClass isPrivate ifTrue:[
-        self rememberChangedClass:oldClass topOwningClass.
+	self rememberChangedClass:oldClass topOwningClass.
     ].
-    ClassRemoveChange::ClassBeingRemovedQuery 
-        answer:oldClass
-        do:[
-            self addChange:newChange
-        ]
+    ClassRemoveChange::ClassBeingRemovedQuery
+	answer:oldClass
+	do:[
+	    self addChange:newChange
+	]
     "Modified: / 14.11.2001 / 13:35:39 / cg"
 !
 
@@ -1192,9 +1194,9 @@
 
     |newChange|
 
-    newChange := ClassInstVarDefinitionChange 
-                        class:aClass
-                        source:(aClass name , ' instanceVariableNames:' , aClass instanceVariableString storeString).
+    newChange := ClassInstVarDefinitionChange
+			class:aClass
+			source:(aClass name , ' instanceVariableNames:' , aClass instanceVariableString storeString).
     newChange classInstVarNames:aClass instanceVariableString asCollectionOfWords.
     self rememberChangedClass:aClass.
     self addChange:newChange
@@ -1207,10 +1209,10 @@
 
     |newChange|
 
-    newChange := MethodCategoryChange 
-                        class:aClass
-                        selector:(aClass selectorAtMethod:aMethod)
-                        category:newCategory.
+    newChange := MethodCategoryChange
+			class:aClass
+			selector:(aClass selectorAtMethod:aMethod)
+			category:newCategory.
     self rememberChangedClass:aClass.
     self addChange:newChange
 
@@ -1222,13 +1224,13 @@
 
     |newChange|
 
-    newChange := MethodDefinitionChange 
-                        class:aClass
-                        selector:aMethod selector
-                        source:aMethod source
-                        category:aMethod category.
+    newChange := MethodDefinitionChange
+			class:aClass
+			selector:aMethod selector
+			source:aMethod source
+			category:aMethod category.
     oldMethod notNil ifTrue:[
-        newChange previousVersion:oldMethod.
+	newChange previousVersion:oldMethod.
     ].
     self rememberChangedClass:aClass.
     self addChange:newChange.
@@ -1241,11 +1243,11 @@
 
     |newChange|
 
-    newChange := MethodDefinitionChange 
-                        class:aClass
-                        selector:aMethod selector
-                        source:aMethod source
-                        category:aMethod category.
+    newChange := MethodDefinitionChange
+			class:aClass
+			selector:aMethod selector
+			source:aMethod source
+			category:aMethod category.
     newChange package:(aMethod package).
     self rememberChangedClass:aClass.
     self addChange:newChange
@@ -1261,10 +1263,10 @@
     selector := (aClass selectorAtMethod:aMethod).
     selector isNil ifTrue:[^ self].
 
-    newChange := MethodPackageChange 
-                        class:aClass
-                        selector:selector
-                        package:newPackage.
+    newChange := MethodPackageChange
+			class:aClass
+			selector:selector
+			package:newPackage.
     self rememberChangedClass:aClass.
     self addChange:newChange
 
@@ -1276,10 +1278,10 @@
 
     |newChange|
 
-    newChange := MethodPrivacyChange 
-                        class:aClass
-                        selector:(aClass selectorAtMethod:aMethod)
-                        privacy:aMethod privacy.
+    newChange := MethodPrivacyChange
+			class:aClass
+			selector:(aClass selectorAtMethod:aMethod)
+			privacy:aMethod privacy.
     self rememberChangedClass:aClass.
     self addChange:newChange
 
@@ -1293,7 +1295,7 @@
     |newChange|
 
     newChange := ClassPrimitiveDefinitionsChange new
-                        class:aClass source:(aClass primitiveDefinitionsString).
+			class:aClass source:(aClass primitiveDefinitionsString).
     self rememberChangedClass:aClass.
     self addChange:newChange
 
@@ -1306,7 +1308,7 @@
     |newChange|
 
     newChange := ClassPrimitiveFunctionsChange new
-                        class:aClass source:(aClass primitiveFunctionsString).
+			class:aClass source:(aClass primitiveFunctionsString).
     self rememberChangedClass:aClass.
     self addChange:newChange
 
@@ -1319,7 +1321,7 @@
     |newChange|
 
     newChange := ClassPrimitiveVariablesChange new
-                         class:aClass source:(aClass primitiveVariablesString).
+			 class:aClass source:(aClass primitiveVariablesString).
     self rememberChangedClass:aClass.
     self addChange:newChange
 
@@ -1333,7 +1335,7 @@
 
     newChange := MethodRemoveChange class:aClass selector:aSelector.
     oldMethod notNil ifTrue:[
-        newChange previousVersion:oldMethod.
+	newChange previousVersion:oldMethod.
     ].
     self rememberChangedClass:aClass.
     self addChange:newChange
@@ -1368,19 +1370,19 @@
 
 !ChangeSet methodsFor:'fileIn / fileOut'!
 
-fileInFrom:aStream 
+fileInFrom:aStream
     self fileInFrom:aStream while:[:change | true]
 !
 
 fileInFrom:aStream while:aConditionBlock
     self class
-        changesFromStream:aStream 
-        for:self 
-        reader:(ChangeFileReader new)
-        do:[:aChange :lineNumberOrNil :posOrNil |
-            self add:aChange.
-            (aConditionBlock value:aChange) ifFalse:[^ self].
-        ].
+	changesFromStream:aStream
+	for:self
+	reader:(ChangeFileReader new)
+	do:[:aChange :lineNumberOrNil :posOrNil |
+	    self add:aChange.
+	    (aConditionBlock value:aChange) ifFalse:[^ self].
+	].
 !
 
 fileOutAs: aStringOrFilename
@@ -1388,7 +1390,7 @@
     | stream |
     stream := aStringOrFilename asFilename writeStream.
     [ self fileOutOn: stream ]
-        ensure: [stream close]
+	ensure: [stream close]
 
     "Created: / 05-12-2009 / 12:33:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -1416,22 +1418,22 @@
     |changeClass|
 
     aChange timeOfChangeIfKnown isNil ifTrue:[
-        aChange timeStamp:(Timestamp now).
+	aChange timeStamp:(Timestamp now).
     ].
 
     self add:aChange.
     changedClasses notNil ifTrue:[
-        (changeClass := aChange changeClass) notNil ifTrue:[      
-            changedClasses add:changeClass.
-        ].
+	(changeClass := aChange changeClass) notNil ifTrue:[
+	    changedClasses add:changeClass.
+	].
     ].
     changeSelectors notNil ifTrue:[
-        aChange isMethodChange ifTrue:[
-            changeSelectors add:aChange selector.
-        ].
+	aChange isMethodChange ifTrue:[
+	    changeSelectors add:aChange selector.
+	].
     ].
 
-"/    aChange sendChangeNotificationThroughSmalltalk. 
+"/    aChange sendChangeNotificationThroughSmalltalk.
     self changed:#addChange: with:aChange.
 
     "Created: / 14-11-2001 / 13:35:11 / cg"
@@ -1448,15 +1450,15 @@
 
 rememberChangedClass:aClass
     changedClasses notNil ifTrue:[
-        changedClasses add:aClass
+	changedClasses add:aClass
     ].
 !
 
 removeAll:aCollection
     aCollection notEmpty ifTrue:[
-        super removeAll:aCollection.
-        changedClasses := changeSelectors := nil.
-        self changed:#removeAll: with:aCollection.
+	super removeAll:aCollection.
+	changedClasses := changeSelectors := nil.
+	self changed:#removeAll: with:aCollection.
     ]
 !
 
@@ -1474,32 +1476,32 @@
     changedPackages := Set new.
 
     self do:[:chg |
-        |p mthd cls|
-
-        p := chg package.
-        p isNil ifTrue:[
-            chg isMethodChange ifTrue:[
-                mthd := chg changeMethod.
-                mthd notNil ifTrue:[
-                    p := mthd package.
-                ] ifFalse:[
-                    cls := chg changeClass.
-                    cls notNil ifTrue:[
-                        p := cls package.
-                    ]
-                ]
-            ] ifFalse:[
-                chg isClassChange ifTrue:[
-                    cls := chg changeClass.
-                    cls notNil ifTrue:[
-                        p := cls package.
-                    ]
-                ]
-            ].
-        ].
-        p notNil ifTrue:[
-            changedPackages add:p.
-        ]
+	|p mthd cls|
+
+	p := chg package.
+	p isNil ifTrue:[
+	    chg isMethodChange ifTrue:[
+		mthd := chg changeMethod.
+		mthd notNil ifTrue:[
+		    p := mthd package.
+		] ifFalse:[
+		    cls := chg changeClass.
+		    cls notNil ifTrue:[
+			p := cls package.
+		    ]
+		]
+	    ] ifFalse:[
+		chg isClassChange ifTrue:[
+		    cls := chg changeClass.
+		    cls notNil ifTrue:[
+			p := cls package.
+		    ]
+		]
+	    ].
+	].
+	p notNil ifTrue:[
+	    changedPackages add:p.
+	]
     ].
 
 "/    self changedClasses do:[:cls |
@@ -1512,7 +1514,7 @@
     ^ changedPackages.
 
     "
-     ChangeSet current changedPackages  
+     ChangeSet current changedPackages
     "
 
     "Created: / 22-09-2006 / 16:37:40 / cg"
@@ -1521,29 +1523,29 @@
 
 changesForPackage:aPackageSymbol
     ^(self select:[:aChange |
-        |includeThis mClass mthd|
-
-        includeThis := false.
-        (aChange isMethodChange or:[aChange isMethodRemoveChange]) ifTrue:[
-            mClass := aChange changeClass.
-            mClass notNil ifTrue:[
-                mthd := mClass compiledMethodAt:(aChange selector).
-                mthd isNil ifTrue:[
-                    aChange isMethodRemoveChange ifTrue:[
-                        includeThis := (mClass package = aPackageSymbol)
-                    ].
-                ] ifFalse:[
-                    includeThis := (mthd package = aPackageSymbol)
-                ]
-            ].
-        ] ifFalse:[
-            (aChange isClassChange) ifTrue:[
-                (aChange changeClass notNil) ifTrue:[
-                    includeThis := (aChange changeClass package = aPackageSymbol)
-                ].
-            ].
-        ].
-        includeThis
+	|includeThis mClass mthd|
+
+	includeThis := false.
+	(aChange isMethodChange or:[aChange isMethodRemoveChange]) ifTrue:[
+	    mClass := aChange changeClass.
+	    mClass notNil ifTrue:[
+		mthd := mClass compiledMethodAt:(aChange selector).
+		mthd isNil ifTrue:[
+		    aChange isMethodRemoveChange ifTrue:[
+			includeThis := (mClass package = aPackageSymbol)
+		    ].
+		] ifFalse:[
+		    includeThis := (mthd package = aPackageSymbol)
+		]
+	    ].
+	] ifFalse:[
+	    (aChange isClassChange) ifTrue:[
+		(aChange changeClass notNil) ifTrue:[
+		    includeThis := (aChange changeClass package = aPackageSymbol)
+		].
+	    ].
+	].
+	includeThis
     ])
 
     "
@@ -1586,14 +1588,14 @@
 
     nameOfClass := aClass name.
 
-    ^ self contains:[:aChange | 
-                        selector = aChange selector 
-                        ifFalse:[
-                            false
-                        ] ifTrue:[
-                            nameOfClass = aChange className
-                        ]
-                    ]
+    ^ self contains:[:aChange |
+			selector = aChange selector
+			ifFalse:[
+			    false
+			] ifTrue:[
+			    nameOfClass = aChange className
+			]
+		    ]
 
     "
      ChangeSet current includesChangeForClass:ChangeSet selector:#includesChangeForClass:
@@ -1619,16 +1621,16 @@
     nameOfMetaclass := aClass theMetaclass name.
 
     (self changedClasses contains:[:eachClass | eachClass theNonMetaclass name = nameOfClass]) ifFalse:[
-        ^ false.
+	^ false.
     ].
 
 
-    ^ self contains:[:eachChange | 
-                        |changeClassName|
-
-                        changeClassName := eachChange className.
-                        changeClassName = nameOfClass or:[changeClassName = nameOfMetaclass]
-                    ]
+    ^ self contains:[:eachChange |
+			|changeClassName|
+
+			changeClassName := eachChange className.
+			changeClassName = nameOfClass or:[changeClassName = nameOfMetaclass]
+		    ]
 
     "Modified: / 09-10-2006 / 13:40:29 / cg"
 !
@@ -1639,19 +1641,19 @@
     nameOfClass := aClass theNonMetaclass name.
     nameOfMetaclass := aClass theMetaclass name.
 
-    self do:[:aChange | 
-        |changeClassName changeClass|
-
-        changeClassName := aChange className.
-        (changeClassName = nameOfClass) ifTrue:[^ true].
-        (changeClassName = nameOfMetaclass) ifTrue:[^ true].
-
-        changeClass := aChange changeClass.
-        (changeClass notNil
-        and:[changeClass isPrivate
-        and:[changeClass owningClass == aClass]]) ifTrue:[
-            ^ true
-        ]
+    self do:[:aChange |
+	|changeClassName changeClass|
+
+	changeClassName := aChange className.
+	(changeClassName = nameOfClass) ifTrue:[^ true].
+	(changeClassName = nameOfMetaclass) ifTrue:[^ true].
+
+	changeClass := aChange changeClass.
+	(changeClass notNil
+	and:[changeClass isPrivate
+	and:[changeClass owningClass == aClass]]) ifTrue:[
+	    ^ true
+	]
     ].
     ^ false
 
@@ -1664,19 +1666,19 @@
     namesOfClasses := (aCollectionOfClasses collect:[:eachClass | eachClass theNonMetaclass name]) asArray.
     namesOfMetaclasses := (aCollectionOfClasses collect:[:eachClass | eachClass theMetaclass name]) asArray.
 
-    self do:[:aChange | 
-        |changeClassName changeClass|
-
-        changeClassName := aChange className.
-        (namesOfClasses includes:changeClassName) ifTrue:[^ true].
-        (namesOfMetaclasses includes:changeClassName) ifTrue:[^ true].
-
-        changeClass := aChange changeClass.
-        (changeClass notNil and:[changeClass isPrivate]) ifTrue:[
-            (aCollectionOfClasses includes:changeClass owningClass) ifTrue:[
-                ^ true
-            ].
-        ]
+    self do:[:aChange |
+	|changeClassName changeClass|
+
+	changeClassName := aChange className.
+	(namesOfClasses includes:changeClassName) ifTrue:[^ true].
+	(namesOfMetaclasses includes:changeClassName) ifTrue:[^ true].
+
+	changeClass := aChange changeClass.
+	(changeClass notNil and:[changeClass isPrivate]) ifTrue:[
+	    (aCollectionOfClasses includes:changeClass owningClass) ifTrue:[
+		^ true
+	    ].
+	]
     ].
     ^ false
 
@@ -1699,49 +1701,49 @@
     ^ self select:[:chg | chg isMethodDefinitionChange and:[chg className = aClassName]] as:OrderedCollection.
 !
 
-selectClassesForWhichIncludesChangeForClassOrMetaclassOrPrivateClassFrom:aCollectionOfClasses 
+selectClassesForWhichIncludesChangeForClassOrMetaclassOrPrivateClassFrom:aCollectionOfClasses
     "return the set of classes from a given collection, for which I have changes."
-    
+
     |selected alreadyProcessed classes prev|
 
-    classes := (aCollectionOfClasses 
-            collect:[:eachClass | eachClass theNonMetaclass]) as:IdentitySet.
+    classes := (aCollectionOfClasses
+	    collect:[:eachClass | eachClass theNonMetaclass]) as:IdentitySet.
 
     selected := IdentitySet new.
     alreadyProcessed := IdentitySet new.
 
-    self do:[:eachChange | 
-        |changeClassName changeClass isIn|
-
-        changeClass := eachChange changeClass.
-        (changeClass notNil and:[changeClass ~~ prev]) ifTrue:[
-            changeClass := changeClass theNonMetaclass.
-            (alreadyProcessed includes:changeClass) ifFalse:[
-                (classes includes:changeClass) ifTrue:[
-                    selected add:changeClass
-                ].
-                
-                "/ Care for private classes. If one of its owningClass
-                "/ is in the given collection, add **that owningClass** into
-                "/ result too!!!!
-                
-                changeClass isPrivate ifTrue:[
-                    |owner|
-
-                    owner := changeClass owningClass.
-                    [owner notNil] whileTrue:[
-                        (classes includes:owner) ifTrue:[
-                            selected add:owner.
-                            owner := nil.
-                        ] ifFalse:[
-                            owner := owner owningClass.
-                        ].
-                    ].
-                ].
-                alreadyProcessed add: changeClass.
-            ].
-            prev := changeClass.
-        ].
+    self do:[:eachChange |
+	|changeClassName changeClass isIn|
+
+	changeClass := eachChange changeClass.
+	(changeClass notNil and:[changeClass ~~ prev]) ifTrue:[
+	    changeClass := changeClass theNonMetaclass.
+	    (alreadyProcessed includes:changeClass) ifFalse:[
+		(classes includes:changeClass) ifTrue:[
+		    selected add:changeClass
+		].
+
+		"/ Care for private classes. If one of its owningClass
+		"/ is in the given collection, add **that owningClass** into
+		"/ result too!!!!
+
+		changeClass isPrivate ifTrue:[
+		    |owner|
+
+		    owner := changeClass owningClass.
+		    [owner notNil] whileTrue:[
+			(classes includes:owner) ifTrue:[
+			    selected add:owner.
+			    owner := nil.
+			] ifFalse:[
+			    owner := owner owningClass.
+			].
+		    ].
+		].
+		alreadyProcessed add: changeClass.
+	    ].
+	    prev := changeClass.
+	].
     ].
     ^ selected.
 
@@ -1759,21 +1761,21 @@
 
     selected := ChangeSet new.
 
-    self do:[:eachChange | 
-        |changeClassName changeClass isIn|
-
-        changeClass := eachChange changeClass.
-        (changeClass notNil) ifTrue:[
-            changeClass := changeClass theNonMetaclass.
-            ((classes includes:changeClass)
-                or: [
-                    changeClass isPrivate
-                    and: [ (classes includes:changeClass owningClass) ]
-                ]
-            ) ifTrue:[
-                selected add: eachChange
-            ].
-        ]
+    self do:[:eachChange |
+	|changeClassName changeClass isIn|
+
+	changeClass := eachChange changeClass.
+	(changeClass notNil) ifTrue:[
+	    changeClass := changeClass theNonMetaclass.
+	    ((classes includes:changeClass)
+		or: [
+		    changeClass isPrivate
+		    and: [ (classes includes:changeClass owningClass) ]
+		]
+	    ) ifTrue:[
+		selected add: eachChange
+	    ].
+	]
     ].
     ^ selected.
 
@@ -1786,7 +1788,7 @@
     "apply all changes in the receiver's changeSet"
 
     self do:[:aChange |
-        aChange apply
+	aChange apply
     ]
 !
 
@@ -1796,9 +1798,9 @@
     changesToKeep := self class new.
     changesToRemove := self class new.
     self reverseDo:[:change|
-        (changesToKeep anySatisfy:[:each|each isForSameAs: change])
-            ifTrue:[changesToRemove add: change]
-            ifFalse:[changesToKeep add: change]
+	(changesToKeep anySatisfy:[:each|each isForSameAs: change])
+	    ifTrue:[changesToRemove add: change]
+	    ifFalse:[changesToKeep add: change]
     ].
     self condenseChanges: changesToRemove.
 
@@ -1809,16 +1811,16 @@
     "remove the given changes - a helper for the rest of the condense protocol"
 
     changesToRemove notEmpty ifTrue:[
-        changedClasses := changeSelectors := nil.
-        self removeAll:changesToRemove.
-        "/ self changed. "/  -- removeAll already sends out a notification
-        Smalltalk changed:#currentChangeSet with:self.
+	changedClasses := changeSelectors := nil.
+	self removeAll:changesToRemove.
+	"/ self changed. "/  -- removeAll already sends out a notification
+	Smalltalk changed:#currentChangeSet with:self.
     ].
 
     "Created: / 12-10-2006 / 16:51:11 / cg"
 !
 
-condenseChangesForClass:aClass 
+condenseChangesForClass:aClass
     "remove all changes for aClass (and its metaclass)
      (i.e. leave changes for other classes)."
 
@@ -1855,60 +1857,60 @@
     className := aClass theNonMetaclass name.
     metaClassName := aClass theMetaclass name.
 
-    changesToRemove := 
-        self select:[:aChange | 
-            |chgClassName chgClass removeThis mClass mthd|
-
-            removeThis := false.
-            chgClassName := aChange className.
-            (chgClassName = className or:[chgClassName = metaClassName]) ifTrue:[
-                removeThis := true
-            ] ifFalse:[
-                chgCls := aChange changeClass.
-                chgCls isNil ifTrue:[
-                    (chgClassName startsWith:(aClass name,':')) ifTrue:[
-                        "a change for a private class of a no-longer present one..."
-                            removeThis := true
-                    ].
-                ].
-
-                (chgCls notNil
-                and:[chgCls isPrivate
-                and:[chgCls topOwningClass == aClass]]) ifTrue:[
-                    removeThis := true
-                ]
-            ].
-            selectorOrNil notNil ifTrue:[
-                (aChange isMethodChange or:[aChange isMethodRemoveChange]) ifFalse:[
-                    removeThis := false.
-                ] ifTrue:[
-                    aChange selector = selectorOrNil ifFalse:[
-                        removeThis := false.
-                    ].
-                ]
-            ].
-
-            removeThis ifTrue:[
-                aChange isMethodChange ifTrue:[
-                    mClass := aChange changeClass.
-                    mClass notNil ifTrue:[
-                        mthd := mClass compiledMethodAt:(aChange selector).
-                        mthd isNil ifTrue:[
-                            "/ mthd does no longer exist
-                            "/ I no longer understand what this was meant for .. (sigh)
-                            "/                        aPackageSymbol notNil ifTrue:[
-                            "/                            removeThis := false
-                            "/                        ]
-                        ] ifFalse:[
-                            (aPackageSymbol notNil and:[mthd package ~= aPackageSymbol]) ifTrue:[
-                                removeThis := false
-                            ]
-                        ]
-                    ]
-                ].
-            ].
-            removeThis
-        ].
+    changesToRemove :=
+	self select:[:aChange |
+	    |chgClassName chgClass removeThis mClass mthd|
+
+	    removeThis := false.
+	    chgClassName := aChange className.
+	    (chgClassName = className or:[chgClassName = metaClassName]) ifTrue:[
+		removeThis := true
+	    ] ifFalse:[
+		chgCls := aChange changeClass.
+		chgCls isNil ifTrue:[
+		    (chgClassName startsWith:(aClass name,':')) ifTrue:[
+			"a change for a private class of a no-longer present one..."
+			    removeThis := true
+		    ].
+		].
+
+		(chgCls notNil
+		and:[chgCls isPrivate
+		and:[chgCls topOwningClass == aClass]]) ifTrue:[
+		    removeThis := true
+		]
+	    ].
+	    selectorOrNil notNil ifTrue:[
+		(aChange isMethodChange or:[aChange isMethodRemoveChange]) ifFalse:[
+		    removeThis := false.
+		] ifTrue:[
+		    aChange selector = selectorOrNil ifFalse:[
+			removeThis := false.
+		    ].
+		]
+	    ].
+
+	    removeThis ifTrue:[
+		aChange isMethodChange ifTrue:[
+		    mClass := aChange changeClass.
+		    mClass notNil ifTrue:[
+			mthd := mClass compiledMethodAt:(aChange selector).
+			mthd isNil ifTrue:[
+			    "/ mthd does no longer exist
+			    "/ I no longer understand what this was meant for .. (sigh)
+			    "/                        aPackageSymbol notNil ifTrue:[
+			    "/                            removeThis := false
+			    "/                        ]
+			] ifFalse:[
+			    (aPackageSymbol notNil and:[mthd package ~= aPackageSymbol]) ifTrue:[
+				removeThis := false
+			    ]
+			]
+		    ]
+		].
+	    ].
+	    removeThis
+	].
 
     self condenseChanges:changesToRemove
 
@@ -1924,26 +1926,26 @@
 
     changesToRemove := OrderedCollection new.
 
-    changesToRemove := self select:[:aChange | 
-        |removeThis mClass mthd|
-
-        (aChange isMethodChange or:[aChange isMethodRemoveChange]) ifTrue:[
-            removeThis := false.
-            mClass := aChange changeClass.
-            (mClass notNil and:[mClass package ~= aPackageSymbol]) ifTrue:[
-                mthd := mClass compiledMethodAt:(aChange selector).
-                mthd isNil ifTrue:[
-                    aChange isMethodRemoveChange ifTrue:[
-                        removeThis := true
-                    ].
-                ] ifFalse:[
-                    mthd package = aPackageSymbol ifTrue:[
-                        removeThis := true
-                    ]
-                ]
-            ].
-        ].
-        removeThis
+    changesToRemove := self select:[:aChange |
+	|removeThis mClass mthd|
+
+	(aChange isMethodChange or:[aChange isMethodRemoveChange]) ifTrue:[
+	    removeThis := false.
+	    mClass := aChange changeClass.
+	    (mClass notNil and:[mClass package ~= aPackageSymbol]) ifTrue:[
+		mthd := mClass compiledMethodAt:(aChange selector).
+		mthd isNil ifTrue:[
+		    aChange isMethodRemoveChange ifTrue:[
+			removeThis := true
+		    ].
+		] ifFalse:[
+		    mthd package = aPackageSymbol ifTrue:[
+			removeThis := true
+		    ]
+		]
+	    ].
+	].
+	removeThis
     ].
 
     self condenseChanges:changesToRemove
@@ -1958,30 +1960,30 @@
 
     |changesToRemove|
 
-    changesToRemove := self select:[:aChange | 
-        |removeThis mClass mthd|
-
-        removeThis := false.
-        (aChange isMethodChange or:[aChange isMethodRemoveChange]) ifTrue:[
-            mClass := aChange changeClass.
-            mClass notNil ifTrue:[
-                mthd := mClass compiledMethodAt:(aChange selector).
-                mthd isNil ifTrue:[
-                    aChange isMethodRemoveChange ifTrue:[
-                        removeThis := (mClass package = aPackageSymbol)
-                    ].
-                ] ifFalse:[
-                    removeThis := (mthd package = aPackageSymbol)
-                ]
-            ].
-        ] ifFalse:[
-            (aChange isClassChange) ifTrue:[
-                (aChange changeClass notNil) ifTrue:[
-                    removeThis := (aChange changeClass package = aPackageSymbol)     
-                ].
-            ].
-        ].
-        removeThis
+    changesToRemove := self select:[:aChange |
+	|removeThis mClass mthd|
+
+	removeThis := false.
+	(aChange isMethodChange or:[aChange isMethodRemoveChange]) ifTrue:[
+	    mClass := aChange changeClass.
+	    mClass notNil ifTrue:[
+		mthd := mClass compiledMethodAt:(aChange selector).
+		mthd isNil ifTrue:[
+		    aChange isMethodRemoveChange ifTrue:[
+			removeThis := (mClass package = aPackageSymbol)
+		    ].
+		] ifFalse:[
+		    removeThis := (mthd package = aPackageSymbol)
+		]
+	    ].
+	] ifFalse:[
+	    (aChange isClassChange) ifTrue:[
+		(aChange changeClass notNil) ifTrue:[
+		    removeThis := (aChange changeClass package = aPackageSymbol)
+		].
+	    ].
+	].
+	removeThis
     ].
 
     self condenseChanges:changesToRemove
@@ -1993,11 +1995,11 @@
 diffSetsAgainst:anotherChangeSet
     "walk over the receiver and anotherChangeSet,
      add all changes to one of the tree lists:
-        onlyInReceiver, onlyInArg or changed,
+	onlyInReceiver, onlyInArg or changed,
      each being a changeSet containing corresponding changes.
-     WARNING: 
-        destructive; could modify both the receiver and the argument by possibly
-        changing methodChanges into categoryChanges"
+     WARNING:
+	destructive; could modify both the receiver and the argument by possibly
+	changing methodChanges into categoryChanges"
 
     |otherChangeIndicesBySelector otherNonMethodChangeIndices changeIndicesBySelector nonMethodChangeIndices
      onlyInReceiver onlyInArg changedMethods same
@@ -2017,79 +2019,79 @@
 
     "/ these caches reduces square runtime to almost linear...
     anotherChangeSet keysAndValuesDo:[:idxB :aChangeInB |
-        |setOfOtherChangeIndicesForThisSelector|
-
-        aChangeInB isMethodChange ifTrue:[
-            setOfOtherChangeIndicesForThisSelector := otherChangeIndicesBySelector at:(aChangeInB selector) ifAbsentPut:[OrderedCollection new].
-            setOfOtherChangeIndicesForThisSelector add:idxB.
-        ] ifFalse:[
-            otherNonMethodChangeIndices add:idxB
-        ].
+	|setOfOtherChangeIndicesForThisSelector|
+
+	aChangeInB isMethodChange ifTrue:[
+	    setOfOtherChangeIndicesForThisSelector := otherChangeIndicesBySelector at:(aChangeInB selector) ifAbsentPut:[OrderedCollection new].
+	    setOfOtherChangeIndicesForThisSelector add:idxB.
+	] ifFalse:[
+	    otherNonMethodChangeIndices add:idxB
+	].
     ].
 
     self keysAndValuesDo:[:idxA :aChangeInA |
-        |indicesOfChangesToExplore anyFound ch|
-
-        anyFound := false.
-
-        aChangeInA isMethodChange ifTrue:[
-            indicesOfChangesToExplore := otherChangeIndicesBySelector at:(aChangeInA selector) ifAbsent:#()
-        ] ifFalse:[
-            indicesOfChangesToExplore := otherNonMethodChangeIndices.
-        ].
-
-        indicesOfChangesToExplore do:[:idxB |
-            |aChangeInB|
-
-            aChangeInB := anotherChangeSet at:idxB.
-
-            (aChangeInA isForSameAs:aChangeInB) ifTrue:[
-                anyFound := true.
-
-                "/ also in B - is it different ?
-                (aChangeInA sameAs:aChangeInB) ifFalse:[
-                    changedMethods add:aChangeInA.
-                    indexFromChangedMethodsToA add:idxA.
-                    indexFromChangedMethodsToB add:idxB.
-                ] ifTrue:[
-                    aChangeInA isMethodChange ifTrue:[
-                        aChangeInA methodCategory ~= aChangeInB methodCategory ifTrue:[
-                            "/ only the category is different;
-                            "/ make it a MethodCategory changes.
-
-                            ch := MethodCategoryChange new
-                                    className:aChangeInA className
-                                    selector:aChangeInA selector
-                                    category:aChangeInA methodCategory;
-                                    "JV@2012-03-20: Also keeps origin, required by merge tool"
-                                    origin: aChangeInA.
-                            self at:idxA put:ch.
-
-                            ch := MethodCategoryChange new
-                                    className:aChangeInB className
-                                    selector:aChangeInB selector
-                                    category:aChangeInB methodCategory;
-                                    "JV@2012-03-20: Also keeps origin, required by merge tool"
-                                    origin: aChangeInB.
-                            anotherChangeSet at:idxB put:ch.
-
-                            changedMethods add:aChangeInA.
-                            indexFromChangedMethodsToA add:idxA.
-                            indexFromChangedMethodsToB add:idxB.
-                        ]
-                    ].
-                ]
-            ] ifFalse:[
-                (aChangeInA sameAs:aChangeInB) ifTrue:[
-                    anyFound := true.
-                ] ifFalse:[
-                ]
-            ]
-        ].
-
-        anyFound ifFalse:[
-            onlyInReceiver add:aChangeInA.
-        ]
+	|indicesOfChangesToExplore anyFound ch|
+
+	anyFound := false.
+
+	aChangeInA isMethodChange ifTrue:[
+	    indicesOfChangesToExplore := otherChangeIndicesBySelector at:(aChangeInA selector) ifAbsent:#()
+	] ifFalse:[
+	    indicesOfChangesToExplore := otherNonMethodChangeIndices.
+	].
+
+	indicesOfChangesToExplore do:[:idxB |
+	    |aChangeInB|
+
+	    aChangeInB := anotherChangeSet at:idxB.
+
+	    (aChangeInA isForSameAs:aChangeInB) ifTrue:[
+		anyFound := true.
+
+		"/ also in B - is it different ?
+		(aChangeInA sameAs:aChangeInB) ifFalse:[
+		    changedMethods add:aChangeInA.
+		    indexFromChangedMethodsToA add:idxA.
+		    indexFromChangedMethodsToB add:idxB.
+		] ifTrue:[
+		    aChangeInA isMethodChange ifTrue:[
+			aChangeInA methodCategory ~= aChangeInB methodCategory ifTrue:[
+			    "/ only the category is different;
+			    "/ make it a MethodCategory changes.
+
+			    ch := MethodCategoryChange new
+				    className:aChangeInA className
+				    selector:aChangeInA selector
+				    category:aChangeInA methodCategory;
+				    "JV@2012-03-20: Also keeps origin, required by merge tool"
+				    origin: aChangeInA.
+			    self at:idxA put:ch.
+
+			    ch := MethodCategoryChange new
+				    className:aChangeInB className
+				    selector:aChangeInB selector
+				    category:aChangeInB methodCategory;
+				    "JV@2012-03-20: Also keeps origin, required by merge tool"
+				    origin: aChangeInB.
+			    anotherChangeSet at:idxB put:ch.
+
+			    changedMethods add:aChangeInA.
+			    indexFromChangedMethodsToA add:idxA.
+			    indexFromChangedMethodsToB add:idxB.
+			]
+		    ].
+		]
+	    ] ifFalse:[
+		(aChangeInA sameAs:aChangeInB) ifTrue:[
+		    anyFound := true.
+		] ifFalse:[
+		]
+	    ]
+	].
+
+	anyFound ifFalse:[
+	    onlyInReceiver add:aChangeInA.
+	]
     ].
 
     "/ these caches reduces square runtime to almost linear...
@@ -2097,80 +2099,80 @@
     nonMethodChangeIndices := OrderedCollection new.
 
     self keysAndValuesDo:[:idxA :aChangeInA |
-        |setOfChangeIndicesForThisSelector|
-
-        aChangeInA isMethodChange ifTrue:[
-            setOfChangeIndicesForThisSelector := changeIndicesBySelector at:(aChangeInA selector) ifAbsentPut:[OrderedCollection new].
-            setOfChangeIndicesForThisSelector add:idxA.
-        ] ifFalse:[
-            nonMethodChangeIndices add:idxA
-        ].
+	|setOfChangeIndicesForThisSelector|
+
+	aChangeInA isMethodChange ifTrue:[
+	    setOfChangeIndicesForThisSelector := changeIndicesBySelector at:(aChangeInA selector) ifAbsentPut:[OrderedCollection new].
+	    setOfChangeIndicesForThisSelector add:idxA.
+	] ifFalse:[
+	    nonMethodChangeIndices add:idxA
+	].
     ].
 
     anotherChangeSet keysAndValuesDo:[:idxB :aChangeInB |
-        |anyFound indicesOfChangesToExplore|
-
-        anyFound := false.
-
-        aChangeInB isMethodChange ifTrue:[
-            indicesOfChangesToExplore := changeIndicesBySelector at:(aChangeInB selector) ifAbsent:#()
-        ] ifFalse:[
-            indicesOfChangesToExplore := nonMethodChangeIndices.
-        ].
-
-        indicesOfChangesToExplore do:[:idxA |
-            |aChangeInA idxM|
-
-            aChangeInA := self at:idxA.
-
-            (aChangeInA isForSameAs:aChangeInB) ifTrue:[
-                anyFound := true.
-
-                "/ also in B - is it different ?
-                (aChangeInA sameAs:aChangeInB) ifFalse:[
-                    "/ already there ?
-                    idxM := changedMethods findFirst:[:c | c isForSameAs:aChangeInB].
-                    idxM == 0 ifTrue:[
-                        changedMethods add:aChangeInB.
-                        indexFromChangedMethodsToB add:idxB.
-                    ] ifFalse:[
-                        indexFromChangedMethodsToB at:idxM put:idxB
-                    ]
-                ]
-            ] ifFalse:[
-                (aChangeInA sameAs:aChangeInB) ifTrue:[
-                    anyFound := true.
-                ] ifFalse:[
-                ]
-            ]
-        ].
-        anyFound ifFalse:[
-            onlyInArg add:aChangeInB.
-        ]
+	|anyFound indicesOfChangesToExplore|
+
+	anyFound := false.
+
+	aChangeInB isMethodChange ifTrue:[
+	    indicesOfChangesToExplore := changeIndicesBySelector at:(aChangeInB selector) ifAbsent:#()
+	] ifFalse:[
+	    indicesOfChangesToExplore := nonMethodChangeIndices.
+	].
+
+	indicesOfChangesToExplore do:[:idxA |
+	    |aChangeInA idxM|
+
+	    aChangeInA := self at:idxA.
+
+	    (aChangeInA isForSameAs:aChangeInB) ifTrue:[
+		anyFound := true.
+
+		"/ also in B - is it different ?
+		(aChangeInA sameAs:aChangeInB) ifFalse:[
+		    "/ already there ?
+		    idxM := changedMethods findFirst:[:c | c isForSameAs:aChangeInB].
+		    idxM == 0 ifTrue:[
+			changedMethods add:aChangeInB.
+			indexFromChangedMethodsToB add:idxB.
+		    ] ifFalse:[
+			indexFromChangedMethodsToB at:idxM put:idxB
+		    ]
+		]
+	    ] ifFalse:[
+		(aChangeInA sameAs:aChangeInB) ifTrue:[
+		    anyFound := true.
+		] ifFalse:[
+		]
+	    ]
+	].
+	anyFound ifFalse:[
+	    onlyInArg add:aChangeInB.
+	]
     ].
 
 "/    info := OrderedCollection new:(changedMethods size).
 "/    changedMethods keysAndValuesDo:[:idx :changedMethod |
-"/        info add:(Array 
+"/        info add:(Array
 "/                        with:(indexFromChangedMethodsToA at:idx)
 "/                        with:(indexFromChangedMethodsToB at:idx)
 "/                 )
 "/    ].
     changedMethods := (1 to:changedMethods size) asOrderedCollection collect:[:idx |
-                        |cA cB|
-
-                        cA := self at:(indexFromChangedMethodsToA at:idx).
-                        cB := anotherChangeSet at:(indexFromChangedMethodsToB at:idx).
-                        Array with:cA with:cB
-                      ].
+			|cA cB|
+
+			cA := self at:(indexFromChangedMethodsToA at:idx).
+			cB := anotherChangeSet at:(indexFromChangedMethodsToB at:idx).
+			Array with:cA with:cB
+		      ].
 
     same := self reject:[:chg|(changedMethods contains:[:pair|pair first == chg]) or:[onlyInReceiver includes: chg]].
 
     ret := DiffSet new
-                changed:changedMethods
-                onlyInReceiver:onlyInReceiver
-                onlyInArg:onlyInArg
-                same: same.
+		changed:changedMethods
+		onlyInReceiver:onlyInReceiver
+		onlyInArg:onlyInArg
+		same: same.
 "/    ret info:info.
     ^ret
 
@@ -2199,7 +2201,7 @@
 
     flatten := self class new: self size.
     self do:[:ea|
-        ea do:[:ea2| flatten add: ea2]
+	ea do:[:ea2| flatten add: ea2]
     ].
     ^ flatten
 
@@ -2209,11 +2211,11 @@
 groupBy: groupBlock labelAs: labelBlock
 
     "
-        returns a new changeset consisting of CompositeChanges.
-        Changes are grouped together by value (tag) of groupBlock.
-        Each composite change is then labeled using label
-        returned by labelBlock (called with the tag returned
-        by groupBlock as arg)
+	returns a new changeset consisting of CompositeChanges.
+	Changes are grouped together by value (tag) of groupBlock.
+	Each composite change is then labeled using label
+	returned by labelBlock (called with the tag returned
+	by groupBlock as arg)
     "
 
     ^ self groupBy: groupBlock labelAs: labelBlock sort: false
@@ -2234,35 +2236,35 @@
     | buckets newChangeset keys |
 
     buckets := OrderedDictionary new.
-    self do:[:change| 
-        | tag |
-
-        tag := groupBlock value: change.
-        (buckets at: tag ifAbsentPut: [self class new:4]) add: change
+    self do:[:change|
+	| tag |
+
+	tag := groupBlock value: change.
+	(buckets at: tag ifAbsentPut: [self class new:4]) add: change
     ].
     newChangeset := self class new: buckets size.
 
     keys := buckets keys select:[:k | k notNil].
     doSort ifTrue:[ keys sort ].
     keys do:[:tag |
-        |changes classDefs|
-
-        changes := buckets at:tag.
-
-        "Move class definition to the front"
-        classDefs := changes select:[:chg|chg isClassDefinitionChange].
-        changes removeAll: classDefs.
-        changes addAllFirst: classDefs.
-
-        tag notNil ifTrue:[
-            newChangeset add:
-                (CompositeChange 
-                    name: (labelBlock value: tag)
-                    changes: changes)
-        ]
+	|changes classDefs|
+
+	changes := buckets at:tag.
+
+	"Move class definition to the front"
+	classDefs := changes select:[:chg|chg isClassDefinitionChange].
+	changes removeAll: classDefs.
+	changes addAllFirst: classDefs.
+
+	tag notNil ifTrue:[
+	    newChangeset add:
+		(CompositeChange
+		    name: (labelBlock value: tag)
+		    changes: changes)
+	]
     ].
     (buckets includesKey: nil) ifTrue:[
-        newChangeset addAll: (buckets at: nil)
+	newChangeset addAll: (buckets at: nil)
     ].
     ^newChangeset
 
@@ -2276,19 +2278,19 @@
     |nm|
 
     ^self
-        groupBy: [:change|
-            change isClassChange ifTrue: [
-                nm := change className.
-                (nm notNil and:[nm endsWith:' class']) ifTrue:[nm := nm copyTo: nm size - 6].
-                nm
-            ] ifFalse: [
-                nil
-            ]
-        ]
-        labelAs: [:className|
-            className
-        ]
-        sort: true
+	groupBy: [:change|
+	    change isClassChange ifTrue: [
+		nm := change className.
+		(nm notNil and:[nm endsWith:' class']) ifTrue:[nm := nm copyTo: nm size - 6].
+		nm
+	    ] ifFalse: [
+		nil
+	    ]
+	]
+	labelAs: [:className|
+	    className
+	]
+	sort: true
 
     "Created: / 25-07-2009 / 19:43:14 / Jan Vrany <vranyj1@fel.cvut.cz>"
     "Modified: / 24-10-2009 / 18:49:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -2334,9 +2336,9 @@
      Supported formats are:
        nil ............ chunk changeset file
        #classSource ... class fileout format, assumes that
-                        the receiver is a changeset containing
-                        single class (possibly with its private 
-                        classes)
+			the receiver is a changeset containing
+			single class (possibly with its private
+			classes)
     "
 
     |s|
@@ -2354,20 +2356,20 @@
      Supported formats are:
        nil ............ chunk changeset file format
        #classSource ... class fileout format, assumes that
-                        the receiver is a changeset containing
-                        single class (possibly with its private 
-                        classes)
+			the receiver is a changeset containing
+			single class (possibly with its private
+			classes)
     "
 
 
     formatSymbolOrNil isNil ifTrue:[
-        ChangeFileWriter new fileOut:self on:aStream.
-        ^ self.
+	ChangeFileWriter new fileOut:self on:aStream.
+	^ self.
     ].
 
     formatSymbolOrNil == #classSource ifTrue:[
-        ClassSourceWriter new fileOut:self on:aStream.
-        ^ self.
+	ClassSourceWriter new fileOut:self on:aStream.
+	^ self.
     ].
 
     self error:'Unknown format, possible formats are { nil, #classSource }'
@@ -2399,14 +2401,14 @@
     timestamp notNil ifTrue:[change timeStamp: timestamp].
     timestamp := nil.
     change isClassChange ifTrue:[
-        change package: Class packageQuerySignal query.
-        change nameSpace: Class nameSpaceQuerySignal query.
+	change package: Class packageQuerySignal query.
+	change nameSpace: Class nameSpaceQuerySignal query.
     ].
 
-    changeAction 
-        valueWithOptionalArgument:change 
-        and:lineNumber 
-        and:position.
+    changeAction
+	valueWithOptionalArgument:change
+	and:lineNumber
+	and:position.
 
     "Modified: / 11-06-2013 / 15:57:01 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -2426,33 +2428,33 @@
 
 
     (aReceiver isUnaryMessage and:[aReceiver selector == #class]) ifTrue:[
-        isMeta := true.
-        clsNode := aReceiver receiver.
+	isMeta := true.
+	clsNode := aReceiver receiver.
     ] ifFalse:[
-        clsNode := aReceiver.
+	clsNode := aReceiver.
     ].
 
     clsNode isMessage ifFalse:[
-        "Normal smalltalk method on Smalltalk class"
-        clsName := clsNode name
+	"Normal smalltalk method on Smalltalk class"
+	clsName := clsNode name
     ] ifTrue:[
-        "Maybe a Java class?"
-        ((clsNode selector == #classForName:) and:[clsNode receiver name = 'Java']) ifTrue:[
-            clsName := '(Java classForName:''%1'')' bindWith: clsNode arguments first value.
-            classIsJava := true.
-        ].
+	"Maybe a Java class?"
+	((clsNode selector == #classForName:) and:[clsNode receiver name = 'Java']) ifTrue:[
+	    clsName := '(Java classForName:''%1'')' bindWith: clsNode arguments first value.
+	    classIsJava := true.
+	].
     ].
 
     isMeta ifTrue:[
-        clsName := clsName , ' class'.
+	clsName := clsName , ' class'.
     ].
 
     (nameSpace ~~ Smalltalk and:[(clsName startsWith: nameSpace name) not])
-        ifTrue:[
-            ^ nameSpace name , '::' , clsName
-        ] ifFalse:[     
-            ^ clsName
-        ].
+	ifTrue:[
+	    ^ nameSpace name , '::' , clsName
+	] ifFalse:[
+	    ^ clsName
+	].
 
     "Modified: / 30-01-2013 / 10:02:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -2468,58 +2470,58 @@
 
 
     (aReceiver isUnaryMessage and:[aReceiver selector == #class]) ifTrue:[
-        isMeta := true.
-        clsNode := aReceiver receiver.
+	isMeta := true.
+	clsNode := aReceiver receiver.
     ] ifFalse:[
-        clsNode := aReceiver.
+	clsNode := aReceiver.
     ].
 
     clsNode isMessage ifFalse:[
-        "Normal smalltalk method on Smalltalk class"
-        clsName := clsNode name
+	"Normal smalltalk method on Smalltalk class"
+	clsName := clsNode name
     ] ifTrue:[
-        "Maybe a Java class?"
-        ((clsNode selector == #classForName:) and:[clsNode receiver name = 'Java']) ifTrue:[
-            clsName := '(Java classForName:''%1'')' bindWith: clsNode arguments first value.
-            classIsJava := true.
-        ].
+	"Maybe a Java class?"
+	((clsNode selector == #classForName:) and:[clsNode receiver name = 'Java']) ifTrue:[
+	    clsName := '(Java classForName:''%1'')' bindWith: clsNode arguments first value.
+	    classIsJava := true.
+	].
     ].
 
     isMeta ifTrue:[
-        clsName := clsName , ' class'.
+	clsName := clsName , ' class'.
     ].
 
     "Strip off the namespace"
     (classIsJava not and:[ nameSpace ~~ Smalltalk]) ifTrue:[
-        (clsName startsWith: nameSpace name) ifTrue:[
-            clsName := clsName copyFrom: nameSpace name size + 3.
-        ]
+	(clsName startsWith: nameSpace name) ifTrue:[
+	    clsName := clsName copyFrom: nameSpace name size + 3.
+	]
     ].
 
     (nameSpace ~~ Smalltalk and:[(clsName startsWith: nameSpace name) not])
-        ifTrue:[
-            "/ old: remember namespace in name
-            "/ ^ nameSpace name , '::' , clsName
-            "/ new: remember in override
-            nameSpaceOverride := nameSpace.
-            ^ clsName
-        ] ifFalse:[
-            nameSpaceOverride := nil.
-            ^ clsName
-        ].
+	ifTrue:[
+	    "/ old: remember namespace in name
+	    "/ ^ nameSpace name , '::' , clsName
+	    "/ new: remember in override
+	    nameSpaceOverride := nameSpace.
+	    ^ clsName
+	] ifFalse:[
+	    nameSpaceOverride := nil.
+	    ^ clsName
+	].
 
     "Modified: / 11-06-2013 / 17:55:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 extractMethodsClassAndSelectorFromReceiver
     "helper for all changes which are of the form:
-        (className compiledMethodAt:#methodSelector) something: ...
+	(className compiledMethodAt:#methodSelector) something: ...
     "
 
     (receiver isMessage
     and:[receiverSelector == #'compiledMethodAt:']) ifFalse:[
-        self error:'unexpected change' mayProceed:true.
-        ^ false.
+	self error:'unexpected change' mayProceed:true.
+	^ false.
     ].
 
     "/ className := self classNameOf:receiverReceiver.
@@ -2553,7 +2555,7 @@
     "given a parse-tree (from parsing some changes source/chunk),
      create changes and evaluate changeAction on each.
      The chnageAction-block is invoked with the change and a lineNumberOrNil as
-     arg; the lineNumber is only valid, if the underlying inputStream 
+     arg; the lineNumber is only valid, if the underlying inputStream
      provides line-numbers; otherwise, nil is passed."
 
     ^self changesFromParseTree:aTree lineNumber:initialLineNumberOrNil position:initialPositionOrNil chunk: nil
@@ -2565,7 +2567,7 @@
     "given a parse-tree (from parsing some changes source/chunk),
      create changes and evaluate changeAction on each.
      The chnageAction-block is invoked with the change and a lineNumberOrNil as
-     arg; the lineNumber is only valid, if the underlying inputStream 
+     arg; the lineNumber is only valid, if the underlying inputStream
      provides line-numbers; otherwise, nil is passed."
 
     lineNumber := initialLineNumberOrNil.
@@ -2578,8 +2580,8 @@
     arguments := aTree arguments.
 
     receiver isMessage ifTrue:[
-        receiverSelector := receiver selector.
-        receiverReceiver := receiver receiver.
+	receiverSelector := receiver selector.
+	receiverReceiver := receiver receiver.
     ].
 
     ^ self processChange
@@ -2599,43 +2601,43 @@
     attributes := OrderedCollection new.
 
     [
-        inputStream skipSeparators.
-        category := inputStream nextChunk.
-        category notEmptyOrNil
+	inputStream skipSeparators.
+	category := inputStream nextChunk.
+	category notEmptyOrNil
     ] whileTrue:[
-        ( #( 'public' 'private' ) includes: category) ifTrue:[
-            attributes add:category
-        ] ifFalse:[
-            categories add:category
-        ].
+	( #( 'public' 'private' ) includes: category) ifTrue:[
+	    attributes add:category
+	] ifFalse:[
+	    categories add:category
+	].
     ].
     categories size == 1 ifTrue:[
-        "/ easy
-        change := MethodCategoryChange 
-                        className:className
-                        selector:selector
-                        source:(parseTree printString)
-                        category:(categories first).
-        self addChange:change.
+	"/ easy
+	change := MethodCategoryChange
+			className:className
+			selector:selector
+			source:(parseTree printString)
+			category:(categories first).
+	self addChange:change.
     ] ifFalse:[
-        self halt:'multiple/missing categories not supported'.
+	self halt:'multiple/missing categories not supported'.
     ].
 
     attributes size == 1 ifTrue:[
-        "/ easy
-        (attributes first = 'public') ifTrue:[
-            "/ default anyway - ignore
-        ] ifFalse:[
-            change := MethodPrivacyChange 
-                        className:className
-                        selector:selector
-                        privacy:(attributes first asSymbol).
-            change nameSpaceOverride:nameSpaceOverride.
-            change source:(parseTree printString).
-            self addChange:change.
-        ].
+	"/ easy
+	(attributes first = 'public') ifTrue:[
+	    "/ default anyway - ignore
+	] ifFalse:[
+	    change := MethodPrivacyChange
+			className:className
+			selector:selector
+			privacy:(attributes first asSymbol).
+	    change nameSpaceOverride:nameSpaceOverride.
+	    change source:(parseTree printString).
+	    self addChange:change.
+	].
     ] ifFalse:[
-        self halt:'multiple/missing attributes not supported'.
+	self halt:'multiple/missing attributes not supported'.
     ].
     ^ true
 
@@ -2672,34 +2674,34 @@
     change := ClassDefinitionChange new.
     change className:className; source:(parseTree printString).
     receiver isVariable ifTrue:[
-        change superClassName:receiver name.
+	change superClassName:receiver name.
     ].
     selector keywords with:arguments do:[:kw :arg |
-        kw = #'instanceVariableNames:' ifTrue:[
-            change instanceVariableString:arg evaluate.
-        ].
-        kw = #'classVariableNames:' ifTrue:[
-            change classVariableString:arg evaluate.
-        ].
-        kw = #'poolDictionaries:' ifTrue:[
-            change poolDictionaries:arg evaluate.
-        ].
-        kw = #'category:' ifTrue:[
-            change category:arg evaluate.
-        ].
-        kw = #'privateIn:' ifTrue:[
-            | nm |
-
-            nm := arg name.
-            nameSpace notNil ifTrue:[
-                (nm startsWith: nameSpace name) ifTrue:[
-                    nm := nm copyFrom: nameSpace name size + 3.
-                ].
-            ].
-            change className:(nm ,'::',change classNameWithoutNamespace).
-            change owningClassName:nm.
-            change private:true.
-        ].
+	kw = #'instanceVariableNames:' ifTrue:[
+	    change instanceVariableString:arg evaluate.
+	].
+	kw = #'classVariableNames:' ifTrue:[
+	    change classVariableString:arg evaluate.
+	].
+	kw = #'poolDictionaries:' ifTrue:[
+	    change poolDictionaries:arg evaluate.
+	].
+	kw = #'category:' ifTrue:[
+	    change category:arg evaluate.
+	].
+	kw = #'privateIn:' ifTrue:[
+	    | nm |
+
+	    nm := arg name.
+	    nameSpace notNil ifTrue:[
+		(nm startsWith: nameSpace name) ifTrue:[
+		    nm := nm copyFrom: nameSpace name size + 3.
+		].
+	    ].
+	    change className:(nm ,'::',change classNameWithoutNamespace).
+	    change owningClassName:nm.
+	    change private:true.
+	].
     ].
 
     change package:(Class packageQuerySignal query).
@@ -2714,7 +2716,7 @@
     "Modified: / 11-06-2013 / 22:30:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-handleClassInitializeChange 
+handleClassInitializeChange
     | change nm |
 
     nm := self receiversClassNameRememberingNamespace.
@@ -2748,14 +2750,14 @@
     |change|
 
     self extractMethodsClassAndSelectorFromReceiver ifFalse:[
-        ^ false.
+	^ false.
     ].
 
     change := MethodCategoryChange new.
-    change 
-        className:className
-        selector:methodSelector
-        category:(arguments at:1) evaluate.
+    change
+	className:className
+	selector:methodSelector
+	category:(arguments at:1) evaluate.
 
     self addChange:change.
     ^ true
@@ -2770,10 +2772,10 @@
     className := self receiversClassNameRememberingNamespace.
 
     change := MethodCategoryRenameChange new.
-    change 
-        className:className;
-        oldCategoryName:(arguments at:1) evaluate
-        newCategoryName:(arguments at:2) evaluate.
+    change
+	className:className;
+	oldCategoryName:(arguments at:1) evaluate
+	newCategoryName:(arguments at:2) evaluate.
 
     self addChange:change.
     ^ true
@@ -2783,19 +2785,19 @@
 
 handleMethodChange
     [
-        ^ self handleMethodChangeUnsafe
+	^ self handleMethodChangeUnsafe
     ] on: Error do:[:ex|
-        | change |
-
-        change := InvalidChange new source: chunk.
-        self addChange: change.
-
-        "Read methods that may follow"    
-
-        [ (chunk := inputStream nextChunk) notEmptyOrNil ] whileTrue:[
-            change := InvalidChange new source: chunk.
-            self addChange: change.
-        ]
+	| change |
+
+	change := InvalidChange new source: chunk.
+	self addChange: change.
+
+	"Read methods that may follow"
+
+	[ (chunk := inputStream nextChunk) notEmptyOrNil ] whileTrue:[
+	    change := InvalidChange new source: chunk.
+	    self addChange: change.
+	]
     ].
 
     ^ true
@@ -2809,68 +2811,68 @@
     className := self receiversClassNameRememberingNamespace.
 
     (selector == #'ignoredMethodsFor:') ifTrue:[
-        priv := #ignored.
+	priv := #ignored.
     ] ifFalse:[
-        priv := nil
+	priv := nil
     ].
     classIsJava := false.
-    ((selector == #'methods') 
+    ((selector == #'methods')
     or:[(selector == #'publicMethods')
     or:[(selector == #'methodsFor')]]) ifTrue:[
-        categoryName := 'uncategorized public'
+	categoryName := 'uncategorized public'
     ] ifFalse:[
-        (selector == #'privateMethods') ifTrue:[
-            categoryName := 'uncategorized private'
-        ] ifFalse:[
-            categoryName := (arguments at:1) evaluate.
-        ]
+	(selector == #'privateMethods') ifTrue:[
+	    categoryName := 'uncategorized private'
+	] ifFalse:[
+	    categoryName := (arguments at:1) evaluate.
+	]
     ].
     inputStream skipSeparators.
     lineNumber := inputStream lineNumber.
     "/ Care for non-positionable streams
     position := nil.
     inputStream isPositionable ifTrue:[
-        position := inputStream position + 1.
+	position := inputStream position + 1.
     ].
 
     methodSource := chunk := inputStream nextChunk.
     changes := OrderedCollection new.
 
     [methodSource notEmptyOrNil] whileTrue:[
-        parser := Parser
-                    parseMethodArgAndVarSpecification:methodSource 
-                    in:nil 
-                    ignoreErrors:true 
-                    ignoreWarnings:true
-                    parseBody:false.
-
-        parser isNil ifTrue:[
-            "/ something wierd ...
-            methodSelector := '????'.
-        ] ifFalse:[
-            methodSelector := parser selector.
-        ].
-
-        change := MethodDefinitionChange new.
-        change 
-            className:className
-            selector:methodSelector
-            source:methodSource
-            category:categoryName
-            privacy:priv.
-        "/ huh - where is classIsJava: implemented???
-        classIsJava ifTrue:[ change classIsJava: classIsJava ].
-
-        self addChange:change.
-
-        inputStream skipSeparators.
-        lineNumber := inputStream lineNumber.
-        "/ Care for non-positionable streams
-        position := nil.
-        inputStream isPositionable ifTrue:[
-            position := inputStream position + 1.
-        ].   
-        methodSource := chunk := inputStream nextChunk.
+	parser := Parser
+		    parseMethodArgAndVarSpecification:methodSource
+		    in:nil
+		    ignoreErrors:true
+		    ignoreWarnings:true
+		    parseBody:false.
+
+	parser isNil ifTrue:[
+	    "/ something wierd ...
+	    methodSelector := '????'.
+	] ifFalse:[
+	    methodSelector := parser selector.
+	].
+
+	change := MethodDefinitionChange new.
+	change
+	    className:className
+	    selector:methodSelector
+	    source:methodSource
+	    category:categoryName
+	    privacy:priv.
+	"/ huh - where is classIsJava: implemented???
+	classIsJava ifTrue:[ change classIsJava: classIsJava ].
+
+	self addChange:change.
+
+	inputStream skipSeparators.
+	lineNumber := inputStream lineNumber.
+	"/ Care for non-positionable streams
+	position := nil.
+	inputStream isPositionable ifTrue:[
+	    position := inputStream position + 1.
+	].
+	methodSource := chunk := inputStream nextChunk.
     ].
     ^ true
 
@@ -2882,14 +2884,14 @@
     |change|
 
     self extractMethodsClassAndSelectorFromReceiver ifFalse:[
-        ^ false.
+	^ false.
     ].
 
     change := MethodPackageChange new.
-    change 
-        className:className
-        selector:methodSelector
-        package:(arguments at:1) evaluate.
+    change
+	className:className
+	selector:methodSelector
+	package:(arguments at:1) evaluate.
 
     self addChange:change.
     ^ true
@@ -2902,14 +2904,14 @@
     |change|
 
     self extractMethodsClassAndSelectorFromReceiver ifFalse:[
-        ^ false.
+	^ false.
     ].
 
     change := MethodPrivacyChange new.
-    change 
-        className:className
-        selector:methodSelector
-        privacy:(arguments at:1) evaluate.
+    change
+	className:className
+	selector:methodSelector
+	privacy:(arguments at:1) evaluate.
 
     self addChange:change.
     ^ true
@@ -2922,10 +2924,10 @@
     |change|
 
     (self checkReceiverIsGlobalNamed:#Namespace) ifFalse:[
-        (self checkReceiverIsGlobalNamed:#NameSpace) ifFalse:[
-            self error:'unexpected receiver in nameSpace message' mayProceed:true.
-            ^ false
-        ].
+	(self checkReceiverIsGlobalNamed:#NameSpace) ifFalse:[
+	    self error:'unexpected receiver in nameSpace message' mayProceed:true.
+	    ^ false
+	].
     ].
 
     className := (arguments at:1) evaluate.
@@ -2936,7 +2938,7 @@
     ^ true
 !
 
-handlePrimitiveChange 
+handlePrimitiveChange
     self handlePrimitiveChange:nil
 !
 
@@ -2949,20 +2951,20 @@
     className := self receiversClassNameRememberingNamespace.
 
     sourceOrNil notNil ifTrue:[
-        primSource := sourceOrNil
+	primSource := sourceOrNil
     ] ifFalse:[
-        inputStream skipSeparators.
-        primSource := inputStream nextChunk.
+	inputStream skipSeparators.
+	primSource := inputStream nextChunk.
     ].
 
     (selector == #'primitiveDefinitions' or:[ selector == #'primitiveDefinitions:' ]) ifTrue:[
-        change := ClassPrimitiveDefinitionsChange new
+	change := ClassPrimitiveDefinitionsChange new
     ] ifFalse:[
-        (selector == #'primitiveFunctions' or:[ selector == #'primitiveFunctions:' ]) ifTrue:[
-            change := ClassPrimitiveFunctionsChange new
-        ] ifFalse:[
-            change := ClassPrimitiveVariablesChange new
-        ]
+	(selector == #'primitiveFunctions' or:[ selector == #'primitiveFunctions:' ]) ifTrue:[
+	    change := ClassPrimitiveFunctionsChange new
+	] ifFalse:[
+	    change := ClassPrimitiveVariablesChange new
+	]
     ].
     change className:className source:primSource.
     self addChange:change.
@@ -2976,8 +2978,8 @@
     |change|
 
     (self checkReceiverIsGlobalNamed:#Smalltalk) ifFalse:[
-        self error:'unexpected receiver in remove-class message' mayProceed:true.
-        ^ false
+	self error:'unexpected receiver in remove-class message' mayProceed:true.
+	^ false
     ].
 
     className := (arguments at:1) name.
@@ -3007,8 +3009,8 @@
     |oldName newName change|
 
     (self checkReceiverIsGlobalNamed:#Smalltalk) ifFalse:[
-        self error:'unexpected receiver in rename-class message' mayProceed:true.
-        ^ false.
+	self error:'unexpected receiver in rename-class message' mayProceed:true.
+	^ false.
     ].
 
     oldName := (arguments at:1) name.
@@ -3058,16 +3060,16 @@
     "given a parse-tree (from parsing some changes source/chunk),
      create changes and evaluate changeAction on each.
      The block is invoked with the change and a lineNumberOrNil as
-     arg; the lineNumber is only valid, if the underlying stream 
+     arg; the lineNumber is only valid, if the underlying stream
      provides line-numbers; otherwise, nil is passed."
 
     [
-        ^ self processChangeUnsafe
+	^ self processChangeUnsafe
     ] on: Error do:[:ex|
-        | change |
-
-        change := DoItChange new source: chunk.
-        self addChange: change.
+	| change |
+
+	change := DoItChange new source: chunk.
+	self addChange: change.
     ].
 
     ^true
@@ -3079,7 +3081,7 @@
     "given a parse-tree (from parsing some changes source/chunk),
      create changes and evaluate changeAction on each.
      The block is invoked with the change and a lineNumberOrNil as
-     arg; the lineNumber is only valid, if the underlying stream 
+     arg; the lineNumber is only valid, if the underlying stream
      provides line-numbers; otherwise, nil is passed."
 
     |dispatchSelector|
@@ -3087,13 +3089,13 @@
     dispatchSelector := ('process_',(selector copyReplaceAll:$: with:$_)) asSymbol.
 "/ Transcript showCR:dispatchSelector.
     (self respondsTo:dispatchSelector) ifTrue:[
-        ^ self perform:dispatchSelector.
+	^ self perform:dispatchSelector.
     ].
 
     "/ any subclass definiton selector ?
     (Behavior definitionSelectors includes:selector)
     ifTrue:[
-        ^ self handleClassDefinitionChange.
+	^ self handleClassDefinitionChange.
     ].
 
     self error:'unhandled change selector: ',selector.
@@ -3119,17 +3121,17 @@
     inputStream skip: 5.
     kind := inputStream upTo: Character space.
     (kind endsWith:$:) ifTrue:[
-        kind := kind copyButLast:1
+	kind := kind copyButLast:1
     ].
     sel := ('process_', kind) asSymbolIfInterned.
     sel notNil ifTrue:[
-        MessageNotUnderstood handle:[   
-            self process_otherInfo:kind    
-        ] do:[
-            self perform: sel.
-        ]
-    ] ifFalse:[   
-        self process_otherInfo:kind    
+	MessageNotUnderstood handle:[
+	    self process_otherInfo:kind
+	] do:[
+	    self perform: sel.
+	]
+    ] ifFalse:[
+	self process_otherInfo:kind
     ]
 
     "Created: / 30-03-2012 / 16:44:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -3423,35 +3425,35 @@
     "/ Care for non-positionable streams
     position := nil.
     inputStream isPositionable ifTrue:[
-        position := inputStream position + 1.
+	position := inputStream position + 1.
     ].
     methodSource := inputStream nextChunk.
 
     parser := Parser
-                parseMethodArgAndVarSpecification:methodSource 
-                in:nil 
-                ignoreErrors:true 
-                ignoreWarnings:true
-                parseBody:false.
+		parseMethodArgAndVarSpecification:methodSource
+		in:nil
+		ignoreErrors:true
+		ignoreWarnings:true
+		parseBody:false.
 
     parser isNil ifTrue:[
-        "/ something wierd ...
-        methodSelector := '????'.
+	"/ something wierd ...
+	methodSelector := '????'.
     ] ifFalse:[
-        methodSelector := parser selector.
+	methodSelector := parser selector.
     ].
 
     isClassMethod ifTrue:[
-        className := className , ' class'
+	className := className , ' class'
     ].
 
     change := MethodDefinitionChange new.
-    change 
-        className:className
-        selector:methodSelector
-        source:methodSource
-        category:categoryName
-        privacy:nil.
+    change
+	className:className
+	selector:methodSelector
+	source:methodSource
+	category:categoryName
+	privacy:nil.
 
     self addChange:change.
 
@@ -3473,10 +3475,10 @@
     traitName := (arguments at:1) evaluate.
 
     change := TraitDefinitionChange new.
-    change 
-        className:className,' class';
-        baseTrait:traitName;
-        source:chunk.
+    change
+	className:className,' class';
+	baseTrait:traitName;
+	source:chunk.
 "/ self halt.
     self addChange:change.
     ^ true
@@ -3492,11 +3494,11 @@
     superclassName := SourceFileLoader::SourceFileReader classNameMappingFor:gravelSuperclassName.
 
     change := TraitDefinitionChange new.
-    change 
-        className:className;
-        superClassName:superclassName;
-        baseTrait:traitName;
-        source:chunk.
+    change
+	className:className;
+	superClassName:superclassName;
+	baseTrait:traitName;
+	source:chunk.
 "/ self halt.
     self addChange:change.
     ^ true
@@ -3515,10 +3517,10 @@
     (nameSpace == Smalltalk) ifTrue:[ nameSpace := nil ].
 
     change := ClassDefinitionChange new.
-    change 
-        className:className; 
-        superClassName:superclassName;
-        source:chunk.
+    change
+	className:className;
+	superClassName:superclassName;
+	source:chunk.
 "/ self halt.
     self addChange:change.
     ^ true
@@ -3535,9 +3537,9 @@
     (nameSpace == Smalltalk) ifTrue:[ nameSpace := nil ].
 
     change := TraitDefinitionChange new.
-    change 
-        className:className; 
-        source:chunk.
+    change
+	className:className;
+	source:chunk.
 "/ self halt.
     self addChange:change.
     ^ true
@@ -3571,7 +3573,7 @@
     "given a parse-tree (from parsing some changes source/chunk),
      create changes and evaluate changeAction on each.
      The block is invoked with the change and a lineNumberOrNil as
-     arg; the lineNumber is only valid, if the underlying stream 
+     arg; the lineNumber is only valid, if the underlying stream
      provides line-numbers; otherwise, nil is passed."
 
     |dispatchSelector|
@@ -3579,13 +3581,13 @@
     dispatchSelector := ('process_',(selector copyReplaceAll:$: with:$_)) asSymbol.
 "/ Transcript showCR:dispatchSelector.
     (self respondsTo:dispatchSelector) ifTrue:[
-        ^ self perform:dispatchSelector.
+	^ self perform:dispatchSelector.
     ].
 
     "/ any subclass definiton selector ?
     (Behavior definitionSelectors includes:selector)
     ifTrue:[
-        ^ self handleClassDefinitionChange.
+	^ self handleClassDefinitionChange.
     ].
 
     self error:'unhandled change selector: ',selector.
@@ -3670,40 +3672,40 @@
     | hasWideChars stream lastNameSpace |
 
     hasWideChars := aChangeSet contains:[:each | each source isWideString ].
-    hasWideChars ifTrue:[ 
-        stream := EncodedStream stream: aStream encoder: CharacterEncoder encoderForUTF8.
-        stream nextPutAll: '"{ Encoding: utf8 }"'; cr; cr.
-        stream nextPutAll: '!!'; cr; cr.
-    ] ifFalse:[ 
-        stream := aStream 
+    hasWideChars ifTrue:[
+	stream := EncodedStream stream: aStream encoder: CharacterEncoder encoderForUTF8.
+	stream nextPutAll: '"{ Encoding: utf8 }"'; cr; cr.
+	stream nextPutAll: '!!'; cr; cr.
+    ] ifFalse:[
+	stream := aStream
     ].
 
     lastNameSpace := nil.
 
     aChangeSet do:[:eachChange |
-        eachChange isClassChange ifTrue:[
-            | changeNameSpace |
-
-            changeNameSpace := eachChange nameSpaceName.
-            changeNameSpace ~= lastNameSpace ifTrue:[ 
-                aStream nextPutAll: ('"{ NameSpace: %1 }"' bindWith: changeNameSpace).
-                aStream cr; cr.     
-                stream nextPutLine:'!!'.
-                lastNameSpace := changeNameSpace. 
-            ].
-            eachChange isMethodCodeChange ifTrue:[
-                stream nextPutAll:'!!'; nextPutAll:(eachChange className); nextPutAll:' methodsFor: '.
-                stream nextPutAll:(eachChange methodCategory storeString).
-                stream nextPutLine:'!!'.
-                stream cr.
-                stream nextPutAllAsChunk:(eachChange source).
-                stream nextPutLine:'!! !!'.
-            ] ifFalse:[
-                stream nextPutAll:(eachChange source).
-                stream nextPutLine:'!!'.
-            ].
-        ].
-        aStream cr.
+	eachChange isClassChange ifTrue:[
+	    | changeNameSpace |
+
+	    changeNameSpace := eachChange nameSpaceName.
+	    changeNameSpace ~= lastNameSpace ifTrue:[
+		aStream nextPutAll: ('"{ NameSpace: %1 }"' bindWith: changeNameSpace).
+		aStream cr; cr.
+		stream nextPutLine:'!!'.
+		lastNameSpace := changeNameSpace.
+	    ].
+	    eachChange isMethodCodeChange ifTrue:[
+		stream nextPutAll:'!!'; nextPutAll:(eachChange className); nextPutAll:' methodsFor: '.
+		stream nextPutAll:(eachChange methodCategory storeString).
+		stream nextPutLine:'!!'.
+		stream cr.
+		stream nextPutAllAsChunk:(eachChange source).
+		stream nextPutLine:'!! !!'.
+	    ] ifFalse:[
+		stream nextPutAll:(eachChange source).
+		stream nextPutLine:'!!'.
+	    ].
+	].
+	aStream cr.
     ].
 
     "Created: / 04-02-2014 / 18:51:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -3720,68 +3722,68 @@
     topClassName := nil.
     "Pass 1 - collect classes"
     changeSetBeingSaved do:[:change|
-        | pkg |
-        pkg := change package.
-        packageName isNil ifTrue:[
-            packageName := pkg.
-        ] ifFalse:[
-            "/Just a defensive check...
-            self assert: (pkg isNil or:[pkg = packageName]) description: 'STC does not support multiple packages in source files'.
-        ].
-
-        change isClassDefinitionChange ifTrue:[
-            | nm ns |
-
-
-
-            nm := change className.
-            (nm endsWith:' class') ifFalse:[
-                (classInfos includesKey: nm) ifTrue:[
-                    self error:'Multiple definitions of class ', nm.
-                    ^self.
-                ].
-                classInfos at: nm put: (ClassInfo new name: nm).
-                metaInfos at: nm put: (ClassInfo new name: nm , ' class').
-                change isPrivateClassDefinitionChange ifFalse:[
-                    topClassName notNil ifTrue:[
-                        self error: ('Multiple top class definitions (%1 vs %2)' bindWith: topClassName with: nm).
-                        ^self.
-                    ].
-                    topClassName := nm.
-                    namespaceName := change nameSpaceName.
-
-                ]
-            ]
-        ]
+	| pkg |
+	pkg := change package.
+	packageName isNil ifTrue:[
+	    packageName := pkg.
+	] ifFalse:[
+	    "/Just a defensive check...
+	    self assert: (pkg isNil or:[pkg = packageName]) description: 'STC does not support multiple packages in source files'.
+	].
+
+	change isClassDefinitionChange ifTrue:[
+	    | nm ns |
+
+
+
+	    nm := change className.
+	    (nm endsWith:' class') ifFalse:[
+		(classInfos includesKey: nm) ifTrue:[
+		    self error:'Multiple definitions of class ', nm.
+		    ^self.
+		].
+		classInfos at: nm put: (ClassInfo new name: nm).
+		metaInfos at: nm put: (ClassInfo new name: nm , ' class').
+		change isPrivateClassDefinitionChange ifFalse:[
+		    topClassName notNil ifTrue:[
+			self error: ('Multiple top class definitions (%1 vs %2)' bindWith: topClassName with: nm).
+			^self.
+		    ].
+		    topClassName := nm.
+		    namespaceName := change nameSpaceName.
+
+		]
+	    ]
+	]
     ].
 
     "/ Could be an extension container...
     topClassName isNil ifTrue:[
-        ^self
+	^self
     ].
 
     "Pass 2: fill in infos"
     changeSetBeingSaved do:[:change|
-        change isClassChange ifTrue:[
-            | nm info |
-
-            nm := change className.
-            (nm endsWith: ' class') ifTrue:[
-                info := metaInfos at: (nm copyButLast:(' class' size)).
-            ] ifFalse:[
-                info := classInfos at: nm.
-                "Fill superclass info..."                
-                change isClassDefinitionChange ifTrue:[
-                    | superNm |
-                    superNm := change superClassName.
-                    (classInfos includesKey: superNm) ifTrue:[
-                        info superclass: (classInfos at: superNm).
-                        (metaInfos at: nm) superclass: (classInfos at: superNm).
-                    ].
-                ].
-            ].
-            info addChange: change.
-        ]
+	change isClassChange ifTrue:[
+	    | nm info |
+
+	    nm := change className.
+	    (nm endsWith: ' class') ifTrue:[
+		info := metaInfos at: (nm copyButLast:(' class' size)).
+	    ] ifFalse:[
+		info := classInfos at: nm.
+		"Fill superclass info..."
+		change isClassDefinitionChange ifTrue:[
+		    | superNm |
+		    superNm := change superClassName.
+		    (classInfos includesKey: superNm) ifTrue:[
+			info superclass: (classInfos at: superNm).
+			(metaInfos at: nm) superclass: (classInfos at: superNm).
+		    ].
+		].
+	    ].
+	    info addChange: change.
+	]
     ].
 
     classInfos do:[:info|info namespace: namespaceName].
@@ -3789,10 +3791,10 @@
 
 
     "
-        ChangeSet::ClassSourceWriter new
-            changeSetBeingSaved: (ChangeSet forExistingClass: ChangeSet);
-            analyze;
-            yourself
+	ChangeSet::ClassSourceWriter new
+	    changeSetBeingSaved: (ChangeSet forExistingClass: ChangeSet);
+	    analyze;
+	    yourself
 
     "
 
@@ -3810,11 +3812,11 @@
 
     classInfoNameSz := classInfo name size.
     ^classInfos values select:[:info|
-        info name size > classInfoNameSz and:[
-            (info name startsWith: classInfo name)
-                and:[(info name at:classInfoNameSz + 1) == $:
-                    and:[(info name at:classInfoNameSz + 2) == $:
-                        and:[(info name indexOf: $: startingAt: classInfo name size + 3) == 0]]]]
+	info name size > classInfoNameSz and:[
+	    (info name startsWith: classInfo name)
+		and:[(info name at:classInfoNameSz + 1) == $:
+		    and:[(info name at:classInfoNameSz + 2) == $:
+			and:[(info name indexOf: $: startingAt: classInfo name size + 3) == 0]]]]
     ]
 
     "Created: / 15-03-2012 / 19:31:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -3826,18 +3828,18 @@
 
     classes := self privateClassesOf: classInfo.
     (classes size > 0) ifTrue:[
-        classes := classes asOrderedCollection.
-        classes sort:[:a :b | a name < b name].
-
-        classes topologicalSort:[:a :b |
-            "/ a must come before b iff:
-            "/    b is a subclass of a
-            "/    b has a private class which is a subclass of a
-
-            |mustComeBefore privateClassesOfB|
-            mustComeBefore := (b isSubclassOf:a) or:[b isPrivateClassOf: a].
-            mustComeBefore
-        ].
+	classes := classes asOrderedCollection.
+	classes sort:[:a :b | a name < b name].
+
+	classes topologicalSort:[:a :b |
+	    "/ a must come before b iff:
+	    "/    b is a subclass of a
+	    "/    b has a private class which is a subclass of a
+
+	    |mustComeBefore privateClassesOfB|
+	    mustComeBefore := (b isSubclassOf:a) or:[b isPrivateClassOf: a].
+	    mustComeBefore
+	].
     ].
     ^ classes.
 
@@ -3852,14 +3854,14 @@
 
 !ChangeSet::ClassSourceWriter methodsFor:'source writing'!
 
-fileOut:aChangeSet on:outStreamArg 
+fileOut:aChangeSet on:outStreamArg
     ^ self
-        fileOut: aChangeSet
-        on:outStreamArg 
-        withTimeStamp:false 
-        withInitialize:true 
-        withDefinition:true
-        methodFilter:nil encoder:nil.
+	fileOut: aChangeSet
+	on:outStreamArg
+	withTimeStamp:false
+	withInitialize:true
+	withDefinition:true
+	methodFilter:nil encoder:nil.
 
     "Created: / 04-02-2014 / 18:36:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -3875,16 +3877,16 @@
     self analyze.
 
     encoderOrNil isNil ifTrue:[
-        outStream := outStreamArg.
+	outStream := outStreamArg.
     ] ifFalse:[
-        outStream := EncodedStream stream:outStreamArg encoder:encoderOrNil.
-        outStream nextPutAll:'"{ Encoding: ' , encoderOrNil nameOfEncoding , ' }"'; cr; cr.
+	outStream := EncodedStream stream:outStreamArg encoder:encoderOrNil.
+	outStream nextPutAll:'"{ Encoding: ' , encoderOrNil nameOfEncoding , ' }"'; cr; cr.
     ].
 
     "/ Just a bunch of extensions?
     topClassName isNil ifTrue:[
-        self fileOutMethodsOn: outStream. 
-        ^self.
+	self fileOutMethodsOn: outStream.
+	^self.
     ].
 
     nonMeta := classInfos at: topClassName.
@@ -3906,34 +3908,34 @@
     self generateHeaderWithCopyrightOn:outStream.
 
     stampIt ifTrue:[
-        "/
-        "/ first, a timestamp
-        "/
-        outStream nextPutAll:(Smalltalk timeStamp).
-        outStream nextPutChunkSeparator. 
-        outStream cr; cr.
+	"/
+	"/ first, a timestamp
+	"/
+	outStream nextPutAll:(Smalltalk timeStamp).
+	outStream nextPutChunkSeparator.
+	outStream cr; cr.
     ].
 
     withDefinition ifTrue:[
-        "/
-        "/ then the definition(s)
-        "/
-        self fileOutAllDefinitionsOf:nonMeta on:outStream.
-        "/
-        "/ a comment - if any
-        "/
-
-        (comment := nonMeta comment) notNil ifTrue:[
-            nonMeta printClassNameOn: outStream.
-            outStream nextPutAll:' comment:'.
-            comment comment storeOn: outStream.
-            outStream cr.
-            outStream nextPut:$!!; cr; cr.
-        ].
-        "/
-        "/ ST/X primitive definitions - if any
-        "/
-        self fileOutPrimitiveSpecsOf: nonMeta on:outStream.
+	"/
+	"/ then the definition(s)
+	"/
+	self fileOutAllDefinitionsOf:nonMeta on:outStream.
+	"/
+	"/ a comment - if any
+	"/
+
+	(comment := nonMeta comment) notNil ifTrue:[
+	    nonMeta printClassNameOn: outStream.
+	    outStream nextPutAll:' comment:'.
+	    comment comment storeOn: outStream.
+	    outStream cr.
+	    outStream nextPut:$!!; cr; cr.
+	].
+	"/
+	"/ ST/X primitive definitions - if any
+	"/
+	self fileOutPrimitiveSpecsOf: nonMeta on:outStream.
     ].
 
     "/
@@ -3947,15 +3949,15 @@
     allMetaClassSelectors := meta methodDictionary keys.
     versionSelectors := allMetaClassSelectors select:[:selector | AbstractSourceCodeManager isVersionMethodSelector:selector ].
     versionMethods := versionSelectors collect:[:eachSelector | meta methodDictionary at:eachSelector].
-    extensionVersionSelectors := allMetaClassSelectors select:[:selector | AbstractSourceCodeManager isExtensionsVersionMethodSelector:selector ]. 
+    extensionVersionSelectors := allMetaClassSelectors select:[:selector | AbstractSourceCodeManager isExtensionsVersionMethodSelector:selector ].
     extensionVersionMethods := extensionVersionSelectors collect:[:eachSelector | meta methodDictionary at:eachSelector].
     allVersionMethods := Set new addAll:versionMethods; addAll:extensionVersionMethods; yourself.
 
     collectionOfCategories notNil ifTrue:[
-        "/
-        "/ documentation first (if any), but not the version method
-        "/
-        (collectionOfCategories includes:'documentation') ifTrue:[
+	"/
+	"/ documentation first (if any), but not the version method
+	"/
+	(collectionOfCategories includes:'documentation') ifTrue:[
 
 "/            versionMethods do:[:versionMethod |
 "/                |source|
@@ -3964,35 +3966,35 @@
 "/                (source isEmptyOrNil or:[(source startsWith:nonMeta nameOfOldVersionMethod) not]) ifTrue:[
 "/                    "something bad happend to the classes code"
 "/
-"/                    Class fileOutErrorSignal 
+"/                    Class fileOutErrorSignal
 "/                        raiseRequestWith:aClass
 "/                        errorString:' - bad source for version method (uncompiled class file?): ', (versionMethod displayString)
 "/                ].
 "/            ].
 
-            self fileOutCategory:'documentation' of:meta except:allVersionMethods only:nil methodFilter:methodFilter on:outStream.
-        ].
-
-        "/
-        "/ initialization next (if any)
-        "/
-        (collectionOfCategories includes:'initialization') ifTrue:[
-            self fileOutCategory:'initialization' of:meta methodFilter:methodFilter on:outStream.
-        ].
-
-        "/
-        "/ instance creation next (if any)
-        "/
-        (collectionOfCategories includes:'instance creation') ifTrue:[
-            self fileOutCategory:'instance creation' of:meta methodFilter:methodFilter on:outStream.
-        ].
-        collectionOfCategories do:[:aCategory |
-            ((aCategory ~= 'documentation')
-            and:[(aCategory ~= 'initialization')
-            and:[aCategory ~= 'instance creation']]) ifTrue:[
-                self fileOutCategory:aCategory of:meta methodFilter:methodFilter on:outStream.
-            ]
-        ]
+	    self fileOutCategory:'documentation' of:meta except:allVersionMethods only:nil methodFilter:methodFilter on:outStream.
+	].
+
+	"/
+	"/ initialization next (if any)
+	"/
+	(collectionOfCategories includes:'initialization') ifTrue:[
+	    self fileOutCategory:'initialization' of:meta methodFilter:methodFilter on:outStream.
+	].
+
+	"/
+	"/ instance creation next (if any)
+	"/
+	(collectionOfCategories includes:'instance creation') ifTrue:[
+	    self fileOutCategory:'instance creation' of:meta methodFilter:methodFilter on:outStream.
+	].
+	collectionOfCategories do:[:aCategory |
+	    ((aCategory ~= 'documentation')
+	    and:[(aCategory ~= 'initialization')
+	    and:[aCategory ~= 'instance creation']]) ifTrue:[
+		self fileOutCategory:aCategory of:meta methodFilter:methodFilter on:outStream.
+	    ]
+	]
     ].
 
     "/ if there are any primitive definitions (vw-like ffi-primitives),
@@ -4000,9 +4002,9 @@
     "/ Otherwise, we might have trouble when filing in later, because the types are needed
     "/ for the primitive calls.
     nonMeta methodDictionary keysAndValuesDo:[:sel :m |
-        m isVisualWorksTypedef ifTrue:[
-            self fileOutCategory:m category of:nonMeta except:nil only:(Array with:m) methodFilter:methodFilter on:outStream.
-        ].
+	m isVisualWorksTypedef ifTrue:[
+	    self fileOutCategory:m category of:nonMeta except:nil only:(Array with:m) methodFilter:methodFilter on:outStream.
+	].
     ].
 
     "/
@@ -4010,16 +4012,16 @@
     "/
     collectionOfCategories := nonMeta categories asSortedCollection.
     collectionOfCategories notNil ifTrue:[
-        collectionOfCategories do:[:aCategory |
-            self fileOutCategory:aCategory of:nonMeta methodFilter:methodFilter on:outStream.
-        ]
+	collectionOfCategories do:[:aCategory |
+	    self fileOutCategory:aCategory of:nonMeta methodFilter:methodFilter on:outStream.
+	]
     ].
 
     "/
     "/ any private classes' methods
     "/
     (self privateClassesSortedOf: nonMeta) do:[:aClass |
-        self fileOutAllMethodsOf:aClass on:outStream methodFilter:methodFilter
+	self fileOutAllMethodsOf:aClass on:outStream methodFilter:methodFilter
     ].
 
 
@@ -4027,30 +4029,30 @@
     "/ finally, the previously skipped version method(s) - but NOT the extension version methods
     "/
     versionMethods notEmpty ifTrue: [
-        self fileOutCategory:'documentation' of:meta except:nil only:versionMethods methodFilter:methodFilter on:outStream.
+	self fileOutCategory:'documentation' of:meta except:nil only:versionMethods methodFilter:methodFilter on:outStream.
     ].
 
     initIt ifTrue:[
-        "/
-        "/ optionally an initialize message
-        "/
-        classesImplementingInitialize := OrderedCollection new.
-
-        classInfos values with: metaInfos values do:[:class :meta|
-            (meta includesSelector: #initialize) ifTrue:[
-                classesImplementingInitialize add: class.
-            ]
-        ].
-
-        classesImplementingInitialize size ~~ 0 ifTrue:[
-            classesImplementingInitialize topologicalSort:[:a :b | b isSubclassOf:a].
-            outStream cr.
-            classesImplementingInitialize do:[:eachClass |
-                eachClass printClassNameOn:outStream. outStream nextPutAll:' initialize'.
-                outStream nextPutChunkSeparator.
-                outStream cr.
-            ].
-        ].
+	"/
+	"/ optionally an initialize message
+	"/
+	classesImplementingInitialize := OrderedCollection new.
+
+	classInfos values with: metaInfos values do:[:class :meta|
+	    (meta includesSelector: #initialize) ifTrue:[
+		classesImplementingInitialize add: class.
+	    ]
+	].
+
+	classesImplementingInitialize size ~~ 0 ifTrue:[
+	    classesImplementingInitialize topologicalSort:[:a :b | b isSubclassOf:a].
+	    outStream cr.
+	    classesImplementingInitialize do:[:eachClass |
+		eachClass printClassNameOn:outStream. outStream nextPutAll:' initialize'.
+		outStream nextPutChunkSeparator.
+		outStream cr.
+	    ].
+	].
     ]
 
     "Created: / 15-11-1995 / 12:53:06 / cg"
@@ -4067,14 +4069,14 @@
 
     definition := nonMetaInfo definition.
     definition isPrivateClassDefinitionChange ifFalse:[
-        definition package notNil ifTrue:[
-            aStream nextPutAll: ('"{ Package: ''%1'' }"' bindWith: definition package).
-            aStream cr; cr.
-        ].
-        namespaceName notNil ifTrue:[
-            aStream nextPutAll: ('"{ NameSpace: %1 }"' bindWith: namespaceName).
-            aStream cr; cr.
-        ].
+	definition package notNil ifTrue:[
+	    aStream nextPutAll: ('"{ Package: ''%1'' }"' bindWith: definition package).
+	    aStream cr; cr.
+	].
+	namespaceName notNil ifTrue:[
+	    aStream nextPutAll: ('"{ NameSpace: %1 }"' bindWith: namespaceName).
+	    aStream cr; cr.
+	].
     ].
 
     aStream nextChunkPut: (definition definitionStringInNamespace: namespaceName).
@@ -4086,50 +4088,50 @@
     metaInfo := metaInfos at: nonMetaInfo name.
     metaDefinition := metaInfo definition.
     metaDefinition notNil ifTrue:[
-        | anySuperClassInstVar myClass |
-        aStream 
-            nextPutAll: metaDefinition className; 
-            nextPutAll:' instanceVariableNames:';
-            nextPutAll: (metaDefinition classInstVarNames asStringWith:' ') storeString.
-        "mhmh - good idea; saw this in SmallDraw sourcecode ..."
-
-        anySuperClassInstVar := false.
-        myClass := metaDefinition changeClass.
-        myClass notNil ifTrue:[myClass := myClass theNonMetaclass].
-        myClass notNil ifTrue:[
-            myClass allSuperclassesDo:[:aSuperClass |
-                aSuperClass class instVarNames do:[:ignored | anySuperClassInstVar := true].
-            ].
-
-            aStream cr; cr; nextPut:(Character doubleQuote); cr; space.
-            anySuperClassInstVar ifFalse:[
-                aStream
-                    nextPutLine:'No other class instance variables are inherited by this class.'.
-            ] ifTrue:[
-                aStream
-                    nextPutLine:'The following class instance variables are inherited by this class:'.
-                aStream cr.
-                myClass allSuperclassesDo:[:aSuperClass |
-                    aStream tab; nextPutAll:aSuperClass name; nextPutAll:' - '.
-                    aStream nextPutLine:(aSuperClass class instanceVariableString).
-                ].
-
-            ].
-        ].
-        aStream nextPut:(Character doubleQuote); cr.
-        aStream nextPut:$!!; cr; cr
+	| anySuperClassInstVar myClass |
+	aStream
+	    nextPutAll: metaDefinition className;
+	    nextPutAll:' instanceVariableNames:';
+	    nextPutAll: (metaDefinition classInstVarNames asStringWith:' ') storeString.
+	"mhmh - good idea; saw this in SmallDraw sourcecode ..."
+
+	anySuperClassInstVar := false.
+	myClass := metaDefinition changeClass.
+	myClass notNil ifTrue:[myClass := myClass theNonMetaclass].
+	myClass notNil ifTrue:[
+	    myClass allSuperclassesDo:[:aSuperClass |
+		aSuperClass class instVarNames do:[:ignored | anySuperClassInstVar := true].
+	    ].
+
+	    aStream cr; cr; nextPut:(Character doubleQuote); cr; space.
+	    anySuperClassInstVar ifFalse:[
+		aStream
+		    nextPutLine:'No other class instance variables are inherited by this class.'.
+	    ] ifTrue:[
+		aStream
+		    nextPutLine:'The following class instance variables are inherited by this class:'.
+		aStream cr.
+		myClass allSuperclassesDo:[:aSuperClass |
+		    aStream tab; nextPutAll:aSuperClass name; nextPutAll:' - '.
+		    aStream nextPutLine:(aSuperClass class instanceVariableString).
+		].
+
+	    ].
+	].
+	aStream nextPut:(Character doubleQuote); cr.
+	aStream nextPut:$!!; cr; cr
     ].
 
     "/ here, the full nameSpace prefixes are output,
-    "/ to avoid confusing stc 
+    "/ to avoid confusing stc
     "/ (which otherwise could not find the correct superclass)
     "/
     Class fileOutNameSpaceQuerySignal answer:false do:[
-        Class forceNoNameSpaceQuerySignal answer:true do:[
-            (self privateClassesSortedOf: nonMetaInfo) do:[:i |
-                 self fileOutAllDefinitionsOf:i on:aStream
-            ]
-        ]
+	Class forceNoNameSpaceQuerySignal answer:true do:[
+	    (self privateClassesSortedOf: nonMetaInfo) do:[:i |
+		 self fileOutAllDefinitionsOf:i on:aStream
+	    ]
+	]
     ].
 
     "Created: / 15-10-1996 / 11:15:19 / cg"
@@ -4145,21 +4147,21 @@
 
     collectionOfCategories := meta categories asSortedCollection.
     collectionOfCategories notNil ifTrue:[
-        collectionOfCategories do:[:aCategory |
-            self fileOutCategory:aCategory of:meta  methodFilter:methodFilter on:aStream.
+	collectionOfCategories do:[:aCategory |
+	    self fileOutCategory:aCategory of:meta  methodFilter:methodFilter on:aStream.
 "/            aStream cr.
-        ]
+	]
     ].
     collectionOfCategories := aClass categories asSortedCollection.
     collectionOfCategories notNil ifTrue:[
-        collectionOfCategories do:[:aCategory |
-            self fileOutCategory:aCategory of:aClass methodFilter:methodFilter on:aStream.
+	collectionOfCategories do:[:aCategory |
+	    self fileOutCategory:aCategory of:aClass methodFilter:methodFilter on:aStream.
 "/            aStream cr.
-        ]
+	]
     ].
 
     (self privateClassesSortedOf: aClass) do:[:privateClass |
-        self fileOutAllMethodsOf:privateClass on:aStream methodFilter:methodFilter
+	self fileOutAllMethodsOf:privateClass on:aStream methodFilter:methodFilter
     ].
 
     "Created: / 15-10-1996 / 11:13:00 / cg"
@@ -4174,14 +4176,14 @@
     | changeToFileOut |
 
     change isMethodCategoryChange ifTrue:[
-        self assert: change origin notNil.
-        changeToFileOut := change origin copy.
-        changeToFileOut category: change category.
+	self assert: change origin notNil.
+	changeToFileOut := change origin copy.
+	changeToFileOut category: change category.
     ] ifFalse:[
-        changeToFileOut := change.
+	changeToFileOut := change.
     ].
     changeToFileOut source notEmptyOrNil ifTrue:[
-        super fileOutMethod:changeToFileOut on:aStream
+	super fileOutMethod:changeToFileOut on:aStream
     ] ifFalse:[
 "/        self error: 'Should not happen' mayProceed: true.
     ]
@@ -4199,65 +4201,65 @@
     | methodsSortedByName |
 
 
-        stream nextPutAll:'"{ Package: '''.
-        stream nextPutAll:packageName asString.
-        stream nextPutAll:''' }"'; nextPutChunkSeparator; cr; cr.
+	stream nextPutAll:'"{ Package: '''.
+	stream nextPutAll:packageName asString.
+	stream nextPutAll:''' }"'; nextPutChunkSeparator; cr; cr.
 
 "/        s nextPutAll:(Smalltalk timeStamp).
-"/        s nextPutChunkSeparator. 
+"/        s nextPutChunkSeparator.
 "/        s cr; cr.
 
-        "/ sort them by name (to avoid conflict due to CVS merge)
-        methodsSortedByName := changeSetBeingSaved.
-        methodsSortedByName sort:[:a :b |
-                                    |clsA clsB|
-
-                                    clsA := a className.
-                                    clsB := b className.
-                                    clsA < clsB ifTrue:[
-                                        true
-                                    ] ifFalse:[
-                                        clsA > clsB ifTrue:[
-                                            false
-                                        ] ifFalse:[
-                                            a selector < b selector
-                                        ]
-                                    ]
-                                  ].
-        methodsSortedByName do:[:aMethod |
-            |cat source privacy|
-
-            self assert: aMethod package = packageName.
-            "/self assert: aMethod programmingLanguage isSmalltalk.
-
-
-            stream nextPutChunkSeparator.
-            aMethod className printOn: stream.
-
-            (privacy := aMethod privacy) ~~ #public ifTrue:[
-                stream space; nextPutAll:privacy; nextPutAll:'MethodsFor:'.
-            ] ifFalse:[
-                stream nextPutAll:' methodsFor:'.
-            ].
-
-            cat := aMethod category ? ''.
-            stream nextPutAll:cat asString storeString.
-            stream nextPutChunkSeparator; cr; cr.
-
-            source := aMethod source.
-            source isNil ifTrue:[
-                "FileOutErrorSignal"Error
-                    raiseRequestWith:self
-                    errorString:(' - no source for method: ' ,
-                                 self className , '>>' ,
-                                 aMethod selector)
-            ] ifFalse:[
-                stream nextChunkPut:source.
-            ].
-            stream space.
-            stream nextPutChunkSeparator.
-            stream cr.
-        ].
+	"/ sort them by name (to avoid conflict due to CVS merge)
+	methodsSortedByName := changeSetBeingSaved.
+	methodsSortedByName sort:[:a :b |
+				    |clsA clsB|
+
+				    clsA := a className.
+				    clsB := b className.
+				    clsA < clsB ifTrue:[
+					true
+				    ] ifFalse:[
+					clsA > clsB ifTrue:[
+					    false
+					] ifFalse:[
+					    a selector < b selector
+					]
+				    ]
+				  ].
+	methodsSortedByName do:[:aMethod |
+	    |cat source privacy|
+
+	    self assert: aMethod package = packageName.
+	    "/self assert: aMethod programmingLanguage isSmalltalk.
+
+
+	    stream nextPutChunkSeparator.
+	    aMethod className printOn: stream.
+
+	    (privacy := aMethod privacy) ~~ #public ifTrue:[
+		stream space; nextPutAll:privacy; nextPutAll:'MethodsFor:'.
+	    ] ifFalse:[
+		stream nextPutAll:' methodsFor:'.
+	    ].
+
+	    cat := aMethod category ? ''.
+	    stream nextPutAll:cat asString storeString.
+	    stream nextPutChunkSeparator; cr; cr.
+
+	    source := aMethod source.
+	    source isNil ifTrue:[
+		"FileOutErrorSignal"Error
+		    raiseRequestWith:self
+		    errorString:(' - no source for method: ' ,
+				 self className , '>>' ,
+				 aMethod selector)
+	    ] ifFalse:[
+		stream nextChunkPut:source.
+	    ].
+	    stream space.
+	    stream nextPutChunkSeparator.
+	    stream cr.
+	].
 
     "Created: / 30-01-2013 / 09:35:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -4271,22 +4273,22 @@
      primitive definitions - if any
     "
     (s := nonMeta primitiveDefinitionsString) notNil ifTrue:[
-        aStream nextPutChunkSeparator.
-        nonMeta printClassNameOn:aStream.
-        aStream nextPutAll:' primitiveDefinitions';
-                nextPutChunkSeparator;
-                cr.
-        aStream nextPutAll:s.
-        aStream nextPutChunkSeparator; space; nextPutChunkSeparator; cr; cr
+	aStream nextPutChunkSeparator.
+	nonMeta printClassNameOn:aStream.
+	aStream nextPutAll:' primitiveDefinitions';
+		nextPutChunkSeparator;
+		cr.
+	aStream nextPutAll:s.
+	aStream nextPutChunkSeparator; space; nextPutChunkSeparator; cr; cr
     ].
     (s := nonMeta primitiveVariablesString) notNil ifTrue:[
-        aStream nextPutChunkSeparator.
-        nonMeta printClassNameOn:aStream.
-        aStream nextPutAll:' primitiveVariables';
-                nextPutChunkSeparator;
-                cr.
-        aStream nextPutAll:s.
-        aStream nextPutChunkSeparator; space; nextPutChunkSeparator; cr; cr
+	aStream nextPutChunkSeparator.
+	nonMeta printClassNameOn:aStream.
+	aStream nextPutAll:' primitiveVariables';
+		nextPutChunkSeparator;
+		cr.
+	aStream nextPutAll:s.
+	aStream nextPutChunkSeparator; space; nextPutChunkSeparator; cr; cr
     ].
 
     "Created: / 15-03-2012 / 19:48:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -4296,26 +4298,26 @@
     |copyrightChange copyrightText|
 
     copyrightChange :=
-        (metaInfos at: topClassName) methodAt: #copyright.
+	(metaInfos at: topClassName) methodAt: #copyright.
 
 
     copyrightChange notNil ifTrue:[
-        "
-         get the copyright method's comment-text, strip off empty and blank lines
-         and insert at beginning.
-        "
-        copyrightText := Parser methodCommentFromSource: copyrightChange source.
-        copyrightText notEmptyOrNil ifTrue:[
-            copyrightText := copyrightText asCollectionOfLines asStringCollection.
-            copyrightText := copyrightText withoutLeadingBlankLines.
-            copyrightText := copyrightText withoutTrailingBlankLines.
-            copyrightText notEmpty ifTrue:[
-                copyrightText addFirst:'"'.
-                copyrightText addLast:'"'.
-                copyrightText := copyrightText asString.
-                outStream nextPutAllAsChunk:copyrightText.
-            ].
-        ].
+	"
+	 get the copyright method's comment-text, strip off empty and blank lines
+	 and insert at beginning.
+	"
+	copyrightText := Parser methodCommentFromSource: copyrightChange source.
+	copyrightText notEmptyOrNil ifTrue:[
+	    copyrightText := copyrightText asCollectionOfLines asStringCollection.
+	    copyrightText := copyrightText withoutLeadingBlankLines.
+	    copyrightText := copyrightText withoutTrailingBlankLines.
+	    copyrightText notEmpty ifTrue:[
+		copyrightText addFirst:'"'.
+		copyrightText addLast:'"'.
+		copyrightText := copyrightText asString.
+		outStream nextPutAllAsChunk:copyrightText.
+	    ].
+	].
     ].
 
     "Created: / 15-03-2012 / 19:01:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -4326,7 +4328,7 @@
 copyright
 "
  COPYRIGHT (c) 2006 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
@@ -4338,7 +4340,7 @@
 !
 
 version_SVN
-    ^ '$Id: ChangeSet.st,v 1.259 2015-03-23 15:16:00 cg Exp $'
+    ^ '$Id: ChangeSet.st,v 1.260 2015-04-07 10:37:39 cg Exp $'
 ! !
 
 !ChangeSet::ClassSourceWriter::ClassInfo class methodsFor:'instance creation'!
@@ -4374,7 +4376,7 @@
     definition := something.
 !
 
-methodAt: selector 
+methodAt: selector
     ^methods detect:[:each|each selector == selector] ifNone:[nil].
 
     "Created: / 15-03-2012 / 19:11:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -4383,7 +4385,7 @@
 methodDictionary
 
     methodDictionary isNil ifTrue:[
-        methodDictionary := Dictionary new.
+	methodDictionary := Dictionary new.
     ].
     ^methodDictionary
 
@@ -4423,9 +4425,9 @@
 !
 
 primitiveDefinitionsString
-    ^ primitiveDefinitions isNil 
-        ifTrue:[nil]
-        ifFalse:[primitiveDefinitions source]
+    ^ primitiveDefinitions isNil
+	ifTrue:[nil]
+	ifFalse:[primitiveDefinitions source]
 
     "Created: / 13-04-2012 / 13:14:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -4435,9 +4437,9 @@
 !
 
 primitiveFunctionsString
-    ^ primitiveFunctions isNil 
-        ifTrue:[nil]
-        ifFalse:[primitiveFunctions source]
+    ^ primitiveFunctions isNil
+	ifTrue:[nil]
+	ifFalse:[primitiveFunctions source]
 
     "Created: / 13-04-2012 / 13:15:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -4447,9 +4449,9 @@
 !
 
 primitiveVariablesString
-    ^ primitiveVariables isNil 
-        ifTrue:[nil]
-        ifFalse:[primitiveVariables source]
+    ^ primitiveVariables isNil
+	ifTrue:[nil]
+	ifFalse:[primitiveVariables source]
 
     "Created: / 13-04-2012 / 13:15:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -4473,50 +4475,50 @@
 addChange: change
 
     change isClassDefinitionChange ifTrue:[
-        self assert: definition isNil.
-        definition := change.
-        ^self.
+	self assert: definition isNil.
+	definition := change.
+	^self.
     ].
     change isMethodCodeChange ifTrue:[
-        methods add: change.
-        ^self.
+	methods add: change.
+	^self.
     ].
     change isMethodCategoryChange ifTrue:[
-        methods add: change.
-        ^self.
+	methods add: change.
+	^self.
     ].
 
     change isClassInstVarDefinitionChange ifTrue:[
-        self assert: definition isNil.
-        definition := change.
-        ^self
+	self assert: definition isNil.
+	definition := change.
+	^self
     ].
 
     change isPrimitiveDefinitionsChange ifTrue:[
-        primitiveDefinitions := change.
-        ^self
+	primitiveDefinitions := change.
+	^self
     ].
 
     change isPrimitiveVariablesChange ifTrue:[
-        primitiveVariables := change.
-        ^self
+	primitiveVariables := change.
+	^self
     ].
 
     change isPrimitiveFunctionsChange ifTrue:[
-        primitiveFunctions := change.
-        ^self
+	primitiveFunctions := change.
+	^self
     ].
 
     change isClassCommentChange ifTrue:[
-        comment := change.
-        ^self
+	comment := change.
+	^self
     ].
 
-    change isClassInitializeChange ifTrue:[ 
-        "/ Ignore it, the class inititalization chunk is
-        "/ written fileOut:on:withTimeStamp:withInitialize:withDefinition:methodFilter:encoder:
-        "/ for all class implementing class-side #initialize
-        ^ self
+    change isClassInitializeChange ifTrue:[
+	"/ Ignore it, the class inititalization chunk is
+	"/ written fileOut:on:withTimeStamp:withInitialize:withDefinition:methodFilter:encoder:
+	"/ for all class implementing class-side #initialize
+	^ self
     ].
 
     self error: 'Unknown change'
@@ -4590,8 +4592,8 @@
 isPrivateClassOf: classInfo
 
     ^(name startsWith: classInfo name)
-        and:[ (name at: (classInfo name size + 1)) == $:
-            and:[ (name at: (classInfo name size + 2)) == $:]]
+	and:[ (name at: (classInfo name size + 1)) == $:
+	    and:[ (name at: (classInfo name size + 2)) == $:]]
 
     "Created: / 15-03-2012 / 19:42:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -4599,7 +4601,7 @@
 isSubclassOf: classInfo
 
     ^superclass notNil and:
-        [superclass == classInfo or:[superclass isSubclassOf: classInfo]]
+	[superclass == classInfo or:[superclass isSubclassOf: classInfo]]
 
     "Created: / 15-03-2012 / 19:41:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
@@ -4631,7 +4633,7 @@
     "Modified: / 12-10-2006 / 22:06:03 / cg"
 !
 
-changed:changedArg onlyInReceiver:onlyInReceiverArg onlyInArg:onlyInArgArg 
+changed:changedArg onlyInReceiver:onlyInReceiverArg onlyInArg:onlyInArgArg
     self changed:changedArg onlyInReceiver:onlyInReceiverArg onlyInArg:onlyInArgArg same:nil
 !
 
@@ -4699,10 +4701,10 @@
 
 copy
     ^ self class new
-        changed:changed copy
-        onlyInReceiver:onlyInReceiver copy
-        onlyInArg:onlyInArg copy
-        same:same copy
+	changed:changed copy
+	onlyInReceiver:onlyInReceiver copy
+	onlyInArg:onlyInArg copy
+	same:same copy
 
     "Created: / 12-10-2006 / 22:50:56 / cg"
     "Modified: / 19-03-2012 / 21:36:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -4711,18 +4713,18 @@
 !ChangeSet::DiffSet methodsFor:'misc'!
 
 removeAllVersionMethods
-    changed := changed 
-                    reject:[:pair |
-                        pair first isMethodChangeForVersionMethod
-                    ].
-    onlyInReceiver := onlyInReceiver 
-                    reject:[:chg |
-                        chg isMethodChangeForVersionMethod
-                    ].
-    onlyInArg := onlyInArg 
-                    reject:[:chg |
-                        chg isMethodChangeForVersionMethod
-                    ].
+    changed := changed
+		    reject:[:pair |
+			pair first isMethodChangeForVersionMethod
+		    ].
+    onlyInReceiver := onlyInReceiver
+		    reject:[:chg |
+			chg isMethodChangeForVersionMethod
+		    ].
+    onlyInArg := onlyInArg
+		    reject:[:chg |
+			chg isMethodChangeForVersionMethod
+		    ].
 ! !
 
 !ChangeSet::DiffSet methodsFor:'queries'!
@@ -4733,9 +4735,9 @@
     allChangedClasses := Set new.
     allChangedClasses addAll:(onlyInArg changedClasses).
     allChangedClasses addAll:(onlyInReceiver changedClasses).
-    changed do:[:eachChangePair | 
-        allChangedClasses add:(eachChangePair first changeClass).
-        allChangedClasses add:(eachChangePair second changeClass).
+    changed do:[:eachChangePair |
+	allChangedClasses add:(eachChangePair first changeClass).
+	allChangedClasses add:(eachChangePair second changeClass).
     ].
     allChangedClasses remove:nil ifAbsent:[].
     ^ allChangedClasses
@@ -4761,16 +4763,16 @@
     |category change|
 
     [
-        inputStream skipSeparators.
-        category := inputStream nextChunk.
-        category notEmpty
+	inputStream skipSeparators.
+	category := inputStream nextChunk.
+	category notEmpty
     ] whileTrue:[
-        change := ClassCategoryChange new.
-        change 
-            className:className
-            category:category.
-
-        self addChange:change.
+	change := ClassCategoryChange new.
+	change
+	    className:className
+	    category:category.
+
+	self addChange:change.
     ].
     ^ true
 !
@@ -4784,23 +4786,23 @@
 
     categories := OrderedCollection new.
     [
-        |done category |
-
-        category := inputStream nextChunk withoutSeparators.
-        done := category isEmpty.
-        done ifFalse:[
-            categories add:category
-        ].
-        done
+	|done category |
+
+	category := inputStream nextChunk withoutSeparators.
+	done := category isEmpty.
+	done ifFalse:[
+	    categories add:category
+	].
+	done
     ] whileFalse.
 
     categories size > 1 ifTrue:[
-        isPrivate := categories includes:'private'.
-        categories remove:'private' ifAbsent:nil.
+	isPrivate := categories includes:'private'.
+	categories remove:'private' ifAbsent:nil.
     ].
     categories size > 1 ifTrue:[
-        isPublic := categories includes:'public'.
-        categories remove:'public' ifAbsent:nil.
+	isPublic := categories includes:'public'.
+	categories remove:'public' ifAbsent:nil.
     ].
 "/    categories size > 1 ifTrue:[
 "/        self halt.
@@ -4808,14 +4810,14 @@
 
     category := categories first.
     isPrivate ifTrue:[
-        category := category , '-private'. 
+	category := category , '-private'.
     ].
 
     change := MethodCategoryChange new.
-    change 
-        className:className
-        selector:methodSelector
-        category:category.
+    change
+	className:className
+	selector:methodSelector
+	category:category.
 
     self addChange:change.
     ^ true
@@ -4825,17 +4827,17 @@
     "given a parse-tree (from parsing some changes source/chunk),
      create changes and evaluate changeAction on each.
      The block is invoked with the change and a lineNumberOrNil as
-     arg; the lineNumber is only valid, if the underlying stream 
+     arg; the lineNumber is only valid, if the underlying stream
      provides line-numbers; otherwise, nil is passed."
 
     (selector == #'categoriesForClass') ifTrue:[
-        ^ self handleCategoriesForClass.
+	^ self handleCategoriesForClass.
     ].
     (selector == #'categoriesFor:') ifTrue:[
-        ^ self handleCategoriesForMethod.
+	^ self handleCategoriesForMethod.
     ].
     selector == #'subclass:instanceVariableNames:classVariableNames:poolDictionaries:classInstanceVariableNames:' ifTrue:[
-        ^ self handleClassDefinitionChange.
+	^ self handleClassDefinitionChange.
     ].
 "/    selector == #'guid:' ifTrue:[
 "/        ^ self handleGUIDChange.
@@ -4889,25 +4891,25 @@
     key = 'Prerequisite' ifTrue:[
 "/        change := SIFPrerequisiteChange new prerequisiteFileName:value.
 "/        self addChange:change.
-        ^ true
+	^ true
     ].
 
     lastChange := changeSet last.
 
     key = 'package' ifTrue:[
-        change := ClassCategoryChange new className:(lastChange className) category:value.
-        self addChange:change.
-        ^ true
+	change := ClassCategoryChange new className:(lastChange className) category:value.
+	self addChange:change.
+	^ true
     ].
     key = 'category' ifTrue:[
 "/        change := MethodCategoryChange new className:(lastChange className) selector:(lastChange selector) category:value.
 "/        self addChange:change.
-        lastChange category:value.
-        ^ true
+	lastChange category:value.
+	^ true
     ].
     key = 'stamp' ifTrue:[
-        "/ lastChange timeStamp:value.
-        ^ true
+	"/ lastChange timeStamp:value.
+	^ true
     ].
     ^ false
 !
@@ -4916,14 +4918,14 @@
     |nameSpace change|
 
     (self checkReceiverIsGlobalNamed:#Class) ifFalse:[
-        self error:'unexpected receiver in classDefinition message' mayProceed:true.
-        ^ false.
+	self error:'unexpected receiver in classDefinition message' mayProceed:true.
+	^ false.
     ].
     className := (arguments at:1) evaluate.
 
     nameSpace := Class nameSpaceQuerySignal query.
     nameSpace ~~ Smalltalk ifTrue:[
-        className := nameSpace name , '::' , className
+	className := nameSpace name , '::' , className
     ].
 
     change := ClassDefinitionChange new.
@@ -4939,7 +4941,7 @@
 
     className := self receiversClassName.
     isMeta ifTrue:[
-        className := className , ' class'
+	className := className , ' class'
     ].
 
     categoryName := 'uncategorized'.
@@ -4951,26 +4953,26 @@
     methodSource := inputStream nextChunk.
 
     parser := Parser
-                parseMethodArgAndVarSpecification:methodSource 
-                in:nil 
-                ignoreErrors:true 
-                ignoreWarnings:true
-                parseBody:false.
+		parseMethodArgAndVarSpecification:methodSource
+		in:nil
+		ignoreErrors:true
+		ignoreWarnings:true
+		parseBody:false.
 
     parser isNil ifTrue:[
-        "/ something wierd ...
-        methodSelector := '????'.
+	"/ something wierd ...
+	methodSelector := '????'.
     ] ifFalse:[
-        methodSelector := parser selector.
+	methodSelector := parser selector.
     ].
 
     change := MethodDefinitionChange new.
-    change 
-        className:className
-        selector:methodSelector
-        source:methodSource
-        category:categoryName
-        privacy:nil.
+    change
+	className:className
+	selector:methodSelector
+	source:methodSource
+	category:categoryName
+	privacy:nil.
 
     self addChange:change.
     ^ true
@@ -4980,32 +4982,32 @@
     "given a parse-tree (from parsing some changes source/chunk),
      create changes and evaluate changeAction on each.
      The block is invoked with the change and a lineNumberOrNil as
-     arg; the lineNumber is only valid, if the underlying stream 
+     arg; the lineNumber is only valid, if the underlying stream
      provides line-numbers; otherwise, nil is passed."
 
     (selector == #'interchangeVersion:') ifTrue:[
-        ^ true
+	^ true
     ].
     selector == #named:superclass:indexedInstanceVariables:instanceVariableNames:classVariableNames:sharedPools:classInstanceVariableNames: ifTrue:[
-        ^ self handleClassDefinitionChange.
+	^ self handleClassDefinitionChange.
     ].
     (selector == #'key:value:') ifTrue:[
-        (self checkReceiverIsGlobalNamed:'Annotation') ifTrue:[
-            ^ self handleAnnotation.
-        ]
+	(self checkReceiverIsGlobalNamed:'Annotation') ifTrue:[
+	    ^ self handleAnnotation.
+	]
     ].
     selector == #'method' ifTrue:[
-        ^ self handleMethodChange:false.
+	^ self handleMethodChange:false.
     ].
     selector == #'classMethod' ifTrue:[
-        ^ self handleMethodChange:true.
+	^ self handleMethodChange:true.
     ].
 
     selector == #'initializer' ifTrue:[
-        ^ true
+	^ true
     ].
     selector == #'initialize' ifTrue:[
-        ^ true
+	^ true
     ].
 
     ^ false
@@ -5017,11 +5019,11 @@
 !ChangeSet class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/ChangeSet.st,v 1.259 2015-03-23 15:16:00 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic3/ChangeSet.st,v 1.260 2015-04-07 10:37:39 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic3/ChangeSet.st,v 1.259 2015-03-23 15:16:00 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic3/ChangeSet.st,v 1.260 2015-04-07 10:37:39 cg Exp $'
 !
 
 version_HG
@@ -5030,6 +5032,5 @@
 !
 
 version_SVN
-    ^ '$Id: ChangeSet.st,v 1.259 2015-03-23 15:16:00 cg Exp $'
+    ^ '$Id: ChangeSet.st,v 1.260 2015-04-07 10:37:39 cg Exp $'
 ! !
-