[Vm-dev] VM Maker: VMMaker.oscog-tpr.1091.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Mar 12 21:40:26 UTC 2015


tim Rowledge uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-tpr.1091.mcz

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

Name: VMMaker.oscog-tpr.1091
Author: tpr
Time: 12 March 2015, 2:38:37.189 pm
UUID: f570cbcd-13a8-4dc8-9cb9-2714d07ca58e
Ancestors: VMMaker.oscog-tpr.1090

second attempt to save tpr.1090
It'll all end in tears

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

Item was changed:
  CogAbstractInstruction subclass: #CogARMCompiler
  	instanceVariableNames: ''
+ 	classVariableNames: 'AL AddOpcode AndOpcode BICCqR BicOpcode CArg0Reg CArg1Reg CArg2Reg CArg3Reg CC CS CmpOpcode EQ GE GT HI LDMFD LE LR LS LT MI NE OrOpcode PC PL R0 R1 R10 R11 R12 R2 R3 R4 R5 R6 R7 R8 R9 RISCTempReg SP STMFD SubOpcode VC VS XorOpcode'
- 	classVariableNames: 'AL BICCqR CArg0Reg CArg1Reg CArg2Reg CArg3Reg CC CS EQ GE GT HI LDMFD LE LR LS LT MI NE PC PL R0 R1 R10 R11 R12 R2 R3 R4 R5 R6 R7 R8 R9 RISCTempReg SP STMFD VC VS'
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!
  
  !CogARMCompiler commentStamp: 'lw 8/23/2012 19:38' prior: 0!
  I generate ARM instructions from CogAbstractInstructions.  For reference see
  http://infocenter.arm.com/help/index.jsp?topic=/com.arm.doc.set.architecture/index.html
  
  The Architecture Reference Manual used is that of version 5, which includes some version 6 instructions. Of those, only pld is used(for PrefetchAw).
  
  This class does not take any special action to flush the instruction cache on instruction-modification.!

Item was changed:
  ----- Method: CogARMCompiler class>>initialize (in category 'class initialization') -----
  initialize
  	
  	"Initialize various ARM instruction-related constants."
  	"CogARMCompiler initialize"
  	
  	| specificOpcodes refs |
  	super initialize.
  	self ~~ CogARMCompiler ifTrue: [^self].
  	
  	R0 := 0.
  	R1 := 1.
  	R2 := 2.
  	R3 := 3.
  	R4 := 4.
  	R5 := 5.
  	R6 := 6.
  	R7 := 7.
  	R8 := 8.
  	R9 := 9.
  	R10 := 10.
  	R11 := 11.
  	R12 := 12..
  	SP := 13..
  	LR := 14.
  	PC := 15.
  	
  	CArg0Reg := 0.
  	CArg1Reg := 1.
  	CArg2Reg := 2.
  	CArg3Reg := 3.
  	
  	RISCTempReg := R10.
  	
  	"Condition Codes. Note that cc=16rF is NOT ALLOWED as a condition; it specifies an extension instruction. See e.g.ARM_ARM v5 DDI01001.pdf A3.2.1"
  	EQ := 0.
  	NE := 1.
  	CS := 2.
  	CC := 3.
  	MI := 4.
  	PL := 5.
  	VS := 6.
  	VC := 7.
  	HI := 8.
  	LS := 9.
  	GE := 10.
  	LT := 11.
  	GT := 12.
  	LE := 13.
  	AL := 14.
+ 
+ 	AddOpcode := 	4.
+ 	AndOpcode := 0.
+ 	BicOpcode := 16rE.
+ 	CmpOpcode := 10.
+ 	OrOpcode := 16rC.
+ 	SubOpcode := 2.
+ 	XorOpcode := 1.
- 	
  	"Specific instructions"
  	LastRTLCode isNil ifTrue:
  		[CogRTLOpcodes initialize].
  	specificOpcodes := #(LDMFD STMFD BICCqR).
  	refs := (thisContext method literals select: [:l| l isVariableBinding and: [classPool includesKey: l key]]) collect:
  				[:ea| ea key].
  	(classPool keys reject: [:k| (specificOpcodes includes: k) or: [refs includes: k]]) do:
  		[:k|
  		Undeclared declare: k from: classPool].
  	specificOpcodes withIndexDo:
  		[:classVarName :value|
  		self classPool
  			declare: classVarName from: Undeclared;
  			at: classVarName put: value + LastRTLCode - 1]!

Item was changed:
  ----- Method: CogARMCompiler>>callInstructionByteSize (in category 'accessing') -----
  callInstructionByteSize
+ 	"we only get to use quick B[LX] calls. We hope"
  	^4!

