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

commits at source.squeak.org commits at source.squeak.org
Sun Feb 2 00:15:39 UTC 2020


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

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

Name: VMMaker.oscog-eem.2694
Author: eem
Time: 1 February 2020, 4:15:25.674627 pm
UUID: 3e4df132-369b-423f-ba3e-7c1d2a402b22
Ancestors: VMMaker.oscog-nice.2693

Cogit:
Add support for a substitute SPReg to cope with the ARMv8's typical 16-byte stack pointer alignment requirement.

Consequently...
- add NativePopR NativePushR NativeRetN abstract instructions (so far only NativeRetN needs to be implemented; see ceCaptureCStackPointers)
- add ABICalleeSavedRegisterMask & ABICallerSavedRegisterMask to CogAbstractRegisters
- refactor register initialization (initializeAbstractRegisters et al) to provide more validation and to equate SPReg and NativeSPReg if NativeSPReg has not been initialized (i.e. default it to be SPReg)

Given the option of having different SPReg and NativeSPReg be much more careful about simulating leaf calls (used for ceCaptureCStackPointers), and generate an improved ceCaptureCStackPointers.

Now that ProcessorSimulationTrap is resumable, simplify the exception handlers in simulateCogCodeAt: and simulateLeafCallOf: so that out-of-bounds reads & writes are resumed from.
Nuke some obsolete register mask code.
Fix a regression in forgetting to revert initializedInstanceForTests:.

=============== Diff against VMMaker.oscog-nice.2693 ===============

