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

commits at source.squeak.org commits at source.squeak.org
Mon Oct 3 21:04:17 UTC 2011


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

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

Name: VMMaker.oscog-eem.129
Author: eem
Time: 3 October 2011, 2:02:35.139 pm
UUID: 1b6f9029-666c-4ca4-b58c-9973784bb7ba
Ancestors: VMMaker.oscog-eem.128

Deal with some realities in the minValidCallAddress checking code.
At least on Mac OS under gcc -O, gcc will reorder code so that
primitiveFail comes before interpret.
Also firm up the signatures of rewriteInlineCacheAt:tag:target: &
rewriteCallAt:target:.

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

Item was changed:
  ----- Method: CoInterpreter>>interpretAddress (in category 'trampoline support') -----
  interpretAddress
  	"This is used for asserts that check that inline cache editing results in valid addresses.
+ 	 In the C VM primitiveFail is presumed to come before any primitives and so it constitutes
- 	 In the C VM interpret is guaranteed to come before any primitives and so it constitutes
  	 the lowest address in C code that machine code should be linked.  In the simulator
+ 	 we just answer something not low."
- 	we just answer something not low."
  	<api>
  	<returnTypeC: #usqInt>
  	^self cCode: [(self addressOf: #interpret) asUnsignedInteger]
  		inSmalltalk: [heapBase]!

Item was added:
+ ----- Method: CoInterpreter>>primitiveFailAddress (in category 'trampoline support') -----
+ primitiveFailAddress
+ 	"This is used for asserts that check that inline cache editing results in valid addresses.
+ 	 In the C VM primitiveFail is presumed to come before any primitives and so it constitutes
+ 	 the lowest address in C code that machine code should be linked.  In the simulator
+ 	 we just answer something not low."
+ 	<api>
+ 	<returnTypeC: #usqInt>
+ 	^self cCode: [(self addressOf: #primitiveFail) asUnsignedInteger]
+ 		inSmalltalk: [heapBase]!

Item was changed:
  ----- Method: CogIA32Compiler>>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 |
  	"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) signedIntToLong.
  	objectMemory
  		byteAt: callSiteReturnAddress - 1 put: (callDistance >> 24 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 2 put: (callDistance >> 16 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 3 put: (callDistance >>   8 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 4 put: (callDistance            bitAnd: 16rFF).
  	self assert: (self callTargetFromReturnAddress: callSiteReturnAddress) signedIntToLong = callTargetAddress.
  	"self cCode: ''
  		inSmalltalk: [cogit disassembleFrom: callSiteReturnAddress - 10 to: callSiteReturnAddress - 1]."
  	^5!

Item was changed:
  ----- Method: CogIA32Compiler>>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."
  	<var: #callSiteReturnAddress type: #usqInt>
+ 	<var: #callTargetAddress type: #usqInt>
  	| callDistance |
  	"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) signedIntToLong.
  	objectMemory
  		byteAt: callSiteReturnAddress - 1 put: (callDistance >> 24 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 2 put: (callDistance >> 16 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 3 put: (callDistance >>   8 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 4 put: (callDistance            bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 6 put: (cacheTag >> 24 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 7 put: (cacheTag >> 16 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 8 put: (cacheTag >>   8 bitAnd: 16rFF);
  		byteAt: callSiteReturnAddress - 9 put: (cacheTag            bitAnd: 16rFF).
  	self assert: (self callTargetFromReturnAddress: callSiteReturnAddress) signedIntToLong = callTargetAddress.
  	"self cCode: ''
  		inSmalltalk: [cogit disassembleFrom: callSiteReturnAddress - 10 to: callSiteReturnAddress - 1]."
  	^10!

Item was changed:
  ----- Method: Cogit>>initializeCodeZoneFrom:upTo: (in category 'initialization') -----
  initializeCodeZoneFrom: startAddress upTo: endAddress
  	<api>
  	self cCode: [self sqMakeMemoryExecutableFrom: startAddress To: endAddress]
  		inSmalltalk: [self initializeProcessor].
  	codeBase := methodZoneBase := (self
  											cCode: [startAddress]
  											inSmalltalk: [startAddress + guardPageSize]).
+ 	minValidCallAddress := (codeBase min: coInterpreter interpretAddress)
+ 								min: coInterpreter primitiveFailAddress.
- 	minValidCallAddress := codeBase min: coInterpreter interpretAddress.
  	self initializeBackend.
  	self maybeGenerateCheckFeatures.
  	self maybeGenerateICacheFlush.
  	self generateVMOwnerLockFunctions.
  	ceGetSP := self cCoerceSimple: self genGetLeafCallStackPointer to: #'unsigned long (*)(void)'.
  	self generateStackPointerCapture.
  	self generateTrampolines.
  	self checkPrimitiveTableEnablers.
  	methodZone manageFrom: methodZoneBase to: endAddress.
  	self computeEntryOffsets.
  	self generateClosedPICPrototype.
  	"N.B. this is assumed to be the last thing done in initialization; see Cogit>>initialized"
  	self generateOpenPICPrototype!



More information about the Vm-dev mailing list