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

commits at source.squeak.org commits at source.squeak.org
Tue Nov 26 02:26:10 UTC 2013


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

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

Name: VMMaker.oscog-eem.522
Author: eem
Time: 25 November 2013, 6:23:21.686 pm
UUID: 4fd1d094-9a41-41df-b776-1989665951d5
Ancestors: VMMaker.oscog-eem.521

Fix evolutiuon of send site linked to closed PIC into site linked to
open PIC to enforce invariant that cache tags of sites linked to
open PICs are selectors; this for checkIfValidObjectRef:pc:cogMethod:'s
cache tag checks.

Fix caxche tag checks in checkValidObjectReferencesInClosedPIC:
for Spur via CogObjectRepresentation>>inlineCacheTagsMayBeObjects.

Fix compilation of Spur's cogit.c by marking wordSize <api> now
that wordSize is not handled specially by CCodeGenerator.

Add some subclassResponsibilities to CogObjectRepresentation.

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

Item was added:
+ ----- Method: CogObjectRepresentation>>canLinkToYoungClasses (in category 'in-line cacheing') -----
+ canLinkToYoungClasses
+ 	^self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentation>>inlineCacheTagForInstance: (in category 'in-line cacheing') -----
+ inlineCacheTagForInstance: oop
+ 	"c.f. getInlineCacheClassTagFrom:into:"
+ 	^self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentation>>inlineCacheTagIsYoung: (in category 'in-line cacheing') -----
+ inlineCacheTagIsYoung: cacheTag
+ 	^self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentation>>inlineCacheTagsMayBeObjects (in category 'in-line cacheing') -----
+ inlineCacheTagsMayBeObjects
+ 	^self subclassResponsibility!

Item was added:
+ ----- Method: CogObjectRepresentationForSpur>>inlineCacheTagsMayBeObjects (in category 'in-line cacheing') -----
+ inlineCacheTagsMayBeObjects
+ 	^false!

Item was added:
+ ----- Method: CogObjectRepresentationForSqueakV3>>inlineCacheTagsMayBeObjects (in category 'in-line cacheing') -----
+ inlineCacheTagsMayBeObjects
+ 	^true!

