DSurface.st
author Claus Gittinger <cg@exept.de>
Tue, 19 Aug 1997 17:28:51 +0200
changeset 1872 2a10e693d93f
parent 1851 6a6225647696
child 1884 a2e2ff3a6b4e
permissions -rw-r--r--
break non-windowGroup expose-poll loop after a while (10 seconds) to avoid blocking forever.

"
 COPYRIGHT (c) 1992 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

GraphicsMedium subclass:#DisplaySurface
	instanceVariableNames:'viewBackground cursor eventMask middleButtonMenu keyCommands
		gotExpose backed saveUnder delegate'
	classVariableNames:''
	poolDictionaries:''
	category:'Graphics-Support'
!

!DisplaySurface class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1992 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    this abstract class describes stuff common to any Window on a display 
    device. i.e. RootWindow, TopWindows, PopUps and Subwindows.
    That is, they have a viewBackground, cursor etc. and especially events.
    A special feature is the delegate field, which allows key- and button 
    events to be stolen from a view. 
    If the delegate is non-nil, these events will be sent to it instead.
    So you can change a views behavior even if it was not initially designed 
    for it. Also, controller functionality could be simulated using delegates.

    [instance variables:]

        viewBackground  <Color|Form|Image>      the views background

        cursor          <Cursor>                the cursor

        eventMask                               mask specifying the enabled
                                                events.

        middleButtonMenu                        a popup menu for the middle
                                                button.

        keyCommands                             not yet supported

        gotExpose                               for exposure handling after
        exposePending                           after a scroll

        backed                                  true if backing store for that
                                                view is enabled

        saveUnder                               true if saveunder store for 
                                                that view is enabled

        delegate                                for event delegation

    [see also:]
        DeviceWorkstation
        WindowGroup
        StandardSYstemView SimpleView View

    [author:]
        Claus Gittinger
"
! !

!DisplaySurface methodsFor:'accessing'!

depth
    "return the depth in pixels of the view.
     Notice, that this is currently the devices depth, 
     but support for mixed depth views is being prepared.
     (especially useful on SGI, with 24bit view)"

    ^ device depth
!

insideColor:aColor
    "set the views background color - ST-80 compatibility"

    self viewBackground:aColor.
    self background:aColor
!

setViewBackground
    "install the viewBackground for the receiver on the device"

    |id devBgPixmap bgPixmap w h colorMap 
     pixmapDepth deviceDepth|

    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
        ].

        "
         must now have:
         a dithered color or bitmap or pixmap
        "
        bgPixmap isNil ifTrue:[
            'DisplaySurface [warning]: background not convertable - ignored' errorPrintCR.
            ^ 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
                    ]
                ].

                "
                 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"
!

viewBackground
    "return the viewBackground"

    ^ viewBackground
!

viewBackground:something
    "set the viewBackground to something, a color, image or form.
     The viewBackground is the color or pattern with which exposed
     regions are filled - do not confuse this with the drawing background
     color, which is used with opaque drawing."

    viewBackground ~~ something ifTrue:[
	viewBackground := something.
	drawableId notNil ifTrue:[
	    self setViewBackground
	]
    ]
!

viewBackgroundAndClear:something
    "set the viewBackground to something, a color, image or form.
     and clear the View.
     The viewBackground is the color or pattern with which exposed
     regions are filled - do not confuse this with the drawing background
     color, which is used with opaque drawing."

    self viewBackground:something.
    self clear.

    "Created: 27.4.1996 / 14:09:08 / cg"
!

viewGravity
    "return the views gravity"

    ^ #NorthWest
!

viewOrigin
    "0@0 here, since by default we cannot be scrolled"

    ^ 0 @ 0
!

widget
    "ST-80 compatibility"

    ^ self
! !

!DisplaySurface methodsFor:'accessing-cursor'!

cursor
    "return the views cursor"

    ^ cursor
!

cursor:aCursor
    "set the views cursor. This cursor will be automatically displayed whenever 
     the mouse-pointer enters the receiver. 
     Cursors are typically set at view creation time and left as installed."

    self cursor:aCursor now:true

    "
     |v|

     v := View new.
     v cursor:(Cursor wait).
     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).
     ]
    "

    "Modified: 14.12.1995 / 21:28:14 / cg"
!

