many redraw changes to avoid flicker when resizing or moving
authorClaus Gittinger <cg@exept.de>
Mon, 18 May 2009 15:28:09 +0200
changeset 2536 408cba0cbef4
parent 2535 961e4b080571
child 2537 12e3b32befe4
many redraw changes to avoid flicker when resizing or moving
UIObjectView.st
--- a/UIObjectView.st	Mon May 18 13:57:41 2009 +0200
+++ b/UIObjectView.st	Mon May 18 15:28:09 2009 +0200
@@ -28,7 +28,7 @@
 !
 
 Object subclass:#ResizeData
-	instanceVariableNames:'object selector delta'
+	instanceVariableNames:'object selector checkForChangeSelector delta'
 	classVariableNames:''
 	poolDictionaries:''
 	privateIn:UIObjectView
@@ -698,30 +698,33 @@
 invertOutlineOf:something
     "invert outline of an object or collection of objects"
 
-    |wasClipped|
-
-^ self.
-    (wasClipped := clipChildren) ifTrue:[
-        self clippedByChildren:(clipChildren := false).
-    ].
-
-    self xoring:[
-        |p|
-
-        something isCollection ifTrue:[
-            something do:[:v |
-                p := v originRelativeTo:self.
-                self displayRectangle:(p extent:v extent).
-            ].
-        ] ifFalse:[
-            p := something originRelativeTo:self.
-            self displayRectangle:(p extent:something extent).
-        ]
-    ].
-
-    wasClipped ifTrue:[
-        self clippedByChildren:(clipChildren := true).
-    ].
+    ^ self.
+
+"/ cg: nope - all done via handles now.
+
+"/    |wasClipped|
+"/
+"/    (wasClipped := clipChildren) ifTrue:[
+"/        self clippedByChildren:(clipChildren := false).
+"/    ].
+"/
+"/    self xoring:[
+"/        |p|
+"/
+"/        something isCollection ifTrue:[
+"/            something do:[:v |
+"/                p := v originRelativeTo:self.
+"/                self displayRectangle:(p extent:v extent).
+"/            ].
+"/        ] ifFalse:[
+"/            p := something originRelativeTo:self.
+"/            self displayRectangle:(p extent:something extent).
+"/        ]
+"/    ].
+"/
+"/    wasClipped ifTrue:[
+"/        self clippedByChildren:(clipChildren := true).
+"/    ].
 !
 
 minClosedViewSetFor:setOfViews
@@ -765,20 +768,32 @@
 !UIObjectView methodsFor:'object moving'!
 
 doObjectMove:aPoint
-    "move movedOject (which is a misnomer - its actually a collection of objects to move)"
-
-    movedObject notNil ifTrue:[
-        self hideSelection.
-
-        self invertOutlineOf:movedObject.
-
-        movedObject keysAndValuesDo:[:i :v|
-            self moveObject:v to:(aPoint - (moveDelta at:i)).
-        ].
-        self invertOutlineOf:movedObject.
-
-        self showSelection.
-    ]
+    "move movedOject (which is a misnomer - it's actually a collection of objects to move)"
+
+    |anyMove|
+
+    movedObject isEmptyOrNil ifTrue:[^ self].
+
+    anyMove := false.
+    "/ to avoid flicker, check if this really involves a move (due to align)
+    movedObject keysAndValuesDo:[:i :obj|
+        |newOrigin delta|
+
+        newOrigin := (aPoint - (moveDelta at:i)).
+        delta := (self alignToGrid:newOrigin) - obj computeOrigin.
+        delta ~= (0@0) ifTrue:[ anyMove := true ].
+    ].
+    anyMove ifFalse:[^ self ].
+
+    self hideSelection.
+    self invertOutlineOf:movedObject.
+
+    movedObject keysAndValuesDo:[:i :v|
+        self moveObject:v to:(aPoint - (moveDelta at:i)).
+    ].
+
+    self invertOutlineOf:movedObject.
+    self showSelection.
 !
 
 endObjectMove
@@ -793,22 +808,22 @@
                          ifFalse:[ newSel := movedObject ].
     movedObject := nil.
 
