canTab and visibilityChannel are not instVars
authorClaus Gittinger <cg@exept.de>
Tue, 07 Nov 2000 14:00:40 +0100
changeset 3364 efca1b5b2b0f
parent 3363 de7e8628d329
child 3365 a76614b953c7
canTab and visibilityChannel are not instVars (no longer use obj-attributes)
SimpleView.st
--- a/SimpleView.st	Tue Nov 07 12:51:16 2000 +0100
+++ b/SimpleView.st	Tue Nov 07 14:00:40 2000 +0100
@@ -19,7 +19,8 @@
 		originRule extentRule cornerRule insets layout shown
 		hiddenOnRealize name level margin innerClipRect shadowColor
 		lightColor bitGravity viewGravity controller windowGroup
-		preferredExtent explicitExtent dependents layoutManager'
+		preferredExtent explicitExtent dependents layoutManager canTab
+		visibilityChannel'
 	classVariableNames:'Grey CentPoint ViewSpacing DefaultStyle StyleSheet
 		DefaultViewBackgroundColor DefaultBorderColor DefaultLightColor
 		DefaultShadowColor DefaultBorderWidth DefaultFocusColor
@@ -1042,15 +1043,15 @@
 
     StyleSheet := ViewStyle fromFile:(DefaultStyle , '.style').
     StyleSheet fileReadFailed ifTrue:[
-        ('SimpleView [warning]: ***** no styleSheet for ' , DefaultStyle , '-style.') errorPrintCR.
-        DefaultStyle ~~ #normal ifTrue:[
-            DefaultStyle := #normal.
-            StyleSheet := ViewStyle fromFile:(DefaultStyle , '.style').
+	('SimpleView [warning]: ***** no styleSheet for ' , DefaultStyle , '-style.') errorPrintCR.
+	DefaultStyle ~~ #normal ifTrue:[
+	    DefaultStyle := #normal.
+	    StyleSheet := ViewStyle fromFile:(DefaultStyle , '.style').
         
-            StyleSheet fileReadFailed ifTrue:[
-                'SimpleView [warning]: not even a styleSheet for normal-style (using defaults).' errorPrintCR.
-            ]
-        ]
+	    StyleSheet fileReadFailed ifTrue:[
+		'SimpleView [warning]: not even a styleSheet for normal-style (using defaults).' errorPrintCR.
+	    ]
+	]
     ].
 
     "Created: / 15.9.1998 / 22:03:06 / cg"
@@ -1099,16 +1100,16 @@
     |defStyle|
 
     DefaultStyle isNil ifTrue:[
-        defStyle := OperatingSystem getEnvironment:'STX_VIEWSTYLE'.
-        defStyle notNil ifTrue:[
-            DefaultStyle := defStyle asSymbol.
-        ] ifFalse:[
-            OperatingSystem isMSWINDOWSlike ifTrue:[
-                DefaultStyle := #mswindows95
-            ] ifFalse:[
-                DefaultStyle := #motif
-            ]
-        ].
+	defStyle := OperatingSystem getEnvironment:'STX_VIEWSTYLE'.
+	defStyle notNil ifTrue:[
+	    DefaultStyle := defStyle asSymbol.
+	] ifFalse:[
+	    OperatingSystem isMSWINDOWSlike ifTrue:[
+		DefaultStyle := #mswindows95
+	    ] ifFalse:[
+		DefaultStyle := #motif
+	    ]
+	].
     ].
 !
 
@@ -1167,8 +1168,8 @@
      anyway."
 
     <resource: #style (#viewSpacing #font #borderWidth #borderColor
-                       #viewBackground #shadowColor #lightColor
-                       #focusColor #focusBorderWidth)>
+		       #viewBackground #shadowColor #lightColor
+		       #focusColor #focusBorderWidth)>
 
     |bgGrey currentScreen|
 
@@ -1177,68 +1178,68 @@
      and keep the values in fast class variables
     "
     StyleSheet isNil ifTrue:[
-        self setDefaultStyle.
-        self readStyleSheet.
+	self setDefaultStyle.
+	self readStyleSheet.
     ].
 
     currentScreen := Screen current.
 
     Grey := StyleSheet viewGrey.
     Grey isNil ifTrue:[
-        Grey := Color grey
+	Grey := Color grey
     ].
     Grey := Grey onDevice:currentScreen.
 
     StyleSheet fileReadFailed ifTrue:[
-        bgGrey := White
+	bgGrey := White
     ] ifFalse:[
-        currentScreen hasGrayscales ifTrue:[
-            bgGrey := Grey
-        ] ifFalse:[
-            bgGrey := White 
-        ]
+	currentScreen hasGrayscales ifTrue:[
+	    bgGrey := Grey
+	] ifFalse:[
+	    bgGrey := White 
+	]
     ].
     bgGrey := bgGrey onDevice:currentScreen.
 
     ViewSpacing := StyleSheet at:#viewSpacing.
     ViewSpacing isNil ifTrue:[
-        ViewSpacing := currentScreen defaultStyleValueFor:#viewSpacing.
+	ViewSpacing := currentScreen defaultStyleValueFor:#viewSpacing.
     ].
 
     DefaultBorderColor := StyleSheet colorAt:#borderColor.
     DefaultBorderColor isNil ifTrue:[
-        DefaultBorderColor := currentScreen defaultStyleValueFor:#borderColor
+	DefaultBorderColor := currentScreen defaultStyleValueFor:#borderColor
     ].
 
     StyleSheet fileReadFailed ifTrue:[
-        DefaultBorderWidth := 1.
-        DefaultShadowColor := Black.
-        DefaultLightColor :=  White.
-        DefaultFocusColor := Black.
-        DefaultFocusBorderWidth := 2.
-        DefaultViewBackgroundColor := White.
+	DefaultBorderWidth := 1.
+	DefaultShadowColor := Black.
+	DefaultLightColor :=  White.
+	DefaultFocusColor := Black.
+	DefaultFocusBorderWidth := 2.
+	DefaultViewBackgroundColor := White.
     ] ifFalse:[
-        DefaultBorderWidth := StyleSheet at:#borderWidth default:0.
-        DefaultViewBackgroundColor := StyleSheet colorAt:#viewBackground default:bgGrey.
-        DefaultShadowColor := StyleSheet colorAt:#shadowColor.
-        DefaultLightColor := StyleSheet colorAt:#lightColor.
-        DefaultFocusColor := StyleSheet colorAt:#focusColor default:Color red.
-        DefaultFocusBorderWidth := StyleSheet at:'focusBorderWidth' default:2.
+	DefaultBorderWidth := StyleSheet at:#borderWidth default:0.
+	DefaultViewBackgroundColor := StyleSheet colorAt:#viewBackground default:bgGrey.
+	DefaultShadowColor := StyleSheet colorAt:#shadowColor.
+	DefaultLightColor := StyleSheet colorAt:#lightColor.
+	DefaultFocusColor := StyleSheet colorAt:#focusColor default:Color red.
+	DefaultFocusBorderWidth := StyleSheet at:'focusBorderWidth' default:2.
     ].
 
     self == SimpleView ifTrue:[
-        DefaultFont := StyleSheet at:#font.
-        DefaultFont isNil ifTrue:[
-            DefaultFont := Font family:'courier' face:'medium' style:'roman' size:12.
-        ].
-        DefaultFont := DefaultFont onDevice:currentScreen.
+	DefaultFont := StyleSheet at:#font.
+	DefaultFont isNil ifTrue:[
+	    DefaultFont := Font family:'courier' face:'medium' style:'roman' size:12.
+	].
+	DefaultFont := DefaultFont onDevice:currentScreen.
     ] ifFalse:[
-        DefaultFont := nil
+	DefaultFont := nil
     ].
 
     DefaultViewBackgroundColor isNil ifTrue:[
-        'SimpleView [warning]: bad viewBackground in style - using white' errorPrintCR.
-        DefaultViewBackgroundColor := White
+	'SimpleView [warning]: bad viewBackground in style - using white' errorPrintCR.
+	DefaultViewBackgroundColor := White
     ].
 
     "Modified: / 29.4.1997 / 11:16:52 / dq"
