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

commits at source.squeak.org commits at source.squeak.org
Sat Jun 28 22:45:01 UTC 2014


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

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

Name: VMMaker.oscog-tpr.784
Author: tpr
Time: 28 June 2014, 3:42:06.906 pm
UUID: 31d41aa3-9d3c-43fb-b1f6-9bb2f6df8165
Ancestors: VMMaker.oscog-tpr.783

Rework the rotatable quick constant logic a little and clean up users.
Fix concretizeMoveRXbrR to do byte not word loads.
Fix concretizeConditionalJumpLong: to actually be conditional. Oops.

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

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).
- 			self machineCodeAt: 0 put: (self adds: reg rn: reg imm: immediate ror: rot<<1).
  			^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).
- 					self machineCodeAt: 0 put: (self subs: reg rn: reg imm: immediate ror: rot<<1).
  					^machineCodeSize := 4]
  				ifFalse: [^self concretizeDataOperationCwR: 4]]!

Item was changed:
  ----- 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).
- 			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).
- 					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>>concretizeConditionalJumpLong: (in category 'generate machine code - concretize') -----
  concretizeConditionalJumpLong: 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>
  	| jumpTarget instrOffset|
  	<var: #jumpTarget type: #'AbstractInstruction *'>
  	jumpTarget := self longJumpTargetAddress.
  	instrOffset := self at: 0 moveCw: jumpTarget intoR: RISCTempReg.
  	"bx RISCTempReg"
+ 	self machineCodeAt: instrOffset put: (self cond: conditionCode bx: 0 target: RISCTempReg).
- 	self machineCodeAt: instrOffset put: (self bx: RISCTempReg).
  	^machineCodeSize := instrOffset + 4!

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 | | 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)).
- 			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>>concretizeMoveCqR (in category 'generate machine code - concretize') -----
  concretizeMoveCqR
  	"Will get inlined into concretizeAt: switch."
  	"If the quick constant is in fact a shiftable 8bit, generate the apropriate MOV, otherwise do what is necessary for a whole word."
  	<inline: true>
  	self 
  		rotateable8bitImmediate: (operands at: 0) 
  		ifTrue: [:rot :immediate | | reg |
  			reg := self concreteRegister: (operands at: 1).
+ 			self machineCodeAt: 0 put: (self mov: reg imm: immediate ror: rot).
- 			self machineCodeAt: 0 put: (self type: 1 op: 16rD set: 0 rn: 0 rd: reg shifterOperand: (rot << 8 bitOr: immediate)).
  			^machineCodeSize := 4]
  		ifFalse: [^self concretizeMoveCwR].
  	!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveRR (in category 'generate machine code - concretize') -----
  concretizeMoveRR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| srcReg destReg |
  	srcReg := self concreteRegister: (operands at: 0).
  	destReg := self concreteRegister: (operands at: 1).
  	"cond 000 1101 0 0000 dest 0000 0000 srcR"
+ 	self machineCodeAt: 0 put: (self mov: destReg rn: srcReg).
- 	self machineCodeAt: 0 put: (self type: 0 op: 16rD set: 0 rn: 0 rd: destReg shifterOperand: srcReg).
  	^machineCodeSize := 4!

Item was changed:
  ----- 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	b	src, [base, +index, LSL #0]"
+ 	"cond 011 1100 0 base srcR 00000 00 0 index"
+ 	self machineCodeAt: 0 put: (self strb: src rn: base rm: index).
- 	"str		src, [base, +index, LSL #0]"
- 	"cond 011 1100 0 base srcR 00000 00 0 inde"
- 	self machineCodeAt: 0 put: (self type: 3 op: 16rC set: 0 rn: base rd: src shifterOperand: index).
  	^machineCodeSize := 4!

Item was changed:
  ----- 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). "index is number of *words* = 4* bytes"
- 	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 str: src rn: base rm: (16r100 bitOr: index)).
- 	self machineCodeAt: 0 put: (self type: 3 op: 16rC set: 0 rn: base rd: src shifterOperand: (16r100 bitOr: index)).
  	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveXbrRR (in category 'generate machine code - concretize') -----
  concretizeMoveXbrRR
  	"Will get inlined into concretizeAt: switch."
  	
  	<inline: true>
  	| index base dest |
+ 	index := self concreteRegister: (operands at: 0). "index is number of *bytes*"
- 	index := self concreteRegister: (operands at: 0).
  	base := self concreteRegister: (operands at: 1).
  	dest := self concreteRegister: (operands at: 2).
+ 	"LDRB	dest, [base, +index, LSL #0]"
- 	"LDR	dest, [base, +index, LSL #0]"
  	"cond 011 1100 1 base dest 00000 00 0 inde"
+ 	self machineCodeAt: 0 put: (self ldrb: dest rn: base rm: index).
- 	self machineCodeAt: 0 put: (self type: 3 op: 16rC set: 1 rn: base rd: dest shifterOperand: index).
  	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeMoveXwrRR (in category 'generate machine code - concretize') -----
  concretizeMoveXwrRR
  	"Will get inlined into concretizeAt: switch."
  	
  	<inline: true>
  	| index base dest |
  	index := self concreteRegister: (operands at: 0).
  	base := self concreteRegister: (operands at: 1).
  	dest := self concreteRegister: (operands at: 2).
  	"LDR	dest, [base, +index, LSL #2]"
  	"cond 011 1100 1 base dest 00010 00 0 inde"
+ 	self machineCodeAt: 0 put: (self ldr: dest rn: base rm: (16r100 bitOr: index)).
- 	self machineCodeAt: 0 put: (self type: 3 op: 16rC set: 1 rn: base rd: dest shifterOperand: (16r100 bitOr: index)).
  	^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)
  		ifTrue: [ :rot :immediate | | reg |
  			reg := self concreteRegister: (operands at: 1).
+ 			self machineCodeAt: 0 put: (self subs: reg rn: reg imm: immediate ror: rot).
- 			self machineCodeAt: 0 put: (self subs: reg rn: reg imm: immediate ror: rot<<1).
  			^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).
- 					self machineCodeAt: 0 put: (self adds: reg rn: reg imm: immediate ror: rot<<1).
  					^machineCodeSize := 4]
  				ifFalse: [^self concretizeDataOperationCwR: 2]]!

Item was changed:
  ----- Method: CogARMCompiler>>rotateable8bitImmediate:ifTrue:ifFalse: (in category 'testing') -----
  rotateable8bitImmediate: constant ifTrue: trueAlternativeBlock ifFalse: falseAlternativeBlock
  	"For data processing operands, there is the immediate shifter_operand variant, 
  	where an 8 bit value is ring shifted _right_ by 2*i.
  	This is only suitable for quick constant(Cq), which don't change."
  	
  	(constant bitAnd: 16rFF) = constant ifTrue: [ ^trueAlternativeBlock value: 0 value: constant].
+ 	2 to: 30 do: [:i |
+ 		(constant bitAnd: 16rFF << i) = constant 
+ 			ifTrue: [ ^trueAlternativeBlock value: 32 - i value: constant >> i ]].
- 	1 to: 15 do: [:i |
- 		(constant bitAnd: 16rFF << (i<<1)) = constant 
- 			ifTrue: [ ^trueAlternativeBlock value: 16 - i value: constant >> (i << 1)]].
  	^falseAlternativeBlock value!



More information about the Vm-dev mailing list