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

commits at source.squeak.org commits at source.squeak.org
Fri Aug 6 22:09:05 UTC 2021


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

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

Name: VMMaker.oscog-eem.3032
Author: eem
Time: 6 August 2021, 3:07:44.151308 pm
UUID: dbec694d-7e87-4069-897c-b41dd2535256
Ancestors: VMMaker.oscog-eem.3031

Cogit: implement simulation support for AndreasSystemProfiler that doesn't require it to be loaded.  Fix a slip in CogX64Compiler>>#concretizeMovePerfCnt64RL.

Fix stack access bugs in compileInterpreterPrimitive:flags: after calling ceTakeProfileSample:, and in genPrimReturnEnterCogCodeEnilopmart: on calling ceCheckProfileTick.

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

Item was changed:
  ----- Method: CoInterpreter>>ceCheckProfileTick (in category 'cog jit support') -----
  ceCheckProfileTick
  	"Check if the profile timer has expired and if so take a sample.
  	 If the primitive has failed sample the profileMethod as nil.
  	 As a courtesy to compileInterpreterPrimitive: map NULL to nilObj."
  	<api>
  	newMethod ifNil: [newMethod := objectMemory nilObject].
  	self cCode: [] inSmalltalk:
  		[newMethod = 0 ifTrue: [newMethod := objectMemory nilObject].
  		 "Get round the assert in checkProfileTick: when just testing."
+ 		 nextProfileTick = 0 ifTrue:
+ 			[self ifTestProfilingAdvanceNextProfileTick]].
+ 	self checkProfileTick: newMethod.
+ 	self cCode: [] inSmalltalk:
+ 		[self ifTestProfilingAdvanceNextProfileTick]!
- 		 (nextProfileTick = 0 and: [InitializationOptions at: #profiling ifAbsent: [false]]) ifTrue:
- 			[nextProfileTick := 1]].
- 	self checkProfileTick: newMethod!

Item was changed:
  ----- Method: CoInterpreter>>ceTakeProfileSample: (in category 'cog jit support') -----
  ceTakeProfileSample: aCogMethod
  	"A primitive has succeeded and the nextProfileTick has been reached (all done in machine code).
  	 Now take a sample. c.f. checkProfileTick:"
  	<api>
  	<var: 'aCogMethod' type: #'CogMethod *'>
  	self cCode: '' inSmalltalk:
  		[aCogMethod isInteger ifTrue:
  			[^self ceTakeProfileSample: (cogit cCoerceSimple: aCogMethod to: #'CogMethod *')]].
  	profileProcess := self activeProcess.
  	profileMethod := aCogMethod methodObject.
  	self forceInterruptCheck.
+ 	self zeroNextProfileTick!
- 	nextProfileTick := 0!

Item was changed:
  ----- Method: CoInterpreterMT>>checkForEventsMayContextSwitch: (in category 'process primitive support') -----
  checkForEventsMayContextSwitch: mayContextSwitch
  	"Check for possible interrupts and handle one if necessary.
  	 Answer if a context switch has occurred."
  	| switched sema now |
  	<inline: false>
  	<var: #now type: #usqLong>
  	self assertSaneThreadAndProcess.
  	cogit assertCStackWellAligned.
  	statCheckForEvents := statCheckForEvents + 1.
  
  	"restore the stackLimit if it has been smashed."
  	self restoreStackLimit.
  	self externalWriteBackHeadFramePointers.
  	self assert: stackPage = stackPages mostRecentlyUsedPage.
  
  	"Allow the platform to do anything it needs to do synchronously."
  	self ioSynchronousCheckForEvents.
  
  	self checkCogCompiledCodeCompactionCalledFor.
  
  	objectMemory needGCFlag ifTrue:
  		["sufficientSpaceAfterGC: runs the incremental GC and
  		 then, if not enough space is available, the fullGC."
  		 (objectMemory sufficientSpaceAfterGC: 0) ifFalse:
  			[self setSignalLowSpaceFlagAndSaveProcess]].
  
  	mayContextSwitch ifFalse: [^false].
  
  	switched := false.
  	self assert: deferThreadSwitch not.
  	deferThreadSwitch := true.
  
  	(profileProcess ~= objectMemory nilObject
  	 or: [nextProfileTick > 0 and:[self ioHighResClock >= nextProfileTick]]) ifTrue:
+ 		[self zeroNextProfileTick.
- 		[nextProfileTick := 0.
  		 "Take a sample (if not already done so) for the profiler if it is active.  This
  		  must be done before any of the synchronousSignals below or else we will
  		  attribute a pause in ioRelinquishProcessor to the newly activated process."
  		 profileProcess = objectMemory nilObject ifTrue:
  			[profileProcess := self activeProcess.
  			 profileMethod := objectMemory nilObject].
  		 "and signal the profiler semaphore if it is present"
  		 (profileSemaphore ~= objectMemory nilObject
  		  and: [self synchronousSignal: profileSemaphore]) ifTrue:
  			[switched := true]].
  
  	objectMemory signalLowSpace ifTrue:
  		[objectMemory signalLowSpace: false. "reset flag"
  		 sema := objectMemory splObj: TheLowSpaceSemaphore.
  		 (sema ~= objectMemory nilObject
  		  and: [self synchronousSignal: sema]) ifTrue:
  			[switched := true]].
  
  	"inIOProcessEvents prevents reentrancy into ioProcessEvents and allows disabling
  	 ioProcessEvents e.g. for native GUIs.  We would like to manage that here but can't
  	 since the platform code may choose to call ioProcessEvents itself in various places."
  	false
  		ifTrue:
  			[((now := self ioUTCMicroseconds) >= nextPollUsecs
  			 and: [inIOProcessEvents = 0]) ifTrue:
  				[statIOProcessEvents := statIOProcessEvents + 1.
  				 inIOProcessEvents := inIOProcessEvents + 1.
  				 self ioProcessEvents. "sets interruptPending if interrupt key pressed; may callback"
  				 inIOProcessEvents > 0 ifTrue:
  					[inIOProcessEvents := inIOProcessEvents - 1].
  				 nextPollUsecs := now + 20000
  				 "msecs to wait before next call to ioProcessEvents.  Note that strictly
  				  speaking we might need to update 'now' at this point since
  				  ioProcessEvents could take a very long time on some platforms"]]
  		ifFalse:
  			[(now := self ioUTCMicroseconds) >= nextPollUsecs ifTrue:
  				[statIOProcessEvents := statIOProcessEvents + 1.
  				 self ioProcessEvents. "sets interruptPending if interrupt key pressed; may callback"
  				 nextPollUsecs := now + 20000
  				 "msecs to wait before next call to ioProcessEvents.  Note that strictly
  				  speaking we might need to update 'now' at this point since
  				  ioProcessEvents could take a very long time on some platforms"]].
  
  	interruptPending ifTrue:
  		[interruptPending := false.
  		 "reset interrupt flag"
  		 sema := objectMemory splObj: TheInterruptSemaphore.
  		 (sema ~= objectMemory nilObject
  		  and: [self synchronousSignal: sema]) ifTrue:
  			[switched := true]].
  
  	nextWakeupUsecs ~= 0 ifTrue:
  		[now >= nextWakeupUsecs ifTrue:
  			[nextWakeupUsecs := 0.
  			 "set timer interrupt to 0 for 'no timer'"
  			 sema := objectMemory splObj: TheTimerSemaphore.
  			 (sema ~= objectMemory nilObject
  			  and: [self synchronousSignal: sema]) ifTrue:
  				[switched := true]]].
  
  	"signal any pending finalizations"
  	pendingFinalizationSignals > 0 ifTrue:
  		[pendingFinalizationSignals := 0.
  		 sema := objectMemory splObj: TheFinalizationSemaphore.
  		 (sema ~= objectMemory nilObject
  		  and: [self synchronousSignal: sema]) ifTrue:
  			[switched := true]].
  
  	"signal all semaphores in semaphoresToSignal"
  	self signalExternalSemaphores ifTrue:
  		[switched := true].
  
  	deferThreadSwitch := false.
  	checkThreadActivation ifTrue:
  		[checkThreadActivation := false.
  		 self cedeToHigherPriorityThreads]. "N.B.  This may not return if we do switch."
  
  	self threadSwitchIfNecessary: self activeProcess from: CSCheckEvents.
  	^switched!

Item was added:
+ ----- Method: CogAbstractInstruction>>genLoadStackPointerForPrimCall: (in category 'smalltalk calling convention') -----
+ genLoadStackPointerForPrimCall: spareReg
+ 	"Switch back to the Smalltalk stack where there may be a C return address on top of stack below
+ 	 the last primitive argument. Assign SPReg first because typically it is used immediately afterwards."
+ 	self hasLinkRegister
+ 		ifTrue: [cogit MoveAw: cogit stackPointerAddress R: SPReg]
+ 		ifFalse:
+ 			[cogit
+ 				MoveAw: cogit stackPointerAddress R: spareReg;
+ 				"N.B. dont use SubCq:R:R: since it may generate MoveR:spareRegR:SPReg;SubCq:wordSize R:SPReg
+ 				 which allows for the ret addr to be smashed by an interrupt between the two instructions."
+ 				SubCq: objectMemory wordSize R: spareReg;
+ 				MoveR: spareReg R: SPReg].
+ 	^0!

Item was changed:
  CoInterpreterMT subclass: #CogVMSimulator
+ 	instanceVariableNames: 'parent enableCog byteCount lastPollCount lastExtPC sendCount lookupCount printSends traceOn myBitBlt displayForm fakeForm imageName pluginList mappedPluginEntries quitBlock transcript displayView eventTransformer printFrameAtEachStep printBytecodeAtEachStep systemAttributes uniqueIndices uniqueIndex breakCount atEachStepBlock startMicroseconds lastYieldMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize debugStackDepthDictionary performFilters eventQueue effectiveCogCodeSize expectedSends expecting inputSemaphoreIndex zeroNextProfileTickCount'
- 	instanceVariableNames: 'parent enableCog byteCount lastPollCount lastExtPC sendCount lookupCount printSends traceOn myBitBlt displayForm fakeForm imageName pluginList mappedPluginEntries quitBlock transcript displayView eventTransformer printFrameAtEachStep printBytecodeAtEachStep systemAttributes uniqueIndices uniqueIndex breakCount atEachStepBlock startMicroseconds lastYieldMicroseconds externalSemaphoreSignalRequests externalSemaphoreSignalResponses extSemTabSize debugStackDepthDictionary performFilters eventQueue effectiveCogCodeSize expectedSends expecting inputSemaphoreIndex'
  	classVariableNames: 'ByteCountsPerMicrosecond ExpectedSends NLRFailures NLRSuccesses StackAlteringPrimitives'
  	poolDictionaries: ''
  	category: 'VMMaker-JITSimulation'!
  
  !CogVMSimulator commentStamp: 'eem 9/3/2013 11:16' prior: 0!
  This class defines basic memory access and primitive simulation so that the CoInterpreter can run simulated in the Squeak environment.  It also defines a number of handy object viewing methods to facilitate pawing around in the object memory.  Remember that you can test the Cogit using its class-side in-image compilation facilities.
  
  To see the thing actually run, you could (after backing up this image and changes), execute
  
  	(CogVMSimulator new openOn: Smalltalk imageName) test
  
  and be patient both to wait for things to happen, and to accept various things that may go wrong depending on how large or unusual your image may be.  We usually do this with a small and simple benchmark image.
  
  Here's an example to launch the simulator in a window.  The bottom-right window has a menu packed with useful stuff:
  
  (CogVMSimulator newWithOptions: #(Cogit StackToRegisterMappingCogit))
  	desiredNumStackPages: 8;
  	openOn: '/Users/eliot/Cog/startreader.image';
  	openAsMorph;
  	run
  
  Here's a hairier example that I (Eliot) actually use in daily development with some of the breakpoint facilities commented out.
  
  | cos proc opts |
  CoInterpreter initializeWithOptions: (opts := Dictionary newFromPairs: #(Cogit StackToRegisterMappingCogit)).
  CogVMSimulator chooseAndInitCogitClassWithOpts: opts.
  cos := CogVMSimulator new.
  "cos initializeThreadSupport." "to test the multi-threaded VM"
  cos desiredNumStackPages: 8. "to set the size of the stack zone"
  "cos desiredCogCodeSize: 8 * 1024 * 1024." "to set the size of the Cogit's code zone"
  cos openOn: '/Users/eliot/Squeak/Squeak4.4/trunk44.image'. "choose your favourite image"
  "cos setBreakSelector: 'r:degrees:'." "set a breakpoint at a specific selector"
  proc := cos cogit processor.
  "cos cogit sendTrace: 7." "turn on tracing"
  "set a complex breakpoint at a specific point in machine code"
  "cos cogit singleStep: true; breakPC: 16r56af; breakBlock: [:cg|  cos framePointer > 16r101F3C and: [(cos longAt: cos framePointer - 4) = 16r2479A and: [(cos longAt: 16r101F30) = (cos longAt: 16r101F3C) or: [(cos longAt: 16r101F2C) = (cos longAt: 16r101F3C)]]]]; sendTrace: 1".
  "[cos cogit compilationTrace: -1] on: MessageNotUnderstood do: [:ex|]." "turn on compilation tracing in the StackToRegisterMappingCogit"
  "cos cogit setBreakMethod: 16rB38880."
  cos
  	openAsMorph;
  	"toggleTranscript;" "toggleTranscript will send output to the Transcript instead of the morph's rather small window"
  	halt;
  	run!

Item was added:
+ ----- Method: CogVMSimulator>>ifTestProfilingAdvanceNextProfileTick (in category 'simulation only') -----
+ ifTestProfilingAdvanceNextProfileTick
+ 	"bump nextProfileTick along if simulating; but not by much so the mechanism is stressed a lot"
+ 	(InitializationOptions at: #profiling ifAbsent: [false]) ifTrue:
+ 		[nextProfileTick := self ioHighResClock + ((InitializationOptions at: #profileIncrement ifAbsent: [10000])).
+ 		 self assert: nextProfileTick > (self ioHighResClock + 5000)]!

Item was changed:
  ----- Method: CogVMSimulator>>initialize (in category 'initialize-release') -----
  initialize
  	"Initialize the CogVMSimulator when running the interpreter inside Smalltalk.  The
  	 primary responsibility of this method is to allocate Smalltalk Arrays for variables
  	 that will be declared as statically-allocated global arrays in the translated code."
  	super initialize.
  
  	transcript := Transcript.
  
  	objectMemory ifNil:
  		[objectMemory := self class objectMemoryClass simulatorClass new].
  	cogit ifNil:
  		[cogit := self class cogitClass new setInterpreter: self].
  	objectMemory coInterpreter: self cogit: cogit.
  
  	(cogit numRegArgs > 0
  	 and: [VMClass initializationOptions at: #CheckStackDepth ifAbsent: [true]]) ifTrue:
  		[debugStackDepthDictionary := Dictionary new].
  
  	cogThreadManager ifNotNil:
  		[super initialize].
  
  	self assert: ConstMinusOne = (objectMemory integerObjectOf: -1).
  
  	cogMethodZone := cogit methodZone. "Because Slang can't remove intermediate implicit receivers (cogit methodZone foo doesn't reduce to foo())"
  	enableCog := true.
  
  	methodCache := Array new: MethodCacheSize.
  	nsMethodCache := Array new: NSMethodCacheSize.
  	atCache := nil.
  	self flushMethodCache.
  	cogCompiledCodeCompactionCalledFor := false.
  	gcSemaphoreIndex := 0.
  	externalSemaphoreSignalRequests := externalSemaphoreSignalResponses := #().
  	externalPrimitiveTable := CArrayAccessor on: (Array new: MaxExternalPrimitiveTableSize).
  	externalPrimitiveTableFirstFreeIndex := 0.
  	primitiveTable := self class primitiveTable copy.
  	self initializePluginEntries.
  	desiredNumStackPages := InitializationOptions at: #desiredNumStackPages ifAbsent: [0].
  	desiredEdenBytes := InitializationOptions at: #desiredEdenBytes ifAbsent: [0].
  	desiredCogCodeSize  := InitializationOptions at: #desiredCogCodeSize ifAbsent: [0].
  	"This is initialized on loading the image, but convenient for testing stack page values..."
  	numStackPages := self defaultNumStackPages. 
  	startMicroseconds := lastYieldMicroseconds := self ioUTCStartMicroseconds.
  	maxLiteralCountForCompile := MaxLiteralCountForCompile.
  	minBackwardJumpCountForCompile := MinBackwardJumpCountForCompile.
  	flagInterpretedMethods := false.
  
  	"initialize InterpreterSimulator variables used for debugging"
  	byteCount := lastPollCount := sendCount := lookupCount := 0.
  	quitBlock := [^self close].
  	traceOn := true.
  	printSends := printFrameAtEachStep := printBytecodeAtEachStep := false.
  	myBitBlt := BitBltSimulator new setInterpreter: self.
  	displayForm := fakeForm := 'Display has not yet been installed' asDisplayText form.
  	suppressHeartbeatFlag := deferSmash := deferredSmash := false.
  	systemAttributes := Dictionary new.
  	primTraceLog := CArrayAccessor on: (Array new: 256 withAll: 0).
  	primTraceLogIndex := 0.
  	traceLog := CArrayAccessor on: (Array new: TraceBufferSize withAll: 0).
  	traceLogIndex := 0.
  	traceSources := TraceSources.
  	statCodeCompactionCount := 0.
  	statCodeCompactionUsecs := 0.
+ 	extSemTabSize := 256.
+ 	zeroNextProfileTickCount := 0!
- 	extSemTabSize := 256!

Item was changed:
  ----- Method: CogVMSimulator>>ioHighResClock (in category 'I/O primitives support') -----
  ioHighResClock
+ 	^cogit backEnd has64BitPerformanceCounter
+ 		ifTrue: [cogit ioHighResClock]
+ 		ifFalse: [self ioUTCMicroseconds]!
- 	^self ioUTCMicroseconds!

Item was added:
+ ----- Method: CogVMSimulator>>zeroNextProfileTick (in category 'simulation only') -----
+ zeroNextProfileTick
+ 	zeroNextProfileTickCount := zeroNextProfileTickCount + 1.
+ 	super zeroNextProfileTick.
+ 	self ifTestProfilingAdvanceNextProfileTick!

Item was changed:
  ----- Method: CogX64Compiler>>concretizeMovePerfCnt64RL (in category 'generate machine code - concretize') -----
  concretizeMovePerfCnt64RL
  	"Generate code for
  		0x0: 50					pushq	%rax
  		0x1: 52					pushq	%rdx
  		0x2: 0f 31				rdtsc
  		0x4: 48 c1 e2 20		shlq	$0x20, %rdx
  		0x8: 48 09 d0			orq		%rdx, %rax
  		0xb: 48 89 f8			movq	%rdi, %rax
  		0xe: 5a					popq	%rdx
  		0xf: 58					popq	%rax
  	 et al"
  	| reg liveRegisters offset |
  	reg := operands at: 0.
  	liveRegisters := operands at: 1.
  	offset := 0.
  	(liveRegisters anyMask: (cogit registerMaskFor: RAX)) ifTrue:
  		[machineCode at: 0 put: 16r50. "push %eax"
  		 offset := offset + 1].
  	(liveRegisters anyMask: (cogit registerMaskFor: RDX)) ifTrue:
  		[machineCode at: offset put: 16r52. "push %edx"
  		 offset := offset + 1].
  	"too lazy to define the swap cases for the moment..."
  	self deny: reg = RDX.
  	machineCode
  		at: offset		put: 16r0F;							"rdtsc"
  		at: offset + 1	put: 16r31;
  		at: offset + 2	put: (self rexR: 0 x: 0 b: RDX);					"shlq   $0x20, %rdx"
  		at: offset + 3	put: 16rC1;
  		at: offset + 4	put: (self mod: ModReg RM: RDX RO: 4);
  		at: offset + 5	put: 32;
  		at: offset + 6	put: (self rexR: RDX x: 0 b: RAX);				"orq 	%rax, %rdx"
  		at: offset + 7	put: 16r0B;
  		at: offset + 8	put: (self mod: ModReg RM: RAX RO: RDX).
  	offset := offset + 9.
  	reg ~= RAX ifTrue:
  		[machineCode
+ 			at: offset put: (self rexR: RAX x: 0 b: reg);				"movq	%rDEST, %rax"
+ 			at: offset + 1 put: 16r89;
+ 			at: offset + 2 put: (self mod: ModReg RM: reg RO: RAX).
- 			at: 11 put: (self rexR: reg x: 0 b: RAX);				"movq	%rDEST, %rax"
- 			at: 12 put: 16r89;
- 			at: 13 put: (self mod: ModReg RM: RAX RO: reg).
  		 offset := offset + 3].
  	(liveRegisters anyMask: (cogit registerMaskFor: RDX)) ifTrue:
  		[machineCode at: offset put: 16r5A. "pop %edx"
  		 offset := offset + 1].
  	(liveRegisters anyMask: (cogit registerMaskFor: RAX)) ifTrue:
  		[machineCode at: offset put: 16r58. "pop %eax"
  		 offset := offset + 1].
  	^offset
  
  	"{	cogit processor disassembleInstructionAt: 0 In: machineCode object.
- 		cogit processor disassembleInstructionAt: 1 In: machineCode object.
  		cogit processor disassembleInstructionAt: 2 In: machineCode object.
+ 		cogit processor disassembleInstructionAt: 6 In: machineCode object.
+ 		cogit processor disassembleInstructionAt: 9 In: machineCode object }"!
- 		cogit processor disassembleInstructionAt: 4 In: machineCode object.
- 		cogit processor disassembleInstructionAt: 8 In: machineCode object.
- 		cogit processor disassembleInstructionAt: 11 In: machineCode object.
- 		cogit processor disassembleInstructionAt: 14 In: machineCode object.
- 		cogit processor disassembleInstructionAt: 15 In: machineCode object }"!

Item was changed:
  CogClass subclass: #Cogit
(excessive size, no diff calculated)

Item was changed:
  ----- Method: Cogit class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  	| backEnd |
  	backEnd := CogCompilerClass basicNew.
  	#(	'coInterpreter' 'objectMemory' 'methodZone' 'objectRepresentation'
  		'cogBlockMethodSurrogateClass' 'cogMethodSurrogateClass' 'nsSendCacheSurrogateClass'
+ 		'threadManager' 'processor' 'lastNInstructions' 'simulatedAddresses' 'ioHighResClock'
- 		'threadManager' 'processor' 'lastNInstructions' 'simulatedAddresses'
  		'simulatedTrampolines' 'simulatedVariableGetters' 'simulatedVariableSetters'
  		'processorFrameValid' 'printRegisters' 'printInstructions' 'clickConfirm' 'singleStep'
  		'codeZoneIsExecutableNotWritable' 'debugAPISelector' 'shortCutTrampolineBlocks') 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"
  	"N.B. We *do not* include sq.h; it pulls in conflicting definitions now that sqVirtualMachine.h
  	 declares cointerp's functions, and declares some of them inaccurately for histrical reasons.
  	 We pull in CoInterpreter's api via cointerp.h which is accurate."
  	aCCodeGenerator
  		addHeaderFile:'"sqConfig.h"'; "config.h must be first on linux"
  		addHeaderFile:'<stddef.h>'; "for e.g. offsetof"
  		addHeaderFile:'<stdio.h>';
  		addHeaderFile:'<stdlib.h>';
  		addHeaderFile:'<string.h>';
  		addHeaderFile:'"sqPlatformSpecific.h"'; "e.g. solaris overrides things for sqCogStackAlignment.h"
  		addHeaderFile:'"sqMemoryAccess.h"';
  		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: #ceInvokeInterpret
  			declareC: 'void (*ceInvokeInterpret)(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: #postCompileHook
  			declareC: 'void (*postCompileHook)(CogMethod *)';
  		var: #openPICList declareC: 'CogMethod *openPICList = 0';
  		var: #maxMethodBefore type: #'CogBlockMethod *';
  		var: 'enumeratingCogMethod' type: #'CogMethod *'.
  	
  	aCCodeGenerator
  		var: #ceTryLockVMOwner
  		declareC: '#if COGMTVM\usqIntptr_t (*ceTryLockVMOwner)(usqIntptr_t)\#endif'.
  
  	backEnd numICacheFlushOpcodes > 0 ifTrue:
  		[aCCodeGenerator
  			var: #ceFlushICache
  				declareC: 'static void (*ceFlushICache)(usqIntptr_t from, usqIntptr_t to)'].
  	aCCodeGenerator
  		var: #ceFlushDCache
  			declareC: '#if DUAL_MAPPED_CODE_ZONE\static void (*ceFlushDCache)(usqIntptr_t from, usqIntptr_t to)\#endif';
  		var: #codeToDataDelta
  			declareC: '#if DUAL_MAPPED_CODE_ZONE\static sqInt codeToDataDelta\#else\# define codeToDataDelta 0\#endif'.
  
  	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: #cPICPrototype type: #'CogMethod *';
  		declareVar: #blockStarts type: #'BlockStart *';
  		declareVar: #fixups type: #'BytecodeFixup *';
  		declareVar: #methodZoneBase type: #usqInt.
  	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
  		addConstantForBinding: self bindingForNumTrampolines;
  		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: #minValidCallAddress 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 Smalltalk 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'.
  	self declareFlagVarsAsByteIn: aCCodeGenerator!

Item was changed:
  ----- Method: Cogit>>initializeCodeZoneFrom:upTo: (in category 'initialization') -----
  initializeCodeZoneFrom: startAddress upTo: endAddress
  	<api>
  	self initializeBackend.
  	self sqMakeMemoryExecutableFrom: startAddress
  		To: endAddress
  		CodeToDataDelta: (self cppIf: #DUAL_MAPPED_CODE_ZONE
  								ifTrue: [self addressOf: codeToDataDelta put: [:v| codeToDataDelta := v]]
  								ifFalse: [nil]).
+ 	codeBase := methodZoneBase := startAddress.
  	backEnd stopsFrom: startAddress to: endAddress - 1.
  	self cCode: '' inSmalltalk:
  		[self initializeProcessor.
+ 		 backEnd stopsFrom: 0 to: guardPageSize - 1.
+ 		 backEnd has64BitPerformanceCounter ifTrue:
+ 			[self initializeSimulationIOHighResClockForProfiling]].
- 		 backEnd stopsFrom: 0 to: guardPageSize - 1].
- 	codeBase := methodZoneBase := startAddress.
  	minValidCallAddress := (codeBase min: coInterpreter interpretAddress)
  								min: coInterpreter primitiveFailAddress.
  	methodZone manageFrom: methodZoneBase to: endAddress.
  	self assertValidDualZone.
  	backEnd detectFeatures.
  	self maybeGenerateCacheFlush.
  	self generateVMOwnerLockFunctions.
  	self genGetLeafCallStackPointers.
  	self generateStackPointerCapture.
  	self generateTrampolines.
  	self computeEntryOffsets.
  	self computeFullBlockEntryOffsets.
  	self generateClosedPICPrototype.
  	self alignMethodZoneBase.
  
  	"None of the above is executed beyond ceCheckFeatures, so a bulk flush now is the leanest thing to do."
  	backEnd flushICacheFrom: startAddress to: methodZoneBase asUnsignedInteger.
  	self maybeFlushWritableZoneFrom: startAddress to: methodZoneBase asUnsignedInteger.
  	"Repeat so that now the methodZone ignores the generated run-time."
  	methodZone manageFrom: methodZoneBase to: endAddress.
  	"N.B. this is assumed to be the last thing done in initialization; see Cogit>>initialized.
  	 This is done only to compute openPICSize; the generated code is discarded."
  	self generateOpenPICPrototype!

Item was added:
+ ----- Method: Cogit>>initializeSimulationIOHighResClockForProfiling (in category 'simulation only') -----
+ initializeSimulationIOHighResClockForProfiling
+ 	"For simulating timing, hack in ioHighResClock in the guard page"
+ 	self allocateOpcodes: 4 bytecodes: 0.
+ 	objectRepresentation wordSize = 8
+ 		ifTrue:
+ 			[self MovePerfCnt64R: ABIResultReg L: ABICalleeSavedRegisterMask]
+ 		ifFalse:
+ 			[self MovePerfCnt64R: ABIResultReg R: ABIResultRegHigh L: ABICalleeSavedRegisterMask].
+ 	self RetN: 0.
+ 	ioHighResClock := self outputInstructionsForGeneratedRuntimeAt: codeBase - (backEnd machineCodeBytes * 2).
+ 	self resetMethodZoneBase: codeBase.
+ 	coInterpreter ifTestProfilingAdvanceNextProfileTick
+ 
+ 	"self disassembleFrom: ioHighResClock to: self class guardPageSize"!

Item was added:
+ ----- Method: Cogit>>ioHighResClock (in category 'simulation only') -----
+ ioHighResClock
+ 	<doNotGenerate>
+ 	| end memory savedsp |
+ 	end := self class guardPageSize.
+ 	memory := coInterpreter memory.
+ 	(coInterpreter isOnRumpCStack: (savedsp := processor sp)) ifFalse:
+ 		[processor sp: (coInterpreter heapBase bitAnd: (cStackAlignment - 1) bitInvert)].
+ 	processor simulateLeafCallOf: ioHighResClock nextpc: end memory: memory.
+ 	[processor pc ~= end] whileTrue:
+ 		[processor
+ 			singleStepIn: memory
+ 			minimumAddress: ioHighResClock
+ 			readOnlyBelow: end].
+ 	processor sp: savedsp.
+ 	backEnd class wordSize = 8 ifTrue:
+ 		[^processor cResultRegister].
+ 	^(processor cResultRegisterHigh bitShift: 32) + processor cResultRegister
+ 
+ 	"self disassembleFrom: ioHighResClock to: self class guardPageSize"!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compileInterpreterPrimitive:flags: (in category 'primitive generators') -----
  compileInterpreterPrimitive: primitiveRoutine flags: flags
  	"Compile a call to an interpreter primitive.  Call the C routine with the
  	 usual stack-switching dance, test the primFailCode and then either
  	 return on success or continue to the method body."
  	<var: #primitiveRoutine declareC: 'void (*primitiveRoutine)(void)'>
  	| jmp continueAfterProfileSample jumpToTakeSample |
  	self deny: (backEnd hasVarBaseRegister
  				and: [self register: VarBaseReg isInMask: ABICallerSavedRegisterMask]).
  
  	"Save processor fp, sp and return pc in the interpreter's frame stack and instruction pointers"
  	self genExternalizePointersForPrimitiveCall.
  	"Switch to the C stack."
  	self genLoadCStackPointersForPrimCall.
  
  	"Old old full prim trace is in VMMaker-eem.550 and prior.
  	 Old simpler full prim trace is in VMMaker-eem.2969 and prior."
  	(coInterpreter recordPrimTraceForMethod: methodObj) ifTrue:
  		[self genFastPrimTraceUsing: ClassReg and: SendNumArgsReg].
  
  	"Clear the primFailCode and set argumentCount"
  	self MoveCq: 0 R: TempReg.
  	self MoveR: TempReg Aw: coInterpreter primFailCodeAddress.
  	methodOrBlockNumArgs ~= 0 ifTrue:
  		[self AddCq: methodOrBlockNumArgs R: TempReg]. "As small or smaller than move on most archs"
  	self MoveR: TempReg Aw: coInterpreter argumentCountAddress.
  
  	"If required, set primitiveFunctionPointer and newMethod"
  	(flags anyMask: PrimCallNeedsPrimitiveFunction) ifTrue:
  		[self MoveCw: primitiveRoutine asInteger R: TempReg.
  		 self MoveR: TempReg Aw: coInterpreter primitiveFunctionPointerAddress].
  	(flags anyMask: PrimCallNeedsNewMethod+PrimCallMayEndureCodeCompaction) ifTrue:
  		["The ceActivateFailingPrimitiveMethod: machinery can't handle framelessness."
  		 (flags anyMask: PrimCallMayEndureCodeCompaction) ifTrue:
  			[needsFrame := true].
  		 methodLabel addDependent:
  			(self annotateAbsolutePCRef:
  				(self MoveCw: methodLabel asInteger R: ClassReg)).
  		 self MoveMw: (self offset: CogMethod of: #methodObject) r: ClassReg R: TempReg.
  		 self MoveR: TempReg Aw: coInterpreter newMethodAddress].
  
  	"Invoke the primitive.  If the primitive (potentially) contains a call-back then its code
  	 may disappear and consequently we cannot return here, sicne here may evaporate.
  	 Instead sideways-call the routine, substituting cePrimReturnEnterCogCode[Profiling]
  	 as the return address, so the call always returns there."
  	self PrefetchAw: coInterpreter primFailCodeAddress.
  	(flags anyMask: PrimCallMayEndureCodeCompaction) ifTrue:
  		["On Spur ceActivateFailingPrimitiveMethod: would like to retry if forwarders
  		  are found. So insist on PrimCallNeedsPrimitiveFunction being set too."
  		 objectMemory hasSpurMemoryManagerAPI ifTrue:
  			[self assert: (flags anyMask: PrimCallNeedsPrimitiveFunction)].
  		 backEnd
  			genMarshallNArgs: 0 arg: nil arg: nil arg: nil arg: nil;
  			genSubstituteReturnAddress:
  				((flags anyMask: PrimCallCollectsProfileSamples)
  					ifTrue: [cePrimReturnEnterCogCodeProfiling]
  					ifFalse: [cePrimReturnEnterCogCode]).
  		 self JumpFullRT: primitiveRoutine asInteger.
  		 ^0].
  
  	"Call the C primitive routine."
  	backEnd genMarshallNArgs: 0 arg: 0 arg: 0 arg: 0 arg: 0.
  	self CallFullRT: primitiveRoutine asInteger.
  	backEnd genRemoveNArgsFromStack: 0.
  	objectRepresentation maybeCompileRetryOnPrimitiveFail: primitiveIndex.
  	"Switch back to the Smalltalk stack.  Stack better be in either of these two states:
  		success:	stackPointer ->	result (was receiver)
  									arg1
  									...
  									argN
  									return pc
  		failure:						receiver
  									arg1
  									...
  					stackPointer ->	argN
  									return pc"
  	backEnd genLoadStackPointersForPrimCall: ClassReg.
  	"genLoadStackPointersForPrimCall: leaves the stack in these states:
  			NoLinkRegister 												LinkRegister
  		success:					result (was receiver)		stackPointer ->	result (was receiver)
  					stackPointer ->	arg1										arg1
  									...											...
  									argN										argN
  									return pc
  
  		failure:						receiver									receiver
  									arg1										arg1
  									...											...
  									argN						stackPointer ->	argN
  					stackPointer ->	return pc
  	which corresponds to the stack on entry after pushRegisterArgs.
  	 In either case we can write the instructionPointer to top of stack or load it into the LinkRegister to reestablish the return pc."
  	backEnd hasLinkRegister
  		ifTrue:
  			[self MoveAw: coInterpreter instructionPointerAddress R: LinkReg]
  		ifFalse:
  			[self MoveAw: coInterpreter instructionPointerAddress R: ClassReg.
  			 self MoveR: ClassReg Mw: 0 r: SPReg].
  	"Test primitive failure"
  	self MoveAw: coInterpreter primFailCodeAddress R: TempReg.
  	self flag: 'ask concrete code gen if move sets condition codes?'.
  	self CmpCq: 0 R: TempReg.
  	jmp := self JumpNonZero: 0.
  	"placing the test here attributes the tick to the primitive plus any checkForAndFollowForwardedPrimitiveState
  	 scanning, but attributes all of a failing primitive to the current method (in ceStackOverflow: on frame build)."
  	(backEnd has64BitPerformanceCounter
  	 and: [flags anyMask: PrimCallCollectsProfileSamples]) ifTrue:
  		[jumpToTakeSample := self genCheckForProfileTimerTick: (self registerMaskFor: NoReg)].
  	"Fetch result from stack"
  	continueAfterProfileSample :=
  	self MoveMw: (backEnd hasLinkRegister ifTrue: [0] ifFalse: [objectMemory wordSize])
  		r: SPReg
  		R: ReceiverResultReg.
  	self RetN: objectMemory wordSize.	"return to caller, popping receiver"
  	(backEnd has64BitPerformanceCounter
  	 and: [flags anyMask: PrimCallCollectsProfileSamples]) ifTrue:
  		[jumpToTakeSample jmpTarget: self Label.
  		 self genTakeProfileSample.
+ 		 backEnd genLoadStackPointerForPrimCall: ClassReg.
  		 backEnd hasLinkRegister
  			ifTrue:
  				[self MoveAw: coInterpreter instructionPointerAddress R: LinkReg]
  			ifFalse:
  				[self MoveAw: coInterpreter instructionPointerAddress R: ClassReg.
  				 self MoveR: ClassReg Mw: 0 r: SPReg].
  		 self Jump: continueAfterProfileSample].
  
  	"Jump to restore of receiver reg and proceed to frame build for failure."
  	 jmp jmpTarget: self Label.
  	 "Restore receiver reg from stack.  If on RISCs ret pc is in LinkReg, if on CISCs ret pc is on stack."
  	 self MoveMw: objectMemory wordSize * (methodOrBlockNumArgs + (backEnd hasLinkRegister ifTrue: [0] ifFalse: [1]))
  		r: SPReg
  		R: ReceiverResultReg.
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genCheckForProfileTimerTick: (in category 'primitive generators') -----
  genCheckForProfileTimerTick: liveRegisters
  	<inline: #always>
  	objectMemory wordSize = 8
  		ifTrue:
  			[| reg |
  			 reg := backEnd preferredRegisterForMovePerfCnt64RL = NoReg
  						ifTrue: [Arg0Reg]
  						ifFalse: [backEnd preferredRegisterForMovePerfCnt64RL].
  			 self MovePerfCnt64R: reg L: liveRegisters.
  			 self MoveAw: coInterpreter nextProfileTickAddress R: Arg1Reg.
+ 			 self CmpR: Arg1Reg R: reg.
+ 			 ^self JumpAboveOrEqual: 0]
- 			 self CmpR: reg R: Arg1Reg.
- 			 ^self JumpGreaterOrEqual: 0]
  		ifFalse:
  			[| effectiveLiveRegisters regLo regHi |
  			 self flag: #endianness.
  			 self deny: ((self registerMaskFor: ClassReg and: SendNumArgsReg) anyMask: liveRegisters).
  			 effectiveLiveRegisters := liveRegisters bitOr: (self registerMaskFor: ClassReg and: SendNumArgsReg).
  			 regLo := Arg0Reg. regHi := Arg1Reg.
  			 backEnd preferredRegisterPairForMovePerfCnt64RRLInto:
  				[:prefRegLo :prefRegHi|
  				(self register: prefRegLo isInMask: liveRegisters) ifFalse:
  					[regLo := prefRegLo].
  				(self register: prefRegHi isInMask: liveRegisters) ifFalse:
  					[regHi := prefRegHi]].
  			 self MoveAw: coInterpreter nextProfileTickAddress R: ClassReg.
  			 self MoveAw: coInterpreter nextProfileTickAddress + 4 R: SendNumArgsReg.
  			 self MovePerfCnt64R: regLo R: regHi L: liveRegisters.
+ 			 self SubR: ClassReg R: regLo.
+ 			 self SubbR: SendNumArgsReg R: regHi.
+ 			 ^self JumpAboveOrEqual: 0]!
- 			 self SubR: regLo R: ClassReg.
- 			 self SubbR: regHi R: SendNumArgsReg.
- 			 ^self JumpGreaterOrEqual: 0]!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genPrimReturnEnterCogCodeEnilopmart: (in category 'initialization') -----
  genPrimReturnEnterCogCodeEnilopmart: profiling
  	"Generate the substitute return code for an external or FFI primitive call.
  	 On success simply return, extracting numArgs from newMethod.
  	 On primitive failure call ceActivateFailingPrimitiveMethod: newMethod."
  	| jmpSample continuePostSample jmpFail |
  	<var: #jmpSample type: #'AbstractInstruction *'>
  	<var: #continuePostSample type: #'AbstractInstruction *'>
  	<var: #jmpFail type: #'AbstractInstruction *'>
  	self zeroOpcodeIndex.
  	backEnd hasVarBaseRegister ifTrue:
  		[self MoveCq: self varBaseAddress R: VarBaseReg]. "Must happen sometime"
  
  	"Test primitive failure"
  	self MoveAw: coInterpreter primFailCodeAddress R: TempReg.
  	self flag: 'ask concrete code gen if move sets condition codes?'.
  	self CmpCq: 0 R: TempReg.
  	jmpFail := self JumpNonZero: 0.
  
  	(profiling and: [backEnd has64BitPerformanceCounter]) ifTrue:
  		[jmpSample := self genCheckForProfileTimerTick: (self registerMaskFor: NoReg).
  		continuePostSample := self Label].
  
  	"Switch back to the Smalltalk stack.  Stack better be in either of these two states:
  		success:	stackPointer	->	result (was receiver)
  										arg1
  										...
  										argN
  										return pc
  		failure:							receiver
  										arg1
  										...
  					stackPointer	->	argN
  										return pc
  	We push the instructionPointer to reestablish the return pc in the success case,
  	but leave it to ceActivateFailingPrimitiveMethod: to do so in the failure case."
  
  	backEnd hasLinkRegister
  		ifTrue:
  			[backEnd genLoadStackPointers.											"Switch back to Smalltalk stack."
  			 backEnd hasPCRegister
  				ifTrue:
  					[self PopR: ReceiverResultReg.										"Pop result from stack"
  					 self MoveAw: coInterpreter instructionPointerAddress R: PCReg]	"Return"
  				ifFalse:
  					[self MoveMw: 0 r: SPReg R: ReceiverResultReg.						"Fetch result from stack"
  					 self MoveAw: coInterpreter instructionPointerAddress R: LinkReg.	"Get ret pc"
  					 self RetN: objectMemory wordSize]]								"Return, popping result from stack"
  		ifFalse:
  			[self MoveAw: coInterpreter instructionPointerAddress R: ClassReg.	"Get return pc"
  			 backEnd genLoadStackPointers.									"Switch back to Smalltalk stack."
  			 self MoveMw: 0 r: SPReg R: ReceiverResultReg.						"Fetch result from stack"
  			 self MoveR: ClassReg Mw: 0 r: SPReg.								"Restore return pc"
  			 self RetN: 0].														"Return, popping result from stack"
  
  	"Primitive failed.  Invoke C code to build the frame and continue."
  	jmpFail jmpTarget: (self MoveAw: coInterpreter newMethodAddress R: SendNumArgsReg).
  	"Reload sp with CStackPointer; easier than popping args of checkProfileTick."
  	self MoveAw: self cStackPointerAddress R: SPReg.
  	self 
  		compileCallFor: #ceActivateFailingPrimitiveMethod:
  		numArgs: 1
  		arg: SendNumArgsReg
  		arg: nil
  		arg: nil
  		arg: nil
  		resultReg: NoReg
  		regsToSave: self emptyRegisterMask.
  
  	"On Spur ceActivateFailingPrimitiveMethod: may retry the primitive and return if successful.
  	 So continue by returning to the caller.
  	 Switch back to the Smalltalk stack.  Stack should be in this state:
  				success:	stackPointer ->	result (was receiver)
  											arg1
  											...
  											argN
  											return pc
  	 We can push the instructionPointer or load it into the LinkRegister to reestablish the return pc"
  	self MoveAw: coInterpreter instructionPointerAddress
  		R: (backEnd hasLinkRegister ifTrue: [LinkReg] ifFalse: [ClassReg]).
  	backEnd genLoadStackPointers.
  	backEnd hasLinkRegister
  		ifTrue:
  			[self MoveMw: 0 r: SPReg R: ReceiverResultReg]	"Fetch result from stack"
  		ifFalse:
  			[self MoveMw: objectMemory wordSize r: SPReg R: ReceiverResultReg.	"Fetch result from stack"
  			 self PushR: ClassReg].											"Restore return pc on CISCs"
  	self RetN: objectMemory wordSize.	"return to caller, popping receiver"
  
  	(profiling and: [backEnd has64BitPerformanceCounter]) ifTrue:
+ 		["Call ceCheckProfileTick to record sample and then continue.  newMethod
- 		["Call ceCheckProfileTick: to record sample and then continue.  newMethod
  		 should be up-to-date.  Need to save and restore the link reg around this call."
  		 jmpSample jmpTarget: self Label.
+ 		 backEnd genMarshallNArgs: 0 arg: 0 arg: 0 arg: 0 arg: 0.
+ 		 self CallFullRT: (self cCode: [#ceCheckProfileTick asUnsignedInteger]
+ 							inSmalltalk: [self simulatedTrampolineFor: #ceCheckProfileTick]).
+ 		 backEnd genRemoveNArgsFromStack: 0.
- 		 backEnd saveAndRestoreLinkRegAround:
- 			[self CallFullRT: (self cCode: '(usqIntptr_t)ceCheckProfileTick'
- 						inSmalltalk: [self simulatedTrampolineFor: #ceCheckProfileTick])].
  		 self Jump: continuePostSample]!

Item was changed:
  ----- Method: StackInterpreter>>checkForEventsMayContextSwitch: (in category 'process primitive support') -----
  checkForEventsMayContextSwitch: mayContextSwitch
  	"Check for possible interrupts and handle one if necessary.
  	 Answer if a context switch has occurred."
  	| switched sema now |
  	<inline: false>
  	<var: #now type: #usqLong>
  	statCheckForEvents := statCheckForEvents + 1.
  
  	"restore the stackLimit if it has been smashed."
  	self restoreStackLimit.
  	self externalWriteBackHeadFramePointers.
  	self assert: stackPage = stackPages mostRecentlyUsedPage.
  
  	"Allow the platform to do anything it needs to do synchronously."
  	self ioSynchronousCheckForEvents.
  
  	self checkCogCompiledCodeCompactionCalledFor.
  
  	objectMemory needGCFlag ifTrue:
  		["sufficientSpaceAfterGC: runs the incremental GC and
  		 then, if not enough space is available, the fullGC."
  		 (objectMemory sufficientSpaceAfterGC: 0) ifFalse:
  			[self setSignalLowSpaceFlagAndSaveProcess]].
  
  	mayContextSwitch ifFalse: [^false].
  
  	switched := false.
  
  	(profileProcess ~= objectMemory nilObject
  	 or: [nextProfileTick > 0 and:[self ioHighResClock >= nextProfileTick]]) ifTrue:
+ 		[self zeroNextProfileTick.
- 		[nextProfileTick := 0.
  		 "Take a sample (if not already done so) for the profiler if it is active.  This
  		  must be done before any of the synchronousSignals below or else we will
  		  attribute a pause in ioRelinquishProcessor to the newly activated process."
  		 profileProcess = objectMemory nilObject ifTrue:
  			[profileProcess := self activeProcess.
  			 profileMethod := objectMemory nilObject].
  		 "and signal the profiler semaphore if it is present"
  		 (profileSemaphore ~= objectMemory nilObject
  		  and: [self synchronousSignal: profileSemaphore]) ifTrue:
  			[switched := true]].
  
  	objectMemory signalLowSpace ifTrue:
  		[objectMemory signalLowSpace: false. "reset flag"
  		 sema := objectMemory splObj: TheLowSpaceSemaphore.
  		 (sema ~= objectMemory nilObject
  		  and: [self synchronousSignal: sema]) ifTrue:
  			[switched := true]].
  
  	"inIOProcessEvents prevents reentrancy into ioProcessEvents and allows disabling
  	 ioProcessEvents e.g. for native GUIs.  We would like to manage that here but can't
  	 since the platform code may choose to call ioProcessEvents itself in various places."
  	false
  		ifTrue:
  			[((now := self ioUTCMicroseconds) >= nextPollUsecs
  			 and: [inIOProcessEvents = 0]) ifTrue:
  				[statIOProcessEvents := statIOProcessEvents + 1.
  				 inIOProcessEvents := inIOProcessEvents + 1.
  				 self ioProcessEvents. "sets interruptPending if interrupt key pressed; may callback"
  				 inIOProcessEvents > 0 ifTrue:
  					[inIOProcessEvents := inIOProcessEvents - 1].
  				 nextPollUsecs := now + 20000
  				 "msecs to wait before next call to ioProcessEvents.  Note that strictly
  				  speaking we might need to update 'now' at this point since
  				  ioProcessEvents could take a very long time on some platforms"]]
  		ifFalse:
  			[(now := self ioUTCMicroseconds) >= nextPollUsecs ifTrue:
  				[statIOProcessEvents := statIOProcessEvents + 1.
  				 self ioProcessEvents. "sets interruptPending if interrupt key pressed; may callback"
  				 nextPollUsecs := now + 20000
  				 "msecs to wait before next call to ioProcessEvents.  Note that strictly
  				  speaking we might need to update 'now' at this point since
  				  ioProcessEvents could take a very long time on some platforms"]].
  
  	interruptPending ifTrue:
  		[interruptPending := false.
  		 "reset interrupt flag"
  		 sema := objectMemory splObj: TheInterruptSemaphore.
  		 (sema ~= objectMemory nilObject
  		  and: [self synchronousSignal: sema]) ifTrue:
  			[switched := true]].
  
  	nextWakeupUsecs ~= 0 ifTrue:
  		[now >= nextWakeupUsecs ifTrue:
  			[nextWakeupUsecs := 0.
  			 "set timer interrupt to 0 for 'no timer'"
  			 sema := objectMemory splObj: TheTimerSemaphore.
  			 (sema ~= objectMemory nilObject
  			  and: [self synchronousSignal: sema]) ifTrue:
  				[switched := true]]].
  
  	"signal any pending finalizations"
  	pendingFinalizationSignals > 0 ifTrue:
  		[pendingFinalizationSignals := 0.
  		 sema := objectMemory splObj: TheFinalizationSemaphore.
  		 (sema ~= objectMemory nilObject
  		  and: [self synchronousSignal: sema]) ifTrue:
  			[switched := true]].
  
  	"signal all semaphores in semaphoresToSignal"
  	self signalExternalSemaphores ifTrue:
  		[switched := true].
  
  	^switched!

Item was changed:
  ----- Method: StackInterpreter>>checkProfileTick: (in category 'process primitive support') -----
  checkProfileTick: aPrimitiveMethod
  	"Check if the profile timer has expired and if so take a sample.
  	 If the primitive has failed sample the profileMethod as nil."
  	<inline: false>
  	self assert: nextProfileTick ~= 0.
  	self ioHighResClock >= nextProfileTick ifTrue:
  		[profileProcess := self activeProcess.
  		 profileMethod := self successful ifTrue: [aPrimitiveMethod] ifFalse: [objectMemory nilObject].
  		 self forceInterruptCheck.
+ 		 self zeroNextProfileTick]!
- 		 nextProfileTick := 0]!

Item was added:
+ ----- Method: StackInterpreter>>zeroNextProfileTick (in category 'process primitive support') -----
+ zeroNextProfileTick
+ 	"this is a hook for the simulator..."
+ 	<inline: #always>
+ 	nextProfileTick := 0!



More information about the Vm-dev mailing list