WindowEvent.st
author Claus Gittinger <cg@exept.de>
Sat, 12 Apr 1997 11:31:08 +0200
changeset 1590 18ca787fd066
parent 1588 8f9468059ef7
child 1730 484d0d28f4c7
permissions -rw-r--r--
checkin from browser

"
 COPYRIGHT (c) 1993 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.
"

Object subclass:#WindowEvent
	instanceVariableNames:'view type arguments'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-Support'
!

WindowEvent subclass:#KeyboardEvent
	instanceVariableNames:'rawKey modifierFlags'
	classVariableNames:'F_CTRL F_ALT F_META F_SHIFT'
	poolDictionaries:''
	privateIn:WindowEvent
!

WindowEvent subclass:#ClientEvent
	instanceVariableNames:'eventData'
	classVariableNames:''
	poolDictionaries:''
	privateIn:WindowEvent
!

WindowEvent subclass:#ButtonEvent
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:WindowEvent
!

!WindowEvent class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1993 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
"
    Instances of WindowEvent are created for every event coming from
    the graphics device. 
    Usually, they are enqueued by the event dispatcher process into
    a sensors input queue, and dequeued & processed by a windowGroup process
    in its event loop.

    WindowEvents hold the event type and additional information (such as key,
    x/y coordinates etc). Also, windowEvents know how to send themself to some
    destination. To provide a common (single) place where event dispatching is
    implemented, this forwarding is done by a class method here (i.e. not by the
    window group itself).

    The algorithm for event dispatching is:

        - if the destination view has a keyboard focus set,
          AND the event is a keyboard event,
          THEN recursively invoke the event dispatching method,
               sending the event to the focus view (or its delegate, as below)

        - if the destination view has a delegate,
          AND its a keyboard, button or pointer event,
          AND the delegate is interested in that event 
              (i.e. implements & responds to #handlesXXX with true)
          THEN send the event to the delegate, passing the original view
               as additional argument

        - if the view has a nonNil controller,
          AND its a key, button or pointer event,
          THEN send the event to the controller

        - otherwise send the event to the view


    If the view has a non-nil transformation, the event is sent as a
    #deviceXXX message, passing device coordinates. Typically, subclasses
    of view do not redefine this method and the inherited default method
    translates these device coordinates into logical coordinates and resends
    an XXX message.
    If the view has no transformation, the XXX message is directly sent here.

    For example, a 'buttonPress:button x:x y:y' event leads to sending of
    'aView deviceButtonPress:button x:x y:y' which resends
    'aView buttonPress:button x:(x-logical) y:(y-logical)'

    This allows views which are interested in deviceCoordinates to get them
    (by redefining #deviceXXX) and other views to transparently get & use
    logical coordinates.

    Therefore, for a delegated keyPress messages, the flow is:

        sendEvent
            view has delegate
                ------> ask delegate via 'handlesKeyPress:key inView:view'
                <------ returns true
                ------> 'delegate keyPress:key x:x y:y view:view'
                        -----> delegate does whatever it wants to do
                               (typically sends the event to some other view)

    for an undelegated message:

        sendEvent
            view has delegate
                ------> ask delegate via 'handlesKeyPress:key inView:view'
                <------ returns false
            view has controller
                ------> 'controller keyPress:key x:x y:y'
            view has no controller
                view has transformation
                    ----> 'view deviceKeyPress:key x:x y:y'
                          inverse transform x/y
                          ----> 'self keyPress:key x:xLogical y:yLogical'
                view has no transformation
                    ----> 'view keyPress:key x:x y:y'

    [author:]
        Claus Gittinger

    [see also:]
        WindowGroup WindowSensor
        DeviceWorkstation View
        KeyboardMap KeyboardForwarder EventListener

"
! !

!WindowEvent class methodsFor:'instance creation'!

damageFor:aView rectangle:aRectangle
    "create and return a new damage Event for aRectangle
     in aView"

    ^ (self new) for:aView type:#damage arguments:aRectangle

!

for:aView type:aSymbol
    "create and return a new windowEvent for sending
     aSymbol-message with no arguments to aView"

    ^ (self new) for:aView type:aSymbol arguments:#()
!

for:aView type:aSymbol arguments:argArray
    "create and return a new windowEvent for sending
     aSymbol-message with arguments to aView"

    ^ (self new) for:aView type:aSymbol arguments:argArray
! !

!WindowEvent class methodsFor:'event class access'!

buttonEvent
    ^ ButtonEvent

    "Created: 4.4.1997 / 13:45:04 / cg"
!

clientEvent
    ^ ClientEvent

    "Created: 4.4.1997 / 13:58:25 / cg"
!

keyboardEvent
    ^ KeyboardEvent

    "Created: 4.4.1997 / 13:41:44 / cg"
! !

!WindowEvent class methodsFor:'forwarding events'!

sendEvent:type arguments:arguments view:view
    "forward the event represented by type and arguments to the views delegate,
     the views controller or the view. 

     If there is a delegate, only messages which are understood by it are 
     forwarded. Also, the delegate is asked if it is willing to handle the event
     before.
     Delegated messages get the original view as an extra argument.
     Delegation has higher priority than controller forwarding."

    ^ self 
	sendEvent:type 
	arguments:arguments 
	view:view 
	withFocusOn:nil 
	delegate:true
!

sendEvent:type arguments:argArray view:view withFocusOn:focusView
    "forward the event represented by type and arguments to the views delegate,
     the views controller or the view. 
     If focusView is nonNil, and it is a keyboard event, it is forwarded to this
     view (even if there is a delegate).

     If there is a delegate, only messages which are understood by it are 
     forwarded. Also, the delegate is asked if it is willing to handle the event
     before.
     Delegated messages get the original view as an extra argument.
     Delegation has higher priority than both controller or focusView 
     forwarding."

    ^ self 
	sendEvent:type 
	arguments:argArray 
	view:view 
	withFocusOn:focusView 
	delegate:true 
!

sendEvent:type arguments:argArray view:view withFocusOn:focusView delegate:doDelegate
    "forward the event represented by type and arguments to the views delegate,
     the views controller or the view. 
     If focusView is nonNil, and it is a keyboard event, it is forwarded to this
     view (but not if there was a delegate in the first place).

     If doDelegate is true, keyboard and button events are forwarded to a
     delegate object (if non-nil). DoDelegate may be passed as true, to
     handle events which are already delegated.
     If there is a delegate, only messages which are understood by it are 
     forwarded. Also, the delegate is asked if it is willing to handle the event
     before.
     Delegated messages get the original view as an extra argument.
     Delegation has higher priority than both controller or focusView 
     forwarding."

    |delegate selector delegateMessage delegateQuery 
     eventReceiver controller deviceMessage
     isKeyEvent isButtonEvent isPointerEvent trans
     rect x y w h|

    isKeyEvent := isButtonEvent := isPointerEvent := false.

    type == #damage ifTrue:[
        view shown ifTrue:[
            rect := argArray.
            x := rect left.
            y := rect top.
            w := rect width.
            h := rect height.
            view transformation notNil ifTrue:[
                view deviceExposeX:x y:y width:w height:h
            ] ifFalse:[
                view exposeX:x y:y width:w height:h
            ]
        ].
        ^ self
    ].

    (type == #'keyPress:x:y:') ifTrue:[
        isKeyEvent := true.
        deviceMessage := #'deviceKeyPress:x:y:'.
        delegateMessage := #'keyPress:x:y:view:'.
        delegateQuery := #'handlesKeyPress:inView:'.
    ] ifFalse:[ (type == #'keyRelease:x:y:') ifTrue:[
        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:'.
    ] ifFalse:[ (type == #'buttonPress:x:y:') ifTrue:[
        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:'.
    ] ifFalse:[ (type == #'buttonShiftPress:x:y:') ifTrue:[
        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:'.
    ] ifFalse:[ (type == #'pointerEnter:x:y:') ifTrue:[
        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:'.
    ] ifFalse:[ (type == #'exposeX:y:width:height:') ifTrue:[
        deviceMessage := #'deviceExposeX:y:width:height:'.
    ] ifFalse:[ (type == #'graphicsExposeX:y:width:height:final:') ifTrue:[
        deviceMessage := #'deviceGraphicsExposeX:y:width:height:final:'.
    ]]]]]]]]]]].

    "
     if there is a focusView, and its a keyboard event, pass it
     to that view (or its controller, or its delegate). 
     In this case, a coordinate which is outside of
     the focusView (0 @ 0) is passed as x/y coordinates.
    "
    (focusView notNil 
    and:[isKeyEvent]) ifTrue:[
        self sendEvent:type 
             arguments:(Array with:(argArray at:1) with:0 with:0)
             view:focusView 
             withFocusOn:nil
             delegate:doDelegate.
        ^ self
    ].

    doDelegate ifTrue:[
        "
         handle delegated messages
        "
        (isKeyEvent 
         or:[isButtonEvent 
         or:[isPointerEvent]]) ifTrue:[
            delegate := view 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:view]) ifTrue:[
                    "
                     mhmh ... have to convert to logical coordinates
                    "        
                    (trans := view transformation) notNil ifTrue:[
                        argArray size > 2 ifTrue:[
                            argArray at:2 put:(trans applyInverseToX:(argArray at:2)).
                            argArray at:3 put:(trans applyInverseToY:(argArray at:3)).
                        ].
                    ].
                    argArray isNil ifTrue:[
                        delegate perform:delegateMessage with:view
                    ] ifFalse:[
                        delegate perform:delegateMessage withArguments:(argArray copyWith:view)
                    ].
                    ^ self
                ]
            ].
        ].
    ].

    (isKeyEvent 
     or:[isButtonEvent 
     or:[isPointerEvent]]) ifTrue:[
        view realized ifFalse:[
            ^ self
        ]
    ].

    "
     if there is a controller, that one gets all user events
    "
    eventReceiver := view.
    (controller := view controller) notNil ifTrue:[  
        (isKeyEvent 
         or:[isButtonEvent 
         or:[isPointerEvent
         or:[(type == #focusIn)
         or:[(type == #focusOut)]]]]) ifTrue:[
            eventReceiver := controller.
        ]
    ].

    "
     finally, another one:
     if the view has a transformation, edit the selector
     from #foo to #deviceFoo...
     This allows the view to handle the event either in device or
     logical coordinates. (since the deviceFoo-messages default implementation
     in DisplaySurface translates and resends).
     Actually, I could always send deviceXXX without speed penalty
     (event sending is no high frequency operation), but that just adds 
     another context to any debuggers walkback, making things less clear.
    "
    selector := type.

    view transformation notNil ifTrue:[
        (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

    "Modified: 20.3.1997 / 14:25:31 / cg"
! !

!WindowEvent methodsFor:'accessing'!

arguments
    "return the arguments of the event"

    ^ arguments
!

arguments:anArray
    "set the arguments"

    arguments := anArray
!

key
    "return the key of the key-event. For non key-events, nil is returned."

    ((type == #keyPress:x:y:)
    or:[type == #keyRelease:x:y:]) ifTrue:[
	^ arguments at:1
    ].
    ^ nil
!

rectangle
    "return the damage rectangle"

    ^ arguments "consider this a kludge"
!

type
    "return the type of the event"

    ^ type
!

view
    "return the view, for which the event is for"

    ^ view
!

view:aView
    "set the view, for which the event is for"

    view := aView
! !

!WindowEvent methodsFor:'printing & storing'!

displayString
    ^ self className 
      , '(' , type storeString 
      , ' view: ' , view className 
      , ' args: ' , arguments displayString
      , ')'

    "Created: 7.3.1996 / 14:55:50 / cg"
    "Modified: 7.3.1996 / 14:58:21 / cg"
! !

!WindowEvent methodsFor:'private accessing'!

for:aView type:aSymbol arguments:argArray
    "set the instance variables of the event"

    view := aView.
    type := aSymbol.
    arguments := argArray
! !

!WindowEvent methodsFor:'queries'!

hasAlt
    "return true, if this is a keyboard event, with ALT pressed"

    ^ false

    "Created: 12.4.1997 / 11:04:10 / cg"
!

hasCtrl
    "return true, if this is a keyboard event, with CTRL pressed"

    ^ false

    "Created: 12.4.1997 / 11:04:03 / cg"
!

hasMeta
    "return true, if this is a keyboard event, with META pressed"

    ^ false

    "Created: 12.4.1997 / 11:04:16 / cg"
!

hasShift
    "return true, if this is a keyboard event, with SHIFT pressed"

    ^ false

    "Created: 12.4.1997 / 11:30:59 / cg"
!

isButtonEvent
    "return true, if this event is a button event"

    ^ (type == #buttonPress:x:y:) 
      or:[type == #buttonRelease:x:y:
      or:[type == #'buttonShiftPress:x:y:'
      or:[type == #'buttonMultiPress:x:y:'
      or:[type == #'buttonMotion:x:y:']]]]
!

isButtonPressEvent
    "return true, if this event is a buttonPress event"

    ^ (type == #buttonPress:x:y:)

    "Created: 5.3.1997 / 12:25:43 / cg"
!

isDamage
    "return true, if this is a damage event"

    ^ type == #damage
!

isFocusEvent
    "return true, if this event is a focusIn/focusOut event"

    ^ (type == #focusIn) or:[type == #focusOut]

    "Created: 5.3.1997 / 12:12:37 / cg"
!

isFocusInEvent
    "return true, if this event is a focusIn event"

    ^ (type == #focusIn)

    "Created: 5.3.1997 / 12:18:10 / cg"
!

isKeyEvent
    "return true, if this event is a keyboard event"

    ^ (type == #keyPress:x:y:) or:[type == #keyRelease:x:y:]
!

isKeyPressEvent
    "return true, if this event is a keyboard event"

    ^ (type == #keyPress:x:y:)
!

isPointerEnterEvent
    "return true, if this event is a pointer-enter event"

    ^ (type == #pointerEnter:x:y:)

    "Created: 9.1.1996 / 15:51:24 / cg"
    "Modified: 9.1.1996 / 15:51:40 / cg"
!

isPointerEnterLeaveEvent
    "return true, if this event is a pointer-enter/leave event"

    ^ (type == #pointerEnter:x:y:) or:[type == #pointerLeave:view:]

    "Created: 9.1.1996 / 15:51:18 / cg"
!

isPointerLeaveEvent
    "return true, if this event is a pointer-leave event"

    ^ type == #pointerLeave:view:

    "Created: 9.1.1996 / 15:51:36 / cg"
!

isUserEvent
    "return true, if this event is a user event (i.e. mouse, keyboard or button)"

    (type == #buttonPress:x:y:) ifTrue:[^ true].
    (type == #buttonRelease:x:y:) ifTrue:[^ true].
    (type == #buttonShiftPress:x:y:) ifTrue:[^ true].
    (type == #buttonMultiPress:x:y:) ifTrue:[^ true].
    (type == #buttonMotion:x:y:) ifTrue:[^ true].

    (type == #keyPress:x:y:) ifTrue:[^ true].
    (type == #keyRelease:x:y:) ifTrue:[^ true].

    (type == #pointerEnter:x:y:) ifTrue:[^ true].
"/    (type == #pointerLeave:) ifTrue:[^ true].

    ^ false

    "Modified: 5.3.1997 / 11:27:40 / cg"
! !

!WindowEvent methodsFor:'sending'!

sendEvent
    "forward the event represented by the receiver to the views delegate,
     the views controller or the view. Ignore any focusView."

    self sendEventWithFocusOn:nil
!

sendEventWithFocusOn:focusView
    "forward the event represented by the receiver to the views delegate,
     the views controller or the view. 
     If focusView is nonNil, and the receiver is a keyboard event, 
     the event will be forwarded to the focusView instead 
     (or its delegate, or its controller)."

    self class 
	sendEvent:type 
	arguments:arguments 
	view:view 
	withFocusOn:focusView
	delegate:true
! !

!WindowEvent::KeyboardEvent class methodsFor:'class initialization'!

initialize
    F_SHIFT := 1.
    F_CTRL := 2.
    F_ALT := 4.
    F_META := 8.

    "Created: 12.4.1997 / 11:08:28 / cg"
! !

!WindowEvent::KeyboardEvent methodsFor:'accessing'!

hasShift:shift hasCtrl:ctrl hasAlt:alt hasMeta:meta
    |f "{ Class: SmallInteger }"|

    f := 0.
    shift ifTrue:[f := f bitOr:F_SHIFT].
    ctrl ifTrue:[f := f bitOr:F_CTRL].
    alt ifTrue:[f := f bitOr:F_ALT].
    meta ifTrue:[f := f bitOr:F_META].
    modifierFlags := f.

    "Modified: 12.4.1997 / 11:10:38 / cg"
!

rawKey
    ^ rawKey

    "Created: 4.4.1997 / 13:47:15 / cg"
!

rawKey:aKey
    rawKey := aKey

    "Created: 4.4.1997 / 13:47:10 / cg"
! !

!WindowEvent::KeyboardEvent methodsFor:'queries'!

hasAlt
    "return true, if this is a keyboard event, with ALT pressed"

    ^ (modifierFlags bitAnd:F_ALT) ~~ 0

    "Created: 12.4.1997 / 11:05:09 / cg"
    "Modified: 12.4.1997 / 11:10:57 / cg"
!

hasCtrl
    "return true, if this is a keyboard event, with CTRL pressed"

    ^ (modifierFlags bitAnd:F_CTRL) ~~ 0

    "Created: 12.4.1997 / 11:05:04 / cg"
    "Modified: 12.4.1997 / 11:11:03 / cg"
!

hasMeta
    "return true, if this is a keyboard event, with META pressed"

    ^ (modifierFlags bitAnd:F_META) ~~ 0

    "Created: 12.4.1997 / 11:04:45 / cg"
    "Modified: 12.4.1997 / 11:11:10 / cg"
!

hasShift
    "return true, if this is a keyboard event, with SHIFT pressed"

    ^ (modifierFlags bitAnd:F_SHIFT) ~~ 0

    "Created: 12.4.1997 / 11:11:21 / cg"
!

isKeyEvent
    "return true, if this event is a keyboard event"

    ^ true

    "Created: 4.4.1997 / 13:39:59 / cg"
! !

!WindowEvent::ClientEvent methodsFor:'accessing'!

eventData
    "return the value of the instance variable 'eventData' (automatically generated)"

    ^ eventData

    "Created: 4.4.1997 / 17:41:50 / cg"
!

eventData:something
    "set the value of the instance variable 'eventData' (automatically generated)"

    eventData := something.

    "Created: 4.4.1997 / 17:41:57 / cg"
! !

!WindowEvent::ButtonEvent methodsFor:'queries'!

isButtonEvent
    "return true, if this event is a button event"

    ^ true

    "Created: 4.4.1997 / 13:44:11 / cg"
!

isButtonPressEvent
    "return true, if this event is a buttonPress event"

    ^ (type == #buttonPress:x:y:)

    "Created: 4.4.1997 / 13:44:22 / cg"
! !

!WindowEvent class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview/WindowEvent.st,v 1.42 1997-04-12 09:31:08 cg Exp $'
! !