[Q] Morphic Color Problems

Chris Burkert christian.burkert at s2000.tu-chemnitz.de
Sat Jun 14 23:35:39 UTC 2003


Hi

I attached a changeset with all the code. The Problem can be 
discovered in WorldMenu>>build ... you can file it in, it just 
adds classes and you can remove everything by deleting category CGUI.

Here the 'problematic' lines how they theoretical should be:

controller1 _ CGUIRadioButtonController new
	when: #a send: #color: to: menu with: col1;
	when: #b send: #color: to: menu with: col2;
	when: #c send: #color: to: menu with: col3.

The Problem is, when I do a 'WorldMenu new open' the three Radio 
Buttons for the color don't change the color, but ... they change 
the color _sometimes_ if I empty the trash and/or write:

controller1 _ CGUIRadioButtonController new
	when: #a send: #color: to: menu with: col1 inspect;
	when: #b send: #color: to: menu with: col2;
	when: #c send: #color: to: menu with: col3.

Try it out and play with emptying the trash ... is this 
arbitrariness?

thanks a lot for answers ... I despair of that!
            Chris Burkert
-- 
http://www.chrisburkert.de/
-------------- next part --------------
'From Squeak3.6alpha of ''17 March 2003'' [latest update: #5247] on 15 June 2003 at 1:18:14 am'!
RectangleMorph subclass: #CGUIMenuHeadMorph
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'CGUI-Menu'!

!CGUIMenuHeadMorph commentStamp: 'chbu 12/4/2002 17:17' prior: 0!
I am the Header of a Menu. You can add more than one Header at any position from top to bottom in the Menu. Enjoy!!!

RectangleMorph subclass: #CGUIMenuItemMorph
	instanceVariableNames: 'target selector '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'CGUI-Menu'!

!CGUIMenuItemMorph commentStamp: 'chbu 12/4/2002 17:16' prior: 0!
I am a abstract Class for some Entrys of a CGUIMenuMorph, for example Buttons or Checkboxes. Look at my Subclasses.

Structure:
 target			Object
					Every Entry has a Target. The Button, the Checkbox, etc.
 selector		Symbol
					The Symbol, which is performed with the target at some event.!

CGUIMenuItemMorph subclass: #CGUIMenuButtonMorph
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'CGUI-Menu'!

!CGUIMenuButtonMorph commentStamp: 'chbu 12/4/2002 17:18' prior: 0!
I am a Button for the CGUIMenuMorph. When I'm clicked, I perform the selector on the target (see CGUIMenuItemMorph).!

CGUIMenuItemMorph subclass: #CGUIMenuCheckboxMorph
	instanceVariableNames: 'currentMorph currentState trueMorph falseMorph getState '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'CGUI-Menu'!
RectangleMorph subclass: #CGUIMenuMorph
	instanceVariableNames: 'morphs subMenus radioButtonController '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'CGUI-Menu'!

!CGUIMenuMorph commentStamp: 'chbu 12/4/2002 17:12' prior: 0!
I am the MenuMorph. You can add Buttons, Headers, SubMenuButtons, Checkboxes and RadioButtons. If you want more write the Maintainer of the Package, or write it yourself :=)

Structure:
 morphs			OrderedCollection
					I remember my submorphs, because I add them later as
					Submorphs.
 subMenus		Set
					I remember all the subMenus to delete them, if I am
					deleted, because they are not Submorphs of myself.!

CGUIMenuItemMorph subclass: #CGUIMenuRadioButtonMorph
	instanceVariableNames: 'trueMorph falseMorph key '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'CGUI-Menu'!
CGUIMenuItemMorph subclass: #CGUIMenuSubMorph
	instanceVariableNames: 'menu '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'CGUI-Menu'!

!CGUIMenuSubMorph commentStamp: 'chbu 12/4/2002 17:21' prior: 0!
I am a Morph that pops up a new (Sub-) Menu when the Mouse squeaks over me :=)

Structure:
 menu			CGUIMenuMorph
					I remember the Menu I controll.!

Object subclass: #CGUIRadioButtonController
	instanceVariableNames: 'radioButtons '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'CGUI-Controller'!
Object subclass: #WorldMenu
	instanceVariableNames: 'head button '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'CGUI-Menu-Examples'!

!WorldMenu commentStamp: 'chbu 12/4/2002 17:04' prior: 0!
I am an example for the CGUIMenuMorph and it's related Classes in CGUI-Menu. I'm just a Wrapperclass and hold the information for this (and possible more) Menu.