@@ -1476,9 +1477,9 @@
      recursively in all of my subviews"
 
     subViews notNil ifTrue:[
-        subViews do:[:v|
-            v allViewBackground:something
-        ]
+	subViews do:[:v|
+	    v allViewBackground:something
+	]
     ]
 
     "Modified: / 18.7.1996 / 13:34:26 / cg"
@@ -1490,10 +1491,10 @@
      in myself and recursively in all of my subviews"
 
     viewBackground ~~ something ifTrue:[
-        self viewBackground:something.
-        shown ifTrue:[
-            self invalidate
-        ].
+	self viewBackground:something.
+	shown ifTrue:[
+	    self invalidate
+	].
     ].
 
     self allSubViewsBackground:something
@@ -1711,17 +1712,17 @@
 
     "/ debug check only:
     something isNil ifTrue:[
-        self error:'invalid viewBackground argument'.
-        ^ self
+	self error:'invalid viewBackground argument'.
+	^ self
     ].
 
     something isColor ifTrue:[
-        device hasGrayscales ifTrue:[
-            avgColor := something averageColorIn:(0@0 corner:7@7).
-
-            shadowColor := avgColor darkened "on:device".
-            lightColor := avgColor lightened "on:device".
-        ]
+	device hasGrayscales ifTrue:[
+	    avgColor := something averageColorIn:(0@0 corner:7@7).
+
+	    shadowColor := avgColor darkened "on:device".
+	    lightColor := avgColor lightened "on:device".
+	]
     ].
     super viewBackground:something
 
@@ -1789,6 +1790,40 @@
     ^ newChannel
 
     "Modified: / 31.10.1997 / 14:47:21 / cg"
+!
+
+visibilityChannel 
+    "return a valueHolder for visible/invisible"
+
+    ^ visibilityChannel
+
+    "Modified: / 30.3.1999 / 13:49:56 / stefan"
+!
+
+visibilityChannel:aValueHolder 
+    "set the valueHolder, which holds the visible boolean value"
+
+    |prev|
+
+    prev := visibilityChannel.
+    visibilityChannel := aValueHolder.
+    self setupChannel:aValueHolder for:#visibilityStateChanged withOld:prev
+
+    "
+      |v h|
+
+      v := View new.
+      v visibilityChannel:(h := ValueHolder with:true).
+      v open.
+      Delay waitForSeconds:2.
+      h value:false.
+      Delay waitForSeconds:2.
+      h value:true.
+      Delay waitForSeconds:2.
+    "
+
+    "Created: / 14.1.1998 / 17:11:15 / stefan"
+    "Modified: / 14.1.1998 / 17:33:40 / stefan"
 ! !
 
 !SimpleView methodsFor:'accessing-contents'!
@@ -2417,75 +2452,75 @@
     |extent shapeForm borderForm w h f|
 
     device supportsRoundShapedViews ifTrue:[
-        "/ TODO: add code for round shaped view (mswin)
+	"/ TODO: add code for round shaped view (mswin)
     ].
 
     device supportsArbitraryShapedViews ifTrue:[
-        extent := self extent.
-        w := extent x.
-        h := extent y.
-        borderForm := Form extent:extent.
-        shapeForm  := Form extent:extent.
-
-        borderForm fillArcX:0 y:0 
-                  width:w
-                 height:h
-                   from:0
-                  angle:360.
-
-        opaque ifFalse:[
-            f := borderForm.
-            borderForm foreground:(Color colorId:0).
-        ] ifTrue:[
-            f := shapeForm.
-            shapeForm foreground:(Color colorId:1).
-        ].
-
-        f fillArcX:lineWidth y:lineWidth 
-                width:w - (bw * 2)
-               height:h - (bw * 2)
-                 from:0
-                angle:360.
-
-        self borderShape:borderForm.
-        self viewShape:shapeForm.
-        ^ self.
-
-
-        extent := self extent.
-
-        w := extent x.  
-        h := extent y.
-        borderForm := Form width:w height:h.
+	extent := self extent.
+	w := extent x.
+	h := extent y.
+	borderForm := Form extent:extent.
+	shapeForm  := Form extent:extent.
+
+	borderForm fillArcX:0 y:0 
+		  width:w
+		 height:h
+		   from:0
+		  angle:360.
+
+	opaque ifFalse:[
+	    f := borderForm.
+	    borderForm foreground:(Color colorId:0).
+	] ifTrue:[
+	    f := shapeForm.
+	    shapeForm foreground:(Color colorId:1).
+	].
+
+	f fillArcX:lineWidth y:lineWidth 
+		width:w - (bw * 2)
+	       height:h - (bw * 2)
+		 from:0
+		angle:360.
+
+	self borderShape:borderForm.
+	self viewShape:shapeForm.
+	^ self.
+
+
+	extent := self extent.
+
+	w := extent x.  
+	h := extent y.
+	borderForm := Form width:w height:h.
 "/        borderForm fill:(Color colorId:0).
 "/
-        shapeForm := Form width:w height:h.
+	shapeForm := Form width:w height:h.
 "/        shapeForm fill:(Color colorId:0).
 
-        borderForm foreground:(Color colorId:1).
-        borderForm 
-            fillArcX:0 y:0 
-            width:w
-            height:h
-            from:0
-            angle:360.
-
-        opaque ifFalse:[
-            f := borderForm.
-            borderForm foreground:(Color colorId:0).
-        ] ifTrue:[
-            f := shapeForm.
-            shapeForm foreground:(Color colorId:1).
-        ].
-        f 
-            fillArcX:bw y:bw 
-            width:(w - (bw * 2))
-            height:(h - (bw * 2))
-            from:0
-            angle:360.
-
-        self borderShape:borderForm.
-        self viewShape:shapeForm
+	borderForm foreground:(Color colorId:1).
+	borderForm 
+	    fillArcX:0 y:0 
+	    width:w
+	    height:h
+	    from:0
+	    angle:360.
+
+	opaque ifFalse:[
+	    f := borderForm.
+	    borderForm foreground:(Color colorId:0).
+	] ifTrue:[
+	    f := shapeForm.
+	    shapeForm foreground:(Color colorId:1).
+	].
+	f 
+	    fillArcX:bw y:bw 
+	    width:(w - (bw * 2))
+	    height:(h - (bw * 2))
+	    from:0
+	    angle:360.
+
+	self borderShape:borderForm.
+	self viewShape:shapeForm
     ]
 
 !
@@ -2501,28 +2536,28 @@
 "/    ].
 
     device supportsArbitraryShapedViews ifTrue:[
-        extent := self extent.
-        w := extent x.
-        h := extent y.
-        borderForm := Form extent:extent.
-        shapeForm  := Form extent:extent.
-
-        borderForm 
-            fillRectangleX:0 y:0
-            width:w
-            height:h.
-
-        f := borderForm.
-        borderForm foreground:(Color colorId:0).
-
-        borderForm
-            fillRectangleX:bw y:bw
-            width:w - (bw * 2)
-            height:h - (bw * 2).
-
-        self borderShape:borderForm.
-        self viewShape:shapeForm.
-        ^ self.
+	extent := self extent.
+	w := extent x.
+	h := extent y.
+	borderForm := Form extent:extent.
+	shapeForm  := Form extent:extent.
+
+	borderForm 
+	    fillRectangleX:0 y:0
+	    width:w
+	    height:h.
+
+	f := borderForm.
+	borderForm foreground:(Color colorId:0).
+
+	borderForm
+	    fillRectangleX:bw y:bw
+	    width:w - (bw * 2)
+	    height:h - (bw * 2).
+
+	self borderShape:borderForm.
+	self viewShape:shapeForm.
+	^ self.
     ]
 
 !