cursor:aCursor now:showImmediately
    "set the views cursor. This cursor will be automatically displayed whenever 
     the mouse-pointer enters the receiver. 
     Cursors are typically set at view creation time and left as installed."

    |id|

    aCursor notNil ifTrue:[
        (aCursor ~~ cursor) ifTrue:[
            cursor := aCursor.
            drawableId notNil ifTrue:[
                cursor := cursor onDevice:device.
                cursor isNil ifTrue:[ ^ self].
                id := cursor id.
                id isNil ifTrue:[
                    'DisplaySurface [warning]: nil cursorId ignored; shape=' errorPrint. cursor shape errorPrintCR.
                    ^ self
                ].
                device setCursor:id in:drawableId.
                (showImmediately and:[realized]) ifTrue:[
                    "flush, to make cursor immediately visible"
                    device flush
                ]
            ]
        ]
    ]

    "
     |v|

     v := View new.
     v cursor:(Cursor wait).
     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).
     ]
    "

    "Created: 14.12.1995 / 21:28:00 / cg"
    "Modified: 28.3.1997 / 13:47:58 / cg"
!

withCursor:aCursor do:aBlock
    "evaluate aBlock showing aCursor until ready; then restore the old cursor
     and return the value as returned by aBlock.

     Notice, that this method only changes the cursor for a SINGLE (sub-)view.
     Most applications want to have the cursor changed in all of its views.
     Use 'aView windowGroup withCursor:do:' or 'aView topView withCursor:do:'
     to acomplish this."

    |savedCursor|

    cursor == aCursor ifTrue:[
        ^ aBlock value
    ].

    savedCursor := cursor.
    self cursor:aCursor.
    ^ aBlock valueNowOrOnUnwindDo:[self cursor:savedCursor]

    "Modified: 27.2.1997 / 17:20:43 / cg"
!

withExecuteCursorDo:aBlock
    "evaluate aBlock while showing an execute cursor in all my views.
     Return the value as returned by aBlock."

    ^ self withCursor:(Cursor execute) do:aBlock

    "Created: 10.1.1996 / 13:53:03 / cg"
!

withReadCursorDo:aBlock
    "evaluate aBlock while showing a readCursor in all my views.
     Return the value as returned by aBlock."

    ^ self withCursor:(Cursor read) do:aBlock

    "Modified: 14.12.1995 / 20:57:40 / cg"
    "Created: 10.1.1996 / 13:52:52 / cg"
!

withWaitCursorDo:aBlock
    "evaluate aBlock while showing a waitCursor in all my views.
     Return the value as returned by aBlock."

    ^ self withCursor:(Cursor wait) do:aBlock

    "Created: 10.1.1996 / 13:51:08 / cg"
! !

!DisplaySurface methodsFor:'accessing-hierarchy'!

delegate
    "return the delegate - thats the one getting keyboard and button events"

    ^ delegate
!

delegate:someOne
    "set the delegate - keyboard- and button events will be forwarded to
     that object if it is interested in them.
     See the sendEvent... method in WindowEvent."

    delegate := someOne
!

superView
    "return the superView - nil here"

    ^ nil
!

topComponent
    "return the topView - that the one with no superview"

    ^ self

    "Created: 9.5.1996 / 01:39:43 / cg"
!

topView
    "return the topView - that the one with no superview"

    ^ self
! !

!DisplaySurface methodsFor:'accessing-limits'!

maxExtent
    "return the views maximum extent - this is nil here.
     Only standardSystemViews support this."

    ^ nil
!

maxExtent:extent
    "set the views maximum extent - ignored here.
     Only standardSystemViews support this."

    ^ self
!

minExtent
    "return the views minimum extent - this is nil here.
     Only standardSystemViews support this."

    ^ nil
!

minExtent:extent
    "set the views minimum extent - ignored here.
     Only standardSystemViews support this."

    ^ self
! !

!DisplaySurface methodsFor:'accessing-misc'!

backingStore:how
    "turn on/off backingStore (saving my pixels)
     how may true/false, but also #always, #whenMapped or #never."

    how ~~ backed ifTrue:[
	backed := how.
	drawableId notNil ifTrue:[
	    device setBackingStore:how in:drawableId
	]
    ]
!

eventMask
    "return a (numeric) mask of allowed events -
     this is X-specific and will be removed / replaced by symbolic values)"
    
    ^ eventMask
!

eventMask:aMask
    "set a (numeric) mask of allowed events -
     this is X-specific and will be removed / replaced by symbolic values)"
     
    eventMask := aMask
!

getKeyboardFocus
    "tell the Display to assign keyboard focus to the receiver"

    drawableId notNil ifTrue:[
	self shown ifTrue:[
	    device setInputFocusTo:drawableId
	]
    ].
!

isInputOnly
    "return true, if the receiver is an input only view - that is: 
     the view will realize as a transparent view, into which you cannot
     draw, but get events as usual. Thich can be used to catch events away from 
     others, which where never meant to work in such a setup.
     (for example, if you want to manipulate views in some DrawTool-like manner).
     This uses a special X feature, which might not be supported in the near future
     or on other plattforms."

    ^ false

    "Created: 1.6.1996 / 13:21:51 / cg"
!

