[squeak-dev] The Trunk: Kernel-mt.1333.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Jul 15 09:22:36 UTC 2020


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

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

Name: Kernel-mt.1333
Author: mt
Time: 15 July 2020, 11:22:34.685718 am
UUID: 4e50519a-d1e3-4a74-85cc-3c02660d650f
Ancestors: Kernel-nice.1332

Clean up code for non-event-based input processing, primarily used in ST80.

Moves some methods to ST80 package. Needs more work to remove all sends from Morphic such as #shiftPressed etc.

Also rely on in-image interrupt-key handling only. Recent VMs do not fire the old-style interrupt semaphore anymore. See #userInterruptWatcher.

=============== Diff against Kernel-nice.1332 ===============

Item was changed:
  Object subclass: #EventSensor
  	instanceVariableNames: 'mouseButtons mousePosition mouseWheelDelta keyboardBuffer interruptKey interruptSemaphore eventQueue inputSemaphore lastEventPoll hasInputSemaphore'
+ 	classVariableNames: 'ButtonDecodeTable EventPollPeriod EventTicklerProcess InterruptWatcherProcess KeyDecodeTable'
- 	classVariableNames: 'ButtonDecodeTable EventPollPeriod EventTicklerProcess InterruptSemaphore InterruptWatcherProcess KeyDecodeTable'
  	poolDictionaries: 'EventSensorConstants'
  	category: 'Kernel-Processes'!
  
  !EventSensor commentStamp: 'mt 12/13/2019 14:38' prior: 0!
  An EventSensor is an interface to the user input devices.
  There is at least one instance of EventSensor named Sensor in the system.
  
  EventSensor is a replacement for the earlier InputSensor implementation based on a set of (optional) event primitives. An EventSensor updates its state when events are received so that all state based users of Sensor (e.g., Sensor keyboard, Sensor leftShiftDown, Sensor mouseButtons) will work exactly as before, by moving the current VM mechanisms into EventSensor itself. An optional input semaphore is part of the new design.
  
  For platforms that support true asynchronous event notification, the semaphore will be signaled to indicate pending events.
  On platforms that do not support asynchronous notifications about events, the UI will have to poll EventSensor periodically to read events from the VM.
  
  Instance variables:
  	mouseButtons <Integer>	- mouse button state as replacement for primMouseButtons
  	mousePosition <Point>	- mouse position as replacement for primMousePt
  	keyboardBuffer <SharedQueue>	- keyboard input buffer
  	interruptKey <Integer>			- currently defined interrupt key
  	interruptSemaphore <Semaphore>	- the semaphore signaled when the interruptKey is detected
  	eventQueue <SharedQueue>	- an optional event queue for event driven applications
  	inputSemaphore <Semaphore>- the semaphore signaled by the VM if asynchronous event notification is supported
  	lastEventPoll <Integer>		- the last millisecondClockValue at which we called fetchMoreEvents
  	hasInputSemaphore <Boolean>	- true if my inputSemaphore has actually been signaled at least once.
  
  Class variables:
  	ButtonDecodeTable <ByteArray> - maps mouse buttons as reported by the VM to ones reported in the events.
  	KeyDecodeTable <Dictionary<SmallInteger->SmallInteger>> - maps some keys and their modifiers to other keys (used for instance to map Ctrl-X to Alt-X)
  	InterruptSemaphore <Semaphore> - signalled by the the VM and/or the event loop upon receiving an interrupt keystroke.
  	InterruptWatcherProcess <Process> - waits on the InterruptSemaphore and then responds as appropriate.
  	EventPollPeriod <Integer>	- the number of milliseconds to wait between polling for more events in the userInterruptHandler.
  	EventTicklerProcess <Process>	- the process that makes sure that events are polled for often enough (at least every EventPollPeriod milliseconds).
  
  Event format:
  The current event format is very simple. Each event is recorded into an 8 element array. All events must provide some SmallInteger ID (the first field in the event buffer) and a time stamp (the second field in the event buffer), so that the difference between the time stamp of an event and the current time can be reported.
  
  Currently, the following events are defined:
  
  Null event
  =============
  The Null event is returned when the ST side asks for more events but no more events are available.
  Structure:
  [1]		- event type 0
  [2-8]	- unused
  
  Mouse event structure
  ==========================
  Mouse events are generated when mouse input is detected.
  [1]	- event type 1
  [2]	- time stamp
  [3]	- mouse x position
  [4]	- mouse y position
  [5]	- button state; bitfield with the following entries:
  		1	-	2r001	yellow (e.g., right) button
  		2	-	2r010	blue (e.g., middle) button
  		4	-	2r100	red (e.g., left) button
  		[all other bits are currently undefined]
  [6]	- modifier keys; bitfield with the following entries:
  		1	-	shift key
  		2	-	ctrl key
  		4	-	(Mac specific) option key
  		8	-	Cmd/Alt key
  		[all other bits are currently undefined]
  [7]	- reserved.
  [8]	- host window id.
  
  Keyboard events
  ====================
  Keyboard events are generated when keyboard input is detected.
  [1]	- event type 2
  [2]	- time stamp
  [3]	- character code (Ascii)
  		For now the character code is in Mac Roman encoding. See #macToSqueak.
  		For key press/release (see [4]), character codes are normalized.
  [4]	- press state; integer with the following meaning
  		0	-	character (aka. key stroke or key still pressed)
  		1	-	key press (aka. key down)
  		2	- 	key release (aka. key up)
  [5]	- modifier keys (same as in mouse events)
  		For key press/release (see [4]), modifier keys are still accessible.
  [6]	- character code (Unicode UTF32)
  		Manual decoding via KeyboardInputInterpreter possible.
  		For key press/release (see [4]), character codes are normalized.
  [7]	- reserved.
  [8]	- host window id.
  	
  Mouse-wheel event structure
  ==========================
  Mouse-wheel events are generated when mouse-wheel input is detected.
  [1] - event type 7
  [2] - time stamp
  [3] - horizontal scroll delta
  [4] - vertical scroll delta
  [5] - button state (same as in mouse events)
  [6] - modifier keys (same as in mouse events)
  [7] - reserved.
  [8] - host window id.
  !

