[squeak-dev] The Inbox: Morphic-phite.429.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Apr 26 08:28:58 UTC 2010


A new version of Morphic was added to project The Inbox:
http://source.squeak.org/inbox/Morphic-phite.429.mcz

==================== Summary ====================

Name: Morphic-phite.429
Author: phite
Time: 26 April 2010, 10:28:16.551 am
UUID: 9b7e8e83-92c6-3742-b34d-e06b6e88450c
Ancestors: Morphic-phite.428

Refactored the DockingBar and the WorldMenu to add custom self-defined menus. (See class comment of MenuEntrySpec)

Changed Class comments of TheWorldMenu and TheWorldMainDockingBar. They now reference MenuEntrySpec to explain how new menu entries may be added.

=============== Diff against Morphic-phite.428 ===============

Item was changed:
  ----- Method: MenuMorph>>addLine (in category 'construction') -----
  addLine
  	"Append a divider line to this menu. Suppress duplicate lines."
  	self hasItems
  		ifFalse: [^ self].
  	(self lastSubmorph isKindOf: MenuLineMorph)
  		ifFalse: [self addMorphBack: MenuLineMorph new] !

Item was changed:
  ----- Method: MenuEntrySpec classSide>>newFrom: (in category 'as yet unclassified') -----
  newFrom: aDict
  	"Creates a new MenuEntrySpec from a Dictionary.
  	Possible keys are: #contents, #help, #icon, #selectedIcon,
+ 	#target, #selector, #argument, #location, #position, #dockingBar, #worldMenu
- 	#target, #selector, #argument, #location, #position
  	where #location describes where the menuEntry should be placed
