[squeak-dev] The Trunk: KernelTests-mt.424.mcz

commits at source.squeak.org commits at source.squeak.org
Tue May 31 13:24:36 UTC 2022


Marcel Taeumel uploaded a new version of KernelTests to project The Trunk:
http://source.squeak.org/trunk/KernelTests-mt.424.mcz

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

Name: KernelTests-mt.424
Author: mt
Time: 31 May 2022, 3:24:36.006029 pm
UUID: 54f976c3-1296-964f-9a2a-1890202ae545
Ancestors: KernelTests-jar.423

Moves ProcessTerminateBug from Tests to KernelTests package.

Makes re-used semaphore in (Process)UnwindTest more explicit by having an AbstractProcessTest. Downside is that those 5 ClassTestCase tests will be executed too often.

Thanks to Jaromir (jar) for the pointer!

=============== Diff against KernelTests-jar.423 ===============

Item was added:
+ ClassTestCase subclass: #AbstractProcessTest
+ 	instanceVariableNames: 'semaphore'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'KernelTests-Processes'!

Item was added:
+ ----- Method: AbstractProcessTest class>>isAbstract (in category 'testing') -----
+ isAbstract
+ 
+ 	^ self name = #AbstractProcessTest!

Item was added:
+ ----- Method: AbstractProcessTest>>genuineProcess (in category 'support') -----
+ genuineProcess
+ 	"Usually, we don't want to expose this from the class under test but we need it in the test context."
+ 
+ 	^ Processor instVarNamed: 'genuineProcess'!

Item was added:
+ ----- Method: AbstractProcessTest>>setUp (in category 'running') -----
+ setUp
+ 
+ 	super setUp.
+ 	semaphore := Semaphore new.!

Item was added:
+ ----- Method: AbstractProcessTest>>targetClass (in category 'support') -----
+ targetClass
+ 
+ 	^ self environment classNamed: #Process!

Item was added:
+ ----- Method: AbstractProcessTest>>tearDown (in category 'running') -----
+ tearDown	
+ 	"Release all processes still waiting at the semaphore or in the active priority queue."
+ 
+ 	Processor yield.
+ 	[semaphore isEmpty] whileFalse: [semaphore signal].
+ 
+ 	super tearDown.!

Item was added:
+ AbstractProcessTest subclass: #ProcessTerminateBug
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'KernelTests-Processes'!

Item was added:
+ ----- Method: ProcessTerminateBug>>testSchedulerTermination (in category 'tests') -----
+ testSchedulerTermination
+    | process sema gotHere sema2 |
+    gotHere := false.
+    sema := Semaphore new.
+    sema2 := Semaphore new.
+    process := [
+        sema signal.
+        sema2 wait.
+        "will be suspended here"
+        gotHere := true. "e.g., we must *never* get here"
+    ] forkAt: Processor activeProcess priority.
+    sema wait. "until process gets scheduled"
+    process terminate.
+    sema2 signal.
+    Processor yield. "will give process a chance to continue and
+ horribly screw up"
+    self assert: gotHere not.
+ !

Item was added:
+ ----- Method: ProcessTerminateBug>>testTerminationDuringUnwind (in category 'tests') -----
+ testTerminationDuringUnwind
+ 	"An illustration of the issue of process termination during unwind.
+ 	This uses a well-behaved unwind block that we should allow to complete
+ 	if at all possible."
+ 	| unwindStarted unwindFinished p |
+ 	unwindStarted := unwindFinished := false.
+ 	p := [[] ensure:[
+ 			unwindStarted := true.
+ 			Processor yield.
+ 			unwindFinished := true.
+ 		]] fork.
+ 	self deny: unwindStarted.
+ 	Processor yield.
+ 	self assert: unwindStarted.
+ 	self deny: unwindFinished.
+ 	p terminate.
+ 	self assert: unwindFinished.!

Item was added:
+ ----- Method: ProcessTerminateBug>>testUnwindFromActiveProcess (in category 'tests') -----
+ testUnwindFromActiveProcess
+ 	| sema process |
+ 	sema := Semaphore forMutualExclusion.
+ 	self assert:(sema isSignaled).
+ 	process := [
+ 		sema critical:[
+ 			self deny: sema isSignaled.
+ 			Processor activeProcess terminate.
+ 		]
+ 	] forkAt: Processor userInterruptPriority.
+ 	self assert: sema isSignaled.!

