[Vm-dev] VM Maker: VMMaker.oscog-rmacnak.1533.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Nov 27 22:41:59 UTC 2015


Ryan Macnak uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-rmacnak.1533.mcz

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

Name: VMMaker.oscog-rmacnak.1533
Author: rmacnak
Time: 27 November 2015, 2:07:17.218 pm
UUID: 6f75f364-358a-4762-b934-fefc76c19285
Ancestors: VMMaker.oscog-rmacnak.1532

Move MIPSConstants to VMMaker.

Add CogMIPSELCompilerTests.

Move noteFollowingConditionalBranch: to catch branches created outside of Jump<Cond>:

Fix Br instructions that use slt[u] right, left.

Fix backwards SubRR. Two address instructions are bizarre.

CPIC patching (architecture independent): fix call mistaken for a jump and conditional branch mistaken for a jump.

=============== Diff against VMMaker.oscog-rmacnak.1532 ===============

Item was added:
+ ----- Method: AbstractInstructionTests>>genConditionalBranch:operand: (in category 'generating machine code') -----
+ genConditionalBranch: opcode operand: operandOne
+ 	^self previousInstruction noteFollowingConditionalBranch: (self gen: opcode operand: operandOne)!

Item was added:
+ ----- Method: AbstractInstructionTests>>previousInstruction (in category 'as yet unclassified') -----
+ previousInstruction
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	^opcodes last!

Item was changed:
  ----- Method: AbstractInstructionTests>>runBinaryConditionalJumps: (in category 'running') -----
  runBinaryConditionalJumps: assertPrintBar
  	"self defaultTester runBinaryConditionalJumps: false"
+ 	| mask count reg1 reg2 reg3 reg1Getter reg2Setter reg3Setter |
- 	| mask reg1 reg2 reg3 |
  	mask := (1 << self processor bitsInWord) - 1.
+ 	count := 0.
  	self concreteCompilerClass dataRegistersWithAccessorsDo:
  		[:n :get :set|
+ 		count = 0 ifTrue: [reg1 := n. reg1Getter := get].
+ 		count = 1 ifTrue: [reg2 := n. reg2Setter := set].
+ 		count = 2 ifTrue: [reg3 := n. reg3Setter := set].
+ 		count := count + 1].
+ 	self assert: reg1 ~= nil.
+ 	self assert: reg2 ~= nil.
+ 	self assert: reg3 ~= nil.
- 		n = 0 ifTrue: [reg1 := get].
- 		n = 1 ifTrue: [reg2 := set].
- 		n = 2 ifTrue: [reg3 := set]].
  	#(	(JumpAbove > unsigned)			(JumpBelowOrEqual <= unsigned)
  		(JumpBelow < unsigned)			(JumpAboveOrEqual >= unsigned)
  		(JumpGreater > signed)			(JumpLessOrEqual <= signed)
  		(JumpLess < signed)				(JumpGreaterOrEqual >= signed)
  		(JumpZero = signed)				(JumpNonZero ~= signed)) do:
  		[:triple|
  		[:opName :relation :signednessOrResult| | opcode jumpNotTaken jumpTaken nop memory bogus |
  		self resetGen.
  		opcode := CogRTLOpcodes classPool at: opName.
+ 		self gen: CmpRR operand: reg3 operand: reg2.
+ 		jumpTaken := self genConditionalBranch: opcode operand: 0.
+ 		self gen: MoveCqR operand: 0 operand: reg1.
- 		self gen: CmpRR operand: 2 operand: 1.
- 		jumpTaken := self gen: opcode.
- 		self gen: MoveCqR operand: 0 operand: 0.
  		jumpNotTaken := self gen: Jump.
+ 		jumpTaken jmpTarget: (self gen: MoveCqR operand: 1 operand: reg1).
- 		jumpTaken jmpTarget: (self gen: MoveCqR operand: 1 operand: 0).
  		jumpNotTaken jmpTarget: (nop := self gen: Nop).
  		memory := self generateInstructions.
+ 		"self processor disassembleFrom: 0 to: memory size in: memory on: Transcript."
- 		"self processor disassembleFrom: 0 to: memory size in: memory on: Transcript"
  		bogus := false.
  		self pairs: (-2 to: 2)  do:
  			[:a :b| | taken |
  			self processor
  				reset;
+ 				perform: reg2Setter with: (processor convertIntegerToInternal: a);
+ 				perform: reg3Setter with: (processor convertIntegerToInternal: b).
- 				perform: reg2 with: (processor convertIntegerToInternal: a);
- 				perform: reg3 with: (processor convertIntegerToInternal: b).
  			[self processor singleStepIn: memory.
  			 self processor pc ~= nop address] whileTrue.
+ 			taken := (self processor perform: reg1Getter) = 1.
- 			taken := (self processor perform: reg1) = 1.
  			assertPrintBar
  				ifTrue:
  					[self assert: taken equals: (signednessOrResult == #unsigned
  												ifTrue: [(a bitAnd: mask) perform: relation with: (b bitAnd: mask)]
  												ifFalse: [a perform: relation with: b])]
  				ifFalse:
  					[Transcript
  						nextPutAll: reg2; nextPut: $(; print: a; nextPutAll: ') '; nextPutAll: relation; space;
  						nextPutAll: reg3; nextPut: $(; print: b; nextPutAll: ') = ';
  						print: taken; cr; flush.
  					 taken = (signednessOrResult == #unsigned
  											ifTrue: [(a bitAnd: mask) perform: relation with: (b bitAnd: mask)]
  											ifFalse: [a perform: relation with: b]) ifFalse:
  						[bogus := true]]].
  			 bogus ifTrue:
  				[self processor printRegistersOn: Transcript.
  				 Transcript show: (self processor disassembleInstructionAt: jumpTaken address In: memory); cr]]
  					valueWithArguments: triple]!

Item was changed:
  ----- Method: AbstractInstructionTests>>runBinaryConditionalJumpsViaCmpCqR: (in category 'running') -----
  runBinaryConditionalJumpsViaCmpCqR: assertPrintBar
  	"self defaultTester runBinaryConditionalJumpsViaCmpCqR: false"
+ 	| mask count reg1 reg2 resultRegNum operandRegNum |
- 	| mask reg1 reg2 resultRegNum operandRegNum |
  	mask := (1 << self processor bitsInWord) - 1.
+ 	count := 0.
- 	resultRegNum := 0.
- 	operandRegNum := 1.
  	self concreteCompilerClass dataRegistersWithAccessorsDo:
  		[:n :get :set|
+ 		count = 0 ifTrue: [resultRegNum := n. reg1 := get].
+ 		count = 1 ifTrue: [operandRegNum := n. reg2 := set].
+ 		count := count + 1].
+ 	self assert: resultRegNum ~= nil.
+ 	self assert: operandRegNum ~= nil.
- 		n = resultRegNum ifTrue: [reg1 := get].
- 		n = operandRegNum ifTrue: [reg2 := set]].
  	#(	(JumpAbove > unsigned)			(JumpBelowOrEqual <= unsigned)
  		(JumpBelow < unsigned)			(JumpAboveOrEqual >= unsigned)
  		(JumpGreater > signed)			(JumpLessOrEqual <= signed)
  		(JumpLess < signed)				(JumpGreaterOrEqual >= signed)
  		(JumpZero = signed)				(JumpNonZero ~= signed)) do:
  		[:triple|
  		[:opName :relation :signednessOrResult| | opcode |
  		opcode := CogRTLOpcodes classPool at: opName.
  		(-2 to: 2) do:
  			[:b| | jumpNotTaken jumpTaken nop memory bogus |
  			self resetGen.
  			self gen: CmpCqR operand: b operand: operandRegNum.
+ 			jumpTaken := self genConditionalBranch: opcode operand: 0.
- 			jumpTaken := self gen: opcode.
  			self gen: MoveCqR operand: 0 operand: resultRegNum.
  			jumpNotTaken := self gen: Jump.
  			jumpTaken jmpTarget: (self gen: MoveCqR operand: 1 operand: resultRegNum).
  			jumpNotTaken jmpTarget: (nop := self gen: Nop).
  			memory := self generateInstructions.
  			assertPrintBar ifFalse:
  				[Transcript print: triple; cr.
  				 self disassembleOpcodesIn: memory to: Transcript].
  			bogus := false.
  			(-2 to: 2) do:
  				[:a| | taken expected |
  				self processor
  					reset;
  					perform: reg2 with: (processor convertIntegerToInternal: a).
  				[self processor singleStepIn: memory.
  				 self processor pc ~= nop address] whileTrue.
  				taken := (self processor perform: reg1) = 1.
  				expected := signednessOrResult == #unsigned
  								ifTrue: [(a bitAnd: mask) perform: relation with: (b bitAnd: mask)]
  								ifFalse: [a perform: relation with: b].
  				assertPrintBar
  					ifTrue:
  						[self assert: taken equals: expected]
  					ifFalse:
  						[Transcript
  							nextPutAll: 'CmpCqR '; print: b; space; nextPutAll: reg2; tab; tab;
  							nextPutAll: reg2; nextPut: $(; print: a; nextPut: $); space;
  							nextPutAll: relation; space; print: b; nextPutAll: ' = ';
  							print: taken;  nextPutAll: ' ('; print: expected; nextPut: $).
  						 taken ~= expected ifTrue:
  							[Transcript nextPutAll: ' !!!!'.
  							 bogus := true].
  						 Transcript cr; flush]].
  				bogus ifTrue:
  					[self processor printRegistersOn: Transcript.
  					 Transcript nextPutAll: jumpTaken symbolic; tab; show: (self processor disassembleInstructionAt: jumpTaken address In: memory); cr]]]
  						valueWithArguments: triple]!

Item was changed:
  ----- Method: AbstractInstructionTests>>runBinaryConditionalJumpsViaSubCqR: (in category 'running') -----
  runBinaryConditionalJumpsViaSubCqR: assertPrintBar
  	"self defaultTester runBinaryConditionalJumpsViaSubCqR: false"
+ 	| mask count reg1 reg2 setreg2 resultRegNum operandRegNum |
- 	| mask reg1 reg2 setreg2 resultRegNum operandRegNum |
  	mask := (1 << self processor bitsInWord) - 1.
