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

commits at source.squeak.org commits at source.squeak.org
Tue Jan 21 21:15:08 UTC 2020


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

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

Name: VMMaker.oscog-eem.2670
Author: eem
Time: 21 January 2020, 1:14:55.130247 pm
UUID: a70bae48-dc3d-45e3-8f7a-3740c47c5426
Ancestors: VMMaker.oscog-eem.2669

Cogit:
Refactor simulation of flushICacheFrom:to: so that it actully runs on processors which choose to implment this in machine code.  The implementation is now in the backEnd and defers to the simulator if required.

Compute numTrampolines more accurately, deferring to the backEnd class for backEnd specific trampolines such as ceCheckFeatures.

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

Item was changed:
  ----- Method: CogARMCompiler>>flushICacheFrom:to: (in category 'inline cacheing') -----
  flushICacheFrom: startAddress "<Integer>" to: endAddress "<Integer>"
  	<cmacro: '(me,startAddress,endAddress) __clear_cache((char*) startAddress, (char*) (endAddress ))'>
  	"On ARM we almost certainly need to flush and wash hands. On linux we use __clear_cache (see http://community.arm.com/groups/processors/blog/2010/02/17/caches-and-self-modifying-code for a decent example) and remember that the end address is *exclusive* so we can just use the end address passed in since it is always the byte after the actual last one needing flushing"
+ 	cogit processor flushICacheFrom: startAddress to: endAddress!
- 	self halt: #ceFlushICache!

Item was added:
+ ----- Method: CogAbstractInstruction class>>numTrampolines (in category 'trampoline support') -----
+ numTrampolines
+ 	"By default back ends don't define any trampolines.  But some subclassses
+ 	 may want to, e.g. for cache flushing.  They will override as appropriate."
+ 	^0!

