revised
authortz
Tue, 14 Apr 1998 21:14:54 +0200
changeset 1546 ffea21e237ed
parent 1545 e2d6f6ca36ef
child 1547 c0798d0ca18e
revised
NewChangesBrowser.st
--- a/NewChangesBrowser.st	Tue Apr 14 15:08:18 1998 +0200
+++ b/NewChangesBrowser.st	Tue Apr 14 21:14:54 1998 +0200
@@ -1,9 +1,8 @@
 ToolApplicationModel subclass:#NewChangesBrowser
-	instanceVariableNames:'changes changeFileName skipSignal compareChanges
-		changeFileTimestamp modified autoUpdateBlock editingClassSource
-		filterCompletionBlock'
+	instanceVariableNames:'changes changeFileName skipSignal changeFileTimestamp
+		autoUpdateBlock filterCompletionBlock editingClassSource modified'
 	classVariableNames:'AutoUpdate CompressSnapshotInfo CategoryColumn DeltaInfoColumn
-		TypeColumn TimeStampColumn PositionColumn'
+		TypeColumn TimeStampColumn PositionColumn PrivateAsSeparate'
 	poolDictionaries:''
 	category:'Interface-Browsers'
 !
@@ -36,17 +35,18 @@
 !NewChangesBrowser class methodsFor:'instance creation'!
 
 openOnFile:aFileName
-    "create c changes browser on a change file"
-
-    ^ ((self new label:(self label , ': ', aFileName)) 
-        changeFileName:aFileName) open
+    "opens a Changes Browser with the changes of the aFileName"
+
+    ^self new 
+        changeFileName:aFileName;
+        open
 
 ! !
 
 !NewChangesBrowser class methodsFor:'accessing'!
 
 autoSelectNext
-    "returning true here, makes a Delete operation automatically
+    "returns true here, makes a Delete operation automatically
      select the next change"
 
     ^ true
@@ -55,6 +55,7 @@
 !
 
 label
+    "returns my label"
 
     ^'Changes Browser'
 ! !
@@ -91,6 +92,9 @@
 #applyToEnd
 'Apply all changes from the selected one up to the last made change.'
 
+#deleteAll
+'Deletes all changes from the first one to the last made change.'
+
 #deleteCompress
 'Deletes all multiple changes but leaving the last one.'
 
@@ -136,6 +140,9 @@
 #settingsColumnsType
 'Turns on/off whether a column for the type of the change is shown by the table.'
 
+#settingsPrivateAsSeparate
+'Turns on/off that private classes are separately handled when applying, deleting, or compressing for a certain class.'
+
 #testCompareWithCurrentVersion
 'Opens a info dialog showing the compare results between the method code of the selected change with the current code.'
 
@@ -309,11 +316,11 @@
           #window: 
            #(#WindowSpec
               #name: ''
-              #layout: #(#LayoutFrame 329 0 181 0 828 0 580 0)
+              #layout: #(#LayoutFrame 257 0 290 0 756 0 689 0)
               #label: ''
               #min: #(#Point 10 10)
               #max: #(#Point 1152 900)
-              #bounds: #(#Rectangle 329 181 829 581)
+              #bounds: #(#Rectangle 257 290 757 690)
               #menu: #menu
               #usePreferredExtent: false
           )
@@ -375,7 +382,6 @@
                                                   #layout: #(#LayoutFrame 41 0.0 3 0 285 0 25 0)
                                                   #model: #valueOfFilter
                                                   #immediateAccept: false
-                                                  #acceptOnReturn: false
                                               )
                                                #(#ProgressIndicatorSpec
                                                   #name: 'readProgressIndicator'
@@ -625,24 +631,33 @@
                           #enabled: #valueOfHavingChangeSelection
                       )
                        #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'All'
+                          #value: #doApplyAll
+                          #activeHelpKey: #applyAll
+                          #enabled: #valueOfNotReading
+                      )
+                       #(#MenuItem
                           #label: 'To End'
                           #value: #doApplyToEnd
                           #activeHelpKey: #applyToEnd
                           #enabled: #valueOfHavingSelection
                       )
                        #(#MenuItem
+                          #label: 'All For Class'
+                          #value: #doApplyAllForClass
+                          #activeHelpKey: #applyForClassToEnd
+                          #enabled: #valueOfHavingChangeSelection
+                      )
+                       #(#MenuItem
                           #label: 'For Class To End'
                           #value: #doApplyForClassToEnd
                           #activeHelpKey: #applyForClassToEnd
                           #enabled: #valueOfHavingChangeSelection
                       )
                        #(#MenuItem
-                          #label: 'All'
-                          #value: #doApplyAll
-                          #activeHelpKey: #applyAll
-                          #enabled: #valueOfNotReading
-                      )
-                       #(#MenuItem
                           #label: '-'
                       )
                        #(#MenuItem
@@ -669,12 +684,27 @@
                           #enabled: #valueOfHavingSelection
                       )
                        #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
