much better history in history method
authorClaus Gittinger <cg@exept.de>
Sat, 25 Oct 1997 01:08:09 +0200
changeset 624 93c286b0509a
parent 623 f047fa038d8c
child 625 06f4ed35832b
much better history in history method
HistMgr.st
HistoryManager.st
Make.proto
--- a/HistMgr.st	Fri Oct 10 19:33:06 1997 +0200
+++ b/HistMgr.st	Sat Oct 25 01:08:09 1997 +0200
@@ -11,6 +11,8 @@
  hereby transferred.
 "
 
+'From Smalltalk/X, Version:3.2.1 on 24-oct-1997 at 2:51:15 pm'                  !
+
 Object subclass:#HistoryManager
 	instanceVariableNames:'historyMode fullHistoryUpdate'
 	classVariableNames:'TheOneAndOnlyInstance'
@@ -18,6 +20,14 @@
 	category:'System-Changes-History'
 !
 
+Object subclass:#HistoryLine
+	instanceVariableNames:'date time user what firstPositionInSourceCode type'
+	classVariableNames:'Quote Separator ModifiedString DeletedString IndentString
+		UseGECOS CreatedString AddedString'
+	poolDictionaries:''
+	privateIn:HistoryManager
+!
+
 !HistoryManager class methodsFor:'documentation'!
 
 copyright 
@@ -44,11 +54,20 @@
     contains a timestamp and the name of the changing user. 
     This is acually the UniX loginname.
 
-    The Manager registers all Classes in the system to get notifications 
+    The Manager registers itself to get notifications 
     on change, intercepts them and appends a historyLine to the methods
     code.
 
-    The HistoryManager can be turned off via the Launcher menu.
+    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
+    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).
+    Full mode is enabled via:
+        HistoryManager fullHistoryUpdate:true
+    or via the Launchers compilation-settings dialog.
 
     claus:
         I changed things to avoid depending on every class in the system.
@@ -93,8 +112,8 @@
     "because there can be only ONE HistoryManager, new must me redefiend"
 
     TheOneAndOnlyInstance isNil ifTrue:[
-	TheOneAndOnlyInstance := super new initialize.
-	HistoryLine initialize.
+        TheOneAndOnlyInstance := super new initialize.
+        HistoryLine initialize.
     ].
 
    ^ TheOneAndOnlyInstance
@@ -109,6 +128,26 @@
 
 !HistoryManager class methodsFor:'accessing'!
 
+fullHistoryUpdate
+    "return true, if the historyManagement does full updates"
+
+    ^ TheOneAndOnlyInstance fullHistoryUpdate
+
+    "Modified: / 27.8.1995 / 00:32:12 / claus"
+    "Modified: / 20.4.1996 / 20:31:32 / cg"
+    "Created: / 24.10.1997 / 02:24:34 / cg"
+!
+
+fullHistoryUpdate:aBoolean
+    "set/clear, full updates"
+
+    TheOneAndOnlyInstance fullHistoryUpdate:aBoolean
+
+    "Modified: / 27.8.1995 / 00:32:12 / claus"
+    "Modified: / 20.4.1996 / 20:31:32 / cg"
+    "Created: / 24.10.1997 / 02:24:58 / cg"
+!
+
 instance
     "return the one and only historyManager instance"
 
@@ -180,6 +219,22 @@
 
 !HistoryManager class methodsFor:'helpers'!
 
+createInitialHistoryMethodIn:aClass
+    "create an initial (empty) history method"
+
+    |histStream|
+
+    histStream := '' writeStream.
+    histStream nextPutLine:'history'.
+    histStream nextPutLine:(HistoryLine newCreated printString).
+    Compiler 
+        compile:(histStream contents)
+        forClass:aClass 
+        inCategory:'documentation'.
+
+    "Created: / 24.10.1997 / 02:41:43 / cg"
+!
+
 getAllHistoriesFrom:someString
     "returns anArray of HistoryLines from a string.
      Usually, the argument is a methods source code."
@@ -340,7 +395,7 @@
 
 "/        Transcript show: 'Class definition: ', changedClass printString;cr.
         fullHistoryUpdate == true ifTrue:[
-            self addHistory:#modification toHistoryMethodOf:changedClass.
+            self addHistory:#modification with:'class definition' toHistoryMethodOf:changedClass.
         ].
         ^ self
     ].
@@ -355,7 +410,7 @@
         "/ (someArgument does not contain the class we are interested in)
 
         fullHistoryUpdate == true ifTrue:[
-            self addHistory:#modification toHistoryMethodOf:changedObject.
+            self addHistory:#modification with:'class variables' toHistoryMethodOf:changedObject.
         ].
         ^ self
     ].    
@@ -369,7 +424,7 @@
         "/ 
         fullHistoryUpdate == true ifTrue:[
             self createHistoryMethodFor:someArgument.
-            self addHistory:#creation toHistoryMethodOf:someArgument.
+            self addHistory:#creation with:nil toHistoryMethodOf:someArgument.
         ].
 
         "/ claus: old implementation
@@ -400,6 +455,11 @@
         ].
 
         something == #methodInClassRemoved ifTrue:[
+            fullHistoryUpdate == true ifTrue:[
+                changedClass := someArgument at:1.
+                selector := someArgument at:2.
+                self addHistory:#deletion with:('#' , selector) toHistoryMethodOf:changedClass.
+            ].
             ^ self.
         ].
 
@@ -430,39 +490,47 @@
             sourceCode isNil ifTrue:[
                 "method has been deleted"
 "/                Transcript showCR: 'method has been deleted'.
-            ] ifFalse:[
-                newMethod := changedClass compiledMethodAt:selector.
+                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:[
-                    oldSource := oldMethod source.
-                    oldSource notNil ifTrue:[
-                        (oldSource asString withTabsExpanded = sourceCode asString withTabsExpanded) ifTrue:[
-                             "/ no change (accepted same code again ?)
-                            ^ self
-                        ].
-                    ]
+                    what := #modification
+                ] ifFalse:[
+                    what := #creation
                 ].
 
                 "/
-                "/ dont add historylines to documentation methods ...
+                "/ update the history line-comment in
+                "/ the methods source
                 "/
-                (changedClass isMeta not
-                or:[newMethod category ~= 'documentation']) ifTrue:[
-                    oldMethod notNil ifTrue:[
-                        what := #modification
-                    ] ifFalse:[
-                        what := #creation
-                    ].
+            
+                sourceCode := self addHistory:what with:nil to:sourceCode filter:true.
+                newMethod source: sourceCode.
+"/                    Transcript showCR: 'history updated / added'.
+            ].
 
-                    "/
-                    "/ update the history line-comment in
-                    "/ the methods source
-                    "/
-                
-                    sourceCode := self addHistory:what to:sourceCode.
-                    newMethod source: sourceCode.
-"/                    Transcript showCR: 'history updated / added'.
-                ]
+            fullHistoryUpdate == true ifTrue:[
+                self addHistory:what with:('#' , selector) toHistoryMethodOf:changedClass.
             ].
             ^self
         ]. 
@@ -479,7 +547,7 @@
 
 "/            Transcript show: 'Class definition: ', changedClass printString;cr.
             fullHistoryUpdate == true ifTrue:[
-                self addHistory:#modification toHistoryMethodOf:changedClass.
+                self addHistory:#modification with:'class definition' toHistoryMethodOf:changedClass.
             ].
             ^self
         ].
@@ -489,7 +557,7 @@
     ^self
 
     "Modified: 27.8.1995 / 02:14:43 / claus"
