[Vm-dev] VM Maker: VMMaker.oscog-eem.819.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Jul 14 19:40:44 UTC 2014


Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.819.mcz

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

Name: VMMaker.oscog-eem.819
Author: eem
Time: 14 July 2014, 12:37:52.726 pm
UUID: 8ec2ee28-4740-4d74-9dce-9cc89e7604d3
Ancestors: VMMaker.oscog-eem.818

Fix localization bug.  Variables in initialize methods were not
considered references (cuz there are excluded).  This caused
VMMaker.oscog-eem.816's extraction of zero/false vars to
StackInterpreter>>#initialize to cause nextPollUsecs to be
localized to checkForEventsMayContextSwitch:.

=============== Diff against VMMaker.oscog-eem.818 ===============

Item was changed:
  ----- Method: CCodeGenerator>>addMethodFor:selector: (in category 'utilities') -----
  addMethodFor: aClass selector: selector
  	"Add the given method to the code base and answer its translation
  	 or nil if it shouldn't be translated."
  
  	| method tmethod |
- 	selector == #initialize ifTrue:
- 		[^nil].
  	method := aClass compiledMethodAt: selector.
  	(method pragmaAt: #doNotGenerate) ifNotNil:
  		["only remove a previous method if this one overrides it, i.e. this is a subclass method.
  		 If the existing method is in a different hierarchy this method must be merely a redeirect."
  		 (methods at: selector ifAbsent: []) ifNotNil:
  			[:tm|
  			(aClass includesBehavior: tm definingClass) ifTrue:
  				[methods removeKey: selector]].
  		 ^nil].
  	method isSubclassResponsibility ifTrue:
  		[methods removeKey: selector ifAbsent: [].
  		 ^nil].
  	(self shouldIncludeMethodFor: aClass selector: selector) ifFalse:
  		[methods removeKey: selector ifAbsent: [].
  		 ^nil].
+ 	tmethod := self compileToTMethodSelector: selector in: aClass.
+ 	"Even thoug we exclude initialize methods, we must consider their
+ 	 global variable usage, otherwise globals may be incorrectly localized."
+ 	selector == #initialize ifTrue:
+ 		[self checkForGlobalUsage: tmethod allReferencedVariables in: tmethod.
+ 		 ^nil].
+ 	self addMethod: tmethod.
- 	tmethod := self addMethod: (self compileToTMethodSelector: selector in: aClass).
  	"If the method has a macro then add the macro.  But keep the method
  	 for analysis purposes (e.g. its variable accesses)."
  	(method pragmaAt: #cmacro:) ifNotNil:
  		[:pragma|
  		self addMacro: (pragma argumentAt: 1) for: selector.
  		(inlineList includes: selector) ifTrue:
  			[inlineList := inlineList copyWithout: selector]].
  	(method propertyValueAt: #cmacro:) ifNotNil:
  		[:macro|
  		self addMacro: macro for: selector.
  		(inlineList includes: selector) ifTrue:
  			[inlineList := inlineList copyWithout: selector]].
  	^tmethod!

Item was changed:
  ----- Method: CCodeGenerator>>localizeGlobalVariables (in category 'utilities') -----
  localizeGlobalVariables
  	| candidates elected localized |
  
  	"find all globals used in only one method"
  	candidates := globalVariableUsage select: [:e | e size = 1].
  	(candidates keys select: [:k| vmClass mustBeGlobal: k]) do:
  		[:k| candidates removeKey: k].
  	elected := Set new.
  	localized := Dictionary new. "for an ordered report"
  	"move any suitable global to be local to the single method using it"
  	candidates keysAndValuesDo:
  		[:key :targets |
  		targets do:
+ 			[:name |
+ 			(methods at: name ifAbsent: []) ifNotNil:
+ 				[:procedure | | newDeclaration |
+ 				procedure isRealMethod ifTrue:
+ 					[(localized at: name ifAbsentPut: [SortedCollection new]) add: key.
+ 					elected add: (procedure locals add: key).
+ 					newDeclaration := variableDeclarations at: key ifAbsent: ['sqInt ', key].
+ 					(self initializerForInstVar: key inStartClass: procedure definingClass) ifNotNil:
+ 						[:initializerNode|
+ 						newDeclaration := String streamContents:
+ 												[:s|
+ 												 s nextPutAll: newDeclaration; nextPutAll: ' = '.
+ 												 initializerNode emitCCodeOn: s level: 0 generator: self]].
+ 					procedure declarationAt: key put: newDeclaration.
+ 					variableDeclarations removeKey: key ifAbsent: []]]]].
- 			[:name | | procedure newDeclaration |
- 			procedure := methods at: name.
- 			procedure isRealMethod ifTrue:
- 				[(localized at: name ifAbsentPut: [SortedCollection new]) add: key.
- 				elected add: (procedure locals add: key).
- 				newDeclaration := variableDeclarations at: key ifAbsent: ['sqInt ', key].
- 				(self initializerForInstVar: key inStartClass: procedure definingClass) ifNotNil:
- 					[:initializerNode|
- 					newDeclaration := String streamContents:
- 											[:s|
- 											 s nextPutAll: newDeclaration; nextPutAll: ' = '.
- 											 initializerNode emitCCodeOn: s level: 0 generator: self]].
- 				procedure declarationAt: key put: newDeclaration.
- 				variableDeclarations removeKey: key ifAbsent: []]]].
  	logger ifNotNil:
  		[localized keys asSortedCollection do:
  			[:name|
  			(localized at: name) do:
  				[:var|
  				logger ensureCr; show: var, ' localised to ', name; cr]]].
  	elected do: [:ea| (variables includes: ea) ifTrue: [self checkDeleteVariable: ea]].
  	variables removeAllFoundIn: elected!

Item was changed:
  ----- Method: CCodeGeneratorGlobalStructure>>buildSortedVariablesCollection (in category 'C code generator') -----
  buildSortedVariablesCollection
  	"Build sorted vars, end result will be sorted collection based on static usage, 
  	perhaps cache lines will like this!!"
  
  	| globalNames |
  	globalNames := Bag new: globalVariableUsage size.
  	globalVariableUsage keysAndValuesDo:
  		[:k :v | | count |
  		count := 0.
  		v do:
+ 			[:methodName|
+ 			(methods at: methodName ifAbsent: []) ifNotNil:
+ 				[:method|
+ 				 method parseTree nodesDo:
+ 					[:n|
+ 					(n isVariable
+ 					 and: [n name hasEqualElements: k]) ifTrue:
+ 						[count := count + 1]]]].
- 			[:methodName| | method |
- 			method := methods at: methodName.
- 			method parseTree nodesDo:
- 				[:n|
- 				(n isVariable
- 				 and: [n name hasEqualElements: k]) ifTrue:
- 					[count := count + 1]]].
  		globalNames
  			add: k		"move arrays (e.g. methodCache) to end of struct"
  			withOccurrences: (((variableDeclarations at: k ifAbsent: ['']) includes: $[)
  								ifTrue: [count]
  								ifFalse: [count + 1000])].
  	variableDeclarations keysDo:
  		[:e | globalNames add: e withOccurrences: 0].
  	variables do:
  		[:e | globalNames add: e withOccurrences: 0].
  	^(globalNames sortedElements asSortedCollection:
  		[:a1 :a2| a1 value > a2 value or: [a1 value = a2 value and: [a1 key <= a2 key]]]) collect:
  			[:ea| ea key]!

Item was added:
+ ----- Method: TMethod>>allReferencedVariables (in category 'accessing') -----
+ allReferencedVariables
+ 	"Answer the set of all variables referenced in the receiver."
+ 	| refs |
+ 	refs := Set new.
+ 	"find all the variable names referenced in this method"
+ 	parseTree nodesDo:
+ 		[:node|
+ 		node isVariable ifTrue: [refs add: node name asString].
+ 		node isStmtList ifTrue: [refs addAll: node args]].
+ 	"add all the non-arg declarations (might be variables used only in cCode sections)"
+ 	refs addAll: (declarations keys reject: [:e | self args includes: e]).
+ 	^refs!

Item was changed:
  ----- Method: TMethod>>removeUnusedTemps (in category 'utilities') -----
  removeUnusedTemps
+ 	"Remove all of the unused temps in this method. Answer a set of the references."
+ 	"After inlining some variable references are now obsolete, we could fix them there
+ 	 but the code seems a bit complicated, the other choice to to rebuild the locals
+ 	 before extruding. This is done here"
- 	"Remove all of the unused temps in this method. Answer a bag (why the hell a bag???) with the references."
- 	"After inlining some variable references are now obsolete, we could fix them there but the 
- 	code seems a bit complicated, the other choice to to rebuild the locals before extruding. This is done here"
  	| refs |
+ 	refs := self allReferencedVariables.
- 	refs := Bag new.
- 	"find all the variable names referenced in this method"
- 	parseTree nodesDo: [ :node |
- 		node isVariable ifTrue: [ refs add: node name asString ].
- 		node isStmtList ifTrue: [refs addAll: node args]].
- 	"add all the non-arg declarations (might be variables used only in cCode sections)"
- 	refs addAll: (declarations keys reject: [:e | self args includes: e]).
  	"reset the locals to be only those still referred to"
+ 	locals := locals select: [:e| refs includes: e].
+ 	^refs!
- 	locals := locals select: [:e | refs includes: e].
- 	^refs
- !



More information about the Vm-dev mailing list