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

commits at source.squeak.org commits at source.squeak.org
Mon Jan 7 21:33:18 UTC 2013


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

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

Name: VMMaker.oscog-eem.250
Author: eem
Time: 7 January 2013, 1:30:28.165 pm
UUID: e0de5572-7682-4c5e-b5a0-ca2f32cf0c81
Ancestors: VMMaker.oscog-eem.249

Improve absent receiver send marshalling to only shuffled currently
spilled args.

Revert rush-of-blood-to-the-head change to ceImplicitReceiver
trampoline, but use Arg1Reg rather than Arg0Reg.

Fix (old) bug in ssAllocateRequiredRegMask:upThrough:
that would flush entire stack if allocating any register.

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

Item was changed:
  ----- Method: Cogit>>generateNewspeakRuntime (in category 'initialization') -----
  generateNewspeakRuntime
  	<option: #NewspeakVM>
  	| jumpMiss jumpItsTheReceiverStupid |
  	<var: #jumpMiss type: #'AbstractInstruction *'>
  	<var: #jumpItsTheReceiverStupid type: #'AbstractInstruction *'>
  	"Generate the non-send runtime support for Newspeak, explicit outer and implicit receiver.
  	 The dynamic frequency of explicit outer is so low we merely call an interpreter routine."
  	ceExplicitReceiverTrampoline := self genTrampolineFor: #ceExplicitReceiverAt:
  										called: 'ceExplicitReceiverTrampoline'
  										arg: SendNumArgsReg
  										result: ReceiverResultReg.
  	"Cached push implicit receiver implementation.  Caller looks like
  				mov selector, ClassReg
  				call ceImplicitReceiver
  				br continue
  		Lclass:	.word
  		Lmixin::	.word
  		continue:
  	 If class matches class of receiver then mixin contains either 0 or the implicit receiver.
  	 If 0, answer the actual receiver, otherwise the mixin.
+ 	 Generate the class fetch and cache probe inline for speed. Smashes Arg0Reg and caller-saved regs."
- 	 Generate the class fetch and cache probe inline for speed. Smashes caller-saved regs."
  	opcodeIndex := 0.
  	self MoveMw: FoxMFReceiver r: FPReg R: ReceiverResultReg.
  	objectRepresentation genGetClassObjectOf: ReceiverResultReg into: ClassReg scratchReg: TempReg.
+ 	self MoveMw: 0 r: SPReg R: TempReg.
+ 	self MoveMw: backEnd jumpShortByteSize r: TempReg R: Arg1Reg.
+ 	self CmpR: ClassReg R: Arg1Reg.
- 	self MoveMw: 0 r: SPReg R: TempReg. "get return address..."
- 	self MoveMw: backEnd jumpShortByteSize r: TempReg R: ReceiverResultReg. "get cached class..."
- 	self CmpR: ClassReg R: ReceiverResultReg.
  	jumpMiss := self JumpNonZero: 0.
  	self MoveMw: backEnd jumpShortByteSize + BytesPerOop r: TempReg R: ClassReg.
  	self CmpCq: 0 R: ClassReg.
  	jumpItsTheReceiverStupid := self JumpZero: 0.
  	self MoveR: ClassReg R: ReceiverResultReg.
  	jumpItsTheReceiverStupid jmpTarget: (self RetN: 0).
  	jumpMiss jmpTarget: self Label.
  	ceImplicitReceiverTrampoline := self
  										genTrampolineFor: #ceImplicitReceiverFor:receiver:class:
  										called: 'ceImplicitReceiverTrampoline'
  										callJumpBar: true
  										numArgs: 3
  										arg: SendNumArgsReg
  										arg: ReceiverResultReg
  										arg: ClassReg
  										arg: nil
  										saveRegs: false
  										resultReg: ReceiverResultReg
  										appendOpcodes: true!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genGetImplicitReceiverFor: (in category 'bytecode generators') -----
  genGetImplicitReceiverFor: selector
  	"Cached implicit receiver implementation.  Caller looks like
  		mov selector, ClassReg
  				call cePushImplicitReceiver
  				br continue
  		Lclass	.word
  		Lmixin:	.word
  		continue:
  	 If class matches class of receiver then mixin contains either 0 or the implicit receiver.
  	 If 0, answer the actual receiver.  This is done in the trampoline.
  	 See generateNewspeakRuntime."
