[Vm-dev] VM Maker: VMMaker.oscog-eem.1228.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Apr 21 00:03:13 UTC 2015


Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.1228.mcz

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

Name: VMMaker.oscog-eem.1228
Author: eem
Time: 20 April 2015, 5:00:18.118 pm
UUID: 486228a3-4d6f-474c-8f04-7b9105457d09
Ancestors: VMMaker.oscog-tpr.1227

CogARMCompiler:
Fix pc-relative addressing for generating the
method reference in frame build.  Attempting
to use pc-relative addressing shouldn't have the
side-effect of altering the value pushed when pc-
relative addressing can't be used.

Accept that not all method references can be
handled this way (i.e. mehtod reference following
a long generated primitive such as new:) and so
make relocateMethodReferenceBeforeAddress:by:
handle those rare cases.

Recategorize.

Fix some stupidities in CurrentImageCoInterpreterFacade;
perhaps the headerToMethodMap is unnecessary.

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

Item was changed:
+ ----- Method: CogARMCompiler>>at:moveCw:intoR: (in category 'generate machine code - support') -----
- ----- Method: CogARMCompiler>>at:moveCw:intoR: (in category 'generate machine code - concretize') -----
  at: offset moveCw: constant intoR: destReg
  	"This loads aWord into the inter-opcode temporary register. Because most ARM instruction enable using a (8-12bit) offset relative to a register, the LS Byte can be included in that instruction, saving one instruction. This is done in a decorator, e.g. CmpCqR"
  	"Generates:along the lines of
  	MOV destReg, #<constantByte3>, 12
  	ORR destReg, destReg, #<constantByte2>, 8
  	ORR destReg, destReg, #<constantByte1>, 4
  	ORR destReg, destReg, #<constantByte0>, 0
  	with minimal choice of the rotation (last digit)"
  	"The same area can be modified multiple times, because the opperation is (inclusive) or."
  	<inline: true>
  	"self assert: destReg < 12."
  
  	self machineCodeAt: offset put: (self mov: destReg imm: (constant >>24 bitAnd: 16rFF) ror: 8).
  	self machineCodeAt: offset +4 put: (self orr: destReg imm: (constant >> 16 bitAnd: 16rFF) ror: 16).
  	self machineCodeAt: offset +8 put: (self orr: destReg imm: (constant >> 8 bitAnd: 16rFF) ror: 24).
  	self machineCodeAt: offset +12 put: (self orr: destReg imm: (constant bitAnd: 16rFF) ror: 0).
  	^16!

Item was removed:
- ----- Method: CogARMCompiler>>concretizeConditionalJumpFull: (in category 'generate machine code - concretize') -----
- concretizeConditionalJumpFull: 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: ConcreteIPReg.
- 	self assert: instrOffset = 16.
- 	"bx RISCTempReg"
- 	self machineCodeAt: instrOffset put: (self cond: conditionCode bx: 0 target: ConcreteIPReg).
- 	^machineCodeSize := instrOffset + 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizePushCw (in category 'generate machine code - concretize') -----
  concretizePushCw
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
+ 	| operand instrOffset distance |
+ 	operand := operands at: 0.
+ 	instrOffset := 0.
+ 	"First try and encode as a pc-relative reference..."
+ 	(cogit addressIsInCodeZone: operand) ifTrue:
+ 		[distance := operand  - (address + 8).
+ 		 self rotateable8bitImmediate: distance
+ 		 	ifTrue: [ :rot :immediate |
+ 		 		self machineCodeAt: 0 put: (self add: ConcreteIPReg rn: PC imm: immediate ror: rot).
+ 		 		instrOffset := 4]
+ 		 	ifFalse:
+ 		 		[self rotateable8bitImmediate: distance negated
+ 		 			ifTrue: [ :rot :immediate |
+ 		 				self machineCodeAt: 0 put: (self sub: ConcreteIPReg rn: PC imm: immediate ror: rot).
+ 		 				instrOffset := 4]
+ 				ifFalse: [instrOffset := 0]]].
+ 	"If this fails, use the conventional and painfully long 4 instruction sequence."
+ 	instrOffset = 0 ifTrue:
+ 		[instrOffset := self at: 0 moveCw: operand intoR: ConcreteIPReg].
+ 	self machineCodeAt: instrOffset put: (self pushR: ConcreteIPReg).
+ 	^machineCodeSize := instrOffset + 4!
- 	| word  instrOffset |
- 	word := (operands at: 0) - (address + 8).
- 	
- 	self rotateable8bitImmediate: word
- 		ifTrue: [ :rot :immediate |
- 			self machineCodeAt: 0 put: (self add: ConcreteIPReg rn: PC imm: immediate ror: rot).
- 			instrOffset := 4]
- 		ifFalse: [self rotateable8bitImmediate: word negated
- 				ifTrue: [ :rot :immediate |
- 					self machineCodeAt: 0 put: (self sub: ConcreteIPReg rn: PC imm: immediate ror: rot).
- 					instrOffset := 4]
- 				ifFalse: [instrOffset := self at: 0 moveCw: word intoR: ConcreteIPReg]].
- 		self machineCodeAt: instrOffset put: (self pushR: ConcreteIPReg).
- 	^machineCodeSize := instrOffset +4!

