Semaphore.st
changeset 16625 09b045c29e25
parent 16286 4fd3aa76f29e
child 16631 ba77908696d0
--- a/Semaphore.st	Tue Jun 24 19:08:02 2014 +0200
+++ b/Semaphore.st	Tue Jun 24 19:10:33 2014 +0200
@@ -12,7 +12,7 @@
 "{ Package: 'stx:libbasic' }"
 
 Object subclass:#Semaphore
-	instanceVariableNames:'count waitingProcesses lastOwner name'
+	instanceVariableNames:'count waitingProcesses lastOwnerId name'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Kernel-Processes'
@@ -39,7 +39,7 @@
     Semaphores are used to synchronize processes providing a nonBusy wait
     mechanism. A process can wait for the availability of some resource by
     performing a Semaphore>>wait, which will suspend the process until the
-    resource becomes available. Signalling is done by (another process performing) 
+    resource becomes available. Signalling is done by (another process performing)
     Semaphore>>signal.
     If the resource has been already available before the wait, no suspending is
     done, but the resource immediately allocated.
@@ -48,214 +48,214 @@
     can be waited-upon that many times without blocking.
     On the other hand, if initialized with a negative count, the semaphore
     must be signalled that many times more often in order for a wait to not block.
-    In other words: whenever the semaphore has a count greater than zero, 
+    In other words: whenever the semaphore has a count greater than zero,
     the wait operation will proceed. Otherwise, it will block until the count has
     been incremented by signal operations to be greater than zero.
 
     There are also semaphores for mutual access to a critical region
     (Semaphore>>forMutualExclusion and Semaphore>>critical:).
 
-    Additional protocol is provided for oneShot semaphores, 
+    Additional protocol is provided for oneShot semaphores,
     (#signalOnce) and for conditional signalling (#signalIf).
 
     You can also attach semaphores to external events (such as I/O arrival or
-    timer events). 
-    This is done by telling the Processor to signal the semaphore 
+    timer events).
+    This is done by telling the Processor to signal the semaphore
     under some condition.
     See 'Processor>>signal:afterSeconds:', 'Processor>>signal:onInput:' etc.
 
     See examples in doc/coding (found in the CodingExamples-nameSpace).
 
     Warning/Note/Hint:
-        a Semaphore-forMutualExclusion does NEVER allow for the critical
-        region to be entered twice - NOT EVEN by the same process.
-        That means, that a recursive attempt to enter that section leads
-        to a deadlock.
-        Use a RecursionLock instead, to avoid this.
+	a Semaphore-forMutualExclusion does NEVER allow for the critical
+	region to be entered twice - NOT EVEN by the same process.
+	That means, that a recursive attempt to enter that section leads
+	to a deadlock.
+	Use a RecursionLock instead, to avoid this.
 
     Hint:
-        now (Jul2002), Semaphores now allow for a negative count; this allows for
-        a sync-point to be implemented easily (i.e. to wait for multiple other processes
-        to arrive at a sync-point).
-        See examples.
+	now (Jul2002), Semaphores now allow for a negative count; this allows for
+	a sync-point to be implemented easily (i.e. to wait for multiple other processes
+	to arrive at a sync-point).
+	See examples.
 
 
     [instance variables:]
-        count                   <SmallInteger>          the number of waits, that will go through
-                                                        without blocking.
-                                                        Incremented on #signal; decremented on #wait.
+	count                   <SmallInteger>          the number of waits, that will go through
+							without blocking.
+							Incremented on #signal; decremented on #wait.
 
-        waitingProcesses        <OrderedCollection>     waiting processes - will be served first
-                                                        come first served when signalled.
+	waitingProcesses        <OrderedCollection>     waiting processes - will be served first
+							come first served when signalled.
 
-        lastOwnerID             <SmallInteger>          a debugging aid: set when count drops
-                                                        to zero to the current processes id.
-                                                        Helps in finding deadlocks.
+	lastOwnerId             <SmallInteger>          a debugging aid: set when count drops
+							to zero to the current processes id.
+							Helps in finding deadlocks.
 
-        name                    <String>                a debugging aid: an optional userFriendly
-                                                        name; helps to identify a semaphore easier.
+	name                    <String>                a debugging aid: an optional userFriendly
+							name; helps to identify a semaphore easier.
 
     [see also:]
-        SemaphoreSet RecursionLock Monitor
-        SharedQueue Delay 
-        Process ProcessorScheduler
+	SemaphoreSet RecursionLock Monitor
+	SharedQueue Delay
+	Process ProcessorScheduler
 
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 "
 !
 
 examples
 "
     two processes synchronizing on a sema:
-                                                        [exBegin]
-        |sema thread1 thread2|
+							[exBegin]
+	|sema thread1 thread2|
 
-        sema := Semaphore new.
+	sema := Semaphore new.
 
