[squeak-dev] The Inbox: Kernel-jar.1437.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Dec 22 17:36:24 UTC 2021


A new version of Kernel was added to project The Inbox:
http://source.squeak.org/inbox/Kernel-jar.1437.mcz

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

Name: Kernel-jar.1437
Author: jar
Time: 22 December 2021, 6:36:20.744925 pm
UUID: 0f4d0c71-d03e-a840-ba8f-c404aa5c999d
Ancestors: Kernel-ct.1436

update #teminate fix with the fixes of two more bugs - see summary in 
http://lists.squeakfoundation.org/pipermail/squeak-dev/2021-December/217765.html

also update comments to refer to #terminateAggressively and #destroy

Please remove previous version from the Inbox, i.e. Kernel-jar.1436, Kernel-jar.1435 and Kernel-jar.1426

=============== Diff against Kernel-ct.1436 ===============

Item was added:
+ ----- Method: Context>>releaseCriticalSection: (in category 'private') -----
+ releaseCriticalSection: runnable
+ 	"Figure out if we are terminating a process that is in the ensure: block of a critical section.
+ 	 In this case, if the block has made progress, pop the suspendedContext so that we leave the
+ 	 ensure: block inside the critical: without signaling the semaphore/exiting the primitive section,
+ 	 since presumably this has already happened.  But if it hasn't made progress but is beyond the
+ 	 wait (which we can tell by the oldList being one of the runnable lists, i.e. a LinkedList, not a
+ 	 Semaphore or Mutex, et al), then the ensure: block needs to be run."
+ 	| selectorJustSent suspendedContext |
+ 	suspendedContext := self.
+ 	(suspendedContext method pragmaAt: #criticalSection) ifNil: [^self].
+ 	selectorJustSent := suspendedContext selectorJustSentOrSelf.
+ 
+ 	"Receiver and/or argument blocks of ensure: in Semaphore>>critical: or Mutex>>#critical:"
+ 	suspendedContext isClosureContext ifTrue:
+ 		[suspendedContext sender isUnwindContext ifTrue:
+ 			[| notWaitingButMadeNoProgress progressedIntoEnsureArgument |
+ 			"Avoid running the ensure: block twice, popping it if it has already been run. If runnable
+ 			 but at the wait, leave it in place. N.B. No need to check if the block receiver of ensure: has
+ 			 not started to run (via suspendedContext pc = suspendedContext startpc) because ensure:
+ 			 uses valueNoContextSwitch, and so there is no suspension point before the wait."
+ 			 notWaitingButMadeNoProgress :=
+ 				runnable
+ 				and: [selectorJustSent == #wait
+ 				and: [suspendedContext sender selectorJustSentOrSelf == #valueNoContextSwitch]].
+ 			 progressedIntoEnsureArgument :=
+ 				runnable
+ 				and: [suspendedContext sender selectorJustSentOrSelf == #value].
+ 			 (notWaitingButMadeNoProgress or: [progressedIntoEnsureArgument]) ifFalse:
+ 				[suspendedContext := suspendedContext home]].
+ 		 ^suspendedContext].
+ 
+ 	"Either Semaphore>>critical: or Mutex>>#critical:.  Is the process still blocked?  If so, nothing further to do."
+ 	runnable ifFalse: [^self].
+ 
+ 	"If still at the wait the ensure: block has not been activated, so signal to restore."
+ 	selectorJustSent == #wait ifTrue:
+ 		[suspendedContext receiver signal].
+ 
+ 	"If still at the lock primitive and the lock primitive just acquired ownership (indicated by it answering false)
+ 	 then the ensure block has not been activated, so explicitly primitiveExitCriticalSection to unlock."
+ 	(selectorJustSent == #primitiveEnterCriticalSection
+ 	 or: [selectorJustSent == #primitiveTestAndSetOwnershipOfCriticalSection]) ifTrue:
+ 		[(suspendedContext stackPtr > 0
+ 		  and: [suspendedContext top == false]) ifTrue:
+ 			[suspendedContext receiver primitiveExitCriticalSection]]
+ !

Item was added:
+ ----- Method: Context>>runUnwindTo:onBehalfOf: (in category 'private') -----
+ runUnwindTo: aContext onBehalfOf: aProcess
+ 	"Run self on behalf of aProcess on aProcess's (i.e. self's) stack until aContext returns. Avoid a context that cannot return. Note: self must be a stack top context. Note: to avoid infinite recursion of MNU error: e.g. a wrapper around the message sentTo: receiver in #doesNotUnderstand: must be implemented.
+ 	This method is meant to be used exclusively by Process>>#terminate."
+ 
+ 	Processor activeProcess
+ 		evaluate: [ 
+ 			| here unwindBottom newTop |
+ 			here := thisContext.
+ 			"Avoid a context that cannot return (see Note 1 below)"
+ 			unwindBottom := (self findContextSuchThat: [:ctx | ctx selector = #cannotReturn:]) ifNil: [aContext].
+ 			newTop := aContext sender.
+ 			"Insert ensure context under unwindBottom in self's stack (see Note 2 below)"
+ 			unwindBottom insertSender: (Context contextEnsure: [here jump]).
+ 			self jump.  "Control jumps to self (see Note 2 below)"
+ 			"Control resumes here once the above inserted ensure block is executed"
+ 			^newTop ]  "Return the new top context (see Note 3 below)"
+ 		onBehalfOf: aProcess
+ 
+ 	"Note 1: returning from #cannotReturn's sender would crash the VM so we install a guard ensure context right above it and after returning to #terminate the unwind will continue safely. Try running and debugging this example (avoid Proceeding the BCR error though; it would indeed crash the image):
+ 	[[[] ensure: [^2]] ensure: [^42]] fork"
+ 	"Note 2: self is run by jumping directly to it (the active process abandons thisContext and executes self on aProcess's stack; self is its top context). However, before jumping to self we insert an ensure block under unwindBottom context that jumps back to thisContext when evaluated. The inserted guard ensure context is removed once control jumps back to thisContext."
+ 	"Note 3: it doesn't matter newTop is not a proper stack top context because #terminate will use it only as a starting point in the search for the next unwind context and the computation will never return here. Cf. the pattern in #runUntilErrorOrReturnFrom:: removing the inserted ensure context by stepping until popped when executing non-local returns is not applicable here and would fail tests testTerminateInNestedEnsureWithReturn1 through 4."
+ 
+ !

Item was changed:
  ----- Method: Process>>terminate (in category 'changing process state') -----
  terminate 
+ 	"Stop the process that the receiver represents forever.
+ 	 Unwind to execute pending ensure:/ifCurtailed: blocks before terminating;
+ 	 allow all unwind blocks to run; if they are currently in progress, let them finish.
+ 	 If the process is in the middle of a #critical: critical section, release it properly.
+ 	 This is the behavior we expect when terminating a healthy process.
+ 	 See further comments in #terminateAggressively and #destroy methods dealing 
+ 	 with process termination when closing a debugger or after a catastrophic failure."
- 	"Stop the receiver forever.
- 	Run all unwind contexts (#ensure:/#ifCurtailed: blocks) on the stack, even if they are currently in progress. If already active unwind contexts should not be continued, send #terminateAggressively instead.
- 	Note that ill unwind contexts are theoretically able to stall the termination (for instance, by placing a non-local return in an unwind block); however, this is a disrecommended practice.
- 	If the process is in the middle of a critical section, release it properly."
  
+ 	| oldList top newTop ctxt outerMost unwindBlock |
+ 	"If terminating the active process, suspend it first and terminate it as a suspended process."
- 	| ctxt unwindBlock oldList outerMost |
  	self isActiveProcess ifTrue: [
- 		"If terminating the active process, suspend it first and terminate it as a suspended process."
  		[self terminate] fork.
  		^self suspend].
  
+ 	[] ensure: ["Execute termination as an ensure block to ensure it completes even if terminated
+ 		before the termination is finished; see testTerminateInTerminate."
- 	"Always suspend the process first so it doesn't accidentally get woken up.
- 	 N.B. If oldList is a LinkedList then the process is runnable. If it is a Semaphore/Mutex et al
- 	 then the process is blocked, and if it is nil then the process is already suspended."
- 	oldList := self suspend.
- 	suspendedContext ifNotNil:
- 		["Release any method marked with the <criticalSection> pragma.
- 		  The argument is whether the process is runnable."
- 		 self releaseCriticalSection: (oldList isNil or: [oldList class == LinkedList]).
  
+ 		"Always suspend the process first so it doesn't accidentally get woken up.
+ 		N.B. If oldList is a LinkedList then the process is runnable. If it is a Semaphore/Mutex et al
+ 		then the process is blocked, and if it is nil then the process is already suspended."
+ 		oldList := self suspend.
+ 		"Disable terminating process while running its stack in active process below so it doesn't 
+ 		accidentally get resumed or terminated again; 	see Process>>#resume and tests
+ 		testResumeTerminatingProcess and testTerminateTerminatingProcess"
+ 		top := suspendedContext ifNil: [^self error: 'Process already terminated or terminating'].
+ 		suspendedContext := nil. 
+ 		"Release any method marked with the <criticalSection> pragma and answer the new top context. 
+ 		The argument is whether the process was runnable (or suspended); for detailed description see 
+ 		http://forum.world.st/Solving-termination-of-critical-sections-in-the-context-of-priority-inversion-was-SemaphoreTest-fail-td5082184.html."
+ 		ctxt := top := top releaseCriticalSection: (oldList isNil or: [oldList class == LinkedList]).
+ 
  		"If terminating a process halfways through an unwind, try to complete that unwind block first;
+ 		if there are multiple such nested unwind blocks, try to complete the outer-most one; nested unwind 
+ 		blocks will be completed in the process; see tests in UnwindTest, and testTerminationDuringUnwind. 
+ 		Note: Halfway-through blocks have already set the complete variable (tempAt: 2) in their defining
+ 		#ensure:/#ifCurtailed contexts from nil to true; we'll search for the bottom-most one.
+ 		Note: #findNextUnwindContextUpTo: starts searching from the receiver's sender but the receiver 
+ 		itself may be an unwind context; see testTerminateEnsureAsStackTop."
+ 		ctxt isUnwindContext ifFalse: [ctxt := ctxt findNextUnwindContextUpTo: nil].
+ 		[ctxt isNil] whileFalse: [
+ 			(ctxt tempAt:2) ifNotNil: [
+ 				outerMost := ctxt].
+ 			ctxt := ctxt findNextUnwindContextUpTo: nil].
+ 		outerMost ifNotNil: [newTop := top runUnwindTo: outerMost onBehalfOf: self].
- 		if there are multiple such nested unwind blocks, try to complete the outer-most one; the inner
- 		blocks will be completed in the process."
- 		ctxt := suspendedContext.
- 		[(ctxt := ctxt findNextUnwindContextUpTo: nil) isNil] whileFalse: 
- 			"Contexts under evaluation have already set their complete (tempAt: 2) to true."
- 			[(ctxt tempAt:2) ifNotNil: [outerMost := ctxt]].
- 		outerMost ifNotNil: [
- 			"This is the outer-most unwind context currently under evaluation;
- 			let's find an inner context executing outerMost's argument block (tempAt: 1)"
- 			(suspendedContext findContextSuchThat: [:ctx | 
- 				ctx closure == (outerMost tempAt: 1)]) ifNotNil: [:inner | 
- 					"Let's finish the unfinished unwind context only (i.e. up to inner) and return here"
- 					suspendedContext runUntilErrorOrReturnFrom: inner. 
- 					"Update the receiver's suspendedContext (the previous step reset its sender to nil);
- 					return, if the execution stack reached its bottom (e.g. in case of non-local returns)."
- 					(suspendedContext := outerMost sender) ifNil: [^self]]]. 
  
+ 		"By now no halfway-through unwind blocks are on the stack. Create a new top context for each 
+ 		pending unwind block (tempAt: 1) and execute it on the unwind block's stack on behalf of self, i.e.
+ 		the process being terminated, to preserve process identity; see testProcessFaithfulTermination.
+ 		Cf. the unwind pattern in #resume:through: : using #value instead of #runUnwindTo:onBehalfOf: 
+ 		would lead to an incorrect evaluation of non-local returns on the wrong stack (active process's).
+ 		Note: newTop sender points to the former outerMost sender, i.e. the next unexplored context."
+ 		ctxt := newTop ifNil: [top] ifNotNil: [newTop sender].
- 		"Now all unwind blocks caught halfway through have been completed; 
- 		let's execute the ones still pending. Note: #findNextUnwindContextUpTo: starts
- 		searching from the receiver's sender but the receiver itself may be an unwind context."
- 		ctxt := suspendedContext.
  		ctxt isUnwindContext ifFalse: [ctxt := ctxt findNextUnwindContextUpTo: nil].
  		[ctxt isNil] whileFalse: [
  			(ctxt tempAt: 2) ifNil: [
  				ctxt tempAt: 2 put: true.
  				unwindBlock := ctxt tempAt: 1.
+ 				newTop := unwindBlock asContextWithSender: ctxt.
+ 				newTop runUnwindTo: newTop onBehalfOf: self].
+ 			ctxt := ctxt findNextUnwindContextUpTo: nil]
+ 	]
+ !
- 				"Create a context for the unwind block and execute it on the unwind block's stack. 
- 				Note: using #value instead of #runUntilErrorOrReturnFrom: would lead to executing 
- 				the unwind on the wrong stack preventing the correct execution of non-local returns."
- 				suspendedContext := unwindBlock asContextWithSender: ctxt.
- 				suspendedContext runUntilErrorOrReturnFrom: suspendedContext].
- 			ctxt := ctxt findNextUnwindContextUpTo: nil].
- 
- 		"Reset the context's pc and sender to nil for the benefit of isTerminated."
- 		suspendedContext terminate]!



More information about the Squeak-dev mailing list