[squeak-dev] The Trunk: Morphic-eem.1735.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Mar 4 21:13:12 UTC 2021


Eliot Miranda uploaded a new version of Morphic to project The Trunk:
http://source.squeak.org/trunk/Morphic-eem.1735.mcz

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

Name: Morphic-eem.1735
Author: eem
Time: 4 March 2021, 1:13:03.650992 pm
UUID: 7ba0bde5-351e-b94c-a4b5-a4846f3f907c
Ancestors: Morphic-eem.1734

Use the constants on the class side of MouseEvent (adding numButtons to them) when creating the button field that (incredibly annoyingly) combines mouse buttons and modifier keys.  This is a necessary first step to increasing the nu,ber of buttons to include the moveLeft and moveRight buttons on modern gaming mice.

=============== Diff against Morphic-eem.1734 ===============

Item was changed:
  ----- Method: HandMorph>>generateDropFilesEvent: (in category 'private events') -----
  generateDropFilesEvent: evtBuf 
  	"Generate the appropriate mouse event for the given raw event buffer."
  
  	| position buttons modifiers stamp numFiles dragType |
  	stamp := evtBuf second.
  	stamp = 0 ifTrue: [stamp := Time eventMillisecondClock].
  	dragType := evtBuf third.
  	position := evtBuf fourth @ evtBuf fifth.
  	buttons := MouseEvent redButton. "hacked because necessary for correct mouseMoveDragging handling"
  	modifiers := evtBuf sixth.
