ChangeSetBrowser.st
author Claus Gittinger <cg@exept.de>
Sat, 07 Feb 1998 19:12:24 +0100
changeset 1470 6c0fc11207fe
parent 224 1ca3d2486f59
child 1474 a791314e2e1d
permissions -rw-r--r--
checkin from browser

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

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

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

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

!ChangeSetBrowser class methodsFor:'defaults'!

defaultLabel
    ^ 'ChangeSet Browser'

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

!ChangeSetBrowser methodsFor:'initialize / release'!

changeListMenu
    |labels selectors|

    labels := #(
			     'apply change'
			     'apply changes to end'
			     'apply all changes'
			     '-'
			     'delete'
			     'delete to end'
			     'delete changes for this class to end'
			     'delete all changes for this class'
			     '-'
			     'update'
"/                             'compress'
			     'compare with current version'
			     '-'
			     'make change a patch'
"/                             'update sourcefile from change'
			     '-'
			     'saveback changeSet'
		).

    selectors := #(
			     doApply
			     doApplyRest
			     doApplyAll
			     nil
			     doDelete
			     doDeleteRest
			     doDeleteClassRest
			     doDeleteClassAll
			     nil
			     doUpdate
"/                             doCompress
			     doCompare
			     nil
			     doMakePatch
"/                             doMakePermanent
			     nil
			     doSaveBack
		).

    ^ PopUpMenu 
	 labels:labels
	 selectors:selectors
	 receiver:self

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

!ChangeSetBrowser methodsFor:'private'!

changeIsFollowupMethodChange:changeNr
    ^ false

    "Created: / 6.2.1998 / 13:04:59 / 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 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"
!

classNameOfChange:nr
    ^ (changeSet at:nr) class name

    "Created: 3.12.1995 / 18:15:56 / cg"
    "Modified: 3.12.1995 / 18:20:12 / cg"
!

fullClassNameOfChange:nr
    ^ (changeSet at:nr) className

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

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"

    changeSet size == 0 ifTrue:[^ nil].

    self newLabel:'updating ...'.
    self withCursor:(Cursor read) do:[
	changeChunks := OrderedCollection new.
	changeHeaderLines := OrderedCollection new.

	changeSet do:[:aChange |
	    changeChunks add:(aChange printString).
	    changeHeaderLines add:(aChange printString)
	].
	changeClassNames := OrderedCollection new:(changeChunks size).
	anyChanges := false
    ].
    self newLabel:''.

    "Created: 3.12.1995 / 18:02:39 / 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"

    anyChanges := true.
    changeChunks removeIndex:changeNr.
    changeHeaderLines removeIndex:changeNr.
"/    changeClassNames removeIndex:changeNr.
    changeSet removeIndex:changeNr

    "Created: 3.12.1995 / 18:14:17 / cg"
    "Modified: 3.12.1995 / 18:18:42 / cg"
!

streamForChange:changeNr
    "answer a stream for change"

    |change|

    change := changeSet at:changeNr.
    change isNil ifTrue:[^nil].
    ^ ReadStream on:(change source)
! !

!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.12 1998-02-07 18:11:26 cg Exp $'
! !