Item was changed:
  ----- Method: CogARMCompiler>>computeMaximumSize (in category 'generate machine code') -----
  computeMaximumSize
  	"Because we don't use Thumb, each ARM instruction has 4 bytes. Some abstract opcodes need more than one instruction."
  	
  	| rotateableAt0then4or20Block |
  	rotateableAt0then4or20Block := [^self rotateable8bitImmediate: (operands at: 0)
  											ifTrue: [:r :i| maxSize := 4]
  											ifFalse: [maxSize := 20]].
  	
  	
  	(opcode between: FirstShortJump and: LastJump) ifTrue: [^maxSize := 16].
  	
  	opcode
  		caseOf: {
  			[Label]					-> [^maxSize := 0].
  			[AlignmentNops]		-> [^maxSize := (operands at: 0) - 1].
  			[MoveAwR]				-> [^maxSize := 20].
  			[MoveCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
  											ifTrue: [:r :i| maxSize := 4]
  											ifFalse: [maxSize := 16]].
  			[MoveCwR]				-> [^maxSize := 16].
  			[MoveRAw]				-> [^maxSize := 20].
  			[MoveRMwr]			-> [self is12BitValue: (operands at: 1)
  											ifTrue: [ :u :i | ^maxSize := 4]
  											ifFalse: [ ^maxSize := 20 ]].
  			[MoveRMbr]				-> [self is12BitValue: (operands at: 1)
  											ifTrue: [ :u :i | ^maxSize := 4]
  											ifFalse: [ ^maxSize := 20 ]].
  			[MoveMwrR]			-> [self is12BitValue: (operands at: 0)
  											ifTrue: [ :u :i | ^maxSize := 4]
  											ifFalse: [ ^maxSize := 20 ]].
  			[MoveMbrR]				-> [self is12BitValue: (operands at: 0)
  											ifTrue: [ :u :i | ^maxSize := 4]
  											ifFalse: [ ^maxSize := 20 ]].
  			[PrefetchAw] 			-> [^maxSize := 20].
  			[Call]					-> [^maxSize := 20 "recomputed in #sizePCDependentInstruction."].
  			[RetN]					-> [^(operands at: 0) = 0 
  											ifTrue: [maxSize := 4]
  											ifFalse: [maxSize := 8]].
  			[CmpCqR]				-> [rotateableAt0then4or20Block value].
  			[AddCqR]				-> [rotateableAt0then4or20Block value].
  			[BICCqR]				-> [rotateableAt0then4or20Block value].
  			[SubCqR]				-> [rotateableAt0then4or20Block value].
  			[AndCqR]				-> [rotateableAt0then4or20Block value].
  			[OrCqR]					-> [rotateableAt0then4or20Block value].
+ 			[TstCqR]				-> [rotateableAt0then4or20Block value].
  			[XorCqR]				-> [rotateableAt0then4or20Block value].
  			[CmpCwR]				-> [^maxSize := 20].
  			[AddCwR]				-> [^maxSize := 20].
  			[SubCwR]				-> [^maxSize := 20].
  			[AndCwR]				-> [^maxSize := 20].
  			[OrCwR]				-> [^maxSize := 20].
  			[XorCwR]				-> [^maxSize := 20].
  			[JumpR]					-> [^maxSize := 4].
  			[JumpFPEqual]			-> [^maxSize := 8].
  			[JumpFPNotEqual]		-> [^maxSize := 8].
  			[JumpFPLess]			-> [^maxSize := 8].
  			[JumpFPGreaterOrEqual]-> [^maxSize := 8].
  			[JumpFPGreater]		-> [^maxSize := 8].
  			[JumpFPLessOrEqual]	-> [^maxSize := 8].
  			[JumpFPOrdered]		-> [^maxSize := 8].
  			[JumpFPUnordered]		-> [^maxSize := 8].
  			[JumpLong]				-> [^maxSize := 20].
  			[JumpLongZero]		-> [^maxSize := 20].
  			[JumpLongNonZero]	-> [^maxSize := 20].
  			[LoadEffectiveAddressMwrR] -> [rotateableAt0then4or20Block value].
  			[PushCw]				-> [^maxSize := 20].
  		}
  		otherwise: [^maxSize := 4].
  	^4 "to keep C compiler quiet"
  !

Item was removed:
- ----- Method: CogARMCompiler>>concretizeCmpCqR (in category 'generate machine code - concretize') -----
- concretizeCmpCqR
- 	"Will get inlined into concretizeAt: switch."
- 	"All other data operations write back their results. The write back register should be zero for CMP."
- 	<inline: true>
- 	| size |
- 	size := self concretizeDataOperationCqR: 16rA.
- 	machineCode at: size - 3 put: ((machineCode at: size -3) bitAnd: 16rFF).
- 	^size
- !

Item was removed:
- ----- Method: CogARMCompiler>>concretizeCmpCwR (in category 'generate machine code - concretize') -----
- concretizeCmpCwR
- 	"Will get inlined into concretizeAt: switch."
- 	"All other data operations write back their results. The write back register should be zero for CMP."
- 	<inline: true>
- 	| size |
- 	size := self concretizeDataOperationCwR: 16rA.
- 	machineCode at: size - 3 put: ((machineCode at: size -3) bitAnd: 16rFF).
- 	^size!