-    "Modified: 5.7.1997 / 21:18:15 / cg"
+    "Modified: 24.10.1997 / 01:41:19 / cg"
 ! !
 
 !HistoryManager methodsFor:'initialization'!
@@ -562,7 +630,7 @@
 
 !HistoryManager methodsFor:'updateHistory'!
 
-addHistory:what to:someString
+addHistory:what with:argument to: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
@@ -578,10 +646,25 @@
 
     previousHistories := self class getAllHistoriesFrom:someString.
 
+    newLine := HistoryLine new.
+
     what == #creation ifTrue:[
-        newLine := (HistoryLine newCreated).
+        newLine isForCreation.
     ] ifFalse:[
-        newLine := (HistoryLine new)
+        what == #deletion ifTrue:[
+            newLine isForDeletion.
+        ] ifFalse:[
+            what == #addition ifTrue:[
+                newLine isForAddition.
+            ] ifFalse:[
+                what == #modification ifTrue:[
+                    newLine isForModification.
+                ]
+            ]
+        ]
+    ].
+    argument notNil ifTrue:[
+        newLine what:argument
     ].
 
     "extract source body."
@@ -595,10 +678,14 @@
     "add the actual user's historyLine."
     previousHistories add:newLine.
 
-    "Filtering historyLines (each user with one entry)."
-    histLines := HistoryLine filterHistoryLines: previousHistories.
+    doFilter ifTrue:[
+        "Filtering historyLines (each user with one entry)."
+        histLines := HistoryLine filterHistoryLines: previousHistories.
+    ] ifFalse:[
+        histLines := previousHistories
+    ].
 
-    "create new body with added historyLine"
+    "create new method body with added historyLine"
     wStream := WriteStream on: String new.
     wStream nextPutAll: sourceCode; cr.
 
@@ -612,11 +699,11 @@
 
     "Modified: 11.8.1995 / 16:51:50 / robert"
     "Modified: 8.9.1995 / 17:55:38 / claus"
-    "Created: 12.10.1996 / 20:33:35 / cg"
-    "Modified: 9.11.1996 / 00:41:51 / cg"
+    "Created: 24.10.1997 / 00:16:38 / cg"
+    "Modified: 24.10.1997 / 01:27:21 / cg"
 !
 
-addHistory:what toHistoryMethodOf:aClass
+addHistory:what with:arg toHistoryMethodOf:aClass
     "private - add a historyLine at end of the classes history methods
      source - if there is one"
 
@@ -633,13 +720,15 @@
         oldSource notNil ifTrue:[
             newSource := self 
                             addHistory:what
-                            to:oldSource. 
+                            with:arg
+                            to:oldSource
+                            filter:false. 
             historyMethod source:newSource.
         ]
     ]
 
-    "Modified: 20.4.1996 / 20:35:06 / cg"
     "Created: 12.10.1996 / 20:31:50 / cg"
+    "Modified: 24.10.1997 / 00:14:33 / cg"
 !
 
 createHistoryMethodFor:aClass
@@ -663,9 +752,740 @@
     "Modified: 14.10.1996 / 16:58:20 / cg"
 ! !
 
