*** empty log message ***
authorClaus Gittinger <cg@exept.de>
Sat, 22 May 1999 16:34:01 +0200
changeset 2720 c1ab612afb4a
parent 2719 cc6080a64232
child 2721 2575a1e771cc
*** empty log message ***
DSurface.st
DisplaySurface.st
bc.mak
nt.mak
ntw.mak
ntx.mak
--- a/DSurface.st	Sat May 22 16:33:27 1999 +0200
+++ b/DSurface.st	Sat May 22 16:34:01 1999 +0200
@@ -120,112 +120,112 @@
      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:[
-            "
-             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)
-
-        (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:[
-                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 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.
+	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)
+
+	(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:[
+		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 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.
     ]
 
     "Modified: / 4.5.1999 / 18:42:22 / cg"
@@ -517,10 +517,10 @@
     "tell the Display to assign keyboard focus to the receiver"
 
     drawableId notNil ifTrue:[
-        self shown ifTrue:[
+	self shown ifTrue:[
 "/            self requestFocus.
-            device setInputFocusTo:drawableId.
-        ]
+	    device setInputFocusTo:drawableId.
+	]
     ].
 
     "Modified: / 15.3.1999 / 08:25:10 / cg"
@@ -715,16 +715,16 @@
     |oldPaint org|
 
     viewBackground isColor ifFalse:[
-        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.
-        ]
+	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.
+	]
     ].
 
     "
@@ -746,15 +746,15 @@
     |pX pY pW pH|
 
     transformation notNil ifTrue:[
-        pX := transformation applyToX:x.
-        pY := transformation applyToY:y.
-        pW := transformation applyScaleX:w.
-        pH := transformation applyScaleY:h.
+	pX := transformation applyToX:x.
+	pY := transformation applyToY:y.
+	pW := transformation applyScaleX:w.
+	pH := transformation applyScaleY:h.
     ] ifFalse:[
-        pX := x.
-        pY := y.
-        pW := w.
-        pH := h.
+	pX := x.
+	pY := y.
+	pW := w.
+	pH := h.
     ].
 
     pX := pX rounded.
@@ -804,10 +804,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.
@@ -823,16 +823,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 := 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.
     ].
     self deviceClippingRectangle:(x@y extent:w@h).
 
@@ -841,24 +841,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.
 
@@ -875,9 +875,9 @@
      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
 
 !
 
@@ -891,26 +891,26 @@
     |pX pY nW nH|
 
     gcId isNil ifTrue:[
-        self initGC
+	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 := 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.
+	].
     ] ifFalse:[
-        pX := x.
-        pY := y.
-        nW := w.
-        nH := h.
+	pX := x.
+	pY := y.
+	nW := w.
+	nH := h.
     ].
     pX := pX rounded.
     pY := pY rounded.
@@ -918,9 +918,9 @@
     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"
 
@@ -934,9 +934,9 @@
      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
 
 !
 
@@ -1151,72 +1151,72 @@
      rect x y w h|
 
     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
     ].
 
     isKeyEvent := isButtonEvent := isPointerEvent := false.
 
     (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:'.
     ]]]]]]]]]]].
 
     "
@@ -1226,64 +1226,64 @@
      the focusView (0 @ 0) is passed as x/y coordinates.
     "
     (focusView notNil and:[self ~~ focusView]) ifTrue:[
-        isKeyEvent ifTrue:[
-            focusView 
-                dispatchEvent:type 
-                arguments:(Array with:(argArray at:1) with:-1 with:-1)
-                withFocusOn:nil
-                delegate:doDelegate.
-            ^ self
-        ].
-        type == #mouseWheelMotion:state: ifTrue:[
-            focusView 
-                dispatchEvent:type 
-                arguments:argArray
-                withFocusOn:nil
-                delegate:doDelegate.
-            ^ self
-        ]
+	isKeyEvent ifTrue:[
+	    focusView 
+		dispatchEvent:type 
+		arguments:(Array with:(argArray at:1) with:-1 with:-1)
+		withFocusOn:nil
+		delegate:doDelegate.
+	    ^ self
+	].
+	type == #mouseWheelMotion:state:deltaTime: ifTrue:[
+	    focusView 
+		dispatchEvent:type 
+		arguments:argArray
+		withFocusOn:nil
+		delegate:doDelegate.
+	    ^ self
+	]
     ].
 
     doDelegate ifTrue:[
-        "
-         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
-                ]
-            ].
-        ].
+	"
+	 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
+		]
+	    ].
+	].
     ].
 
     "
