added:
authorClaus Gittinger <cg@exept.de>
Thu, 30 Jun 2011 19:09:51 +0200
changeset 2394 f867c637b7cb
parent 2393 f1330a09ba45
child 2395 e9082ccc0d80
added: #updateAfterClassChange:in: #updateAfterClassdefinitionChangeIn: #updateAfterMethodChange:in: comment/format in: #addHistory:with:to:filter: more detail; detect format-only changes using the refactorybrowser
HistoryManager.st
--- a/HistoryManager.st	Thu Jun 30 17:41:22 2011 +0200
+++ b/HistoryManager.st	Thu Jun 30 19:09:51 2011 +0200
@@ -22,7 +22,8 @@
 Object subclass:#HistoryLine
 	instanceVariableNames:'date time user what firstPositionInSourceCode type'
 	classVariableNames:'Quote Separator ModifiedString DeletedString IndentString
-		UseGECOS CreatedString AddedString EnforcedUserName'
+		UseGECOS CreatedString AddedString EnforcedUserName
+		FormattedString CommentedString VariableRenamedString'
 	poolDictionaries:''
 	privateIn:HistoryManager
 !
@@ -51,7 +52,7 @@
 
     All Methods and Classes in the system get a HistroyLine which 
     contains a timestamp and the name of the changing user. 
-    This is acually the UniX loginname.
+    This is acually the Unix loginname.
 
     The Manager registers itself to get notifications 
     on change, intercepts them and appends a historyLine to the methods
@@ -60,7 +61,7 @@
     The HistoryManager can be turned on/off from aprivate.rc script,
     or via the Launcher menu.
 
-    The methods history line is filtered, to only contain one
+    The method's history line is filtered, to only contain one
     entry per modifying user, containing the date of the last change.
     If fullHistoryMode is on, the classes history-ethod is also updated for
     every change (containing every change).
@@ -406,8 +407,7 @@
     "arrive here, whenever any class changed somehow.
      (something contains aSymbol describing what happened)"
 
-    |sourceCode newMethod selector oldMethod what
-     changedClass whatChange oldSource|
+    |selector oldMethod changedClass whatChange|
 
     "/
     "/ no action, if disabled
@@ -429,34 +429,19 @@
         ^ self 
     ].
 
-    "
+    "                  
      definition, instance / classVariables of a class have changed
     "
     (something == #definition) ifTrue:[
         "/ it is a class definition that has changed
         "/ add a line to the history method; if present
-
-"/        Transcript show: 'Class definition: ', changedClass printString;cr.
-        fullHistoryUpdate == true ifTrue:[
-            changedObject theMetaclass compilerClass == Compiler ifFalse:[^ self].
-            self addHistory:#modification with:'class definition' toHistoryMethodOf:changedObject.
-        ].
+        self updateAfterClassChange:'class definition' in:changedObject.
         ^ self
     ].
 
     "this is a sub item of #definition"    
     (something == #classVariables) ifTrue:[
-        "/
-        "/ Transcript showCR: 'classVariables changed'.
-        "/
-
-        "/ does not yet work;
-        "/ (someArgument does not contain the class we are interested in)
-
-        fullHistoryUpdate == true ifTrue:[
-            changedObject theMetaclass compilerClass == Compiler ifFalse:[^ self].
-            self addHistory:#modification with:'class variables' toHistoryMethodOf:changedObject.
-        ].
+        self updateAfterClassChange:'class variables' in:changedObject.
         ^ self
     ].    
 
@@ -518,8 +503,7 @@
     "/ the new mechanism; I only need to depend upon
     "/ Smalltalk, to get all method changes
 
