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

commits at source.squeak.org commits at source.squeak.org
Fri Jun 30 07:26:26 UTC 2017


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

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

Name: Morphic-mt.1342
Author: mt
Time: 30 June 2017, 9:26:09.827527 am
UUID: 42b6a5ae-42d0-9849-ac5e-5950b96e6e55
Ancestors: Morphic-nice.1341

Extract initial invocation of halo or meta menu to event filter at world level. Having this, EventHandler is more reliable and invocation logic is fully captured in PasteUpMorph >> #tryInvokeHalo:. Further halo transfer logic enclosed in SimpleHaloMorph.

This works now:

m := Morph new.
m openInWorld. 

m wantsHaloFromClick: false.
m wantsYellowButtonMenu: false.
m wantsMetaMenu: false.

m on: #mouseDown send: #value: to:[:evt|
        evt redButtonPressed ifTrue:[m color: Color red].
        evt yellowButtonPressed ifTrue:[m color: Color yellow].
        evt blueButtonPressed ifTrue:[m color: Color blue]].

=============== Diff against Morphic-nice.1341 ===============

Item was removed:
- ----- Method: DockingBarMorph>>blueButtonDown: (in category 'meta-actions') -----
- blueButtonDown: anEvent 
- 	"Special gestures (cmd-mouse on the Macintosh; Alt-mouse on  
- 	Windows and Unix) allow a mouse-sensitive morph to be  
- 	moved or bring up a halo for the morph."
- 	"In NoviceMode we don't want halos"
- 	
- 	Preferences noviceMode 
- 	ifFalse: [super blueButtonDown: anEvent]
- 	!

