SimpleView.st
changeset 5428 62da57f5206d
parent 5422 b43b5950922d
child 5436 59effbe755f7
--- a/SimpleView.st	Tue Oct 27 10:50:02 2009 +0100
+++ b/SimpleView.st	Tue Oct 27 17:40:18 2009 +0100
@@ -5396,7 +5396,8 @@
 configureX:x y:y width:newWidth height:newHeight
     "my size has changed by window manager action"
 
-    |how anyEdge mustRedrawBottomEdge mustRedrawRightEdge p originChanged|
+    |how anyEdge mustRedrawBottomEdge mustRedrawRightEdge 
+     mustRedrawPreviousRightBorderArea mustRedrawPreviousBottomBorderArea p originChanged|
 
     originChanged := (left ~= x) or:[top ~= y].
 
@@ -5405,64 +5406,67 @@
 
     (superView isNil
     and:[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
-	    ]
-	].
-
-	level ~~ 0 ifTrue:[
-	    mustRedrawBottomEdge := newHeight < height.
-	    mustRedrawRightEdge := newWidth < width.
-	    anyEdge := mustRedrawBottomEdge or:[mustRedrawRightEdge]
-	] ifFalse:[
-	    anyEdge := 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
-	"
+        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 := 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-1-margin)) extent:width@margin) repairNow:false.
-	    ].
-	    mustRedrawRightEdge ifTrue:[
-		self invalidateDeviceRectangle:((width-1-margin)@0 extent:margin@height) repairNow:false.
-	    ].
+        self sizeChanged:how.
+
+        (anyEdge and:[shown]) ifTrue:[
+            mustRedrawBottomEdge ifTrue:[
+                self invalidateDeviceRectangle:((0 @ (height-1-margin)) extent:width@margin) repairNow:false.
+            ].
+            mustRedrawRightEdge ifTrue:[
+                self invalidateDeviceRectangle:((width-1-margin)@0 extent:margin@height) repairNow:false.
+            ].
 "/ OLD code:
 "/            self clippingRectangle:nil.
 "/            mustRedrawBottomEdge ifTrue:[
@@ -5472,11 +5476,11 @@
 "/                self drawRightEdge
 "/            ].
 "/            self deviceClippingRectangle:innerClipRect
-	]
+        ]
     ].
 
     originChanged ifTrue:[
-	self changed:#origin.
+        self changed:#origin.
     ].
 
     "Modified: / 10.10.2001 / 14:14:19 / cg"
@@ -7703,150 +7707,151 @@
      a dimension <= 0 ... (although I think that 0 maks sense ...)
     "
     newWidth < 1 ifTrue:[
-	newWidth := 1.
+        newWidth := 1.
     ].
     newHeight < 1 ifTrue:[
-	newHeight := 1
+        newHeight := 1
     ].
 
     ((newWidth == width) and:[newHeight == height]) ifTrue:[
-	sameOrigin ifTrue:[^ self].
-	self changed:#origin.
-	^ self pixelOrigin:origin
-    ].
+        sameOrigin ifTrue:[^ self].
+        self changed:#origin.
+        ^ self pixelOrigin:origin
+    ].
+
     top := newTop.
     left := newLeft.
 
 "/    shown ifTrue:[                  "4-nov-94 actually correct,"
     drawableId notNil ifTrue:[        "but theres a bug in menus when resized while hidden"
-	mustRedrawBottomEdge := (level ~~ 0) and:[newHeight < height].
-	mustRedrawRightEdge := (level ~~ 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:[
-	    (level ~~ 0) ifTrue:[
-		"clear the old edges"
-
-		newWidth > width ifTrue:[
-		    self clippingRectangle:nil.
-		    oldPaint := paint.
-		    self paint:viewBackground.
-		    self fillDeviceRectangleX:(width - margin)
-					    y:0
-					width:margin
-				       height:height.
-		    self paint:oldPaint.
-		    mustRepaintRight := true.
-		].
-		newHeight > height ifTrue:[
-		    self clippingRectangle:nil.
-		    oldPaint := paint.
-		    self paint:viewBackground.
-		    self fillDeviceRectangleX:0
-					    y:(height - margin)
-					width:width
-				       height:margin.
-		    self paint:oldPaint.
-		    mustRepaintBottom := true.
-		]
-	    ]
-	].
-
-	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: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"
+
+                newWidth > width ifTrue:[
+                    self clippingRectangle:nil.
+                    oldPaint := paint.
+                    self paint:viewBackground.
+                    self fillDeviceRectangleX:(width - margin)
+                                            y:0
+                                        width:margin
+                                       height:height.
+                    self paint:oldPaint.
+                    mustRepaintRight := true.
+                ].
+                newHeight > height ifTrue:[
+                    self clippingRectangle:nil.
+                    oldPaint := paint.
+                    self paint:viewBackground.
+                    self fillDeviceRectangleX:0
+                                            y:(height - margin)
+                                        width:width
+                                       height:margin.
+                    self paint:oldPaint.
+                    mustRepaintBottom := true.
+                ]
+            ]
+        ].
+
+        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: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: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:[
-		self deviceClippingRectangle:nil.
-		oldPaint := paint.
-		mustRedrawBottomEdge ifTrue:[
-		    self drawBottomEdge
-		].
-		mustRedrawRightEdge ifTrue:[
-		    self drawRightEdge
-		].
-		self paint:oldPaint.
-		self deviceClippingRectangle:innerClipRect
-	    ].
-	].
-
-	mustRepaintRight ifTrue:[
-	    self invalidateDeviceRectangle:(((oldWidth - margin) @ 0)
-					   extent:margin@height)
-				 repairNow:false.
+            device moveResizeWindow: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:[
+                self deviceClippingRectangle:nil.
+                oldPaint := paint.
+                mustRedrawBottomEdge ifTrue:[
+                    self drawBottomEdge
+                ].
+                mustRedrawRightEdge ifTrue:[
+                    self drawRightEdge
+                ].
+                self paint:oldPaint.
+                self deviceClippingRectangle: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 size > 0 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 size > 0 ifTrue:[
+            self extentChangedBeforeCreatedFlag:true.
+        ].
     ].
     sameOrigin ifFalse:[
-	self changed:#origin.
+        self changed:#origin.
     ].
 
     "Modified: / 25.5.1999 / 14:49:56 / cg"
@@ -10536,11 +10541,11 @@
 !SimpleView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview/SimpleView.st,v 1.646 2009-10-24 19:56:54 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview/SimpleView.st,v 1.647 2009-10-27 16:40:18 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libview/SimpleView.st,v 1.646 2009-10-24 19:56:54 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview/SimpleView.st,v 1.647 2009-10-27 16:40:18 cg Exp $'
 ! !
 
 SimpleView initialize!