To see how to use CGUIMenuMorph look at #build and #open in my Class Methods.

Of course you can can add some methods to support the special action you want to be done. But add it in a class like me, not in CGUIMenuMorph!!!


!CGUIMenuHeadMorph methodsFor: 'accessing' stamp: 'chbu 12/11/2002 21:34'!
label: aLabel

	| label start |

	label _ StringMorph contents: aLabel.
	label
		name:	#label;
		color:	Color white;
		lock.
	start _ (self topLeft) + (1 at 0).
	self addMorph: label.
	self fillStyle
			origin: start;
			direction: ((self bottomLeft) - start).! !

!CGUIMenuHeadMorph methodsFor: 'initialization' stamp: 'chbu 12/11/2002 21:50'!
initialize

	| fill |

	super initialize.
	fill _ GradientFillStyle ramp: {
								0.0 -> ( Color	r: 0.3	g: 0.35	b: 0.4 ).
								1.0 -> ( Color	r: 0.55	g: 0.59	b: 0.62 )
								}.
	fill radial: false.
	self
		layoutPolicy:	TableLayout new;
		hResizing:		#spaceFill;
		vResizing:		#shrinkWrap;
		wrapCentering:	#center;
		layoutInset:		2;
		height:			15;
		borderWidth:	1;
		borderColor: 	Color black;
		color: 			( Color	r: 0.95	g: 0.95	b: 0.95 );
		fillStyle:		fill.! !


!CGUIMenuItemMorph methodsFor: 'accessing' stamp: 'chbu 12/3/2002 23:59'!
label: aLabel

	| label |

	label _ StringMorph contents: ' ', aLabel, ' '.
	label
		name:	#label;
		color:	Color white;
		lock.
	self addMorphBack: label.! !

!CGUIMenuItemMorph methodsFor: 'event handling' stamp: 'chbu 12/9/2002 22:46'!
aMouseDown: evt

	evt wasHandled: true.
	self borderColor: ( Color black ).! !

!CGUIMenuItemMorph methodsFor: 'event handling' stamp: 'chbu 12/9/2002 22:46'!
aMouseEnter: evt

	evt wasHandled: true.
	self borderColor: ( Color white ).! !

!CGUIMenuItemMorph methodsFor: 'event handling' stamp: 'chbu 12/9/2002 22:46'!
aMouseLeave: evt

	evt wasHandled: true.
	self borderColor: ( Color transparent ).! !

!CGUIMenuItemMorph methodsFor: 'event handling' stamp: 'chbu 12/9/2002 22:46'!
aMouseUp: evt

	evt wasHandled: true.
	self borderColor: ( Color transparent ).! !

