ChangeSetBrowser.st
author Claus Gittinger <cg@exept.de>
Mon, 06 Mar 2006 09:53:24 +0100
changeset 6644 8e8e857780ba
parent 6603 18a7130a71b8
child 6683 26f871e5e907
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1993 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:libtool' }"

ChangesBrowser subclass:#ChangeSetBrowser
	instanceVariableNames:'changeSet originalChangeSet'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-Browsers'
!

!ChangeSetBrowser class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1993 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
"
    like a changesBrowser, but manipulates the per-project change-lists.

    This is operating on changes as a list of Change-instances 
    as opposed to the ChangesBrowser which is doing it completely non-object oriented,
    as a list of text-chunks.

    ChangeSetBrowser is going to completely replace the ChangesBrowser class in the near
    future.
"
! !

!ChangeSetBrowser class methodsFor:'instance creation'!

open
    "create a changes browser on the current change set"

    ^ self openOn:(ChangeSet current)

    "
     ChangeSetBrowser open
    "
!

openOn:aChangeSet
    "create a changes browser on a change set"

    ^ ((self new label:'ChangeSet Browser') changeSet:aChangeSet) open
!

openOnFile:aFileName
    |changeSet|

    changeSet := ChangeSet fromFile:aFileName.
    ^ self openOn:changeSet
! !

!ChangeSetBrowser class methodsFor:'defaults'!

defaultLabel
    ^ self classResources string:'ChangeSet Browser'

    "Created: / 6.2.1998 / 13:25:47 / cg"
! !

!ChangeSetBrowser class methodsFor:'menu specs'!

