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

commits at source.squeak.org commits at source.squeak.org
Sun Apr 5 01:56:48 UTC 2015


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

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

Name: VMMaker.oscog-eem.1163
Author: eem
Time: 4 April 2015, 6:54:44.393 pm
UUID: da9d6c8a-90b3-4ffd-a306-b6ac5c777078
Ancestors: VMMaker.oscog-rmacnak.1162

Abstract out voiding nsSendCaches.

framePointer needs to be <api> for the new
ceSICMiss:.

=============== Diff against VMMaker.oscog-rmacnak.1162 ===============

Item was added:
+ ----- Method: CoInterpreter>>framePointer (in category 'accessing') -----
+ framePointer
+ 	<api>
+ 	^framePointer!

Item was removed:
- ----- Method: CogVMSimulator>>framePointer (in category 'debug support') -----
- framePointer
- 	^framePointer!

Item was changed:
  ----- Method: Cogit>>initializeNSSendCache:selector:numArgs:depth: (in category 'newspeak support') -----
  initializeNSSendCache: cacheAddress selector: selector numArgs: numArgs depth: depth
+ 	<inline: true>
  	| nsSendCache |
  	nsSendCache := self cCoerceSimple: cacheAddress to: #'NSSendCache *'.
  	nsSendCache selector: selector.
  	nsSendCache numArgs: numArgs.
  	nsSendCache depth: depth.
  	nsSendCache classTag: objectRepresentation illegalClassTag.
  !

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 := backEnd literalBeforeFollowingAddress: mcpc asUnsignedInteger.
  		 (objectRepresentation
  				markAndTraceLiteral: literal
  				in: (self cCoerceSimple: cogMethod to: #'CogMethod *')
  				atpc: mcpc asUnsignedInteger) ifTrue:
  			[codeModified := true]].
  
  	self cppIf: 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 := entryPoint - cmNoCheckEntryOffset.
  				 (self markAndTraceOrFreeCogMethod: targetMethod
  					firstVisit: targetMethod asUnsignedInteger > mcpc asUnsignedInteger) ifTrue:	
+ 						[self voidNSSendCache: nsSendCache]].
- 						[nsSendCache classTag: objectRepresentation illegalClassTag; enclosingObject: 0; target: 0]].
  			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 *')]]]].
  
  	annotation = IsNSSendCall ifTrue:
  		[self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPoint :cacheTag :tagCouldBeObj | | cacheTagMarked |
  			 self assert: annotation ~= IsNSSendCall.
  			 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: cogMethod
  							atpc: mcpc asUnsignedInteger) ifTrue:
  						[codeModified := true]]]].
  
  	^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:
  		[| 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]].
- 						[nsSendCache classTag: objectRepresentation illegalClassTag; enclosingObject: 0; target: 0]].
  			^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 = CMMethod ifTrue: "send target not freed; just relocate."
  					[backEnd
  						relocateCallBeforeReturnPC: mcpc asInteger
  						by: (delta - targetMethod objectHeader) negated.
  					 ^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>>unlinkIfForwardedSend:pc:ignored: (in category 'in-line cacheing') -----
  unlinkIfForwardedSend: annotation pc: mcpc ignored: superfluity
  	<var: #mcpc type: #'char *'>
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| entryPoint |
  
  	self cppIf: NewspeakVM ifTrue:
  		[| nsSendCache |
  		 annotation = IsNSSendCall ifTrue:
  			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			 (nsSendCache classTag ~= objectRepresentation illegalClassTag
  			  and: [objectMemory isForwardedClassIndex: nsSendCache classTag]) ifTrue:
+ 				[self voidNSSendCache: nsSendCache]].
- 				[nsSendCache classTag: objectRepresentation illegalClassTag; enclosingObject: 0; target: 0]].
  			"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...."
  				[(objectMemory isForwardedClassIndex: (backEnd inlineCacheTagAt: mcpc asInteger)) ifTrue:
  					[self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  						[:targetMethod :sendTable|
  						 self unlinkSendAt: mcpc targetMethod: targetMethod sendTable: sendTable]]]].
  
  	^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:
  		[| 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]].
- 					[nsSendCache classTag: objectRepresentation illegalClassTag; enclosingObject: 0; target: 0]].
  			^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>>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:
  		[| nsSendCache |
  		 annotation = IsNSSendCall ifTrue:
  			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			nsSendCache classTag ~= objectRepresentation illegalClassTag ifTrue: "Send is linked"
+ 				[self voidNSSendCache: nsSendCache].
- 				[nsSendCache classTag: objectRepresentation illegalClassTag; enclosingObject: 0; target: 0].
  			^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:
  		[| nsSendCache |
  		 annotation = IsNSSendCall ifTrue:
  			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			nsSendCache selector = theSelector ifTrue:
+ 				[self voidNSSendCache: nsSendCache].
- 				[nsSendCache classTag: objectRepresentation illegalClassTag; enclosingObject: 0; target: 0].
  			^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:
  		[| nsSendCache |
  		 annotation = IsNSSendCall ifTrue:
  			[nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			(entryPoint := nsSendCache target) ~= 0 ifTrue:
  				[ | targetMethod |
  				targetMethod := entryPoint - cmNoCheckEntryOffset.
  				targetMethod = theCogMethod ifTrue:
+ 					[self voidNSSendCache: nsSendCache]].
- 					[nsSendCache classTag: objectRepresentation illegalClassTag; enclosingObject: 0; target: 0]].
  			^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:
  		[| 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]].
- 					[nsSendCache classTag: objectRepresentation illegalClassTag; enclosingObject: 0; target: 0]].
  			^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"!

Item was added:
+ ----- Method: Cogit>>voidNSSendCache: (in category 'in-line cacheing') -----
+ voidNSSendCache: nsSendCache
+ 	<inline: true>
+ 	nsSendCache classTag: objectRepresentation illegalClassTag; enclosingObject: 0; target: 0!



More information about the Vm-dev mailing list