undo history; keep view identifier
authorca
Wed, 28 May 1997 12:27:24 +0200
changeset 134 d5ab85ec27fd
parent 133 e12f82d3afb7
child 135 8f4b6117ccaa
undo history; keep view identifier modification flag
UIObjectView.st
UIPainterView.st
--- a/UIObjectView.st	Wed May 28 12:25:20 1997 +0200
+++ b/UIObjectView.st	Wed May 28 12:27:24 1997 +0200
@@ -8,14 +8,14 @@
 !
 
 Object subclass:#UndoHistory
-	instanceVariableNames:'history transaction enabled'
+	instanceVariableNames:'startIdentifier identifier painter history transaction enabled'
 	classVariableNames:''
 	poolDictionaries:''
 	privateIn:UIObjectView
 !
 
 Object subclass:#Transaction
-	instanceVariableNames:'type text actions'
+	instanceVariableNames:'identifier type text actions'
 	classVariableNames:''
 	poolDictionaries:''
 	privateIn:UIObjectView::UndoHistory
@@ -262,6 +262,12 @@
 
 !
 
+resetModification
+    "set modification state to false
+    "
+    undoHistory resetModification
+!
+
 testMode
     "returns true if running test
     "
@@ -382,7 +388,7 @@
 
     self setDefaultActions.
 
-    undoHistory          := UndoHistory new.
+    undoHistory          := UndoHistory on:self.
     enableChannel        := true asValue.
     clipChildren         := true.
     selectionHiddenLevel := 0.
@@ -665,7 +671,7 @@
         dX := delta x.
         dY := delta y.
 
-        undoHistory disabledTransitionDo:[
+        undoHistory withoutTransactionDo:[
             self shiftLayout:anObject top:dY bottom:dY left:dX right:dX
         ]
     ]
@@ -689,7 +695,7 @@
 
     self transaction:#move objects:movedObject do:[:aView|
         self invertOutlineOf:aView.
-        self undoLayoutView:aView
+        self createUndoLayout:aView
     ].
 
 !
@@ -830,7 +836,7 @@
     self actionResize:object selector:b.
 
     self transaction:#resize selectionDo:[:aView|
-        self undoLayoutView:aView
+        self createUndoLayout:aView
     ].
     self setSelection:nil withRedraw:true.
 
@@ -972,7 +978,7 @@
 resize:aView bottom:aPoint
     "resize a views bottom
     "
