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

commits at source.squeak.org commits at source.squeak.org
Thu Apr 23 00:56:42 UTC 2015


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

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

Name: VMMaker.oscog-eem.1242
Author: eem
Time: 22 April 2015, 5:53:15.54 pm
UUID: 24d3608c-2198-4927-90b4-477af0cca4e7
Ancestors: VMMaker.oscog-eem.1241

Fix the read-before-written initializer to not initialize
structs (if the struct types can be identified).

Make the allOldMarkedWeakObjectsOnWeaklingStack
assert an eassert: (it /is/ extremely expensive) and
correct some typos in eassert:.

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

Item was changed:
  ----- Method: SpurMemoryManager>>nilUnmarkedWeaklingSlots (in category 'weakness and ephemerality') -----
  nilUnmarkedWeaklingSlots
  	"Nil the unmarked slots in the weaklings on the
  	 weakling stack, finalizing those that lost references.
  	 Finally, empty the weaklingStack."
  	<inline: #never> "for profiling"
  	self cCode: '' inSmalltalk: [coInterpreter transcript nextPutAll: 'nilling...'; flush].
+ 	self eassert: self allOldMarkedWeakObjectsOnWeaklingStack.
- 	self assert: self allOldMarkedWeakObjectsOnWeaklingStack.
  	weaklingStack = nilObj ifTrue:
  		[^self].
  	self objStack: weaklingStack from: 0 do:
  		[:weakling| | anyUnmarked |
  		anyUnmarked := self nilUnmarkedWeaklingSlotsIn: weakling.
  		anyUnmarked ifTrue:
  			[coInterpreter signalFinalization: weakling]].
  	self emptyObjStack: weaklingStack!

Item was removed:
- ----- Method: TMethod>>findReadBeforeAssignedIn: (in category 'utilities') -----
- findReadBeforeAssignedIn: variables
- 	| readBeforeAssigned |
- 	readBeforeAssigned := Set new.
- 	parseTree
- 		addReadBeforeAssignedIn: variables
- 		to: readBeforeAssigned
- 		assignments: Set new.
- 	^readBeforeAssigned!

Item was added:
+ ----- Method: TMethod>>findReadBeforeAssignedIn:in: (in category 'utilities') -----
+ findReadBeforeAssignedIn: variables in: aCodeGen
+ 	| readBeforeAssigned |
+ 	readBeforeAssigned := Set new.
+ 	parseTree
+ 		addReadBeforeAssignedIn: variables
+ 		to: readBeforeAssigned
+ 		assignments: Set new
+ 		in: aCodeGen.
+ 	^readBeforeAssigned!