menuSpec
    "This resource specification was automatically generated
     by the MenuEditor of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the MenuEditor may not be able to read the specification."

    "
     MenuEditor new openOnClass:ChangeSetBrowser andSelector:#menuSpec
     (Menu new fromLiteralArrayEncoding:(ChangeSetBrowser menuSpec)) startUp
    "

    <resource: #menu>

    ^ 
     #(#Menu
        #(
         #(#MenuItem
            #label: 'File'
            #translateLabel: true
            #submenu: 
           #(#Menu
              #(
               #(#MenuItem
                  #label: 'Compress'
                  #itemValue: #doCompress
                  #translateLabel: true
                  #isVisible: #notEditingClassSourceAndNotReadOnly
                )
               #(#MenuItem
                  #enabled: #hasSelection
                  #label: 'Compress for Class'
                  #itemValue: #doCompressClass
                  #translateLabel: true
                  #isVisible: #notEditingClassSourceAndNotReadOnly
                )
               #(#MenuItem
                  #label: 'Compare and Compress'
                  #itemValue: #doCompareAndCompress
                  #translateLabel: true
                  #isVisible: #notEditingClassSourceAndNotReadOnly
                )
               #(#MenuItem
                  #label: '-'
                  #isVisible: #notEditingClassSourceAndNotReadOnly
                )
               #(#MenuItem
                  #enabled: #hasSelection
                  #label: 'Fileout && Delete all Changes for Class'
                  #itemValue: #doFileoutAndDeleteClassAll
                  #translateLabel: true
                  #isVisible: #notEditingClassSourceAndNotReadOnly
                )
               #(#MenuItem
                  #enabled: #hasSelection
                  #label: 'CheckIn && Delete all Changes for Class'
                  #itemValue: #doCheckinAndDeleteClassAll
                  #translateLabel: true
                  #isVisible: #notEditingClassSourceAndNotReadOnly
                )
               #(#MenuItem
                  #label: '-'
                  #isVisible: #notEditingClassSourceAndNotReadOnly
                )
               #(#MenuItem
                  #enabled: #hasSelection
                  #label: 'Save in...'
                  #itemValue: #doSave
                  #translateLabel: true
                )
               #(#MenuItem
                  #enabled: #hasSelection
                  #label: 'Save to End in...'
                  #itemValue: #doSaveRest
                  #translateLabel: true
                )
               #(#MenuItem
                  #enabled: #hasSelection
                  #label: 'Save for Class to End in...'
                  #itemValue: #doSaveClassRest
                  #translateLabel: true
                )
               #(#MenuItem
                  #enabled: #hasSelection
                  #label: 'Save All for Class in...'
                  #itemValue: #doSaveClassAll
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: '-'
                )
               #(#MenuItem
                  #label: 'Saveback ChangeSet'
                  #itemValue: #doSaveBack
                  #translateLabel: true
                  #isVisible: #notReadOnly
                )
               #(#MenuItem
                  #label: '-'
                  #isVisible: #notReadOnly
                )
               #(#MenuItem
                  #label: 'Update'
                  #itemValue: #doUpdate
                  #translateLabel: true
                  #isVisible: #notReadOnly
                )
               #(#MenuItem
                  #label: '-'
                  #isVisible: #notReadOnly
                )
               #(#MenuItem
                  #label: 'Exit'
                  #itemValue: #menuExit
                  #translateLabel: true
                )
               )
              nil
              nil
            )
          )
         #(#MenuItem
            #label: 'Change'
            #translateLabel: true
            #submenu: 
           #(#Menu
              #(
               #(#MenuItem
                  #label: 'Undo (undelete Method)'
                  #itemValue: #doUndoRemoveMethod
                  #translateLabel: true
                  #isVisible: #hasUndoableRemoveMethodChangeSelected
                )
               #(#MenuItem
                  #label: 'Undo (previous Version)'
                  #itemValue: #doUndoMethodChange
                  #translateLabel: true
                  #isVisible: #hasUndoableMethodChangeSelected
                )
               #(#MenuItem
                  #enabled: false
                  #label: 'Undo'
                  #itemValue: #doUndoMethodChange
                  #translateLabel: true
                  #isVisible: #hasNotUndoableChangeSelected
                )
               #(#MenuItem
                  #label: '-'
                )
               #(#MenuItem
                  #enabled: #hasSelection
                  #label: 'Apply'
                  #itemValue: #doApply
                  #translateLabel: true
                )
               #(#MenuItem
                  #enabled: #hasSelection
                  #label: 'Apply to End'
                  #itemValue: #doApplyRest
                  #translateLabel: true
                )
               #(#MenuItem
                  #enabled: #hasSelection
                  #label: 'Apply for Class to End'
                  #itemValue: #doApplyClassRest
                  #translateLabel: true
                )
               #(#MenuItem
                  #enabled: #hasNoSelection
                  #label: 'Apply All'
                  #itemValue: #doApplyAll
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: '-'
                )
               #(#MenuItem
                  #enabled: #hasSelection
                  #label: 'Delete'
                  #itemValue: #doDelete
                  #translateLabel: true
                  #isVisible: #notReadOnly
                )
               #(#MenuItem
                  #enabled: #hasSelection
                  #label: 'Delete to End'
                  #itemValue: #doDeleteRest
                  #translateLabel: true
                  #isVisible: #notReadOnly
                )
               #(#MenuItem
                  #enabled: #hasSelection
                  #label: 'Delete for Class to End'
                  #itemValue: #doDeleteClassRest
                  #translateLabel: true
                  #isVisible: #notReadOnly
                )
               #(#MenuItem
                  #enabled: #hasSelection
                  #label: 'Delete for Class from Begin'
                  #itemValue: #doDeleteClassFromBeginning
                  #translateLabel: true
                  #isVisible: #notReadOnly
                )
               #(#MenuItem
                  #enabled: #hasSelection
                  #label: 'Delete All for Class'
                  #itemValue: #doDeleteClassAll
                  #translateLabel: true
                  #isVisible: #notReadOnly
                )
               #(#MenuItem
                  #enabled: #hasSelection
                  #label: 'Delete All for Class && its Private Classes'
                  #itemValue: #doDeleteClassAndPrivateClassesAll
                  #translateLabel: true
                  #isVisible: #notReadOnly
                )
               #(#MenuItem
                  #label: '-'
                  #isVisible: #notReadOnly
                )
               #(#MenuItem
                  #enabled: #hasSelection
                  #label: 'Compare with Current'
                  #itemValue: #doCompare
                  #translateLabel: true
                )
               #(#MenuItem
                  #enabled: #hasSelection
                  #label: 'Browse'
                  #itemValue: #doBrowse
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: '-'
                )
               #(#MenuItem
                  #enabled: #hasSelection
                  #label: 'Make Change a Patch'
                  #itemValue: #doMakePatch
                  #translateLabel: true
                )
               )
              nil
              nil
            )
          )
         #(#MenuItem
            #label: 'Search'
            #translateLabel: true
            #submenu: 
           #(#Menu
              #(
               #(#MenuItem
                  #label: 'Class...'
                  #itemValue: #findClass
                  #translateLabel: true
                )
               #(#MenuItem
                  #enabled: #hasSelection
                  #label: 'Previous for Class'
                  #itemValue: #findPreviousForClass
                  #translateLabel: true
                )
               #(#MenuItem
                  #enabled: #hasSelection
                  #label: 'Next for Class'
                  #itemValue: #findNextForClass
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: '-'
                )
               #(#MenuItem
                  #label: 'Selector...'
                  #itemValue: #findSelector
                  #translateLabel: true
                )
               #(#MenuItem
                  #enabled: #hasSelection
                  #label: 'Previous for Selector'
                  #itemValue: #findPreviousForSelector
                  #translateLabel: true
                )
               #(#MenuItem
                  #enabled: #hasSelection
                  #label: 'Next for Selector'
                  #itemValue: #findNextForSelector
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: '-'
                )
               #(#MenuItem
                  #label: 'String...'
                  #itemValue: #findString
                  #translateLabel: true
                )
               #(#MenuItem
                  #enabled: #hasSelection
                  #label: 'Previous with String'
                  #itemValue: #findPreviousForString
                  #translateLabel: true
                )
               #(#MenuItem
                  #enabled: #hasSelection
                  #label: 'Next with String'
                  #itemValue: #findNextForString
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: '-'
                )
               #(#MenuItem
                  #enabled: #hasSelection
                  #label: 'Previous Snapshot'
                  #itemValue: #findPreviousSnapshot
                  #translateLabel: true
                )
               #(#MenuItem
                  #enabled: #hasSelection
                  #label: 'Next Snapshot'
                  #itemValue: #findNextSnapshot
                  #translateLabel: true
                )
               )
              nil
              nil
            )
          )
         #(#MenuItem
            #label: 'Browse'
            #translateLabel: true
            #submenu: 
           #(#Menu
              #(
               #(#MenuItem
                  #enabled: #hasSingleSelection
                  #label: 'Class'
                  #itemValue: #doBrowse
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: '-'
                )
               #(#MenuItem
                  #label: 'Senders...'
                  #itemValue: #doBrowseSenders
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: 'Implementors...'
                  #itemValue: #doBrowseImplementors
                  #translateLabel: true
                )
               )
              nil
              nil
            )
          )
         #(#MenuItem
            #label: 'Settings'
            #translateLabel: true
            #submenu: 
           #(#Menu
              #(
               #(#MenuItem
                  #label: 'Auto Compare'
                  #translateLabel: true
                  #indication: #autoCompare
                )
               #(#MenuItem
                  #label: 'Auto Update'
                  #translateLabel: true
                  #isVisible: #notReadOnly
                  #indication: #autoUpdate
                )
               #(#MenuItem
                  #label: '-'
                )
               #(#MenuItem
                  #label: 'Add Applies to ChangeSet...'
                  #translateLabel: true
                  #indication: #updateChangeSet
                )
               #(#MenuItem
                  #label: 'Apply in Original NameSpace'
                  #translateLabel: true
                  #indication: #applyInOriginalNameSpace
                )
               #(#MenuItem
                  #label: '-'
                )
               #(#MenuItem
                  #label: 'Apply into Package...'
                  #itemValue: #setEnforcedPackage
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: 'Apply in NameSpace...'
                  #itemValue: #setEnforcedNameSpace
                  #translateLabel: true
                )
               )
              nil
              nil
            )
          )
         #(#MenuItem
            #label: 'Help'
            #translateLabel: true
            #startGroup: #right
            #submenu: 
           #(#Menu
              #(
               #(#MenuItem
                  #label: 'ChangesBrowser Documentation'
                  #itemValue: #openHTMLDocument:
                  #translateLabel: true
                  #argument: 'tools/cbrowser/TOP.html'
                )
               #(#MenuItem
                  #label: '-'
                )
               #(#MenuItem
                  #label: 'About ChangesBrowser...'
                  #itemValue: #openAboutThisApplication
                  #translateLabel: true
                )
               )
              nil
              nil
            )
          )
         )
        nil
        nil
      )