preferredDepth
    "return a non nil integer, if a specific depth is wanted in this view.
     Return nil if we do not care (i.e. the displays default is wanted).
     This is experimental and may change/vanish - do not use it."

    ^ nil
!

preferredVisual
    "return a non nil id, if a specific visual is wanted in this view.
     Return nil if we do not care (i.e. the displays default is wanted). 
     This is experimental and may change/vanish - do not use it."

    ^ nil
!

saveUnder:aBoolean
    "turn on/off saveUnder (saving pixels under myself)
     - used for temporary views (i.e. PopUps and ModalBoxes)"

    saveUnder := aBoolean.
    drawableId notNil ifTrue:[
	device setSaveUnder:aBoolean in:drawableId
    ]
! !

!DisplaySurface methodsFor:'accessing-names'!

icon
    "return the views icon - this is nil here.
     Only standardSystemViews support labels and icons."

    ^ nil
!

icon:aBitmap
    "set the views icon - ignored here.
     Only standardSystemViews support labels and icons."

    ^ self
!

iconLabel
    "return the views icon label - this is nil here.
     Only standardSystemViews support labels and icons."

    ^ nil
!

iconLabel:aLabel
    "set the views icon label - ignored here.
     Only standardSystemViews support labels and icons."

    ^ self
!

iconMask
    "return the views iconMask - this is nil here.
     Only standardSystemViews may support labels and icons."

    ^ nil
!

iconView
    "return the views iconView - this is nil here.
     Only standardSystemViews support labels and icons."

    ^ nil
!

iconView:aView
    "set the views icon view - ignored here.
     Only standardSystemViews support labels and icons."

    ^ self
!

label
    "return the views label - this is nil here.
     Only standardSystemViews support labels and icons."

    ^ nil
!

label:aLabel
    "set the views label - ignored here.
     Only standardSystemViews support labels and icons."

    ^ self
! !

!DisplaySurface methodsFor:'binary storage'!

readBinaryContentsFrom: stream manager: manager
    "tell the newly restored View to recreate itself.
     Bug: does not work correctly yet.
          (restored view looses its position & wg process)"

    |wasRealized|

    super readBinaryContentsFrom: stream manager: manager.

    gcId := nil.
    drawableId := nil.
    wasRealized := realized.
    realized := false.
    self recreate.
    wasRealized ifTrue:[
        self remap
    ]


    "
     |s l|
     s := 'storedLabel.boss' asFilename writeStream binary.
     l := (Label label:'hello there') realize.
     Delay waitForSeconds:1.
     l storeBinaryOn:s.
     s close.
    "

    "
     |s l|
     s := 'storedLabel.boss' asFilename writeStream binary.
     (l := Label label:'hello there') open.
     (Delay forSeconds:10) wait.
     l storeBinaryOn:s.
     s close.
     l destroy.
    "

    "
     |s|
     s := 'storedLabel.boss' asFilename readStream binary.
     (Object readBinaryFrom:s)
    "

    "Modified: 3.5.1996 / 23:59:38 / stefan"
    "Modified: 14.2.1997 / 15:42:55 / cg"
! !

!DisplaySurface methodsFor:'button menus'!

middleButtonMenu
    "return the menu associated with the middle mouse button"

    ^ middleButtonMenu
!

middleButtonMenu:aMenu
    "associate aMenu with the middle mouse button"

    middleButtonMenu notNil ifTrue:[
	middleButtonMenu destroy
    ].
    middleButtonMenu := aMenu
!

setMiddleButtonMenu:aMenu
    "associate aMenu with the middle mouse button.
     Do not destroy old menu if any"

    middleButtonMenu := aMenu
! !

!DisplaySurface methodsFor:'drawing'!

clearDeviceRectangleX:x y:y width:w height:h
    "clear a rectangular area to viewBackground -
     redefined since GraphicsMedium fills with background
     - not viewBackground as we want here."

    |oldPaint org|

    oldPaint := paint.
    self paint:viewBackground.

    viewBackground isColor ifFalse:[
	gcId notNil ifTrue:[
	    org := self viewOrigin.
	    device setMaskOriginX:org x rounded negated
				y:org y rounded negated
			       in:gcId
	].
    ].
    "
     fill in device coordinates - not logical coordinates
    "
    self fillDeviceRectangleX:x y:y width:w height:h "with:viewBackground".
    self paint:oldPaint
!

clearRectangleX:x y:y width:w height:h
    "clear a rectangular area to viewBackground -
     redefined since GraphicsMedium fills with background
     - not viewBackground as we want here."

    |oldPaint org|

    oldPaint := paint.
    self paint:viewBackground.

    viewBackground isColor ifFalse:[
	gcId notNil ifTrue:[
	    org := self viewOrigin.
	    device setMaskOriginX:org x rounded negated
				y:org y rounded negated
			       in:gcId
	].
    ].
    self fillRectangleX:x y:y width:w height:h.
    self paint:oldPaint
