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

commits at source.squeak.org commits at source.squeak.org
Thu Sep 25 22:37:16 UTC 2014


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

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

Name: VMMaker.oscog-eem.885
Author: eem
Time: 25 September 2014, 3:34:13.601 pm
UUID: 292f0a8d-0afa-4943-90fd-be53fb40772a
Ancestors: VMMaker.oscog-eem.884

Fix regression in youngReferrers management in
V3 become introduced in VMMaker.oscog-eem.882.
We /must/ priune young referrers if
mapObjectReferencesInMachineCodeForBecome
removes a cog method from youngReferrers because
it may get added back and youngReferrers cannot
contain duplicates.

Fix potential bug in Spur become argument validation.
Check for immediates needs to come /after/
following forwarders since an object can
become-forward to an immediate.

Fix cPICHasForwardedClass:; this did /not/
enumerate the classIndices in a Spur Closed PIC.

Fix codeGeneratorToComputeAccessorDepth.  I
went to all that trouble in VMMaker.oscog-eem.873
to not rely on cogitClass et al but forgot to change
the operative case.

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

Item was changed:
  ----- Method: CogVMSimulator>>codeGeneratorToComputeAccessorDepth (in category 'primitive support') -----
  codeGeneratorToComputeAccessorDepth
  	^VMMaker new
- 		cogitClass: self class cogitClass;
  		buildCodeGeneratorForInterpreter: CoInterpreterPrimitives
  		includeAPIMethods: false
  		initializeClasses: false!

Item was changed:
  ----- Method: Cogit>>cPICHasForwardedClass: (in category 'in-line cacheing') -----
  cPICHasForwardedClass: cPIC
  	<var: #cPIC type: #'CogMethod *'>
  	| pc |
+ 	pc := cPIC asUnsignedInteger
+ 		+ firstCPICCaseOffset
+ 		+ cPICCaseSize
+ 		- backEnd jumpLongConditionalByteSize.
+ 	2 to: cPIC cPICNumCases do:
- 	pc := cPIC asInteger + firstCPICCaseOffset.
- 	1 to: cPIC cPICNumCases do:
  		[:i| | classIndex |
+ 		classIndex := backEnd inlineCacheTagAt: pc.
- 		classIndex := backEnd inlineCacheTagAt: pc
- 												- backEnd jumpLongConditionalByteSize
- 												- backEnd loadLiteralByteSize.
  		(objectMemory isForwardedClassIndex: classIndex) ifTrue:
  			[^true].
  		pc := pc + cPICCaseSize].
  	^false!

Item was changed:
  ----- Method: Cogit>>mapObjectReferencesInMachineCodeForBecome (in category 'garbage collection') -----
  mapObjectReferencesInMachineCodeForBecome
  	"Update all references to objects in machine code for a become.
  	 Unlike incrementalGC or fullGC a method that does not refer to young may
  	 refer to young as a result of the become operation.  Unlike incrementalGC
  	 or fullGC the reference from a Cog method to its methodObject *must not*
  	 change since the two are two halves of the same object."
  	| cogMethod hasYoungObj hasYoungObjPtr freedPIC |
  	<var: #cogMethod type: #'CogMethod *'>
  	hasYoungObj := false.
  	hasYoungObjPtr := (self addressOf: hasYoungObj put: [:val| hasYoungObj := val]) asInteger.
  	codeModified := freedPIC := false.
  	self mapObjectReferencesInGeneratedRuntime.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[self assert: hasYoungObj not.
  		 cogMethod cmType ~= CMFree ifTrue:
  			[self assert: (self cogMethodDoesntLookKosher: cogMethod) = 0.
  			 cogMethod selector: (objectRepresentation remapOop: cogMethod selector).
  			 cogMethod cmType = CMClosedPIC
  				ifTrue:
  					[((objectMemory isYoung: cogMethod selector)
  					   or: [self mapObjectReferencesInClosedPIC: cogMethod]) ifTrue:
  						[freedPIC := true.
  						 methodZone freeMethod: cogMethod]]
  				ifFalse:
  					[(objectMemory isYoung: cogMethod selector) ifTrue:
  						[hasYoungObj := true].
  					 cogMethod cmType = CMMethod ifTrue:
  						[| remappedMethod |
  						 self assert: cogMethod objectHeader = objectMemory nullHeaderForMachineCodeMethod.
  						 remappedMethod := objectRepresentation remapOop: cogMethod methodObject.
  						 remappedMethod ~= cogMethod methodObject ifTrue:
  							[(coInterpreter methodHasCogMethod: remappedMethod) ifTrue:
  								[self error: 'attempt to become two cogged methods'].
  							 (objectMemory
  									withoutForwardingOn: cogMethod methodObject
  									and: remappedMethod
  									with: cogMethod cmUsesPenultimateLit
  									sendToCogit: #method:hasSameCodeAs:checkPenultimate:) ifFalse:
  								[self error: 'attempt to become cogged method into different method'].
  							 "For non-Newspeak there should ne a one-to-one mapping between bytecoded and
  							  cog methods.  For Newspeak not necessarily, but only for anonymous accessors."
  							 "Only reset the method object's header if it is referring to this CogMethod."
  							 (coInterpreter rawHeaderOf: cogMethod methodObject) = cogMethod asInteger
  								ifTrue:
  									[coInterpreter
  										rawHeaderOf: cogMethod methodObject
  										put: cogMethod methodHeader.
  									 cogMethod
  										methodHeader: (coInterpreter rawHeaderOf: remappedMethod);
  										methodObject: remappedMethod.
  									 coInterpreter
  										rawHeaderOf: remappedMethod
  										put: cogMethod asInteger]
  								ifFalse:
  									[self assert: (self noAssertMethodClassAssociationOf: cogMethod methodObject)
  													= objectMemory nilObject.
  									 cogMethod
  										methodHeader: (coInterpreter rawHeaderOf: remappedMethod);
  										methodObject: remappedMethod]].
  						 (objectMemory isYoung: cogMethod methodObject) ifTrue:
  							[hasYoungObj := true]].
  					 self mapFor: cogMethod
  						 performUntil: #remapIfObjectRef:pc:hasYoung:
  						 arg: hasYoungObjPtr.
  					 hasYoungObj
  						ifTrue:
  							[methodZone ensureInYoungReferrers: cogMethod.
  							hasYoungObj := false]
  						ifFalse:
  							[cogMethod cmRefersToYoung: false]]].
  		cogMethod := methodZone methodAfter: cogMethod].
+ 	"we /must/ prune youngReferrers here because a) the [cogMethod cmRefersToYoung: false]
+ 	 block could have removed a method and subsequently it could be added back, and b) we
+ 	 can not tolerate duplicates in the youngReferrers list."  
+ 	methodZone pruneYoungReferrers.
  	freedPIC ifTrue:
  		[self unlinkSendsToFree].
  	codeModified ifTrue: "After updating oops in inline caches we need to flush the icache."
  		[processor flushICacheFrom: codeBase to: methodZone limitZony asInteger]!