+!HistoryManager::HistoryLine class methodsFor:'converting'!
+
+convertAStringToADate: aString
+   "kludge while not having the Time and Date format spec Class"
+
+    | day  month year coll |
+
+    "delete delimiter from the date string"
+    aString replaceAll: $. with: $ .
+    coll := aString asArrayOfSubstrings.
+    day := (coll at: 1) asNumber.
+    month := (coll at: 2 ) asNumber.
+    year := (coll at: 3 ) asNumber.
+
+    ^Date newDay: day month: month year: year.
+
+    "
+     HistoryLine convertAStringToADate:'18.10.1995'
+     HistoryLine convertAStringToADate:'18.10.95'
+    "
+
+    "Modified: 23.8.1995 / 21:28:58 / robert"
+    "Modified: 1.7.1996 / 14:22:38 / cg"
+    "Modified: 16.9.1997 / 14:35:03 / stefan"
+!
+
+convertAStringToATime: aString
+   "kludge while not having the Time and Date format spec Class"
+
+    | h m s|
+
+    h := (aString copyFrom: 1 to: 2) asNumber.
+    m := (aString copyFrom: 4 to: 5) asNumber.
+    s := (aString copyFrom: 7 to: 8) asNumber.
+
+
+    ^Time hour:h  minutes: m seconds: s.        
+
+    "
+     HistoryLine convertAStringToATime:'18:23:15' 
+    "
+
+    "Modified: 15.08.1995 / 18:56:18 / robert"
+! !
+
+!HistoryManager::HistoryLine class methodsFor:'documentation'!
+
+copyright 
+"
+ COPYRIGHT (c) 1995 by AEG Industry Automation
+ COPYRIGHT (c) 1995 by Claus Gittinger
+	      All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
+documentation
+"
+    The class HistoryLine is part of the HistoryManagerProjcet.
+
+    HistoryLine knows how to compose and parse comment lines which are
+    used to keep track of changes. These historyLines are added at the end of
+    a methods source code and to the special history classmethod.
+
+    HistoryLine and HistoryManager where generously provided by AEG for inclusion into the
+    ST/X class delivery.
+
+    [see also:]
+        HistoryManager
+
+    [author:]
+        Robert Sailer - AEG
+"
+!
+
+examples
+"
+    HistoryLine initialize.
+
+    HistoryLine new.
+
+    HistoryLine for: 'R.Sailer'.    for integration purposes ONLY
+
+    HistoryLine deleted.
+"
+!
+
+history
+
+    "Created: / 24.10.1997 / 02:43:10 / cg"
+!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/Attic/HistMgr.st,v 1.38 1997-10-24 23:08:06 cg Exp $'
+! !
+
+!HistoryManager::HistoryLine class methodsFor:'filtering'!
+
+filterHistoryLines:  aCollectionOfHistoryLines
+    "check the collection against multiple occurrence of the same user,
+     and remove all but the youngest (per user)."
+
+    |newCollection|
+
+    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 ifTrue:[
+                    anotherHistLine user = histLine user ifTrue:[
+                        skip := true
+                    ]
+                ]
+            ].
+        ] ifFalse:[
+            "/
+            "/ filter out multiple created messages
+            "/ (this only occurs if a method was copied from ClassA to ClassB)
+            "/
+            histLine isCreated ifTrue:[
+                aCollectionOfHistoryLines from:index+1 do:[:anotherHistLine |
+                    anotherHistLine isCreated ifTrue:[
+                        skip := true
+                    ]
+                ].
+            ].
+        ].
+        skip ifFalse:[
+            newCollection add:histLine.
+        ]
+    ].
+    ^ newCollection.
+
+"/    | allUsers newCollection aHistLine |
+"/
+"/    allUsers := Set new.
+"/
+"/    anOrderdCollectionOfHistoryLines do:[ :hl| allUsers add: hl user ].
+"/
+"/    allUsers size ~~ anOrderdCollectionOfHistoryLines ifTrue:[
+"/        "there is at least one user twice"
+"/        newCollection := OrderedCollection new.
+"/        1 to: (anOrderdCollectionOfHistoryLines size - 1) do:[ :index|
+"/            aHistLine :=(anOrderdCollectionOfHistoryLines at: index).
+"/            allUsers last = aHistLine user ifFalse:[
+"/                newCollection add: aHistLine.
+"/            ].
+"/        ].
+"/        "add the last element with the actucal HistoryLine"
+"/        newCollection add: anOrderdCollectionOfHistoryLines last.
+"/
+"/
+"/        "the new collection shold now be sorted at timeStamp. --- for further study"
+"/
+"/        ^newCollection.
+"/    ].
+"/
+"/    ^ anOrderdCollectionOfHistoryLines
+
+
+    "
+     |u1 u2 u3 u4 u5 oc |
+     u1 := HistoryLine new.
+     u2 := HistoryLine for: 'claus'.
+     u3 := HistoryLine for: 'chris'.
+     u4 := HistoryLine new.
+     u5 := HistoryLine new.
+
+     oc := OrderedCollection new.
+     oc add: u1.
+     oc add: u2.
+     oc add: u3.
+     oc add: u4.
+     oc add: u5.
+
+     oc inspect.
+     (HistoryLine filterHistoryLines: oc) inspect 
+    "
+
+    "Modified: 8.9.1995 / 17:20:40 / claus"
+    "Modified: 20.4.1996 / 20:23:07 / cg"
+! !
+
+!HistoryManager::HistoryLine class methodsFor:'initialization'!
+
+initialize
+    "setup class variables"
+
+    Quote isNil ifTrue:[
+        Quote := '"'.
+        Separator := '/'.
+        ModifiedString := 'Modified:'.
+        DeletedString := 'Deleted:'.
+        CreatedString := 'Created:'.
+        AddedString := 'Added:'.
+        IndentString := '    '.
+        UseGECOS := false.
+    ]
+
+    "
+     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"
+! !
+
+!HistoryManager::HistoryLine class methodsFor:'instance creation'!
+
+fromString: aString
+    "parses the argument, aString; 
+     create & return a new Instance with the values" 
+
+    ^ self fromString: aString at: 0.
+
+    "
+     HistoryLine fromString: 'Modified: 01.12.93 / 18:32:30 / M.Noell'
+     HistoryLine fromString: 'Created: 01.12.93 / 18:32:30 / M.Noell'
+    "
+
+    "Modified: 23.8.1995 / 22:14:13 / robert"
+    "Modified: 20.4.1996 / 20:24:47 / cg"
+!
+
+fromString: aString at: position
+    "parses the String and creates a new Instance with the values. 
+     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 strings|
+
+    inst := self basicNew.  
+
+    anArray := aString asArrayOfSubstrings.
+    anArray size < 5 ifTrue:[^ nil].
+    anArray := anArray collect:[:word | word withoutSpaces].
+
+    "
+        Modified / Deleted / Created
+        [what]
+        Separator
+        date asString
+        Separator
+        time asString
+        Separator
+        UserName ...
+    "
+
+    type := anArray at:1.
+
+    ((Array 
+        with:ModifiedString
+        with:DeletedString
+        with:CreatedString
+        with:AddedString) includes:type) ifFalse:[^ nil].
+
+    inst type:type.
+
+    "/ sigh backward compatibility ...
+
+    (anArray at:2) first isDigit ifTrue:[
+        "/ date follows ...
+        idx := 2
+    ] ifFalse:[
+        idx := anArray 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).
+            inst what:what.
+        ].
+
+        idx := idx + 1.
+    ].
+    aDate := self convertAStringToADate: (anArray at: idx).
+    inst date: aDate.
+    (anArray at:idx+1) ~= Separator ifTrue:[^ nil].
+    idx := idx + 2.
+
+    aTime := self convertAStringToATime: (anArray at: idx).
+    inst time: aTime.
+    (anArray 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.
+
+    inst user:userName.
+    inst firstPositionInSourceCode:position.
+
+    ^ inst
+
+    "
+     HistoryLine fromString: 'Modified: 21.12.93 / 18:32:30 / R.Sailer'
+     HistoryLine fromString: 'Created: 21.12.1993 / 18:32:30 / Felicitas Gabriele Felger'
+     HistoryLine fromString: 'Deleted: 21.12.93 / 18:32:30 / Astrid Weißeise'
+     HistoryLine fromString: 'Deleted: foo bar / 21.12.93 / 18:32:30 / Astrid Weißeise'
+    "
+
+    "Modified: / 23.8.1995 / 22:24:47 / robert"
+    "Modified: / 19.9.1995 / 14:14:48 / claus"
+    "Modified: / 24.10.1997 / 02:10:01 / cg"
+!
+
+new
+    "get a new history line. 
+     Preinitialize it as a modified-Line for the current user"    
+
+    ^ self type:ModifiedString what:nil
+!
+
+newCreated
+    "public - get a new created-Line for the current user"    
+
+    ^ self type:CreatedString what:nil
+
+    "
+     HistoryLine newCreated
+    "
+
+    "Modified: 23.8.1995 / 22:14:24 / robert"
+    "Modified: 24.10.1997 / 00:18:30 / cg"
+! !
+
+!HistoryManager::HistoryLine class methodsFor:'private'!
+
+currentUserName
+    "return the current users name - 
+     thats either the userInfos-gecos field, or the users login name."
+
+    UseGECOS == true ifTrue:[
+        ^ OperatingSystem getFullUserName.
+    ].
+    ^ (OperatingSystem getLoginName).
+
+    "
+     HistoryLine currentUserName
+    "
+
+    "Modified: 15.7.1996 / 12:43:14 / cg"
+!
+
+type:type what:what
+    "private - for integration purposes only"
+
+    | inst |
+
+    inst := self basicNew.
+    inst date: Date today.
+    inst time: Time now.
+    inst firstPositionInSourceCode: 0.
+    inst user:(self currentUserName).
+    inst type:type.    
+    inst what:what.    
+
+    ^ inst
+
+    "Modified: 23.08.1995 / 21:35:44 / robert"
+! !
+
+!HistoryManager::HistoryLine methodsFor:'accessing'!
+
+date
+    "return the date"
+
+    ^ date
+
+    "Modified: 20.4.1996 / 20:22:12 / cg"
+!
+
+date:something
+    "set the date"
+
+    date := something.
+
+    "Modified: 20.4.1996 / 20:22:16 / cg"
+!
+
+firstPositionInSourceCode
+    "return firstPositionInSourceCode"
+
+    ^ firstPositionInSourceCode!
+
+firstPositionInSourceCode:something
+    "set firstPositionInSourceCode"
+
+    firstPositionInSourceCode := something.!
+
+isForAddition
+    type := AddedString
+!
+
+isForCreation
+    type := CreatedString
+!
+
+isForDeletion
+    type := DeletedString
+!
+
+isForModification
+    type := ModifiedString
+!
+
+time
+    "return the time"
+
+    ^ time
+
+    "Modified: 20.4.1996 / 20:22:04 / cg"
+!
+
+time:something
+    "set the time"
+
+    time := something.
+
+    "Modified: 20.4.1996 / 20:21:58 / cg"
+!
+
+type
+    "return the type"
+
+    ^ type
+
+    "Modified: 20.4.1996 / 20:21:54 / cg"
+!
+
+type:something
+    "set the type"
+
+    type := something.
+
+    "Modified: 20.4.1996 / 20:21:39 / cg"
+!
+
+user
+    "return the user"
+
+    ^ user
+
+    "Modified: 20.4.1996 / 20:21:45 / cg"
+!
+
+user:something
+    "set the user"
+
+    user := something.
+
+    "Modified: 20.4.1996 / 20:21:48 / cg"
+!
+
+what
+    "return the what-changed info"
+
+    ^ what
+
+    "Modified: 20.4.1996 / 20:21:54 / cg"
+    "Created: 24.10.1997 / 00:20:33 / cg"
+!
+
+what:someStringOrSelector
+    "set the what-changed info"
+
+    what := someStringOrSelector
+
+    "Modified: 20.4.1996 / 20:21:54 / cg"
+    "Created: 24.10.1997 / 00:21:00 / cg"
+! !
+
+!HistoryManager::HistoryLine methodsFor:'comparing'!
+
+= aHistoryLine
+    "compares two instances of HistoryLine"
+
+    (aHistoryLine user = self user) ifTrue:[
+        (aHistoryLine date = self date) ifTrue:[
+            (aHistoryLine time = self time) ifTrue:[
+                (aHistoryLine type = self type) ifTrue:[
+                    (aHistoryLine what = self what) ifTrue:[
+                        ^ true
+                    ]
+                ]
+            ]
+        ]
+    ].
+
+    ^ false
+
+"
+    | h1 h2 |
+
+    h1 := HistoryLine for: OperatingSystem getLoginName.
+    h2 := h1 copy.
+
+    h1 = h2 ifTrue:[
+        InfoBox new title: 'users are equal'; show.
+    ].
+
+    h2 := HistoryLine for: OperatingSystem getLoginName.
+    h1 = h2 ifFalse:[
+        InfoBox new title: 'users are not equal'; show.
+    ].
+"
+
+    "Modified: 23.8.1995 / 22:26:40 / robert"
+    "Modified: 24.10.1997 / 00:22:09 / cg"
+!
+
+hash
+    "return a hash key for the receiver"
+
+    ^user hash        
+
+"
+    Check hashCode
+
+    |h1 h2 oc |
+
+    h1 := HistoryLine new hash.
+    h2 := HistoryLine new hash.
+    oc := OrderedCollection new.
+    oc add: h1.
+    oc add: h2.
+    ^oc
+
+    using hash in a set:
+
+    | h1 h2 aSet oc |
+    h1 := HistoryLine new hash.
+    h2 := HistoryLine new hash.
+    oc := OrderedCollection new.
+    oc add: h1.
+    oc add: h2.
+    aSet := oc asSet.
+    ^aSet
+"
+
+    "Modified: 23.08.1995 / 22:26:44 / robert"
+!
+
+sameDate: aHistoryLine
+    "returns true if aUserName = user in preperation for a SortedCollection of HistoryLines"
+
+    ^aHistoryLine date = date
+
+"
+    | h1 h2 |
+
+    h1 := HistoryLine new.
+    h2 := h1 copy.
+
+    (h1 sameDate: h2)  ifTrue:[
+	InfoBox new title: 'Dates are equal'; show.
+    ].
+
+    h2 := HistoryLine for: 'R.Sailer'.
+    h2 date: (Date day: 12 month: 6 year:1981).
+    (h1 sameDate: h2) ifFalse:[
+	InfoBox new title: 'users are not equal'; show.
+    ].
+
+"
+
+    "Modified: 23.08.1995 / 22:26:47 / robert"
+!
+
+sameType: aHistoryLine
+    "returns true if the Type = type in preperation for a SortedCollection of HistoryLines"
+
+    ^aHistoryLine type = type
+
+"
+    | h1 h2 |
+
+    h1 := HistoryLine new.
+    h2 := h1 copy.
+
+    (h1 sameType: h2)  ifTrue:[
+	InfoBox new title: 'Types are equal'; show.
+    ].
+
+    h2 := HistoryLine createdBy: 'R.Sailer'.
+    (h1 sameType: h2) ifFalse:[
+	InfoBox new title: 'Types are not equal'; show.
+    ].
+
+"
+
+    "Modified: 23.08.1995 / 22:26:49 / robert"
+!
+
+sameUser: aHistoryLine
+    "returns true if aUserName = user in preperation for a SortedCollection of HistoryLines"
+
+    ^aHistoryLine user = user
+
+
+"
+    | h1 h2 |
+
+    h1 := HistoryLine new.
+    h2 := h1 copy.
+
+    (h1 sameUser: h2)  ifTrue:[
+	InfoBox new title: 'users are equal'; show.
+    ].
+
+    h2 := HistoryLine for: 'R.Sailer'.
+    (h1 sameUser: h2) ifFalse:[
+	InfoBox new title: 'users are not equal'; show.
+    ].
+
+"
+
+    "Modified: 23.08.1995 / 22:26:51 / robert"
+!
+
+sameWhat: aHistoryLine
+    "returns true if the what = type in preperation for a SortedCollection of HistoryLines"
+
+    ^aHistoryLine what = what
+
+    "Created: 24.10.1997 / 00:21:46 / cg"
+! !
+
+!HistoryManager::HistoryLine methodsFor:'printing & storing'!
+
+printString
+    "return a printed representation of a HistoryLine as a string"
+
+    | aStream |
+
+    aStream := WriteStream on: String new.
+    aStream nextPutAll:IndentString.
+    aStream nextPutAll:Quote.
+    aStream nextPutAll:type.
+    what notNil ifTrue:[
+        aStream space.
+        aStream nextPutAll:what.
+    ].
+    aStream space; nextPutAll:Separator; space.
+    aStream nextPutAll:(date printFormat:#(1 2 3 $. 1 1)).
+    aStream space; nextPutAll:Separator; space.
+    time print24HourFormatOn:aStream. 
+    aStream space; nextPutAll:Separator; space.
+    aStream nextPutAll:user.
+    aStream nextPutAll:Quote.
+    ^ aStream contents.
+
+    "Modified: 24.10.1997 / 01:46:10 / cg"
+
+    "Modified: / 24.10.1997 / 02:01:43 / cg"
+
+    "Modified:  24.10.1997  02:07:23  cg"
+! !
+
+!HistoryManager::HistoryLine methodsFor:'queries'!
+
+isCreated
+    "returns true if the bodytext is CreatedString"
+
+    ^type = CreatedString
+
+"
+
+        HistoryLine new isModified
+        (HistoryLine for: 'R.Sailer') isCreated 
+        (HistoryLine createdBy: 'R.Sailer') isCreated 
+        HistoryLine deleted isModified 
+        (HistoryLine deletedBy: 'M.Noell') isModified 
+        
+"
+
+    "Modified: 23.8.1995 / 22:30:23 / robert"
+    "Modified: 20.4.1996 / 20:20:36 / cg"
+!
+
+isDeleted
+    "returns true if the bodytext is DeletedString"
+
+    ^type = DeletedString
+
+"
+
+        HistoryLine deleted isDeleted
+        HistoryLine new isDeleted
+
+
+
+"
+
+    "Modified: 20.4.1996 / 20:20:32 / 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/Attic/HistMgr.st,v 1.37 1997-07-05 19:21:23 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic3/Attic/HistMgr.st,v 1.38 1997-10-24 23:08:06 cg Exp $'
 ! !
 HistoryManager initialize!
--- a/HistoryManager.st	Fri Oct 10 19:33:06 1997 +0200
+++ b/HistoryManager.st	Sat Oct 25 01:08:09 1997 +0200
@@ -11,6 +11,8 @@
  hereby transferred.
 "
 
+'From Smalltalk/X, Version:3.2.1 on 24-oct-1997 at 2:51:15 pm'                  !
+
 Object subclass:#HistoryManager
 	instanceVariableNames:'historyMode fullHistoryUpdate'
 	classVariableNames:'TheOneAndOnlyInstance'
@@ -18,6 +20,14 @@
 	category:'System-Changes-History'
 !
 
+Object subclass:#HistoryLine
+	instanceVariableNames:'date time user what firstPositionInSourceCode type'
+	classVariableNames:'Quote Separator ModifiedString DeletedString IndentString
+		UseGECOS CreatedString AddedString'
+	poolDictionaries:''
+	privateIn:HistoryManager
+!
+
 !HistoryManager class methodsFor:'documentation'!
 
 copyright 
@@ -44,11 +54,20 @@
     contains a timestamp and the name of the changing user. 
     This is acually the UniX loginname.
 
-    The Manager registers all Classes in the system to get notifications 
+    The Manager registers itself to get notifications 
     on change, intercepts them and appends a historyLine to the methods
     code.
 
-    The HistoryManager can be turned off via the Launcher menu.
+    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
+    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).
+    Full mode is enabled via:
+        HistoryManager fullHistoryUpdate:true
+    or via the Launchers compilation-settings dialog.
 
     claus:
         I changed things to avoid depending on every class in the system.
@@ -93,8 +112,8 @@
     "because there can be only ONE HistoryManager, new must me redefiend"
 
     TheOneAndOnlyInstance isNil ifTrue:[
-	TheOneAndOnlyInstance := super new initialize.
-	HistoryLine initialize.
+        TheOneAndOnlyInstance := super new initialize.
+        HistoryLine initialize.
     ].
 
    ^ TheOneAndOnlyInstance
@@ -109,6 +128,26 @@
 
 !HistoryManager class methodsFor:'accessing'!
 
+fullHistoryUpdate
+    "return true, if the historyManagement does full updates"
+
+    ^ TheOneAndOnlyInstance fullHistoryUpdate
+
+    "Modified: / 27.8.1995 / 00:32:12 / claus"
+    "Modified: / 20.4.1996 / 20:31:32 / cg"
+    "Created: / 24.10.1997 / 02:24:34 / cg"
+!
+
+fullHistoryUpdate:aBoolean
+    "set/clear, full updates"
+
+    TheOneAndOnlyInstance fullHistoryUpdate:aBoolean
+
+    "Modified: / 27.8.1995 / 00:32:12 / claus"
+    "Modified: / 20.4.1996 / 20:31:32 / cg"
+    "Created: / 24.10.1997 / 02:24:58 / cg"
+!
+
 instance
     "return the one and only historyManager instance"
 
@@ -180,6 +219,22 @@
 
 !HistoryManager class methodsFor:'helpers'!
 
+createInitialHistoryMethodIn:aClass
+    "create an initial (empty) history method"
+
+    |histStream|
+
+    histStream := '' writeStream.
+    histStream nextPutLine:'history'.
+    histStream nextPutLine:(HistoryLine newCreated printString).
+    Compiler 
+        compile:(histStream contents)
+        forClass:aClass 
+        inCategory:'documentation'.
+
+    "Created: / 24.10.1997 / 02:41:43 / cg"
+!
+
 getAllHistoriesFrom:someString
     "returns anArray of HistoryLines from a string.
      Usually, the argument is a methods source code."
@@ -340,7 +395,7 @@
 
 "/        Transcript show: 'Class definition: ', changedClass printString;cr.
         fullHistoryUpdate == true ifTrue:[
-            self addHistory:#modification toHistoryMethodOf:changedClass.
+            self addHistory:#modification with:'class definition' toHistoryMethodOf:changedClass.
         ].
         ^ self
     ].