+ 	count := 0.
- 	resultRegNum := 0.
- 	operandRegNum := 1.
  	self concreteCompilerClass dataRegistersWithAccessorsDo:
  		[:n :get :set|
+ 		count = 0 ifTrue: [resultRegNum := n. reg1 := get].
+ 		count = 1 ifTrue: [operandRegNum := n. reg2 := get. setreg2 := set].
+ 		count := count + 1].
+ 	self assert: resultRegNum ~= nil.
+ 	self assert: operandRegNum ~= nil.
+ 	
- 		n = resultRegNum ifTrue: [reg1 := get].
- 		n = operandRegNum ifTrue: [reg2 := get. setreg2 := set]].
  	#(	(JumpAbove > unsigned)			(JumpBelowOrEqual <= unsigned)
  		(JumpBelow < unsigned)			(JumpAboveOrEqual >= unsigned)
  		(JumpGreater > signed)			(JumpLessOrEqual <= signed)
  		(JumpLess < signed)				(JumpGreaterOrEqual >= signed)
  		(JumpZero = signed)				(JumpNonZero ~= signed)) do:
  		[:triple|
  		[:opName :relation :signednessOrResult| | opcode |
  		opcode := CogRTLOpcodes classPool at: opName.
  		(-2 to: 2) do:
  			[:b| | jumpNotTaken jumpTaken nop memory bogus |
  			self resetGen.
  			self gen: SubCqR operand: b operand: operandRegNum.
+ 			jumpTaken := self genConditionalBranch: opcode operand: 0.
- 			jumpTaken := self gen: opcode.
  			self gen: MoveCqR operand: 0 operand: resultRegNum.
  			jumpNotTaken := self gen: Jump.
  			jumpTaken jmpTarget: (self gen: MoveCqR operand: 1 operand: resultRegNum).
  			jumpNotTaken jmpTarget: (nop := self gen: Nop).
  			memory := self generateInstructions.
  			assertPrintBar ifFalse:
  				[Transcript print: triple; cr.
  				 self disassembleOpcodesIn: memory to: Transcript].
  			bogus := false.
  			(-2 to: 2) do:
  				[:a| | taken result expected |
  				self processor
  					reset;
  					perform: setreg2 with: (self processor convertIntegerToInternal: a).
  				[self processor singleStepIn: memory.
  				 self processor pc ~= nop address] whileTrue.
  				taken := (self processor perform: reg1) = 1.
  				result := signednessOrResult == #unsigned
  							ifTrue: [(a bitAnd: mask) - (b bitAnd: mask)]
  							ifFalse: [a - b].
  				expected := result perform: relation with: 0.
  				assertPrintBar
  					ifTrue:
  						[self assert: (taken = expected
  									  and: [(result bitAnd: mask) = (processor perform: reg2)])]
  					ifFalse:
  						[Transcript
  							nextPutAll: 'SubCqR '; print: b; space; nextPutAll: reg2; tab; tab;
  							print: b; space; nextPutAll: relation; space;
  							nextPutAll: reg2; nextPut: $(; print: a; nextPutAll: ') = ';
  							print: taken;  nextPutAll: ' ('; print: expected; nextPut: $).
  						 taken ~= expected ifTrue:
  							[Transcript nextPutAll: ' !!!!'.
  							 bogus := true].
  						 Transcript cr; flush]].
  				bogus ifTrue:
  					[self processor printRegistersOn: Transcript.
  					 Transcript nextPutAll: jumpTaken symbolic; tab; show: (self processor disassembleInstructionAt: jumpTaken address In: memory); cr]]]
  						valueWithArguments: triple]!

Item was added:
+ ----- Method: CogARMCompiler>>rewriteConditionalJumpLongAt:target: (in category 'inline cacheing') -----
+ rewriteConditionalJumpLongAt: callSiteReturnAddress target: callTargetAddress
+ 	^self rewriteJumpLongAt: callSiteReturnAddress target: callTargetAddress!

Item was added:
+ ----- Method: CogIA32Compiler>>rewriteConditionalJumpLongAt:target: (in category 'inline cacheing') -----
+ rewriteConditionalJumpLongAt: callSiteReturnAddress target: callTargetAddress
+ 	^self rewriteJumpLongAt: callSiteReturnAddress target: callTargetAddress!

Item was added:
+ ----- Method: CogMIPSELCompiler>>canMulRR (in category 'testing') -----
+ canMulRR
+ 	<inline: true>
+ 	^true!

Item was changed:
  ----- Method: CogMIPSELCompiler>>computeMaximumSize (in category 'generate machine code') -----
  computeMaximumSize
  	"Each MIPS instruction has 4 bytes. Many abstract opcodes need more than one
  	 instruction. Instructions that refer to constants and/or literals depend on literals
  	 being stored in-line or out-of-line.
  
  	 N.B.  The ^N forms are to get around the bytecode compiler's long branch
  	 limits which are exceeded when each case jumps around the otherwise."
  
  	opcode
  		caseOf: {
  		[BrEqualRR]						-> [^8].
  		[BrNotEqualRR]					-> [^8].
  		[BrUnsignedLessRR]			-> [^12].
  		[BrUnsignedLessEqualRR]		-> [^12].
  		[BrUnsignedGreaterRR]			-> [^12].
  		[BrUnsignedGreaterEqualRR]	-> [^12].
  		[BrSignedLessRR]				-> [^12].
  		[BrSignedLessEqualRR]			-> [^12].
  		[BrSignedGreaterRR]			-> [^12].
  		[BrSignedGreaterEqualRR]		-> [^12].
  		[BrLongEqualRR]				-> [^16].
  		[BrLongNotEqualRR]				-> [^16].
  		[MulRR]					-> [^4].
  		[DivRR]					-> [^4].
  		[MoveLowR]			-> [^4].
  		[MoveHighR]			-> [^4].
  
  		"Noops & Pseudo Ops"
  		[Label]					-> [^0].
  		[Literal]					-> [^4].
  		[AlignmentNops]		-> [^(operands at: 0) - 4].
  		[Fill16]					-> [^4].
  		[Fill32]					-> [^4].
  		[FillFromWord]			-> [^4].
  		[Nop]					-> [^4].
  		"Control"
  		[Call]					-> [^self literalLoadInstructionBytes + 8].
  		[CallFull]				-> [^self literalLoadInstructionBytes + 8].
  		[JumpR]					-> [^8].
  		[Jump]					-> [^8].
  		[JumpFull]				-> [^self literalLoadInstructionBytes + 8].
  		[JumpLong]				-> [^self literalLoadInstructionBytes + 8].
  		[JumpZero]				-> [^8].
  		[JumpNonZero]			-> [^8].
  		[JumpNegative]			-> [^8].
  		[JumpNonNegative]		-> [^8].
  		[JumpOverflow]			-> [^8].
  		[JumpNoOverflow]		-> [^8].
  		[JumpCarry]			-> [^8].
  		[JumpNoCarry]			-> [^8].
  		[JumpLess]				-> [^8].
  		[JumpGreaterOrEqual]	-> [^8].
  		[JumpGreater]			-> [^8].
  		[JumpLessOrEqual]		-> [^8].
  		[JumpBelow]			-> [^8].
  		[JumpAboveOrEqual]	-> [^8].
  		[JumpAbove]			-> [^8].
  		[JumpBelowOrEqual]	-> [^8].
  		[JumpLongZero]		-> [^self literalLoadInstructionBytes + 8].
  		[JumpLongNonZero]	-> [^self literalLoadInstructionBytes + 8].
  		[JumpFPEqual]			-> [^8].
  		[JumpFPNotEqual]		-> [^8].
  		[JumpFPLess]			-> [^8].
  		[JumpFPGreaterOrEqual]-> [^8].
  		[JumpFPGreater]		-> [^8].
  		[JumpFPLessOrEqual]	-> [^8].
  		[JumpFPOrdered]		-> [^8].
  		[JumpFPUnordered]		-> [^8].
  		[RetN]					-> [^8].
  		[Stop]					-> [^4].
  
  		"Arithmetic"
  		[AddCqR]				-> [^12].
  		[AndCqR]				-> [^16].
  		[AndCqRR]				-> [^12].
  		[CmpCqR]				-> [^28].
  		[OrCqR]					-> [^12].
  		[SubCqR]				-> [^12].
  		[TstCqR]				-> [^12].
  		[XorCqR]				-> [^12].
  		[AddCwR]				-> [^12].
  		[AndCwR]				-> [^12].
  		[CmpCwR]				-> [^28].
  		[OrCwR]				-> [^12].
  		[SubCwR]				-> [^12].
  		[XorCwR]				-> [^12].
  		[AddRR]					-> [^4].
  		[AndRR]					-> [^4].
  		[CmpRR]				-> [^20].
  		[OrRR]					-> [^4].
  		[XorRR]					-> [^4].
  		[SubRR]					-> [^4].
  		[NegateR]				-> [^4].
  		[LoadEffectiveAddressMwrR] -> [^12].
  		[LogicalShiftLeftCqR]		-> [^4].
  		[LogicalShiftRightCqR]		-> [^4].
  		[ArithmeticShiftRightCqR]	-> [^4].
  		[LogicalShiftLeftRR]			-> [^4].
  		[LogicalShiftRightRR]		-> [^4].
  		[ArithmeticShiftRightRR]		-> [^4].
  		[AddRdRd]					-> [^4].
  		[CmpRdRd]					-> [^4].
  		[SubRdRd]					-> [^4].
  		[MulRdRd]					-> [^4].
  		[DivRdRd]					-> [^4].
  		[SqrtRd]					-> [^4].
  		[AddCheckOverflowCqR]	-> [^28].
  		[AddCheckOverflowRR]		-> [^20].
  		[SubCheckOverflowCqR]	-> [^28].
  		[SubCheckOverflowRR]		-> [^20].
+ 		[MulCheckOverflowRR]		-> [^20].
  		"Data Movement"						
  		[MoveCqR]				-> [^8 "or 4"].
  		[MoveCwR]				-> [^8].
  		[MoveRR]				-> [^4].
  		[MoveRdRd]				-> [^4].
  		[MoveAwR]				-> [^(self isAddressRelativeToVarBase: (operands at: 0))
  													ifTrue: [4]
  													ifFalse: [self literalLoadInstructionBytes + 4]].
  		[MoveRAw]				-> [^(self isAddressRelativeToVarBase: (operands at: 1))
  													ifTrue: [4]
  													ifFalse: [self literalLoadInstructionBytes + 4]].
  		[MoveAbR]				-> [^(self isAddressRelativeToVarBase: (operands at: 0))
  													ifTrue: [4]
  													ifFalse: [self literalLoadInstructionBytes + 4]].
  		[MoveRAb]				-> [^(self isAddressRelativeToVarBase: (operands at: 1))
  													ifTrue: [4]
  													ifFalse: [self literalLoadInstructionBytes + 4]].
  		[MoveRMwr]			-> [^16].
  		[MoveRdM64r]			-> [^self literalLoadInstructionBytes + 4]. 
  		[MoveMbrR]				-> [^16].
  		[MoveRMbr]				-> [^16].
  		[MoveM16rR]			-> [^4].
  		[MoveM64rRd]			-> [^self literalLoadInstructionBytes + 4].
  		[MoveMwrR]			-> [^16].
  		[MoveXbrRR]			-> [^8].
  		[MoveRXbrR]			-> [^8].
  		[MoveXwrRR]			-> [^12].
  		[MoveRXwrR]			-> [^12].
  		[PopR]					-> [^8].
  		[PushR]					-> [^8].
  		[PushCw]				-> [^16].
  		[PushCq]				-> [^16].
  		[PrefetchAw] 			-> [^12].
  		"Conversion"
  		[ConvertRRd]			-> [^8].
  		}.
  	^0 "to keep C compiler quiet"
  !

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeBrSignedGreaterRR (in category 'generate machine code - concretize') -----
  concretizeBrSignedGreaterRR
  	| offset leftReg rightReg |
  	offset := self computeJumpTargetOffsetPlus: 8. "Relative to delay slot"
  	leftReg := self concreteRegister: (operands at: 1).
  	rightReg := self concreteRegister: (operands at: 2).
  	self machineCodeAt: 0 put: (self sltR: BranchTemp R: rightReg R: leftReg).