Item was changed:
  ----- Method: SpurMemoryManager>>containsOnlyValidBecomeObjects: (in category 'become implementation') -----
  containsOnlyValidBecomeObjects: array
  	"Answer 0 if the array contains only unpinned non-immediates.
  	 Otherwise answer an informative error code.
  	 Can't become: immediates!!  Shouldn't become pinned objects."
  	| fieldOffset effectsFlags oop |
  	fieldOffset := self lastPointerOf: array.
  	effectsFlags := 0.
  	"same size as array2"
  	[fieldOffset >= self baseHeaderSize] whileTrue:
  		[oop := self longAt: array + fieldOffset.
+ 		 (self isOopForwarded: oop) ifTrue:
- 		 (self isImmediate: oop) ifTrue: [^PrimErrInappropriate].
- 		 (self isForwarded: oop) ifTrue:
  			[oop := self followForwarded: oop.
  			 self longAt: array + fieldOffset put: oop].
+ 		 (self isImmediate: oop) ifTrue: [^PrimErrInappropriate].
  		 (self isPinned: oop) ifTrue: [^PrimErrObjectIsPinned].
  		 effectsFlags := effectsFlags bitOr: (self becomeEffectFlagsFor: oop).
  		 fieldOffset := fieldOffset - BytesPerOop].
  	"only set flags after checking all args."
  	becomeEffectsFlags := effectsFlags.
  	^0!

Item was changed:
  ----- Method: SpurMemoryManager>>containsOnlyValidBecomeObjects:and: (in category 'become implementation') -----
  containsOnlyValidBecomeObjects: array1 and: array2
  	"Answer 0 if neither array contains only unpinned non-immediates.
  	 Otherwise answer an informative error code.
  	 Can't become: immediates!!  Shouldn't become pinned objects."
  	| fieldOffset effectsFlags oop |
  	fieldOffset := self lastPointerOf: array1.
  	effectsFlags := 0.
  	"same size as array2"
  	[fieldOffset >= self baseHeaderSize] whileTrue:
  		[oop := self longAt: array1 + fieldOffset.
+ 		 (self isOopForwarded: oop) ifTrue:
- 		 (self isImmediate: oop) ifTrue: [^PrimErrInappropriate].
- 		 (self isForwarded: oop) ifTrue:
  			[oop := self followForwarded: oop.
  			 self longAt: array1 + fieldOffset put: oop].
+ 		 (self isImmediate: oop) ifTrue: [^PrimErrInappropriate].
  		 (self isPinned: oop) ifTrue: [^PrimErrObjectIsPinned].
  		 effectsFlags := effectsFlags bitOr: (self becomeEffectFlagsFor: oop).
  		 oop := self longAt: array2 + fieldOffset.
+ 		 (self isOopForwarded: oop) ifTrue:
- 		 (self isImmediate: oop) ifTrue: [^PrimErrInappropriate].
- 		 (self isForwarded: oop) ifTrue:
  			[oop := self followForwarded: oop.
  			 self longAt: array2 + fieldOffset put: oop].
+ 		 (self isImmediate: oop) ifTrue: [^PrimErrInappropriate].
  		 (self isPinned: oop) ifTrue: [^PrimErrObjectIsPinned].
  		 effectsFlags := effectsFlags bitOr: (self becomeEffectFlagsFor: oop).
  		 fieldOffset := fieldOffset - BytesPerOop].
  	"only set flags after checking all args."
  	becomeEffectsFlags := effectsFlags.
  	^0!



More information about the Vm-dev mailing list