!

redraw
    "nothing done here"

    ^ self
! !

!DisplaySurface methodsFor:'enable/disable events'!

compressMotionEvents:aBoolean
    "enable/disable motion event compression
     (i.e. replacing all motion events by the last one).
     Compression makes almost always sense, except when
     doing things like freehand drawing"

    |s|

    (s := self sensor) notNil ifTrue:[
	s compressMotionEvents:aBoolean
    ]
!

disableButtonEvents
    "disable all button events"

    self disableEvent:#buttonPress; disableEvent:#buttonRelease

    "Modified: 29.4.1996 / 11:09:25 / cg"
!

disableButtonMotionEvents
    "disable button motion-while-button-is-pressed events"

    self disableEvent:#buttonMotion
!

disableButtonPressEvents
    "disable button press events"

    self disableEvent:#buttonPress
!

disableButtonReleaseEvents
    "disable button release events"

    self disableEvent:#buttonRelease
!

disableEnterLeaveEvents
    "disable both mouse-pointer enter and leave events"

    self disableEvent:#enter; disableEvent:#leave

    "Modified: 29.4.1996 / 11:09:37 / cg"
!

disableEvent:anEventSymbol
    "disable an event -
     this is a private (internal) method not to be used externally.
     for a list of allowed event symbols see Workstation class"
     
    eventMask := eventMask bitAnd:(device eventMaskFor:anEventSymbol) bitInvert.
    drawableId notNil ifTrue:[
	device setEventMask:eventMask in:drawableId
    ]
!

disableMotionEvents
    "disable mouse-pointer motion events"
    
    self disableEvent:#pointerMotion
!

enableButtonEvents
    "enable both mouse button press and release events.
     These are enabled by default anyway."
    
    self enableEvent:#buttonPress; enableEvent:#buttonRelease

    "Modified: 29.4.1996 / 11:09:46 / cg"
!

enableButtonMotionEvents
    "enable mouse-pointer motion-while-button-is-pressed events.
     These are enabled by default anyway."
    
    self enableEvent:#buttonMotion
!

enableButtonPressEvents
    "enable mouse button press events.
     These are enabled by default anyway."
    
    self enableEvent:#buttonPress
!

enableButtonReleaseEvents
    "enable mouse button release events.
     These are enabled by default anyway."
    
    self enableEvent:#buttonRelease
!

enableEnterEvents
    "enable mouse-pointer enter events"
    
    self enableEvent:#enter
!

enableEnterLeaveEvents
    "enable both mouse-pointer enter and leave events"
    
    self enableEvent:#enter; enableEvent:#leave

    "Modified: 29.4.1996 / 11:09:55 / cg"
!

enableEvent:anEventSymbol
    "enable an event -
     this is a private (internal) method not to be used externally.
     for a list of allowed event symbols see Workstation class"
    
    eventMask := eventMask bitOr:(device eventMaskFor:anEventSymbol).
    drawableId notNil ifTrue:[
	device setEventMask:eventMask in:drawableId
    ]
!

enableFocusEvents
    "enable keyboard focus change events"
    
    self enableEvent:#focusChange
!

enableKeyEvents
    "this is a compatibility leftover - 
     starting with 2.10.3, keyPress is always enabled to allow 
     ^C processing."

!

enableKeyPressEvents
    "this is a compatibility leftover - 
     starting with 2.10.3, keyPress is always enabled to allow 
     ^C processing."
    
!

enableKeyReleaseEvents
    "enable key release events"
    
    self enableEvent:#keyRelease
!

enableLeaveEvents
    "enable mouse-pointer leave events"
    
    self enableEvent:#leave
!

enableMotionEvents
    "enable mouse-pointer motion events"
    
    self enableEvent:#pointerMotion
! !

!DisplaySurface methodsFor:'event handling'!

activateMenu
    "if there is a menu, show it."

    middleButtonMenu notNil ifTrue:[
        middleButtonMenu showAtPointer
    ]

    "Created: 1.3.1996 / 13:24:55 / cg"
!

buttonMotion:state x:x y:y
    "mouse was moved while button is pressed - do nothing here"

    ^ self
!

buttonMultiPress:button x:x y:y
    "button was pressed fast after previous press - default to press-again"

    ^ self buttonPress:button x:x y:y
!