@@ -3276,26 +3311,26 @@
     aWindowSpecOrSpecSymbol isNil ifTrue:[^ self].
 
     (builder := aBuilder) isNil ifTrue:[
-        "/ problem: anApplication could have no builder
-        "/          or anApplication could be a non-appModel (theoretically - only providing a spec)
-        notAnAppModel := false.
-        builder := anApplication perform:#builder ifNotUnderstood:[notAnAppModel := true. nil].
-        builder isNil ifTrue:[
-            notAnAppModel ifTrue:[
-                 builder := UIBuilder new.    
-            ] ifFalse:[
-                 anApplication createBuilder.
-                 builder := anApplication builder
-            ]
-        ]
+	"/ problem: anApplication could have no builder
+	"/          or anApplication could be a non-appModel (theoretically - only providing a spec)
+	notAnAppModel := false.
+	builder := anApplication perform:#builder ifNotUnderstood:[notAnAppModel := true. nil].
+	builder isNil ifTrue:[
+	    notAnAppModel ifTrue:[
+		 builder := UIBuilder new.    
+	    ] ifFalse:[
+		 anApplication createBuilder.
+		 builder := anApplication builder
+	    ]
+	]
     ].
 
     (subSpec := aWindowSpecOrSpecSymbol) isSymbol ifTrue:[
-        anApplication isNil ifTrue:[^ self].
-        subSpec := anApplication class interfaceSpecFor:aWindowSpecOrSpecSymbol.
-        subSpec isNil ifTrue:[
-            ^ self
-        ].
+	anApplication isNil ifTrue:[^ self].
+	subSpec := anApplication class interfaceSpecFor:aWindowSpecOrSpecSymbol.
+	subSpec isNil ifTrue:[
+	    ^ self
+	].
     ].
     builder buildFromSpec:subSpec in:self.
 
@@ -3509,12 +3544,12 @@
 
     self hiddenOnRealize:true.
     realized ifTrue:[
-        (superView isNil              "/ I am a topView
-        or:[superView realized        "/ superview already shown
-        or:[superView id notNil]])     "/ superview already created
-            ifTrue:[
-                self unmap
-            ]
+	(superView isNil              "/ I am a topView
+	or:[superView realized        "/ superview already shown
+	or:[superView id notNil]])     "/ superview already created
+	    ifTrue:[
+		self unmap
+	    ]
     ]
 
     "Modified: 3.4.1997 / 21:20:40 / cg"
@@ -3532,20 +3567,20 @@
 
     self hiddenOnRealize:false.
     realized ifFalse:[
-        superView isNil                 "/ I am a topView
-        ifTrue:[
-            drawableId isNil ifTrue:[
-                self realize.
-            ] ifFalse:[
-                self remap.
-            ].
-        ] ifFalse:[
-            (superView realized          "/ superview already shown
-            or:[superView id notNil])    "/ superview already created
-            ifTrue:[
-                self realize
-            ]
-        ].
+	superView isNil                 "/ I am a topView
+	ifTrue:[
+	    drawableId isNil ifTrue:[
+		self realize.
+	    ] ifFalse:[
+		self remap.
+	    ].
+	] ifFalse:[
+	    (superView realized          "/ superview already shown
+	    or:[superView id notNil])    "/ superview already created
+	    ifTrue:[
+		self realize
+	    ]
+	].
     ]
 
     "
@@ -3647,13 +3682,7 @@
 setVisibilityChannel:aValueHolder 
     "set the valueHolder, which holds the visible boolean value"
 
-    aValueHolder notNil ifTrue:[
-        self objectAttributeAt:#visibilityChannel put:aValueHolder.
-    ] ifFalse:[
-        self removeObjectAttribute:#visibilityChannel
-    ]
-
-    "Modified: / 18.2.2000 / 11:19:14 / cg"
+    visibilityChannel := aValueHolder
 !
 
 shown
@@ -3661,27 +3690,6 @@
      Shown means: the view is mapped and is not completely covered."
 
     ^ shown
-!
-
-visibilityChannel
-    "return the valueHolder, which holds the visible boolean value"
-
-    ^ self objectAttributeAt:#visibilityChannel.
-
-
-!
-
-visibilityChannel:aValueHolder 
-    "set the valueHolder, which holds the visible boolean value,
-     and setup a #visibilityStateChanged callBack, whenever it changes."
-
-    |prev|
-
-    prev := self visibilityChannel.
-    self setVisibilityChannel:aValueHolder.
-    self setupChannel:aValueHolder for:#visibilityStateChanged withOld:prev
-
-
 ! !
 
 !SimpleView methodsFor:'adding & removing components'!
@@ -4035,35 +4043,35 @@
 
     wasBlocked := OperatingSystem blockInterrupts.
     [
-        |deps|
-
-        deps := dependents.
-        "/
-        "/ store the very first dependent directly in
-        "/ the dependents instVar
-        "/
-        (deps isNil and:[anObject isCollection not]) ifTrue:[
-            dependents := anObject
-        ] ifFalse:[
-            "/
-            "/ store more dependents in the dependents collection
-            "/
-            deps isCollection ifTrue:[
-                deps add:anObject
-            ] ifFalse:[
-                deps == anObject ifFalse:[
-                    deps isNil ifTrue:[
-                        dependents := (IdentitySet with:anObject)
-                    ] ifFalse:[
-                        dependents := (IdentitySet with:deps with:anObject)
-                    ]
-                ]
-            ]
-        ]
+	|deps|
+
+	deps := dependents.
+	"/
+	"/ store the very first dependent directly in
+	"/ the dependents instVar
+	"/
+	(deps isNil and:[anObject isCollection not]) ifTrue:[
+	    dependents := anObject
+	] ifFalse:[
+	    "/
+	    "/ store more dependents in the dependents collection
+	    "/
+	    deps isCollection ifTrue:[
+		deps add:anObject
+	    ] ifFalse:[
+		deps == anObject ifFalse:[
+		    deps isNil ifTrue:[
+			dependents := (IdentitySet with:anObject)
+		    ] ifFalse:[
+			dependents := (IdentitySet with:deps with:anObject)
+		    ]
+		]
+	    ]
+	]
     ] valueNowOrOnUnwindDo:[
-        wasBlocked ifFalse:[
-            OperatingSystem unblockInterrupts
-        ]
+	wasBlocked ifFalse:[
+	    OperatingSystem unblockInterrupts
+	]
     ]
 
     "Modified: 8.1.1997 / 23:40:30 / cg"
@@ -4778,8 +4786,6 @@
     "view has been destroyed by someone else (usually window system)"
 
     shown := false.
-    self removeObjectAttribute:#visibilityChannel.
-    self removeObjectAttribute:#canTab.
     super destroyed
 
     "Modified: / 18.2.2000 / 11:20:34 / cg"