+ 	self ssAllocateCallReg: SendNumArgsReg and: ReceiverResultReg and: ClassReg and: Arg1Reg.
- 	self ssAllocateCallReg: SendNumArgsReg and: ReceiverResultReg and: ClassReg.
  	^super genGetImplicitReceiverFor: selector!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>marshallImplicitReceiverSendArguments: (in category 'simulation stack') -----
  marshallImplicitReceiverSendArguments: numArgs
  	"Spill everything on the simulated stack that needs spilling (that below arguments).
  	 Marshall arguments to stack and/or registers depending on arg count.
  	 If the args don't fit in registers push receiver and args (spill everything).  Assume
  	 receiver already in ResultReceiverReg so shuffle args and push it if necessary."
  	numArgs > self numRegArgs
  		ifTrue:
  			["The arguments must be pushed to the stack, and hence the receiver
+ 			   must be inserted beneath the args.  Reduce or eliminate the argument
+ 			   shuffle by only moving already spilled items."
+ 			| numSpilled |
+ 			numSpilled := self numberOfSpillsInTopNItems: numArgs.
+ 			numSpilled > 0
- 			   must be inserted beneath the args.  If nothing has been spilled first
- 			   avoid the argument shuffle by pushing ReceiverResultReg first."
- 			 (self noSpillsInTopNItems: numArgs)
  				ifTrue:
+ 					[self MoveMw: 0 r: SPReg R: TempReg.
- 					[self PushR: ReceiverResultReg.
- 					 self ssFlushTo: simStackPtr]
- 				ifFalse:
- 					[self ssFlushTo: simStackPtr.
- 					 self MoveMw: 0 r: SPReg R: TempReg.
  					 self PushR: TempReg.
+ 					 2 to: numSpilled do:
- 					 2 to: numArgs do:
  						[:index|
  						self MoveMw: index * BytesPerWord r: SPReg R: TempReg.
  						self MoveR: TempReg Mw: index - 1 * BytesPerWord r: SPReg].
+ 					 self MoveR: ReceiverResultReg Mw: numSpilled * BytesPerWord r: SPReg]
+ 				ifFalse:
+ 					[self PushR: ReceiverResultReg].
+ 			self ssFlushTo: simStackPtr]
- 					 self MoveR: ReceiverResultReg Mw: numArgs * BytesPerWord r: SPReg]]
  		"Move the args to the register arguments, being careful to do
  		 so last to first so e.g. previous contents don't get overwritten.
  		 Also check for any arg registers in use by other args."
  		ifFalse:
  			[self ssFlushTo: simStackPtr - numArgs - 1.
  			 numArgs > 0 ifTrue:
  				[(self numRegArgs > 1 and: [numArgs > 1])
  					ifTrue:
  						[self ssAllocateRequiredReg: Arg0Reg upThrough: simStackPtr - 2.
  						 self ssAllocateRequiredReg: Arg1Reg upThrough: simStackPtr - 1]
  					ifFalse:
  						[self ssAllocateRequiredReg: Arg0Reg upThrough: simStackPtr - 1]].
  			 (self numRegArgs > 1 and: [numArgs > 1]) ifTrue:
  				[(self simStackAt: simStackPtr) popToReg: Arg1Reg].
  			 numArgs > 0 ifTrue:
  				[(self simStackAt: simStackPtr - numArgs + 1)
  					popToReg: Arg0Reg]].
  	self ssPop: numArgs!

Item was removed:
- ----- Method: StackToRegisterMappingCogit>>noSpillsInTopNItems: (in category 'simulation stack') -----
- noSpillsInTopNItems: n
- 	"Answer if the simStack contains no spills in the top n items."
- 	0 to: n - 1 do:
- 		[:i| (self simStackAt: i) type = SSSpill ifTrue: [^false]].
- 	^true!

Item was added:
+ ----- Method: StackToRegisterMappingCogit>>numberOfSpillsInTopNItems: (in category 'simulation stack') -----
+ numberOfSpillsInTopNItems: n
+ 	simStackPtr to: simStackPtr - n + 1 by: -1 do:
+ 		[:i| (self simStackAt: i) type = SSSpill ifTrue:
+ 			[^n - (simStackPtr - i)]].
+ 	^0!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>ssAllocateRequiredRegMask:upThrough: (in category 'simulation stack') -----
  ssAllocateRequiredRegMask: requiredRegsMask upThrough: stackPtr
  	| lastRequired liveRegs |
  	lastRequired := -1.
  	"compute live regs while noting the last occurrence of required regs.
  	 If these are not free we must spill from simSpillBase to last occurrence.
  	 Note we are conservative here; we could allocate FPReg in frameless methods."
  	liveRegs := self registerMaskFor: FPReg and: SPReg.
  	(simSpillBase max: 0) to: stackPtr do:
  		[:i|
  		liveRegs := liveRegs bitOr: (self simStackAt: i) registerMask.
+ 		((self simStackAt: i) registerMask bitAnd: requiredRegsMask) ~= 0 ifTrue:
- 		(liveRegs bitAnd: requiredRegsMask) ~= 0 ifTrue:
  			[lastRequired := i]].
  	"If any of requiredRegsMask are live we must spill."
  	(liveRegs bitAnd: requiredRegsMask) = 0 ifFalse:
  		["Some live, must spill"
  		self ssFlushTo: lastRequired.
  		self assert: (self liveRegisters bitAnd: requiredRegsMask) = 0]!



More information about the Vm-dev mailing list