[Vm-dev] VM Maker: VMMaker.oscog-cb.1761.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Apr 5 15:33:29 UTC 2016


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

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

Name: VMMaker.oscog-cb.1761
Author: cb
Time: 5 April 2016, 8:30:22.911 am
UUID: 9c2db655-156a-4a19-ad6b-562101255631
Ancestors: VMMaker.oscog-cb.1760

correctly reset the extension state in many places.

=============== Diff against VMMaker.oscog-cb.1760 ===============

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genJumpIf:to: (in category 'bytecode generator support') -----
  genJumpIf: boolean to: targetBytecodePC
  	<inline: false>
  	"Cunning trick by LPD.  If true and false are contiguous subtract the smaller.
  	 Correct result is either 0 or the distance between them.  If result is not 0 or
  	 their distance send mustBeBoolean."
  	| ok |
  	<var: #ok type: #'AbstractInstruction *'>
  	self assert: (objectMemory objectAfter: objectMemory falseObject) = objectMemory trueObject.
  	self PopR: TempReg.
  	self annotate: (self SubCw: boolean R: TempReg) objRef: boolean.
  	self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC).
  	self CmpCq: (boolean == objectMemory falseObject
  					ifTrue: [objectMemory trueObject - objectMemory falseObject]
  					ifFalse: [objectMemory falseObject - objectMemory trueObject])
  		R: TempReg.
  	ok := self JumpZero: 0.
  	self CallRT: (boolean == objectMemory falseObject
  					ifTrue: [ceSendMustBeBooleanAddFalseTrampoline]
  					ifFalse: [ceSendMustBeBooleanAddTrueTrampoline]).
  	ok jmpTarget: (self annotateBytecode: self Label).
+ 	extA := 0. "ignores the flag"
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genStorePop:LiteralVariable: (in category 'bytecode generator support') -----
  genStorePop: popBoolean LiteralVariable: litVarIndex
  	<inline: false>
  	| association |
  	"The only reason we assert needsFrame here is that in a frameless method
  	 ReceiverResultReg must and does contain only self, but the ceStoreCheck
  	 trampoline expects the target of the store to be in ReceiverResultReg.  So
  	 in a frameless method we would have a conflict between the receiver and
  	 the literal store, unless we we smart enough to realise that ReceiverResultReg
  	 was unused after the literal variable store, unlikely given that methods
  	 return self by default."
+ 	extB := 0. "do the store check anyway"
  	self assert: needsFrame.
  	association := self getLiteral: litVarIndex.
  	self genMoveConstant: association R: ReceiverResultReg.
  	objectRepresentation
  		genEnsureObjInRegNotForwarded: ReceiverResultReg
  		scratchReg: TempReg.
  	popBoolean
  		ifTrue: [self PopR: ClassReg]
  		ifFalse: [self MoveMw: 0 r: SPReg R: ClassReg].
  	self
  		genStoreSourceReg: ClassReg 
  		slotIndex: ValueIndex 
  		destReg: ReceiverResultReg 
  		scratchReg: TempReg 
  		inFrame: needsFrame.
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genStorePop:MaybeContextReceiverVariable: (in category 'bytecode generator support') -----
  genStorePop: popBoolean MaybeContextReceiverVariable: slotIndex
  	<inline: false>
  	| jmpSingle jmpDone |
  	<var: #jmpSingle type: #'AbstractInstruction *'>
  	<var: #jmpDone type: #'AbstractInstruction *'>
  	"The reason we need a frame here is that assigning to an inst var of a context may
  	 involve wholesale reorganization of stack pages, and the only way to preserve the
  	 execution state of an activation in that case is if it has a frame."
+ 	extB := 0. "do the store check anyway"
  	self assert: needsFrame.
  	self putSelfInReceiverResultReg.
  	objectRepresentation
  		genLoadSlot: SenderIndex
  		sourceReg: ReceiverResultReg
  		destReg: TempReg.
  	self MoveMw: 0 r: SPReg R: ClassReg.
  	jmpSingle := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
  	self MoveCq: slotIndex R: SendNumArgsReg.
  	self CallRT: ceStoreContextInstVarTrampoline.
  	jmpDone := self Jump: 0.
  	jmpSingle jmpTarget: self Label.
  	popBoolean ifTrue:
  		[self AddCq: objectMemory wordSize R: SPReg].
  	self
  		genStoreSourceReg: ClassReg 
  		slotIndex: slotIndex 
  		destReg: ReceiverResultReg 
  		scratchReg: TempReg 
  		inFrame: needsFrame.
  	jmpDone jmpTarget: self Label.
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genStorePop:ReceiverVariable: (in category 'bytecode generator support') -----
  genStorePop: popBoolean ReceiverVariable: slotIndex
  	<inline: false>
