[squeak-dev] The Inbox: KernelTests-jar.443.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Jan 30 16:33:24 UTC 2023


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

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

Name: KernelTests-jar.443
Author: jar
Time: 30 January 2023, 5:33:22.893677 pm
UUID: 4f815d5d-a166-d141-8fca-d9d0d57f0b93
Ancestors: KernelTests-tpr.441

Complement Kernel-jar.1498

=============== Diff against KernelTests-tpr.441 ===============

Item was removed:
- ----- Method: MutexTest>>expectedFailures (in category 'failures') -----
- expectedFailures
- 
- 	^ #(testUnwindMutexBlockedInCritical)!

Item was added:
+ ----- Method: MutexTest>>testMutexAfterCriticalWait2 (in category 'tests') -----
+ testMutexAfterCriticalWait2
+ 	"This tests whether a process that has just left the primitiveEnterCriticalSection in Mutex>>critical:
+ 	leaves it with the mutex correctly released."
+ 	| lock p beenHere |
+ 	lock := Mutex new. beenHere := false.
+ 	p := [lock critical: [beenHere := true]] newProcess.
+ 	p priority: Processor activePriority - 1.
+ 	lock critical: "We now own it; p can't enter properly"
+ 		[p resume.
+ 		 "wait until p enters the critical section; it doesn't own the Mutex so is blocked..."
+ 		 [p suspendingList == lock] whileFalse: [(Delay forMilliseconds: 10) wait].
+ 		 self deny: lock isEmpty].
+ 	"p is waiting on lock; on our exiting critical: p is now the notional owner. Terminate before it has a chance to run".
+ 	p terminate.
+ 	self deny: lock isOwned.
+ 	self assert: lock isEmpty.
+ 	self deny: beenHere!

Item was added:
+ ----- Method: MutexTest>>testMutexAfterCriticalWaitCf (in category 'tests') -----
+ testMutexAfterCriticalWaitCf
+ 	"This tests whether a process that has just left the primitiveEnterCriticalSection in Mutex>>critical:
+ 	leaves it with the mutex correctly released."
+ 	| lock p beenHere |
+ 	lock := Mutex new. beenHere := false.
+ 	p := [lock critical: [beenHere := true]] newProcess.
+ 	p priority: Processor activePriority - 1.
+ 	lock critical: "We now own it; p can't enter properly"
+ 		[p resume.
+ 		 "wait until p enters the critical section; it doesn't own the Mutex so is blocked..."
+ 		 [p suspendingList == lock] whileFalse: [(Delay forMilliseconds: 10) wait].
+ 		 self deny: lock isEmpty.
+ 		"p is waiting on lock; on our exiting critical: p is now the notional owner. Terminate before it has a chance to run".
+ 		p terminate].
+ 	self deny: lock isOwned.
+ 	self assert: lock isEmpty.
+ 	self deny: beenHere!

Item was added:
+ ----- Method: MutexTest>>testMutexAfterCriticalWaitInEnsure (in category 'tests') -----
+ testMutexAfterCriticalWaitInEnsure
+ 	"This tests whether a process that has just left the primitiveEnterCriticalSection in Mutex>>critical:
+ 	leaves it with the mutex correctly released."
+ 	| lock p |
+ 	lock := Mutex new.
+ 	p := [[] ensure: [lock critical: []]] newProcess.
+ 	p priority: Processor activePriority - 1.
+ 	lock critical: "We now own it; p can't enter properly"
+ 		[p resume.
+ 		 "wait until p enters the critical section; it doesn't own the Mutex so is blocked..."
+ 		 [p suspendingList == lock] whileFalse: [(Delay forMilliseconds: 10) wait].
+ 		 self deny: lock isEmpty].
+ 	"p is waiting on lock; on our exiting critical: p is now the notional owner. Terminate before it has a chance to run".
+ 	p terminate.
+ 	self deny: lock isOwned.
+ 	self assert: lock isEmpty!

