[ENH - I hope] Window Selection

Joshua Gargus josh at 24.65.218.157.ab.wave.home.com
Mon May 31 00:02:20 UTC 1999


Hello,

Desiring a way to select windows directly from the keyboard, I whipped
the following up.  When you press 'cmd-~', it pops up a list of all visible
SystemWindows.  It also displays a thumbnail representation of the currently
selected window, and a translucent rectangle over the window (in case it is
partly or completely covered).  These latter two behaviors can be independently
turned on or off (in case they slow down things too much).

I think this is kind of nifty, but it is also a bit slow.  I understand that
creating thumbnails cannot be speeded up too much, but it seems to me that
the translucent rectangle is slower than it should be.  I'm still getting the
hang of Morphic, so if anyone can see a glaring problem with my approach,
please let me know.

Hope it's useful,
Josh

Content-Type: TEXT/PLAIN; charset=US-ASCII; name="WindowSelection.30May1151pm.cs"
Content-ID: <Pine.LNX.3.96.990531000220.22228B at 24.65.218.157.ab.wave.home.com>
Content-Description: 

'From Squeak 2.4b of April 23, 1999 on 30 May 1999 at 11:51:49 pm'!
StringHolder subclass: #WindowListModel
	instanceVariableNames: 'windowList stringList thumbnailList thumbnailHeight index defaultBackgroundColor '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Josh-WindowSelection'!
MorphicModel subclass: #WindowListMorph
	instanceVariableNames: 'thumbnail transform outline '
	classVariableNames: 'OutlinesOn ThumbnailsOn '
	poolDictionaries: ''
	category: 'Josh-WindowSelection'!

!HandMorph methodsFor: 'event handling' stamp: 'jcg 5/14/1999 00:02'!
handleAsSpecialEvent: evt
	
	"Tries to do something special with the event.  If we can't find anything to do with it, we answer nil and let the regular event handling take over."

	(evt anyButtonPressed and:
	 [evt controlKeyPressed and:
	 [lastEvent anyButtonPressed not]]) ifTrue:
		[eventTransform _ MorphicTransform identity.
		lastEvent _ evt.
		^ self invokeMetaMenu: evt].

	evt blueButtonPressed ifTrue:
		[lastEvent blueButtonPressed 
			ifTrue: [^ self specialDrag: evt]
			ifFalse: [eventTransform _ MorphicTransform identity.
					lastEvent _ evt.
					^ self specialGesture: evt]].

	"check if the character '`' and the commandKey are pressed.  If so, bring up a window menu"
	((evt isKeystroke 
		and: [evt commandKeyPressed])
		and: [evt keyValue = 96])  
			ifTrue: [^ WindowListModel popupPluggableList]. 



	^ nil		"event is not special after all."! !

!HandMorph methodsFor: 'event handling' stamp: 'jcg 5/3/1999 00:15'!
handleEvent: evt
	
	| special |

	eventSubscribers do: [:m | m handleEvent: evt].
"--"
	"allows us to designate and handle certain events that will be handled here, and not passed on to a submorph"
	special _ self handleAsSpecialEvent: evt.
	special ifNotNil: [^ special].

"--"
	lastEvent _ evt.
	self position ~= evt cursorPoint
		ifTrue: [self position: evt cursorPoint].

	evt isMouse ifTrue: [
		evt isMouseMove ifTrue: [^ self handleMouseMove: evt].
		evt isMouseDown ifTrue: [ ^ self handleMouseDown: evt].
		evt isMouseUp ifTrue: [^ self handleMouseUp: evt]].

	evt isKeystroke ifTrue: [
		keyboardFocus ifNotNil: [keyboardFocus keyStroke: evt].
		^ self].
! !

Smalltalk renameClassNamed: #TestAltTab as: #WindowListModel!

!WindowListModel reorganize!
('window switching test')
('events' dealWithKeystroke:from: windowChosenFrom:)
('accessing' defaultBackgroundColor defaultBackgroundColor: index index: outline stringList thumbnail thumbnailHeight windowList)
('initialize' initialize)
!


!WindowListModel methodsFor: 'events' stamp: 'jcg 5/12/1999 00:36'!
dealWithKeystroke: aChar from: view
	"If it is a return, do something.  Otherwise, check if it is an arrow key"

	(aChar = Character cr) ifTrue: [^ self windowChosenFrom: view ].
	^ self arrowKey: aChar from: view.! !

!WindowListModel methodsFor: 'events' stamp: 'jcg 5/12/1999 15:01'!
windowChosenFrom: aView
	"Activate the chosen window".
	
	(windowList at: index) activate.
	aView owner delete.
