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

commits at source.squeak.org commits at source.squeak.org
Sat Oct 31 06:01:53 UTC 2020


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

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

Name: VMMaker.oscog-eem.2868
Author: eem
Time: 30 October 2020, 11:01:42.573574 pm
UUID: ff18b9dd-739b-43c9-b4c1-a994d4da65b8
Ancestors: VMMaker.oscog-eem.2867

smashCallerSavedRegistersWithValuesFrom:by:in: is not a good idea. smashCallerSavedRegistersWithValuesFrom:by: is just fine. And we do need abiUnmarshal: for x86.
COGMTVM:
Fix a missing fix in CoInterpreterMT>>transferTo:from: from CoInterpreter's verison.
Fix a slip in windowIsClosing.
Fix the assert in preemptDisowningThread.
Set both processor's stack pointers and CoInterprteer's saved C stack poi nters when initializing a thread.  This is incorrect but gets us going.  Need to think about how and when to reset CStack/FramePointer.

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

Item was changed:
  ----- Method: CoInterpreterMT>>initializeProcessorStackForSimulation: (in category 'initialization') -----
  initializeProcessorStackForSimulation: vmThread
  	<inline: #always>
  	self cCode: [] inSmalltalk:
  		[| range |
  		 range := self cStackRangeForThreadIndex: vmThread index.
  		 cogit processor
  			setFramePointer: range last
+ 			stackPointer: range last - 32.
+ 		 self setCFramePointer: cogit processor fp setCStackPointer: cogit processor sp]!
- 			stackPointer: range last - 32]!

Item was changed:
  ----- Method: CoInterpreterMT>>preemptDisowningThread (in category 'vm scheduling') -----
  preemptDisowningThread
  	"Set the relevant state for disowningVMThread so that it can resume after
  	 being preempted and set disowningVMThread to nil to indicate preemption.
  
  	 N.B.  This should only be sent from checkPreemptionOfDisowningThread.
  
  	 There are essentially four things to do.
  	 a)	save the VM's notion of the current C stack pointers; these are pointers
  		into a thread's stack and must be saved and restored in thread switch.
  	 b)	save the VM's notion of the current Smalltalk execution point.  This is
  		simply the suspend half of a process switch that saves the current context
  		in the current process.
  	 c)	add the process to the thread's set of AWOL processes so that the scheduler
  		won't try to run the process while the thread has disowned the VM.
  	 d)	save the in-primitive VM state, newMethod and argumentCount
  
  	 ownVM: will restore the VM context as of disownVM: from the above when it
  	 finds it has been preempted."
  
  	| activeProc activeContext preemptedThread |
  	<var: #preemptedThread type: #'CogVMThread *'>
  	<inline: false>
  	self assert: disowningVMThread notNil.
  	self assert: (disowningVMThread state = CTMUnavailable
  				or: [disowningVMThread state = CTMWantingOwnership]).
  	self cCode: ''
  		inSmalltalk:
  			[| range |
  			 range := self cStackRangeForThreadIndex: disowningVMThread index.
+ 			 disowningVMThread index = cogThreadManager getVMOwner
+ 				ifTrue: [self assert: ((range includes: CStackPointer) and: [range includes: CFramePointer])]
+ 				ifFalse: [self deny: ((range includes: CStackPointer) or: [range includes: CFramePointer])]].
- 			 self assert: (range includes: CStackPointer).
- 			 self assert: (range includes: CFramePointer)].
  	cogit recordEventTrace ifTrue:
  		[self recordTrace: TracePreemptDisowningThread
  			thing: (objectMemory integerObjectOf: disowningVMThread index)
  			source: 0].
  	disowningVMThread cStackPointer: CStackPointer.
  	disowningVMThread cFramePointer: CFramePointer.
  	activeProc := self activeProcess.
  	self assert: (objectMemory fetchPointer: MyListIndex ofObject: activeProc) = objectMemory nilObject.
  	objectMemory
  		storePointer: MyListIndex
  		ofObject: activeProc
  		withValue: (objectMemory splObj: ProcessInExternalCodeTag).
  	"The instructionPointer must be pushed because the convention for inactive stack pages is that the
  	 instructionPointer is top of stack.  We need to know if this primitive is called from machine code
  	 because the invariant that the return pc of an interpreter callee calling a machine code caller is
  	 ceReturnToInterpreterPC must be maintained."
  	self push: instructionPointer.
  	self externalWriteBackHeadFramePointers.
  	activeContext := self ensureFrameIsMarried: framePointer SP: stackPointer.
  	objectMemory
  		storePointer: SuspendedContextIndex
  		ofObject: activeProc
  		withValue: activeContext.
  	"Since pushing the awol process may realloc disowningVMThread we need to reassign.
  	 But since we're going to nil disowningVMThread anyway we can assign to a local."
  	preemptedThread := cogThreadManager pushAWOLProcess: activeProc on: disowningVMThread.
  	disowningVMThread := nil.
  	preemptedThread priority: (self quickFetchInteger: PriorityIndex ofObject: activeProc).
  	(self ownerIndexOfProcess: activeProc) = 0
  		ifTrue: [self setOwnerIndexOfProcess: activeProc to: preemptedThread index bind: false]
  		ifFalse: [self assert: (self ownerIndexOfProcess: activeProc) = preemptedThread index].
  	preemptedThread
  		newMethodOrNull: newMethod;
  		argumentCount: argumentCount;
  		primitiveFunctionPointer: primitiveFunctionPointer;
  		inMachineCode: instructionPointer asUnsignedInteger <= objectMemory startOfMemory!

