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

commits at source.squeak.org commits at source.squeak.org
Tue Nov 24 04:08:53 UTC 2015


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

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

Name: VMMaker.oscog-rmacnak.1532
Author: rmacnak
Time: 23 November 2015, 8:07:29.718 pm
UUID: 20303656-4854-4e5b-8bcd-eeff8cf5d262
Ancestors: VMMaker.oscog-eem.1531

MIPS: Add multiply and divide instructions.

Add some variants of add/sub with overflow checks.

Adjust some CPIC patching for merged CmpC32R/JumpLongZero.

Recast noteFollowingConditionalBranch: as N + M instead of N x M. Fix isJump. Mark concretizeJump<Cond> other than overflow as unreachable.

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

Item was changed:
  CogAbstractInstruction subclass: #CogMIPSELCompiler
  	instanceVariableNames: ''
+ 	classVariableNames: 'AddCheckOverflowCqR AddCheckOverflowRR BrEqualRR BrLongEqualRR BrLongNotEqualRR BrNotEqualRR BrSignedGreaterEqualRR BrSignedGreaterRR BrSignedLessEqualRR BrSignedLessRR BrUnsignedGreaterEqualRR BrUnsignedGreaterRR BrUnsignedLessEqualRR BrUnsignedLessRR BranchTemp Cmp ConcreteVarBaseReg DivRR MoveHighR MoveLowR MulCheckOverflowRR MulRR Overflow OverflowTemp1 OverflowTemp2 SubCheckOverflowCqR SubCheckOverflowRR TargetReg'
- 	classVariableNames: 'AddCheckOverflowCqR AddCheckOverflowRR BrEqCqR BrEqRR BrGtzRR BrLezRR BrNeCqR BrNeRR Cmp CmpSGT CmpSLT CmpUGT CmpULT ConcreteVarBaseReg MulCheckOverflowRR MulRR Overflow OverflowTemp1 OverflowTemp2 SubCheckOverflowCqR SubCheckOverflowRR TargetReg'
  	poolDictionaries: 'MIPSConstants'
  	category: 'VMMaker-JIT'!
+ 
+ !CogMIPSELCompiler commentStamp: 'rmacnak 11/23/2015 19:32:02' prior: 0!
+ Implemenation for 32-bit, little-endian MIPS running with the OABI (Debian port name 'mipsel').!

Item was changed:
  ----- Method: CogMIPSELCompiler class>>initialize (in category 'class initialization') -----
  initialize
+ 	"CogRTLOpcodes initialize. CogMIPSELCompiler initialize"
- 	"CogMIPSELCompiler initialize"
  
  	super initialize.
  	
  	ConcreteVarBaseReg := S6.
  
- 	"Simulating a condition register."
  	Cmp := T0.
+ 
- 	CmpSLT := T1.
- 	CmpSGT := T2.
- 	CmpULT := T3.
- 	CmpUGT := T4.
  	Overflow := T0.
  	OverflowTemp1 := T1.
  	OverflowTemp2 := T2.
+ 	
+ 	"Can't use AT, Cmp or Overflow because we may need to preserve them for sequences like
+ 	 CmpCwR
+ 	 JumpZero
+ 	 JumpBelow"
+ 	BranchTemp := T1.
  
  	"OABI position independent code expects T9 to have its entry point on entry?"
  	self flag: #OABI.
  	TargetReg := T9.
  
  	"Specific instructions"
+ 	self initializeSpecificOpcodes: #(
+ 		MulRR
+ 		DivRR
+ 		MoveLowR
+ 		MoveHighR
+ 		AddCheckOverflowCqR 
+ 		AddCheckOverflowRR
+ 		MulCheckOverflowRR
+ 		SubCheckOverflowCqR
+ 		SubCheckOverflowRR
+ 		BrEqualRR
+ 		BrNotEqualRR 
+ 		BrUnsignedLessRR
+ 		BrUnsignedLessEqualRR
+ 		BrUnsignedGreaterRR
+ 		BrUnsignedGreaterEqualRR
+ 		BrSignedLessRR
+ 		BrSignedLessEqualRR
+ 		BrSignedGreaterRR
+ 		BrSignedGreaterEqualRR
+ 		BrLongEqualRR
+ 		BrLongNotEqualRR) 
+ 			in: thisContext method
+ 		
+ 	!
- 	self
- 		initializeSpecificOpcodes: #(MulRR
- 									AddCheckOverflowCqR AddCheckOverflowRR MulCheckOverflowRR SubCheckOverflowCqR SubCheckOverflowRR
- 									"Ryan, here are proposed opcodes for conditional branches."
- 									BrEqRR BrNeRR BrLezRR BrGtzRR BrEqCqR BrNeCqR)
- 		in: thisContext method!

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

Item was changed:
  ----- Method: CogMIPSELCompiler>>cmpC32RTempByteSize (in category 'accessing') -----
  cmpC32RTempByteSize
+ 	^8!
- 	self flag: #todo. "value - reg or reg - value?"
- 	self flag: #inefficient. "Cog RTL assumes we can do any kind of conditional branch after a Cmp."
- 	^28!

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].
  		"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].
