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

commits at source.squeak.org commits at source.squeak.org
Sat Dec 26 20:30:00 UTC 2015


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

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

Name: VMMaker.oscog-eem.1613
Author: eem
Time: 26 December 2015, 8:28:05.311 pm
UUID: c484a2ad-5f40-4de8-a9c2-3c4f4a4942aa
Ancestors: VMMaker.oscog-eem.1612

SpurMemoryManagers: Add Spur32BitMemoryManager or Spur64BitMemoryManager to the options so that Cogit can select small float prims properly.

Cogit:
Improve instruction printing so that floating point ops print with the right register names.  Refactor computing the print format to allow special casing throughout the CogAbstractInstruction hierarchy.

Split out the abstract register names from CogRTLOpcodes to CogAbstractRegisters so that the mapping from opcode index to opcode name (and indeed the mapping from register index to register name) works straight-forwardly without hacks to prevent register index and opcode index confusion.

Make initializeAbstractRegisters initialize all abstract registers to #undefined before defining the used subset to the relevant concrete registers.

Nuke unused method.

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

Item was changed:
  TestCase subclass: #AbstractInstructionTests
  	instanceVariableNames: 'processor opcodes'
  	classVariableNames: ''
+ 	poolDictionaries: 'CogAbstractRegisters CogRTLOpcodes'
- 	poolDictionaries: 'CogRTLOpcodes'
  	category: 'VMMaker-Tests'!

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."
  
  	"N.B. According to BSABI, R0-R3 are caller-save, R4-R12 are callee save.
  	 Note that R9 might be a special register for the implementation. In some slides
  	 it is refered to as sb. R10 can contain the stack limit (sl), R11 the fp. R12 is an
  	 intra-procedure scratch instruction pointer for link purposes. It can also be used.
  	 R10 is used as temporary inside a single abstract opcode implementation"
  	"R0-R3 are used when calling back to the interpreter. Using them would require
  	 saving and restoring their values, so they are omitted so far. R12 is the only
  	 scratch register at the moment.."
  
+ 	super initializeAbstractRegisters.
+ 
  	TempReg			:= R0.
  	ClassReg			:= R8.
  	ReceiverResultReg	:= R7.
  	SendNumArgsReg	:= R6.
  	SPReg				:= SP. "R13"
  	FPReg				:= R11.
  	Arg0Reg			:= R4.
  	Arg1Reg			:= R5.
  	VarBaseReg		:= ConcreteVarBaseReg. "Must be callee saved"
  	RISCTempReg		:= ConcreteIPReg. "a.k.a. IP"
  	Scratch0Reg		:= R12.
  	LinkReg				:= LR. "R14"
  	PCReg				:= PC. "R15"	
  
  	DPFPReg0			:= D0.
  	DPFPReg1			:= D1.
  	DPFPReg2			:= D2.
  	DPFPReg3			:= D3.
  	DPFPReg4			:= D4.
  	DPFPReg5			:= D5.
  	DPFPReg6			:= D6.
  	DPFPReg7			:= D7
  !