Item was removed:
- ----- Method: CogARMCompiler>>isAddressRelativeToPC: (in category 'testing') -----
- isAddressRelativeToPC: pcAddress
- 	"Support for addressing the method relative to the PC."
- 	^pcAddress notNil
- 	  and: [pcAddress <= address
- 	  and: [address - pcAddress < (1 << 12)]]!

Item was removed:
- ----- Method: CogARMCompiler>>isPCRelativeAddress: (in category 'abstract instructions') -----
- isPCRelativeAddress: operand
- 	"Provided the receiver's address has been determined we can
- 	 answer if operand can be accessed via pc-relative addressing."
- 
- 	self assert: address notNil.
- 	^operand between: address + 8 - (1 << 12 - 1) and: address + 8 + (1 << 12 - 1)!

Item was changed:
+ ----- Method: CogARMCompiler>>movePCRelative:into: (in category 'generate machine code - support') -----
- ----- Method: CogARMCompiler>>movePCRelative:into: (in category 'abstract instructions') -----
  movePCRelative: operand into: reg
+ 	"Load a pc relative value into the register"
+ 	| offset sign instr |
+ 	offset := operand - (address + 8).
+ 	sign := offset >= 0 ifTrue: [1] ifFalse: [0].
+ 	instr := self ldr: reg rn: PC plus: sign imm: offset abs.
+ 	self machineCodeAt: 0 put: instr.
+ 	^4!
- "Load a pc relative value into the register"
- 	| offset sign |
- 	offset := operand - address +8.
- 	sign := offset > 0 ifTrue:[1] ifFalse:[0].
- 	self ldr: reg rn: PC plus: sign imm: offset abs!

Item was changed:
+ ----- Method: CogARMCompiler>>nopsFrom:to: (in category 'generate machine code - support') -----
- ----- Method: CogARMCompiler>>nopsFrom:to: (in category 'generate machine code - concretize') -----
  nopsFrom: startAddr to: endAddr
  "fill with MOV R0, R0 no-op instructions"
  	self assert: endAddr - startAddr + 1 \\ 4 = 0.
  	startAddr to: endAddr by: 4 do:
  		[:p| objectMemory 
  			byteAt: p put: 16r0;
  			byteAt: p+1 put: 16r0;
  			byteAt: p+2 put: 16rA0;
  			byteAt: p+3 put: 16rE1]!

Item was changed:
+ ----- Method: CogARMCompiler>>padIfPossibleWithNopsFrom:to: (in category 'generate machine code') -----
- ----- Method: CogARMCompiler>>padIfPossibleWithNopsFrom:to: (in category 'generate machine code - concretize') -----
  padIfPossibleWithNopsFrom: startAddr to: endAddr
  	| nullBytes |
  	nullBytes := (endAddr - startAddr + 1) \\ 4.
  	self nopsFrom: startAddr to: endAddr - nullBytes.
  	endAddr - nullBytes + 1 to: endAddr 
  		do: [ :p | objectMemory byteAt: p put: 16r0]!

