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

commits at source.squeak.org commits at source.squeak.org
Tue Jul 27 19:15:17 UTC 2021


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

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

Name: VMMaker.oscog-eem.3001
Author: eem
Time: 27 July 2021, 12:15:10.344248 pm
UUID: 36517924-4356-4398-91f4-383c14d4c0d0
Ancestors: VMMaker.oscog-mt.3000

Fix two errors in the new compileInterpreterPrimitive:flags: :
- remember to zero primFailCode before retrying a primitive after encountering forwarders
- reload the stack pointer correctly on CISCs. The retpc of the send is on top of stack, below the last primitive argument.

=============== Diff against VMMaker.oscog-mt.3000 ===============

Item was added:
+ ----- Method: CogAbstractInstruction>>genLoadStackPointersForFastPrimCall: (in category 'smalltalk calling convention') -----
+ genLoadStackPointersForFastPrimCall: spareReg
+ 	"Switch back to the Smalltalk stack where there may be a C return address on top of stack below
+ 	 the last primitive argument. Assign SPReg first because typically it is used immediately afterwards."
+ 	self hasLinkRegister
+ 		ifTrue: [self genLoadStackPointers]
+ 		ifFalse:
+ 			[cogit
+ 				MoveAw: cogit stackPointerAddress R: spareReg;
+ 				"N.B. dont use SubCq:R:R: since it may generate MoveR:spareRegR:SPReg;SubCq:wordSize R:SPReg
+ 				 which allows for the ret addr to be smashed by an interrupt between the two insructions."
+ 				SubCq: objectMemory wordSize R: spareReg;
+ 				MoveR: spareReg R: SPReg;
+ 				MoveAw: cogit framePointerAddress R: FPReg].
+ 	^0!