-    (changedObject == Smalltalk
-    and:[something == #methodInClass]) ifTrue:[
+    (changedObject == Smalltalk and:[something == #methodInClass]) ifTrue:[
         changedClass := someArgument at:1.
         selector := someArgument at:2.
         oldMethod := someArgument at:3.
@@ -531,73 +515,19 @@
 
         whatChange == #methodDictionary ifTrue:[
             "/ ok; it is a changed method
-
-            "/
-            "/ fetch sourceString of the method
-            "/
-            sourceCode := changedClass sourceCodeAt:selector.
-            sourceCode isNil ifTrue:[
-                "method has been deleted"
-"/                Transcript showCR: 'method has been deleted'.
-                fullHistoryUpdate == true ifTrue:[
-                    self addHistory:#deletion with:('#' , selector) toHistoryMethodOf:changedClass.
-                ].
-                ^ self.
-            ].
-
-            newMethod := changedClass compiledMethodAt:selector.
-
-            oldMethod notNil ifTrue:[
-                oldSource := oldMethod source.
-                oldSource notNil ifTrue:[
-                    (oldSource asString withTabsExpanded = sourceCode asString withTabsExpanded) ifTrue:[
-                         "/ no change (accepted same code again ?)
-                        ^ self
-                    ].
-                ]
-            ].
-
-            "/
-            "/ dont add historylines to documentation methods ...
-            "/
-            (changedClass isMeta not
-            or:[newMethod category ~= 'documentation']) ifTrue:[
-                oldMethod notNil ifTrue:[
-                    what := #modification
-                ] ifFalse:[
-                    what := #creation
-                ].
-
-                "/
-                "/ update the history line-comment in
-                "/ the methods source
-                "/
-            
-                sourceCode := self addHistory:what with:nil to:sourceCode filter:true.
-                newMethod source: sourceCode.
-"/                    Transcript showCR: 'history updated / added'.
-            ].
-
-            fullHistoryUpdate == true ifTrue:[
-                self addHistory:what with:('#' , selector) toHistoryMethodOf:changedClass.
-            ].
+            self updateAfterMethodChange:selector from:oldMethod in:changedClass.
             ^self
         ]. 
 
         whatChange == #comment ifTrue:[
             "the classes comment - we are no longer interested in that one"
-
             ^ self.
         ].
 
         whatChange == #classDefinition ifTrue:[
             "/ it is a class definition that has changed
             "/ add a line to the history method; if present
-
-"/            Transcript show: 'Class definition: ', changedClass printString;cr.
-            fullHistoryUpdate == true ifTrue:[
-                self addHistory:#modification with:'class definition' toHistoryMethodOf:changedClass.
-            ].
+            self updateAfterClassClassChange:'class definition' in:changedClass.
             ^self
         ].
     ].
@@ -605,9 +535,135 @@
 
     ^self
 
