[Cuis-dev] Enable state for pluggable button

Hilaire Fernandes hilaire at drgeo.eu
Thu Nov 18 12:04:26 PST 2021


Hi Juan,

I add an enable state to the pluggableButton and refactored a bit the class.

Hilaire

-- 
GNU Dr. Geo
http://drgeo.eu
http://blog.drgeo.eu

-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://lists.cuis.st/mailman/archives/cuis-dev/attachments/20211118/478d0a6b/attachment.htm>
-------------- next part --------------
'From Cuis 5.0 [latest update: #4958] on 5 November 2021 at 10:00:07 am'!
!classDefinition: #PluggableButtonMorph category: #'Morphic-Widgets'!
PluggableMorph subclass: #PluggableButtonMorph
	instanceVariableNames: 'label font icon getStateSelector actionSelector isPressed mouseIsOver magnifiedIcon actWhen roundButtonStyle iconName secondaryActionSelector stateSelector enableSelector '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Widgets'!

!PluggableButtonMorph commentStamp: 'hlsf 11/5/2021 09:20:20' prior: 0!
A PluggableButtonMorph is a combination of an indicator for a boolean value stored in its model and an action button. The action of a button is often, but not always, to toggle the boolean value that it shows. Its pluggable selectors are:
		enableSelector fetch a boolean value from the model (Am I enabled, i.e. Can I be activated?)
		stateSelector		 fetch a boolean value from the model (Am I selected?)
		actionSelector			invoke this button's action on the model
		secondaryActionSelector invoke this action when the button-up event occures

Any of the above selectors can be nil, meaning that the model does not supply behavior for the given action, and the default behavior should be used. For example, if stateSelector is nil, then this button shows the state of a read-only boolean that is always false.

The model informs its view(s) of changes by sending #changed: to itself with stateSelector as a parameter. The view tells the model when the button is pressed by sending actionSelector.

If the actionSelector takes one or more arguments, then the following are relevant:
		arguments			A list of arguments to provide when the actionSelector is called.
		argumentsProvider	The object that is sent the argumentSelector to obtain arguments, if dynamic
		argumentsSelector	The message sent to the argumentProvider to obtain the arguments.!


!PluggableButtonMorph methodsFor: 'drawing' stamp: 'hlsf 11/5/2021 09:58:02'!
enableColorWith: aColor
	^ self getEnabled 
		ifTrue: [aColor] ifFalse: [aColor twiceLighter ]! !

!PluggableButtonMorph methodsFor: 'initialization' stamp: 'hlsf 11/5/2021 09:21:00'!
enableSelector: aSymbol
	enableSelector _ aSymbol ! !

!PluggableButtonMorph methodsFor: 'private' stamp: 'hlsf 11/5/2021 09:23:47'!
getEnabled
	"Answer the result of sending the receiver's model the enableSelector message."

	^ enableSelector 
		ifNil: [true]
		ifNotNil: [model perform: enableSelector ]! !

!PluggableButtonMorph methodsFor: 'private' stamp: 'hlsf 11/5/2021 09:18:26'!
getState
	"Answer the result of sending the receiver's model the stateSelector message."

	^ stateSelector 
		ifNil: [false]
		ifNotNil: [model perform: stateSelector]! !


!Switch methodsFor: 'state' stamp: 'hlsf 11/5/2021 09:51:46'!
turnOff
	"Set the state of the receiver to 'off'. If the state of the receiver was 
	previously 'on', then 'self change' is sent and the receiver's off action is 
	executed."

	self isOn
		ifTrue: 
			[on _ false.
			self changed: #isOn.
			self doAction: offAction]! !

!Switch methodsFor: 'state' stamp: 'hlsf 11/5/2021 09:51:57'!
turnOn
	"Set the state of the receiver to 'on'. If the state of the receiver was 
	previously 'off', then 'self change' is sent and the receiver's on action is 
	executed."

	self isOff
		ifTrue: 
			[on _ true.
			self changed: #isOn.
			self doAction: onAction]! !


!PluggableButtonMorph methodsFor: 'accessing' stamp: 'hlsf 11/5/2021 09:42:46'!
performAction
	"Inform the model that this button has been pressed. "
	self getEnabled ifFalse: [^ self].
	actionSelector ifNotNil: [
		model perform: actionSelector ]! !

