SimpleView.st
branchjv
changeset 7286 c3b4c3c664d4
parent 7254 dd5c3a4a295a
parent 7262 cad293885151
child 7287 1e2a3258dd8a
--- a/SimpleView.st	Sun Apr 03 16:05:41 2016 +0100
+++ b/SimpleView.st	Sun Apr 03 17:09:29 2016 +0100
@@ -842,19 +842,20 @@
      If its later realized and no superview has ever been set,
      it will come up as a topview."
 
-    |newView device|
+    |newView viewsDevice|
 
     newView := self basicNew.
     aView notNil ifTrue:[
-	newView initializeForDevice:(aView graphicsDevice).
+        viewsDevice := aView graphicsDevice.
 "/      newView container:aView.
     ] ifFalse:[
-	newView initializeForDevice:Screen current
-    ].
-    (newView device supportsNativeWidgetType:newView nativeWindowType) ifTrue:[
-	newView beNativeWidget.
-	device := Screen current
-    ].
+        viewsDevice := Screen current
+    ].
+    newView device:viewsDevice.
+    (viewsDevice supportsNativeWidgetType:newView nativeWindowType) ifTrue:[
+        newView beNativeWidget
+    ].
+    newView initialize.
     aView notNil ifTrue:[aView addSubView:newView].
     ^ newView
 
@@ -899,14 +900,14 @@
      Used with popUpMenus, which should be created on the device of
      its masterView."
 
-    |device|
+    |viewsDevice|
 
     anotherView notNil ifTrue:[
-	device := anotherView graphicsDevice.
+        viewsDevice := anotherView graphicsDevice.
     ] ifFalse:[
-	device := Screen current.
-    ].
-    ^ self onDevice:device
+        viewsDevice := Screen current.
+    ].
+    ^ self onDevice:viewsDevice
 
     "Modified: 28.5.1996 / 20:25:05 / cg"
 !
@@ -1994,18 +1995,18 @@
     "set the borderShape to aForm"
 
     aForm isNil ifTrue:[
-	viewShape := nil.
-	self drawableId notNil ifTrue:[
-	    self graphicsDevice setWindowBorderShape:nil in:self drawableId
-	]
+        viewShape := nil.
+        self drawableId notNil ifTrue:[
+            device setWindowBorderShape:nil in:self drawableId
+        ]
     ] ifFalse:[
-	viewShape isNil ifTrue:[
-	    viewShape := ArbitraryViewShape new
-	].
-	viewShape borderShapeForm:aForm.
-	self drawableId notNil ifTrue:[
-	    self graphicsDevice setWindowBorderShape:(aForm id) in:self drawableId
-	]
+        viewShape isNil ifTrue:[
+            viewShape := ArbitraryViewShape new
+        ].
+        viewShape borderShapeForm:aForm.
+        self drawableId notNil ifTrue:[
+            device setWindowBorderShape:(aForm id) in:self drawableId
+        ]
     ]
 
     "Modified: 18.9.1997 / 11:09:40 / cg"
@@ -2238,11 +2239,11 @@
     self assert:(something notNil) message:'invalid viewBackground argument'.
 
     something isColor ifTrue:[
-	self graphicsDevice 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
 
@@ -2265,19 +2266,19 @@
     "set the viewShape to aForm"
 
     aForm isNil ifTrue:[
-	viewShape := nil.
-	self drawableId notNil ifTrue:[
-	    self graphicsDevice setWindowShape:nil in:self drawableId
-	]
+        viewShape := nil.
+        self drawableId notNil ifTrue:[
+            device setWindowShape:nil in:self drawableId
+        ]
     ] ifFalse:[
-	viewShape isNil ifTrue:[
-	    viewShape := ArbitraryViewShape new
-	].
-
-	viewShape viewShapeForm:aForm.
-	self drawableId notNil ifTrue:[
-	    self graphicsDevice setWindowShape:(aForm id) in:self drawableId
-	]
+        viewShape isNil ifTrue:[
+            viewShape := ArbitraryViewShape new
+        ].
+
+        viewShape viewShapeForm:aForm.
+        self drawableId notNil ifTrue:[
+            device setWindowShape:(aForm id) in:self drawableId
+        ]
     ]
 
     "Modified: 18.9.1997 / 11:11:04 / cg"
@@ -3000,7 +3001,7 @@
      deviceLeft deviceRight deviceTop deviceBottom origin corner
      referencePoint|
 
-    myDevice := self graphicsDevice.
+    myDevice := device.
 
     newTop := top.
     newLeft := left.
@@ -3090,40 +3091,40 @@
 
     |extent shapeForm borderForm w h f lw|
 
-    self graphicsDevice supportsRoundShapedViews ifTrue:[
-	"/ TODO: add code for round shaped view (mswin)
-    ].
-
-    self graphicsDevice 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:(lw := gc lineWidth) y:lw
-		width:w - (bw * 2)
-	       height:h - (bw * 2)
-		 from:0
-		angle:360.
-
-	self borderShape:borderForm.
-	self viewShape:shapeForm.
-	^ self.
+"/    device supportsRoundShapedViews ifTrue:[
+"/        "/ 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:(lw := gc lineWidth) y:lw
+                width:w - (bw * 2)
+               height:h - (bw * 2)
+                 from:0
+                angle:360.
+
+        self borderShape:borderForm.
+        self viewShape:shapeForm.
+        ^ self.
 
 "/
 "/        extent := self extent.
@@ -3173,29 +3174,29 @@
 "/        "/ TODO: add code for mswin
 "/    ].
 
-    self graphicsDevice 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.
+    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.
     ]
 !
 
@@ -3343,17 +3344,17 @@
     sumX := 0.
     sumY := 0.
     [currentView notNil] whileTrue:[
-	(currentView == aView) ifTrue:[
-	    ^ (sumX @ sumY)
-	].
-	bw := currentView borderWidth.
-	sumX := sumX + (currentView left) + bw.
-	sumY := sumY + (currentView top) + bw.
-	currentView := currentView superView
-    ].
-    (aView isNil or:[aView == self graphicsDevice rootView]) ifTrue:[
-	"return relative to screen ..."
-	^ (sumX @ sumY)
+        (currentView == aView) ifTrue:[
+            ^ (sumX @ sumY)
+        ].
+        bw := currentView borderWidth.
+        sumX := sumX + (currentView left) + bw.
+        sumY := sumY + (currentView top) + bw.
+        currentView := currentView superView
+    ].
+    (aView isNil or:[aView == device rootView]) ifTrue:[
+        "return relative to screen ..."
+        ^ (sumX @ sumY)
     ].
     ^ nil
 
