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

commits at source.squeak.org commits at source.squeak.org
Thu Mar 13 22:32:22 UTC 2014


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

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

Name: VMMaker.oscog-eem.640
Author: eem
Time: 13 March 2014, 3:29:13.957 pm
UUID: b52d099d-350b-40ce-8ef3-0bbf96ca7539
Ancestors: VMMaker.oscog-eem.639

Now that Slang inline block support is better rewrite the
machine-code scanning routines to use two new control structures,
offsetCacheTagAndCouldBeObjectAt:annotation:into: &
targetMethodAndSendTableFor:annotation:into:.

Hence eliminate all the duplication between Newspeak and Squeak
in teh scanning routines, such as markNSYoungObjects:pc:method:.

Inline methodAfter: & roundUpLength: (the latter via a macro, sigh).

Make CogVMSimulator>>ceStackOverflow: bump the byteCount by
1k so the microsecond clock advances faster when in machine code.

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

Item was changed:
  ----- Method: CCodeGenerator>>initializeCTranslationDictionary (in category 'C translation') -----
  initializeCTranslationDictionary 
  	"Initialize the dictionary mapping message names to actions for C code generation."
  
  	| pairs |
  	
  	translationDict := Dictionary new: 200.
  	pairs := #(
  	#&				#generateAnd:on:indent:
  	#|				#generateOr:on:indent:
  	#and:			#generateSequentialAnd:on:indent:
  	#or:			#generateSequentialOr:on:indent:
  	#not			#generateNot:on:indent:
  
  	#+				#generatePlus:on:indent:
  	#-				#generateMinus:on:indent:
  	#negated		#generateNegated:on:indent:
  	#*				#generateTimes:on:indent:
  	#/				#generateDivide:on:indent:
  	#//				#generateDivide:on:indent:
  	#\\				#generateModulo:on:indent:
  	#<<			#generateShiftLeft:on:indent:
  	#>>			#generateShiftRight:on:indent:
  	#min:			#generateMin:on:indent:
  	#max:			#generateMax:on:indent:
  	#between:and:	#generateBetweenAnd:on:indent:
  
  	#bitAnd:			#generateBitAnd:on:indent:
  	#bitOr:				#generateBitOr:on:indent:
  	#bitXor:			#generateBitXor:on:indent:
  	#bitShift:			#generateBitShift:on:indent:
  	#signedBitShift:	#generateSignedBitShift:on:indent:
  	#bitInvert32		#generateBitInvert32:on:indent:
  	#bitClear:			#generateBitClear:on:indent:
  	#truncateTo:		#generateTruncateTo:on:indent:
  	#rounded			#generateRounded:on:indent:
  
  	#<				#generateLessThan:on:indent:
  	#<=			#generateLessThanOrEqual:on:indent:
  	#=				#generateEqual:on:indent:
  	#>				#generateGreaterThan:on:indent:
  	#>=			#generateGreaterThanOrEqual:on:indent:
  	#~=			#generateNotEqual:on:indent:
  	#==			#generateEqual:on:indent:
  	#~~			#generateNotEqual:on:indent:
  	#isNil			#generateIsNil:on:indent:
  	#notNil			#generateNotNil:on:indent:
  
  	#whileTrue: 	#generateWhileTrue:on:indent:
  	#whileFalse:	#generateWhileFalse:on:indent:
  	#whileTrue 	#generateDoWhileTrue:on:indent:
  	#whileFalse		#generateDoWhileFalse:on:indent:
  	#to:do:			#generateToDo:on:indent:
  	#to:by:do:		#generateToByDo:on:indent:
  	#repeat 		#generateRepeat:on:indent:
  
  	#ifTrue:			#generateIfTrue:on:indent:
  	#ifFalse:		#generateIfFalse:on:indent:
  	#ifTrue:ifFalse:	#generateIfTrueIfFalse:on:indent:
  	#ifFalse:ifTrue:	#generateIfFalseIfTrue:on:indent:
  
  	#ifNotNil:		#generateIfNotNil:on:indent:
  	#ifNil:			#generateIfNil:on:indent:
  	#ifNotNil:ifNil:	#generateIfNotNilIfNil:on:indent:
  	#ifNil:ifNotNil:	#generateIfNilIfNotNil:on:indent:
  
  	#at:				#generateAt:on:indent:
  	#at:put:			#generateAtPut:on:indent:
  	#basicAt:		#generateAt:on:indent:
  	#basicAt:put:	#generateAtPut:on:indent:
  
  	#integerValueOf:			#generateIntegerValueOf:on:indent:
  	#integerObjectOf:			#generateIntegerObjectOf:on:indent:
  	#isIntegerObject: 			#generateIsIntegerObject:on:indent:
  	#cCode:					#generateInlineCCode:on:indent:
  	#cCode:inSmalltalk:			#generateInlineCCode:on:indent:
  	#cPreprocessorDirective:	#generateInlineCPreprocessorDirective:on:indent:
  	#cppIf:ifTrue:ifFalse:		#generateInlineCppIfElse:on:indent:
  	#cppIf:ifTrue:				#generateInlineCppIfElse:on:indent:
  	#cCoerce:to:				#generateCCoercion:on:indent:
  	#cCoerceSimple:to:			#generateCCoercion:on:indent:
  	#addressOf:				#generateAddressOf:on:indent:
  	#addressOf:put:			#generateAddressOf:on:indent:
  	#signedIntFromLong		#generateSignedIntFromLong:on:indent:
  	#signedIntToLong			#generateSignedIntToLong:on:indent:
  	#signedIntFromShort		#generateSignedIntFromShort:on:indent:
  	#signedIntToShort			#generateSignedIntToShort:on:indent:
  	#preIncrement				#generatePreIncrement:on:indent:
  	#preDecrement			#generatePreDecrement:on:indent:
  	#inline:						#generateInlineDirective:on:indent:
  	#asFloat					#generateAsFloat:on:indent:
  	#asInteger					#generateAsInteger:on:indent:
  	#asUnsignedInteger		#generateAsUnsignedInteger:on:indent:
  	#asLong					#generateAsLong:on:indent:
  	#asUnsignedLong			#generateAsUnsignedLong:on:indent:
  	#asVoidPointer				#generateAsVoidPointer:on:indent:
  	#asSymbol					#generateAsSymbol:on:indent:
  	#flag:						#generateFlag:on:indent:
  	#anyMask:					#generateBitAnd:on:indent:
  	#noMask:					#generateNoMask:on:indent:
  	#raisedTo:					#generateRaisedTo:on:indent:
  	#touch:						#generateTouch:on:indent:
  
  	#bytesPerWord 			#generateBytesPerWord:on:indent:
  	#baseHeaderSize			#generateBaseHeaderSize:on:indent:
  	
  	#sharedCodeNamed:inCase:		#generateSharedCodeDirective:on:indent:
  
  	#perform:							#generatePerform:on:indent:
  	#perform:with:						#generatePerform:on:indent:
  	#perform:with:with:					#generatePerform:on:indent:
  	#perform:with:with:with:				#generatePerform:on:indent:
  	#perform:with:with:with:with:		#generatePerform:on:indent:
  	#perform:with:with:with:with:with:	#generatePerform:on:indent:
  
  	#value								#generateValue:on:indent:
  	#value:								#generateValue:on:indent:
  	#value:value:						#generateValue:on:indent:
+ 	#value:value:value:					#generateValue:on:indent:
  
  	#shouldNotImplement				#generateSmalltalkMetaError:on:indent:
  	#shouldBeImplemented			#generateSmalltalkMetaError:on:indent:
  	#subclassResponsibility			#generateSmalltalkMetaError:on:indent:
  	).
  
  	1 to: pairs size by: 2 do: [:i |
  		translationDict at: (pairs at: i) put: (pairs at: i + 1)].
  
  	pairs := #(
  	#ifTrue:					#generateIfTrueAsArgument:on:indent:	
  	#ifFalse:				#generateIfFalseAsArgument:on:indent:
  	#ifTrue:ifFalse:			#generateIfTrueIfFalseAsArgument:on:indent:
  	#ifFalse:ifTrue:			#generateIfFalseIfTrueAsArgument:on:indent:
  	#ifNotNil:				#generateIfNotNilAsArgument:on:indent:	
  	#ifNil:					#generateIfNilAsArgument:on:indent:
  	#ifNotNil:ifNil:			#generateIfNotNilIfNilAsArgument:on:indent:
  	#ifNil:ifNotNil:			#generateIfNilIfNotNilAsArgument:on:indent:
  	#cCode:				#generateInlineCCodeAsArgument:on:indent:
  	#cCode:inSmalltalk:		#generateInlineCCodeAsArgument:on:indent:
  	#cppIf:ifTrue:ifFalse:	#generateInlineCppIfElseAsArgument:on:indent:
  	#cppIf:ifTrue:			#generateInlineCppIfElseAsArgument:on:indent:
  
  	#value					#generateValueAsArgument:on:indent:
  	#value:					#generateValueAsArgument:on:indent:
  	#value:value:			#generateValueAsArgument:on:indent:
  	).
  
  	asArgumentTranslationDict := Dictionary new: 8.
  	1 to: pairs size by: 2 do: [:i |
  		asArgumentTranslationDict at: (pairs at: i) put: (pairs at: i + 1)].
  !

Item was changed:
  ----- Method: CogMethodZone>>methodAfter: (in category 'accessing') -----
  methodAfter: cogMethod
  	<var: #cogMethod type: #'CogMethod *'>
+ 	<inline: true>
  	^coInterpreter
  		cCoerceSimple: (self roundUpLength: cogMethod asInteger + cogMethod blockSize)
  		to: #'CogMethod *'!

Item was changed:
  ----- Method: CogMethodZone>>roundUpLength: (in category 'accessing') -----
  roundUpLength: numBytes
+ 	<cmacro: '(numBytes) ((numBytes) + 7 & -8)'>
  	^numBytes + 7 bitAnd: -8!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>markAndTraceLiteralIfYoung: (in category 'garbage collection') -----
  markAndTraceLiteralIfYoung: literal
- 	self shouldNotImplement.  "sumpin' wrong surely ;-)"
  	((self couldBeObject: literal)
  	 and: [objectMemory isYoungObject: literal]) ifTrue:
  		[self assert: (objectMemory addressCouldBeObj: literal).
  		 objectMemory markAndTrace: literal]!

Item was added:
+ ----- Method: CogVMSimulator>>ceStackOverflow: (in category 'trampolines') -----
+ ceStackOverflow: contextSwitchIfNotNil
+ 	"Override to bump up the byteCount from which the microsecond clock is derived."
+ 	byteCount := byteCount + 1000.
+ 	^super ceStackOverflow: contextSwitchIfNotNil!

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 |
- 		[| entryPoint selectorOrCacheTag offset sendTable |
  		 entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
  		 entryPoint <= methodZoneBase
  			ifTrue:
  				[offset := entryPoint]
  			ifFalse:
  				[self
  					offsetAndSendTableFor: entryPoint
  					annotation: annotation
+ 					into: [:off :table| offset := off]].
- 					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]])
  			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>>checkIfValidObjectRefAndTarget:pc:cogMethod: (in category 'garbage collection') -----
  checkIfValidObjectRefAndTarget: annotation pc: mcpc cogMethod: cogMethod
  	<var: #mcpc type: #'char *'>