-    undoHistory disabledTransitionDo:[
+    undoHistory withoutTransactionDo:[
         self shiftLayout:aView top:0 bottom:((aPoint y) - (aView computeCorner y))
     ]
 !
@@ -980,7 +986,7 @@
 resize:aView bottomLeft:aPoint
     "resize a views bottom and left
     "
-    undoHistory disabledTransitionDo:[
+    undoHistory withoutTransactionDo:[
         self shiftLayout:aView top:0
                             bottom:((aPoint y) - (aView computeCorner y))
                               left:((aPoint x) - (aView computeOrigin x))
@@ -998,7 +1004,7 @@
 
     delta := aPoint - aView computeCorner.
 
-    undoHistory disabledTransitionDo:[
+    undoHistory withoutTransactionDo:[
         self shiftLayout:aView top:0 bottom:(delta y) left:0 right:(delta x)
     ]
 !
@@ -1006,7 +1012,7 @@
 resize:aView left:aPoint
     "resize a views left
     "
-    undoHistory disabledTransitionDo:[
+    undoHistory withoutTransactionDo:[
         self shiftLayout:aView left:((aPoint x) - (aView computeOrigin x)) right:0
     ]
 
@@ -1019,7 +1025,7 @@
 
     delta := aPoint - aView computeOrigin.
 
-    undoHistory disabledTransitionDo:[
+    undoHistory withoutTransactionDo:[
         self shiftLayout:aView top:(delta y) bottom:0 left:(delta x) right:0
     ]
 
@@ -1028,7 +1034,7 @@
 resize:aView right:aPoint
     "resize a views right
     "
-    undoHistory disabledTransitionDo:[
+    undoHistory withoutTransactionDo:[
         self shiftLayout:aView left:0 right:((aPoint x) - (aView computeCorner x))
     ]
 !
@@ -1036,7 +1042,7 @@
 resize:aView top:aPoint
     "resize a views top
     "
-    undoHistory disabledTransitionDo:[
+    undoHistory withoutTransactionDo:[
         self shiftLayout:aView top:((aPoint y) - (aView computeOrigin y)) bottom:0
     ]
 !
@@ -1044,7 +1050,7 @@
 resize:aView topRight:aPoint
     "resize a views top and right
     "
-    undoHistory disabledTransitionDo:[
+    undoHistory withoutTransactionDo:[
         self shiftLayout:aView top:((aPoint y) - (aView computeOrigin y))
                             bottom:0
                               left:0
@@ -1082,7 +1088,7 @@
     type := self class layoutType:aView.
 
     type notNil ifTrue:[
-        self undoLayoutView:aView.
+        self createUndoLayout:aView.
 
         type == #Extent ifTrue:[
             oldExt := aView extent.
@@ -1474,12 +1480,6 @@
 
 !
 
-hasUndos
-    "returns true if undoHistory not empty
-    "
-    ^ undoHistory notEmpty
-!
-
 isHorizontalResizable:aComponent
     "returns true if instance is horizontal resizeable
     "
@@ -1488,6 +1488,12 @@
 
 !
 
+isModified
+    "returns true if painter is modified
+    "
+  ^ undoHistory isModified
+!
+
 isSelected:anObject
     "return true, if the argument, anObject is selected
     "
@@ -1516,6 +1522,13 @@
 
 !UIObjectView methodsFor:'transaction'!
 
+createUndoLayout:aView
+    "prepare undo action for a view changing its layout
+    "
+    self subclassResponsibility
+
+!
+
 transaction:aType objects:something do:aOneArgBlock
     "opens a transaction and evaluates a block within the transaction; the
      argument to the block is a view from derived from something
@@ -1532,13 +1545,6 @@
     self transaction:aType objects:(self selection) do:aOneArgBlock
 
 
-!
-
-undoLayoutView:aView
-    "prepare undo action for a view changing its layout
-    "
-    self subclassResponsibility
-
 ! !
 
 !UIObjectView methodsFor:'user actions - arrange'!
@@ -1600,7 +1606,7 @@
     "paste the copied extent to all objects in the selection
     "
     copiedExtent notNil ifTrue:[
-        self transition:#pasteExtent dimensionDo:[:v|
+        self transaction:#pasteExtent dimensionDo:[:v|
             self resize:v corner:(v computeOrigin + copiedExtent)
         ]    
     ]    
@@ -1610,7 +1616,7 @@
     "paste the copied extent height to all objects in the selection
     "
     copiedExtent notNil ifTrue:[
-        self transition:#pasteHeight dimensionDo:[:v|
+        self transaction:#pasteHeight dimensionDo:[:v|
             self resize:v bottom:(v computeOrigin + copiedExtent)
         ]    
     ]    
@@ -1621,7 +1627,7 @@
     "paste layout to all objects in the selection
     "
     copiedLayout notNil ifTrue:[
-        self transition:#pasteLayout dimensionDo:[:v|
+        self transaction:#pasteLayout dimensionDo:[:v|
             v geometryLayout:(copiedLayout copy)
         ]    
     ]    
@@ -1631,7 +1637,7 @@
     "paste the copied extent width to all objects in the selection
     "
     copiedExtent notNil ifTrue:[
-        self transition:#pasteWidth dimensionDo:[:v|
+        self transaction:#pasteWidth dimensionDo:[:v|
             self resize:v right:(v computeOrigin + copiedExtent)
         ]    
     ]    
@@ -1641,7 +1647,7 @@
 setDimension:aLayout
     "change layout for all selected objects
     "
-    self transition:#layout dimensionDo:[:v|
+    self transaction:#layout dimensionDo:[:v|
         v geometryLayout:(aLayout copy)
     ].    
 
@@ -1650,7 +1656,7 @@
 setExtent:anExtent
     "change extent for all selected objects
     "
-    self transition:#extent dimensionDo:[:v|
+    self transaction:#extent dimensionDo:[:v|
         v geometryLayout:nil.
         v extent:anExtent.
     ].
@@ -1661,7 +1667,7 @@
 setToDefaultExtent
     "change extent of all selected views to their default extent
     "
-    self transition:#defaultExtent dimensionDo:[:v|
+    self transaction:#defaultExtent dimensionDo:[:v|
         self resize:v corner:(v computeOrigin + (v preferredExtent))
     ]    
 
@@ -1670,7 +1676,7 @@
 setToDefaultHeight
     "change height of all selected views to their default height
     "
-    self transition:#defaultHeight dimensionDo:[:v|
+    self transaction:#defaultHeight dimensionDo:[:v|
         self resize:v bottom:(v computeOrigin + (v preferredExtent))
     ]    
 
@@ -1679,20 +1685,20 @@
 setToDefaultWidth
     "change width of all selected views to their default width
     "
-    self transition:#defaultWidth dimensionDo:[:v|
+    self transaction:#defaultWidth dimensionDo:[:v|
         self resize:v right:(v computeOrigin + (v preferredExtent))
     ]    
 
 !
 
-transition:aType dimensionDo:aOneArgBlock
+transaction:aType dimensionDo:aOneArgBlock
     "change dimension within a transaction for the selected elements by evaluating
      the block with the argument a view.
     "
     self withSelectionHiddenDo:[
         self transaction:aType selectionDo:[:aView|
             (self class layoutType:aView) notNil ifTrue:[
-                self undoLayoutView:aView.
+                self createUndoLayout:aView.
                 aOneArgBlock value:aView.
                 self elementChangedSize:aView.
             ]
@@ -1952,10 +1958,10 @@
                     layout := self class asLayoutFrameFromView:aView.
 
                     layout notNil ifTrue:[
-                        self undoLayoutView:aView.
+                        self createUndoLayout:aView.
                         aView geometryLayout:layout.
 
-                        undoHistory disabledTransitionDo:[    
+                        undoHistory withoutTransactionDo:[    
                             self shiftLayout:aView left:(lmost - (aView computeOrigin x))
                                                   right:(rmost - (aView computeCorner x)).
                         ].
@@ -2048,10 +2054,10 @@
                     layout := self class asLayoutFrameFromView:aView.
 
                     layout notNil ifTrue:[
-                        self undoLayoutView:aView.
+                        self createUndoLayout:aView.
                         aView geometryLayout:layout.
 
-                        undoHistory disabledTransitionDo:[    
+                        undoHistory withoutTransactionDo:[    
                             self shiftLayout:aView top:(tmost - (aView computeOrigin y))
                                                 bottom:(bmost - (aView computeCorner y)).
                         ].
@@ -2149,7 +2155,7 @@
         layout := self class asLayoutFrameFromView:aView.
 
         layout notNil ifTrue:[
-            self undoLayoutView:aView.
+            self createUndoLayout:aView.
             aBlock value:layout.
             aView geometryLayout:layout.
             self elementChangedSize:aView.
@@ -2253,10 +2259,12 @@
 openUndoMenu
     "open undo menu
     "
-    self select:nil.
-
-    self withSelectionHiddenDo:[
-        undoHistory openUndoMenu
+    undoHistory isEmpty ifFalse:[
+        self select:nil.
+
+        self withSelectionHiddenDo:[
+            undoHistory openUndoMenu
+        ]
     ].
 
 !
@@ -2264,16 +2272,18 @@
 removeUndoHistory
     "delete total undo history
     "
-    undoHistory reinitialize
+    undoHistory on:self
 !
 
 undoLast
     "undo last action
     "
-    self select:nil.
-
-    self withSelectionHiddenDo:[
-        undoHistory undoLast:1
+    undoHistory isEmpty ifFalse:[
+        self select:nil.
+
+        self withSelectionHiddenDo:[
+            undoHistory undoLast:1
+        ]
     ].
 
 ! !
@@ -2284,7 +2294,7 @@
     "returns maximum size of history before removing oldest
      record
     "
-    ^ 50
+    ^ 100
 
 
 ! !
@@ -2307,14 +2317,31 @@
 
 !UIObjectView::UndoHistory class methodsFor:'instance creation'!
 
-new
-    ^ self basicNew initialize
+on:aPainter
+    |history|
+
+    history := self new.
+    history on:aPainter.
+  ^ history
 
 
 ! !
 
 !UIObjectView::UndoHistory methodsFor:'accessing'!
 
+addUndoSelector:aSelector withArgs:anArray
+    "add a selector with arguments to the current opened transaction; in case that no
+     transaction is opened or disabled the block will not be kept in the history.
+    "
+    self isTransactionOpen ifTrue:[
+        transaction add:(Association key:aSelector value:anArray)
+    ]
+
+
+! !
+
+!UIObjectView::UndoHistory methodsFor:'accessing behavior'!
+
 enabled
     ^ enabled
 !
@@ -2323,33 +2350,56 @@
     enabled := aState
 !
 
-historySize
-    ^ history size
-!
-
-lastTypeAsString
-    "returns type of last undo asString or nil
+resetModification
+    "set modification state to false
+    "
+    startIdentifier := identifier
+! !
+
+!UIObjectView::UndoHistory methodsFor:'activation'!
+
+withinTransaction:aType text:aTextOrNil do:aBlock
+    "open a transaction; perform the block; at least close the transaction
     "
-    history notEmpty ifTrue:[
-        ^ history last typeAsString
-    ].
-    ^ nil
-
-
+    (enabled and:[transaction isNil]) ifTrue:[
+        transaction := Transaction type:aType text:aTextOrNil.
+
+        aBlock value.
+
+        transaction isEmpty ifFalse:[
+            identifier := identifier + 1.
+            transaction identifier:identifier.
+            history addLast:transaction.
+            history size > (self class maxHistorySize) ifTrue:[history removeFirst]
+        ].
+        transaction := nil
+
+    ] ifFalse:[
+        aBlock value
+    ]
+!
+
+withoutTransactionDo:aNoneArgBlock
+    "evaluate the block without opening a transaction or keeping changes
+     within a still opened transaction
+    "
+    |oldState|
+
+    oldState := enabled.
+    enabled  := false.
+    aNoneArgBlock value.
+    enabled  := oldState.
 ! !
 
 !UIObjectView::UndoHistory methodsFor:'initialization'!
 
-initialize
-    super initialize.
-    self  reinitialize.
-
-
-!
-
-reinitialize
-    "reinitialize all attributes
+on:aPainter
+    "setup for a painter and delete all existing history records
     "
+    identifier      := 0.
+    startIdentifier := 0.
+
+    painter     := aPainter.
     history     := OrderedCollection new.
     transaction := nil.
     enabled     := true.
@@ -2413,62 +2463,17 @@
 
 !
 
+isModified
+    "returns true if history is modified
+    "
+    self isEmpty ifTrue:[
+        ^ false
+    ].
+  ^ history last identifier ~~ startIdentifier
+!
+
 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
-    "
-    self isTransactionOpen ifTrue:[
-        transaction add:anUndoBlock
-    ]
-
-
-!
-
-disabledTransitionDo:aBlock
-    "disable transitions during evaluating the block
-    "
-    |oldState|
-
-    oldState := enabled.
-    enabled  := false.
-    aBlock value.
-    enabled  := oldState.
-!
-
-transaction:aType do:aBlock
-    self transaction:aType text:nil do:aBlock
-!
-
-transaction:aType text:aTextOrNil do:aBlock
-    "open a transaction; perform the block; at least close the transaction
-    "
-    (enabled and:[transaction isNil]) ifTrue:[
-        transaction := Transaction type:aType text:aTextOrNil.
-
-        aBlock value.
-
-        transaction isEmpty ifFalse:[
-            history addLast:transaction.
-            history size > (self class maxHistorySize) ifTrue:[history removeFirst]
-        ].
-        transaction := nil
-
-    ] ifFalse:[
-        aBlock value
-    ]
 ! !
 
 !UIObjectView::UndoHistory methodsFor:'undo'!
@@ -2477,18 +2482,25 @@
     "undo last n transactions; an open transaction will be closed;
      transactions during undo are disabled
     "
-    |n|
+    |repeatTimes transaction actions|
 
     transaction := nil.
-    n := nTransactions min:(history size).
-
-    n ~~ 0 ifTrue:[
-        enabled := false.
-        n timesRepeat:[ (history removeLast) undo ].
-        enabled := true.
-    ]
-
-
+    enabled     := false.
+    repeatTimes := nTransactions min:(history size).
+
+    repeatTimes timesRepeat:[
+        transaction := history removeLast.
+        actions     := transaction actions.
+
+        actions isCollection ifTrue:[
+            actions reverseDo:[:aBlock|
+                painter perform:(aBlock key) with:(aBlock value)
+            ]
+        ] ifFalse:[
+            painter perform:(actions key) with:(actions value)
+        ]
+    ].
+    enabled := true.
 ! !
 
 !UIObjectView::UndoHistory::Transaction class methodsFor:'documentation'!
@@ -2514,20 +2526,38 @@
 
 !UIObjectView::UndoHistory::Transaction methodsFor:'accessing'!
 
+actions
+    "returns actions associated with transaction
+    "
+  ^ actions
+!
+
+identifier
+    "gets my identifier
+    "
+  ^ identifier
+!
+
+identifier:anIdentifier
+    "sets my identifier
+    "
+    identifier := anIdentifier
+!
+
 text
-    "returns text or nil assigned to transition
+    "returns text or nil assigned to transaction
     "
     ^ text
 !
 
 type
-    "returns type assigned to transition
+    "returns type assigned to transaction
     "
     ^ type
 !
 
 type:aType
-    "change type assigned to transition
+    "change type assigned to transaction
     "
     type := aType
 !
@@ -2558,41 +2588,25 @@
     ^ name
 ! !
 
-!UIObjectView::UndoHistory::Transaction methodsFor:'add & undo'!
+!UIObjectView::UndoHistory::Transaction methodsFor:'adding'!
 
 add:anUndoBlock
-    "add an undo action to the transition
+    "add an undo action to the current transaction
     "
     actions isNil ifTrue:[
         actions := anUndoBlock
     ] ifFalse:[
         actions isCollection ifFalse:[
-            |temp|
-
-            temp := OrderedCollection new.
-            temp add:actions.
-            actions := temp.
+            actions := OrderedCollection with:actions
         ].
         actions add:anUndoBlock.
     ]
-!
-
-undo
-    "undo transition
-    "
-    actions notNil ifTrue:[
-        actions isCollection ifFalse:[
-            actions value
-        ] ifTrue:[
-            actions reverseDo:[:anUndoBlock| anUndoBlock value ]
-        ]
-    ]
 ! !
 
 !UIObjectView::UndoHistory::Transaction methodsFor:'initialization'!
 
 type:aType text:aTextOrNil
-    "initialize transition
+    "initialize transaction
     "
     type := aType.
     text := aTextOrNil.
@@ -2604,12 +2618,6 @@
     "returns true if no undo action is registered
     "
     ^ actions isNil
-!
-
-notEmpty
-    "returns true if any undo action is registered
-    "
-    ^ actions notNil
 ! !
 
 !UIObjectView class methodsFor:'documentation'!
--- a/UIPainterView.st	Wed May 28 12:25:20 1997 +0200
+++ b/UIPainterView.st	Wed May 28 12:27:24 1997 +0200
@@ -403,7 +403,7 @@
     "delete the selection; copy the selection into the cut&paste-buffer
      and open a transaction
     "
-    |text specs coll|
+    |specs coll|
 
     coll := self minSetOfSuperViews:(self selection).
 
@@ -411,14 +411,11 @@
         listHolder disableNotificationsWhileEvaluating:[
             self select:nil.
             specs := coll collect:[:aView| self fullSpecFor:aView ].
-            text  := self transactionTextFor:coll.
 
-            undoHistory transaction:#cut text:text do:[
-                coll reverseDo:[:o||p|
-                    (p := self propertyOfView:o) notNil ifTrue:[
-                        self undoRemove:(p identifier)
-                    ].
-                    self remove:o
+            self withinTransaction:#cut objects:coll do:[
+                coll reverseDo:[:aView|
+                    self createUndoRemove:aView.
+                    self remove:aView
                 ]
             ].
             self setSelection:specs.
@@ -481,9 +478,11 @@
         ].
     ].
 
-    self transaction:#paste objects:newSel do:[:v|
-        self undoCreate:((self propertyOfView:v) identifier)
+    self withinTransaction:#paste objects:newSel do:[
+        undoHistory addUndoSelector:#undoCreate:
+                           withArgs:(newSel collect:[:v|(self propertyOfView:v) identifier])
     ].
+
     newSel size == 1 ifTrue:[
         newSel := newSel at:1
     ].
@@ -539,6 +538,10 @@
 !
 
 generateAspectMethodFor:aspect spec:protoSpec inClass:targetClass
+    |modelClass|
+
+    modelClass := protoSpec defaultModelClass.
+
     ^ ('!!' , targetClass name , ' methodsFor:''aspects''!!\\' ,
       aspect , '\' ,
       '    "automatically generated by UIPainter ..."\' ,
@@ -546,7 +549,7 @@
       '    |holder|\' ,
       '\' ,
       '    (holder := builder bindingAt:#' , aspect , ') isNil ifTrue:[\' ,
-      '        builder aspectAt:#' , aspect , ' put:(holder := ' , ' ValueHolder new' , ').\' ,
+      '        builder aspectAt:#' , aspect , ' put:(holder := ' , ' ' , modelClass name , ' new' , ').\' ,
       '    ].\' ,
       '    ^ holder\' ,
       '!! !!\\') withCRs
@@ -566,9 +569,13 @@
     listHolder propertiesDo:[:aProp |
         |modelSelector menuSelector protoSpec thisCode|
 
+        protoSpec := aProp spec.
+        protoSpec isNil ifTrue:[
+            self halt.
+            protoSpec := aProp view specClass basicNew.
+        ].
         (modelSelector := aProp model) notNil ifTrue:[
             (cls implements:modelSelector asSymbol) ifFalse:[
-                protoSpec := aProp view specClass basicNew.
                 "/ kludge ..
                 (protoSpec isMemberOf:ActionButtonSpec) ifTrue:[
                     thisCode := (self generateActionMethodFor:modelSelector spec:protoSpec inClass:cls).
@@ -581,7 +588,6 @@
 
         (menuSelector := aProp menu) notNil ifTrue:[
             (cls implements:menuSelector asSymbol) ifFalse:[
-                protoSpec := aProp view specClass basicNew.
                 "/ kludge ..
                 thisCode := (self generateAspectMethodFor:menuSelector spec:protoSpec inClass:cls).
                 code := code , thisCode
@@ -590,7 +596,6 @@
 
         aProp spec aspectSelectors do:[:aSel|
             (cls implements:aSel asSymbol) ifFalse:[
-                protoSpec := aProp view specClass basicNew.
                 "/ kludge ..
                 thisCode := (self generateAspectMethodFor:aSel spec:protoSpec inClass:cls).
                 code := code , thisCode
@@ -624,6 +629,8 @@
 
     |code|
 
+    self resetModification.
+
     code := ''.
 
 "/    (Smalltalk classNamed:className asSymbol) isNil ifTrue:[
@@ -995,8 +1002,8 @@
         spec label:(props name)
     ].
 
-    undoHistory transaction:#create text:(props name) do:[
-        self undoCreate:(props identifier).
+    undoHistory withinTransaction:#create text:(props name) do:[
+        undoHistory addUndoSelector:#undoCreate: withArgs:(props identifier)
     ].
 !
 
@@ -1049,7 +1056,7 @@
         menu disableAll
     ].
     menu enabledAt:#paste put:canPaste.
-    menu enabledAt:#undo  put:(undoHistory notEmpty).
+    menu enabledAt:#undo  put:(undoHistory isEmpty not).
     menu startUp.
   ^ nil
 
@@ -1106,7 +1113,9 @@
 remove:anObject
     "remove anObject from the contents do redraw
     "
-    listHolder remove:anObject.
+    anObject notNil ifTrue:[
+        listHolder remove:anObject
+    ]
 !
 
 removeAll
@@ -1114,8 +1123,8 @@
     "
     listHolder disableNotificationsWhileEvaluating:[
         self select:nil.
-        listHolder  removeAll.
-        undoHistory reinitialize.
+        listHolder removeAll.
+        self removeUndoHistory.
     ]
 ! !
 
@@ -1390,7 +1399,7 @@
                     ]
                 ].
                 aSpec name:name.
-                self undoSpecModify:(props identifier).
+                self createUndoSpecModify:props.
 
                 aSpec needsRebuildForAttributes ifTrue:[
                     v := aSpec buildViewWithLayoutFor:builder in:aView superView.
@@ -1474,143 +1483,154 @@
     "opens a transaction and evaluates a block within the transaction; the
      argument to the block is a view from derived from something
     "
-    |text|
-
-    something notNil ifTrue:[
-        text := self transactionTextFor:something.
-
-        undoHistory transaction:aType text:text do:[
-            something isCollection ifTrue:[
-                something do:[:aView| aOneArgBlock value:aView ]
-            ] ifFalse:[
-                aOneArgBlock value:something
-            ]
-        ]
+    self withinTransaction:aType objects:something do:[
+        self forEach:something do:aOneArgBlock
     ]
 !
 
-transactionTextFor:anElementOrCollection
-    "returns text used by transaction or nil
+withinTransaction:aType objects:objects do:aNoneArgBlock
+    "evaluate a block with no arguments within a transaction
     "
-    |props size|
+    |text size prop|
+
+    objects isNil ifTrue:[ ^ self ].
+
+    size := objects size.
 
-    anElementOrCollection notNil ifTrue:[
-        anElementOrCollection isCollection ifTrue:[
-            size := anElementOrCollection size.
-            size == 0 ifTrue:[^ nil].
-            size ~~ 1 ifTrue:[^ size printString, ' elements'].
+    objects isCollection ifTrue:[
+        size == 0 ifTrue:[ ^ self ].
+        size == 1 ifTrue:[ prop := self propertyOfView:(objects first) ]
+    ] ifFalse:[
+        prop := self propertyOfView:objects
+    ].
 
-            props := self propertyOfView:(anElementOrCollection at:1).
-        ] ifFalse:[
-            props := self propertyOfView:anElementOrCollection
-        ].
-        props notNil ifTrue:[ ^ props name ]
+    prop notNil ifTrue:[
+        text := prop name
+    ] ifFalse:[
+        text := size printString, ' elements'
     ].
-    ^ nil
+
+    undoHistory withinTransaction:aType text:text do:[
+        aNoneArgBlock value
+    ]
 ! !
 
 !UIPainterView methodsFor:'undo actions'!
 
-undoCreate:aViewId
-    "undo method when creating or pasting an object
-    "
-    undoHistory addUndoBlock:[
-        self remove:(self findViewWithId:aViewId)
-    ]
-
-!
-
-undoLayout:aViewId
-    "undo method when changing the layout (position or dimension)
+createUndoLayout:aView
+    "create undo action before changing a views layout
     "
-    |view layout extent|
-
-    (view := self findViewWithId:aViewId) notNil ifTrue:[
-        (layout := view geometryLayout copy) isNil ifTrue:[
-            extent := view extent copy
-        ].
-        undoHistory addUndoBlock:[
-            (view := self findViewWithId:aViewId) notNil ifTrue:[
-                layout notNil ifTrue:[view geometryLayout:layout]
-                             ifFalse:[view extent:extent]
-            ]
-        ]
-    ].
-    view := nil
-!
-
-undoLayoutView:aView
-    "undo method for changing layout on a view
-    "
-    |prop|
+    |lyt args prop|
 
     undoHistory isTransactionOpen ifTrue:[
         prop := self propertyOfView:aView.
+
         prop notNil ifTrue:[
-            self undoLayout:(prop identifier)
+            args := Array new:3.
+            args at:1 put:(prop identifier).
+
+            (lyt := aView geometryLayout) notNil ifTrue:[
+                args at:2 put:#geometryLayout:
+            ] ifFalse:[
+                lyt extent.
+                args at:2 put:#extent:
+            ].
+            args at:3 put:(lyt copy).
+            undoHistory addUndoSelector:#undoLayout: withArgs:args.
         ]
     ]
 !
 
-undoRemove:aViewId
-    "undo method when removing an object
+createUndoRemove:aView
+    "create undo method before deleting views
     "
-    |frame prop spec parentId|
+    |frame prop pId spec|
+
+    (prop := self propertyOfView:aView) notNil ifTrue:[
+        spec  := self fullSpecFor:aView.
+        frame := aView superView.
 
-    frame := self findViewWithId:aViewId.
-    spec  := self fullSpecFor:frame.
-    frame := frame superView.
+        (self canPasteInto:frame) ifTrue:[
+            (frame := self propertyOfView:frame) notNil ifTrue:[
+                pId := frame identifier
+            ]
+        ].
+        undoHistory addUndoSelector:#undoRemove:
+                           withArgs:(Array with:spec with:(prop identifier) with:pId)
+    ]
+!
 
-    (self canPasteInto:frame) ifTrue:[
-        (prop := self propertyOfView:frame) notNil ifTrue:[
-            parentId := prop identifier
-        ]
-    ].
-    frame := nil.
-    prop  := nil.
+createUndoSpecModify:aProp
+    "undo method when changing the specification for an object
+    "
+    aProp notNil ifTrue:[
+        undoHistory addUndoSelector:#undoSpecModify:
+                           withArgs:(Array with:(aProp spec) with:(aProp identifier))
+    ]
+!
 
-    undoHistory addUndoBlock:[
-        |view|
+undoCreate:something
+    "undo method for creating or pasting an object
+    "
+    self forEach:something do:[:anId|self remove:(self findViewWithId:anId)].
+!
 
-        frame := self findViewWithId:parentId.
-        frame isNil ifTrue:[
-            frame := self
-        ].
-        view := self addSpec:spec builder:(UIBuilder new) in:frame.
-        view realize.
-        inputView raise.
+undoLayout:args
+    "undo method to set the old layout; see 'createUndoLayout:'
+    "
+    |view|
+
+    (view := self findViewWithId:(args at:1)) notNil ifTrue:[
+        view perform:(args at:2) with:(args at:3)
     ]
 !
 
-undoSpecModify:aViewId
-    "undo method when changing the specification for an object
+undoRemove:args
+    "undo method when removing an object; see 'createUndoRemove:'
+    "
+    |frame prop view|
+
+    (args at:3) notNil ifTrue:[
+        frame := self findViewWithId:(args at:3).
+    ].
+    frame isNil ifTrue:[
+        frame := self
+    ].
+    view := self addSpec:(args at:1) builder:(UIBuilder new) in:frame.
+    view realize.
+    inputView raise.
+
+    prop := self propertyOfView:view.
+    prop identifier:(args at:2).
+
+!
+
+undoSpecModify:args
+    "undo method when changing a spec; see 'createUndoSpecModify:'
     "
     |builder view spec v props|
 
-    (view := self findViewWithId:aViewId) notNil ifTrue:[
-        spec := self specFor:view.
-        view := nil.
+    props := self propertyOfIdentifier:(args at:2).
 
-        undoHistory addUndoBlock:[
-            props := self propertyOfIdentifier:aViewId.
-            props notNil ifTrue:[
-                view    := props view.
-                builder := UIBuilder new.
-                props spec:spec.
+    props notNil ifTrue:[
+        view    := props view.
+        spec    := args at:1.
+        builder := UIBuilder new.
+        props spec:spec.
 
-                spec needsRebuildForAttributes ifTrue:[
-                    v := spec buildViewWithLayoutFor:builder in:view superView.
-                    v realize.    
-                    view destroy.
-                    view become:v
-                ] ifFalse:[
-                    spec setAttributesIn:view with:builder.
-                    self elementChangedSize:view.
-                ].
-                listHolder propertyChanged:props.
-            ]
-        ]
-    ].
+        spec needsRebuildForAttributes ifTrue:[
+            v := spec buildViewWithLayoutFor:builder in:view superView.
+            v realize.    
+            view destroy.
+            view become:v
+        ] ifFalse:[
+            spec setAttributesIn:view with:builder.
+            self elementChangedSize:view.
+        ].
+        listHolder propertyChanged:props.
+    ] ifFalse:[
+        self halt
+    ]
 
 
 
@@ -1643,6 +1663,13 @@
     ^ identifier
 !
 
+identifier:anIdentifier
+    "set the unique identifier assigned to property; called after an restore of
+     a deleted instance
+    "
+    identifier := anIdentifier
+!
+
 spec
     "return the value of the instance variable 'spec' (automatically generated)"