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

commits at source.squeak.org commits at source.squeak.org
Fri Aug 6 03:35:26 UTC 2021


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

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

Name: VMMaker.oscog-eem.3028
Author: eem
Time: 5 August 2021, 8:26:48.025191 pm
UUID: fb9d7e7c-4f0c-475c-81a3-1c3952da642c
Ancestors: VMMaker.oscog-eem.3027

Cogit: reimplement profiling support for AndreasSystemProfiler:

- check the profile clock *after* a primitive has succeeded, not before.  testing before is clearly broken (what was I thinking?!?!?).
- use the same support that ioHighResClock uses; hence no AArch32 support for now (but we could put a SIGSEGV handler around an initiali invocation to check if support is available).
- Add a new operand type for CogRTLOpcodes; L means "live registers" and allows the code generators to generate tight code for MovePerfCnt64RRL & MovePerfCnt64RL, avoiding saving registers that are not live.
- rewrite compileInterpreterPrimitive:flags: to split off the sideways call, and make the flow through a normal call, retry, prodflie sample sequence.

Frame printing: go some way to printing strings better for arg fields of a frame.  This stuff needs regularizing.

Simulation: fix accessing the two halves of nextProfileTick om 32-bit platforms.

In-image compilation: fix compiling a primitive with profiling turned on.  There's still probles with compiling 64-bit methods on a 32-bit ISA (& possibly vice verse).

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

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 and: [InitializationOptions at: #profiling ifAbsent: [false]]) ifTrue:
+ 			[nextProfileTick := 1]].
- 		[newMethod = 0 ifTrue: [newMethod := objectMemory nilObject]].
  	self checkProfileTick: newMethod!

Item was added:
+ ----- 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.
+ 	nextProfileTick := 0!