- 		[MoveXbrRR]			-> [^0].
- 		[MoveRXbrR]			-> [^0].
  		[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 added:
+ ----- Method: CogMIPSELCompiler>>concretizeAddCheckOverflowCqR (in category 'generate machine code - concretize') -----
+ concretizeAddCheckOverflowCqR
+ 	| value reg |
+ 	value := operands at: 0.
+ 	reg := self concreteRegister: (operands at: 1).
+ 	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: value)).
+ 	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: value)).
+ 
+ 	"Save original LHS"
+ 	self machineCodeAt: 8 put: (self adduR: OverflowTemp1 R: reg R: ZR). 
+ 	
+ 	"The actual addition"
+ 	self machineCodeAt: 12 put: (self adduR: reg R: reg R: AT). 
+ 
+ 	"Set sign bit of OverflowTemp2 if sign of result differs from sign of RHS."
+ 	self machineCodeAt: 16 put: (self xorR: OverflowTemp2 R: reg R: AT).
+ 	"Set sign bit of OverflowTemp1 if sign of result differs from sign of LHS."
+ 	self machineCodeAt: 20 put: (self xorR: OverflowTemp1 R: reg R: OverflowTemp1).
+ 	"Set sign bit of Overflow if sign of result differs from both LHS and RHS, which indicates overflow."
+ 	self machineCodeAt: 24 put: (self andR: Overflow R: OverflowTemp1 R: OverflowTemp2).
+ 	^machineCodeSize := 28!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeAddCheckOverflowRR (in category 'generate machine code - concretize') -----
+ concretizeAddCheckOverflowRR
+ 	| leftReg rightReg |
+ 	leftReg := self concreteRegister: (operands at: 0).
+ 	rightReg := self concreteRegister: (operands at: 1).
+ 
+ 	"Save original RHS"
+ 	self machineCodeAt: 0 put: (self adduR: OverflowTemp1 R: rightReg R: ZR). 
+ 	
+ 	"The actual addition"
+ 	self machineCodeAt: 4 put: (self adduR: rightReg R: leftReg R: rightReg). 
+ 
+ 	"Set sign bit of OverflowTemp2 if sign of result differs from sign of RHS."
+ 	self machineCodeAt: 8 put: (self xorR: OverflowTemp2 R: rightReg R: leftReg).
+ 	"Set sign bit of OverflowTemp1 if sign of result differs from sign of LHS."
+ 	self machineCodeAt: 12 put: (self xorR: OverflowTemp1 R: rightReg R: OverflowTemp1).
+ 	"Set sign bit of Overflow if sign of result differs from both LHS and RHS, which indicates overflow."
+ 	self machineCodeAt: 16 put: (self andR: Overflow R: OverflowTemp1 R: OverflowTemp2).
+ 	^machineCodeSize := 20!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeAndCwR (in category 'generate machine code - concretize') -----
  concretizeAndCwR
  	| value reg |
  	value := operands at: 0.
  	reg := self concreteRegister: (operands at: 1).
  	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: value)).
  	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: value)).
  	self machineCodeAt: 8 put: (self andR: reg R: reg R: AT).
+ 	^machineCodeSize := 12!
- 	self flag: #inefficient. "Cog RTL assumes we can do any kind of conditional branch after a Cmp."
- 	self machineCodeAt: 12 put: (self andR: Cmp R: reg R: AT).
- 	^machineCodeSize := 16!

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

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeBrEqualRR (in category 'generate machine code - concretize') -----
+ concretizeBrEqualRR
+ 	| offset leftReg rightReg |
+ 	offset := self computeJumpTargetOffsetPlus: 4.
+ 	leftReg := self concreteRegister: (operands at: 1).
+ 	rightReg := self concreteRegister: (operands at: 2).
+ 	self machineCodeAt: 0 put: (self beqR: leftReg R: rightReg offset: offset).
+ 	self machineCodeAt: 4 put: (self nop). "Delay slot"
+ 	^machineCodeSize := 8!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeBrLongEqualRR (in category 'generate machine code - concretize') -----
+ concretizeBrLongEqualRR
+ 	| jumpTarget leftReg rightReg |
+ 	<var: #jumpTarget type: #'AbstractInstruction *'>
+ 	jumpTarget := self longJumpTargetAddress.
+ 	self flag: #todo. "Check not crossing 256MB block."
+ 	jumpTarget := jumpTarget bitAnd: 16rFFFFFFF.
+ 	leftReg := self concreteRegister: (operands at: 1).
+ 	rightReg := self concreteRegister: (operands at: 2).
+ 
+ 	self machineCodeAt: 0 put: (self bneR: leftReg R: rightReg offset: 12).
+ 	self machineCodeAt: 4 put: (self nop). "Delay slot"
+ 	self machineCodeAt: 8 put: (self jA: jumpTarget).
+ 	self machineCodeAt: 12 put: self nop. "Delay slot"
+ 	^machineCodeSize := 16!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeBrLongNotEqualRR (in category 'generate machine code - concretize') -----
+ concretizeBrLongNotEqualRR
+ 	| jumpTarget leftReg rightReg |
+ 	<var: #jumpTarget type: #'AbstractInstruction *'>
+ 	jumpTarget := self longJumpTargetAddress.
+ 	self flag: #todo. "Check not crossing 256MB block."
+ 	jumpTarget := jumpTarget bitAnd: 16rFFFFFFF.
+ 	leftReg := self concreteRegister: (operands at: 1).
+ 	rightReg := self concreteRegister: (operands at: 2).
+ 
+ 	self machineCodeAt: 0 put: (self beqR: leftReg R: rightReg offset: 12).
+ 	self machineCodeAt: 4 put: (self nop). "Delay slot"
+ 	self machineCodeAt: 8 put: (self jA: jumpTarget).
+ 	self machineCodeAt: 12 put: self nop. "Delay slot"
+ 	^machineCodeSize := 16!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeBrNotEqualRR (in category 'generate machine code - concretize') -----
+ concretizeBrNotEqualRR
+ 	| offset leftReg rightReg |
+ 	offset := self computeJumpTargetOffsetPlus: 4.
+ 	leftReg := self concreteRegister: (operands at: 1).
+ 	rightReg := self concreteRegister: (operands at: 2).
+ 	self machineCodeAt: 0 put: (self bneR: leftReg R: rightReg offset: offset).
+ 	self machineCodeAt: 4 put: (self nop). "Delay slot"
+ 	^machineCodeSize := 8!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeBrSignedGreaterEqualRR (in category 'generate machine code - concretize') -----
+ concretizeBrSignedGreaterEqualRR
+ 	| 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: leftReg R: rightReg).
+ 	self machineCodeAt: 4 put: (self beqR: BranchTemp R: ZR offset: offset).
+ 	self machineCodeAt: 8 put: (self nop). "Delay slot"
+ 	^machineCodeSize := 12!

