DisplaySurface.st
branchdelegated_gc
changeset 6472 5b21ff383a12
parent 6240 f38855c7fec3
child 6524 1647b1f4874a
child 6572 1bdb5a2b47c8
--- a/DisplaySurface.st	Thu Feb 06 12:50:14 2014 +0100
+++ b/DisplaySurface.st	Thu May 08 10:27:51 2014 +0200
@@ -9,6 +9,8 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
+'From Smalltalk/X, Version:6.2.3.0 on 24-03-2014 at 09:59:12'                   !
+
 "{ Package: 'stx:libview' }"
 
 GraphicsMedium subclass:#DisplaySurface
@@ -19,13 +21,6 @@
 	category:'Graphics-Support'
 !
 
-DeviceHandle subclass:#DeviceViewHandle
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	privateIn:DisplaySurface
-!
-
 !DisplaySurface class methodsFor:'documentation'!
 
 copyright
@@ -111,22 +106,22 @@
      newTop newBottom newLeft newRight|
 
     updateRegion isNil ifTrue:[
-        updateRegion := OrderedCollection with:newRectangle.
-        ^ true
+	updateRegion := OrderedCollection with:newRectangle.
+	^ true
     ].
     (updateRegion contains:[:oldRectangle | (newRectangle isContainedIn:oldRectangle)]) ifTrue:[
-        ^ false.
+	^ false.
     ].
 
     numRect := updateRegion size.
     numRect > 20 ifTrue:[
-        closure := updateRegion
-                        inject:newRectangle
-                        into:[:boundsSoFar :thisRectangle |
-                                boundsSoFar quickMerge:thisRectangle
-                             ].
-        updateRegion := OrderedCollection with:closure.
-        ^ true
+	closure := updateRegion
+			inject:newRectangle
+			into:[:boundsSoFar :thisRectangle |
+				boundsSoFar quickMerge:thisRectangle
+			     ].
+	updateRegion := OrderedCollection with:closure.
+	^ true
     ].
 
     lastRect := updateRegion at:numRect.
@@ -140,24 +135,24 @@
     newRight := newRectangle right.
 
     lastTop = newTop ifTrue:[
-        lastBottom = newBottom ifTrue:[
-            lastLeft <= newLeft ifTrue:[
-                lastRight >= newLeft ifTrue:[
-                    updateRegion at:numRect put:(lastRect copy right:newRight).
-                    ^ false "/ true
-                ]
-            ]
-        ].
+	lastBottom = newBottom ifTrue:[
+	    lastLeft <= newLeft ifTrue:[
+		lastRight >= newLeft ifTrue:[
+		    updateRegion at:numRect put:(lastRect copy right:newRight).
+		    ^ false "/ true
+		]
+	    ]
+	].
     ].
     lastLeft = newLeft ifTrue:[
-        lastRight = newRight ifTrue:[
-            lastTop <= newTop ifTrue:[
-                lastBottom >= newTop ifTrue:[
-                    updateRegion at:numRect put:(lastRect copy bottom:newBottom).
-                    ^ false "/ true
-                ]
-            ]
-        ].
+	lastRight = newRight ifTrue:[
+	    lastTop <= newTop ifTrue:[
+		lastBottom >= newTop ifTrue:[
+		    updateRegion at:numRect put:(lastRect copy bottom:newBottom).
+		    ^ false "/ true
+		]
+	    ]
+	].
     ].
 
     updateRegion add:newRectangle.
