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

commits at source.squeak.org commits at source.squeak.org
Mon Jun 20 15:14:36 UTC 2016


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

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

Name: Morphic-mt.1182
Author: mt
Time: 20 June 2016, 5:13:55.570796 pm
UUID: 825d8e52-1878-af49-9f7a-437b23e68d8c
Ancestors: Morphic-mt.1181

Moves implementation of focus event dispatching from various places into MorphicEventDispatcher. This will ensure consistency in the future because MorphicEventDispatcher encode the tree iteration with capturing and bubbling. Doing a focus event is just a shortcut into the tree. TextMorphs use that. Pop-up menus use that. Modal dialogs use that.

Fixes missing coordinate transformations when capturing and bubbling for focus events.

Simplify focus-related code in MenuMorph, UserDialogBoxMorph, and DockingBarMorph.

At the time of writing, there seems to be no need anymore for Morph >> #handleFocusEvent:. Still, keep it for compatibility to other projects.

=============== Diff against Morphic-mt.1181 ===============

Item was removed:
- ----- 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].
- 
- 	result := self processEvent: evt.
- 	filteredEvent := result == #rejected ifTrue: [evt] ifFalse: [result].
- 
- 	"Need to handle keyboard input if we have the focus."
- 	filteredEvent isKeyboard ifTrue: [^ super handleFocusEvent: filteredEvent].
- 
- 	"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].
- 	"What remains are mouse buttons and moves"
- 	filteredEvent isMove ifFalse:[^super handleFocusEvent: filteredEvent]. "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]].
- !

Item was added:
+ ----- Method: DockingBarMorph>>mouseMove: (in category 'events-processing') -----
+ mouseMove: evt
+ 	"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: evt].!

Item was added:
+ ----- Method: DockingBarMorph>>processFocusEvent:using: (in category 'events-processing') -----
+ processFocusEvent: evt using: dispatcher
+ 
+ 	^ dispatcher dispatchFocusEventFully: evt with: self!

Item was added:
+ ----- Method: DockingBarMorph>>wantsEveryMouseMove (in category 'events-processing') -----
+ wantsEveryMouseMove
+ 	^ true!

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 becomeActiveDuring:[
  		ActiveHand := self.
  		ActiveEvent := anEvent.
+ 		result := focusHolder processFocusEvent: anEvent.
- 		result := focusHolder handleFocusEvent: 
- 			(anEvent transformedBy: (focusHolder transformedFrom: self)).
  	].
+ 	^ result == #rejected ifTrue: [anEvent] ifFalse: [result "filtered event"]!
- 	^result == #rejected ifTrue: [anEvent] ifFalse: [result "filtered event"]!

Item was removed:
- ----- 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].
- 
- 	"Need to handle keyboard input if we have the focus."
- 	filteredEvent isKeyboard ifTrue: [^ super handleFocusEvent: filteredEvent].
- 
- 	"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].
- 	"What remains are mouse buttons and moves"
- 	filteredEvent isMove ifFalse:[^super handleFocusEvent: filteredEvent]. "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 ]
- 			ifFalse: [ 
- 				(self containsPoint: filteredEvent position) ifFalse: [ 
- 					self selectItem: nil event: filteredEvent ] ] ].
- 	"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!

Item was removed:
- ----- Method: MenuMorph>>handleMouseMove: (in category 'events') -----
- handleMouseMove: evt
- 	" If the mouse moves over an item not selected, we try to set it as selected.
- 	If this happens depends on that the current selected item wants to release
- 	its selection. "
- 
- 	self selectedItem ifNil: [ ^super handleMouseMove: evt ].
- 	(self selectedItem containsPoint: evt position) ifTrue: [ ^super handleMouseMove: evt ].
- 	self 
- 		selectItem: (
- 			self items 
- 				detect: [ :each | each containsPoint: evt position ] 
- 				ifNone: [ nil ])
- 		event: evt.
- 	super handleMouseMove: evt!

