[Pkg] The Trunk: Kernel-ul.1063.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Mar 13 14:47:55 UTC 2017


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

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

Name: Kernel-ul.1063
Author: ul
Time: 13 March 2017, 5:08:47.219548 am
UUID: 3959a034-7e65-47a1-b70f-e493b376d673
Ancestors: Kernel-eem.1062

SortedCollection Whack-a-mole

=============== Diff against Kernel-eem.1062 ===============

Item was changed:
  ----- Method: Behavior>>compressedSourceCodeAt: (in category 'accessing method dictionary') -----
  compressedSourceCodeAt: selector
  	"(Paragraph compressedSourceCodeAt: #displayLines:affectedRectangle:) size 721 1921
  	Paragraph selectors inject: 0 into: [:tot :sel | tot + (Paragraph compressedSourceCodeAt: sel) size] 13606 31450"
  	| rawText parse |
  	rawText := (self sourceCodeAt: selector) asString.
  	parse := self newCompiler parse: rawText in: self notifying: nil.
  	^ rawText compressWithTable:
  		((selector keywords ,
  		parse tempNames ,
  		self instVarNames ,
  		#(self super ifTrue: ifFalse:) ,
  		((0 to: 7) collect:
  			[:i | String streamContents:
  				[:s | s cr. i timesRepeat: [s tab]]]) ,
  		(self compiledMethodAt: selector) literalStrings)
+ 			sorted: [:a :b | a size > b size])!
- 			asSortedCollection: [:a :b | a size > b size])!

Item was changed:
  ----- Method: Categorizer>>changeFromCategorySpecs: (in category 'accessing') -----
  changeFromCategorySpecs: categorySpecs 
  	"Tokens is an array of categorySpecs as scanned from a browser 'reorganize' pane, or built up by some other process, such as a scan of an environment."
  
+ 	| newCategories newStops cc currentStop oldElements newElements |
- 	| newCategories newStops temp cc currentStop oldElements newElements |
  	oldElements := elementArray asSet.
  	newCategories := Array new: categorySpecs size.
  	newStops := Array new: categorySpecs size.
  	currentStop := 0.
  	newElements := WriteStream on: (Array new: 16).
  	1 to: categorySpecs size do: 
+ 		[:i | | catSpec |
- 		[:i | | catSpec selectors |
  		catSpec := categorySpecs at: i.
  		newCategories at: i put: catSpec first asSymbol.
+ 		catSpec allButFirst
+ 			replace: [ :each | 
+ 				each isSymbol
+ 					ifTrue: [each]
+ 					ifFalse: [each printString asSymbol ] ];
+ 			sort;
+ 			do: [ :elem |
+ 				(oldElements remove: elem ifAbsent: nil) ifNotNil: [
+ 					newElements nextPut: elem.
+ 					currentStop := currentStop+1]].
- 		selectors := catSpec allButFirst collect: [:each | each isSymbol
- 							ifTrue: [each]
- 							ifFalse: [each printString asSymbol]].
- 		selectors asSortedCollection do:
- 			[:elem |
- 			(oldElements remove: elem ifAbsent: [nil]) notNil ifTrue:
- 				[newElements nextPut: elem.
- 				currentStop := currentStop+1]].
  		newStops at: i put: currentStop].
  
  	"Ignore extra elements but don't lose any existing elements!!"
  	oldElements := oldElements collect:
  		[:elem | Array with: (self categoryOfElement: elem) with: elem].
  	newElements := newElements contents.
  	categoryArray := newCategories.
  	(cc := categoryArray asSet) size = categoryArray size ifFalse: ["has duplicate element"
+ 		| uniqueElements |
+ 		uniqueElements := cc copy.
+ 		categoryArray withIndexDo: [ :dup :ii |
+ 			uniqueElements remove: dup ifAbsent: [ "real duplicate"
+ 				| dup2 num | 
+ 				num := 2.
+ 				[dup2 := (dup,' #', num printString) asSymbol.  cc includes: dup2] whileTrue: [num := num + 1].
+ 				cc add: dup2.
+ 				categoryArray at: ii put: dup2 ] ] ].
- 		temp := categoryArray asOrderedCollection.
- 		temp removeAll: categoryArray asSet asOrderedCollection.
- 		temp do: [:dup | | ii dup2 num | 
- 			ii := categoryArray indexOf: dup.
- 			num := 2..
- 			[dup2 := (dup,' #', num printString) asSymbol.  cc includes: dup2] whileTrue: [num := num + 1].
- 			cc add: dup2.
- 			categoryArray at: ii put: dup2]].
  	categoryStops := newStops.
  	elementArray := newElements.
  	oldElements do: [:pair | self classify: pair last under: pair first].!