@@ -3792,7 +3793,7 @@
     "bring to back"
 
     self drawableId isNil ifTrue:[self create].
-    self graphicsDevice lowerWindow:self drawableId
+    device lowerWindow:self drawableId
 
     "
      Transcript topView lower
@@ -3809,7 +3810,7 @@
      or mark as #beScreenDialog before opening"
 
     self drawableId isNil ifTrue:[self create].
-    self graphicsDevice raiseWindowToTop:self drawableId
+    device raiseWindowToTop:self drawableId
 
     "
      Transcript topView raise
@@ -3963,14 +3964,14 @@
      the model first, then use the views menu.
     "
     (menuHolder respondsTo:sym) ifFalse:[
-	(self respondsTo:sym) ifTrue:[
-	    menuHolder := self
-	]
+        (self respondsTo:sym) ifTrue:[
+            menuHolder := self
+        ]
     ].
 
     sym numArgs > 0 ifTrue:[
-	"/ squeak compatibility (with args): create the empty menu here, let model add items
-	^ menuHolder perform:sym withOptionalArgument:(Menu new) and:(self graphicsDevice shiftDown).
+        "/ squeak compatibility (with args): create the empty menu here, let model add items
+        ^ menuHolder perform:sym withOptionalArgument:(Menu new) and:(device shiftDown).
     ].
 
     "
@@ -4439,7 +4440,7 @@
      visible."
 
     self beVisible.
-    self graphicsDevice sync.    "that's a round-trip; when returning, the view is definitely visible"
+    device sync.    "that's a round-trip; when returning, the view is definitely visible"
 
 "/    realized := true.
 "/    shown := true.
@@ -4859,11 +4860,11 @@
     "common code for addSubView* methods"
 
     aView container:self.
