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

commits at source.squeak.org commits at source.squeak.org
Sat Dec 19 03:05:24 UTC 2015


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

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

Name: VMMaker.oscog-eem.1610
Author: eem
Time: 18 December 2015, 7:03:36.871 pm
UUID: 30dfc36f-1c08-4c13-a442-f4aa09bfe11f
Ancestors: VMMaker.oscog-eem.1609

Cogit:
Execute the "abstract registers simply name concrete registers" coup.

I've tested the x86, ARM & x64 code generators for Squeak.  I haven't yet tested Newspeak but suspect it will be fine.  More importantly I haven't tested Sista, and given that Sista makes much more use of registers there could be issues here.  Clément, apologies for any disturbance.

SImulator:
Fix a simulation-time assert failure if printStackCallStackOf: is given a StackInterpreter frame pointer (which are negative).

Add accessors for printSends.

Slang:
Make slang check for cppIf:'s first argument being a string before using isEmpty/notEmpty, for robustness.

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

Item was changed:
  ----- Method: CCodeGenerator>>generateInlineCCodeAsArgument:on:indent: (in category 'C translation') -----
  generateInlineCCodeAsArgument: msgNode on: aStream indent: level
  	"Generate the C code for this message onto the given stream.
  	 There are two forms, self cCode: aString ... and self cCode: aBlock."
  
+ 	(msgNode args first isConstant
+ 	 and: [msgNode args first value isString])
- 	msgNode args first isConstant
  		ifTrue:
  			[(msgNode args first value at: 1 ifAbsent: nil) = $# ifTrue:
  				[aStream cr].
  			aStream nextPutAll: msgNode args first value]
  		ifFalse: [msgNode args first
  					emitCCodeAsArgumentOn: aStream
  					level: level
  					generator: self]!

Item was added:
+ ----- 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.."
+ 
+ 	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 removed:
- ----- Method: CogARMCompiler>>abstractRegisterForConcreteRegister: (in category 'private') -----
- abstractRegisterForConcreteRegister: reg
- 	(self concreteRegister: TempReg) = reg ifTrue: [^TempReg].
- 	(self concreteRegister: ReceiverResultReg) = reg ifTrue: [^ReceiverResultReg].
- 	(self concreteRegister: ClassReg) = reg ifTrue: [^ClassReg].
- 	(self concreteRegister: SendNumArgsReg) = reg ifTrue: [^SendNumArgsReg].
- 	(self concreteRegister: Arg0Reg) = reg ifTrue: [^Arg0Reg].
- 	(self concreteRegister: Arg1Reg) = reg ifTrue: [^Arg1Reg].
- 	(self concreteRegister: FPReg) = reg ifTrue: [^FPReg].
- 	(self concreteRegister: SPReg) = reg ifTrue: [^SPReg].
- 	(self concreteRegister: LinkReg) = reg ifTrue: [^LinkReg].
- 	(self concreteRegister: RISCTempReg) = reg ifTrue: [^RISCTempReg].
- 	(self concreteRegister: PCReg) = reg ifTrue: [^PCReg].
- 	(self concreteRegister: VarBaseReg) = reg ifTrue: [^VarBaseReg].
- 	(self concreteRegister: Scratch0Reg) = reg ifTrue: [^Scratch0Reg].
- 	self error: 'could not find abstract register'.
- 	^0
- 
- 	"({	TempReg. ReceiverResultReg. ClassReg. SendNumArgsReg. Arg0Reg. Arg1Reg.
- 		FPReg. SPReg.
- 		LinkReg. RISCTempReg. PCReg. VarBaseReg.
- 		Scratch0Reg } collect: [:i| self basicNew concreteRegister: i]) sort"
- 
- 	"While the below works fine in Smalltalk it of course doesn't work in C ;)"
- 	
- 	"^reg caseOf: {
- 		[self concreteRegister: TempReg] -> [TempReg].
- 		[self concreteRegister: ReceiverResultReg] -> [ReceiverResultReg].
- 		[self concreteRegister: ClassReg] -> [ClassReg].
- 		[self concreteRegister: SendNumArgsReg] -> [SendNumArgsReg].
- 		[self concreteRegister: Arg0Reg] -> [Arg0Reg].
- 		[self concreteRegister: Arg1Reg] -> [Arg1Reg].
- 		[self concreteRegister: FPReg] -> [FPReg].
- 		[self concreteRegister: SPReg] -> [SPReg] }"!

Item was removed:
- ----- Method: CogARMCompiler>>concreteDPFPRegister: (in category 'encoding') -----
- concreteDPFPRegister: registerIndex
- 	 "Map a possibly abstract double-precision floating-point register into a concrete one.
- 	  Abstract registers (defined in CogAbstractOpcodes) are all negative.  If registerIndex
- 	  is negative assume it is an abstract register."
- 
- 	^registerIndex
- 		caseOf: {
- 			[DPFPReg0]	-> [D0].
- 			[DPFPReg1]	-> [D1].
- 			[DPFPReg2]	-> [D2].
- 			[DPFPReg3]	-> [D3].
- 			[DPFPReg4]	-> [D4].
- 			[DPFPReg5]	-> [D5].
- 			[DPFPReg6]	-> [D6].
- 			[DPFPReg7]	-> [D7] }
- 		otherwise:
- 			[self assert: (registerIndex between: D0 and: D7).
- 			 registerIndex]!

