[squeak-dev] The Trunk: Morphic-mt.1161.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Jun 4 16:39:06 UTC 2016


Marcel Taeumel uploaded a new version of Morphic to project The Trunk:
http://source.squeak.org/trunk/Morphic-mt.1161.mcz

==================== Summary ====================

Name: Morphic-mt.1161
Author: mt
Time: 4 June 2016, 6:38:28.65943 pm
UUID: aa80b684-784c-7549-bb0c-a1c9026a4797
Ancestors: Morphic-mt.1160

Adds event filters. Includes refactorings for MorphicEventDispatcher and HandMorph >> #handleEvent:. Also fixes event bubbling for focus events. Sorry for this agglomeration of changes.

See Morph >> #eventFilterDocumentation.

=============== Diff against Morphic-mt.1160 ===============

Item was changed:
  ----- Method: DockingBarMorph>>handleFocusEvent: (in category 'events-processing') -----
  handleFocusEvent: evt
  	"Handle focus events. Valid menu transitions are determined based on the menu currently holding the focus after the mouse went down on one of its children."
  
+ 	| result filteredEvent |
+ 	(evt isMouse and:[ evt isMouseUp ]) ifTrue:[^ evt].
- 	(evt isMouse and:[ evt isMouseUp ]) ifTrue:[^ self].
  
+ 	result := self processEvent: evt.
+ 	filteredEvent := result == #rejected ifTrue: [evt] ifFalse: [result].
- 	self processEvent: evt.
  
  	"Need to handle keyboard input if we have the focus."
+ 	filteredEvent isKeyboard ifTrue: [^ super handleFocusEvent: filteredEvent].
- 	evt isKeyboard ifTrue: [^ self handleEvent: evt].
  
  	"We need to handle button clicks outside and transitions to local popUps so throw away everything else"
+ 	(filteredEvent isMouseOver or:[filteredEvent isMouse not]) ifTrue:[^filteredEvent].
- 	(evt isMouseOver or:[evt isMouse not]) ifTrue:[^self].
  	"What remains are mouse buttons and moves"
+ 	filteredEvent isMove ifFalse:[^super handleFocusEvent: filteredEvent]. "handle clicks outside by regular means"
- 	evt isMove ifFalse:[^self handleEvent: evt]. "handle clicks outside by regular means"
  	"Now it's getting tricky. On #mouseMove we might transfer control to *either* the currently active submenu or the pop up owner, if any. Since the active sub menu is always displayed upfront check it first."
+ 	selectedItem ifNotNil:[(selectedItem activateSubmenu: filteredEvent) ifTrue:[^filteredEvent]].
- 	selectedItem ifNotNil:[(selectedItem activateSubmenu: evt) ifTrue:[^self]].
  !

Item was added:
+ ----- Method: DropEvent>>translateTo: (in category 'transforming') -----
+ translateTo: point
+ 
+ 	position := point.!

Item was changed:
  Morph subclass: #HandMorph
+ 	instanceVariableNames: 'mouseFocus keyboardFocus eventListeners mouseListeners keyboardListeners eventFilters mouseFilters keyboardFilters eventCaptureFilters mouseCaptureFilters keyboardCaptureFilters mouseClickState mouseOverHandler lastMouseEvent targetOffset damageRecorder cacheCanvas cachedCanvasHasHoles temporaryCursor temporaryCursorOffset hardwareCursor hasChanged savedPatch userInitials lastEventBuffer genieGestureProcessor keyboardInterpreter'
- 	instanceVariableNames: 'mouseFocus keyboardFocus eventListeners mouseListeners keyboardListeners mouseClickState mouseOverHandler lastMouseEvent targetOffset damageRecorder cacheCanvas cachedCanvasHasHoles temporaryCursor temporaryCursorOffset hardwareCursor hasChanged savedPatch userInitials lastEventBuffer genieGestureProcessor keyboardInterpreter'
  	classVariableNames: 'CompositionWindowManager DoubleClickTime DragThreshold EventStats NewEventRules NormalCursor PasteBuffer ShowEvents'
  	poolDictionaries: 'EventSensorConstants'
  	category: 'Morphic-Kernel'!
  
  !HandMorph commentStamp: '<historical>' prior: 0!
  The cursor may be thought of as the HandMorph.  The hand's submorphs hold anything being carried by dragging.  
  
  There is some minimal support for multiple hands in the same world.!

Item was changed:
+ ----- Method: HandMorph>>addEventListener: (in category 'events-listening') -----
- ----- Method: HandMorph>>addEventListener: (in category 'listeners') -----
  addEventListener: anObject
  	"Make anObject a listener for all events. All events will be reported to the object."
  	self eventListeners: (self addListener: anObject to: self eventListeners)!

Item was changed:
+ ----- Method: HandMorph>>addKeyboardListener: (in category 'events-listening') -----
- ----- Method: HandMorph>>addKeyboardListener: (in category 'listeners') -----
  addKeyboardListener: anObject
  	"Make anObject a listener for keyboard events. All keyboard events will be reported to the object."
  	self keyboardListeners: (self addListener: anObject to: self keyboardListeners)!

Item was changed:
+ ----- Method: HandMorph>>addListener:to: (in category 'events-listening') -----
- ----- Method: HandMorph>>addListener:to: (in category 'listeners') -----
  addListener: anObject to: aListenerGroup
  	"Add anObject to the given listener group. Return the new group."
  	| listeners |
  	listeners := aListenerGroup.
  	(listeners notNil and:[listeners includes: anObject]) ifFalse:[
  		listeners
  			ifNil:[listeners := WeakArray with: anObject]
  			ifNotNil:[listeners := listeners copyWith: anObject]].
  	listeners := listeners copyWithout: nil. "obsolete entries"
  	^listeners!

Item was changed:
+ ----- Method: HandMorph>>addMouseListener: (in category 'events-listening') -----
- ----- Method: HandMorph>>addMouseListener: (in category 'listeners') -----
  addMouseListener: anObject
  	"Make anObject a listener for mouse events. All mouse events will be reported to the object."
  	self mouseListeners: (self addListener: anObject to: self mouseListeners)!

