SimpleView.st
changeset 7728 00826284cb7d
parent 7713 5e4be080979a
child 7729 0f3e3a39bc44
--- a/SimpleView.st	Mon Nov 28 21:29:59 2016 +0100
+++ b/SimpleView.st	Wed Dec 07 14:51:45 2016 +0100
@@ -5871,7 +5871,8 @@
     "my size has changed by window manager action"
 
     |how anyEdge mustRedrawBottomEdge mustRedrawRightEdge
-     mustRedrawPreviousRightBorderArea mustRedrawPreviousBottomBorderArea p originChanged|
+     mustRedrawPreviousRightBorderArea mustRedrawPreviousBottomBorderArea p originChanged
+     oldWidth oldHeight|
 
     originChanged := (left ~= x) or:[top ~= y].
 
@@ -5880,88 +5881,82 @@
 
     (superView isNil
     and:[self drawableId notNil]) ifTrue:[
-	"/ have to be careful - some window managers (motif) wrap another
-	"/ view around and the reported origin is relative to that.
-	"/ not relative to the screen.
-	p := device translatePoint:0@0 fromView:self toView:nil.
-	p := p + self borderWidth.
-	left := p x.
-	top := p y.
+        "/ have to be careful - some window managers (motif) wrap another
+        "/ view around and the reported origin is relative to that.
+        "/ not relative to the screen.
+        p := device translatePoint:0@0 fromView:self toView:nil.
+        p := p + self borderWidth.
+        left := p x.
+        top := p y.
     ].
 
     ((width ~~ newWidth) or:[height ~~ newHeight]) ifTrue:[
-	realized ifFalse:[
-	    width := newWidth.
-	    height := newHeight.
-	    self extentChangedFlag:true.
-	    ^ self
-	].
-
-	((newWidth <= width) and:[newHeight <= height]) ifTrue:[
-	    how := #smaller
-	] ifFalse:[
-	    ((newWidth >= width) and:[newHeight >= height]) ifTrue:[
-		how := #larger
-	    ]
-	].
-
-	margin ~~ 0 ifTrue:[
-	    mustRedrawBottomEdge := newHeight < height.
-	    mustRedrawRightEdge := newWidth < width.
-	    anyEdge := mustRedrawBottomEdge or:[mustRedrawRightEdge].
-
-	    mustRedrawPreviousRightBorderArea := newWidth > width.
-	    mustRedrawPreviousBottomBorderArea := newHeight > height.
-	] ifFalse:[
-	    anyEdge := mustRedrawPreviousRightBorderArea := mustRedrawPreviousBottomBorderArea := false
-	].
-
-	mustRedrawPreviousRightBorderArea ifTrue:[
-	    self invalidateDeviceRectangle:((width-margin)@0 extent:margin@height) repairNow:false.
-	].
-	mustRedrawPreviousBottomBorderArea ifTrue:[
-	    self invalidateDeviceRectangle:((0 @ (height-margin)) extent:width@margin) repairNow:false.
-	].
-
-	width := newWidth.
-	height := newHeight.
-
-	"recompute inner-clip if needed"
-	self setInnerClip.
-
-	"
-	 must first process pending exposes;
-	 otherwise, those may be drawn at a wrong position
-	"
-"/ claus: no; expose events are in the same queue as configure events;
-"/        which is exactly for that reason ...
-
-"/        windowGroup notNil ifTrue:[
-"/            windowGroup processExposeEvents
-"/        ].
-	self sizeChanged:how.
-
-	(anyEdge and:[shown]) ifTrue:[
-	    mustRedrawBottomEdge ifTrue:[
-		self invalidateDeviceRectangle:((0 @ (height-margin)) extent:width@margin) repairNow:false.
-	    ].
-	    mustRedrawRightEdge ifTrue:[
-		self invalidateDeviceRectangle:((width-margin)@0 extent:margin@height) repairNow:false.
-	    ].
-"/ OLD code:
-"/            self clippingRectangle:nil.
-"/            mustRedrawBottomEdge ifTrue:[
-"/                self drawBottomEdge
-"/            ].
-"/            mustRedrawRightEdge ifTrue:[
-"/                self drawRightEdge
-"/            ].
-"/            self deviceClippingRectangle:innerClipRect
-	]
+        realized ifFalse:[
+            width := newWidth.
+            height := newHeight.
+            self extentChangedFlag:true.
+            ^ self
+        ].
+
+        ((newWidth <= width) and:[newHeight <= height]) ifTrue:[
+            how := #smaller
+        ] ifFalse:[
+            ((newWidth >= width) and:[newHeight >= height]) ifTrue:[
+                how := #larger
+            ]
+        ].
+
+        margin ~~ 0 ifTrue:[
+            mustRedrawBottomEdge := newHeight < height.
+            mustRedrawRightEdge := newWidth < width.
+            anyEdge := mustRedrawBottomEdge or:[mustRedrawRightEdge].
+
+            mustRedrawPreviousRightBorderArea := newWidth > width.
+            mustRedrawPreviousBottomBorderArea := newHeight > height.
+        ] ifFalse:[
+            anyEdge := mustRedrawPreviousRightBorderArea := mustRedrawPreviousBottomBorderArea := false
+        ].
+
+        mustRedrawPreviousRightBorderArea ifTrue:[
+            self invalidateDeviceRectangle:((width-margin)@0 extent:margin@height) repairNow:false.
+        ].
+        mustRedrawPreviousBottomBorderArea ifTrue:[
+            self invalidateDeviceRectangle:((0 @ (height-margin)) extent:width@margin) repairNow:false.
+        ].
+
+        oldWidth := width.
+        oldHeight := height.
+        
+        width := newWidth.
+        height := newHeight.
+
+        "recompute inner-clip if needed"
+        self setInnerClip.
+
+        "
+         must first process pending exposes;
+         otherwise, those may be drawn at a wrong position
+        "
+        "/ claus: no; expose events are in the same queue as configure events;
+        "/        which is exactly for that reason ...
+
+        "/        windowGroup notNil ifTrue:[
+        "/            windowGroup processExposeEvents
+        "/        ].
+        self sizeChanged:how from:(oldWidth@oldHeight).
+
+        (anyEdge and:[shown]) ifTrue:[
+            mustRedrawBottomEdge ifTrue:[
+                self invalidateDeviceRectangle:((0 @ (height-margin)) extent:width@margin) repairNow:false.
+            ].
+            mustRedrawRightEdge ifTrue:[
+                self invalidateDeviceRectangle:((width-margin)@0 extent:margin@height) repairNow:false.
+            ].
+        ]
     ].
 
     originChanged ifTrue:[
-	dependents notNil ifTrue:[ self changed:#origin ].
+        dependents notNil ifTrue:[ self changed:#origin ].
     ].
 
     "Modified: / 10.10.2001 / 14:14:19 / cg"
@@ -6669,6 +6664,23 @@
     "Modified: / 2.4.1998 / 13:59:59 / cg"
 !
 
+sizeChanged:how from:oldExtent
+    "tell subviews that I changed size.
+     How is either #smaller, #larger or nil, and is used to control the order,
+     in which subviews are notified (possibly reducing redraw activity).
+
+     In previous versions, there was only one argument, how,
+     which was either #smaller or #larger or nil (if not known).
+     This argument was used in some widgets to optimize (avoid) some recomputations.
+     However, it was too unspecific on which dimension changed;
+     therefore, now this method is called.
+     For backward compatibility, it calls the old sizeChanged: method.
+     If you redefine this, make sure to call super sizeChanged:, not super sizeChanged:from:,
+     to avoid an endless recursion."
+     
+    self sizeChanged:how
+!
+
 subViewChangedSize
     "some subview has changed its size; we are not interested
      in that here, but some geometry managers redefine this, to reorganize
@@ -8638,16 +8650,16 @@
      a dimension <= 0 ... (although I think that 0 makes sense ...)
     "
     newWidth < 1 ifTrue:[
-	newWidth := 1.
+        newWidth := 1.
     ].
     newHeight < 1 ifTrue:[
-	newHeight := 1
+        newHeight := 1
     ].
 
     ((newWidth == width) and:[newHeight == height]) ifTrue:[
-	sameOrigin ifTrue:[^ self].
-	dependents notNil ifTrue:[ self changed:#origin ].
-	^ self pixelOrigin:origin
+        sameOrigin ifTrue:[^ self].
+        dependents notNil ifTrue:[ self changed:#origin ].
+        ^ self pixelOrigin:origin
     ].
 
     top := newTop.
@@ -8655,142 +8667,144 @@
 
 "/    shown ifTrue:[                  "4-nov-94 actually correct,"
     self drawableId notNil ifTrue:[        "but theres a bug in menus when resized while hidden"
-	mustRedrawBottomEdge := (margin ~~ 0) and:[newHeight < height].
-	mustRedrawRightEdge := (margin ~~ 0) and:[newWidth < width].
-
-	((newHeight <= height) and:[newWidth <= width]) ifTrue:[
-	    how := #smaller
-	] ifFalse:[
-	    ((newHeight >= height) and:[newWidth >= width]) ifTrue:[
-		how := #larger
-	    ]
-	].
-
-	mustRepaintRight := false.
-	mustRepaintBottom := false.
-
-	oldWidth := width.
-	oldHeight := height.
-
-	shown ifTrue:[
-	    (margin ~~ 0) ifTrue:[
-		"clear the old edges"
-
-		oldPaint := nil.
-		newWidth > width ifTrue:[
-		    self clippingBounds:nil.
-		    oldPaint := self paint.
-		    self paint:viewBackground.
-		    self fillDeviceRectangleX:(width - margin)
-					    y:0
-					width:margin
-				       height:height.
-		    mustRepaintRight := true.
-		].
-		newHeight > height ifTrue:[
-		    self clippingBounds:nil.
-		    oldPaint := self paint.
-		    self paint:viewBackground.
-		    self fillDeviceRectangleX:0
-					    y:(height - margin)
-					width:width
-				       height:margin.
-		    mustRepaintBottom := true.
-		].
-		oldPaint notNil ifTrue:[ self paint:oldPaint. ]
-	    ]
-	].
-
-	width := newWidth.
-	height := newHeight.
-
-	self setInnerClip.
-
-	"if view becomes smaller, send sizeChanged first"
-	true  "(how == #smaller)" ifTrue:[
-	    self sizeChanged:how
-	].
-
-	"have to tell X, when extent of view is changed"
-	sameOrigin ifTrue:[
-	    device resizeWindow:self drawableId width:width height:height.
-	] ifFalse:[
-	    "claus: some xservers seem to do better when resizing
-	     first ...."
+        mustRedrawBottomEdge := (margin ~~ 0) and:[newHeight < height].
+        mustRedrawRightEdge := (margin ~~ 0) and:[newWidth < width].
+
+        ((newHeight <= height) and:[newWidth <= width]) ifTrue:[
+            how := #smaller
+        ] ifFalse:[
+            ((newHeight >= height) and:[newWidth >= width]) ifTrue:[
+                how := #larger
+            ]
+        ].
+
+        mustRepaintRight := false.
+        mustRepaintBottom := false.
+
+        oldWidth := width.
+        oldHeight := height.
+
+        shown ifTrue:[
+            (margin ~~ 0) ifTrue:[
+                "clear the old edges"
+
+                oldPaint := nil.
+                newWidth > width ifTrue:[
+                    self clippingBounds:nil.
+                    oldPaint := self paint.
+                    self paint:viewBackground.
+                    self fillDeviceRectangleX:(width - margin)
+                                            y:0
+                                        width:margin
+                                       height:height.
+                    mustRepaintRight := true.
+                ].
+                newHeight > height ifTrue:[
+                    self clippingBounds:nil.
+                    oldPaint := self paint.
+                    self paint:viewBackground.
+                    self fillDeviceRectangleX:0
+                                            y:(height - margin)
+                                        width:width
+                                       height:margin.
+                    mustRepaintBottom := true.
+                ].
+                oldPaint notNil ifTrue:[ self paint:oldPaint. ]
+            ]
+        ].
+
+        width := newWidth.
+        height := newHeight.
+
+        self setInnerClip.
+
+        "if view becomes smaller, send sizeChanged first"
+        "now always"
+        true  "(how == #smaller)" ifTrue:[
+            self sizeChanged:how from:(oldWidth @ oldHeight)
+        ].
+
+        "have to tell X, when extent of view is changed"
+        sameOrigin ifTrue:[
+            device resizeWindow:self drawableId width:width height:height.
+        ] ifFalse:[
+            "claus: some xservers seem to do better when resizing
+             first ...."
 "
-	    (how == #smaller) ifTrue:[
-		device resizeWindow:drawableId width:width height:height.
-		device moveWindow:drawableId x:left y:top
-	    ] ifFalse:[
-		device moveResizeWindow:drawableId x:left y:top width:width height:height
-	    ].
+            (how == #smaller) ifTrue:[
+                device resizeWindow:drawableId width:width height:height.
+                device moveWindow:drawableId x:left y:top
+            ] ifFalse:[
+                device moveResizeWindow:drawableId x:left y:top width:width height:height
+            ].
 "
-	    device moveResizeWindow:self drawableId x:left y:top
-					   width:width height:height.
-	].
-
-	"if view becomes bigger, send sizeChanged after"
-	false "(how ~~ #smaller)" ifTrue:[
-	    self sizeChanged:how
-	].
-
-	shown ifTrue:[
-	    (mustRedrawBottomEdge or:[mustRedrawRightEdge]) ifTrue:[
-		border notNil ifTrue:[
-		    mustRedrawBottomEdge ifTrue:[
-			self invalidateDeviceRectangle:((0 @ (height - margin)) extent:width@margin) repairNow:false.
-		    ].
-		    mustRedrawRightEdge ifTrue:[
-			self invalidateDeviceRectangle:(((width - margin) @ 0) extent:margin@height) repairNow:false.
-		    ].
-		] ifFalse:[
-		    self deviceClippingBounds:nil.
-		    oldPaint := self paint.
-		    mustRedrawBottomEdge ifTrue:[
-			self drawBottomEdge
-		    ].
-		    mustRedrawRightEdge ifTrue:[
-			self drawRightEdge
-		    ].
-		    self paint:oldPaint.
-		    self deviceClippingBounds:innerClipRect
-		]
-	    ].
-	].
-
-	mustRepaintRight ifTrue:[
-	    self invalidateDeviceRectangle:(((oldWidth - margin) @ 0)
-					   extent:margin@height)
-				 repairNow:false.
+            device moveResizeWindow:self drawableId x:left y:top
+                                           width:width height:height.
+        ].
+
+        "if view becomes bigger, send sizeChanged after"
+        "no longer"
+        false "(how ~~ #smaller)" ifTrue:[
+            self sizeChanged:how from:(oldWidth @ oldHeight)
+        ].
+
+        shown ifTrue:[
+            (mustRedrawBottomEdge or:[mustRedrawRightEdge]) ifTrue:[
+                border notNil ifTrue:[
+                    mustRedrawBottomEdge ifTrue:[
+                        self invalidateDeviceRectangle:((0 @ (height - margin)) extent:width@margin) repairNow:false.
+                    ].
+                    mustRedrawRightEdge ifTrue:[
+                        self invalidateDeviceRectangle:(((width - margin) @ 0) extent:margin@height) repairNow:false.
+                    ].
+                ] ifFalse:[
+                    self deviceClippingBounds:nil.
+                    oldPaint := self paint.
+                    mustRedrawBottomEdge ifTrue:[
+                        self drawBottomEdge
+                    ].
+                    mustRedrawRightEdge ifTrue:[
+                        self drawRightEdge
+                    ].
+                    self paint:oldPaint.
+                    self deviceClippingBounds:innerClipRect
+                ]
+            ].
+        ].
+
+        mustRepaintRight ifTrue:[
+            self invalidateDeviceRectangle:(((oldWidth - margin) @ 0)
+                                           extent:margin@height)
+                                 repairNow:false.
 "/            self redrawDeviceX:(oldWidth - margin)
 "/                             y:0
 "/                         width:margin
 "/                        height:height.
-	].
-	mustRepaintBottom ifTrue:[
-	    self invalidateDeviceRectangle:((0 @ (oldHeight - margin))
-					   extent:width@margin)
-				 repairNow:false.
+        ].
+        mustRepaintBottom ifTrue:[
+            self invalidateDeviceRectangle:((0 @ (oldHeight - margin))
+                                           extent:width@margin)
+                                 repairNow:false.
 "/            self redrawDeviceX:0
 "/                             y:(oldHeight - margin)
 "/                         width:width
 "/                        height:margin.
-	].
+        ].
     ] ifFalse:[
-	"otherwise memorize the need for a sizeChanged message"
-
-	width := newWidth.
-	height := newHeight.
-	sameOrigin ifFalse:[
-	    self originChangedFlag:true.
-	].
-	self extentChangedFlag:true.
-	subViews notEmptyOrNil ifTrue:[
-	    self extentChangedBeforeCreatedFlag:true.
-	].
+        "otherwise memorize the need for a sizeChanged message"
+
+        width := newWidth.
+        height := newHeight.
+        sameOrigin ifFalse:[
+            self originChangedFlag:true.
+        ].
+        self extentChangedFlag:true.
+        subViews notEmptyOrNil ifTrue:[
+            self extentChangedBeforeCreatedFlag:true.
+        ].
     ].
     sameOrigin ifFalse:[
-	dependents notNil ifTrue:[ self changed:#origin ].
+        dependents notNil ifTrue:[ self changed:#origin ].
     ].
 
     "Modified: / 25.5.1999 / 14:49:56 / cg"