-    "Modified: / 27-08-1995 / 02:14:43 / claus"
-    "Modified: / 18-03-1999 / 18:21:47 / stefan"
-    "Modified: / 13-07-2006 / 17:41:35 / cg"
+    "Created: / 30-06-2011 / 16:43:46 / cg"
+!
+
+updateAfterClassChange:whatChange in:aClass 
+    "/ it is a class definition that has changed
+    "/ add a line to the history method; if present
+    "/        Transcript show: 'Class definition: ', changedClass printString;cr.
+    
+    fullHistoryUpdate == true ifTrue:[
+        "/ check for the programming-language...
+        aClass theMetaclass compilerClass == Compiler ifFalse:[
+            ^ self
+        ].
+        self 
+            addHistory:#modification
+            with:whatChange
+            toHistoryMethodOf:aClass.
+    ].
+
+    "Modified (Format): / 30-06-2011 / 16:27:23 / cg"
+    "Created: / 30-06-2011 / 16:28:22 / cg"
+!
+
+updateAfterMethodChange:selector from:oldMethod in:changedClass
+    |newSource newSourceWithoutHistory newHistories newMethod newTree newComments
+     oldSource oldSourceWithoutHistory oldHistories oldTree oldComments
+     renamedVariables
+     whatChange pos|
+
+    changedClass theMetaclass compilerClass == Compiler ifFalse:[^ self].
+
+    "/ ok; it is a changed method
+
+    "/
+    "/ fetch sourceString of the method
+    "/
+    newSource := changedClass sourceCodeAt:selector.
+    newSource isNil ifTrue:[
+        "method has been deleted"
+"/                Transcript showCR: 'method has been deleted'.
+        fullHistoryUpdate == true ifTrue:[
+            self addHistory:#deletion with:('#' , selector) toHistoryMethodOf:changedClass.
+        ].
+        ^ self.
+    ].
+    newHistories := self class getAllHistoriesFrom:newSource.
+
+    newMethod := changedClass compiledMethodAt:selector.
+
+    oldMethod isNil ifTrue:[
+        whatChange := #creation
+    ] ifFalse:[
+        whatChange := #modification.
+
+        oldSource := oldMethod source.
+        oldSource notNil ifTrue:[
+            (oldSource asString withTabsExpanded = newSource asString withTabsExpanded) ifTrue:[
+                 "/ no change (accepted same code again ?)
+                ^ self
+            ].
+
+            oldHistories := self class getAllHistoriesFrom:oldSource.
+            oldHistories notEmptyOrNil ifTrue: [
+                "/ compare source without history...
+                pos := (oldHistories first) firstPositionInSourceCode.
+                oldSourceWithoutHistory := (oldSource copyFrom:1 to:pos - 1) withoutSeparators.
+            ] ifFalse:[
+                oldSourceWithoutHistory := oldSource
+            ].
+
+            newHistories notEmptyOrNil ifTrue: [
+                "/ compare source without history...
+                pos := (newHistories first) firstPositionInSourceCode.
+                newSourceWithoutHistory := (newSource copyFrom:1 to:pos - 1) withoutSeparators.
+            ] ifFalse:[
+                newSourceWithoutHistory := newSource
+            ].
+
+            (oldSourceWithoutHistory asString withTabsExpanded = newSourceWithoutHistory asString withTabsExpanded) ifTrue:[
+                 "/ no change (except for history lines)
+                UserPreferences current historyManagerAllowEditOfHistory ifFalse:[
+                    newMethod source: oldSource.
+                ].
+                ^ self
+            ].
+
+            RBParser notNil ifTrue:[
+                "/ same structure?
+                oldTree := RBParser parseMethod:oldSourceWithoutHistory onError:[:aString :pos | nil].
+                newTree := RBParser parseMethod:newSourceWithoutHistory onError:[:aString :pos | nil].
+                (oldTree equalTo:newTree withMapping:(renamedVariables := Dictionary new)) ifTrue:[
+                    "/ only formatting?
+                        (renamedVariables keysAndValuesSelect:[:k :v | k ~= v]) isEmpty ifTrue:[
+                        "/ only formatting...
+                        whatChange := #formatted.
+                        oldComments := oldTree allComments.
+                        newComments := newTree allComments.
+                        (oldComments size ~= newComments size
+                        or:[ oldComments with:newComments contains:[:ca :cb | ca characters ~= cb characters]]) ifTrue:[
+                            whatChange := #commented.
+                        ].
+                    ] ifFalse:[
+                        renamedVariables halt.    
+                    ]
+                ]
+            ]
+        ]
+    ].
+
+    "/
+    "/ don't add historylines to documentation methods on the class side...
+    "/
+    (changedClass isMeta 
+    and:[newMethod category = 'documentation']) ifFalse:[
+        "/
+        "/ update the history line-comment in
+        "/ the methods source
+        "/            
+        newSource := self addHistory:whatChange with:nil to:oldHistories inSource:newSource filter:true.
+        newMethod source: newSource.
+        "/ Transcript showCR: 'history updated / added'.
+    ].
+
+    fullHistoryUpdate == true ifTrue:[
+        self addHistory:whatChange with:('#' , selector) toHistoryMethodOf:changedClass.
+    ].
+
+
+    "Created: / 30-06-2011 / 16:51:19 / cg"
 ! !
 
 !HistoryManager methodsFor:'initialization'!