-        thread1 := [
-                        Transcript showCR:'here is thread 1; now waiting ...'.
-                        sema wait.
-                        Transcript showCR:'here is thread 1 again.'.
-                   ] newProcess.
+	thread1 := [
+			Transcript showCR:'here is thread 1; now waiting ...'.
+			sema wait.
+			Transcript showCR:'here is thread 1 again.'.
+		   ] newProcess.
 
-        thread2 := [
-                        Transcript showCR:'here is thread 2; delaying a bit ...'.
-                        Delay waitForSeconds:5.
-                        Transcript showCR:'here is thread 2 again; now signalling the sema'.
-                        sema signal.
-                        Transcript showCR:'here is thread 2 after the signalling.'.
-                  ] newProcess.
+	thread2 := [
+			Transcript showCR:'here is thread 2; delaying a bit ...'.
+			Delay waitForSeconds:5.
+			Transcript showCR:'here is thread 2 again; now signalling the sema'.
+			sema signal.
+			Transcript showCR:'here is thread 2 after the signalling.'.
+		  ] newProcess.
 
-        thread1 priority:7.
-        thread2 priority:6.
+	thread1 priority:7.
+	thread2 priority:6.
 
-        thread1 resume.
-        thread2 resume.
-                                                        [exEnd]
+	thread1 resume.
+	thread2 resume.
+							[exEnd]
 
     semaphore for critical regions:
-                                                        [exBegin]
-        |accessLock|
+							[exBegin]
+	|accessLock|
 
-        accessLock := Semaphore forMutualExclusion.
+	accessLock := Semaphore forMutualExclusion.
 
-        [
-            5 timesRepeat:[
-                Delay waitForSeconds:2.
-                accessLock critical:[
-                    Transcript showCR:'thread1 in critical region'.
-                    Delay waitForSeconds:1.
-                    Transcript showCR:'thread1 leaving critical region'.
-                ].
-            ]
-        ] forkAt:5.
+	[
+	    5 timesRepeat:[
+		Delay waitForSeconds:2.
+		accessLock critical:[
+		    Transcript showCR:'thread1 in critical region'.
+		    Delay waitForSeconds:1.
+		    Transcript showCR:'thread1 leaving critical region'.
+		].
+	    ]
+	] forkAt:5.
 
-        [
-            5 timesRepeat:[
-                Delay waitForSeconds:1.
-                accessLock critical:[
-                    Transcript showCR:'thread2 in critical region'.
-                    Delay waitForSeconds:2.
-                    Transcript showCR:'thread2 leaving critical region'.
-                ].
-            ]
-        ] forkAt:4.
-                                                        [exEnd]
+	[
+	    5 timesRepeat:[
+		Delay waitForSeconds:1.
+		accessLock critical:[
+		    Transcript showCR:'thread2 in critical region'.
+		    Delay waitForSeconds:2.
+		    Transcript showCR:'thread2 leaving critical region'.
+		].
+	    ]
+	] forkAt:4.
+							[exEnd]
 
     a deadlock due to recursive enter of a critical region:
-                                                        [exBegin]
-        |accessLock block|
+							[exBegin]
+	|accessLock block|
 
-        accessLock := Semaphore forMutualExclusion.
+	accessLock := Semaphore forMutualExclusion.
 
-        block := [:arg |
-                    Transcript showCR:'about to enter'.
-                    accessLock critical:[
-                        Transcript showCR:'entered - doing action'.
-                        arg value
-                    ].
-                    Transcript showCR:'left region'.
-                 ].
+	block := [:arg |
+		    Transcript showCR:'about to enter'.
+		    accessLock critical:[
+			Transcript showCR:'entered - doing action'.
+			arg value
+		    ].
+		    Transcript showCR:'left region'.
+		 ].
 
-        block value:[].                 'this works'.
-        block value:[block value:[] ].  'this deadlocks'.
-                                                        [exEnd]
+	block value:[].                 'this works'.
+	block value:[block value:[] ].  'this deadlocks'.
+							[exEnd]
 
     Avoid the deadlock by using a RecursionLock instead:
-                                                        [exBegin]
-        |accessLock block|
+							[exBegin]
+	|accessLock block|
 
-        accessLock := RecursionLock new.
+	accessLock := RecursionLock new.
 
-        block := [:arg |
-                    Transcript showCR:'about to enter'.
-                    accessLock critical:[
-                        Transcript showCR:'entered - doing action'.
-                        arg value
-                    ].
-                    Transcript showCR:'left region'.
-                 ].
+	block := [:arg |
+		    Transcript showCR:'about to enter'.
+		    accessLock critical:[
+			Transcript showCR:'entered - doing action'.
+			arg value
+		    ].
+		    Transcript showCR:'left region'.
+		 ].
 
