[Vm-dev] VM Maker: VMMaker.oscog-lw.193.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Aug 1 12:03:35 UTC 2012


Lars Wassermann uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-lw.193.mcz

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

Name: VMMaker.oscog-lw.193
Author: lw
Time: 1 August 2012, 2:00:23.969 pm
UUID: 930a01b6-2f8b-9b4e-b8c2-a1357af8276c
Ancestors: VMMaker.oscog-lw.192

- added some more concretize methods, namely some move methods with multiplication (e.g. MoveRXwrR), and LoadEffectiveAddressMwrR

- added tests for PrefetchAw, MoveCwR and PushR. MoveCwR is used in half the opcodes, whenever there is a word-constant. Therefore testing was important.

- changed the preamble of Call, because for call, there should not be sane address checks.

=============== Diff against VMMaker.oscog-lw.192 ===============

Item was changed:
  ----- Method: CogARMCompiler>>callerSavedRegisterMask (in category 'accessing') -----
  callerSavedRegisterMask
+ 	"registers r0-r3, the lowest four, +lr"
+ 		^16r40F!
- 	"registers r0-r3, the lowest four"
- 		^16rF!

Item was changed:
  ----- Method: CogARMCompiler>>computeMaximumSize (in category 'generate machine code') -----
  computeMaximumSize
  	"Because we don't use Thumb, each instruction has a multiple of 4 bytes. Most have exactly 4, but some abstract opcodes need more than one instruction."
  	
  	({CmpCqR. AddCqR. SubCqR. AndCqR. OrCqR. XorCqR} 
  		anySatisfy: [ :each | each = opcode])
  			ifTrue: [^self rotateable8bitImmediate: (operands at: 0)
  											ifTrue: [:r :i| maxSize := 4]
  											ifFalse: [maxSize := 20]].
  	({CmpCwR. AddCwR. SubCwR. AndCwR. OrCwR. XorCwR} 
  		anySatisfy: [ :each | each = opcode])
  			ifTrue: [^maxSize := 20].
  	
  	({Jump. JumpR. JumpZero. JumpNonZero. JumpNegative. JumpNonNegative. JumpOverflow.
  	JumpOverflow. JumpNoOverflow. JumpCarry. JumpNoCarry. JumpLess. JumpGreaterOrEqual. JumpGreater. JumpLessOrEqual. JumpBelow. JumpAboveOrEqual} 
  		anySatisfy: [ :each | each = opcode])
  			ifTrue: [^maxSize := 20].
  	
  	opcode
  		caseOf: {
  			[Label]					-> [^maxSize := 0].
  			[AlignmentNops]		-> [^maxSize := (operands at: 0) - 1].
  			[MoveAwR]				-> [^maxSize := 16].
  			[MoveCqR]				-> [^self rotateable8bitImmediate: (operands at: 0)
  											ifTrue: [:r :i| maxSize := 4]
  											ifFalse: [maxSize := 16]].
  			[MoveCwR]				-> [^maxSize := 16].
  			[MoveRAw]				-> [^maxSize := 16].
+ 			[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 := 16].
  			[RetN]					-> [^(operands at: 0) = 0 
  											ifTrue: [maxSize := 4]
  											ifFalse: [maxSize := 8]].
  			[JumpR]					-> [^maxSize := 8].
  			[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] -> [self rotateable8bitImmediate: (operands at: 0)
+ 												ifTrue: [ :r :i | ^maxSize := 4]
+ 												ifFalse: [^maxSize := 20]].
+ 			[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)
- 	^self rotateable8bitImmediate: (operands at: 0)
  		ifTrue: [ :rot :immediate | | reg |
  			reg := self concreteRegister: (operands at: 1).
  			self machineCodeAt: 0 put: ((self t: 1 o: 4 s: 1) bitOr: reg << 16).
  			machineCode at: 0 put: immediate.
  			machineCode at: 1 put: (reg << 4 bitOr: rot).
  			^machineCodeSize := 4]
  		ifFalse: [
  			self rotateable8bitImmediate: (operands at: 0) negated
  				ifTrue: [ :r :i | 
  						opcode := SubCqR.
  						operands at: 0 put: (operands at: 0) negated.
+ 						^self concretizeDataOperationCqR: 2]
+ 				ifFalse: [^self concretizeDataOperationCwR: 4]]!
- 						self concretizeDataOperationCqR: 2]
- 				ifFalse: [self concretizeDataOperationCwR: 4]]!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeCall (in category 'generate machine code - concretize') -----
  concretizeCall
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
+ 	| offset |
+ 	self assert: (operands at: 0) ~= 0.
+ 	self assert: (operands at: 0) \\ 4 = 0.
+ 	offset := (operands at: 0) signedIntFromLong - (address + 8) signedIntFromLong.
- 	| jumpTarget offset |
- 	"TODO extract method: jumpTarget calculator together with CogIA32Compiler>>concretizeConditionalJump: and self class>>concretizeConditionalJump:"
- 	<var: #jumpTarget type: #'AbstractInstruction *'>
- 	jumpTarget := cogit cCoerceSimple: (operands at: 0) to: #'AbstractInstruction *'.
- 	cogit assertSaneJumpTarget: jumpTarget.
- 	(self isAnInstruction: jumpTarget) ifTrue:
- 		[jumpTarget := cogit cCoerceSimple: jumpTarget address to: #'AbstractInstruction *'].
- 	self assert: jumpTarget ~= 0.
- 	offset := jumpTarget signedIntFromLong - (address + 8) signedIntFromLong.
-  	
  	(self isQuick: offset)
  		ifTrue: [
  			self machineCodeAt: 0 put: (self t: 5 o: 8) + (offset >> 2 bitAnd: 16r00FFFFFF). "BL offset"
  			^machineCodeSize := 4]
  		ifFalse: [
  			self halt]
  	"We should push at least lr. The problem is, that any push added here is only executed after return, and therefore useless."!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeConditionalJump: (in category 'generate machine code - concretize') -----
  concretizeConditionalJump: conditionCode
  	"Will get inlined into concretizeAt: switch."
  	"Sizing/generating jumps.
  		Jump targets can be to absolute addresses or other abstract instructions.
  		Generating initial trampolines instructions may have no maxSize and be to absolute addresses.
  		Otherwise instructions must have a machineCodeSize which must be kept to."
  	<inline: true>
  	| offset |
  	offset := self computeJumpTargetOffsetPlus: 8.
   	(self isQuick: offset)
  		ifTrue: [
  			self machineCodeAt: 0 put: (self t: 5 o: 8) + (offset >> 2 bitAnd: 16r00FFFFFF). "BL offset"
  			^machineCodeSize := 4]
  		ifFalse: [
+ 			^self concretizeConditionalJumpLong: conditionCode]!
- 			self concretizeConditionalJumpLong: conditionCode]!

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"
- 	"For 0, we can mov reg, #0"
  	<inline: true>
  	self 
  		rotateable8bitImmediate: (operands at: 0) 
  		ifTrue: [:rot :immediate | | reg |
  			reg := self concreteRegister: (operands at: 1).
  			self machineCodeAt: 0 put: ((self t: 1 o: opcode s: 1) bitOr: reg << 16).
  			machineCode at: 0 put: immediate.
  			machineCode at: 1 put: (reg << 4 bitOr: rot).
  			^machineCodeSize := 4]
  		ifFalse: [^self concretizeDataOperationCwR: opcode].
  	!