+ 	self machineCodeAt: 4 put: (self bneR: BranchTemp R: ZR offset: offset).
- 	self machineCodeAt: 4 put: (self beqR: BranchTemp R: ZR offset: offset).
  	self machineCodeAt: 8 put: (self nop). "Delay slot"
  	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeBrSignedLessEqualRR (in category 'generate machine code - concretize') -----
  concretizeBrSignedLessEqualRR
  	| offset leftReg rightReg |
  	offset := self computeJumpTargetOffsetPlus: 8. "Relative to delay slot"
  	leftReg := self concreteRegister: (operands at: 1).
  	rightReg := self concreteRegister: (operands at: 2).
  	self machineCodeAt: 0 put: (self sltR: BranchTemp R: rightReg R: leftReg).
+ 	self machineCodeAt: 4 put: (self beqR: BranchTemp R: ZR offset: offset).
- 	self machineCodeAt: 4 put: (self bneR: BranchTemp R: ZR offset: offset).
  	self machineCodeAt: 8 put: (self nop). "Delay slot"
  	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeBrUnsignedGreaterRR (in category 'generate machine code - concretize') -----
  concretizeBrUnsignedGreaterRR
  	| offset leftReg rightReg |
  	offset := self computeJumpTargetOffsetPlus: 8. "Relative to delay slot"
  	leftReg := self concreteRegister: (operands at: 1).
  	rightReg := self concreteRegister: (operands at: 2).
  	self machineCodeAt: 0 put: (self sltuR: BranchTemp R: rightReg R: leftReg).
+ 	self machineCodeAt: 4 put: (self bneR: BranchTemp R: ZR offset: offset).
- 	self machineCodeAt: 4 put: (self beqR: BranchTemp R: ZR offset: offset).
  	self machineCodeAt: 8 put: (self nop). "Delay slot"
  	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeBrUnsignedLessEqualRR (in category 'generate machine code - concretize') -----
  concretizeBrUnsignedLessEqualRR
  	| offset leftReg rightReg |
  	offset := self computeJumpTargetOffsetPlus: 8. "Relative to delay slot"
  	leftReg := self concreteRegister: (operands at: 1).
  	rightReg := self concreteRegister: (operands at: 2).
  	self machineCodeAt: 0 put: (self sltuR: BranchTemp R: rightReg R: leftReg).
+ 	self machineCodeAt: 4 put: (self beqR: BranchTemp R: ZR offset: offset).
- 	self machineCodeAt: 4 put: (self bneR: BranchTemp R: ZR offset: offset).
  	self machineCodeAt: 8 put: (self nop). "Delay slot"
  	^machineCodeSize := 12!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeFill32 (in category 'generate machine code - concretize') -----
  concretizeFill32
  	"fill with operand 0 according to the processor's endianness"
  	| word |
  	<var: #word type: #'unsigned long'>
  	
  	self flag: #bogus. "Gaps in the instruction stream should be filled with the stop instruction."
  	
  	word := operands at: 0.
  	self machineCodeAt: 0 put: word.
  	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeMoveM16rR (in category 'generate machine code - concretize') -----
  concretizeMoveM16rR
  	<var: #offset type: #sqInt>
  	| srcReg offset destReg |
  	offset := operands at: 0.
  	srcReg := self concreteRegister: (operands at: 1).
  	destReg := self concreteRegister: (operands at: 2).
+ 	self machineCodeAt: 0 put: (self lhuR: destReg base: srcReg offset: offset).
- 	self machineCodeAt: 0 put: (self lhR: destReg base: srcReg offset: offset).
  	^machineCodeSize := 4!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeMulCheckOverflowRR (in category 'generate machine code - concretize') -----
+ concretizeMulCheckOverflowRR
+ 	| leftReg rightReg |
+ 	leftReg := self concreteRegister: (operands at: 0).
+ 	rightReg := self concreteRegister: (operands at: 1). "Also destReg."
+ 
+ 	"Overflow occured if the sign bit of the low part is different from the high part."
+ 	self machineCodeAt: 0 put: (self multR: leftReg R: rightReg).
+ 	self machineCodeAt: 4 put: (self mfloR: rightReg).
+ 	self machineCodeAt: 8 put: (self sraR: OverflowTemp1 R: rightReg C: 31).
+ 	self machineCodeAt: 12 put: (self mfhiR: OverflowTemp2).
+ 	"Overflow contains 0 on overflow, non-zero otherwise."
+ 	self machineCodeAt: 16 put: (self subuR: Overflow R: OverflowTemp1 R: OverflowTemp2).
+ 	^machineCodeSize := 20!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeNegateR (in category 'generate machine code - concretize') -----
+ concretizeNegateR
+ 	| reg |
+ 	reg := self concreteRegister: (operands at: 0).
+ 	self machineCodeAt: 0 put: (self subuR: reg R: ZR R: reg).
+ 	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeSubRR (in category 'generate machine code - concretize') -----
  concretizeSubRR
  	| leftReg rightReg |