! !

!WindowListModel methodsFor: 'accessing' stamp: 'jcg 5/12/1999 15:08'!
defaultBackgroundColor

	^ defaultBackgroundColor! !

!WindowListModel methodsFor: 'accessing' stamp: 'jcg 5/12/1999 15:08'!
defaultBackgroundColor: aColor

	defaultBackgroundColor _ aColor.
! !

!WindowListModel methodsFor: 'accessing' stamp: 'jcg 5/7/1999 00:59'!
index
	
	^ index	! !

!WindowListModel methodsFor: 'accessing' stamp: 'jcg 5/19/1999 01:39'!
index: anInteger

	index _ anInteger.
	self changed: #index.
! !

!WindowListModel methodsFor: 'accessing' stamp: 'jcg 5/19/1999 01:05'!
outline
	^ (windowList at: index) bounds
! !

!WindowListModel methodsFor: 'accessing' stamp: 'jcg 5/7/1999 00:50'!
stringList
	
	^ stringList	! !

!WindowListModel methodsFor: 'accessing' stamp: 'jcg 5/14/1999 01:19'!
thumbnail
	(thumbnailList at: index) ifNil:
		[thumbnailList at: index put:
			(MorphThumbnail new 
				height: thumbnailHeight; 
				width: 1200; 
				morphRepresented: (windowList at: index))].
	^ thumbnailList at: index.
! !

!WindowListModel methodsFor: 'accessing' stamp: 'jcg 5/14/1999 00:59'!
thumbnailHeight
	^ thumbnailHeight.! !

!WindowListModel methodsFor: 'accessing' stamp: 'jcg 5/7/1999 00:49'!
windowList
	
	^ windowList	! !

!WindowListModel methodsFor: 'initialize' stamp: 'jcg 5/19/1999 01:05'!
initialize

	stringList _ self class getWindowsAsStrings.
	windowList _ self class getWindows.
	thumbnailList _ Array new: windowList size.
	thumbnailHeight _ 90.

	self index: 1.! !


!WindowListModel class reorganize!
('instance creation' new)
('choose windows' popupPluggableList)
('private' getWindows getWindowsAsStrings)
!


!WindowListModel class methodsFor: 'instance creation' stamp: 'jcg 5/12/1999 16:09'!
new
	^ super new initialize.

! !

!WindowListModel class methodsFor: 'choose windows' stamp: 'jcg 5/14/1999 18:34'!
popupPluggableList
	"pop up a PluggableList to choose the desired SystemWindow from."

	| list model win |
	model _ WindowListModel new.

	"create a list"
	list _ PluggableListMorph
			on: model
			list: #stringList
			selected: #index
			changeSelected: #index:
			menu: nil
			keystroke: #dealWithKeystroke:from:.

	win _ WindowListMorph 
		newBounds: (Rectangle center: Sensor mousePoint extent: 300 at 400)
		model: model
		slotName: 'Window Chooser'
		list: list.

	win color: Color lightBlue.

	"create a list"
"	list _ PluggableListMorph
			on: model
			list: #stringList
			selected: #index
			changeSelected: #index:
			menu: nil
			keystroke: #dealWithKeystroke:from:.
	list position: (win bounds topLeft + (10 at 10)).
	list extent: (win extent - (20 at 110)).

	win addMorph: list."



	win openInWorld.
! !

!WindowListModel class methodsFor: 'private' stamp: 'jcg 5/6/1999 23:45'!
getWindows
	"answers an Array of SystemWindow in world"

	^ SystemWindow windowsIn: self currentWorld satisfying: [:dummy | true].! !

!WindowListModel class methodsFor: 'private' stamp: 'jcg 5/7/1999 00:23'!
getWindowsAsStrings
	"answers an Array of string names of SystemWindows in world"
	| prefix |
	prefix _ 'a SystemWindow('.
	^ self getWindows collect: 
		[:window | window asString 
			copyFrom: prefix size + 1 
			to: window asString size - 1].! !


!WindowListMorph methodsFor: 'updating' stamp: 'jcg 5/19/1999 01:32'!
update: aSymbol
	"Refer to the comment in View|update:."

	aSymbol == #index ifTrue:
		[ThumbnailsOn ifTrue: [self thumbnail: model thumbnail].
		OutlinesOn ifTrue: [self outline: model outline]].
		"[ self outline: model outline]."

	^ self.! !

