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

commits at source.squeak.org commits at source.squeak.org
Tue Jul 27 20:49:46 UTC 2021


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

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

Name: VMMaker.oscog-eem.3003
Author: eem
Time: 27 July 2021, 1:49:36.504414 pm
UUID: dd2cf315-8c10-45ac-9ad5-336ddc486b87
Ancestors: VMMaker.oscog-eem.3002

Cogit: fix what is hopefully the last bug with the new FastCPrimitive scheme.  ReceiverResultReg must be reloaded if it is in the ABI's caller saved registers sicne it may have been smashed and the prologue sequence assumes ReceiverResultReg is live.

Simulation: get the ThreadedFFIPlugin to load and simulate.  Cope with checkForAndFollowForwardedPrimitiveState returning a boolean in handleCallOrJumpSimulationTrap:.

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

Item was changed:
  ----- Method: Cogit>>checkIfValidOopRefAndTarget:pc:cogMethod: (in category 'garbage collection') -----
  checkIfValidOopRefAndTarget: annotation pc: mcpc cogMethod: cogMethod
  	"Check for a valid object reference, if any, at a map entry.  Answer a code unique to each error for debugging."
  	<var: #mcpc type: #'char *'>
+ 	<var: #cogMethod type: #'CogMethod *'>
+ 
  	<var: #nsSendCache type: #'NSSendCache *'>
  	| literal entryPoint |
  	annotation = IsObjectReference ifTrue:
  		[literal := literalsManager fetchLiteralAtAnnotatedAddress: mcpc asUnsignedInteger using: backEnd.
  		 (self asserta: (objectRepresentation checkValidOopReference: literal)) ifFalse:
  			[^1].
  		((objectRepresentation couldBeObject: literal)
  		 and: [objectMemory isReallyYoungObject: literal]) ifTrue:
  			[(self asserta: (self cCoerceSimple: cogMethod to: #'CogMethod *') cmRefersToYoung) ifFalse:
  				[^2]]].
  
  	NewspeakVM ifTrue:
  		[annotation = IsNSSendCall ifTrue:
  			[| nsSendCache classTag enclosingObject nsTargetMethod |
  			nsSendCache := self nsSendCacheFromReturnAddress: mcpc asInteger.
  			(self asserta: (objectRepresentation checkValidOopReference: nsSendCache selector)) ifFalse:
  				[^9].
  			classTag := nsSendCache classTag.
  			(self asserta: (classTag = 0 or: [objectRepresentation validInlineCacheTag: classTag])) ifFalse:
  				[^10].
  			enclosingObject := nsSendCache enclosingObject.
  			(self asserta: (enclosingObject = 0 or: [objectRepresentation checkValidOopReference: enclosingObject])) ifFalse:
  				[^11].
  			entryPoint := nsSendCache target.
  			entryPoint ~= 0 ifTrue: [
  				nsTargetMethod := self cCoerceSimple: entryPoint - cmNoCheckEntryOffset to: #'CogMethod *'.
  				(self asserta: (nsTargetMethod cmType = CMMethod)) ifFalse:
  					[^12]]]].
  
  	(self isPureSendAnnotation: annotation) ifTrue:
  		[(self asserta: (self cCoerceSimple: cogMethod to: #'CogMethod *') cmType = CMMethod) ifFalse:
  			[^3].
  		 self entryCacheTagAndCouldBeObjectAt: mcpc annotation: annotation into:
  			[:entryPt :cacheTag :tagCouldBeObject|
  			entryPoint := entryPt.
  			tagCouldBeObject
  				ifTrue:
  					[(objectRepresentation couldBeObject: cacheTag)
  						ifTrue:
  							[(self asserta: (objectRepresentation checkValidOopReference: cacheTag)) ifFalse:
  								[^4]]
  						ifFalse:
  							[(self asserta: (objectRepresentation validInlineCacheTag: cacheTag)) ifFalse:
  								[^5]].
  					((objectRepresentation couldBeObject: cacheTag)
  					 and: [objectMemory isReallyYoungObject: cacheTag]) ifTrue:
  						[(self asserta: (self cCoerceSimple: cogMethod to: #'CogMethod *') cmRefersToYoung) ifFalse:
  							[^6]]]
  				ifFalse:
  					[(self inlineCacheTagsAreIndexes
  					  and: [self entryPointTagIsSelector: entryPoint])
  						ifTrue:
  							[cacheTag signedIntFromLong < 0
  								ifTrue:
  									[cacheTag signedIntFromLong negated > NumSpecialSelectors ifTrue:
  										[^7]]
  								ifFalse:
  									[cacheTag >= (objectMemory literalCountOf: enumeratingCogMethod methodObject) ifTrue:
  										[^8]]]
  						ifFalse:
  							[(self asserta: (objectRepresentation validInlineCacheTag: cacheTag)) ifFalse:
  								[^9]]]].
  		entryPoint > methodZoneBase ifTrue:
  			["It's a linked send; find which kind."
  			 self targetMethodAndSendTableFor: entryPoint annotation: annotation into:
  					[:targetMethod :sendTable|
  					 (self asserta: (targetMethod cmType = CMMethod
  								   or: [targetMethod cmType = CMClosedPIC
  								   or: [targetMethod cmType = CMOpenPIC]])) ifFalse:
  						[^10]]]].
  	^0 "keep scanning"!

Item was changed:
  ----- Method: Cogit>>handleCallOrJumpSimulationTrap: (in category 'simulation only') -----
  handleCallOrJumpSimulationTrap: aProcessorSimulationTrap
  	<doNotGenerate>
+ 	| evaluable function memory result savedFramePointer savedStackPointer savedArgumentCount retpc invalidStackPointersExpected index |
- 	| 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: [(index := #(nil true false continueNoReturn) indexOf: result) > 0
+ 				and: [result := #(0 1 0 16rF00BA4) at: index. true]]]]).
- 			or: [#(nil true false continueNoReturn) includes: result]]]).
  	processor cResultRegister: (result
  								ifNil: [0]
  								ifNotNil: [result isInteger
  											ifTrue: [result]
  											ifFalse: [16rF00BA222]])!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveCalloutToFFI (in category 'plugin primitives') -----
  primitiveCalloutToFFI
  	"Perform a function call to a foreign function.
  	Only invoked from method containing explicit external call spec.
  	Due to this we use the pluggable prim mechanism explicitly here
  	(the first literal of any FFI spec'ed method is an ExternalFunction
  	and not an array as used in the pluggable primitive mechanism)."
  
  	<accessorDepth: 2> "Manually copied from primitiveCalloutAccessorDepth in the ThreadedFFIPlugins..."
  	<var: #primitiveCallout declareC: 'void (*primitiveCallout)(void)'>
  	self functionForPrimitiveCallout
  		ifNil: [self primitiveFail]
+ 		ifNotNil: [:primitiveCallout| self dispatchFunctionPointer: primitiveCallout]!
- 		ifNotNil: [:primitiveCallout| self perform: primitiveCallout]!

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."
  	 
  	<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
  		  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:
  			(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.
  		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].
+ 	"Finally remember to reload ReceiverResultReg if required.  Even if
+ 	 arguments have been pushed, the prolog sequence assumes it is live."
+ 	(self register: ReceiverResultReg isInMask: ABICallerSavedRegisterMask) ifTrue:
+ 		[self MoveMw: (backEnd hasLinkRegister ifTrue: [methodOrBlockNumArgs] ifFalse: [methodOrBlockNumArgs + 1]) * objectMemory wordSize
+ 			r: SPReg
+ 			R: ReceiverResultReg].
  	^0!

Item was added:
+ ----- Method: ThreadedFFIPluginPartialSimulator class>>shouldBeTranslated (in category 'translation') -----
+ shouldBeTranslated
+ 	^false!



More information about the Vm-dev mailing list