| 123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697 | Smalltalk current createPackage: 'Helios-KeyBindings'!Object subclass: #HLBinding	instanceVariableNames: 'key label'	package: 'Helios-KeyBindings'!!HLBinding methodsFor: 'accessing'!atKey: aKey	^ nil!displayLabel	^ self label!key	^ key!key: anInteger	key := anInteger!label	^ label!label: aString	label := aString!shortcut	^ String fromCharCode: self key! !!HLBinding methodsFor: 'actions'!applyOn: aKeyBinder!release! !!HLBinding methodsFor: 'rendering'!renderActionFor: aBinder html: html	html span class: 'command'; with: [		html span 			class: 'label'; 			with: self shortcut asLowercase.  		html a         	class: 'action';             with: self displayLabel;  			onClick: [ aBinder applyBinding: self ] ]!renderOn: aBindingHelper html: html! !!HLBinding methodsFor: 'testing'!isActive	^ self subclassResponsibility!isFinal	" Answer true if the receiver is the final binding of a sequence "		^ false! !!HLBinding class methodsFor: 'instance creation'!on: anInteger labelled: aString	^ self new    	key: anInteger;        label: aString;        yourself! !HLBinding subclass: #HLBindingAction	instanceVariableNames: 'command'	package: 'Helios-KeyBindings'!!HLBindingAction methodsFor: 'accessing'!command	^ command!command: aCommand	command := aCommand!inputBinding	^ HLBindingInput new		label: self command inputLabel;		ghostText: self command displayLabel;		defaultValue: self command defaultInput;		inputCompletion: self command inputCompletion;		callback: [ :val | 			self command 				input: val;				execute ];		yourself! !!HLBindingAction methodsFor: 'actions'!applyOn: aKeyBinder	self command isInputRequired		ifTrue: [ aKeyBinder selectBinding: self inputBinding ]		ifFalse: [ self command execute ]! !!HLBindingAction methodsFor: 'testing'!isActive	^ self command isActive!isFinal	^ self command isInputRequired not! !HLBinding subclass: #HLBindingGroup	instanceVariableNames: 'bindings'	package: 'Helios-KeyBindings'!!HLBindingGroup methodsFor: 'accessing'!activeBindings	^ self bindings select: [ :each | each isActive ]!add: aBinding	^ self bindings add: aBinding!addActionKey: anInteger labelled: aString callback: aBlock	self add: ((HLBindingAction on: anInteger labelled: aString)    	callback: aBlock;        yourself)!addGroupKey: anInteger labelled: aString	self add: (HLBindingGroup on: anInteger labelled: aString)!at: aString	^ self bindings     	detect: [ :each | each label = aString ]      	ifNone: [ nil ]!at: aString add: aBinding	| binding |		binding := self at: aString.	binding ifNil: [ ^ self ].			binding add: aBinding!atKey: anInteger	^ self bindings     	detect: [ :each | each key = anInteger ]      	ifNone: [ nil ]!bindings	^ bindings ifNil: [ bindings := OrderedCollection new ]!displayLabel	^ super displayLabel, '...'! !!HLBindingGroup methodsFor: 'actions'!release	self bindings do: [ :each | each release ]! !!HLBindingGroup methodsFor: 'rendering'!renderOn: aBindingHelper html: html	self isActive ifTrue: [		aBindingHelper renderBindingGroup: self on: html ]! !!HLBindingGroup methodsFor: 'testing'!isActive	^ self activeBindings notEmpty! !HLBinding subclass: #HLBindingInput	instanceVariableNames: 'input callback status wrapper binder ghostText isFinal message messageTag inputCompletion defaultValue'	package: 'Helios-KeyBindings'!!HLBindingInput methodsFor: 'accessing'!atKey: aKey	aKey = 13 ifFalse: [ ^ nil ]!callback	^ callback ifNil: [ callback := [ :value | ] ]!callback: aBlock	callback := aBlock!defaultValue	^ defaultValue ifNil: [ '' ]!defaultValue: aString	defaultValue := aString!ghostText	^ ghostText!ghostText: aText	ghostText := aText!input	^ input!inputCompletion	^ inputCompletion ifNil: [ #() ]!inputCompletion: aCollection	inputCompletion := aCollection!message	^ message ifNil: [ message := '' ]!message: aString	message := aString!status	^ status ifNil: [ status := 'info' ]!status: aStatus	status := aStatus! !!HLBindingInput methodsFor: 'actions'!applyOn: aKeyBinder	self isFinal: true.	self evaluate: self input asJQuery val!clearStatus	self status: 'info'.	self message: ''.	self refresh!errorStatus	self status: 'error'.	self refresh!evaluate: aString		[ self callback value: aString ]	on: Error	do: [:ex |		self input asJQuery 			one: 'keydown' 			do: [ self clearStatus ].		self message: ex messageText.		self errorStatus.		self isFinal: false ].!release	status := nil.	wrapper := nil.	binder := nil! !!HLBindingInput methodsFor: 'rendering'!refresh	wrapper ifNil: [ ^ self ].    	wrapper class: self status.	messageTag contents: self message!renderOn: aBinder html: html	binder := aBinder.	wrapper ifNil: [ wrapper := html span ].	wrapper 		class: self status;		with: [			input := html input				placeholder: self ghostText;				value: self defaultValue;				yourself.			input asJQuery 				typeahead: #{ 'source' -> self inputCompletion }.			messageTag := (html span				class: 'help-inline';				with: self message;				yourself) ].		"Evaluate with a timeout to ensure focus.	Commands can be executed from a menu, clicking on the menu to	evaluate the command would give it the focus otherwise"		[ input asJQuery focus ] valueWithTimeout: 10! !!HLBindingInput methodsFor: 'testing'!isActive	^ true!isFinal	^ isFinal ifNil: [ isFinal := super isFinal ]!isFinal: aBoolean	isFinal := aBoolean! !Object subclass: #HLKeyBinder	instanceVariableNames: 'modifierKey helper bindings selectedBinding'	package: 'Helios-KeyBindings'!!HLKeyBinder methodsFor: 'accessing'!activationKey	"SPACE"	^ 32!activationKeyLabel	^ 'ctrl + space'!bindings	^ bindings ifNil: [ bindings := self defaultBindings ]!escapeKey	"ESC"	^ 27!helper	^ helper!selectedBinding	^ selectedBinding ifNil: [ self bindings ]! !!HLKeyBinder methodsFor: 'actions'!activate	self helper show!applyBinding: aBinding	aBinding isActive ifFalse: [ ^ self ].		self selectBinding: aBinding.    aBinding applyOn: self.		aBinding isFinal ifTrue: [ self deactivate ]!deactivate	selectedBinding ifNotNil: [ selectedBinding release ].    selectedBinding := nil.	self helper hide!flushBindings	bindings := nil!selectBinding: aBinding	aBinding = selectedBinding ifTrue: [ ^ self ].		selectedBinding := aBinding.	self helper refresh! !!HLKeyBinder methodsFor: 'defaults'!defaultBindings	| group |		group := HLBindingGroup new		addGroupKey: 86 labelled: 'View';		add: HLCloseTabCommand new asBinding;		yourself.			HLOpenCommand registerConcreteClassesOn: group.					^ group! !!HLKeyBinder methodsFor: 'events'!handleActiveKeyDown: event	"ESC or ctrl+g deactivate the keyBinder"	(event which = self escapeKey or: [		event which = 71 and: [ event ctrlKey ] ])        	ifTrue: [             	self deactivate.				event preventDefault.				^ false ].                "Handle the keybinding"    ^ self handleBindingFor: event!handleBindingFor: anEvent	| binding |    binding := self selectedBinding atKey: anEvent which.        binding ifNotNil: [     	self applyBinding: binding.		anEvent preventDefault.		^ false ]!handleInactiveKeyDown: event	event which = self activationKey ifTrue: [    	event ctrlKey ifTrue: [			self activate.             event preventDefault.             ^ false ] ]!handleKeyDown: event	^ self isActive    	ifTrue: [ self handleActiveKeyDown: event ]      	ifFalse: [ self handleInactiveKeyDown: event ]!setupEvents	(window jQuery: 'body') keydown: [ :event | self handleKeyDown: event ]! !!HLKeyBinder methodsFor: 'initialization'!initialize	super initialize.	helper := HLKeyBinderHelper on: self.	helper 			renderStart;		renderCog! !!HLKeyBinder methodsFor: 'testing'!isActive	^ ('.', self helper cssClass) asJQuery is: ':visible'!systemIsMac	^ navigator platform match: 'Mac'! !HLWidget subclass: #HLKeyBinderHelper	instanceVariableNames: 'keyBinder'	package: 'Helios-KeyBindings'!!HLKeyBinderHelper methodsFor: 'accessing'!cssClass	^ 'key_helper'!keyBinder	^ keyBinder!keyBinder: aKeyBinder	keyBinder := aKeyBinder!selectedBinding	^ self keyBinder selectedBinding! !!HLKeyBinderHelper methodsFor: 'actions'!hide	('.', self cssClass) asJQuery remove.	self showCog!hideCog	'#cog-helper' asJQuery hide!show	self hideCog.	self appendToJQuery: 'body' asJQuery!showCog	'#cog-helper' asJQuery show! !!HLKeyBinderHelper methodsFor: 'keyBindings'!registerBindings	"Do nothing"! !!HLKeyBinderHelper methodsFor: 'rendering'!renderBindingGroup: aBindingGroup on: html	(aBindingGroup activeBindings     	sorted: [ :a :b | a key < b key ])        do: [ :each | each renderActionFor: self keyBinder html: html ]!renderBindingOn: html	self selectedBinding renderOn: self html: html!renderCloseOn: html	html a		class: 'close';		with: [ (html tag: 'i') class: 'icon-remove' ];		onClick: [ self keyBinder deactivate ]!renderCog	[ :html |		html 			div id: 'cog-helper'; 			with: [				html a 					with: [ (html tag: 'i') class: 'icon-cog' ];					onClick: [ self keyBinder activate ] ] ]		appendToJQuery: 'body' asJQuery!renderContentOn: html	html div class: self cssClass; with: [      	self         	renderSelectionOn:html;          	renderBindingOn: html;			renderCloseOn: html ]!renderSelectionOn: html		html span         	class: 'selected';             with: (self selectedBinding label ifNil: [ 'Action' ])!renderStart	(window jQuery: '#helper') remove.	[ :html |		html div 			id: 'helper';			with: 'Press ', self keyBinder activationKeyLabel, ' to start' ] appendToJQuery: 'body' asJQuery.		[ (window jQuery: '#helper') fadeOut: 1000 ] 		valueWithTimeout: 2000! !!HLKeyBinderHelper class methodsFor: 'instance creation'!on: aKeyBinder	^ self new    	keyBinder: aKeyBinder;        yourself! !Object subclass: #HLRepeatingKeyBindingHandler	instanceVariableNames: 'repeatInterval delay interval keyBindings widget isKeyCurrentlyPressed'	package: 'Helios-KeyBindings'!!HLRepeatingKeyBindingHandler commentStamp!##Usage    (HLRepeatingKeyBindingHandler forWidget: aWidget)        whileKeyPressed: keyCode do: [xxxx];        whileKeyPressed: anotherKey do: [yyy];        rebindPerforms an action on a key press, waits for 300 ms and then preforms the action every repeatInterval ms until the button is released!!HLRepeatingKeyBindingHandler methodsFor: 'accessing'!repeatInterval: aMillisecondIntegerValue 	repeatInterval := aMillisecondIntegerValue!whileKeyPressed: aKey do: aBlock	keyBindings at: aKey put: aBlock!widget: aWidget	widget := aWidget! !!HLRepeatingKeyBindingHandler methodsFor: 'actions'!bindKeys	widget bindKeyDown: [ :e | self handleKeyDown: e ] up: [ :e | self handleKeyUp: e ]!delayBeforeStartingRepeatWithAction: action	^ [ interval := self startRepeatingAction: action ] valueWithTimeout: 300!handleKeyUp	isKeyCurrentlyPressed := false.	interval ifNotNil: [ interval clearInterval ].	delay ifNotNil: [ delay clearTimeout ]!rebindKeys	self unbindKeys;		bindKeys!startRepeatingAction: action	^ [ (widget hasFocus)		ifTrue: [ action value ]		ifFalse: [ self handleKeyUp ] ] valueWithInterval: repeatInterval!unbindKeys	widget unbindKeyDownUp! !!HLRepeatingKeyBindingHandler methodsFor: 'events-processing'!handleKeyDown: e	 keyBindings keysAndValuesDo: [ :key :action | 		self ifKey: key wasPressedIn: e thenDo: action ]!handleKeyUp: e	isKeyCurrentlyPressed		ifTrue: [ self handleKeyUp ]!ifKey: key wasPressedIn: e thenDo: action	(e which = key and: [ isKeyCurrentlyPressed = false ])		ifTrue: [  self whileTheKeyIsPressedDo: action ]!whileTheKeyIsPressedDo: action	isKeyCurrentlyPressed := true.	action value.	delay := self delayBeforeStartingRepeatWithAction: action! !!HLRepeatingKeyBindingHandler methodsFor: 'initialization'!initialize 	super initialize.	keyBindings := Dictionary new.	isKeyCurrentlyPressed := false.	repeatInterval := 70.! !!HLRepeatingKeyBindingHandler class methodsFor: 'instance-creation'!forWidget: aWidget	^self new		widget: aWidget;		yourself! !
 |