Item was changed:
  ----- Method: HandMorph>>dropMorph:event: (in category 'grabbing/dropping') -----
  dropMorph: aMorph event: anEvent
  	"Drop the given morph which was carried by the hand"
  	| event dropped |
  	(anEvent isMouseUp and:[aMorph shouldDropOnMouseUp not]) ifTrue:[^self].
  
  	"Note: For robustness in drag and drop handling we remove the morph BEFORE we drop him, but we keep his owner set to the hand. This prevents system lockups when there is a problem in drop handling (for example if there's an error in #wantsToBeDroppedInto:). THIS TECHNIQUE IS NOT RECOMMENDED FOR CASUAL USE."
  	self privateRemove: aMorph.
  	aMorph privateOwner: self.
  
  	dropped := aMorph.
  	(dropped hasProperty: #addedFlexAtGrab) 
  		ifTrue:[dropped := aMorph removeFlexShell].
  	event := DropEvent new setPosition: self position contents: dropped hand: self.
  	
  	[ "In case of an error, ensure that the morph-to-be-dropped will be disposed. Otherwise it may confuse garbage handler. See the sends of #privateRemove: and #privateOwner: above."
+ 		event := self sendEvent: event focus: nil. "event filters can apply and filtered events will be returned"
- 		self sendEvent: event focus: nil.
  		event wasHandled ifFalse: [aMorph rejectDropMorphEvent: event] ]
  			ensure: [ aMorph owner == self ifTrue: [aMorph delete] ].
  	
  	self mouseOverHandler processMouseOver: anEvent.!

Item was added:
+ ----- Method: HandMorph>>eventBubbleFilters (in category 'events-filtering-bubbling') -----
+ eventBubbleFilters
+ 	Error signal: 'Hand morphs do only have capture filters. Install top-most bubble filters in the world.'!

Item was added:
+ ----- Method: HandMorph>>eventCaptureFilters (in category 'events-filtering-capturing') -----
+ eventCaptureFilters
+ 	^ eventCaptureFilters!

Item was added:
+ ----- Method: HandMorph>>eventCaptureFilters: (in category 'events-filtering-capturing') -----
+ eventCaptureFilters: anArrayOrNil
+ 	eventCaptureFilters := anArrayOrNil!

Item was changed:
+ ----- Method: HandMorph>>eventListeners (in category 'events-listening') -----
- ----- Method: HandMorph>>eventListeners (in category 'listeners') -----
  eventListeners
  	^eventListeners!

Item was changed:
+ ----- Method: HandMorph>>eventListeners: (in category 'events-listening') -----
- ----- Method: HandMorph>>eventListeners: (in category 'listeners') -----
  eventListeners: anArrayOrNil
  	eventListeners := anArrayOrNil!

Item was changed:
  ----- Method: HandMorph>>handleEvent: (in category 'events-processing') -----
+ handleEvent: unfilteredEvent
- handleEvent: anEvent
- 	| evt ofs |
- 	owner ifNil:[^self].
- 	evt := anEvent.
  
+ 	| filteredEvent |
+ 	owner ifNil: [^ unfilteredEvent  "not necessary but good style -- see Morph >> #handleEvent:"].
+ 	
+ 	self logEvent: unfilteredEvent.
- 	EventStats ifNil:[EventStats := IdentityDictionary new].
- 	EventStats at: #count put: (EventStats at: #count ifAbsent:[0]) + 1.
- 	EventStats at: evt type put: (EventStats at: evt type ifAbsent:[0]) + 1.
  
+ 	"Mouse-over events occur really, really, really often. They are kind of the heart beat of the Morphic UI process."
+ 	unfilteredEvent isMouseOver ifTrue: [^ self sendMouseEvent: unfilteredEvent].
- 	evt isMouseOver ifTrue:[^self sendMouseEvent: evt].
  
+ 	self showEvent: unfilteredEvent.
+ 	self sendListenEvents: unfilteredEvent.
+ 	
+ 	filteredEvent := self sendFilterEventCapture: unfilteredEvent for: nil.
+ 	"filteredEvent := unfilteredEvent" " <-- use this to disable global capture filters"
+ 	
+ 	filteredEvent wasIgnored ifTrue: [
+ 		self mouseOverHandler processMouseOver: lastMouseEvent.
+ 		^ filteredEvent].
+ 	
+ 	filteredEvent isWindowEvent ifTrue: [
+ 		self sendEvent: filteredEvent focus: nil.
+ 		self mouseOverHandler processMouseOver: lastMouseEvent.
+ 		^ filteredEvent].
- ShowEvents == true ifTrue:[
- 	Display fill: (0 at 0 extent: 300 at 120) rule: Form over fillColor: Color white.
- 	ofs := (owner hands indexOf: self) - 1 * 60.
- 	evt isKeyboard
- 		ifTrue: [ 'key: ', evt printString displayAt: (0 at ofs) + (0 at 30) ]
- 		ifFalse: [ 'evt: ', evt printString displayAt: (0 at ofs) + (0 at 0) ].
- 	'kf:  ', self keyboardFocus printString displayAt: (0 at ofs)+(0 at 45).
- ].
- 	"Notify listeners"
- 	self sendListenEvent: evt to: self eventListeners.
  
+ 	filteredEvent isKeyboard ifTrue:[
+ 		self sendKeyboardEvent: filteredEvent.
+ 		self mouseOverHandler processMouseOver: lastMouseEvent.
+ 		^ filteredEvent].
+ 			
+ 	filteredEvent isDropEvent ifTrue:[
+ 		self sendEvent: filteredEvent focus: nil.
+ 		self mouseOverHandler processMouseOver: lastMouseEvent.
+ 		^ filteredEvent].
- 	evt isWindowEvent ifTrue: [
- 		self sendEvent: evt focus: nil.
- 		^self mouseOverHandler processMouseOver: lastMouseEvent].
  
+ 	filteredEvent isMouse ifFalse: [
+ 		self mouseOverHandler processMouseOver: lastMouseEvent.
+ 		^ filteredEvent].
- 	evt isKeyboard ifTrue:[
- 		self sendListenEvent: evt to: self keyboardListeners.
- 		self sendKeyboardEvent: evt.
- 		^self mouseOverHandler processMouseOver: lastMouseEvent].
  
+ 	" ********** MOUSE EVENT *********** "
- 	evt isDropEvent ifTrue:[
- 		self sendEvent: evt focus: nil.
- 		^self mouseOverHandler processMouseOver: lastMouseEvent].
  
+ 	lastMouseEvent := filteredEvent.
- 	evt isMouse ifTrue:[
- 		self sendListenEvent: evt to: self mouseListeners.
- 		lastMouseEvent := evt].
  
  	"Check for pending drag or double click operations."
  	mouseClickState ifNotNil:[
+ 		(mouseClickState handleEvent: filteredEvent from: self) ifFalse:[
- 		(mouseClickState handleEvent: evt from: self) ifFalse:[
  			"Possibly dispatched #click: or something and will not re-establish otherwise"
+ 			self mouseOverHandler processMouseOver: lastMouseEvent.
+ 			^ filteredEvent]].
- 			^self mouseOverHandler processMouseOver: lastMouseEvent]].
  
+ 	filteredEvent isMove ifTrue:[
+ 		self position: filteredEvent position.
+ 		self sendMouseEvent: filteredEvent.
+ 		self mouseOverHandler processMouseOver: lastMouseEvent.
+ 		^ filteredEvent].
+ 
+ 	"Issue a synthetic move event if we're not at the position of the event"
+ 	filteredEvent position = self position
+ 		ifFalse: [self moveToEvent: filteredEvent].
+ 	
+ 	"Drop submorphs on button events"
+ 	self hasSubmorphs
+ 		ifTrue:[self dropMorphs: filteredEvent]
+ 		ifFalse:[self sendMouseEvent: filteredEvent].
+ 
- 	evt isMove ifTrue:[
- 		self position: evt position.
- 		self sendMouseEvent: evt.
- 	] ifFalse:[
- 		"Issue a synthetic move event if we're not at the position of the event"
- 		(evt position = self position) ifFalse:[self moveToEvent: evt].
- 		"Drop submorphs on button events"
- 		(self hasSubmorphs) 
- 			ifTrue:[self dropMorphs: evt]
- 			ifFalse:[self sendMouseEvent: evt].
- 	].
- 	ShowEvents == true ifTrue:['mf: ', self mouseFocus printString displayAt: (0 at ofs) + (0 at 15)].
  	self mouseOverHandler processMouseOver: lastMouseEvent.
+ 	^ filteredEvent "not necessary but good style -- see Morph >> #handleEvent:"	!
- 	"self handleDragOutside: anEvent."
- !

Item was added:
+ ----- Method: HandMorph>>keyboardBubbleFilters (in category 'events-filtering-bubbling') -----
+ keyboardBubbleFilters
+ 	Error signal: 'Hand morphs do only have capture filters. Install top-most bubble filters in the world.'!

Item was added:
+ ----- Method: HandMorph>>keyboardCaptureFilters (in category 'events-filtering-capturing') -----
+ keyboardCaptureFilters
+ 	^ keyboardCaptureFilters!