buttonPress:button x:x y:y
    "button was pressed - if its middle button and there is a menu,
     show it."

    ((button == 2) or:[button == #menu]) ifTrue:[
        self activateMenu.
    ]

    "Modified: 1.3.1996 / 13:25:07 / cg"
!

buttonRelease:button x:x y:y
    "button was released - do nothing here"

    ^ self
!

catchExpose
    "this MUST be sent BEFORE doing a bit-blt copy (i.e. copyFrom...), 
     to tell the sensor that incoming expose events are to be remembered.
     Sometime after the bit-blt, waitForExpose should be sent, to finally
     suspend until the expose/noExpose event arrives. 
     This is an X speciality - for devices which do not need this kind of 
     asynchronous bit-blt confirmation, this is a noop.
    "

    |wg|

    device scrollsAsynchronous ifFalse:[
        gotExpose := true.
        ^ self
    ].

    self setGraphicsExposures:true.

    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
    ]

    "Modified: 6.8.1997 / 19:50:15 / cg"
!

deviceButtonMotion:state x:x y:y
    "this is the low-level (untransformed) event as received
     from the device (i.e. coordinates are in device coordinates). 
     If there is a transformation, apply the inverse
     and send a #buttonMotion with the logical coordinates.

     Views which are interested in deviceCoordinates should
     redefine this method - 
     those which are interested in logical coordinates
     should redefine #buttonMotion:x:y:"

    |lx ly|

    lx := x.
    ly := y.
    transformation notNil ifTrue:[
        lx notNil ifTrue:[
            lx := transformation applyInverseToX:lx.
            ly := transformation applyInverseToY:ly.
        ].
    ].
    self buttonMotion:state x:lx y:ly

    "Modified: 20.5.1996 / 17:45:25 / cg"
    "Modified: 14.10.1996 / 22:25:12 / stefan"
!

deviceButtonMultiPress:butt x:x y:y
    "this is the low-level (untransformed) event as received
     from the device (i.e. coordinates are in device coordinates). 
     If there is a transformation, apply the inverse
     and send a buttonMultiPress with the logical coordinates.

     Views which are interested in deviceCoordinates should
     redefine this method - 
     those which are interested in logical coordinates
     should redefine #buttonMultiPress:x:y:"

    |lx ly|

    lx := x.
    ly := y.
    transformation notNil ifTrue:[
        lx notNil ifTrue:[
            lx := transformation applyInverseToX:lx.
            ly := transformation applyInverseToY:ly.
        ].
    ].
    self buttonMultiPress:butt x:lx y:ly

    "Modified: 20.5.1996 / 17:45:22 / cg"
    "Modified: 14.10.1996 / 22:25:22 / stefan"
!

deviceButtonPress:butt x:x y:y
    "this is the low-level (untransformed) event as received
     from the device (i.e. coordinates are in device coordinates). 
     If there is a transformation, apply the inverse
     and send a buttonPress with the logical coordinates.

     Views which are interested in deviceCoordinates should
     redefine this method - 
     those which are interested in logical coordinates
     should redefine #buttonPress:x:y:"

    |lx ly|

    lx := x.
    ly := y.
    transformation notNil ifTrue:[
        lx notNil ifTrue:[
            lx := transformation applyInverseToX:lx.
            ly := transformation applyInverseToY:ly.
        ].
    ].
    self buttonPress:butt x:lx y:ly

    "Modified: 20.5.1996 / 17:45:18 / cg"
    "Modified: 14.10.1996 / 22:25:30 / stefan"
!

deviceButtonRelease:butt x:x y:y
    "this is the low-level (untransformed) event as received
     from the device (i.e. coordinates are in device coordinates). 
     If there is a transformation, apply the inverse
     and send a buttonRelease with the logical coordinates.

     Views which are interested in deviceCoordinates should
     redefine this method - 
     those which are interested in logical coordinates
     should redefine #buttonRelease:x:y:"

    |lx ly|

    lx := x.
    ly := y.
    transformation notNil ifTrue:[
        lx notNil ifTrue:[
            lx := transformation applyInverseToX:lx.
            ly := transformation applyInverseToY:ly.
        ].
    ].
    self buttonRelease:butt x:lx y:ly

    "Modified: 20.5.1996 / 17:45:14 / cg"
    "Modified: 14.10.1996 / 22:25:37 / stefan"
!

deviceButtonShiftPress:butt x:x y:y
    "this is the low-level (untransformed) event as received
     from the device (i.e. coordinates are in device coordinates). 
     If there is a transformation, apply the inverse
     and send a buttonShiftPress with the logical coordinates.

     Views which are interested in deviceCoordinates should
     redefine this method - 
     those which are interested in logical coordinates
     should redefine #buttonShiftPress:x:y:"

    |lx ly|

    lx := x.
    ly := y.
    transformation notNil ifTrue:[
        lx notNil ifTrue:[
            lx := transformation applyInverseToX:lx.
            ly := transformation applyInverseToY:ly.
        ].
    ].
    self buttonShiftPress:butt x:lx y:ly

    "Modified: 20.5.1996 / 17:45:09 / cg"
    "Modified: 14.10.1996 / 22:25:49 / stefan"
