[Pkg] The Trunk: Tools-dtl.196.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Feb 27 16:59:17 UTC 2010


David T. Lewis uploaded a new version of Tools to project The Trunk:
http://source.squeak.org/trunk/Tools-dtl.196.mcz

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

Name: Tools-dtl.196
Author: dtl
Time: 27 February 2010, 11:57:11.983 am
UUID: 8a071b8d-fbcc-49be-939e-b4aec1c1bb03
Ancestors: Tools-ar.195

Add CustomMenu>>addStayUpItemSpecial and CustomMenu>>addTitle: compatibility methods.
Remove #isMorphic testing in various places.
Use Project uiProcess in ProcessBrowser class>>isUIProcess: to eliminate an #isMorphic

=============== Diff against Tools-ar.195 ===============

Item was changed:
  ----- Method: ChangeSorter>>classListMenu:shifted: (in category 'class list') -----
  classListMenu: aMenu shifted: shifted
  	"Fill aMenu with items appropriate for the class list"
  
  	aMenu title: 'class list'.
+ 	aMenu addStayUpItemSpecial.
- 	Smalltalk isMorphic ifTrue: [aMenu addStayUpItemSpecial].
  	(parent notNil and: [shifted not])
  		ifTrue: [aMenu addList: #( "These two only apply to dual change sorters"
  			('copy class chgs to other side'			copyClassToOther)	
  			('move class chgs to other side'			moveClassToOther))].
  
  	aMenu addList: (shifted
  		ifFalse: [#(
  			-
  			('delete class from change set (d)'		forgetClass)
  			('remove class from system (x)'			removeClass)
  			-
  			('browse full (b)'						browseMethodFull)
  			('browse hierarchy (h)'					spawnHierarchy)
  			('browse protocol (p)'					browseFullProtocol)
  			-
  			('printOut'								printOutClass)
  			('fileOut'								fileOutClass)
  			-
  			('inst var refs...'						browseInstVarRefs)
  			('inst var defs...'						browseInstVarDefs)
  			('class var refs...'						browseClassVarRefs)
  			('class vars'								browseClassVariables)
  			('class refs (N)'							browseClassRefs)
  			-
  			('more...'								offerShiftedClassListMenu))]
  
  		ifTrue: [#(
  			-
  			('unsent methods'						browseUnusedMethods)
  			('unreferenced inst vars'				showUnreferencedInstVars)
  			('unreferenced class vars'				showUnreferencedClassVars)
  			-
  			('sample instance'						makeSampleInstance)
  			('inspect instances'						inspectInstances)
  			('inspect subinstances'					inspectSubInstances)
  			-
  			('more...'								offerUnshiftedClassListMenu ))]).
  	^ aMenu!

Item was changed:
  ----- Method: ChangeList>>changeListMenu: (in category 'menu actions') -----
  changeListMenu: aMenu
  	"Fill aMenu up so that it comprises the primary changelist-browser menu"
  