Item was added:
+ ----- Method: MutexTest>>testMutexAfterCriticalWaitInEnsure2 (in category 'tests') -----
+ testMutexAfterCriticalWaitInEnsure2
+ 	"This tests whether a process that has just left the primitiveEnterCriticalSection in Mutex>>critical:
+ 	leaves it with the mutex correctly released."
+ 	| lock p beenHere |
+ 	lock := Mutex new. beenHere := false.
+ 	p := [[] ensure: [lock critical: [beenHere := true]]] newProcess.
+ 	p priority: Processor activePriority - 1.
+ 	lock critical: "We now own it; p can't enter properly"
+ 		[p resume.
+ 		 "wait until p enters the critical section; it doesn't own the Mutex so is blocked..."
+ 		 [p suspendingList == lock] whileFalse: [(Delay forMilliseconds: 10) wait].
+ 		 self deny: lock isEmpty].
+ 	"p is waiting on lock; on our exiting critical: p is now the notional owner. Terminate before it has a chance to run".
+ 	p terminate.
+ 	self deny: lock isOwned.
+ 	self assert: lock isEmpty.
+ 	self assert: beenHere!

Item was added:
+ ----- Method: MutexTest>>testMutexAfterCriticalWaitInEnsureCf (in category 'tests') -----
+ testMutexAfterCriticalWaitInEnsureCf
+ 	"This tests whether a process that has just left the primitiveEnterCriticalSection in Mutex>>critical:
+ 	leaves it with the mutex correctly released."
+ 	| lock p beenHere |
+ 	lock := Mutex new. beenHere := false.
+ 	p := [[] ensure: [lock critical: [beenHere := true]]] newProcess.
+ 	p priority: Processor activePriority - 1.
+ 	lock critical: "We now own it; p can't enter properly"
+ 		[p resume.
+ 		 "wait until p enters the critical section; it doesn't own the Mutex so is blocked..."
+ 		 [p suspendingList == lock] whileFalse: [(Delay forMilliseconds: 10) wait].
+ 		 self deny: lock isEmpty.
+ 		"p is waiting on lock; on our exiting critical: p is now the notional owner. Terminate before it has a chance to run".
+ 		p terminate].
+ 	self deny: lock isOwned.
+ 	self assert: lock isEmpty.
+ 	self deny: beenHere!

Item was added:
+ ----- Method: MutexTest>>testMutexBlockedInCritical (in category 'tests') -----
+ testMutexBlockedInCritical
+ 	"This tests whether a process that is inside the primitiveEnterCriticalSection in Mutex>>critical:
+ 	leaves it unchanged."
+ 	| lock sock proc wait |
+ 	lock := Mutex new.
+ 	sock := Semaphore new.
+ 	proc := [lock critical: [sock wait]] fork.
+ 	wait := [lock critical: []] fork.
+ 	Processor yield.
+ 	self assert: proc suspendingList == sock.
+ 	self assert: wait suspendingList == lock.
+ 	self deny: lock isEmpty.
+ 	self assert: lock isOwned.
+ 	wait terminate.
+ 	Processor yield.
+ 	self assert: wait isTerminated.
+ 	self assert: proc suspendingList == sock.
+ 	self assert: wait suspendingList == nil.
+ 	self assert: lock isEmpty.
+ 	self assert: lock isOwned.
+ 	proc terminate!

Item was added:
+ ----- Method: MutexTest>>testMutexBlockedInCritical2 (in category 'tests') -----
+ testMutexBlockedInCritical2
+ 	"This tests whether a process that is inside the primitiveEnterCriticalSection in Mutex>>critical:
+ 	leaves it unchanged."
+ 	| lock sock proc wait beenHere beenHereToo |
+ 	lock := Mutex new.
+ 	sock := Semaphore new.
+ 	beenHere := beenHereToo := false.
+ 	proc := [lock critical: [sock wait]] fork.
+ 	wait := [lock critical: [beenHere := true]. beenHereToo := true] fork.
+ 	Processor yield.
+ 	self assert: proc suspendingList == sock.
+ 	self assert: wait suspendingList == lock.
+ 	self deny: lock isEmpty.
+ 	self assert: lock isOwned.
+ 	wait terminate.
+ 	Processor yield.
+ 	self assert: wait isTerminated.
+ 	self assert: proc suspendingList == sock.
+ 	self assert: wait suspendingList == nil.
+ 	self assert: lock isEmpty.
+ 	self assert: lock isOwned.
+ 	self deny: beenHere.
+ 	self deny: beenHereToo.
+ 	proc terminate!