+ 	| literal cacheTag entryPoint |
- 	| literal cacheTag entryPoint offset targetMethod |
- 	<var: #targetMethod type: #'CogMethod *'>
  	annotation = IsObjectReference ifTrue:
  		[literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
  		 (self asserta: (objectRepresentation checkValidObjectReference: literal)) ifFalse:
  			[^1].
  		((objectRepresentation couldBeObject: literal)
  		 and: [objectMemory isReallyYoungObject: literal]) ifTrue:
  			[(self asserta: (self cCoerceSimple: cogMethod to: #'CogMethod *') cmRefersToYoung) ifFalse:
  				[^2]]].
  	(self isSendAnnotation: annotation) ifTrue:
  		[(self asserta: (self cCoerceSimple: cogMethod to: #'CogMethod *') cmType = CMMethod) ifFalse:
  			[^3].
  		 cacheTag := backEnd inlineCacheTagAt: mcpc asInteger.
  		 (self asserta: (objectRepresentation checkValidInlineCacheTag: cacheTag)) ifFalse:
  			[^4].
  		((objectRepresentation couldBeObject: cacheTag)
  		 and: [coInterpreter isReallyYoungObject: cacheTag]) ifTrue:
  			[(self asserta: (self cCoerceSimple: cogMethod to: #'CogMethod *') cmRefersToYoung) ifFalse:
  				[^5]].
  		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:
+ 						[^6]]]].
- 			 self
- 				offsetAndSendTableFor: entryPoint
- 				annotation: annotation
- 				into: [:off :table| offset := off].
- 			 targetMethod := self cCoerceSimple: entryPoint - offset to: #'CogMethod *'.
- 			 (self asserta: (targetMethod cmType = CMMethod
- 						   or: [targetMethod cmType = CMClosedPIC
- 						   or: [targetMethod cmType = CMOpenPIC]])) ifFalse:
- 				[^6]]].
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>followForwardedLiteralsIn: (in category 'garbage collection') -----
  followForwardedLiteralsIn: cogMethod
  	<api>
  	<option: #SpurObjectMemory>
  	<var: #cogMethod type: #'CogMethod *'>
  	self assert: (objectMemory shouldRemapOop: cogMethod methodObject) not.
  	(objectMemory shouldRemapOop: cogMethod selector) ifTrue:
  		[cogMethod selector: (objectMemory remapObj: cogMethod selector)].
  	self mapFor: cogMethod
+ 		performUntil: #remapIfObjectRef:pc:hasYoung:
- 		performUntil: (self cppIf: NewspeakVM
- 							ifTrue: [#remapNSIfObjectRef:pc:hasYoung:]
- 							ifFalse: [#remapIfObjectRef:pc:hasYoung:])
  		arg: 0!

Item was changed:
  ----- Method: Cogit>>incrementUsageOfTargetIfLinkedSend:mcpc:ignored: (in category 'compaction') -----
  incrementUsageOfTargetIfLinkedSend: annotation mcpc: mcpc ignored: superfluity
  	<var: #mcpc type: #'char *'>
+ 	| entryPoint |
- 	| entryPoint offset targetMethod |
- 	<var: #targetMethod type: #'CogMethod *'>
  	(self isSendAnnotation: annotation) ifTrue:
  		[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]]]].
- 			[self
- 				offsetAndSendTableFor: entryPoint
- 				annotation: annotation
- 				into: [:off :table| offset := off].
- 			targetMethod := self cCoerceSimple: entryPoint - offset to: #'CogMethod *'.
- 			targetMethod cmUsageCount < (CMMaxUsageCount // 2) ifTrue:
- 				[targetMethod cmUsageCount: targetMethod cmUsageCount + 1]]].
  	^0 "keep scanning"!

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:
- 						 performUntil: (self cppIf: NewspeakVM
- 											ifTrue: [#remapNSIfObjectRef:pc:hasYoung:]
- 											ifFalse: [#remapIfObjectRef:pc:hasYoung:])
  						 arg: hasYoungObjPtr.
  					 hasYoungObj
  						ifTrue:
  							[cogMethod cmRefersToYoung ifFalse:
  								[cogMethod cmRefersToYoung: true.
  								 methodZone addToYoungReferrers: cogMethod].
  							hasYoungObj := false]
  						ifFalse: [cogMethod cmRefersToYoung: false]]].
  		cogMethod := methodZone methodAfter: cogMethod].
  	methodZone pruneYoungReferrers.
  	freedPIC ifTrue:
  		[self unlinkSendsToFree.
  		 codeModified := true].
  	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: Cogit>>mapObjectReferencesInMachineCodeForFullGC (in category 'garbage collection') -----
  mapObjectReferencesInMachineCodeForFullGC
  	"Update all references to objects in machine code for a full gc.  Since
  	 the current (New)ObjectMemory GC makes everything old in a full GC
  	 a method not referring to young will not refer to young afterwards"
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	codeModified := false.
  	self mapObjectReferencesInGeneratedRuntime.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[cogMethod cmType ~= CMFree ifTrue:
  			[self assert: (self cogMethodDoesntLookKosher: cogMethod) = 0.
  			 cogMethod selector: (objectRepresentation remapOop: cogMethod selector).
  			 cogMethod cmType = CMClosedPIC
  				ifTrue:
  					[self assert: cogMethod cmRefersToYoung not.
  					 self mapObjectReferencesInClosedPIC: cogMethod]
  				ifFalse:
  					[cogMethod cmType = CMMethod ifTrue:
  						[self assert: cogMethod objectHeader = objectMemory nullHeaderForMachineCodeMethod.
  						 cogMethod methodObject: (objectRepresentation remapOop: cogMethod methodObject)].
  					 self mapFor: cogMethod
+ 						 performUntil: #remapIfObjectRef:pc:hasYoung:
- 						 performUntil: (self cppIf: NewspeakVM
- 											ifTrue: [#remapNSIfObjectRef:pc:hasYoung:]
- 											ifFalse: [#remapIfObjectRef:pc:hasYoung:])
  						 arg: 0.
  					 (cogMethod cmRefersToYoung
  					  and: [objectRepresentation allYoungObjectsAgeInFullGC]) ifTrue:
  						[cogMethod cmRefersToYoung: false]]].
  		cogMethod := methodZone methodAfter: cogMethod].
  	methodZone pruneYoungReferrers.
  	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: Cogit>>mapObjectReferencesInMachineCodeForYoungGC (in category 'garbage collection') -----
  mapObjectReferencesInMachineCodeForYoungGC
  	"Update all references to objects in machine code for either a Spur scavenging gc
  	 or a Squeak V3 incremental GC.  Avoid scanning all code by using the youngReferrers
  	 list.  In a young gc a method referring to young may no longer refer to young, but a
  	 method not referring to young cannot and will not refer to young afterwards."
  	| pointer cogMethod hasYoungObj hasYoungObjPtr |
  	<var: #cogMethod type: #'CogMethod *'>
  	hasYoungObj := false.
  	hasYoungObjPtr := (self addressOf: hasYoungObj put: [:val| hasYoungObj := val]) asInteger.
  	codeModified := false.
  	pointer := methodZone youngReferrers.
  	[pointer < methodZone zoneEnd] whileTrue:
  		[self assert: hasYoungObj not.
  		 cogMethod := coInterpreter cCoerceSimple: (objectMemory longAt: pointer) to: #'CogMethod *'.
  		 cogMethod cmType = CMFree
  			ifTrue: [self assert: cogMethod cmRefersToYoung not]
  			ifFalse:
  				[self assert: (self cogMethodDoesntLookKosher: cogMethod) = 0.
  				 cogMethod cmRefersToYoung ifTrue:
  					[self assert: (cogMethod cmType = CMMethod
  								or: [cogMethod cmType = CMOpenPIC]).
  					 cogMethod selector: (objectRepresentation remapOop: cogMethod selector).
  					 (objectMemory isYoung: cogMethod selector) ifTrue:
  						[hasYoungObj := true].
  					 cogMethod cmType = CMMethod ifTrue:
  						[self assert: cogMethod objectHeader = objectMemory nullHeaderForMachineCodeMethod.
  						 cogMethod methodObject: (objectRepresentation remapOop: cogMethod methodObject).
  						 (objectMemory isYoung: cogMethod methodObject) ifTrue:
  							[hasYoungObj := true]].
  					 self mapFor: cogMethod
+ 						 performUntil: #remapIfObjectRef:pc:hasYoung:
- 						 performUntil: (self cppIf: NewspeakVM
- 											ifTrue: [#remapNSIfObjectRef:pc:hasYoung:]
- 											ifFalse: [#remapIfObjectRef:pc:hasYoung:])
  						 arg: hasYoungObjPtr.
  					 hasYoungObj
  						ifTrue: [hasYoungObj := false]
  						ifFalse: [cogMethod cmRefersToYoung: false]]].
  		 pointer := pointer + BytesPerWord].
  	methodZone pruneYoungReferrers.
  	codeModified ifTrue: "After updating oops in inline caches we need to flush the icache."
  		[processor flushICacheFrom: methodZoneBase to: methodZone limitZony asInteger]!

Item was removed:
- ----- Method: Cogit>>markAndTraceObjectReferencesInMachineCode (in category 'jit - api') -----
- markAndTraceObjectReferencesInMachineCode
- 	"Mark and trace any object references in the generated run-time."
- 	0 to: runtimeObjectRefIndex - 1 do:
- 		[:i| | mcpc literal |
- 		 mcpc := objectReferencesInRuntime at: i.
- 		 literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
- 		 objectRepresentation markAndTraceLiteral: literal]!

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 *'>
+ 	| literal |
- 	| literal cacheTag cacheTagMarked entryPoint targetMethod offset sendTable unlinkedRoutine |
- 	<var: #targetMethod type: #'CogMethod *'>
- 	<var: #sendTable type: #'sqInt *'>
  	annotation = IsObjectReference ifTrue:
  		[literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
  		 objectRepresentation markAndTraceLiteral: literal].
  	(self isSendAnnotation: 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| | unlinkedRoutine |
+ 						 (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."
+ 							 unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
+ 							 backEnd
+ 								rewriteInlineCacheAt: mcpc asInteger
+ 								tag: targetMethod selector
+ 								target: unlinkedRoutine.
+ 							 codeModified := true.
+ 							 objectRepresentation markAndTraceLiteral: targetMethod selector]]]
+ 				ifFalse:
+ 					[objectRepresentation markAndTraceLiteral: cacheTag.  "cacheTag is selector"
+ 					 self cppIf: NewspeakVM ifTrue:
+ 						[entryPoint = ceImplicitReceiverTrampoline ifTrue:
+ 							[| classpc mixinpc class mixin |
+ 							 objectRepresentation markAndTraceLiteral: cacheTag.  "cacheTag is selector"
+ 							 classpc := mcpc asInteger + backEnd jumpShortByteSize.
+ 							 mixinpc := mcpc asInteger + backEnd jumpShortByteSize + BytesPerOop.
+ 							 class := backEnd unalignedLongAt: classpc.
+ 							 class ~= 0
+ 								ifTrue:
+ 									[self assert: (objectMemory addressCouldBeObj: class).
+ 									 (objectRepresentation cacheTagIsMarked: class)
+ 										ifTrue:
+ 											[(mixin := backEnd unalignedLongAt: mixinpc) ~= 0 ifTrue:
+ 												[objectRepresentation markAndTraceLiteral: mixin]]
+ 										ifFalse:
+ 											[backEnd
+ 												unalignedLongAt: classpc put: 0;
+ 												unalignedLongAt: mixinpc put: 0.
+ 											 codeModified := true]]
+ 								ifFalse:
+ 									[self assert: (backEnd unalignedLongAt: mixinpc) = 0]]]]]].
- 		[cacheTag := backEnd inlineCacheTagAt: mcpc asInteger.
- 		 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 *'.
- 				offset = cmNoCheckEntryOffset
- 					ifTrue: [objectRepresentation markAndTraceLiteral: cacheTag. "cacheTag is selector"
- 							cacheTagMarked := true]
- 					ifFalse: [cacheTagMarked := objectRepresentation cacheTagIsMarked: cacheTag].
- 				(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."
- 					 unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
- 					 backEnd
- 						rewriteInlineCacheAt: mcpc asInteger
- 						tag: targetMethod selector
- 						target: unlinkedRoutine.
- 					 codeModified := true.
- 					 objectRepresentation markAndTraceLiteral: targetMethod selector]]
- 			ifFalse:
- 				[objectRepresentation markAndTraceLiteral: cacheTag]].
  	^0 "keep scanning"!

Item was removed:
- ----- Method: Cogit>>markLiteralsAndUnlinkIfUnmarkedSendOrPushImplicit:pc:method: (in category 'garbage collection') -----
- markLiteralsAndUnlinkIfUnmarkedSendOrPushImplicit: annotation pc: mcpc method: cogMethod
- 	<option: #NewspeakVM>
- 	"Mark and trace literals.  Unlink sends that have unmarked cache tags or targets."
- 	<var: #mcpc type: #'char *'>
- 	| literal cacheTag cacheTagMarked entryPoint targetMethod offset sendTable unlinkedRoutine |
- 	<var: #targetMethod type: #'CogMethod *'>
- 	<var: #sendTable type: #'sqInt *'>
- 	annotation = IsObjectReference ifTrue:
- 		[literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
- 		 objectRepresentation markAndTraceLiteral: literal].
- 	(self isSendAnnotation: annotation) ifTrue:
- 		[entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
- 		 cacheTag := backEnd inlineCacheTagAt: mcpc asInteger.
- 		 cacheTagMarked := objectRepresentation cacheTagIsMarked: cacheTag.
- 		 entryPoint = ceImplicitReceiverTrampoline
- 			ifTrue:
- 				[| classpc mixinpc class mixin |
- 				 objectRepresentation markAndTraceLiteral: cacheTag.  "cacheTag is selector"
- 				 classpc := mcpc asInteger + backEnd jumpShortByteSize.
- 				 mixinpc := mcpc asInteger + backEnd jumpShortByteSize + BytesPerOop.
- 				 class := backEnd unalignedLongAt: classpc.
- 				 class ~= 0
- 					ifTrue:
- 						[self assert: (objectMemory addressCouldBeObj: class).
- 						 (objectRepresentation cacheTagIsMarked: class)
- 							ifTrue:
- 								[(mixin := backEnd unalignedLongAt: mixinpc) ~= 0 ifTrue:
- 									[objectRepresentation markAndTraceLiteral: mixin]]
- 							ifFalse:
- 								[backEnd
- 									unalignedLongAt: classpc put: 0;
- 									unalignedLongAt: mixinpc put: 0.
- 								 codeModified := true]]
- 					ifFalse:
- 						[self assert: (backEnd unalignedLongAt: mixinpc) = 0]]
- 			ifFalse:
- 				[entryPoint > methodZoneBase
- 					ifTrue: "It's a linked send."
- 						[self
- 							offsetAndSendTableFor: entryPoint
- 							annotation: annotation
- 							into: [:off :table| offset := off. sendTable := table].
- 						offset = cmNoCheckEntryOffset
- 							ifTrue: [objectRepresentation markAndTraceLiteral: cacheTag. "cacheTag is selector"
- 									cacheTagMarked := true]
- 							ifFalse: [cacheTagMarked := objectRepresentation cacheTagIsMarked: cacheTag].
- 						targetMethod := self cCoerceSimple: entryPoint - offset to: #'CogMethod *'.
- 						(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."
- 							 unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
- 							 backEnd
- 								rewriteInlineCacheAt: mcpc asInteger
- 								tag: targetMethod selector
- 								target: unlinkedRoutine.
- 							 codeModified := true.
- 							 objectRepresentation markAndTraceLiteral: targetMethod selector]]
- 					ifFalse:
- 						[objectRepresentation markAndTraceLiteral: cacheTag]]].
- 	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>markLiteralsAndUnlinkUnmarkedSendsIn: (in category 'garbage collection') -----
  markLiteralsAndUnlinkUnmarkedSendsIn: cogMethod
  	"Unlink sends that have unmarked classes in inline caches or freed/freeable targets.
  	 Nil-out inline caches linked to open PICs.
  	 Assert that any selectors are marked.  We can do this since
  	 this is only run on marked methods and thus any selectors they
  	 reference should already be marked."
  	<var: #cogMethod type: #'CogMethod *'>
  	<inline: true>
  	self assert: cogMethod cmType = CMMethod.
  	self assert: (objectMemory isMarked: cogMethod methodObject).
  	objectRepresentation markAndTraceLiteral: cogMethod selector.
  	self mapFor: cogMethod
+ 		 performUntil: #markLiteralsAndUnlinkIfUnmarkedSend:pc:method:
- 		 performUntil: (self cppIf: NewspeakVM
- 						ifTrue: [#markLiteralsAndUnlinkIfUnmarkedSendOrPushImplicit:pc:method:]
- 						ifFalse: [#markLiteralsAndUnlinkIfUnmarkedSend:pc:method:])
  		 arg: cogMethod asInteger!

Item was removed:
- ----- Method: Cogit>>markNSYoungObjects:pc:method: (in category 'garbage collection') -----
- markNSYoungObjects: annotation pc: mcpc method: cogMethod
- 	<option: #NewspeakVM>
- 	"Mark and trace young literals."
- 	<var: #mcpc type: #'char *'>
- 	| literal cacheTag entryPoint |
- 	annotation = IsObjectReference ifTrue:
- 		[literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
- 		 objectRepresentation markAndTraceLiteralIfYoung: literal].
- 	(self isSendAnnotation: annotation) ifTrue:
- 		[cacheTag := backEnd inlineCacheTagAt: mcpc asInteger.
- 		 objectRepresentation markAndTraceLiteralIfYoung: cacheTag.
- 		 entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
- 		 entryPoint = ceImplicitReceiverTrampoline ifTrue:
- 			[| class mixin |
- 			 (class := backEnd unalignedLongAt: mcpc asInteger + backEnd jumpShortByteSize) ~= 0 ifTrue:
- 				[objectRepresentation markAndTraceLiteralIfYoung: class.
- 				 mixin := backEnd unalignedLongAt: mcpc asInteger + backEnd jumpShortByteSize + BytesPerOop.
- 				 objectRepresentation markAndTraceLiteralIfYoung: mixin]]].
- 	^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 *'>
+ 	| literal |
- 	| literal cacheTag |
  	annotation = IsObjectReference ifTrue:
  		[literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
  		 objectRepresentation markAndTraceLiteralIfYoung: literal].
  	(self isSendAnnotation: annotation) ifTrue:
+ 		[self offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
+ 			[:entryPoint :cacheTag :tagCouldBeObj |
+ 			 tagCouldBeObj ifTrue:
+ 				[objectRepresentation markAndTraceLiteralIfYoung: cacheTag].
+ 				 self cppIf: NewspeakVM ifTrue:
+ 					[entryPoint = ceImplicitReceiverTrampoline ifTrue:
+ 						[| class mixin |
+ 						 (class := backEnd unalignedLongAt: mcpc asInteger + backEnd jumpShortByteSize) ~= 0 ifTrue:
+ 							[objectRepresentation markAndTraceLiteralIfYoung: class.
+ 							 mixin := backEnd unalignedLongAt: mcpc asInteger + backEnd jumpShortByteSize + BytesPerOop.
+ 							 objectRepresentation markAndTraceLiteralIfYoung: mixin]]]]].
- 		[cacheTag := backEnd inlineCacheTagAt: mcpc asInteger.
- 		 objectRepresentation markAndTraceLiteralIfYoung: cacheTag].
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>markYoungObjectsIn: (in category 'garbage collection') -----
  markYoungObjectsIn: cogMethod
  	"Mark young literals in the method."
  	<var: #cogMethod type: #'CogMethod *'>
  	<inline: true>
  	self assert: (cogMethod cmType = CMMethod
  				or: [cogMethod cmType = CMOpenPIC]).
  	 (objectMemory isYoung: cogMethod selector) ifTrue:
  		[objectMemory markAndTrace: cogMethod selector].
  	(cogMethod cmType = CMMethod
  	 and: [objectMemory isYoung: cogMethod methodObject]) ifTrue:
  		[objectMemory markAndTrace: cogMethod methodObject].
  	self mapFor: cogMethod
+ 		 performUntil: #markYoungObjects:pc:method:
- 		 performUntil: (self cppIf: NewspeakVM
- 						ifTrue: [#markNSYoungObjects:pc:method:]
- 						ifFalse: [#markYoungObjects:pc:method:])
  		 arg: cogMethod asInteger!

Item was added:
+ ----- Method: Cogit>>offsetCacheTagAndCouldBeObjectAt:annotation:into: (in category 'in-line cacheing') -----
+ offsetCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into: trinaryBlock
+ 	"Evaluate trinaryBlock with the entry, inline cache tag and whether the cache
+ 	 tag could be an object, for the send at mcpc with annotation annotation."
+ 	<inline: true>
+ 	| cacheTag entryPoint tagCouldBeObj |
+ 	cacheTag := backEnd inlineCacheTagAt: mcpc asInteger.
+ 	entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
+ 	"in-line cache tags are the selectors of sends if sends are unlinked,
+ 	 the selectors of super sends (entry offset = cmNoCheckEntryOffset)
+ 	 or in-line cache tags (classes, class indices, immediate bit patterns, etc).
+ 	 Note that selectors can be immediate so there is no guarantee that they
+ 	 are markable/remappable objects."
+ 	tagCouldBeObj := objectRepresentation inlineCacheTagsMayBeObjects
+ 						or: [entryPoint < methodZoneBase
+ 						or: [(entryPoint bitAnd: entryPointMask) = cmNoCheckEntryOffset]].
+ 	trinaryBlock
+ 		value: entryPoint
+ 		value: cacheTag
+ 		value: tagCouldBeObj!

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 *'>
  	annotation = IsObjectReference ifTrue:
  		[| literal mappedLiteral |
  		 literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
  		 (objectRepresentation couldBeObject: literal) ifTrue:
  			[mappedLiteral := objectRepresentation remapObject: literal.
  			 literal ~= mappedLiteral ifTrue:
  				[backEnd storeLiteral: mappedLiteral beforeFollowingAddress: mcpc asInteger.
  				 codeModified := true].
  			 (hasYoungPtr ~= 0
  			  and: [objectMemory isYoung: mappedLiteral]) ifTrue:
  				[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]].
  	(self isSendAnnotation: 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 asInteger.
+ 					 codeModified := true].
+ 				 (hasYoungPtr ~= 0
+ 				  and: [objectMemory isYoung: mappedCacheTag]) ifTrue:
+ 					[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]].
+ 			 (self cppIf: NewspeakVM
+ 					ifTrue: [entryPoint = ceImplicitReceiverTrampoline]
+ 					ifFalse: [false])
+ 				ifTrue:
+ 					[| pc oop mappedOop |
+ 					 pc := mcpc asInteger + backEnd jumpShortByteSize.
+ 					 (oop := backEnd unalignedLongAt: pc) ~= 0 ifTrue:
+ 						[mappedOop := objectRepresentation remapOop: oop.
+ 						 mappedOop ~= oop ifTrue:
+ 							[backEnd unalignedLongAt: pc put: mappedOop].
+ 						 (hasYoungPtr ~= 0
+ 						  and: [objectMemory isYoung: mappedOop]) ifTrue:
+ 							[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true].
+ 						 pc := mcpc asInteger + backEnd jumpShortByteSize + BytesPerOop.
+ 						 (oop := backEnd unalignedLongAt: pc) ~= 0 ifTrue:
+ 							[mappedOop := objectRepresentation remapOop: oop.
+ 							 mappedOop ~= oop ifTrue:
+ 								[backEnd unalignedLongAt: pc put: mappedOop].
+ 						 (hasYoungPtr ~= 0
+ 						  and: [objectMemory isYoung: mappedOop]) ifTrue:
+ 							[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]]]
+ 				ifFalse:
+ 					[hasYoungPtr ~= 0 ifTrue:
+ 						[| offset targetMethod |
+ 						 "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."
+ 							[offset := (entryPoint bitAnd: entryPointMask) = checkedEntryAlignment
+ 										ifTrue: [cmEntryOffset]
+ 										ifFalse: [cmNoCheckEntryOffset].
+ 							targetMethod := self cCoerceSimple: entryPoint - offset to: #'CogMethod *'.
+ 							(objectMemory isYoung: targetMethod selector) ifTrue:
+ 								[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]]]]].
- 		[| cacheTag mappedCacheTag |
- 		 cacheTag := backEnd inlineCacheTagAt: mcpc asInteger.
- 		 (objectRepresentation couldBeObject: cacheTag) ifTrue:
- 			[mappedCacheTag := objectRepresentation remapObject: cacheTag.
- 			 cacheTag ~= mappedCacheTag ifTrue:
- 				[backEnd rewriteInlineCacheTag: mappedCacheTag at: mcpc asInteger.
- 				 codeModified := true].
- 			 (hasYoungPtr ~= 0
- 			  and: [objectMemory isYoung: mappedCacheTag]) ifTrue:
- 				[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]].
- 		 hasYoungPtr ~= 0 ifTrue:
- 			[| entryPoint offset targetMethod |
- 			 "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 := backEnd callTargetFromReturnAddress: mcpc asInteger.
- 			 entryPoint > methodZoneBase ifTrue: "It's a linked send."
- 				[offset := (entryPoint bitAnd: entryPointMask) = checkedEntryAlignment
- 							ifTrue: [cmEntryOffset]
- 							ifFalse: [cmNoCheckEntryOffset].
- 				targetMethod := self cCoerceSimple: entryPoint - offset to: #'CogMethod *'.
- 				(objectMemory isYoung: targetMethod selector) ifTrue:
- 					[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]]].
  	^0 "keep scanning"!

Item was removed:
- ----- Method: Cogit>>remapNSIfObjectRef:pc:hasYoung: (in category 'garbage collection') -----
- remapNSIfObjectRef: annotation pc: mcpc hasYoung: hasYoungPtr
- 	<option: #NewspeakVM>
- 	<var: #mcpc type: #'char *'>
- 	<var: #targetMethod type: #'CogMethod *'>
- 	annotation = IsObjectReference ifTrue:
- 		[| literal mappedLiteral |
- 		 literal := backEnd literalBeforeFollowingAddress: mcpc asInteger.
- 		 (objectRepresentation couldBeObject: literal) ifTrue:
- 			[mappedLiteral := objectRepresentation remapObject: literal.
- 			 literal ~= mappedLiteral ifTrue:
- 				[backEnd storeLiteral: mappedLiteral beforeFollowingAddress: mcpc asInteger.
- 				 codeModified := true].
- 			 (hasYoungPtr ~= 0
- 			  and: [objectMemory isYoung: mappedLiteral]) ifTrue:
- 				[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]].
- 	(self isSendAnnotation: annotation) ifTrue:
- 		[| cacheTag mappedCacheTag entryPoint |
- 		 cacheTag := backEnd inlineCacheTagAt: mcpc asInteger.
- 		 (objectRepresentation couldBeObject: cacheTag) ifTrue:
- 			[mappedCacheTag := objectRepresentation remapObject: cacheTag.
- 			 cacheTag ~= mappedCacheTag ifTrue:
- 				[backEnd rewriteInlineCacheTag: mappedCacheTag at: mcpc asInteger.
- 				 codeModified := true].
- 			 (hasYoungPtr ~= 0
- 			  and: [objectMemory isYoung: mappedCacheTag]) ifTrue:
- 				[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]].
- 		 entryPoint := backEnd callTargetFromReturnAddress: mcpc asInteger.
- 		 entryPoint = ceImplicitReceiverTrampoline
- 			ifTrue:
- 				[| pc oop mappedOop |
- 				 pc := mcpc asInteger + backEnd jumpShortByteSize.
- 				 (oop := backEnd unalignedLongAt: pc) ~= 0 ifTrue:
- 					[mappedOop := objectRepresentation remapOop: oop.
- 					 mappedOop ~= oop ifTrue:
- 						[backEnd unalignedLongAt: pc put: mappedOop].
- 					 (hasYoungPtr ~= 0
- 					  and: [objectMemory isYoung: mappedOop]) ifTrue:
- 						[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true].
- 					 pc := mcpc asInteger + backEnd jumpShortByteSize + BytesPerOop.
- 					 (oop := backEnd unalignedLongAt: pc) ~= 0 ifTrue:
- 						[mappedOop := objectRepresentation remapOop: oop.
- 						 mappedOop ~= oop ifTrue:
- 							[backEnd unalignedLongAt: pc put: mappedOop].
- 					 (hasYoungPtr ~= 0
- 					  and: [objectMemory isYoung: mappedOop]) ifTrue:
- 						[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]]]
- 			ifFalse:
- 				[hasYoungPtr ~= 0 ifTrue:
- 					[| offset targetMethod |
- 					 "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."
- 						[offset := (entryPoint bitAnd: entryPointMask) = checkedEntryAlignment
- 									ifTrue: [cmEntryOffset]
- 									ifFalse: [cmNoCheckEntryOffset].
- 						targetMethod := self cCoerceSimple: entryPoint - offset to: #'CogMethod *'.
- 						(objectMemory isYoung: targetMethod selector) ifTrue:
- 							[(self cCoerceSimple: hasYoungPtr to: #'sqInt *') at: 0 put: true]]]]].
- 	^0 "keep scanning"!

Item was added:
+ ----- Method: Cogit>>targetMethodAndSendTableFor:annotation:into: (in category 'in-line cacheing') -----
+ targetMethodAndSendTableFor: entryPoint annotation: annotation into: binaryBlock
+ 	"Evaluate binaryBlock with the targetMethod and relevant send table for a linked-send
+ 	 to entryPoint.  Do so based on the alignment of entryPoint.  N.B.  For Newspeak sends
+ 	 we don't need to distinguish between ceImplicitReceiver and the other sends since
+ 	 ceImplicitReceiver will never appear to be linked, so only three cases here."
+ 	<inline: true>
+ 	| targetMethod sendTable |
+ 	<var: #targetMethod type: #'CogMethod *'>
+ 	<var: #sendTable type: #'sqInt *'>
+ 	self cppIf: NewspeakVM
+ 		ifTrue:
+ 			[(entryPoint bitAnd: entryPointMask) = checkedEntryAlignment
+ 				ifTrue:
+ 					[self assert: annotation = IsSendCall.
+ 					 targetMethod := self cCoerceSimple: entryPoint - cmEntryOffset to: #'CogMethod *'.
+ 					 sendTable := sendTrampolines]
+ 				ifFalse:
+ 					[(entryPoint bitAnd: entryPointMask) = dynSuperEntryAlignment
+ 						ifTrue:
+ 							[self assert: annotation = IsNSSendCall.
+ 							 targetMethod := self cCoerceSimple: entryPoint - cmDynSuperEntryOffset to: #'CogMethod *'.
+ 							 sendTable := dynamicSuperSendTrampolines]
+ 						ifFalse:
+ 							[self assert: annotation = IsSendCall.
+ 							 targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
+ 							 sendTable := superSendTrampolines]]]
+ 		ifFalse:
+ 			[(entryPoint bitAnd: entryPointMask) = checkedEntryAlignment
+ 				ifTrue:
+ 					[targetMethod := self cCoerceSimple: entryPoint - cmEntryOffset to: #'CogMethod *'.
+ 					 sendTable := sendTrampolines]
+ 				ifFalse:
+ 					[targetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
+ 					 sendTable := superSendTrampolines]].
+ 	binaryBlock
+ 		value: targetMethod
+ 		value: sendTable!

Item was changed:
  ----- Method: Cogit>>unlinkIfFreeOrLinkedSend:pc:of: (in category 'in-line cacheing') -----
  unlinkIfFreeOrLinkedSend: annotation pc: mcpc of: theSelector
  	<var: #mcpc type: #'char *'>
+ 	| entryPoint |
- 	| 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 targetMethodAndSendTableFor: entryPoint annotation: annotation into:
+ 					[:targetMethod :sendTable| | unlinkedRoutine |
+ 					 (targetMethod cmType = CMFree
+ 					  or: [targetMethod selector = theSelector]) ifTrue:
+ 						[unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
+ 						 backEnd
+ 							rewriteInlineCacheAt: mcpc asInteger
+ 							tag: targetMethod selector
+ 							target: unlinkedRoutine.
+ 						 codeModified := true]]]
- 				[self
- 					offsetAndSendTableFor: entryPoint
- 					annotation: annotation
- 					into: [:off :table| offset := off. sendTable := table].
- 				targetMethod := self cCoerceSimple: entryPoint - offset to: #'CogMethod *'.
- 				(targetMethod cmType = CMFree
- 				 or: [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
+ 					 and: [(backEnd inlineCacheTagAt: mcpc asInteger) = theSelector]) ifTrue:
+ 					 	[backEnd
+ 							unalignedLongAt: mcpc asInteger + backEnd jumpShortByteSize put: 0;
+ 							unalignedLongAt: mcpc asInteger + backEnd jumpShortByteSize + BytesPerOop put: 0]]]].
- 					[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]]]]].
  	^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 *'>
+ 	| entryPoint |
- 	| 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 targetMethodAndSendTableFor: entryPoint annotation: annotation into:
+ 					[:targetMethod :sendTable| | unlinkedRoutine |
+ 					 unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
+ 					 backEnd
+ 						rewriteInlineCacheAt: mcpc asInteger
+ 						tag: targetMethod selector
+ 						target: unlinkedRoutine]]
- 				[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]]]].
  	^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 |
- 	| 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 targetMethodAndSendTableFor: entryPoint annotation: annotation into:
+ 					[:targetMethod :sendTable| | unlinkedRoutine |
+ 					 targetMethod selector = theSelector ifTrue:
+ 						[unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
+ 						 backEnd
+ 							rewriteInlineCacheAt: mcpc asInteger
+ 							tag: targetMethod selector
+ 							target: unlinkedRoutine.
+ 						 codeModified := true]]]
- 				[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
+ 					  and: [(backEnd inlineCacheTagAt: mcpc asInteger) = theSelector]) ifTrue:
+ 						[backEnd
+ 							unalignedLongAt: mcpc asInteger + backEnd jumpShortByteSize put: 0;
+ 							unalignedLongAt: mcpc asInteger + backEnd jumpShortByteSize + BytesPerOop put: 0]]]].
- 					[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]]]]].
  	^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 |
- 	| 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 targetMethodAndSendTableFor: entryPoint annotation: annotation into:
+ 					[:targetMethod :sendTable| | unlinkedRoutine |
+ 					 targetMethod asInteger = theCogMethod ifTrue:
+ 						[unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
+ 						 backEnd
+ 							rewriteInlineCacheAt: mcpc asInteger
+ 							tag: targetMethod selector
+ 							target: unlinkedRoutine.
+ 						 codeModified := true]]]
- 				[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]]]].
  	^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 *'>