-        block value:[].                 'this works'.
-        block value:[block value:[] ].  'this deadlocks'.
-                                                        [exEnd]
+	block value:[].                 'this works'.
+	block value:[block value:[] ].  'this deadlocks'.
+							[exEnd]
 
 
    Wait for multiple processes to arrive at a sync-point:
-                                                        [exBegin]
-        |syncSema proceedSema thread1 thread2 thread3|
+							[exBegin]
+	|syncSema proceedSema thread1 thread2 thread3|
 
-        syncSema := Semaphore new.
-        syncSema setCount:(1-3).
-        proceedSema := Semaphore new.
+	syncSema := Semaphore new.
+	syncSema setCount:(1-3).
+	proceedSema := Semaphore new.
 
-        thread1 := [
-                        Transcript showCR:'here is thread 1; now busy ...'.
-                        Delay waitForSeconds:(2 + (Random nextIntegerBetween:2 and:4)).
-                        Transcript showCR:'here is thread 1 again - now syncing.'.
-                        syncSema signal.
-                        Transcript showCR:'thread 1 is waiting for all others...'.
-                        proceedSema wait.
-                        Transcript showCR:'thread 1 done.'.
-                   ] newProcess.
+	thread1 := [
+			Transcript showCR:'here is thread 1; now busy ...'.
+			Delay waitForSeconds:(2 + (Random nextIntegerBetween:2 and:4)).
+			Transcript showCR:'here is thread 1 again - now syncing.'.
+			syncSema signal.
+			Transcript showCR:'thread 1 is waiting for all others...'.
+			proceedSema wait.
+			Transcript showCR:'thread 1 done.'.
+		   ] newProcess.
 
-        thread2 := [
-                        Transcript showCR:'here is thread 2; now busy ...'.
-                        Delay waitForSeconds:(3 + (Random nextIntegerBetween:2 and:4)).
-                        Transcript showCR:'here is thread 2 again - now syncing.'.
-                        syncSema signal.
-                        Transcript showCR:'thread 2 is waiting for all others...'.
-                        proceedSema wait.
-                        Transcript showCR:'thread 2 done.'.
-                  ] newProcess.
+	thread2 := [
+			Transcript showCR:'here is thread 2; now busy ...'.
+			Delay waitForSeconds:(3 + (Random nextIntegerBetween:2 and:4)).
+			Transcript showCR:'here is thread 2 again - now syncing.'.
+			syncSema signal.
+			Transcript showCR:'thread 2 is waiting for all others...'.
+			proceedSema wait.
+			Transcript showCR:'thread 2 done.'.
+		  ] newProcess.
 
-        thread3 := [
-                        Transcript showCR:'here is thread 3; now busy ...'.
-                        Delay waitForSeconds:(4 + (Random nextIntegerBetween:2 and:4)).
-                        Transcript showCR:'here is thread 3 again - now syncing.'.
-                        syncSema signal.
-                        Transcript showCR:'thread 3 is waiting for all others...'.
-                        proceedSema wait.
-                        Transcript showCR:'thread 3 done.'.
-                  ] newProcess.
+	thread3 := [
+			Transcript showCR:'here is thread 3; now busy ...'.
+			Delay waitForSeconds:(4 + (Random nextIntegerBetween:2 and:4)).
+			Transcript showCR:'here is thread 3 again - now syncing.'.
+			syncSema signal.
+			Transcript showCR:'thread 3 is waiting for all others...'.
+			proceedSema wait.
+			Transcript showCR:'thread 3 done.'.
+		  ] newProcess.
 
-        thread1 priority:7.
-        thread2 priority:6.
-        thread3 priority:9.
+	thread1 priority:7.
+	thread2 priority:6.
+	thread3 priority:9.
 
-        thread1 resume.
-        thread2 resume.
-        thread3 resume.
+	thread1 resume.
+	thread2 resume.
+	thread3 resume.
 
-        Transcript showCR:'main thread: now waiting for other threads...'.
-        syncSema wait.
-        Transcript showCR:'main thread: all other threads at syncPoint.'.
-        Delay waitForSeconds:2.
-        Transcript showCR:'main thread: now let them proceed...'.
-        proceedSema signalForAll.
-        Transcript showCR:'main thread: done.'.
-                                                        [exEnd]
+	Transcript showCR:'main thread: now waiting for other threads...'.
+	syncSema wait.
+	Transcript showCR:'main thread: all other threads at syncPoint.'.
+	Delay waitForSeconds:2.
+	Transcript showCR:'main thread: now let them proceed...'.
+	proceedSema signalForAll.
+	Transcript showCR:'main thread: done.'.
+							[exEnd]
 
    waitWithTimeout:0 can also be used to conditionally aquire the semaphore
    i.e. only aquire it if its available.