Item was changed:
  ----- Method: CoInterpreterMT>>transferTo:from: (in category 'process primitive support') -----
  transferTo: newProc from: sourceCode
  	"Record a process to be awoken on the next interpreter cycle.  Override to
  	 potentially switch threads either if the new process is bound to another thread,
  	 or if there is no runnable process but there is a waiting thread. Note that the
  	 abort on no runnable process has beeen moved here from wakeHighestPriority."
+ 	| sched oldProc activeContext |
- 	| sched oldProc activeContext vmThread |
  	<inline: false>
- 	<var: #vmThread type: #'CogVMThread *'>
  	statProcessSwitch := statProcessSwitch + 1.
  	self push: instructionPointer.
  	self externalWriteBackHeadFramePointers.
  	self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer.
  	"ensureMethodIsCogged: in makeBaseFrameFor: in
  	 externalSetStackPageAndPointersForSuspendedContextOfProcess:
  	 below may do a code compaction. Nil instructionPointer to avoid it getting pushed twice."
  	instructionPointer := 0.
  	sched := self schedulerPointer.
  	oldProc := objectMemory fetchPointer: ActiveProcessIndex ofObject: sched.
  	self recordContextSwitchFrom: oldProc in: sourceCode.
+ 	activeContext := self ensureFrameIsMarried: framePointer SP: stackPointer + objectMemory wordSize.
- 	activeContext := self ensureFrameIsMarried: framePointer SP: stackPointer.
  	objectMemory storePointer: SuspendedContextIndex ofObject: oldProc withValue: activeContext.
  
+ 	newProc ifNil:
- 	newProc isNil ifTrue:
  		["Two possibilities.  One, there is at least one thread waiting to own the VM in which
  		  case it should be activated.  Two, there are no processes to run and so abort."
+ 		 self willingVMThread ifNotNil:
+ 			 [:vmThread|
+ 			  vmThread state = CTMWantingOwnership ifTrue:
+ 				[self returnToSchedulingLoopAndReleaseVMOrWakeThread: vmThread source: sourceCode]].
+ 		 self error: 'scheduler could not find a runnable process'].
- 		 vmThread := self willingVMThread.
- 		 (vmThread notNil and: [vmThread state = CTMWantingOwnership]) ifTrue:
- 			[self returnToSchedulingLoopAndReleaseVMOrWakeThread: vmThread source: sourceCode].
- 		self error: 'scheduler could not find a runnable process'].
  
+ 	objectMemory
+ 		storePointer: ActiveProcessIndex ofObject: sched withValue: newProc;
+ 		storePointerUnchecked: MyListIndex ofObject: newProc withValue: objectMemory nilObject.
- 	objectMemory storePointer: ActiveProcessIndex ofObject: sched withValue: newProc.
- 	objectMemory storePointerUnchecked: MyListIndex ofObject: newProc withValue: objectMemory nilObject.
  
  	self threadSwitchIfNecessary: newProc from: sourceCode.
  
  	self externalSetStackPageAndPointersForSuspendedContextOfProcess: newProc!