Item was added:
+ ----- Method: MenuMorph>>mouseMove: (in category 'events') -----
+ mouseMove: evt
+ 	" If the mouse moves over an item not selected, we try to set it as selected.
+ 	If this happens depends on that the current selected item wants to release
+ 	its selection. "
+ 
+ 	self selectedItem ifNil: [ ^ self ].
+ 	(self selectedItem containsPoint: evt position) ifTrue: [ ^ self ].
+ 	self 
+ 		selectItem: (
+ 			self items 
+ 				detect: [ :each | each containsPoint: evt position ] 
+ 				ifNone: [ nil ])
+ 		event: evt.
+ 
+ 	"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: evt) 
+ 			ifTrue: [ ^self ]
+ 			ifFalse: [ 
+ 				(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: evt]!

Item was added:
+ ----- Method: MenuMorph>>processFocusEvent:using: (in category 'events') -----
+ processFocusEvent: evt using: dispatcher
+ 
+ 	^ dispatcher dispatchFocusEventFully: evt with: self!

Item was added:
+ ----- Method: MenuMorph>>wantsEveryMouseMove (in category 'events') -----
+ wantsEveryMouseMove
+ 	^ true!

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. However, it might already have been handled due to overrides in #processFocusEvent:using:. We might want to get rid of this call-back in the future..."
- 	"Handle the given event. This message is sent if the receiver currently has the focus and is therefore receiving events directly from some hand.
  	
+ 	^ anEvent wasHandled
+ 		ifTrue: [anEvent]
+ 		ifFalse: [self handleEvent: anEvent]!
- 	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"
- 			morph == anEvent hand ifFalse: [ "Fixes drag-and-drop bug."
- 				filteredEvent := morph sendFilterEventCapture: filteredEvent for: morph.
- 				filteredEvent wasIgnored ifTrue: [^ filteredEvent]]].
- 
- 	"Event bubbling. Filters are processed in #handleEvent:."
- 	self withAllOwnersDo: [:morph |
- 		morph == anEvent hand ifFalse: [ "Fixes drag-and-drop bug."
- 			filteredEvent := morph handleEvent: filteredEvent.
- 			filteredEvent wasIgnored ifTrue: [^ filteredEvent]]].
- 
- 	^ filteredEvent!

Item was added:
+ ----- Method: Morph>>processFocusEvent: (in category 'events-processing') -----
+ processFocusEvent: anEvent
+ 
+ 	^self processFocusEvent: anEvent using: self defaultEventDispatcher!

Item was added:
+ ----- Method: Morph>>processFocusEvent:using: (in category 'events-processing') -----
+ processFocusEvent: anEvent using: defaultDispatcher
+ 	"Event dispatching shortcut."
+ 
+ 	^ defaultDispatcher dispatchFocusEvent: anEvent with: self!

Item was changed:
+ ----- Method: MorphicEventDispatcher>>dispatchEvent:toSubmorphsOf: (in category 'support') -----
- ----- Method: MorphicEventDispatcher>>dispatchEvent:toSubmorphsOf: (in category 'private') -----
  dispatchEvent: anEvent toSubmorphsOf: aMorph
  	"Dispatch the given event to the submorphs of the given morph. For coordinate transformations, work only with copies. Either return the given event or a copy of any filtered event to employ immutability to some extent. --- PRIVATE!!"
  
  	| localEvent filteredEvent |	
  	aMorph submorphsDo: [:child |
  		localEvent := anEvent transformedBy: (child transformedFrom: aMorph).
  		filteredEvent := child
  			processEvent: localEvent
  			using: self. "use same dispatcher"
  		filteredEvent == #rejected ifFalse: [ "some event or #rejected symbol"
  			self flag: #overlappingChildren. "mt: We cannot give two overlapping siblings the chance to handle the event!!"	
+ 			^ self nextFromOriginal: anEvent local: localEvent filtered: filteredEvent]].
- 			filteredEvent == localEvent
- 				ifTrue: [
- 					localEvent wasHandled ifTrue: [anEvent copyHandlerState: localEvent].
- 					anEvent wasIgnored: localEvent wasIgnored.
- 					^ anEvent]
- 				ifFalse: [
- 					filteredEvent := filteredEvent copy.
- 					filteredEvent translateTo: anEvent position. "restore to untransformed coordinates"
- 					filteredEvent wasHandled ifFalse: [filteredEvent copyHandlerState: anEvent]. "restore handler if needed"
- 					^ filteredEvent]]].
  
  	^ #rejected!

