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

commits at source.squeak.org commits at source.squeak.org
Fri Apr 1 00:14:06 UTC 2016


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

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

Name: VMMaker.oscog-eem.1756
Author: eem
Time: 1 January 1970, 5:12:04.098931 pm
UUID: 141cf0f3-955a-486f-8082-decbc14645d7
Ancestors: VMMaker.oscog-eem.1755

Spur:
Have WideString>>at: fail to answer an out-of-range character in the interpreter primitive.

Cogit:
rescue compilability by making the immutability support routines option: #IMMUTABILITY.

Fix the ARM's caller-saved register mask now that we can name all the actual registers.

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

Item was changed:
  ----- Method: CogARMCompiler>>callerSavedRegisterMask (in category 'accessing') -----
  callerSavedRegisterMask
  	"According to IHI0042E ARM Architecture Procedure Calling Standard, in section 5.1.1:
  		A subroutine must preserve the contents of the registers r4-r8, r10, r11 and SP (and r9 in PCS variants that designate r9 as v6).
  	 SP = r13, so the callee-saved regs are r4-r8 & r10-r12.
  	 The caller-saved registers are those that are not callee-saved and not reserved for hardware/abi uses,
+ 	 i..e r0-r3, r9 & r12."
+ 	^cogit registerMaskFor: 0 and: 1 and: 2 and: 3 and: 9 and: 12!
- 	 i..e r0-r3, r9 & r12.  We can't name all the C argument registers.  So..."
- 	^cogit
- 		registerMaskFor: 0
- 		"and: 1"
- 		"and: 2"
- 		"and: 3"
- 		"and: 9"
- 		and: 12!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genStoreWithImmutabilityAndStoreCheckSourceReg:slotIndex:destReg:scratchReg:needRestoreRcvr: (in category 'compile abstract instructions') -----
  genStoreWithImmutabilityAndStoreCheckSourceReg: sourceReg slotIndex: index destReg: destReg scratchReg: scratchReg needRestoreRcvr: needRestoreRcvr 
  	"Store check code is duplicated to use a single trampoline"
+ 	<option: #IMMUTABILITY>
  	| immutableJump jmpImmediate jmpDestYoung jmpSourceOld jmpAlreadyRemembered |
  	<var: #immutableJump type: #'AbstractInstruction *'>
  	<var: #jmpImmediate type: #'AbstractInstruction *'>
  	<var: #jmpDestYoung type: #'AbstractInstruction *'>
  	<var: #jmpSourceOld type: #'AbstractInstruction *'>
  	<var: #jmpAlreadyRemembered type: #'AbstractInstruction *'>
  
  	immutableJump := self genJumpImmutable: destReg scratchReg: scratchReg.
  	
  	cogit genTraceStores.
  	
  	"do the store"
  	cogit MoveR: sourceReg
  		   Mw: index * objectMemory wordSize + objectMemory baseHeaderSize
  		   r: destReg.
  	
  	"store check"
  	jmpImmediate := self genJumpImmediate: sourceReg.
  	"Get the old/new boundary in scratchReg"
  	cogit MoveCw: objectMemory storeCheckBoundary R: scratchReg.
  	"Is target young?  If so we're done"
  	cogit CmpR: scratchReg R: destReg. "N.B. FLAGS := destReg - scratchReg"
  	jmpDestYoung := cogit JumpBelow: 0.
  	"Is value stored old?  If so we're done."
  	cogit CmpR: scratchReg R: sourceReg. "N.B. FLAGS := valueReg - scratchReg"
  	jmpSourceOld := cogit JumpAboveOrEqual: 0.
  	"value is young and target is old.
  	 Need to remember this only if the remembered bit is not already set."
  	CheckRememberedInTrampoline ifFalse:
  		[jmpAlreadyRemembered := self genCheckRememberedBitOf: destReg scratch: scratchReg].
  	"Set the inst var index for the benefit of the immutability check. The trampoline will
  	 repeat the check to choose between the immutbality violation and the store check."
  	immutableJump jmpTarget: cogit Label.
  	self genStoreTrampolineCall: index.
  	needRestoreRcvr ifTrue: [ cogit putSelfInReceiverResultReg ].
  
  	jmpImmediate jmpTarget:
  	(jmpDestYoung jmpTarget:
  	(jmpSourceOld jmpTarget:
  		cogit Label)).
  	CheckRememberedInTrampoline ifFalse:
  		[jmpAlreadyRemembered jmpTarget: jmpSourceOld getJmpTarget].
  	^ 0!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genStoreWithImmutabilityButNoStoreCheckSourceReg:slotIndex:destReg:scratchReg:needRestoreRcvr: (in category 'compile abstract instructions') -----
  genStoreWithImmutabilityButNoStoreCheckSourceReg: sourceReg slotIndex: index destReg: destReg scratchReg: scratchReg needRestoreRcvr: needRestoreRcvr
