UndoSupport.st
author Claus Gittinger <cg@exept.de>
Sat, 08 Mar 2008 11:53:23 +0100
changeset 1932 7bafb4c076d3
parent 1588 7a69b6a027b0
child 2136 2accac6ffb0f
permissions -rw-r--r--
also show \"what-would-be-done\" in redo item

"
 COPYRIGHT (c) 2004 by eXept Software AG
              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:libbasic2' }"

Object subclass:#UndoSupport
	instanceVariableNames:'actionPerformer transaction undoList redoList
		infoOfCurrentTransaction'
	classVariableNames:''
	poolDictionaries:''
	category:'Views-Text'
!

Object subclass:#CompoundAction
	instanceVariableNames:'actions userFriendlyInfo'
	classVariableNames:''
	poolDictionaries:''
	privateIn:UndoSupport
!

!UndoSupport class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2004 by eXept Software AG
              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
"
    Framework for undo & redo.
    See concrete usage in EditTextView.

    [author:]
         (cg@betti)

    [instance variables:]

    [class variables:]

    [see also:]

"
!

examples
"
    See usage in EditTextView
"
! !

!UndoSupport class methodsFor:'instance creation'!

for:anActionPerformer
    ^ self new actionPerformer:anActionPerformer.
!

new
    ^ self basicNew initialize.
! !

!UndoSupport methodsFor:'accessing'!

actionInfo:aString
    infoOfCurrentTransaction := aString
! !

!UndoSupport methodsFor:'initialization'!

actionPerformer:something
    actionPerformer := something.
!

initialize
    self resetHistories.
!

resetHistories
    transaction := nil.
    undoList := OrderedCollection new.
    redoList := OrderedCollection new.
! !

!UndoSupport methodsFor:'undo & again'!

addUndo:action
    transaction notNil ifTrue:[
        transaction add:action
    ].
!

closeTransactionAndAddTo:aList
    |actionToAdd lastAction canCombine|

    transaction notEmptyOrNil ifTrue:[
        canCombine := false.
        (transaction size == 1 and:[infoOfCurrentTransaction isNil]) ifTrue:[
            actionToAdd := transaction first.

            aList notEmpty ifTrue:[
                lastAction := aList last.
                canCombine := lastAction perform:#canCombineWithNext: with:actionToAdd ifNotUnderstood:false.
            ].
        ] ifFalse:[
            actionToAdd := (CompoundAction new actions:transaction).
            actionToAdd info:infoOfCurrentTransaction.
        ].

        canCombine ifTrue:[
            lastAction combineWithNext:actionToAdd.
        ] ifFalse:[
            aList add:actionToAdd.
        ].
    ].
    infoOfCurrentTransaction := nil.
    transaction := nil
!

executeActionFrom:doList addUndoTo:unDoList
    |action previousTransaction|

    doList notEmptyOrNil ifTrue:[
        action := doList removeLast.

        previousTransaction := transaction.
        [
            transaction := OrderedCollection new.

            action executeIn:actionPerformer.

            self closeTransactionAndAddTo:unDoList.
        ] ensure:[
            transaction := previousTransaction.
        ]
    ]
!

hasRedoAction
    ^ redoList size > 0
!

hasUndoAction
    ^ undoList size > 0
!

lastRedoAction
    ^ redoList removeLast
!

lastUndoAction
    ^ undoList removeLast
!

nonUndoableDo:aBlock
    |prev|

    prev := transaction.
    transaction := nil.
    aBlock 
        ensure:[
            transaction := prev.
        ].
!

redo
    self executeActionFrom:redoList addUndoTo:undoList
!

redoActionInfo
    ^ redoList last info
!

undo
    self executeActionFrom:undoList addUndoTo:redoList
!

undoActionInfo
    ^ undoList last info
!

undoableDo:aBlock
    self undoableDo:aBlock info:nil.
!

undoableDo:aBlock info:aString
    transaction notNil ifTrue:[
        infoOfCurrentTransaction := infoOfCurrentTransaction ? aString.
        aBlock value.
    ] ifFalse:[
        transaction := OrderedCollection new.
        infoOfCurrentTransaction := aString.
        aBlock 
            ensure:[  
                self closeTransactionAndAddTo:undoList.
            ].
    ].
! !

!UndoSupport::CompoundAction methodsFor:'accessing'!

info
    ^ userFriendlyInfo
!

info:aString
    userFriendlyInfo := aString
! !

!UndoSupport::CompoundAction methodsFor:'adding'!

actions:aCollection
    actions := aCollection
!

add:action
    actions isNil ifTrue:[
        actions := OrderedCollection new.
    ].
    actions add:action
! !

!UndoSupport::CompoundAction methodsFor:'execution'!

executeIn:editor 
    actions reverseDo:[:each | each executeIn:editor ]
! !

!UndoSupport::CompoundAction methodsFor:'queries'!

canCombineWithNext:nextAction
    ^ false.
! !

!UndoSupport class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/UndoSupport.st,v 1.9 2008-03-08 10:53:23 cg Exp $'
! !