! !

!ChangeSetBrowser methodsFor:'initialization & release'!

askIfChangesAreToBeWrittenBack
    |action|

    anyChanges ifFalse:[^ self].

    action := OptionBox 
                      request:(resources string:'The modified changeSet has not been saved.\\Update the changeSet before closing ?') withCRs
                      label:'ChangesBrowser'
                      form:(WarningBox iconBitmap)
                      buttonLabels:(resources array:#('Cancel' 'Don''t Update' 'Update'))
                      values:#(#abort #ignore #save)
                      default:#save
                      onCancel:#abort.

    action == #abort ifTrue:[^ self].
    action  == #save ifTrue:[
        self saveBackChanges
    ].
!

changeListMenu
    <resource: #programMenu >

    |items m|

    items := #(
                             ('Apply'                              doApply)
                             ('Apply to End'                       doApplyRest)
                             ('Apply All changes'                  doApplyAll)
                             ('-'                                  )
                             ('Delete'                             doDelete)
                             ('Delete to End'                      doDeleteRest)
                             ('Delete for Class to End'            doDeleteClassRest)
                             ('Delete All for Class'               doDeleteClassAll)
                             ('-'                                  )
"/                             ('Compress'                          doCompress)
                             ('Compare with Current'               doCompare)
                             ('-'                                  )
                             ('Make Change a Patch'                doMakePatch)
                             ('-'                                  )
                             ('Saveback ChangeSet'                 doSaveBack)
                             ('-'                                  )
                             ('Update'                             doUpdate)
                ).

    device ctrlDown ifTrue:[
        items := #(
                                 ('Inspect Change'                 doInspectChange)
                  ).
    ].

    m := PopUpMenu 
         itemList:items
         resources:resources.

    readOnly == true ifTrue:[
        m disableAll:#(doDelete doDeleteRest doDeleteClassRest doDeleteClassAll 
                       doDeleteClassAndPrivateClassesAll doCompress 
                       doFileoutAndDeleteClassAll doCheckinAndDeleteClassAll
                       doWriteBack doSaveBack doUpdate
                       doApplyAll doApplyRest)
    ].

    self hasSelection ifTrue:[
        m disable:#doApplyAll
    ].

    ^ m

    "Created: 3.12.1995 / 18:06:35 / cg"
    "Modified: 3.12.1995 / 18:13:06 / cg"