@@ -686,8 +742,7 @@
      What may be one of #modification or #creation, to choose among
      'Modified' or 'Created' lines."
 
-    | histLines pos wStream sourceCode previousHistories
-      newLine |
+    |previousHistories|
 
     "Check whether we want a history to be added"    
     historyMode ifFalse:[
@@ -695,44 +750,64 @@
     ].
 
     previousHistories := self class getAllHistoriesFrom:someString.
+    ^ self addHistory:what with:argument to:previousHistories inSource:someString filter:doFilter
+
+    "Modified: / 30-06-2011 / 16:54:27 / cg"
+    "Modified (Format): / 30-06-2011 / 18:17:58 / cg"
+!
+
+addHistory:what with:argument to:previousHistories inSource:someString filter:doFilter
+    "private - add a historyLine at end to the sourceCode;
+     check for multiple lines of the same user and merge into one.
+     What may be one of #modification or #creation, to choose among
+     'Modified' or 'Created' lines."
+
+    |histories histLines pos wStream sourceCode newLine |
+
+    "Check whether we want a history to be added"    
+    historyMode ifFalse:[
+        ^ someString
+    ].
 
     newLine := HistoryLine new.
 
     what == #creation ifTrue:[
         newLine isForCreation.
-    ] ifFalse:[
-        what == #deletion ifTrue:[
-            newLine isForDeletion.
-        ] ifFalse:[
-            what == #addition ifTrue:[
-                newLine isForAddition.
-            ] ifFalse:[
-                what == #modification ifTrue:[
-                    newLine isForModification.
-                ]
-            ]
-        ]
-    ].
+    ] ifFalse:[ what == #deletion ifTrue:[
+        newLine isForDeletion.
+    ] ifFalse:[ what == #addition ifTrue:[
+        newLine isForAddition.
+    ] ifFalse:[ what == #modification ifTrue:[
+        newLine isForModification.
+    ] ifFalse:[ what == #formatted ifTrue:[
+        newLine isForFormatted.
+    ] ifFalse:[ what == #commented ifTrue:[
+        newLine isForCommented.
+    ] ifFalse:[ what == #variableRenamed ifTrue:[
+        newLine isForVariableRenamed
+    ] ifFalse:[ 
+        self breakPoint:#cg
+    ]]]]]]].
     argument notNil ifTrue:[
         newLine what:argument
     ].
 
     "extract source body."
-    previousHistories isEmpty ifTrue: [
+    histories := self class getAllHistoriesFrom:someString.
+    histories isEmpty ifTrue: [
         sourceCode := someString withoutSeparators.
     ] ifFalse: [
-        pos := (previousHistories first) firstPositionInSourceCode.
+        pos := (histories first) firstPositionInSourceCode.
         sourceCode := (someString copyFrom: 1 to: pos - 1) withoutSeparators.
     ].
 
     "add the actual user's historyLine."
-    previousHistories add:newLine.
+    histLines := (previousHistories ? histories).
+    histLines add:newLine.
 
     doFilter ifTrue:[
         "Filtering historyLines (each user with one entry)."
-        histLines := HistoryLine filterHistoryLines: previousHistories.
-    ] ifFalse:[
-        histLines := previousHistories
+        histLines := HistoryLine filterHistoryLines: histLines.
     ].
 
     "create new method body with added historyLine"
@@ -747,10 +822,7 @@
 
     ^ wStream contents.
 
-    "Modified: / 11-08-1995 / 16:51:50 / robert"
-    "Modified: / 08-09-1995 / 17:55:38 / claus"
-    "Created: / 24-10-1997 / 00:16:38 / cg"
-    "Modified: / 18-09-2006 / 20:48:58 / cg"
+    "Modified: / 30-06-2011 / 17:07:18 / cg"
 !
 
 addHistory:what with:arg toHistoryMethodOf:aClass
@@ -793,7 +865,10 @@
             inCategory:'documentation'
     ].
 
