WindowEvent.st
author claus
Tue, 07 Mar 1995 22:57:31 +0100
changeset 115 1d93fd8c5371
parent 89 ea2bf46eb669
child 118 25e775072a89
permissions -rw-r--r--
*** empty log message ***

"
 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 comment:'
COPYRIGHT (c) 1993 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libview/WindowEvent.st,v 1.12 1995-03-07 21:56:53 claus Exp $
'!

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

version
"
$Header: /cvs/stx/stx/libview/WindowEvent.st,v 1.12 1995-03-07 21:56:53 claus Exp $
"
!

documentation
"
    Instances of WindowEvent are created for every event coming from
    the graphics device, to be handled by a windowGroup. 
    Usually, they are queued by a sensor, and processed in some event loop
    in the window group.
"
! !

!WindowEvent class methodsFor:'instance creation'!

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
!

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:#()
!

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

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

! !

!WindowEvent methodsFor:'queries'!

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:)
!

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:']]]]
!

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

    ^ type == #damage
! !

!WindowEvent methodsFor:'accessing'!

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

    ^ view
!

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

    view := aView
!

type
    "return the type of the event"

    ^ type
!

arguments
    "return the arguments of the event"

    ^ arguments
!

arguments:anArray
    "set the arguments"

    arguments := anArray
!

rectangle
    "return the damage rectangle"

    ^ arguments "consider this a kludge"
!

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

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

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 (but not if there was a delegate in the first place).

     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|

    isKeyEvent := isButtonEvent := isPointerEvent := false.

    (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 == #'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 == #'buttonMotion:x:y:') ifTrue:[
	isButtonEvent := true.
	deviceMessage := #'deviceButtonMotion:x:y:'.
	delegateMessage := #'buttonMotion:x:y:view:'.
	delegateQuery := #'handlesButtonMotion: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.
	delegateMessage := #'pointerLeave:view:'.
	delegateQuery := #'handlesPointerLeave:inView:'.
    ] ifFalse:[ (type == #'exposeX:y:width:height:') ifTrue:[
	deviceMessage := #'deviceExposeX:y:width:height:'.
    ] ifFalse:[ (type == #'graphicExposeX:y:width:height:') ifTrue:[
	deviceMessage := #'deviceGraphicExposeX:y:width:height:'.
    ]]]]]]]]]]].

    "
     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 respondsTo:delegateMessage) ifTrue:[
	    "
	     is the delegate interrested in that event ?
	     (if it does not respond to the handlesXXX message,
	      we assume: yes)
	    "
	    ((delegate respondsTo:delegateQuery) not
	    or:[delegate perform:delegateQuery 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
	    ]
	].
    ].

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

    "
     if there is a focusView, and its a keyboard event, pass it
     to that view (or its controller). 
     In this case, a coordinate which is outside of
     the focusView (-1 @ -1) is passed as x/y coordinates.
     Q: should we follow its delegate again ?
    "
    (focusView notNil 
    and:[isKeyEvent]) ifTrue:[
	eventReceiver := focusView.
	(controller := focusView controller) notNil ifTrue:[  
	    eventReceiver := controller.
	].
	eventReceiver perform:type 
		withArguments:(Array with:(argArray at:1)
				     with:-1
				     with:-1).
	^ self
    ].

    "
     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 PseudoView 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:[(type == #'pointerEnter:x:y:')
	 or:[(type == #'exposeX:y:width:height:')
	 or:[(type == #'graphicExposeX:y:width:height:')]]]]) ifTrue:[
	    selector := deviceMessage
	]        
    ].
    eventReceiver perform:selector withArguments:argArray
! !

!WindowEvent methodsFor:'sending'!

sendEvent
    "forward the event represented by the receiver to the delegate,
     the controller or the view."

    self sendEventWithFocusOn:nil
!

sendEventWithFocusOn:focusView
    "forward the event represented by the receiver to the delegate,
     the controller or the view. If focusView is nonNil, and its a keyboard
     event, the event is forwarded to it."

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

!WindowEvent methodsFor:'private accessing'!

for:aView type:aSymbol arguments:argArray
    "set the instances of the window event"

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