!

showingDiffsDefault
    ^ "false" super showingDiffsDefault 
! !

!ChangeSetBrowser methodsFor:'menu aspects'!

hasNotUndoableChangeSelected
    ^ (self hasUndoableMethodChangeSelected
      or:[self hasUndoableRemoveMethodChangeSelected]) not
!

hasUndoableMethodChangeSelected
    |nr chg|

    self hasSingleSelection ifTrue:[
        nr := self theSingleSelection.
        nr notNil ifTrue:[
            chg := changeSet at:nr.
            chg isMethodChange ifTrue:[
                chg isMethodRemoveChange ifFalse:[
                    chg previousVersion notNil ifTrue:[
                        ^ true
                    ]
                ]
            ]
        ]
    ].
    ^ false
!

hasUndoableRemoveMethodChangeSelected
    |nr chg|

    self hasSingleSelection ifTrue:[
        nr := self theSingleSelection.
        nr notNil ifTrue:[
            chg := changeSet at:nr.
            chg isMethodRemoveChange ifTrue:[
                chg previousVersion notNil ifTrue:[
                    ^ true
                ]
            ]
        ]
    ].
    ^ false
! !

!ChangeSetBrowser methodsFor:'private'!

applyChange:changeNr
    "fileIn a change"

    |nm applyAction aborted|

    nm := self classNameOfChange:changeNr.
    nm notNil ifTrue:[
        |cls|

        cls := Smalltalk at:(nm asSymbol) ifAbsent:[].
        cls notNil ifTrue:[
            cls isLoaded ifFalse:[
                cls autoload
            ]
        ]
    ].

    changeNrProcessed := changeNr.
    aborted := false.

    applyAction := [
        |sig|

        (skipSignal notNil) ifTrue:[
            sig := skipSignal
        ] ifFalse:[
            sig := AbortOperationRequest
        ].
        sig handle:[:ex |
            aborted := (sig == AbortOperationRequest).
        ] do:[
            Parser::ParseError handle:[:ex |       
                ex signal == Parser::UndefinedSuperclassError ifTrue:[
                    codeView error:(ex errorString) position:1 to:nil from:nil 
                ] ifFalse:[
                    codeView error:(ex description) position:(ex startPosition) to:(ex endPosition) from:(ex parser) 
                ]
            ] do:[
                |nameSpace pkg|

                nameSpace := self nameSpaceForApply.
                pkg := enforcedPackage ? Class packageQuerySignal query.             
                Class packageQuerySignal answer:pkg
                do:[    
                    Class nameSpaceQuerySignal answer:nameSpace
                    do:[
                        self applyPossiblyModifiedChange:(changeSet at:changeNr).
                    ]
                ]
            ]
        ].
        changeNrProcessed := nil.
    ].

    "/
    "/ if I am showing the changes file, dont update it
    "/
    changeFileName = ObjectMemory nameForChanges ifTrue:[
        Class withoutUpdatingChangesDo:applyAction
    ] ifFalse:[
        applyAction value
    ].
    ^ aborted not

    "Created: / 7.2.1998 / 19:32:35 / cg"
    "Modified: / 7.2.1998 / 19:35:11 / cg"