Item was added:
+ ----- Method: MutexTest>>testMutexBlockedInCriticalInEnsure (in category 'tests') -----
+ testMutexBlockedInCriticalInEnsure
+ 	"This tests whether a process that is inside the primitiveEnterCriticalSection in Mutex>>critical:
+ 	leaves it unchanged."
+ 	| lock sock proc wait |
+ 	lock := Mutex new.
+ 	sock := Semaphore new.
+ 	proc := [lock critical: [sock wait]] fork.
+ 	wait := [[] ensure: [lock critical: []]] fork.
+ 	Processor yield.
+ 	self assert: proc suspendingList == sock.
+ 	self assert: wait suspendingList == lock.
+ 	self deny: lock isEmpty.
+ 	self assert: lock isOwned.
+ 	wait terminate.
+ 	Processor yield.
+ 	self assert: wait isTerminated.
+ 	self assert: proc suspendingList == sock.
+ 	self assert: wait suspendingList == nil.
+ 	self assert: lock isEmpty.
+ 	self assert: lock isOwned.
+ 	proc terminate!

Item was added:
+ ----- Method: MutexTest>>testMutexBlockedInCriticalInEnsure2 (in category 'tests') -----
+ testMutexBlockedInCriticalInEnsure2
+ 	"This tests whether a process that is inside the primitiveEnterCriticalSection in Mutex>>critical:
+ 	leaves it unchanged."
+ 	| lock sock proc wait beenHere beenHereToo |
+ 	lock := Mutex new.
+ 	sock := Semaphore new.
+ 	beenHere := beenHereToo := false.
+ 	proc := [lock critical: [sock wait]] fork.
+ 	wait := [[] ensure: [lock critical: [beenHere := true]. beenHereToo := true]] fork.
+ 	Processor yield.
+ 	self assert: proc suspendingList == sock.
+ 	self assert: wait suspendingList == lock.
+ 	self deny: lock isEmpty.
+ 	self assert: lock isOwned.
+ 	wait terminate.
+ 	Processor yield.
+ 	self assert: wait isTerminated.
+ 	self assert: proc suspendingList == sock.
+ 	self assert: wait suspendingList == nil.
+ 	self assert: lock isEmpty.
+ 	self assert: lock isOwned.
+ 	self deny: beenHere.
+ 	self assert: beenHereToo.
+ 	proc terminate!

Item was added:
+ ----- Method: MutexTest>>testMutexInCriticalWait2 (in category 'tests') -----
+ testMutexInCriticalWait2
+ 	"This tests whether a process that has got past the primitiveEnterCriticalSection in Mutex>>critical:
+ 	leaves it unowned."
+ 	| lock sock proc beenHere beenHereToo |
+ 	lock := Mutex new.
+ 	sock := Semaphore new.
+ 	beenHere := beenHereToo := false.
+ 	proc := [lock critical: [sock wait. beenHere := true]. beenHereToo := true] fork.
+ 	Processor yield.
+ 	self assert: proc suspendingList == sock.
+ 	proc terminate.
+ 	self deny: lock isOwned.
+ 	self assert: lock isEmpty.
+ 	self deny: beenHere.
+ 	self deny: beenHereToo!

Item was added:
+ ----- Method: MutexTest>>testMutexInCriticalWaitInEnsure (in category 'tests') -----
+ testMutexInCriticalWaitInEnsure
+ 	"This tests whether a process that has got past the primitiveEnterCriticalSection in Mutex>>critical:
+ 	leaves it unowned."
+ 	| lock sock proc |
+ 	lock := Mutex new.
+ 	sock := Semaphore new.
+ 	proc := [[] ensure: [lock critical: [sock wait]]] fork.
+ 	Processor yield.
+ 	self assert: proc suspendingList == sock.
+ 	proc terminate.
+ 	self deny: lock isOwned.
+ 	self assert: lock isEmpty!

Item was added:
+ ----- Method: MutexTest>>testMutexInCriticalWaitInEnsure2 (in category 'tests') -----
+ testMutexInCriticalWaitInEnsure2
+ 	"This tests whether a process that has got past the primitiveEnterCriticalSection in Mutex>>critical:
+ 	leaves it unowned."
+ 	| lock sock proc beenHere beenHereToo |
+ 	lock := Mutex new.
+ 	sock := Semaphore new.
+ 	beenHere := beenHereToo := false.
+ 	proc := [[] ensure: [lock critical: [sock wait. beenHere := true]. beenHereToo := true]] fork.
+ 	Processor yield.
+ 	self assert: proc suspendingList == sock.
+ 	proc terminate.
+ 	self deny: lock isOwned.
+ 	self assert: lock isEmpty.
+ 	self assert: beenHere.
+ 	self assert: beenHereToo!

