HistoryManager.st
author Claus Gittinger <cg@exept.de>
Wed, 17 Mar 2004 12:22:00 +0100
changeset 1383 e243ae633fac
parent 1382 d6cb0f200d52
child 1384 4e05f325b284
permissions -rw-r--r--
handle monthname in history line

"
 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.
"

"{ Package: 'stx:libbasic3' }"

Object subclass:#HistoryManager
	instanceVariableNames:'historyMode fullHistoryUpdate'
	classVariableNames:'TheOneAndOnlyInstance'
	poolDictionaries:''
	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 
"
 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
"
    This class is part of the HistoryManagerProject.
    It helps to keep track of changes made to methods.

    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.

    The Manager registers itself to get notifications 
    on change, intercepts them and appends a historyLine to the methods
    code.

    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.
        Now also catch Smalltalk change messages, related to class changes.

    [author:]
        Robert Sailer - AEG

    [see also:]
        HistoryLine

    [start with:]
         HistoryManager activate
         HistoryManager deactivate

"
! !

!HistoryManager class methodsFor:'initialization'!

initMe
    "setup theOneAndOnly instance of myself (if not already present"

    ^self new.

    "Modified: 14.8.1995 / 09:02:00 / robert"
    "Modified: 20.4.1996 / 20:33:44 / cg"
!

initialize
    "add myself as a dependent of ObjectMemory to be told about image restarts"

    ObjectMemory addDependent: self.

    "Modified: 14.8.1995 / 09:09:06 / robert"
    "Modified: 20.4.1996 / 20:34:09 / cg"
! !

!HistoryManager class methodsFor:'instance creation'!

new
    "because there can be only ONE HistoryManager, new must me redefiend"

    TheOneAndOnlyInstance isNil ifTrue:[
        TheOneAndOnlyInstance := super new initialize.
        HistoryLine initialize.
    ].

   ^ TheOneAndOnlyInstance

"

    HistoryManager new.
"

    "Modified: 11.08.1995 / 17:01:29 / robert"
! !

!HistoryManager class methodsFor:'accessing'!

fullHistoryUpdate
    "return true, if the historyManagement does full updates"

    TheOneAndOnlyInstance isNil ifTrue:[^ false].
    ^ TheOneAndOnlyInstance fullHistoryUpdate

    "Modified: / 27.8.1995 / 00:32:12 / claus"
    "Created: / 24.10.1997 / 02:24:34 / cg"
    "Modified: / 29.10.1997 / 15:48:22 / cg"
!

fullHistoryUpdate:aBoolean
    "set/clear, full updates"

    TheOneAndOnlyInstance isNil ifTrue:[^ self].
    TheOneAndOnlyInstance fullHistoryUpdate:aBoolean

    "Modified: / 27.8.1995 / 00:32:12 / claus"
    "Created: / 24.10.1997 / 02:24:58 / cg"
    "Modified: / 29.10.1997 / 15:48:36 / cg"
!

instance
    "return the one and only historyManager instance"

    ^ TheOneAndOnlyInstance

    "Modified: 20.4.1996 / 20:31:18 / cg"
!

isActive 
    "return true, if the historyManagement is activated"

    ^ TheOneAndOnlyInstance notNil

    "Modified: 27.8.1995 / 00:32:12 / claus"
    "Modified: 20.4.1996 / 20:31:32 / cg"
! !

!HistoryManager class methodsFor:'activation / deactivation'!

activate
    "activate the HistoryManagement"

    self new   "/ creating an instance activates me

    "
     HistoryManager activate
    "

    "Modified: 20.4.1996 / 20:31:46 / cg"
!

deactivate
    "deactivate the HistoryManagement"

    |mgr|

    mgr := TheOneAndOnlyInstance.
    mgr notNil ifTrue:[
        mgr releaseDependencies.
    ].
    TheOneAndOnlyInstance := nil.

    "
     HistoryManager deactivate
    "

    "Modified: 8.1.1997 / 23:09:08 / cg"
! !

!HistoryManager class methodsFor:'change & update'!

update:what with:aParameter from:changedObject
    "intercepts system restart - reinstall mySelf as dependent of all classes"

    (what == #restarted) ifTrue:[
        TheOneAndOnlyInstance notNil ifTrue:[
            "
             smalltalk is about to restart from an Image -
            "
"/            'HistoryManager initialize (via update)' infoPrintNL.
            self initMe.
        ]
    ].

    "Modified: 27.8.1995 / 16:33:02 / claus"
    "Modified: 20.4.1996 / 20:33:02 / cg"
    "Created: 15.6.1996 / 15:25:53 / cg"
! !