Item was removed:
- ----- Method: CogARMCompiler>>concretizeCmpRR (in category 'generate machine code - concretize') -----
- concretizeCmpRR
- 	"Will get inlined into concretizeAt: switch."
- 	"All other data operations write back their results. The write back register should be zero for CMP."
- 	<inline: true>
- 	| size |
- 	size := self concretizeDataOperationRR: 16rA.
- 	machineCode at: size - 3 put: ((machineCode at: size -3) bitAnd: 16rFF).
- 	^size!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeDataOperationCqR: (in category 'generate machine code - concretize') -----
  concretizeDataOperationCqR: opcode
  	"Will get inlined into concretizeAt: switch."
  	"4 == Add, 2 == Sub, Xor == 1, And == 0, Or == 12, Bic == 14"
  	<inline: true>
  	self 
  		rotateable8bitImmediate: (operands at: 0) 
+ 		ifTrue: [:rot :immediate | | rd rn |
+ 			rn := self concreteRegister: (operands at: 1).
+ 			rd := opcode = CmpOpcode ifTrue: [0] ifFalse:[rn].
+ 			self machineCodeAt: 0 put: (self type: 1 op: opcode set: 1 rn: rn rd: rd shifterOperand: ((rot>>1)"in this usage we have to halve the rot value" << 8 bitOr: immediate)).
- 		ifTrue: [:rot :immediate | | reg |
- 			reg := self concreteRegister: (operands at: 1).
- 			self machineCodeAt: 0 put: (self type: 1 op: opcode set: 1 rn: reg rd: reg shifterOperand: ((rot>>1)"in this usage we have to halve the rot value" << 8 bitOr: immediate)).
  			^machineCodeSize := 4]
  		ifFalse: [^self concretizeDataOperationCwR: opcode].
  	!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeDataOperationCwR: (in category 'generate machine code - concretize') -----
  concretizeDataOperationCwR: opcode
  	"Will get inlined into concretizeAt: switch."
  	"Load the word into the RISCTempReg, then cmp R, RISCTempReg"
  	<inline: true>
+ 	| constant rn rd instrOffset|
- 	| constant srcDestReg instrOffset|
  	constant := operands at: 0.
+ 	rn := (self concreteRegister: (operands at: 1)).
+ 	rd := opcode = CmpOpcode ifTrue: [0] ifFalse:[rn].
- 	srcDestReg := (self concreteRegister: (operands at: 1)).
  	instrOffset := self at: 0 moveCw: constant intoR: RISCTempReg.
  	self machineCodeAt: instrOffset 
+ 		put: (self type: 0 op: opcode set: 1 rn: rn rd: rd shifterOperand: RISCTempReg).
- 		put: (self type: 0 op: opcode set: 1 rn: srcDestReg rd: srcDestReg shifterOperand: RISCTempReg).
  	^machineCodeSize := instrOffset + 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeDataOperationRR: (in category 'generate machine code - concretize') -----
  concretizeDataOperationRR: opcode
  	"Will get inlined into concretizeAt: switch."
+ 	"Load the word into the RISCTempReg, then op R, RISCTempReg"
- 	"Load the word into the RISCTempReg, then cmp R, RISCTempReg"
  	<inline: true>
+ 	| rn rd srcReg |
- 	| destReg srcReg |
  	srcReg := self concreteRegister: (operands at: 0).
+ 	rn := (self concreteRegister: (operands at: 1)).
+ 	rd := opcode = CmpOpcode ifTrue: [0] ifFalse: [rn].
- 	destReg := (self concreteRegister: (operands at: 1)).
  	self machineCodeAt: 0 
+ 		put: (self type: 0 op: opcode set: 1 rn: rn rd: rd shifterOperand: srcReg).
- 		put: (self type: 0 op: opcode set: 1 rn: destReg rd: destReg shifterOperand: srcReg).
  	^machineCodeSize := 4.!

Item was added:
+ ----- Method: CogARMCompiler>>concretizeTstCqR (in category 'generate machine code - concretize') -----
+ concretizeTstCqR
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	self rotateable8bitImmediate: (operands at: 0)
+ 		ifTrue: [ :rot :immediate | | reg |
+ 			reg := self concreteRegister: (operands at: 1).
+ 			self machineCodeAt: 0 put: (self tst: reg rn: reg imm: immediate ror: rot).
+ 			^machineCodeSize := 4]
+ 		ifFalse: [^self concretizeDataOperationCwR: 8]!

Item was changed:
  ----- Method: CogARMCompiler>>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].
  		"Specific Control/Data Movement"
  		"[LDM]					-> [^self concretizeLDM].
  		[STM]					-> [^self concretizeSTM]."
  		"Control"
  		[Call]						-> [^self concretizeCall].
  		[JumpR]						-> [^self concretizeJumpR].
  		[JumpLong]					-> [^self concretizeConditionalJumpLong: AL].
  		[JumpLongZero]			-> [^self concretizeConditionalJumpLong: EQ].
  		[JumpLongNonZero]		-> [^self concretizeConditionalJumpLong: NE].
  		[Jump]						-> [^self concretizeConditionalJump: AL].
  		[JumpZero]					-> [^self concretizeConditionalJump: EQ].
  		[JumpNonZero]				-> [^self concretizeConditionalJump: NE].
  		[JumpNegative]				-> [^self concretizeConditionalJump: MI].
  		[JumpNonNegative]			-> [^self concretizeConditionalJump: PL].
  		[JumpOverflow]				-> [^self concretizeConditionalJump: VS].
  		[JumpNoOverflow]			-> [^self concretizeConditionalJump: VC].
  		[JumpCarry]				-> [^self concretizeConditionalJump: CS].
  		[JumpNoCarry]				-> [^self concretizeConditionalJump: CC].
  		[JumpLess]					-> [^self concretizeConditionalJump: LT].
  		[JumpGreaterOrEqual]		-> [^self concretizeConditionalJump: GE].
  		[JumpGreater]				-> [^self concretizeConditionalJump: GT].
  		[JumpLessOrEqual]			-> [^self concretizeConditionalJump: LE].
  		[JumpBelow]				-> [^self concretizeConditionalJump: CC]. "unsigned lower"
  		[JumpAboveOrEqual]		-> [^self concretizeConditionalJump: CS]. "unsigned greater or equal"
  		[JumpAbove]				-> [^self concretizeConditionalJump: HI].
  		[JumpBelowOrEqual]		-> [^self concretizeConditionalJump: LS].
  		[JumpFPEqual]				-> [^self concretizeFPConditionalJump: EQ].
  		[JumpFPNotEqual]			-> [^self concretizeFPConditionalJump: NE].
  		"[JumpFPLess]				-> [^self concretizeFPConditionalJump: LT].
  		[JumpFPGreaterOrEqual]	-> [^self concretizeFPConditionalJump: GE].
  		[JumpFPGreater]			-> [^self concretizeFPConditionalJump: GT].
  		[JumpFPLessOrEqual]		-> [^self concretizeFPConditionalJump: LE].
  		[JumpFPOrdered]			-> [^self concretizeFPConditionalJump: VC].
  		[JumpFPUnordered]			-> [^self concretizeFPConditionalJump: VS]."
  		[RetN]						-> [^self concretizeRetN].
  		"Arithmetic"
  		[AddCqR]					-> [^self concretizeAddCqR].