Item was added:
+ ----- Method: CoInterpreter>>setCFramePointer: (in category 'simulation') -----
+ setCFramePointer: cfp
+ 	"Set the CFramePointer, either on initialization (see initializeProcessorStack:) or from
+ 	 machine code in ceCaptureCStackPointers.  Since the CFramePointer should not change,
+ 	 (except during callbacks, which we don't yet simulate) unless we are initializing,
+ 	 ceCaptureCFramePointers should yield the same value every time."
+ 	<doNotGenerate>
+ 	CFramePointer ifNotNil: [self assert: CFramePointer = cfp].
+ 	^CFramePointer := cfp!

Item was added:
+ ----- Method: CoInterpreter>>setCStackPointer: (in category 'simulation') -----
+ setCStackPointer: csp
+ 	"Set the CStackPointer, either on initialization (see initializeProcessorStack:) or from
+ 	 machine code in ceCaptureCStackPointers.  Since the CStackPointer should not change,
+ 	 (except during callbacks, which we don't yet simulate) unless we are initializing,
+ 	 ceCaptureCStackPointers should yield the same value every time."
+ 	<doNotGenerate>
+ 	CStackPointer ifNotNil: [self assert: CStackPointer = csp].
+ 	^CStackPointer := csp!

Item was changed:
  ----- Method: CogARMCompiler class>>initializeAbstractRegisters (in category 'class initialization') -----
  initializeAbstractRegisters
  	"Assign the abstract registers with the identities/indices of the relevant concrete registers."
  
- 	super initializeAbstractRegisters.
- 
- 	"According to IHI0042E ARM Architecture Procedure Calling Standard, in section 5.1.1:
- 		A subroutine must preserve the contents of the registers r4-r8, r10, r11 and SP (and r9 in PCS variants that designate r9 as v6).
- 	 SP = r13, so the callee-saved regs are r4-r8 & r10-r12.
- 	 The caller-saved registers are those that are not callee-saved and not reserved for hardware/abi uses,
- 	 i..e r0-r3, r9 & r12.
- 	 We exclude registers 0 & 1 (TempReg/CArg0Reg & CArg1Reg) from the CallerSavedRegisterMask because we only
- 	 use them for argument passing and so never want to save and restore them.  In fact restoring TempReg/CArg0Reg
- 	 would overwrite function results, so it shouldn't be included under any circumstances."
- 
- 	CallerSavedRegisterMask := self registerMaskFor: "0 and: 1 and:" 2 and: 3 and: 9 and: 12.
- 
  	TempReg			:= R0.
  	ClassReg			:= R2.
  	ReceiverResultReg	:= R5.
  	SendNumArgsReg	:= R6.
  	SPReg				:= SP. "a.k.a. R13" self assert: SP = 13.
  	FPReg				:= R11.
  	Arg0Reg			:= R3. "overlaps with last C arg reg"
  	Arg1Reg			:= R4.
  	Extra0Reg			:= R7.
  	Extra1Reg			:= R8.
  	Extra2Reg			:= R9.
  	VarBaseReg		:= R10.	"Must be callee saved" self assert: ConcreteVarBaseReg = R10.
  	RISCTempReg		:= R12.	"a.k.a. IP" self assert: ConcreteIPReg = R12.
  	LinkReg				:= LR. "R14"
  	PCReg				:= PC. "R15"	
  
+ 	"According to IHI0042E ARM Architecture Procedure Calling Standard, in section 5.1.1:
+ 		A subroutine must preserve the contents of the registers r4-r8, r10, r11 and SP (and r9 in PCS variants that designate r9 as v6).
+ 	 SP = r13, so the callee-saved regs are r4-r8 & r10-r12.
+ 	 The caller-saved registers are those that are not callee-saved and not reserved for hardware/abi uses,
+ 	 i..e r0-r3, r9 & r12.
+ 	 We exclude registers 0 & 1 (TempReg/CArg0Reg & CArg1Reg) from the CallerSavedRegisterMask because we only
+ 	 use them for argument passing and so never want to save and restore them.  In fact restoring TempReg/CArg0Reg
+ 	 would overwrite function results, so it shouldn't be included under any circumstances."
+ 
+ 	ABICalleeSavedRegisterMask := self registerMaskFor: 4 and: 5 and: 6 and: 7 and: 10 and: 11.
+ 	ABICallerSavedRegisterMask := self registerMaskFor: 0 and: 1 and: 2 and: 3 and: 9 and: 12.
+ 	CallerSavedRegisterMask := ABICallerSavedRegisterMask
+ 								bitAnd: (self registerMaskFor: ClassReg and: ReceiverResultReg and: SendNumArgsReg and: Arg0Reg and: Arg1Reg).
+ 
  	NumRegisters := 16.
  
  	DPFPReg0			:= D0.
  	DPFPReg1			:= D1.
  	DPFPReg2			:= D2.
  	DPFPReg3			:= D3.
  	DPFPReg4			:= D4.
  	DPFPReg5			:= D5.
  	DPFPReg6			:= D6.
  	DPFPReg7			:= D7.
  
  	NumFloatRegisters := 8!

Item was removed:
- ----- Method: CogARMCompiler>>concreteCalleeSavedRegisterMask (in category 'accessing') -----
- concreteCalleeSavedRegisterMask
- 	"According to IHI0042E ARM Architecture Procedure Calling Standard, in section 5.1.1:
- 		A subroutine must preserve the contents of the registers r4-r8, r10, r11 and SP (and r9 in PCS variants that designate r9 as v6).
- 	 SP = r13, so..."
- 	^2r0000110111110000!

Item was removed:
- ----- Method: CogARMCompiler>>concreteCallerSavedRegisterMask (in category 'accessing') -----
- concreteCallerSavedRegisterMask
- 	"According to IHI0042E ARM Architecture Procedure Calling Standard, in section 5.1.1:
- 		A subroutine must preserve the contents of the registers r4-r8, r10, r11 and SP (and r9 in PCS variants that designate r9 as v6).
- 	 SP = r13, so the callee-saved regs are r4-r8 & r10-r12.
- 	 The caller-saved registers are those that are not callee-saved and not reserved for hardware/abi uses,
- 	 i..e r0-r3, r9 & r12."
- 	^2r1001000001111!

Item was changed:
  ----- Method: CogAbstractInstruction class>>initializeAbstractRegisters (in category 'class initialization') -----
  initializeAbstractRegisters
  	"Assign the abstract registers with the identities/indices of the relevant concrete registers,
  	 and assign CallerSavedRegisterMask appropriately.
  	 First set all abstract registers to #undefined via CogAbstractRegisters initialize, and then,
  	 each subclasses assigns the subset they choose with values of specific concrete registers."
+ 
+ 	CogAbstractRegisters initialize.
+ 	
+ 	CogCompilerClass ifNotNil:
+ 		[(CogCompilerClass withAllSuperclasses copyUpTo: CogAbstractInstruction) reverseDo:
+ 			[:compilerClass| compilerClass initialize; initializeAbstractRegisters]].
+ 
+ 	NativeSPReg == #undefined ifTrue:
+ 		[NativeSPReg := SPReg].
+ 
+ 	self assert: Arg0Reg isInteger.
+ 	self assert: ClassReg isInteger.
+ 	self assert: ReceiverResultReg isInteger.
+ 	self assert: SendNumArgsReg isInteger.
+ 	self assert: TempReg isInteger.
+ 	self assert: FPReg isInteger.
+ 	self assert: SPReg isInteger.
+ 
+ 	self assert: ABICallerSavedRegisterMask isInteger.
+ 	self assert: CallerSavedRegisterMask isInteger.
+ 
+ 	self assert: (VarBaseReg = #undefined or: [SimpleStackBasedCogit basicNew register: VarBaseReg isInMask: ABICalleeSavedRegisterMask])!
- 	CallerSavedRegisterMask := #undefined.
- 	CogAbstractRegisters initialize!

Item was added:
+ ----- Method: CogAbstractInstruction>>usesNativeSPReg (in category 'testing') -----
+ usesNativeSPReg
+ 	"Answer if the code model implemented by the receiver uses the native stack pointer for SPReg.
+ 	 By default answer true."
+ 	^true!

Item was changed:
  SharedPool subclass: #CogAbstractRegisters
  	instanceVariableNames: ''
+ 	classVariableNames: 'ABICalleeSavedRegisterMask ABICallerSavedRegisterMask Arg0Reg Arg1Reg CallerSavedRegisterMask ClassReg DPFPReg0 DPFPReg1 DPFPReg10 DPFPReg11 DPFPReg12 DPFPReg13 DPFPReg14 DPFPReg15 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7 DPFPReg8 DPFPReg9 Extra0Reg Extra1Reg Extra2Reg Extra3Reg Extra4Reg Extra5Reg Extra6Reg Extra7Reg Extra8Reg FPReg LinkReg NativeSPReg NoReg NumFloatRegisters NumRegisters PCReg RISCTempReg ReceiverResultReg SPReg SendNumArgsReg TempReg VarBaseReg'
- 	classVariableNames: 'Arg0Reg Arg1Reg CallerSavedRegisterMask ClassReg DPFPReg0 DPFPReg1 DPFPReg10 DPFPReg11 DPFPReg12 DPFPReg13 DPFPReg14 DPFPReg15 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7 DPFPReg8 DPFPReg9 Extra0Reg Extra1Reg Extra2Reg Extra3Reg Extra4Reg Extra5Reg Extra6Reg Extra7Reg Extra8Reg FPReg LinkReg NoReg NumFloatRegisters NumRegisters PCReg RISCTempReg ReceiverResultReg SPReg SendNumArgsReg TempReg VarBaseReg'
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!
  
+ !CogAbstractRegisters commentStamp: 'eem 2/1/2020 12:44' prior: 0!
+ I am a pool for the abstract register set that the Cogit uses to define its model of Smalltalk compiled to machine code.  My values are defined by each processor's CogAbstractInstruction subclass (e.g. CogIA32Compiler for x86).  See each class side initializeAbstractRegisters method.  Each register's value is an integer if it is available on the processor, or is the symbol #undefined if it is not.
+ 
+ NoReg
+ 	a value that cannot be confused with a register.  The registers below are given values from 0 to N, corresponding to their meaning in the processor's ISA.
+ 	The numbers used may overlap, e.g. floating point registers are numbered from 0 to N and overlap the integer registers numbered from 0 to N
+ 
+ NumFloatRegisters
+ 	the number of floating point registers (DPFPReg0 on up) that the processor provides
+ 	
+ NumRegisters
+ 	the number of integer registers that the processor provides
+ 
+ ABICalleeSavedRegisterMask
+ 	this is the callee saved registers as defined by the platform ABI as a register mask (1 << regM bitOr: 1 << regN etc)
+ ABICallerSavedRegisterMask
+ 	this is the caller saved registers as defined by the platform ABI as a register mask (1 << regM bitOr: 1 << regN etc)
+ CallerSavedRegisterMask
+ 	this is the intersection of the ABICallerSavedRegisterMask and the fixed use registers (Arg0Reg, Arg1Reg, ClassReg, ReceiverResultReg, and SendNumArgsReg)
+ 	i.e. these are the registers that must be preserved when calling a run-time routine that returns
+ 
+ Fixed use Smalltalk registers:
+ 	Arg0Reg
+ 		the register used to pass the zero'th argument in one or two argument sends (on V3 only one argument sends; see CogObjectRepresentation>>numRegArgs)
+ 	Arg1Reg
+ 		the register used to pass the zero'th argument in one or two argument sends (on V3 unused)
+ 	ClassReg
+ 		the register used to pass either the selector (or selector index) in an unlinked send, or the class tag in a linked send, used for checking inline cache sends
+ 	ReceiverResultReg
+ 		the register holding the receiver on send, the result on return, and typically used to hold self when a method is accessing inst vars
+ 	SendNumArgsReg
+ 		the register that passes the number of arguments if the arith of the send is greater than two (see ceSendNArgs et al)
+ 	TempReg
+ 		a generic temporary, that can usefully be equated with the C result register
+ 
+ Dual use Smalltalk registers:
+ 	FPReg
+ 		a register (which is ideally the processor's frame pointer register) used as the frame pointer in frameful methods
+ 	SPReg
+ 		a register (which is ideally the processor's stack pointer register) used as the stack pointer in generated machine code
+ 	NativeSPReg
+ 		the processor's native stack pointer register, which may or may not be equal to SPReg
+ 
+ Allocatable registers
+ 	Extra0Reg through Extra8Reg
+ 		registers allocatable by the code generator. This is work-in-progress.  These should be able to be assigned for temporaries by RegisterAllocatingCogit et al
+ 
+ Code Generator registers
+ RISCTempReg
+ 	a register reserved by a code generator for a RISC (e.g. CogARMCompiler) that is used to synthesize complex instructions
+ 
+ VarBaseReg
+ 	if enough registers are available then this is a register that holds the base address of the CoInterpreter's variables such as stackPointer, newMethod, etc.
+ 	VarBaseReg allows much more concise code accessing those variables from generated machine code
+ 
+ Floating point registers
+ 	DPFPReg0 through DPFPReg15
+ 		the available floating point registers (note that ARMv8 has 32, and that the code generator only uses DPFPReg0 & DPFPReg1).  The processor defines as many as it has
+ 
+ Processor registers
+ 	FPReg
+ 		the processor's frame pointer register (or a register that is used as the Smalltalk frame pointer)
+ 	SPReg
+ 		the processor's stack pointer register
+ 	LinkReg
+ 		if a RISC then the processor's link register, which is loaded with the return address by a call instruction
+ 	PCReg
+ 		if a RISC with an explicit PC register that is one of its general purpose integer registers (as for example does 32-bit ARM, but /not/ 64-bit ARMv8), then this is the register!
- !CogAbstractRegisters commentStamp: 'eem 12/26/2015 14:06' prior: 0!
- I am a pool for the abstract register set that the Cogit uses to define its model of Smalltalk compiled to machine code.!

Item was changed:
  ----- Method: CogAbstractRegisters class>>initialize (in category 'class initialization') -----
  initialize
  	"Define a fixed set of abstract register names used in code generation for Smalltalk code.
  	 These are given concrete values by the currently in-use back end, which is a subclass of
  	 CogAbstractInstruction; see implementors of initializeAbstractRegisters.
  
  	 We assume concrete registers defined by the back ends are in the range 0 to N, possibly
  	 with integer registers and floating-point registers using overlapping ranges of indices.
  	 Here we initialize all registers to #undefined, leaving it to initializeAbstractRegisters to
  	 initialize the subset of the abstract registers that a platform actually uses."
  
  	"NoReg encodes no register, e.g. for parameters that supply an optional register.
  	 Being negative it is distinct from abstract and concrete registers in the 0 to N range."
  	NoReg := -1.
  
+ 	ABICalleeSavedRegisterMask := ABICallerSavedRegisterMask := CallerSavedRegisterMask := 0.
+ 
  	"The core set of abstract registers that define the Cogit's model of Smalltalk code
  	 provide for a register-based calling convention oriented towards inline cacheing and
  	 executing a core set of machine code primitives in registers.  The set is composed of
  	 8 registers, dictated by the available registers on IA32."
  	"Smalltalk machine code executes on stack pages in the stack zone, requiring frame and stack pointers."
  	FPReg				:= #undefined.	"A frame pointer is used for Smalltalk frames."
  	SPReg				:= #undefined.
  	ReceiverResultReg	:= #undefined.	"The receiver at point of send, and return value of a send"
  	ClassReg			:= #undefined.	"The inline send cache class tag is in this register, loaded at the send site"
  	SendNumArgsReg	:= #undefined.	"Sends > 2 args set the arg count in this reg"
  	Arg0Reg			:= #undefined.	"In the StackToRegisterMappingCogit 1 & 2 arg sends marshall into these registers."
  	Arg1Reg			:= #undefined.
  	TempReg			:= #undefined.
  
  	"A small fixed set of abstract scratch registers for register-rich machines (ARM can use 1, x64 can use 6 or 7)."
  	Extra0Reg := #undefined.
  	Extra1Reg := #undefined.
  	Extra2Reg := #undefined.
  	Extra3Reg := #undefined.
  	Extra4Reg := #undefined.
  	Extra5Reg := #undefined.
  	Extra6Reg := #undefined.
  	Extra7Reg := #undefined.
  	Extra8Reg := #undefined.
  
+ 	"processor-specific registers"
+ 	NativeSPReg := #undefined.
+ 
  	"RISC-specific registers"
  	LinkReg		:= #undefined.
  	RISCTempReg	:= #undefined.		"Used to synthesize CISC instructions from multiple RISC instructions."
  	PCReg			:= #undefined.		"If the processor has an assignable pc, e.g. ARM"
  	VarBaseReg		:= #undefined.		"If useful, points to base of interpreter variables."
  
  	NumRegisters	:= #undefined.	"Number of basic/integer regsiters (we don't do M68k ;-) )"
  
  	"Up to 16 floating-point registers. e.g. IA32+SSE2 can use 8, x64 can use 16."
  	DPFPReg0	:= #undefined.
  	DPFPReg1	:= #undefined.
  	DPFPReg2	:= #undefined.
  	DPFPReg3	:= #undefined.
  	DPFPReg4	:= #undefined.
  	DPFPReg5	:= #undefined.
  	DPFPReg6	:= #undefined.
  	DPFPReg7	:= #undefined.
  	DPFPReg8	:= #undefined.
  	DPFPReg9	:= #undefined.
  	DPFPReg10	:= #undefined.
  	DPFPReg11	:= #undefined.
  	DPFPReg12	:= #undefined.
  	DPFPReg13	:= #undefined.
  	DPFPReg14	:= #undefined.
  	DPFPReg15	:= #undefined.
  
+ 	NumFloatRegisters	:= #undefined.	"Number of floating-point registers (we don;t do single-precision; we don't do xmm high (yet)."
+ 
+ 	classPool keysAndValuesDo:
+ 		[:k :value|
+ 		self assert: value == (#(-1 0 0 0) at: (#(NoReg ABICalleeSavedRegisterMask ABICallerSavedRegisterMask CallerSavedRegisterMask) indexOf: k) ifAbsent: [#undefined])]!
- 	NumFloatRegisters	:= #undefined.	"Number of floating-point registers (we don;t do single-precision; we don't do xmm high (yet)."!

Item was changed:
  ----- Method: CogIA32Compiler class>>initializeAbstractRegisters (in category 'class initialization') -----
  initializeAbstractRegisters
  	"Assign the abstract registers with the identities/indices of the relevant concrete registers."
  
- 	super initializeAbstractRegisters.
- 
  	"N.B. EAX ECX & EDX are caller-save (scratch) registers.  Hence we use ECX for class and EDX for
  		receiver/result since these are written in all normal sends.  EBX ESI & EDI are callee-save."
  
- 	CallerSavedRegisterMask := self registerMaskFor: EAX and: ECX and: EDX.
- 
  	TempReg				:= EAX.
  	ClassReg				:= ECX.
  	ReceiverResultReg		:= EDX.
  	SendNumArgsReg		:= EBX.
  	SPReg					:= ESP.
  	FPReg					:= EBP.
  	Arg0Reg				:= ESI.
  	Arg1Reg				:= EDI.
  
+ 	ABICalleeSavedRegisterMask := self registerMaskFor: EBX and: ESI and: EDI.
+ 	ABICallerSavedRegisterMask := self registerMaskFor: EAX and: ECX and: EDX.
+ 	CallerSavedRegisterMask := ABICallerSavedRegisterMask
+ 								bitAnd: (self registerMaskFor: ClassReg and: ReceiverResultReg and: SendNumArgsReg and: Arg0Reg and: Arg1Reg).
+ 
  	NumRegisters := 8.
  
  	DPFPReg0				:= XMM0L.
  	DPFPReg1				:= XMM1L.
  	DPFPReg2				:= XMM2L.
  	DPFPReg3				:= XMM3L.
  	DPFPReg4				:= XMM4L.
  	DPFPReg5				:= XMM5L.
  	DPFPReg6				:= XMM6L.
  	DPFPReg7				:= XMM7L.
  
  	NumFloatRegisters := 8!

Item was changed:
  ----- Method: CogMIPSELCompiler class>>initializeAbstractRegisters (in category 'class initialization') -----
  initializeAbstractRegisters
  	"Assign the abstract registers with the identities/indices of the relevant concrete registers."
  
  	"See MIPSConstants>>initializeRegisters for a description of the C ABI."
  
  	"Note we can fit all of the abstract registers in C preserved registers, and
  	 not need to save or restore them at runtime calls."
- 	super initializeAbstractRegisters.
  
- 	self flag: #OABI.
- 	CallerSavedRegisterMask := self
- 									registerMaskFor: T0 and: T1 and: T2 and: T3
- 									and: T4 and: T5 and: T6 and: T7 and: T8 and: T9.
- 
  	ReceiverResultReg		:= S0.
  	Arg0Reg				:= S1.
  	Arg1Reg				:= S2.
  	ClassReg				:= S3.
  	SendNumArgsReg		:= S4.
  	TempReg				:= S5.
+ 	VarBaseReg				:= S6. "Must be callee saved"
- 	VarBaseReg			:= S6. "Must be callee saved"
  	SPReg					:= SP.
  	FPReg					:= FP.
  	RISCTempReg			:= AT.
+ 	LinkReg				:= RA.
- 	LinkReg					:= RA.
  
+ 	self flag: #OABI.
+ 	ABICallerSavedRegisterMask := self
+ 									registerMaskFor: T0 and: T1 and: T2 and: T3
+ 									and: T4 and: T5 and: T6 and: T7 and: T8 and: T9.
+ 	CallerSavedRegisterMask := ABICallerSavedRegisterMask
+ 								bitAnd: (self registerMaskFor: ClassReg and: ReceiverResultReg and: SendNumArgsReg and: Arg0Reg and: Arg1Reg).
+ 
  	NumRegisters := 32.
  
  	self flag: #todo.
  	"Extra0Reg			:= ??.
  	Extra1Reg			:= ??.
  	Extra2Reg			:= ??.
  	Extra3Reg			:= ??.
  	Extra4Reg			:= ??.
  	Extra5Reg			:= ??.
  	Extra6Reg			:= ??.
  	Extra7Reg			:= ??."
  
  	self flag: #todo.
  	"DPFPReg0				:= ??.
  	DPFPReg1				:= ??.
  	DPFPReg2				:= ??.
  	DPFPReg3				:= ??.
  	DPFPReg4				:= ??.
  	DPFPReg5				:= ??.
  	DPFPReg6				:= ??.
  	DPFPReg7				:= ??.
  	DPFPReg8				:= ??.
  	DPFPReg9				:= ??.
  	DPFPReg10				:= ??.
  	DPFPReg11				:= ??.
  	DPFPReg12				:= ??.
  	DPFPReg13				:= ??.
  	DPFPReg14				:= ??.
  	DPFPReg15				:= ??"!

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 JumpNegative JumpNoCarry JumpNoOverflow JumpNonNegative JumpNonZero JumpOverflow JumpR JumpZero Label LastJump LastRTLCode Literal LoadEffectiveAddressMwrR LogicalShiftLeftCqR LogicalShiftLeftCqRR LogicalShiftLeftRR LogicalShiftRightCqR LogicalShiftRightCqRR LogicalShiftRightRR MoveA32R MoveAbR MoveAwR MoveC32R Mo
 veCqR 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'
- 	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 JumpNegative JumpNoCarry JumpNoOverflow JumpNonNegative JumpNonZero JumpOverflow JumpR JumpZero Label LastJump LastRTLCode Literal LoadEffectiveAddressMwrR LogicalShiftLeftCqR LogicalShiftLeftCqRR LogicalShiftLeftRR LogicalShiftRightCqR LogicalShiftRightCqRR LogicalShiftRightRR MoveA32R MoveAbR MoveAwR MoveC32R Mo
 veCqR 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 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 added:
+ ----- Method: CogVMSimulator>>printRumpCStack (in category 'rump c stack') -----
+ printRumpCStack
+ 	self printRumpCStackTo: heapBase - objectMemory wordSize!

Item was changed:
  ----- Method: CogX64Compiler class>>initializeAbstractRegisters (in category 'class initialization') -----
  initializeAbstractRegisters
  	"Assign the abstract registers with the identities/indices of the relevant concrete registers."
  	"[1] Figure 3.4 Register Usage in
  		System V Application Binary Interface
  		AMD64 Architecture Processor Supplement"
  
- 	super initializeAbstractRegisters.
- 
  	"N.B. RAX RCX & RDX are caller-save (scratch) registers.  Hence we use RCX for class and RDX for
  		receiver/result since these are written in all normal sends."
  
  	SysV
  		ifTrue: [self initializeAbstractRegistersSysV]
  		ifFalse: [self initializeAbstractRegistersWin64].
  
+ 	CallerSavedRegisterMask := ABICallerSavedRegisterMask
+ 								bitAnd: (self registerMaskFor: ClassReg and: ReceiverResultReg and: SendNumArgsReg and: Arg0Reg and: Arg1Reg).
+ 
  	NumRegisters := 16.
  
  	DPFPReg0				:= XMM0L.
  	DPFPReg1				:= XMM1L.
  	DPFPReg2				:= XMM2L.
  	DPFPReg3				:= XMM3L.
  	DPFPReg4				:= XMM4L.
  	DPFPReg5				:= XMM5L.
  	DPFPReg6				:= XMM6L.
  	DPFPReg7				:= XMM7L.
  	DPFPReg8				:= XMM8L.
  	DPFPReg9				:= XMM9L.
  	DPFPReg10				:= XMM10L.
  	DPFPReg11				:= XMM11L.
  	DPFPReg12				:= XMM12L.
  	DPFPReg13				:= XMM13L.
  	DPFPReg14				:= XMM14L.
  	DPFPReg15				:= XMM15L.
  
  	NumFloatRegisters := 16!

Item was changed:
  ----- Method: CogX64Compiler class>>initializeAbstractRegistersSysV (in category 'class initialization') -----
  initializeAbstractRegistersSysV
  	"Assign the abstract registers with the identities/indices of the relevant concrete registers."
  	"[1] Figure 3.4 Register Usage in
  		System V Application Binary Interface
  		AMD64 Architecture Processor Supplement"
  
  	"N.B. RAX RCX & RDX are caller-save (scratch) registers.  Hence we use RCX for class and RDX for
  		receiver/result since these are written in all normal sends."
  
+ 	ABICalleeSavedRegisterMask := self registerMaskFor: RBX and: R12 and: R13 and: R14 and: R15.
+ 	ABICallerSavedRegisterMask := self
- 	CallerSavedRegisterMask := self
  									registerMaskFor: RAX
  									and: RCX
  									and: RDX
  									and: RSI
  									and: RDI
  									and: R8
  									and: R9
  									and: R10
  									and: R11.
  
  	TempReg				:= RAX.
  	ClassReg				:= RCX.
  	ReceiverResultReg		:= RDX.
  	SendNumArgsReg		:= R9.
  	SPReg					:= RSP.
  	FPReg					:= RBP.
  	Arg0Reg				:= RDI. "So as to agree with C ABI arg 0"
  	Arg1Reg				:= RSI. "So as to agree with C ABI arg 1"
+ 	VarBaseReg				:= RBX. "Must be callee saved"
- 	VarBaseReg			:= RBX. "Must be callee saved"
  	"R8 is either RISCTempReg or Extra6Reg depending on subclass."
  	Extra0Reg				:= R10.
  	Extra1Reg				:= R11.
  	Extra2Reg				:= R12.
  	Extra3Reg				:= R13.
  	Extra4Reg				:= R14.
  	Extra5Reg				:= R15!

Item was changed:
  ----- Method: CogX64Compiler class>>initializeAbstractRegistersWin64 (in category 'class initialization') -----
  initializeAbstractRegistersWin64
  	"Assign the abstract registers with the identities/indices of the relevant concrete registers."
  
  	"N.B. Since receiver/result are written in all normal sends,
+ 	 it's better to use scratch registers for them (those which are caller-saved).
+ 	 In Win64 ABI, this does not leave that many choices:
+ 		- RAX is TempReg (overwritten by result etc...)
+ 		- RCX and RDX are used for first 2 args (see genMarshallNArgs:arg:arg:arg:arg:)
+ 		- it remains R8,R9,R10 & R11 : we choose the first two"
- 	it's better to use scratch registers for them (those which are caller-saved).
- 	In Win64 ABI, this does not let that many choices:
- 	- RAX is TempReg (overwritten by result etc...)
- 	- RCX and RDX are used for first 2 args (see genMarshallNArgs:arg:arg:arg:arg:)
- 	- it remains R8,R9,R10 & R11 : we choose the first two"
  
+ 	ABICalleeSavedRegisterMask := self registerMaskFor: RBX and: RSI and: RDI and: R12 and: R13 and: R14 and: R15.
+ 	ABICallerSavedRegisterMask := self
- 	CallerSavedRegisterMask := self
  									registerMaskFor: RAX
  									and: RCX
  									and: RDX
  									and: R8
  									and: R9
  									and: R10
  									and: R11.
  
  	TempReg				:= RAX.
  	ClassReg				:= R8.
  	ReceiverResultReg		:= R9.
  	SendNumArgsReg		:= R10.
  	SPReg					:= RSP.
  	FPReg					:= RBP.
  	Arg0Reg				:= RCX. "So as to agree with C ABI arg 0"
  	Arg1Reg				:= RDX. "So as to agree with C ABI arg 1"
+ 	VarBaseReg				:= RBX. "Must be callee saved"
- 	VarBaseReg			:= RBX. "Must be callee saved"
  	"R11 is either RISCTempReg or Extra6Reg depending on subclass."
  	Extra0Reg				:= RDI.
  	Extra1Reg				:= RSI.
  	Extra2Reg				:= R12.
  	Extra3Reg				:= R13.
  	Extra4Reg				:= R14.
  	Extra5Reg				:= R15!

Item was changed:
  ----- Method: Cogit class>>initializeMiscConstants (in category 'class initialization') -----
  initializeMiscConstants
  	super initializeMiscConstants.
  	Debug := InitializationOptions at: #Debug ifAbsent: [false].
  	(InitializationOptions includesKey: #EagerInstructionDecoration)
  		ifTrue:
  			[EagerInstructionDecoration := InitializationOptions at: #EagerInstructionDecoration]
  		ifFalse:
  			[EagerInstructionDecoration ifNil:
  				[EagerInstructionDecoration := false]]. "speeds up single stepping but could lose fidelity"
  
  	ProcessorClass := (InitializationOptions at: #ISA ifAbsentPut: [self objectMemoryClass defaultISA]) caseOf: {
  							[#X64] 	->	[BochsX64Alien].
  							[#IA32] 	->	[BochsIA32Alien].
  							[#ARMv5]	->	[GdbARMAlien].
  							[#ARMv8]	->	[GdbARMv8Alien].
  							[#MIPSEL]	->	[MIPSELSimulator] }.
  	CogCompilerClass := self activeCompilerClass.
+ 	CogAbstractInstruction initializeAbstractRegisters.
+ 
- 	(CogCompilerClass withAllSuperclasses copyUpTo: CogAbstractInstruction) reverseDo:
- 		[:compilerClass| compilerClass initialize; initializeAbstractRegisters].
  	self objectMemoryClass objectRepresentationClass initializeMiscConstants.
  	"Our criterion for which methods to JIT is literal count.  The default value is 60 literals or less."
  	MaxLiteralCountForCompile := InitializationOptions at: #MaxLiteralCountForCompile ifAbsent: [60].
  	"we special-case 0, 1 & 2 argument sends, N is numArgs >= 3"
  	NumSendTrampolines := 4.
  	"Currently not even the ceImplicitReceiverTrampoline contains object references."
  	NumObjRefsInRuntime := 0.
  	"6 is a fine number for the max number of PCI entries.  8 is too large."
  	MaxCPICCases := 6.
  
  	"One variable defines whether in a block and whether in a vanilla or full block."
  	InVanillaBlock := 1.
  	InFullBlock := 2.
  
  	NSCSelectorIndex := (NSSendCache instVarNames indexOf: #selector) - 1.
  	NSCNumArgsIndex := (NSSendCache instVarNames indexOf: #numArgs) - 1.
  	NSCClassTagIndex := (NSSendCache instVarNames indexOf: #classTag) - 1.
  	NSCEnclosingObjectIndex := (NSSendCache instVarNames indexOf: #enclosingObject) - 1.
  	NSCTargetIndex := (NSSendCache instVarNames indexOf: #target) - 1.
  	NumOopsPerNSC := NSSendCache instVarNames size.
  
  	"Max size to alloca when compiling.
  	 Mac OS X 10.6.8 segfaults approaching 8Mb.
  	 Linux 2.6.9 segfaults above 11Mb.
  	 WIndows XP segfaults approaching 2Mb."
  	MaxStackAllocSize := 1024 * 1024 * 3 / 2 !

Item was changed:
  ----- Method: Cogit class>>initializedInstanceForTests: (in category 'in-image compilation support') -----
  initializedInstanceForTests: optionsDictionaryOrArray
  	"Answer an instance of a Cogit suitable for running tests that has initialized
  	 its method zone (generated trampolines etc)"
  	| cogit coInterpreter |
  	cogit := self instanceForTests: optionsDictionaryOrArray.
  	coInterpreter := CurrentImageCoInterpreterFacade forCogit: cogit.
  	[cogit
  		setInterpreter: coInterpreter;
  		singleStep: true;
+ 		initializeCodeZoneFrom: 1024 upTo: coInterpreter memory byteSize.
- 		initializeCodeZoneFrom: 1024 upTo: coInterpreter memory byteSize writableCodeZone: 0.
  	 cogit methodZone freeStart: (cogit methodZone freeStart roundUpTo: 1024)]
  		on: Notification
  		do: [:ex|
  			(ex messageText beginsWith: 'cannot find receiver for') ifTrue:
  				[ex resume: coInterpreter].
  			ex pass].
  	^cogit!

Item was added:
+ ----- Method: Cogit>>NativeRetN: (in category 'abstract instructions') -----
+ NativeRetN: offset
+ 	^self gen: (NativeSPReg = SPReg ifTrue: [RetN] ifFalse: [NativeRetN]) operand: offset!

Item was added:
+ ----- Method: Cogit>>availableRegisterOrNoneIn: (in category 'register management') -----
+ availableRegisterOrNoneIn: liveRegsMask
+ 	"Answer an unused abstract register in the registerMask, or NoReg if none."
+ 	liveRegsMask ~= 0 ifTrue:
+ 		[0 to: 31 do:
+ 			[:reg| (liveRegsMask anyMask: 1 << reg) ifTrue: [^reg]]].
+ 	^NoReg!

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

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

Item was removed:
- ----- Method: Cogit>>handleSimulationTrap: (in category 'simulation only') -----
- handleSimulationTrap: aProcessorSimulationTrap
- 	<doNotGenerate>
- 	aProcessorSimulationTrap type caseOf:
- 		{ [#read] -> [self handleReadSimulationTrap: aProcessorSimulationTrap].
- 		  [#write] -> [self handleWriteSimulationTrap: aProcessorSimulationTrap].
- 		  [#call] -> [self handleCallOrJumpSimulationTrap: aProcessorSimulationTrap].
- 		  [#jump] -> [self handleCallOrJumpSimulationTrap: aProcessorSimulationTrap] }!

Item was changed:
  ----- Method: Cogit>>initializeProcessorStack: (in category 'initialization') -----
  initializeProcessorStack: rumpCStackAddress
  	"Initialize the simulation processor's stack pointers, arranging that they are somewhere on the rump C stack."
  	<doNotGenerate>
  	| stackPad cFramePointer cStackPointer |
  	stackPad := 64 max: cStackAlignment.
  	cStackPointer := rumpCStackAddress - stackPad + expectedSPAlignment.
  	cFramePointer := rumpCStackAddress - stackPad + cStackAlignment + expectedFPAlignment.
  	self assert: cStackPointer \\ cStackAlignment = expectedSPAlignment.
  	self assert: cFramePointer \\ cStackAlignment = expectedFPAlignment.
+ 	processor
+ 		setFramePointer: (coInterpreter setCFramePointer: cFramePointer)
+ 		stackPointer: (coInterpreter setCStackPointer: cStackPointer)!
- 	processor setFramePointer: cFramePointer stackPointer: cStackPointer!

Item was changed:
  ----- Method: Cogit>>provideContextForCurrentInstruction (in category 'simulation processor access') -----
  provideContextForCurrentInstruction
  	printRegisters ifFalse:
  		[processor printRegistersOn: coInterpreter transcript].
  	printInstructions ifFalse:
+ 		[(self addressIsInCodeZone: processor pc) ifTrue:
+ 			[self disassembleFrom: processor pc to: processor pc]]!
- 		[self disassembleFrom: processor pc to: processor pc]!

Item was changed:
  ----- Method: Cogit>>simulateCogCodeAt: (in category 'simulation only') -----
  simulateCogCodeAt: address "<Integer>"
  	<doNotGenerate>
  	| stackZoneBase |
  	stackZoneBase := coInterpreter stackZoneBase.
  	processor pc: address.
  	[[[singleStep
  		ifTrue:
  			[[processor sp < stackZoneBase ifTrue: [self halt].
  			  self recordProcessing.
  			  self maybeBreakAt: processor pc] value. "So that the Debugger's Over steps over all this"
  			  processor
  					singleStepIn: coInterpreter memory
  					minimumAddress: guardPageSize
  					readOnlyBelow: methodZone zoneEnd]
  		ifFalse:
  			[processor
  					runInMemory: coInterpreter memory
  					minimumAddress: guardPageSize
  					readOnlyBelow: methodZone zoneEnd].
  	   "((printRegisters or: [printInstructions]) and: [clickConfirm]) ifTrue:
  	 	[(self confirm: 'continue?') ifFalse:
  			[clickConfirm := false. self halt]]."
  	   true] whileTrue]
  		on: ProcessorSimulationTrap
+ 		do: [:ex|
+ 			ex type == #read ifTrue:
+ 				[self handleReadSimulationTrap: ex. ex resume: processor].
+ 			ex type == #write ifTrue:
+ 		 		[self handleWriteSimulationTrap: ex. ex resume: processor].
+ 			self handleCallOrJumpSimulationTrap: ex].
- 		do: [:ex| self handleSimulationTrap: ex].
  	 true] whileTrue!

Item was changed:
  ----- Method: Cogit>>simulateLeafCallOf: (in category 'simulation only') -----
  simulateLeafCallOf: someFunction
  	"Simulate execution of machine code that leaf-calls someFunction,
  	 answering the result returned by someFunction."
+ 	"CogProcessorAlienInspector openFor: coInterpreter"
  	<doNotGenerate>
+ 	| priorSP priorPC spOnEntry |
- 	| spOnEntry |
  	self recordRegisters.
+ 	priorSP := processor sp.
+ 	priorPC := processor pc.
  	processor
+ 		setFramePointer: coInterpreter getCFramePointer stackPointer: coInterpreter getCStackPointer;
  		simulateLeafCallOf: someFunction
  		nextpc: 16rBADF00D5
  		memory: coInterpreter memory.
  	spOnEntry := processor sp.
  	self recordInstruction: {'(simulated call of '. someFunction. ')'}.
+ 	[processor pc between: 0 and: methodZone zoneEnd] whileTrue:
+ 		[[singleStep
- 	[[processor pc between: 0 and: methodZone zoneEnd] whileTrue:
- 		[singleStep
  			ifTrue: [self recordProcessing.
  					self maybeBreakAt: processor pc.
  					processor
  						singleStepIn: coInterpreter memory
  						minimumAddress: guardPageSize
  						readOnlyBelow: methodZone zoneEnd]
  			ifFalse: [processor
  						runInMemory: coInterpreter memory
  						minimumAddress: guardPageSize
+ 						readOnlyBelow: methodZone zoneEnd]]
+ 			on: ProcessorSimulationTrap, Error
+ 			do: [:ex| | retpc |
+ 				processor pc = 16rBADF00D5 ifTrue:
+ 					[retpc := processor leafRetpcIn: coInterpreter memory.
+ 					 self assert: retpc = 16rBADF00D5.
+ 					 self recordInstruction: {'(simulated (real) return to '. retpc. ')'}.
+ 					 ^processor cResultRegister].
+ 				ex class == ProcessorSimulationTrap ifTrue:
+ 					[ex type == #read ifTrue:
+ 						[self handleReadSimulationTrap: ex. ex resume: processor].
+ 					 ex type == #write ifTrue:
+ 		 				[self handleWriteSimulationTrap: ex. ex resume: processor]].
+ 				ex pass]].
+ 	processor pc = 16rBADF00D5 ifTrue:
+ 		[self recordInstruction: {'(simulated (real) return to '. processor pc. ')'}].
- 						readOnlyBelow: methodZone zoneEnd]]]
- 		on: ProcessorSimulationTrap
- 		do: [:ex| | retpc |
- 			"If the ip is out of bounds the return has already occurred."
- 			((processor pc between: 0 and: methodZone zoneEnd)
- 			 and: [processor sp <= spOnEntry]) ifTrue:
- 				[retpc := processor leafRetpcIn: coInterpreter memory.
- 				 self assert: retpc = 16rBADF00D5.
- 				 self recordInstruction: {'(simulated return to '. retpc. ')'.
- 				 processor simulateLeafReturnIn: coInterpreter memory}.
- 				 self recordRegisters]].
  	^processor cResultRegister!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>getCFramePointer (in category 'accessing') -----
+ getCFramePointer
+ 	^coInterpreter getCFramePointer!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>getCStackPointer (in category 'accessing') -----
+ getCStackPointer
+ 	^coInterpreter getCStackPointer!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>setCFramePointer: (in category 'accessing') -----
+ setCFramePointer: cfp
+ 	^coInterpreter setCFramePointer: cfp!

Item was added:
+ ----- Method: CurrentImageCoInterpreterFacade>>setCStackPointer: (in category 'accessing') -----
+ setCStackPointer: csp
+ 	^coInterpreter setCStackPointer: csp!

Item was changed:
  ----- Method: VMClass class>>openCogitMultiWindowBrowser (in category 'utilities') -----
  openCogitMultiWindowBrowser
  	"Answer a new multi-window browser on the ObjectMemory classes, the Cog Interpreter classes, and the main JIT classes"
  	"self openCogitMultiWindowBrowser"
  	| b |
  	b := Browser open.
+ 	{CogRTLOpcodes. CogAbstractRegisters },
+ 	(CogAbstractInstruction withAllSubclasses reject: [:c| c name endsWith: 'Tests']),
  	Cogit withAllSubclasses,
+ 	{CogMethodZone },
  	CogObjectRepresentation withAllSubclasses,
- 	{CogMethodZone. CogRTLOpcodes },
  	(CogAbstractInstruction withAllSubclasses reject: [:c| c name endsWith: 'Tests']),
  	CogBytecodeFixup withAllSubclasses,
  	CogSimStackEntry withAllSubclasses,
  	{VMStructType. VMMaker. CCodeGenerator. TMethod}
  		do: [:class|
  			b selectCategoryForClass: class; selectClass: class]
  		separatedBy:
  			[b multiWindowState addNewWindow].
  	b multiWindowState selectWindowIndex: 1!




More information about the Vm-dev mailing list