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

commits at source.squeak.org commits at source.squeak.org
Sun Jan 3 06:12:37 UTC 2021


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

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

Name: VMMaker.oscog-eem.2919
Author: eem
Time: 2 January 2021, 10:12:29.080225 pm
UUID: 3c606a29-4e7f-4ce7-9d1b-5ba006cff614
Ancestors: VMMaker.oscog-eem.2918

SImulation:
Add the halt check to click step when enetering interpret.
Fix CoInterpreterMT>>#enterSmalltalkExecutive as per VMMaker.oscog-eem.2918.

Refactor getReturnAddress so it can be extracted from ThisContext (the Debugger's version of thisContext).

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

Item was added:
+ ----- Method: CoInterpreterMT>>enterSmalltalkExecutive (in category 'initialization') -----
+ enterSmalltalkExecutive
+ 	"Main entry-point into the interpreter at each execution level, where an
+ 	 execution level is either the start of execution or reentry for a callback.
+ 
+ 	 N.B. It also provides the simulator's implementation of ceReturnToInterpreter/ceInvokeInterpreter, which
+ 	 via a simulation trap raise the ReenterInterpreter signal in handleCallOrJumpSimulationTrap:/reenterInterpreter.
+ 	 So when ReenterInterpreter is caught this method invokes interpret directly."
+ 	<cmacro: '() enterSmalltalkExecutiveImplementation()'>
+ 	"Simulation of the setjmp in enterSmalltalkExecutiveImplementation for reentry into interpreter."
+ 	| caught |
+ 	caught := false.
+ 	[[caught
+ 			ifFalse: [self enterSmalltalkExecutiveImplementation]
+ 			ifTrue: [self interpret]]
+ 		on: ReenterInterpreter
+ 		do: [:ex|
+ 			caught := true.
+ 			self assert: ex returnValue = ReturnToInterpreter.
+ 			ex return: true]] whileTrue!

Item was changed:
  ----- Method: CogVMSimulator>>getReturnAddress (in category 'simulation only') -----
  getReturnAddress
  	"In the real VM this answers the return address for its caller, i.e. for interpret.
  	 In the simulator we're playing fast and loose with initialEnterSmalltalkExecutive
  	 and enterSmalltalkExecutiveImplementation and need them to look and act the same."
  	| selector |
+ 	selector := thisContext getReturnAddress.
+ 	^(selector == #initialEnterSmalltalkExecutive
+ 	  or: [selector == #enterSmalltalkExecutive])
- 	selector := (thisContext findContextSuchThat: [:ctxt| ctxt selector == #interpret]) sender method selector.
- 	^selector == #initialEnterSmalltalkExecutive
  		ifTrue: [#enterSmalltalkExecutiveImplementation]
  		ifFalse: [selector]!

Item was changed:
  ----- Method: Cogit>>handleCallOrJumpSimulationTrap: (in category 'simulation only') -----
  handleCallOrJumpSimulationTrap: aProcessorSimulationTrap
  	<doNotGenerate>
  	| evaluable function memory result savedFramePointer savedStackPointer savedArgumentCount retpc |
  
  	"This is a hack fix before we revise the simulators.  When a jump call is made, the next
  	 pc is effectively the return address on the stack, not the instruction following the jump."
  	aProcessorSimulationTrap type == #jump ifTrue:
  		[processor hackFixNextPCOfJumpFor: aProcessorSimulationTrap using: objectMemory].
  
  	evaluable := simulatedTrampolines
  					at: aProcessorSimulationTrap address
  					ifAbsent: [self errorProcessingSimulationTrap: aProcessorSimulationTrap
  								in: simulatedTrampolines].
  	function := evaluable isBlock
  					ifTrue: ['aBlock; probably some plugin primitive']
  					ifFalse:
  						[evaluable receiver == backEnd ifTrue: "this is for invoking ARMv5 floating-point intrinsics"
  							[^self handleABICallOrJumpSimulationTrap: aProcessorSimulationTrap evaluable: evaluable].
  						 evaluable selector].
  	memory := coInterpreter memory.
  	function == #interpret ifTrue: "i.e. we're here via ceInvokeInterpret/ceReturnToInterpreterTrampoline and should discard all state back to enterSmalltalkExecutiveImplementation"
  		[self recordInstruction: {'(simulated jump call of '. aProcessorSimulationTrap address. '/'. function. ')'}.
+ 		 "self halt: evaluable selector."
+ 	   	 clickConfirm ifTrue:
+ 		 	[(self confirm: 'skip jump to interpret?') ifFalse:
+ 				[clickConfirm := false. self halt]].
  		 processor simulateJumpCallOf: aProcessorSimulationTrap address memory: memory.
  		 coInterpreter reenterInterpreter.
  		 "NOTREACHED"
  		 self halt].
  	function ~~ #ceBaseFrameReturn: ifTrue:
  		[coInterpreter assertValidExternalStackPointers].
  	(backEnd wantsNearAddressFor: function) ifTrue:
  		[^self perform: function with: aProcessorSimulationTrap].
  	processor
  		simulateCallOf: aProcessorSimulationTrap address
  		nextpc: aProcessorSimulationTrap nextpc
  		memory: memory.
  	retpc := processor retpcIn: memory.
  	self recordInstruction: {'(simulated call of '. aProcessorSimulationTrap address. '/'. function. ')'}.
  	savedFramePointer := coInterpreter framePointer.
  	savedStackPointer := coInterpreter stackPointer.
  	savedArgumentCount := coInterpreter argumentCount.
  	result := ["self halt: evaluable selector."
  		   	   clickConfirm ifTrue:
  			 	[(self confirm: 'skip run-time call?') ifFalse:
  					[clickConfirm := false. self halt]].
  			   evaluable valueWithArguments: (processor
  												postCallArgumentsNumArgs: evaluable numArgs
  												in: memory)]
  				on: ReenterMachineCode
  				do: [:ex| ex return: #continueNoReturn].
  			
  	coInterpreter assertValidExternalStackPointers.
  	"Verify the stack layout assumption compileInterpreterPrimitive: makes, provided we've
  	 not called something that has built a frame, such as closure value or evaluate method, or
  	 switched frames, such as primitiveSignal, primitiveWait, primitiveResume, primitiveSuspend et al."
  	(function beginsWith: 'primitive') ifTrue:
  		[coInterpreter primFailCode = 0
  			ifTrue: [(CogVMSimulator stackAlteringPrimitives includes: function) ifFalse:
  						["This is a rare case (e.g. in Scorch where a married context's sender is set to nil on trapTrpped and hence the stack layout is altered."
  						 (function == #primitiveSlotAtPut and: [objectMemory isContext: (coInterpreter frameReceiver: coInterpreter framePointer)]) ifFalse:
  							[self assert: savedFramePointer = coInterpreter framePointer.
  							 self assert: savedStackPointer + (savedArgumentCount * objectMemory wordSize)
  									= coInterpreter stackPointer]]]
  			ifFalse:
  				[self assert: savedFramePointer = coInterpreter framePointer.
  				 self assert: savedStackPointer = coInterpreter stackPointer]].
  	result ~~ #continueNoReturn ifTrue:
  		[self recordInstruction: {'(simulated return to '. processor retpcIn: memory. ')'}.
  		 processor simulateReturnIn: memory.
  		 self assert: processor pc = retpc.
  		 processor smashCallerSavedRegistersWithValuesFrom: 16r80000000 by: objectMemory wordSize].
  	self assert: (result isInteger "an oop result"
  			or: [result == coInterpreter
  			or: [result == objectMemory
  			or: [result == nil
  			or: [result == #continueNoReturn]]]]).
  	processor cResultRegister: (result
  								ifNil: [0]
  								ifNotNil: [result isInteger
  											ifTrue: [result]
  											ifFalse: [16rF00BA222]])!

Item was changed:
  ----- Method: Cogit>>tryLockVMOwnerTo: (in category 'multi-threading') -----
  tryLockVMOwnerTo: value
  	<api>
  	"ceTryLockVMOwner does an atomic compare-and-swap of the vmOwner
  	 variable with zero and the argument, setting vmOwner to value if it was
+ 	 zero. It answers if the lock was zero and hence was acquired.
+ 
+ 	 See CogThreadManager>>#tryLockVMOwnerTo: for the simulation of
+ 	 processor thread switching which surrounds this method."
- 	 zero. It answers if the lock was zero and hence was acquired."
  	<cmacro: '(value) ceTryLockVMOwner(value)'>
  	processor abiMarshalArg0: value in: objectMemory memory.
  	^[	| result |
  		result := self simulateLeafCallOf: ceTryLockVMOwner.
  		self assert: (result ~= 0) = (coInterpreter threadManager getVMOwner = value).
  		result ~= 0] ensure:
  			[processor abiUnmarshal: 1]!

Item was added:
+ ----- Method: Context>>getReturnAddress (in category '*VMMaker-simulation') -----
+ getReturnAddress
+ 	"Simulate access to the return address, used in the CoInterpreter in fast interpreter activation.
+ 	 For simulaiton map return addresses to sender selectors."
+ 	^(self findContextSuchThat: [:ctxt| ctxt selector == #interpret]) sender method selector!



More information about the Vm-dev mailing list