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

commits at source.squeak.org commits at source.squeak.org
Thu Nov 12 04:51:33 UTC 2015


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

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

Name: VMMaker.oscog-rmacnak.1514
Author: rmacnak
Time: 11 November 2015, 8:50:09.071 pm
UUID: 8504ecc7-5b6f-42d1-90de-3176997a24f7
Ancestors: VMMaker.oscog-tpr.1513

Initial commit of MIPSEL backend.

=============== Diff against VMMaker.oscog-tpr.1513 ===============

Item was added:
+ CogAbstractInstruction subclass: #CogMIPSELCompiler
+ 	instanceVariableNames: ''
+ 	classVariableNames: 'Cmp CmpSGT CmpSLT CmpUGT CmpULT ConcreteVarBaseReg TargetReg'
+ 	poolDictionaries: 'MIPSConstants'
+ 	category: 'VMMaker-JIT'!

Item was added:
+ ----- Method: CogMIPSELCompiler class>>ISA (in category 'as yet unclassified') -----
+ ISA
+ 	^#MIPSEL!

Item was added:
+ ----- Method: CogMIPSELCompiler class>>initialize (in category 'as yet unclassified') -----
+ initialize
+ 	"CogMIPSELCompiler initialize"
+ 
+ 	super initialize.
+ 	
+ 	ConcreteVarBaseReg := S6.
+ 
+ 	"Simulating a condition register."
+ 	Cmp := T0.
+ 	CmpSLT := T1.
+ 	CmpSGT := T2.
+ 	CmpULT := T3.
+ 	CmpUGT := T4.
+ 
+ 	"OABI position independent code expects T9 to have its entry point on entry?"
+ 	self flag: #OABI.
+ 	TargetReg := T9. !

Item was added:
+ ----- Method: CogMIPSELCompiler>>addiuR:R:C: (in category 'encoding - arithmetic') -----
+ addiuR: destReg R: srcReg C: imm
+ 	^self itype: ADDIU rs: srcReg rt: destReg signedImmediate: imm!

Item was added:
+ ----- Method: CogMIPSELCompiler>>adduR:R:R: (in category 'encoding - arithmetic') -----
+ adduR: destReg R: leftReg R: rightReg
+ 	^self rtype: SPECIAL rs: leftReg rt: rightReg rd: destReg sa: 0 funct: ADDU!

Item was added:
+ ----- Method: CogMIPSELCompiler>>andR:R:R: (in category 'encoding - arithmetic') -----
+ andR: destReg R: leftReg R: rightReg
+ 	^self rtype: SPECIAL rs: leftReg rt: rightReg rd: destReg sa: 0 funct: AND!

Item was added:
+ ----- Method: CogMIPSELCompiler>>andiR:R:C: (in category 'encoding - arithmetic') -----
+ andiR: destReg R: srcReg C: imm
+ 	^self itype: ANDI rs: srcReg rt: destReg eitherImmediate: imm!

Item was added:
+ ----- Method: CogMIPSELCompiler>>beqR:R:offset: (in category 'encoding - control') -----
+ beqR: leftReg R: rightReg offset: offset
+ 	self assert: (offset bitAnd: 3) = 0.
+ 	self assert: (offset between: -16r20000 and: 16r1FFFF).
+ 	^self itype: BEQ rs: leftReg rt: rightReg signedImmediate: offset >> 2!

Item was added:
+ ----- Method: CogMIPSELCompiler>>bgezR:offset: (in category 'encoding - control') -----
+ bgezR: cmpReg offset: offset
+ 	self assert: (offset bitAnd: 3) = 0.
+ 	self assert: (offset between: -16r20000 and: 16r1FFFF).
+ 	^self itype: REGIMM rs: cmpReg rt: BGEZ signedImmediate: offset >> 2!

Item was added:
+ ----- Method: CogMIPSELCompiler>>bgtzR:offset: (in category 'encoding - control') -----
+ bgtzR: cmpReg offset: offset
+ 	self assert: (offset bitAnd: 3) = 0.
+ 	self assert: (offset between: -16r20000 and: 16r1FFFF).
+ 	^self itype: BGTZ rs: cmpReg rt: 0 signedImmediate: offset >> 2!

Item was added:
+ ----- Method: CogMIPSELCompiler>>blezR:offset: (in category 'encoding - control') -----
+ blezR: cmpReg offset: offset
+ 	self assert: (offset bitAnd: 3) = 0.
+ 	self assert: (offset between: -16r20000 and: 16r1FFFF).
+ 	^self itype: BLEZ rs: cmpReg rt: 0 signedImmediate: offset >> 2!

Item was added:
+ ----- Method: CogMIPSELCompiler>>bltzR:offset: (in category 'encoding - control') -----
+ bltzR: cmpReg offset: offset
+ 	self assert: (offset bitAnd: 3) = 0.
+ 	self assert: (offset between: -16r20000 and: 16r1FFFF).
+ 	^self itype: REGIMM rs: cmpReg rt: BLTZ signedImmediate: offset >> 2!

Item was added:
+ ----- Method: CogMIPSELCompiler>>bneR:R:offset: (in category 'encoding - control') -----
+ bneR: leftReg R: rightReg offset: offset
+ 	self assert: (offset bitAnd: 3) = 0.
+ 	self assert: (offset between: -16r20000 and: 16r1FFFF).
+ 	^self itype: BNE rs: leftReg rt: rightReg signedImmediate: offset >> 2!

Item was added:
+ ----- Method: CogMIPSELCompiler>>break: (in category 'encoding - control') -----
+ break: code
+ 	self assert: (code between: 0 and: 16rFFFFF).
+ 	^(code << 6) bitOr: BREAK!

Item was added:
+ ----- Method: CogMIPSELCompiler>>cResultRegister (in category 'generate machine code') -----
+ cResultRegister
+ 	"Answer the abstract register for the C result register."
+ 	^V0!

Item was added:
+ ----- Method: CogMIPSELCompiler>>callInstructionByteSize (in category 'accessing') -----
+ callInstructionByteSize
+ 	self flag: #todo. "Which call opcode does this want the size of?"
+ 	^16!

Item was added:
+ ----- Method: CogMIPSELCompiler>>callerSavedRegisterMask (in category 'accessing') -----
+ callerSavedRegisterMask
+ 	"See MIPSConstants initializeRegisters."
+ 	| mask |
+ 	self flag: #OABI.
+ 	mask := 0.
+ 	mask := mask bitOr: 1 << S0.
+ 	mask := mask bitOr: 1 << S1.
+ 	mask := mask bitOr: 1 << S2.
+ 	mask := mask bitOr: 1 << S3.
+ 	mask := mask bitOr: 1 << S4.
+ 	mask := mask bitOr: 1 << S5.
+ 	mask := mask bitOr: 1 << S6.
+ 	mask := mask bitOr: 1 << S7.
+ 	^mask!

Item was added:
+ ----- Method: CogMIPSELCompiler>>codeGranularity (in category 'accessing') -----
+ codeGranularity
+ 	"Answer the size in bytes of a unit of machine code."
+ 	<inline: true>
+ 	^4!