Item was added:
+ ----- 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 beqR: BranchTemp R: ZR offset: offset).
+ 	self machineCodeAt: 8 put: (self nop). "Delay slot"
+ 	^machineCodeSize := 12!

Item was added:
+ ----- 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 bneR: BranchTemp R: ZR offset: offset).
+ 	self machineCodeAt: 8 put: (self nop). "Delay slot"
+ 	^machineCodeSize := 12!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeBrSignedLessRR (in category 'generate machine code - concretize') -----
+ concretizeBrSignedLessRR
+ 	| 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: leftReg R: rightReg).
+ 	self machineCodeAt: 4 put: (self bneR: BranchTemp R: ZR offset: offset).
+ 	self machineCodeAt: 8 put: (self nop). "Delay slot"
+ 	^machineCodeSize := 12!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeBrUnsignedGreaterEqualRR (in category 'generate machine code - concretize') -----
+ concretizeBrUnsignedGreaterEqualRR
+ 	| 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: leftReg R: rightReg).
+ 	self machineCodeAt: 4 put: (self beqR: BranchTemp R: ZR offset: offset).
+ 	self machineCodeAt: 8 put: (self nop). "Delay slot"
+ 	^machineCodeSize := 12!

Item was added:
+ ----- 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 beqR: BranchTemp R: ZR offset: offset).
+ 	self machineCodeAt: 8 put: (self nop). "Delay slot"
+ 	^machineCodeSize := 12!

Item was added:
+ ----- 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 bneR: BranchTemp R: ZR offset: offset).
+ 	self machineCodeAt: 8 put: (self nop). "Delay slot"
+ 	^machineCodeSize := 12!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeBrUnsignedLessRR (in category 'generate machine code - concretize') -----
+ concretizeBrUnsignedLessRR
+ 	| 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: leftReg R: rightReg).
+ 	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>>concretizeCmpCwR (in category 'generate machine code - concretize') -----
  concretizeCmpCwR
+ 	self unreachable. "Should have been rewritten by noteFollowingConditionalBranch:"
+ 	^0!
- 	| value reg |
- 	value := operands at: 0.
- 	reg := self concreteRegister: (operands at: 1).
- 	self flag: #todo. "value - reg or reg - value?"
- 	self flag: #inefficient. "Cog RTL assumes we can do any kind of conditional branch after a Cmp."
- 	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: value)).
- 	self machineCodeAt: 4 put: (self oriR: AT R: AT C: (self low16BitsOf: value)).
- 	self machineCodeAt: 8 put: (self subuR: Cmp R: reg R: AT).
- 	self machineCodeAt: 12 put: (self sltR: CmpSLT R: reg R: AT).
- 	self machineCodeAt: 16 put: (self sltR: CmpSGT R: AT R: reg).
- 	self machineCodeAt: 20 put: (self sltuR: CmpULT R: reg R: AT).
- 	self machineCodeAt: 24 put: (self sltuR: CmpUGT R: AT R: reg).
- 	^machineCodeSize := 28!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeCmpRR (in category 'generate machine code - concretize') -----
  concretizeCmpRR
+ 	self unreachable. "Should have been rewritten by noteFollowingConditionalBranch:"
+ 	^0!
- 	| leftReg rightReg |
- 	"CmpRR RHS LHS computes LHS - RHS, i.e. apparently reversed.  You have to think subtract."
- 	rightReg := self concreteRegister: (operands at: 0).
- 	leftReg := self concreteRegister: (operands at: 1).
- 	self flag: #inefficient. "Cog RTL assumes we can do any kind of conditional branch after a Cmp."
- 	self machineCodeAt: 0 put: (self subuR: Cmp R: leftReg R: rightReg).
- 	self machineCodeAt: 4 put: (self sltR: CmpSLT R: leftReg R: rightReg).
- 	self machineCodeAt: 8 put: (self sltR: CmpSGT R: rightReg R: leftReg).
- 	self machineCodeAt: 12 put: (self sltuR: CmpULT R: leftReg R: rightReg).
- 	self machineCodeAt: 16 put: (self sltuR: CmpUGT R: rightReg R: leftReg).
- 	^machineCodeSize := 20!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeDivRR (in category 'generate machine code - concretize') -----
+ concretizeDivRR
+ 	| dividendReg divisorReg |
+ 	dividendReg := self concreteRegister: (operands at: 0).
+ 	divisorReg := self concreteRegister: (operands at: 1).
+ 	self machineCodeAt: 0 put: (self divR: dividendReg R: divisorReg).
+ 	^machineCodeSize := 4!