@@ -1292,9 +1292,9 @@
     (isKeyEvent 
      or:[isButtonEvent 
      or:[isPointerEvent]]) ifTrue:[
-        realized ifFalse:[
-            ^ self
-        ]
+	realized ifFalse:[
+	    ^ self
+	]
     ].
 
     "
@@ -1302,13 +1302,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.
+	]
     ].
 
     "
@@ -1324,13 +1324,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
@@ -1781,50 +1781,50 @@
     |wg endPollTime pollDelay|
 
     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
-        "/
-        device platformName = 'WIN32' ifTrue:[
-            pollDelay := 1.
-        ] ifFalse:[
-            pollDelay := 3.
-        ].
-        endPollTime := AbsoluteTime now addSeconds:pollDelay.
-
-        [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
-
-            AbsoluteTime now > endPollTime ifTrue:[
-                'DisplaySurface [warning]: lost expose event' errorPrintCR.
-                gotExpose := true.
-                ^ self
-            ].
-            Processor yield.
-        ].
+	"/
+	"/ a pure event driven view.
+	"/ wait by doing a direct dispatch loop until the event arrives.
+	"/ i.e. poll for the event
+	"/
+	device platformName = 'WIN32' ifTrue:[
+	    pollDelay := 1.
+	] ifFalse:[
+	    pollDelay := 3.
+	].
+	endPollTime := AbsoluteTime now addSeconds:pollDelay.
+
+	[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
+
+	    AbsoluteTime now > endPollTime ifTrue:[
+		'DisplaySurface [warning]: lost expose event' errorPrintCR.
+		gotExpose := true.
+		^ self
+	    ].
+	    Processor yield.
+	].
     ]
 
     "Modified: / 9.1.1999 / 01:58:09 / cg"
@@ -1838,13 +1838,13 @@
      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
     ].
     self destroyView.
     Lobby unregister:self.
@@ -1856,9 +1856,9 @@
     "physically destroy the view."
      
     drawableId notNil ifTrue:[
-        device destroyView:self withId:drawableId.
-        drawableId := nil.
-        realized := false.
+	device destroyView:self withId:drawableId.
+	drawableId := nil.
+	realized := false.
     ].
 !
 
@@ -2237,5 +2237,5 @@
 !DisplaySurface class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview/Attic/DSurface.st,v 1.66 1999-05-21 18:09:35 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview/Attic/DSurface.st,v 1.67 1999-05-22 14:33:05 cg Exp $'
 ! !
--- a/DisplaySurface.st	Sat May 22 16:33:27 1999 +0200
+++ b/DisplaySurface.st	Sat May 22 16:34:01 1999 +0200
@@ -120,112 +120,112 @@
      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:[
-            "
-             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)
-
-        (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:[
-                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 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.
+	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)
+
+	(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:[
+		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 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.
     ]
 
     "Modified: / 4.5.1999 / 18:42:22 / cg"
@@ -517,10 +517,10 @@
     "tell the Display to assign keyboard focus to the receiver"
 
     drawableId notNil ifTrue:[
-        self shown ifTrue:[
+	self shown ifTrue:[
 "/            self requestFocus.
-            device setInputFocusTo:drawableId.
-        ]
+	    device setInputFocusTo:drawableId.
+	]
     ].
 
     "Modified: / 15.3.1999 / 08:25:10 / cg"
@@ -715,16 +715,16 @@
     |oldPaint org|
 
     viewBackground isColor ifFalse:[
-        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.
-        ]
+	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.
+	]
     ].
 
     "
@@ -746,15 +746,15 @@
     |pX pY pW pH|
 
     transformation notNil ifTrue:[
-        pX := transformation applyToX:x.
-        pY := transformation applyToY:y.
-        pW := transformation applyScaleX:w.
-        pH := transformation applyScaleY:h.
+	pX := transformation applyToX:x.
+	pY := transformation applyToY:y.
+	pW := transformation applyScaleX:w.
+	pH := transformation applyScaleY:h.
     ] ifFalse:[
-        pX := x.
-        pY := y.
-        pW := w.
-        pH := h.
+	pX := x.
+	pY := y.
+	pW := w.
+	pH := h.
     ].
 
     pX := pX rounded.
@@ -804,10 +804,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.
@@ -823,16 +823,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 := 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.
     ].
     self deviceClippingRectangle:(x@y extent:w@h).
 
@@ -841,24 +841,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.
 
@@ -875,9 +875,9 @@
      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
 
 !
 