Item was added:
+ ----- Method: CogARMCompiler>>relocateMethodReferenceBeforeAddress:by: (in category 'inline cacheing') -----
+ relocateMethodReferenceBeforeAddress: pc by: delta
+ 	"If possible we generate the method address using pc-relative addressing.
+ 	 If so we don't need to relocate it in code.  So check if pc-relative code was
+ 	 generated, and if not, adjust a long sequence."
+ 	| location |
+ 	(self isPCRelativeValueLoad: (objectMemory longAt: pc - 8)) ifFalse:
+ 		[location :=    ((objectMemory byteAt: pc - 20) << 24)
+ 					+  ((objectMemory byteAt: pc - 16) << 16)
+ 					+  ((objectMemory byteAt: pc - 12) << 8)
+ 					+   (objectMemory byteAt: pc - 8).
+ 		 location := location + delta.
+ 		objectMemory byteAt: pc - 20 put: (location >> 24 bitAnd: 16rFF).
+ 		objectMemory byteAt: pc - 16 put: (location >> 16 bitAnd: 16rFF).
+ 		objectMemory byteAt: pc - 12 put: (location >> 8 bitAnd: 16rFF).
+ 		objectMemory byteAt: pc - 8 put: (location  bitAnd: 16rFF)]!

Item was added:
+ ----- Method: CogAbstractInstruction>>isPCRelativeValueLoad: (in category 'testing') -----
+ isPCRelativeValueLoad: instr
+ 	"add ip, pc, blah->  '16rE28FC000'
+ 	 sub ip, pc, blah -> '16rE24FC000'"
+ 	^(instr bitAnd: 16rFFFFF000) = 16rE28FC000
+ 	  or: [(instr bitAnd: 16rFFFFF000) = 16rE24FC000]!

Item was changed:
  ----- Method: CogAbstractInstruction>>relocateMethodReferenceBeforeAddress:by: (in category 'inline cacheing') -----
  relocateMethodReferenceBeforeAddress: pc by: delta
+ 	"On some processors the method reference is a load constant and
+ 	 hence needs changing when methods are moved.  On others the
+ 	 method reference is pc-relative and hence nothing needs to happen."
+ 	self subclassResponsibility!
- 	self relocateCallBeforeReturnPC: pc by: delta!

Item was added:
+ ----- Method: Cogit>>addressIsInCodeZone: (in category 'testing') -----
+ addressIsInCodeZone: address
+ 	"N.B. We /don't/ write this as address between: codeBase and: methodZone limitZony in case we're
+ 	 testing an address in a method whose code has yet to be allocated and is hence >= methodZone limitZony"
+ 	^address asUnsignedInteger >= codeBase
+ 	  and: [address < methodZone youngReferrers]!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>argumentCountOfMethodHeader: (in category 'accessing') -----
  argumentCountOfMethodHeader: aSmallIntegerOop
+ 	"a.k.a. (headerToMethodMap at: aSmallIntegerOop) numArgs"
+ 	^coInterpreter argumentCountOfMethodHeader: aSmallIntegerOop!
- 	^(headerToMethodMap at: aSmallIntegerOop) numArgs!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>startPCOfMethodHeader: (in category 'accessing') -----
  startPCOfMethodHeader: aSmallIntegerOop
+ 	"a.k.a. (headerToMethodMap at: aSmallIntegerOop) initialPC - 1"
+ 	^coInterpreter startPCOfMethodHeader: aSmallIntegerOop!
- 	^(headerToMethodMap at: aSmallIntegerOop) initialPC - 1!

Item was changed:
  ----- Method: CurrentImageCoInterpreterFacade>>temporaryCountOfMethodHeader: (in category 'accessing') -----
+ temporaryCountOfMethodHeader: aSmallIntegerOop
+ 	"a.k.a. (headerToMethodMap at: aSmallIntegerOop) numTemps"
+ 	^coInterpreter temporaryCountOfMethodHeader: aSmallIntegerOop!
- temporaryCountOfMethodHeader: header
- 	^(CompiledMethod
- 			newMethod: 8
- 			header: (header <= SmallInteger maxVal
- 						ifTrue: [header]
- 						ifFalse: [(header bitAnd: SmallInteger maxVal) + SmallInteger minVal]))
- 		numTemps!



More information about the Vm-dev mailing list