Item was removed:
- ----- Method: EventSensor>>characterForKeycode: (in category 'keyboard') -----
- characterForKeycode: keycode
- 	"Map the given keycode to a Smalltalk character object. Encoding:
- 		A keycode is 12 bits:   <4 modifer bits><8 bit ISO character>
- 		Modifier bits are:       <command><option><control><shift>"
- 
- 	"NOTE: the command and option keys are specific to the Macintosh and may not have equivalents on other platforms."
- 
- 	keycode = nil ifTrue: [ ^nil ].
- 	keycode class = Character ifTrue: [ ^keycode ].  "to smooth the transition!!"
- 	^ Character value: (keycode bitAnd: 16rFF)!

Item was changed:
+ ----- Method: EventSensor>>cursorPoint (in category 'mouse') -----
- ----- Method: EventSensor>>cursorPoint (in category 'cursor') -----
  cursorPoint
  	"Answer a Point indicating the cursor location."
  
  	^ self peekPosition!

Item was changed:
+ ----- Method: EventSensor>>cursorPoint: (in category 'mouse') -----
- ----- Method: EventSensor>>cursorPoint: (in category 'cursor') -----
  cursorPoint: aPoint 
  	"Set aPoint to be the current cursor location."
  
  	^self primCursorLocPut: aPoint!

Item was removed:
- ----- Method: EventSensor>>flushAllButDandDEvents (in category 'accessing') -----
- flushAllButDandDEvents
- 	| newQueue oldQueue  |
- 	
- 	newQueue := SharedQueue new.
- 	self eventQueue ifNil: [ 
- 		self eventQueue: newQueue.
- 		^ self].
- 	oldQueue := self eventQueue.
- 	[oldQueue size > 0] whileTrue: 
- 		[| item type | 
- 		item := oldQueue next.
- 		type := item at: 1.
- 		type = EventTypeDragDropFiles ifTrue: [ newQueue nextPut: item]].
- 	self eventQueue: newQueue.!

Item was changed:
  ----- Method: EventSensor>>flushEvents (in category 'accessing') -----
  flushEvents