Item was changed:
  ----- Method: Cogit>>handleCallOrJumpSimulationTrap: (in category 'simulation only') -----
  handleCallOrJumpSimulationTrap: aProcessorSimulationTrap
  	<doNotGenerate>
  	| evaluable function memory result savedFramePointer savedStackPointer savedArgumentCount retpc invalidStackPointersExpected |
  	"Execution of a single instruction must be within the processorLock critical section to ensure
  	 simulation traps are executed atomically.  However, at this point control is leaving machine
  	 code and entering the run-time and hence the lock must be released."
  	processorLock primitiveExitCriticalSection.
  	"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, and for the short-cut tracing trampolines"
  							[^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].
  	invalidStackPointersExpected := false.
  	function ~~ #ceBaseFrameReturn: ifTrue:
  		[evaluable isBlock
  			ifTrue: "external primitives..."
  				["The only acceptable exception to the rule are fast C primitive calls..."
  				 (methodZone cogMethodContaining: (self mostLikelyPrimInvocationPC: processor pc or: (processor leafRetpcIn: memory)))
  					ifNil: [self assertf: 'call to block evaluable from non-external method']
  					ifNotNil: [:cogMethod|
  							self assert: (self cogMethodHasExternalPrim: cogMethod).
  							(coInterpreter hasFastCLinkage: cogMethod methodObject)
  								ifTrue: [invalidStackPointersExpected := true. coInterpreter nilLocalFP]
  								ifFalse: [coInterpreter assertValidExternalStackPointers]]]
  			ifFalse:
  				[coInterpreter assertValidExternalStackPointers]].
  	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].
  			
  	invalidStackPointersExpected ifFalse:
  		[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: [#(nil true false continueNoReturn) includes: result]]]).
- 			or: [result == nil
- 			or: [result == #continueNoReturn]]]]).
  	processor cResultRegister: (result
  								ifNil: [0]
  								ifNotNil: [result isInteger
  											ifTrue: [result]
  											ifFalse: [16rF00BA222]])!

Item was changed:
  ----- Method: Integer>>asUnsignedInteger (in category '*VMMaker-interpreter simulator') -----
  asUnsignedInteger
+ 	"Since the simulator deals with positive integers most of the time we assert that the receiver is greater than
+ 	 zero. One exception is stack pointers in the StackInterpreterSimulator, which are negative. Another is the fast
+ 	 isLargeIntegerInstance: test in SpurMemoryManager. So don't fail in these cases."
- 	"Since the simulator deals with positive integers most of the time we assert that the receiver is greater than zero.
- 	 But one major exception is stack pointers in the StackInterpreterSimulator, which are negative.  So don't fail
- 	 if the sender is a StackInterpreter and the receiver could be a stack pointer."
  	self >= 0 ifFalse:
+ 		[thisContext sender selector == #isLargeIntegerInstance: ifTrue:
+ 			[^self bitAnd: (1 bitShift: thisContext sender receiver wordSize * 8) - 1].
+ 		 self assert: (((thisContext sender methodClass includesBehavior: CoInterpreter)
- 		[self assert: (((thisContext sender methodClass includesBehavior: CoInterpreter)
  					   and: [self between: Cogit maxNegativeErrorCode and: -1])
  					or: [(thisContext sender methodClass includesBehavior: StackInterpreter)
  					   and: [thisContext sender receiver stackPages couldBeFramePointer: self]])].
+ 	
  	^self!

Item was changed:
  Cogit subclass: #SimpleStackBasedCogit
+ 	instanceVariableNames: 'primitiveGeneratorTable introspectionDataIndex introspectionData'
- 	instanceVariableNames: 'primitiveGeneratorTable primSetFunctionLabel primInvokeInstruction introspectionDataIndex introspectionData'
  	classVariableNames: ''
  	poolDictionaries: 'VMMethodCacheConstants VMObjectIndices VMSqueakClassIndices'
  	category: 'VMMaker-JIT'!
  
  !SimpleStackBasedCogit commentStamp: '<historical>' prior: 0!
  I am the stage one JIT for Cog that does not attempt to eliminate the stack via deferred code generation.!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compileInterpreterPrimitive:flags: (in category 'primitive generators') -----
  compileInterpreterPrimitive: primitiveRoutine flags: flags
  	"Compile a call to an interpreter primitive.  Call the C routine with the
  	 usual stack-switching dance, test the primFailCode and then either
  	 return on success or continue to the method body."
  	<var: #primitiveRoutine declareC: 'void (*primitiveRoutine)(void)'>
  	| jmp jmpSamplePrim continuePostSamplePrim jmpSampleNonPrim continuePostSampleNonPrim |
  	"Save processor fp, sp and return pc in the interpreter's frame stack and instruction pointers"
  	self genExternalizePointersForPrimitiveCall.
  	"Switch to the C stack."
  	self genLoadCStackPointersForPrimCall.
  
  	(flags anyMask: PrimCallCollectsProfileSamples) ifTrue:
  		["Test nextProfileTick for being non-zero and call checkProfileTick if so"
  		objectMemory wordSize = 4
  			ifTrue:
  				[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
  				 self MoveAw: coInterpreter nextProfileTickAddress + objectMemory wordSize R: ClassReg.
  				 self OrR: TempReg R: ClassReg]
  			ifFalse:
  				[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
  				 self CmpCq: 0 R: TempReg].
  		"If set, jump to record sample call."
  		jmpSampleNonPrim := self JumpNonZero: 0.
  		continuePostSampleNonPrim := self Label].
  
  	"Old old full prim trace is in VMMaker-eem.550 and prior.
  	 Old simpler full prim trace is in VMMaker-eem.2969 and prior."
  	(coInterpreter recordPrimTraceForMethod: methodObj) ifTrue:
  		[self genFastPrimTraceUsing: ClassReg and: SendNumArgsReg].
  
  	"Clear the primFailCode and set argumentCount"
  	self MoveCq: 0 R: TempReg.
  	self MoveR: TempReg Aw: coInterpreter primFailCodeAddress.
  	methodOrBlockNumArgs ~= 0 ifTrue:
  		[self MoveCq: methodOrBlockNumArgs R: TempReg].
  	self MoveR: TempReg Aw: coInterpreter argumentCountAddress.
  
  	"If required, set primitiveFunctionPointer and newMethod"
  	(flags anyMask: PrimCallNeedsPrimitiveFunction) ifTrue:
  		[self MoveCw: primitiveRoutine asInteger R: TempReg.
- 		 primSetFunctionLabel :=
  		 self MoveR: TempReg Aw: coInterpreter primitiveFunctionPointerAddress].
  	(flags anyMask: PrimCallNeedsNewMethod+PrimCallMayEndureCodeCompaction) ifTrue:
  		["The ceActivateFailingPrimitiveMethod: machinery can't handle framelessness."
  		 (flags anyMask: PrimCallMayEndureCodeCompaction) ifTrue:
  			[needsFrame := true].
  		 methodLabel addDependent:
  			(self annotateAbsolutePCRef:
  				(self MoveCw: methodLabel asInteger R: ClassReg)).
  		 self MoveMw: (self offset: CogMethod of: #methodObject) r: ClassReg R: TempReg.
  		 self MoveR: TempReg Aw: coInterpreter newMethodAddress].
  
  	"Invoke the primitive"
  	self PrefetchAw: coInterpreter primFailCodeAddress.
  	(flags anyMask: PrimCallMayEndureCodeCompaction)
  		ifTrue: "Sideways call the C primitive routine so that we return through cePrimReturnEnterCogCode."
  			["On Spur ceActivateFailingPrimitiveMethod: would like to retry if forwarders
  			  are found. So insist on PrimCallNeedsPrimitiveFunction being set too."
  			 objectMemory hasSpurMemoryManagerAPI ifTrue:
  				[self assert: (flags anyMask: PrimCallNeedsPrimitiveFunction)].
  			 backEnd
  				genMarshallNArgs: 0 arg: nil arg: nil arg: nil arg: nil;
  				genSubstituteReturnAddress:
  					((flags anyMask: PrimCallCollectsProfileSamples)
  						ifTrue: [cePrimReturnEnterCogCodeProfiling]
  						ifFalse: [cePrimReturnEnterCogCode]).
+ 			 self JumpFullRT: primitiveRoutine asInteger.
- 			 primInvokeInstruction := self JumpFullRT: primitiveRoutine asInteger.
  			 jmp := jmpSamplePrim := continuePostSamplePrim := nil]
  		ifFalse:
  			["Call the C primitive routine."
  			backEnd genMarshallNArgs: 0 arg: 0 arg: 0 arg: 0 arg: 0.
+ 			self CallFullRT: primitiveRoutine asInteger.
- 			primInvokeInstruction := self CallFullRT: primitiveRoutine asInteger.
  			backEnd genRemoveNArgsFromStack: 0.
  			(flags anyMask: PrimCallCollectsProfileSamples) ifTrue:
  				[self assert: (flags anyMask: PrimCallNeedsNewMethod).
  				"Test nextProfileTick for being non-zero and call checkProfileTick if so"
  				objectMemory wordSize = 4
  					ifTrue:
  						[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
  						 self MoveAw: coInterpreter nextProfileTickAddress + objectMemory wordSize R: ClassReg.
  						 self OrR: TempReg R: ClassReg]
  					ifFalse:
  						[self MoveAw: coInterpreter nextProfileTickAddress R: TempReg.
  						 self CmpCq: 0 R: TempReg].
  				"If set, jump to record sample call."
  				jmpSamplePrim := self JumpNonZero: 0.
  				continuePostSamplePrim := self Label].
  			objectRepresentation maybeCompileRetryOnPrimitiveFail: primitiveIndex.
  			"Switch back to the Smalltalk stack.  Stack better be in either of these two states:
  				success:	stackPointer ->	result (was receiver)
  											arg1
  											...
  											argN
  											return pc
  				failure:						receiver
  											arg1
  											...
  							stackPointer ->	argN
  											return pc
  			In either case we can push the instructionPointer or load it into the LinkRegister to reestablish the return pc"
  			self MoveAw: coInterpreter instructionPointerAddress
  				R: (backEnd hasLinkRegister ifTrue: [LinkReg] ifFalse: [ClassReg]).
  			backEnd genLoadStackPointers.
  			"Test primitive failure"
  			self MoveAw: coInterpreter primFailCodeAddress R: TempReg.
  			backEnd hasLinkRegister ifFalse: [self PushR: ClassReg]. "Restore return pc on CISCs"
  			self flag: 'ask concrete code gen if move sets condition codes?'.
  			self CmpCq: 0 R: TempReg.
  			jmp := self JumpNonZero: 0.
  			"Fetch result from stack"
  			self MoveMw: (backEnd hasLinkRegister ifTrue: [0] ifFalse: [objectMemory wordSize])
  				r: SPReg
  				R: ReceiverResultReg.
  			self RetN: objectMemory wordSize].	"return to caller, popping receiver"
  
  	(flags anyMask: PrimCallCollectsProfileSamples) ifTrue:
  		["The sample is collected by cePrimReturnEnterCogCode for external calls"
  		jmpSamplePrim ifNotNil:
  			["Call ceCheckProfileTick: to record sample and then continue."
  			jmpSamplePrim jmpTarget: self Label.
  			self assert: (flags anyMask: PrimCallNeedsNewMethod).
  			self CallFullRT: (self cCode: [#ceCheckProfileTick asUnsignedIntegerPtr]
  							   inSmalltalk: [self simulatedTrampolineFor: #ceCheckProfileTick]).
  			"reenter the post-primitive call flow"
  			self Jump: continuePostSamplePrim].
  		"Null newMethod and call ceCheckProfileTick: to record sample and then continue.
  		 ceCheckProfileTick will map null/0 to coInterpreter nilObject"
  		jmpSampleNonPrim jmpTarget: self Label.
  		self MoveCq: 0 R: TempReg.
  		self MoveR: TempReg Aw: coInterpreter newMethodAddress.
  		self CallFullRT: (self cCode: [#ceCheckProfileTick asUnsignedIntegerPtr]
  						   inSmalltalk: [self simulatedTrampolineFor: #ceCheckProfileTick]).
  		"reenter the post-primitive call flow"
  		self Jump: continuePostSampleNonPrim].
  
  	jmp ifNotNil:
  		["Jump to restore of receiver reg and proceed to frame build for failure."
  		 jmp jmpTarget: self Label.
  		 "Restore receiver reg from stack.  If on RISCs ret pc is in LinkReg, if on CISCs ret pc is on stack."
  		 self MoveMw: objectMemory wordSize * (methodOrBlockNumArgs + (backEnd hasLinkRegister ifTrue: [0] ifFalse: [1]))
  			r: SPReg
  			R: ReceiverResultReg].
  	^0!

Item was changed:
  ----- Method: SimpleStackBasedCogit>>compileOnStackExternalPrimitive: (in category 'primitive generators') -----
  compileOnStackExternalPrimitive: primitiveRoutine
  	"Compile a fast call of a C primitive using the current stack page, avoiding the stack switch except on failure.
  	 This convention still uses stackPointer and argumentCount to access operands.  Push all operands to the stack,
  	 assign stackPointer, argumentCount, and zero primFailCode.  Make the call (saving a LinkReg if required).
  	 Test for failure and return.  On failure on Spur, if there is an accessor depth, assign framePointer and newMethod,
  	 do the stack switch, call checkForAndFollowForwardedPrimitiveState, and loop back if forwarders are found.
+ 	 Fall through to frame build."
- 	 Fall throguh tio frame build."
  	 
  	<var: #primitiveRoutine declareC: 'void (*primitiveRoutine)(void)'>
  	| jmp retry calleeSavedReg |
  	"Clear the primFailCode and set argumentCount"
  	self MoveCq: 0 R: TempReg.
  	self MoveR: TempReg Aw: coInterpreter primFailCodeAddress.
  	methodOrBlockNumArgs ~= 0 ifTrue:
  		[self MoveCq: methodOrBlockNumArgs R: TempReg].
  	self MoveR: TempReg Aw: coInterpreter argumentCountAddress.
  	self genExternalizeStackPointerForFastPrimitiveCall.
  	backEnd hasLinkRegister ifTrue:
  		[self PushR: LinkReg].
  	retry := self Label.
  	calleeSavedReg := NoReg.
  	(SPReg ~= NativeSPReg
  	 and: [(self isCalleeSavedReg: SPReg) not]) ifTrue:
  		[calleeSavedReg := self availableRegisterOrNoneIn: ABICalleeSavedRegisterMask.
  		 self deny: calleeSavedReg = NoReg.
  		 self MoveR: SPReg R: calleeSavedReg].
  	self CallFullRT: primitiveRoutine.
  	self MoveAw: coInterpreter primFailCodeAddress R: TempReg.
  	calleeSavedReg ~= NoReg ifTrue:
  		[self MoveR: calleeSavedReg R: SPReg].
  	self CmpCq: 0 R: TempReg.
  	jmp := self JumpNonZero: 0.
  	backEnd hasLinkRegister
  		ifTrue: [self PopR: LinkReg]
  		ifFalse: [self PopR: TempReg]. "i.e. save retpc"
  	self MoveAw: coInterpreter stackPointerAddress R: SPReg.
  	self PopR: ReceiverResultReg.
  	backEnd hasLinkRegister ifFalse: [self PushR: TempReg]. "i.e. restore retpc"
  	self RetN: 0.
  
  	jmp jmpTarget: self Label.
  	(objectRepresentation hasSpurMemoryManagerAPI
  	 and: [(coInterpreter accessorDepthForExternalPrimitiveMethod: methodObj) >= 0]) ifTrue:
+ 		[| skip |
+ 		 "Given that following primitive state to the accessor depth is recursive, we're asking for
- 		["Given that following primitive state to the accessor depth is recursive, we're asking for
  		  trouble if we run the fixup on the Smalltalk stack page.  Run it on the full C stack instead.
  		 This won't be a performance issue since primitive failure should be very rare."
  		self MoveR: FPReg Aw: coInterpreter framePointerAddress.
+ 		self MoveCw: primitiveRoutine asInteger R: TempReg.
+ 		self MoveR: TempReg Aw: coInterpreter primitiveFunctionPointerAddress.
  		self genLoadCStackPointersForPrimCall.
+ 		methodLabel addDependent:
- 		 methodLabel addDependent:
  			(self annotateAbsolutePCRef:
  				(self MoveCw: methodLabel asInteger R: ClassReg)).
  		self MoveMw: (self offset: CogMethod of: #methodObject) r: ClassReg R: TempReg.
  		self MoveR: TempReg Aw: coInterpreter newMethodAddress.
  		self CallFullRT: (self cCode: [#checkForAndFollowForwardedPrimitiveState asUnsignedIntegerPtr]
  							   inSmalltalk: [self simulatedTrampolineFor: #checkForAndFollowForwardedPrimitiveState]).
+ 		backEnd genLoadStackPointersForFastPrimCall: ClassReg.
- 		backEnd genLoadStackPointers.
  		self CmpCq: 0 R: ABIResultReg.
+ 		skip := self JumpZero: 0.
+ 		self MoveCq: 0 R: TempReg.
+ 		self MoveR: TempReg Aw: coInterpreter primFailCodeAddress.
+ 		self Jump: retry.
+ 		skip jmpTarget: self Label].
- 		self JumpNonZero: retry].
  	^0!



More information about the Vm-dev mailing list