[comp.lang.smalltalk] tri-state button goody

ross@prls.UUCP (Ross Morley) (09/01/90)

Here's a little goody which many of you may find useful.
It's a SwitchView with three states (black, grey and white) and two ways
to press it (click or prolonged press). It can be plugged into your
application very easily (see examples included) by defining three simple
messages in your application class that is to be its model. You can name
the messages as you like - simply tell the TriStateButtonView what they
are called when you plug it in. The corresponding methods in your model
class determine the semantics of the button: which color it is, and the
effects of clicking or pressing it. I have included a contrived example
application with two TriStateButtons with different semantics, so you can
play with them as soon as you file this in. 

I will post a couple more goodies in the next few days.

---------------------------- cut here -----------------------------------

'From Smalltalk-80, Version 2.3 of 13 June 1988 on 31 August 1990 at 12:11:57 pm'!

SwitchView subclass: #TriStateButtonView
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Interface-VisualControls'!

TriStateButtonView comment:
'I am a pluggable tri-state button. I can display white, black or grey depending on the state of 
my aspect in the model. My controller senses two kinds of events, a click and a prolonged press, 
and signals the model accordingly. Some interfacing methods must be built into the model - see
comments on instance creation methods.

						Copyright (C) 1990, Ross P. Morley. 
	This program is placed in the public domain. You may use and alter this program freely
	for non-commercial purposes as long as you leave this message intact.  Neither I nor
	my company will recognize any responsibility for damages arising from use of this program.
'!

!TriStateButtonView methodsFor: 'controller access'!

defaultControllerClass
	^TriStateButtonController! !

!TriStateButtonView methodsFor: 'deEmphasizing'!

deEmphasizeView
	"Redisplay without emphasis."

	emphasisOn _ false.
	self displayView!

emphasizeView
	"Redisplay with emphasis."

	emphasisOn _ true.
	self displayView! !

!TriStateButtonView methodsFor: 'displaying'!

displayLabelClippingBox: aRectangle rule: ruleInteger mask: maskInteger
	"Display the label in the specified manner."

	| center |
	label isNil ifTrue: [^self].
	center _ label boundingBox center.
	label displayOn: Display
		at: (label offset + (self displayTransformation applyTo: center) - center) rounded
		clippingBox: aRectangle
		rule: ruleInteger
		mask: maskInteger!

displayView
	"Interrogate the model and display the receiver accordingly."

	| box0 box1 box2 state |
	box0 _ self insetDisplayBox.
	box1 _ box0 insetBy: 1.
	box2 _ box1 insetBy: 1.
	Display white: box0.
	state _ self interrogateModel.		"#white, #grey or #black"
	state == #grey ifTrue: [Display veryLightGray: box0].
	state == #black ifTrue: [Display black: box1].
	emphasisOn 
		ifFalse: [
			Display white: box2.
			self displayLabelClippingBox: box2 rule: Form under mask: Form black]
		ifTrue: [
			state == #black 
				ifTrue: [self displayLabelClippingBox: box2 rule: Form erase mask: Form black]
				ifFalse: [self displayLabelClippingBox: box2 rule: Form under mask: Form black]]! !

!TriStateButtonView methodsFor: 'initialize-release'!

initialize
	super initialize.
	selector _ #white! !

!TriStateButtonView methodsFor: 'selector'!