+ 	rightReg := self concreteRegister: (operands at: 0).
+ 	leftReg := self concreteRegister: (operands at: 1).
+ 	self machineCodeAt: 0 put: (self subuR: leftReg R: leftReg R: rightReg).
- 	leftReg := self concreteRegister: (operands at: 0).
- 	rightReg := self concreteRegister: (operands at: 1).
- 	self machineCodeAt: 0 put: (self subuR: rightReg R: leftReg R: rightReg).
  	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogMIPSELCompiler>>dispatchConcretize (in category 'generate machine code') -----
  dispatchConcretize
  	"Attempt to generate concrete machine code for the instruction at address.
  	 This is the inner dispatch of concretizeAt: actualAddress which exists only
  	 to get around the branch size limits in the SqueakV3 (blue book derived)
  	 bytecode set."
  	<returnTypeC: #void>		 
  	opcode caseOf: {
  		[BrEqualRR]						-> [^self concretizeBrEqualRR].
  		[BrNotEqualRR]					-> [^self concretizeBrNotEqualRR].
  		[BrUnsignedLessRR]			-> [^self concretizeBrUnsignedLessRR].
  		[BrUnsignedLessEqualRR]		-> [^self concretizeBrUnsignedLessEqualRR].
  		[BrUnsignedGreaterRR]			-> [^self concretizeBrUnsignedGreaterRR].
  		[BrUnsignedGreaterEqualRR]	-> [^self concretizeBrUnsignedGreaterEqualRR].
  		[BrSignedLessRR]				-> [^self concretizeBrSignedLessRR].
  		[BrSignedLessEqualRR]			-> [^self concretizeBrSignedLessEqualRR].
  		[BrSignedGreaterRR]			-> [^self concretizeBrSignedGreaterRR].
  		[BrSignedGreaterEqualRR]		-> [^self concretizeBrSignedGreaterEqualRR].	
  		[BrLongEqualRR]				-> [^self concretizeBrLongEqualRR].
  		[BrLongNotEqualRR]				-> [^self concretizeBrLongNotEqualRR].
  		[MulRR]				-> [^self concretizeMulRR].
  		[DivRR]				-> [^self concretizeDivRR].
  		[MoveLowR]		-> [^self concretizeMoveLowR].
  		[MoveHighR]		-> [^self concretizeMoveHighR].
  
  										
  		"Noops & Pseudo Ops"
  		[Label]					-> [^self concretizeLabel].
  		[AlignmentNops]		-> [^self concretizeAlignmentNops].
  		[Fill16]					-> [^self concretizeFill16].
  		[Fill32]					-> [^self concretizeFill32].
  		[FillFromWord]			-> [^self concretizeFillFromWord].
  		[Nop]					-> [^self concretizeNop].
  		"Control"
  		[Call]						-> [^self concretizeCall]. "call code within code space"
  		[CallFull]					-> [^self concretizeCallFull]. "call code anywhere in address space"
  		[JumpR]						-> [^self concretizeJumpR].
  		[JumpFull]					-> [^self concretizeJumpFull]."jump within address space"
  		[JumpLong]					-> [^self concretizeJumpLong]."jumps witihn code space"
  		[JumpLongZero]			-> [^self concretizeJumpLongZero].
  		[JumpLongNonZero]		-> [^self concretizeJumpLongNonZero].
  		[Jump]						-> [^self concretizeJump].
  		[JumpZero]					-> [^self concretizeJumpZero].
  		[JumpNonZero]				-> [^self concretizeJumpNonZero].
  		[JumpNegative]				-> [^self concretizeUnimplemented].
  		[JumpNonNegative]			-> [^self concretizeUnimplemented].
  		[JumpOverflow]				-> [^self concretizeJumpOverflow].
  		[JumpNoOverflow]			-> [^self concretizeJumpNoOverflow].
  		[JumpCarry]				-> [^self concretizeUnimplemented].
  		[JumpNoCarry]				-> [^self concretizeUnimplemented].
  		[JumpLess]					-> [^self concretizeJumpSignedLessThan].
  		[JumpGreaterOrEqual]		-> [^self concretizeJumpSignedGreaterEqual].
  		[JumpGreater]				-> [^self concretizeJumpSignedGreaterThan].
  		[JumpLessOrEqual]			-> [^self concretizeJumpSignedLessEqual].
  		[JumpBelow]				-> [^self concretizeJumpUnsignedLessThan].
  		[JumpAboveOrEqual]		-> [^self concretizeJumpUnsignedGreaterEqual].
  		[JumpAbove]				-> [^self concretizeJumpUnsignedGreaterThan].
  		[JumpBelowOrEqual]		-> [^self concretizeJumpUnsignedLessEqual].
  		[JumpFPEqual]				-> [^self concretizeUnimplemented].
  		[JumpFPNotEqual]			-> [^self concretizeUnimplemented].
  		[JumpFPLess]				-> [^self concretizeUnimplemented].
  		[JumpFPGreaterOrEqual]	-> [^self concretizeUnimplemented].
  		[JumpFPGreater]			-> [^self concretizeUnimplemented].
  		[JumpFPLessOrEqual]		-> [^self concretizeUnimplemented].
  		[JumpFPOrdered]			-> [^self concretizeUnimplemented].
  		[JumpFPUnordered]			-> [^self concretizeUnimplemented].
  		[RetN]						-> [^self concretizeRetN].
  		[Stop]						-> [^self concretizeStop].
  		"Arithmetic"
  		[AddCqR]					-> [^self concretizeAddCqR].
  		[AndCqR]					-> [^self concretizeAndCqR].
  		[AndCqRR]					-> [^self concretizeAndCqRR].
  		[CmpCqR]					-> [^self concretizeCmpCqR].
  		[OrCqR]						-> [^self concretizeOrCqR].
  		[SubCqR]					-> [^self concretizeSubCqR].
  		[TstCqR]					-> [^self concretizeTstCqR].
  		[XorCqR]					-> [^self concretizeXorCqR].
  		[AddCwR]					-> [^self concretizeAddCwR].
  		[AndCwR]					-> [^self concretizeAndCwR].
  		[CmpCwR]					-> [^self concretizeCmpCwR].
  		[OrCwR]					-> [^self concretizeOrCwR].
  		[SubCwR]					-> [^self concretizeSubCwR].
  		[XorCwR]					-> [^self concretizeXorCwR].
  		[AddRR]						-> [^self concretizeAddRR].
  		[AndRR]						-> [^self concretizeAndRR].
  		[CmpRR]					-> [^self concretizeCmpRR].
  		[OrRR]						-> [^self concretizeOrRR].
  		[SubRR]						-> [^self concretizeSubRR].
  		[XorRR]						-> [^self concretizeXorRR].
  		[AddRdRd]					-> [^self concretizeUnimplemented].
  		[CmpRdRd]					-> [^self concretizeUnimplemented].
  		[DivRdRd]					-> [^self concretizeUnimplemented].
  		[MulRdRd]					-> [^self concretizeUnimplemented].
  		[SubRdRd]					-> [^self concretizeUnimplemented].
  		[SqrtRd]					-> [^self concretizeUnimplemented].
  		[NegateR]						-> [^self concretizeNegateR].
  		[LoadEffectiveAddressMwrR]	-> [^self concretizeLoadEffectiveAddressMwrR].
  		[ArithmeticShiftRightCqR]		-> [^self concretizeArithmeticShiftRightCqR].
  		[LogicalShiftRightCqR]			-> [^self concretizeLogicalShiftRightCqR].
  		[LogicalShiftLeftCqR]			-> [^self concretizeLogicalShiftLeftCqR].
  		[ArithmeticShiftRightRR]			-> [^self concretizeArithmeticShiftRightRR].
  		[LogicalShiftLeftRR]				-> [^self concretizeLogicalShiftLeftRR].
  		[LogicalShiftRightRR]			-> [^self concretizeLogicalShiftRightRR].
  		"Data Movement"
  		[MoveCqR]			-> [^self concretizeMoveCqR].
  		[MoveCwR]			-> [^self concretizeMoveCwR].
  		[MoveRR]			-> [^self concretizeMoveRR].
  		[MoveAwR]			-> [^self concretizeMoveAwR].
  		[MoveRAw]			-> [^self concretizeMoveRAw].
  		[MoveAbR]			-> [^self concretizeMoveAbR].
  		[MoveRAb]			-> [^self concretizeMoveRAb].
  		[MoveMbrR]			-> [^self concretizeMoveMbrR].
  		[MoveRMbr]			-> [^self concretizeRMbr].
  		[MoveM16rR]		-> [^self concretizeMoveM16rR].
  		[MoveM64rRd]		-> [^self concretizeM64rRd].
  		[MoveMwrR]		-> [^self concretizeMoveMwrR].
  		[MoveXbrRR]		-> [^self concretizeMoveXbrRR].
  		[MoveRXbrR]		-> [^self concretizeMoveRXbrR].
  		[MoveXwrRR]		-> [^self concretizeMoveXwrRR].
  		[MoveRXwrR]		-> [^self concretizeMoveRXwrR].
  		[MoveRMwr]		-> [^self concretizeMoveRMwr].
  		[MoveRdM64r]		-> [^self concretizeRdM64r].
  		[PopR]				-> [^self concretizePopR].
  		[PushR]				-> [^self concretizePushR].
  		[PushCq]			-> [^self concretizePushCq].
  		[PushCw]			-> [^self concretizePushCw].
  		[PrefetchAw]		-> [^self concretizePrefetchAw].
  		[AddCheckOverflowCqR] -> [^self concretizeAddCheckOverflowCqR].
  		[AddCheckOverflowRR] -> [^self concretizeAddCheckOverflowRR].
  		[SubCheckOverflowCqR] -> [^self concretizeSubCheckOverflowCqR].
  		[SubCheckOverflowRR] -> [^self concretizeSubCheckOverflowRR].
+ 		[MulCheckOverflowRR] -> [^self concretizeMulCheckOverflowRR].
  		"Conversion"
  		[ConvertRRd]		-> [^self concretizeUnimplemented]}!

Item was added:
+ ----- Method: CogMIPSELCompiler>>genAlignCStackSavingRegisters:numArgs:wordAlignment: (in category 'abi') -----
+ genAlignCStackSavingRegisters: saveRegs numArgs: numArgs wordAlignment: alignment 
+ 	| wordsPushedModAlignment delta |
+ 	self numIntRegArgs >= (saveRegs
+ 								ifTrue: [self numberOfSaveableRegisters + numArgs]
+ 								ifFalse: [numArgs])  ifTrue:
+ 		[^0].
+ 	wordsPushedModAlignment := ((saveRegs ifTrue: [self numberOfSaveableRegisters] ifFalse: [0])
+ 									+ numArgs)
+ 									\\ alignment.
+ 	wordsPushedModAlignment ~= 0 ifTrue:
+ 		[delta := alignment - wordsPushedModAlignment.
+ 		 cogit SubCq: delta * 4 R: SPReg].
+ 	^0!

Item was added:
+ ----- Method: CogMIPSELCompiler>>genMulR:R: (in category 'abstract instructions') -----
+ genMulR: regSource R: regDest
+ 	cogit gen: MulRR operand: regSource operand: regDest.
+ 	^0!

Item was added:
+ ----- Method: CogMIPSELCompiler>>genSubstituteReturnAddress: (in category 'abstract instructions') -----
+ genSubstituteReturnAddress: retpc
+ 	<inline: true>
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	^cogit MoveCw: retpc R: RA!

Item was added:
+ ----- Method: CogMIPSELCompiler>>hasDoublePrecisionFloatingPointSupport (in category 'testing') -----
+ hasDoublePrecisionFloatingPointSupport
+ 	<inline: true>
+ 	self flag: #todo.
+ 	^false!

Item was added:
+ ----- Method: CogMIPSELCompiler>>isCallPrecedingReturnPC: (in category 'testing') -----
+ isCallPrecedingReturnPC: mcpc
+ 	cogit disassembleFrom: mcpc - 8 to: mcpc.
+ 
+ 	(self opcodeAtAddress: mcpc - 8) = JAL ifTrue: [^true].
+ 	
+ 	((self opcodeAtAddress: mcpc - 8) = SPECIAL
+ 		and: [(self opcodeAtAddress: mcpc - 8) = JALR]) ifTrue: [^true].
+ 	
+ 	^false!

Item was changed:
+ ----- Method: CogMIPSELCompiler>>isJump (in category 'testing') -----
- ----- Method: CogMIPSELCompiler>>isJump (in category 'as yet unclassified') -----
  isJump
  	^super isJump or: [opcode between: BrEqualRR and: BrLongNotEqualRR]!