@@ -355,7 +410,7 @@
         "/ (someArgument does not contain the class we are interested in)
 
         fullHistoryUpdate == true ifTrue:[
-            self addHistory:#modification toHistoryMethodOf:changedObject.
+            self addHistory:#modification with:'class variables' toHistoryMethodOf:changedObject.
         ].
         ^ self
     ].    
@@ -369,7 +424,7 @@
         "/ 
         fullHistoryUpdate == true ifTrue:[
             self createHistoryMethodFor:someArgument.
-            self addHistory:#creation toHistoryMethodOf:someArgument.
+            self addHistory:#creation with:nil toHistoryMethodOf:someArgument.
         ].
 
         "/ claus: old implementation
@@ -400,6 +455,11 @@
         ].
 
         something == #methodInClassRemoved ifTrue:[
+            fullHistoryUpdate == true ifTrue:[
+                changedClass := someArgument at:1.
+                selector := someArgument at:2.
+                self addHistory:#deletion with:('#' , selector) toHistoryMethodOf:changedClass.
+            ].
             ^ self.
         ].
 
@@ -430,39 +490,47 @@
             sourceCode isNil ifTrue:[
                 "method has been deleted"
 "/                Transcript showCR: 'method has been deleted'.
-            ] ifFalse:[
-                newMethod := changedClass compiledMethodAt:selector.
+                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:[
-                    oldSource := oldMethod source.
-                    oldSource notNil ifTrue:[
-                        (oldSource asString withTabsExpanded = sourceCode asString withTabsExpanded) ifTrue:[
-                             "/ no change (accepted same code again ?)
-                            ^ self
-                        ].
-                    ]
+                    what := #modification
+                ] ifFalse:[
+                    what := #creation
                 ].
 
                 "/
-                "/ dont add historylines to documentation methods ...
+                "/ update the history line-comment in
+                "/ the methods source
                 "/
-                (changedClass isMeta not
-                or:[newMethod category ~= 'documentation']) ifTrue:[
-                    oldMethod notNil ifTrue:[
-                        what := #modification
-                    ] ifFalse:[
-                        what := #creation
-                    ].
+            
+                sourceCode := self addHistory:what with:nil to:sourceCode filter:true.
+                newMethod source: sourceCode.
+"/                    Transcript showCR: 'history updated / added'.
+            ].
 
-                    "/
-                    "/ update the history line-comment in
-                    "/ the methods source
-                    "/
-                
-                    sourceCode := self addHistory:what to:sourceCode.
-                    newMethod source: sourceCode.
-"/                    Transcript showCR: 'history updated / added'.
-                ]
+            fullHistoryUpdate == true ifTrue:[
+                self addHistory:what with:('#' , selector) toHistoryMethodOf:changedClass.
             ].
             ^self
         ]. 
