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

commits at source.squeak.org commits at source.squeak.org
Wed Apr 12 21:47:38 UTC 2017


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

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

Name: VMMaker.oscog-eem.2193
Author: eem
Time: 12 April 2017, 2:46:53.675491 pm
UUID: cf454521-165e-4268-ae52-4e47159af4c4
Ancestors: VMMaker.oscog-eem.2192

Fix ancient bug with non-local return in the StackToRegisterMappingCogit; the stack must be flushed before calling the non-local return trampoline.  Solves some, if not all, of the stack depth mismatches on non-local return.

Make sure some Siata bytecodes are recognised by the StackDepthFinder.

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

Item was changed:
  ----- Method: CogVMSimulator>>maybeCheckStackDepth:sp:pc: (in category 'debug support') -----
  maybeCheckStackDepth: delta sp: sp pc: mcpc
  	| asp bcpc startbcpc cogHomeMethod cogBlockMethod csp debugStackPointers |
  	debugStackDepthDictionary ifNil: [^self].
  	(self isMachineCodeFrame: framePointer) ifFalse: [^self].
  	cogBlockMethod := self mframeCogMethod: framePointer.
  	cogHomeMethod := self asCogHomeMethod: cogBlockMethod.
  	debugStackPointers := debugStackDepthDictionary
  								at: cogHomeMethod methodObject
  								ifAbsentPut: [self debugStackPointersFor: cogHomeMethod methodObject].
  	startbcpc := cogHomeMethod = cogBlockMethod
  					ifTrue: [self startPCOfMethod: cogHomeMethod methodObject]
  					ifFalse: [self startPCOfClosure: (self pushedReceiverOrClosureOfFrame: framePointer)].
  	bcpc := cogit bytecodePCFor: mcpc startBcpc: startbcpc in: cogBlockMethod.
  	self assert: bcpc ~= 0.
  	((cogBlockMethod ~= cogHomeMethod or: [cogBlockMethod cmIsFullBlock])
  	 and: [cogit isNonLocalReturnPC: mcpc]) ifTrue:
  		[| lastbcpc |
  		 "Method returns within a block (within an unwind-protect) must check the stack depth at the
  		  return, not the bytecode following, but the pc mapping maps to the bytecode following the
  		  return. lastBytecodePCForBlockAt:in: catches method returns at the end of a block, modifying
  		  the bcpc to that of the return.  isNonLocalReturnPC: catches method returns not at the end.
  		  Assumes method return bytecodes are 1 bytecode long;a  dodgy assumption, but good enough."
  		 lastbcpc := cogBlockMethod cmIsFullBlock
  						ifTrue: [cogit endPCOf: cogHomeMethod methodObject]
  						ifFalse: [cogit lastBytecodePCForBlockAt: startbcpc in: cogHomeMethod methodObject].
+ 		 bcpc > lastbcpc ifTrue: [bcpc := lastbcpc]].
- 		 bcpc := bcpc > lastbcpc ifTrue: [lastbcpc] ifFalse: [bcpc - 1]].
  	asp := self stackPointerIndexForFrame: framePointer WithSP: sp + objectMemory wordSize.
  	csp := debugStackPointers at: bcpc ifAbsent: [-1].
  	"Compensate for some edge cases"
  	asp - delta = csp ifTrue:
  		["Compensate for the implicit context receiver push in a trap bytecode with the absence of a contnuation.
  		  Assumes trap bytecodes are 1 byte bytecodes."
  		 (SistaVM
  		  and: [cogit isTrapAt: mcpc]) ifTrue:
  			[csp := csp + 1].
  		"Compensate lazily for absent receiver sends (cuz mapping is slow, even though incrememting csp is a dodgy idea)."
  		(NewspeakVM
  		 and: [cogit isAbsentReceiverSendAt: mcpc in: cogHomeMethod]) ifTrue:
  			[csp := debugStackPointers at: bcpc put: csp + 1]].
  	self assert: asp - delta + 1 = csp!

Item was added:
+ ----- Method: StackDepthFinder>>branchIfNotInstanceOf:distance: (in category 'instruction decoding') -----
+ branchIfNotInstanceOf: behaviorOrArrayOfBehavior distance: delta 
+ 	self drop.
+ 	self doJump: delta!

Item was changed:
+ ----- Method: StackDepthFinder>>ensureAllocateableSlots: (in category 'instruction decoding') -----
- ----- Method: StackDepthFinder>>ensureAllocateableSlots: (in category 'as yet unclassified') -----
  ensureAllocateableSlots: numSlots
  	"nothing to do here..."!

Item was changed:
  ----- Method: StackToRegisterMappingCogit>>genUpArrowReturn (in category 'bytecode generators') -----
  genUpArrowReturn
  	"Generate a method return from within a method or a block.
  	 Frameless method activation looks like
  	 CISCs (x86):
  				receiver
  				args
  		sp->	ret pc.
  	 RISCs (ARM):
  				receiver
  				args
  				ret pc in LR.
  	 A fully framed activation is described in CoInterpreter class>initializeFrameIndices.
  	 Return pops receiver and arguments off the stack.  Callee pushes the result."
- 	| framelessReturn |
  	deadCode := true. "can't fall through"
  	inBlock > 0 ifTrue:
+ 		[self assert: needsFrame.
+ 		 self ssFlushTo: simStackPtr.
- 		[self assert: needsFrame. 
  		 self CallRT: ceNonLocalReturnTrampoline.
  		 self annotateBytecode: self Label.
  		 ^0].
+ 	(self cppIf: IMMUTABILITY ifTrue: [needsFrame and: [useTwoPaths not]] ifFalse: [needsFrame])
- 	self 
- 		cppIf: IMMUTABILITY
- 		ifTrue: [framelessReturn := needsFrame and: [useTwoPaths not]]
- 		ifFalse: [framelessReturn := needsFrame].
- 	framelessReturn
  		ifTrue:
+ 			[LowcodeVM ifTrue: [ hasNativeFrame ifTrue: [ self leaveNativeFrame ] ].
- 			[
- 			 LowcodeVM ifTrue: [ hasNativeFrame ifTrue: [ self leaveNativeFrame ] ].
  			 self MoveR: FPReg R: SPReg.
  			 self PopR: FPReg.
  			 backEnd hasLinkRegister ifTrue:
  				[self PopR: LinkReg].
  			 self RetN: methodOrBlockNumArgs + 1 * objectMemory wordSize]
  		ifFalse:
  			[self RetN: ((methodOrBlockNumArgs > self numRegArgs
  						"A method with an interpreter prim will push its register args for the prim.  If the failure
  						 body is frameless the args must still be popped, see e.g. Behavior>>nextInstance."
  						or: [regArgsHaveBeenPushed])
  							ifTrue: [methodOrBlockNumArgs + 1 * objectMemory wordSize]
  							ifFalse: [0])].
  	^0!

Item was added:
+ ----- Method: VMObjectProxy>>selector (in category 'accessing') -----
+ selector
+ 	| selector |
+ 	selector := coInterpreter maybeSelectorOfMethod: oop.
+ 	^coInterpreter stringOf: selector!



More information about the Vm-dev mailing list