+ 	| entryPoint |
- 	| 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 targetMethodAndSendTableFor: entryPoint annotation: annotation into:
+ 				[:targetMethod :sendTable| | unlinkedRoutine |
+ 				 targetMethod cmType = CMFree ifTrue:
+ 					[unlinkedRoutine := sendTable at: (targetMethod cmNumArgs min: NumSendTrampolines - 1).
+ 					 backEnd
+ 						rewriteInlineCacheAt: mcpc asInteger
+ 						tag: targetMethod selector
+ 						target: unlinkedRoutine.
+ 					 codeModified := true]]]].
- 			[self
- 				offsetAndSendTableFor: entryPoint
- 				annotation: annotation
- 				into: [:off :table| offset := off. sendTable := table].
- 			targetMethod := self cCoerceSimple: entryPoint - offset to: #'CogMethod *'.
- 			targetMethod cmType = CMFree 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: StackInterpreter>>penultimateLiteralOf: (in category 'debug printing') -----
  penultimateLiteralOf: aMethodOop
+ 	<api>
  	self assert: (objectMemory isOopCompiledMethod: aMethodOop).
  	^self literal: (self literalCountOf: aMethodOop) - 2 ofMethod: aMethodOop!

Item was changed:
  ----- Method: TMethod>>isFunctional (in category 'inlining') -----
  isFunctional
  	"Answer true if the receiver is a functional method. That is, if it
  	 consists of a single return statement of an expression that contains
  	 no other returns.
  
  	 Answer false for methods with return types other than the simple
  	 integer types to work around bugs in the inliner."
  
+ 	(parseTree statements size = 1
+ 	 and: [parseTree statements last isReturn]) ifFalse: [ ^false ].
- 	(parseTree statements size = 1 and:
- 	 [parseTree statements last isReturn]) ifFalse: [ ^false ].
  	parseTree statements last expression nodesDo: [ :n | n isReturn ifTrue: [ ^false ]].
+ 	^#(sqInt usqInt sqLong usqLong #'sqInt *' #'CogMethod *') includes: returnType!
- 	^#(sqInt usqInt sqLong usqLong #'sqInt *') includes: returnType!



More information about the Vm-dev mailing list