HistoryManager.st
author Claus Gittinger <cg@exept.de>
Mon, 14 Oct 1996 18:01:30 +0200
changeset 497 abebd0d145e5
parent 494 6bc61cd32f7c
child 504 b77d99f3bdb6
permissions -rw-r--r--
dont add a changeRecord for the automatically created history method.

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

Object subclass:#HistoryManager
	instanceVariableNames:'historyMode'
	classVariableNames:'TheOneAndOnlyInstance'
	poolDictionaries:''
	category:'System-Changes-History'
!

!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 all Classes in the system 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.

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

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.
    Smalltalk allClassesDo:[:aClass |
        aClass removeDependent:mgr.
        aClass class removeDependent:mgr.
    ].
    TheOneAndOnlyInstance := nil.

    "
     HistoryManager deactivate
    "

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

!HistoryManager  class methodsFor:'change and 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'!

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

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:'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.
    exclusionlist := self exclude.

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

    ^self

    "Modified: 11.08.1995 / 17:12:51 / robert"
! !

!HistoryManager methodsFor:'updateHistory'!

addHistory:what to:someString
    "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.

    what == #creation ifTrue:[
        newLine := (HistoryLine newCreated).
    ] ifFalse:[
        newLine := (HistoryLine new)
    ].

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

    "Filtering historyLines (each user with one entry)."
    histLines := HistoryLine filterHistoryLines: previousHistories.

    "create new 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 nextPutAll:hl printString; cr.
    ].

    ^wStream contents.

    "Modified: 11.8.1995 / 16:51:50 / robert"
    "Modified: 8.9.1995 / 17:55:38 / claus"
    "Modified: 13.12.1995 / 14:07:03 / cg"
    "Created: 12.10.1996 / 20:33:35 / cg"
!

addHistory:what 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
                            to:oldSource. 
            historyMethod source:newSource.
        ]
    ]

    "Modified: 20.4.1996 / 20:35:06 / cg"
    "Created: 12.10.1996 / 20:31:50 / cg"
!

createHistoryMethodFor:aClass
    "private - create a history method"

    |cls|

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

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

    "Modified: 14.10.1996 / 16:58:20 / cg"
!

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|

"/    changedObject == self ifTrue:[  "for development only"
"/        self halt.
"/        ^self.
"/    ].

    fileInOrRecompiling := Class updateChangeFileQuerySignal raise.

"/    changedObject isMeta ifTrue:[
"/        Transcript showCR: 'metaClass = ',  changedObject printString.
"/    ].

    fileInOrRecompiling ifFalse:[ 
"/        Transcript showCR: '* noChange in history'. 
        ^ self 
    ].
    historyMode ifFalse:[
        ^ self
    ].

    "
    Class Variables
    "
    (something == #definition) ifTrue:[
        "add handling for classes here ..."        
        "/ self addHistory:#modification toHistoryMethodOf:changedObject.
    ].

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

        self addHistory:#modification toHistoryMethodOf:changedObject.
        ^ self
    ].    

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

        someArgument addDependent: self.
        someArgument class addDependent: self.   "for class methods"
        ^ self
    ].

    "/
    "/ changed methods
    "/
    changedObject isBehavior ifTrue:[
        something = #methodDictionary ifTrue:[
            someArgument isArray ifTrue:[
                selector := someArgument at:1.
                oldMethod := someArgument at:2
            ] ifFalse:[
                selector := someArgument
            ].

            "/
            "/ fetch sourceString of the method
            "/
            sourceCode := changedObject sourceCodeAt:selector.
            sourceCode isNil ifTrue:[
                "method has been deleted"
"/                Transcript showCR: 'method has been deleted'.
            ] ifFalse:[
                newMethod := changedObject compiledMethodAt:selector.

                oldMethod notNil ifTrue:[
                    (oldMethod source asString withTabsExpanded = sourceCode asString withTabsExpanded) ifTrue:[
                         "/ no change (accepted same code again ?)
                        ^ self
                    ].
                ].

                "/
                "/ dont add historylines to documentation methods ...
                "/
                (changedObject isMeta not
                or:[newMethod category ~= 'documentation']) ifTrue:[
                    oldMethod notNil ifTrue:[
                        what := #modification
                    ] ifFalse:[
                        what := #creation
                    ].
                    sourceCode := self addHistory:what to:sourceCode.
                    newMethod source: sourceCode.
"/                Transcript showCR: 'history updated / added'.
                ]
            ].
            ^self
        ]. 

        something == #comment ifTrue:[
            "in someArgument steht jetzt der alte kommentar"
            ^ self.
        ] ifFalse:[
            "it is a class definition"
"/            Transcript show: 'Class definition: ', changedObject printString;cr.
            self addHistory:#modification toHistoryMethodOf:changedObject.
        ].
    ].

    ^self

    "Modified: 27.8.1995 / 02:14:43 / claus"
    "Modified: 12.10.1996 / 20:47:40 / cg"
! !

!HistoryManager  class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic3/HistoryManager.st,v 1.31 1996-10-14 16:01:30 cg Exp $'
! !
HistoryManager initialize!