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

commits at source.squeak.org commits at source.squeak.org
Sat Jul 18 21:14:54 UTC 2015


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

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

Name: VMMaker.oscog-eem.1427
Author: eem
Time: 18 July 2015, 2:12:47.196 pm
UUID: c5cb18c5-f69e-4e41-8f87-943a495659b4
Ancestors: VMMaker.oscog-eem.1426

Revert some of the cppIf: NewspeakVM changes; they are needed to hide nsSendCache variables from non-Newspeak VMs.

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

Item was changed:
  ----- Method: Cogit>>checkIfValidOopRef:pc:cogMethod: (in category 'garbage collection') -----
  checkIfValidOopRef: annotation pc: mcpc cogMethod: cogMethod
  	"Check for a valid object reference, if any, at a map entry.  Answer a code unique to each error for debugging."
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	annotation = IsObjectReference ifTrue:
  		[| literal |
  		 literal := literalsManager fetchLiteralAtAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
  		 (objectRepresentation checkValidOopReference: literal) ifFalse:
  			[coInterpreter print: 'object ref leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
  			^1]].
  
+ 	self cppIf: NewspeakVM ifTrue:
- 	NewspeakVM ifTrue:
  		[annotation = IsNSSendCall ifTrue:
  			[| nsSendCache enclosingObject |
  			nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			[(objectRepresentation checkValidOopReference: nsSendCache selector) ifFalse:
  				[coInterpreter print: 'selector leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
  				^1]].
  			(enclosingObject := nsSendCache enclosingObject) ~= 0 ifTrue:
  				[[(objectRepresentation checkValidOopReference: enclosingObject) ifFalse:
  					[coInterpreter print: 'enclosing object leak in CM '; printHex: cogMethod asInteger; print: ' @ '; printHex: mcpc asInteger; cr.
  					^1]]]]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[| entryPoint selectorOrCacheTag offset |
  		 entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint <= methodZoneBase
  			ifTrue:
  				[offset := entryPoint]
  			ifFalse:
  				[self
  					offsetAndSendTableFor: entryPoint
  					annotation: annotation
  					into: [:off :table| offset := off]].
  		 selectorOrCacheTag := backEnd inlineCacheTagAt: mcpc asInteger.
  		 (entryPoint > methodZoneBase
  		  and: [offset ~= cmNoCheckEntryOffset
  		  and: [(self cCoerceSimple: entryPoint - offset to: #'CogMethod *') cmType ~= CMOpenPIC]])
  			ifTrue: "linked non-super send, cacheTag is a cacheTag"
  				[(objectRepresentation validInlineCacheTag: 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 checkValidOopReference: 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>>checkIfValidOopRefAndTarget:pc:cogMethod: (in category 'garbage collection') -----
  checkIfValidOopRefAndTarget: annotation pc: mcpc cogMethod: cogMethod
  	"Check for a valid object reference, if any, at a map entry.  Answer a code unique to each error for debugging."
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| literal entryPoint |
  	annotation = IsObjectReference ifTrue:
  		[literal := literalsManager fetchLiteralAtAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
  		 (self asserta: (objectRepresentation checkValidOopReference: literal)) ifFalse:
  			[^1].
  		((objectRepresentation couldBeObject: literal)
  		 and: [objectMemory isReallyYoungObject: literal]) ifTrue:
  			[(self asserta: (self cCoerceSimple: cogMethod to: #'CogMethod *') cmRefersToYoung) ifFalse:
  				[^2]]].
  
+ 	self cppIf: NewspeakVM ifTrue:
- 	NewspeakVM ifTrue:
  		[annotation = IsNSSendCall ifTrue:
  			[| nsSendCache classTag enclosingObject nsTargetMethod |
  			nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			(self asserta: (objectRepresentation checkValidOopReference: nsSendCache selector)) ifFalse:
  				[^9].
  			classTag := nsSendCache classTag.
  			(self asserta: (classTag = 0 or: [objectRepresentation validInlineCacheTag: classTag])) ifFalse:
  				[^10].
  			enclosingObject := nsSendCache enclosingObject.
  			(self asserta: (enclosingObject = 0 or: [objectRepresentation checkValidOopReference: enclosingObject])) ifFalse:
  				[^11].
  			entryPoint := nsSendCache target.
  			entryPoint ~= 0 ifTrue: [
  				nsTargetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  				(self asserta: (nsTargetMethod cmType = CMMethod)) ifFalse:
  					[^12]]]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[(self asserta: (self cCoerceSimple: cogMethod to: #'CogMethod *') cmType = CMMethod) ifFalse:
  			[^3].
  		 self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:offset :cacheTag :tagCouldBeObject|
  			tagCouldBeObject
  				ifTrue:
  					[(objectRepresentation couldBeObject: cacheTag)
  						ifTrue:
  							[(self asserta: (objectRepresentation checkValidOopReference: cacheTag)) ifFalse:
  								[^4]]
  						ifFalse:
  							[(self asserta: (objectRepresentation validInlineCacheTag: cacheTag)) ifFalse:
  								[^5]].
  					((objectRepresentation couldBeObject: cacheTag)
  					 and: [objectMemory isReallyYoungObject: cacheTag]) ifTrue:
  						[(self asserta: (self cCoerceSimple: cogMethod to: #'CogMethod *') cmRefersToYoung) ifFalse:
  							[^6]]]
  				ifFalse:
  					[(self asserta: (objectRepresentation validInlineCacheTag: cacheTag)) ifFalse:
  						[^7]]].
  		entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		entryPoint > methodZoneBase ifTrue:
  			["It's a linked send; find which kind."
  			 self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  					[:targetMethod :sendTable|
  					 (self asserta: (targetMethod cmType = CMMethod
  								   or: [targetMethod cmType = CMClosedPIC
  								   or: [targetMethod cmType = CMOpenPIC]])) ifFalse:
  						[^8]]]].
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>incrementUsageOfTargetIfLinkedSend:mcpc:ignored: (in category 'compaction') -----
  incrementUsageOfTargetIfLinkedSend: annotation mcpc: mcpc ignored: superfluity
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| entryPoint |
  
+ 	self cppIf: NewspeakVM ifTrue:
- 	NewspeakVM ifTrue:
  		[annotation = IsNSSendCall ifTrue:
  			[| nsSendCache |
  			 nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			 nsSendCache classTag ~= objectRepresentation illegalClassTag ifTrue: "send is linked"
  				[ | targetMethod |
  				entryPoint := nsSendCache target.
  				targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  				self assert: (self isPCWithinMethodZone: targetMethod).
  				targetMethod cmUsageCount < (CMMaxUsageCount // 2) ifTrue:
  					[targetMethod cmUsageCount: targetMethod cmUsageCount + 1]]]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[self assert: annotation ~= IsNSSendCall.
  		 entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase ifTrue: "It's a linked send."
  			[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  				[:targetMethod :sendTable|
  				 targetMethod cmUsageCount < (CMMaxUsageCount // 2) ifTrue:
  					[targetMethod cmUsageCount: targetMethod cmUsageCount + 1]]]].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>markLiterals:pc:method: (in category 'garbage collection') -----
  markLiterals: annotation pc: mcpc method: cogMethod
  	"Mark and trace literals.
  	 Additionally in Newspeak, void push implicits that have unmarked classes."
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| literal |
  	annotation = IsObjectReference ifTrue:
  		[literal := literalsManager fetchLiteralAtAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
  		 (objectRepresentation
  				markAndTraceLiteral: literal
  				in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
  				atpc: mcpc asUnsignedInteger) ifTrue:
  			[codeModified := true]].
  
+ 	self cppIf: NewspeakVM ifTrue:
- 	NewspeakVM ifTrue:
  		[annotation = IsNSSendCall ifTrue:
  			[| nsSendCache sel eo |
  			nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			sel := nsSendCache selector.
  				(objectMemory isForwarded: sel)
  					ifFalse: [objectMemory markAndTrace: sel]
  					ifTrue: [sel := objectMemory followForwarded: literal.
  							nsSendCache selector: sel.
  							self markAndTraceUpdatedLiteral: sel in: (self cCoerceSimple: cogMethod to: #'CogMethod *')].
  			eo := nsSendCache enclosingObject.
  			eo ~= 0 ifTrue:
  				[(objectMemory isForwarded: eo)
  					ifFalse: [objectMemory markAndTrace: eo]
  					ifTrue: [eo := objectMemory followForwarded: literal.
  							nsSendCache enclosingObject: eo.
  							self markAndTraceUpdatedLiteral: eo in: (self cCoerceSimple: cogMethod to: #'CogMethod *')]]]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPoint :cacheTag :tagCouldBeObj |
  			 tagCouldBeObj ifTrue:
  				[(objectRepresentation
  						markAndTraceCacheTagLiteral: cacheTag
  						in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
  						atpc: mcpc asUnsignedInteger) ifTrue:
  					["cacheTag is selector" codeModified := true]]]].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>markLiteralsAndUnlinkIfUnmarkedSend:pc:method: (in category 'garbage collection') -----
  markLiteralsAndUnlinkIfUnmarkedSend: annotation pc: mcpc method: cogMethod
  	"Mark and trace literals.  Unlink sends that have unmarked cache tags or targets."
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| literal |
  	annotation = IsObjectReference ifTrue:
  		[literal := literalsManager fetchLiteralAtAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
  		 (objectRepresentation
  				markAndTraceLiteral: literal
  				in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
  				atpc: mcpc asUnsignedInteger) ifTrue:
  			[codeModified := true]].
  
+ 	self cppIf: NewspeakVM ifTrue:
- 	NewspeakVM ifTrue:
  		[annotation = IsNSSendCall ifTrue:
  			[| nsSendCache entryPoint targetMethod sel eo |
  			nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			entryPoint := nsSendCache target.
  			entryPoint ~= 0 ifTrue: "Send is linked"
  				[targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  				 (self markAndTraceOrFreeCogMethod: targetMethod
  					firstVisit: targetMethod asUnsignedInteger > mcpc asUnsignedInteger) ifTrue:	
  						[self voidNSSendCache: nsSendCache]].
  			sel := nsSendCache selector.
  			(objectMemory isForwarded: sel)
  				ifFalse: [objectMemory markAndTrace: sel]
  				ifTrue: [sel := objectMemory followForwarded: literal.
  						nsSendCache selector: sel.
  						self markAndTraceUpdatedLiteral: sel in: (self cCoerceSimple: cogMethod to: #'CogMethod *')].
  			eo := nsSendCache enclosingObject.
  			eo ~= 0 ifTrue:
  				[(objectMemory isForwarded: eo)
  					ifFalse: [objectMemory markAndTrace: eo]
  					ifTrue: [eo := objectMemory followForwarded: literal.
  							nsSendCache enclosingObject: eo.
  							self markAndTraceUpdatedLiteral: eo in: (self cCoerceSimple: cogMethod to: #'CogMethod *')]]]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPoint :cacheTag :tagCouldBeObj | | cacheTagMarked |
  			 cacheTagMarked := tagCouldBeObj and: [objectRepresentation cacheTagIsMarked: cacheTag].
  			 entryPoint > methodZoneBase
  				ifTrue: "It's a linked send."
  					[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  						[:targetMethod :sendTable| 
  						 (cacheTagMarked not
  						  or: [self markAndTraceOrFreeCogMethod: targetMethod
  								firstVisit: targetMethod asUnsignedInteger > mcpc asUnsignedInteger]) ifTrue:
  							["Either the cacheTag is unmarked (e.g. new class) or the target
  							  has been freed (because it is unmarked), so unlink the send."
  							 self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable.
  							 objectRepresentation
  								markAndTraceLiteral: targetMethod selector
  								in: targetMethod
  								at: (self addressOf: targetMethod selector put: [:val| targetMethod selector: val])]]]
  				ifFalse:  "cacheTag is selector"
  					[(objectRepresentation
  							markAndTraceCacheTagLiteral: cacheTag
  							in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
  							atpc: mcpc asUnsignedInteger) ifTrue:
  						[codeModified := true]]]].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>markYoungObjects:pc:method: (in category 'garbage collection') -----
  markYoungObjects: annotation pc: mcpc method: cogMethod
  	"Mark and trace young literals."
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| literal |
  	annotation = IsObjectReference ifTrue:
  		[literal := literalsManager fetchLiteralAtAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
  		 objectRepresentation markAndTraceLiteralIfYoung: literal].
  
+ 	self cppIf: NewspeakVM ifTrue: [annotation = IsNSSendCall ifTrue:
- 	NewspeakVM ifTrue: [annotation = IsNSSendCall ifTrue:
  		[| nsSendCache |
  		 nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  		 objectRepresentation markAndTraceLiteralIfYoung: nsSendCache selector.
  		 nsSendCache enclosingObject ~= 0 ifTrue:
  			[objectRepresentation markAndTraceLiteralIfYoung: nsSendCache enclosingObject]]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPoint :cacheTag :tagCouldBeObj |
  			 tagCouldBeObj ifTrue:
  				[objectRepresentation markAndTraceLiteralIfYoung: cacheTag]]].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>relocateIfCallOrMethodReference:mcpc:delta: (in category 'compaction') -----
  relocateIfCallOrMethodReference: annotation mcpc: mcpc delta: delta
  	<var: #mcpc type: #'char *'>
  	| entryPoint targetMethod unlinkedRoutine |
  	<var: #targetMethod type: #'CogMethod *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  
+ 	self cppIf: NewspeakVM ifTrue:
- 	NewspeakVM ifTrue:
  		[| nsSendCache |
  		 annotation = IsNSSendCall ifTrue:
  			["Retrieve the send cache before relocating the stub call. Fetching the send
  			  cache asserts the stub call points below all the cogged methods, but
  			  until this method is actually moved, the adjusted stub call may appear to
  			  point to somewhere in the method zone."
  			nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  
  			"Fix call to trampoline. This method is moving [delta] bytes, and calls are
  			 relative, so adjust the call by -[delta] bytes"
  			backEnd relocateCallBeforeReturnPC: mcpc asInteger by: delta negated.
  
  			nsSendCache target ~= 0 ifTrue: "Send is linked"
  				[entryPoint := nsSendCache target.
  				targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  				targetMethod cmType = CMMethod
  					ifTrue: "send target not freed; just relocate. The cache has an absolute
  							target, so only adjust by the target method's displacement."
  						[nsSendCache target: entryPoint + targetMethod objectHeader]
  					ifFalse: "send target was freed, unlink"
  						[self voidNSSendCache: nsSendCache]].
  			^0]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		entryPoint <= methodZoneBase ifTrue: "send is not linked; just relocate"
  			[backEnd relocateCallBeforeReturnPC: mcpc asInteger by: delta negated.
  			 ^0].
  		"It's a linked send; find which kind."
  		self
  			offsetAndSendTableFor: entryPoint
  			annotation: annotation
  			into: [:offset :sendTable|
  				 targetMethod := self cCoerceSimple: entryPoint - offset to: #'CogMethod *'.
  				 targetMethod cmType ~= CMFree ifTrue: "send target not freed; just relocate."
  					[backEnd
  						relocateCallBeforeReturnPC: mcpc asInteger
  						by: (delta - targetMethod objectHeader) negated.
  					 SistaVM ifTrue: "See comment in planCompaction"
  						[methodZone restorePICUsageCount: targetMethod].
  					 ^0].
  				 "Target was freed; map back to an unlinked send; but include this method's reocation"
  				 unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
  				 unlinkedRoutine := unlinkedRoutine - delta.
  				 backEnd
  					rewriteInlineCacheAt: mcpc asInteger
  					tag: targetMethod selector
  					target: unlinkedRoutine.
  				 ^0]].
  
  	annotation = IsRelativeCall ifTrue:
  		[backEnd relocateCallBeforeReturnPC: mcpc asInteger by: delta negated.
  		 ^0].
  
  	annotation = IsAbsPCReference ifTrue:
  		[backEnd relocateMethodReferenceBeforeAddress: mcpc asInteger by: delta].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>remapIfObjectRef:pc:hasYoung: (in category 'garbage collection') -----
  remapIfObjectRef: annotation pc: mcpc hasYoung: hasYoungPtr
  	<var: #mcpc type: #'char *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	annotation = IsObjectReference ifTrue:
  		[| literal mappedLiteral |
  		 literal := literalsManager fetchLiteralAtAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
  		 (objectRepresentation couldBeObject: literal) ifTrue:
  			[mappedLiteral := objectRepresentation remapObject: literal.
  			 literal ~= mappedLiteral ifTrue:
  				[literalsManager storeLiteral: mappedLiteral atAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
  				 codeModified := true].
  			 (hasYoungPtr ~= 0
  			  and: [objectMemory isYoung: mappedLiteral]) ifTrue:
  				[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]].
  
+ 	self cppIf: NewspeakVM ifTrue: [annotation = IsNSSendCall ifTrue:
- 	NewspeakVM ifTrue: [annotation = IsNSSendCall ifTrue:
  		[| nsSendCache oop mappedOop |
  		nsSendCache := self nsSendCacheFromReturnAddress: mcpc.
  		oop := nsSendCache selector.	
  		mappedOop := objectRepresentation remapObject: oop.
  		oop ~= mappedOop ifTrue:
  			[nsSendCache selector: mappedOop.
  			(hasYoungPtr ~= 0 and: [objectMemory isYoung: mappedOop]) ifTrue:
  				[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]].
  		oop := nsSendCache enclosingObject.	
  		oop ~= 0 ifTrue: [
  			mappedOop := objectRepresentation remapObject: oop.
  			oop ~= mappedOop ifTrue:
  				[nsSendCache enclosingObject: mappedOop.
  				(hasYoungPtr ~= 0 and: [objectMemory isYoung: mappedOop]) ifTrue:
  					[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]].
  		^0 "keep scanning"]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPoint :cacheTag :tagCouldBeObj | | mappedCacheTag |
  			 (tagCouldBeObj
  			  and: [objectRepresentation couldBeObject: cacheTag]) ifTrue:
  				[mappedCacheTag := objectRepresentation remapObject: cacheTag.
  				 cacheTag ~= mappedCacheTag ifTrue:
  					[backEnd rewriteInlineCacheTag: mappedCacheTag at: mcpc asUnsignedInteger.
  					 codeModified := true].
  				 (hasYoungPtr ~= 0
  				  and: [objectMemory isYoung: mappedCacheTag]) ifTrue:
  					[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]].
  			hasYoungPtr ~= 0 ifTrue:
  				["Since the unlinking routines may rewrite the cacheTag to the send's selector, and
  				  since they don't have the cogMethod to hand and can't add it to youngReferrers,
  				  the method must remain in youngReferrers if the targetMethod's selector is young."
  				 entryPoint > methodZoneBase ifTrue: "It's a linked send."
  					[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  						[:targetMethod :ignored|
  						 (objectMemory isYoung: targetMethod selector) ifTrue:
  							[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]]]]].
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>unlinkIfFreeOrLinkedSend:pc:of: (in category 'in-line cacheing') -----
  unlinkIfFreeOrLinkedSend: annotation pc: mcpc of: theSelector
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| entryPoint |
  
+ 	self cppIf: NewspeakVM ifTrue:
- 	NewspeakVM ifTrue:
  		[| nsSendCache |
  		 annotation = IsNSSendCall ifTrue:
  			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			 (entryPoint := nsSendCache target) ~= 0 ifTrue:
  				[ | targetMethod |
  				targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  				(targetMethod cmType = CMFree or: [nsSendCache selector = theSelector]) ifTrue:
  					[self voidNSSendCache: nsSendCache]].
  			^0 "keep scanning"]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase
  			ifTrue: "It's a linked send."
  				[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  					[:targetMethod :sendTable| 
  					 (targetMethod cmType = CMFree
  					  or: [targetMethod selector = theSelector]) ifTrue:
  						[self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>unlinkIfInvalidClassSend:pc:ignored: (in category 'in-line cacheing') -----
  unlinkIfInvalidClassSend: annotation pc: mcpc ignored: superfluity
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| entryPoint |
  
+ 	self cppIf: NewspeakVM ifTrue:
- 	NewspeakVM ifTrue:
  		[| nsSendCache |
  		 annotation = IsNSSendCall ifTrue:
  			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			 (nsSendCache classTag ~= objectRepresentation illegalClassTag
  			  and: [objectMemory isForwardedClassIndex: nsSendCache classTag]) ifTrue:
  				[self voidNSSendCache: nsSendCache]].
  			"Should we check if the enclosing object's class is forwarded as well?"
  			^0 "keep scanning"].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase ifTrue: "It's a linked send, but maybe a super send or linked to an OpenPIC, in which case the cache tag will be a selector...."
  			[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  				[:targetMethod :sendTable|
  				 ((self annotationIsForUncheckedEntryPoint: annotation)
  				  or: [targetMethod cmType = CMOpenPIC]) ifFalse:
  					[(objectMemory isValidClassTag: (backEnd inlineCacheTagAt: mcpc asInteger)) ifFalse:
  						[self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]]].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>unlinkIfLinkedSend:pc:ignored: (in category 'in-line cacheing') -----
  unlinkIfLinkedSend: annotation pc: mcpc ignored: superfluity
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| entryPoint |
  
+ 	self cppIf: NewspeakVM ifTrue:
- 	NewspeakVM ifTrue:
  		[| nsSendCache |
  		 annotation = IsNSSendCall ifTrue:
  			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			nsSendCache classTag ~= objectRepresentation illegalClassTag ifTrue: "Send is linked"
  				[self voidNSSendCache: nsSendCache].
  			^0 "keep scanning"]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase
  			ifTrue: "It's a linked send."
  				[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  					[:targetMethod :sendTable| 
  					 self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>unlinkIfLinkedSend:pc:of: (in category 'in-line cacheing') -----
  unlinkIfLinkedSend: annotation pc: mcpc of: theSelector
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| entryPoint |
  
+ 	self cppIf: NewspeakVM ifTrue:
- 	NewspeakVM ifTrue:
  		[| nsSendCache |
  		 annotation = IsNSSendCall ifTrue:
  			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			nsSendCache selector = theSelector ifTrue:
  				[self voidNSSendCache: nsSendCache].
  			^0 "keep scanning"]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase
  			ifTrue: "It's a linked send."
  				[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  					[:targetMethod :sendTable| 
  					 targetMethod selector = theSelector ifTrue:
  						[self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>unlinkIfLinkedSend:pc:to: (in category 'in-line cacheing') -----
  unlinkIfLinkedSend: annotation pc: mcpc to: theCogMethod
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| entryPoint |
  
+ 	self cppIf: NewspeakVM ifTrue:
- 	NewspeakVM ifTrue:
  		[| nsSendCache |
  		 annotation = IsNSSendCall ifTrue:
  			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			(entryPoint := nsSendCache target) ~= 0 ifTrue:
  				[ | targetMethod |
  				targetMethod := entryPoint - cmNoCheckEntryOffset.
  				targetMethod = theCogMethod ifTrue:
  					[self voidNSSendCache: nsSendCache]].
  			^0 "keep scanning"]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase
  			ifTrue: "It's a linked send."
  				[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  					[:targetMethod :sendTable| 
  					 targetMethod asInteger = theCogMethod ifTrue:
  						[self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]].
  
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>unlinkIfLinkedSendToFree:pc:ignored: (in category 'in-line cacheing') -----
  unlinkIfLinkedSendToFree: annotation pc: mcpc ignored: superfluity
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	<var: #nsTargetMethod type: #'CogMethod *'>
  	| entryPoint |
  
+ 	self cppIf: NewspeakVM ifTrue:
- 	NewspeakVM ifTrue:
  		[| nsSendCache nsTargetMethod |
  		 annotation = IsNSSendCall ifTrue:
  			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			(entryPoint := nsSendCache target) ~= 0 ifTrue: "It's a linked send."
  				[nsTargetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  				nsTargetMethod cmType = CMFree ifTrue:
  					[self voidNSSendCache: nsSendCache]].
  			^0 "keep scanning"]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint > methodZoneBase ifTrue: "It's a linked send."
  			[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  				[:targetMethod :sendTable| 
  				 targetMethod cmType = CMFree ifTrue:
  					[self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]].
  
  	^0 "keep scanning"!



More information about the Vm-dev mailing list