!

applyPossiblyModifiedChange:aChange
    |ns superClass superClassName|

    applyInOriginalNameSpace value ifFalse:[
        aChange isClassDefinitionChange ifTrue:[
            superClassName := aChange superClassName.

            ns := Class nameSpaceQuerySignal query.
            superClass := ns at:superClassName.
            (superClass isNil and:[ superClass ~~ Smalltalk ]) ifTrue:[
                superClass := Smalltalk at:superClassName.
            ].
            superClass isNil ifTrue:[
                (superClassName includes:$:) ifFalse:[
                    superClass := ns at:superClassName.
                ].
            ].
            superClass notNil ifTrue:[
                aChange superClassName:superClass name.
            ]
        ].
    ].

    aChange apply.
!

changeIsFollowupMethodChange:changeNr
    ^ false

    "Created: / 6.2.1998 / 13:04:59 / cg"
    "Modified: / 7.2.1998 / 19:28:52 / cg"
!

changeSet:aChangeSet
    originalChangeSet := aChangeSet.
    changeSet := OrderedCollection new.
    originalChangeSet notNil ifTrue:[
	originalChangeSet do:[:aChange |
	    changeSet add:aChange
	].
    ].
!

checkIfFileHasChanged
    Processor removeTimedBlock:checkBlock.
    changeSet size ~= originalChangeSet size ifTrue:[
        self newLabel:'(outdated)'.
        autoUpdate value ifTrue:[
            self doUpdate
        ]
    ] ifFalse:[
        "/ self newLabel:''
    ].
    Processor addTimedBlock:checkBlock afterSeconds:5.

    "Created: 3.12.1995 / 13:52:30 / cg"
    "Modified: 3.12.1995 / 14:15:06 / cg"
!

fullClassNameOfChange:nr
    ^ (changeSet at:nr) fullClassName

    "Created: / 6.2.1998 / 13:02:25 / cg"
    "Modified: / 6.2.1998 / 13:07:02 / cg"
!

isChangeSetBrowser
    ^ true
!

numberOfChanges
    ^ changeSet size

    "Created: 3.12.1995 / 18:15:56 / cg"
!

queryCloseText
	^ 'Quit without updating changeSet ?'
!

readChangesFileInBackground:dummy
    "read the changeSet, create a list of header-lines"

    |tabSpec|

    self withCursor:(Cursor read) do:[
        changeSet size == 0 ifTrue:[
            changeFileName notNil ifTrue:[
                changeSet := self class readXMLChangesFromFile:changeFileName inBackground:false.
            ].
        ].
        changeSet size == 0 ifTrue:[
            ^ nil
        ].

        tabSpec := TabulatorSpecification new.
        tabSpec unit:#inch.
        tabSpec positions:#(-1      0        5      8.5 ).
        "                   +/-    cls>>sel  type   info"
        tabSpec align:    #(#left  #left     #left  #left).

        changeChunks := OrderedCollection new.
        changeHeaderLines := OrderedCollection new.

        changeSet do:[:aChange | |entry|
            changeChunks add:(aChange printString).
            "/ changeHeaderLines add:(aChange printString)
            entry := MultiColListEntry new.
            entry tabulatorSpecification:tabSpec.
            entry colAt:1 put:''. "/ changeDelta.
            entry colAt:2 put:aChange printString.
            entry colAt:3 put:''. "/ changeType.
        
            (aChange respondsTo:#timeOfChangeIfKnown) ifTrue:[
                aChange timeOfChangeIfKnown notNil ifTrue:[
                    entry colAt:4 put:(aChange timeOfChangeIfKnown printString).
                ]
            ].    
            changeHeaderLines add:entry
        ].
        changeClassNames := OrderedCollection new:(changeChunks size).
        anyChanges := false
    ].

    "Created: 3.12.1995 / 18:02:39 / cg"