@@ -891,26 +891,26 @@
     |pX pY nW nH|
 
     gcId isNil ifTrue:[
-        self initGC
+	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 := 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.
+	].
     ] ifFalse:[
-        pX := x.
-        pY := y.
-        nW := w.
-        nH := h.
+	pX := x.
+	pY := y.
+	nW := w.
+	nH := h.
     ].
     pX := pX rounded.
     pY := pY rounded.
@@ -918,9 +918,9 @@
     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"
 
@@ -934,9 +934,9 @@
      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
 
 !
 
@@ -1151,72 +1151,72 @@
      rect x y w h|
 
     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
     ].
 
     isKeyEvent := isButtonEvent := isPointerEvent := false.
 
     (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:'.
     ]]]]]]]]]]].
 
     "
@@ -1226,64 +1226,64 @@
      the focusView (0 @ 0) is passed as x/y coordinates.
     "
     (focusView notNil and:[self ~~ focusView]) ifTrue:[
-        isKeyEvent ifTrue:[
-            focusView 
-                dispatchEvent:type 
-                arguments:(Array with:(argArray at:1) with:-1 with:-1)
-                withFocusOn:nil
-                delegate:doDelegate.
-            ^ self
-        ].
-        type == #mouseWheelMotion:state: ifTrue:[
-            focusView 
-                dispatchEvent:type 
-                arguments:argArray
-                withFocusOn:nil
-                delegate:doDelegate.
-            ^ self
-        ]
+	isKeyEvent ifTrue:[
+	    focusView 
+		dispatchEvent:type 
+		arguments:(Array with:(argArray at:1) with:-1 with:-1)
+		withFocusOn:nil
+		delegate:doDelegate.
+	    ^ self
+	].
+	type == #mouseWheelMotion:state:deltaTime: ifTrue:[
+	    focusView 
+		dispatchEvent:type 
+		arguments:argArray
+		withFocusOn:nil
+		delegate:doDelegate.
+	    ^ self
+	]
     ].
 
     doDelegate ifTrue:[
-        "
-         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
-                ]
-            ].
-        ].
+	"
+	 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
+		]
+	    ].
+	].
     ].
 
     "
@@ -1292,9 +1292,9 @@
     (isKeyEvent 
      or:[isButtonEvent 
      or:[isPointerEvent]]) ifTrue:[
-        realized ifFalse:[
-            ^ self
-        ]
+	realized ifFalse:[
+	    ^ self
+	]
     ].
 
     "
@@ -1302,13 +1302,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.
+	]
     ].
 
     "
@@ -1324,13 +1324,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
@@ -1781,50 +1781,50 @@
     |wg endPollTime pollDelay|
 
     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
-        "/
-        device platformName = 'WIN32' ifTrue:[
-            pollDelay := 1.
-        ] ifFalse:[
-            pollDelay := 3.
-        ].
-        endPollTime := AbsoluteTime now addSeconds:pollDelay.
-
-        [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
-
-            AbsoluteTime now > endPollTime ifTrue:[
-                'DisplaySurface [warning]: lost expose event' errorPrintCR.
-                gotExpose := true.
-                ^ self
-            ].
-            Processor yield.
-        ].
+	"/
+	"/ a pure event driven view.
+	"/ wait by doing a direct dispatch loop until the event arrives.
+	"/ i.e. poll for the event
+	"/
+	device platformName = 'WIN32' ifTrue:[
+	    pollDelay := 1.
+	] ifFalse:[
+	    pollDelay := 3.
+	].
+	endPollTime := AbsoluteTime now addSeconds:pollDelay.
+
+	[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
+
+	    AbsoluteTime now > endPollTime ifTrue:[
+		'DisplaySurface [warning]: lost expose event' errorPrintCR.
+		gotExpose := true.
+		^ self
+	    ].
+	    Processor yield.
+	].
     ]
 
     "Modified: / 9.1.1999 / 01:58:09 / cg"
@@ -1838,13 +1838,13 @@
      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
     ].
     self destroyView.
     Lobby unregister:self.
@@ -1856,9 +1856,9 @@
     "physically destroy the view."
      
     drawableId notNil ifTrue:[
-        device destroyView:self withId:drawableId.
-        drawableId := nil.
-        realized := false.
+	device destroyView:self withId:drawableId.
+	drawableId := nil.
+	realized := false.
     ].
 !
 
@@ -2237,5 +2237,5 @@
 !DisplaySurface class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview/DisplaySurface.st,v 1.66 1999-05-21 18:09:35 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview/DisplaySurface.st,v 1.67 1999-05-22 14:33:05 cg Exp $'
 ! !
