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

commits at source.squeak.org commits at source.squeak.org
Tue Apr 7 21:05:42 UTC 2015


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

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

Name: VMMaker.oscog-tpr.1171
Author: tpr
Time: 7 April 2015, 2:04:16.488 pm
UUID: 06201046-1d4c-437b-9646-fb607702e22c
Ancestors: VMMaker.oscog-eem.1170

Simple terminology change to accomodate ARM habits; 'quick' means small constants to us, not short jump intervals. Just change the naming to make it less cognitively dissonant. Happiness ensues. Chocolate may be consumed.

This is the correct one. The recently saved Cog-tpr.258 was in fact empty because of a stupid missed button.

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

Item was changed:
  ----- Method: CogARMCompiler>>concretizeCall (in category 'generate machine code - concretize') -----
  concretizeCall
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	"build either a
  	BL offset
  	or
  	{move offset to offsetReg}
  	BLX offsetReg
  	instruction sequence. In production VMs we expect never to have long calls within generated code"
  	| offset |
  	self assert: (operands at: 0) ~= 0.
  	self assert: (operands at: 0) \\ 4 = 0.
  	offset := (operands at: 0) signedIntFromLong - (address + 8 "normal pc offset") signedIntFromLong.
+ 	(self isInImmediateJumpRange: offset)
- 	(self isQuick: offset)
  		ifTrue: [
  			self machineCodeAt: 0 put: (self bl: offset). "BL offset"
  			^machineCodeSize := 4]
  		ifFalse: [
  			"self error: 'While we know how to generate a long distance call, we can''t update such a send site yet. Please restart with smaller cache size'."
  			^self concretizeLongCall]!

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 isInImmediateJumpRange: offset)
-  	(self isQuick: offset)
  		ifTrue: [
  			self machineCodeAt: 0 put: (self cond: conditionCode br: 0 offset: offset). "B offset"
  			^machineCodeSize := 4]
  		ifFalse: [
  			^self concretizeConditionalJumpLong: conditionCode]!

Item was added:
+ ----- Method: CogARMCompiler>>isInImmediateJumpRange: (in category 'testing') -----
+ isInImmediateJumpRange: operand
+ 	<var: #operand type: #'unsigned long'>
+ 	^operand signedIntFromLong between: -33554432 and: 33554428!

Item was removed:
- ----- Method: CogARMCompiler>>isQuick: (in category 'testing') -----
- isQuick: operand
- 	<var: #operand type: #'unsigned long'>
- 	^operand signedIntFromLong between: -33554432 and: 33554428!

Item was changed:
  ----- 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 isInImmediateJumpRange: callDistance). "we don't support long call updates, yet"
- 	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 changed:
  ----- Method: CogARMCompiler>>rewriteInlineCacheAt:tag:target: (in category 'inline cacheing') -----
  rewriteInlineCacheAt: callSiteReturnAddress tag: cacheTag target: callTargetAddress
  	"Rewrite an inline cache to call a different target for a new tag.  This variant is used
  	 to link unlinked sends in ceSend:to:numArgs: et al.  Answer the extent of the code
  	 change which is used to compute the range of the icache to flush."
  	
  	"chacheTag contains an oop to the selector which need be loaded before jumping"
  	<var: #callSiteReturnAddress type: #usqInt>
  	<var: #callTargetAddress type: #usqInt>
  	| call callDistance |
  	"cogit disassembleFrom: callSiteReturnAddress - 40 to: callSiteReturnAddress + 9"
  	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 isInImmediateJumpRange: callDistance). "we don't support long call updates, yet"
- 	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.
  	
  	"The cacheTag is loaded byte by byte. Each byte needs to be encoded with minimal right ring rotation. See also #at:moveCw:intoR:"
  	objectMemory byteAt: callSiteReturnAddress - 20 put: (cacheTag >> 24 bitAnd: 16rFF).
  	objectMemory byteAt: callSiteReturnAddress - 16 put: (cacheTag >> 16 bitAnd: 16rFF).
  	objectMemory byteAt: callSiteReturnAddress - 12 put: (cacheTag >> 8 bitAnd: 16rFF).
  	objectMemory byteAt: callSiteReturnAddress - 8 put: (cacheTag  bitAnd: 16rFF).
  
  	self assert: (self callTargetFromReturnAddress: callSiteReturnAddress) signedIntToLong = callTargetAddress.
  	"self cCode: ''
  		inSmalltalk: [cogit disassembleFrom: callSiteReturnAddress - 20 to: callSiteReturnAddress - 1]."
  	^20!

Item was changed:
  ----- Method: CogARMCompiler>>sizePCDependentInstructionAt: (in category 'generate machine code') -----
  sizePCDependentInstructionAt: eventualAbsoluteAddress
  	"Size a jump and set its address.  The target may be another instruction
  	 or an absolute address.  On entry the address inst var holds our virtual
  	 address. On exit address is set to eventualAbsoluteAddress, which is
  	 where this instruction will be output.  The span of a jump to a following
  	 instruction is therefore between that instruction's address and this
  	 instruction's address ((which are both still their virtual addresses), but the
  	 span of a jump to a preceeding instruction or to an absolute address is
  	 between that instruction's address (which by now is its eventual absolute
  	 address) or absolute address and eventualAbsoluteAddress."
  
  	| target maximumSpan abstractInstruction |
  	<var: #abstractInstruction type: #'AbstractInstruction *'>
  	opcode = AlignmentNops ifTrue:
  		[| alignment |
  		 address := eventualAbsoluteAddress.
  		 alignment := operands at: 0.
  		 ^machineCodeSize := (eventualAbsoluteAddress + (alignment - 1) bitAnd: alignment negated)
  							   - eventualAbsoluteAddress].
  	self assert: (self isJump or: [opcode = Call]).
  	self isJump ifTrue: [self resolveJumpTarget].
  	target := operands at: 0.
  	abstractInstruction := cogit cCoerceSimple: target to: #'AbstractInstruction *'.
  	"maximumSpan calculation copied from CogIA32Compiler TODO: extract method?"
  	(self isAnInstruction: abstractInstruction)
  		ifTrue:
  			[maximumSpan := abstractInstruction address
  							- (((cogit abstractInstruction: self follows: abstractInstruction)
  								ifTrue: [eventualAbsoluteAddress]
  								ifFalse: [address]) + 2)]
  		ifFalse:
  			[maximumSpan := target - (eventualAbsoluteAddress + 2)].
  	address := eventualAbsoluteAddress.
  	^machineCodeSize := opcode = Call 
+ 				ifTrue: [(self isInImmediateJumpRange: maximumSpan) ifTrue: [4] ifFalse: [20]]
+ 				ifFalse: [(self isLongJump not and: [self isInImmediateJumpRange: maximumSpan])
- 				ifTrue: [(self isQuick: maximumSpan) ifTrue: [4] ifFalse: [20]]
- 				ifFalse: [(self isLongJump not and: [self isQuick: maximumSpan])
  								ifTrue: [4]
  								ifFalse: [20]] "load address to register, add"!



More information about the Vm-dev mailing list