!CGUIMenuItemMorph methodsFor: 'event handling' stamp: 'chbu 12/11/2002 21:17'!
disable

	| label |

	self lock.
	label _ (self submorphNamed: #label).
	label color: (label color alpha: 0.2).
	! !

!CGUIMenuItemMorph methodsFor: 'event handling' stamp: 'chbu 12/11/2002 21:18'!
enable

	| label |

	self unlock.
	label _ (self submorphNamed: #label).
	label color: (label color alpha: 1).
	! !

!CGUIMenuItemMorph methodsFor: 'initialization' stamp: 'chbu 12/11/2002 21:07'!
initialize

	super initialize.
	self
		on: #mouseEnter		send: #aMouseEnter:		to: self;
		on: #mouseLeave		send: #aMouseLeave:	to: self;
		on: #mouseDown		send: #aMouseDown:		to: self;
		on: #mouseUp			send: #aMouseUp:		to: self;
		borderWidth:	1;
		borderColor: 	Color transparent;
		color: 			Color transparent.
	self
		layoutPolicy:	TableLayout new;
		listDirection:	#rightToLeft;
		hResizing:		#spaceFill;
		vResizing:		#shrinkWrap;
		wrapCentering:	#bottomRight;
		lock.! !

!CGUIMenuItemMorph methodsFor: 'initialization' stamp: 'chbu 12/11/2002 21:09'!
selector: a

	selector _ a.
	(target ~~ nil and: [ selector ~~ nil ]) ifTrue: [ self unlock ].! !

!CGUIMenuItemMorph methodsFor: 'initialization' stamp: 'chbu 12/11/2002 21:09'!
target: a

	target _ a.
	(target ~~ nil and: [ selector ~~ nil ]) ifTrue: [ self unlock ].! !


!CGUIMenuButtonMorph methodsFor: 'event handling' stamp: 'chbu 12/9/2002 22:48'!
aMouseUp: evt

	super aMouseUp: evt.
	(target ~~ nil and: [selector ~~ nil]) ifTrue: [target perform: selector].! !

!CGUIMenuButtonMorph methodsFor: 'initialization' stamp: 'chbu 12/4/2002 16:05'!
initialize

	| symbol |

	super initialize.
	symbol _ (Form extent: 10 at 5 depth: 1 fromArray: #(
														2r00000000000000000000000000000000
														2r00000000000000000000000000000000
														2r00000000000000000000000000000000
														2r00000000000000000000000000000000
														2r00000000000000000000000000000000
														) offset: 0 at 0) asMorph.
	self addMorphBack: symbol.! !


!CGUIMenuCheckboxMorph methodsFor: 'event handling' stamp: 'chbu 12/9/2002 22:48'!
aMouseUp: evt

	super aMouseUp: evt.
	(target ~~ nil and: [selector ~~ nil]) ifTrue: [target perform: selector].
	self updateState.! !

!CGUIMenuCheckboxMorph methodsFor: 'initialization' stamp: 'chbu 12/4/2002 18:16'!
initialize

	super initialize.
	trueMorph _ (Form extent: 10 at 8 depth: 1 fromArray: #(
														2r11111111000000000000000000000000
														2r10000101000000000000000000000000
														2r10000101000000000000000000000000
														2r11001001000000000000000000000000
														2r10101001000000000000000000000000
														2r10110001000000000000000000000000
														2r10010001000000000000000000000000
														2r11111111000000000000000000000000
														) offset: 0 at 0) asMorph.
	falseMorph _ (Form extent: 10 at 8 depth: 1 fromArray: #(
														2r11111111000000000000000000000000
														2r10000001000000000000000000000000
														2r10000001000000000000000000000000
														2r10000001000000000000000000000000
														2r10000001000000000000000000000000
														2r10000001000000000000000000000000
														2r10000001000000000000000000000000
														2r11111111000000000000000000000000
														) offset: 0 at 0) asMorph.
	currentMorph _ falseMorph.
	self addMorphBack: falseMorph.! !

!CGUIMenuCheckboxMorph methodsFor: 'private' stamp: 'chbu 12/4/2002 18:11'!
updateState

	(target ~~ nil and: [getState ~~ nil])
		ifTrue: [
		(target perform: getState)
			ifTrue:	[
				self replaceSubmorph: currentMorph by: trueMorph.
				currentMorph _ trueMorph.
			]
			ifFalse:	[
				self replaceSubmorph: currentMorph by: falseMorph.
				currentMorph _ falseMorph.
			]
		]
	! !

!CGUIMenuCheckboxMorph methodsFor: 'accessing' stamp: 'chbu 12/4/2002 18:08'!
getState: a

	getState _ a.
	self updateState.! !

!CGUIMenuCheckboxMorph methodsFor: 'accessing' stamp: 'chbu 12/4/2002 17:43'!
toggleState: a

	super selector: a.! !


!CGUIMenuMorph methodsFor: 'accessing' stamp: 'chbu 12/4/2002 16:24'!
addButton: aBlock

	| button |

	button _ CGUIMenuButtonMorph new.
	aBlock value: button.
	self remember: button! !

!CGUIMenuMorph methodsFor: 'accessing' stamp: 'chbu 12/4/2002 17:41'!
addCheckbox: aBlock

	| box |

	box _ CGUIMenuCheckboxMorph new.
	aBlock value: box.
	self remember: box! !

!CGUIMenuMorph methodsFor: 'accessing' stamp: 'chbu 12/4/2002 16:24'!
addHeader: aBlock

	| head |

	head _ CGUIMenuHeadMorph new.
	aBlock value: head.
	self remember: head.! !

!CGUIMenuMorph methodsFor: 'accessing' stamp: 'chbu 12/11/2002 19:55'!
addLine

	self addLine: [ :a | ].! !

!CGUIMenuMorph methodsFor: 'accessing' stamp: 'chbu 12/4/2002 16:24'!
addLine: aBlock

	| line |

	line _ Morph new.
	line
		hResizing:		#spaceFill;
		height:			1;
		color:			Color black.
	aBlock value: line.
	self remember: line.! !