Item was added:
+ ----- Method: HandMorph>>keyboardCaptureFilters: (in category 'events-filtering-capturing') -----
+ keyboardCaptureFilters: anArrayOrNil
+ 	keyboardCaptureFilters := anArrayOrNil!

Item was changed:
+ ----- Method: HandMorph>>keyboardListeners (in category 'events-listening') -----
- ----- Method: HandMorph>>keyboardListeners (in category 'listeners') -----
  keyboardListeners
  	^keyboardListeners!

Item was changed:
+ ----- Method: HandMorph>>keyboardListeners: (in category 'events-listening') -----
- ----- Method: HandMorph>>keyboardListeners: (in category 'listeners') -----
  keyboardListeners: anArrayOrNil
  	keyboardListeners := anArrayOrNil!

Item was added:
+ ----- Method: HandMorph>>logEvent: (in category 'events-debugging') -----
+ logEvent: anEvent
+ 	"Update statistics for processed events."
+ 	
+ 	EventStats ifNil:[EventStats := IdentityDictionary new].
+ 	EventStats at: #count put: (EventStats at: #count ifAbsent:[0]) + 1.
+ 	EventStats at: anEvent type put: (EventStats at: anEvent type ifAbsent:[0]) + 1.!

Item was added:
+ ----- Method: HandMorph>>mouseBubbleFilters (in category 'events-filtering-bubbling') -----
+ mouseBubbleFilters
+ 	Error signal: 'Hand morphs do only have capture filters. Install top-most bubble filters in the world.'!

Item was added:
+ ----- Method: HandMorph>>mouseCaptureFilters (in category 'events-filtering-capturing') -----
+ mouseCaptureFilters
+ 	^ mouseCaptureFilters!

Item was added:
+ ----- Method: HandMorph>>mouseCaptureFilters: (in category 'events-filtering-capturing') -----
+ mouseCaptureFilters: anArrayOrNil
+ 	mouseCaptureFilters := anArrayOrNil!

Item was changed:
+ ----- Method: HandMorph>>mouseListeners (in category 'events-listening') -----
- ----- Method: HandMorph>>mouseListeners (in category 'listeners') -----
  mouseListeners
  	^mouseListeners!

Item was changed:
+ ----- Method: HandMorph>>mouseListeners: (in category 'events-listening') -----
- ----- Method: HandMorph>>mouseListeners: (in category 'listeners') -----
  mouseListeners: anArrayOrNil
  	mouseListeners := anArrayOrNil!

Item was changed:
+ ----- Method: HandMorph>>removeEventListener: (in category 'events-listening') -----
- ----- Method: HandMorph>>removeEventListener: (in category 'listeners') -----
  removeEventListener: anObject
  	"Remove anObject from the current event listeners."
  	self eventListeners: (self removeListener: anObject from: self eventListeners).!

Item was changed:
+ ----- Method: HandMorph>>removeKeyboardListener: (in category 'events-listening') -----
- ----- Method: HandMorph>>removeKeyboardListener: (in category 'listeners') -----
  removeKeyboardListener: anObject
  	"Remove anObject from the current keyboard listeners."
  	self keyboardListeners: (self removeListener: anObject from: self keyboardListeners).!

Item was changed:
+ ----- Method: HandMorph>>removeListener:from: (in category 'events-listening') -----
- ----- Method: HandMorph>>removeListener:from: (in category 'listeners') -----
  removeListener: anObject from: aListenerGroup 
  	"Remove anObject from the given listener group. Return the new group."
  
  	| listeners |
  	aListenerGroup ifNil: [^nil].
  	listeners := aListenerGroup.
  	listeners := listeners copyWithout: anObject.
  	listeners := listeners copyWithout: nil.	"obsolete entries"
  	listeners isEmpty ifTrue: [listeners := nil].
  	^listeners!

Item was changed:
+ ----- Method: HandMorph>>removeMouseListener: (in category 'events-listening') -----
- ----- Method: HandMorph>>removeMouseListener: (in category 'listeners') -----
  removeMouseListener: anObject
  	"Remove anObject from the current mouse listeners."
  	self mouseListeners: (self removeListener: anObject from: self mouseListeners).!

Item was changed:
  ----- Method: HandMorph>>sendEvent:focus:clear: (in category 'private events') -----
  sendEvent: anEvent focus: focusHolder clear: aBlock
  	"Send the event to the morph currently holding the focus, or if none to the owner of the hand."
  	| result |
  	focusHolder ifNotNil:[^self sendFocusEvent: anEvent to: focusHolder clear: aBlock].
  	ActiveEvent := anEvent.
+ 	[result := owner processEvent: anEvent]
+ 		ensure: [ActiveEvent := nil].
+ 	^ result == #rejected ifTrue: [anEvent] ifFalse: [result "filtered event"]!
- 	result := owner processEvent: anEvent.
- 	ActiveEvent := nil.
- 	^result!

Item was added:
+ ----- Method: HandMorph>>sendFilterEventCaptureAgain:for: (in category 'events-processing') -----
+ sendFilterEventCaptureAgain: anEvent for: anObjectOrNil
+ 	"Apply keyboard-specific and mouse-specific capturing filters. If a filter changes the event type, filter again. WARNING: This is a powerful mechanism. Filters can create endless loops, which are difficult to debug.
+ 	
+ 	Overwritten to provide keyboard and mouse focus holders to event filters. Note that hence the event target in such global filters can be nil."
+ 
+ 	| filteredEvent |
+ 	filteredEvent := anEvent.
+ 	
+ 	filteredEvent isKeyboard ifTrue: [
+ 		filteredEvent := self sendFilterEvent: filteredEvent for: self keyboardFocus to: self keyboardCaptureFilters.
+ 		filteredEvent isKeyboard not ifTrue: [^ self sendFilterEventCaptureAgain: filteredEvent for: anObjectOrNil]].
+ 		
+ 	filteredEvent isMouse ifTrue: [
+ 		filteredEvent := self sendFilterEvent: filteredEvent for: self mouseFocus to: self mouseCaptureFilters.
+ 		filteredEvent isMouse not ifTrue: [^ self sendFilterEventCaptureAgain: filteredEvent for: anObjectOrNil]].
+ 
+ 	^ filteredEvent!

Item was changed:
  ----- Method: HandMorph>>sendFocusEvent:to:clear: (in category 'private events') -----
  sendFocusEvent: anEvent to: focusHolder clear: aBlock
  	"Send the event to the morph currently holding the focus"
  	| result w |
+ 	w := focusHolder world ifNil:[aBlock value. ^ anEvent].
- 	w := focusHolder world ifNil:[^ aBlock value].
  	w becomeActiveDuring:[
  		ActiveHand := self.
  		ActiveEvent := anEvent.
  		result := focusHolder handleFocusEvent: 
  			(anEvent transformedBy: (focusHolder transformedFrom: self)).
  	].
+ 	^result == #rejected ifTrue: [anEvent] ifFalse: [result "filtered event"]!
- 	^result!

Item was added:
+ ----- Method: HandMorph>>sendListenEvents: (in category 'private events') -----
+ sendListenEvents: anEvent
+ 	"Send the given event to all registered event listeners."
+ 	
+ 	self sendListenEvent: anEvent to: self eventListeners.
+ 	
+ 	anEvent isKeyboard
+ 		ifTrue: [self sendListenEvent: anEvent to: self keyboardListeners].
+ 		
+ 	anEvent isMouse
+ 		ifTrue: [self sendListenEvent: anEvent to: self mouseListeners].!

