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

commits at source.squeak.org commits at source.squeak.org
Sun Nov 29 06:54:36 UTC 2020


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

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

Name: VMMaker.oscog-eem.2901
Author: eem
Time: 28 November 2020, 10:54:27.351264 pm
UUID: 62f5de98-d59e-4cdc-b4a5-1c0c2d987c71
Ancestors: VMMaker.oscog-eem.2900

MTVM: Eliminate some compiler warnings.  Fix a slip in the assert in cogMethodContainng:
In simulation get register state correct on proceeding from ioWaitOnOSSemaphore:

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

Item was changed:
  ----- Method: CoInterpreter>>markActiveMethodsAndReferents (in category 'cog jit support') -----
  markActiveMethodsAndReferents
  	<api>
  	"If instructionPointer is referring to machine code, as it will be if a primitive is in progress
  	 (see isCodeCompactingPrimitiveIndex:) it may refer to a method, and if so that method
  	 must be retained."
  	 instructionPointer ~= 0 ifTrue:
  		[(cogit cogMethodContaining: instructionPointer) ifNotNil:
  			[:primCogMethod|
+ 			 cogit markMethodAndReferents: (self cCoerceSimple: primCogMethod to: #'CogBlockMethod *')]].
- 			 cogit markMethodAndReferents: primCogMethod]].
  
  	0 to: numStackPages - 1 do:
  		[:i| | thePage |
  		thePage := stackPages stackPageAt: i.
  		(stackPages isFree: thePage) ifFalse:
  			[self markCogMethodsAndReferentsOnPage: thePage]]!

Item was changed:
  ----- Method: CoInterpreterMT>>primitiveRelinquishProcessor (in category 'I/O primitives') -----
  primitiveRelinquishProcessor
  	"Relinquish the processor for up to the given number of microseconds.
  	 The exact behavior of this primitive is platform dependent.
  	 Override to check for waiting threads."
  
  	| microSecs threadIndexAndFlags currentCStackPointer currentCFramePointer |
+ 	<var: #currentCStackPointer type: #'volatile usqIntptr_t'>
+ 	<var: #currentCFramePointer type: #'volatile usqIntptr_t'>
- 	<var: #currentCStackPointer type: #'void *'>
- 	<var: #currentCFramePointer type: #'void *'>
  	microSecs := self stackTop.
  	(objectMemory isIntegerObject: microSecs) ifFalse:
  		[^self primitiveFail].
  	self assert: (objectMemory fetchPointer: MyListIndex ofObject: self activeProcess) = objectMemory nilObject.
  	self assert: relinquishing not.
  	"DO NOT allow relinquishing the processor while we are profiling since this
  	 may skew the time base for our measures (it may reduce processor speed etc).
  	 Instead we go full speed, therefore measuring the precise time we spend in the
  	 inner idle loop as a busy loop."
  	nextProfileTick = 0 ifTrue:
  		"Presumably we have nothing to do; this primitive is typically called from the
  		 background process. So we should /not/ try and activate any threads in the
  		 pool; they will waste cycles finding there is no runnable process, and will
  		 cause a VM abort if no runnable process is found.  But we /do/ want to allow
  		 FFI calls that have completed, or callbacks a chance to get into the VM; they
  		 do have something to do.  DisownVMForProcessorRelinquish indicates this."
  		[currentCStackPointer := CStackPointer.
  		 currentCFramePointer := CFramePointer.
  		 threadIndexAndFlags := self disownVM: DisownVMForProcessorRelinquish.
  		 self assert: relinquishing.
  		 self ioRelinquishProcessorForMicroseconds: (objectMemory integerValueOf: microSecs).
  		 self assert: relinquishing.
  		 self ownVM: threadIndexAndFlags.
  		 self assert: relinquishing not.
  		 self assert: cogThreadManager currentVMThread state = CTMAssignableOrInVM.
  		 self assert: currentCStackPointer = CStackPointer.
  		 self assert: currentCFramePointer = CFramePointer.
  		 "In simulation we allow ioRelinquishProcessorForMicroseconds: to fail so that
+ 		  we can arrange that the simulator responds to input events promptly.  This
- 		  we can arrange that the simulator responds to input events promply.  This
  		  *DOES NOT HAPPEN* in the real vm."
  		 self cCode: [] inSmalltalk: [primFailCode ~= 0 ifTrue: [^self]]].
  	self assert: (objectMemory fetchPointer: MyListIndex ofObject: self activeProcess) = objectMemory nilObject.
  	self pop: 1  "microSecs; leave rcvr on stack"!

Item was changed:
  ----- Method: CogMethodZone>>cogMethodContaining: (in category 'jit - api') -----
  cogMethodContaining: mcpc
  	"Answer the method containing mcpc for the purposes of code zone compaction,
  	 where mcpc is actually the value of instructionPointer at the time of a compaction."
  	<var: 'mcpc' type: #usqInt>
  	<api>
  	| cogMethod prevMethod |
  	mcpc > limitAddress ifTrue:
  		[^nil].
  	mcpc < baseAddress ifTrue:
  		[cogit assertMcpcIsPrimReturn: mcpc.
  		 ^nil].
  	self assert: mcpc < self limitZony.
  	cogMethod := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'.
+ 	[cogMethod asUnsignedInteger < mcpc] whileTrue:
- 	[cogMethod < mcpc] whileTrue:
  		[prevMethod := cogMethod.
  		 cogMethod := self methodAfter: cogMethod].
  
  	"Since mcpc is actually instructionPointer we expect that it is either at the stack check
  	 (normal code zone reclamation invoked through checkForEventsMayContextSwitch:)
  	 or is in a primitive, immediately following the call of the C primitive routine."
  	self assert: (prevMethod notNil
+ 				and: [mcpc = (prevMethod asUnsignedInteger + prevMethod stackCheckOffset)
- 				and: [mcpc = prevMethod asUnsignedInteger + prevMethod stackCheckOffset
  					or: [(coInterpreter
  							primitiveIndexOfMethod: prevMethod methodObject
  							header: prevMethod methodHeader) > 0
  						and: [cogit backEnd isCallPrecedingReturnPC: mcpc]]]).
  	 ^prevMethod!

Item was changed:
  ----- Method: CogThreadManager>>ioWaitOnOSSemaphore: (in category 'simulation') -----
  ioWaitOnOSSemaphore: aSemaphorePtr
  	<var: #anOSSemaphore type: #'sqOSSemaphore *'>
  	<returnTypeC: #void>
  	<doNotGenerate>
  	"See platforms/Cross/vm/sq.h for the real definition."
  	"Simulate the VM's heartbeat by calling checkVMOwnershipFromHeartbeat
  	 if the wait times-out."
  	[aSemaphorePtr value waitTimeoutMSecs: 1000] whileTrue:
+ 		[coInterpreter checkVMOwnershipFromHeartbeat].
+ 	self deny: vmOwner = 0.
+ 	cogit processor setRegisterState: (registerStates at: vmOwner
+ 										ifAbsentPut:
+ 											[self ensureInitializedProcessor: cogit processor forThreadIndex: vmOwner.
+ 											 cogit processor registerState])!
- 		[coInterpreter checkVMOwnershipFromHeartbeat]!

Item was changed:
  ----- Method: CogVMThread class>>instVarNamesAndTypesForTranslationDo: (in category 'translation') -----
  instVarNamesAndTypesForTranslationDo: aBinaryBlock
  	"enumerate aBinaryBlock with the names and C type strings for the inst vars to include in a CogVMThread struct."
  
  	self allInstVarNames do:
  		[:ivn|
  		aBinaryBlock
  			value: ivn
  			value: (ivn caseOf: {
  						['awolProcesses']			-> [{#sqInt. '[', CogThreadManager awolProcessesIncrement printString, ']'}].
+ 						['cStackPointer']			-> [#usqIntptr_t].
+ 						['cFramePointer']			-> [#usqIntptr_t].
+ 						['primitiveFunctionPointer']	-> [#('static void (*' ')()')].
- 						['cStackPointer']			-> [#'void *'].
- 						['cFramePointer']		-> [#'void *'].
  						['osSemaphore']			-> ['sqOSSemaphore'].
+ 						['osThread']					-> ['sqOSThread'].
+ 						['reenterInterpreter']		-> ['jmp_buf'] }
- 						['osThread']				-> ['sqOSThread'].
- 						['reenterInterpreter']	-> ['jmp_buf'] }
  					otherwise:
  						[#sqInt])]!

Item was changed:
  ----- Method: StackInterpreter>>printCallStackOf: (in category 'debug printing') -----
  printCallStackOf: aContextOrProcessOrFrame
  	<api>
  	| context |
  	<inline: false>
  	(stackPages couldBeFramePointer: aContextOrProcessOrFrame) ifTrue:
  		[^self printCallStackFP: (self cCoerceSimple: aContextOrProcessOrFrame to: #'char *')].
  	aContextOrProcessOrFrame = self activeProcess ifTrue:
+ 		[^self printCallStackOf: (self cCode: [framePointer asInteger] inSmalltalk: [self headFramePointer])].
- 		[^self printCallStackOf: (self cCode: [framePointer] inSmalltalk: [self headFramePointer])].
  	(self couldBeProcess: aContextOrProcessOrFrame) ifTrue:
  		[^self printCallStackOf: (objectMemory
  									fetchPointer: SuspendedContextIndex
  									ofObject: aContextOrProcessOrFrame)].
  	context := aContextOrProcessOrFrame.
  	[context = objectMemory nilObject] whileFalse:
  		[(self isMarriedOrWidowedContext: context)
  			ifTrue:
  				[(self checkIsStillMarriedContext: context currentFP: framePointer) ifFalse:
  					[self shortPrintContext: context.
  					 ^nil].
  				 context := self shortReversePrintFrameAndCallers: (self frameOfMarriedContext: context)]
  			ifFalse:
  				[context := self printContextCallStackOf: context]]!



More information about the Vm-dev mailing list