Item was added:
+ ----- 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: {
+ 		"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]
+ 									-> [^self rotateable8bitImmediate: (operands at: 0)
+ 											ifTrue: [:r :i| 4]
+ 											ifFalse: [self literalLoadInstructionBytes + 4]].
+ 
+ 		[LogicalShiftLeftCqR]		-> [^4].
+ 		[LogicalShiftRightCqR]		-> [^4].
+ 		[ArithmeticShiftRightCqR]	-> [^4].
+ 		[LogicalShiftLeftRR]			-> [^4].
+ 		[LogicalShiftRightRR]		-> [^4].
+ 		[ArithmeticShiftRightRR]		-> [^4].
+ 		[AddRdRd]					-> [^4].
+ 		[CmpRdRd]					-> [^4].
+ 		[SubRdRd]					-> [^4].
+ 		[MulRdRd]					-> [^4].
+ 		[DivRdRd]					-> [^4].
+ 		[SqrtRd]					-> [^4].
+ 		"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]].
+ 		[MoveRMwr]			-> [^16].
+ 		[MoveRdM64r]			-> [^self literalLoadInstructionBytes + 4]. 
+ 		[MoveMbrR]				-> [^16].
+ 		[MoveRMbr]				-> [^16].
+ 		[MoveM16rR]			-> [^4].
+ 		[MoveM64rRd]			-> [^self literalLoadInstructionBytes + 4].
+ 		[MoveMwrR]			-> [^16].
+ 		[MoveXbrRR]			-> [^0].
+ 		[MoveRXbrR]			-> [^0].
+ 		[MoveXwrRR]			-> [^12].
+ 		[MoveRXwrR]			-> [^12].
+ 		[PopR]					-> [^8].
+ 		[PushR]					-> [^8].
+ 		[PushCw]				-> [^16].
+ 		[PushCq]				-> [^16].
+ 		[PrefetchAw] 			-> [^(self isAddressRelativeToVarBase: (operands at: 0))
+ 										ifTrue: [4]
+ 										ifFalse: [self literalLoadInstructionBytes + 4]].
+ 		"Conversion"
+ 		[ConvertRRd]			-> [^8].
+ 		}.
+ 	^0 "to keep C compiler quiet"
+ !

Item was added:
+ ----- Method: CogMIPSELCompiler>>concreteRegister: (in category 'encoding') -----
+ concreteRegister: registerIndex
+ 	"Map a possibly abstract register into a concrete one.  Abstract registers
+ 	 (defined in CogAbstractOpcodes) are all negative.  If registerIndex is
+ 	 negative assume it is an abstract register."
+ 	
+ 	"See MIPSConstants>>initializeRegisters for a description of the C ABI."
+ 
+ 	"Note we can fit all of the abstract registers in C preserved registers, and
+ 	 not need to save or restore them at runtime calls."
+ 	
+ 	^registerIndex
+ 		caseOf: {
+ 			[ReceiverResultReg]	-> [S0].
+ 			[Arg0Reg]				-> [S1].
+ 			[Arg1Reg]				-> [S2].
+ 			[ClassReg]				-> [S3].
+ 			[SendNumArgsReg]		-> [S4].
+ 			[TempReg]				-> [S5].
+ 			[VarBaseReg]			-> [S6]. "Must be callee saved"
+ 			[SPReg]					-> [SP].
+ 			[FPReg]					-> [FP].
+ 			[RISCTempReg]			-> [AT].
+ 			[LinkReg]				-> [RA]. }
+ 		otherwise:
+ 			[self assert: (registerIndex between: R0 and: R31).
+ 			 registerIndex]!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeAddCqR (in category 'generate machine code - concretize') -----
+ concretizeAddCqR
+ 	^self concretizeAddCwR!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeAddCwR (in category 'generate machine code - concretize') -----
+ concretizeAddCwR
+ 	| val reg |
+ 	val := operands at: 0.
+ 	reg := self concreteRegister: (operands at: 1).
+ 	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: val)).
+ 	self machineCodeAt: 4 put: (self oriR: AT R: ZR C: (self low16BitsOf: val)).
+ 	self machineCodeAt: 8 put: (self adduR: reg R: reg R: AT).
+ 	^machineCodeSize := 12!

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

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeAlignmentNops (in category 'generate machine code - concretize') -----
+ concretizeAlignmentNops
+ 	self assert: machineCodeSize \\ 4 = 0.
+ 	0 to: machineCodeSize - 1 by: 4 do:
+ 		[:p | self machineCodeAt: p put: self nop]!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeAndCqR (in category 'generate machine code - concretize') -----
+ concretizeAndCqR
+ 	^self concretizeAndCwR!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeAndCqRR (in category 'generate machine code - concretize') -----
+ concretizeAndCqRR
+ 	| value srcReg dstReg |
+ 	value := operands at: 0.
+ 	srcReg := self concreteRegister: (operands at: 1).
+ 	dstReg := self concreteRegister: (operands at: 2).
+ 	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: value)).
+ 	self machineCodeAt: 4 put: (self oriR: AT R: ZR C: (self low16BitsOf: value)).
+ 	self machineCodeAt: 8 put: (self andR: dstReg R: srcReg R: AT).
+ 	^machineCodeSize := 12!