Item was removed:
- ----- Method: CogARMCompiler>>concreteRegister: (in category 'encoding') -----
- concreteRegister: registerIndex
- 	 "Map a possibly abstract register into a concrete one.  Abstract registers
- 	  (defined in CogAbstractOpcodes) are all negative.  If registerIndex is
- 	  negative assume it is an abstract register."
- 	
- 	"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.."
- 	^registerIndex
- 		caseOf: {
- 			[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" }
- 		otherwise:
- 			[self assert: (registerIndex between: R0 and: PC).
- 			 registerIndex]!

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

Item was added:
+ ----- Method: CogAbstractInstruction class>>initializeAbstractRegisters (in category 'class initialization') -----
+ initializeAbstractRegisters
+ 	"Assign the abstract registers with the identities/indices of the relevant concrete registers."
+ 	self subclassResponsibility!

Item was changed:
  ----- Method: CogAbstractInstruction>>abstractRegisterForConcreteRegister: (in category 'private') -----
  abstractRegisterForConcreteRegister: reg
+ 	<inline: true>
+ 	self cCode: [] inSmalltalk: [self assert: reg isInteger].
+ 	^reg!
- 	(self concreteRegister: TempReg) = reg ifTrue: [^TempReg].
- 	(self concreteRegister: ReceiverResultReg) = reg ifTrue: [^ReceiverResultReg].
- 	(self concreteRegister: ClassReg) = reg ifTrue: [^ClassReg].
- 	(self concreteRegister: SendNumArgsReg) = reg ifTrue: [^SendNumArgsReg].
- 	(self concreteRegister: Arg0Reg) = reg ifTrue: [^Arg0Reg].
- 	(self concreteRegister: Arg1Reg) = reg ifTrue: [^Arg1Reg].
- 	(self concreteRegister: FPReg) = reg ifTrue: [^FPReg].
- 	(self concreteRegister: SPReg) = reg ifTrue: [^SPReg].
- 	self error: 'could not find abstract register'.
- 	^0
- 
- 	"While the below works fine in Smalltalk it of course doesn't work in C ;)"
- 	
- 	"^reg caseOf: {
- 		[self concreteRegister: TempReg] -> [TempReg].
- 		[self concreteRegister: ReceiverResultReg] -> [ReceiverResultReg].
- 		[self concreteRegister: ClassReg] -> [ClassReg].
- 		[self concreteRegister: SendNumArgsReg] -> [SendNumArgsReg].
- 		[self concreteRegister: Arg0Reg] -> [Arg0Reg].
- 		[self concreteRegister: Arg1Reg] -> [Arg1Reg].
- 		[self concreteRegister: FPReg] -> [FPReg].
- 		[self concreteRegister: SPReg] -> [SPReg] }"!

Item was added:
+ ----- Method: CogAbstractInstruction>>concreteDPFPRegister: (in category 'encoding') -----
+ concreteDPFPRegister: reg
+ 	<inline: true>
+ 	self cCode: [] inSmalltalk: [self assert: reg isInteger].
+ 	^reg!

Item was added:
+ ----- Method: CogAbstractInstruction>>concreteRegister: (in category 'private') -----
+ concreteRegister: reg
+ 	<inline: true>
+ 	self cCode: [] inSmalltalk: [self assert: reg isInteger].
+ 	^reg!

Item was changed:
  ----- Method: CogAbstractInstruction>>genMarshallNArgs:arg:arg:arg:arg: (in category 'abi') -----
  genMarshallNArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3
+ 	"Generate the code to pass up to four arguments in a C run-time call.  Hack: each argument is
+ 	 either a negative number, which encodes a constant, or a non-negative number, that of a register.
- 	"Generate the code to pass up to four arguments in a C run-time call.  Hack: each argument is either a
- 	 negative number, that of an abstract register, or a non-negative number, that of a constant parameter.
  
  	 Run-time calls have no more than four arguments, so chosen so that on ARM, where in its C ABI the
  	 first four integer arguments are passed in registers, all arguments can be passed in registers.  We
+ 	 defer to the back end to generate this code not so much that the back end knows whether it uses
- 	 defer to the back end to generate this code not so much that teh back end knows whether it uses
  	 the stack or registers to pass arguments (it does, but...). In fact we defer for an extremely evil reason.
  	 Doing so allows the x64 (where up to 6 args are passed) to assign the register arguments in an order
+ 	 that allows some of the argument registers to be used for specific abstract  registers, specifically
+ 	 ReceiverResultReg and ClassReg.  This is evil, evil, evil, but also it's really nice to keep using the old
+ 	 register assignments the original author has grown accustomed to."
- 	 that allows some of the argument registers to be used for specificabstract  registers, specifically
- 	 ReceiverResultReg and ClassReg.  This is evil, evil, evil, but also its really nice to keep using the old
- 	 register assignments the principal author has grown accustomed to."
  	<inline: true>
  	^self subclassResponsibility!

Item was added:
+ ----- 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."
+ 
+ 	TempReg				:= EAX.
+ 	ClassReg				:= ECX.
+ 	ReceiverResultReg		:= EDX.
+ 	SendNumArgsReg		:= EBX.
+ 	SPReg					:= ESP.
+ 	FPReg					:= EBP.
+ 	Arg0Reg				:= ESI.
+ 	Arg1Reg				:= EDI.
+ 
+ 	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 removed:
- ----- Method: CogIA32Compiler>>concreteDPFPRegister: (in category 'encoding') -----
- concreteDPFPRegister: registerIndex
- 	 "Map a possibly abstract double-precision floating-point register into a concrete one.
- 	  Abstract registers (defined in CogAbstractOpcodes) are all negative.  If registerIndex
- 	  is negative assume it is an abstract register.
- 
- 	[1] IA-32 Intel® Architecture Software Developer's Manual Volume 2A: Instruction Set Reference, A-M"
- 
- 	^registerIndex
- 		caseOf: {
- 			[DPFPReg0]	-> [XMM0L / 2].
- 			[DPFPReg1]	-> [XMM1L / 2].
- 			[DPFPReg2]	-> [XMM2L / 2].
- 			[DPFPReg3]	-> [XMM3L / 2].
- 			[DPFPReg4]	-> [XMM4L / 2].
- 			[DPFPReg5]	-> [XMM5L / 2].
- 			[DPFPReg6]	-> [XMM6L / 2].
- 			[DPFPReg7]	-> [XMM7L / 2] }
- 		otherwise:
- 			[self assert: (registerIndex between: XMM0L and: XMM7L).
- 			 self assert: (registerIndex bitAnd: 1) = 0.
- 			 registerIndex / 2]!

Item was removed:
- ----- Method: CogIA32Compiler>>concreteRegister: (in category 'encoding') -----
- concreteRegister: registerIndex
- 	 "Map a possibly abstract register into a concrete one.  Abstract registers
- 	  (defined in CogAbstractOpcodes) are all negative.  If registerIndex is
- 	 negative assume it is an abstract register.
- 
- 	[1] IA-32 Intel® Architecture Software Developer's Manual Volume 2A: Instruction Set Reference, A-M
- 
- 
- 	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."
- 
- 	^registerIndex
- 		caseOf: {
- 			[TempReg]				-> [EAX].
- 			[ClassReg]				-> [ECX].
- 			[ReceiverResultReg]	-> [EDX].
- 			[SendNumArgsReg]		-> [EBX].
- 			[SPReg]					-> [ESP].
- 			[FPReg]					-> [EBP].
- 			[Arg0Reg]				-> [ESI].
- 			[Arg1Reg]				-> [EDI] }
- 		otherwise:
- 			[self assert: (registerIndex between: EAX and: EDI).
- 			 registerIndex]!

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

Item was removed:
- ----- Method: CogIA32CompilerForTests>>concreteRegister: (in category 'encoding') -----
- concreteRegister: value
- 	^value!

Item was added:
+ ----- 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
+ 
+ 	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 removed:
- ----- Method: CogInLineLiteralsX64Compiler>>concreteRegister: (in category 'encoding') -----
- concreteRegister: registerIndex
- 	 "Map a possibly abstract register into a concrete one.  Abstract registers
- 	  (defined in CogAbstractOpcodes) are all negative.  If registerIndex is
- 	 negative assume it is an abstract register.
- 
- 	[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."
- 
- 	^registerIndex
- 		caseOf: {
- 			[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] }
- 		otherwise:
- 			[self assert: (registerIndex between: RAX and: R15).
- 			 registerIndex]!

Item was added:
+ ----- 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."
+ 	
+ 	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 removed:
- ----- Method: CogMIPSELCompiler>>concreteRegister: (in category 'encoding') -----
- concreteRegister: registerIndex
- 	"Map a possibly abstract register into a concrete one.  Abstract registers
- 	 (defined in CogAbstractOpcodes) are all negative.  If registerIndex is
- 	 negative assume it is an abstract register."
- 	
- 	"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."
- 	
- 	^registerIndex
- 		caseOf: {
- 			[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]. }
- 		otherwise:
- 			[self assert: (registerIndex between: R0 and: R31).
- 			 registerIndex]!

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

Item was added:
+ ----- 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
+ 
+ 	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 removed:
- ----- Method: CogOutOfLineLiteralsX64Compiler>>concreteRegister: (in category 'encoding') -----
- concreteRegister: registerIndex
- 	 "Map a possibly abstract register into a concrete one.  Abstract registers
- 	  (defined in CogAbstractOpcodes) are all negative.  If registerIndex is
- 	 negative assume it is an abstract register.
- 
- 	[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."
- 
- 	^registerIndex
- 		caseOf: {
- 			[TempReg]				-> [RAX].
- 			[ClassReg]				-> [RCX].
- 			[ReceiverResultReg]	-> [RDX].
- 			[SendNumArgsReg]		-> [R8].
- 			[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]			-> [R9].
- 			[Scratch1Reg]			-> [R10].
- 			[Scratch2Reg]			-> [R11].
- 			[Scratch3Reg]			-> [R12].
- 			[Scratch4Reg]			-> [R13].
- 			[Scratch5Reg]			-> [R14].
- 			[Scratch6Reg]			-> [R15] }
- 		otherwise:
- 			[self assert: (registerIndex between: RAX and: R15).
- 			 registerIndex]!

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

Item was added:
+ ----- Method: CogX64Compiler class>>initializeAbstractRegisters (in category 'class initialization') -----
+ initializeAbstractRegisters
+ 	"Assign the abstract registers with the identities/indices of the relevant concrete registers."
+ 	self ~~ CogX64Compiler ifTrue:
+ 		[self subclassResponsibility]!

Item was removed:
- ----- Method: CogX64Compiler>>abstractRegisterForConcreteRegister: (in category 'private') -----
- abstractRegisterForConcreteRegister: reg
- 	(self concreteRegister: TempReg) = reg ifTrue: [^TempReg].
- 	(self concreteRegister: ReceiverResultReg) = reg ifTrue: [^ReceiverResultReg].
- 	(self concreteRegister: ClassReg) = reg ifTrue: [^ClassReg].
- 	(self concreteRegister: SendNumArgsReg) = reg ifTrue: [^SendNumArgsReg].
- 	(self concreteRegister: Arg0Reg) = reg ifTrue: [^Arg0Reg].
- 	(self concreteRegister: Arg1Reg) = reg ifTrue: [^Arg1Reg].
- 	(self concreteRegister: FPReg) = reg ifTrue: [^FPReg].
- 	(self concreteRegister: SPReg) = reg ifTrue: [^SPReg].
- 	(self concreteRegister: RISCTempReg) = reg ifTrue: [^RISCTempReg].
- 	(self concreteRegister: VarBaseReg) = reg ifTrue: [^VarBaseReg].
- 	(self concreteRegister: Scratch0Reg) = reg ifTrue: [^Scratch0Reg].
- 	(self concreteRegister: Scratch1Reg) = reg ifTrue: [^Scratch1Reg].
- 	(self concreteRegister: Scratch2Reg) = reg ifTrue: [^Scratch2Reg].
- 	(self concreteRegister: Scratch3Reg) = reg ifTrue: [^Scratch3Reg].
- 	(self concreteRegister: Scratch4Reg) = reg ifTrue: [^Scratch4Reg].
- 	(self concreteRegister: Scratch5Reg) = reg ifTrue: [^Scratch5Reg].
- 	self error: 'could not find abstract register'.
- 	^0
- 
- 	"({	TempReg. ReceiverResultReg. ClassReg. SendNumArgsReg. Arg0Reg. Arg1Reg.
- 		FPReg. SPReg.
- 		RISCTempReg. VarBaseReg.
- 		Scratch0Reg. Scratch1Reg. Scratch2Reg. Scratch3Reg. Scratch4Reg. Scratch5Reg. } collect: [:i| self basicNew concreteRegister: i]) sort"
- 
- 	"While the below works fine in Smalltalk it of course doesn't work in C ;)"
- 	
- 	"^reg caseOf: {
- 		[self concreteRegister: TempReg] -> [TempReg].
- 		[self concreteRegister: ReceiverResultReg] -> [ReceiverResultReg].
- 		[self concreteRegister: ClassReg] -> [ClassReg].
- 		[self concreteRegister: SendNumArgsReg] -> [SendNumArgsReg].
- 		[self concreteRegister: Arg0Reg] -> [Arg0Reg].
- 		[self concreteRegister: Arg1Reg] -> [Arg1Reg].
- 		[self concreteRegister: FPReg] -> [FPReg].
- 		[self concreteRegister: SPReg] -> [SPReg] }"!