Item was changed:
  ----- Method: HaloMorph>>addGraphicalHandleFrom:at: (in category 'private') -----
  addGraphicalHandleFrom: formKey at: aPoint
  	"Add the supplied form as a graphical handle centered at the given point.  Return the handle."
  	| handle aForm |
  	aForm := (ScriptingSystem formAtKey: formKey) ifNil: [ScriptingSystem formAtKey: #SolidMenu].
  	handle := ImageMorph new image: aForm; bounds: (Rectangle center: aPoint extent: aForm extent).
  	handle wantsYellowButtonMenu: false.
  	self addMorph: handle.
+ 	handle on: #mouseUp send: #endInteraction: to: self.
- 	handle on: #mouseUp send: #endInteraction to: self.
  	^ handle
  !

Item was changed:
  ----- Method: HaloMorph>>addHandleAt:color:icon:on:send:to: (in category 'private') -----
  addHandleAt: aPoint color: aColor icon: iconName on: eventName send: selector to: recipient 
  	"Add a handle centered at the given point with the given color, 
  	and set it up to respond to the given event by sending the 
  	given selector to the given recipient. Return the handle."
  	| handle |
  	handle := self createHandleAt: aPoint color: (aColor alpha: 0.8) iconName: iconName.
  	self addMorph: handle.
  
+ 	handle on: #mouseUp send: #endInteraction: to: self.
- 	handle on: #mouseUp send: #endInteraction to: self.
  	handle on: eventName send: selector to: recipient.
  	handle setBalloonText: (target balloonHelpTextForHandle: handle) translated.
  
  	^ handle !

Item was removed:
- ----- Method: HaloMorph>>blueButtonDown: (in category 'events') -----
- blueButtonDown: event
- 
- 	self isMagicHalo
- 		ifFalse: [super blueButtonDown: event]
- 		ifTrue: [
- 			self isMagicHalo: false.
- 			self magicAlpha: 1.0].!

Item was removed:
- ----- Method: HaloMorph>>containsPoint: (in category 'geometry testing') -----
- containsPoint: aPoint 
- 	"This method is overridden so that, once up, the handles will stay up as long as the mouse is within the box that encloses all the handles even if it is not over any handle or over its owner."
- 
- 	^target
- 		ifNil: [super containsPoint: aPoint] 
- 		ifNotNil: [false]!

Item was removed:
- ----- Method: HaloMorph>>containsPoint:event: (in category 'events') -----
- containsPoint: aPoint event: anEvent
- 	"Blue buttons are handled by the halo"
- 	(anEvent isMouse and:[anEvent isMouseDown and:[anEvent blueButtonPressed]])
- 		ifFalse:[^super containsPoint: aPoint event: anEvent].
- 	^bounds containsPoint: anEvent position!

Item was changed:
  ----- Method: HaloMorph>>doDebug:with: (in category 'private') -----
  doDebug: evt with: menuHandle
  	"Ask hand to invoke the a debugging menu for my inner target.  If shift key is down, immediately put up an inspector on the inner target"
  
  	| menu |
+ 	evt shiftPressed ifTrue: [
+ 		evt hand removeHalo.
- 	self obtainHaloForEvent: evt andRemoveAllHandlesBut: nil.
- 	self world displayWorld.
- 	evt shiftPressed ifTrue: 
- 		[self delete.
  		^ innerTarget inspectInMorphic: evt].
  
  	menu := innerTarget buildDebugMenu: evt hand.
  	menu addTitle: (innerTarget externalName truncateWithElipsisTo: 40).
+ 	menu popUpEvent: evt in: self world.
+ 	evt hand removeHalo.!
- 	menu popUpEvent: evt in: self world!

Item was changed:
  ----- Method: HaloMorph>>doMenu:with: (in category 'private') -----
  doMenu: evt with: menuHandle
  	"Ask hand to invoke the halo menu for my inner target."
  
  	| menu |
- 	self obtainHaloForEvent: evt andRemoveAllHandlesBut: nil.
- 	self world displayWorld.
  	menu := innerTarget buildHandleMenu: evt hand.
  	innerTarget addTitleForHaloMenu: menu.
  	menu popUpEvent: evt in: self world.
+ 	evt hand removeHalo.
  !

Item was removed:
- ----- Method: HaloMorph>>endInteraction (in category 'private') -----
- endInteraction
- 	"Clean up after a user interaction with the a halo control"
- 
- 	| m |
- 	self isMagicHalo: false.	"no longer"
- 	self magicAlpha: 1.0.
- 	(target isInWorld not or: [owner isNil]) ifTrue: [^self].
- 	[target isFlexMorph and: [target hasNoScaleOrRotation]] whileTrue: 
- 			[m := target firstSubmorph.
- 			target removeFlexShell.
- 			target := m].
- 	self isInWorld 
- 		ifTrue: 
- 			["make sure handles show in front, even if flex shell added"
- 
- 			self comeToFront.
- 			self addHandles].
- 	(self valueOfProperty: #commandInProgress) ifNotNil: 
- 			[:cmd | 
- 			self rememberCommand: cmd.
- 			self removeProperty: #commandInProgress]!

Item was added:
+ ----- Method: HaloMorph>>endInteraction: (in category 'private') -----
+ endInteraction: event
+ 	"Clean up after a user interaction with the a halo control"
+ 
+ 	| m |
+ 	self isMagicHalo: false.	"no longer"
+ 	self magicAlpha: 1.0.
+ 	(target isInWorld not or: [owner isNil]) ifTrue: [^self].
+ 	[target isFlexMorph and: [target hasNoScaleOrRotation]] whileTrue: 
+ 			[m := target firstSubmorph.
+ 			target removeFlexShell.
+ 			target := m].
+ 	self isInWorld 
+ 		ifTrue: 
+ 			["make sure handles show in front, even if flex shell added"
+ 			self flag: #tofix. "mt: Try to avoid deleting and re-creating an event handler (here: the handle) while handling the event."
+ 			self comeToFront.
+ 			self addHandles.
+ 			event hand newMouseFocus: self].
+ 	(self valueOfProperty: #commandInProgress) ifNotNil: 
+ 			[:cmd | 
+ 			self rememberCommand: cmd.
+ 			self removeProperty: #commandInProgress].!

Item was added:
+ ----- Method: HaloMorph>>mouseDown: (in category 'events') -----
+ mouseDown: event
+ 
+ 	self isMagicHalo ifTrue: [
+ 		self isMagicHalo: false.
+ 		self magicAlpha: 1.0].
+ 		
+ 	super mouseDown: event.!

Item was changed:
  ----- Method: HaloMorph>>setCenterOfRotation:with: (in category 'private') -----
  setCenterOfRotation: evt with: rotationHandle
  	| localPt |
  	evt hand obtainHalo: self.
  	evt hand showTemporaryCursor: nil.
  	(rotationHandle hasProperty: #trackCenterOfRotation) ifTrue:
  		[localPt  :=  innerTarget transformFromWorld globalPointToLocal: rotationHandle center.
  		innerTarget setRotationCenterFrom: localPt].
  	
  	rotationHandle removeProperty: #trackCenterOfRotation.
+ 	self endInteraction: evt.!
- 	self endInteraction!

Item was changed:
  ----- Method: HaloMorph>>setDirection:with: (in category 'private') -----
  setDirection: anEvent with: directionHandle
  	"The user has let up after having dragged the direction arrow; now set the forward direction of the actual SketchMorph accordingly"
  	(directionHandle hasProperty: #trackDirectionArrow) ifTrue:
  		[anEvent hand obtainHalo: self.
  		target setDirectionFrom: directionHandle center.
  		directionHandle removeProperty: #trackDirectionArrow.
+ 		self endInteraction: anEvent]!
- 		self endInteraction]!

Item was changed:
  ----- Method: MenuItemMorph>>handleMouseUp: (in category 'events') -----
  handleMouseUp: anEvent
  	"The handling of control between menu item requires them to act on mouse up even if not the current focus. This is different from the default behavior which really only wants to handle mouse ups when they got mouse downs before"
  	anEvent wasHandled ifTrue:[^self]. "not interested"
  	anEvent hand releaseMouseFocus: self.
  	anEvent wasHandled: true.
+ 	self mouseUp: anEvent.!
- 	anEvent blueButtonChanged
- 		ifTrue:[self blueButtonUp: anEvent]
- 		ifFalse:[self mouseUp: anEvent].!

Item was removed:
- ----- Method: Morph>>blueButtonDown: (in category 'meta-actions') -----
- blueButtonDown: anEvent
- 	"Special gestures (cmd-mouse on the Macintosh; Alt-mouse on Windows and Unix) allow a mouse-sensitive morph to be moved or bring up a halo for the morph."
- 	| h tfm doNotDrag |
- 	h := anEvent hand halo.
- 	"Prevent wrap around halo transfers originating from throwing the event back in"
- 	doNotDrag := false.
- 	h ifNotNil:[
- 		(h innerTarget == self) ifTrue:[doNotDrag := true].
- 		(h innerTarget hasOwner: self) ifTrue:[doNotDrag := true].
- 		(self hasOwner: h target) ifTrue:[doNotDrag := true]].
- 
- 	tfm := (self transformedFrom: nil) inverseTransformation.
- 
- 	"cmd-drag on flexed morphs works better this way"
- 	h := self addHalo: (anEvent transformedBy: tfm).
- 	h ifNil: [^ self].
- 	doNotDrag ifTrue:[^self].
- 	"Initiate drag transition if requested"
- 	anEvent hand 
- 		waitForClicksOrDrag: h
- 		event: (anEvent transformedBy: tfm)
- 		selectors: { nil. nil. nil. #startDragTarget:. }
- 		threshold: HandMorph dragThreshold.
- 	"Pass focus explicitly here"
- 	anEvent hand newMouseFocus: h.!

Item was removed:
- ----- Method: Morph>>blueButtonUp: (in category 'meta-actions') -----
- blueButtonUp: anEvent
- 	"Ignored. Theoretically we should never get here since control is transferred to the halo on #blueButtonDown: but subclasses may implement this differently."!

Item was changed:
  ----- Method: Morph>>handleMouseDown: (in category 'events-processing') -----
  handleMouseDown: anEvent
  	"System level event handling."
  	anEvent wasHandled ifTrue:[^self]. "not interested"
  	anEvent hand removePendingBalloonFor: self.
  	anEvent hand removePendingHaloFor: self.
  	anEvent wasHandled: true.
  
- 	(anEvent controlKeyPressed
- 			and: [anEvent blueButtonChanged not
- 				and: [Preferences cmdGesturesEnabled]])
- 		ifTrue: [^ self invokeMetaMenu: anEvent].
- 
  	"Make me modal during mouse transitions"
  	anEvent hand newMouseFocus: self event: anEvent.
- 	(anEvent blueButtonChanged and:[Preferences cmdGesturesEnabled]) ifTrue:[^self blueButtonDown: anEvent].
  	
  	"this mouse down could be the start of a gesture, or the end of a gesture focus"
  	(self isGestureStart: anEvent)
  		ifTrue: [^ self gestureStart: anEvent].
  
  	self mouseDown: anEvent.
  
- 	Preferences maintainHalos
- 		ifFalse:[ anEvent hand removeHaloFromClick: anEvent on: self ].
- 
  	(self handlesMouseStillDown: anEvent) ifTrue:[
  		self startStepping: #handleMouseStillDown: 
  			at: Time millisecondClockValue + self mouseStillDownThreshold
  			arguments: {anEvent copy resetHandlerFields}
  			stepTime: self mouseStillDownStepRate ].
  !

Item was changed:
  ----- Method: Morph>>handleMouseUp: (in category 'events-processing') -----
  handleMouseUp: anEvent
  	"System level event handling."
  	anEvent wasHandled ifTrue:[^self]. "not interested"
  	anEvent hand mouseFocus == self ifFalse:[^self]. "Not interested in other parties"
  	anEvent hand releaseMouseFocus: self.
  	anEvent wasHandled: true.
+ 	self mouseUp: anEvent.
+ 	self stopSteppingSelector: #handleMouseStillDown:.!
- 	anEvent blueButtonChanged
- 		ifTrue:[self blueButtonUp: anEvent]
- 		ifFalse:[self mouseUp: anEvent.
- 				self stopSteppingSelector: #handleMouseStillDown:].!

Item was removed:
- ----- Method: Morph>>handlerForBlueButtonDown: (in category 'meta-actions') -----
- handlerForBlueButtonDown: anEvent
- 	"Return the (prospective) handler for a mouse down event. The handler is temporarily installed and can be used for morphs further down the hierarchy to negotiate whether the inner or the outer morph should finally handle the event.
- 	Note: Halos handle blue button events themselves so we will only be asked if there is currently no halo on top of us."
- 	self wantsHaloFromClick ifFalse:[^nil].
- 	anEvent handler ifNil:[^self].
- 	anEvent handler isPlayfieldLike ifTrue:[^self]. "by default exclude playfields"
- 	(anEvent shiftPressed)
- 		ifFalse:[^nil] "let outer guy have it"
- 		ifTrue:[^self] "let me have it"
- !

Item was removed:
- ----- Method: Morph>>handlerForMetaMenu: (in category 'meta-actions') -----
- handlerForMetaMenu: evt
- 	"Return the prospective handler for invoking the meta menu. By default, the top-most morph in the innermost world gets this menu"
- 	self isWorldMorph ifTrue:[^self].
- 	evt handler ifNotNil:[evt handler isWorldMorph ifTrue:[^self]].
- 	^nil!

Item was changed:
  ----- Method: Morph>>handlerForMouseDown: (in category 'event handling') -----
  handlerForMouseDown: anEvent 
  	"Return the (prospective) handler for a mouse down event. The handler is temporarily 
  	installed and can be used for morphs further down the hierarchy to negotiate whether 
  	the inner or the outer morph should finally handle the event."
  
- 	anEvent blueButtonPressed
- 		ifTrue: [^ self handlerForBlueButtonDown: anEvent].
  	anEvent yellowButtonPressed
  		ifTrue: [^ self handlerForYellowButtonDown: anEvent].
- 	anEvent controlKeyPressed
- 		ifTrue: [^ self handlerForMetaMenu: anEvent].
  	(self handlesMouseDown: anEvent)
  		ifFalse: [^ nil].	"not interested"
  
  	anEvent handler
  		ifNil: [^ self ].	"Same priority but I am innermost"
  
  	"Nobody else was interested"
  	^self mouseDownPriority >= anEvent handler mouseDownPriority
  		ifTrue: [ self]
  		ifFalse: [ nil]!

Item was added:
+ ----- Method: Morph>>invokeHaloOrMove: (in category 'meta-actions') -----
+ invokeHaloOrMove: anEvent
+ 	"Special gestures (cmd-mouse on the Macintosh; Alt-mouse on Windows and Unix) allow a mouse-sensitive morph to be moved or bring up a halo for the morph."
+ 	| h tfm doNotDrag |
+ 	h := anEvent hand halo.
+ 	"Prevent wrap around halo transfers originating from throwing the event back in"
+ 	doNotDrag := false.
+ 	h ifNotNil:[
+ 		(h innerTarget == self) ifTrue:[doNotDrag := true].
+ 		(h innerTarget hasOwner: self) ifTrue:[doNotDrag := true].
+ 		(self hasOwner: h target) ifTrue:[doNotDrag := true]].
+ 
+ 	tfm := (self transformedFrom: nil) inverseTransformation.
+ 
+ 	"cmd-drag on flexed morphs works better this way"
+ 	h := self addHalo: (anEvent transformedBy: tfm).
+ 	h ifNil: [^ self].
+ 	doNotDrag ifTrue:[^self].
+ 	"Initiate drag transition if requested"
+ 	anEvent hand 
+ 		waitForClicksOrDrag: h
+ 		event: (anEvent transformedBy: tfm)
+ 		selectors: { nil. nil. nil. #startDragTarget:. }
+ 		threshold: HandMorph dragThreshold.
+ 	"Pass focus explicitly here"
+ 	anEvent hand newMouseFocus: h.!

Item was changed:
  ----- Method: Morph>>invokeMetaMenu: (in category 'meta-actions') -----
  invokeMetaMenu: evt
- 	"Put up the 'meta' menu, invoked via control-click, unless eToyFriendly is true."
  
  	| menu |
- 	Preferences eToyFriendly ifTrue: [^ self].
- 
  	menu := self buildMetaMenu: evt.
  	menu addTitle: self externalName.
  	menu popUpEvent: evt in: self world!

Item was added:
+ ----- Method: Morph>>wantsHaloFromClick: (in category 'halos and balloon help') -----
+ wantsHaloFromClick: aBoolean
+ 
+ 	self 
+ 		setProperty: #wantsHaloFromClick
+ 		toValue: aBoolean.!

Item was added:
+ ----- Method: Morph>>wantsMetaMenu (in category 'menu') -----
+ wantsMetaMenu
+ 
+ 	^ self valueOfProperty: #wantsMetaMenu ifAbsent: [true]!

Item was added:
+ ----- Method: Morph>>wantsMetaMenu: (in category 'menu') -----
+ wantsMetaMenu: aBoolean
+ 
+ 	self 
+ 		setProperty: #wantsMetaMenu
+ 		toValue: aBoolean.!

Item was added:
+ ----- Method: PasteUpMorph>>addMouseShortcuts (in category 'initialization') -----
+ addMouseShortcuts
+ 	
+ 	self addMouseCaptureFilter: self.!

Item was changed:
  ----- Method: PasteUpMorph>>filterEvent:for: (in category 'events-processing') -----
+ filterEvent: mouseOrKeyboardEvent for: anObject
- filterEvent: aKeyboardEvent for: anObject
- 	"Provide keyboard shortcuts."
  
+ 	"1) Mouse shortcuts"
+ 	mouseOrKeyboardEvent isMouse ifTrue: [
- 	"Delegate keyboard shortcuts to my docking bars."
- 	self submorphsDo: [:ea | ea isDockingBar ifTrue: [
- 		ea filterEvent: aKeyboardEvent for: anObject. "No support for converting events here!!"
- 		aKeyboardEvent wasIgnored ifTrue: [^ aKeyboardEvent "early out"]]].
  	
+ 		"Only accept mouse down, no up."
+ 		mouseOrKeyboardEvent isMouseDown
+ 			ifFalse: [^ mouseOrKeyboardEvent].
+ 	
+ 		mouseOrKeyboardEvent blueButtonPressed
+ 			ifTrue: [	self tryInvokeHalo: mouseOrKeyboardEvent]
+ 			ifFalse: [mouseOrKeyboardEvent controlKeyPressed
+ 				ifTrue: [self tryInvokeMetaMenu: mouseOrKeyboardEvent]].
- 	aKeyboardEvent isKeystroke
- 		ifFalse: [^ aKeyboardEvent].
  
+ 		^ mouseOrKeyboardEvent].
- 	aKeyboardEvent commandKeyPressed ifTrue: [
- 		aKeyboardEvent keyCharacter caseOf: {
- 			[$R] -> [Utilities browseRecentSubmissions].
- 			[$L] -> [self findAFileList: aKeyboardEvent].
- 			[$O] -> [self findAMonticelloBrowser].
- 			[$P] -> [self findAPreferencesPanel: aKeyboardEvent].
- 			"[$Z] -> [ChangeList browseRecentLog]."
- 			[$]] -> [Smalltalk snapshot: true andQuit: false].
- 			[$+] -> [Preferences increaseFontSize].
- 			[$-] -> [Preferences decreaseFontSize].
- 			[$=] -> [Preferences restoreDefaultFonts].
- 		} otherwise: [^ aKeyboardEvent "no hit"].
- 		^ aKeyboardEvent ignore "hit!!"].
  
+ 	"2) Keyboard shortcuts"
+ 	mouseOrKeyboardEvent isKeyboard ifTrue: [
+ 
+ 		"Delegate keyboard shortcuts to my docking bars."
+ 		self submorphsDo: [:ea | ea isDockingBar ifTrue: [
+ 			ea filterEvent: mouseOrKeyboardEvent for: anObject. "No support for converting events here!!"
+ 			mouseOrKeyboardEvent wasIgnored ifTrue: [^ mouseOrKeyboardEvent "early out"]]].
+ 	
+ 		"Only accept key strokes as shortcuts, no down/up."
+ 		mouseOrKeyboardEvent isKeystroke
+ 			ifFalse: [^ mouseOrKeyboardEvent].
+ 
+ 		self tryInvokeKeyboardShortcut: mouseOrKeyboardEvent.
+ 	
+ 		^ mouseOrKeyboardEvent].
+ 	
+ 	"Should not be necessary if this filter is correctly configured."
+ 	^ mouseOrKeyboardEvent!
- 	^ aKeyboardEvent "no hit"!

Item was changed:
  ----- Method: PasteUpMorph>>initialize (in category 'initialization') -----
  initialize
  "initialize the state of the receiver"
  	super initialize.
  ""
  	cursor := 1.
  	padding := 3.
  	self enableDragNDrop.
  	self isWorldMorph
  		ifTrue: [self setProperty: #automaticPhraseExpansion toValue: true].
  	self clipSubmorphs: true.
+ 	self initializeKeyboardShortcuts.
+ 	self initializeMouseShortcuts.!
- 	self initializeKeyboardShortcuts.!

Item was added:
+ ----- Method: PasteUpMorph>>initializeMouseShortcuts (in category 'initialization') -----
+ initializeMouseShortcuts
+ 	
+ 	self addMouseShortcuts.!

Item was added:
+ ----- Method: PasteUpMorph>>tryInvokeHalo: (in category 'events-processing') -----
+ tryInvokeHalo: anEvent
+ 
+ 	| innerMost target |
+ 	anEvent hand halo ifNotNil: [^ self "No invocation needed. Halo will handle transfer itself."].
+ 	Preferences noviceMode ifTrue: [^ self "No halo in novice mode."].
+ 	Preferences cmdGesturesEnabled ifFalse: [^ self].
+ 	
+ 	innerMost := (self morphsAt: anEvent position unlocked: true) first.
+ 	
+ 	"1) Try to use innermost morph but skip all the ones that do not want to show a halo along the owner chain."
+ 	target := innerMost.
+ 	[target isNil or: [target wantsHaloFromClick]]
+ 		whileFalse: [target := target owner].
+ 	target ifNil: [^ self].
+ 	
+ 	"2) Without a modifier, which is normal, find the outermost container for that inner morph."
+ 	(innerMost == self or: [anEvent shiftPressed]) ifFalse: [
+ 		| previousTargets |
+ 		previousTargets := OrderedCollection new.
+ 		[target notNil and: [target owner ~~ self]] whileTrue: [
+ 			previousTargets add: target.
+ 			target := target owner].
+ 		target ifNil: [^ self].
+ 		[previousTargets isEmpty or: [target wantsHaloFromClick]] whileFalse: [
+ 			target := previousTargets removeLast].
+ 		target wantsHaloFromClick ifFalse: [^ self]].
+ 	
+ 	"3) Show the container of that nested structure, which is usually my direct submorph."
+ 	target withAllOwnersDo: [:ea | ea owner == self ifTrue: [ea comeToFront]].
+ 	
+ 	"4) Now that we have the target, show the halo. Abort event dispatching, too, to avoid confusion."
+ 	anEvent hand newMouseFocus: target event: anEvent.
+ 	target invokeHaloOrMove: anEvent.
+ 	anEvent ignore.!

Item was added:
+ ----- Method: PasteUpMorph>>tryInvokeKeyboardShortcut: (in category 'events-processing') -----
+ tryInvokeKeyboardShortcut: aKeyboardEvent
+ 
+ 	aKeyboardEvent commandKeyPressed ifFalse: [^ self].
+ 	
+ 	aKeyboardEvent keyCharacter caseOf: {
+ 		[$R] -> [Utilities browseRecentSubmissions].
+ 		[$L] -> [self findAFileList: aKeyboardEvent].
+ 		[$O] -> [self findAMonticelloBrowser].
+ 		[$P] -> [self findAPreferencesPanel: aKeyboardEvent].
+ 		"[$Z] -> [ChangeList browseRecentLog]."
+ 		[$]] -> [Smalltalk snapshot: true andQuit: false].
+ 		[$+] -> [Preferences increaseFontSize].
+ 		[$-] -> [Preferences decreaseFontSize].
+ 		[$=] -> [Preferences restoreDefaultFonts].
+ 	} otherwise: [^ self "no hit"].
+ 	
+ 	aKeyboardEvent ignore "hit!!".!

Item was added:
+ ----- Method: PasteUpMorph>>tryInvokeMetaMenu: (in category 'events-processing') -----
+ tryInvokeMetaMenu: anEvent
+ 
+ 	| innerMost target |
+ 	Preferences cmdGesturesEnabled ifFalse: [^ self].
+ 	Preferences eToyFriendly ifTrue: [^ self].
+ 	
+ 	innerMost := (self morphsAt: anEvent position unlocked: true) first.
+ 	
+ 	"Traverse the owner chain if some morph does not want to show its meta menu."
+ 	target := innerMost.
+ 	[target isNil or: [target wantsMetaMenu]] whileFalse: [target := target owner].
+ 	target ifNil: [^ self].
+ 	
+ 	target invokeMetaMenu: anEvent.
+ 	anEvent ignore.!

Item was removed:
- ----- Method: SimpleHaloMorph>>blueButtonDown: (in category 'events') -----
- blueButtonDown: event
- 	"Transfer the halo to the next likely recipient"
- 	
- 	self target ifNil: [^self delete].
- 	event hand obtainHalo: self.
- 
- 	self positionOffset: (event position - (self target point: self target position in: self owner)).
- 
- 	"wait for drags or transfer"
- 	event hand 
- 		waitForClicksOrDrag: self 
- 		event: event
- 		selectors: { #transferHalo:. nil. nil. #startDragTarget:. }
- 		threshold: HandMorph dragThreshold.!

Item was added:
+ ----- Method: SimpleHaloMorph>>handleMouseUp: (in category 'events') -----
+ handleMouseUp: evt
+ 
+ 	super handleMouseUp: evt.
+ 	evt hand newMouseFocus: self.!

Item was removed:
- ----- Method: SimpleHaloMorph>>handlerForBlueButtonDown: (in category 'events') -----
- handlerForBlueButtonDown: anEvent
- 	"Blue button was clicked within the receiver"
- 	^self!

Item was added:
+ ----- Method: SimpleHaloMorph>>handlesMouseDown: (in category 'events') -----
+ handlesMouseDown: evt
+ 
+ 	^ true!

Item was added:
+ ----- Method: SimpleHaloMorph>>mouseDown: (in category 'events') -----
+ mouseDown: event
+ 	"Transfer the halo to the next likely recipient"
+ 
+ 	((self containsPoint: event position) not or: [event blueButtonPressed not])
+ 		ifTrue: [
+ 			"Close this halo and give another morph the chance to react."
+ 			event hand removeHalo.
+ 			event resetHandlerFields.
+ 			event hand world processEvent: event.
+ 			^ self].
+ 
+ 	self target ifNil: [^self delete].
+ 	event hand obtainHalo: self.
+ 
+ 	self positionOffset: (event position - (self target point: self target position in: self owner)).
+ 
+ 	"wait for drags or transfer"
+ 	event hand 
+ 		waitForClicksOrDrag: self 
+ 		event: event
+ 		selectors: { #transferHalo:. nil. nil. #startDragTarget:. }
+ 		threshold: HandMorph dragThreshold.!

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

Item was added:
+ ----- Method: SimpleHaloMorph>>transferHalo:from: (in category 'halos and balloon help') -----
+ transferHalo: event from: formerHaloOwner
+ 	"Ignore. No halo for halo."!

Item was changed:
+ (PackageInfo named: 'Morphic') postscript: 'Project allMorphicProjects do: [:ea | ea world addMouseShortcuts].'!
- (PackageInfo named: 'Morphic') postscript: 'TheWorldMainDockingBar updateInstances. "For more fine-granular visual settings."
- 
- "These are all in UI Themes now but remained as deprecated, so the preference got not removed automatically."
- Preferences removePreference: #''BalloonMorph>>balloonColor''.
- Preferences removePreference: #''MenuMorph>>menuBorderColor''.
- Preferences removePreference: #''MenuMorph>>menuBorderWidth''.
- Preferences removePreference: #''MenuMorph>>menuColor''.
- Preferences removePreference: #''MenuMorph>>menuLineColor''.
- Preferences removePreference: #''MenuMorph>>menuSelectionColor''.
- Preferences removePreference: #''MenuMorph>>menuTitleBorderColor''.
- Preferences removePreference: #''MenuMorph>>menuTitleBorderWidth''.
- Preferences removePreference: #''MenuMorph>>menuTitleColor''.
- '!



More information about the Squeak-dev mailing list