Recent Changes - Search:

OtherPlaces

PmWiki

pmwiki.org

edit SideBar

MenuSystem

Notes:

  • Where you see 'aBuilder' used in connection with pragmas (those words inside pointy brackets, like <worldMenu>, this is shorthand for aPragmaMenuBuilder (the class is PragmaMenuBuilder, not Builder). PragmaMenuBuilder actually has comments. Find it in a system browser, click on the ? button. PragmaMenuBuilder notes?
  • You can't add anything before the pragma. For example, you can't add Transcript show: 'something';cr.
  • As far as I know, you can't add anything at the end (i.e., the pragma takes over the entire method).

In general bits and pieces that make up the World menu are spread all over the place. Don't expect to find them in one area. If you want to change something, you almost have to know where it is before you can find it. For example, in the World menu, under Tools, there's a link to 'Configuration Browser'. That one entry is all by itself in

 MetacelloConfigurationBrowserclass >>menuCommandOn: aBuilder  
	<worldMenu>
	(aBuilder item: 'Configuration Browser')
		parent: #Tools;
		order: 0.5;
		action: [self open]; 
		icon:  self theme smallLoadProjectIcon 

Three points:

  • Use the Finder.
  • Search for the selector "menuCommandOn:"
  • If you still can't find it, try searching 'Source' for "<worldMenu>". At this date (26 April 2011) a search in Source is case sensitive, so check your spelling. Hopefully that will be changed.

  • An example of how to add something to the world menu
 Object subclass: #LessonListEditor ...
 !LessonListEditor class methodsFor: 'menu' stamp: 'DougEdmunds 3/31/2011
 11:16'!
 menuCommandOn: aBuilder 

	<worldMenu> 
	(aBuilder item: #'Manage lessons')
			action:[ self open].
			! !

I wanted the option to go to a full browser directly when in a method. So I copied (slightly reworded):

 (aBuilder item: #'Browser (b)' translated) selector: #browseIt.

from SmalltalkEditor class >> smalltalkEditorShiftedMenuOn: to SmalltalkEditor class>> smalltalkEditorMenuOn:


I wanted to open/close a Transcript window through code. Note: this is Pharo v1.3 specific. By using Finder, and searching menuCommandOn I found a listing under ThreadSafeTranscript class>>:

 menuCommandOn: aBuilder 
	<worldMenu> 
	(aBuilder item: #'Transcript')
		parent: #Tools;
		action:[TranscriptMorph openWindow]; 
		icon: self taskbarIcon.

I open ThreadSafeTranscript in a browser. There's an 'open' method. But does it work? (ThreadSafeTranscript new open) No. But since it did in v1.2, I am thinking WTF??? Look again at the menuCommandOn method. The action is "TranscriptMorph openWindow". I try that, and it opens the more recent version of a Transcript window (one which I personally hate). How? In a Workspace, I typed this:

  t := TranscriptMorph new openWindow.  

What's t?

  t class (click printIt) --> "SystemWindow"

So, with that in mind, I can close a Transcript window using "delete"

  t delete.

Some examples from Pharo, showing how parts of the system menus are built

  • The "World" menu (part of it, at least)
 WorldState class >>mostUsedToolsOn: aBuilder   
	<worldMenu>
	(aBuilder group: #MostUsedTools)
		withSeparatorAfter;
		order: 0;
		with: [
			(aBuilder item: #'System Browser') action: [ToolSet default
			openClassBrowser]; icon: Browser taskbarIcon.
			(aBuilder item: #Workspace) action: [ToolSet default openWorkspace]; icon:
			Workspace taskbarIcon.

			Smalltalk globals at: #TestRunner ifPresent: [ :class |
				(aBuilder item: #'Test Runner') action: [ToolSet default openTestRunner];
				icon: class taskbarIcon.
			].
			(aBuilder item: #'Monticello Browser') action: [ToolSet default
			openMonticelloBrowser]; icon: MCWorkingCopyBrowser taskbarIcon]

 WorldState class >>quitItemsOn: aBuilder 
	<worldMenu>
	(aBuilder group: #QuitPharo)
		order: 9999; 
		with: [{
				{'Save'. {Smalltalk . #saveSession}. 'save the current version of the image
				on disk'}.
				{'Save as...'. {self. #saveAs}. 'save the current version of the image on
				disk under a new name.'}.
				{'Save and quit'. {self. #saveAndQuit}. 'save the current image on disk,
				and quit Pharo.'}.
	 			{'Quit'. {self. #quitSession}. 'quit Pharo.'}
			} do: [:triplet |
					(aBuilder item: triplet first asSymbol) 
						target: triplet second first;
				 		selector: triplet second second;
						help: (triplet size > 2 ifTrue: [triplet third] ifFalse: [nil])]]

  • In the middle
 WorldState class >> systemOn: aBuilder 

	<worldMenu>  
	(aBuilder item: #System)
		order: 3.0;
		icon: UITheme current smallConfigurationIcon;
		with: [
			(aBuilder item: #'About...') 
				order: 0;
				icon: UITheme current smallLanguageIcon;
				action: [Smalltalk aboutThisSystem].
			(aBuilder item: #'Software update')
				order: 2;
				icon: UITheme current smallUpdateIcon;
				action: [UpdateStreamer new updateFromServer ];
				help: 'Load latest code updates via the internet';
			withSeparatorAfter.

			(aBuilder item: #'Vm statistics') 
				action: [(StringHolder new contents: Smalltalk  vmStatisticsReportString)
				openLabel: 'VM Statistics'].
			(aBuilder item: #'Start profiling all Processes') 
				action: [self startMessageTally].
			(aBuilder item: #'Start profiling UI ') 
				action: [self startThenBrowseMessageTally].
			(aBuilder item: #'Space left') 
				action: [Smalltalk garbageCollectAndReport];
			withSeparatorAfter.

			(aBuilder item: #'Start drawing again') 
				action: [World  resumeAfterDrawError].
			(aBuilder item: #'Start stepping again') 
				action: [World  resumeAfterStepError]; 
			withSeparatorAfter.

			(aBuilder item: #'Restore display (r)') 
				action: [World restoreMorphicDisplay].
			self haltOnceEnabled
				ifTrue: [(aBuilder item: 'Disable halt/inspect once') action: [self
				clearHaltOnce]]
				ifFalse: [(aBuilder item: 'Enable halt/inspect once') action: [self
				setHaltOnce]]].

 WorldState class >> windowsOn: aBuilder 
	<worldMenu>
	(aBuilder item: #Windows)
		order: 4.0;
		withSeparatorAfter ;
		icon: UITheme current smallWindowIcon;
		with: [
			(aBuilder item: # 'Collapse all windows') 
				action: [World collapseAll];
				help: 'Reduce all open windows to collapsed forms that only show titles'
				translated.
			(aBuilder item: # 'Expand all windows') 
				action: [World expandAll];
				help: 'Expand all collapsed windows back to their expanded forms'
				translated.
			(aBuilder item: # 'Fit all windows') 
				action: [World fitAll];
				help: 'Fit all open windows as visible in World' translated.
			(aBuilder item: #'Close all debuggers') 
				action: [Debugger closeAllDebuggers].
			(aBuilder item: # 'Send top window to back (\)') 
				action: [SystemWindow sendTopWindowToBack];
				help: 'Make the topmost window become the backmost one, and activate the
				window just beneath it.' translated.
			(aBuilder item: # 'Move windows onscreen') 
				action: [World bringWindowsFullOnscreen];
				help: 'Make all windows fully visible on the screen' translated.
			(aBuilder item: # 'Delete unchanged windows') 
				action: [World closeUnchangedWindows];
				help: 'Deletes all windows that do not have unsaved text edits.'
				translated]

  • When you right click in a text area of a browser:
 SmalltalkEditor class >> smalltalkEditorMenuOn: aBuilder 
	"Specify the menu used when writing code. Try it with:
	(PragmaMenuBuilder 
		pragmaKeyword: 'smalltalkEditorMenu'
		model: nil) menu popUpInWorld
	"
	<smalltalkEditorMenu>
	(aBuilder item: #'Do it (d)' translated) selector: #doIt; help: nil; icon:
	UITheme current smallDoItIcon.
	(aBuilder item: #'Print it (p)' translated) selector: #printIt; help: nil;
	icon: UITheme current smallPrintIcon.
	(aBuilder item: #'Inspect it (i)' translated) selector: #inspectIt; help:
	nil; icon: UITheme current smallInspectItIcon.
	(aBuilder item: #'Explore it (I)' translated) selector: #exploreIt; help:
	nil; icon: UITheme current smallInspectItIcon.
	(aBuilder item: #'Debug it (D)' translated) selector: #debugIt; help: nil;
	icon: UITheme current smallDebugIcon.
	(aBuilder item: #'Profile it' translated) selector: #tallyIt; icon: UITheme
	current smallDebugIcon; withSeparatorAfter.
	(aBuilder item: #'Find...(f)' translated) selector: #find; help: nil; icon:
	UITheme current smallFindIcon.
	(aBuilder item: #'Find again (g)' translated) selector: #findAgain; help:
	nil; icon: UITheme current smallFindIcon.
	(aBuilder item: #'Extended search...' translated) selector:
	#shiftedTextPaneMenuRequest; withSeparatorAfter.
	(aBuilder item: #'Do again (j)' translated) selector: #again; help: nil;
	icon: UITheme current smallRedoIcon.
	(aBuilder item: #'Undo (z)' translated) selector: #undo; help: nil; icon:
	UITheme current smallUndoIcon; withSeparatorAfter.
	(aBuilder item: #'Copy (c)' translated) selector: #copySelection; help:
	nil; icon: UITheme current smallCopyIcon.
	(aBuilder item: #'Cut (x)' translated) selector: #cut; help: nil; icon:
	UITheme current smallCutIcon.
	(aBuilder item: #'Paste (v)' translated) selector: #paste; help: nil; icon:
	UITheme current smallPasteIcon.
	(aBuilder item: #'Paste...' translated) selector: #pasteRecent; help: nil;
	icon: UITheme current smallCopyIcon; withSeparatorAfter.
	(aBuilder item: #'Accept (s)' translated) selector: #accept; help: nil;
	icon: UITheme current smallOkIcon.
	(aBuilder item: #'Cancel (l)' translated) selector: #cancel; help: nil;
	icon: UITheme current smallCancelIcon.

  • From in that menu, you click on 'Extended search'
 ScrollPane >> shiftedTextPaneMenuRequest
	"The more... button was hit from the text-pane menu"
        Transcript show: 'at ScrollPane shiftedTextPaneMenuRequest'; cr. "dae
        added"
	^ self yellowButtonActivity: true

  • which takes you here ...
 ScrollPane >> yellowButtonActivity: shiftKeyState "true"
	| menu |
	(menu := self getMenu: shiftKeyState) ifNotNil:
		[menu setInvokingView: self.
		menu popUpEvent: self activeHand lastEvent in: self world]

  • which then takes you here ...
 ScrollPane >> getMenu: shiftKeyState "true"
	"Answer the menu for this text view, supplying an empty menu to be filled
	in. 
         If the menu selector takes an extra argument, pass in the current state of
         the shift key."
	| menu aMenu aTitle |
	getMenuSelector == nil ifTrue: [^ nil].
	menu := MenuMorph new defaultTarget: model.
	aTitle := getMenuTitleSelector ifNotNil: [model perform:
	getMenuTitleSelector].
	getMenuSelector numArgs = 1 ifTrue:
		[aMenu := model perform: getMenuSelector with: menu.
		aTitle ifNotNil:  [aMenu addTitle: aTitle].
		^ aMenu].
	getMenuSelector numArgs = 2 ifTrue:
		[aMenu := model perform: getMenuSelector with: menu with: shiftKeyState.
		aTitle ifNotNil:  [aMenu addTitle: aTitle].
		^ aMenu].
	^ self error: 'The getMenuSelector must be a 1- or 2-keyword symbol'

All I can say at this point is ARGH! Where does this end?

  • getMenuSelector is an instance variable of ScrollPane (Morphic-Windows)
  • 'model' is an instance variable of MorphicModel (Morphic-Kernel), the parent class of ScrollPane.
  • SmalltalkEditor (System-Text)

SmalltalkEditor class >> smalltalkEditorShiftedMenuOn: aBuilder

 smalltalkEditorShiftedMenuOn: aBuilder 
	"Specify the menu used when writing code. Try it with:
	(PragmaMenuBuilder 
		pragmaKeyword: 'smalltalkEditorShiftedMenu'
		model: nil) menu popUpInWorld"

	<smalltalkEditorShiftedMenu>
	(aBuilder item: #'browse it (b)' translated) selector: #browseIt.
	(aBuilder item: #'senders of it (n)' translated) selector: #sendersOfIt.
	(aBuilder item: #'implementors of it (m)' translated) selector:
	#implementorsOfIt.
	(aBuilder item: #'references to it (N)' translated) selector:
	#referencesToIt.
	(aBuilder item: #'selectors containing it (W)' translated) selector:
	#methodNamesContainingIt.
	(aBuilder item: #'method strings with it (E)' translated) selector:
	#methodStringsContainingit.
	(aBuilder item: #'method source with it' translated) selector:
	#methodSourceContainingIt.
	(aBuilder item: #'class names containing it' translated) selector:
	#classNamesContainingIt.
	(aBuilder item: #'class comments with it' translated) selector:
	#classCommentsContainingIt.
	(aBuilder item: #'change sets with it' translated) selector:
	#browseChangeSetsWithSelector.

If you are in a Workspace and right click, it calls a method named after the antiquated 'yellow button' -- got one of those? :)

 yellowButtonMenu
	^  (UIManager default
		newMenuIn: textMorph for: self)
		addList:  {
			{'Do it (d)' translated.					#doIt. nil. #smallDoItIcon}.
			{'Print it (p)' translated.					#printIt. nil. #smallPrintIcon}.
			{'Inspect it (i)' translated.				#inspectIt. nil. #smallInspectItIcon}.
			{'Explore it (I)' translated.				#exploreIt. nil. #smallInspectItIcon}.
			{'Debug it (D)' translated.				#debugIt. nil. #smallDebugItIcon}.
			{'Profile it' translated.					#tallyIt}.
		     {'Watch it' translated.					#watchIt}.	 

			#-.
			{'Find...(f)' translated.					#find. nil. #smallFindIcon}.
			{'Find again (g)' translated.				#findAgain.nil. #smallFindIcon}.
			{'Extended search...' translated.			#shiftedTextPaneMenuRequest}.
			#-.
			{'Do again (j)' translated.				#again. nil. #smallDoItIcon}.
			{'Undo (z)' translated.					#undo. nil. #smallUndocon}.
			#-.
			{'Copy (c)' translated.					#copySelection. nil. #smallCopyIcon}.
			{'Cut (x)' translated.						#cut. nil. #smallCutIcon}.
			{'Paste (v)' translated.					#paste. nil. #smallPasteIcon}.
			{'Paste...' translated.					#pasteRecent. nil. #smallCopyIcon}.
			#-.
			{'Accept (s)' translated.					#accept. nil. #smallOkIcon}.
			{'Cancel (l)' translated.					#cancel. nil. #smallCancelIcon}.
		}.

Or you can hold down shift to get another menu. If you look above you'll recognize this is the same menu that pops up when you click on 'Extended search', but instead of calling 'shiftedYellowButtonMenu, it calls 'shiftedTextPaneMenuRequest'. It's getting that method either from ScrollPane or TextEditor, but right now I'm too far out on the limb to try to figure out which it is. The point is that you end up in the same place -- shiftedYellowButtonMenu.

 Workspace>> shiftedYellowButtonMenu
	"Answer the menu to be presented when the yellow button is pressed while
	the shift key is down"

	^ (UIManager default
		newMenuIn: textMorph for: self)
		addList: {

		{'Browse it (b)' translated.					#browseIt}.
		{'Senders of it (n)' translated.				#sendersOfIt}.
		{'Implementors of it (m)' translated.		#implementorsOfIt}.
		{'References to it (N)' translated.			#referencesToIt}.
		#-.
		{'Selectors containing it (W)' translated.	#methodNamesContainingIt}.
		{'Method strings with it (E)' translated.	#methodStringsContainingit}.
		{'Method source with it' translated.		#methodSourceContainingIt}.
		{'Class names containing it' translated.	#classNamesContainingIt}.
		{'Class comments with it' translated.		#classCommentsContainingIt}.
		{'Change sets with it' translated.			#browseChangeSetsWithSelector}.
	"	#-.
		{'Pretty print' translated.					#prettyPrint}.
		{'Pretty print with color' translated.		#prettyPrintWithColor}.
		{'File it in (G)' translated.					#fileItIn}.
		#-.
		{'Back...' translated.						#yellowButtonActivity}.
	"
	}
Edit - History - Print - Recent Changes - Search
Page last modified on April 26, 2011, at 10:31 AM