Item was added:
+ ----- Method: CogARMCompiler>>nameForFPRegister: (in category 'printing') -----
+ nameForFPRegister: reg "<Integer>"
+ 	<doNotGenerate>
+ 	(reg between: 0 and: 7) ifTrue:
+ 		[^#(D0 D1 D2 D3 D4 D5 D6 D7) at: reg + 1].
+ 	^super nameForFPRegister: reg!

Item was changed:
  VMStructType subclass: #CogAbstractInstruction
  	instanceVariableNames: 'opcode machineCodeSize maxSize annotation machineCode operands address dependent cogit objectMemory bcpc'
  	classVariableNames: 'NumOperands'
+ 	poolDictionaries: 'CogAbstractRegisters CogCompilationConstants CogRTLOpcodes'
- 	poolDictionaries: 'CogCompilationConstants CogRTLOpcodes'
  	category: 'VMMaker-JIT'!
  
  !CogAbstractInstruction commentStamp: 'eem 4/21/2015 09:12' prior: 0!
  I am an abstract instruction generated by the Cogit.  I am subsequently concretized to machine code for the current processor.  A sequence of concretized CogAbstractInstructions are concatenated to form the code for a CogMethod.  I am an abstract class.  My concrete subclasses concretize to the machine code of a specific processor.
  
  Instance Variables
  	address:			<Integer>
  	bcpc:				<Integer>
  	cogit:				<Cogit>
  	dependent:			<AbstractInstruction|nil>
  	machineCode:		<CArray on: (ByteArray|Array)>
  	machineCodeSize:	<Integer>
  	maxSize:			<Integer>
  	objectMemory:		<NewCoObjectMemory|SpurCoMemoryManager etc>
  	opcode:			<Integer>
  	operands:			<CArray on: Array>
  
  address
  	- the address at which the instruction will be generated
  
  bcpc
  	- the bytecode pc for which the instruction was generated; simulation only
  
  cogit
  	- the Cogit assembling the receiver; simulation only
  
  dependent
  	- a reference to another instruction which depends on the receiver, if any; in C this is a pointer
  
  machineCode
  	- the array of machine code the receiver generates when concretized
  
  machineCodeSize
  	- the size of machineCode in bytes
  
  maxSize
  	- the maximum size of machine code that the current instruction will generate, in bytes
  
  objectMemory
  	- the memory manager for the system; simulation only
  
  opcode
  	- the opcode for the receiver which defines which abstract opcode it represents; see CogRTLOpcodes class>>initialize and CogAbstractInstruction subclass initialize methods
  
  operands
  	- the array containing any operands the instruction may have; the opcode defines implicitly how many operands are consdered!

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.
+ 	 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!
- 	"Assign the abstract registers with the identities/indices of the relevant concrete registers."
- 	self subclassResponsibility!

Item was added:
+ ----- Method: CogAbstractInstruction class>>printFormatForOpcodeName: (in category 'debug printing') -----
+ printFormatForOpcodeName: opcodeName
+ 	"Answer a sequence of $r, $f or nil for the operands in the opcode, used for printing, where
+ 	 r => integer register, f => floating point register, and nil => numeric or address operand.
+ 	 Subclasses can override to provide a format string for their own private opcodes."
+ 	^#()!

Item was added:
+ ----- Method: CogAbstractInstruction>>nameForFPRegister: (in category 'printing') -----
+ nameForFPRegister: reg "<Integer>"
+ 	"subclasses with special purpose registers may need to override."
+ 	<doNotGenerate>
+ 	^CogAbstractRegisters nameForFPRegister: reg!

Item was changed:
  ----- Method: CogAbstractInstruction>>nameForRegister: (in category 'printing') -----
  nameForRegister: reg "<Integer>"
  	"subclasses with special purpose registers may need to override."
  	<doNotGenerate>
+ 	^CogAbstractRegisters nameForRegister: reg!
- 	^CogRTLOpcodes nameForRegister: reg!

Item was changed:
  ----- Method: CogAbstractInstruction>>printStateOn: (in category 'printing') -----
  printStateOn: aStream
  	| opcodeName orneryOperands format |
  	<doNotGenerate> "Smalltalk-side only"
  	opcode ifNil:
  		[^self].
  	aStream space; nextPut: $(; nextPutAll: (opcodeName := self class nameForOpcode: opcode).
  	orneryOperands := operands isCObjectAccessor
  							ifTrue: [operands object]
  							ifFalse: [operands].
+ 	format := ((CogRTLOpcodes classPool includesKey: opcodeName)
+ 				ifTrue: [CogRTLOpcodes]
+ 				ifFalse: [self class]) printFormatForOpcodeName: opcodeName.
- 	format := [CogRTLOpcodes printFormatForOpcodeName: opcodeName]
- 				on: Error
- 				do: [:ex| ].
  	orneryOperands withIndexDo:
  		[:operand :index|
  		operand ifNotNil:
  			[aStream space.
  			 index >= (orneryOperands identityIndexOf: nil ifAbsent: [orneryOperands size + 1]) ifTrue:
  				[aStream print: index - 1; nextPut: $:].
+ 			 (format notNil and: ['rf' includes: (format at: index ifAbsent: $-)])
+ 				ifTrue: [aStream nextPutAll: ((format at: index) = $r
+ 												ifTrue: [self nameForRegister: operand]
+ 												ifFalse: [self nameForFPRegister: operand])]
- 			 (format notNil and: [(format at: index ifAbsent: nil) = $r])
- 				ifTrue: [aStream nextPutAll: (self nameForRegister: operand)]
  				ifFalse:
  					[aStream print: operand.
  					 (operand isInteger and: [operand > 16 and: [opcode ~= Label]]) ifTrue:
  						[(operand allMask: 16r80000000) ifTrue:
  							[aStream nextPut: $/; print: operand signedIntFromLong].
  						 aStream nextPut: $/.
  						 operand printOn: aStream base: 16]]]].
  	machineCodeSize ifNotNil:
  		[(machineCodeSize between: 1 and: machineCode size) ifTrue:
  			[0 to: machineCodeSize - 1 by: self codeGranularity do:
  				[:i|
  				 aStream space.
  				 (self machineCodeAt: i)
  					ifNil: [aStream nextPut: $.]
  					ifNotNil:
  						[:mc|
  						mc isInteger
  							ifTrue: [mc printOn: aStream base: 16]
  							ifFalse: [mc printOn: aStream]]]]].
  	address ifNotNil:
  		[aStream nextPut: $@.
  		 address printOn: aStream base: 16].
  	aStream nextPut: $)!

Item was added:
+ SharedPool subclass: #CogAbstractRegisters
+ 	instanceVariableNames: ''
+ 	classVariableNames: 'Arg0Reg Arg1Reg ClassReg DPFPReg0 DPFPReg1 DPFPReg10 DPFPReg11 DPFPReg12 DPFPReg13 DPFPReg14 DPFPReg15 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7 DPFPReg8 DPFPReg9 FPReg LinkReg NoReg PCReg RISCTempReg ReceiverResultReg SPReg Scratch0Reg Scratch1Reg Scratch2Reg Scratch3Reg Scratch4Reg Scratch5Reg Scratch6Reg Scratch7Reg SendNumArgsReg TempReg VarBaseReg'
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-JIT'!
+ 
+ !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 added:
+ ----- 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.
+ 
+ 	"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)."
+ 	Scratch0Reg := #undefined.
+ 	Scratch1Reg := #undefined.
+ 	Scratch2Reg := #undefined.
+ 	Scratch3Reg := #undefined.
+ 	Scratch4Reg := #undefined.
+ 	Scratch5Reg := #undefined.
+ 	Scratch6Reg := #undefined.
+ 	Scratch7Reg := #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."
+ 
+ 	"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!

Item was added:
+ ----- Method: CogAbstractRegisters class>>nameForFPRegister: (in category 'debug printing') -----
+ nameForFPRegister: reg "<Integer>"
+ 	^#(DPFPReg0 DPFPReg1 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7
+ 		DPFPReg8 DPFPReg9 DPFPReg10 DPFPReg11 DPFPReg12 DPFPReg13 DPFPReg14 DPFPReg15)
+ 		detect: [:sym| (classPool at: sym) = reg]
+ 		ifNone: ['REG', reg printString, '?']!