@@ -479,7 +547,7 @@
 
 "/            Transcript show: 'Class definition: ', changedClass printString;cr.
             fullHistoryUpdate == true ifTrue:[
-                self addHistory:#modification toHistoryMethodOf:changedClass.
+                self addHistory:#modification with:'class definition' toHistoryMethodOf:changedClass.
             ].
             ^self
         ].
@@ -489,7 +557,7 @@
     ^self
 
     "Modified: 27.8.1995 / 02:14:43 / claus"
-    "Modified: 5.7.1997 / 21:18:15 / cg"
+    "Modified: 24.10.1997 / 01:41:19 / cg"
 ! !
 
 !HistoryManager methodsFor:'initialization'!
@@ -562,7 +630,7 @@
 
 !HistoryManager methodsFor:'updateHistory'!
 
-addHistory:what to:someString
+addHistory:what with:argument to: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
@@ -578,10 +646,25 @@
 
     previousHistories := self class getAllHistoriesFrom:someString.
 
+    newLine := HistoryLine new.
+
     what == #creation ifTrue:[
-        newLine := (HistoryLine newCreated).
+        newLine isForCreation.
     ] ifFalse:[
-        newLine := (HistoryLine new)
+        what == #deletion ifTrue:[
+            newLine isForDeletion.
+        ] ifFalse:[
+            what == #addition ifTrue:[
+                newLine isForAddition.
+            ] ifFalse:[
+                what == #modification ifTrue:[
+                    newLine isForModification.
+                ]
+            ]
+        ]
+    ].
+    argument notNil ifTrue:[
+        newLine what:argument
     ].
 
     "extract source body."
@@ -595,10 +678,14 @@
     "add the actual user's historyLine."
     previousHistories add:newLine.
 
-    "Filtering historyLines (each user with one entry)."
-    histLines := HistoryLine filterHistoryLines: previousHistories.
+    doFilter ifTrue:[
+        "Filtering historyLines (each user with one entry)."
+        histLines := HistoryLine filterHistoryLines: previousHistories.
+    ] ifFalse:[
+        histLines := previousHistories
+    ].
 