+ 	buttons := buttons bitOr: (modifiers bitShift: MouseEvent numButtons).
- 	buttons := buttons bitOr: (modifiers bitShift: 3).
  	numFiles := evtBuf seventh.
  	
  	dragType caseOf: {
  		[1] -> [ "dragEnter"
  			externalDropMorph := TransferMorph new
  				dragTransferType: #filesAndDirectories;
  				source: self;
  				passenger: (numFiles = 0 "Usually, numFiles and drop paths are delivered on dragDrop only. Still reserving this possibility for able host implementations."
  					ifTrue: [self flag: #vmCapabilityMissing. 'Unknown host content' translated]
  					ifFalse: [FileDirectory dropFilesAndDirectories: numFiles]);
  				yourself.
  			
  			"During the drag operation, the host system is responsible for displaying the cursor."
  			self grabMorph: externalDropMorph.
  			self showTemporaryCursor: Cursor blank.
  			externalDropMorph bottomRight: self topLeft. "Southeast area of the cursor is blocked by drawings from the source application. Display our drop morph at the opposite corner of the cursor." ].
  		[2] -> [ "dragMove"
  			^ MouseMoveEvent new 
  				setType: #mouseMove
  				startPoint: self position
  				endPoint: position
  				trail: "{self position. position}"(self mouseDragTrailFrom: evtBuf)
  				buttons: buttons
  				hand: self
  				stamp: stamp ].
  		[3]  -> [ "dragLeave"
  			externalDropMorph ifNotNil: #abandon.
  			externalDropMorph := nil.
  			self showTemporaryCursor: nil ].
  		[4] -> [ "dragDrop"
  			| oldButtons |
  			externalDropMorph ifNil: [
  				"dragDrop has been sent without prior dragging. This happens when the VM is configured as singleton application and has been called again (aka #launchDrop)."
  				^ self error: 'Launch drop for singleton Squeak 	not yet implemented.'].
  			
  			self showTemporaryCursor: nil.
  			externalDropMorph passenger isString ifTrue: [
  				self flag: #vmCapabilityMissing. "See above."
  				externalDropMorph passenger: (FileDirectory dropFilesAndDirectories: numFiles)].
  			externalDropMorph := nil.
  			
  			(Smalltalk classNamed: #DropFilesEvent) ifNotNil: [:eventClass |
  				| classicEvent |
  				"Generate classic DropFilesEvent, providing backward compatibility."
  				classicEvent := eventClass new
  					setPosition: position
  					contents: numFiles
  					hand: self.
  				self processEvent: classicEvent.
  				classicEvent wasHandled ifTrue: [^ nil]].
  			
  			oldButtons := lastEventBuffer fifth
+ 				bitOr: (lastEventBuffer sixth bitShift: MouseEvent numButtons).
- 				bitOr: (lastEventBuffer sixth bitShift: 3).
  			^ MouseButtonEvent new 
  				setType: #mouseUp
  				position: position
  				which: (oldButtons bitXor: buttons)
  				buttons: buttons
  				nClicks: 0
  				hand: self
  				stamp: stamp ].
  		[5] -> [ "drag request"
  			"For dnd out. Not properly implemented at the moment."
  			self shouldBeImplemented] }.
  	^ nil!

Item was changed:
  ----- Method: HandMorph>>generateKeyboardEvent: (in category 'private events') -----
  generateKeyboardEvent: evtBuf
  	"Generate the appropriate mouse event for the given raw event buffer"
  
  	| buttons modifiers type pressType stamp keyValue |
  	stamp := evtBuf second.
  	stamp = 0 ifTrue: [stamp := Sensor eventTimeNow].
  	pressType := evtBuf fourth.
  	pressType = EventKeyDown ifTrue: [type := #keyDown].
  	pressType = EventKeyUp ifTrue: [type := #keyUp].
  	pressType = EventKeyChar ifTrue: [type := #keystroke].
  	modifiers := evtBuf fifth.
+ 	buttons := (modifiers bitShift: MouseEvent numButtons) bitOr: (lastMouseEvent buttons bitAnd: MouseEvent anyButton).
- 	buttons := (modifiers bitShift: 3) bitOr: (lastMouseEvent buttons bitAnd: 7).
  	type = #keystroke
  		ifTrue: [keyValue := (self keyboardInterpreter nextCharFrom: Sensor firstEvt: evtBuf) asInteger]
  		ifFalse: [keyValue := evtBuf third].
  	^ KeyboardEvent new
  		setType: type
  		buttons: buttons
  		position: self position
  		keyValue: keyValue
  		hand: self
  		stamp: stamp.
  !

Item was changed:
  ----- Method: HandMorph>>generateMouseEvent: (in category 'private events') -----
  generateMouseEvent: evtBuf 
  	"Generate the appropriate mouse event for the given raw event buffer"
  
  	| position buttons modifiers type trail stamp oldButtons evtChanged |
  	evtBuf first = lastEventBuffer first 
  		ifTrue: 
  			["Workaround for Mac VM bug, *always* generating 3 events on clicks"
  
  			evtChanged := false.
  			3 to: evtBuf size
  				do: [:i | (lastEventBuffer at: i) = (evtBuf at: i) ifFalse: [evtChanged := true]].
  			evtChanged ifFalse: [^nil]].
  	stamp := evtBuf second.
  	stamp = 0 ifTrue: [stamp := Sensor eventTimeNow].
  	position := evtBuf third @ evtBuf fourth.
  	buttons := evtBuf fifth.
  	modifiers := evtBuf sixth.
  
  	type := buttons = 0 
+ 			ifTrue:
+ 				[lastEventBuffer fifth = 0 		
+ 					ifTrue: [#mouseMove] 		"this time no button and previously no button .. just mouse move"
+ 					ifFalse: [#mouseUp]]		"this time no button but previously some button ... therefore button was released"
+ 			ifFalse:
+ 				[buttons = lastEventBuffer fifth
+ 						ifTrue: [#mouseMove]	"button states are the same .. now and past .. therfore a mouse movement"
+ 						ifFalse:					"button states are different .. button was pressed or released"
+ 							[buttons > lastEventBuffer fifth
- 		ifTrue:[
- 				lastEventBuffer fifth = 0 		
- 					ifTrue: [#mouseMove] 	"this time no button and previously no button .. just mouse move"
- 					ifFalse: [#mouseUp]		"this time no button but previously some button ... therefore button was released"
- 		]
- 		ifFalse:[
- 				buttons = lastEventBuffer fifth
- 						ifTrue: [#mouseMove]		"button states are the same .. now and past .. therfore a mouse movement"
- 						ifFalse: [					"button states are different .. button was pressed or released"
- 							buttons > lastEventBuffer fifth
  								ifTrue: [#mouseDown]
+ 								ifFalse:[#mouseUp]]].
+ 	buttons := buttons bitOr: (modifiers bitShift: MouseEvent numButtons).
+ 	oldButtons := lastEventBuffer fifth bitOr: (lastEventBuffer sixth bitShift: MouseEvent numButtons).
- 								ifFalse:[#mouseUp].
- 						].
- 		].
- 	buttons := buttons bitOr: (modifiers bitShift: 3).
- 	oldButtons := lastEventBuffer fifth 
- 				bitOr: (lastEventBuffer sixth bitShift: 3).
  	lastEventBuffer := evtBuf.
+ 	type == #mouseMove ifTrue: 
+ 		[trail := self mouseTrailFrom: evtBuf.
+ 		^MouseMoveEvent new 
+ 			setType: type
+ 			startPoint: self position
+ 			endPoint: trail last
+ 			trail: trail
+ 			buttons: buttons
+ 			hand: self
+ 			stamp: stamp].
- 	type == #mouseMove 
- 		ifTrue: 
- 			[trail := self mouseTrailFrom: evtBuf.
- 			^MouseMoveEvent new 
- 				setType: type
- 				startPoint: (self position)
- 				endPoint: trail last
- 				trail: trail
- 				buttons: buttons
- 				hand: self
- 				stamp: stamp].
  	^MouseButtonEvent new 
  		setType: type
  		position: position
  		which: (oldButtons bitXor: buttons)
  		buttons: buttons
  		nClicks: (evtBuf seventh ifNil: [0])
  		hand: self
  		stamp: stamp!

Item was changed:
  ----- Method: HandMorph>>showEvent: (in category 'events-debugging') -----
  showEvent: anEvent
  	"Show details about the event on the display form. Useful for debugging."
+ 	"ShowEvents := true"
+ 	"ShowEvents := false"
- 	
  	| message borderWidth |
  	ShowEvents == true ifFalse: [^ self].
  	
  	borderWidth := 5.
  	message := String streamContents: [:strm |
  		strm
  			nextPutAll: '[HandMorph >> #showEvent:]'; cr;
  			nextPutAll: 'event'; tab; tab; tab; tab; nextPutAll: anEvent printString; cr;
  			nextPutAll: 'keyboard focus'; tab; tab; nextPutAll: self keyboardFocus printString; cr;
  			nextPutAll: 'mouse focus'; tab; tab; nextPutAll: self mouseFocus printString].
  		
  	message := message asDisplayText
  		foregroundColor: Color black
  		backgroundColor: Color white.
  	
  	"Offset to support multiple hands debugging."
  	Display fill: (0 @ 0 extent: message form extent + (borderWidth asPoint * 2)) rule: Form over fillColor: Color white.
  	message displayOn: Display at: borderWidth asPoint + (0 @  ((owner hands indexOf: self) - 1 * message form height)).!

Item was added:
+ ----- Method: MouseEvent class>>numButtons (in category 'constants') -----
+ numButtons
+ 	"We support three button mice."
+ 	^3!



More information about the Squeak-dev mailing list