-    "Modified: / 13-07-2006 / 17:42:25 / cg"
+    "Modified (Format): / 30-06-2011 / 17:11:38 / cg"
+    "Modified (Format): / 30-06-2011 / 17:11:42 / cg"
+    "Modified (Format): / 30-06-2011 / 17:11:45 / cg"
+    "Modified (Format): / 30-06-2011 / 17:11:47 / cg"
 ! !
 
 !HistoryManager::HistoryLine class methodsFor:'converting'!
@@ -801,13 +876,25 @@
 convertStringToDate: aString
     "kludge"
 
-    | day month year words |
+    | day month year words firstNumber |
 
     "delete delimiter from the date string"
     words := aString asCollectionOfSubstringsSeparatedByAny:'.-/'.
 
-    day := Number readFromString:(words at: 1).
-    month := Number readFrom:(words at: 2 ) onError:nil.
+    "/ figure out if european or yyyy-mm-dd format
+    firstNumber := Number readFromString:(words at: 1).
+    firstNumber > 1900 ifTrue:[
+        year := firstNumber.
+        month := Number readFrom:(words at: 2 ) onError:nil.
+        day := Number readFromString:(words at: 3 ).
+    ] ifFalse:[
+        day := firstNumber.
+        month := Number readFrom:(words at: 2 ) onError:nil.
+        year := Number readFromString:(words at: 3 ).
+        (year between:0 and:99) ifTrue:[
+            year := UserPreferences current twoDigitDateHandler value:year.
+        ].
+    ].
     month isNil ifTrue:[
         month := Date indexOfMonth:(words at:2) language:#en.
         month == 0 ifTrue:[
@@ -818,23 +905,20 @@
             ^ Date today.
         ].
     ].
-    year := Number readFromString:(words at: 3 ).
 
-    (year between:0 and:99) ifTrue:[
-        year := UserPreferences current twoDigitDateHandler value:year.
-    ].
     ^ Date newDay:day month:month year:year.
 
     "
-     HistoryLine convertStringToDate:'18.10.1995'
+     HistoryLine convertStringToDate:'18.10.1995' 
      HistoryLine convertStringToDate:'18.10.95'    
      HistoryLine convertStringToDate:'18.10.01'    
+     HistoryLine convertStringToDate:'2001-03-01'    
     "
 
     "Modified: / 23-08-1995 / 21:28:58 / robert"
     "Modified: / 16-09-1997 / 14:35:03 / stefan"
     "Created: / 06-03-2007 / 17:04:34 / cg"
-    "Modified: / 06-03-2007 / 18:28:57 / cg"
+    "Modified (Comment): / 30-06-2011 / 18:37:09 / cg"
 !
 
 convertStringToTime: aString
@@ -909,43 +993,50 @@
 !
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic3/HistoryManager.st,v 1.73 2011-01-31 17:31:22 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic3/HistoryManager.st,v 1.74 2011-06-30 17:09:51 cg Exp $'
 ! !
 
 !HistoryManager::HistoryLine class methodsFor:'filtering'!
 
-filterHistoryLines:  aCollectionOfHistoryLines
+filterHistoryLines:aCollectionOfHistoryLines
     "check the collection against multiple occurrence of the same user,
      and remove all but the youngest (per user)."
 
-    |newCollection|
+    |newCollection skipNext|
 