-    self withSelectionHiddenDo:[
-        self setSelection:newSel withRedraw:false.
-
-        components notEmptyOrNil ifTrue:[
-            self invalidate.
-        ].
-        self allSubViewsDo:[:v|
-            v shown ifTrue:[
-                v fill:v viewBackground.
-                v exposeX:0 y:0 width:v width height:v height.
-            ].
-        ].
-
-        self setDefaultActions.
-        self layoutChanged.
-    ].
+"/    self withSelectionHiddenDo:[
+"/        self setSelection:newSel withRedraw:false.
+"/
+"/        components notEmptyOrNil ifTrue:[
+"/            self invalidate.
+"/        ].
+"/        self allSubViewsDo:[:v|
+"/            v shown ifTrue:[
+"/                v fill:v viewBackground.
+"/                v exposeX:0 y:0 width:v width height:v height.
+"/            ].
+"/        ].
+"/    ].
+
+    self setDefaultActions.
+    self layoutChanged.
 !
 
 moveObject:anObject to:aPoint
@@ -956,15 +971,15 @@
 !UIObjectView methodsFor:'object resize'!
 
 actionResize:anObject selector:aSelector
-    "create and initialize action for resize
-    "
-    |selector delta|
+    "create and initialize action for resize"
+
+    |delta|
 
     delta    := anObject container originRelativeTo:self.
-    selector := ('resize:', aSelector, ':') asSymbol.
-
     resizeData := ResizeData new
-		      object:anObject selector:selector delta:delta.
+                        object:anObject 
+                        selector:aSelector
+                        delta:delta.
 
 "can change cursor dependent on vertical/horizontal resizing
 "
@@ -975,18 +990,23 @@
 !
 
 doDragResize:aPoint
-    "do a widget resize drag
-    "
+    "do a widget resize drag"
+
     |p object|
 
     object := resizeData object.
+    p := (self alignToGrid:aPoint) - (resizeData delta).
+
+    (self resize:object handle:(resizeData selector) to:p check:true) ifFalse:[
+        ^ self  "/ no real change (due to align)
+    ].
 
     self hideSelection.
 
     self invertOutlineOf:object.
