DisplaySurface.st
changeset 2300 87306f56da51
parent 2196 f78bbe9789b0
child 2341 a7dc2588d6dc
--- a/DisplaySurface.st	Tue Sep 08 11:58:41 1998 +0200
+++ b/DisplaySurface.st	Tue Sep 08 11:59:30 1998 +0200
@@ -54,36 +54,36 @@
 
     [instance variables:]
 
-        viewBackground  <Color|Form|Image>      the views background
+	viewBackground  <Color|Form|Image>      the views background
 
-        cursor          <Cursor>                the cursor
+	cursor          <Cursor>                the cursor
 
-        eventMask                               mask specifying the enabled
-                                                events.
+	eventMask                               mask specifying the enabled
+						events.
 
-        middleButtonMenu                        a popup menu for the middle
-                                                button.
+	middleButtonMenu                        a popup menu for the middle
+						button.
 
-        keyCommands                             not yet supported
+	keyCommands                             not yet supported
 
-        gotExpose                               for exposure handling after
-        exposePending                           after a scroll
+	gotExpose                               for exposure handling after
+	exposePending                           after a scroll
 
-        backed                                  true if backing store for that
-                                                view is enabled
+	backed                                  true if backing store for that
+						view is enabled
 
-        saveUnder                               true if saveunder store for 
-                                                that view is enabled
+	saveUnder                               true if saveunder store for 
+						that view is enabled
 
-        delegate                                for event delegation
+	delegate                                for event delegation
 
     [see also:]
-        DeviceWorkstation
-        WindowGroup
-        StandardSYstemView SimpleView View
+	DeviceWorkstation
+	WindowGroup
+	StandardSYstemView SimpleView View
 
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 "
 ! !
 
@@ -117,94 +117,117 @@
     "install the viewBackground for the receiver on the device"
 
     |id devBgPixmap bgPixmap w h colorMap 
-     pixmapDepth deviceDepth|
+     pixmapDepth deviceDepth defBG|
 
     drawableId notNil ifTrue:[
-        viewBackground isColor ifTrue:[
-            viewBackground := viewBackground on: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:[
-            "
-             assume, it can convert itself to a form
-            "
-            bgPixmap := viewBackground asFormOn:device
-        ].
+	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:[
+	    "
+	     assume, it can convert itself to a form
+	    "
+	    bgPixmap := viewBackground asFormOn:device
+	].
 
-        "
-         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)
 
-        w := bgPixmap width.
-        h := bgPixmap height.
+	device supportsViewBackgroundPixmaps ifFalse:[
+	    defBG := View defaultViewBackgroundColor.
+	    defBG isColor ifTrue:[
+		defBG := defBG onDevice:device.
+		id := defBG colorId.
+		id notNil ifTrue:[
+		    device setWindowBackground:id in:drawableId.
+		].
+	    ].
+	].
 
-        deviceDepth := device depth.
-        pixmapDepth := bgPixmap depth.
+	"
+	 must now have:
+	 a dithered color or bitmap or pixmap
+	"
+	bgPixmap isNil ifTrue:[
+	    'DisplaySurface [warning]: background not convertable - ignored' errorPrintCR.
+	    ^ self
+	].
 
-        (pixmapDepth ~~ deviceDepth) ifTrue:[
-            (pixmapDepth ~~ 1) ifTrue:[
-                self error:'bad dither depth (must be one or devices depth)'.
-                ^ self
-            ].
+	w := bgPixmap width.
+	h := bgPixmap height.
+
+	deviceDepth := device depth.
+	pixmapDepth := bgPixmap depth.
+
+	(pixmapDepth ~~ deviceDepth) ifTrue:[
+	    (pixmapDepth ~~ 1) ifTrue:[
+		self error:'bad dither depth (must be one or devices depth)'.
+		^ self
+	    ].
 
-            "
-             convert it into a deep form
-            "
-            colorMap := bgPixmap colorMap.
-            devBgPixmap := Form width:w height:h depth:deviceDepth on:device.
-            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
-                    ]
-                ].
+	    "
+	     convert it into a deep form
+	    "
+	    colorMap := bgPixmap colorMap.
+	    devBgPixmap := Form width:w height:h depth:deviceDepth on: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 on: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.
+		"
+		 no, must invert it
+		"
+		devBgPixmap := Form width:w height:h depth:deviceDepth on: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.
     ]
 