+                          #label: 'All'
+                          #value: #doDeleteAll
+                          #activeHelpKey: #deleteAll
+                          #enabled: #valueOfNotReading
+                      )
+                       #(#MenuItem
                           #label: 'To End'
                           #value: #doDeleteToEnd
                           #activeHelpKey: #deleteToEnd
                           #enabled: #valueOfHavingSelection
                       )
                        #(#MenuItem
+                          #label: 'All For Class'
+                          #value: #doDeleteAllForClass
+                          #activeHelpKey: #applyForClassToEnd
+                          #enabled: #valueOfHavingChangeSelection
+                      )
+                       #(#MenuItem
                           #label: 'For Class To End'
                           #value: #doDeleteForClassToEnd
                           #activeHelpKey: #deleteForClassToEnd
@@ -750,6 +780,15 @@
                           #label: '-'
                       )
                        #(#MenuItem
+                          #label: 'Private As Separate'
+                          #activeHelpKey: #settingsPrivateAsSeparate
+                          #enabled: #valueOfNotReading
+                          #indication: #privateAsSeparate:
+                      )
+                       #(#MenuItem
+                          #label: '-'
+                      )
+                       #(#MenuItem
                           #label: 'Columns'
                           #activeHelpKey: #settingsColumns
                           #submenu: 
@@ -840,6 +879,12 @@
                 #enabled: #valueOfHavingSelection
             )
              #(#MenuItem
+                #label: 'Apply All For Class'
+                #value: #doApplyAllForClass
+                #activeHelpKey: #applyForClassToEnd
+                #enabled: #valueOfHavingChangeSelection
+            )
+             #(#MenuItem
                 #label: 'Apply For Class To End'
                 #value: #doApplyForClassToEnd
                 #activeHelpKey: #applyForClassToEnd
@@ -861,6 +906,12 @@
                 #enabled: #valueOfHavingSelection
             )
              #(#MenuItem
+                #label: 'Delete All For Class'
+                #value: #doDeleteAllForClass
+                #activeHelpKey: #applyForClassToEnd
+                #enabled: #valueOfHavingChangeSelection
+            )
+             #(#MenuItem
                 #label: 'Delete For Class To End'
                 #value: #doDeleteForClassToEnd
                 #activeHelpKey: #deleteForClassToEnd
@@ -1001,52 +1052,63 @@
 !NewChangesBrowser methodsFor:'accesssing - columns'!
 
 categoryColumn
+    "returns whether the column for the category attribute of the changes is shown"
 
     ^CategoryColumn ? (CategoryColumn := true)
 !
 
 categoryColumn: aBoolean
+    "sets whether the column for the category attribute of the changes is shown"
 
     self changeColumn: 'Category' add: (CategoryColumn := aBoolean)
 !
 
 deltaInfoColumn
+    "returns whether the column for the delta info attribute of the changes is shown"
 
     ^DeltaInfoColumn ? (DeltaInfoColumn := false)
 !
 
 deltaInfoColumn: aBoolean
-
-    self changeColumn: 'Delta Info' add: (DeltaInfoColumn := aBoolean)
+    "sets whether the column for the delta info attribute of the changes is shown; and updates"
+
+    self changeColumn: 'Delta Info' add: (DeltaInfoColumn := aBoolean).
+    (self window notNil and: [DeltaInfoColumn]) ifTrue: [self doReload]
 !
 
 positionColumn
+    "returns whether the column for the position attribute of the changes is shown"
 
     ^PositionColumn ? (PositionColumn := true)
 !
 
 positionColumn: aBoolean
+    "sets whether the column for the position attribute of the changes is shown"
 
     self changeColumn: 'Position' add: (PositionColumn := aBoolean)
 !
 
 timeStampColumn
+    "returns whether the column for the time stamp attribute of the changes is shown"
 
     ^TimeStampColumn ? (TimeStampColumn := false)
 !
 
 timeStampColumn: aBoolean
+    "sets whether the column for the time stamp attribute of the changes is shown"
 
     self changeColumn: 'Time Stamp' add: (TimeStampColumn := aBoolean)
 
 !
 
 typeColumn
+    "returns whether the column for the type attribute of the changes is shown"
 
     ^TypeColumn ? (TypeColumn := false)
 !
 
 typeColumn: aBoolean
+    "sets whether the column for the type attribute of the changes is shown"
 
     self changeColumn: 'Type' add: (TypeColumn := aBoolean)
 
@@ -1055,6 +1117,7 @@
 !NewChangesBrowser methodsFor:'accesssing - views'!
 
 filterField
+    "returns the view of the filterField"
 
     ^builder componentAt: #filterField
 
@@ -1063,6 +1126,7 @@
 !
 
 filterLabel
+    "returns the view of the filterLabel"
 
     ^builder componentAt: #filterLabel
 
@@ -1071,6 +1135,7 @@
 !
 
 readProgressIndicator
+    "returns the view of the readProgressIndicator"
 
     ^builder componentAt: #readProgressIndicator
 
@@ -1081,6 +1146,7 @@
 !NewChangesBrowser methodsFor:'aspects'!
 
 listOfChangeColumns