!CGUIMenuMorph methodsFor: 'accessing' stamp: 'chbu 12/11/2002 18:35'!
addRadioButton: aBlock

	| b |

	b _ CGUIMenuRadioButtonMorph new.
	aBlock value: b.
	self remember: b! !

!CGUIMenuMorph methodsFor: 'accessing' stamp: 'chbu 12/4/2002 16:25'!
addSubMenu: aBlock

	| menu |

	menu _ CGUIMenuSubMorph new.
	aBlock value: menu.
	self
		remember: menu;
		rememberSubMenu: menu.! !

!CGUIMenuMorph methodsFor: 'accessing' stamp: 'chbu 12/2/2002 23:43'!
build

	self
		layoutPolicy:		TableLayout new;
		listDirection:		#topToBottom;
		hResizing:			#shrinkWrap;
		vResizing:			#shrinkWrap;
		yourself.
	morphs do: [ :morph |
		self addMorphBack: morph
		].! !

!CGUIMenuMorph methodsFor: 'initialization' stamp: 'chbu 6/15/2003 01:03'!
initialize

	super initialize.
	morphs					_ OrderedCollection new.
	subMenus				_ Set new.
	radioButtonController	_ Dictionary new.
	self
		height:			15;
		borderWidth:	1;
		borderColor: 	Color black;
		color: 			self defaultColor.
! !

!CGUIMenuMorph methodsFor: 'private' stamp: 'chbu 6/15/2003 01:03'!
defaultColor

	^Color	r: 0.55	g: 0.59	b: 0.72! !

!CGUIMenuMorph methodsFor: 'private' stamp: 'chbu 12/4/2002 16:57'!
delete

	subMenus do: [ :each |
		each deleteYourMenu.
	].
	super delete.! !

!CGUIMenuMorph methodsFor: 'private' stamp: 'chbu 12/4/2002 16:24'!
remember: aMorph

	morphs add: aMorph.! !

!CGUIMenuMorph methodsFor: 'private' stamp: 'chbu 12/11/2002 18:24'!
rememberRadioButtonController: aController

	radioButtonController at: (aController key) put: aController.! !

!CGUIMenuMorph methodsFor: 'private' stamp: 'chbu 12/4/2002 16:25'!
rememberSubMenu: aMorph

	subMenus add: aMorph.! !


!CGUIMenuRadioButtonMorph methodsFor: 'event handling' stamp: 'chbu 12/11/2002 19:49'!
aMouseUp: evt

	super aMouseUp: evt.
	(target ~~ nil) ifTrue: [target triggerEvent: key].
	self select.! !

!CGUIMenuRadioButtonMorph methodsFor: 'initialization' stamp: 'chbu 12/11/2002 19:48'!
initialize

	super initialize.
	trueMorph _ (Form extent: 10 at 8 depth: 1 fromArray: #(
														2r00111100000000000000000000000000
														2r01000010000000000000000000000000
														2r10011001000000000000000000000000
														2r10111101000000000000000000000000
														2r10111101000000000000000000000000
														2r10011001000000000000000000000000
														2r01000010000000000000000000000000
														2r00111100000000000000000000000000
														) offset: 0 at 0) asMorph name: #true.
	falseMorph _ (Form extent: 10 at 8 depth: 1 fromArray: #(
														2r00111100000000000000000000000000
														2r01000010000000000000000000000000
														2r10000001000000000000000000000000
														2r10000001000000000000000000000000
														2r10000001000000000000000000000000
														2r10000001000000000000000000000000
														2r01000010000000000000000000000000
														2r00111100000000000000000000000000
														) offset: 0 at 0) asMorph name: #false.
	self addMorphBack: falseMorph.! !

