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

commits at source.squeak.org commits at source.squeak.org
Fri Apr 8 16:08:54 UTC 2016


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

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

Name: VMMaker.oscog-cb.1783
Author: cb
Time: 8 April 2016, 9:04:13.062 am
UUID: e9911aea-b813-48dd-9870-db6dbabe40bb
Ancestors: VMMaker.oscog-cb.1782

Added theoretical support for remote inst var access in SimpleStackBAsedCogit for system completion.

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

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genExtPushRemoteTempOrInstVarLongBytecode (in category 'bytecode generators') -----
  genExtPushRemoteTempOrInstVarLongBytecode
  	| index |
  	^ (byte2 noMask: 1 << 7)
  		ifTrue: [ self genPushRemoteTempLongBytecode ]
  		ifFalse: 
  			[ index := byte1 + (extA << 8).
  			extA := 0.
+ 			extB := 0. "don't use flags in the simple cogit"
- 			extB := 0.
  			(coInterpreter isReadMediatedContextInstVarIndex: index)
  				ifTrue: [ self genPushMaybeContextRemoteInstVar: index inObjectAt: byte2 - (1 << 7) ]
  				ifFalse: [ self genPushRemoteInstVar: index inObjectAt: byte2 - (1 << 7) ] ]!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>genExtStorePopRemoteTempOrInstVarLongBytecode: (in category 'bytecode generators') -----
+ genExtStorePopRemoteTempOrInstVarLongBytecode: popBoolean
- genExtStorePopRemoteTempOrInstVarLongBytecode: boolean
  	| index |
  	extB := 0. "simple cogit don't use the extra flag"
  	(byte2 noMask: 1 << 7)
  		ifTrue: 
+ 			[ self genStorePop: popBoolean RemoteTemp: byte1 At: byte2.
- 			[ self genStorePop: boolean RemoteTemp: byte1 At: byte2.
  			self cppIf: IMMUTABILITY ifTrue: [ self annotateBytecode: self Label ] ]
  		ifFalse: 
  			[ index := byte1 + (extA << 8).
  			extA := 0.
  			(coInterpreter isWriteMediatedContextInstVarIndex: index)
  				ifTrue: [ self 
+ 						genStorePop: popBoolean 
- 						genStorePop: boolean 
  						MaybeContextRemoteInstVar: index 
  						ofObjectAt: byte2 - (1 << 7) ]
  				ifFalse: [ self 
+ 						genStorePop: popBoolean 
- 						genStorePop: boolean 
  						RemoteInstVar: index 
  						ofObjectAt: byte2 - (1 << 7)  ] ].
  	^ 0!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genPushMaybeContextRemoteInstVar:inObjectAt: (in category 'bytecode generator support') -----
+ genPushMaybeContextRemoteInstVar: slotIndex inObjectAt: objectIndex
+ 	| jmpSingle jmpDone |
+ 	<var: #jmpSingle type: #'AbstractInstruction *'>
+ 	<var: #jmpDone type: #'AbstractInstruction *'>
+ 	self assert: needsFrame.
+ 	"See CoInterpreter>>contextInstructionPointer:frame: for an explanation
+ 	 of the instruction pointer slot handling."
+ 	self MoveMw: (self frameOffsetOfTemporary: objectIndex) r: FPReg R: ReceiverResultReg.
+ 	objectRepresentation 
+ 		genEnsureOopInRegNotForwarded: ReceiverResultReg 
+ 		scratchReg: TempReg.
+ 	slotIndex = InstructionPointerIndex ifTrue:
+ 		[self MoveCq: slotIndex R: SendNumArgsReg.
+ 		 self CallRT: ceFetchContextInstVarTrampoline.
+ 		 self PushR: SendNumArgsReg.
+ 		 ^0].
+ 	objectRepresentation
+ 		genLoadSlot: SenderIndex
+ 		sourceReg: ReceiverResultReg
+ 		destReg: TempReg.
+ 	jmpSingle := objectRepresentation genJumpNotSmallIntegerInScratchReg: TempReg.
+ 	self MoveCq: slotIndex R: SendNumArgsReg.
+ 	self CallRT: ceFetchContextInstVarTrampoline.
+ 	jmpDone := self Jump: 0.
+ 	jmpSingle jmpTarget: self Label.
+ 	objectRepresentation
+ 		genLoadSlot: slotIndex
+ 		sourceReg: ReceiverResultReg
+ 		destReg: SendNumArgsReg.
+ 	jmpDone jmpTarget: (self PushR: SendNumArgsReg).
+ 	^0
+ !

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genPushRemoteInstVar:inObjectAt: (in category 'bytecode generator support') -----
+ genPushRemoteInstVar: index inObjectAt: objectIndex
+ 	self MoveMw: (self frameOffsetOfTemporary: objectIndex) r: FPReg R: ClassReg.
+ 	objectRepresentation 
+ 		genEnsureOopInRegNotForwarded: ClassReg 
+ 		scratchReg: TempReg.
+ 	objectRepresentation
+ 		genLoadSlot: index
+ 		sourceReg: ClassReg
+ 		destReg: TempReg.
+ 	self PushR: TempReg.
+ 	^0!

Item was added:
+ ----- Method: SimpleStackBasedCogit>>genStorePop:MaybeContextRemoteInstVar:ofObjectAt: (in category 'bytecode generator support') -----
+ genStorePop: popBoolean MaybeContextRemoteInstVar: slotIndex ofObjectAt: objectIndex
+ 	<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."
+ 	self assert: needsFrame.
+ 	self MoveMw: (self frameOffsetOfTemporary: objectIndex) r: FPReg R: ReceiverResultReg.
+ 	objectRepresentation 
+ 		genEnsureOopInRegNotForwarded: ReceiverResultReg 
+ 		scratchReg: TempReg.
+ 	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 added:
+ ----- Method: SimpleStackBasedCogit>>genStorePop:RemoteInstVar:ofObjectAt: (in category 'bytecode generator support') -----
+ genStorePop: popBoolean RemoteInstVar: slotIndex ofObjectAt: 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."
+ 	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!



More information about the Vm-dev mailing list