-    "create new body with added historyLine"
+    "create new method body with added historyLine"
     wStream := WriteStream on: String new.
     wStream nextPutAll: sourceCode; cr.
 
@@ -612,11 +699,11 @@
 
     "Modified: 11.8.1995 / 16:51:50 / robert"
     "Modified: 8.9.1995 / 17:55:38 / claus"
-    "Created: 12.10.1996 / 20:33:35 / cg"
-    "Modified: 9.11.1996 / 00:41:51 / cg"
+    "Created: 24.10.1997 / 00:16:38 / cg"
+    "Modified: 24.10.1997 / 01:27:21 / cg"
 !
 
-addHistory:what toHistoryMethodOf:aClass
+addHistory:what with:arg toHistoryMethodOf:aClass
     "private - add a historyLine at end of the classes history methods
      source - if there is one"
 
@@ -633,13 +720,15 @@
         oldSource notNil ifTrue:[
             newSource := self 
                             addHistory:what
-                            to:oldSource. 
+                            with:arg
+                            to:oldSource
+                            filter:false. 
             historyMethod source:newSource.
         ]
     ]
 
-    "Modified: 20.4.1996 / 20:35:06 / cg"
     "Created: 12.10.1996 / 20:31:50 / cg"
+    "Modified: 24.10.1997 / 00:14:33 / cg"
 !
 
 createHistoryMethodFor:aClass
@@ -663,9 +752,740 @@
     "Modified: 14.10.1996 / 16:58:20 / cg"
 ! !
 