Item was removed:
- ----- Method: MutexTest>>testUnwindMutexBlockedInCritical (in category 'tests') -----
- testUnwindMutexBlockedInCritical	"self run: #testMutexBlockedInCritical"
- 	"This tests whether a mutex that is inside the primitiveEnterCriticalSection in Mutex>>critical:
- 	leaves it unchanged."
- 	| lock sock proc wait |
- 	lock := Mutex new.
- 	sock := Semaphore new.
- 	proc := [lock critical: [sock wait]] fork.
- 	wait := [[] ensure: [lock critical: []]] fork.
- 	Processor yield.
- 	self assert: proc suspendingList == sock.
- 	self assert: wait suspendingList == lock.
- 	self deny: lock isEmpty.
- 	self assert: lock isOwned.
- 	wait terminate.
- 	Processor yield.
- 	self assert: wait isTerminated.
- 	self assert: proc suspendingList == sock.
- 	self assert: wait suspendingList == nil.
- 	self assert: lock isEmpty.
- 	self assert: lock isOwned
- !

Item was removed:
- ----- Method: ProcessTest>>expectedFailures (in category 'failures') -----
- expectedFailures
- 
- 	^ #(testTerminateTerminatingProcess testResumeTerminatingProcess)!

Item was changed:
  ----- Method: ProcessTest>>testResumeTerminatingProcess (in category 'tests') -----
  testResumeTerminatingProcess
+ 	"An attempt to resume a terminating process in the middle of preparing its suspended context should raise an error;
+ 	 one possible solution is to nil the suspended context of the terminating process while executing the vulnerable code"
+ 	
+ 	"Note: another solution could be to run the vulnerable part of the code in #terminate using #valueUnpreemptively;
+ 	 currently, however, #valueUnpreemptively is affected by the #priority: bug described here:
+ 	 http://lists.squeakfoundation.org/pipermail/squeak-dev/2021-December/217473.html"
- 	"An attempt to resume a terminating process should probably raise an error;
- 	leave this test as an expected failure for the moment."
  
+ 	| terminatee terminator unwound |
+ 	unwound := false.
+ 	terminatee := [[Processor activeProcess suspend] ensure: [unwound := unwound not]] newProcess.
+ 	terminatee priority: Processor activePriority + 1. 
+ 	terminatee resume.
- 	| terminatee terminator resumed |
- 	terminatee := [semaphore critical:[]. resumed := true] fork.
- 	Processor yield.
  	terminator := [terminatee terminate] newProcess.
+ 	terminator priority: Processor activePriority + 1. 
+ 	self assert: terminatee isSuspended.
- 	self assert: terminatee suspendingList == semaphore.
  	self assert: terminator isSuspended. 
  	"run terminator and stop inside #terminate"
