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

commits at source.squeak.org commits at source.squeak.org
Wed Apr 1 04:13:11 UTC 2015


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

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

Name: VMMaker.oscog-tpr.1143
Author: tpr
Time: 31 March 2015, 9:11:29.066 pm
UUID: 76e7613a-1b56-4e2b-9932-42df34c06102
Ancestors: VMMaker.oscog-eem.1142

More constant generation improvements in CogARMCompiler.
Also some NSSendCacheSurrogate categorization changes that are there purely as artefacts of MC usage and don't actually represent any deliberate change at all.

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

Item was removed:
- ----- Method: CogARMCompiler>>ands:rn:rm:lsr: (in category 'ARM convenience instructions') -----
- ands: destReg rn: srcReg rm: addReg lsr: shft
- "return an ANDS destReg, srcReg, addReg lsl #shft"
- "important detail - a 0 shft requires setting the shift-type code to 0 to avoid potential instruction confusion"
- 	shft = 0
- 		ifTrue:[^self type: 0 op: AndOpcode set: 1 rn: srcReg rd: destReg shifterOperand: addReg]
- 		ifFalse:[^self type: 0 op: AndOpcode set: 1 rn: srcReg rd: destReg shifterOperand: ((shft <<7 bitOr: 32) bitOr:  addReg)]!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeAndCqR (in category 'generate machine code - concretize') -----
  concretizeAndCqR
  	"Will get inlined into concretizeAt: switch."
  	"AND is very important since it's used to mask all sorts of flags in the jit. We take special care to try to find fast ways to make the masks"
  	<inline: true>
  	|val|
  	val := operands at: 0.
  	self rotateable8bitImmediate: val
  		ifTrue: [ :rot :immediate | | reg |
  			reg := self concreteRegister: (operands at: 1).
  			self machineCodeAt: 0 put: (self ands: reg rn: reg imm: immediate ror: rot).
  			^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"
  			|invVal|
  			val <0
  				ifTrue:[invVal := -1 - val]
  				ifFalse:[invVal := val bitInvert32].
  			self rotateable8bitImmediate: invVal
  				ifTrue: [ :rot :immediate | |reg|
  					reg := self concreteRegister: (operands at: 1).
  					self machineCodeAt: 0 put: (self bics: reg rn: reg imm: immediate ror: rot).
  					^machineCodeSize := 4]
  				ifFalse: ["let's try to see if the constant can be made from a simple shift of 0xFFFFFFFF"
  					|hb reg|
  					reg := self concreteRegister: (operands at: 1).
  					hb := (operands at: 0) highBit.
  					1 << hb = (val +1)
  						ifTrue: [ "MVN temp reg, 0, making 0xffffffff"
  							self machineCodeAt: 0 put:(self mvn: ConcreteIPReg imm: 0 ror: 0).
  							"Then AND reg, temp reg, lsr #(32-hb)"
+ 							 self machineCodeAt: 4 put:(self dataOpType: AndOpcode rd: reg rn: reg rm: ConcreteIPReg lsr: (32-hb )).
- 							 self machineCodeAt: 4 put:(self ands: reg rn: reg rm: ConcreteIPReg lsr: (32-hb )).
  							^machineCodeSize :=8]
  						ifFalse: [^self concretizeDataOperationCwR: AndOpcode]]]!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeAndCqRR (in category 'generate machine code - concretize') -----
  concretizeAndCqRR
  	"Will get inlined into concretizeAt: switch."
  	"AND is very important since it's used to mask all sorts of flags in the jit. We take special care to try to find fast ways to make the masks"
  	<inline: true>
  	| val srcReg dstReg |
  	val := operands at: 0.
  	srcReg := self concreteRegister: (operands at: 1).
  	dstReg := self concreteRegister: (operands at: 2).
  	self rotateable8bitImmediate: val
  		ifTrue:
  			[ :rot :immediate |
  			self machineCodeAt: 0 put: (self ands: dstReg rn: srcReg imm: immediate ror: rot).
  			^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"
  			|invVal|
  			invVal := val < 0
  						ifTrue:[-1 - val]
  						ifFalse:[val bitInvert32].
  			self rotateable8bitImmediate: invVal
  				ifTrue:
  					[ :rot :immediate |
  					self machineCodeAt: 0 put: (self bics: dstReg rn: srcReg imm: immediate ror: rot).
  					^machineCodeSize := 4]
  				ifFalse: "let's try to see if the constant can be made from a simple shift of 0xFFFFFFFF"
  					[| hb |
  					hb := (operands at: 0) highBit.
  					1 << hb = (val +1)
  						ifTrue: "MVN temp reg, 0, making 0xffffffff"
  							[self machineCodeAt: 0 put:(self mvn: ConcreteIPReg imm: 0 ror: 0).
  							"Then AND reg, temp reg, lsr #(32-hb)"
+ 							 self machineCodeAt: 4 put: (self dataOpType: AndOpcode rd: dstReg rn: srcReg rm: ConcreteIPReg lsr: 32 - hb).
- 							 self machineCodeAt: 4 put: (self ands: dstReg rn: srcReg rm: ConcreteIPReg lsr: 32 - hb).
  							^machineCodeSize := 8]
  						ifFalse:
  							[^self concretizeDataOperationCwR: AndOpcode]]]!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeDataOperationCqR: (in category 'generate machine code - concretize') -----
  concretizeDataOperationCqR: armOpcode
  	"Will get inlined into concretizeAt: switch."
  	"4 == Add, 2 == Sub, Xor == 1, And == 0, Or == 12, Bic == 14"
  	<inline: true>