Item was changed:
  ----- Method: CogMIPSELCompiler>>noteFollowingConditionalBranch: (in category 'abstract instructions') -----
  noteFollowingConditionalBranch: branch
  	"Support for processors without condition codes, such as the MIPS.
  	 Answer the branch opcode.  Modify the receiver and the branch to
  	 implement a suitable conditional branch that doesn't depend on
  	 condition codes being set by the receiver."
  	<var: #branch type: #'AbstractInstruction *'>
  	| newBranchLeft newBranchOpcode newBranchRight |
  
  	((branch opcode = JumpOverflow) or: [branch opcode = JumpNoOverflow]) ifTrue:
  		[opcode := opcode caseOf: {
  			[AddCqR]	-> [AddCheckOverflowCqR].
  			[AddRR]		-> [AddCheckOverflowRR].
  			[MulRR]		-> [MulCheckOverflowRR].
  			[SubCqR]	-> [SubCheckOverflowCqR].
  			[SubRR]		-> [SubCheckOverflowRR].
  		} otherwise: [self unreachable].
  		^branch].
  
  	newBranchOpcode := branch opcode caseOf: {
  		[JumpZero] 			-> [BrEqualRR].
  		[JumpNonZero]			-> [BrNotEqualRR].
  		[JumpBelow]			-> [BrUnsignedLessRR].
  		[JumpBelowOrEqual]	-> [BrUnsignedLessEqualRR].
  		[JumpAbove]			-> [BrUnsignedGreaterRR].
  		[JumpAboveOrEqual]	-> [BrUnsignedGreaterEqualRR].
  		[JumpLess]				-> [BrSignedLessRR].
  		[JumpLessOrEqual]		-> [BrSignedLessEqualRR].
  		[JumpGreater]			-> [BrSignedGreaterRR].
  		[JumpGreaterOrEqual]	-> [BrSignedGreaterEqualRR].
  		[JumpLongZero] 		-> [BrLongEqualRR].
  		[JumpLongNonZero]	-> [BrLongNotEqualRR].
+ 		
+ 		[JumpNegative]			-> [BrSignedLessRR].
  	} otherwise: [self unreachable].
  	
  	opcode caseOf: {
  		[BrEqualRR]	->	["I.e., two jumps after a compare."
  						newBranchLeft := operands at: 1.
+ 						newBranchRight := operands at: 2].
+ 		[BrUnsignedLessRR]	->	["I.e., two jumps after a compare."
+ 						newBranchLeft := operands at: 1.
+ 						newBranchRight := operands at: 2].
+ 
+ 		[CmpRR] 	-> 	[newBranchLeft := operands at: 1.
+ 						 newBranchRight := operands at: 0.
- 						newBranchRight := operands at: 2].	
- 		[CmpRR] 	-> 	[newBranchLeft := operands at: 0.
- 						 newBranchRight := operands at: 1.
  						 opcode := Label].
+ 		[CmpCqR]	-> 	[newBranchLeft := operands at: 1.
+ 						 newBranchRight := AT.
- 		[CmpCqR]	-> 	[newBranchLeft := AT.
- 						 newBranchRight := operands at: 1.
  						 opcode := MoveCqR.
  						 operands at: 1 put: AT].
+ 		[CmpCwR]	-> 	[newBranchLeft := operands at: 1.
+ 						 newBranchRight := AT.
- 		[CmpCwR]	-> 	[newBranchLeft := AT.
- 						 newBranchRight := operands at: 1.
  						 opcode := MoveCwR.
  						 operands at: 1 put: AT].
  		[TstCqR]	->	[newBranchLeft := Cmp.
  						 newBranchRight := ZR].
  		[AndCqR]	->	[newBranchLeft := operands at: 1.
  						 newBranchRight := ZR].
  		[AndCqRR]	->	[newBranchLeft := operands at: 2.
  						 newBranchRight := ZR].
  		[OrRR]	->		[newBranchLeft := operands at: 1.
  						 newBranchRight := ZR].
  		[XorRR]	->		[newBranchLeft := operands at: 1.
  						 newBranchRight := ZR].
  		[SubCwR]	->	[newBranchLeft := operands at: 1.
  						 newBranchRight := ZR].
  		[SubCqR]	->	[newBranchLeft := operands at: 1.
  						 newBranchRight := ZR].
+ 		[ArithmeticShiftRightCqR]	->	[newBranchLeft := operands at: 1.
+ 						 newBranchRight := ZR].
  	} otherwise: [self unreachable].
  
  	branch rewriteOpcode: newBranchOpcode with: newBranchLeft with: newBranchRight.
  	^branch!

Item was changed:
  ----- Method: CogMIPSELCompiler>>rewriteCPICJumpAt:target: (in category 'inline cacheing') -----
  rewriteCPICJumpAt: addressFollowingJump target: jumpTargetAddress
  	"Rewrite a jump instruction to call a different target.  This variant is used to reset the 
  	jumps in the prototype CPIC to suit each use,.   
  	Answer the extent of the code change which is used to compute the range of the icache to flush."
  	<var: #addressFollowingJump type: #usqInt>
  	<var: #jumpTargetAddress type: #usqInt>
  	
+ 	"self CmpR: ClassReg R: TempReg.
+ 	^self JumpNonZero: 0"
+ 	
+ 	"bne s5, s3, +156 ; =BE7C
+ 	 nop (delay slot)
+ 	 .... <-- addressFollowingJump"
+ 	
+ 	self assert: (self opcodeAtAddress: addressFollowingJump - 8) = BNE.
+ 	self assert: (objectMemory longAt: addressFollowingJump - 4) = self nop.
+ 	cogit disassembleFrom: addressFollowingJump - 8 to: addressFollowingJump.
+ 	
+ 	self rewriteITypeBranchAtAddress: addressFollowingJump - 8 target: jumpTargetAddress.
+ 	
+ 	self assert: (self opcodeAtAddress: addressFollowingJump - 8) = BNE.
+ 	self assert: (objectMemory longAt: addressFollowingJump - 4) = self nop.
+ 	cogit disassembleFrom: addressFollowingJump - 8 to: addressFollowingJump.!
- 	cogit disassembleFrom: addressFollowingJump - 16 to: addressFollowingJump + 16.
- 	self halt.!

Item was added:
+ ----- Method: CogMIPSELCompiler>>rewriteConditionalJumpLongAt:target: (in category 'inline cacheing') -----
+ rewriteConditionalJumpLongAt: callSiteReturnAddress target: callTargetAddress
+ 	"Rewrite a jump instruction to call a different target.  This variant is used to reset the 
+ 	jumps in the prototype CPIC to suit each use,.   
+ 	Answer the extent of the code change which is used to compute the range of the icache to flush."
+ 	<var: #callSiteReturnAddress type: #usqInt>
+ 	<var: #callTargetAddress type: #usqInt>
+ 	
+ 	self assert: (self opcodeAtAddress: callSiteReturnAddress - 8) = J.
+ 	self assert: (objectMemory longAt: callSiteReturnAddress - 4) = self nop.
+ 	cogit disassembleFrom: callSiteReturnAddress - 8 to: callSiteReturnAddress.
+ 
+ 	self rewriteJTypeAtAddress: callSiteReturnAddress - 8 target: callTargetAddress.
+ 
+ 	self assert: (self opcodeAtAddress: callSiteReturnAddress - 8) = J.
+ 	self assert: (objectMemory longAt: callSiteReturnAddress - 4) = self nop.
+ 	cogit disassembleFrom: callSiteReturnAddress - 8 to: callSiteReturnAddress.
+ !

Item was changed:
  ----- Method: CogMIPSELCompiler>>rewriteJumpLongAt:target: (in category 'inline cacheing') -----
  rewriteJumpLongAt: callSiteReturnAddress target: callTargetAddress
  	"Rewrite a jump instruction to call a different target.  This variant is used to reset the 
  	jumps in the prototype CPIC to suit each use,.   
  	Answer the extent of the code change which is used to compute the range of the icache to flush."
  	<var: #callSiteReturnAddress type: #usqInt>
  	<var: #callTargetAddress type: #usqInt>
  	
- 	self assert: (self opcodeAtAddress: callSiteReturnAddress - 8) = J.
- 	self assert: (objectMemory longAt: callSiteReturnAddress - 4) = self nop.
- 	cogit disassembleFrom: callSiteReturnAddress - 8 to: callSiteReturnAddress.
- 
- 	self rewriteJTypeAtAddress: callSiteReturnAddress - 8 target: callTargetAddress.
- 
- 	self assert: (self opcodeAtAddress: callSiteReturnAddress - 8) = J.
- 	self assert: (objectMemory longAt: callSiteReturnAddress - 4) = self nop.
- 	cogit disassembleFrom: callSiteReturnAddress - 8 to: callSiteReturnAddress.
- 
- 	^8
- 	
  	"lui t9, stub/targetHigh
  	 ori t9, t9, stub/targetLow
  	 jr t9
  	 nop (delay slot)
  	 ...  <-- callSiteReturnAddress"
  
+ 	self assert: (self opcodeAtAddress: callSiteReturnAddress - 16) = LUI.
- 	"self assert: (self opcodeAtAddress: callSiteReturnAddress - 16) = LUI.
  	self assert: (self opcodeAtAddress: callSiteReturnAddress - 12) = ORI.
  	self assert: (self opcodeAtAddress: callSiteReturnAddress - 8) = SPECIAL.
  	self assert: (self functionAtAddress: callSiteReturnAddress - 8) = JR.
  	self assert: (objectMemory longAt: callSiteReturnAddress - 4) = self nop.
  	
  	cogit disassembleFrom: callSiteReturnAddress - 16 to: callSiteReturnAddress.
  
  	self literalAtAddress: callSiteReturnAddress - 12 put: callTargetAddress.
  
  	self assert: (self opcodeAtAddress: callSiteReturnAddress - 16) = LUI.
  	self assert: (self opcodeAtAddress: callSiteReturnAddress - 12) = ORI.
  	self assert: (self opcodeAtAddress: callSiteReturnAddress - 8) = SPECIAL.
  	self assert: (self functionAtAddress: callSiteReturnAddress - 8) = JR.
  	self assert: (objectMemory longAt: callSiteReturnAddress - 4) = self nop.
  
  	cogit disassembleFrom: callSiteReturnAddress - 16 to: callSiteReturnAddress.
  
+ 	^20!
- 	^20"!

Item was changed:
  ----- Method: CogMIPSELCompiler>>setsConditionCodesFor: (in category 'testing') -----
  setsConditionCodesFor: aConditionalJumpOpcode
  	<inline: false>
+ 	"Not really, but we can merge this in noteFollowingConditionalBranch:."
+ 	opcode = XorRR ifTrue: [^true]. 
+ 	opcode = ArithmeticShiftRightCqR ifTrue: [^true].
- 	opcode = XorRR ifTrue: [^true]. "Not really, but we can merge this in noteFollowingConditionalBranch:."
  	self unreachable.
  	^false!

Item was added:
+ CogMIPSELCompiler subclass: #CogMIPSELCompilerForTests
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-Tests'!

Item was added:
+ ----- Method: CogMIPSELCompilerForTests class>>dataRegistersWithAccessorsDo: (in category 'as yet unclassified') -----
+ dataRegistersWithAccessorsDo: aTrinaryBlock
+ 	#((16 s0 s0:)
+ 		(17 s1 s1:)
+ 		(18 s2 s2:)
+ 		(19 s3 s3:)
+ 		(20 s4 s4:)
+ 		(21 s5 s5:)
+ 		(22 s6 s6:)
+ 		(29 sp sp:)
+ 		(30 fp fp:)
+ 		(31 ra ra:)) do: [:triple | aTrinaryBlock valueWithArguments: triple].!

Item was added:
+ ----- Method: CogMIPSELCompilerForTests class>>isConcreteRISCTempRegister: (in category 'as yet unclassified') -----
+ isConcreteRISCTempRegister: concreteRegister
+ 	"For tests to filter-out bogus values left in the ConcreteRISCTempRegister, if any."
+ 	^concreteRegister = AT
+ 		or: [concreteRegister = Cmp
+ 		or: [concreteRegister = Overflow
+ 		or: [concreteRegister = BranchTemp]]]!

Item was added:
+ AbstractInstructionTests subclass: #CogMIPSELCompilerTests
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-Tests'!

Item was added:
+ ----- Method: CogMIPSELCompilerTests>>assertCheckLongArithOpCodeSize: (in category 'accessing') -----
+ assertCheckLongArithOpCodeSize: bytes
+ 	self assert: bytes = 12.!

Item was added:
+ ----- Method: CogMIPSELCompilerTests>>assertCheckQuickArithOpCodeSize: (in category 'as yet unclassified') -----
+ assertCheckQuickArithOpCodeSize: bytes
+ 	self flag: #todo. "We always generate the full 3 instructions for now."
+ 	self assert: bytes = 12!

Item was added:
+ ----- Method: CogMIPSELCompilerTests>>concreteCompilerClass (in category 'accessing') -----
+ concreteCompilerClass
+ 	^CogMIPSELCompilerForTests!

Item was added:
+ ----- Method: CogMIPSELCompilerTests>>memoryAsBytes: (in category 'as yet unclassified') -----
+ memoryAsBytes: instructionMachineCode
+ 	"Manage the fact that in the simulator inst machineCode object is an Array and the disassembler requires a ByteArray or some such."
+ 	| bytes |
+ 	instructionMachineCode isCObjectAccessor ifTrue:
+ 		[^self memoryAsBytes: instructionMachineCode object].
+ 	instructionMachineCode isArray ifFalse:
+ 		[self assert: instructionMachineCode class isBits.
+ 		 ^instructionMachineCode].
+ 	bytes := ByteArray new: instructionMachineCode size * 4.
+ 	1 to: instructionMachineCode size do:
+ 		[:i|
+ 		(instructionMachineCode at: i) ifNotNil:
+ 			[:word|
+ 			bytes unsignedLongAt: i - 1* 4 + 1 put: word]].
+ 	^bytes!

Item was added:
+ ----- Method: CogMIPSELCompilerTests>>processor (in category 'accessing') -----
+ processor
+ 	processor ifNil:
+ 		[processor := MIPSELSimulator new].
+ 	^processor!

Item was changed:
  ----- Method: Cogit>>JumpAbove: (in category 'abstract instructions') -----
  JumpAbove: jumpTarget
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
  	<var: #jumpTarget type: #'void *'>
+ 	^self genConditionalBranch: JumpAbove operand: jumpTarget asInteger!
- 	^self previousInstruction noteFollowingConditionalBranch:
- 		(self gen: JumpAbove operand: jumpTarget asInteger)!

Item was changed:
  ----- Method: Cogit>>JumpAboveOrEqual: (in category 'abstract instructions') -----
  JumpAboveOrEqual: jumpTarget
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
  	<var: #jumpTarget type: #'void *'>
+ 	^self genConditionalBranch: JumpAboveOrEqual operand: jumpTarget asInteger!
- 	^self previousInstruction noteFollowingConditionalBranch:
- 		(self gen: JumpAboveOrEqual operand: jumpTarget asInteger)!

Item was changed:
  ----- Method: Cogit>>JumpBelow: (in category 'abstract instructions') -----
  JumpBelow: jumpTarget
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
  	<var: #jumpTarget type: #'void *'>
+ 	^self genConditionalBranch: JumpBelow operand: jumpTarget asInteger!
- 	^self previousInstruction noteFollowingConditionalBranch:
- 		(self gen: JumpBelow operand: jumpTarget asInteger)!

Item was changed:
  ----- Method: Cogit>>JumpBelowOrEqual: (in category 'abstract instructions') -----
  JumpBelowOrEqual: jumpTarget
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
  	<var: #jumpTarget type: #'void *'>
+ 	^self genConditionalBranch: JumpBelowOrEqual operand: jumpTarget asInteger!
- 	^self previousInstruction noteFollowingConditionalBranch:
- 		(self gen: JumpBelowOrEqual operand: jumpTarget asInteger)!

Item was changed:
  ----- Method: Cogit>>JumpCarry: (in category 'abstract instructions') -----
  JumpCarry: jumpTarget
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
  	<var: #jumpTarget type: #'void *'>
+ 	^self genConditionalBranch: JumpCarry operand: jumpTarget asInteger!
- 	^self previousInstruction noteFollowingConditionalBranch:
- 		(self gen: JumpCarry operand: jumpTarget asInteger)!

Item was changed:
  ----- Method: Cogit>>JumpGreater: (in category 'abstract instructions') -----
  JumpGreater: jumpTarget
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
  	<var: #jumpTarget type: #'void *'>
+ 	^self genConditionalBranch: JumpGreater operand: jumpTarget asInteger!
- 	^self previousInstruction noteFollowingConditionalBranch:
- 		(self gen: JumpGreater operand: jumpTarget asInteger)!

Item was changed:
  ----- Method: Cogit>>JumpGreaterOrEqual: (in category 'abstract instructions') -----
  JumpGreaterOrEqual: jumpTarget
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
  	<var: #jumpTarget type: #'void *'>
+ 	^self genConditionalBranch: JumpGreaterOrEqual operand: jumpTarget asInteger!
- 	^self previousInstruction noteFollowingConditionalBranch:
- 		(self gen: JumpGreaterOrEqual operand: jumpTarget asInteger)!

Item was changed:
  ----- Method: Cogit>>JumpLess: (in category 'abstract instructions') -----
  JumpLess: jumpTarget
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
  	<var: #jumpTarget type: #'void *'>
+ 	^self genConditionalBranch: JumpLess operand: jumpTarget asInteger!
- 	^self previousInstruction noteFollowingConditionalBranch:
- 		(self gen: JumpLess operand: jumpTarget asInteger)!

Item was changed:
  ----- Method: Cogit>>JumpLessOrEqual: (in category 'abstract instructions') -----
  JumpLessOrEqual: jumpTarget
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
  	<var: #jumpTarget type: #'void *'>
+ 	^self genConditionalBranch: JumpLessOrEqual operand: jumpTarget asInteger!
- 	^self previousInstruction noteFollowingConditionalBranch:
- 		(self gen: JumpLessOrEqual operand: jumpTarget asInteger)!

Item was changed:
  ----- Method: Cogit>>JumpLongNonZero: (in category 'abstract instructions') -----
  JumpLongNonZero: jumpTarget
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
+ 	^self genConditionalBranch: JumpLongNonZero operand: jumpTarget asInteger!
- 	^self previousInstruction noteFollowingConditionalBranch:
- 		(self gen: JumpLongNonZero operand: jumpTarget asInteger)!

Item was changed:
  ----- Method: Cogit>>JumpLongZero: (in category 'abstract instructions') -----
  JumpLongZero: jumpTarget
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
+ 	^self genConditionalBranch: JumpLongZero operand: jumpTarget asInteger!
- 	^self previousInstruction noteFollowingConditionalBranch:
- 		(self gen: JumpLongZero operand: jumpTarget asInteger)!

Item was changed:
  ----- Method: Cogit>>JumpNegative: (in category 'abstract instructions') -----
  JumpNegative: jumpTarget
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
  	<var: #jumpTarget type: #'void *'>
+ 	^self genConditionalBranch: JumpNegative operand: jumpTarget asInteger!
- 	^self previousInstruction noteFollowingConditionalBranch:
- 		(self gen: JumpNegative operand: jumpTarget asInteger)!

Item was changed:
  ----- Method: Cogit>>JumpNoCarry: (in category 'abstract instructions') -----
  JumpNoCarry: jumpTarget
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
  	<var: #jumpTarget type: #'void *'>
+ 	^self genConditionalBranch: JumpNoCarry operand: jumpTarget asInteger!
- 	^self previousInstruction noteFollowingConditionalBranch:
- 		(self gen: JumpNoCarry operand: jumpTarget asInteger)!

Item was changed:
  ----- Method: Cogit>>JumpNoOverflow: (in category 'abstract instructions') -----
  JumpNoOverflow: jumpTarget
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
  	<var: #jumpTarget type: #'void *'>
+ 	^self genConditionalBranch: JumpNoOverflow operand: jumpTarget asInteger!
- 	^self previousInstruction noteFollowingConditionalBranch:
- 		(self gen: JumpNoOverflow operand: jumpTarget asInteger)!

Item was changed:
  ----- Method: Cogit>>JumpNonNegative: (in category 'abstract instructions') -----
  JumpNonNegative: jumpTarget
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
  	<var: #jumpTarget type: #'void *'>
+ 	^self genConditionalBranch: JumpNonNegative operand: jumpTarget asInteger!
- 	^self previousInstruction noteFollowingConditionalBranch:
- 		(self gen: JumpNonNegative operand: jumpTarget asInteger)!

Item was changed:
  ----- Method: Cogit>>JumpNonZero: (in category 'abstract instructions') -----
  JumpNonZero: jumpTarget
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
  	<var: #jumpTarget type: #'void *'>
+ 	^self genConditionalBranch: JumpNonZero operand: jumpTarget asInteger!
- 	^self previousInstruction noteFollowingConditionalBranch:
- 		(self gen: JumpNonZero operand: jumpTarget asInteger)!

Item was changed:
  ----- Method: Cogit>>JumpOverflow: (in category 'abstract instructions') -----
  JumpOverflow: jumpTarget
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
  	<var: #jumpTarget type: #'void *'>
+ 	^self genConditionalBranch: JumpOverflow operand: jumpTarget asInteger!
- 	^self previousInstruction noteFollowingConditionalBranch:
- 		(self gen: JumpOverflow operand: jumpTarget asInteger)!

Item was changed:
  ----- Method: Cogit>>JumpZero: (in category 'abstract instructions') -----
  JumpZero: jumpTarget
  	<inline: true>
  	<returnTypeC: #'AbstractInstruction *'>
  	<var: #jumpTarget type: #'void *'>
+ 	^self genConditionalBranch: JumpZero operand: jumpTarget asInteger!
- 	^self previousInstruction noteFollowingConditionalBranch:
- 		(self gen: JumpZero operand: jumpTarget asInteger)!

Item was changed:
  ----- Method: Cogit>>configureMNUCPIC:methodOperand:numArgs:delta: (in category 'in-line cacheing') -----
  configureMNUCPIC: cPIC methodOperand: methodOperand numArgs: numArgs delta: addrDelta
  	"Configure a copy of the prototype CPIC for a one-case MNU CPIC that calls ceMNUFromPIC for
  	 case0Tag The tag for case0 is at the send site and so doesn't need to be generated.
  	 addDelta is the address change from the prototype to the new CPIC location, needed
  	 because the loading of the CPIC label at the end may be a literal instead of a pc-relative load."
  	<var: #cPIC type: #'CogMethod *'>
  	| operand |
  
  	"adjust the jump at missOffset, the ceAbortXArgs"
+ 	backEnd rewriteCallAt: cPIC asInteger + missOffset target: (self picAbortTrampolineFor: numArgs).
- 	backEnd rewriteJumpLongAt: cPIC asInteger + missOffset target: (self picAbortTrampolineFor: numArgs).
  	
  	"We do not scavenge PICs, hence we cannot cache the MNU method if it is in new space."
  	operand := (methodOperand isNil or: [objectMemory isYoungObject: methodOperand])
  					ifTrue: [0]
  					ifFalse: [methodOperand].
  	"set the jump to the case0 method"
  	backEnd rewriteJumpLongAt: cPIC asInteger + firstCPICCaseOffset target: cPIC asInteger + (self sizeof: CogMethod) .
  
  	backEnd storeLiteral: operand beforeFollowingAddress: cPIC asInteger + firstCPICCaseOffset - backEnd jumpLongByteSize.
  
  	"rewrite the final desperate jump to cePICMissXArgs"
  	backEnd rewriteJumpLongAt: cPIC asInteger + cPICEndOfCodeOffset target: (self cPICMissTrampolineFor: numArgs).	
  
  	"update the loading of the CPIC label address"
  	backEnd relocateMethodReferenceBeforeAddress: cPIC asInteger + cPICEndOfCodeOffset - backEnd jumpLongByteSize by: addrDelta.
  
  	"finally, rewrite the jump 3 instr before firstCPICCaseOffset to jump to the end of case 2, missing the actual case"
  	self rewriteCPIC: cPIC caseJumpTo: (self addressOfEndOfCase: 2 inCPIC: cPIC). 
  
  	^0!

Item was added:
+ ----- Method: Cogit>>genConditionalBranch:operand: (in category 'compile abstract instructions') -----
+ genConditionalBranch: opcode operand: operandOne
+ 	^self previousInstruction noteFollowingConditionalBranch: (self gen: opcode operand: operandOne)!

Item was changed:
  ----- Method: Cogit>>rewriteCPICCaseAt:tag:objRef:target: (in category 'in-line cacheing') -----
  rewriteCPICCaseAt: followingAddress tag: newTag objRef: newObjRef target: newTarget
  	"Rewrite the three values involved in a CPIC case.  Used by the initialize & extend CPICs.
  	 c.f. expectedClosedPICPrototype:"
  
  	"write the obj ref/operand via the second ldr"
  	| classTagPC methodObjPC |
  	methodObjPC := followingAddress - backEnd jumpLongConditionalByteSize - backEnd cmpC32RTempByteSize.
  	backEnd storeLiteral: newObjRef beforeFollowingAddress: methodObjPC.
  
  	classTagPC := followingAddress - backEnd jumpLongConditionalByteSize.
  	"rewite the tag via the first ldr"	
  	backEnd storeLiteral32: newTag beforeFollowingAddress: classTagPC.
  
  	"write the jump address for the new target address"
+ 	backEnd rewriteConditionalJumpLongAt: followingAddress target: newTarget!
- 	backEnd rewriteJumpLongAt: followingAddress target: newTarget!

Item was added:
+ SharedPool subclass: #MIPSConstants
+ 	instanceVariableNames: ''
+ 	classVariableNames: 'A0 A1 A2 A3 ADDIU ADDU AND ANDI AT BEQ BGEZ BGTZ BLEZ BLTZ BNE BREAK DIV FP GP HintLoad HintStore J JAL JALR JR K0 K1 LB LBU LH LHU LUI LW MFHI MFLO MULT OR ORI OneInstruction PREF R0 R1 R10 R11 R12 R13 R14 R15 R16 R17 R18 R19 R2 R20 R21 R22 R23 R24 R25 R26 R27 R28 R29 R3 R30 R31 R4 R5 R6 R7 R8 R9 RA REGIMM S0 S1 S2 S3 S4 S5 S6 S7 SB SH SLL SLLV SLT SLTI SLTIU SLTU SP SPECIAL SRA SRAV SRL SRLV SUBU SW T0 T1 T2 T3 T4 T5 T6 T7 T8 T9 TwoInstructions V0 V1 XOR XORI ZR'
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-JIT'!
+ 
+ !MIPSConstants commentStamp: 'rmacnak 11/11/2015 20:29:59' prior: 0!
+ MIPS opcodes and register names.!

Item was added:
+ ----- Method: MIPSConstants class>>initialize (in category 'as yet unclassified') -----
+ initialize
+ 	super initialize.
+ 	
+ 	OneInstruction := 4.
+ 	TwoInstructions := 8.
+ 	
+ 	HintLoad := 0.
+ 	HintStore := 1.
+ 		
+ 	self initializeRegisters.
+ 	self initializeOpcodes.
+ 	self initializeSpecialFunctions.
+ 	self initializeRegImmRts.!

Item was added:
+ ----- Method: MIPSConstants class>>initializeOpcodes (in category 'as yet unclassified') -----
+ initializeOpcodes
+ 	SPECIAL := 0.
+ 	REGIMM := 1.
+ 	J := 2.
+ 	JAL := 3.
+ 	BEQ := 4.
+ 	BNE := 5.
+ 	BLEZ := 6.
+ 	BGTZ := 7.
+ 	ADDIU := 9.
+ 	SLTI := 10.
+ 	SLTIU := 11.
+ 	ANDI := 12.
+ 	ORI := 13.
+ 	XORI := 14.
+ 	LUI := 15.
+ 	LB := 32.
+ 	LH := 33.
+ 	LW := 35.
+ 	LBU := 36.
+ 	LHU := 37.
+ 	SB := 40.
+ 	SH := 41.
+ 	SW := 43.
+ 	PREF := 51.!

Item was added:
+ ----- Method: MIPSConstants class>>initializeRegImmRts (in category 'as yet unclassified') -----
+ initializeRegImmRts
+ 	BLTZ := 0.
+ 	BGEZ := 1.!

Item was added:
+ ----- Method: MIPSConstants class>>initializeRegisters (in category 'as yet unclassified') -----
+ initializeRegisters
+ 	self flag: #OABI.
+ 	R0 := ZR := 0. "Hardwired zero"
+ 	R1 := AT := 1. "Assembler temp - used to expand psuedo instructions"
+ 	R2 := V0 := 2. "ABI: result register"
+ 	R3 := V1 := 3. "ABI: result register"
+ 	R4 := A0 := 4. "ABI: argument register"
+ 	R5 := A1 := 5. "ABI: argument register"
+ 	R6 := A2 := 6. "ABI: argument register"
+ 	R7 := A3 := 7. "ABI: argument register"
+ 	R8 := T0 := 8. "ABI: volatile"
+ 	R9 := T1 := 9. "ABI: volatile"
+ 	R10 := T2 := 10. "ABI: volatile"
+ 	R11 := T3 := 11. "ABI: volatile"
+ 	R12 := T4 := 12. "ABI: volatile"
+ 	R13 := T5 := 13. "ABI: volatile"
+ 	R14 := T6 := 14. "ABI: volatile"
+ 	R15 := T7 := 15. "ABI: volatile"
+ 	R16 := S0 := 16. "ABI: preserved"
+ 	R17 := S1 := 17. "ABI: preserved"
+ 	R18 := S2 := 18. "ABI: preserved"
+ 	R19 := S3 := 19. "ABI: preserved"
+ 	R20 := S4 := 20. "ABI: preserved"
+ 	R21 := S5 := 21. "ABI: preserved"
+ 	R22 := S6 := 22. "ABI: preserved"
+ 	R23 := S7 := 23. "ABI: preserved"
+ 	R24 := T8 := 24. "ABI: volatile"
+ 	R25 := T9 := 25. "Special use in some position-independent code"
+ 	R26 := K0 := 26. "Reserved for OS"
+ 	R27 := K1 := 27. "Reserved for OS"
+ 	R28 := GP := 28. "Special use in some position-independent code"
+ 	R29 := SP := 29. "Stack pointer"
+ 	R30 := FP := 30. "Frame pointer"
+ 	R31 := RA := 31. "Link register"
+ 
+ 	!

Item was added:
+ ----- Method: MIPSConstants class>>initializeSpecialFunctions (in category 'as yet unclassified') -----
+ initializeSpecialFunctions
+ 	SLL := 0.
+ 	SRL := 2.
+ 	SRA := 3.
+ 	SLLV := 4.
+ 	SRLV := 6.
+ 	SRAV := 7.
+ 	JR := 8.
+ 	JALR := 9.
+ 	BREAK := 13.
+ 	MFHI := 16.
+ 	MFLO := 18.
+ 	MULT := 24.
+ 	DIV := 26.
+ 	ADDU := 33.
+ 	SUBU := 35.
+ 	AND := 36.
+ 	OR := 37.
+ 	XOR := 38.
+ 	SLT := 42.
+ 	SLTU := 43.!

Item was added:
+ ----- Method: MIPSConstants class>>nameForRegister: (in category 'as yet unclassified') -----
+ nameForRegister: registerNumber
+ 	^#(zr at v0 v1 a0 a1 a2 a3
+ 		t0 t1 t2 t3 t4 t5 t6 t7
+ 		s0 s1 s2 s3 s4 s5 s6 s7
+ 		t8 t9 k0 k1 gp sp fp ra) at: registerNumber + 1!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genSpecialSelectorComparison (in category 'bytecode generators') -----
  genSpecialSelectorComparison
  	"Override to count inlined branches if followed by a conditional branch.
  	 We borrow the following conditional branch's counter and when about to
  	 inline the comparison we decrement the counter (without writing it back)
  	 and if it trips simply abort the inlining, falling back to the normal send which
  	 will then continue to the conditional branch which will trip and enter the abort."
  	| nextPC postBranchPC targetBytecodePC primDescriptor branchDescriptor
  	  rcvrIsInt argIsInt argInt jumpNotSmallInts inlineCAB annotateInst
  	  counterAddress countTripped counterReg index |
  	<var: #countTripped type: #'AbstractInstruction *'>
  	<var: #primDescriptor type: #'BytecodeDescriptor *'>
  	<var: #jumpNotSmallInts type: #'AbstractInstruction *'>
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  
  	(coInterpreter isOptimizedMethod: methodObj) ifTrue: [ ^ self genSpecialSelectorComparisonWithoutCounters ].
  
  	self ssFlushTo: simStackPtr - 2.
  	primDescriptor := self generatorAt: byte0.
  	argIsInt := self ssTop type = SSConstant
  				 and: [objectMemory isIntegerObject: (argInt := self ssTop constant)].
  	rcvrIsInt := (self ssValue: 1) type = SSConstant
  				 and: [objectMemory isIntegerObject: (self ssValue: 1) constant].
  
  	"short-cut the jump if operands are SmallInteger constants."
  	(argIsInt and: [rcvrIsInt]) ifTrue:
  		[^ self genStaticallyResolvedSpecialSelectorComparison].
  
  	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
  		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
  	
  	"Only interested in inlining if followed by a conditional branch."
  	inlineCAB := branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse].
  	"Further, only interested in inlining = and ~= if there's a SmallInteger constant involved.
  	 The relational operators successfully statically predict SmallIntegers; the equality operators do not."
  	(inlineCAB and: [primDescriptor opcode = JumpZero or: [primDescriptor opcode = JumpNonZero]]) ifTrue:
  		[inlineCAB := argIsInt or: [rcvrIsInt]].
  	inlineCAB ifFalse:
  		[^self genSpecialSelectorSend].
  
  	argIsInt
  		ifTrue:
  			[(self ssValue: 1) popToReg: ReceiverResultReg.
  			 annotateInst := self ssTop annotateUse.
  			 self ssPop: 2.
  			 self MoveR: ReceiverResultReg R: TempReg]
  		ifFalse:
  			[self marshallSendArguments: 1.
  			 self MoveR: Arg0Reg R: TempReg.
  			 rcvrIsInt ifFalse:
  				[objectRepresentation isSmallIntegerTagNonZero
  					ifTrue: [self AndR: ReceiverResultReg R: TempReg]
  					ifFalse: [self OrR: ReceiverResultReg R: TempReg]]].
  	jumpNotSmallInts := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
  
  	counterReg := self allocateRegNotConflictingWith: (self registerMaskFor: ReceiverResultReg and: Arg0Reg).
  	self 
  		genExecutionCountLogicInto: [ :cAddress :countTripBranch | 
  			counterAddress := cAddress. 
  			countTripped := countTripBranch ] 
  		counterReg: counterReg.
  
  	argIsInt
  		ifTrue: [annotateInst
  					ifTrue: [self annotateBytecode: (self CmpCq: argInt R: ReceiverResultReg)]
  					ifFalse: [self CmpCq: argInt R: ReceiverResultReg]]
  		ifFalse: [self CmpR: Arg0Reg R: ReceiverResultReg].
  	"Cmp is weird/backwards so invert the comparison.  Further since there is a following conditional
  	 jump bytecode define non-merge fixups and leave the cond bytecode to set the mergeness."