+ 		[AddCwR]					-> [^self concretizeDataOperationCwR: AddOpcode].
+ 		[AddRR]						-> [^self concretizeDataOperationRR: AddOpcode].
- 		[AddCwR]					-> [^self concretizeDataOperationCwR: 4].
- 		[AddRR]						-> [^self concretizeDataOperationRR: 4].
  		"[AddRdRd]					-> [^self concretizeSEE2OpRdRd: 16r58]."
  		[AndCqR]					-> [^self concretizeAndCqR].
+ 		[AndCwR]					-> [^self concretizeDataOperationCwR: AndOpcode].
+ 		[AndRR]						-> [^self concretizeDataOperationRR: AndOpcode].
+ 		[BICCqR]					-> [^self concretizeDataOperationCqR: BicOpcode].
+ 		[CmpCqR]					-> [^self concretizeDataOperationCqR: CmpOpcode].
+ 		[CmpCwR]					-> [^self concretizeDataOperationCwR: CmpOpcode].
+ 		[CmpRR]					-> [^self concretizeDataOperationRR: CmpOpcode].
- 		[AndCwR]					-> [^self concretizeDataOperationCwR: 0].
- 		[AndRR]						-> [^self concretizeDataOperationRR: 0].
- 		[BICCqR]					-> [^self   concretizeDataOperationCqR: 16rE].
- 		[CmpCqR]					-> [^self concretizeCmpCqR].
- 		[CmpCwR]					-> [^self concretizeCmpCwR].
- 		[CmpRR]					-> [^self concretizeCmpRR].
  		[CmpRdRd]					-> [^self concretizeCmpRdRd].
  		"[DivRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5E].
  		[MulRdRd]					-> [^self concretizeSEE2OpRdRd: 16r59]."
+ 		[OrCqR]						-> [^self concretizeDataOperationCqR: OrOpcode].
+ 		[OrCwR]					-> [^self concretizeDataOperationCwR: OrOpcode].
+ 		[OrRR]						-> [^self concretizeDataOperationRR: OrOpcode].
- 		[OrCqR]						-> [^self concretizeDataOperationCqR: 16rC].
- 		[OrCwR]					-> [^self concretizeDataOperationCwR: 16rC].
- 		[OrRR]						-> [^self concretizeDataOperationRR: 16rC].
  		[SubCqR]					-> [^self concretizeSubCqR].
+ 		[SubCwR]					-> [^self concretizeDataOperationCwR: SubOpcode].
+ 		[SubRR]						-> [^self concretizeDataOperationRR: SubOpcode].
- 		[SubCwR]					-> [^self concretizeDataOperationCwR: 2].
- 		[SubRR]						-> [^self concretizeDataOperationRR: 2].
  		"[SubRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5C]."
  		[SqrtRd]						-> [^self concretizeSqrtRd].