+ 	aMenu addTitle: 'change list'.
+ 	aMenu addStayUpItemSpecial.
- 	Smalltalk isMorphic ifTrue:
- 		[aMenu addTitle: 'change list'.
- 		aMenu addStayUpItemSpecial].
  
  	aMenu addList: #(
  
  	('fileIn selections'							fileInSelections						'import the selected items into the image')
  	('fileOut selections...	'						fileOutSelections						'create a new file containing the selected items')
  	-
  	('compare to current'						compareToCurrentVersion			'open a separate window which shows the text differences between the on-file version and the in-image version.' )
  	('toggle diffing (D)'							toggleDiffing						'start or stop showing diffs in the code pane.')
  	-
  	('select conflicts with any changeset'		selectAllConflicts					'select methods in the file which also occur in any change-set in the system')
  	('select conflicts with current changeset'	selectConflicts						'select methods in the file which also occur in the current change-set')
  	('select conflicts with...'						selectConflictsWith					'allows you to designate a file or change-set against which to check for code conflicts.')
  	-
  	('select unchanged methods'					selectUnchangedMethods				'select methods in the file whose in-image versions are the same as their in-file counterparts' )
  	('select new methods'						selectNewMethods					'select methods in the file that do not current occur in the image')
  	('select methods for this class'				selectMethodsForThisClass			'select all methods in the file that belong to the currently-selected class')
  
  	-
  	('select all (a)'								selectAll								'select all the items in the list')
  	('deselect all'								deselectAll							'deselect all the items in the list')
  	('invert selections'							invertSelections						'select every item that is not currently selected, and deselect every item that *is* currently selected')
  	-
  	('browse all versions of single selection'			browseVersions		'open a version browser showing the versions of the currently selected method')
  	('browse all versions of selections'			browseAllVersionsOfSelections		'open a version browser showing all the versions of all the selected methods')
  	('browse current versions of selections'		browseCurrentVersionsOfSelections	'open a message-list browser showing the current (in-image) counterparts of the selected methods')
  	('destroy current methods of selections'		destroyCurrentCodeOfSelections		'remove (*destroy*) the in-image counterparts of all selected methods')
  	-
  	('remove doIts'								removeDoIts							'remove all items that are doIts rather than methods')
  	('remove older versions'						removeOlderMethodVersions			'remove all but the most recent versions of methods in the list')
  	('remove up-to-date versions'				removeExistingMethodVersions		'remove all items whose code is the same as the counterpart in-image code')
  	('remove selected items'						removeSelections					'remove the selected items from the change-list')
  	('remove unselected items'					removeNonSelections					'remove all the items not currently selected from the change-list')).
  
  	^ aMenu
  
  !

Item was added:
+ ----- Method: CustomMenu>>addStayUpItemSpecial (in category 'construction') -----
+ addStayUpItemSpecial
+ 	"For compatibility with MenuMorph.  Here it is a no-op"!

Item was changed:
  ----- Method: ChangeSetBrowser>>shiftedChangeSetMenu: (in category 'menu') -----
  shiftedChangeSetMenu: aMenu
  	"Set up aMenu to hold items relating to the change-set-list pane when the shift key is down"
  
