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

commits at source.squeak.org commits at source.squeak.org
Sat Jun 7 00:48:12 UTC 2014


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

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

Name: VMMaker.oscog-tpr.761
Author: tpr
Time: 5 June 2014, 11:53:45.293 pm
UUID: abc7690f-c63b-4909-acda-9cfd1cbd4301
Ancestors: VMMaker.oscog-eem.760

Add a bunch of ARM instruction convenience methods, add a load more trap handling methods to get us well past ceSICMiss: and into IC futzing.

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

Item was changed:
  ----- Method: CogARMCompiler>>add:rn:imm:ror: (in category 'ARM convenience instructions') -----
  add: destReg rn: srcReg imm: immediate ror: rot
+ "return an ADD destReg, srcReg, immediat ROR rot instruction. Remember the ROR is doubled by the cpu so use 30>>1 etc"
- "return an ADD destReg, srcReg, immediat ROR rot instruction"
  
+ 	^self type: 1 op: 4 set: 0 rn: srcReg rd: destReg shifterOperand: ((rot>>1) <<8 bitOr: immediate)!
- 	^self type: 1 op: 4 set: 0 rn: srcReg rd: destReg shifterOperand: (rot <<8 bitOr: immediate)!

Item was changed:
  ----- Method: CogARMCompiler>>adds:rn:imm:ror: (in category 'ARM convenience instructions') -----
  adds: destReg rn: srcReg imm: immediate ror: rot
+ "return an ADDS destReg, srcReg, immediat ROR rot instruction. Remember the ROR is doubled by the cpu so use 30>>1 etc"
- "return an ADDS destReg, srcReg, immediat ROR rot instruction"
  
+ 	^self type: 1 op: 4 set: 1 rn: srcReg rd: destReg shifterOperand: ((rot>>1) <<8 bitOr: immediate)!
- 	^self type: 1 op: 4 set: 1 rn: srcReg rd: destReg shifterOperand: (rot <<8 bitOr: immediate)!

Item was added:
+ ----- Method: CogARMCompiler>>and:rn:imm:ror: (in category 'ARM convenience instructions') -----
+ and: destReg rn: srcReg imm: immediate ror: rot
+ "return an AND destReg, srcReg, immediat ROR rot instruction. Remember the ROR is doubled by the cpu so use 30>>1 etc"
+ 
+ 	^self type: 1 op: 0 set: 0 rn: srcReg rd: destReg shifterOperand: ((rot>>1) <<8 bitOr: immediate)!

Item was added:
+ ----- Method: CogARMCompiler>>ands:rn:imm:ror: (in category 'ARM convenience instructions') -----
+ ands: destReg rn: srcReg imm: immediate ror: rot
+ "return an ANDS destReg, srcReg, immediat ROR rot instruction. Remember the ROR is doubled by the cpu so use 30>>1 etc"
+ 
+ 	^self type: 1 op: 0 set: 1 rn: srcReg rd: destReg shifterOperand: ((rot>>1) <<8 bitOr: immediate)!

Item was added:
+ ----- Method: CogARMCompiler>>bics:rn:imm:ror: (in category 'ARM convenience instructions') -----
+ bics: destReg rn: srcReg imm: immediate ror: rot
+ "return a BICS destReg, srcReg, immediat ROR rot instruction. Remember the ROR is doubled by the cpu so use 30>>1 etc"
+ 
+ 	^self type: 1 op: 14 set: 1 rn: srcReg rd: destReg shifterOperand: ((rot>>1) <<8 bitOr: immediate)!

Item was changed:
  ----- Method: CogARMCompiler>>callTargetFromReturnAddress: (in category 'inline cacheing') -----
  callTargetFromReturnAddress: callSiteReturnAddress
  	"Answer the address the call immediately preceeding callSiteReturnAddress will jump to."
  	"this is also used by #jumpLongTargetBeforeFOllowingAddress: and so we check for both call and jump related instructions; later on we can use simpler tests once it feels safe to assume we get here always with a call/jump in the proper place"
  	| callDistance call |
  	call := self instructionBeforeAddress: callSiteReturnAddress.
  	self assert: call ~= 0. "andeq r0, r0 will not be generated, not even as nops"
  	((self instructionIsB: call) or:[self instructionIsBL: call])