Item was added:
+ ----- 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>>concretizeJumpLongNonZero (in category 'generate machine code - concretize') -----
  concretizeJumpLongNonZero
+ 	self unreachable. "Should have been rewritten by noteFollowingConditionalBranch:"
+ 	^0!
- 	| jumpTarget |
- 	<var: #jumpTarget type: #'AbstractInstruction *'>
- 	jumpTarget := self longJumpTargetAddress.
- 	self flag: #todo. "Check not crossing 256MB block."
- 	jumpTarget := jumpTarget bitAnd: 16rFFFFFFF.
- 	self machineCodeAt: 0 put: (self beqR: Cmp R: ZR offset: 12).
- 	self machineCodeAt: 4 put: self nop. "Delay slot"
- 	self machineCodeAt: 8 put: (self jA: jumpTarget).
- 	self machineCodeAt: 12 put: self nop. "Delay slot"
- 	^machineCodeSize := 16!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeJumpLongZero (in category 'generate machine code - concretize') -----
  concretizeJumpLongZero
+ 	self unreachable. "Should have been rewritten by noteFollowingConditionalBranch:"
+ 	^0!
- 	| jumpTarget |
- 	<var: #jumpTarget type: #'AbstractInstruction *'>
- 	jumpTarget := self longJumpTargetAddress.
- 	self flag: #todo. "Check not crossing 256MB block."
- 	jumpTarget := jumpTarget bitAnd: 16rFFFFFFF.
- 	self machineCodeAt: 0 put: (self bneR: Cmp R: ZR offset: 12).
- 	self machineCodeAt: 4 put: self nop. "Delay slot"
- 	self machineCodeAt: 8 put: (self jA: jumpTarget).
- 	self machineCodeAt: 12 put: self nop. "Delay slot"
- 	^machineCodeSize := 16!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeJumpNonZero (in category 'generate machine code - concretize') -----
  concretizeJumpNonZero
+ 	self unreachable. "Should have been rewritten by noteFollowingConditionalBranch:"
+ 	^0!
- 	| offset |
- 	offset := self computeJumpTargetOffsetPlus: 4.
- 	self flag: #BranchRange.
- 	self machineCodeAt: 0 put: (self bneR: Cmp R: ZR offset: offset).
- 	self machineCodeAt: 4 put: self nop. "Delay slot"
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeJumpSignedGreaterEqual (in category 'generate machine code - concretize') -----
  concretizeJumpSignedGreaterEqual
+ 	self unreachable. "Should have been rewritten by noteFollowingConditionalBranch:"
+ 	^0!
- 	| offset |
- 	offset := self computeJumpTargetOffsetPlus: 4.
- 	self machineCodeAt: 0 put: (self bneR: CmpSLT R: ZR offset: offset).
- 	self machineCodeAt: 4 put: (self nop). "Delay slot"
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeJumpSignedGreaterThan (in category 'generate machine code - concretize') -----
  concretizeJumpSignedGreaterThan
+ 	self unreachable. "Should have been rewritten by noteFollowingConditionalBranch:"
+ 	^0!
- 	| offset |
- 	offset := self computeJumpTargetOffsetPlus: 4.
- 	self machineCodeAt: 0 put: (self bneR: CmpSGT R: ZR offset: offset).
- 	self machineCodeAt: 4 put: (self nop). "Delay slot"
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeJumpSignedLessEqual (in category 'generate machine code - concretize') -----
  concretizeJumpSignedLessEqual
+ 	self unreachable. "Should have been rewritten by noteFollowingConditionalBranch:"
+ 	^0!
- 	| offset |
- 	offset := self computeJumpTargetOffsetPlus: 4.
- 	self machineCodeAt: 0 put: (self beqR: CmpSGT R: ZR offset: offset).
- 	self machineCodeAt: 4 put: (self nop). "Delay slot"
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeJumpSignedLessThan (in category 'generate machine code - concretize') -----
  concretizeJumpSignedLessThan
+ 	self unreachable. "Should have been rewritten by noteFollowingConditionalBranch:"
+ 	^0!
- 	| offset |
- 	offset := self computeJumpTargetOffsetPlus: 4.
- 	self machineCodeAt: 0 put: (self bneR: CmpSLT R: ZR offset: offset).
- 	self machineCodeAt: 4 put: (self nop). "Delay slot"
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeJumpUnsignedGreaterEqual (in category 'generate machine code - concretize') -----
  concretizeJumpUnsignedGreaterEqual
+ 	self unreachable. "Should have been rewritten by noteFollowingConditionalBranch:"
+ 	^0!
- 	| offset |
- 	offset := self computeJumpTargetOffsetPlus: 4.
- 	self machineCodeAt: 0 put: (self bneR: CmpULT R: ZR offset: offset).
- 	self machineCodeAt: 4 put: (self nop). "Delay slot"
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeJumpUnsignedGreaterThan (in category 'generate machine code - concretize') -----
  concretizeJumpUnsignedGreaterThan