Item was added:
+ ----- 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: ZR C: (self low16BitsOf: value)).
+ 	self machineCodeAt: 8 put: (self andR: reg R: reg R: AT).
+ 	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>>concretizeArithmeticShiftRightCqR (in category 'generate machine code - concretize') -----
+ concretizeArithmeticShiftRightCqR
+ 	| distance reg |
+ 	distance := (operands at: 0) min: 31.
+ 	reg := self concreteRegister: (operands at: 1).
+ 	self machineCodeAt: 0 put: (self sraR: reg R: reg C: distance).
+ 	^machineCodeSize := 4!

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

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeAt: (in category 'generate machine code') -----
+ concretizeAt: actualAddress
+ 	"Generate concrete machine code for the instruction at actualAddress,
+ 	 setting machineCodeSize, and answer the following address."
+ 
+ 	self assert: actualAddress \\ 4 = 0.
+ 	^super concretizeAt: actualAddress!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeCall (in category 'generate machine code - concretize') -----
+ concretizeCall
+ 	"Call is used only for calls within code-space, See CallFull for general anywhere in address space calling"
+ 	"Relative branches in MIPS have a displacement of +/- 131kB (signed 18 bits), which is too small to cover
+ 	 the method zone."
+ 	^self concretizeCallFull!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeCallFull (in category 'generate machine code - concretize') -----
+ concretizeCallFull
+ 	| jumpTarget |
+ 	<var: #jumpTarget type: #'AbstractInstruction *'>
+ 	jumpTarget := self longJumpTargetAddress.
+ 	self machineCodeAt: 0 put: (self luiR: TargetReg C: (self high16BitsOf: jumpTarget)).
+ 	self machineCodeAt: 4 put: (self oriR: TargetReg R: ZR C: (self low16BitsOf: jumpTarget)).	
+ 	self machineCodeAt: 8 put: (self jalR: TargetReg).
+ 	self machineCodeAt: 12 put: self nop. "Delay slot"
+ 	^machineCodeSize := 16!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeCmpCqR (in category 'generate machine code - concretize') -----
+ concretizeCmpCqR
+ 	^self concretizeCmpCwR!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeCmpCwR (in category 'generate machine code - concretize') -----
+ concretizeCmpCwR
+ 	| 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: ZR 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 added:
+ ----- Method: CogMIPSELCompiler>>concretizeCmpRR (in category 'generate machine code - concretize') -----
+ concretizeCmpRR
+ 	| 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>>concretizeJump (in category 'generate machine code - concretize') -----
+ concretizeJump
+ 	| offset |
+ 	offset := self computeJumpTargetOffsetPlus: 8.
+ 	self flag: #BranchRange.
+ 	self machineCodeAt: 0 put: (self beqR: ZR R: ZR offset: offset).
+ 	self machineCodeAt: 4 put: self nop. "Delay slot"
+ 	^machineCodeSize := 8!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeJumpFull (in category 'generate machine code - concretize') -----
+ concretizeJumpFull
+ 	| jumpTarget |
+ 	<var: #jumpTarget type: #'AbstractInstruction *'>
+ 	jumpTarget := self longJumpTargetAddress.
+ 	self machineCodeAt: 0 put: (self luiR: TargetReg C: (self high16BitsOf: jumpTarget)).
+ 	self machineCodeAt: 4 put: (self oriR: TargetReg R: ZR C: (self low16BitsOf: jumpTarget)).	
+ 	self machineCodeAt: 8 put: (self jR: TargetReg).
+ 	self machineCodeAt: 12 put: self nop. "Delay slot"
+ 	^machineCodeSize := 16!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeJumpLong (in category 'generate machine code - concretize') -----
+ concretizeJumpLong
+ 	^self concretizeJumpFull!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeJumpLongNonZero (in category 'generate machine code - concretize') -----
+ concretizeJumpLongNonZero
+ 	| 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 added:
+ ----- Method: CogMIPSELCompiler>>concretizeJumpLongZero (in category 'generate machine code - concretize') -----
+ concretizeJumpLongZero
+ 	| 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 added:
+ ----- Method: CogMIPSELCompiler>>concretizeJumpNonZero (in category 'generate machine code - concretize') -----
+ concretizeJumpNonZero
+ 	| offset |
+ 	offset := self computeJumpTargetOffsetPlus: 12.
+ 	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 added:
+ ----- Method: CogMIPSELCompiler>>concretizeJumpR (in category 'generate machine code - concretize') -----
+ concretizeJumpR
+ 	| reg |
+ 	self flag: #OABI. "Does this ever target C code? If so we should move the target into TargetReg first."
+ 	reg := self concreteRegister: (operands at: 0).
+ 	self machineCodeAt: 0 put: (self jR: reg).
+ 	self machineCodeAt: 4 put: self nop. "Delay slot"
+ 	^machineCodeSize := 8!

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

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

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

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

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

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

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

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

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeJumpZero (in category 'generate machine code - concretize') -----
+ concretizeJumpZero
+ 	| offset |
+ 	offset := self computeJumpTargetOffsetPlus: 12.
+ 	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>>concretizeLogicalShiftLeftCqR (in category 'generate machine code - concretize') -----
+ concretizeLogicalShiftLeftCqR
+ 	| distance reg |
+ 	distance := (operands at: 0) min: 31.
+ 	reg := self concreteRegister: (operands at: 1).
+ 	self machineCodeAt: 0 put: (self sllR: reg R: reg C: distance).
+ 	^machineCodeSize := 4!

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

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeLogicalShiftRightCqR (in category 'generate machine code - concretize') -----
+ concretizeLogicalShiftRightCqR
+ 	| distance reg |
+ 	distance := (operands at: 0) min: 31.
+ 	reg := self concreteRegister: (operands at: 1).
+ 	self machineCodeAt: 0 put: (self srlR: reg R: reg C: distance).
+ 	^machineCodeSize := 4!

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

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeMoveAwR (in category 'generate machine code - concretize') -----
+ concretizeMoveAwR
+ 	| srcAddr destReg |
+ 	srcAddr := operands at: 0.
+ 	destReg := self concreteRegister: (operands at: 1).
+ 
+ 	(self isAddressRelativeToVarBase: srcAddr) ifTrue:
+ 		[self machineCodeAt: 0 put: (self lwR: destReg base: ConcreteVarBaseReg offset: srcAddr - cogit varBaseAddress).
+ 		 ^machineCodeSize := 4].
+ 
+ 	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: srcAddr)).
+ 	self machineCodeAt: 4 put: (self oriR: AT R: ZR C: (self low16BitsOf: srcAddr)).
+ 	self machineCodeAt: 8 put: (self lwR: destReg base: AT offset: 0).
+ 	^machineCodeSize := 12!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeMoveCqR (in category 'generate machine code - concretize') -----
+ concretizeMoveCqR
+ 	<var: #word type: #sqInt>
+ 	| word reg |
+ 	word := operands at: 0.
+ 	reg := self concreteRegister: (operands at: 1).
+ 	
+ 	(word between: -16r8000 and: 16r7FFF) ifFalse: [^self concretizeMoveCwR].
+ 	"Could also load up to 16rFFFF with ori or 16rXXXX0000 with lui"
+ 	
+ 	self machineCodeAt: 0 put: (self addiuR: reg R: ZR C: word).
+ 	^machineCodeSize := 4!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeMoveCwR (in category 'generate machine code - concretize') -----
+ concretizeMoveCwR
+ 	<var: #word type: #sqInt>
+ 	| word reg |
+ 	word := operands at: 0.
+ 	reg := self concreteRegister: (operands at: 1).	
+ 	self machineCodeAt: 0 put: (self luiR: reg C: (self high16BitsOf: word)).
+ 	self machineCodeAt: 4 put: (self oriR: reg R: ZR C: (self low16BitsOf: word)).
+ 	^machineCodeSize := 8!

