ChangeSetBrowser.st
author Claus Gittinger <cg@exept.de>
Mon, 18 Nov 2002 18:12:40 +0100
changeset 4279 1fbb8fa63669
parent 4232 88e1552f4da9
child 4316 a0d59a6735e2
permissions -rw-r--r--
care for parser errors when applying

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

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

!ChangeSetBrowser methodsFor:'initialize / release'!

askIfChangesAreToBeWrittenBack
    |action|

    anyChanges ifFalse:[^ self].

    action := OptionBox 
                      request:(resources at:'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)
"/                             ('update sourcefile from change'    doMakePermanent)
                             ('-'                                  )
                             ('Saveback ChangeSet'                 doSaveBack)
                             ('-'                                  )
                             ('Update'                             doUpdate)
                ).

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

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

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

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

    changeNrProcessed := changeNr.

    applyAction := [
        |sig|

        (skipSignal notNil) ifTrue:[
            sig := skipSignal
        ] ifFalse:[
            sig := Object abortSignal
        ].
        sig catch:[

            Parser::ParseError handle:[:ex |       
                ex signal == Parser::UndefinedSuperclassError ifTrue:[
                    codeView error:(ex errorString) position:1 to:nil from:nil 
                ] ifFalse:[
                    codeView error:(ex errorMessage) position:(ex startPosition) to:(ex endPosition) from:(ex parser) 
                ]
            ] do:[
                (changeSet at:changeNr) apply.
            ]
        ].
        changeNrProcessed := nil.
    ].

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

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

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

    "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
    ].
    self newLabel:''.

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

    change := changeSet at:changeNr.
    change isNil ifTrue:[^nil].
    change isMethodChange ifTrue:[
        s := '!!' , change className , 
             ' methodsFor:''' , change methodCategory , '''!!\' withCRs ,
             change source , '\' withCRs , '!! !!\' withCRs.
        ^ ReadStream on:s
    ].
    ^ ReadStream on:(change source)

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

!ChangeSetBrowser methodsFor:'user actions'!

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

!ChangeSetBrowser class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libtool/ChangeSetBrowser.st,v 1.29 2002-11-18 17:12:40 cg Exp $'
! !