+ 		[TstCqR]					-> [^self concretizeTstCqR].
+ 		[XorCqR]						-> [^self concretizeDataOperationCqR: XorOpcode].
+ 		[XorCwR]						-> [^self concretizeDataOperationCwR: XorOpcode].
+ 		[XorRR]							-> [^self concretizeDataOperationRR: XorOpcode].
- 		[XorCqR]						-> [^self concretizeDataOperationCqR: 1].
- 		[XorCwR]						-> [^self concretizeDataOperationCwR: 1].
- 		[XorRR]							-> [^self concretizeDataOperationRR: 1].
  		[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].
  		"While the two MoveMbR and MoveMwR are quite similar (off by 1 bit), they differ way more to
  		MoveM16R and MoveM64R. Because of that, they are not merged."
  		[MoveMbrR]			-> [^self concretizeMoveMbrR].
  		[MoveRMbr]			-> [^self concretizeMoveRMbr].
  		[MoveM16rR]		-> [^self concretizeMoveM16rR].
  		[MoveM64rRd]		-> [^self concretizeMoveM64rRd].
  		[MoveMwrR]		-> [^self concretizeMoveMwrR].
  		[MoveXbrRR]		-> [^self concretizeMoveXbrRR].
  		[MoveRXbrR]		-> [^self concretizeMoveRXbrR].
  		[MoveXwrRR]		-> [^self concretizeMoveXwrRR].
  		[MoveRXwrR]		-> [^self concretizeMoveRXwrR].
  		[MoveRMwr]		-> [^self concretizeMoveRMwr].
  		[MoveRdM64r]		-> [^self concretizeMoveRdM64r].
  		[PopR]				-> [^self concretizePopR].
  		[PushR]				-> [^self concretizePushR].
  		[PushCw]			-> [^self concretizePushCw].
  		[PrefetchAw]		-> [^self concretizePrefetchAw].
  		"Conversion"
  		[ConvertRRd]		-> [^self concretizeConvertRRd].
  		"ARM specific opcodes" 
  		[LDMFD]			-> [^self concretizeLDMFD].
  		[STMFD]			-> [^self concretizeSTMFD]	}!

Item was changed:
  ----- Method: CogARMCompiler>>genAlignCStackSavingRegisters:numArgs:wordAlignment: (in category 'abi') -----
  genAlignCStackSavingRegisters: saveRegs numArgs: numArgs wordAlignment: alignment 
+ "ARM doesn't push the first 4 arguments. Now, currently Cog doesn't use more than 4 args so we should never need to push any - but just in case we'll check for it"
+ 	| wordsPushedModAlignment delta |
+ 	wordsPushedModAlignment := ((saveRegs ifTrue: [self numberOfSaveableRegisters] ifFalse: [0])
+ 									+ (numArgs > 4 ifTrue:[numArgs - 4] ifFalse:[0]))
+ 									\\ alignment.
+ 	wordsPushedModAlignment ~= 0 ifTrue:
+ 		[delta := alignment - wordsPushedModAlignment.
+ 		 cogit SubCq: delta * 4 R: SPReg].
- 	"ARM needs 8 byte stack alignment but it's hard to be sure where the stack is at this
- 	 point due to the complexities of whether we push the return address or not.  So do
- 	 a simple bitAnd to effectively round-down the SP - except the vagaries of the ARM
- 	 instruction set means we actually need a BIC sp, sp, $7"
- 
  	^0!

Item was added:
+ ----- Method: CogARMCompiler>>tst:rn:imm:ror: (in category 'ARM convenience instructions') -----
+ tst: ignored rn: srcReg imm: immediate ror: rot
+ "return a TST srcReg, immediat ROR rot instruction. Remember the ROR is doubled by the cpu so use 30>>1 etc"
+ "also note that TST has no destREg"
+ 
+ 	^self type: 1 op: 8 set: 1 rn: srcReg rd: 0 shifterOperand: ((rot>>1) <<8 bitOr: immediate)!

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

Item was changed:
  ----- Method: CogObjectRepresentationForSqueakV3>>genGetInlineCacheClassTagFrom:into:forEntry: (in category 'compile abstract instructions') -----
  genGetInlineCacheClassTagFrom: sourceReg into: destReg forEntry: forEntry
  	"Extract the inline cache tag for the object in sourceReg into destReg. The inline cache tag
  	 for a given object is the value loaded in inline caches to distinguish objects of different
  	 classes.  In Spur this is either the tags for immediates, or the receiver's classIndex.
  	 The inline cache tag for a given object is the value loaded in inline caches to distinguish
  	 objects of different classes.  In SqueakV3 the tag is the integer tag bit for SmallIntegers (1),
  	 the compact class index shifted by log: 2 word size for objects with compact classes
  	 (1 * 4 to: 31 * 4 by: 4), or the class.  These ranges cannot overlap because the heap
  	 (and hence the lowest class object) is beyond the machine code zone.
  	 If forEntry is true answer the entry label at which control is to enter (cmEntryOffset).
  	 If forEntry is false, control enters at the start."
  	| entryLabel jumpIsInt jumpCompact |
  	<var: #entryLabel type: #'AbstractInstruction *'>
  	<var: #jumpIsInt type: #'AbstractInstruction *'>
  	<var: #jumpCompact type: #'AbstractInstruction *'>
  	cogit AlignmentNops: (objectMemory wordSize max: 8).
  	entryLabel := cogit Label.