-    p := (self alignToGrid:aPoint) - (resizeData delta).
-
-    self perform:(resizeData selector) with:object with:p.
+
+    self resize:object handle:(resizeData selector) to:p check:false.
+
     Delay waitForSeconds:0.05.
     [self sensor hasExposeEventFor:nil] whileTrue:[
         self windowGroup processExposeEvents
@@ -999,45 +1019,246 @@
 !
 
 endResize
-    "cleanup after object resize
-    "
-    |object savedSelection|
+    "cleanup after object resize"
+
+    |object savedSelection anyLayoutWrapper anyTransparentBox|
 
     object := resizeData object.
     resizeData := nil.
 
-    self invertOutlineOf:object.
-
-    "/ temporarily hide the selection, in order to allow the container to move the
-    "/ element around...
-    savedSelection := selection.
-    self selection:nil.
-    "/ handle any expose events (for subcomponents) before
-    "/ redrawing the handles.
-    self windowGroup processExposeEvents.
-
+    "/ container objects might want to rearrange their elements after a size change;
+    "/ therefore, we hide the handles while this is possibly done.
+    "/ however, to avoid flicker, we check for containers first.
+    anyLayoutWrapper := anyTransparentBox := false.
+    self forEach:object do:[:aViewOrComponent | 
+        aViewOrComponent isLayoutWrapper ifTrue:[ anyLayoutWrapper := true ].
+        aViewOrComponent isTransparentBox ifTrue:[ anyTransparentBox := true ].
+    ].
+
+    (anyLayoutWrapper or:[anyTransparentBox]) ifTrue:[
+
+        self invertOutlineOf:object.
+
+        "/ temporarily hide the selection, in order to allow the container to move the
+        "/ element around...
+        savedSelection := selection.
+        self setSelection:nil withRedraw:true.
+
+        "/ handle any expose events (for subcomponents) before
+        "/ redrawing the handles.
+        self windowGroup processExposeEvents.
+
+        self elementChangedSize:object.
+
+        "/ handle any expose events (for subcomponents) before
+        "/ redrawing the handles.
+        Delay waitForSeconds:0.05.
+        [self sensor hasExposeEventFor:nil] whileTrue:[
+            self windowGroup processExposeEvents
+        ].
+
+        self forEach:savedSelection do:[:aView |
+            self recomputeShapeIfTransparentBox:aView.
+        ].
+
+        self setSelection:object withRedraw:true.
+    ].
+
+    self layoutChanged.
     self setDefaultActions.
-    self elementChangedSize:object.
-
-    "/ handle any expose events (for subcomponents) before
-    "/ redrawing the handles.
-    Delay waitForSeconds:0.05.
-    [self sensor hasExposeEventFor:nil] whileTrue:[
-        self windowGroup processExposeEvents
-    ].
-
-    self forEach:savedSelection do:[:aView |
-        self recomputeShapeIfTransparentBox:aView.
-    ].
-    self layoutChanged.
-
-    self selection:savedSelection.
-    self setSelection:object withRedraw:true.
 !
 
 layoutChanged
 !
 
+resize:aView bottom:aPoint
+    "obsolete: resize a views bottom"
+
+    self resize:aView handle:#bottom to:aPoint check:false.
+"/    undoHistory withoutTransactionDo:[
+"/        self shiftLayout:aView top:0 bottom:((aPoint y) - (aView computeCorner y))
+"/    ].
+!
+
+resize:aView bottomLeft:aPoint
+    "obsolete: resize a views bottom and left"
+
+    self resize:aView handle:#bottomLeft to:aPoint check:false.
+"/    undoHistory withoutTransactionDo:[
+"/        self shiftLayout:aView top:0
+"/                            bottom:((aPoint y) - (aView computeCorner y))
+"/                              left:((aPoint x) - (aView computeOrigin x))
+"/                             right:0
+"/
+"/    ]
+!
+
+resize:aView corner:aPoint
+    "obsolete: resize a views corner"
+
+    self resize:aView handle:#corner to:aPoint check:false.
+"/    |delta|
+"/
+"/    delta := aPoint - aView computeCorner.
+"/    undoHistory withoutTransactionDo:[
+"/        self shiftLayout:aView top:0 bottom:(delta y) left:0 right:(delta x)
+"/    ]
+!
+
+resize:aComponent endPoint:newEndPoint
+    "obsolete: move a component's endPoint"
+
+    self resize:aComponent handle:#endPoint to:newEndPoint check:false
+
+"/    undoHistory 
+"/        withoutTransactionDo:[
+"/            self shiftLayout:aComponent startPoint:0 endPoint:(newEndPoint - (aComponent endPoint))
+"/        ]
+!
+
+resize:aComponent handle:aSymbol to:aPoint check:doCheck
+    "resize a views handle - if doCheck is true, only check if the handle would change
+     (used to avoid flicker, when an aligned move would actually not move anything)"
+
+    |newX newY oldBottom oldTop oldLeft oldRight 
+     oldOrigin oldCorner shiftTop shiftBottom shiftLeft shiftRight|
+
+    aSymbol == #startPoint ifTrue:[
+        doCheck ifTrue:[
+            ^ aPoint ~= (aComponent startPoint)
+        ].
+        self 
+            shiftLayout:aComponent 
+            startPoint:(aPoint - (aComponent startPoint)) endPoint:0.
+        ^ self.
+    ].
+    aSymbol == #endPoint ifTrue:[
+        doCheck ifTrue:[
+            ^ aPoint ~= (aComponent endPoint)
+        ].
+        self 
+            shiftLayout:aComponent 
+            startPoint:0 endPoint:(aPoint - (aComponent endPoint)).
+        ^ self.
+    ].
+
+    newX := aPoint x.
+    newY := aPoint y.
+    shiftTop := shiftBottom := shiftLeft := shiftRight := 0.
+
+    oldOrigin := aComponent computeOrigin.
+    oldCorner := aComponent computeCorner.
+
+    oldTop := oldOrigin y.
+    oldBottom := oldCorner y.
+    oldLeft := oldOrigin x.
+    oldRight := oldCorner x.
+
+    aSymbol == #bottom ifTrue:[
+        shiftBottom := newY - oldBottom.
+    ]. 
+    aSymbol == #top ifTrue:[     
+        shiftTop := newY - oldTop.
+    ].
+    aSymbol == #left ifTrue:[
+        shiftLeft := newX - oldLeft.
+    ].
+    aSymbol == #right ifTrue:[
+        shiftRight := newX - oldRight.
+    ].
+    aSymbol == #origin ifTrue:[
+        shiftLeft := newX - oldLeft.
+        shiftTop := newY - oldTop.
+    ].
+    aSymbol == #topRight ifTrue:[
+        shiftRight := newX - oldRight.
+        shiftTop := newY - oldTop.
+    ].
+    aSymbol == #corner ifTrue:[
+        shiftRight := newX - oldRight.
+        shiftBottom := newY - oldBottom.
+    ].
+    aSymbol == #bottomLeft ifTrue:[
+        shiftLeft := newX - oldLeft.
+        shiftBottom := newY - oldBottom.
+    ].
+
+    doCheck ifTrue:[
+        ^ (shiftTop ~= 0) or:[ shiftBottom ~= 0 or:[ shiftLeft ~= 0 or:[ shiftRight ~= 0 ]]]
+    ].
+
+    undoHistory withoutTransactionDo:[
+        self 
+            shiftLayout:aComponent 
+            top:shiftTop bottom:shiftBottom 
+            left:shiftLeft right:shiftRight
+    ].
+!
+
+resize:aView left:aPoint
+    "obsolete: resize a views left"
+
+    self resize:aView handle:#left to:aPoint check:false.
+"/    undoHistory withoutTransactionDo:[
+"/        self shiftLayout:aView left:((aPoint x) - (aView computeOrigin x)) right:0
+"/    ]
+!
+
+resize:aView origin:aPoint
+    "obsolete: resize a views origin"
+
+    self resize:aView handle:#origin to:aPoint check:false.
+"/    |delta|
+"/
+"/    delta := aPoint - aView computeOrigin.
+"/    undoHistory withoutTransactionDo:[
+"/        self shiftLayout:aView top:(delta y) bottom:0 left:(delta x) right:0
+"/    ]
+!
+
+resize:aView right:aPoint
+    "obsolete: resize a views right"
+
+    self resize:aView handle:#right to:aPoint check:false.
+"/    undoHistory withoutTransactionDo:[
+"/        self shiftLayout:aView left:0 right:((aPoint x) - (aView computeCorner x))
+"/    ]
+!
+
+resize:aComponent startPoint:newStartPoint
+    "obsolete: move a component's startPoint"
+
+    self resize:aComponent handle:#startPoint to:newStartPoint check:false
+"/    undoHistory 
+"/        withoutTransactionDo:[
+"/            self shiftLayout:aComponent startPoint:(newStartPoint - (aComponent startPoint)) endPoint:0
+"/        ]
+!
+
+resize:aView top:aPoint
+    "obsolete: resize a views top"
+
+    self resize:aView handle:#top to:aPoint check:false.
+"/    undoHistory withoutTransactionDo:[
+"/        self shiftLayout:aView 
+"/                top:((aPoint y) - (aView computeOrigin y)) 
+"/                bottom:0
+"/    ]
+!
+
+resize:aView topRight:aPoint
+    "obsolete: resize a views top and right"
+
+    self resize:aView handle:#topRight to:aPoint check:false.
+"/    undoHistory withoutTransactionDo:[
+"/        self shiftLayout:aView 
+"/                top:((aPoint y) - (aView computeOrigin y))
+"/                bottom:0
+"/                left:0
+"/                right:((aPoint x) - (aView computeCorner x))
+"/    ]
+!
+
 startResizeBorder:borderHandleSelector
     "start resizing the selected view at the given borderHandle"
 