Item was added:
+ ----- Method: CogAbstractRegisters class>>nameForRegister: (in category 'debug printing') -----
+ nameForRegister: reg "<Integer>"
+ 	^#(Arg0Reg Arg1Reg ClassReg FPReg ReceiverResultReg SPReg SendNumArgsReg TempReg
+ 		LinkReg RISCTempReg VarBaseReg PCReg
+ 		Scratch0Reg Scratch1Reg Scratch2Reg Scratch3Reg Scratch4Reg Scratch5Reg)
+ 			detect: [:sym| (classPool at: sym) = reg]
+ 			ifNone: ['REG', reg printString, '?']!

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."
  
  	"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."
  
+ 	super initializeAbstractRegisters.
+ 
  	TempReg				:= EAX.
  	ClassReg				:= ECX.
  	ReceiverResultReg		:= EDX.
  	SendNumArgsReg		:= EBX.
  	SPReg					:= ESP.
  	FPReg					:= EBP.
  	Arg0Reg				:= ESI.
  	Arg1Reg				:= EDI.
  
+ 	DPFPReg0				:= XMM0L.
+ 	DPFPReg1				:= XMM1L.
+ 	DPFPReg2				:= XMM2L.
+ 	DPFPReg3				:= XMM3L.
+ 	DPFPReg4				:= XMM4L.
+ 	DPFPReg5				:= XMM5L.
+ 	DPFPReg6				:= XMM6L.
+ 	DPFPReg7				:= XMM7L!
- 	DPFPReg0				:= XMM0L / 2.
- 	DPFPReg1				:= XMM1L / 2.
- 	DPFPReg2				:= XMM2L / 2.
- 	DPFPReg3				:= XMM3L / 2.
- 	DPFPReg4				:= XMM4L / 2.
- 	DPFPReg5				:= XMM5L / 2.
- 	DPFPReg6				:= XMM6L / 2.
- 	DPFPReg7				:= XMM7L / 2!

Item was changed:
  ----- Method: CogInLineLiteralsX64Compiler 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.
+ 	RISCTempReg := R8!
- 	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."
- 
- 	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"
- 	RISCTempReg			:= R8.
- 	Scratch0Reg			:= R10.
- 	Scratch1Reg			:= R11.
- 	Scratch2Reg			:= R12.
- 	Scratch3Reg			:= R13.
- 	Scratch4Reg			:= R14.
- 	Scratch5Reg			:= R15.
- 
- 	DPFPReg0				:= XMM0L / 2.
- 	DPFPReg1				:= XMM1L / 2.
- 	DPFPReg2				:= XMM2L / 2.
- 	DPFPReg3				:= XMM3L / 2.
- 	DPFPReg4				:= XMM4L / 2.
- 	DPFPReg5				:= XMM5L / 2.
- 	DPFPReg6				:= XMM6L / 2.
- 	DPFPReg7				:= XMM7L / 2!

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.
+ 
  	ReceiverResultReg		:= S0.
  	Arg0Reg				:= S1.
  	Arg1Reg				:= S2.
  	ClassReg				:= S3.
  	SendNumArgsReg		:= S4.
  	TempReg				:= S5.
  	VarBaseReg			:= S6. "Must be callee saved"
  	SPReg					:= SP.
  	FPReg					:= FP.
  	RISCTempReg			:= AT.
  	LinkReg					:= RA!