+    skipNext := false.
     newCollection := OrderedCollection new.
     aCollectionOfHistoryLines keysAndValuesDo:[:index :histLine |
         |skip|
 
-        skip := false.
-        histLine isModified ifTrue:[
-            "/ if there is another one, skip this
-            aCollectionOfHistoryLines from:index+1 do:[:anotherHistLine |
-                ((anotherHistLine isModified 
-                    and: [anotherHistLine user = histLine user])
-                        and:[anotherHistLine what = histLine what])
-                            ifTrue:[skip := true]
-                ].
+        skip := skipNext.
+        skipNext := false.
+        histLine isKindOfModified ifTrue:[
+            aCollectionOfHistoryLines do: [:anotherHistLine |
+                (anotherHistLine isCreated and: [anotherHistLine user = histLine user])
+                ifTrue: [
+                    (self timeIsShortFrom:histLine to:anotherHistLine) ifTrue: [skip := true]
+                ]
+            ].
+
             skip ifFalse: [
-                aCollectionOfHistoryLines do: [:anotherHistLine |
-                    (anotherHistLine isCreated and: [anotherHistLine user = histLine user])
-                        ifTrue: [
-                            ((Timestamp
-                                fromDate: histLine date
-                                andTime: histLine time) secondDeltaFrom:
-                                    (Timestamp
-                                        fromDate: anotherHistLine date
-                                        andTime: anotherHistLine time)) < self modificationLimit
-                            ifTrue: [skip := true]
-                        ]
-                ]
+               "/ if there is another one, skip this
+                aCollectionOfHistoryLines from:index+1 do:[:anotherHistLine |
+                    (anotherHistLine isKindOfModified 
+                    and:[anotherHistLine user = histLine user
+                    and:[anotherHistLine what = histLine what]])
+                    ifTrue:[
+                        "/ don't replace a modified by a modified format
+                        (histLine isModified not or:[anotherHistLine isModified]) ifTrue:[
+                            skip := true
+                        ] ifFalse:[
+                            "/ remove next comment/format modification if this is a modified
+                            (histLine isModified and:[anotherHistLine isModified not]) ifTrue:[
+                                (self timeIsShortFrom:histLine to:anotherHistLine) ifTrue: [skip := true]
+                            ].
+                        ].
+                    ]
+                ].
             ]
         ] ifFalse:[
             "/ filter out multiple created messages
@@ -955,6 +1046,16 @@
                     (anotherHistLine isCreated and:[anotherHistLine what = histLine what]) 
                         ifTrue:[skip := true]
                 ].
+                skip ifFalse:[
+                    "/ create followed by a modification, within the historyManagerModificationLimit:
+                    "/ skip the modified message
+                    (index+1) == aCollectionOfHistoryLines size ifTrue:[
+                        | anotherHistLine |
+                        anotherHistLine := aCollectionOfHistoryLines at:index+1.
+                        (anotherHistLine isKindOfModified and:[anotherHistLine user = histLine user]) 
+                            ifTrue:[skipNext := true]
+                    ].
+                ].
             ].
         ].
         skip ifFalse:[
@@ -966,7 +1067,7 @@
     "Modified: / 08-09-1995 / 17:20:40 / claus"
     "Modified: / 20-06-2004 / 16:36:00 / masca"
     "Modified: / 01-09-2004 / 20:20:42 / janfrog"
-    "Modified: / 12-01-2008 / 10:37:25 / cg"
+    "Modified: / 30-06-2011 / 18:32:22 / cg"
 !
 
 modificationLimit
@@ -978,6 +1079,16 @@
 
     "Created: / 20.6.2004 / 16:32:35 / masca"
     "Modified: / 2.9.2004 / 15:33:09 / janfrog"
+!
+
+timeIsShortFrom:histLine1 to:histLine2
+    |t1 t2|
+
+    t1 := (Timestamp fromDate: histLine1 date andTime: histLine1 time).
+    t2 := (Timestamp fromDate: histLine2 date andTime: histLine2 time).
+    ^ (t1 secondDeltaFrom:t2) abs < self modificationLimit
+
+    "Created: / 30-06-2011 / 18:23:04 / cg"
 ! !
 
 !HistoryManager::HistoryLine class methodsFor:'initialization'!
@@ -992,6 +1103,9 @@
         DeletedString := 'Deleted:'.
         CreatedString := 'Created:'.
         AddedString := 'Added:'.
+        FormattedString := 'Modified (format):'.
+        CommentedString := 'Modified (comment):'.
+        VariableRenamedString := 'Modified (variable name):'.
         IndentString := '    '.
         UseGECOS := false.
     ]