+ 	aMenu title: 'Change set (shifted)'.
+ 	aMenu addStayUpItemSpecial.
- 	Smalltalk isMorphic ifTrue:
- 		[aMenu title: 'Change set (shifted)'.
- 		aMenu addStayUpItemSpecial].
  	aMenu add: 'conflicts with other change sets' action: #browseMethodConflicts.
  	aMenu balloonTextForLastItem: 
  'Browse all methods that occur both in this change set and in at least one other change set.'.
  
  	aMenu addLine.
  	aMenu add: 'check for slips' action: #lookForSlips.
  	aMenu balloonTextForLastItem: 
  'Check this change set for halts and references to Transcript.'.
  
  	aMenu add: 'check for unsent messages' action: #checkForUnsentMessages.
  	aMenu balloonTextForLastItem:
  'Check this change set for messages that are not sent anywhere in the system'.
  
  	aMenu add: 'check for uncommented methods' action: #checkForUncommentedMethods.
  	aMenu balloonTextForLastItem:
  'Check this change set for methods that do not have comments'.
  
  	aMenu add: 'check for uncommented classes' action: #checkForUncommentedClasses.
  	aMenu balloonTextForLastItem:
  'Check for classes with code in this changeset which lack class comments'.
  
  
  	Utilities authorInitialsPerSe isEmptyOrNil ifFalse:
  		[aMenu add: 'check for other authors' action: #checkForAlienAuthorship.
  		aMenu balloonTextForLastItem:
  'Check this change set for methods whose current authoring stamp does not start with "', Utilities authorInitials, '"'.
  
  		aMenu add: 'check for any other authors' action: #checkForAnyAlienAuthorship.
  		aMenu balloonTextForLastItem:
  'Check this change set for methods any of whose previous authoring stamps do not start with "', Utilities authorInitials, '"'].
  
  	aMenu add: 'check for uncategorized methods' action: #checkForUnclassifiedMethods.
  	aMenu balloonTextForLastItem:
  'Check to see if any methods in the selected change set have not yet been assigned to a category.  If any are found, open a browser on them.'.
  	aMenu addLine.
  
  	aMenu add: 'inspect change set' action: #inspectChangeSet.
  	aMenu balloonTextForLastItem: 
  'Open an inspector on this change set. (There are some details in a change set which you don''t see in a change sorter.)'.
  
  	aMenu add: 'update' action: #update.
  	aMenu balloonTextForLastItem: 
  'Update the display for this change set.  (This is done automatically when you activate this window, so is seldom needed.)'.
  
  	aMenu add: 'go to change set''s project' action: #goToChangeSetsProject.
  	aMenu balloonTextForLastItem: 
  'If this change set is currently associated with a Project, go to that project right now.'.
  
  	aMenu add: 'trim history' action: #trimHistory.
  	aMenu balloonTextForLastItem: 
  ' Drops any methods added and then removed, as well as renaming and reorganization of newly-added classes.  NOTE: can cause confusion if later filed in over an earlier version of these changes'.
  
  	aMenu add: 'clear this change set' action: #clearChangeSet.
  	aMenu balloonTextForLastItem: 
  'Reset this change set to a pristine state where it holds no information. CAUTION: this is destructive and irreversible!!'.
  	aMenu add: 'expunge uniclasses' action: #expungeUniclasses.
  	aMenu balloonTextForLastItem:
  'Remove from the change set all memory of uniclasses, e.g. classes added on behalf of etoys, fabrik, etc., whose classnames end with a digit.'.
  
  	aMenu add: 'uninstall this change set' action: #uninstallChangeSet.
  	aMenu balloonTextForLastItem: 
  'Attempt to uninstall this change set. CAUTION: this may not work completely and is irreversible!!'.
  
  	aMenu addLine.
  
  	aMenu add: 'more...' action: #offerUnshiftedChangeSetMenu.
  	aMenu balloonTextForLastItem: 
  'Takes you back to the primary change-set menu.'.
  
  	^ aMenu!

Item was changed:
  ----- Method: ProcessBrowser class>>isUIProcess: (in category 'process control') -----
  isUIProcess: aProcess
+ 	^aProcess == Project uiProcess
+ !
- 	^aProcess == (Smalltalk isMorphic
- 		ifTrue: [ Project uiProcess ]
- 		ifFalse: [ ScheduledControllers activeControllerProcess ])!

Item was changed:
  ----- Method: ChangeSorter>>messageMenu:shifted: (in category 'message list') -----
  messageMenu: aMenu shifted: shifted
  	"Fill aMenu with items appropriate for the message list; could be for a single or double changeSorter"
  
  	shifted ifTrue: [^ self shiftedMessageMenu: aMenu].
  
  	aMenu title: 'message list'.
+ 	aMenu addStayUpItemSpecial.
- 	Smalltalk isMorphic ifTrue: [aMenu addStayUpItemSpecial].
  
  	parent ifNotNil:
  		[aMenu addList: #(
  			('copy method to other side'			copyMethodToOther)
  			('move method to other side'			moveMethodToOther))].
  
  	aMenu addList: #(
  			('delete method from changeSet (d)'	forget)
  			-
  			('remove method from system (x)'	removeMessage)
  				-
  			('browse full (b)'					browseMethodFull)
  			('browse hierarchy (h)'				spawnHierarchy)
  			('browse method (O)'				openSingleMessageBrowser)
  			('browse protocol (p)'				browseFullProtocol)
  			-
  			('fileOut'							fileOutMessage)
  			('printOut'							printOutMessage)
  			-
  			('senders of... (n)'					browseSendersOfMessages)
  			('implementors of... (m)'				browseMessages)
  			('inheritance (i)'					methodHierarchy)
  			('versions (v)'						browseVersions)
  			-
  			('more...'							shiftedYellowButtonActivity)).
  	^ aMenu
  !