+ 	self genConditionalBranch: (branchDescriptor isBranchTrue
- 	self gen: (branchDescriptor isBranchTrue
  				ifTrue: [primDescriptor opcode]
  				ifFalse: [self inverseBranchFor: primDescriptor opcode])
  		operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
  		
  	self genFallsThroughCountLogicCounterReg: counterReg counterAddress: counterAddress.
  	
  	self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC).
  	countTripped jmpTarget: (jumpNotSmallInts jmpTarget: self Label).
  	
  	argIsInt ifTrue:
  		[self MoveCq: argInt R: Arg0Reg].
  	index := byte0 - self firstSpecialSelectorBytecodeOffset.
  	^self genMarshalledSend: index negated - 1 numArgs: 1 sendTable: ordinarySendTrampolines!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genBinaryInlineComparison:opFalse:destReg: (in category 'inline primitive generators') -----
  genBinaryInlineComparison: opTrue opFalse: opFalse destReg: destReg
  	"Inlined comparison. opTrue = jump for true and opFalse = jump for false"
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  	| nextPC branchDescriptor targetBytecodePC postBranchPC |	
  		
  	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
  		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
  	
  	(branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse])
  		ifTrue: "This is the path where the inlined comparison is followed immediately by a branch"
  			[ (self fixupAt: nextPC - initialPC) targetInstruction = 0
  				ifTrue: "The next instruction is dead.  we can skip it."
  					[deadCode := true.
  				 	 self ensureFixupAt: targetBytecodePC - initialPC.
  					 self ensureFixupAt: postBranchPC - initialPC ]
  				ifFalse:
  					[self ssPushConstant: objectMemory trueObject]. "dummy value"
+ 			self genConditionalBranch: (branchDescriptor isBranchTrue ifTrue: [opTrue] ifFalse: [opFalse])
- 			self gen: (branchDescriptor isBranchTrue ifTrue: [opTrue] ifFalse: [opFalse])
  				operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger. 
  			deadCode ifFalse: [ self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC) ] ]
  		ifFalse: "This is the path where the inlined comparison is *not* followed immediately by a branch"
  			[| condJump jump |
+ 			condJump := self genConditionalBranch: opTrue operand: 0.
- 			condJump := self gen: opTrue operand: 0.
  			self genMoveFalseR: destReg.
  	 		jump := self Jump: 0.
  			condJump jmpTarget: (self genMoveTrueR: destReg).
  			jump jmpTarget: self Label].
  	^ 0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSmallIntegerComparison: (in category 'primitive generators') -----
  genSmallIntegerComparison: jumpOpcode
  	| jumpFail jumpTrue |
  	<var: #jumpFail type: #'AbstractInstruction *'>
  	<var: #jumpTrue type: #'AbstractInstruction *'>
  	jumpFail := objectRepresentation genJumpNotSmallInteger: Arg0Reg scratchReg: TempReg.
  	self CmpR: Arg0Reg R: ReceiverResultReg. "N.B. FLAGS := RRReg - Arg0Reg"