+!HistoryManager::HistoryLine class methodsFor:'converting'!
+
+convertAStringToADate: aString
+   "kludge while not having the Time and Date format spec Class"
+
+    | day  month year coll |
+
+    "delete delimiter from the date string"
+    aString replaceAll: $. with: $ .
+    coll := aString asArrayOfSubstrings.
+    day := (coll at: 1) asNumber.
+    month := (coll at: 2 ) asNumber.
+    year := (coll at: 3 ) asNumber.
+
+    ^Date newDay: day month: month year: year.
+
+    "
+     HistoryLine convertAStringToADate:'18.10.1995'
+     HistoryLine convertAStringToADate:'18.10.95'
+    "
+
+    "Modified: 23.8.1995 / 21:28:58 / robert"
+    "Modified: 1.7.1996 / 14:22:38 / cg"
+    "Modified: 16.9.1997 / 14:35:03 / stefan"
+!
+
+convertAStringToATime: aString
+   "kludge while not having the Time and Date format spec Class"
+
+    | h m s|
+
+    h := (aString copyFrom: 1 to: 2) asNumber.
+    m := (aString copyFrom: 4 to: 5) asNumber.
+    s := (aString copyFrom: 7 to: 8) asNumber.
+
+
+    ^Time hour:h  minutes: m seconds: s.        
+
+    "
+     HistoryLine convertAStringToATime:'18:23:15' 
+    "
+
+    "Modified: 15.08.1995 / 18:56:18 / robert"
+! !
+
+!HistoryManager::HistoryLine class methodsFor:'documentation'!
+
+copyright 
+"
+ COPYRIGHT (c) 1995 by AEG Industry Automation
+ COPYRIGHT (c) 1995 by Claus Gittinger
+	      All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
+documentation
+"
+    The class HistoryLine is part of the HistoryManagerProjcet.
+
+    HistoryLine knows how to compose and parse comment lines which are
+    used to keep track of changes. These historyLines are added at the end of
+    a methods source code and to the special history classmethod.
+
+    HistoryLine and HistoryManager where generously provided by AEG for inclusion into the
+    ST/X class delivery.
+
+    [see also:]
+        HistoryManager
+
+    [author:]
+        Robert Sailer - AEG
+"
+!
+
+examples
+"
+    HistoryLine initialize.
+
+    HistoryLine new.
+
+    HistoryLine for: 'R.Sailer'.    for integration purposes ONLY
+
+    HistoryLine deleted.
+"
+!
+
+history
+
+    "Created: / 24.10.1997 / 02:43:10 / cg"
+!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic3/HistoryManager.st,v 1.38 1997-10-24 23:08:06 cg Exp $'
+! !
+
+!HistoryManager::HistoryLine class methodsFor:'filtering'!
+
+filterHistoryLines:  aCollectionOfHistoryLines
+    "check the collection against multiple occurrence of the same user,
+     and remove all but the youngest (per user)."
+
+    |newCollection|
+
+    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 ifTrue:[
+                    anotherHistLine user = histLine user ifTrue:[
+                        skip := true
+                    ]
+                ]
+            ].
+        ] ifFalse:[
+            "/
+            "/ filter out multiple created messages
+            "/ (this only occurs if a method was copied from ClassA to ClassB)
+            "/
+            histLine isCreated ifTrue:[
+                aCollectionOfHistoryLines from:index+1 do:[:anotherHistLine |
+                    anotherHistLine isCreated ifTrue:[
+                        skip := true
+                    ]
+                ].
+            ].
+        ].
+        skip ifFalse:[
+            newCollection add:histLine.
+        ]
+    ].
+    ^ newCollection.
+
+"/    | allUsers newCollection aHistLine |
+"/
+"/    allUsers := Set new.
+"/
+"/    anOrderdCollectionOfHistoryLines do:[ :hl| allUsers add: hl user ].
+"/
+"/    allUsers size ~~ anOrderdCollectionOfHistoryLines ifTrue:[
+"/        "there is at least one user twice"
+"/        newCollection := OrderedCollection new.
+"/        1 to: (anOrderdCollectionOfHistoryLines size - 1) do:[ :index|
+"/            aHistLine :=(anOrderdCollectionOfHistoryLines at: index).
+"/            allUsers last = aHistLine user ifFalse:[
+"/                newCollection add: aHistLine.
+"/            ].
+"/        ].
+"/        "add the last element with the actucal HistoryLine"
+"/        newCollection add: anOrderdCollectionOfHistoryLines last.
+"/
+"/
+"/        "the new collection shold now be sorted at timeStamp. --- for further study"
+"/
+"/        ^newCollection.
+"/    ].
+"/
+"/    ^ anOrderdCollectionOfHistoryLines
+
+
+    "
+     |u1 u2 u3 u4 u5 oc |
+     u1 := HistoryLine new.
+     u2 := HistoryLine for: 'claus'.
+     u3 := HistoryLine for: 'chris'.
+     u4 := HistoryLine new.
+     u5 := HistoryLine new.
+
+     oc := OrderedCollection new.
+     oc add: u1.
+     oc add: u2.
+     oc add: u3.
+     oc add: u4.
+     oc add: u5.
+
+     oc inspect.
+     (HistoryLine filterHistoryLines: oc) inspect 
+    "
+
+    "Modified: 8.9.1995 / 17:20:40 / claus"
+    "Modified: 20.4.1996 / 20:23:07 / cg"
+! !
+
+!HistoryManager::HistoryLine class methodsFor:'initialization'!
+
+initialize
+    "setup class variables"
+
+    Quote isNil ifTrue:[
+        Quote := '"'.
+        Separator := '/'.
+        ModifiedString := 'Modified:'.
+        DeletedString := 'Deleted:'.
+        CreatedString := 'Created:'.
+        AddedString := 'Added:'.
+        IndentString := '    '.
+        UseGECOS := false.
+    ]
+
+    "
+     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"
+! !
+
+!HistoryManager::HistoryLine class methodsFor:'instance creation'!
+
+fromString: aString
+    "parses the argument, aString; 
+     create & return a new Instance with the values" 
+
+    ^ self fromString: aString at: 0.
+
+    "
+     HistoryLine fromString: 'Modified: 01.12.93 / 18:32:30 / M.Noell'
+     HistoryLine fromString: 'Created: 01.12.93 / 18:32:30 / M.Noell'
+    "
+
+    "Modified: 23.8.1995 / 22:14:13 / robert"
+    "Modified: 20.4.1996 / 20:24:47 / cg"
+!
+
+fromString: aString at: position
+    "parses the String and creates a new Instance with the values. 
+     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 strings|
+
+    inst := self basicNew.  
+
+    anArray := aString asArrayOfSubstrings.
+    anArray size < 5 ifTrue:[^ nil].
+    anArray := anArray collect:[:word | word withoutSpaces].
+
+    "
+        Modified / Deleted / Created
+        [what]
+        Separator
+        date asString
+        Separator
+        time asString
+        Separator
+        UserName ...
+    "
+
+    type := anArray at:1.
+
+    ((Array 
+        with:ModifiedString
+        with:DeletedString
+        with:CreatedString
+        with:AddedString) includes:type) ifFalse:[^ nil].
+
+    inst type:type.
+
+    "/ sigh backward compatibility ...
+
+    (anArray at:2) first isDigit ifTrue:[
+        "/ date follows ...
+        idx := 2
+    ] ifFalse:[
+        idx := anArray 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).
+            inst what:what.
+        ].
+
+        idx := idx + 1.
+    ].
+    aDate := self convertAStringToADate: (anArray at: idx).
+    inst date: aDate.
+    (anArray at:idx+1) ~= Separator ifTrue:[^ nil].
+    idx := idx + 2.
+
+    aTime := self convertAStringToATime: (anArray at: idx).
+    inst time: aTime.
+    (anArray 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.
+
+    inst user:userName.
+    inst firstPositionInSourceCode:position.
+
+    ^ inst
+
+    "
+     HistoryLine fromString: 'Modified: 21.12.93 / 18:32:30 / R.Sailer'
+     HistoryLine fromString: 'Created: 21.12.1993 / 18:32:30 / Felicitas Gabriele Felger'
+     HistoryLine fromString: 'Deleted: 21.12.93 / 18:32:30 / Astrid Weißeise'
+     HistoryLine fromString: 'Deleted: foo bar / 21.12.93 / 18:32:30 / Astrid Weißeise'
+    "
+
+    "Modified: / 23.8.1995 / 22:24:47 / robert"
+    "Modified: / 19.9.1995 / 14:14:48 / claus"
+    "Modified: / 24.10.1997 / 02:10:01 / cg"
+!
+
+new
+    "get a new history line. 
+     Preinitialize it as a modified-Line for the current user"    
+
+    ^ self type:ModifiedString what:nil
+!
+
+newCreated
+    "public - get a new created-Line for the current user"    
+
+    ^ self type:CreatedString what:nil
+
+    "
+     HistoryLine newCreated
+    "
+
+    "Modified: 23.8.1995 / 22:14:24 / robert"
+    "Modified: 24.10.1997 / 00:18:30 / cg"
+! !
+
+!HistoryManager::HistoryLine class methodsFor:'private'!
+
+currentUserName
+    "return the current users name - 
+     thats either the userInfos-gecos field, or the users login name."
+
+    UseGECOS == true ifTrue:[
+        ^ OperatingSystem getFullUserName.
+    ].
+    ^ (OperatingSystem getLoginName).
+
+    "
+     HistoryLine currentUserName
+    "
+
+    "Modified: 15.7.1996 / 12:43:14 / cg"
+!
+
+type:type what:what
+    "private - for integration purposes only"
+
+    | inst |
+
+    inst := self basicNew.
+    inst date: Date today.
+    inst time: Time now.
+    inst firstPositionInSourceCode: 0.
+    inst user:(self currentUserName).
+    inst type:type.    
+    inst what:what.    
+
+    ^ inst
+
+    "Modified: 23.08.1995 / 21:35:44 / robert"
+! !
+
+!HistoryManager::HistoryLine methodsFor:'accessing'!
+
+date
+    "return the date"
+
+    ^ date
+
+    "Modified: 20.4.1996 / 20:22:12 / cg"
+!
+
+date:something
+    "set the date"
+
+    date := something.
+
+    "Modified: 20.4.1996 / 20:22:16 / cg"
+!
+
+firstPositionInSourceCode
+    "return firstPositionInSourceCode"
+
+    ^ firstPositionInSourceCode!
+
+firstPositionInSourceCode:something
+    "set firstPositionInSourceCode"
+
+    firstPositionInSourceCode := something.!
+
+isForAddition
+    type := AddedString
+!
+
+isForCreation
+    type := CreatedString
+!
+
+isForDeletion
+    type := DeletedString
+!
+
+isForModification
+    type := ModifiedString
+!
+
+time
+    "return the time"
+
+    ^ time
+
+    "Modified: 20.4.1996 / 20:22:04 / cg"
+!
+
+time:something
+    "set the time"
+
+    time := something.
+
+    "Modified: 20.4.1996 / 20:21:58 / cg"
+!
+
+type
+    "return the type"
+
+    ^ type
+
+    "Modified: 20.4.1996 / 20:21:54 / cg"
+!
+
+type:something
+    "set the type"
+
+    type := something.
+
+    "Modified: 20.4.1996 / 20:21:39 / cg"
+!
+
+user
+    "return the user"
+
+    ^ user
+
+    "Modified: 20.4.1996 / 20:21:45 / cg"
+!
+
+user:something
+    "set the user"
+
+    user := something.
+
+    "Modified: 20.4.1996 / 20:21:48 / cg"
+!
+
+what
+    "return the what-changed info"
+
+    ^ what
+
+    "Modified: 20.4.1996 / 20:21:54 / cg"
+    "Created: 24.10.1997 / 00:20:33 / cg"
+!
+
+what:someStringOrSelector
+    "set the what-changed info"
+
+    what := someStringOrSelector
+
+    "Modified: 20.4.1996 / 20:21:54 / cg"
+    "Created: 24.10.1997 / 00:21:00 / cg"
+! !
+
+!HistoryManager::HistoryLine methodsFor:'comparing'!
+
+= aHistoryLine
+    "compares two instances of HistoryLine"
+
+    (aHistoryLine user = self user) ifTrue:[
+        (aHistoryLine date = self date) ifTrue:[
+            (aHistoryLine time = self time) ifTrue:[
+                (aHistoryLine type = self type) ifTrue:[
+                    (aHistoryLine what = self what) ifTrue:[
+                        ^ true
+                    ]
+                ]
+            ]
+        ]
+    ].
+
+    ^ false
+
+"
+    | h1 h2 |
+
+    h1 := HistoryLine for: OperatingSystem getLoginName.
+    h2 := h1 copy.
+
+    h1 = h2 ifTrue:[
+        InfoBox new title: 'users are equal'; show.
+    ].
+
+    h2 := HistoryLine for: OperatingSystem getLoginName.
+    h1 = h2 ifFalse:[
+        InfoBox new title: 'users are not equal'; show.
+    ].
+"
+
+    "Modified: 23.8.1995 / 22:26:40 / robert"
+    "Modified: 24.10.1997 / 00:22:09 / cg"
+!
+
+hash
+    "return a hash key for the receiver"
+
+    ^user hash        
+
+"
+    Check hashCode
+
+    |h1 h2 oc |
+
+    h1 := HistoryLine new hash.
+    h2 := HistoryLine new hash.
+    oc := OrderedCollection new.
+    oc add: h1.
+    oc add: h2.
+    ^oc
+
+    using hash in a set:
+
+    | h1 h2 aSet oc |
+    h1 := HistoryLine new hash.
+    h2 := HistoryLine new hash.
+    oc := OrderedCollection new.
+    oc add: h1.
+    oc add: h2.
+    aSet := oc asSet.
+    ^aSet
+"
+
+    "Modified: 23.08.1995 / 22:26:44 / robert"
+!
+
+sameDate: aHistoryLine
+    "returns true if aUserName = user in preperation for a SortedCollection of HistoryLines"
+
+    ^aHistoryLine date = date
+
+"
+    | h1 h2 |
+
+    h1 := HistoryLine new.
+    h2 := h1 copy.
+
+    (h1 sameDate: h2)  ifTrue:[
+	InfoBox new title: 'Dates are equal'; show.
+    ].
+
+    h2 := HistoryLine for: 'R.Sailer'.
+    h2 date: (Date day: 12 month: 6 year:1981).
+    (h1 sameDate: h2) ifFalse:[
+	InfoBox new title: 'users are not equal'; show.
+    ].
+
+"
+
+    "Modified: 23.08.1995 / 22:26:47 / robert"
+!
+
+sameType: aHistoryLine
+    "returns true if the Type = type in preperation for a SortedCollection of HistoryLines"
+
+    ^aHistoryLine type = type
+
+"
+    | h1 h2 |
+
+    h1 := HistoryLine new.
+    h2 := h1 copy.
+
+    (h1 sameType: h2)  ifTrue:[
+	InfoBox new title: 'Types are equal'; show.
+    ].
+
+    h2 := HistoryLine createdBy: 'R.Sailer'.
+    (h1 sameType: h2) ifFalse:[
+	InfoBox new title: 'Types are not equal'; show.
+    ].
+
+"
+
+    "Modified: 23.08.1995 / 22:26:49 / robert"
+!
+
+sameUser: aHistoryLine
+    "returns true if aUserName = user in preperation for a SortedCollection of HistoryLines"
+
+    ^aHistoryLine user = user
+
+
+"
+    | h1 h2 |
+
+    h1 := HistoryLine new.
+    h2 := h1 copy.
+
+    (h1 sameUser: h2)  ifTrue:[
+	InfoBox new title: 'users are equal'; show.
+    ].
+
+    h2 := HistoryLine for: 'R.Sailer'.
+    (h1 sameUser: h2) ifFalse:[
+	InfoBox new title: 'users are not equal'; show.
+    ].
+
+"
+
+    "Modified: 23.08.1995 / 22:26:51 / robert"
+!
+
+sameWhat: aHistoryLine
+    "returns true if the what = type in preperation for a SortedCollection of HistoryLines"
+
+    ^aHistoryLine what = what
+
+    "Created: 24.10.1997 / 00:21:46 / cg"
+! !
+
+!HistoryManager::HistoryLine methodsFor:'printing & storing'!
+
+printString
+    "return a printed representation of a HistoryLine as a string"
+
+    | aStream |
+
+    aStream := WriteStream on: String new.
+    aStream nextPutAll:IndentString.
+    aStream nextPutAll:Quote.
+    aStream nextPutAll:type.
+    what notNil ifTrue:[
+        aStream space.
+        aStream nextPutAll:what.
+    ].
+    aStream space; nextPutAll:Separator; space.
+    aStream nextPutAll:(date printFormat:#(1 2 3 $. 1 1)).
+    aStream space; nextPutAll:Separator; space.
+    time print24HourFormatOn:aStream. 
+    aStream space; nextPutAll:Separator; space.
+    aStream nextPutAll:user.
+    aStream nextPutAll:Quote.
+    ^ aStream contents.
+
+    "Modified: 24.10.1997 / 01:46:10 / cg"
+
+    "Modified: / 24.10.1997 / 02:01:43 / cg"
+
+    "Modified:  24.10.1997  02:07:23  cg"
+! !
+
+!HistoryManager::HistoryLine methodsFor:'queries'!
+
+isCreated
+    "returns true if the bodytext is CreatedString"
+
+    ^type = CreatedString
+
+"
+
+        HistoryLine new isModified
+        (HistoryLine for: 'R.Sailer') isCreated 
+        (HistoryLine createdBy: 'R.Sailer') isCreated 
+        HistoryLine deleted isModified 
+        (HistoryLine deletedBy: 'M.Noell') isModified 
+        
+"
+
+    "Modified: 23.8.1995 / 22:30:23 / robert"
+    "Modified: 20.4.1996 / 20:20:36 / cg"
+!
+
+isDeleted
+    "returns true if the bodytext is DeletedString"
+
+    ^type = DeletedString
+
+"
+
+        HistoryLine deleted isDeleted
+        HistoryLine new isDeleted
+
+
+
+"
+
+    "Modified: 20.4.1996 / 20:20:32 / 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.37 1997-07-05 19:21:23 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic3/HistoryManager.st,v 1.38 1997-10-24 23:08:06 cg Exp $'
 ! !
 HistoryManager initialize!
--- a/Make.proto	Fri Oct 10 19:33:06 1997 +0200
+++ b/Make.proto	Sat Oct 25 01:08:09 1997 +0200
@@ -1,4 +1,4 @@
-# $Header: /cvs/stx/stx/libbasic3/Make.proto,v 1.33 1997-09-20 21:42:12 cg Exp $
+# $Header: /cvs/stx/stx/libbasic3/Make.proto,v 1.34 1997-10-24 23:08:09 cg Exp $
 #
 # -------------- no need to change anything below ----------
 
@@ -21,7 +21,6 @@
 # these are uncritical - save some bytes by compiling with optspace
 #
 UNCRITICALOBJS=                                     \
-	HistLine.$(O)                               \
 	HistMgr.$(O)                                \
 	Change.$(O)                                 \
 	  ClassChg.$(O)                             \
@@ -33,8 +32,8 @@
 	  MethodChg.$(O)                            \
 	    MthdCatChg.$(O)                         \
 	    MthdPrivChg.$(O)                        \
-	 ChangeSet.$(O)				    \
-	AbstrSCMgr.$(O)				    \
+	 ChangeSet.$(O)                             \
+	AbstrSCMgr.$(O)                             \
 	  CVSSCMgr.$(O)
 
 OBJS=                                               \
@@ -49,14 +48,13 @@
 	    MthdCatChg.$(O)                         \
 	    MthdPrivChg.$(O)                        \
 	ChangeSet.$(O)                              \
-	HistLine.$(O)                               \
 	HistMgr.$(O)                                \
 	MsgTally.$(O)                               \
 	CallChain.$(O)                              \
 	ProfileTree.$(O)                            \
 	MsgTracer.$(O)                              \
-	WMethod.$(O)				    \
-	AbstrSCMgr.$(O)				    \
+	WMethod.$(O)                                \
+	AbstrSCMgr.$(O)                             \
 	  CVSSCMgr.$(O)
 
 objs::  $(OBJS)
@@ -87,7 +85,6 @@
 ClsPDChg.$(O): ClsPDChg.st $(STCHDR) ../include/Object.H
 ClsPFChg.$(O): ClsPFChg.st $(STCHDR) ../include/Object.H
 ClsPVChg.$(O): ClsPVChg.st $(STCHDR) ../include/Object.H
-HistLine.$(O): HistLine.st $(STCHDR) ../include/Object.H
 HistMgr.$(O): HistMgr.st $(STCHDR) ../include/Object.H
 MethodChg.$(O): MethodChg.st $(STCHDR) ../include/Object.H
 MsgTally.$(O): MsgTally.st $(STCHDR) ../include/Object.H