+ 
+ 	keyboardBuffer flush.
+ 	mouseWheelDelta := 0 at 0.
+ 
+ 	self eventQueue ifNotNil: [:queue | queue flush].!
- 	self eventQueue ifNotNil:[:queue | queue flush].!

Item was removed:
- ----- Method: EventSensor>>flushKeyboard (in category 'keyboard') -----
- flushKeyboard
- 	"Remove all characters from the keyboard buffer."
- 
- 	[self keyboardPressed]
- 		whileTrue: [self keyboard]!

Item was removed:
- ----- Method: EventSensor>>flushNonKbdEvents (in category 'private') -----
- flushNonKbdEvents
- 	"We do NOT use 'isKeybdEvent: ' here,
- 	 as that would have us flush key press-release events,
- 	 which is not appropriate when flushing non-keyboard events."
- 	self eventQueue ifNotNil:
- 		[:queue |
- 		 queue flushAllSuchThat: [:buf | (self isAnyKbdEvent: buf) not]]!

Item was changed:
  ----- Method: EventSensor>>initialize (in category 'initialize') -----
  initialize
+ 
- 	"Initialize the receiver"
  	mouseButtons := 0.
+ 	mousePosition := 0 at 0.
+ 	mouseWheelDelta := 0 at 0.
- 	mousePosition := 0 @ 0.
- 	mouseWheelDelta := 0 @ 0.
  	keyboardBuffer := SharedQueue new.
+ 	
+ 	interruptKey := $. asciiValue bitOr: 16r0800. 	"cmd-."
+ 	interruptSemaphore := Semaphore new.
+ 	
+ 	eventQueue := SharedQueue new.
+ 	
- 	self setInterruptKey: (interruptKey ifNil: [$. asciiValue bitOr: 16r0800 ]). 	"cmd-."
- 	interruptSemaphore := (Smalltalk specialObjectsArray at: 31) ifNil: [Semaphore new].
- 	self flushAllButDandDEvents.
  	inputSemaphore := Semaphore new.
  	hasInputSemaphore := false.!

Item was changed:
  ----- Method: EventSensor>>installInterruptWatcher (in category 'user interrupts') -----
  installInterruptWatcher
  	"Initialize the interrupt watcher process. Terminate the old process if any."
  	"Sensor installInterruptWatcher"
  
  	InterruptWatcherProcess ifNotNil: [InterruptWatcherProcess terminate].
+ 	InterruptWatcherProcess := [self userInterruptWatcher] forkAt: Processor lowIOPriority.!
- 	InterruptSemaphore := Semaphore new.
- 	InterruptWatcherProcess := [self userInterruptWatcher] forkAt: Processor lowIOPriority.
- 	self primInterruptSemaphore: InterruptSemaphore.!

Item was removed:
- ----- Method: EventSensor>>kbdTest (in category 'keyboard') -----
- kbdTest    "Sensor kbdTest"
- 	"This test routine will print the unmodified character, its keycode,
- 	and the OR of all its modifier bits, until the character x is typed"
- 	| char evt |
- 	char := nil.
- 	[char = $x] whileFalse: 
- 		[[(evt := self peekKeyboardEvent) isNil] whileTrue.
- 		char := self characterForKeycode: evt third.
- 		(String streamContents: 
- 			[:s |
- 			s nextPut: char.
- 			(3 to: 8) with: 'cpmurw' do:
- 				[:i :c|
- 				s space; nextPut: c; nextPut: $:; print: (evt at: i); nextPutAll: '     ']])
- 			displayAt: 10 at 10]!

Item was removed:
- ----- Method: EventSensor>>keyboard (in category 'keyboard') -----
- keyboard
- 	"Answer the next character from the keyboard."
- 
- 	| firstCharacter secondCharactor stream multiCharacter converter |
- 	firstCharacter := self characterForKeycode: self primKbdNext.
- 	secondCharactor := self peekKeyboard.
- 	secondCharactor isNil
- 		ifTrue: [^ firstCharacter].
- 	converter := TextConverter defaultSystemConverter.
- 	converter isNil
- 		ifTrue: [^ firstCharacter].
- 	stream := ReadStream
- 				on: (String with: firstCharacter with: secondCharactor).
- 	multiCharacter := converter nextFromStream: stream.
- 	multiCharacter isOctetCharacter
- 		ifTrue: [^ multiCharacter].
- 	self primKbdNext.
- 	^ multiCharacter
- !