!

deviceExposeX:x y:y width:w height:h
    "this is the low-level (untransformed) event as received
     from the device (i.e. coordinates are in device coordinates). 
     If there is a transformation, apply the inverse
     and send an expose with the logical coordinates.

     Views which are interested in deviceCoordinates should
     redefine this method - 
     those which are interested in logical coordinates
     should redefine #exposeX:x:y:width:height:"

    |lx ly lw lh|

    lx := x.
    ly := y.
    lw := w.
    lh := h.
    transformation notNil ifTrue:[
        lx := transformation applyInverseToX:lx.
        ly := transformation applyInverseToY:ly.
        lw := transformation applyInverseScaleX:lw.
        lh := transformation applyInverseScaleY:lh.
    ].
    self exposeX:lx y:ly width:lw height:lh

    "Modified: 13.5.1996 / 11:31:44 / cg"
    "Modified: 14.10.1996 / 22:26:00 / stefan"
!

deviceGraphicsExposeX:x y:y width:w height:h final:final
    "this is the low-level (untransformed) event as received
     from the device (i.e. coordinates are in device coordinates). 
     If there is a transformation, apply the inverse
     and send a graphicsExpose with the logical coordinates.

     Views which are interested in deviceCoordinates should
     redefine this method - 
     those which are interested in logical coordinates
     should redefine #graphicsExposeX:x:y:width:height:"

    |lx ly lw lh|

    lx := x.
    ly := y.
    lw := w.
    lh := h.
    transformation notNil ifTrue:[
        lx := transformation applyInverseToX:lx.
        ly := transformation applyInverseToY:ly.
        lw := transformation applyInverseScaleX:lw.
        lh := transformation applyInverseScaleY:lh.
    ].
    self graphicsExposeX:lx y:ly width:lw height:lh final:final

    "Modified: 13.5.1996 / 11:31:54 / cg"
    "Modified: 14.10.1996 / 22:26:08 / stefan"
!

deviceKeyPress:key x:x y:y
    "this is the low-level (untransformed) event as received
     from the device (i.e. coordinates are in device coordinates). 
     If there is a transformation, apply the inverse
     and send a keyPress with the logical coordinates.

     Views which are interested in deviceCoordinates should
     redefine this method - 
     those which are interested in logical coordinates
     should redefine #keyPress:x:y:"

    |lx ly|

    lx := x.
    ly := y.
    transformation notNil ifTrue:[
        lx notNil ifTrue:[
            lx := transformation applyInverseToX:lx.
            ly := transformation applyInverseToY:ly.
        ]
    ].
    self keyPress:key x:lx y:ly

    "Modified: 20.5.1996 / 17:44:59 / cg"
    "Modified: 14.10.1996 / 22:26:17 / stefan"
!

deviceKeyRelease:key x:x y:y
    "this is the low-level (untransformed) event as received
     from the device (i.e. coordinates are in device coordinates). 
     If there is a transformation, apply the inverse
     and send a keyRelease with the logical coordinates.

     Views which are interested in deviceCoordinates should
     redefine this method - 
     those which are interested in logical coordinates
     should redefine #keyRelease:x:y:"

    |lx ly|

    lx := x.
    ly := y.
    transformation notNil ifTrue:[
        lx notNil ifTrue:[
            lx := transformation applyInverseToX:lx.
            ly := transformation applyInverseToY:ly.
        ]
    ].
    self keyRelease:key x:lx y:ly

    "Modified: 20.5.1996 / 17:44:42 / cg"
    "Modified: 14.10.1996 / 22:26:28 / stefan"
!

devicePointerEnter:state x:x y:y
    "this is the low-level (untransformed) event as received
     from the device (i.e. coordinates are in device coordinates). 
     If there is a transformation, apply the inverse
     and send a pointerEnter with the logical coordinates.

     Views which are interested in deviceCoordinates should
     redefine this method - 
     those which are interested in logical coordinates
     should redefine #pointerEnter:x:y:"

    |lx ly|

    lx := x.
    ly := y.
    transformation notNil ifTrue:[
        lx notNil ifTrue:[
            lx := transformation applyInverseToX:lx.
            ly := transformation applyInverseToY:ly.
        ]
    ].
    self pointerEnter:state x:lx y:ly

    "Modified: 20.5.1996 / 17:44:54 / cg"
    "Modified: 14.10.1996 / 22:26:35 / stefan"
!

exposeX:x y:y width:w height:h
    "an expose event - nothing done here"

    ^ self
!

focusIn
    "got keyboard focus - do nothing here"

    ^ self
!

focusOut
    "lost keyboard focus - do nothing here"

    ^ self
!

graphicsExposeX:x y:y width:w height:h final:final
    "an expose event after a scroll - do normal redraw processing"

    self exposeX:x y:y width:w height:h
