[squeak-dev] The Trunk: System-ul.525.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Apr 27 22:02:32 UTC 2013


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

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

Name: System-ul.525
Author: ul
Time: 27 April 2013, 10:55:01.783 pm
UUID: 53a81762-7921-4495-9fb1-2fae75e89b63
Ancestors: System-fbs.524

Reshaped SpaceTally a bit. It's still messy, but simpler and faster than before. Also fixed the printing part.

=============== Diff against System-fbs.524 ===============

Item was changed:
  ----- Method: SpaceTally>>computeSpaceUsage (in category 'class analysis') -----
  computeSpaceUsage
  
+ 	results
+ 		do: [ :entry |
+ 			| class instanceSpaceAndCount |
+ 			class := self class environment at: entry analyzedClassName.
+ 			Smalltalk garbageCollectMost.
+ 			instanceSpaceAndCount := self spaceForInstancesOf: class.
+ 			entry 
+ 				codeSize: class spaceUsed;
+ 				instanceCount: instanceSpaceAndCount second;
+ 				spaceForInstances: instanceSpaceAndCount first ]
+ 		displayingProgress: 'Taking statistics...'!
- 	| entry c instanceCount |
- 	1 to: results size do: [:i |
- 		entry := results at: i.
- 		c := self class environment at: entry analyzedClassName.
- 		instanceCount := c instanceCount.
- 		entry codeSize: c spaceUsed.
- 		entry instanceCount: instanceCount.
- 		entry spaceForInstances: (self spaceForInstancesOf: c withInstanceCount: instanceCount).
- 		Smalltalk garbageCollectMost].
- 	
- !

Item was changed:
  ----- Method: SpaceTally>>printSpaceAnalysis:on: (in category 'fileOut') -----
  printSpaceAnalysis: threshold on: fileName
  	"SpaceTally new printSpaceAnalysis: 1000 on: 'STspace.text1'"
  
  	"sd-This method should be rewrote to be more coherent within the rest of the class 
  	ie using preAllocate and spaceForInstanceOf:"
  
  	"If threshold > 0, then only those classes with more than that number
  	of instances will be shown, and they will be sorted by total instance space.
  	If threshold = 0, then all classes will appear, sorted by name."
  