+ 	cogit backEnd hasLinkRegister
+ 		ifFalse:[ cogit MoveR: sourceReg R: destReg.
+ 				cogit AndCq: 1 R: destReg]
+ 		ifTrue:[cogit TstCq: 1 R: sourceReg]. "<---- this works for ARM but is not yet implemented for x86"
- 	cogit MoveR: sourceReg R: destReg.
- 	cogit AndCq: 1 R: destReg.
  	jumpIsInt := cogit JumpNonZero: 0.
  	"Get header word in destReg"
  	cogit MoveMw: 0 r: sourceReg R: destReg.
  	"Extract the compact class field, and if non-zero use it as the tag.."
  	self assert: self compactClassFieldMask << objectMemory compactClassFieldLSB < objectMemory nilObject asUnsignedInteger.
  	cogit AndCq: self compactClassFieldMask << objectMemory compactClassFieldLSB R: destReg.
  	jumpCompact := cogit JumpNonZero: 0.
  	cogit MoveMw: objectMemory classFieldOffset r: sourceReg R: destReg.
  	"The use of signedIntFromLong is a hack to get round short addressing mode computations.
  	 Much easier if offsets are signed and the arithmetic machinery we have makes it difficult to
  	 mix signed and unsigned offsets."
  	cogit AndCq: AllButTypeMask signedIntFromLong R: destReg.
  	jumpCompact jmpTarget: (jumpIsInt jmpTarget: cogit Label).
  	^entryLabel!

Item was changed:
  SharedPool subclass: #CogRTLOpcodes
  	instanceVariableNames: ''
+ 	classVariableNames: 'AddCqR AddCwR AddRR AddRdRd AlignmentNops AndCqR AndCwR AndRR Arg0Reg Arg1Reg ArithmeticShiftRightCqR ArithmeticShiftRightRR Call ClassReg CmpCqR CmpCwR CmpRR CmpRdRd ConvertRRd DPFPReg0 DPFPReg1 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7 DivRdRd FPReg Fill16 Fill32 Fill8 FillBytesFrom FillFromWord FirstJump FirstShortJump GPRegMax GPRegMin Jump JumpAbove JumpAboveOrEqual JumpBelow JumpBelowOrEqual JumpCarry JumpFPEqual JumpFPGreater JumpFPGreaterOrEqual JumpFPLess JumpFPLessOrEqual JumpFPNotEqual JumpFPOrdered JumpFPUnordered JumpGreater JumpGreaterOrEqual JumpLess JumpLessOrEqual JumpLong JumpLongNonZero JumpLongZero JumpNegative JumpNoCarry JumpNoOverflow JumpNonNegative JumpNonZero JumpOverflow JumpR JumpZero Label LastJump LastRTLCode LinkReg LoadEffectiveAddressMwrR LoadEffectiveAddressXowrR LogicalShiftLeftCqR LogicalShiftLeftRR LogicalShiftRightCqR LogicalShiftRightRR MoveAbR MoveAwR MoveC32R MoveC64R MoveCqR MoveCwR MoveM16rR MoveM32rR MoveM64rRd MoveMbrR MoveMwrR MoveRAb MoveRAw MoveRM16r MoveRM32r MoveRMbr MoveRMwr MoveRR MoveRX16rR MoveRX32rR MoveRXbrR MoveRXowr MoveRXwrR MoveRdM64r MoveRdRd MoveX16rRR MoveX32rRR MoveXbrRR MoveXowrR MoveXwrRR MulCqR MulCwR MulRR MulRdRd NegateR Nop OrCqR OrCwR OrRR PCReg PopR PrefetchAw PushCw PushR ReceiverResultReg RetN SPReg SendNumArgsReg SqrtRd SubCqR SubCwR SubRR SubRdRd TempReg TstCqR XorCqR XorCwR XorRR'
- 	classVariableNames: 'AddCqR AddCwR AddRR AddRdRd AlignmentNops AndCqR AndCwR AndRR Arg0Reg Arg1Reg ArithmeticShiftRightCqR ArithmeticShiftRightRR Call ClassReg CmpCqR CmpCwR CmpRR CmpRdRd ConvertRRd DPFPReg0 DPFPReg1 DPFPReg2 DPFPReg3 DPFPReg4 DPFPReg5 DPFPReg6 DPFPReg7 DivRdRd FPReg Fill16 Fill32 Fill8 FillBytesFrom FillFromWord FirstJump FirstShortJump GPRegMax GPRegMin Jump JumpAbove JumpAboveOrEqual JumpBelow JumpBelowOrEqual JumpCarry JumpFPEqual JumpFPGreater JumpFPGreaterOrEqual JumpFPLess JumpFPLessOrEqual JumpFPNotEqual JumpFPOrdered JumpFPUnordered JumpGreater JumpGreaterOrEqual JumpLess JumpLessOrEqual JumpLong JumpLongNonZero JumpLongZero JumpNegative JumpNoCarry JumpNoOverflow JumpNonNegative JumpNonZero JumpOverflow JumpR JumpZero Label LastJump LastRTLCode LinkReg LoadEffectiveAddressMwrR LoadEffectiveAddressXowrR LogicalShiftLeftCqR LogicalShiftLeftRR LogicalShiftRightCqR LogicalShiftRightRR MoveAbR MoveAwR MoveC32R MoveC64R MoveCqR MoveCwR MoveM16rR MoveM32rR MoveM64rRd MoveMbrR MoveMwrR MoveRAb MoveRAw MoveRM16r MoveRM32r MoveRMbr MoveRMwr MoveRR MoveRX16rR MoveRX32rR MoveRXbrR MoveRXowr MoveRXwrR MoveRdM64r MoveRdRd MoveX16rRR MoveX32rRR MoveXbrRR MoveXowrR MoveXwrRR MulCqR MulCwR MulRR MulRdRd NegateR Nop OrCqR OrCwR OrRR PCReg PopR PrefetchAw PushCw PushR ReceiverResultReg RetN SPReg SendNumArgsReg SqrtRd SubCqR SubCwR SubRR SubRdRd TempReg XorCqR XorCwR XorRR'
  	poolDictionaries: ''
  	category: 'VMMaker-JIT'!
  
  !CogRTLOpcodes commentStamp: '<historical>' prior: 0!
  I am a pool for the Register-Transfer-Language to which Cog compiles.  I define unique integer values for all RTL opcodes and abstract registers.  See CogAbstractInstruction for instances of instructions with the opcodes that I define.!