Item was added:
+ ----- 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 lhR: destReg base: srcReg offset: offset).
+ 	^machineCodeSize := 4!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeMoveMbrR (in category 'generate machine code - concretize') -----
+ concretizeMoveMbrR
+ 	<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 lbuR: destReg base: srcReg offset: offset).
+ 	^machineCodeSize := 4
+ 	!

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

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeMoveRAw (in category 'generate machine code - concretize') -----
+ concretizeMoveRAw
+ 	| srcReg destAddr |
+ 	srcReg := self concreteRegister: (operands at: 0).
+ 	destAddr := operands at: 1.
+ 
+ 	(self isAddressRelativeToVarBase: destAddr) ifTrue:
+ 		[self machineCodeAt: 0 put: (self swR: srcReg base: ConcreteVarBaseReg offset: destAddr - cogit varBaseAddress).
+ 		 ^machineCodeSize := 4].
+ 
+ 	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: destAddr)).
+ 	self machineCodeAt: 4 put: (self oriR: AT R: ZR C: (self low16BitsOf: destAddr)).
+ 	self machineCodeAt: 8 put: (self swR: srcReg base: AT offset: 0).
+ 	^machineCodeSize := 12!

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

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

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeMoveRXwrR (in category 'generate machine code - concretize') -----
+ concretizeMoveRXwrR
+ 	| 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 sllR: AT R: indexReg C: 2). "index is number of words"
+ 	self machineCodeAt: 4 put: (self adduR: AT R: baseReg R: AT).
+ 	self machineCodeAt: 8 put: (self swR: srcReg base: AT offset: 0).
+ 	^machineCodeSize := 12!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeMoveXwrRR (in category 'generate machine code - concretize') -----
+ concretizeMoveXwrRR
+ 	| indexReg baseReg destReg |
+ 	indexReg := self concreteRegister: (operands at: 0).
+ 	baseReg := self concreteRegister: (operands at: 1).
+ 	destReg := self concreteRegister: (operands at: 2).
+ 	self machineCodeAt: 0 put: (self sllR: AT R: indexReg C: 2). "index is in words"
+ 	self machineCodeAt: 4 put: (self adduR: AT R: baseReg R: AT).
+ 	self machineCodeAt: 8 put: (self lwR: destReg base: baseReg offset: 0).
+ 	^machineCodeSize := 12!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeNop (in category 'generate machine code - concretize') -----
+ concretizeNop
+ 	self machineCodeAt: 0 put: self nop.
+ 	^machineCodeSize := 4!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeOrCqR (in category 'generate machine code - concretize') -----
+ concretizeOrCqR
+ 	^self concretizeOrCwR!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeOrCwR (in category 'generate machine code - concretize') -----
+ concretizeOrCwR
+ 	| 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: ZR C: (self low16BitsOf: value)).
+ 	self machineCodeAt: 8 put: (self orR: reg R: reg R: AT).
+ 	^machineCodeSize := 12!

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

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizePopR (in category 'generate machine code - concretize') -----
+ concretizePopR
+ 	| destReg |
+ 	destReg := self concreteRegister: (operands at: 0).
+ 	self machineCodeAt: 0 put: (self lwR: destReg base: SP offset: 0).
+ 	self machineCodeAt: 4 put: (self addiuR: SP R: SP C: 4).
+ 	^machineCodeSize := 8!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizePushR (in category 'generate machine code - concretize') -----
+ concretizePushR
+ 	| srcReg |
+ 	srcReg := self concreteRegister: (operands at: 0).
+ 	self machineCodeAt: 0 put: (self addiuR: SP R: SP C: -4).
+ 	self machineCodeAt: 4 put: (self swR: srcReg base: SP offset: 0).
+ 	^machineCodeSize := 8!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeRetN (in category 'generate machine code - concretize') -----
+ concretizeRetN
+ 	<var: #offset type: #sqInt>
+ 	| offset |
+ 	offset := operands at: 0.
+ 	self machineCodeAt: 0 put: (self jR: RA).
+ 	offset = 0 
+ 		ifTrue: [self machineCodeAt: 4 put: self nop "Delay slot"]
+ 		ifFalse: [self machineCodeAt: 4 put: (self addiuR: SP R: SP C: offset) "We actually get to fill a delay slot!!"].
+ 	^machineCodeSize := 8!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeStop (in category 'generate machine code - concretize') -----
+ concretizeStop
+ 	self machineCodeAt: 0 put: self stop.
+ 	^machineCodeSize := 4!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeSubCqR (in category 'generate machine code - concretize') -----
+ concretizeSubCqR
+ 	^self concretizeSubCwR!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeSubCwR (in category 'generate machine code - concretize') -----
+ concretizeSubCwR
+ 	| 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: ZR C: (self low16BitsOf: value)).
+ 	self machineCodeAt: 8 put: (self subuR: reg R: reg R: AT).
+ 	^machineCodeSize := 12!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeSubRR (in category 'generate machine code - concretize') -----
+ concretizeSubRR
+ 	| leftReg 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 added:
+ ----- Method: CogMIPSELCompiler>>concretizeTstCqR (in category 'generate machine code - concretize') -----
+ concretizeTstCqR
+ 	^self concretizeTstCwR!

Item was added:
+ ----- Method: CogMIPSELCompiler>>concretizeTstCwR (in category 'generate machine code - concretize') -----
+ concretizeTstCwR
+ 	| val reg |
+ 	val := operands at: 0.
+ 	reg := self concreteRegister: (operands at: 1).
+ 	self machineCodeAt: 0 put: (self luiR: AT C: (self high16BitsOf: val)).
+ 	self machineCodeAt: 4 put: (self oriR: AT R: ZR C: (self low16BitsOf: val)).
+ 	self machineCodeAt: 8 put: (self andR: Cmp R: reg R: AT).
+ 	^machineCodeSize := 12!

Item was added:
+ ----- 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: {
+ 		"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 concretizeUnimplemented].
+ 		[JumpNoOverflow]			-> [^self concretizeUnimplemented].
+ 		[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 concretizeUnimplemented].
+ 		[AddRdRd]					-> [^self concretizeUnimplemented].
+ 		[CmpRdRd]					-> [^self concretizeUnimplemented].
+ 		[DivRdRd]					-> [^self concretizeUnimplemented].
+ 		[MulRdRd]					-> [^self concretizeUnimplemented].
+ 		[SubRdRd]					-> [^self concretizeUnimplemented].
+ 		[SqrtRd]					-> [^self concretizeUnimplemented].
+ 		[NegateR]						-> [^self concretizeNegateR].
+ 		[LoadEffectiveAddressMwrR]	-> [^self concretizeUnimplemented].
+ 		[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].
+ 		[MoveMbrR]			-> [^self concretizeMoveMbrR].
+ 		[MoveRMbr]			-> [^self concretizeUnimplemented].
+ 		[MoveM16rR]		-> [^self concretizeMoveM16rR].
+ 		[MoveM64rRd]		-> [^self concretizeUnimplemented].
+ 		[MoveMwrR]		-> [^self concretizeMoveMwrR].
+ 		[MoveXbrRR]		-> [^self concretizeUnimplemented].
+ 		[MoveRXbrR]		-> [^self concretizeUnimplemented].
+ 		[MoveXwrRR]		-> [^self concretizeMoveXwrRR].
+ 		[MoveRXwrR]		-> [^self concretizeMoveRXwrR].
+ 		[MoveRMwr]		-> [^self concretizeMoveRMwr].
+ 		[MoveRdM64r]		-> [^self concretizeUnimplemented].
+ 		[PopR]				-> [^self concretizePopR].
+ 		[PushR]				-> [^self concretizePushR].
+ 		[PushCq]			-> [^self concretizeUnimplemented].
+ 		[PushCw]			-> [^self concretizeUnimplemented].
+ 		[PrefetchAw]		-> [^self concretizeUnimplemented].
+ 		"Conversion"
+ 		[ConvertRRd]		-> [^self concretizeUnimplemented]}!

Item was added:
+ ----- Method: CogMIPSELCompiler>>fullCallsAreRelative (in category 'abi') -----
+ fullCallsAreRelative
+ 	"Answer if CallFull and/or JumpFull are relative and hence need relocating on method
+ 	 compation. If so, they are annotated with IsRelativeCall in methods and relocated in
+ 	 relocateIfCallOrMethodReference:mcpc:delta:"
+ 	^false!

Item was added:
+ ----- Method: CogMIPSELCompiler>>functionAtAddress: (in category 'inline cacheing') -----
+ functionAtAddress: mcpc
+ 	^(objectMemory longAt: mcpc) bitAnd: 63
+ !

Item was added:
+ ----- Method: CogMIPSELCompiler>>genGetLeafCallStackPointerFunction (in category 'assertions') -----
+ genGetLeafCallStackPointerFunction
+ 	cogit MoveR: SP R: V0.
+ 	cogit RetN: 0!

Item was added:
+ ----- Method: CogMIPSELCompiler>>genLoadCStackPointers (in category 'smalltalk calling convention') -----
+ genLoadCStackPointers
+ 	"Load the frame and stack pointer registers with those of the C stack,
+ 	 effecting a switch to the C stack.  Used when machine code calls into
+ 	 the CoInterpreter run-time (e.g. to invoke interpreter primitives)."
+ 	cogit MoveAw: cogit cStackPointerAddress R: SPReg.
+ 	cogit MoveAw: cogit cFramePointerAddress R: FPReg.
+ 	^0!

Item was added:
+ ----- Method: CogMIPSELCompiler>>genLoadStackPointers (in category 'smalltalk calling convention') -----
+ genLoadStackPointers
+ 	"Switch back to the Smalltalk stack. Assign SPReg first
+ 	 because typically it is used immediately afterwards."
+ 	cogit MoveAw: cogit stackPointerAddress R: SPReg.
+ 	cogit MoveAw: cogit framePointerAddress R: FPReg.
+ 	^0!

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

