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

commits at source.squeak.org commits at source.squeak.org
Tue Mar 19 16:31:56 UTC 2013


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

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

Name: VMMaker.oscog-eem.275
Author: eem
Time: 19 March 2013, 9:27:45.262 am
UUID: 69d4c949-ec25-4846-a014-417705bb4611
Ancestors: VMMaker.oscog-eem.274

Remember to flush PushImplicit/SendAbsentImplicit caches on
global cache flush and flush cache by method.  Fix comment for
flush-cache-by-method workhorse.  Streamline the code.

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

Item was changed:
  ----- Method: Cogit>>unlinkIfLinkedSend:pc:ignored: (in category 'in-line cacheing') -----
  unlinkIfLinkedSend: annotation pc: mcpc ignored: superfluity
  	<var: #mcpc type: #'char *'>
  	| entryPoint targetMethod offset sendTable unlinkedRoutine |
  	<var: #targetMethod type: #'CogMethod *'>
  	<var: #sendTable type: #'sqInt *'>
  	(self isSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
+ 		 entryPoint > methodZoneBase
+ 			ifTrue: "It's a linked send."
+ 				[self
+ 					offsetAndSendTableFor: entryPoint
+ 					annotation: annotation
+ 					into: [:off :table| offset := off. sendTable := table].
+ 				targetMethod := self cCoerceSimple: entryPoint - offset to: #'CogMethod *'.
+ 				unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
+ 				backEnd
+ 					rewriteInlineCacheAt: mcpc asInteger
+ 					tag: targetMethod selector
+ 					target: unlinkedRoutine]
+ 			ifFalse:
+ 				[self cppIf: NewspeakVM ifTrue:
+ 					[entryPoint = ceImplicitReceiverTrampoline ifTrue:
+ 						[backEnd
+ 							unalignedLongAt: mcpc asInteger + backEnd jumpShortByteSize put: 0;
+ 							unalignedLongAt: mcpc asInteger + backEnd jumpShortByteSize + BytesPerOop put: 0]]]].
- 		 entryPoint > methodZoneBase ifTrue: "It's a linked send."
- 			[self
- 				offsetAndSendTableFor: entryPoint
- 				annotation: annotation
- 				into: [:off :table| offset := off. sendTable := table].
- 			targetMethod := self cCoerceSimple: entryPoint - offset to: #'CogMethod *'.
- 			unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
- 			backEnd
- 				rewriteInlineCacheAt: mcpc asInteger
- 				tag: targetMethod selector
- 				target: unlinkedRoutine]].
  	^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 *'>
  	| entryPoint targetMethod offset sendTable unlinkedRoutine |
  	<var: #targetMethod type: #'CogMethod *'>
  	<var: #sendTable type: #'sqInt *'>
  	(self isSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
+ 		 entryPoint > methodZoneBase
+ 			ifTrue: "It's a linked send."
+ 				[self
+ 					offsetAndSendTableFor: entryPoint
+ 					annotation: annotation
+ 					into: [:off :table| offset := off. sendTable := table].
+ 				targetMethod := self cCoerceSimple: entryPoint - offset to: #'CogMethod *'.
+ 				targetMethod selector = theSelector ifTrue:
+ 					[unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
+ 					 backEnd
+ 						rewriteInlineCacheAt: mcpc asInteger
+ 						tag: targetMethod selector
+ 						target: unlinkedRoutine.
+ 					 codeModified := true]]
+ 			ifFalse:
+ 				[self cppIf: NewspeakVM ifTrue:
+ 					[entryPoint = ceImplicitReceiverTrampoline ifTrue:
+ 						[(backEnd inlineCacheTagAt: mcpc asInteger) = theSelector ifTrue:
+ 						 	[backEnd
+ 								unalignedLongAt: mcpc asInteger + backEnd jumpShortByteSize put: 0;
+ 								unalignedLongAt: mcpc asInteger + backEnd jumpShortByteSize + BytesPerOop put: 0]]]]].
- 		 self cppIf: NewspeakVM ifTrue:
- 			[entryPoint = ceImplicitReceiverTrampoline ifTrue:
- 				[(backEnd inlineCacheTagAt: mcpc asInteger) = theSelector ifTrue:
- 				 	[backEnd
- 						unalignedLongAt: mcpc asInteger + backEnd jumpShortByteSize put: 0;
- 						unalignedLongAt: mcpc asInteger + backEnd jumpShortByteSize + BytesPerOop put: 0]]].
- 		 entryPoint > methodZoneBase ifTrue: "It's a linked send."
- 			[self
- 				offsetAndSendTableFor: entryPoint
- 				annotation: annotation
- 				into: [:off :table| offset := off. sendTable := table].
- 			targetMethod := self cCoerceSimple: entryPoint - offset to: #'CogMethod *'.
- 			targetMethod selector = theSelector ifTrue:
- 				[unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
- 				 backEnd
- 					rewriteInlineCacheAt: mcpc asInteger
- 					tag: targetMethod selector
- 					target: unlinkedRoutine.
- 				 codeModified := true]]].
  	^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 *'>
  	| entryPoint targetMethod offset sendTable unlinkedRoutine |
  	<var: #targetMethod type: #'CogMethod *'>
  	<var: #sendTable type: #'sqInt *'>
  	(self isSendAnnotation: annotation) ifTrue:
  		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