@@ -263,24 +263,24 @@
 
      s := Semaphore new.
      [
-          (s waitWithTimeout:0) notNil ifTrue:[
-                Transcript showCR:'process1 got the sema'.
-                Delay waitForSeconds:1.
-                Transcript showCR:'process1 signals sema'.
-                s signal.
-          ] ifFalse:[
-                Transcript showCR:'process1 has NOT got the sema'.
-          ].
+	  (s waitWithTimeout:0) notNil ifTrue:[
+		Transcript showCR:'process1 got the sema'.
+		Delay waitForSeconds:1.
+		Transcript showCR:'process1 signals sema'.
+		s signal.
+	  ] ifFalse:[
+		Transcript showCR:'process1 has NOT got the sema'.
+	  ].
      ] fork.
      [
-          (s waitWithTimeout:0) notNil ifTrue:[
-                Transcript showCR:'process2 got the sema'.
-                Delay waitForSeconds:1.
-                Transcript showCR:'process2 signals sema'.
-                s signal.
-          ] ifFalse:[
-                Transcript showCR:'process2 has NOT got the sema'.
-          ]
+	  (s waitWithTimeout:0) notNil ifTrue:[
+		Transcript showCR:'process2 got the sema'.
+		Delay waitForSeconds:1.
+		Transcript showCR:'process2 signals sema'.
+		s signal.
+	  ] ifFalse:[
+		Transcript showCR:'process2 has NOT got the sema'.
+	  ]
      ] fork.
      s signal.
      Delay waitForSeconds:0.5.
@@ -294,13 +294,15 @@
 
 cleanup
     "an emergency helper: manually signal all semaphores which were held by a now dead process.