+ 	extB := 0. "do the store check anyway"
  	needsFrame ifTrue:
  		[self putSelfInReceiverResultReg].
  	popBoolean
  		ifTrue: [self PopR: ClassReg]
  		ifFalse: [self MoveMw: 0 r: SPReg R: ClassReg].
  	self
  		genStoreSourceReg: ClassReg 
  		slotIndex: slotIndex 
  		destReg: ReceiverResultReg 
  		scratchReg: TempReg 
  		inFrame: needsFrame.
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genStorePop:RemoteInstVar:At: (in category 'bytecode generator support') -----
  genStorePop: popBoolean RemoteInstVar: slotIndex At: objectIndex 
  	<inline: false>
  	"The only reason we assert needsFrame here is that in a frameless method
  	 ReceiverResultReg must and does contain only self, but the ceStoreCheck
  	 trampoline expects the target of the store to be in ReceiverResultReg.  So
  	 in a frameless method we would have a conflict between the receiver and
  	 the temote temp store, unless we we smart enough to realise that
  	 ReceiverResultReg was unused after the literal variable store, unlikely given
  	 that methods return self by default."
+ 	extB := 0. "do the store check anyway"
  	self assert: needsFrame.
  	popBoolean
  		ifTrue: [self PopR: ClassReg]
  		ifFalse: [self MoveMw: 0 r: SPReg R: ClassReg].
  	self MoveMw: (self frameOffsetOfTemporary: objectIndex) r: FPReg R: ReceiverResultReg.
  	objectRepresentation 
  		genEnsureOopInRegNotForwarded: ReceiverResultReg 
  		scratchReg: TempReg.
  	^objectRepresentation
  		genStoreSourceReg: ClassReg
  		slotIndex: slotIndex
  		destReg: ReceiverResultReg
  		scratchReg: TempReg
  		inFrame: needsFrame!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genStorePop:RemoteTemp:At: (in category 'bytecode generator support') -----
  genStorePop: popBoolean RemoteTemp: slotIndex At: remoteTempIndex
  	<inline: false>
  	"The only reason we assert needsFrame here is that in a frameless method
  	 ReceiverResultReg must and does contain only self, but the ceStoreCheck
  	 trampoline expects the target of the store to be in ReceiverResultReg.  So
  	 in a frameless method we would have a conflict between the receiver and
  	 the temote temp store, unless we we smart enough to realise that
  	 ReceiverResultReg was unused after the literal variable store, unlikely given
  	 that methods return self by default."
+ 	extB := 0. "do the store check anyway"
  	self assert: needsFrame.
  	popBoolean
  		ifTrue: [self PopR: ClassReg]
  		ifFalse: [self MoveMw: 0 r: SPReg R: ClassReg].
  	self MoveMw: (self frameOffsetOfTemporary: remoteTempIndex) r: FPReg R: ReceiverResultReg.
  	^objectRepresentation
  		genStoreSourceReg: ClassReg
  		slotIndex: slotIndex
  		destReg: ReceiverResultReg
  		scratchReg: TempReg
  		inFrame: needsFrame!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>genCounterTripOnlyJumpIf:to: (in category 'bytecode generator support') -----
  genCounterTripOnlyJumpIf: boolean to: targetBytecodePC 
  	"Specific version if the branch is only reached while falling through if the counter trips after an inlined #== branch. We do not regenerate the counter logic in this case to avoid 24 bytes instructions."
  	
  	<var: #ok type: #'AbstractInstruction *'>
  	<var: #mustBeBooleanTrampoline type: #'AbstractInstruction *'>
  
  	| ok mustBeBooleanTrampoline |
  
+ 	extA := 0. "reset it, we don't care if MBB not needed as we need the trampoline anyway"
+ 
  	self ssFlushTo: simStackPtr - 1.
  	
  	self ssTop popToReg: TempReg.
  	
  	self ssPop: 1.
  
  	counterIndex := counterIndex + 1. "counters are increased / decreased in the inlined branch"
  
  	"We need SendNumArgsReg because of the mustBeBooleanTrampoline"
  	self ssAllocateRequiredReg: SendNumArgsReg.
  	self MoveCq: 1 R: SendNumArgsReg.
  	
  	"The first time this is reached, it calls necessarily the counter trip for the trampoline because SendNumArgsReg is non zero"
  	mustBeBooleanTrampoline := self CallRT: (boolean == objectMemory falseObject
  						ifTrue: [ceSendMustBeBooleanAddFalseTrampoline]
  						ifFalse: [ceSendMustBeBooleanAddTrueTrampoline]).
  
  	self annotateBytecode: self Label.
  
  	"Cunning trick by LPD.  If true and false are contiguous subtract the smaller.
  	 Correct result is either 0 or the distance between them.  If result is not 0 or
  	 their distance send mustBeBoolean."
  	self assert: (objectMemory objectAfter: objectMemory falseObject) = objectMemory trueObject.
  	self annotate: (self SubCw: boolean R: TempReg) objRef: boolean.
  	self JumpZero: (self ensureFixupAt: targetBytecodePC - initialPC).
  
  	self CmpCq: (boolean == objectMemory falseObject
  					ifTrue: [objectMemory trueObject - objectMemory falseObject]
  					ifFalse: [objectMemory falseObject - objectMemory trueObject])
  		R: TempReg.
  		
  	ok := self JumpZero: 0.
  	self MoveCq: 0 R: SendNumArgsReg. "if counterReg is 0 this is a mustBeBoolean, not a counter trip."		
  
  	self Jump: mustBeBooleanTrampoline.
  	
  	ok jmpTarget: self Label.
  	^0!



More information about the Vm-dev mailing list