interrogateModel
	"Send the selector message to the model to obtain the state of the aspect of the model 
	the receiver indicates. Answer the result (a Symbol: #black, #grey or #white)."

	^model perform: selector! !

!TriStateButtonView methodsFor: 'updating'!

update: aspectSymbol
	"The model has changed in aspect 'aspectSymbol'. If this is the receiver's aspect, redisplay."

	aspectSymbol == selector ifTrue: [self display]! !

TriStateButtonView class
	instanceVariableNames: ''!

!TriStateButtonView class methodsFor: 'instance creation'!

on: model aspect: aspectSymbol label: labelString click: clickSymbol press: pressSymbol
	"Create a pluggable tri-state button on an aspect of model, where:
		aspectSymbol	is the selector sent to the model to get the current status which must
						be #black, #grey or #white;
		label			is the label on the button;
		clickSymbol		is the selector sent to the model when the user clicks the button;
		pressSymbol	is the selector sent to the model when the user presses the button
						and holds it for a predefined time."

	| view |
	(view _ self new)
		model: model;
		selector: aspectSymbol;
		label: labelString asParagraph.
	view controller
		clickSelector: clickSymbol;
		pressSelector: pressSymbol.
	^view! !

!TriStateButtonView class methodsFor: 'examples'!

bothSwitches

	TriStateButtonExample bothSwitches!

stateSwitch

	TriStateButtonExample stateSwitch!

thisAndThatSwitch

	TriStateButtonExample thisAndThatSwitch! !

SwitchController subclass: #TriStateButtonController
	instanceVariableNames: 'pressSelector downTime pressed '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Interface-VisualControls'!

TriStateButtonController comment:
'I work with TriStateButtonView. I sense two kinds of events, a click and a prolonged press, 
and signal my model accordingly. The minimum duration of a press is defined by my class method
pressTime.

Instance Variables:

selector		The selector I send for a click. A Symbol. This variable is defined in my superclass.
pressSelector	The selector I send for a press (button held for a preset time).
downTime		The absolute time (from the millisecond clock) when the mouse button was pressed.
pressed			A Boolean indicating that a press event has occurred (button down timed out).

						Copyright (C) 1990, Ross P. Morley. 
	This program is placed in the public domain. You may use and alter this program freely
	for non-commercial purposes as long as you leave this message intact.  Neither I nor
	my company will recognize any responsibility for damages arising from use of this program.
'!

!TriStateButtonController methodsFor: 'accessing'!

clickSelector
	"Answer the selector the receiver sends to its model when the user clicks on it 
	(a Symbol, or nil if none)."

	^selector!

clickSelector: aSymbolOrNil
	"Set the selector the receiver sends to its model when the clicks on it. 
	If nil, nothing is sent."

	selector _ aSymbolOrNil!

downTime
	"Recall the absolute time (from the millisecond clock) when the red button was pressed."

	^downTime!

pressSelector
	"Answer the selector the receiver sends to its model when the user presses it 
	for at least a preset length of time (a Symbol, or nil if none)."

	^pressSelector!

pressSelector: aSymbolOrNil
	"Set the selector the receiver sends to its model when the user presses it for. 
	a preset length of time. If nil, nothing is sent."

	pressSelector _ aSymbolOrNil! !

!TriStateButtonController methodsFor: 'basic control sequence'!

controlInitialize
	"The red button has gone down on the receiver. Begin timing it."

	view indicatorReverse.
	self markDownTime;
		clearPressed!

controlTerminate
	"The red button has been released. If not pressed send a click event. Relinquish control."

	self hasBeenPressed ifTrue: [^self].
	view indicatorReverse.
	self sendClick! !

!TriStateButtonController methodsFor: 'control defaults'!

controlActivity
	"Called repeatedly as long as a button is held. Check how long the button has been down
	and, if long enough, generate a press event. After a press event has been generated, do
	nothing (control is retained until the button is released)."

	self hasBeenPressed ifTrue: [^self].
	Time millisecondClockValue - self downTime > self class pressTime 
		ifTrue: [
			view indicatorReverse.
			self setPressed;
				sendPress]!

isControlActive
	"Answer whether the receiver still wants control. True as long as a mouse button is held."

	^sensor anyButtonPressed!

isControlWanted
	"Answer whether the receiver initially wants control. Override the superclass to avoid 
	setting the cursor because it is never restored (SwitchController bug)."

	^self viewHasCursor & sensor redButtonPressed! !

!TriStateButtonController methodsFor: 'initialize-release'!

initialize
	super initialize.
	self clickSelector: #click; 
		pressSelector: #press;
		markDownTime;
		clearPressed! !

!TriStateButtonController methodsFor: 'private'!

clearPressed

	pressed _ false!

hasBeenPressed

	^pressed!

markDownTime
	"Record the absolute time from the millisecond clock. Done when the red button is pressed."

	downTime _ Time millisecondClockValue!

sendClick
	"Send a click event to the model, if it wants it."

	self clickSelector notNil
		ifTrue: [model perform: self clickSelector]!

sendPress
	"Send a press event to the model, if it wants it."

	self pressSelector notNil
		ifTrue: [model perform: self pressSelector]!

setPressed

	pressed _ true! !

TriStateButtonController class
	instanceVariableNames: ''!

!TriStateButtonController class methodsFor: 'defaults'!

pressTime
	"Answer the length of time (ms) the button must be held down to be considered pressed.
	If released before this time it is considered to have been clicked. An Integer."

	^1200! !

Model subclass: #TriStateButtonExample
	instanceVariableNames: 'state thisIs thatIs '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Interface-VisualControls'!

TriStateButtonExample comment:
'This class exists to demonstrate TriStateButtons. It is not intended to be used itself in an
application, but merely to show how to interface a TriStateButtonView/Controller to an
application. It actually contains interfaces to two independent aspects which can be 
indicated and controlled by tri-state buttons. Only the "interface" instance protocols
need to be provided in your application class. The example class methods can be executed
to show tri-state buttons in action.

Instance Variables:

state		A Symbol (#yes, #no or #maybe).
thisIs		A Boolean.
thatIs		A Boolean.'!

!TriStateButtonExample methodsFor: 'accessing'!

state
	"Answer the current state (a Symbol: #yes, #no or #maybe)."

	^state!

state: aSymbol
	"Set the current state (#yes, #no or #maybe)."

	state _ aSymbol!

thatIs
	"Answer whether that is true."

	^thatIs!

thatIs: aBoolean

	thatIs _ aBoolean!

thisIs
	"Answer whether this is true."

	^thisIs!

thisIs: aBoolean

	thisIs _ aBoolean! !

!TriStateButtonExample methodsFor: 'initialize-release'!

initialize

	state _ #maybe.
	thisIs _ thatIs _ false! !

!TriStateButtonExample methodsFor: 'interface - state'!

stateSwitchClick
	 "The 'state' switch has been clicked. Respond to it and notify the TriStateSwitchView
	(a dependent) of the change. Click toggles between yes and no states, but has no effect
	in a maybe state."

	self state == #maybe ifTrue: [^self].
	self state == #yes 
		ifTrue: [self state: #no]
		ifFalse: [self state: #yes].
	self changed: #stateSwitchState!

stateSwitchPress
	 "The 'state' switch has been pressed. Respond to it and notify the TriStateSwitchView
	(a dependent) of the change. Press changes to the maybe state from yes or no, or to the
	no state from maybe (spoils the symmetry, but better have some way out of maybe!!)."

	self state == #maybe 
		ifTrue: [self state: #no]
		ifFalse: [self state: #maybe].
	self changed: #stateSwitchState!

stateSwitchState
	 "Answer the state the tri-state switch should be in for the present state 
	(a Symbol: #black, #grey or #white)."

	self state == #yes ifTrue: [^#black].
	self state == #no ifTrue: [^#white].
	^#grey! !

!TriStateButtonExample methodsFor: 'interface - this & that'!

thisAndThatSwitchClick
	"The 'this & that' switch has been clicked. If this is then toggle that, otherwise that is 
	irrelevant so remember its previous state and (as a shortcut) set this. 
	Notify the TriStateSwitchView (a dependent) of the change."

	self thisIs 
		ifTrue: [self thatIs: self thatIs not]
		ifFalse: [self thisIs: true].
	self changed: #thisAndThatSwitchState!

thisAndThatSwitchPress
	"The 'this & that' switch has been pressed. Toggle this. 
	Notify the TriStateSwitchView (a dependent) of the change."

	self 
		thisIs: self thisIs not;
		changed: #thisAndThatSwitchState!

thisAndThatSwitchState
	"Answer the state the tri-state switch should be in according to this and that
	(a Symbol: #black, #grey or #white)."

	self thisIs
		ifTrue: [self thatIs 
					ifTrue: [^#black] 	"this is and that is"
					ifFalse: [^#grey]	"this is but that isn't"
				]
		ifFalse: [^#white]				"this isn't and don't care about that"! !

TriStateButtonExample class
	instanceVariableNames: ''!

!TriStateButtonExample class methodsFor: 'instance creation'!

new

	^super new initialize! !

!TriStateButtonExample class methodsFor: 'examples'!

bothSwitches
	"Open a window with two TriStateSwitchViews."
	"TriStateButtonExample bothSwitches"

	| model sSwitch ttSwitch topView |
	model _ self new.
	sSwitch _ TriStateButtonView on: model
			aspect: #stateSwitchState 
			label: 'State' 
			click: #stateSwitchClick
			press: #stateSwitchPress.
	ttSwitch _ TriStateButtonView on: model
			aspect: #thisAndThatSwitchState 
			label: 'This & That' 
			click: #thisAndThatSwitchClick
			press: #thisAndThatSwitchPress.
	(topView _ StandardSystemView new)
		model: model;
		minimumSize: 100@80;
		borderWidth: 1;
		addSubView: sSwitch in: (0@0 corner: 1.0@0.5) borderWidth: 1;
		addSubView: ttSwitch in: (0@0.5 corner: 1.0@1.0) borderWidth: 1.
	topView controller open.!

stateSwitch
	"Open a window with a TriStateSwitchView on my state."
	"TriStateButtonExample stateSwitch"

	| model switch topView |
	model _ self new.
	switch _ TriStateButtonView on: model
			aspect: #stateSwitchState 
			label: 'State' 
			click: #stateSwitchClick
			press: #stateSwitchPress.
	(topView _ StandardSystemView new)
		model: model;
		minimumSize: 100@50;
		borderWidth: 1;
		addSubView: switch.
	topView controller open.!

thisAndThatSwitch
	"Open a window with a TriStateSwitchView on my this and that."
	"TriStateButtonExample thisAndThatSwitch"

	| model switch topView |
	model _ self new.
	switch _ TriStateButtonView on: model
			aspect: #thisAndThatSwitchState 
			label: 'This & That' 
			click: #thisAndThatSwitchClick
			press: #thisAndThatSwitchPress.
	(topView _ StandardSystemView new)
		model: model;
		minimumSize: 100@50;
		borderWidth: 1;
		addSubView: switch.
	topView controller open.! !


---------------------------- cut here -----------------------------------

-- 
Ross P. Morley                                  pyramid!prls!ross
Philips Research, Sunnyvale                     philabs!prls!ross
811 E. Arques Ave (MS02)			ross@prls.uucp
Sunnyvale, CA 94088-3409                        Tel. (408) 991 5057