Item was changed:
  ----- Method: ChangeSorter>>changeSetMenu:shifted: (in category 'changeSet menu') -----
  changeSetMenu: aMenu shifted: isShifted 
  	"Set up aMenu to hold commands for the change-set-list pane.  This could be for a single or double changeSorter"
  
  	isShifted ifTrue: [^ self shiftedChangeSetMenu: aMenu].
  	Smalltalk isMorphic
  		ifTrue:
+ 			[aMenu title: 'Change Set']
- 			[aMenu title: 'Change Set'.
- 			aMenu addStayUpItemSpecial]
  		ifFalse:
  			[aMenu title: 'Change Set:
  ' , myChangeSet name].
+ 	aMenu addStayUpItemSpecial.
  
  	aMenu add: 'make changes go to me (m)' action: #newCurrent.
  	aMenu addLine.
  	aMenu add: 'new change set... (n)' action: #newSet.
  	aMenu add: 'find...(f)' action: #findCngSet.
  	aMenu add: 'select change set...' action: #chooseCngSet.
  	aMenu addLine.
  	aMenu add: 'rename change set (r)' action: #rename.
  	aMenu add: 'file out (o)' action: #fileOut.
  	aMenu add: 'mail to list' action: #mailOut.
  	aMenu add: 'browse methods (b)' action: #browseChangeSet.
  	aMenu add: 'browse change set (B)' action: #openChangeSetBrowser.
  	aMenu addLine.
  	parent
  		ifNotNil: 
  			[aMenu add: 'copy all to other side (c)' action: #copyAllToOther.
  			aMenu add: 'submerge into other side' action: #submergeIntoOtherSide.
  			aMenu add: 'subtract other side (-)' action: #subtractOtherSide.
  			aMenu addLine].
  	myChangeSet hasPreamble
  		ifTrue: 
  			[aMenu add: 'edit preamble (p)' action: #addPreamble.
  			aMenu add: 'remove preamble' action: #removePreamble]
  		ifFalse: [aMenu add: 'add preamble (p)' action: #addPreamble].
  	myChangeSet hasPostscript
  		ifTrue: 
  			[aMenu add: 'edit postscript...' action: #editPostscript.
  			aMenu add: 'remove postscript' action: #removePostscript]
  		ifFalse: [aMenu add: 'add postscript...' action: #editPostscript].
  	aMenu addLine.
  
  	aMenu add: 'destroy change set (x)' action: #remove.
  	aMenu addLine.
  	aMenu add: 'more...' action: #offerShiftedChangeSetMenu.
  	^ aMenu!

Item was changed:
  ----- Method: Inspector>>fieldListMenu: (in category 'menu commands') -----
  fieldListMenu: aMenu
  	"Arm the supplied menu with items for the field-list of the receiver"
  
+ 	aMenu addStayUpItemSpecial.
- 	Smalltalk isMorphic ifTrue:
- 		[aMenu addStayUpItemSpecial].
  
  	aMenu addList: #(
  		('inspect (i)'						inspectSelection)
  		('explore (I)'						exploreSelection)).
  
  	self addCollectionItemsTo: aMenu.
  
  	aMenu addList: #(
  		-
  		('method refs to this inst var'		referencesToSelection)
  		('methods storing into this inst var'	defsOfSelection)
  		('objects pointing to this value'		objectReferencesToSelection)
  		('chase pointers'					chasePointers)
  		('explore pointers'				explorePointers)
  		-
  		('browse full (b)'					browseMethodFull)
  		('browse class'						browseClass)
  		('browse hierarchy (h)'					classHierarchy)
  		('browse protocol (p)'				browseFullProtocol)
  		-
  		('inst var refs...'					browseInstVarRefs)
  		('inst var defs...'					browseInstVarDefs)
  		('class var refs...'					classVarRefs)
  		('class variables'					browseClassVariables)
  		('class refs (N)'						browseClassRefs)
  		-
  		('copy name (c)'					copyName)		
  		('basic inspect'						inspectBasic)).
  
  	Smalltalk isMorphic ifTrue:
  		[aMenu addList: #(
  			-
  			('tile for this value	(t)'			tearOffTile)
  			('viewer for this value (v)'		viewerForValue))].
  
  	^ aMenu
  
  
  "			-
  			('alias for this value'			aliasForValue)
  			('watcher for this slot'			watcherForSlot)"
  
  !

Item was changed:
  ----- Method: ChangeSorter>>shiftedChangeSetMenu: (in category 'changeSet menu') -----
  shiftedChangeSetMenu: aMenu
  	"Set up aMenu to hold items relating to the change-set-list pane when the shift key is down"
  
+ 	aMenu title: 'Change set (shifted)'.
+ 	aMenu addStayUpItemSpecial.
- 	Smalltalk isMorphic ifTrue:
- 		[aMenu title: 'Change set (shifted)'.
- 		aMenu addStayUpItemSpecial].
  
  	"CONFLICTS SECTION"
  	aMenu add: 'conflicts with other change sets' action: #browseMethodConflicts.
  	aMenu balloonTextForLastItem: 
  'Browse all methods that occur both in this change set and in at least one other change set.'.
  	parent ifNotNil:
  		[aMenu add: 'conflicts with change set opposite' action: #methodConflictsWithOtherSide.
  			aMenu balloonTextForLastItem: 
  'Browse all methods that occur both in this change set and in the one on the opposite side of the change sorter.'.].
  	aMenu addLine.
  
  	"CHECKS SECTION"
  	aMenu add: 'check for slips' action: #lookForSlips.
  	aMenu balloonTextForLastItem: 
  'Check this change set for halts and references to Transcript.'.
  
  	aMenu add: 'check for unsent messages' action: #checkForUnsentMessages.
  	aMenu balloonTextForLastItem:
  'Check this change set for messages that are not sent anywhere in the system'.
  
  	aMenu add: 'check for uncommented methods' action: #checkForUncommentedMethods.
  	aMenu balloonTextForLastItem:
  'Check this change set for methods that do not have comments'.
  
  	aMenu add: 'check for uncommented classes' action: #checkForUncommentedClasses.
  	aMenu balloonTextForLastItem:
  'Check for classes with code in this changeset which lack class comments'.
  
  	Utilities authorInitialsPerSe isEmptyOrNil ifFalse:
  		[aMenu add: 'check for other authors' action: #checkForAlienAuthorship.
  		aMenu balloonTextForLastItem:
  'Check this change set for methods whose current authoring stamp does not start with "', Utilities authorInitials, '"'.
  
  	aMenu add: 'check for any other authors' action: #checkForAnyAlienAuthorship.
  	aMenu balloonTextForLastItem:
  'Check this change set for methods any of whose authoring stamps do not start with "', Utilities authorInitials, '"'].
  
  	aMenu add: 'check for uncategorized methods' action: #checkForUnclassifiedMethods.
  	aMenu balloonTextForLastItem:
  'Check to see if any methods in the selected change set have not yet been assigned to a category.  If any are found, open a browser on them.'.
  	aMenu addLine.
  
  	aMenu add: 'inspect change set' action: #inspectChangeSet.
  	aMenu balloonTextForLastItem: 
  'Open an inspector on this change set. (There are some details in a change set which you don''t see in a change sorter.)'.
  
  	aMenu add: 'update' action: #update.
  	aMenu balloonTextForLastItem: 
  'Update the display for this change set.  (This is done automatically when you activate this window, so is seldom needed.)'.
  
  	aMenu add: 'go to change set''s project' action: #goToChangeSetsProject.
  	aMenu balloonTextForLastItem: 
  'If this change set is currently associated with a Project, go to that project right now.'.
  
  	aMenu add: 'promote to top of list' action: #promoteToTopChangeSet.
  	aMenu balloonTextForLastItem:
  'Make this change set appear first in change-set lists in all change sorters.'.
  
  	aMenu add: 'trim history' action: #trimHistory.
  	aMenu balloonTextForLastItem: 
  ' Drops any methods added and then removed, as well as renaming and reorganization of newly-added classes.  NOTE: can cause confusion if later filed in over an earlier version of these changes'.
  
  	aMenu add: 'remove contained in class categories...' action: #removeContainedInClassCategories.
  	aMenu balloonTextForLastItem: ' Drops any changes in given class categories'.
  
  	aMenu add: 'clear this change set' action: #clearChangeSet.
  	aMenu balloonTextForLastItem: 
  'Reset this change set to a pristine state where it holds no information. CAUTION: this is destructive and irreversible!!'.
  	aMenu add: 'expunge uniclasses' action: #expungeUniclasses.
  	aMenu balloonTextForLastItem:
  'Remove from the change set all memory of uniclasses, e.g. classes added on behalf of etoys, fabrik, etc., whose classnames end with a digit.'.
  
  	aMenu add: 'uninstall this change set' action: #uninstallChangeSet.
  	aMenu balloonTextForLastItem: 
  'Attempt to uninstall this change set. CAUTION: this may not work completely and is irreversible!!'.
  
  	aMenu addLine.
  	aMenu add: 'file into new...' action: #fileIntoNewChangeSet.
  	aMenu balloonTextForLastItem: 
  'Load a fileout from disk and place its changes into a new change set (seldom needed -- much better to do this from a file-list browser these days.)'.
  
  	aMenu add: 'reorder all change sets' action: #reorderChangeSets.
  	aMenu balloonTextForLastItem:
  'Applies a standard reordering of all change-sets in the system -- at the bottom will come the sets that come with the release; next will come all the numbered updates; finally, at the top, will come all other change sets'.
  
  	aMenu addLine.
  
  	aMenu add: 'more...' action: #offerUnshiftedChangeSetMenu.
  	aMenu balloonTextForLastItem: 
  'Takes you back to the primary change-set menu.'.
  
  	^ aMenu!

Item was changed:
  ----- Method: FileList>>fullFileListMenu:shifted: (in category 'file list menu') -----
  fullFileListMenu: aMenu shifted: aBoolean
  	"Fill the menu with all possible items for the file list pane, regardless of selection."
  
  	| lastProvider |
  	aMenu title: 'all possible file operations' translated.
+ 	aMenu addStayUpItemSpecial.
- 	Smalltalk isMorphic ifTrue: [aMenu addStayUpItemSpecial].
  
  	lastProvider := nil.
  	(self itemsForFile: 'a.*') do: [ :svc |
  		(lastProvider notNil and: [svc provider ~~ lastProvider])
  			ifTrue: [ aMenu addLine ].
  		svc addServiceFor: self toMenu: aMenu.
  		Smalltalk isMorphic ifTrue: [aMenu submorphs last setBalloonText: svc description].
  		lastProvider := svc provider.
  		svc addDependent: self.
  	].
  
  	^aMenu!

Item was changed:
  ----- Method: VersionsBrowser>>versionsMenu: (in category 'menu') -----
  versionsMenu: aMenu
  	"Fill aMenu with menu items appropriate to the receiver"
  
+ 	aMenu title: 'Versions' translated.
+ 	aMenu addStayUpItemSpecial.
- 	Smalltalk isMorphic ifTrue:
- 		[aMenu title: 'Versions' translated.
- 		aMenu addStayUpItemSpecial].
  
  	listIndex > 0 ifTrue:[
  		(list size > 1 ) ifTrue: [ aMenu addTranslatedList: #(
  			('compare to current'		compareToCurrentVersion		'compare selected version to the current version')
  			('compare to version...'	compareToOtherVersion		'compare selected version to another selected version'))].
  		"Note: Revert to selected should be visible for lists of length one for having the ability to revert to an accidentally deleted method"
  		 aMenu addTranslatedList: #(
  			('revert to selected version'	fileInSelections					'resubmit the selected version, so that it becomes the current version') )].
  
  	aMenu addTranslatedList: #(
  		('remove from changes'		removeMethodFromChanges	'remove this method from the current change set, if present')
  		('edit current method (O)'	openSingleMessageBrowser		'open a single-message browser on the current version of this method')		
  		('find original change set'	findOriginalChangeSet			'locate the changeset which originally contained this version')
  		-
  		('toggle diffing (D)'			toggleDiffing					'toggle whether or not diffs should be shown here')
  		('update list'				reformulateList					'reformulate the list of versions, in case it somehow got out of synch with reality')
  		-
  		('senders (n)'				browseSenders					'browse all senders of this selector')
  		('implementors (m)'			browseImplementors			'browse all implementors of this selector')
  		-
  		('help...'					offerVersionsHelp				'provide an explanation of the use of this tool')).
  											
  	^aMenu!