Item was removed:
- ----- Method: EventSensor>>keyboardPressed (in category 'keyboard') -----
- keyboardPressed
- 	"Answer true if keystrokes are available."
- 
- 	^self peekKeyboard notNil!

Item was changed:
  ----- Method: EventSensor>>nextEvent (in category 'accessing') -----
  nextEvent
+ 	"Return the next event from the receiver. If the queue is empty, try to fetch more events once."
- 	"Return the next event from the receiver."
  
  	^ self eventQueue 
+ 		ifNil: [
+ 			self fetchMoreEvents.
+ 			self nextEventSynthesized]
+ 		ifNotNil: [:queue |
+ 			keyboardBuffer flush.
+ 			mouseWheelDelta := 0 at 0.
+ 			queue isEmpty ifTrue: [self fetchMoreEvents].
+ 			queue nextOrNil]!
- 		ifNil: [self nextEventSynthesized]
- 		ifNotNil: [self nextEventFromQueue]
- !

Item was removed:
- ----- Method: EventSensor>>nextEventFromQueue (in category 'private') -----
- nextEventFromQueue
- 	"Return the next event from the receiver. If the queue is empty, try to fetch more events once."
- 
- 	self eventQueue isEmpty
- 		ifTrue: [self fetchMoreEvents].
- 
- 	^ self eventQueue isEmpty
- 		ifTrue: [nil]
- 		ifFalse: [self eventQueue next]!

Item was changed:
  ----- Method: EventSensor>>nextEventSynthesized (in category 'private') -----
  nextEventSynthesized
- 	"Return a synthesized event. This method is called if an event driven client wants to receive events but the primary user interface is not event-driven (e.g., the receiver does not have an event queue but only updates its state). This can, for instance, happen if a Morphic World is run in an MVC window. To simplify the clients work this method will always return all available keyboard events first, and then (repeatedly) the mouse events. Since mouse events come last, the client can assume that after one mouse event has been received there are no more to come. Note that it is impossible for EventSensor to determine if a mouse event has been issued before so the client must be aware of the possible problem of getting repeatedly the same mouse events. See HandMorph>>processEvents for an example on how to deal with this."
- 	| kbd array buttons pos modifiers mapped |
- 	"First check for keyboard"
- 	array := Array new: 8.
- 	kbd := self primKbdNext.
- 	kbd ifNotNil:
- 		["simulate keyboard event"
- 		array at: 1 put: EventTypeKeyboard. "evt type"
- 		array at: 2 put: Time eventMillisecondClock. "time stamp"
- 		array at: 3 put: (kbd bitAnd: 255). "char code"
- 		array at: 4 put: EventKeyChar. "key press/release"
- 		array at: 5 put: (kbd bitShift: -8). "modifier keys"
- 		^ array].
  
+ 	| synthesizedEvent |
+ 	synthesizedEvent := self peekEventSynthesized.
+ 	keyboardBuffer nextOrNil.
+ 	^ synthesizedEvent!
- 	"Then check for mouse"
- 	pos := self peekPosition.
- 	buttons := mouseButtons.
- 	modifiers := buttons bitShift: -3.
- 	buttons := buttons bitAnd: 7.
- 	mapped := self mapButtons: buttons modifiers: modifiers.
- 	array 
- 		at: 1 put: EventTypeMouse;
- 		at: 2 put: Time eventMillisecondClock;
- 		at: 3 put: pos x;
- 		at: 4 put: pos y;
- 		at: 5 put: mapped;
- 		at: 6 put: modifiers.
- 	^ array
- 
- !

Item was removed:
- ----- Method: EventSensor>>peekButtons (in category 'accessing') -----
- peekButtons
- 	self fetchMoreEvents.
- 	self flushNonKbdEvents.
- 	^ mouseButtons!

Item was changed:
  ----- Method: EventSensor>>peekEvent (in category 'accessing') -----
  peekEvent
  	"Look ahead at the next event. Try to fetch more events first."
  
  	^ self eventQueue