@@ -4831,118 +4837,118 @@
      check if there is a need to draw an edge (i.e. if margin is hit)
     "
     (margin ~~ 0) ifTrue:[
-        leftEdge := false.
-        topEdge := false.
-        rightEdge := false.
-        botEdge := false.
-        transformation notNil ifTrue:[
-            "
-             need device coordinates for this test
-            "
-            nx := transformation applyToX:nx.
-            ny := transformation applyToY:ny.
-            nw := transformation applyScaleX:nw.
-            nh := transformation applyScaleY:nh.
-        ].
-        "
-         adjust expose rectangle, to exclude the margin.
-         Care for rounding errors ...
-        "
-        (nx isMemberOf:SmallInteger) ifFalse:[
-            old := nx.
-            nx := nx truncated.
-            nw := nw + (nx - old).
-        ].
-        (ny isMemberOf:SmallInteger) ifFalse:[
-            old := ny.
-            ny := ny truncated.
-            nh := nh + (ny - old).
-        ].
-        (nw isMemberOf:SmallInteger) ifFalse:[
-            nw := nw truncated + 1
-        ].
-        (nh isMemberOf:SmallInteger) ifFalse:[
-            nh := nh truncated + 1
-        ].
-
-        dx := nx.
-        dy := ny.
-        dw := nw.
-        dh := nh.
-
-        (nx < margin) ifTrue:[
-            old := nx.
-            nx := margin.
-            nw := nw - (nx - old).
-            leftEdge := anyEdge := true.
-        ].
-        ((nx + nw - 1) >= (width - margin)) ifTrue:[
-            nw := (width - margin - nx).
-            rightEdge := anyEdge := true.
-        ].
-        (ny < margin) ifTrue:[
-            old := ny.
-            ny := margin.
-            nh := nh - (ny - old).
-            topEdge := anyEdge := true.
-        ].
-        ((ny + nh - 1) >= (height - margin)) ifTrue:[
-            nh := (height - margin - ny).
-            botEdge := anyEdge := true.
-        ].
-        transformation notNil ifTrue:[
-            "
-             need logical coordinates for redraw
-            "
-            nx := transformation applyInverseToX:nx.
-            ny := transformation applyInverseToY:ny.
-            nw := transformation applyInverseScaleX:nw.
-            nh := transformation applyInverseScaleY:nh.
-        ].
+	leftEdge := false.
+	topEdge := false.
+	rightEdge := false.
+	botEdge := false.
+	transformation notNil ifTrue:[
+	    "
+	     need device coordinates for this test
+	    "
+	    nx := transformation applyToX:nx.
+	    ny := transformation applyToY:ny.
+	    nw := transformation applyScaleX:nw.
+	    nh := transformation applyScaleY:nh.
+	].
+	"
+	 adjust expose rectangle, to exclude the margin.
+	 Care for rounding errors ...
+	"
+	(nx isMemberOf:SmallInteger) ifFalse:[
+	    old := nx.
+	    nx := nx truncated.
+	    nw := nw + (nx - old).
+	].
+	(ny isMemberOf:SmallInteger) ifFalse:[
+	    old := ny.
+	    ny := ny truncated.
+	    nh := nh + (ny - old).
+	].
+	(nw isMemberOf:SmallInteger) ifFalse:[
+	    nw := nw truncated + 1
+	].
+	(nh isMemberOf:SmallInteger) ifFalse:[
+	    nh := nh truncated + 1
+	].
+
+	dx := nx.
+	dy := ny.
+	dw := nw.
+	dh := nh.
+
+	(nx < margin) ifTrue:[
+	    old := nx.
+	    nx := margin.
+	    nw := nw - (nx - old).
+	    leftEdge := anyEdge := true.
+	].
+	((nx + nw - 1) >= (width - margin)) ifTrue:[
+	    nw := (width - margin - nx).
+	    rightEdge := anyEdge := true.
+	].
+	(ny < margin) ifTrue:[
+	    old := ny.
+	    ny := margin.
+	    nh := nh - (ny - old).
+	    topEdge := anyEdge := true.
+	].
+	((ny + nh - 1) >= (height - margin)) ifTrue:[
+	    nh := (height - margin - ny).
+	    botEdge := anyEdge := true.
+	].
+	transformation notNil ifTrue:[
+	    "
+	     need logical coordinates for redraw
+	    "
+	    nx := transformation applyInverseToX:nx.
+	    ny := transformation applyInverseToY:ny.
+	    nw := transformation applyInverseScaleX:nw.
+	    nh := transformation applyInverseScaleY:nh.
+	].
     ].
 
     (nw > 0 and:[nh > 0]) ifTrue:[
-        "
-         redraw inside area
-        "
-        self clippingRectangle:(Rectangle left:nx top:ny width:nw height:nh).
-
-        device supportsAnyViewBackgroundPixmaps ifFalse:[
-            "/ workaround: non-existing bg-pixmap support (win95)
-
-            viewBackground isImageOrForm ifTrue:[
-                (device supportsViewBackgroundPixmap:viewBackground) ifFalse:[
-                    self fillRectangleWithViewBackgroundX:nx y:ny width:nw height:nh
-                ]
-            ].
-        ].
-
-        self redrawX:nx y:ny width:nw height:nh.
+	"
+	 redraw inside area
+	"
+	self clippingRectangle:(Rectangle left:nx top:ny width:nw height:nh).
+
+	device supportsAnyViewBackgroundPixmaps ifFalse:[
+	    "/ workaround: non-existing bg-pixmap support (win95)
+
+	    viewBackground isImageOrForm ifTrue:[
+		(device supportsViewBackgroundPixmap:viewBackground) ifFalse:[
+		    self fillRectangleWithViewBackgroundX:nx y:ny width:nw height:nh
+		]
+	    ].
+	].
+
+	self redrawX:nx y:ny width:nw height:nh.
     ].
 
     "
      redraw edge(s)
     "
     anyEdge ifTrue:[
-        self deviceClippingRectangle:nil.
-        oldPaint := paint.
-        (topEdge and:[leftEdge and:[botEdge and:[rightEdge]]]) ifTrue:[
-            self drawEdges
-        ] ifFalse:[
-            topEdge ifTrue:[
-                self drawTopEdge
-            ].
-            leftEdge ifTrue:[
-                self drawLeftEdge
-            ].
-            botEdge ifTrue:[
-                self drawBottomEdge
-            ].
-            rightEdge ifTrue:[
-                self drawRightEdge
-            ]
-        ].
-        self paint:oldPaint.
+	self deviceClippingRectangle:nil.
+	oldPaint := paint.
+	(topEdge and:[leftEdge and:[botEdge and:[rightEdge]]]) ifTrue:[
+	    self drawEdges
+	] ifFalse:[
+	    topEdge ifTrue:[
+		self drawTopEdge
+	    ].
+	    leftEdge ifTrue:[
+		self drawLeftEdge
+	    ].
+	    botEdge ifTrue:[
+		self drawBottomEdge
+	    ].
+	    rightEdge ifTrue:[
+		self drawRightEdge
+	    ]
+	].
+	self paint:oldPaint.
     ].
     self deviceClippingRectangle:innerClipRect.
 
@@ -4979,44 +4985,44 @@
     |focusView|
 
     components notNil ifTrue:[
-        components notNil ifTrue:[
-            self componentsContainingX:x y:y do:[:comp :cx :cy |
-                comp keyPress:key x:cx y:cy.
-                ^ self
-            ]
-        ].
+	components notNil ifTrue:[
+	    self componentsContainingX:x y:y do:[:comp :cx :cy |
+		comp keyPress:key x:cx y:cy.
+		^ self
+	    ]
+	].
     ].
 
     key == #Menu ifTrue:[
-        ((focusView := self windowGroup focusView) notNil
-        and:[focusView ~~ self])
-        ifTrue:[
-           "/ forward to the focusView
-           focusView keyPress:key x:-1 y:-1.
-            ^ self
-        ].
-        ^ self activateMenu.
+	((focusView := self windowGroup focusView) notNil
+	and:[focusView ~~ self])
+	ifTrue:[
+	   "/ forward to the focusView
+	   focusView keyPress:key x:-1 y:-1.
+	    ^ self
+	].
+	^ self activateMenu.
     ].
 
     x isNil ifTrue:[
-        "/ already redelegated, but nowhere handled
-        superView notNil ifTrue:[
-            superView keyPress:key x:nil y:nil.
-        ].
-        ^ self
+	"/ already redelegated, but nowhere handled
+	superView notNil ifTrue:[
+	    superView keyPress:key x:nil y:nil.
+	].
+	^ self
     ].
 
     superView notNil ifTrue:[
-        superView
-            dispatchEvent:#keyPress:x:y:
-            arguments:(Array with:key with:0 with:0)
+	superView
+	    dispatchEvent:#keyPress:x:y:
+	    arguments:(Array with:key with:0 with:0)
         
 "/        WindowEvent
 "/            sendEvent:#keyPress:x:y:
 "/            arguments:(Array with:key with:0 with:0)
 "/            view:superView
     ] ifFalse:[
-        super keyPress:key x:x y:y
+	super keyPress:key x:x y:y
     ]
 
     "Modified: / 20.5.1998 / 22:55:08 / cg"
@@ -5292,7 +5298,7 @@
 visibilityStateChanged
     "this is called when our visibilityChannel changes"
 
-    self isVisible:(self visibilityChannel value)
+    self isVisible:(visibilityChannel value)
 
     "Modified: / 30.3.1999 / 16:09:14 / stefan"
 ! !