Item was added:
+ ----- Method: CogARMCompiler>>concretizeLoadEffectiveAddressMwrR (in category 'generate machine code - concretize') -----
+ concretizeLoadEffectiveAddressMwrR
+ 	"Will get inlined into concretizeAt: switch."
+ 	"destReg = destReg + offset"
+ 	<inline: true>
+ 	| srcReg offset destReg |
+ 	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"
+ 				put: (self t: 1 o: 4 s: 0 rn: srcReg rd: destReg shifterOperand: (rot <<8 bitOr: immediate)).
+ 			^machineCodeSize := 4]
+ 		ifFalse: [ 
+ 			self at: 0 moveCw: offset intoR: RISCTempReg.
+ 			"add destReg, srcReg, RISCTempReg"
+ 			self machineCodeAt: 16 put: (self t: 0 o: 4 s: 0 rn: srcReg rd: destReg shifterOperand: RISCTempReg).
+ 			^machineCodeSize := 20 ]!

Item was added:
+ ----- Method: CogARMCompiler>>concretizeMoveMbrR (in category 'generate machine code - concretize') -----
+ concretizeMoveMbrR
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| srcReg offset destReg |
+ 	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 
+ 				"ldr destReg, [srcReg, #immediate]"
+ 				put: (self t: 2 o: (16rA bitOr: u <<2) s: 1 rn: srcReg rd: destReg shifterOperand: immediate).
+ 			^machineCodeSize := 4]
+ 		ifFalse: [ 
+ 			self at: 0 moveCw: offset intoR: RISCTempReg.
+ 			"ldr destReg, [srcReg, RISCTempReg]"
+ 			self machineCodeAt: 16 put: (self t: 3 o: 16rE s: 1 rn: srcReg rd: destReg shifterOperand: RISCTempReg).
+ 			^machineCodeSize := 20 ]!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveMwrR (in category 'generate machine code - concretize') -----
  concretizeMoveMwrR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset destReg |
  	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 