Item was changed:
+ ----- Method: MorphicEventDispatcher>>dispatchEvent:withHandler:withMorph: (in category 'support') -----
- ----- 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 added:
+ ----- Method: MorphicEventDispatcher>>dispatchFocusEvent:with: (in category 'focus events') -----
+ dispatchFocusEvent: anEventWithGlobalPosition with: focusMorph
+ 	"Dispatch the given event to the given morph. Simulate capturing phase, handle the event, then do bubbling."
+ 
+ 	| currentEvent |
+ 	"1) Capturing phase."
+ 	currentEvent := self doCapturingForFocusEvent: anEventWithGlobalPosition with: focusMorph.
+ 	currentEvent == #rejected ifTrue: [^ #rejected].
+ 	currentEvent wasIgnored ifTrue: [^ currentEvent].
+ 	
+ 	"2) No sub-tree processing here. Use #dispatchFocusEventFully:with: if you want that, too."
+ 	
+ 	"3) Let the focus morph handle the event." 
+ 	currentEvent := self doHandlingForFocusEvent: currentEvent with: focusMorph.
+ 	currentEvent wasIgnored ifTrue: [^ currentEvent].
+ 	
+ 	"4) Bubbling phase"
+ 	^ self doBubblingForFocusEvent: currentEvent with: focusMorph!

Item was added:
+ ----- Method: MorphicEventDispatcher>>dispatchFocusEventFully:with: (in category 'focus events') -----
+ dispatchFocusEventFully: anEventWithGlobalPosition with: focusMorph
+ 	"Dispatch the given event to the given morph. Do capturing, processing in sub-tree, and bubbling."
+ 	
+ 	| currentEvent |
+ 	"1) Capturing phase."
+ 	currentEvent := self doCapturingForFocusEvent: anEventWithGlobalPosition with: focusMorph.
+ 	currentEvent == #rejected ifTrue: [^ #rejected].
+ 	currentEvent wasIgnored ifTrue: [^ currentEvent].
+ 	
+ 	"2) Sub-tree processing."
+ 	currentEvent := self doProcessingForFocusEvent: currentEvent with: focusMorph.
+ 	currentEvent wasIgnored ifTrue: [^ currentEvent].
+ 
+ 	"3) Let the focus morph handle the event. Usually no effect because previous sub-tree processing involved the focus morph already -- at least in the bubbling phase. Skip it?"
+ 	currentEvent := self doHandlingForFocusEvent: currentEvent with: focusMorph.
+ 	currentEvent wasIgnored ifTrue: [^ currentEvent].
+ 	
+ 	"4) Bubbling phase."
+ 	^ self doBubblingForFocusEvent: currentEvent with: focusMorph!

Item was added:
+ ----- Method: MorphicEventDispatcher>>doBubblingForFocusEvent:with: (in category 'support') -----
+ doBubblingForFocusEvent: anEvent with: focusMorph
+ 	"Simulate real event bubbling up to the focused morph's outermost owner. Applies event bubble filters via Morph >> #handleEvent:. Watch out for coordinate transformations and some globals (ActiveWorld, ...)."
+ 
+ 	| currentEvent filteredEvent localEvent referenceMorph |
+ 	currentEvent := anEvent.
+ 	referenceMorph := anEvent hand.
+ 
+ 	focusMorph allOwnersDo: [:ownerMorph |
+ 		ownerMorph == anEvent hand ifFalse: [ "Never bubble up to the hand morph but only up to the world."
+ 			localEvent := currentEvent transformedBy: (ownerMorph transformedFrom: referenceMorph).
+ 			filteredEvent := ownerMorph handleEvent: localEvent.
+ 			currentEvent := self nextFromOriginal: currentEvent local: localEvent filtered: filteredEvent.
+ 			currentEvent wasIgnored ifTrue: [^ currentEvent]]].
+ 
+ 	^ currentEvent!