+ 	"Gen an immutability check with no store check (e.g. assigning an immediate literal)"
+ 	<option: #IMMUTABILITY>
- 
  	<var: #mutableJump type: #'AbstractInstruction *'>
  	<var: #immutabilityFailure type: #'AbstractInstruction *'>
  	| immutabilityFailure mutableJump |
  	
  	"imm check has its own trampoline"
  	mutableJump := self genJumpMutable: destReg scratchReg: scratchReg.
  	self genStoreTrampolineCall: index.
  	needRestoreRcvr ifTrue: [ cogit putSelfInReceiverResultReg ].
  	immutabilityFailure := cogit Jump: 0.
  	mutableJump jmpTarget: cogit Label.
  
  	cogit genTraceStores.
  	
  	"do the store"
  	cogit MoveR: sourceReg
  		   Mw: index * objectMemory wordSize + objectMemory baseHeaderSize
  		   r: destReg.
  		
  	immutabilityFailure jmpTarget: cogit Label.
  
  	^ 0!

Item was changed:
  ----- Method: CogObjectRepresentationForSpur>>genStoreWithImmutabilityCheckSourceReg:slotIndex:destReg:scratchReg:needsStoreCheck:needRestoreRcvr: (in category 'compile abstract instructions') -----
  genStoreWithImmutabilityCheckSourceReg: sourceReg slotIndex: index destReg: destReg scratchReg: scratchReg needsStoreCheck: needsStoreCheck needRestoreRcvr: needRestoreRcvr
  	"We know there is a frame as immutability check requires a frame"
  	"needRestoreRcvr has to be true to keep RcvrResultReg live with the receiver in it across the trampoline"
+ 	<option: #IMMUTABILITY>
- 	
  	"Trampoline convention..."
  	self assert: destReg == ReceiverResultReg.
  	self assert: scratchReg == TempReg.
    	self assert: sourceReg == ClassReg.
  	
  	needsStoreCheck
  		ifTrue: 
  			[ self 
  				genStoreWithImmutabilityAndStoreCheckSourceReg: sourceReg 
  				slotIndex: index 
  				destReg: destReg 
  				scratchReg: scratchReg 
  				needRestoreRcvr: needRestoreRcvr ]
  		ifFalse: 
  			[ self 
  				genStoreWithImmutabilityButNoStoreCheckSourceReg: sourceReg 
  				slotIndex: index 
  				destReg: destReg 
  				scratchReg: scratchReg 
  				needRestoreRcvr: needRestoreRcvr ].
  	^ 0!

Item was changed:
  ----- Method: StackInterpreter>>commonAt: (in category 'indexing primitive support') -----
  commonAt: stringy
  	"This code is called if the receiver responds primitively to at:.
  	 N.B. this does *not* use the at cache, instead inlining stObject:at:.
  	 Using the at cache here would require that callers set messageSelector
  	 and lkupClass and that is onerous and error-prone, and in any case,
  	 inlining produces much better performance than using the at cache here."
  	| index rcvr result |
  	<inline: true> "to get it inlined in primitiveAt and primitiveStringAt"
  	self initPrimCall.
  	rcvr := self stackValue: 1.
  	index := self stackTop.
  	(objectMemory isImmediate: rcvr) ifTrue:
  		[^self primitiveFailFor: PrimErrInappropriate].
  	"No need to test for large positive integers here.  No object has 1g elements"
  	((objectMemory isNonIntegerObject: index)
  	 or: [argumentCount > 1 "e.g. object:basicAt:"
  		 and: [objectMemory isForwarded: rcvr]]) ifTrue:
  		[^self primitiveFailFor: PrimErrBadArgument].
  	index := objectMemory integerValueOf: index.
  	result := self stObject: rcvr at: index.
  	self successful ifTrue:
+ 		[stringy ifTrue:
+ 			[(objectMemory isInRangeCharacterCode: result) ifFalse:
+ 				[^self primitiveFailFor: PrimErrBadReceiver].
+ 			 result := self characterForAscii: (objectMemory integerValueOf: result)].
- 		[stringy ifTrue: [result := self characterForAscii: (objectMemory integerValueOf: result)].
  		 self pop: argumentCount+1 thenPush: result]!



More information about the Vm-dev mailing list