@@ -1000,14 +1114,8 @@
      HistoryLine initialize
     "
 
-    "Modified: 23.8.1995 / 22:14:03 / robert"
-    "Modified: 20.4.1996 / 20:23:29 / cg"
-
-    "Modified: 24.10.1997 / 01:18:56 / cg"
-
-    "Modified: / 24.10.1997 / 02:01:20 / cg"
-
-    "Modified:  24.10.1997  02:07:16  cg"
+    "Modified: / 23-08-1995 / 22:14:03 / robert"
+    "Modified: / 30-06-2011 / 12:28:43 / cg"
 ! !
 
 !HistoryManager::HistoryLine class methodsFor:'instance creation'!
@@ -1032,16 +1140,24 @@
      The positionvalue is normally used to remove the HistoryLines from the sourceCode.
      Claus: return nil, if the string is not a valid historyString."
 
-    | inst anArray type aTime aDate userName idx what|
+    |inst array type aTime aDate userName idx what|
 
     inst := self basicNew.  
 
-    anArray := aString asArrayOfSubstrings.
-    anArray size < 5 ifTrue:[^ nil].
-    anArray := anArray collect:[:word | word withoutSpaces].
+    array := aString asArrayOfSubstrings.
+    array size < 5 ifTrue:[^ nil].
+
+    array := array collect:[:word | word withoutSpaces].
+    type := array at:1.
+
+    "/ kludge for the 'Modified (what)' strings
+    ((array at:2) startsWith:'(') ifTrue:[
+        type := type , ' ' , (array at:2).
+        array := (Array with:type) , (array copyFrom:3)
+    ].
 
     "
-        Modified / Deleted / Created
+     Modified [(detail)] / Deleted / Created
         [what]
         Separator
         date asString
@@ -1051,47 +1167,49 @@
         UserName ...
     "
 
-    type := anArray at:1.
-
     ((Array 
         with:ModifiedString
         with:DeletedString
         with:CreatedString
-        with:AddedString) includes:type) ifFalse:[^ nil].
+        with:AddedString
+        with:FormattedString 
+        with:CommentedString 
+        with:VariableRenamedString
+    ) includes:type) ifFalse:[^ nil].
 
     inst type:type.
 
     "/ sigh backward compatibility ...
 