Item was added:
+ ----- Method: CogMIPSELCompiler>>genPushRegisterArgsForAbortMissNumArgs: (in category 'smalltalk calling convention') -----
+ genPushRegisterArgsForAbortMissNumArgs: numArgs
+ 	"Ensure that the register args are pushed before the outer and
+ 	 inner retpcs at an entry miss for arity <= self numRegArgs.  The
+ 	 outer retpc is that of a call at a send site.  The inner is the call
+ 	 from a method or PIC abort/miss to the trampoline."
+ 
+ 	"Putting the receiver and args above the return address means the
+ 	 CoInterpreter has a single machine-code frame format which saves
+ 	 us a lot of work."
+ 
+ 	"Iff there are register args convert
+ 		sp		->	outerRetpc			(send site retpc)
+ 		linkReg = innerRetpc			(PIC abort/miss retpc)
+ 	 to
+ 		base	->	receiver
+ 					(arg0)
+ 					(arg1)
+ 		sp		->	outerRetpc			(send site retpc)
+ 		sp		->	linkReg/innerRetpc	(PIC abort/miss retpc)"
+ 						
+ 	self flag: #inefficient. "Update SP once."
+ 	
+ 	numArgs <= cogit numRegArgs ifTrue:
+ 		[self assert: cogit numRegArgs <= 2.
+ 		 cogit MoveMw: 0 r: SPReg R: TempReg. "Save return address"
+ 		 cogit MoveR: ReceiverResultReg Mw: 0 r: SPReg.
+ 		 numArgs > 0 ifTrue:
+ 			[cogit PushR: Arg0Reg.
+ 			 numArgs > 1 ifTrue:
+ 				[cogit PushR: Arg1Reg]].
+ 		cogit PushR: TempReg]. "push back return address"
+ 	cogit PushR: LinkReg!

Item was added:
+ ----- Method: CogMIPSELCompiler>>genPushRegisterArgsForNumArgs:scratchReg: (in category 'smalltalk calling convention') -----
+ genPushRegisterArgsForNumArgs: numArgs scratchReg: ignored
+ 	"Ensure that the register args are pushed before the retpc for arity <= self numRegArgs."
+ 	"This is easy on a RISC like ARM because the return address is in the link register.  Putting
+ 	 the receiver and args above the return address means the CoInterpreter has a single
+ 	 machine-code frame format which saves us a lot of work
+ 	NOTA BENE: we do NOT push the return address here, which means it must be dealt with later."
+ 	self flag: #inefficient. "Update SP once."
+ 	numArgs <= cogit numRegArgs ifTrue:
+ 		[self assert: cogit numRegArgs <= 2.
+ 		 cogit PushR: ReceiverResultReg.
+ 		numArgs > 0 ifTrue:
+ 			[cogit PushR: Arg0Reg.
+ 			 numArgs > 1 ifTrue:
+ 				[cogit PushR: Arg1Reg]]]!

Item was added:
+ ----- Method: CogMIPSELCompiler>>genRemoveNArgsFromStack: (in category 'abi') -----
+ genRemoveNArgsFromStack: n
+ 	"This is a no-op on MIPS since the ABI passes up to 4 args in registers and trampolines currently observe that limit."
+ 	self assert: n <= 4.
+ 	^0!

Item was added:
+ ----- Method: CogMIPSELCompiler>>genRestoreRegs (in category 'abi') -----
+ genRestoreRegs
+ 	"This method is poorly named. Is this for a Smalltalk -> C call or C -> Smalltalk call?
+ 	 If the former we don't need to do anything because all of the abstract registers are
+ 	 allocated to C preserved registers."
+ 	self flag: #bogus.!

Item was added:
+ ----- Method: CogMIPSELCompiler>>genSaveRegisters (in category 'abi') -----
+ genSaveRegisters
+ 	"This method is poorly named. Is this for a Smalltalk -> C call or C -> Smalltalk call?
+ 	 If the former we don't need to do anything because all of the abstract registers are
+ 	 allocated to C preserved registers."
+ 	self flag: #bogus.!

Item was added:
+ ----- Method: CogMIPSELCompiler>>genSaveStackPointers (in category 'smalltalk calling convention') -----
+ genSaveStackPointers
+ 	"Save the frame and stack pointer registers to the framePointer
+ 	 and stackPointer variables.  Used to save the machine code frame
+ 	 for use by the run-time when calling into the CoInterpreter run-time."
+ 	cogit MoveR: FPReg Aw: cogit framePointerAddress.
+ 	cogit MoveR: SPReg Aw: cogit stackPointerAddress.
+ 	^0!

Item was added:
+ ----- Method: CogMIPSELCompiler>>hasLinkRegister (in category 'testing') -----
+ hasLinkRegister
+ 	^true "RA"!

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

Item was added:
+ ----- Method: CogMIPSELCompiler>>high16BitsOf: (in category 'encoding') -----
+ high16BitsOf: word
+ 	^word >> 16!

Item was added:
+ ----- Method: CogMIPSELCompiler>>initialize (in category 'generate machine code') -----
+ initialize
+ 	"This method intializes the Smalltalk instance.  The C instance is merely a struct and doesn't need initialization."
+ 	<doNotGenerate>
+ 	operands := CArrayAccessor on: (Array new: NumOperands).
+ 	machineCode := CArrayAccessor on: (Array new: self machineCodeWords)!

Item was added:
+ ----- Method: CogMIPSELCompiler>>isAddressRelativeToVarBase: (in category 'testing') -----
+ isAddressRelativeToVarBase: varAddress
+ 	<inline: true>
+ 	<var: #varAddress type: #usqInt>
+ 	"Support for addressing variables off the dedicated VarBaseReg"
+ 	^varAddress notNil
+ 	  and: [(cogit varBaseAddress - (1 << 15)) < varAddress
+ 	  and: [varAddress < (cogit varBaseAddress + (1 << 15))]]!

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

Item was added:
+ ----- Method: CogMIPSELCompiler>>isPCDependent (in category 'testing') -----
+ isPCDependent
+ 	"Answer if the receiver is a pc-dependent instruction."
+ 	^self isJump or: [opcode = AlignmentNops]!

Item was added:
+ ----- Method: CogMIPSELCompiler>>itype:rs:rt:eitherImmediate: (in category 'encoding') -----
+ itype: opcode rs: rs rt: rt eitherImmediate: signedImmediate	
+ 	| unsignedImmediate |
+ 	self assert: (opcode between: 0 and: 63).
+ 	self assert: (rs between: 0 and: 31).
+ 	self assert: (rt between: 0 and: 31).
+ 	signedImmediate < 0
+ 		ifTrue: [unsignedImmediate := signedImmediate + 16r10000]
+ 		ifFalse: [unsignedImmediate := signedImmediate].
+ 	self assert: (unsignedImmediate between: 0 and: 16rFFFF).
+ 	^(((opcode << 26) bitOr: (rs << 21)) bitOr: (rt << 16)) bitOr: unsignedImmediate!

Item was added:
+ ----- Method: CogMIPSELCompiler>>itype:rs:rt:signedImmediate: (in category 'encoding') -----
+ itype: opcode rs: rs rt: rt signedImmediate: signedImmediate	
+ 	| unsignedImmediate |
+ 	self assert: (opcode between: 0 and: 63).
+ 	self assert: (rs between: 0 and: 31).
+ 	self assert: (rt between: 0 and: 31).
+ 	self assert: (signedImmediate between: -16r8000 and: 16r7FFF).
+ 	signedImmediate < 0
+ 		ifTrue: [unsignedImmediate := signedImmediate + 16r10000]
+ 		ifFalse: [unsignedImmediate := signedImmediate].
+ 	self assert: (unsignedImmediate between: 0 and: 16rFFFF).
+ 	^(((opcode << 26) bitOr: (rs << 21)) bitOr: (rt << 16)) bitOr: unsignedImmediate!

