Eliot Miranda uploaded a new version of VMMaker to project VM Maker: http://source.squeak.org/VMMaker/VMMaker.oscog-eem.2865.mcz ==================== Summary ==================== Name: VMMaker.oscog-eem.2865 Author: eem Time: 30 October 2020, 7:58:58.320942 am UUID: f9e6957e-d20a-47ba-b579-29e37af6cef3 Ancestors: VMMaker.oscog-eem.2864 Get the CoInterpreterMT to simulate. Refactor _setjmp:/_longjmp:_: for the added use for reentering the thread scheduling loop. =============== Diff against VMMaker.oscog-eem.2864 =============== Item was changed: ----- Method: CoInterpreter>>_longjmp:_: (in category 'cog jit support') ----- _longjmp: aJumpBuf _: returnValue "Hack simulation of _setjmp/_longjmp, intended to invoke the most minimal setjmp/longjmp pair available on the platform; no saving/restoring signal masks, no stack unwinding, etc. Signal the exception that simulates a longjmp back to the interpreter." <doNotGenerate> + self halt: 'This should not be encountered now we use ceInvokeInterpreter!!!!'! - self halt: 'This should not be encountered now we use ceInvokeInterpreter!!!!'. - (aJumpBuf == reenterInterpreter - and: [returnValue ~= 2 "2 == returnToThreadSchedulingLoopVia:"]) ifTrue: - [self assert: (self isOnRumpCStack: cogit processor sp). - self assertValidExecutionPointe: instructionPointer r: framePointer s: stackPointer imbar: true line: nil]. - aJumpBuf returnValue: returnValue; signal! Item was changed: CoInterpreterPrimitives subclass: #CoInterpreterMT + instanceVariableNames: 'cogThreadManager checkThreadActivation maxWaitingPriority foreignCallbackPriority deferThreadSwitch disowningVMThread disownCount foreignCallbackProcessSlot willNotThreadWarnCount activeProcessAffined relinquishing processHasThreadId noThreadingOfGUIThread reenterThreadSchedulingLoop' - instanceVariableNames: 'cogThreadManager checkThreadActivation maxWaitingPriority foreignCallbackPriority deferThreadSwitch disowningVMThread disownCount foreignCallbackProcessSlot willNotThreadWarnCount activeProcessAffined relinquishing processHasThreadId noThreadingOfGUIThread' classVariableNames: 'DisownFlagsShift DisownVMForProcessorRelinquish LockGUIThreadFlag LockGUIThreadShift OwnVMForeignThreadFlag ProcessUnaffinedOnDisown ReturnToThreadSchedulingLoop VMAlreadyOwnedHenceDoNotDisown' poolDictionaries: 'VMThreadingConstants' category: 'VMMaker-Multithreading'! Item was added: + ----- Method: CoInterpreterMT>>_longjmp:_: (in category 'cog jit support') ----- + _longjmp: aJumpBuf _: returnValue + "Hack simulation of _setjmp/_longjmp, intended to invoke the most minimal setjmp/longjmp + pair available on the platform; no saving/restoring signal masks, no stack unwinding, etc. + Signal the exception that simulates a longjmp back to the interpreter." + <doNotGenerate> + self assert: aJumpBuf == reenterThreadSchedulingLoop. + aJumpBuf returnValue: returnValue; signal! Item was changed: ----- Method: CoInterpreterMT>>initializeInterpreter: (in category 'initialization') ----- initializeInterpreter: bytesToShift super initializeInterpreter: bytesToShift. foreignCallbackProcessSlot := (objectMemory lengthOf: objectMemory specialObjectsOop) > ForeignCallbackProcess ifTrue: [ForeignCallbackProcess] + ifFalse: [NilObject]. + self cCode: '' inSmalltalk: + [reenterThreadSchedulingLoop := ReenterThreadSchedulingLoop new]. + ! - ifFalse: [NilObject]! Item was added: + ----- 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]! Item was changed: ----- Method: CoInterpreterMT>>mapInterpreterOops (in category 'object memory support') ----- mapInterpreterOops "Map all oops in the interpreter's state to their new values during garbage collection or a become: operation." "Assume: All traced variables contain valid oops." <var: #vmThread type: #'CogVMThread *'> super mapInterpreterOops. "Per-thread state; trace each thread's own newMethod and stack of awol processes." 1 to: cogThreadManager getNumThreads do: [:i| | vmThread | vmThread := cogThreadManager vmThreadAt: i. vmThread state ifNotNil: [(vmThread newMethodOrNull notNil and: [objectMemory shouldRemapOop: vmThread newMethodOrNull]) ifTrue: [vmThread newMethodOrNull: (objectMemory remapObj: vmThread newMethodOrNull)]. 0 to: vmThread awolProcIndex - 1 do: [:j| (objectMemory shouldRemapOop: (vmThread awolProcesses at: j)) ifTrue: + [vmThread awolProcesses at: j put: (objectMemory remapObj: (vmThread awolProcesses at: j))]]]]! - [vmThread awolProcesses at: j put: (objectMemory remap: (vmThread awolProcesses at: j))]]]]! Item was changed: ----- Method: CoInterpreterMT>>returnToSchedulingLoopAndReleaseVMOrWakeThread:source: (in category 'process primitive support') ----- returnToSchedulingLoopAndReleaseVMOrWakeThread: vmThread source: source <var: #vmThread type: #'CogVMThread *'> <inline: false> self cCode: [self flag: 'this is just for debugging. Note the current C stack pointers'. cogThreadManager currentVMThread cStackPointer: CStackPointer; cFramePointer: CFramePointer] inSmalltalk: [| range | range := self cStackRangeForThreadIndex: cogThreadManager getVMOwner. self assert: (range includes: CStackPointer). self assert: (range includes: CFramePointer)]. self recordThreadSwitchTo: (vmThread ifNotNil: [vmThread index] ifNil: [0]) source: source. vmThread ifNotNil: [cogThreadManager wakeVMThreadFor: vmThread index] ifNil: [cogThreadManager releaseVM]. + "I am not frightened of flying. + Any value will do. I don't mind. + Why should I be frightened of flying? + There's no reason for it." + self _longjmp: reenterThreadSchedulingLoop _: 1 ! - "2 implies returning to the threadSchedulingLoop." - self shouldBeImplemented. - "was: self _longjmp: savedReenterInterpreter _: ReturnToThreadSchedulingLoop. - But now we have ceInvokeInterpret, not reenterInterpreter, so we have to fugure out a new way in..."! Item was changed: ----- Method: CoInterpreterMT>>threadSchedulingLoop: (in category 'vm scheduling') ----- threadSchedulingLoop: vmThread "Enter a loop attempting to run the VM with the highest priority process and blocking on the thread's OS semaphore when unable to run that process. + This version is for simulation only, simulating the longjmp back to the real + threadSchedulingLoopImplementation: through exception handling." + + <cmacro: '(vmThread) threadSchedulingLoopImplementation(vmThread)'> + self initializeProcessorStackForSimulation: vmThread. + [([self threadSchedulingLoopImplementation: vmThread] + on: ReenterThreadSchedulingLoop + do: [:ex| ex return: ex returnValue]) = ReenterThreadSchedulingLoop] whileTrue! - We will return to this via threadSwitchIfNecessary:from: which is called in the - middle of transferTo:from: once the active process has been stored in the scheduler." - <var: #vmThread type: #'CogVMThread *'> - | attemptToRun | - <inline: false> - [self assert: vmThread state = CTMAssignableOrInVM. - attemptToRun := false. - (cogThreadManager getVMOwner = vmThread index) - ifTrue: [attemptToRun := true] - ifFalse: - [(cogit tryLockVMToIndex: vmThread index) ifTrue: - ["If relinquishing is true, then primitiveRelinquishProcessor has disowned the - VM and only a returning call or callback should take ownership in that case." - relinquishing - ifTrue: [cogThreadManager releaseVM] - ifFalse: [attemptToRun := true]]]. - attemptToRun ifTrue: - [self tryToExecuteSmalltalk: vmThread]. - (cogThreadManager testVMOwnerIs: vmThread index) ifFalse: - [cogThreadManager waitForWork: vmThread]. - true] whileTrue! Item was added: + ----- Method: CoInterpreterMT>>threadSchedulingLoopImplementation: (in category 'vm scheduling') ----- + threadSchedulingLoopImplementation: vmThread + "Enter a loop attempting to run the VM with the highest priority process and + blocking on the thread's OS semaphore when unable to run that process. + We will return to this via threadSwitchIfNecessary:from: which is called in the + middle of transferTo:from: once the active process has been stored in the scheduler." + <var: #vmThread type: #'CogVMThread *'> + | attemptToRun | + <inline: false> + self _setjmp: reenterThreadSchedulingLoop. + [self assert: vmThread state = CTMAssignableOrInVM. + attemptToRun := false. + (cogThreadManager getVMOwner = vmThread index) + ifTrue: [attemptToRun := true] + ifFalse: + [(cogit tryLockVMToIndex: vmThread index) ifTrue: + ["If relinquishing is true, then primitiveRelinquishProcessor has disowned the + VM and only a returning call or callback should take ownership in that case." + relinquishing + ifTrue: [cogThreadManager releaseVM] + ifFalse: [attemptToRun := true]]]. + attemptToRun ifTrue: + [self tryToExecuteSmalltalk: vmThread]. + (cogThreadManager testVMOwnerIs: vmThread index) ifFalse: + [cogThreadManager waitForWork: vmThread]. + true] whileTrue! Item was added: + ----- Method: CogVMSimulator>>_longjmp:_: (in category 'multi-threading simulation switch') ----- + _longjmp: aJumpBuf _: returnValue + "This method includes or excludes CoInterpreterMT methods as required. + Auto-generated by CogVMSimulator>>ensureMultiThreadingOverridesAreUpToDate" + + ^self perform: #'_longjmp:_:' + withArguments: {aJumpBuf. returnValue} + inSuperclass: (cogThreadManager ifNil: [CoInterpreterPrimitives] ifNotNil: [CoInterpreterMT])! Item was added: + Notification subclass: #ReenterThreadSchedulingLoop + instanceVariableNames: 'returnValue' + classVariableNames: '' + poolDictionaries: '' + category: 'VMMaker-JITSimulation'! Item was changed: ----- Method: StackInterpreter>>_setjmp: (in category 'primitive support') ----- _setjmp: aJumpBuf "Hack simulation of _setjmp/_longjmp, intended to invoke the most minimal setjmp/longjmp + pair available on the platform; no saving/restoring signal masks, no stack unwinding, etc." - pair available on the platform; no saving/restoring signal masks, no stack unwinding, etc. - Assign to reenterInterpreter the exception that when raised simulates a _longjmp back to the interpreter." <doNotGenerate> + self assert: (#(ReenterInterpreter ReenterThreadSchedulingLoop) includes: aJumpBuf class name). - reenterInterpreter := ReenterInterpreter new returnValue: 0; yourself. ^0! Item was changed: ----- Method: StackInterpreter>>initializeInterpreter: (in category 'initialization') ----- initializeInterpreter: bytesToShift "Initialize Interpreter state before starting execution of a new image." interpreterProxy := self sqGetInterpreterProxy. self dummyReferToProxy. objectMemory initializeObjectMemory: bytesToShift. self checkAssumedCompactClasses. self initializeExtraClassInstVarIndices. method := newMethod := objectMemory nilObject. self cCode: '' inSmalltalk: [breakSelectorLength ifNil: [breakSelectorLength := objectMemory minSmallInteger]. + breakLookupClassTag ifNil: [breakLookupClassTag := -1]. + reenterInterpreter := ReenterInterpreter new]. - breakLookupClassTag ifNil: [breakLookupClassTag := -1]]. methodDictLinearSearchLimit := 8. self initialCleanup. LowcodeVM ifTrue: [ self setupNativeStack ]. profileSemaphore := profileProcess := profileMethod := objectMemory nilObject. interruptKeycode := 2094. "cmd-. as used for Mac but no other OS" [globalSessionID = 0] whileTrue: [globalSessionID := self cCode: [(self time: #NULL) + self ioMSecs] inSmalltalk: [(Random new next * (SmallInteger maxVal min: 16rFFFFFFFF)) asInteger]]. metaAccessorDepth := -2. super initializeInterpreter: bytesToShift! |
Free forum by Nabble | Edit this page |