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

commits at source.squeak.org commits at source.squeak.org
Fri Oct 11 00:25:56 UTC 2019


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

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

Name: VMMaker.oscog-eem.2570
Author: eem
Time: 10 October 2019, 5:25:36.463979 pm
UUID: b61e294a-cb2a-4d9a-9e7e-8cc17676c920
Ancestors: VMMaker.oscog-eem.2569

Cog:
Refactor to make CFramePointer and CStackPointer private variables of CoInterpreter.  This needs associated C changes to isCFramePointerInUse (changes are on deck in my repository), which now takes pointers to the two variables instead of referencing them directly.  The result is that CFramePointer and CStackPointer are accessed via VarBaseReg on relevant platforms.  This nearly halves the size of the generated trampolines/enilopmarts on x86_64.

Fix a reg arg order overwrite problem with the ceDirectedSuperSend?Args trampolines on ARM32.

Simulation:
Eliminate use of the near address hack for CFramePointer and CStackPointer on X64 so that simulation is faithful to the new scheme above.

Slang: Fix a bug in inferring the type of addressOf:[put:].

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

Item was changed:
  ----- Method: CCodeGenerator>>returnTypeForSend:in:ifNil: (in category 'type inference') -----
  returnTypeForSend: sendNode in: aTMethod ifNil: typeIfNil
  	"Answer the return type for a send.  Unbound sends default to typeIfNil.
  	 Methods with types as yet unknown have a type determined either by the
  	 kernelReturnTypes or the table below, or, if they are in neither set, then nil.
  	 The inferred type should match as closely as possible the C type of
  	 generated expessions so that inlining would not change the expression.
  	 If there is a method for sel but its return type is as yet unknown it mustn't
  	 be defaulted, since on a subsequent pass its type may be computable."
  	| sel methodOrNil |
  	methodOrNil := self anyMethodNamed: (sel := sendNode selector).
  	(methodOrNil notNil and: [methodOrNil returnType notNil]) ifTrue:
  		[^self baseTypeForType: methodOrNil returnType].
  	^kernelReturnTypes
  		at: sel
  		ifAbsent:
  			[sel
  				caseOf: {
  				[#integerValueOf:]		->	[#sqInt].
  				[#isIntegerObject:]		->	[#int].
  				[#negated]				->	[self promoteArithmeticTypes: (sendNode receiver typeFrom: self in: aTMethod) and: #int].
  				[#+]					->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#-]						->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#*]					->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#/]						->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#//]					->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#\\]					->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#rem:]					->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#quo:]					->	[self typeForArithmetic: sendNode in: aTMethod].
  				"C99 Sec Bitwise shift operators ... 3 Sematics ...
  				 The integer promotions are performed on each of the operands. The type of the result is that of the promoted left operand..."
  				[#>>]					->	[sendNode receiver typeFrom: self in: aTMethod].
  				[#<<]					->	[sendNode receiver typeFrom: self in: aTMethod].
+ 				[#addressOf:]			->	[(sendNode args first typeFrom: self in: aTMethod)
- 				[#addressOf:]			->	[(sendNode receiver typeFrom: self in: aTMethod)
  												ifNil: [#sqInt]
+ 												ifNotNil: [:type| type, (type last isSeparator ifTrue: ['*'] ifFalse: [' *'])]].
+ 				[#addressOf:put:]		->	[(sendNode args first typeFrom: self in: aTMethod)
+ 												ifNil: [#sqInt]
+ 												ifNotNil: [:type| type, (type last isSeparator ifTrue: ['*'] ifFalse: [' *'])]].
- 												ifNotNil: [:type| type, (type last isLetter ifTrue: [' *'] ifFalse: ['*'])]].
  				[#at:]					->	[self typeForDereference: sendNode in: aTMethod].
  				[#bitAnd:]				->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#bitOr:]				->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#bitXor:]				->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#bitClear:]				->	[self typeForArithmetic: sendNode in: aTMethod].
  				[#bitInvert32]			->	[#'unsigned int'].
  				[#bitInvert64]			->	[self promoteArithmeticTypes: (sendNode receiver typeFrom: self in: aTMethod) and: #int].
  				[#byteSwap32]			->	[#'unsigned int'].
  				[#byteSwap64]			->	[#'unsigned long long'].
  				[#byteSwapped32IfBigEndian:]	->	[#'unsigned int'].
  				[#byteSwapped64IfBigEndian:]	->	[#'unsigned long long'].
  				[#=]					->	[#int].
  				[#~=]					->	[#int].
  				[#==]					->	[#int].
  				[#~~]					->	[#int].
  				[#<]					->	[#int].
  				[#<=]					->	[#int].
  				[#>]					->	[#int].
  				[#>=]					->	[#int].
  				[#between:and:]		->	[#int].
  				[#anyMask:]				->	[#int].
  				[#allMask:]				->	[#int].
  				[#noMask:]				->	[#int].
  				[#isNil]					->	[#int].
  				[#notNil]				->	[#int].
  				[#&]					->	[#int].
  				[#|]						->	[#int].
  				[#not]					->	[#int].
  				[#asFloat]				->	[#double].
  				[#atan]					->	[#double].
  				[#exp]					->	[#double].
  				[#log]					->	[#double].
  				[#sin]					->	[#double].
  				[#sqrt]					->	[#double].
  				[#asLong]				->	[#long].
  				[#asInteger]			->	[#sqInt].
  				[#asIntegerPtr]			->	[#'sqIntptr_t'].
  				[#asUnsignedInteger]	->	[#usqInt].
  				[#asUnsignedIntegerPtr]->	[#'usqIntptr_t'].
  				[#asUnsignedLong]		->	[#'unsigned long'].
  				[#asUnsignedLongLong]		->	[#'unsigned long long'].
  				[#asVoidPointer]		->	[#'void *'].
  				[#signedIntToLong]		->	[#usqInt]. "c.f. generateSignedIntToLong:on:indent:"
  				[#signedIntToShort]	->	[#usqInt]. "c.f. generateSignedIntToShort:on:indent:"
  				[#cCoerce:to:]			->	[self conventionalTypeForType: sendNode args last value].
  				[#cCoerceSimple:to:]	->	[self conventionalTypeForType: sendNode args last value].
  				[#sizeof:]				->	[#'usqIntptr_t']. "Technically it's a size_t but it matches on target architectures so far..."
  				[#ifTrue:ifFalse:]		->	[self typeForConditional: sendNode in: aTMethod].
  				[#ifFalse:ifTrue:]		->	[self typeForConditional: sendNode in: aTMethod].
  				[#ifTrue:]				->	[self typeForConditional: sendNode in: aTMethod].
  				[#ifFalse:]				->	[self typeForConditional: sendNode in: aTMethod].
  				[#and:]					->	[#sqInt].
  				[#or:]					->	[#sqInt].
  				[#caseOf:]				->	[self typeFor: sendNode args first in: aTMethod] }
  				otherwise: "If there /is/ a method for sel but its return type is as yet unknown it /mustn't/ be defaulted,
  							since on a subsequent pass its type may be computable.  Only default unbound selectors."
  					[methodOrNil ifNotNil: [nil] ifNil: [typeIfNil]]]!

Item was changed:
  StackInterpreterPrimitives subclass: #CoInterpreter
+ 	instanceVariableNames: 'cogit cogMethodZone gcMode cogCodeSize desiredCogCodeSize heapBase lastCoggableInterpretedBlockMethod deferSmash deferredSmash primTraceLog primTraceLogIndex traceLog traceLogIndex traceSources cogCompiledCodeCompactionCalledFor statCodeCompactionCount statCodeCompactionUsecs lastUncoggableInterpretedBlockMethod flagInterpretedMethods maxLiteralCountForCompile minBackwardJumpCountForCompile CFramePointer CStackPointer'
- 	instanceVariableNames: 'cogit cogMethodZone gcMode cogCodeSize desiredCogCodeSize heapBase lastCoggableInterpretedBlockMethod deferSmash deferredSmash primTraceLog primTraceLogIndex traceLog traceLogIndex traceSources cogCompiledCodeCompactionCalledFor statCodeCompactionCount statCodeCompactionUsecs lastUncoggableInterpretedBlockMethod flagInterpretedMethods maxLiteralCountForCompile minBackwardJumpCountForCompile'
  	classVariableNames: 'CSCallbackEnter CSCallbackLeave CSCheckEvents CSEnterCriticalSection CSExitCriticalSection CSOwnVM CSResume CSSignal CSSuspend CSSwitchIfNeccessary CSThreadBind CSThreadSchedulingLoop CSWait CSYield HasBeenReturnedFromMCPC HasBeenReturnedFromMCPCOop MFMethodFlagFrameIsMarkedFlag MinBackwardJumpCountForCompile PrimNumberHashMultiply PrimTraceLogSize RumpCStackSize TraceBlockActivation TraceBlockCreation TraceBufferSize TraceCodeCompaction TraceContextSwitch TraceDisownVM TraceFullGC TraceIncrementalGC TraceIsFromInterpreter TraceIsFromMachineCode TraceOwnVM TracePreemptDisowningThread TracePrimitiveFailure TracePrimitiveRetry TraceSources TraceStackOverflow TraceThreadSwitch TraceVMCallback TraceVMCallbackReturn'
  	poolDictionaries: 'CogMethodConstants VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  
+ !CoInterpreter commentStamp: 'eem 10/10/2019 09:08' prior: 0!
- !CoInterpreter commentStamp: 'eem 12/7/2017 11:19' prior: 0!
  I am a variant of the StackInterpreter that can co-exist with the Cog JIT.  I interpret unjitted methods, either because they have been found for the first time or because they are judged to be too big to JIT.  See CogMethod class's comment for method interoperability.
  
  cogCodeSize
  	- the current size of the machine code zone
  
  cogCompiledCodeCompactionCalledFor
  	- a variable set when the machine code zone runs out of space, causing a machine code zone compaction at the next available opportunity
  
  cogMethodZone
  	- the manager for the machine code zone (instance of CogMethodZone)
  
  cogit
  	- the JIT (co-jit) (instance of SimpleStackBasedCogit, StackToRegisterMappoingCogit, etc)
  
  deferSmash
  	- a flag causing deferral of smashes of the stackLimit around the call of functionSymbol (for assert checks)
  
  deferredSmash
  	- a flag noting deferral of smashes of the stackLimit around the call of functionSymbol (for assert checks)
  
  desiredCogCodeSize
  	- the desred size of the machine code zone, set at startup or via primitiveVMParameter to be written at snapshot time
  
  flagInterpretedMethods
  	- true if methods that are interpreted shoudl have their flag bit set (used to identity methods that are interpreted because they're unjittable for some reason)
  
  gcMode
  	- the variable holding the gcMode, used to inform the cogit of how to scan the machine code zone for oops on GC
  
  heapBase
  	- the address in memory of the base of the objectMemory's heap, which is immediately above the machine code zone
  
  lastCoggableInterpretedBlockMethod
  	- a variable used to invoke the cogit for a block mehtod being invoked repeatedly in the interpreter
  
  lastUncoggableInterpretedBlockMethod
  	- a variable used to avoid invoking the cogit for an unjittable method encountered on block evaluation
  
  maxLiteralCountForCompile
  	- the variable controlling which methods to jit.  methods with a literal count above this value will not be jitted (on the grounds that large methods are typically used for initialization, and take up a lot of space in the code zone)
  
  minBackwardJumpCountForCompile
  	- the variable controlling when to attempt to jit a method being interpreted.  If as many backward jumps as this occur, the current method will be jitted
  
  primTraceLog
  	- a small array implementing a crcular buffer logging the last N primitive invocations, GCs, code compactions, etc used for crash reporting
  
  primTraceLogIndex
  	- the index into primTraceLog of the next entry
  
  reenterInterpreter
  	- the jmpbuf used to jmp back into the interpreter when transitioning from machine code to the interpreter
  
  statCodeCompactionCount
  	- the count of machine code zone compactions
  
  statCodeCompactionUsecs
  	- the total microseconds spent in machine code zone compactions
  
  traceLog
  	- a log of various events, used in debugging
  
  traceLogIndex
  	- the index into traceLog of the next entry
  
  traceSources
+ 	- the names associated with the codes of events in traceLog
+ 
+ CFramePointer
+ 	- if in use, the value of the C frame pointer on most recent entry to the interpreter after start-up or a callback.  Used to establish the C stack when calling the run-time from generated machine code.
+ 
+ CStackPointer
+ 	- the value of the C stack pointer on most recent entry to the interpreter after start-up or a callback.  Used to establish the C stack when calling the run-time from generated machine code.!
- 	- the names associated with the codes of events in traceLog!

Item was changed:
  ----- Method: CoInterpreter class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	"Override to avoid repeating StackInterpreter's declarations and add our own extensions"
  	self class == thisContext methodClass ifFalse: [^self]. "Don't duplicate decls in subclasses"
  	aCCodeGenerator
  		addHeaderFile:'"sqCogStackAlignment.h"';
  		addHeaderFile:'"cogmethod.h"'.
  	NewspeakVM ifTrue:
  		[aCCodeGenerator addHeaderFile:'"nssendcache.h"'].
  	aCCodeGenerator
  		addHeaderFile: (aCCodeGenerator vmClass isThreadedVM 
  			ifTrue: ['"cointerpmt.h"'] 
  			ifFalse: ['"cointerp.h"']);
  		addHeaderFile:'"cogit.h"'.
  	aCCodeGenerator vmClass
  		declareInterpreterVersionIn: aCCodeGenerator
  		defaultName: aCCodeGenerator interpreterVersion.
  	aCCodeGenerator
  		var: #heapBase type: #usqInt;
  		var: #statCodeCompactionUsecs type: #usqLong;
  		var: #maxLiteralCountForCompile
  			declareC: 'sqInt maxLiteralCountForCompile = MaxLiteralCountForCompile /* ', MaxLiteralCountForCompile printString, ' */';
  		var: #minBackwardJumpCountForCompile
  			declareC: 'sqInt minBackwardJumpCountForCompile = MinBackwardJumpCountForCompile /* ', MinBackwardJumpCountForCompile printString, ' */'.
  	aCCodeGenerator removeVariable: 'atCache'. "Way too much trouble than it's worth in the Cog VM"
  	aCCodeGenerator
  		var: #primTraceLogIndex type: #'unsigned char';
  		var: #primTraceLog declareC: 'sqInt primTraceLog[256]';
  		var: #traceLog
  		declareC: 'sqInt traceLog[TraceBufferSize /* ', TraceBufferSize printString, ' */]';
+ 		var: #traceSources type: #'char *' array: TraceSources.
+ 	aCCodeGenerator
+ 		var: #CFramePointer type: #'usqIntptr_t';
+ 		var: #CStackPointer type: #'usqIntptr_t'!
- 		var: #traceSources type: #'char *' array: TraceSources!

Item was added:
+ ----- Method: CoInterpreter>>cFramePointerAddress (in category 'cog jit support') -----
+ cFramePointerAddress
+ 	<api>
+ 	^self cCode: [self addressOf: CFramePointer] inSmalltalk: [self error: 'Use Cogit''s version  when simulating']!

Item was added:
+ ----- Method: CoInterpreter>>cStackPointerAddress (in category 'cog jit support') -----
+ cStackPointerAddress
+ 	<api>
+ 	^self cCode: [self addressOf: CStackPointer] inSmalltalk: [self error: 'Use Cogit''s version  when simulating']!

Item was changed:
  ----- Method: CoInterpreter>>callbackEnter: (in category 'callback support') -----
  callbackEnter: callbackID
  	"Re-enter the interpreter for executing a callback"
  	| currentCStackPointer currentCFramePointer savedReenterInterpreter
  	  wasInMachineCode calledFromMachineCode |
  	<volatile>
  	<export: true>
  	<var: #currentCStackPointer type: #'void *'>
  	<var: #currentCFramePointer type: #'void *'>
  	<var: #callbackID type: #'sqInt *'>
  	<var: #savedReenterInterpreter type: #'jmp_buf'>
  
  	"For now, do not allow a callback unless we're in a primitiveResponse"
  	(self asserta: primitiveFunctionPointer ~= 0) ifFalse:
  		[^false].
  
  	self assert: primFailCode = 0.
  
  	"Check if we've exceeded the callback depth"
  	(self asserta: jmpDepth < MaxJumpBuf) ifFalse:
  		[^false].
  	jmpDepth := jmpDepth + 1.
  
  	wasInMachineCode := self isMachineCodeFrame: framePointer.
  	calledFromMachineCode := instructionPointer <= objectMemory startOfMemory.
  
  	"Suspend the currently active process"
  	suspendedCallbacks at: jmpDepth put: self activeProcess.
  	"We need to preserve newMethod explicitly since it is not activated yet
  	and therefore no context has been created for it. If the caller primitive
  	for any reason decides to fail we need to make sure we execute the correct
  	method and not the one 'last used' in the call back"
  	suspendedMethods at: jmpDepth put: newMethod.
  	self flag: 'need to debug this properly.  Conceptually it is the right thing to do but it crashes in practice'.
  	false
  		ifTrue:
  			["Signal external semaphores since a signalSemaphoreWithIndex: request may
  			  have been issued immediately prior to this callback before the VM has any
  			  chance to do a signalExternalSemaphores in checkForEventsMayContextSwitch:"
  			 self signalExternalSemaphores.
  			 "If no process is awakened by signalExternalSemaphores then transfer
  			  to the highest priority runnable one."
  			 (suspendedCallbacks at: jmpDepth) = self activeProcess ifTrue:
  				[self transferTo: self wakeHighestPriority from: CSCallbackLeave]]
  		ifFalse:
  			[self transferTo: self wakeHighestPriority from: CSCallbackLeave].
  
  	"Typically, invoking the callback means that some semaphore has been 
  	signaled to indicate the callback. Force an interrupt check as soon as possible."
  	self forceInterruptCheck.
  
  	"Save the previous CStackPointers and interpreter entry jmp_buf."
+ 	currentCStackPointer := CStackPointer.
+ 	currentCFramePointer := CFramePointer.
- 	currentCStackPointer := cogit getCStackPointer.
- 	currentCFramePointer := cogit getCFramePointer.
  	self memcpy: savedReenterInterpreter asVoidPointer
  		_: reenterInterpreter
  		_: (self sizeof: #'jmp_buf').
  	cogit assertCStackWellAligned.
  	(self setjmp: (jmpBuf at: jmpDepth)) = 0 ifTrue: "Fill in callbackID"
  		[callbackID at: 0 put: jmpDepth.
  		 self enterSmalltalkExecutive.
  		 self assert: false "NOTREACHED"].
  
  	"Restore the previous CStackPointers and interpreter entry jmp_buf."
+ 	self setCFramePointer: currentCFramePointer setCStackPointer: currentCStackPointer.
- 	cogit setCStackPointer: currentCStackPointer.
- 	cogit setCFramePointer: currentCFramePointer.
  	self memcpy: reenterInterpreter
  		_: (self cCoerceSimple: savedReenterInterpreter to: #'void *')
  		_: (self sizeof: #'jmp_buf').
  
  	"Transfer back to the previous process so that caller can push result"
  	self putToSleep: self activeProcess yieldingIf: preemptionYields.
  	self transferTo: (suspendedCallbacks at: jmpDepth) from: CSCallbackLeave.
  	newMethod := suspendedMethods at: jmpDepth.	"see comment above"
  	argumentCount := self argumentCountOf: newMethod.
  	self assert: wasInMachineCode = (self isMachineCodeFrame: framePointer).
  	calledFromMachineCode
  		ifTrue:
  			[instructionPointer asUnsignedInteger >= objectMemory startOfMemory ifTrue:
  				[self iframeSavedIP: framePointer put: instructionPointer.
  				 instructionPointer := cogit ceReturnToInterpreterPC]]
  		ifFalse:
  			["Even if the context was flushed to the heap and rebuilt in transferTo:from:
  			  above it will remain an interpreted frame because the context's pc would
  			  remain a bytecode pc.  So the instructionPointer must also be a bytecode pc."
  			 self assert: (self isMachineCodeFrame: framePointer) not.
  			 self assert: instructionPointer > objectMemory startOfMemory].
  	self assert: primFailCode = 0.
  	jmpDepth := jmpDepth-1.
  	^true!

Item was added:
+ ----- Method: CoInterpreter>>checkIfCFramePointerInUse (in category 'cog jit support') -----
+ checkIfCFramePointerInUse
+ 	<api>
+ 	"Necessary because we very much want CStackPointer and CFramePointer to be static/private and grouped
+ 	 with other interpreter variables which will hence be accessed via VarBaseReg on platforms trhat have one."
+ 	^self isCFramePointerInUse: (self addressOf: CFramePointer) _: (self addressOf: CStackPointer)!

Item was changed:
  ----- Method: CoInterpreter>>divorceSomeFramesWithMachineCodePrimitiveMethod (in category 'frame access') -----
  divorceSomeFramesWithMachineCodePrimitiveMethod
  	"Divorce at most one frame (since the divorce may cause the containing
  	 page to be split) and answer whether a frame was divorced."
- 	<var: #cogMethod type: #'CogMethod *'>
  	| divorcedSome |
  	<var: #aPage type: #'StackPage *'>
  	divorcedSome := false.
  	0 to: numStackPages - 1 do:
  		[:i| | aPage |
  		aPage := stackPages stackPageAt: i.
  		(stackPages isFree: aPage) ifFalse:
  			["this to avoid assert in externalDivorceFrame:andContext:"
  			 stackPages markStackPageMostRecentlyUsed: stackPage.
  			 (self divorceAMachineCodeFrameWithMachineCodePrimitiveMethodIn: aPage) ifTrue:
  				[divorcedSome := true]]].
  	^divorcedSome!

Item was added:
+ ----- Method: CoInterpreter>>getCFramePointer (in category 'callback support') -----
+ getCFramePointer
+ 	<doNotGenerate>
+ 	^CFramePointer!

Item was added:
+ ----- Method: CoInterpreter>>getCStackPointer (in category 'callback support') -----
+ getCStackPointer
+ 	<doNotGenerate>
+ 	^CStackPointer!

Item was added:
+ ----- Method: CoInterpreter>>isCFramePointerInUse:_: (in category 'cog jit support') -----
+ isCFramePointerInUse: cFrmPtrPtr _: cStkPtrPtr
+ 	<var: 'cFrmPtrPtr' type: 'usqIntptr_t *'>
+ 	<var: 'cStkPtrPtr' type: 'usqIntptr_t *'>
+ 	<doNotGenerate>
+ 	"This must be implemented externally, e.g. in sqPlatMain.c."
+ 	^self class initializationOptions at: #isCFramePointerInUse ifAbsent: [true]!

Item was changed:
  ----- Method: CoInterpreter>>restoreCStackStateForCallbackContext: (in category 'callback support') -----
  restoreCStackStateForCallbackContext: vmCallbackContext
  	<var: #vmCallbackContext type: #'VMCallbackContext *'>
+ 	self setCFramePointer: vmCallbackContext savedCFramePointer setCStackPointer: vmCallbackContext savedCStackPointer.
- 	cogit
- 		setCStackPointer: vmCallbackContext savedCStackPointer;
- 		setCFramePointer: vmCallbackContext savedCFramePointer.
  	self memcpy: reenterInterpreter
  		_: vmCallbackContext savedReenterInterpreter asVoidPointer
  		_: (self sizeof: #'jmp_buf')!

Item was changed:
  ----- Method: CoInterpreter>>saveCStackStateForCallbackContext: (in category 'callback support') -----
  saveCStackStateForCallbackContext: vmCallbackContext
  	<var: #vmCallbackContext type: #'VMCallbackContext *'>
  	vmCallbackContext
+ 		savedCStackPointer: CStackPointer;
+ 		savedCFramePointer: CFramePointer.
- 		savedCStackPointer: cogit getCStackPointer;
- 		savedCFramePointer: cogit getCFramePointer.
  	super saveCStackStateForCallbackContext: vmCallbackContext!

Item was added:
+ ----- Method: CoInterpreter>>setCFramePointer:setCStackPointer: (in category 'callback support') -----
+ setCFramePointer: cFramePointer setCStackPointer: cStackPointer
+ 	<inline: #always>
+ 	CStackPointer := cStackPointer.
+ 	CFramePointer := cFramePointer.
+ 	self cCode: [] inSmalltalk:
+ 		[objectMemory
+ 			longAt: self inMemoryCFramePointerAddress
+ 				put: cFramePointer;
+ 			longAt: self inMemoryCStackPointerAddress
+ 				put: cStackPointer]!

Item was changed:
  ----- Method: CoInterpreterMT>>assertCStackPointersBelongToCurrentThread (in category 'simulation') -----
  assertCStackPointersBelongToCurrentThread
  	<doNotGenerate>
  	| range |
  	range := self cStackRangeForCurrentThread.
+ 	self assert: ((range includes: CStackPointer)
+ 				and: [range includes: CFramePointer])!
- 	self assert: ((range includes: cogit getCStackPointer)
- 				and: [range includes: cogit getCFramePointer])!

Item was changed:
  ----- Method: CoInterpreterMT>>assertCStackPointersBelongToCurrentVMOwner (in category 'simulation') -----
  assertCStackPointersBelongToCurrentVMOwner
  	<doNotGenerate>
  	| range |
  	range := self cStackRangeForCurrentVMOwner.
  	self assert: (range notNil "VM is owned"
+ 				and: [(range includes: CStackPointer)
+ 				and: [range includes: CFramePointer]])!
- 				and: [(range includes: cogit getCStackPointer)
- 				and: [range includes: cogit getCFramePointer]])!

Item was changed:
  ----- Method: CoInterpreterMT>>disownVM: (in category 'vm scheduling') -----
  disownVM: flags
  	"Release the VM to other threads and answer the current thread's index.
  	 Currently valid flags:
  		DisownVMLockOutFullGC	- prevent fullGCs while this thread disowns the VM
  		DisownVMForFFICall			- informs the VM that it is entering an FFI call
  		DisownVMForThreading		- informs the VM that it is entering an FFI call etc during which threading should be permitted
  		OwnVMForeignThreadFlag	- indicates lowest-level entry from a foreign thread
  									- not to be used explicitly by clients
  									- only set by ownVMFromUnidentifiedThread
  		VMAlreadyOwnedHenceDoNotDisown
  									- indicates an ownVM from a callback was made when
  									  the vm was still owned.
  									- not to be used explicitly by clients
  									- only set by ownVMFromUnidentifiedThread
  
  	 This is the entry-point for plugins and primitives that wish to release the VM while
  	 performing some operation that may potentially block, and for callbacks returning
  	 back to some blocking operation.  If this thread does not reclaim the VM before-
  	 hand then when the next heartbeat occurs the thread manager will schedule a
  	 thread to acquire the VM which may start running the VM in place of this thread.
  
  	 N.B. Most of the state needed to resume after preemption is set in preemptDisowningThread."
  	<api>
  	<inline: false>
  	| vmThread result |
  	<var: #vmThread type: #'CogVMThread *'>
  	self assert: self successful.
  	cogit recordEventTrace ifTrue:
  		[self recordTrace: TraceDisownVM thing: (objectMemory integerObjectOf: flags) source: 0].
  	processHasThreadId ifFalse:
  		[willNotThreadWarnCount < 10 ifTrue:
  			[self print: 'warning: VM parameter 48 indicates Process doesn''t have threadId; VM will not thread'; cr.
  			 willNotThreadWarnCount := willNotThreadWarnCount + 1]].
  	vmThread := cogThreadManager currentVMThread.
  	(flags anyMask: VMAlreadyOwnedHenceDoNotDisown) ifTrue:
  		[disowningVMThread := vmThread.
  		 vmThread state: CTMUnavailable.
  		 ^0].
  	self cCode: ''
  		inSmalltalk:
  			[| range |
  			 range := self cStackRangeForThreadIndex: vmThread index.
+ 			 self assert: (range includes: CStackPointer).
+ 			 self assert: (range includes: CFramePointer)].
- 			 self assert: (range includes: cogit getCStackPointer).
- 			 self assert: (range includes: cogit getCFramePointer)].
  	(flags anyMask: DisownVMForProcessorRelinquish) ifTrue:
  		[| proc |
  		 (proc := objectMemory splObj: foreignCallbackProcessSlot) ~= objectMemory nilObject ifTrue:
  			[foreignCallbackPriority := self quickFetchInteger: PriorityIndex ofObject: proc].
  		 relinquishing := true.
  		 self sqLowLevelMFence].
  	(flags anyMask: DisownVMLockOutFullGC) ifTrue:
  		[objectMemory incrementFullGCLock].
  	(noThreadingOfGUIThread and: [self inGUIThread]) ifTrue:
  		[^vmThread index
  		 + LockGUIThreadFlag
  		 + (activeProcessAffined ifTrue: [0] ifFalse: [ProcessUnaffinedOnDisown])
  		 + (flags << DisownFlagsShift)].
  	disownCount := disownCount + 1.
  	disowningVMThread := vmThread.
  	"self cr; cr; print: 'disownVM  Csp: '; printHex: vmThread cStackPointer; cr.
  	(0 to: 16 by: 4) do:
  		[:offset|
  		self print: ' *(esp+'; printNum: offset; print: ': '; printHex: (stackPages longAt: cogit processor sp + offset); cr].
  	cogit processor printIntegerRegistersOn: Transcript."
  
  	"OwnVMForeignThreadFlag indicates lowest-level of entry by a foreign
  	 thread. If that's where we are then release the vmThread.  Otherwise
  	 indicate the vmThread is off doing something outside of the VM."
  	(flags anyMask: OwnVMForeignThreadFlag)
  		ifTrue:
  			["I don't think this is quite right.  Josh's use case is creating some foreign thread and then registering
  			 it with the VM. That's not the same as binding a process to a foreign thread given that the foreign
  			 callback process is about to terminate anyway (it is returning from a callback here).  So do we need
  			 an additional concept, that of a vmThread being either of the set known to the VM or floating?"
  			self flag: 'issue with registering foreign threads with the VM'.
  			(self isBoundProcess: self activeProcess) ifFalse:
  				[cogThreadManager unregisterVMThread: vmThread]]
  		ifFalse: [vmThread state: CTMUnavailable].
  	result := vmThread index
  				+ (activeProcessAffined ifTrue: [0] ifFalse: [ProcessUnaffinedOnDisown])
  				+ (flags << DisownFlagsShift).
  	cogThreadManager releaseVM.
  	^result!

Item was changed:
  ----- Method: CoInterpreterMT>>ownVM: (in category 'vm scheduling') -----
  ownVM: threadIndexAndFlags
  	<api>
  	<inline: false>
  	"This is the entry-point for plugins and primitives that wish to reacquire the VM after having
  	 released it via disownVM or callbacks that want to acquire it without knowing their ownership
  	 status.  This call will block until the VM is owned by the current thread or an error occurs.
  	 The argument should be the value answered by disownVM, or 0 for callbacks that don't know
  	 if they have disowned or not.  This is both an optimization to avoid having to query thread-
  	 local storage for the current thread's index (since it can easily keep it in some local variable),
  	 and a record of when an unbound process becomes affined to a thread for the dynamic
  	 extent of some operation.
  
  	 Answer 0 if the current thread is known to the VM.
  	 Answer 1 if the current thread is unknown to the VM and takes ownership.
  	 Answer -1 if the current thread is unknown to the VM and fails to take ownership."
  	| threadIndex flags vmThread myProc activeProc sched |
  	<var: #vmThread type: #'CogVMThread *'>
  	threadIndexAndFlags = 0 ifTrue:
  		[^self ownVMFromUnidentifiedThread].
  	threadIndex := threadIndexAndFlags bitAnd: ThreadIdMask.
  	flags := threadIndexAndFlags >> DisownFlagsShift.
  	(flags anyMask: DisownVMForProcessorRelinquish) ifTrue:
  		[relinquishing := false.
  		 self sqLowLevelMFence].
  	(threadIndexAndFlags anyMask: LockGUIThreadFlag) ifTrue:
  		[self assert: (noThreadingOfGUIThread and: [self inGUIThread]).
  		 self assert: disowningVMThread = nil.
  		 (flags anyMask: DisownVMLockOutFullGC) ifTrue:
  			[objectMemory decrementFullGCLock].
  		 cogit recordEventTrace ifTrue:
  			[self recordTrace: TraceOwnVM thing: ConstZero source: 0].
  		 ^0].
  
  	vmThread := cogThreadManager acquireVMFor: threadIndex.
  	disownCount := disownCount - 1.
  
  	(flags anyMask: DisownVMLockOutFullGC) ifTrue:
  		[objectMemory decrementFullGCLock].
  	disowningVMThread notNil ifTrue:
  		[vmThread = disowningVMThread ifTrue:
  			[self cCode: ''
  				inSmalltalk:
  					[| range |
  					 range := self cStackRangeForThreadIndex: threadIndex.
+ 					 self assert: (range includes: CStackPointer).
+ 					 self assert: (range includes: CFramePointer)].
- 					 self assert: (range includes: cogit getCStackPointer).
- 					 self assert: (range includes: cogit getCFramePointer)].
  			 self assert: self successful.
  			 self assert: (objectMemory fetchPointer: MyListIndex ofObject: self activeProcess) = objectMemory nilObject.
  			 disowningVMThread := nil.
  			 cogit recordEventTrace ifTrue:
  				[self recordTrace: TraceOwnVM thing: ConstOne source: 0].
  			 ^0].  "if not preempted we're done."
  		self preemptDisowningThread].
  	"We've been preempted; we must restore state and update the threadId
  	 in our process, and may have to put the active process to sleep."
  	sched := self schedulerPointer.
  	activeProc := objectMemory fetchPointer: ActiveProcessIndex ofObject: sched.
  	(threadIndexAndFlags anyMask: OwnVMForeignThreadFlag)
  		ifTrue:
  			[self assert: foreignCallbackProcessSlot == ForeignCallbackProcess.
  			 myProc := objectMemory splObj: foreignCallbackProcessSlot.
  			self assert: myProc ~= objectMemory nilObject.
  			objectMemory splObj: foreignCallbackProcessSlot put: objectMemory nilObject]
  		ifFalse: [myProc := cogThreadManager popAWOLProcess: vmThread].
  	self assert: activeProc ~= myProc.
  	(activeProc ~= objectMemory nilObject
  	 and: [(objectMemory fetchPointer: MyListIndex ofObject: activeProc) = objectMemory nilObject]) ifTrue:
  		[self putToSleep: activeProc yieldingIf: preemptionYields].
  	self assert: (objectMemory fetchPointer: MyListIndex ofObject: myProc) = (objectMemory splObj: ProcessInExternalCodeTag).
  	objectMemory
  		storePointer: ActiveProcessIndex ofObject: sched withValue: myProc;
  		storePointerUnchecked: MyListIndex ofObject: myProc withValue: objectMemory nilObject.
  	"Only unaffine if the process was affined at this level and did not become bound in the interim."
  	((threadIndexAndFlags anyMask: ProcessUnaffinedOnDisown)
  	 and: [(self isBoundProcess: myProc) not]) ifTrue:
  		[self setOwnerIndexOfProcess: myProc to: 0 bind: false].
  	self initPrimCall.
  	self externalSetStackPageAndPointersForSuspendedContextOfProcess: myProc.
  	"If this primitive is called from machine code maintain the invariant that the return pc
  	 of an interpreter callee calling a machine code caller is ceReturnToInterpreterPC."
  	(vmThread inMachineCode
  	 and: [instructionPointer >= objectMemory startOfMemory]) ifTrue:
  		[self iframeSavedIP: framePointer put: instructionPointer.
  		 instructionPointer := cogit ceReturnToInterpreterPC].
  	newMethod := vmThread newMethodOrNull.
  	argumentCount := vmThread argumentCount.
  	self cCode:
  			[self memcpy: reenterInterpreter
  				_: vmThread reenterInterpreter
  				_: (self sizeof: #'jmp_buf')]
  		inSmalltalk:
  			[reenterInterpreter := vmThread reenterInterpreter].
  	vmThread newMethodOrNull: nil.
  	self cCode: ''
  		inSmalltalk:
  			[| range |
  			 range := self cStackRangeForThreadIndex: threadIndex.
  			 self assert: (range includes: vmThread cStackPointer).
  			 self assert: (range includes: vmThread cFramePointer)].
+ 	self setCFramePointer: vmThread cFramePointer setCStackPointer: vmThread cStackPointer.
- 	cogit setCStackPointer: vmThread cStackPointer.
- 	cogit setCFramePointer: vmThread cFramePointer.
  	self assert: newMethod ~~ nil.
  	cogit recordEventTrace ifTrue:
  		[self recordTrace: TraceOwnVM thing: ConstTwo source: 0].
  	^threadIndexAndFlags bitAnd: OwnVMForeignThreadFlag!

Item was changed:
  ----- Method: CoInterpreterMT>>preemptDisowningThread (in category 'vm scheduling') -----
  preemptDisowningThread
  	"Set the relevant state for disowningVMThread so that it can resume after
  	 being preempted and set disowningVMThread to nil to indicate preemption.
  
  	 N.B.  This should only be sent from checkPreemptionOfDisowningThread.
  
  	 There are essentially four things to do.
  	 a)	save the VM's notion of the current C stack pointers; these are pointers
  		into a thread's stack and must be saved and restored in thread switch.
  	 b)	save the VM's notion of the current Smalltalk execution point.  This is
  		simply the suspend half of a process switch that saves the current context
  		in the current process.
  	 c)	add the process to the thread's set of AWOL processes so that the scheduler
  		won't try to run the process while the thread has disowned the VM.
  	 d)	save the in-primitive VM state, newMethod and argumentCount
  
  	 ownVM: will restore the VM context as of disownVM: from the above when it
  	 finds it has been preempted."
  
  	| activeProc activeContext preemptedThread |
  	<var: #preemptedThread type: #'CogVMThread *'>
  	<inline: false>
  	self assert: disowningVMThread notNil.
  	self assert: (disowningVMThread state = CTMUnavailable
  				or: [disowningVMThread state = CTMWantingOwnership]).
  	self cCode: ''
  		inSmalltalk:
  			[| range |
  			 range := self cStackRangeForThreadIndex: disowningVMThread index.
+ 			 self assert: (range includes: CStackPointer).
+ 			 self assert: (range includes: CFramePointer)].
- 			 self assert: (range includes: cogit getCStackPointer).
- 			 self assert: (range includes: cogit getCFramePointer)].
  	cogit recordEventTrace ifTrue:
  		[self recordTrace: TracePreemptDisowningThread
  			thing: (objectMemory integerObjectOf: disowningVMThread index)
  			source: 0].
+ 	disowningVMThread cStackPointer: CStackPointer.
+ 	disowningVMThread cFramePointer: CFramePointer.
- 	disowningVMThread cStackPointer: cogit getCStackPointer.
- 	disowningVMThread cFramePointer: cogit getCFramePointer.
  	activeProc := self activeProcess.
  	self assert: (objectMemory fetchPointer: MyListIndex ofObject: activeProc) = objectMemory nilObject.
  	objectMemory
  		storePointer: MyListIndex
  		ofObject: activeProc
  		withValue: (objectMemory splObj: ProcessInExternalCodeTag).
  	"The instructionPointer must be pushed because the convention for inactive stack pages is that the
  	 instructionPointer is top of stack.  We need to know if this primitive is called from machine code
  	 because the invariant that the return pc of an interpreter callee calling a machine code caller is
  	 ceReturnToInterpreterPC must be maintained."
  	self push: instructionPointer.
  	self externalWriteBackHeadFramePointers.
  	activeContext := self ensureFrameIsMarried: framePointer SP: stackPointer.
  	objectMemory
  		storePointer: SuspendedContextIndex
  		ofObject: activeProc
  		withValue: activeContext.
  	"Since pushing the awol process may realloc disowningVMThread we need to reassign.
  	 But since we're going to nil disowningVMThread anyway we can assign to a local."
  	preemptedThread := cogThreadManager pushAWOLProcess: activeProc on: disowningVMThread.
  	disowningVMThread := nil.
  	preemptedThread priority: (self quickFetchInteger: PriorityIndex ofObject: activeProc).
  	(self ownerIndexOfProcess: activeProc) = 0
  		ifTrue: [self setOwnerIndexOfProcess: activeProc to: preemptedThread index bind: false]
  		ifFalse: [self assert: (self ownerIndexOfProcess: activeProc) = preemptedThread index].
  	preemptedThread
  		newMethodOrNull: newMethod;
  		argumentCount: argumentCount;
  		inMachineCode: instructionPointer asUnsignedInteger <= objectMemory startOfMemory.
  	self cCode:
  			[self memcpy: preemptedThread reenterInterpreter
  				_: reenterInterpreter
  				_: (self sizeof: #'jmp_buf')]
  		inSmalltalk:
  			[preemptedThread reenterInterpreter: reenterInterpreter]!

Item was changed:
  ----- Method: CoInterpreterMT>>primitiveRelinquishProcessor (in category 'I/O primitives') -----
  primitiveRelinquishProcessor
  	"Relinquish the processor for up to the given number of microseconds.
  	 The exact behavior of this primitive is platform dependent.
  	 Override to check for waiting threads."
  
  	| microSecs threadIndexAndFlags currentCStackPointer currentCFramePointer savedReenterInterpreter |
  	<var: #currentCStackPointer type: #'void *'>
  	<var: #currentCFramePointer type: #'void *'>
  	<var: #savedReenterInterpreter type: #'jmp_buf'>
  	microSecs := self stackTop.
  	(objectMemory isIntegerObject: microSecs) ifFalse:
  		[^self primitiveFail].
  	self assert: (objectMemory fetchPointer: MyListIndex ofObject: self activeProcess) = objectMemory nilObject.
  	self assert: relinquishing not.
  	"DO NOT allow relinquishing the processor while we are profiling since this
  	 may skew the time base for our measures (it may reduce processor speed etc).
  	 Instead we go full speed, therefore measuring the precise time we spend in the
  	 inner idle loop as a busy loop."
  	nextProfileTick = 0 ifTrue:
  		"Presumably we have nothing to do; this primitive is typically called from the
  		 background process. So we should /not/ try and activate any threads in the
  		 pool; they will waste cycles finding there is no runnable process, and will
  		 cause a VM abort if no runnable process is found.  But we /do/ want to allow
  		 FFI calls that have completed, or callbacks a chance to get into the VM; they
  		 do have something to do.  DisownVMForProcessorRelinquish indicates this."
+ 		[currentCStackPointer := CStackPointer.
+ 		 currentCFramePointer := CFramePointer.
- 		[currentCStackPointer := cogit getCStackPointer.
- 		 currentCFramePointer := cogit getCFramePointer.
  		 self cCode:
  			[self memcpy: savedReenterInterpreter asVoidPointer
  				_: reenterInterpreter
  				_: (self sizeof: #'jmp_buf')].
  		 threadIndexAndFlags := self disownVM: DisownVMForProcessorRelinquish.
  		 self assert: relinquishing.
  		 self ioRelinquishProcessorForMicroseconds: (objectMemory integerValueOf: microSecs).
  		 self assert: relinquishing.
  		 self ownVM: threadIndexAndFlags.
  		 self assert: relinquishing not.
  		 self assert: cogThreadManager currentVMThread state = CTMAssignableOrInVM.
+ 		 self assert: currentCStackPointer = CStackPointer.
+ 		 self assert: currentCFramePointer = CFramePointer.
- 		 self assert: currentCStackPointer = cogit getCStackPointer.
- 		 self assert: currentCFramePointer = cogit getCFramePointer.
  		 self cCode:
  			[self assert: (self mem: (self cCoerceSimple: savedReenterInterpreter to: #'void *')
  						cm: reenterInterpreter
  						p: (self sizeof: #'jmp_buf')) = 0]].
  	self assert: (objectMemory fetchPointer: MyListIndex ofObject: self activeProcess) = objectMemory nilObject.
  	self pop: 1  "microSecs; leave rcvr on stack"!

Item was changed:
  ----- Method: CoInterpreterMT>>returnToSchedulingLoopAndReleaseVMOrWakeThread:source: (in category 'process primitive support') -----
  returnToSchedulingLoopAndReleaseVMOrWakeThread: vmThread source: source
  	| savedReenterInterpreter |
  	<var: #savedReenterInterpreter type: #'jmp_buf'>
  	<var: #vmThread type: #'CogVMThread *'>
  	<inline: false>
  	self cCode:
  			[self flag: 'this is just for debugging.  Note the current C stack pointers'.
  			 cogThreadManager currentVMThread
+ 				cStackPointer: CStackPointer;
+ 				cFramePointer: CFramePointer]
- 				cStackPointer: cogit getCStackPointer;
- 				cFramePointer: cogit getCFramePointer]
  		inSmalltalk:
  			[| range |
  			 range := self cStackRangeForThreadIndex: cogThreadManager getVMOwner.
+ 			 self assert: (range includes: CStackPointer).
+ 			 self assert: (range includes: CFramePointer)].
- 			 self assert: (range includes: cogit getCStackPointer).
- 			 self assert: (range includes: cogit getCFramePointer)].
  	"We must use a copy of reenterInterpreter since we're giving up the VM to another vmThread."
  	self cCode:
  			[self memcpy: savedReenterInterpreter asVoidPointer
  				_: reenterInterpreter
  				_: (self sizeof: #'jmp_buf')]
  		inSmalltalk:
  			[savedReenterInterpreter := reenterInterpreter].
  	self recordThreadSwitchTo: (vmThread ifNotNil: [vmThread index] ifNil: [0]) source: source.
  	vmThread
  		ifNotNil: [cogThreadManager wakeVMThreadFor: vmThread index]
  		ifNil: [cogThreadManager releaseVM].
  	"2 implies returning to the threadSchedulingLoop."
  	self siglong: savedReenterInterpreter jmp: ReturnToThreadSchedulingLoop!

Item was changed:
  ----- Method: CogARMCompiler>>genMarshallNArgs:arg:arg:arg:arg: (in category 'abi') -----
  genMarshallNArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3
  	"Generate the code to pass up to four arguments in a C run-time call.  Hack: each argument is
  	 either a negative number, which encodes a constant, or a non-negative number, that of a register.
  
  	 Run-time calls have no more than four arguments, so chosen so that on ARM, where in its C ABI the
  	 first four integer arguments are passed in registers, all arguments can be passed in registers.  We
  	 defer to the back end to generate this code not so much that the back end knows whether it uses
  	 the stack or registers to pass arguments (it does, but...). In fact we defer for an extremely evil reason.
  	 Doing so allows the x64 (where up to 6 args are passed) to assign the register arguments in an order
+ 	 that allows some of the argument registers to be used for specific abstract registers, specifically
- 	 that allows some of the argument registers to be used for specific abstract  registers, specifically
  	 ReceiverResultReg and ClassReg.  This is evil, evil, evil, but also it's really nice to keep using the old
  	 register assignments the original author has grown accustomed to."
  	<inline: true>
  	numArgs = 0 ifTrue: [^self].
+ 	"Avoid arg regs being overwritten before they are read."
+ 	numArgs > 1 ifTrue:
+ 		[((cogit isTrampolineArgConstant: regOrConst1) not
+ 		   and: [regOrConst1 = CArg0Reg]) ifTrue:
+ 			[cogit MoveR: regOrConst1 R: Extra0Reg.
+ 			 ^self genMarshallNArgs: numArgs arg: regOrConst0 arg: Extra0Reg arg: regOrConst2 arg: regOrConst3].
+ 		 numArgs > 2 ifTrue:
+ 			[((cogit isTrampolineArgConstant: regOrConst2) not
+ 			   and: [regOrConst2 = CArg0Reg or: [regOrConst2 = CArg1Reg]]) ifTrue:
+ 				[cogit MoveR: regOrConst2 R: Extra1Reg.
+ 				 ^self genMarshallNArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: Extra1Reg arg: regOrConst3].
+ 			 numArgs > 3 ifTrue:
+ 				[((cogit isTrampolineArgConstant: regOrConst3) not
+ 				   and: [regOrConst3 = CArg0Reg or: [regOrConst3 = CArg1Reg or: [regOrConst3 = CArg2Reg]]]) ifTrue:
+ 					[cogit MoveR: regOrConst3 R: Extra2Reg.
+ 					 ^self genMarshallNArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: Extra2Reg]]]].
  	(cogit isTrampolineArgConstant: regOrConst0)
  		ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst0) R: CArg0Reg]
  		ifFalse: [cogit MoveR: regOrConst0 R: CArg0Reg].
  	numArgs = 1 ifTrue: [^self].
  	(cogit isTrampolineArgConstant: regOrConst1)
  		ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst1) R: CArg1Reg]
  		ifFalse: [cogit MoveR: regOrConst1 R: CArg1Reg].
  	numArgs = 2 ifTrue: [^self].
  	(cogit isTrampolineArgConstant: regOrConst2)
  		ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst2) R: CArg2Reg]
  		ifFalse: [cogit MoveR: regOrConst2 R: CArg2Reg].
  	numArgs = 3 ifTrue: [^self].
  	(cogit isTrampolineArgConstant: regOrConst3)
  		ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst3) R: CArg3Reg]
  		ifFalse: [cogit MoveR: regOrConst3 R: CArg3Reg]!

Item was removed:
- ----- Method: CogInLineLiteralsX64Compiler>>wantsNearAddressFor: (in category 'simulation') -----
- wantsNearAddressFor: anObject
- 	"A hack hook to allow x64 to address CStackPointer and CFramePointer relative to VarBaseReg.
- 	 With this regime we do _not_ want to access via VarBasereg but instead test the
- 	 MoveAwR & MoveRAw hack fetch/storing through RAX."
- 	<doNotGenerate>
- 	^false!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genGetClassObjectOf:into:scratchReg:mayBeAForwarder: (in category 'compile abstract instructions') -----
+ genGetClassObjectOf: instReg into: destReg scratchReg: scratchReg mayBeAForwarder: mayBeForwarder
- genGetClassObjectOf: instReg into: destReg scratchReg: scratchReg mayBeAForwarder: mayBeAForwarder
  	"Fetch the instance's class into destReg.  If the instance is not the receiver and is forwarded, follow forwarding."
  	| jumpIsImm jumpNotForwarded loop |
  	<var: #jumpIsImm type: #'AbstractInstruction *'>
  	<var: #jumpNotForwarded type: #'AbstractInstruction *'>
  	<var: #loop type: #'AbstractInstruction *'>
  	(instReg = destReg or: [instReg = scratchReg or: [destReg = scratchReg]]) ifTrue:
  		[^BadRegisterSet].
  	loop := cogit MoveR: instReg R: scratchReg.
  	cogit AndCq: objectMemory tagMask R: scratchReg.
  	jumpIsImm := cogit JumpNonZero: 0.
  	self flag: #endianness.
  	"Get least significant half of header word in destReg"
  	cogit MoveMw: 0 r: instReg R: scratchReg.
  	"mask off class index"
  	cogit AndCq: objectMemory classIndexMask R: scratchReg.
+ 	mayBeForwarder ifTrue:
- 	mayBeAForwarder ifTrue:
  		["if it is forwarded..."
  		cogit CmpCq: objectMemory isForwardedObjectClassIndexPun R: scratchReg.
  		jumpNotForwarded := cogit JumpNonZero: 0.
  		"...follow the forwarding pointer and loop to fetch its classIndex"
  		cogit MoveMw: objectMemory baseHeaderSize r: instReg R: instReg.
  		cogit Jump: loop.
  		jumpNotForwarded jmpTarget: cogit Label].
  	jumpIsImm jmpTarget:
  	(cogit MoveR: scratchReg R: destReg).
  	scratchReg = TempReg
  		ifTrue:
  			[cogit PushR: instReg.
  			 self genGetClassObjectOfClassIndex: destReg into: instReg scratchReg: TempReg.
  			 cogit MoveR: instReg R: destReg.
  			 cogit PopR: instReg]
  		ifFalse:
  			[self genGetClassObjectOfClassIndex: destReg into: scratchReg scratchReg: TempReg.
  			 cogit MoveR: scratchReg R: destReg].
  	^0!

Item was changed:
  ----- Method: CogVMSimulator>>utilitiesMenu: (in category 'UI') -----
  utilitiesMenu: aMenuMorph
  	aMenuMorph
  		add: 'toggle transcript' action: #toggleTranscript;
  		add: 'clone VM' action: #cloneSimulationWindow;
  		addLine;
  		add: 'print ext head frame' action: #printExternalHeadFrame;
  		add: 'print int head frame' action: #printHeadFrame;
  		add: 'print mc/cog head frame' action: [self printFrame: cogit processor fp WithSP: cogit processor sp];
  		add: 'short print ext head frame & callers' action: [self shortPrintFrameAndCallers: framePointer];
  		add: 'short print int head frame & callers' action: [self shortPrintFrameAndCallers: localFP];
  		add: 'short print mc/cog head frame & callers' action: [self shortPrintFrameAndCallers: cogit processor fp];
  		add: 'long print ext head frame & callers' action: [self printFrameAndCallers: framePointer SP: stackPointer];
  		add: 'long print int head frame & callers' action: [self printFrameAndCallers: localFP SP: localSP];
  		add: 'long print mc/cog head frame & callers' action: [self printFrameAndCallers: cogit processor fp SP: cogit processor sp];
  		add: 'print frame...' action: [(self promptHex: 'print frame') ifNotNil: [:fp| self printFrame: fp]];
  		add: 'print call stack' action: #printCallStack;
  		add: 'print stack call stack' action: #printStackCallStack;
  		add: 'print stack call stack of...' action: [(self promptHex: 'frame') ifNotNil: [:fp| self printStackCallStackOf: fp]];
  		add: 'print call stack of...' action: [(self promptHex: 'context or process oop') ifNotNil: [:obj| self printCallStackOf: obj]];
  		add: 'print call stack of frame...' action: [(self promptHex: 'frame') ifNotNil: [:fp| self printCallStackFP: fp]];
  		add: 'print all stacks' action: #printAllStacks;
  		add: 'write back local ptrs' action: [stackPointer := localSP. framePointer := localFP. instructionPointer := localIP.
  											self writeBackHeadFramePointers];
  		add: 'write back mc ptrs' action: [stackPointer := cogit processor sp. framePointer := cogit processor fp. instructionPointer := cogit processor pc.
  											self externalWriteBackHeadFramePointers];
  		addLine;
+ 		add: 'print rump C stack' action: [objectMemory printMemoryFrom: cogit processor sp to: CFramePointer];
- 		add: 'print rump C stack' action: [objectMemory printMemoryFrom: cogit processor sp to: cogit getCStackPointer];
  		add: 'print registers' action: [cogit processor printRegistersOn: transcript];
  		add: 'print register map' action: [cogit printRegisterMapOn: transcript];
  		add: 'disassemble method/trampoline...' action: [(self promptHex: 'pc') ifNotNil: [:pc| cogit disassembleCodeAt: pc]];
  		add: 'disassemble method/trampoline at pc' action:
  			[cogit disassembleCodeAt: (((cogit codeEntryFor: cogit processor pc) isNil
  										  and: [(cogit methodZone methodFor: cogit processor pc) = 0])
  											ifTrue: [instructionPointer]
  											ifFalse: [cogit processor pc])];
  		add: 'disassemble ext head frame method' action: [cogit disassembleMethod: (self frameMethod: framePointer)];
  		add: 'print oop...' action: [(self promptHex: 'print oop') ifNotNil: [:oop| self printOop: oop]];
  		add: 'long print oop...' action: [(self promptHex: 'print oop') ifNotNil: [:oop| self longPrintOop: oop]];
  		add: 'print context...' action: [(self promptHex: 'print context') ifNotNil: [:oop| self printContext: oop]];
  		add: 'symbolic method...' action: [(self promptHex: 'method bytecodes') ifNotNil: [:oop| self symbolicMethod: oop]];
  		addLine;
  		add: 'inspect object memory' target: objectMemory action: #inspect;
  		add: 'run leak checker' action: [Cursor execute showWhile: [self runLeakChecker]];
  		add: 'inspect cointerpreter' action: #inspect;
  		add: 'inspect cogit' target: cogit action: #inspect;
  		add: 'inspect method zone' target: cogit methodZone action: #inspect.
  	self isThreadedVM ifTrue:
  		[aMenuMorph add: 'inspect thread manager' target: self threadManager action: #inspect].
  	aMenuMorph
  		addLine;
  		add: 'print cog methods' target: cogMethodZone action: #printCogMethods;
  		add: 'print cog methods with prim...' action:
  			[(self promptNum: 'prim index') ifNotNil: [:pix| cogMethodZone printCogMethodsWithPrimitive: pix]];
  		add: 'print cog methods with selector...' action:
  			[|s| s := UIManager default request: 'selector'.
  			s notEmpty ifTrue:
  				[s = 'nil' ifTrue: [s := nil].
  				 cogMethodZone methodsDo:
  					[:m|
  					(s ifNil: [m selector = objectMemory nilObject]
  					 ifNotNil: [(objectMemory numBytesOf: m selector) = s size
  							and: [(self strncmp: s
  											_: (m selector + objectMemory baseHeaderSize)
  											_: (objectMemory numBytesOf: m selector)) = 0]]) ifTrue:
  						[cogit printCogMethod: m]]]];
  		add: 'print cog methods with method...' action:
  			[(self promptHex: 'method') ifNotNil: [:methodOop| cogMethodZone printCogMethodsWithMethod: methodOop]];
  		add: 'print cog method for...' action: [(self promptHex: 'pc') ifNotNil: [:pc| cogit printCogMethodFor: pc]];
  		add: 'print cog method header for...' action: [(self promptHex: 'pc') ifNotNil: [:pc| cogit printCogMethodHeaderFor: pc]];
  		add: 'print trampoline table' target: cogit action: #printTrampolineTable;
  		add: 'print prim trace log' action: #dumpPrimTraceLog;
  		add: 'report recent instructions' target: cogit action: #reportLastNInstructions;
  		add: (cogit printRegisters
  				ifTrue: ['no print registers each instruction']
  				ifFalse: ['print registers each instruction'])
  			action: [cogit printRegisters: cogit printRegisters not];
  		add: (cogit printInstructions
  				ifTrue: ['no print instructions each instruction']
  				ifFalse: ['print instructions each instruction'])
  			action: [cogit printInstructions: cogit printInstructions not];
  		addLine;
  		add: (cogit singleStep
  				ifTrue: ['no single step']
  				ifFalse: ['single step'])
  			action: [cogit singleStep: cogit singleStep not];
  		add: 'click step' action: [cogit setClickStepBreakBlock];
  		add: 'set break pc', cogit breakPC menuPrompt, '...-ve to disable or remove' action: [cogit promptForBreakPC];
  		add: 'set break count...' action: [|s| s := UIManager default request: 'break count (dec)'.
  											s notEmpty ifTrue: [breakCount := Integer readFrom: s readStream]];
  		add: 'set break selector...' action: [|s| s := UIManager default request: 'break selector (MNU:foo for MNU)'.
  											s notEmpty ifTrue:
  												[(s size > 4 and: [s beginsWith: 'MNU:'])
  													ifTrue: [self setBreakMNUSelector: (s allButFirst: 4)]
  													ifFalse: [self setBreakSelector: s]]];
  		add: 'set break block...' action: [|s| s := UIManager default request: 'break block' initialAnswer: '[:theCogit| false]'.
  											s notEmpty ifTrue: [self setBreakBlockFromString: s]];
  		add: 'set cogit break method...' action: [(self promptHex: 'cogit breakMethod') ifNotNil: [:bm| cogit setBreakMethod: bm]];
  		add: (printBytecodeAtEachStep
  				ifTrue: ['no print bytecode each bytecode']
  				ifFalse: ['print bytecode each bytecode'])
  			action: [self ensureDebugAtEachStepBlock.
  					printBytecodeAtEachStep := printBytecodeAtEachStep not];
  		add: (printFrameAtEachStep
  				ifTrue: ['no print frame each bytecode']
  				ifFalse: ['print frame each bytecode'])
  			action: [self ensureDebugAtEachStepBlock.
  					printFrameAtEachStep := printFrameAtEachStep not].
  	^aMenuMorph!

Item was changed:
  CogClass subclass: #Cogit
+ 	instanceVariableNames: 'coInterpreter objectMemory objectRepresentation processor threadManager methodZone methodZoneBase codeBase minValidCallAddress lastNInstructions simulatedAddresses simulatedTrampolines simulatedVariableGetters simulatedVariableSetters printRegisters printInstructions compilationTrace clickConfirm breakPC breakBlock singleStep guardPageSize traceFlags traceStores breakMethod methodObj enumeratingCogMethod methodHeader initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent hasMovableLiteral primitiveIndex backEnd literalsManager postCompileHook methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry fullBlockEntry cbEntryOffset fullBlockNoContextSwitchEntry cbNoSwitchEntryOffset picMNUAbort picInterpretAbort endCPICCase0 endCPICCase1 firstCPICCaseOffs
 et cPICCaseSize cPICEndSize closedPICSize openPICSize fixups abstractOpcodes generatorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceReapAndResetErrorCodeTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceEnclosingObjectTrampoline ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetFP ceGetSP ceCa
 ptureCStackPointers ordinarySendTrampolines superSendTrampolines directedSuperSendTrampolines directedSuperBindingSendTrampolines dynamicSuperSendTrampolines outerSendTrampolines selfSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner extA extB numExtB tempOop numIRCs indexOfIRC theIRCs receiverTags implicitReceiverSendTrampolines cogMethodSurrogateClass cogBlockMethodSurrogateClass nsSendCacheSurrogateClass cPICPrototype cPICEndOfCodeOffset cPICEndOfCodeLabel ceMallocTrampoline ceFreeTrampoline ceFFICalloutTrampoline debugBytecodePointers debugOpcodeIndices disassemblingMethod cogConstituentIndex directedSendUsesBinding ceCheckLZCNTFunction'
- 	instanceVariableNames: 'coInterpreter objectMemory objectRepresentation processor threadManager methodZone methodZoneBase codeBase minValidCallAddress lastNInstructions simulatedAddresses simulatedTrampolines simulatedVariableGetters simulatedVariableSetters printRegisters printInstructions compilationTrace clickConfirm breakPC breakBlock singleStep guardPageSize traceFlags traceStores breakMethod methodObj enumeratingCogMethod methodHeader initialPC endPC methodOrBlockNumArgs inBlock needsFrame hasYoungReferent hasMovableLiteral primitiveIndex backEnd literalsManager postCompileHook methodLabel stackCheckLabel blockEntryLabel blockEntryNoContextSwitch blockNoContextSwitchOffset stackOverflowCall sendMiss missOffset entryPointMask checkedEntryAlignment uncheckedEntryAlignment cmEntryOffset entry cmNoCheckEntryOffset noCheckEntry fullBlockEntry cbEntryOffset fullBlockNoContextSwitchEntry cbNoSwitchEntryOffset picMNUAbort picInterpretAbort endCPICCase0 endCPICCase1 firstCPICCaseOffs
 et cPICCaseSize cPICEndSize closedPICSize openPICSize fixups abstractOpcodes generatorTable byte0 byte1 byte2 byte3 bytecodePC bytecodeSetOffset opcodeIndex numAbstractOpcodes blockStarts blockCount labelCounter cStackAlignment expectedSPAlignment expectedFPAlignment codeModified maxLitIndex ceMethodAbortTrampoline cePICAbortTrampoline ceCheckForInterruptTrampoline ceCPICMissTrampoline ceReturnToInterpreterTrampoline ceBaseFrameReturnTrampoline ceReapAndResetErrorCodeTrampoline ceSendMustBeBooleanAddTrueTrampoline ceSendMustBeBooleanAddFalseTrampoline ceCannotResumeTrampoline ceEnterCogCodePopReceiverReg ceCallCogCodePopReceiverReg ceCallCogCodePopReceiverAndClassRegs cePrimReturnEnterCogCode cePrimReturnEnterCogCodeProfiling ceNonLocalReturnTrampoline ceFetchContextInstVarTrampoline ceStoreContextInstVarTrampoline ceEnclosingObjectTrampoline ceFlushICache ceCheckFeaturesFunction ceTraceLinkedSendTrampoline ceTraceBlockActivationTrampoline ceTraceStoreTrampoline ceGetFP ceGetSP ceCa
 ptureCStackPointers ordinarySendTrampolines superSendTrampolines directedSuperSendTrampolines directedSuperBindingSendTrampolines dynamicSuperSendTrampolines outerSendTrampolines selfSendTrampolines firstSend lastSend realCEEnterCogCodePopReceiverReg realCECallCogCodePopReceiverReg realCECallCogCodePopReceiverAndClassRegs trampolineTableIndex trampolineAddresses objectReferencesInRuntime runtimeObjectRefIndex cFramePointerInUse debugPrimCallStackOffset ceTryLockVMOwner ceUnlockVMOwner extA extB numExtB tempOop numIRCs indexOfIRC theIRCs receiverTags implicitReceiverSendTrampolines cogMethodSurrogateClass cogBlockMethodSurrogateClass nsSendCacheSurrogateClass CStackPointer CFramePointer cPICPrototype cPICEndOfCodeOffset cPICEndOfCodeLabel ceMallocTrampoline ceFreeTrampoline ceFFICalloutTrampoline debugBytecodePointers debugOpcodeIndices disassemblingMethod cogConstituentIndex directedSendUsesBinding ceCheckLZCNTFunction'
  	classVariableNames: 'AltBlockCreationBytecodeSize AltFirstSpecialSelector AltNSSendIsPCAnnotated AltNumSpecialSelectors AnnotationConstantNames AnnotationShift AnnotationsWithBytecodePCs BlockCreationBytecodeSize Debug DisplacementMask DisplacementX2N EagerInstructionDecoration FirstAnnotation FirstSpecialSelector HasBytecodePC IsAbsPCReference IsAnnotationExtension IsDirectedSuperBindingSend IsDirectedSuperSend IsDisplacementX2N IsNSDynamicSuperSend IsNSImplicitReceiverSend IsNSSelfSend IsNSSendCall IsObjectReference IsRelativeCall IsSendCall IsSuperSend MapEnd MaxCPICCases MaxCompiledPrimitiveIndex MaxStackAllocSize MaxX2NDisplacement NSCClassTagIndex NSCEnclosingObjectIndex NSCNumArgsIndex NSCSelectorIndex NSCTargetIndex NSSendIsPCAnnotated NumObjRefsInRuntime NumOopsPerNSC NumSpecialSelectors NumTrampolines ProcessorClass RRRName'
  	poolDictionaries: 'CogAbstractRegisters CogCompilationConstants CogMethodConstants CogRTLOpcodes VMBasicConstants VMBytecodeConstants VMObjectIndices VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!
  
+ !Cogit commentStamp: 'eem 10/10/2019 09:40' prior: 0!
- !Cogit commentStamp: 'eem 2/25/2017 17:53' prior: 0!
  I am the code generator for the Cog VM.  My job is to produce machine code versions of methods for faster execution and to manage inline caches for faster send performance.  I can be tested in the current image using my class-side in-image compilation facilities.  e.g. try
  
  	StackToRegisterMappingCogit genAndDis: (Integer >> #benchFib)
  
  I have concrete subclasses that implement different levels of optimization:
  	SimpleStackBasedCogit is the simplest code generator.
  
  	StackToRegisterMappingCogit is the current production code generator  It defers pushing operands
  	to the stack until necessary and implements a register-based calling convention for low-arity sends.
  
  	SistaCogit is an experimental code generator with support for counting
  	conditional branches, intended to support adaptive optimization.
  
  	RegisterAllocatingCogit is an experimental code generator with support for allocating temporary variables
  	to registers. It is inended to serve as the superclass to SistaCogit once it is working.
  
  	SistaRegisterAllocatingCogit and SistaCogitClone are temporary classes that allow testing a clone of
  	SistaCogit that inherits from RegisterAllocatingCogit.  Once things work these will be merged and
  	will replace SistaCogit.
  
  coInterpreter <CoInterpreterSimulator>
  	the VM's interpreter with which I cooperate
  methodZoneManager <CogMethodZoneManager>
  	the manager of the machine code zone
  objectRepresentation <CogObjectRepresentation>
  	the object used to generate object accesses
  processor <BochsIA32Alien|?>
  	the simulator that executes the IA32/x86 machine code I generate when simulating execution in Smalltalk
  simulatedTrampolines <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap jump addresses to run-time routines used to warp from simulated machine code in to the Smalltalk run-time.
  simulatedVariableGetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap read addresses to variables in run-time objects used to allow simulated machine code to read variables in the Smalltalk run-time.
  simulatedVariableSetters <Dictionary of Integer -> MessageSend>
  	the dictionary mapping trap write addresses to variables in run-time objects used to allow simulated machine code to write variables in the Smalltalk run-time.
  printRegisters printInstructions clickConfirm <Boolean>
  	flags controlling debug printing and code simulation
  breakPC <Integer>
  	machine code pc breakpoint
- cFramePointer cStackPointer <Integer>
- 	the variables representing the C stack & frame pointers, which must change on FFI callback and return
  selectorOop <sqInt>
  	the oop of the methodObj being compiled
  methodObj <sqInt>
  	the bytecode method being compiled
  initialPC endPC <Integer>
  	the start and end pcs of the methodObj being compiled
  methodOrBlockNumArgs <Integer>
  	argument count of current method or block being compiled
  needsFrame <Boolean>
  	whether methodObj or block needs a frame to execute
  primitiveIndex <Integer>
  	primitive index of current method being compiled
  methodLabel <CogAbstractOpcode>
  	label for the method header
  blockEntryLabel <CogAbstractOpcode>
  	label for the start of the block dispatch code
  stackOverflowCall <CogAbstractOpcode>
  	label for the call of ceStackOverflow in the method prolog
  sendMissCall <CogAbstractOpcode>
  	label for the call of ceSICMiss in the method prolog
  entryOffset <Integer>
  	offset of method entry code from start (header) of method
  entry <CogAbstractOpcode>
  	label for the first instruction of the method entry code
  noCheckEntryOffset <Integer>
  	offset of the start of a method proper (after the method entry code) from start (header) of method
  noCheckEntry <CogAbstractOpcode>
  	label for the first instruction of start of a method proper
  fixups <Array of <AbstractOpcode Label | nil>>
  	the labels for forward jumps that will be fixed up when reaching the relevant bytecode.  fixups has one element per byte in methodObj's bytecode; initialPC maps to fixups[0].
  abstractOpcodes <Array of <AbstractOpcode>>
  	the code generated when compiling methodObj
  byte0 byte1 byte2 byte3 <Integer>
  	individual bytes of current bytecode being compiled in methodObj
  bytecodePointer <Integer>
  	bytecode pc (same as Smalltalk) of the current bytecode being compiled
  opcodeIndex <Integer>
  	the index of the next free entry in abstractOpcodes (this code is translated into C where OrderedCollection et al do not exist)
  numAbstractOpcodes <Integer>
  	the number of elements in abstractOpcocdes
  blockStarts <Array of <BlockStart>>
  	the starts of blocks in the current method
  blockCount
  	the index into blockStarts as they are being noted, and hence eventually the total number of blocks in the current method
  labelCounter <Integer>
  	a nicety for numbering labels not needed in the production system but probably not expensive enough to worry about
  ceStackOverflowTrampoline <Integer>
  ceSend0ArgsTrampoline <Integer>
  ceSend1ArgsTrampoline <Integer>
  ceSend2ArgsTrampoline <Integer>
  ceSendNArgsTrampoline <Integer>
  ceSendSuper0ArgsTrampoline <Integer>
  ceSendSuper1ArgsTrampoline <Integer>
  ceSendSuper2ArgsTrampoline <Integer>
  ceSendSuperNArgsTrampoline <Integer>
  ceSICMissTrampoline <Integer>
  ceCPICMissTrampoline <Integer>
  ceStoreCheckTrampoline <Integer>
  ceReturnToInterpreterTrampoline <Integer>
  ceBaseFrameReturnTrampoline <Integer>
  ceSendMustBeBooleanTrampoline <Integer>
  ceClosureCopyTrampoline <Integer>
  	the various trampolines (system-call-like jumps from machine code to the run-time).
  	See Cogit>>generateTrampolines for the mapping from trampoline to run-time
  	routine and then read the run-time routine for a funcitonal description.
  ceEnterCogCodePopReceiverReg <Integer>
  	the enilopmart (jump from run-time to machine-code)
  methodZoneBase <Integer>
  !
  Cogit class
  	instanceVariableNames: 'generatorTable primitiveTable'!

Item was changed:
  ----- Method: Cogit class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	#(	'coInterpreter' 'objectMemory' 'methodZone' 'objectRepresentation'
  		'cogBlockMethodSurrogateClass' 'cogMethodSurrogateClass' 'nsSendCacheSurrogateClass'
  		'threadManager' 'processor' 'lastNInstructions' 'simulatedAddresses'
  		'simulatedTrampolines' 'simulatedVariableGetters' 'simulatedVariableSetters'
  		'printRegisters' 'printInstructions' 'clickConfirm' 'singleStep') do:
  			[:simulationVariableNotNeededForRealVM|
  			aCCodeGenerator removeVariable: simulationVariableNotNeededForRealVM].
  	NewspeakVM ifFalse:
  		[#(	'selfSendTrampolines' 'dynamicSuperSendTrampolines'
  			'implicitReceiverSendTrampolines' 'outerSendTrampolines'
  			'ceEnclosingObjectTrampoline' 'numIRCs' 'indexOfIRC' 'theIRCs') do:
  				[:variableNotNeededInNormalVM|
  				aCCodeGenerator removeVariable: variableNotNeededInNormalVM]].
  	aCCodeGenerator removeConstant: #COGMTVM. "this should be defined at compile time"
  	aCCodeGenerator
  		addHeaderFile:'<stddef.h>'; "for e.g. offsetof"
  		addHeaderFile:'"sqCogStackAlignment.h"';
  		addHeaderFile:'"dispdbg.h"'; "must precede cointerp.h & cogit.h otherwise NoDbgRegParms gets screwed up"
  		addHeaderFile:'"cogmethod.h"'.
  	NewspeakVM ifTrue:
  		[aCCodeGenerator addHeaderFile:'"nssendcache.h"'].
  	aCCodeGenerator
  		addHeaderFile:'#if COGMTVM';
  		addHeaderFile:'"cointerpmt.h"';
  		addHeaderFile:'#else';
  		addHeaderFile:'"cointerp.h"';
  		addHeaderFile:'#endif';
  		addHeaderFile:'"cogit.h"'.
  	aCCodeGenerator
  		var: #ceGetFP
  			declareC: 'usqIntptr_t (*ceGetFP)(void)';
  		var: #ceGetSP
  			declareC: 'usqIntptr_t (*ceGetSP)(void)';
  		var: #ceCaptureCStackPointers
  			declareC: 'void (*ceCaptureCStackPointers)(void)';
  		var: #ceEnterCogCodePopReceiverReg
  			declareC: 'void (*ceEnterCogCodePopReceiverReg)(void)';
  		var: #realCEEnterCogCodePopReceiverReg
  			declareC: 'void (*realCEEnterCogCodePopReceiverReg)(void)';
  		var: #ceCallCogCodePopReceiverReg
  			declareC: 'void (*ceCallCogCodePopReceiverReg)(void)';
  		var: #realCECallCogCodePopReceiverReg
  			declareC: 'void (*realCECallCogCodePopReceiverReg)(void)';
  		var: #ceCallCogCodePopReceiverAndClassRegs
  			declareC: 'void (*ceCallCogCodePopReceiverAndClassRegs)(void)';
  		var: #realCECallCogCodePopReceiverAndClassRegs
  			declareC: 'void (*realCECallCogCodePopReceiverAndClassRegs)(void)';
  		var: #ceFlushICache
  			declareC: 'static void (*ceFlushICache)(usqIntptr_t from, usqIntptr_t to)';
  		var: #ceCheckFeaturesFunction
  			declareC: 'static usqIntptr_t (*ceCheckFeaturesFunction)(void)';
  		var: #ceCheckLZCNTFunction
  			declareC: 'static usqIntptr_t (*ceCheckLZCNTFunction)(void)';
  		var: #ceTryLockVMOwner
  			declareC: 'usqIntptr_t (*ceTryLockVMOwner)(void)';
  		var: #ceUnlockVMOwner
  			declareC: 'void (*ceUnlockVMOwner)(void)';
  		var: #postCompileHook
  			declareC: 'void (*postCompileHook)(CogMethod *)';
  		var: #openPICList declareC: 'CogMethod *openPICList = 0';
  		var: #maxMethodBefore type: #'CogBlockMethod *';
  		var: 'enumeratingCogMethod' type: #'CogMethod *'.
  	aCCodeGenerator
  		declareVar: 'aMethodLabel' type: #'AbstractInstruction'; "Has to come lexicographically before backEnd & methodLabel"
  		var: #backEnd declareC: 'AbstractInstruction * const backEnd = &aMethodLabel';
  		var: #methodLabel declareC: 'AbstractInstruction * const methodLabel = &aMethodLabel'.
  	self declareC: #(abstractOpcodes stackCheckLabel
  					blockEntryLabel blockEntryNoContextSwitch
  					stackOverflowCall sendMiss
  					entry noCheckEntry selfSendEntry dynSuperEntry
  					fullBlockNoContextSwitchEntry fullBlockEntry
  					picMNUAbort picInterpretAbort  endCPICCase0 endCPICCase1 cPICEndOfCodeLabel)
  			as: #'AbstractInstruction *'
  				in: aCCodeGenerator.
  	aCCodeGenerator
  		declareVar: #blockStarts type: #'BlockStart *';
  		declareVar: #fixups type: #'BytecodeFixup *'.
  	aCCodeGenerator
  		var: #ordinarySendTrampolines
  			declareC: 'sqInt ordinarySendTrampolines[NumSendTrampolines]';
  		var: #superSendTrampolines
  			declareC: 'sqInt superSendTrampolines[NumSendTrampolines]'.
  	BytecodeSetHasDirectedSuperSend ifTrue:
  		[aCCodeGenerator
  			var: #directedSuperSendTrampolines
  				declareC: 'sqInt directedSuperSendTrampolines[NumSendTrampolines]';
  			var: #directedSuperBindingSendTrampolines
  				declareC: 'sqInt directedSuperBindingSendTrampolines[NumSendTrampolines]'].
  	NewspeakVM ifTrue:
  		[aCCodeGenerator
  			var: #selfSendTrampolines
  				declareC: 'sqInt selfSendTrampolines[NumSendTrampolines]';
  			var: #dynamicSuperSendTrampolines
  				declareC: 'sqInt dynamicSuperSendTrampolines[NumSendTrampolines]';
  			var: #implicitReceiverSendTrampolines
  				declareC: 'sqInt implicitReceiverSendTrampolines[NumSendTrampolines]';
  			var: #outerSendTrampolines
  				declareC: 'sqInt outerSendTrampolines[NumSendTrampolines]'].
  	aCCodeGenerator
  		var: #trampolineAddresses
  			declareC: 'static char *trampolineAddresses[NumTrampolines*2]';
  		var: #objectReferencesInRuntime
  			declareC: 'static usqInt objectReferencesInRuntime[NumObjRefsInRuntime+1]';
  		var: #labelCounter
  			type: #int;
  		var: #traceFlags
  			declareC: 'int traceFlags = 8 /* prim trace log on by default */';
  		var: #cStackAlignment
  			declareC: 'const int cStackAlignment = STACK_ALIGN_BYTES'.
  	aCCodeGenerator
- 		declareVar: #CFramePointer type: #'void *';
- 		declareVar: #CStackPointer type: #'void *';
  		declareVar: #minValidCallAddress type: #'usqIntptr_t';
  		declareVar: #debugPrimCallStackOffset type: #'usqIntptr_t'.
  	aCCodeGenerator vmClass generatorTable ifNotNil:
  		[:bytecodeGenTable|
  		aCCodeGenerator
  			var: #generatorTable
  				declareC: 'static BytecodeDescriptor generatorTable[', bytecodeGenTable size printString, ']',
  							(self tableInitializerFor: bytecodeGenTable
  								in: aCCodeGenerator)].
  	"In C the abstract opcode names clash with the Smalltak generator syntactic sugar.
  	 Most of the syntactic sugar is inlined, but alas some remains.  Rename the syntactic
  	 sugar to avoid the clash."
  	(self organization listAtCategoryNamed: #'abstract instructions') do:
  		[:s|
  		aCCodeGenerator addSelectorTranslation: s to: 'g', (aCCodeGenerator cFunctionNameFor: s)].
  	aCCodeGenerator addSelectorTranslation: #halt: to: 'haltmsg'!

Item was changed:
  ----- Method: Cogit>>cFramePointerAddress (in category 'trampoline support') -----
  cFramePointerAddress
+ 	"Real VM's version is in CoInterpreter"
+ 	<doNotGenerate>
- 	<cmacro: '() ((usqIntptr_t)&CFramePointer)'>
  	^(backEnd wantsNearAddressFor: #CFramePointer)
  		ifTrue: [self simulatedReadWriteVariableAddress: #getCFramePointer in: self]
  		ifFalse: [coInterpreter inMemoryCFramePointerAddress]!

Item was changed:
  ----- Method: Cogit>>cStackPointerAddress (in category 'trampoline support') -----
  cStackPointerAddress
+ 	"Real VM's version is in CoInterpreter"
+ 	<doNotGenerate>
- 	<cmacro: '() ((usqIntptr_t)&CStackPointer)'>
  	^(backEnd wantsNearAddressFor: #CStackPointer)
  		ifTrue: [self simulatedReadWriteVariableAddress: #getCStackPointer in: self]
  		ifFalse: [coInterpreter inMemoryCStackPointerAddress]!

Item was changed:
  ----- Method: Cogit>>ceCaptureCStackPointers (in category 'jit - api') -----
  ceCaptureCStackPointers
  	<api: 'extern void (*ceCaptureCStackPointers)()'>
  	<doNotGenerate>
  	| range |
  	coInterpreter isThreadedVM ifFalse:
  		[^self].
  	thisContext sender selector == #generateStackPointerCapture ifTrue:
  		[^self].
  	range := coInterpreter cStackRangeForThreadIndex: coInterpreter threadManager getVMOwner.
  	self assert: (range notNil "VM is owned"
  				and: [(range includes: processor sp)
  				and: [range includes: processor fp]]).
+ 	coInterpreter setCFramePointer: processor fp setCStackPointer: processor sp!
- 	self setCStackPointer: processor sp.
- 	self setCFramePointer: processor fp!

Item was changed:
  ----- Method: Cogit>>generateStackPointerCapture (in category 'initialization') -----
  generateStackPointerCapture
  	"Generate a routine ceCaptureCStackPointers that will capture the C stack pointer,
  	 and, if it is in use, the C frame pointer.  These are used in trampolines to call
  	 run-time routines in the interpreter from machine-code."
  
  	| oldMethodZoneBase oldTrampolineTableIndex |
  	cFramePointerInUse := false. "For the benefit of the following assert, assume the minimum at first."
  	self assertCStackWellAligned.
  	oldMethodZoneBase := methodZoneBase.
  	oldTrampolineTableIndex := trampolineTableIndex.
  	self generateCaptureCStackPointers: true.
  	self perform: #ceCaptureCStackPointers.
+ 	(cFramePointerInUse := coInterpreter checkIfCFramePointerInUse) ifFalse:
- 	(cFramePointerInUse := self isCFramePointerInUse) ifFalse:
  		[methodZoneBase := oldMethodZoneBase.
  		 trampolineTableIndex := oldTrampolineTableIndex.
  		 self generateCaptureCStackPointers: false].
+ 	self assertCStackWellAligned!
- 	self assertCStackWellAligned.!

Item was removed:
- ----- Method: Cogit>>getCFramePointer (in category 'accessing') -----
- getCFramePointer
- 	<api>
- 	<cmacro: '() CFramePointer'>
- 	"and in the simulator we use..."
- 	^(backEnd wantsNearAddressFor: #CFramePointer)
- 		ifTrue: [CFramePointer]
- 		ifFalse: [(objectMemory longAt: coInterpreter inMemoryCFramePointerAddress) asVoidPointer]!

Item was removed:
- ----- Method: Cogit>>getCStackPointer (in category 'accessing') -----
- getCStackPointer
- 	<api>
- 	<cmacro: '() CStackPointer'>
- 	"and in the simulator we use..."
- 	^(backEnd wantsNearAddressFor: #CStackPointer)
- 		ifTrue: [CStackPointer]
- 		ifFalse: [(objectMemory longAt: coInterpreter inMemoryCStackPointerAddress) asVoidPointer]!

Item was changed:
  ----- Method: Cogit>>initializeProcessor (in category 'initialization') -----
  initializeProcessor
  	"Initialize the simulation processor, arranging that its initial stack is somewhere on the rump C stack."
  	<doNotGenerate>
  	guardPageSize := self class guardPageSize.
  	lastNInstructions := OrderedCollection new.
  	processor initializeStackFor: self.
  	self initializeProcessorStack: coInterpreter rumpCStackAddress.
+ 	coInterpreter setCFramePointer: processor fp setCStackPointer: processor sp.
- 	self setCFramePointer: processor fp.
- 	self setCStackPointer: processor sp.
  	threadManager ifNotNil:
  		[processor := MultiProcessor for: processor coInterpreter: coInterpreter]!

Item was removed:
- ----- Method: Cogit>>isCFramePointerInUse (in category 'initialization') -----
- isCFramePointerInUse
- 	<doNotGenerate>
- 	"This should be implemented externally, e.g. in sqPlatMain.c."
- 	^true!

Item was removed:
- ----- Method: Cogit>>setCFramePointer: (in category 'accessing') -----
- setCFramePointer: aFramePointer
- 	<api>
- 	<cmacro: '(theFP) (CFramePointer = (void *)(theFP))'>
- 	"and in the simulator we use..."
- 	^(backEnd wantsNearAddressFor: #CFramePointer)
- 		ifTrue: [CFramePointer := aFramePointer]
- 		ifFalse: [(objectMemory
- 					longAt: coInterpreter inMemoryCFramePointerAddress
- 					put: aFramePointer) asVoidPointer]!

Item was removed:
- ----- Method: Cogit>>setCStackPointer: (in category 'accessing') -----
- setCStackPointer: aStackPointer
- 	<api>
- 	<cmacro: '(theSP) (CStackPointer = (void *)(theSP))'>
- 	"and in the simulator we use..."
- 	^(backEnd wantsNearAddressFor: #CStackPointer)
- 		ifTrue: [CStackPointer := aStackPointer]
- 		ifFalse: [(objectMemory
- 					longAt: coInterpreter inMemoryCStackPointerAddress
- 					put: aStackPointer) asVoidPointer]!

Item was changed:
  ----- Method: Cogit>>shortcutTrampoline:to: (in category 'simulation only') -----
  shortcutTrampoline: aProcessorSimulationTrap to: aBlock
  	<doNotGenerate>
+ 	"As a simulation performance hack for debugging trampolines such as ceTraceLinkedSend: allow the entire
+ 	 trampoline to be implemented by this method instead of simulating all of the code for the trampoline."
  	backEnd hasLinkRegister ifTrue:
  		[processor pushWord: processor lr in: coInterpreter memory].
  	processor
  		simulateLeafCallOf: aProcessorSimulationTrap address
  		nextpc: aProcessorSimulationTrap nextpc
  		memory: coInterpreter memory.
  	coInterpreter
  		stackPointer: processor sp;
  		framePointer: processor fp.
  	processor
+ 		sp: coInterpreter getCStackPointer;
+ 		fp: coInterpreter getCFramePointer.
- 		sp: self getCStackPointer;
- 		fp: self getCFramePointer.
  	aBlock value.
  	processor
  		sp: coInterpreter stackPointer;
  		fp: coInterpreter framePointer;
  		simulateLeafReturnIn: coInterpreter memory.
  	backEnd hasLinkRegister ifTrue:
  		[processor lr: (processor popWordIn: coInterpreter memory)]!



More information about the Vm-dev mailing list