Item was added:
+ ----- Method: CogMIPSELCompiler>>itype:rs:rt:unsignedImmediate: (in category 'encoding') -----
+ itype: opcode rs: rs rt: rt unsignedImmediate: immediate	
+ 	self assert: (opcode between: 0 and: 63).
+ 	self assert: (rs between: 0 and: 31).
+ 	self assert: (rt between: 0 and: 31).
+ 	self assert: (immediate between: 0 and: 16rFFFF).
+ 	^(((opcode << 26) bitOr: (rs << 21)) bitOr: (rt << 16)) bitOr: immediate!

Item was added:
+ ----- Method: CogMIPSELCompiler>>jA: (in category 'encoding - control') -----
+ jA: target
+ 	self assert: (target bitAnd: 3) = 0.
+ 	^self jtype: J target: (target bitAnd: 16r0FFFFFFF) >> 2!

Item was added:
+ ----- Method: CogMIPSELCompiler>>jR: (in category 'encoding - control') -----
+ jR: targetReg
+ 	^self rtype: SPECIAL rs: targetReg rt: 0 rd: 0 sa: 0 funct: JR.!

Item was added:
+ ----- Method: CogMIPSELCompiler>>jalA: (in category 'encoding - control') -----
+ jalA: target
+ 	self assert: (target bitAnd: 3) = 0.
+ 	^self jtype: JAL target: (target bitAnd: 16r0FFFFFFF) >> 2!

Item was added:
+ ----- Method: CogMIPSELCompiler>>jalR: (in category 'encoding - control') -----
+ jalR: targetReg
+ 	^self rtype: SPECIAL rs: targetReg rt: 0 rd: RA sa: 0 funct: JALR.!

Item was added:
+ ----- Method: CogMIPSELCompiler>>jtype:target: (in category 'encoding') -----
+ jtype: opcode target: target
+ 	self assert: (opcode between: 0 and: 63).
+ 	self assert: (opcode between: 0 and: 16r7FFFFFF).
+ 	^(opcode << 26) bitOr: target!

Item was added:
+ ----- Method: CogMIPSELCompiler>>jumpLongByteSize (in category 'accessing') -----
+ jumpLongByteSize
+ 	self flag: #bogus. "Caller seems to actually want jumpFullByteSize"
+ 	^16!

Item was added:
+ ----- Method: CogMIPSELCompiler>>jumpLongConditionalByteSize (in category 'inline cacheing') -----
+ jumpLongConditionalByteSize
+ 	^16!

Item was added:
+ ----- Method: CogMIPSELCompiler>>jumpLongTargetBeforeFollowingAddress: (in category 'inline cacheing') -----
+ jumpLongTargetBeforeFollowingAddress: mcpc 
+ 	"Answer the target address for the long jump immediately preceding mcpc"
+ 	self assert: (objectMemory longAt: mcpc - 4) == self nop. "Delay slot"
+ 	self assert: (self opcodeAtAddress: mcpc - 8) == SPECIAL.
+ 	self assert: (self functionAtAddress: mcpc - 8) == JR.
+ 	^self literalAtAddress: mcpc - 12
+ 	!

Item was added:
+ ----- Method: CogMIPSELCompiler>>lbR:base:offset: (in category 'encoding - memory') -----
+ lbR: destReg base: baseReg offset: offset
+ 	^self itype: LB rs: baseReg rt: destReg signedImmediate: offset!

Item was added:
+ ----- Method: CogMIPSELCompiler>>lbuR:base:offset: (in category 'encoding - memory') -----
+ lbuR: destReg base: baseReg offset: offset
+ 	^self itype: LBU rs: baseReg rt: destReg signedImmediate: offset!

Item was added:
+ ----- Method: CogMIPSELCompiler>>leafCallStackPointerDelta (in category 'abi') -----
+ leafCallStackPointerDelta
+ 	"Answer the delta from the stack pointer after a call to the stack pointer
+ 	 immediately prior to the call.  This is used to compute the stack pointer
+ 	 immediately prior to  call from within a leaf routine, which in turn is used
+ 	 to capture the c stack pointer to use in trampolines back into the C run-time."
+ 	"This might actually be false, since directly after a call, lr, fp and variable registers need be pushed onto the stack. It depends on the implementation of call."
+ 	^0!

Item was added:
+ ----- Method: CogMIPSELCompiler>>lhR:base:offset: (in category 'encoding - memory') -----
+ lhR: destReg base: baseReg offset: offset
+ 	^self itype: LH rs: baseReg rt: destReg signedImmediate: offset!

Item was added:
+ ----- Method: CogMIPSELCompiler>>lhuR:base:offset: (in category 'encoding - memory') -----
+ lhuR: destReg base: baseReg offset: offset
+ 	^self itype: LHU rs: baseReg rt: destReg signedImmediate: offset!

Item was added:
+ ----- Method: CogMIPSELCompiler>>literalAtAddress: (in category 'inline cacheing') -----
+ literalAtAddress: mcpc
+ 	| high low |
+ 	self assert: (self opcodeAtAddress: mcpc) = ORI.
+ 	self assert: (self opcodeAtAddress: mcpc - 4) = LUI.
+ 	low := (objectMemory longAt: mcpc) bitAnd: 16rFFFF.
+ 	high := (objectMemory longAt: mcpc - 4) bitAnd: 16rFFFF.
+ 	^high << 16 bitOr: low
+ !

Item was added:
+ ----- 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"
+ 	
+ 	| lastInstruction lastOpcode lastFunction oriAddress |
+ 	lastInstruction := objectMemory longAt: followingAddress - 4.
+ 	lastOpcode := lastInstruction >> 26.
+ 	lastFunction := lastInstruction bitAnd: 63.
+ 	oriAddress := 0.
+ 	lastOpcode = ORI ifTrue: [oriAddress := followingAddress - 4].
+ 	lastOpcode = ADDIU ifTrue: [oriAddress := followingAddress - 16].
+ 	(lastOpcode = SPECIAL and: [lastFunction = SLTU]) ifTrue: [oriAddress := followingAddress - 24].
+ 	self assert: oriAddress ~= 0.
+ 	^self literalAtAddress: oriAddress
+ !

Item was added:
+ ----- Method: CogMIPSELCompiler>>literalLoadInstructionBytes (in category 'testing') -----
+ literalLoadInstructionBytes
+ 	"Answer the size of a literal load instruction (which may or may not include the size of the literal).
+ 	 This differs between in-line and out-of-line literal generation."
+ 	<inline: true>
+ 	^8!

Item was added:
+ ----- Method: CogMIPSELCompiler>>loadLiteralByteSize (in category 'accessing') -----
+ loadLiteralByteSize
+ 	^8!

Item was added:
+ ----- Method: CogMIPSELCompiler>>low16BitsOf: (in category 'encoding') -----
+ low16BitsOf: word
+ 	^word bitAnd: 16rFFFF!

Item was added:
+ ----- Method: CogMIPSELCompiler>>luiR:C: (in category 'encoding - arithmetic') -----
+ luiR: destReg C: imm
+ 	^self itype: LUI rs: 0 rt: destReg eitherImmediate: imm!

