The Trunk: Kernel-nice.276.mcz

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

The Trunk: Kernel-nice.276.mcz

commits-2
Nicolas Cellier uploaded a new version of Kernel to project The Trunk:
http://source.squeak.org/trunk/Kernel-nice.276.mcz

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

Name: Kernel-nice.276
Author: nice
Time: 20 October 2009, 10:19:32 am
UUID: 76a252f2-4063-451a-86d2-e063dc8be599
Ancestors: Kernel-nice.275

Track keys and selectors usage, use #includesSelector: #selectorsDo: and #asSet where due

+ make #classVarNames a sorted Array

=============== Diff against Kernel-nice.275 ===============

Item was changed:
  ----- Method: ClassDescription>>chooseClassVarName (in category 'instance variables') -----
  chooseClassVarName
  "Present the user with a list of class variable names and answer the one selected, or nil if none"
 
  | lines labelStream allVars index |
  lines := OrderedCollection new.
  allVars := OrderedCollection new.
  labelStream := WriteStream on: (String new: 200).
  self withAllSuperclasses reverseDo:
  [:class | | vars |
+ vars := class classVarNames.
- vars := class classVarNames asSortedCollection.
  vars do:
  [:var |
  labelStream nextPutAll: var; cr.
  allVars add: var].
  vars isEmpty ifFalse: [lines add: allVars size]].
  labelStream contents isEmpty ifTrue: [^Beeper beep]. "handle nil superclass better"
  labelStream skip: -1 "cut last CR".
  index := (UIManager default chooseFrom: (labelStream contents substrings) lines: lines).
  index = 0 ifTrue: [^ nil].
  ^ allVars at: index!

Item was changed:
  ----- Method: Behavior>>whichSelectorsAccess: (in category 'testing method dictionary') -----
  whichSelectorsAccess: instVarName
+ "Answer a collection of selectors whose methods access the argument,
- "Answer a set of selectors whose methods access the argument,
  instVarName, as a named instance variable."
 
  | instVarIndex |
  instVarIndex := self allInstVarNames indexOf: instVarName ifAbsent: [^IdentitySet new].
  ^ self methodDict keys select:
  [:sel |
  ((self methodDict at: sel)
  readsField: instVarIndex)
  or: [(self methodDict at: sel) writesField: instVarIndex]]
 
  "Point whichSelectorsAccess: 'x'."!

Item was changed:
  ----- Method: InstructionPrinter class>>printClass: (in category 'printing') -----
  printClass: class
  "Create a file whose name is the argument followed by '.bytes'. Store on
  the file the symbolic form of the compiled methods of the class."
  | file |
  file := FileStream newFileNamed: class name , '.bytes'.
+ class selectorsDo:
- class selectors do:
  [:sel |
  file cr; nextPutAll: sel; cr.
  (self on: (class compiledMethodAt: sel)) printInstructionsOn: file].
  file close
  "InstructionPrinter printClass: Parser."
  !

Item was changed:
  ----- Method: ClassDescription>>replaceSilently:to: (in category 'instance variables') -----
  replaceSilently: old to: new
  "text-replace any part of a method.  Used for class and pool variables.  Don't touch the header.  Not guaranteed to work if name appears in odd circumstances"
  | oldCode newCode parser header body sels oldName newName |
 
  oldName := old asString.
  newName := new asString.
  self withAllSubclasses do:
+ [:cls | sels := cls selectors asSet.
- [:cls | sels := cls selectors.
  sels removeAllFoundIn: #(DoIt DoItIn:).
  sels do:
  [:sel |
  oldCode := cls sourceCodeAt: sel.
  "Don't make changes in the method header"
  (parser := cls parserClass new) parseSelector: oldCode.
  header := oldCode copyFrom: 1 to: (parser endOfLastToken min: oldCode size).
  body := header size > oldCode size
  ifTrue: ['']
  ifFalse: [oldCode copyFrom: header size+1 to: oldCode size].
  newCode := header , (body copyReplaceTokens: oldName with: newName).
  newCode ~= oldCode ifTrue:
  [cls compile: newCode
  classified: (cls organization categoryOfElement: sel)
  notifying: nil]].
  cls isMeta ifFalse:
  [oldCode := cls comment.
  newCode := oldCode copyReplaceTokens: oldName with: newName.
  newCode ~= oldCode ifTrue:
  [cls comment: newCode]]]!

Item was changed:
  ----- Method: Behavior>>whichSelectorsStoreInto: (in category 'testing method dictionary') -----
  whichSelectorsStoreInto: instVarName
+ "Answer a collection of selectors whose methods access the argument,
- "Answer a Set of selectors whose methods access the argument,
  instVarName, as a named instance variable."
  | instVarIndex |
  instVarIndex := self allInstVarNames indexOf: instVarName ifAbsent: [^IdentitySet new].
  ^ self methodDict keys select:
  [:sel | (self methodDict at: sel) writesField: instVarIndex]
 
  "Point whichSelectorsStoreInto: 'x'."!

Item was changed:
  ----- Method: Behavior>>classVarNames (in category 'accessing instances and variables') -----
  classVarNames
+ "Answer a collection of the receiver's class variable names."
- "Answer a Set of the receiver's class variable names."
 
+ ^#()!
- ^Set new!

Item was changed:
  ----- Method: Class>>classVarNames (in category 'class variables') -----
  classVarNames
+ "Answer a collection of the names of the class variables defined in the receiver."
- "Answer a Set of the names of the class variables defined in the receiver."
 
+ ^self classPool keys asArray sort!
- ^self classPool keys!

Item was changed:
  ----- Method: Class>>allClassVarNames (in category 'class variables') -----
  allClassVarNames
  "Answer a Set of the names of the receiver's class variables, including those
  defined in the superclasses of the receiver."
 
  | aSet |
  self superclass == nil
  ifTrue:
+ [^self classVarNames asSet]  "This is the keys so it is a new Set."
- [^self classVarNames]  "This is the keys so it is a new Set."
  ifFalse:
  [aSet := self superclass allClassVarNames.
  aSet addAll: self classVarNames.
  ^aSet]!