[GOODIE] KeyBinder - SystemWindow Switcher

Hernan Tylim htylim at yahoo.com.ar
Sun Aug 8 06:33:31 UTC 2004


Hi, 
	A couple of days ago someone asked on this list if it was
possible to switch between SystemWindows in squeak like you do in
Windows.

	Well, before wasn't posible, now it is. I present to you
KeyBinder. 

	The idea behind KeyBinder is to provide a mechanism for
assigning global key bindings. KeyBinder does this by changing the way
Squeak handles Keyboard events, it basically adds to HandMorph the
ability to manage more than 1 keyboard focus. The main advantage of this
approach is that it can capture any keyboard event that is generated on
Squeak.

	As a proof on concept for KeyBinder I made a KeyBinding for
switching between SystemWindows. With <cmd>-\ (backslash) you will be
able to switch forward, while with <cmd>-| (pipe) you will be able to
switch backwards.

	To test KeyBinder just file it in and from a Workspace evaluate:
"KeyBinder new openInWorld". A tiny green rectangle will appear on the
top left corner of the World. Click on the rectangle with the right
mouse button and select: 'add Window Switcher' to enable the key binding
of window switching, and that's it. Try it and have fun.

	And please (please!) tell me what you think about it.

Thanks

ps: 3:32 am, time to go to sleep.


Saludos,
Hernán 
-------------- next part --------------
'From Squeak3.7gamma of ''17 July 2004'' [latest update: #5985] on 8 August 2004 at 3:00:46 am'!
"Change Set:		KeyBinder-hpt
Date:			8 August 2004
Author:			Hernan Tylim

Here in Argentina are 3 am and this is not time for writing preambles, so please look at the code and treat it as a proof of concept.

After filing in evaluate: KeyBinder new openInWorld and a little box will appear on the topLeft corner of your desktop, Click on the morph with the right (yellow) mouse button and select: 'add Window Switcher'. To switch forward hit <cmd>-\ (backslash) and to switch backwards hit <cmd>-| (pipe).
"!

Morph subclass: #HandMorph
	instanceVariableNames: 'mouseFocus keyboardFocus eventListeners mouseListeners keyboardListeners mouseClickState mouseOverHandler lastMouseEvent targetOffset damageRecorder cacheCanvas cachedCanvasHasHoles temporaryCursor temporaryCursorOffset hasChanged savedPatch userInitials lastEventBuffer genieGestureProcessor additionalKeyboardFocuses '
	classVariableNames: 'DoubleClickTime EventStats NewEventRules NormalCursor PasteBuffer ShowEvents '
	poolDictionaries: 'EventSensorConstants'
	category: 'Morphic-Kernel'!
BorderedMorph subclass: #KeyBinder
	instanceVariableNames: 'keyBindings enabled'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'KeyBinder'!
Object subclass: #KeyBinding
	instanceVariableNames: 'enabled'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'KeyBinder'!
Smalltalk renameClassNamed: #WindowSwicherKeyBinding as: #WindowSwitcherKeyBinding!
KeyBinding subclass: #WindowSwitcherKeyBinding
	instanceVariableNames: 'windows last'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'KeyBinder'!

!HandMorph methodsFor: 'focus handling' stamp: 'hpt 8/8/2004 01:52'!
addAdditionalKeyboardFocus: aMorph
	(self additionalKeyboardFocuses includes: aMorph)
		ifFalse: [self additionalKeyboardFocuses add: aMorph]! !

!HandMorph methodsFor: 'focus handling' stamp: 'hpt 8/7/2004 23:47'!
additionalKeyboardFocuses
	^additionalKeyboardFocuses ifNil: [additionalKeyboardFocuses _ OrderedCollection new].! !

!HandMorph methodsFor: 'focus handling' stamp: 'hpt 8/8/2004 00:12'!
clearFocusHolder: aMorph
	self keyboardFocus == aMorph
		ifTrue: 	[^self keyboardFocus: nil].
	(self additionalKeyboardFocuses includes: aMorph)
		ifTrue: [self removeAdditionalKeyboardFocus: aMorph].! !

!HandMorph methodsFor: 'focus handling' stamp: 'hpt 8/7/2004 23:48'!
fullKeyboardFocuses
	^self additionalKeyboardFocuses copyWith: self keyboardFocus.! !