@@ -5372,22 +5378,13 @@
 canTab
     "returns true if widget is tabable
     "
-    ^ (self objectAttributeAt:#tabable) == true
+    ^ canTab == true
 !
 
 canTab:aBool
     "set widget tabable or not
     "
-    aBool == true ifTrue:[
-        self objectAttributeAt:#tabable put:true
-    ] ifFalse:[
-        self removeObjectAttribute:#tabable
-"/        (self objectAttributeAt:#tabable) == true ifTrue:[
-"/            self objectAttributeAt:#tabable put:false
-"/        ]
-    ].
-
-    "Modified: / 5.2.2000 / 19:44:55 / cg"
+    canTab := aBool 
 !
 
 focusNext
@@ -5397,17 +5394,17 @@
     |viewInSubView|
 
     (shown and:[subViews notNil]) ifTrue:[
-        subViews do:[:aSubView|
-            aSubView shown ifTrue:[
-                (aSubView canTab and:[aSubView enabled]) ifTrue:[
-                    ^ aSubView
-                ].
-
-                (viewInSubView := aSubView focusNext) notNil ifTrue:[
-                    ^ viewInSubView
-                ]
-            ]
-        ]
+	subViews do:[:aSubView|
+	    aSubView shown ifTrue:[
+		(aSubView canTab and:[aSubView enabled]) ifTrue:[
+		    ^ aSubView
+		].
+
+		(viewInSubView := aSubView focusNext) notNil ifTrue:[
+		    ^ viewInSubView
+		]
+	    ]
+	]
     ].
     ^ nil
 
@@ -5422,18 +5419,18 @@
     |viewInSubView|
 
     (shown and:[subViews notNil]) ifTrue:[
-        subViews reverseDo:[:aSubView|
-            aSubView shown ifTrue:[
-                viewInSubView := aSubView focusPrevious.
-
-                viewInSubView notNil ifTrue:[
-                    ^ viewInSubView
-                ].
-                (aSubView canTab and:[aSubView enabled]) ifTrue:[
-                    ^ aSubView
-                ].
-            ]
-        ]
+	subViews reverseDo:[:aSubView|
+	    aSubView shown ifTrue:[
+		viewInSubView := aSubView focusPrevious.
+
+		viewInSubView notNil ifTrue:[
+		    ^ viewInSubView
+		].
+		(aSubView canTab and:[aSubView enabled]) ifTrue:[
+		    ^ aSubView
+		].
+	    ]
+	]
     ].
     ^ nil
 
@@ -5463,30 +5460,30 @@
     |delta clrId bd|
 
     explicit ifTrue:[
-        (drawableId notNil and:[superView notNil]) ifTrue:[
-            (styleSheet at:#'focus.showBorder' default:true) ifTrue:[
-                (device supportsWindowBorder:(bd := DefaultFocusBorderWidth)) ifFalse:[
-                    (device supportsWindowBorder:(bd := 1)) ifFalse:[
-                        bd := 0.
-                    ]
-                ].
-                delta := bd - borderWidth.
-                delta ~~ 0 ifTrue:[
-                    (left == 0 or:[top == 0]) ifTrue:[
-                        device resizeWindow:drawableId width:width-delta-delta height:height-delta-delta.
-                    ] ifFalse:[
-                        device moveWindow:drawableId x:left-delta y:top-delta.
-                    ].
-                    device setWindowBorderWidth:bd in:drawableId.
-                ].
-
-                clrId := (DefaultFocusColor onDevice:device) colorId.
-                clrId isNil ifTrue:[
-                    clrId := device blackpixel
-                ].
-                device setWindowBorderColor:clrId in:drawableId.
-            ]
-        ]
+	(drawableId notNil and:[superView notNil]) ifTrue:[
+	    (styleSheet at:#'focus.showBorder' default:true) ifTrue:[
+		(device supportsWindowBorder:(bd := DefaultFocusBorderWidth)) ifFalse:[
+		    (device supportsWindowBorder:(bd := 1)) ifFalse:[
+			bd := 0.
+		    ]
+		].
+		delta := bd - borderWidth.
+		delta ~~ 0 ifTrue:[
+		    (left == 0 or:[top == 0]) ifTrue:[
+			device resizeWindow:drawableId width:width-delta-delta height:height-delta-delta.
+		    ] ifFalse:[
+			device moveWindow:drawableId x:left-delta y:top-delta.
+		    ].
+		    device setWindowBorderWidth:bd in:drawableId.
+		].
+
+		clrId := (DefaultFocusColor onDevice:device) colorId.
+		clrId isNil ifTrue:[
+		    clrId := device blackpixel
+		].
+		device setWindowBorderColor:clrId in:drawableId.
+	    ]
+	]
     ] ifFalse:[
 "/        superView notNil ifTrue:[
 "/            superView showFocus:explicit
@@ -5505,22 +5502,22 @@
     |delta bd|
 
     explicit ifTrue:[
-        (drawableId notNil and:[superView notNil]) ifTrue:[
-            (styleSheet at:#'focus.showBorder' default:true) ifTrue:[
-                (device supportsWindowBorder:(bd := borderWidth)) ifFalse:[
-                    (device supportsWindowBorder:(bd := 1)) ifFalse:[
-                        bd := 0.
-                    ]
-                ].
-                delta := DefaultFocusBorderWidth - bd.
-                delta ~~ 0 ifTrue:[
-                    device setWindowBorderWidth:bd in:drawableId.
-                    device moveWindow:drawableId x:left y:top.
-                    device resizeWindow:drawableId width:width height:height.
-                ].
-                self setBorderColor.
-            ]
-        ]
+	(drawableId notNil and:[superView notNil]) ifTrue:[
+	    (styleSheet at:#'focus.showBorder' default:true) ifTrue:[
+		(device supportsWindowBorder:(bd := borderWidth)) ifFalse:[
+		    (device supportsWindowBorder:(bd := 1)) ifFalse:[
+			bd := 0.
+		    ]
+		].
+		delta := DefaultFocusBorderWidth - bd.
+		delta ~~ 0 ifTrue:[
+		    device setWindowBorderWidth:bd in:drawableId.
+		    device moveWindow:drawableId x:left y:top.
+		    device resizeWindow:drawableId width:width height:height.
+		].
+		self setBorderColor.
+	    ]
+	]
     ]
 
     "Modified: / 17.9.1998 / 15:08:02 / cg"
@@ -5687,9 +5684,6 @@
     "unmap & destroy - make me invisible, destroy subviews then
      make me unknown to the device"
 
-    self removeObjectAttribute:#visibilityChannel.
-    self removeObjectAttribute:#canTab.
-
     realized ifTrue:[
         self unmap.            
 "/        "make it go away immediately
@@ -5933,80 +5927,80 @@
      and handled in the superClass (static menus are a historic leftOver).
      Otherwise, the follwing steps are performed:
 
-        - ask the receiver for the menu (via #yellowButtonMenu)
-        - ask the receiver for the menuPerformer.
-        - startUp the menu - it is supposed to return an actionSelector
-        - if the menuPerformer responds to the selector,
-          send it to the performer;
-          otherwise send it to the view (the receiver)
-          This is funny, it allows additional menuItems to be added
-          AND still get the views copy/cut/paste functionality.
-          Without this, you had to redefine and forward all of those
-          messages in the performer."
+	- ask the receiver for the menu (via #yellowButtonMenu)
+	- ask the receiver for the menuPerformer.
+	- startUp the menu - it is supposed to return an actionSelector
+	- if the menuPerformer responds to the selector,
+	  send it to the performer;
+	  otherwise send it to the view (the receiver)
+	  This is funny, it allows additional menuItems to be added
+	  AND still get the views copy/cut/paste functionality.
+	  Without this, you had to redefine and forward all of those
+	  messages in the performer."
 
     |menu menuPerformer actionSelector prevReceiver wg|
 
     middleButtonMenu isNil ifTrue:[
-        "
-         try ST-80 style menus first:
-         if there is a model, and a menuMessage is defined,
-         ask model for the menu and launch that if non-nil.
-        "
-        menu := self yellowButtonMenu.
-        menu notNil ifTrue:[
-            "/ could be a spec ...
-            menu isArray ifTrue:[
-                menu := menu decodeAsLiteralArray
-            ].
-
-            "
-             got one, launch the menu. It is supposed
-             to return an actionSelector.
-            "
-            menuPerformer := self menuPerformer value.
-
-            "
-             a temporary kludge: 
-                 pass myself as receiver, the menuPerformer as performer;
-                 the menu will send its messages to either the
-                 menuPerformer or me (its receiver).
-                 This allows for the ST-80 behavior, where some messages
-                 go to the model, others to the view
-                 (copy/cut/paste).
-            "
-            (prevReceiver := menu receiver) isNil ifTrue:[
-                "/ kludge for oldStyle menus (MenuView/PopUpMenu)
-                "/ not req'd for real Menus
-                "/ (menu isKindOf:Menu) ifFalse:[
-                (menu respondsTo:#menuPerformer:) ifTrue:[
-                    menu receiver:self.    "/ really ?
-                    menu menuPerformer:menuPerformer.
-                ] ifFalse:[
-                "/ ] ifTrue:[
-                    "/ new style menu
-                    menu receiver:menuPerformer.
-                ]
-            ].
-
-            "/
-            "/ startup the menu - this returns a selector
-            "/
-            actionSelector := menu startUp.
-
-            "/ before doing anything else, redraw expose area from
-            "/ the menu (in case the action changes my state)
-            (wg := self windowGroup) notNil ifTrue:[
-                wg processExposeEvents.
-            ].
-
-            (actionSelector notNil and:[actionSelector isSymbol]) ifTrue:[
-                self dispatchMenuSelection:actionSelector to: menuPerformer.
-            ].
-
-            menu receiver:prevReceiver.
-
-            ^ self
-        ].
+	"
+	 try ST-80 style menus first:
+	 if there is a model, and a menuMessage is defined,
+	 ask model for the menu and launch that if non-nil.
+	"
+	menu := self yellowButtonMenu.
+	menu notNil ifTrue:[
+	    "/ could be a spec ...
+	    menu isArray ifTrue:[
+		menu := menu decodeAsLiteralArray
+	    ].
+
+	    "
+	     got one, launch the menu. It is supposed
+	     to return an actionSelector.
+	    "
+	    menuPerformer := self menuPerformer value.
+
+	    "
+	     a temporary kludge: 
+		 pass myself as receiver, the menuPerformer as performer;
+		 the menu will send its messages to either the
+		 menuPerformer or me (its receiver).
+		 This allows for the ST-80 behavior, where some messages
+		 go to the model, others to the view
+		 (copy/cut/paste).
+	    "
+	    (prevReceiver := menu receiver) isNil ifTrue:[
+		"/ kludge for oldStyle menus (MenuView/PopUpMenu)
+		"/ not req'd for real Menus
+		"/ (menu isKindOf:Menu) ifFalse:[
+		(menu respondsTo:#menuPerformer:) ifTrue:[
+		    menu receiver:self.    "/ really ?
+		    menu menuPerformer:menuPerformer.
+		] ifFalse:[
+		"/ ] ifTrue:[
+		    "/ new style menu
+		    menu receiver:menuPerformer.
+		]
+	    ].
+
+	    "/
+	    "/ startup the menu - this returns a selector
+	    "/
+	    actionSelector := menu startUp.
+
+	    "/ before doing anything else, redraw expose area from
+	    "/ the menu (in case the action changes my state)
+	    (wg := self windowGroup) notNil ifTrue:[
+		wg processExposeEvents.
+	    ].
+
+	    (actionSelector notNil and:[actionSelector isSymbol]) ifTrue:[
+		self dispatchMenuSelection:actionSelector to: menuPerformer.
+	    ].
+
+	    menu receiver:prevReceiver.
+
+	    ^ self
+	].
     ].
 
     "/
@@ -6030,8 +6024,8 @@
      mhmh - kludge for selectors with argument
     "
     (menuSelection isMemberOf:Array) ifTrue:[
-        actionArg1 := menuSelection at:2.
-        actionSelector := menuSelection at:1.
+	actionArg1 := menuSelection at:2.
+	actionSelector := menuSelection at:1.
     ].
 
     menuPerformer := aMenuPerformerOrNil ? self menuPerformer.
@@ -6042,26 +6036,26 @@
      Simulate this behavior, by looking what the model responds to.
     "
     actionSelector isSymbol ifTrue:[
-        (menuPerformer respondsTo:actionSelector) ifFalse:[
-            ((app := self application) respondsTo:actionSelector) ifTrue:[
-                menuPerformer := app.
-                actionArg1 := self model.
-                actionArg2 := self controller.
-            ] ifFalse:[
-                (self respondsTo:actionSelector) ifTrue:[
-                    menuPerformer := self
-                ]
-            ]
-        ].
-        actionSelector numArgs ~~ 0 ifTrue:[
-            actionSelector numArgs ~~ 1 ifTrue:[
-                menuPerformer perform:actionSelector with:actionArg1 with:actionArg2
-            ] ifFalse:[
-                menuPerformer perform:actionSelector with:actionArg1
-            ]
-        ] ifFalse:[
-            menuPerformer perform:actionSelector
-        ]
+	(menuPerformer respondsTo:actionSelector) ifFalse:[
+	    ((app := self application) respondsTo:actionSelector) ifTrue:[
+		menuPerformer := app.
+		actionArg1 := self model.
+		actionArg2 := self controller.
+	    ] ifFalse:[
+		(self respondsTo:actionSelector) ifTrue:[
+		    menuPerformer := self
+		]
+	    ]
+	].
+	actionSelector numArgs ~~ 0 ifTrue:[
+	    actionSelector numArgs ~~ 1 ifTrue:[
+		menuPerformer perform:actionSelector with:actionArg1 with:actionArg2
+	    ] ifFalse:[
+		menuPerformer perform:actionSelector with:actionArg1
+	    ]
+	] ifFalse:[
+	    menuPerformer perform:actionSelector
+	]
     ].
 
     "Created: / 20.6.1997 / 11:47:42 / cg"
@@ -6333,143 +6327,143 @@
      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 pixelOrigin:origin
+	sameOrigin ifTrue:[^ self].
+	^ 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"
-        (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 := (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"
+	(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"
-        (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"
+	(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:[
-            originChanged := true.
-        ].
-        extentChanged := true
+	"otherwise memorize the need for a sizeChanged message"
+
+	width := newWidth.
+	height := newHeight.
+	sameOrigin ifFalse:[
+	    originChanged := true.
+	].
+	extentChanged := true
     ]
 
     "Modified: / 25.5.1999 / 14:49:56 / cg"
@@ -7434,19 +7428,19 @@
     "recreate (i.e. tell X about me) after a snapin or a migration"
 
     drawableId isNil ifTrue:[
-        super recreate.
-        self physicalCreate.
-
-        viewBackground notNil ifTrue:[
-            self setViewBackground 
-        ].
-
-        "
-         XXX has to be changed: eventmasks are device specific -
-         XXX will not allow restart on another Workstation-type.
-         XXX event masks must become symbolic
-        "
-        device setEventMask:eventMask in:drawableId
+	super recreate.
+	self physicalCreate.
+
+	viewBackground notNil ifTrue:[
+	    self setViewBackground 
+	].
+
+	"
+	 XXX has to be changed: eventmasks are device specific -
+	 XXX will not allow restart on another Workstation-type.
+	 XXX event masks must become symbolic
+	"
+	device setEventMask:eventMask in:drawableId
     ]
 !
 
@@ -7535,17 +7529,17 @@
     "unmap the view - the view stays created (but invisible), and can be remapped again later."
 
     realized ifTrue:[
-        realized := false.
-        drawableId notNil ifTrue:[
-            device unmapWindow:drawableId
-        ].
-
-        "/ Normally, this is not correct with X, where the
-        "/ unmap is an asyncronous operation.
-        "/ (shown is cleared also in unmapped event)
-        "/ Do it anyway, to avoid synchronisation problems.
-
-        shown := false.
+	realized := false.
+	drawableId notNil ifTrue:[
+	    device unmapWindow:drawableId
+	].
+
+	"/ Normally, this is not correct with X, where the
+	"/ unmap is an asyncronous operation.
+	"/ (shown is cleared also in unmapped event)
+	"/ Do it anyway, to avoid synchronisation problems.
+
+	shown := false.
     ].
 
     "
@@ -7555,9 +7549,9 @@
      top extent:200@200.
 
      sub := View
-                origin:0.2@0.2
-                corner:0.8@0.8
-                in:top.
+		origin:0.2@0.2
+		corner:0.8@0.8
+		in:top.
 
      sub viewBackground:Color red.
      sub hiddenOnRealize:true.
@@ -8391,7 +8385,7 @@
 
     masterGroup := WindowGroup activeGroup.
     [masterGroup notNil and:[masterGroup isPopUp or:[masterGroup isModal]]] whileTrue:[
-        masterGroup := masterGroup previousGroup.
+	masterGroup := masterGroup previousGroup.
     ].
     ^ self openModal:aBlock inGroup:masterGroup "/ mainGroup.
 
@@ -8410,120 +8404,120 @@
     |tops mainView mainViewID previousGroup |
 
     self isPopUpView ifFalse:[
-        ModalBox usingTransientViews ifTrue:[
-            "make view only transient, if there is a visible topView.
-             If none of them is visible, we do want an icon for ourself"
+	ModalBox usingTransientViews ifTrue:[
+	    "make view only transient, if there is a visible topView.
+	     If none of them is visible, we do want an icon for ourself"
         
-            mainGroup notNil ifTrue:[
-                (tops := mainGroup topViews) notNil ifTrue:[
-                    tops notEmpty ifTrue:[
-                        mainView := tops detect:[:v| v shown] ifNone:nil.
-                        mainView notNil ifTrue:[
-                            mainViewID := mainView id.
-                        ]
-                    ]
-                ].
-            ].
-
-            mainViewID isNil ifTrue:[
-                self origin:(device center - (self extent//2))
-            ].
-
-            drawableId isNil ifTrue:[self create].
-            mainView notNil ifTrue:[
-                device setTransient:drawableId for:mainViewID.
-            ].
-        ].
+	    mainGroup notNil ifTrue:[
+		(tops := mainGroup topViews) notNil ifTrue:[
+		    tops notEmpty ifTrue:[
+			mainView := tops detect:[:v| v shown] ifNone:nil.
+			mainView notNil ifTrue:[
+			    mainViewID := mainView id.
+			]
+		    ]
+		].
+	    ].
+
+	    mainViewID isNil ifTrue:[
+		self origin:(device center - (self extent//2))
+	    ].
+
+	    drawableId isNil ifTrue:[self create].
+	    mainView notNil ifTrue:[
+		device setTransient:drawableId for:mainViewID.
+	    ].
+	].
     ].
 
     self raise.
 
     Processor activeProcessIsSystemProcess ifTrue:[
-        "
-         put myself into the modal group, let it handle events for
-         me as well. This is only a half way solution, since the view
-         is not modal at all ... however, the only situation
-         where this happens is with modal boxes popped while in a
-         modal browser. You will forgive me for that inconvenience.
-        "
-        windowGroup := mainGroup.
-        mainGroup notNil ifTrue:[mainGroup addTopView:self].
-        self realize
+	"
+	 put myself into the modal group, let it handle events for
+	 me as well. This is only a half way solution, since the view
+	 is not modal at all ... however, the only situation
+	 where this happens is with modal boxes popped while in a
+	 modal browser. You will forgive me for that inconvenience.
+	"
+	windowGroup := mainGroup.
+	mainGroup notNil ifTrue:[mainGroup addTopView:self].
+	self realize
     ] ifFalse:[
-        previousGroup := WindowGroup activeGroup.
-
-        "
-         show a stop-cursor in the main group
-        "
-        mainGroup notNil ifTrue:[
-            self isPopUpView ifFalse:[
-                mainGroup showCursor:(Cursor stop).
-                (previousGroup notNil and:[previousGroup ~~ mainGroup]) ifTrue:[
-                    previousGroup showCursor:(Cursor stop).
-                ].
-            ]
-        ].
-
-        "
-         create a new window group and put myself into it
-        "
-        windowGroup := WindowGroup new.
-        windowGroup addTopView:self.
-        windowGroup setPreviousGroup:previousGroup.
-
-        superView notNil ifTrue:[
-            "/
-            "/ special: this is a modal subview,
-            "/ prevent the view from reassigning its windowGroup when realized
-            "/ (subviews normally place themself into the superviews group)
-            "/        
-            windowGroup isForModalSubview:true.
-        ].
-
-        "
-         go dispatch events in this new group
-         (thus current windowgroup is blocked from interaction)
-        "
-        AbortSignal handle:[:ex |
-            self hide.
-            ex return.
-        ] do:[
-            [
-                [
-                    windowGroup startupModal:[realized and:aBlock] forGroup:mainGroup
-                ] valueOnUnwindDo:[
-                    self hide.
-                ]
-            ] valueNowOrOnUnwindDo:[
-                mainGroup notNil ifTrue:[
-                    mainGroup graphicsDevice sync.
-                    "/ ensure that eventListener runs here ...
-                    Delay waitForSeconds:0.05.    
-                    mainGroup processExposeEvents.
-
-                    ReturnFocusWhenClosingModalBoxes ifTrue:[
-                        "
-                         return input focus to previously active groups top.
-                         This helps with windowmanagers which need an explicit click
-                         on the view for the focus.
-                        "
-                        tops := mainGroup topViews.
-                        (tops notNil and:[tops notEmpty]) ifTrue:[
-                            tops first getKeyboardFocus
-                        ].
-                    ].
-
-                    "
-                     restore cursors in the main group & flush its buffered key & mouse events
-                    "
-                    mainGroup restoreCursors.
-                    (previousGroup notNil and:[previousGroup ~~ mainGroup]) ifTrue:[
-                        previousGroup restoreCursors.
-                    ].
+	previousGroup := WindowGroup activeGroup.
+
+	"
+	 show a stop-cursor in the main group
+	"
+	mainGroup notNil ifTrue:[
+	    self isPopUpView ifFalse:[
+		mainGroup showCursor:(Cursor stop).
+		(previousGroup notNil and:[previousGroup ~~ mainGroup]) ifTrue:[
+		    previousGroup showCursor:(Cursor stop).
+		].
+	    ]
+	].
+
+	"
+	 create a new window group and put myself into it
+	"
+	windowGroup := WindowGroup new.
+	windowGroup addTopView:self.
+	windowGroup setPreviousGroup:previousGroup.
+
+	superView notNil ifTrue:[
+	    "/
+	    "/ special: this is a modal subview,
+	    "/ prevent the view from reassigning its windowGroup when realized
+	    "/ (subviews normally place themself into the superviews group)
+	    "/        
+	    windowGroup isForModalSubview:true.
+	].
+
+	"
+	 go dispatch events in this new group
+	 (thus current windowgroup is blocked from interaction)
+	"
+	AbortSignal handle:[:ex |
+	    self hide.
+	    ex return.
+	] do:[
+	    [
+		[
+		    windowGroup startupModal:[realized and:aBlock] forGroup:mainGroup
+		] valueOnUnwindDo:[
+		    self hide.
+		]
+	    ] valueNowOrOnUnwindDo:[
+		mainGroup notNil ifTrue:[
+		    mainGroup graphicsDevice sync.
+		    "/ ensure that eventListener runs here ...
+		    Delay waitForSeconds:0.05.    
+		    mainGroup processExposeEvents.
+
+		    ReturnFocusWhenClosingModalBoxes ifTrue:[
+			"
+			 return input focus to previously active groups top.
+			 This helps with windowmanagers which need an explicit click
+			 on the view for the focus.
+			"
+			tops := mainGroup topViews.
+			(tops notNil and:[tops notEmpty]) ifTrue:[
+			    tops first getKeyboardFocus
+			].
+		    ].
+
+		    "
+		     restore cursors in the main group & flush its buffered key & mouse events
+		    "
+		    mainGroup restoreCursors.
+		    (previousGroup notNil and:[previousGroup ~~ mainGroup]) ifTrue:[
+			previousGroup restoreCursors.
+		    ].
 "/                    mainGroup sensor flushUserEvents.
-                ]
-            ]
-        ].
+		]
+	    ]
+	].
     ]
 
     "Created: 10.12.1995 / 14:06:14 / cg"
@@ -8682,36 +8676,36 @@
      another view (which is only available once visible), 
      use this to suspend the current process until the receiver is shown.
      Caveat:
-        we poll here for the view to be shown - we need a semaphore
-        which is raised by the view in order to do it right."
+	we poll here for the view to be shown - we need a semaphore
+	which is raised by the view in order to do it right."
 
     |wg|
 
     [self shown] whileFalse:[
-        (device notNil and:[device isOpen not]) ifTrue:[^ self].
-        Delay waitForSeconds:0.05.
-        (wg := self windowGroup) ifNotNil:[
-            wg processExposeEvents.
-        ].
+	(device notNil and:[device isOpen not]) ifTrue:[^ self].
+	Delay waitForSeconds:0.05.
+	(wg := self windowGroup) ifNotNil:[
+	    wg processExposeEvents.
+	].
     ].
 
     "does not work (the view is in its opening phase,
      when we attempt to draw a line - this gives an error, since
      its internals are not yet correctly setup):
 
-        |v|
-
-        v := View new open.
-        v displayLineFrom:0@0 to:50@50
+	|v|
+
+	v := View new open.
+	v displayLineFrom:0@0 to:50@50
 
      does work (since we wait until the view has completely finished
      its startup phase):
 
-        |v|
-
-        v := View new open.
-        v waitUntilVisible.
-        v displayLineFrom:0@0 to:50@50
+	|v|
+
+	v := View new open.
+	v waitUntilVisible.
+	v displayLineFrom:0@0 to:50@50
     "
 ! !
 
@@ -8747,55 +8741,148 @@
 
 !SimpleView::ViewShape methodsFor:'queries'!
 
-isRoundShape
-    ^ false
-! !
+waitForSeconds:0.05.    
+                    mainGroup processExposeEvents.
+
+                    ReturnFocusWhenClosingModalBoxes ifTrue:[
+                        "
+                         return input focus to previously active groups top.
+                         This helps with windowmanagers which need an explicit click
+                         on the view for the focus.
+                        "
+                        tops := mainGroup topViews.
+                        (tops notNil and:[tops notEmpty]) ifTrue:[
+                            tops first getKeyboardFocus
+                        ].
+                    ].
+
+                    "
+                     restore cursors in the main group & flush its buffered key & mouse events
+                    "
+                    mainGroup restoreCursors.
+                    (previousGroup notNil and:[previousGroup ~~ mainGroup]) ifTrue:[
+                        previousGroup restoreCursors.
+                    ].
+"/                    mainGroup sensor flushUserEvents.
+                ]
+            ]
+        ].
+    ]
+
+    "Created: 10.12.1995 / 14:06:14 / cg"
+    "Modified: 20.8.1997 / 15:14:44 / cg"! !
 
 !SimpleView::ArbitraryViewShape methodsFor:'accessing'!
 
-borderShapeForm
-    "return the value of the instance variable 'borderShapeForm' (automatically generated)"
-
-    ^ borderShapeForm
-
-    "Created: 18.9.1997 / 11:04:29 / cg"
-!
-
-borderShapeForm:something
-    "set the value of the instance variable 'borderShapeForm' (automatically generated)"
-
-    borderShapeForm := something.
-
-    "Created: 18.9.1997 / 11:04:29 / cg"
-!
-
-viewShapeForm
-    "return the value of the instance variable 'viewShapeForm' (automatically generated)"
-
-    ^ viewShapeForm
-
-    "Created: 18.9.1997 / 11:04:29 / cg"
-!
-
-viewShapeForm:something
-    "set the value of the instance variable 'viewShapeForm' (automatically generated)"
-
-    viewShapeForm := something.
-
-    "Created: 18.9.1997 / 11:04:29 / cg"
-! !
+ReturnFocusWhenClosingModalBoxes ifTrue:[
+                        "
+                         return input focus to previously active groups top.
+                         This helps with windowmanagers which need an explicit click
+                         on the view for the focus.
+                        "
+                        tops := mainGroup topViews.
+                        (tops notNil and:[tops notEmpty]) ifTrue:[
+                            tops first getKeyboardFocus
+                        ].
+                    ].
+
+                    "
+                     restore cursors in the main group & flush its buffered key & mouse events
+                    "
+                    mainGroup restoreCursors.
+                    (previousGroup notNil and:[previousGroup ~~ mainGroup]) ifTrue:[
+                        previousGroup restoreCursors.
+                    ].
+"/                    mainGroup sensor flushUserEvents.
+                ]
+            ]
+        ].
+    ]
+
+    "Created: 10.12.1995 / 14:06:14 / cg"
+    "Modified: 20.8.1997 / 15:14:44 / cg"!
+
+This helps with windowmanagers which need an explicit click
+                         on the view for the focus.
+                        "
+                        tops := mainGroup topViews.
+                        (tops notNil and:[tops notEmpty]) ifTrue:[
+                            tops first getKeyboardFocus
+                        ].
+                    ].
+
+                    "
+                     restore cursors in the main group & flush its buffered key & mouse events
+                    "
+                    mainGroup restoreCursors.
+                    (previousGroup notNil and:[previousGroup ~~ mainGroup]) ifTrue:[
+                        previousGroup restoreCursors.
+                    ].
+"/                    mainGroup sensor flushUserEvents.
+                ]
+            ]
+        ].
+    ]
+
+    "Created: 10.12.1995 / 14:06:14 / cg"
+    "Modified: 20.8.1997 / 15:14:44 / cg"!
+
+(tops notNil and:[tops notEmpty]) ifTrue:[
+                            tops first getKeyboardFocus
+                        ].
+                    ].
+
+                    "
+                     restore cursors in the main group & flush its buffered key & mouse events
+                    "
+                    mainGroup restoreCursors.
+                    (previousGroup notNil and:[previousGroup ~~ mainGroup]) ifTrue:[
+                        previousGroup restoreCursors.
+                    ].
+"/                    mainGroup sensor flushUserEvents.
+                ]
+            ]
+        ].
+    ]
+
+    "Created: 10.12.1995 / 14:06:14 / cg"
+    "Modified: 20.8.1997 / 15:14:44 / cg"!
+
+.
+
+                    "
+                     restore cursors in the main group & flush its buffered key & mouse events
+                    "
+                    mainGroup restoreCursors.
+                    (previousGroup notNil and:[previousGroup ~~ mainGroup]) ifTrue:[
+                        previousGroup restoreCursors.
+                    ].
+"/                    mainGroup sensor flushUserEvents.
+                ]
+            ]
+        ].
+    ]
+
+    "Created: 10.12.1995 / 14:06:14 / cg"
+    "Modified: 20.8.1997 / 15:14:44 / cg"! !
 
 !SimpleView::RoundViewShape methodsFor:'queries'!
 
-isRoundShape
-    ^ true
-
-
-! !
+sGroup ~~ mainGroup]) ifTrue:[
+                        previousGroup restoreCursors.
+                    ].
+"/                    mainGroup sensor flushUserEvents.
+                ]
+            ]
+        ].
+    ]
+
+    "Created: 10.12.1995 / 14:06:14 / cg"
+    "Modified: 20.8.1997 / 15:14:44 / cg"! !
 
 !SimpleView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview/SimpleView.st,v 1.389 2000-11-06 13:18:33 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libview/SimpleView.st,v 1.390 2000-11-07 13:00:40 cg Exp $'
 ! !
 SimpleView initialize!