Item was changed:
  ----- Method: CoInterpreter>>nextProfileTickAddress (in category 'trampoline support') -----
  nextProfileTickAddress
  	<api>
  	<returnTypeC: #usqInt>
  	"N.B. nextProfileTick is 64-bits"
  	^self cCode: [(self addressOf: nextProfileTick) asUnsignedInteger]
  		inSmalltalk:
  			[objectMemory wordSize = 8
  				ifTrue:
  					[cogit simulatedReadWriteVariableAddress: #nextProfileTick in: self]
  				ifFalse:
+ 					["This looks weird, but the cogit doles out fake addresses counting down from
+ 					  16r80000000, so we have to ask for the halves backwards to get them in the
+ 					  right order, and ask for both now so that botehr get defined at teh same time
+ 					  and are hence contiguous in memory."
+ 					 VMBIGENDIAN
- 					[VMBIGENDIAN
  						ifTrue:
+ 							[cogit simulatedReadWriteVariableAddress: #nextProfileTickHigh in: self.
+ 							 cogit simulatedReadWriteVariableAddress: #nextProfileTickLow in: self.
- 							[cogit simulatedReadWriteVariableAddress: #nextProfileTickLow in: self.
  							 cogit simulatedReadWriteVariableAddress: #nextProfileTickHigh in: self]
  						ifFalse:
+ 							[cogit simulatedReadWriteVariableAddress: #nextProfileTickLow in: self.
+ 							 cogit simulatedReadWriteVariableAddress: #nextProfileTickHigh in: self.
- 							[cogit simulatedReadWriteVariableAddress: #nextProfileTickHigh in: self.
  							 cogit simulatedReadWriteVariableAddress: #nextProfileTickLow in: self]]]!

Item was added:
+ ----- Method: CoInterpreter>>primitivePropertyFlagsFor: (in category 'cog jit support') -----
+ primitivePropertyFlagsFor: externalBytecodedMethod
+ 	<doNotGenerate>
+ 	"Support for in-image compilation.  This is intended to do for methods in the image what
+ 	 functionPointerForCompiledMethod:primitiveIndex:primitivePropertyFlagsInto: does for methods in the simulation."
+ 	| flags metadata |
+ 	flags := self primitivePropertyFlags: externalBytecodedMethod primitive.
+ 	externalBytecodedMethod primitive = PrimNumberExternalCall ifTrue:
+ 		 [metadata := self class metadataFlagsForPrimitive: externalBytecodedMethod.
+ 		  flags := flags bitOr: ((metadata bitAnd: SpurPrimitiveFlagsMask) bitShift: PrimitiveMetadataFlagsShift).
+ 		(InitializationOptions at: #profiling ifAbsent: [false]) ifTrue:
+ 			[flags := flags bitOr: PrimCallCollectsProfileSamples]].
+ 	^flags!

Item was added:
+ ----- Method: CoInterpreter>>primitivePropertyFlagsFor:primitiveIndex: (in category 'cog jit support') -----
+ primitivePropertyFlagsFor: externalBytecodedMethod primitiveIndex: primIndex
+ 	<doNotGenerate>
+ 	"Support for in-image compilation.  This is intended to do for methods in the image what
+ 	 functionPointerForCompiledMethod:primitiveIndex:primitivePropertyFlagsInto: does for methods in the simulation."
+ 	| flags metadata |
+ 	flags := self primitivePropertyFlags: primIndex.
+ 	primIndex = PrimNumberExternalCall ifTrue:
+ 		[metadata := self class metadataFlagsForPrimitive: externalBytecodedMethod.
+ 		 "nuke base flags..."
+ 		 flags := (metadata bitAnd: SpurPrimitiveFlagsMask) bitShift: PrimitiveMetadataFlagsShift.
+ 		 (InitializationOptions at: #profiling ifAbsent: [false]) ifTrue:
+ 			[flags := flags bitOr: PrimCallCollectsProfileSamples]].
+ 	^flags!

Item was changed:
  ----- Method: CoInterpreterPrimitives>>primitiveProfileSemaphore (in category 'process primitives') -----
  primitiveProfileSemaphore
  	"Primitive. Install the semaphore to be used for profiling, 
  	or nil if no semaphore should be used.
  	See also primitiveProfileStart."
+ 	| sema flushState |
- 	| sema flushState activeContext |
  	<export: true>
- 	self methodArgumentCount ~= 1 ifTrue:
- 		[^self primitiveFailFor: PrimErrBadNumArgs].
  	sema := self stackValue: 0.
  	sema = objectMemory nilObject
  		ifTrue:
  			[flushState := profileSemaphore ~= objectMemory nilObject]
  		ifFalse:
  			[flushState := profileSemaphore = objectMemory nilObject.
  			 (objectMemory isSemaphoreOop: sema) ifFalse:
  				[^self primitiveFailFor: PrimErrBadArgument]].
  	profileSemaphore := sema.
+ 	profileProcess := profileMethod := objectMemory nilObject.
  	"If we've switched profiling on or off we must void machine code
  	 (and machine code pcs in contexts) since we will start or stop
  	 testing the profile clock in machine code primitive invocations,
  	 and so generate slightly different code from here on in."
+ 	flushState
+ 		ifTrue: [self flushExternalPrimitives]
+ 		ifFalse: [self methodReturnReceiver]!
- 	flushState ifTrue:
- 		[self push: instructionPointer.
- 		 activeContext := self voidVMStateForSnapshotFlushingExternalPrimitivesIf: false.
- 		 self marryContextInNewStackPageAndInitializeInterpreterRegisters: activeContext.
- 		 self assert: (((self stackValue: 0) = objectMemory nilObject and: [profileSemaphore = objectMemory nilObject])
- 				  or: [(self stackValue: 0) = profileSemaphore
- 					  and: [objectMemory isSemaphoreOop: sema]])].
- 	profileProcess := profileMethod := objectMemory nilObject.
- 	self pop: 1.
- 	flushState ifTrue:
- 		[cogit ceInvokeInterpret]!

Item was added:
+ ----- Method: CogARMCompiler>>has64BitPerformanceCounter (in category 'testing') -----
+ has64BitPerformanceCounter
+ 	"AArch32 has a 64-bit counter but it is typically restricted.
+ 	 So for now do without.
+ 	 See e.g. http://neocontra.blogspot.com/2013/05/user-mode-performance-counters-for.html
+ 		https://stackoverflow.com/questions/3247373/how-to-measure-program-execution-time-in-arm-cortex-a8-processor/3250835#3250835"
+ 	<inline: #always>
+ 	^false!

Item was added:
+ ----- Method: CogARMCompiler>>preferredRegisterPairForMovePerfCnt64RRLInto: (in category 'testing') -----
+ preferredRegisterPairForMovePerfCnt64RRLInto: aBlock
+ 	"Evaluate aBlock with the preferred registers to receive the
+ 	 low and high 32-bits of the 64-bit performance counter.
+ 	 AArch32 has a 64-bit counter but it is typically restricted.
+ 	 So for now do without.
+ 	 See e.g. http://neocontra.blogspot.com/2013/05/user-mode-performance-counters-for.html
+ 		https://stackoverflow.com/questions/3247373/how-to-measure-program-execution-time-in-arm-cortex-a8-processor/3250835#3250835"
+ 	<inline: #always>
+ 	aBlock value: NoReg value: NoReg!

Item was changed:
  CogAbstractInstruction subclass: #CogARMv8Compiler
  	instanceVariableNames: ''
+ 	classVariableNames: 'AL ArithmeticAdd ArithmeticAddS ArithmeticSub ArithmeticSubS CASAL CArg0Reg CArg1Reg CArg2Reg CArg3Reg CArg4Reg CArg5Reg CArg6Reg CBNZ CBZ CC CCMPNE CLREX CS CSET D0 D1 D10 D11 D12 D13 D14 D15 D16 D17 D18 D19 D2 D20 D21 D22 D23 D24 D25 D26 D27 D28 D29 D3 D30 D31 D4 D5 D6 D7 D8 D9 DC DC_CISW DC_CIVAC DC_CSW DC_CVAC DC_CVAU DC_ISW DC_IVAC DC_ZVA DMB DSB DSB_ALL DSB_ALLSY DSB_ISH DSB_NSH DSB_OSH DSB_READS DSB_SY DSB_WRITES DivRRR EQ FP GE GT HI IC IC_IALLU IC_IALLUIS IC_IVAU ISB LDAXR LE LR LS LT LogicalAnd LogicalAndS LogicalOr LogicalXor MI MRS_CTR_EL0 MRS_ID_AA64ISAR0_EL1 MSubRRR MoveAwRR MoveRRAw MulOverflowRRR MulRRR NE NativePopRR NativePushRR PL R0 R1 R10 R11 R12 R13 R14 R15 R16 R17 R18 R19 R2 R20 R21 R22 R23 R24 R25 R26 R27 R28 R29 R3 R30 R31 R4 R5 R6 R7 R8 R9 SMULHRRR SP STLR STLXR SXTB SXTH SXTW SXTX UXTB UXTH UXTW UXTX VC VS XZR'
- 	classVariableNames: 'AL ArithmeticAdd ArithmeticAddS ArithmeticSub ArithmeticSubS CASAL CArg0Reg CArg1Reg CArg2Reg CArg3Reg CArg4Reg CArg5Reg CArg6Reg CBNZ CBZ CC CCMPNE CLREX CS CSET D0 D1 D10 D11 D12 D13 D14 D15 D16 D17 D18 D19 D2 D20 D21 D22 D23 D24 D25 D26 D27 D28 D29 D3 D30 D31 D4 D5 D6 D7 D8 D9 DC DC_CISW DC_CIVAC DC_CSW DC_CVAC DC_CVAU DC_ISW DC_IVAC DC_ZVA DMB DSB DSB_ALL DSB_ALLSY DSB_ISH DSB_NSH DSB_OSH DSB_READS DSB_SY DSB_WRITES DataCacheFlushRequired DataCacheLineLength DivRRR EQ FP GE GT HI HasAtomicInstructions IC IC_IALLU IC_IALLUIS IC_IVAU ISB InstructionCacheFlushRequired InstructionCacheLineLength LDAXR LE LR LS LT LogicalAnd LogicalAndS LogicalOr LogicalXor MI MRS_CTR_EL0 MRS_ID_AA64ISAR0_EL1 MSubRRR MoveAwRR MoveRRAw MulOverflowRRR MulRRR NE NativePopRR NativePushRR PL R0 R1 R10 R11 R12 R13 R14 R15 R16 R17 R18 R19 R2 R20 R21 R22 R23 R24 R25 R26 R27 R28 R29 R3 R30 R31 R4 R5 R6 R7 R8 R9 SMULHRRR SP STLR STLXR SXTB SXTH SXTW SXTX UXTB UXTH UXTW UXTX VC VS XZR'
  	poolDictionaries: 'ARMv8A64Opcodes'
  	category: 'VMMaker-JIT'!
  
  !CogARMv8Compiler commentStamp: 'eem 1/7/2021 23:01' prior: 0!
  I generate ARMv8 machine code instructions from CogAbstractInstructions with CogRTLOpcodes.
  Here in "Arm ARM" refers to
  	Arm® Architecture Reference Manual
  	Armv8, for Armv8-A architecture profile
  https://developer.arm.com/docs/ddi0487/latest/arm-architecture-reference-manual-armv8-for-armv8-a-architecture-profile
  
  Some things to know about ARMv8 instructions:
  Whether 31 in a register field implies the zero register or the SP register(s) depends on the specific instruction.
  
  C3.2.1 Load/Store register
  If a Load instruction specifies writeback and the register being loaded is also the base register,
  then behavior is CONSTRAINED UNPREDICTABLE and one of the following behaviors must occur:
  - The instruction is treated as UNDEFINED.
  - The instruction is treated as a NOP.
  - The instruction performs the load using the specified addressing mode and the base register
    becomes UNKNOWN.  In addition, if an exception occurs during the execution of such an
    instruction, the base address might be corrupted so that the instruction cannot be repeated.
  If a Store instruction performs a writeback and the register that is stored is also the base register,
  then behavior is CONSTRAINED UNPREDICTABLE and one of the following behaviors must occur:
  - The instruction is treated as UNDEFINED.
  - The instruction is treated as a NOP.
  - The instruction performs the store to the designated register using the specified addressing
    mode, but the value stored is UNKNOWN.!

Item was added:
+ ----- Method: CogARMv8Compiler>>concretizeMovePerfCnt64RL (in category 'generate machine code - concretize') -----
+ concretizeMovePerfCnt64RL
+ 	"D13.8.26		CNTVCT_EL0, Counter-timer Virtual Count register		p D13-3774"
+ 
+ 	"MRS <Xt>, CNTVCT_EL0		op0:0b11 op1:0b011 CRn:0b1110 CRm:0b0000 op2:0b010"
+ 	machineCode
+ 		at: 0
+ 		put: (2r1101010100111 << 19 "MRS + op0"
+ 			+ (2r011 << 16)	"op1"
+ 			+ (2r1110 << 12)	"CRn"
+ 			+ (2r010 << 5)
+ 			+ (operands at: 0)).
+ 	^4
+ 	"cogit processor disassembleInstructionAt: 0 In: machineCode object"!

Item was changed:
  ----- Method: CogARMv8Compiler>>dispatchConcretize (in category 'generate machine code') -----
  dispatchConcretize
  	"Attempt to generate concrete machine code for the instruction at address.
  	 This is the inner dispatch of concretizeAt: actualAddress which exists only
  	 to get around the branch size limits in the SqueakV3 (blue book derived)
  	 bytecode set."
  		 
  	opcode caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]					-> [^self concretizeLabel].
  		[Literal]					-> [^self concretizeLiteral].
  		[AlignmentNops]		-> [^self concretizeAlignmentNops].
  		[Fill32]					-> [^self concretizeFill32].
  		[Nop]					-> [^self concretizeNop].
  		"Control"
  		[Call]						-> [^self concretizeCall]. "call code within code space"
  		[CallFull]					-> [^self concretizeCallJumpFull: true]. "call code anywhere in address space"
  		[JumpR]					-> [^self concretizeJumpR].
  		[JumpFull]					-> [^self concretizeCallJumpFull: false]."jump within address space"
  		[JumpLong]				-> [^self concretizeJumpLong]."jump within code space"
  		[JumpLongZero]			-> [^self concretizeConditionalLongJump: EQ].
  		[JumpLongNonZero]		-> [^self concretizeConditionalLongJump: NE].
  		[Jump]						-> [^self concretizeConditionalJump: AL]. "jump within a method, etc"
  		[JumpZero]					-> [^self concretizeConditionalJump: EQ].
  		[JumpNonZero]				-> [^self concretizeConditionalJump: NE].
  		[JumpNegative]				-> [^self concretizeConditionalJump: MI].
  		[JumpNonNegative]			-> [^self concretizeConditionalJump: PL].
  		[JumpOverflow]				-> [^self concretizeConditionalJump: VS].
  		[JumpNoOverflow]			-> [^self concretizeConditionalJump: VC].
  		[JumpMulOverflow]			-> [^self concretizeMulOverflowJump].
  		[JumpNoMulOverflow]		-> [^self concretizeMulOverflowJump].
  		[JumpCarry]				-> [^self concretizeConditionalJump: CS].
  		[JumpNoCarry]				-> [^self concretizeConditionalJump: CC].
  		[JumpLess]					-> [^self concretizeConditionalJump: LT].
  		[JumpGreaterOrEqual]		-> [^self concretizeConditionalJump: GE].
  		[JumpGreater]				-> [^self concretizeConditionalJump: GT].
  		[JumpLessOrEqual]			-> [^self concretizeConditionalJump: LE].
  		[JumpBelow]				-> [^self concretizeConditionalJump: CC]. "unsigned lower"
  		[JumpAboveOrEqual]		-> [^self concretizeConditionalJump: CS]. "unsigned greater or equal"
  		[JumpAbove]				-> [^self concretizeConditionalJump: HI].
  		[JumpBelowOrEqual]		-> [^self concretizeConditionalJump: LS].
  		[JumpFPEqual]				-> [^self concretizeConditionalJump: EQ].
  		[JumpFPNotEqual]			-> [^self concretizeConditionalJump: NE].
  		[JumpFPLess]				-> [^self concretizeConditionalJump: LT].
  		[JumpFPGreaterOrEqual]	-> [^self concretizeConditionalJump: GE].
  		[JumpFPGreater]			-> [^self concretizeConditionalJump: GT].
  		[JumpFPLessOrEqual]		-> [^self concretizeConditionalJump: LE].
  		[JumpFPOrdered]			-> [^self concretizeConditionalJump: VC].
  		[JumpFPUnordered]		-> [^self concretizeConditionalJump: VS].
  		[RetN]						-> [^self concretizeRetN].
  		[NativeRetN]				-> [^self concretizeNativeRetN].
  		[Stop]						-> [^self concretizeStop].
  		"Arithmetic"
  		[AddCqR]						-> [^self concretizeAddCqRDest: (operands at: 1)].
  		[AddCqRR]						-> [^self concretizeAddCqRDest: (operands at: 2)].
  		[AndCqR]						-> [^self concretizeLogicalOp: LogicalAndS CqRDest: (operands at: 1)].
  		[AndCqRR]						-> [^self concretizeLogicalOp: LogicalAndS CqRDest: (operands at: 2)].
  		[OrCqR]						-> [^self concretizeLogicalOp: LogicalOr CqRDest: (operands at: 1)].
  		[OrCqRR]						-> [^self concretizeLogicalOp: LogicalOr CqRDest: (operands at: 2)].
  		[CmpCqR]						-> [^self concretizeCmpCqR].
  		[SubCqR]						-> [^self concretizeSubCqR].
  		[TstCqR]						-> [^self concretizeLogicalOp: LogicalAndS CqRDest: XZR].
  		[XorCqR]						-> [^self concretizeLogicalOp: LogicalXor CqRDest: (operands at: 1)].
  		[AddCwR]						-> [^self concretizeCwRArithmetic: ArithmeticAddS Rd: (operands at: 1)].
  		[AndCwR]						-> [^self concretizeCwRLogical: LogicalAndS].
  		[CmpCwR]						-> [^self concretizeCwRArithmetic: ArithmeticSubS Rd: XZR].
  		[CmpC32R]						-> [^self concretizeCmpC32R].
  		[OrCwR]						-> [^self concretizeCwRLogical: LogicalOr].
  		[SubCwR]						-> [^self concretizeCwRArithmetic: ArithmeticSubS Rd: (operands at: 1)].
  		[XorCwR]						-> [^self concretizeCwRLogical: LogicalXor].
  		[AddRR]						-> [^self concretizeRRArithmetic: ArithmeticAddS Rd: (operands at: 1)].
  		[AndRR]						-> [^self concretizeRRLogical: LogicalAndS].
  		[CmpRR]						-> [^self concretizeRRArithmetic: ArithmeticSubS Rd: XZR].
  		[OrRR]							-> [^self concretizeRRLogical: LogicalOr].
  		[SubRR]						-> [^self concretizeRRArithmetic: ArithmeticSubS Rd: (operands at: 1)].
  		[XorRR]							-> [^self concretizeRRLogical: LogicalXor].
  		[AddRRR]						-> [^self concretizeRRArithmetic: ArithmeticAddS Rd: (operands at: 2)].
  		[SubRRR]						-> [^self concretizeRRArithmetic: ArithmeticSubS Rd: (operands at: 2)].
  		[AddRdRd]						-> [^self concretizeMathRdRd: 2r1010].
  		[CmpRdRd]						-> [^self concretizeCmpRdRd].
  		[DivRdRd]						-> [^self concretizeMathRdRd: 2r0110].
  		[MulRdRd]						-> [^self concretizeMathRdRd: 2r0010].
  		[SubRdRd]						-> [^self concretizeMathRdRd: 2r1110].
  		[XorRdRd]						-> [^self concretizeXorRdRd].
  		[SqrtRd]						-> [^self concretizeSqrtRd].
  		[NegateR]						-> [^self concretizeNegateR].
  		[LoadEffectiveAddressMwrR]	-> [^self concretizeLoadEffectiveAddressMwrR].
  		[ArithmeticShiftRightCqR]		-> [^self concretizeArithmeticShiftRightCqR].
  		[ArithmeticShiftRightCqRR]		-> [^self concretizeArithmeticShiftRightCqRR].
  		[LogicalShiftRightCqR]			-> [^self concretizeLogicalShiftRightCqR].
  		[LogicalShiftRightCqRR]		-> [^self concretizeLogicalShiftRightCqRR].
  		[LogicalShiftLeftCqR]			-> [^self concretizeLogicalShiftLeftCqR].
  		[LogicalShiftLeftCqRR]			-> [^self concretizeLogicalShiftLeftCqRR].
  		[ArithmeticShiftRightRR]		-> [^self concretizeShiftRR: 2r001010].
  		[LogicalShiftLeftRR]				-> [^self concretizeShiftRR: 2r001000].
  		[LogicalShiftRightRR]			-> [^self concretizeShiftRR: 2r001001].
  		[RotateRightCqR]				-> [^self concretizeRotateCqR].
  		[RotateLeftCqR]				-> [^self concretizeRotateCqR].
  		[ClzRR]							-> [^self concretizeClzRR].
  		"ARM Specific Arithmetic"
  		[MulRRR]						-> [^self concretizeMulRRR].
  		[MulOverflowRRR]				-> [^self concretizeMulOverflowRRR].
  		[DivRRR]						-> [^self concretizeDivRRR].
  		[MSubRRR]						-> [^self concretizeMSubRRR].
  		"ARM Specific Cache Control"
  		[DC]							-> [^self concretizeDataCacheControl].
  		[DSB]							-> [^self concretizeDataSynchronizationBarrier].
  		[IC]								-> [^self concretizeInstructionCacheControl].
  		[ISB]							-> [^self concretizeInstructionSynchronizationBarrier].
  		[MRS_CTR_EL0]					-> [^self concretizeMRS_CTR_EL0].
  		[MRS_ID_AA64ISAR0_EL1]		-> [^self concretizeMRS_ID_AA64ISAR0_EL1].
  		"Data Movement"
  		[MoveCqR]			-> [^self concretizeMoveCqR].
  		[MoveCwR]			-> [^self concretizeMoveCwR].
  		[MoveC32R]		-> [^self concretizeMoveC32R].
  		[MoveRR]			-> [^self concretizeMoveRR].
  		[MoveRRd]			-> [^self concretizeMoveRRd].
  		[MoveRdR]			-> [^self concretizeMoveRdR].
  		[MoveAwR]			-> [^self concretizeMoveAwR].
  		[MoveRAw]			-> [^self concretizeMoveRAw].
  		[MoveAwRR]		-> [^self concretizeMoveAwRR].
  		[MoveRRAw]		-> [^self concretizeMoveRRAw].
  		[MoveAbR] 			-> [^self concretizeMoveAbR].
   		[MoveRAb]			-> [^self concretizeMoveRAb].
  		[MoveMwrR]		-> [^self concretizeMoveMSrR: 3].
  		[MoveM32rR]		-> [^self concretizeMoveMSrR: 2].
  		[MoveM16rR]		-> [^self concretizeMoveMSrR: 1].
  		[MoveMbrR]		-> [^self concretizeMoveMSrR: 0].
  		[MoveRMwr]		-> [^self concretizeMoveRMSr: 3].
  		[MoveRM32r]		-> [^self concretizeMoveRMSr: 2].
  		[MoveRM16r]		-> [^self concretizeMoveRMSr: 1].
  		[MoveRMbr]		-> [^self concretizeMoveRMSr: 0].
  		[MoveXwrRR]		-> [^self concretizeMoveXSrRR: 3].
  		[MoveX32rRR]		-> [^self concretizeMoveXSrRR: 2].
  		[MoveX16rRR]		-> [^self concretizeMoveXSrRR: 1].
  		[MoveXbrRR]		-> [^self concretizeMoveXSrRR: 0].
  		[MoveRXwrR]		-> [^self concretizeMoveRXSrR: 3].
  		[MoveRX32rR]		-> [^self concretizeMoveRXSrR: 2].
  		[MoveRX16rR]		-> [^self concretizeMoveRXSrR: 1].
  		[MoveRXbrR]		-> [^self concretizeMoveRXSrR: 0].
  		[MoveM64rRd]		-> [^self concretizeMoveM64rRd].
  		[MoveRdM64r]		-> [^self concretizeMoveRdM64r].
  		[PopR]				-> [^self concretizePopR].
  		[PushR]				-> [^self concretizePushR].
  		[NativePopRR]		-> [^self concretizeNativePopRR].
  		[NativePushRR]		-> [^self concretizeNativePushRR].
  		[PushCq]			-> [^self concretizePushCq].
  		[PushCw]			-> [^self concretizePushCw].
  		[PrefetchAw]		-> [^self concretizePrefetchAw].
  		"Conversion"
  		[ConvertRRd]		-> [^self concretizeConvertRRd].
  		[ConvertRdR]		-> [^self concretizeConvertRdR].
  		"[ConvertRRs]		-> [^self concretizeConvertRRs].
  		[ConvertRsR]		-> [^self concretizeConvertRsR].
  		[ConvertRsRd]		-> [^self concretizeConvertRsRd].
  		[ConvertRdRs]		-> [^self concretizeConvertRdRs]."
  			
  		[SignExtend8RR]	-> [^self concretizeSignExtendRR: 8].
  		[SignExtend16RR]	-> [^self concretizeSignExtendRR: 16].
  		[SignExtend32RR]	-> [^self concretizeSignExtendRR: 32].
  		
  		[ZeroExtend8RR]	-> [^self concretizeZeroExtendRR: 8].
  		[ZeroExtend16RR]	-> [^self concretizeZeroExtendRR: 16].
  		[ZeroExtend32RR]	-> [^self concretizeZeroExtendRR: 32].
  
  		"Multi-processing"
  		[LDAXR]			-> [^self concretizeLDAXR].
  		[STLXR]			-> [^self concretizeSTLXR].
  		[CLREX]			-> [^self concretizeCLREX].
  		[STLR]				-> [^self concretizeSTLR].
  		[CASAL]			-> [^self concretizeCASAL].
  		[CCMPNE]			-> [^self concretizeCCMPNE].
  		[CSET]				-> [^self concretizeCSET].
  		[CBNZ]				-> [^self concretizeCB].
+ 		[CBZ]				-> [^self concretizeCB].
- 		[CBZ]				-> [^self concretizeCB]. }.
  
+ 		"miscellaneous"
+ 		[MovePerfCnt64RL]	->	[^self concretizeMovePerfCnt64RL] }.
+ 
  	^0 "keep Slang happy"!

Item was added:
+ ----- Method: CogARMv8Compiler>>preferredRegisterForMovePerfCnt64RL (in category 'feature detection') -----
+ preferredRegisterForMovePerfCnt64RL
+ 	"Answer the preferred register to receive the 64-bit performance counter,
+ 	 or NoReg if none."
+ 	<inline: #always>
+ 	^NoReg!

Item was removed:
- ----- Method: CogAbstractInstruction>>genLoadStackPointersForFastPrimCall: (in category 'smalltalk calling convention') -----
- genLoadStackPointersForFastPrimCall: 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: [self genLoadStackPointers]
- 		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;
- 				MoveAw: cogit framePointerAddress R: FPReg].
- 	^0!

Item was added:
+ ----- Method: CogAbstractInstruction>>genLoadStackPointersForPrimCall: (in category 'smalltalk calling convention') -----
+ genLoadStackPointersForPrimCall: 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: [self genLoadStackPointers]
+ 		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;
+ 				MoveAw: cogit framePointerAddress R: FPReg].
+ 	^0!

Item was added:
+ ----- Method: CogAbstractInstruction>>has64BitPerformanceCounter (in category 'testing') -----
+ has64BitPerformanceCounter
+ 	"At least x86, x86_64, AArch32 and AArch64 have a 64-bit performance counter.
+ 	 Subclasses can turn this off if rquired."
+ 	<inline: #always>
+ 	^true!

Item was added:
+ ----- Method: CogAbstractInstruction>>preferredRegisterForMovePerfCnt64RL (in category 'feature detection') -----
+ preferredRegisterForMovePerfCnt64RL
+ 	"Answer the preferred register to receive the 64-bit performance counter,
+ 	 or NoReg if none."
+ 	<inline: #always>
+ 	objectMemory wordSize = 8 ifTrue:
+ 		[self subclassResponsibility]!

Item was added:
+ ----- Method: CogAbstractInstruction>>preferredRegisterPairForMovePerfCnt64RRLInto: (in category 'feature detection') -----
+ preferredRegisterPairForMovePerfCnt64RRLInto: aBlock
+ 	"Evaluate aBlock with the preferred registers to receive the
+ 	 low and high 32-bits of the 64-bit performance counter."
+ 	<inline: #always>
+ 	objectMemory wordSize = 4 ifTrue:
+ 		[self subclassResponsibility]!

Item was changed:
  ----- Method: CogIA32Compiler>>computeMaximumSize (in category 'generate machine code') -----
(excessive size, no diff calculated)

Item was added:
+ ----- Method: CogIA32Compiler>>concretizeMovePerfCnt64RRL (in category 'generate machine code - concretize') -----
+ concretizeMovePerfCnt64RRL
+ 	"Generate code for
+ 		0x0: 50				pushl  %eax
+ 		0x1: 52				pushl  %edx
+ 		0x2: 0f 31			rdtsc
+ 		0x4: 89 f8			movl   %edi, %eax
+ 		0x6: 89 f2			movl   %esi, %edx
+ 		0x8: 5a				popl   %edx
+ 	 et al"
+ 	| regLo regHi liveRegisters offset |
+ 	regLo := operands at: 0.
+ 	regHi := operands at: 1.
+ 	liveRegisters := operands at: 2.
+ 	offset := 0.
+ 	(liveRegisters anyMask: (cogit registerMaskFor: EAX)) ifTrue:
+ 		[machineCode at: 0 put: 16r50. "push %eax"
+ 		 offset := offset + 1].
+ 	(liveRegisters anyMask: (cogit registerMaskFor: EDX)) ifTrue:
+ 		[machineCode at: offset put: 16r52. "push %edx"
+ 		 offset := offset + 1].
+ 	"too lazy to define the swap cases for the moment..."
+ 	self deny: (regLo = EDX or: [regHi = EAX]).
+ 	machineCode
+ 		at: offset		put: 16r0F;									"rdtsc"
+ 		at: offset + 1	put: 16r31.
+ 	offset := offset + 2.
+ 	regHi ~= EDX ifTrue:
+ 		[machineCode
+ 			at: offset		put: 16r89;									"movq	%edx, (=>) %regHi"
+ 			at: offset + 1	put: (self mod: ModReg RM: regHi RO: EDX).
+ 		 offset := offset + 2].
+ 	regLo ~= EAX ifTrue:
+ 		[machineCode
+ 			at: offset + 4	put: 16r89;									"movq	%eax, (=>) %regLo"
+ 			at: offset + 5	put: (self mod: ModReg RM: regLo RO: EAX).
+ 		 offset := offset + 2].
+ 	(liveRegisters anyMask: (cogit registerMaskFor: EDX)) ifTrue:
+ 		[machineCode at: offset put: 16r5A. "pop %edx"
+ 		 offset := offset + 1].
+ 	(liveRegisters anyMask: (cogit registerMaskFor: EAX)) ifTrue:
+ 		[machineCode at: offset put: 16r58. "pop %eax"
+ 		 offset := offset + 1].
+ 	^offset
+ 
+ 	"(liveRegisters anyMask: (cogit registerMaskFor: EAX and: EDX))
+ 		ifTrue:
+ 			[{	cogit processor disassembleInstructionAt: 0 In: machineCode object.
+ 				cogit processor disassembleInstructionAt: 1 In: machineCode object.
+ 				cogit processor disassembleInstructionAt: 2 In: machineCode object.
+ 				cogit processor disassembleInstructionAt: 4 In: machineCode object.
+ 				cogit processor disassembleInstructionAt: 6 In: machineCode object.
+ 				cogit processor disassembleInstructionAt: 8 In: machineCode object.
+ 				cogit processor disassembleInstructionAt: 9 In: machineCode object }]
+ 		ifFalse:
+ 			[{	cogit processor disassembleInstructionAt: 0 In: machineCode object.
+ 				cogit processor disassembleInstructionAt: 2 In: machineCode object.
+ 				cogit processor disassembleInstructionAt: 5 In: machineCode object }]"!

Item was removed:
- ----- Method: CogIA32Compiler>>concretizeSubbRR (in category 'generate machine code - concretize') -----
- concretizeSubbRR
- 	"Will get inlined into concretizeAt: switch."
- 	<inline: true>
- 	"Assemble the SBB instruction"
- 	| regLHS regRHS |
- 	regLHS := operands at: 0.
- 	regRHS := operands at: 1.
- 	machineCode
- 		at: 0 put: 16r1B;
- 		at: 1 put: (self mod: ModReg RM: regLHS RO: regRHS).
- 	^2!

Item was changed:
  ----- Method: CogIA32Compiler>>dispatchConcretize (in category 'generate machine code') -----
  dispatchConcretize
  	"Attempt to generate concrete machine code for the instruction at address.
  	 This is the inner dispatch of concretizeAt: actualAddress which exists only
  	 to get around the branch size limits in the SqueakV3 (blue book derived)
  	 bytecode set."
  	opcode >= CPUID ifTrue:
  		[^self dispatchConcretizeProcessorSpecific].
  
  	opcode caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]				-> [^self concretizeLabel].
  		[AlignmentNops]	-> [^self concretizeAlignmentNops].
  		[Fill32]				-> [^self concretizeFill32].
  		[Nop]				-> [^self concretizeNop].
  		"Control"
  		[Call]					-> [^self concretizeCall].
  		[CallR]					-> [^self concretizeCallR].
  		[CallFull]				-> [^self concretizeCall].
  		[JumpR]				-> [^self concretizeJumpR].
  		[JumpFull]				-> [^self concretizeJumpLong].
  		[JumpLong]			-> [^self concretizeJumpLong].
  		[JumpLongZero]		-> [^self concretizeConditionalJump: 16r4].
  		[JumpLongNonZero]	-> [^self concretizeConditionalJump: 16r5].
  		[Jump]					-> [^self concretizeJump].
  		"Table B-1 Intel® 64 and IA-32 Architectures Software Developer's Manual Volume 1: Basic Architecture"
  		[JumpZero]				-> [^self concretizeConditionalJump: 16r4].
  		[JumpNonZero]			-> [^self concretizeConditionalJump: 16r5].
  		[JumpNegative]			-> [^self concretizeConditionalJump: 16r8].
  		[JumpNonNegative]		-> [^self concretizeConditionalJump: 16r9].
  		[JumpOverflow]			-> [^self concretizeConditionalJump: 16r0].
  		[JumpNoOverflow]		-> [^self concretizeConditionalJump: 16r1].
  		[JumpCarry]			-> [^self concretizeConditionalJump: 16r2].
  		[JumpNoCarry]			-> [^self concretizeConditionalJump: 16r3].
  		[JumpLess]				-> [^self concretizeConditionalJump: 16rC].
  		[JumpGreaterOrEqual]	-> [^self concretizeConditionalJump: 16rD].
  		[JumpGreater]			-> [^self concretizeConditionalJump: 16rF].
  		[JumpLessOrEqual]		-> [^self concretizeConditionalJump: 16rE].
  		[JumpBelow]			-> [^self concretizeConditionalJump: 16r2].
  		[JumpAboveOrEqual]	-> [^self concretizeConditionalJump: 16r3].
  		[JumpAbove]			-> [^self concretizeConditionalJump: 16r7].
  		[JumpBelowOrEqual]	-> [^self concretizeConditionalJump: 16r6].
  		[JumpFPEqual]				-> [^self concretizeConditionalJump: 16r4].
  		[JumpFPNotEqual]			-> [^self concretizeConditionalJump: 16r5].
  		[JumpFPLess]				-> [^self concretizeConditionalJump: 16r2].
  		[JumpFPGreaterOrEqual]	-> [^self concretizeConditionalJump: 16r3].
  		[JumpFPGreater]			-> [^self concretizeConditionalJump: 16r7].
  		[JumpFPLessOrEqual]		-> [^self concretizeConditionalJump: 16r6].
  		[JumpFPOrdered]			-> [^self concretizeConditionalJump: 16rB].
  		[JumpFPUnordered]			-> [^self concretizeConditionalJump: 16rA].
  		[RetN]						-> [^self concretizeRetN].
  		[Stop]						-> [^self concretizeStop].
  		"Arithmetic"
  		[AddCqR]					-> [^self concretizeAddCqR].
  		[AddCwR]					-> [^self concretizeAddCwR].
  		[AddRR]					-> [^self concretizeOpRR: 16r03].
  		[AddcRR]					-> [^self concretizeAddcRR].
  		[AddcCqR]					-> [^self concretizeAddcCqR].
  		[AddRdRd]					-> [^self concretizeSEE2OpRdRd: 16r58].
  		[AddRsRs]					-> [^self concretizeSEEOpRsRs: 16r58].
  		[AndCqR]					-> [^self concretizeAndCqR].
  		[AndCwR]					-> [^self concretizeAndCwR].
  		[AndRR]					-> [^self concretizeOpRR: 16r23].
  		[TstCqR]					-> [^self concretizeTstCqR].
  		[CmpCqR]					-> [^self concretizeCmpCqR].
  		[CmpCwR]					-> [^self concretizeCmpCwR].
  		[CmpRR]					-> [^self concretizeReverseOpRR: 16r39].
  		[CmpRdRd]					-> [^self concretizeCmpRdRd].
  		[CmpRsRs]					-> [^self concretizeCmpRsRs].
  		[DivRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5E].
  		[DivRsRs]					-> [^self concretizeSEEOpRsRs: 16r5E].
  		[MulRdRd]					-> [^self concretizeSEE2OpRdRd: 16r59].
  		[MulRsRs]					-> [^self concretizeSEEOpRsRs: 16r59].
  		[OrCqR]					-> [^self concretizeOrCqR].
  		[OrCwR]					-> [^self concretizeOrCwR].
  		[OrRR]						-> [^self concretizeOpRR: 16r0B].
  		[SubCqR]					-> [^self concretizeSubCqR].
  		[SubCwR]					-> [^self concretizeSubCwR].
  		[SubRR]					-> [^self concretizeOpRR: 16r2B].
+ 		[SubbRR]					-> [^self concretizeOpRR: 16r1B].
- 		[SubbRR]					-> [^self concretizeSubbRR].
  		[SubRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5C].
  		[SubRsRs]					-> [^self concretizeSEEOpRsRs: 16r5C].
  		[SqrtRd]						-> [^self concretizeSqrtRd].
  		[SqrtRs]						-> [^self concretizeSqrtRs].
  		[XorCwR]						-> [^self concretizeXorCwR].
  		[XorRR]							-> [^self concretizeOpRR: 16r33].
  		[XorRdRd]						-> [^self concretizeXorRdRd].
  		[XorRsRs]						-> [^self concretizeXorRsRs].
  		[NegateR]						-> [^self concretizeNegateR].
  		[NotR]							-> [^self concretizeNotR].
  		[LoadEffectiveAddressMwrR]	-> [^self concretizeLoadEffectiveAddressMwrR].
  		[ArithmeticShiftRightCqR]		-> [^self concretizeArithmeticShiftRightCqR].
  		[LogicalShiftRightCqR]			-> [^self concretizeLogicalShiftRightCqR].
  		[LogicalShiftLeftCqR]			-> [^self concretizeLogicalShiftLeftCqR].
  		[ArithmeticShiftRightRR]		-> [^self concretizeArithmeticShiftRightRR].
  		[LogicalShiftLeftRR]				-> [^self concretizeLogicalShiftLeftRR].
  		[ClzRR]						-> [^self concretizeClzRR].
  		"Data Movement"
  		[MoveCqR]			-> [^self concretizeMoveCqR].
  		[MoveCwR]			-> [^self concretizeMoveCwR].
  		[MoveRR]			-> [^self concretizeReverseOpRR: 16r89].
  		[MoveRdRd]		-> [^self concretizeMoveRdRd].
  		[MoveRsRs]			-> [^self concretizeMoveRsRs].
  		[MoveAwR]			-> [^self concretizeMoveAwR].
  		[MoveRAw]			-> [^self concretizeMoveRAw].
  		[MoveAbR]			-> [^self concretizeMoveAbR].
  		[MoveRAb]			-> [^self concretizeMoveRAb].
  		[MoveMbrR]		-> [^self concretizeMoveMbrR].
  		[MoveRMbr]		-> [^self concretizeMoveRMbr].
  		[MoveRM8r]		-> [^self concretizeMoveRMbr].
  		[MoveM8rR]		-> [^self concretizeMoveM8rR].
  		[MoveM16rR]		-> [^self concretizeMoveM16rR].
  		[MoveRM16r]		-> [^self concretizeMoveRM16r].
  		[MoveM32rR]		-> [^self concretizeMoveMwrR].
  		[MoveRM32r]		-> [^self concretizeMoveRMwr].
  		[MoveM32rRs]		-> [^self concretizeMoveM32rRs].
  		[MoveRsM32r]		-> [^self concretizeMoveRsM32r].
  		[MoveM64rRd]		-> [^self concretizeMoveM64rRd].
  		[MoveMwrR]		-> [^self concretizeMoveMwrR].
  		[MoveXbrRR]		-> [^self concretizeMoveXbrRR].
  		[MoveRXbrR]		-> [^self concretizeMoveRXbrR].
  		[MoveXwrRR]		-> [^self concretizeMoveXwrRR].
  		[MoveRXwrR]		-> [^self concretizeMoveRXwrR].
  		[MoveRMwr]		-> [^self concretizeMoveRMwr].
  		[MoveRdM64r]		-> [^self concretizeMoveRdM64r].
  		[PopR]				-> [^self concretizePopR].
  		[PushR]				-> [^self concretizePushR].
  		[PushCq]			-> [^self concretizePushCq].
  		[PushCw]			-> [^self concretizePushCw].
  		[PrefetchAw]		-> [^self concretizePrefetchAw].
  		"Conversion"
  		[ConvertRRd]		-> [^self concretizeConvertRRd].
  		[ConvertRdR]		-> [^self concretizeConvertRdR].
  		
  		[ConvertRsRd]		-> [^self concretizeConvertRsRd].
  		[ConvertRdRs]		-> [^self concretizeConvertRdRs].
  		[ConvertRsR]		-> [^self concretizeConvertRsR].
  		[ConvertRRs]		-> [^self concretizeConvertRRs].
  			
  		[SignExtend8RR]		-> [^self concretizeSignExtend8RR].
  		[SignExtend16RR]		-> [^self concretizeSignExtend16RR].
  		
  		[ZeroExtend8RR]		-> [^self concretizeZeroExtend8RR].
+ 		[ZeroExtend16RR]		-> [^self concretizeZeroExtend16RR].
- 		[ZeroExtend16RR]		-> [^self concretizeZeroExtend16RR] }.
  
+ 		"miscellaneous"
+ 		[MovePerfCnt64RRL]	->	[^self concretizeMovePerfCnt64RRL]
+ 		 }.
+ 
  	^0 "keep Slang happy"!

Item was added:
+ ----- Method: CogIA32Compiler>>preferredRegisterPairForMovePerfCnt64RRLInto: (in category 'feature detection') -----
+ preferredRegisterPairForMovePerfCnt64RRLInto: aBlock
+ 	"Evaluate aBlock with the preferred registers to receive the
+ 	 low and high 32-bits of the 64-bit performance counter."
+ 	<inline: #always>
+ 	aBlock value: EAX value: EDX!

Item was added:
+ ----- Method: CogMIPSELCompiler>>has64BitPerformanceCounter (in category 'testing') -----
+ has64BitPerformanceCounter
+ 	"At least for the moment..."
+ 	<inline: #always>
+ 	^false!

Item was changed:
  SharedPool subclass: #CogRTLOpcodes
  	instanceVariableNames: ''
+ 	classVariableNames: 'AddCqR AddCqRR AddCwR AddRR AddRRR AddRdRd AddRsRs AddcCqR AddcRR AlignmentNops AndCqR AndCqRR AndCwR AndRR ArithmeticShiftRightCqR ArithmeticShiftRightCqRR ArithmeticShiftRightRR Call CallFull CallR ClzRR CmpC32R CmpCqR CmpCwR CmpRR CmpRdRd CmpRsRs ConvertRRd ConvertRRs ConvertRdR ConvertRdRs ConvertRsR ConvertRsRd DivRdRd DivRsRs Fill32 FirstJump FirstShortJump Jump JumpAbove JumpAboveOrEqual JumpBelow JumpBelowOrEqual JumpCarry JumpFPEqual JumpFPGreater JumpFPGreaterOrEqual JumpFPLess JumpFPLessOrEqual JumpFPNotEqual JumpFPOrdered JumpFPUnordered JumpFull JumpGreater JumpGreaterOrEqual JumpLess JumpLessOrEqual JumpLong JumpLongNonZero JumpLongZero JumpMulOverflow JumpNegative JumpNoCarry JumpNoMulOverflow JumpNoOverflow JumpNonNegative JumpNonZero JumpOverflow JumpR JumpZero Label LastJump LastRTLCode Literal LoadEffectiveAddressMwrR LogicalShiftLeftCqR LogicalShiftLeftCqRR LogicalShiftLeftRR LogicalShiftRightCqR LogicalShiftRightCqRR LogicalShiftRightRR Mo
 veA32R MoveAbR MoveAwR MoveC32R MoveCqR MoveCwR MoveM16rR MoveM32rR MoveM32rRs MoveM64rRd MoveM8rR MoveMbrR MoveMs8rR MoveMwrR MovePerfCnt64RL MovePerfCnt64RRL MoveRA32 MoveRAb MoveRAw MoveRM16r MoveRM32r MoveRM8r MoveRMbr MoveRMwr MoveRR MoveRRd MoveRX16rR MoveRX32rR MoveRXbrR MoveRXwrR MoveRdM64r MoveRdR MoveRdRd MoveRsM32r MoveRsRs MoveX16rRR MoveX32rRR MoveXbrRR MoveXwrRR MulRdRd MulRsRs NativePopR NativePushR NativeRetN NegateR Nop NotR OrCqR OrCqRR OrCwR OrRR PopR PrefetchAw PushCq PushCw PushR RetN RotateLeftCqR RotateRightCqR SignExtend16RR SignExtend32RR SignExtend8RR SqrtRd SqrtRs Stop SubCqR SubCwR SubRR SubRRR SubRdRd SubRsRs SubbCqR SubbRR TstCqR XorCqR XorCwR XorRR XorRdRd XorRsRs ZeroExtend16RR ZeroExtend32RR ZeroExtend8RR'
- 	classVariableNames: 'AddCqR AddCqRR AddCwR AddRR AddRRR AddRdRd AddRsRs AddcCqR AddcRR AlignmentNops AndCqR AndCqRR AndCwR AndRR ArithmeticShiftRightCqR ArithmeticShiftRightCqRR ArithmeticShiftRightRR Call CallFull CallR ClzRR CmpC32R CmpCqR CmpCwR CmpRR CmpRdRd CmpRsRs ConvertRRd ConvertRRs ConvertRdR ConvertRdRs ConvertRsR ConvertRsRd DivRdRd DivRsRs Fill32 FirstJump FirstShortJump Jump JumpAbove JumpAboveOrEqual JumpBelow JumpBelowOrEqual JumpCarry JumpFPEqual JumpFPGreater JumpFPGreaterOrEqual JumpFPLess JumpFPLessOrEqual JumpFPNotEqual JumpFPOrdered JumpFPUnordered JumpFull JumpGreater JumpGreaterOrEqual JumpLess JumpLessOrEqual JumpLong JumpLongNonZero JumpLongZero JumpMulOverflow JumpNegative JumpNoCarry JumpNoMulOverflow JumpNoOverflow JumpNonNegative JumpNonZero JumpOverflow JumpR JumpZero Label LastJump LastRTLCode Literal LoadEffectiveAddressMwrR LogicalShiftLeftCqR LogicalShiftLeftCqRR LogicalShiftLeftRR LogicalShiftRightCqR LogicalShiftRightCqRR LogicalShiftRightRR Mo
 veA32R MoveAbR MoveAwR MoveC32R MoveCqR MoveCwR MoveM16rR MoveM32rR MoveM32rRs MoveM64rRd MoveM8rR MoveMbrR MoveMs8rR MoveMwrR MoveRA32 MoveRAb MoveRAw MoveRM16r MoveRM32r MoveRM8r MoveRMbr MoveRMwr MoveRR MoveRRd MoveRX16rR MoveRX32rR MoveRXbrR MoveRXwrR MoveRdM64r MoveRdR MoveRdRd MoveRsM32r MoveRsRs MoveX16rRR MoveX32rRR MoveXbrRR MoveXwrRR MulRdRd MulRsRs NativePopR NativePushR NativeRetN NegateR Nop NotR OrCqR OrCqRR OrCwR OrRR PopR PrefetchAw PushCq PushCw PushR RetN RotateLeftCqR RotateRightCqR SignExtend16RR SignExtend32RR SignExtend8RR SqrtRd SqrtRs Stop SubCqR SubCwR SubRR SubRRR SubRdRd SubRsRs SubbCqR SubbRR TstCqR XorCqR XorCwR XorRR XorRdRd XorRsRs ZeroExtend16RR ZeroExtend32RR ZeroExtend8RR'
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!
  
  !CogRTLOpcodes commentStamp: 'eem 12/26/2015 14:00' prior: 0!
  I am a pool for the Register-Transfer-Language to which Cog compiles.  I define unique integer values for all RTL opcodes.  See CogAbstractInstruction for instances of instructions with the opcodes that I define.!

Item was changed:
  ----- Method: CogRTLOpcodes class>>initialize (in category 'class initialization') -----
(excessive size, no diff calculated)

Item was changed:
  ----- Method: CogX64Compiler>>computeMaximumSize (in category 'generate machine code') -----
(excessive size, no diff calculated)

Item was added:
+ ----- 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: 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: 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:
  ----- Method: CogX64Compiler>>dispatchConcretize (in category 'generate machine code') -----
  dispatchConcretize
  	"Attempt to generate concrete machine code for the instruction at address.
  	 This is the inner dispatch of concretizeAt: actualAddress which exists only
  	 to get around the branch size limits in the SqueakV3 (blue book derived)
  	 bytecode set."
  	opcode >= CPUID ifTrue:
  		[^self dispatchConcretizeProcessorSpecific].
  
  	opcode caseOf: {
  		"Noops & Pseudo Ops"
  		[Label]				-> [^self concretizeLabel].
  		[AlignmentNops]	-> [^self concretizeAlignmentNops].
  		[Fill32]				-> [^self concretizeFill32].
  		[Nop]				-> [^self concretizeNop].
  		"Control"
  		[Call]					-> [^self concretizeCall].
  		[CallR]					-> [^self concretizeCallR].
  		[CallFull]				-> [^self concretizeCallFull].
  		[JumpR]					-> [^self concretizeJumpR].
  		[JumpFull]				-> [^self concretizeJumpFull].
  		[JumpLong]				-> [^self concretizeJumpLong].
  		[JumpLongZero]		-> [^self concretizeConditionalJump: 16r4].
  		[JumpLongNonZero]	-> [^self concretizeConditionalJump: 16r5].
  		[Jump]					-> [^self concretizeJump].
  		"Table B-1 Intel 64 and IA-32 Architectures Software Developer's Manual Volume 1: Basic Architecture"
  		[JumpZero]				-> [^self concretizeConditionalJump: 16r4].
  		[JumpNonZero]			-> [^self concretizeConditionalJump: 16r5].
  		[JumpNegative]			-> [^self concretizeConditionalJump: 16r8].
  		[JumpNonNegative]		-> [^self concretizeConditionalJump: 16r9].
  		[JumpOverflow]			-> [^self concretizeConditionalJump: 16r0].
  		[JumpNoOverflow]		-> [^self concretizeConditionalJump: 16r1].
  		[JumpCarry]			-> [^self concretizeConditionalJump: 16r2].
  		[JumpNoCarry]			-> [^self concretizeConditionalJump: 16r3].
  		[JumpLess]				-> [^self concretizeConditionalJump: 16rC].
  		[JumpGreaterOrEqual]	-> [^self concretizeConditionalJump: 16rD].
  		[JumpGreater]			-> [^self concretizeConditionalJump: 16rF].
  		[JumpLessOrEqual]		-> [^self concretizeConditionalJump: 16rE].
  		[JumpBelow]			-> [^self concretizeConditionalJump: 16r2].
  		[JumpAboveOrEqual]	-> [^self concretizeConditionalJump: 16r3].
  		[JumpAbove]			-> [^self concretizeConditionalJump: 16r7].
  		[JumpBelowOrEqual]	-> [^self concretizeConditionalJump: 16r6].
  		[JumpFPEqual]				-> [^self concretizeConditionalJump: 16r4].
  		[JumpFPNotEqual]			-> [^self concretizeConditionalJump: 16r5].
  		[JumpFPLess]				-> [^self concretizeConditionalJump: 16r2].
  		[JumpFPGreaterOrEqual]	-> [^self concretizeConditionalJump: 16r3].
  		[JumpFPGreater]			-> [^self concretizeConditionalJump: 16r7].
  		[JumpFPLessOrEqual]		-> [^self concretizeConditionalJump: 16r6].
  		[JumpFPOrdered]			-> [^self concretizeConditionalJump: 16rB].
  		[JumpFPUnordered]			-> [^self concretizeConditionalJump: 16rA].
  		[RetN]						-> [^self concretizeRetN].
  		[Stop]						-> [^self concretizeStop].
  		"Arithmetic"
  		[AddCqR]					-> [^self concretizeArithCqRWithRO: 0 raxOpcode: 15r05].
  		[AddcCqR]					-> [^self concretizeArithCqRWithRO: 2 raxOpcode: 15r15].
  		[AddCwR]					-> [^self concretizeArithCwR: 16r03].
  		[AddRR]						-> [^self concretizeOpRR: 16r03].
  		[AddRsRs]					-> [^self concretizeSEEOpRsRs: 16r58].
  		[AddRdRd]					-> [^self concretizeSEE2OpRdRd: 16r58].
  		[AndCqR]					-> [^self concretizeArithCqRWithRO: 4 raxOpcode: 16r25].
  		[AndCwR]					-> [^self concretizeArithCwR: 16r23].
  		[AndRR]						-> [^self concretizeOpRR: 16r23].
  		[TstCqR]					-> [^self concretizeTstCqR].
  		[CmpCqR]					-> [^self concretizeArithCqRWithRO: 7 raxOpcode: 16r3D].
  		[CmpCwR]					-> [^self concretizeArithCwR: 16r39].
  		[CmpC32R]					-> [^self concretizeCmpC32R].
  		[CmpRR]					-> [^self concretizeReverseOpRR: 16r39].
  		[CmpRdRd]					-> [^self concretizeCmpRdRd].
  		[CmpRsRs]					-> [^self concretizeCmpRsRs].
  		[DivRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5E].
  		[DivRsRs]					-> [^self concretizeSEEOpRsRs: 16r5E].
  		[MulRdRd]					-> [^self concretizeSEE2OpRdRd: 16r59].
  		[MulRsRs]					-> [^self concretizeSEEOpRsRs: 16r59].
  		[OrCqR]						-> [^self concretizeArithCqRWithRO: 1 raxOpcode: 16r0D].
  		[OrCwR]					-> [^self concretizeArithCwR: 16r0B].
  		[OrRR]						-> [^self concretizeOpRR: 16r0B].
  		[SubCqR]					-> [^self concretizeArithCqRWithRO: 5 raxOpcode: 16r2D].
  		[SubbCqR]					-> [^self concretizeArithCqRWithRO: 3 raxOpcode: 16r1D].
  		[SubCwR]					-> [^self concretizeArithCwR: 16r2B].
  		[SubRR]						-> [^self concretizeOpRR: 16r2B].
  		[SubRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5C].
  		[SubRsRs]					-> [^self concretizeSEEOpRsRs: 16r5C].
  		[SqrtRd]					-> [^self concretizeSqrtRd].
  		[SqrtRs]					-> [^self concretizeSqrtRs].
  		[XorCwR]					-> [^self concretizeArithCwR: 16r33].
  		[XorRR]						-> [^self concretizeOpRR: 16r33].
  		[XorRdRd]						-> [^self concretizeXorRdRd].
  		[XorRsRs]						-> [^self concretizeXorRsRs].
  		[NegateR]					-> [^self concretizeNegateR].
  		[LoadEffectiveAddressMwrR]	-> [^self concretizeLoadEffectiveAddressMwrR].
  		[RotateLeftCqR]				-> [^self concretizeShiftCqRegOpcode: 0].
  		[RotateRightCqR]				-> [^self concretizeShiftCqRegOpcode: 1].
  		[ArithmeticShiftRightCqR]		-> [^self concretizeShiftCqRegOpcode: 7].
  		[LogicalShiftRightCqR]			-> [^self concretizeShiftCqRegOpcode: 5].
  		[LogicalShiftLeftCqR]			-> [^self concretizeShiftCqRegOpcode: 4].
  		[ArithmeticShiftRightRR]			-> [^self concretizeShiftRegRegOpcode: 7].
  		[LogicalShiftLeftRR]				-> [^self concretizeShiftRegRegOpcode: 4].
  		[ClzRR]						-> [^self concretizeClzRR].
  		"Data Movement"
  		[MoveCqR]			-> [^self concretizeMoveCqR].
  		[MoveCwR]			-> [^self concretizeMoveCwR].
  		[MoveC32R]		-> [^self concretizeMoveC32R].
  		[MoveRR]			-> [^self concretizeReverseOpRR: 16r89].
  		[MoveAwR]			-> [^self concretizeMoveAwR].
  		[MoveA32R]		-> [^self concretizeMoveA32R].
  		[MoveRAw]			-> [^self concretizeMoveRAw].
  		[MoveRA32]		-> [^self concretizeMoveRA32].
  		[MoveAbR]			-> [^self concretizeMoveAbR].
  		[MoveRAb]			-> [^self concretizeMoveRAb].
  		[MoveMbrR]			-> [^self concretizeMoveMbrR].
  		[MoveRMbr]			-> [^self concretizeMoveRMbr].
  		[MoveM8rR]		-> [^self concretizeMoveMbrR].
  		[MoveRM8r]		-> [^self concretizeMoveRMbr].
  		[MoveM16rR]		-> [^self concretizeMoveM16rR].
  		[MoveRM16r]		-> [^self concretizeMoveRM16r].
  		[MoveM32rR]		-> [^self concretizeMoveM32rR].
  		[MoveM32rRs]		-> [^self concretizeMoveM32rRs].
  		[MoveM64rRd]		-> [^self concretizeMoveM64rRd].
  		[MoveMwrR]		-> [^self concretizeMoveMwrR].
  		[MoveXbrRR]		-> [^self concretizeMoveXbrRR].
  		[MoveRXbrR]		-> [^self concretizeMoveRXbrR].
  		[MoveXwrRR]		-> [^self concretizeMoveXwrRR].
  		[MoveRXwrR]		-> [^self concretizeMoveRXwrR].
  		[MoveX32rRR]		-> [^self concretizeMoveX32rRR].
  		[MoveRX32rR]		-> [^self concretizeMoveRX32rR].
  		[MoveRMwr]		-> [^self concretizeMoveRMwr].
  		[MoveRM32r]		-> [^self concretizeMoveRM32r].
  		[MoveRsM32r]		-> [^self concretizeMoveRsM32r].
  		[MoveRdM64r]		-> [^self concretizeMoveRdM64r].
  		[MoveRdR]			-> [^self concretizeMoveRdR].
  		[MoveRRd]			-> [^self concretizeMoveRRd].
  		[MoveRdRd]		-> [^self concretizeMoveRdRd].
  		[MoveRsRs]		-> [^self concretizeMoveRsRs].
  		[PopR]				-> [^self concretizePopR].
  		[PushR]				-> [^self concretizePushR].
  		[PushCq]			-> [^self concretizePushCq].
  		[PushCw]			-> [^self concretizePushCw].
  		[PrefetchAw]		-> [^self concretizePrefetchAw].
  		"Conversion"
  		[ConvertRRd]		-> [^self concretizeConvertRRd].
  		[ConvertRdR]		-> [^self concretizeConvertRdR].
  		[ConvertRRs]		-> [^self concretizeConvertRRs].
  		[ConvertRsR]		-> [^self concretizeConvertRsR].
  		[ConvertRsRd]	-> [^self concretizeConvertRsRd].
  		[ConvertRdRs]	-> [^self concretizeConvertRdRs].
  			
  		[SignExtend8RR]		-> [^self concretizeSignExtend8RR].
  		[SignExtend16RR]	-> [^self concretizeSignExtend16RR].
  		[SignExtend32RR]	-> [^self concretizeSignExtend32RR].
  		
  		[ZeroExtend8RR]		-> [^self concretizeZeroExtend8RR].
  		[ZeroExtend16RR]	-> [^self concretizeZeroExtend16RR].
  		[ZeroExtend32RR]	-> [^self concretizeZeroExtend32RR].
+ 
+ 		"miscellaneous"
+ 		[MovePerfCnt64RL]	->	[^self concretizeMovePerfCnt64RL]
  		}.
  
  	^0 "keep Slang happy"!

Item was changed:
  ----- Method: CogX64Compiler>>genRemoveNArgsFromStack: (in category 'abi') -----
  genRemoveNArgsFromStack: n
  	"This is a no-op on x64 SysV since the ABI passes up to 6 args in registers and trampolines currently observe a limit of 4.
+ 	 But the WIN64 ABI always reserve shadow space for saving up to 4 parameter registers (even if less than 4 args)."
- 	But the WIN64 ABI allways reserve shadow space for saving up to 4 parameter registers (even if less than 4 args)."
  	<inline: true>
  	self assert: n <= 4.
  	SysV ifFalse: [cogit AddCq: 32 R: RSP].
  	^0!

Item was added:
+ ----- Method: CogX64Compiler>>preferredRegisterForMovePerfCnt64RL (in category 'feature detection') -----
+ preferredRegisterForMovePerfCnt64RL
+ 	"Answer the preferred register to receive the 64-bit performance counter,
+ 	 or NoReg if none."
+ 	<inline: #always>
+ 	^RAX!

Item was added:
+ ----- Method: Cogit>>MovePerfCnt64R:L: (in category 'abstract instructions') -----
+ MovePerfCnt64R: destReg L: liveRegisters
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	self assert: (backEnd has64BitPerformanceCounter and: [objectMemory wordSize = 8]).
+ 	^self gen: MovePerfCnt64RL operand: destReg operand: liveRegisters!

Item was added:
+ ----- Method: Cogit>>MovePerfCnt64R:R:L: (in category 'abstract instructions') -----
+ MovePerfCnt64R: destRegLo R: destRegHi L: liveRegisters
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	self assert: (backEnd has64BitPerformanceCounter and: [objectMemory wordSize = 4]).
+ 	^self gen: MovePerfCnt64RRL operand: destRegLo operand: destRegHi operand: liveRegisters!

Item was changed:
  ----- Method: Cogit>>handleCallOrJumpSimulationTrap: (in category 'simulation only') -----
  handleCallOrJumpSimulationTrap: aProcessorSimulationTrap
  	<doNotGenerate>
  	| evaluable function memory result savedFramePointer savedStackPointer savedArgumentCount retpc invalidStackPointersExpected index |
  	"Execution of a single instruction must be within the processorLock critical section to ensure
  	 simulation traps are executed atomically.  However, at this point control is leaving machine
  	 code and entering the run-time and hence the lock must be released."
  	processorLock primitiveExitCriticalSection.
  	"This is a hack fix before we revise the simulators.  When a jump call is made, the next
  	 pc is effectively the return address on the stack, not the instruction following the jump."
  	aProcessorSimulationTrap type == #jump ifTrue:
  		[processor hackFixNextPCOfJumpFor: aProcessorSimulationTrap using: objectMemory].
  
  	evaluable := simulatedTrampolines
  					at: aProcessorSimulationTrap address
  					ifAbsent: [self errorProcessingSimulationTrap: aProcessorSimulationTrap
  								in: simulatedTrampolines].
  	function := evaluable isBlock
  					ifTrue: ['aBlock; probably some plugin primitive']
  					ifFalse:
  						[evaluable receiver == backEnd ifTrue: "this is for invoking ARMv5 floating-point intrinsics, and for the short-cut tracing trampolines"
  							[^self handleABICallOrJumpSimulationTrap: aProcessorSimulationTrap evaluable: evaluable].
  						 evaluable selector].
  	memory := coInterpreter memory.
  	function == #interpret ifTrue: "i.e. we're here via ceInvokeInterpret/ceReturnToInterpreterTrampoline and should discard all state back to enterSmalltalkExecutiveImplementation"
  		[self recordInstruction: {'(simulated jump call of '. aProcessorSimulationTrap address. '/'. function. ')'}.
  		 "self halt: evaluable selector."
  	   	 clickConfirm ifTrue:
  		 	[(self confirm: 'skip jump to interpret?') ifFalse:
  				[clickConfirm := false. self halt]].
  		 processor simulateJumpCallOf: aProcessorSimulationTrap address memory: memory.
  		 coInterpreter reenterInterpreter.
  		 "NOTREACHED"
  		 self halt].
+ 	(function == #ceBaseFrameReturn:
+ 	or: [function == #ceTakeProfileSample:])
+ 		ifTrue: [invalidStackPointersExpected := true]
+ 		ifFalse:
+ 			[invalidStackPointersExpected := false.
+ 			 evaluable isBlock
+ 				ifTrue: "external primitives..."
+ 					["The only acceptable exception to the rule are fast C primitive calls..."
+ 					 (methodZone cogMethodContaining: (self mostLikelyPrimInvocationPC: processor pc or: (processor leafRetpcIn: memory)))
+ 						ifNil: [self assertf: 'call to block evaluable from non-external method']
+ 						ifNotNil: [:cogMethod|
+ 								self assert: (self cogMethodHasExternalPrim: cogMethod).
+ 								(coInterpreter hasFastCLinkage: cogMethod methodObject)
+ 									ifTrue: [invalidStackPointersExpected := true. coInterpreter nilLocalFP]
+ 									ifFalse: [coInterpreter assertValidExternalStackPointers]]]
+ 				ifFalse:
+ 					[coInterpreter assertValidExternalStackPointers]].
- 	invalidStackPointersExpected := false.
- 	function ~~ #ceBaseFrameReturn: ifTrue:
- 		[evaluable isBlock
- 			ifTrue: "external primitives..."
- 				["The only acceptable exception to the rule are fast C primitive calls..."
- 				 (methodZone cogMethodContaining: (self mostLikelyPrimInvocationPC: processor pc or: (processor leafRetpcIn: memory)))
- 					ifNil: [self assertf: 'call to block evaluable from non-external method']
- 					ifNotNil: [:cogMethod|
- 							self assert: (self cogMethodHasExternalPrim: cogMethod).
- 							(coInterpreter hasFastCLinkage: cogMethod methodObject)
- 								ifTrue: [invalidStackPointersExpected := true. coInterpreter nilLocalFP]
- 								ifFalse: [coInterpreter assertValidExternalStackPointers]]]
- 			ifFalse:
- 				[coInterpreter assertValidExternalStackPointers]].
  	processor
  		simulateCallOf: aProcessorSimulationTrap address
  		nextpc: aProcessorSimulationTrap nextpc
  		memory: memory.
  	retpc := processor retpcIn: memory.
  	self recordInstruction: {'(simulated call of '. aProcessorSimulationTrap address. '/'. function. ')'}.
  	savedFramePointer := coInterpreter framePointer.
  	savedStackPointer := coInterpreter stackPointer.
  	savedArgumentCount := coInterpreter argumentCount.
  	result := ["self halt: evaluable selector."
  		   	   clickConfirm ifTrue:
  			 	[(self confirm: 'skip run-time call?') ifFalse:
  					[clickConfirm := false. self halt]].
  			   evaluable valueWithArguments: (processor
  												postCallArgumentsNumArgs: evaluable numArgs
  												in: memory)]
  				on: ReenterMachineCode
  				do: [:ex| ex return: #continueNoReturn].
  			
  	invalidStackPointersExpected ifFalse:
  		[coInterpreter assertValidExternalStackPointers].
  	"Verify the stack layout assumption compileInterpreterPrimitive: makes, provided we've
  	 not called something that has built a frame, such as closure value or evaluate method, or
  	 switched frames, such as primitiveSignal, primitiveWait, primitiveResume, primitiveSuspend et al."
  	(function beginsWith: 'primitive') ifTrue:
  		[coInterpreter primFailCode = 0
  			ifTrue: [(CogVMSimulator stackAlteringPrimitives includes: function) ifFalse:
  						["This is a rare case (e.g. in Scorch where a married context's sender is set to nil on trapTrpped and hence the stack layout is altered."
  						 (function == #primitiveSlotAtPut and: [objectMemory isContext: (coInterpreter frameReceiver: coInterpreter framePointer)]) ifFalse:
  							[self assert: savedFramePointer = coInterpreter framePointer.
  							 self assert: savedStackPointer + (savedArgumentCount * objectMemory wordSize)
  									= coInterpreter stackPointer]]]
  			ifFalse:
  				[self assert: savedFramePointer = coInterpreter framePointer.
  				 self assert: savedStackPointer = coInterpreter stackPointer]].
  	result ~~ #continueNoReturn ifTrue:
  		[self recordInstruction: {'(simulated return to '. processor retpcIn: memory. ')'}.
  		 processor simulateReturnIn: memory.
  		 self assert: processor pc = retpc.
  		 processor smashCallerSavedRegistersWithValuesFrom: 16r80000000 by: objectMemory wordSize].
  	self assert: (result isInteger "an oop result"
  			or: [result == coInterpreter
  			or: [result == objectMemory
  			or: [(index := #(nil true false continueNoReturn) indexOf: result) > 0
  				and: [result := #(0 1 0 16rF00BA4) at: index. true]]]]).
  	processor cResultRegister: (result
  								ifNil: [0]
  								ifNotNil: [result isInteger
  											ifTrue: [result]
  											ifFalse: [16rF00BA222]])!

Item was changed:
  ----- Method: Cogit>>registerMaskFor: (in category 'register management') -----
  registerMaskFor: reg
+ 	"N.B. (self registerMaskFor: NoReg) = 0"
  	<inline: true>
+ 	^1 bitShift: reg!
- 	^1 << reg!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>ceTakeProfileSample: (in category 'cog jit support') -----
+ ceTakeProfileSample: aCogMethod
+ 	self placeholder!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>checkForAndFollowForwardedPrimitiveState (in category 'cog jit support') -----
+ checkForAndFollowForwardedPrimitiveState
+ 	self placeholder!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>functionPointerForCompiledMethod:primitiveIndex:primitivePropertyFlagsInto: (in category 'accessing') -----
  functionPointerForCompiledMethod: methodOop primitiveIndex: primIndex primitivePropertyFlagsInto: flagsPtr
  	^([coInterpreter
  		functionPointerForCompiledMethod: methodOop
  		primitiveIndex: primIndex
  		primitivePropertyFlagsInto: flagsPtr]
  			on: Error
  			do: [:ex|
+ 				#someExternalPrimitive]) ifNotNil:
- 				"N.B. THIS IS WORK IN PROGRESS!! NO TIME TO MAKE fakeLinkedExternalLiteralFor: WORK PROPERLY AT THE MOMENT"
- 				(ex signalerContext findContextSuchThat: [:ctxt| ctxt selector == #attemptToLinkExternalPrimitive:])
- 					ifNotNil: [ex resume: (self fakeLinkedExternalLiteralFor: methodOop)]
- 					ifNil: [#someExternalPrimitive]]) ifNotNil:
  		[:symbol|
  		self addressForLabel: symbol]!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>nextProfileTickAddress (in category 'accessing') -----
  nextProfileTickAddress
+ 	self addressForLabel: #nextProfileTickLow.
+ 	self addressForLabel: #nextProfileTickHigh.
+ 	^self addressForLabel: #nextProfileTickLow!
- 	^self addressForLabel: #nextProfileTick!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>placeholder (in category 'private') -----
+ placeholder
+ 	self error: 'should not be sent'!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>rawHeaderOf: (in category 'accessing') -----
  rawHeaderOf: aMethodOop
+ 	| method header correctedHeader headerOop |
- 	| method headerOop |
  	method := self objectForOop: aMethodOop.
+ 	header := method header.
+ 
+ 	"(index 0)		15 bits:	number of literals (#numLiterals)
+ 	 (index 15)		  1 bit:	jit without counters - reserved for methods that have been optimized by Sista
+ 	 (index 16)		  1 bit:	has primitive
+ 	 (index 17)		  1 bit:	whether a large frame size is needed (#frameSize => either SmallFrame or LargeFrame)
+ 	 (index 18)		  6 bits:	number of temporary variables (#numTemps)
+ 	 (index 24)		  4 bits:	number of arguments to the method (#numArgs)
+ 	 (index 28)		  2 bits:	reserved for an access modifier (00-unused, 01-private, 10-protected, 11-public), although accessors for bit 29 exist (see #flag).
+ 	 sign bit:		  1 bit: selects the instruction set, >= 0 Primary, < 0 Secondary (#signFlag)"
+ 
+ 	correctedHeader := self wordSize = Smalltalk wordSize
+ 							ifTrue: [header]
+ 							ifFalse:
+ 								[(header bitAnd: (1 bitShift: 30) - 1)
+ 								- (header < 0 ifTrue: [2 raisedTo: self wordSize * 8] ifFalse: [0])].
+ 	headerOop := objectMemory integerObjectOf: correctedHeader.
+ 	headerOop := headerOop bitAnd: (2 raisedTo: self wordSize * 8) - 1.
+ 	self assert: (objectMemory literalCountOfMethodHeader: headerOop) = method numLiterals.
+ 	self assert: (coInterpreter argumentCountOfMethodHeader: headerOop) = method numArgs.
+ 	self assert: (coInterpreter temporaryCountOfMethodHeader: headerOop) = method numTemps.
+ 	self assert: (objectMemory headerIndicatesAlternateBytecodeSet: headerOop) = method signFlag.
+ 	headerToMethodMap
+ 		at: headerOop
+ 		ifPresent: [:existing| self assert: existing == method]
+ 		ifAbsentPut: [method].
- 	headerOop := objectMemory integerObjectOf: (self objectForOop: aMethodOop) header.
- 	self assert: method header = (headerToMethodMap at: headerOop ifAbsentPut: [method]) header.
  	^headerOop!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>recordFastCCallPrimTraceForMethod: (in category 'accessing') -----
+ recordFastCCallPrimTraceForMethod: methodOop
+ 	^cogit recordFastCCallPrimTrace!

Item was changed:
+ ----- Method: CurrentImageCoInterpreterFacade>>recordPrimTraceForMethod: (in category 'accessing') -----
- ----- Method: CurrentImageCoInterpreterFacade>>recordPrimTraceForMethod: (in category 'cog jit support') -----
  recordPrimTraceForMethod: methodOop
+ 	^cogit recordPrimTrace!
- 	^coInterpreter recordPrimTraceForMethod: methodOop!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacadeFor64BitSpurObjectRepresentation>>functionPointerForCompiledMethod:primitiveIndex:primitivePropertyFlagsInto: (in category 'accessing') -----
+ functionPointerForCompiledMethod: methodOop primitiveIndex: primIndex primitivePropertyFlagsInto: flagsPtr
+ 	| candidates literal method |
+ 	primIndex = PrimNumberExternalCall ifTrue:
+ 		[method := self objectForOop: methodOop.
+ 		 self assert: method primitive = PrimNumberExternalCall.
+ 		 literal := method literalAt: 1.
+ 		 candidates := self sn
+ 							allImplementorsOf: literal second
+ 							localTo: (literal first basicSize = 0
+ 										ifTrue: [InterpreterPrimitives]
+ 										ifFalse: [InterpreterPlugin allSubclasses
+ 													detect: [:pluginClass| pluginClass moduleName = literal first]]).
+ 		 self assert: candidates size = 1.
+ 		 flagsPtr
+ 			at: 0
+ 			put: (coInterpreter
+ 					primitivePropertyFlagsFor: candidates first compiledMethod
+ 					primitiveIndex: primIndex).
+ 		 ^self oopForObject: literal second].
+ 	^super functionPointerForCompiledMethod: methodOop primitiveIndex: primIndex primitivePropertyFlagsInto: flagsPtr!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacadeFor64BitSpurObjectRepresentation>>nextProfileTickAddress (in category 'accessing') -----
+ nextProfileTickAddress
+ 	^self addressForLabel: #nextProfileTick!

Item was changed:
  CurrentImageCoInterpreterFacade subclass: #CurrentImageCoInterpreterFacadeForSpurObjectRepresentation
  	instanceVariableNames: 'hiddenRoots'
  	classVariableNames: ''
+ 	poolDictionaries: 'VMSpurObjectRepresentationConstants'
- 	poolDictionaries: ''
  	category: 'VMMaker-Support'!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacadeForSpurObjectRepresentation>>accessorDepthForExternalPrimitiveMethod: (in category 'cog jit support') -----
+ accessorDepthForExternalPrimitiveMethod: methodOop
+ 	| metadata |
+ 	metadata := StackInterpreter metadataFlagsForPrimitive: (self primitiveMethodForMethodContainingExternalPrimitive: methodOop).
+ 	^metadata bitShift: SpurPrimitiveAccessorDepthShift negated!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacadeForSpurObjectRepresentation>>functionPointerForCompiledMethod:primitiveIndex:primitivePropertyFlagsInto: (in category 'cog jit support') -----
+ functionPointerForCompiledMethod: methodOop primitiveIndex: primIndex primitivePropertyFlagsInto: flagsPtr
+ 	primIndex = PrimNumberExternalCall ifTrue:
+ 		[flagsPtr
+ 			at: 0
+ 			put: (coInterpreter
+ 					primitivePropertyFlagsFor: (self primitiveMethodForMethodContainingExternalPrimitive: methodOop)
+ 					primitiveIndex: primIndex).
+ 		 ^self oopForObject: ((self objectForOop: methodOop) literalAt: 1) second].
+ 	^super functionPointerForCompiledMethod: methodOop primitiveIndex: primIndex primitivePropertyFlagsInto: flagsPtr!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacadeForSpurObjectRepresentation>>primitiveMethodForMethodContainingExternalPrimitive: (in category 'cog jit support') -----
+ primitiveMethodForMethodContainingExternalPrimitive: methodOop
+ 	"Look up a primitive in a method and answer that method."
+ 	| candidates literal method |
+ 	method := self objectForOop: methodOop.
+ 	self assert: method primitive = PrimNumberExternalCall.
+ 	literal := method literalAt: 1.
+ 	candidates := self sn
+ 						allImplementorsOf: literal second
+ 						localTo: (literal first basicSize = 0
+ 									ifTrue: [InterpreterPrimitives]
+ 									ifFalse: [InterpreterPlugin allSubclasses
+ 												detect: [:pluginClass| pluginClass moduleName = literal first]]).
+ 	self assert: candidates size = 1.
+ 	^candidates first compiledMethod!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveHighResClock (in category 'system control primitives') -----
  primitiveHighResClock
+ 	"Return the value of the high resolution clock if this system has any.
+ 	 The exact frequency of the high res clock is undefined specifically so that we can use
+ 	 processor dependent instructions (like RDTSC). The only use for the high res clock is for
+ 	 profiling where we can allocate time based on sub-msec resolution of the high res clock.
+ 	 If no high-resolution counter is available, the platform should return zero. ar 6/22/2007"
+ 	<export: true flags: #FastCPrimitiveFlag>
+ 	self methodReturnValue: (self positive64BitIntegerFor: self ioHighResClock)!
- 	"Return the value of the high resolution clock if this system has any. The exact frequency of the high res clock is undefined specifically so that we can use processor dependent instructions (like RDTSC). The only use for the high res clock is for profiling where we can allocate time based on sub-msec resolution of the high res clock. If no high-resolution counter is available, the platform should return zero."
- 	<export: true>
- 	self pop: 1.
- 	self push: (self positive64BitIntegerFor: self ioHighResClock).!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveProfileSample (in category 'process primitives') -----
  primitiveProfileSample
  	"Primitive. Answer the last sample taken by the profiler, or nil if the profiler isn't active.
  	See also primitiveProfileStart."
+ 	<export: true flags: #FastCPrimitiveFlag>
+ 	self methodReturnValue: profileProcess.
- 	<export: true>
- 	self methodArgumentCount = 0 ifFalse:
- 		[^self primitiveFail].
- 	self pop: 1 thenPush: profileProcess.
  	profileProcess := objectMemory nilObject!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveProfileStart (in category 'process primitives') -----
  primitiveProfileStart
  	"Primitive. Begin profiling execution every by using the interrupt check-counter instead of a time-based process (which is limited to timing resolution and triggers off the same signal that many of the processes being profiled trigger off leading to consistently wrong results).
  	The argument is the number of interrupt checks (method activations) to let go by before taking a sample. The sample is being stored in the profileSample iVar which can be retrieved by executing primitiveProfileSample. When a sample is taken, it signals the semaphore specified in primitiveProfileSemaphore.
  	If the argument is less or equal to zero, it disables profiling."
+ 	<export: true flags: #FastCPrimitiveFlag>
  	| deltaTicks |
+ 	deltaTicks := self stackValue: 0.
+ 	(objectMemory isIntegerObject: deltaTicks) ifTrue:
+ 		[nextProfileTick := self ioHighResClock + (objectMemory integerValueOf: deltaTicks).
+ 		 ^self methodReturnReceiver].
+ 	^self primitiveFailFor: PrimErrBadArgument!
- 	<export: true>
- 	self methodArgumentCount = 1 ifFalse:[^self success: false].
- 	deltaTicks := self stackIntegerValue: 0.
- 	self successful ifTrue:[
- 		nextProfileTick := self ioHighResClock + deltaTicks.
- 		self pop: 1.
- 	]!

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 |
- 	| jmp jmpSamplePrim continuePostSamplePrim jmpSampleNonPrim continuePostSampleNonPrim |
  	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.
  
- 	(flags anyMask: PrimCallCollectsProfileSamples) ifTrue:
- 		["Test nextProfileTick for being non-zero and call checkProfileTick if so"
- 		objectMemory wordSize = 4
- 			ifTrue:
- 				[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
- 				 self MoveAw: coInterpreter nextProfileTickAddress + objectMemory wordSize R: ClassReg.
- 				 self OrR: TempReg R: ClassReg]
- 			ifFalse:
- 				[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
- 				 self CmpCq: 0 R: TempReg].
- 		"If set, jump to record sample call."
- 		jmpSampleNonPrim := self JumpNonZero: 0.
- 		continuePostSampleNonPrim := self Label].
- 
  	"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."
- 	"Invoke the primitive"
  	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].
- 	(flags anyMask: PrimCallMayEndureCodeCompaction)
- 		ifTrue: "Sideways call the C primitive routine so that we return through cePrimReturnEnterCogCode."
- 			["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.
- 			 jmp := jmpSamplePrim := continuePostSamplePrim := nil]
- 		ifFalse:
- 			["Call the C primitive routine."
- 			backEnd genMarshallNArgs: 0 arg: 0 arg: 0 arg: 0 arg: 0.
- 			self CallFullRT: primitiveRoutine asInteger.
- 			backEnd genRemoveNArgsFromStack: 0.
- 			(flags anyMask: PrimCallCollectsProfileSamples) ifTrue:
- 				[self assert: (flags anyMask: PrimCallNeedsNewMethod).
- 				"Test nextProfileTick for being non-zero and call checkProfileTick if so"
- 				objectMemory wordSize = 4
- 					ifTrue:
- 						[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
- 						 self MoveAw: coInterpreter nextProfileTickAddress + objectMemory wordSize R: ClassReg.
- 						 self OrR: TempReg R: ClassReg]
- 					ifFalse:
- 						[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
- 						 self CmpCq: 0 R: TempReg].
- 				"If set, jump to record sample call."
- 				jmpSamplePrim := self JumpNonZero: 0.
- 				continuePostSamplePrim := self Label].
- 			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
- 			In either case 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.
- 			"Test primitive failure"
- 			self MoveAw: coInterpreter primFailCodeAddress R: TempReg.
- 			backEnd hasLinkRegister ifFalse: [self PushR: ClassReg]. "Restore return pc on CISCs"
- 			self flag: 'ask concrete code gen if move sets condition codes?'.
- 			self CmpCq: 0 R: TempReg.
- 			jmp := self JumpNonZero: 0.
- 			"Fetch result from stack"
- 			self MoveMw: (backEnd hasLinkRegister ifTrue: [0] ifFalse: [objectMemory wordSize])
- 				r: SPReg
- 				R: ReceiverResultReg.
- 			self RetN: objectMemory wordSize].	"return to caller, popping receiver"
  
+ 	"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
- 	(flags anyMask: PrimCallCollectsProfileSamples) ifTrue:
- 		["The sample is collected by cePrimReturnEnterCogCode for external calls"
- 		jmpSamplePrim ifNotNil:
- 			["Call ceCheckProfileTick: to record sample and then continue."
- 			jmpSamplePrim jmpTarget: self Label.
- 			self assert: (flags anyMask: PrimCallNeedsNewMethod).
- 			self CallFullRT: (self cCode: [#ceCheckProfileTick asUnsignedIntegerPtr]
- 							   inSmalltalk: [self simulatedTrampolineFor: #ceCheckProfileTick]).
- 			"reenter the post-primitive call flow"
- 			self Jump: continuePostSamplePrim].
- 		"Null newMethod and call ceCheckProfileTick: to record sample and then continue.
- 		 ceCheckProfileTick will map null/0 to coInterpreter nilObject"
- 		jmpSampleNonPrim jmpTarget: self Label.
- 		self MoveCq: 0 R: TempReg.
- 		self MoveR: TempReg Aw: coInterpreter newMethodAddress.
- 		self CallFullRT: (self cCode: [#ceCheckProfileTick asUnsignedIntegerPtr]
- 						   inSmalltalk: [self simulatedTrampolineFor: #ceCheckProfileTick]).
- 		"reenter the post-primitive call flow"
- 		self Jump: continuePostSampleNonPrim].
  
+ 		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 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.
- 	jmp ifNotNil:
- 		["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>>compileOnStackExternalPrimitive:flags: (in category 'primitive generators') -----
  compileOnStackExternalPrimitive: primitiveRoutine flags: flags
  	"Compile a fast call of a C primitive using the current stack page, avoiding the stack switch except on failure.
  	 This convention still uses stackPointer and argumentCount to access operands.  Push all operands to the stack,
  	 assign stackPointer, argumentCount, and zero primFailCode.  Make the call (saving a LinkReg if required).
  	 Test for failure and return.  On failure on Spur, if there is an accessor depth, assign framePointer and newMethod,
  	 do the stack switch, call checkForAndFollowForwardedPrimitiveState, and loop back if forwarders are found.
  	 Fall through to frame build."
  	<option: #SpurObjectMemory>
  	<var: #primitiveRoutine declareC: 'void (*primitiveRoutine)(void)'>
+ 	| calleeSavedRegisterMask linkRegSaveRegister spRegSaveRegister jmp retry continueAfterProfileSample jumpToTakeSample |
- 	| calleeSavedRegisterMask linkRegSaveRegister spRegSaveRegister jmp retry |
  	self assert: (objectRepresentation hasSpurMemoryManagerAPI and: [flags anyMask: PrimCallOnSmalltalkStack]).
  	self deny: (backEnd hasVarBaseRegister
  				and: [self register: VarBaseReg isInMask: ABICallerSavedRegisterMask]).
  
  	(coInterpreter recordFastCCallPrimTraceForMethod: 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.
  	self genExternalizeStackPointerForFastPrimitiveCall.
  	"We may need to save LinkReg and/or SPReg, and given the stack machinations
  	  it is much easier to save them in callee saved registers than on the stack itself."
  	calleeSavedRegisterMask := ABICalleeSavedRegisterMask bitClear: (self registerMaskFor: ClassReg).
  	backEnd hasLinkRegister ifTrue:
  		[linkRegSaveRegister := self availableRegisterOrNoneIn: calleeSavedRegisterMask.
  		 self deny: linkRegSaveRegister = NoReg.
  		 self MoveR: LinkReg R: linkRegSaveRegister.
  		 calleeSavedRegisterMask := calleeSavedRegisterMask bitClear: (self registerMaskFor: linkRegSaveRegister)].
  	spRegSaveRegister := NoReg.
  	(SPReg ~= NativeSPReg
  	 and: [(self isCalleeSavedReg: SPReg) not]) ifTrue:
  		[spRegSaveRegister := self availableRegisterOrNoneIn: calleeSavedRegisterMask.
  		 self deny: spRegSaveRegister = NoReg.
  		 self MoveR: SPReg R: spRegSaveRegister].
  	retry := self Label.
  	(flags anyMask: PrimCallOnSmalltalkStackAlign2x)
  		ifTrue: [self AndCq: (objectMemory wordSize * 2 - 1) bitInvert R: SPReg R: NativeSPReg]
  		ifFalse:
  			[SPReg ~= NativeSPReg ifTrue:
  				[backEnd genLoadNativeSPRegWithAlignedSPReg]].
+ 	backEnd genMarshallNArgs: 0 arg: 0 arg: 0 arg: 0 arg: 0.
+ 	self CallFullRT: primitiveRoutine asInteger.
+ 	backEnd genRemoveNArgsFromStack: 0.
- 	self CallFullRT: primitiveRoutine.
  	self MoveAw: coInterpreter primFailCodeAddress R: TempReg.
  	spRegSaveRegister ~= NoReg ifTrue:
  		[self MoveR: spRegSaveRegister R: SPReg].
  	self CmpCq: 0 R: TempReg.
  	jmp := self JumpNonZero: 0.
  	"Remember to restore the native stack pointer to point to the C stack,
  	 otherwise the Smalltalk frames will get overwritten on an interrupt."
  	SPReg ~= NativeSPReg ifTrue:
  		[backEnd genLoadCStackPointer].
+ 	"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)].
  	"At this point the primitive has cut back stackPointer to point to the result."
+ 	continueAfterProfileSample :=
  	self MoveAw: coInterpreter stackPointerAddress R: TempReg.
  	"get result and restore retpc"
  	backEnd hasLinkRegister
  		ifTrue:
  			[self MoveMw: 0 r: TempReg R: ReceiverResultReg;
  				AddCq: objectMemory wordSize R: TempReg R: SPReg;
  				MoveR: linkRegSaveRegister R: LinkReg]
  		ifFalse:
  			[| retpcOffset |
  			"The original retpc is (argumentCount + 1) words below stackPointer."
  			 retpcOffset := (methodOrBlockNumArgs + 1 * objectMemory wordSize) negated.
  			 self MoveMw: retpcOffset r: TempReg R: ClassReg; "get retpc"
  				MoveR: TempReg R: SPReg;
  			 	MoveMw: 0 r: TempReg R: ReceiverResultReg;
  				MoveR: ClassReg Mw: 0 r: TempReg "put it back on stack for the return..."].
  	self RetN: 0.
  
+ 	(backEnd has64BitPerformanceCounter
+ 	 and: [flags anyMask: PrimCallCollectsProfileSamples]) ifTrue:
+ 		[jumpToTakeSample jmpTarget: self Label.
+ 		 self genTakeProfileSample.
+ 		 self Jump: continueAfterProfileSample].
+ 
  	jmp jmpTarget: self Label.
  	(coInterpreter accessorDepthForExternalPrimitiveMethod: methodObj) >= 0
  		ifTrue:
  			[| skip |
  			 "Given that following primitive state to the accessor depth is recursive, we're asking for
  			  trouble if we run the fixup on the Smalltalk stack page.  Run it on the full C stack instead.
  			 This won't be a performance issue since primitive failure should be very rare."
  			self MoveR: FPReg Aw: coInterpreter framePointerAddress.
  			self MoveCw: primitiveRoutine asInteger R: TempReg.
  			self MoveR: TempReg Aw: coInterpreter primitiveFunctionPointerAddress.
  			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.
  			self genLoadCStackPointersForPrimCall.
+ 			backEnd genMarshallNArgs: 0 arg: 0 arg: 0 arg: 0 arg: 0.
  			self CallFullRT: (self cCode: [#checkForAndFollowForwardedPrimitiveState asUnsignedIntegerPtr]
  								   inSmalltalk: [self simulatedTrampolineFor: #checkForAndFollowForwardedPrimitiveState]).
+ 			backEnd genLoadStackPointersForPrimCall: ClassReg.
- 			backEnd genLoadStackPointersForFastPrimCall: ClassReg.
  			self CmpCq: 0 R: ABIResultReg.
  			skip := self JumpZero: 0.
  			self MoveCq: 0 R: TempReg.
  			self MoveR: TempReg Aw: coInterpreter primFailCodeAddress.
  			self Jump: retry.
  			skip jmpTarget: self Label]
  		ifFalse: "must reload SPReg to undo any alignment change,"
  			[(flags anyMask: PrimCallOnSmalltalkStackAlign2x) ifTrue:
  				[backEnd genLoadStackPointersForFastPrimCall: ClassReg]].
  	"Remember to restore the native stack pointer to point to the C stack,
  	 otherwise the Smalltalk frames will get overwritten on an interrupt."
  	SPReg ~= NativeSPReg ifTrue:
  		[backEnd genLoadCStackPointer].
  	"The LinkRegister now contains the return address either of the primitive call or of checkForAndFollowForwardedPrimitiveState.
  	 It must be restored to the return address of the send invoking this primtiive method."
  	backEnd hasLinkRegister ifTrue:
  		[self MoveR: linkRegSaveRegister R: LinkReg].
  	"Finally remember to reload ReceiverResultReg if required.  Even if
  	 arguments have been pushed, the prolog sequence assumes it is live."
  	(self register: ReceiverResultReg isInMask: ABICallerSavedRegisterMask) ifTrue:
  		[self MoveMw: (methodOrBlockNumArgs + (backEnd hasLinkRegister ifTrue: [0] ifFalse: [1])) * objectMemory wordSize
  			r: SPReg
  			R: ReceiverResultReg].
  	"continue to frame build..."
  	^0!

Item was added:
+ ----- 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: 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: 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"
  
- 	profiling ifTrue:
- 		["Test nextProfileTick for being non-zero and call checkProfileTick: if so.
- 		  N.B. nextProfileTick is 64-bits so 32-bit systems need to test both halves."
- 		objectMemory wordSize = 4
- 			ifTrue:
- 				[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
- 				 self MoveAw: coInterpreter nextProfileTickAddress + objectMemory wordSize R: ClassReg.
- 				 self OrR: TempReg R: ClassReg]
- 			ifFalse:
- 				[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
- 				 self CmpCq: 0 R: TempReg].
- 		"If set, jump to record sample call."
- 		jmpSample := self JumpNonZero: 0.
- 		continuePostSample := self Label].
- 
  	"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:
- 	profiling ifTrue:
  		["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 saveAndRestoreLinkRegAround:
  			[self CallFullRT: (self cCode: '(usqIntptr_t)ceCheckProfileTick'
  						inSmalltalk: [self simulatedTrampolineFor: #ceCheckProfileTick])].
  		 self Jump: continuePostSample]!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genTakeProfileSample (in category 'primitive generators') -----
+ genTakeProfileSample
+ 	methodLabel addDependent:
+ 		(self annotateAbsolutePCRef:
+ 			(self MoveCw: methodLabel asInteger R: ClassReg)).
+ 	backEnd genMarshallNArgs: 1 arg: ClassReg arg: nil arg: nil arg: nil.
+ 	SPReg ~= NativeSPReg ifTrue:
+ 				[backEnd genLoadNativeSPRegWithAlignedSPReg].
+ 	self CallFullRT: (self cCode: [#ceTakeProfileSample: asUnsignedIntegerPtr]
+ 						   inSmalltalk: [self simulatedTrampolineFor: #ceTakeProfileSample:]).
+ 	backEnd genRemoveNArgsFromStack: 1.
+ 	"Remember to restore the native stack pointer to point to the C stack,
+ 	 otherwise the Smalltalk frames will get overwritten on an interrupt."
+ 	SPReg ~= NativeSPReg ifTrue:
+ 		[backEnd genLoadCStackPointer]!

Item was changed:
  ----- Method: StackInterpreter>>initializeInterpreter: (in category 'initialization') -----
  initializeInterpreter: bytesToShift
  	"Initialize Interpreter state before starting execution of a new image."
  	interpreterProxy := self sqGetInterpreterProxy.
  	self dummyReferToProxy.
  	objectMemory initializeObjectMemory: bytesToShift.
  	self checkAssumedCompactClasses.
  	self initializeExtraClassInstVarIndices.
  	method := newMethod := objectMemory nilObject.
  	self cCode: '' inSmalltalk:
  		[breakSelectorLength ifNil:
  			[breakSelectorLength := objectMemory minSmallInteger].
  		 breakLookupClassTag ifNil: [breakLookupClassTag := -1].
  		 reenterInterpreter := ReenterInterpreter new].
  	methodDictLinearSearchLimit := 8.
  	self initialCleanup.
  	LowcodeVM ifTrue: [ self setupNativeStack ].
  	profileSemaphore := profileProcess := profileMethod := objectMemory nilObject.
+ 	self cCode: '' inSmalltalk:
+ 		[InitializationOptions at: #profiling ifPresent:
+ 			[:profiling| "hack turn on profiling, for testing in the simulator."
+ 			 profiling ifTrue:
+ 				[profileSemaphore := objectMemory cloneObject: (objectMemory splObj: TheInterruptSemaphore).
+ 				 objectMemory
+ 					storePointerUnchecked: FirstLinkIndex ofObject: profileSemaphore withValue: objectMemory nilObject;
+ 					storePointerUnchecked: NextLinkIndex ofObject: profileSemaphore withValue: objectMemory nilObject;
+ 					storePointerUnchecked: ExcessSignalsIndex ofObject: profileSemaphore withValue: (objectMemory integerObjectOf: 0)]]].
  	interruptKeycode := 2094. "cmd-. as used for Mac but no other OS"
  	[globalSessionID = 0] whileTrue:
  		[globalSessionID := self
  								cCode: [((self time: #NULL) + self ioMSecs) bitAnd: 16r7FFFFFFF]
  								inSmalltalk: [(Random new next * (SmallInteger maxVal min: 16r7FFFFFFF)) asInteger]].
  	metaAccessorDepth := -2.
  	super initializeInterpreter: bytesToShift!

Item was changed:
  ----- Method: StackInterpreter>>printStringOf: (in category 'debug printing') -----
  printStringOf: oop
  	| fmt len cnt max i |
  	<inline: false>
  	(objectMemory isImmediate: oop) ifTrue:
  		[^self].
  	(objectMemory addressCouldBeObj: oop) ifFalse:
  		[^self].
  	fmt := objectMemory formatOf: oop.
  	fmt < objectMemory firstByteFormat ifTrue: [^self].
  
  	cnt := (max := 128) min: (len := objectMemory lengthOf: oop).
  	i := 0.
  
  	((objectMemory is: oop
  		  instanceOf: (objectMemory splObj: ClassByteArray)
  		  compactClassIndex: classByteArrayCompactIndex)
  	or: [(objectMemory isLargeIntegerInstance: oop)])
  		ifTrue:
  			[[i < cnt] whileTrue:
  				[self printHex: (objectMemory fetchByte: i ofObject: oop).
  				 i := i + 1]]
  		ifFalse:
  			[[i < cnt] whileTrue:
+ 				[| code |
+ 				code := objectMemory fetchByte: i ofObject: oop.
+ 				code
+ 					caseOf: {
+ 						[10 "Character lf asInteger"] -> [self print: '<LF>'].
+ 						[13 "Character cr asInteger"] -> [self print: '<CR>'] }
+ 					otherwise: [self printChar: code].
- 				[self cCode:
- 						[(objectMemory fetchByte: i ofObject: oop) = 13 "Character cr asInteger" ifTrue:
- 							[self print: '<CR>'.
- 							 i + 1 < len ifTrue:
- 								[self print: '...'].
- 							 ^self]].
- 				 self printChar: (objectMemory fetchByte: i ofObject: oop).
  				 i := i + 1]].
  	len > max ifTrue:
  		[self print: '...'].
  	self flush!



More information about the Vm-dev mailing list