Item was changed:
  ----- Method: CogIA32Compiler>>cpuid: (in category 'feature detection') -----
  cpuid: n
  	<doNotGenerate>
  	"This is simulation only invocation of the throw-away CPUID function generated to initialize cpuidWord0 and cpuidWord1"
+ 	| result |
  	cogit processor abiMarshalArg0: n in: objectMemory memory.
+ 	result := cogit simulateLeafCallOf: cogit methodZoneBase.
+ 	cogit processor abiUnmarshal: 1.
+ 	^result!
- 	^cogit simulateLeafCallOf: cogit methodZoneBase!

Item was changed:
  ----- Method: CogVMSimulator>>windowIsClosing (in category 'primitive support') -----
  windowIsClosing
  	self threadManager ifNotNil:
  		[:threadManager|
  		threadManager guiProcess ifNotNil:
  			[:guiProcess|
  			(guiProcess ~= Processor activeProcess
  			 and: [guiProcess isInteger not]) ifTrue:
  				[guiProcess
  					signalException:
+ 						(Notification new tag: #evaluateQuit; yourself).
+ 				Processor terminateActive]]].
- 						(Notification new tag: #evaluateQuit; yourself)].
- 			Processor terminateActive]].
  	quitBlock ifNotNil:
  		[:effectiveQuitBlock|
  		quitBlock := nil. "stop recursion on explicit window close."
  		[effectiveQuitBlock value]
  			on: BlockCannotReturn
  			do: [:ex|]]	"Cause return from #test, et al"!

Item was added:
+ ----- Method: CogX64Compiler class>>callerSavedRegisterSetters (in category 'accessing') -----
+ callerSavedRegisterSetters
+ 	"Answer the register setters for the caller-saved registers on the current ABI"
+ 	^SysV
+ 			ifTrue: [#(rax: rcx: rdx: rsi: rdi: r8: r9: r10: r11:)]
+ 			ifFalse: [#(rax: rcx: rdx: r8: r9: r10: r11:)]!

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:
  							[^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. ')'}.
+ 		 processor smashCallerSavedRegistersWithValuesFrom: 16r80000000 by: objectMemory wordSize.
- 		 processor smashCallerSavedRegistersWithValuesFrom: 16r80000000 by: objectMemory wordSize in: 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].
- 		 processor smashCallerSavedRegistersWithValuesFrom: 16r80000000 by: objectMemory wordSize in: memory].
  	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>>simulateCeFlushDCacheFrom:to: (in category 'simulation only') -----
  simulateCeFlushDCacheFrom: start to: finish
  	<doNotGenerate>
  	processor abiMarshalArg0: start arg1: finish in: objectMemory memory.
+ 	self simulateLeafCallOf: ceFlushDCache.
+ 	processor abiUnmarshal: 2!
- 	self simulateLeafCallOf: ceFlushDCache!

Item was changed:
  ----- Method: Cogit>>simulateCeFlushICacheFrom:to: (in category 'simulation only') -----
  simulateCeFlushICacheFrom: start to: finish
  	<doNotGenerate>
  	processor abiMarshalArg0: start arg1: finish in: objectMemory memory.
+ 	self simulateLeafCallOf: ceFlushICache.
+ 	processor abiUnmarshal: 2!
- 	self simulateLeafCallOf: ceFlushICache!

Item was changed:
  ----- Method: Cogit>>tryLockVMOwner: (in category 'multi-threading') -----
  tryLockVMOwner: 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."
- 		"ceTryLockVMOwner does an atomic compare-and-swap of the lock
- 		 with the argument and zero, setting the lock to value if it was zero. 
- 		 It answers non-zero if the lock was zero."
  	<cmacro: '(value) ceTryLockVMOwner(value)'>
  	processor abiMarshalArg0: value in: objectMemory memory.
+ 	^[(self simulateLeafCallOf: ceTryLockVMOwner) ~= 0] ensure:
+ 		[processor abiUnmarshal: 1]!
- 	^0 ~= (self simulateLeafCallOf: ceTryLockVMOwner)!



More information about the Vm-dev mailing list