Item was changed:
  ----- Method: CogRTLOpcodes class>>initialize (in category 'class initialization') -----
  initialize
  	"Abstract opcodes are a compound of a one word operation specifier and zero or more operand type specifiers.
  	 e.g. MoveRR is the Move opcode with two register operand specifiers and defines a move register to
  	 register instruction from operand 0 to operand 1.  The word and register size is assumed to be either 32-bits on
  	 a 32-bit architecture or 64-bits on a 64-bit architecture.		(self initialize)
  	The operand specifiers are
  		R		- general purpose register
  		Rd		- double-precision floating-point register
  		Cq		- a quick constant that can be encoded in the minimum space possible.
  		Cw		- a constant with word size where word is the default operand size for the Smalltalk VM, 32-bits
  				  for a 32-bit VM, 64-bits for a 64-bit VM.  The generated constant must occupy the default number
  				  of bits.  This allows e.g. a garbage collector to update the value without invalidating the code.
  		C32	- a constant with 32 bit size.  The generated constant must occupy 32 bits.
  		C64	- a constant with 64 bit size.  The generated constant must occupy 64 bits.
  		Aw		- memory word with an absolute address
  		Ab		- memory byte with an absolute address
  		Mwr	- memory word whose address is at a constant offset from an address in a register
  		Mbr		- memory byte whose address is at a constant offset from an address in a register
  		M16r	- memory 16-bit halfword whose address is at a constant offset from an address in a register
  		M32r	- memory 32-bit halfword whose address is at a constant offset from an address in a register
  		M64r	- memory 64-bit doubleword whose address is at a constant offset from an address in a register
  		XbrR	- memory word whose address is r * byte size away from an address in a register
  		X16rR	- memory word whose address is r * (2 bytes size) away from an address in a register
  		XwrR	- memory word whose address is r * word size away from an address in a register
  		XowrR	- memory word whose address is (r * word size) + o away from an address in a register (scaled indexed)
  
  	An alternative would be to decouple opcodes from operands, e.g.
  		Move := 1. Add := 2. Sub := 3...
  		RegisterOperand := 1. ConstantQuickOperand := 2. ConstantWordOperand := 3...
  	But not all combinations make sense and even fewer are used so we stick with the simple compound approach.
  
  	The assumption is that comparison and arithmetic instructions set condition codes and that move instructions
  	leave the condition codes unaffected.  In particular LoadEffectiveAddressMwrR does not set condition codes
  	although it can be used to do arithmetic.
  
  	Not all of the definitions in opcodeDefinitions below are implemented.  In particular we do not implement the
  	 XowrR scaled index addressing mode since it requires 4 operands.
  
  	Note that there are no generic division instructions defined, but a processor may define some."
  
  	| opcodeNames refs |
  	FPReg := -1.
  	SPReg := -2.
  	ReceiverResultReg := GPRegMax := -3.
  	TempReg := -4.
  	ClassReg := -5.
  	SendNumArgsReg := -6.
  	Arg0Reg := -7.
  	Arg1Reg := GPRegMin := -8.
  
  	DPFPReg0 := -9.
  	DPFPReg1 := -10.
  	DPFPReg2 := -11.
  	DPFPReg3 := -12.
  	DPFPReg4 := -13.
  	DPFPReg5 := -14.
  	DPFPReg6 := -15.
  	DPFPReg7 := -16.
  	
  	LinkReg := -17.
  	PCReg := -18.
  
  	opcodeNames := #("Noops & Pseudo Ops"
  						Label
  						AlignmentNops
  						FillBytesFrom	"output operand 0's worth of bytes from the address in operand 1"
  						Fill8				"output a byte's worth of bytes with operand 0"
  						Fill16			"output two byte's worth of bytes with operand 0"
  						Fill32			"output four byte's worth of bytes with operand 0"
  						FillFromWord	"output BytesPerWord's worth of bytes with operand 0 + operand 1"
  						Nop
  
  						"Control"
  						Call
  						RetN
  						JumpR				"Not a regular jump, i.e. not pc dependent."
  
  						"N.B.  Jumps are contiguous.  Long jumps are contigiuous within them.  See FirstJump et al below"
  						JumpLong
  						JumpLongZero		"a.k.a. JumpLongEqual"
  						JumpLongNonZero	"a.k.a. JumpLongNotEqual"
  						Jump
  						JumpZero			"a.k.a. JumpEqual"
  						JumpNonZero		"a.k.a. JumpNotEqual"
  						JumpNegative
  						JumpNonNegative
  						JumpOverflow
  						JumpNoOverflow
  						JumpCarry
  						JumpNoCarry
  						JumpLess			"signed"
  						JumpGreaterOrEqual
  						JumpGreater
  						JumpLessOrEqual
  						JumpBelow			"unsigned"
  						JumpAboveOrEqual
  						JumpAbove
  						JumpBelowOrEqual
  
  						JumpFPEqual
  						JumpFPNotEqual
  						JumpFPLess
  						JumpFPLessOrEqual
  						JumpFPGreater
  						JumpFPGreaterOrEqual
  						JumpFPOrdered
  						JumpFPUnordered
  
  						"Data Movement; destination is always last operand"
  						MoveRR
  						MoveAwR
  						MoveRAw
  						MoveAbR
  						MoveRAb
  						MoveMwrR MoveRMwr MoveXwrRR MoveRXwrR MoveXowrR MoveRXowr
  						MoveM16rR MoveRM16r MoveX16rRR MoveRX16rR
  						MoveM32rR MoveRM32r MoveX32rRR MoveRX32rR
  						MoveMbrR MoveRMbr MoveXbrRR MoveRXbrR
  						MoveCqR MoveCwR MoveC32R MoveC64R
  						MoveRdRd MoveM64rRd MoveRdM64r
  						PopR PushR PushCw
  						PrefetchAw
  
  						"Arithmetic; destination is always last operand except Cmp; CmpXR is SubRX with no update of result"
  						LoadEffectiveAddressMwrR LoadEffectiveAddressXowrR "Variants of add/multiply"
  						NegateR "2's complement negation"
  						ArithmeticShiftRightCqR ArithmeticShiftRightRR
  						LogicalShiftRightCqR LogicalShiftRightRR
  						LogicalShiftLeftCqR LogicalShiftLeftRR
  
  						CmpRR AddRR SubRR AndRR OrRR XorRR MulRR
  						CmpCqR AddCqR SubCqR AndCqR OrCqR XorCqR MulCqR
  						CmpCwR AddCwR SubCwR AndCwR OrCwR XorCwR MulCwR
  
