The Trunk: Protocols-ul.59.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: Protocols-ul.59.mcz

commits-2
Levente Uzonyi uploaded a new version of Protocols to project The Trunk:
http://source.squeak.org/trunk/Protocols-ul.59.mcz

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

Name: Protocols-ul.59
Author: ul
Time: 13 March 2017, 2:53:13.396649 pm
UUID: 63ac89e9-5ac0-466b-b292-7f86f691f733
Ancestors: Protocols-jr.58

SortedCollection Whack-a-mole

=============== Diff against Protocols-jr.58 ===============

Item was changed:
  ----- Method: Lexicon>>methodListFromSearchString: (in category 'search') -----
  methodListFromSearchString: fragment
  "Answer a method list of methods whose selectors match the given fragment"
 
  |  aList searchFor |
  currentQueryParameter := fragment.
  currentQuery := #selectorName.
  autoSelectString := fragment.
  searchFor := fragment asString asLowercase withBlanksTrimmed.
 
  aList := targetClass allSelectors select:
  [:aSelector | currentVocabulary includesSelector: aSelector forInstance: self targetObject ofClass: targetClass limitClass: limitClass].
  searchFor size > 0 ifTrue:
  [aList := aList select:
  [:aSelector | aSelector includesSubstring: searchFor caseSensitive: false]].
+ ^ aList sorted
- ^ aList asSortedArray
  !

Item was changed:
  ----- Method: Lexicon>>navigateToASender (in category 'senders') -----
  navigateToASender
  "Present the user with a list of senders of the currently-selected
  message, and navigate to the chosen one"
  | selectorSet chosen aSelector |
  aSelector := self selectedMessageName.
  selectorSet := Set new.
  (self systemNavigation allCallsOn: aSelector)
  do: [:anItem | selectorSet add: anItem methodSymbol].
  selectorSet := selectorSet
  select: [:sel | currentVocabulary
  includesSelector: sel
  forInstance: self targetObject
  ofClass: targetClass
  limitClass: limitClass].
  selectorSet size = 0
  ifTrue: [^ Beeper beep].
  self okToChange
  ifFalse: [^ self].
+ selectorSet := selectorSet sorted.
+ chosen := UIManager default chooseFrom: selectorSet values: selectorSet.
- chosen := UIManager default chooseFrom: selectorSet asSortedArray values: selectorSet asSortedArray.
  chosen isEmptyOrNil
  ifFalse: [self displaySelector: chosen]!

Item was changed:
  ----- Method: Lexicon>>selectorsMatching (in category 'search') -----
  selectorsMatching
  "Anwer a list of selectors in the receiver that match the current search string"
 
  | fragment aList |
  fragment := self lastSearchString asLowercase.
  aList := targetClass allSelectors select:
  [:aSelector | (aSelector includesSubstring: fragment caseSensitive: false) and:
  [currentVocabulary includesSelector: aSelector forInstance: self targetObject ofClass: targetClass limitClass: limitClass]].
 
+ ^ aList sorted!
- ^ aList asSortedArray!

Item was changed:
  ----- Method: Lexicon>>selectorsSendingSelectedSelector (in category 'senders') -----
  selectorsSendingSelectedSelector
  "Assumes lastSendersSearchSelector is already set"
  | selectorSet |
  autoSelectString := (self lastSendersSearchSelector upTo: $:) asString.
  selectorSet := Set new.
  (self systemNavigation allCallsOn: self lastSendersSearchSelector)
  do: [:anItem | | sel cl |
  sel := anItem methodSymbol.
  cl := anItem actualClass.
  ((currentVocabulary
  includesSelector: sel
  forInstance: self targetObject
  ofClass: targetClass
  limitClass: limitClass)
  and: [targetClass includesBehavior: cl])
  ifTrue: [selectorSet add: sel]].
+ ^ selectorSet sorted!
- ^ selectorSet asSortedArray!