!PluggableButtonMorph methodsFor: 'drawing' stamp: 'hlsf 11/5/2021 09:54:03'!
draw3DLookOn: aCanvas

	| borderStyleSymbol c |
	borderStyleSymbol _ self isPressed ifFalse: [ #raised ] ifTrue: [ #inset ].
	c _ color.
	self mouseIsOver ifTrue: [ c _ c  lighter ].
	aCanvas
		fillRectangle: self morphLocalBounds
		color: (self enableColorWith: c)
		borderWidth: borderWidth
		borderStyleSymbol: borderStyleSymbol
		baseColorForBorder: (self enableColorWith: c).

	self drawRegularLabelOn: aCanvas! !

!PluggableButtonMorph methodsFor: 'drawing' stamp: 'hlsf 11/5/2021 09:53:29'!
drawEmbossedLabelOn: aCanvas

	| availableW center colorForLabel f l labelMargin targetSize w x y |
	label ifNotNil: [
		colorForLabel _ self enableColorWith: Theme current buttonLabel.
		self isPressed
			ifFalse: [
				self mouseIsOver
					ifFalse: [ colorForLabel _ colorForLabel adjustSaturation: -0.10 brightness: 0.10 ]]
			ifTrue: [ colorForLabel _ colorForLabel adjustSaturation: 0.0 brightness: -0.07 ].
		f _ self fontToUse.
		center _ extent // 2.
		labelMargin _ 3.
		w _ f widthOfString: label.
		availableW _ extent x - labelMargin - labelMargin.
		availableW >= w
			ifTrue: [
				l _ label ]
			ifFalse: [
				x _ labelMargin.
				targetSize _ label size * availableW // w.
				l _ label squeezedTo: targetSize.
				(f widthOfString: l) > availableW ifTrue: [
					targetSize _ targetSize - 1.
					l _ label squeezedTo: targetSize ]].
		
		w _ f widthOfString: l.
		x _ center x - (w // 2).
		y _ center y - (f lineSpacing // 2).
		aCanvas
			drawString: l
			at: x at y
			font: f
			color: colorForLabel
			embossed: true ]! !

!PluggableButtonMorph methodsFor: 'drawing' stamp: 'hlsf 11/5/2021 09:53:29'!
drawRegularLabelOn: aCanvas

	| w f center x y  availableW l labelMargin |

	f _ self fontToUse.
	center _ extent // 2.

	label ifNotNil: [
		labelMargin _ 4.
		w _ f widthOfString: label.
		availableW _ extent x - labelMargin - labelMargin - 1.
		availableW >= w
			ifTrue: [
				x _ center x - (w // 2).
				l _ label ]
			ifFalse: [
				x _ labelMargin.
				l _ label squeezedTo: (label size * availableW / w) rounded ].
		y _ center y - (f lineSpacing // 2).
		self isPressed ifTrue: [
			x _ x + 1.
			y _ y + 1 ].
		aCanvas
			drawString: l
			at: x at y
			font: f
			color: (self enableColorWith: Theme current buttonLabel) ]! !

!PluggableButtonMorph methodsFor: 'drawing' stamp: 'hlsf 11/5/2021 09:54:39'!
drawRoundLookOn: aCanvas
	| r colorForButton rect |
	colorForButton _ self isPressed
		ifFalse: [
			self mouseIsOver
				ifTrue: [	 Color h: color hue s: color saturation * 1.3 v: color brightness * 0.9 ]
				ifFalse: [ color ]]
		ifTrue: [ color adjustSaturation: 0.1 brightness: -0.1 ].

	colorForButton ifNotNil: [
		r _ Theme current roundedButtonRadius.
		rect _ self morphLocalBounds insetBy: `3 at 3`.
		r _ r min: (rect width min: rect height) * 0.5.
		aCanvas roundRect: rect color: (self enableColorWith: colorForButton) radius: r ].

	Theme current embossedButtonLabels
		ifTrue: [ self drawEmbossedLabelOn: aCanvas ]
		ifFalse: [ self drawRegularLabelOn: aCanvas ].! !

!PluggableButtonMorph methodsFor: 'event handling testing' stamp: 'hlsf 11/5/2021 09:29:24'!
handlesMouseDown: aMouseButtonEvent
	"Do I want to receive mouseDown events (mouseDown:, mouseMove:, mouseUp:)?"
	^self getEnabled ! !

!PluggableButtonMorph methodsFor: 'event handling testing' stamp: 'hlsf 11/5/2021 09:29:29'!
handlesMouseOver: evt
	"Do I want to receive mouseEnter: and mouseLeave: when the button is up and the hand is empty?" 
	^self getEnabled ! !

!PluggableButtonMorph methodsFor: 'event handling testing' stamp: 'hlsf 11/5/2021 09:29:50'!
handlesMouseStillDown: evt
	"Return true if the receiver wants to get repeated #mouseStillDown messages between #mouseDown: and #mouseUp"
	"Acting when down (instead of waiting until releasing the button)
	also means that the button action is repeated if the button is kept pressed"
	^actWhen == #buttonStillDown and: [self getEnabled ]! !

!PluggableButtonMorph methodsFor: 'initialization' stamp: 'hlsf 11/5/2021 09:18:40'!
initialize
	"initialize the state of the receiver"
	super initialize.

	roundButtonStyle _ nil.	"nil: honor Theme. true: draw as round button. false: draw as classic 3d border square button"
	model _ nil.
	enableSelector _ nil.
	stateSelector _ nil.
	actionSelector _ nil.
	isPressed _ false.
	mouseIsOver _ false.
	actWhen _ #buttonUp.
	extent _  `20 @ 15`! !

!PluggableButtonMorph methodsFor: 'initialization' stamp: 'hlsf 11/5/2021 09:17:47'!
model: anObject
	"Set my model and make me me a dependent of the given object."

	model ifNotNil: [model removeDependent: self].
	stateSelector ifNotNil: [
		anObject ifNotNil: [anObject addDependent: self]].
	model _ anObject! !

!PluggableButtonMorph methodsFor: 'initialization' stamp: 'hlsf 11/5/2021 09:17:47'!
model: anObject stateGetter: getStateSel action: actionSel label: aString

	stateSelector _ getStateSel.
	actionSelector _ actionSel.
	self model: anObject.
	self label: aString! !

!PluggableButtonMorph methodsFor: 'updating' stamp: 'hlsf 11/5/2021 09:50:54'!
update: aSymbol
	super update: aSymbol.
	(aSymbol == stateSelector or: [aSymbol == enableSelector ]) ifTrue: [
		self redrawNeeded ]! !

!PluggableButtonMorph methodsFor: 'testing' stamp: 'hlsf 11/5/2021 09:18:26'!
isPressed
	^isPressed | self getState! !

!PluggableButtonMorph methodsFor: 'testing' stamp: 'hlsf 11/5/2021 09:29:08'!
mouseIsOver
	^mouseIsOver and: [self getEnabled ]! !


!PluggableButtonMorph class methodsFor: 'example' stamp: 'hlsf 11/5/2021 09:51:34'!
example
	"
	PluggableButtonMorph example openInWorld
	"

	| s1 s2 s3 b1 b2 b3 row |
	s1 _ Switch new.
	s2 _ Switch new turnOn.
	s3 _ Switch new.
	s1 onAction: [s3 turnOn].
	s2 onAction: [s3 turnOff].
	s3 onAction: [s2 turnOff].
	b1 _ (PluggableButtonMorph model: s1 stateGetter: #isOn action: #switch) label: 'S1'.
	b2 _ (PluggableButtonMorph model: s2 stateGetter: #isOn action: #turnOn) label: 'S2'.
	b3 _ (PluggableButtonMorph model: s3 stateGetter: nil action: #switch) 
		enableSelector: #isOn;
		label: 'S3'.
	b1 color: `Color lightRed`.
	b2 color: `Color lightRed`.
	b3 color: `Color lightRed`.
	row _ LayoutMorph newRow
		addMorphs: (Array with: b1 with: b2 with: b3);
		morphExtent: `120 at 35`.
	^ row! !

!methodRemoval: PluggableButtonMorph #labelColorWith: stamp: 'hlsf 11/5/2021 09:53:29'!
PluggableButtonMorph removeSelector: #labelColorWith:!
!methodRemoval: PluggableButtonMorph #getModelState stamp: 'hlsf 11/5/2021 09:18:26'!
PluggableButtonMorph removeSelector: #getModelState!
!classDefinition: #PluggableButtonMorph category: #'Morphic-Widgets'!
PluggableMorph subclass: #PluggableButtonMorph
	instanceVariableNames: 'label font icon stateSelector enableSelector actionSelector isPressed mouseIsOver magnifiedIcon actWhen roundButtonStyle iconName secondaryActionSelector'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Widgets'!

!PluggableButtonMorph reorganize!
('accessing' actWhen: action: actionSelector adoptWidgetsColor: icon: iconDrawSelector iconDrawSelector: iconName iconName: label: label:font: performAction roundButtonStyle:)
('drawing' draw3DLookOn: drawEmbossedLabelOn: drawOn: drawRegularLabelOn: drawRoundLookOn: enableColorWith: fontToUse)
('events' mouseButton1Down:localPosition: mouseButton1Up:localPosition: mouseButton2Up:localPosition: mouseEnter: mouseLeave: mouseStillDown)
('event handling testing' handlesMouseDown: handlesMouseOver: handlesMouseStillDown:)
('event handling' mouseStillDownStepRate)
('initialization' defaultBorderWidth enableSelector: initialize model: model:stateGetter:action:label: secondaryActionSelector:)
('updating' update:)
('private' getEnabled getState magnifiedIcon)
('testing' is: isPressed isRoundButton mouseIsOver)
('geometry' extentChanged: minimumExtent)
('geometry testing')
('scrollbar button')
!



More information about the Cuis-dev mailing list