--- a/bc.mak	Sat May 22 16:33:27 1999 +0200
+++ b/bc.mak	Sat May 22 16:34:01 1999 +0200
@@ -6,7 +6,7 @@
 
 #
 
-# $Header: /cvs/stx/stx/libview/bc.mak,v 1.28 1999-05-18 12:12:57 cg Exp $
+# $Header: /cvs/stx/stx/libview/bc.mak,v 1.29 1999-05-22 14:34:00 cg Exp $
 
 #
 
@@ -69,14 +69,9 @@
   $(OUTDIR)ImageMask.$(O)
 
 
-
-
 !INCLUDE $(TOP)\rules\stdRules_nt
 
 
-
-
-
 $(OUTDIR)GraphicsDevice.$(O): GraphicsDevice.st
 
 $(OUTDIR)HostGraphicsDevice.$(O): HostGraphicsDevice.st
@@ -85,15 +80,15 @@
 
 $(OUTDIR)Image.$(O): Image.st
 
-$(OUTDIR)Depth1Image.$(O): Depth1Image.st
+$(OUTDIR)Depth1Image.$(O): $(STX_INCDIR)\Image.sth Depth1Image.st
 
-$(OUTDIR)Depth2Image.$(O): Depth2Image.st
+$(OUTDIR)Depth2Image.$(O): $(STX_INCDIR)\Image.sth Depth2Image.st
 
-$(OUTDIR)Depth4Image.$(O): Depth4Image.st
+$(OUTDIR)Depth4Image.$(O): $(STX_INCDIR)\Image.sth Depth4Image.st
 
-$(OUTDIR)Depth8Image.$(O): Depth8Image.st
+$(OUTDIR)Depth8Image.$(O): $(STX_INCDIR)\Image.sth Depth8Image.st
 
-$(OUTDIR)Depth24Image.$(O): Depth24Image.st
+$(OUTDIR)Depth24Image.$(O): $(STX_INCDIR)\Image.sth Depth24Image.st
 
 $(OUTDIR)ImageRdr.$(O): ImageRdr.st
 
@@ -157,11 +152,11 @@
 
 $(OUTDIR)ViewStyle.$(O): ViewStyle.st
 
-$(OUTDIR)Depth16Image.$(O): Depth16Image.st
+$(OUTDIR)Depth16Image.$(O): $(STX_INCDIR)\Image.sth Depth16Image.st
 
-$(OUTDIR)Depth32Image.$(O): Depth32Image.st
+$(OUTDIR)Depth32Image.$(O): $(STX_INCDIR)\Image.sth Depth32Image.st
 
-$(OUTDIR)ImageMask.$(O): ImageMask.st
+$(OUTDIR)ImageMask.$(O): $(STX_INCDIR)\Image.sth ImageMask.st
 
 
 
--- a/nt.mak	Sat May 22 16:33:27 1999 +0200
+++ b/nt.mak	Sat May 22 16:34:01 1999 +0200
@@ -6,7 +6,7 @@
 
 #
 
-# $Header: /cvs/stx/stx/libview/Attic/nt.mak,v 1.28 1999-05-18 12:12:57 cg Exp $
+# $Header: /cvs/stx/stx/libview/Attic/nt.mak,v 1.29 1999-05-22 14:34:00 cg Exp $
 
 #
 
@@ -69,14 +69,9 @@
   $(OUTDIR)ImageMask.$(O)
 
 
-
-
 !INCLUDE $(TOP)\rules\stdRules_nt
 
 
-
-
-
 $(OUTDIR)GraphicsDevice.$(O): GraphicsDevice.st
 
 $(OUTDIR)HostGraphicsDevice.$(O): HostGraphicsDevice.st
@@ -85,15 +80,15 @@
 
 $(OUTDIR)Image.$(O): Image.st
 
-$(OUTDIR)Depth1Image.$(O): Depth1Image.st
+$(OUTDIR)Depth1Image.$(O): $(STX_INCDIR)\Image.sth Depth1Image.st
 
-$(OUTDIR)Depth2Image.$(O): Depth2Image.st
+$(OUTDIR)Depth2Image.$(O): $(STX_INCDIR)\Image.sth Depth2Image.st
 
-$(OUTDIR)Depth4Image.$(O): Depth4Image.st
+$(OUTDIR)Depth4Image.$(O): $(STX_INCDIR)\Image.sth Depth4Image.st
 
-$(OUTDIR)Depth8Image.$(O): Depth8Image.st
+$(OUTDIR)Depth8Image.$(O): $(STX_INCDIR)\Image.sth Depth8Image.st
 