Item was removed:
- ----- Method: CogX64Compiler>>concreteDPFPRegister: (in category 'encoding') -----
- concreteDPFPRegister: registerIndex
- 	 "Map a possibly abstract double-precision floating-point register into a concrete one.
- 	  Abstract registers (defined in CogAbstractOpcodes) are all negative.  If registerIndex
- 	  is negative assume it is an abstract register.
- 
- 	[1] IA-32 Intel® Architecture Software Developer's Manual Volume 2A: Instruction Set Reference, A-M"
- 
- 	^registerIndex
- 		caseOf: {
- 			[DPFPReg0]	-> [XMM0L / 2].
- 			[DPFPReg1]	-> [XMM1L / 2].
- 			[DPFPReg2]	-> [XMM2L / 2].
- 			[DPFPReg3]	-> [XMM3L / 2].
- 			[DPFPReg4]	-> [XMM4L / 2].
- 			[DPFPReg5]	-> [XMM5L / 2].
- 			[DPFPReg6]	-> [XMM6L / 2].
- 			[DPFPReg7]	-> [XMM7L / 2] }
- 		otherwise:
- 			[self assert: (registerIndex between: XMM0L and: XMM15L).
- 			 self assert: (registerIndex bitAnd: 1) = 0.
- 			 registerIndex / 2]!

