#REFACTORING by stefan
authorStefan Vogel <sv@exept.de>
Mon, 24 Jul 2017 12:02:53 +0200
changeset 22077 f0e611b43114
parent 22076 a0ca167d3248
child 22078 24f52f37b7c0
#REFACTORING by stefan Class: RecursionLock Make RecursionLock a subclass of Semaphore. Fix a possivle race condition. The changes in Semaphore 1.111, ProcessorScheduler 1.365 and RecursionLock 1.51 depend on each other.
RecursionLock.st
--- a/RecursionLock.st	Mon Jul 24 12:02:31 2017 +0200
+++ b/RecursionLock.st	Mon Jul 24 12:02:53 2017 +0200
@@ -13,8 +13,8 @@
 
 "{ NameSpace: Smalltalk }"
 
-Object subclass:#RecursionLock
-	instanceVariableNames:'process sema'
+Semaphore subclass:#RecursionLock
+	instanceVariableNames:'process'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Kernel-Processes'
@@ -41,7 +41,7 @@
 "
     like a Semaphore for mutual exclusion, but avoids the deadlock
     if a critical region is reentered by the same process again.
-    I.e. allows reentering the critical region IFF the current process 
+    I.e. allows reentering the critical region IFF the current process
     is the one which did the original locking.
 
     WARNING:
@@ -93,78 +93,52 @@
 
 !RecursionLock class methodsFor:'instance creation'!
 
-forMutualExclusion
-    "same as new, for easy exchangability with regular mutual-exclusion Semaphores."
+new
+    ^ self basicNew setCount:1
 
-    ^ self new 
+    "Modified: / 20-02-2017 / 16:32:11 / stefan"
 !
 
-new
-    ^ self basicNew initialize
+new:n
+    ^ self shouldNotImplement
 
+    "Created: / 20-02-2017 / 15:55:38 / stefan"
 ! !
 
-!RecursionLock methodsFor:'printing & storing'!
+!RecursionLock methodsFor:'not implemented'!
 
-displayOn:aGCOrStream
-    "return a string to display the receiver - include the
-     count for your convenience"
+signalForAll
+    ^ self shouldNotImplement
 
-    "/ what a kludge - Dolphin and Squeak mean: printOn: a stream;
-    "/ old ST80 means: draw-yourself on a GC.
-    (aGCOrStream isStream) ifFalse:[
-        ^ super displayOn:aGCOrStream
-    ].
-    
-    aGCOrStream
-        nextPutAll:self class name;
-        nextPut:$(.
-    sema count printOn:aGCOrStream.
-    aGCOrStream nextPutAll:' name: '.
-    (self name ? 'unnamed') printOn:aGCOrStream.
-    aGCOrStream nextPut:$).
+    "Created: / 20-02-2017 / 16:05:15 / stefan"
+!
 
-    "Modified (format): / 22-02-2017 / 17:04:21 / cg"
+signalIf
+    ^ self shouldNotImplement
+
+    "Created: / 20-02-2017 / 16:05:19 / stefan"
 !
 
-name
-    "return the semaphore's userFriendly name"
+signalOnce
+    ^ self shouldNotImplement
 
-    ^ sema name
-
-    "Created: / 28-06-1997 / 16:19:40 / cg"
-    "Modified: / 14-12-1999 / 21:03:46 / cg"
-    "Modified (comment): / 23-02-2017 / 16:48:49 / cg"
+    "Created: / 20-02-2017 / 16:05:25 / stefan"
 !
 
-name:aString
-    "set the semaphore's userFriendly name"
-
-    sema name:aString
+waitUncounted
+    ^ self shouldNotImplement
 
-    "Created: / 28-06-1997 / 16:19:47 / cg"
-    "Modified: / 14-12-1999 / 21:03:52 / cg"
-    "Modified (comment): / 23-02-2017 / 16:48:53 / cg"
-! !
+    "Created: / 20-02-2017 / 16:02:50 / stefan"
+!
 
-!RecursionLock methodsFor:'private-initialization'!
+waitUncountedWithTimeoutMs:milliSeconds
+    ^ self shouldNotImplement
 
-initialize
-    sema := Semaphore forMutualExclusion name:'recursionLock'
-
-    "Modified: 25.1.1997 / 00:19:15 / cg"
+    "Created: / 20-02-2017 / 16:04:31 / stefan"
 ! !
 
 !RecursionLock methodsFor:'queries'!
 
