UIObjectView.st
author ca
Sat, 15 Feb 1997 19:15:25 +0100
changeset 50 fb4359c9bdc4
parent 49 7f58dd5fc836
child 51 01d0c9394944
permissions -rw-r--r--
checkin from browser

Object subclass:#UndoHistory
	instanceVariableNames:'history transaction enabled modifiedAction'
	classVariableNames:''
	poolDictionaries:''
	privateIn:UIObjectView
!

!UIObjectView::UndoHistory class methodsFor:'instance creation'!

new
    ^ self basicNew initialize


! !

!UIObjectView::UndoHistory class methodsFor:'constants'!

maxHistorySize
    "returns maximum size of history before removing oldest
     record
    "
    ^ 50


! !

!UIObjectView::UndoHistory methodsFor:'accessing'!

modifiedAction:aBlockWithOneArg
    "the block is evaluated whenever the history changed; the argument to the
     block is the newest transaction identifier retrived from 'openTransaction'
    "
    modifiedAction := aBlockWithOneArg


! !

!UIObjectView::UndoHistory methodsFor:'initialization'!

initialize
    super initialize.
    self  reinitialize.


!

reinitialize
    "reinitialize all attributes
    "
    history := OrderedCollection new.
    transaction := nil.
    enabled := true.


! !

!UIObjectView::UndoHistory methodsFor:'notifications'!

modified
    "raise notification; history changed
    "
    modifiedAction notNil ifTrue:[
        |what|

        history isEmpty ifTrue:[what := nil]
                       ifFalse:[what := history last first].

        modifiedAction value:what
    ]


! !

!UIObjectView::UndoHistory methodsFor:'testing'!

isEmpty
    "returns true if undo history is empty
    "
    ^ history isEmpty


!

isTransactionOpen
    ^ (enabled and:[transaction notNil])
!

notEmpty
    "returns true if undo history is not empty
    "
    ^ history notEmpty


! !

!UIObjectView::UndoHistory methodsFor:'transaction'!

addUndoBlock:anUndoBlock
    "undo block to restore changes; add block to current transaction
    "
    enabled ifTrue:[
        transaction isNil ifTrue:[
            "no existing transaction
            "
            self halt
        ] ifFalse:[
            (transaction at:2) add:anUndoBlock
        ]
    ]


!

closeTransaction
    "close current transaction
    "
    self isTransactionOpen ifTrue:[
        transaction last isEmpty ifTrue:[
            "empty undo transaction
            "
            transaction := nil
        ] ifFalse:[
            history addLast:transaction.
            transaction := nil.

            history size > (self class maxHistorySize) ifTrue:[
                history removeFirst
            ].
            self modified
        ]
    ]


!

disabledTransitionDo:aBlock
    "disable transitions during evaluating the block
    "
    |oldState|

    oldState := enabled.
    enabled  := false.
    aBlock value.
    enabled  := oldState.
!

openTransaction:what
    "open a new transaction
    "
    enabled ifTrue:[
        transaction notNil ifTrue:[
            "transaction within transaction
            "
            self halt.
        ] ifFalse:[
            transaction := Array with:what with:OrderedCollection new
        ]
    ]

!

transactionNamed:what do:aBlock
    "open a transaction; perform the block; at least close the transaction
    "
    self isTransactionOpen ifFalse:[
        self openTransaction:what.
        aBlock value.
        self closeTransaction
    ] ifTrue:[
        aBlock value
    ]
! !

!UIObjectView::UndoHistory methodsFor:'undo'!

undoLast
    "undo last transactions; an open transaction will be closed;
     transactions during undo are disabled
    "
    self undoLast:1


!

undoLast:nTransactions
    "undo last n transactions; an open transaction will be closed;
     transactions during undo are disabled
    "
    |actions n|

    transaction := nil.
    n := nTransactions min:(history size).

    n ~~ 0 ifTrue:[
        enabled := false.

        n timesRepeat:[
            actions := (history removeLast) last.

            actions reverseDo:[:aUndoBlock|
                aUndoBlock value
            ]
        ].
        enabled := true.
        self modified.
    ]


! !