+ 	jumpTrue := self genConditionalBranch: jumpOpcode operand: 0.
- 	jumpTrue := self gen: jumpOpcode.
  	self genMoveFalseR: ReceiverResultReg.
  	self RetN: 0.
  	jumpTrue jmpTarget: (self genMoveTrueR: ReceiverResultReg).
  	self RetN: 0.
  	jumpFail jmpTarget: self Label.
  	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genSpecialSelectorComparison (in category 'bytecode generators') -----
  genSpecialSelectorComparison
  	| nextPC postBranchPC targetBytecodePC primDescriptor branchDescriptor
  	  rcvrIsInt argIsInt argInt jumpNotSmallInts inlineCAB annotateInst index |
  	<var: #primDescriptor type: #'BytecodeDescriptor *'>
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  	<var: #jumpNotSmallInts type: #'AbstractInstruction *'>
  	self ssFlushTo: simStackPtr - 2.
  	primDescriptor := self generatorAt: byte0.
  	argIsInt := self ssTop type = SSConstant
  				 and: [objectMemory isIntegerObject: (argInt := self ssTop constant)].
  	rcvrIsInt := (self ssValue: 1) type = SSConstant
  				 and: [objectMemory isIntegerObject: (self ssValue: 1) constant].
  
  	(argIsInt and: [rcvrIsInt]) ifTrue:
  		[^ self genStaticallyResolvedSpecialSelectorComparison].
  
  	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
  		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
  
  	"Only interested in inlining if followed by a conditional branch."
  	inlineCAB := branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse].
  	"Further, only interested in inlining = and ~= if there's a SmallInteger constant involved.
  	 The relational operators successfully statically predict SmallIntegers; the equality operators do not."
  	(inlineCAB and: [primDescriptor opcode = JumpZero or: [primDescriptor opcode = JumpNonZero]]) ifTrue:
  		[inlineCAB := argIsInt or: [rcvrIsInt]].
  	inlineCAB ifFalse:
  		[^self genSpecialSelectorSend].
  
  	argIsInt
  		ifTrue:
  			[(self ssValue: 1) popToReg: ReceiverResultReg.
  			 annotateInst := self ssTop annotateUse.
  			 self ssPop: 2.
  			 self MoveR: ReceiverResultReg R: TempReg]
  		ifFalse:
  			[self marshallSendArguments: 1.
  			 self MoveR: Arg0Reg R: TempReg.
  			 rcvrIsInt ifFalse:
  				[objectRepresentation isSmallIntegerTagNonZero
  					ifTrue: [self AndR: ReceiverResultReg R: TempReg]
  					ifFalse: [self OrR: ReceiverResultReg R: TempReg]]].
  	jumpNotSmallInts := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
  	argIsInt
  		ifTrue: [annotateInst
  					ifTrue: [self annotateBytecode: (self CmpCq: argInt R: ReceiverResultReg)]
  					ifFalse: [self CmpCq: argInt R: ReceiverResultReg]]
  		ifFalse: [self CmpR: Arg0Reg R: ReceiverResultReg].
  	"Cmp is weird/backwards so invert the comparison.  Further since there is a following conditional
  	 jump bytecode define non-merge fixups and leave the cond bytecode to set the mergeness."