-numberOfWaitingProcesses
-    "return the number of waiting processes"
-
-    ^ sema numberOfWaitingProcesses
-
-    "Created: 18.4.1996 / 17:18:08 / cg"
-!
-
 owner
     "return the owning processes (or nil)"
 
@@ -172,13 +146,13 @@
 !
 
 wouldBlock
-    "Check if the resource represented by the receiver is  
+    "Check if the resource represented by the receiver is
      already in use by another process.
      Attention: if asked without some global lock (blockedInterrupts),
      the returned value may be outdated right away."
 
     |p|
-    
+
     ^ (p := process) notNil and:[Processor activeProcess ~~ p and:[p isDead not]]
 ! !
 
@@ -188,13 +162,15 @@
     |wasBlocked|
 
     process ~~ Processor activeProcess ifTrue:[
-        self error:'RecursionLock - signaling process doesn''t own the lock'.
+	self error:'RecursionLock - signaling process doesn''t own the lock'.
     ].
 
     wasBlocked := OperatingSystem blockInterrupts.
     process := nil.
-    sema signal.
+    super signal.
     wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+
+    "Modified: / 18-02-2017 / 21:44:40 / stefan"
 ! !
 
 !RecursionLock methodsFor:'waiting'!
@@ -227,46 +203,48 @@
     "/                 sema wait !!!!!! DEADLOCK
     "/
     wasBlocked := OperatingSystem blockInterrupts.