+ 		ifNil: [
- 		ifNil: [nil]
- 		ifNotNil: [:queue |
  			self fetchMoreEvents.
+ 			self peekEventSynthesized]
+ 		ifNotNil: [:queue |
+ 			queue isEmpty ifTrue: [self fetchMoreEvents].
  			queue peek]!

Item was added:
+ ----- Method: EventSensor>>peekEventSynthesized (in category 'private') -----
+ peekEventSynthesized
+ 	"Return a synthesized event. This method is called if an event driven client wants to receive events but the primary user interface is not event-driven (e.g., the receiver does not have an event queue but only updates its state). This can, for instance, happen if a Morphic World is run in an MVC window. To simplify the clients work this method will always return all available keyboard events first, and then (repeatedly) the mouse events. Since mouse events come last, the client can assume that after one mouse event has been received there are no more to come. Note that it is impossible for EventSensor to determine if a mouse event has been issued before so the client must be aware of the possible problem of getting repeatedly the same mouse events. See HandMorph>>processEvents for an example on how to deal with this."
+ 	| kbd array buttons pos modifiers mapped |
+ 	"First check for keyboard"
+ 	array := Array new: 8.
+ 	keyboardBuffer isEmpty ifFalse:
+ 		["simulate keyboard event"
+ 		array at: 1 put: EventTypeKeyboard. "evt type"
+ 		array at: 2 put: Time eventMillisecondClock. "time stamp"
+ 		array at: 3 put: ((kbd := keyboardBuffer peek) bitAnd: 255). "char code"
+ 		array at: 4 put: EventKeyChar. "key press/release"
+ 		array at: 5 put: (kbd bitShift: -8). "modifier keys"
+ 		^ array].
+ 
+ 	"Then check for mouse"
+ 	pos := mousePosition.
+ 	buttons := mouseButtons.
+ 	modifiers := buttons bitShift: -3.
+ 	buttons := buttons bitAnd: 7.
+ 	mapped := self mapButtons: buttons modifiers: modifiers.
+ 	array 
+ 		at: 1 put: EventTypeMouse;
+ 		at: 2 put: Time eventMillisecondClock;
+ 		at: 3 put: pos x;
+ 		at: 4 put: pos y;
+ 		at: 5 put: mapped;
+ 		at: 6 put: modifiers.
+ 	^ array
+ 
+ !

Item was removed:
- ----- Method: EventSensor>>peekKeyboard (in category 'keyboard') -----
- peekKeyboard
- 	"Answer the next character in the keyboard buffer without removing it, or nil if it is empty."
- 
- 	| char |
- 	self fetchMoreEvents.
- 	keyboardBuffer isEmpty ifFalse: [^ self characterForKeycode: keyboardBuffer peek].
- 	char := nil.
- 	self eventQueue ifNotNil: [:queue |
- 		queue nextOrNilSuchThat:  "NOTE: must not return out of this block, so loop to end"
- 			[:buf | (self isKbdEvent: buf) ifTrue: [char ifNil: [char := buf at: 3]].
- 			false  "NOTE: block value must be false so Queue won't advance"]].
- 	^ self characterForKeycode: char!

Item was removed:
- ----- Method: EventSensor>>peekKeyboardEvent (in category 'accessing') -----
- peekKeyboardEvent
- 	"Return the next keyboard char event from the receiver or nil if none available"
- 	
- 	^ self eventQueue
- 		ifNil: [nil]
- 		ifNotNil: [:queue |
- 			self fetchMoreEvents.
- 			queue nextOrNilSuchThat: [:buf | 
- 				buf first = EventTypeKeyboard and: [(buf fourth) = EventKeyChar]]]!

Item was removed:
- ----- Method: EventSensor>>peekPosition (in category 'accessing') -----
- peekPosition
- 	self fetchMoreEvents.
- 	"self flushNonKbdEvents. -- mt: Should not be necessary here."
- 	^ mousePosition!

Item was removed:
- ----- Method: EventSensor>>peekWheelDelta (in category 'accessing') -----
- peekWheelDelta
- 	self fetchMoreEvents.
- 	^ mouseWheelDelta!

Item was changed:
+ ----- Method: EventSensor>>primCursorLocPut: (in category 'private-I/O') -----
- ----- Method: EventSensor>>primCursorLocPut: (in category 'primitives-cursor') -----
  primCursorLocPut: aPoint
  	"If the primitive fails, try again with a rounded point."
  
  	<primitive: 91>
  	^ self primCursorLocPutAgain: aPoint rounded!

Item was changed:
+ ----- Method: EventSensor>>primCursorLocPutAgain: (in category 'private-I/O') -----
- ----- Method: EventSensor>>primCursorLocPutAgain: (in category 'primitives-cursor') -----
  primCursorLocPutAgain: aPoint
  	"Do nothing if primitive is not implemented."
  
  	<primitive: 91>
  	^ self!

Item was removed:
- ----- Method: EventSensor>>primInterruptSemaphore: (in category 'private') -----
- primInterruptSemaphore: aSemaphore 
- 	"Primitive. Install the argument as the semaphore to be signalled whenever the user presses the interrupt key. The semaphore will be signaled once each time the interrupt key is pressed."
- 	interruptSemaphore := aSemaphore.
- 	"backward compatibility: use the old primitive which is obsolete now"
- 	self oldPrimInterruptSemaphore: aSemaphore!

Item was removed:
- ----- Method: EventSensor>>primKbdNext (in category 'private') -----
- primKbdNext
- 	"Allows for use of old Sensor protocol to get at the keyboard,
- 	as when running kbdTest or the InterpreterSimulator in Morphic"
- 	| evtBuf |
- 	
- 	self flag: #refactor. "mt: Suspiciously similar to #peekKeyboardEvent"
- 	self fetchMoreEvents.
- 	keyboardBuffer isEmpty ifFalse:[^ keyboardBuffer next].
- 	self eventQueue ifNotNil: [:queue |
- 		evtBuf := queue nextOrNilSuchThat: [:buf | self isKbdEvent: buf].
- 		self flushNonKbdEvents].
- 	^ evtBuf ifNotNil: [evtBuf at: 3]
- !

Item was removed:
- ----- Method: EventSensor>>primSetInterruptKey: (in category 'private') -----
- primSetInterruptKey: anInteger
- 	"Primitive. Register the given keycode as the user interrupt key. The low byte of the keycode is the ISO character and its next four bits are the Smalltalk modifer bits <cmd><opt><ctrl><shift>."
- 	interruptKey := anInteger.
- 	"backward compatibility: use the old primitive which is obsolete now"
- 	self oldPrimSetInterruptKey: anInteger!

Item was changed:
  ----- Method: EventSensor>>processEvent: (in category 'private-I/O') -----
  processEvent: evt 
  	"Process a single event. This method is run at high priority."
  	| type buttons window |
  	type := evt at: 1.
  
  	"Only process main window events, forward others to host window proxies"
  	window := evt at: 8.
  	(window isNil or: [window isZero]) ifTrue: 
  		[window := 1. 
  		evt at: 8 put: window].
  	window = 1 ifFalse: [
  		^Smalltalk at: #HostWindowProxy ifPresent: [:w | w processEvent: evt]].
  
  	"Tackle mouse events and mouse wheel events first"
  	(type = EventTypeMouse or: [type = EventTypeMouseWheel])
  		ifTrue: [buttons := (ButtonDecodeTable at: (evt at: 5) + 1). 
  				evt at: 5 put: (Smalltalk platformName = 'Mac OS'
  							ifTrue: [ buttons ]
  							ifFalse: [ self mapButtons: buttons modifiers: (evt at: 6) ]).
  				self queueEvent: evt.
+ 				type = EventTypeMouseWheel
+ 					ifTrue: [^ self processMouseWheelEvent: evt].				
+ 				type = EventTypeMouse
+ 					ifTrue: [^ self processMouseEvent: evt]].
- 				type = EventTypeMouse ifTrue: [self processMouseEvent: evt].
- 				type = EventTypeMouseWheel ifTrue: [self processMouseWheelEvent: evt].				
- 				^self].
  	
  	"Store the event in the queue if there's any"
  	type = EventTypeKeyboard
  		ifTrue: [ "Check if the event is a user interrupt"
  			((evt at: 4) = EventKeyChar
  				and: [((evt at: 3)
  						bitOr: (((evt at: 5)
  							bitAnd: 8)
  							bitShift: 8))
  							= interruptKey])
  					ifTrue: ["interrupt key is meta - not reported as event"
  							^ interruptSemaphore signal].
  			"Decode keys for characters (i.e., duplicate or swap, ctrl <-> alt/cmd)."
  			(evt at: 4) = EventKeyChar
  				ifTrue: [ | unicode ascii |
  					"Copy lookup key first in case of key swap."
  					unicode := {evt at: 6. evt at: 5}.
  					ascii := {evt at: 3. evt at: 5}.
  					KeyDecodeTable "Unicode character first"
  						at: unicode
  						ifPresent: [:a | evt at: 6 put: a first;
  								 at: 5 put: a second]. 
  					KeyDecodeTable "ASCII character second"
  						at: ascii
  						ifPresent: [:a | evt at: 3 put: a first;
  								 at: 5 put: a second]]. 
  			self queueEvent: evt. 
  			self processKeyboardEvent: evt . 
  			^self ].
  				
  	"Handle all events other than Keyboard or Mouse."
  	self queueEvent: evt.
  	!

Item was changed:
  ----- Method: EventSensor>>processKeyboardEvent: (in category 'private-I/O') -----
  processKeyboardEvent: evt
  	"process a keyboard event, updating EventSensor state"
  	| charCode pressCode |
  	"Never update keyboardBuffer if we have an eventQueue active"
  	mouseButtons := (mouseButtons bitAnd: 7) bitOr: ((evt at: 5) bitShift: 3).
+ 	
- 	self eventQueue ifNotNil:[^self]. 
  	charCode := evt at: 3.
  	charCode = nil ifTrue:[^self]. "extra characters not handled in MVC"
  	pressCode := evt at: 4.
  	pressCode = EventKeyChar ifFalse:[^self]. "key down/up not handled in MVC"
  	"mix in modifiers"
  	charCode := charCode bitOr: ((evt at: 5) bitShift: 8).
  	keyboardBuffer nextPut: charCode.!

Item was changed:
  ----- Method: EventSensor>>processMouseWheelEvent: (in category 'private-I/O') -----
  processMouseWheelEvent: evt
  	"process a mouse wheel event, updating EventSensor state"
  	
  	| modifiers buttons mapped |
+ 	mouseWheelDelta := mouseWheelDelta + ((evt at: 3) @ (evt at: 4)).
- 	mouseWheelDelta := (evt at: 3) @ (evt at: 4).
  	buttons := evt at: 5.
  	modifiers := evt at: 6.
  	mapped := self mapButtons: buttons modifiers: modifiers.
  	mouseButtons := mapped bitOr: (modifiers bitShift: 3).!

Item was removed:
- ----- Method: EventSensor>>setInterruptKey: (in category 'user interrupts') -----
- setInterruptKey: anInteger
- 	"Register the given keycode as the user interrupt key."
- 
- 	self primSetInterruptKey: anInteger.
- !

Item was changed:
  ----- Method: EventSensor>>startUp (in category 'initialize') -----
  startUp
  
  	self initialize.
  	self primSetInputSemaphore: (Smalltalk registerExternalObject: inputSemaphore).
  
  	self installInterruptWatcher.
  	self installEventTickler.
  
+ 	self eventQueue: SharedQueue new.
- 	Smalltalk isMorphic ifTrue: [self flushAllButDandDEvents].
  
  	"Attempt to discover whether the input semaphore is actually being signaled."
  	hasInputSemaphore := false.
  	inputSemaphore initSignals.!

Item was changed:
  ----- Method: EventSensor>>userInterruptWatcher (in category 'user interrupts') -----
  userInterruptWatcher
  	"Wait for user interrupts and open a notifier on the active process when one occurs."
+ 	[ interruptSemaphore wait.
- 	[ InterruptSemaphore wait.
  	Display deferUpdates: false.
  	SoundService stop.
  	Smalltalk handleUserInterrupt ] repeat!



More information about the Squeak-dev mailing list