HistoryManager.st
changeset 2394 f867c637b7cb
parent 2317 d62da5a37fc3
child 2404 9cfb670a7b72
equal deleted inserted replaced
2393:f1330a09ba45 2394:f867c637b7cb
    20 !
    20 !
    21 
    21 
    22 Object subclass:#HistoryLine
    22 Object subclass:#HistoryLine
    23 	instanceVariableNames:'date time user what firstPositionInSourceCode type'
    23 	instanceVariableNames:'date time user what firstPositionInSourceCode type'
    24 	classVariableNames:'Quote Separator ModifiedString DeletedString IndentString
    24 	classVariableNames:'Quote Separator ModifiedString DeletedString IndentString
    25 		UseGECOS CreatedString AddedString EnforcedUserName'
    25 		UseGECOS CreatedString AddedString EnforcedUserName
       
    26 		FormattedString CommentedString VariableRenamedString'
    26 	poolDictionaries:''
    27 	poolDictionaries:''
    27 	privateIn:HistoryManager
    28 	privateIn:HistoryManager
    28 !
    29 !
    29 
    30 
    30 !HistoryManager class methodsFor:'documentation'!
    31 !HistoryManager class methodsFor:'documentation'!
    49     This class is part of the HistoryManagerProject.
    50     This class is part of the HistoryManagerProject.
    50     It helps to keep track of changes made to methods.
    51     It helps to keep track of changes made to methods.
    51 
    52 
    52     All Methods and Classes in the system get a HistroyLine which 
    53     All Methods and Classes in the system get a HistroyLine which 
    53     contains a timestamp and the name of the changing user. 
    54     contains a timestamp and the name of the changing user. 
    54     This is acually the UniX loginname.
    55     This is acually the Unix loginname.
    55 
    56 
    56     The Manager registers itself to get notifications 
    57     The Manager registers itself to get notifications 
    57     on change, intercepts them and appends a historyLine to the methods
    58     on change, intercepts them and appends a historyLine to the methods
    58     code.
    59     code.
    59 
    60 
    60     The HistoryManager can be turned on/off from aprivate.rc script,
    61     The HistoryManager can be turned on/off from aprivate.rc script,
    61     or via the Launcher menu.
    62     or via the Launcher menu.
    62 
    63 
    63     The methods history line is filtered, to only contain one
    64     The method's history line is filtered, to only contain one
    64     entry per modifying user, containing the date of the last change.
    65     entry per modifying user, containing the date of the last change.
    65     If fullHistoryMode is on, the classes history-ethod is also updated for
    66     If fullHistoryMode is on, the classes history-ethod is also updated for
    66     every change (containing every change).
    67     every change (containing every change).
    67     Full mode is enabled via:
    68     Full mode is enabled via:
    68         HistoryManager fullHistoryUpdate:true
    69         HistoryManager fullHistoryUpdate:true
   404 
   405 
   405 update:something with:someArgument from:changedObject
   406 update:something with:someArgument from:changedObject
   406     "arrive here, whenever any class changed somehow.
   407     "arrive here, whenever any class changed somehow.
   407      (something contains aSymbol describing what happened)"
   408      (something contains aSymbol describing what happened)"
   408 
   409 
   409     |sourceCode newMethod selector oldMethod what
   410     |selector oldMethod changedClass whatChange|
   410      changedClass whatChange oldSource|
       
   411 
   411 
   412     "/
   412     "/
   413     "/ no action, if disabled
   413     "/ no action, if disabled
   414     "/
   414     "/
   415     historyMode ifFalse:[
   415     historyMode ifFalse:[
   427     Class updateHistoryLineQuerySignal query ifFalse:[ 
   427     Class updateHistoryLineQuerySignal query ifFalse:[ 
   428 "/        Transcript showCR: '* noChange in history'. 
   428 "/        Transcript showCR: '* noChange in history'. 
   429         ^ self 
   429         ^ self 
   430     ].
   430     ].
   431 
   431 
   432     "
   432     "                  
   433      definition, instance / classVariables of a class have changed
   433      definition, instance / classVariables of a class have changed
   434     "
   434     "
   435     (something == #definition) ifTrue:[
   435     (something == #definition) ifTrue:[
   436         "/ it is a class definition that has changed
   436         "/ it is a class definition that has changed
   437         "/ add a line to the history method; if present
   437         "/ add a line to the history method; if present
   438 
   438         self updateAfterClassChange:'class definition' in:changedObject.
   439 "/        Transcript show: 'Class definition: ', changedClass printString;cr.
       
   440         fullHistoryUpdate == true ifTrue:[
       
   441             changedObject theMetaclass compilerClass == Compiler ifFalse:[^ self].
       
   442             self addHistory:#modification with:'class definition' toHistoryMethodOf:changedObject.
       
   443         ].
       
   444         ^ self
   439         ^ self
   445     ].
   440     ].
   446 
   441 
   447     "this is a sub item of #definition"    
   442     "this is a sub item of #definition"    
   448     (something == #classVariables) ifTrue:[
   443     (something == #classVariables) ifTrue:[
   449         "/
   444         self updateAfterClassChange:'class variables' in:changedObject.
   450         "/ Transcript showCR: 'classVariables changed'.
       
   451         "/
       
   452 
       
   453         "/ does not yet work;
       
   454         "/ (someArgument does not contain the class we are interested in)
       
   455 
       
   456         fullHistoryUpdate == true ifTrue:[
       
   457             changedObject theMetaclass compilerClass == Compiler ifFalse:[^ self].
       
   458             self addHistory:#modification with:'class variables' toHistoryMethodOf:changedObject.
       
   459         ].
       
   460         ^ self
   445         ^ self
   461     ].    
   446     ].    
   462 
   447 
   463     "/
   448     "/
   464     "/ new Class creation
   449     "/ new Class creation
   516     ].
   501     ].
   517 
   502 
   518     "/ the new mechanism; I only need to depend upon
   503     "/ the new mechanism; I only need to depend upon
   519     "/ Smalltalk, to get all method changes
   504     "/ Smalltalk, to get all method changes
   520 
   505 
   521     (changedObject == Smalltalk
   506     (changedObject == Smalltalk and:[something == #methodInClass]) ifTrue:[
   522     and:[something == #methodInClass]) ifTrue:[
       
   523         changedClass := someArgument at:1.
   507         changedClass := someArgument at:1.
   524         selector := someArgument at:2.
   508         selector := someArgument at:2.
   525         oldMethod := someArgument at:3.
   509         oldMethod := someArgument at:3.
   526         whatChange := #methodDictionary.
   510         whatChange := #methodDictionary.
   527     ].
   511     ].
   529     changedClass notNil ifTrue:[
   513     changedClass notNil ifTrue:[
   530         changedClass theMetaclass compilerClass == Compiler ifFalse:[^ self].
   514         changedClass theMetaclass compilerClass == Compiler ifFalse:[^ self].
   531 
   515 
   532         whatChange == #methodDictionary ifTrue:[
   516         whatChange == #methodDictionary ifTrue:[
   533             "/ ok; it is a changed method
   517             "/ ok; it is a changed method
   534 
   518             self updateAfterMethodChange:selector from:oldMethod in:changedClass.
   535             "/
       
   536             "/ fetch sourceString of the method
       
   537             "/
       
   538             sourceCode := changedClass sourceCodeAt:selector.
       
   539             sourceCode isNil ifTrue:[
       
   540                 "method has been deleted"
       
   541 "/                Transcript showCR: 'method has been deleted'.
       
   542                 fullHistoryUpdate == true ifTrue:[
       
   543                     self addHistory:#deletion with:('#' , selector) toHistoryMethodOf:changedClass.
       
   544                 ].
       
   545                 ^ self.
       
   546             ].
       
   547 
       
   548             newMethod := changedClass compiledMethodAt:selector.
       
   549 
       
   550             oldMethod notNil ifTrue:[
       
   551                 oldSource := oldMethod source.
       
   552                 oldSource notNil ifTrue:[
       
   553                     (oldSource asString withTabsExpanded = sourceCode asString withTabsExpanded) ifTrue:[
       
   554                          "/ no change (accepted same code again ?)
       
   555                         ^ self
       
   556                     ].
       
   557                 ]
       
   558             ].
       
   559 
       
   560             "/
       
   561             "/ dont add historylines to documentation methods ...
       
   562             "/
       
   563             (changedClass isMeta not
       
   564             or:[newMethod category ~= 'documentation']) ifTrue:[
       
   565                 oldMethod notNil ifTrue:[
       
   566                     what := #modification
       
   567                 ] ifFalse:[
       
   568                     what := #creation
       
   569                 ].
       
   570 
       
   571                 "/
       
   572                 "/ update the history line-comment in
       
   573                 "/ the methods source
       
   574                 "/
       
   575             
       
   576                 sourceCode := self addHistory:what with:nil to:sourceCode filter:true.
       
   577                 newMethod source: sourceCode.
       
   578 "/                    Transcript showCR: 'history updated / added'.
       
   579             ].
       
   580 
       
   581             fullHistoryUpdate == true ifTrue:[
       
   582                 self addHistory:what with:('#' , selector) toHistoryMethodOf:changedClass.
       
   583             ].
       
   584             ^self
   519             ^self
   585         ]. 
   520         ]. 
   586 
   521 
   587         whatChange == #comment ifTrue:[
   522         whatChange == #comment ifTrue:[
   588             "the classes comment - we are no longer interested in that one"
   523             "the classes comment - we are no longer interested in that one"
   589 
       
   590             ^ self.
   524             ^ self.
   591         ].
   525         ].
   592 
   526 
   593         whatChange == #classDefinition ifTrue:[
   527         whatChange == #classDefinition ifTrue:[
   594             "/ it is a class definition that has changed
   528             "/ it is a class definition that has changed
   595             "/ add a line to the history method; if present
   529             "/ add a line to the history method; if present
   596 
   530             self updateAfterClassClassChange:'class definition' in:changedClass.
   597 "/            Transcript show: 'Class definition: ', changedClass printString;cr.
       
   598             fullHistoryUpdate == true ifTrue:[
       
   599                 self addHistory:#modification with:'class definition' toHistoryMethodOf:changedClass.
       
   600             ].
       
   601             ^self
   531             ^self
   602         ].
   532         ].
   603     ].
   533     ].
   604 "/    Transcript show: 'unhandled change: ', something printString;cr.
   534 "/    Transcript show: 'unhandled change: ', something printString;cr.
   605 
   535 
   606     ^self
   536     ^self
   607 
   537 
   608     "Modified: / 27-08-1995 / 02:14:43 / claus"
   538     "Created: / 30-06-2011 / 16:43:46 / cg"
   609     "Modified: / 18-03-1999 / 18:21:47 / stefan"
   539 !
   610     "Modified: / 13-07-2006 / 17:41:35 / cg"
   540 
       
   541 updateAfterClassChange:whatChange in:aClass 
       
   542     "/ it is a class definition that has changed
       
   543     "/ add a line to the history method; if present
       
   544     "/        Transcript show: 'Class definition: ', changedClass printString;cr.
       
   545     
       
   546     fullHistoryUpdate == true ifTrue:[
       
   547         "/ check for the programming-language...
       
   548         aClass theMetaclass compilerClass == Compiler ifFalse:[
       
   549             ^ self
       
   550         ].
       
   551         self 
       
   552             addHistory:#modification
       
   553             with:whatChange
       
   554             toHistoryMethodOf:aClass.
       
   555     ].
       
   556 
       
   557     "Modified (Format): / 30-06-2011 / 16:27:23 / cg"
       
   558     "Created: / 30-06-2011 / 16:28:22 / cg"
       
   559 !
       
   560 
       
   561 updateAfterMethodChange:selector from:oldMethod in:changedClass
       
   562     |newSource newSourceWithoutHistory newHistories newMethod newTree newComments
       
   563      oldSource oldSourceWithoutHistory oldHistories oldTree oldComments
       
   564      renamedVariables
       
   565      whatChange pos|
       
   566 
       
   567     changedClass theMetaclass compilerClass == Compiler ifFalse:[^ self].
       
   568 
       
   569     "/ ok; it is a changed method
       
   570 
       
   571     "/
       
   572     "/ fetch sourceString of the method
       
   573     "/
       
   574     newSource := changedClass sourceCodeAt:selector.
       
   575     newSource isNil ifTrue:[
       
   576         "method has been deleted"
       
   577 "/                Transcript showCR: 'method has been deleted'.
       
   578         fullHistoryUpdate == true ifTrue:[
       
   579             self addHistory:#deletion with:('#' , selector) toHistoryMethodOf:changedClass.
       
   580         ].
       
   581         ^ self.
       
   582     ].
       
   583     newHistories := self class getAllHistoriesFrom:newSource.
       
   584 
       
   585     newMethod := changedClass compiledMethodAt:selector.
       
   586 
       
   587     oldMethod isNil ifTrue:[
       
   588         whatChange := #creation
       
   589     ] ifFalse:[
       
   590         whatChange := #modification.
       
   591 
       
   592         oldSource := oldMethod source.
       
   593         oldSource notNil ifTrue:[
       
   594             (oldSource asString withTabsExpanded = newSource asString withTabsExpanded) ifTrue:[
       
   595                  "/ no change (accepted same code again ?)
       
   596                 ^ self
       
   597             ].
       
   598 
       
   599             oldHistories := self class getAllHistoriesFrom:oldSource.
       
   600             oldHistories notEmptyOrNil ifTrue: [
       
   601                 "/ compare source without history...
       
   602                 pos := (oldHistories first) firstPositionInSourceCode.
       
   603                 oldSourceWithoutHistory := (oldSource copyFrom:1 to:pos - 1) withoutSeparators.
       
   604             ] ifFalse:[
       
   605                 oldSourceWithoutHistory := oldSource
       
   606             ].
       
   607 
       
   608             newHistories notEmptyOrNil ifTrue: [
       
   609                 "/ compare source without history...
       
   610                 pos := (newHistories first) firstPositionInSourceCode.
       
   611                 newSourceWithoutHistory := (newSource copyFrom:1 to:pos - 1) withoutSeparators.
       
   612             ] ifFalse:[
       
   613                 newSourceWithoutHistory := newSource
       
   614             ].
       
   615 
       
   616             (oldSourceWithoutHistory asString withTabsExpanded = newSourceWithoutHistory asString withTabsExpanded) ifTrue:[
       
   617                  "/ no change (except for history lines)
       
   618                 UserPreferences current historyManagerAllowEditOfHistory ifFalse:[
       
   619                     newMethod source: oldSource.
       
   620                 ].
       
   621                 ^ self
       
   622             ].
       
   623 
       
   624             RBParser notNil ifTrue:[
       
   625                 "/ same structure?
       
   626                 oldTree := RBParser parseMethod:oldSourceWithoutHistory onError:[:aString :pos | nil].
       
   627                 newTree := RBParser parseMethod:newSourceWithoutHistory onError:[:aString :pos | nil].
       
   628                 (oldTree equalTo:newTree withMapping:(renamedVariables := Dictionary new)) ifTrue:[
       
   629                     "/ only formatting?
       
   630                         (renamedVariables keysAndValuesSelect:[:k :v | k ~= v]) isEmpty ifTrue:[
       
   631                         "/ only formatting...
       
   632                         whatChange := #formatted.
       
   633                         oldComments := oldTree allComments.
       
   634                         newComments := newTree allComments.
       
   635                         (oldComments size ~= newComments size
       
   636                         or:[ oldComments with:newComments contains:[:ca :cb | ca characters ~= cb characters]]) ifTrue:[
       
   637                             whatChange := #commented.
       
   638                         ].
       
   639                     ] ifFalse:[
       
   640                         renamedVariables halt.    
       
   641                     ]
       
   642                 ]
       
   643             ]
       
   644         ]
       
   645     ].
       
   646 
       
   647     "/
       
   648     "/ don't add historylines to documentation methods on the class side...
       
   649     "/
       
   650     (changedClass isMeta 
       
   651     and:[newMethod category = 'documentation']) ifFalse:[
       
   652         "/
       
   653         "/ update the history line-comment in
       
   654         "/ the methods source
       
   655         "/            
       
   656         newSource := self addHistory:whatChange with:nil to:oldHistories inSource:newSource filter:true.
       
   657         newMethod source: newSource.
       
   658         "/ Transcript showCR: 'history updated / added'.
       
   659     ].
       
   660 
       
   661     fullHistoryUpdate == true ifTrue:[
       
   662         self addHistory:whatChange with:('#' , selector) toHistoryMethodOf:changedClass.
       
   663     ].
       
   664 
       
   665 
       
   666     "Created: / 30-06-2011 / 16:51:19 / cg"
   611 ! !
   667 ! !
   612 
   668 
   613 !HistoryManager methodsFor:'initialization'!
   669 !HistoryManager methodsFor:'initialization'!
   614 
   670 
   615 exclude
   671 exclude
   684     "private - add a historyLine at end to the sourceCode;
   740     "private - add a historyLine at end to the sourceCode;
   685      check for multiple lines of the same user and merge into one.
   741      check for multiple lines of the same user and merge into one.
   686      What may be one of #modification or #creation, to choose among
   742      What may be one of #modification or #creation, to choose among
   687      'Modified' or 'Created' lines."
   743      'Modified' or 'Created' lines."
   688 
   744 
   689     | histLines pos wStream sourceCode previousHistories
   745     |previousHistories|
   690       newLine |
       
   691 
   746 
   692     "Check whether we want a history to be added"    
   747     "Check whether we want a history to be added"    
   693     historyMode ifFalse:[
   748     historyMode ifFalse:[
   694         ^ someString
   749         ^ someString
   695     ].
   750     ].
   696 
   751 
   697     previousHistories := self class getAllHistoriesFrom:someString.
   752     previousHistories := self class getAllHistoriesFrom:someString.
       
   753     ^ self addHistory:what with:argument to:previousHistories inSource:someString filter:doFilter
       
   754 
       
   755     "Modified: / 30-06-2011 / 16:54:27 / cg"
       
   756     "Modified (Format): / 30-06-2011 / 18:17:58 / cg"
       
   757 !
       
   758 
       
   759 addHistory:what with:argument to:previousHistories inSource:someString filter:doFilter
       
   760     "private - add a historyLine at end to the sourceCode;
       
   761      check for multiple lines of the same user and merge into one.
       
   762      What may be one of #modification or #creation, to choose among
       
   763      'Modified' or 'Created' lines."
       
   764 
       
   765     |histories histLines pos wStream sourceCode newLine |
       
   766 
       
   767     "Check whether we want a history to be added"    
       
   768     historyMode ifFalse:[
       
   769         ^ someString
       
   770     ].
   698 
   771 
   699     newLine := HistoryLine new.
   772     newLine := HistoryLine new.
   700 
   773 
   701     what == #creation ifTrue:[
   774     what == #creation ifTrue:[
   702         newLine isForCreation.
   775         newLine isForCreation.
   703     ] ifFalse:[
   776     ] ifFalse:[ what == #deletion ifTrue:[
   704         what == #deletion ifTrue:[
   777         newLine isForDeletion.
   705             newLine isForDeletion.
   778     ] ifFalse:[ what == #addition ifTrue:[
   706         ] ifFalse:[
   779         newLine isForAddition.
   707             what == #addition ifTrue:[
   780     ] ifFalse:[ what == #modification ifTrue:[
   708                 newLine isForAddition.
   781         newLine isForModification.
   709             ] ifFalse:[
   782     ] ifFalse:[ what == #formatted ifTrue:[
   710                 what == #modification ifTrue:[
   783         newLine isForFormatted.
   711                     newLine isForModification.
   784     ] ifFalse:[ what == #commented ifTrue:[
   712                 ]
   785         newLine isForCommented.
   713             ]
   786     ] ifFalse:[ what == #variableRenamed ifTrue:[
   714         ]
   787         newLine isForVariableRenamed
   715     ].
   788     ] ifFalse:[ 
       
   789         self breakPoint:#cg
       
   790     ]]]]]]].
   716     argument notNil ifTrue:[
   791     argument notNil ifTrue:[
   717         newLine what:argument
   792         newLine what:argument
   718     ].
   793     ].
   719 
   794 
   720     "extract source body."
   795     "extract source body."
   721     previousHistories isEmpty ifTrue: [
   796     histories := self class getAllHistoriesFrom:someString.
       
   797     histories isEmpty ifTrue: [
   722         sourceCode := someString withoutSeparators.
   798         sourceCode := someString withoutSeparators.
   723     ] ifFalse: [
   799     ] ifFalse: [
   724         pos := (previousHistories first) firstPositionInSourceCode.
   800         pos := (histories first) firstPositionInSourceCode.
   725         sourceCode := (someString copyFrom: 1 to: pos - 1) withoutSeparators.
   801         sourceCode := (someString copyFrom: 1 to: pos - 1) withoutSeparators.
   726     ].
   802     ].
   727 
   803 
   728     "add the actual user's historyLine."
   804     "add the actual user's historyLine."
   729     previousHistories add:newLine.
   805     histLines := (previousHistories ? histories).
       
   806     histLines add:newLine.
   730 
   807 
   731     doFilter ifTrue:[
   808     doFilter ifTrue:[
   732         "Filtering historyLines (each user with one entry)."
   809         "Filtering historyLines (each user with one entry)."
   733         histLines := HistoryLine filterHistoryLines: previousHistories.
   810         histLines := HistoryLine filterHistoryLines: histLines.
   734     ] ifFalse:[
       
   735         histLines := previousHistories
       
   736     ].
   811     ].
   737 
   812 
   738     "create new method body with added historyLine"
   813     "create new method body with added historyLine"
   739     wStream := WriteStream on: (sourceCode species) new.
   814     wStream := WriteStream on: (sourceCode species) new.
   740     wStream nextPutAll: sourceCode; cr.
   815     wStream nextPutAll: sourceCode; cr.
   745        wStream nextPutLine:hl printString.
   820        wStream nextPutLine:hl printString.
   746     ].
   821     ].
   747 
   822 
   748     ^ wStream contents.
   823     ^ wStream contents.
   749 
   824 
   750     "Modified: / 11-08-1995 / 16:51:50 / robert"
   825     "Modified: / 30-06-2011 / 17:07:18 / cg"
   751     "Modified: / 08-09-1995 / 17:55:38 / claus"
       
   752     "Created: / 24-10-1997 / 00:16:38 / cg"
       
   753     "Modified: / 18-09-2006 / 20:48:58 / cg"
       
   754 !
   826 !
   755 
   827 
   756 addHistory:what with:arg toHistoryMethodOf:aClass
   828 addHistory:what with:arg toHistoryMethodOf:aClass
   757     "private - add a historyLine at end of the classes history methods
   829     "private - add a historyLine at end of the classes history methods
   758      source - if there is one"
   830      source - if there is one"
   791             compile:'history' 
   863             compile:'history' 
   792             forClass:meta 
   864             forClass:meta 
   793             inCategory:'documentation'
   865             inCategory:'documentation'
   794     ].
   866     ].
   795 
   867 
   796     "Modified: / 13-07-2006 / 17:42:25 / cg"
   868     "Modified (Format): / 30-06-2011 / 17:11:38 / cg"
       
   869     "Modified (Format): / 30-06-2011 / 17:11:42 / cg"
       
   870     "Modified (Format): / 30-06-2011 / 17:11:45 / cg"
       
   871     "Modified (Format): / 30-06-2011 / 17:11:47 / cg"
   797 ! !
   872 ! !
   798 
   873 
   799 !HistoryManager::HistoryLine class methodsFor:'converting'!
   874 !HistoryManager::HistoryLine class methodsFor:'converting'!
   800 
   875 
   801 convertStringToDate: aString
   876 convertStringToDate: aString
   802     "kludge"
   877     "kludge"
   803 
   878 
   804     | day month year words |
   879     | day month year words firstNumber |
   805 
   880 
   806     "delete delimiter from the date string"
   881     "delete delimiter from the date string"
   807     words := aString asCollectionOfSubstringsSeparatedByAny:'.-/'.
   882     words := aString asCollectionOfSubstringsSeparatedByAny:'.-/'.
   808 
   883 
   809     day := Number readFromString:(words at: 1).
   884     "/ figure out if european or yyyy-mm-dd format
   810     month := Number readFrom:(words at: 2 ) onError:nil.
   885     firstNumber := Number readFromString:(words at: 1).
       
   886     firstNumber > 1900 ifTrue:[
       
   887         year := firstNumber.
       
   888         month := Number readFrom:(words at: 2 ) onError:nil.
       
   889         day := Number readFromString:(words at: 3 ).
       
   890     ] ifFalse:[
       
   891         day := firstNumber.
       
   892         month := Number readFrom:(words at: 2 ) onError:nil.
       
   893         year := Number readFromString:(words at: 3 ).
       
   894         (year between:0 and:99) ifTrue:[
       
   895             year := UserPreferences current twoDigitDateHandler value:year.
       
   896         ].
       
   897     ].
   811     month isNil ifTrue:[
   898     month isNil ifTrue:[
   812         month := Date indexOfMonth:(words at:2) language:#en.
   899         month := Date indexOfMonth:(words at:2) language:#en.
   813         month == 0 ifTrue:[
   900         month == 0 ifTrue:[
   814             month := Date indexOfMonth:(words at:2).
   901             month := Date indexOfMonth:(words at:2).
   815         ].
   902         ].
   816         month == 0 ifTrue:[
   903         month == 0 ifTrue:[
   817             self halt:'invalid month in history line'.
   904             self halt:'invalid month in history line'.
   818             ^ Date today.
   905             ^ Date today.
   819         ].
   906         ].
   820     ].
   907     ].
   821     year := Number readFromString:(words at: 3 ).
   908 
   822 
       
   823     (year between:0 and:99) ifTrue:[
       
   824         year := UserPreferences current twoDigitDateHandler value:year.
       
   825     ].
       
   826     ^ Date newDay:day month:month year:year.
   909     ^ Date newDay:day month:month year:year.
   827 
   910 
   828     "
   911     "
   829      HistoryLine convertStringToDate:'18.10.1995'
   912      HistoryLine convertStringToDate:'18.10.1995' 
   830      HistoryLine convertStringToDate:'18.10.95'    
   913      HistoryLine convertStringToDate:'18.10.95'    
   831      HistoryLine convertStringToDate:'18.10.01'    
   914      HistoryLine convertStringToDate:'18.10.01'    
       
   915      HistoryLine convertStringToDate:'2001-03-01'    
   832     "
   916     "
   833 
   917 
   834     "Modified: / 23-08-1995 / 21:28:58 / robert"
   918     "Modified: / 23-08-1995 / 21:28:58 / robert"
   835     "Modified: / 16-09-1997 / 14:35:03 / stefan"
   919     "Modified: / 16-09-1997 / 14:35:03 / stefan"
   836     "Created: / 06-03-2007 / 17:04:34 / cg"
   920     "Created: / 06-03-2007 / 17:04:34 / cg"
   837     "Modified: / 06-03-2007 / 18:28:57 / cg"
   921     "Modified (Comment): / 30-06-2011 / 18:37:09 / cg"
   838 !
   922 !
   839 
   923 
   840 convertStringToTime: aString
   924 convertStringToTime: aString
   841    "kludge"
   925    "kludge"
   842 
   926 
   907     HistoryLine deleted.
   991     HistoryLine deleted.
   908 "
   992 "
   909 !
   993 !
   910 
   994 
   911 version
   995 version
   912     ^ '$Header: /cvs/stx/stx/libbasic3/HistoryManager.st,v 1.73 2011-01-31 17:31:22 cg Exp $'
   996     ^ '$Header: /cvs/stx/stx/libbasic3/HistoryManager.st,v 1.74 2011-06-30 17:09:51 cg Exp $'
   913 ! !
   997 ! !
   914 
   998 
   915 !HistoryManager::HistoryLine class methodsFor:'filtering'!
   999 !HistoryManager::HistoryLine class methodsFor:'filtering'!
   916 
  1000 
   917 filterHistoryLines:  aCollectionOfHistoryLines
  1001 filterHistoryLines:aCollectionOfHistoryLines
   918     "check the collection against multiple occurrence of the same user,
  1002     "check the collection against multiple occurrence of the same user,
   919      and remove all but the youngest (per user)."
  1003      and remove all but the youngest (per user)."
   920 
  1004 
   921     |newCollection|
  1005     |newCollection skipNext|
   922 
  1006 
       
  1007     skipNext := false.
   923     newCollection := OrderedCollection new.
  1008     newCollection := OrderedCollection new.
   924     aCollectionOfHistoryLines keysAndValuesDo:[:index :histLine |
  1009     aCollectionOfHistoryLines keysAndValuesDo:[:index :histLine |
   925         |skip|
  1010         |skip|
   926 
  1011 
   927         skip := false.
  1012         skip := skipNext.
   928         histLine isModified ifTrue:[
  1013         skipNext := false.
   929             "/ if there is another one, skip this
  1014         histLine isKindOfModified ifTrue:[
   930             aCollectionOfHistoryLines from:index+1 do:[:anotherHistLine |
  1015             aCollectionOfHistoryLines do: [:anotherHistLine |
   931                 ((anotherHistLine isModified 
  1016                 (anotherHistLine isCreated and: [anotherHistLine user = histLine user])
   932                     and: [anotherHistLine user = histLine user])
  1017                 ifTrue: [
   933                         and:[anotherHistLine what = histLine what])
  1018                     (self timeIsShortFrom:histLine to:anotherHistLine) ifTrue: [skip := true]
   934                             ifTrue:[skip := true]
  1019                 ]
       
  1020             ].
       
  1021 
       
  1022             skip ifFalse: [
       
  1023                "/ if there is another one, skip this
       
  1024                 aCollectionOfHistoryLines from:index+1 do:[:anotherHistLine |
       
  1025                     (anotherHistLine isKindOfModified 
       
  1026                     and:[anotherHistLine user = histLine user
       
  1027                     and:[anotherHistLine what = histLine what]])
       
  1028                     ifTrue:[
       
  1029                         "/ don't replace a modified by a modified format
       
  1030                         (histLine isModified not or:[anotherHistLine isModified]) ifTrue:[
       
  1031                             skip := true
       
  1032                         ] ifFalse:[
       
  1033                             "/ remove next comment/format modification if this is a modified
       
  1034                             (histLine isModified and:[anotherHistLine isModified not]) ifTrue:[
       
  1035                                 (self timeIsShortFrom:histLine to:anotherHistLine) ifTrue: [skip := true]
       
  1036                             ].
       
  1037                         ].
       
  1038                     ]
   935                 ].
  1039                 ].
   936             skip ifFalse: [
       
   937                 aCollectionOfHistoryLines do: [:anotherHistLine |
       
   938                     (anotherHistLine isCreated and: [anotherHistLine user = histLine user])
       
   939                         ifTrue: [
       
   940                             ((Timestamp
       
   941                                 fromDate: histLine date
       
   942                                 andTime: histLine time) secondDeltaFrom:
       
   943                                     (Timestamp
       
   944                                         fromDate: anotherHistLine date
       
   945                                         andTime: anotherHistLine time)) < self modificationLimit
       
   946                             ifTrue: [skip := true]
       
   947                         ]
       
   948                 ]
       
   949             ]
  1040             ]
   950         ] ifFalse:[
  1041         ] ifFalse:[
   951             "/ filter out multiple created messages
  1042             "/ filter out multiple created messages
   952             "/ (this only occurs if a method was copied from ClassA to ClassB)
  1043             "/ (this only occurs if a method was copied from ClassA to ClassB)
   953             histLine isCreated ifTrue:[
  1044             histLine isCreated ifTrue:[
   954                 aCollectionOfHistoryLines from:index+1 do:[:anotherHistLine |
  1045                 aCollectionOfHistoryLines from:index+1 do:[:anotherHistLine |
   955                     (anotherHistLine isCreated and:[anotherHistLine what = histLine what]) 
  1046                     (anotherHistLine isCreated and:[anotherHistLine what = histLine what]) 
   956                         ifTrue:[skip := true]
  1047                         ifTrue:[skip := true]
   957                 ].
  1048                 ].
       
  1049                 skip ifFalse:[
       
  1050                     "/ create followed by a modification, within the historyManagerModificationLimit:
       
  1051                     "/ skip the modified message
       
  1052                     (index+1) == aCollectionOfHistoryLines size ifTrue:[
       
  1053                         | anotherHistLine |
       
  1054                         anotherHistLine := aCollectionOfHistoryLines at:index+1.
       
  1055                         (anotherHistLine isKindOfModified and:[anotherHistLine user = histLine user]) 
       
  1056                             ifTrue:[skipNext := true]
       
  1057                     ].
       
  1058                 ].
   958             ].
  1059             ].
   959         ].
  1060         ].
   960         skip ifFalse:[
  1061         skip ifFalse:[
   961             newCollection add:histLine.
  1062             newCollection add:histLine.
   962         ]
  1063         ]
   964     ^ newCollection.
  1065     ^ newCollection.
   965 
  1066 
   966     "Modified: / 08-09-1995 / 17:20:40 / claus"
  1067     "Modified: / 08-09-1995 / 17:20:40 / claus"
   967     "Modified: / 20-06-2004 / 16:36:00 / masca"
  1068     "Modified: / 20-06-2004 / 16:36:00 / masca"
   968     "Modified: / 01-09-2004 / 20:20:42 / janfrog"
  1069     "Modified: / 01-09-2004 / 20:20:42 / janfrog"
   969     "Modified: / 12-01-2008 / 10:37:25 / cg"
  1070     "Modified: / 30-06-2011 / 18:32:22 / cg"
   970 !
  1071 !
   971 
  1072 
   972 modificationLimit
  1073 modificationLimit
   973     "Answer the number of seconds between creation and
  1074     "Answer the number of seconds between creation and
   974      modifcation of a method within which the modification
  1075      modifcation of a method within which the modification
   976 
  1077 
   977     ^ 3600 "/one hour
  1078     ^ 3600 "/one hour
   978 
  1079 
   979     "Created: / 20.6.2004 / 16:32:35 / masca"
  1080     "Created: / 20.6.2004 / 16:32:35 / masca"
   980     "Modified: / 2.9.2004 / 15:33:09 / janfrog"
  1081     "Modified: / 2.9.2004 / 15:33:09 / janfrog"
       
  1082 !
       
  1083 
       
  1084 timeIsShortFrom:histLine1 to:histLine2
       
  1085     |t1 t2|
       
  1086 
       
  1087     t1 := (Timestamp fromDate: histLine1 date andTime: histLine1 time).
       
  1088     t2 := (Timestamp fromDate: histLine2 date andTime: histLine2 time).
       
  1089     ^ (t1 secondDeltaFrom:t2) abs < self modificationLimit
       
  1090 
       
  1091     "Created: / 30-06-2011 / 18:23:04 / cg"
   981 ! !
  1092 ! !
   982 
  1093 
   983 !HistoryManager::HistoryLine class methodsFor:'initialization'!
  1094 !HistoryManager::HistoryLine class methodsFor:'initialization'!
   984 
  1095 
   985 initialize
  1096 initialize
   990         Separator := '/'.
  1101         Separator := '/'.
   991         ModifiedString := 'Modified:'.
  1102         ModifiedString := 'Modified:'.
   992         DeletedString := 'Deleted:'.
  1103         DeletedString := 'Deleted:'.
   993         CreatedString := 'Created:'.
  1104         CreatedString := 'Created:'.
   994         AddedString := 'Added:'.
  1105         AddedString := 'Added:'.
       
  1106         FormattedString := 'Modified (format):'.
       
  1107         CommentedString := 'Modified (comment):'.
       
  1108         VariableRenamedString := 'Modified (variable name):'.
   995         IndentString := '    '.
  1109         IndentString := '    '.
   996         UseGECOS := false.
  1110         UseGECOS := false.
   997     ]
  1111     ]
   998 
  1112 
   999     "
  1113     "
  1000      HistoryLine initialize
  1114      HistoryLine initialize
  1001     "
  1115     "
  1002 
  1116 
  1003     "Modified: 23.8.1995 / 22:14:03 / robert"
  1117     "Modified: / 23-08-1995 / 22:14:03 / robert"
  1004     "Modified: 20.4.1996 / 20:23:29 / cg"
  1118     "Modified: / 30-06-2011 / 12:28:43 / cg"
  1005 
       
  1006     "Modified: 24.10.1997 / 01:18:56 / cg"
       
  1007 
       
  1008     "Modified: / 24.10.1997 / 02:01:20 / cg"
       
  1009 
       
  1010     "Modified:  24.10.1997  02:07:16  cg"
       
  1011 ! !
  1119 ! !
  1012 
  1120 
  1013 !HistoryManager::HistoryLine class methodsFor:'instance creation'!
  1121 !HistoryManager::HistoryLine class methodsFor:'instance creation'!
  1014 
  1122 
  1015 fromString: aString
  1123 fromString: aString
  1030 fromString: aString at: position
  1138 fromString: aString at: position
  1031     "parses the String and creates a new Instance with the values. 
  1139     "parses the String and creates a new Instance with the values. 
  1032      The positionvalue is normally used to remove the HistoryLines from the sourceCode.
  1140      The positionvalue is normally used to remove the HistoryLines from the sourceCode.
  1033      Claus: return nil, if the string is not a valid historyString."
  1141      Claus: return nil, if the string is not a valid historyString."
  1034 
  1142 
  1035     | inst anArray type aTime aDate userName idx what|
  1143     |inst array type aTime aDate userName idx what|
  1036 
  1144 
  1037     inst := self basicNew.  
  1145     inst := self basicNew.  
  1038 
  1146 
  1039     anArray := aString asArrayOfSubstrings.
  1147     array := aString asArrayOfSubstrings.
  1040     anArray size < 5 ifTrue:[^ nil].
  1148     array size < 5 ifTrue:[^ nil].
  1041     anArray := anArray collect:[:word | word withoutSpaces].
  1149 
  1042 
  1150     array := array collect:[:word | word withoutSpaces].
  1043     "
  1151     type := array at:1.
  1044         Modified / Deleted / Created
  1152 
       
  1153     "/ kludge for the 'Modified (what)' strings
       
  1154     ((array at:2) startsWith:'(') ifTrue:[
       
  1155         type := type , ' ' , (array at:2).
       
  1156         array := (Array with:type) , (array copyFrom:3)
       
  1157     ].
       
  1158 
       
  1159     "
       
  1160      Modified [(detail)] / Deleted / Created
  1045         [what]
  1161         [what]
  1046         Separator
  1162         Separator
  1047         date asString
  1163         date asString
  1048         Separator
  1164         Separator
  1049         time asString
  1165         time asString
  1050         Separator
  1166         Separator
  1051         UserName ...
  1167         UserName ...
  1052     "
  1168     "
  1053 
  1169 
  1054     type := anArray at:1.
       
  1055 
       
  1056     ((Array 
  1170     ((Array 
  1057         with:ModifiedString
  1171         with:ModifiedString
  1058         with:DeletedString
  1172         with:DeletedString
  1059         with:CreatedString
  1173         with:CreatedString
  1060         with:AddedString) includes:type) ifFalse:[^ nil].
  1174         with:AddedString
       
  1175         with:FormattedString 
       
  1176         with:CommentedString 
       
  1177         with:VariableRenamedString
       
  1178     ) includes:type) ifFalse:[^ nil].
  1061 
  1179 
  1062     inst type:type.
  1180     inst type:type.
  1063 
  1181 
  1064     "/ sigh backward compatibility ...
  1182     "/ sigh backward compatibility ...
  1065 
  1183 
  1066     (anArray at:2) first isDigit ifTrue:[
  1184     (array at:2) first isDigit ifTrue:[
  1067         "/ date follows ...
  1185         "/ date follows ...
  1068         idx := 2
  1186         idx := 2
  1069     ] ifFalse:[
  1187     ] ifFalse:[
  1070         idx := anArray indexOf:Separator startingAt:2.
  1188         idx := array indexOf:Separator startingAt:2.
  1071         idx == 0 ifTrue:[
  1189         idx == 0 ifTrue:[
  1072             "/ not a valid history string
  1190             "/ not a valid history string
  1073             ^ nil
  1191             ^ nil
  1074         ].
  1192         ].
  1075 
  1193 
  1076         idx ~~ 2 ifTrue:[
  1194         idx ~~ 2 ifTrue:[
  1077             what := (anArray copyFrom:2 to:(idx-1)) asStringWith:(Character space).
  1195             what := (array copyFrom:2 to:(idx-1)) asStringWith:(Character space).
  1078             inst what:what.
  1196             inst what:what.
  1079         ].
  1197         ].
  1080 
  1198 
  1081         idx := idx + 1.
  1199         idx := idx + 1.
  1082     ].
  1200     ].
  1083     aDate := self convertStringToDate: (anArray at: idx).
  1201     aDate := self convertStringToDate: (array at: idx).
  1084     inst date: aDate.
  1202     inst date: aDate.
  1085     (anArray at:idx+1) ~= Separator ifTrue:[^ nil].
  1203     (array at:idx+1) ~= Separator ifTrue:[^ nil].
  1086     idx := idx + 2.
  1204     idx := idx + 2.
  1087 
  1205 
  1088     aTime := self convertStringToTime: (anArray at: idx).
  1206     aTime := self convertStringToTime: (array at: idx).
  1089     inst time: aTime.
  1207     inst time: aTime.
  1090     (anArray at:idx+1) ~= Separator ifTrue:[^ nil].
  1208     (array at:idx+1) ~= Separator ifTrue:[^ nil].
  1091     idx := idx + 2.
  1209     idx := idx + 2.
  1092 
  1210 
  1093     "the user's name may be more that one word"
  1211     "the user's name may be more that one word"
  1094     userName := (anArray copyFrom:idx) asStringWith:Character space.
  1212     userName := (array copyFrom:idx) asStringWith:Character space.
  1095 
  1213 
  1096     inst user:userName.
  1214     inst user:userName.
  1097     inst firstPositionInSourceCode:position.
  1215     inst firstPositionInSourceCode:position.
  1098 
  1216 
  1099     ^ inst
  1217     ^ inst
  1103      HistoryLine fromString: 'Created: 21.12.1993 / 18:32:30 / Felicitas Gabriele Felger'
  1221      HistoryLine fromString: 'Created: 21.12.1993 / 18:32:30 / Felicitas Gabriele Felger'
  1104      HistoryLine fromString: 'Deleted: 21.12.93 / 18:32:30 / Astrid Weisseise'
  1222      HistoryLine fromString: 'Deleted: 21.12.93 / 18:32:30 / Astrid Weisseise'
  1105      HistoryLine fromString: 'Deleted: foo bar / 21.12.93 / 18:32:30 / Astrid Weisseise'
  1223      HistoryLine fromString: 'Deleted: foo bar / 21.12.93 / 18:32:30 / Astrid Weisseise'
  1106     "
  1224     "
  1107 
  1225 
  1108     "Modified: / 23.8.1995 / 22:24:47 / robert"
  1226     "Modified: / 23-08-1995 / 22:24:47 / robert"
  1109     "Modified: / 19.9.1995 / 14:14:48 / claus"
  1227     "Modified: / 19-09-1995 / 14:14:48 / claus"
  1110     "Modified: / 24.10.1997 / 02:10:01 / cg"
  1228     "Modified: / 30-06-2011 / 16:09:16 / cg"
       
  1229     "Modified (Comment): / 30-06-2011 / 19:08:22 / cg"
  1111 !
  1230 !
  1112 
  1231 
  1113 new
  1232 new
  1114     "get a new history line. 
  1233     "get a new history line. 
  1115      Preinitialize it as a modified-Line for the current user"    
  1234      Preinitialize it as a modified-Line for the current user"    
  1132 
  1251 
  1133 !HistoryManager::HistoryLine class methodsFor:'private'!
  1252 !HistoryManager::HistoryLine class methodsFor:'private'!
  1134 
  1253 
  1135 currentUserName
  1254 currentUserName
  1136     "return the current users name - 
  1255     "return the current users name - 
  1137      thats either the userInfos-gecos field, or the users login name."
  1256      that's either the userInfos-gecos field, or the users login name."
  1138 
  1257 
  1139     |nm|
  1258     |nm|
  1140 
  1259 
  1141     (nm := HistoryManager enforcedUserName) notNil ifTrue:[
  1260     (nm := HistoryManager enforcedUserName) notNil ifTrue:[
  1142         ^ nm
  1261         ^ nm
  1150      HistoryLine currentUserName
  1269      HistoryLine currentUserName
  1151     "
  1270     "
  1152 
  1271 
  1153     "Modified: / 15-07-1996 / 12:43:14 / cg"
  1272     "Modified: / 15-07-1996 / 12:43:14 / cg"
  1154     "Modified: / 20-06-2006 / 13:26:49 / User"
  1273     "Modified: / 20-06-2006 / 13:26:49 / User"
       
  1274     "Modified (Comment): / 30-06-2011 / 18:54:30 / cg"
  1155 !
  1275 !
  1156 
  1276 
  1157 type:type what:what
  1277 type:type what:what
  1158     "private - for integration purposes only"
  1278     "private - for integration purposes only"
  1159 
  1279 
  1177 date
  1297 date
  1178     "return the date"
  1298     "return the date"
  1179 
  1299 
  1180     ^ date
  1300     ^ date
  1181 
  1301 
  1182     "Modified: 20.4.1996 / 20:22:12 / cg"
  1302     "Modified (Format): / 30-06-2011 / 16:23:15 / cg"
  1183 !
  1303 !
  1184 
  1304 
  1185 date:something
  1305 date:something
  1186     "set the date"
  1306     "set the date"
  1187 
  1307 
  1204 
  1324 
  1205 isForAddition
  1325 isForAddition
  1206     type := AddedString
  1326     type := AddedString
  1207 !
  1327 !
  1208 
  1328 
       
  1329 isForCommented
       
  1330     type := CommentedString
       
  1331 
       
  1332     "Created: / 30-06-2011 / 12:24:22 / cg"
       
  1333 !
       
  1334 
  1209 isForCreation
  1335 isForCreation
  1210     type := CreatedString
  1336     type := CreatedString
  1211 !
  1337 !
  1212 
  1338 
  1213 isForDeletion
  1339 isForDeletion
  1214     type := DeletedString
  1340     type := DeletedString
  1215 !
  1341 !
  1216 
  1342 
       
  1343 isForFormatted
       
  1344     type := FormattedString
       
  1345 
       
  1346     "Created: / 30-06-2011 / 12:24:11 / cg"
       
  1347 !
       
  1348 
  1217 isForModification
  1349 isForModification
  1218     type := ModifiedString
  1350     type := ModifiedString
       
  1351 !
       
  1352 
       
  1353 isForVariableRenamed
       
  1354     type := VariableRenamedString
       
  1355 
       
  1356     "Created: / 30-06-2011 / 12:24:36 / cg"
       
  1357     "Modified (Format): / 30-06-2011 / 12:28:27 / cg"
  1219 !
  1358 !
  1220 
  1359 
  1221 time
  1360 time
  1222     "return the time"
  1361     "return the time"
  1223 
  1362 
  1504 "
  1643 "
  1505 
  1644 
  1506     "Modified: 20.4.1996 / 20:20:32 / cg"
  1645     "Modified: 20.4.1996 / 20:20:32 / cg"
  1507 !
  1646 !
  1508 
  1647 
  1509 isModified
  1648 isKindOfModified
  1510     "returns true if the bodytext is ModifiedString"
  1649     "returns true if the bodytext is ModifiedString"
  1511 
  1650 
  1512     ^type = ModifiedString
  1651     ^ self isModified 
  1513 
  1652         or:[ type = CommentedString
  1514 "
  1653         or:[ type = FormattedString
  1515 
  1654         or:[ type = VariableRenamedString ]]]
       
  1655 
       
  1656     "
  1516         HistoryLine new isModified
  1657         HistoryLine new isModified
  1517         (HistoryLine for: 'R.Sailer') isModified 
  1658         (HistoryLine for: 'R.Sailer') isModified 
  1518         HistoryLine deleted isModified 
  1659         HistoryLine deleted isModified 
  1519         (HistoryLine deletedBy: 'M.Noell') isModified 
  1660         (HistoryLine deletedBy: 'M.Noell') isModified 
  1520         
  1661     "
  1521 "
  1662 
       
  1663     "Created: / 30-06-2011 / 17:15:12 / cg"
       
  1664 !
       
  1665 
       
  1666 isModified
       
  1667     "returns true if the bodytext is ModifiedString"
       
  1668 
       
  1669     ^type = ModifiedString
       
  1670 
       
  1671     "
       
  1672         HistoryLine new isModified
       
  1673         (HistoryLine for: 'R.Sailer') isModified 
       
  1674         HistoryLine deleted isModified 
       
  1675         (HistoryLine deletedBy: 'M.Noell') isModified 
       
  1676     "
  1522 
  1677 
  1523     "Modified: 20.4.1996 / 20:20:29 / cg"
  1678     "Modified: 20.4.1996 / 20:20:29 / cg"
  1524 ! !
  1679 ! !
  1525 
  1680 
  1526 !HistoryManager class methodsFor:'documentation'!
  1681 !HistoryManager class methodsFor:'documentation'!
  1527 
  1682 
  1528 version
       
  1529     ^ '$Header: /cvs/stx/stx/libbasic3/HistoryManager.st,v 1.73 2011-01-31 17:31:22 cg Exp $'
       
  1530 !
       
  1531 
       
  1532 version_CVS
  1683 version_CVS
  1533     ^ '$Header: /cvs/stx/stx/libbasic3/HistoryManager.st,v 1.73 2011-01-31 17:31:22 cg Exp $'
  1684     ^ '$Header: /cvs/stx/stx/libbasic3/HistoryManager.st,v 1.74 2011-06-30 17:09:51 cg Exp $'
  1534 ! !
  1685 ! !
  1535 
  1686 
  1536 HistoryManager initialize!
  1687 HistoryManager initialize!
  1537 HistoryManager::HistoryLine initialize!
  1688 HistoryManager::HistoryLine initialize!