HistoryManager.st
author claus
Fri, 08 Sep 1995 21:06:02 +0200
changeset 47 db2d5d021237
parent 46 c53838e4783c
child 48 115a12443621
permissions -rw-r--r--
.

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

'From Smalltalk/X, Version:2.10.7 on 23-aug-1995 at 10:30:30 pm'                !

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

HistoryManager comment:'''Historymanagement for Smalltalk MultiUser Environment''
'!

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

version
"
$Header: /cvs/stx/stx/libbasic3/HistoryManager.st,v 1.5 1995-09-08 19:06:02 claus Exp $
"
!

documentation
"
    This class is part of the 
	       -----------------------
		HistoryManagerProject.
	       -----------------------
    It is used to create a multi user Smalltalk developers Environemt.

    All Methods and Classes in the system get a HistroyLine which contains a timestamp
    and the name of the Editor. This is acually the UniX loginname.
    The Manager registers all Classes in the System to get notifications on change.

    Author: Robert Sailer - AEG
"
!

examples
"
    HistoryManager new
"
    "Modified: 11.08.1995 / 16:50:47 / robert"
! !

!HistoryManager class methodsFor:'initialization'!

initialize
    ""
    ObjectMemory addDependent: self.

    "Modified: 14.08.1995 / 9:49:56 / robert"
!

initMe
    "setup TheOneAndOnlyInstance (if not already present"
    ^self new.

    "Modified: 14.08.1995 / 9:52:40 / robert"
! !

!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 class variable"

    ^TheOneAndOnlyInstance
!

isActive 
    ^TheOneAndOnlyInstance notNil

    "Modified: 27.8.1995 / 00:32:12 / claus"
! !

!HistoryManager class methodsFor:'change and update'!

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

    "Modified: 27.8.1995 / 16:33:02 / claus"
! !

!HistoryManager class methodsFor:'activation / deactivation'!

activate
    self new   "/ creating an instance activates me
!

deactivate
    Smalltalk allClassesDo:[:aClass |
	aClass removeDependent:TheOneAndOnlyInstance.
	aClass class removeDependent:TheOneAndOnlyInstance.
    ].
    TheOneAndOnlyInstance := nil.

"
    HistoryManager release
"
! !

!HistoryManager class methodsFor:'helpers'!

getAllHistoriesFrom:someString
    "returns anArray of HistoryLines"

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

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

    | box  exclusionlist|

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

    Smalltalk allClasses do:[: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'!

addHistoryTo:someString
    "private - add a historyLine at end to the sourceCode;
     check for multiple lines of the same user and merge into one."

    | histLines pos hm wStream sourceCode historyMode previousHistories
      newLine |

    previousHistories := self class getAllHistoriesFrom:someString.
    "Check whether there is a Manager"    
"/    hm := Smalltalk at: #HistoryManager ifAbsent: [ Transcript show: 'no HistoryManager present'.^someString].

"/    historyMode := hm instance historyMode.     "this method (addHistroy is called only by the historyManager)"
"/
"/    historyMode = false ifTrue: [
"/        "do nothing with the Code i.e. for filein"
"/        ^someString
"/    ].    


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

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

update: something with: someArgument from: changedObject
    "public - sent whenever any class changed somehow.
     (something contains aSymbol or nil)"

    | sourceCode aMethod fileInOrRecompiling |

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

    fileInOrRecompiling := Class updateChangeFileQuerySignal raise. "Class updatingChanges."

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

    (changedObject == Smalltalk) & (something == #newClass) ifTrue:[
	someArgument addDependent: self.
	someArgument class  addDependent: self.   "for class methods"
    ].

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

    "
    Class Variables
    "
    (something == #definition) ifTrue:[
	"hier die gesamt behandlung fuer Klassen"        
    ].

    "this is a sub item of #definition"    
    (something == #classVariables) ifTrue:[
	"
	Transcript showCr: 'classVariables changed'.
	"
" das geht noch nicht, weil in someArgument nicht die Klasse steht die das betrifft"
	sourceCode := changedObject sourceCodeAt: #history.
	sourceCode isNil ifTrue:[
	    "method has not been created"
"/            Transcript showCr: 'method class-history has not been created'.
	] ifFalse:[
	    aMethod := changedObject compiledMethodAt: #history.
	    sourceCode := self addHistoryTo:sourceCode.
	    aMethod source: sourceCode.
"/            Transcript showCr: 'history updated / added'.
	    ^self
	].
    ].    

    "
    New Class creation
    "
    ((changedObject == Smalltalk)and:[ (something == #newClass)]) ifTrue:[
	" self in die Dependents eintragen damit die notification bei den Methoden kommt."
	someArgument addDependent: self.
	someArgument history: (self addHistoryTo:String new).  "append historyString for new class"
    ].

    "
    Instance Handling
    "
    changedObject isBehavior ifTrue:[
	something = #methodDictionary ifTrue:[
	    "SourceString der Methode holen"
	    sourceCode := changedObject sourceCodeAt: someArgument.
	    sourceCode isNil ifTrue:[
		"method has been deleted"
"/                Transcript showCr: 'method has been deleted'.
	    ] ifFalse:[
		aMethod := changedObject compiledMethodAt: someArgument.
		sourceCode := self addHistoryTo:sourceCode.
		aMethod 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.
	    sourceCode := changedObject sourceCodeAt: #history.
	    sourceCode isNil ifTrue:[
		"method has not been created"
"/                Transcript showCr: 'method class-history has not been created'.
	    ] ifFalse:[
		aMethod := changedObject compiledMethodAt: #history.

		sourceCode := self addHistoryTo:sourceCode.
		aMethod source: sourceCode.

"/                Transcript showCr: 'history updated / added'.
	    ].
	].
    ].

    ^self

    "Modified: 27.8.1995 / 02:14:43 / claus"
! !

HistoryManager initialize!