Item was added:
+ ----- Method: CogMIPSELCompiler class>>printFormatForOpcodeName: (in category 'debug printing') -----
+ printFormatForOpcodeName: opcodeName
+ 	"Answer a sequence of $r, $f or nil for the operands in the opcode, used for printing, where
+ 	 r => integer register, f => floating point register, and nil => numeric or address operand.
+ 	 Subclasses can override to provide a format string for their own private opcodes."
+ 	^(opcodeName startsWith: 'Br') ifTrue: [' rr'] ifFalse: [#()]!

Item was changed:
  CogClass subclass: #CogObjectRepresentation
  	instanceVariableNames: 'cogit methodZone objectMemory coInterpreter ceStoreCheckTrampoline'
  	classVariableNames: ''
+ 	poolDictionaries: 'CogAbstractRegisters CogCompilationConstants CogMethodConstants CogRTLOpcodes VMBasicConstants VMObjectIndices VMSqueakClassIndices VMStackFrameOffsets'
- 	poolDictionaries: 'CogCompilationConstants CogMethodConstants CogRTLOpcodes VMBasicConstants VMObjectIndices VMSqueakClassIndices VMStackFrameOffsets'
  	category: 'VMMaker-JIT'!
  
  !CogObjectRepresentation commentStamp: '<historical>' prior: 0!
  I am an abstract superclass for object representations whose job it is to generate abstract instructions for accessing objects.  It is hoped that this level of indirection between the Cogit code generator and object access makes it easier to adapt the code generator to different garbage collectors, object representations and languages.!

Item was changed:
  ----- Method: CogOutOfLineLiteralsX64Compiler 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.
+ 	Scratch6Reg := R8!
- 	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."
- 
- 	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"
- 	"No need for a RISCTempReg because out-of-line literal loads imply no need for a special MoveCwR"
- 	"RISCTempReg			:= R8."
- 	Scratch0Reg			:= R10.
- 	Scratch1Reg			:= R11.
- 	Scratch2Reg			:= R12.
- 	Scratch3Reg			:= R13.
- 	Scratch4Reg			:= R14.
- 	Scratch5Reg			:= R15.
- 	Scratch6Reg			:= R8.
- 
- 	DPFPReg0				:= XMM0L / 2.
- 	DPFPReg1				:= XMM1L / 2.
- 	DPFPReg2				:= XMM2L / 2.
- 	DPFPReg3				:= XMM3L / 2.
- 	DPFPReg4				:= XMM4L / 2.
- 	DPFPReg5				:= XMM5L / 2.
- 	DPFPReg6				:= XMM6L / 2.
- 	DPFPReg7				:= XMM7L / 2!

Item was changed:
  SharedPool subclass: #CogRTLOpcodes
  	instanceVariableNames: ''
+ 	classVariableNames: 'AddCqR AddCwR AddRR AddRdRd AlignmentNops AndCqR AndCqRR AndCwR AndRR ArithmeticShiftRightCqR ArithmeticShiftRightRR Call CallFull CmpC32R CmpCqR CmpCwR CmpRR CmpRdRd ConvertRRd DivRdRd 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 LoadEffectiveAddressXowrR LogicalShiftLeftCqR LogicalShiftLeftRR LogicalShiftRightCqR LogicalShiftRightRR MoveAbR MoveAwR MoveC32R MoveC64R MoveCqR MoveCwR MoveM16rR MoveM32rR MoveM64rRd MoveMbrR MoveMwrR MoveRAb MoveRAw MoveRM16r MoveRM32r MoveRMbr MoveRMwr MoveRR MoveRRd MoveRX16rR MoveRX32rR MoveRXbrR MoveRXowr MoveRXwrR MoveRdM64r MoveRdR MoveRdRd MoveX16rRR MoveX32rRR MoveXbrRR MoveXowrR MoveXwrRR MulRdRd NegateR Nop OrCqR OrCwR OrRR PopR PrefetchAw PushCq PushCw PushR RetN RotateLeftCqR RotateRightCqR SqrtRd Stop SubCqR SubCwR SubRR SubRdRd TstCqR XorCqR XorCwR XorRR'
- 	classVariableNames: 'AddCqR AddCwR AddRR AddRdRd AlignmentNops AndCqR AndCqRR AndCwR AndRR Arg0Reg Arg1Reg ArithmeticShiftRightCqR ArithmeticShiftRightRR Call CallFull ClassReg CmpC32R CmpCqR CmpCwR CmpRR CmpRdRd ConvertRRd DPFPReg0 DPFPReg1 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7 DivRdRd FPReg 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 LinkReg Literal LoadEffectiveAddressMwrR LoadEffectiveAddressXowrR LogicalShiftLeftCqR LogicalShiftLeftRR LogicalShiftRightCqR LogicalShiftRightRR MoveAbR MoveAwR MoveC32R MoveC64R MoveCqR MoveCwR MoveM16rR MoveM32rR MoveM64rRd MoveMbrR MoveMwrR MoveRAb MoveRAw MoveRM16r MoveRM32r MoveRMbr MoveRMwr MoveRR MoveRRd MoveRX16rR MoveRX32rR MoveRXbrR MoveRXowr MoveRXwrR MoveRdM64r MoveRdR MoveRdRd MoveX16rRR MoveX32rRR MoveXbrRR MoveXowrR MoveXwrRR MulRdRd NegateR NoReg Nop OrCqR OrCwR OrRR PCReg PopR PrefetchAw PushCq PushCw PushR RISCTempReg ReceiverResultReg RetN RotateLeftCqR RotateRightCqR SPReg Scratch0Reg Scratch1Reg Scratch2Reg Scratch3Reg Scratch4Reg Scratch5Reg Scratch6Reg Scratch7Reg SendNumArgsReg SqrtRd Stop SubCqR SubCwR SubRR SubRdRd TempReg TstCqR VarBaseReg XorCqR XorCwR XorRR'
  	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.!
- !CogRTLOpcodes commentStamp: '<historical>' prior: 0!
- I am a pool for the Register-Transfer-Language to which Cog compiles.  I define unique integer values for all RTL opcodes and abstract registers.  See CogAbstractInstruction for instances of instructions with the opcodes that I define.!

Item was changed:
  ----- Method: CogRTLOpcodes class>>initialize (in category 'class initialization') -----
  initialize
  	"Abstract opcodes are a compound of a one word operation specifier and zero or more operand type specifiers.
  	 The assembler is in Cogit protocol abstract instructions and uses `at&t' syntax, assigning to the register on the
  	 right. e.g. MoveRR is the Move opcode with two register operand specifiers and defines a move register to
  	 register instruction from operand 0 to operand 1.  The word and register size is assumed to be either 32-bits
  	 on a 32-bit architecture or 64-bits on a 64-bit architecture.  The abstract machine is mostly a 2 address machine
  	 with the odd three address instruction added to better exploit RISCs.
  			(self initialize)
  	The operand specifiers are
  		R		- general purpose register
  		Rd		- double-precision floating-point register
  		Cq		- a `quick' constant that can be encoded in the minimum space possible.
  		Cw		- a constant with word size where word is the default operand size for the Smalltalk VM, 32-bits
  				  for a 32-bit VM, 64-bits for a 64-bit VM.  The generated constant must occupy the default number
  				  of bits.  This allows e.g. a garbage collector to update the value without invalidating the code.
  		C32	- a constant with 32 bit size.  The generated constant must occupy 32 bits.
  		C64	- a constant with 64 bit size.  The generated constant must occupy 64 bits.
  		Aw		- memory word at an absolute address
  		Ab		- memory byte at an absolute address
  		Mwr	- memory word whose address is at a constant offset from an address in a register
  		Mbr		- memory byte whose address is at a constant offset from an address in a register (zero-extended on read)
  		M16r	- memory 16-bit halfword whose address is at a constant offset from an address in a register
  		M32r	- memory 32-bit halfword whose address is at a constant offset from an address in a register
  		M64r	- memory 64-bit doubleword whose address is at a constant offset from an address in a register
+ 		Xbr		- memory word whose address is r * byte size away from an address in a register
+ 		X16r	- memory word whose address is r * (2 bytes size) away from an address in a register
+ 		X32r	- memory word whose address is r * (4 bytes size) away from an address in a register
+ 		Xwr		- memory word whose address is r * word size away from an address in a register
+ 		Xowr	- memory word whose address is o + (r * word size) away from an address in a register (scaled indexed)
- 		XbrR	- memory word whose address is r * byte size away from an address in a register
- 		X16rR	- memory word whose address is r * (2 bytes size) away from an address in a register
- 		X32rR	- memory word whose address is r * (4 bytes size) away from an address in a register
- 		XwrR	- memory word whose address is r * word size away from an address in a register
- 		XowrR	- memory word whose address is (r * word size) + o away from an address in a register (scaled indexed)
  
  	An alternative would be to decouple opcodes from operands, e.g.
  		Move := 1. Add := 2. Sub := 3...
  		RegisterOperand := 1. ConstantQuickOperand := 2. ConstantWordOperand := 3...
  	But not all combinations make sense and even fewer are used so we stick with the simple compound approach.
  
  	The assumption is that comparison and arithmetic instructions set condition codes and that move instructions
  	leave the condition codes unaffected.  In particular LoadEffectiveAddressMwrR does not set condition codes
  	although it can be used to do arithmetic.  On processors such as MIPS this distinction is invalid; there are no
  	condition codes.  So the backend is allowed to collapse operation, branch pairs to internal instruciton definitions
  	(see sender and implementors of noteFollowingConditionalBranch:). 
  
  	Not all of the definitions in opcodeDefinitions below are implemented.  In particular we do not implement the
  	XowrR scaled index addressing mode since it requires 4 operands.
  
  	Not all instructions make sense on all architectures.  MoveRRd and MoveRdR aqre meaningful only on 64-bit machines.
  
  	Note that there are no generic division instructions defined, but a processor may define some.
  
  	Branch/Call ranges.  Jump[Cond] can be generated as short as possible.  Call/Jump[Cond]Long must be generated
  	in the same number of bytes irrespective of displacement since their targets may be updated, but they need only
  	span 16Mb, the maximum size of the code zone.  This allows e.g. ARM to use single-word call and jump instructions
  	for most calls and jumps.  CallFull/JumpFull must also be generated in the same number of bytes irrespective of
  	displacement for the same reason, but they must be able to span the full (32-bit or 64-bit) address space because
  	they are used to call code in the C runtime, which may be distant from the code zone.  CallFull/JumpFull are allowed
  	to use the cResultRegister as a scratch if required (e.g. on x64 where there is no direct 64-bit call or jump).
  
  	Byte reads.  If the concrete compiler class answers true to byteReadsZeroExtend then byte reads must zero-extend
  	the byte read into the destination register.  If not, the other bits of the register should be left undisturbed and the
  	Cogit will add an instruction to zero the register as required.  Under no circumstances should byte reads sign-extend.
  
  	16-bit (and on 64-bits, 32-bit) reads.  These /are/ expected to always zero-extend."
  
  	| opcodeNames refs |
- 	"A small fixed set of abstract register names are defined and used in code
- 	 generation for Smalltalk code, which executes on stack pages in the stack zone."
- 
- 	"NoReg encodes no register."
- 	NoReg := -1.
- 
- 	"The core set of abstract registers that define the Cogits model of Smalltalk code.
- 	 These are given concrete values by the currently in-use back end; see implementors
- 	 of initializeAbstractRegisters."
- 	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"
- 	TempReg			:= #undefined.
- 	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.
- 
- 	"A small fixed set of abstract scratch registers for register-rich machines (ARM can use 1, x64 can use 6 or 7)."
- 	Scratch0Reg := #undefined.
- 	Scratch1Reg := #undefined.
- 	Scratch2Reg := #undefined.
- 	Scratch3Reg := #undefined.
- 	Scratch4Reg := #undefined.
- 	Scratch5Reg := #undefined.
- 	Scratch6Reg := #undefined.
- 	Scratch7Reg := #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."
- 
- 	"Floating-point registers"
- 	DPFPReg0 := #undefined.
- 	DPFPReg1 := #undefined.
- 	DPFPReg2 := #undefined.
- 	DPFPReg3 := #undefined.
- 	DPFPReg4 := #undefined.
- 	DPFPReg5 := #undefined.
- 	DPFPReg6 := #undefined.
- 	DPFPReg7 := #undefined.
- 
  	opcodeNames := #("Noops & Pseudo Ops"
  						Label
  						Literal			"a word-sized literal"
  						AlignmentNops
  						Fill32			"output four byte's worth of bytes with operand 0"
  						Nop
  
  						"Control"
  						Call					"call within the code zone"
  						CallFull				"call anywhere within the full address space"
  						RetN
  						JumpR				"Not a regular jump, i.e. not pc dependent."
  						Stop				"Halt the processor"
  
  						"N.B.  Jumps are contiguous.  Long and Full jumps are contigiuous within them.  See FirstJump et al below"
  						JumpFull			"Jump anywhere within the address space"
  						JumpLong			"Jump anywhere within the 16mb code zone."
  						JumpLongZero			"a.k.a. JumpLongEqual"
  						JumpLongNonZero		"a.k.a. JumpLongNotEqual"
  						Jump				"short jumps; can be encoded in as few bytes as possible; will not be disturbed by GC or relocation."
  						JumpZero				"a.k.a. JumpEqual"
  						JumpNonZero			"a.k.a. JumpNotEqual"
  						JumpNegative
  						JumpNonNegative
  						JumpOverflow
  						JumpNoOverflow
  						JumpCarry
  						JumpNoCarry
  						JumpLess			"signed"
  						JumpGreaterOrEqual
  						JumpGreater
  						JumpLessOrEqual
  						JumpBelow			"unsigned"
  						JumpAboveOrEqual
  						JumpAbove
  						JumpBelowOrEqual
  
  						JumpFPEqual
  						JumpFPNotEqual
  						JumpFPLess
  						JumpFPLessOrEqual
  						JumpFPGreater
  						JumpFPGreaterOrEqual
  						JumpFPOrdered
  						JumpFPUnordered
  
  						"Data Movement; destination is always last operand"
  						MoveRR
  						MoveAwR
  						MoveRAw
  						MoveAbR
  						MoveRAb
  						MoveMwrR MoveRMwr MoveXwrRR MoveRXwrR MoveXowrR MoveRXowr
  						MoveM16rR MoveRM16r MoveX16rRR MoveRX16rR
  						MoveM32rR MoveRM32r MoveX32rRR MoveRX32rR
  						MoveMbrR MoveRMbr MoveXbrRR MoveRXbrR
  						MoveCqR MoveCwR MoveC32R MoveC64R
  						MoveRRd MoveRdR MoveRdRd MoveM64rRd MoveRdM64r
  						PopR PushR PushCq PushCw
  						PrefetchAw
  
  						"Arithmetic; destination is always last operand except Cmp; CmpXR is SubRX with no update of result"
  						LoadEffectiveAddressMwrR LoadEffectiveAddressXowrR "Variants of add/multiply"
  						NegateR "2's complement negation"
  						ArithmeticShiftRightCqR ArithmeticShiftRightRR
  						LogicalShiftRightCqR LogicalShiftRightRR
  						LogicalShiftLeftCqR LogicalShiftLeftRR
  						RotateLeftCqR RotateRightCqR
  
  						CmpRR AddRR SubRR AndRR OrRR XorRR
  						CmpCqR AddCqR SubCqR AndCqR OrCqR TstCqR XorCqR
  						CmpCwR CmpC32R AddCwR SubCwR AndCwR OrCwR XorCwR
  
  						AndCqRR "Three address ops for RISCs; feel free to add and extend"
  
  						CmpRdRd AddRdRd SubRdRd MulRdRd DivRdRd SqrtRd
  
  						"Conversion"
  						ConvertRRd
  
  						LastRTLCode).
  
  	"Magic auto declaration. Add to the classPool any new variables and nuke any obsolete ones, and assign values"
  	"Find the variables directly referenced by this method"
  	refs := (thisContext method literals select: [:l| l isVariableBinding and: [classPool includesKey: l key]]) collect:
  				[:ea| ea key].
  	"Move to Undeclared any opcodes in classPool not in opcodes or this method."
  	(classPool keys reject: [:k| (opcodeNames includes: k) or: [refs includes: k]]) do:
  		[:k|
  		Undeclared declare: k from: classPool].
  	"Declare as class variables and number elements of opcodeArray above"
  	opcodeNames withIndexDo:
  		[:classVarName :value|
  		self classPool
  			declare: classVarName from: Undeclared;
  			at: classVarName put: value].
  
  	"For CogAbstractInstruction>>isJump etc..."
  	FirstJump := JumpFull.
  	LastJump := JumpFPUnordered.
  	FirstShortJump := Jump.
  
  	"And now initialize the backends; they add their own opcodes and hence these must be reinitialized."
  	(Smalltalk classNamed: #CogAbstractInstruction) ifNotNil:
  		[:cogAbstractInstruction| cogAbstractInstruction allSubclasses do: [:sc| sc initialize]]!

Item was changed:
  ----- Method: CogRTLOpcodes class>>nameForOpcode: (in category 'debug printing') -----
  nameForOpcode: opcode "<Integer>"
+ 	opcode < LastRTLCode ifTrue:
+ 		[classPool associations do:
+ 			[:assoc| | opcodeName |
+ 			 assoc value = opcode ifTrue:
+ 				[(((opcodeName := assoc key) beginsWith: 'First')
+ 				   or: [(opcodeName beginsWith: 'Last')]) ifFalse:
+ 					[^opcodeName]]]].
+ 	^nil!
- 	^opcode < LastRTLCode ifTrue:
- 		[(classPool keyAtValue: opcode ifAbsent: []) ifNotNil:
- 			[:opcodeName|
- 			((opcodeName beginsWith: 'First')
- 			 or: [opcodeName beginsWith: 'Last'])
- 				ifTrue: [#(JumpFull JumpLong JumpBelowOrEqual Jump) detect: [:k| (classPool at: k) = opcode]]
- 				ifFalse: [opcodeName]]]!

Item was removed:
- ----- Method: CogRTLOpcodes class>>nameForRegister: (in category 'debug printing') -----
- nameForRegister: reg "<Integer>"
- 	^#(Arg0Reg Arg1Reg ClassReg FPReg ReceiverResultReg SPReg SendNumArgsReg TempReg
- 		DPFPReg0 DPFPReg1 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7
- 		LinkReg RISCTempReg VarBaseReg PCReg
- 		Scratch0Reg Scratch1Reg Scratch2Reg Scratch3Reg Scratch4Reg Scratch5Reg)
- 			detect: [:sym| (classPool at: sym) = reg]
- 			ifNone: ['REG', reg printString, '?']!

Item was changed:
  ----- Method: CogRTLOpcodes class>>printFormatForOpcodeName: (in category 'debug printing') -----
  printFormatForOpcodeName: opcodeName
+ 	"Answer a sequence of $r, $f or nil for the operands in the opcode, used for printing, where
+ 	 r => integer register, f => floating point register, and nil => numeric or address operand."
+ 	| printFormat operands |
+ 	printFormat := OrderedCollection new.
+ 	operands := opcodeName.
+ 	[(#(	('Ab' nil) ('Aw' nil)
+ 		('Cw' nil) ('Cq' nil) ('C32' nil)
+ 		(Fill32 nil)
+ 		(Label nil) (Literal nil)
+ 		('Mb' nil) ('Mw' nil) ('M16' nil) ('M32' nil) ('M64' nil)
+ 		('Nops' nil)
+ 		('R' $r) ('Rd' $f)
+ 		('Xbr' $r) ('Xwr' $r) ('X16r' $r) ('X32r' $r) ('X64r' $r) ('X' $r) ('ow' nil)
+ 		('Greater' exit) ('Xor' exit) ('r' $r))
+ 				detect: [:pair| operands endsWith: pair first]
+ 				ifNone: [])
+ 			ifNil: [false]
+ 			ifNotNil:
+ 				[:match|
+ 				match last ~~ #exit
+ 				and: [operands := operands allButLast: match first size.
+ 					 printFormat addFirst: match last.
+ 					 true]]]
+ 		whileTrue.
+ 	(printFormat isEmpty and: [(operands beginsWith: 'Jump') or: [operands beginsWith: 'Call']]) ifTrue:
+ 		[printFormat addFirst: nil].
+ 	^printFormat
- 	"Answer a sequence of $r or nil for the operands in the opcode, used for printing."
- 	| format operands size |
- 	format := OrderedCollection new.
- 	size := (operands := opcodeName) size.
- 	(operands startsWith: 'Br') ifTrue: [^' rr'].
- 	[#('XwrR' 'X16rR' 'XbrR' 'RR' 'RdR' 'RRd' 'RdRd') do:
- 		[:regRegFmt|
- 		(operands endsWith: regRegFmt) ifTrue:
- 			[format addLast: $r; addLast: $r.
- 			 operands := operands allButLast: regRegFmt size]].
- 	  #('Mwr' 'M16r' 'Mbr' 'M64r') do:
- 		[:constRegFmt|
- 		(operands endsWith: constRegFmt) ifTrue:
- 			[format addLast: $r; addLast: nil.
- 			 operands := operands allButLast: constRegFmt size]].
- 	  #('Cq' 'Cw' 'C32' 'C64' 'Aw' 'Ab') do:
- 		[:constFmt|
- 		(operands endsWith: constFmt) ifTrue:
- 			[format addLast: nil.
- 			 operands := operands allButLast: constFmt size]].
- 	 #('R' 'Rd') do:
- 		[:regFmt|
- 		(operands endsWith: regFmt) ifTrue:
- 			[format addLast: $r.
- 			 operands := operands allButLast: regFmt size]].
- 	 operands size < size]
- 		whileTrue: [size := operands size].
- 	^format reverse
  	