+ 						CmpRdRd AddRdRd SubRdRd MulRdRd DivRdRd TstCqR SqrtRd
- 						CmpRdRd AddRdRd SubRdRd MulRdRd DivRdRd SqrtRd
  
  						"Conversion"
  						ConvertRRd
  
  						LastRTLCode).
  
  	"Magic auto declaration. Add to the classPool any new variables and nuke any obsolete ones, and assign values"
  	"Find the variables directly referenced by this method"
  	refs := (thisContext method literals select: [:l| l isVariableBinding and: [classPool includesKey: l key]]) collect:
  				[:ea| ea key].
  	"Move to Undeclared any opcodes in classPool not in opcodes or this method."
  	(classPool keys reject: [:k| (opcodeNames includes: k) or: [refs includes: k]]) do:
  		[:k|
  		Undeclared declare: k from: classPool].
  	"Declare as class variables and number elements of opcodeArray above"
  	opcodeNames withIndexDo:
  		[:classVarName :value|
  		self classPool
  			declare: classVarName from: Undeclared;
  			at: classVarName put: value].
  
  	"For CogAbstractInstruction>>isJump etc..."
  	FirstJump := JumpLong.
  	LastJump := JumpFPUnordered.
  	FirstShortJump := Jump.
  
  	"And now initialize the backends; they add their own opcodes and hence these must be reinitialized."
  	(Smalltalk classNamed: #CogAbstractInstruction) ifNotNil:
  		[:cogAbstractInstruction| cogAbstractInstruction allSubclasses do: [:sc| sc initialize]]!

Item was added:
+ ----- Method: Cogit>>TstCq:R: (in category 'abstract instructions') -----
+ TstCq: quickConstant R: reg
+ 	<inline: true>
+ 	<returnTypeC: #'AbstractInstruction *'>
+ 	^self gen: TstCqR operand: quickConstant operand: reg!



More information about the Vm-dev mailing list