!

keyPress:key x:x y:y
    "a key was pressed in this view.
     Here only keyCommands are handled - more action has to
     be implemented by redefining this method"
      
    |action|

    keyCommands notNil ifTrue:[
        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

            self keyPress:(key copyFrom:#Basic size) asSymbol x:x y:y
        ].
    ].

    "Modified: 6.11.1996 / 17:51:15 / cg"
!

keyRelease:key x:x y:y
    "default action is to do nothing"
    
    key isSymbol ifTrue:[
        (key startsWith:#Basic) ifTrue:[
            "/ an unhandled BasicFoo key;
            "/ retry as Foo

            self keyRelease:(key copyFrom:#Basic size) asSymbol x:x y:y
        ].
    ].

    ^ self

    "Modified: 6.11.1996 / 17:51:20 / cg"
!

noExpose
    "a no expose event after a scroll (event-mode only)"

    gotExpose := true
!

pointerEnter:state x:x y:y
    "mouse cursor entered view - do nothing here"

    ^ self
!

pointerLeave:state
    "mouse cursor left view - do nothing here"

    ^ self
!

resizeRequest
    ^ self
!

waitForExpose
    "wait until an expose event arrives (to wait for scroll-finish)"

    |wg endPollTime|

    device scrollsAsynchronous ifFalse:[
        gotExpose := true.
        ^ self
    ].

    wg := self windowGroup.
    wg notNil ifTrue:[
        "/
        "/ 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.

        [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: 19.8.1997 / 17:22:46 / cg"
! !

!DisplaySurface methodsFor:'initialize / release'!

destroy
    "view is about to be destroyed -
     first destroy menu if there is one and also destroy the GC.
     then the view is physically destroyed."
     
    middleButtonMenu notNil ifTrue:[
        middleButtonMenu destroy.
        middleButtonMenu := nil
    ].
    keyCommands := nil.
    gcId notNil ifTrue:[
        device destroyGC:gcId.
        gcId := nil
    ].
    drawableId notNil ifTrue:[
        device destroyView:self withId:drawableId.
        drawableId := nil.
        realized := false.
    ].
    Lobby unregister:self.

    "Modified: 8.2.1997 / 15:50:04 / cg"
!

destroyed
    "view has been destroyed by someone else"

    drawableId notNil ifTrue:[
        device removeKnownView:self withId:drawableId.
        drawableId := nil.
        realized := false. 
    ].
    self destroy

    "Modified: 22.3.1997 / 14:56:34 / cg"
!

initCursor
    "default cursor for all views"

    cursor := Cursor arrow
!

initStyle
    "nothing done here"

    ^ self
!

initialize
    "initialize defaults"

    super initialize.

    eventMask := Display defaultEventMask.
    viewBackground := background.
    backed := false.
    saveUnder := false.
    self initCursor

    "Modified: 18.1.1997 / 18:09:41 / cg"
!

reAdjustGeometry
    "sent late during snapin processing, nothing done here"

    ^ self
!

recreate
    "recreate (i.e. tell X about me) after a snapin"

    viewBackground isColor ifTrue:[
        viewBackground := viewBackground on:device
    ].
    super recreate.
    cursor := cursor onDevice:device.

    "Modified: 28.3.1997 / 13:48:06 / cg"
!

reinitStyle
    "nothing done here"

    ^ self
!

shallowCopyForFinalization
    "redefined for faster creation of finalization copies
     (only device, gcId and drawableId are needed)"

    |aCopy|

    aCopy := DeviceViewHandle basicNew.
    aCopy setDevice:device id:drawableId gcId:gcId.
    ^ aCopy

    "Created: 3.5.1996 / 15:35:13 / stefan"
! !

!DisplaySurface methodsFor:'keyboard commands'!

addActionForKey:aKey action:aBlock
    "define a keyboard command function"

    keyCommands isNil ifTrue:[
	keyCommands := IdentityDictionary new
    ].
    keyCommands at:aKey put:aBlock
!

removeActionForKey:aKey
    keyCommands notNil ifTrue:[
	keyCommands removeKey:aKey ifAbsent:[]
    ]
! !

!DisplaySurface methodsFor:'queries'!

buttonMotionEventPending
    "return true, if a button motion event is pending.
     Normally, you dont want to use this, since no polling is needed
     (not even for mouse-tracking).
     Dont use it, since it does not honor the windowGroup, but
     goes directly to the device instead.
     Actually, its a historical leftover"

    device flush.
    ^ device eventPending:#buttonMotion for:drawableId
!

buttonReleaseEventPending
    "return true, if a button release event is pending.
     Dont use it, since it does not honor the windowGroup, but
     goes directly to the device instead.
     Actually, its a historical leftover"

    device flush.
    ^ device eventPending:#buttonRelease for:drawableId
!

exposeEventPending
    "return true, if an expose event is pending."

    |sensor|

    ((sensor := self sensor) notNil and:[sensor hasDamageFor:self]) ifTrue:[^ true].
    ^ device eventPending:#expose for:drawableId
!

isRootView
    "return true, if the receiver is a root view
     false is returned here, this is only redefined in DisplayRootView."

    ^ false

    "Modified: 28.5.1996 / 19:27:34 / cg"
    "Created: 5.7.1996 / 14:58:55 / cg"
!

isTopView
    "return true, if the receiver is some kind of topview;
     false is returned here; redefined in some subclasses."

    ^ false

    "Modified: 28.5.1996 / 19:27:34 / cg"
    "Created: 22.3.1997 / 14:45:29 / cg"
!

isView
    "return true, if the receiver is some kind of view;
     true is returned here."

    ^ true

    "Modified: 28.5.1996 / 19:27:34 / cg"
!

isXtWidget
    ^ false
!

redrawsFull
    ^ false

    "Created: 4.3.1996 / 14:17:22 / cg"
! !

!DisplaySurface methodsFor:'queries-contents'!

heightOfContents
    "return the height of the contents in pixels.
     Since we dont know here, just return the views size.
     This will make your scrollbars show 100%-visible.
     Must be redefined in subviews to make scrollbars really work."

    ^ self height
!

widthOfContents
    "return the width of the contents in pixels.
     Since we dont know here, just return the views size.
     This will make your scrollbars show 100%-visible.
     Must be redefined in subviews to make scrollbars really work."

    ^ self width
!

xOriginOfContents
    "return the x-origin of the contents in pixels.
     Since we dont know here, just return 0 for left.
     Must be redefined in subviews to make scrollbars really work."

    ^ 0
!

yOriginOfContents
    "return the y-origin of the contents in pixels.
     Since we dont know here, just return 0 for top.
     Must be redefined in subviews to make scrollbars really work."

    ^ 0
! !

!DisplaySurface methodsFor:'selection handling '!

getSelection
    "return the object selection - either the local one, or the displays
     clipBoard buffer."

    |sel|

    sel := device getCopyBuffer.
    sel isNil ifTrue:[
        sel := device getSelectionFor:drawableId.
        sel isNil ifTrue:[^ nil].
    ].
    ^ sel

    "Modified: 13.2.1997 / 13:18:50 / cg"
!

getTextSelection
    "return the text selection - either the local one, or the displays
     clipBoard buffer."

    |sel|

    sel := device getCopyBuffer.
    sel isNil ifTrue:[
        sel := device getTextSelectionFor:drawableId.
        sel isNil ifTrue:[^ nil].
    ].
    ^ sel

    "Modified: 13.2.1997 / 13:19:26 / cg"
!

pasteFromClipBoard:aString
    "this is sent from the display as a reply to a request for a
     selection. The view should be prepared to paste the received
     string (it asked for it so that should not be a problem)"

    self paste:aString

    "Created: 13.2.1997 / 13:06:11 / cg"
!

setSelection:something
    "set the object selection - both the local one, and tell the display
     that we have changed it (i.e. place it into the clipBoard)."

    device setLastCopyBuffer:nil.
    device setCopyBuffer:something.

    (device setSelection:something owner:drawableId) ifFalse:[
        'DisplaySurface [warning]: selection failed' errorPrintCR
    ]

    "Modified: 13.2.1997 / 13:19:51 / cg"
!

setTextSelection:something
    "set the text selection - both the local one, and tell the display
     that we have changed it (i.e. place it into the clipBoard)."

    |s|

    device setLastCopyBuffer:nil.
    device setCopyBuffer:something.
    s := something.
    s isString ifFalse:[
        s := s asStringWithCRsFrom:1 to:(s size) compressTabs:false withCR:false
    ].
    (device setTextSelection:s owner:drawableId) ifFalse:[
        'DisplaySurface [warning]: selection failed' errorPrintCR
    ]

    "Modified: 13.2.1997 / 13:20:00 / cg"
! !

!DisplaySurface methodsFor:'user notification'!

beep
    "output an audible beep or bell on my screen device"

    device beep; flush

    "Created: 28.5.1996 / 16:16:13 / cg"
    "Modified: 28.5.1996 / 16:58:25 / cg"
!

showActivity:aMessage
    "this is sent indirectly by the activityNotification mechanism.
     Defined here as a fallback, if ever sent to non topviews."

    Transcript showCR:aMessage

    "Modified: 18.5.1996 / 15:44:33 / cg"
! !

!DisplaySurface class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview/Attic/DSurface.st,v 1.32 1997-08-19 15:28:27 cg Exp $'
! !