Item was added:
+ ----- Method: CogMIPSELCompiler>>lwR:base:offset: (in category 'encoding - memory') -----
+ lwR: destReg base: baseReg offset: offset
+ 	^self itype: LW rs: baseReg rt: destReg signedImmediate: offset!

Item was added:
+ ----- Method: CogMIPSELCompiler>>machineCodeAt: (in category 'accessing') -----
+ machineCodeAt: anOffset
+ 	"read aWord from machineCode, with little endian"
+ 	<inline: true>
+ 	^machineCode at: anOffset // 4!

Item was added:
+ ----- Method: CogMIPSELCompiler>>machineCodeAt:put: (in category 'accessing') -----
+ machineCodeAt: anOffset put: aWord
+ 	"add aWord to machineCode, with little endian"
+ 	<inline: true>
+ 	machineCode at: anOffset // 4 put: aWord!

Item was added:
+ ----- Method: CogMIPSELCompiler>>machineCodeWords (in category 'generate machine code') -----
+ machineCodeWords
+ 	"Answer the maximum number of words of machine code generated for any abstract instruction.
+ 	 e.g. CmpCwR =>
+ 			mov R3, #<addressByte1>, 12
+ 			orr R3, R3, #<addressByte2>, 8
+ 			orr R3, R3, #<addressByte3>, 4
+ 			orr R3, R3, #<addressByte4>, 0
+ 			cmp R?, R3"
+ 	^7!

Item was added:
+ ----- Method: CogMIPSELCompiler>>maxAbstractGeneralPurposeReg (in category 'accessing') -----
+ maxAbstractGeneralPurposeReg
+ 	"Answer the largest index of an abstract general-purpose register used by this compiler.
+ 	 N.B.  Abstract registers are negative numbers."
+ 	<inline: true>
+ 	self flag: #bogus. "The caller should ask for a register mask, not a range."
+ 	^TempReg!

Item was added:
+ ----- Method: CogMIPSELCompiler>>maybeEstablishVarBase (in category 'abstract instructions') -----
+ maybeEstablishVarBase
+ 	"The receiver has a VarBaseReg; generate the code to set it to its value."
+ 	cogit MoveCq: cogit varBaseAddress R: VarBaseReg!

Item was added:
+ ----- Method: CogMIPSELCompiler>>minAbstractGeneralPurposeReg (in category 'accessing') -----
+ minAbstractGeneralPurposeReg
+ 	"Answer the smallest index of an abstract general-purpose register used by this compiler.
+ 	 N.B.  Abstract registers are negative numbers."
+ 	<inline: true>
+ 	self flag: #bogus. "The caller should ask for a register mask, not a range."
+ 	^TempReg!

Item was added:
+ ----- Method: CogMIPSELCompiler>>nameForRegister: (in category 'printing') -----
+ nameForRegister: reg "<Integer>"
+ 	<doNotGenerate>
+ 	reg < 0 ifTrue: [^super nameForRegister: reg].
+ 	^MIPSConstants nameForRegister: reg!

Item was added:
+ ----- Method: CogMIPSELCompiler>>nop (in category 'encoding - arithmetic') -----
+ nop
+ 	^0 "SLL ZR, ZR, 0"!

Item was added:
+ ----- Method: CogMIPSELCompiler>>nopsFrom:to: (in category 'generate machine code') -----
+ nopsFrom: startAddr to: endAddr
+ 	self assert: endAddr - startAddr + 1 \\ 4 = 0.
+ 	self assert: (self nop = 0).
+ 	startAddr to: endAddr do: [:p| objectMemory byteAt: p put: 0].!

Item was added:
+ ----- Method: CogMIPSELCompiler>>numIntRegArgs (in category 'abi') -----
+ numIntRegArgs
+ 	self flag: #OABI.
+ 	^4!

Item was added:
+ ----- Method: CogMIPSELCompiler>>numberOfSaveableRegisters (in category 'abi') -----
+ numberOfSaveableRegisters
+ 	"Answer the number of registers to be saved in a trampoline call that saves registers.
+ 	 None, See genSaveRegisters."
+ 	<cmacro: '(self) 0'>
+ 	^0!

Item was added:
+ ----- Method: CogMIPSELCompiler>>opcodeAtAddress: (in category 'inline cacheing') -----
+ opcodeAtAddress: mcpc
+ 	^(objectMemory longAt: mcpc) >> 26
+ !

Item was added:
+ ----- Method: CogMIPSELCompiler>>orR:R:R: (in category 'encoding - arithmetic') -----
+ orR: destReg R: leftReg R: rightReg
+ 	^self rtype: SPECIAL rs: leftReg rt: rightReg rd: destReg sa: 0 funct: OR!

Item was added:
+ ----- Method: CogMIPSELCompiler>>oriR:R:C: (in category 'encoding - arithmetic') -----
+ oriR: destReg R: srcReg C: imm
+ 	^self itype: ORI rs: srcReg rt: destReg eitherImmediate: imm!