-    retVal :=  [
-                    (process notNil and:[process isDead]) ifTrue:[
-                        process := nil. 
-                        "#signal must be in the #ifCurtailed protected block - #signal may reschedule"
-                        sema signal.
-                        'RecursionLock [warning]: cleanup lock from dead process' infoPrintCR.
+    count > 0 ifTrue:[
+        "can get it fast, without waiting"
+        count := count - 1.
+        process := active.
+        count == 0 ifTrue:[
+            lastOwnerId := Processor activeProcessId.
+        ].
+        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+        retVal := aBlock ifCurtailed:[self signal].
+    ] ifFalse:[
+        "we have to wait..."
+        retVal :=  [
+                        (process notNil and:[process isDead]) ifTrue:[
+                            "this is in the #ifCurtailed protected block - #signal may reschedule"
+                            process := nil.
+                            super signal.
+                            'RecursionLock [warning]: cleanup lock from dead process' infoPrintCR.
+                        ].
+                        gotSema := super wait.
+                        process := active.
+                        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+                        aBlock value.
+                   ] ifCurtailed:[
+                        "be careful - the unwind may occur both while waiting
+                         AND while evaluating the block"
+                        gotSema notNil ifTrue:[
+                            self signal.
+                        ].
+                        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
                     ].
-                    gotSema := sema wait.
-                    process := active.
-                    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
-                    aBlock value.
-               ] ifCurtailed:[
-                    "be careful - the unwind may occur both while waiting
-                     AND while evaluating the block"
-                    gotSema notNil ifTrue:[
-                        OperatingSystem blockInterrupts.
-                        process := nil.
-                        sema signal.
-                    ].
-                    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
-                ].
-
+    ].
     OperatingSystem blockInterrupts.
     process := nil.
-    sema signal.
+    super signal.
     wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
     ^ retVal.
 
-    "Modified (comment): / 20-02-2017 / 15:35:41 / stefan"
-!
-
-critical:aBlock ifBlocking:blockingBlock
-    "like critical:, but do not block if the lock cannot be acquired.
-     Instead, return the value of the second argument, blockingBlock."
-
-    ^ self critical:aBlock timeoutMs:0 ifBlocking:blockingBlock.
+    "Modified: / 27-02-2017 / 20:43:19 / stefan"
 !
 
 critical:aBlock timeoutMs:timeoutMs ifBlocking:blockingBlock
-    "like critical:, but do not block if the lock cannot be acquired 
+    "like critical:, but do not block if the lock cannot be acquired
      within timeoutMs milliseconds.
      Instead, return the value of blockingBlock."
 
@@ -294,48 +272,63 @@
     "/                 sema wait !!!!!! DEADLOCK
     "/
     wasBlocked := OperatingSystem blockInterrupts.
-    retVal :=  [
-                    (process notNil and:[process isDead]) ifTrue:[
-                        process := nil. 
-                        "signal must be in the #ifCurtailed protected block - #signal may reschedule"
-                        sema signal.
-                        'RecursionLock [warning]: cleanup lock from dead process' infoPrintCR.
-                    ].
-                    gotSema := sema waitWithTimeoutMs:timeoutMs.
-                    gotSema notNil ifTrue:[
-                        process := active.
-                        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
-                        aBlock value.
-                    ].
-               ] ifCurtailed:[
-                    "be careful - the unwind may occur both while waiting
-                     AND while evaluating the block"
-                    gotSema notNil ifTrue:[
-                        OperatingSystem blockInterrupts.
-                        process := nil.
-                        sema signal.
-                    ].
-                    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
-               ].
+    count > 0 ifTrue:[
+        "can get it fast, without waiting"
+        count := count - 1.
+        process := active.
+        count == 0 ifTrue:[
+            lastOwnerId := Processor activeProcessId.
+        ].
+        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+
+        retVal := aBlock ifCurtailed:[self signal].
+
+        OperatingSystem blockInterrupts.
+        process := nil.
+        super signal.
+        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+        ^ retVal.
+    ]. 
+
+    "if we come here, we have to wait"
+    retVal := [
+        (process notNil and:[process isDead]) ifTrue:[
+            process := nil.
+            "this is in the #ifCurtailed protected block - #signal may reschedule"
+            super signal.
+            'RecursionLock [warning]: cleanup lock from dead process' infoPrintCR.
+        ].
+        gotSema := super waitWithTimeoutMs:timeoutMs.
+        gotSema notNil ifTrue:[
+            process := active.
+            wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+            aBlock value.
+        ].
+    ] ifCurtailed:[
+        "be careful - the unwind may occur both while waiting
+         AND while evaluating the block"
+        gotSema notNil ifTrue:[
+            self signal.
+        ].
+        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+    ].
 
     gotSema notNil ifTrue:[
         OperatingSystem blockInterrupts.
         process := nil.
-        sema signal.
+        super signal.
         wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
     ] ifFalse:[
         wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
         retVal := blockingBlock value.
     ].
-
     ^ retVal.
 
-    "Modified (comment): / 20-02-2017 / 15:37:18 / stefan"
+    "Modified (comment): / 22-02-2017 / 15:35:25 / stefan"
 !
 
 wait
-    "wait, but do not block,
-     if this lock is already held by the current process.
+    "wait, but do not block, if this lock is already held by the current process.
      Answer false, if already locked, true if lock has been just acquired."
 
     |active wasBlocked|
@@ -349,14 +342,46 @@
     wasBlocked := OperatingSystem blockInterrupts.
     (process notNil and:[process isDead]) ifTrue:[
         "/ a process which had the lock died without a chance to release it (i.e. it was hard terminated)
-        process := nil. 
+        process := nil.
+        super signal.
         'RecursionLock [info]: cleanup leftover lock from dead process' infoPrintCR.
-        sema signal.
     ].
-    sema wait.
+    super wait.
     process := active.
     wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
     ^ true.
+
+    "Modified: / 18-02-2017 / 21:48:36 / stefan"
+    "Modified (comment): / 20-02-2017 / 15:48:25 / stefan"
+!
+
+waitWithTimeoutMs:milliSeconds
+    "wait, but do not block, if this lock is already held by the current process.
+     Answer false, if already locked, true if lock has been just acquired,
+     nil if the lock could not be acquired in time."
+
+    |active wasBlocked gotSema|
+
+    active := Processor activeProcess.
+    process == active ifTrue:[
+        "I have already got the lock"
+        ^ false.
+    ].
+
+    wasBlocked := OperatingSystem blockInterrupts.
+    (process notNil and:[process isDead]) ifTrue:[
+        "/ a process which had the lock died without a chance to release it (i.e. it was hard terminated)
+        process := nil.
+        super signal.
+        'RecursionLock [info]: cleanup leftover lock from dead process' infoPrintCR.
+    ].
+    gotSema := super waitWithTimeoutMs:milliSeconds.
+    gotSema notNil ifTrue:[
+        gotSema := true.
+        process := active.
+    ].
+    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+    ^ gotSema.
 ! !
 
 !RecursionLock class methodsFor:'documentation'!