Item was changed:
  ----- Method: TMethod>>removeUnusedTempsAndNilIfRequiredIn: (in category 'utilities') -----
  removeUnusedTempsAndNilIfRequiredIn: aCodeGen
  	"Remove all of the unused temps in this method. Answer a set of the references.
  	 As a side-effect introduce explicit temp := nil statements for temps that are
  	 tested for nil before necessarily being assigned."
  	| refs readBeforeAssigned |
  	refs := self removeUnusedTempsIn: aCodeGen.
  	"reset the locals to be only those still referred to"
  	locals := locals select: [:e| refs includes: e].
  	(locals notEmpty
+ 	 and: [aCodeGen
+ 			pushScope: declarations
+ 			while: [(readBeforeAssigned := (self findReadBeforeAssignedIn: locals in: aCodeGen)) notEmpty]]) ifTrue:
- 	 and: [(readBeforeAssigned := (self findReadBeforeAssignedIn: locals)) notEmpty]) ifTrue:
  		[readBeforeAssigned := readBeforeAssigned reject:
  			[:v| | d | "don't initialize externa and/or arrays"
  			 d := self declarationAt: v.
  			 (d beginsWith: 'extern') or: [d includes: $[]].
  		 parseTree statements addAllFirst:
  			(readBeforeAssigned asSortedCollection collect:
  				[:var|
  				TAssignmentNode new
  					setVariable: (TVariableNode new setName: var; yourself)
  					expression: (TConstantNode new setValue: 0; yourself)])].
  	^refs!

Item was removed:
- ----- Method: TStmtListNode>>addReadBeforeAssignedIn:to:assignments: (in category 'utilities') -----
- addReadBeforeAssignedIn: variables to: readBeforeAssigned assignments: assigned
- 	"Add any variables in variables that are read before written to readBeforeAssigned.
- 	 Add unconditional assignments to assigned.  For convenience answer assigned."
- 	self
- 		nodesWithParentsDo:
- 			[:node :parent|
- 			(node isAssignment
- 			 and: [variables includes: node variable name]) ifTrue:
- 				[assigned add: node variable name].
- 			(node isVariable
- 			 and: [(variables includes: node name)
- 			 and: [(assigned includes: node name) not
- 			 and: [(parent notNil and: [parent isAssignment and: [parent variable == node]]) not]]]) ifTrue:
- 				[readBeforeAssigned add: node name]]
- 		unless:
- 			[:node :parent| | conditionalAssignments mayHaveSideEffects |
- 			node isSend
- 				ifTrue:
- 					["First deal with implicit assignments..."
- 					node isValueExpansion ifTrue:
- 						[assigned addAll: node receiver args].
- 					(#(mem:cp:y: mem:mo:ve:) includes: node selector) ifTrue:
- 						[assigned add: (node args first detect: [:subnode| subnode isVariable]) name].
- 					(#(to:do: to:by:do:) includes: node selector) ifTrue:
- 						[assigned addAll: (node args at: node selector numArgs) args.
- 						 mayHaveSideEffects := node args size = 4. "See TMethod>>prepareMethodIn:"
- 						 mayHaveSideEffects ifTrue:
- 							[assigned add: node args last name]].
- 					"Then deal with read-before-written in the arms of conditionals..."
- 					(#(ifTrue: ifFalse: ifNil: ifNotNil:) intersection: node selector keywords) notEmpty
- 						ifTrue:
- 							["First find assignments in the expression..."
- 							 (TStmtListNode new setStatements: {node receiver}; yourself)
- 								addReadBeforeAssignedIn: variables
- 								to: readBeforeAssigned
- 								assignments: assigned.
- 							 "Now find read-before-written in each arm, and collect the assignments to spot those assigned in both arms"
- 							 conditionalAssignments :=
- 								node args
- 									collect:
- 										[:block|
- 										block isStmtList ifTrue:
- 											[block
- 												addReadBeforeAssignedIn: variables
- 												to: readBeforeAssigned
- 												assignments: assigned copy]]
- 									thenSelect: [:each| each notNil].
- 							 "add to assigned those variables written to in both arms"
- 							 conditionalAssignments size = 2 ifTrue:
- 								[conditionalAssignments := conditionalAssignments collect: [:set| set difference: assigned].
- 								 assigned addAll: (conditionalAssignments first intersection: conditionalAssignments last)].
- 							 true]
- 						ifFalse:
- 							[false]]
- 				ifFalse:
- 					[false]].
- 	^assigned!

Item was added:
+ ----- Method: TStmtListNode>>addReadBeforeAssignedIn:to:assignments:in: (in category 'utilities') -----
+ addReadBeforeAssignedIn: variables to: readBeforeAssigned assignments: assigned in: aCodeGen
+ 	"Add any variables in variables that are read before written to readBeforeAssigned.
+ 	 Add unconditional assignments to assigned.  For convenience answer assigned."
+ 	self
+ 		nodesWithParentsDo:
+ 			[:node :parent|
+ 			(node isAssignment
+ 			 and: [variables includes: node variable name]) ifTrue:
+ 				[assigned add: node variable name].
+ 			(node isVariable
+ 			 and: [(variables includes: node name)
+ 			 and: [(assigned includes: node name) not
+ 			 and: [(node structTargetKindIn: aCodeGen) isNil
+ 			 and: [(parent notNil and: [parent isAssignment and: [parent variable == node]]) not]]]]) ifTrue:
+ 				[node name = 'theCalloutState' ifTrue:
+ 					[self halt].
+ 				 readBeforeAssigned add: node name]]
+ 		unless:
+ 			[:node :parent| | conditionalAssignments mayHaveSideEffects |
+ 			node isSend
+ 				ifTrue:
+ 					["First deal with implicit assignments..."
+ 					node isValueExpansion ifTrue:
+ 						[assigned addAll: node receiver args].
+ 					(#(mem:cp:y: mem:mo:ve:) includes: node selector) ifTrue:
+ 						[assigned add: (node args first detect: [:subnode| subnode isVariable]) name].
+ 					(#(to:do: to:by:do:) includes: node selector) ifTrue:
+ 						[assigned addAll: (node args at: node selector numArgs) args.
+ 						 mayHaveSideEffects := node args size = 4. "See TMethod>>prepareMethodIn:"
+ 						 mayHaveSideEffects ifTrue:
+ 							[assigned add: node args last name]].
+ 					"Then deal with read-before-written in the arms of conditionals..."
+ 					(#(ifTrue: ifFalse: ifNil: ifNotNil:) intersection: node selector keywords) notEmpty
+ 						ifTrue:
+ 							["First find assignments in the expression..."
+ 							 (TStmtListNode new setStatements: {node receiver}; yourself)
+ 								addReadBeforeAssignedIn: variables
+ 								to: readBeforeAssigned
+ 								assignments: assigned
+ 								in: aCodeGen.
+ 							 "Now find read-before-written in each arm, and collect the assignments to spot those assigned in both arms"
+ 							 conditionalAssignments :=
+ 								node args
+ 									collect:
+ 										[:block|
+ 										block isStmtList ifTrue:
+ 											[block
+ 												addReadBeforeAssignedIn: variables
+ 												to: readBeforeAssigned
+ 												assignments: assigned copy
+ 												in: aCodeGen]]
+ 									thenSelect: [:each| each notNil].
+ 							 "add to assigned those variables written to in both arms"
+ 							 conditionalAssignments size = 2 ifTrue:
+ 								[conditionalAssignments := conditionalAssignments collect: [:set| set difference: assigned].
+ 								 assigned addAll: (conditionalAssignments first intersection: conditionalAssignments last)].
+ 							 true]
+ 						ifFalse:
+ 							[false]]
+ 				ifFalse:
+ 					[false]].
+ 	^assigned!

Item was changed:
  ----- Method: VMClass>>eassert: (in category 'debug support') -----
  eassert: aBooleanExpressionOrBlock
  	"This is for expensive asserts that we're only interested in checking in extremis.
+ 	 For example now that Spur objStacks are debugged there's no benefit to
+ 	 evaluating isValidObjStack: throughout the mark loop because its damn slow."
- 	 For exampl,e now that Spur objStacks are debugged there's no benefit to evaluating
- 	 isValidObjStack: throguhout the mark loop because its damn slow."
  	<doNotGenerate>
  	ExpensiveAsserts ifTrue:
  		[aBooleanExpressionOrBlock value ifFalse:
  			[AssertionFailure signal: 'Assertion failed']]!



More information about the Vm-dev mailing list