+ 				"ldr destReg, [srcReg, #immediate]"
  				put: (self t: 2 o: (8 bitOr: u <<2) s: 1 rn: srcReg rd: destReg shifterOperand: immediate).
  			^machineCodeSize := 4]
  		ifFalse: [ 
  			self at: 0 moveCw: offset intoR: RISCTempReg.
+ 			"ldr destReg, [srcReg, RISCTempReg]"
+ 			self machineCodeAt: 16 put: (self t: 3 o: 16rC s: 1 rn: srcReg rd: destReg shifterOperand: RISCTempReg).
- 			self machineCodeAt: 16 put: (self t: 0 o: 4 s: 0 rn: srcReg rd: destReg shifterOperand: RISCTempReg).
  			^machineCodeSize := 20 ]!

Item was added:
+ ----- Method: CogARMCompiler>>concretizeMoveRMbr (in category 'generate machine code - concretize') -----
+ concretizeMoveRMbr
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| srcReg offset destReg |
+ 	srcReg := self concreteRegister: (operands at: 0).
+ 	offset := operands at: 1.
+ 	destReg := self concreteRegister: (operands at: 2).
+ 	self is12BitValue: offset
+ 		ifTrue: [ :u :immediate | 
+ 			"ldr:       (self t: 2 o: (8 bitOr: u <<2) s: 1 rn: srcReg rd: destReg shifterOperand: immediate)."
+ 			self machineCodeAt: 0 
+ 			"strb 	destReg, [srcReg, #immediate]"
+ 				put: (self t: 2 o: (16rA bitOr: u<<2) s: 0 rn: destReg rd: srcReg shifterOperand: immediate).
+ 			^machineCodeSize := 4]
+ 		ifFalse: [ 
+ 			self at: 0 moveCw: offset intoR: RISCTempReg.
+ 			"strb 	destReg, [srcReg, RISCTempReg]"
+ 			self machineCodeAt: 16 put: (self t: 3 o: 16rE s: 0 rn: srcReg rd: destReg shifterOperand: RISCTempReg).
+ 			^machineCodeSize := 20 ]!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveRMwr (in category 'generate machine code - concretize') -----
  concretizeMoveRMwr
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg offset destReg |
  	srcReg := self concreteRegister: (operands at: 0).
  	offset := operands at: 1.
  	destReg := self concreteRegister: (operands at: 2).
  	self is12BitValue: offset
  		ifTrue: [ :u :immediate | 
+ 			"ldr     (self t: 2 o: (8 bitOr: u <<2) s: 1 rn: srcReg rd: destReg shifterOperand: immediate)."
- 			"LDR"
- 			"STR:     (self t: 2 o: (8 bitOr: u <<2) s: 1 rn: srcReg rd: destReg shifterOperand: immediate)."
  			self machineCodeAt: 0 
+ 			"strb 	destReg, [srcReg, #immediate]"
  				put: (self t: 2 o: (8 bitOr: u<<2) s: 0 rn: destReg rd: srcReg shifterOperand: immediate).
  			^machineCodeSize := 4]
  		ifFalse: [ 
+ 			self at: 0 moveCw: offset intoR: RISCTempReg.
+ 			"strb 	destReg, [srcReg, RISCTempReg]"
+ 			self machineCodeAt: 16 put: (self t: 3 o: 16rC s: 0 rn: srcReg rd: destReg shifterOperand: RISCTempReg).
- 			self halt.
- 			
  			^machineCodeSize := 20 ]!

Item was added:
+ ----- Method: CogARMCompiler>>concretizeMoveRX16rR (in category 'generate machine code - concretize') -----
+ concretizeMoveRX16rR
+ 	"Will get inlined into concretizeAt: switch."
+ 	"Write the word in R(src) into memory at address (base+2*index)"
+ 	<inline: true>
+ 	| index base src |
+ 	src := self concreteRegister: (operands at: 0).
+ 	index := self concreteRegister: (operands at: 1).
+ 	base := self concreteRegister: (operands at: 2).
+ 	"str		src, [base, +index, LSL #1]"
+ 	"cond 011 1100 0 base srcR 00001 00 0 inde"
+ 	self machineCodeAt: 0 put: (self t: 3 o: 16rC s: 0 rn: base rd: src shifterOperand: (16r080 bitOr: index)).
+ 	^machineCodeSize := 4!