+ 	"classPool keys sort collect: [:k| { k. (self printFormatForOpcodeName: k) asArray}]"!
- 	"classPool keys collect: [:k| { k. (self printFormatForOpcodeName: k) asArray}]"!

Item was changed:
  VMStructType subclass: #CogSimStackEntry
  	instanceVariableNames: 'cogit objectRepresentation type spilled annotateUse register offset constant bcptr'
  	classVariableNames: ''
+ 	poolDictionaries: 'CogAbstractRegisters CogCompilationConstants CogRTLOpcodes'
- 	poolDictionaries: 'CogCompilationConstants CogRTLOpcodes'
  	category: 'VMMaker-JIT'!

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
+ 
+ 	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."
+ 
+ 	super initializeAbstractRegisters.
+ 
+ 	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"
+ 	"R8 is either RISCTempReg or Scratch6Reg depending on subclass."
+ 	Scratch0Reg			:= R10.
+ 	Scratch1Reg			:= R11.
+ 	Scratch2Reg			:= R12.
+ 	Scratch3Reg			:= R13.
+ 	Scratch4Reg			:= R14.
+ 	Scratch5Reg			:= R15.
+ 
+ 	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!
- 	self ~~ CogX64Compiler ifTrue:
- 		[self subclassResponsibility]!

