[squeak-dev] The Trunk: Tools-ul.1145.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Mar 31 07:41:14 UTC 2022


Levente Uzonyi uploaded a new version of Tools to project The Trunk:
http://source.squeak.org/trunk/Tools-ul.1145.mcz

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

Name: Tools-ul.1145
Author: ul
Time: 30 March 2022, 5:28:44.378745 pm
UUID: 1012c26d-a7d8-4985-a836-a050c950331a
Ancestors: Tools-mt.1144

- fix MessageSet >> #sortByDate by keeping messageList an OrderedCollection
- use Symbol class >> #lookUp: instead of #hasInterned:ifTrue:

=============== Diff against Tools-mt.1144 ===============

Item was changed:
  ----- Method: MessageNames>>computeSelectorListFrom: (in category 'search') -----
  computeSelectorListFrom: searchString
  	"Compute selector list from search string. The searchString is a list of expressions separated by ;. Each expression is matched individually. An expression can be a simple string (same as *expression*), a string with double quotes (exact match) or a match expression (see String >> #match:)."
  	
  	^ (Array streamContents: [ :stream |
  			(searchString findBetweenSubStrs: ';') do: [ :selPat |
  				(selPat first = $" and: [ selPat last = $" and: [ selPat size > 2 ] ])
  					ifTrue: [
+ 						(Symbol lookup: (selPat copyFrom: 2 to: selPat size - 1))
+ 							ifNotNil: [ :sym | stream nextPut: sym ] ]
- 						Symbol 
- 							hasInterned: (selPat copyFrom: 2 to: selPat size - 1)
- 							ifTrue: [ :sym | stream nextPut: sym ] ]
  					ifFalse: [
  						| raw n m |
  						n := selPat occurrencesOf: $*.
  						m := selPat occurrencesOf:  $#.
  						raw := ((n > 0 or: [ m > 0 ]) 	and: [ selPat size > (n + m) ])
  							ifTrue: [ Symbol selectorsMatching: selPat ]
  							ifFalse: [ Symbol selectorsContaining: selPat ].
  						stream nextPutAll: raw ] ] ]) 
  			sort: [ :x :y | x caseInsensitiveLessOrEqual: y ]!

Item was changed:
  ----- Method: MessageSet>>filterToImplementorsOf (in category 'filtering') -----
  filterToImplementorsOf
  	"Filter the receiver's list down to only those items with a given selector"
  
  	| aFragment inputWithBlanksTrimmed |
  
  	aFragment := self request: 'type selector:' initialAnswer: ''.
  	aFragment  isEmptyOrNil ifTrue: [^ self].
  	inputWithBlanksTrimmed := aFragment withBlanksTrimmed.
+ 	(Symbol lookup: inputWithBlanksTrimmed) ifNotNil:
- 	Symbol hasInterned: inputWithBlanksTrimmed ifTrue:
  		[:aSymbol | 
  			self filterFrom:
  				[:aClass :aSelector |
  					aSelector == aSymbol]]!

Item was changed:
  ----- Method: MessageSet>>filterToNotImplementorsOf (in category 'filtering') -----
  filterToNotImplementorsOf
  	"Filter the receiver's list down to only those items whose selector is NOT one solicited from the user."
  
  	| aFragment inputWithBlanksTrimmed |
  
  	aFragment := self request: 'type selector: ' initialAnswer: ''.
  	aFragment  isEmptyOrNil ifTrue: [^ self].
  	inputWithBlanksTrimmed := aFragment withBlanksTrimmed.
+ 	(Symbol lookup: inputWithBlanksTrimmed) ifNotNil:
- 	Symbol hasInterned: inputWithBlanksTrimmed ifTrue:
  		[:aSymbol | 
  			self filterFrom:
  				[:aClass :aSelector |
  					aSelector ~~ aSymbol]]!

Item was changed:
  ----- Method: MessageSet>>filterToNotSendersOf (in category 'filtering') -----
  filterToNotSendersOf
  	"Filter the receiver's list down to only those items which do not send a given selector"
  
  	| aFragment inputWithBlanksTrimmed |
  
  	aFragment := self request: 'type selector:' initialAnswer: ''.
  	aFragment  isEmptyOrNil ifTrue: [^ self].
  	inputWithBlanksTrimmed := aFragment withBlanksTrimmed.
+ 	(Symbol lookup: inputWithBlanksTrimmed) ifNotNil:
- 	Symbol hasInterned: inputWithBlanksTrimmed ifTrue:
  		[:aSymbol | 
  			self filterFrom:
  				[:aClass :aSelector | | aMethod |
  					(aMethod := aClass compiledMethodAt: aSelector) isNil or:
  						[(aMethod hasLiteral: aSymbol) not]]]!

Item was changed:
  ----- Method: MessageSet>>filterToSendersOf (in category 'filtering') -----
  filterToSendersOf
  	"Filter the receiver's list down to only those items which send a given selector"
  
  	| aFragment inputWithBlanksTrimmed |
  
  	aFragment := self request: 'type selector:' initialAnswer: ''.
  	aFragment  isEmptyOrNil ifTrue: [^ self].
  	inputWithBlanksTrimmed := aFragment withBlanksTrimmed.
+ 	(Symbol lookup: inputWithBlanksTrimmed) ifNotNil:
- 	Symbol hasInterned: inputWithBlanksTrimmed ifTrue:
  		[:aSymbol | 
  			self filterFrom:
  				[:aClass :aSelector | | aMethod |
  					(aMethod := aClass compiledMethodAt: aSelector) notNil and:
  						[aMethod hasLiteral: aSymbol]]]
  
  !

Item was changed:
  ----- Method: MessageSet>>sortByDate (in category 'message list') -----
  sortByDate
  	"Sort the message-list by date of time-stamp"
  
+ 	| associations |
+ 	associations := messageList collect:
- 	| assocs inOrder |
- 	assocs := messageList collect:
  		[:aRef | | aDate aCompiledMethod |
  			aDate := aRef methodSymbol == #Comment
  				ifTrue:
  					[aRef actualClass organization dateCommentLastSubmitted]
  				ifFalse:
  					[aCompiledMethod := aRef actualClass compiledMethodAt: aRef methodSymbol ifAbsent: [nil].
  					aCompiledMethod ifNotNil: [aCompiledMethod dateMethodLastSubmitted]].
  			aRef -> (aDate ifNil: [Date fromString: '01/01/1996'])].  "The dawn of Squeak history"
+ 	messageList := associations 
+ 		sort: #value asSortFunction;
+ 		replace: [ :association | association key ];
+ 		yourself.
- 	inOrder := assocs asArray sort: [:a :b | a value < b value].
- 
- 	messageList := inOrder collect: [:assoc | assoc key].
  	self changed: #messageList!



More information about the Squeak-dev mailing list