+ 	self unreachable. "Should have been rewritten by noteFollowingConditionalBranch:"
+ 	^0!
- 	| offset |
- 	offset := self computeJumpTargetOffsetPlus: 4.
- 	self machineCodeAt: 0 put: (self bneR: CmpUGT R: ZR offset: offset).
- 	self machineCodeAt: 4 put: (self nop). "Delay slot"
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeJumpUnsignedLessEqual (in category 'generate machine code - concretize') -----
  concretizeJumpUnsignedLessEqual
+ 	self unreachable. "Should have been rewritten by noteFollowingConditionalBranch:"
+ 	^0!
- 	| offset |
- 	offset := self computeJumpTargetOffsetPlus: 4.
- 	self machineCodeAt: 0 put: (self beqR: CmpUGT R: ZR offset: offset).
- 	self machineCodeAt: 4 put: (self nop). "Delay slot"
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeJumpUnsignedLessThan (in category 'generate machine code - concretize') -----
  concretizeJumpUnsignedLessThan
+ 	self unreachable. "Should have been rewritten by noteFollowingConditionalBranch:"
+ 	^0!
- 	| offset |
- 	offset := self computeJumpTargetOffsetPlus: 4.
- 	self machineCodeAt: 0 put: (self bneR: CmpULT R: ZR offset: offset).
- 	self machineCodeAt: 4 put: (self nop). "Delay slot"
- 	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogMIPSELCompiler>>concretizeJumpZero (in category 'generate machine code - concretize') -----
  concretizeJumpZero
+ 	self unreachable. "Should have been rewritten by noteFollowingConditionalBranch:"
+ 	^0!
- 	| offset |
- 	offset := self computeJumpTargetOffsetPlus: 4.
- 	self flag: #BranchRange.
- 	self machineCodeAt: 0 put: (self beqR: Cmp R: ZR offset: offset).
- 	self machineCodeAt: 4 put: self nop. "Delay slot"
- 	^machineCodeSize := 8!

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

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

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeMoveRXbrR (in category 'generate machine code - concretize') -----
+ concretizeMoveRXbrR
+ 	| srcReg indexReg baseReg |
+ 	srcReg := self concreteRegister: (operands at: 0).
+ 	indexReg := self concreteRegister: (operands at: 1).
+ 	baseReg := self concreteRegister: (operands at: 2).
+ 	self machineCodeAt: 0 put: (self adduR: AT R: baseReg R: indexReg).
+ 	self machineCodeAt: 4 put: (self sbR: srcReg base: AT offset: 0).
+ 	^machineCodeSize := 8!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeMoveXbrRR (in category 'generate machine code - concretize') -----
+ concretizeMoveXbrRR
+ 	| indexReg baseReg destReg |
+ 	indexReg := self concreteRegister: (operands at: 0). "index is number of *bytes*"
+ 	baseReg := self concreteRegister: (operands at: 1).
+ 	destReg := self concreteRegister: (operands at: 2).
+ 	self machineCodeAt: 0 put: (self adduR: AT R: baseReg R: indexReg).
+ 	self machineCodeAt: 4 put: (self lbuR: destReg base: AT offset: 0).
+ 	^machineCodeSize := 8!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeSubCheckOverflowRR (in category 'generate machine code - concretize') -----
+ concretizeSubCheckOverflowRR
+ 	| leftReg rightReg |
+ 	leftReg := self concreteRegister: (operands at: 0).
+ 	rightReg := self concreteRegister: (operands at: 1).
+ 
+ 	"Save original RHS"
+ 	self machineCodeAt: 0 put: (self adduR: OverflowTemp1 R: rightReg R: ZR). 
+ 	
+ 	"The actual subtraction"
+ 	self machineCodeAt: 4 put: (self subuR: rightReg R: leftReg R: rightReg). 
+ 
+ 	"Set sign bit of OverflowTemp2 if sign of result differs from sign of RHS."
+ 	self machineCodeAt: 8 put: (self xorR: OverflowTemp2 R: rightReg R: leftReg).
+ 	"Set sign bit of OverflowTemp1 if sign of result differs from sign of LHS."
+ 	self machineCodeAt: 12 put: (self xorR: OverflowTemp1 R: rightReg R: OverflowTemp1).
+ 	"Set sign bit of Overflow if sign of result differs from both LHS and RHS, which indicates overflow."
+ 	self machineCodeAt: 16 put: (self andR: Overflow R: OverflowTemp1 R: OverflowTemp2).
+ 	^machineCodeSize := 20!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeXorRR (in category 'generate machine code - concretize') -----
+ concretizeXorRR
+ 	| leftReg rightReg |
+ 	leftReg := self concreteRegister: (operands at: 0).
+ 	rightReg := self concreteRegister: (operands at: 1).
+ 	self machineCodeAt: 0 put: (self xorR: 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].
- 		[JumpOverflow]				-> [^self concretizeUnimplemented].
  		[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].
- 		[XorRR]						-> [^self concretizeUnimplemented].
  		[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].
- 		[MoveRMbr]			-> [^self concretizeUnimplemented].
  		[MoveM16rR]		-> [^self concretizeMoveM16rR].
+ 		[MoveM64rRd]		-> [^self concretizeM64rRd].
- 		[MoveM64rRd]		-> [^self concretizeUnimplemented].
  		[MoveMwrR]		-> [^self concretizeMoveMwrR].