Item was added:
+ ----- Method: CogARMCompiler>>concretizeMoveRXbrR (in category 'generate machine code - concretize') -----
+ concretizeMoveRXbrR
+ 	"Will get inlined into concretizeAt: switch."
+ 	"Write the word in R(src) into memory at address (base+1*index)"
+ 	<inline: true>
+ 	| index base src |
+ 	src := self concreteRegister: (operands at: 0).
+ 	index := self concreteRegister: (operands at: 1).
+ 	base := self concreteRegister: (operands at: 2).
+ 	"str		src, [base, +index, LSL #0]"
+ 	"cond 011 1100 0 base srcR 00000 00 0 inde"
+ 	self machineCodeAt: 0 put: (self t: 3 o: 16rC s: 0 rn: base rd: src shifterOperand: index).
+ 	^machineCodeSize := 4!

Item was added:
+ ----- Method: CogARMCompiler>>concretizeMoveRXwrR (in category 'generate machine code - concretize') -----
+ concretizeMoveRXwrR
+ 	"Will get inlined into concretizeAt: switch."
+ 	"Write the word in R(src) into memory at address (base+4*index)"
+ 	<inline: true>
+ 	| index base src |
+ 	src := self concreteRegister: (operands at: 0).
+ 	index := self concreteRegister: (operands at: 1).
+ 	base := self concreteRegister: (operands at: 2).
+ 	"str		src, [base, +index, LSL #2]"
+ 	"cond 011 1100 0 base srcR 00010 00 0 inde"
+ 	self machineCodeAt: 0 put: (self t: 3 o: 16rC s: 0 rn: base rd: src shifterOperand: (16r100 bitOr: index)).
+ 	^machineCodeSize := 4!

Item was added:
+ ----- Method: CogARMCompiler>>concretizePrefetchAw (in category 'generate machine code - concretize') -----
+ concretizePrefetchAw
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| addressOperand |
+ 	addressOperand := operands at: 0.
+ 	self at: 0 moveCw: addressOperand intoR: RISCTempReg.
+ 	"pld	[RISCTempReg, +<byte 0>]"
+ 	"u = 1, I = 0"
+ 	"1111 0101 1101 RTem 1111 0000 byte"
+ 	machineCode
+ 		at: 15 put: 16rF5;
+ 		at: 14 put: (16rD0 bitOr: RISCTempReg);
+ 		at: 13 put: 16rF0.
+ 	^machineCodeSize := 16!

Item was added:
+ ----- Method: CogARMCompiler>>concretizePushCw (in category 'generate machine code - concretize') -----
+ concretizePushCw
+ 	"Will get inlined into concretizeAt: switch."
+ 	<inline: true>
+ 	| word |
+ 	word := operands at: 0.
+ 	self at: 0 moveCw: word intoR: RISCTempReg.
+ 	self machineCodeAt: 16 put: (self t: 2 o: 9 s: 0 rn: SP rd: RISCTempReg shifterOperand: 4).
+ 	^machineCodeSize := 20!

Item was changed:
  ----- Method: CogARMCompiler>>concretizePushR (in category 'generate machine code - concretize') -----
  concretizePushR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg |
  	srcReg := self concreteRegister: (operands at: 0).
