[squeak-dev] The Trunk: Tools-mt.864.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Aug 4 14:36:13 UTC 2019


Marcel Taeumel uploaded a new version of Tools to project The Trunk:
http://source.squeak.org/trunk/Tools-mt.864.mcz

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

Name: Tools-mt.864
Author: mt
Time: 4 August 2019, 4:36:12.203381 pm
UUID: cb8e1c1e-b28e-a647-a72e-1c49fe42bcc0
Ancestors: Tools-mt.856, Tools-mt.863

Merges and refines Tools-mt.856 based on the discussion on squeak-dev: http://forum.world.st/The-Inbox-Tools-mt-856-mcz-td5101574.html

Note that if you notice any performance problems on slower machines, we might want to make this a preference.

=============== Diff against Tools-mt.863 ===============

Item was changed:
  ----- Method: Browser>>messageList (in category 'message list') -----
  messageList
+ 	"Answer an Array of the message selectors of the currently selected message category. If no category is selected or the '-- all --' category is selected, return all method selectors. Make deprecated messages look gray and struck-out."
+ 	
- 	"Answer an Array of the message selectors of the currently selected message category, provided that the messageCategoryListIndex is in proper range.  Otherwise, answer an empty Array  If messageCategoryListIndex is found to be larger than the number of categories (it happens!!), it is reset to zero."
- 	| sel |
- 	(sel := self messageCategoryListSelection) ifNil: 
- 		[
- 			^ self classOrMetaClassOrganizer
- 				ifNil:		[Array new]
- 				ifNotNil:	[self classOrMetaClassOrganizer allMethodSelectors]
- 			"^ Array new"
- 		].
  
+ 	^ (self selectedMessageCategoryName isNil or: [self selectedMessageCategoryName = ClassOrganizer allCategory])
+ 		ifTrue: [
+ 			self classOrMetaClassOrganizer
+ 				ifNil: [Array new]
+ 				ifNotNil: [:organizer | organizer allMethodSelectors collect: [:ea |
+ 					self formattedLabel: ea]]]
+ 		ifFalse: [
+ 			(self classOrMetaClassOrganizer listAtCategoryNamed: self selectedMessageCategoryName)
+ 				collect: [:ea | self formattedLabel: ea]]!
- 	^ sel = ClassOrganizer allCategory
- 		ifTrue: 
- 			[self classOrMetaClassOrganizer
- 				ifNil:		[Array new]
- 				ifNotNil:	[self classOrMetaClassOrganizer allMethodSelectors]]
- 		ifFalse:
- 			[(self classOrMetaClassOrganizer listAtCategoryNamed: self selectedMessageCategoryName )
- 				ifNil: [selectedMessageCategoryName := nil. Array new]]!

Item was added:
+ ----- Method: CodeHolder>>formattedLabel: (in category 'message list') -----
+ formattedLabel: aString
+ 
+ 	^ self
+ 		formattedLabel: aString
+ 		forSelector: aString
+ 		inClass: self selectedClassOrMetaClass!

Item was added:
+ ----- Method: CodeHolder>>formattedLabel:forSelector:inClass: (in category 'message list') -----
+ formattedLabel: aString forSelector: aSymbol inClass: aClass
+ 	"Show deprecated messages differently so that users recognize them quickly to avoid them."
+ 	
+ 	| formattedLabel |
+ 	aSymbol = #Definition
+ 		ifTrue: [aClass isDeprecated not
+ 			ifTrue: [^ aString]]
+ 		ifFalse: [(aClass compiledMethodAt: aSymbol) isDeprecated not
+ 			ifTrue: [^ aString]].
+ 	
+ 	formattedLabel := aString asText.
+ 	
+ 	(self userInterfaceTheme deprecatedMessageAttributes ifNil: [{TextColor gray. TextEmphasis struckOut}]) do: [:textAttribute |
+ 		formattedLabel addAttribute: textAttribute].
+ 
+ 	^ formattedLabel.!

Item was changed:
  CodeHolder subclass: #MessageSet
+ 	instanceVariableNames: 'growable messageList messageListFormatted autoSelectString messageListIndex editSelection'
- 	instanceVariableNames: 'growable messageList autoSelectString messageListIndex editSelection'
  	classVariableNames: 'UseUnifiedMessageLabels'
  	poolDictionaries: ''
  	category: 'Tools-Browser'!
  
  !MessageSet commentStamp: '<historical>' prior: 0!
  I represent a query path of the retrieval result of making a query about methods in the system. The result is a set of methods, denoted by a message selector and the class in which the method was found. As a StringHolder, the string I represent is the source code of the currently selected method. I am typically viewed in a Message Set Browser consisting of a MessageListView and a BrowserCodeView.!

Item was changed:
  ----- Method: MessageSet>>buildMessageListWith: (in category 'toolbuilder') -----
  buildMessageListWith: builder
  	| listSpec |
  	listSpec := builder pluggableListSpec new.
  	listSpec 
  		model: self;
+ 		list: #messageListFormatted;
- 		list: #messageList; 
  		getIndex: #messageListIndex; 
  		setIndex: #messageListIndex:;
  		icon: #messageIconAt:;
  		help: #messageHelpAt:; 
  		menu: #messageListMenu:shifted:; 
  		keyPress: #messageListKey:from:.
  	SystemBrowser browseWithDragNDrop 
  		ifTrue:[listSpec dragItem: #dragFromMessageList:].
  	^listSpec
  !

Item was added:
+ ----- Method: MessageSet>>changed: (in category 'updating') -----
+ changed: aspect
+ 
+ 	super changed: aspect.
+ 	
+ 	aspect = #messageList ifTrue: [
+ 		messageListFormatted := nil.
+ 		self changed: #messageListFormatted].!

Item was added:
+ ----- Method: MessageSet>>formattedLabel: (in category 'message list') -----
+ formattedLabel: aStringOrCodeReference
+ 
+ 	self class parse: aStringOrCodeReference toClassAndSelector: [:cls :sel |
+ 		^ self
+ 			formattedLabel: aStringOrCodeReference asString
+ 			forSelector: sel
+ 			inClass: cls]!

Item was added:
+ ----- Method: MessageSet>>messageListFormatted (in category 'message list') -----
+ messageListFormatted
+ 
+ 	^ messageListFormatted ifNil: [
+ 		messageListFormatted := messageList collect: [:ea | self formattedLabel: ea]]!

Item was changed:
  ----- Method: MessageTrace>>buildMessageListWith: (in category 'private initializing') -----
  buildMessageListWith: builder
  	| listSpec |
  	listSpec := builder pluggableAlternateMultiSelectionListSpec new.
  	listSpec 
  		model: self ;
+ 		list: #messageListFormatted ;
- 		list: #messageList ;
  		getIndex: #messageListIndex ;
  		setIndex: #toggleSelectionAt:shifted:controlled: ;
  		icon: #messageIconAt:;
  		help: #messageHelpAt:; 
  		menu: #messageListMenu:shifted: ; 
  		getSelectionList: #isMessageSelectedAt: ;
  		setSelectionList: #messageAt:beSelected: ;
  		keyPress: #messageListKey:from:.
  	SystemBrowser browseWithDragNDrop 
  		ifTrue: [ listSpec dragItem: #dragFromMessageList: ].
  	^ listSpec!



More information about the Squeak-dev mailing list