Item was changed:
  ----- Method: ClassDescription>>allMethodsInCategory: (in category 'accessing method dictionary') -----
  allMethodsInCategory: aName 
  	"Answer a list of all the method categories of the receiver and all its 
  	superclasses "
+ 	| set |
+ 	set := Set new.
+ 	self withAllSuperclassesDo: [:aClass |
+ 		set	addAll: (
+ 			aName = ClassOrganizer allCategory
+ 					ifTrue: [aClass organization allMethodSelectors]
+ 					ifFalse: [aClass organization listAtCategoryNamed: aName])].
+ 	^set sorted
- 	| aColl |
- 	aColl := OrderedCollection new.
- 	self withAllSuperclasses
- 		do: [:aClass | aColl
- 				addAll: (aName = ClassOrganizer allCategory
- 						ifTrue: [aClass organization allMethodSelectors]
- 						ifFalse: [aClass organization listAtCategoryNamed: aName])].
- 	^ aColl asSet asSortedArray
  
  	"TileMorph allMethodsInCategory: #initialization"!

Item was changed:
  ----- Method: ClassDescription>>chooseInstVarAlphabeticallyThenDo: (in category 'instance variables') -----
  chooseInstVarAlphabeticallyThenDo: aBlock
  	| allVars index |
  	"Put up a menu of all the instance variables in the receiver, presented in alphabetical order, and when the user chooses one, evaluate aBlock with the chosen variable as its parameter."
  
+ 	allVars := self allInstVarNames.
- 	allVars := self allInstVarNames asSortedArray.
  	allVars isEmpty ifTrue: [^ self inform: 'There are no
  instance variables'].
+ 	allVars sort.
  
  	index := (UIManager default chooseFrom: allVars lines: #() title: 'Instance variables in
  ', self name).
  	index = 0 ifTrue: [^ self].
  	aBlock value: (allVars at: index)!

Item was changed:
  ----- Method: ClassDescription>>classCommentBlank (in category 'accessing comment') -----
  classCommentBlank
  
  	^String streamContents:
  		[:stream|
  		 stream
  			nextPutAll: 'A';
  			nextPutAll: (self name first isVowel ifTrue: ['n '] ifFalse: [' ']);
  			nextPutAll: self name;
  			nextPutAll: ' is xxxxxxxxx.';
  			cr; cr;
  			nextPutAll: 'Instance Variables'.
  
+ 		 self instVarNames sorted do: [:each |
- 		 self instVarNames asSortedCollection do: [:each |
  			stream
  				crtab; nextPutAll: each;
  				nextPut: $:;
  				tab: 2;
  				nextPutAll: '<Object>'].
  		  stream cr.
+ 		  self instVarNames sorted do: [:each |
- 		  self instVarNames asSortedCollection do: [:each |
  			stream
  				cr; nextPutAll: each;
  				crtab; nextPutAll: '- xxxxx'; cr]]!

Item was changed:
  ----- Method: ClassDescription>>printSubclassesOn:level: (in category 'accessing class hierarchy') -----
  printSubclassesOn: aStream level: level 
  	"As part of the algorithm for printing a description of the receiver, print the
  	subclass on the file stream, aStream, indenting level times."
  
  	| subclassNames |
  	aStream crtab: level.
  	aStream nextPutAll: self name.
  	aStream space; print: self instVarNames.
  	self == Class
  		ifTrue: 
  			[aStream crtab: level + 1; nextPutAll: '[ ... all the Metaclasses ... ]'.
  			^self].
+ 	subclassNames := self subclasses sort:[:c1 :c2| c1 name <= c2 name].
- 	subclassNames := self subclasses asSortedCollection:[:c1 :c2| c1 name <= c2 name].
  	"Print subclasses in alphabetical order"
  	subclassNames do:
  		[:subclass | subclass printSubclassesOn: aStream level: level + 1]!



More information about the Packages mailing list