+ 		ifTrue: [ "a short call/jump" callDistance := self extractOffsetFromBL: call.
+ 			^callSiteReturnAddress + 4 + callDistance signedIntFromLong].
+ 	
+ 	((self instructionIsBX: call) or:[self instructionIsBLX: call])
+ 		ifTrue:["A Long Call/Jump. Extract the value saved to RISCTempReg from all the instructions before."
+ 			^self extractOffsetFromBXAt: callSiteReturnAddress - 4].
+ 	self halt
+ 	!
- 		ifTrue: [ "a short call/jump" callDistance := self extractOffsetFromBL: call]
- 		ifFalse: [ "A Long Call/Jump. Extract the value saved to RISCTempReg from all the instructions before."
- 			((self instructionIsBX: call) or:[self instructionIsBLX: call])
- 				ifTrue:[self extractOffsetFromBXAt: self halt].
- 			self notYetImplemented ].
- 	^callSiteReturnAddress + 4 + callDistance signedIntFromLong!

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].
  			[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 changed:
  ----- Method: CogARMCompiler>>concretizeAddCqR (in category 'generate machine code - concretize') -----
  concretizeAddCqR
  	"Will get inlined into concretizeAt: switch."
  	"Try whether the quick constant is a small negative number. If it is, optimize."
  	<inline: true>
  	self rotateable8bitImmediate: (operands at: 0)
  		ifTrue: [ :rot :immediate | | reg |
  			reg := self concreteRegister: (operands at: 1).
+ 			self machineCodeAt: 0 put: (self adds: reg rn: reg imm: immediate ror: rot<<1).
- 			self machineCodeAt: 0 put: (self adds: reg rn: reg imm: immediate ror: rot).
  			^machineCodeSize := 4]
  		ifFalse: [
  			self rotateable8bitImmediate: (operands at: 0) negated
+ 				ifTrue: [ :rot :immediate | |reg|
+ 					reg := self concreteRegister: (operands at: 1).
+ 					self machineCodeAt: 0 put: (self subs: reg rn: reg imm: immediate ror: rot<<1).
+ 					^machineCodeSize := 4]
- 				ifTrue: [ :r :i | 
- 						opcode := SubCqR.
- 						operands at: 0 put: (operands at: 0) negated.
- 						^self concretizeDataOperationCqR: 2]
  				ifFalse: [^self concretizeDataOperationCwR: 4]]!

Item was added:
+ ----- Method: CogARMCompiler>>concretizeAndCqR (in category 'generate machine code - concretize') -----
+ concretizeAndCqR
+ 	"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 ands: reg rn: reg imm: immediate ror: rot<<1).
+ 			^machineCodeSize := 4]
+ 		ifFalse: [
+ 			"see if the constant bit-inverted makes a quick value and if so BIC it instead
+ 			If the value is -ve, we 2s complement it instead"
+ 			|val|
+ 			val := operands at: 0.
+ 			val <0 ifTrue:[val := -1 - val] ifFalse:[val := val bitInvert32].
+ 			self rotateable8bitImmediate: val
+ 				ifTrue: [ :rot :immediate | |reg|
+ 					reg := self concreteRegister: (operands at: 1).
+ 					self machineCodeAt: 0 put: (self bics: reg rn: reg imm: immediate ror: rot<<1).
+ 					^machineCodeSize := 4]
+ 				ifFalse: [^self concretizeDataOperationCwR: 0]]!

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"
- 	"4 == Add, 2 == Sub, Xor == 1, And == 0, Or == 12"
  	<inline: true>
  	self 
  		rotateable8bitImmediate: (operands at: 0) 
  		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 << 8 bitOr: immediate)).
  			^machineCodeSize := 4]
  		ifFalse: [^self concretizeDataOperationCwR: opcode].
  	!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeLoadEffectiveAddressMwrR (in category 'generate machine code - concretize') -----
  concretizeLoadEffectiveAddressMwrR
  	"Will get inlined into concretizeAt: switch."
  	"destReg = srcReg (which contains an address) + offset"
  	<inline: true>
  	| srcReg offset destReg instrOffset |
  	offset := operands at: 0.
  	srcReg := self concreteRegister: (operands at: 1).
  	destReg := self concreteRegister: (operands at: 2).
  	self rotateable8bitImmediate: offset
  		ifTrue: [ :rot :immediate | 
  			self machineCodeAt: 0 
  				"add destReg, srcReg, #immediate ROR rot"
+ 				put: (self add: destReg rn: srcReg imm: immediate ror: rot<<1).
- 				put: (self add: destReg rn: srcReg imm: immediate ror: rot).
  			^machineCodeSize := 4]
  		ifFalse: [ 
  			instrOffset := self at: 0 moveCw: offset intoR: RISCTempReg.
  			"add destReg, srcReg, RISCTempReg"
  			self machineCodeAt: 16 put: (self add: destReg rn: srcReg rm: RISCTempReg).
  			^machineCodeSize := instrOffset + 4 ]!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveMbrR (in category 'generate machine code - concretize') -----
  concretizeMoveMbrR
  	"Will get inlined into concretizeAt: switch."