!HandMorph methodsFor: 'focus handling' stamp: 'hpt 8/7/2004 23:43'!
keyboardFocuses
	keyboardFocuses ifNil: [keyboardFocuses := OrderedCollection new].
	^keyboardFocuses! !

!HandMorph methodsFor: 'focus handling' stamp: 'hpt 8/7/2004 23:49'!
removeAdditionalKeyboardFocus: aMorph
	self additionalKeyboardFocuses remove: aMorph! !

!HandMorph methodsFor: 'private events' stamp: 'hpt 8/8/2004 01:18'!
sendFocusEvent: anEvent to: focusHolder clear: aBlock
	"Send the event to the morph currently holding the focus"
	| result w e |
	w _ focusHolder world ifNil:[^ aBlock value].
	w becomeActiveDuring:[
		ActiveHand _ self.
		ActiveEvent _ anEvent.
		e _ (anEvent transformedBy: (focusHolder transformedFrom: self)).
		result _ focusHolder handleFocusEvent: e	.
		anEvent wasHandled: e wasHandled.
	].
	^result! !

!HandMorph methodsFor: 'private events' stamp: 'hpt 8/8/2004 01:09'!
sendKeyboardEvent: anEvent
	"Send the event to the morph currently holding the focus, or if none to the owner of the hand."

	self fullKeyboardFocuses do: [:focusHolder |
		"(anEvent keyCharacter = $\) ifTrue: [self halt]."
		anEvent wasHandled
			ifFalse: [self sendEvent: anEvent focus: focusHolder clear:[self clearFocusHolder: focusHolder]]].! !


!KeyBinder methodsFor: 'initialization' stamp: 'hpt 8/8/2004 02:52'!
initialize
	super initialize.
	keyBindings _ OrderedCollection new.
	self registerAsAdditionalFocusHolder.
	self borderWidth: 1.
	self extent: 15 at 15.
	self updateColor.! !

!KeyBinder methodsFor: 'initialization' stamp: 'hpt 8/8/2004 01:03'!
registerAsAdditionalFocusHolder
	self activeHand addAdditionalKeyboardFocus: self.! !

!KeyBinder methodsFor: 'initialization' stamp: 'hpt 8/8/2004 02:50'!
updateColor
	self enabled
		ifTrue: [self color: Color green muchLighter]
		ifFalse: [self color: Color red muchLighter]! !

!KeyBinder methodsFor: 'key bindings' stamp: 'hpt 8/8/2004 00:28'!
addKeyBinding: aKeyBinding
	keyBindings add: aKeyBinding! !

!KeyBinder methodsFor: 'key bindings' stamp: 'hpt 8/8/2004 02:39'!
availableKeyBindingsForAddition
	| alreadyHave forAddition |
	alreadyHave _ self keyBindings collect: [:ea | ea class].
	forAddition _ KeyBinding allSubclasses difference: alreadyHave.
	^forAddition collect: [:ea | ea new].! !

!KeyBinder methodsFor: 'key bindings' stamp: 'hpt 8/8/2004 02:30'!
keyBindings
	^keyBindings ifNil: [keyBindings _ OrderedCollection new]! !

!KeyBinder methodsFor: 'key bindings' stamp: 'hpt 8/8/2004 00:42'!
keyBindingsForEvent: anEvent
	^keyBindings select: [:aKeyBinding | aKeyBinding handlesEvent: anEvent]! !

!KeyBinder methodsFor: 'event handling' stamp: 'hpt 8/8/2004 02:16'!
handlesKeyboard: anEvent
	^self enabled and: [(self keyBindingsForEvent: anEvent) notEmpty]! !

!KeyBinder methodsFor: 'event handling' stamp: 'hpt 8/8/2004 02:09'!
handlesMouseDown: anEvent
	^anEvent yellowButtonPressed! !

!KeyBinder methodsFor: 'event handling' stamp: 'hpt 8/8/2004 01:04'!
keyStroke: anEvent
	(self keyBindingsForEvent: anEvent) do: [:aKeyBinding | aKeyBinding handleEvent: anEvent].! !

!KeyBinder methodsFor: 'event handling' stamp: 'hpt 8/8/2004 02:11'!
mouseDown: anEvent
	self invokeMenu: anEvent! !