!HistoryManager class methodsFor:'helpers'!

createInitialHistoryMethodIn:aClass
    "create an initial (empty) history method"

    |histStream|

    histStream := '' writeStream.
    histStream nextPutLine:'history'.
    histStream nextPutLine:(HistoryLine newCreated printString).
    CodeGeneratorTool
        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."

    |position aReadWriteStream firstFound nextFound  aHistoryString rcOC h|

    "read begining from the end and look there for the first comment character. If there's none return"

    rcOC := OrderedCollection new.
    position := someString size.
    firstFound := false.
    nextFound := false.

    someString reverseDo:[ :aChar|
        position := position - 1.
        aChar == $" ifTrue:[
            firstFound ifTrue:[
                firstFound := false.
                nextFound := true.
            ] ifFalse:[
                aReadWriteStream := ReadWriteStream on: String new.
                firstFound := true.
                nextFound := false.
            ].
        ].
        (firstFound and: [nextFound not]) ifTrue:[
            "now collect all up to the next comment character"
            aChar == $" ifFalse:[     
                aReadWriteStream nextPut: aChar.
            ].
        ].
        nextFound ifTrue:[
            "End reached - now try to make a HistoryLine"
            aHistoryString := (aReadWriteStream contents) reverse.
            "
                Transcript showCR: aHistoryString.
            "
            h := HistoryLine fromString: aHistoryString at: position.
            h notNil ifTrue:[
                rcOC add:h.
            ].
"/            (aHistoryString startsWith: 'Modified:') ifTrue:[
"/                "a history line was found - now make a NewInstance of HistoryLine"
"/                rcOC add: ( HistoryLine fromString: aHistoryString at: position).
"/            ].
            nextFound := false.
        ].
    ].

    ^rcOC reverse  "the OrderedCollection with HistoryLines in the right order"

    "Modified: 21.12.1993 / 18:32:30 / M.Noell"
    "Modified: 9.8.1995 / 22:45:30 / R.Sailer"
    "Modified: 8.9.1995 / 17:54:33 / claus"
    "Modified: 20.4.1996 / 20:33:22 / cg"
!

withoutHistoryLines:someString
    "given some methods sourceString, return a copy without any
     history lines"

    | pos sourceCode previousHistories |

    someString isNil ifTrue:[^ someString].

    previousHistories := self getAllHistoriesFrom:someString.

    "extract source body."
    previousHistories isEmpty ifTrue: [
        sourceCode := someString withoutSeparators.
    ] ifFalse: [
        pos := (previousHistories first) firstPositionInSourceCode.
        sourceCode := (someString copyFrom: 1 to: pos - 1) withoutSeparators.
    ].

    ^ sourceCode

    "
     HistoryManager withoutHistoryLines:nil  
     HistoryManager withoutHistoryLines:''  
     HistoryManager 
        withoutHistoryLines:(HistoryManager class 
                                compiledMethodAt:#withoutHistoryLines:) source
    "

    "Created: 5.3.1996 / 15:11:12 / cg"
    "Modified: 30.4.1996 / 10:57:35 / cg"
! !

!HistoryManager methodsFor:'accessing'!

fullHistoryUpdate
    "return the fullHistoryUpdate; 
     if true, the classes history method is also updated."

    ^ fullHistoryUpdate

    "Modified: 11.08.1995 / 16:52:12 / robert"
!

fullHistoryUpdate:aBoolean
    "set the fullHistoryUpdate; 
     if true, the classes history method is also updated."

    fullHistoryUpdate := aBoolean.

    "Modified: 11.08.1995 / 16:52:12 / robert"
!

historyMode
    "return historyMode"

    ^ historyMode

    "Modified: 11.08.1995 / 16:51:56 / robert"
!

historyMode:something
    "set historyMode"

    historyMode := something.

    "Modified: 11.08.1995 / 16:52:12 / robert"
! !

!HistoryManager methodsFor:'change & update'!

update:something with:someArgument from:changedObject
    "arrive here, whenever any class changed somehow.
     (something contains aSymbol describing what happened)"

    |sourceCode newMethod fileInOrRecompiling selector oldMethod what
     changedClass whatChange oldSource|

    "/
    "/ no action, if disabled
    "/
    historyMode ifFalse:[
        ^ self
    ].

    "/
    "/ no action, if changeFile update is locked
    "/ (since then, this may be a recompile or fileIn)
    "/
    fileInOrRecompiling := Class updateChangeFileQuerySignal query.
    fileInOrRecompiling ifFalse:[ 
"/        Transcript showCR: '* noChange in history'. 
        ^ 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:[
            self addHistory:#modification with:'class definition' toHistoryMethodOf: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:[
            self addHistory:#modification with:'class variables' toHistoryMethodOf:changedObject.
        ].
        ^ self
    ].    

    "/
    "/ new Class creation
    "/
    ((changedObject == Smalltalk) and:[something == #newClass]) ifTrue:[
        "/ 
        "/  add myself as dependents in order to get future change notifications
        "/ 
        fullHistoryUpdate == true ifTrue:[
            self createHistoryMethodFor:someArgument.
            self addHistory:#creation with:nil toHistoryMethodOf:someArgument.
        ].

        "/ claus: old implementation

"/        someArgument addDependent: self.
"/        someArgument class addDependent: self.   "for class methods"

        ^ self
    ].

    "/ changed methods
    "/ for backward compatibility, still handle the
    "/ classes own change notification.
    "/ (only if I am a dependent of all classes)

    changedObject isBehavior ifTrue:[
        changedClass := changedObject.

        something == #methodDictionary ifTrue:[
            whatChange := #methodDictionary.

            someArgument isArray ifTrue:[
                selector := someArgument at:1.
                oldMethod := someArgument at:2
            ] ifFalse:[
                selector := someArgument
            ].
        ].

        something == #methodInClassRemoved ifTrue:[
            fullHistoryUpdate == true ifTrue:[
                changedClass := someArgument at:1.
                selector := someArgument at:2.
                self addHistory:#deletion with:('#' , selector) toHistoryMethodOf:changedClass.
            ].
            ^ self.
        ].

        something == #comment ifTrue:[
            whatChange := #comment.
        ].
    ].

    "/ the new mechanism; I only need to depend upon
    "/ Smalltalk, to get all method changes

    (changedObject == Smalltalk
    and:[something == #methodInClass]) ifTrue:[
        changedClass := someArgument at:1.
        selector := someArgument at:2.
        oldMethod := someArgument at:3.
        whatChange := #methodDictionary.
    ].

    changedClass notNil ifTrue:[
        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
        ]. 

        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
        ].
    ].