-    "Modified: 16.1.1997 / 23:53:45 / cg"
+    "Modified: / 6.9.1998 / 14:19:23 / cg"
 !
 
 viewBackground
@@ -297,16 +320,16 @@
      Cursors are typically set at view creation time and left as installed."
 
     aCursor notNil ifTrue:[
-        (aCursor ~~ cursor) ifTrue:[
-            cursor := aCursor.
-            drawableId notNil ifTrue:[
+	(aCursor ~~ cursor) ifTrue:[
+	    cursor := aCursor.
+	    drawableId notNil ifTrue:[
 		self setCursor.
-                (showImmediately and:[realized]) ifTrue:[
-                    "flush, to make cursor immediately visible"
-                    device flush
-                ]
-            ]
-        ]
+		(showImmediately and:[realized]) ifTrue:[
+		    "flush, to make cursor immediately visible"
+		    device flush
+		]
+	    ]
+	]
     ]
 
     "
@@ -317,10 +340,10 @@
      v open.
      [v shown] whileFalse:[Processor yield].
      [v shown] whileTrue:[   
-        (Delay forSeconds:1) wait.
-        v cursor:(Cursor normal).
-        (Delay forSeconds:1) wait.
-        v cursor:(Cursor wait).
+	(Delay forSeconds:1) wait.
+	v cursor:(Cursor normal).
+	(Delay forSeconds:1) wait.
+	v cursor:(Cursor wait).
      ]
     "
 
@@ -357,7 +380,7 @@
     |savedCursor|
 
     cursor == aCursor ifTrue:[
-        ^ aBlock value
+	^ aBlock value
     ].
 
     savedCursor := cursor.
@@ -609,7 +632,7 @@
 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)"
+	  (restored view looses its position & wg process)"
 
     |wasRealized|
 
@@ -621,7 +644,7 @@
     realized := false.
     self recreate.
     wasRealized ifTrue:[
-        self remap
+	self remap
     ]
 
 
@@ -727,6 +750,57 @@
     self paint:oldPaint
 !
 
