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

commits at source.squeak.org commits at source.squeak.org
Sun Apr 25 18:17:28 UTC 2010


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

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

Name: Morphic-phite.428
Author: phite
Time: 25 April 2010, 8:16:06.137 pm
UUID: a876e2b3-d755-1845-9002-16c2c0dde809
Ancestors: Morphic-ar.427

Refactored DockingBar to add dynamically add entries.

Any class that implements #menuEntrySpecification may create a new menuEntry.

#menuEntrySpecification answers a MenuEntrySpec.
Example:
menuEntrySpecification
	"Answer a MenuEntrySpec object that declares my menuEntrie in the world docking"

	^ MenuEntrySpec newFrom: (Dictionary newFromPairs: #(
		#contents 'Well... hello?'
		#help 'Displays the Hello World'
		#location #('Help')
		#target MenuMorph #selector #inform: #arguments #('Hello World!')
		#position #first))
		
#location specifies the location within the DockingBar. It may be #() to create a top-level menu or #('Help' 'subMenu1' 'subMenu2') to create a menuEntry within some sub menus in Help.

#position may be #first, #last or #(before 'Keyboard Shortcuts'), #(#after ''Keyboard Shortcuts'') to declare the menuEntry's position within the a menu.

=============== Diff against Morphic-ar.427 ===============

Item was added:
+ ----- Method: MenuEntrySpec>>selectedIcon (in category 'accessing') -----
+ selectedIcon
+ 
+ 	^ selectedIcon!

Item was added:
+ ----- Method: MenuEntrySpec>>selectedIcon: (in category 'accessing') -----
+ selectedIcon: anIcon
+ 
+ 	selectedIcon := anIcon!

Item was changed:
  ----- Method: DockingBarMorph>>add:icon:selectedIcon:help:subMenu: (in category 'construction') -----
  add: wordingString icon: aForm selectedIcon: anotherForm help: helpString subMenu: aMenuMorph 
  	"Append the given submenu with the given label."
+ 
+ 	self add: wordingString icon: aForm selectedIcon: anotherForm help: helpString subMenu: aMenuMorph position: {#back}.!
- 	| item |
- 	item := DockingBarItemMorph new
- 		contents: wordingString;
- 		subMenu: aMenuMorph;
- 		icon: aForm;
- 		selectedIcon: anotherForm.
- 	helpString isNil ifFalse: [
- 		item setBalloonText: helpString ].
- 	self addMorphBack: item!

Item was added:
+ ----- 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
+ 	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)!

Item was added:
+ ----- Method: MenuEntrySpec>>selector (in category 'accessing') -----
+ selector
+ 
+ 	^ selector!

Item was added:
+ ----- Method: MenuEntrySpec>>installOn: (in category 'menu-creation') -----
+ installOn: aDockingBar
+ 	"Installs a menuEntry corresponding to this specification into the given DockingBar"
+ 
+ 	| menu |
+ 	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>>target: (in category 'accessing') -----
+ target: anObject
+ 
+ 	target := anObject!

Item was added:
+ ----- Method: MenuEntrySpec>>position (in category 'accessing') -----
+ position
+ 
+ 	^ position!

Item was added:
+ ----- Method: MenuEntrySpec>>location (in category 'accessing') -----
+ location
+ 	"An Array containing the menu and submenues the menu should be placed."
+ 	
+ 	^ location!

Item was added:
+ ----- Method: MenuEntrySpec>>contents (in category 'accessing') -----
+ contents
+ 	"The label of the menuEntry."
+ 	
+ 	^ contents!

Item was added:
+ ----- Method: MenuMorph>>addMenuItem:at: (in category 'construction') -----
+ addMenuItem: aMenuItemMorph at: position
+ 	"adds the Menu at the given position. Position is an Array of the form
+ 		{#last}, {#first}, {#before . 'Help'}, {#after . 'Tools'}"
+ 
+ 	((position at: 1) = #first) ifTrue: [ ^ self addMorphFront: aMenuItemMorph ].
+ 	((position at: 1) = #before) ifTrue: [ ^ self addMorph: aMenuItemMorph inFrontOf:
+ 		(self menus detect: [ :menu | menu contents = (position at: 2) ]) ].
+ 	((position at: 1) = #after) ifTrue: [ ^ self addMorph: aMenuItemMorph behind:
+ 		(self menus detect: [ :menu | menu contents = (position at: 2) ]) ].
+ 	"#last"
+ 	self addMorphBack: aMenuItemMorph.!

Item was added:
+ ----- Method: DockingBarMenuMorph>>menus (in category 'as yet unclassified') -----
+ menus
+ 	"Answers an array of my menuEntries"
+ 	^ self submorphs select: [:aMorph | aMorph isKindOf: MenuItemMorph]!

Item was added:
+ ----- 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])!

Item was added:
+ ----- Method: MenuEntrySpec>>arguments: (in category 'accessing') -----
+ arguments: anArray
+ 
+ 	arguments := anArray!

Item was added:
+ ----- Method: DockingBarMorph>>subMenu (in category 'accessing') -----
+ subMenu
+ 	"This is for convenience and makes the DockingBar look more like a MenuMorph."
+ 
+ 	^ self!

Item was added:
+ ----- Method: DockingBarMorph>>addMenu:atPosition: (in category 'construction') -----
+ addMenu: item atPosition: position
+ 	"adds the Menu at the given position. Position is an Array of the form
+ 		{#last}, {#first}, {#before . 'Help'}, {#after . 'Tools'}"
+ 
+ 	((position at: 1) = #first) ifTrue: [ ^ self addMorphFront: item ].
+ 	((position at: 1) = #before) ifTrue: [ ^ self addMorph: item inFrontOf:
+ 		(self menus detect: [ :menu | menu contents = (position at: 2) ]) ].
+ 	((position at: 1) = #after) ifTrue: [ ^ self addMorph: item behind:
+ 		(self menus detect: [ :menu | menu contents = (position at: 2) ]) ].
+ 	"#last"
+ 	self addMorphBack: item.!

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

Item was added:
+ ----- Method: MenuEntrySpec>>icon: (in category 'accessing') -----
+ icon: anIcon
+ 
+ 	icon := anIcon!

Item was added:
+ ----- Method: MenuEntrySpec>>findOrCreateLocationIn: (in category 'menu-creation') -----
+ findOrCreateLocationIn: aDockingBar
+ 	"find the menu my location points at - create it, if it does not exist."
+ 
+ 	| currentMenu |
+ 	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 added:
+ ----- Method: DockingBarMorph>>addItem:at: (in category 'construction') -----
+ addItem: aBlock at: position
+ 	| item |
+ 	item := DockingBarItemMorph new.
+ 	aBlock value: item.
+ 	self addMenu: item atPosition: position.!

Item was added:
+ ----- Method: MenuItemMorph>>menus (in category 'accessing') -----
+ menus
+ 	"Answers an array of my submenus"
+ 	self subMenu ifNil: [ ^ #() ].
+ 	^ self subMenu submorphs select: [:aMorph | aMorph isKindOf: MenuItemMorph]!

Item was added:
+ ----- Method: DockingBarItemMorph>>menus (in category 'as yet unclassified') -----
+ menus
+ 	"Answers an array of my submenus"
+ 	self subMenu ifNil: [ ^ #() ].
+ 	^ self subMenu submorphs select: [:aMorph | aMorph isKindOf: MenuItemMorph]!

Item was added:
+ ----- Method: MenuEntrySpec>>target (in category 'accessing') -----
+ target
+ 
+ 	^ target!

Item was added:
+ ----- Method: MenuEntrySpec>>location: (in category 'accessing') -----
+ location: stringOrArray
+ 	"Encapsulates the parameter into an Array."
+ 	
+ 	stringOrArray ifNil: [ location := #() ].
+ 	stringOrArray isString ifTrue: [ location := #(stringOrArray) ].
+ 	stringOrArray isArray ifTrue: [ location := stringOrArray ].!

Item was added:
+ ----- 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>>selector: (in category 'accessing') -----
+ selector: aSymbol
+ 
+ 	selector := aSymbol!

Item was added:
+ ----- Method: DockingBarMorph>>menus (in category 'menu') -----
+ menus
+ 	"Answers an array of menus in this docking bar"
+ 	^ self submorphs select: [:aMorph | aMorph isKindOf: MenuItemMorph]!

Item was changed:
  ----- Method: DockingBarMorph>>add:icon:help:subMenu: (in category 'construction') -----
  add: wordingString icon: aForm help: helpString subMenu: aMenuMorph 
  	"Append the given submenu with the given label."
+ 
+ 	self add: wordingString icon: aForm selectedIcon: nil help: helpString subMenu: aMenuMorph.!
- 	| item |
- 	item := DockingBarItemMorph new.
- 	item contents: wordingString.
- 	item subMenu: aMenuMorph.
- 	item icon: aForm.
- 	helpString isNil
- 		ifFalse: [item setBalloonText: helpString].
- 	self addMorphBack: item!

Item was added:
+ ----- Method: MenuEntrySpec>>help: (in category 'accessing') -----
+ help: aString
+ 
+ 	help := aString!

Item was added:
+ ----- Method: MenuEntrySpec>>position: (in category 'accessing') -----
+ position: symbolOrArray
+ 	"The Array either is kind of #(#symbol) - where #symbol is #first or #last
+ 	or #(#symbol 'string') - where #symbol is #before or #after and string is the label of a menu"
+ 
+ 	symbolOrArray isSymbol ifTrue: [ position := { symbolOrArray } ].
+ 	symbolOrArray isArray ifTrue: [ position := symbolOrArray ].!

Item was added:
+ ----- Method: MenuMorph>>menus (in category 'accessing') -----
+ menus
+ 	"Answers an array of my menuEntries"
+ 	^ self submorphs select: [:aMorph | aMorph isKindOf: MenuItemMorph]!

Item was added:
+ ----- Method: MenuEntrySpec>>arguments (in category 'accessing') -----
+ arguments
+ 
+ 	^ arguments!

Item was added:
+ ----- Method: DockingBarMorph>>add:icon:selectedIcon:help:subMenu:position: (in category 'construction') -----
+ add: wordingString icon: aForm selectedIcon: anotherForm help: helpString subMenu: aMenuMorph position: position
+ 	"Append the given submenu with the given label."
+ 	| item |
+ 	item := DockingBarItemMorph new
+ 		contents: wordingString;
+ 		subMenu: aMenuMorph;
+ 		icon: aForm;
+ 		selectedIcon: anotherForm.
+ 	helpString isNil ifFalse: [
+ 		item setBalloonText: helpString ].
+ 	self addMenu: item atPosition: position.!

Item was added:
+ ----- Method: MenuEntrySpec>>help (in category 'accessing') -----
+ help
+ 
+ 	^ help!

Item was added:
+ Object subclass: #MenuEntrySpec
+ 	instanceVariableNames: 'contents help icon selectedIcon target selector location arguments position'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Morphic-Menus-DockingBar'!

Item was added:
+ ----- Method: MenuEntrySpec>>contents: (in category 'accessing') -----
+ contents: aString
+ 	"The label of the menuEntry."
+ 	
+ 	contents := aString!

Item was changed:
  ----- Method: DockingBarMorph>>addItem: (in category 'construction') -----
  addItem: aBlock
+ 
+ 	self addItem: aBlock at: { #last }.!
- 	| item |
- 	item := DockingBarItemMorph new.
- 	aBlock value: item.
- 	self addMorphBack: item!

Item was added:
+ ----- Method: MenuEntrySpec>>icon (in category 'accessing') -----
+ icon
+ 
+ 	^ icon!

Item was changed:
  ----- Method: TheWorldMainDockingBar>>menusOn: (in category 'construction') -----
+ menusOn: aDockingBar
- menusOn: aDockingBar 
  
  	self 
  		squeakMenuOn: aDockingBar;
  		projectsMenuOn: aDockingBar;
  		toolsMenuOn: aDockingBar;
  		extrasMenuOn: aDockingBar;
  		windowsMenuOn: aDockingBar;
+ 		helpMenuOn: aDockingBar;
+ 		customMenusOn: aDockingBar.
- 		helpMenuOn: aDockingBar.
  	aDockingBar addSpacer.
  	self
  		searchBarOn: aDockingBar;
  		clockOn: aDockingBar!

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

Item was removed:
- ----- Method: MenuMorph>>addMenuItem: (in category 'construction') -----
- addMenuItem: aMenuItemMorph
- 	self addMorphBack: aMenuItemMorph!




More information about the Squeak-dev mailing list