!KeyBinder methodsFor: 'menu' stamp: 'hpt 8/8/2004 02:45'!
addKeyBindingsForAdditionToMenu: aMenu
	self availableKeyBindingsForAddition do: [:aKeyBinding |
		aMenu 
			add: 'add ', aKeyBinding name
			selector: #addKeyBinding:
			argument: aKeyBinding]! !

!KeyBinder methodsFor: 'menu' stamp: 'hpt 8/8/2004 02:32'!
addKeyBindingsToMenu: aMenu
	self keyBindings do: [:ea |
		aMenu 
			addUpdating: #enableOptionString 
			target: ea 
			selector: #toggleEnable 
			argumentList: EmptyArray]! !

!KeyBinder methodsFor: 'menu' stamp: 'hpt 8/8/2004 02:17'!
enableOptionString
	^(self enabled
		ifTrue: ['<yes>']
		ifFalse: ['<no>']), 'KeyBinder enabled'.! !

!KeyBinder methodsFor: 'menu' stamp: 'hpt 8/8/2004 02:46'!
invokeMenu: anEvent
	| aMenu |
	aMenu _ MenuMorph new
		defaultTarget: self;
		yourself.
	aMenu 
		addUpdating: #enableOptionString action: #toggleEnable;
		addLine.
	self addKeyBindingsToMenu: aMenu.
	aMenu 
		addLine.
	self addKeyBindingsForAdditionToMenu: aMenu.
	aMenu
		addLine.
	aMenu
		add: 'exit' action: #delete.
	aMenu popUpEvent: anEvent in: self world.! !

!KeyBinder methodsFor: 'accessing' stamp: 'hpt 8/8/2004 02:50'!
disable
	enabled _ false.
	self updateColor.! !

!KeyBinder methodsFor: 'accessing' stamp: 'hpt 8/8/2004 02:49'!
disabled
	^self enabled not.! !

!KeyBinder methodsFor: 'accessing' stamp: 'hpt 8/8/2004 02:48'!
enable
	enabled _ true.
	self updateColor.! !

!KeyBinder methodsFor: 'accessing' stamp: 'hpt 8/8/2004 02:15'!
enabled
	^enabled ifNil: [enabled _ true].! !

!KeyBinder methodsFor: 'accessing' stamp: 'hpt 8/8/2004 02:18'!
toggleEnable
	self enabled
		ifTrue: [self disable]
		ifFalse: [self enable]! !


!KeyBinding methodsFor: 'event handling' stamp: 'hpt 8/8/2004 00:30'!
handleEvent: anEvent
	self subclassResponsibility ! !

!KeyBinding methodsFor: 'event handling' stamp: 'hpt 8/8/2004 02:33'!
handlesEvent: anEvent
	^self enabled! !

!KeyBinding methodsFor: 'accessing' stamp: 'hpt 8/8/2004 02:25'!
disable
	enabled _ false.! !

!KeyBinding methodsFor: 'accessing' stamp: 'hpt 8/8/2004 02:25'!
disabled
	^self enabled not! !

!KeyBinding methodsFor: 'accessing' stamp: 'hpt 8/8/2004 02:25'!
enable
	enabled _ true! !

!KeyBinding methodsFor: 'accessing' stamp: 'hpt 8/8/2004 02:35'!
enableOptionString
	^(self enabled
		ifTrue: ['<yes>']
		ifFalse: ['<no>']), self name, ' enabled'.! !

!KeyBinding methodsFor: 'accessing' stamp: 'hpt 8/8/2004 02:25'!
enabled
	^enabled ifNil: [enabled _ true]! !

!KeyBinding methodsFor: 'accessing' stamp: 'hpt 8/8/2004 02:25'!
name
	^self className.! !

!KeyBinding methodsFor: 'accessing' stamp: 'hpt 8/8/2004 02:34'!
toggleEnable
	self enabled
		ifTrue: [self disable]
		ifFalse: [self enable].! !


!WindowSwitcherKeyBinding methodsFor: 'event handling' stamp: 'hpt 8/8/2004 00:38'!
activeSystemWindow
	^self systemWindows detect: [:aWindow | aWindow isActive]! !

!WindowSwitcherKeyBinding methodsFor: 'event handling' stamp: 'hpt 8/8/2004 02:22'!
currentWindow
	^self windows detect: [:ea | ea isActive].! !