+ 	self genConditionalBranch: (branchDescriptor isBranchTrue
- 	self gen: (branchDescriptor isBranchTrue
  				ifTrue: [primDescriptor opcode]
  				ifFalse: [self inverseBranchFor: primDescriptor opcode])
  		operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
  	self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC).
  	jumpNotSmallInts jmpTarget: self Label.
  	argIsInt ifTrue:
  		[self MoveCq: argInt R: Arg0Reg].
  	index := byte0 - self firstSpecialSelectorBytecodeOffset.
  	^self genMarshalledSend: index negated - 1 numArgs: 1 sendTable: ordinarySendTrampolines!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genVanillaSpecialSelectorEqualsEquals (in category 'bytecode generators') -----
  genVanillaSpecialSelectorEqualsEquals
  	| nextPC postBranchPC targetBytecodePC branchDescriptor
  	  rcvrReg argReg argIsConstant rcvrIsConstant  |
  	<var: #branchDescriptor type: #'BytecodeDescriptor *'>
  	
  	self extractMaybeBranchDescriptorInto: [ :descr :next :postBranch :target | 
  		branchDescriptor := descr. nextPC := next. postBranchPC := postBranch. targetBytecodePC := target ].
  	
  	argIsConstant := self ssTop type = SSConstant.
  	"they can't be both constants because we do not have instructions manipulating two constants, 
  	if this is the case, which can happen due to annotable constants that can be moved in memory 
  	with become and therefore can't resolve #== at compilation time, still write the rcvr into a 
  	register as if it was not a constant. It's uncommon anyway."
  	rcvrIsConstant := argIsConstant not and: [(self ssValue: 1) type = SSConstant]. 
  	
  	self 
  		allocateEqualsEqualsRegistersArgNeedsReg: argIsConstant not 
  		rcvrNeedsReg: rcvrIsConstant not 
  		into: [ :rcvr :arg | rcvrReg:= rcvr. argReg := arg ].
  	
  	"If not followed by a branch, resolve to true or false."
  	(branchDescriptor isBranchTrue or: [branchDescriptor isBranchFalse]) ifFalse:
  		[ ^ self genEqualsEqualsNoBranchArgIsConstant: argIsConstant rcvrIsConstant: rcvrIsConstant argReg: argReg rcvrReg: rcvrReg].
  	
  	"If branching the stack must be flushed for the merge"
  	self ssFlushTo: simStackPtr - 2.
  	
  	self genEqualsEqualsComparisonArgIsConstant: argIsConstant rcvrIsConstant: rcvrIsConstant argReg: argReg rcvrReg: rcvrReg.
  	self ssPop: 2.
  
  	"Further since there is a following conditional jump bytecode, define
  	 non-merge fixups and leave the cond bytecode to set the mergeness."
  	(self fixupAt: nextPC - initialPC) targetInstruction = 0
  		ifTrue: "The next instruction is dead.  we can skip it."
  			[deadCode := true.
  		 	 self ensureFixupAt: targetBytecodePC - initialPC.
  			 self ensureFixupAt: postBranchPC - initialPC]
  		ifFalse:
  			[self ssPushConstant: objectMemory trueObject]. "dummy value"
  		
+ 	self genConditionalBranch: (branchDescriptor isBranchTrue ifTrue: [JumpZero] ifFalse: [JumpNonZero])
- 	self gen: (branchDescriptor isBranchTrue ifTrue: [JumpZero] ifFalse: [JumpNonZero])
  		operand: (self ensureNonMergeFixupAt: targetBytecodePC - initialPC) asUnsignedInteger.
  
  	"If the branch is dead, then we can just fall through postBranchPC (only a nop in-between), else 
  	we need to jump over the code of the branch"
  	deadCode ifFalse: [self Jump: (self ensureNonMergeFixupAt: postBranchPC - initialPC)].
  	^0!



More information about the Vm-dev mailing list