+ 	"cond | 010 | 1001 | 0 | -Rn- | -Rd- | 0000 0000 0100" "STR srcReg, [sp, #-4]"
+ 	self machineCodeAt: 0 put: (self t: 2 o: 9 s: 0 rn: SP rd: srcReg shifterOperand: 4).
- 	"cond | 010 | 1001 | 1 | -Rn- | -Rd- | 0000 0000 0100" "STR srcReg, [sp, #-4]"
- 	self machineCodeAt: 0 put: (self t: 2 o: 9 s: 1 rn: SP rd: srcReg shifterOperand: 4).
  	^machineCodeSize := 4!

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)
- 	^self rotateable8bitImmediate: (operands at: 0)
  		ifTrue: [ :rot :immediate | | reg |
  			reg := self concreteRegister: (operands at: 1).
  			self machineCodeAt: 0 put: ((self t: 1 o: 2 s: 1) bitOr: reg << 16).
  			machineCode at: 0 put: immediate.
  			machineCode at: 1 put: (reg << 4 bitOr: rot).
  			^machineCodeSize := 4]
  		ifFalse: [
  			self rotateable8bitImmediate: (operands at: 0) negated
  				ifTrue: [ :r :i | 
  						opcode := AddCqR.
  						operands at: 0 put: (operands at: 0) negated.
+ 						^self concretizeDataOperationCqR: 4]
+ 				ifFalse: [^self concretizeDataOperationCwR: 2]]!
- 						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."
  
  	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: CS]. "according to http://courses.engr.illinois.edu/ece390/books/labmanual/assembly.html"
  		[JumpAboveOrEqual]		-> [^self concretizeConditionalJump: CC]. " --""-- "
  		[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 concretizeDataOperationCqR: 0].
  		[AndCwR]					-> [^self concretizeDataOperationCwR: 0].
  		[AndRR]						-> [^self concretizeDataOperationRR: 0].
  		[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].
  		[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 added:
+ ----- Method: CogARMCompilerTests>>testMoveCwR (in category 'tests') -----
+ testMoveCwR
+ 	"self new testMoveCwR"
+ 	
+ 	| memory |
+ 	memory := ByteArray new: 16.
+ 	#(16rFF00FF00 16r00000012 16r12345678) do:
+ 		[:n| | inst len |
+ 		self concreteCompilerClass dataRegistersWithAccessorsDo: 
+ 			[ :r :rgetter :rset |
+ 			inst := self gen: MoveCwR operand: n operand: r.
+ 			len := inst concretizeAt: 0.
+ 			memory replaceFrom: 1 to: len with: inst machineCode object startingAt: 1.
+ 			self processor
+ 				reset.
+ 			[[processor pc < len] whileTrue:
+ 				[self processor singleStepIn: memory]]
+ 				on: Error
+ 				do: [:ex| ].
+ 			self concreteCompilerClass dataRegistersWithAccessorsDo:
+ 				[:ireg :getter :setter| | expected |
+ 				expected := getter == rgetter ifTrue: [ n ] ifFalse: [0].
+ 				self assert: (self processor perform: getter) = expected].
+ 			self assert: self processor pc = 16]]
+ !

Item was added:
+ ----- Method: CogARMCompilerTests>>testPrefetchAw (in category 'tests') -----
+ testPrefetchAw
+ 	"self new testPrefetchAw"
+ 	
+ 	#(16rFF00FF00 16r00000012) do:
+ 		[:n| | inst len |
+ 		inst := self gen: PrefetchAw operand: n.
+ 		len := inst concretizeAt: 0.
+ 		self processor
+ 			disassembleInstructionAt: 12
+ 			In: inst machineCode object
+ 			into: [:str :sz| | plainJane herIntended |
+ 				"Convert e.g. '00000000: movl %eax, 0x2(%eax) : 89 40 02' to  'movl %eax, 0x2(%eax)'"
+ 				plainJane := self strip: str.
+ 				herIntended := 'pld	[r3', ((n bitAnd: 16rFF) = 0 ifTrue: [''] ifFalse: [', #', (n bitAnd: 16rFF) asString]) ,']'.
+ 				self assert: (plainJane match: herIntended).
+ 				self assert: len = 16]].
+ !

Item was added:
+ ----- Method: CogARMCompilerTests>>testPushR (in category 'tests') -----
+ testPushR
+ 	"self new testPushR"
+ 	
+ 	self concreteCompilerClass registersWithNamesDo:
+ 		[:r :name | | inst len |
+ 		inst := self gen: PushR operand: r.
+ 		len := inst concretizeAt: 0.
+ 		self processor
+ 			disassembleInstructionAt: 0
+ 			In: inst machineCode object
+ 			into: [:str :sz| | plainJane herIntended |
+ 				"Convert e.g. '00000000: movl %eax, 0x2(%eax) : 89 40 02' to  'movl %eax, 0x2(%eax)'"
+ 				plainJane := self strip: str.
+ 				herIntended := 'push	{', name ,'}'.
+ 				self assert: (plainJane match: herIntended).
+ 				self assert: len = 4]].
+ !

Item was changed:
  ----- Method: CogIA32Compiler>>concretizePrefetchAw (in category 'generate machine code') -----
  concretizePrefetchAw
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| addressOperand |
  	machineCodeSize := maxSize.
  	maxSize > 0 ifTrue:
  		[addressOperand := operands at: 0.
  		 machineCode
  			at: 0 put: 16r0f;
  			at: 1 put: 16r18;
+ 			at: 2 put: (self mod: 0 RM: 5 RO: 1); "prefetch0, prefetch using the T0 temporal data hint"
- 			at: 2 put: (self mod: 0 RM: 5 RO: 1); "prefetch0, prefetch using the T0 tremporal data hint"
  			at: 3 put: (addressOperand bitAnd: 16rFF);
  			at: 4 put: (addressOperand >> 8 bitAnd: 16rFF);
  			at: 5 put: (addressOperand >> 16 bitAnd: 16rFF);
  			at: 6 put: (addressOperand >> 24 bitAnd: 16rFF)].
  	^maxSize!



More information about the Vm-dev mailing list