"/    Transcript show: 'unhandled change: ', something printString;cr.

    ^self

    "Modified: / 27.8.1995 / 02:14:43 / claus"
    "Modified: / 24.10.1997 / 01:41:19 / cg"
    "Modified: / 18.3.1999 / 18:21:47 / stefan"
! !

!HistoryManager methodsFor:'initialization'!

exclude
    "public - return an exclusionlist for some smalltalk classes which should not be notified or historisized"

    | oc |
        
    oc := OrderedCollection new.
    oc add: self.

    ^oc

    "Modified: 11.08.1995 / 17:02:18 / robert"
!

initialize
    "public - make me depend on all smalltalk classes (except the exclusionList)
     to be notified later about changes. This intercepts source installation and allows
     be to patch the source-string with a historyLine."

    |exclusionlist|

    super initialize.
    historyMode := true.
    fullHistoryUpdate := false.
    exclusionlist := self exclude.

    "/ old implementation:
    "/ made myself a dependent of all classes ...

"/    Smalltalk allClassesDo:[:aClass|
"/        "all classes should send a notification if changed"
"/        "aClass = self " false ifFalse: [
"/            (exclusionlist includes: aClass) ifFalse:[
"/                aClass addDependent: self.
"/                aClass class addDependent: self.   "for class methods"
"/            ].
"/        ].
"/    ].

    "/ old implementation:
    "/ Smalltalk also sends class-change notifications ...

    Smalltalk addDependent:self.

    ^self

    "Modified: 11.8.1995 / 17:12:51 / robert"
    "Modified: 8.1.1997 / 23:07:14 / cg"
!

releaseDependencies
    "no longer depend on class changes"

    "/ old implementation:
    "/ made myself a dependent of all classes ...

"/    Smalltalk allClassesDo:[:aClass |
"/        aClass removeDependent:self.
"/        aClass class removeDependent:self.
"/    ].

    "/ new implementation:
    "/ Smalltalk also sends class-change notifications ...

    Smalltalk removeDependent:self.
! !