Item was changed:
  ----- Method: CogX64Compiler>>genMarshallNArgs:arg:arg:arg:arg: (in category 'abi') -----
  genMarshallNArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3
+ 	"Generate the code to pass up to four arguments in a C run-time call.  Hack: each argument is
+ 	 either a negative number, which encodes a constant, or a non-negative number, that of a register.
- 	"Generate the code to pass up to four arguments in a C run-time call.  Hack: each argument is either a
- 	 negative number, that of an abstract register, or a non-negative number, that of a constant parameter.
  
  	 Run-time calls have no more than four arguments, so chosen so that on ARM, where in its C ABI the
  	 first four integer arguments are passed in registers, all arguments can be passed in registers.  We
  	 defer to the back end to generate this code not so much that the back end knows whether it uses
  	 the stack or registers to pass arguments (it does, but...). In fact we defer for an extremely evil reason.
  	 Doing so allows the x64 (where up to 6 args are passed) to assign the register arguments in an order
  	 that allows some of the argument registers to be used for specific abstract  registers, specifically
+ 	 ReceiverResultReg and ClassReg.  This is evil, evil, evil, but also it's really nice to keep using the old
+ 	 register assignments the original author has grown accustomed to.
- 	 ReceiverResultReg and ClassReg.  This is evil, evil, evil, but also its really nice to keep using the old
- 	 register assignments the principal author has grown accustomed to.
  
  	 How can this possibly work?  Look at Cogit class>>runtime for a list of the run-time calls and their
  	 arguments, including which arguments are passed in which registers.  Look at CogX64Compiler's