@@ -1099,107 +1320,6 @@
         aView computeShape.
         aView clear; redraw
     ].
-!
-
-resize:aView bottom:aPoint
-    "resize a views bottom"
-
-    undoHistory withoutTransactionDo:[
-        self shiftLayout:aView top:0 bottom:((aPoint y) - (aView computeCorner y))
-    ].
-!
-
-resize:aView bottomLeft:aPoint
-    "resize a views bottom and left"
-
-    undoHistory withoutTransactionDo:[
-        self shiftLayout:aView top:0
-                            bottom:((aPoint y) - (aView computeCorner y))
-                              left:((aPoint x) - (aView computeOrigin x))
-                             right:0
-
-    ]
-!
-
-resize:aView corner:aPoint
-    "resize a views corner"
-
-    |delta|
-
-    delta := aPoint - aView computeCorner.
-
-    undoHistory withoutTransactionDo:[
-        self shiftLayout:aView top:0 bottom:(delta y) left:0 right:(delta x)
-    ]
-!
-
-resize:aComponent endPoint:newEndPoint
-    "move a component's endPoint"
-
-    undoHistory 
-        withoutTransactionDo:[
-            self shiftLayout:aComponent startPoint:0 endPoint:(newEndPoint - (aComponent endPoint))
-        ]
-!
-
-resize:aView left:aPoint
-    "resize a views left"
-
-    undoHistory withoutTransactionDo:[
-        self shiftLayout:aView left:((aPoint x) - (aView computeOrigin x)) right:0
-    ]
-!
-
-resize:aView origin:aPoint
-    "resize a views origin"
-
-    |delta|
-
-    delta := aPoint - aView computeOrigin.
-
-    undoHistory withoutTransactionDo:[
-        self shiftLayout:aView top:(delta y) bottom:0 left:(delta x) right:0
-    ]
-!
-
-resize:aView right:aPoint
-    "resize a views right"
-
-    undoHistory withoutTransactionDo:[
-        self shiftLayout:aView left:0 right:((aPoint x) - (aView computeCorner x))
-    ]
-!
-
-resize:aComponent startPoint:newStartPoint
-    "move a component's startPoint"
-
-    undoHistory 
-        withoutTransactionDo:[
-            self shiftLayout:aComponent startPoint:(newStartPoint - (aComponent startPoint)) endPoint:0
-        ]
-!
-
-resize:aView top:aPoint
-    "resize a views top"
-
-    undoHistory withoutTransactionDo:[
-        self shiftLayout:aView 
-                top:((aPoint y) - (aView computeOrigin y)) 
-                bottom:0
-    ]
-!
-
-resize:aView topRight:aPoint
-    "resize a views top and right"
-
-    undoHistory withoutTransactionDo:[
-        self shiftLayout:aView 
-                top:((aPoint y) - (aView computeOrigin y))
-                bottom:0
-                left:0
-                right:((aPoint x) - (aView computeCorner x))
-
-    ]
 ! !
 
 !UIObjectView methodsFor:'private-shift layout'!