+    "initializes (during the startup) and returns the value holder for the columns"
 
     |holder|
     (holder := builder bindingAt:#listOfChangeColumns) isNil ifTrue:[
@@ -1102,6 +1168,7 @@
 !
 
 listOfChanges
+    "returns the value holder for the changes"
 
     |holder| 
     (holder := builder bindingAt:#listOfChanges) isNil ifTrue:[
@@ -1111,6 +1178,7 @@
 !
 
 selectionOfChange
+    "returns the value holder for the selected change"
 
     |holder|
     (holder := builder bindingAt:#selectionOfChange) isNil ifTrue:[
@@ -1120,6 +1188,7 @@
 !
 
 valueOfChangeText
+    "returns the value holder for the source code of the selected change"
 
     |holder|
     (holder := builder bindingAt:#valueOfChangeText) isNil ifTrue:[
@@ -1129,15 +1198,18 @@
 !
 
 valueOfFilter
+    "returns the value holder for the string of the filter"
 
     |holder|
     (holder := builder bindingAt:#valueOfFilter) isNil ifTrue:[
         builder aspectAt:#valueOfFilter put:(holder :=  ValueHolder new).
+        holder addDependent: self
     ].
     ^ holder
 !
 
 valueOfHavingChangeSelection
+    "returns whether the selected change can be applied as value holder"
 
     |holder|
     (holder := builder bindingAt:#valueOfHavingChangeSelection) isNil ifTrue:[
@@ -1147,6 +1219,7 @@
 !
 
 valueOfHavingSelection
+    "returns whether a change is selected as value holder"
 
     |holder|
     (holder := builder bindingAt:#valueOfHavingSelection) isNil ifTrue:[
@@ -1156,6 +1229,7 @@
 !
 
 valueOfNotReading
+    "returns whether it is not reading or compressing as value holder"
 
     |holder|
     (holder := builder bindingAt:#valueOfReading) isNil ifTrue:[
@@ -1165,6 +1239,7 @@
 !
 
 valueOfReadProgress
+    "returns the stage of reading or compressing as value holder"
 
     |holder|
     (holder := builder bindingAt:#valueOfReadProgress) isNil ifTrue:[
@@ -1176,7 +1251,7 @@
 !NewChangesBrowser methodsFor:'callbacks'!
 
 changeSelected: lineNr
-    "show a change in the codeView"
+    "fetches the source code of the change and shows it in the codeView"
 
     |aStream sawExcla chunk selectedRow changeNr|
 
@@ -1192,13 +1267,48 @@
     aStream close.        
     self valueOfChangeText value:chunk.
 
-    (selectedRow := changes at: changeNr ifAbsent: nil) notNil
+    self updateChannels
+! !
+
+!NewChangesBrowser methodsFor:'change & update'!
+
+update:something with:aParameter from:changedObject
+    "evaluates the filterCompletionBlock after returning the filter string"
+
+    super update:something with:aParameter from:changedObject.
+
+    changedObject == self valueOfFilter 
+        ifTrue: [filterCompletionBlock value: changedObject value]
+
+
+
+
+
+
+!
+
+updateChannels
+    "updates my channels"
+
+    |change|           
+    (change := self selectionOfChange value) notNil
     ifTrue:
     [
         self valueOfHavingSelection value: true.
         self valueOfHavingChangeSelection value: 
-            ((selectedRow type = 'method') or: [(selectedRow type = 'class')])
+            ((change type = 'method') or: [(change type = 'class')])
+    ]
+    ifFalse:
+    [
+        self valueOfHavingSelection value: false.
+        self valueOfHavingChangeSelection value: false
     ]
+
+
+
+
+
+
 ! !
 
 !NewChangesBrowser methodsFor:'compiler interface'!
@@ -1215,7 +1325,7 @@
 !NewChangesBrowser methodsFor:'help'!
 
 defaultInfoLabel
-    "get default label for the info bar"
+    "returns the default label for the info bar"
 
     changeFileName asFilename exists ifTrue: [^changeFileName].
     ^'No change file name defined.'
@@ -1227,13 +1337,14 @@
 !NewChangesBrowser methodsFor:'initialization'!
 
 initialize
+    "initializes the instance variables"
 
     super initialize.
 
-    changes        := List new.
-    changeFileName := (Filename currentDirectory asAbsoluteFilename construct: ObjectMemory nameForChanges) name. 
-    AutoUpdate     := AutoUpdate ? false.                                     
-    compareChanges := true.
+    changes           := List new.
+    self changeFileName: ObjectMemory nameForChanges. 
+    AutoUpdate        := AutoUpdate ? false.                                     
+    PrivateAsSeparate := PrivateAsSeparate ? false.
 
     ObjectMemory addDependent:self.
 ! !
@@ -1252,19 +1363,33 @@
 
     AutoUpdate := aMode
 
+!
+
+privateAsSeparate
+    "returns whether private classes are handled as separate changes"
+
+    ^PrivateAsSeparate
+
+!
+
+privateAsSeparate: aMode
+    "sets the PrivateAsSeparate to aMode"
+
+    PrivateAsSeparate := aMode
+
 ! !
 
 !NewChangesBrowser methodsFor:'private'!
 
-applyChange:change
-    "fileIn a change"
+applyChange:aChange
+    "applies aChange"
 
     |aStream nm applyAction changeNr|
 
-    aStream := self streamForChange:change.
+    aStream := self streamForChange:aChange.
     aStream isNil ifTrue:[^ self].
 
-    nm := self classNameOfChange:change.
+    nm := self classNameOfChange:aChange.
     nm notNil ifTrue:[
         |cls|
 
@@ -1288,8 +1413,8 @@
             |reader doItChunk methodsForChunk|
 
             "/ a followup methodsFor: chunk ...
-            change followUp ifTrue:[
-                methodsForChunk := change chunk.
+            aChange followUp ifTrue:[
+                methodsForChunk := aChange chunk.
             ] ifFalse:[
                 doItChunk := aStream nextChunk.   "/ an empty chunk sometimes ...
                 doItChunk notEmpty ifTrue:[
@@ -1320,59 +1445,74 @@
     aStream close
 !
 
-autoSelectChange:change
-    "select a change"
+autoSelectChange:aChange
+    "selects aChange"
 
     self class autoSelectNext ifTrue:[         
-        ((self listOfChanges indexOf: change) <= self listOfChanges size) ifTrue:[      
-            self selectionOfChange value: change.
-            self changeSelected:(self listOfChanges indexOf: change).
+        ((self listOfChanges indexOf: aChange) <= self listOfChanges size) ifTrue:[      
+            self selectionOfChange value: aChange.
+            self changeSelected:(self listOfChanges indexOf: aChange).
+            self updateChannels.
             ^ self
         ]
     ].
-    self clearCodeView. 
-    self selectionOfChange value:nil
+    self updateChannels.
+    self unselectChange
 !
 
 autoSelectLast
-    "select the last change"
-
-    self autoSelectChange: self listOfChanges last
+    "selects the last change"
+
+    self autoSelectChange: (self listOfChanges at: self listOfChanges size ifAbsent: nil).
+    self updateChannels.
+
 !
 
-autoSelectOrEnd:change
-    "select change or the last"
+autoSelectOrEnd:aChange
+    "selects aChange or the last"
 
     |last|
 
     last := self listOfChanges size.
-    change notNil ifTrue:[  
-        self autoSelectChange:change
+    aChange notNil ifTrue:[  
+        self autoSelectChange:aChange
     ] ifFalse:[
         self selectionOfChange value: (self listOfChanges at: last ifAbsent: nil).
         self changeSelected: last
-    ] 
+    ].
+    self updateChannels
 !
 
 changeColumn: aColumnLabel add: addOrRemove
+    "adds or removes a attribute column to the table"
 
     addOrRemove
     ifTrue:
-    [
-        self listOfChangeColumns add: 
-            ((self class specOfChangeColumns collect: [:i| i decodeAsLiteralArray]) detect: [:column| column label = aColumnLabel]) 
-    ]
+    [     
+        self listOfChangeColumns contents: (self listOfChangeColumns add: 
+            ((self class specOfChangeColumns collect: [:i| i decodeAsLiteralArray]) detect: [:column| column label = aColumnLabel]); yourself)
+        asArray.                           
+
+        ]
     ifFalse:
     [
-        self listOfChangeColumns remove: 
-            (self listOfChangeColumns detect: [:column| column label = aColumnLabel] ifNone: [^nil])
+        self listOfChangeColumns contents: (self listOfChangeColumns remove: 
+            (self listOfChangeColumns detect: [:column| column label = aColumnLabel] ifNone: nil) ifAbsent: [self listOfChangeColumns]; yourself)
+        asArray
     ]
 
 
 
 !
 
+changeFileName:aFileName
+    "sets the name of the file with the changes"
+
+    changeFileName := (Filename currentDirectory asAbsoluteFilename construct: aFileName) name.
+!
+
 checkClassIsLoaded:aClass
+    "returns true if aClass is loaded"
 
     |cls|
     aClass isMeta ifTrue:[
@@ -1390,8 +1530,9 @@
 !
 
 checkIfFileHasChanged
-
-    |f info |
+    "checks if changes file has changed"
+
+    |f info|
 
     Processor removeTimedBlock:autoUpdateBlock.   
     f := changeFileName asFilename.
@@ -1410,13 +1551,13 @@
     Processor addTimedBlock:autoUpdateBlock afterSeconds:5.
 !
 
-classNameOfChange:changeNr
-    "return the classname of a change 
+classNameOfChange:aChange
+    "returns the classname of aChange 
      (for classChanges (i.e. xxx class), the non-metaClassName (i.e. xxx) is returned)"
 
     |name|
 
-    name := self fullClassNameOfChange:changeNr.
+    name := self fullClassNameOfChange:aChange.
     name isNil ifTrue:[^ nil].
     (name endsWith:' class') ifTrue:[
         ^ name copyWithoutLast:6
@@ -1424,29 +1565,23 @@
     ^ name
 !
 
-clearCodeView
-
-    self unselectChange.
-    self valueOfChangeText value: nil
-!
-
-compareChange:change
-    "compare a change with current version"
+compareChange:aChange
+    "compares aChange with the current version"
 
     |aStream chunk sawExcla parseTree thisClass cat oldSource newSource
      parser sel oldMethod outcome showDiff d t1 t2 selector isLoaded
      method beep|
 
-    aStream := self streamForChange:change.
+    aStream := self streamForChange:aChange.
     aStream isNil ifTrue:[^ self].
 
     showDiff := false.
 
-    change followUp ifFalse:[
+    aChange followUp ifFalse:[
         sawExcla := aStream peekFor:(aStream class chunkSeparator).
         chunk := aStream nextChunk.
     ] ifTrue:[
-        chunk := change chunk.
+        chunk := aChange chunk.
         sawExcla := true.
     ].
 
@@ -1587,7 +1722,7 @@
 !
 
 compressForClass:aClassNameOrNil
-    "compress the change-set; 
+    "compresses the list of changes; 
      this replaces multiple method-changes by the last (i.e. the most recent) change.
      If the class argument is nil, compress for all classes.
      otherwise, only changes for that class are compressed."
@@ -1718,9 +1853,11 @@
                     thisClass isMeta ifTrue:[
                         compressThis := aClassNameOrNil = thisClass soleInstance name. 
                     ] ifFalse:[
-                        compressThis := aClassNameOrNil = thisClass name
+                        compressThis := aClassNameOrNil = thisClass name.
+                        (PrivateAsSeparate not and: [thisClass isPrivate])
+                            ifTrue:[compressThis := aClassNameOrNil = thisClass owningClass name]
                     ]
-                ]
+                 ]
             ].
 
             compressThis ifTrue:[
@@ -1754,7 +1891,7 @@
                 self silentDeleteChange: (changes at: (deleteSet at:index)).
                 index := index - 1
             ].
-            "self setChangeList"
+            self setChangeList
         ].
     ].
     self valueOfNotReading value: true.
@@ -1785,16 +1922,17 @@
 !
 
 deleteChangesFrom:start to:stop
-    "delete a range of changes"
+    "deletes a range of changes"
 
     self unselectChange.
     stop to:start by:-1 do:[:changeNr|
         self silentDeleteChange:(self listOfChanges at: changeNr)
-    ]
+    ].
+    self setChangeList
 !
 
-fullClassNameOfChange:change
-    "return the full classname of a change 
+fullClassNameOfChange:aChange
+    "returns the full classname of aChange 
      (for classChanges (i.e. xxx class), a string ending in ' class' is returned.
      - since parsing ascii methods is slow, keep result cached in 
        changeClassNames for the next query"
@@ -1802,15 +1940,15 @@
     |chunk aParseTree recTree sel name arg1Tree isMeta prevMethodDefNr
      words changeStream fullParseTree ownerTree ownerName oldDollarSetting|
 
-    change isNil ifTrue:[^ nil].
+    aChange isNil ifTrue:[^ nil].
 
     "
      first look, if not already known
     "
-    name := change className.
+    name := aChange className.
     name notNil ifTrue:[^ name].
 
-    prevMethodDefNr := changes indexOf: change.
+    prevMethodDefNr := changes indexOf: aChange.
     [(changes at:prevMethodDefNr) followUp] whileTrue:[
         prevMethodDefNr := prevMethodDefNr - 1.
     ].
@@ -1826,7 +1964,7 @@
         words size > 2 ifTrue:[
             (words at:2) = 'checkin' ifTrue:[
                 name := words at:3.
-                change className: name.
+                aChange className: name.
                 ^ name
             ]
         ].
@@ -1898,7 +2036,7 @@
                 isMeta ifTrue:[
                     name := name , ' class'.
                 ].
-                change className: name.
+                aChange className: name.
                 ^ name
             ]
         ].
@@ -1914,7 +2052,7 @@
         "/ must parse the full changes text, to get
         "/ privacy information.
 
-        changeStream := self streamForChange:change.
+        changeStream := self streamForChange:aChange.
         changeStream notNil ifTrue:[
             chunk := changeStream nextChunk.
             changeStream close.
@@ -1942,7 +2080,7 @@
                 ownerName := ownerTree name asString.
                 name := ownerName , '::' , name
             ].
-            change className: name.
+            aChange className: name.
             ^ name
         ].
         "very strange"
@@ -1960,7 +2098,7 @@
             arg1Tree := aParseTree arg1.
             (arg1Tree notNil and:[arg1Tree isPrimary]) ifTrue:[
                 name := arg1Tree name.
-                change className: name.
+                aChange className: name.
                 ^ name
             ].
         ]
@@ -1987,7 +2125,7 @@
                     name := name , ' class'.
                 ].
                 name := recTree name.
-                change className: name.
+                aChange className: name.
                 ^ name
             ]
         ]
@@ -1996,13 +2134,14 @@
 !
 
 newLabel:how
+    "sets the label"
 
     how size = 0 ifTrue: [^self window label:self class label].
     self window label:self class label, '(', how, ')'
 !
 
 readChangesFileInBackground:inBackground
-    "read the changes file, create a list of header-lines (changeChunks)
+    "reads the changes file, creates a list of header-lines (changeChunks)
      and a list of chunk-positions (changePositions).
      Starting with 2.10.3, the entries are multi-col entries;
      the cols are:
@@ -2165,7 +2304,7 @@
                                     ].
                                     sel := (p args at:1) evaluate.
 
-                                    compareChanges ifTrue:[
+                                    DeltaInfoColumn ifTrue:[
                                         (changeClass isNil or:[changeClass isLoaded not]) ifTrue:[
                                             changeDelta := '?'
                                         ] ifFalse:[
@@ -2294,7 +2433,7 @@
                                         headerLine := className , ' ' , sel , ' ' , '(change category: ''' , category , ''')'.
                                     ].
 
-                                    compareChanges ifTrue:[ 
+                                    DeltaInfoColumn ifTrue:[ 
                                         changeClass isNil ifFalse:[
                                             changeClass isMeta ifTrue:[
                                                 cls := changeClass soleInstance
@@ -2362,7 +2501,6 @@
         ].
     ].
     self setChangeList.
-    self setChangeSelection.
     self valueOfNotReading value: true.
     self filterField raise.
     self filterLabel label: 'Filter:'.
@@ -2371,12 +2509,12 @@
 
 !
 
-selectorOfMethodChange:change
-    "return a method-changes selector, or nil if its not a methodChange"
+selectorOfMethodChange:aChange
+    "returns the selector of the method change, or nil if it is not a method change"
 
     |source parser sel|
 
-    source := self sourceOfMethodChange:change.
+    source := self sourceOfMethodChange:aChange.
     source isNil ifTrue:[^ nil].
 
     parser := Parser 
@@ -2392,61 +2530,34 @@
 !
 
 setChangeList
-    "extract type-information from changes and stuff into top selection
-     view"
-
-    self valueOfFilter value: nil.
-    self listOfChanges contents: changes.
-    changes size == 0
-    ifTrue:
-    [                     
-        self unselectChange.
-        self valueOfHavingSelection value: false.
-        self valueOfHavingChangeSelection value: false.
-    ]
-    ifFalse:
-    [       
-        self selectionOfChange value: (self listOfChanges size > 0 ifTrue: [self listOfChanges last] ifFalse: [nil])
-    ]
+    "sets the list of changes into the list for the table by evaluating filterCompletionBlock"
+
+    self unselectChange.
+    filterCompletionBlock value: self valueOfFilter value.
 !
 
-setChangeSelection
-    "extract type-information from changes and stuff into top selection
-     view"
-
-    changes size == 0
-    ifTrue:
-    [                     
-        self unselectChange.
-        self valueOfHavingSelection value: false.
-        self valueOfHavingChangeSelection value: false.
-    ]
-    ifFalse:
-    [       
-        self selectionOfChange value: self listOfChanges last
-    ]
-!
-
-silentDeleteChange:change
-    "delete a change do not update changeListView"
+silentDeleteChange:aChange
+    "delete aChange do not update changeListView"
 
     modified := true.      
 
-    changes remove:change.
-    self listOfChanges remove:change
+    changes remove:aChange
 !
 
 silentDeleteChangesFor:aClassName from:start to:stop
-    "delete changes for a given class in a range.
-     Return the number of deleted changes."
-
-    |thisClassName index numDeleted|
+    "deletes changes for aChange in the range [start,stop]
+     and returns the number of the deleted changes"
+
+    |index numDeleted clsName|
 
     numDeleted := 0.
-    index := stop.
-    [index >= start] whileTrue:[
-        thisClassName := self classNameOfChange:(self listOfChanges at: index).
-        thisClassName = aClassName ifTrue:[
+    index := stop.          
+    [index >= start] whileTrue:
+    [                                         
+        ((clsName := self classNameOfChange:(self listOfChanges at: index)) notNil and:
+        [(clsName = aClassName or: [PrivateAsSeparate not and: [(clsName upTo: $:) = aClassName]])])
+        ifTrue:
+        [     
             self silentDeleteChange:(self listOfChanges at: index).
             numDeleted := numDeleted + 1.
         ].
@@ -2455,19 +2566,19 @@
     ^ numDeleted
 !
 
-sourceOfMethodChange:change
-    "return a method-changes source code, or nil if its not a methodChange."
+sourceOfMethodChange:aChange
+    "returns the source code of the method change, or nil if it is not a method change."
 
     |aStream chunk sawExcla parseTree sourceChunk|
 
-    aStream := self streamForChange:change. 
+    aStream := self streamForChange:aChange. 
     aStream isNil ifTrue:[^ nil].
 
-    change followUp ifFalse:[
+    aChange followUp ifFalse:[
         sawExcla := aStream peekFor:(aStream class chunkSeparator).
         chunk := aStream nextChunk.
     ] ifTrue:[
-        chunk := change chunk.
+        chunk := aChange chunk.
         sawExcla := true.
     ].
 
@@ -2483,22 +2594,24 @@
     ^ sourceChunk
 !
 
-streamForChange:change
-    "answer a stream for change"
+streamForChange:aChange
+    "returns the stream for aChange"
 
     |aStream|
 
     aStream := FileStream readonlyFileNamed:changeFileName.
     aStream isNil ifTrue:[^ nil].
-    aStream position:change position.
+    aStream position:aChange position.
     ^ aStream
 
 !
 
 unselectChange
-    "common unselect"
-
-    self selectionOfChange value: nil
+    "unselects the current change"
+
+    self selectionOfChange value: nil.
+    self valueOfChangeText value: nil
+
 !
 
 withSelectedChangeDo:aBlock
@@ -2516,6 +2629,7 @@
 !NewChangesBrowser methodsFor:'startup / release'!
 
 closeRequest
+    "asks for saving before closing"
 
     self valueOfNotReading value ifFalse: [^nil].
 
@@ -2533,6 +2647,8 @@
 !
 
 postOpenWith:aBuilder
+    "starts reading the changes from the file and
+     builds entryCompletionBlock for the filterField before opening"
 
     super postOpenWith:aBuilder.
 
@@ -2543,7 +2659,6 @@
             v redraw
         ] 
     ].
-    self readChangesFileInBackground:true.
 
     autoUpdateBlock := [self checkIfFileHasChanged].
     Processor addTimedBlock:autoUpdateBlock afterSeconds:5.  
@@ -2552,7 +2667,7 @@
     self filterField entryCompletionBlock:
     (filterCompletionBlock := [:value|
         |filter filters i changesCopy|
-        self clearCodeView.
+        self unselectChange.
         ((filter := self filterField contents) notNil and:
         [(filters := filter asArrayOfSubstrings) size > 0]) ifTrue: 
         [
@@ -2569,13 +2684,17 @@
         ] 
         ifFalse: 
         [
-            self setChangeList
+            self listOfChanges contents: changes
         ].
         self autoSelectLast.
-    ])
+    ]).
+
+    self readChangesFileInBackground:true.
+
 !
 
 uninitialize
+    "removes the autoUpdateBlock from the Processor and myself from the ObjectMemory"
 
     Processor removeTimedBlock:autoUpdateBlock.
     ObjectMemory removeDependent:self
@@ -2584,7 +2703,7 @@
 !NewChangesBrowser methodsFor:'user actions'!
 
 doApply
-    "user wants a change to be applied"
+    "applies the selected change"
 
     self withSelectedChangeDo:[:change|
         skipSignal := nil.
@@ -2594,11 +2713,11 @@
 !
 
 doApplyAll
-    "user wants all changes to be applied"
+    "applies all changes"
 
     self withExecuteCursorDo:[
         |change|
-        self clearCodeView.
+        self unselectChange.
         skipSignal isNil ifTrue:[skipSignal := Signal new].
         1 to:self listOfChanges size do:[:changeNr |
             self selectionOfChange value:(change := self listOfChanges at: changeNr).
@@ -2609,22 +2728,38 @@
 
 !
 
+doApplyAllForClass
+    "applies all changes having the same class like the selected one"
+
+    self doApplyForClassToEndFrom: 1
+
+
+!
+
 doApplyForClassToEnd
-    "user wants all changes for this class from changeNr to be applied"
+    "applies all changes having the same class like the selected one from the selected to the end"
+
+    self doApplyForClassToEndFrom: (self listOfChanges indexOf: self selectionOfChange value)
+!
+
+doApplyForClassToEndFrom: start
+    "applies changes with same class like the selected one from start to end"
 
     self withSelectedChangeDo:[:change|
-        |thisClassName classNameToApply lastChange change2|
+        |classNameToApply thisClassName lastChange change2|
         (classNameToApply := self classNameOfChange:change) notNil 
         ifTrue:
-        [
-            self clearCodeView.
+        [             
+            self unselectChange.
             skipSignal isNil ifTrue:[skipSignal := Signal new].
-            (self listOfChanges indexOf: change) to:self listOfChanges size do:
+            start to:self listOfChanges size do:
             [:changeNr|
-                change2 := self listOfChanges indexOf: changeNr.
-                (thisClassName := self classNameOfChange:change2) = classNameToApply 
+                change2 := self listOfChanges at: changeNr.
+                ((thisClassName := self classNameOfChange:change2) notNil and:
+                [thisClassName = classNameToApply or:
+                [PrivateAsSeparate not and: [(thisClassName upTo: $:) = classNameToApply]]])
                 ifTrue:
-                [
+                [                           
                     self selectionOfChange value: change2.
                     self applyChange:change2.
                     lastChange := change2
@@ -2637,16 +2772,17 @@
 !
 
 doApplyFromLastSnapshot
+    "applies all changes made since the last snapshot"
 
     self autoSelectLast.
     (self doFindSnapshot: 'last') ifTrue: [self doApplyToEnd]
 !
 
 doApplyToEnd
-    "user wants all changes from changeNr to be applied"
+    "applies all changes from selected one to be end"
 
     self withSelectedChangeDo:[:change|
-        self clearCodeView.
+        self unselectChange.
         skipSignal isNil ifTrue:[skipSignal := Signal new].
         (self listOfChanges indexOf: change) to: self listOfChanges size do:[:changeNr|
             self selectionOfChange value:(self listOfChanges at: changeNr).
@@ -2658,7 +2794,7 @@
 !
 
 doBrowseClass
-    "user wants a browser on the class of a change"
+    "opens a System Browser on the class of a change (and selector)"
 
     |className cls isMeta|
 
@@ -2682,8 +2818,7 @@
 !
 
 doCompare
-    "compare change with current system version
-     - give a note in transcript"
+    "compares a change with the current system version"
 
     |change|
 
@@ -2694,15 +2829,14 @@
 !
 
 doCompress
-    "compress the change-set; this replaces multiple method-changes by the last 
-     (i.e. the most recent) change"
+    "compresses the changes, i.e. replaces multiple changes by the last change"
 
     |changesSizeBefore|
-    changesSizeBefore := changes size.
+    (changesSizeBefore := changes size) == 0 ifTrue: [^self warn: 'Nothing to compress!!'].
     self setChangeList.
     self unselectChange.
     self compressForClass:nil.
-    filterCompletionBlock value: self valueOfFilter value.        
+    self setChangeList.    
     self updateInfoLabel.
 
     self information: 
@@ -2715,7 +2849,7 @@
 !
 
 doCompressForClass
-    "compress changes for the selected class.
+    "compresses changes for the selected class.
      this replaces multiple method-changes by the last (i.e. the most recent) change."
 
     self withSelectedChangeDo:[:change|
@@ -2731,7 +2865,7 @@
 !
 
 doDelete
-    "delete currently selected change"
+    "deletes the selected change"
 
     |change selectionIndex|
 
@@ -2739,43 +2873,72 @@
         selectionIndex := self listOfChanges indexOf: change.
         self unselectChange.
         self silentDeleteChange:change.
+        self listOfChanges remove:change.
         self autoSelectOrEnd: (self listOfChanges at: selectionIndex ifAbsent: [nil]).
     ]
+!
+
+doDeleteAll
+    "deletes all changes"
+
+    self unselectChange.
+    self deleteChangesFrom:1 to: self listOfChanges size.
+    self autoSelectOrEnd: nil
+
+!
+
+doDeleteAllForClass
+    "deletes all changes having the same class like the selected one"
+
+    self doDeleteForClassToEndFrom: 1
 
 !
 
 doDeleteForClassToEnd
-    "delete rest of changes with same class as currently selected change"
+    "deletes all changes having the same class like the selected one from the selected to the end"
+
+    self withSelectedChangeDo:[:change|
+        self doDeleteForClassToEndFrom: (self listOfChanges indexOf: change)
+    ]
+
+
+!
+
+doDeleteForClassToEndFrom: start
+    "deletes changes with same class like the selected one from start to end"
 
     self withSelectedChangeDo:[:change|
         |classNameToDelete|
         (classNameToDelete := self classNameOfChange:change) notNil ifTrue:[
             self unselectChange.
             self silentDeleteChangesFor:classNameToDelete 
-                                   from:(self listOfChanges indexOf: change)
+                                   from:start
                                      to:self listOfChanges size.
+            self setChangeList.
             self autoSelectOrEnd: nil
         ]
-    ]
+    ].
+
 
 
 !
 
 doDeleteToEnd
-    "delete all changes from current to the end"
+    "deletes all changes from selected one to be end"
 
     |changeNr|
 
     changeNr := (self listOfChanges indexOf: self selectionOfChange value).
     changeNr ~~ 0 ifTrue:[
         self deleteChangesFrom:changeNr to: self listOfChanges size.
-        self clearCodeView.
+        self unselectChange.
         self autoSelectOrEnd: nil
     ]
 
 !
 
 doFindSnapshot: what
+    "finds the last made snapshot and selects it"
 
     self listOfChanges detect: [:change| change type = 'image'] ifNone: [^self warn: 'No snapshot found!!'].
 
@@ -2808,6 +2971,7 @@
 !
 
 doLoadFrom
+    "opens a dialog for loading changes from a file"
 
     |fileName|
     (fileName :=
@@ -2828,12 +2992,11 @@
 !
 
 doReload
-    "reloads the changes-file"
+    "reloads the changes from the file"
 
     changes removeAll.
     self unselectChange.
     self readChangesFileInBackground:true.
-    filterCompletionBlock value: self valueOfFilter value.
     self autoSelectLast
 
 !
@@ -2927,27 +3090,6 @@
     ^ true
 
 
-!
-
-doSaveAs 
-
-    |fileName|
-    (fileName :=
-        (FileSelectionBrowser
-            request: 'Load Changes From'
-            fileName: changeFileName
-            withFileFilters: #('changes*'))) notNil
-    ifTrue:
-    [        
-        (fileName := (Filename named:fileName) writeStream) notNil
-        ifTrue:
-        [
-            fileName close.
-            changeFileName := fileName pathName.
-            self doSave.
-            self updateInfoLabel
-        ]
-    ]
 ! !
 
 !NewChangesBrowser::Change methodsFor:'accessing'!
@@ -3068,5 +3210,6 @@
 !NewChangesBrowser class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/NewChangesBrowser.st,v 1.1 1998-04-14 13:08:18 tz Exp $'
+    ^ '$Header: /cvs/stx/stx/libtool/NewChangesBrowser.st,v 1.2 1998-04-14 19:14:54 tz Exp $'
+
 ! !