-     Can only (;-?) happen, if a semaphore-holding process was hard terminated 
+     Can only (;-?) happen, if a semaphore-holding process was hard terminated
      (i.e. no ensure handling happened), and semas remain in a bad state."
 
     self allInstancesDo:[:sema |
-        (sema count == 0 
-        and:[sema lastOwner notNil
-        and:[sema lastOwner isDead]]) ifTrue:[
+        |lastOwner|
+
+        (sema count == 0
+         and:[(lastOwner := sema lastOwner) notNil
+         and:[lastOwner isDead]]) ifTrue:[
             sema signal
         ]
     ]
@@ -354,11 +356,11 @@
     "/ what a kludge - Dolphin and Squeak mean: printOn: a stream;
     "/ ST/X (and some old ST80's) mean: draw-yourself on a GC.
     (aGCOrStream isStream) ifFalse:[
-        ^ super displayOn:aGCOrStream
+	^ super displayOn:aGCOrStream
     ].
     aGCOrStream
-        nextPutAll:self class name;
-        nextPut:$(.
+	nextPutAll:self class name;
+	nextPut:$(.
     count printOn:aGCOrStream.
     aGCOrStream nextPutAll:' name: '.
     (name ? 'unnamed') printOn:aGCOrStream.
@@ -390,15 +392,15 @@
 
     "for now"
     waitingProcesses isNil ifTrue:[
-        waitingProcesses := Array with:aProcess
+	waitingProcesses := Array with:aProcess
     ] ifFalse:[
-        waitingProcesses isArray ifTrue:[
-            "add 2 to reserve space for additional waiters"
-            waitingProcesses := (OrderedCollection new:waitingProcesses size + 2) 
-                                    addAll:waitingProcesses; 
-                                    yourself.
-        ].
-        waitingProcesses add:aProcess.
+	waitingProcesses isArray ifTrue:[
+	    "add 2 to reserve space for additional waiters"
+	    waitingProcesses := (OrderedCollection new:waitingProcesses size + 2)
+				    addAll:waitingProcesses;
+				    yourself.
+	].
+	waitingProcesses add:aProcess.
     ].
 
 "/    "Sort, so that higher priority process are resumed first.
@@ -406,7 +408,7 @@
 "/
 "/    |priority insertIndex|
 "/
-"/    (waitingProcesses size == 0 
+"/    (waitingProcesses size == 0
 "/     or:[(priority := aProcess priority) <= waitingProcesses last priority]) ifTrue:[
 "/        waitingProcesses add:aProcess.
 "/        ^ self.
@@ -428,19 +430,19 @@
     nWaiting == 0 ifTrue:[^ self].
 
     nWaiting == 1 ifTrue:[
-        (waitingProcesses at:1) == aProcess ifTrue:[
-            waitingProcesses := nil.
-        ].
-        ^ self.
+	(waitingProcesses at:1) == aProcess ifTrue:[
+	    waitingProcesses := nil.
+	].
+	^ self.
     ].
     waitingProcesses removeIdentical:aProcess ifAbsent:[].
 !
 
 wakeupWaiters
     "remove all waiting processes from the list of waiting processes
-     and resume them. 
+     and resume them.
      NOTE: Must be called when known that waitingProcesses is nonNil and
-           also with blocked interrupts"
+	   also with blocked interrupts"
 
     |processes anyDead needsReschedule|
 
@@ -450,22 +452,22 @@
 
     needsReschedule := false.
     anyDead := false.
-    processes do:[:eachProcess | 
-        (Processor makeRunnable:eachProcess) ifTrue:[
-            needsReschedule := true.
-        ] ifFalse:[
-            "if process is nil or dead (or for other reasons) makeRunnable returns false.
-             So check here."
-            (eachProcess isNil or:[eachProcess isDead]) ifTrue:[
-                "printing to Transcript might not be a good idea while interrupts are blocked"
-                'Semaphore>>wakeupWaiters: removing a dead process: ' infoPrint. eachProcess infoPrintCR.
-                anyDead := true.
-            ].
-        ].
+    processes do:[:eachProcess |
+	(Processor makeRunnable:eachProcess) ifTrue:[
+	    needsReschedule := true.
+	] ifFalse:[
+	    "if process is nil or dead (or for other reasons) makeRunnable returns false.
+	     So check here."
+	    (eachProcess isNil or:[eachProcess isDead]) ifTrue:[
+		"printing to Transcript might not be a good idea while interrupts are blocked"
+		'Semaphore>>wakeupWaiters: removing a dead process: ' infoPrint. eachProcess infoPrintCR.
+		anyDead := true.
+	    ].
+	].
     ].
     anyDead ifTrue:[
-        "interrupts are already blocked by sender"
-        waitingProcesses := processes reject:[:p | p isNil or:[p isDead]]
+	"interrupts are already blocked by sender"
+	waitingProcesses := processes reject:[:p | p isNil or:[p isDead]]
     ].
 
     ^ needsReschedule.
@@ -514,7 +516,7 @@
      (the one which counted to zero).
      May be very useful in debugging deadLock situations"
 
-    ^ lastOwner
+    ^ Processor processWithId:lastOwnerId.
 
     "Created: / 11-08-2011 / 14:35:36 / cg"
 !
@@ -524,10 +526,7 @@
      (the one which counted to zero).
      May be very useful in debugging deadLock situations"
 
-    lastOwner notNil ifTrue:[
-        ^ lastOwner id
-    ].
-    ^ nil
+    ^ lastOwnerId
 
     "Created: / 24-01-1997 / 23:09:33 / cg"
 !
@@ -559,14 +558,14 @@
     "
 
     count > 0 ifTrue:[
-        count := count - 1.
-        count == 0 ifTrue:[
-            lastOwner := Processor activeProcess.
-        ].
-        ^ true
+	count := count - 1.
+	count == 0 ifTrue:[
+	    lastOwnerId := Processor activeProcessId.
+	].
+	^ true
     ].
     (waitingProcesses notNil and:[(waitingProcesses includesIdentical:process)]) ifFalse:[
-        self addWaitingProcess:process.
+	self addWaitingProcess:process.
     ].
     ^ false
 
@@ -585,16 +584,16 @@
     needsReschedule := false.
     wasBlocked := OperatingSystem blockInterrupts.
     [
-        count := count + 1.
-        waitingProcesses size ~~ 0 ifTrue:[
-            needsReschedule := self wakeupWaiters.
-        ].
+	count := count + 1.
+	waitingProcesses size ~~ 0 ifTrue:[
+	    needsReschedule := self wakeupWaiters.
+	].
     ] ensure:[
-        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+	wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
     ].
     needsReschedule ifTrue:[
-        "now, schedule the highest priority process"
-        Processor reschedule.
+	"now, schedule the highest priority process"
+	Processor reschedule.
     ].
 
     "Modified: / 4.2.1998 / 21:01:07 / cg"
@@ -608,23 +607,23 @@
     |wasBlocked needsReschedule|
 
     waitingProcesses size ~~ 0 ifTrue:[
-        needsReschedule := false.
-        wasBlocked := OperatingSystem blockInterrupts.
-        [
-            "first, make them all runnable, but do not schedule
-             (in case one has higher prio and goes into a wait immediately again.)"
-            waitingProcesses size ~~ 0 ifTrue:[
-                needsReschedule := self wakeupWaiters.
-                "wakeupWaites may have removed dead processes from waitingProcesses!!"
-                count := count + waitingProcesses size.
-            ].
-        ] ensure:[
-            wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
-        ].
-        needsReschedule ifTrue:[
-            "now, schedule the highest priority process"
-            Processor reschedule.
-        ].
+	needsReschedule := false.
+	wasBlocked := OperatingSystem blockInterrupts.
+	[
+	    "first, make them all runnable, but do not schedule
+	     (in case one has higher prio and goes into a wait immediately again.)"
+	    waitingProcesses size ~~ 0 ifTrue:[
+		needsReschedule := self wakeupWaiters.
+		"wakeupWaites may have removed dead processes from waitingProcesses!!"
+		count := count + waitingProcesses size.
+	    ].
+	] ensure:[
+	    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+	].
+	needsReschedule ifTrue:[
+	    "now, schedule the highest priority process"
+	    Processor reschedule.
+	].
     ]
 
     "Modified: / 5.2.1998 / 10:40:26 / cg"
@@ -638,14 +637,14 @@
     |wasBlocked|
 
     waitingProcesses notNil ifTrue:[
-        wasBlocked := OperatingSystem blockInterrupts.
-        [
-            waitingProcesses size ~~ 0 ifTrue:[
-                self signal
-            ].
-        ] ensure:[
-            wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
-        ]
+	wasBlocked := OperatingSystem blockInterrupts.
+	[
+	    waitingProcesses size ~~ 0 ifTrue:[
+		self signal
+	    ].
+	] ensure:[
+	    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+	]
     ]
 
     "Modified: 28.2.1996 / 21:23:57 / cg"
@@ -658,25 +657,25 @@
     |wasBlocked needsReschedule|
 
     count <= 0 ifTrue:[
-        needsReschedule := false.
-        wasBlocked := OperatingSystem blockInterrupts.
-        "/ check again - now interrupts are blocked.
-        [
-            count <= 0 ifTrue:[
-                count := count + 1.
-                count == 1 ifTrue:[
-                    waitingProcesses size ~~ 0 ifTrue:[
-                        needsReschedule := self wakeupWaiters.
-                    ].
-                ].
-            ].
-        ] ensure:[
-            wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
-        ].
-        needsReschedule ifTrue:[
-            "now, schedule the highest priority process"
-            Processor reschedule.
-        ].
+	needsReschedule := false.
+	wasBlocked := OperatingSystem blockInterrupts.
+	"/ check again - now interrupts are blocked.
+	[
+	    count <= 0 ifTrue:[
+		count := count + 1.
+		count == 1 ifTrue:[
+		    waitingProcesses size ~~ 0 ifTrue:[
+			needsReschedule := self wakeupWaiters.
+		    ].
+		].
+	    ].
+	] ensure:[
+	    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+	].
+	needsReschedule ifTrue:[
+	    "now, schedule the highest priority process"
+	    Processor reschedule.
+	].
     ].
 
     "Modified: 28.2.1996 / 21:24:08 / cg"
@@ -735,39 +734,39 @@
     "/ inlined common case - ugly kludge but helpful
     wasBlocked := OperatingSystem blockInterrupts.
     count > 0 ifTrue:[
-        count := count - 1.
-        count == 0 ifTrue:[
-            lastOwner := Processor activeProcess.
-        ].
-        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+	count := count - 1.
+	count == 0 ifTrue:[
+	    lastOwnerId := Processor activeProcessId.
+	].
+	wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
 
-        retVal := aBlock ifCurtailed:[ self signal ].
+	retVal := aBlock ifCurtailed:[ self signal ].
 
-        OperatingSystem blockInterrupts.
-        needsReschedule := false.
-        [
-            count := count + 1.
-            waitingProcesses size ~~ 0 ifTrue:[
-                needsReschedule := self wakeupWaiters.
-            ].
-        ] ensure:[
-            wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
-        ].
-        needsReschedule ifTrue:[
-            "now, schedule the highest priority process"
-            Processor reschedule.
-        ].
-        ^ retVal.
+	OperatingSystem blockInterrupts.
+	needsReschedule := false.
+	[
+	    count := count + 1.
+	    waitingProcesses size ~~ 0 ifTrue:[
+		needsReschedule := self wakeupWaiters.
+	    ].
+	] ensure:[
+	    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+	].
+	needsReschedule ifTrue:[
+	    "now, schedule the highest priority process"
+	    Processor reschedule.
+	].
+	^ retVal.
     ].
     wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
 
     [
-        gotSema := self wait.
-        retVal := aBlock value.
+	gotSema := self wait.
+	retVal := aBlock value.
     ] ifCurtailed:[
-        "/ be careful - the unwind may occur both while waiting
-        "/ AND while evaluating the block.
-        gotSema notNil ifTrue:[self signal].
+	"/ be careful - the unwind may occur both while waiting
+	"/ AND while evaluating the block.
+	gotSema notNil ifTrue:[self signal].
     ].
     self signal.
     ^ retVal
@@ -784,21 +783,21 @@
      coll := OrderedCollection new:10.
 
      [
-        1 to:1000 do:[:i |
-            sema critical:[
-                coll addLast:i.
-                (Delay forSeconds:0.1) wait.
-            ]
-        ]
+	1 to:1000 do:[:i |
+	    sema critical:[
+		coll addLast:i.
+		(Delay forSeconds:0.1) wait.
+	    ]
+	]
      ] forkAt:4.
 
      [
-        1 to:1000 do:[:i |
-            sema critical:[
-                coll removeFirst.
-                (Delay forSeconds:0.1) wait.
-            ]
-        ]
+	1 to:1000 do:[:i |
+	    sema critical:[
+		coll removeFirst.
+		(Delay forSeconds:0.1) wait.
+	    ]
+	]
      ] forkAt:4.
     "
 
@@ -814,37 +813,37 @@
     wasBlocked := OperatingSystem blockInterrupts.
 
     count <= 0 ifTrue:[
-        activeProcess := Processor activeProcess.
-        "
-         need a while-loop here, since more than one process may
-         wait for it and another one may also wake up.
-         Thus, the count is not always non-zero after returning from
-         suspend.
-        "
-        [
-            self addWaitingProcess:activeProcess.
-            "
-             for some more descriptive info in processMonitor ...
-             ... set the state to #wait (instead of #suspend)
-            "
-            [
-                activeProcess suspendWithState:#wait
-            ] ifCurtailed:[
-                "interrupts are not blocked when entered through Processor>>#interruptActive"
-                OperatingSystem blockInterrupts.
-                self removeWaitingProcess:activeProcess.
-                wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
-            ].
-            self removeWaitingProcess:activeProcess.
+	activeProcess := Processor activeProcess.
+	"
+	 need a while-loop here, since more than one process may
+	 wait for it and another one may also wake up.
+	 Thus, the count is not always non-zero after returning from
+	 suspend.
+	"
+	[
+	    self addWaitingProcess:activeProcess.
+	    "
+	     for some more descriptive info in processMonitor ...
+	     ... set the state to #wait (instead of #suspend)
+	    "
+	    [
+		activeProcess suspendWithState:#wait
+	    ] ifCurtailed:[
+		"interrupts are not blocked when entered through Processor>>#interruptActive"
+		OperatingSystem blockInterrupts.
+		self removeWaitingProcess:activeProcess.
+		wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+	    ].
+	    self removeWaitingProcess:activeProcess.
 
-            count <= 0
-        ] whileTrue.
+	    count <= 0
+	] whileTrue.
     ].
 
     count := count - 1.
     count == 0 ifTrue:[
-        activeProcess isNil ifTrue:[activeProcess := Processor activeProcess].
-        lastOwner := activeProcess.
+	activeProcess isNil ifTrue:[activeProcess := Processor activeProcess].
+	lastOwnerId := activeProcess id.
     ].
     wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
 
@@ -859,7 +858,7 @@
     |activeProcess wasBlocked|
 
     count > 0 ifTrue:[
-        ^ self
+	^ self
     ].
     activeProcess := Processor activeProcess.
 
@@ -871,20 +870,20 @@
      suspend.
     "
     [count <= 0] whileTrue:[
-        self addWaitingProcess:activeProcess.
-        "
-         for some more descriptive info in processMonitor ...
-         ... set the state to #wait (instead of #suspend)
-        "
-        [
-            activeProcess suspendWithState:#wait
-        ] ifCurtailed:[
-            "interrupts are not blocked when entered through Processor>>#interruptActive"
-            OperatingSystem blockInterrupts.
-            self removeWaitingProcess:activeProcess.
-            wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
-        ].
-        self removeWaitingProcess:activeProcess.
+	self addWaitingProcess:activeProcess.
+	"
+	 for some more descriptive info in processMonitor ...
+	 ... set the state to #wait (instead of #suspend)
+	"
+	[
+	    activeProcess suspendWithState:#wait
+	] ifCurtailed:[
+	    "interrupts are not blocked when entered through Processor>>#interruptActive"
+	    OperatingSystem blockInterrupts.
+	    self removeWaitingProcess:activeProcess.
+	    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+	].
+	self removeWaitingProcess:activeProcess.
     ].
     wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
 
@@ -895,7 +894,7 @@
 waitWithTimeout:seconds
     "wait for the semaphore, but abort the wait after some time (seconds).
      return the receiver if the semaphore triggered normal, nil if we return
-     due to a timeout. 
+     due to a timeout.
      The seconds-argument may be a float (i.e. use 0.1 for a 100ms timeout).
      With zero timeout, this can be used to poll a semaphore (returning
      the receiver if the semaphore is available, nil if not).
@@ -905,7 +904,7 @@
     |millis|
 
     seconds notNil ifTrue:[
-        millis := seconds * 1000 
+	millis := seconds * 1000
     ].
     ^ self waitWithTimeoutMs:millis.
 !
@@ -913,7 +912,7 @@
 waitWithTimeoutMs:milliSeconds
     "wait for the semaphore, but abort the wait after some time.
      return the receiver if the semaphore triggered normal, nil if we return
-     due to a timeout. 
+     due to a timeout.
      With zero timeout, this can be used to poll a semaphore (returning
      the receiver if the semaphore is available, nil if not).
      However, polling is not the intended use of semaphores, though.
@@ -924,75 +923,75 @@
     wasBlocked := OperatingSystem blockInterrupts.
 
     count <= 0 ifTrue:[
-        "with zero-timeout, this is a poll"
-        milliSeconds == 0 ifTrue:[
-            wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
-            ^ nil
-        ].
+	"with zero-timeout, this is a poll"
+	milliSeconds == 0 ifTrue:[
+	    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+	    ^ nil
+	].
 
-        activeProcess := Processor activeProcess.
-        timeoutOccured := false.
+	activeProcess := Processor activeProcess.
+	timeoutOccured := false.
 
-        milliSeconds notNil ifTrue:[
-            "Wait with timeout: calculate the end-time"
-            now := OperatingSystem getMillisecondTime.
-            endTime := OperatingSystem millisecondTimeAdd:now and:milliSeconds.
+	milliSeconds notNil ifTrue:[
+	    "Wait with timeout: calculate the end-time"
+	    now := OperatingSystem getMillisecondTime.
+	    endTime := OperatingSystem millisecondTimeAdd:now and:milliSeconds.
 
-            timeoutBlock := [
-                    timeoutOccured := true. 
-                    timeoutBlock:= nil. 
-                    Processor resume:activeProcess.
-                ].
-            Processor addTimedBlock:timeoutBlock for:activeProcess atMilliseconds:endTime.
-        ].
+	    timeoutBlock := [
+		    timeoutOccured := true.
+		    timeoutBlock:= nil.
+		    Processor resume:activeProcess.
+		].
+	    Processor addTimedBlock:timeoutBlock for:activeProcess atMilliseconds:endTime.
+	].
 
-        "
-         need a while-loop here, since more than one process may
-         wait for it and another one may also wake up.
-         Thus, the count is not always non-zero after returning from
-         suspend.
-        "
-        [
-            self addWaitingProcess:activeProcess.
+	"
+	 need a while-loop here, since more than one process may
+	 wait for it and another one may also wake up.
+	 Thus, the count is not always non-zero after returning from
+	 suspend.
+	"
+	[
+	    self addWaitingProcess:activeProcess.
 
-            "
-             for some more descriptive info in processMonitor ...
-             ... set the state to #wait (instead of #suspend)
-            "
-            [
-                "sleep until resumed..."
-                activeProcess suspendWithState:#wait.
-            ] ifCurtailed:[
-                "interrupts are not blocked when entered through Processor>>#interruptActive"
-                OperatingSystem blockInterrupts.
-                timeoutBlock notNil ifTrue:[
-                    Processor removeTimedBlock:timeoutBlock.
-                    timeoutBlock := nil.
-                ].
-                self removeWaitingProcess:activeProcess.
-                wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
-            ].
+	    "
+	     for some more descriptive info in processMonitor ...
+	     ... set the state to #wait (instead of #suspend)
+	    "
+	    [
+		"sleep until resumed..."
+		activeProcess suspendWithState:#wait.
+	    ] ifCurtailed:[
+		"interrupts are not blocked when entered through Processor>>#interruptActive"
+		OperatingSystem blockInterrupts.
+		timeoutBlock notNil ifTrue:[
+		    Processor removeTimedBlock:timeoutBlock.
+		    timeoutBlock := nil.
+		].
+		self removeWaitingProcess:activeProcess.
+		wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+	    ].
 
-            self removeWaitingProcess:activeProcess.
-            timeoutOccured ifTrue:[
-                wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
-                ^ nil
-            ].
+	    self removeWaitingProcess:activeProcess.
+	    timeoutOccured ifTrue:[
+		wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+		^ nil
+	    ].
 
-            count <= 0
-        ] whileTrue.
+	    count <= 0
+	] whileTrue.
 
-        timeoutBlock notNil ifTrue:[
-            Processor removeTimedBlock:timeoutBlock.
-            timeoutBlock := nil.
-        ].
+	timeoutBlock notNil ifTrue:[
+	    Processor removeTimedBlock:timeoutBlock.
+	    timeoutBlock := nil.
+	].
     ].
 
     "if we come here, we have acquired the semaphore"
     count := count - 1.
     count == 0 ifTrue:[
-        activeProcess isNil ifTrue:[activeProcess := Processor activeProcess].
-        lastOwner := activeProcess.
+	activeProcess isNil ifTrue:[activeProcess := Processor activeProcess].
+	lastOwnerId := activeProcess id.
     ].
     wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
     ^ self
@@ -1004,10 +1003,10 @@
 !Semaphore class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Semaphore.st,v 1.96 2014-03-28 13:39:32 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Semaphore.st,v 1.97 2014-06-24 17:10:33 stefan Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/Semaphore.st,v 1.96 2014-03-28 13:39:32 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Semaphore.st,v 1.97 2014-06-24 17:10:33 stefan Exp $'
 ! !