!HistoryManager methodsFor:'updateHistory'!

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
     'Modified' or 'Created' lines."

    | histLines pos wStream sourceCode previousHistories
      newLine |

    "Check whether we want a history to be added"    
    historyMode ifFalse:[
        ^ someString
    ].

    previousHistories := self class getAllHistoriesFrom: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.
                ]
            ]
        ]
    ].
    argument notNil ifTrue:[
        newLine what:argument
    ].

    "extract source body."
    previousHistories isEmpty ifTrue: [
        sourceCode := someString withoutSeparators.
    ] ifFalse: [
        pos := (previousHistories first) firstPositionInSourceCode.
        sourceCode := (someString copyFrom: 1 to: pos - 1) withoutSeparators.
    ].

    "add the actual user's historyLine."
    previousHistories add:newLine.

    doFilter ifTrue:[
        "Filtering historyLines (each user with one entry)."
        histLines := HistoryLine filterHistoryLines: previousHistories.
    ] ifFalse:[
        histLines := previousHistories
    ].

    "create new method body with added historyLine"
    wStream := WriteStream on: String new.
    wStream nextPutAll: sourceCode; cr.

    "append the historyLines to the source"
    wStream cr.
    histLines do: [:hl |
       wStream nextPutLine:hl printString.
    ].

    ^ wStream contents.

    "Modified: 11.8.1995 / 16:51:50 / robert"
    "Modified: 8.9.1995 / 17:55:38 / claus"
    "Created: 24.10.1997 / 00:16:38 / cg"
    "Modified: 24.10.1997 / 01:27:21 / cg"
!

addHistory:what with:arg toHistoryMethodOf:aClass
    "private - add a historyLine at end of the classes history methods
     source - if there is one"

    |cls historyMethod oldSource newSource|

    aClass isMeta ifFalse:[
        cls := aClass class.
    ] ifTrue:[
        cls := aClass
    ].
    historyMethod := cls compiledMethodAt: #history.
    historyMethod notNil ifTrue:[
        oldSource := historyMethod source.
        oldSource notNil ifTrue:[
            newSource := self 
                            addHistory:what
                            with:arg
                            to:oldSource
                            filter:false. 
            historyMethod source:newSource.
        ]
    ]

    "Created: 12.10.1996 / 20:31:50 / cg"
    "Modified: 24.10.1997 / 00:14:33 / cg"
!

createHistoryMethodFor:aClass
    "private - create a history method"

    |cls|

    aClass isMeta ifFalse:[
        cls := aClass class.
    ] ifTrue:[
        cls := aClass
    ].

    Class updateChangeFileQuerySignal answer:false do:[
        Class updateChangeListQuerySignal answer:false do:[
            Compiler
                compile:'history' 
                forClass:cls 
                inCategory:'documentation'
        ].
    ].

    "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"

    | s day month year coll |

    "delete delimiter from the date string"
    s := aString copyReplaceAll: $. with:(Character space) .
    s replaceAll: $- with:(Character space).
    s replaceAll: $/ with:(Character space).
    coll := s asArrayOfSubstrings.
    day := (coll at: 1) asNumber.
    month := Number readFrom:(coll at: 2 ) onError:nil.
    month isNil ifTrue:[
        month := Date indexOfMonth:(coll at:2) language:#en.
        month == 0 ifTrue:[
            month := Date indexOfMonth:(coll at:2).
        ].
        month == 0 ifTrue:[
            self halt:'invalid month in history line'
        ].
    ].
    year := (coll at: 3 ) asNumber.

    (year between:0 and:99) ifTrue:[
        year := UserPreferences current twoDigitDateHandler value:year.
    ].
    ^ Date newDay:day month:month year:year.

    "
     HistoryLine convertAStringToADate:'18.10.1995'
     HistoryLine convertAStringToADate:'18.10.95'
     HistoryLine convertAStringToADate:'18.10.01'
    "

    "Modified: / 23-08-1995 / 21:28:58 / robert"
    "Modified: / 16-09-1997 / 14:35:03 / stefan"
    "Modified: / 17-03-2004 / 12:38:23 / cg"
!

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 hours: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.
"
!

version
    ^ '$Header: /cvs/stx/stx/libbasic3/HistoryManager.st,v 1.53 2004-03-17 11:22:00 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|

    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 Weisseise'
     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"
!

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'!

printOn:aStream
    "return a printed representation of a HistoryLine as a string"

    aStream nextPutAll:IndentString.
    aStream nextPutAll:Quote.
    aStream nextPutAll:type.
    what notNil ifTrue:[
        aStream space.
        aStream nextPutAll:what.
    ].
    aStream space; nextPutAll:Separator; space.
    date printOn:aStream language:#en.
    aStream space; nextPutAll:Separator; space.
    time print24HourFormatOn:aStream. 
    aStream space; nextPutAll:Separator; space.
    aStream nextPutAll:user.
    aStream nextPutAll:Quote.

    "
     self new printOn:Transcript
    "

    "Modified: / 24.10.1997 / 02:07:23 / cg"
    "Modified: / 20.1.1998 / 12:58:53 / stefan"
! !

!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.53 2004-03-17 11:22:00 cg Exp $'
! !

HistoryManager initialize!
HistoryManager::HistoryLine initialize!