-$(OUTDIR)Depth24Image.$(O): Depth24Image.st
+$(OUTDIR)Depth24Image.$(O): $(STX_INCDIR)\Image.sth Depth24Image.st
 
 $(OUTDIR)ImageRdr.$(O): ImageRdr.st
 
@@ -157,11 +152,11 @@
 
 $(OUTDIR)ViewStyle.$(O): ViewStyle.st
 
-$(OUTDIR)Depth16Image.$(O): Depth16Image.st
+$(OUTDIR)Depth16Image.$(O): $(STX_INCDIR)\Image.sth Depth16Image.st
 
-$(OUTDIR)Depth32Image.$(O): Depth32Image.st
+$(OUTDIR)Depth32Image.$(O): $(STX_INCDIR)\Image.sth Depth32Image.st
 
-$(OUTDIR)ImageMask.$(O): ImageMask.st
+$(OUTDIR)ImageMask.$(O): $(STX_INCDIR)\Image.sth ImageMask.st
 
 
 
--- a/ntw.mak	Sat May 22 16:33:27 1999 +0200
+++ b/ntw.mak	Sat May 22 16:34:01 1999 +0200
@@ -1,5 +1,5 @@
 #
-# $Header: /cvs/stx/stx/libview/Attic/ntw.mak,v 1.6 1999-05-17 18:20:47 cg Exp $
+# $Header: /cvs/stx/stx/libview/Attic/ntw.mak,v 1.7 1999-05-22 14:33:59 cg Exp $
 #
 
 
@@ -17,8 +17,6 @@
 RESFILES=$(OUTDIR)WinWorkstat.res
 LIB_BASE=$(WINWORKSTAT_BASE)
 
-
-
 STCLOCALOPT= -staticMethods "-package=$(PACKAGE)" $(COMMONSYMBOLS) +optspace2 $(SEPINITCODE)
 
 STCFLAGS_WW=-H$(STX_INCDIR) -staticMethods "-package=(stx:libview)" $(COMMONSYMBOLS)
@@ -28,13 +26,11 @@
 ALL: $(LIBDIR)\$(LIBNAME).lib $(BINDIR)\$(LIBNAME).dll 
 
 
-
+OBJS= \
+    $(OUTDIR)WinWorkstat.$(O)                      
 
 
-OBJS= \
-    $(OUTDIR)$(LIBNAME).$(O)                      
-
-
+$(OUTDIR)WinWorkstat.$(O):   $(STX_INCDIR)\DevWorkst.STH
 
 NOINCLINK=YES
 
--- a/ntx.mak	Sat May 22 16:33:27 1999 +0200
+++ b/ntx.mak	Sat May 22 16:34:01 1999 +0200
@@ -1,6 +1,6 @@
 #
 
-# $Header: /cvs/stx/stx/libview/ntx.mak,v 1.6 1999-05-17 18:20:48 cg Exp $
+# $Header: /cvs/stx/stx/libview/ntx.mak,v 1.7 1999-05-22 14:34:01 cg Exp $
 
 #
 
@@ -8,14 +8,9 @@
 
 TOP=..
 
-
-
 !INCLUDE        $(TOP)\rules\stdHeader_nt
 
 
-
-
-
 LIBNAME=XWorkstat
 RESFILES=$(OUTDIR)XWorkstat.res
 PACKAGE=stx:libview
@@ -23,7 +18,6 @@
 LIB_BASE=$(XWORKSTAT_BASE)
 
 
-
 STCLOCALOPT= -staticMethods "-package=$(PACKAGE)" $(COMMONSYMBOLS) +optspace2 $(SEPINITCODE)
 
 STCFLAGS_WW=-H$(STX_INCDIR) -staticMethods "-package=(stx:libview)" $(COMMONSYMBOLS)
@@ -33,11 +27,11 @@
 ALL: xlibs $(LIBDIR)\$(LIBNAME).lib $(BINDIR)\$(LIBNAME).dll 
 
 
-
 OBJS= \
-    $(OUTDIR)$(LIBNAME).$(O)                      
+    $(OUTDIR)XWorkstat.$(O)                      
 
 
+$(OUTDIR)XWorkstat.$(O):       $(STX_INCDIR)\DevWorkst.STH
 
 NOINCLINK=YES
 
@@ -62,7 +56,6 @@
 xlibs: $(X11_LIBS)
 
 
-
 ..\lib\X11OMF.lib: ..\support\win32\borland\X11OMF.lib
 	copy ..\support\win32\borland\X11OMF.lib ..\lib