!WindowListMorph methodsFor: 'private' stamp: 'jcg 5/19/1999 01:05'!
outline: aRectangle
	outline bounds: aRectangle

! !

!WindowListMorph methodsFor: 'private' stamp: 'jcg 5/14/1999 19:15'!
positionList: aListMorph

	aListMorph width: (self width - 20).
	aListMorph height: (self height - 20 - model thumbnailHeight).
	aListMorph position: (self topLeft + (10 at 10)).

! !

!WindowListMorph methodsFor: 'private' stamp: 'jcg 5/14/1999 18:43'!
positionThumbnail: aThumbnail
	| x y |

	x _ self left + (self width - thumbnail width / 2) rounded.
	y _ self bottom - thumbnail height - 10.
	thumbnail position: x at y.
! !

!WindowListMorph methodsFor: 'private' stamp: 'jcg 5/14/1999 19:11'!
thumbnail: aThumb


	| x y |
	thumbnail ifNotNil: [thumbnail delete].
	thumbnail _ aThumb.
	self addMorph: thumbnail.

"	thumbnail ifNotNil: [thumbnail hide].
	thumbnail _ aThumb show.
	
	x _ self left + (self width - aThumb width / 2) rounded.
	y _ self bottom - aThumb height - 10.
	aThumb position: x at y.
	self addMorph: aThumb.
	transform addMorph: aThumb.
	aThumb openInWorld."! !

!WindowListMorph methodsFor: 'initilization' stamp: 'jcg 5/19/1999 01:25'!
initialize
	super initialize.
	outline _ RectangleMorph new color: (Color blue alpha: 0.7).
	outline extent: 0 at 0.
	self addMorph: outline.
	"transform _ TransformMorph new.
	self addMorphCentered: transform."! !

!WindowListMorph methodsFor: 'change reporting' stamp: 'jcg 5/14/1999 19:02'!
layoutChanged
	submorphs do: [:m | (m class = PluggableListMorph) 
		ifTrue: [ self positionList: m ] 
		ifFalse: [ (m class = MorphThumbnail)
			ifTrue: [ self positionThumbnail: m ]]].
	super layoutChanged.
! !


!WindowListMorph class reorganize!
('instance creation' newBounds:model:slotName: newBounds:model:slotName:list:)
('display properties' setOutlineDisplay: setThumbnailDisplay:)
!


!WindowListMorph class methodsFor: 'instance creation' stamp: 'jcg 5/14/1999 01:53'!
newBounds: aRectangle model: aModel slotName: aString 
	
	| newguy |
	newguy _ super 
		newBounds: aRectangle
		model: aModel
		slotName: aString.

	"hack.  shouldn't be necessary if MorphicModel uses 'model:' instead of assignment"
	self flag: #joshG.
	aModel addDependent: newguy.	

	^ newguy! !

!WindowListMorph class methodsFor: 'instance creation' stamp: 'jcg 5/14/1999 18:38'!
newBounds: aRectangle model: aModel slotName: aString list: aListMorph
	
	| newguy |
	newguy _ super 
		newBounds: aRectangle
		model: aModel
		slotName: aString.
		
	newguy addMorph: aListMorph.

	"hack.  shouldn't be necessary if MorphicModel uses 'model:' instead of assignment"
	self flag: #joshG.
	aModel addDependent: newguy.	

	^ newguy! !

!WindowListMorph class methodsFor: 'display properties' stamp: 'jcg 5/19/1999 01:31'!
setOutlineDisplay: aBool
	
	OutlinesOn _ aBool.! !

!WindowListMorph class methodsFor: 'display properties' stamp: 'jcg 5/19/1999 01:30'!
setThumbnailDisplay: aBool
	
	ThumbnailsOn _ aBool.! !


HandMorph removeSelector: #handleAsSpecialKeyboardEvent:!
HandMorph removeSelector: #handleSpecialEvent:!
WindowListModel removeSelector: #windowChosen!
WindowListModel removeSelector: #stringList:!
WindowListModel removeSelector: #windowList:!
WindowListModel removeSelector: #windowBounds!
WindowListModel removeSelector: #getWindows!
WindowListMorph removeSelector: #thumbnailHeight!
WindowListMorph removeSelector: #thumbnailHeight:!
WindowListMorph class removeSelector: #newBounds:model:slotName:thumbnailHeight:!
"Postscript:
By default, we want to enable both the outline and thumbnail display options."
WindowListMorph setOutlineDisplay: true.
WindowListMorph setThumbnailDisplay: true.
!





More information about the Squeak-dev mailing list