+ 	"ldrb destReg, [srcReg, #immediate] or ldrb destReg, [srcReg, RISCTempReg]"
  	<inline: true>
  	| srcReg offset destReg instrOffset|
  	offset := operands at: 0.
  	srcReg := self concreteRegister: (operands at: 1).
  	destReg := self concreteRegister: (operands at: 2).
  	self is12BitValue: offset
  		ifTrue: [ :u :immediate | 
  			self machineCodeAt: 0 
  				"ldrb destReg, [srcReg, #immediate]"
  				put: (self ldrb: destReg rn: srcReg plus: u imm: immediate).
  			^machineCodeSize := 4]
  		ifFalse: [ 
  			instrOffset := self at: 0 moveCw: offset intoR: RISCTempReg.
  			"ldrb destReg, [srcReg, RISCTempReg]"
  			self machineCodeAt: instrOffset put: (self ldrb: destReg rn: srcReg rm: RISCTempReg).
  			^machineCodeSize := instrOffset + 4 ]!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveRAw (in category 'generate machine code - concretize') -----
  concretizeMoveRAw
  	"Will get inlined into concretizeAt: switch."
+ 	"LEA RISCTempReg
+ 	str srcReg, [RISCTempReg]"
  	<inline: true>
  	| srcReg destAddr instrOffset|
  	srcReg := self concreteRegister: (operands at: 0).
  	destAddr := operands at: 1.
  	"load the address into RISCTempReg"
  	instrOffset := self at: 0 moveCw: destAddr intoR: RISCTempReg.
  	"We *could* overwrite the last instruction above with a LDR a, b, last-byte-of-srcAddr BUT that would break if we change to loading literals instead of forming long constants"
  	self machineCodeAt: instrOffset put: (self str: srcReg rn: RISCTempReg plusImm: 0).
  	^machineCodeSize := instrOffset + 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeRetN (in category 'generate machine code - concretize') -----
  concretizeRetN
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| offset |
  	offset := operands at: 0.
  	offset = 0 ifTrue:
  		[self machineCodeAt: 0 put: (self mov: PC rn: LR). "pop	{pc}"
  		^machineCodeSize := 4].
  	self assert: offset < 32. "We have an 8 bit immediate. If needed, we could rotate it less than 30 bit."
  	"add sp, sp, #n, ROR (15<<2) <- ie shift left 2 to convert words to bytes"
  	self machineCodeAt: 0 put: (self add: SP rn: SP imm: offset ror: 30).
  	self machineCodeAt: 4 put: (self mov: PC rn: LR).  "pop	{pc}"
  	^machineCodeSize := 8!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeSubCqR (in category 'generate machine code - concretize') -----
  concretizeSubCqR
  	"Will get inlined into concretizeAt: switch."
  	"Try whether the quick constant is a small negative number. If it is, optimize."
  	<inline: true>
  	self rotateable8bitImmediate: (operands at: 0)
  		ifTrue: [ :rot :immediate | | reg |
  			reg := self concreteRegister: (operands at: 1).
+ 			self machineCodeAt: 0 put: (self subs: reg rn: reg imm: immediate ror: rot<<1).
- 			self machineCodeAt: 0 put: (self type: 1 op: 2 set: 1 rn: reg rd: reg shifterOperand: (rot << 8 bitOr: immediate)).
  			^machineCodeSize := 4]
  		ifFalse: [
+ 			"before building a full load of a big cinstant, see if we can do an add of the constant negated"
  			self rotateable8bitImmediate: (operands at: 0) negated
+ 				ifTrue: [ :rot :immediate | | reg |
+ 					reg := self concreteRegister: (operands at: 1).
+ 					self machineCodeAt: 0 put: (self adds: reg rn: reg imm: immediate ror: rot<<1).
+ 					^machineCodeSize := 4]
- 				ifTrue: [ :r :i | 
- 						opcode := AddCqR.
- 						operands at: 0 put: (operands at: 0) negated.
- 						^self concretizeDataOperationCqR: 4]
  				ifFalse: [^self concretizeDataOperationCwR: 2]]!

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: 4].
  		[AddRR]						-> [^self concretizeDataOperationRR: 4].
  		"[AddRdRd]					-> [^self concretizeSEE2OpRdRd: 16r58]."