Item was changed:
  ----- Method: Browser>>shiftedMessageListMenu: (in category 'message functions') -----
  shiftedMessageListMenu: aMenu
  	"Fill aMenu with the items appropriate when the shift key is held down"
  
+ 	aMenu addStayUpItem.
- 	Smalltalk isMorphic ifTrue: [aMenu addStayUpItem].
  	aMenu addList: #(
  		('toggle diffing (D)'						toggleDiffing)
  		('implementors of sent messages'			browseAllMessages)
  		-
  		('local senders of...'						browseLocalSendersOfMessages)
  		('local implementors of...'				browseLocalImplementors)
  		-
  		('spawn sub-protocol'					spawnProtocol)
  		('spawn full protocol'					spawnFullProtocol)
  		-
  		('sample instance'						makeSampleInstance)
  		('inspect instances'						inspectInstances)
  		('inspect subinstances'					inspectSubInstances)).
  
  	self addExtraShiftedItemsTo: aMenu.
  	aMenu addList: #(
  		-
  		('change category...'					changeCategory)).
  
  	self canShowMultipleMessageCategories ifTrue: [aMenu addList:
  		 #(('show category (C)'						showHomeCategory))].
  	aMenu addList: #(
  		-
  		('change sets with this method'			findMethodInChangeSets)
  		('revert to previous version'				revertToPreviousVersion)
  		('remove from current change set'		removeFromCurrentChanges)
  		('revert & remove from changes'		revertAndForget)
  		('add to current change set'				adoptMessageInCurrentChangeset)
  		('copy up or copy down...'				copyUpOrCopyDown)
  		-
  		('more...' 								unshiftedYellowButtonActivity)).
  	^ aMenu
  !