Item was added:
+ ----- Method: MorphicEventDispatcher>>doCapturingForFocusEvent:with: (in category 'support') -----
+ doCapturingForFocusEvent: anEvent with: focusMorph
+ 	"Simulate real event capturing down to the focused morph. Apply event capture filters. Watch out for coordinate transformations. Keep the filter-ignore-reject order like in Morph >> #processEvent:using:."
+ 
+ 	| currentEvent filteredEvent localEvent referenceMorph |
+ 	currentEvent := anEvent.
+ 	referenceMorph := anEvent hand.
+ 
+ 	"Event capturing. Filters only because the capturing phase was bypassed by using the keyboard/mouse focus."
+ 	focusMorph withAllOwners reverseDo: [:ownerMorph | "reverse order to comply with regular dispatching"
+ 		ownerMorph == anEvent hand ifFalse: [ "Never dispatch the hand morph. It already did so."
+ 			localEvent := currentEvent transformedBy: (ownerMorph transformedFrom: referenceMorph).
+ 			
+ 			filteredEvent := ownerMorph sendFilterEventCapture: localEvent for: ownerMorph.
+ 			
+ 			"Ignoring has higher priority but the reject-check must be with local event coodinates."
+ 			(filteredEvent wasIgnored not and: [ownerMorph rejectsEvent: filteredEvent])
+ 				ifTrue: [^ #rejected].
+ 			
+ 			currentEvent := self nextFromOriginal: currentEvent local: localEvent filtered: filteredEvent.
+ 			currentEvent wasIgnored ifTrue: [^ currentEvent]]].
+ 	
+ 	^ currentEvent!

Item was added:
+ ----- Method: MorphicEventDispatcher>>doHandlingForFocusEvent:with: (in category 'support') -----
+ doHandlingForFocusEvent: currentEvent with: focusMorph
+ 
+ 	| localEvent filteredEvent |
+ 	localEvent := currentEvent transformedBy: (focusMorph transformedFrom: currentEvent hand).
+ 	filteredEvent := focusMorph handleFocusEvent: localEvent.
+ 	^ self nextFromOriginal: currentEvent local: localEvent filtered: filteredEvent.!

Item was added:
+ ----- Method: MorphicEventDispatcher>>doProcessingForFocusEvent:with: (in category 'support') -----
+ doProcessingForFocusEvent: currentEvent with: focusMorph
+ 	"Sub-tree processing (including capturing from focus morph down to something and bubbling up back to focus morph). Never reject in the end."
+ 	
+ 	| localEvent filteredEvent |
+ 	localEvent := currentEvent transformedBy: (focusMorph transformedFrom: currentEvent hand).
+ 	filteredEvent := focusMorph processEvent: localEvent using: self.
+ 	^ filteredEvent == #rejected
+ 		ifTrue: [currentEvent] "Can happen if you click, e.g., outside the bounds of the focus morph"
+ 		ifFalse: [self nextFromOriginal: currentEvent local: localEvent filtered: filteredEvent]!

Item was added:
+ ----- Method: MorphicEventDispatcher>>nextFromOriginal:local:filtered: (in category 'support') -----
+ nextFromOriginal: originalEvent local: localEvent filtered: filteredEvent
+ 	"Take the filtered event if different but always keep the original coordinates."
+ 	
+ 	filteredEvent == localEvent
+ 		ifTrue: [ "Use original event but keep track of ignored flag."
+ 			localEvent wasHandled ifTrue: [originalEvent copyHandlerState: localEvent].
+ 			originalEvent wasIgnored: localEvent wasIgnored.
+ 			^ originalEvent]
+ 		ifFalse: [ "There was an event transformation. Copy, revert coordinates, keep handler state."
+ 			| result |
+ 			result := filteredEvent copy. "Never mutate position without copying. MouseClickState etc. will break otherwise."
+ 			result translateTo: originalEvent position. "restore to untransformed coordinates"
+ 			result wasHandled ifFalse: [result copyHandlerState: originalEvent].
+ 			^ result].
+ !

Item was removed:
- ----- 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."
- 
- 	| result filteredEvent |
- 	result := self processEvent: evt.
- 	filteredEvent := result == #rejected ifTrue: [evt] ifFalse: [result].
- 
- 	^ super handleFocusEvent: filteredEvent!

Item was added:
+ ----- Method: UserDialogBoxMorph>>processFocusEvent:using: (in category 'events') -----
+ processFocusEvent: evt using: dispatcher
+ 
+ 	^ dispatcher dispatchFocusEventFully: evt with: self!



More information about the Squeak-dev mailing list