Item was added:
+ ----- Method: HandMorph>>showEvent: (in category 'events-debugging') -----
+ showEvent: anEvent
+ 	"Show details about the event on the display form. Useful for debugging."
+ 	
+ 	| ofs |
+ 	ShowEvents == true ifFalse: [^ self].
+ 	
+ 	Display fill: (0 at 0 extent: 300 at 120) rule: Form over fillColor: Color white.
+ 	ofs := (owner hands indexOf: self) - 1 * 60.
+ 
+ 	anEvent isKeyboard
+ 		ifTrue: [ 'key: ', anEvent printString displayAt: (0 at ofs) + (0 at 30) ]
+ 		ifFalse: [ 'evt ', anEvent printString displayAt: (0 at ofs) + (0 at 0) ].
+ 
+ 	'kf:  ', self keyboardFocus printString displayAt: (0 at ofs)+(0 at 45).
+ 	'mf: ', self mouseFocus printString displayAt: (0 at ofs) + (0 at 15)
+ !

Item was removed:
- ----- Method: KeyboardEvent>>setType:buttons:position:keyValue:charCode:hand:stamp: (in category 'private') -----
- setType: aSymbol buttons: anInteger position: pos keyValue: aValue charCode: ignoredUsedInOBTesting hand: aHand stamp: stamp
- 	self setType: aSymbol buttons: anInteger position: pos keyValue: aValue hand: aHand stamp: stamp!

Item was changed:
  ----- Method: MenuMorph>>handleFocusEvent: (in category 'events') -----
  handleFocusEvent: evt
  	"Handle focus events. Valid menu transitions are determined based on the menu currently holding the focus after the mouse went down on one of its children."
+ 	| result filteredEvent |
+ 	result := self processEvent: evt.
+ 	filteredEvent := result == #rejected ifTrue: [evt] ifFalse: [result].
- 	self processEvent: evt.
  
  	"Need to handle keyboard input if we have the focus."
+ 	filteredEvent isKeyboard ifTrue: [^ super handleFocusEvent: filteredEvent].
- 	evt isKeyboard ifTrue: [^ self handleEvent: evt].
  
  	"We need to handle button clicks outside and transitions to local popUps so throw away everything else"
+ 	(filteredEvent isMouseOver or:[filteredEvent isMouse not]) ifTrue:[^filteredEvent].
- 	(evt isMouseOver or:[evt isMouse not]) ifTrue:[^self].
  	"What remains are mouse buttons and moves"
+ 	filteredEvent isMove ifFalse:[^super handleFocusEvent: filteredEvent]. "handle clicks outside by regular means"
- 	evt isMove ifFalse:[^self handleEvent: evt]. "handle clicks outside by regular means"
  	"Now it's getting tricky. On #mouseMove we might transfer control to *either* the currently active submenu or the pop up owner, if any. Since the active sub menu is always displayed upfront check it first."	
  	selectedItem ifNotNil: [
+ 		(selectedItem activateSubmenu: filteredEvent) 
+ 			ifTrue: [ ^filteredEvent ]
- 		(selectedItem activateSubmenu: evt) 
- 			ifTrue: [ ^self ]
  			ifFalse: [ 
+ 				(self containsPoint: filteredEvent position) ifFalse: [ 
+ 					self selectItem: nil event: filteredEvent ] ] ].
- 				(self containsPoint: evt position) ifFalse: [ 
- 					self selectItem: nil event: evt ] ] ].
  	"Note: The following does not traverse upwards but it's the best I can do for now"
+ 	popUpOwner ifNotNil:[(popUpOwner activateOwnerMenu: filteredEvent) ifTrue:[^filteredEvent]].
+ 	^ filteredEvent!
- 	popUpOwner ifNotNil:[(popUpOwner activateOwnerMenu: evt) ifTrue:[^self]].!

Item was added:
+ ----- Method: Morph>>addEventBubbleFilter: (in category 'events-filtering-bubbling') -----
+ addEventBubbleFilter: anObject
+ 	self eventBubbleFilters: (self addFilter: anObject to: self eventBubbleFilters).!

Item was added:
+ ----- Method: Morph>>addEventCaptureFilter: (in category 'events-filtering-capturing') -----
+ addEventCaptureFilter: anObject
+ 	self eventCaptureFilters: (self addFilter: anObject to: self eventCaptureFilters).!

Item was added:
+ ----- Method: Morph>>addFilter:to: (in category 'events-filtering') -----
+ addFilter: anObject to: aFilterGroup
+ 	"Add anObject to the given listener group. Return the new group."
+ 	| filters |
+ 	filters := aFilterGroup.
+ 	(filters notNil and:[filters includes: anObject]) ifFalse:[
+ 		filters
+ 			ifNil:[filters := WeakArray with: anObject]
+ 			ifNotNil:[filters := filters copyWith: anObject]].
+ 	filters := filters copyWithout: nil. "obsolete entries"
+ 	^filters!

Item was added:
+ ----- Method: Morph>>addKeyboardBubbleFilter: (in category 'events-filtering-bubbling') -----
+ addKeyboardBubbleFilter: anObject
+ 	self keyboardBubbleFilters: (self addFilter: anObject to: self keyboardBubbleFilters).!

Item was added:
+ ----- Method: Morph>>addKeyboardCaptureFilter: (in category 'events-filtering-capturing') -----
+ addKeyboardCaptureFilter: anObject
+ 	self keyboardCaptureFilters: (self addFilter: anObject to: self keyboardCaptureFilters).!

Item was added:
+ ----- Method: Morph>>addMouseBubbleFilter: (in category 'events-filtering-bubbling') -----
+ addMouseBubbleFilter: anObject
+ 	self mouseBubbleFilters: (self addFilter: anObject to: self mouseBubbleFilters).!

Item was added:
+ ----- Method: Morph>>addMouseCaptureFilter: (in category 'events-filtering-capturing') -----
+ addMouseCaptureFilter: anObject
+ 	self mouseCaptureFilters: (self addFilter: anObject to: self mouseCaptureFilters).!

Item was added:
+ ----- Method: Morph>>eventBubbleFilters (in category 'events-filtering-bubbling') -----
+ eventBubbleFilters
+ 	^ self valueOfProperty: #eventBubbleFilters!

Item was added:
+ ----- Method: Morph>>eventBubbleFilters: (in category 'events-filtering-bubbling') -----
+ eventBubbleFilters: anArrayOrNil
+ 	^ self setProperty: #eventBubbleFilters toValue: anArrayOrNil!

Item was added:
+ ----- Method: Morph>>eventCaptureFilters (in category 'events-filtering-capturing') -----
+ eventCaptureFilters
+ 	^ self valueOfProperty: #eventCaptureFilters!

Item was added:
+ ----- Method: Morph>>eventCaptureFilters: (in category 'events-filtering-capturing') -----
+ eventCaptureFilters: anArrayOrNil
+ 	^ self setProperty: #eventCaptureFilters toValue: anArrayOrNil!