Item was changed:
  ----- Method: Cogit>>ceSICMiss: (in category 'in-line cacheing') -----
  ceSICMiss: receiver
  	"An in-line cache check in a method has failed.  The failing entry check has jumped
  	 to the ceMethodAbort abort call at the start of the method which has called this routine.
  	 If possible allocate a closed PIC for the current and existing classes.
  	 The stack looks like:
  			receiver
  			args
  			sender return address
  	  sp=>	ceMethodAbort call return address
  	 So we can find the method that did the failing entry check at
  		ceMethodAbort call return address - missOffset
  	 and we can find the send site from the outer return address."
  	<api>
  	| pic innerReturn outerReturn entryPoint targetMethod newTargetMethodOrNil errorSelectorOrNil cacheTag extent result |
  	<var: #pic type: #'CogMethod *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	"Whether we can relink to a PIC or not we need to pop off the inner return and identify the target method."
  	innerReturn := coInterpreter popStack.
  	targetMethod := self cCoerceSimple: innerReturn - missOffset to: #'CogMethod *'.
  	outerReturn := coInterpreter stackTop.
  	self assert: (outerReturn between: methodZoneBase and: methodZone freeStart).
  	entryPoint := backEnd callTargetFromReturnAddress: outerReturn.
  
  	self assert: targetMethod selector ~= objectMemory nilObject.
  	self cppIf: NewspeakVM ifTrue:
  		[self assert: (targetMethod asInteger + cmEntryOffset = entryPoint
  					or: [targetMethod asInteger + cmDynSuperEntryOffset = entryPoint]).
  		 "Avoid the effort of implementing PICs for the relatively low dynamic frequency
  		  dynamic super send and simply rebind the send site."
  		 targetMethod asInteger + cmDynSuperEntryOffset = entryPoint ifTrue:
  			[^coInterpreter
  				ceDynamicSuperSend: targetMethod selector
  				to: receiver
  				numArgs: targetMethod cmNumArgs]].
  	self assert: targetMethod asInteger + cmEntryOffset = entryPoint.
  
  	self lookup: targetMethod selector
  		for: receiver
  		methodAndErrorSelectorInto:
  			[:method :errsel|
  			newTargetMethodOrNil := method.
  			errorSelectorOrNil := errsel].
  	"We assume lookupAndCog:for: will *not* reclaim the method zone"
  	self assert: outerReturn = coInterpreter stackTop.
  	cacheTag := objectRepresentation inlineCacheTagForInstance: receiver.
  	((errorSelectorOrNil notNil and: [errorSelectorOrNil ~= SelectorDoesNotUnderstand])
  	 or: [(objectRepresentation inlineCacheTagIsYoung: cacheTag)
  	 or: [newTargetMethodOrNil isNil
  	 or: [objectMemory isYoung: newTargetMethodOrNil]]]) ifTrue:
  		[result := self patchToOpenPICFor: targetMethod selector
  					numArgs: targetMethod cmNumArgs
  					receiver: receiver.
  		 self assert: result not. "If patchToOpenPICFor:.. returns we're out of code memory"
  		 ^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
  	"See if an Open PIC is already available."
  	pic := methodZone openPICWithSelector: targetMethod selector.
  	pic isNil ifTrue:
  		["otherwise attempt to create a closed PIC for the two cases."
  		 pic := self cogPICSelector: targetMethod selector
  					numArgs: targetMethod cmNumArgs
  					Case0Method: targetMethod
  					Case1Method: newTargetMethodOrNil
  					tag: cacheTag
  					isMNUCase: errorSelectorOrNil = SelectorDoesNotUnderstand.
  		 (pic asInteger between: MaxNegativeErrorCode and: -1) ifTrue:
  			["For some reason the PIC couldn't be generated, most likely a lack of code memory.
  			  Continue as if this is an unlinked send."
  			 pic asInteger = InsufficientCodeSpace ifTrue:
  				[coInterpreter callForCogCompiledCodeCompaction].
  			^coInterpreter ceSendFromInLineCacheMiss: targetMethod].
  		 processor flushICacheFrom: pic asInteger to: pic asInteger + closedPICSize].
+ 	"Relink the send site to the pic.  If to an open PIC then reset the cache tag to the selector,
+ 	 for the benefit of the cacheTag assert check in checkIfValidObjectRef:pc:cogMethod:."
+ 	extent := pic cmType = CMOpenPIC
+ 				ifTrue:
+ 					[backEnd
+ 						rewriteInlineCacheAt: outerReturn
+ 						tag: targetMethod selector
+ 						target: pic asInteger + cmEntryOffset]
+ 				ifFalse:
+ 					[backEnd
+ 						rewriteCallAt: outerReturn
+ 						target: pic asInteger + cmEntryOffset].
- 	"Relink the send site to the pic."
- 	extent := backEnd
- 				rewriteCallAt: outerReturn
- 				target: pic asInteger + cmEntryOffset.
  	processor flushICacheFrom: outerReturn - 1 - extent to: outerReturn - 1.
  	"Jump back into the pic at its entry in case this is an MNU (newTargetMethodOrNil is nil)"
  	coInterpreter
  		executeCogMethodFromLinkedSend: pic
  		withReceiver: receiver
  		andCacheTag: (backEnd inlineCacheTagAt: outerReturn).
  	"NOTREACHED"
  	^nil!

Item was changed:
  ----- Method: Cogit>>checkIfValidObjectRef:pc:cogMethod: (in category 'garbage collection') -----
  checkIfValidObjectRef: annotation pc: mcpc cogMethod: cogMethod
  	<var: #mcpc type: #'char *'>
  	<var: #sendTable type: #'sqInt *'>
  	annotation = IsObjectReference ifTrue:
  		[| literal |
  		 literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
  		 (objectRepresentation checkValidObjectReference: literal) ifFalse:
  			[coInterpreter print: 'object ref leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
  			^1]].
  	(self isSendAnnotation: annotation) ifTrue:
  		[| entryPoint selectorOrCacheTag offset sendTable |
  		 entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 self
  			offsetAndSendTableFor: entryPoint
  			annotation: annotation
  			into: [:off :table| offset := off. sendTable := table].
  		 selectorOrCacheTag := backEnd inlineCacheTagAt: mcpc asInteger.
  		 (entryPoint > methodZoneBase
  		  and: [offset ~= cmNoCheckEntryOffset
+ 		  and: [(self cCoerceSimple: entryPoint - offset to: #'CogMethod *') cmType ~= CMOpenPIC]])
- 		  and: [(self cCoerceSimple: entryPoint + offset to: #'CogMethod *') cmType ~= CMOpenPIC
- 				or: [(objectRepresentation couldBeObject: selectorOrCacheTag) not]]])
  			ifTrue: "linked non-super send, cacheTag is a cacheTag"
  				[(objectRepresentation checkValidInlineCacheTag: selectorOrCacheTag) ifFalse:
  					[coInterpreter print: 'cache tag leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
  					^1]]
  			ifFalse: "unlinked send or super send; cacheTag is a selector"
  				[(objectRepresentation checkValidObjectReference: selectorOrCacheTag) ifFalse:
  					[coInterpreter print: 'selector leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
  					^1]]].
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>checkValidObjectReferencesInClosedPIC: (in category 'garbage collection') -----
  checkValidObjectReferencesInClosedPIC: cPIC
  	<var: #cPIC type: #'CogMethod *'>
  	| ok pc |
  	ok := true.
  	pc := cPIC asInteger + firstCPICCaseOffset.
  	(self checkMaybeObjRefAt: pc - backEnd jumpLongByteSize) ifFalse:
  		[self print: 'object leak in CPIC '; printHex: cPIC asInteger;
  			print: ' @ '; printHex: pc - backEnd jumpLongByteSize; cr.
  		 ok := false].
  	pc := pc + cPICCaseSize.
  	2 to: cPIC cPICNumCases do:
  		[:i|
+ 		objectRepresentation inlineCacheTagsMayBeObjects ifTrue:
+ 			[(self checkMaybeObjRefAt: pc - backEnd jumpLongConditionalByteSize - backEnd loadLiteralByteSize) ifFalse:
+ 				[self print: 'object leak in CPIC '; printHex: cPIC asInteger;
+ 					print: ' @ '; printHex: pc - backEnd jumpLongConditionalByteSize - backEnd loadLiteralByteSize; cr.
+ 				 ok := false]].
- 		(self checkMaybeObjRefAt: pc - backEnd jumpLongConditionalByteSize - backEnd loadLiteralByteSize) ifFalse:
- 			[self print: 'object leak in CPIC '; printHex: cPIC asInteger;
- 				print: ' @ '; printHex: pc - backEnd jumpLongConditionalByteSize - backEnd loadLiteralByteSize; cr.
- 			 ok := false].
  		(self checkMaybeObjRefAt: pc - backEnd jumpLongConditionalByteSize) ifFalse:
  			[self print: 'object leak in CPIC '; printHex: cPIC asInteger;
  				print: ' @ '; printHex: pc - backEnd jumpLongConditionalByteSize; cr.
  			 ok := false].
  		pc := pc + cPICCaseSize].
  	^ok!

Item was changed:
  ----- Method: Spur32BitMemoryManager>>wordSize (in category 'word size') -----
  wordSize
+ 	<api>
+ 	<cmacro: '() 4'>
  	^4!

Item was changed:
  ----- Method: Spur64BitMemoryManager>>wordSize (in category 'word size') -----
  wordSize
+ 	<cmacro: '() 8'>
  	^8!



More information about the Vm-dev mailing list