+ 		[AndCqR]					-> [^self concretizeAndCqR].
- 		[AndCqR]					-> [^self concretizeDataOperationCqR: 0].
  		[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: 16rC].
  		[OrCwR]					-> [^self concretizeDataOperationCwR: 16rC].
  		[OrRR]						-> [^self concretizeDataOperationRR: 16rC].
  		[SubCqR]					-> [^self concretizeSubCqR].
  		[SubCwR]					-> [^self concretizeDataOperationCwR: 2].
  		[SubRR]						-> [^self concretizeDataOperationRR: 2].
  		"[SubRdRd]					-> [^self concretizeSEE2OpRdRd: 16r5C]."
  		[SqrtRd]						-> [^self concretizeSqrtRd].
  		[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>>extractOffsetFromBXAt: (in category 'testing') -----
  extractOffsetFromBXAt: address
  "this should return the long call/jump target"
+ 	^(objectMemory byteAt: address -4) 
+ 		+ ((objectMemory byteAt: address - 8) << 8) 
+ 		+ ((objectMemory byteAt: address - 12) << 16) 
+ 		+ ((objectMemory byteAt: address - 16) << 24)!
- 	self notYetImplemented!

Item was added:
+ ----- Method: CogARMCompiler>>genAlignCStackSavingRegisters:numArgs:wordAlignment: (in category 'abi') -----
+ genAlignCStackSavingRegisters: saveRegs numArgs: numArgs wordAlignment: alignment 
+ "ARM needs 8 byte stack alignment but it's hard to be sure where the stack is at this point due to the cpmplexities 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"
+ 	cogit BICCq: 2r111 R: SPReg.
+ 	^ 0!

Item was changed:
  ----- Method: CogARMCompiler>>genGetLeafCallStackPointerFunction (in category 'assertions') -----
  genGetLeafCallStackPointerFunction
+ "create a tiny leaf function that just returns the SP in r0; doesn't seem to actually get used. "
  	cogit MoveR: SP R: R0.
  	cogit RetN: 0!

Item was changed:
  ----- Method: CogARMCompiler>>isCallPreceedingReturnPC: (in category 'testing') -----
  isCallPreceedingReturnPC: mcpc
  	"Assuming mcpc is a return pc answer if the instruction before it is a call."
  	"There are two types of calls: BL and/BLX encoding"
  	| call |
  	call := self instructionBeforeAddress: mcpc.
+ 	^(self instructionIsBL: call) or:[self instructionIsBLX: call]!
- 	^(self instructionIsBX: call) or:[self instructionIsBLX: call]!

Item was added:
+ ----- Method: CogARMCompiler>>rewriteCallAt:target: (in category 'inline cacheing') -----
+ rewriteCallAt: callSiteReturnAddress target: callTargetAddress
+ 	"Rewrite a call instruction to call a different target.  This variant is used to link PICs
+ 	 in ceSendMiss et al, and to rewrite cached primitive calls.   Answer the extent of
+ 	 the code change which is used to compute the range of the icache to flush."
+ 	<var: #callSiteReturnAddress type: #usqInt>
+ 	<var: #callTargetAddress type: #usqInt>
+ 	| callDistance call |
+ 	"self cCode: ''
+ 		inSmalltalk: [cogit disassembleFrom: callSiteReturnAddress - 10 to: callSiteReturnAddress - 1]."
+ 	false
+ 		ifTrue: [self assert: callTargetAddress >= cogit minCallAddress]
+ 		ifFalse: [callTargetAddress >= cogit minCallAddress ifFalse:
+ 					[self error: 'linking callsite to invalid address']].
+ 	callDistance := (callTargetAddress - (callSiteReturnAddress + 8 "pc offset"- 4 "return offset")) signedIntToLong.
+ 	self assert: (self isQuick: callDistance). "we don't support long call updates, yet"
+ 	call := self cond: AL br: 1 offset: callDistance.
+ 	objectMemory longAt:  callSiteReturnAddress - 4 put: call.
+ 
+ 	self assert: (self callTargetFromReturnAddress: callSiteReturnAddress) signedIntToLong = callTargetAddress.
+ 	"self cCode: ''
+ 		inSmalltalk: [cogit disassembleFrom: callSiteReturnAddress - 10 to: callSiteReturnAddress - 1]."
+ 	^4!

Item was added:
+ ----- Method: CogARMCompiler>>rewriteJumpLongAt:target: (in category 'inline cacheing') -----
+ rewriteJumpLongAt: callSiteReturnAddress target: callTargetAddress
+ 	"Rewrite a long jump instruction to jump to a different target.  This variant
+ 	 is used to rewrite cached primitive calls.   Answer the extent of the
+ 	 code change which is used to compute the range of the icache to flush."
+ 	<var: #callSiteReturnAddress type: #usqInt>
+ 	<var: #callTargetAddress type: #usqInt>
+ 	"cogit disassembleFrom: callSiteReturnAddress - 40 to: callSiteReturnAddress + 9"
+ 
+ 	"check that the instruction involved is actually a long jump BX"
+ 	self assert: (objectMemory longAt:  callSiteReturnAddress - 4) = 16rE12FFF1A .
+ 	
+ 	"The callTargetAddress is loaded byte by byte."
+ 	objectMemory byteAt: callSiteReturnAddress - 20 put: (callTargetAddress >> 24 bitAnd: 16rFF).
+ 	objectMemory byteAt: callSiteReturnAddress - 16 put: (callTargetAddress >> 16 bitAnd: 16rFF).
+ 	objectMemory byteAt: callSiteReturnAddress - 12 put: (callTargetAddress >> 8 bitAnd: 16rFF).
+ 	objectMemory byteAt: callSiteReturnAddress - 8 put: (callTargetAddress  bitAnd: 16rFF).
+ 
+ 	self assert: (self callTargetFromReturnAddress: callSiteReturnAddress) signedIntToLong = callTargetAddress.
+ 	"self cCode: ''
+ 		inSmalltalk: [cogit disassembleFrom: callSiteReturnAddress - 20 to: callSiteReturnAddress - 1]."
+ 	^20!

Item was added:
+ ----- Method: CogARMCompiler>>subs:rn:imm:ror: (in category 'ARM convenience instructions') -----
+ subs: destReg rn: srcReg imm: immediate ror: rot
+ "return a SUBDS destReg, srcReg, immediat ROR rot instruction. Remember the ROR is doubled by the cpu so use 30>>1 etc"
+ 
+ 	^self type: 1 op: 2 set: 1 rn: srcReg rd: destReg shifterOperand: ((rot>>1) <<8 bitOr: immediate)!

Item was changed:
  ----- Method: CogARMCompilerForTests class>>dataRegistersWithAccessorsDo: (in category 'test support') -----
  dataRegistersWithAccessorsDo: aTrinaryBlock
  	"r0 ... sp. We can't use pc or RISCTempReg, because some opcodes may be encoded as multiple instructions and this, we need to be able to step."
  	#(0 1 2 3 4 5 6 7 8 9 11 12 13 14) withIndexDo:
  		[:reg :i|
  		aTrinaryBlock
  			value: reg
+ 			value: (#(r0 r1 r2 r3 r4 r5 r6 r7 r8 r9 fp r12 sp lr) at: i)
+ 			value: (#(r0: r1: r2: r3: r4: r5: r6: r7: r8: r9: fp: r12: sp: lr:) at: i)]!
- 			value: (#(r0 r1 r2 r3 r4 r5 r6 r7 r8 r9 r11 r12 sp lr) at: i)
- 			value: (#(r0: r1: r2: r3: r4: r5: r6: r7: r8: r9: r11: r12: sp: lr:) at: i)]!

Item was changed:
  SharedPool subclass: #CogRTLOpcodes
  	instanceVariableNames: ''
+ 	classVariableNames: 'AddCqR AddCwR AddRR AddRdRd AlignmentNops AndCqR AndCwR AndRR Arg0Reg Arg1Reg ArithmeticShiftRightCqR ArithmeticShiftRightRR BICCqR 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 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 PopR PrefetchAw PushCw PushR ReceiverResultReg RetN SPReg SendNumArgsReg SqrtRd SubCqR SubCwR SubRR SubRdRd TempReg 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 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 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.  
  	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."
  
  	"CogRTLOpcodes initialize.
  	 CogAbstractInstruction allSubclasses do: [:sc| sc initialize]"
  
  	| 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.
  
  	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
  						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 BICCqR "tpr - ARM only" OrCqR XorCqR MulCqR
- 						CmpCqR AddCqR SubCqR AndCqR OrCqR XorCqR MulCqR
  						CmpCwR AddCwR SubCwR AndCwR OrCwR XorCwR MulCwR
  
  						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!

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

Item was changed:
  ----- Method: Cogit>>compileTrampolineFor:callJumpBar:numArgs:arg:arg:arg:arg:saveRegs:resultReg: (in category 'initialization') -----
  compileTrampolineFor: aRoutine callJumpBar: callJumpBar "<Boolean>" numArgs: numArgs arg: regOrConst0 arg: regOrConst1 arg: regOrConst2 arg: regOrConst3 saveRegs: saveRegs 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>
  	"If on a RISC processor the return address needs to be pushed to the
  	 stack so that the interpreter sees the same stack layout as on CISC."
+ 	"tpr evil test hack for stack imbalance problem"
+ 	aRoutine ~=  #ceCheckForInterrupts ifTrue:[backEnd hasLinkRegister ifTrue:
+ 		[self PushR: LinkReg]].
- 	backEnd hasLinkRegister ifTrue:
- 		[self PushR: LinkReg].
  	self genSmalltalkToCStackSwitch.
  	cStackAlignment > BytesPerWord ifTrue:
  		[backEnd
  			genAlignCStackSavingRegisters: saveRegs
  			numArgs: numArgs
  			wordAlignment: cStackAlignment / BytesPerWord].
  	saveRegs ifTrue:
  		[callJumpBar ifFalse:
  			[self error: 'why save registers when you''re not going to return?'].
  		 backEnd genSaveRegisters].
  	numArgs > 0 ifTrue:
  		[numArgs > 1 ifTrue:
  			[numArgs > 2 ifTrue:
  				[numArgs > 3 ifTrue:
  					[regOrConst3 < 0
  						ifTrue: [backEnd genPassReg: regOrConst3 asArgument: 3]
  						ifFalse: [backEnd genPassConst: regOrConst3 asArgument: 3]].
  				 regOrConst2 < 0
  					ifTrue: [backEnd genPassReg: regOrConst2 asArgument: 2]
  					ifFalse: [backEnd genPassConst: regOrConst2 asArgument: 2]].
  			regOrConst1 < 0
  				ifTrue: [backEnd genPassReg: regOrConst1 asArgument: 1]
  				ifFalse: [backEnd genPassConst: regOrConst1 asArgument: 1]].
  		regOrConst0 < 0
  			ifTrue: [backEnd genPassReg: regOrConst0 asArgument: 0]
  			ifFalse: [backEnd genPassConst: regOrConst0 asArgument: 0]].
  	self gen: (callJumpBar ifTrue: [Call] ifFalse: [Jump])
  		operand: (self cCode: [aRoutine asUnsignedInteger]
  					   inSmalltalk: [self simulatedTrampolineFor: aRoutine]).
  	callJumpBar ifTrue:
  		[resultRegOrNil ifNotNil:
  			[backEnd genWriteCResultIntoReg: resultRegOrNil].
  		 saveRegs ifTrue:
  			[numArgs > 0 ifTrue:
  				[backEnd genRemoveNArgsFromStack: numArgs].
  			resultRegOrNil
  				ifNotNil: [backEnd genRestoreRegsExcept: resultRegOrNil]
  				ifNil: [backEnd genRestoreRegs]].
  		backEnd genLoadStackPointers.
  		backEnd hasLinkRegister ifTrue:
  			[self PopR: LinkReg].
  		self RetN: 0]!

Item was changed:
  ----- Method: Cogit>>genNonLocalReturnTrampoline (in category 'initialization') -----
  genNonLocalReturnTrampoline
  	opcodeIndex := 0.
+ 	"write the return address to the coInterpreter instructionPointerAddress; IA32 will have pushed it on the stack, so pop it first; ARM will have it in LR so just write it"
  	backEnd hasLinkRegister
  		ifTrue:
  			[self MoveR: LinkReg Aw: coInterpreter instructionPointerAddress]
  		ifFalse:
  			[self PopR: TempReg. "instruction pointer"
  			 self MoveR: TempReg Aw: coInterpreter instructionPointerAddress].
  	^self genTrampolineFor: #ceNonLocalReturn:
  		called: 'ceNonLocalReturnTrampoline'
  		callJumpBar: true
  		numArgs: 1
  		arg: ReceiverResultReg
  		arg: nil
  		arg: nil
  		arg: nil
  		saveRegs: false
  		resultReg: nil
  		appendOpcodes: true!

Item was changed:
  ----- Method: Cogit>>initializeProcessor (in category 'initialization') -----
  initializeProcessor
  	"Initialize the simulation processor, arranging that its initial stack is somewhere on the rump C stack."
  	<doNotGenerate>
  	guardPageSize := self class guardPageSize.
  	lastNInstructions := OrderedCollection new.
+ 	processor initializeStackFor: self.
- 	"This is for testing.  On many OS's the stack must remain aligned;
- 	 e.g. IA32 using SSE requires 16 byte alignment."
- 	expectedSPAlignment := 0. expectedFPAlignment := 8. cStackAlignment := 16.
- 	processor class setStackAlignmentDelta: cStackAlignment.
  	self initializeProcessorStack: coInterpreter rumpCStackAddress.
  	objectMemory
  		longAt: self cFramePointerAddress put: processor fp;
  		longAt: self cStackPointerAddress put: processor sp.
  	threadManager ifNotNil:
  		[processor := MultiProcessor for: processor coInterpreter: coInterpreter]!

Item was changed:
  ----- Method: Cogit>>recordProcessing (in category 'simulation only') -----
  recordProcessing
  	| inst |
  	self recordRegisters.
  	inst := self recordLastInstruction.
  	printRegisters ifTrue:
  		[processor printRegistersOn: coInterpreter transcript].
  	printInstructions ifTrue:
  		[printRegisters ifTrue:
  			[coInterpreter transcript cr].
+ 		 coInterpreter transcript nextPutAll: inst; cr; flush.
+ 		processor writePopPushDetailsIn: coInterpreter memory in: coInterpreter transcript for: self]!
- 		 coInterpreter transcript nextPutAll: inst; cr; flush]!

Item was added:
+ ----- Method: Cogit>>setStackAlignment:expectedSPOffset:expectedFPOffset: (in category 'initialization') -----
+ setStackAlignment: stackAlignment expectedSPOffset: spOffset expectedFPOffset: fpOffset
+ 	"the processor wants certain stack alignment settings"
+ 	expectedSPAlignment := spOffset. 
+ 	expectedFPAlignment := fpOffset. 
+ 	cStackAlignment := stackAlignment
+ !

Item was added:
+ ----- Method: Cogit>>simulatedVariableAt: (in category 'initialization') -----
+ simulatedVariableAt: address
+ 	"Answer a simulated variable's value for handling the push/pop tracer."
+ 	<doNotGenerate>
+ 	^(simulatedVariableGetters
+ 		at: address
+ 		ifAbsent:[0]) value!



More information about the Vm-dev mailing list