+ 	[terminator suspendedContext selectorToSendOrSelf == #bottomContext] whileFalse: [terminator step].
+ 	self assert: terminatee suspendedContext isNil.
+ 	self deny: unwound.
- 	terminator runUntil: [:ctx | ctx selectorToSendOrSelf = #priority:].
  	self assert: terminator isSuspended.
+ 	"resuming the terminatee process should causes the VM to raise an error while its suspended context is nil"
- 	"resume the terminatee process and and check if the VM raises an error;
- 	an error is expected because terminatee's suspendedContext equals nil"
  	self should: [terminatee resume] raise: Error.
+ 	self assert: terminatee suspendedContext isNil.
+ 	self deny: unwound.
+ 	self assert: terminator isSuspended.
+ 	"now let the terminator finish its interrupted termination of the terminatee process"
- 	"now let the terminator finish terminating the terminatee process"
  	terminator resume.
- 	Processor yield.
- 	self assert: resumed isNil.
  	self assert: terminatee isTerminated.
+ 	self assert: unwound.
  	self assert: terminator isTerminated!

Item was changed:
  ----- Method: ProcessTest>>testTerminateTerminatingProcess (in category 'tests') -----
  testTerminateTerminatingProcess
+ 	"An attempt to terminate a terminating process in the middle of preparing its suspended context should do nothing;
+ 	 one possible solution is to nil the suspended context of the terminating process while executing the vulnerable code."
+ 	
+ 	"Note: another solution could be to run the vulnerable part of the code in #terminate using #valueUnpreemptively;
+ 	 currently, however, #valueUnpreemptively is affected by the #priority: bug described here:
+ 	 http://lists.squeakfoundation.org/pipermail/squeak-dev/2021-December/217473.html"
- 	"An attempt to terminate a terminating process should probably raise an error;
- 	leave this test as an expected failure for the moment."
  
+ 	| terminatee terminator unwound |
+ 	unwound := false.
+ 	terminatee := [[Processor activeProcess suspend] ensure: [unwound := unwound not]] newProcess.
+ 	terminatee priority: Processor activePriority + 1. 
+ 	terminatee resume.
- 	| terminatee terminator resumed |
- 	terminatee := [semaphore critical:[]. resumed := true] fork.
- 	Processor yield.
  	terminator := [terminatee terminate] newProcess.
+ 	terminator priority: Processor activePriority + 1. 
+ 	self assert: terminatee isSuspended.
- 	self assert: terminatee suspendingList == semaphore.
  	self assert: terminator isSuspended. 
  	"run terminator and stop inside #terminate"
+ 	[terminator suspendedContext selectorToSendOrSelf == #bottomContext] whileFalse: [terminator step].
+ 	self assert: terminatee suspendedContext isNil.
+ 	self deny: unwound.
- 	terminator runUntil: [:ctx | ctx selectorToSendOrSelf = #priority:].
  	self assert: terminator isSuspended.
+ 	"terminating the terminatee process again should make no difference while its suspended context is nil"
+ 	terminatee terminate.
+ 	self assert: terminatee suspendedContext isNil.
+ 	self deny: unwound.
+ 	self assert: terminator isSuspended.
+ 	"now let the terminator finish its interrupted termination of the terminatee process"
- 	"terminate the terminatee process again and let the termination finish;
- 	an error is expected because #terminate detected multiple termination"
- 	self should: [terminatee terminate] raise: Error.
- 	"now let the terminator finish terminating the terminatee process"
  	terminator resume.
- 	Processor yield.
- 	self assert: resumed isNil.
  	self assert: terminatee isTerminated.
+ 	self assert: unwound.
  	self assert: terminator isTerminated!

Item was added:
+ ----- Method: ProcessTest>>testTerminateTerminatingProcessBeforeUnwindTo (in category 'tests') -----
+ testTerminateTerminatingProcessBeforeUnwindTo
+ 	"Terminating a terminatee process after the terminator process restarted the terminatee
+ 	 process should unwind the terminatee process and let the terminator process terminate."
+ 	
+ 	| terminator terminatee unwound |
+ 	unwound := false.
+ 	terminatee := [[Semaphore new wait] ensure: [unwound := true]] fork.
+ 	Processor yield.
+ 	terminator := [terminatee terminate] newProcess.
+ 	self assert: terminatee isBlocked.
+ 	self assert: terminator isSuspended.
+ 	terminator runUntil: [:ctx | ctx selectorToSendOrSelf = #resume].
+ 	"terminator steps until terminatee's unwind context is set"
+ 	terminator suspendedContext nextInstruction. "skip terminatee resume instruction"
+ 	terminator resume. "and run until parked at wait"
+ 	"terminatee is inside its helper stack, about to call #unwindTo:"
+ 	self assert: terminatee isSuspended.
+ 	terminatee terminate.
+ 	self assert: terminatee isTerminated. 
+ 	self assert: unwound.
+ 	Processor yield.
+ 	self assert: terminator isTerminated!

Item was removed:
- ----- Method: SemaphoreTest>>expectedFailures (in category 'failures') -----
- expectedFailures
- 
- 	^ #(testUnwindSemaInCriticalWait)!

Item was added:
+ ----- Method: SemaphoreTest>>testSemaAfterCriticalWait2 (in category 'tests') -----
+ testSemaAfterCriticalWait2
+ 	"This tests whether a process that has just left the wait in Semaphore>>critical:
+ 	leaves it with signaling the associated semaphore."
+ 	| s p beenHere |
+ 	s := Semaphore new. beenHere := false.
+ 	p := [s critical: [beenHere := true]] forkAt: Processor activePriority-1.
+ 	"wait until p entered the critical section"
+ 	[p suspendingList == s] whileFalse: [(Delay forMilliseconds: 10) wait].
+ 	"Now that p entered it, signal the semaphore. p now 'owns' the semaphore
+ 	but since we are running at higher priority than p it will not get to do
+ 	anything."
+ 	s signal.
+ 	p terminate.
+ 	self assert: 1 equals: s excessSignals.
+ 	self deny: beenHere!

Item was added:
+ ----- Method: SemaphoreTest>>testSemaAfterCriticalWaitInEnsure (in category 'tests') -----
+ testSemaAfterCriticalWaitInEnsure
+ 	"This tests whether a process that has just left the wait in Semaphore>>critical:
+ 	leaves it with signaling the associated semaphore."
+ 	| s p |
+ 	s := Semaphore new.
+ 	p := [[] ensure: [s critical:[]]] forkAt: Processor activePriority-1.
+ 	"wait until p entered the critical section"
+ 	[p suspendingList == s] whileFalse: [(Delay forMilliseconds: 10) wait].
+ 	"Now that p entered it, signal the semaphore. p now 'owns' the semaphore
+ 	but since we are running at higher priority than p it will not get to do
+ 	anything."
+ 	s signal.
+ 	p terminate.
+ 	self assert: 1 equals: s excessSignals!

Item was added:
+ ----- Method: SemaphoreTest>>testSemaAfterCriticalWaitInEnsure2 (in category 'tests') -----
+ testSemaAfterCriticalWaitInEnsure2
+ 	"This tests whether a process that has just left the wait in Semaphore>>critical:
+ 	leaves it with signaling the associated semaphore."
+ 	| s p beenHere |
+ 	s := Semaphore new. beenHere := false.
+ 	p := [[] ensure: [s critical: [beenHere := true]]] forkAt: Processor activePriority-1.
+ 	"wait until p entered the critical section"
+ 	[p suspendingList == s] whileFalse: [(Delay forMilliseconds: 10) wait].
+ 	"Now that p entered it, signal the semaphore. p now 'owns' the semaphore
+ 	but since we are running at higher priority than p it will not get to do
+ 	anything."
+ 	s signal.
+ 	p terminate.
+ 	self assert: 1 equals: s excessSignals.
+ 	self assert: beenHere!

Item was added:
+ ----- Method: SemaphoreTest>>testSemaInCriticalWait2 (in category 'tests') -----
+ testSemaInCriticalWait2
+ 	"This tests whether a process that has entered the wait in Semaphore>>critical:
+ 	leaves it without signaling the associated semaphore."
+ 	| s p beenHere |
+ 	s := Semaphore new. beenHere := false.
+ 	p := [s critical: [beenHere := true]] fork.
+ 	Processor yield.
+ 	self assert: s equals: p suspendingList.
+ 	p terminate.
+ 	self assert: 0 equals: s excessSignals.
+ 	self deny: beenHere!

Item was added:
+ ----- Method: SemaphoreTest>>testSemaInCriticalWaitInEnsure (in category 'tests') -----
+ testSemaInCriticalWaitInEnsure
+ 	"This tests whether a process that has entered the wait in Semaphore>>critical:
+ 	leaves it without signaling the associated semaphore."
+ 	| s p |
+ 	s := Semaphore new.
+ 	p := [[] ensure: [s critical: []]] fork.
+ 	Processor yield.
+ 	self assert: s equals: p suspendingList.
+ 	p terminate.
+ 	self assert: 0 equals: s excessSignals!

Item was added:
+ ----- Method: SemaphoreTest>>testSemaInCriticalWaitInEnsure2 (in category 'tests') -----
+ testSemaInCriticalWaitInEnsure2
+ 	"This tests whether a process that has entered the wait in Semaphore>>critical:
+ 	leaves it without signaling the associated semaphore."
+ 	| s p beenHere |
+ 	s := Semaphore new. beenHere := false.
+ 	p := [[] ensure: [s critical: [beenHere := true]]] fork.
+ 	Processor yield.
+ 	self assert: s equals: p suspendingList.
+ 	p terminate.
+ 	self assert: 0 equals: s excessSignals.
+ 	self deny: beenHere!

Item was removed:
- ----- Method: SemaphoreTest>>testUnwindSemaInCriticalWait (in category 'tests') -----
- testUnwindSemaInCriticalWait	"self run: #testSemaInCriticalWait"
- 	"This tests whether a semaphore that has entered the wait in Semaphore>>critical:
- 	leaves it without signaling the associated semaphore."
- 	| s p |
- 	s := Semaphore new.
- 	p := [[] ensure: [s critical:[]]] fork.
- 	Processor yield.
- 	self assert:(p suspendingList == s).
- 	p terminate.
- 	self assert: 0 equals: s excessSignals!



More information about the Squeak-dev mailing list