+ 	FileStream newFileNamed: fileName do: [ :file |
+ 		self printSpaceAnalysis: threshold onStream: file ]!
- 	| f totalCodeSpace totalInstCount totalInstSpace n totalPercent |
- 	Smalltalk garbageCollect.
- 	totalCodeSpace := totalInstCount := totalInstSpace := n := 0.
- 	results := OrderedCollection new: Smalltalk classNames size.
- 'Taking statistics...'
- 	displayProgressFrom: 0
- 	to: Smalltalk classNames size
- 	during: [:bar |
- 	Smalltalk allClassesDo:
- 		[:cl | | instSpace eltSize instCount codeSpace | codeSpace := cl spaceUsed.
- 		bar value: (n := n+1).
- 		Smalltalk garbageCollectMost.
- 		instCount := cl instanceCount.
- 		instSpace := (cl indexIfCompact > 0 ifTrue: [4] ifFalse: [8])*instCount. "Object headers"
- 		cl isVariable
- 			ifTrue: [eltSize := cl isBytes ifTrue: [1] ifFalse: [4].
- 					cl allInstancesDo: [:x | instSpace := instSpace + (x basicSize*eltSize)]]
- 			ifFalse: [instSpace := instSpace + (cl instSize*instCount*4)].
- 		results add: (SpaceTallyItem analyzedClassName: cl name codeSize: codeSpace instanceCount:  instCount spaceForInstances: instSpace).
- 		totalCodeSpace := totalCodeSpace + codeSpace.
- 		totalInstCount := totalInstCount + instCount.
- 		totalInstSpace := totalInstSpace + instSpace]].
- 	totalPercent := 0.0.
- 
- 	f := FileStream newFileNamed: fileName.
- 	f timeStamp.
- 	f nextPutAll: ('Class' padded: #right to: 30 with: $ );
- 			nextPutAll: ('code space' padded: #left to: 12 with: $ );
- 			nextPutAll: ('# instances' padded: #left to: 12 with: $ );
- 			nextPutAll: ('inst space' padded: #left to: 12 with: $ );
- 			nextPutAll: ('percent' padded: #left to: 8 with: $ ); cr.
- 
- 	threshold > 0 ifTrue:
- 		["If inst count threshold > 0, then sort by space"
- 		results := (results select: [:s | s instanceCount >= threshold or: [s spaceForInstances > (totalInstSpace // 500)]])
- 				asSortedCollection: [:s :s2 | s spaceForInstances > s2 spaceForInstances]].
- 
- 	results do:
- 		[:s | | percent | f nextPutAll: (s analyzedClassName padded: #right to: 30 with: $ );
- 			nextPutAll: (s codeSize printString padded: #left to: 12 with: $ );
- 			nextPutAll: (s instanceCount printString padded: #left to: 12 with: $ );
- 			nextPutAll: (s spaceForInstances printString padded: #left to: 14 with: $ ).
- 		percent := s spaceForInstances*100.0/totalInstSpace roundTo: 0.1.
- 		totalPercent := totalPercent + percent.
- 		percent >= 0.1 ifTrue:
- 			[f nextPutAll: (percent printString padded: #left to: 8 with: $ )].
- 		f cr].
- 
- 	f cr; nextPutAll: ('Total' padded: #right to: 30 with: $ );
- 		nextPutAll: (totalCodeSpace printString padded: #left to: 12 with: $ );
- 		nextPutAll: (totalInstCount printString padded: #left to: 12 with: $ );
- 		nextPutAll: (totalInstSpace printString padded: #left to: 14 with: $ );
- 		nextPutAll: ((totalPercent roundTo: 0.1) printString padded: #left to: 8 with: $ ).
- 	f close!

Item was added:
+ ----- Method: SpaceTally>>printSpaceAnalysis:onStream: (in category 'fileOut') -----
+ printSpaceAnalysis: threshold onStream: stream
+ 	"If threshold > 0, then only those classes with more than that number
+ 	of instances will be shown, and they will be sorted by total instance space.
+ 	If threshold = 0, then all classes will appear, sorted by name."
+ 
+ 	| totalCodeSpace totalInstCount totalInstSpace totalPercent classNameLength printRow |
+ 	self systemWideSpaceTally.
+ 	totalCodeSpace := totalInstCount := totalInstSpace := 0.
+ 	classNameLength := 1.
+ 	results do: [ :each |
+ 		classNameLength := classNameLength max: each analyzedClassName size.
+ 		totalCodeSpace := totalCodeSpace + each codeSize.
+ 		totalInstCount := totalInstCount + each instanceCount.
+ 		totalInstSpace := totalInstSpace + each spaceForInstances ].
+ 	totalPercent := 0.0.
+ 
+ 	printRow := [ :class :codeSpace :instanceCount :instanceSpace :percent |
+ 		stream
+ 			nextPutAll: (class padded: #right to: classNameLength + 1 with: $ );
+ 			nextPutAll: (codeSpace padded: #left to: 12 with: $ );
+ 			nextPutAll: (instanceCount padded: #left to: 12 with: $ );
+ 			nextPutAll: (instanceSpace padded: #left to: 14 with: $ );
+ 			nextPutAll: (percent padded: #left to: 8 with: $ );
+ 			cr ].
+ 
+ 	stream timeStamp.
+ 	printRow valueWithArguments: { 'Class'. 'code space'. '# instances'. 'inst space'. 'percent' }.
+ 
+ 	threshold > 0 ifTrue: [
+ 		"If inst count threshold > 0, then sort by space"
+ 		results := results select: [ :s |
+ 			s instanceCount >= threshold or: [
+ 				s spaceForInstances > (totalInstSpace // 500) ] ].
+ 		results sort: [ :s :s2 | s spaceForInstances > s2 spaceForInstances ] ].
+ 
+ 	results do: [ :s |
+ 		| percent | 
+ 		percent := s spaceForInstances * 100.0 / totalInstSpace.
+ 		totalPercent := totalPercent + percent.
+ 		printRow valueWithArguments: {
+ 			s analyzedClassName.
+ 			s codeSize printString.
+ 			s instanceCount printString.
+ 			s spaceForInstances printString.
+ 			percent printShowingDecimalPlaces: 1 } ].
+ 
+ 	stream cr.
+ 	printRow valueWithArguments: {
+ 		'Total'.
+ 		totalCodeSpace printString.
+ 		totalInstCount printString.
+ 		totalInstSpace printString.
+ 		totalPercent printShowingDecimalPlaces: 1 }!

Item was added:
+ ----- Method: SpaceTally>>spaceForInstancesOf: (in category 'instance size') -----
+ spaceForInstancesOf: aClass
+ 	"Answer the number of bytes consumed by all instances of the given class, including their object headers and the number of instances."
+ 
+ 	| smallHeaderSize instVarBytes isVariable bytesPerElement  total lastInstance instance instanceCount |
+ 	instance := aClass someInstance ifNil: [ ^#(0 0) ].	
+ 	smallHeaderSize := aClass isCompact ifTrue: [ 4 ] ifFalse: [ 8 ].
+ 	instVarBytes := aClass instSize * 4.
+ 	isVariable := aClass isVariable.
+ 	bytesPerElement := isVariable
+ 		ifFalse: [ 0 ]
+ 		ifTrue: [ aClass isBytes ifTrue: [ 1 ] ifFalse: [ 4 ] ].
+ 	total := 0.
+ 	instanceCount := 0.
+ 	"A modified version of #allInstancesDo: is inlined here. It avoids an infinite loop when another process is creating new instances of aClass."
+ 	self flag: #allInstancesDo:.
+ 	lastInstance := aClass basicNew.
+ 	[ instance == lastInstance ] whileFalse: [
+ 		| contentBytes headerBytes |
+ 		contentBytes := instVarBytes + (isVariable
+ 			ifFalse: [ 0 ]
+ 			ifTrue: [ instance basicSize * bytesPerElement ]).
+ 		headerBytes := contentBytes > 255
+ 			ifTrue: [ 12 ]
+ 			ifFalse: [ smallHeaderSize ].
+ 		total := total + headerBytes + (contentBytes roundUpTo: 4).
+ 		instanceCount := instanceCount + 1.
+ 		instance := instance nextInstance ].
+ 	^{ total. instanceCount }!

Item was removed:
- ----- Method: SpaceTally>>spaceForInstancesOf:withInstanceCount: (in category 'instance size') -----
- spaceForInstancesOf: aClass withInstanceCount: instCount
- 	"Answer the number of bytes consumed by all instances of the given class, including their object headers."
- 
- 	| isCompact instVarBytes bytesPerElement headerBytes total |
- 	instCount = 0 ifTrue: [^ 0].
- 	isCompact := aClass indexIfCompact > 0.
- 	instVarBytes := aClass instSize * 4.
- 	aClass isVariable
- 		ifTrue: [
- 			bytesPerElement := aClass isBytes ifTrue: [1] ifFalse: [4].
- 			total := 0.
- 			aClass allInstancesDo: [:inst | | contentBytes |
- 				contentBytes := instVarBytes + (inst size * bytesPerElement).
- 				headerBytes :=
- 					contentBytes > 255
- 						ifTrue: [12]
- 						ifFalse: [isCompact ifTrue: [4] ifFalse: [8]].
- 				total := total + headerBytes + contentBytes].
- 			^ total]
- 		ifFalse: [
- 			headerBytes :=
- 				instVarBytes > 255
- 					ifTrue: [12]
- 					ifFalse: [isCompact ifTrue: [4] ifFalse: [8]].
- 			^ instCount * (headerBytes + instVarBytes)].
- !



More information about the Squeak-dev mailing list