!

realClassNameOfChange:nr
    ^ (changeSet at:nr) className.

    "Created: / 5.11.2001 / 18:10:38 / cg"
!

saveBackChanges
    "save back the change set"

    [originalChangeSet isEmpty] whileFalse:[
	originalChangeSet removeLast
    ].
    changeSet do:[:aChange |
	originalChangeSet add:aChange
    ]
!

selectorOfMethodChange:changeNr
    ^ (changeSet at:changeNr) selector

    "Created: / 6.2.1998 / 13:28:20 / cg"
    "Modified: / 6.2.1998 / 13:29:59 / cg"
!

silentDeleteChange:changeNr
    "delete a change do not update changeListView"

    changeSet removeIndex:changeNr.
    super silentDeleteChange:changeNr.

    "Created: / 3.12.1995 / 18:14:17 / cg"
    "Modified: / 7.2.1998 / 19:57:57 / cg"
!

silentDeleteInternalChange:changeNr
    "delete a change do not update changeListView"

    changeSet removeIndex:changeNr.
    super silentDeleteInternalChange:changeNr.

    "Modified: / 7.2.1998 / 19:44:45 / cg"
    "Created: / 7.2.1998 / 19:58:02 / cg"
!

sourceOfChange:changeNr
    "answer a changes source"

    |change|

    change := changeSet at:changeNr.
    change isNil ifTrue:[^nil].
    ^ change source

    "Modified: / 7.2.1998 / 19:52:44 / cg"
!

streamForChange:changeNr
    "answer a stream for change"

    |change str source|

    change := changeSet at:changeNr.
    change isNil ifTrue:[^nil].
    change isMethodDefinitionChange ifTrue:[
        str := WriteStream on:''.
        str nextPutChunkSeparator.
        str nextPutAll:(change className , ' methodsFor:''' , change methodCategory , '''').
        str nextPutChunkSeparator.
        str cr.
        str nextPutAllAsChunk:change source.
        str nextPutChunkSeparator.
        str space.
        str nextPutChunkSeparator.
        str cr.
        source := str contents
    ] ifFalse:[
        source := change source
    ].
    ^ ReadStream on:source

    "Modified: / 7.2.1998 / 19:52:44 / cg"
! !

!ChangeSetBrowser methodsFor:'user actions'!

doInspectChange
    self withSelectedChangesDo:[:changeNr |
        (changeSet at:changeNr) inspect
    ].
!

doSaveBack
    anyChanges ifTrue:[
	self saveBackChanges.
	self doUpdate
    ]
!

doUpdate
    changeSet := OrderedCollection new.
    originalChangeSet notNil ifTrue:[
        originalChangeSet do:[:aChange |
            changeSet add:aChange
        ].
    ].
    super doUpdate

    "Created: 3.12.1995 / 13:54:14 / cg"
!

updateDiffViewFor:changeNr
    |change class selector oldMethod newSource oldSource|

    change := changeSet at:changeNr.
    change isMethodChange ifTrue:[
        newSource := change source.
        class := change changeClass.
        class notNil ifTrue:[
            selector := change changeSelector.
            selector notNil ifTrue:[
                oldMethod := class compiledMethodAt:selector.
                oldMethod notNil ifTrue:[
                    oldSource := oldMethod source.
                    diffView text1:(oldSource ? '') text2:(newSource ? '').
                    ^ self.
                ]
            ].
        ]
    ].

    super updateDiffViewFor:changeNr.
! !

!ChangeSetBrowser class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libtool/ChangeSetBrowser.st,v 1.42 2006-03-06 08:53:24 cg Exp $'
! !