+ 		[MoveXbrRR]		-> [^self concretizeMoveXbrRR].
+ 		[MoveRXbrR]		-> [^self concretizeMoveRXbrR].
- 		[MoveXbrRR]		-> [^self concretizeUnimplemented].
- 		[MoveRXbrR]		-> [^self concretizeUnimplemented].
  		[MoveXwrRR]		-> [^self concretizeMoveXwrRR].
  		[MoveRXwrR]		-> [^self concretizeMoveRXwrR].
  		[MoveRMwr]		-> [^self concretizeMoveRMwr].
+ 		[MoveRdM64r]		-> [^self concretizeRdM64r].
- 		[MoveRdM64r]		-> [^self concretizeUnimplemented].
  		[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].
  		"Conversion"
  		[ConvertRRd]		-> [^self concretizeUnimplemented]}!

Item was added:
+ ----- Method: CogMIPSELCompiler>>divR:R: (in category 'encoding - arithmetic') -----
+ divR: dividendReg R: divisorReg
+ 	self flag: #todo. "Ascertain what ISA revision adds this instruction"
+ 	^self rtype: SPECIAL rs: dividendReg rt: divisorReg rd: 0 sa: 0 funct: DIV!

Item was added:
+ ----- Method: CogMIPSELCompiler>>genDivR:R:Quo:Rem: (in category 'abstract instructions') -----
+ genDivR: abstractRegDivisor R: abstractRegDividend Quo: abstractRegQuotient Rem: abstractRegRemainder
+ 	cogit gen: DivRR operand: abstractRegDividend operand: abstractRegDivisor.
+ 	cogit gen: MoveLowR operand: abstractRegQuotient.
+ 	cogit gen: MoveHighR operand: abstractRegRemainder.
+ 	^0!

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

Item was changed:
  ----- Method: CogMIPSELCompiler>>literalBeforeFollowingAddress: (in category 'inline cacheing') -----
  literalBeforeFollowingAddress: followingAddress
  	"Answer the literal embedded in the instruction immediately preceding followingAddress.
  	 This is used in the MoveCwR, PushCwR and CmpCwR cases."
  	
  	"lui/ori, lui/ori/sw/addi, lui/ori/subu/slt/slt/sltu/sltu"
  	
  	| lastOpcode lastFunction oriAddress |
  	lastOpcode := self opcodeAtAddress: followingAddress - 4.
  	lastFunction := self functionAtAddress: followingAddress - 4.
  	oriAddress := 0.
  	lastOpcode = ORI ifTrue: [oriAddress := followingAddress - 4].
  	lastOpcode = ADDIU ifTrue: [oriAddress := followingAddress - 16].
+ 	(lastOpcode = SPECIAL and: [lastFunction = SUBU]) ifTrue: [oriAddress := followingAddress - 8].
- 	(lastOpcode = SPECIAL and: [lastFunction = SLTU]) ifTrue: [oriAddress := followingAddress - 24].
  	self assert: oriAddress ~= 0.
  	^self literalAtAddress: oriAddress
  !

Item was added:
+ ----- Method: CogMIPSELCompiler>>mfhiR: (in category 'encoding - arithmetic') -----
+ mfhiR: destReg
+ 	self flag: #todo. "Ascertain what ISA revision adds this instruction"
+ 	^self rtype: SPECIAL rs: 0 rt: 0 rd: destReg sa: 0 funct: MFHI!

Item was added:
+ ----- Method: CogMIPSELCompiler>>mfloR: (in category 'encoding - arithmetic') -----
+ mfloR: destReg
+ 	self flag: #todo. "Ascertain what ISA revision adds this instruction"
+ 	^self rtype: SPECIAL rs: 0 rt: 0 rd: destReg sa: 0 funct: MFLO!