Item was changed:
  ----- Method: Lexicon>>setMethodListFromSearchString (in category 'search') -----
  setMethodListFromSearchString
  "Set the method list of the receiver based on matches from the search string"
 
  | fragment aList |
  self okToChange ifFalse: [^ self].
  fragment := currentQueryParameter.
  fragment := fragment asString asLowercase withBlanksTrimmed.
 
  aList := targetClass allSelectors select:
  [:aSelector | currentVocabulary includesSelector: aSelector forInstance: self targetObject ofClass: targetClass limitClass: limitClass].
  fragment size > 0 ifTrue:
  [aList := aList select:
  [:aSelector | aSelector includesSubstring: fragment caseSensitive: false]].
  aList size = 0 ifTrue:
  [^ Beeper beep].
+ self initListFrom: aList sorted highlighting: targetClass.
- self initListFrom: aList asSortedArray highlighting: targetClass.
  messageListIndex :=  messageListIndex min: messageList size.
  self changed: #messageList
  !

Item was changed:
  ----- Method: ProtocolBrowser>>on: (in category 'private') -----
  on: aClass
  "Initialize with the entire protocol for the class, aClass."
+ self initListFrom: aClass allSelectors sorted
- self initListFrom: aClass allSelectors asSortedCollection
  highlighting: aClass!

Item was changed:
  ----- Method: ProtocolBrowser>>onSubProtocolOf: (in category 'private') -----
  onSubProtocolOf: aClass
  "Initialize with the entire protocol for the class, aClass,
  but excluding those inherited from Object."
  | selectors |
  selectors := Set new.
  aClass withAllSuperclasses do:
  [:each | (each == Object or: [each == ProtoObject])
  ifFalse: [selectors addAll: each selectors]].
+ self initListFrom: selectors sorted
- self initListFrom: selectors asSortedCollection
  highlighting: aClass!

Item was changed:
  ----- Method: Vocabulary>>initializeFromTable: (in category 'initialization') -----
  initializeFromTable: aTable
  "Initialize the receiver from a list of method-specification tuples, each of the form:
  (1) selector
  (2) companion setter selector (#none or nil indicate none)
  (3)  argument specification array, each element being an array of the form
  <arg name>  <arg type>
  (4)  result type, (#none or nil indicate none)
  (5)  array of category symbols, i.e. the categories in which this element should appear.
  (6)  help message. (optional)
  (7)  wording (optional)
  (8)  auto update flag (optional) - if #updating, set readout to refetch automatically
 
  Consult Vocabulary class.initializeTestVocabulary for an example of use"
 
  | categoryList |
  categoryList := Set new.
  aTable do:
  [:tuple | categoryList addAll: tuple fifth].
+ categoryList sorted do:
- categoryList := categoryList asSortedArray.
- categoryList do:
  [:aCategorySymbol | | aMethodCategory |
  aMethodCategory := ElementCategory new categoryName: aCategorySymbol.
  aTable do:
  [:tuple | | doc aSelector wording aMethodInterface |
  (tuple fifth includes: aCategorySymbol) ifTrue:
  [aMethodInterface := MethodInterface new.
  aSelector := tuple first.
  aMethodInterface selector: aSelector type: tuple fourth setter: tuple second.
  aMethodCategory elementAt: aSelector put: aMethodInterface.
  self atKey: aSelector putMethodInterface: aMethodInterface.
  ((tuple third ~~ #none) and: [tuple third isEmptyOrNil not])
  ifTrue:
  [aMethodInterface argumentVariables: (tuple third collect:
  [:pair | Variable new name: pair first type: pair second])].
  doc := (tuple size >= 6 and: [(#(nil none unused) includes: tuple sixth) not])
  ifTrue:
  [tuple sixth]
  ifFalse:
  [nil].
    wording := (tuple size >= 7 and: [(#(nil none unused) includes: tuple seventh) not])
  ifTrue:
  [tuple seventh]
  ifFalse:
  [aSelector asString].
  aMethodInterface
  wording: wording;
  helpMessage: doc.
  tuple size >= 8 ifTrue:
  [aMethodInterface setToRefetch]]].
  self addCategory: aMethodCategory]!