@@ -172,7 +167,7 @@
 
     viewBackground ~~ something ifTrue:[
 	viewBackground := something.
-	drawableId notNil ifTrue:[
+	self drawableId notNil ifTrue:[
 	    self setViewBackground
 	]
     ]
@@ -190,7 +185,7 @@
      but support for mixed depth views is being prepared.
      (especially useful on SGI, with 24bit view)"
 
-    ^ device depth
+    ^ self graphicsDevice depth
 !
 
 insideColor:aColor
@@ -205,7 +200,7 @@
      However, subclasses may redefine this, to return their own
      keyboard map (for example a terminalView may want treat CTRL-C as regular key)"
 
-    ^ device keyboardMap
+    ^ self graphicsDevice keyboardMap
 !
 
 renderer
@@ -231,123 +226,123 @@
     |id devBgPixmap bgPixmap w h colorMap
      pixmapDepth deviceDepth defBG|
 
-    drawableId notNil ifTrue:[
-        viewBackground isColor ifTrue:[
-            viewBackground := viewBackground onDevice:device.
-            id := viewBackground colorId.
-            "
-             a real color (i.e. one supported by the device) ?
-            "
-            id notNil ifTrue:[
-                device setWindowBackground:id in:drawableId.
-                ^ self
-            ].
-            "
-             no, a dithered one - must have a dither-pattern
-             (which is ready for the device, since viewBackground
-              is already assigned to the device)
-            "
-            bgPixmap := viewBackground ditherForm.
-        ] ifFalse:[
-            viewBackground notNil ifTrue:[
-                viewBackground isViewBackground ifTrue:[
-                    ^ self.
-                ].
-
-                "
-                 assume, it can convert itself to a form
-                "
-                bgPixmap := viewBackground asFormOn:device.
-                bgPixmap isNil ifTrue:[
-                    "/ assume it knows how to draw itself
-                    ^ self
-                ].
-            ].
-        ].
-
-        "
-         must now have:
-         a dithered color or bitmap or pixmap
-        "
-        bgPixmap isNil ifTrue:[
-            'DisplaySurface [warning]: background not convertable - ignored' errorPrintCR.
-            ^ self
-        ].
-
-        "/ if the device does not support background pixmaps,
-        "/ set the backgroundColor to the default background.
-        "/ this will avoid flicker in win32 systems,
-        "/ since that background is drawn directly in the
-        "/ devices expose event handling.
-        "/ (in contrast, the pixmap filling is done by the
-        "/ window itself in its expose event handler)
-
-        (device supportsViewBackgroundPixmap:bgPixmap) ifFalse:[
-            defBG := View defaultViewBackgroundColor.
-            defBG isColor ifTrue:[
-                defBG := defBG onDevice:device.
-                id := defBG colorId.
-                id notNil ifTrue:[
-                    device setWindowBackground:id in:drawableId.
-                ].
-            ].
-            ^ self
-        ].
-
-        w := bgPixmap width.
-        h := bgPixmap height.
-
-        deviceDepth := device depth.
-        pixmapDepth := bgPixmap depth.
-
-        (pixmapDepth ~~ deviceDepth) ifTrue:[
-            (pixmapDepth ~~ 1) ifTrue:[
-                'DisplaySurface [warning]: Bad dither depth (must be one or devices depth)' errorPrintCR.
-                ^ self
-            ].
-
-            "
-             convert it into a deep form
-            "
-            colorMap := bgPixmap colorMap.
-            devBgPixmap := Form width:w height:h depth:deviceDepth onDevice:device.
-            devBgPixmap isNil ifTrue:[
-                'DisplaySurface [warning]: could not create a device form for viewBackground' infoPrintCR.
-                ^ self
-            ].
-            devBgPixmap paint:(colorMap at:1).
-            devBgPixmap fillRectangleX:0 y:0 width:w height:h.
-            devBgPixmap foreground:(colorMap at:2) background:(colorMap at:1).
-            devBgPixmap copyPlaneFrom:bgPixmap x:0 y:0 toX:0 y:0 width:w height:h.
-            bgPixmap := devBgPixmap.
-        ] ifFalse:[
-            (pixmapDepth == 1) ifTrue:[
-                "
-                 although depth matches,
-                 values in the dither are to be interpreted via the ditherForms
-                 colormap, which is not always the same as blackpixel/whitepixel ...
-                "
-                colorMap := bgPixmap colorMap.
-                (colorMap at:1) colorId == device whitepixel ifTrue:[
-                    (colorMap at:2) colorId == device blackpixel ifTrue:[
-                        "
-                         ok, can use it
-                        "
-                        device setWindowBackgroundPixmap:(bgPixmap id) in:drawableId.
-                        ^ self
-                    ]
-                ].
-
-                "
-                 no, must invert it
-                "
-                devBgPixmap := Form width:w height:h depth:deviceDepth onDevice:device.
-                devBgPixmap paint:(colorMap at:2) on:(colorMap at:1).
-                devBgPixmap copyPlaneFrom:bgPixmap x:0 y:0 toX:0 y:0 width:w height:h.
-                bgPixmap := devBgPixmap.
-            ]
-        ].
-        device setWindowBackgroundPixmap:(bgPixmap id) in:drawableId.
+    self drawableId notNil ifTrue:[
+	viewBackground isColor ifTrue:[
+	    viewBackground := viewBackground onDevice:self graphicsDevice.
+	    id := viewBackground colorId.
+	    "
+	     a real color (i.e. one supported by the device) ?
+	    "
+	    id notNil ifTrue:[
+		self graphicsDevice setWindowBackground:id in:self drawableId.
+		^ self
+	    ].
+	    "
+	     no, a dithered one - must have a dither-pattern
+	     (which is ready for the device, since viewBackground
+	      is already assigned to the device)
+	    "
+	    bgPixmap := viewBackground ditherForm.
+	] ifFalse:[
+	    viewBackground notNil ifTrue:[
+		viewBackground isViewBackground ifTrue:[
+		    ^ self.
+		].
+
+		"
+		 assume, it can convert itself to a form
+		"
+		bgPixmap := viewBackground asFormOn:self graphicsDevice.
+		bgPixmap isNil ifTrue:[
+		    "/ assume it knows how to draw itself
+		    ^ self
+		].
+	    ].
+	].
+
+	"
+	 must now have:
+	 a dithered color or bitmap or pixmap
+	"
+	bgPixmap isNil ifTrue:[
+	    'DisplaySurface [warning]: background not convertable - ignored' errorPrintCR.
+	    ^ self
+	].
+
+	"/ if the device does not support background pixmaps,
+	"/ set the backgroundColor to the default background.
+	"/ this will avoid flicker in win32 systems,
+	"/ since that background is drawn directly in the
+	"/ devices expose event handling.
+	"/ (in contrast, the pixmap filling is done by the
+	"/ window itself in its expose event handler)
+
+	(self graphicsDevice supportsViewBackgroundPixmap:bgPixmap) ifFalse:[
+	    defBG := View defaultViewBackgroundColor.
+	    defBG isColor ifTrue:[
+		defBG := defBG onDevice:self graphicsDevice.
+		id := defBG colorId.
+		id notNil ifTrue:[
+		    self graphicsDevice setWindowBackground:id in:self drawableId.
+		].
+	    ].
+	    ^ self
+	].
+
+	w := bgPixmap width.
+	h := bgPixmap height.
+
+	deviceDepth := self depth.
+	pixmapDepth := bgPixmap depth.
+
+	(pixmapDepth ~~ deviceDepth) ifTrue:[
+	    (pixmapDepth ~~ 1) ifTrue:[
+		'DisplaySurface [warning]: Bad dither depth (must be one or devices depth)' errorPrintCR.
+		^ self
+	    ].
+
+	    "
+	     convert it into a deep form
+	    "
+	    colorMap := bgPixmap colorMap.
+	    devBgPixmap := Form width:w height:h depth:deviceDepth onDevice:self graphicsDevice.
+	    devBgPixmap isNil ifTrue:[
+		'DisplaySurface [warning]: could not create a device form for viewBackground' infoPrintCR.
+		^ self
+	    ].
+	    devBgPixmap paint:(colorMap at:1).
+	    devBgPixmap fillRectangleX:0 y:0 width:w height:h.
+	    devBgPixmap foreground:(colorMap at:2) background:(colorMap at:1).
+	    devBgPixmap copyPlaneFrom:bgPixmap x:0 y:0 toX:0 y:0 width:w height:h.
+	    bgPixmap := devBgPixmap.
+	] ifFalse:[
+	    (pixmapDepth == 1) ifTrue:[
+		"
+		 although depth matches,
+		 values in the dither are to be interpreted via the ditherForms
+		 colormap, which is not always the same as blackpixel/whitepixel ...
+		"
+		colorMap := bgPixmap colorMap.
+		(colorMap at:1) colorId == self graphicsDevice whitepixel ifTrue:[
+		    (colorMap at:2) colorId == self graphicsDevice blackpixel ifTrue:[
+			"
+			 ok, can use it
+			"
+			self graphicsDevice setWindowBackgroundPixmap:(bgPixmap id) in:self drawableId.
+			^ self
+		    ]
+		].
+
+		"
+		 no, must invert it
+		"
+		devBgPixmap := Form width:w height:h depth:deviceDepth onDevice:self graphicsDevice.
+		devBgPixmap paint:(colorMap at:2) on:(colorMap at:1).
+		devBgPixmap copyPlaneFrom:bgPixmap x:0 y:0 toX:0 y:0 width:w height:h.
+		bgPixmap := devBgPixmap.
+	    ]
+	].
+	self graphicsDevice setWindowBackgroundPixmap:(bgPixmap id) in:self drawableId.
     ]
 
     "Modified: / 23-01-2011 / 01:44:38 / cg"
@@ -409,10 +404,18 @@
     ^ self
 !
 
+windowClass:classString name:nameString
+    gc windowClass:classString name:nameString.
+!
+
 windowGroup
     "return nil - I have no windowGroup"
 
     ^ nil
+!
+
+windowName:aString
+    gc windowName:aString.
 ! !
 
 !DisplaySurface methodsFor:'accessing-cursor'!
@@ -456,11 +459,11 @@
     aCursor notNil ifTrue:[
 	(aCursor ~~ cursor) ifTrue:[
 	    cursor := aCursor.
-	    drawableId notNil ifTrue:[
+	    self drawableId notNil ifTrue:[
 		self setCursor.
 		(showImmediately and:[realized]) ifTrue:[
 		    "flush, to make cursor immediately visible"
-		    device flush
+		    self flush
 		]
 	    ]
 	]
@@ -489,16 +492,16 @@
     |id|
 
     cursor isNil ifTrue:[ ^ self].
-    cursor := cursor onDevice:self device.
+    cursor := cursor onDevice:self graphicsDevice.
     cursor isNil ifTrue:[ ^ self].
 
     id := cursor id.
     id isNil ifTrue:[
-        'DisplaySurface [warning]: nil cursorId ignored; shape=' errorPrint.
-        cursor shape errorPrintCR.
-        ^ self.
+	'DisplaySurface [warning]: nil cursorId ignored; shape=' errorPrint.
+	cursor shape errorPrintCR.
+	^ self.
     ].
-    self setCursorId:id .
+    gc setCursorId:id .
 !
 
 withCursor:aCursor do:aBlock
@@ -550,19 +553,19 @@
     |ret|
 
     cursor == aCursor ifTrue:[
-        ^ aBlock value
+	^ aBlock value
     ].
 
-    self 
-        withCursor:aCursor do:[
-            |time|
-
-            time := Time millisecondsToRun:[ ret := aBlock value].
-            time := UserPreferences current waitCursorVisibleTime - time.
-            time > 0 ifTrue:[
-                Delay waitForMilliseconds:time.
-            ].
-        ].
+    self
+	withCursor:aCursor do:[
+	    |time|
+
+	    time := Time millisecondsToRun:[ ret := aBlock value].
+	    time := UserPreferences current waitCursorVisibleTime - time.
+	    time > 0 ifTrue:[
+		Delay waitForMilliseconds:time.
+	    ].
+	].
     ^ ret.
 
     "Modified (comment): / 12-09-2011 / 12:14:29 / cg"
@@ -590,7 +593,8 @@
 !DisplaySurface methodsFor:'accessing-hierarchy'!
 
 delegate
-    "return the delegate - thats the one getting keyboard and button events"
+    "return the delegate - that's the one getting keyboard and button events.
+     See dispatchEvent:... method"
 
     ^ delegate
 !
@@ -598,7 +602,7 @@
 delegate:someOne
     "set the delegate - keyboard- and button events will be forwarded to
      that object if it is interested in them.
-     See the sendEvent... method in WindowEvent."
+     See the dispatchEvent... method."
 
     delegate := someOne
 !
@@ -660,8 +664,8 @@
      how may true/false, but also #always, #whenMapped or #never."
 
     how ~~ backed ifTrue:[
-        backed := how.
-        super backingStore:how.
+	backed := how.
+	super backingStore:how.
     ]
 !
 
@@ -683,7 +687,7 @@
     "tell the Display to assign keyboard focus to the receiver"
 
     self shown ifTrue:[
-	device setInputFocusTo:drawableId.
+	self graphicsDevice setInputFocusTo:self drawableId.
     ].
 
     "Modified: / 15.3.1999 / 08:25:10 / cg"
@@ -730,17 +734,17 @@
      - used for temporary views (i.e. PopUps and ModalBoxes)"
 
     aBoolean ifTrue:[
-        flags := flags bitOr:SaveUnderFlagMask.
+	flags := flags bitOr:SaveUnderFlagMask.
     ] ifFalse:[
-        flags := flags bitClear:SaveUnderFlagMask.
+	flags := flags bitClear:SaveUnderFlagMask.
     ].
-    super saveUnder:aBoolean.
+    gc saveUnder:aBoolean.
 !
 
 setPointerPosition:aRelativePoint
     "set the pointer to aRelativePoint relative to the views origin"
 
-    device setPointerPosition:aRelativePoint in:drawableId.
+    self graphicsDevice setPointerPosition:aRelativePoint in:self drawableId.
 
     "
 	Transcript setPointerPosition:Transcript extent // 2.
@@ -834,15 +838,15 @@
 
 setAttribute:key to:newValue
     newValue isNil ifTrue:[
-        moreAttributes notNil ifTrue:[
-            moreAttributes removeKey:key ifAbsent:[].
-            moreAttributes := moreAttributes asNilIfEmpty
-        ]
+	moreAttributes notNil ifTrue:[
+	    moreAttributes removeKey:key ifAbsent:[].
+	    moreAttributes := moreAttributes asNilIfEmpty
+	]
     ] ifFalse:[
-        moreAttributes isNil ifTrue:[
-            moreAttributes := IdentityDictionary new.
-        ].
-        moreAttributes at:key put:newValue.
+	moreAttributes isNil ifTrue:[
+	    moreAttributes := IdentityDictionary new.
+	].
+	moreAttributes at:key put:newValue.
     ].
 !
 
@@ -852,6 +856,53 @@
     flags := flags bitOr:GotExposeFlagMask.
 ! !
 
+!DisplaySurface methodsFor:'binary storage'!
+
+readBinaryContentsFrom: stream manager: manager
+    "tell the newly restored View to recreate itself.
+     Bug: does not work correctly yet.
+	  (restored view looses its position & wg process)"
+
+    |wasRealized|
+
+    super readBinaryContentsFrom: stream manager: manager.
+
+    wasRealized := realized.
+    realized := false.
+    self recreate.
+    wasRealized ifTrue:[
+	self remap
+    ]
+
+
+    "
+     |s l|
+     s := 'storedLabel.boss' asFilename writeStream binary.
+     l := (Label label:'hello there') realize.
+     Delay waitForSeconds:1.
+     l storeBinaryOn:s.
+     s close.
+    "
+
+    "
+     |s l|
+     s := 'storedLabel.boss' asFilename writeStream binary.
+     (l := Label label:'hello there') open.
+     (Delay forSeconds:10) wait.
+     l storeBinaryOn:s.
+     s close.
+     l destroy.
+    "
+
+    "
+     |s|
+     s := 'storedLabel.boss' asFilename readStream binary.
+     (Object readBinaryFrom:s)
+    "
+
+    "Modified: 3.5.1996 / 23:59:38 / stefan"
+    "Modified: 14.2.1997 / 15:42:55 / cg"
+! !
 
 !DisplaySurface methodsFor:'button menus'!
 
@@ -885,9 +936,9 @@
     |oldMenu|
 
     (oldMenu := self getMiddleButtonMenu) notNil ifTrue:[
-        oldMenu isArray ifFalse:[
-            oldMenu destroy
-        ]
+	oldMenu isArray ifFalse:[
+	    oldMenu destroy
+	]
     ].
     self setMiddleButtonMenu:aMenu
 
@@ -907,7 +958,7 @@
     "return the object selection
      - either the local one, or the displays clipBoard buffer."
 
-    ^ device getClipboardObjectFor:drawableId.
+    ^ self graphicsDevice getClipboardObjectFor:self drawableId.
 
     "Modified: 13.2.1997 / 13:18:50 / cg"
 !
@@ -928,7 +979,7 @@
 
      Return aString or nil if there is no selection"
 
-    ^ device getClipboardText:selectionBufferSymbol for:drawableId.
+    ^ self graphicsDevice getClipboardText:selectionBufferSymbol for:self drawableId.
 !
 
 getSelection
@@ -966,14 +1017,14 @@
     "set the object selection - both the local one, and tell the display
      that we have changed it (i.e. place it into the clipBoard)."
 
-    device setClipboardObject:something ownerView:self.
+    self graphicsDevice setClipboardObject:something ownerView:self.
 !
 
 setClipboardText:something
     "set the text selection - both the local one, and tell the display
      that we have changed it (i.e. place it into the clipBoard)."
 
-    device setClipboardText:something ownerView:self
+    self graphicsDevice setClipboardText:something ownerView:self
 !
 
 setSelection:something
@@ -983,7 +1034,7 @@
     <resource: #obsolete>
 
     self obsoleteMethodWarning:'use setClipboardObject:'.
-    device setClipboardObject:something ownerView:self.
+    self graphicsDevice setClipboardObject:something ownerView:self.
 !
 
 setTextSelection:something
@@ -993,7 +1044,7 @@
     <resource: #obsolete>
 
     self obsoleteMethodWarning:'use setClipboardText:'.
-    device setClipboardText:something ownerView:self
+    self graphicsDevice setClipboardText:something ownerView:self
 ! !
 
 !DisplaySurface methodsFor:'drawing'!
@@ -1003,33 +1054,31 @@
      redefined since GraphicsMedium fills with background
      - not viewBackground as we want here."
 
-    |oldPaint org|
+    |oldPaint|
 
     viewBackground isColor ifFalse:[
-        viewBackground isViewBackground ifTrue:[
-            self paint:background.
-            self fillDeviceRectangleX:x y:y width:w height:h.
-            self paint:paint.
-            viewBackground fillRectangleX:x y:y width:w height:h in:self.
-            ^ self.
-        ].
-
-        gcId notNil ifTrue:[
-            org := self viewOrigin.
-            device setMaskOriginX:org x rounded negated
-                                y:org y rounded negated
-                               in:gcId
-        ].
-        (device supportsMaskedDrawingWith:viewBackground) ifFalse:[
-            self fillDeviceRectangleWithViewBackgroundX:x y:y width:w height:h.
-            ^ self.
-        ]
+	viewBackground isViewBackground ifTrue:[
+	    oldPaint := self paint.
+	    self paint:self background.
+	    self fillDeviceRectangleX:x y:y width:w height:h.
+	    self paint:oldPaint.
+	    viewBackground fillRectangleX:x y:y width:w height:h in:self.
+	    ^ self.
+	].
+
+	gc notNil ifTrue:[
+	    self maskOrigin:self viewOrigin negated.
+	    (gc graphicsDevice supportsMaskedDrawingWith:viewBackground) ifFalse:[
+		gc graphicsDevice fillDeviceRectangleWithViewBackgroundX:x y:y width:w height:h.
+		^ self.
+	    ].
+	].
     ].
 
     "
      fill in device coordinates - not logical coordinates
     "
-    oldPaint := paint.
+    oldPaint := self paint.
     self paint:viewBackground.
     self fillDeviceRectangleX:x y:y width:w height:h "with:viewBackground".
     self paint:oldPaint
@@ -1042,13 +1091,14 @@
      redefined since GraphicsMedium fills with background
      - not viewBackground as we want here."
 
-    |pX pY pW pH|
-
-    transformation notNil ifTrue:[
-	pX := transformation applyToX:x.
-	pY := transformation applyToY:y.
-	pW := transformation applyScaleX:w.
-	pH := transformation applyScaleY:h.
+    |pX pY pW pH currentTransformation|
+
+    currentTransformation := gc transformation.
+    currentTransformation notNil ifTrue:[
+	pX := currentTransformation applyToX:x.
+	pY := currentTransformation applyToY:y.
+	pW := currentTransformation applyScaleX:w.
+	pH := currentTransformation applyScaleY:h.
     ] ifFalse:[
 	pX := x.
 	pY := y.
@@ -1056,17 +1106,13 @@
 	pH := h.
     ].
 
-    pX := pX rounded.
-    pY := pY rounded.
-    pW := pW rounded.
-    pH := pH rounded.
-
-    ^ self clearDeviceRectangleX:pX y:pY width:pW height:pH.
+    ^ self clearDeviceRectangleX:pX rounded y:pY rounded width:pW rounded height:pH rounded.
 
     "Modified: / 30.10.1998 / 15:00:37 / cg"
 !
 
 fillDeviceRectangleWithPattern:aPixmap x:xIn y:yIn width:wIn height:hIn patternOffset:pattOffs
+    <resource: #obsolete>
     "fill a rectangular area with some pattern.
      A helper for devices which do not support pixmap drawing (i.e. win95).
      This is never invoked with X11 or Win-NT/XP/Vista systems.
@@ -1102,10 +1148,10 @@
     oldClip := self clippingRectangleOrNil.
 
     oldClip notNil ifTrue:[
-        x := x max:oldClip left.
-        y := y max:oldClip top.
-        r := r min:oldClip right.
-        b := b min:oldClip bottom.
+	x := x max:oldClip left.
+	y := y max:oldClip top.
+	r := r min:oldClip right.
+	b := b min:oldClip bottom.
     ].
     w := r-x+1.
     h := b-y+1.
@@ -1121,16 +1167,16 @@
     xR0 >= yE ifTrue:[^ self].
 
     aPixmap depth == 1 ifTrue:[
-        oldFg := foreground.
-        oldBg := background.
-        (clrMap := aPixmap colorMap) notNil ifTrue:[
-            bg := clrMap at:1.
-            fg := clrMap at:2.
-        ] ifFalse:[
-            bg := Color white.
-            fg := Color black.
-        ].
-        self foreground:fg background:bg.
+	oldFg := self foreground.
+	oldBg := self background.
+	(clrMap := aPixmap colorMap) notNil ifTrue:[
+	    bg := clrMap at:1.
+	    fg := clrMap at:2.
+	] ifFalse:[
+	    bg := Color white.
+	    fg := Color black.
+	].
+	self foreground:fg background:bg.
     ].
     self deviceClippingRectangle:(x@y extent:w@h).
 
@@ -1139,24 +1185,24 @@
 
     oY := offsY.
     [yR < yE] whileTrue:[
-        xR := xR0.
-        oX := offsX.
-        [xR < xE] whileTrue:[
-            self
-                copyFrom:aPixmap
-                x:oX y:oY
-                toX:xR y:yR
-                width:(pW - oX) height:(pH - oY)
-                async:true.
-            xR := xR + pW - oX.
-            oX := 0.
-        ].
-        yR := yR + pH - oY.
-        oY := 0.
+	xR := xR0.
+	oX := offsX.
+	[xR < xE] whileTrue:[
+	    self
+		copyFrom:aPixmap
+		x:oX y:oY
+		toX:xR y:yR
+		width:(pW - oX) height:(pH - oY)
+		async:true.
+	    xR := xR + pW - oX.
+	    oX := 0.
+	].
+	yR := yR + pH - oY.
+	oY := 0.
     ].
 
     oldFg notNil ifTrue:[
-        self foreground:oldFg background:oldBg.
+	self foreground:oldFg background:oldBg.
     ].
     self deviceClippingRectangle:oldClip.
 
@@ -1166,46 +1212,46 @@
 !
 
 fillDeviceRectangleWithViewBackgroundX:xIn y:yIn width:wIn height:hIn
+    <resource: #obsolete>
     "fill a rectangular area with the viewBackground.
      A helper for devices which do not support background pixmaps (i.e. win95 screens).
      This is never invoked with X11 or Win-NT/XP/Vista systems.
      Caller must ensure that the viewBackground is really a form"
 
     self
-        fillDeviceRectangleWithPattern:viewBackground
-        x:xIn y:yIn width:wIn height:hIn
-        patternOffset:self viewOrigin
+	fillDeviceRectangleWithPattern:viewBackground
+	x:xIn y:yIn width:wIn height:hIn
+	patternOffset:self viewOrigin
 !
 
 fillRectangleWithPattern:aPixmap x:x y:y width:w height:h patternOffset:pattOffs
+    <resource: #obsolete>
     "fill a rectangular area with aPixmap.
      A helper for devices which do not support pixmap filling (i.e. win95 screens).
      This is never invoked with X11 or Win-NT/XP/Vista systems.
      Caller must ensure that the aPixmap is really a form"
 
-    |pX pY nW nH|
-
-    gcId isNil ifTrue:[
-        self initGC
-    ].
-    transformation notNil ifTrue:[
-        pX := transformation applyToX:x.
-        pY := transformation applyToY:y.
-        nW := transformation applyScaleX:w.
-        nH := transformation applyScaleY:h.
-        nW < 0 ifTrue:[
-              nW := nW abs.
-              pX := pX - nW.
-        ].
-        nH < 0 ifTrue:[
-              nH := nH abs.
-              pY := pY - nH.
-        ].
+    |pX pY nW nH currentTransformation|
+
+    currentTransformation := gc transformation.
+    currentTransformation notNil ifTrue:[
+	pX := currentTransformation applyToX:x.
+	pY := currentTransformation applyToY:y.
+	nW := currentTransformation applyScaleX:w.
+	nH := currentTransformation applyScaleY:h.
+	nW < 0 ifTrue:[
+	      nW := nW abs.
+	      pX := pX - nW.
+	].
+	nH < 0 ifTrue:[
+	      nH := nH abs.
+	      pY := pY - nH.
+	].
     ] ifFalse:[
-        pX := x.
-        pY := y.
-        nW := w.
-        nH := h.
+	pX := x.
+	pY := y.
+	nW := w.
+	nH := h.
     ].
     pX := pX rounded.
     pY := pY rounded.
@@ -1213,23 +1259,24 @@
     nH := nH rounded.
 
     self
-        fillDeviceRectangleWithPattern:aPixmap
-        x:pX y:pY width:nW height:nH
-        patternOffset:pattOffs
+	fillDeviceRectangleWithPattern:aPixmap
+	x:pX y:pY width:nW height:nH
+	patternOffset:pattOffs
 
     "Modified: 4.6.1996 / 17:58:49 / cg"
 !
 
 fillRectangleWithViewBackgroundX:x y:y width:w height:h
+    <resource: #obsolete>
     "fill a rectangular area with the viewBackground.
      A helper for devices which do not support background pixmaps (i.e. win95 screens).
      This is never invoked with X11 or Win-NT/XP/Vista systems.
      Caller must ensure that the viewBackground is really a form"
 
     self
-        fillRectangleWithPattern:viewBackground
-        x:x y:y width:w height:h
-        patternOffset:self viewOrigin
+	fillRectangleWithPattern:viewBackground
+	x:x y:y width:w height:h
+	patternOffset:self viewOrigin
 !
 
 redraw
@@ -1292,9 +1339,9 @@
      this is a private (internal) method not to be used externally.
      for a list of allowed event symbols see Workstation class"
 
-    eventMask := eventMask bitAnd:(device eventMaskFor:anEventSymbol) bitInvert.
-    drawableId notNil ifTrue:[
-	device setEventMask:eventMask in:drawableId
+    eventMask := eventMask bitAnd:(self graphicsDevice eventMaskFor:anEventSymbol) bitInvert.
+    self drawableId notNil ifTrue:[
+	self graphicsDevice setEventMask:eventMask in:self drawableId
     ]
 !
 
@@ -1353,9 +1400,9 @@
      this is a private (internal) method not to be used externally.
      for a list of allowed event symbols see Workstation class"
 
-    eventMask := (eventMask ? 0) bitOr:(device eventMaskFor:anEventSymbol).
-    drawableId notNil ifTrue:[
-	device setEventMask:eventMask in:drawableId
+    eventMask := (eventMask ? 0) bitOr:(self graphicsDevice eventMaskFor:anEventSymbol).
+    self drawableId notNil ifTrue:[
+	self graphicsDevice setEventMask:eventMask in:self drawableId
     ]
 !
 
@@ -1453,7 +1500,7 @@
 	    y := rect top.
 	    w := rect width.
 	    h := rect height.
-	    transformation notNil ifTrue:[
+	    gc transformation notNil ifTrue:[
 		self deviceExposeX:x y:y width:w height:h
 	    ] ifFalse:[
 		self exposeX:x y:y width:w height:h
@@ -1476,7 +1523,7 @@
 			y := rect top.
 			w := rect width.
 			h := rect height.
-			transformation notNil ifTrue:[
+			gc transformation notNil ifTrue:[
 			    self deviceExposeX:x y:y width:w height:h
 			] ifFalse:[
 			    self exposeX:x y:y width:w height:h
@@ -1589,10 +1636,13 @@
 		    "
 		     mhmh ... have to convert to logical coordinates
 		    "
-		    transformation notNil ifTrue:[
+		    |currentTransformation|
+
+		    currentTransformation := gc transformation.
+		    currentTransformation notNil ifTrue:[
 			argArray size > 2 ifTrue:[
-			    argArray at:2 put:(transformation applyInverseToX:(argArray at:2)).
-			    argArray at:3 put:(transformation applyInverseToY:(argArray at:3)).
+			    argArray at:2 put:(currentTransformation applyInverseToX:(argArray at:2)).
+			    argArray at:3 put:(currentTransformation applyInverseToY:(argArray at:3)).
 			].
 		    ].
 		    argArray isNil ifTrue:[
@@ -1645,7 +1695,7 @@
     "
     selector := type.
 
-    transformation notNil ifTrue:[
+    gc transformation notNil ifTrue:[
 	(isKeyEvent
 	 or:[isButtonEvent
 	 or:[isMouseWheelEvent
@@ -1694,12 +1744,12 @@
     |menu|
 
     (menu := self middleButtonMenu) notNil ifTrue:[
-        menu isArray ifTrue:[
-            "/ a spec array
-            menu := menu decodeAsLiteralArray.
-            menu receiver:self.
-        ].
-        menu showAtPointer
+	menu isArray ifTrue:[
+	    "/ a spec array
+	    menu := menu decodeAsLiteralArray.
+	    menu receiver:self.
+	].
+	menu showAtPointer
     ]
 
     "Created: 1.3.1996 / 13:24:55 / cg"
@@ -1721,9 +1771,9 @@
     "button was pressed - if its middle button and there is a menu, show it."
 
     (button == 2) ifTrue:[
-        UserPreferences current showRightButtonMenuOnRelease ifFalse:[
-            self activateMenu.
-        ].
+	UserPreferences current showRightButtonMenuOnRelease ifFalse:[
+	    self activateMenu.
+	].
     ]
 
     "Modified: 1.3.1996 / 13:25:07 / cg"
@@ -1731,9 +1781,9 @@
 
 buttonRelease:button x:x y:y
     (button == 2) ifTrue:[
-        UserPreferences current showRightButtonMenuOnRelease ifTrue:[
-            self activateMenu.
-        ].
+	UserPreferences current showRightButtonMenuOnRelease ifTrue:[
+	    self activateMenu.
+	].
     ].
 !
 
@@ -1748,7 +1798,7 @@
 
     |wg|
 
-    device scrollsAsynchronous ifFalse:[
+    self graphicsDevice scrollsAsynchronous ifFalse:[
 	self setGotExposeFlag.
 	^ self
     ].
@@ -1786,14 +1836,15 @@
      those which are interested in logical coordinates
      should redefine #buttonMotion:x:y:"
 
-    |lx ly|
+    |lx ly currentTransformation|
 
     lx := x.
     ly := y.
-    transformation notNil ifTrue:[
+    currentTransformation := gc transformation.
+    currentTransformation notNil ifTrue:[
 	lx notNil ifTrue:[
-	    lx := transformation applyInverseToX:lx.
-	    ly := transformation applyInverseToY:ly.
+	    lx := currentTransformation applyInverseToX:lx.
+	    ly := currentTransformation applyInverseToY:ly.
 	].
     ].
     self buttonMotion:state x:lx y:ly
@@ -1813,14 +1864,15 @@
      those which are interested in logical coordinates
      should redefine #buttonMultiPress:x:y:"
 
-    |lx ly|
+    |lx ly currentTransformation|
 
     lx := x.
     ly := y.
-    transformation notNil ifTrue:[
+    currentTransformation := gc transformation.
+    currentTransformation notNil ifTrue:[
 	lx notNil ifTrue:[
-	    lx := transformation applyInverseToX:lx.
-	    ly := transformation applyInverseToY:ly.
+	    lx := currentTransformation applyInverseToX:lx.
+	    ly := currentTransformation applyInverseToY:ly.
 	].
     ].
     self buttonMultiPress:butt x:lx y:ly
@@ -1840,14 +1892,15 @@
      those which are interested in logical coordinates
      should redefine #buttonPress:x:y:"
 
-    |lx ly|
+    |lx ly currentTransformation|
 
     lx := x.
     ly := y.
-    transformation notNil ifTrue:[
+    currentTransformation := gc transformation.
+    currentTransformation notNil ifTrue:[
 	lx notNil ifTrue:[
-	    lx := transformation applyInverseToX:lx.
-	    ly := transformation applyInverseToY:ly.
+	    lx := currentTransformation applyInverseToX:lx.
+	    ly := currentTransformation applyInverseToY:ly.
 	].
     ].
     self buttonPress:butt x:lx y:ly
@@ -1867,14 +1920,15 @@
      those which are interested in logical coordinates
      should redefine #buttonRelease:x:y:"
 
-    |lx ly|
+    |lx ly currentTransformation|
 
     lx := x.
     ly := y.
-    transformation notNil ifTrue:[
+    currentTransformation := gc transformation.
+    currentTransformation notNil ifTrue:[
 	lx notNil ifTrue:[
-	    lx := transformation applyInverseToX:lx.
-	    ly := transformation applyInverseToY:ly.
+	    lx := currentTransformation applyInverseToX:lx.
+	    ly := currentTransformation applyInverseToY:ly.
 	].
     ].
     self buttonRelease:butt x:lx y:ly
@@ -1894,14 +1948,15 @@
      those which are interested in logical coordinates
      should redefine #buttonShiftPress:x:y:"
 
-    |lx ly|
+    |lx ly currentTransformation|
 
     lx := x.
     ly := y.
-    transformation notNil ifTrue:[
+    currentTransformation := gc transformation.
+    currentTransformation notNil ifTrue:[
 	lx notNil ifTrue:[
-	    lx := transformation applyInverseToX:lx.
-	    ly := transformation applyInverseToY:ly.
+	    lx := currentTransformation applyInverseToX:lx.
+	    ly := currentTransformation applyInverseToY:ly.
 	].
     ].
     self buttonShiftPress:butt x:lx y:ly
@@ -1921,17 +1976,18 @@
      those which are interested in logical coordinates
      should redefine #exposeX:x:y:width:height:"
 
-    |lx ly lw lh|
+    |lx ly lw lh currentTransformation|
 
     lx := x.
     ly := y.
     lw := w.
     lh := h.
-    transformation notNil ifTrue:[
-	lx := transformation applyInverseToX:lx.
-	ly := transformation applyInverseToY:ly.
-	lw := transformation applyInverseScaleX:lw.
-	lh := transformation applyInverseScaleY:lh.
+    currentTransformation := gc transformation.
+    currentTransformation notNil ifTrue:[
+	lx := currentTransformation applyInverseToX:lx.
+	ly := currentTransformation applyInverseToY:ly.
+	lw := currentTransformation applyInverseScaleX:lw.
+	lh := currentTransformation applyInverseScaleY:lh.
     ].
     self exposeX:lx y:ly width:lw height:lh
 
@@ -1950,17 +2006,18 @@
      those which are interested in logical coordinates
      should redefine #graphicsExposeX:x:y:width:height:"
 
-    |lx ly lw lh|
+    |lx ly lw lh currentTransformation|
 
     lx := x.
     ly := y.
     lw := w.
     lh := h.
-    transformation notNil ifTrue:[
-	lx := transformation applyInverseToX:lx.
-	ly := transformation applyInverseToY:ly.
-	lw := transformation applyInverseScaleX:lw.
-	lh := transformation applyInverseScaleY:lh.
+    currentTransformation := gc transformation.
+    currentTransformation notNil ifTrue:[
+	lx := currentTransformation applyInverseToX:lx.
+	ly := currentTransformation applyInverseToY:ly.
+	lw := currentTransformation applyInverseScaleX:lw.
+	lh := currentTransformation applyInverseScaleY:lh.
     ].
     self graphicsExposeX:lx y:ly width:lw height:lh final:final
 
@@ -1979,14 +2036,15 @@
      those which are interested in logical coordinates
      should redefine #keyPress:x:y:"
 
-    |lx ly|
+    |lx ly currentTransformation|
 
     lx := x.
     ly := y.
-    transformation notNil ifTrue:[
+    currentTransformation := gc transformation.
+    currentTransformation notNil ifTrue:[
 	lx notNil ifTrue:[
-	    lx := transformation applyInverseToX:lx.
-	    ly := transformation applyInverseToY:ly.
+	    lx := currentTransformation applyInverseToX:lx.
+	    ly := currentTransformation applyInverseToY:ly.
 	]
     ].
     self keyPress:key x:lx y:ly
@@ -2006,14 +2064,15 @@
      those which are interested in logical coordinates
      should redefine #keyRelease:x:y:"
 
-    |lx ly|
+    |lx ly currentTransformation|
 
     lx := x.
     ly := y.
-    transformation notNil ifTrue:[
+    currentTransformation := gc transformation.
+    currentTransformation notNil ifTrue:[
 	lx notNil ifTrue:[
-	    lx := transformation applyInverseToX:lx.
-	    ly := transformation applyInverseToY:ly.
+	    lx := currentTransformation applyInverseToX:lx.
+	    ly := currentTransformation applyInverseToY:ly.
 	]
     ].
     self keyRelease:key x:lx y:ly
@@ -2033,14 +2092,15 @@
      those which are interested in logical coordinates
      should redefine #pointerEnter:x:y:"
 
-    |lx ly|
+    |lx ly currentTransformation|
 
     lx := x.
     ly := y.
-    transformation notNil ifTrue:[
+    currentTransformation := gc transformation.
+    currentTransformation notNil ifTrue:[
 	lx notNil ifTrue:[
-	    lx := transformation applyInverseToX:lx.
-	    ly := transformation applyInverseToY:ly.
+	    lx := currentTransformation applyInverseToX:lx.
+	    ly := currentTransformation applyInverseToY:ly.
 	]
     ].
     self pointerEnter:state x:lx y:ly
@@ -2086,20 +2146,20 @@
     |action rest restKey keyCommands|
 
     (keyCommands := self keyCommands) notNil ifTrue:[
-        action := keyCommands at:key ifAbsent:[nil].
-        action value
+	action := keyCommands at:key ifAbsent:[nil].
+	action value
     ].
 
     key isSymbol ifTrue:[
-        (key startsWith:'Basic') ifTrue:[
-            "/ an unhandled BasicFoo key;
-            "/ retry as Foo
-            rest := key withoutPrefix:'Basic'.
-            restKey := rest asSymbolIfInterned.
-            restKey notNil ifTrue:[
-                self keyPress:restKey x:x y:y
-            ]
-        ].
+	(key startsWith:'Basic') ifTrue:[
+	    "/ an unhandled BasicFoo key;
+	    "/ retry as Foo
+	    rest := key withoutPrefix:'Basic'.
+	    restKey := rest asSymbolIfInterned.
+	    restKey notNil ifTrue:[
+		self keyPress:restKey x:x y:y
+	    ]
+	].
     ].
 
     "Modified: 6.11.1996 / 17:51:15 / cg"
@@ -2147,9 +2207,10 @@
 waitForExpose
     "wait until an expose event arrives (to wait for scroll-finish)"
 
-    |wg endPollTime pollDelay|
-
-    device scrollsAsynchronous ifFalse:[
+    |wg endPollTime pollDelay graphicsDevice|
+
+    graphicsDevice := self graphicsDevice.
+    graphicsDevice scrollsAsynchronous ifFalse:[
 	self setGotExposeFlag.
 	^ self
     ].
@@ -2167,7 +2228,7 @@
 	"/ wait by doing a direct dispatch loop until the event arrives.
 	"/ i.e. poll for the event
 	"/
-	device platformName = 'WIN32' ifTrue:[
+	graphicsDevice platformName = 'WIN32' ifTrue:[
 	    pollDelay := 1.
 	] ifFalse:[
 	    pollDelay := 3.
@@ -2176,8 +2237,8 @@
 
 	[self gotExpose] whileFalse:[
 	    realized ifTrue:[
-		(device exposeEventPendingFor:drawableId withSync:true) ifTrue:[
-		    device dispatchExposeEventFor:drawableId.
+		(graphicsDevice exposeEventPendingFor:self drawableId withSync:true) ifTrue:[
+		    graphicsDevice dispatchExposeEventFor:self drawableId.
 		].
 	    ].
 	    realized ifFalse:[
@@ -2206,43 +2267,10 @@
      first destroy menu if there is one and also destroy the GC.
      then the view is physically destroyed."
 
-    |id|
-
-    self middleButtonMenu:nil.
-    self keyCommands:nil.
-    id := gcId.
-    id notNil ifTrue:[
-        gcId := nil.
-        device destroyGC:id.
-    ].
-    self destroyView.
-    Lobby unregister:self.
-
-    "Modified: 8.2.1997 / 15:50:04 / cg"
-!
-
-destroyGC
-    "physically destroy the gc"
-
-    |id|
-
-    id := gcId.
-    id notNil ifTrue:[
-	gcId := nil.
-	device destroyGC:id.
-    ].
-!
-
-destroyView
-    "physically destroy the view."
-
-    |id|
-
-    (id := drawableId) notNil ifTrue:[
-	drawableId := nil.
-	device destroyView:self withId:id.
-	realized := false.
-    ].
+    self
+	middleButtonMenu:nil;
+	keyCommands:nil.
+    super destroy.
 !
 
 destroyed
@@ -2250,9 +2278,9 @@
 
     |id|
 
-    (id := drawableId) notNil ifTrue:[
-	drawableId := nil.
-	device removeKnownView:self withId:id.
+    (id := self drawableId) notNil ifTrue:[
+	self setId:nil.
+	self graphicsDevice removeKnownView:self withId:id.
 	realized := false.
     ].
     self destroy
@@ -2260,22 +2288,6 @@
     "Modified: 22.3.1997 / 14:56:34 / cg"
 !
 
-executor
-    "redefined for faster creation of finalization copies
-     (only device, gcId and drawableId are needed)"
-
-    |aCopy container parentId|
-
-    container := self container.
-    container notNil ifTrue:[ parentId := container id ].
-
-    aCopy := DeviceViewHandle basicNew.
-    aCopy setDevice:device id:drawableId gcId:gcId parentId:parentId.
-    ^ aCopy
-
-    "Created: 3.5.1996 / 15:35:13 / stefan"
-!
-
 initCursor
     "default cursor for all views"
 
@@ -2294,10 +2306,10 @@
     super initialize.
 
     eventMask := 0.
-    device notNil ifTrue:[
-	eventMask := device defaultEventMask.
+    self graphicsDevice notNil ifTrue:[
+	eventMask := self graphicsDevice defaultEventMask.
     ].
-    viewBackground := background.
+    viewBackground := self background.
     backed := false.
     flags := 0.
     self initCursor
@@ -2305,6 +2317,12 @@
     "Modified: 18.1.1997 / 18:09:41 / cg"
 !
 
+prepareForReinit
+    gc notNil ifTrue:[
+	gc prepareForReinit.
+    ].
+!
+
 reAdjustGeometry
     "sent late during snapin processing, nothing done here"
 
@@ -2315,10 +2333,12 @@
     "recreate (i.e. tell X about me) after a snapin or a migration"
 
     viewBackground isColor ifTrue:[
-	viewBackground := viewBackground onDevice:device
+	viewBackground := viewBackground onDevice:self graphicsDevice
     ].
     super recreate.
-    cursor := cursor onDevice:device.
+    cursor notNil ifTrue:[
+	cursor := cursor onDevice:self graphicsDevice.
+    ].
 
     "Modified: 28.3.1997 / 13:48:06 / cg"
 !
@@ -2330,14 +2350,8 @@
 !
 
 releaseDeviceResources
-    self destroyGC.
-    self destroyView.
-    self unregisterFromLobby.
+    super destroy.
     self setDevice:nil id:nil gcId:nil.
-!
-
-unregisterFromLobby
-    Lobby unregister:self.
 ! !
 
 !DisplaySurface methodsFor:'keyboard commands'!
@@ -2375,12 +2389,12 @@
     "return true, if a button motion event is pending.
      Normally, you don't want to use this, since no polling is needed
      (not even for mouse-tracking).
-     Also, don't use it, since it does not honor the windowGroup, 
+     Also, don't use it, since it does not honor the windowGroup,
      but goes directly to the device instead.
      Actually, its a historical leftover"
 
-    device flush.
-    ^ device eventPending:#buttonMotion for:drawableId
+    self graphicsDevice flush.
+    ^ self graphicsDevice eventPending:#buttonMotion for:self drawableId
 !
 
 buttonReleaseEventPending
@@ -2389,8 +2403,8 @@
      goes directly to the device instead.
      Actually, its a historical leftover"
 
-    device flush.
-    ^ device eventPending:#buttonRelease for:drawableId
+    self graphicsDevice flush.
+    ^ self graphicsDevice eventPending:#buttonRelease for:self drawableId
 !
 
 exposeEventPending
@@ -2402,7 +2416,7 @@
     windowGroup notNil ifTrue:[
 	(windowGroup sensor hasExposeEventFor:self) ifTrue:[^ true].
     ].
-    ^ device eventPending:#expose for:drawableId
+    ^ self graphicsDevice eventPending:#expose for:self drawableId
 
     "Modified: / 15.9.1998 / 23:18:16 / cg"
 !
@@ -2504,7 +2518,7 @@
 beep
     "output an audible beep or bell on my screen device"
 
-    device beep; flush
+    self graphicsDevice beep; flush
 
     "Created: 28.5.1996 / 16:16:13 / cg"
     "Modified: 28.5.1996 / 16:58:25 / cg"
@@ -2519,78 +2533,10 @@
     "Modified: 18.5.1996 / 15:44:33 / cg"
 ! !
 
-!DisplaySurface::DeviceViewHandle class methodsFor:'documentation'!
-
-documentation
-"
-    This is used as a finalization handle for views - in previous systems,
-    a shallowCopy of a view was responsible to destroy the underlying
-    devices view. To make the memory requirements smaller and to speed up
-    view creation a bit, this lightweight class is used now, which only
-    keeps the device handle for finalization.
-
-    [see also:]
-	DeviceHandle DisplaySurface
-
-    [author:]
-	Claus Gittinger
-"
-! !
-
-!DisplaySurface::DeviceViewHandle methodsFor:'finalization'!
-
-finalize
-    "the view for which I am a handle was collected
-     - release system resources"
-
-    |id|
-
-    drawableId notNil ifTrue:[
-	[
-	    (device viewIdKnown:drawableId) ifTrue:[
-"/ 'Display [info]: recycled view (' infoPrint. v infoPrint. ') not destroyed: ' infoPrint.
-"/ drawableId displayString infoPrintCR.
-		drawableId := nil.
-	    ] ifFalse:[
-		(id := gcId) notNil ifTrue:[
-		    gcId := nil.
-		    device deviceIOErrorSignal handle:[:ex |
-		    ] do:[
-			device destroyGC:id.
-		    ]
-		].
-
-		"/ care for lost-view trouble:
-		"/ if the windowID is still registered,
-		"/ this may be due to a not-yet-reclaimed
-		"/ subview of a view which has already been destroyed
-		"/ (X recycles window handles.)
-		"/ In this case, we arrive here with a nil-view argument,
-		"/ and a windowId, which is already reused for some other view.
-		"/ The situation is detected by finding a non-nil (and non-zero)
-		"/ view in the devices id<->view table for the given windowId.
-
-"/ 'GC destroy: ' print. drawableId displayString printCR.
-"/ device checkKnownViewId:drawableId.
-		id := drawableId.
-		drawableId := nil.
-		device deviceIOErrorSignal handle:[:ex |
-		] do:[
-		    device destroyView:nil withId:id.
-		].
-		DeviceGraphicsContext cleanupLobbyForChildrenOfViewWithDevice:device id:id.
-	    ]
-	] valueUninterruptably.
-    ].
-
-    "Created: / 25.9.1997 / 10:01:46 / stefan"
-    "Modified: / 15.11.2001 / 14:17:12 / cg"
-! !
-
 !DisplaySurface class methodsFor:'documentation'!
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libview/DisplaySurface.st,v 1.160 2014-02-05 13:30:29 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview/DisplaySurface.st,v 1.162.2.1 2014-05-08 08:27:50 stefan Exp $'
 ! !