Item was added:
+ ----- Method: CogMIPSELCompiler>>outputMachineCodeAt: (in category 'generate machine code') -----
+ outputMachineCodeAt: targetAddress
+ 	"Override to move machine code a word at a time."
+ 	<inline: true>
+ 	0 to: machineCodeSize - 1 by: 4 do:
+ 		[:j|
+ 		objectMemory longAt: targetAddress + j put: (machineCode at: j // 4)]!

Item was added:
+ ----- Method: CogMIPSELCompiler>>pushLinkRegisterByteSize (in category 'accessing') -----
+ pushLinkRegisterByteSize
+ 	^8!

Item was added:
+ ----- Method: CogMIPSELCompiler>>rtype:rs:rt:rd:sa:funct: (in category 'encoding') -----
+ rtype: opcode rs: rs rt: rt rd: rd sa: sa funct: funct
+ 	self assert: (opcode between: 0 and: 63).
+ 	self assert: (rs between: 0 and: 31).
+ 	self assert: (rt between: 0 and: 31).
+ 	self assert: (rd between: 0 and: 31).
+ 	self assert: (sa between: 0 and: 15).
+ 	self assert: (funct between: 0 and: 63).
+ 	^(((((opcode << 26) bitOr: (rs << 21)) bitOr: (rt << 16)) bitOr: (rd << 11)) bitOr: (sa << 6)) bitOr: funct!

Item was added:
+ ----- Method: CogMIPSELCompiler>>saveAndRestoreLinkRegAround: (in category 'abi') -----
+ saveAndRestoreLinkRegAround: aBlock
+ 	"If the processor's ABI includes a link register, generate instructions
+ 	 to save and restore it around aBlock, which is assumed to generate code."
+ 	<inline: true>
+ 	| inst |
+ 	inst := cogit PushR: LinkReg.
+ 	aBlock value.
+ 	cogit PopR: LinkReg.
+ 	^inst!

Item was added:
+ ----- Method: CogMIPSELCompiler>>sbR:base:offset: (in category 'encoding - memory') -----
+ sbR: srcReg base: baseReg offset: offset
+ 	^self itype: SB rs: baseReg rt: srcReg signedImmediate: offset!

Item was added:
+ ----- Method: CogMIPSELCompiler>>shR:base:offset: (in category 'encoding - memory') -----
+ shR: srcReg base: baseReg offset: offset
+ 	^self itype: SH rs: baseReg rt: srcReg signedImmediate: offset!

Item was added:
+ ----- Method: CogMIPSELCompiler>>sizePCDependentInstructionAt: (in category 'generate machine code') -----
+ sizePCDependentInstructionAt: eventualAbsoluteAddress
+ 	"Size a jump and set its address.  The target may be another instruction
+ 	 or an absolute address.  On entry the address inst var holds our virtual
+ 	 address. On exit address is set to eventualAbsoluteAddress, which is
+ 	 where this instruction will be output.  The span of a jump to a following
+ 	 instruction is therefore between that instruction's address and this
+ 	 instruction's address ((which are both still their virtual addresses), but the
+ 	 span of a jump to a preceding instruction or to an absolute address is
+ 	 between that instruction's address (which by now is its eventual absolute
+ 	 address) or absolute address and eventualAbsoluteAddress.
+ 
+ 	 ARM is simple; the 26-bit call/jump range means no short jumps.  This routine
+ 	 only has to determine the targets of jumps, not determine sizes."
+ 
+ 	opcode = AlignmentNops ifTrue:
+ 		[| alignment |
+ 		 address := eventualAbsoluteAddress.
+ 		 alignment := operands at: 0.
+ 		 ^machineCodeSize := (eventualAbsoluteAddress + (alignment - 1) bitAnd: alignment negated)
+ 							   - eventualAbsoluteAddress].
+ 	self assert: (self isJump or: [opcode = Call or: [opcode = CallFull]]).
+ 	self isJump ifTrue: [self resolveJumpTarget].
+ 	address := eventualAbsoluteAddress.
+ 	^machineCodeSize := maxSize!

Item was added:
+ ----- Method: CogMIPSELCompiler>>sllR:R:C: (in category 'encoding - arithmetic') -----
+ sllR: destReg R: sourceReg C: shiftAmount
+ 	^self rtype: SPECIAL rs: 0 rt: sourceReg rd: destReg sa: shiftAmount funct: SLL!

Item was added:
+ ----- Method: CogMIPSELCompiler>>sllvR:R:R: (in category 'encoding - arithmetic') -----
+ sllvR: destReg R: leftReg R: rightReg
+ 	^self rtype: SPECIAL rs: rightReg rt: leftReg rd: destReg sa: 0 funct: SLLV!

Item was added:
+ ----- Method: CogMIPSELCompiler>>sltR:R:R: (in category 'encoding - arithmetic') -----
+ sltR: destReg R: leftReg R: rightReg
+ 	^self rtype: SPECIAL rs: leftReg rt: rightReg rd: destReg sa: 0 funct: SLT!

Item was added:
+ ----- Method: CogMIPSELCompiler>>sltiR:R:C: (in category 'encoding - arithmetic') -----
+ sltiR: destReg R: leftReg C: imm
+ 	^self itype: SLTI rs: leftReg rt: destReg signedImmediate: imm!

Item was added:
+ ----- Method: CogMIPSELCompiler>>sltiuR:R:C: (in category 'encoding - arithmetic') -----
+ sltiuR: destReg R: leftReg C: imm
+ 	^self itype: SLTIU rs: leftReg rt: destReg signedImmediate: imm!

Item was added:
+ ----- Method: CogMIPSELCompiler>>sltuR:R:R: (in category 'encoding - arithmetic') -----
+ sltuR: destReg R: leftReg R: rightReg
+ 	^self rtype: SPECIAL rs: leftReg rt: rightReg rd: destReg sa: 0 funct: SLTU!

Item was added:
+ ----- Method: CogMIPSELCompiler>>sraR:R:C: (in category 'encoding - arithmetic') -----
+ sraR: destReg R: sourceReg C: shiftAmount
+ 	^self rtype: SPECIAL rs: 0 rt: sourceReg rd: destReg sa: shiftAmount funct: SRA!

Item was added:
+ ----- Method: CogMIPSELCompiler>>sravR:R:R: (in category 'encoding - arithmetic') -----
+ sravR: destReg R: leftReg R: rightReg
+ 	^self rtype: SPECIAL rs: rightReg rt: leftReg rd: destReg sa: 0 funct: SRAV!

Item was added:
+ ----- Method: CogMIPSELCompiler>>srlR:R:C: (in category 'encoding - arithmetic') -----
+ srlR: destReg R: sourceReg C: shiftAmount
+ 	^self rtype: SPECIAL rs: 0 rt: sourceReg rd: destReg sa: shiftAmount funct: SRL!

Item was added:
+ ----- Method: CogMIPSELCompiler>>srlvR:R:R: (in category 'encoding - arithmetic') -----
+ srlvR: destReg R: leftReg R: rightReg
+ 	^self rtype: SPECIAL rs: rightReg rt: leftReg rd: destReg sa: 0 funct: SRLV!

Item was added:
+ ----- Method: CogMIPSELCompiler>>stop (in category 'encoding - control') -----
+ stop
+ 	^self break: 0!

Item was added:
+ ----- Method: CogMIPSELCompiler>>subuR:R:R: (in category 'encoding - arithmetic') -----
+ subuR: destReg R: leftReg R: rightReg
+ 	^self rtype: SPECIAL rs: leftReg rt: rightReg rd: destReg sa: 0 funct: SUBU!

Item was added:
+ ----- Method: CogMIPSELCompiler>>swR:base:offset: (in category 'encoding - memory') -----
+ swR: srcReg base: baseReg offset: offset
+ 	^self itype: SW rs: baseReg rt: srcReg signedImmediate: offset!

Item was added:
+ ----- Method: CogMIPSELCompiler>>xorR:R:R: (in category 'encoding - arithmetic') -----
+ xorR: destReg R: leftReg R: rightReg
+ 	^self rtype: SPECIAL rs: leftReg rt: rightReg rd: destReg sa: 0 funct: XOR!

Item was added:
+ ----- Method: CogMIPSELCompiler>>xoriR:R:C: (in category 'encoding - arithmetic') -----
+ xoriR: destReg R: srcReg C: imm
+ 	^self itype: XORI rs: srcReg rt: destReg eitherImmediate: imm!

Item was added:
+ ----- Method: CogX64Compiler class>>ISA (in category 'translation') -----
+ ISA
+ 	^#X64!

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

Item was changed:
  ----- Method: Cogit>>compileTrampolineFor:numArgs:arg:arg:arg:arg:saveRegs:pushLinkReg:resultReg: (in category 'initialization') -----
  compileTrampolineFor: aRoutine numArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3 saveRegs: saveRegs pushLinkReg: pushLinkReg resultReg: resultRegOrNil
  	"Generate a trampoline with up to four arguments.  Generate either a call or a jump to aRoutine
  	 as requested by callJumpBar.  If generating a call and resultRegOrNil is non-zero pass the C result
  	 back in resultRegOrNil.
  	 Hack: a negative value indicates an abstract register, a non-negative value indicates a constant."
  	<var: #aRoutine type: #'void *'>
  	<inline: false>
  	self genSmalltalkToCStackSwitch: pushLinkReg.
  	self
  		compileCallFor: aRoutine
  		numArgs: numArgs
  		arg: regOrConst0
  		arg: regOrConst1
  		arg: regOrConst2
  		arg: regOrConst3
  		resultReg: resultRegOrNil
  		saveRegs: saveRegs.
  	backEnd genLoadStackPointers.
  	(pushLinkReg and: [backEnd hasLinkRegister])
+ 		ifTrue: [
+ 			backEnd hasPCRegister
+ 				ifTrue: [self PopR: PCReg]
+ 				ifFalse: [self PopR: LinkReg. 
+ 						self RetN: 0]]
+ 		ifFalse: [self RetN: 0]!
- 		ifTrue: [self PopR: PCReg] "since we know there is no SP messing to do, might as well pop the stacked return address straight into PC"
- 		ifFalse:[ self RetN: 0]!



More information about the Vm-dev mailing list