Item was added:
+ ----- Method: Morph>>eventFilterDocumentation (in category 'events-filtering') -----
+ eventFilterDocumentation
+ 	"
+ 	Event filters represent a mechanism to intercept events *before* morphs get the chance to handle them. So, there are still event handlers, which are usually the morphs themselves. However, morphs can also be their own event filters. One application of event filters is keyboard shortcuts. Such filters should invoke the shortcut but ignore the original event to *be sure* that no other morph ever handles that. System windows have window shortcuts. The world has world shortcuts.
+ 	
+ 	When user input events are dispatched, there is a capturing phase and a bubbling phase. This dispatching behavior is described in MorphicEventDispatcher. Capturing means that we are looking for the handler (resp. morph) to handle the event, traversing submorph hierarchy. Bubbling means that once a morph handled the event, all owners get also the chance to handle that event *if* they honor the #wasHandled flag.. Event filters can be attached to any morph for the capturing or the bubbling phase. See it as code that is execute before/after the event handlers.
+ 	
+ 	Event filters are objects that implement #filterEvent:for:. All objects understand that message but do nothing. There is a PluggableEventFilter for a more dynamic programming approach.
+ 	
+ 	Morphic hands have specific focus holders. There is a keyboard focus and a mouse focus. For example, text morphs are good candidates for holders of the keyboard focus. Both foci bypass the traditional event capturing phase, which usually start at the world morph. However, capture filters are also apply before handling the focus event. See Morph >> #handleFocusEvent: for that. Note that after handling the focus event, events do bubble along their owners, which usually do nothing if they honor the #wasHandled flag, and hence all bubble event filters are executed unless events get ignored. Thus, we mimick the behavior of MorphicEventDispatcher in #handleFocusEvent:.
+ 	
+ 	There are event filters for all kinds of events, filters for keyboard events, and filters for mouse events. You can always install generic event filters and then check for the particular event type in that filter. However, it is good style to not install keyboard event filters as generic event filters. It makes code more readable.
+ 	
+ 	You can install global event capture filters in instances of HandMorph. For example,  Project current world firstHand provides access to the project's world's hand. Avoid using globals such as ActiveHand or ActiveWorld. BEWARE that global event filters can have unexpected effects and may be difficult to debug. Note that you cannot install global event bubble filters in the HandMorph. You have to install such a filter in the world because hands are not part of the event bubbling phase.
+ 	
+ 	For an example of keyboard capturing filters see SystemWindow >> #addKeyboardShortcuts and SystemWindow >> #filterEvent:for:. You can also take a look at: PasteUpMorph >> #addKeyboardShortcuts and PasteUpMorph >> #filterEvent:for: and DockingBarMorph >> #filterEvent:for: for a more elaborate example.
+ 	
+ 	Event filters include all the behavior of event listeners. An event listener converted to an event filter would be a global event capture filter that sents a copy of the event to itself:
+ 	
+ 	| listenerFilter someMorph |
+ 	someMorph := Morph new.
+ 	listenerFilter := PluggableEventFilter on: [:event :target | event copy sentTo: someMorph. event].
+ 	Project current world activeHand addEventCaptureFilter: listenerFilter.
+ 	
+ 	Instead of:
+ 
+ 	| someMorph |
+ 	someMorph := Morph new.
+ 	Project current world activeHand addEventListener: someMorph.
+ 	
+ 	The filter version might look more complicated than the traditional listener version but note that it is quite rare to install global event filters. The example for keyboard shortcuts reflects the simplicity of event filters."!

Item was changed:
  ----- Method: Morph>>handleEvent: (in category 'events-processing') -----
  handleEvent: anEvent
+ 	"Apply event filters and then handle the resulting event. We have to return the event to chain filters."
+ 
+ 	| filteredEvent |
+ 	filteredEvent := self sendFilterEventBubble: anEvent for: self.
+ 	filteredEvent wasIgnored ifFalse: [filteredEvent sentTo: self].
+ 	^ filteredEvent!
- 	"Handle the given event"
- 	^anEvent sentTo: self.!

Item was changed:
  ----- Method: Morph>>handleFocusEvent: (in category 'events-processing') -----
  handleFocusEvent: anEvent
+ 	"Handle the given event. This message is sent if the receiver currently has the focus and is therefore receiving events directly from some hand.
+ 	
+ 	1) Event bubbling. Do event bubbling known from MorphicEventDispatcher by calling #handleEvent: also on all owners.
+ 	2) Event capture filters. Walk along the owner chain in reverse order and apply capture filters as known from MorphicEventDispatcher.
+ 	
+ 	If you want to overwrite this in a subclass (for example to implement modal dialogs) ensure to call super instead if #handleEvent: directly."
+ 
+ 	| filteredEvent |
+ 	filteredEvent := anEvent.
+ 	
+ 	"TODO: Add a check to ensure that our event dispatcher is actually of kind MorphicEventDispatcher?!! We do copy its behavior though... like self defaultEventDispatcher class == MorphicEventDispatcher? Or #isKindOf:? Anyway, the outermost morph determines the event dispatcher. See HandMorph >> #sendEvent:focus:clear: and PasteUpMorph >> #processEvent:."
+ 
+ 	"Event capturing. Filters only because the capturing phase was bypassed by using the keyboard/mouse focus."
+ 	self withAllOwners reverseDo: [:morph | "reverse order to comply with default MorphEventDispatcher"
+ 			filteredEvent := morph sendFilterEventCapture: filteredEvent for: morph.
+ 			filteredEvent wasIgnored ifTrue: [^ filteredEvent]].
+ 
+ 	"Event bubbling. Filters are processed in #handleEvent:."
+ 	self withAllOwnersDo: [:morph |
+ 		filteredEvent := morph handleEvent: filteredEvent.
+ 		filteredEvent wasIgnored ifTrue: [^ filteredEvent]].
+ 
+ 	^ filteredEvent!
- 	"Handle the given event. This message is sent if the receiver currently has the focus and is therefore receiving events directly from some hand."
- 	^self handleEvent: anEvent!

Item was added:
+ ----- Method: Morph>>keyboardBubbleFilters (in category 'events-filtering-bubbling') -----
+ keyboardBubbleFilters
+ 	^ self valueOfProperty: #keyboardBubbleFilters!

Item was added:
+ ----- Method: Morph>>keyboardBubbleFilters: (in category 'events-filtering-bubbling') -----
+ keyboardBubbleFilters: anArrayOrNil
+ 	^ self setProperty: #keyboardBubbleFilters toValue: anArrayOrNil!

Item was added:
+ ----- Method: Morph>>keyboardCaptureFilters (in category 'events-filtering-capturing') -----
+ keyboardCaptureFilters
+ 	^ self valueOfProperty: #keyboardCaptureFilters!

Item was added:
+ ----- Method: Morph>>keyboardCaptureFilters: (in category 'events-filtering-capturing') -----
+ keyboardCaptureFilters: anArrayOrNil
+ 	^ self setProperty: #keyboardCaptureFilters toValue: anArrayOrNil!

Item was added:
+ ----- Method: Morph>>mouseBubbleFilters (in category 'events-filtering-bubbling') -----
+ mouseBubbleFilters
+ 	^ self valueOfProperty: #mouseBubbleFilters!

Item was added:
+ ----- Method: Morph>>mouseBubbleFilters: (in category 'events-filtering-bubbling') -----
+ mouseBubbleFilters: anArrayOrNil
+ 	^ self setProperty: #mouseBubbleFilters toValue: anArrayOrNil!

Item was added:
+ ----- Method: Morph>>mouseCaptureFilters (in category 'events-filtering-capturing') -----
+ mouseCaptureFilters
+ 	^ self valueOfProperty: #mouseCaptureFilters!

Item was added:
+ ----- Method: Morph>>mouseCaptureFilters: (in category 'events-filtering-capturing') -----
+ mouseCaptureFilters: anArrayOrNil
+ 	^ self setProperty: #mouseCaptureFilters toValue: anArrayOrNil!

Item was changed:
  ----- Method: Morph>>processEvent:using: (in category 'events-processing') -----
  processEvent: anEvent using: defaultDispatcher
  	"This is the central entry for dispatching events in morphic. Given some event and a default dispatch strategy, find the right receiver and let him handle it.