Item was changed:
  ----- Method: CogClass>>cCoerceSimple:to: (in category 'translation support') -----
  cCoerceSimple: value to: cTypeString
  	<doNotGenerate>
  	"Type coercion for translation and simulation.
  	 For simulation answer a suitable surrogate for the struct types"
  	^cTypeString caseOf:
  	   {	[#'unsigned long']							->	[value].
  		[#'unsigned int']							->	[value].
  		[#'unsigned short']							->	[value].
  		[#sqInt]									->	[value].
  		[#'sqIntptr_t']								->	[value].
  		[#'usqIntptr_t']								->	[value].
  		[#usqInt]									->	[value].
  		[#sqLong]									->	[value].
  		[#usqLong]								->	[value].
  		[#'AbstractInstruction *']					->	[value].
  		[#'SpurSegmentInfo *']						->	[value].
  		[#'BytecodeFixup *']						->	[value].
  		[#'CogMethod *']							->	[value].
  		[#'char *']									->	[value].
  		[#'sqInt *']									->	[value].
  		[#'void *']									->	[value].
  		[#void]										->	[value].
  		[#'void (*)()']								->	[value].
  		[#'void (*)(void)']							->	[value].
+ 		[#'usqIntptr_t (*)(void)']					->	[value].
+ 		[#'void (*)(usqIntptr_t,usqIntptr_t)']		->	[value] }!
- 		[#'unsigned long (*)(void)']					->	[value].
- 		[#'void (*)(unsigned long,unsigned long)']	->	[value].
- 		[#'usqIntptr_t (*)(void)']					->	[value] }!

Item was added:
+ ----- Method: CogIA32Compiler class>>numTrampolines (in category 'trampoline support') -----
+ numTrampolines
+ 	^2 "ceCheckFeatures and ceCheckLZCNTFunction"!

Item was changed:
  ----- Method: CogIA32Compiler>>flushICacheFrom:to: (in category 'inline cacheing') -----
  flushICacheFrom: startAddress "<Integer>" to: endAddress "<Integer>"
  	<cmacro: '(me,startAddress,endAddress) 0'>
  	"On Intel processors where code and data have the same linear address, no
  	 special action is required to flush the instruction cache.  One only needs to
  	 execute a serializing instruction (e.g. CPUID) if code and data are at different
  	 virtual addresses (e.g. a debugger using memory-mapping to access a debugee).
+ 	 Using the macro avoids an unnecessary call."!
- 	 Using the macro avoids an unnecessary call."
- 	self halt: #ceFlushICache!

Item was changed:
  ----- Method: CogICacheFlushingIA32Compiler>>flushICacheFrom:to: (in category 'inline cacheing') -----
  flushICacheFrom: startAddress "<Integer>" to: endAddress "<Integer>"
  	<cmacro: '(me,startAddress,endAddress) ceFlushICache(startAddress,endAddress)'>
+ 	^cogit simulateCeFlushICacheFrom: startAddress to: endAddress!
- 	self halt: #ceFlushICache!

Item was changed:
  ----- Method: CogMIPSELCompiler>>flushICacheFrom:to: (in category 'inline cacheing') -----
  flushICacheFrom: startAddress "<Integer>" to: endAddress "<Integer>"
  	<cmacro: '(me,startAddress,endAddress) cacheflush((char*) startAddress, endAddress - startAddress, ICACHE)'>
+ 	"See http://www.linux-mips.org/wiki/Cacheflush_Syscall"!
- 	"See http://www.linux-mips.org/wiki/Cacheflush_Syscall"
- 	self halt: #ceFlushICache!

Item was changed:
+ ----- Method: CogObjectRepresentation class>>numTrampolines (in category 'trampoline support') -----
- ----- Method: CogObjectRepresentation class>>numTrampolines (in category 'accessing') -----
  numTrampolines
  	^1 "ceStoreCheckTrampoline" + (LowcodeVM ifTrue: [ 9 ] ifFalse: [ 0 ])!

Item was changed:
+ ----- Method: CogObjectRepresentationFor32BitSpur class>>numTrampolines (in category 'trampoline support') -----
- ----- Method: CogObjectRepresentationFor32BitSpur class>>numTrampolines (in category 'accessing') -----
  numTrampolines
  	^ super numTrampolines + (LowcodeVM ifTrue: [4] ifFalse: [0])!

Item was changed:
+ ----- Method: CogObjectRepresentationForSpur class>>numTrampolines (in category 'trampoline support') -----
- ----- Method: CogObjectRepresentationForSpur class>>numTrampolines (in category 'accessing') -----
  numTrampolines
  	^super numTrampolines
  		 + (SistaV1BytecodeSet
  			ifTrue: [9] "(small,large)x(method,block,fullBlock) context creation,
  						 ceNewHashTrampoline, ceStoreCheckContextReceiverTrampoline and ceScheduleScavengeTrampoline"
  			ifFalse: [7] "(small,large)x(method,block) context creation, 
  						 ceNewHashTrampoline, ceStoreCheckContextReceiverTrampoline and ceScheduleScavengeTrampoline")
  		 + NumStoreTrampolines
  		 + (SistaVM
  			ifTrue: [1] "inline newHash"
  			ifFalse: [0])!

Item was changed:
+ ----- Method: CogObjectRepresentationForSqueakV3 class>>numTrampolines (in category 'trampoline support') -----
- ----- Method: CogObjectRepresentationForSqueakV3 class>>numTrampolines (in category 'accessing') -----
  numTrampolines
  	^super numTrampolines + 4 + (LowcodeVM ifTrue: [ 3 ] ifFalse: [ 0 ])!

Item was added:
+ ----- Method: CogX64Compiler class>>numTrampolines (in category 'trampoline support') -----
+ numTrampolines
+ 	^1 "ceCheckLZCNTFunction"!

Item was changed:
  ----- Method: CogX64Compiler>>flushICacheFrom:to: (in category 'inline cacheing') -----
  flushICacheFrom: startAddress "<Integer>" to: endAddress "<Integer>"
  	<cmacro: '(me,startAddress,endAddress) 0'>
  	"On Intel processors where code and data have the same linear address, no
  	 special action is required to flush the instruciton cache.  One only needs to
  	 execute a serializing instruction (e.g. CPUID) if code and data are at different
  	 virtual addresses (e.g. a debugger using memory-mapping to access a debugee).
+ 	 Using the macro avoids an unnecessary call."!
- 	 Using the macro avoids an unnecessary call."
- 	self halt: #ceFlushICache!

Item was changed:
+ ----- Method: Cogit class>>numTrampolines (in category 'trampoline support') -----
- ----- Method: Cogit class>>numTrampolines (in category 'accessing') -----
  numTrampolines
+ 	^38 "30 + 4 each for self and super sends" + (LowcodeVM ifTrue: [1] ifFalse: [0]) + CogCompilerClass numTrampolines
- 	^39 "31 + 4 each for self and super sends" + (LowcodeVM ifTrue: [1] ifFalse: [0])
  
  	"self withAllSubclasses collect: [:c| {c. (c instVarNames select: [:ea| ea beginsWith: 'ce']) size}]"!

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

Item was changed:
  ----- Method: Cogit>>cogExtendPIC:CaseNMethod:tag:isMNUCase: (in category 'in-line cacheing') -----
  cogExtendPIC: cPIC CaseNMethod: caseNMethod tag: caseNTag isMNUCase: isMNUCase
  	"Extend the cPIC with the supplied case.  If caseNMethod is cogged dispatch direct to
  	 its unchecked entry-point.  If caseNMethod is not cogged, jump to the fast interpreter
  	 dispatch, and if isMNUCase then dispatch to fast MNU invocation and mark the cPIC as
  	 having the MNU case for cache flushing."
   	<var: #cPIC type: #'CogMethod *'>
  	| operand target address |
  
  	coInterpreter
  		compilationBreak: cPIC selector
  		point: (objectMemory numBytesOf: cPIC selector)
  		isMNUCase: isMNUCase.
  
  	self assert: (objectRepresentation inlineCacheTagIsYoung: caseNTag) not.
  	"Caller patches to open pic if caseNMethod is young."
  	self assert: (caseNMethod notNil and: [(objectMemory isYoung: caseNMethod) not]).
  	(isMNUCase not and: [coInterpreter methodHasCogMethod: caseNMethod])
  		ifTrue: "this isn't an MNU and we have an already cogged method to jump to"
  			[operand := 0.
  			 target := (coInterpreter cogMethodOf: caseNMethod) asInteger + cmNoCheckEntryOffset]
  		ifFalse: 
  			[operand := caseNMethod.
  			 isMNUCase
  				ifTrue: "this is an MNU so tag the CPIC header and setup a jump to the MNUAbort"
  					[cPIC cpicHasMNUCase: true.
  					 target := cPIC asInteger + (self sizeof: CogMethod)]
  				ifFalse: "setup a jump to the interpretAborth so we can cog the target method"
  					[target := cPIC asInteger + self picInterpretAbortOffset]].
  
  	"find the end address of the new case"
  	address := self addressOfEndOfCase: cPIC cPICNumCases +1 inCPIC: cPIC.
  	
  	self rewriteCPICCaseAt: address tag: caseNTag objRef: operand target: target.
  
  	"finally, rewrite the jump 3 instr  before firstCPICCaseOffset to jump to the beginning of this new case"
  	self rewriteCPIC: cPIC caseJumpTo: address - cPICCaseSize. 
  
+ 	backEnd flushICacheFrom: cPIC asUnsignedInteger to: cPIC asUnsignedInteger + closedPICSize.
- 	processor flushICacheFrom: cPIC asUnsignedInteger to: cPIC asUnsignedInteger + closedPICSize.
  	"update the header flag for the number of cases"
  	cPIC cPICNumCases: cPIC cPICNumCases + 1.
  	^0!

Item was changed:
  ----- Method: Cogit>>compactCogCompiledCode (in category 'jit - api') -----
  compactCogCompiledCode
  	<api>
  	self assert: self noCogMethodsMaximallyMarked.
  	coInterpreter markActiveMethodsAndReferents.
  	methodZone freeOlderMethodsForCompaction.
  	self compactPICsWithFreedTargets.
  	methodZone planCompaction.
  	coInterpreter updateStackZoneReferencesToCompiledCodePreCompaction.
  	methodZone relocateMethodsPreCompaction.
  	methodZone compactCompiledCode.
  	self assert: self allMethodsHaveCorrectHeader.
  	self assert: methodZone kosherYoungReferrers.
  	backEnd stopsFrom: methodZone freeStart to: methodZone youngReferrers - 1.
+ 	backEnd
- 	processor
  		flushICacheFrom: methodZoneBase asUnsignedInteger
  		to: methodZone youngReferrers asUnsignedInteger!

Item was changed:
  ----- Method: Cogit>>fillInCPICHeader:numArgs:numCases:hasMNUCase:selector: (in category 'generate machine code') -----
  fillInCPICHeader: pic numArgs: numArgs numCases: numCases hasMNUCase: hasMNUCase selector: selector
  	<returnTypeC: #'CogMethod *'>
  	<var: #pic type: #'CogMethod *'>
  	<inline: true>
  	self assert: (objectMemory isYoung: selector) not.
  	pic cmType: CMClosedPIC.
  	pic objectHeader: 0.
  	pic blockSize: closedPICSize.
  	pic methodObject: 0.
  	pic methodHeader: 0.
  	pic selector: selector.
  	pic cmNumArgs: numArgs.
  	pic cmHasMovableLiteral: false.
  	pic cmRefersToYoung: false.
  	pic cmUsageCount: self initialClosedPICUsageCount.
  	pic cpicHasMNUCase: hasMNUCase.
  	pic cPICNumCases: numCases.
  	pic blockEntryOffset: 0.
  	self assert: pic cmType = CMClosedPIC.
  	self assert: pic selector = selector.
  	self assert: pic cmNumArgs = numArgs.
  	self assert: pic cPICNumCases = numCases.
  	self assert: (backEnd callTargetFromReturnAddress: pic asInteger + missOffset) = (self picAbortTrampolineFor: numArgs).
  	self assert: closedPICSize = (methodZone roundUpLength: closedPICSize).
+ 	backEnd flushICacheFrom: pic asUnsignedInteger to: pic asUnsignedInteger + closedPICSize.
- 	processor flushICacheFrom: pic asUnsignedInteger to: pic asUnsignedInteger + closedPICSize.
  	self maybeEnableSingleStep.
  	^pic!

Item was changed:
  ----- Method: Cogit>>fillInMethodHeader:size:selector: (in category 'generate machine code') -----
  fillInMethodHeader: method size: size selector: selector
  	<returnTypeC: #'CogMethod *'>
  	<var: #method type: #'CogMethod *'>
  	| originalMethod rawHeader |
  	<var: #originalMethod type: #'CogMethod *'>
  	method cmType: CMMethod.
  	method objectHeader: objectMemory nullHeaderForMachineCodeMethod.
  	method blockSize: size.
  	method methodObject: methodObj.
  	rawHeader := coInterpreter rawHeaderOf: methodObj.
  	"If the method has already been cogged (e.g. Newspeak accessors) then
  	 leave the original method attached to its cog method, but get the right header."
  	(coInterpreter isCogMethodReference: rawHeader)
  		ifTrue:
  			[originalMethod := self cCoerceSimple: rawHeader to: #'CogMethod *'.
  			self assert: originalMethod blockSize = size.
  			self assert: methodHeader = originalMethod methodHeader.
  			NewspeakVM ifTrue:
  				[methodZone addToUnpairedMethodList: method]]
  		ifFalse:
  			[coInterpreter rawHeaderOf: methodObj put: method asInteger.
  			 NewspeakVM ifTrue:
  				[method nextMethodOrIRCs: theIRCs]].
  	method methodHeader: methodHeader.
  	method selector: selector.
  	method cmNumArgs: (coInterpreter argumentCountOfMethodHeader: methodHeader).
  	method cmHasMovableLiteral: hasMovableLiteral.
  	(method cmRefersToYoung: hasYoungReferent) ifTrue:
  		[methodZone addToYoungReferrers: method].
  	method cmUsageCount: self initialMethodUsageCount.
  	method cpicHasMNUCase: false.
  	method cmUsesPenultimateLit: maxLitIndex >= ((objectMemory literalCountOfMethodHeader: methodHeader) - 2).
  	method blockEntryOffset: (blockEntryLabel notNil
  								ifTrue: [blockEntryLabel address - method asInteger]
  								ifFalse: [0]).
  	"This can be an error check since a large stackCheckOffset is caused by compiling
  	 a machine-code primitive, and hence depends on the Cogit, not the input method."
  	needsFrame ifTrue:
  		[stackCheckLabel address - method asInteger <= MaxStackCheckOffset ifFalse:
  			[self error: 'too much code for stack check offset']].
  	method stackCheckOffset: (needsFrame
  								ifTrue: [stackCheckLabel address - method asInteger]
  								ifFalse: [0]).
  	self assert: (backEnd callTargetFromReturnAddress: method asInteger + missOffset)
  				= (self methodAbortTrampolineFor: method cmNumArgs).
  	self assert: size = (methodZone roundUpLength: size).
+ 	backEnd flushICacheFrom: method asUnsignedInteger to: method asUnsignedInteger + size.
- 	processor flushICacheFrom: method asUnsignedInteger to: method asUnsignedInteger + size.
  	self maybeEnableSingleStep.
  	^method!

Item was changed:
  ----- Method: Cogit>>fillInOPICHeader:numArgs:selector: (in category 'generate machine code') -----
  fillInOPICHeader: pic numArgs: numArgs selector: selector
  	<returnTypeC: #'CogMethod *'>
  	<var: #pic type: #'CogMethod *'>
  	<inline: true>
  	pic cmType: CMOpenPIC.
  	pic objectHeader: 0.
  	pic blockSize: openPICSize.
  	"pic methodObject: 0.""This is also the nextOpenPIC link so don't initialize it"
  	methodZone addToOpenPICList: pic.
  	pic methodHeader: 0.
  	pic selector: selector.
  	pic cmNumArgs: numArgs.
  	pic cmHasMovableLiteral: (objectMemory isNonImmediate: selector).
  	(pic cmRefersToYoung: (objectMemory isYoung: selector)) ifTrue:
  		[methodZone addToYoungReferrers: pic].
  	pic cmUsageCount: self initialOpenPICUsageCount.
  	pic cpicHasMNUCase: false.
  	pic cPICNumCases: 0.
  	pic blockEntryOffset: 0.
  	self assert: pic cmType = CMOpenPIC.
  	self assert: pic selector = selector.
  	self assert: pic cmNumArgs = numArgs.
  	self assert: (backEnd callTargetFromReturnAddress: pic asInteger + missOffset) = (self picAbortTrampolineFor: numArgs).
  	self assert: openPICSize = (methodZone roundUpLength: openPICSize).
+ 	backEnd flushICacheFrom: pic asUnsignedInteger to: pic asUnsignedInteger + openPICSize.
- 	processor flushICacheFrom: pic asUnsignedInteger to: pic asUnsignedInteger + openPICSize.
  	self maybeEnableSingleStep.
  	^pic!

Item was changed:
  ----- Method: Cogit>>followMovableLiteralsAndUpdateYoungReferrers (in category 'garbage collection') -----
  followMovableLiteralsAndUpdateYoungReferrers
  	"To avoid runtime checks on literal variable and literal accesses in == and ~~, 
  	 we follow literals in methods having movable literals in the postBecome action.
  	 To avoid scanning every method, we annotate cogMethods with the 
  	 cmHasMovableLiteral flag."
  	<option: #SpurObjectMemory>
  	<api>
  	<returnTypeC: #void>
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	self assert: methodZone kosherYoungReferrers.
  	"methodZone firstBogusYoungReferrer"
  	"methodZone occurrencesInYoungReferrers: methodZone firstBogusYoungReferrer"
  	codeModified := false.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[cogMethod cmType ~= CMFree ifTrue:
  			[cogMethod cmHasMovableLiteral ifTrue:
  				[self followForwardedLiteralsIn: cogMethod]].
  		 cogMethod := methodZone methodAfter: cogMethod]..
  	methodZone pruneYoungReferrers.
  	codeModified ifTrue: "After updating oops in inline caches we need to flush the icache."
+ 		[backEnd flushICacheFrom: codeBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]!
- 		[processor flushICacheFrom: codeBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]!

Item was changed:
  ----- Method: Cogit>>generateCaptureCStackPointers: (in category 'initialization') -----
  generateCaptureCStackPointers: captureFramePointer
  	"Generate the routine that writes the current values of the C frame and stack pointers into
  	 variables.  These are used to establish the C stack in trampolines back into the C run-time.
  
  	 This is a presumptuous quick hack for x86.  It is presumptuous for two reasons.  Firstly
  	 the system's frame and stack pointers may differ from those we use in generated code,
  	 e.g. on register-rich RISCs.  Secondly the ABI may not support a simple frameless call
  	 as written here (for example 128-bit stack alignment on Mac OS X)."
  	| startAddress |
  	<inline: false>
  	self allocateOpcodes: 32 bytecodes: 0.
  	startAddress := methodZoneBase.
  	 "Must happen first; value may be used in accessing any of the following addresses"
  	backEnd hasVarBaseRegister ifTrue:
  		[self
  			PushR: VarBaseReg;
  			MoveCq: self varBaseAddress R: VarBaseReg].
  	captureFramePointer ifTrue:
  		[self MoveR: FPReg Aw: self cFramePointerAddress].
  	"Capture the stack pointer prior to the call.  If we've pushed VarBaseReg take that into account."
  	(backEnd leafCallStackPointerDelta ~= 0
  	 or: [backEnd hasVarBaseRegister])
  		ifTrue:
  			[self LoadEffectiveAddressMw:
  					(backEnd hasVarBaseRegister
  						ifTrue: [backEnd leafCallStackPointerDelta + objectMemory wordSize]
  						ifFalse: [backEnd leafCallStackPointerDelta])
  				r: SPReg
  				R: TempReg.
  			 self MoveR: TempReg Aw: self cStackPointerAddress]
  		ifFalse: [self MoveR: SPReg Aw: self cStackPointerAddress].
  	backEnd hasVarBaseRegister ifTrue:
  		[self PopR: VarBaseReg].
  	self RetN: 0.
  	self outputInstructionsForGeneratedRuntimeAt: startAddress.
+ 	backEnd flushICacheFrom: startAddress asUnsignedInteger to: methodZoneBase asUnsignedInteger.
- 	processor flushICacheFrom: startAddress asUnsignedInteger to: methodZoneBase asUnsignedInteger.
  	self recordGeneratedRunTime: 'ceCaptureCStackPointers' address: startAddress.
  	ceCaptureCStackPointers := self cCoerceSimple: startAddress to: #'void (*)(void)'!

Item was changed:
  ----- Method: Cogit>>generateTrampolines (in category 'initialization') -----
  generateTrampolines
  	"Generate the run-time entries and exits at the base of the native code zone and update the base.
  	 Read the class-side method trampolines for documentation on the various trampolines"
  	| methodZoneStart |
  	methodZoneStart := methodZoneBase.
  	methodLabel address: methodZoneStart.
  	self allocateOpcodes: 80 bytecodes: 0.
  	self setHasYoungReferent: false.
  	objectRepresentation maybeGenerateSelectorIndexDereferenceRoutine.
  	self generateSendTrampolines.
  	self generateMissAbortTrampolines.
  	objectRepresentation generateObjectRepresentationTrampolines.
  	self generateRunTimeTrampolines.
  	NewspeakVM ifTrue: [self generateNewspeakRuntime].
  	SistaVM ifTrue: [self generateSistaRuntime].
  	self generateEnilopmarts.
  	self generateTracingTrampolines.
  
  	"finish up"
  	self recordGeneratedRunTime: 'methodZoneBase' address: methodZoneBase.
+ 	backEnd flushICacheFrom: methodZoneStart asUnsignedInteger to: methodZoneBase asUnsignedInteger!
- 	processor flushICacheFrom: methodZoneStart asUnsignedInteger to: methodZoneBase asUnsignedInteger!

Item was changed:
  ----- Method: Cogit>>linkSendAt:in:to:offset:receiver: (in category 'in-line cacheing') -----
  linkSendAt: callSiteReturnAddress in: sendingMethod to: targetMethod offset: theEntryOffset receiver: receiver
  	<api>
  	<var: #sendingMethod type: #'CogMethod *'>
  	<var: #targetMethod type: #'CogMethod *'>
  	| inlineCacheTag address extent |
  	self assert: (theEntryOffset = cmEntryOffset or: [theEntryOffset = cmNoCheckEntryOffset]).
  	self assert: (callSiteReturnAddress between: methodZoneBase and: methodZone freeStart).
  	inlineCacheTag := theEntryOffset = cmNoCheckEntryOffset
  						ifTrue: [targetMethod selector "i.e. no change"]
  						ifFalse: [objectRepresentation inlineCacheTagForInstance: receiver].
  	(objectRepresentation inlineCacheTagIsYoung: inlineCacheTag) ifTrue:
  		[methodZone ensureInYoungReferrers: sendingMethod].
  	address := targetMethod asInteger + theEntryOffset.
  	extent := backEnd
  				rewriteInlineCacheAt: callSiteReturnAddress
  				tag: inlineCacheTag
  				target: address.
+ 	backEnd
- 	processor
  		flushICacheFrom: callSiteReturnAddress asUnsignedInteger  - extent
  		to: callSiteReturnAddress asUnsignedInteger !

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:
  						 arg: hasYoungObjPtr.
  					 hasYoungObj
  						ifTrue:
  							[methodZone ensureInYoungReferrers: cogMethod.
  							hasYoungObj := false]
  						ifFalse:
  							[cogMethod cmRefersToYoung: false]]].
  		cogMethod := methodZone methodAfter: cogMethod].
  	"we /must/ prune youngReferrers here because a) the [cogMethod cmRefersToYoung: false]
  	 block could have removed a method and subsequently it could be added back, and b) we
  	 can not tolerate duplicates in the youngReferrers list."  
  	methodZone pruneYoungReferrers.
  	freedPIC ifTrue:
  		[self unlinkSendsToFree].
  	codeModified ifTrue: "After updating oops in inline caches we need to flush the icache."
+ 		[backEnd flushICacheFrom: codeBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]!
- 		[processor flushICacheFrom: codeBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]!

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:
  						 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."
+ 		[backEnd flushICacheFrom: codeBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]!
- 		[processor flushICacheFrom: codeBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]!

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:
  						 arg: hasYoungObjPtr.
  					 hasYoungObj
  						ifTrue: [hasYoungObj := false]
  						ifFalse: [cogMethod cmRefersToYoung: false]]].
  		 pointer := pointer + objectMemory wordSize].
  	methodZone pruneYoungReferrers.
  	codeModified ifTrue: "After updating oops in inline caches we need to flush the icache."
+ 		[backEnd flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]!
- 		[processor flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]!

Item was changed:
  ----- Method: Cogit>>markAndTraceMachineCodeForNewSpaceGC (in category 'jit - api') -----
  markAndTraceMachineCodeForNewSpaceGC
  	"Free any methods that refer to unmarked objects, unlinking sends to freed methods."
  	| pointer cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	objectMemory leakCheckNewSpaceGC ifTrue:
  		[self asserta: self allMachineCodeObjectReferencesValid].
  	codeModified := false.
  	pointer := methodZone youngReferrers.
  	[pointer < methodZone zoneEnd] whileTrue:
  		[cogMethod := coInterpreter cCoerceSimple: (objectMemory longAt: pointer) to: #'CogMethod *'.
  		 cogMethod cmRefersToYoung ifTrue:
  			[self assert: (self cogMethodDoesntLookKosher: cogMethod) = 0.
  			 self assert: (cogMethod cmType = CMMethod
  						or: [cogMethod cmType = CMOpenPIC]).
  			 (objectMemory isYoung: cogMethod selector) ifTrue:
  				[objectMemory markAndTrace: cogMethod selector].
  			 cogMethod cmType = CMMethod ifTrue:
  				[(objectMemory isYoung: cogMethod methodObject) ifTrue:
  					[objectMemory markAndTrace: cogMethod methodObject].
  				self markYoungObjectsIn: cogMethod]].
  		 pointer := pointer + objectMemory wordSize].
  	objectMemory leakCheckNewSpaceGC ifTrue:
  		[self asserta: self allMachineCodeObjectReferencesValid].
  	codeModified ifTrue: "After updating oops in inline caches we need to flush the icache."
+ 		[backEnd flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]!
- 		[processor flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]!

Item was changed:
  ----- Method: Cogit>>markAndTraceMachineCodeOfMarkedMethods (in category 'jit - api') -----
  markAndTraceMachineCodeOfMarkedMethods
  	"Mark objects in machine-code of marked methods (or open PICs with marked selectors)."
  	<api>
  	<option: #SpurObjectMemory>
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	objectMemory leakCheckFullGC ifTrue:
  		[self asserta: self allMachineCodeObjectReferencesValid].
  	codeModified := false.
  	self markAndTraceObjectReferencesInGeneratedRuntime.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[(cogMethod cmType = CMMethod
  		  and: [objectMemory isMarked: cogMethod methodObject]) ifTrue:
  			[self markAndTraceLiteralsIn: cogMethod].
  		 (cogMethod cmType = CMOpenPIC
  		  and: [(objectMemory isImmediate: cogMethod selector)
  				or: [objectMemory isMarked: cogMethod selector]]) ifTrue:
  			[self markAndTraceLiteralsIn: cogMethod].
  		 cogMethod := methodZone methodAfter: cogMethod].
  	objectMemory leakCheckFullGC ifTrue:
  		[self asserta: self allMachineCodeObjectReferencesValid].
  	codeModified ifTrue: "After updating oops in inline caches we need to flush the icache."
+ 		[backEnd flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]!
- 		[processor flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]!

Item was changed:
  ----- Method: Cogit>>markAndTraceOrFreeMachineCodeForFullGC (in category 'jit - api') -----
  markAndTraceOrFreeMachineCodeForFullGC
  	"Free any methods that refer to unmarked objects, unlinking sends to freed methods."
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	objectMemory leakCheckFullGC ifTrue:
  		[self asserta: self allMachineCodeObjectReferencesValid].
  	codeModified := false.
  	self markAndTraceObjectReferencesInGeneratedRuntime.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[self markAndTraceOrFreeCogMethod: cogMethod firstVisit: true.
  		 cogMethod := methodZone methodAfter: cogMethod].
  	objectMemory leakCheckFullGC ifTrue:
  		[self asserta: self allMachineCodeObjectReferencesValid].
  	codeModified ifTrue: "After updating oops in inline caches we need to flush the icache."
+ 		[backEnd flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]!
- 		[processor flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]!

Item was changed:
  ----- Method: Cogit>>patchToOpenPICFor:numArgs:receiver: (in category 'in-line cacheing') -----
  patchToOpenPICFor: selector numArgs: numArgs receiver: receiver
  	"Code entry closed PIC full or miss to an instance of a young class or to a young target method.
  	 Attempt to patch the send site to an open PIC.  Answer if the attempt succeeded; in fact it will
  	 only return if the attempt failed.
  	 The stack looks like:
  			receiver
  			args
  	 sp=>	sender return address"
  	<api>
  	| oPIC outerReturn extent |
  	<var: #oPIC type: #'CogMethod *'>
  	outerReturn := coInterpreter stackTop.
  	"See if an Open PIC is already available."
  	oPIC := methodZone openPICWithSelector: selector.
  	oPIC ifNil:
  		["otherwise attempt to create an Open PIC."
  		oPIC := self cogOpenPICSelector: selector numArgs: numArgs.
  		(oPIC asInteger between: MaxNegativeErrorCode and: -1) ifTrue:
  			["For some reason the PIC couldn't be generated, most likely a lack of code memory."
  			oPIC asInteger = InsufficientCodeSpace ifTrue:
  				[coInterpreter callForCogCompiledCodeCompaction].
  			^false]].
  	"Relink the send site to the pic.  Reset the cache tag to the selector, for the
  	 benefit of the cacheTag assert check in checkIfValidOopRef:pc:cogMethod: et al."
  	extent := backEnd
  				rewriteInlineCacheAt: outerReturn
  				tag: (self inlineCacheValueForSelector: selector
  						  in: coInterpreter mframeHomeMethodExport
  						  at: outerReturn)
  				target: oPIC asInteger + cmEntryOffset.
+ 	backEnd
- 	processor
  		flushICacheFrom: outerReturn asUnsignedInteger - extent to: outerReturn asUnsignedInteger;
  		flushICacheFrom: oPIC asUnsignedInteger to: oPIC asUnsignedInteger + openPICSize.
  	"Jump into the oPIC at its entry"
  	coInterpreter executeCogMethod: oPIC fromLinkedSendWithReceiver: receiver.
  	"NOTREACHED"
  	^true!

Item was added:
+ ----- Method: Cogit>>simulateCeFlushICacheFrom:to: (in category 'simulation only') -----
+ simulateCeFlushICacheFrom: start to: finish
+ 	<doNotGenerate>
+ 	processor abiMarshallArg0: start arg1: start.
+ 	self simulateLeafCallOf: ceFlushICache!

Item was changed:
  ----- Method: Cogit>>unlinkAllSends (in category 'jit - api') -----
  unlinkAllSends
  	<api>
  	"Unlink all sends in cog methods."
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	methodZoneBase ifNil: [^self].
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	methodZone voidOpenPICList.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[cogMethod cmType = CMMethod
  			ifTrue:
  				[self mapFor: cogMethod
  					 performUntil: #unlinkIfLinkedSend:pc:ignored:
  					 arg: 0]
  			ifFalse:
  				[cogMethod cmType ~= CMFree ifTrue:
  					[methodZone freeMethod: cogMethod]].
  		cogMethod := methodZone methodAfter: cogMethod].
  	"After updating inline caches we need to flush the icache."
+ 	backEnd flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger!
- 	processor flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger!

Item was changed:
  ----- Method: Cogit>>unlinkSendsLinkedForInvalidClasses (in category 'jit - api') -----
  unlinkSendsLinkedForInvalidClasses
  	<api>
  	<option: #SpurObjectMemory>
  	"Unlink all sends in cog methods whose class tag is that of a forwarded class."
  	| cogMethod freedPIC |
  	<var: #cogMethod type: #'CogMethod *'>
  	methodZoneBase ifNil: [^self].
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	codeModified := freedPIC := false.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[cogMethod cmType = CMMethod
  			ifTrue:
  				[self mapFor: cogMethod
  					 performUntil: #unlinkIfInvalidClassSend:pc:ignored:
  					 arg: 0]
  			ifFalse:
  				[(cogMethod cmType = CMClosedPIC
  				  and: [self cPICHasForwardedClass: cogMethod]) ifTrue:
  					[methodZone freeMethod: cogMethod.
  					 freedPIC := true]].
  		cogMethod := methodZone methodAfter: cogMethod].
  	freedPIC
  		ifTrue: [self unlinkSendsToFree]
  		ifFalse:
  			[codeModified ifTrue: "After possibly updating inline caches we need to flush the icache."
+ 				[backEnd flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]]!
- 				[processor flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]]!

Item was changed:
  ----- Method: Cogit>>unlinkSendsOf:isMNUSelector: (in category 'jit - api') -----
  unlinkSendsOf: selector isMNUSelector: isMNUSelector
  	<api>
  	"Unlink all sends in cog methods. Free all Closed PICs with the selector,
  	 or with an MNU case if isMNUSelector.  First check if any method actually
  	 has the selector; if not there can't be any linked send to it.  This routine
  	 (including descendents) is performance critical.  It contributes perhaps
  	 30% of entire execution time in Compiler recompileAll."
  	| cogMethod mustScanAndUnlink |
  	<var: #cogMethod type: #'CogMethod *'>
  	methodZoneBase ifNil: [^self].
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	mustScanAndUnlink := false.
  	isMNUSelector
  		ifTrue:
  			[[cogMethod < methodZone limitZony] whileTrue:
  				[cogMethod cmType ~= CMFree ifTrue:
  					[cogMethod cpicHasMNUCase
  						ifTrue:
  							[self assert: cogMethod cmType = CMClosedPIC.
  							 methodZone freeMethod: cogMethod.
  							 mustScanAndUnlink := true]
  						ifFalse:
  							[cogMethod selector = selector ifTrue:
  								[mustScanAndUnlink := true.
  								 cogMethod cmType = CMClosedPIC ifTrue:
  									[methodZone freeMethod: cogMethod]]]].
  				 cogMethod := methodZone methodAfter: cogMethod]]
  		ifFalse:
  			[[cogMethod < methodZone limitZony] whileTrue:
  				[(cogMethod cmType ~= CMFree
  				  and: [cogMethod selector = selector]) ifTrue:
  					[mustScanAndUnlink := true.
  					 cogMethod cmType = CMClosedPIC ifTrue:
  						[methodZone freeMethod: cogMethod]].
  				 cogMethod := methodZone methodAfter: cogMethod]].
  	mustScanAndUnlink ifFalse:
  		[^self].
  	codeModified := false.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[cogMethod cmType = CMMethod ifTrue:
  			[self mapFor: cogMethod
  				 performUntil: #unlinkIfFreeOrLinkedSend:pc:of:
  				 arg: selector].
  		cogMethod := methodZone methodAfter: cogMethod].
  	codeModified ifTrue: "After possibly updating inline caches we need to flush the icache."
+ 		[backEnd flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]!
- 		[processor flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]!

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."
  	| 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 ifNil: [^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."
+ 				[backEnd flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]]!
- 				[processor flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]]!

Item was changed:
  ----- Method: Cogit>>unlinkSendsToFree (in category 'garbage collection') -----
  unlinkSendsToFree
  	<api>
  	"Unlink all sends in cog methods to free methods and/or pics."
  	| cogMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	methodZoneBase ifNil: [^self].
  	codeModified := false.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[cogMethod cmType = CMMethod
  			ifTrue:
  				[self mapFor: cogMethod
  					 performUntil: #unlinkIfLinkedSendToFree:pc:ignored:
  					 arg: 0]
  			ifFalse:
  				[cogMethod cmType = CMClosedPIC ifTrue:
  					[self assert: (self noTargetsFreeInClosedPIC: cogMethod)]].
  		cogMethod := methodZone methodAfter: cogMethod].
  	codeModified ifTrue: "After possibly updating inline caches we need to flush the icache."
+ 		[backEnd flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]!
- 		[processor flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]!

Item was changed:
  ----- Method: Cogit>>unlinkSendsToMachineCodePrimitiveMethodsAndFreeIf: (in category 'jit - api') -----
  unlinkSendsToMachineCodePrimitiveMethodsAndFreeIf: freeIfTrue
  	<api>
  	"Unlink all sends in cog methods to methods with a machine code
  	 primitive, and free machine code primitive methods if freeIfTrue.
  	 To avoid having to scan PICs, free any and all PICs"
  	| cogMethod freedSomething |
  	<var: #cogMethod type: #'CogMethod *'>
  	methodZoneBase ifNil: [^self].
  	codeModified := freedSomething := false.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[cogMethod cmType = CMMethod
  			ifTrue:
  				[(freeIfTrue
  				  and: [self cogMethodHasMachineCodePrim: cogMethod])
  					ifTrue:
  						[methodZone freeMethod: cogMethod.
  						 freedSomething := true]
  					ifFalse:
  						[self mapFor: cogMethod
  							 performUntil: #unlinkIfLinkedSend:pc:toMachineCodePrim:
  							 arg: 0]]
  			ifFalse:
  				[cogMethod cmType = CMClosedPIC ifTrue:
  					[methodZone freeMethod: cogMethod.
  					 freedSomething := true]].
  		cogMethod := methodZone methodAfter: cogMethod].
  	freedSomething
  		ifTrue: [self unlinkSendsToFree]
  		ifFalse:
  			[codeModified ifTrue: "After possibly updating inline caches we need to flush the icache."
+ 				[backEnd flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]]!
- 				[processor flushICacheFrom: methodZoneBase asUnsignedInteger to: methodZone limitZony asUnsignedInteger]]!

Item was changed:
+ ----- Method: RegisterAllocatingCogit class>>numTrampolines (in category 'trampoline support') -----
- ----- Method: RegisterAllocatingCogit class>>numTrampolines (in category 'accessing') -----
  numTrampolines
  	^super numTrampolines + 2 "includes long sendMustBeBoolean trampolines"
  
  	"Cogit withAllSubclasses, CogObjectRepresentation withAllSubclasses collect:
  		[:c| {c. (c instVarNames select: [:ea| ea beginsWith: 'ce']) size}]"
  	"self allInstVarNames select: [:ea| ea beginsWith: 'ce']"
  	"self instVarNames select: [:ea| ea beginsWith: 'ce']"!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>rewritePrimInvocationIn:to: (in category 'external primitive support') -----
  rewritePrimInvocationIn: cogMethod to: primFunctionPointer
  	<api>
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #primFunctionPointer declareC: #'void (*primFunctionPointer)(void)'>
  	| primIndex flags address extent |
  	self cCode: [] inSmalltalk:
  		[primFunctionPointer isInteger ifFalse:
  			[^self rewritePrimInvocationIn: cogMethod to: (self simulatedTrampolineFor: primFunctionPointer)]].
  	self assert: cogMethod cmType = CMMethod.
  	primIndex := coInterpreter
  					primitiveIndexOfMethod: cogMethod methodObject
  					header: cogMethod methodHeader.
  	flags := coInterpreter primitivePropertyFlags: primIndex.
  	(flags anyMask: PrimCallNeedsPrimitiveFunction) ifTrue:
  		[backEnd
  			storeLiteral: primFunctionPointer asUnsignedInteger
  			beforeFollowingAddress: cogMethod asUnsignedInteger
  									+ (externalSetPrimOffsets at: cogMethod cmNumArgs)].
  	"See compileInterpreterPrimitive:"
  	(flags anyMask: PrimCallMayCallBack)
  		ifTrue:
  			[address := cogMethod asUnsignedInteger
  						+ (externalPrimJumpOffsets at: cogMethod cmNumArgs).
  			extent := backEnd
  						rewriteJumpFullAt: address
  						target: primFunctionPointer asUnsignedInteger]
  		ifFalse:
  			[address := cogMethod asUnsignedInteger
  						+ (externalPrimCallOffsets at: cogMethod cmNumArgs).
  			extent := backEnd
  						rewriteCallFullAt: address
  						target: primFunctionPointer asUnsignedInteger].
  	extent > 0 ifTrue:
+ 		[backEnd
- 		[processor
  			flushICacheFrom: cogMethod asUnsignedInteger + cmNoCheckEntryOffset
  			to: address asUnsignedInteger + extent]!

Item was changed:
+ ----- Method: SistaCogit class>>numTrampolines (in category 'trampoline support') -----
- ----- Method: SistaCogit class>>numTrampolines (in category 'accessing') -----
  numTrampolines
  	^super numTrampolines + 1
  
  	"Cogit withAllSubclasses collect: [:c| {c. (c instVarNames select: [:ea| ea beginsWith: 'ce']) size}]"
  	"self instVarNames select: [:ea| ea beginsWith: 'ce']"!

Item was changed:
+ ----- Method: SistaCogitClone class>>numTrampolines (in category 'trampoline support') -----
- ----- Method: SistaCogitClone class>>numTrampolines (in category 'accessing') -----
  numTrampolines
  	^super numTrampolines + 1
  
  	"Cogit withAllSubclasses collect: [:c| {c. (c instVarNames select: [:ea| ea beginsWith: 'ce']) size}]"
  	"self instVarNames select: [:ea| ea beginsWith: 'ce']"!

Item was changed:
+ ----- Method: StackToRegisterMappingCogit class>>numTrampolines (in category 'trampoline support') -----
- ----- Method: StackToRegisterMappingCogit class>>numTrampolines (in category 'accessing') -----
  numTrampolines
  	^super numTrampolines + 12 "includes register args aborts"
  
  	"Cogit withAllSubclasses collect: [:c| {c. (c instVarNames select: [:ea| ea beginsWith: 'ce']) size}]"
  	"self instVarNames select: [:ea| ea beginsWith: 'ce']"!



More information about the Vm-dev mailing list