+fillWithViewBackgroundX:x y:y width:w height:h
+    "fill a rectangular area with the viewBackground.
+     A helper for devices which do not support background pixmaps
+     (i.e. win32 screens).
+     Caller must ensure that viewBackground is really a form"
+
+    |pW pH xR yR oldFg oldBg oldClip fg bg|
+
+    pW := viewBackground width.
+    pH := viewBackground height.
+
+    oldFg := foreground.
+    oldBg := background.
+    oldClip := self clippingRectangleOrNil.
+
+    viewBackground depth == 1 ifTrue:[
+	viewBackground colorMap notNil ifTrue:[
+	    bg := viewBackground colorMap at:1.
+	    fg := viewBackground colorMap at:2.
+	] ifFalse:[
+	    bg := Color white.
+	    fg := Color black.
+	].
+	self foreground:fg.
+	self background:bg.
+    ].
+    self clippingRectangle:(x@y extent:w@h).
+
+    yR := (y // pH) * pH.
+
+    [yR < (y+h)] whileTrue:[
+	xR := (x // pW) * pW.
+	[xR < (x+w)] whileTrue:[
+	    self
+		copyFrom:viewBackground 
+		x:0 y:0 
+		toX:xR y:yR 
+		width:pW height:pH 
+		async:false.
+	    xR := xR + pW.
+	].
+	yR := yR + pH.
+    ].
+
+    self foreground:oldFg.
+    self background:oldBg.
+    self clippingRectangle:oldClip.
+
+    "Created: / 6.9.1998 / 14:00:50 / cg"
+!
+
 redraw
     "nothing done here"
 
@@ -898,20 +972,20 @@
     "dispatch the event"
 
     self 
-        dispatchEvent:event type
-        arguments:(event arguments)
-        withFocusOn:nil
-        delegate:true
+	dispatchEvent:event type
+	arguments:(event arguments)
+	withFocusOn:nil
+	delegate:true
 
     "Modified: / 20.5.1998 / 23:01:15 / cg"
 !
 
 dispatchEvent:type arguments:arguments
     ^ self 
-        dispatchEvent:type 
-        arguments:arguments 
-        withFocusOn:nil 
-        delegate:true
+	dispatchEvent:type 
+	arguments:arguments 
+	withFocusOn:nil 
+	delegate:true
 
     "Modified: / 20.5.1998 / 22:50:31 / cg"
 !
@@ -940,70 +1014,70 @@
     isKeyEvent := isButtonEvent := isPointerEvent := false.
 
     type == #damage ifTrue:[
-        self shown ifTrue:[
-            rect := argArray.
-            x := rect left.
-            y := rect top.
-            w := rect width.
-            h := rect height.
-            transformation notNil ifTrue:[
-                self deviceExposeX:x y:y width:w height:h
-            ] ifFalse:[
-                self exposeX:x y:y width:w height:h
-            ]
-        ].
-        ^ self
+	self shown ifTrue:[
+	    rect := argArray.
+	    x := rect left.
+	    y := rect top.
+	    w := rect width.
+	    h := rect height.
+	    transformation notNil ifTrue:[
+		self deviceExposeX:x y:y width:w height:h
+	    ] ifFalse:[
+		self exposeX:x y:y width:w height:h
+	    ]
+	].
+	^ self
     ].
 
     (type == #'keyPress:x:y:') ifTrue:[
-        isKeyEvent := true.
-        deviceMessage := #'deviceKeyPress:x:y:'.
-        delegateMessage := #'keyPress:x:y:view:'.
-        delegateQuery := #'handlesKeyPress:inView:'.
+	isKeyEvent := true.
+	deviceMessage := #'deviceKeyPress:x:y:'.
+	delegateMessage := #'keyPress:x:y:view:'.
+	delegateQuery := #'handlesKeyPress:inView:'.
     ] ifFalse:[ (type == #'keyRelease:x:y:') ifTrue:[
-        isKeyEvent := true.
-        deviceMessage := #'deviceKeyRelease:x:y:'.
-        delegateMessage := #'keyRelease:x:y:view:'.
-        delegateQuery := #'handlesKeyRelease:inView:'.
+	isKeyEvent := true.
+	deviceMessage := #'deviceKeyRelease:x:y:'.
+	delegateMessage := #'keyRelease:x:y:view:'.
+	delegateQuery := #'handlesKeyRelease:inView:'.
     ] ifFalse:[ (type == #'buttonMotion:x:y:') ifTrue:[
-        isButtonEvent := true.
-        deviceMessage := #'deviceButtonMotion:x:y:'.
-        delegateMessage := #'buttonMotion:x:y:view:'.
-        delegateQuery := #'handlesButtonMotion:inView:'.
+	isButtonEvent := true.
+	deviceMessage := #'deviceButtonMotion:x:y:'.
+	delegateMessage := #'buttonMotion:x:y:view:'.
+	delegateQuery := #'handlesButtonMotion:inView:'.
     ] ifFalse:[ (type == #'buttonPress:x:y:') ifTrue:[
-        isButtonEvent := true.
-        deviceMessage := #'deviceButtonPress:x:y:'.
-        delegateMessage := #'buttonPress:x:y:view:'.
-        delegateQuery := #'handlesButtonPress:inView:'.
+	isButtonEvent := true.
+	deviceMessage := #'deviceButtonPress:x:y:'.
+	delegateMessage := #'buttonPress:x:y:view:'.
+	delegateQuery := #'handlesButtonPress:inView:'.
     ] ifFalse:[ (type == #'buttonRelease:x:y:') ifTrue:[
-        isButtonEvent := true.
-        deviceMessage := #'deviceButtonRelease:x:y:'.
-        delegateMessage := #'buttonRelease:x:y:view:'.
-        delegateQuery := #'handlesButtonRelease:inView:'.
+	isButtonEvent := true.
+	deviceMessage := #'deviceButtonRelease:x:y:'.
+	delegateMessage := #'buttonRelease:x:y:view:'.
+	delegateQuery := #'handlesButtonRelease:inView:'.
     ] ifFalse:[ (type == #'buttonShiftPress:x:y:') ifTrue:[
-        isButtonEvent := true.
-        deviceMessage := #'deviceButtonShiftPress:x:y:'.
-        delegateMessage := #'buttonShiftPress:x:y:view:'.
-        delegateQuery := #'handlesButtonShiftPress:inView:'.
+	isButtonEvent := true.
+	deviceMessage := #'deviceButtonShiftPress:x:y:'.
+	delegateMessage := #'buttonShiftPress:x:y:view:'.
+	delegateQuery := #'handlesButtonShiftPress:inView:'.
     ] ifFalse:[ (type == #'buttonMultiPress:x:y:') ifTrue:[
-        isButtonEvent := true.
-        deviceMessage := #'deviceButtonMultiPress:x:y:'.
-        delegateMessage := #'buttonMultiPress:x:y:view:'.
-        delegateQuery := #'handlesButtonMultiPress:inView:'.
+	isButtonEvent := true.
+	deviceMessage := #'deviceButtonMultiPress:x:y:'.
+	delegateMessage := #'buttonMultiPress:x:y:view:'.
+	delegateQuery := #'handlesButtonMultiPress:inView:'.
     ] ifFalse:[ (type == #'pointerEnter:x:y:') ifTrue:[
-        isPointerEvent := true.
-        deviceMessage := #'devicePointerEnter:x:y:'.
-        delegateMessage := #'pointerEnter:x:y:view:'.
-        delegateQuery := #'handlesPointerEnter:inView:'.
+	isPointerEvent := true.
+	deviceMessage := #'devicePointerEnter:x:y:'.
+	delegateMessage := #'pointerEnter:x:y:view:'.
+	delegateQuery := #'handlesPointerEnter:inView:'.
     ] ifFalse:[ (type == #'pointerLeave:') ifTrue:[
-        isPointerEvent := true.
-        deviceMessage := type.
-        delegateMessage := #'pointerLeave:view:'.
-        delegateQuery := #'handlesPointerLeave:inView:'.
+	isPointerEvent := true.
+	deviceMessage := type.
+	delegateMessage := #'pointerLeave:view:'.
+	delegateQuery := #'handlesPointerLeave:inView:'.
     ] ifFalse:[ (type == #'exposeX:y:width:height:') ifTrue:[
-        deviceMessage := #'deviceExposeX:y:width:height:'.
+	deviceMessage := #'deviceExposeX:y:width:height:'.
     ] ifFalse:[ (type == #'graphicsExposeX:y:width:height:final:') ifTrue:[
-        deviceMessage := #'deviceGraphicsExposeX:y:width:height:final:'.
+	deviceMessage := #'deviceGraphicsExposeX:y:width:height:final:'.
     ]]]]]]]]]]].
 
     "
@@ -1014,62 +1088,62 @@
     "
     (focusView notNil 
     and:[isKeyEvent]) ifTrue:[
-        focusView 
-            dispatchEvent:type 
-            arguments:(Array with:(argArray at:1) with:0 with:0)
-            withFocusOn:nil
-            delegate:doDelegate.
-        ^ self
+	focusView 
+	    dispatchEvent:type 
+	    arguments:(Array with:(argArray at:1) with:0 with:0)
+	    withFocusOn:nil
+	    delegate:doDelegate.
+	^ self
     ].
 
     doDelegate ifTrue:[
-        "
-         handle delegated messages
-        "
-        (isKeyEvent 
-         or:[isButtonEvent 
-         or:[isPointerEvent]]) ifTrue:[
-            delegate := self delegate.
+	"
+	 handle delegated messages
+	"
+	(isKeyEvent 
+	 or:[isButtonEvent 
+	 or:[isPointerEvent]]) ifTrue:[
+	    delegate := self delegate.
 
-            "
-             what a kludge - sending to delegate requires
-             another selector and an additional argument ...
-            "
-            (delegate notNil
-            and:[delegate respondsTo:delegateMessage]) ifTrue:[
-                "
-                 is the delegate interested in that event ?
-                 (if it does not respond to the handlesXXX message,
-                  we assume: NO)
-                "
-                ((delegate respondsTo:delegateQuery) 
-                and:[delegate perform:delegateQuery with:(argArray at:1) with:self]) ifTrue:[
-                    "
-                     mhmh ... have to convert to logical coordinates
-                    "        
-                    transformation 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 isNil ifTrue:[
-                        delegate perform:delegateMessage with:self
-                    ] ifFalse:[
-                        delegate perform:delegateMessage withArguments:(argArray copyWith:self)
-                    ].
-                    ^ self
-                ]
-            ].
-        ].
+	    "
+	     what a kludge - sending to delegate requires
+	     another selector and an additional argument ...
+	    "
+	    (delegate notNil
+	    and:[delegate respondsTo:delegateMessage]) ifTrue:[
+		"
+		 is the delegate interested in that event ?
+		 (if it does not respond to the handlesXXX message,
+		  we assume: NO)
+		"
+		((delegate respondsTo:delegateQuery) 
+		and:[delegate perform:delegateQuery with:(argArray at:1) with:self]) ifTrue:[
+		    "
+		     mhmh ... have to convert to logical coordinates
+		    "        
+		    transformation 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 isNil ifTrue:[
+			delegate perform:delegateMessage with:self
+		    ] ifFalse:[
+			delegate perform:delegateMessage withArguments:(argArray copyWith:self)
+		    ].
+		    ^ self
+		]
+	    ].
+	].
     ].
 
     (isKeyEvent 
      or:[isButtonEvent 
      or:[isPointerEvent]]) ifTrue:[
-        realized ifFalse:[
-            ^ self
-        ]
+	realized ifFalse:[
+	    ^ self
+	]
     ].
 
     "
@@ -1077,13 +1151,13 @@
     "
     eventReceiver := self.
     (controller := self controller) notNil ifTrue:[  
-        (isKeyEvent 
-         or:[isButtonEvent 
-         or:[isPointerEvent
-         or:[(type == #focusIn)
-         or:[(type == #focusOut)]]]]) ifTrue:[
-            eventReceiver := controller.
-        ]
+	(isKeyEvent 
+	 or:[isButtonEvent 
+	 or:[isPointerEvent
+	 or:[(type == #focusIn)
+	 or:[(type == #focusOut)]]]]) ifTrue:[
+	    eventReceiver := controller.
+	]
     ].
 
     "
@@ -1099,13 +1173,13 @@
     selector := type.
 
     transformation notNil ifTrue:[
-        (isKeyEvent
-         or:[isButtonEvent
-         or:[isPointerEvent
-         or:[(type == #'exposeX:y:width:height:')
-         or:[(type == #'graphicsExposeX:y:width:height:final:')]]]]) ifTrue:[
-            selector := deviceMessage
-        ]        
+	(isKeyEvent
+	 or:[isButtonEvent
+	 or:[isPointerEvent
+	 or:[(type == #'exposeX:y:width:height:')
+	 or:[(type == #'graphicsExposeX:y:width:height:final:')]]]]) ifTrue:[
+	    selector := deviceMessage
+	]        
     ].
 
     eventReceiver perform:selector withArguments:argArray
@@ -1120,7 +1194,7 @@
     "if there is a menu, show it."
 
     middleButtonMenu notNil ifTrue:[
-        middleButtonMenu showAtPointer
+	middleButtonMenu showAtPointer
     ]
 
     "Created: 1.3.1996 / 13:24:55 / cg"
@@ -1143,7 +1217,7 @@
      show it."
 
     ((button == 2) or:[button == #menu]) ifTrue:[
-        self activateMenu.
+	self activateMenu.
     ]
 
     "Modified: 1.3.1996 / 13:25:07 / cg"
@@ -1167,8 +1241,8 @@
     |wg|
 
     device scrollsAsynchronous ifFalse:[
-        gotExpose := true.
-        ^ self
+	gotExpose := true.
+	^ self
     ].
 
     self setGraphicsExposures:true.
@@ -1176,13 +1250,13 @@
     gotExpose := false.
     wg := self windowGroup.
     wg notNil ifTrue:[
-        "
-         must process eny pending expose events, since
-         usually the origin is changed soon so that previous
-         expose events coordinates are invalid 
-        "
-        wg processRealExposeEventsFor:self.
-        wg sensor catchExposeFor:self
+	"
+	 must process eny pending expose events, since
+	 usually the origin is changed soon so that previous
+	 expose events coordinates are invalid 
+	"
+	wg processRealExposeEventsFor:self.
+	wg sensor catchExposeFor:self
     ]
 
     "Modified: 6.8.1997 / 19:50:15 / cg"
@@ -1204,10 +1278,10 @@
     lx := x.
     ly := y.
     transformation notNil ifTrue:[
-        lx notNil ifTrue:[
-            lx := transformation applyInverseToX:lx.
-            ly := transformation applyInverseToY:ly.
-        ].
+	lx notNil ifTrue:[
+	    lx := transformation applyInverseToX:lx.
+	    ly := transformation applyInverseToY:ly.
+	].
     ].
     self buttonMotion:state x:lx y:ly
 
@@ -1231,10 +1305,10 @@
     lx := x.
     ly := y.
     transformation notNil ifTrue:[
-        lx notNil ifTrue:[
-            lx := transformation applyInverseToX:lx.
-            ly := transformation applyInverseToY:ly.
-        ].
+	lx notNil ifTrue:[
+	    lx := transformation applyInverseToX:lx.
+	    ly := transformation applyInverseToY:ly.
+	].
     ].
     self buttonMultiPress:butt x:lx y:ly
 
@@ -1258,10 +1332,10 @@
     lx := x.
     ly := y.
     transformation notNil ifTrue:[
-        lx notNil ifTrue:[
-            lx := transformation applyInverseToX:lx.
-            ly := transformation applyInverseToY:ly.
-        ].
+	lx notNil ifTrue:[
+	    lx := transformation applyInverseToX:lx.
+	    ly := transformation applyInverseToY:ly.
+	].
     ].
     self buttonPress:butt x:lx y:ly
 
@@ -1285,10 +1359,10 @@
     lx := x.
     ly := y.
     transformation notNil ifTrue:[
-        lx notNil ifTrue:[
-            lx := transformation applyInverseToX:lx.
-            ly := transformation applyInverseToY:ly.
-        ].
+	lx notNil ifTrue:[
+	    lx := transformation applyInverseToX:lx.
+	    ly := transformation applyInverseToY:ly.
+	].
     ].
     self buttonRelease:butt x:lx y:ly
 
@@ -1312,10 +1386,10 @@
     lx := x.
     ly := y.
     transformation notNil ifTrue:[
-        lx notNil ifTrue:[
-            lx := transformation applyInverseToX:lx.
-            ly := transformation applyInverseToY:ly.
-        ].
+	lx notNil ifTrue:[
+	    lx := transformation applyInverseToX:lx.
+	    ly := transformation applyInverseToY:ly.
+	].
     ].
     self buttonShiftPress:butt x:lx y:ly
 
@@ -1341,10 +1415,10 @@
     lw := w.
     lh := h.
     transformation notNil ifTrue:[
-        lx := transformation applyInverseToX:lx.
-        ly := transformation applyInverseToY:ly.
-        lw := transformation applyInverseScaleX:lw.
-        lh := transformation applyInverseScaleY:lh.
+	lx := transformation applyInverseToX:lx.
+	ly := transformation applyInverseToY:ly.
+	lw := transformation applyInverseScaleX:lw.
+	lh := transformation applyInverseScaleY:lh.
     ].
     self exposeX:lx y:ly width:lw height:lh
 
@@ -1370,10 +1444,10 @@
     lw := w.
     lh := h.
     transformation notNil ifTrue:[
-        lx := transformation applyInverseToX:lx.
-        ly := transformation applyInverseToY:ly.
-        lw := transformation applyInverseScaleX:lw.
-        lh := transformation applyInverseScaleY:lh.
+	lx := transformation applyInverseToX:lx.
+	ly := transformation applyInverseToY:ly.
+	lw := transformation applyInverseScaleX:lw.
+	lh := transformation applyInverseScaleY:lh.
     ].
     self graphicsExposeX:lx y:ly width:lw height:lh final:final
 
@@ -1397,10 +1471,10 @@
     lx := x.
     ly := y.
     transformation notNil ifTrue:[
-        lx notNil ifTrue:[
-            lx := transformation applyInverseToX:lx.
-            ly := transformation applyInverseToY:ly.
-        ]
+	lx notNil ifTrue:[
+	    lx := transformation applyInverseToX:lx.
+	    ly := transformation applyInverseToY:ly.
+	]
     ].
     self keyPress:key x:lx y:ly
 
@@ -1424,10 +1498,10 @@
     lx := x.
     ly := y.
     transformation notNil ifTrue:[
-        lx notNil ifTrue:[
-            lx := transformation applyInverseToX:lx.
-            ly := transformation applyInverseToY:ly.
-        ]
+	lx notNil ifTrue:[
+	    lx := transformation applyInverseToX:lx.
+	    ly := transformation applyInverseToY:ly.
+	]
     ].
     self keyRelease:key x:lx y:ly
 
@@ -1451,10 +1525,10 @@
     lx := x.
     ly := y.
     transformation notNil ifTrue:[
-        lx notNil ifTrue:[
-            lx := transformation applyInverseToX:lx.
-            ly := transformation applyInverseToY:ly.
-        ]
+	lx notNil ifTrue:[
+	    lx := transformation applyInverseToX:lx.
+	    ly := transformation applyInverseToY:ly.
+	]
     ].
     self pointerEnter:state x:lx y:ly
 
@@ -1494,18 +1568,18 @@
     |action|
 
     keyCommands notNil ifTrue:[
-        action := keyCommands at:key ifAbsent:[nil].
-        action notNil ifTrue:[
-            action value
-        ]
+	action := keyCommands at:key ifAbsent:[nil].
+	action notNil ifTrue:[
+	    action value
+	]
     ].
     key isSymbol ifTrue:[
-        (key startsWith:#Basic) ifTrue:[
-            "/ an unhandled BasicFoo key;
-            "/ retry as Foo
+	(key startsWith:#Basic) ifTrue:[
+	    "/ an unhandled BasicFoo key;
+	    "/ retry as Foo
 
-            self keyPress:(key copyFrom:#Basic size) asSymbol x:x y:y
-        ].
+	    self keyPress:(key copyFrom:#Basic size) asSymbol x:x y:y
+	].
     ].
 
     "Modified: 6.11.1996 / 17:51:15 / cg"
@@ -1515,12 +1589,12 @@
     "default action is to do nothing"
     
     key isSymbol ifTrue:[
-        (key startsWith:#Basic) ifTrue:[
-            "/ an unhandled BasicFoo key;
-            "/ retry as Foo
+	(key startsWith:#Basic) ifTrue:[
+	    "/ an unhandled BasicFoo key;
+	    "/ retry as Foo
 
-            self keyRelease:(key copyFrom:#Basic size) asSymbol x:x y:y
-        ].
+	    self keyRelease:(key copyFrom:#Basic size) asSymbol x:x y:y
+	].
     ].
 
     ^ self
@@ -1556,45 +1630,45 @@
     |wg endPollTime|
 
     device scrollsAsynchronous ifFalse:[
-        gotExpose := true.
-        ^ self
+	gotExpose := true.
+	^ self
     ].
 
     wg := self windowGroup.
     wg notNil ifTrue:[
-        "/
-        "/ a normal (suspendable) view.
-        "/ wait by doing a real wait
-        "/
-         wg waitForExposeFor:self
+	"/
+	"/ a normal (suspendable) view.
+	"/ wait by doing a real wait
+	"/
+	 wg waitForExposeFor:self
     ] ifFalse:[
-        "/
-        "/ a pure event driven view.
-        "/ wait by doing a direct dispatch loop until the event arrives.
-        "/ i.e. poll for the event
-        "/
-        endPollTime := AbsoluteTime now addSeconds:10.
+	"/
+	"/ a pure event driven view.
+	"/ wait by doing a direct dispatch loop until the event arrives.
+	"/ i.e. poll for the event
+	"/
+	endPollTime := AbsoluteTime now addSeconds:10.
 
-        [gotExpose] whileFalse:[
-            realized ifTrue:[
-                (device exposeEventPendingFor:drawableId withSync:true) ifTrue:[
-                    device dispatchExposeEventFor:drawableId.
-                ].
-            ].
-            realized ifFalse:[
-                gotExpose := true.
-                ^ self
-            ].
+	[gotExpose] whileFalse:[
+	    realized ifTrue:[
+		(device exposeEventPendingFor:drawableId withSync:true) ifTrue:[
+		    device dispatchExposeEventFor:drawableId.
+		].
+	    ].
+	    realized ifFalse:[
+		gotExpose := true.
+		^ self
+	    ].
 
-            "/ break out of the poll after a while
+	    "/ break out of the poll after a while
 
-            AbsoluteTime now > endPollTime ifTrue:[
-                'DisplaySurface [warning]: lost expose event' errorPrintCR.
-                gotExpose := true.
-                ^ self
-            ].
-            Processor yield.
-        ].
+	    AbsoluteTime now > endPollTime ifTrue:[
+		'DisplaySurface [warning]: lost expose event' errorPrintCR.
+		gotExpose := true.
+		^ self
+	    ].
+	    Processor yield.
+	].
     ]
 
     "Modified: 19.8.1997 / 17:22:46 / cg"
@@ -1608,18 +1682,18 @@
      then the view is physically destroyed."
      
     middleButtonMenu notNil ifTrue:[
-        middleButtonMenu destroy.
-        middleButtonMenu := nil
+	middleButtonMenu destroy.
+	middleButtonMenu := nil
     ].
     keyCommands := nil.
     gcId notNil ifTrue:[
-        device destroyGC:gcId.
-        gcId := nil
+	device destroyGC:gcId.
+	gcId := nil
     ].
     drawableId notNil ifTrue:[
-        device destroyView:self withId:drawableId.
-        drawableId := nil.
-        realized := false.
+	device destroyView:self withId:drawableId.
+	drawableId := nil.
+	realized := false.
     ].
     Lobby unregister:self.
 
@@ -1630,9 +1704,9 @@
     "view has been destroyed by someone else"
 
     drawableId notNil ifTrue:[
-        device removeKnownView:self withId:drawableId.
-        drawableId := nil.
-        realized := false. 
+	device removeKnownView:self withId:drawableId.
+	drawableId := nil.
+	realized := false. 
     ].
     self destroy
 
@@ -1675,7 +1749,7 @@
     "recreate (i.e. tell X about me) after a snapin"
 
     viewBackground isColor ifTrue:[
-        viewBackground := viewBackground on:device
+	viewBackground := viewBackground on:device
     ].
     super recreate.
     cursor := cursor onDevice:device.
@@ -1846,8 +1920,8 @@
 
     sel := device getCopyBuffer.
     sel isNil ifTrue:[
-        sel := device getSelectionFor:drawableId.
-        sel isNil ifTrue:[^ nil].
+	sel := device getSelectionFor:drawableId.
+	sel isNil ifTrue:[^ nil].
     ].
     ^ sel
 
@@ -1862,8 +1936,8 @@
 
     sel := device getCopyBuffer.
     sel isNil ifTrue:[
-        sel := device getTextSelectionFor:drawableId.
-        sel isNil ifTrue:[^ nil].
+	sel := device getTextSelectionFor:drawableId.
+	sel isNil ifTrue:[^ nil].
     ].
     ^ sel
 
@@ -1888,7 +1962,7 @@
     device setCopyBuffer:something.
 
     (device setSelection:something owner:drawableId) ifFalse:[
-        'DisplaySurface [warning]: could not copy selection to clipBoard' errorPrintCR
+	'DisplaySurface [warning]: could not copy selection to clipBoard' errorPrintCR
     ]
 
     "Modified: 13.2.1997 / 13:19:51 / cg"
@@ -1904,14 +1978,14 @@
     device setCopyBuffer:something.
     s := something.
     s isString ifFalse:[
-        s := s asStringWithCRsFrom:1 to:(s size) compressTabs:false withCR:false
+	s := s asStringWithCRsFrom:1 to:(s size) compressTabs:false withCR:false
     ].
 
     "/ for now - should add support to pass emphasis information too
     s := s string.
 
     (device setTextSelection:s owner:drawableId) ifFalse:[
-        'DisplaySurface [warning]: could not copy selection to clipBoard' errorPrintCR.
+	'DisplaySurface [warning]: could not copy selection to clipBoard' errorPrintCR.
     ]
 
     "Modified: / 16.7.1998 / 21:38:55 / cg"
@@ -1948,10 +2022,10 @@
     keeps the device handle for finalization.
 
     [see also:]
-        DisplaySurface
+	DisplaySurface
 
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 "
 ! !
 
@@ -1964,32 +2038,32 @@
     |v id|
 
     drawableId notNil ifTrue:[
-        (id := gcId) notNil ifTrue:[
-            gcId := nil.
-            device destroyGC:id.
-        ].
+	(id := gcId) notNil ifTrue:[
+	    gcId := nil.
+	    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.
+	"/ 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.
 
-        (device viewIdKnown:drawableId) ifTrue:[
+	(device viewIdKnown:drawableId) ifTrue:[
 "/ 'Display [info]: recycled view (' infoPrint. v infoPrint. ') not destroyed: ' infoPrint.
 "/ drawableId displayString infoPrintCR.
-            drawableId := nil.
-        ] ifFalse:[
+	    drawableId := nil.
+	] ifFalse:[
 "/ 'GC destroy: ' print. drawableId displayString printCR.
 "/ device checkKnownViewId:drawableId.
 	    id := drawableId.
-            drawableId := nil.
-            device destroyView:nil withId:id.
-        ]
+	    drawableId := nil.
+	    device destroyView:nil withId:id.
+	]
     ].
 
     "Modified: 4.4.1997 / 11:01:48 / cg"
@@ -1999,5 +2073,5 @@
 !DisplaySurface class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview/DisplaySurface.st,v 1.42 1998-07-28 14:12:31 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview/DisplaySurface.st,v 1.43 1998-09-08 09:59:30 cg Exp $'
 ! !