!CGUIMenuRadioButtonMorph methodsFor: 'private' stamp: 'chbu 12/11/2002 19:50'!
deselect

	(self submorphNamed: #true) ifNotNil: [self replaceSubmorph: trueMorph by: falseMorph]! !

!CGUIMenuRadioButtonMorph methodsFor: 'private' stamp: 'chbu 12/11/2002 19:49'!
select

	(self submorphNamed: #false) ifNotNil: [self replaceSubmorph: falseMorph by: trueMorph]! !

!CGUIMenuRadioButtonMorph methodsFor: 'accessing' stamp: 'chbu 12/11/2002 19:46'!
key

	^key.! !

!CGUIMenuRadioButtonMorph methodsFor: 'accessing' stamp: 'chbu 12/11/2002 21:10'!
sendsKey: a to: b

	b register: self.
	self
		target: b;
		unlock.
	key _ a.! !


!CGUIMenuSubMorph methodsFor: 'event handling' stamp: 'chbu 12/9/2002 22:49'!
aMouseEnter: evt

	super aMouseEnter: evt.
	(target ~~ nil and: [selector ~~ nil]) ifTrue: [
		(menu ~~ nil)
			ifFalse: [
				menu _ target perform: selector.
			].
			menu openInWorld.
			menu position: (self topRight).
		].! !

!CGUIMenuSubMorph methodsFor: 'event handling' stamp: 'chbu 12/9/2002 22:49'!
aMouseLeave: evt

	super aMouseLeave: evt.
	(evt position x < self topRight x)
	ifTrue:
	[	(menu ~~ nil)
		ifTrue:
		[	menu delete.
		]
	]! !

!CGUIMenuSubMorph methodsFor: 'initialization' stamp: 'chbu 12/4/2002 00:58'!
initialize

	| symbol |

	super initialize.
	symbol _ (Form extent: 10 at 5 depth: 1 fromArray: #(
														2r11000000000000000000000000000000
														2r11110000000000000000000000000000
														2r11111110000000000000000000000000
														2r11110000000000000000000000000000
														2r11000000000000000000000000000000
														) offset: 0 at 0) asMorph.
	self addMorphBack: symbol.! !

!CGUIMenuSubMorph methodsFor: 'accessing' stamp: 'chbu 12/4/2002 16:56'!
deleteYourMenu

	(menu ~~ nil) ifTrue: [ menu delete ]! !


!CGUIRadioButtonController methodsFor: 'accessing' stamp: 'chbu 12/11/2002 19:41'!
register: aButton

	radioButtons add: aButton.! !

!CGUIRadioButtonController methodsFor: 'as yet unclassified' stamp: 'chbu 12/11/2002 19:40'!
initialize

	radioButtons _ Set new.! !

!CGUIRadioButtonController methodsFor: 'as yet unclassified' stamp: 'chbu 6/15/2003 01:00'!
triggerEvent: anEventSelector

	super triggerEvent: anEventSelector.
	radioButtons do: [ :each |
		(each key = anEventSelector) ifFalse: [ each deselect ].
	]! !


!CGUIRadioButtonController class methodsFor: 'as yet unclassified' stamp: 'chbu 12/11/2002 19:39'!
new

	^ super new initialize! !


!WorldMenu methodsFor: 'scripting' stamp: 'chbu 12/4/2002 20:30'!
headIsVisible

	^head visible! !

!WorldMenu methodsFor: 'scripting' stamp: 'chbu 12/9/2002 10:17'!
headToggleVisibility

	(self headIsVisible)
		ifFalse:	[ head show. head triggerEvent: #toggle ]
		ifTrue:	[ head hide. head triggerEvent: #toggle ]! !

!WorldMenu methodsFor: 'scripting' stamp: 'chbu 12/11/2002 21:28'!
transcriptIsEnabled

	^button isLocked not! !

!WorldMenu methodsFor: 'scripting' stamp: 'chbu 12/11/2002 21:28'!
transcriptToggle

	(self transcriptIsEnabled)
		ifFalse:	[ button enable. button triggerEvent: #toggle ]
		ifTrue:	[ button disable. button triggerEvent: #toggle ]! !

!WorldMenu methodsFor: 'accessing' stamp: 'chbu 6/15/2003 01:14'!
build
	" WorldMenu new open "

	| menu controller1 col1 col2 col3 |

	menu _ CGUIMenuMorph new.
	col1 _ menu defaultColor.
	col2 _ menu defaultColor alpha: 0.8.
	col3 _ menu defaultColor alpha: 0.3.
	controller1 _ CGUIRadioButtonController new
		when: #a		send: #color:		to: menu		with: col1;
		when: #b		send: #color:		to: menu		with: col2;
		when: #c		send: #color:		to: menu		with: col3.

	^menu
		addHeader:		[ :h1 | head _ h1
							label:			'Menu Example'
						];
		addButton:		[ :b1 | button _ b1
							label:			'open Transcript';
							setBalloonText:	'Open a new Transcript';
							target:			Transcript;
							selector:			#open
						];
		addLine;
		addRadioButton:	[ :r1 | r1
 							label:			'Default Menucolor';
							setBalloonText:	'change the Color of the Menu';
							sendsKey: #a	to: controller1.
						];
		addRadioButton:	[ :r2 | r2
 							label:			'transparent Default Menucolor';
							setBalloonText:	'change the Color of the Menu';
							sendsKey: #b	to: controller1.
						];
		addRadioButton:	[ :r3 | r3
 							label:			'transparent Black Menucolor';
							setBalloonText:	'change the Color of the Menu';
							sendsKey: #c	to: controller1.
						];
		addLine;
		addCheckbox:	[ :c1 | c1
							label:			'show / hide Header';
							setBalloonText:	'toggle the Header of this Menu on or off ... that''s just for fun to see if it works ... everything with events :-)';
							target:			self;
							getState:		#headIsVisible;
							selector:			#headToggleVisibility.
							head when: #toggle send: #updateState to: c1
						];
		addCheckbox:	[ :c2 | c2
							label:			'show / hide Header';
							setBalloonText:	'toggle the Header of this Menu on or off ... that''s just for fun to see if it works ... everything with events :-)';
							target:			self;
							getState:		#headIsVisible;
							selector:			#headToggleVisibility;
							disable;
							enable.
							head when: #toggle send: #updateState to: c2
						];
		addCheckbox:	[ :c3 | c3
							label:			'enable / disable Transcript Button';
							setBalloonText:	'toggle the Button on or off';
							target:			self;
							getState:		#transcriptIsEnabled;
							selector:			#transcriptToggle.
							head when: #toggle send: #updateState to: c3
						];
		addLine;
		addSubMenu:	[ :s1 | s1
							label:			'open ..';
							setBalloonText:	'a Menu with usefull Tools';
							target:			self;
							selector:			#buildOpenMenu
						];
		build.! !

!WorldMenu methodsFor: 'accessing' stamp: 'chbu 12/9/2002 10:39'!
buildOpenMenu

	| menu |

	menu _ CGUIMenuMorph new.
	^menu
		addHeader:		[ :h1 | h1
							label:			'open ..'
						];
		addButton:		[ :b1 | b1
							label:			'browser (b)';
							setBalloonText:	'A five-paned tool that lets you see all the code in the system';
							target:			Browser;
							selector:			#openBrowser
						];
		addButton:		[ :b2 | b2
							label:			'package-pane browser';
							setBalloonText:	'Similar to the regular browser, but adds an extra pane at top-left that groups class-categories that start with the same prefix';
							target:			PackagePaneBrowser;
							selector:			#openBrowser
						];
		addLine:		[ :l1 |
						];
		addButton:		[ :b7 | b7
							label:			'method finder';
							setBalloonText:	'A tool for discovering methods';
							target:			(TheWorldMenu new);
							selector:			#openSelectorBrowser
						];
		addButton:		[ :b8 | b8
							label:			'message names (W)';
							setBalloonText:	'A tool for finding and editing methods that contain any given keyword in their names.';
							target:			(TheWorldMenu new);
							selector:			#openMessageNames
						];
		addLine:		[ :l3 |
						];
		addButton:		[ :b15 | b15
							label:			'mvc project';
							setBalloonText:	'Creates a new project of the classic "mvc" style';
							target:			(TheWorldMenu new);
							selector:			#openMVCProject
						];
		addButton:		[ :b16 | b16
							label:			'morphic project';
							setBalloonText:	'Creates a new morphic project';
							target:			(TheWorldMenu new);
							selector:			#openMorphicProject
						];
		build.! !

!WorldMenu methodsFor: 'accessing' stamp: 'chbu 6/15/2003 00:44'!
open
	" WorldMenu new open "

	self build openInHand.! !

WorldMenu removeSelector: #trans!

!WorldMenu reorganize!
('scripting' headIsVisible headToggleVisibility transcriptIsEnabled transcriptToggle)
('accessing' build buildOpenMenu open)
!

CGUIMenuMorph removeSelector: #color:!
CGUIMenuMorph removeSelector: #trans!

!CGUIMenuCheckboxMorph reorganize!
('event handling' aMouseUp:)
('initialization' initialize)
('private' updateState)
('accessing' getState: toggleState:)
!



More information about the Squeak-dev mailing list