+ 	WARNING: This is a powerful hook. If you want to use a different event dispatcher from the default, here is the place to hook it in. Depending on how the dispatcher is written (e.g., whether it calls simply #processEvent: or #processEvent:using:) you can change the dispatch strategy for entire trees of morphs. Similarly, you can disable entire trees of morphs from receiving any events whatsoever. Read the documentation in class MorphicEventDispatcher before playing with it.
+ 	Event filters for this capture phase can both influence and overrule the way the receiver can reject the event. If the filter ignores the event, the whole event procecssing will stop. If the filtered event is still not ignored, the receiver can decide to still reject it end regular event dispatch will go on."
+ 	
+ 	| filteredEvent |
+ 	filteredEvent := self sendFilterEventCapture: anEvent for: self.
+ 	filteredEvent wasIgnored ifTrue: [^ filteredEvent].
+ 	
+ 	(self rejectsEvent: filteredEvent) ifTrue:[^#rejected].
+ 	^defaultDispatcher dispatchEvent: filteredEvent with: self!
- 	WARNING: This is a powerful hook. If you want to use a different event dispatcher from the default, here is the place to hook it in. Depending on how the dispatcher is written (e.g., whether it calls simply #processEvent: or #processEvent:using:) you can change the dispatch strategy for entire trees of morphs. Similarly, you can disable entire trees of morphs from receiving any events whatsoever. Read the documentation in class MorphicEventDispatcher before playing with it. "
- 	(self rejectsEvent: anEvent) ifTrue:[^#rejected].
- 	^defaultDispatcher dispatchEvent: anEvent with: self!

Item was added:
+ ----- Method: Morph>>removeEventBubbleFilter: (in category 'events-filtering-bubbling') -----
+ removeEventBubbleFilter: anObject
+ 	self eventBubbleFilters: (self removeFilter: anObject from: self eventBubbleFilters).!

Item was added:
+ ----- Method: Morph>>removeEventCaptureFilter: (in category 'events-filtering-capturing') -----
+ removeEventCaptureFilter: anObject
+ 	self eventCaptureFilters: (self removeFilter: anObject from: self eventCaptureFilters).!

Item was added:
+ ----- Method: Morph>>removeFilter:from: (in category 'events-filtering') -----
+ removeFilter: anObject from: aFilterGroup 
+ 	"Remove anObject from the given listener group. Return the new group."
+ 
+ 	| filters |
+ 	aFilterGroup ifNil: [^nil].
+ 	filters := aFilterGroup.
+ 	filters := filters copyWithout: anObject.
+ 	filters := filters copyWithout: nil.	"obsolete entries"
+ 	filters isEmpty ifTrue: [filters := nil].
+ 	^filters!

Item was added:
+ ----- Method: Morph>>removeKeyboardBubbleFilter: (in category 'events-filtering-bubbling') -----
+ removeKeyboardBubbleFilter: anObject
+ 	self keyboardBubbleFilters: (self removeFilter: anObject from: self keyboardBubbleFilters).!

Item was added:
+ ----- Method: Morph>>removeKeyboardCaptureFilter: (in category 'events-filtering-capturing') -----
+ removeKeyboardCaptureFilter: anObject
+ 	self keyboardCaptureFilters: (self removeFilter: anObject from: self keyboardCaptureFilters).!

Item was added:
+ ----- Method: Morph>>removeMouseBubbleFilter: (in category 'events-filtering-bubbling') -----
+ removeMouseBubbleFilter: anObject
+ 	self mouseBubbleFilters: (self removeFilter: anObject from: self mouseBubbleFilters).!

Item was added:
+ ----- Method: Morph>>removeMouseCaptureFilter: (in category 'events-filtering-capturing') -----
+ removeMouseCaptureFilter: anObject
+ 	self mouseCaptureFilters: (self removeFilter: anObject from: self mouseCaptureFilters).!

Item was added:
+ ----- Method: Morph>>sendFilterEvent:for:to: (in category 'events-processing') -----
+ sendFilterEvent: anEvent for: anObject to: filterGroup
+ 	"An event gets filtered if some event filter wants to filter it."
+ 	
+ 	| filteredEvent |
+ 	filterGroup ifNil: [^anEvent].
+ 
+ 	filteredEvent := anEvent.
+ 	filterGroup do: [:filterOrNil | filterOrNil ifNotNil: [:filter |
+ 		filteredEvent := filter filterEvent: filteredEvent for: anObject]].
+ 	
+ 	^ filteredEvent!

Item was added:
+ ----- Method: Morph>>sendFilterEventBubble:for: (in category 'events-processing') -----
+ sendFilterEventBubble: anEvent for: anObject
+ 	"Apply event bubbling filters."
+ 
+ 	^ self
+ 		sendFilterEventBubbleAgain: (self sendFilterEvent: anEvent for: anObject to: self eventBubbleFilters)
+ 		for: anObject!

Item was added:
+ ----- Method: Morph>>sendFilterEventBubbleAgain:for: (in category 'events-processing') -----
+ sendFilterEventBubbleAgain: anEvent for: anObject
+ 	"Apply keyboard-specific and mouse-specific bubbling filters. If a filter changes the event type, filter again. WARNING: This is a powerful mechanism. Filters can create endless loops, which are difficult to debug."
+ 
+ 	| filteredEvent |
+ 	filteredEvent := anEvent.
+ 	
+ 	filteredEvent isKeyboard ifTrue: [
+ 		filteredEvent := self sendFilterEvent: filteredEvent for: anObject to: self keyboardBubbleFilters.
+ 		filteredEvent isKeyboard not ifTrue: [^ self sendFilterEventBubbleAgain: filteredEvent for: anObject]].
+ 		
+ 	filteredEvent isMouse ifTrue: [
+ 		filteredEvent := self sendFilterEvent: filteredEvent for: anObject to: self mouseBubbleFilters.
+ 		filteredEvent isMouse not ifTrue: [^ self sendFilterEventBubbleAgain: filteredEvent for: anObject]].
+ 
+ 	^ filteredEvent!

Item was added:
+ ----- Method: Morph>>sendFilterEventCapture:for: (in category 'events-processing') -----
+ sendFilterEventCapture: anEvent for: anObject
+ 	"Apply event capturing filters."
+ 
+ 	^ self
+ 		sendFilterEventCaptureAgain: (self sendFilterEvent: anEvent for: anObject to: self eventCaptureFilters)
+ 		for: anObject!

Item was added:
+ ----- Method: Morph>>sendFilterEventCaptureAgain:for: (in category 'events-processing') -----
+ sendFilterEventCaptureAgain: anEvent for: anObject
+ 	"Apply keyboard-specific and mouse-specific capturing filters. If a filter changes the event type, filter again. WARNING: This is a powerful mechanism. Filters can create endless loops, which are difficult to debug."
+ 
+ 	| filteredEvent |
+ 	filteredEvent := anEvent.
+ 	
+ 	filteredEvent isKeyboard ifTrue: [
+ 		filteredEvent := self sendFilterEvent: filteredEvent for: anObject to: self keyboardCaptureFilters.
+ 		filteredEvent isKeyboard not ifTrue: [^ self sendFilterEventCaptureAgain: filteredEvent for: anObject]].
+ 		
+ 	filteredEvent isMouse ifTrue: [
+ 		filteredEvent := self sendFilterEvent: filteredEvent for: anObject to: self mouseCaptureFilters.
+ 		filteredEvent isMouse not ifTrue: [^ self sendFilterEventCaptureAgain: filteredEvent for: anObject]].
+ 
+ 	^ filteredEvent!

Item was added:
+ ----- Method: MorphicEvent>>ignore (in category 'dispatching') -----
+ ignore
+ 
+ 	self wasIgnored: true.!

Item was added:
+ ----- Method: MorphicEvent>>translateTo: (in category 'transforming') -----
+ translateTo: point
+ !

Item was added:
+ ----- Method: MorphicEvent>>wasIgnored (in category 'accessing') -----
+ wasIgnored
+ 	^ false!

Item was added:
+ ----- Method: MorphicEvent>>wasIgnored: (in category 'accessing') -----
+ wasIgnored: boolean
+ !

Item was changed:
+ ----- Method: MorphicEventDispatcher>>dispatchDefault:with: (in category 'specific') -----
- ----- Method: MorphicEventDispatcher>>dispatchDefault:with: (in category 'dispatching') -----
  dispatchDefault: anEvent with: aMorph
  	"Dispatch the given event. The event will be passed to the front-most visible submorph that contains the position wrt. to the event."
- 	| localEvt index child morphs inside |
- 	"See if we're fully outside aMorphs bounds"
- 	(aMorph fullBounds containsPoint: anEvent position) ifFalse:[^#rejected]. "outside"
- 	"Traverse children"
- 	index := 1.
- 	morphs := aMorph submorphs.
- 	inside := false.
- 	[index <= morphs size] whileTrue:[
- 		child := morphs at: index.
- 		localEvt := anEvent transformedBy: (child transformedFrom: aMorph).
- 		(child processEvent: localEvt using: self) == #rejected ifFalse:[
- 			"Not rejected. The event was in some submorph of the receiver"
- 			inside := true.
- 			localEvt wasHandled ifTrue:[anEvent copyHandlerState: localEvt].
- 			index := morphs size. "break"
- 		].
- 		index := index + 1.
- 	].
  
+ 	"Try to get out quickly"
+ 	anEvent wasIgnored ifTrue: [^anEvent "propagate the ignored event"].
+ 	(aMorph fullBounds containsPoint: anEvent position) ifFalse:[^#rejected].
+ 
+ 	^ self
+ 		dispatchEvent: anEvent
+ 		withHandler: aMorph
+ 		withMorph: aMorph!
- 	"Check for being inside the receiver"
- 	inside ifFalse:[inside := aMorph containsPoint: anEvent position event: anEvent].
- 	inside ifTrue:[^aMorph handleEvent: anEvent].
- 	^#rejected
- !

Item was changed:
+ ----- Method: MorphicEventDispatcher>>dispatchDropEvent:with: (in category 'specific') -----
- ----- Method: MorphicEventDispatcher>>dispatchDropEvent:with: (in category 'dispatching') -----
  dispatchDropEvent: anEvent with: aMorph
  	"Find the appropriate receiver for the event and let it handle it. The dispatch is similar to the default dispatch with one difference: Morphs are given the chance to reject an entire drop operation. If the operation is rejected, no drop will be executed."
+ 
- 	| inside index morphs child localEvt |
  	"Try to get out quickly"
+ 	anEvent wasIgnored ifTrue: [^anEvent "propagate the ignored event"].
+ 	(aMorph fullBounds containsPoint: anEvent position) ifFalse:[^#rejected].
+ 
- 	(aMorph fullBounds containsPoint: anEvent cursorPoint)
- 		ifFalse:[^#rejected].
  	"Give aMorph a chance to repel the dropping morph"
  	aMorph rejectDropEvent: anEvent.
+ 	anEvent wasHandled ifTrue:[^anEvent].
- 	anEvent wasHandled ifTrue:[^self].
  
+ 	^ self
+ 		dispatchEvent: anEvent
+ 		withHandler: aMorph
+ 		withMorph: aMorph!
- 	"Go looking if any of our submorphs wants it"
- 	index := 1.
- 	inside := false.
- 	morphs := aMorph submorphs.
- 	[index <= morphs size] whileTrue:[
- 		child := morphs at: index.
- 		localEvt := anEvent transformedBy: (child transformedFrom: aMorph).
- 		(child processEvent: localEvt using: self) == #rejected ifFalse:[
- 			localEvt wasHandled ifTrue:[^anEvent wasHandled: true]. "done"
- 			inside := true.
- 			index := morphs size]. "break"
- 		index := index + 1.
- 	].
- 
- 	inside ifFalse:[inside := aMorph containsPoint: anEvent cursorPoint event: anEvent].
- 	inside ifTrue:[^aMorph handleEvent: anEvent].
- 	^#rejected!

Item was added:
+ ----- Method: MorphicEventDispatcher>>dispatchEvent:toSubmorphsOf: (in category 'private') -----
+ dispatchEvent: anEvent toSubmorphsOf: aMorph
+ 	"Dispatch the given event to the submorphs of the given morph. --- PRIVATE!!"
+ 
+ 	| filteredEvent |	
+ 	aMorph submorphsDo: [:child |
+ 		filteredEvent := child
+ 			processEvent: (anEvent transformedBy: (child transformedFrom: aMorph))
+ 			using: self. "use same dispatcher"
+ 		filteredEvent == #rejected ifFalse: [ "filteredEvent or #rejected"
+ 			filteredEvent translateTo: anEvent position. "restore to untransformed coordinates"
+ 			filteredEvent wasHandled ifFalse: [filteredEvent copyHandlerState: anEvent]. "restore handler if needed"
+ 			self flag: #overlappingChildren. "mt: We cannot give two overlapping siblings the chance to handle the event!!"
+ 			^ filteredEvent]].
+ 
+ 	^ #rejected!

Item was added:
+ ----- Method: MorphicEventDispatcher>>dispatchEvent:withHandler:withMorph: (in category 'private') -----
+ dispatchEvent: anEvent withHandler: aHandler withMorph: aMorph
+ 	"Perform the actual event dispatch. Use the given object as handler. Ask submorphs first to handle the event. Then bubble up. Stop if ignored. Note that event rejection and event filters are two separete concepts. Filters come from the outside. Rejection is a morph's decision.
+ 	
+ 	* The top-most chain of visible, unlocked morphs containing the event position will get a chance to handle the event.
+ 	* When travelling up, the prospective handler is always executed. The handler needs to check if the event was handled before as well as checking if somebody else's handler has been installed.
+ 	* If another handler has been installed but the event was not handled it means that somebody up in the hierarchy wants to handle the event."
+ 	
+ 	| result filteredEvent |
+ 	
+ 	result := self dispatchEvent: anEvent toSubmorphsOf: aMorph.
+ 
+ 	result == #rejected "Anybody?"
+ 		ifFalse: [filteredEvent := result]
+ 		ifTrue: [
+ 			"My submorphs did not want it. Do I want it anyway? It's about locked children..."
+ 			(aMorph containsPoint: anEvent position event: anEvent)
+ 				ifFalse: [^ #rejected].
+ 			filteredEvent := anEvent "there was no filtering, only basic rejects"].
+ 	
+ 	"Receiver is in the top-most unlocked, visible chain."
+ 	(aHandler notNil and: [filteredEvent wasIgnored not])
+ 		ifTrue: [filteredEvent := aHandler handleEvent: filteredEvent].
+ 
+ 	^ filteredEvent!

Item was changed:
+ ----- Method: MorphicEventDispatcher>>dispatchMouseDown:with: (in category 'specific') -----
- ----- Method: MorphicEventDispatcher>>dispatchMouseDown:with: (in category 'dispatching') -----
  dispatchMouseDown: anEvent with: aMorph
+ 	"Find the appropriate receiver for the event and let it handle it. When travelling down the hierarchy a prospective handler for the event is installed. This prospective handler can be used by submorphs wishing to handle the mouse down for negotiating who the receiver is."
+ 	
+ 	| handler lastHandler |
+ 	
- 	"Find the appropriate receiver for the event and let it handle it. Default rules:
- 	* The top-most chain of visible, unlocked morphs containing the event position will get a chance to handle the event.
- 	* When travelling down the hierarchy a prospective handler for the event is installed. This prospective handler can be used by submorphs wishing to handle the mouse down for negotiating who the receiver is.
- 	* When travelling up, the prospective handler is always executed. The handler needs to check if the event was handled before as well as checking if somebody else's handler has been installed.
- 	* If another handler has been installed but the event was not handled it means that somebody up in the hierarchy wants to handle the event.
- "
- 	| globalPt localEvt index child morphs handler inside lastHandler |
  	"Try to get out quickly"
+ 	anEvent wasIgnored ifTrue: [^anEvent "propagate the ignored event"].
+ 	(aMorph fullBounds containsPoint: anEvent position) ifFalse:[^#rejected].
- 	globalPt := anEvent cursorPoint.
- 	(aMorph fullBounds containsPoint: globalPt) ifFalse:[^#rejected].
  
+ 	"In case the mouse wasn't even in the receiver"
+ 	lastHandler := anEvent handler. 
+ 
+ 	"Negotiate and install the actual handler."
- 	"Install the prospective handler for the receiver"
- 	lastHandler := anEvent handler. "in case the mouse wasn't even in the receiver"
  	handler := aMorph handlerForMouseDown: anEvent.
+ 	handler ifNotNil: [anEvent handler: handler].
- 	handler ifNotNil:[anEvent handler: handler].
  
+ 	[^ self
+ 		dispatchEvent: anEvent
+ 		withHandler: handler
+ 		withMorph: aMorph
+ 	] ensure: [
+ 		anEvent handler: lastHandler. "good style"].!
- 	"Now give our submorphs a chance to handle the event"
- 	index := 1.
- 	morphs := aMorph submorphs.
- 	[index <= morphs size] whileTrue:[
- 		child := morphs at: index.
- 		localEvt := anEvent transformedBy: (child transformedFrom: aMorph).
- 		(child processEvent: localEvt using: self) == #rejected ifFalse:[
- 			"Some child did contain the point so we're part of the top-most chain."
- 			inside := false.
- 			localEvt wasHandled ifTrue:[anEvent copyHandlerState: localEvt].
- 			index := morphs size].
- 		index := index + 1.
- 	].
- 
- 	(inside == false or:[aMorph containsPoint: anEvent cursorPoint event: anEvent]) ifTrue:[
- 		"Receiver is in the top-most unlocked, visible chain."
- 		handler ifNotNil:[handler handleEvent: anEvent].
- 		"Note: Re-installing the handler is not really necessary but good style."
- 		anEvent handler: lastHandler.
- 		^self
- 	].
- 	"Mouse was not on receiver nor any of its children"
- 	anEvent handler: lastHandler.
- 	^#rejected!

Item was changed:
+ ----- Method: MorphicEventDispatcher>>dispatchWindowEvent:with: (in category 'specific') -----
- ----- Method: MorphicEventDispatcher>>dispatchWindowEvent:with: (in category 'dispatching') -----
  dispatchWindowEvent: anEvent with: aMorph
  	"Host window events do not have a position and are only dispatched to the World"
+ 
+ 	anEvent wasIgnored ifTrue: [^anEvent].
  	aMorph isWorldMorph ifFalse: [^#rejected].
+ 	anEvent wasHandled ifTrue:[^anEvent].
- 	anEvent wasHandled ifTrue:[^self].
  	^aMorph handleEvent: anEvent!

Item was added:
+ ----- Method: Object>>filterEvent:for: (in category '*Morphic-Events-Filtering') -----
+ filterEvent: anEvent for: aMorphOrNil
+ 	"Get the chance to intercept the event. Note that global event filters might not be provided with the actual target. Returns the event that should be processed any further. If you want to ignore them, call #ignore on them."
+ 	
+ 	^ anEvent "no change"!

Item was changed:
  ----- Method: PasteUpMorph>>processEvent:using: (in category 'events-processing') -----
  processEvent: anEvent using: defaultDispatcher
  	"Reimplemented to install the receiver as the new ActiveWorld if it is one"
  	| priorWorld result |
  	self isWorldMorph ifFalse:[^super processEvent: anEvent using: defaultDispatcher].
  	priorWorld := ActiveWorld.
  	ActiveWorld := self.
+ 	[result := super processEvent: anEvent using: defaultDispatcher]
+ 		ensure: [ActiveWorld := priorWorld].
+ 	^result
+ !
- 	result := super processEvent: anEvent using: defaultDispatcher.
- 	ActiveWorld := priorWorld.
- 	^result!

Item was added:
+ Object subclass: #PluggableEventFilter
+ 	instanceVariableNames: 'filterBlock'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Morphic-Events'!

Item was added:
+ ----- Method: PluggableEventFilter class>>on: (in category 'instance creation') -----
+ on: filterBlock
+ 
+ 	^ self new filterBlock: filterBlock!

Item was added:
+ ----- Method: PluggableEventFilter>>filterBlock (in category 'accessing') -----
+ filterBlock
+ 
+ 	^ filterBlock!

Item was added:
+ ----- Method: PluggableEventFilter>>filterBlock: (in category 'accessing') -----
+ filterBlock: anObject
+ 
+ 	filterBlock := anObject!

Item was added:
+ ----- Method: PluggableEventFilter>>filterEvent:for: (in category 'events-filtering') -----
+ filterEvent: event for: target
+ 
+ 	^ self filterBlock
+ 		ifNil: [event]
+ 		ifNotNil: [:b | b cull: event cull: target]!

Item was changed:
  ----- Method: UserDialogBoxMorph>>handleFocusEvent: (in category 'constructing') -----
  handleFocusEvent: evt
+ 	"Handle focus events. Valid menu transitions are determined based on the menu currently holding the focus after the mouse went down on one of its children. Need to handle keyboard input if we have the focus."
- 	"Handle focus events. Valid menu transitions are determined based on the menu currently holding the focus after the mouse went down on one of its children."
- 	self processEvent: evt.
  
+ 	| result filteredEvent |
+ 	result := self processEvent: evt.
+ 	filteredEvent := result == #rejected ifTrue: [evt] ifFalse: [result].
+ 
+ 	^ super handleFocusEvent: filteredEvent!
- 	"Need to handle keyboard input if we have the focus."
- 	^self handleEvent: evt!

Item was changed:
  MorphicEvent subclass: #UserInputEvent
+ 	instanceVariableNames: 'type buttons position handler wasHandled wasIgnored'
- 	instanceVariableNames: 'type buttons position handler wasHandled'
  	classVariableNames: ''
  	poolDictionaries: 'EventSensorConstants'
  	category: 'Morphic-Events'!

Item was added:
+ ----- Method: UserInputEvent>>initialize (in category 'initialize') -----
+ initialize
+ 
+ 	super initialize.
+ 	wasIgnored := false.!

Item was added:
+ ----- Method: UserInputEvent>>translateTo: (in category 'transforming') -----
+ translateTo: point
+ 
+ 	position := point.!

Item was added:
+ ----- Method: UserInputEvent>>wasIgnored (in category 'accessing') -----
+ wasIgnored
+ 	^ wasIgnored!

Item was added:
+ ----- Method: UserInputEvent>>wasIgnored: (in category 'accessing') -----
+ wasIgnored: aBoolean
+ 	wasIgnored := aBoolean.!



More information about the Squeak-dev mailing list