Item was added:
+ ----- Method: CogX64Compiler>>nameForFPRegister: (in category 'printing') -----
+ nameForFPRegister: reg "<Integer>"
+ 	<doNotGenerate>
+ 	(reg between: 0 and: 15) ifTrue:
+ 		[^#(XMM0L XMM1L XMM2L XMM3L XMM4L XMM5L XMM6L XMM7L XMM8L XMM9L XMM10L XMM11L XMM12L XMM13L XMM14L XMM15L) at: reg + 1].
+ 	^super nameForFPRegister: reg!

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

Item was changed:
  ----- Method: Cogit class>>cog:selector:options: (in category 'in-image compilation') -----
  cog: aCompiledMethod selector: aSelector options: optionsDictionaryOrArray
  	"StackToRegisterMappingCogit cog: (Integer >> #benchFib) selector: #benchFib options: #(COGMTVM false)"
+ 	| initOptions coInterpreter cogit |
+ 	initOptions := self asOptionsDictionary: optionsDictionaryOrArray.
+ 	CoInterpreter initializeWithOptions: initOptions.
+ 	CoInterpreter objectMemoryClass initializeWithOptions: initOptions.
+ 	self initializeWithOptions: initOptions.
- 	| coInterpreter cogit |
- 	self initializeWithOptions: (self asOptionsDictionary: optionsDictionaryOrArray).
- 	CoInterpreter initializeWithOptions: initializationOptions.
- 	CoInterpreter objectMemoryClass initializeWithOptions: initializationOptions.
  	coInterpreter := CurrentImageCoInterpreterFacade forCogit: (cogit := self new).
  	[cogit
  		setInterpreter: coInterpreter;
  		singleStep: true;
  		initializeCodeZoneFrom: 1024 upTo: coInterpreter memory size / 2. "leave space for rump C stack"
  	 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].
  	^{ coInterpreter.
  		cogit.
  		cogit cog: (coInterpreter oopForObject: aCompiledMethod) selector: (coInterpreter oopForObject: aSelector) }!

Item was changed:
  VMClass subclass: #OutOfLineLiteralsManager
  	instanceVariableNames: 'cogit objectMemory objectRepresentation firstOpcodeIndex nextLiteralIndex lastDumpedLiteralIndex literals literalsSize savedFirstOpcodeIndex savedNextLiteralIndex savedLastDumpedLiteralIndex'
  	classVariableNames: ''
+ 	poolDictionaries: 'CogAbstractRegisters CogCompilationConstants CogRTLOpcodes'
- 	poolDictionaries: 'CogCompilationConstants CogRTLOpcodes'
  	category: 'VMMaker-JIT'!
  
  !OutOfLineLiteralsManager commentStamp: 'eem 6/7/2015 12:10' prior: 0!
  An OutOfLineLiteralsManager manages the dumping of literals for backends that wat to keep literals out-of-line, accessed by pc-relative addressing.
  
  Instance Variables
  	cogit:		<Cogit>!

Item was removed:
- ----- Method: SimpleStackBasedCogit>>compileFallbackToInterpreterPrimitive (in category 'primitive generators') -----
- compileFallbackToInterpreterPrimitive
- 	<inline: false>
- 	^self compileInterpreterPrimitive: (coInterpreter
- 											functionPointerForCompiledMethod: methodObj
- 											primitiveIndex: primitiveIndex)!

Item was added:
+ ----- Method: Spur32BitCoMemoryManager class>>initializeWithOptions: (in category 'class initialization') -----
+ initializeWithOptions: optionsDictionary
+ 	"SpurMemoryManager initializeWithOptions: Dictionary new"
+ 
+ 	optionsDictionary at: #Spur32BitMemoryManager put: true.
+ 	super initializeWithOptions: optionsDictionary!

Item was added:
+ ----- Method: Spur64BitCoMemoryManager class>>initializeWithOptions: (in category 'class initialization') -----
+ initializeWithOptions: optionsDictionary
+ 	"SpurMemoryManager initializeWithOptions: Dictionary new"
+ 
+ 	optionsDictionary at: #Spur64BitMemoryManager put: true.
+ 	super initializeWithOptions: optionsDictionary!

Item was changed:
  ----- Method: VMClass class>>shouldIncludeMethodForSelector: (in category 'translation') -----
  shouldIncludeMethodForSelector: selector
  	"Answer whether a primitive method shoud be translated.  Emit a warning to the transcript if the method doesn't exist."
  	^(self whichClassIncludesSelector: selector)
  		ifNotNil:
  			[:c|
  			 (c >> selector pragmaAt: #option:)
  				ifNotNil:
  					[:pragma|
+ 					 initializationOptions at: pragma arguments first ifAbsent: [false]]
- 					 initializationOptions at: (pragma arguments first) ifAbsent: [false]]
  				ifNil: [true]]
  		ifNil:
  			[Transcript nextPutAll: 'Cannot find implementation of '; nextPutAll: selector; nextPutAll: ' in hierarchy of '; print: self; cr; flush.
  			 false]!



More information about the Vm-dev mailing list