How do you make a Morph communicate with several other Morphs?

Bruce Cohen cohenb at gemstone.com
Wed Apr 29 20:52:10 UTC 1998


>> How do you make a button Morph tell three StringMorphs to change their contents?

Just for grins, I reconstructed the MultiTargetButtonMorph:

'From Squeak 1.31 of Feb 4, 1998 on 29 April 1998 at 12:45:29 pm'!
SimpleButtonMorph subclass: #MultiTargetButtonMorph
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Widgets'!

!MultiTargetButtonMorph methodsFor: 'initialization' stamp: 'bc 4/29/98 12:19'!
initialize

	super initialize.
	target := OrderedCollection new.! !


!MultiTargetButtonMorph methodsFor: 'events' stamp: 'bc 4/29/98 12:38'!
doButtonAction
	"Perform the action of this button. Subclasses may override this method. The default behavior is to send the button's actionSelector to its target object with its arguments."

	(target ~~ nil and: [actionSelector ~~ nil]) ifTrue: [
		Cursor normal showWhile: [
			target do: [ :item | item perform: actionSelector withArguments: arguments]]].
! !


!MultiTargetButtonMorph methodsFor: 'menu' stamp: 'bc 4/29/98 12:35'!
addCustomMenuItems: aCustomMenu hand: aHandMorph

	super addCustomMenuItems: aCustomMenu hand: aHandMorph.
	((self world rootMorphsAt: aHandMorph targetOffset) size > 1) ifTrue: [
		aCustomMenu add: 'add to target' action: #addToTarget:.
		aCustomMenu add: 'remove from target' action: #removeFromTarget:].

! !

!MultiTargetButtonMorph methodsFor: 'menu' stamp: 'bc 4/29/98 12:21'!
addToTarget: evt

	| rootMorphs |
	rootMorphs _ self world rootMorphsAt: evt hand targetOffset.
	rootMorphs size > 1
		ifTrue: [target addLast: (rootMorphs at: 2)]
		ifFalse: [^ self].
! !

!MultiTargetButtonMorph methodsFor: 'menu' stamp: 'bc 4/29/98 12:21'!
removeFromTarget: evt

	| rootMorphs |
	rootMorphs _ self world rootMorphsAt: evt hand targetOffset.
	rootMorphs size > 1
		ifTrue: [target remove: (rootMorphs at: 2)]
		ifFalse: [^ self].
! !

!MultiTargetButtonMorph methodsFor: 'menu' stamp: 'bc 4/29/98 12:27'!
setTarget: evt

	| rootMorphs |
	rootMorphs _ self world rootMorphsAt: evt hand targetOffset.
	target := OrderedCollection new.
	rootMorphs size > 1
		ifTrue: [target addLast: (rootMorphs at: 2)]
		ifFalse: [^ self].
! !





More information about the Squeak-dev mailing list