@@ -1244,41 +1364,41 @@
 shiftLayout:aView top:t bottom:b left:l right:r
     "shift layout for a view; in case of an open transaction, the undo action is registered"
 
-    |type layout oldExt|
+    |type layout oldExt dX dY|
 
     type := self class layoutType:aView.
-
-    type notNil ifTrue:[
-        self createUndoLayout:aView.
-
-        type == #Extent ifTrue:[
-            oldExt := aView extent.
-            aView extent:(oldExt + ((r-l) @ (b-t))).
-            ^ self 
-        ].
-
-        layout := aView geometryLayout copy.
-
-        layout isLayout ifTrue:[
-            layout leftOffset:(layout leftOffset + l)
-                    topOffset:(layout topOffset  + t).
-                    
-            type == #LayoutFrame ifTrue:[
-                layout bottomOffset:(layout bottomOffset + b).
-                layout  rightOffset:(layout rightOffset  + r).
-            ]
-        ] ifFalse:[
-            type == #Rectangle ifTrue:[
-                layout left:(layout left   + l)
-                      right:(layout right  + r)
-                        top:(layout top    + t)
-                     bottom:(layout bottom + b).
-            ] ifFalse:[     "POINT"
-                layout x:(layout x + l) y:(layout y + t).
-            ]
-        ].
-        aView geometryLayout:layout
-    ]
+    type isNil ifTrue:[ ^ self ].
+
+    self createUndoLayout:aView.
+
+    type == #Extent ifTrue:[
+        oldExt := aView extent.
+        dX := r-l.
+        dY := b-t.
+        aView extent:(oldExt + (dX @ dY)).
+        ^ self 
+    ].
+
+    layout := aView geometryLayout copy.
+    layout isLayout ifTrue:[
+        layout leftOffset:(layout leftOffset + l)
+                topOffset:(layout topOffset  + t).
+                
+        type == #LayoutFrame ifTrue:[
+            layout bottomOffset:(layout bottomOffset + b).
+            layout rightOffset:(layout rightOffset  + r).
+        ]
+    ] ifFalse:[
+        type == #Rectangle ifTrue:[
+            layout left:(layout left   + l)
+                  right:(layout right  + r)
+                    top:(layout top    + t)
+                 bottom:(layout bottom + b).
+        ] ifFalse:[     "POINT"
+            layout x:(layout x + l) y:(layout y + t).
+        ]
+    ].
+    aView geometryLayout:layout
 !
 
 shiftLayout:aViewOrComponent vertical:n
@@ -2690,6 +2810,10 @@
 
 !UIObjectView::ResizeData methodsFor:'accessing'!
 
+checkForChangeSelector
+    ^ checkForChangeSelector
+!
+
 delta
     ^ delta
 
@@ -2702,6 +2826,15 @@
     "Created: / 2.2.1998 / 13:40:24 / cg"
 !
 
+object:anObject selector:selectorArg checkForChangeSelector:checkForChangeSelectorArg delta:anInteger
+    object := anObject.
+    selector := selectorArg.
+    checkForChangeSelector := checkForChangeSelectorArg.
+    delta := anInteger.
+
+    "Created: / 2.2.1998 / 13:39:22 / cg"
+!
+
 object:anObject selector:aSymbol delta:anInteger
     object := anObject.
     selector := aSymbol.