Item was changed:
  ----- Method: ClassCommentVersionsBrowser>>versionsMenu: (in category 'menu') -----
  versionsMenu: aMenu
  	"Fill aMenu with menu items appropriate to the receiver"
  
+ 	aMenu title: 'versions'.
+ 	aMenu addStayUpItemSpecial.
- 	Smalltalk isMorphic ifTrue:
- 		[aMenu title: 'versions'.
- 		aMenu addStayUpItemSpecial].
  	^ aMenu addList: #(
  
  		('compare to current'		compareToCurrentVersion		'compare selected version to the current version')
  		('revert to selected version'	fileInSelections					'resubmit the selected version, so that it becomes the current version')
  		('remove from changes'		removeMethodFromChanges		'remove this method from the current change set, if present')
  		('edit current method (O)'	openSingleMessageBrowser		'open a single-message browser on the current version of this method')		
  		-
  		('toggle diffing (D)'			toggleDiffing					'toggle whether or not diffs should be shown here')
  		('update list'				reformulateList					'reformulate the list of versions, in case it somehow got out of synch with reality')
  		-
  		('help...'					offerVersionsHelp				'provide an explanation of the use of this tool'))
  !

Item was added:
+ ----- Method: CustomMenu>>addTitle: (in category 'construction') -----
+ addTitle: aString
+ 	"For compatibility with MenuMorph.  Here it is a no-op"!



More information about the Packages mailing list