+ 		#location -> nil creates a new menuEntry in the Menu
- 		#location -> nil creates a new menuEntry in the DockingBar
  		#location -> #('Tools' 'subMenu' 'subMenu2') puts the menuEntry into submenus
  	and where #position describes the position of the menuEntry within a menu eg.
  		#position -> #last - adds the menuEntry at the end of the menu (#first at the beginning)
  		#position -> #(#before 'Help') - adds the menuEntry just before the 'Help' entry (#after adds it after the entry)"
  
  	^ self new
  		contents: (aDict at: #contents ifAbsent: '');
  		help: (aDict at: #help ifAbsent: nil);
  		icon: (aDict at: #icon ifAbsent: nil);
  		selectedIcon: (aDict at: #selectedIcon ifAbsent: nil);
  		target: (aDict at: #target ifAbsent: nil);
  		selector: (aDict at: #selector ifAbsent: nil);
  		arguments: (aDict at: #arguments ifAbsent: nil);
  		location: (aDict at: #location ifAbsent: nil);
+ 		position: (aDict at: #position ifAbsent: #last);
+ 		dockingBar: (aDict at: #dockingBar ifAbsent: true);
+ 		worldMenu: (aDict at: #worldMenu ifAbsent: true)!
- 		position: (aDict at: #position ifAbsent: #last)!

Item was changed:
  ----- Method: MenuEntrySpec>>installOn: (in category 'menu-creation') -----
+ installOn: aMenu
+ 	"Installs a menuEntry corresponding to this specification into the given menu"
- installOn: aDockingBar
- 	"Installs a menuEntry corresponding to this specification into the given DockingBar"
  
  	| menu |
+ 	menu := self findOrCreateLocationIn: aMenu.
- 	menu := self findOrCreateLocationIn: aDockingBar.
  	menu subMenu ifNil: [ menu addSubMenu: [:subMenu |] ].
  	menu subMenu addItem: [ :item |
  		item
  			contents: self contents;
  			help: self help;
  			icon: self icon;
  			target: self target;
  			selector: self selector;
  			arguments: self arguments.
  		(item respondsTo: #selectedIcon:) ifTrue: [ item selectedIcon: self selectedIcon ].]
  		at: self position.!

Item was added:
+ ----- Method: MenuEntrySpec>>worldMenu: (in category 'accessing') -----
+ worldMenu: aBoolean
+ 	"True/False - wether this menu entry describes a MenuEntry in the WorldMenu"
+ 	worldMenu := aBoolean!

Item was changed:
  ----- Method: TheWorldMenu>>buildWorldMenu (in category 'construction') -----
  buildWorldMenu
  	"Build the menu that is put up when the screen-desktop is clicked on"
  	| menu |
  	menu := MenuMorph new defaultTarget: self.
  	menu commandKeyHandler: self.
  	self colorForDebugging: menu.
  	menu addStayUpItem.
  	self makeConvenient: menu.
  	Smalltalk at: #ServiceGUI ifPresent:[:sgui|
  		sgui worldMenu: menu.
  		sgui onlyServices ifTrue: [^ menu].
  	].
  	self addProjectEntries: menu.
  	myWorld addUndoItemsTo: menu.
  	self addRestoreDisplay: menu.
  	self addUtilities: menu.
  	self addObjectsAndTools: menu.
  	self addPrintAndDebug: menu.
  	self addSaveAndQuit: menu.
+ 	self addCustomMenus: menu.
  	^ menu!

Item was added:
+ ----- Method: MenuEntrySpec>>worldMenu (in category 'accessing') -----
+ worldMenu
+ 	"True/False - wether this menu entry describes a MenuEntry in the WorldMenu"
+ 	^ worldMenu!

Item was added:
+ ----- Method: MenuEntrySpec classSide>>findAllForDockingBar (in category 'as yet unclassified') -----
+ findAllForDockingBar
+ 	"Searches for MenuEntrySpecs which are meant do be displayed in the DockingBar."
+ 
+ 	^ self findAll select: [ :spec | spec dockingBar ]!

Item was changed:
  ----- Method: TheWorldMainDockingBar>>customMenusOn: (in category 'construction') -----
  customMenusOn: aDockingBar
  	"Searches for MenuEntrySpecs and add the corresponding menus to the docking bar."
+ 	
+ 	MenuEntrySpec findAllForDockingBar do: [ :spec |
- 	| menuSpecs |
- 	menuSpecs := self searchForMenuSpecs sortBy: [ :a :b | a location size > b location size].
- 	menuSpecs do: [ :spec |
  		spec installOn: aDockingBar].!

Item was added:
+ ----- Method: MenuMorph>>subMenu (in category 'accessing') -----
+ subMenu
+ 	"For convenience. As I don't have submenus, I act as the submenu."
+ 	^ self!

Item was added:
+ ----- Method: MenuEntrySpec>>dockingBar (in category 'accessing') -----
+ dockingBar
+ 	"True/False - wether this menu entry describes a MenuEntry in the DockingBar"
+ 	^ dockingBar!

Item was changed:
  ----- Method: MenuEntrySpec>>findOrCreateLocationIn: (in category 'menu-creation') -----
+ findOrCreateLocationIn: aMenu
- findOrCreateLocationIn: aDockingBar
  	"find the menu my location points at - create it, if it does not exist."
  
  	| currentMenu |
+ 	location size = 0 ifTrue: [ ^ aMenu ].
+ 	currentMenu := aMenu.
- 	location size = 0 ifTrue: [ ^ aDockingBar ].
- 	currentMenu := aDockingBar.
  	(1 to: location size) do: [ :i |
  		currentMenu := currentMenu menus detect:
  		[ :m | m contents = (location at: i) ]
  		ifNone: [
  			currentMenu subMenu ifNil: [ currentMenu addSubMenu:[:subMenu| ]].
  			currentMenu subMenu addItem: [:item|
  				item contents: (location at: i)].
  			currentMenu menus detect: [ :m | m contents = (location at: i) ]]].
  	^ currentMenu!

Item was changed:
  Object subclass: #TheWorldMainDockingBar
  	instanceVariableNames: ''
  	classVariableNames: 'Instance TS'
  	poolDictionaries: ''
  	category: 'Morphic-Kernel'!
+ 
+ !TheWorldMainDockingBar commentStamp: 'phite 4/26/2010 09:48' prior: 0!
+ TheWorldMainDockingBar serves to present a Squeak menu which is always visible whithin a World.
+ 
+ It is possible to add custom menu entries to the WorldMenu. Please have a look at the MenuEntrySpec comments for examples.!

Item was changed:
  ----- Method: MenuMorph>>add:action: (in category 'construction') -----
  add: aString action: aSymbolOrValuable
  	"Append a menu item with the given label. If the item is selected, it will send the given selector to the default target object."
  	"Details: Note that the menu item added captures the default target object at the time the item is added; the default target can later be changed before added additional items without affecting the targets of previously added entries. The model is that each entry is like a button that knows everything it needs to perform its action."
  	aSymbolOrValuable isSymbol ifTrue:[
  		self add: aString
  			target: defaultTarget
  			selector: aSymbolOrValuable
  			argumentList: EmptyArray.
  	] ifFalse:[
  		self add: aString
  			target: aSymbolOrValuable
  			selector: #value
  			argumentList: EmptyArray.
  	]
  !

Item was changed:
  Object subclass: #TheWorldMenu
  	instanceVariableNames: 'myProject myWorld myHand'
  	classVariableNames: 'OpenMenuRegistry'
  	poolDictionaries: ''
  	category: 'Morphic-Kernel'!
  
+ !TheWorldMenu commentStamp: 'phite 4/26/2010 09:47' prior: 0!
- !TheWorldMenu commentStamp: 'sw 10/5/2002 00:44' prior: 0!
  Instances of TheWorldMenu serve to present the primary Squeak menu obtained by clicking on open desktop, which is variously spoken of as the "screen menu", the "desktop menu", or the "world menu".
  
  myProject is the Project I pertain to.
  myWorld is the world, a PasteUpMorph, that I pertain to.
+ myHand is the hand that invoked the menu.
+ 
+ It is possible to add custom menu entries to the WorldMenu. Please have a look at the MenuEntrySpec comments for examples.!
- myHand is the hand that invoked the menu.!

Item was added:
+ ----- Method: MenuEntrySpec classSide>>findAllForWorldMenu (in category 'as yet unclassified') -----
+ findAllForWorldMenu
+ 	"Searches for MenuEntrySpecs which are meant do be displayed in the WorldMenu."
+ 
+ 	^ self findAll select: [ :spec | spec worldMenu ]!

Item was added:
+ ----- Method: MenuEntrySpec classSide>>allSpecAndSpecArrays (in category 'as yet unclassified') -----
+ allSpecAndSpecArrays
+ 	"Searches for MenuEntrySpecs. We scan all classes for #menuEntrySpecification methods and answer an Array of all menuSpecs found."
+ 	
+ 	^ ((self systemNavigation allClassesImplementing: #menuEntrySpecification)
+ 		collect: [ :aClass | aClass theNonMetaClass menuEntrySpecification])!

Item was added:
+ ----- Method: MenuEntrySpec>>dockingBar: (in category 'accessing') -----
+ dockingBar: aBoolean
+ 	"True/False - wether this menu entry describes a MenuEntry in the DockingBar"
+ 	dockingBar := aBoolean!

Item was changed:
  ----- Method: MenuMorph>>addItem:at: (in category 'construction') -----
  addItem: aBlock at: position
  	| item |
  	item := MenuItemMorph new.
  	aBlock value: item.
  	self addMenuItem: item at: position!

Item was added:
+ ----- Method: MenuEntrySpec classSide>>newForDockingBarFrom: (in category 'as yet unclassified') -----
+ newForDockingBarFrom: aDict
+ 	"Creates a new MenuEntrySpec from a Dictionary.
+ 	Possible keys are: #contents, #help, #icon, #selectedIcon,
+ 	#target, #selector, #argument, #location, #position
+ 	where #location describes where the menuEntry should be placed
+ 		#location -> nil creates a new menuEntry in the DockingBar
+ 		#location -> #('Tools' 'subMenu' 'subMenu2') puts the menuEntry into submenus
+ 	and where #position describes the position of the menuEntry within a menu eg.
+ 		#position -> #last - adds the menuEntry at the end of the menu (#first at the beginning)
+ 		#position -> #(#before 'Help') - adds the menuEntry just before the 'Help' entry (#after adds it after the entry)"
+ 
+ 	^ self new
+ 		contents: (aDict at: #contents ifAbsent: '');
+ 		help: (aDict at: #help ifAbsent: nil);
+ 		icon: (aDict at: #icon ifAbsent: nil);
+ 		selectedIcon: (aDict at: #selectedIcon ifAbsent: nil);
+ 		target: (aDict at: #target ifAbsent: nil);
+ 		selector: (aDict at: #selector ifAbsent: nil);
+ 		arguments: (aDict at: #arguments ifAbsent: nil);
+ 		location: (aDict at: #location ifAbsent: nil);
+ 		position: (aDict at: #position ifAbsent: #last);
+ 		dockingBar: true;
+ 		worldMenu: false.!

Item was added:
+ ----- Method: MenuEntrySpec classSide>>newForWorldMenuFrom: (in category 'as yet unclassified') -----
+ newForWorldMenuFrom: aDict
+ 	"Creates a new MenuEntrySpec from a Dictionary.
+ 	Possible keys are: #contents, #help, #icon, #selectedIcon,
+ 	#target, #selector, #argument, #location, #position
+ 	where #location describes where the menuEntry should be placed
+ 		#location -> nil creates a new menuEntry in the DockingBar
+ 		#location -> #('Tools' 'subMenu' 'subMenu2') puts the menuEntry into submenus
+ 	and where #position describes the position of the menuEntry within a menu eg.
+ 		#position -> #last - adds the menuEntry at the end of the menu (#first at the beginning)
+ 		#position -> #(#before 'Help') - adds the menuEntry just before the 'Help' entry (#after adds it after the entry)"
+ 
+ 	^ self new
+ 		contents: (aDict at: #contents ifAbsent: '');
+ 		help: (aDict at: #help ifAbsent: nil);
+ 		icon: (aDict at: #icon ifAbsent: nil);
+ 		selectedIcon: (aDict at: #selectedIcon ifAbsent: nil);
+ 		target: (aDict at: #target ifAbsent: nil);
+ 		selector: (aDict at: #selector ifAbsent: nil);
+ 		arguments: (aDict at: #arguments ifAbsent: nil);
+ 		location: (aDict at: #location ifAbsent: nil);
+ 		position: (aDict at: #position ifAbsent: #last);
+ 		dockingBar: false;
+ 		worldMenu: true.!

Item was added:
+ ----- Method: TheWorldMenu>>addCustomMenus: (in category 'construction') -----
+ addCustomMenus: menu
+ 	"Looks for menuEntries defined in other classes and adds them."
+ 
+ 	MenuEntrySpec findAllForWorldMenu do: [ :spec |
+ 		spec installOn: menu ].!

Item was changed:
  Object subclass: #MenuEntrySpec
+ 	instanceVariableNames: 'contents help icon selectedIcon target selector location arguments position dockingBar worldMenu'
- 	instanceVariableNames: 'contents help icon selectedIcon target selector location arguments position'
  	classVariableNames: ''
  	poolDictionaries: ''
+ 	category: 'Morphic-Menus'!
+ 
+ !MenuEntrySpec commentStamp: 'phite 4/26/2010 10:20' prior: 0!
+ You may define MenuEntrySpecs to add custom menus to TheWorldMainDockingBar or TheWorldMenu.
+ 
+ To add add custom menu entries your class needs to answer to #menuEntrySpecification.
+ #menuEntrySpecification may answer an instance of MenuEntrySpec or an array of MenuEntrySpecs for multiple menus.
+ 
+ Example:
+ MenuEntrySpec newForDockingBarFrom: (Dictionary newFromPairs: #(
+ 		#contents 'Hello?'
+ 		#location #('Help' 'a subMenu' 'another subMenu')
+ 		#target MenuMorph #selector #inform: #arguments #('Hello World!!')
+ 		))
+ 
+ The example above creates a MenuEntrySpec called 'Hello?' located in the Help-menu within some submenus. As you may see MenuEntrySpecs can be created with the help of an options dictionary. The options are explained later. Remember: You do not need to specify option you do not need.
+ 
+ MenuEntrySpec newForDockingBarFrom:  a Dictionary - created a menu entry for the DockingBar
+ MenuEntrySpec newForWorldMenuFrom: a Dictionary - creates a menu entry for the WorldMenu
+ MenuEntrySpec newFrom: a Dictionary - creates a menu entry for both
+ 
+ Possible options:
+ #contents
+ 	A String that is the visible label the user should click on
+ #help
+ 	A String that may be shown in a bubble near the menu entry for the user's help
+ #icon
+ 	A Form which is displayed near the label
+ #selectedIcon
+ 	A Form which is displayed instead of the icon when the menuEntry is selected
+ #target
+ 	An Object which is called when the user clicks on the menu entry
+ #selector
+ 	A Symol which is sent the the target
+ #argument
+ 	An Array of Arguments which are sent with the selector
+ #location
+ 	An Arrray of Strings which describes the place the menuEntry should be displayed.
+ 	#location -> nil or #() creates the menu entry in the top-level of the menu
+ 	#location -> #('Help') creates the menu entry in the Help-menu
+ 	#location -> #('Help' 'mySubMenu') creates the entry in a submenu of the Help-menu. If the submenu 'mySubMenu' does not exist it will be created
+ #position
+ 	A Symbol or Array describing the position of the menu entry within a menu.
+ 	#position -> #first creates the entry in the first slot of a menu
+ 	#position -> #last creates the entry in the last slot
+ 	#position -> #(#before 'Help') creates the entry just before the Help-menu
+ 	#position -> #(#after 'Help') creates the entry just after the Help-menu
+ 	If you reference a menu entry with #before or #after, be sure the menu entry exists.
+ #dockingBar
+ 	A Boolean that defines whether the menu entry should be displayed in the DockingBar.
+ 	This is always true if you use MenuEntrySpec newForDockingBarFrom:  a Dictionary
+ #worldMenu
+ 	A Boolean that defines whether the menu entry should be displayed in the WorldMenu.
+ 	This is always true if you use MenuEntrySpec newForWorldMenuFrom:  a Dictionary!
- 	category: 'Morphic-Menus-DockingBar'!

Item was added:
+ ----- Method: MenuEntrySpec classSide>>findAll (in category 'as yet unclassified') -----
+ findAll
+ 	"Searches for MenuEntrySpecs. We scan all classes for #menuEntrySpecification methods and answer an Array of all menuSpecs found."
+ 	
+ 	| flattenEncoder |
+ 	"We may get the specs in arrays, so we need to flatten."
+ 	flattenEncoder := FlattenEncoder stream: (WriteStream with: #()).
+ 	self allSpecAndSpecArrays flattenOnStream: flattenEncoder.
+ 	^ flattenEncoder contents!

Item was removed:
- ----- Method: TheWorldMainDockingBar>>searchForMenuSpecs (in category 'construction') -----
- searchForMenuSpecs
- 	"This is a one-time only method for creating the worlds DockingBar. Here we scann all classes for #menuEntrySpecification methods and answer an Array of all menuSpecs found."
- 
- 	^ ((self systemNavigation allClassesImplementing: #menuEntrySpecification)
- 		collect: [ :aClass | aClass theNonMetaClass menuEntrySpecification])!




More information about the Squeak-dev mailing list