Item was added:
+ ----- Method: ProcessTerminateBug>>testUnwindFromForeignProcess (in category 'tests') -----
+ testUnwindFromForeignProcess
+ 	| sema process |
+ 	sema := Semaphore forMutualExclusion.
+ 	self assert: sema isSignaled.
+ 	process := [
+ 		sema critical:[
+ 			self deny: sema isSignaled.
+ 			sema wait. "deadlock"
+ 		]
+ 	] forkAt: Processor userInterruptPriority.
+ 	self deny: sema isSignaled.
+ 	"This is for illustration only - the BlockCannotReturn cannot 
+ 	be handled here (it's truncated already)"
+ 	self shouldnt: [process terminate] raise: BlockCannotReturn.
+ 	self assert: sema isSignaled.
+ 	!

Item was changed:
+ AbstractProcessTest subclass: #ProcessTest
+ 	instanceVariableNames: ''
- ClassTestCase subclass: #ProcessTest
- 	instanceVariableNames: 'semaphore'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'KernelTests-Processes'!
  
  !ProcessTest commentStamp: 'ul 8/16/2011 11:35' prior: 0!
  I hold test cases for generic Process-related behaviour.!

Item was removed:
- ----- Method: ProcessTest>>genuineProcess (in category 'support') -----
- genuineProcess
- 
- 	"Usually, we don't want to expose this from the class under test."
- 	^ Processor instVarNamed: 'genuineProcess'!

Item was removed:
- ----- Method: ProcessTest>>setUp (in category 'running') -----
- setUp
- 	semaphore := Semaphore new!

Item was removed:
- ----- Method: ProcessTest>>tearDown (in category 'running') -----
- tearDown
- 	Processor activeProcess environmentRemoveKey: #processTests ifAbsent: [].
- 	
- 	"Release all processes still waiting at the semaphore or in the active priority queue."
- 	Processor yield.
- 	[semaphore isEmpty] whileFalse: [semaphore signal]!

Item was changed:
+ ----- Method: ProcessTest>>testProcessFaithfulTermination: (in category 'support') -----
- ----- Method: ProcessTest>>testProcessFaithfulTermination: (in category 'tests') -----
  testProcessFaithfulTermination: terminator
  	"When terminating a process, unwind blocks should be evaluated as if they were executed by the process being terminated."
  
  	| process result |
  	process := [
  		[Processor activeProcess suspend]
  			ensure: [result := Processor activeProcess environmentAt: #foo]]
  		fork.
  	Processor yield.
  	process environmentAt: #foo put: 42.
  	
  	terminator value: process.
  	
  	self should: process isTerminated.
  	self assert: 42 equals: result.!

Item was changed:
+ ----- Method: ProcessTest>>testProcessStateTestTermination: (in category 'support') -----
- ----- Method: ProcessTest>>testProcessStateTestTermination: (in category 'tests') -----
  testProcessStateTestTermination: terminator
  	"I test that a process is terminated when it reaches the last instruction 
  	of the bottom context for methods other than Process>>#terminate; 
  	this test would fail with the version of isTerminated before 3/11/2021."
  
  	| bottomContext newProcess |
  	
  	newProcess := Process new.
  	bottomContext := Context 
  		sender: nil 
  		receiver: newProcess 
  		method: (ProcessTest>>#terminated) 
  		arguments: {}.
  	newProcess suspendedContext: ([] asContextWithSender: bottomContext).
  	newProcess priority: Processor activePriority.
  	
  	self deny: newProcess isTerminated.
  	terminator value: newProcess.
  	self assert: newProcess isTerminated.
  !

Item was added:
+ AbstractProcessTest subclass: #ProcessUnwindTest
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'KernelTests-Processes'!

Item was added:
+ ----- Method: ProcessUnwindTest>>testTerminateActiveInNestedEnsure1 (in category 'tests') -----
+ testTerminateActiveInNestedEnsure1
+ 	"Terminate active process.
+ 	Test all nested unwind blocks are correctly executed; 
+ 	all unwind blocks halfway through their execution should be completed."
+ 
+ 	| p x1 x2 x3 x4 |
+ 	x1 := x2 := x3 := x4 := false.
+ 	p := 
+ 		[
+ 			[
+ 				[ ] ensure: [
+ 					[Processor activeProcess terminate] ensure: [
+ 						x1 := true]. 
+ 					x2 := true]
+ 			] ensure: [
+ 				x3 := true].
+ 			x4 := true.
+ 		] newProcess.
+ 	p resume.
+ 	Processor yield.
+ 	self assert: p isTerminated.
+ 	self assert: x1 & x2 & x3.
+ 	self deny: x4.!

Item was added:
+ ----- Method: ProcessUnwindTest>>testTerminateActiveInNestedEnsure2 (in category 'tests') -----
+ testTerminateActiveInNestedEnsure2
+ 	"Terminate active process.
+ 	Test all nested unwind blocks are correctly executed; 
+ 	all unwind blocks halfway through their execution should be completed."
+ 
+ 	| p x1 x2 x3 x4 |
+ 	x1 := x2 := x3 := x4 := false.
+ 	p := 
+ 		[
+ 			[
+ 				[ ] ensure: [
+ 					[ ] ensure: [
+ 						Processor activeProcess terminate.
+ 						x1 := true]. 
+ 					x2 := true]
+ 			] ensure: [
+ 				x3 := true].
+ 			x4 := true.
+ 		] newProcess.
+ 	p resume.
+ 	Processor yield.
+ 	self assert: p isTerminated.
+ 	self assert: x1 & x2 & x3.
+ 	self deny: x4.!

Item was added:
+ ----- Method: ProcessUnwindTest>>testTerminateBlockedInNestedEnsure1 (in category 'tests') -----
+ testTerminateBlockedInNestedEnsure1
+ 	"Terminate blocked process.
+ 	Test all nested unwind blocks are correctly executed; 
+ 	all unwind blocks halfway through their execution should be completed."
+ 
+ 	| p x1 x2 x3 x4 |
+ 	x1 := x2 := x3 := x4 := false.
+ 	p := 
+ 		[
+ 			[
+ 				[ ] ensure: [
+ 					[semaphore wait] ensure: [
+ 						x1 := true]. 
+ 					x2 := true]
+ 			] ensure: [
+ 				x3 := true].
+ 			x4 := true.
+ 		] newProcess.
+ 	p resume.
+ 	Processor yield.
+ 	"make sure p is blocked and none of the unwind blocks has finished yet"
+ 	self assert: p isBlocked.
+ 	self deny: x1 | x2 | x3 | x4.
+ 	"now terminate the process and make sure all unwind blocks have finished"
+ 	p terminate.
+ 	self assert: p isTerminated.
+ 	self assert: x1 & x2 & x3.
+ 	self deny: x4.!

Item was added:
+ ----- Method: ProcessUnwindTest>>testTerminateBlockedInNestedEnsure2 (in category 'tests') -----
+ testTerminateBlockedInNestedEnsure2
+ 	"Terminate blocked process.
+ 	Test all nested unwind blocks are correctly executed; 
+ 	all unwind blocks halfway through their execution should be completed."
+ 
+ 	| p x1 x2 x3 x4 |
+ 	x1 := x2 := x3 := x4 := false.
+ 	p := 
+ 		[
+ 			[
+ 				[ ] ensure: [
+ 					[ ] ensure: [
+ 						semaphore wait.
+ 						x1 := true]. 
+ 					x2 := true]
+ 			] ensure: [
+ 				x3 := true].
+ 			x4 := true.
+ 		] newProcess.
+ 	p resume.
+ 	Processor yield.
+ 	"make sure p is blocked and none of the unwind blocks has finished yet"
+ 	self assert: p isBlocked.
+ 	self deny: x1 | x2 | x3 | x4. 
+ 	"now terminate the process and make sure all unwind blocks have finished"
+ 	p terminate.
+ 	self assert: p isTerminated.
+ 	self assert: x1 & x2 & x3.
+ 	self deny: x4.!

Item was added:
+ ----- Method: ProcessUnwindTest>>testTerminateInNestedEnsureWithReturn1 (in category 'tests') -----
+ testTerminateInNestedEnsureWithReturn1
+ 	"Terminate suspended process.
+ 	Test all nested unwind blocks are correctly executed; 
+ 	all unwind blocks halfway through their execution should be completed."
+ 
+ 	| p x1 x2 x3 x4 |
+ 	x1 := x2 := x3 := x4 := false.
+ 	p := 
+ 	[
+ 		[:return | 
+ 			[
+ 				[ ] ensure: [
+ 					[Processor activeProcess suspend] ensure: [
+ 						x1 := true. return value]. 
+ 					x2 := true]
+ 			] ensure: [
+ 				x3 := true].
+ 			x4 := true.
+ 		] valueWithExit
+ 	] newProcess.
+ 	p resume.
+ 	Processor yield.
+ 	"make sure p is suspended and none of the unwind blocks has finished yet"
+ 	self assert: p isSuspended.
+ 	self deny: x1 | x2 | x3 | x4.
+ 	"now terminate the process and make sure all unwind blocks have finished"
+ 	p terminate.
+ 	self assert: p isTerminated.
+ 	self assert: x1 & x3.
+ 	self deny: x2 & x4.!

Item was added:
+ ----- Method: ProcessUnwindTest>>testTerminateInNestedEnsureWithReturn2 (in category 'tests') -----
+ testTerminateInNestedEnsureWithReturn2
+ 	"Terminate suspended process.
+ 	Test all nested unwind blocks are correctly executed; 
+ 	all unwind blocks halfway through their execution should be completed."
+ 
+ 	| p x1 x2 x3 x4 |
+ 	x1 := x2 := x3 := x4 := false.
+ 	p := 
+ 	[
+ 		[:return | 
+ 			[
+ 				[ ] ensure: [
+ 					[] ensure: [
+ 						Processor activeProcess suspend.
+ 						x1 := true. return value]. 
+ 					x2 := true]
+ 			] ensure: [
+ 				x3 := true].
+ 			x4 := true.
+ 		] valueWithExit
+ 	] newProcess.
+ 	p resume.
+ 	Processor yield.
+ 	"make sure p is suspended and none of the unwind blocks has finished yet"
+ 	self assert: p isSuspended.
+ 	self deny: x1 | x2 | x3 | x4.
+ 	"now terminate the process and make sure all unwind blocks have finished"
+ 	p terminate.
+ 	self assert: p isTerminated.
+ 	self assert: x1 & x3.
+ 	self deny: x2 & x4.!

Item was added:
+ ----- Method: ProcessUnwindTest>>testTerminateInNestedEnsureWithReturn3 (in category 'tests') -----
+ testTerminateInNestedEnsureWithReturn3
+ 	"Terminate suspended process.
+ 	Test all nested unwind blocks are correctly executed; 
+ 	all unwind blocks halfway through their execution should be completed."
+ 
+ 	| p x1 x2 x3 x4 |
+ 	x1 := x2 := x3 := x4 := false.
+ 	p := 
+ 	[
+ 		[:return | 
+ 			[
+ 				[ ] ensure: [
+ 					[Processor activeProcess suspend] ensure: [
+ 						x1 := true]. 
+ 					x2 := true. return value]
+ 			] ensure: [
+ 				x3 := true].
+ 			x4 := true.
+ 		] valueWithExit
+ 	] newProcess.
+ 	p resume.
+ 	Processor yield.
+ 	"make sure p is suspended and none of the unwind blocks has finished yet"
+ 	self assert: p isSuspended.
+ 	self deny: x1 | x2 | x3 | x4.
+ 	"now terminate the process and make sure all unwind blocks have finished"
+ 	p terminate.
+ 	self assert: p isTerminated.
+ 	self assert: x1 & x2 & x3.
+ 	self deny: x4.!

Item was added:
+ ----- Method: ProcessUnwindTest>>testTerminateInNestedEnsureWithReturn4 (in category 'tests') -----
+ testTerminateInNestedEnsureWithReturn4
+ 	"Terminate suspended process.
+ 	Test all nested unwind blocks are correctly executed; 
+ 	all unwind blocks halfway through their execution should be completed."
+ 
+ 	| p x1 x2 x3 x4 |
+ 	x1 := x2 := x3 := x4 := false.
+ 	p := 
+ 	[
+ 		[:return | 
+ 			[
+ 				[ ] ensure: [
+ 					[] ensure: [
+ 						Processor activeProcess suspend.
+ 						x1 := true]. 
+ 					x2 := true. return value]
+ 			] ensure: [
+ 				x3 := true].
+ 			x4 := true.
+ 		] valueWithExit
+ 	] newProcess.
+ 	p resume.
+ 	Processor yield.
+ 	"make sure p is suspended and none of the unwind blocks has finished yet"
+ 	self assert: p isSuspended.
+ 	self deny: x1 | x2 | x3 | x4.
+ 	"now terminate the process and make sure all unwind blocks have finished"
+ 	p terminate.
+ 	self assert: p isTerminated.
+ 	self assert: x1 & x2 & x3.
+ 	self deny: x4.!

Item was added:
+ ----- Method: ProcessUnwindTest>>testTerminateInNestedEnsureWithReturn5 (in category 'tests') -----
+ testTerminateInNestedEnsureWithReturn5
+ 	"Terminate suspended process.
+ 	Test all nested unwind blocks are correctly executed; 
+ 	all unwind blocks halfway through their execution should be completed."
+ 
+ 	| p x1 x2 x3 x4 |
+ 	x1 := x2 := x3 := x4 := false.
+ 	p := 
+ 	[
+ 		[:return | 
+ 			[
+ 				[ ] ensure: [
+ 					[Processor activeProcess suspend] ensure: [
+ 						x1 := true]. 
+ 					x2 := true]
+ 			] ensure: [
+ 				x3 := true. return value].
+ 			x4 := true.
+ 		] valueWithExit
+ 	] newProcess.
+ 	p resume.
+ 	Processor yield.
+ 	"make sure p is suspended and none of the unwind blocks has finished yet"
+ 	self assert: p isSuspended.
+ 	self deny: x1 | x2 | x3 | x4.
+ 	"now terminate the process and make sure all unwind blocks have finished"
+ 	p terminate.
+ 	self assert: p isTerminated.
+ 	self assert: x1 & x2 & x3.
+ 	self deny: x4.!

Item was added:
+ ----- Method: ProcessUnwindTest>>testTerminateInNestedEnsureWithReturn6 (in category 'tests') -----
+ testTerminateInNestedEnsureWithReturn6
+ 	"Terminate suspended process.
+ 	Test all nested unwind blocks are correctly executed; 
+ 	all unwind blocks halfway through their execution should be completed."
+ 
+ 	| p x1 x2 x3 x4 |
+ 	x1 := x2 := x3 := x4 := false.
+ 	p := 
+ 	[
+ 		[:return | 
+ 			[
+ 				[ ] ensure: [
+ 					[] ensure: [
+ 						Processor activeProcess suspend.
+ 						x1 := true]. 
+ 					x2 := true]
+ 			] ensure: [
+ 				x3 := true. return value].
+ 			x4 := true.
+ 		] valueWithExit
+ 	] newProcess.
+ 	p resume.
+ 	Processor yield.
+ 	"make sure p is suspended and none of the unwind blocks has finished yet"
+ 	self assert: p isSuspended.
+ 	self deny: x1 | x2 | x3 | x4.
+ 	"now terminate the process and make sure all unwind blocks have finished"
+ 	p terminate.
+ 	self assert: p isTerminated.
+ 	self assert: x1 & x2 & x3.
+ 	self deny: x4.!

Item was added:
+ ----- Method: ProcessUnwindTest>>testTerminateInNestedEnsureWithReturn7 (in category 'tests') -----
+ testTerminateInNestedEnsureWithReturn7
+ 	"Terminate suspended process.
+ 	Test all nested unwind blocks are correctly executed; 
+ 	all unwind blocks halfway through their execution should be completed."
+ 
+ 	| p x1 x2 x3 x4 |
+ 	x1 := x2 := x3 := x4 := false.
+ 	p := 
+ 	[
+ 		[:return | 
+ 			[
+ 				[ ] ensure: [
+ 					[Processor activeProcess suspend] ensure: [
+ 						x1 := true]. 
+ 					x2 := true]
+ 			] ensure: [
+ 				x3 := true].
+ 			x4 := true. return value.
+ 		] valueWithExit
+ 	] newProcess.
+ 	p resume.
+ 	Processor yield.
+ 	"make sure p is suspended and none of the unwind blocks has finished yet"
+ 	self assert: p isSuspended.
+ 	self deny: x1 | x2 | x3 | x4.
+ 	"now terminate the process and make sure all unwind blocks have finished"
+ 	p terminate.
+ 	self assert: p isTerminated.
+ 	self assert: x1 & x2 & x3.
+ 	self deny: x4.!

Item was added:
+ ----- Method: ProcessUnwindTest>>testTerminateInNestedEnsureWithReturn8 (in category 'tests') -----
+ testTerminateInNestedEnsureWithReturn8
+ 	"Terminate suspended process.
+ 	Test all nested unwind blocks are correctly executed; 
+ 	all unwind blocks halfway through their execution should be completed."
+ 
+ 	| p x1 x2 x3 x4 |
+ 	x1 := x2 := x3 := x4 := false.
+ 	p := 
+ 	[
+ 		[:return | 
+ 			[
+ 				[ ] ensure: [
+ 					[] ensure: [
+ 						Processor activeProcess suspend.
+ 						x1 := true]. 
+ 					x2 := true]
+ 			] ensure: [
+ 				x3 := true].
+ 			x4 := true. return value.
+ 		] valueWithExit
+ 	] newProcess.
+ 	p resume.
+ 	Processor yield.
+ 	"make sure p is suspended and none of the unwind blocks has finished yet"
+ 	self assert: p isSuspended.
+ 	self deny: x1 | x2 | x3 | x4.
+ 	"now terminate the process and make sure all unwind blocks have finished"
+ 	p terminate.
+ 	self assert: p isTerminated.
+ 	self assert: x1 & x2 & x3.
+ 	self deny: x4.!

Item was added:
+ ----- Method: ProcessUnwindTest>>testTerminateRunnableInNestedEnsure1 (in category 'tests') -----
+ testTerminateRunnableInNestedEnsure1
+ 	"Terminate runnable process.
+ 	Test all nested unwind blocks are correctly executed; 
+ 	all unwind blocks halfway through their execution should be completed."
+ 
+ 	| p x1 x2 x3 x4 |
+ 	x1 := x2 := x3 := x4 := false.
+ 	p := 
+ 		[
+ 			[
+ 				[ ] ensure: [
+ 					[Processor yield] ensure: [
+ 						x1 := true]. 
+ 					x2 := true]
+ 			] ensure: [
+ 				x3 := true].
+ 			x4 := true.
+ 		] newProcess.
+ 	p resume.
+ 	Processor yield.
+ 	"make sure p is runnable and none of the unwind blocks has finished yet"
+ 	self assert: p isRunnable.
+ 	self deny: x1 | x2 | x3 | x4.
+ 	"now terminate the process and make sure all unwind blocks have finished"
+ 	p terminate.
+ 	self assert: p isTerminated.
+ 	self assert: x1 & x2 & x3.
+ 	self deny: x4.!

Item was added:
+ ----- Method: ProcessUnwindTest>>testTerminateRunnableInNestedEnsure2 (in category 'tests') -----
+ testTerminateRunnableInNestedEnsure2
+ 	"Terminate runnable process.
+ 	Test all nested unwind blocks are correctly executed; 
+ 	all unwind blocks halfway through their execution should be completed."
+ 
+ 	| p x1 x2 x3 x4 |
+ 	x1 := x2 := x3 := x4 := false.
+ 	p := 
+ 		[
+ 			[
+ 				[ ] ensure: [
+ 					[ ] ensure: [
+ 						Processor yield. 
+ 						x1 := true]. 
+ 					x2 := true]
+ 			] ensure: [
+ 				x3 := true].
+ 			x4 := true.
+ 		] newProcess.
+ 	p resume.
+ 	Processor yield.
+ 	"make sure p is runnable and none of the unwind blocks has finished yet"
+ 	self assert: p isRunnable.
+ 	self deny: x1 | x2 | x3 | x4.
+ 	"now terminate the process and make sure all unwind blocks have finished"
+ 	p terminate.
+ 	self assert: p isTerminated.
+ 	self assert: x1 & x2 & x3.
+ 	self deny: x4.!

Item was added:
+ ----- Method: ProcessUnwindTest>>testTerminateSuspendedInNestedEnsure1 (in category 'tests') -----
+ testTerminateSuspendedInNestedEnsure1
+ 	"Terminate suspended process.
+ 	Test all nested unwind blocks are correctly executed; 
+ 	all unwind blocks halfway through their execution should be completed."
+ 
+ 	| p x1 x2 x3 x4 |
+ 	x1 := x2 := x3 := x4 := false.
+ 	p := 
+ 		[
+ 			[
+ 				[ ] ensure: [
+ 					[Processor activeProcess suspend] ensure: [
+ 						x1 := true]. 
+ 					x2 := true]
+ 			] ensure: [
+ 				x3 := true].
+ 			x4 := true.
+ 		] newProcess.
+ 	p resume.
+ 	Processor yield.
+ 	"make sure p is suspended and none of the unwind blocks has finished yet"
+ 	self assert: p isSuspended.
+ 	self deny: x1 | x2 | x3 | x4.
+ 	"now terminate the process and make sure all unwind blocks have finished"
+ 	p terminate.
+ 	self assert: p isTerminated.
+ 	self assert: x1 & x2 & x3.
+ 	self deny: x4.!

Item was added:
+ ----- Method: ProcessUnwindTest>>testTerminateSuspendedInNestedEnsure2 (in category 'tests') -----
+ testTerminateSuspendedInNestedEnsure2
+ 	"Terminate suspended process.
+ 	Test all nested unwind blocks are correctly executed; 
+ 	all unwind blocks halfway through their execution should be completed."
+ 
+ 	| p x1 x2 x3 x4 |
+ 	x1 := x2 := x3 := x4 := false.
+ 	p := 
+ 		[
+ 			[
+ 				[ ] ensure: [
+ 					[ ] ensure: [
+ 						Processor activeProcess suspend. 
+ 						x1 := true]. 
+ 					x2 := true]
+ 			] ensure: [
+ 				x3 := true].
+ 			x4 := true.
+ 		] newProcess.
+ 	p resume.
+ 	Processor yield.
+ 	"make sure p is suspended and none of the unwind blocks has finished yet"
+ 	self assert: p isSuspended.
+ 	self deny: x1 | x2 | x3 | x4.
+ 	"now terminate the process and make sure all unwind blocks have finished"
+ 	p terminate.
+ 	self assert: p isTerminated.
+ 	self assert: x1 & x2 & x3.
+ 	self deny: x4.!

Item was removed:
- ProcessTest subclass: #UnwindTest
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'KernelTests-Processes'!

Item was removed:
- ----- Method: UnwindTest>>testTerminateActiveInNestedEnsure1 (in category 'tests') -----
- testTerminateActiveInNestedEnsure1
- 	"Terminate active process.
- 	Test all nested unwind blocks are correctly executed; 
- 	all unwind blocks halfway through their execution should be completed."
- 
- 	| p x1 x2 x3 x4 |
- 	x1 := x2 := x3 := x4 := false.
- 	p := 
- 		[
- 			[
- 				[ ] ensure: [
- 					[Processor activeProcess terminate] ensure: [
- 						x1 := true]. 
- 					x2 := true]
- 			] ensure: [
- 				x3 := true].
- 			x4 := true.
- 		] newProcess.
- 	p resume.
- 	Processor yield.
- 	self assert: p isTerminated.
- 	self assert: x1 & x2 & x3.
- 	self deny: x4.!

Item was removed:
- ----- Method: UnwindTest>>testTerminateActiveInNestedEnsure2 (in category 'tests') -----
- testTerminateActiveInNestedEnsure2
- 	"Terminate active process.
- 	Test all nested unwind blocks are correctly executed; 
- 	all unwind blocks halfway through their execution should be completed."
- 
- 	| p x1 x2 x3 x4 |
- 	x1 := x2 := x3 := x4 := false.
- 	p := 
- 		[
- 			[
- 				[ ] ensure: [
- 					[ ] ensure: [
- 						Processor activeProcess terminate.
- 						x1 := true]. 
- 					x2 := true]
- 			] ensure: [
- 				x3 := true].
- 			x4 := true.
- 		] newProcess.
- 	p resume.
- 	Processor yield.
- 	self assert: p isTerminated.
- 	self assert: x1 & x2 & x3.
- 	self deny: x4.!

Item was removed:
- ----- Method: UnwindTest>>testTerminateBlockedInNestedEnsure1 (in category 'tests') -----
- testTerminateBlockedInNestedEnsure1
- 	"Terminate blocked process.
- 	Test all nested unwind blocks are correctly executed; 
- 	all unwind blocks halfway through their execution should be completed."
- 
- 	| p x1 x2 x3 x4 |
- 	x1 := x2 := x3 := x4 := false.
- 	p := 
- 		[
- 			[
- 				[ ] ensure: [
- 					[semaphore wait] ensure: [
- 						x1 := true]. 
- 					x2 := true]
- 			] ensure: [
- 				x3 := true].
- 			x4 := true.
- 		] newProcess.
- 	p resume.
- 	Processor yield.
- 	"make sure p is blocked and none of the unwind blocks has finished yet"
- 	self assert: p isBlocked.
- 	self deny: x1 | x2 | x3 | x4.
- 	"now terminate the process and make sure all unwind blocks have finished"
- 	p terminate.
- 	self assert: p isTerminated.
- 	self assert: x1 & x2 & x3.
- 	self deny: x4.!

Item was removed:
- ----- Method: UnwindTest>>testTerminateBlockedInNestedEnsure2 (in category 'tests') -----
- testTerminateBlockedInNestedEnsure2
- 	"Terminate blocked process.
- 	Test all nested unwind blocks are correctly executed; 
- 	all unwind blocks halfway through their execution should be completed."
- 
- 	| p x1 x2 x3 x4 |
- 	x1 := x2 := x3 := x4 := false.
- 	p := 
- 		[
- 			[
- 				[ ] ensure: [
- 					[ ] ensure: [
- 						semaphore wait.
- 						x1 := true]. 
- 					x2 := true]
- 			] ensure: [
- 				x3 := true].
- 			x4 := true.
- 		] newProcess.
- 	p resume.
- 	Processor yield.
- 	"make sure p is blocked and none of the unwind blocks has finished yet"
- 	self assert: p isBlocked.
- 	self deny: x1 | x2 | x3 | x4. 
- 	"now terminate the process and make sure all unwind blocks have finished"
- 	p terminate.
- 	self assert: p isTerminated.
- 	self assert: x1 & x2 & x3.
- 	self deny: x4.!

Item was removed:
- ----- Method: UnwindTest>>testTerminateInNestedEnsureWithReturn1 (in category 'tests') -----
- testTerminateInNestedEnsureWithReturn1
- 	"Terminate suspended process.
- 	Test all nested unwind blocks are correctly executed; 
- 	all unwind blocks halfway through their execution should be completed."
- 
- 	| p x1 x2 x3 x4 |
- 	x1 := x2 := x3 := x4 := false.
- 	p := 
- 	[
- 		[:return | 
- 			[
- 				[ ] ensure: [
- 					[Processor activeProcess suspend] ensure: [
- 						x1 := true. return value]. 
- 					x2 := true]
- 			] ensure: [
- 				x3 := true].
- 			x4 := true.
- 		] valueWithExit
- 	] newProcess.
- 	p resume.
- 	Processor yield.
- 	"make sure p is suspended and none of the unwind blocks has finished yet"
- 	self assert: p isSuspended.
- 	self deny: x1 | x2 | x3 | x4.
- 	"now terminate the process and make sure all unwind blocks have finished"
- 	p terminate.
- 	self assert: p isTerminated.
- 	self assert: x1 & x3.
- 	self deny: x2 & x4.!

Item was removed:
- ----- Method: UnwindTest>>testTerminateInNestedEnsureWithReturn2 (in category 'tests') -----
- testTerminateInNestedEnsureWithReturn2
- 	"Terminate suspended process.
- 	Test all nested unwind blocks are correctly executed; 
- 	all unwind blocks halfway through their execution should be completed."
- 
- 	| p x1 x2 x3 x4 |
- 	x1 := x2 := x3 := x4 := false.
- 	p := 
- 	[
- 		[:return | 
- 			[
- 				[ ] ensure: [
- 					[] ensure: [
- 						Processor activeProcess suspend.
- 						x1 := true. return value]. 
- 					x2 := true]
- 			] ensure: [
- 				x3 := true].
- 			x4 := true.
- 		] valueWithExit
- 	] newProcess.
- 	p resume.
- 	Processor yield.
- 	"make sure p is suspended and none of the unwind blocks has finished yet"
- 	self assert: p isSuspended.
- 	self deny: x1 | x2 | x3 | x4.
- 	"now terminate the process and make sure all unwind blocks have finished"
- 	p terminate.
- 	self assert: p isTerminated.
- 	self assert: x1 & x3.
- 	self deny: x2 & x4.!

Item was removed:
- ----- Method: UnwindTest>>testTerminateInNestedEnsureWithReturn3 (in category 'tests') -----
- testTerminateInNestedEnsureWithReturn3
- 	"Terminate suspended process.
- 	Test all nested unwind blocks are correctly executed; 
- 	all unwind blocks halfway through their execution should be completed."
- 
- 	| p x1 x2 x3 x4 |
- 	x1 := x2 := x3 := x4 := false.
- 	p := 
- 	[
- 		[:return | 
- 			[
- 				[ ] ensure: [
- 					[Processor activeProcess suspend] ensure: [
- 						x1 := true]. 
- 					x2 := true. return value]
- 			] ensure: [
- 				x3 := true].
- 			x4 := true.
- 		] valueWithExit
- 	] newProcess.
- 	p resume.
- 	Processor yield.
- 	"make sure p is suspended and none of the unwind blocks has finished yet"
- 	self assert: p isSuspended.
- 	self deny: x1 | x2 | x3 | x4.
- 	"now terminate the process and make sure all unwind blocks have finished"
- 	p terminate.
- 	self assert: p isTerminated.
- 	self assert: x1 & x2 & x3.
- 	self deny: x4.!

Item was removed:
- ----- Method: UnwindTest>>testTerminateInNestedEnsureWithReturn4 (in category 'tests') -----
- testTerminateInNestedEnsureWithReturn4
- 	"Terminate suspended process.
- 	Test all nested unwind blocks are correctly executed; 
- 	all unwind blocks halfway through their execution should be completed."
- 
- 	| p x1 x2 x3 x4 |
- 	x1 := x2 := x3 := x4 := false.
- 	p := 
- 	[
- 		[:return | 
- 			[
- 				[ ] ensure: [
- 					[] ensure: [
- 						Processor activeProcess suspend.
- 						x1 := true]. 
- 					x2 := true. return value]
- 			] ensure: [
- 				x3 := true].
- 			x4 := true.
- 		] valueWithExit
- 	] newProcess.
- 	p resume.
- 	Processor yield.
- 	"make sure p is suspended and none of the unwind blocks has finished yet"
- 	self assert: p isSuspended.
- 	self deny: x1 | x2 | x3 | x4.
- 	"now terminate the process and make sure all unwind blocks have finished"
- 	p terminate.
- 	self assert: p isTerminated.
- 	self assert: x1 & x2 & x3.
- 	self deny: x4.!

Item was removed:
- ----- Method: UnwindTest>>testTerminateInNestedEnsureWithReturn5 (in category 'tests') -----
- testTerminateInNestedEnsureWithReturn5
- 	"Terminate suspended process.
- 	Test all nested unwind blocks are correctly executed; 
- 	all unwind blocks halfway through their execution should be completed."
- 
- 	| p x1 x2 x3 x4 |
- 	x1 := x2 := x3 := x4 := false.
- 	p := 
- 	[
- 		[:return | 
- 			[
- 				[ ] ensure: [
- 					[Processor activeProcess suspend] ensure: [
- 						x1 := true]. 
- 					x2 := true]
- 			] ensure: [
- 				x3 := true. return value].
- 			x4 := true.
- 		] valueWithExit
- 	] newProcess.
- 	p resume.
- 	Processor yield.
- 	"make sure p is suspended and none of the unwind blocks has finished yet"
- 	self assert: p isSuspended.
- 	self deny: x1 | x2 | x3 | x4.
- 	"now terminate the process and make sure all unwind blocks have finished"
- 	p terminate.
- 	self assert: p isTerminated.
- 	self assert: x1 & x2 & x3.
- 	self deny: x4.!

Item was removed:
- ----- Method: UnwindTest>>testTerminateInNestedEnsureWithReturn6 (in category 'tests') -----
- testTerminateInNestedEnsureWithReturn6
- 	"Terminate suspended process.
- 	Test all nested unwind blocks are correctly executed; 
- 	all unwind blocks halfway through their execution should be completed."
- 
- 	| p x1 x2 x3 x4 |
- 	x1 := x2 := x3 := x4 := false.
- 	p := 
- 	[
- 		[:return | 
- 			[
- 				[ ] ensure: [
- 					[] ensure: [
- 						Processor activeProcess suspend.
- 						x1 := true]. 
- 					x2 := true]
- 			] ensure: [
- 				x3 := true. return value].
- 			x4 := true.
- 		] valueWithExit
- 	] newProcess.
- 	p resume.
- 	Processor yield.
- 	"make sure p is suspended and none of the unwind blocks has finished yet"
- 	self assert: p isSuspended.
- 	self deny: x1 | x2 | x3 | x4.
- 	"now terminate the process and make sure all unwind blocks have finished"
- 	p terminate.
- 	self assert: p isTerminated.
- 	self assert: x1 & x2 & x3.
- 	self deny: x4.!

Item was removed:
- ----- Method: UnwindTest>>testTerminateInNestedEnsureWithReturn7 (in category 'tests') -----
- testTerminateInNestedEnsureWithReturn7
- 	"Terminate suspended process.
- 	Test all nested unwind blocks are correctly executed; 
- 	all unwind blocks halfway through their execution should be completed."
- 
- 	| p x1 x2 x3 x4 |
- 	x1 := x2 := x3 := x4 := false.
- 	p := 
- 	[
- 		[:return | 
- 			[
- 				[ ] ensure: [
- 					[Processor activeProcess suspend] ensure: [
- 						x1 := true]. 
- 					x2 := true]
- 			] ensure: [
- 				x3 := true].
- 			x4 := true. return value.
- 		] valueWithExit
- 	] newProcess.
- 	p resume.
- 	Processor yield.
- 	"make sure p is suspended and none of the unwind blocks has finished yet"
- 	self assert: p isSuspended.
- 	self deny: x1 | x2 | x3 | x4.
- 	"now terminate the process and make sure all unwind blocks have finished"
- 	p terminate.
- 	self assert: p isTerminated.
- 	self assert: x1 & x2 & x3.
- 	self deny: x4.!

Item was removed:
- ----- Method: UnwindTest>>testTerminateInNestedEnsureWithReturn8 (in category 'tests') -----
- testTerminateInNestedEnsureWithReturn8
- 	"Terminate suspended process.
- 	Test all nested unwind blocks are correctly executed; 
- 	all unwind blocks halfway through their execution should be completed."
- 
- 	| p x1 x2 x3 x4 |
- 	x1 := x2 := x3 := x4 := false.
- 	p := 
- 	[
- 		[:return | 
- 			[
- 				[ ] ensure: [
- 					[] ensure: [
- 						Processor activeProcess suspend.
- 						x1 := true]. 
- 					x2 := true]
- 			] ensure: [
- 				x3 := true].
- 			x4 := true. return value.
- 		] valueWithExit
- 	] newProcess.
- 	p resume.
- 	Processor yield.
- 	"make sure p is suspended and none of the unwind blocks has finished yet"
- 	self assert: p isSuspended.
- 	self deny: x1 | x2 | x3 | x4.
- 	"now terminate the process and make sure all unwind blocks have finished"
- 	p terminate.
- 	self assert: p isTerminated.
- 	self assert: x1 & x2 & x3.
- 	self deny: x4.!

Item was removed:
- ----- Method: UnwindTest>>testTerminateRunnableInNestedEnsure1 (in category 'tests') -----
- testTerminateRunnableInNestedEnsure1
- 	"Terminate runnable process.
- 	Test all nested unwind blocks are correctly executed; 
- 	all unwind blocks halfway through their execution should be completed."
- 
- 	| p x1 x2 x3 x4 |
- 	x1 := x2 := x3 := x4 := false.
- 	p := 
- 		[
- 			[
- 				[ ] ensure: [
- 					[Processor yield] ensure: [
- 						x1 := true]. 
- 					x2 := true]
- 			] ensure: [
- 				x3 := true].
- 			x4 := true.
- 		] newProcess.
- 	p resume.
- 	Processor yield.
- 	"make sure p is runnable and none of the unwind blocks has finished yet"
- 	self assert: p isRunnable.
- 	self deny: x1 | x2 | x3 | x4.
- 	"now terminate the process and make sure all unwind blocks have finished"
- 	p terminate.
- 	self assert: p isTerminated.
- 	self assert: x1 & x2 & x3.
- 	self deny: x4.!

Item was removed:
- ----- Method: UnwindTest>>testTerminateRunnableInNestedEnsure2 (in category 'tests') -----
- testTerminateRunnableInNestedEnsure2
- 	"Terminate runnable process.
- 	Test all nested unwind blocks are correctly executed; 
- 	all unwind blocks halfway through their execution should be completed."
- 
- 	| p x1 x2 x3 x4 |
- 	x1 := x2 := x3 := x4 := false.
- 	p := 
- 		[
- 			[
- 				[ ] ensure: [
- 					[ ] ensure: [
- 						Processor yield. 
- 						x1 := true]. 
- 					x2 := true]
- 			] ensure: [
- 				x3 := true].
- 			x4 := true.
- 		] newProcess.
- 	p resume.
- 	Processor yield.
- 	"make sure p is runnable and none of the unwind blocks has finished yet"
- 	self assert: p isRunnable.
- 	self deny: x1 | x2 | x3 | x4.
- 	"now terminate the process and make sure all unwind blocks have finished"
- 	p terminate.
- 	self assert: p isTerminated.
- 	self assert: x1 & x2 & x3.
- 	self deny: x4.!

Item was removed:
- ----- Method: UnwindTest>>testTerminateSuspendedInNestedEnsure1 (in category 'tests') -----
- testTerminateSuspendedInNestedEnsure1
- 	"Terminate suspended process.
- 	Test all nested unwind blocks are correctly executed; 
- 	all unwind blocks halfway through their execution should be completed."
- 
- 	| p x1 x2 x3 x4 |
- 	x1 := x2 := x3 := x4 := false.
- 	p := 
- 		[
- 			[
- 				[ ] ensure: [
- 					[Processor activeProcess suspend] ensure: [
- 						x1 := true]. 
- 					x2 := true]
- 			] ensure: [
- 				x3 := true].
- 			x4 := true.
- 		] newProcess.
- 	p resume.
- 	Processor yield.
- 	"make sure p is suspended and none of the unwind blocks has finished yet"
- 	self assert: p isSuspended.
- 	self deny: x1 | x2 | x3 | x4.
- 	"now terminate the process and make sure all unwind blocks have finished"
- 	p terminate.
- 	self assert: p isTerminated.
- 	self assert: x1 & x2 & x3.
- 	self deny: x4.!

Item was removed:
- ----- Method: UnwindTest>>testTerminateSuspendedInNestedEnsure2 (in category 'tests') -----
- testTerminateSuspendedInNestedEnsure2
- 	"Terminate suspended process.
- 	Test all nested unwind blocks are correctly executed; 
- 	all unwind blocks halfway through their execution should be completed."
- 
- 	| p x1 x2 x3 x4 |
- 	x1 := x2 := x3 := x4 := false.
- 	p := 
- 		[
- 			[
- 				[ ] ensure: [
- 					[ ] ensure: [
- 						Processor activeProcess suspend. 
- 						x1 := true]. 
- 					x2 := true]
- 			] ensure: [
- 				x3 := true].
- 			x4 := true.
- 		] newProcess.
- 	p resume.
- 	Processor yield.
- 	"make sure p is suspended and none of the unwind blocks has finished yet"
- 	self assert: p isSuspended.
- 	self deny: x1 | x2 | x3 | x4.
- 	"now terminate the process and make sure all unwind blocks have finished"
- 	p terminate.
- 	self assert: p isTerminated.
- 	self assert: x1 & x2 & x3.
- 	self deny: x4.!



More information about the Squeak-dev mailing list