+ 		 entryPoint > methodZoneBase
+ 			ifTrue: "It's a linked send."
+ 				[self
+ 					offsetAndSendTableFor: entryPoint
+ 					annotation: annotation
+ 					into: [:off :table| offset := off. sendTable := table].
+ 				targetMethod := self cCoerceSimple: entryPoint - offset to: #'CogMethod *'.
+ 				targetMethod asInteger = theCogMethod ifTrue:
+ 					[unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
+ 					 backEnd
+ 						rewriteInlineCacheAt: mcpc asInteger
+ 						tag: targetMethod selector
+ 						target: unlinkedRoutine.
+ 					 codeModified := true]]
+ 			ifFalse: "Can't tell the target with PushReciver/SendImplicit so flush anyway."
+ 				[self cppIf: NewspeakVM ifTrue:
+ 					[entryPoint = ceImplicitReceiverTrampoline ifTrue:
+ 						[backEnd
+ 							unalignedLongAt: mcpc asInteger + backEnd jumpShortByteSize put: 0;
+ 							unalignedLongAt: mcpc asInteger + backEnd jumpShortByteSize + BytesPerOop put: 0]]]].
- 		 entryPoint > methodZoneBase ifTrue: "It's a linked send."
- 			[self
- 				offsetAndSendTableFor: entryPoint
- 				annotation: annotation
- 				into: [:off :table| offset := off. sendTable := table].
- 			targetMethod := self cCoerceSimple: entryPoint - offset to: #'CogMethod *'.
- 			targetMethod asInteger = theCogMethod ifTrue:
- 				[unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
- 				 backEnd
- 					rewriteInlineCacheAt: mcpc asInteger
- 					tag: targetMethod selector
- 					target: unlinkedRoutine.
- 				 codeModified := true]]].
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>unlinkSendsTo:andFreeIf: (in category 'jit - api') -----
  unlinkSendsTo: targetMethodObject andFreeIf: freeIfTrue
  	<api>
  	"Unlink all sends in cog methods to a particular target method.
  	 If targetMethodObject isn't actually a method (perhaps being
+ 	 used via invokeAsMethod) then there's nothing to do."
- 	 used via invokeAsMethod) then flush all sends since anything
- 	 could be affected."
  	| cogMethod targetMethod freedPIC |
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	((objectMemory isOopCompiledMethod: targetMethodObject)
  	and: [coInterpreter methodHasCogMethod: targetMethodObject]) ifFalse:
  		[^self].
  	targetMethod := coInterpreter cogMethodOf: targetMethodObject.
  	methodZoneBase isNil ifTrue: [^self].
  	codeModified := freedPIC := false.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[cogMethod cmType = CMMethod
  			ifTrue:
  				[self mapFor: cogMethod
  					 performUntil: #unlinkIfLinkedSend:pc:to:
  					 arg: targetMethod asInteger]
  			ifFalse:
  				[(cogMethod cmType = CMClosedPIC
  				  and: [self cPIC: cogMethod HasTarget: targetMethod]) ifTrue:
  					[methodZone freeMethod: cogMethod.
  					 freedPIC := true]].
  		cogMethod := methodZone methodAfter: cogMethod].
  	freeIfTrue ifTrue: [self freeMethod: targetMethod].
  	freedPIC
  		ifTrue: [self unlinkSendsToFree]
  		ifFalse:
  			[codeModified ifTrue: "After possibly updating inline caches we need to flush the icache."
  				[processor flushICacheFrom: methodZoneBase to: methodZone limitZony asInteger]]!



More information about the Vm-dev mailing list