!WindowSwitcherKeyBinding methodsFor: 'event handling' stamp: 'hpt 8/8/2004 02:05'!
handleEvent: anEvent
	| w | 
	anEvent wasHandled: true.
	w _ anEvent keyCharacter = $|
			ifTrue: [self prevWindow]
			ifFalse: [self nextWindow].
	w ifNotNil: [w activate].! !

!WindowSwitcherKeyBinding methodsFor: 'event handling' stamp: 'hpt 8/8/2004 02:33'!
handlesEvent: anEvent
	^(super handlesEvent: anEvent) 
		and: [	((anEvent commandKeyPressed & (anEvent keyCharacter = $\)) | 
				(anEvent commandKeyPressed & (anEvent keyCharacter = $|)))]! !

!WindowSwitcherKeyBinding methodsFor: 'event handling' stamp: 'hpt 8/8/2004 02:21'!
nextWindow
	| w current |
	current _ self currentWindow.
	w _ self windows.
	w isEmpty 
		ifTrue: [nil].
	last 
		ifNil: [w first].
	^(w last == current) 
			ifTrue: [w first] 
			ifFalse: [w after: current ifAbsent: [w first]]! !

!WindowSwitcherKeyBinding methodsFor: 'event handling' stamp: 'hpt 8/8/2004 02:21'!
prevWindow
	| w current |
	current _ self currentWindow.
	w _ self windows.
	w isEmpty 
		ifTrue: [nil].
	current
		ifNil: [w first].
	^(w first == current)
			ifTrue: [w last]
			ifFalse: [w before: current ifAbsent: [w last]]
	
	! !

!WindowSwitcherKeyBinding methodsFor: 'event handling' stamp: 'hpt 8/8/2004 01:44'!
windows
	| w |
	w _ ActiveWorld submorphs select: [:aMorph | aMorph renderedMorph isSystemWindow].
	windows addAll: (w difference: windows).
	windows removeAll: (windows difference: w).
	^windows.! !

!WindowSwitcherKeyBinding methodsFor: 'initialization' stamp: 'hpt 8/8/2004 01:39'!
initialize
	windows _ OrderedCollection new.
	direction _ #forward! !

!WindowSwitcherKeyBinding methodsFor: 'accessing' stamp: 'hpt 8/8/2004 02:35'!
name
	^'Window Switcher'! !

WindowSwitcherKeyBinding removeSelector: #systemWindows!
WindowSwitcherKeyBinding removeSelector: #toggleDirection!
WindowSwitcherKeyBinding removeSelector: #updateWindows!

!WindowSwitcherKeyBinding reorganize!
('event handling' activeSystemWindow currentWindow handleEvent: handlesEvent: nextWindow prevWindow windows)
('initialization' initialize)
('accessing' name)
!

KeyBinding removeSelector: #menuOptionString!

!KeyBinding reorganize!
('event handling' handleEvent: handlesEvent:)
('accessing' disable disabled enable enableOptionString enabled name toggleEnable)
!

KeyBinder removeSelector: #availableKeyBindings!
KeyBinder removeSelector: #keystroke:!

!KeyBinder reorganize!
('initialization' initialize registerAsAdditionalFocusHolder updateColor)
('key bindings' addKeyBinding: availableKeyBindingsForAddition keyBindings keyBindingsForEvent:)
('event handling' handlesKeyboard: handlesMouseDown: keyStroke: mouseDown:)
('menu' addKeyBindingsForAdditionToMenu: addKeyBindingsToMenu: enableOptionString invokeMenu:)
('accessing' disable disabled enable enabled toggleEnable)
!

HandMorph removeSelector: #addKeyboarFocus:!
HandMorph removeSelector: #removeKeyboarFocus:!
Morph subclass: #HandMorph
	instanceVariableNames: 'mouseFocus keyboardFocus eventListeners mouseListeners keyboardListeners mouseClickState mouseOverHandler lastMouseEvent targetOffset damageRecorder cacheCanvas cachedCanvasHasHoles temporaryCursor temporaryCursorOffset hasChanged savedPatch userInitials lastEventBuffer genieGestureProcessor additionalKeyboardFocuses'
	classVariableNames: 'DoubleClickTime EventStats NewEventRules NormalCursor PasteBuffer ShowEvents'
	poolDictionaries: 'EventSensorConstants'
	category: 'Morphic-Kernel'!


More information about the Squeak-dev mailing list