+ 	|val rd rn |
+ 	val := operands at: 0.
+ 	rn := self concreteRegister: (operands at: 1).
+ 	rd := opcode = CmpOpcode ifTrue: [0] ifFalse:[rn].
+ 
+ 	self  rotateable8bitImmediate: val 
+ 		ifTrue: [:rot :immediate |
- 	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: armOpcode set: 1 rn: rn rd: rd shifterOperand: ((rot>>1)"in this usage we have to halve the rot value" << 8 bitOr: immediate)).
  			^machineCodeSize := 4]
+ 		ifFalse: ["let's try to see if the constant can be made from a simple shift of 0xFFFFFFFF"
+ 				val > 0 ifTrue: [
+ 					|hb |
+ 					hb := val highBit.
+ 					1 << hb = (val +1)
+ 						ifTrue: [ "MVN temp,  #0, making 0xffffffff"
+ 							self machineCodeAt: 0 put:(self mvn: ConcreteIPReg imm: 0 ror: 0).
+ 							"Then armOpcode reg, temp reg, lsr #(32-hb)"
+ 							 self machineCodeAt: 4 put:(self dataOpType: armOpcode rd: rd  rn: rn rm: ConcreteIPReg lsr: (32-hb)).
+ 							^machineCodeSize :=8]].
+ 					^self concretizeDataOperationCwR: armOpcode].
- 		ifFalse: [^self concretizeDataOperationCwR: armOpcode].
  	!

Item was added:
+ ----- Method: CogARMCompiler>>dataOpType:rd:rn:rm:lsr: (in category 'ARM convenience instructions') -----
+ dataOpType: opcode rd: destReg rn: srcReg rm: addReg lsr: shft
+ "return an {opcode} destReg, srcReg, addReg lsl #shft"
+ "important detail - a 0 shft requires setting the shift-type code to 0 to avoid potential instruction confusion"
+ 	shft = 0
+ 		ifTrue:[^self type: 0 op: opcode set: 1 rn: srcReg rd: destReg shifterOperand: addReg]
+ 		ifFalse:[^self type: 0 op: opcode set: 1 rn: srcReg rd: destReg shifterOperand: ((shft <<7 bitOr: 32) bitOr:  addReg)]!

Item was changed:
  SharedPool subclass: #CogRTLOpcodes
  	instanceVariableNames: ''
+ 	classVariableNames: 'AddCqR AddCwR AddRR AddRdRd AlignmentNops AndCqR AndCqRR 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 RISCTempReg ReceiverResultReg RetN SPReg SendNumArgsReg SqrtRd SubCqR SubCwR SubRR SubRdRd TempReg TstCqR UnusedARMRegister VarBaseReg XorCqR XorCwR XorRR'
- 	classVariableNames: 'AddCqR AddCwR AddRR AddRdRd AlignmentNops AndCqR AndCqRR 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 RISCTempReg ReceiverResultReg RetN SPReg SendNumArgsReg SqrtRd SubCqR SubCwR SubRR SubRdRd TempReg TstCqR VarBaseReg 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: NSSendCacheSurrogate32 class>>alignedByteSize (in category 'accessing') -----
- ----- Method: NSSendCacheSurrogate32 class>>alignedByteSize (in category 'as yet unclassified') -----
  alignedByteSize
  	^20!

Item was changed:
+ ----- Method: NSSendCacheSurrogate32>>classTag (in category 'accessing') -----
- ----- Method: NSSendCacheSurrogate32>>classTag (in category 'as yet unclassified') -----
  classTag
  	^memory unsignedLongAt: address + 9!

Item was changed:
+ ----- Method: NSSendCacheSurrogate32>>enclosingObject (in category 'accessing') -----
- ----- Method: NSSendCacheSurrogate32>>enclosingObject (in category 'as yet unclassified') -----
  enclosingObject
  	^memory unsignedLongAt: address + 13!

Item was changed:
  ----- Method: NSSendCacheSurrogate32>>enclosingObject: (in category 'accessing') -----
  enclosingObject: aValue
  	^memory
  		unsignedLongAt: address + 13
  		put: aValue!

Item was changed:
+ ----- Method: NSSendCacheSurrogate32>>numArgs (in category 'accessing') -----
- ----- Method: NSSendCacheSurrogate32>>numArgs (in category 'as yet unclassified') -----
  numArgs
  	^memory unsignedLongAt: address + 5!

Item was changed:
+ ----- Method: NSSendCacheSurrogate32>>selector (in category 'accessing') -----
- ----- Method: NSSendCacheSurrogate32>>selector (in category 'as yet unclassified') -----
  selector
  	^memory unsignedLongAt: address + 1!

Item was changed:
+ ----- Method: NSSendCacheSurrogate32>>target (in category 'accessing') -----
- ----- Method: NSSendCacheSurrogate32>>target (in category 'as yet unclassified') -----
  target
  	^memory unsignedLongAt: address + 17!

Item was changed:
+ ----- Method: NSSendCacheSurrogate64 class>>alignedByteSize (in category 'accessing') -----
- ----- Method: NSSendCacheSurrogate64 class>>alignedByteSize (in category 'as yet unclassified') -----
  alignedByteSize
  	^40!



More information about the Vm-dev mailing list