[ENH] Request for Inclusion: scroll wheel fixes

Henrik Gedenryd Henrik.Gedenryd at lucs.lu.se
Wed Apr 26 19:40:44 UTC 2000


I vote for the attached change set (by Torge) to be included in the base
image. I have tweaked it for the new (2.8 alpha) preferences panel.

Henrik



"Change Set:        ctrl-scroll-tweak-th
Date:            24 December 1999
Author:            Torge Husfeldt

Tweaks the ctrl-scroll feature from bf:
1) works with mice that produce commandKey actions
2) works for ObjectExplorer and Preferences

Torge"

-------------- next part --------------
'From Squeak2.8alpha of 19 January 2000 [latest update: #2005] on 26 April 2000 at 2:58:07 pm'!
"Change Set:		ctrl-scroll-tweak-th
Date:			24 December 1999
Author:			Torge Husfeldt

Tweaks the ctrl-scroll feature from bf:
1) works with mice that produce commandKey actions
2) works for ObjectExplorer and Preferences

Torge"!

ScrollPane subclass: #SimpleListMorph
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Windows'!

!SimpleListMorph commentStamp: '<historical>' prior: 0!
This class represents a simple list morph.
It is intended for use by Preferences>>openPreferencesControlPanel.
Other classes that now use ScrollPane might want to use
it because it allows mouse wheel scrolling.
It seemed impossible for me, though, to implement
this directly in ScrollPane.!

!Preferences class methodsFor: 'preferences panel' stamp: 'hg 4/26/2000 14:57'!
openPreferencesControlPanel
	"Preferences openPreferencesControlPanel"
	| aPanel aWindow aRow wrapper but aList odd aColor w width1 width2 spacer |
	Smalltalk verifyMorphicAvailability ifFalse: [^ self beep].
	true ifTrue: [^ self openFactoredPanel].

	"What follows below is the former (pre-2.8alpha) implementation of the prefs panel"
	aPanel _ AlignmentMorph newColumn.
	aPanel beSticky.
	aList _ OrderedCollection new.
	FlagDictionary associationsDo: [:assoc | aList add: (Array
				with: assoc key
				with: assoc value
				with: (self helpMessageForPreference: assoc key))].
	odd _ false.
	width1 _ 172.
	spacer _ 4.
	width2 _ 14.
	(aList asSortedCollection: [:a :b | a first < b first])
		do: 
			[:triplet | 
			aPanel addMorphBack: (aRow _ AlignmentMorph newRow).
			aRow color: (aColor _ odd
							ifTrue: [Color green muchLighter]
							ifFalse: [Color red veryMuchLighter]).
			odd _ odd not.
			aRow addMorph: (wrapper _ Morph new color: aColor).
			wrapper setBalloonText: triplet third.
			wrapper extent: width1 @ 15.
			wrapper addMorph: (StringMorph new contents: triplet first).
			aRow addMorphBack: (Morph new color: aColor;
				 extent: spacer @ 15).
			aRow addMorphBack: (wrapper _ Morph new color: aColor).
			wrapper extent: width2 @ 15.
			wrapper addMorphBack: (but _ UpdatingBooleanStringMorph new contents: triplet second printString).
			but getSelector: triplet first;
			 putSelector: #setPreference:toValue:;
			 stepTime: 1800;
			 target: self].
	wrapper _ ScrollPane new.
	wrapper scroller addMorph: aPanel.
	Smalltalk isMorphic
		ifTrue: 
			[aWindow _ SystemWindow new model: self.
			aWindow addMorph: wrapper frame: (0 @ 0 extent: 1 @ 1).
			aWindow setLabel: 'Preferences'.
			aWindow openInWorld]
		ifFalse: 
			[(w _ MVCWiWPasteUpMorph newWorldForProject: nil) addMorph: wrapper.
			wrapper retractable: false;
			 extent: self initialExtent + (wrapper scrollbarWidth @ 0).
			w startSteppingSubmorphsOf: wrapper.
			MorphWorldView
				openOn: w
				label: 'Preferences'
				extent: w fullBounds extent]! !


!ScrollController methodsFor: 'scrolling' stamp: 'th 12/11/1999 16:57'!
scrollByKeyboard
	| keyEvent |
	keyEvent _ sensor keyboardPeek.
	keyEvent ifNil: [^ false].
	(sensor controlKeyPressed or:[sensor commandKeyPressed]) ifFalse: [^ false].
	keyEvent asciiValue = 30
		ifTrue: 
			[sensor keyboard.
			self scrollViewDown ifTrue: [self moveMarker].
			^ true].
	keyEvent asciiValue = 31
		ifTrue: 
			[sensor keyboard.
			self scrollViewUp ifTrue: [self moveMarker].
			^ true].
	^ false! !


!ScrollPane methodsFor: 'pane events' stamp: 'th 12/11/1999 17:21'!
scrollByKeyboard: event 
	"If event is ctrl+up/down then scroll and answer true"
	(event controlKeyPressed or:[event commandKeyPressed]) ifFalse: [^ false].
	event keyValue = 30
		ifTrue: 
			[scrollBar scrollUp: 3.
			^ true].
	event keyValue = 31
		ifTrue: 
			[scrollBar scrollDown: 3.
			^ true].
	^ false! !


!SimpleHierarchicalListMorph methodsFor: 'model access' stamp: 'th 12/11/1999 17:35'!
keyStroke: event 
	"Process potential command keys"
	| args aCharacter |
	(self scrollByKeyboard: event)
		ifTrue: [^ self].
	keystrokeActionSelector == nil ifTrue: [^ nil].
	aCharacter _ event keyCharacter.
	(args _ keystrokeActionSelector numArgs) = 1 ifTrue: [^ model perform: keystrokeActionSelector with: aCharacter].
	args = 2 ifTrue: [^ model
			perform: keystrokeActionSelector
			with: aCharacter
			with: self].
	^ self error: 'The keystrokeActionSelector must be a 1- or 2-keyword symbol'! !


!SimpleListMorph methodsFor: 'events' stamp: 'th 12/12/1999 14:03'!
mouseEnter: event 
	super mouseEnter: event.
	event hand newKeyboardFocus: self! !



More information about the Squeak-dev mailing list