+ 	 subclass implementations of initializeAbstractregisters.  There are no calls in which ReceiverResultReg
+ 	 (RDX) and/or ClassReg (RCX) are passed along with Arg0Reg and Arg1Reg, and none in which the use of
- 	 subclass implementations of concreteRegister:.  There are no calls in which ReceiverResultReg (RDX)
- 	 and/or ClassReg (RCX) are passed along with Arg0Reg and Arg1Reg, and none in which the use of
  	 either ReceiverResultReg or ClassReg conflict for args 3 & 4.  So if args are assigned in order, the
  	 registers do not get overwritten.  Yes, this is evil, but it's so nice to continue to use RCX & RDX."
  	<inline: true>
  	numArgs = 0 ifTrue: [^self].
+ 	(cogit isTrampolineArgConstant: regOrConst0)
+ 		ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst0) R: RDI]
- 	regOrConst0 >= 0
- 		ifTrue: [cogit MoveCq: regOrConst0 R: RDI]
  		ifFalse:
+ 			[regOrConst0 ~= RDI ifTrue:
- 			[(self concreteRegister: regOrConst0) ~= RDI ifTrue:
  				[cogit MoveR: regOrConst0 R: RDI]].
  	numArgs = 1 ifTrue: [^self].
+ 	(cogit isTrampolineArgConstant: regOrConst1)
+ 		ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst1) R: RSI]
- 	regOrConst1 >= 0
- 		ifTrue: [cogit MoveCq: regOrConst1 R: RSI]
  		ifFalse:
+ 			[regOrConst1 ~= RSI ifTrue:
- 			[(self concreteRegister: regOrConst1) ~= RSI ifTrue:
  				[cogit MoveR: regOrConst1 R: RSI]].
  	numArgs = 2 ifTrue: [^self].
  	self cppIf: ABI == #SysV ifTrue:
+ 		[(cogit isTrampolineArgConstant: regOrConst2)
+ 			ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst2) R: RDX]
- 		[regOrConst2 >= 0
- 			ifTrue: [cogit MoveCq: regOrConst2 R: RDX]
  			ifFalse:
+ 				[regOrConst2 ~= RDX ifTrue:
- 				[(self concreteRegister: regOrConst2) ~= RDX ifTrue:
  					[cogit MoveR: regOrConst2 R: RDX]].
  		 numArgs = 3 ifTrue: [^self].
+ 		 (cogit isTrampolineArgConstant: regOrConst3)
+ 				ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst3) R: RCX]
- 		 regOrConst3 >= 0
- 				ifTrue: [cogit MoveCq: regOrConst3 R: RCX]
  				ifFalse:
+ 					[regOrConst3 ~= RCX ifTrue:
- 					[(self concreteRegister: regOrConst3) ~= RCX ifTrue:
  						[cogit MoveR: regOrConst3 R: RCX]]].
  	self cppIf: ABI == #MSVC ifTrue:
+ 		[(cogit isTrampolineArgConstant: regOrConst2)
+ 			ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst2) R: R8]
- 		[regOrConst2 >= 0
- 			ifTrue: [cogit MoveCq: regOrConst2 R: R8]
  			ifFalse:
+ 				[regOrConst2 ~= R8 ifTrue:
- 				[(self concreteRegister: regOrConst2) ~= R8 ifTrue:
  					[cogit MoveR: regOrConst2 R: R8]].
  		 numArgs = 3 ifTrue: [^self].
+ 		 (cogit isTrampolineArgConstant: regOrConst3)
+ 				ifTrue: [cogit MoveCq: (cogit trampolineArgValue: regOrConst3) R: R9]
- 		 regOrConst3 >= 0
- 				ifTrue: [cogit MoveCq: regOrConst3 R: R9]
  				ifFalse:
+ 					[regOrConst3 ~= R9 ifTrue:
- 					[(self concreteRegister: regOrConst3) ~= R9 ifTrue:
  						[cogit MoveR: regOrConst3 R: R9]]].
  	self assert: numArgs <= 4!

Item was removed:
- ----- Method: CogX64CompilerForTests>>concreteRegister: (in category 'encoding') -----
- concreteRegister: value
- 	^value!

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].
  							[#MIPSEL]	->	[MIPSELSimulator] }.
  	CogCompilerClass := self activeCompilerClass.
+ 	(CogCompilerClass withAllSuperclasses copyUpTo: CogAbstractInstruction) reverseDo:
+ 		[:compilerClass| compilerClass initialize; initializeAbstractRegisters].
- 	(CogCompilerClass withAllSuperclasses copyUpTo: CogAbstractInstruction) do:
- 		[:compilerClass| compilerClass initialize].
  	"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.
  
  	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>>generateSendTrampolines (in category 'initialization') -----
  generateSendTrampolines
  	0 to: NumSendTrampolines - 1 do:
  		[:numArgs|
  		ordinarySendTrampolines
  			at: numArgs
  			put: (self genTrampolineFor: #ceSend:super:to:numArgs:
  					  called: (self trampolineName: 'ceSend' numArgs: numArgs)
  					  arg: ClassReg
+ 					  arg: (self trampolineArgConstant: false)
- 					  arg: 0
  					  arg: ReceiverResultReg
  					  arg: (self numArgsOrSendNumArgsReg: numArgs))].
  
  	"Generate these in the middle so they are within [firstSend, lastSend]."
  	NewspeakVM ifTrue:
  		[self generateNewspeakSendTrampolines].
  	BytecodeSetHasDirectedSuperSend ifTrue:
  		[0 to: NumSendTrampolines - 1 do:
  			[:numArgs|
  			directedSuperSendTrampolines
  				at: numArgs
  				put: (self genTrampolineFor: #ceSend:above:to:numArgs:
  						  called: (self trampolineName: 'ceDirectedSuperSend' numArgs: numArgs)
  						  arg: ClassReg
  						  arg: TempReg
  						  arg: ReceiverResultReg
  						  arg: (self numArgsOrSendNumArgsReg: numArgs))]].
  
  	0 to: NumSendTrampolines - 1 do:
  		[:numArgs|
  		superSendTrampolines
  			at: numArgs
  			put: (self genTrampolineFor: #ceSend:super:to:numArgs:
  					  called: (self trampolineName: 'ceSuperSend' numArgs: numArgs)
  					  arg: ClassReg
+ 					  arg: (self trampolineArgConstant: true)
- 					  arg: 1
  					  arg: ReceiverResultReg
  					  arg: (self numArgsOrSendNumArgsReg: numArgs))].
  	firstSend := ordinarySendTrampolines at: 0.
  	lastSend := superSendTrampolines at: NumSendTrampolines - 1!

Item was added:
+ ----- Method: Cogit>>isTrampolineArgConstant: (in category 'initialization') -----
+ isTrampolineArgConstant: n
+ 	"Test for true and false and 0 to N encoded via trampolineArgConstant:"
+ 	<inline: true>
+ 	^n < NoReg!

Item was changed:
  ----- Method: Cogit>>numArgsOrSendNumArgsReg: (in category 'initialization') -----
  numArgsOrSendNumArgsReg: numArgs
  	"The send trampolines have different versions for different arg counts, with special
  	 cases for 0 through NumSendTrampolines - 2, and a general case for more, passing
  	 the arg count in SendNumArgsReg.  This computes the relevant argument."
  	<inline: true>
+ 	^numArgs <= (NumSendTrampolines - 2)
+ 		ifTrue: [self trampolineArgConstant: numArgs]
+ 		ifFalse: [SendNumArgsReg]!
- 	^numArgs <= (NumSendTrampolines - 2) ifTrue: [numArgs] ifFalse: [SendNumArgsReg]!

Item was changed:
  ----- Method: Cogit>>registerMaskFor: (in category 'register management') -----
  registerMaskFor: reg
+ 	^1 << reg!
- 	"Answer a bit mask identifying the symbolic register.
- 	 Registers are negative numbers."
- 	^1 << (1 - reg)!

Item was changed:
  ----- Method: Cogit>>registerMaskFor:and: (in category 'register management') -----
  registerMaskFor: reg1 and: reg2
+ 	^1 << reg1 bitOr: 1 << reg2!
- 	"Answer a bit mask identifying the symbolic registers.
- 	 Registers are negative numbers."
- 	^1 << (1 - reg1) bitOr: 1 << (1 - reg2)!

Item was changed:
  ----- Method: Cogit>>registerMaskFor:and:and: (in category 'register management') -----
  registerMaskFor: reg1 and: reg2 and: reg3
+ 	^(1 << reg1 bitOr: 1 << reg2) bitOr: 1 << reg3!
- 	"Answer a bit mask identifying the symbolic registers.
- 	 Registers are negative numbers."
- 	^(1 << (1 - reg1) bitOr: 1 << (1 - reg2)) bitOr: 1 << (1 - reg3)!

Item was changed:
  ----- Method: Cogit>>registerMaskFor:and:and:and: (in category 'register management') -----
  registerMaskFor: reg1 and: reg2 and: reg3 and: reg4
+ 	^((1 << reg1 bitOr: 1 << reg2) bitOr: 1 << reg3) bitOr: 1 << reg4!
- 	"Answer a bit mask identifying the symbolic registers.
- 	 Registers are negative numbers."
- 	^((1 << (1 - reg1) bitOr: 1 << (1 - reg2)) bitOr: 1 << (1 - reg3)) bitOr: 1 << (1 - reg4)!

Item was changed:
  ----- Method: Cogit>>registerMaskFor:and:and:and:and: (in category 'register management') -----
  registerMaskFor: reg1 and: reg2 and: reg3 and: reg4 and: reg5
+ 	^(((1 << reg1 bitOr: 1 << reg2) bitOr: 1 << reg3) bitOr: 1 << reg4) bitOr: 1 << reg5!
- 	"Answer a bit mask identifying the symbolic registers.
- 	 Registers are negative numbers."
- 	^(((1 << (1 - reg1) bitOr: 1 << (1 - reg2)) bitOr: 1 << (1 - reg3)) bitOr: 1 << (1 - reg4)) bitOr: 1 << (1 - reg5)!

Item was changed:
  ----- Method: Cogit>>registerMaskFor:and:and:and:and:and: (in category 'register management') -----
  registerMaskFor: reg1 and: reg2 and: reg3 and: reg4 and: reg5 and: reg6
+ 	^((((1 << reg1 bitOr: 1 << reg2) bitOr: 1 << reg3) bitOr: 1 << reg4) bitOr: 1 << reg5) bitOr: 1 << reg6!
- 	"Answer a bit mask identifying the symbolic registers.
- 	 Registers are negative numbers."
- 	^((((1 << (1 - reg1) bitOr: 1 << (1 - reg2)) bitOr: 1 << (1 - reg3)) bitOr: 1 << (1 - reg4)) bitOr: 1 << (1 - reg5)) bitOr: 1 << (1 - reg6)!

Item was changed:
  ----- Method: Cogit>>registerMaskFor:and:and:and:and:and:and: (in category 'register management') -----
  registerMaskFor: reg1 and: reg2 and: reg3 and: reg4 and: reg5 and: reg6 and: reg7
+ 	^(((((1 << reg1 bitOr: 1 << reg2) bitOr: 1 << reg3) bitOr: 1 << reg4) bitOr: 1 << reg5) bitOr: 1 << reg6) bitOr: 1 << reg7!
- 	"Answer a bit mask identifying the symbolic registers.
- 	 Registers are negative numbers."
- 	^(((((1 << (1 - reg1) bitOr: 1 << (1 - reg2)) bitOr: 1 << (1 - reg3)) bitOr: 1 << (1 - reg4)) bitOr: 1 << (1 - reg5)) bitOr: 1 << (1 - reg6)) bitOr: 1 << (1 - reg7)!

Item was changed:
  ----- Method: Cogit>>registerMaskFor:and:and:and:and:and:and:and: (in category 'register management') -----
  registerMaskFor: reg1 and: reg2 and: reg3 and: reg4 and: reg5 and: reg6 and: reg7 and: reg8
+ 	^((((((1 << reg1 bitOr: 1 << reg2) bitOr: 1 << reg3) bitOr: 1 << reg4) bitOr: 1 << reg5) bitOr: 1 << reg6) bitOr: 1 << reg7) bitOr: 1 << reg8!
- 	"Answer a bit mask identifying the symbolic registers.
- 	 Registers are negative numbers."
- 	^((((((1 << (1 - reg1) bitOr: 1 << (1 - reg2)) bitOr: 1 << (1 - reg3)) bitOr: 1 << (1 - reg4)) bitOr: 1 << (1 - reg5)) bitOr: 1 << (1 - reg6)) bitOr: 1 << (1 - reg7)) bitOr: 1 << (1 - reg8)!

Item was changed:
  ----- Method: Cogit>>registerMaskFor:and:and:and:and:and:and:and:and: (in category 'register management') -----
  registerMaskFor: reg1 and: reg2 and: reg3 and: reg4 and: reg5 and: reg6 and: reg7 and: reg8 and: reg9
+ 	^(((((((1 << reg1 bitOr: 1 << reg2) bitOr: 1 << reg3) bitOr: 1 << reg4) bitOr: 1 << reg5) bitOr: 1 << reg6) bitOr: 1 << reg7) bitOr: 1 << reg8) bitOr: 1 << reg9!
- 	"Answer a bit mask identifying the symbolic registers.
- 	 Registers are negative numbers."
- 	^(((((((1 << (1 - reg1) bitOr: 1 << (1 - reg2)) bitOr: 1 << (1 - reg3)) bitOr: 1 << (1 - reg4)) bitOr: 1 << (1 - reg5)) bitOr: 1 << (1 - reg6)) bitOr: 1 << (1 - reg7)) bitOr: 1 << (1 - reg8)) bitOr: 1 << (1 - reg9)!

Item was added:
+ ----- Method: Cogit>>trampolineArgConstant: (in category 'initialization') -----
+ trampolineArgConstant: booleanOrInteger
+ 	"Encode true and false and 0 to N such that they can't be confused for register numbers (including NoReg)
+ 	 and can be tested for by isTrampolineArgConstant: and decoded by trampolineArgValue:"
+ 	<inline: true>
+ 	self cCode: []
+ 		inSmalltalk: [booleanOrInteger isInteger ifFalse: [^self trampolineArgConstant: (booleanOrInteger ifTrue: [1] ifFalse: [0])]].
+ 	self assert: booleanOrInteger >= 0.
+ 	^-2 - booleanOrInteger "0...N => -2...-(N+2)"!

Item was added:
+ ----- Method: Cogit>>trampolineArgValue: (in category 'initialization') -----
+ trampolineArgValue: n
+ 	"Decode true and false and 0 to N to their C equivalents from the encoding by trampolineArgConstant:"
+ 	<inline: true>
+ 	^-2 - n!

Item was changed:
  ----- Method: StackInterpreter>>printStackCallStackOf: (in category 'debug printing') -----
  printStackCallStackOf: aContextOrProcessOrFrame
  	<api>
  	| theFP context |
  	<var: #theFP type: #'char *'>
+ 	(self cCode: [false] "In the stack simulator, frame pointers are negative which upsets addressCouldBeObj:"
+ 		inSmalltalk: [stackPages couldBeFramePointer: aContextOrProcessOrFrame]) ifFalse:
+ 		[(objectMemory addressCouldBeObj: aContextOrProcessOrFrame) ifTrue:
+ 			[((objectMemory isContext: aContextOrProcessOrFrame)
+ 			  and: [self checkIsStillMarriedContext: aContextOrProcessOrFrame currentFP: nil]) ifTrue:
+ 				[^self printStackCallStackOf: (self frameOfMarriedContext: aContextOrProcessOrFrame) asInteger].
+ 			 (self couldBeProcess: aContextOrProcessOrFrame) ifTrue:
+ 				[^self printCallStackOf: (objectMemory
+ 											fetchPointer: SuspendedContextIndex
+ 											ofObject: aContextOrProcessOrFrame)].
+ 			 ^nil]].
- 	(objectMemory addressCouldBeObj: aContextOrProcessOrFrame) ifTrue:
- 		[((objectMemory isContext: aContextOrProcessOrFrame)
- 		  and: [self checkIsStillMarriedContext: aContextOrProcessOrFrame currentFP: nil]) ifTrue:
- 			[^self printStackCallStackOf: (self frameOfMarriedContext: aContextOrProcessOrFrame) asInteger].
- 		 (self couldBeProcess: aContextOrProcessOrFrame) ifTrue:
- 			[^self printCallStackOf: (objectMemory
- 										fetchPointer: SuspendedContextIndex
- 										ofObject: aContextOrProcessOrFrame)].
- 		 ^nil].
  
  	theFP := aContextOrProcessOrFrame asVoidPointer.
  	[context := self shortReversePrintFrameAndCallers: theFP.
  	 ((self isMarriedOrWidowedContext: context)
  	  and:
  		[theFP := self frameOfMarriedContext: context.
  		 self checkIsStillMarriedContext: context currentFP: theFP]) ifFalse:
  			[^nil]] repeat!

Item was added:
+ ----- Method: StackInterpreterSimulator>>printSends (in category 'debug printing') -----
+ printSends
+ 	^printSends!

Item was added:
+ ----- Method: StackInterpreterSimulator>>printSends: (in category 'debug printing') -----
+ printSends: aBoolean
+ 	printSends := aBoolean!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>generateSendTrampolines (in category 'initialization') -----
  generateSendTrampolines
  	"Override to generate code to push the register arg(s) for <= numRegArg arity sends."
  	0 to: NumSendTrampolines - 1 do:
  		[:numArgs|
  		ordinarySendTrampolines
  			at: numArgs
  			put: (self genSendTrampolineFor: #ceSend:super:to:numArgs:
  					  numArgs: numArgs
  					  called: (self trampolineName: 'ceSend' numArgs: numArgs)
  					  arg: ClassReg
+ 					  arg: (self trampolineArgConstant: false)
- 					  arg: 0
  					  arg: ReceiverResultReg
  					  arg: (self numArgsOrSendNumArgsReg: numArgs))].
  
  	"Generate these in the middle so they are within [firstSend, lastSend]."
  	NewspeakVM ifTrue: [self generateNewspeakSendTrampolines].
  	BytecodeSetHasDirectedSuperSend ifTrue:
  		[0 to: NumSendTrampolines - 1 do:
  			[:numArgs|
  			directedSuperSendTrampolines
  				at: numArgs
  				put: (self genSendTrampolineFor: #ceSend:above:to:numArgs:
  						  numArgs: numArgs
  						  called: (self trampolineName: 'ceDirectedSuperSend' numArgs: numArgs)
  						  arg: ClassReg
  						  arg: TempReg
  						  arg: ReceiverResultReg
  						  arg: (self numArgsOrSendNumArgsReg: numArgs))]].
  
  	0 to: NumSendTrampolines - 1 do:
  		[:numArgs|
  		superSendTrampolines
  			at: numArgs
  			put: (self genSendTrampolineFor: #ceSend:super:to:numArgs:
  					  numArgs: numArgs
  					  called: (self trampolineName: 'ceSuperSend' numArgs: numArgs)
  					  arg: ClassReg
+ 					  arg: (self trampolineArgConstant: true)
- 					  arg: 1
  					  arg: ReceiverResultReg
  					  arg: (self numArgsOrSendNumArgsReg: numArgs))].
  	firstSend := ordinarySendTrampolines at: 0.
  	lastSend := superSendTrampolines at: NumSendTrampolines - 1!

Item was changed:
  ----- Method: TSendNode>>isNonNullCCode (in category 'testing') -----
  isNonNullCCode
  	^(#(cCode: cCode:inSmalltalk:) includes: selector)
  	   and: [arguments first isConstant
+ 	   and: [arguments first value isString
+ 	   and: [arguments first value notEmpty]]]!
- 	   and: [arguments first value notEmpty]]!



More information about the Vm-dev mailing list