IconicButton ohne Border!

Lic. Edgar J. De Cleene edgardec2001 at yahoo.com.ar
Wed Aug 24 13:38:32 UTC 2005


I think what working code could be useful, so I take a part of my old
LogicCircus.
FileIn first the .st and then the Morph.
Works in any Squeak what you have , but in 3.8 all you need is drag and drop
into working .image.
The Switch is derived from ImageMorph and have two forms , one for ON and
one for OFF state.
See how change the ballon and how you could have a Morph with a menu
activated via yellow button (Option - click on Mac).

Cheers

Edgar

-------------- next part --------------
A non-text attachment was scrubbed...
Name: Switch.morph
Type: application/octet-stream
Size: 5381 bytes
Desc: not available
Url : http://lists.squeakfoundation.org/pipermail/squeak-dev/attachments/20050824/e948cd78/Switch.obj
-------------- next part --------------
'From Squeak3.8 of ''5 May 2005'' [latest update: #6665] on 24 August 2005 at 10:29:56 am'!
ImageMorph subclass: #Switch2Morph
	instanceVariableNames: 'imageON imageOFF state connection'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'LogicCircus'!

!Switch2Morph methodsFor: 'initialization' stamp: 'edc 3/31/2004 06:52'!
drawSockets
	| x y pataE |
	pataE _ PataMorph new.
	x _ self left - pataE width.
	y _ self center y.
	pataE position: x @ y.
	self addMorph: pataE! !

!Switch2Morph methodsFor: 'initialization' stamp: 'edc 3/31/2004 06:52'!
initialize
	super initialize.
	imageON _ Form fromFileNamed: 'SwitchON.gif'.
	imageOFF _ Form fromFileNamed: 'SwitchOFF2.gif'.
	state _ false.
	self image: imageOFF.
	self drawSockets.
	self isPartsBin.
	self openInHand! !


!Switch2Morph methodsFor: 'accessing' stamp: 'EDC 9/19/2002 06:56'!
state
^state! !


!Switch2Morph methodsFor: 'change reporting' stamp: 'EDC 9/19/2002 06:56'!
remoteControl: aBoolean 
	state _ aBoolean.
	self state
		ifTrue: [self image: imageON]
		ifFalse: [self image: imageOFF]! !


!Switch2Morph methodsFor: 'event handling' stamp: 'edc 3/31/2004 07:40'!
click: evt 
	state _ state not.
	self state
		ifTrue: [self image: imageON]
		ifFalse: [self image: imageOFF].
	
	self notifyConnection! !

!Switch2Morph methodsFor: 'event handling' stamp: 'EDC 9/19/2002 09:25'!
firstClickTimedOut: evt 
	| root popUp |
	root _ owner rootForGrabOf: self.
	root == nil
		ifTrue: ["Display hidden card in front"
			popUp _ self copy.
			self board owner owner addMorphFront: popUp.
			self world displayWorld.
			(Delay forMilliseconds: 750) wait.
			popUp delete]
		ifFalse: [evt hand grabMorph: root]! !

!Switch2Morph methodsFor: 'event handling' stamp: 'EDC 9/20/2002 07:36'!
handlesMouseDown: anEvent 
	^ self isPartsDonor not! !

!Switch2Morph methodsFor: 'event handling' stamp: 'EDC 9/19/2002 09:29'!
mouseDown: evt 
	| menu |
	evt yellowButtonPressed
		ifFalse: [^ evt hand waitForClicksOrDrag: self event: evt].
	menu _ MenuMorph new defaultTarget: self.
	self addMenuItemsTo: menu hand: evt hand.
	menu popUpEvent: evt in: self world! !

!Switch2Morph methodsFor: 'event handling' stamp: 'EDC 9/19/2002 08:29'!
startDrag: evt 
	"We'll get a mouseDown first, some mouseMoves, and a mouseUp event  
	last"
	self isSticky
		ifTrue: [^ self].
	evt isMouseDown
		ifTrue: [self showBalloon: 'drag (mouse down)' hand: evt hand.
			self world displayWorld.
			(Delay forMilliseconds: 750) wait].
	evt isMouseUp
		ifTrue: [self showBalloon: 'drag (mouse up)' hand: evt hand].
	(evt isMouseUp
			or: [evt isMouseDown])
		ifFalse: [self showBalloon: 'drag (mouse still down)' hand: evt hand.
			evt hand grabMorph: self]! !


!Switch2Morph methodsFor: 'connection'!
connection
	"Answer the object that connects the receiver to other Switches."

	^connection! !

!Switch2Morph methodsFor: 'connection'!
connection: anObject 
	"Set anObject to be the connection among two or more Switches. Make the 
	receiver a dependent of the argument, anObject."

	connection _ anObject.
	connection addDependent: self! !

!Switch2Morph methodsFor: 'connection' stamp: 'EDC 9/11/2002 18:03'!
isConnectionSet
	"Answer whether the receiver is connected to an object that coordinates  
	updates among switches."
	connection == nil
		ifTrue: [state _ true.^ false]
		ifFalse: 
			[^ true]! !

!Switch2Morph methodsFor: 'connection' stamp: 'EDC 9/19/2002 14:50'!
notifyConnection
	"Send the receiver's connection (if it exists) the message 'changed: self'  
	in  
	order for the connection to broadcast the change to other objects  
	connected by the connection."
	self isConnectionSet
		ifTrue: [self connection remoteControl: self state.
			"self connection doRemoteControlOther: submorphs first"]! !

!Switch2Morph methodsFor: 'connection' stamp: 'EDC 9/12/2002 11:40'!
removeConnection
	
	 connection _ nil! !


!Switch2Morph methodsFor: 'halos and balloon help' stamp: 'EDC 10/10/2002 06:35'!
balloonText
^'I `m a Switch and my state is ', state asString! !


!Switch2Morph methodsFor: 'menu' stamp: 'edc 3/30/2004 19:28'!
addMenuItemsTo: aMenu hand: aHandMorph 
	| menu |
	menu _ MenuMorph new.
	menu color: Color blue.
	menu
		color: (menu color alpha: 0.3).
	menu
		add: 'descablear '
		target: self
		action: #descablear.
	menu items
		do: [:i | i color: Color yellow;
				
				font: (StrikeFont
						familyName: 'Comic Bold'
						size: 18
						emphasized: 1)].
	menu invokeModal! !

!Switch2Morph methodsFor: 'menu' stamp: 'edc 3/31/2004 06:58'!
descablear
	submorphs
		do: [:each | 
			each isConnectionSet
				ifTrue: [each notifyRemoveMe].
			each color: Color yellow]! !


More information about the Squeak-dev mailing list