-    (anArray at:2) first isDigit ifTrue:[
+    (array at:2) first isDigit ifTrue:[
         "/ date follows ...
         idx := 2
     ] ifFalse:[
-        idx := anArray indexOf:Separator startingAt:2.
+        idx := array indexOf:Separator startingAt:2.
         idx == 0 ifTrue:[
             "/ not a valid history string
             ^ nil
         ].
 
         idx ~~ 2 ifTrue:[
-            what := (anArray copyFrom:2 to:(idx-1)) asStringWith:(Character space).
+            what := (array copyFrom:2 to:(idx-1)) asStringWith:(Character space).
             inst what:what.
         ].
 
         idx := idx + 1.
     ].
-    aDate := self convertStringToDate: (anArray at: idx).
+    aDate := self convertStringToDate: (array at: idx).
     inst date: aDate.
-    (anArray at:idx+1) ~= Separator ifTrue:[^ nil].
+    (array at:idx+1) ~= Separator ifTrue:[^ nil].
     idx := idx + 2.
 
-    aTime := self convertStringToTime: (anArray at: idx).
+    aTime := self convertStringToTime: (array at: idx).
     inst time: aTime.
-    (anArray at:idx+1) ~= Separator ifTrue:[^ nil].
+    (array at:idx+1) ~= Separator ifTrue:[^ nil].
     idx := idx + 2.
 
     "the user's name may be more that one word"
-    userName := (anArray copyFrom:idx) asStringWith:Character space.
+    userName := (array copyFrom:idx) asStringWith:Character space.
 
     inst user:userName.
     inst firstPositionInSourceCode:position.
@@ -1105,9 +1223,10 @@
      HistoryLine fromString: 'Deleted: foo bar / 21.12.93 / 18:32:30 / Astrid Weisseise'
     "
 
-    "Modified: / 23.8.1995 / 22:24:47 / robert"
-    "Modified: / 19.9.1995 / 14:14:48 / claus"
-    "Modified: / 24.10.1997 / 02:10:01 / cg"
+    "Modified: / 23-08-1995 / 22:24:47 / robert"
+    "Modified: / 19-09-1995 / 14:14:48 / claus"
+    "Modified: / 30-06-2011 / 16:09:16 / cg"
+    "Modified (Comment): / 30-06-2011 / 19:08:22 / cg"
 !
 
 new
@@ -1134,7 +1253,7 @@
 
 currentUserName
     "return the current users name - 
-     thats either the userInfos-gecos field, or the users login name."
+     that's either the userInfos-gecos field, or the users login name."
 
     |nm|
 
@@ -1152,6 +1271,7 @@
 
     "Modified: / 15-07-1996 / 12:43:14 / cg"
     "Modified: / 20-06-2006 / 13:26:49 / User"
+    "Modified (Comment): / 30-06-2011 / 18:54:30 / cg"
 !
 
 type:type what:what
@@ -1179,7 +1299,7 @@
 
     ^ date
 
-    "Modified: 20.4.1996 / 20:22:12 / cg"
+    "Modified (Format): / 30-06-2011 / 16:23:15 / cg"
 !
 
 date:something
@@ -1206,6 +1326,12 @@
     type := AddedString
 !
 
+isForCommented
+    type := CommentedString
+
+    "Created: / 30-06-2011 / 12:24:22 / cg"
+!
+
 isForCreation
     type := CreatedString
 !
@@ -1214,10 +1340,23 @@
     type := DeletedString
 !
 
+isForFormatted
+    type := FormattedString
+
+    "Created: / 30-06-2011 / 12:24:11 / cg"
+!
+
 isForModification
     type := ModifiedString
 !
 
+isForVariableRenamed
+    type := VariableRenamedString
+
+    "Created: / 30-06-2011 / 12:24:36 / cg"
+    "Modified (Format): / 30-06-2011 / 12:28:27 / cg"
+!
+
 time
     "return the time"
 
@@ -1506,31 +1645,43 @@
     "Modified: 20.4.1996 / 20:20:32 / cg"
 !
 
+isKindOfModified
+    "returns true if the bodytext is ModifiedString"
+
+    ^ self isModified 
+        or:[ type = CommentedString
+        or:[ type = FormattedString
+        or:[ type = VariableRenamedString ]]]
+
+    "
+        HistoryLine new isModified
+        (HistoryLine for: 'R.Sailer') isModified 
+        HistoryLine deleted isModified 
+        (HistoryLine deletedBy: 'M.Noell') isModified 
+    "
+
+    "Created: / 30-06-2011 / 17:15:12 / cg"
+!
+
 isModified
     "returns true if the bodytext is ModifiedString"
 
     ^type = ModifiedString
 
-"
-
+    "
         HistoryLine new isModified
         (HistoryLine for: 'R.Sailer') isModified 
         HistoryLine deleted isModified 
         (HistoryLine deletedBy: 'M.Noell') isModified 
-        
-"
+    "
 
     "Modified: 20.4.1996 / 20:20:29 / cg"
 ! !
 
 !HistoryManager class methodsFor:'documentation'!
 
-version
-    ^ '$Header: /cvs/stx/stx/libbasic3/HistoryManager.st,v 1.73 2011-01-31 17:31:22 cg Exp $'
-!
-
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic3/HistoryManager.st,v 1.73 2011-01-31 17:31:22 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic3/HistoryManager.st,v 1.74 2011-06-30 17:09:51 cg Exp $'
 ! !
 
 HistoryManager initialize!