-    (aView graphicsDevice ~~ self graphicsDevice) ifTrue:[
-	'SimpleView [warning]: subview (' errorPrint. aView class name errorPrint.
-	') has different device than me (' errorPrint.
-	self class name errorPrint. ').' errorPrintCR.
-	aView device:self graphicsDevice
+    (aView graphicsDevice ~~ device) ifTrue:[
+        'SimpleView [warning]: subview (' errorPrint. aView class name errorPrint.
+        ') has different device than me (' errorPrint.
+        self class name errorPrint. ').' errorPrintCR.
+        aView device:device
     ].
 
     "Created: 9.5.1996 / 00:46:59 / cg"
@@ -4940,7 +4941,7 @@
 	cursors := bitmaps collect:[:form | (Cursor sourceForm:form
 						      maskForm:maskForm
 							  hotX:8
-							  hotY:8) onDevice:self graphicsDevice].
+                                                          hotY:8) onDevice:device].
 
 	process := [
 		    Delay waitForSeconds:0.25.
@@ -5335,33 +5336,33 @@
     count == 0 ifTrue:[^ self].
 
     (count < 0) ifTrue:[
-	leftFg := shadowColor.
-	leftHalfFg := halfShadowColor.
-	count := count negated.
+        leftFg := shadowColor.
+        leftHalfFg := halfShadowColor.
+        count := count negated.
     ] ifFalse:[
-	leftFg := lightColor.
-	leftHalfFg := halfLightColor.
+        leftFg := lightColor.
+        leftHalfFg := halfLightColor.
     ].
     leftHalfFg isNil ifTrue:[
-	leftHalfFg := leftFg
+        leftHalfFg := leftFg
     ].
 
     ((edgeStyle == #soft) and:[level > 0]) ifTrue:[
-	paint := leftHalfFg
+        paint := leftHalfFg
     ] ifFalse:[
-	paint := leftFg
+        paint := leftFg
     ].
     super paint:paint.
     super lineWidth:0.
 
     b := height - 1.
     0 to:(count - 1) do:[:i |
-	super displayDeviceLineFromX:i y:i toX:i y:(b - i)
+        super displayDeviceLineFromX:i y:i toX:i y:(b - i)
     ].
 
     ((edgeStyle == #soft) and:[level > 2]) ifTrue:[
-	super paint:(self graphicsDevice blackColor).
-	super displayDeviceLineFromX:0 y:0 toX:0 y:b.
+        super paint:(device blackColor).
+        super displayDeviceLineFromX:0 y:0 toX:0 y:b.
     ].
 
     self edgeDrawn:#left.
@@ -5460,7 +5461,7 @@
         super displayDeviceLineFromX:i y:y+i toX:(r - i) y:y+i
     ].
     ((edgeStyle == #soft) and:[level > 2]) ifTrue:[
-        super paint:(self graphicsDevice blackColor).
+        super paint:(device blackColor).
         super displayDeviceLineFromX:0 y:y+0 toX:r y:y+0.
     ].
 
@@ -5505,7 +5506,7 @@
         super displayDeviceLineFromX:i y:i toX:(r - i) y:i
     ].
     ((edgeStyle == #soft) and:[level > 2]) ifTrue:[
-        super paint:(self graphicsDevice blackColor).
+        super paint:(device blackColor).
         super displayDeviceLineFromX:0 y:0 toX:r y:0.
     ].
 
@@ -5854,74 +5855,74 @@
 
     (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 := self graphicsDevice 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 := 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
-	"
+        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.
-	    ].
+        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:[
@@ -5931,11 +5932,11 @@
 "/                self drawRightEdge
 "/            ].
 "/            self deviceClippingRectangle:innerClipRect
-	]
+        ]
     ].
 
     originChanged ifTrue:[
-	self changed:#origin.
+        self changed:#origin.
     ].
 
     "Modified: / 10.10.2001 / 14:14:19 / cg"
@@ -6089,17 +6090,17 @@
 
     (dropTypeSymbol == WindowEvent dropType_file
     or:[dropTypeSymbol == WindowEvent dropType_directory]) ifTrue:[
-	dropObjects := Array with:(DropObject newFile:dropValue)
+        dropObjects := Array with:(DropObject newFile:dropValue)
     ] ifFalse:[
-	dropTypeSymbol == WindowEvent dropType_files ifTrue:[
-	   dropObjects := (dropValue collect:[:fn | DropObject newFile:fn])
-	] ifFalse:[
-	    dropTypeSymbol == WindowEvent dropType_text ifTrue:[
-	       dropObjects := Array with:(DropObject newText:dropValue)
-	    ] ifFalse:[
-	       dropObjects := Array with:(DropObject new:dropValue)
-	    ]
-	]
+        dropTypeSymbol == WindowEvent dropType_files ifTrue:[
+           dropObjects := (dropValue collect:[:fn | DropObject newFile:fn])
+        ] ifFalse:[
+            dropTypeSymbol == WindowEvent dropType_text ifTrue:[
+               dropObjects := Array with:(DropObject newText:dropValue)
+            ] ifFalse:[
+               dropObjects := Array with:(DropObject new:dropValue)
+            ]
+        ]
     ].
 
 "/    Transcript showCR:'Drop:'.
@@ -6108,7 +6109,7 @@
 "/    Transcript show:'  Data:'; showCR:dropObjects.
 
     self alienDrop:dropObjects position:dropPosition.
-    self graphicsDevice dragFinish:dropHandle.
+    device dragFinish:dropHandle.
 
     "Modified: / 13-10-2006 / 10:10:23 / cg"
 !
@@ -6997,8 +6998,8 @@
 
     sendDisplayEvent ifTrue:[
         "/ translate to screen coordinates
-        pointXLated := self device translatePoint:aPoint from:(self id) to:(self device rootWindowId).
-        self device 
+        pointXLated := device translatePoint:aPoint from:(self id) to:(device rootWindowId).
+        device 
             sendKeyOrButtonEvent:ev type 
             x:pointXLated x y:pointXLated y 
             keyOrButton:(ev isKeyEvent ifTrue:[ev rawKey] ifFalse:[ev button])
@@ -7021,7 +7022,7 @@
             self subViews do:[:each |
                 |whichView|
 
-                whichView := each simulateUserEvent:ev at:(self graphicsDevice translatePoint:aPoint fromView:self toView:each).
+                whichView := each simulateUserEvent:ev at:(device translatePoint:aPoint fromView:self toView:each).
                 whichView notNil ifTrue:[^ whichView].
             ].
             targetView := self.
@@ -7029,7 +7030,7 @@
     ].
 
     targetView notNil ifTrue:[
-        pointXLated := self device translatePoint:aPoint fromView:self toView:targetView.
+        pointXLated := device translatePoint:aPoint fromView:self toView:targetView.
         ev x:(pointXLated x).
         ev y:(pointXLated y).
         ev view:targetView.
@@ -7051,15 +7052,15 @@
 
     self stopButtonLongPressedHandlerProcess.
     p :=
-	[
-	    Delay waitForSeconds:0.7.
-	    self sensor leftButtonPressed ifTrue:[
-		"/ simulate a right-button press
-		self buttonPress:2 x:0 y:0
-	    ]
-	] newProcess.
-
-    self graphicsDevice buttonLongPressedHandlerProcess:p.
+        [
+            Delay waitForSeconds:0.7.
+            self sensor leftButtonPressed ifTrue:[
+                "/ simulate a right-button press
+                self buttonPress:2 x:0 y:0
+            ]
+        ] newProcess.
+
+    device buttonLongPressedHandlerProcess:p.
     p resume.
 !
 
@@ -7068,10 +7069,10 @@
 
     |p|
 
-    (p := self graphicsDevice buttonLongPressedHandlerProcess) notNil ifTrue:[
+    (p := device buttonLongPressedHandlerProcess) notNil ifTrue:[
 "/ Transcript showCR:'stop'.
-	self graphicsDevice buttonLongPressedHandlerProcess:nil.
-	p terminate.
+        device buttonLongPressedHandlerProcess:nil.
+        p terminate.
     ].
 ! !
 
@@ -7082,7 +7083,7 @@
 
     wg := self windowGroup.
     wg notNil ifTrue:[
-        self graphicsDevice isWindowsPlatform ifTrue:[
+        device isWindowsPlatform ifTrue:[
             wg focusView:aConsumer byTab:true.
         ] ifFalse:[
             aConsumer requestFocus.
@@ -7352,7 +7353,7 @@
 	and:[superView notNil
 	and:[styleSheet notNil]]) ifTrue:[
 	    (styleSheet at:#'focus.showBorder' default:true) ifTrue:[
-		graphicsDevice := self graphicsDevice.
+                graphicsDevice := device.
 
 		(graphicsDevice supportsWindowBorder:(bd := DefaultFocusBorderWidth)) ifFalse:[
 		    (graphicsDevice supportsWindowBorder:(bd := 1)) ifFalse:[
@@ -7396,7 +7397,7 @@
     explicit ifTrue:[
 	(self drawableId notNil and:[superView notNil]) ifTrue:[
 	    (styleSheet at:#'focus.showBorder' default:true) ifTrue:[
-		graphicsDevice := self graphicsDevice.
+                graphicsDevice := device.
 
 		(graphicsDevice supportsWindowBorder:(bd := self borderWidth)) ifFalse:[
 		    (graphicsDevice supportsWindowBorder:(bd := 1)) ifFalse:[
@@ -7495,13 +7496,13 @@
 forceUngrabKeyboard
     "force a keyboard ungrab - even if was not the grabber"
 
-    self graphicsDevice ungrabKeyboard.
+    device ungrabKeyboard.
 !
 
 forceUngrabPointer
     "force a pointer ungrab - even if was not the grabber"
 
-    self graphicsDevice ungrabPointer
+    device ungrabPointer
 !
 
 grabKeyboard
@@ -7510,7 +7511,7 @@
      Returns true, if the grab was sucessfull (could fail, if some other
      application has a grab - but thats very unlikely)."
 
-    ^ self graphicsDevice grabKeyboardInView:self.
+    ^ device grabKeyboardInView:self.
 !
 
 grabPointer
@@ -7537,12 +7538,11 @@
 "/        "/ now, flush all pointer events
 "/        sensor flushMotionEventsFor:nil
 "/    ].
-
     aCursorOrNil notNil ifTrue:[
-	cursor := (aCursorOrNil onDevice:self graphicsDevice).
-	^ self graphicsDevice grabPointerInView:self withCursor:cursor
-    ].
-    ^ self graphicsDevice grabPointerInView:self
+        cursor := (aCursorOrNil onDevice:device).
+        ^ device grabPointerInView:self withCursor:cursor
+    ].
+    ^ device grabPointerInView:self
 !
 
 ungrabKeyboard
@@ -7550,15 +7550,15 @@
 
     |sensor|
 
-    self graphicsDevice activeKeyboardGrab == self ifTrue:[
-	(sensor := self sensor) notNil ifTrue:[
-	    "/ make certain all X events have been received
-	    self graphicsDevice sync.
-	    "/ now all events have been received.
-	    "/ now, flush all pointer events
-	    sensor flushKeyboardFor:self
-	].
-	self graphicsDevice ungrabKeyboard.
+    device activeKeyboardGrab == self ifTrue:[
+        (sensor := self sensor) notNil ifTrue:[
+            "/ make certain all X events have been received
+            device sync.
+            "/ now all events have been received.
+            "/ now, flush all pointer events
+            sensor flushKeyboardFor:self
+        ].
+        device ungrabKeyboard.
     ].
 !
 
@@ -7567,15 +7567,15 @@
 
     |sensor|
 
-    self graphicsDevice activePointerGrab == self ifTrue:[
-	(sensor := self sensor) notNil ifTrue:[
-	    "/ make certain all X events have been received
-	    self graphicsDevice sync.
-	    "/ now all events have been received.
-	    "/ now, flush all pointer events
-	    sensor flushMotionEventsFor:self
-	].
-	self graphicsDevice ungrabPointer.
+    device activePointerGrab == self ifTrue:[
+        (sensor := self sensor) notNil ifTrue:[
+            "/ make certain all X events have been received
+            device sync.
+            "/ now all events have been received.
+            "/ now, flush all pointer events
+            sensor flushMotionEventsFor:self
+        ].
+        device ungrabPointer.
     ]
 ! !
 
@@ -7705,32 +7705,32 @@
     viewBackground := DefaultViewBackgroundColor.
 
     DefaultLightColor notNil ifTrue:[
-	lightColor := DefaultLightColor.
+        lightColor := DefaultLightColor.
     ] ifFalse:[
-	self graphicsDevice hasGrayscales ifTrue:[
-	    (viewBackground isImageOrForm and:[viewBackground colorMap isNil]) ifTrue:[
-		lightColor := viewBackground averageColor lightened.
-	    ] ifFalse:[
-		lightColor := viewBackground lightened.
-	    ].
-	    DefaultLightColor := lightColor.
-	] ifFalse:[
-	    "
-	     this seems strange: on B&W screens, we create the light color
-	     darker than normal viewBackground (White) -
-	     to make the boundary of the view visible
-	    "
-	    lightColor := Color gray:50
-	]
+        device hasGrayscales ifTrue:[
+            (viewBackground isImageOrForm and:[viewBackground colorMap isNil]) ifTrue:[
+                lightColor := viewBackground averageColor lightened.
+            ] ifFalse:[
+                lightColor := viewBackground lightened.
+            ].
+            DefaultLightColor := lightColor.
+        ] ifFalse:[
+            "
+             this seems strange: on B&W screens, we create the light color
+             darker than normal viewBackground (White) -
+             to make the boundary of the view visible
+            "
+            lightColor := Color gray:50
+        ]
     ].
     DefaultShadowColor notNil ifTrue:[
-	shadowColor := DefaultShadowColor.
+        shadowColor := DefaultShadowColor.
     ] ifFalse:[
-	shadowColor := self blackColor.
+        shadowColor := self blackColor.
     ].
 
     ((DefaultBorderWidth ? 1) ~= 0 and:[DefaultBorderColor notNil]) ifTrue:[
-	self border:(SimpleBorder width:(DefaultBorderWidth ? 1) color:DefaultBorderColor)
+        self border:(SimpleBorder width:(DefaultBorderWidth ? 1) color:DefaultBorderColor)
     ].
 
     "/ font := self defaultFont.  -- already done in #initialize
@@ -7859,16 +7859,16 @@
 
     "if I have already been reinited - return"
     self drawableId notNil ifTrue:[
-	^ self
+        ^ self
     ].
 
     "
      superView must be there, first
     "
     superView notNil ifTrue:[
-	(sv := superView view) id isNil ifTrue:[
-	    sv reinitialize
-	]
+        (sv := superView view) id isNil ifTrue:[
+            sv reinitialize
+        ]
     ].
 
     "reinit cursor"
@@ -7880,18 +7880,18 @@
 
     "if I was mapped, do it again"
     realized ifTrue:[
-	"only remap if I have a superview - otherwise, I might be
-	 a hidden iconView or menu ..."
-	superView notNil ifTrue:[
+        "only remap if I have a superview - otherwise, I might be
+         a hidden iconView or menu ..."
+        superView notNil ifTrue:[
 "/            shown ifTrue:[
-	    self graphicsDevice
-		moveResizeWindow:self drawableId x:left y:top width:width height:height;
-		mapWindow:self drawableId
+            device
+                moveResizeWindow:self drawableId x:left y:top width:width height:height;
+                mapWindow:self drawableId
 "/                mapView:self id:self drawableId iconified:false
 "/                atX:left y:top width:width height:height
 "/                minExtent:(self minExtent) maxExtent:(self maxExtent)
 "/            ].
-	].
+        ].
     ].
 
     "restore controller"
@@ -8375,17 +8375,17 @@
     |subViews|
 
     (subViews := self subViews) notNil ifTrue:[
-	subViews do:[:v| |p|
-	    (ignoreInvisible or:[v shown]) ifTrue:[
-		(    (aPoint x between:(v left) and:(v right))
-		 and:[aPoint y between:(v top)  and:(v bottom)]
-		) ifTrue:[
-		    "/ found a subview - the point is there
-		    p := self graphicsDevice translatePoint:aPoint fromView:self toView:v.
-		    ^ v detectViewAt:p ignoreInvisible:ignoreInvisible.
-		]
-	    ]
-	]
+        subViews do:[:v| |p|
+            (ignoreInvisible or:[v shown]) ifTrue:[
+                (    (aPoint x between:(v left) and:(v right))
+                 and:[aPoint y between:(v top)  and:(v bottom)]
+                ) ifTrue:[
+                    "/ found a subview - the point is there
+                    p := device translatePoint:aPoint fromView:self toView:v.
+                    ^ v detectViewAt:p ignoreInvisible:ignoreInvisible.
+                ]
+            ]
+        ]
     ].
     "/ no subview - the point is here
     ^ self
@@ -8417,50 +8417,50 @@
     bw := self borderWidth ? 0.
 
     superView isNil ifTrue:[
-	inRect := 0@0 extent:self graphicsDevice extent
+        inRect := 0@0 extent:device extent
     ] ifFalse:[
-	inRect := superView viewRectangle.
+        inRect := superView viewRectangle.
     ].
 
     bw2 := bw * 2.
 
     rel := aPoint x.
     rel isInteger ifFalse:[
-	newX := (rel * (inRect width + bw2)) asInteger + inRect left.
-	(bw ~~ 0) ifTrue:[
-	    newX := newX - bw
-	].
+        newX := (rel * (inRect width + bw2)) asInteger + inRect left.
+        (bw ~~ 0) ifTrue:[
+            newX := newX - bw
+        ].
     ] ifTrue:[
-	newX := rel
+        newX := rel
     ].
 
     rel := aPoint y.
     rel isInteger ifFalse:[
-	newY := (rel * (inRect height + bw2)) asInteger + inRect top.
-	(bw ~~ 0) ifTrue:[
-	    newY := newY - bw
-	].
+        newY := (rel * (inRect height + bw2)) asInteger + inRect top.
+        (bw ~~ 0) ifTrue:[
+            newY := newY - bw
+        ].
     ] ifTrue:[
-	newY := rel
+        newY := rel
     ].
 
     insets notNil ifTrue:[
-	i := insets at:1.   "top"
-	(i  ~~ 0) ifTrue:[
-	    newX := newX - i
-	].
-	i := insets at:3.   "left"
-	(i  ~~ 0) ifTrue:[
-	    newX := newX - i
-	].
-	i := insets at:2.   "right"
-	(i ~~ 0) ifTrue:[
-	    newY := newY - i
-	].
-	i := insets at:4.   "bottom"
-	(i ~~ 0) ifTrue:[
-	    newY := newY - i
-	].
+        i := insets at:1.   "top"
+        (i  ~~ 0) ifTrue:[
+            newX := newX - i
+        ].
+        i := insets at:3.   "left"
+        (i  ~~ 0) ifTrue:[
+            newX := newX - i
+        ].
+        i := insets at:2.   "right"
+        (i ~~ 0) ifTrue:[
+            newY := newY - i
+        ].
+        i := insets at:4.   "bottom"
+        (i ~~ 0) ifTrue:[
+            newY := newY - i
+        ].
     ].
     ^ newX @ newY
 !
@@ -8546,7 +8546,7 @@
         "/ (otherwise, we could not move unmapped views around ...
         "/
         self drawableId notNil ifTrue:[
-            self graphicsDevice moveWindow:self drawableId x:left y:top
+            device moveWindow:self drawableId x:left y:top
         ] ifFalse:[
             self originChangedFlag:true
         ]
@@ -8661,19 +8661,19 @@
 
         "have to tell X, when extent of view is changed"
         sameOrigin ifTrue:[
-            self graphicsDevice resizeWindow:self drawableId width:width height:height.
+            device resizeWindow:self drawableId width:width height:height.
         ] ifFalse:[
             "claus: some xservers seem to do better when resizing
              first ...."
 "
             (how == #smaller) ifTrue:[
-                self graphicsDevice resizeWindow:drawableId width:width height:height.
-                self graphicsDevice moveWindow:drawableId x:left y:top
+                device resizeWindow:drawableId width:width height:height.
+                device moveWindow:drawableId x:left y:top
             ] ifFalse:[
-                self graphicsDevice moveResizeWindow:drawableId x:left y:top width:width height:height
+                device moveResizeWindow:drawableId x:left y:top width:width height:height
             ].
 "
-            self graphicsDevice moveResizeWindow:self drawableId x:left y:top
+            device moveResizeWindow:self drawableId x:left y:top
                                            width:width height:height.
         ].
 
@@ -8756,39 +8756,39 @@
     bw := self borderWidth ? 0.
 
     superView isNil ifTrue:[
-	superWidth := self graphicsDevice width + bw.
-	superHeight := self graphicsDevice height + bw.
-	superLeft := superTop := 0.
+        superWidth := device width + bw.
+        superHeight := device height + bw.
+        superLeft := superTop := 0.
     ] ifFalse:[
-	inRect := superView viewRectangle.
-	superWidth := inRect width.
-	superHeight := inRect height.
-	superLeft := inRect left.
-	superTop := inRect top.
+        inRect := superView viewRectangle.
+        superWidth := inRect width.
+        superHeight := inRect height.
+        superLeft := inRect left.
+        superTop := inRect top.
     ].
 
     rel := p x.
     rel isInteger ifTrue:[
-	newX := rel
+        newX := rel
     ] ifFalse:[
-	newX := (rel * superWidth) asInteger + superLeft.
-	(bw ~~ 0) ifTrue:[
-	    rel ~= 1.0 ifTrue:[
-		newX := newX - bw
-	    ]
-	]
+        newX := (rel * superWidth) asInteger + superLeft.
+        (bw ~~ 0) ifTrue:[
+            rel ~= 1.0 ifTrue:[
+                newX := newX - bw
+            ]
+        ]
     ].
 
     rel := p y.
     rel isInteger ifTrue:[
-	newY := rel
+        newY := rel
     ] ifFalse:[
-	newY := (rel * superHeight) asInteger + superTop.
-	(bw ~~ 0) ifTrue:[
-	    rel ~= 1.0 ifTrue:[
-		newY := newY - bw
-	    ]
-	]
+        newY := (rel * superHeight) asInteger + superTop.
+        (bw ~~ 0) ifTrue:[
+            rel ~= 1.0 ifTrue:[
+                newY := newY - bw
+            ]
+        ]
     ].
     ^ newX @ newY
 
@@ -8864,22 +8864,22 @@
     "/ focusViewInWindowGroup := windowGroup focusView.
     "/ focusViewToCheck := focusViewInWindowGroup.
 
-    focusViewOnDisplay := self graphicsDevice focusView.
+    focusViewOnDisplay := device focusView.
     focusViewToCheck := focusViewOnDisplay.
 
     focusViewToCheck == self ifTrue:[ ^ true ].
 
     focusViewToCheck notNil ifTrue:[
-	(focusViewToCheck isComponentOf: self) ifTrue:[ ^ true ].
-
-	"mhmh - is there a delegation to me ?"
-	(delegate := focusViewToCheck delegate) notNil ifTrue:[
-	    delegate == self ifTrue:[^ true].
-	    "/ no: delegate does not understand this (EnterFieldGroup or KbdForwarder)
-	    "/ we will see, if commenting this leads to problems...
-	    "/ (delegate isComponentOf: self) ifTrue:[ ^ true ].
-	    ^ delegate askFor:#delegatesTo: with:self
-	]
+        (focusViewToCheck isComponentOf: self) ifTrue:[ ^ true ].
+
+        "mhmh - is there a delegation to me ?"
+        (delegate := focusViewToCheck delegate) notNil ifTrue:[
+            delegate == self ifTrue:[^ true].
+            "/ no: delegate does not understand this (EnterFieldGroup or KbdForwarder)
+            "/ we will see, if commenting this leads to problems...
+            "/ (delegate isComponentOf: self) ifTrue:[ ^ true ].
+            ^ delegate askFor:#delegatesTo: with:self
+        ]
     ].
     ^ false
 
@@ -8995,17 +8995,17 @@
     "/ focusViewInWindowGroup := windowGroup focusView.
     "/ focusViewToCheck := focusViewInWindowGroup.
 
-    focusViewOnDisplay := self graphicsDevice focusView.
+    focusViewOnDisplay := device focusView.
     focusViewToCheck := focusViewOnDisplay.
 
     focusViewToCheck == self ifTrue:[ ^ true ].
 
     focusViewToCheck notNil ifTrue:[
-	"mhmh - is there a delegation to me ?"
-	(delegate := focusViewToCheck delegate) notNil ifTrue:[
-	    delegate == self ifTrue:[^ true].
-	    ^ delegate askFor:#delegatesTo: with:self
-	]
+        "mhmh - is there a delegation to me ?"
+        (delegate := focusViewToCheck delegate) notNil ifTrue:[
+            delegate == self ifTrue:[^ true].
+            ^ delegate askFor:#delegatesTo: with:self
+        ]
     ].
     ^ false
 
@@ -9474,11 +9474,11 @@
      This does not make the view visible (needs a #map for that)"
 
     self drawableId isNil ifTrue:[
-	"
-	 make certain that superview is created also
-	"
-	superView notNil ifTrue:[
-	     superView view create.
+        "
+         make certain that superview is created also
+        "
+        superView notNil ifTrue:[
+             superView view create.
 
 "/            "and put my controller into the superviews controller list"
 "/            controller notNil ifTrue:[
@@ -9486,42 +9486,42 @@
 "/                    controller manager:(superView controller manager)
 "/                ]
 "/            ]
-	] ifFalse:[
-	    "/
-	    "/ if the display is not already dispatching events,
-	    "/ this starts the event process.
-	    "/
-	    self graphicsDevice startDispatch
-	].
-
-	cursor notNil ifTrue:[
-	    cursor := cursor onDevice:self graphicsDevice.
-	].
-
-	self extentChangedBeforeCreatedFlag ifTrue:[
-	    "/ this is true, if the extent was changed before
-	    "/ this view was created (and therefore, no sizeChangeEvent
-	    "/ was sent to me, which would notify children.)
-	    "/ have to do this here.
-	    self sizeChanged:nil.   "/ must tell children (if any)
-	].
-	self hasExplicitExtent ifFalse:[
-	    self resize
-	].
-
-	self physicalCreate.
-
-	viewBackground notNil ifTrue:[
-	   self setViewBackground
-	].
-
-	self initEvents.
-
-	"
-	 this is the first create,
-	 force sizechange messages to be sent to the view
-	"
-	self originChangedFlag:true extentChangedFlag:true
+        ] ifFalse:[
+            "/
+            "/ if the display is not already dispatching events,
+            "/ this starts the event process.
+            "/
+            device startDispatch
+        ].
+
+        cursor notNil ifTrue:[
+            cursor := cursor onDevice:device.
+        ].
+
+        self extentChangedBeforeCreatedFlag ifTrue:[
+            "/ this is true, if the extent was changed before
+            "/ this view was created (and therefore, no sizeChangeEvent
+            "/ was sent to me, which would notify children.)
+            "/ have to do this here.
+            self sizeChanged:nil.   "/ must tell children (if any)
+        ].
+        self hasExplicitExtent ifFalse:[
+            self resize
+        ].
+
+        self physicalCreate.
+
+        viewBackground notNil ifTrue:[
+           self setViewBackground
+        ].
+
+        self initEvents.
+
+        "
+         this is the first create,
+         force sizechange messages to be sent to the view
+        "
+        self originChangedFlag:true extentChangedFlag:true
     ]
 
     "Modified: 28.3.1997 / 13:50:17 / cg"
@@ -9546,15 +9546,11 @@
      but possibly slower, since resources are reallocated over and over.
      If you redefine this method, make certain that 'super fetchDeviceResources'
      is always sent."
-
-    |device|
     
     shadowColor notNil ifTrue:[
-        device := self graphicsDevice.
         shadowColor := shadowColor onDevice:device
     ].
     lightColor notNil ifTrue:[
-        device isNil ifTrue:[ device := self graphicsDevice].
         lightColor := lightColor onDevice:device
     ].
 
@@ -9611,7 +9607,7 @@
                 self originFromRelativeOrigin:relativeOrigin
             ] ifFalse:[
                 shown ifTrue:[
-                    self graphicsDevice moveWindow:self drawableId x:left y:top.
+                    device moveWindow:self drawableId x:left y:top.
                 ] ifFalse:[
                     self pixelOrigin:left@top
                 ].
@@ -9712,61 +9708,61 @@
      (unless you have a dictator as windowManager ;-).
      If the iconified argument is true, the window is created as icon initially.
      Notice:
-	Actually, this method is only valid for topViews;
-	however, it is defined here to allow things like 'Button new realize'"
+        Actually, this method is only valid for topViews;
+        however, it is defined here to allow things like 'Button new realize'"
 
     |subs|
 
     realized ifFalse:[
-	self drawableId isNil ifTrue:[
-	    "
-	     first time ?
-	     yes, realize (implies a map)
-	    "
-	    self realizeKeepingGroup:false at:aPoint iconified:iconified
-	] ifFalse:[
-	    "
-	     no, map only
-	    "
-	    realized := true.
-	    aPoint isNil ifTrue:[
-		iconified ifTrue:[
-		    self graphicsDevice
-			mapView:self id:self drawableId iconified:iconified
-			atX:0 y:0
-			width:width height:height
-			minExtent:(self minExtent) maxExtent:(self maxExtent).
-		] ifFalse:[
-		    self graphicsDevice mapWindow:self drawableId.
-		]
-	    ] ifFalse:[
-		left := aPoint x.
-		top := aPoint y.
-		self graphicsDevice
-		    mapView:self id:self drawableId iconified:iconified
-		    atX:left y:top
-		    width:width height:height
-		    minExtent:(self minExtent) maxExtent:(self maxExtent).
-	    ].
-
-	    "/
-	    "/ implies that all realized subviews
-	    "/ are now also mapped
-	    "/
-	    "/ not needed for topViews - the mapped event does exactly the same
-	    "/ however, X does not generate mapped events for non-topViews
-	    "/ when a view gets deiconified.
-
-	    superView notNil ifTrue:[
-		(subs := self subViews) notNil ifTrue:[
-		    subs do:[:v |
-			v realized "shown" ifFalse:[
-			    v mapped
-			]
-		    ]
-		]
-	    ]
-	].
+        self drawableId isNil ifTrue:[
+            "
+             first time ?
+             yes, realize (implies a map)
+            "
+            self realizeKeepingGroup:false at:aPoint iconified:iconified
+        ] ifFalse:[
+            "
+             no, map only
+            "
+            realized := true.
+            aPoint isNil ifTrue:[
+                iconified ifTrue:[
+                    device
+                        mapView:self id:self drawableId iconified:iconified
+                        atX:0 y:0
+                        width:width height:height
+                        minExtent:(self minExtent) maxExtent:(self maxExtent).
+                ] ifFalse:[
+                    device mapWindow:self drawableId.
+                ]
+            ] ifFalse:[
+                left := aPoint x.
+                top := aPoint y.
+                device
+                    mapView:self id:self drawableId iconified:iconified
+                    atX:left y:top
+                    width:width height:height
+                    minExtent:(self minExtent) maxExtent:(self maxExtent).
+            ].
+
+            "/
+            "/ implies that all realized subviews
+            "/ are now also mapped
+            "/
+            "/ not needed for topViews - the mapped event does exactly the same
+            "/ however, X does not generate mapped events for non-topViews
+            "/ when a view gets deiconified.
+
+            superView notNil ifTrue:[
+                (subs := self subViews) notNil ifTrue:[
+                    subs do:[:v |
+                        v realized "shown" ifFalse:[
+                            v mapped
+                        ]
+                    ]
+                ]
+            ]
+        ].
     ]
 
     "Modified: 23.8.1996 / 14:53:55 / stefan"
@@ -10043,22 +10039,22 @@
     "recreate (i.e. tell X about me) after a snapin or a migration"
 
     self 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
-	"
-	eventMask isNil ifTrue:[
-	    eventMask := self graphicsDevice defaultEventMask
-	].
-	self graphicsDevice setEventMask:eventMask in:self 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
+        "
+        eventMask isNil ifTrue:[
+            eventMask := device defaultEventMask
+        ].
+        device setEventMask:eventMask in:self drawableId
     ]
 !
 
@@ -10086,14 +10082,14 @@
      are known to ignore this ..."
 
     realized ifFalse:[
-	"
-	 now, make the view visible
-	"
-	realized := true.
-	self graphicsDevice
-	    mapView:self id:self drawableId iconified:false
-	    atX:left y:top width:width height:height
-	    minExtent:(self minExtent) maxExtent:(self maxExtent)
+        "
+         now, make the view visible
+        "
+        realized := true.
+        device
+            mapView:self id:self drawableId iconified:false
+            atX:left y:top width:width height:height
+            minExtent:(self minExtent) maxExtent:(self maxExtent)
     ]
 
     "Created: 8.5.1996 / 09:33:06 / cg"
@@ -10134,17 +10130,17 @@
     "rerealize myself with all subviews"
 
     self drawableId notNil ifTrue:[
-	realized := true.
-	self realizeAllSubViews.
-	superView isNil ifTrue:[
-	    self graphicsDevice
-		mapView:self id:self drawableId iconified:false
-		atX:left y:top width:width height:height
-		minExtent:(self minExtent) maxExtent:(self maxExtent)
-	] ifFalse:[
-	    self graphicsDevice
-		mapWindow:self drawableId
-	].
+        realized := true.
+        self realizeAllSubViews.
+        superView isNil ifTrue:[
+            device
+                mapView:self id:self drawableId iconified:false
+                atX:left y:top width:width height:height
+                minExtent:(self minExtent) maxExtent:(self maxExtent)
+        ] ifFalse:[
+            device
+                mapWindow:self drawableId
+        ].
     ]
 
     "Modified: 28.1.1997 / 17:59:28 / cg"
@@ -10176,24 +10172,24 @@
     "unmap the view - the view stays created (but invisible), and can be remapped again later."
 
     realized ifTrue:[
-	realized := false.
-	self drawableId notNil ifTrue:[
-	    self graphicsDevice unmapWindow:self drawableId.
-
-	    "/ make it go away immediately
-	    "/ (this hides the subview killing)
-	    self flush.
-	].
-
-	"/ Normally, this is not correct with X, where the
-	"/ unmap is an asynchronous operation.
-	"/ (shown is cleared also in unmapped event)
-	"/ Do it anyway, to avoid synchronisation problems.
-
-	shown ifTrue:[
-	    shown := false.
-	    self changed:#visibility.
-	]
+        realized := false.
+        self drawableId notNil ifTrue:[
+            device unmapWindow:self drawableId.
+
+            "/ make it go away immediately
+            "/ (this hides the subview killing)
+            self flush.
+        ].
+
+        "/ Normally, this is not correct with X, where the
+        "/ unmap is an asynchronous operation.
+        "/ (shown is cleared also in unmapped event)
+        "/ Do it anyway, to avoid synchronisation problems.
+
+        shown ifTrue:[
+            shown := false.
+            self changed:#visibility.
+        ]
     ].
 
     "
@@ -10203,9 +10199,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.
@@ -10540,12 +10536,12 @@
     self clippingRectangle:area.
 
     self clearExposedAreaInRedraw ifTrue:[
-	"/ win95 workaround: non-existing bg-pixmap support (obsolete)
-	(viewBackground isImageOrForm and:[ self graphicsDevice supportsAnyViewBackgroundPixmaps not ]) ifTrue:[
-	    self fillRectangleWithViewBackgroundX:x y:y width:w height:h
-	] ifFalse:[
-	    self clearRectangleX:x y:y width:w height:h.
-	]
+        "/ win95 workaround: non-existing bg-pixmap support (obsolete)
+        (viewBackground isImageOrForm and:[ device supportsAnyViewBackgroundPixmaps not ]) ifTrue:[
+            self fillRectangleWithViewBackgroundX:x y:y width:w height:h
+        ] ifFalse:[
+            self clearRectangleX:x y:y width:w height:h.
+        ]
     ].
 
     self renderOrRedraw.
@@ -10621,7 +10617,7 @@
     "return the amount to scroll when stepping left/right.
      Subclasses may want to redefine this."
 
-    ^ (self graphicsDevice horizontalPixelPerMillimeter * 20) asInteger
+    ^ (device horizontalPixelPerMillimeter * 20) asInteger
 !
 
 pageDown
@@ -10847,7 +10843,7 @@
     "return the amount to scroll when stepping up/down (also used for mouseWheel).
      Subclasses may want to redefine this."
 
-    ^ (self graphicsDevice verticalPixelPerMillimeter * 20) asInteger
+    ^ (device verticalPixelPerMillimeter * 20) asInteger
 !
 
 widthForScrollBetween:yStart and:yEnd
@@ -11273,7 +11269,7 @@
 	    ^ self
 	].
 	"/ the following allows for hooks to add a bell sound or other whenever a dialog opens
-	self graphicsDevice modalWindowListenersDo:[:listener | listener aboutToOpenWindow:self].
+        device modalWindowListenersDo:[:listener | listener aboutToOpenWindow:self].
 
 	"/ the following raises the corresponding mainview, so the dialog shows above
 	"/ any currently covered view. However, be careful if being debugged, or if this dialog
@@ -11297,7 +11293,7 @@
 	     This is currently used for X, to tell the Window Manager
 	     That this view should be always on top of the mainView"
 	    self drawableId isNil ifTrue:[self create].
-	    self graphicsDevice setTransient:self drawableId for:mainView id.
+            device setTransient:self drawableId for:mainView id.
 	]
     ].
 
@@ -11408,7 +11404,7 @@
     "open up the view modeless - positions the view
      (i.e. circumvents window managers positioning)"
 
-    ^ self openModalAt:(self graphicsDevice centerOfMonitorHavingPointer - (self extent//2)).
+    ^ self openModalAt:(device centerOfMonitorHavingPointer - (self extent//2)).
 
     "
      View new openModal
@@ -11421,7 +11417,7 @@
 !
 
 openModalAtPointer
-    ^ self openModalAt:(self graphicsDevice pointerPosition)
+    ^ self openModalAt:(device pointerPosition)
 
     "
      View new openModalAtPointer
@@ -11491,25 +11487,25 @@
     self drawableId isNil ifTrue:[self create].
 
     windowGroup isNil ifTrue:[
-	newGroup := true.
-	windowGroup := self windowGroupClass new.
+        newGroup := true.
+        windowGroup := self windowGroupClass new.
     ] ifFalse:[
-	newGroup := false.
+        newGroup := false.
     ].
 
     windowGroup addTopView:self.
 
     "/ the following allows for hooks to be informed whenever a non-modal view opens
-    self graphicsDevice nonModalWindowListenersDo:[:listener | listener aboutToOpenWindow:self].
+    device nonModalWindowListenersDo:[:listener | listener aboutToOpenWindow:self].
 
     newGroup ifTrue:[
-	(aPoint isNil and:[iconified not]) ifTrue:[
-	    windowGroup startupWith:[self realize].
-	] ifFalse:[
-	    windowGroup startupWith:[self realizeKeepingGroup:false at:aPoint iconified:iconified].
-	].
+        (aPoint isNil and:[iconified not]) ifTrue:[
+            windowGroup startupWith:[self realize].
+        ] ifFalse:[
+            windowGroup startupWith:[self realizeKeepingGroup:false at:aPoint iconified:iconified].
+        ].
     ] ifFalse:[
-	self realizeInGroup.
+        self realizeInGroup.
     ].
 
     "
@@ -11528,7 +11524,7 @@
     "open up the view modeless - positions the view
      (i.e. circumvents window managers positioning)"
 
-    ^ self openModelessAt:(self graphicsDevice centerOfMonitorHavingPointer - (self extent//2)).
+    ^ self openModelessAt:(device centerOfMonitorHavingPointer - (self extent//2)).
 
     "
      View new openModeless
@@ -11545,7 +11541,7 @@
      The view will be handled by its own process, effectively running in
      parallel (i.e. control is returned to the sender immediately)."
 
-    self openModelessAt:(self graphicsDevice pointerPosition)
+    self openModelessAt:(device pointerPosition)
 
     "
      (Button label:'hello') openModelessAtPointer
@@ -11585,7 +11581,7 @@
 
     n := 0.
     [self shown] whileFalse:[
-        (self graphicsDevice notNil and:[self graphicsDevice isOpen not]) ifTrue:[^ self].
+        (device notNil and:[device isOpen not]) ifTrue:[^ self].
 
         "/ this was added to avoid a deadlock, when called from within
         "/ the event dispatch process (as when doing foo inspect there).