Item was added:
+ ----- Method: CogMIPSELCompiler>>multR:R: (in category 'encoding - arithmetic') -----
+ multR: leftReg R: rightReg
+ 	self flag: #todo. "Ascertain what ISA revision adds this instruction"
+ 	^self rtype: SPECIAL rs: leftReg rt: rightReg rd: 0 sa: 0 funct: MULT!

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].
+ 	} otherwise: [self unreachable].
+ 	
+ 	opcode caseOf: {
+ 		[BrEqualRR]	->	["I.e., two jumps after a compare."
+ 						newBranchLeft := operands at: 1.
+ 						newBranchRight := operands at: 2].	
+ 		[CmpRR] 	-> 	[newBranchLeft := operands at: 0.
+ 						 newBranchRight := operands at: 1.
+ 						 opcode := Label].
+ 		[CmpCqR]	-> 	[newBranchLeft := AT.
+ 						 newBranchRight := operands at: 1.
+ 						 opcode := MoveCqR.
+ 						 operands at: 1 put: 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].
+ 	} otherwise: [self unreachable].
+ 
+ 	branch rewriteOpcode: newBranchOpcode with: newBranchLeft with: newBranchRight.
- 	branch opcode caseOf: {
- 		[JumpOverflow]		-> [opcode := opcode caseOf: {
- 										[AddCqR]	-> [AddCheckOverflowCqR].
- 										[AddRR]		-> [AddCheckOverflowRR].
- 										[MulRR]		-> [MulCheckOverflowRR].
- 										[SubCqR]	-> [SubCheckOverflowCqR].
- 										[SubRR]		-> [SubCheckOverflowRR].
- 										}].
- 		[JumpNoOverflow]	-> [opcode := opcode caseOf: {
- 										[AddCqR]	-> [AddCheckOverflowCqR].
- 										[AddRR]		-> [AddCheckOverflowRR].
- 										[MulRR]		-> [MulCheckOverflowRR].
- 										[SubCqR]	-> [SubCheckOverflowCqR].
- 										[SubRR]		-> [SubCheckOverflowRR].
- 										}].
- 		"Ryan, I'm imagining that all the other cases go in here, such as collapsing CmpRR; JumpZero to Label; BrEqRR.
- 		 This is obviously not nearly complete."
- 		[JumpZero]			-> [opcode caseOf: {
- 									[CmpRR]	-> [branch setOpcode: BrEqRR andOperandsFrom: self.
- 													branch operands at: 2 put: (operands at: 1).
- 													opcode := Label].
- 								}].
- 		[JumpNonZero]		-> [opcode caseOf: {
- 									[CmpRR]	-> [branch setOpcode: BrNeRR andOperandsFrom: self.
- 													branch operands at: 2 put: (operands at: 1).
- 													opcode := Label].
- 									[CmpCqR]	-> [branch setOpcode: BrNeCqR andOperandsFrom: self.
- 													branch operands at: 2 put: (operands at: 1).
- 													opcode := Label].
- 								}].
- 		[JumpLongZero]		-> [opcode caseOf: {
- 									[CmpRR]	-> [branch setOpcode: BrNeRR andOperandsFrom: self.
- 													"skip the following long branch"
- 													branch operands at: 2 put: self jumpLongByteSize.
- 													opcode := JumpLong].
- 									[CmpCqR]	-> [branch setOpcode: BrNeCqR andOperandsFrom: self.
- 													"skip the following long branch"
- 													branch operands at: 2 put: self jumpLongByteSize.
- 													opcode := JumpLong].
- 								}].
- 		[JumpLongNonZero]	-> [opcode caseOf: {
- 									[CmpRR]	-> [branch setOpcode: BrEqRR andOperandsFrom: self.
- 													"skip the following long branch"
- 													branch operands at: 2 put: self jumpLongByteSize.
- 													opcode := JumpLong].
- 								}].
- 		}
- 		"No otherwise for now to catch all cases"
- 		"otherwise: []".
  	^branch!

Item was changed:
  ----- Method: CogMIPSELCompiler>>rewriteCallAt:target: (in category 'inline cacheing') -----
  rewriteCallAt: callSiteReturnAddress target: callTargetAddress
  	"Rewrite a call instruction to call a different target.  This variant is used to link PICs
  	 in ceSendMiss et al,.   
  	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>
  	
  	"lui t9, stub/targetHigh
  	 ori t9, t9, stub/targetLow
  	 jalr t9
  	 nop (delay slot)
  	 ...  <-- callSiteReturnAddress"
- 
  	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) = JALR.
  	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) = JALR.
  	self assert: (objectMemory longAt: callSiteReturnAddress - 4) = self nop.
  
  	cogit disassembleFrom: callSiteReturnAddress - 16 to: callSiteReturnAddress.
  
  	^20!

Item was added:
+ ----- Method: CogMIPSELCompiler>>rewriteITypeBranchAtAddress:target: (in category 'inline cacheing') -----
+ rewriteITypeBranchAtAddress: mcpc target: newTarget
+ 	| newDisplacement oldInstruction newInstruction |	
+ 	newDisplacement := newTarget - (mcpc - 4). "Displacement relative to delay slot"
+ 	newDisplacement := newDisplacement >> 2.
+ 	
+ 	self assert: (newDisplacement between: -16r8000 and: 16r7FFF).
+ 	newDisplacement < 0
+ 		ifTrue: [newDisplacement := newDisplacement + 16r10000]
+ 		ifFalse: [newDisplacement := newDisplacement].
+ 	self assert: (newDisplacement between: 0 and: 16rFFFF).
+ 
+ 	oldInstruction := objectMemory longAt: mcpc.
+ 	newInstruction := (oldInstruction bitAnd: 16rFFFF0000) bitOr: newDisplacement.
+ 	
+ 	objectMemory longAt: mcpc put: newInstruction.!

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 added:
+ ----- Method: CogMIPSELCompiler>>rewriteOpcode:with:with: (in category 'abstract instructions') -----
+ rewriteOpcode: anOpcode with: left with: right
+ 	<inline: true>
+ 	self assert: anOpcode isInteger.
+ 	self assert: left isInteger.
+ 	self assert: right isInteger.
+ 	
+ 	opcode := anOpcode.
+ 	operands
+ 		"0 is target"
+ 		at: 1 put: left;
+ 		at: 2 put: right!

Item was removed:
- ----- Method: CogMIPSELCompiler>>setOpcode:andOperandsFrom: (in category 'accessing') -----
- setOpcode: anOpcode andOperandsFrom: cmpInstruction
- 	<var: #cmpInstruction type: #'AbstractInstruction *'>
- 	<inline: true>
- 	opcode := anOpcode.
- 	operands
- 		at: 0 put: (cmpInstruction operands at: 0);
- 		at: 1 put: (cmpInstruction operands at: 1)!

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

Item was changed:
  ----- Method: CogMIPSELCompiler>>storeLiteral:beforeFollowingAddress: (in category 'inline cacheing') -----
  storeLiteral: literal beforeFollowingAddress: followingAddress
  	"Rewrite the long constant loaded by a MoveCwR or PushCwR before the given address"
+ 	| lastOpcode lastFunction oriAddress |
- 	| lastOpcode oriAddress |
- 	
  	self flag: #bogus. "The caller ought to know what it is patching, and this should be split into separate methods with stricter checking."
  	
  	lastOpcode := self opcodeAtAddress: followingAddress - 4.
+ 	lastFunction := self functionAtAddress: followingAddress - 4.
  	oriAddress := 0.
  	lastOpcode = ORI ifTrue: [oriAddress := followingAddress - 4].
  	lastOpcode = ADDIU ifTrue: [oriAddress := followingAddress - 16].
+ 	lastOpcode = SPECIAL ifTrue: [lastFunction = SUBU ifTrue: [oriAddress := followingAddress - 8]].
  	self assert: oriAddress ~= 0.
  	^self literalAtAddress: oriAddress put: literal!

Item was changed:
  ----- Method: CogRTLOpcodes class>>printFormatForOpcodeName: (in category 'debug printing') -----
  printFormatForOpcodeName: opcodeName
  	"Answer a sequence of $r or nil for the operands in the opcode, used for printing."
  	| format operands size |
  	format := OrderedCollection new.
  	size := (operands := opcodeName) size.
+ 	(operands startsWith: 'Br') ifTrue: [^' rr'].
  	[#('XwrR' 'X16rR' 'XbrR' 'RR' 'RdR' 'RRd' 'RdRd') do:
  		[:regRegFmt|
  		(operands endsWith: regRegFmt) ifTrue:
  			[format addLast: $r; addLast: $r.
  			 operands := operands allButLast: regRegFmt size]].
  	  #('Mwr' 'M16r' 'Mbr' 'M64r') do:
  		[:constRegFmt|
  		(operands endsWith: constRegFmt) ifTrue:
  			[format addLast: $r; addLast: nil.
  			 operands := operands allButLast: constRegFmt size]].
  	  #('Cq' 'Cw' 'C32' 'C64' 'Aw' 'Ab') do:
  		[:constFmt|
  		(operands endsWith: constFmt) ifTrue:
  			[format addLast: nil.
  			 operands := operands allButLast: constFmt size]].
  	 #('R' 'Rd') do:
  		[:regFmt|
  		(operands endsWith: regFmt) ifTrue:
  			[format addLast: $r.
  			 operands := operands allButLast: regFmt size]].
  	 operands size < size]
  		whileTrue: [size := operands size].
  	^format reverse
  	
  	"classPool keys collect: [:k| { k. (self printFormatForOpcodeName: k) asArray}]"!

Item was removed:
- ----- Method: Cogit>>AddCheckOverflowCq:R: (in category 'abstract instructions') -----
- AddCheckOverflowCq: quickConstant R: reg
- 	<inline: true>
- 	<returnTypeC: #'AbstractInstruction *'>
- 	backEnd hasConditionRegister ifTrue:
- 		[^self AddCq: quickConstant R: reg].
- 	^self gen: AddCheckOverflowCqR quickConstant: quickConstant operand: reg!

Item was removed:
- ----- Method: Cogit>>AddCheckOverflowR:R: (in category 'abstract instructions') -----
- AddCheckOverflowR: reg1 R: reg2
- 	<inline: true>
- 	<returnTypeC: #'AbstractInstruction *'>
- 	backEnd hasConditionRegister ifTrue:
- 		[^self AddR: reg1 R: reg2].
- 	^self gen: AddCheckOverflowRR operand: reg1 operand: reg2!

Item was removed:
- ----- Method: Cogit>>MulCheckOverflowR:R: (in category 'abstract instructions') -----
- MulCheckOverflowR: reg1 R: reg2
- 	"Multiplication is a little weird on some processors.  Defer to the backEnd
- 	 to allow it to generate any special code it may need to."
- 	<returnTypeC: #'AbstractInstruction *'>
- 	<inline: false>
- 	backEnd hasConditionRegister ifTrue:
- 		[^self MulR: reg1 R: reg2].
- 	backEnd genCheckOverflowMulR: reg1 R: reg2.
- 	^self abstractInstructionAt: opcodeIndex - 1!

Item was removed:
- ----- Method: Cogit>>SubCheckOverflowCq:R: (in category 'abstract instructions') -----
- SubCheckOverflowCq: quickConstant R: reg
- 	<inline: true>
- 	<returnTypeC: #'AbstractInstruction *'>
- 	backEnd hasConditionRegister ifTrue:
- 		[^self SubCq: quickConstant R: reg].
- 	^self gen: SubCheckOverflowCqR quickConstant: quickConstant operand: reg!

Item was removed:
- ----- Method: Cogit>>SubCheckOverflowR:R: (in category 'abstract instructions') -----
- SubCheckOverflowR: reg1 R: reg2
- 	<inline: true>
- 	<returnTypeC: #'AbstractInstruction *'>
- 	backEnd hasConditionRegister ifTrue:
- 		[^self SubR: reg1 R: reg2].
- 	^self gen: SubCheckOverflowRR operand: reg1 operand: reg2!



More information about the Vm-dev mailing list